From git at git.haskell.org Mon Oct 2 11:27:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 11:27:25 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: includes/rts: Drop trailing comma (e84d76d) Message-ID: <20171002112725.91C3F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/e84d76d3258d754e757a19c6e830684887a18a0b/ghc >--------------------------------------------------------------- commit e84d76d3258d754e757a19c6e830684887a18a0b Author: Ben Gamari Date: Thu Sep 7 22:49:22 2017 -0400 includes/rts: Drop trailing comma This trailing comma snuck in in a recent patch. There is nothing wrong with the comma; it's perfectly valid C99, yet nevertheless Mac OS X's dtrace utility chokes on it with, dtrace: failed to compile script rts/RtsProbes.d: "includes/rts/EventLogFormat.h", line 245: syntax error near "}" make[1]: *** [rts/dist/build/RtsProbes.h] Error 1 (cherry picked from commit be514a694f2cddbb1b23af971430364a223eb894) >--------------------------------------------------------------- e84d76d3258d754e757a19c6e830684887a18a0b includes/rts/EventLogFormat.h | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/includes/rts/EventLogFormat.h b/includes/rts/EventLogFormat.h index f47e3ea..70c1c8d 100644 --- a/includes/rts/EventLogFormat.h +++ b/includes/rts/EventLogFormat.h @@ -240,7 +240,7 @@ typedef enum { HEAP_PROF_BREAKDOWN_TYPE_DESCR, HEAP_PROF_BREAKDOWN_RETAINER, HEAP_PROF_BREAKDOWN_BIOGRAPHY, - HEAP_PROF_BREAKDOWN_CLOSURE_TYPE, + HEAP_PROF_BREAKDOWN_CLOSURE_TYPE } HeapProfBreakdown; #if !defined(EVENTLOG_CONSTANTS_ONLY) From git at git.haskell.org Mon Oct 2 11:27:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 11:27:31 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Use libpthread instead of libthr on FreeBSD (fd201db) Message-ID: <20171002112731.265833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/fd201db6ed7a02474bfcfbfe6806d11926e29f9b/ghc >--------------------------------------------------------------- commit fd201db6ed7a02474bfcfbfe6806d11926e29f9b Author: Ben Gamari Date: Mon Jul 24 19:02:56 2017 -0400 Use libpthread instead of libthr on FreeBSD Since #847 we have used libthr due to reported hangs with FreeBSD's KSE-based M:N pthread implementation. However, this was nearly 12 years ago and today libpthread seems to work fine. Moreover, adding -lthr to the linker flags break when used in conjunction with -r when gold is used (since -l and -r are incompatible although BFD ld doesn't complain). Test Plan: Validate on FreeBSD Reviewers: kgardas, austin Subscribers: rwbarton, thomie GHC Trac Issues: #847 Differential Revision: https://phabricator.haskell.org/D3773 (cherry picked from commit d8051c6cf08f02331f98fed7d5e88a95bd76e534) >--------------------------------------------------------------- fd201db6ed7a02474bfcfbfe6806d11926e29f9b compiler/main/DynFlags.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 10bf671..1a7d3c7 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1436,11 +1436,7 @@ wayOptl :: Platform -> Way -> [String] wayOptl _ (WayCustom {}) = [] wayOptl platform WayThreaded = case platformOS platform of - -- FreeBSD's default threading library is the KSE-based M:N libpthread, - -- which GHC has some problems with. It's currently not clear whether - -- the problems are our fault or theirs, but it seems that using the - -- alternative 1:1 threading library libthr works around it: - OSFreeBSD -> ["-lthr"] + OSFreeBSD -> ["-pthread"] OSOpenBSD -> ["-pthread"] OSNetBSD -> ["-pthread"] _ -> [] From git at git.haskell.org Mon Oct 2 11:27:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 11:27:28 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: configure: Make sure we try all possible linkers (5bce35c) Message-ID: <20171002112728.655893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/5bce35caf1767b65fce32ca55b7036fbd0d546f7/ghc >--------------------------------------------------------------- commit 5bce35caf1767b65fce32ca55b7036fbd0d546f7 Author: Ben Gamari Date: Wed Sep 27 15:30:18 2017 -0400 configure: Make sure we try all possible linkers Previously if we had both ld.lld and ld.gold installed but a gcc which didn't support -fuse-ld=lld we would fail when trying ld.lld and fall immediately back to plain ld. Now we will try ld.gold as well. This was brought to light by #14280, where using ld.bfd resulted in a broken stage2 compiler. Test Plan: Configure Reviewers: angerman, hvr, austin Reviewed By: angerman Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #14280 Differential Revision: https://phabricator.haskell.org/D4038 (cherry picked from commit a10729f028d7175980d9f65e22c9bb9a933461c2) >--------------------------------------------------------------- 5bce35caf1767b65fce32ca55b7036fbd0d546f7 aclocal.m4 | 59 +++++++++++++++++++++++++++++++++++++++++------------------ 1 file changed, 41 insertions(+), 18 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 516584b..d5078de 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2340,28 +2340,51 @@ AC_DEFUN([FIND_LD],[ [], [enable_ld_override=yes]) - if test "x$enable_ld_override" = "xyes"; then - TmpLd="$LD" # In case the user set LD - AC_CHECK_TARGET_TOOLS([TmpLd], [ld.lld ld.gold ld]) - - out=`$TmpLd --version` - 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 '$TmpLd']) + find_ld() { + # Make sure the user didn't specify LD manually. + if test "z$LD" != "z"; then AC_CHECK_TARGET_TOOL([LD], [ld]) - else - LD="$TmpLd" + return fi - else + + # Manually iterate over possible names since we want to ensure that, e.g., + # if ld.lld is installed but gcc doesn't support -fuse-ld=lld, that we + # then still try ld.gold and -fuse-ld=gold. + for possible_ld in ld.lld ld.gold ld; do + TmpLd="" # In case the user set LD + AC_CHECK_TARGET_TOOL([TmpLd], [$possible_ld]) + if test "x$TmpLd" = "x"; then continue; fi + + out=`$TmpLd --version` + case $out in + "GNU ld"*) FP_CC_LINKER_FLAG_TRY(bfd, $2) ;; + "GNU gold"*) FP_CC_LINKER_FLAG_TRY(gold, $2) ;; + "LLD"*) FP_CC_LINKER_FLAG_TRY(lld, $2) ;; + *) AC_MSG_NOTICE([unknown linker version $out]) ;; + esac + if test "z$$2" = "z"; then + AC_MSG_NOTICE([unable to convince '$CC' to use linker '$TmpLd']) + # a terrible hack to prevent autoconf from caching the previous + # AC_CHECK_TARGET_TOOL result since next time we'll be looking + # for another ld variant. + $as_unset ac_cv_prog_ac_ct_TmpLd + else + LD="$TmpLd" + return + fi + done + + # Fallback AC_CHECK_TARGET_TOOL([LD], [ld]) - fi + } + + if test "x$enable_ld_override" = "xyes"; then + find_ld + else + AC_CHECK_TARGET_TOOL([LD], [ld]) + fi - CHECK_LD_COPY_BUG([$1]) + CHECK_LD_COPY_BUG([$1]) ]) # LocalWords: fi From git at git.haskell.org Mon Oct 2 13:35:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 13:35:59 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T14289' created Message-ID: <20171002133559.5098C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T14289 Referencing: 61c83ffaa3649b12dfe8e95aaee8959c20925fec From git at git.haskell.org Mon Oct 2 13:36:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 13:36:02 +0000 (UTC) Subject: [commit: ghc] wip/T14289: Pretty-printing of derived multi-parameter classes omits parentheses (61c83ff) Message-ID: <20171002133602.D5C243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14289 Link : http://ghc.haskell.org/trac/ghc/changeset/61c83ffaa3649b12dfe8e95aaee8959c20925fec/ghc >--------------------------------------------------------------- commit 61c83ffaa3649b12dfe8e95aaee8959c20925fec Author: Alan Zimmerman Date: Sun Oct 1 19:36:03 2017 +0200 Pretty-printing of derived multi-parameter classes omits parentheses Summary: Pretty printing a splice with an HsAppType in the deriving clause, such as $([d| data Foo a = Foo a deriving (C a) |]) would omit the parens. Test Plan: ./validate Reviewers: RyanGlScott, austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14289 Differential Revision: https://phabricator.haskell.org/D4056 >--------------------------------------------------------------- 61c83ffaa3649b12dfe8e95aaee8959c20925fec compiler/hsSyn/HsDecls.hs | 2 ++ testsuite/tests/parser/should_compile/all.T | 1 + testsuite/tests/printer/Makefile | 8 ++++++ testsuite/tests/printer/T14289.hs | 32 ++++++++++++++++++++++ testsuite/tests/printer/T14289.stdout | 16 +++++++++++ testsuite/tests/printer/T14289b.hs | 42 +++++++++++++++++++++++++++++ testsuite/tests/printer/T14289b.stdout | 1 + testsuite/tests/printer/all.T | 2 ++ 8 files changed, 104 insertions(+) diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/hsSyn/HsDecls.hs index ecb11a0..9b21913 100644 --- a/compiler/hsSyn/HsDecls.hs +++ b/compiler/hsSyn/HsDecls.hs @@ -1102,7 +1102,9 @@ instance (SourceTextX pass, OutputableBndrId pass) -- This complexity is to distinguish between -- deriving Show -- deriving (Show) + pp_dct [a@(HsIB { hsib_body = L _ HsAppTy{} })] = parens (ppr a) pp_dct [a@(HsIB { hsib_body = L _ HsAppsTy{} })] = parens (ppr a) + pp_dct [a@(HsIB { hsib_body = L _ HsOpTy{} })] = parens (ppr a) pp_dct [a] = ppr a pp_dct _ = parens (interpp'SP dct) diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T index c008bd4..48e2b80 100644 --- a/testsuite/tests/parser/should_compile/all.T +++ b/testsuite/tests/parser/should_compile/all.T @@ -109,3 +109,4 @@ test('DumpRenamedAst', normal, compile, ['-dsuppress-uniques -ddump-rn-ast'] test('DumpTypecheckedAst', normal, compile, ['-dsuppress-uniques -ddump-tc-ast']) test('T13747', normal, compile, ['']) test('T14189', normal, compile, ['-dsuppress-uniques -ddump-rn-ast']) +test('T14189tc', normal, compile, ['-dsuppress-uniques -ddump-tc-ast']) diff --git a/testsuite/tests/printer/Makefile b/testsuite/tests/printer/Makefile index 1c2f299..36aa050 100644 --- a/testsuite/tests/printer/Makefile +++ b/testsuite/tests/printer/Makefile @@ -213,3 +213,11 @@ T13550: .PHONY: T13942 T13942: $(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" T13942.hs + +.PHONY: T14289 +T14289: + $(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" T14289.hs + +.PHONY: T14289b +T14289b: + $(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" T14289b.hs diff --git a/testsuite/tests/printer/T14289.hs b/testsuite/tests/printer/T14289.hs new file mode 100644 index 0000000..04b9176 --- /dev/null +++ b/testsuite/tests/printer/T14289.hs @@ -0,0 +1,32 @@ +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TemplateHaskell #-} +{-# OPTIONS_GHC -ddump-splices -dsuppress-uniques #-} + +import Language.Haskell.TH + +class C a b + +$([d| data Foo a = Foo a deriving (C a) |]) + +{- + +Note: to debug + +~/inplace/bin/ghc-stage2 --interactive +load the following +---------------------------------------- +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TemplateHaskell #-} +{-# OPTIONS_GHC -ddump-splices -dsuppress-uniques #-} + +import Language.Haskell.TH + +class C a b + +main :: IO () +main = putStrLn $([d| data Foo a = Foo a deriving (C a) |] >>= stringE . show) + +---------------------------------------- + +-} diff --git a/testsuite/tests/printer/T14289.stdout b/testsuite/tests/printer/T14289.stdout new file mode 100644 index 0000000..3f0754a --- /dev/null +++ b/testsuite/tests/printer/T14289.stdout @@ -0,0 +1,16 @@ +T14289.hs:10:3-42: Splicing declarations + [d| data Foo a + = Foo a + deriving (C a) |] + ======> + data Foo a + = Foo a + deriving (C a) +T14289.ppr.hs:(7,3)-(9,25): Splicing declarations + [d| data Foo a + = Foo a + deriving (C a) |] + ======> + data Foo a + = Foo a + deriving (C a) diff --git a/testsuite/tests/printer/T14289b.hs b/testsuite/tests/printer/T14289b.hs new file mode 100644 index 0000000..3ff3980 --- /dev/null +++ b/testsuite/tests/printer/T14289b.hs @@ -0,0 +1,42 @@ +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeOperators #-} +{-# OPTIONS_GHC -ddump-splices -dsuppress-uniques #-} + +import Language.Haskell.TH + +class (a `C` b) c + +$([d| data Foo a = Foo a deriving (y `C` z) |]) + +{- + +Note: to debug + +~/inplace/bin/ghc-stage2 --interactive +load the following +---------------------------------------- +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TemplateHaskell #-} +{-# OPTIONS_GHC -ddump-splices -dsuppress-uniques #-} + +import Language.Haskell.TH + +class (a `C` b) c + +main :: IO () +main + = putStrLn $([d| data Foo a = Foo a deriving (y `C` z) |] >>= stringE . show) + +---------------------------------------- +Bceomes + + +[DataD [] Foo_0 [PlainTV a_2] Nothing + [NormalC Foo_1 [(Bang NoSourceUnpackedness NoSourceStrictness,VarT a_2)]] + [DerivClause Nothing + [AppT (AppT (ConT Main.C) (VarT y_6989586621679027885)) + (VarT z_6989586621679027886)]]] + +-} diff --git a/testsuite/tests/printer/T14289b.stdout b/testsuite/tests/printer/T14289b.stdout new file mode 100644 index 0000000..9f26b63 --- /dev/null +++ b/testsuite/tests/printer/T14289b.stdout @@ -0,0 +1 @@ +Foo \ No newline at end of file diff --git a/testsuite/tests/printer/all.T b/testsuite/tests/printer/all.T index a71d6e3..43ab92b 100644 --- a/testsuite/tests/printer/all.T +++ b/testsuite/tests/printer/all.T @@ -50,3 +50,5 @@ test('T13199', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T1319 test('T13050p', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T13050p']) test('T13550', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T13550']) test('T13942', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T13942']) +test('T14289', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T14289']) +test('T14289b', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T14289b']) From git at git.haskell.org Mon Oct 2 14:14:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 14:14:14 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Revert "Fix #11963 by checking for more mixed type/kinds" (5e2d3e6) Message-ID: <20171002141414.95A1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/5e2d3e6d06a051dd30c0ce1919cd2d3d0ece087b/ghc >--------------------------------------------------------------- commit 5e2d3e6d06a051dd30c0ce1919cd2d3d0ece087b Author: Ben Gamari Date: Mon Oct 2 10:13:42 2017 -0400 Revert "Fix #11963 by checking for more mixed type/kinds" This reverts commit 18dee8912f6afdcf13073d3d95d85513c14180e3. It causes a few Hackage programs to be rejected, which we want to avoid for a point release. >--------------------------------------------------------------- 5e2d3e6d06a051dd30c0ce1919cd2d3d0ece087b compiler/rename/RnTypes.hs | 25 ++++--------------- testsuite/tests/typecheck/should_fail/T11963.hs | 29 ---------------------- .../tests/typecheck/should_fail/T11963.stderr | 20 --------------- testsuite/tests/typecheck/should_fail/all.T | 1 - 4 files changed, 5 insertions(+), 70 deletions(-) diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 58d7c9f..589cc02 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -1707,25 +1707,11 @@ extract_hs_tv_bndrs tvs = do { FKTV bndr_kvs _ <- foldrM extract_lkind emptyFKTV [k | L _ (KindedTyVar _ k) <- tvs] - ; let locals = map hsLTyVarLocName tvs - - -- These checks are all tested in typecheck/should_fail/T11963 - ; check_for_mixed_vars bndr_kvs acc_tvs - ; check_for_mixed_vars bndr_kvs body_tvs - ; check_for_mixed_vars body_tvs acc_kvs - ; check_for_mixed_vars body_kvs acc_tvs - ; check_for_mixed_vars locals body_kvs - + ; let locals = map hsLTyVarName tvs ; return $ - FKTV (filterOut (`elemRdr` locals) (bndr_kvs ++ body_kvs) + FKTV (filterOut ((`elem` locals) . unLoc) (bndr_kvs ++ body_kvs) ++ acc_kvs) - (filterOut (`elemRdr` locals) body_tvs ++ acc_tvs) } - where - check_for_mixed_vars :: [Located RdrName] -> [Located RdrName] -> RnM () - check_for_mixed_vars tvs1 tvs2 = mapM_ check tvs1 - where - check tv1 = when (isRdrTyVar (unLoc tv1) && (tv1 `elemRdr` tvs2)) $ - mixedVarsErr tv1 + (filterOut ((`elem` locals) . unLoc) body_tvs ++ acc_tvs) } extract_tv :: TypeOrKind -> Located RdrName -> FreeKiTyVars -> RnM FreeKiTyVars extract_tv t_or_k ltv@(L _ tv) acc @@ -1740,6 +1726,8 @@ extract_tv t_or_k ltv@(L _ tv) acc mixedVarsErr ltv ; return (FKTV (ltv : kvs) tvs) } | otherwise = return acc + where + elemRdr x = any (eqLocated x) mixedVarsErr :: Located RdrName -> RnM () mixedVarsErr (L loc tv) @@ -1752,6 +1740,3 @@ mixedVarsErr (L loc tv) -- just used in this module; seemed convenient here nubL :: Eq a => [Located a] -> [Located a] nubL = nubBy eqLocated - -elemRdr :: Located RdrName -> [Located RdrName] -> Bool -elemRdr x = any (eqLocated x) diff --git a/testsuite/tests/typecheck/should_fail/T11963.hs b/testsuite/tests/typecheck/should_fail/T11963.hs deleted file mode 100644 index c4f78ae..0000000 --- a/testsuite/tests/typecheck/should_fail/T11963.hs +++ /dev/null @@ -1,29 +0,0 @@ -{-# LANGUAGE GADTs, PolyKinds, RankNTypes #-} - -module T11963 where - --- this module should be rejected without TypeInType - -import Data.Proxy - --- see code in RnTypes.extract_hs_tv_bndrs which checks for these bad cases - - -- bndr_kvs vs body_tvs -data Typ k t where - Typ :: (forall (a :: k -> *). a t -> a t) -> Typ k t - - -- bndr_kvs vs acc_tvs -foo :: (forall (t :: k). Proxy t) -> Proxy k -foo _ = undefined - - -- locals vs body_kvs -bar :: forall k. forall (t :: k). Proxy t -bar = undefined - - -- body_kvs vs acc_tvs -quux :: (forall t. Proxy (t :: k)) -> Proxy k -quux _ = undefined - - -- body_tvs vs acc_kvs -blargh :: (forall a. a -> Proxy k) -> Proxy (t :: k) -blargh _ = undefined diff --git a/testsuite/tests/typecheck/should_fail/T11963.stderr b/testsuite/tests/typecheck/should_fail/T11963.stderr deleted file mode 100644 index 74c3ab0..0000000 --- a/testsuite/tests/typecheck/should_fail/T11963.stderr +++ /dev/null @@ -1,20 +0,0 @@ - -T11963.hs:13:26: error: - Variable ‘k’ used as both a kind and a type - Did you intend to use TypeInType? - -T11963.hs:16:22: error: - Variable ‘k’ used as both a kind and a type - Did you intend to use TypeInType? - -T11963.hs:20:15: error: - Variable ‘k’ used as both a kind and a type - Did you intend to use TypeInType? - -T11963.hs:24:32: error: - Variable ‘k’ used as both a kind and a type - Did you intend to use TypeInType? - -T11963.hs:28:33: error: - Variable ‘k’ used as both a kind and a type - Did you intend to use TypeInType? diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 9f9752a..2f75316 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -434,7 +434,6 @@ test('T12709', normal, compile_fail, ['']) test('T13446', normal, compile_fail, ['']) test('T13320', normal, compile_fail, ['']) test('T13677', normal, compile_fail, ['']) -test('T11963', normal, compile_fail, ['']) test('T14000', normal, compile_fail, ['']) test('T11672', normal, compile_fail, ['']) test('T13929', normal, compile_fail, ['']) From git at git.haskell.org Mon Oct 2 14:24:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 14:24:10 +0000 (UTC) Subject: [commit: ghc] master: Bump submodule nofib again (Semigroup now required) (e299121) Message-ID: <20171002142410.3ECD53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e29912125218aa4e874504e7d403e2f97331b8c9/ghc >--------------------------------------------------------------- commit e29912125218aa4e874504e7d403e2f97331b8c9 Author: Joachim Breitner Date: Thu Sep 14 16:42:53 2017 -0400 Bump submodule nofib again (Semigroup now required) Commit 063e0b4e5ea53a02713eb48555bbd99d934a3de5 accidentially undid 7b8827ab24a3af8555f1adf250b7b541e41d8f5d where I bumped nofib previously. >--------------------------------------------------------------- e29912125218aa4e874504e7d403e2f97331b8c9 nofib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nofib b/nofib index 999a46a..5748d42 160000 --- a/nofib +++ b/nofib @@ -1 +1 @@ -Subproject commit 999a46a1a73832795c532e142a3e37664417f35c +Subproject commit 5748d428204ea0552f70b2981eaf30d4a5cfd3e9 From git at git.haskell.org Mon Oct 2 14:40:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 14:40:17 +0000 (UTC) Subject: [commit: libffi-tarballs] branch 'libffi-3.99999+git20171002+77e130c' created Message-ID: <20171002144017.264063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/libffi-tarballs New branch : libffi-3.99999+git20171002+77e130c Referencing: 96d02800759dcedb9c98a18a5797b86eb3b6e7c2 From git at git.haskell.org Mon Oct 2 14:40:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 14:40:19 +0000 (UTC) Subject: [commit: libffi-tarballs] libffi-3.99999+git20171002+77e130c: Snapshot of libffi 77e130c (3a92c1e) Message-ID: <20171002144019.2C97D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/libffi-tarballs On branch : libffi-3.99999+git20171002+77e130c Link : http://git.haskell.org/libffi-tarballs.git/commitdiff/3a92c1edd1012913de969504cfeaec2bd491fc71 >--------------------------------------------------------------- commit 3a92c1edd1012913de969504cfeaec2bd491fc71 Author: Ben Gamari Date: Mon Oct 2 09:48:06 2017 -0400 Snapshot of libffi 77e130c >--------------------------------------------------------------- 3a92c1edd1012913de969504cfeaec2bd491fc71 LICENSE | 21 +++++++++++++++++++++ README.md | 7 +++++++ libffi-3.99999+git20171002+77e130c.tar.gz | Bin 0 -> 935464 bytes 3 files changed, 28 insertions(+) diff --git a/LICENSE b/LICENSE new file mode 100644 index 0000000..aa60342 --- /dev/null +++ b/LICENSE @@ -0,0 +1,21 @@ +libffi - Copyright (c) 1996-2012 Anthony Green, Red Hat, Inc and others. +See source files for details. + +Permission is hereby granted, free of charge, to any person obtaining +a copy of this software and associated documentation files (the +``Software''), to deal in the Software without restriction, including +without limitation the rights to use, copy, modify, merge, publish, +distribute, sublicense, and/or sell copies of the Software, and to +permit persons to whom the Software is furnished to do so, subject to +the following conditions: + +The above copyright notice and this permission notice shall be +included in all copies or substantial portions of the Software. + +THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, +EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF +MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. +IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY +CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, +TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE +SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. diff --git a/README.md b/README.md new file mode 100644 index 0000000..7aed2ba --- /dev/null +++ b/README.md @@ -0,0 +1,7 @@ +# libffi snapshot tarball for GHC + +This source snapshot was produced from +[libffi](https://github.com/libffi/libffi) commit +[77e130c](https://github.com/libffi/libffi/commit/77e130c) for GHC. See the +`master` branch of this repository for more information about the rationale +and tools for producing these snapshots. diff --git a/libffi-3.99999+git20171002+77e130c.tar.gz b/libffi-3.99999+git20171002+77e130c.tar.gz new file mode 100644 index 0000000..0d06367 Binary files /dev/null and b/libffi-3.99999+git20171002+77e130c.tar.gz differ From git at git.haskell.org Mon Oct 2 14:40:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 14:40:21 +0000 (UTC) Subject: [commit: libffi-tarballs] libffi-3.99999+git20171002+77e130c: Add patch with which the tarball was generated (96d0280) Message-ID: <20171002144021.308593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/libffi-tarballs On branch : libffi-3.99999+git20171002+77e130c Link : http://git.haskell.org/libffi-tarballs.git/commitdiff/96d02800759dcedb9c98a18a5797b86eb3b6e7c2 >--------------------------------------------------------------- commit 96d02800759dcedb9c98a18a5797b86eb3b6e7c2 Author: Ben Gamari Date: Mon Oct 2 10:39:32 2017 -0400 Add patch with which the tarball was generated >--------------------------------------------------------------- 96d02800759dcedb9c98a18a5797b86eb3b6e7c2 0001-Ensure-libffi.map-is-generated.patch | 24 ++++++++++++++++++++++++ 1 file changed, 24 insertions(+) diff --git a/0001-Ensure-libffi.map-is-generated.patch b/0001-Ensure-libffi.map-is-generated.patch new file mode 100644 index 0000000..9c8913c --- /dev/null +++ b/0001-Ensure-libffi.map-is-generated.patch @@ -0,0 +1,24 @@ +From 77e130c1e2f2879ffe9b7add0873101c50208d1a Mon Sep 17 00:00:00 2001 +From: Ben Gamari +Date: Mon, 2 Oct 2017 09:45:05 -0400 +Subject: [PATCH] Ensure libffi.map is generated + +--- + configure.ac | 2 +- + 1 file changed, 1 insertion(+), 1 deletion(-) + +diff --git a/configure.ac b/configure.ac +index d155a6d..f3162d5 100644 +--- a/configure.ac ++++ b/configure.ac +@@ -383,6 +383,6 @@ test -d src/$TARGETDIR || mkdir src/$TARGETDIR + + AC_CONFIG_LINKS(include/ffitarget.h:src/$TARGETDIR/ffitarget.h) + +-AC_CONFIG_FILES(include/Makefile include/ffi.h Makefile testsuite/Makefile man/Makefile doc/Makefile libffi.pc) ++AC_CONFIG_FILES(include/Makefile include/ffi.h Makefile testsuite/Makefile man/Makefile doc/Makefile libffi.pc libffi.map) + + AC_OUTPUT +-- +2.11.0 + From git at git.haskell.org Mon Oct 2 14:56:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 14:56:03 +0000 (UTC) Subject: [commit: ghc] master: Travis: Install texinfo (00ff023) Message-ID: <20171002145603.7A68B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/00ff02352f07bff7d422e4e48e4e5df9a0b63d83/ghc >--------------------------------------------------------------- commit 00ff02352f07bff7d422e4e48e4e5df9a0b63d83 Author: Joachim Breitner Date: Mon Oct 2 10:55:45 2017 -0400 Travis: Install texinfo >--------------------------------------------------------------- 00ff02352f07bff7d422e4e48e4e5df9a0b63d83 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 09d9fef..55995b7 100644 --- a/.travis.yml +++ b/.travis.yml @@ -22,6 +22,7 @@ addons: - alex-3.1.7 - happy-1.19.5 - python3 + - texinfo #- llvm-3.7 before_install: From git at git.haskell.org Mon Oct 2 17:08:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 17:08:28 +0000 (UTC) Subject: [commit: ghc] master: CircleCI: Install texinfo (11a59de) Message-ID: <20171002170828.DE3A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/11a59de25d49f999eed0ea55df29d916a66ecd91/ghc >--------------------------------------------------------------- commit 11a59de25d49f999eed0ea55df29d916a66ecd91 Author: Joachim Breitner Date: Mon Oct 2 13:08:12 2017 -0400 CircleCI: Install texinfo >--------------------------------------------------------------- 11a59de25d49f999eed0ea55df29d916a66ecd91 .circleci/config.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 6ee6c48..a19dc24 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -10,7 +10,7 @@ jobs: name: git command: | apt-get update - apt-get install -y git openssh-client make automake autoconf gcc perl python3 + apt-get install -y git openssh-client make automake autoconf gcc perl python3 texinfo - checkout - run: name: submodules From git at git.haskell.org Mon Oct 2 18:15:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 18:15:37 +0000 (UTC) Subject: [commit: ghc] master: Pretty-printer missing parens for infix class declaration (0e96812) Message-ID: <20171002181537.20F383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0e9681268a38cbc15c9c2b50979624732c9077ce/ghc >--------------------------------------------------------------- commit 0e9681268a38cbc15c9c2b50979624732c9077ce Author: Alan Zimmerman Date: Mon Oct 2 18:09:37 2017 +0200 Pretty-printer missing parens for infix class declaration class (a `C` b) c Is pretty printed as class a `C` b c Fixes #14306 >--------------------------------------------------------------- 0e9681268a38cbc15c9c2b50979624732c9077ce compiler/hsSyn/HsDecls.hs | 4 ++++ testsuite/tests/printer/Makefile | 4 ++++ testsuite/tests/printer/T14306.hs | 10 ++++++++++ testsuite/tests/printer/all.T | 1 + 4 files changed, 19 insertions(+) diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/hsSyn/HsDecls.hs index ecb11a0..35fccd3 100644 --- a/compiler/hsSyn/HsDecls.hs +++ b/compiler/hsSyn/HsDecls.hs @@ -695,6 +695,10 @@ pp_vanilla_decl_head thing (HsQTvs { hsq_explicit = tyvars }) fixity context = hsep [pprHsContext context, pp_tyvars tyvars] where pp_tyvars (varl:varsr) + | fixity == Infix && length varsr > 1 + = hsep [char '(',ppr (unLoc varl), pprInfixOcc (unLoc thing) + , (ppr.unLoc) (head varsr), char ')' + , hsep (map (ppr.unLoc) (tail varsr))] | fixity == Infix = hsep [ppr (unLoc varl), pprInfixOcc (unLoc thing) , hsep (map (ppr.unLoc) varsr)] diff --git a/testsuite/tests/printer/Makefile b/testsuite/tests/printer/Makefile index 1c2f299..4565e83 100644 --- a/testsuite/tests/printer/Makefile +++ b/testsuite/tests/printer/Makefile @@ -213,3 +213,7 @@ T13550: .PHONY: T13942 T13942: $(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" T13942.hs + +.PHONY: T14306 +T14306: + $(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" T14306.hs diff --git a/testsuite/tests/printer/T14306.hs b/testsuite/tests/printer/T14306.hs new file mode 100644 index 0000000..c39807e --- /dev/null +++ b/testsuite/tests/printer/T14306.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE MultiParamTypeClasses #-} +module T14306 where + +class (a `C` b) c + +class (a `D` b) c d + +class (a `E` b) + +class a `F` b diff --git a/testsuite/tests/printer/all.T b/testsuite/tests/printer/all.T index a71d6e3..9a1170e 100644 --- a/testsuite/tests/printer/all.T +++ b/testsuite/tests/printer/all.T @@ -50,3 +50,4 @@ test('T13199', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T1319 test('T13050p', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T13050p']) test('T13550', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T13550']) test('T13942', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T13942']) +test('T14306', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T14306']) From git at git.haskell.org Mon Oct 2 21:55:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 21:55:05 +0000 (UTC) Subject: [commit: ghc] master: Bump libffi-tarballs submodule (e462b65) Message-ID: <20171002215505.CE55F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e462b657daa003d365440afdad14c5756898b5e0/ghc >--------------------------------------------------------------- commit e462b657daa003d365440afdad14c5756898b5e0 Author: Ben Gamari Date: Mon Oct 2 10:47:10 2017 -0400 Bump libffi-tarballs submodule >--------------------------------------------------------------- e462b657daa003d365440afdad14c5756898b5e0 libffi-tarballs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libffi-tarballs b/libffi-tarballs index 81fbf2e..96d0280 160000 --- a/libffi-tarballs +++ b/libffi-tarballs @@ -1 +1 @@ -Subproject commit 81fbf2e78a082c6ad464d4025b44402b3db8acdf +Subproject commit 96d02800759dcedb9c98a18a5797b86eb3b6e7c2 From git at git.haskell.org Mon Oct 2 21:55:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 21:55:08 +0000 (UTC) Subject: [commit: ghc] master: rel-notes: Mention libffi packaging change (e30d9ca) Message-ID: <20171002215508.8B77A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e30d9ca6641289daa02962c775e13346dcb4782a/ghc >--------------------------------------------------------------- commit e30d9ca6641289daa02962c775e13346dcb4782a Author: Ben Gamari Date: Sat Sep 30 12:18:02 2017 -0400 rel-notes: Mention libffi packaging change [skip ci] >--------------------------------------------------------------- e30d9ca6641289daa02962c775e13346dcb4782a docs/users_guide/8.4.1-notes.rst | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/docs/users_guide/8.4.1-notes.rst b/docs/users_guide/8.4.1-notes.rst index f525a81..107519d 100644 --- a/docs/users_guide/8.4.1-notes.rst +++ b/docs/users_guide/8.4.1-notes.rst @@ -239,3 +239,9 @@ Build system There is currently no explicit dependency between the two in the build system and such there is no way to notify ``base`` that the ``rts`` has been split, or vice versa. (see :ghc-ticket:`5987`). + +- GHC now ships with a snapshot of the ``libffi`` library, which is used for + foreign function invocation on some platforms. This was necessary as there + were numerous fixes which have not yet been incorporated into a ``libffi`` + release. However, you can still use the ``--with-system-libffi`` ``configure`` + flag to tell the build system to use the ``libffi`` installed on your system. From git at git.haskell.org Mon Oct 2 21:55:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 21:55:11 +0000 (UTC) Subject: [commit: ghc] master: Rewrite boot in Python (c0e6c73) Message-ID: <20171002215511.592C03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c0e6c73482881ac966a5fc12ef671d405af9262a/ghc >--------------------------------------------------------------- commit c0e6c73482881ac966a5fc12ef671d405af9262a Author: Ben Gamari Date: Sat Sep 30 11:53:16 2017 -0400 Rewrite boot in Python One step closer to being able to drop the Windows Perl tarball. We previously attempted to do this in D3567 but were forced to revert due to Windows problems. Acknowledgements: * @Phyx kindly contributed the codepath allowing this to work on Windows. Test Plan: Validate Reviewers: hvr, austin, Phyx Subscribers: erikd, thomie, rwbarton Differential Revision: https://phabricator.haskell.org/D3918 >--------------------------------------------------------------- c0e6c73482881ac966a5fc12ef671d405af9262a INSTALL.md | 8 +- MAKEHELP.md | 2 +- boot | 398 +++++++++++++++++++++++++---------------------------------- configure.ac | 2 +- validate | 4 +- 5 files changed, 178 insertions(+), 236 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c0e6c73482881ac966a5fc12ef671d405af9262a From git at git.haskell.org Mon Oct 2 22:05:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Oct 2017 22:05:50 +0000 (UTC) Subject: [commit: ghc] master: user-guide: Fix :since: annotation of -pie and add documentation for -fPIE (d5e60de) Message-ID: <20171002220550.15E5D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d5e60de307874432f42aa7fea2460e6901c057e1/ghc >--------------------------------------------------------------- commit d5e60de307874432f42aa7fea2460e6901c057e1 Author: Ben Gamari Date: Mon Oct 2 18:02:40 2017 -0400 user-guide: Fix :since: annotation of -pie and add documentation for -fPIE [skip ci] >--------------------------------------------------------------- d5e60de307874432f42aa7fea2460e6901c057e1 docs/users_guide/phases.rst | 14 ++++++++++++-- 1 file changed, 12 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst index 0b75462..d14a7fa 100644 --- a/docs/users_guide/phases.rst +++ b/docs/users_guide/phases.rst @@ -578,6 +578,16 @@ Options affecting code generation Windows, position-independent code is never used so the flag is a no-op on that platform. +.. ghc-flag:: -fPIE + :shortdesc: Generate code for a position-independent executable (where available) + :type: dynamic + :category: codegen + + Generate code in such a way to be linkable into a position-independent + executable This currently works on Linux x86 and x86-64. On Windows, + position-independent code is never used so the flag is a no-op on that + platform. To link the final executable use :ghc-flag:`-pie`. + .. ghc-flag:: -dynamic :shortdesc: Build dynamically-linked object files and executables :type: dynamic @@ -1119,7 +1129,7 @@ for example). :type: dynamic :category: linking - :since: 8.2.1 + :since: 8.2.2 This instructs the linker to produce a position-independent executable. This flag is only valid while producing executables and all object code @@ -1136,4 +1146,4 @@ for example). loaded into the address space of another Haskell process. Also, you may need to use the :ghc-flags:`-rdynamic` flag to ensure that - that symbols are not dropped from your PIE object. + that symbols are not dropped from your PIE objects. From git at git.haskell.org Tue Oct 3 00:23:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 00:23:14 +0000 (UTC) Subject: [commit: ghc] master: No libffi docs (d0c5d8d) Message-ID: <20171003002314.6B1F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d0c5d8dec85b2d389ada5167be9c805f83349f8f/ghc >--------------------------------------------------------------- commit d0c5d8dec85b2d389ada5167be9c805f83349f8f Author: Moritz Angermann Date: Sun Oct 1 17:39:28 2017 +0800 No libffi docs Summary: building libffi docs with our intree-libffi seems rather pointless. Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4054 >--------------------------------------------------------------- d0c5d8dec85b2d389ada5167be9c805f83349f8f libffi/ghc.mk | 1 + 1 file changed, 1 insertion(+) diff --git a/libffi/ghc.mk b/libffi/ghc.mk index 691eda7..6bc8897 100644 --- a/libffi/ghc.mk +++ b/libffi/ghc.mk @@ -99,6 +99,7 @@ $(libffi_STAMP_CONFIGURE): $(TOUCH_DEP) "$(SHELL)" ./configure \ --prefix=$(TOP)/libffi/build/inst \ --libdir=$(TOP)/libffi/build/inst/lib \ + --disable-docs \ --enable-static=yes \ --enable-shared=$(libffi_EnableShared) \ --host=$(TargetPlatformFull) From git at git.haskell.org Tue Oct 3 01:23:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 01:23:42 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Build utilities with the bootstrap compiler when cross compiling (a1cfec3) Message-ID: <20171003012342.A99863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/a1cfec3a3bd9ae0f9f5412f7035d1f68101d66ed/ghc >--------------------------------------------------------------- commit a1cfec3a3bd9ae0f9f5412f7035d1f68101d66ed Author: Moritz Angermann Date: Fri Sep 29 14:45:44 2017 +0800 Build utilities with the bootstrap compiler when cross compiling Summary: This should fix Trac #14297. When building a cross compiler, we have rather little use of utilities that do not run on the host, where the compiler runs. As such we should build the utilities with the bootstrap (stage 0) compiler rather than witht he in-tree (stage 1) compiler when CrossCompiling. This used to results in the utilities we ship in the binary distribution to be built for the wrong host. This diff tries to rectify the situation and allow the binary distribution to contain the utilities for the host when CrossCompiling. Reviewers: bgamari, trofi, hvr, austin Subscribers: rwbarton, thomie GHC Trac Issues: #14297 Differential Revision: https://phabricator.haskell.org/D4048 >--------------------------------------------------------------- a1cfec3a3bd9ae0f9f5412f7035d1f68101d66ed ghc.mk | 15 +++++++++++++-- utils/compare_sizes/ghc.mk | 4 +++- utils/hpc/ghc.mk | 18 +++++++++++++++++- utils/hsc2hs | 2 +- 4 files changed, 34 insertions(+), 5 deletions(-) diff --git a/ghc.mk b/ghc.mk index c3edc5e..f397f7c 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1056,6 +1056,17 @@ ifneq "$(CLEANING)" "YES" # This rule seems to hold some files open on Windows which prevents # cleaning, perhaps due to the $(wildcard). +# when building stage1only (a cross-compiler), we need to put the +# stage0 compiled ghc-cabal into the binary distribution. As the +# stage1 compiled ghc-cabal is built for the target, however +# ghc-cabal is used during 'make install' on the host, when +# installing the binary distribution. +ifeq "$(Stage1Only)" "YES" +DIST_GHC_CABAL=utils/ghc-cabal/dist/build/tmp/ghc-cabal +else +DIST_GHC_CABAL=utils/ghc-cabal/dist-install/build/tmp/ghc-cabal +endif + $(eval $(call bindist-list,.,\ LICENSE \ README \ @@ -1067,7 +1078,7 @@ $(eval $(call bindist-list,.,\ Makefile \ mk/config.mk.in \ $(INPLACE_BIN)/mkdirhier \ - utils/ghc-cabal/dist-install/build/tmp/ghc-cabal \ + $(DIST_GHC_CABAL) \ $(BINDIST_WRAPPERS) \ $(BINDIST_PERL_SOURCES) \ $(BINDIST_LIBS) \ @@ -1127,7 +1138,7 @@ unix-binary-dist-prep: echo "BUILD_SPHINX_HTML = $(BUILD_SPHINX_HTML)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_PDF = $(BUILD_SPHINX_PDF)" >> $(BIN_DIST_MK) echo "BUILD_MAN = $(BUILD_MAN)" >> $(BIN_DIST_MK) - echo "override ghc-cabal_INPLACE = utils/ghc-cabal/dist-install/build/tmp/ghc-cabal-bindist" >> $(BIN_DIST_MK) + echo "override ghc-cabal_INPLACE = $(DIST_GHC_CABAL)" >> $(BIN_DIST_MK) echo "UseSystemLibFFI = $(UseSystemLibFFI)" >> $(BIN_DIST_MK) # See Note [Persist CrossCompiling in binary distributions] echo "CrossCompiling = $(CrossCompiling)" >> $(BIN_DIST_MK) diff --git a/utils/compare_sizes/ghc.mk b/utils/compare_sizes/ghc.mk index d659a5e..1e601a3 100644 --- a/utils/compare_sizes/ghc.mk +++ b/utils/compare_sizes/ghc.mk @@ -5,5 +5,7 @@ utils/compare_sizes_MODULES = Main utils/compare_sizes_dist-install_PROGNAME = compareSizes utils/compare_sizes_dist-install_INSTALL_INPLACE = NO +# build compare_sizes only if not Stage1Only or not CrossCompiling. +ifeq "$(Stage1Only) $(CrossCompiling)" "NO NO" $(eval $(call build-prog,utils/compare_sizes,dist-install,1)) - +endif diff --git a/utils/hpc/ghc.mk b/utils/hpc/ghc.mk index f70be94..697e795 100644 --- a/utils/hpc/ghc.mk +++ b/utils/hpc/ghc.mk @@ -12,10 +12,26 @@ utils/hpc_USES_CABAL = YES utils/hpc_PACKAGE = hpc-bin -utils/hpc_dist-install_INSTALL = YES + +# built by ghc-stage0 +utils/hpc_dist_INSTALL_INPLACE = NO +utils/hpc_dist_PROGNAME = hpc +utils/hpc_dist_SHELL_WRAPPER = YES +utils/hpc_dist_INSTALL_SHELL_WRAPPER_NAME = hpc + +# built by ghc-stage1 utils/hpc_dist-install_INSTALL_INPLACE = YES utils/hpc_dist-install_PROGNAME = hpc utils/hpc_dist-install_SHELL_WRAPPER = YES utils/hpc_dist-install_INSTALL_SHELL_WRAPPER_NAME = hpc +ifeq "$(Stage1Only)" "YES" +utils/hpc_dist_INSTALL = YES +utils/hpc_dist-install_INSTALL = NO +else +utils/hpc_dist_INSTALL = NO +utils/hpc_dist-install_INSTALL = YES +endif + +$(eval $(call build-prog,utils/hpc,dist,0)) $(eval $(call build-prog,utils/hpc,dist-install,1)) diff --git a/utils/hsc2hs b/utils/hsc2hs index 936b088..94af7d9 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 936b0885ee794db83dc8473e17e153936e56d62f +Subproject commit 94af7d9a27307f40a8b18da0f8e0fd9e9d77e818 From git at git.haskell.org Tue Oct 3 01:23:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 01:23:48 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: [genapply] feed args. (86c7b26) Message-ID: <20171003012348.2025F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/86c7b263b472042ca9465d858a73af39edafe1fd/ghc >--------------------------------------------------------------- commit 86c7b263b472042ca9465d858a73af39edafe1fd Author: Moritz Angermann Date: Mon Sep 25 20:34:28 2017 +0800 [genapply] feed args. >--------------------------------------------------------------- 86c7b263b472042ca9465d858a73af39edafe1fd utils/genapply/Main.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/genapply/Main.hs b/utils/genapply/Main.hs index 9248c22..b30c9f8 100644 --- a/utils/genapply/Main.hs +++ b/utils/genapply/Main.hs @@ -858,7 +858,7 @@ genApplyFast regstatus args = nest 4 (vcat [ text "Sp_adj" <> parens (int (-sp_offset)) <> semi, saveRegOffs reg_locs, - mkJump regstatus fun_ret_label [] [] <> semi + mkJump regstatus fun_ret_label [] args <> semi ]), char '}' ]), From git at git.haskell.org Tue Oct 3 01:23:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 01:23:45 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Fix binary distributions of cross compilers (67ab675c) Message-ID: <20171003012345.649623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/67ab675cfbe1f7e6846accd07e3626b6cb3c2a79/ghc >--------------------------------------------------------------- commit 67ab675cfbe1f7e6846accd07e3626b6cb3c2a79 Author: Moritz Angermann Date: Mon Oct 2 13:47:45 2017 +0800 Fix binary distributions of cross compilers Summary: - copy over the original settings file Otherwise most of the custom cross compiler toolchain will be screwed up upon install. I'd rather have someone complain about a proper target-prefixed tool being missing, than getting garbaled output and a slew of strange errors because the final configure selected tools on the install machine just don't match up. - persist target-prefix. For cross compilers, retain the $target- prefix. This allows installing multiple cross compierls targetting different targets alongside each other. Reviewers: austin, hvr, bgamari Subscribers: rwbarton, trofi, thomie, hvr, bgamari, erikd Differential Revision: https://phabricator.haskell.org/D4058 >--------------------------------------------------------------- 67ab675cfbe1f7e6846accd07e3626b6cb3c2a79 distrib/configure.ac.in | 19 ++++++++++++++----- ghc.mk | 22 ++++++++++++++++++++-- 2 files changed, 34 insertions(+), 7 deletions(-) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index 509e74e..7e0aef1 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -36,9 +36,9 @@ FPTOOLS_SET_PLATFORM_VARS FP_FIND_ROOT # ToDo: if Stage1Only=YES, should be YES -CrossCompiling=NO -CrossCompilePrefix="" -TargetPlatformFull="${target}" +CrossCompiling=@CrossCompiling@ +CrossCompilePrefix=@CrossCompilePrefix@ +TargetPlatformFull=@TargetPlatformFull@ AC_SUBST(CrossCompiling) AC_SUBST(CrossCompilePrefix) @@ -198,8 +198,17 @@ fi FP_SETTINGS -# -AC_CONFIG_FILES(settings mk/config.mk mk/install.mk) +dnl ** Hack tools for cross compilers +dnl -------------------------------------------------------------- +dnl When building a binary distribution for cross compilers, +dnl we likely want to retain the target-prefixed tools, and not +dnl have configure overwrite them with what ever it finds, as +dnl the found tools likely do not target the target. +AC_CONFIG_FILES(mk/config.mk mk/install.mk) +if test "x$CrossCompiling" = "xNO"; then +AC_CONFIG_FILES(settings) +fi + AC_OUTPUT # We get caught by diff --git a/ghc.mk b/ghc.mk index c3edc5e..012bffa 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1056,12 +1056,30 @@ ifneq "$(CLEANING)" "YES" # This rule seems to hold some files open on Windows which prevents # cleaning, perhaps due to the $(wildcard). +# when building stage1only (a cross-compiler), we need to put the +# stage0 compiled ghc-cabal into the binary distribution. As the +# stage1 compiled ghc-cabal is built for the target, however +# ghc-cabal is used during 'make install' on the host, when +# installing the binary distribution. We will also copy the original +# `settings` file instead of having `configure` compute a new one +# when runningt `./configure && make install`. We do this because +# configure at install by default picks up the non-target prefixed +# toolchain; and cross compilers can be very sensitive to +# the toolchain. +ifeq "$(Stage1Only)" "YES" +DIST_GHC_CABAL=utils/ghc-cabal/dist/build/tmp/ghc-cabal +DIST_SETTINGS=settings +else +DIST_GHC_CABAL=utils/ghc-cabal/dist-install/build/tmp/ghc-cabal +DIST_SETTINGS=settings.in +endif + $(eval $(call bindist-list,.,\ LICENSE \ README \ INSTALL \ configure config.sub config.guess install-sh \ - settings.in \ + $(DIST_SETTINGS) \ llvm-targets \ packages \ Makefile \ @@ -1122,7 +1140,7 @@ BIN_DIST_MK = $(BIN_DIST_PREP_DIR)/bindist.mk unix-binary-dist-prep: $(call removeTrees,bindistprep/) "$(MKDIRHIER)" $(BIN_DIST_PREP_DIR) - set -e; for i in packages LICENSE compiler ghc iserv rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh settings.in llvm-targets ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done + set -e; for i in packages LICENSE compiler ghc iserv rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh $(DIST_SETTINGS) llvm-targets ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done echo "HADDOCK_DOCS = $(HADDOCK_DOCS)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_HTML = $(BUILD_SPHINX_HTML)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_PDF = $(BUILD_SPHINX_PDF)" >> $(BIN_DIST_MK) From git at git.haskell.org Tue Oct 3 01:23:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 01:23:56 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds `-llvmng` (b873ec7) Message-ID: <20171003012356.18C5D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/b873ec754557555f9cb32ede327b01098670a834/ghc >--------------------------------------------------------------- commit b873ec754557555f9cb32ede327b01098670a834 Author: Moritz Angermann Date: Mon Jul 31 15:18:49 2017 +0800 Adds `-llvmng` >--------------------------------------------------------------- b873ec754557555f9cb32ede327b01098670a834 .gitmodules | 9 + compiler/cmm/CmmSwitch.hs | 1 + compiler/codeGen/StgCmmPrim.hs | 3 +- compiler/ghc.cabal.in | 8 +- compiler/llvmGen-ng/Data/BitCode/LLVM/Gen.hs | 1783 ++++++++++++++++++++ compiler/llvmGen-ng/Data/BitCode/LLVM/Gen/Monad.hs | 86 + compiler/main/CodeOutput.hs | 10 + compiler/main/DriverPipeline.hs | 5 +- compiler/main/DynFlags.hs | 12 +- compiler/typecheck/TcForeign.hs | 4 +- ghc.mk | 8 + libraries/base/tests/all.T | 2 +- libraries/data-bitcode | 1 + libraries/data-bitcode-edsl | 1 + libraries/data-bitcode-llvm | 1 + mk/build.mk.sample | 13 +- mk/flavours/{prof.mk => prof-llvmng.mk} | 6 +- mk/flavours/{quick-cross.mk => quick-cross-ng.mk} | 4 +- mk/flavours/{quick.mk => quick-llvmng.mk} | 4 +- packages | 3 + testsuite/config/ghc | 16 +- 21 files changed, 1961 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b873ec754557555f9cb32ede327b01098670a834 From git at git.haskell.org Tue Oct 3 01:23:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 01:23:51 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds test (8c2924e) Message-ID: <20171003012351.5B8543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/8c2924ef9972f0647152a5f0d6f013fd81f887f9/ghc >--------------------------------------------------------------- commit 8c2924ef9972f0647152a5f0d6f013fd81f887f9 Author: Moritz Angermann Date: Thu Sep 21 22:07:44 2017 +0800 Adds test >--------------------------------------------------------------- 8c2924ef9972f0647152a5f0d6f013fd81f887f9 testsuite/tests/codeGen/should_run/T14251.hs | 22 ++++++++++++++++++++++ testsuite/tests/codeGen/should_run/T14251.stdout | 1 + testsuite/tests/codeGen/should_run/all.T | 1 + 3 files changed, 24 insertions(+) diff --git a/testsuite/tests/codeGen/should_run/T14251.hs b/testsuite/tests/codeGen/should_run/T14251.hs new file mode 100644 index 0000000..6f552e1 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14251.hs @@ -0,0 +1,22 @@ +{-# LANGUAGE MagicHash, BangPatterns #-} +module Main where + +-- A minor modification from T8064.hs. +-- +-- The key here is that we ensure that +-- subsequently passed floats do not +-- accidentally end up in previous +-- registers. +-- + +import GHC.Exts + +{-# NOINLINE f #-} +f :: (Int# -> Float# -> Double# -> Float# -> Double# -> String) -> String +f g = g 3# 4.0# 5.0## 6.0# 6.9## ++ " World!" + +{-# NOINLINE q #-} +q :: Int# -> Float# -> Double# -> Float# -> Double# -> String +q i j k l m = "Hello " ++ show (F# l) ++ " " ++ show (D# m) + +main = putStrLn (f $ q) diff --git a/testsuite/tests/codeGen/should_run/T14251.stdout b/testsuite/tests/codeGen/should_run/T14251.stdout new file mode 100644 index 0000000..8ec577b --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14251.stdout @@ -0,0 +1 @@ +Hello 6.0 6.9 World! diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 271a420..36e4855 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -158,3 +158,4 @@ test('T9577', [ unless(arch('x86_64') or arch('i386'),skip), test('T13425', normal, compile_and_run, ['-O']) test('castFloatWord', normal, compile_and_run, ['-dcmm-lint']) +test('T14251', normal, compile_and_run, ['-O2']) From git at git.haskell.org Tue Oct 3 01:24:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 01:24:00 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Merge branch 'feature/fix-T14297' into wip/angerman/llvmng (e602a6d) Message-ID: <20171003012400.AFF533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/e602a6d6c12e50e57b69359ab40bac7f86db5326/ghc >--------------------------------------------------------------- commit e602a6d6c12e50e57b69359ab40bac7f86db5326 Merge: 86c7b26 a1cfec3 Author: Moritz Angermann Date: Tue Oct 3 09:16:07 2017 +0800 Merge branch 'feature/fix-T14297' into wip/angerman/llvmng >--------------------------------------------------------------- e602a6d6c12e50e57b69359ab40bac7f86db5326 ghc.mk | 15 +++++++++++++-- utils/compare_sizes/ghc.mk | 4 +++- utils/hpc/ghc.mk | 18 +++++++++++++++++- utils/hsc2hs | 2 +- 4 files changed, 34 insertions(+), 5 deletions(-) From git at git.haskell.org Tue Oct 3 01:24:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 01:24:05 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Merge branch 'feature/cross-compiler-bindist' into wip/angerman/llvmng (e534f8d) Message-ID: <20171003012405.5951C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/e534f8d2158d8e5075c12724411b56335e98b806/ghc >--------------------------------------------------------------- commit e534f8d2158d8e5075c12724411b56335e98b806 Merge: e602a6d 67ab675c Author: Moritz Angermann Date: Tue Oct 3 09:17:15 2017 +0800 Merge branch 'feature/cross-compiler-bindist' into wip/angerman/llvmng # Conflicts: # ghc.mk >--------------------------------------------------------------- e534f8d2158d8e5075c12724411b56335e98b806 distrib/configure.ac.in | 19 ++++++++++++++----- ghc.mk | 13 ++++++++++--- 2 files changed, 24 insertions(+), 8 deletions(-) From git at git.haskell.org Tue Oct 3 01:24:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 01:24:08 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng's head updated: Merge branch 'feature/cross-compiler-bindist' into wip/angerman/llvmng (e534f8d) Message-ID: <20171003012408.49EAD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/angerman/llvmng' now includes: 5935acd mkDataConRep: fix bug in strictness signature (#14290) 7aa000b Fix #13391 by checking for kind-GADTs 464396d Fix Raspberry Pi target name 9c05fc4 user-guide: Document -Weverything 626f045 Document a law for TH's Lift class effcd56 Don't use "character" in haddocks of Char c15c427 iserv: Don't build vanilla iserv unless vanilla libraries are built e515c7f Allow libffi snapshots a1cfec3 Build utilities with the bootstrap compiler when cross compiling 67ab675c Fix binary distributions of cross compilers e299121 Bump submodule nofib again (Semigroup now required) 00ff023 Travis: Install texinfo 11a59de CircleCI: Install texinfo 0e96812 Pretty-printer missing parens for infix class declaration c0e6c73 Rewrite boot in Python e30d9ca rel-notes: Mention libffi packaging change e462b65 Bump libffi-tarballs submodule d5e60de user-guide: Fix :since: annotation of -pie and add documentation for -fPIE d0c5d8d No libffi docs b873ec7 Adds `-llvmng` 8c2924e Adds test 86c7b26 [genapply] feed args. e602a6d Merge branch 'feature/fix-T14297' into wip/angerman/llvmng e534f8d Merge branch 'feature/cross-compiler-bindist' into wip/angerman/llvmng From git at git.haskell.org Tue Oct 3 05:01:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 05:01:32 +0000 (UTC) Subject: [commit: ghc] master: Adds x86 NONE relocation type (a4ee289) Message-ID: <20171003050132.8B5A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a4ee28978acbcf68da9dfb6f198cb6e1ff38ccca/ghc >--------------------------------------------------------------- commit a4ee28978acbcf68da9dfb6f198cb6e1ff38ccca Author: Moritz Angermann Date: Tue Oct 3 09:58:35 2017 +0800 Adds x86 NONE relocation type Summary: As reported by Alex Lang, R_X86_64_NONE relocations appear in per-package object files, not per-module object files. This diff adds _NONE relocations for x86. Reviewers: bgamari, geekosaur, austin, erikd, simonmar Reviewed By: geekosaur Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4062 >--------------------------------------------------------------- a4ee28978acbcf68da9dfb6f198cb6e1ff38ccca rts/linker/Elf.c | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/rts/linker/Elf.c b/rts/linker/Elf.c index 58fa593..f2fd88f 100644 --- a/rts/linker/Elf.c +++ b/rts/linker/Elf.c @@ -1097,6 +1097,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, switch (reloc_type) { # ifdef i386_HOST_ARCH + case COMPAT_R_386_NONE: break; case COMPAT_R_386_32: *pP = value; break; case COMPAT_R_386_PC32: *pP = value - P; break; # endif @@ -1571,6 +1572,9 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, # endif #if defined(x86_64_HOST_ARCH) + case COMPAT_R_X86_64_NONE: + break; + case COMPAT_R_X86_64_64: *(Elf64_Xword *)P = value; break; From git at git.haskell.org Tue Oct 3 13:45:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 13:45:28 +0000 (UTC) Subject: [commit: ghc] master: Make GHC.IO.Buffer.summaryBuffer strict (b1e0c65) Message-ID: <20171003134528.6EED33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b1e0c65a1302f998917e6d33d6e1ebb84cd09fa8/ghc >--------------------------------------------------------------- commit b1e0c65a1302f998917e6d33d6e1ebb84cd09fa8 Author: Simon Peyton Jones Date: Mon Oct 2 15:28:35 2017 +0100 Make GHC.IO.Buffer.summaryBuffer strict I came across this when debugging something else. Making it strict improves the code slightly without affecting behaviour. >--------------------------------------------------------------- b1e0c65a1302f998917e6d33d6e1ebb84cd09fa8 libraries/base/GHC/IO/Buffer.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/IO/Buffer.hs b/libraries/base/GHC/IO/Buffer.hs index 33eee63..f3cabb2 100644 --- a/libraries/base/GHC/IO/Buffer.hs +++ b/libraries/base/GHC/IO/Buffer.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Trustworthy, BangPatterns #-} {-# LANGUAGE CPP, NoImplicitPrelude #-} {-# OPTIONS_GHC -funbox-strict-fields #-} @@ -264,7 +264,8 @@ foreign import ccall unsafe "memmove" memmove :: Ptr a -> Ptr a -> CSize -> IO (Ptr a) summaryBuffer :: Buffer a -> String -summaryBuffer buf = "buf" ++ show (bufSize buf) ++ "(" ++ show (bufL buf) ++ "-" ++ show (bufR buf) ++ ")" +summaryBuffer !buf -- Strict => slightly better code + = "buf" ++ show (bufSize buf) ++ "(" ++ show (bufL buf) ++ "-" ++ show (bufR buf) ++ ")" -- INVARIANTS on Buffers: -- * r <= w From git at git.haskell.org Tue Oct 3 13:45:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 13:45:32 +0000 (UTC) Subject: [commit: ghc] master: Fix nasty bug in w/w for absence analysis (dbbee1b) Message-ID: <20171003134532.94C3B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dbbee1bacef1a8accc630908c31cf267a3cb98a9/ghc >--------------------------------------------------------------- commit dbbee1bacef1a8accc630908c31cf267a3cb98a9 Author: Simon Peyton Jones Date: Mon Oct 2 15:25:02 2017 +0100 Fix nasty bug in w/w for absence analysis This dark corner was exposed by Trac #14285. It involves the interaction between absence analysis and INLINABLE pragmas. There is a full explanation in Note [aBSENT_ERROR_ID] in MkCore, which you can read there. The changes in this patch are * Make exprIsHNF return True for absentError, treating absentError like an honorary data constructor. * Make absentError /not/ be diverging, unlike other error Ids. This is all a bit horrible. * While doing this I found that exprOkForSpeculation didn't have a case for value lambdas so I added one. It's not really called on lifted types much, but it seems like the right thing >--------------------------------------------------------------- dbbee1bacef1a8accc630908c31cf267a3cb98a9 compiler/basicTypes/MkId.hs | 16 +-- compiler/coreSyn/CoreUtils.hs | 32 +++--- compiler/coreSyn/MkCore.hs | 110 +++++++++++++++++++-- compiler/simplCore/Simplify.hs | 98 +++++++++--------- compiler/stranal/WwLib.hs | 37 ++++--- testsuite/tests/stranal/should_run/T14285.hs | 9 ++ .../tests/stranal/should_run/T14285.stdout | 0 testsuite/tests/stranal/should_run/T14285a.hs | 37 +++++++ testsuite/tests/stranal/should_run/all.T | 1 + 9 files changed, 244 insertions(+), 96 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dbbee1bacef1a8accc630908c31cf267a3cb98a9 From git at git.haskell.org Tue Oct 3 13:45:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 13:45:35 +0000 (UTC) Subject: [commit: ghc] master: Comments only (a1fc7ce) Message-ID: <20171003134535.4CBC93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a1fc7ce3f16e302b19ab39174ee065fa116b6afd/ghc >--------------------------------------------------------------- commit a1fc7ce3f16e302b19ab39174ee065fa116b6afd Author: Simon Peyton Jones Date: Fri Sep 29 11:39:28 2017 +0100 Comments only >--------------------------------------------------------------- a1fc7ce3f16e302b19ab39174ee065fa116b6afd compiler/prelude/PrelRules.hs | 17 +++++++++-------- compiler/stranal/WorkWrap.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 2 +- 3 files changed, 11 insertions(+), 10 deletions(-) diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs index 810fd2b..8838c4a 100644 --- a/compiler/prelude/PrelRules.hs +++ b/compiler/prelude/PrelRules.hs @@ -897,21 +897,22 @@ tagToEnumRule = do _ -> WARN( True, text "tagToEnum# on non-enumeration type" <+> ppr ty ) return $ mkRuntimeErrorApp rUNTIME_ERROR_ID ty "tagToEnum# on non-enumeration type" -{- -For dataToTag#, we can reduce if either - - (a) the argument is a constructor - (b) the argument is a variable whose unfolding is a known constructor --} - +------------------------------ dataToTagRule :: RuleM CoreExpr +-- Rules for dataToTag# dataToTagRule = a `mplus` b where + -- dataToTag (tagToEnum x) ==> x a = do [Type ty1, Var tag_to_enum `App` Type ty2 `App` tag] <- getArgs guard $ tag_to_enum `hasKey` tagToEnumKey guard $ ty1 `eqType` ty2 - return tag -- dataToTag (tagToEnum x) ==> x + return tag + + -- dataToTag (K e1 e2) ==> tag-of K + -- This also works (via exprIsConApp_maybe) for + -- dataToTag x + -- where x's unfolding is a constructor application b = do dflags <- getDynFlags [_, val_arg] <- getArgs diff --git a/compiler/stranal/WorkWrap.hs b/compiler/stranal/WorkWrap.hs index 28b0df3..ac8798e 100644 --- a/compiler/stranal/WorkWrap.hs +++ b/compiler/stranal/WorkWrap.hs @@ -182,7 +182,7 @@ If we have where f is strict in y, we might get a more efficient loop by w/w'ing f. But that would make a new unfolding which would overwrite the old -one! So the function would no longer be ININABLE, and in particular +one! So the function would no longer be INLNABLE, and in particular will not be specialised at call sites in other modules. This comes in practice (Trac #6056). diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 8767843..fa8b2bb 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -3002,7 +3002,7 @@ checkValidRoleAnnots role_annots tc ; _ <- zipWith3M checkRoleAnnot vis_vars the_role_annots vis_roles -- Representational or phantom roles for class parameters -- quickly lead to incoherence. So, we require - -- IncoherentInstances to have them. See #8773. + -- IncoherentInstances to have them. See #8773, #14292 ; incoherent_roles_ok <- xoptM LangExt.IncoherentInstances ; checkTc ( incoherent_roles_ok || (not $ isClassTyCon tc) From git at git.haskell.org Tue Oct 3 13:45:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 13:45:38 +0000 (UTC) Subject: [commit: ghc] master: Fix bug in the short-cut solver (a8fde18) Message-ID: <20171003134538.87C3A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a8fde1831f4b99885b8ed444f9cd7dffd9252150/ghc >--------------------------------------------------------------- commit a8fde1831f4b99885b8ed444f9cd7dffd9252150 Author: Simon Peyton Jones Date: Mon Oct 2 15:58:46 2017 +0100 Fix bug in the short-cut solver Trac #13943 showed that the relatively-new short-cut solver for class constraints (aka -fsolve-constant-dicts) was wrong. In particular, see "Type families" under Note [Shortcut solving] in TcInteract. The short-cut solver recursively solves sub-goals, but it doesn't flatten type-family applications, and as a result it erroneously thought that C (F a) cannot possibly match (C 0), which is simply untrue. That led to an inifinte loop in the short-cut solver. The significant change is the one line + , all isTyFamFree preds -- See "Type families" in + -- Note [Shortcut solving] but, as ever, I do some other refactoring. (E.g. I changed the name of the function to shortCutSolver rather than the more generic trySolveFromInstance.) I also made the short-cut solver respect the solver-depth limit, so that if this happens again it won't just produce an infinite loop. A bit of other refactoring, notably moving isTyFamFree from TcValidity to TcType >--------------------------------------------------------------- a8fde1831f4b99885b8ed444f9cd7dffd9252150 compiler/typecheck/TcInteract.hs | 135 +++++++++++++-------- compiler/typecheck/TcType.hs | 8 +- compiler/typecheck/TcValidity.hs | 4 - testsuite/tests/typecheck/should_compile/T13943.hs | 68 +++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 5 files changed, 158 insertions(+), 58 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 a8fde1831f4b99885b8ed444f9cd7dffd9252150 From git at git.haskell.org Tue Oct 3 13:45:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 13:45:42 +0000 (UTC) Subject: [commit: ghc] master: Suppress error cascade in record fields (cb76754) Message-ID: <20171003134542.277E73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb767542307b41c91061e743a4a4f448949b34cf/ghc >--------------------------------------------------------------- commit cb767542307b41c91061e743a4a4f448949b34cf Author: Simon Peyton Jones Date: Tue Oct 3 14:42:56 2017 +0100 Suppress error cascade in record fields When a record contruction or pattern uses a data constructor that isn't in scope, we may produce spurious ambiguous-field errors (Trac #14307). E.g. f (A { fld = x }) = e where 'A' is not in scope. We want to draw attention to the out-of-scope data constructor first; once that is fixed we can think about the fields. This patch suppresses the field errors if the data con is out of scope. >--------------------------------------------------------------- cb767542307b41c91061e743a4a4f448949b34cf compiler/rename/RnPat.hs | 32 ++++++++++++++++-------- testsuite/tests/rename/should_fail/T14307.hs | 10 ++++++++ testsuite/tests/rename/should_fail/T14307.stderr | 2 ++ testsuite/tests/rename/should_fail/T2901.stderr | 4 --- testsuite/tests/rename/should_fail/T5372.stderr | 4 --- testsuite/tests/rename/should_fail/all.T | 1 + 6 files changed, 34 insertions(+), 19 deletions(-) diff --git a/compiler/rename/RnPat.hs b/compiler/rename/RnPat.hs index ce8f379..2846754 100644 --- a/compiler/rename/RnPat.hs +++ b/compiler/rename/RnPat.hs @@ -51,6 +51,7 @@ import RnUtils ( HsDocContext(..), newLocalBndrRn, bindLocalNames , warnUnusedMatches, newLocalBndrRn , checkDupNames, checkDupAndShadowedNames , checkTupSize , unknownSubordinateErr ) +import RnUnbound ( mkUnboundName ) import RnTypes import PrelNames import TyCon ( tyConName ) @@ -58,6 +59,7 @@ import ConLike import Type ( TyThing(..) ) import Name import NameSet +import OccName ( setOccNameSpace, tcName ) import RdrName import BasicTypes import Util @@ -589,13 +591,9 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) ; return (all_flds, mkFVs (getFieldIds all_flds)) } where mb_con = case ctxt of - HsRecFieldCon con | not (isUnboundName con) -> Just con - HsRecFieldPat con | not (isUnboundName con) -> Just con - _ {- update or isUnboundName con -} -> Nothing - -- The unbound name test is because if the constructor - -- isn't in scope the constructor lookup will add an error - -- add an error, but still return an unbound name. - -- We don't want that to screw up the dot-dot fill-in stuff. + HsRecFieldCon con -> Just con + HsRecFieldPat con -> Just con + _ {- update -} -> Nothing doc = case mb_con of Nothing -> text "constructor field name" @@ -624,11 +622,11 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) -- out of scope constructor) -> [LHsRecField GhcRn (Located arg)] -- Explicit fields -> RnM [LHsRecField GhcRn (Located arg)] -- Filled in .. fields - rn_dotdot Nothing _mb_con _flds -- No ".." at all - = return [] - rn_dotdot (Just {}) Nothing _flds -- Constructor out of scope - = return [] rn_dotdot (Just n) (Just con) flds -- ".." on record construction / pat match + | not (isUnboundName con) -- This test is because if the constructor + -- isn't in scope the constructor lookup will add + -- an error but still return an unbound name. We + -- don't want that to screw up the dot-dot fill-in stuff. = ASSERT( flds `lengthIs` n ) do { loc <- getSrcSpanM -- Rather approximate ; dd_flag <- xoptM LangExt.RecordWildCards @@ -665,6 +663,12 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) , let sel = flSelector fl , let arg_rdr = mkVarUnqual (flLabel fl) ] } + rn_dotdot _dotdot _mb_con _flds + = return [] + -- _dotdot = Nothing => No ".." at all + -- _mb_con = Nothing => Record update + -- _mb_con = Just unbound => Out of scope data constructor + check_disambiguation :: Bool -> Maybe Name -> RnM (Maybe Name) -- When disambiguation is on, return name of parent tycon. check_disambiguation disambig_ok mb_con @@ -679,6 +683,12 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) -- or 'Nothing' if it is a pattern synonym or not in scope. -- That's the parent to use for looking up record fields. find_tycon env con_name + | isUnboundName con_name + = Just (mkUnboundName (setOccNameSpace tcName (getOccName con_name))) + -- If the data con is not in scope, return an unboundName tycon + -- That way the calls to lookupRecFieldOcc in rn_fld won't generate + -- an error cascade; see Trac #14307 + | Just (AConLike (RealDataCon dc)) <- wiredInNameTyThing_maybe con_name = Just (tyConName (dataConTyCon dc)) -- Special case for [], which is built-in syntax diff --git a/testsuite/tests/rename/should_fail/T14307.hs b/testsuite/tests/rename/should_fail/T14307.hs new file mode 100644 index 0000000..9bb33b7 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T14307.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE NamedFieldPuns #-} + +module T14307 where + +data A = A { field :: Int } +data B = B { field :: Int } + +f :: B -> Int +f (C { field }) = field diff --git a/testsuite/tests/rename/should_fail/T14307.stderr b/testsuite/tests/rename/should_fail/T14307.stderr new file mode 100644 index 0000000..1470a40 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T14307.stderr @@ -0,0 +1,2 @@ + +T14307.hs:10:4: error: Not in scope: data constructor ‘C’ diff --git a/testsuite/tests/rename/should_fail/T2901.stderr b/testsuite/tests/rename/should_fail/T2901.stderr index 2128989..d5a5bbd 100644 --- a/testsuite/tests/rename/should_fail/T2901.stderr +++ b/testsuite/tests/rename/should_fail/T2901.stderr @@ -2,7 +2,3 @@ T2901.hs:6:5: error: Not in scope: data constructor ‘F.Foo’ No module named ‘F’ is imported. - -T2901.hs:6:13: error: - Not in scope: ‘F.field’ - No module named ‘F’ is imported. diff --git a/testsuite/tests/rename/should_fail/T5372.stderr b/testsuite/tests/rename/should_fail/T5372.stderr index f6a466e..d8b8e8f 100644 --- a/testsuite/tests/rename/should_fail/T5372.stderr +++ b/testsuite/tests/rename/should_fail/T5372.stderr @@ -2,7 +2,3 @@ T5372.hs:4:11: error: Not in scope: data constructor ‘MkS’ Perhaps you meant ‘T5372a.MkS’ (imported from T5372a) - -T5372.hs:4:17: error: - Not in scope: ‘x’ - Perhaps you meant ‘T5372a.x’ (imported from T5372a) diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index 9feee3d..b086372 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -129,3 +129,4 @@ test('T13644', normal, multimod_compile_fail, ['T13644','-v0']) test('T13568', normal, multimod_compile_fail, ['T13568','-v0']) test('T13947', normal, compile_fail, ['']) test('T13847', normal, multimod_compile_fail, ['T13847','-v0']) +test('T14307', normal, compile_fail, ['']) From git at git.haskell.org Tue Oct 3 14:12:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 14:12:46 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for #9725 (a02039c) Message-ID: <20171003141246.213563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a02039c7dcb4300b0aca80a994466a8f3039a3fc/ghc >--------------------------------------------------------------- commit a02039c7dcb4300b0aca80a994466a8f3039a3fc Author: Ryan Scott Date: Tue Oct 3 10:10:39 2017 -0400 Add regression test for #9725 Kind equalities saves the day! >--------------------------------------------------------------- a02039c7dcb4300b0aca80a994466a8f3039a3fc testsuite/tests/polykinds/T9725.hs | 51 ++++++++++++++++++++++++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + 2 files changed, 52 insertions(+) diff --git a/testsuite/tests/polykinds/T9725.hs b/testsuite/tests/polykinds/T9725.hs new file mode 100644 index 0000000..9a3d529 --- /dev/null +++ b/testsuite/tests/polykinds/T9725.hs @@ -0,0 +1,51 @@ +{-# LANGUAGE GADTs, DataKinds, KindSignatures, PolyKinds, FlexibleContexts, RankNTypes, ScopedTypeVariables #-} +module T9725 where + +data En = M Bool +class Kn (l :: En) + +instance Kn (M b) + +data Fac :: En -> * where + Mo :: Kn (M b) => Fac (M b) + +data Fm :: * -> * where + HiF :: Kn (ent b) => Fm (Fac (ent b)) -> Fm (O ent) + MoF :: Kn (M b) => Fm (Fac (M b)) + +data O :: (k -> En) -> * where + Hi :: Fac (ent k) -> O ent + +data Co :: (* -> *) -> * -> * where + Ab :: (t -> f t) -> Co f t + +-- Restricted kind signature: +--test :: forall (ent :: Bool -> En) . (forall i . Kn (ent i) => Fm (Fac (ent i))) -> Co Fm (O ent) + +test :: forall ent . (forall i . Kn (ent i) => Fm (Fac (ent i))) -> Co Fm (O ent) +test de = Ab h + where h :: O ent -> Fm (O ent) + h (Hi m at Mo) = HiF (d m) + d :: Kn (ent i) => Fac (ent i) -> Fm (Fac (ent i)) + d _ = de + +{- +9725.hs:27:25: + Could not deduce (Kn (ent k1)) arising from a use of ‘HiF’ + from the context (ent k1 ~ 'M b, Kn ('M b)) + bound by a pattern with constructor + Mo :: forall (b :: Bool). Kn ('M b) => Fac ('M b), + in an equation for ‘h’ + at 9725.hs:27:19-20 + In the expression: HiF (d m) + In an equation for ‘h’: h (Hi m at Mo) = HiF (d m) + In an equation for ‘test’: + test de + = Ab h + where + h :: O ent -> Fm (O ent) + h (Hi m at Mo) = HiF (d m) + d :: Kn (ent i) => Fac (ent i) -> Fm (Fac (ent i)) + d _ = de +Failed, modules loaded: none. +-} diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 0e5bcf1..fc7249e 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -103,6 +103,7 @@ test('T9263', normal, run_command, ['$MAKE -s --no-print-directory T9263']) test('T9063', normal, compile, ['']) test('T9200', normal, compile, ['']) test('T9200b', normal, compile_fail, ['']) +test('T9725', normal, compile, ['']) test('T9750', normal, compile, ['']) test('T9569', normal, compile, ['']) test('T9838', normal, multimod_compile, ['T9838.hs','-v0']) From git at git.haskell.org Tue Oct 3 14:42:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 14:42:46 +0000 (UTC) Subject: [commit: ghc] master: Revert installing texinfo in CI systems (a36eea1) Message-ID: <20171003144246.AF3643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a36eea1af4faabdf8fcf0a68dbd4f9946bf6d65a/ghc >--------------------------------------------------------------- commit a36eea1af4faabdf8fcf0a68dbd4f9946bf6d65a Author: Joachim Breitner Date: Tue Oct 3 10:42:08 2017 -0400 Revert installing texinfo in CI systems This reverts commit 00ff02352f07bff7d422e4e48e4e5df9a0b63d83. This reverts commit 11a59de25d49f999eed0ea55df29d916a66ecd91. >--------------------------------------------------------------- a36eea1af4faabdf8fcf0a68dbd4f9946bf6d65a .circleci/config.yml | 2 +- .travis.yml | 1 - 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index a19dc24..6ee6c48 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -10,7 +10,7 @@ jobs: name: git command: | apt-get update - apt-get install -y git openssh-client make automake autoconf gcc perl python3 texinfo + apt-get install -y git openssh-client make automake autoconf gcc perl python3 - checkout - run: name: submodules diff --git a/.travis.yml b/.travis.yml index 55995b7..09d9fef 100644 --- a/.travis.yml +++ b/.travis.yml @@ -22,7 +22,6 @@ addons: - alex-3.1.7 - happy-1.19.5 - python3 - - texinfo #- llvm-3.7 before_install: From git at git.haskell.org Tue Oct 3 14:48:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 14:48:37 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: user-guide: Mention COMPLETE pragma in release notes (b5c50d6) Message-ID: <20171003144837.3A17E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/b5c50d60111ec826a76fc6415dcb1bce60fe8f42/ghc >--------------------------------------------------------------- commit b5c50d60111ec826a76fc6415dcb1bce60fe8f42 Author: Ben Gamari Date: Mon Oct 2 10:59:13 2017 -0400 user-guide: Mention COMPLETE pragma in release notes >--------------------------------------------------------------- b5c50d60111ec826a76fc6415dcb1bce60fe8f42 docs/users_guide/8.2.1-notes.rst | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 43134fa..b591549 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -54,6 +54,10 @@ Language - Support for overloaded record fields via a new ``HasField`` class and associated compiler logic (see :ref:`record-field-selector-polymorphism`) +- GHC now recognizes the ``COMPLETE`` language pragma, allowing the user to + specify sets of patterns (including pattern synonyms) which constitute a + complete pattern match. See :ref:`complete-pragma` for details. + Compiler ~~~~~~~~ From git at git.haskell.org Tue Oct 3 14:48:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 14:48:41 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add support for producing position-independent executables (f701e15) Message-ID: <20171003144841.10B523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/f701e15bc0d945ea059aa5ebb4bbd506a4f1d7a3/ghc >--------------------------------------------------------------- commit f701e15bc0d945ea059aa5ebb4bbd506a4f1d7a3 Author: Ben Gamari Date: Tue Aug 22 11:41:47 2017 -0400 Add support for producing position-independent executables Previously due to #12759 we disabled PIE support entirely. However, this breaks the user's ability to produce PIEs. Add an explicit flag, -fPIE, allowing the user to build PIEs. Test Plan: Validate Reviewers: rwbarton, austin, simonmar Subscribers: trommler, simonmar, trofi, jrtc27, thomie GHC Trac Issues: #12759, #13702 Differential Revision: https://phabricator.haskell.org/D3589 (cherry-picked from commit 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a) >--------------------------------------------------------------- f701e15bc0d945ea059aa5ebb4bbd506a4f1d7a3 compiler/cmm/CmmPipeline.hs | 2 +- compiler/codeGen/StgCmmCon.hs | 4 +-- compiler/main/DriverPipeline.hs | 10 +++----- compiler/main/DynFlags.hs | 48 ++++++++++++++++++++++++++--------- compiler/main/SysTools.hs | 15 +---------- compiler/nativeGen/AsmCodeGen.hs | 6 ++--- compiler/nativeGen/PIC.hs | 33 ++++++++++++------------ compiler/nativeGen/PPC/CodeGen.hs | 6 ++--- compiler/nativeGen/SPARC/CodeGen.hs | 2 +- compiler/nativeGen/X86/CodeGen.hs | 4 +-- docs/users_guide/phases.rst | 24 ++++++++++++++++++ docs/users_guide/shared_libs.rst | 4 +++ testsuite/tests/dynlibs/Makefile | 6 +++++ testsuite/tests/dynlibs/T13702.hs | 9 +++++++ testsuite/tests/dynlibs/T13702.stdout | 2 ++ testsuite/tests/dynlibs/T13702a.hs | 12 +++++++++ testsuite/tests/dynlibs/all.T | 4 +++ 17 files changed, 131 insertions(+), 60 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f701e15bc0d945ea059aa5ebb4bbd506a4f1d7a3 From git at git.haskell.org Tue Oct 3 14:48:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 14:48:43 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: user-guide: Fix :since: annotation of -pie and add documentation for -fPIE (a2883ef) Message-ID: <20171003144843.C28AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/a2883ef3a7fc4ccb82a51ff09b69b0e2f667d516/ghc >--------------------------------------------------------------- commit a2883ef3a7fc4ccb82a51ff09b69b0e2f667d516 Author: Ben Gamari Date: Mon Oct 2 18:02:40 2017 -0400 user-guide: Fix :since: annotation of -pie and add documentation for -fPIE [skip ci] (cherry picked from commit d5e60de307874432f42aa7fea2460e6901c057e1) >--------------------------------------------------------------- a2883ef3a7fc4ccb82a51ff09b69b0e2f667d516 docs/users_guide/phases.rst | 14 ++++++++++++-- 1 file changed, 12 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst index 5be93f8..d9a59ab 100644 --- a/docs/users_guide/phases.rst +++ b/docs/users_guide/phases.rst @@ -458,6 +458,16 @@ Options affecting code generation Windows, position-independent code is never used so the flag is a no-op on that platform. +.. ghc-flag:: -fPIE + :shortdesc: Generate code for a position-independent executable (where available) + :type: dynamic + :category: codegen + + Generate code in such a way to be linkable into a position-independent + executable This currently works on Linux x86 and x86-64. On Windows, + position-independent code is never used so the flag is a no-op on that + platform. To link the final executable use :ghc-flag:`-pie`. + .. ghc-flag:: -dynamic :noindex: @@ -883,7 +893,7 @@ for example). :type: dynamic :category: linking - :since: 8.2.1 + :since: 8.2.2 This instructs the linker to produce a position-independent executable. This flag is only valid while producing executables and all object code @@ -900,4 +910,4 @@ for example). loaded into the address space of another Haskell process. Also, you may need to use the :ghc-flags:`-rdynamic` flag to ensure that - that symbols are not dropped from your PIE object. + that symbols are not dropped from your PIE objects. From git at git.haskell.org Tue Oct 3 14:48:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 14:48:46 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: [RTS] Make -po work (18d66fe) Message-ID: <20171003144846.8DB9B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/18d66feb0620512adefc00e0aee5578f3058c23c/ghc >--------------------------------------------------------------- commit 18d66feb0620512adefc00e0aee5578f3058c23c Author: Bartosz Nitka Date: Thu Sep 14 02:50:05 2017 -0700 [RTS] Make -po work db2a667655506c43dd3c8260d29031bde55f1bee added `-po` option, but the part that parses it was missing. Test Plan: On a simple file: ``` ./inplace/bin/ghc-stage2 A.hs -prof -main-is A; ./A +RTS -P -potest ``` produced test.prof file and didn't produce A.prof file. ``` ./A +RTS -P ``` produced A.prof file Reviewers: simonmar, bgamari, austin, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3946 (cherry picked from commit b6b56dd1b6adc9051593955eecaef85c9d6e96b8) >--------------------------------------------------------------- 18d66feb0620512adefc00e0aee5578f3058c23c rts/RtsFlags.c | 13 +++++++++++-- 1 file changed, 11 insertions(+), 2 deletions(-) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index 0a12ba3..c2de960 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -183,11 +183,12 @@ void initRtsFlagsDefaults(void) RtsFlags.DebugFlags.compact = false; #if defined(PROFILING) - RtsFlags.CcFlags.doCostCentres = 0; + RtsFlags.CcFlags.doCostCentres = COST_CENTRES_NONE; + RtsFlags.CcFlags.outputFileNameStem = NULL; #endif /* PROFILING */ RtsFlags.ProfFlags.doHeapProfile = false; - RtsFlags.ProfFlags. heapProfileInterval = USToTime(100000); // 100ms + RtsFlags.ProfFlags.heapProfileInterval = USToTime(100000); // 100ms #ifdef PROFILING RtsFlags.ProfFlags.includeTSOs = false; @@ -1072,6 +1073,14 @@ error = true; case 'j': RtsFlags.CcFlags.doCostCentres = COST_CENTRES_JSON; break; + case 'o': + if (rts_argv[arg][3] == '\0') { + errorBelch("flag -po expects an argument"); + error = true; + break; + } + RtsFlags.CcFlags.outputFileNameStem = rts_argv[arg]+3; + break; case '\0': if (rts_argv[arg][1] == 'P') { RtsFlags.CcFlags.doCostCentres = COST_CENTRES_VERBOSE; From git at git.haskell.org Tue Oct 3 14:48:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 14:48:49 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Model divergence of retry# as ThrowsExn, not Diverges (6a32850) Message-ID: <20171003144849.5497B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/6a328506526e3c425bdb61058083fbfb880f71c3/ghc >--------------------------------------------------------------- commit 6a328506526e3c425bdb61058083fbfb880f71c3 Author: Ben Gamari Date: Wed Sep 13 12:22:27 2017 -0400 Model divergence of retry# as ThrowsExn, not Diverges The demand signature of the retry# primop previously had a Diverges result. However, this caused the demand analyser to conclude that a program of the shape, catchRetry# (... >> retry#) would diverge. Of course, this is plainly wrong; catchRetry#'s sole reason to exist is to "catch" the "exception" thrown by retry#. While catchRetry#'s demand signature correctly had the ExnStr flag set on its first argument, indicating that it should catch divergence, the logic associated with this flag doesn't apply to Diverges results. This resulted in #14171. The solution here is to treat the divergence of retry# as an exception. Namely, give it a result type of ThrowsExn rather than Diverges. Updates stm submodule for tests. Test Plan: Validate with T14171 Reviewers: simonpj, austin Subscribers: rwbarton, thomie GHC Trac Issues: #14171, #8091 Differential Revision: https://phabricator.haskell.org/D3919 (cherry picked from commit 10a1a4781c646f81ca9e2ef7a2585df2cbe3a014) >--------------------------------------------------------------- 6a328506526e3c425bdb61058083fbfb880f71c3 compiler/basicTypes/Demand.hs | 1 + compiler/prelude/primops.txt.pp | 7 +++++-- libraries/stm | 2 +- 3 files changed, 7 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 98b1915..a2ea238 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -1437,6 +1437,7 @@ postProcessDmdType du@(JD { sd = ss }) (DmdType fv _ res_ty) postProcessDmdResult :: Str () -> DmdResult -> DmdResult postProcessDmdResult Lazy _ = topRes postProcessDmdResult (Str ExnStr _) ThrowsExn = topRes -- Key point! +-- Note that only ThrowsExn results can be caught, not Diverges postProcessDmdResult _ res = res postProcessDmdEnv :: DmdShell -> DmdEnv -> DmdEnv diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index ef83efb..e31cff2 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -2072,7 +2072,7 @@ primop AtomicallyOp "atomically#" GenPrimOp out_of_line = True has_side_effects = True --- NB: retry#'s strictness information specifies it to return bottom. +-- NB: retry#'s strictness information specifies it to throw an exception -- This lets the compiler perform some extra simplifications, since retry# -- will technically never return. -- @@ -2082,10 +2082,13 @@ primop AtomicallyOp "atomically#" GenPrimOp -- with: -- retry# s1 -- where 'e' would be unreachable anyway. See Trac #8091. +-- +-- Note that it *does not* return botRes as the "exception" that is throw may be +-- "caught" by catchRetry#. This mistake caused #14171. primop RetryOp "retry#" GenPrimOp State# RealWorld -> (# State# RealWorld, a #) with - strictness = { \ _arity -> mkClosedStrictSig [topDmd] botRes } + strictness = { \ _arity -> mkClosedStrictSig [topDmd] exnRes } out_of_line = True has_side_effects = True diff --git a/libraries/stm b/libraries/stm index 9c3c3bb..b6e863e 160000 --- a/libraries/stm +++ b/libraries/stm @@ -1 +1 @@ -Subproject commit 9c3c3bb28834d1ba9574be7f887c8914afd4232c +Subproject commit b6e863e517bdcc3c5de1fbcb776a3fd7e6fe2103 From git at git.haskell.org Tue Oct 3 18:49:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 18:49:29 +0000 (UTC) Subject: [commit: ghc] master: Sync base/changelog.md (55001c0) Message-ID: <20171003184929.860003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/55001c0c9934de2cf94d3879cea20c0faf73695c/ghc >--------------------------------------------------------------- commit 55001c0c9934de2cf94d3879cea20c0faf73695c Author: Herbert Valerio Riedel Date: Tue Oct 3 20:46:23 2017 +0200 Sync base/changelog.md This updates the base-4.10.0.0 entry heading which has diverged from http://hackage.haskell.org/package/base-4.10.0.0/src/changelog.md and while at it also sets the GHC version for the base-4.11 entry to avoid confusion about what GHC 8.2.2's base is going to include. [skip ci] >--------------------------------------------------------------- 55001c0c9934de2cf94d3879cea20c0faf73695c libraries/base/changelog.md | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 4671c71..2ce4fd3 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -1,7 +1,7 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) ## 4.11.0.0 *TBA* - * Bundled with GHC *TBA* + * Bundled with GHC 8.4.1 * Add `Alternative` instance for `ZipList` (#13520) @@ -53,8 +53,8 @@ * Add `installSEHHandlers` to `MiscFlags` in `GHC.RTS.Flags` to determine if exception handling is enabled. -## 4.10.0.0 *April 2017* - * Bundled with GHC *TBA* +## 4.10.0.0 *July 2017* + * Bundled with GHC 8.2.1 * `Data.Type.Bool.Not` given a type family dependency (#12057). From git at git.haskell.org Tue Oct 3 21:56:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:56:10 +0000 (UTC) Subject: [commit: ghc] master: Add ability to produce crash dumps on Windows (ec9ac20) Message-ID: <20171003215610.AF9A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ec9ac20d0964c9f1323105b5a2df24f50d4fe3ef/ghc >--------------------------------------------------------------- commit ec9ac20d0964c9f1323105b5a2df24f50d4fe3ef Author: Tamar Christina Date: Tue Oct 3 13:37:52 2017 -0400 Add ability to produce crash dumps on Windows It's often hard to debug things like segfaults on Windows, mostly because gdb isn't always of use and users don't know how to effectively use it. This patch provides a way to create a crash drump by passing `+RTS --generate-crash-dumps` as an option. If any unhandled exception is triggered a dump is made that contains enough information to be able to diagnose things successfully. Currently the created dumps are a bit big because I include all registers, code and threads information. This looks like ``` $ testsuite/tests/rts/derefnull.run/derefnull.exe +RTS --generate-crash-dumps Access violation in generated code when reading 0000000000000000 Crash dump created. Dump written to: E:\msys64\tmp\ghc-20170901-220250-11216-16628.dmp ``` Test Plan: ./validate Reviewers: austin, hvr, bgamari, erikd, simonmar Reviewed By: bgamari, simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3912 >--------------------------------------------------------------- ec9ac20d0964c9f1323105b5a2df24f50d4fe3ef docs/users_guide/8.4.1-notes.rst | 3 ++ docs/users_guide/runtime_control.rst | 7 +++++ includes/rts/Flags.h | 1 + libraries/base/GHC/RTS/Flags.hsc | 2 ++ libraries/base/changelog.md | 3 ++ rts/RtsFlags.c | 15 ++++++++++ rts/package.conf.in | 1 + rts/win32/veh_excn.c | 58 +++++++++++++++++++++++++++++++++++- rts/win32/veh_excn.h | 3 ++ 9 files changed, 92 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ec9ac20d0964c9f1323105b5a2df24f50d4fe3ef From git at git.haskell.org Tue Oct 3 21:56:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:56:13 +0000 (UTC) Subject: [commit: ghc] master: Optimize linker by minimizing calls to tryGCC to avoid fork/exec overhead. (8d64745) Message-ID: <20171003215613.7AB323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8d647450655713e035091349d5163a1a28be18f4/ghc >--------------------------------------------------------------- commit 8d647450655713e035091349d5163a1a28be18f4 Author: Tamar Christina Date: Tue Oct 3 14:55:28 2017 -0400 Optimize linker by minimizing calls to tryGCC to avoid fork/exec overhead. On Windows process creations are fairly expensive. As such calling them in what's essentially a hot loop is also fairly expensive. Each time we make a call to `tryGCC` the following fork/exec/wait happen ``` gcc -> realgcc -> cc1 ``` This is very problematic, because according to the profiler about 20% of the time is spent on just process creation and spin time. The goal of the patch is to mitigate this by asking GCC once for it's search directories, caching these (because it's very hard to change these at all after the process started since GCC's base dirs don't change unless with extra supplied `-B` flags.). We also do the same for the `findSysDll` function, since this computes the search path every time by registery accesses etc. These changes and D3909 drop GHC on Windows startup time from 2-3s to 0.5s. The remaining issue is a 1.5s wait lock on `CONIN$` which can be addressed with the new I/O manager code. But this makes GHCi as responsive on Windows as GHC 7.8 was. Test Plan: ./validate Reviewers: austin, hvr, bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3910 >--------------------------------------------------------------- 8d647450655713e035091349d5163a1a28be18f4 compiler/ghci/Linker.hs | 125 ++++++++++++++++++++++++++++++++------- docs/users_guide/8.4.1-notes.rst | 10 ++-- 2 files changed, 109 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8d647450655713e035091349d5163a1a28be18f4 From git at git.haskell.org Tue Oct 3 21:56:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:56:17 +0000 (UTC) Subject: [commit: ghc] master: Track the order of user-written tyvars in DataCon (ef26182) Message-ID: <20171003215617.83BEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef26182e2014b0a2a029ae466a4b121bf235e4e4/ghc >--------------------------------------------------------------- commit ef26182e2014b0a2a029ae466a4b121bf235e4e4 Author: Ryan Scott Date: Tue Oct 3 14:58:27 2017 -0400 Track the order of user-written tyvars in DataCon After typechecking a data constructor's type signature, its type variables are partitioned into two distinct groups: the universally quantified type variables and the existentially quantified type variables. Then, when prompted for the type of the data constructor, GHC gives this: ```lang=haskell MkT :: forall . (...) ``` For H98-style datatypes, this is a fine thing to do. But for GADTs, this can sometimes produce undesired results with respect to `TypeApplications`. For instance, consider this datatype: ```lang=haskell data T a where MkT :: forall b a. b -> T a ``` Here, the user clearly intended to have `b` be available for visible type application before `a`. That is, the user would expect `MkT @Int @Char` to be of type `Int -> T Char`, //not// `Char -> T Int`. But alas, up until now that was not how GHC operated—regardless of the order in which the user actually wrote the tyvars, GHC would give `MkT` the type: ```lang=haskell MkT :: forall a b. b -> T a ``` Since `a` is universal and `b` is existential. This makes predicting what order to use for `TypeApplications` quite annoying, as demonstrated in #11721 and #13848. This patch cures the problem by tracking more carefully the order in which a user writes type variables in data constructor type signatures, either explicitly (with a `forall`) or implicitly (without a `forall`, in which case the order is inferred). This is accomplished by adding a new field `dcUserTyVars` to `DataCon`, which is a subset of `dcUnivTyVars` and `dcExTyVars` that is permuted to the order in which the user wrote them. For more details, refer to `Note [DataCon user type variables]` in `DataCon.hs`. An interesting consequence of this design is that more data constructors require wrappers. This is because the workers always expect the first arguments to be the universal tyvars followed by the existential tyvars, so when the user writes the tyvars in a different order, a wrapper type is needed to swizzle the tyvars around to match the order that the worker expects. For more details, refer to `Note [Data con wrappers and GADT syntax]` in `MkId.hs`. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonpj Reviewed By: goldfire, simonpj Subscribers: ezyang, goldfire, rwbarton, thomie GHC Trac Issues: #11721, #13848 Differential Revision: https://phabricator.haskell.org/D3687 >--------------------------------------------------------------- ef26182e2014b0a2a029ae466a4b121bf235e4e4 compiler/backpack/RnModIface.hs | 4 +- compiler/basicTypes/DataCon.hs | 237 ++++++++++++++++----- compiler/basicTypes/DataCon.hs-boot | 6 +- compiler/basicTypes/MkId.hs | 57 ++++- compiler/iface/BuildTyCl.hs | 25 ++- compiler/iface/IfaceSyn.hs | 59 ++--- compiler/iface/IfaceType.hs | 13 +- compiler/iface/MkIface.hs | 21 +- compiler/iface/TcIface.hs | 26 ++- compiler/prelude/TysWiredIn.hs | 19 +- compiler/typecheck/TcTyClsDecls.hs | 131 +++++------- compiler/types/TyCoRep.hs | 15 +- compiler/vectorise/Vectorise/Generic/PData.hs | 8 +- compiler/vectorise/Vectorise/Type/TyConDecl.hs | 5 +- docs/users_guide/8.4.1-notes.rst | 11 + testsuite/tests/gadt/gadtSyntaxFail003.stderr | 2 +- testsuite/tests/ghci/scripts/T11721.script | 7 + testsuite/tests/ghci/scripts/T11721.stdout | 3 + testsuite/tests/ghci/scripts/all.T | 1 + testsuite/tests/patsyn/should_fail/T11010.stderr | 2 +- testsuite/tests/polykinds/T8566.stderr | 2 +- testsuite/tests/typecheck/should_compile/T13848.hs | 41 ++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 23 files changed, 493 insertions(+), 203 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 ef26182e2014b0a2a029ae466a4b121bf235e4e4 From git at git.haskell.org Tue Oct 3 21:56:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:56:20 +0000 (UTC) Subject: [commit: ghc] master: Implement Div, Mod, and Log for type-level nats. (fa8035e) Message-ID: <20171003215620.5C7353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fa8035e3ee83aff5a20fc5e7e2697bac1686d6a6/ghc >--------------------------------------------------------------- commit fa8035e3ee83aff5a20fc5e7e2697bac1686d6a6 Author: Iavor Diatchki Date: Tue Oct 3 14:58:47 2017 -0400 Implement Div, Mod, and Log for type-level nats. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: RyanGlScott, dfeuer, adamgundry, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4002 >--------------------------------------------------------------- fa8035e3ee83aff5a20fc5e7e2697bac1686d6a6 compiler/prelude/PrelNames.hs | 36 ++--- compiler/typecheck/TcTypeNats.hs | 146 +++++++++++++++++++++ libraries/base/GHC/TypeLits.hs | 1 + libraries/base/GHC/TypeNats.hs | 13 ++ libraries/base/changelog.md | 3 + testsuite/tests/ghci/scripts/T9181.stdout | 7 + .../typecheck/should_compile/TcTypeNatSimple.hs | 15 +++ 7 files changed, 206 insertions(+), 15 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fa8035e3ee83aff5a20fc5e7e2697bac1686d6a6 From git at git.haskell.org Tue Oct 3 21:56:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:56:24 +0000 (UTC) Subject: [commit: ghc] master: Include libraries which fill holes as deps when linking. (f3f624a) Message-ID: <20171003215624.460933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f3f624aeb1360c1f902930b3cc62346d2e5201c0/ghc >--------------------------------------------------------------- commit f3f624aeb1360c1f902930b3cc62346d2e5201c0 Author: Edward Z. Yang Date: Tue Oct 3 15:08:24 2017 -0400 Include libraries which fill holes as deps when linking. Fixes the issue reported at https://github.com/haskell/cabal/issues/4755 and fixes #14304 in the GHC tracker. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: bgamari, austin, goldfire Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14304 Differential Revision: https://phabricator.haskell.org/D4057 >--------------------------------------------------------------- f3f624aeb1360c1f902930b3cc62346d2e5201c0 compiler/main/Packages.hs | 4 ++- testsuite/tests/backpack/cabal/T14304/Makefile | 36 ++++++++++++++++++++++ .../backpack/cabal/{bkpcabal01 => T14304}/Setup.hs | 0 .../cabal/T14304/T14304.stderr} | 2 ++ testsuite/tests/backpack/cabal/T14304/all.T | 9 ++++++ .../tests/backpack/cabal/T14304/indef/Indef.hs | 3 ++ .../tests/backpack/cabal/T14304/indef/Sig.hsig | 2 ++ .../tests/backpack/cabal/T14304/indef/indef.cabal | 9 ++++++ testsuite/tests/backpack/cabal/T14304/p/P.hs | 3 ++ testsuite/tests/backpack/cabal/T14304/p/p.cabal | 8 +++++ .../T8025/A.hs => backpack/cabal/T14304/th/TH.hs} | 4 +-- testsuite/tests/backpack/cabal/T14304/th/th.cabal | 9 ++++++ 12 files changed, 86 insertions(+), 3 deletions(-) diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index 172e181..949cc0f 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -1878,8 +1878,10 @@ listVisibleModuleNames dflags = -- | Find all the 'PackageConfig' in both the preload packages from 'DynFlags' and corresponding to the list of -- 'PackageConfig's getPreloadPackagesAnd :: DynFlags -> [PreloadUnitId] -> IO [PackageConfig] -getPreloadPackagesAnd dflags pkgids = +getPreloadPackagesAnd dflags pkgids0 = let + pkgids = pkgids0 ++ map (toInstalledUnitId . moduleUnitId . snd) + (thisUnitIdInsts dflags) state = pkgState dflags pkg_map = pkgIdMap state preload = preloadPackages state diff --git a/testsuite/tests/backpack/cabal/T14304/Makefile b/testsuite/tests/backpack/cabal/T14304/Makefile new file mode 100644 index 0000000..1f58184 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/Makefile @@ -0,0 +1,36 @@ +TOP=../../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +SETUP='$(PWD)/Setup' -v0 +CONFIGURE=$(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db='$(PWD)/tmp.d' --prefix='$(PWD)/inst' --enable-shared + +T14304: clean + $(MAKE) -s --no-print-directory clean + '$(GHC_PKG)' init tmp.d + '$(TEST_HC)' -v0 --make Setup + # typecheck indef + rm -rf indef/dist + (cd indef; $(CONFIGURE) --ipid "indef-0.1") + (cd indef; $(SETUP) build) + (cd indef; $(SETUP) copy) + (cd indef; $(SETUP) register) + # build p + rm -rf p/dist + (cd p; $(CONFIGURE) --ipid "p-0.1") + (cd p; $(SETUP) build) + (cd p; $(SETUP) copy) + (cd p; $(SETUP) register) + # build indef instantiated with p + rm -rf indef/dist + (cd indef; $(CONFIGURE) --ipid "indef-0.1" --instantiate-with "Sig=p-0.1:P") + (cd indef; $(SETUP) build) + (cd indef; $(SETUP) copy) + (cd indef; $(SETUP) register) + # build th (which tests if we have correct linkage) + rm -rf th/dist + (cd th; $(CONFIGURE)) + (cd th; $(SETUP) build) + +clean : + $(RM) -r tmp.d inst dist Setup$(exeext) diff --git a/testsuite/tests/backpack/cabal/bkpcabal01/Setup.hs b/testsuite/tests/backpack/cabal/T14304/Setup.hs similarity index 100% copy from testsuite/tests/backpack/cabal/bkpcabal01/Setup.hs copy to testsuite/tests/backpack/cabal/T14304/Setup.hs diff --git a/testsuite/tests/typecheck/T13168/T13168.stderr b/testsuite/tests/backpack/cabal/T14304/T14304.stderr similarity index 66% copy from testsuite/tests/typecheck/T13168/T13168.stderr copy to testsuite/tests/backpack/cabal/T14304/T14304.stderr index e69dbaa..89a07b9 100644 --- a/testsuite/tests/typecheck/T13168/T13168.stderr +++ b/testsuite/tests/backpack/cabal/T14304/T14304.stderr @@ -2,3 +2,5 @@ Warning: -rtsopts and -with-rtsopts have no effect with -shared. Call hs_init_ghc() from your main() function to set these options. Warning: -rtsopts and -with-rtsopts have no effect with -shared. Call hs_init_ghc() from your main() function to set these options. +Warning: -rtsopts and -with-rtsopts have no effect with -shared. + Call hs_init_ghc() from your main() function to set these options. diff --git a/testsuite/tests/backpack/cabal/T14304/all.T b/testsuite/tests/backpack/cabal/T14304/all.T new file mode 100644 index 0000000..f25285d --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/all.T @@ -0,0 +1,9 @@ +if config.cleanup: + cleanup = 'CLEANUP=1' +else: + cleanup = 'CLEANUP=0' + +test('T14304', + extra_files(['p', 'indef', 'th', 'Setup.hs']), + run_command, + ['$MAKE -s --no-print-directory T14304 ' + cleanup]) diff --git a/testsuite/tests/backpack/cabal/T14304/indef/Indef.hs b/testsuite/tests/backpack/cabal/T14304/indef/Indef.hs new file mode 100644 index 0000000..0bd438e --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/indef/Indef.hs @@ -0,0 +1,3 @@ +module Indef where +import Sig +data T = MkT B diff --git a/testsuite/tests/backpack/cabal/T14304/indef/Sig.hsig b/testsuite/tests/backpack/cabal/T14304/indef/Sig.hsig new file mode 100644 index 0000000..a37b190 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/indef/Sig.hsig @@ -0,0 +1,2 @@ +signature Sig where +data B diff --git a/testsuite/tests/backpack/cabal/T14304/indef/indef.cabal b/testsuite/tests/backpack/cabal/T14304/indef/indef.cabal new file mode 100644 index 0000000..d89f055 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/indef/indef.cabal @@ -0,0 +1,9 @@ +name: indef +version: 1.0 +build-type: Simple +cabal-version: >= 2.0 + +library + build-depends: base + signatures: Sig + exposed-modules: Indef diff --git a/testsuite/tests/backpack/cabal/T14304/p/P.hs b/testsuite/tests/backpack/cabal/T14304/p/P.hs new file mode 100644 index 0000000..f570e0b --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/p/P.hs @@ -0,0 +1,3 @@ +module P where +type B = Foo +newtype Foo = Foo Double diff --git a/testsuite/tests/backpack/cabal/T14304/p/p.cabal b/testsuite/tests/backpack/cabal/T14304/p/p.cabal new file mode 100644 index 0000000..f49ce42 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/p/p.cabal @@ -0,0 +1,8 @@ +name: p +version: 1.0 +build-type: Simple +cabal-version: >= 2.0 + +library + build-depends: base + exposed-modules: P diff --git a/testsuite/tests/th/should_compile/T8025/A.hs b/testsuite/tests/backpack/cabal/T14304/th/TH.hs similarity index 51% copy from testsuite/tests/th/should_compile/T8025/A.hs copy to testsuite/tests/backpack/cabal/T14304/th/TH.hs index c0e3083..5d921cf 100644 --- a/testsuite/tests/th/should_compile/T8025/A.hs +++ b/testsuite/tests/backpack/cabal/T14304/th/TH.hs @@ -1,3 +1,3 @@ {-# LANGUAGE TemplateHaskell #-} -module A where -a = [|3|] +module TH where +$( return [] ) diff --git a/testsuite/tests/backpack/cabal/T14304/th/th.cabal b/testsuite/tests/backpack/cabal/T14304/th/th.cabal new file mode 100644 index 0000000..2b17f09 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/th/th.cabal @@ -0,0 +1,9 @@ +name: th +version: 1.0 +build-type: Simple +cabal-version: >= 2.0 + +library + build-depends: p, indef, base + mixins: p (P as Sig) + exposed-modules: TH From git at git.haskell.org Tue Oct 3 21:56:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:56:27 +0000 (UTC) Subject: [commit: ghc] master: genapply: Explicitly specify arguments (de1b802) Message-ID: <20171003215627.082C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/de1b802b651de5397bb3c42cdf0189fdc41a8f82/ghc >--------------------------------------------------------------- commit de1b802b651de5397bb3c42cdf0189fdc41a8f82 Author: Moritz Angermann Date: Tue Oct 3 15:06:29 2017 -0400 genapply: Explicitly specify arguments We seem to not be feeding either live registers or the arguments when generating the fast call in genapply. This results in strange signature missmatches between the callee (expecting no registers) and the call site, expecting to pass registers. Test Plan: validate Reviewers: bgamari, simonmar, austin Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4029 >--------------------------------------------------------------- de1b802b651de5397bb3c42cdf0189fdc41a8f82 utils/genapply/Main.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/genapply/Main.hs b/utils/genapply/Main.hs index 9248c22..b30c9f8 100644 --- a/utils/genapply/Main.hs +++ b/utils/genapply/Main.hs @@ -858,7 +858,7 @@ genApplyFast regstatus args = nest 4 (vcat [ text "Sp_adj" <> parens (int (-sp_offset)) <> semi, saveRegOffs reg_locs, - mkJump regstatus fun_ret_label [] [] <> semi + mkJump regstatus fun_ret_label [] args <> semi ]), char '}' ]), From git at git.haskell.org Tue Oct 3 21:56:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:56:29 +0000 (UTC) Subject: [commit: ghc] master: base: Add missing @since annotations in GHC.TypeNats (377d5a2) Message-ID: <20171003215629.D0A7E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/377d5a262ba7e065dc6fb4683a8053f0e5e1379c/ghc >--------------------------------------------------------------- commit 377d5a262ba7e065dc6fb4683a8053f0e5e1379c Author: Ben Gamari Date: Tue Oct 3 15:04:16 2017 -0400 base: Add missing @since annotations in GHC.TypeNats [skip ci] >--------------------------------------------------------------- 377d5a262ba7e065dc6fb4683a8053f0e5e1379c libraries/base/GHC/TypeNats.hs | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/libraries/base/GHC/TypeNats.hs b/libraries/base/GHC/TypeNats.hs index e3322a2..a5ee0fc 100644 --- a/libraries/base/GHC/TypeNats.hs +++ b/libraries/base/GHC/TypeNats.hs @@ -103,6 +103,8 @@ infixl 7 * infixr 8 ^ -- | Comparison of type-level naturals, as a constraint. +-- +-- @since 4.7.0.0 type x <= y = (x <=? y) ~ 'True -- | Comparison of type-level naturals, as a function. @@ -117,12 +119,18 @@ Please let us know, if you encounter discrepancies between the two. -} type family (m :: Nat) <=? (n :: Nat) :: Bool -- | Addition of type-level naturals. +-- +-- @since 4.7.0.0 type family (m :: Nat) + (n :: Nat) :: Nat -- | Multiplication of type-level naturals. +-- +-- @since 4.7.0.0 type family (m :: Nat) * (n :: Nat) :: Nat -- | Exponentiation of type-level naturals. +-- +-- @since 4.7.0.0 type family (m :: Nat) ^ (n :: Nat) :: Nat -- | Subtraction of type-level naturals. @@ -132,14 +140,20 @@ type family (m :: Nat) - (n :: Nat) :: Nat -- | Division (round down) of natural numbers. -- @Div x 0@ is undefined (i.e., it cannot be reduced). +-- +-- @since 4.11.0.0 type family Div (m :: Nat) (n :: Nat) :: Nat -- | Modulus of natural numbers. -- @Mod x 0@ is undefined (i.e., it cannot be reduced). +-- +-- @since 4.11.0.0 type family Mod (m :: Nat) (n :: Nat) :: Nat -- | Log base 2 (round down) of natural numbers. -- @Log 0@ is undefined (i.e., it cannot be reduced). +-- +-- @since 4.11.0.0 type family Log2 (m :: Nat) :: Nat -------------------------------------------------------------------------------- From git at git.haskell.org Tue Oct 3 21:56:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:56:32 +0000 (UTC) Subject: [commit: ghc] master: Don't pass HscEnv to functions in the Hsc monad (4899a86) Message-ID: <20171003215632.A12C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4899a86b69a3cf8b487329d5db8bb205152950ce/ghc >--------------------------------------------------------------- commit 4899a86b69a3cf8b487329d5db8bb205152950ce Author: Douglas Wilson Date: Tue Oct 3 15:08:47 2017 -0400 Don't pass HscEnv to functions in the Hsc monad `Hsc` is a reader monad in `HscEnv`. Several functions in HscMain were taking parameters of type `HscEnv` or `DynFlags`, and returning values of type `Hsc a`. This patch removes those parameters in favour of asking them from the context. This removes a source of confusion and should make refactoring a bit easier. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4061 >--------------------------------------------------------------- 4899a86b69a3cf8b487329d5db8bb205152950ce compiler/main/HscMain.hs | 98 ++++++++++++++++++++++++++---------------------- 1 file changed, 53 insertions(+), 45 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 4899a86b69a3cf8b487329d5db8bb205152950ce From git at git.haskell.org Tue Oct 3 21:56:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:56:35 +0000 (UTC) Subject: [commit: ghc] master: base: Remove deprecated Chan combinators (361af62) Message-ID: <20171003215635.5EABA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/361af6280d7025ac3e24d79c209b465db6f231f8/ghc >--------------------------------------------------------------- commit 361af6280d7025ac3e24d79c209b465db6f231f8 Author: Ben Gamari Date: Tue Oct 3 15:09:12 2017 -0400 base: Remove deprecated Chan combinators Removes isEmptyChan and unGetChan, which have been deprecated for a very long time. See #13561. Test Plan: Validate Reviewers: austin, hvr Subscribers: rwbarton, thomie GHC Trac Issues: #13561 Differential Revision: https://phabricator.haskell.org/D4060 >--------------------------------------------------------------- 361af6280d7025ac3e24d79c209b465db6f231f8 libraries/base/Control/Concurrent/Chan.hs | 21 --------------------- libraries/base/changelog.md | 3 +++ 2 files changed, 3 insertions(+), 21 deletions(-) diff --git a/libraries/base/Control/Concurrent/Chan.hs b/libraries/base/Control/Concurrent/Chan.hs index ebbec7e..9bfd40b 100644 --- a/libraries/base/Control/Concurrent/Chan.hs +++ b/libraries/base/Control/Concurrent/Chan.hs @@ -1,6 +1,5 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP #-} -{-# LANGUAGE StandaloneDeriving #-} ----------------------------------------------------------------------------- -- | @@ -31,8 +30,6 @@ module Control.Concurrent.Chan writeChan, readChan, dupChan, - unGetChan, - isEmptyChan, -- * Stream interface getChanContents, @@ -137,24 +134,6 @@ dupChan (Chan _ writeVar) = do newReadVar <- newMVar hole return (Chan newReadVar writeVar) --- |Put a data item back onto a channel, where it will be the next item read. -unGetChan :: Chan a -> a -> IO () -unGetChan (Chan readVar _) val = do - new_read_end <- newEmptyMVar - modifyMVar_ readVar $ \read_end -> do - putMVar new_read_end (ChItem val read_end) - return new_read_end -{-# DEPRECATED unGetChan "if you need this operation, use Control.Concurrent.STM.TChan instead. See for details" #-} -- deprecated in 7.0 - --- |Returns 'True' if the supplied 'Chan' is empty. -isEmptyChan :: Chan a -> IO Bool -isEmptyChan (Chan readVar writeVar) = do - withMVar readVar $ \r -> do - w <- readMVar writeVar - let eq = r == w - eq `seq` return eq -{-# DEPRECATED isEmptyChan "if you need this operation, use Control.Concurrent.STM.TChan instead. See for details" #-} -- deprecated in 7.0 - -- Operators for interfacing with functional streams. -- |Return a lazy list representing the contents of the supplied diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 7778ceb..2f42e22 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -56,6 +56,9 @@ * Add `installSEHHandlers` to `MiscFlags` in `GHC.RTS.Flags` to determine if exception handling is enabled. + * The deprecated functions `isEmptyChan` and `unGetChan` in + `Control.Concurrent.Chan` have been removed (#13561). + * Add `generateCrashDumpFile` to `MiscFlags` in `GHC.RTS.Flags` to determine if a core dump will be generated on crashes. From git at git.haskell.org Tue Oct 3 21:56:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:56:38 +0000 (UTC) Subject: [commit: ghc] master: user-guide: Mention COMPLETE pragma in release notes (3201d85) Message-ID: <20171003215638.25A4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3201d85f48e47ea10a49d4222ca0570824aa81d8/ghc >--------------------------------------------------------------- commit 3201d85f48e47ea10a49d4222ca0570824aa81d8 Author: Ben Gamari Date: Tue Oct 3 15:09:41 2017 -0400 user-guide: Mention COMPLETE pragma in release notes Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #14305 Differential Revision: https://phabricator.haskell.org/D4059 >--------------------------------------------------------------- 3201d85f48e47ea10a49d4222ca0570824aa81d8 docs/users_guide/8.2.1-notes.rst | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 89acec8..ca045ee 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -54,6 +54,10 @@ Language - Support for overloaded record fields via a new ``HasField`` class and associated compiler logic (see :ref:`record-field-selector-polymorphism`) +- GHC now recognizes the ``COMPLETE`` language pragma, allowing the user to + specify sets of patterns (including pattern synonyms) which constitute a + complete pattern match. See :ref:`complete-pragma` for details. + Compiler ~~~~~~~~ From git at git.haskell.org Tue Oct 3 21:58:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:58:41 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: user-guide: add `:type +d` and `:type +v` in release highlight (61c7b3d) Message-ID: <20171003215841.459C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/61c7b3d440ff614a750fa68161cc2054b7798794/ghc >--------------------------------------------------------------- commit 61c7b3d440ff614a750fa68161cc2054b7798794 Author: Takenobu Tani Date: Thu Aug 17 10:29:43 2017 -0400 user-guide: add `:type +d` and `:type +v` in release highlight Add new ghci command to release highlight and fix link anchor. This commit is for ghc-8.2 branch. Test Plan: build Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #11975 Differential Revision: https://phabricator.haskell.org/D3850 (cherry picked from commit 82ee71fa85aca087b2cd62cb354fc3df46db4411) >--------------------------------------------------------------- 61c7b3d440ff614a750fa68161cc2054b7798794 docs/users_guide/8.2.1-notes.rst | 2 ++ 1 file changed, 2 insertions(+) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index b591549..3190254 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -251,6 +251,8 @@ GHCi - Added support for :ghc-flag:`-XStaticPointers` in interpreted modules. Note, however, that ``static`` expressions are still not allowed in expressions evaluated in the REPL. +- Added support for :ghci-cmd:`:type +d` and :ghci-cmd:`:type +v`. (:ghc-ticket:`11975`) + Template Haskell ~~~~~~~~~~~~~~~~ From git at git.haskell.org Tue Oct 3 21:58:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:58:44 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: user-guide: fix examples of ghci commands (83e438e) Message-ID: <20171003215844.15DCB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/83e438ee1f52bf8995a2f47f5aa5569d1071e9a0/ghc >--------------------------------------------------------------- commit 83e438ee1f52bf8995a2f47f5aa5569d1071e9a0 Author: Takenobu Tani Date: Thu Aug 17 10:28:01 2017 -0400 user-guide: fix examples of ghci commands Fix examples of ghci commands: * correct typos * add top-level binding without let statement * modify Time.getClockTime to Data.Time.getZonedTime * modify Directory.setCurrentDirectory * modify ghc version number Test Plan: build Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3852 (cherry picked from commit 3385669683b8bc150c6df3cb43320dfc6f80fcd9) >--------------------------------------------------------------- 83e438ee1f52bf8995a2f47f5aa5569d1071e9a0 docs/users_guide/ghci.rst | 29 +++++++++++++++++++---------- docs/users_guide/using.rst | 4 ++-- 2 files changed, 21 insertions(+), 12 deletions(-) diff --git a/docs/users_guide/ghci.rst b/docs/users_guide/ghci.rst index dce7904..e2fb361 100644 --- a/docs/users_guide/ghci.rst +++ b/docs/users_guide/ghci.rst @@ -37,7 +37,7 @@ command ``ghci``: .. code-block:: none $ ghci - GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help + GHCi, version 8.y.z: http://www.haskell.org/ghc/ :? for help Prelude> There may be a short pause while GHCi loads the prelude and standard @@ -69,6 +69,15 @@ GHCi, since the expression can also be interpreted in the ``IO`` monad, a ``let`` binding with no accompanying ``in`` statement can be signalled by an empty line, as in the above example. +Since GHC 8.0.1, you can bind values and functions to names without ``let`` statement: + +.. code-block:: none + + Prelude> x = 42 + Prelude> x + 42 + Prelude> + .. _loading-source-files: Loading source files @@ -987,10 +996,10 @@ of type ``a``. eg.: .. code-block:: none - Prelude> Time.getClockTime - Wed Mar 14 12:23:13 GMT 2001 + Prelude> Data.Time.getZonedTime + 2017-04-10 12:34:56.93213581 UTC Prelude> print it - Wed Mar 14 12:23:13 GMT 2001 + 2017-04-10 12:34:56.93213581 UTC The corresponding translation for an IO-typed ``e`` is @@ -1162,7 +1171,7 @@ printed value. Running GHCi with the command: .. code-block:: none - ghci -interactive-print=SpecPrinter.sprinter SpecPrinter + ghci -interactive-print=SpecPrinter.sprint SpecPrinter will start an interactive session where values with be printed using ``sprint``: @@ -1971,7 +1980,7 @@ by using the :ghc-flag:`-package ⟨pkg⟩` flag: .. code-block:: none $ ghci -package readline - GHCi, version 6.8.1: http://www.haskell.org/ghc/ :? for help + GHCi, version 8.y.z: http://www.haskell.org/ghc/ :? for help Loading package base ... linking ... done. Loading package readline-1.0 ... linking ... done. Prelude> @@ -2238,17 +2247,17 @@ commonly used commands. .. code-block:: none - Prelude> let date _ = Time.getClockTime >>= print >> return "" + Prelude> let date _ = Data.Time.getZonedTime >>= print >> return "" Prelude> :def date date Prelude> :date - Fri Mar 23 15:16:40 GMT 2001 + 2017-04-10 12:34:56.93213581 UTC Here's an example of a command that takes an argument. It's a re-implementation of :ghci-cmd:`:cd`: .. code-block:: none - Prelude> let mycd d = Directory.setCurrentDirectory d >> return "" + Prelude> let mycd d = System.Directory.setCurrentDirectory d >> return "" Prelude> :def mycd mycd Prelude> :mycd .. @@ -2745,7 +2754,7 @@ commonly used commands. *X> :type +v length length :: forall (t :: * -> *). Foldable t => forall a. t a -> Int -.. ghci-cmd:: :type +d ⟨expression⟩ +.. ghci-cmd:: :type +d; ⟨expression⟩ Infers and prints the type of ⟨expression⟩, defaulting type variables if possible. In this mode, if the inferred type is constrained by diff --git a/docs/users_guide/using.rst b/docs/users_guide/using.rst index dff9603..6dde0ee 100644 --- a/docs/users_guide/using.rst +++ b/docs/users_guide/using.rst @@ -636,8 +636,8 @@ messages and in GHCi: .. code-block:: none ghci> :set -fprint-unicode-syntax - ghci> :t (>>) - (>>) :: ∀ (m :: * → *) a b. Monad m ⇒ m a → m b → m b + ghci> :t +v (>>) + (>>) ∷ Monad m ⇒ ∀ a b. m a → m b → m b .. _pretty-printing-types: From git at git.haskell.org Tue Oct 3 21:58:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Oct 2017 21:58:47 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Include libraries which fill holes as deps when linking. (876fec0) Message-ID: <20171003215847.EE73F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/876fec04c04061d5a2257675fcd0deb35ecb0aaf/ghc >--------------------------------------------------------------- commit 876fec04c04061d5a2257675fcd0deb35ecb0aaf Author: Edward Z. Yang Date: Tue Oct 3 15:08:24 2017 -0400 Include libraries which fill holes as deps when linking. Fixes the issue reported at https://github.com/haskell/cabal/issues/4755 and fixes #14304 in the GHC tracker. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: bgamari, austin, goldfire Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14304 Differential Revision: https://phabricator.haskell.org/D4057 (cherry picked from commit f3f624aeb1360c1f902930b3cc62346d2e5201c0) >--------------------------------------------------------------- 876fec04c04061d5a2257675fcd0deb35ecb0aaf compiler/main/Packages.hs | 4 ++- testsuite/tests/backpack/cabal/T14304/Makefile | 36 ++++++++++++++++++++++ .../backpack/cabal/{bkpcabal01 => T14304}/Setup.hs | 0 .../tests/backpack/cabal/T14304/T14304.stderr | 6 ++++ testsuite/tests/backpack/cabal/T14304/all.T | 9 ++++++ .../tests/backpack/cabal/T14304/indef/Indef.hs | 3 ++ .../tests/backpack/cabal/T14304/indef/Sig.hsig | 2 ++ .../tests/backpack/cabal/T14304/indef/indef.cabal | 9 ++++++ testsuite/tests/backpack/cabal/T14304/p/P.hs | 3 ++ testsuite/tests/backpack/cabal/T14304/p/p.cabal | 8 +++++ .../Sub1.hs => backpack/cabal/T14304/th/TH.hs} | 4 +-- testsuite/tests/backpack/cabal/T14304/th/th.cabal | 9 ++++++ 12 files changed, 90 insertions(+), 3 deletions(-) diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index 2c5833f..08b0ceb 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -1875,8 +1875,10 @@ listVisibleModuleNames dflags = -- | Find all the 'PackageConfig' in both the preload packages from 'DynFlags' and corresponding to the list of -- 'PackageConfig's getPreloadPackagesAnd :: DynFlags -> [PreloadUnitId] -> IO [PackageConfig] -getPreloadPackagesAnd dflags pkgids = +getPreloadPackagesAnd dflags pkgids0 = let + pkgids = pkgids0 ++ map (toInstalledUnitId . moduleUnitId . snd) + (thisUnitIdInsts dflags) state = pkgState dflags pkg_map = pkgIdMap state preload = preloadPackages state diff --git a/testsuite/tests/backpack/cabal/T14304/Makefile b/testsuite/tests/backpack/cabal/T14304/Makefile new file mode 100644 index 0000000..1f58184 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/Makefile @@ -0,0 +1,36 @@ +TOP=../../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +SETUP='$(PWD)/Setup' -v0 +CONFIGURE=$(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db='$(PWD)/tmp.d' --prefix='$(PWD)/inst' --enable-shared + +T14304: clean + $(MAKE) -s --no-print-directory clean + '$(GHC_PKG)' init tmp.d + '$(TEST_HC)' -v0 --make Setup + # typecheck indef + rm -rf indef/dist + (cd indef; $(CONFIGURE) --ipid "indef-0.1") + (cd indef; $(SETUP) build) + (cd indef; $(SETUP) copy) + (cd indef; $(SETUP) register) + # build p + rm -rf p/dist + (cd p; $(CONFIGURE) --ipid "p-0.1") + (cd p; $(SETUP) build) + (cd p; $(SETUP) copy) + (cd p; $(SETUP) register) + # build indef instantiated with p + rm -rf indef/dist + (cd indef; $(CONFIGURE) --ipid "indef-0.1" --instantiate-with "Sig=p-0.1:P") + (cd indef; $(SETUP) build) + (cd indef; $(SETUP) copy) + (cd indef; $(SETUP) register) + # build th (which tests if we have correct linkage) + rm -rf th/dist + (cd th; $(CONFIGURE)) + (cd th; $(SETUP) build) + +clean : + $(RM) -r tmp.d inst dist Setup$(exeext) diff --git a/testsuite/tests/backpack/cabal/bkpcabal01/Setup.hs b/testsuite/tests/backpack/cabal/T14304/Setup.hs similarity index 100% copy from testsuite/tests/backpack/cabal/bkpcabal01/Setup.hs copy to testsuite/tests/backpack/cabal/T14304/Setup.hs diff --git a/testsuite/tests/backpack/cabal/T14304/T14304.stderr b/testsuite/tests/backpack/cabal/T14304/T14304.stderr new file mode 100644 index 0000000..89a07b9 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/T14304.stderr @@ -0,0 +1,6 @@ +Warning: -rtsopts and -with-rtsopts have no effect with -shared. + Call hs_init_ghc() from your main() function to set these options. +Warning: -rtsopts and -with-rtsopts have no effect with -shared. + Call hs_init_ghc() from your main() function to set these options. +Warning: -rtsopts and -with-rtsopts have no effect with -shared. + Call hs_init_ghc() from your main() function to set these options. diff --git a/testsuite/tests/backpack/cabal/T14304/all.T b/testsuite/tests/backpack/cabal/T14304/all.T new file mode 100644 index 0000000..f25285d --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/all.T @@ -0,0 +1,9 @@ +if config.cleanup: + cleanup = 'CLEANUP=1' +else: + cleanup = 'CLEANUP=0' + +test('T14304', + extra_files(['p', 'indef', 'th', 'Setup.hs']), + run_command, + ['$MAKE -s --no-print-directory T14304 ' + cleanup]) diff --git a/testsuite/tests/backpack/cabal/T14304/indef/Indef.hs b/testsuite/tests/backpack/cabal/T14304/indef/Indef.hs new file mode 100644 index 0000000..0bd438e --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/indef/Indef.hs @@ -0,0 +1,3 @@ +module Indef where +import Sig +data T = MkT B diff --git a/testsuite/tests/backpack/cabal/T14304/indef/Sig.hsig b/testsuite/tests/backpack/cabal/T14304/indef/Sig.hsig new file mode 100644 index 0000000..a37b190 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/indef/Sig.hsig @@ -0,0 +1,2 @@ +signature Sig where +data B diff --git a/testsuite/tests/backpack/cabal/T14304/indef/indef.cabal b/testsuite/tests/backpack/cabal/T14304/indef/indef.cabal new file mode 100644 index 0000000..d89f055 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/indef/indef.cabal @@ -0,0 +1,9 @@ +name: indef +version: 1.0 +build-type: Simple +cabal-version: >= 2.0 + +library + build-depends: base + signatures: Sig + exposed-modules: Indef diff --git a/testsuite/tests/backpack/cabal/T14304/p/P.hs b/testsuite/tests/backpack/cabal/T14304/p/P.hs new file mode 100644 index 0000000..f570e0b --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/p/P.hs @@ -0,0 +1,3 @@ +module P where +type B = Foo +newtype Foo = Foo Double diff --git a/testsuite/tests/backpack/cabal/T14304/p/p.cabal b/testsuite/tests/backpack/cabal/T14304/p/p.cabal new file mode 100644 index 0000000..f49ce42 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/p/p.cabal @@ -0,0 +1,8 @@ +name: p +version: 1.0 +build-type: Simple +cabal-version: >= 2.0 + +library + build-depends: base + exposed-modules: P diff --git a/testsuite/tests/driver/recomp009/Sub1.hs b/testsuite/tests/backpack/cabal/T14304/th/TH.hs similarity index 51% copy from testsuite/tests/driver/recomp009/Sub1.hs copy to testsuite/tests/backpack/cabal/T14304/th/TH.hs index 25ea755..5d921cf 100644 --- a/testsuite/tests/driver/recomp009/Sub1.hs +++ b/testsuite/tests/backpack/cabal/T14304/th/TH.hs @@ -1,3 +1,3 @@ {-# LANGUAGE TemplateHaskell #-} -module Sub where -x = [| 1 |] +module TH where +$( return [] ) diff --git a/testsuite/tests/backpack/cabal/T14304/th/th.cabal b/testsuite/tests/backpack/cabal/T14304/th/th.cabal new file mode 100644 index 0000000..2b17f09 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T14304/th/th.cabal @@ -0,0 +1,9 @@ +name: th +version: 1.0 +build-type: Simple +cabal-version: >= 2.0 + +library + build-depends: p, indef, base + mixins: p (P as Sig) + exposed-modules: TH From git at git.haskell.org Wed Oct 4 00:41:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Oct 2017 00:41:54 +0000 (UTC) Subject: [commit: ghc] master: rts: Print newline after "Stack trace:" on barf (3030eee) Message-ID: <20171004004154.1B7F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3030eee24c9d538f7ae2c854fd86129563b6ddf3/ghc >--------------------------------------------------------------- commit 3030eee24c9d538f7ae2c854fd86129563b6ddf3 Author: Ben Gamari Date: Tue Oct 3 20:41:17 2017 -0400 rts: Print newline after "Stack trace:" on barf [skip ci] >--------------------------------------------------------------- 3030eee24c9d538f7ae2c854fd86129563b6ddf3 rts/RtsMessages.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/RtsMessages.c b/rts/RtsMessages.c index 5782c0d..ba1f02d 100644 --- a/rts/RtsMessages.c +++ b/rts/RtsMessages.c @@ -166,7 +166,7 @@ rtsFatalInternalErrorFn(const char *s, va_list ap) vfprintf(stderr, s, ap); #if USE_LIBDW fprintf(stderr, "\n"); - fprintf(stderr, "Stack trace:"); + fprintf(stderr, "Stack trace:\n"); LibdwSession *session = libdwInit(); Backtrace *bt = libdwGetBacktrace(session); libdwPrintBacktrace(session, stderr, bt); From git at git.haskell.org Wed Oct 4 12:39:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Oct 2017 12:39:16 +0000 (UTC) Subject: [commit: ghc] master: configure: Accept *-msys as a Windows OS in a triple (7109fa8) Message-ID: <20171004123916.037CA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7109fa8157f3258912c947f28dab7617b5e5d281/ghc >--------------------------------------------------------------- commit 7109fa8157f3258912c947f28dab7617b5e5d281 Author: Ben Gamari Date: Wed Oct 4 08:37:26 2017 -0400 configure: Accept *-msys as a Windows OS in a triple >--------------------------------------------------------------- 7109fa8157f3258912c947f28dab7617b5e5d281 aclocal.m4 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index b34f898..7e1e3e1 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1899,7 +1899,7 @@ AC_DEFUN([GHC_LLVM_TARGET], [ llvm_target_vendor="unknown" llvm_target_os="$3""hf" ;; - *-mingw32|*-mingw64) + *-mingw32|*-mingw64|*-msys) llvm_target_vendor="unknown" llvm_target_os="windows" ;; From git at git.haskell.org Wed Oct 4 23:52:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Oct 2017 23:52:52 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: Merge branch 'master' into wip/kavon-nosplit-llvm (7bcb31c) Message-ID: <20171004235252.13CCE3A5EA@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/7bcb31c882f606c49a79a34c275ab5c0dca54c7c/ghc >--------------------------------------------------------------- commit 7bcb31c882f606c49a79a34c275ab5c0dca54c7c Merge: 79dd250 6bb32ba Author: Kavon Farvardin Date: Wed Oct 4 17:48:06 2017 -0500 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 7bcb31c882f606c49a79a34c275ab5c0dca54c7c From git at git.haskell.org Wed Oct 4 23:52:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Oct 2017 23:52:54 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: temporary fix to workaround travis ci issue (e601e67) Message-ID: <20171004235254.C2A363A5EA@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/e601e67a06451de4b8a5adc069e3af0fc15c0426/ghc >--------------------------------------------------------------- commit e601e67a06451de4b8a5adc069e3af0fc15c0426 Author: Kavon Farvardin Date: Wed Oct 4 18:52:14 2017 -0500 temporary fix to workaround travis ci issue >--------------------------------------------------------------- e601e67a06451de4b8a5adc069e3af0fc15c0426 compiler/llvmGen/LlvmMangler.hs | 17 +++++++++++++++-- 1 file changed, 15 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index 25c46dc..9a20092 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -81,10 +81,10 @@ type LabRewrite = State -> Rewrite -- above that label. addInfoTable :: LabelMap ManglerStr -> LabRewrite addInfoTable info FirstLabel dflags line = do - retPt <- B.stripPrefix labPrefix line + retPt <- stripPrefix labPrefix line (i, _) <- B.readInt retPt statics <- mapLookup (toKey i) info - fullName <- B.stripSuffix colon line + fullName <- stripSuffix colon line return $ B.concat $ (map (\f -> f fullName) statics) ++ [line] where @@ -99,6 +99,19 @@ addInfoTable info FirstLabel dflags line = do colon = B.pack ":" toKey = uniqueToLbl . intToUnique + -- TODO(kavon): on Travis CI, it seems the bytestring package is out of date, and + -- we're missing B.stripSuffix and B.stripPrefix. I've reimplemented them here. + -- please remove these when that issue is resolved. + stripPrefix pfx line + | B.isPrefixOf pfx line + = Just $ B.drop (B.length pfx) line + | otherwise = Nothing + + stripSuffix sfx line + | B.isSuffixOf sfx line + = Just $ B.take ((B.length line) - (B.length sfx)) line + | otherwise = Nothing + addInfoTable _ _ _ _ = Nothing -- | Rewrite a line of assembly source with the given rewrites, From git at git.haskell.org Wed Oct 4 23:52:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Oct 2017 23:52:57 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm's head updated: temporary fix to workaround travis ci issue (e601e67) Message-ID: <20171004235257.701D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/kavon-nosplit-llvm' now includes: b8f8736 base/inputReady: Whitespace cleanup 914962c Update docs to reflect changes to DeriveDataTypeable 9ef909d Allow bytecode interpreter to make unsafe foreign calls 12a3c39 testsuite: Add broken test for #13871 1346525 typecheck: Consider types containing coercions non-Typeable 1e47126 rts: Clarify whitehole logic in threadPaused 6567c81 Treat banged bindings as FunBinds b070858 Make module membership on ModuleGraph faster 22b917e Revert "Make module membership on ModuleGraph faster" 4bdac33 Fix the in-scope set in TcHsType.instantiateTyN c80920d Do zonking in tcLHsKindSig fae672f Fix constraint solving for forall-types 87c5fdb Zap stable unfoldings in worker/wrapper 78c80c2 Typos in comments and manual [ci skip] 3f9422c More typos in comments [ci skip] 7097f94 Remove unneeded import 54ccf0c remove dead function 'tcInstBinders' 3b0e755 Fix lexically-scoped type variables 58c781d Revert "Remove the Windows GCC driver." c2fb6e8 Typos in comments c3f12ec Fix T13701 allocation for Linux 7de2c07 users-guide: Document FFI safety guarantees 6171b0b configure: Check for binutils #17166 007f255 Allow optional instance keyword in associated type family instances 625143f configure: Coerce gcc to use $LD instead of system default 9b514de rts/RetainerProfile: Const-correctness fixes 1ef4156 Prevent ApplicativeDo from applying to strict pattern matches (#13875) 0592318 Fix paper link in MVar docs [ci skip] 544ac0d rename tcInstBinder(s)X to tcInstBinder(s) 84d6831a users-guide: Wibbles in shared libraries discussion 287a405 Allow per-argument documentation on pattern synonym signatures 1a9c3c4 Implement recompilation checking for -fignore-asserts f9c6d53 Tag the FUN before making a PAP (#13767) c3a7862 Fix #13311 by using tcSplitNestedSigmaTys in the right place d55bea1 Fix -fno-code for modules that use -XQuasiQuotes 0c1f905 CmmParse: Emit source notes for assignments 5aee331 Bump array submodule to v0.5.2.0 8f8d756 rts: Fix uninitialised variable uses af403b2 ApplicativeDo: document behaviour with strict patterns (#13875) ef63ff2 configure: Remove --with-curses-includes flag a6f3d1b rts: Fix isByteArrayPinned#'s treatment of large arrays 960918b Add -fuse-ld flag to CFLAGS during configure 0836bfb testsuite: Add testcase for #13615 fd7a7a6 Eagerly blackhole AP_STACKs 9492703 rts/sm/Storage.c: tweak __clear_cache proto for clang 7040660 Revert "rts/sm/Storage.c: tweak __clear_cache proto for clang" 3eeb55e rts/sm/Storage.c: tweak __clear_cache proto for clang 555e5cc rts: Address AP_STACK comment suggestion from Simon 4997177 mkDocs: Don't install *.ps f3979b7 lowercase clang 99adcc8 Typos in comments [ci skip] bd4fdc6 Implement split-sections support for windows. c2303df aclocal.m4: allow arbitrary string in toolchain triplets e1146ed Fix typos in Bag.hs [ci skip] 81377e9 Big-obj support for the Windows runtime linker c506f83 Pretty-printer no longer butchers function arrow fixity 4f69013 testsuite: Decrease T13701 allocations 31ceaba user-guide: Various fixes to FFI section 905dc8b Make ':info Coercible' display an arbitrary string (fixes #12390) 7c9e356 Fix Work Balance computation in RTS stats b0c9f34 Improve Wmissing-home-modules warning under Cabal 6cff2ca Add testcase for T13818 15fcd9a Suppress unused warnings for selectors for some derived classes cb8db9b Sort list of failed tests for easier comparison between runs b8f33bc Always allow -staticlib fe6618b ByteCodeGen: use depth instead of offsets in BCEnv ccb849f users-guide/rel-notes: Describe #13875 fix 81de42c Add Template Haskell support for overloaded labels abda03b Optimize TimerManager ea75124 Fix logic error in GhcMake.enableCodeGenForTH ba46e63 Fix #13948 by being pickier about when to suggest DataKinds 85ac65c Fix #13947 by checking for unbounded names more ef7fd0a Parenthesize infix type names in data declarations in TH printer ec351b8 Add Template Haskell support for overloaded labels a249e93 Remove unnecessarily returned res_ty from rejigConRes d3bdd6c testsuite: Fix T13701 allocations yet again fcd2db1 configure: Ensure that we don't set LD to unusable linker be04c16 StgLint: Don't loop on tycons with runtime rep arguments 20880b5 testsuite: Show stderr output on command failure a0d9169 Fix minor typo 3a163aa Remove redundant import; fix note 4befb41 Mention which -Werror promoted a warning to an error 9b9f978 Use correct section types syntax for architecture 1ee49cb Fix missing escape in macro 60ec8f7 distrib/configure: Fail if we can't detect machine's word size 7ae4a28 [iserv] Fixing the word size for RemotePtr and toWordArray 5743581 testsuite: Update haddock allocations 4700baa testsuite: Again update allocations of T13701 1909985 Fix some excessive spacing in error messages f656fba [skip ci] Temporarily disable split-sections on Windows. 12ae1fa Fix a missing getNewNursery(), and related cleanup 935acb6 Typos in comments and explanation for unusused imports b8fec69 Make module membership on ModuleGraph faster 6ab3c5f Typeable: Always use UTF-8 string unpacking primitive d7b1751 configure: Cleanup ARM COPY bug test artifacts a051b55 testsuite: Ensure that hs_try_putmvar003 terminates c9e4c86 Allow visible type application for [] 1ed41a7 Fix links to SPJ’s papers (fixes #12578) 0b89b2d Add Haddocks for Eq (STRef a) and Eq (IORef a) c940e3b dmdAnal: Ensure that ExnStr flag isn't dropped inappropriately 6e3c901 Fix #13983 by creating a TyConFlavour type, and using it 927e781 typo: -XUndeci[d]ableInstances b066d93 base: Improve docs to clarify when finalizers may not be run cc839c5 Typeable: Ensure that promoted data family instance tycons get bindings a273c73 Spelling fixes eeb141d Demand: Improve comments 8e51bfc Introduce -fcatch-bottoms c9c762d testsuite: Pipe stdin directly to process a85a595 arcconfig: Set project ruleset to use master merge-base by default 194384f Fix busy-wait in SysTools.builderMainLoop fdb6a5b Make IfaceAxiom typechecking lazier. 5469ac8 Interpreter.c: use macros to access/modify Sp bade356 rts: Claim AP_STACK before adjusting Sp 1480080 distrib/configure: Canonicalize triples b2d3ec3 testsuite: Add test for #13916 ccac387 Revert "testsuite: Add test for #13916" 36e8bcb HsPat: Assume that no spliced patterns are irrefutable fefcbfa build system: Ensure there are no duplicate files in bindist list acbbb50 Fix ungrammatical error message cbbf083 fix dllwrap issue. c1d9690 Avoid linear lookup in unload_wkr in the Linker ee1047e Update autoconf scripts 98ab12a distrib/configure: Carry FFI include/lib paths from source distribution fb08252 users-guide: Improve legibility of OverlappingInstances documentation 0ae0f46 Preserve HaskellHaveRTSLinker in bindist 646ec0e Bump a bunch of submodules b8afdaf Update release notes for 8.2.1 fb17cc5 Bump integer-gmp version ecc9e9a ghc-prim: Bump version d4e9721 testsuite: Fix cabal01 for real this time 44b090b users-guide: Standardize and repair all flag references c945195 users-guide: Fix various wibbles 2dff2c7 Fix more documentation wibbles 145f1c7 Remove 8.0.2 release notes file 88f20bd Add a caveat to the GHC.Generics examples about :+: nesting a602b65 users-guides: Fix errant whitespace 0c04d78 users-guide: Cross-reference more flags 58b62d6 users-guide: Eliminate some redundant index entries 3e5d0f1 users-guide: Make it easier to reference haddocks 897366a users-guide: Fix URL of deferred type errors paper 85a295d ghc-prim: Don't allocate a thunk for each unpacked UTF-8 character 8a8cee7 DynFlags: Drop rtsBuildTag field d8051c6 Use libpthread instead of libthr on FreeBSD 8ec7770 testsuite: Add testcase for #13168 2183ac1 Fix import error with -XPackageImports when the module has a duplicate name 58545fd base: Introduce GHC.ByteOrder 104c72b Expose FrontendPluginAction 7d1909a Remove unused language pragma 36b270a Revert "Remove unused language pragma" 6bb32ba Fix #10684 by processing deriving clauses with finer grain 7bcb31c Merge branch 'master' into wip/kavon-nosplit-llvm e601e67 temporary fix to workaround travis ci issue From git at git.haskell.org Thu Oct 5 00:29:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Oct 2017 00:29:20 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: merged up to 7109fa8157f from master into wip/kavon-nosplit-llvm (5eae140) Message-ID: <20171005002920.F218F3A5EA@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/5eae140ebeca8f09c43a500ba0cd855b9de1c620/ghc >--------------------------------------------------------------- commit 5eae140ebeca8f09c43a500ba0cd855b9de1c620 Merge: e601e67 7109fa8 Author: Kavon Farvardin Date: Wed Oct 4 19:29:08 2017 -0500 merged up to 7109fa8157f from 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 5eae140ebeca8f09c43a500ba0cd855b9de1c620 From git at git.haskell.org Thu Oct 5 00:29:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Oct 2017 00:29:24 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm's head updated: merged up to 7109fa8157f from master into wip/kavon-nosplit-llvm (5eae140) Message-ID: <20171005002924.B8ECC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/kavon-nosplit-llvm' now includes: 746ab0b Add an Outputable instance for ListMap 75bf11c Fix binder visiblity for default methods 6386fc3 Comments and tc-tracing only f959624 Comments only d31181b Test Trac #14033 362339d Fix note references and some typos d774b4e Fix #13968 by consulting isBuiltInOcc_maybe 4a26415 Remove unneeded import 8e15e3d Improve error messages around kind mismatches. c9667d3 Fix #11400, #11560 by documenting an infelicity. 9a54975 Test #11672 in typecheck/should_fail/T11672. ef39af7 Don't tidy vars when dumping a type bb2a446 Preserve CoVar uniques during pretty printing 79cfb19 Remove old coercion pretty-printer c2417b8 Fix #13819 by refactoring TypeEqOrigin.uo_thing fb75213 Track visibility in TypeEqOrigin 10d13b6 Fix #11963 by checking for more mixed type/kinds ca47186 Document that type holes kill polymorphic recursion 1696dbf Fix #12176 by being a bit more careful instantiating. 4239238 Fix #12369 by being more flexible with data insts 791947d Refactor tcInferApps. 7af0b90 Initialize hs_init with UTF8 encoded arguments on Windows. 6b77914 Fix instantiation of pattern synonyms af6d225 Remove redundant constraint in context b1317a3 Fix ASSERT failure in tc269 452755d Do not discard insolubles in implications ad0037e Add DebugCallStack to piResultTy d618649 Error eagerly after renaming failures in reifyInstances b3b564f Merge types and kinds in DsMeta 424ecad Add regression tests for #13601, #13780, #13877 5e940bd Switched out optparse for argparse in runtests.py 54d3a1f testsuite: Produce JUnit output 262bb95 testsuite: Add test for #14028 274e9b2 Add “BINARY_DIST_DIR” to Makefile dac4b9d ByteCodeGen: use byte indexing for BCenv 2974f81 Fix lld detection if both gold and lld are found f134bfb gitmodules: Delete entry for dead hoopl submodule d08b9cc configure: Ensure that user's LD setting is respected 0e3c101 Ensure that we always link against libm 0e3eacc testsuite: Don't pass allow_abbrev 121fee9 Remove unnecessary GHC option from SrcLoc 9e9fb57 Fix hs-boot knot-tying with record wild cards. d75bba8 Add rtsopts ignore and ignoreAll. 84f8e86 Ensure that GHC.Stack.callStack doesn't fail 9cfabbb Add '<&>' operator to Data.Functor. '<&>' calls '<$>' with flipped arguments. d1ef223 Fix #14045 by omitting an unnecessary check f839b9d Add regression test for #14055 7089dc2 Follow-up to #13887, for promoted infix constructors 9699286 Typofixes [ci skip] f2c12c3 Add haddock markup 49e334c Allow Windows to set blank environment variables c6d4219 Clarify comment about data family arities 2535a67 Refactoring around FunRhs 4636886 Improve the desugaring of -XStrict 3ab342e Do a bit more CSE af89d68 Reject top-level banged bindings 7f2dee8 Remove redundant goop 4fdc523 Use field names for all uses of datacon Match 2ef973e A bunch of typofixes 7a74f50 Typofixes [ci skip] 5a7af95 KnownUniques: Handle DataCon wrapper names 29f07b1 Allow bundling pattern synonyms with exported data families 74c7016 rts: Fix "variable set but not used" warning b311096 Simplify OccurAnal.tagRecBinders c13720c Drop GHC 7.10 compatibility 36fe21a Enable building Cabal with parsec 9df71bf Bump unix submodule 8ef8520 Add .gitmodules entries for text, parsec, mtl submodules d74983e Get the roles right for newtype instances f68a00c Remove unneeded uses of ImplicitParams 884bd21 Add the bootstrapping/ dir to .gitignore 394c391 Add MonadIO Q - by requiring MonadIO => Quasi a81b5b0 Remove the deprecated Typeable{1..7} type synonyms a267580 Don't warn when empty casing on Type 6ea13e9 Add forgotten > in Control.Applicative e8fe12f Fix string escaping in JSON 2f29f19 Convert examples to doctests, and add a handful of new ones 14457cf Fix EmptyCase documentation a4f347c Split out inferConstraintsDataConArgs from inferConstraints 3f05e5f Don't suppress unimplemented type family warnings with DeriveAnyClass 7d69978 Use NonEmpty lists to represent lists of duplicate elements 4f1f986 Change isClosedAlgType to be TYPE-aware, and rename it to pmIsClosedType 0bb1e84 Expand type synonyms during role inference c6462ab Add test for #14101 7c37ffe Point to FunDeps documentation on Haskell wiki ad7b945 Fix #14060 by more conservatively annotating TH-reified types 0a891c8 Properly handle dlerror() message on FreeBSD when linking linker scripts ddb870b Don't drop GHCi-defined functions with -fobject-code enabled ed7a830 Use a ReaderT in TcDeriv to avoid some tedious plumbing 21bd9b2 Recognize FreeBSD compiler as Clang. a520adc Bump mtl, parsec, text submodules 441c52d Add Semigroup/Monoid instances to ST monad b0285d1 Bump nofib submodule e054c5f Bump mtl, parsec, text submodules 6e9c8eb Bump mtl, parsec, text submodules (again) a8da0de Speed up compilation of profiling stubs b0ed07f Allow TcDerivInfer to compile with GHC 8.0.1 38260a9 Fix #13972 by producing tidier errors 039fa1b Suggest how to fix illegally nested foralls in GADT constructor type signatures c948b78 Fix #11785 by making reifyKind = reifyType af9f3fa Remove extra ` from "kind-indexed GADTs" doc 03327bf Handle ListPat in isStrictPattern 36d1b08 Doctest for Void.absurd 49ddea9 Sections with undefined operators have non-standard behavior 43b0c2c Insert missing blank line to fix Applicative doc 63397cb Add some Monoid doctests f762181 Mention the category laws explicitly a30187d Convert documentation examples to doctests for ReadP module bfa9048 Loads of doc(test)s 2c0ab47 Add missing initial version for extension doc. 0e1b6f8 Fix index entries in "separate compilation" section 3385669 user-guide: fix examples of ghci commands 69a0f01 rts: Enable USDT probes object on Linux 82ee71f user-guide: add `:type +d` and `:type +v` in release highlight dc42c0d Fix #13399 by documenting higher-rank kinds. 0385347 Remove unneeded reqlibs for mtl and parsec in the GHC testsuite c5605ae Make function intToSBigNat# preserve sign (fixes #14085) 0286214 testsuite: Add test for #13916 fee253f CSE.cseOneExpr: Set InScopeSet correctly 6257fb5 Comments about GlobalRdrEnv shadowing 118efb0 Restrict Lint's complaints about recursive INLINEs somewhat 698adb5 Tracing in OccAnal (commented out) 4c6fcd7 Comments only 61c4246 Test Trac #14110 f50e30e Doctests for Data.Tuple 6267d8c Enable -Wcpp-undef for GHC and runtime system cf8ab1c users_guide: Convert mkUserGuidePart generation to a Sphinx extension 8e5b6ec Add strict variant of iterate ee2e9ec Correct incorrect free in PE linker 1cdceb9 Revert "Add strict variant of iterate" 34bd43d Fix loading of dlls on 32bit windows 6982ee9 Fix #14125 by normalizing data family instances more aggressively a89bb80 Fix #14114 by checking for duplicate vars on pattern synonym RHSes 79b259a Fix #13885 by freshening reified GADT constructors' universal tyvars 8476097 Revise function arity mismatch errors involving TypeApplications 8fd9599 Make the Read instance for Proxy (and friends) ignore precedence afc2f79 Move validate cleaning from distclean to clean 4717ce8 Fix incorrect retypecheck loop in -j (#14075) 9afaebe StgLint: Allow join point bindings of unlifted type cd5a970 Make law for Foldable.length explicit 20c7053 Bump haddock submodule 090d896 fix typo (expreesions -> expressions) 028645c Fixed a typo in template-haskell documentation dbaa9a2 DynFlags: Add inverse of -dno-debug-output 3625728 Add support for producing position-independent executables 7463a95 users-guide: Better error messages on incomplete ghc-flag directives 74af2e7 Typo fixed 11657c4 Better pretty-printing for CHoleCan a211dca Fix defer-out-of-scope-variables aeb4bd9 Remove typeKind from Type.hs-boot 5f3d2d3 CNF: Implement compaction for small pointer arrays a0b7b10 Restrict exprOkForSpeculation/case to unlifted types 407c11b Bottoming expressions should not be expandable 33452df Refactor the Mighty Simplifier 8649535 Don't do the RhsCtxt thing for join points dd89a13 Comments, plus adjust debug print of TcTyThing(ATyVar) a67b66e Add strict variant of iterate f135fb2 rts: Fix warnings on aarch64 and clean up style 80ccea8 rts: Fix references to Note [BFD import library] 76e59a2 rts: Fix ASSERTs with space before opening paren 8f19c65 Rip out mkUserGuidePart 83484a6 Fix two typos in the ImpredicativeTypes user guide a055f24 Adjust test suite stats 682e8e6 Actually bump T12150 29da01e Make parsed AST dump output lazily 6e0e0b0 Comments only 8834d48 Better debug-printing for Outputable TyConBinder 547e4c0 A bit more -ddump-tc tracing 6f050d9 Add TcRnMonad.unlessXOptM 0257dac Refactor bindHsQTyVars and friends 86e6a5f Small refactoring of meta-tyvar cloning 4455c86 Use a well-kinded substitution to instantiate 8eead4d Improve kind-application-error message a6c448b Small refactor of getRuntimeRep aed7d43 Add HasDebugStack for typeKind 248ad30 testsuite: Add test for #14128 db3a8e1 desugar: Ensure that a module's dep_orphs doesn't contain itself 5266ab9 Remove dll-split. 895a765 Refactor type family instance abstract syntax declarations 3c6b2fc Fix decomposition error on Windows 5f6a820 Add gen-dll as replacement for dll-split f86de44 ghc-pkg: Try opening lockfiles in read-write mode first a27bb1b base: Add support for file unlocking 779b9e6 PackageDb: Explicitly unlock package database before closing 9d57d8c nativeGen: Don't index into linked lists 651b4dc StgLint: Show type of out-of-scope binders a36b34c StgLint: Enforce MultiValAlt liveness invariant only after unariser f17f106 StgLint: Give up on trying to compare types 1561525 HsExpr: Fix typo 6f1ccaa Add a Note describing #14128 567dca6 Add some traceRn and (Outputable StmtTree) 628b666 Add comments to RnTypes fca1962 Define and use HsArg 805b29b Add debugPprType 3790ea9 Small changes to ddump-tc tracing 2c133b6 Really fix Trac #14158 c0feee9 Add missing Semigroup instances to compiler b2c2e3e Add missing Semigroup instances in utils/{hpc,runghc} dd643bc Improve stm haddocks 1f052c5 Fix order of PrelRule 8a1de42 Add testcase for #14178 f089c32 Remove broken citeseer citation links 590e737 Update transformers submodule 6330b0b Document the intricacies of ForallC variable quantification better 5dd6b13 Disallow bang/lazy patterns in the RHSes of implicitly bidirectional patsyns 8e4229a Fix #14167 by using isGadtSyntaxTyCon in more places 0ec4376 Document the Generic(1) laws cb3363e Move NonEmpty definition into GHC.Base 31281a4 testsuite: Fix validation of ways b996e12 testsuite: Add test for #14129 7e5d4a0 Remember the AvailInfo for each IE b9ac9e0 Fix egregious duplication of vars in RnTypes 1300afa get-win32-tarballs: Use bash, not sh a4c2ac2 get-win32-tarballs: Use correct `find` 542f89f Replace hashing function for string keys implementation with xxhash cd857dd SetLevels: Substitute in ticks in lvlMFE 6458b8d base: Update acosh to handle -1::Complex c2881a2 StgLint: Show constructor arity in mismatch message 822abbb eventlog: Clean up profiling heap breakdown type 24e50f9 rts: Add heap breakdown type for -hT 0829821 Implicitly bind kind variables in type family instance RHSes when it's sensible 0cd467b rts: Fix use of #if 2273353 Clean up opt and llc c6726d6 Cleanups, remove commented-out code a04cfcf Update xhtml submodule fee403f Handle W80 in floatFormat d97a6fe Fix typos in diagnostics, testsuite and comments 055d73c Travis: Boot with ghc-8.2.1, and disable test suite 8ae263c Make Semigroup a superclass of Monoid (re #14191) be514a6 includes/rts: Drop trailing comma cb4878f Drop special handling of iOS and Android 011e15a Deal with unbreakable blocks in Applicative Do 22f11f1 Bump T783 expected allocations cf6b4d1 Remove now redundant CPP 122f183 Remove now redundant cabal conditionals in {ghc,template-haskell}.cabal 400ead8 Remove makefile logic for legacy -this-package-key dab0e51 Canonicalise Monoid instances in GHC 346e562 Canonicalise MonoidFail instances in GHC 838a10f Retire cabal_macros_boot.h hack fe35b85 Add testcase for #14186 fe04f37 Allow CSE'ing of work-wrapped bindings (#14186) 0ebc8dc Add a test for #14140 9ff9c35 Check if -XStaticPointers is enabled when renaming static expressions dafa012 Add regression test for #14209 b890e88 rts: Print message before SIGUSR2 backtrace d645e44 DriverMkDepend: Kill redundant import f8e383f Clarify Data.Data documentation 91262e7 Use ar for -staticlib e62391a [RTS] Harden against buffer overflow cbd4911 Make IntPtr and WordPtr as instance of Data.Data typeclass, fix #13115 8ff11c4 Fix @since annotations in GHC.Stats 6139f7f Add non-ASCII isLetter True example 2fe6f6b Option "-ddump-rn-ast" dumps imports and exports too f9bf621 Better document TypeRep patterns 4be195e Simplify Data.Type.Equality.== 4e22220 Clarify seq documentation 4cead3c rts: Add regsterCc(s)List to RTS symbols list 10a1a47 Model divergence of retry# as ThrowsExn, not Diverges 959a623 No need to check ambiguity for visible type args ab2d3d5 More refinements to debugPprType 3a27e34 Fix subtle bug in TcTyClsDecls.mkGADTVars 8bf865d Tidying could cause ill-kinded types 0390e4a Refactor to eliminate FamTyConShape a38acda Refactor tcInferApps 9218ea6 Interim fix for a nasty type-matching bug 9e46167 Remove unused variable binding b6b56dd [RTS] Make -po work 93da9f9 Add test for Trac #14232 3b68687 Test #14038 in dependent/should_compile/T14038 c813d8c Regression test for #12742 b977630 Test #12938 in indexed-types/should_compile/T12938 04bb873 Fix #13407 by suppressing invisibles better. ecb316c nativeGen: A few strictness fixes 58f1f73 Bump primitive submodule 3edbf5c testsuite: Fix dependence on grep behavior in T8129 89c8d4d Fix #13909 by tweaking an error message. e5beb6e Make rejigConRes do kind substitutions fa626f3 Fix #13929 by adding another levity polymorphism check 86e1db7 Test #13938, with expect_broken 8f99cd6 Fix #13963. 7b8827a Bump submodule nofib (Semigroup now required) f043cd5 Fix name of note 4340165 Ignore untracked in text, parsec and mtl submodules [skip ci] 9e227bb Fix missing fields warnings in empty record construction, fix #13870 f4d50a0 Fix #14228 by marking SumPats as non-irrefutable 2bfba9e base: Fix mixed tabs/spaces indentation in inputReady.c 9498c50 Renamer now preserves location for IEThingWith list items 47a9ec7 Remove dead function TcUnify.wrapFunResCoercion b099171 base: Enable TypeInType in Data.Type.Equality 4ec4ca9 base: Add missing MonadFail instance for strict ST 60a3f11 Fix pointer tagging mistake a83f17e base: Fix missing import of Control.Monad.Fail 2258a29 testsuite: Fix MonadFail test output for new ST instance cdaf5f2 [RTS] Add getObjectLoadStatus 120c568 Allow opt+llc from LLVM5 10ca801 Generalise constraint on `instance Monoid (Maybe a)` to Semigroup a2f004b Remove redundant/obsolete CPP usage 1db0f4a Fix unused-given-constraint bug 6252292 rts/RetainerProfile: Adding missing closure types to isRetainer 8b007ab nativeGen: Consistently use blockLbl to generate CLabels from BlockIds 12a92fe OccurAnal: Ensure SourceNotes don't interfere with join-point analysis f63bc73 compiler: introduce custom "GhcPrelude" Prelude 7c7914d Fix Windows build regression due to GhcPrelude change 28a115e base: fdReady(): Improve accuracy and simplify code. c2a1fa7 base: Fix fdReady() potentially running forever on Windows. 826c3b1 base: Fix fdReady() potentially running forever for Windows Char devices. 66240c9 base: Fix fdReady() returning immediately for pipes on Windows. 11c478b rts: Update comment about FreeBSD's unsigned FD_SETSIZE b7f2d12 rts: Fix typo in comment ba4dcc7 base: Make it less likely for fdReady() to fail on Windows sockets. 022455f base: Add more detail to FD_SETSIZE related error message bbb8cb9 users-guide: Mention changes necessary due to #13391 3198956 Factor mkCoreApp and mkCoreApps 7920a7d cmm/CBE: Collapse blocks equivalent up to alpha renaming of local registers 0aba999 Restore function powModSecInteger 11d9615 Make zipWith and zipWith3 inlinable. 02ff705 Add 'stm' package to the global package database d7705f2 aclocal.m4: call cygpath on mingw32 only ced2cb5 Typofixes (visiblity -> visibility) 283eb1a Initial CircleCI support. cc6be3a Typeable: Allow App to match arrow types 9e46d88 Typeable: Generalize kind of represented type 72b00c3 Identify fields by selector when type-checking (fixes #13644) acd346e testsuite: Add testcase for #14253 d86b237 testsuite: Add unboxed sum to T13929 58a7062 base: Add changelog entry for withTypeable generalization 063e0b4 Bump base to 4.11.0.0 1c92083 Also show types that subsume a hole as valid substitutions for that hole. ddb38b5 testsuite: Bump allocations of T12150 9aa7389 cmm/CBE: Use foldLocalRegsDefd feac0a3 Reexport Semigroup's <> operator from Prelude (#14191) 760b9a3 rts: Set unwind information for remaining stack frames a9d417d rts: Set unwind information for catch_frame 1755869 Implement TH addCorePlugin. d7b8da1 Fix broken LLVM code gen 5a8b843 Remove 'stm' from EXTRA_PACKAGES set 2f10438 Fix build with GhcWithInterpreter=NO 65943a3 Bump haskeline submodule c2373b7 Additional LLVM_TARGET logic. d559612 Fix AsmTempLabel d7b260f [Semigroup] fix genapply 9c7d065 Revert "Typeable: Allow App to match arrow types" b3ae47c don't allow AsmTempLabel in UNREG mode (Trac #14264) 3c74a51 Deal with large extra-contraints wildcards 7721e8e Make pprQuotedList use fsep not hsep 3b4833a Comments only 1b476ab Improve type-error reporting abed9bf Fix solving of implicit parameter constraints 0e60cc1 Document how GHC disambiguates between multiple COMPLETE sets 3804a7e Bump template-haskell to 2.13.0.0 2b2595e Ensure text mode when calling debug functions c839c57 Fix the searching of target AR tool abca29f Adds mingw64 to the valid GHC OSs. 6de1a5a Document Typeable's treatment of kind polymorphic tycons d07b8c7 Include original process name in worker thread name (#14153) 9acbeb5 integer-gmp: Fix style d11611f Add NOINLINE pragma to builtinRules 9738e8b Use SIGQUIT for DWARF backtraces instead of SIGUSR2 49c1a20 configure: Catch case where LLVM tools can't be found 65f7d87 configure: Don't hard-code strip tool 2f8e6e7 testsuite: Expect T13168 to be broken on Windows 7446c7f A bunch of typofixes c41ccbf Omit Typeable from the "naturally coherent" list 6e7c09d StgCmmMonad: Remove unnecessary use of unboxed tuples 6246407 primops: Add some notes regarding the meaning of the "type" field 1d1b991 rts: Inform kernel that we won't need reserved address space 57372a7 PrelRules: Handle Int left shifts of more than word-size bits 0ffa396 testsuite: Add test for #14272 f9f1e38 TcInteract: Remove redundant import of Typeable 3ec579d Release console for ghci wrapper 8c23b54 Rules: Show the binder type in the unbound template binder error 7fb89e8 rts: Silence missing __noreturn__ warning 1825cbd Switch VEH to VCH and allow disabling of SEH completely. 8f468fe base: fdReady(): Add note about O_NONBLOCK requirement 018c40f desugar: Catch levity polymorphism in unboxed sum expressions 30a1eee rts: Throw proper HeapOverflow exception on allocating large array 47888fd Revert "Switch VEH to VCH and allow disabling of SEH completely." 1421d87 Switch VEH to VCH and allow disabling of SEH completely. 07ddeaf GHC_LLVM_TARGET: Keep android OS 60b0645 llvm-targets: drop soft-float 4364f1e Typofixes 1e9f90a Move check-ppr and check-api-annotations to testsuite/utils 9bf6310 Add TODO about getMonotonicNSec() wrapping that can no longer happen. dddef31 fdReady(): Fix some C -Wconversion warnings. 03009aa base: fdReady(): Ensure and doc that return values are always -1/0/1 a10729f configure: Make sure we try all possible linkers 5935acd mkDataConRep: fix bug in strictness signature (#14290) 7aa000b Fix #13391 by checking for kind-GADTs 464396d Fix Raspberry Pi target name 9c05fc4 user-guide: Document -Weverything 626f045 Document a law for TH's Lift class effcd56 Don't use "character" in haddocks of Char c15c427 iserv: Don't build vanilla iserv unless vanilla libraries are built e515c7f Allow libffi snapshots e299121 Bump submodule nofib again (Semigroup now required) 00ff023 Travis: Install texinfo 11a59de CircleCI: Install texinfo 0e96812 Pretty-printer missing parens for infix class declaration c0e6c73 Rewrite boot in Python e30d9ca rel-notes: Mention libffi packaging change e462b65 Bump libffi-tarballs submodule d5e60de user-guide: Fix :since: annotation of -pie and add documentation for -fPIE d0c5d8d No libffi docs a4ee289 Adds x86 NONE relocation type a1fc7ce Comments only a8fde18 Fix bug in the short-cut solver b1e0c65 Make GHC.IO.Buffer.summaryBuffer strict dbbee1b Fix nasty bug in w/w for absence analysis cb76754 Suppress error cascade in record fields a02039c Add regression test for #9725 a36eea1 Revert installing texinfo in CI systems 55001c0 Sync base/changelog.md ec9ac20 Add ability to produce crash dumps on Windows 8d64745 Optimize linker by minimizing calls to tryGCC to avoid fork/exec overhead. ef26182 Track the order of user-written tyvars in DataCon fa8035e Implement Div, Mod, and Log for type-level nats. 377d5a2 base: Add missing @since annotations in GHC.TypeNats de1b802 genapply: Explicitly specify arguments f3f624a Include libraries which fill holes as deps when linking. 4899a86 Don't pass HscEnv to functions in the Hsc monad 361af62 base: Remove deprecated Chan combinators 3201d85 user-guide: Mention COMPLETE pragma in release notes 3030eee rts: Print newline after "Stack trace:" on barf 7109fa8 configure: Accept *-msys as a Windows OS in a triple 5eae140 merged up to 7109fa8157f from master into wip/kavon-nosplit-llvm From git at git.haskell.org Thu Oct 5 15:28:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Oct 2017 15:28:06 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (5744240) Message-ID: <20171005152806.14BC03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/574424051da4d9f2564693612a1a205d12439b1b/ghc >--------------------------------------------------------------- commit 574424051da4d9f2564693612a1a205d12439b1b Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- 574424051da4d9f2564693612a1a205d12439b1b compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 399 ++++++++++++++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 8 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + 12 files changed, 445 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 574424051da4d9f2564693612a1a205d12439b1b From git at git.haskell.org Thu Oct 5 15:28:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Oct 2017 15:28:08 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (9b3181b) Message-ID: <20171005152808.D5D563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/9b3181ba94dbe724f99de87cd3dfb5d20bb90b04/ghc >--------------------------------------------------------------- commit 9b3181ba94dbe724f99de87cd3dfb5d20bb90b04 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration >--------------------------------------------------------------- 9b3181ba94dbe724f99de87cd3dfb5d20bb90b04 compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 3 +++ compiler/simplCore/SimplCore.hs | 37 ++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 35 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9b3181ba94dbe724f99de87cd3dfb5d20bb90b04 From git at git.haskell.org Thu Oct 5 15:28:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Oct 2017 15:28:11 +0000 (UTC) Subject: [commit: ghc] wip/T14152's head updated: Inline exit join points in the "final" simplifier iteration (9b3181b) Message-ID: <20171005152811.402BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14152' now includes: 7aa000b Fix #13391 by checking for kind-GADTs 464396d Fix Raspberry Pi target name 9c05fc4 user-guide: Document -Weverything 626f045 Document a law for TH's Lift class effcd56 Don't use "character" in haddocks of Char c15c427 iserv: Don't build vanilla iserv unless vanilla libraries are built e515c7f Allow libffi snapshots e299121 Bump submodule nofib again (Semigroup now required) 00ff023 Travis: Install texinfo 11a59de CircleCI: Install texinfo 0e96812 Pretty-printer missing parens for infix class declaration c0e6c73 Rewrite boot in Python e30d9ca rel-notes: Mention libffi packaging change e462b65 Bump libffi-tarballs submodule d5e60de user-guide: Fix :since: annotation of -pie and add documentation for -fPIE d0c5d8d No libffi docs a4ee289 Adds x86 NONE relocation type a1fc7ce Comments only a8fde18 Fix bug in the short-cut solver b1e0c65 Make GHC.IO.Buffer.summaryBuffer strict dbbee1b Fix nasty bug in w/w for absence analysis cb76754 Suppress error cascade in record fields a02039c Add regression test for #9725 a36eea1 Revert installing texinfo in CI systems 55001c0 Sync base/changelog.md ec9ac20 Add ability to produce crash dumps on Windows 8d64745 Optimize linker by minimizing calls to tryGCC to avoid fork/exec overhead. ef26182 Track the order of user-written tyvars in DataCon fa8035e Implement Div, Mod, and Log for type-level nats. 377d5a2 base: Add missing @since annotations in GHC.TypeNats de1b802 genapply: Explicitly specify arguments f3f624a Include libraries which fill holes as deps when linking. 4899a86 Don't pass HscEnv to functions in the Hsc monad 361af62 base: Remove deprecated Chan combinators 3201d85 user-guide: Mention COMPLETE pragma in release notes 3030eee rts: Print newline after "Stack trace:" on barf 7109fa8 configure: Accept *-msys as a Windows OS in a triple 5744240 Implement a dedicated exitfication pass #14152 9b3181b Inline exit join points in the "final" simplifier iteration From git at git.haskell.org Thu Oct 5 16:18:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Oct 2017 16:18:02 +0000 (UTC) Subject: [commit: ghc] master: Remove m_type from Match (#14313) (d8d87fa) Message-ID: <20171005161802.25BCF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d8d87fa2b22404b7939956974f53858c41ec7769/ghc >--------------------------------------------------------------- commit d8d87fa2b22404b7939956974f53858c41ec7769 Author: Joachim Breitner Date: Tue Oct 3 22:09:49 2017 -0400 Remove m_type from Match (#14313) this is a remains from supporting Result Type Signaturs in the ancient past. Differential Revision: https://phabricator.haskell.org/D4066 >--------------------------------------------------------------- d8d87fa2b22404b7939956974f53858c41ec7769 compiler/hsSyn/Convert.hs | 6 ++---- compiler/hsSyn/HsExpr.hs | 9 --------- compiler/hsSyn/HsUtils.hs | 3 +-- compiler/parser/Parser.y | 20 +++++++------------- compiler/parser/RdrHsSyn.hs | 12 +++++------- compiler/rename/RnBinds.hs | 23 +++-------------------- compiler/typecheck/TcArrows.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 3 +-- compiler/typecheck/TcMatches.hs | 13 +++---------- testsuite/tests/rename/should_fail/T2310.hs | 5 ----- testsuite/tests/rename/should_fail/T2310.stderr | 5 ----- testsuite/tests/rename/should_fail/all.T | 1 - 12 files changed, 23 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 d8d87fa2b22404b7939956974f53858c41ec7769 From git at git.haskell.org Thu Oct 5 19:48:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Oct 2017 19:48:41 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for #14326 (429fafb) Message-ID: <20171005194841.E80093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/429fafb5b2b1ac02fd04d9a98e30b5991125692c/ghc >--------------------------------------------------------------- commit 429fafb5b2b1ac02fd04d9a98e30b5991125692c Author: Ryan Scott Date: Thu Oct 5 15:46:05 2017 -0400 Add regression test for #14326 Commit 6b77914cd37b697354611bcd87897885c1e5b4a6 wound up fixing #14326. Let's add a regression test so that it stays that way. >--------------------------------------------------------------- 429fafb5b2b1ac02fd04d9a98e30b5991125692c testsuite/tests/patsyn/should_compile/T14326.hs | 21 +++++++++++++++++++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 2 files changed, 22 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T14326.hs b/testsuite/tests/patsyn/should_compile/T14326.hs new file mode 100644 index 0000000..59a1eb4 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T14326.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ExplicitForAll #-} +{-# OPTIONS_GHC -fwarn-incomplete-patterns #-} +module T14326 where + +data E a b = L' a | R b +pattern L :: forall b a. a -> E a b +pattern L a = L' a +{-# COMPLETE L, R #-} + +testMono :: E (E Int Int) Int -> Int +testMono x = case x of + L (L _) -> 0 + L (R _) -> 1 + R _ -> 2 + +testPoly :: E (E a b) c -> Int +testPoly x = case x of + L (L _) -> 0 + L (R _) -> 1 + R _ -> 2 diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index b8c9806..8bc9dbd 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -73,3 +73,4 @@ test('T13752a', normal, compile, ['']) test('T13768', normal, compile, ['']) test('T14058', [extra_files(['T14058.hs', 'T14058a.hs'])], multimod_compile, ['T14058', '-v0']) +test('T14326', normal, compile, ['']) From git at git.haskell.org Fri Oct 6 14:30:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Oct 2017 14:30:58 +0000 (UTC) Subject: [commit: ghc] master: Testsuite update following d8d87fa (f6bca0c) Message-ID: <20171006143058.1F7B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f6bca0c5e3c53fa6f06949d4f997d0f1761ae06b/ghc >--------------------------------------------------------------- commit f6bca0c5e3c53fa6f06949d4f997d0f1761ae06b Author: Joachim Breitner Date: Fri Oct 6 10:29:44 2017 -0400 Testsuite update following d8d87fa >--------------------------------------------------------------- f6bca0c5e3c53fa6f06949d4f997d0f1761ae06b testsuite/tests/parser/should_compile/DumpParsedAst.stderr | 1 - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr | 1 - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr | 1 - 3 files changed, 3 deletions(-) diff --git a/testsuite/tests/parser/should_compile/DumpParsedAst.stderr b/testsuite/tests/parser/should_compile/DumpParsedAst.stderr index b6b74a4..46ab214 100644 --- a/testsuite/tests/parser/should_compile/DumpParsedAst.stderr +++ b/testsuite/tests/parser/should_compile/DumpParsedAst.stderr @@ -212,7 +212,6 @@ (Prefix) (NoSrcStrict)) [] - (Nothing) (GRHSs [({ DumpParsedAst.hs:11:6-23 } (GRHS diff --git a/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr b/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr index 6d6dac1..c7daf90 100644 --- a/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr +++ b/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr @@ -22,7 +22,6 @@ (Prefix) (NoSrcStrict)) [] - (Nothing) (GRHSs [({ DumpRenamedAst.hs:18:6-23 } (GRHS diff --git a/testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr b/testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr index ff6379f..e0d810d 100644 --- a/testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr +++ b/testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr @@ -252,7 +252,6 @@ (Prefix) (NoSrcStrict)) [] - (Nothing) (GRHSs [({ DumpTypecheckedAst.hs:11:6-23 } (GRHS From git at git.haskell.org Fri Oct 6 14:34:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Oct 2017 14:34:02 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (3a91d05) Message-ID: <20171006143402.C72183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/3a91d05f7ad2f34175d0035160485cf8e68000e7/ghc >--------------------------------------------------------------- commit 3a91d05f7ad2f34175d0035160485cf8e68000e7 Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- 3a91d05f7ad2f34175d0035160485cf8e68000e7 compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 403 ++++++++++++++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 8 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + 12 files changed, 449 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3a91d05f7ad2f34175d0035160485cf8e68000e7 From git at git.haskell.org Fri Oct 6 14:34:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Oct 2017 14:34:05 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (0108a33) Message-ID: <20171006143405.93EF83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/0108a3370d35cb45e9d0a2e8e39ae75073993538/ghc >--------------------------------------------------------------- commit 0108a3370d35cb45e9d0a2e8e39ae75073993538 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration >--------------------------------------------------------------- 0108a3370d35cb45e9d0a2e8e39ae75073993538 compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 6 ++++++ compiler/simplCore/SimplCore.hs | 40 +++++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 41 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0108a3370d35cb45e9d0a2e8e39ae75073993538 From git at git.haskell.org Fri Oct 6 14:34:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Oct 2017 14:34:07 +0000 (UTC) Subject: [commit: ghc] wip/T14152's head updated: Inline exit join points in the "final" simplifier iteration (0108a33) Message-ID: <20171006143407.CD1F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14152' now includes: d8d87fa Remove m_type from Match (#14313) 429fafb Add regression test for #14326 f6bca0c Testsuite update following d8d87fa 3a91d05 Implement a dedicated exitfication pass #14152 0108a33 Inline exit join points in the "final" simplifier iteration From git at git.haskell.org Sat Oct 7 21:07:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Oct 2017 21:07:36 +0000 (UTC) Subject: [commit: ghc] master: Incorporate changes from #11721 into Template Haskell (341d3a7) Message-ID: <20171007210736.46FEC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/341d3a7896385f14580d048ea7681232e5b242ce/ghc >--------------------------------------------------------------- commit 341d3a7896385f14580d048ea7681232e5b242ce Author: Ryan Scott Date: Sat Oct 7 16:58:56 2017 -0400 Incorporate changes from #11721 into Template Haskell Summary: #11721 changed the order of type variables in GADT constructor type signatures, but these changes weren't reflected in Template Haskell reification of GADTs. Let's do that. Along the way, I: * noticed that the `T13885` test was claiming to test TH reification of GADTs, but the reified data type wasn't actually a GADT! Since this patch touches that part of the codebase, I decided to fix this. * incorporated some feedback from @simonpj in https://phabricator.haskell.org/D3687#113566. (These changes alone don't account for any different in behavior.) Test Plan: make test TEST=T11721_TH Reviewers: goldfire, austin, bgamari, simonpj Reviewed By: goldfire, bgamari, simonpj Subscribers: rwbarton, thomie, simonpj GHC Trac Issues: #11721 Differential Revision: https://phabricator.haskell.org/D4070 >--------------------------------------------------------------- 341d3a7896385f14580d048ea7681232e5b242ce compiler/basicTypes/DataCon.hs | 27 ++++++++++++++------------- compiler/basicTypes/DataCon.hs-boot | 1 - compiler/typecheck/TcSplice.hs | 20 +++++++++++--------- docs/users_guide/8.4.1-notes.rst | 10 ++++++++++ testsuite/tests/th/T11721_TH.hs | 26 ++++++++++++++++++++++++++ testsuite/tests/th/T13885.hs | 5 +++-- testsuite/tests/th/all.T | 1 + 7 files changed, 65 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 341d3a7896385f14580d048ea7681232e5b242ce From git at git.haskell.org Sat Oct 7 21:07:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Oct 2017 21:07:39 +0000 (UTC) Subject: [commit: ghc] master: Fix #14320 by looking through HsParTy in more places (f1d2db6) Message-ID: <20171007210739.7EC763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f1d2db68d87f2c47a8dd4d86910e415599777f9f/ghc >--------------------------------------------------------------- commit f1d2db68d87f2c47a8dd4d86910e415599777f9f Author: Ryan Scott Date: Sat Oct 7 16:59:03 2017 -0400 Fix #14320 by looking through HsParTy in more places Summary: GHC was needlessly rejecting GADT constructors' type signatures that were surrounded in parentheses due to the fact that `splitLHsForAllTy` and `splitLHsQualTy` (which are used to check as part of checking if GADT constructor return types are correct) weren't looking through parentheses (i.e., `HsParTy`). This is easily fixed, though. Test Plan: make test TEST=T14320 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14320 Differential Revision: https://phabricator.haskell.org/D4072 >--------------------------------------------------------------- f1d2db68d87f2c47a8dd4d86910e415599777f9f compiler/hsSyn/HsTypes.hs | 6 ++++-- testsuite/tests/gadt/T14320.hs | 15 +++++++++++++++ testsuite/tests/gadt/all.T | 1 + 3 files changed, 20 insertions(+), 2 deletions(-) diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs index b9cd946..e9dea63 100644 --- a/compiler/hsSyn/HsTypes.hs +++ b/compiler/hsSyn/HsTypes.hs @@ -1053,11 +1053,13 @@ splitLHsSigmaTy ty splitLHsForAllTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsType pass) splitLHsForAllTy (L _ (HsForAllTy { hst_bndrs = tvs, hst_body = body })) = (tvs, body) -splitLHsForAllTy body = ([], body) +splitLHsForAllTy (L _ (HsParTy t)) = splitLHsForAllTy t +splitLHsForAllTy body = ([], body) splitLHsQualTy :: LHsType pass -> (LHsContext pass, LHsType pass) splitLHsQualTy (L _ (HsQualTy { hst_ctxt = ctxt, hst_body = body })) = (ctxt, body) -splitLHsQualTy body = (noLoc [], body) +splitLHsQualTy (L _ (HsParTy t)) = splitLHsQualTy t +splitLHsQualTy body = (noLoc [], body) splitLHsInstDeclTy :: LHsSigType GhcRn -> ([Name], LHsContext GhcRn, LHsType GhcRn) diff --git a/testsuite/tests/gadt/T14320.hs b/testsuite/tests/gadt/T14320.hs new file mode 100644 index 0000000..4acd4c8 --- /dev/null +++ b/testsuite/tests/gadt/T14320.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE RankNTypes, GADTs, KindSignatures #-} +module T14320 +where + +data Exp :: * where + Lit :: (Int -> Exp) + +newtype TypedExp :: * -> * where + TEGood :: forall a . (Exp -> (TypedExp a)) + +-- The only difference here is that the type is wrapped in parentheses, +-- but GHC 8.0.1 rejects this program +-- +newtype TypedExpToo :: * -> * where + TEBad :: (forall a . (Exp -> (TypedExpToo a))) diff --git a/testsuite/tests/gadt/all.T b/testsuite/tests/gadt/all.T index 3c825f0..c81ab80 100644 --- a/testsuite/tests/gadt/all.T +++ b/testsuite/tests/gadt/all.T @@ -114,3 +114,4 @@ test('T9096', normal, compile, ['']) test('T9380', normal, compile_and_run, ['']) test('T12087', normal, compile_fail, ['']) test('T12468', normal, compile_fail, ['']) +test('T14320', normal, compile, ['']) From git at git.haskell.org Sat Oct 7 22:01:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Oct 2017 22:01:51 +0000 (UTC) Subject: [commit: ghc] master: Simply Data instance context for AmbiguousFieldOcc (f337a20) Message-ID: <20171007220151.9D48A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f337a208b1e1a53cbdfee8b49887858cc3a500f6/ghc >--------------------------------------------------------------- commit f337a208b1e1a53cbdfee8b49887858cc3a500f6 Author: Ryan Scott Date: Sat Oct 7 17:59:07 2017 -0400 Simply Data instance context for AmbiguousFieldOcc The current, verbose instance context can be compacted into `DataId pass`. Indeed, that's what most of the `Data` instances in this module already do, so this just makes things consistent. >--------------------------------------------------------------- f337a208b1e1a53cbdfee8b49887858cc3a500f6 compiler/hsSyn/HsTypes.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs index e9dea63..e9fc71b 100644 --- a/compiler/hsSyn/HsTypes.hs +++ b/compiler/hsSyn/HsTypes.hs @@ -1129,10 +1129,7 @@ mkFieldOcc rdr = FieldOcc rdr PlaceHolder data AmbiguousFieldOcc pass = Unambiguous (Located RdrName) (PostRn pass (IdP pass)) | Ambiguous (Located RdrName) (PostTc pass (IdP pass)) -deriving instance ( Data pass - , Data (PostTc pass (IdP pass)) - , Data (PostRn pass (IdP pass))) - => Data (AmbiguousFieldOcc pass) +deriving instance DataId pass => Data (AmbiguousFieldOcc pass) instance Outputable (AmbiguousFieldOcc pass) where ppr = ppr . rdrNameAmbiguousFieldOcc From git at git.haskell.org Tue Oct 10 18:55:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Oct 2017 18:55:37 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix bug in the short-cut solver (0461305) Message-ID: <20171010185537.07AC13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/046130558d825dd05734238c8c87bae4a148bdc1/ghc >--------------------------------------------------------------- commit 046130558d825dd05734238c8c87bae4a148bdc1 Author: Simon Peyton Jones Date: Mon Oct 2 15:58:46 2017 +0100 Fix bug in the short-cut solver Trac #13943 showed that the relatively-new short-cut solver for class constraints (aka -fsolve-constant-dicts) was wrong. In particular, see "Type families" under Note [Shortcut solving] in TcInteract. The short-cut solver recursively solves sub-goals, but it doesn't flatten type-family applications, and as a result it erroneously thought that C (F a) cannot possibly match (C 0), which is simply untrue. That led to an inifinte loop in the short-cut solver. The significant change is the one line + , all isTyFamFree preds -- See "Type families" in + -- Note [Shortcut solving] but, as ever, I do some other refactoring. (E.g. I changed the name of the function to shortCutSolver rather than the more generic trySolveFromInstance.) I also made the short-cut solver respect the solver-depth limit, so that if this happens again it won't just produce an infinite loop. A bit of other refactoring, notably moving isTyFamFree from TcValidity to TcType (cherry picked from commit a8fde1831f4b99885b8ed444f9cd7dffd9252150) >--------------------------------------------------------------- 046130558d825dd05734238c8c87bae4a148bdc1 compiler/typecheck/TcInteract.hs | 139 +++++++++++++-------- compiler/typecheck/TcType.hs | 8 +- compiler/typecheck/TcValidity.hs | 4 - testsuite/tests/typecheck/should_compile/T13943.hs | 68 ++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 5 files changed, 161 insertions(+), 59 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 046130558d825dd05734238c8c87bae4a148bdc1 From git at git.haskell.org Tue Oct 10 18:59:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Oct 2017 18:59:25 +0000 (UTC) Subject: [commit: ghc] master: Split SysTools up some (e51e565) Message-ID: <20171010185925.E91943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e51e565da82fe406bf9d5f2c4a72e0737ba7e6ce/ghc >--------------------------------------------------------------- commit e51e565da82fe406bf9d5f2c4a72e0737ba7e6ce Author: Tamar Christina Date: Tue Oct 10 19:58:56 2017 +0100 Split SysTools up some Summary: SysTools and DriverTools have an annoying mutual dependency. They also each contain pieces of the linker. In order for changes to be shared between the library and the exe linking code this dependency needs to be broken in order to avoid using hs-boot files. Reviewers: austin, bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4071 >--------------------------------------------------------------- e51e565da82fe406bf9d5f2c4a72e0737ba7e6ce compiler/ghc.cabal.in | 4 + compiler/main/DriverPipeline.hs | 190 +------- compiler/main/SysTools.hs | 898 +------------------------------------ compiler/main/SysTools/ExtraObj.hs | 239 ++++++++++ compiler/main/SysTools/Info.hs | 256 +++++++++++ compiler/main/SysTools/Process.hs | 347 ++++++++++++++ compiler/main/SysTools/Tasks.hs | 343 ++++++++++++++ 7 files changed, 1199 insertions(+), 1078 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 e51e565da82fe406bf9d5f2c4a72e0737ba7e6ce From git at git.haskell.org Wed Oct 11 12:30:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 12:30:10 +0000 (UTC) Subject: [commit: ghc] master: Change "cobox" to "co" in debug output (79ae03a) Message-ID: <20171011123010.148F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/79ae03aa32c277ae93827519ed7738938e3e1572/ghc >--------------------------------------------------------------- commit 79ae03aa32c277ae93827519ed7738938e3e1572 Author: Simon Peyton Jones Date: Fri Oct 6 13:39:54 2017 +0100 Change "cobox" to "co" in debug output These coercions are /not/ boxed, so "cobox" is positively misleading. And it's longer than necessary. >--------------------------------------------------------------- 79ae03aa32c277ae93827519ed7738938e3e1572 compiler/typecheck/TcMType.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index eabb44d..e89abe1 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -242,7 +242,7 @@ newDict cls tys predTypeOccName :: PredType -> OccName predTypeOccName ty = case classifyPredType ty of ClassPred cls _ -> mkDictOcc (getOccName cls) - EqPred _ _ _ -> mkVarOccFS (fsLit "cobox") + EqPred _ _ _ -> mkVarOccFS (fsLit "co") IrredPred _ -> mkVarOccFS (fsLit "irred") {- From git at git.haskell.org Wed Oct 11 12:30:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 12:30:12 +0000 (UTC) Subject: [commit: ghc] master: Tidy up some convoluted "child/parent" code (7720c29) Message-ID: <20171011123012.D446F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7720c293e7f5ca5089e3d154aad99e8060d6ac63/ghc >--------------------------------------------------------------- commit 7720c293e7f5ca5089e3d154aad99e8060d6ac63 Author: Simon Peyton Jones Date: Wed Oct 4 10:48:10 2017 +0100 Tidy up some convoluted "child/parent" code In investigating something else (Trac #14307) I encountered the wonders of TcRnExports.lookupChildrenExport, and the data type ChildLookupResult. I managed to remove the NameErr constructor from ChildLookupResult, and simplify the code significantly at the same time. This is just refactoring; no change in behaviour. >--------------------------------------------------------------- 7720c293e7f5ca5089e3d154aad99e8060d6ac63 compiler/rename/RnEnv.hs | 15 ++--- compiler/typecheck/TcRnExports.hs | 133 +++++++++++++++++--------------------- 2 files changed, 65 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7720c293e7f5ca5089e3d154aad99e8060d6ac63 From git at git.haskell.org Wed Oct 11 12:30:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 12:30:16 +0000 (UTC) Subject: [commit: ghc] master: Fix over-eager error suppression in TcErrors (c81f66c) Message-ID: <20171011123016.25ED63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c81f66ccafdb4c6c7a09cfaf6819c8797c518491/ghc >--------------------------------------------------------------- commit c81f66ccafdb4c6c7a09cfaf6819c8797c518491 Author: Simon Peyton Jones Date: Thu Oct 5 17:40:28 2017 +0100 Fix over-eager error suppression in TcErrors See Note [Given insolubles] in TcRnTypes Fixes Trac #14325. >--------------------------------------------------------------- c81f66ccafdb4c6c7a09cfaf6819c8797c518491 compiler/typecheck/TcRnTypes.hs | 24 ++++++++++++++++++++++-- testsuite/tests/typecheck/should_fail/T14325.hs | 11 +++++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 34 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index ba0777b..3c7d67f 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -2319,7 +2319,7 @@ trulyInsoluble :: Ct -> Bool -- Yuk! trulyInsoluble insol | isHoleCt insol = isOutOfScopeCt insol - | otherwise = True + | otherwise = not (isGivenCt insol) -- See Note [Given insolubles] instance Outputable WantedConstraints where ppr (WC {wc_simple = s, wc_impl = i, wc_insol = n}) @@ -2334,7 +2334,27 @@ ppr_bag doc bag | otherwise = hang (doc <+> equals) 2 (foldrBag (($$) . ppr) empty bag) -{- +{- Note [Given insolubles] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider (Trac #14325, comment:) + class (a~b) => C a b + + foo :: C a b => a -> b + foo x = x + + hm3 :: C (f b) b => b -> f b + hm3 x = foo x + +From the [G] C (f b) b we get the insoluble [G] f b ~# b. Then we we also +get an unsolved [W] C b (f b). If trulyInsouble is true of this, we'll +set cec_suppress to True, and suppress reports of the [W] C b (f b). But we +may not report the insoluble [G] f b ~# b either (see Note [Given errors] +in TcErrors), so we may fail to report anything at all! Yikes. + +Bottom line: we must be certain to report anything trulyInsoluble. Easiest +way to guaranteed this is to make truly Insoluble false of Givens. + + ************************************************************************ * * Implication constraints diff --git a/testsuite/tests/typecheck/should_fail/T14325.hs b/testsuite/tests/typecheck/should_fail/T14325.hs new file mode 100644 index 0000000..edb6038 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14325.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE GADTs, MultiParamTypeClasses #-} + +module T14325 where + +class (a~b) => C a b + +foo :: C a b => a -> b +foo x = x + +hm3 :: C (f b) b => b -> f b +hm3 x = foo x diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index fe71e37..381e2c5 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -458,3 +458,4 @@ test('T14055', normal, compile_fail, ['']) test('T13909', normal, compile_fail, ['']) test('T13929', normal, compile_fail, ['']) test('T14232', normal, compile_fail, ['']) +test('T14325', normal, compile_fail, ['']) From git at git.haskell.org Wed Oct 11 12:30:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 12:30:18 +0000 (UTC) Subject: [commit: ghc] master: Minor refactoring (461c831) Message-ID: <20171011123018.E36483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/461c83162d70eaf1ab6cb2c45bc590ddee2a9147/ghc >--------------------------------------------------------------- commit 461c83162d70eaf1ab6cb2c45bc590ddee2a9147 Author: Simon Peyton Jones Date: Thu Oct 5 15:02:45 2017 +0100 Minor refactoring I'm trying to understand Check.hs. This patch is a very minor refactoring. No change in behaviour. >--------------------------------------------------------------- 461c83162d70eaf1ab6cb2c45bc590ddee2a9147 compiler/deSugar/Check.hs | 32 ++++++++++++++++---------------- 1 file changed, 16 insertions(+), 16 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 23e4f0e..8fb9553 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -109,20 +109,20 @@ liftD m = ListT $ \sk fk -> m >>= \a -> sk a fk -- users' guide. If you update the implementation of this function, make sure -- to update that section of the users' guide as well. getResult :: PmM PmResult -> DsM PmResult -getResult ls = do - res <- fold ls goM (pure Nothing) - case res of - Nothing -> panic "getResult is empty" - Just a -> return a +getResult ls + = do { res <- fold ls goM (pure Nothing) + ; case res of + Nothing -> panic "getResult is empty" + Just a -> return a } where goM :: PmResult -> DsM (Maybe PmResult) -> DsM (Maybe PmResult) - goM mpm dpm = do - pmr <- dpm - return $ go pmr mpm + goM mpm dpm = do { pmr <- dpm + ; return $ Just $ go pmr mpm } + -- Careful not to force unecessary results - go :: Maybe PmResult -> PmResult -> Maybe PmResult - go Nothing rs = Just rs - go old@(Just (PmResult prov rs (UncoveredPatterns us) is)) new + go :: Maybe PmResult -> PmResult -> PmResult + go Nothing rs = rs + go (Just old@(PmResult prov rs (UncoveredPatterns us) is)) new | null us && null rs && null is = old | otherwise = let PmResult prov' rs' (UncoveredPatterns us') is' = new @@ -130,8 +130,8 @@ getResult ls = do `mappend` (compareLength is is') `mappend` (compareLength rs rs') `mappend` (compare prov prov') of - GT -> Just new - EQ -> Just new + GT -> new + EQ -> new LT -> old go (Just (PmResult _ _ (TypeOfUncovered _) _)) _new = panic "getResult: No inhabitation candidates" @@ -281,9 +281,9 @@ instance Monoid PartialResult where -- data PmResult = PmResult { - pmresultProvenance :: Provenance - , pmresultRedundant :: [Located [LPat GhcTc]] - , pmresultUncovered :: UncoveredCandidates + pmresultProvenance :: Provenance + , pmresultRedundant :: [Located [LPat GhcTc]] + , pmresultUncovered :: UncoveredCandidates , pmresultInaccessible :: [Located [LPat GhcTc]] } -- | Either a list of patterns that are not covered, or their type, in case we From git at git.haskell.org Wed Oct 11 12:30:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 12:30:21 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments only (ab1a758) Message-ID: <20171011123021.BAB9B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ab1a7583635fe2da3a91b70278366ed8f28aa676/ghc >--------------------------------------------------------------- commit ab1a7583635fe2da3a91b70278366ed8f28aa676 Author: Simon Peyton Jones Date: Thu Oct 5 15:02:12 2017 +0100 Typos in comments only >--------------------------------------------------------------- ab1a7583635fe2da3a91b70278366ed8f28aa676 compiler/typecheck/TcErrors.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 82bcb51..27569b5 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -683,7 +683,7 @@ We'd like to point out that the T3 match is inaccessible. It will have a Given constraint [G] Int ~ Bool. But we don't want to report ALL insoluble Given constraints. See Trac -#12466 for a long discussion on. For example, if we aren't careful +#12466 for a long discussion. For example, if we aren't careful we'll complain about f :: ((Int ~ Bool) => a -> a) -> Int which arguably is OK. It's more debatable for @@ -691,7 +691,7 @@ which arguably is OK. It's more debatable for but it's tricky to distinguish these cases to we don't report either. -The bottom line is this: find_gadt_match looks for an encosing +The bottom line is this: find_gadt_match looks for an enclosing pattern match which binds some equality constraints. If we find one, we report the insoluble Given. -} From git at git.haskell.org Wed Oct 11 12:30:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 12:30:24 +0000 (UTC) Subject: [commit: ghc] master: Delete two unused functions (3e44562) Message-ID: <20171011123024.8E9183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e44562ae18526ae0df6370078321dd19b00616f/ghc >--------------------------------------------------------------- commit 3e44562ae18526ae0df6370078321dd19b00616f Author: Simon Peyton Jones Date: Mon Oct 9 13:18:13 2017 +0100 Delete two unused functions Delete unused functions pprArrowChain pprPrefixApp from TyCoRep >--------------------------------------------------------------- 3e44562ae18526ae0df6370078321dd19b00616f compiler/types/TyCoRep.hs | 12 ------------ compiler/types/Type.hs | 2 +- 2 files changed, 1 insertion(+), 13 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 07470e6..5e32bb1 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -61,7 +61,6 @@ module TyCoRep ( pprThetaArrowTy, pprClassPred, pprKind, pprParendKind, pprTyLit, TyPrec(..), maybeParen, - pprPrefixApp, pprArrowChain, pprDataCons, ppSuggestExplicitKinds, pprCo, pprParendCo, @@ -2665,17 +2664,6 @@ pprTypeApp tc tys -- TODO: toIfaceTcArgs seems rather wasteful here ------------------ - -pprPrefixApp :: TyPrec -> SDoc -> [SDoc] -> SDoc -pprPrefixApp = pprIfacePrefixApp - ----------------- -pprArrowChain :: TyPrec -> [SDoc] -> SDoc --- pprArrowChain p [a,b,c] generates a -> b -> c -pprArrowChain _ [] = empty -pprArrowChain p (arg:args) = maybeParen p FunPrec $ - sep [arg, sep (map (arrow <+>) args)] - ppSuggestExplicitKinds :: SDoc -- Print a helpful suggstion about -fprint-explicit-kinds, -- if it is not already on diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index d28f18c..6eaacdf 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -189,7 +189,7 @@ module Type ( pprTheta, pprThetaArrowTy, pprClassPred, pprKind, pprParendKind, pprSourceTyCon, TyPrec(..), maybeParen, - pprTyVar, pprTyVars, pprPrefixApp, pprArrowChain, + pprTyVar, pprTyVars, -- * Tidying type related things up for printing tidyType, tidyTypes, From git at git.haskell.org Wed Oct 11 12:30:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 12:30:27 +0000 (UTC) Subject: [commit: ghc] master: Remove wc_insol from WantedConstraints (f20cf98) Message-ID: <20171011123027.6A0953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f20cf982f126aea968ed6a482551550ffb6650cf/ghc >--------------------------------------------------------------- commit f20cf982f126aea968ed6a482551550ffb6650cf Author: Simon Peyton Jones Date: Mon Oct 9 13:16:59 2017 +0100 Remove wc_insol from WantedConstraints This patch is a pure refactoring, which I've wanted to do for some time. The main payload is * Remove the wc_insol field from WantedConstraints; instead put all the insolubles in wc_simple * Remove inert_insols from InertCans Instead put all the insolubles in inert_irreds * Add a cc_insol flag to CIrredCan, to record that the constraint is definitely insoluble Reasons * Quite a bit of code gets slightly simpler * Fewer concepts to keep separate * Insolubles don't happen at all in production code that is just being recompiled, so previously there was a lot of moving-about of empty sets A couple of error messages acutally improved. >--------------------------------------------------------------- f20cf982f126aea968ed6a482551550ffb6650cf compiler/typecheck/TcCanonical.hs | 46 +++-- compiler/typecheck/TcErrors.hs | 13 +- compiler/typecheck/TcInteract.hs | 25 +-- compiler/typecheck/TcMType.hs | 18 +- compiler/typecheck/TcRnMonad.hs | 11 ++ compiler/typecheck/TcRnTypes.hs | 186 ++++++++++++--------- compiler/typecheck/TcRules.hs | 23 +-- compiler/typecheck/TcSMonad.hs | 84 +++++----- compiler/typecheck/TcSimplify.hs | 44 ++--- compiler/typecheck/TcType.hs | 17 +- testsuite/tests/deriving/should_fail/T3621.stderr | 16 +- testsuite/tests/indexed-types/should_fail/T8518.hs | 0 .../tests/typecheck/should_compile/tc211.stderr | 20 +-- .../tests/typecheck/should_fail/T12589.stderr | 4 +- .../tests/typecheck/should_fail/T13311.stderr | 4 +- testsuite/tests/typecheck/should_fail/T7851.stderr | 4 +- testsuite/tests/typecheck/should_fail/T8603.stderr | 7 +- .../tests/typecheck/should_fail/tcfail122.stderr | 2 +- .../warnings/should_fail/CaretDiagnostics1.stderr | 4 +- 19 files changed, 280 insertions(+), 248 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 f20cf982f126aea968ed6a482551550ffb6650cf From git at git.haskell.org Wed Oct 11 12:58:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 12:58:01 +0000 (UTC) Subject: [commit: ghc] master: Fix #10816 by renaming FixitySigs more consistently (9c3f731) Message-ID: <20171011125801.6D2D33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9c3f73168a6f7f6632b6a3ffd2cfcd774976a7f1/ghc >--------------------------------------------------------------- commit 9c3f73168a6f7f6632b6a3ffd2cfcd774976a7f1 Author: Ryan Scott Date: Wed Oct 11 08:43:37 2017 -0400 Fix #10816 by renaming FixitySigs more consistently Summary: #10816 surfaced because we were renaming top-level fixity declarations with a different code path (`rnSrcFixityDecl`) than the code path for fixity declarations inside of type classes, which is not privy to names that exist in the type namespace. Luckily, the fix is simple: use `rnSrcFixityDecl` in both places. Test Plan: make test TEST=T10816 Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #10816 Differential Revision: https://phabricator.haskell.org/D4077 >--------------------------------------------------------------- 9c3f73168a6f7f6632b6a3ffd2cfcd774976a7f1 compiler/rename/RnBinds.hs | 41 +++++++++++++++++++++--- compiler/rename/RnSource.hs | 42 ++----------------------- testsuite/tests/rename/should_compile/T10816.hs | 11 +++++++ testsuite/tests/rename/should_compile/all.T | 1 + 4 files changed, 50 insertions(+), 45 deletions(-) diff --git a/compiler/rename/RnBinds.hs b/compiler/rename/RnBinds.hs index bf3ee26..02a37b2 100644 --- a/compiler/rename/RnBinds.hs +++ b/compiler/rename/RnBinds.hs @@ -21,7 +21,7 @@ module RnBinds ( -- Other bindings rnMethodBinds, renameSigs, - rnMatchGroup, rnGRHSs, rnGRHS, + rnMatchGroup, rnGRHSs, rnGRHS, rnSrcFixityDecl, makeMiniFixityEnv, MiniFixityEnv, HsSigCtxt(..) ) where @@ -941,7 +941,6 @@ renameSigs ctxt sigs -- Doesn't seem worth much trouble to sort this. renameSig :: HsSigCtxt -> Sig GhcPs -> RnM (Sig GhcRn, FreeVars) --- FixitySig is renamed elsewhere. renameSig _ (IdSig x) = return (IdSig x, emptyFVs) -- Actually this never occurs @@ -988,9 +987,9 @@ renameSig ctxt sig@(InlineSig v s) = do { new_v <- lookupSigOccRn ctxt sig v ; return (InlineSig new_v s, emptyFVs) } -renameSig ctxt sig@(FixSig (FixitySig vs f)) - = do { new_vs <- mapM (lookupSigOccRn ctxt sig) vs - ; return (FixSig (FixitySig new_vs f), emptyFVs) } +renameSig ctxt (FixSig fsig) + = do { new_fsig <- rnSrcFixityDecl ctxt fsig + ; return (FixSig new_fsig, emptyFVs) } renameSig ctxt sig@(MinimalSig s (L l bf)) = do new_bf <- traverse (lookupSigOccRn ctxt sig) bf @@ -1223,6 +1222,38 @@ rnGRHS' ctxt rnBody (GRHS guards rhs) is_standard_guard _ = False {- +********************************************************* +* * + Source-code fixity declarations +* * +********************************************************* +-} + +rnSrcFixityDecl :: HsSigCtxt -> FixitySig GhcPs -> RnM (FixitySig GhcRn) +-- Rename a fixity decl, so we can put +-- the renamed decl in the renamed syntax tree +-- Errors if the thing being fixed is not defined locally. +rnSrcFixityDecl sig_ctxt = rn_decl + where + rn_decl :: FixitySig GhcPs -> RnM (FixitySig GhcRn) + -- GHC extension: look up both the tycon and data con + -- for con-like things; hence returning a list + -- If neither are in scope, report an error; otherwise + -- return a fixity sig for each (slightly odd) + rn_decl (FixitySig fnames fixity) + = do names <- concatMapM lookup_one fnames + return (FixitySig names fixity) + + lookup_one :: Located RdrName -> RnM [Located Name] + lookup_one (L name_loc rdr_name) + = setSrcSpan name_loc $ + -- This lookup will fail if the name is not defined in the + -- same binding group as this fixity declaration. + do names <- lookupLocalTcNames sig_ctxt what rdr_name + return [ L name_loc name | (_, name) <- names ] + what = text "fixity signature" + +{- ************************************************************************ * * \subsection{Error messages} diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index b47686e..b182382 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -177,7 +177,8 @@ rnSrcDecls group@(HsGroup { hs_valds = val_decls, -- Rename fixity declarations and error if we try to -- fix something from another module (duplicates were checked in (A)) let { all_bndrs = tc_bndrs `unionNameSet` val_bndr_set } ; - rn_fix_decls <- rnSrcFixityDecls all_bndrs fix_decls ; + rn_fix_decls <- mapM (mapM (rnSrcFixityDecl (TopSigCtxt all_bndrs))) + fix_decls ; -- Rename deprec decls; -- check for duplicates and ensure that deprecated things are defined locally @@ -266,45 +267,6 @@ rnDocDecl (DocGroup lev doc) = do {- ********************************************************* * * - Source-code fixity declarations -* * -********************************************************* --} - -rnSrcFixityDecls :: NameSet -> [LFixitySig GhcPs] -> RnM [LFixitySig GhcRn] --- Rename the fixity decls, so we can put --- the renamed decls in the renamed syntax tree --- Errors if the thing being fixed is not defined locally. --- --- The returned FixitySigs are not actually used for anything, --- except perhaps the GHCi API -rnSrcFixityDecls bndr_set fix_decls - = do fix_decls <- mapM rn_decl fix_decls - return (concat fix_decls) - where - sig_ctxt = TopSigCtxt bndr_set - - rn_decl :: LFixitySig GhcPs -> RnM [LFixitySig GhcRn] - -- GHC extension: look up both the tycon and data con - -- for con-like things; hence returning a list - -- If neither are in scope, report an error; otherwise - -- return a fixity sig for each (slightly odd) - rn_decl (L loc (FixitySig fnames fixity)) - = do names <- mapM lookup_one fnames - return [ L loc (FixitySig name fixity) - | name <- names ] - - lookup_one :: Located RdrName -> RnM [Located Name] - lookup_one (L name_loc rdr_name) - = setSrcSpan name_loc $ - -- this lookup will fail if the definition isn't local - do names <- lookupLocalTcNames sig_ctxt what rdr_name - return [ L name_loc name | (_, name) <- names ] - what = text "fixity signature" - -{- -********************************************************* -* * Source-code deprecations declarations * * ********************************************************* diff --git a/testsuite/tests/rename/should_compile/T10816.hs b/testsuite/tests/rename/should_compile/T10816.hs new file mode 100644 index 0000000..3f8cc60 --- /dev/null +++ b/testsuite/tests/rename/should_compile/T10816.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TypeOperators, TypeFamilies #-} +module T10816 where + +class C a where + type a # b + infix 4 # + + type a *** b + type a +++ b + infixr 5 ***, +++ + (***), (+++) :: a -> a -> a diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T index 0b46f90..4eb584f 100644 --- a/testsuite/tests/rename/should_compile/all.T +++ b/testsuite/tests/rename/should_compile/all.T @@ -139,6 +139,7 @@ test('T7969', [], run_command, ['$MAKE -s --no-print-directory T7969']) test('T9127', normal, compile, ['']) test('T4426', normal, compile_fail, ['']) test('T9778', normal, compile, ['-fwarn-unticked-promoted-constructors']) +test('T10816', normal, compile, ['']) test('T11164', [], multimod_compile, ['T11164', '-v0']) test('T11167', normal, compile, ['']) test('T11167_ambig', normal, compile, ['']) From git at git.haskell.org Wed Oct 11 14:00:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 14:00:38 +0000 (UTC) Subject: [commit: ghc] master: Pretty-printing of derived multi-parameter classes omits parentheses (6869864) Message-ID: <20171011140038.EC5B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6869864eac211885edcd4b14425fd368069e4aba/ghc >--------------------------------------------------------------- commit 6869864eac211885edcd4b14425fd368069e4aba Author: Alan Zimmerman Date: Sun Oct 1 19:36:03 2017 +0200 Pretty-printing of derived multi-parameter classes omits parentheses Summary: Pretty printing a splice with an HsAppType in the deriving clause, such as $([d| data Foo a = Foo a deriving (C a) |]) would omit the parens. Test Plan: ./validate Reviewers: RyanGlScott, austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14289 Differential Revision: https://phabricator.haskell.org/D4056 >--------------------------------------------------------------- 6869864eac211885edcd4b14425fd368069e4aba compiler/hsSyn/Convert.hs | 30 +++++++++++++++++++++--- compiler/hsSyn/HsDecls.hs | 5 ++-- compiler/hsSyn/HsTypes.hs | 13 ++++++++++- testsuite/tests/printer/Makefile | 12 ++++++++++ testsuite/tests/printer/T14289.hs | 32 ++++++++++++++++++++++++++ testsuite/tests/printer/T14289.stdout | 16 +++++++++++++ testsuite/tests/printer/T14289b.hs | 42 ++++++++++++++++++++++++++++++++++ testsuite/tests/printer/T14289b.stdout | 16 +++++++++++++ testsuite/tests/printer/T14289c.hs | 40 ++++++++++++++++++++++++++++++++ testsuite/tests/printer/T14289c.stdout | 16 +++++++++++++ testsuite/tests/printer/all.T | 3 +++ 11 files changed, 219 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6869864eac211885edcd4b14425fd368069e4aba From git at git.haskell.org Wed Oct 11 14:01:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 14:01:05 +0000 (UTC) Subject: [commit: ghc] master: Avoid creating dependent types in FloatOut (4bb54a4) Message-ID: <20171011140105.325633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4bb54a4522d44a81b2c47233f48252bd73c38279/ghc >--------------------------------------------------------------- commit 4bb54a4522d44a81b2c47233f48252bd73c38279 Author: Simon Peyton Jones Date: Wed Oct 11 14:58:38 2017 +0100 Avoid creating dependent types in FloatOut This bug was exposed by Trac #14270. The problem and its cure is described in SetLevels, Note [Floating and kind casts]. It's simple and will affect very few programs. But the very fact that it was so unexpected is discomforting. >--------------------------------------------------------------- 4bb54a4522d44a81b2c47233f48252bd73c38279 compiler/simplCore/SetLevels.hs | 81 +++++++++++++++++++------- testsuite/tests/polykinds/T14270.hs | 110 ++++++++++++++++++++++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + 3 files changed, 172 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4bb54a4522d44a81b2c47233f48252bd73c38279 From git at git.haskell.org Wed Oct 11 15:41:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Oct 2017 15:41:24 +0000 (UTC) Subject: [commit: ghc] master: Add a missing zonk in TcDerivInfer.simplifyDeriv (13fdca3) Message-ID: <20171011154124.DE89B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/13fdca3d174ff15ac347c5db78370f457a3013ee/ghc >--------------------------------------------------------------- commit 13fdca3d174ff15ac347c5db78370f457a3013ee Author: Simon Peyton Jones Date: Wed Oct 11 16:17:41 2017 +0100 Add a missing zonk in TcDerivInfer.simplifyDeriv I'm astonished that anything worked without this! Fixes Trac #14339 >--------------------------------------------------------------- 13fdca3d174ff15ac347c5db78370f457a3013ee compiler/typecheck/TcDerivInfer.hs | 2 ++ testsuite/tests/deriving/should_compile/T14339.hs | 17 +++++++++++++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 3 files changed, 20 insertions(+) diff --git a/compiler/typecheck/TcDerivInfer.hs b/compiler/typecheck/TcDerivInfer.hs index f598e70..9095977 100644 --- a/compiler/typecheck/TcDerivInfer.hs +++ b/compiler/typecheck/TcDerivInfer.hs @@ -676,6 +676,8 @@ simplifyDeriv pred tvs thetas -- Simplify the constraints ; solved_implics <- runTcSDeriveds $ solveWantedsAndDrop $ unionsWC wanteds + -- It's not yet zonked! Obviously zonk it before peering at it + ; solved_implics <- zonkWC solved_implics -- See [STEP DAC HOIST] -- Split the resulting constraints into bad and good constraints, diff --git a/testsuite/tests/deriving/should_compile/T14339.hs b/testsuite/tests/deriving/should_compile/T14339.hs new file mode 100644 index 0000000..e2521f2 --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T14339.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE UndecidableInstances #-} +module Bug where + +import GHC.TypeLits + +newtype Baz = Baz Foo + deriving Bar + +newtype Foo = Foo Int + +class Bar a where + bar :: a + +instance (TypeError (Text "Boo")) => Bar Foo where + bar = undefined diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 65c6d72..82cee03 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -96,3 +96,4 @@ test('T13919', normal, compile, ['']) test('T13998', normal, compile, ['']) test('T14045b', normal, compile, ['']) test('T14094', normal, compile, ['']) +test('T14339', normal, compile, ['']) From git at git.haskell.org Thu Oct 12 08:27:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Oct 2017 08:27:53 +0000 (UTC) Subject: [commit: ghc] master: Do not quantify over deriving clauses (82b77ec) Message-ID: <20171012082753.125013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/82b77ec375ab74678ac2afecf55dc574fa24490f/ghc >--------------------------------------------------------------- commit 82b77ec375ab74678ac2afecf55dc574fa24490f Author: Simon Peyton Jones Date: Thu Oct 12 09:25:25 2017 +0100 Do not quantify over deriving clauses Trac #14331 showed that in a data type decl like data D = D deriving (C (a :: k)) we were quantifying D over the 'k' in the deriving clause. Yikes. Easily fixed, by deleting code in RnTypes.extractDataDefnKindVars See the discussion on the ticket, esp comment:8. >--------------------------------------------------------------- 82b77ec375ab74678ac2afecf55dc574fa24490f compiler/rename/RnTypes.hs | 22 +++++++++++++--------- testsuite/tests/deriving/should_compile/T14331.hs | 10 ++++++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 3 files changed, 24 insertions(+), 9 deletions(-) diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index dc519b5..dd66cd3 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -1719,14 +1719,23 @@ extractRdrKindSigVars (L _ resultSig) extractDataDefnKindVars :: HsDataDefn GhcPs -> RnM [Located RdrName] -- Get the scoped kind variables mentioned free in the constructor decls --- Eg data T a = T1 (S (a :: k) | forall (b::k). T2 (S b) --- Here k should scope over the whole definition +-- Eg: data T a = T1 (S (a :: k) | forall (b::k). T2 (S b) +-- Here k should scope over the whole definition +-- +-- However, do NOT collect free kind vars from the deriving clauses: +-- Eg: (Trac #14331) class C p q +-- data D = D deriving ( C (a :: k) ) +-- Here k should /not/ scope over the whole definition. We intend +-- this to elaborate to: +-- class C @k1 @k2 (p::k1) (q::k2) +-- data D = D +-- instance forall k (a::k). C @k @* a D where ... +-- extractDataDefnKindVars (HsDataDefn { dd_ctxt = ctxt, dd_kindSig = ksig - , dd_cons = cons, dd_derivs = L _ derivs }) + , dd_cons = cons }) = (nubL . freeKiTyVarsKindVars) <$> (extract_lctxt TypeLevel ctxt =<< extract_mb extract_lkind ksig =<< - extract_sig_tys (concatMap (unLoc . deriv_clause_tys . unLoc) derivs) =<< foldrM (extract_con . unLoc) emptyFKTV cons) where extract_con (ConDeclGADT { }) acc = return acc @@ -1744,11 +1753,6 @@ extract_lctxt :: TypeOrKind -> LHsContext GhcPs -> FreeKiTyVars -> RnM FreeKiTyVars extract_lctxt t_or_k ctxt = extract_ltys t_or_k (unLoc ctxt) -extract_sig_tys :: [LHsSigType GhcPs] -> FreeKiTyVars -> RnM FreeKiTyVars -extract_sig_tys sig_tys acc - = foldrM (\sig_ty acc -> extract_lty TypeLevel (hsSigType sig_ty) acc) - acc sig_tys - extract_ltys :: TypeOrKind -> [LHsType GhcPs] -> FreeKiTyVars -> RnM FreeKiTyVars extract_ltys t_or_k tys acc = foldrM (extract_lty t_or_k) acc tys diff --git a/testsuite/tests/deriving/should_compile/T14331.hs b/testsuite/tests/deriving/should_compile/T14331.hs new file mode 100644 index 0000000..4fe40fa --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T14331.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeInType #-} +module Bug where + +class C p q + +data D = D deriving (C (a :: k)) diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 82cee03..431129f 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -97,3 +97,4 @@ test('T13998', normal, compile, ['']) test('T14045b', normal, compile, ['']) test('T14094', normal, compile, ['']) test('T14339', normal, compile, ['']) +test('T14331', normal, compile, ['']) From git at git.haskell.org Thu Oct 12 11:46:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Oct 2017 11:46:14 +0000 (UTC) Subject: [commit: ghc] master: Add missing T14325.stderr (15aefb4) Message-ID: <20171012114614.3D8EC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/15aefb48d946f01b4bc348c34ac4aa8113de45fa/ghc >--------------------------------------------------------------- commit 15aefb48d946f01b4bc348c34ac4aa8113de45fa Author: Simon Peyton Jones Date: Thu Oct 12 12:45:43 2017 +0100 Add missing T14325.stderr >--------------------------------------------------------------- 15aefb48d946f01b4bc348c34ac4aa8113de45fa testsuite/tests/typecheck/should_fail/T14325.stderr | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T14325.stderr b/testsuite/tests/typecheck/should_fail/T14325.stderr new file mode 100644 index 0000000..1508c4a --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14325.stderr @@ -0,0 +1,9 @@ + +T14325.hs:11:9: error: + • Could not deduce (C b (f b)) arising from a use of ‘foo’ + from the context: C (f b) b + bound by the type signature for: + hm3 :: forall (f :: * -> *) b. C (f b) b => b -> f b + at T14325.hs:10:1-28 + • In the expression: foo x + In an equation for ‘hm3’: hm3 x = foo x From git at git.haskell.org Thu Oct 12 11:53:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Oct 2017 11:53:51 +0000 (UTC) Subject: [commit: ghc] master: Re-apply "Typeable: Allow App to match arrow types" (3de788c) Message-ID: <20171012115351.DFCBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3de788c4eaa0592165bf1fb9e9a6d5b8e2c27554/ghc >--------------------------------------------------------------- commit 3de788c4eaa0592165bf1fb9e9a6d5b8e2c27554 Author: Simon Peyton Jones Date: Thu Oct 5 17:45:20 2017 +0100 Re-apply "Typeable: Allow App to match arrow types" This re-applies commit cc6be3a2f23c9b2e04f9f491099149e1e1d4d20b Author: Ben Gamari Date: Tue Sep 19 18:57:38 2017 -0400 Typeable: Allow App to match arrow types which was reverted because of Trac #14270. Now the latter is fixed we can re-apply it. The original ticket was Trac #14236 >--------------------------------------------------------------- 3de788c4eaa0592165bf1fb9e9a6d5b8e2c27554 libraries/base/Data/Typeable/Internal.hs | 74 ++++++++++++++++++++-- libraries/base/changelog.md | 2 + testsuite/tests/typecheck/should_run/T14236.hs | 14 ++++ testsuite/tests/typecheck/should_run/T14236.stdout | 3 + testsuite/tests/typecheck/should_run/all.T | 1 + 5 files changed, 88 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index d876a2b..24ab515 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -180,11 +180,17 @@ rnfTyCon (TyCon _ _ m n _ k) = rnfModule m `seq` rnfTrName n `seq` rnfKindRep k data TypeRep (a :: k) where TrTyCon :: {-# UNPACK #-} !Fingerprint -> !TyCon -> [SomeTypeRep] -> TypeRep (a :: k) + + -- | Invariant: Saturated arrow types (e.g. things of the form @a -> b@) + -- are represented with @'TrFun' a b@, not @TrApp (TrApp funTyCon a) b at . TrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). {-# UNPACK #-} !Fingerprint -> TypeRep (a :: k1 -> k2) -> TypeRep (b :: k1) -> TypeRep (a b) + + -- | @TrFun fpr a b@ represents a function type @a -> b at . We use this for + -- the sake of efficiency as functions are quite ubiquitous. TrFun :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (a :: TYPE r1) (b :: TYPE r2). {-# UNPACK #-} !Fingerprint @@ -272,6 +278,13 @@ mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep (a :: k1 -> k2) -> TypeRep (b :: k1) -> TypeRep (a b) +mkTrApp rep@(TrApp _ (TrTyCon _ con _) (x :: TypeRep x)) (y :: TypeRep y) + | con == funTyCon -- cheap check first + , Just (IsTYPE (rx :: TypeRep rx)) <- isTYPE (typeRepKind x) + , Just (IsTYPE (ry :: TypeRep ry)) <- isTYPE (typeRepKind y) + , Just HRefl <- withTypeable x $ withTypeable rx $ withTypeable ry + $ typeRep @((->) x :: TYPE ry -> Type) `eqTypeRep` rep + = mkTrFun x y mkTrApp a b = TrApp fpr a b where fpr_a = typeRepFingerprint a @@ -281,17 +294,39 @@ mkTrApp a b = TrApp fpr a b -- | A type application. -- -- For instance, +-- -- @ -- typeRep \@(Maybe Int) === App (typeRep \@Maybe) (typeRep \@Int) -- @ --- Note that this will never match a function type (e.g. @Int -> Char@). +-- +-- Note that this will also match a function type, +-- +-- @ +-- typeRep \@(Int# -> Char) +-- === +-- App (App arrow (typeRep \@Int#)) (typeRep \@Char) +-- @ +-- +-- where @arrow :: TypeRep ((->) :: TYPE IntRep -> Type -> Type)@. -- pattern App :: forall k2 (t :: k2). () => forall k1 (a :: k1 -> k2) (b :: k1). (t ~ a b) => TypeRep a -> TypeRep b -> TypeRep t -pattern App f x <- TrApp _ f x +pattern App f x <- (splitApp -> Just (IsApp f x)) where App f x = mkTrApp f x +data IsApp (a :: k) where + IsApp :: forall k k' (f :: k' -> k) (x :: k'). () + => TypeRep f -> TypeRep x -> IsApp (f x) + +splitApp :: forall k (a :: k). () + => TypeRep a + -> Maybe (IsApp a) +splitApp (TrApp _ f x) = Just (IsApp f x) +splitApp rep@(TrFun _ a b) = Just (IsApp (mkTrApp arr a) b) + where arr = bareArrow rep +splitApp (TrTyCon{}) = Nothing + -- | Use a 'TypeRep' as 'Typeable' evidence. withTypeable :: forall (a :: k) (r :: TYPE rep). () => TypeRep a -> (Typeable a => r) -> r @@ -326,6 +361,7 @@ pattern Con con <- TrTyCon _ con _ pattern Con' :: forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a pattern Con' con ks <- TrTyCon _ con ks +-- TODO: Remove Fun when #14253 is fixed {-# COMPLETE Fun, App, Con #-} {-# COMPLETE Fun, App, Con' #-} @@ -362,7 +398,7 @@ typeRepKind :: TypeRep (a :: k) -> TypeRep k typeRepKind (TrTyCon _ tc args) = unsafeCoerceRep $ tyConKind tc args typeRepKind (TrApp _ f _) - | Fun _ res <- typeRepKind f + | TrFun _ _ res <- typeRepKind f = res | otherwise = error ("Ill-kinded type application: " ++ show (typeRepKind f)) @@ -392,9 +428,9 @@ instantiateKindRep vars = go go (KindRepVar var) = vars A.! var go (KindRepApp f a) - = SomeTypeRep $ App (unsafeCoerceRep $ go f) (unsafeCoerceRep $ go a) + = SomeTypeRep $ mkTrApp (unsafeCoerceRep $ go f) (unsafeCoerceRep $ go a) go (KindRepFun a b) - = SomeTypeRep $ Fun (unsafeCoerceRep $ go a) (unsafeCoerceRep $ go b) + = SomeTypeRep $ mkTrFun (unsafeCoerceRep $ go a) (unsafeCoerceRep $ go b) go (KindRepTYPE r) = unkindedTypeRep $ tYPE `kApp` runtimeRepTypeRep r go (KindRepTypeLitS sort s) = mkTypeLitFromString sort (unpackCStringUtf8# s) @@ -417,7 +453,7 @@ kApp :: SomeKindedTypeRep (k -> k') -> SomeKindedTypeRep k -> SomeKindedTypeRep k' kApp (SomeKindedTypeRep f) (SomeKindedTypeRep a) = - SomeKindedTypeRep (App f a) + SomeKindedTypeRep (mkTrApp f a) kindedTypeRep :: forall (a :: k). Typeable a => SomeKindedTypeRep k kindedTypeRep = SomeKindedTypeRep (typeRep @a) @@ -483,6 +519,32 @@ vecElemTypeRep e = rep :: forall (a :: VecElem). Typeable a => SomeKindedTypeRep VecElem rep = kindedTypeRep @VecElem @a +bareArrow :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) + (a :: TYPE r1) (b :: TYPE r2). () + => TypeRep (a -> b) + -> TypeRep ((->) :: TYPE r1 -> TYPE r2 -> Type) +bareArrow (TrFun _ a b) = + mkTrCon funTyCon [SomeTypeRep rep1, SomeTypeRep rep2] + where + rep1 = getRuntimeRep $ typeRepKind a :: TypeRep r1 + rep2 = getRuntimeRep $ typeRepKind b :: TypeRep r2 +bareArrow _ = error "Data.Typeable.Internal.bareArrow: impossible" + +data IsTYPE (a :: Type) where + IsTYPE :: forall (r :: RuntimeRep). TypeRep r -> IsTYPE (TYPE r) + +-- | Is a type of the form @TYPE rep@? +isTYPE :: TypeRep (a :: Type) -> Maybe (IsTYPE a) +isTYPE (TrApp _ f r) + | Just HRefl <- f `eqTypeRep` typeRep @TYPE + = Just (IsTYPE r) +isTYPE _ = Nothing + +getRuntimeRep :: forall (r :: RuntimeRep). TypeRep (TYPE r) -> TypeRep r +getRuntimeRep (TrApp _ _ r) = r +getRuntimeRep _ = error "Data.Typeable.Internal.getRuntimeRep: impossible" + + ------------------------------------------------------------- -- -- The Typeable class and friends diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 2f42e22..7c521f9 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -50,6 +50,8 @@ * Make `zipWith` and `zipWith3` inlinable (#14224) + * `Type.Reflection.App` now matches on function types (fixes #14236) + * `Type.Reflection.withTypeable` is now polymorphic in the `RuntimeRep` of its result. diff --git a/testsuite/tests/typecheck/should_run/T14236.hs b/testsuite/tests/typecheck/should_run/T14236.hs new file mode 100644 index 0000000..c08682b --- /dev/null +++ b/testsuite/tests/typecheck/should_run/T14236.hs @@ -0,0 +1,14 @@ +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE MagicHash #-} +import GHC.Exts +import Type.Reflection + +main = do + case typeRep @(Int -> Char) of + App a b -> print (a, b) + + case typeRep @(Int# -> Char) of + App a b -> print (a, b) + + case typeRep @(Int# -> Char) of + App a b -> print $ App a (typeRep @String) diff --git a/testsuite/tests/typecheck/should_run/T14236.stdout b/testsuite/tests/typecheck/should_run/T14236.stdout new file mode 100644 index 0000000..a168ea8 --- /dev/null +++ b/testsuite/tests/typecheck/should_run/T14236.stdout @@ -0,0 +1,3 @@ +((->) 'LiftedRep 'LiftedRep Int,Char) +((->) 'IntRep 'LiftedRep Int#,Char) +Int# -> [Char] diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T index 3d1aa36..2907612 100755 --- a/testsuite/tests/typecheck/should_run/all.T +++ b/testsuite/tests/typecheck/should_run/all.T @@ -124,3 +124,4 @@ test('T13435', normal, compile_and_run, ['']) test('T11715', exit_code(1), compile_and_run, ['']) test('T13594a', normal, ghci_script, ['T13594a.script']) test('T14218', normal, compile_and_run, ['']) +test('T14236', normal, compile_and_run, ['']) From git at git.haskell.org Thu Oct 12 11:53:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Oct 2017 11:53:55 +0000 (UTC) Subject: [commit: ghc] master: Do not bind coercion variables in SpecConstr rules (fb050a3) Message-ID: <20171012115355.2A4F73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fb050a330ad202c1eb43038dc18cca2a5be26f4a/ghc >--------------------------------------------------------------- commit fb050a330ad202c1eb43038dc18cca2a5be26f4a Author: Simon Peyton Jones Date: Thu Oct 12 11:00:19 2017 +0100 Do not bind coercion variables in SpecConstr rules Trac #14270 showed that SpecConstr could cause nasty Lint failures if it generates a RULE that binds coercion varables. See * Note [SpecConstr and casts], and * the test simplCore/should_compile/T14270. This doesn't feel like the final word to me, because somehow the specialisation "ought" to work. So I left in a debug WARN to yell if the new check acutally fires. Meanwhile, it stops the erroneous specialisation. binding coercion >--------------------------------------------------------------- fb050a330ad202c1eb43038dc18cca2a5be26f4a compiler/specialise/SpecConstr.hs | 44 +++++++++++++++++++++- .../tests/simplCore/should_compile/T14270a.hs | 27 +++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 3 files changed, 70 insertions(+), 2 deletions(-) diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs index 609e70c..86d7093 100644 --- a/compiler/specialise/SpecConstr.hs +++ b/compiler/specialise/SpecConstr.hs @@ -1883,6 +1883,41 @@ by trim_pats. * Otherwise we sort the patterns to choose the most general ones first; more general => more widely applicable. + +Note [SpecConstr and casts] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider (Trac #14270) a call like + + let f = e + in ... f (K @(a |> co)) ... + +where 'co' is a coercion variable not in scope at f's definition site. +If we aren't caereful we'll get + + let $sf a co = e (K @(a |> co)) + RULE "SC:f" forall a co. f (K @(a |> co)) = $sf a co + f = e + in ... + +But alas, when we match the call we won't bind 'co', because type-matching +(for good reasons) discards casts). + +I don't know how to solve this, so for now I'm just discarding any +call patterns that + * Mentions a coercion variable + * That is not in scope at the binding of the function + +I think this is very rare. + +Note that this /also/ discards the call pattern if we have a cast in a +/term/, although in fact Rules.match does make a very flaky and +fragile attempt to match coercions. e.g. a call like + f (Maybe Age) (Nothing |> co) blah + where co :: Maybe Int ~ Maybe Age +will be discarded. It's extremely fragile to match on the form of a +coercion, so I think it's better just not to try. A more complicated +alternative would be to discard calls that mention coercion variables +only in kind-casts, but I'm doing the simple thing for now. -} type CallPat = ([Var], [CoreExpr]) -- Quantified variables and arguments @@ -1985,7 +2020,7 @@ callToPats :: ScEnv -> [ArgOcc] -> Call -> UniqSM (Maybe CallPat) -- Type variables come first, since they may scope -- over the following term variables -- The [CoreExpr] are the argument patterns for the rule -callToPats env bndr_occs (Call _ args con_env) +callToPats env bndr_occs call@(Call _ args con_env) | args `ltLength` bndr_occs -- Check saturated = return Nothing | otherwise @@ -2014,8 +2049,13 @@ callToPats env bndr_occs (Call _ args con_env) sanitise id = id `setIdType` expandTypeSynonyms (idType id) -- See Note [Free type variables of the qvar types] + bad_covars = filter isCoVar ids + -- See Note [SpecConstr and casts] + ; -- pprTrace "callToPats" (ppr args $$ ppr bndr_occs) $ - if interesting + WARN( not (null bad_covars), text "SpecConstr: bad covars:" <+> ppr bad_covars + $$ ppr call ) + if interesting && null bad_covars then return (Just (qvars', pats)) else return Nothing } diff --git a/testsuite/tests/simplCore/should_compile/T14270a.hs b/testsuite/tests/simplCore/should_compile/T14270a.hs new file mode 100644 index 0000000..840b1e8 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T14270a.hs @@ -0,0 +1,27 @@ +{-# LANGUAGE TypeApplications, ScopedTypeVariables, GADTs, RankNTypes, TypeInType, KindSignatures #-} +{-# OPTIONS_GHC -O2 #-} -- We are provoking a bug in SpecConstr + +module T14270a where + +import Data.Kind +import Data.Proxy + +data T a = T1 (T a) | T2 + +data K (a :: k) where + K1 :: K (a :: Type) + K2 :: K a + +f :: T (a :: Type) -> Bool +f (T1 x) = f x +f T2 = True + +g :: forall (a :: k). K a -> T a -> Bool +g kv x = case kv of + K1 -> f @a T2 -- f @a (T1 x) gives a different crash + k2 -> True + +-- The point here is that the call to f looks like +-- f @(a |> co) (T2 @(a |> co)) +-- where 'co' is bound by the pattern match on K1 +-- See Note [SpecConstr and casts] in SpecConstr diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 7f21331..28e26ed 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -281,3 +281,4 @@ test('T14140', ['$MAKE -s --no-print-directory T14140']) test('T14272', normal, compile, ['']) +test('T14270a', normal, compile, ['']) From git at git.haskell.org Fri Oct 13 13:13:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 13 Oct 2017 13:13:59 +0000 (UTC) Subject: [commit: ghc] master: Delete obsolete docs on GADT interacton with TypeApplications (2be55b8) Message-ID: <20171013131359.4BFAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2be55b85b4c7479639b01c3b8f47c1e49ddbcb0a/ghc >--------------------------------------------------------------- commit 2be55b85b4c7479639b01c3b8f47c1e49ddbcb0a Author: Ryan Scott Date: Fri Oct 13 09:10:21 2017 -0400 Delete obsolete docs on GADT interacton with TypeApplications Even since ef26182e2014b0a2a029ae466a4b121bf235e4e4, this section of the users' guide is wrong, as there are no longer special rules for the order of type variables in GADT constructors' type signatures vis-à-vis visible type application. As a result, this section can simply be deleted, as there is no longer anything interesting to say about the topic. >--------------------------------------------------------------- 2be55b85b4c7479639b01c3b8f47c1e49ddbcb0a docs/users_guide/glasgow_exts.rst | 16 ---------------- 1 file changed, 16 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 9402885..9e16ebd 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -10125,22 +10125,6 @@ Here are the details: if you want the most accurate information with respect to visible type application properties. -- Data constructors declared with GADT syntax follow different rules - for the time being; it is expected that these will be brought in line - with other declarations in the future. The rules for GADT - data constructors are as follows: - - * All kind and type variables are considered specified and available for - visible type application. - - * Universal variables always come first, in precisely the order they - appear in the type declaration. Universal variables that are - constrained by a GADT return type are not included in the data constructor. - - * Existential variables come next. Their order is determined by a user- - written `forall`; or, if there is none, by taking the left-to-right order - in the data constructor's type and doing a stable topological sort. - .. _implicit-parameters: Implicit parameters From git at git.haskell.org Sat Oct 14 17:52:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Oct 2017 17:52:09 +0000 (UTC) Subject: [commit: ghc] branch 'wip/ttg-2017-10-13' created Message-ID: <20171014175209.4A9823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/ttg-2017-10-13 Referencing: 232456523fdc09bac7887e46c80c9b4016a983a2 From git at git.haskell.org Sat Oct 14 17:52:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Oct 2017 17:52:12 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: WIP on Doing a combined Step 1 and 3 for Trees That Grow (2324565) Message-ID: <20171014175212.16D403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/232456523fdc09bac7887e46c80c9b4016a983a2/ghc >--------------------------------------------------------------- commit 232456523fdc09bac7887e46c80c9b4016a983a2 Author: Alan Zimmerman Date: Sat Oct 14 16:00:35 2017 +0200 WIP on Doing a combined Step 1 and 3 for Trees That Grow >--------------------------------------------------------------- 232456523fdc09bac7887e46c80c9b4016a983a2 compiler/hsSyn/HsBinds.hs | 70 +++++++++++++++---- compiler/hsSyn/HsExpr.hs | 95 ++++++++++++++++++++++++++ compiler/hsSyn/HsExtension.hs | 153 ++++++++++++++++++++++++++++++++++++++++-- compiler/hsSyn/HsPat.hs | 56 +++++++++++++++- 4 files changed, 355 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 232456523fdc09bac7887e46c80c9b4016a983a2 From git at git.haskell.org Sun Oct 15 09:51:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Oct 2017 09:51:10 +0000 (UTC) Subject: [commit: ghc] master: Remove section about ApplicativeDo & existentials (#13875) (4a677f7) Message-ID: <20171015095110.1CE543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4a677f76155f94086dd645a41a889d362da04e77/ghc >--------------------------------------------------------------- commit 4a677f76155f94086dd645a41a889d362da04e77 Author: Simon Marlow Date: Thu Oct 12 08:39:15 2017 +0100 Remove section about ApplicativeDo & existentials (#13875) Summary: This section is irrelevant now that strict pattern matches don't get the ApplicativeDo treatment. Test Plan: ``` make html FAST=YES ``` Reviewers: bgamari, austin, erikd Subscribers: rwbarton, thomie GHC Trac Issues: #13875 Differential Revision: https://phabricator.haskell.org/D4087 >--------------------------------------------------------------- 4a677f76155f94086dd645a41a889d362da04e77 docs/users_guide/glasgow_exts.rst | 40 --------------------------------------- 1 file changed, 40 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 9e16ebd..453a70e 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -1074,46 +1074,6 @@ will always be connected with ``>>=``, to retain the same strictness semantics as the standard do-notation. If you don't want this, simply put a ``~`` on the pattern match to make it lazy. -.. _applicative-do-existential: - -Existential patterns and GADTs -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - -When the pattern in a statement matches a constructor with -existential type variables and/or constraints, the transformation that -``ApplicativeDo`` performs may mean that the pattern does not scope -over the statements that follow it. This is because the rearrangement -happens before the expression is typechecked. For example, this -program does not typecheck:: - - {-# LANGUAGE RankNTypes, GADTs, ApplicativeDo #-} - - data T where A :: forall a . Eq a => a -> T - - test = do - A x <- undefined - _ <- return 'a' - _ <- return 'b' - return (x == x) - -The reason is that the ``Eq`` constraint that would be brought into -scope from the pattern match ``A x`` is not available when -typechecking the expression ``x == x``, because ``ApplicativeDo`` has -rearranged the expression to look like this:: - - test = - (\x _ -> x == x) - <$> do A x <- undefined; _ <- return 'a'; return x - <*> return 'b' - -(Note that the ``return 'a'`` and ``return 'b'`` statements are needed -to make ``ApplicativeDo`` apply despite the restriction noted in -:ref:`applicative-do-strict`, because ``A x`` is a strict pattern match.) - -Turning off ``ApplicativeDo`` lets the program typecheck. This is -something to bear in mind when using ``ApplicativeDo`` in combination -with :ref:`existential-quantification` or :ref:`gadt`. - .. _applicative-do-pitfall: Things to watch out for From git at git.haskell.org Sun Oct 15 12:10:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Oct 2017 12:10:01 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: ValBinds worked through, compiles and expected tests pass (a3d5e68) Message-ID: <20171015121001.AAEF83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/a3d5e6881d9df0166ce17bb4b404b5ee09acb437/ghc >--------------------------------------------------------------- commit a3d5e6881d9df0166ce17bb4b404b5ee09acb437 Author: Alan Zimmerman Date: Sun Oct 15 14:09:17 2017 +0200 ValBinds worked through, compiles and expected tests pass >--------------------------------------------------------------- a3d5e6881d9df0166ce17bb4b404b5ee09acb437 compiler/deSugar/DsMeta.hs | 6 +++--- compiler/hsSyn/Convert.hs | 2 +- compiler/hsSyn/HsBinds.hs | 43 +++++++++++++++++++++++++++++----------- compiler/hsSyn/HsDecls.hs | 2 +- compiler/hsSyn/HsExpr.hs | 35 ++++++++++++++++---------------- compiler/hsSyn/HsExpr.hs-boot | 12 +++++------ compiler/hsSyn/HsExtension.hs | 22 +++++++++++--------- compiler/hsSyn/HsLit.hs | 2 +- compiler/hsSyn/HsTypes.hs | 10 +++++----- compiler/hsSyn/HsUtils.hs | 8 ++++---- compiler/main/InteractiveEval.hs | 3 ++- compiler/parser/RdrHsSyn.hs | 2 +- compiler/rename/RnBinds.hs | 10 +++++----- compiler/rename/RnExpr.hs | 2 +- compiler/rename/RnNames.hs | 2 +- compiler/rename/RnSource.hs | 10 +++++----- compiler/typecheck/TcDeriv.hs | 2 +- 17 files changed, 98 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 a3d5e6881d9df0166ce17bb4b404b5ee09acb437 From git at git.haskell.org Sun Oct 15 20:14:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Oct 2017 20:14:47 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: More HsPats worked in (500cbe2) Message-ID: <20171015201447.BC9FF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/500cbe2923292418173ac21113cbf699fec67255/ghc >--------------------------------------------------------------- commit 500cbe2923292418173ac21113cbf699fec67255 Author: Alan Zimmerman Date: Sun Oct 15 22:13:55 2017 +0200 More HsPats worked in But not (yet) as replacements for PostTc / PostRn types >--------------------------------------------------------------- 500cbe2923292418173ac21113cbf699fec67255 compiler/deSugar/Check.hs | 24 ++--- compiler/deSugar/DsArrows.hs | 20 ++-- compiler/deSugar/DsExpr.hs | 2 +- compiler/deSugar/DsMeta.hs | 26 +++-- compiler/deSugar/DsUtils.hs | 61 +++++------ compiler/deSugar/Match.hs | 45 +++++---- compiler/hsSyn/Convert.hs | 33 +++--- compiler/hsSyn/HsExtension.hs | 69 ++++--------- compiler/hsSyn/HsPat.hs | 201 +++++++++++++++++++++++-------------- compiler/hsSyn/HsUtils.hs | 74 +++++++------- compiler/hsSyn/PlaceHolder.hs | 5 + compiler/main/HscStats.hs | 2 +- compiler/parser/RdrHsSyn.hs | 18 ++-- compiler/rename/RnExpr.hs | 34 +++---- compiler/rename/RnPat.hs | 46 +++++---- compiler/rename/RnSplice.hs | 2 +- compiler/typecheck/TcGenDeriv.hs | 2 +- compiler/typecheck/TcGenFunctor.hs | 1 + compiler/typecheck/TcHsSyn.hs | 78 +++++++------- compiler/typecheck/TcPat.hs | 45 +++++---- compiler/typecheck/TcPatSyn.hs | 68 ++++++------- compiler/typecheck/TcRnDriver.hs | 12 ++- compiler/typecheck/TcTyDecls.hs | 3 +- ghc/GHCi/UI/Info.hs | 4 +- utils/ghctags/Main.hs | 16 +-- 25 files changed, 470 insertions(+), 421 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 500cbe2923292418173ac21113cbf699fec67255 From git at git.haskell.org Mon Oct 16 08:24:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 08:24:04 +0000 (UTC) Subject: [commit: ghc] master: Fix calculation in threadStackOverflow (8adb84f) Message-ID: <20171016082404.CFA0D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8adb84fe190260cdd4bc12a40962e894f1f9ed18/ghc >--------------------------------------------------------------- commit 8adb84fe190260cdd4bc12a40962e894f1f9ed18 Author: Simon Marlow Date: Sat Sep 30 13:11:07 2017 -0500 Fix calculation in threadStackOverflow Summary: The calculation was too conservative, and could result in copying zero frames into the new stack chunk, which caused a knock-on failure in the interpreter. Test Plan: Tested on an in-house repro (not shareable, unfortunately) Reviewers: niteria, bgamari, austin, erikd Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4052 >--------------------------------------------------------------- 8adb84fe190260cdd4bc12a40962e894f1f9ed18 rts/Threads.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/Threads.c b/rts/Threads.c index 836cdd6..79c86f7 100644 --- a/rts/Threads.c +++ b/rts/Threads.c @@ -640,8 +640,8 @@ threadStackOverflow (Capability *cap, StgTSO *tso) // if including this frame would exceed the size of the // new stack (taking into account the underflow frame), // then stop at the previous frame. - if (sp + size > old_stack->stack + (new_stack->stack_size - - sizeofW(StgUnderflowFrame))) { + if (sp + size > old_stack->sp + (new_stack->stack_size - + sizeofW(StgUnderflowFrame))) { break; } sp += size; From git at git.haskell.org Mon Oct 16 09:18:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 09:18:39 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Get rid of PostTc type in TuplePat (345366e) Message-ID: <20171016091839.85E233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/345366ea8d6435fcc993b1fb8fbf7b6a1060ea15/ghc >--------------------------------------------------------------- commit 345366ea8d6435fcc993b1fb8fbf7b6a1060ea15 Author: Alan Zimmerman Date: Sun Oct 15 23:34:42 2017 +0200 Get rid of PostTc type in TuplePat >--------------------------------------------------------------- 345366ea8d6435fcc993b1fb8fbf7b6a1060ea15 compiler/deSugar/Check.hs | 2 +- compiler/deSugar/DsArrows.hs | 2 +- compiler/deSugar/DsMeta.hs | 2 +- compiler/deSugar/DsUtils.hs | 8 ++--- compiler/deSugar/Match.hs | 2 +- compiler/hsSyn/Convert.hs | 4 +-- compiler/hsSyn/HsPat.hs | 82 +++++++++++++++++++++--------------------- compiler/hsSyn/HsUtils.hs | 24 ++++++------- compiler/hsSyn/PlaceHolder.hs | 14 +++++--- compiler/parser/RdrHsSyn.hs | 2 +- compiler/rename/RnPat.hs | 4 +-- compiler/typecheck/TcHsSyn.hs | 6 ++-- compiler/typecheck/TcPat.hs | 4 +-- compiler/typecheck/TcPatSyn.hs | 6 ++-- utils/ghctags/Main.hs | 2 +- 15 files changed, 84 insertions(+), 80 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 345366ea8d6435fcc993b1fb8fbf7b6a1060ea15 From git at git.haskell.org Mon Oct 16 09:18:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 09:18:42 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Fully work TTG into ListPat (0593bcc) Message-ID: <20171016091842.6CD463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/0593bccece43d5fec2d260716cfa0f9fcaf943af/ghc >--------------------------------------------------------------- commit 0593bccece43d5fec2d260716cfa0f9fcaf943af Author: Alan Zimmerman Date: Mon Oct 16 11:17:46 2017 +0200 Fully work TTG into ListPat There are now specific variants for each compiler pass >--------------------------------------------------------------- 0593bccece43d5fec2d260716cfa0f9fcaf943af compiler/deSugar/Check.hs | 6 +++--- compiler/deSugar/DsArrows.hs | 2 +- compiler/deSugar/DsMeta.hs | 8 ++++---- compiler/deSugar/Match.hs | 9 +++++---- compiler/hsSyn/Convert.hs | 3 +-- compiler/hsSyn/HsPat.hs | 24 +++++++++++++++--------- compiler/hsSyn/HsUtils.hs | 18 +++++++++--------- compiler/parser/RdrHsSyn.hs | 2 +- compiler/rename/RnPat.hs | 10 ++++------ compiler/typecheck/TcHsSyn.hs | 12 ++++++------ compiler/typecheck/TcPat.hs | 9 +++++---- compiler/typecheck/TcPatSyn.hs | 30 +++++++++++++++--------------- utils/ghctags/Main.hs | 2 +- 13 files changed, 70 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0593bccece43d5fec2d260716cfa0f9fcaf943af From git at git.haskell.org Mon Oct 16 11:42:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 11:42:50 +0000 (UTC) Subject: [commit: ghc] master: Fix typo (6aa6a86) Message-ID: <20171016114250.8AE943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6aa6a86b836efaabcb471894d0b549a2e56703e6/ghc >--------------------------------------------------------------- commit 6aa6a86b836efaabcb471894d0b549a2e56703e6 Author: Peter Trommler Date: Sun Oct 15 13:29:57 2017 +0200 Fix typo >--------------------------------------------------------------- 6aa6a86b836efaabcb471894d0b549a2e56703e6 compiler/typecheck/TcGenDeriv.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index bd9902e..9e27ad5 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -126,7 +126,7 @@ possibly zero of them). Here's an example, with both \tr{N}ullary and case (a1 `eqFloat#` a2) of r -> r for that particular test. -* If there are a lot of (more than en) nullary constructors, we emit a +* If there are a lot of (more than ten) nullary constructors, we emit a catch-all clause of the form: (==) a b = case (con2tag_Foo a) of { a# -> From git at git.haskell.org Mon Oct 16 11:42:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 11:42:53 +0000 (UTC) Subject: [commit: ghc] master: Fix typo (afac6b1) Message-ID: <20171016114253.495213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/afac6b1107e63cab8833b66fc5853d4e00635098/ghc >--------------------------------------------------------------- commit afac6b1107e63cab8833b66fc5853d4e00635098 Author: Peter Trommler Date: Sun Oct 15 11:34:10 2017 +0200 Fix typo >--------------------------------------------------------------- afac6b1107e63cab8833b66fc5853d4e00635098 compiler/prelude/PrelNames.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index a36f77b..760aea5 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -24,7 +24,7 @@ Nota Bene: all Names defined in here should come from the base package One of these Names contains (a) the module and occurrence name of the thing (b) its Unique - The may way the compiler "knows about" one of these things is + The way the compiler "knows about" one of these things is where the type checker or desugarer needs to look it up. For example, when desugaring list comprehensions the desugarer needs to conjure up 'foldr'. It does this by looking up From git at git.haskell.org Mon Oct 16 17:04:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 17:04:00 +0000 (UTC) Subject: [commit: ghc] master: Fix panic for `ByteArray#` arguments in CApiFFI foreign imports (add85cc) Message-ID: <20171016170400.7F3913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/add85cc2a3ec0bda810dca2a35264308ffaab069/ghc >--------------------------------------------------------------- commit add85cc2a3ec0bda810dca2a35264308ffaab069 Author: Herbert Valerio Riedel Date: Mon Oct 16 19:02:01 2017 +0200 Fix panic for `ByteArray#` arguments in CApiFFI foreign imports Declarations such as foreign import capi unsafe "string.h strlen" c_strlen_capi :: ByteArray# -> IO CSize foreign import capi unsafe "string.h memset" c_memset_capi :: MutableByteArray# s -> CInt -> CSize -> IO () would cause GHC to panic because the CApiFFI c-wrapper generator didn't know what C type to use for `(Mutable)ByteArray#` types (unlike the `ccall` codepath). This addresses #9274 Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4092 >--------------------------------------------------------------- add85cc2a3ec0bda810dca2a35264308ffaab069 compiler/deSugar/DsForeign.hs | 6 ++++++ testsuite/tests/ffi/should_run/T9274.hs | 24 ++++++++++++++++++++++ .../tests/ffi/should_run/T9274.stdout | 0 testsuite/tests/ffi/should_run/all.T | 2 ++ 4 files changed, 32 insertions(+) diff --git a/compiler/deSugar/DsForeign.hs b/compiler/deSugar/DsForeign.hs index 01173c9..492d353 100644 --- a/compiler/deSugar/DsForeign.hs +++ b/compiler/deSugar/DsForeign.hs @@ -717,6 +717,12 @@ toCType = f False -- through one layer of type synonym etc. | Just t' <- coreView t = f voidOK t' + -- This may be an 'UnliftedFFITypes'-style ByteArray# argument + -- (which is marshalled like a Ptr) + | Just byteArrayPrimTyCon == tyConAppTyConPicky_maybe t + = (Nothing, text "const void*") + | Just mutableByteArrayPrimTyCon == tyConAppTyConPicky_maybe t + = (Nothing, text "void*") -- Otherwise we don't know the C type. If we are allowing -- void then return that; otherwise something has gone wrong. | voidOK = (Nothing, text "void") diff --git a/testsuite/tests/ffi/should_run/T9274.hs b/testsuite/tests/ffi/should_run/T9274.hs new file mode 100644 index 0000000..814deff --- /dev/null +++ b/testsuite/tests/ffi/should_run/T9274.hs @@ -0,0 +1,24 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CApiFFI #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE UnliftedFFITypes #-} + +module Main where + +import qualified Data.ByteString.Short.Internal as SBS +import Foreign.C.Types +import GHC.Exts + +foreign import capi unsafe "string.h strlen" + c_strlen_capi :: ByteArray# -> IO CSize + +foreign import capi unsafe "string.h memset" + c_memset_capi :: MutableByteArray# s -> CInt -> CSize -> IO () + +main :: IO () +main = do + n <- c_strlen_capi ba# + print (n == 13) + where + !(SBS.SBS ba#) = "Hello FFI!!!!\NUL" diff --git a/libraries/base/tests/IO/IOError002.stdout b/testsuite/tests/ffi/should_run/T9274.stdout similarity index 100% copy from libraries/base/tests/IO/IOError002.stdout copy to testsuite/tests/ffi/should_run/T9274.stdout diff --git a/testsuite/tests/ffi/should_run/all.T b/testsuite/tests/ffi/should_run/all.T index 1bb58c5..fd0af7e 100644 --- a/testsuite/tests/ffi/should_run/all.T +++ b/testsuite/tests/ffi/should_run/all.T @@ -174,6 +174,8 @@ test('T4012', [expect_broken_for(7388, ['ghci'])], multimod_compile_and_run, test('T8083', [omit_ways(['ghci'])], compile_and_run, ['T8083_c.c']) +test('T9274', [omit_ways(['ghci'])], compile_and_run, ['']) + test('ffi023', [ omit_ways(['ghci']), extra_clean(['ffi023_c.o']), extra_run_opts('1000 4'), From git at git.haskell.org Mon Oct 16 19:09:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 19:09:34 +0000 (UTC) Subject: [commit: ghc] master: Implement new `compareByteArrays#` primop (e3ba26f) Message-ID: <20171016190934.246D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e3ba26f8b49700b41ff4672f3f7f6a4e453acdcc/ghc >--------------------------------------------------------------- commit e3ba26f8b49700b41ff4672f3f7f6a4e453acdcc Author: Herbert Valerio Riedel Date: Mon Oct 16 21:01:57 2017 +0200 Implement new `compareByteArrays#` primop The new primop compareByteArrays# :: ByteArray# -> Int# {- offset -} -> ByteArray# -> Int# {- offset -} -> Int# {- length -} -> Int# allows to compare the subrange of the first `ByteArray#` to the (same-length) subrange of the second `ByteArray#` and returns a value less than, equal to, or greater than zero if the range is found, respectively, to be byte-wise lexicographically less than, to match, or be greater than the second range. Under the hood, the new primop is implemented in terms of the standard ISO C `memcmp(3)` function. It is currently an out-of-line primop but work is underway to optimise this into an inline primop for a future follow-up Differential (see D4091). This primop has applications in packages like `text`, `text-short`, `bytestring`, `text-containers`, `primitive`, etc. which currently have to incur the overhead of an ordinary FFI call to directly or indirectly invoke `memcmp(3)` as well has having to deal with some `unsafePerformIO`-variant. While at it, this also improves the documentation for the existing `copyByteArray#` primitive which has a non-trivial type-signature that significantly benefits from a more explicit description of its arguments. Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4090 >--------------------------------------------------------------- e3ba26f8b49700b41ff4672f3f7f6a4e453acdcc compiler/prelude/primops.txt.pp | 25 ++- includes/stg/MiscClosures.h | 1 + rts/PrimOps.cmm | 14 ++ rts/RtsSymbols.c | 1 + testsuite/tests/codeGen/should_run/all.T | 1 + .../tests/codeGen/should_run/compareByteArrays.hs | 167 +++++++++++++++++++++ .../codeGen/should_run/compareByteArrays.stdout | 12 ++ 7 files changed, 218 insertions(+), 3 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e3ba26f8b49700b41ff4672f3f7f6a4e453acdcc From git at git.haskell.org Mon Oct 16 20:19:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 20:19:39 +0000 (UTC) Subject: [commit: ghc] master: Override default `clearBit` method impl for `Natural` (5984a69) Message-ID: <20171016201939.30B013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5984a698fc2974b719365a9647a7cae1bed51eec/ghc >--------------------------------------------------------------- commit 5984a698fc2974b719365a9647a7cae1bed51eec Author: Herbert Valerio Riedel Date: Mon Oct 16 22:12:03 2017 +0200 Override default `clearBit` method impl for `Natural` The default implementation of `clearBit` is in terms of `complement`. However, `complement` is not well-defined for `Natural` and this consequently renders the default implementation of `clearBit` dysfunctional. This implements `clearBit` in terms of `testBit` and `setBit` which are both well-defined for `Natural`s. This addresses #13203 >--------------------------------------------------------------- 5984a698fc2974b719365a9647a7cae1bed51eec libraries/base/GHC/Natural.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index 99cfb8f..edffb10 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -345,6 +345,11 @@ instance Bits Natural where -- TODO: setBit, clearBit, complementBit (needs more primitives) + -- NB: We cannot use the default impl of 'clearBit' due to + -- 'complement' not being well-defined for 'Natural' (c.f. #13203) + clearBit x i | testBit x i = complementBit x i + | otherwise = x + shiftL n 0 = n shiftL (NatS# 0##) _ = NatS# 0## shiftL (NatS# 1##) i = bit i From git at git.haskell.org Mon Oct 16 20:26:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 20:26:28 +0000 (UTC) Subject: [commit: ghc] master: Enable testing 'Natural' type in TEST=arith011 (843772b) Message-ID: <20171016202628.A9BB83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/843772b86b62df686a9e57648fa9d3ed06b13973/ghc >--------------------------------------------------------------- commit 843772b86b62df686a9e57648fa9d3ed06b13973 Author: Herbert Valerio Riedel Date: Sat Oct 14 20:37:47 2017 +0200 Enable testing 'Natural' type in TEST=arith011 This now passes thanks to 5984a698fc2974b719365a9647a7cae1bed51eec (re #13203) >--------------------------------------------------------------- 843772b86b62df686a9e57648fa9d3ed06b13973 testsuite/tests/numeric/should_run/arith011.hs | 33 +- testsuite/tests/numeric/should_run/arith011.stdout | 656 +++++++++++++++++++++ .../tests/numeric/should_run/arith011.stdout-ws-64 | 656 +++++++++++++++++++++ 3 files changed, 1341 insertions(+), 4 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 843772b86b62df686a9e57648fa9d3ed06b13973 From git at git.haskell.org Mon Oct 16 20:31:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 20:31:53 +0000 (UTC) Subject: [commit: ghc] master: Implement {set, clear, complement}BitBigNat primitives (6cc232a) Message-ID: <20171016203153.4612A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6cc232ae925bc6fc88229d96589a851068a9cace/ghc >--------------------------------------------------------------- commit 6cc232ae925bc6fc88229d96589a851068a9cace Author: Herbert Valerio Riedel Date: Sat Oct 14 09:38:01 2017 +0200 Implement {set,clear,complement}BitBigNat primitives This implements the missing `{set,clear,complement}BitBigNat` primitives and hooks them up to `Natural`'s `Bits` instance. This doesn't yet benefit `Integer`, as we still need "negative" `BigNat` variants of those primitives. Addresses #7860 (partly) Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D3415 >--------------------------------------------------------------- 6cc232ae925bc6fc88229d96589a851068a9cace libraries/base/GHC/Natural.hs | 20 +++-- .../integer-gmp/src/GHC/Integer/GMP/Internals.hs | 3 + libraries/integer-gmp/src/GHC/Integer/Type.hs | 88 ++++++++++++++++++++-- 3 files changed, 97 insertions(+), 14 deletions(-) diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index edffb10..7e6d0a1 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -343,12 +343,20 @@ instance Bits Natural where testBit (NatS# w) i = testBit (W# w) i testBit (NatJ# bn) (I# i#) = testBitBigNat bn i# - -- TODO: setBit, clearBit, complementBit (needs more primitives) - - -- NB: We cannot use the default impl of 'clearBit' due to - -- 'complement' not being well-defined for 'Natural' (c.f. #13203) - clearBit x i | testBit x i = complementBit x i - | otherwise = x + clearBit n@(NatS# w#) i + | i < finiteBitSize (0::Word) = let !(W# w2#) = clearBit (W# w#) i in NatS# w2# + | otherwise = n + clearBit (NatJ# bn) (I# i#) = bigNatToNatural (clearBitBigNat bn i#) + + setBit (NatS# w#) i@(I# i#) + | i < finiteBitSize (0::Word) = let !(W# w2#) = setBit (W# w#) i in NatS# w2# + | otherwise = bigNatToNatural (setBitBigNat (wordToBigNat w#) i#) + setBit (NatJ# bn) (I# i#) = bigNatToNatural (setBitBigNat bn i#) + + complementBit (NatS# w#) i@(I# i#) + | i < finiteBitSize (0::Word) = let !(W# w2#) = complementBit (W# w#) i in NatS# w2# + | otherwise = bigNatToNatural (setBitBigNat (wordToBigNat w#) i#) + complementBit (NatJ# bn) (I# i#) = bigNatToNatural (complementBitBigNat bn i#) shiftL n 0 = n shiftL (NatS# 0##) _ = NatS# 0## diff --git a/libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs b/libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs index fcf4da5..6c7fccf 100644 --- a/libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs +++ b/libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs @@ -107,6 +107,9 @@ module GHC.Integer.GMP.Internals , shiftRBigNat , shiftLBigNat , testBitBigNat + , clearBitBigNat + , complementBitBigNat + , setBitBigNat , andBigNat , xorBigNat , popCountBigNat diff --git a/libraries/integer-gmp/src/GHC/Integer/Type.hs b/libraries/integer-gmp/src/GHC/Integer/Type.hs index 5815950..5dcbdce 100644 --- a/libraries/integer-gmp/src/GHC/Integer/Type.hs +++ b/libraries/integer-gmp/src/GHC/Integer/Type.hs @@ -1060,7 +1060,7 @@ bitBigNat i# mbn@(MBN# mba#) <- newBigNat# (li# +# 1#) -- FIXME: do we really need to zero-init MBAs returned by 'newByteArray#'? -- clear all limbs (except for the most-significant limb) - _ <- svoid (setByteArray# mba# 0# (li# `uncheckedIShiftL#` GMP_LIMB_SHIFT#) 0#) + _ <- svoid (clearWordArray# mba# 0# li#) -- set single bit in most-significant limb _ <- svoid (writeBigNat# mbn li# (uncheckedShiftL# 1## bi#)) unsafeFreezeBigNat# mbn @@ -1091,6 +1091,67 @@ testBitNegBigNat bn i# allZ j | isTrue# (indexBigNat# bn (j -# 1#) `eqWord#` 0##) = allZ (j -# 1#) | True = False + +clearBitBigNat :: BigNat -> Int# -> BigNat +clearBitBigNat bn i# + | not (inline testBitBigNat bn i#) = bn + | isTrue# (nx# ==# 1#) = wordToBigNat (bigNatToWord bn `xor#` bitWord# bi#) + | isTrue# (li# +# 1# ==# nx#) = -- special case, operating on most-sig limb + case indexBigNat# bn li# `xor#` bitWord# bi# of + 0## -> do -- most-sig limb became zero -> result has less limbs + case fmssl bn (li# -# 1#) of + 0# -> zeroBigNat + n# -> runS $ do + mbn <- newBigNat# n# + _ <- copyWordArray bn 0# mbn 0# n# + unsafeFreezeBigNat# mbn + newlimb# -> runS $ do -- no shrinking + mbn <- newBigNat# nx# + _ <- copyWordArray bn 0# mbn 0# li# + _ <- svoid (writeBigNat# mbn li# newlimb#) + unsafeFreezeBigNat# mbn + + | True = runS $ do + mbn <- newBigNat# nx# + _ <- copyWordArray bn 0# mbn 0# nx# + let newlimb# = indexBigNat# bn li# `xor#` bitWord# bi# + _ <- svoid (writeBigNat# mbn li# newlimb#) + unsafeFreezeBigNat# mbn + + where + !(# li#, bi# #) = quotRemInt# i# GMP_LIMB_BITS# + nx# = sizeofBigNat# bn + + + +setBitBigNat :: BigNat -> Int# -> BigNat +setBitBigNat bn i# + | inline testBitBigNat bn i# = bn + | isTrue# (d# ># 0#) = runS $ do -- result BigNat will have more limbs + mbn@(MBN# mba#) <- newBigNat# (li# +# 1#) + _ <- copyWordArray bn 0# mbn 0# nx# + _ <- svoid (clearWordArray# mba# nx# (d# -# 1#)) + _ <- svoid (writeBigNat# mbn li# (bitWord# bi#)) + unsafeFreezeBigNat# mbn + + | True = runS $ do + mbn <- newBigNat# nx# + _ <- copyWordArray bn 0# mbn 0# nx# + _ <- svoid (writeBigNat# mbn li# (indexBigNat# bn li# + `or#` bitWord# bi#)) + unsafeFreezeBigNat# mbn + + where + !(# li#, bi# #) = quotRemInt# i# GMP_LIMB_BITS# + nx# = sizeofBigNat# bn + d# = li# +# 1# -# nx# + + +complementBitBigNat :: BigNat -> Int# -> BigNat +complementBitBigNat bn i# + | testBitBigNat bn i# = clearBitBigNat bn i# + | True = setBitBigNat bn i# + popCountBigNat :: BigNat -> Int# popCountBigNat bn@(BN# ba#) = word2Int# (c_mpn_popcount ba# (sizeofBigNat# bn)) @@ -1794,6 +1855,15 @@ copyWordArray# src src_ofs dst dst_ofs len dst (dst_ofs `uncheckedIShiftL#` GMP_LIMB_SHIFT#) (len `uncheckedIShiftL#` GMP_LIMB_SHIFT#) +copyWordArray :: BigNat -> Int# -> MutBigNat s -> Int# -> Int# -> S s () +copyWordArray (BN# ba#) ofs_ba# (MBN# mba#) ofs_mba# len# + = svoid (copyWordArray# ba# ofs_ba# mba# ofs_mba# len#) + +clearWordArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s +clearWordArray# mba ofs len + = setByteArray# mba (ofs `uncheckedIShiftL#` GMP_LIMB_SHIFT#) + (len `uncheckedIShiftL#` GMP_LIMB_SHIFT#) 0# + -- | Version of 'normSizeofMutBigNat'#' which scans all allocated 'MutBigNat#' normSizeofMutBigNat# :: MutBigNat s -> State# s -> (# State# s, Int# #) normSizeofMutBigNat# mbn@(MBN# mba) s = normSizeofMutBigNat'# mbn sz# s' @@ -1837,13 +1907,7 @@ byteArrayToBigNat# ba# n0# where !(# baszq#, baszr# #) = quotRemInt# (sizeofByteArray# ba#) GMP_LIMB_BYTES# - n# = fmssl (n0# -# 1#) - - -- find most significant set limb, return normalized size - fmssl i# - | isTrue# (i# <# 0#) = 0# - | isTrue# (neWord# (indexWordArray# ba# i#) 0##) = i# +# 1# - | True = fmssl (i# -# 1#) + n# = fmssl (BN# ba#) (n0# -# 1#) -- | Read 'Integer' (without sign) from memory location at @/addr/@ in -- base-256 representation. @@ -2096,3 +2160,11 @@ cmpI# x# y# = (x# ># y#) -# (x# <# y#) minI# :: Int# -> Int# -> Int# minI# x# y# | isTrue# (x# <=# y#) = x# | True = y# + +-- find most-sig set limb, starting at given index +fmssl :: BigNat -> Int# -> Int# +fmssl !bn i0# = go i0# + where + go i# | isTrue# (i# <# 0#) = 0# + | isTrue# (neWord# (indexBigNat# bn i#) 0##) = i# +# 1# + | True = go (i# -# 1#) From git at git.haskell.org Mon Oct 16 20:39:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 20:39:44 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: ghc-pkg: Try opening lockfiles in read-write mode first (92014a7) Message-ID: <20171016203944.48CC53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/92014a72f12786d8f9c3d9b82a295621ca4b3fff/ghc >--------------------------------------------------------------- commit 92014a72f12786d8f9c3d9b82a295621ca4b3fff Author: Ben Gamari Date: Tue Aug 29 14:26:55 2017 -0400 ghc-pkg: Try opening lockfiles in read-write mode first As pointed out in #13945, some filesystems only allow allow exclusive locks if the fd being locked was opened for write access. This causes ghc-pkg to fail as it first attempts to open and exclusively lock its lockfile in read-only mode to accomodate package databases for which we lack write permissions (e.g. global package databases). Instead, we now try read-write mode first, falling back to read-only mode if this fails. Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13945 Differential Revision: https://phabricator.haskell.org/D3897 (cherry picked from commit f86de44dac0a6ca40c5fcd65f3a1944c45fa6011) >--------------------------------------------------------------- 92014a72f12786d8f9c3d9b82a295621ca4b3fff libraries/ghc-boot/GHC/PackageDb.hs | 22 ++++++++++++++-------- 1 file changed, 14 insertions(+), 8 deletions(-) diff --git a/libraries/ghc-boot/GHC/PackageDb.hs b/libraries/ghc-boot/GHC/PackageDb.hs index bf83d25..9ce07e7 100644 --- a/libraries/ghc-boot/GHC/PackageDb.hs +++ b/libraries/ghc-boot/GHC/PackageDb.hs @@ -239,15 +239,21 @@ lockPackageDbWith mode file = do -- DB for reading then we will require that the installer/packaging has -- included the lock file. -- - -- Thus the logic here is to first try opening in read-only mode (to handle - -- global read-only DBs) and if the file does not exist then try opening in - -- read/write mode to create the lock file. If either succeed then lock the - -- file. IO exceptions (other than the first open attempt failing due to the - -- file not existing) simply propagate. + -- Thus the logic here is to first try opening in read-write mode + -- and if that fails we try read-only (to handle global read-only DBs). + -- If either succeed then lock the file. IO exceptions (other than the first + -- open attempt failing due to the file not existing) simply propagate. + -- + -- Note that there is a complexity here which was discovered in #13945: some + -- filesystems (e.g. NFS) will only allow exclusive locking if the fd was + -- opened for write access. We would previously try opening the lockfile for + -- read-only access first, however this failed when run on such filesystems. + -- Consequently, we now try read-write access first, falling back to read-only + -- if are denied permission (e.g. in the case of a global database). catchJust - (\e -> if isDoesNotExistError e then Just () else Nothing) - (lockFileOpenIn ReadMode) - (const $ lockFileOpenIn ReadWriteMode) + (\e -> if isPermissionError e then Just () else Nothing) + (lockFileOpenIn ReadWriteMode) + (const $ lockFileOpenIn ReadMode) where lock = file <.> "lock" From git at git.haskell.org Mon Oct 16 20:39:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 20:39:50 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix nasty bug in w/w for absence analysis (35f8504) Message-ID: <20171016203950.DF5373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/35f85046d7f639b8aa741069f19add754b546fdc/ghc >--------------------------------------------------------------- commit 35f85046d7f639b8aa741069f19add754b546fdc Author: Simon Peyton Jones Date: Mon Oct 2 15:25:02 2017 +0100 Fix nasty bug in w/w for absence analysis This dark corner was exposed by Trac #14285. It involves the interaction between absence analysis and INLINABLE pragmas. There is a full explanation in Note [aBSENT_ERROR_ID] in MkCore, which you can read there. The changes in this patch are * Make exprIsHNF return True for absentError, treating absentError like an honorary data constructor. * Make absentError /not/ be diverging, unlike other error Ids. This is all a bit horrible. * While doing this I found that exprOkForSpeculation didn't have a case for value lambdas so I added one. It's not really called on lifted types much, but it seems like the right thing (cherry picked from commit dbbee1bacef1a8accc630908c31cf267a3cb98a9) >--------------------------------------------------------------- 35f85046d7f639b8aa741069f19add754b546fdc compiler/basicTypes/MkId.hs | 16 +-- compiler/coreSyn/CoreUtils.hs | 29 ++++-- compiler/coreSyn/MkCore.hs | 110 +++++++++++++++++++-- compiler/simplCore/SetLevels.hs | 3 +- compiler/simplCore/Simplify.hs | 100 +++++++++---------- compiler/stranal/WwLib.hs | 37 ++++--- testsuite/tests/stranal/should_run/T14285.hs | 9 ++ .../tests/stranal/should_run/T14285.stdout | 0 testsuite/tests/stranal/should_run/T14285a.hs | 37 +++++++ testsuite/tests/stranal/should_run/all.T | 1 + 10 files changed, 246 insertions(+), 96 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 35f85046d7f639b8aa741069f19add754b546fdc From git at git.haskell.org Mon Oct 16 20:39:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 20:39:47 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: PackageDb: Explicitly unlock package database before closing (f093d7e) Message-ID: <20171016203947.03F373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/f093d7ea26323f026d95338162913c33525b32fe/ghc >--------------------------------------------------------------- commit f093d7ea26323f026d95338162913c33525b32fe Author: Ben Gamari Date: Tue Aug 29 14:45:28 2017 -0400 PackageDb: Explicitly unlock package database before closing Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13945 Differential Revision: https://phabricator.haskell.org/D3874 (cherry picked from commit 779b9e6965416ee08af6eb15354cf09e9f40e0d9) >--------------------------------------------------------------- f093d7ea26323f026d95338162913c33525b32fe libraries/ghc-boot/GHC/PackageDb.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/libraries/ghc-boot/GHC/PackageDb.hs b/libraries/ghc-boot/GHC/PackageDb.hs index 9ce07e7..a59c46e 100644 --- a/libraries/ghc-boot/GHC/PackageDb.hs +++ b/libraries/ghc-boot/GHC/PackageDb.hs @@ -267,7 +267,11 @@ lockPackageDbWith mode file = do return $ PackageDbLock hnd lockPackageDb = lockPackageDbWith ExclusiveLock -unlockPackageDb (PackageDbLock hnd) = hClose hnd +unlockPackageDb (PackageDbLock hnd) = do +#if MIN_VERSION_base(4,11,0) + hUnlock hnd +#endif + hClose hnd -- MIN_VERSION_base(4,10,0) #else From git at git.haskell.org Mon Oct 16 20:39:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 20:39:54 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Do not quantify over deriving clauses (f0b46f3) Message-ID: <20171016203954.2E7BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/f0b46f3e6a42c29e6d802078e357daf33666ba99/ghc >--------------------------------------------------------------- commit f0b46f3e6a42c29e6d802078e357daf33666ba99 Author: Simon Peyton Jones Date: Thu Oct 12 09:25:25 2017 +0100 Do not quantify over deriving clauses Trac #14331 showed that in a data type decl like data D = D deriving (C (a :: k)) we were quantifying D over the 'k' in the deriving clause. Yikes. Easily fixed, by deleting code in RnTypes.extractDataDefnKindVars See the discussion on the ticket, esp comment:8. (cherry picked from commit 82b77ec375ab74678ac2afecf55dc574fa24490f) >--------------------------------------------------------------- f0b46f3e6a42c29e6d802078e357daf33666ba99 compiler/rename/RnTypes.hs | 22 +++++++++++++--------- testsuite/tests/deriving/should_compile/T14331.hs | 10 ++++++++++ testsuite/tests/deriving/should_compile/all.T | 4 ++++ 3 files changed, 27 insertions(+), 9 deletions(-) diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 589cc02..50e57e5 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -1598,14 +1598,23 @@ extractRdrKindSigVars (L _ resultSig) extractDataDefnKindVars :: HsDataDefn RdrName -> RnM [Located RdrName] -- Get the scoped kind variables mentioned free in the constructor decls --- Eg data T a = T1 (S (a :: k) | forall (b::k). T2 (S b) --- Here k should scope over the whole definition +-- Eg: data T a = T1 (S (a :: k) | forall (b::k). T2 (S b) +-- Here k should scope over the whole definition +-- +-- However, do NOT collect free kind vars from the deriving clauses: +-- Eg: (Trac #14331) class C p q +-- data D = D deriving ( C (a :: k) ) +-- Here k should /not/ scope over the whole definition. We intend +-- this to elaborate to: +-- class C @k1 @k2 (p::k1) (q::k2) +-- data D = D +-- instance forall k (a::k). C @k @* a D where ... +-- extractDataDefnKindVars (HsDataDefn { dd_ctxt = ctxt, dd_kindSig = ksig - , dd_cons = cons, dd_derivs = L _ derivs }) + , dd_cons = cons }) = (nubL . freeKiTyVarsKindVars) <$> (extract_lctxt TypeLevel ctxt =<< extract_mb extract_lkind ksig =<< - extract_sig_tys (concatMap (unLoc . deriv_clause_tys . unLoc) derivs) =<< foldrM (extract_con . unLoc) emptyFKTV cons) where extract_con (ConDeclGADT { }) acc = return acc @@ -1623,11 +1632,6 @@ extract_lctxt :: TypeOrKind -> LHsContext RdrName -> FreeKiTyVars -> RnM FreeKiTyVars extract_lctxt t_or_k ctxt = extract_ltys t_or_k (unLoc ctxt) -extract_sig_tys :: [LHsSigType RdrName] -> FreeKiTyVars -> RnM FreeKiTyVars -extract_sig_tys sig_tys acc - = foldrM (\sig_ty acc -> extract_lty TypeLevel (hsSigType sig_ty) acc) - acc sig_tys - extract_ltys :: TypeOrKind -> [LHsType RdrName] -> FreeKiTyVars -> RnM FreeKiTyVars extract_ltys t_or_k tys acc = foldrM (extract_lty t_or_k) acc tys diff --git a/testsuite/tests/deriving/should_compile/T14331.hs b/testsuite/tests/deriving/should_compile/T14331.hs new file mode 100644 index 0000000..4fe40fa --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T14331.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeInType #-} +module Bug where + +class C p q + +data D = D deriving (C (a :: k)) diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 5c3f970..5f94f9d 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -1,3 +1,6 @@ +def just_the_deriving( msg ): + return msg[0:msg.find('Filling in method body')] + test('drv001', normal, compile, ['']) test('drv002', normal, compile, ['']) test('drv003', normal, compile, ['']) @@ -85,3 +88,4 @@ test('T12814', normal, compile, ['-Wredundant-constraints']) test('T13272', normal, compile, ['']) test('T13272a', normal, compile, ['']) test('T13297', normal, compile, ['']) +test('T14331', normal, compile, ['']) From git at git.haskell.org Mon Oct 16 21:15:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:15:36 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Removing more PostTc types (c51fe7b) Message-ID: <20171016211536.C3DC33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/c51fe7bc3c5e016646c893a88d0f331de05fc26e/ghc >--------------------------------------------------------------- commit c51fe7bc3c5e016646c893a88d0f331de05fc26e Author: Alan Zimmerman Date: Mon Oct 16 12:40:02 2017 +0200 Removing more PostTc types >--------------------------------------------------------------- c51fe7bc3c5e016646c893a88d0f331de05fc26e compiler/deSugar/Check.hs | 4 +-- compiler/deSugar/DsArrows.hs | 4 +-- compiler/deSugar/DsMeta.hs | 4 +-- compiler/deSugar/Match.hs | 4 +-- compiler/hsSyn/Convert.hs | 3 +- compiler/hsSyn/HsPat.hs | 69 +++++++++++++++++------------------------- compiler/hsSyn/HsUtils.hs | 6 ++-- compiler/parser/RdrHsSyn.hs | 4 +-- compiler/rename/RnPat.hs | 8 ++--- compiler/typecheck/TcHsSyn.hs | 12 ++++---- compiler/typecheck/TcPat.hs | 8 ++--- compiler/typecheck/TcPatSyn.hs | 14 ++++----- utils/ghctags/Main.hs | 2 +- 13 files changed, 63 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 c51fe7bc3c5e016646c893a88d0f331de05fc26e From git at git.haskell.org Mon Oct 16 21:15:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:15:39 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: More HsPat TTG in place (571f22e) Message-ID: <20171016211539.95C643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/571f22e96525b1ff8786367426d0f7a4f0e9b44f/ghc >--------------------------------------------------------------- commit 571f22e96525b1ff8786367426d0f7a4f0e9b44f Author: Alan Zimmerman Date: Mon Oct 16 17:32:00 2017 +0200 More HsPat TTG in place >--------------------------------------------------------------- 571f22e96525b1ff8786367426d0f7a4f0e9b44f compiler/deSugar/Check.hs | 19 ++++---- compiler/deSugar/DsArrows.hs | 10 ++--- compiler/deSugar/DsMeta.hs | 14 +++--- compiler/deSugar/Match.hs | 27 ++++++------ compiler/deSugar/MatchLit.hs | 15 ++++--- compiler/hsSyn/Convert.hs | 6 +-- compiler/hsSyn/HsExtension.hs | 18 ++++---- compiler/hsSyn/HsPat.hs | 98 ++++++++++++++++++++++++++++-------------- compiler/hsSyn/HsUtils.hs | 40 ++++++++--------- compiler/parser/RdrHsSyn.hs | 8 ++-- compiler/rename/RnExpr.hs | 38 ++++++++-------- compiler/rename/RnPat.hs | 28 ++++++------ compiler/rename/RnSplice.hs | 5 ++- compiler/typecheck/TcHsSyn.hs | 28 ++++++------ compiler/typecheck/TcPat.hs | 21 ++++----- compiler/typecheck/TcPatSyn.hs | 40 ++++++++--------- utils/ghctags/Main.hs | 6 +-- 17 files changed, 230 insertions(+), 191 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 571f22e96525b1ff8786367426d0f7a4f0e9b44f From git at git.haskell.org Mon Oct 16 21:15:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:15:42 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Remove the last PostTc types from HsPat (4be2c2d) Message-ID: <20171016211542.8427E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/4be2c2dc5c97fff0826a96caa9a0cb27396f1789/ghc >--------------------------------------------------------------- commit 4be2c2dc5c97fff0826a96caa9a0cb27396f1789 Author: Alan Zimmerman Date: Mon Oct 16 23:15:04 2017 +0200 Remove the last PostTc types from HsPat >--------------------------------------------------------------- 4be2c2dc5c97fff0826a96caa9a0cb27396f1789 compiler/deSugar/Check.hs | 6 ++--- compiler/deSugar/DsArrows.hs | 4 +-- compiler/deSugar/DsMeta.hs | 6 ++--- compiler/deSugar/Match.hs | 16 ++++++------ compiler/deSugar/MatchLit.hs | 8 +++--- compiler/hsSyn/Convert.hs | 2 +- compiler/hsSyn/HsPat.hs | 59 +++++++++++++++++++----------------------- compiler/hsSyn/HsUtils.hs | 10 +++---- compiler/parser/RdrHsSyn.hs | 2 +- compiler/rename/RnExpr.hs | 2 +- compiler/rename/RnPat.hs | 12 ++++----- compiler/typecheck/TcHsSyn.hs | 18 ++++++------- compiler/typecheck/TcPat.hs | 14 +++++----- compiler/typecheck/TcPatSyn.hs | 8 +++--- utils/ghctags/Main.hs | 2 +- 15 files changed, 82 insertions(+), 87 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 4be2c2dc5c97fff0826a96caa9a0cb27396f1789 From git at git.haskell.org Mon Oct 16 21:26:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:26:38 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Rework and finish debug flag documentation (8536b7f) Message-ID: <20171016212638.918F73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8536b7f859f234cf51ddf442af1042c1c7efbdbe/ghc >--------------------------------------------------------------- commit 8536b7f859f234cf51ddf442af1042c1c7efbdbe Author: Ben Gamari Date: Mon Oct 16 16:49:21 2017 -0400 users-guide: Rework and finish debug flag documentation This documentation was incomplete and not terribly well organized. Given that I've spent a lot of time searching through this page, I figured it is perhaps worth it to clean it up a bit. >--------------------------------------------------------------- 8536b7f859f234cf51ddf442af1042c1c7efbdbe docs/users_guide/debugging.rst | 696 +++++++++++++++++++++++++---------------- 1 file changed, 429 insertions(+), 267 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 8536b7f859f234cf51ddf442af1042c1c7efbdbe From git at git.haskell.org Mon Oct 16 21:26:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:26:41 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Fix various warnings (c5da84d) Message-ID: <20171016212641.63E7B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c5da84db217735ccce47c2350a6917ee9ac00927/ghc >--------------------------------------------------------------- commit c5da84db217735ccce47c2350a6917ee9ac00927 Author: Ben Gamari Date: Mon Oct 16 17:07:45 2017 -0400 users-guide: Fix various warnings [skip ci] >--------------------------------------------------------------- c5da84db217735ccce47c2350a6917ee9ac00927 docs/users_guide/debug-info.rst | 2 +- docs/users_guide/using-warnings.rst | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/debug-info.rst b/docs/users_guide/debug-info.rst index d1bd28c..915591a 100644 --- a/docs/users_guide/debug-info.rst +++ b/docs/users_guide/debug-info.rst @@ -185,7 +185,7 @@ Stack trace functionality is exposed for use by Haskell programs in the :base-ref:`GHC.ExecutionStack.` module. See the Haddock documentation in this module for details regarding usage. -.. _backtrace_signal: +.. _backtrace-signal: Requesting a stack trace with ``SIGQUIT`` ----------------------------------------- diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index 15b6301..65ffe99 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -281,7 +281,7 @@ of ``-W(no-)*``. .. ghc-flag:: -Wdeferred-out-of-scope-variables :shortdesc: Report warnings when variable out-of-scope errors are - :ref:`deferred until runtime. + :ref:`deferred until runtime `. See :ghc-flag:`-fdefer-out-of-scope-variables`. :type: dynamic :reverse: -Wno-deferred-out-of-scope-variables From git at git.haskell.org Mon Oct 16 21:26:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:26:44 +0000 (UTC) Subject: [commit: ghc] master: Levity polymorphic Backpack. (fd8b044) Message-ID: <20171016212644.A39893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fd8b044e9664181d4815e48e8f83be78bc9fe8d2/ghc >--------------------------------------------------------------- commit fd8b044e9664181d4815e48e8f83be78bc9fe8d2 Author: Edward Z. Yang Date: Mon Oct 16 15:27:10 2017 -0400 Levity polymorphic Backpack. This patch makes it possible to specify non * kinds of abstract data types in signatures, so you can have levity polymorphism through Backpack, without the runtime representation constraint! Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: andrewthad, bgamari, austin, goldfire Reviewed By: bgamari Subscribers: goldfire, rwbarton, thomie GHC Trac Issues: #13955 Differential Revision: https://phabricator.haskell.org/D3825 >--------------------------------------------------------------- fd8b044e9664181d4815e48e8f83be78bc9fe8d2 compiler/backpack/RnModIface.hs | 2 + compiler/iface/IfaceSyn.hs | 9 +++-- compiler/typecheck/TcHsType.hs | 27 ++++++++++--- compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 17 +++++++-- docs/users_guide/separate_compilation.rst | 13 ++++++- testsuite/tests/backpack/should_run/T13955.bkp | 44 ++++++++++++++++++++++ .../should_run/T13955.stdout} | 0 testsuite/tests/backpack/should_run/all.T | 1 + testsuite/tests/ghci/scripts/T7627.stdout | 7 +++- 10 files changed, 106 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 fd8b044e9664181d4815e48e8f83be78bc9fe8d2 From git at git.haskell.org Mon Oct 16 21:26:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:26:47 +0000 (UTC) Subject: [commit: ghc] master: configure: Fix CC version check on Apple compilers (71a4235) Message-ID: <20171016212647.6296F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/71a423562a555ef0805bba546a3a42d437803842/ghc >--------------------------------------------------------------- commit 71a423562a555ef0805bba546a3a42d437803842 Author: Ben Gamari Date: Tue Oct 10 16:09:39 2017 -0400 configure: Fix CC version check on Apple compilers It seems that some Apple LLVM wrappers emit multiple messages containing the string "version", which we previously used to find the version number. For instance, Configured with: --prefix=/Applications/Xcode.app/Contents/... Apple LLVM version 9.0.0 (clang-900.0.37) Target: x86_64-apple-darwin16.7.0 Thread model: posix InstalledDir: /Applications/Xcode.app/Contents/Developer/... Found CUDA installation: /usr/local/cuda, version 8.0 We now take care to only look at the first occurrence of this string. New `sed` command due to @merijn. Test Plan: Validate on all the compilers Reviewers: austin, hvr Subscribers: rwbarton, thomie, merijn, erikd Differential Revision: https://phabricator.haskell.org/D4069 >--------------------------------------------------------------- 71a423562a555ef0805bba546a3a42d437803842 aclocal.m4 | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 7e1e3e1..64fa8bf 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1234,7 +1234,9 @@ GccLT44=NO GccLT46=NO AC_CACHE_CHECK([version of gcc], [fp_cv_gcc_version], [ - fp_cv_gcc_version="`$CC -v 2>&1 | grep 'version ' | sed -e 's/.*version [[^0-9]]*\([[0-9.]]*\).*/\1/g'`" + # Be sure only to look at the first occurrence of the "version " string; + # Some Apple compilers emit multiple messages containing this string. + fp_cv_gcc_version="`$CC -v 2>&1 | sed -n -e '1,/version /s/.*version [[^0-9]]*\([[0-9.]]*\).*/\1/p'`" FP_COMPARE_VERSIONS([$fp_cv_gcc_version], [-lt], [3.0], [AC_MSG_ERROR([Need at least gcc version 3.0 (3.4+ recommended)])]) # See #2770: gcc 2.95 doesn't work any more, apparently. There probably From git at git.haskell.org Mon Oct 16 21:26:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:26:50 +0000 (UTC) Subject: [commit: ghc] master: users guide: Eliminate redundant :category: tags in debugging.rst (d7f4f41) Message-ID: <20171016212650.29F8E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d7f4f41b0cbde2cf0a78ea05ba0ed7d66894bade/ghc >--------------------------------------------------------------- commit d7f4f41b0cbde2cf0a78ea05ba0ed7d66894bade Author: Ben Gamari Date: Mon Oct 16 16:52:31 2017 -0400 users guide: Eliminate redundant :category: tags in debugging.rst The categories in this file are defined in flags.py. >--------------------------------------------------------------- d7f4f41b0cbde2cf0a78ea05ba0ed7d66894bade docs/users_guide/debugging.rst | 89 ++---------------------------------------- 1 file changed, 4 insertions(+), 85 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d7f4f41b0cbde2cf0a78ea05ba0ed7d66894bade From git at git.haskell.org Mon Oct 16 21:26:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:26:52 +0000 (UTC) Subject: [commit: ghc] master: FreeBSD dtrace probe support (5dab544) Message-ID: <20171016212652.DE55D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5dab54428229a8d4f1658c4ad94f616b211851fe/ghc >--------------------------------------------------------------- commit 5dab54428229a8d4f1658c4ad94f616b211851fe Author: Ben Gamari Date: Mon Oct 16 15:27:48 2017 -0400 FreeBSD dtrace probe support Reviewers: austin, hvr, erikd, simonmar, bgamari Reviewed By: bgamari Subscribers: snowleopard, raichoo, rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3994 >--------------------------------------------------------------- 5dab54428229a8d4f1658c4ad94f616b211851fe configure.ac | 4 +++- rts/RtsProbes.d | 7 +++++++ rts/ghc.mk | 40 +++++++++++++++++++++++++++++++++------- 3 files changed, 43 insertions(+), 8 deletions(-) diff --git a/configure.ac b/configure.ac index 0416e83..d32ede2 100644 --- a/configure.ac +++ b/configure.ac @@ -794,7 +794,9 @@ dnl ** check for dtrace (currently only implemented for Mac OS X) HaveDtrace=NO AC_PATH_PROG(DtraceCmd,dtrace) if test -n "$DtraceCmd"; then - if test "x$TargetOS_CPP-$TargetVendor_CPP" = "xdarwin-apple" -o "x$TargetOS_CPP-$TargetVendor_CPP" = "xsolaris2-unknown"; then + if test "x$TargetOS_CPP-$TargetVendor_CPP" = "xdarwin-apple" \ + -o "x$TargetOS_CPP-$TargetVendor_CPP" = "xfreebsd-portbld" \ + -o "x$TargetOS_CPP-$TargetVendor_CPP" = "xsolaris2-unknown"; then HaveDtrace=YES fi fi diff --git a/rts/RtsProbes.d b/rts/RtsProbes.d index 277a494..efbe653 100644 --- a/rts/RtsProbes.d +++ b/rts/RtsProbes.d @@ -12,6 +12,13 @@ # endif #endif +#if defined(__FreeBSD__) +/* we need this otherwise dtrace complains about redeclared int types + * TODO: find a better way to do this + */ +#define _INTTYPES_H_ +#endif + #include "HsFFI.h" #include "rts/EventLogFormat.h" diff --git a/rts/ghc.mk b/rts/ghc.mk index 924a048..57db297 100644 --- a/rts/ghc.mk +++ b/rts/ghc.mk @@ -134,6 +134,13 @@ endif endif endif + +ifeq "$(USE_DTRACE)" "YES" +ifneq "$(findstring $(TargetOS_CPP), linux solaris2 freebsd)" "" +NEED_DTRACE_PROBES_OBJ = YES +endif +endif + #----------------------------------------------------------------------------- # Building one way define build-rts-way # args: $1 = way @@ -170,10 +177,6 @@ rts_$1_CMM_OBJS = $$(patsubst rts/%.cmm,rts/dist/build/%.$$($1_osuf),$$(rts_CMM_ rts_$1_OBJS = $$(rts_$1_C_OBJS) $$(rts_$1_S_OBJS) $$(rts_$1_CMM_OBJS) -ifneq "$$(findstring linux solaris2, $(TargetOS_CPP))" "" -NEED_DTRACE_PROBES_OBJ = YES -endif - ifeq "$(USE_DTRACE)" "YES" ifeq "$(NEED_DTRACE_PROBES_OBJ)" "YES" # On Darwin we don't need to generate binary containing probes defined @@ -181,7 +184,7 @@ ifeq "$(NEED_DTRACE_PROBES_OBJ)" "YES" # from the DTrace probes definitions rts_$1_DTRACE_OBJS = rts/dist/build/RtsProbes.$$($1_osuf) -rts/dist/build/RtsProbes.$$($1_osuf) : $$(rts_$1_OBJS) +$$(rts_$1_DTRACE_OBJS) : $$(rts_$1_OBJS) $(DTRACE) -G -C $$(addprefix -I,$$(GHC_INCLUDE_DIRS)) -DDTRACE -s rts/RtsProbes.d -o \ $$@ $$(rts_$1_OBJS) endif @@ -248,9 +251,32 @@ $$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/dist/libs.depend $$( $$(rts_$1_DTRACE_OBJS) -o $$@ endif else -$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) + +ifeq "$(USE_DTRACE)" "YES" +ifeq "$(NEED_DTRACE_PROBES_OBJ)" "YES" +rts_$1_LINKED_OBJS = rts/dist/build/RTS.$$($1_osuf) + +$$(rts_$1_LINKED_OBJS) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) + "$$(RM)" $$(RM_OPTS) $$@ + + # When linking an archive the linker will only include the object files that + # are actually needed during linking. It therefore does not include the dtrace + # specific code for initializing the probes. By creating a single object that + # also includes the probe object code we force the linker to include the + # probes when linking the static runtime. + $(LD) -r -o $$(rts_$1_LINKED_OBJS) $$(rts_$1_DTRACE_OBJS) $$(rts_$1_OBJS) +else +rts_$1_LINKED_OBJS = $$(rts_$1_OBJS) +endif +else +rts_$1_LINKED_OBJS = $$(rts_$1_OBJS) +endif + + +$$(rts_$1_LIB) : $$(rts_$1_LINKED_OBJS) "$$(RM)" $$(RM_OPTS) $$@ - echo $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) | "$$(XARGS)" $$(XARGS_OPTS) "$$(AR_STAGE1)" \ + + echo $$(rts_$1_LINKED_OBJS) | "$$(XARGS)" $$(XARGS_OPTS) "$$(AR_STAGE1)" \ $$(AR_OPTS_STAGE1) $$(EXTRA_AR_ARGS_STAGE1) $$@ ifneq "$$(UseSystemLibFFI)" "YES" From git at git.haskell.org Mon Oct 16 21:26:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:26:55 +0000 (UTC) Subject: [commit: ghc] master: rts: Label all threads created by the RTS (7e790b3) Message-ID: <20171016212655.9BF9D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7e790b38c205da67681f632b00faf7a0ea33510d/ghc >--------------------------------------------------------------- commit 7e790b38c205da67681f632b00faf7a0ea33510d Author: Ben Gamari Date: Mon Oct 16 15:28:02 2017 -0400 rts: Label all threads created by the RTS Reviewers: austin, erikd, simonmar Reviewed By: simonmar Subscribers: pacak, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4068 >--------------------------------------------------------------- 7e790b38c205da67681f632b00faf7a0ea33510d rts/Sparks.c | 3 ++- rts/Weak.c | 3 +++ rts/posix/Signals.c | 17 ++++++++++------- rts/win32/ConsoleHandler.c | 14 ++++++++------ 4 files changed, 23 insertions(+), 14 deletions(-) diff --git a/rts/Sparks.c b/rts/Sparks.c index ecd3c38..a31a5df 100644 --- a/rts/Sparks.c +++ b/rts/Sparks.c @@ -14,6 +14,7 @@ #include "Trace.h" #include "Prelude.h" #include "Sparks.h" +#include "ThreadLabels.h" #include "sm/HeapAlloc.h" #if defined(THREADED_RTS) @@ -43,7 +44,7 @@ createSparkThread (Capability *cap) tso = createIOThread (cap, RtsFlags.GcFlags.initialStkSize, (StgClosure *)runSparks_closure); - + labelThread(cap, tso, "spark evaluator"); traceEventCreateSparkThread(cap, tso->id); appendToRunQueue(cap,tso); diff --git a/rts/Weak.c b/rts/Weak.c index f3e91fb..577d1cd 100644 --- a/rts/Weak.c +++ b/rts/Weak.c @@ -14,6 +14,7 @@ #include "Weak.h" #include "Schedule.h" #include "Prelude.h" +#include "ThreadLabels.h" #include "Trace.h" void @@ -151,5 +152,7 @@ scheduleFinalizers(Capability *cap, StgWeak *list) rts_mkInt(cap,n)), (StgClosure *)arr) ); + scheduleThread(cap,t); + labelThread(cap, t, "weak finalizer thread"); } diff --git a/rts/posix/Signals.c b/rts/posix/Signals.c index e75f99d..cf45019 100644 --- a/rts/posix/Signals.c +++ b/rts/posix/Signals.c @@ -16,6 +16,7 @@ #include "Prelude.h" #include "Ticker.h" #include "Stable.h" +#include "ThreadLabels.h" #include "Libdw.h" #if defined(alpha_HOST_ARCH) @@ -471,14 +472,16 @@ startSignalHandlers(Capability *cap) // freed by runHandler memcpy(info, next_pending_handler, sizeof(siginfo_t)); - scheduleThread(cap, + StgTSO *t = createIOThread(cap, - RtsFlags.GcFlags.initialStkSize, - rts_apply(cap, - rts_apply(cap, - &base_GHCziConcziSignal_runHandlersPtr_closure, - rts_mkPtr(cap, info)), - rts_mkInt(cap, info->si_signo)))); + RtsFlags.GcFlags.initialStkSize, + rts_apply(cap, + rts_apply(cap, + &base_GHCziConcziSignal_runHandlersPtr_closure, + rts_mkPtr(cap, info)), + rts_mkInt(cap, info->si_signo))); + scheduleThread(cap, t); + labelThread(cap, t, "signal handler thread"); } unblockUserSignals(); diff --git a/rts/win32/ConsoleHandler.c b/rts/win32/ConsoleHandler.c index 3d283b0..88c4a61 100644 --- a/rts/win32/ConsoleHandler.c +++ b/rts/win32/ConsoleHandler.c @@ -183,13 +183,15 @@ void startSignalHandlers(Capability *cap) handler = deRefStablePtr((StgStablePtr)console_handler); while (stg_pending_events > 0) { stg_pending_events--; - scheduleThread(cap, + StgTSO *t = createIOThread(cap, - RtsFlags.GcFlags.initialStkSize, - rts_apply(cap, - (StgClosure *)handler, - rts_mkInt(cap, - stg_pending_buf[stg_pending_events])))); + RtsFlags.GcFlags.initialStkSize, + rts_apply(cap, + (StgClosure *)handler, + rts_mkInt(cap, + stg_pending_buf[stg_pending_events]))); + scheduleThread(cap, t); + labelThread(cap, t, "signal handler thread"); } RELEASE_LOCK(&sched_mutex); From git at git.haskell.org Mon Oct 16 21:31:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:31:28 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Override default `clearBit` method impl for `Natural` (3de07dc) Message-ID: <20171016213128.9F3623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/3de07dcf221548e73c3623a085cae99d0b519c8b/ghc >--------------------------------------------------------------- commit 3de07dcf221548e73c3623a085cae99d0b519c8b Author: Herbert Valerio Riedel Date: Mon Oct 16 22:12:03 2017 +0200 Override default `clearBit` method impl for `Natural` The default implementation of `clearBit` is in terms of `complement`. However, `complement` is not well-defined for `Natural` and this consequently renders the default implementation of `clearBit` dysfunctional. This implements `clearBit` in terms of `testBit` and `setBit` which are both well-defined for `Natural`s. This addresses #13203 (cherry picked from commit 5984a698fc2974b719365a9647a7cae1bed51eec) >--------------------------------------------------------------- 3de07dcf221548e73c3623a085cae99d0b519c8b libraries/base/GHC/Natural.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index 0e5abc7..39da862 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -346,6 +346,11 @@ instance Bits Natural where -- TODO: setBit, clearBit, complementBit (needs more primitives) + -- NB: We cannot use the default impl of 'clearBit' due to + -- 'complement' not being well-defined for 'Natural' (c.f. #13203) + clearBit x i | testBit x i = complementBit x i + | otherwise = x + shiftL n 0 = n shiftL (NatS# 0##) _ = NatS# 0## shiftL (NatS# 1##) i = bit i From git at git.haskell.org Mon Oct 16 21:31:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:31:31 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Enable testing 'Natural' type in TEST=arith011 (0a763ba) Message-ID: <20171016213131.6B93F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/0a763ba2c922f2b6ecfd68472fb8633722ea0489/ghc >--------------------------------------------------------------- commit 0a763ba2c922f2b6ecfd68472fb8633722ea0489 Author: Herbert Valerio Riedel Date: Sat Oct 14 20:37:47 2017 +0200 Enable testing 'Natural' type in TEST=arith011 This now passes thanks to 5984a698fc2974b719365a9647a7cae1bed51eec (re #13203) (cherry picked from commit 843772b86b62df686a9e57648fa9d3ed06b13973) >--------------------------------------------------------------- 0a763ba2c922f2b6ecfd68472fb8633722ea0489 testsuite/tests/numeric/should_run/arith011.hs | 33 +- testsuite/tests/numeric/should_run/arith011.stdout | 656 +++++++++++++++++++++ .../tests/numeric/should_run/arith011.stdout-ws-64 | 656 +++++++++++++++++++++ 3 files changed, 1341 insertions(+), 4 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0a763ba2c922f2b6ecfd68472fb8633722ea0489 From git at git.haskell.org Mon Oct 16 21:31:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 21:31:34 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix panic for `ByteArray#` arguments in CApiFFI foreign imports (95c1fee) Message-ID: <20171016213134.9073D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/95c1feeb9ce9b2d6a9453dc4da148b80a5ddce3d/ghc >--------------------------------------------------------------- commit 95c1feeb9ce9b2d6a9453dc4da148b80a5ddce3d Author: Herbert Valerio Riedel Date: Mon Oct 16 19:02:01 2017 +0200 Fix panic for `ByteArray#` arguments in CApiFFI foreign imports Declarations such as foreign import capi unsafe "string.h strlen" c_strlen_capi :: ByteArray# -> IO CSize foreign import capi unsafe "string.h memset" c_memset_capi :: MutableByteArray# s -> CInt -> CSize -> IO () would cause GHC to panic because the CApiFFI c-wrapper generator didn't know what C type to use for `(Mutable)ByteArray#` types (unlike the `ccall` codepath). This addresses #9274 Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4092 (cherry picked from commit add85cc2a3ec0bda810dca2a35264308ffaab069) >--------------------------------------------------------------- 95c1feeb9ce9b2d6a9453dc4da148b80a5ddce3d compiler/deSugar/DsForeign.hs | 6 ++++++ testsuite/tests/ffi/should_run/T9274.hs | 24 ++++++++++++++++++++++ .../tests/ffi/should_run/T9274.stdout | 0 testsuite/tests/ffi/should_run/all.T | 2 ++ 4 files changed, 32 insertions(+) diff --git a/compiler/deSugar/DsForeign.hs b/compiler/deSugar/DsForeign.hs index 65dc16a..80cbe72 100644 --- a/compiler/deSugar/DsForeign.hs +++ b/compiler/deSugar/DsForeign.hs @@ -713,6 +713,12 @@ toCType = f False -- through one layer of type synonym etc. | Just t' <- coreView t = f voidOK t' + -- This may be an 'UnliftedFFITypes'-style ByteArray# argument + -- (which is marshalled like a Ptr) + | Just byteArrayPrimTyCon == tyConAppTyConPicky_maybe t + = (Nothing, text "const void*") + | Just mutableByteArrayPrimTyCon == tyConAppTyConPicky_maybe t + = (Nothing, text "void*") -- Otherwise we don't know the C type. If we are allowing -- void then return that; otherwise something has gone wrong. | voidOK = (Nothing, text "void") diff --git a/testsuite/tests/ffi/should_run/T9274.hs b/testsuite/tests/ffi/should_run/T9274.hs new file mode 100644 index 0000000..814deff --- /dev/null +++ b/testsuite/tests/ffi/should_run/T9274.hs @@ -0,0 +1,24 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CApiFFI #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE UnliftedFFITypes #-} + +module Main where + +import qualified Data.ByteString.Short.Internal as SBS +import Foreign.C.Types +import GHC.Exts + +foreign import capi unsafe "string.h strlen" + c_strlen_capi :: ByteArray# -> IO CSize + +foreign import capi unsafe "string.h memset" + c_memset_capi :: MutableByteArray# s -> CInt -> CSize -> IO () + +main :: IO () +main = do + n <- c_strlen_capi ba# + print (n == 13) + where + !(SBS.SBS ba#) = "Hello FFI!!!!\NUL" diff --git a/libraries/base/tests/IO/IOError002.stdout b/testsuite/tests/ffi/should_run/T9274.stdout similarity index 100% copy from libraries/base/tests/IO/IOError002.stdout copy to testsuite/tests/ffi/should_run/T9274.stdout diff --git a/testsuite/tests/ffi/should_run/all.T b/testsuite/tests/ffi/should_run/all.T index 1bb58c5..fd0af7e 100644 --- a/testsuite/tests/ffi/should_run/all.T +++ b/testsuite/tests/ffi/should_run/all.T @@ -174,6 +174,8 @@ test('T4012', [expect_broken_for(7388, ['ghci'])], multimod_compile_and_run, test('T8083', [omit_ways(['ghci'])], compile_and_run, ['T8083_c.c']) +test('T9274', [omit_ways(['ghci'])], compile_and_run, ['']) + test('ffi023', [ omit_ways(['ghci']), extra_clean(['ffi023_c.o']), extra_run_opts('1000 4'), From git at git.haskell.org Mon Oct 16 23:14:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 23:14:32 +0000 (UTC) Subject: [commit: ghc] master: rts/posix: Ensure that memory commit succeeds (a69fa54) Message-ID: <20171016231432.AD3173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a69fa5441c944d7f74c76bdae9f3dd198007ee42/ghc >--------------------------------------------------------------- commit a69fa5441c944d7f74c76bdae9f3dd198007ee42 Author: Ben Gamari Date: Mon Oct 16 17:30:12 2017 -0400 rts/posix: Ensure that memory commit succeeds Previously we wouldn't check that mmap would succeed. I suspect this may have been the cause of #14329. Test Plan: Validate under low-memory condition Reviewers: simonmar, austin, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #14329 Differential Revision: https://phabricator.haskell.org/D4075 >--------------------------------------------------------------- a69fa5441c944d7f74c76bdae9f3dd198007ee42 rts/posix/OSMem.c | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c index ee727a5..2f0bf3f 100644 --- a/rts/posix/OSMem.c +++ b/rts/posix/OSMem.c @@ -534,7 +534,10 @@ void *osReserveHeapMemory(void *startAddressPtr, W_ *len) void osCommitMemory(void *at, W_ size) { - my_mmap(at, size, MEM_COMMIT); + void *r = my_mmap(at, size, MEM_COMMIT); + if (r == NULL) { + barf("Unable to commit %d bytes of memory", size); + } } void osDecommitMemory(void *at, W_ size) From git at git.haskell.org Mon Oct 16 23:14:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 23:14:38 +0000 (UTC) Subject: [commit: ghc] master: ghci: Include "Rts.h" before using TABLES_NEXT_TO_CODE (366182a) Message-ID: <20171016231438.2E6FE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/366182af1860fd1312007ffe8bedfd0d12d1c171/ghc >--------------------------------------------------------------- commit 366182af1860fd1312007ffe8bedfd0d12d1c171 Author: Ben Gamari Date: Mon Oct 16 17:36:14 2017 -0400 ghci: Include "Rts.h" before using TABLES_NEXT_TO_CODE Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4088 >--------------------------------------------------------------- 366182af1860fd1312007ffe8bedfd0d12d1c171 libraries/ghci/GHCi/InfoTable.hsc | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/ghci/GHCi/InfoTable.hsc b/libraries/ghci/GHCi/InfoTable.hsc index c553897..d650e24 100644 --- a/libraries/ghci/GHCi/InfoTable.hsc +++ b/libraries/ghci/GHCi/InfoTable.hsc @@ -1,5 +1,8 @@ {-# LANGUAGE CPP, MagicHash, ScopedTypeVariables #-} +-- Get definitions for the structs, constants & config etc. +#include "Rts.h" + -- | -- Run-time info table support. This module provides support for -- creating and reading info tables /in the running program/. @@ -24,9 +27,6 @@ import System.IO.Unsafe -- needed for 2nd stage type ItblCodes = Either [Word8] [Word32] --- Get definitions for the structs, constants & config etc. -#include "Rts.h" - -- Ultra-minimalist version specially for constructors #if SIZEOF_VOID_P == 8 type HalfWord = Word32 From git at git.haskell.org Mon Oct 16 23:14:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 23:14:40 +0000 (UTC) Subject: [commit: ghc] master: Flags.hsc: Peek a CBool (Word8), not a Bool (Int32) (9e3add9) Message-ID: <20171016231440.F1A983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9e3add93282536de098cce3c4212e577e2eeb17e/ghc >--------------------------------------------------------------- commit 9e3add93282536de098cce3c4212e577e2eeb17e Author: James Clarke Date: Mon Oct 16 17:37:55 2017 -0400 Flags.hsc: Peek a CBool (Word8), not a Bool (Int32) Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4093 >--------------------------------------------------------------- 9e3add93282536de098cce3c4212e577e2eeb17e libraries/base/GHC/RTS/Flags.hsc | 117 ++++++++++++++++++++++++++------------- 1 file changed, 78 insertions(+), 39 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9e3add93282536de098cce3c4212e577e2eeb17e From git at git.haskell.org Mon Oct 16 23:14:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 23:14:35 +0000 (UTC) Subject: [commit: ghc] master: RtClosureInspect: Fix inspecting Char# on 64-bit big-endian (d6c33da) Message-ID: <20171016231435.6DC863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d6c33da89b97d0d2a3b3b8f8077de8a09432d086/ghc >--------------------------------------------------------------- commit d6c33da89b97d0d2a3b3b8f8077de8a09432d086 Author: James Clarke Date: Mon Oct 16 17:33:45 2017 -0400 RtClosureInspect: Fix inspecting Char# on 64-bit big-endian Char# is represented with a full machine word, whereas Char's Storable instance uses an Int32, so we can't just treat it like a single-element Char array. Instead, read it as an Int and use chr to turn it into a Char. This fixes Trac #11262. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #11262 Differential Revision: https://phabricator.haskell.org/D4089 >--------------------------------------------------------------- d6c33da89b97d0d2a3b3b8f8077de8a09432d086 compiler/ghci/RtClosureInspect.hs | 5 ++++- testsuite/tests/ghci.debugger/scripts/all.T | 3 +-- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/compiler/ghci/RtClosureInspect.hs b/compiler/ghci/RtClosureInspect.hs index 7c532e5..63d1886 100644 --- a/compiler/ghci/RtClosureInspect.hs +++ b/compiler/ghci/RtClosureInspect.hs @@ -57,6 +57,7 @@ import TysWiredIn import DynFlags import Outputable as Ppr import GHC.Arr ( Array(..) ) +import GHC.Char import GHC.Exts import GHC.IO ( IO(..) ) @@ -489,7 +490,9 @@ cPprTermBase y = repPrim :: TyCon -> [Word] -> SDoc repPrim t = rep where rep x - | t == charPrimTyCon = text $ show (build x :: Char) + -- Char# uses native machine words, whereas Char's Storable instance uses + -- Int32, so we have to read it as an Int. + | t == charPrimTyCon = text $ show (chr (build x :: Int)) | t == intPrimTyCon = text $ show (build x :: Int) | t == wordPrimTyCon = text $ show (build x :: Word) | t == floatPrimTyCon = text $ show (build x :: Float) diff --git a/testsuite/tests/ghci.debugger/scripts/all.T b/testsuite/tests/ghci.debugger/scripts/all.T index 9e533aa..d62dcd9 100644 --- a/testsuite/tests/ghci.debugger/scripts/all.T +++ b/testsuite/tests/ghci.debugger/scripts/all.T @@ -21,8 +21,7 @@ test('print018', extra_files(['../Test.hs']), ghci_script, ['print018.script']) test('print019', extra_files(['../Test.hs']), ghci_script, ['print019.script']) test('print020', extra_files(['../HappyTest.hs']), ghci_script, ['print020.script']) test('print021', normal, ghci_script, ['print021.script']) -test('print022', when(arch('powerpc64'), expect_broken(11262)), - ghci_script, ['print022.script']) +test('print022', normal, ghci_script, ['print022.script']) test('print023', extra_files(['../Test.hs']), ghci_script, ['print023.script']) test('print024', extra_files(['../Test.hs']), ghci_script, ['print024.script']) test('print025', normal, ghci_script, ['print025.script']) From git at git.haskell.org Mon Oct 16 23:14:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 23:14:43 +0000 (UTC) Subject: [commit: ghc] master: updateThunk: indirectee can be tagged (aa98268) Message-ID: <20171016231443.B6C893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aa982685f23b1c723802ec4d574c23950b7d1a50/ghc >--------------------------------------------------------------- commit aa982685f23b1c723802ec4d574c23950b7d1a50 Author: James Clarke Date: Mon Oct 16 17:38:14 2017 -0400 updateThunk: indirectee can be tagged Reviewers: austin, bgamari, erikd, simonmar, trofi Reviewed By: trofi Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4100 >--------------------------------------------------------------- aa982685f23b1c723802ec4d574c23950b7d1a50 rts/Threads.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Threads.c b/rts/Threads.c index 79c86f7..b09dfa8 100644 --- a/rts/Threads.c +++ b/rts/Threads.c @@ -446,7 +446,7 @@ updateThunk (Capability *cap, StgTSO *tso, StgClosure *thunk, StgClosure *val) return; } - v = ((StgInd*)thunk)->indirectee; + v = UNTAG_CLOSURE(((StgInd*)thunk)->indirectee); updateWithIndirection(cap, thunk, val); From git at git.haskell.org Mon Oct 16 23:14:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Oct 2017 23:14:46 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Clarify -ddump-asm-regalloc-stages documentation (21b7057) Message-ID: <20171016231446.7489F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/21b7057e958551fb6bf8c832491345c4f6e7f44f/ghc >--------------------------------------------------------------- commit 21b7057e958551fb6bf8c832491345c4f6e7f44f Author: Ben Gamari Date: Mon Oct 16 17:54:38 2017 -0400 users-guide: Clarify -ddump-asm-regalloc-stages documentation [skip ci] >--------------------------------------------------------------- 21b7057e958551fb6bf8c832491345c4f6e7f44f docs/users_guide/debugging.rst | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/debugging.rst b/docs/users_guide/debugging.rst index d33c8b4..52abd74 100644 --- a/docs/users_guide/debugging.rst +++ b/docs/users_guide/debugging.rst @@ -477,10 +477,12 @@ assembler. Dump the result of the register allocation pass. .. ghc-flag:: -ddump-asm-regalloc-stages - :shortdesc: Dump the build/spill stages of the register allocator. + :shortdesc: Dump the build/spill stages of the :ghc-flag:`-fregs-graph` + register allocator. :type: dynamic - Dump the build/spill stages of the register allocator. + Dump the build/spill stages of the :ghc-flag:`-fregs-graph` register + allocator. .. ghc-flag:: -ddump-asm-stats :shortdesc: Dump statistics from the register allocator. From git at git.haskell.org Tue Oct 17 06:51:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 06:51:14 +0000 (UTC) Subject: [commit: ghc] branch 'wip/tdammers-7258' created Message-ID: <20171017065114.293C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/tdammers-7258 Referencing: 19a2ba3ea436b60466fc4022f53a6631e41b87a5 From git at git.haskell.org Tue Oct 17 06:51:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 06:51:16 +0000 (UTC) Subject: [commit: ghc] wip/tdammers-7258: Performance improvements linear regAlloc (#7258) (19a2ba3) Message-ID: <20171017065116.E41063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers-7258 Link : http://ghc.haskell.org/trac/ghc/changeset/19a2ba3ea436b60466fc4022f53a6631e41b87a5/ghc >--------------------------------------------------------------- commit 19a2ba3ea436b60466fc4022f53a6631e41b87a5 Author: Tobias Dammers Date: Mon Oct 16 14:27:40 2017 +0200 Performance improvements linear regAlloc (#7258) >--------------------------------------------------------------- 19a2ba3ea436b60466fc4022f53a6631e41b87a5 compiler/nativeGen/RegAlloc/Linear/Main.hs | 24 +++++++++++++----------- 1 file changed, 13 insertions(+), 11 deletions(-) diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs index 171ce88..6171d8d 100644 --- a/compiler/nativeGen/RegAlloc/Linear/Main.hs +++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs @@ -809,27 +809,29 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc -- case (3): we need to push something out to free up a register [] -> - do let keep' = map getUnique keep + do let inRegOrBoth (InReg _) = True + inRegOrBoth (InBoth _ _) = True + inRegOrBoth _ = False + let candidates' = + flip delListFromUFM keep $ + filterUFM inRegOrBoth $ + assig + -- This is non-deterministic but we do not + -- currently support deterministic code-generation. + -- See Note [Unique Determinism and code generation] + let candidates = nonDetUFMToList candidates' -- the vregs we could kick out that are already in a slot let candidates_inBoth = [ (temp, reg, mem) - | (temp, InBoth reg mem) <- nonDetUFMToList assig - -- This is non-deterministic but we do not - -- currently support deterministic code-generation. - -- See Note [Unique Determinism and code generation] - , temp `notElem` keep' + | (temp, InBoth reg mem) <- candidates , targetClassOfRealReg platform reg == classOfVirtualReg r ] -- the vregs we could kick out that are only in a reg -- this would require writing the reg to a new slot before using it. let candidates_inReg = [ (temp, reg) - | (temp, InReg reg) <- nonDetUFMToList assig - -- This is non-deterministic but we do not - -- currently support deterministic code-generation. - -- See Note [Unique Determinism and code generation] - , temp `notElem` keep' + | (temp, InReg reg) <- candidates , targetClassOfRealReg platform reg == classOfVirtualReg r ] let result From git at git.haskell.org Tue Oct 17 06:51:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 06:51:19 +0000 (UTC) Subject: [commit: ghc] wip/tdammers-7258: Make layLeft and reduceDoc stricter (#7258) (375d4bd) Message-ID: <20171017065119.A70F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers-7258 Link : http://ghc.haskell.org/trac/ghc/changeset/375d4bd0fc2afd72617bc827bf63b5eeb24f2f7c/ghc >--------------------------------------------------------------- commit 375d4bd0fc2afd72617bc827bf63b5eeb24f2f7c Author: Tobias Dammers Date: Mon Oct 16 11:33:01 2017 +0200 Make layLeft and reduceDoc stricter (#7258) >--------------------------------------------------------------- 375d4bd0fc2afd72617bc827bf63b5eeb24f2f7c compiler/utils/Pretty.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/compiler/utils/Pretty.hs b/compiler/utils/Pretty.hs index 78c8e6a..f4987d3 100644 --- a/compiler/utils/Pretty.hs +++ b/compiler/utils/Pretty.hs @@ -433,8 +433,8 @@ maybeParens True = parens -- | Perform some simplification of a built up @GDoc at . reduceDoc :: Doc -> RDoc -reduceDoc (Beside p g q) = beside p g (reduceDoc q) -reduceDoc (Above p g q) = above p g (reduceDoc q) +reduceDoc (Beside p g q) = p `seq` g `seq` (beside p g $! reduceDoc q) +reduceDoc (Above p g q) = p `seq` g `seq` (above p g $! reduceDoc q) reduceDoc p = p -- | List version of '<>'. @@ -1032,11 +1032,11 @@ bufLeftRender b doc = layLeft b (reduceDoc doc) layLeft :: BufHandle -> Doc -> IO () layLeft b _ | b `seq` False = undefined -- make it strict in b layLeft _ NoDoc = error "layLeft: NoDoc" -layLeft b (Union p q) = layLeft b (first p q) -layLeft b (Nest _ p) = layLeft b p +layLeft b (Union p q) = layLeft b $! first p q +layLeft b (Nest _ p) = layLeft b $! p layLeft b Empty = bPutChar b '\n' -layLeft b (NilAbove p) = bPutChar b '\n' >> layLeft b p -layLeft b (TextBeside s _ p) = put b s >> layLeft b p +layLeft b (NilAbove p) = p `seq` (bPutChar b '\n' >> layLeft b p) +layLeft b (TextBeside s _ p) = s `seq` (put b s >> layLeft b p) where put b _ | b `seq` False = undefined put b (Chr c) = bPutChar b c From git at git.haskell.org Tue Oct 17 07:51:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 07:51:40 +0000 (UTC) Subject: [commit: ghc] master: Bump ghc-prim to 0.5.2.0 and update changelog (6cb4642) Message-ID: <20171017075140.D9EE83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6cb46421de6a0f97ca1c8103c19df478f07612d7/ghc >--------------------------------------------------------------- commit 6cb46421de6a0f97ca1c8103c19df478f07612d7 Author: Herbert Valerio Riedel Date: Tue Oct 17 00:35:45 2017 +0200 Bump ghc-prim to 0.5.2.0 and update changelog This is prompted by the addition of `compareByteArrays#` in e3ba26f8b49700b41ff4672f3f7f6a4e453acdcc NOTE: We may switch to synchronise `ghc-prim` with GHC's version at some point >--------------------------------------------------------------- 6cb46421de6a0f97ca1c8103c19df478f07612d7 libraries/ghc-compact/ghc-compact.cabal | 2 +- libraries/ghc-prim/changelog.md | 12 +++++++++++- libraries/ghc-prim/ghc-prim.cabal | 2 +- testsuite/tests/ado/ado004.stderr | 2 +- testsuite/tests/backpack/should_compile/bkp16.stderr | 2 +- testsuite/tests/determinism/determ021/determ021.stdout | 4 ++-- testsuite/tests/driver/json2.stderr | 4 ++-- testsuite/tests/indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr | 2 +- .../tests/partial-sigs/should_compile/BoolToBool.stderr | 2 +- .../partial-sigs/should_compile/DataFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/Defaulting1MROn.stderr | 2 +- .../partial-sigs/should_compile/Defaulting2MROff.stderr | 2 +- .../tests/partial-sigs/should_compile/Defaulting2MROn.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Either.stderr | 2 +- .../partial-sigs/should_compile/EqualityConstraint.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Every.stderr | 2 +- .../tests/partial-sigs/should_compile/EveryNamed.stderr | 2 +- .../tests/partial-sigs/should_compile/ExpressionSig.stderr | 2 +- .../partial-sigs/should_compile/ExpressionSigNamed.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints1.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints2.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints3.stderr | 2 +- .../tests/partial-sigs/should_compile/ExtraNumAMROff.stderr | 2 +- .../tests/partial-sigs/should_compile/ExtraNumAMROn.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Forall1.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr | 2 +- .../tests/partial-sigs/should_compile/HigherRank1.stderr | 2 +- .../tests/partial-sigs/should_compile/HigherRank2.stderr | 2 +- .../partial-sigs/should_compile/LocalDefinitionBug.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- .../tests/partial-sigs/should_compile/MonoLocalBinds.stderr | 2 +- .../tests/partial-sigs/should_compile/NamedTyVar.stderr | 2 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 2 +- .../NamedWildcardInTypeFamilyInstanceLHS.stderr | 2 +- .../partial-sigs/should_compile/ParensAroundContext.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/PatBind.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr | 2 +- .../tests/partial-sigs/should_compile/PatternSig.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Recursive.stderr | 2 +- .../partial-sigs/should_compile/ScopedNamedWildcards.stderr | 2 +- .../should_compile/ScopedNamedWildcardsGood.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- .../partial-sigs/should_compile/SomethingShowable.stderr | 2 +- .../partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr | 2 +- .../tests/partial-sigs/should_compile/UncurryNamed.stderr | 2 +- .../should_compile/WarningWildcardInstantiations.stderr | 2 +- testsuite/tests/roles/should_compile/Roles1.stderr | 2 +- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 2 +- testsuite/tests/roles/should_compile/Roles3.stderr | 2 +- testsuite/tests/roles/should_compile/Roles4.stderr | 2 +- testsuite/tests/roles/should_compile/T8958.stderr | 2 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- testsuite/tests/typecheck/should_compile/T12763.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 2 +- 65 files changed, 77 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 6cb46421de6a0f97ca1c8103c19df478f07612d7 From git at git.haskell.org Tue Oct 17 12:09:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 12:09:44 +0000 (UTC) Subject: [commit: ghc] master: Simplify, no functionality change (ed48d13) Message-ID: <20171017120944.53C423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ed48d133f9b9e41ea6d5dc254f257eeb12ad00b7/ghc >--------------------------------------------------------------- commit ed48d133f9b9e41ea6d5dc254f257eeb12ad00b7 Author: Gabor Greif Date: Tue Oct 17 12:37:25 2017 +0200 Simplify, no functionality change >--------------------------------------------------------------- ed48d133f9b9e41ea6d5dc254f257eeb12ad00b7 compiler/codeGen/StgCmmExpr.hs | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index 95dcc9f..3fcc935 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -616,13 +616,12 @@ cgAlts gc_plan bndr (AlgAlt tycon) alts branches' = [(tag+1,branch) | (tag,branch) <- branches] emitSwitch tag_expr branches' mb_deflt 1 fam_sz - else -- No, get tag from info table - do dflags <- getDynFlags - let -- Note that ptr _always_ has tag 1 - -- when the family size is big enough - untagged_ptr = cmmRegOffB bndr_reg (-1) - tag_expr = getConstrTag dflags (untagged_ptr) - emitSwitch tag_expr branches mb_deflt 0 (fam_sz - 1) + else -- No, get tag from info table + let -- Note that ptr _always_ has tag 1 + -- when the family size is big enough + untagged_ptr = cmmRegOffB bndr_reg (-1) + tag_expr = getConstrTag dflags (untagged_ptr) + in emitSwitch tag_expr branches mb_deflt 0 (fam_sz - 1) ; return AssignedDirectly } From git at git.haskell.org Tue Oct 17 12:09:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 12:09:47 +0000 (UTC) Subject: [commit: ghc] master: Fix grammaros in comments (2f43615) Message-ID: <20171017120947.14D663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2f436151f4810b67d10c7d208fa81bef6e53d490/ghc >--------------------------------------------------------------- commit 2f436151f4810b67d10c7d208fa81bef6e53d490 Author: Gabor Greif Date: Tue Oct 17 13:44:13 2017 +0200 Fix grammaros in comments >--------------------------------------------------------------- 2f436151f4810b67d10c7d208fa81bef6e53d490 compiler/simplCore/CSE.hs | 2 +- compiler/stranal/DmdAnal.hs | 2 +- docs/users_guide/debugging.rst | 2 +- libraries/ghc-boot/GHC/PackageDb.hs | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/simplCore/CSE.hs b/compiler/simplCore/CSE.hs index 16dd64c..65b9af9 100644 --- a/compiler/simplCore/CSE.hs +++ b/compiler/simplCore/CSE.hs @@ -213,7 +213,7 @@ WorkWrap (see Note [Wrapper activation]). We can tell because noUserInlineSpec is then true. Note that we do not (currently) do CSE on the unfolding stored inside -an Id, even if is a 'stable' unfolding. That means that when an +an Id, even if it is a 'stable' unfolding. That means that when an unfolding happens, it is always faithful to what the stable unfolding originally was. diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index 44adc81..77da307 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -401,7 +401,7 @@ situation actually arises in GHC.IO.Handle.Internals.wantReadableHandle So if the scrutinee is a primop call, we *don't* apply the state hack: - - If is a simple, terminating one like getMaskingState, + - If it is a simple, terminating one like getMaskingState, applying the hack is over-conservative. - If the primop is raise# then it returns bottom, so the case alternatives are already discarded. diff --git a/docs/users_guide/debugging.rst b/docs/users_guide/debugging.rst index 52abd74..0096c71 100644 --- a/docs/users_guide/debugging.rst +++ b/docs/users_guide/debugging.rst @@ -49,7 +49,7 @@ Dumping out compiler intermediate structures be a bit more eager in forcing pass results to more accurately account for their costs. - Two types of messages are produced: Those beginning with ``***`` are + Two types of messages are produced: Those beginning with ``***`` do denote the beginning of a compilation phase whereas those starting with ``!!!`` mark the end of a pass and are accompanied by allocation and runtime statistics. diff --git a/libraries/ghc-boot/GHC/PackageDb.hs b/libraries/ghc-boot/GHC/PackageDb.hs index a59c46e..e2e4694 100644 --- a/libraries/ghc-boot/GHC/PackageDb.hs +++ b/libraries/ghc-boot/GHC/PackageDb.hs @@ -249,7 +249,7 @@ lockPackageDbWith mode file = do -- opened for write access. We would previously try opening the lockfile for -- read-only access first, however this failed when run on such filesystems. -- Consequently, we now try read-write access first, falling back to read-only - -- if are denied permission (e.g. in the case of a global database). + -- if we are denied permission (e.g. in the case of a global database). catchJust (\e -> if isPermissionError e then Just () else Nothing) (lockFileOpenIn ReadWriteMode) From git at git.haskell.org Tue Oct 17 13:02:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 13:02:19 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Bring in (Unused) NewPat constructor (29eb240) Message-ID: <20171017130219.789DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/29eb2407a53b25281fdfd5d5f7fc9a695675bae8/ghc >--------------------------------------------------------------- commit 29eb2407a53b25281fdfd5d5f7fc9a695675bae8 Author: Alan Zimmerman Date: Tue Oct 17 11:43:56 2017 +0200 Bring in (Unused) NewPat constructor >--------------------------------------------------------------- 29eb2407a53b25281fdfd5d5f7fc9a695675bae8 compiler/deSugar/Check.hs | 1 + compiler/deSugar/DsArrows.hs | 1 + compiler/hsSyn/HsExtension.hs | 30 +++++++++++++++++++++--------- compiler/hsSyn/HsPat.hs | 13 ++++++++++++- compiler/hsSyn/HsTypes.hs | 2 +- compiler/hsSyn/HsUtils.hs | 1 + compiler/typecheck/TcPatSyn.hs | 2 ++ 7 files changed, 39 insertions(+), 11 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 3a2406e..bb05256 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -829,6 +829,7 @@ translatePat fam_insts pat = case pat of ConPatIn {} -> panic "Check.translatePat: ConPatIn" SplicePat {} -> panic "Check.translatePat: SplicePat" SigPatIn {} -> panic "Check.translatePat: SigPatIn" + NewPat {} -> panic "Check.translatePat: NewPat" -- | Translate an overloaded literal (see `tidyNPat' in deSugar/MatchLit.hs) translateNPat :: FamInstEnvs diff --git a/compiler/deSugar/DsArrows.hs b/compiler/deSugar/DsArrows.hs index d12c733..5c69bfd 100644 --- a/compiler/deSugar/DsArrows.hs +++ b/compiler/deSugar/DsArrows.hs @@ -1212,6 +1212,7 @@ collectl (L _ pat) bndrs go (CoPat _ _ pat _) = collectl (noLoc pat) bndrs go (ViewPat _ _ pat) = collectl pat bndrs go p@(SplicePat {}) = pprPanic "collectl/go" (ppr p) + go p@(NewPat {}) = pprPanic "collectl/go" (ppr p) collectEvBinders :: TcEvBinds -> [Id] collectEvBinders (EvBinds bs) = foldrBag add_ev_bndr [] bs diff --git a/compiler/hsSyn/HsExtension.hs b/compiler/hsSyn/HsExtension.hs index 56d52ad..2bea25b 100644 --- a/compiler/hsSyn/HsExtension.hs +++ b/compiler/hsSyn/HsExtension.hs @@ -67,17 +67,17 @@ type NoConExt = Void -- | A data type index stating "there are no field extensions" -- see "Trees that Grow" type NoFieldExt = () -pattern - NoFieldExt :: NoFieldExt -pattern - NoFieldExt = () +-- pattern +-- NoFieldExt :: NoFieldExt +-- pattern +-- NoFieldExt = () -- | A data type index for pass `x` of GHC -data GHC x +-- data GHC x -- TODO: unify `GHC` and `Ghcpass` by making `GhcTcId` part of `Ghcpass` -deriving instance Data x => Data (GHC x) +-- deriving instance Data x => Data (GHC x) -- | Used as a data type index for the hsSyn AST @@ -160,7 +160,7 @@ type ForallXPat (c :: * -> Constraint) (x :: *) = , c (XNPlusKPat x) , c (XSigPat x) , c (XCoPat x) - -- , c (XNewPat x) + , c (XNewPat x) ) -- --------------------------------------------------------------------- -- ValBindsLR type families @@ -345,8 +345,8 @@ type ConvertIdX a b = -- ---------------------------------------------------------------------- --- | Provide a summary constraint that gives all extension points a Monoid --- constraint. +-- | Provide a summary constraint that gives all a Monoid constraint to +-- extension points needing one type MonoidX p = ( Monoid (XBangPat p) , Monoid (XParPat p) @@ -354,10 +354,21 @@ type MonoidX p = , Monoid (XVarPat p) , Monoid (XLitPat p) , Monoid (XCoPat p) + , Monoid (XNewPat p) ) -- ---------------------------------------------------------------------- +-- | Provide a summary constraint that gives all am Outputable constraint to +-- extension points needing one +type OutputableX p = + ( Outputable (XNewPat p) + , Outputable (XNewPat GhcRn) + ) +-- TODO: Should OutputableX be included in OutputableBndrId? + +-- ---------------------------------------------------------------------- + -- type DataId p = ( Data p @@ -404,4 +415,5 @@ type DataIdLR pL pR = type OutputableBndrId id = ( OutputableBndr (NameOrRdrName (IdP id)) , OutputableBndr (IdP id) + , OutputableX id ) diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index 75a07e6..129da56 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -282,6 +282,10 @@ data Pat p -- During desugaring a (CoPat co pat) turns into a cast with 'co' on -- the scrutinee, followed by a match on 'pat' -- ^ Coercion Pattern + + -- | Trees that Grow extension point for new constructors + | NewPat + (XNewPat p) deriving instance (DataId p) => Data (Pat p) -- | The typechecker-specific information for a 'ListPat' @@ -362,6 +366,10 @@ type instance XSigPat GhcTc = NoFieldExt type instance XCoPat GhcPs = NoFieldExt type instance XCoPat GhcRn = NoFieldExt type instance XCoPat GhcTc = NoFieldExt + +type instance XNewPat GhcPs = NoFieldExt +type instance XNewPat GhcRn = NoFieldExt +type instance XNewPat GhcTc = NoFieldExt {- type instance XConPat (GhcPass pass) = NoFieldExt @@ -598,7 +606,7 @@ pprPat (ConPatOut { pat_con = con, pat_tvs = tvs, pat_dicts = dicts, , ppr binds]) <+> pprConArgs details else pprUserCon (unLoc con) details - +pprPat (NewPat x) = ppr x pprUserCon :: (SourceTextX p, OutputableBndr con, OutputableBndrId p) => con -> HsConPatDetails p -> SDoc @@ -758,6 +766,8 @@ isIrrefutableHsPat pat -- since we cannot know until the splice is evaluated. go1 (SplicePat {}) = False + go1 (NewPat {}) = False + {- Note [Unboxed sum patterns aren't irrefutable] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Unlike unboxed tuples, unboxed sums are *not* irrefutable when used as @@ -801,6 +811,7 @@ hsPatNeedsParens (ListPat {}) = False hsPatNeedsParens (PArrPat {}) = False hsPatNeedsParens (LitPat {}) = False hsPatNeedsParens (NPat {}) = False +hsPatNeedsParens (NewPat {}) = True -- conservative default conPatNeedsParens :: HsConDetails a b -> Bool conPatNeedsParens (PrefixCon {}) = False diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs index 56b7d24..ed54759 100644 --- a/compiler/hsSyn/HsTypes.hs +++ b/compiler/hsSyn/HsTypes.hs @@ -789,7 +789,7 @@ instance (Outputable arg, Outputable rec) -- parser and rejigs them using information about fixities from the renamer. -- See Note [Sorting out the result type] in RdrHsSyn updateGadtResult - :: (Monad m) + :: (Monad m, OutputableX GhcRn) => (SDoc -> m ()) -> SDoc -> HsConDetails (LHsType GhcRn) (Located [LConDeclField GhcRn]) diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index b6e29c9..0c298e9 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -981,6 +981,7 @@ collect_lpat (L _ pat) bndrs = go pat go (SplicePat _ _) = bndrs go (CoPat _ _ pat _) = go pat + go (NewPat {}) = bndrs {- Note [Dictionary binders in ConPatOut] See also same Note in DsArrows diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index d4bbc12..ea023ff 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -698,6 +698,7 @@ tcPatToExpr name args pat = go pat go1 p@(AsPat {}) = notInvertible p go1 p@(ViewPat {}) = notInvertible p go1 p@(NPlusKPat {}) = notInvertible p + go1 p@(NewPat {}) = notInvertible p go1 p@(SplicePat _ (HsTypedSplice {})) = notInvertible p go1 p@(SplicePat _ (HsUntypedSplice {})) = notInvertible p go1 p@(SplicePat _ (HsQuasiQuote {})) = notInvertible p @@ -824,6 +825,7 @@ tcCheckPatSynPat = go go1 ConPatOut{} = panic "ConPatOut in output of renamer" go1 SigPatOut{} = panic "SigPatOut in output of renamer" go1 CoPat{} = panic "CoPat in output of renamer" + go1 NewPat{} = panic "NewPat in output of renamer" asPatInPatSynErr :: (SourceTextX p, OutputableBndrId p) => Pat p -> TcM a asPatInPatSynErr pat From git at git.haskell.org Tue Oct 17 13:02:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 13:02:22 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Clean up, based on @simonpj feedback (d694ac8) Message-ID: <20171017130222.6598F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/d694ac80954056a5c14e4785ca5f973cd4efbb9b/ghc >--------------------------------------------------------------- commit d694ac80954056a5c14e4785ca5f973cd4efbb9b Author: Alan Zimmerman Date: Tue Oct 17 15:01:02 2017 +0200 Clean up, based on @simonpj feedback Updates haddock submodule Tests now pass, HsPat fully implemented for TTG. >--------------------------------------------------------------- d694ac80954056a5c14e4785ca5f973cd4efbb9b compiler/hsSyn/HsBinds.hs | 3 +- compiler/hsSyn/HsExtension.hs | 17 ----- compiler/hsSyn/HsPat.hs | 68 +++-------------- compiler/hsSyn/PlaceHolder.hs | 3 + .../parser/should_compile/DumpRenamedAst.stderr | 87 +++++++++++----------- .../tests/parser/should_compile/T14189.stderr | 7 +- testsuite/tests/quasiquotation/T7918.hs | 2 +- utils/haddock | 2 +- 8 files changed, 66 insertions(+), 123 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 d694ac80954056a5c14e4785ca5f973cd4efbb9b From git at git.haskell.org Tue Oct 17 15:21:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 15:21:39 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Get rid of SigPatIn / SigPatOut (95211f5) Message-ID: <20171017152139.246703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/95211f59a9b457287a6a754a8bd2b39dbf961364/ghc >--------------------------------------------------------------- commit 95211f59a9b457287a6a754a8bd2b39dbf961364 Author: Alan Zimmerman Date: Tue Oct 17 17:21:07 2017 +0200 Get rid of SigPatIn / SigPatOut >--------------------------------------------------------------- 95211f59a9b457287a6a754a8bd2b39dbf961364 compiler/deSugar/Check.hs | 3 +-- compiler/deSugar/DsArrows.hs | 3 +-- compiler/deSugar/DsMeta.hs | 6 +++--- compiler/deSugar/Match.hs | 6 +++--- compiler/hsSyn/Convert.hs | 2 +- compiler/hsSyn/HsExtension.hs | 2 ++ compiler/hsSyn/HsPat.hs | 41 +++++++++++++++++++++-------------------- compiler/hsSyn/HsUtils.hs | 6 ++---- compiler/parser/RdrHsSyn.hs | 2 +- compiler/rename/RnExpr.hs | 3 +-- compiler/rename/RnPat.hs | 4 ++-- compiler/typecheck/TcHsSyn.hs | 6 +++--- compiler/typecheck/TcPat.hs | 4 ++-- compiler/typecheck/TcPatSyn.hs | 8 +++----- utils/ghctags/Main.hs | 3 +-- 15 files changed, 47 insertions(+), 52 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 95211f59a9b457287a6a754a8bd2b39dbf961364 From git at git.haskell.org Tue Oct 17 20:55:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 20:55:50 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Update HsLit for current TTG implementation. (05622d2) Message-ID: <20171017205550.5249D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/05622d2d15317f15f2d3f8bdd63fa08d238de372/ghc >--------------------------------------------------------------- commit 05622d2d15317f15f2d3f8bdd63fa08d238de372 Author: Alan Zimmerman Date: Tue Oct 17 22:55:11 2017 +0200 Update HsLit for current TTG implementation. >--------------------------------------------------------------- 05622d2d15317f15f2d3f8bdd63fa08d238de372 compiler/deSugar/MatchLit.hs | 2 ++ compiler/hsSyn/HsExtension.hs | 53 +++++++------------------------------------ compiler/hsSyn/HsLit.hs | 25 ++++++++++++++++++-- compiler/hsSyn/HsTypes.hs | 1 + compiler/typecheck/TcHsSyn.hs | 6 +++-- 5 files changed, 38 insertions(+), 49 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 05622d2d15317f15f2d3f8bdd63fa08d238de372 From git at git.haskell.org Tue Oct 17 21:42:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Oct 2017 21:42:37 +0000 (UTC) Subject: [commit: ghc] master: Improve user’s guide around deriving (317aa96) Message-ID: <20171017214237.30C703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/317aa966b3d89e45227a5870feba339e34d77a18/ghc >--------------------------------------------------------------- commit 317aa966b3d89e45227a5870feba339e34d77a18 Author: Joachim Breitner Date: Tue Oct 17 17:34:25 2017 -0400 Improve user’s guide around deriving In particular: * add an intro to “10.6. Extensions to the “deriving” mechanism” giving an overview, * make the various sections on `-XDerivingFoo` subsections of “10.6.3. Deriving instances of extra classes (Data, etc.)” * Move the reference anchors for the various `DerivingFoo` extensions to a more appropriate spot. * Add subsection “10.6.6.1. Default deriving strategy” to the deriving section (#14357) >--------------------------------------------------------------- 317aa966b3d89e45227a5870feba339e34d77a18 docs/users_guide/glasgow_exts.rst | 185 ++++++++++++++++++++++++-------------- 1 file changed, 120 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 317aa966b3d89e45227a5870feba339e34d77a18 From git at git.haskell.org Wed Oct 18 08:37:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Oct 2017 08:37:54 +0000 (UTC) Subject: [commit: ghc] master: Better solving for representational equalities (5a66d57) Message-ID: <20171018083754.52B613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5a66d574890ed09859ca912c9e0969dba72f4a23/ghc >--------------------------------------------------------------- commit 5a66d574890ed09859ca912c9e0969dba72f4a23 Author: Simon Peyton Jones Date: Tue Oct 17 16:32:25 2017 +0100 Better solving for representational equalities This patch adds a bit of extra solving power for representational equality constraints to fix Trac #14333 The main changes: * Fix a buglet in TcType.isInsolubleOccursCheck which wrongly reported a definite occurs-check error for (a ~R# b a) * Get rid of TcSMonad.emitInsolubles. It had an ad-hoc duplicate-removal piece that is better handled in interactIrred, now that insolubles are Irreds. We need a little care to keep inert_count (which does not include insolubles) accurate. * Refactor TcInteract.solveOneFromTheOther, to return a much simpler type. It was just over-complicated before. * Make TcInteract.interactIrred look for constraints that match either way around, in TcInteract.findMatchingIrreds This wasn't hard and it cleaned up quite a bit of code. >--------------------------------------------------------------- 5a66d574890ed09859ca912c9e0969dba72f4a23 compiler/typecheck/TcCanonical.hs | 14 +- compiler/typecheck/TcInteract.hs | 257 ++++++++++++++------- compiler/typecheck/TcSMonad.hs | 91 ++------ compiler/typecheck/TcType.hs | 16 +- testsuite/tests/typecheck/should_compile/T14333.hs | 20 ++ testsuite/tests/typecheck/should_compile/all.T | 1 + .../typecheck/should_fail/FrozenErrorTests.hs | 0 7 files changed, 236 insertions(+), 163 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 5a66d574890ed09859ca912c9e0969dba72f4a23 From git at git.haskell.org Wed Oct 18 08:37:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Oct 2017 08:37:57 +0000 (UTC) Subject: [commit: ghc] master: Don't deeply expand insolubles (74cd1be) Message-ID: <20171018083757.60AF23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/74cd1be0b2778ad99566cde085328bde2090294a/ghc >--------------------------------------------------------------- commit 74cd1be0b2778ad99566cde085328bde2090294a Author: Simon Peyton Jones Date: Tue Oct 17 16:30:33 2017 +0100 Don't deeply expand insolubles Trac #13450 went bananas if we expand insoluble constraints. Better just to leave them un-expanded. I'm not sure in detail about why it goes so badly wrong; but regardless, the less we mess around with insoluble contraints the better the error messages will be. >--------------------------------------------------------------- 74cd1be0b2778ad99566cde085328bde2090294a compiler/typecheck/TcCanonical.hs | 22 ++++++--- testsuite/tests/typecheck/should_fail/T14350.hs | 59 +++++++++++++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 76 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 8d4d2a0..39f2def 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -86,7 +86,7 @@ canonicalize (CNonCanonical { cc_ev = ev }) EqPred eq_rel ty1 ty2 -> do traceTcS "canEvNC:eq" (ppr ty1 $$ ppr ty2) canEqNC ev eq_rel ty1 ty2 IrredPred {} -> do traceTcS "canEvNC:irred" (ppr (ctEvPred ev)) - canIrred ev + canIrred ev canonicalize (CIrredCan { cc_ev = ev }) = canIrred ev @@ -486,17 +486,27 @@ mk_strict_superclasses rec_clss ev cls tys canIrred :: CtEvidence -> TcS (StopOrContinue Ct) -- Precondition: ty not a tuple and no other evidence form -canIrred old_ev - = do { let old_ty = ctEvPred old_ev - ; traceTcS "can_pred" (text "IrredPred = " <+> ppr old_ty) - ; (xi,co) <- flatten FM_FlattenAll old_ev old_ty -- co :: xi ~ old_ty - ; rewriteEvidence old_ev xi co `andWhenContinue` \ new_ev -> +canIrred ev + | EqPred eq_rel ty1 ty2 <- classifyPredType pred + = -- For insolubles (all of which are equalities, do /not/ flatten the arguments + -- In Trac #14350 doing so led entire-unnecessary and ridiculously large + -- type function expansion. Instead, canEqNC just applies + -- the substitution to the predicate, and may do decomposition; + -- e.g. a ~ [a], where [G] a ~ [Int], can decompose + canEqNC ev eq_rel ty1 ty2 + + | otherwise + = do { traceTcS "can_pred" (text "IrredPred = " <+> ppr pred) + ; (xi,co) <- flatten FM_FlattenAll ev pred -- co :: xi ~ pred + ; rewriteEvidence ev xi co `andWhenContinue` \ new_ev -> do { -- Re-classify, in case flattening has improved its shape ; case classifyPredType (ctEvPred new_ev) of ClassPred cls tys -> canClassNC new_ev cls tys EqPred eq_rel ty1 ty2 -> canEqNC new_ev eq_rel ty1 ty2 _ -> continueWith $ mkIrredCt new_ev } } + where + pred = ctEvPred ev canHole :: CtEvidence -> Hole -> TcS (StopOrContinue Ct) canHole ev hole diff --git a/testsuite/tests/typecheck/should_fail/T14350.hs b/testsuite/tests/typecheck/should_fail/T14350.hs new file mode 100644 index 0000000..b3de40f --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14350.hs @@ -0,0 +1,59 @@ +{-# LANGUAGE AllowAmbiguousTypes #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE TypeOperators #-} +module T14350 where + +import Data.Kind + +data Proxy a = Proxy +data family Sing (a :: k) + +data SomeSing k where + SomeSing :: Sing (a :: k) -> SomeSing k + +class SingKind k where + type Demote k :: Type + fromSing :: Sing (a :: k) -> Demote k + toSing :: Demote k -> SomeSing k + +data instance Sing (x :: Proxy k) where + SProxy :: Sing 'Proxy + +instance SingKind (Proxy k) where + type Demote (Proxy k) = Proxy k + fromSing SProxy = Proxy + toSing Proxy = SomeSing SProxy + +data TyFun :: Type -> Type -> Type +type a ~> b = TyFun a b -> Type +infixr 0 ~> + +type family Apply (f :: k1 ~> k2) (x :: k1) :: k2 +type a @@ b = Apply a b +infixl 9 @@ + +newtype instance Sing (f :: k1 ~> k2) = + SLambda { applySing :: forall t. Sing t -> Sing (f @@ t) } + +instance (SingKind k1, SingKind k2) => SingKind (k1 ~> k2) where + type Demote (k1 ~> k2) = Demote k1 -> Demote k2 + fromSing sFun x = case toSing x of SomeSing y -> fromSing (applySing sFun y) + toSing = undefined + +dcomp :: forall (a :: Type) + (b :: a ~> Type) + (c :: forall (x :: a). Proxy x ~> b @@ x ~> Type) + (f :: forall (x :: a) (y :: b @@ x). Proxy x ~> Proxy y ~> c @@ ('Proxy :: Proxy x) @@ y) + (g :: forall (x :: a). Proxy x ~> b @@ x) + (x :: a). + Sing f + -> Sing g + -> Sing x + -> c @@ ('Proxy :: Proxy x) @@ (g @@ ('Proxy :: Proxy x)) +dcomp f g x = applySing f Proxy Proxy diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 381e2c5..1aa23c4 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -459,3 +459,4 @@ test('T13909', normal, compile_fail, ['']) test('T13929', normal, compile_fail, ['']) test('T14232', normal, compile_fail, ['']) test('T14325', normal, compile_fail, ['']) +test('T14350', normal, compile_fail, ['']) From git at git.haskell.org Wed Oct 18 13:46:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Oct 2017 13:46:33 +0000 (UTC) Subject: [commit: ghc] wip/tdammers-7258: Factor out readField (#14364) (a6dd03e) Message-ID: <20171018134633.DB8FE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers-7258 Link : http://ghc.haskell.org/trac/ghc/changeset/a6dd03e751d17467be10eea3ff1b1773d8d35893/ghc >--------------------------------------------------------------- commit a6dd03e751d17467be10eea3ff1b1773d8d35893 Author: Tobias Dammers Date: Wed Oct 18 15:44:57 2017 +0200 Factor out readField (#14364) Improves compiler performance of deriving Read instances. >--------------------------------------------------------------- a6dd03e751d17467be10eea3ff1b1773d8d35893 compiler/prelude/PrelNames.hs | 4 ++++ compiler/typecheck/TcGenDeriv.hs | 35 ++++++++++++++++++++--------------- libraries/base/GHC/Read.hs | 18 ++++++++++++++++++ 3 files changed, 42 insertions(+), 15 deletions(-) diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index 760aea5..ae695d4 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -742,6 +742,10 @@ choose_RDR = varQual_RDR gHC_READ (fsLit "choose") lexP_RDR = varQual_RDR gHC_READ (fsLit "lexP") expectP_RDR = varQual_RDR gHC_READ (fsLit "expectP") +readField_RDR, readSymField_RDR :: RdrName +readField_RDR = varQual_RDR gHC_READ (fsLit "readField") +readSymField_RDR = varQual_RDR gHC_READ (fsLit "readSymField") + punc_RDR, ident_RDR, symbol_RDR :: RdrName punc_RDR = dataQual_RDR lEX (fsLit "Punc") ident_RDR = dataQual_RDR lEX (fsLit "Ident") diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index 9e27ad5..2d004be 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -1068,21 +1068,26 @@ gen_Read_binds get_fixity loc tycon read_arg a ty = ASSERT( not (isUnliftedType ty) ) noLoc (mkBindStmt (nlVarPat a) (nlHsVarApps step_RDR [readPrec_RDR])) - read_field lbl a = read_lbl lbl ++ - [read_punc "=", - noLoc (mkBindStmt (nlVarPat a) (nlHsVarApps reset_RDR [readPrec_RDR]))] - - -- When reading field labels we might encounter - -- a = 3 - -- _a = 3 - -- or (#) = 4 - -- Note the parens! - read_lbl lbl | isSym lbl_str - = [read_punc "(", symbol_pat lbl_str, read_punc ")"] - | otherwise - = ident_h_pat lbl_str - where - lbl_str = unpackFS lbl + -- When reading field labels we might encounter + -- a = 3 + -- _a = 3 + -- or (#) = 4 + -- Note the parens! + read_field lbl a = + [noLoc + (mkBindStmt + (nlVarPat a) + (nlHsApps + read_field + [nlHsLit (mkHsString lbl_str), nlHsVar readPrec_RDR] + ) + ) + ] + where + lbl_str = unpackFS lbl + read_field + | isSym lbl_str = readSymField_RDR + | otherwise = readField_RDR {- ************************************************************************ diff --git a/libraries/base/GHC/Read.hs b/libraries/base/GHC/Read.hs index ad29cc5..e69e4a0 100644 --- a/libraries/base/GHC/Read.hs +++ b/libraries/base/GHC/Read.hs @@ -36,6 +36,8 @@ module GHC.Read , choose , readListDefault, readListPrecDefault , readNumber + , readField + , readSymField -- Temporary , readParen @@ -359,6 +361,22 @@ choose sps = foldr ((+++) . try_one) pfail sps L.Symbol s' | s==s' -> p _other -> pfail } +readField :: String -> ReadPrec a -> ReadPrec a +readField fieldName readVal = do + expectP (L.Ident fieldName) + expectP (L.Punc "=") + readVal +{-# NOINLINE readField #-} + +readSymField :: String -> ReadPrec a -> ReadPrec a +readSymField fieldName readVal = do + expectP (L.Punc "(") + expectP (L.Symbol fieldName) + expectP (L.Punc ")") + expectP (L.Punc "=") + readVal +{-# NOINLINE readSymField #-} + -------------------------------------------------------------- -- Simple instances of Read -------------------------------------------------------------- From git at git.haskell.org Wed Oct 18 20:43:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Oct 2017 20:43:03 +0000 (UTC) Subject: [commit: ghc] master: Typofix in comment (aba7786) Message-ID: <20171018204303.CDD033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aba7786068aea673af7576a9082b8201036978b3/ghc >--------------------------------------------------------------- commit aba7786068aea673af7576a9082b8201036978b3 Author: Gabor Greif Date: Wed Oct 18 08:49:21 2017 +0200 Typofix in comment >--------------------------------------------------------------- aba7786068aea673af7576a9082b8201036978b3 compiler/cmm/CmmSwitch.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index 53d00de..02a581b 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -109,7 +109,7 @@ data SwitchTargets = (M.Map Integer Label) -- The branches deriving (Show, Eq) --- | The smart constructr mkSwitchTargets normalises the map a bit: +-- | The smart constructor mkSwitchTargets normalises the map a bit: -- * No entries outside the range -- * No entries equal to the default -- * No default if all elements have explicit values From git at git.haskell.org Wed Oct 18 20:43:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Oct 2017 20:43:06 +0000 (UTC) Subject: [commit: ghc] master: whitespace only (870020e) Message-ID: <20171018204306.9501F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/870020e65728dc03f690e80d3caa0717162891a6/ghc >--------------------------------------------------------------- commit 870020e65728dc03f690e80d3caa0717162891a6 Author: Gabor Greif Date: Wed Oct 18 11:47:52 2017 +0200 whitespace only >--------------------------------------------------------------- 870020e65728dc03f690e80d3caa0717162891a6 rts/Compact.cmm | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/rts/Compact.cmm b/rts/Compact.cmm index 72ad4dd..174444d 100644 --- a/rts/Compact.cmm +++ b/rts/Compact.cmm @@ -24,7 +24,7 @@ import CLOSURE base_GHCziIOziException_cannotCompactPinned_closure; hp = StgCompactNFData_hp(compact); \ if (hp + WDS(sizeW) <= StgCompactNFData_hpLim(compact)) { \ to = hp; \ - StgCompactNFData_hp(compact) = hp + WDS(sizeW); \ + StgCompactNFData_hp(compact) = hp + WDS(sizeW); \ } else { \ ("ptr" to) = ccall allocateForCompact( \ MyCapability() "ptr", compact "ptr", sizeW); \ @@ -453,4 +453,3 @@ stg_compactFixupPointerszh ( W_ first_block, W_ root ) gcstr = str; return (gcstr, ok); } - From git at git.haskell.org Wed Oct 18 21:27:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Oct 2017 21:27:31 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Trees that Grow for HsOverLit (571defd) Message-ID: <20171018212731.8E0F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/571defd9bfbcb19aae3b1530f4a64e144eb05d6e/ghc >--------------------------------------------------------------- commit 571defd9bfbcb19aae3b1530f4a64e144eb05d6e Author: Alan Zimmerman Date: Wed Oct 18 23:26:59 2017 +0200 Trees that Grow for HsOverLit >--------------------------------------------------------------- 571defd9bfbcb19aae3b1530f4a64e144eb05d6e compiler/deSugar/Check.hs | 2 +- compiler/deSugar/DsMeta.hs | 1 + compiler/deSugar/MatchLit.hs | 10 +++++----- compiler/hsSyn/Convert.hs | 6 +++--- compiler/hsSyn/HsExtension.hs | 9 +++++++++ compiler/hsSyn/HsLit.hs | 40 ++++++++++++++++++++++++++++++---------- compiler/hsSyn/HsUtils.hs | 14 ++++++-------- compiler/hsSyn/PlaceHolder.hs | 5 ++++- compiler/parser/Parser.y | 6 ++---- compiler/rename/RnExpr.hs | 2 +- compiler/rename/RnPat.hs | 5 ++--- compiler/typecheck/Inst.hs | 12 ++++++------ compiler/typecheck/TcHsSyn.hs | 6 ++++-- 13 files changed, 74 insertions(+), 44 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 571defd9bfbcb19aae3b1530f4a64e144eb05d6e From git at git.haskell.org Thu Oct 19 12:55:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Oct 2017 12:55:26 +0000 (UTC) Subject: [commit: arcanist-external-json-linter] master: Fix handling of code and original fields (957f9e4) Message-ID: <20171019125526.1DB353A5EA@ghc.haskell.org> Repository : ssh://git at ghc/arcanist-external-json-linter On branch : master Link : http://git.haskell.org/arcanist-external-json-linter.git/commitdiff/957f9e4e8eb422dcb72f02f07767a1ed5969baab >--------------------------------------------------------------- commit 957f9e4e8eb422dcb72f02f07767a1ed5969baab Author: Ben Gamari Date: Thu Oct 19 08:54:40 2017 -0400 Fix handling of code and original fields Thanks to @sujeet for pointing this out. >--------------------------------------------------------------- 957f9e4e8eb422dcb72f02f07767a1ed5969baab src/ArcanistExternalJsonLinter.php | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/ArcanistExternalJsonLinter.php b/src/ArcanistExternalJsonLinter.php index 6527f7d..9a09310 100644 --- a/src/ArcanistExternalJsonLinter.php +++ b/src/ArcanistExternalJsonLinter.php @@ -179,14 +179,14 @@ final class ArcanistExternalJsonLinter extends ArcanistLinter { ->setPath($path) ->setLine($line) ->setChar($char) - ->setCode($this->getLinterName()) + ->setCode($code) ->setSeverity($severity) ->setName($name) ->setDescription($description); $original = idx($message, 'original'); if ($original !== null) { - $lint->setOriginalText($originalText); + $lint->setOriginalText($original); } $replacement = idx($message, 'replacement'); From git at git.haskell.org Thu Oct 19 14:26:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Oct 2017 14:26:17 +0000 (UTC) Subject: [commit: ghc] master: Accept test output for #14350 (20ae22b) Message-ID: <20171019142617.E09CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/20ae22b08c79dc1cf851c79a73601c7c62abca16/ghc >--------------------------------------------------------------- commit 20ae22b08c79dc1cf851c79a73601c7c62abca16 Author: Ryan Scott Date: Thu Oct 19 09:49:48 2017 -0400 Accept test output for #14350 >--------------------------------------------------------------- 20ae22b08c79dc1cf851c79a73601c7c62abca16 .../tests/typecheck/should_fail/T14350.stderr | 30 ++++++++++++++++++++++ 1 file changed, 30 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T14350.stderr b/testsuite/tests/typecheck/should_fail/T14350.stderr new file mode 100644 index 0000000..27b53aa --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14350.stderr @@ -0,0 +1,30 @@ + +T14350.hs:59:15: error: + • Couldn't match expected type ‘Proxy a2 + -> Apply (Apply (c1 x5) 'Proxy) (Apply (g x5) 'Proxy)’ + with actual type ‘Sing (f0 @@ t0)’ + • The function ‘applySing’ is applied to three arguments, + but its type ‘Sing f0 -> Sing t0 -> Sing (f0 @@ t0)’ has only two + In the expression: applySing f Proxy Proxy + In an equation for ‘dcomp’: dcomp f g x = applySing f Proxy Proxy + • Relevant bindings include + x :: Sing x5 (bound at T14350.hs:59:11) + g :: Sing (g x4) (bound at T14350.hs:59:9) + f :: Sing (f x3 y1) (bound at T14350.hs:59:7) + dcomp :: Sing (f x3 y1) + -> Sing (g x4) -> Sing x5 -> (c1 x5 @@ 'Proxy) @@ (g x5 @@ 'Proxy) + (bound at T14350.hs:59:1) + +T14350.hs:59:27: error: + • Couldn't match expected type ‘Sing t0’ + with actual type ‘Proxy a0’ + • In the second argument of ‘applySing’, namely ‘Proxy’ + In the expression: applySing f Proxy Proxy + In an equation for ‘dcomp’: dcomp f g x = applySing f Proxy Proxy + • Relevant bindings include + x :: Sing x5 (bound at T14350.hs:59:11) + g :: Sing (g x4) (bound at T14350.hs:59:9) + f :: Sing (f x3 y1) (bound at T14350.hs:59:7) + dcomp :: Sing (f x3 y1) + -> Sing (g x4) -> Sing x5 -> (c1 x5 @@ 'Proxy) @@ (g x5 @@ 'Proxy) + (bound at T14350.hs:59:1) From git at git.haskell.org Thu Oct 19 14:26:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Oct 2017 14:26:20 +0000 (UTC) Subject: [commit: ghc] master: Disable -XRebindableSyntax when running internal GHCi expressions (e023e78) Message-ID: <20171019142620.A51163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e023e78bc13ffae168f00a52324fc406a146b40f/ghc >--------------------------------------------------------------- commit e023e78bc13ffae168f00a52324fc406a146b40f Author: Ryan Scott Date: Thu Oct 19 09:50:17 2017 -0400 Disable -XRebindableSyntax when running internal GHCi expressions Summary: It's well known that `-XRebindableSyntax` doesn't play nicely with some of the internal expressions that GHCi runs. #13385 was one example where this problem arose, which was fixed at the time by simply avoiding the use of `do`-notation in these internal GHCi expressions. That seemed to work, but it was a technique that proved not to scale, as #14342 demonstrated //another// example where `-XRebindableSyntax` can bite. Instead of delicately arranging the internal GHCi expressions to avoid anything that might be covered under `-XRebindableSyntax`, this patch takes the much more direct approach of disabling `-XRebindableSyntax` entirely when running any internal GHCi expression. This shouldn't hurt, since nothing internal to GHCi was taking advantage of the extension in the first place, and moreover, we can have greater confidence that some other obscure `-XRebindableSyntax` corner case won't pop up in the future. As an added bonus, this lets us once again use `do`-notation in the code that had to be changed when #13385 was (hackily) fixed before. Test Plan: make test TEST=T14342 Reviewers: bgamari, austin Subscribers: rwbarton, thomie GHC Trac Issues: #14342 Differential Revision: https://phabricator.haskell.org/D4086 >--------------------------------------------------------------- e023e78bc13ffae168f00a52324fc406a146b40f ghc/GHCi/UI/Monad.hs | 33 +++++++++++++++------- .../tests/ghci/scripts/T14342.script | 0 testsuite/tests/ghci/scripts/all.T | 2 ++ 3 files changed, 25 insertions(+), 10 deletions(-) diff --git a/ghc/GHCi/UI/Monad.hs b/ghc/GHCi/UI/Monad.hs index 9233beb..45a5271 100644 --- a/ghc/GHCi/UI/Monad.hs +++ b/ghc/GHCi/UI/Monad.hs @@ -62,6 +62,7 @@ import qualified System.Console.Haskeline as Haskeline import Control.Monad.Trans.Class import Control.Monad.IO.Class import Data.Map.Strict (Map) +import qualified GHC.LanguageExtensions as LangExt ----------------------------------------------------------------------------- -- GHCi monad @@ -421,15 +422,13 @@ 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 $ - " 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 $ - " System.IO.hFlush System.IO.stdout" ++ - "`GHC.Base.thenIO` System.IO.hFlush System.IO.stderr" + nobuf <- compileGHCiExpr $ + "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 }" + flush <- compileGHCiExpr $ + "do { System.IO.hFlush System.IO.stdout; " ++ + " System.IO.hFlush System.IO.stderr }" return (nobuf, flush) -- | Invoke "hFlush stdout; hFlush stderr" in the interpreter @@ -452,6 +451,20 @@ turnOffBuffering_ fhv = do mkEvalWrapper :: GhcMonad m => String -> [String] -> m ForeignHValue mkEvalWrapper progname args = - GHC.compileExprRemote $ + compileGHCiExpr $ "\\m -> System.Environment.withProgName " ++ show progname ++ "(System.Environment.withArgs " ++ show args ++ " m)" + +compileGHCiExpr :: GhcMonad m => String -> m ForeignHValue +compileGHCiExpr expr = do + hsc_env <- getSession + let dflags = hsc_dflags hsc_env + -- RebindableSyntax can wreak havoc with GHCi in several ways + -- (see #13385 and #14342 for examples), so we take care to disable it + -- for the duration of running expressions that are internal to GHCi. + no_rb_hsc_env = + hsc_env { hsc_dflags = xopt_unset dflags LangExt.RebindableSyntax } + setSession no_rb_hsc_env + res <- GHC.compileExprRemote expr + setSession hsc_env + pure res diff --git a/libraries/ghc-compact/tests/compact_serialize.stderr b/testsuite/tests/ghci/scripts/T14342.script similarity index 100% copy from libraries/ghc-compact/tests/compact_serialize.stderr copy to testsuite/tests/ghci/scripts/T14342.script diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 4eed55b..e453591 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -260,3 +260,5 @@ test('T13699', normal, ghci_script, ['T13699.script']) test('T13988', normal, ghci_script, ['T13988.script']) test('T13407', normal, ghci_script, ['T13407.script']) test('T13963', normal, ghci_script, ['T13963.script']) +test('T14342', [extra_hc_opts("-XOverloadedStrings -XRebindableSyntax")], + ghci_script, ['T14342.script']) From git at git.haskell.org Thu Oct 19 14:26:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Oct 2017 14:26:24 +0000 (UTC) Subject: [commit: ghc] master: Error when deriving instances in hs-boot files (101a8c7) Message-ID: <20171019142624.8A9263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/101a8c770b9d3abd57ff289bffea3d838cf25c80/ghc >--------------------------------------------------------------- commit 101a8c770b9d3abd57ff289bffea3d838cf25c80 Author: Ryan Scott Date: Thu Oct 19 10:21:17 2017 -0400 Error when deriving instances in hs-boot files Summary: According to the GHC users' guide, one cannot derive instances for data types in `.hs-boot` files. However, GHC was not enforcing this in practice, which led to #14365. Fix this by actually throwing an error if a derived instance is detected in an `.hs-boot` file (and recommend how to fix it in the error message.) Test Plan: make test TEST=T14365 Reviewers: ezyang, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #14365 Differential Revision: https://phabricator.haskell.org/D4102 >--------------------------------------------------------------- 101a8c770b9d3abd57ff289bffea3d838cf25c80 compiler/typecheck/TcDeriv.hs | 4 ++++ testsuite/tests/deriving/should_fail/T14365.stderr | 13 +++++++++++++ testsuite/tests/deriving/should_fail/T14365A.hs | 5 +++++ testsuite/tests/deriving/should_fail/T14365B.hs | 4 ++++ testsuite/tests/deriving/should_fail/T14365B.hs-boot | 7 +++++++ testsuite/tests/deriving/should_fail/all.T | 2 ++ testsuite/tests/deriving/should_fail/drvfail016.stderr | 6 ++++-- 7 files changed, 39 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 77a313b..33ce581 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -956,6 +956,10 @@ mkEqnHelp overlap_mode tvs cls cls_tys tycon tc_args mtheta deriv_strat -- If it's still a data family, the lookup failed; i.e no instance exists ; when (isDataFamilyTyCon rep_tc) (bale_out (text "No family instance for" <+> quotes (pprTypeApp tycon tc_args))) + ; is_boot <- tcIsHsBootOrSig + ; when is_boot $ + bale_out (text "Cannot derive instances in hs-boot files" + $+$ text "Write an instance declaration instead") ; let deriv_env = DerivEnv { denv_overlap_mode = overlap_mode diff --git a/testsuite/tests/deriving/should_fail/T14365.stderr b/testsuite/tests/deriving/should_fail/T14365.stderr new file mode 100644 index 0000000..f8f106f --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14365.stderr @@ -0,0 +1,13 @@ +[1 of 3] Compiling T14365B[boot] ( T14365B.hs-boot, T14365B.o-boot ) + +T14365B.hs-boot:5:13: error: + • Can't make a derived instance of ‘Functor Foo’: + Cannot derive instances in hs-boot files + Write an instance declaration instead + • In the data declaration for ‘Foo’ + +T14365B.hs-boot:7:1: error: + • Can't make a derived instance of ‘Foldable Foo’: + Cannot derive instances in hs-boot files + Write an instance declaration instead + • In the stand-alone deriving instance for ‘Foldable Foo’ diff --git a/testsuite/tests/deriving/should_fail/T14365A.hs b/testsuite/tests/deriving/should_fail/T14365A.hs new file mode 100644 index 0000000..e80e7d1 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14365A.hs @@ -0,0 +1,5 @@ +module T14365A where + +import {-# SOURCE #-} T14365B + +main = return () diff --git a/testsuite/tests/deriving/should_fail/T14365B.hs b/testsuite/tests/deriving/should_fail/T14365B.hs new file mode 100644 index 0000000..596c275 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14365B.hs @@ -0,0 +1,4 @@ +module T14365B where + +data Foo a = Foo a + deriving (Functor) diff --git a/testsuite/tests/deriving/should_fail/T14365B.hs-boot b/testsuite/tests/deriving/should_fail/T14365B.hs-boot new file mode 100644 index 0000000..1dcbc94 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14365B.hs-boot @@ -0,0 +1,7 @@ +{-# LANGUAGE StandaloneDeriving #-} +module T14365B where + +data Foo a + deriving (Functor) + +deriving instance Foldable Foo diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index 77ce145..1861e6d 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -66,3 +66,5 @@ test('T11509_1', [when(doing_ghci(), extra_hc_opts('-fobject-code'))], test('T12163', normal, compile_fail, ['']) test('T12512', omit_ways(['ghci']), compile_fail, ['']) test('T12801', normal, compile_fail, ['']) +test('T14365', [extra_files(['T14365B.hs','T14365B.hs-boot'])], + multimod_compile_fail, ['T14365A','']) diff --git a/testsuite/tests/deriving/should_fail/drvfail016.stderr b/testsuite/tests/deriving/should_fail/drvfail016.stderr index 182b748..05abbf5 100644 --- a/testsuite/tests/deriving/should_fail/drvfail016.stderr +++ b/testsuite/tests/deriving/should_fail/drvfail016.stderr @@ -1,4 +1,6 @@ drvfail016.hs-boot:7:14: error: - Deriving not permitted in hs-boot file - Use an instance declaration instead + • Can't make a derived instance of ‘Show D’: + Cannot derive instances in hs-boot files + Write an instance declaration instead + • In the data declaration for ‘D’ From git at git.haskell.org Thu Oct 19 14:26:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Oct 2017 14:26:28 +0000 (UTC) Subject: [commit: ghc] master: Fix #14369 by making injectivity warnings finer-grained (8846a7f) Message-ID: <20171019142628.586683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8846a7fdcf2060dd37e66b4d1f89bd8fdfad4620/ghc >--------------------------------------------------------------- commit 8846a7fdcf2060dd37e66b4d1f89bd8fdfad4620 Author: Ryan Scott Date: Thu Oct 19 10:21:28 2017 -0400 Fix #14369 by making injectivity warnings finer-grained Summary: Previously, GHC would always raise the possibility that a type family might not be injective in certain error messages, even if that type family actually //was// injective. Fix this by actually checking for a type family's lack of injectivity before emitting such an error message. Test Plan: ./validate Reviewers: goldfire, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #14369 Differential Revision: https://phabricator.haskell.org/D4106 >--------------------------------------------------------------- 8846a7fdcf2060dd37e66b4d1f89bd8fdfad4620 compiler/typecheck/TcErrors.hs | 3 ++- .../indexed-types/should_fail/NoMatchErr.stderr | 5 ++-- .../tests/indexed-types/should_fail/T14369.hs | 27 ++++++++++++++++++++++ .../tests/indexed-types/should_fail/T14369.stderr | 9 ++++++++ .../tests/indexed-types/should_fail/T1897b.stderr | 2 +- .../tests/indexed-types/should_fail/T1900.stderr | 2 +- .../tests/indexed-types/should_fail/T2544.stderr | 4 ++-- .../tests/indexed-types/should_fail/T2664.stderr | 2 +- .../tests/indexed-types/should_fail/T4099.stderr | 2 +- .../tests/indexed-types/should_fail/T4179.stderr | 2 +- .../tests/indexed-types/should_fail/T9036.stderr | 2 +- .../tests/indexed-types/should_fail/T9171.stderr | 2 +- testsuite/tests/indexed-types/should_fail/all.T | 1 + testsuite/tests/typecheck/should_fail/T5853.stderr | 16 ++++--------- testsuite/tests/typecheck/should_fail/T8030.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/T8034.stderr | 2 +- 16 files changed, 58 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 8846a7fdcf2060dd37e66b4d1f89bd8fdfad4620 From git at git.haskell.org Thu Oct 19 14:26:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Oct 2017 14:26:31 +0000 (UTC) Subject: [commit: ghc] master: Export injectiveVarsOf{Binder, Type} from TyCoRep (de8752e) Message-ID: <20171019142631.18FAF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/de8752e40bfdb05727c723abf97bdf158b5d9392/ghc >--------------------------------------------------------------- commit de8752e40bfdb05727c723abf97bdf158b5d9392 Author: Ryan Scott Date: Thu Oct 19 10:21:33 2017 -0400 Export injectiveVarsOf{Binder,Type} from TyCoRep Summary: I ended up needing to use the functionality of `injectiveVarsOfBinder`/`injectiveVarsOfType` in this Haddock PR (https://github.com/haskell/haddock/pull/681), but alas, neither of these functions were exported. Let's do so. Test Plan: Does it compile? Reviewers: austin, goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4107 >--------------------------------------------------------------- de8752e40bfdb05727c723abf97bdf158b5d9392 compiler/typecheck/TcSplice.hs | 29 ----------------------------- compiler/types/TyCoRep.hs | 36 ++++++++++++++++++++++++++++++++++++ 2 files changed, 36 insertions(+), 29 deletions(-) diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs index 04adbc3..45e18e6 100644 --- a/compiler/typecheck/TcSplice.hs +++ b/compiler/typecheck/TcSplice.hs @@ -1912,35 +1912,6 @@ reify_tc_app tc tys in not (subVarSet result_vars dropped_vars) - injectiveVarsOfBinder :: TyConBinder -> FV - injectiveVarsOfBinder (TvBndr tv vis) = - case vis of - AnonTCB -> injectiveVarsOfType (tyVarKind tv) - NamedTCB Required -> FV.unitFV tv `unionFV` - injectiveVarsOfType (tyVarKind tv) - NamedTCB _ -> emptyFV - - injectiveVarsOfType :: Type -> FV - injectiveVarsOfType = go - where - go ty | Just ty' <- coreView ty - = go ty' - go (TyVarTy v) = FV.unitFV v `unionFV` go (tyVarKind v) - go (AppTy f a) = go f `unionFV` go a - go (FunTy ty1 ty2) = go ty1 `unionFV` go ty2 - go (TyConApp tc tys) = - case tyConInjectivityInfo tc of - NotInjective -> emptyFV - Injective inj -> mapUnionFV go $ - filterByList (inj ++ repeat True) tys - -- Oversaturated arguments to a tycon are - -- always injective, hence the repeat True - go (ForAllTy tvb ty) = tyCoFVsBndr tvb $ go (tyVarKind (binderVar tvb)) - `unionFV` go ty - go LitTy{} = emptyFV - go (CastTy ty _) = go ty - go CoercionTy{} = emptyFV - reifyPred :: TyCoRep.PredType -> TcM TH.Pred reifyPred ty -- We could reify the invisible parameter as a class but it seems diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 5e32bb1..55b9e1c 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -79,6 +79,7 @@ module TyCoRep ( tyCoFVsOfCo, tyCoFVsOfCos, tyCoVarsOfCoList, tyCoVarsOfProv, closeOverKinds, + injectiveVarsOfBinder, injectiveVarsOfType, noFreeVarsOfType, noFreeVarsOfCo, @@ -1559,6 +1560,41 @@ closeOverKindsList tvs = fvVarList $ closeOverKindsFV tvs closeOverKindsDSet :: DTyVarSet -> DTyVarSet closeOverKindsDSet = fvDVarSet . closeOverKindsFV . dVarSetElems +-- | Returns the free variables of a 'TyConBinder' that are in injective +-- positions. (See @Note [Kind annotations on TyConApps]@ in "TcSplice" for an +-- explanation of what an injective position is.) +injectiveVarsOfBinder :: TyConBinder -> FV +injectiveVarsOfBinder (TvBndr tv vis) = + case vis of + AnonTCB -> injectiveVarsOfType (tyVarKind tv) + NamedTCB Required -> unitFV tv `unionFV` + injectiveVarsOfType (tyVarKind tv) + NamedTCB _ -> emptyFV + +-- | Returns the free variables of a 'Type' that are in injective positions. +-- (See @Note [Kind annotations on TyConApps]@ in "TcSplice" for an explanation +-- of what an injective position is.) +injectiveVarsOfType :: Type -> FV +injectiveVarsOfType = go + where + go ty | Just ty' <- coreView ty + = go ty' + go (TyVarTy v) = unitFV v `unionFV` go (tyVarKind v) + go (AppTy f a) = go f `unionFV` go a + go (FunTy ty1 ty2) = go ty1 `unionFV` go ty2 + go (TyConApp tc tys) = + case tyConInjectivityInfo tc of + NotInjective -> emptyFV + Injective inj -> mapUnionFV go $ + filterByList (inj ++ repeat True) tys + -- Oversaturated arguments to a tycon are + -- always injective, hence the repeat True + go (ForAllTy tvb ty) = tyCoFVsBndr tvb $ go (tyVarKind (binderVar tvb)) + `unionFV` go ty + go LitTy{} = emptyFV + go (CastTy ty _) = go ty + go CoercionTy{} = emptyFV + -- | Returns True if this type has no free variables. Should be the same as -- isEmptyVarSet . tyCoVarsOfType, but faster in the non-forall case. noFreeVarsOfType :: Type -> Bool From git at git.haskell.org Thu Oct 19 14:38:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Oct 2017 14:38:36 +0000 (UTC) Subject: [commit: ghc] wip/tdammers-7258: Document readField / readSymField (ad349f0) Message-ID: <20171019143836.4CD223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers-7258 Link : http://ghc.haskell.org/trac/ghc/changeset/ad349f0de4372b8ef887ab83a659429cb7f260c8/ghc >--------------------------------------------------------------- commit ad349f0de4372b8ef887ab83a659429cb7f260c8 Author: Tobias Dammers Date: Thu Oct 19 16:31:13 2017 +0200 Document readField / readSymField >--------------------------------------------------------------- ad349f0de4372b8ef887ab83a659429cb7f260c8 libraries/base/GHC/Read.hs | 28 ++++++++++++++++++++++++++++ 1 file changed, 28 insertions(+) diff --git a/libraries/base/GHC/Read.hs b/libraries/base/GHC/Read.hs index e69e4a0..2d8ee3d 100644 --- a/libraries/base/GHC/Read.hs +++ b/libraries/base/GHC/Read.hs @@ -361,6 +361,12 @@ choose sps = foldr ((+++) . try_one) pfail sps L.Symbol s' | s==s' -> p _other -> pfail } +-- See Note [Why readField] + +-- | 'Read' parser for a record field, of the form @fieldName=value at . The +-- @fieldName@ must be an alphanumeric identifier; for symbols (operator-style) +-- field names, e.g. @(#)@, use 'readSymField'). The second argument is a +-- parser for the field value. readField :: String -> ReadPrec a -> ReadPrec a readField fieldName readVal = do expectP (L.Ident fieldName) @@ -368,6 +374,12 @@ readField fieldName readVal = do readVal {-# NOINLINE readField #-} +-- See Note [Why readField] + +-- | 'Read' parser for a symbol record field, of the form @(###)=value@ (where +-- @###@ is the field name). The field name must be a symbol (operator-style), +-- e.g. @(#)@. For regular (alphanumeric) field names, use 'readField'. The +-- second argument is a parser for the field value. readSymField :: String -> ReadPrec a -> ReadPrec a readSymField fieldName readVal = do expectP (L.Punc "(") @@ -377,6 +389,22 @@ readSymField fieldName readVal = do readVal {-# NOINLINE readSymField #-} + +-- Note [Why readField] +-- +-- Previousy, the code for automatically deriving Read instance (in +-- typecheck/TcGenDeriv.hs) would generate inline code for parsing fields; +-- this, however, turned out to produce massive amounts of intermediate code, +-- and produced a considerable performance hit in the code generator. +-- Since Read instances are not generally supposed to be perfomance critical, +-- the readField and readSymField functions have been factored out, and the +-- code generator now just generates calls rather than manually inlining the +-- parsers. For large record types (e.g. 500 fields), this produces a +-- significant performance boost. +-- +-- See also Trac #14364. + + -------------------------------------------------------------- -- Simple instances of Read -------------------------------------------------------------- From git at git.haskell.org Thu Oct 19 14:38:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Oct 2017 14:38:39 +0000 (UTC) Subject: [commit: ghc] wip/tdammers-7258: Fixed regression: derived Read instance must retain reset call (09911dc) Message-ID: <20171019143839.0B2263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers-7258 Link : http://ghc.haskell.org/trac/ghc/changeset/09911dc5017fc4fcbbeaec963e3859ddaff3ecc1/ghc >--------------------------------------------------------------- commit 09911dc5017fc4fcbbeaec963e3859ddaff3ecc1 Author: Tobias Dammers Date: Thu Oct 19 16:17:02 2017 +0200 Fixed regression: derived Read instance must retain reset call See https://phabricator.haskell.org/D4108 >--------------------------------------------------------------- 09911dc5017fc4fcbbeaec963e3859ddaff3ecc1 compiler/typecheck/TcGenDeriv.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index 2d004be..26ac853 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -1079,7 +1079,9 @@ gen_Read_binds get_fixity loc tycon (nlVarPat a) (nlHsApps read_field - [nlHsLit (mkHsString lbl_str), nlHsVar readPrec_RDR] + [ nlHsLit (mkHsString lbl_str) + , nlHsVarApps reset_RDR [readPrec_RDR] + ] ) ) ] From git at git.haskell.org Thu Oct 19 15:56:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Oct 2017 15:56:05 +0000 (UTC) Subject: [commit: ghc] master: User's guide: Fix the category of some flags (7ac22b7) Message-ID: <20171019155605.E544D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ac22b73b38b60bc26ad2508f57732aa17532a80/ghc >--------------------------------------------------------------- commit 7ac22b73b38b60bc26ad2508f57732aa17532a80 Author: Joachim Breitner Date: Thu Oct 19 11:45:19 2017 -0400 User's guide: Fix the category of some flags so now “7.6.12. Language options” only lists `-X` flags, as it should. >--------------------------------------------------------------- 7ac22b73b38b60bc26ad2508f57732aa17532a80 docs/users_guide/flags.rst | 6 ++++-- docs/users_guide/glasgow_exts.rst | 8 +++++--- docs/users_guide/phases.rst | 2 +- docs/users_guide/safe_haskell.rst | 14 +++++++------- 4 files changed, 17 insertions(+), 13 deletions(-) diff --git a/docs/users_guide/flags.rst b/docs/users_guide/flags.rst index a3ec0f6..ce3244b 100644 --- a/docs/users_guide/flags.rst +++ b/docs/users_guide/flags.rst @@ -174,13 +174,15 @@ More details in :ref:`packages` :type: table :category: packages + +.. flags-language-options:: + Language options ---------------- Language options can be enabled either by a command-line option ``-Xblah``, or by a ``{-# LANGUAGE blah #-}`` pragma in the file itself. -See :ref:`options-language`. Some options are enabled using ``-f*`` -flags. +See :ref:`options-language`. .. tabularcolumns:: | p{\dimexpr 0.36\textwidth-2\tabcolsep} | diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index d0e079e..2499287 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -44,6 +44,7 @@ Language options can be controlled in two ways: ``LANGUAGE`` pragma, thus ``{-# LANGUAGE TemplateHaskell #-}`` (see :ref:`language-pragma`). +A compact list of all language options can be found in the `flags reference section <#flags-language-options>`__. Although not recommended, the deprecated :ghc-flag:`-fglasgow-exts` flag enables a large swath of the extensions supported by GHC at once. @@ -53,7 +54,7 @@ a large swath of the extensions supported by GHC at once. see :ref:`options-language` for exactly which ones. :type: dynamic :reverse: -fno-glasgow-exts - :category: + :category: misc The flag ``-fglasgow-exts`` is equivalent to enabling the following extensions: @@ -9071,12 +9072,12 @@ stub out functions that return unboxed types. Printing levity-polymorphic types --------------------------------- -.. ghc-flag:: -Wprint-explicit-runtime-rep +.. ghc-flag:: -fprint-explicit-runtime-rep :shortdesc: Print ``RuntimeRep`` variables in types which are runtime-representation polymorphic. :type: dynamic :reverse: -fno-print-explicit-runtime-reps - :category: + :category: verbosity Print ``RuntimeRep`` parameters as they appear; otherwise, they are defaulted to ``'LiftedRep``. @@ -15158,3 +15159,4 @@ compilation with ``-prof``. On the other hand, as the ``CallStack`` is built up explicitly via the ``HasCallStack`` constraints, it will generally not contain as much information as the simulated call-stacks maintained by the RTS. + diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst index d14a7fa..d3189a5 100644 --- a/docs/users_guide/phases.rst +++ b/docs/users_guide/phases.rst @@ -1145,5 +1145,5 @@ for example). executables to ensure that only one ``libHSrts`` is present if loaded into the address space of another Haskell process. - Also, you may need to use the :ghc-flags:`-rdynamic` flag to ensure that + Also, you may need to use the :ghc-flag:`-rdynamic` flag to ensure that that symbols are not dropped from your PIE objects. diff --git a/docs/users_guide/safe_haskell.rst b/docs/users_guide/safe_haskell.rst index 6b32826..36dcd40 100644 --- a/docs/users_guide/safe_haskell.rst +++ b/docs/users_guide/safe_haskell.rst @@ -583,7 +583,7 @@ trust property of packages: :shortdesc: Expose package ⟨pkg⟩ and set it to be trusted. See :ref:`safe-haskell`. :type: dynamic/ ``:set`` - :category: + :category: packages Exposes package ⟨pkg⟩ if it was hidden and considers it a trusted package regardless of the package database. @@ -592,7 +592,7 @@ trust property of packages: :shortdesc: Expose package ⟨pkg⟩ and set it to be distrusted. See :ref:`safe-haskell`. :type: dynamic/ ``:set`` - :category: + :category: packages Exposes package ⟨pkg⟩ if it was hidden and considers it an untrusted package regardless of the package database. @@ -600,7 +600,7 @@ trust property of packages: .. ghc-flag:: -distrust-all-packages :shortdesc: Distrust all packages by default. See :ref:`safe-haskell`. :type: dynamic/ ``:set`` - :category: + :category: packages Considers all packages distrusted unless they are explicitly set to be trusted by subsequent command-line options. @@ -722,7 +722,7 @@ And one general flag: :shortdesc: Enable :ref:`Safe Haskell ` trusted package requirement for trustworthy modules. :type: dynamic - :category: + :category: packages When enabled, turn on an extra check for a trustworthy module ``M``, requiring the package that ``M`` resides in be considered trusted, for ``M`` @@ -735,7 +735,7 @@ And three warning flags: See :ref:`safe-haskell` :type: dynamic :reverse: -Wno-unsafe - :category: + :category: warnings Issue a warning if the module being compiled is regarded to be unsafe. Should be used to check the safety type of modules when @@ -745,7 +745,7 @@ And three warning flags: :shortdesc: warn if the module being compiled is regarded to be safe. :type: dynamic :reverse: -Wno-safe - :category: + :category: warnings Issue a warning if the module being compiled is regarded to be safe. Should be used to check the safety type of modules when using safe @@ -757,7 +757,7 @@ And three warning flags: :ghc-flag:`-XSafe`, a more informative bound. :type: dynamic :reverse: -Wno-safe - :category: + :category: warnings Issue a warning if the module being compiled is marked as -XTrustworthy but it could instead be marked as From git at git.haskell.org Fri Oct 20 02:38:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:38:12 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Build utilities with the bootstrap compiler when cross compiling (383faef) Message-ID: <20171020023812.77E2A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/383faef5b7e9981eb8a924a0aa7df35cae0d28dc/ghc >--------------------------------------------------------------- commit 383faef5b7e9981eb8a924a0aa7df35cae0d28dc Author: Moritz Angermann Date: Fri Sep 29 14:45:44 2017 +0800 Build utilities with the bootstrap compiler when cross compiling Summary: This should fix Trac #14297. When building a cross compiler, we have rather little use of utilities that do not run on the host, where the compiler runs. As such we should build the utilities with the bootstrap (stage 0) compiler rather than witht he in-tree (stage 1) compiler when CrossCompiling. This used to results in the utilities we ship in the binary distribution to be built for the wrong host. This diff tries to rectify the situation and allow the binary distribution to contain the utilities for the host when CrossCompiling. Reviewers: bgamari, trofi, hvr, austin Subscribers: rwbarton, thomie GHC Trac Issues: #14297 Differential Revision: https://phabricator.haskell.org/D4048 >--------------------------------------------------------------- 383faef5b7e9981eb8a924a0aa7df35cae0d28dc ghc.mk | 15 +++++++++++++-- utils/compare_sizes/ghc.mk | 4 +++- utils/hpc/ghc.mk | 18 +++++++++++++++++- utils/hsc2hs | 2 +- 4 files changed, 34 insertions(+), 5 deletions(-) diff --git a/ghc.mk b/ghc.mk index c3edc5e..f397f7c 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1056,6 +1056,17 @@ ifneq "$(CLEANING)" "YES" # This rule seems to hold some files open on Windows which prevents # cleaning, perhaps due to the $(wildcard). +# when building stage1only (a cross-compiler), we need to put the +# stage0 compiled ghc-cabal into the binary distribution. As the +# stage1 compiled ghc-cabal is built for the target, however +# ghc-cabal is used during 'make install' on the host, when +# installing the binary distribution. +ifeq "$(Stage1Only)" "YES" +DIST_GHC_CABAL=utils/ghc-cabal/dist/build/tmp/ghc-cabal +else +DIST_GHC_CABAL=utils/ghc-cabal/dist-install/build/tmp/ghc-cabal +endif + $(eval $(call bindist-list,.,\ LICENSE \ README \ @@ -1067,7 +1078,7 @@ $(eval $(call bindist-list,.,\ Makefile \ mk/config.mk.in \ $(INPLACE_BIN)/mkdirhier \ - utils/ghc-cabal/dist-install/build/tmp/ghc-cabal \ + $(DIST_GHC_CABAL) \ $(BINDIST_WRAPPERS) \ $(BINDIST_PERL_SOURCES) \ $(BINDIST_LIBS) \ @@ -1127,7 +1138,7 @@ unix-binary-dist-prep: echo "BUILD_SPHINX_HTML = $(BUILD_SPHINX_HTML)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_PDF = $(BUILD_SPHINX_PDF)" >> $(BIN_DIST_MK) echo "BUILD_MAN = $(BUILD_MAN)" >> $(BIN_DIST_MK) - echo "override ghc-cabal_INPLACE = utils/ghc-cabal/dist-install/build/tmp/ghc-cabal-bindist" >> $(BIN_DIST_MK) + echo "override ghc-cabal_INPLACE = $(DIST_GHC_CABAL)" >> $(BIN_DIST_MK) echo "UseSystemLibFFI = $(UseSystemLibFFI)" >> $(BIN_DIST_MK) # See Note [Persist CrossCompiling in binary distributions] echo "CrossCompiling = $(CrossCompiling)" >> $(BIN_DIST_MK) diff --git a/utils/compare_sizes/ghc.mk b/utils/compare_sizes/ghc.mk index d659a5e..1e601a3 100644 --- a/utils/compare_sizes/ghc.mk +++ b/utils/compare_sizes/ghc.mk @@ -5,5 +5,7 @@ utils/compare_sizes_MODULES = Main utils/compare_sizes_dist-install_PROGNAME = compareSizes utils/compare_sizes_dist-install_INSTALL_INPLACE = NO +# build compare_sizes only if not Stage1Only or not CrossCompiling. +ifeq "$(Stage1Only) $(CrossCompiling)" "NO NO" $(eval $(call build-prog,utils/compare_sizes,dist-install,1)) - +endif diff --git a/utils/hpc/ghc.mk b/utils/hpc/ghc.mk index f70be94..697e795 100644 --- a/utils/hpc/ghc.mk +++ b/utils/hpc/ghc.mk @@ -12,10 +12,26 @@ utils/hpc_USES_CABAL = YES utils/hpc_PACKAGE = hpc-bin -utils/hpc_dist-install_INSTALL = YES + +# built by ghc-stage0 +utils/hpc_dist_INSTALL_INPLACE = NO +utils/hpc_dist_PROGNAME = hpc +utils/hpc_dist_SHELL_WRAPPER = YES +utils/hpc_dist_INSTALL_SHELL_WRAPPER_NAME = hpc + +# built by ghc-stage1 utils/hpc_dist-install_INSTALL_INPLACE = YES utils/hpc_dist-install_PROGNAME = hpc utils/hpc_dist-install_SHELL_WRAPPER = YES utils/hpc_dist-install_INSTALL_SHELL_WRAPPER_NAME = hpc +ifeq "$(Stage1Only)" "YES" +utils/hpc_dist_INSTALL = YES +utils/hpc_dist-install_INSTALL = NO +else +utils/hpc_dist_INSTALL = NO +utils/hpc_dist-install_INSTALL = YES +endif + +$(eval $(call build-prog,utils/hpc,dist,0)) $(eval $(call build-prog,utils/hpc,dist-install,1)) diff --git a/utils/hsc2hs b/utils/hsc2hs index 936b088..94af7d9 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 936b0885ee794db83dc8473e17e153936e56d62f +Subproject commit 94af7d9a27307f40a8b18da0f8e0fd9e9d77e818 From git at git.haskell.org Fri Oct 20 02:38:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:38:15 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Fix binary distributions of cross compilers (9ee3151) Message-ID: <20171020023815.472593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/9ee3151537d9fee49bb55e1e918fa62047b58e60/ghc >--------------------------------------------------------------- commit 9ee3151537d9fee49bb55e1e918fa62047b58e60 Author: Moritz Angermann Date: Mon Oct 2 13:47:45 2017 +0800 Fix binary distributions of cross compilers Summary: - copy over the original settings file Otherwise most of the custom cross compiler toolchain will be screwed up upon install. I'd rather have someone complain about a proper target-prefixed tool being missing, than getting garbaled output and a slew of strange errors because the final configure selected tools on the install machine just don't match up. - persist target-prefix. For cross compilers, retain the $target- prefix. This allows installing multiple cross compierls targetting different targets alongside each other. Reviewers: austin, hvr, bgamari Subscribers: rwbarton, trofi, thomie, hvr, bgamari, erikd Differential Revision: https://phabricator.haskell.org/D4058 >--------------------------------------------------------------- 9ee3151537d9fee49bb55e1e918fa62047b58e60 distrib/configure.ac.in | 20 ++++++++++++++------ ghc.mk | 14 ++++++++++---- 2 files changed, 24 insertions(+), 10 deletions(-) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index 509e74e..62f6575 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -35,10 +35,9 @@ FPTOOLS_SET_PLATFORM_VARS # Requires FPTOOLS_SET_PLATFORM_VARS to be run first. FP_FIND_ROOT -# ToDo: if Stage1Only=YES, should be YES -CrossCompiling=NO -CrossCompilePrefix="" -TargetPlatformFull="${target}" +CrossCompiling=@CrossCompiling@ +CrossCompilePrefix=@CrossCompilePrefix@ +TargetPlatformFull=@TargetPlatformFull@ AC_SUBST(CrossCompiling) AC_SUBST(CrossCompilePrefix) @@ -198,8 +197,17 @@ fi FP_SETTINGS -# -AC_CONFIG_FILES(settings mk/config.mk mk/install.mk) +dnl ** Hack tools for cross compilers +dnl -------------------------------------------------------------- +dnl When building a binary distribution for cross compilers, +dnl we likely want to retain the target-prefixed tools, and not +dnl have configure overwrite them with what ever it finds, as +dnl the found tools likely do not target the target. +AC_CONFIG_FILES(mk/config.mk mk/install.mk) +if test "x$CrossCompiling" = "xNO"; then +AC_CONFIG_FILES(settings) +fi + AC_OUTPUT # We get caught by diff --git a/ghc.mk b/ghc.mk index f397f7c..66ae00a 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1060,11 +1060,17 @@ ifneq "$(CLEANING)" "YES" # stage0 compiled ghc-cabal into the binary distribution. As the # stage1 compiled ghc-cabal is built for the target, however # ghc-cabal is used during 'make install' on the host, when -# installing the binary distribution. -ifeq "$(Stage1Only)" "YES" +# installing the binary distribution. We will also copy the original +# `settings` file instead of having `configure` compute a new one. +# We do this because the bindist configure by default picks up +# the non-target prefixed toolchain; and cross compilers can be +# very sensitive to the toolchain. +ifeq "$(Stage1Only) $(CrossCompiling)" "YES YES" DIST_GHC_CABAL=utils/ghc-cabal/dist/build/tmp/ghc-cabal +DIST_SETTINGS=settings else DIST_GHC_CABAL=utils/ghc-cabal/dist-install/build/tmp/ghc-cabal +DIST_SETTINGS=settings.in endif $(eval $(call bindist-list,.,\ @@ -1072,7 +1078,7 @@ $(eval $(call bindist-list,.,\ README \ INSTALL \ configure config.sub config.guess install-sh \ - settings.in \ + $(DIST_SETTINGS) \ llvm-targets \ packages \ Makefile \ @@ -1133,7 +1139,7 @@ BIN_DIST_MK = $(BIN_DIST_PREP_DIR)/bindist.mk unix-binary-dist-prep: $(call removeTrees,bindistprep/) "$(MKDIRHIER)" $(BIN_DIST_PREP_DIR) - set -e; for i in packages LICENSE compiler ghc iserv rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh settings.in llvm-targets ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done + set -e; for i in packages LICENSE compiler ghc iserv rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh $(DIST_SETTINGS) llvm-targets ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done echo "HADDOCK_DOCS = $(HADDOCK_DOCS)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_HTML = $(BUILD_SPHINX_HTML)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_PDF = $(BUILD_SPHINX_PDF)" >> $(BIN_DIST_MK) From git at git.haskell.org Fri Oct 20 02:38:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:38:18 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump submodule. (94c1277) Message-ID: <20171020023818.0C9423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/94c1277d8d5cc5f11fd9817f961415e03664929d/ghc >--------------------------------------------------------------- commit 94c1277d8d5cc5f11fd9817f961415e03664929d Author: Moritz Angermann Date: Wed Oct 4 09:48:01 2017 +0800 bump submodule. >--------------------------------------------------------------- 94c1277d8d5cc5f11fd9817f961415e03664929d libraries/data-bitcode | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/data-bitcode b/libraries/data-bitcode index c9818de..2039075 160000 --- a/libraries/data-bitcode +++ b/libraries/data-bitcode @@ -1 +1 @@ -Subproject commit c9818debd3dae774967c0507882b6b3bec7f0ee4 +Subproject commit 2039075a4fcb1b0767c1df868b2deda96d6022c4 From git at git.haskell.org Fri Oct 20 02:38:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:38:21 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds test (0945f08) Message-ID: <20171020023821.4EC833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/0945f0855179e9a52b074c62266ec62e8fb85984/ghc >--------------------------------------------------------------- commit 0945f0855179e9a52b074c62266ec62e8fb85984 Author: Moritz Angermann Date: Thu Sep 21 22:07:44 2017 +0800 Adds test >--------------------------------------------------------------- 0945f0855179e9a52b074c62266ec62e8fb85984 testsuite/tests/codeGen/should_run/T14251.hs | 22 ++++++++++++++++++++++ testsuite/tests/codeGen/should_run/T14251.stdout | 1 + testsuite/tests/codeGen/should_run/all.T | 1 + 3 files changed, 24 insertions(+) diff --git a/testsuite/tests/codeGen/should_run/T14251.hs b/testsuite/tests/codeGen/should_run/T14251.hs new file mode 100644 index 0000000..6f552e1 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14251.hs @@ -0,0 +1,22 @@ +{-# LANGUAGE MagicHash, BangPatterns #-} +module Main where + +-- A minor modification from T8064.hs. +-- +-- The key here is that we ensure that +-- subsequently passed floats do not +-- accidentally end up in previous +-- registers. +-- + +import GHC.Exts + +{-# NOINLINE f #-} +f :: (Int# -> Float# -> Double# -> Float# -> Double# -> String) -> String +f g = g 3# 4.0# 5.0## 6.0# 6.9## ++ " World!" + +{-# NOINLINE q #-} +q :: Int# -> Float# -> Double# -> Float# -> Double# -> String +q i j k l m = "Hello " ++ show (F# l) ++ " " ++ show (D# m) + +main = putStrLn (f $ q) diff --git a/testsuite/tests/codeGen/should_run/T14251.stdout b/testsuite/tests/codeGen/should_run/T14251.stdout new file mode 100644 index 0000000..8ec577b --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14251.stdout @@ -0,0 +1 @@ +Hello 6.0 6.9 World! diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 6aacea5..a5e5c64 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -159,3 +159,4 @@ test('T9577', [ unless(arch('x86_64') or arch('i386'),skip), test('T13425', normal, compile_and_run, ['-O']) test('castFloatWord', normal, compile_and_run, ['-dcmm-lint']) +test('T14251', normal, compile_and_run, ['-O2']) From git at git.haskell.org Fri Oct 20 02:38:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:38:30 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Merge branch 'feature/D4058-cross-compiler-bindist' into wip/angerman/llvmng (a6d66e4) Message-ID: <20171020023830.6B6773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/a6d66e4b50aff80ac5a1e3f88c8cf82badbc9011/ghc >--------------------------------------------------------------- commit a6d66e4b50aff80ac5a1e3f88c8cf82badbc9011 Merge: 94c1277 9ee3151 Author: Moritz Angermann Date: Fri Oct 20 10:37:03 2017 +0800 Merge branch 'feature/D4058-cross-compiler-bindist' into wip/angerman/llvmng >--------------------------------------------------------------- a6d66e4b50aff80ac5a1e3f88c8cf82badbc9011 distrib/configure.ac.in | 20 ++++++++++++++------ ghc.mk | 25 +++++++++++++++++++++---- utils/compare_sizes/ghc.mk | 4 +++- utils/hpc/ghc.mk | 18 +++++++++++++++++- utils/hsc2hs | 2 +- 5 files changed, 56 insertions(+), 13 deletions(-) From git at git.haskell.org Fri Oct 20 02:38:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:38:26 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds `-llvmng` (c274d4f) Message-ID: <20171020023826.0E5223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/c274d4f6eb7184df0c6cab2cb2a8d6a2e8c5b21b/ghc >--------------------------------------------------------------- commit c274d4f6eb7184df0c6cab2cb2a8d6a2e8c5b21b Author: Moritz Angermann Date: Mon Jul 31 15:18:49 2017 +0800 Adds `-llvmng` >--------------------------------------------------------------- c274d4f6eb7184df0c6cab2cb2a8d6a2e8c5b21b .gitmodules | 9 + compiler/cmm/CmmSwitch.hs | 1 + compiler/codeGen/StgCmmPrim.hs | 3 +- compiler/ghc.cabal.in | 8 +- compiler/llvmGen-ng/Data/BitCode/LLVM/Gen.hs | 1783 ++++++++++++++++++++ compiler/llvmGen-ng/Data/BitCode/LLVM/Gen/Monad.hs | 86 + compiler/main/CodeOutput.hs | 10 + compiler/main/DriverPipeline.hs | 5 +- compiler/main/DynFlags.hs | 12 +- compiler/typecheck/TcForeign.hs | 4 +- ghc.mk | 8 + libraries/base/tests/all.T | 2 +- libraries/data-bitcode | 1 + libraries/data-bitcode-edsl | 1 + libraries/data-bitcode-llvm | 1 + mk/build.mk.sample | 13 +- mk/flavours/{prof.mk => prof-llvmng.mk} | 6 +- mk/flavours/{quick-cross.mk => quick-cross-ng.mk} | 4 +- mk/flavours/{quick.mk => quick-llvmng.mk} | 4 +- packages | 3 + testsuite/config/ghc | 16 +- 21 files changed, 1961 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c274d4f6eb7184df0c6cab2cb2a8d6a2e8c5b21b From git at git.haskell.org Fri Oct 20 02:38:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:38:33 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng's head updated: Merge branch 'feature/D4058-cross-compiler-bindist' into wip/angerman/llvmng (a6d66e4) Message-ID: <20171020023833.8DAAF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/angerman/llvmng' now includes: a4ee289 Adds x86 NONE relocation type a1fc7ce Comments only a8fde18 Fix bug in the short-cut solver b1e0c65 Make GHC.IO.Buffer.summaryBuffer strict dbbee1b Fix nasty bug in w/w for absence analysis cb76754 Suppress error cascade in record fields a02039c Add regression test for #9725 a36eea1 Revert installing texinfo in CI systems 55001c0 Sync base/changelog.md ec9ac20 Add ability to produce crash dumps on Windows 8d64745 Optimize linker by minimizing calls to tryGCC to avoid fork/exec overhead. ef26182 Track the order of user-written tyvars in DataCon fa8035e Implement Div, Mod, and Log for type-level nats. 377d5a2 base: Add missing @since annotations in GHC.TypeNats de1b802 genapply: Explicitly specify arguments f3f624a Include libraries which fill holes as deps when linking. 4899a86 Don't pass HscEnv to functions in the Hsc monad 361af62 base: Remove deprecated Chan combinators 3201d85 user-guide: Mention COMPLETE pragma in release notes 3030eee rts: Print newline after "Stack trace:" on barf 7109fa8 configure: Accept *-msys as a Windows OS in a triple d8d87fa Remove m_type from Match (#14313) 429fafb Add regression test for #14326 f6bca0c Testsuite update following d8d87fa 341d3a7 Incorporate changes from #11721 into Template Haskell f1d2db6 Fix #14320 by looking through HsParTy in more places f337a20 Simply Data instance context for AmbiguousFieldOcc e51e565 Split SysTools up some 7720c29 Tidy up some convoluted "child/parent" code ab1a758 Typos in comments only 461c831 Minor refactoring c81f66c Fix over-eager error suppression in TcErrors 79ae03a Change "cobox" to "co" in debug output 3e44562 Delete two unused functions f20cf98 Remove wc_insol from WantedConstraints 9c3f731 Fix #10816 by renaming FixitySigs more consistently 6869864 Pretty-printing of derived multi-parameter classes omits parentheses 4bb54a4 Avoid creating dependent types in FloatOut 13fdca3 Add a missing zonk in TcDerivInfer.simplifyDeriv 82b77ec Do not quantify over deriving clauses 15aefb4 Add missing T14325.stderr fb050a3 Do not bind coercion variables in SpecConstr rules 3de788c Re-apply "Typeable: Allow App to match arrow types" 2be55b8 Delete obsolete docs on GADT interacton with TypeApplications 4a677f7 Remove section about ApplicativeDo & existentials (#13875) 8adb84f Fix calculation in threadStackOverflow afac6b1 Fix typo 6aa6a86 Fix typo add85cc Fix panic for `ByteArray#` arguments in CApiFFI foreign imports e3ba26f Implement new `compareByteArrays#` primop 5984a69 Override default `clearBit` method impl for `Natural` 843772b Enable testing 'Natural' type in TEST=arith011 6cc232a Implement {set,clear,complement}BitBigNat primitives 71a4235 configure: Fix CC version check on Apple compilers fd8b044 Levity polymorphic Backpack. 5dab544 FreeBSD dtrace probe support 7e790b3 rts: Label all threads created by the RTS 8536b7f users-guide: Rework and finish debug flag documentation d7f4f41 users guide: Eliminate redundant :category: tags in debugging.rst c5da84d users-guide: Fix various warnings a69fa54 rts/posix: Ensure that memory commit succeeds d6c33da RtClosureInspect: Fix inspecting Char# on 64-bit big-endian 366182a ghci: Include "Rts.h" before using TABLES_NEXT_TO_CODE 9e3add9 Flags.hsc: Peek a CBool (Word8), not a Bool (Int32) aa98268 updateThunk: indirectee can be tagged 21b7057 users-guide: Clarify -ddump-asm-regalloc-stages documentation 6cb4642 Bump ghc-prim to 0.5.2.0 and update changelog ed48d13 Simplify, no functionality change 2f43615 Fix grammaros in comments 317aa96 Improve user’s guide around deriving 74cd1be Don't deeply expand insolubles 5a66d57 Better solving for representational equalities aba7786 Typofix in comment 870020e whitespace only 20ae22b Accept test output for #14350 e023e78 Disable -XRebindableSyntax when running internal GHCi expressions 101a8c7 Error when deriving instances in hs-boot files 8846a7f Fix #14369 by making injectivity warnings finer-grained de8752e Export injectiveVarsOf{Binder,Type} from TyCoRep 7ac22b7 User's guide: Fix the category of some flags 383faef Build utilities with the bootstrap compiler when cross compiling 9ee3151 Fix binary distributions of cross compilers c274d4f Adds `-llvmng` 0945f08 Adds test 94c1277 bump submodule. a6d66e4 Merge branch 'feature/D4058-cross-compiler-bindist' into wip/angerman/llvmng From git at git.haskell.org Fri Oct 20 02:43:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:43:02 +0000 (UTC) Subject: [commit: ghc] master: Bump arcanist-external-json-linter submodule (3befc1a) Message-ID: <20171020024302.0A79B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3befc1af5d9f84a1e6b7a7eb66c949a5a50ef853/ghc >--------------------------------------------------------------- commit 3befc1af5d9f84a1e6b7a7eb66c949a5a50ef853 Author: Ben Gamari Date: Thu Oct 19 09:12:00 2017 -0400 Bump arcanist-external-json-linter submodule >--------------------------------------------------------------- 3befc1af5d9f84a1e6b7a7eb66c949a5a50ef853 .arc-linters/arcanist-external-json-linter | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.arc-linters/arcanist-external-json-linter b/.arc-linters/arcanist-external-json-linter index f640b15..957f9e4 160000 --- a/.arc-linters/arcanist-external-json-linter +++ b/.arc-linters/arcanist-external-json-linter @@ -1 +1 @@ -Subproject commit f640b1582f799d16ff500c5f456f9d1037a432bb +Subproject commit 957f9e4e8eb422dcb72f02f07767a1ed5969baab From git at git.haskell.org Fri Oct 20 02:42:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:42:59 +0000 (UTC) Subject: [commit: ghc] master: Expose monotonic time from GHC.Event.Clock (1ba2851) Message-ID: <20171020024259.45FB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ba28510e0731d91fcab560269c4ed5950d5e458/ghc >--------------------------------------------------------------- commit 1ba28510e0731d91fcab560269c4ed5950d5e458 Author: Tom Sydney Kerckhove Date: Wed Oct 18 16:24:46 2017 -0400 Expose monotonic time from GHC.Event.Clock This diff exposes the monotonic time api from GHC.Event.Clock. This is necessary for future work on regression tests (#D4074) for the timeout problems (8684, for example) in #D4041, #D4011, #D4012 Test Plan: Still builds ... Reviewers: nh2, bgamari, austin, hvr Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4079 >--------------------------------------------------------------- 1ba28510e0731d91fcab560269c4ed5950d5e458 libraries/base/GHC/{Event => }/Clock.hsc | 6 +++++- libraries/base/GHC/Event/TimerManager.hs | 2 +- libraries/base/base.cabal | 2 +- 3 files changed, 7 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Event/Clock.hsc b/libraries/base/GHC/Clock.hsc similarity index 90% rename from libraries/base/GHC/Event/Clock.hsc rename to libraries/base/GHC/Clock.hsc index 7f98a03..6339dc0 100644 --- a/libraries/base/GHC/Event/Clock.hsc +++ b/libraries/base/GHC/Clock.hsc @@ -1,7 +1,7 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude #-} -module GHC.Event.Clock +module GHC.Clock ( getMonotonicTime , getMonotonicTimeNSec ) where @@ -11,11 +11,15 @@ import GHC.Real import Data.Word -- | Return monotonic time in seconds, since some unspecified starting point +-- +-- @since 4.11.0.0 getMonotonicTime :: IO Double getMonotonicTime = do w <- getMonotonicTimeNSec return (fromIntegral w / 1000000000) -- | Return monotonic time in nanoseconds, since some unspecified starting point +-- +-- @since 4.11.0.0 foreign import ccall unsafe "getMonotonicNSec" getMonotonicTimeNSec :: IO Word64 diff --git a/libraries/base/GHC/Event/TimerManager.hs b/libraries/base/GHC/Event/TimerManager.hs index f3dbb21..b7e7615 100644 --- a/libraries/base/GHC/Event/TimerManager.hs +++ b/libraries/base/GHC/Event/TimerManager.hs @@ -43,11 +43,11 @@ import Data.Foldable (sequence_) import Data.IORef (IORef, atomicModifyIORef', mkWeakIORef, newIORef, readIORef, writeIORef) import GHC.Base +import GHC.Clock (getMonotonicTimeNSec) import GHC.Conc.Signal (runHandlers) import GHC.Num (Num(..)) import GHC.Real (fromIntegral) import GHC.Show (Show(..)) -import GHC.Event.Clock (getMonotonicTimeNSec) import GHC.Event.Control import GHC.Event.Internal (Backend, Event, evtRead, Timeout(..)) import GHC.Event.Unique (Unique, UniqueSource, newSource, newUnique) diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index 2b9d557..43c7882 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -204,6 +204,7 @@ Library GHC.Base GHC.ByteOrder GHC.Char + GHC.Clock GHC.Conc GHC.Conc.IO GHC.Conc.Signal @@ -369,7 +370,6 @@ Library other-modules: GHC.Event.Arr GHC.Event.Array - GHC.Event.Clock GHC.Event.Control GHC.Event.EPoll GHC.Event.IntTable From git at git.haskell.org Fri Oct 20 02:43:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:43:05 +0000 (UTC) Subject: [commit: ghc] master: Added a test for 'timeout' to be accurate. (13758c6) Message-ID: <20171020024305.4BAF63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/13758c6cfec1cfc8211d8c549ab69ee269f15b1e/ghc >--------------------------------------------------------------- commit 13758c6cfec1cfc8211d8c549ab69ee269f15b1e Author: Tom Sydney Kerckhove Date: Wed Oct 18 16:27:56 2017 -0400 Added a test for 'timeout' to be accurate. This is the first in a series of regression tests prompted by https://ghc.haskell.org/trac/ghc/ticket/8684 and D4011, D4012, D4041 Test Plan: This _is_ a test. Reviewers: nh2, austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #8684 Differential Revision: https://phabricator.haskell.org/D4074 >--------------------------------------------------------------- 13758c6cfec1cfc8211d8c549ab69ee269f15b1e libraries/base/tests/all.T | 1 + libraries/base/tests/timeout-accurate-pure.hs | 28 +++++++++++++++++++++++ libraries/base/tests/timeout-accurate-pure.stdout | 2 ++ 3 files changed, 31 insertions(+) diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index 9055bd5..a1eba6a 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -190,6 +190,7 @@ test('T8089', [exit_code(99), run_timeout_multiplier(0.01)], compile_and_run, ['']) test('T8684', expect_broken(8684), compile_and_run, ['']) +test('timeout-accurate-pure', normal, compile_and_run, ['']) test('T9826',normal, compile_and_run,['']) test('T9848', [ stats_num_field('bytes allocated', diff --git a/libraries/base/tests/timeout-accurate-pure.hs b/libraries/base/tests/timeout-accurate-pure.hs new file mode 100644 index 0000000..a59e785 --- /dev/null +++ b/libraries/base/tests/timeout-accurate-pure.hs @@ -0,0 +1,28 @@ +import Control.Concurrent +import Control.Monad +import GHC.Clock +import System.IO +import System.Timeout + +ack :: Integer -> Integer -> Integer +ack 0 n = n + 1 +ack m 0 = ack (m - 1) 1 +ack m n = ack (m - 1) (ack m (n - 1)) + +main :: IO () +main = do + let microsecondsPerSecond = 1000 * 1000 + let timeToSpend = 1 * microsecondsPerSecond -- One second in microseconds + start <- getMonotonicTimeNSec + timeout timeToSpend $ + -- Something that is guaranteed not to be done in 'timeToSpend' + print $ ack 4 2 + end <- getMonotonicTimeNSec + let timeSpentNano = fromIntegral $ end - start -- in nanoseconds + let nanosecondsPerMicrosecond = 1000 + let timeToSpendNano = timeToSpend * nanosecondsPerMicrosecond + let legRoom = 1 * 1000 * nanosecondsPerMicrosecond -- Nanoseconds + let delta = timeSpentNano - timeToSpendNano + -- We can never wait for a shorter amount of time than specified + putStrLn $ "delta > 0: " ++ show (delta > 0) + putStrLn $ "delta < legroom: " ++ show (delta < legRoom) diff --git a/libraries/base/tests/timeout-accurate-pure.stdout b/libraries/base/tests/timeout-accurate-pure.stdout new file mode 100644 index 0000000..90f4a4c --- /dev/null +++ b/libraries/base/tests/timeout-accurate-pure.stdout @@ -0,0 +1,2 @@ +delta > 0: True +delta < legroom: True From git at git.haskell.org Fri Oct 20 02:43:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:43:08 +0000 (UTC) Subject: [commit: ghc] master: Give a reference to Foreign.Concurrent. (098dc97) Message-ID: <20171020024308.0D3273A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/098dc97b80768a6aeabce4eb6d6d7e6e9a9a75b6/ghc >--------------------------------------------------------------- commit 098dc97b80768a6aeabce4eb6d6d7e6e9a9a75b6 Author: Edward Z. Yang Date: Wed Oct 18 16:32:17 2017 -0400 Give a reference to Foreign.Concurrent. Test Plan: none Reviewers: bgamari, austin, hvr Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4081 >--------------------------------------------------------------- 098dc97b80768a6aeabce4eb6d6d7e6e9a9a75b6 libraries/base/Foreign/ForeignPtr.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/libraries/base/Foreign/ForeignPtr.hs b/libraries/base/Foreign/ForeignPtr.hs index a684a8d..12bd4bf 100644 --- a/libraries/base/Foreign/ForeignPtr.hs +++ b/libraries/base/Foreign/ForeignPtr.hs @@ -15,6 +15,9 @@ -- Foreign Function Interface (FFI) and will usually be imported via -- the "Foreign" module. -- +-- For non-portable support of Haskell finalizers, see the +-- "Foreign.Concurrent" module. +-- ----------------------------------------------------------------------------- module Foreign.ForeignPtr ( From git at git.haskell.org Fri Oct 20 02:43:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:43:11 +0000 (UTC) Subject: [commit: ghc] master: Untag the potential AP_STACK in stg_getApStackValzh (b6204f7) Message-ID: <20171020024311.42F243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b6204f70501ec4ce4015503421c8a83c6f0fa008/ghc >--------------------------------------------------------------- commit b6204f70501ec4ce4015503421c8a83c6f0fa008 Author: James Clarke Date: Wed Oct 18 16:33:28 2017 -0400 Untag the potential AP_STACK in stg_getApStackValzh If the AP_STACK has been evaluated and a GC has run, the BLACKHOLE indirection will have been removed, and the StablePtr for the original AP_STACK referred to be GHCi will therefore now point directly to the value, and may be tagged. Add a hist002 test for this, and make sure hist001 doesn't do an idle GC, so the case when it's still a BLACKHOLE is definitely also tested. Reviewers: austin, bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4099 >--------------------------------------------------------------- b6204f70501ec4ce4015503421c8a83c6f0fa008 rts/PrimOps.cmm | 2 +- testsuite/tests/ghci.debugger/scripts/all.T | 5 ++++- .../tests/ghci.debugger/scripts/{hist001.script => hist002.script} | 5 +++++ .../tests/ghci.debugger/scripts/{hist001.stdout => hist002.stdout} | 0 4 files changed, 10 insertions(+), 2 deletions(-) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index bcf7b62..ca519b6 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -2391,7 +2391,7 @@ stg_noDuplicatezh /* no arg list: explicit stack layout */ stg_getApStackValzh ( P_ ap_stack, W_ offset ) { - if (%INFO_PTR(ap_stack) == stg_AP_STACK_info) { + if (%INFO_PTR(UNTAG(ap_stack)) == stg_AP_STACK_info) { return (1,StgAP_STACK_payload(ap_stack,offset)); } else { return (0,ap_stack); diff --git a/testsuite/tests/ghci.debugger/scripts/all.T b/testsuite/tests/ghci.debugger/scripts/all.T index d62dcd9..00a39d7 100644 --- a/testsuite/tests/ghci.debugger/scripts/all.T +++ b/testsuite/tests/ghci.debugger/scripts/all.T @@ -84,7 +84,10 @@ test('listCommand001', [extra_files(['../Test3.hs']), combined_output], ghci_script, ['listCommand001.script']) test('listCommand002', normal, ghci_script, ['listCommand002.script']) -test('hist001', extra_files(['../Test3.hs']), ghci_script, ['hist001.script']) +test('hist001', [extra_files(['../Test3.hs']), extra_run_opts('+RTS -I0')], + ghci_script, ['hist001.script']) +test('hist002', [extra_files(['../Test3.hs']), extra_run_opts('+RTS -I0')], + ghci_script, ['hist002.script']) test('T2740', normal, ghci_script, ['T2740.script']) diff --git a/testsuite/tests/ghci.debugger/scripts/hist001.script b/testsuite/tests/ghci.debugger/scripts/hist002.script similarity index 51% copy from testsuite/tests/ghci.debugger/scripts/hist001.script copy to testsuite/tests/ghci.debugger/scripts/hist002.script index a15b3b1..0198207 100644 --- a/testsuite/tests/ghci.debugger/scripts/hist001.script +++ b/testsuite/tests/ghci.debugger/scripts/hist002.script @@ -9,6 +9,11 @@ :back :show bindings :force _result +-- Run a GC so the BLACKHOLE indirection for _result (the AP_STACK) is removed, +-- ensuring _result now points directly to the value (in this case, the integer +-- 3). This will be tagged, so we are checking that the pointer isn't naively +-- dereferenced to generate an unaligned load. +System.Mem.performGC :back :forward -- at this point, we can't retrieve the bindings because _result (the AP_STACK) diff --git a/testsuite/tests/ghci.debugger/scripts/hist001.stdout b/testsuite/tests/ghci.debugger/scripts/hist002.stdout similarity index 100% copy from testsuite/tests/ghci.debugger/scripts/hist001.stdout copy to testsuite/tests/ghci.debugger/scripts/hist002.stdout From git at git.haskell.org Fri Oct 20 02:43:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:43:14 +0000 (UTC) Subject: [commit: ghc] master: Outputable: Add pprTraceException (afc04b2) Message-ID: <20171020024314.0B7C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/afc04b2689e5b936ecc8689c194a0ed2c0a2e6da/ghc >--------------------------------------------------------------- commit afc04b2689e5b936ecc8689c194a0ed2c0a2e6da Author: Ben Gamari Date: Thu Oct 19 13:25:51 2017 -0400 Outputable: Add pprTraceException >--------------------------------------------------------------- afc04b2689e5b936ecc8689c194a0ed2c0a2e6da compiler/utils/Outputable.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index c79cbc5..95960f5 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -81,8 +81,9 @@ module Outputable ( -- * Error handling and debugging utilities pprPanic, pprSorry, assertPprPanic, pprPgmError, pprTrace, pprTraceDebug, pprTraceIt, warnPprTrace, pprSTrace, + pprTraceException, trace, pgmError, panic, sorry, assertPanic, - pprDebugAndThen, callStackDoc + pprDebugAndThen, callStackDoc, ) where import GhcPrelude @@ -126,6 +127,8 @@ import Data.List (intersperse) import GHC.Fingerprint import GHC.Show ( showMultiLineString ) import GHC.Stack ( callStack, prettyCallStack ) +import Control.Monad.IO.Class +import Exception {- ************************************************************************ @@ -1168,6 +1171,13 @@ pprTrace str doc x pprTraceIt :: Outputable a => String -> a -> a pprTraceIt desc x = pprTrace desc (ppr x) x +-- | @pprTraceException desc x action@ runs action, printing a message +-- if it throws an exception. +pprTraceException :: ExceptionMonad m => String -> SDoc -> m a -> m a +pprTraceException heading doc = + handleGhcException $ \exc -> liftIO $ do + putStrLn $ showSDocDump unsafeGlobalDynFlags (sep [text heading, nest 2 doc]) + throwGhcExceptionIO exc -- | If debug output is on, show some 'SDoc' on the screen along -- with a call stack when available. From git at git.haskell.org Fri Oct 20 02:43:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:43:16 +0000 (UTC) Subject: [commit: ghc] master: Add Functor Bag instance (2ca8cf6) Message-ID: <20171020024316.C06073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2ca8cf69c50f6fcae17fdcbbcad16227519e5d02/ghc >--------------------------------------------------------------- commit 2ca8cf69c50f6fcae17fdcbbcad16227519e5d02 Author: Ben Gamari Date: Thu Oct 19 13:25:02 2017 -0400 Add Functor Bag instance >--------------------------------------------------------------- 2ca8cf69c50f6fcae17fdcbbcad16227519e5d02 compiler/utils/Bag.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/utils/Bag.hs b/compiler/utils/Bag.hs index a027db2..af5caad 100644 --- a/compiler/utils/Bag.hs +++ b/compiler/utils/Bag.hs @@ -330,5 +330,8 @@ instance Data a => Data (Bag a) where dataTypeOf _ = mkNoRepType "Bag" dataCast1 x = gcast1 x +instance Functor Bag where + fmap = mapBag + instance Foldable.Foldable Bag where foldr = foldrBag From git at git.haskell.org Fri Oct 20 02:43:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:43:56 +0000 (UTC) Subject: [commit: libffi-tarballs] master: Use make dist to generate snapshot (7922be9) Message-ID: <20171020024356.380243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/libffi-tarballs On branch : master Link : http://git.haskell.org/libffi-tarballs.git/commitdiff/7922be9302b92152c06a4fddb32431b5e7829590 >--------------------------------------------------------------- commit 7922be9302b92152c06a4fddb32431b5e7829590 Author: Ben Gamari Date: Mon Oct 2 09:36:20 2017 -0400 Use make dist to generate snapshot >--------------------------------------------------------------- 7922be9302b92152c06a4fddb32431b5e7829590 mk-snapshot.sh | 16 +++++++--------- 1 file changed, 7 insertions(+), 9 deletions(-) diff --git a/mk-snapshot.sh b/mk-snapshot.sh index 942abdc..40d2a85 100755 --- a/mk-snapshot.sh +++ b/mk-snapshot.sh @@ -18,20 +18,18 @@ REPO="${TMPD}/libffi" GHASH=$(git -C ${REPO} rev-parse --short HEAD) GDATE=$(git -C ${REPO} log -1 --pretty=format:%cd --date=format:%Y%m%d) SUFFIX="${GVERS}+git${GDATE}+${GHASH}" -git -C ${REPO} archive --format=tar --prefix="libffi-${SUFFIX}/" HEAD | tar -C ${TMPD} -x -# run and remove autogen, so we don't have to run it on the CI or elsewhere -# and as such incure additional dependencies like libtool. -(cd "${TMPD}/libffi-${SUFFIX}" && ./autogen.sh && rm autogen.sh) +# run autogen and generate distribution tarball. +(cd "$REPO" && ./autogen.sh && ./configure && make dist) # package it up -LIB="libffi-${SUFFIX}.tar.gz" -(cd "${TMPD}" && tar -czf "${LIB}" "libffi-${SUFFIX}") -mv "$TMPD/$LIB" ./$LIB +DISTLIB="libffi-${GVERS}.tar.gz" +FINALLIB="libffi-${SUFFIX}.tar.gz" +mv "$REPO/$DISTLIB" ./$FINALLIB -# create orphan branch +# create orphan libffi-tarballs branch git checkout --orphan "libffi-${SUFFIX}" -git add $LIB +git add $FINALLIB cat >README.md < Repository : ssh://git at git.haskell.org/libffi-tarballs On branch : master Link : http://git.haskell.org/libffi-tarballs.git/commitdiff/6f5a05456900ec39092ffc5602ee9e4c94359f10 >--------------------------------------------------------------- commit 6f5a05456900ec39092ffc5602ee9e4c94359f10 Author: Ben Gamari Date: Mon Oct 2 09:47:32 2017 -0400 Use bgamari's fork for the moment Due to https://github.com/libffi/libffi/pull/321 >--------------------------------------------------------------- 6f5a05456900ec39092ffc5602ee9e4c94359f10 mk-snapshot.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk-snapshot.sh b/mk-snapshot.sh index 40d2a85..bd4b7d5 100755 --- a/mk-snapshot.sh +++ b/mk-snapshot.sh @@ -10,7 +10,7 @@ TMPD=$(mktemp -d) TDIR=$(pwd) # clone the repository (shallow is sufficient) -git -C ${TMPD} clone --depth 1 https://github.com/libffi/libffi.git +git -C ${TMPD} clone --depth 1 https://github.com/bgamari/libffi.git REPO="${TMPD}/libffi" # record the revision and create a copy of only the files From git at git.haskell.org Fri Oct 20 02:57:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:57:48 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Build utilities with the bootstrap compiler when cross compiling (ec2b433) Message-ID: <20171020025748.19BD33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/ec2b433f05fea556989930848bf5290e88983e20/ghc >--------------------------------------------------------------- commit ec2b433f05fea556989930848bf5290e88983e20 Author: Moritz Angermann Date: Fri Sep 29 14:45:44 2017 +0800 Build utilities with the bootstrap compiler when cross compiling Summary: This should fix Trac #14297. When building a cross compiler, we have rather little use of utilities that do not run on the host, where the compiler runs. As such we should build the utilities with the bootstrap (stage 0) compiler rather than witht he in-tree (stage 1) compiler when CrossCompiling. This used to results in the utilities we ship in the binary distribution to be built for the wrong host. This diff tries to rectify the situation and allow the binary distribution to contain the utilities for the host when CrossCompiling. Reviewers: bgamari, trofi, hvr, austin Subscribers: rwbarton, thomie GHC Trac Issues: #14297 Differential Revision: https://phabricator.haskell.org/D4048 >--------------------------------------------------------------- ec2b433f05fea556989930848bf5290e88983e20 ghc.mk | 15 +++++++++++++-- utils/compare_sizes/ghc.mk | 4 +++- utils/hpc/ghc.mk | 18 +++++++++++++++++- utils/hsc2hs | 2 +- 4 files changed, 34 insertions(+), 5 deletions(-) diff --git a/ghc.mk b/ghc.mk index c3edc5e..f397f7c 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1056,6 +1056,17 @@ ifneq "$(CLEANING)" "YES" # This rule seems to hold some files open on Windows which prevents # cleaning, perhaps due to the $(wildcard). +# when building stage1only (a cross-compiler), we need to put the +# stage0 compiled ghc-cabal into the binary distribution. As the +# stage1 compiled ghc-cabal is built for the target, however +# ghc-cabal is used during 'make install' on the host, when +# installing the binary distribution. +ifeq "$(Stage1Only)" "YES" +DIST_GHC_CABAL=utils/ghc-cabal/dist/build/tmp/ghc-cabal +else +DIST_GHC_CABAL=utils/ghc-cabal/dist-install/build/tmp/ghc-cabal +endif + $(eval $(call bindist-list,.,\ LICENSE \ README \ @@ -1067,7 +1078,7 @@ $(eval $(call bindist-list,.,\ Makefile \ mk/config.mk.in \ $(INPLACE_BIN)/mkdirhier \ - utils/ghc-cabal/dist-install/build/tmp/ghc-cabal \ + $(DIST_GHC_CABAL) \ $(BINDIST_WRAPPERS) \ $(BINDIST_PERL_SOURCES) \ $(BINDIST_LIBS) \ @@ -1127,7 +1138,7 @@ unix-binary-dist-prep: echo "BUILD_SPHINX_HTML = $(BUILD_SPHINX_HTML)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_PDF = $(BUILD_SPHINX_PDF)" >> $(BIN_DIST_MK) echo "BUILD_MAN = $(BUILD_MAN)" >> $(BIN_DIST_MK) - echo "override ghc-cabal_INPLACE = utils/ghc-cabal/dist-install/build/tmp/ghc-cabal-bindist" >> $(BIN_DIST_MK) + echo "override ghc-cabal_INPLACE = $(DIST_GHC_CABAL)" >> $(BIN_DIST_MK) echo "UseSystemLibFFI = $(UseSystemLibFFI)" >> $(BIN_DIST_MK) # See Note [Persist CrossCompiling in binary distributions] echo "CrossCompiling = $(CrossCompiling)" >> $(BIN_DIST_MK) diff --git a/utils/compare_sizes/ghc.mk b/utils/compare_sizes/ghc.mk index d659a5e..1e601a3 100644 --- a/utils/compare_sizes/ghc.mk +++ b/utils/compare_sizes/ghc.mk @@ -5,5 +5,7 @@ utils/compare_sizes_MODULES = Main utils/compare_sizes_dist-install_PROGNAME = compareSizes utils/compare_sizes_dist-install_INSTALL_INPLACE = NO +# build compare_sizes only if not Stage1Only or not CrossCompiling. +ifeq "$(Stage1Only) $(CrossCompiling)" "NO NO" $(eval $(call build-prog,utils/compare_sizes,dist-install,1)) - +endif diff --git a/utils/hpc/ghc.mk b/utils/hpc/ghc.mk index f70be94..697e795 100644 --- a/utils/hpc/ghc.mk +++ b/utils/hpc/ghc.mk @@ -12,10 +12,26 @@ utils/hpc_USES_CABAL = YES utils/hpc_PACKAGE = hpc-bin -utils/hpc_dist-install_INSTALL = YES + +# built by ghc-stage0 +utils/hpc_dist_INSTALL_INPLACE = NO +utils/hpc_dist_PROGNAME = hpc +utils/hpc_dist_SHELL_WRAPPER = YES +utils/hpc_dist_INSTALL_SHELL_WRAPPER_NAME = hpc + +# built by ghc-stage1 utils/hpc_dist-install_INSTALL_INPLACE = YES utils/hpc_dist-install_PROGNAME = hpc utils/hpc_dist-install_SHELL_WRAPPER = YES utils/hpc_dist-install_INSTALL_SHELL_WRAPPER_NAME = hpc +ifeq "$(Stage1Only)" "YES" +utils/hpc_dist_INSTALL = YES +utils/hpc_dist-install_INSTALL = NO +else +utils/hpc_dist_INSTALL = NO +utils/hpc_dist-install_INSTALL = YES +endif + +$(eval $(call build-prog,utils/hpc,dist,0)) $(eval $(call build-prog,utils/hpc,dist-install,1)) diff --git a/utils/hsc2hs b/utils/hsc2hs index 936b088..94af7d9 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 936b0885ee794db83dc8473e17e153936e56d62f +Subproject commit 94af7d9a27307f40a8b18da0f8e0fd9e9d77e818 From git at git.haskell.org Fri Oct 20 02:57:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:57:50 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Fix binary distributions of cross compilers (4e4e717) Message-ID: <20171020025750.D5D1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/4e4e71791132a068423001714440f1fd5e040ead/ghc >--------------------------------------------------------------- commit 4e4e71791132a068423001714440f1fd5e040ead Author: Moritz Angermann Date: Mon Oct 2 13:47:45 2017 +0800 Fix binary distributions of cross compilers Summary: - copy over the original settings file Otherwise most of the custom cross compiler toolchain will be screwed up upon install. I'd rather have someone complain about a proper target-prefixed tool being missing, than getting garbaled output and a slew of strange errors because the final configure selected tools on the install machine just don't match up. - persist target-prefix. For cross compilers, retain the $target- prefix. This allows installing multiple cross compierls targetting different targets alongside each other. Reviewers: austin, hvr, bgamari Subscribers: rwbarton, trofi, thomie, hvr, bgamari, erikd Differential Revision: https://phabricator.haskell.org/D4058 >--------------------------------------------------------------- 4e4e71791132a068423001714440f1fd5e040ead distrib/configure.ac.in | 20 ++++++++++++++------ ghc.mk | 14 ++++++++++---- 2 files changed, 24 insertions(+), 10 deletions(-) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index 509e74e..62f6575 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -35,10 +35,9 @@ FPTOOLS_SET_PLATFORM_VARS # Requires FPTOOLS_SET_PLATFORM_VARS to be run first. FP_FIND_ROOT -# ToDo: if Stage1Only=YES, should be YES -CrossCompiling=NO -CrossCompilePrefix="" -TargetPlatformFull="${target}" +CrossCompiling=@CrossCompiling@ +CrossCompilePrefix=@CrossCompilePrefix@ +TargetPlatformFull=@TargetPlatformFull@ AC_SUBST(CrossCompiling) AC_SUBST(CrossCompilePrefix) @@ -198,8 +197,17 @@ fi FP_SETTINGS -# -AC_CONFIG_FILES(settings mk/config.mk mk/install.mk) +dnl ** Hack tools for cross compilers +dnl -------------------------------------------------------------- +dnl When building a binary distribution for cross compilers, +dnl we likely want to retain the target-prefixed tools, and not +dnl have configure overwrite them with what ever it finds, as +dnl the found tools likely do not target the target. +AC_CONFIG_FILES(mk/config.mk mk/install.mk) +if test "x$CrossCompiling" = "xNO"; then +AC_CONFIG_FILES(settings) +fi + AC_OUTPUT # We get caught by diff --git a/ghc.mk b/ghc.mk index f397f7c..66ae00a 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1060,11 +1060,17 @@ ifneq "$(CLEANING)" "YES" # stage0 compiled ghc-cabal into the binary distribution. As the # stage1 compiled ghc-cabal is built for the target, however # ghc-cabal is used during 'make install' on the host, when -# installing the binary distribution. -ifeq "$(Stage1Only)" "YES" +# installing the binary distribution. We will also copy the original +# `settings` file instead of having `configure` compute a new one. +# We do this because the bindist configure by default picks up +# the non-target prefixed toolchain; and cross compilers can be +# very sensitive to the toolchain. +ifeq "$(Stage1Only) $(CrossCompiling)" "YES YES" DIST_GHC_CABAL=utils/ghc-cabal/dist/build/tmp/ghc-cabal +DIST_SETTINGS=settings else DIST_GHC_CABAL=utils/ghc-cabal/dist-install/build/tmp/ghc-cabal +DIST_SETTINGS=settings.in endif $(eval $(call bindist-list,.,\ @@ -1072,7 +1078,7 @@ $(eval $(call bindist-list,.,\ README \ INSTALL \ configure config.sub config.guess install-sh \ - settings.in \ + $(DIST_SETTINGS) \ llvm-targets \ packages \ Makefile \ @@ -1133,7 +1139,7 @@ BIN_DIST_MK = $(BIN_DIST_PREP_DIR)/bindist.mk unix-binary-dist-prep: $(call removeTrees,bindistprep/) "$(MKDIRHIER)" $(BIN_DIST_PREP_DIR) - set -e; for i in packages LICENSE compiler ghc iserv rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh settings.in llvm-targets ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done + set -e; for i in packages LICENSE compiler ghc iserv rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh $(DIST_SETTINGS) llvm-targets ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done echo "HADDOCK_DOCS = $(HADDOCK_DOCS)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_HTML = $(BUILD_SPHINX_HTML)" >> $(BIN_DIST_MK) echo "BUILD_SPHINX_PDF = $(BUILD_SPHINX_PDF)" >> $(BIN_DIST_MK) From git at git.haskell.org Fri Oct 20 02:58:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:58:01 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump submodule. (265d2bb) Message-ID: <20171020025801.BDF4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/265d2bbcf25352ddf69a263ac7ea500e834638bc/ghc >--------------------------------------------------------------- commit 265d2bbcf25352ddf69a263ac7ea500e834638bc Author: Moritz Angermann Date: Wed Oct 4 09:48:01 2017 +0800 bump submodule. >--------------------------------------------------------------- 265d2bbcf25352ddf69a263ac7ea500e834638bc libraries/data-bitcode | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/data-bitcode b/libraries/data-bitcode index c9818de..2039075 160000 --- a/libraries/data-bitcode +++ b/libraries/data-bitcode @@ -1 +1 @@ -Subproject commit c9818debd3dae774967c0507882b6b3bec7f0ee4 +Subproject commit 2039075a4fcb1b0767c1df868b2deda96d6022c4 From git at git.haskell.org Fri Oct 20 02:57:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:57:55 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds `-llvmng` (658ae0b) Message-ID: <20171020025755.9A35F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/658ae0b30f5bc6df6baff52439d13f9acf5e2ad7/ghc >--------------------------------------------------------------- commit 658ae0b30f5bc6df6baff52439d13f9acf5e2ad7 Author: Moritz Angermann Date: Mon Jul 31 15:18:49 2017 +0800 Adds `-llvmng` >--------------------------------------------------------------- 658ae0b30f5bc6df6baff52439d13f9acf5e2ad7 .gitmodules | 9 + compiler/cmm/CmmSwitch.hs | 1 + compiler/codeGen/StgCmmPrim.hs | 3 +- compiler/ghc.cabal.in | 8 +- compiler/llvmGen-ng/Data/BitCode/LLVM/Gen.hs | 1783 ++++++++++++++++++++ compiler/llvmGen-ng/Data/BitCode/LLVM/Gen/Monad.hs | 86 + compiler/main/CodeOutput.hs | 10 + compiler/main/DriverPipeline.hs | 5 +- compiler/main/DynFlags.hs | 12 +- compiler/typecheck/TcForeign.hs | 4 +- ghc.mk | 8 + libraries/base/tests/all.T | 2 +- libraries/data-bitcode | 1 + libraries/data-bitcode-edsl | 1 + libraries/data-bitcode-llvm | 1 + mk/build.mk.sample | 13 +- mk/flavours/{prof.mk => prof-llvmng.mk} | 6 +- mk/flavours/{quick-cross.mk => quick-cross-ng.mk} | 4 +- mk/flavours/{quick.mk => quick-llvmng.mk} | 4 +- packages | 3 + testsuite/config/ghc | 16 +- 21 files changed, 1961 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 658ae0b30f5bc6df6baff52439d13f9acf5e2ad7 From git at git.haskell.org Fri Oct 20 02:57:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:57:58 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds test (8c4816e) Message-ID: <20171020025758.E019D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/8c4816e71f71a0aebbf6a62f119e8c32ce557bc1/ghc >--------------------------------------------------------------- commit 8c4816e71f71a0aebbf6a62f119e8c32ce557bc1 Author: Moritz Angermann Date: Thu Sep 21 22:07:44 2017 +0800 Adds test >--------------------------------------------------------------- 8c4816e71f71a0aebbf6a62f119e8c32ce557bc1 testsuite/tests/codeGen/should_run/T14251.hs | 22 ++++++++++++++++++++++ testsuite/tests/codeGen/should_run/T14251.stdout | 1 + testsuite/tests/codeGen/should_run/all.T | 1 + 3 files changed, 24 insertions(+) diff --git a/testsuite/tests/codeGen/should_run/T14251.hs b/testsuite/tests/codeGen/should_run/T14251.hs new file mode 100644 index 0000000..6f552e1 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14251.hs @@ -0,0 +1,22 @@ +{-# LANGUAGE MagicHash, BangPatterns #-} +module Main where + +-- A minor modification from T8064.hs. +-- +-- The key here is that we ensure that +-- subsequently passed floats do not +-- accidentally end up in previous +-- registers. +-- + +import GHC.Exts + +{-# NOINLINE f #-} +f :: (Int# -> Float# -> Double# -> Float# -> Double# -> String) -> String +f g = g 3# 4.0# 5.0## 6.0# 6.9## ++ " World!" + +{-# NOINLINE q #-} +q :: Int# -> Float# -> Double# -> Float# -> Double# -> String +q i j k l m = "Hello " ++ show (F# l) ++ " " ++ show (D# m) + +main = putStrLn (f $ q) diff --git a/testsuite/tests/codeGen/should_run/T14251.stdout b/testsuite/tests/codeGen/should_run/T14251.stdout new file mode 100644 index 0000000..8ec577b --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14251.stdout @@ -0,0 +1 @@ +Hello 6.0 6.9 World! diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 6aacea5..a5e5c64 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -159,3 +159,4 @@ test('T9577', [ unless(arch('x86_64') or arch('i386'),skip), test('T13425', normal, compile_and_run, ['-O']) test('castFloatWord', normal, compile_and_run, ['-dcmm-lint']) +test('T14251', normal, compile_and_run, ['-O2']) From git at git.haskell.org Fri Oct 20 02:58:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:58:06 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Merge branch 'feature/D4058-cross-compiler-bindist' into wip/angerman/llvmng (aa5f532) Message-ID: <20171020025806.242653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/aa5f532d207388e1b346f2225b081f6010d392ec/ghc >--------------------------------------------------------------- commit aa5f532d207388e1b346f2225b081f6010d392ec Merge: 265d2bb 4e4e717 Author: Moritz Angermann Date: Fri Oct 20 10:57:04 2017 +0800 Merge branch 'feature/D4058-cross-compiler-bindist' into wip/angerman/llvmng >--------------------------------------------------------------- aa5f532d207388e1b346f2225b081f6010d392ec distrib/configure.ac.in | 20 ++++++++++++++------ ghc.mk | 25 +++++++++++++++++++++---- utils/compare_sizes/ghc.mk | 4 +++- utils/hpc/ghc.mk | 18 +++++++++++++++++- utils/hsc2hs | 2 +- 5 files changed, 56 insertions(+), 13 deletions(-) From git at git.haskell.org Fri Oct 20 02:58:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 02:58:09 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng's head updated: Merge branch 'feature/D4058-cross-compiler-bindist' into wip/angerman/llvmng (aa5f532) Message-ID: <20171020025809.065D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/angerman/llvmng' now includes: 3befc1a Bump arcanist-external-json-linter submodule 1ba2851 Expose monotonic time from GHC.Event.Clock 13758c6 Added a test for 'timeout' to be accurate. 098dc97 Give a reference to Foreign.Concurrent. b6204f7 Untag the potential AP_STACK in stg_getApStackValzh 2ca8cf6 Add Functor Bag instance afc04b2 Outputable: Add pprTraceException ec2b433 Build utilities with the bootstrap compiler when cross compiling 4e4e717 Fix binary distributions of cross compilers 658ae0b Adds `-llvmng` 8c4816e Adds test 265d2bb bump submodule. aa5f532 Merge branch 'feature/D4058-cross-compiler-bindist' into wip/angerman/llvmng From git at git.haskell.org Fri Oct 20 12:01:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 12:01:58 +0000 (UTC) Subject: [commit: ghc] master: Comments and white space (c1efc6e) Message-ID: <20171020120158.A52FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1efc6e64edf140c2e5a09a3ef44b719c5d77f70/ghc >--------------------------------------------------------------- commit c1efc6e64edf140c2e5a09a3ef44b719c5d77f70 Author: Simon Peyton Jones Date: Wed Oct 18 15:21:16 2017 +0100 Comments and white space >--------------------------------------------------------------- c1efc6e64edf140c2e5a09a3ef44b719c5d77f70 compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcFlatten.hs | 3 +++ 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index e7f1259..be8bbee 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1845,7 +1845,7 @@ rewriteEvidence old_ev new_pred co | isTcReflCo co -- See Note [Rewriting with Refl] = continueWith (old_ev { ctev_pred = new_pred }) -rewriteEvidence ev@(CtGiven { ctev_evar = old_evar , ctev_loc = loc }) new_pred co +rewriteEvidence ev@(CtGiven { ctev_evar = old_evar, ctev_loc = loc }) new_pred co = do { new_ev <- newGivenEvVar loc (new_pred, new_tm) ; continueWith new_ev } where diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 9fd9cad..4d23b55 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -939,6 +939,9 @@ flatten_one (AppTy ty1 ty2) = do { (xi1,co1) <- flatten_one ty1 ; eq_rel <- getEqRel ; case (eq_rel, nextRole xi1) of + -- We need nextRole here because although ty1 definitely + -- isn't a TyConApp, xi1 might be. + -- ToDo: but can such a substitution change roles?? (NomEq, _) -> flatten_rhs xi1 co1 NomEq (ReprEq, Nominal) -> flatten_rhs xi1 co1 NomEq (ReprEq, Representational) -> flatten_rhs xi1 co1 ReprEq From git at git.haskell.org Fri Oct 20 12:02:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 12:02:02 +0000 (UTC) Subject: [commit: ghc] master: Improve kick-out in the constraint solver (3acd616) Message-ID: <20171020120202.7893B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3acd6164fea6d4d5d87521a291455a18c9c9a8ee/ghc >--------------------------------------------------------------- commit 3acd6164fea6d4d5d87521a291455a18c9c9a8ee Author: Simon Peyton Jones Date: Fri Oct 20 12:08:04 2017 +0100 Improve kick-out in the constraint solver This patch was provoked by Trac #14363. Turned out that we were kicking out too many constraints in TcSMonad.kickOutRewritable, and that mean that the work-list never became empty: infinite loop! That in turn made me look harder at the Main Theorem in Note [Extending the inert equalities]. Main changes * Replace TcType.isTyVarExposed by TcType.isTyVarHead. The over-agressive isTyVarExposed is what caused Trac #14363. See Note [K3: completeness of solving] in TcSMonad. * TcType.Make anyRewriteableTyVar role-aware. In particular, a ~R ty cannot rewrite b ~R f a See Note [anyRewriteableTyVar must be role-aware]. That means it has to be given a role argument, which forces a little refactoring. I think this change is fixing a bug that hasn't yet been reported. The actual reported bug is handled by the previous bullet. But this change is definitely the Right Thing The main changes are in TcSMonad.kick_out_rewritable, and in TcType (isTyVarExposed ---> isTyVarHead). I did a little unforced refactoring: * Use the cc_eq_rel field of a CTyEqCan when it is available, rather than recomputing it. * Define eqCanRewrite :: EqRel -> EqRel -> EqRel, and use it, instead of duplicating its logic >--------------------------------------------------------------- 3acd6164fea6d4d5d87521a291455a18c9c9a8ee compiler/typecheck/TcFlatten.hs | 7 +- compiler/typecheck/TcInteract.hs | 18 +-- compiler/typecheck/TcRnTypes.hs | 36 +++-- compiler/typecheck/TcSMonad.hs | 157 +++++++++++++-------- compiler/typecheck/TcType.hs | 92 +++++++----- testsuite/tests/typecheck/should_compile/T14363.hs | 11 ++ .../tests/typecheck/should_compile/T14363a.hs | 8 ++ testsuite/tests/typecheck/should_compile/all.T | 2 + 8 files changed, 207 insertions(+), 124 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 3acd6164fea6d4d5d87521a291455a18c9c9a8ee From git at git.haskell.org Fri Oct 20 12:50:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 12:50:53 +0000 (UTC) Subject: [commit: ghc] master: Update record-wildcard docs (e375bd3) Message-ID: <20171020125053.D38EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e375bd350bc9e719b757f4dc8c907c330b26ef6e/ghc >--------------------------------------------------------------- commit e375bd350bc9e719b757f4dc8c907c330b26ef6e Author: Simon Peyton Jones Date: Fri Oct 20 13:49:11 2017 +0100 Update record-wildcard docs This patch clarifies the story for record wildcards, following the discussion on Trac #14347. >--------------------------------------------------------------- e375bd350bc9e719b757f4dc8c907c330b26ef6e docs/users_guide/glasgow_exts.rst | 33 ++++++++++++++++++++++----------- 1 file changed, 22 insertions(+), 11 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 2499287..347a9f0 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -3410,11 +3410,6 @@ More details: refers to the nearest enclosing variables that are spelled the same as the omitted field names. -- Record wildcards may *not* be used in record *updates*. For example - this is illegal: :: - - f r = r { x = 3, .. } - - For both pattern and expression wildcards, the "``..``" expands to the missing *in-scope* record fields. Specifically the expansion of "``C {..}``" includes ``f`` if and only if: @@ -3424,12 +3419,6 @@ More details: - The record field ``f`` is in scope somehow (either qualified or unqualified). - - In the case of expressions (but not patterns), the variable ``f`` - is in scope unqualified, and is not imported or bound at top level. - For example, ``f`` can be bound by an enclosing pattern match or - let/where-binding. (The motivation here is that it should be - easy for the reader to figure out what the "``..``" expands to.) - These rules restrict record wildcards to the situations in which the user could have written the expanded version. For example :: @@ -3444,6 +3433,28 @@ More details: ``c`` is not in scope (apart from the binding of the record selector ``c``, of course). +- When record wildcards are use in record construction, a field ``f`` + is initialised only if ``f`` is in scope, + and is not imported or bound at top level. + For example, ``f`` can be bound by an enclosing pattern match or + let/where-binding. For example :: + + module M where + import A( a ) + + data R = R { a,b,c,d :: Int } + + c = 3 :: Int + + f b = R { .. } -- Expands to R { b = b, d = d } + where + d = b+1 + + Here, ``a`` is imported, and ``c`` is bound at top level, so neither + contribute to the expansion of the "``..``". + The motivation here is that it should be + easy for the reader to figure out what the "``..``" expands to. + - Record wildcards cannot be used (a) in a record update construct, and (b) for data constructors that are not declared with record fields. For example: :: From git at git.haskell.org Fri Oct 20 13:59:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 13:59:49 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T14373' created Message-ID: <20171020135949.AF9D73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T14373 Referencing: 9e02458022b4c24525c5f6e41e5d7b34309be424 From git at git.haskell.org Fri Oct 20 13:59:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 13:59:52 +0000 (UTC) Subject: [commit: ghc] wip/T14373: Implement pointer tagging for 'big' families #14373 (9e02458) Message-ID: <20171020135952.7587A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14373 Link : http://ghc.haskell.org/trac/ghc/changeset/9e02458022b4c24525c5f6e41e5d7b34309be424/ghc >--------------------------------------------------------------- commit 9e02458022b4c24525c5f6e41e5d7b34309be424 Author: Gabor Greif Date: Fri Oct 20 15:45:37 2017 +0200 Implement pointer tagging for 'big' families #14373 Formerly we punted on these and evaluated constructors always got a tag of 1. We now cascade switches because we have to check the tag first and when it is MAX_PTR_TAG then get the precise tag from the info table and switch on that. The only technically tricky part is that the default case needs (logical) duplication. To do this we emit an extra label for it and branch to that from the second switch. This avoids duplicated codegen. >--------------------------------------------------------------- 9e02458022b4c24525c5f6e41e5d7b34309be424 compiler/codeGen/StgCmmClosure.hs | 9 ++++-- compiler/codeGen/StgCmmExpr.hs | 61 +++++++++++++++++++++++++++++---------- 2 files changed, 53 insertions(+), 17 deletions(-) diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs index 1da1f70..be2c206 100644 --- a/compiler/codeGen/StgCmmClosure.hs +++ b/compiler/codeGen/StgCmmClosure.hs @@ -354,9 +354,12 @@ type DynTag = Int -- The tag on a *pointer* -- * big, otherwise. -- -- Small families can have the constructor tag in the tag bits. --- Big families only use the tag value 1 to represent evaluatedness. +-- Big families only use the tag value 1..mAX_PTR_TAG to represent +-- evaluatedness, the last one lumping together all overflowing ones. -- We don't have very many tag bits: for example, we have 2 bits on -- x86-32 and 3 bits on x86-64. +-- +-- Also see Note [tagging big families] isSmallFamily :: DynFlags -> Int -> Bool isSmallFamily dflags fam_size = fam_size <= mAX_PTR_TAG dflags @@ -364,10 +367,12 @@ isSmallFamily dflags fam_size = fam_size <= mAX_PTR_TAG dflags tagForCon :: DynFlags -> DataCon -> DynTag tagForCon dflags con | isSmallFamily dflags fam_size = con_tag - | otherwise = 1 + | con_tag <= max_tag = con_tag + | otherwise = max_tag where con_tag = dataConTag con -- NB: 1-indexed fam_size = tyConFamilySize (dataConTyCon con) + max_tag = mAX_PTR_TAG dflags tagForArity :: DynFlags -> RepArity -> DynTag tagForArity dflags arity diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index 3fcc935..a80de94 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -37,6 +37,7 @@ import Cmm import CmmInfo import CoreSyn import DataCon +import DynFlags ( mAX_PTR_TAG ) import ForeignCall import Id import PrimOp @@ -49,9 +50,10 @@ import Util import FastString import Outputable -import Control.Monad (unless,void) -import Control.Arrow (first) +import Control.Monad ( unless, void ) +import Control.Arrow ( first ) import Data.Function ( on ) +import Data.List ( partition ) ------------------------------------------------------------------------ -- cgExpr: the main function @@ -607,21 +609,36 @@ cgAlts gc_plan bndr (AlgAlt tycon) alts ; let fam_sz = tyConFamilySize tycon bndr_reg = CmmLocal (idToReg dflags bndr) + tag_expr = cmmConstrTag1 dflags (CmmReg bndr_reg) + branches' = [(tag+1,branch) | (tag,branch) <- branches] + maxpt = mAX_PTR_TAG dflags + (ptr, info) = partition ((< maxpt) . fst) branches' + small = isSmallFamily dflags fam_sz -- Is the constructor tag in the node reg? - ; if isSmallFamily dflags fam_sz - then do - let -- Yes, bndr_reg has constr. tag in ls bits - tag_expr = cmmConstrTag1 dflags (CmmReg bndr_reg) - branches' = [(tag+1,branch) | (tag,branch) <- branches] - emitSwitch tag_expr branches' mb_deflt 1 fam_sz - - else -- No, get tag from info table - let -- Note that ptr _always_ has tag 1 - -- when the family size is big enough - untagged_ptr = cmmRegOffB bndr_reg (-1) - tag_expr = getConstrTag dflags (untagged_ptr) - in emitSwitch tag_expr branches mb_deflt 0 (fam_sz - 1) + -- See Note [tagging big families] + ; if small || null info + then -- Yes, bndr_reg has constr. tag in ls bits + emitSwitch tag_expr branches' mb_deflt 1 (if small then fam_sz else maxpt) + + else -- No, get exact tag from info table when mAX_PTR_TAG + do + infos_lbl <- newBlockId -- branch destination for info pointer lookup + infos_scp <- getTickScope + + let catchall = (maxpt, (mkBranch infos_lbl, infos_scp)) + prelabel (Just (stmts, scp)) = + do lbl <- newBlockId + return (Just (mkLabel lbl scp <*> stmts, scp), Just (mkBranch lbl, scp)) + prelabel _ = return (Nothing, Nothing) + + (mb_deflt, mb_branch) <- prelabel mb_deflt + emitSwitch tag_expr (catchall : ptr) mb_deflt 1 maxpt + emitLabel infos_lbl + let untagged_ptr = cmmUntag dflags (CmmReg bndr_reg) + tag_expr = getConstrTag dflags untagged_ptr + info0 = (\(tag,branch)->(tag-1,branch)) <$> info + emitSwitch tag_expr info0 mb_branch (maxpt - 1) (fam_sz - 1) ; return AssignedDirectly } @@ -649,6 +666,20 @@ cgAlts _ _ _ _ = panic "cgAlts" -- x = R1 -- goto L1 + +-- Note [tagging big families] +-- +-- Previousy, only the small constructor families were tagged. +-- This penalized greater union which overflow the tag space +-- of TAG_BITS (i.e. 3 on 32 resp. 7 constructors on 64 bit). +-- But there is a clever way of combining pointer and info-table +-- tagging. We now use 1..{2,6} as pointer-resident tags while +-- {3,7} signifies we have to fall back and get the tag from the +-- info-table. +-- +-- Also see Note [Data constructor dynamic tags] + + ------------------- cgAlgAltRhss :: (GcPlan,ReturnKind) -> NonVoid Id -> [StgAlt] -> FCode ( Maybe CmmAGraphScoped From git at git.haskell.org Fri Oct 20 14:27:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Oct 2017 14:27:51 +0000 (UTC) Subject: [commit: ghc] wip/T14373: Implement pointer tagging for 'big' families #14373 (893f700) Message-ID: <20171020142751.8279B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14373 Link : http://ghc.haskell.org/trac/ghc/changeset/893f70083c071482d2c15321ae30caeeb663c0aa/ghc >--------------------------------------------------------------- commit 893f70083c071482d2c15321ae30caeeb663c0aa Author: Gabor Greif Date: Fri Oct 20 15:45:37 2017 +0200 Implement pointer tagging for 'big' families #14373 Formerly we punted on these and evaluated constructors always got a tag of 1. We now cascade switches because we have to check the tag first and when it is MAX_PTR_TAG then get the precise tag from the info table and switch on that. The only technically tricky part is that the default case needs (logical) duplication. To do this we emit an extra label for it and branch to that from the second switch. This avoids duplicated codegen. >--------------------------------------------------------------- 893f70083c071482d2c15321ae30caeeb663c0aa compiler/codeGen/StgCmmClosure.hs | 9 ++++-- compiler/codeGen/StgCmmExpr.hs | 67 ++++++++++++++++++++++++++++++--------- 2 files changed, 59 insertions(+), 17 deletions(-) diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs index 1da1f70..000983f 100644 --- a/compiler/codeGen/StgCmmClosure.hs +++ b/compiler/codeGen/StgCmmClosure.hs @@ -354,9 +354,12 @@ type DynTag = Int -- The tag on a *pointer* -- * big, otherwise. -- -- Small families can have the constructor tag in the tag bits. --- Big families only use the tag value 1 to represent evaluatedness. +-- Big families always use the tag values 1..mAX_PTR_TAG to represent +-- evaluatedness, the last one lumping together all overflowing ones. -- We don't have very many tag bits: for example, we have 2 bits on -- x86-32 and 3 bits on x86-64. +-- +-- Also see Note [tagging big families] isSmallFamily :: DynFlags -> Int -> Bool isSmallFamily dflags fam_size = fam_size <= mAX_PTR_TAG dflags @@ -364,10 +367,12 @@ isSmallFamily dflags fam_size = fam_size <= mAX_PTR_TAG dflags tagForCon :: DynFlags -> DataCon -> DynTag tagForCon dflags con | isSmallFamily dflags fam_size = con_tag - | otherwise = 1 + | con_tag <= max_tag = con_tag + | otherwise = max_tag where con_tag = dataConTag con -- NB: 1-indexed fam_size = tyConFamilySize (dataConTyCon con) + max_tag = mAX_PTR_TAG dflags tagForArity :: DynFlags -> RepArity -> DynTag tagForArity dflags arity diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index 3fcc935..6c00cef 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -37,6 +37,7 @@ import Cmm import CmmInfo import CoreSyn import DataCon +import DynFlags ( mAX_PTR_TAG ) import ForeignCall import Id import PrimOp @@ -49,9 +50,10 @@ import Util import FastString import Outputable -import Control.Monad (unless,void) -import Control.Arrow (first) +import Control.Monad ( unless, void ) +import Control.Arrow ( first ) import Data.Function ( on ) +import Data.List ( partition ) ------------------------------------------------------------------------ -- cgExpr: the main function @@ -607,21 +609,36 @@ cgAlts gc_plan bndr (AlgAlt tycon) alts ; let fam_sz = tyConFamilySize tycon bndr_reg = CmmLocal (idToReg dflags bndr) + tag_expr = cmmConstrTag1 dflags (CmmReg bndr_reg) + branches' = [(tag+1,branch) | (tag,branch) <- branches] + maxpt = mAX_PTR_TAG dflags + (ptr, info) = partition ((< maxpt) . fst) branches' + small = isSmallFamily dflags fam_sz -- Is the constructor tag in the node reg? - ; if isSmallFamily dflags fam_sz - then do - let -- Yes, bndr_reg has constr. tag in ls bits - tag_expr = cmmConstrTag1 dflags (CmmReg bndr_reg) - branches' = [(tag+1,branch) | (tag,branch) <- branches] - emitSwitch tag_expr branches' mb_deflt 1 fam_sz - - else -- No, get tag from info table - let -- Note that ptr _always_ has tag 1 - -- when the family size is big enough - untagged_ptr = cmmRegOffB bndr_reg (-1) - tag_expr = getConstrTag dflags (untagged_ptr) - in emitSwitch tag_expr branches mb_deflt 0 (fam_sz - 1) + -- See Note [tagging big families] + ; if small || null info + then -- Yes, bndr_reg has constr. tag in ls bits + emitSwitch tag_expr branches' mb_deflt 1 (if small then fam_sz else maxpt) + + else -- No, get exact tag from info table when mAX_PTR_TAG + do + infos_lbl <- newBlockId -- branch destination for info pointer lookup + infos_scp <- getTickScope + + let catchall = (maxpt, (mkBranch infos_lbl, infos_scp)) + prelabel (Just (stmts, scp)) = + do lbl <- newBlockId + return (Just (mkLabel lbl scp <*> stmts, scp), Just (mkBranch lbl, scp)) + prelabel _ = return (Nothing, Nothing) + + (mb_deflt, mb_branch) <- prelabel mb_deflt + emitSwitch tag_expr (catchall : ptr) mb_deflt 1 maxpt + emitLabel infos_lbl + let untagged_ptr = cmmUntag dflags (CmmReg bndr_reg) + tag_expr = getConstrTag dflags untagged_ptr + info0 = (\(tag,branch)->(tag-1,branch)) <$> info + emitSwitch tag_expr info0 mb_branch (maxpt - 1) (fam_sz - 1) ; return AssignedDirectly } @@ -649,6 +666,26 @@ cgAlts _ _ _ _ = panic "cgAlts" -- x = R1 -- goto L1 + +-- Note [tagging big families] +-- +-- Previousy, only the small constructor families were tagged. +-- This penalized greater unions which overflow the tag space +-- of TAG_BITS (i.e. 3 on 32 resp. 7 constructors on 64 bit). +-- But there is a clever way of combining pointer and info-table +-- tagging. We now use 1..{2,6} as pointer-resident tags while +-- {3,7} signifies we have to fall back and get the tag from the +-- info-table. +-- Conseqently we now cascade switches because we have to check +-- the tag first and when it is MAX_PTR_TAG then get the precise +-- tag from the info table and switch on that. The only technically +-- tricky part is that the default case needs (logical) duplication. +-- To do this we emit an extra label for it and branch to that from +-- the second switch. This avoids duplicated codegen. +-- +-- Also see Note [Data constructor dynamic tags] + + ------------------- cgAlgAltRhss :: (GcPlan,ReturnKind) -> NonVoid Id -> [StgAlt] -> FCode ( Maybe CmmAGraphScoped From git at git.haskell.org Sat Oct 21 14:19:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 21 Oct 2017 14:19:22 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Bring in Trees that Grow for HsType (6994048) Message-ID: <20171021141922.63DA63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/6994048621498a2d36c81f485fc9f35716a370b4/ghc >--------------------------------------------------------------- commit 6994048621498a2d36c81f485fc9f35716a370b4 Author: Alan Zimmerman Date: Sat Oct 21 16:18:13 2017 +0200 Bring in Trees that Grow for HsType And remove HasDefaultX and MonoidX classes Updates haddock submodule >--------------------------------------------------------------- 6994048621498a2d36c81f485fc9f35716a370b4 compiler/deSugar/Check.hs | 4 +- compiler/deSugar/DsMeta.hs | 54 ++-- compiler/deSugar/DsUtils.hs | 20 +- compiler/hsSyn/Convert.hs | 100 +++--- compiler/hsSyn/HsBinds.hs | 61 ++-- compiler/hsSyn/HsDecls.hs | 143 ++++----- compiler/hsSyn/HsExpr.hs | 208 ++++++++----- compiler/hsSyn/HsExpr.hs-boot | 36 ++- compiler/hsSyn/HsExtension.hs | 107 ++++--- compiler/hsSyn/HsLit.hs | 4 +- compiler/hsSyn/HsPat.hs | 28 +- compiler/hsSyn/HsPat.hs-boot | 6 +- compiler/hsSyn/HsSyn.hs | 5 +- compiler/hsSyn/HsTypes.hs | 343 +++++++++++++-------- compiler/hsSyn/HsUtils.hs | 105 ++++--- compiler/parser/Parser.y | 75 ++--- compiler/parser/RdrHsSyn.hs | 58 ++-- compiler/rename/RnNames.hs | 12 +- compiler/rename/RnSplice.hs | 5 +- compiler/rename/RnTypes.hs | 223 +++++++------- compiler/typecheck/Inst.hs | 5 +- compiler/typecheck/TcAnnotations.hs | 3 +- compiler/typecheck/TcBinds.hs | 5 +- compiler/typecheck/TcEnv.hs | 6 +- compiler/typecheck/TcExpr.hs | 5 +- compiler/typecheck/TcGenDeriv.hs | 13 +- compiler/typecheck/TcHsSyn.hs | 6 +- compiler/typecheck/TcHsType.hs | 74 +++-- compiler/typecheck/TcInstDcls.hs | 3 +- compiler/typecheck/TcPatSyn.hs | 6 +- compiler/typecheck/TcRnDriver.hs | 1 + compiler/typecheck/TcTyClsDecls.hs | 8 +- .../parser/should_compile/DumpParsedAst.stderr | 20 ++ .../parser/should_compile/DumpRenamedAst.stderr | 47 +++ .../tests/parser/should_compile/T14189.stderr | 2 + testsuite/tests/quasiquotation/T7918.hs | 2 +- utils/haddock | 2 +- 37 files changed, 1049 insertions(+), 756 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 6994048621498a2d36c81f485fc9f35716a370b4 From git at git.haskell.org Sat Oct 21 18:23:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 21 Oct 2017 18:23:40 +0000 (UTC) Subject: [commit: ghc] wip/ttg-2017-10-13: Remove PostRn / PostTc from HsType, using TTG (dd5caaa) Message-ID: <20171021182340.7E9643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg-2017-10-13 Link : http://ghc.haskell.org/trac/ghc/changeset/dd5caaaa88407f97ae913b2b4a2bea57d1da301c/ghc >--------------------------------------------------------------- commit dd5caaaa88407f97ae913b2b4a2bea57d1da301c Author: Alan Zimmerman Date: Sat Oct 21 20:22:59 2017 +0200 Remove PostRn / PostTc from HsType, using TTG And update haddock submodule to match >--------------------------------------------------------------- dd5caaaa88407f97ae913b2b4a2bea57d1da301c compiler/deSugar/DsMeta.hs | 18 ++--- compiler/hsSyn/Convert.hs | 11 +-- compiler/hsSyn/HsTypes.hs | 46 +++++++----- compiler/hsSyn/HsUtils.hs | 2 +- compiler/parser/Parser.y | 10 +-- compiler/rename/RnSplice.hs | 10 +-- compiler/rename/RnSplice.hs-boot | 4 +- compiler/rename/RnTypes.hs | 59 ++++++++------- compiler/typecheck/TcHsType.hs | 14 ++-- .../parser/should_compile/DumpParsedAst.stderr | 1 - .../parser/should_compile/DumpRenamedAst.stderr | 87 +++++++++++----------- utils/haddock | 2 +- 12 files changed, 131 insertions(+), 133 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 dd5caaaa88407f97ae913b2b4a2bea57d1da301c From git at git.haskell.org Sun Oct 22 03:25:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 03:25:07 +0000 (UTC) Subject: [commit: nofib] master: fasta: Inline function needs to be static (0574f35) Message-ID: <20171022032507.DF5C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0574f35e65a01b08e3fb8f89aeaa297f3a00900a/nofib >--------------------------------------------------------------- commit 0574f35e65a01b08e3fb8f89aeaa297f3a00900a Author: Joachim Breitner Date: Sat Oct 21 23:20:56 2017 -0400 fasta: Inline function needs to be static if I read http://gcc.gnu.org/onlinedocs/gcc/Inline.html correctly. Also, clean generated files. >--------------------------------------------------------------- 0574f35e65a01b08e3fb8f89aeaa297f3a00900a shootout/fasta/Makefile | 2 ++ shootout/fasta/fasta-c.c | 2 +- 2 files changed, 3 insertions(+), 1 deletion(-) diff --git a/shootout/fasta/Makefile b/shootout/fasta/Makefile index f6beb8e..97a8b17 100644 --- a/shootout/fasta/Makefile +++ b/shootout/fasta/Makefile @@ -5,6 +5,8 @@ include $(TOP)/mk/boilerplate.mk # we don't want to include fasta-c.c SRCS = Main.hs +CLEAN_FILES += fasta-c fasta.faststdout fasta.stdout fasta.slowstdout + FAST_OPTS = 250000 NORM_OPTS = 2500000 SLOW_OPTS = 25000000 # official shootout setting diff --git a/shootout/fasta/fasta-c.c b/shootout/fasta/fasta-c.c index 5779316..7219b49 100644 --- a/shootout/fasta/fasta-c.c +++ b/shootout/fasta/fasta-c.c @@ -37,7 +37,7 @@ amino homosapiens[] = { #define WIDTH 60 #define LENGTH(a) (sizeof(a)/sizeof(a[0])) -inline void str_write(char *s) { +static inline void str_write(char *s) { write(fileno(stdout), s, strlen(s)); } From git at git.haskell.org Sun Oct 22 03:25:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 03:25:09 +0000 (UTC) Subject: [commit: nofib] master: Notes: Link to #8611 (cacheprof nondeterministic) (c241954) Message-ID: <20171022032509.E83AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c24195479551800e1e3f45b1d977f04a546889d3/nofib >--------------------------------------------------------------- commit c24195479551800e1e3f45b1d977f04a546889d3 Author: Joachim Breitner Date: Sat Oct 21 23:24:37 2017 -0400 Notes: Link to #8611 (cacheprof nondeterministic) >--------------------------------------------------------------- c24195479551800e1e3f45b1d977f04a546889d3 Simon-nofib-notes | 1 + 1 file changed, 1 insertion(+) diff --git a/Simon-nofib-notes b/Simon-nofib-notes index 30c4e6f..33e9597 100644 --- a/Simon-nofib-notes +++ b/Simon-nofib-notes @@ -420,6 +420,7 @@ cacheprof ~~~~~~~~~ Sucessive runs with the same data can yield different allocation totals, for some reason. +Reported at https://ghc.haskell.org/trac/ghc/ticket/8611 gg ~~ From git at git.haskell.org Sun Oct 22 11:18:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 11:18:58 +0000 (UTC) Subject: [commit: ghc] master: Add stack traces on crashes on Windows (99c61e2) Message-ID: <20171022111858.6C4523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/99c61e2220c4cba20117107f371aace68668a42f/ghc >--------------------------------------------------------------- commit 99c61e2220c4cba20117107f371aace68668a42f Author: Tamar Christina Date: Sun Oct 22 12:14:22 2017 +0100 Add stack traces on crashes on Windows Summary: This patch adds the ability to generate stack traces on crashes for Windows. When running in the interpreter this attempts to use symbol information from the interpreter and information we know about the loaded object files to resolve addresses to symbols. When running compiled it doesn't have this information and then defaults to using symbol information from PDB files. Which for now means only files compiled with ICC or MSVC will show traces compiled. But I have a future patch that may address this shortcoming. Also since I don't know how to walk a pure haskell stack, I can for now only show the last entry. I'm hoping to figure out how Apply.cmm works to be able to walk the stalk and give more entries for pure haskell code. In GHCi ``` $ echo main | inplace/bin/ghc-stage2.exe --interactive ./testsuite/tests/rts/derefnull.hs GHCi, version 8.3.20170830: http://www.haskell.org/ghc/ :? for help Ok, 1 module loaded. Prelude Main> Access violation in generated code when reading 0x0 Attempting to reconstruct a stack trace... Frame Code address * 0x77cde10 0xc370229 E:\..\base\dist-install\build\HSbase-4.10.0.0.o+0x190031 (base_ForeignziStorable_zdfStorableInt4_info+0x3f) ``` and compiled ``` Access violation in generated code when reading 0x0 Attempting to reconstruct a stack trace... Frame Code address * 0xf0dbd0 0x40bb01 E:\..\rts\derefnull.run\derefnull.exe+0xbb01 ``` Test Plan: ./validate Reviewers: austin, hvr, bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3913 >--------------------------------------------------------------- 99c61e2220c4cba20117107f371aace68668a42f docs/users_guide/8.4.1-notes.rst | 4 + docs/users_guide/runtime_control.rst | 6 + includes/rts/Flags.h | 1 + libraries/base/GHC/RTS/Flags.hsc | 3 + libraries/base/changelog.md | 3 + rts/Linker.c | 15 ++ rts/LinkerInternals.h | 3 + rts/RtsFlags.c | 15 ++ rts/linker/PEi386.c | 196 +++++++++++++++++++++ rts/linker/PEi386.h | 2 + rts/package.conf.in | 1 + rts/win32/veh_excn.c | 96 +++++++++- rts/win32/veh_excn.h | 1 + testsuite/tests/rts/all.T | 8 +- .../rts/derefnull.stdout-i386-unknown-mingw32 | 1 - .../rts/derefnull.stdout-x86_64-unknown-mingw32 | 1 - .../rts/divbyzero.stdout-i386-unknown-mingw32 | 1 - .../rts/divbyzero.stdout-x86_64-unknown-mingw32 | 1 - 18 files changed, 346 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 99c61e2220c4cba20117107f371aace68668a42f From git at git.haskell.org Sun Oct 22 14:36:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 14:36:12 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: No recomputation of host/build/target for binary distributions. (156fe18) Message-ID: <20171022143612.1F2223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/156fe185d416d48e91995fa420e534a5af6ea8fb/ghc >--------------------------------------------------------------- commit 156fe185d416d48e91995fa420e534a5af6ea8fb Author: Moritz Angermann Date: Sun Oct 22 20:33:12 2017 +0800 No recomputation of host/build/target for binary distributions. >--------------------------------------------------------------- 156fe185d416d48e91995fa420e534a5af6ea8fb aclocal.m4 | 2 ++ distrib/configure.ac.in | 5 ++--- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 64fa8bf..9848029 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -170,6 +170,8 @@ AC_DEFUN([FPTOOLS_SET_PLATFORM_VARS], AC_SUBST(exeext_target) AC_SUBST(soext_host) AC_SUBST(soext_target) + + AC_SUBST(windows) ]) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index 62f6575..9d3c2c4 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -30,9 +30,8 @@ AC_CANONICAL_BUILD AC_CANONICAL_HOST AC_CANONICAL_TARGET -FPTOOLS_SET_PLATFORM_VARS - -# Requires FPTOOLS_SET_PLATFORM_VARS to be run first. +# FP_FIND_ROOT requires knowledge about $windows; inherit it. +windows=@windows@ FP_FIND_ROOT CrossCompiling=@CrossCompiling@ From git at git.haskell.org Sun Oct 22 14:36:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 14:36:14 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds a bit of documentation. (759e6b2) Message-ID: <20171022143614.DF2413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/759e6b295716fef86791ca0189bf28fb5556e85c/ghc >--------------------------------------------------------------- commit 759e6b295716fef86791ca0189bf28fb5556e85c Author: Moritz Angermann Date: Sun Oct 22 22:01:37 2017 +0800 Adds a bit of documentation. >--------------------------------------------------------------- 759e6b295716fef86791ca0189bf28fb5556e85c distrib/configure.ac.in | 10 ++++++++++ mk/install.mk.in | 0 2 files changed, 10 insertions(+) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index 9d3c2c4..adecf7c 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -1,6 +1,16 @@ dnl dnl Binary distribution configure script dnl +dnl This script will compute the neccessary substitutions (@...@) for +dnl - mk/config.mk.in +dnl - mk/install.mk.in +dnl and if NOT cross compiling +dnl - settings.in +dnl +dnl The general process is to compute a value, and then make it +dnl available via AC_SUBST, and subsequently calling AC_CONFIG_FILES +dnl to turn a x.in file into x. +dnl #!/bin/sh # From git at git.haskell.org Sun Oct 22 14:36:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 14:36:19 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Merge branch 'feature/no-ghc-triple' into wip/angerman/llvmng (b9279f1) Message-ID: <20171022143619.465213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/b9279f1327fa4aa6717b3cd324ef03abf6177901/ghc >--------------------------------------------------------------- commit b9279f1327fa4aa6717b3cd324ef03abf6177901 Merge: 265d2bb 759e6b2 Author: Moritz Angermann Date: Sun Oct 22 22:34:36 2017 +0800 Merge branch 'feature/no-ghc-triple' into wip/angerman/llvmng >--------------------------------------------------------------- b9279f1327fa4aa6717b3cd324ef03abf6177901 aclocal.m4 | 2 ++ distrib/configure.ac.in | 35 ++++++++++++++++++++++++++--------- ghc.mk | 25 +++++++++++++++++++++---- mk/install.mk.in | 0 utils/compare_sizes/ghc.mk | 4 +++- utils/hpc/ghc.mk | 18 +++++++++++++++++- utils/hsc2hs | 2 +- 7 files changed, 70 insertions(+), 16 deletions(-) From git at git.haskell.org Sun Oct 22 19:12:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 19:12:35 +0000 (UTC) Subject: [commit: ghc] branch 'wip/ttg/2017-10-21' created Message-ID: <20171022191235.C08823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/ttg/2017-10-21 Referencing: 841e5189f9543638f3b67a30350bedf5e9bef5f5 From git at git.haskell.org Sun Oct 22 19:12:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 19:12:41 +0000 (UTC) Subject: [commit: ghc] wip/ttg/2017-10-21: TTG for HsTyVarBndr (d416637) Message-ID: <20171022191241.8CF933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg/2017-10-21 Link : http://ghc.haskell.org/trac/ghc/changeset/d4166374e7c0b13b1faa9b334460ce2797b9d690/ghc >--------------------------------------------------------------- commit d4166374e7c0b13b1faa9b334460ce2797b9d690 Author: Alan Zimmerman Date: Sun Oct 22 13:07:05 2017 +0200 TTG for HsTyVarBndr Updates haddock submodule >--------------------------------------------------------------- d4166374e7c0b13b1faa9b334460ce2797b9d690 compiler/deSugar/DsMeta.hs | 16 +++++++------ compiler/hsSyn/Convert.hs | 4 ++-- compiler/hsSyn/HsDecls.hs | 6 ++--- compiler/hsSyn/HsExtension.hs | 19 +++++++++++++--- compiler/hsSyn/HsTypes.hs | 26 +++++++++++++++++----- compiler/hsSyn/HsUtils.hs | 12 +++++----- compiler/parser/Parser.y | 4 ++-- compiler/parser/RdrHsSyn.hs | 4 ++-- compiler/rename/RnTypes.hs | 19 +++++++++------- compiler/typecheck/TcHsType.hs | 11 +++++---- compiler/typecheck/TcRnDriver.hs | 7 +++--- compiler/typecheck/TcTyClsDecls.hs | 4 ++-- .../parser/should_compile/DumpParsedAst.stderr | 1 + .../parser/should_compile/DumpRenamedAst.stderr | 2 ++ utils/haddock | 2 +- 15 files changed, 89 insertions(+), 48 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 d4166374e7c0b13b1faa9b334460ce2797b9d690 From git at git.haskell.org Sun Oct 22 19:12:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 19:12:44 +0000 (UTC) Subject: [commit: ghc] wip/ttg/2017-10-21: TTG For HsAppType (bcef400) Message-ID: <20171022191244.5E26F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg/2017-10-21 Link : http://ghc.haskell.org/trac/ghc/changeset/bcef400aa322b2d4bb0fe820088c36493c1440d8/ghc >--------------------------------------------------------------- commit bcef400aa322b2d4bb0fe820088c36493c1440d8 Author: Alan Zimmerman Date: Sun Oct 22 14:48:04 2017 +0200 TTG For HsAppType >--------------------------------------------------------------- bcef400aa322b2d4bb0fe820088c36493c1440d8 compiler/hsSyn/Convert.hs | 6 ++-- compiler/hsSyn/HsExtension.hs | 12 ++++++++ compiler/hsSyn/HsTypes.hs | 33 ++++++++++++++-------- compiler/hsSyn/HsUtils.hs | 2 +- compiler/parser/Parser.y | 10 +++---- compiler/parser/RdrHsSyn.hs | 16 +++++------ compiler/rename/RnNames.hs | 4 +-- compiler/rename/RnTypes.hs | 10 ++++--- .../parser/should_compile/DumpParsedAst.stderr | 11 ++++++++ 9 files changed, 70 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bcef400aa322b2d4bb0fe820088c36493c1440d8 From git at git.haskell.org Sun Oct 22 19:12:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 19:12:38 +0000 (UTC) Subject: [commit: ghc] wip/ttg/2017-10-21: WIP on Doing a combined Step 1 and 3 for Trees That Grow (bf1b194) Message-ID: <20171022191238.BA47D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg/2017-10-21 Link : http://ghc.haskell.org/trac/ghc/changeset/bf1b1948288bd5782442c77eedd801faf7f0f423/ghc >--------------------------------------------------------------- commit bf1b1948288bd5782442c77eedd801faf7f0f423 Author: Alan Zimmerman Date: Sat Oct 14 16:00:35 2017 +0200 WIP on Doing a combined Step 1 and 3 for Trees That Grow - ValBinds worked through, compiles and expected tests pass - Tests now pass, HsPat fully implemented for TTG. - Update HsLit for current TTG implementation. - Trees that Grow for HsOverLit - Bring in Trees that Grow for HsType And update haddock submodule to match >--------------------------------------------------------------- bf1b1948288bd5782442c77eedd801faf7f0f423 compiler/deSugar/Check.hs | 53 +-- compiler/deSugar/DsArrows.hs | 30 +- compiler/deSugar/DsExpr.hs | 2 +- compiler/deSugar/DsMeta.hs | 85 ++--- compiler/deSugar/DsUtils.hs | 63 ++-- compiler/deSugar/Match.hs | 71 ++-- compiler/deSugar/MatchLit.hs | 27 +- compiler/hsSyn/Convert.hs | 146 ++++---- compiler/hsSyn/HsBinds.hs | 163 ++++++--- compiler/hsSyn/HsDecls.hs | 145 ++++---- compiler/hsSyn/HsExpr.hs | 334 ++++++++++++------ compiler/hsSyn/HsExpr.hs-boot | 46 +-- compiler/hsSyn/HsExtension.hs | 244 +++++++++---- compiler/hsSyn/HsLit.hs | 71 +++- compiler/hsSyn/HsPat.hs | 299 ++++++++++------ compiler/hsSyn/HsPat.hs-boot | 6 +- compiler/hsSyn/HsSyn.hs | 5 +- compiler/hsSyn/HsTypes.hs | 378 +++++++++++++-------- compiler/hsSyn/HsUtils.hs | 176 +++++----- compiler/hsSyn/PlaceHolder.hs | 19 +- compiler/main/HscStats.hs | 2 +- compiler/main/InteractiveEval.hs | 3 +- compiler/parser/Parser.y | 83 ++--- compiler/parser/RdrHsSyn.hs | 86 ++--- compiler/rename/RnBinds.hs | 10 +- compiler/rename/RnExpr.hs | 41 ++- compiler/rename/RnNames.hs | 14 +- compiler/rename/RnPat.hs | 79 ++--- compiler/rename/RnSource.hs | 10 +- compiler/rename/RnSplice.hs | 16 +- compiler/rename/RnSplice.hs-boot | 4 +- compiler/rename/RnTypes.hs | 246 +++++++------- compiler/typecheck/Inst.hs | 17 +- compiler/typecheck/TcAnnotations.hs | 3 +- compiler/typecheck/TcBinds.hs | 5 +- compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcEnv.hs | 6 +- compiler/typecheck/TcExpr.hs | 5 +- compiler/typecheck/TcGenDeriv.hs | 15 +- compiler/typecheck/TcGenFunctor.hs | 1 + compiler/typecheck/TcHsSyn.hs | 120 +++---- compiler/typecheck/TcHsType.hs | 70 ++-- compiler/typecheck/TcInstDcls.hs | 3 +- compiler/typecheck/TcPat.hs | 71 ++-- compiler/typecheck/TcPatSyn.hs | 122 +++---- compiler/typecheck/TcRnDriver.hs | 13 +- compiler/typecheck/TcTyClsDecls.hs | 8 +- compiler/typecheck/TcTyDecls.hs | 3 +- ghc/GHCi/UI/Info.hs | 4 +- .../parser/should_compile/DumpParsedAst.stderr | 21 +- .../parser/should_compile/DumpRenamedAst.stderr | 137 +++++--- .../tests/parser/should_compile/T14189.stderr | 9 +- testsuite/tests/quasiquotation/T7918.hs | 4 +- utils/ghctags/Main.hs | 23 +- utils/haddock | 2 +- 55 files changed, 2166 insertions(+), 1455 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 bf1b1948288bd5782442c77eedd801faf7f0f423 From git at git.haskell.org Sun Oct 22 19:12:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Oct 2017 19:12:47 +0000 (UTC) Subject: [commit: ghc] wip/ttg/2017-10-21: TTG for FieldOcc and AmbiguousFieldOcc (841e518) Message-ID: <20171022191247.5AB9A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg/2017-10-21 Link : http://ghc.haskell.org/trac/ghc/changeset/841e5189f9543638f3b67a30350bedf5e9bef5f5/ghc >--------------------------------------------------------------- commit 841e5189f9543638f3b67a30350bedf5e9bef5f5 Author: Alan Zimmerman Date: Sun Oct 22 21:10:16 2017 +0200 TTG for FieldOcc and AmbiguousFieldOcc Updates haddock submodule >--------------------------------------------------------------- 841e5189f9543638f3b67a30350bedf5e9bef5f5 compiler/deSugar/DsMeta.hs | 7 +-- compiler/hsSyn/Convert.hs | 2 +- compiler/hsSyn/HsExtension.hs | 35 +++++++++++-- compiler/hsSyn/HsPat.hs | 10 ++-- compiler/hsSyn/HsTypes.hs | 61 ++++++++++++++++------ compiler/hsSyn/HsUtils.hs | 2 +- compiler/hsSyn/PlaceHolder.hs | 7 +-- compiler/parser/Parser.y | 2 +- compiler/parser/RdrHsSyn.hs | 6 ++- compiler/rename/RnExpr.hs | 5 +- compiler/rename/RnFixity.hs | 5 +- compiler/rename/RnNames.hs | 6 ++- compiler/rename/RnPat.hs | 16 +++--- compiler/rename/RnSource.hs | 2 +- compiler/rename/RnTypes.hs | 3 +- compiler/typecheck/TcExpr.hs | 38 ++++++++------ compiler/typecheck/TcHsSyn.hs | 4 +- compiler/typecheck/TcPat.hs | 6 ++- compiler/typecheck/TcTyDecls.hs | 2 +- .../tests/parser/should_compile/T14189.stderr | 4 +- utils/haddock | 2 +- 21 files changed, 146 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 841e5189f9543638f3b67a30350bedf5e9bef5f5 From git at git.haskell.org Mon Oct 23 02:45:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 02:45:11 +0000 (UTC) Subject: [commit: ghc] master: nofib submodule: Fix a problem with fasta-c.c (bb537b2) Message-ID: <20171023024511.8386A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bb537b2ec239202d6ad5e6c9a11299363eda357f/ghc >--------------------------------------------------------------- commit bb537b2ec239202d6ad5e6c9a11299363eda357f Author: Joachim Breitner Date: Sun Oct 22 22:44:39 2017 -0400 nofib submodule: Fix a problem with fasta-c.c >--------------------------------------------------------------- bb537b2ec239202d6ad5e6c9a11299363eda357f nofib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nofib b/nofib index 5748d42..c241954 160000 --- a/nofib +++ b/nofib @@ -1 +1 @@ -Subproject commit 5748d428204ea0552f70b2981eaf30d4a5cfd3e9 +Subproject commit c24195479551800e1e3f45b1d977f04a546889d3 From git at git.haskell.org Mon Oct 23 03:45:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 03:45:02 +0000 (UTC) Subject: [commit: nofib] master: Add digits-of-e1.faststdout (d9e9707) Message-ID: <20171023034502.484C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d9e97074859a1f5bb9168da4d4e1b9fd7d8f0420/nofib >--------------------------------------------------------------- commit d9e97074859a1f5bb9168da4d4e1b9fd7d8f0420 Author: Joachim Breitner Date: Sun Oct 22 23:44:25 2017 -0400 Add digits-of-e1.faststdout >--------------------------------------------------------------- d9e97074859a1f5bb9168da4d4e1b9fd7d8f0420 imaginary/digits-of-e1/digits-of-e1.faststdout | 1 + 1 file changed, 1 insertion(+) diff --git a/imaginary/digits-of-e1/digits-of-e1.faststdout b/imaginary/digits-of-e1/digits-of-e1.faststdout new file mode 100644 index 0000000..bb39642 --- /dev/null +++ b/imaginary/digits-of-e1/digits-of-e1.faststdout @@ -0,0 +1 @@ +[2,7,1,8,2,8,1,8,2,8,4,5,9,0,4,5,2,3,5,3,6,0,2,8,7,4,7,1,3,5,2,6,6,2,4,9,7,7,5,7,2,4,7,0,9,3,6,9,9,9,5,9,5,7,4,9,6,6,9,6,7,6,2,7,7,2,4,0,7,6,6,3,0,3,5,3,5,4,7,5,9,4,5,7,1,3,8,2,1,7,8,5,2,5,1,6,6,4,2,7,4,2,7,4,6,6,3,9,1,9,3,2,0,0,3,0,5,9,9,2,1,8,1,7,4,1,3,5,9,6,6,2,9,0,4,3,5,7,2,9,0,0,3,3,4,2,9,5,2,6,0,5,9,5,6,3,0,7,3,8,1,3,2,3,2,8,6,2,7,9,4,3,4,9,0,7,6,3,2,3,3,8,2,9,8,8,0,7,5,3,1,9,5,2,5,1,0,1,9,0,1,1,5,7,3,8,3,4,1,8,7,9,3,0,7,0,2,1,5,4,0,8,9,1,4,9,9,3,4,8,8,4,1,6,7,5,0,9,2,4,4,7,6,1,4,6,0,6,6,8,0,8,2,2,6,4,8,0,0,1,6,8,4,7,7,4,1,1,8,5,3,7,4,2,3,4,5,4,4,2,4,3,7,1,0,7,5,3,9,0,7,7,7,4,4,9,9,2,0,6,9,5,5,1,7,0,2,7,6,1,8,3,8,6,0,6,2,6,1,3,3,1,3,8,4,5,8,3,0,0,0,7,5,2,0,4,4,9,3,3,8,2,6,5,6,0,2,9,7,6,0,6,7,3,7,1,1,3,2,0,0,7,0,9,3,2,8,7,0,9,1,2,7,4,4,3,7,4,7,0,4,7,2,3,0,6,9,6,9,7,7,2,0,9,3,1,0,1,4,1,6,9,2,8,3,6,8,1,9,0,2,5,5,1,5,1,0,8,6,5,7,4,6,3,7,7,2,1,1,1,2,5,2,3,8,9,7,8,4,4,2,5,0,5,6,9,5,3,6,9] From git at git.haskell.org Mon Oct 23 03:45:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 03:45:33 +0000 (UTC) Subject: [commit: ghc] master: submodule nofib: Add digits-of-e1.faststdout (1e24a24) Message-ID: <20171023034533.5F4E23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1e24a243b30c4dd5a7f3476e3e9927c4eb915c72/ghc >--------------------------------------------------------------- commit 1e24a243b30c4dd5a7f3476e3e9927c4eb915c72 Author: Joachim Breitner Date: Sun Oct 22 23:45:10 2017 -0400 submodule nofib: Add digits-of-e1.faststdout >--------------------------------------------------------------- 1e24a243b30c4dd5a7f3476e3e9927c4eb915c72 nofib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nofib b/nofib index c241954..d9e9707 160000 --- a/nofib +++ b/nofib @@ -1 +1 @@ -Subproject commit c24195479551800e1e3f45b1d977f04a546889d3 +Subproject commit d9e97074859a1f5bb9168da4d4e1b9fd7d8f0420 From git at git.haskell.org Mon Oct 23 04:57:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 04:57:26 +0000 (UTC) Subject: [commit: nofib] master: Add digits-of-e2.faststdout (ef4f8dc) Message-ID: <20171023045726.57B263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef4f8dc8ef51ce3353b76a0761c1a09e5ff30b67/nofib >--------------------------------------------------------------- commit ef4f8dc8ef51ce3353b76a0761c1a09e5ff30b67 Author: Joachim Breitner Date: Mon Oct 23 00:57:15 2017 -0400 Add digits-of-e2.faststdout >--------------------------------------------------------------- ef4f8dc8ef51ce3353b76a0761c1a09e5ff30b67 imaginary/digits-of-e2/digits-of-e2.faststdout | 1 + 1 file changed, 1 insertion(+) diff --git a/imaginary/digits-of-e2/digits-of-e2.faststdout b/imaginary/digits-of-e2/digits-of-e2.faststdout new file mode 100644 index 0000000..5ce87a6 --- /dev/null +++ b/imaginary/digits-of-e2/digits-of-e2.faststdout @@ -0,0 +1 @@ +"2.7182818284590452353602874713526624977572470936999595749669676277240766303535475945713821785251664274274663919320030599218174135966290435729003342952605956307381323286279434907632338298807531952510190115738341879307021540891499348841675092447614606680822648001684774118537423454424371075390777449920695517027618386062613313845830007520449338265602976067371132007093287091274437470472306969772093101416928368190255151086574637721112523897844250569536" From git at git.haskell.org Mon Oct 23 04:57:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 04:57:47 +0000 (UTC) Subject: [commit: ghc] master: submodule nofib: Add digits-of-e2.faststdout (052ec24) Message-ID: <20171023045747.CE92A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/052ec24412e285aa34911d6187cc2227fc7d86d9/ghc >--------------------------------------------------------------- commit 052ec24412e285aa34911d6187cc2227fc7d86d9 Author: Joachim Breitner Date: Mon Oct 23 00:57:33 2017 -0400 submodule nofib: Add digits-of-e2.faststdout >--------------------------------------------------------------- 052ec24412e285aa34911d6187cc2227fc7d86d9 nofib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nofib b/nofib index d9e9707..ef4f8dc 160000 --- a/nofib +++ b/nofib @@ -1 +1 @@ -Subproject commit d9e97074859a1f5bb9168da4d4e1b9fd7d8f0420 +Subproject commit ef4f8dc8ef51ce3353b76a0761c1a09e5ff30b67 From git at git.haskell.org Mon Oct 23 09:47:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 09:47:50 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Retain build/host/target (24e6faa) Message-ID: <20171023094750.AFF3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/24e6faa641d2ee8f084dc0ec6227df57a8e38369/ghc >--------------------------------------------------------------- commit 24e6faa641d2ee8f084dc0ec6227df57a8e38369 Author: Moritz Angermann Date: Mon Oct 23 17:45:53 2017 +0800 Retain build/host/target >--------------------------------------------------------------- 24e6faa641d2ee8f084dc0ec6227df57a8e38369 configure.ac | 4 ++++ distrib/configure.ac.in | 26 ++++++++++++++++++++------ 2 files changed, 24 insertions(+), 6 deletions(-) diff --git a/configure.ac b/configure.ac index d32ede2..98c07b2 100644 --- a/configure.ac +++ b/configure.ac @@ -222,6 +222,10 @@ AC_CANONICAL_TARGET FPTOOLS_SET_PLATFORM_VARS +AC_SUBST([build_alias]) +AC_SUBST([host_alias]) +AC_SUBST([target_alias]) + # Verify that the installed (bootstrap) GHC is capable of generating # code for the requested build platform. if test "$BuildPlatform" != "$bootstrap_target" diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index adecf7c..4e71c92 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -33,6 +33,24 @@ FFILibDir=@FFILibDir@ AC_SUBST(FFILibDir) AC_SUBST(FFIIncludeDir) +CrossCompiling=@CrossCompiling@ +CrossCompilePrefix=@CrossCompilePrefix@ +TargetPlatformFull=@TargetPlatformFull@ + +# when cross compiling, retain the build/host/target values +# from the initial configure step; while still allowing to set +# them via `--build/--host/--target` if need be. +if test "x$CrossCompiling" = "xNO"; then + if text -z "$build_alias"; then + build_alias=@build_alias@ + fi + if test -z "$host_alias"; then + host_alias=@host_alias@ + fi + if text -z "$target_alias"; then + target_alias=@target_alias@ + fi +fi # We have to run these unconditionally as FPTOOLS_SET_PLATFORM_VARS wants the # values it computes. @@ -40,13 +58,9 @@ AC_CANONICAL_BUILD AC_CANONICAL_HOST AC_CANONICAL_TARGET -# FP_FIND_ROOT requires knowledge about $windows; inherit it. -windows=@windows@ -FP_FIND_ROOT +FPTOOLS_SET_PLATFORM_VARS -CrossCompiling=@CrossCompiling@ -CrossCompilePrefix=@CrossCompilePrefix@ -TargetPlatformFull=@TargetPlatformFull@ +FP_FIND_ROOT AC_SUBST(CrossCompiling) AC_SUBST(CrossCompilePrefix) From git at git.haskell.org Mon Oct 23 09:47:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 09:47:53 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Retain build/host/target (e69eb4c) Message-ID: <20171023094753.7F75D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/e69eb4cd2c5f2de20acbc5171f08bcef4f492b16/ghc >--------------------------------------------------------------- commit e69eb4cd2c5f2de20acbc5171f08bcef4f492b16 Author: Moritz Angermann Date: Mon Oct 23 17:45:53 2017 +0800 Retain build/host/target >--------------------------------------------------------------- e69eb4cd2c5f2de20acbc5171f08bcef4f492b16 configure.ac | 4 ++++ distrib/configure.ac.in | 26 ++++++++++++++++++++------ 2 files changed, 24 insertions(+), 6 deletions(-) diff --git a/configure.ac b/configure.ac index d32ede2..98c07b2 100644 --- a/configure.ac +++ b/configure.ac @@ -222,6 +222,10 @@ AC_CANONICAL_TARGET FPTOOLS_SET_PLATFORM_VARS +AC_SUBST([build_alias]) +AC_SUBST([host_alias]) +AC_SUBST([target_alias]) + # Verify that the installed (bootstrap) GHC is capable of generating # code for the requested build platform. if test "$BuildPlatform" != "$bootstrap_target" diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index adecf7c..4e71c92 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -33,6 +33,24 @@ FFILibDir=@FFILibDir@ AC_SUBST(FFILibDir) AC_SUBST(FFIIncludeDir) +CrossCompiling=@CrossCompiling@ +CrossCompilePrefix=@CrossCompilePrefix@ +TargetPlatformFull=@TargetPlatformFull@ + +# when cross compiling, retain the build/host/target values +# from the initial configure step; while still allowing to set +# them via `--build/--host/--target` if need be. +if test "x$CrossCompiling" = "xNO"; then + if text -z "$build_alias"; then + build_alias=@build_alias@ + fi + if test -z "$host_alias"; then + host_alias=@host_alias@ + fi + if text -z "$target_alias"; then + target_alias=@target_alias@ + fi +fi # We have to run these unconditionally as FPTOOLS_SET_PLATFORM_VARS wants the # values it computes. @@ -40,13 +58,9 @@ AC_CANONICAL_BUILD AC_CANONICAL_HOST AC_CANONICAL_TARGET -# FP_FIND_ROOT requires knowledge about $windows; inherit it. -windows=@windows@ -FP_FIND_ROOT +FPTOOLS_SET_PLATFORM_VARS -CrossCompiling=@CrossCompiling@ -CrossCompilePrefix=@CrossCompilePrefix@ -TargetPlatformFull=@TargetPlatformFull@ +FP_FIND_ROOT AC_SUBST(CrossCompiling) AC_SUBST(CrossCompilePrefix) From git at git.haskell.org Mon Oct 23 09:47:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 09:47:57 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Merge branch 'feature/no-ghc-triple' into wip/angerman/llvmng (7ee4b57) Message-ID: <20171023094757.D605F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/7ee4b573ac7e7cb2ca34875fa036ed5cd14a0fc4/ghc >--------------------------------------------------------------- commit 7ee4b573ac7e7cb2ca34875fa036ed5cd14a0fc4 Merge: 24e6faa e69eb4c Author: Moritz Angermann Date: Mon Oct 23 17:46:56 2017 +0800 Merge branch 'feature/no-ghc-triple' into wip/angerman/llvmng >--------------------------------------------------------------- 7ee4b573ac7e7cb2ca34875fa036ed5cd14a0fc4 From git at git.haskell.org Mon Oct 23 13:16:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 13:16:32 +0000 (UTC) Subject: [commit: ghc] branch 'wip/D4112' created Message-ID: <20171023131632.1FCC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/D4112 Referencing: 1db8aecc849658732b6b3035b6b30606725fbd65 From git at git.haskell.org Mon Oct 23 13:16:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 13:16:35 +0000 (UTC) Subject: [commit: ghc] wip/D4112: Make language extensions their own category in the documentation (1db8aec) Message-ID: <20171023131635.0A1BD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/D4112 Link : http://ghc.haskell.org/trac/ghc/changeset/1db8aecc849658732b6b3035b6b30606725fbd65/ghc >--------------------------------------------------------------- commit 1db8aecc849658732b6b3035b6b30606725fbd65 Author: Joachim Breitner Date: Thu Oct 19 14:21:49 2017 -0400 Make language extensions their own category in the documentation I.e. instead of .. ghc-flag:: -XUnboxedTuples :shortdesc: Enable the use of unboxed tuple syntax. :type: dynamic :reverse: -XNoUnboxedTuples :category: one simply writes .. extension:: UnboxedTuples :shortdesc: Enable the use of unboxed tuple syntax. This allows language extensions to be referenced as If :extension:`UnboxedTuples` is enabled, then... This directive still creates the entries for the `-XUnboxedTuples` flag, so in particular, Set :ghc-flag:`-XUnboxedTuples` if you have to. still works, and lists of flags in general (e.g. for the manpage) include these. I also removed lots of links from the shortdesc of the extensions, when this link simply points to the section where the extension is defined. I removed the list of `-X` flags from the flag reference table, but added a table of extension under “10.1. Language options” Lots of text in the manual now refers to “extension `Foo`” rather than “flag `-XFoo`”. I consider `-XFoo` a historic artifact that stems from when language extensions were really just flags. These days, the use of `-XFoo` is (IMHO) deprecated: You should be using `LANGUAGE Foo`, or maybe the appropriate field in a `.cabal` file. See 9278994 which did this change to error messages already. >--------------------------------------------------------------- 1db8aecc849658732b6b3035b6b30606725fbd65 docs/users_guide/ffi-chap.rst | 21 +- docs/users_guide/flags.py | 309 +++++- docs/users_guide/flags.rst | 11 - docs/users_guide/ghci.rst | 21 +- docs/users_guide/glasgow_exts.rst | 1397 +++++++++++---------------- docs/users_guide/phases.rst | 7 +- docs/users_guide/safe_haskell.rst | 102 +- docs/users_guide/what_glasgow_exts_does.rst | 62 +- 8 files changed, 925 insertions(+), 1005 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 1db8aecc849658732b6b3035b6b30606725fbd65 From git at git.haskell.org Mon Oct 23 13:18:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 13:18:37 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (b68febd) Message-ID: <20171023131837.DC1BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/b68febd55cf782e518551dda9cd85367b37aa13b/ghc >--------------------------------------------------------------- commit b68febd55cf782e518551dda9cd85367b37aa13b Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration >--------------------------------------------------------------- b68febd55cf782e518551dda9cd85367b37aa13b compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 6 ++++++ compiler/simplCore/SimplCore.hs | 40 +++++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 41 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b68febd55cf782e518551dda9cd85367b37aa13b From git at git.haskell.org Mon Oct 23 13:18:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 13:18:41 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (f47098c) Message-ID: <20171023131841.4AE623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/f47098c653d8860e2ef42e707988e89ceda1dd30/ghc >--------------------------------------------------------------- commit f47098c653d8860e2ef42e707988e89ceda1dd30 Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- f47098c653d8860e2ef42e707988e89ceda1dd30 compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 403 ++++++++++++++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 8 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + 12 files changed, 449 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f47098c653d8860e2ef42e707988e89ceda1dd30 From git at git.haskell.org Mon Oct 23 13:18:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 13:18:43 +0000 (UTC) Subject: [commit: ghc] wip/T14152's head updated: Inline exit join points in the "final" simplifier iteration (b68febd) Message-ID: <20171023131843.CE9673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14152' now includes: 341d3a7 Incorporate changes from #11721 into Template Haskell f1d2db6 Fix #14320 by looking through HsParTy in more places f337a20 Simply Data instance context for AmbiguousFieldOcc e51e565 Split SysTools up some 7720c29 Tidy up some convoluted "child/parent" code ab1a758 Typos in comments only 461c831 Minor refactoring c81f66c Fix over-eager error suppression in TcErrors 79ae03a Change "cobox" to "co" in debug output 3e44562 Delete two unused functions f20cf98 Remove wc_insol from WantedConstraints 9c3f731 Fix #10816 by renaming FixitySigs more consistently 6869864 Pretty-printing of derived multi-parameter classes omits parentheses 4bb54a4 Avoid creating dependent types in FloatOut 13fdca3 Add a missing zonk in TcDerivInfer.simplifyDeriv 82b77ec Do not quantify over deriving clauses 15aefb4 Add missing T14325.stderr fb050a3 Do not bind coercion variables in SpecConstr rules 3de788c Re-apply "Typeable: Allow App to match arrow types" 2be55b8 Delete obsolete docs on GADT interacton with TypeApplications 4a677f7 Remove section about ApplicativeDo & existentials (#13875) 8adb84f Fix calculation in threadStackOverflow afac6b1 Fix typo 6aa6a86 Fix typo add85cc Fix panic for `ByteArray#` arguments in CApiFFI foreign imports e3ba26f Implement new `compareByteArrays#` primop 5984a69 Override default `clearBit` method impl for `Natural` 843772b Enable testing 'Natural' type in TEST=arith011 6cc232a Implement {set,clear,complement}BitBigNat primitives 71a4235 configure: Fix CC version check on Apple compilers fd8b044 Levity polymorphic Backpack. 5dab544 FreeBSD dtrace probe support 7e790b3 rts: Label all threads created by the RTS 8536b7f users-guide: Rework and finish debug flag documentation d7f4f41 users guide: Eliminate redundant :category: tags in debugging.rst c5da84d users-guide: Fix various warnings a69fa54 rts/posix: Ensure that memory commit succeeds d6c33da RtClosureInspect: Fix inspecting Char# on 64-bit big-endian 366182a ghci: Include "Rts.h" before using TABLES_NEXT_TO_CODE 9e3add9 Flags.hsc: Peek a CBool (Word8), not a Bool (Int32) aa98268 updateThunk: indirectee can be tagged 21b7057 users-guide: Clarify -ddump-asm-regalloc-stages documentation 6cb4642 Bump ghc-prim to 0.5.2.0 and update changelog ed48d13 Simplify, no functionality change 2f43615 Fix grammaros in comments 317aa96 Improve user’s guide around deriving 74cd1be Don't deeply expand insolubles 5a66d57 Better solving for representational equalities aba7786 Typofix in comment 870020e whitespace only 20ae22b Accept test output for #14350 e023e78 Disable -XRebindableSyntax when running internal GHCi expressions 101a8c7 Error when deriving instances in hs-boot files 8846a7f Fix #14369 by making injectivity warnings finer-grained de8752e Export injectiveVarsOf{Binder,Type} from TyCoRep 7ac22b7 User's guide: Fix the category of some flags 3befc1a Bump arcanist-external-json-linter submodule 1ba2851 Expose monotonic time from GHC.Event.Clock 13758c6 Added a test for 'timeout' to be accurate. 098dc97 Give a reference to Foreign.Concurrent. b6204f7 Untag the potential AP_STACK in stg_getApStackValzh 2ca8cf6 Add Functor Bag instance afc04b2 Outputable: Add pprTraceException c1efc6e Comments and white space 3acd616 Improve kick-out in the constraint solver e375bd3 Update record-wildcard docs 99c61e2 Add stack traces on crashes on Windows bb537b2 nofib submodule: Fix a problem with fasta-c.c 1e24a24 submodule nofib: Add digits-of-e1.faststdout 052ec24 submodule nofib: Add digits-of-e2.faststdout f47098c Implement a dedicated exitfication pass #14152 b68febd Inline exit join points in the "final" simplifier iteration From git at git.haskell.org Mon Oct 23 14:22:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 14:22:17 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Yuck! (429a426) Message-ID: <20171023142217.E821D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/429a426fdd2e559294815cfa94a1d8498edcad99/ghc >--------------------------------------------------------------- commit 429a426fdd2e559294815cfa94a1d8498edcad99 Author: Moritz Angermann Date: Mon Oct 23 22:22:03 2017 +0800 Yuck! >--------------------------------------------------------------- 429a426fdd2e559294815cfa94a1d8498edcad99 distrib/configure.ac.in | 33 ++++++++++++++++++--------------- 1 file changed, 18 insertions(+), 15 deletions(-) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index 4e71c92..e3b2c74 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -23,7 +23,6 @@ dnl-------------------------------------------------------------------- FP_GMP dnl Various things from the source distribution configure -bootstrap_target=@TargetPlatform@ HaskellHaveRTSLinker=@HaskellHaveRTSLinker@ AC_SUBST(HaskellHaveRTSLinker) @@ -40,16 +39,18 @@ TargetPlatformFull=@TargetPlatformFull@ # when cross compiling, retain the build/host/target values # from the initial configure step; while still allowing to set # them via `--build/--host/--target` if need be. -if test "x$CrossCompiling" = "xNO"; then - if text -z "$build_alias"; then +if test "x$CrossCompiling" = "xYES"; then + if test -z "$build_alias"; then build_alias=@build_alias@ fi if test -z "$host_alias"; then host_alias=@host_alias@ fi - if text -z "$target_alias"; then + if test -z "$target_alias"; then target_alias=@target_alias@ fi +else + bootstrap_target=@TargetPlatform@ fi # We have to run these unconditionally as FPTOOLS_SET_PLATFORM_VARS wants the @@ -58,8 +59,8 @@ AC_CANONICAL_BUILD AC_CANONICAL_HOST AC_CANONICAL_TARGET -FPTOOLS_SET_PLATFORM_VARS - +# FP_FIND_ROOT requires knowledge about $windows; inherit it. +windows=@windows@ FP_FIND_ROOT AC_SUBST(CrossCompiling) @@ -160,6 +161,15 @@ AC_SUBST(CONF_CPP_OPTS_STAGE0) AC_SUBST(CONF_CPP_OPTS_STAGE1) AC_SUBST(CONF_CPP_OPTS_STAGE2) + +dnl ** Hack tools for cross compilers +dnl -------------------------------------------------------------- +dnl When building a binary distribution for cross compilers, +dnl we likely want to retain the target-prefixed tools, and not +dnl have configure overwrite them with what ever it finds, as +dnl the found tools likely do not target the target. + +if test "x$CrossCompiling" = "xNO"; then dnl ** Which ld to use? dnl -------------------------------------------------------------- FIND_LD([$target],[GccUseLdOpt]) @@ -219,17 +229,10 @@ if test "x$BinDistNeedsLibdw" = "xYES" ; then fi FP_SETTINGS +AC_CONFIG_FILES(settings) +fi # end CrossCompiling == NO -dnl ** Hack tools for cross compilers -dnl -------------------------------------------------------------- -dnl When building a binary distribution for cross compilers, -dnl we likely want to retain the target-prefixed tools, and not -dnl have configure overwrite them with what ever it finds, as -dnl the found tools likely do not target the target. AC_CONFIG_FILES(mk/config.mk mk/install.mk) -if test "x$CrossCompiling" = "xNO"; then -AC_CONFIG_FILES(settings) -fi AC_OUTPUT From git at git.haskell.org Mon Oct 23 14:39:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 14:39:40 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Run Exitification at various stages of the pipeline (1a93f0c) Message-ID: <20171023143940.851FD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/1a93f0cad52e47e31cd21e3dc8bc64e95c7dfb1e/ghc >--------------------------------------------------------------- commit 1a93f0cad52e47e31cd21e3dc8bc64e95c7dfb1e Author: Joachim Breitner Date: Mon Oct 23 10:38:25 2017 -0400 Run Exitification at various stages of the pipeline we probably to run it less, but let’s first see if this recovers the old strength of exitification, and then carefully see if we can do with less iterations. >--------------------------------------------------------------- 1a93f0cad52e47e31cd21e3dc8bc64e95c7dfb1e compiler/simplCore/SimplCore.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index a4dca0f..91227f3 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -255,7 +255,6 @@ getCoreToDo dflags -- initial simplify: mk specialiser happy: minimum effort please simpl_gently, - -- Exitification runWhen exitification CoreDoExitify, -- Specialisation is best done before full laziness @@ -305,6 +304,8 @@ getCoreToDo dflags -- Don't stop now! simpl_phase 0 ["main"] (max max_iter 3) False, + runWhen exitification CoreDoExitify, + runWhen do_float_in CoreDoFloatInwards, -- Run float-inwards immediately before the strictness analyser -- Doing so pushes bindings nearer their use site and hence makes @@ -319,6 +320,8 @@ getCoreToDo dflags runWhen strictness demand_analyser, + runWhen exitification CoreDoExitify, + runWhen full_laziness $ CoreDoFloatOutwards FloatOutSwitches { floatOutLambdas = floatLamArgs dflags, From git at git.haskell.org Mon Oct 23 17:09:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 17:09:41 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Exitification: Preserve exit points in all but the final iteration (caada47) Message-ID: <20171023170941.9DF493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/caada478db2d6a72ec345d739dbbf3b9981266ad/ghc >--------------------------------------------------------------- commit caada478db2d6a72ec345d739dbbf3b9981266ad Author: Joachim Breitner Date: Mon Oct 23 13:08:58 2017 -0400 Exitification: Preserve exit points in all but the final iteration not the other way around… (off by negation bug introduced by me). >--------------------------------------------------------------- caada478db2d6a72ec345d739dbbf3b9981266ad compiler/simplCore/SimplCore.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 91227f3..afb5e24 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -161,7 +161,7 @@ getCoreToDo dflags , CoreDoSimplify iter (base_mode { sm_phase = Phase phase , sm_names = names - , sm_preserve_exit_joins = is_final + , sm_preserve_exit_joins = not is_final -- see Note [Do not inline exit join points] in Exitify.hs }) From git at git.haskell.org Mon Oct 23 20:12:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 20:12:43 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Exitifcation: Experimenting with position in SimplCore (e55a4ef) Message-ID: <20171023201243.6B3BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/e55a4ef0fd4a2119cc7615892dc79a20c41e7749/ghc >--------------------------------------------------------------- commit e55a4ef0fd4a2119cc7615892dc79a20c41e7749 Author: Joachim Breitner Date: Mon Oct 23 16:12:04 2017 -0400 Exitifcation: Experimenting with position in SimplCore Let’s see if it works nicely after `simpl_phases`, but before the `"main"` simpl_phase. >--------------------------------------------------------------- e55a4ef0fd4a2119cc7615892dc79a20c41e7749 compiler/simplCore/SimplCore.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index afb5e24..3427777 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -255,8 +255,6 @@ getCoreToDo dflags -- initial simplify: mk specialiser happy: minimum effort please simpl_gently, - runWhen exitification CoreDoExitify, - -- Specialisation is best done before full laziness -- so that overloaded functions have all their dictionary lambdas manifest runWhen do_specialise CoreDoSpecialising, @@ -292,6 +290,8 @@ getCoreToDo dflags simpl_phases, + runWhen exitification CoreDoExitify, + -- Phase 0: allow all Ids to be inlined now -- This gets foldr inlined before strictness analysis @@ -304,8 +304,6 @@ getCoreToDo dflags -- Don't stop now! simpl_phase 0 ["main"] (max max_iter 3) False, - runWhen exitification CoreDoExitify, - runWhen do_float_in CoreDoFloatInwards, -- Run float-inwards immediately before the strictness analyser -- Doing so pushes bindings nearer their use site and hence makes From git at git.haskell.org Mon Oct 23 21:17:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Oct 2017 21:17:17 +0000 (UTC) Subject: [commit: ghc] wip/ttg/2017-10-21: WIP on implicit binders (2281229) Message-ID: <20171023211717.EB2D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttg/2017-10-21 Link : http://ghc.haskell.org/trac/ghc/changeset/22812296818fe955752fa4762cf72250abd09bf9/ghc >--------------------------------------------------------------- commit 22812296818fe955752fa4762cf72250abd09bf9 Author: Alan Zimmerman Date: Mon Oct 23 10:42:48 2017 +0200 WIP on implicit binders Problem with hs-boot loop >--------------------------------------------------------------- 22812296818fe955752fa4762cf72250abd09bf9 compiler/hsSyn/HsBinds.hs | 8 +++-- compiler/hsSyn/HsDecls.hs | 57 +++++++++++++++++++++------------- compiler/hsSyn/HsExpr.hs | 34 +++++++++++---------- compiler/hsSyn/HsExpr.hs-boot | 12 ++++---- compiler/hsSyn/HsExtension.hs | 35 +++++++++++++++++++++ compiler/hsSyn/HsTypes.hs | 71 ++++++++++++++++++++++++++++++++----------- compiler/parser/Parser.y | 3 +- compiler/rename/RnTypes.hs | 4 +-- 8 files changed, 158 insertions(+), 66 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 22812296818fe955752fa4762cf72250abd09bf9 From git at git.haskell.org Tue Oct 24 10:26:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 10:26:09 +0000 (UTC) Subject: [commit: ghc] master: Comments only (b10a768) Message-ID: <20171024102609.EDC6A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b10a768786f93d174b1cbc64ae8dae4fe60120bf/ghc >--------------------------------------------------------------- commit b10a768786f93d174b1cbc64ae8dae4fe60120bf Author: Simon Peyton Jones Date: Mon Oct 23 09:08:16 2017 +0100 Comments only >--------------------------------------------------------------- b10a768786f93d174b1cbc64ae8dae4fe60120bf compiler/typecheck/TcType.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 7b27ce1..75e0215 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -936,9 +936,9 @@ anyRewritableTyVar ignore_cos role pred ty go_tc ReprEq bvs tc tys = foldr ((&&) . go_arg bvs) False $ (tyConRolesRepresentational tc `zip` tys) - go_arg _ (Phantom, _) = False -- ToDo: check go_arg bvs (Nominal, ty) = go NomEq bvs ty go_arg bvs (Representational, ty) = go ReprEq bvs ty + go_arg _ (Phantom, _) = False -- We never rewrite with phantoms go_co rl bvs co | ignore_cos = False From git at git.haskell.org Tue Oct 24 10:26:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 10:26:13 +0000 (UTC) Subject: [commit: ghc] master: Temporary fix to Trac #14380 (d1eaead) Message-ID: <20171024102613.9F3173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d1eaeadb08c1412c1572124efaf341bdc0976ccb/ghc >--------------------------------------------------------------- commit d1eaeadb08c1412c1572124efaf341bdc0976ccb Author: Simon Peyton Jones Date: Tue Oct 24 11:12:43 2017 +0100 Temporary fix to Trac #14380 This fix replaces an utterly bogus error message with a decent one, rejecting a pattern synonym with a list pattern and rebindable syntax. Not hard to fix properly, but I'm going to wait for a willing volunteer and/or more user pressure. >--------------------------------------------------------------- d1eaeadb08c1412c1572124efaf341bdc0976ccb compiler/typecheck/TcPatSyn.hs | 21 +++++++++++++++++---- testsuite/tests/patsyn/should_fail/T14380.hs | 8 ++++++++ testsuite/tests/patsyn/should_fail/T14380.stderr | 9 +++++++++ testsuite/tests/patsyn/should_fail/all.T | 1 + 4 files changed, 35 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index d234fd5..58d1506 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -672,8 +672,10 @@ tcPatToExpr name args pat = go pat go1 (ParPat pat) = fmap HsPar $ go pat go1 (PArrPat pats ptt) = do { exprs <- mapM go pats ; return $ ExplicitPArr ptt exprs } - go1 (ListPat pats ptt reb) = do { exprs <- mapM go pats - ; return $ ExplicitList ptt (fmap snd reb) exprs } + go1 p@(ListPat pats ptt reb) + | Nothing <- reb = do { exprs <- mapM go pats + ; return $ ExplicitList ptt Nothing exprs } + | otherwise = notInvertibleListPat p go1 (TuplePat pats box _) = do { exprs <- mapM go pats ; return $ ExplicitTuple (map (noLoc . Present) exprs) box } @@ -702,8 +704,10 @@ tcPatToExpr name args pat = go pat go1 p@(SplicePat (HsUntypedSplice {})) = notInvertible p go1 p@(SplicePat (HsQuasiQuote {})) = notInvertible p - notInvertible p = Left $ - text "Pattern" <+> quotes (ppr p) <+> text "is not invertible" + notInvertible p = Left (not_invertible_msg p) + + not_invertible_msg p + = text "Pattern" <+> quotes (ppr p) <+> text "is not invertible" $+$ hang (text "Suggestion: instead use an explicitly bidirectional" <+> text "pattern synonym, e.g.") 2 (hang (text "pattern" <+> pp_name <+> pp_args <+> larrow @@ -713,6 +717,15 @@ tcPatToExpr name args pat = go pat pp_name = ppr name pp_args = hsep (map ppr args) + -- We should really be able to invert list patterns, even when + -- rebindable syntax is on, but doing so involves a bit of + -- refactoring; see Trac #14380. Until then we reject with a + -- helpful error message. + notInvertibleListPat p + = Left (vcat [ not_invertible_msg p + , text "Reason: rebindable syntax is on." + , text "This is fixable: add use-case to Trac #14380" ]) + {- Note [Builder for a bidirectional pattern synonym] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ For a bidirectional pattern synonym we need to produce an /expression/ diff --git a/testsuite/tests/patsyn/should_fail/T14380.hs b/testsuite/tests/patsyn/should_fail/T14380.hs new file mode 100644 index 0000000..aec3985 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T14380.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE OverloadedLists #-} +{-# LANGUAGE PatternSynonyms #-} + +module T14380 where + +data Foo = Foo [Int] +pattern Bar :: Foo +pattern Bar = Foo [] diff --git a/testsuite/tests/patsyn/should_fail/T14380.stderr b/testsuite/tests/patsyn/should_fail/T14380.stderr new file mode 100644 index 0000000..4228d29 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T14380.stderr @@ -0,0 +1,9 @@ + +T14380.hs:8:15: error: + Invalid right-hand side of bidirectional pattern synonym ‘Bar’: + Pattern ‘[]’ is not invertible + Suggestion: instead use an explicitly bidirectional pattern synonym, e.g. + pattern Bar <- Foo [] where Bar = ... + Reason: rebindable syntax is on. + This is fixable: add use-case to Trac #14380 + RHS pattern: Foo [] diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index 8a098d9..388e67b 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -38,3 +38,4 @@ test('T13349', normal, compile_fail, ['']) test('T13470', normal, compile_fail, ['']) test('T14112', normal, compile_fail, ['']) test('T14114', normal, compile_fail, ['']) +test('T14380', normal, compile_fail, ['']) From git at git.haskell.org Tue Oct 24 14:09:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 14:09:37 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (2dde661) Message-ID: <20171024140937.35F843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/2dde6616ab955deba38010532c23f59fe66fef68/ghc >--------------------------------------------------------------- commit 2dde6616ab955deba38010532c23f59fe66fef68 Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- 2dde6616ab955deba38010532c23f59fe66fef68 compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 403 ++++++++++++++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 9 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + 12 files changed, 450 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2dde6616ab955deba38010532c23f59fe66fef68 From git at git.haskell.org Tue Oct 24 14:09:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 14:09:43 +0000 (UTC) Subject: [commit: ghc] wip/T14152's head updated: Inline exit join points in the "final" simplifier iteration (88e7379) Message-ID: <20171024140943.495CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14152' now includes: b10a768 Comments only d1eaead Temporary fix to Trac #14380 2dde661 Implement a dedicated exitfication pass #14152 88e7379 Inline exit join points in the "final" simplifier iteration From git at git.haskell.org Tue Oct 24 14:09:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 14:09:41 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (88e7379) Message-ID: <20171024140941.0F1453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/88e73790bba078eb1956424673be5dc2bd7e65b9/ghc >--------------------------------------------------------------- commit 88e73790bba078eb1956424673be5dc2bd7e65b9 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration >--------------------------------------------------------------- 88e73790bba078eb1956424673be5dc2bd7e65b9 compiler/simplCore/CoreMonad.hs | 7 +- compiler/simplCore/Exitify.hs | 6 + compiler/simplCore/SimplCore.hs | 40 ++-- compiler/simplCore/SimplUtils.hs | 7 +- compiler/simplCore/Simplify.hs | 3 +- testsuite/tests/simplCore/should_compile/T14152.hs | 22 ++ .../tests/simplCore/should_compile/T14152.stderr | 129 ++++++++++++ .../tests/simplCore/should_compile/T14152a.hs | 1 + .../tests/simplCore/should_compile/T14152a.stderr | 222 +++++++++++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 2 + 10 files changed, 417 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 88e73790bba078eb1956424673be5dc2bd7e65b9 From git at git.haskell.org Tue Oct 24 14:37:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 14:37:02 +0000 (UTC) Subject: [commit: ghc] master: User’s guide: Properly link to RTS flag -V (671b1ed) Message-ID: <20171024143702.5CFA13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/671b1ed9bf004ec7a426280799d7cd742836b1d1/ghc >--------------------------------------------------------------- commit 671b1ed9bf004ec7a426280799d7cd742836b1d1 Author: Joachim Breitner Date: Tue Oct 24 10:36:49 2017 -0400 User’s guide: Properly link to RTS flag -V >--------------------------------------------------------------- 671b1ed9bf004ec7a426280799d7cd742836b1d1 docs/users_guide/runtime_control.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/runtime_control.rst b/docs/users_guide/runtime_control.rst index 9b43277..f944ae9 100644 --- a/docs/users_guide/runtime_control.rst +++ b/docs/users_guide/runtime_control.rst @@ -218,7 +218,7 @@ Miscellaneous RTS options interval timer signal is still enabled. The timer signal is either SIGVTALRM or SIGALRM, depending on the RTS configuration and OS capabilities. To disable the timer signal, use the ``-V0`` RTS - option (see above). + option (see :rts-flag:`-V ⟨secs⟩`). .. rts-flag:: --install-seh-handlers=⟨yes|no⟩ From git at git.haskell.org Tue Oct 24 14:44:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 14:44:02 +0000 (UTC) Subject: [commit: ghc] master: Include usg_file_hash in ghc --show-iface output (8843a39) Message-ID: <20171024144402.6CCE33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8843a39b3c941b1908a8d839f52bc323f3b45081/ghc >--------------------------------------------------------------- commit 8843a39b3c941b1908a8d839f52bc323f3b45081 Author: Simon Marlow Date: Fri Oct 20 17:07:27 2017 +0100 Include usg_file_hash in ghc --show-iface output Summary: Otherwise we can get an iface hash difference, but no indication of what caused it in the --show-iface output. Test Plan: Harbourmaster Reviewers: austin, bgamari, erikd Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4115 >--------------------------------------------------------------- 8843a39b3c941b1908a8d839f52bc323f3b45081 compiler/iface/LoadIface.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/iface/LoadIface.hs b/compiler/iface/LoadIface.hs index 6069828..b91d984 100644 --- a/compiler/iface/LoadIface.hs +++ b/compiler/iface/LoadIface.hs @@ -1073,7 +1073,8 @@ pprUsage usage at UsageHomeModule{} ) pprUsage usage at UsageFile{} = hsep [text "addDependentFile", - doubleQuotes (text (usg_file_path usage))] + doubleQuotes (text (usg_file_path usage)), + ppr (usg_file_hash usage)] pprUsage usage at UsageMergedRequirement{} = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] From git at git.haskell.org Tue Oct 24 14:58:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 14:58:42 +0000 (UTC) Subject: [commit: ghc] branch 'wip/circleci' created Message-ID: <20171024145843.00DDD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/circleci Referencing: 6fc69426d2f87437080002af77f2ac48aa48f152 From git at git.haskell.org Tue Oct 24 14:58:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 14:58:45 +0000 (UTC) Subject: [commit: ghc] wip/circleci: CircleCI: Try ./validate slow (6fc6942) Message-ID: <20171024145845.C91313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/circleci Link : http://ghc.haskell.org/trac/ghc/changeset/6fc69426d2f87437080002af77f2ac48aa48f152/ghc >--------------------------------------------------------------- commit 6fc69426d2f87437080002af77f2ac48aa48f152 Author: Joachim Breitner Date: Tue Oct 24 10:57:49 2017 -0400 CircleCI: Try ./validate slow This sets -DDEBUG when compiling stage2, which occasionally uncovers bugs. Let’s see how much longer it takes on CircleCI… >--------------------------------------------------------------- 6fc69426d2f87437080002af77f2ac48aa48f152 .circleci/config.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 6ee6c48..5f79075 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -25,4 +25,4 @@ jobs: command: | echo 'BUILD_SPHINX_HTML = NO' >> mk/validate.mk echo 'BUILD_SPHINX_PDF = NO' >> mk/validate.mk - THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --fast --quiet + THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --slow --quiet From git at git.haskell.org Tue Oct 24 17:53:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 17:53:07 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: rts/posix: Ensure that memory commit succeeds (cb7f91d) Message-ID: <20171024175307.085E13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/cb7f91db3e70cc36b2cc745e267adcb11c843f60/ghc >--------------------------------------------------------------- commit cb7f91db3e70cc36b2cc745e267adcb11c843f60 Author: Ben Gamari Date: Mon Oct 16 17:30:12 2017 -0400 rts/posix: Ensure that memory commit succeeds Previously we wouldn't check that mmap would succeed. I suspect this may have been the cause of #14329. Test Plan: Validate under low-memory condition Reviewers: simonmar, austin, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #14329 Differential Revision: https://phabricator.haskell.org/D4075 (cherry picked from commit a69fa5441c944d7f74c76bdae9f3dd198007ee42) >--------------------------------------------------------------- cb7f91db3e70cc36b2cc745e267adcb11c843f60 rts/posix/OSMem.c | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c index e2aa288..d25aaf8 100644 --- a/rts/posix/OSMem.c +++ b/rts/posix/OSMem.c @@ -521,7 +521,10 @@ void *osReserveHeapMemory(void *startAddressPtr, W_ *len) void osCommitMemory(void *at, W_ size) { - my_mmap(at, size, MEM_COMMIT); + void *r = my_mmap(at, size, MEM_COMMIT); + if (r == NULL) { + barf("Unable to commit %d bytes of memory", size); + } } void osDecommitMemory(void *at, W_ size) From git at git.haskell.org Tue Oct 24 17:53:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 17:53:09 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: base: Make Foreign.Marshal.Alloc.allocBytes[Aligned] NOINLINE (404bf05) Message-ID: <20171024175309.C77613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/404bf05ed3193e918875cd2f6c95ae0da5989be2/ghc >--------------------------------------------------------------- commit 404bf05ed3193e918875cd2f6c95ae0da5989be2 Author: Ben Gamari Date: Tue Oct 24 12:19:08 2017 -0400 base: Make Foreign.Marshal.Alloc.allocBytes[Aligned] NOINLINE As noted in #14346, touch# may be optimized away when the simplifier can see that the continuation passed to allocaBytes will not return. Marking CPS-style functions with NOINLINE ensures that the simplier can't draw any unsound conclusions. Ultimately the right solution here will be to do away with touch# and instead introduce a scoped primitive as is suggested in #14375. >--------------------------------------------------------------- 404bf05ed3193e918875cd2f6c95ae0da5989be2 libraries/base/Foreign/Marshal/Alloc.hs | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/libraries/base/Foreign/Marshal/Alloc.hs b/libraries/base/Foreign/Marshal/Alloc.hs index 2a3c756..10b6d36 100644 --- a/libraries/base/Foreign/Marshal/Alloc.hs +++ b/libraries/base/Foreign/Marshal/Alloc.hs @@ -123,6 +123,19 @@ alloca = doAlloca undefined doAlloca :: Storable a' => a' -> (Ptr a' -> IO b') -> IO b' doAlloca dummy = allocaBytesAligned (sizeOf dummy) (alignment dummy) +-- Note [NOINLINE for touch#] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- Both allocaBytes and allocaBytesAligned use the touch#, which is notoriously +-- fragile in the presence of simplification (see #14346). In particular, the +-- simplifier may drop the continuation containing the touch# if it can prove +-- that the action passed to allocaBytes will not return. The hack introduced to +-- fix this for 8.2.2 is to mark allocaBytes as NOINLINE, ensuring that the +-- simplifier can't see the divergence. +-- +-- These can be removed once #14375 is fixed, which suggests that we instead do +-- away with touch# in favor of a primitive that will capture the scoping left +-- implicit in the case of touch#. + -- |@'allocaBytes' n f@ executes the computation @f@, passing as argument -- a pointer to a temporarily allocated block of memory of @n@ bytes. -- The block of memory is sufficiently aligned for any of the basic @@ -141,6 +154,8 @@ allocaBytes (I# size) action = IO $ \ s0 -> case touch# barr# s3 of { s4 -> (# s4, r #) }}}}} +-- See Note [NOINLINE for touch#] +{-# NOINLINE allocaBytes #-} allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 -> @@ -152,6 +167,8 @@ allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 -> case touch# barr# s3 of { s4 -> (# s4, r #) }}}}} +-- See Note [NOINLINE for touch#] +{-# NOINLINE allocaBytesAligned #-} -- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes' -- to the size needed to store values of type @b at . The returned pointer From git at git.haskell.org Tue Oct 24 17:53:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 17:53:13 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix over-eager error suppression in TcErrors (8a07a52) Message-ID: <20171024175313.4560C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/8a07a522ec9062886fd79b78d55924622ed72a69/ghc >--------------------------------------------------------------- commit 8a07a522ec9062886fd79b78d55924622ed72a69 Author: Simon Peyton Jones Date: Thu Oct 5 17:40:28 2017 +0100 Fix over-eager error suppression in TcErrors See Note [Given insolubles] in TcRnTypes Fixes Trac #14325. (cherry picked from commit c81f66ccafdb4c6c7a09cfaf6819c8797c518491) >--------------------------------------------------------------- 8a07a522ec9062886fd79b78d55924622ed72a69 compiler/typecheck/TcRnTypes.hs | 24 ++++++++++++++++++++-- testsuite/tests/typecheck/should_fail/T14325.hs | 11 ++++++++++ .../tests/typecheck/should_fail/T14325.stderr | 9 ++++++++ testsuite/tests/typecheck/should_fail/all.T | 2 +- 4 files changed, 43 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index cbc05b2..f38d255 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -2251,7 +2251,7 @@ trulyInsoluble :: Ct -> Bool -- Yuk! trulyInsoluble insol | isHoleCt insol = isOutOfScopeCt insol - | otherwise = True + | otherwise = not (isGivenCt insol) -- See Note [Given insolubles] instance Outputable WantedConstraints where ppr (WC {wc_simple = s, wc_impl = i, wc_insol = n}) @@ -2266,7 +2266,27 @@ ppr_bag doc bag | otherwise = hang (doc <+> equals) 2 (foldrBag (($$) . ppr) empty bag) -{- +{- Note [Given insolubles] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider (Trac #14325, comment:) + class (a~b) => C a b + + foo :: C a b => a -> b + foo x = x + + hm3 :: C (f b) b => b -> f b + hm3 x = foo x + +From the [G] C (f b) b we get the insoluble [G] f b ~# b. Then we we also +get an unsolved [W] C b (f b). If trulyInsouble is true of this, we'll +set cec_suppress to True, and suppress reports of the [W] C b (f b). But we +may not report the insoluble [G] f b ~# b either (see Note [Given errors] +in TcErrors), so we may fail to report anything at all! Yikes. + +Bottom line: we must be certain to report anything trulyInsoluble. Easiest +way to guaranteed this is to make truly Insoluble false of Givens. + + ************************************************************************ * * Implication constraints diff --git a/testsuite/tests/typecheck/should_fail/T14325.hs b/testsuite/tests/typecheck/should_fail/T14325.hs new file mode 100644 index 0000000..edb6038 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14325.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE GADTs, MultiParamTypeClasses #-} + +module T14325 where + +class (a~b) => C a b + +foo :: C a b => a -> b +foo x = x + +hm3 :: C (f b) b => b -> f b +hm3 x = foo x diff --git a/testsuite/tests/typecheck/should_fail/T14325.stderr b/testsuite/tests/typecheck/should_fail/T14325.stderr new file mode 100644 index 0000000..1508c4a --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14325.stderr @@ -0,0 +1,9 @@ + +T14325.hs:11:9: error: + • Could not deduce (C b (f b)) arising from a use of ‘foo’ + from the context: C (f b) b + bound by the type signature for: + hm3 :: forall (f :: * -> *) b. C (f b) b => b -> f b + at T14325.hs:10:1-28 + • In the expression: foo x + In an equation for ‘hm3’: hm3 x = foo x diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 2f75316..22d5ae0 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -437,4 +437,4 @@ test('T13677', normal, compile_fail, ['']) test('T14000', normal, compile_fail, ['']) test('T11672', normal, compile_fail, ['']) test('T13929', normal, compile_fail, ['']) - +test('T14325', normal, compile_fail, ['']) From git at git.haskell.org Tue Oct 24 20:09:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 20:09:50 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (620381c) Message-ID: <20171024200950.468863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/620381cae28af93b13d33450056447829a308cbb/ghc >--------------------------------------------------------------- commit 620381cae28af93b13d33450056447829a308cbb Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 The idea is described in #14152, and can be summarized: Float the exit path out of a joinrec, so that the simplifier can do more with it. See the test case for a nice example. The floating goes against what the simplifier usually does, hence we need to be careful not inline them back. The position of exitification in the pipeline was chosen after a small amount of experimentation, but may need to be improved. For example, exitification can allow rewrite rules to fire, but for that it would have to happen before the `simpl_phases`. Together with the next patch, perf.haskell.org reports these nice performance wins: Nofib allocations prev change gain fannkuch-redux 78446688 - 99.92% 64608 k-nucleotide 109466432 - 91.32% 9502064 simple 72424696 - 5.96% 68109560 Nofib instruction counts compress2 573354476 + 3.34% 592476104 k-nucleotide 2310080537 - 5.59% 2180917263 scs 1979135192 - 3.2% 1915880589 simple 670348375 - 4.9% 637507288 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- 620381cae28af93b13d33450056447829a308cbb compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 403 ++++++++++++++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 9 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + 12 files changed, 450 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 620381cae28af93b13d33450056447829a308cbb From git at git.haskell.org Tue Oct 24 20:09:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 20:09:56 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Exitification: In simplLetUnfolding, set noUnfolding for exitJoinPoint (a6a08cd) Message-ID: <20171024200956.DAA1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/a6a08cd4fc4ff5cdd1099efeb37e55d90b9f436f/ghc >--------------------------------------------------------------- commit a6a08cd4fc4ff5cdd1099efeb37e55d90b9f436f Author: Joachim Breitner Date: Tue Oct 24 16:06:57 2017 -0400 Exitification: In simplLetUnfolding, set noUnfolding for exitJoinPoint Previously, this was using the existing unfolding, but that was bogus, because it was not simplified, and hence could refer to variables that are no longer in scope. This now matches what Note [Do not inline exit join points] actually says is happening. >--------------------------------------------------------------- a6a08cd4fc4ff5cdd1099efeb37e55d90b9f436f compiler/simplCore/Simplify.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index ac03968..bac0148 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -3237,7 +3237,7 @@ simplLetUnfolding env top_lvl cont_mb id new_rhs unf = simplStableUnfolding env top_lvl cont_mb id unf | sm_preserve_exit_joins (getMode env) , isExitJoinId id - = return unf -- see Note [Do not inline exit join points] + = return noUnfolding -- see Note [Do not inline exit join points] | otherwise = mkLetUnfolding (seDynFlags env) top_lvl InlineRhs id new_rhs From git at git.haskell.org Tue Oct 24 20:09:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 20:09:54 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (33033b8) Message-ID: <20171024200954.23ECE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/33033b8d8bbfd0755c5dc1c87c3be49c86627ad0/ghc >--------------------------------------------------------------- commit 33033b8d8bbfd0755c5dc1c87c3be49c86627ad0 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration >--------------------------------------------------------------- 33033b8d8bbfd0755c5dc1c87c3be49c86627ad0 compiler/simplCore/CoreMonad.hs | 7 +- compiler/simplCore/Exitify.hs | 6 + compiler/simplCore/SimplCore.hs | 40 ++-- compiler/simplCore/SimplUtils.hs | 7 +- compiler/simplCore/Simplify.hs | 3 +- testsuite/tests/simplCore/should_compile/T14152.hs | 22 ++ .../tests/simplCore/should_compile/T14152.stderr | 129 ++++++++++++ .../tests/simplCore/should_compile/T14152a.hs | 1 + .../tests/simplCore/should_compile/T14152a.stderr | 222 +++++++++++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 2 + 10 files changed, 417 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 33033b8d8bbfd0755c5dc1c87c3be49c86627ad0 From git at git.haskell.org Tue Oct 24 20:16:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Oct 2017 20:16:36 +0000 (UTC) Subject: [commit: ghc] branch 'wip/circleci' deleted Message-ID: <20171024201636.E13BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/circleci From git at git.haskell.org Wed Oct 25 03:14:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 03:14:31 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (48f451f) Message-ID: <20171025031431.5F03F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/48f451fd4085022f4aa1228a1f84658770f7a561/ghc >--------------------------------------------------------------- commit 48f451fd4085022f4aa1228a1f84658770f7a561 Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 The idea is described in #14152, and can be summarized: Float the exit path out of a joinrec, so that the simplifier can do more with it. See the test case for a nice example. The floating goes against what the simplifier usually does, hence we need to be careful not inline them back. The position of exitification in the pipeline was chosen after a small amount of experimentation, but may need to be improved. For example, exitification can allow rewrite rules to fire, but for that it would have to happen before the `simpl_phases`. Together with the next patch, perf.haskell.org reports these nice performance wins: Nofib allocations prev change gain fannkuch-redux 78446688 - 99.92% 64608 k-nucleotide 109466432 - 91.32% 9502064 simple 72424696 - 5.96% 68109560 Nofib instruction counts compress2 573354476 + 3.34% 592476104 k-nucleotide 2310080537 - 5.59% 2180917263 scs 1979135192 - 3.2% 1915880589 simple 670348375 - 4.9% 637507288 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- 48f451fd4085022f4aa1228a1f84658770f7a561 compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 403 ++++++++++++++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 9 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + 12 files changed, 450 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 48f451fd4085022f4aa1228a1f84658770f7a561 From git at git.haskell.org Wed Oct 25 03:14:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 03:14:35 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (a5770be) Message-ID: <20171025031435.415B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/a5770be56f57c099c0f9a173d146e52e388d64d6/ghc >--------------------------------------------------------------- commit a5770be56f57c099c0f9a173d146e52e388d64d6 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration because the extra jump is a bit pointless there. It still increases the number of instructions of `compress2` by 3.82%, so that needs to be investiaged. >--------------------------------------------------------------- a5770be56f57c099c0f9a173d146e52e388d64d6 compiler/simplCore/CoreMonad.hs | 7 +- compiler/simplCore/Exitify.hs | 6 + compiler/simplCore/SimplCore.hs | 40 ++-- compiler/simplCore/SimplUtils.hs | 7 +- compiler/simplCore/Simplify.hs | 3 +- testsuite/tests/simplCore/should_compile/T14152.hs | 22 ++ .../tests/simplCore/should_compile/T14152.stderr | 129 ++++++++++++ .../tests/simplCore/should_compile/T14152a.hs | 1 + .../tests/simplCore/should_compile/T14152a.stderr | 222 +++++++++++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 2 + 10 files changed, 417 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a5770be56f57c099c0f9a173d146e52e388d64d6 From git at git.haskell.org Wed Oct 25 07:24:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 07:24:52 +0000 (UTC) Subject: [commit: ghc] master: Windows: Bump to GCC 7.2 for GHC 8.4 (b62097d) Message-ID: <20171025072452.C87733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b62097d10e0ff490f862661a24e3ca1cc1bba841/ghc >--------------------------------------------------------------- commit b62097d10e0ff490f862661a24e3ca1cc1bba841 Author: Tamar Christina Date: Wed Oct 25 08:13:55 2017 +0100 Windows: Bump to GCC 7.2 for GHC 8.4 Summary: GHC 8.4 is expected to ship with an updated GCC bindist based on GCC 7.2. I am however at this time not updating the crt due to an issue introduced in september. https://sourceforge.net/p/mingw-w64/mailman/message/36085637/ Unless a favorable fix comes out of the discussion I will just ship the old crt with GHC 8.4. Test Plan: ./validate Reviewers: austin, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4119 >--------------------------------------------------------------- b62097d10e0ff490f862661a24e3ca1cc1bba841 mk/get-win32-tarballs.sh | 23 ++++++++++---------- mk/win32-tarballs.md5sum | 56 ++++++++++++++++++++++++------------------------ 2 files changed, 39 insertions(+), 40 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 b62097d10e0ff490f862661a24e3ca1cc1bba841 From git at git.haskell.org Wed Oct 25 07:24:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 07:24:49 +0000 (UTC) Subject: [commit: ghc] master: Remove the 'legroom' part of the timeout-accurate-pure test. (3825b7e) Message-ID: <20171025072449.E53293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3825b7e222bc1b7d643fce0755cf6b728fb1d854/ghc >--------------------------------------------------------------- commit 3825b7e222bc1b7d643fce0755cf6b728fb1d854 Author: Tom Sydney Kerckhove Date: Wed Oct 25 08:09:35 2017 +0100 Remove the 'legroom' part of the timeout-accurate-pure test. Summary: This removes the part of the test that checks whether the timeout happened in a 'reasonable' amount of time, because it is flaky. In subsequent work, we can turn this into a benchmark. Test Plan: This _is_ a test Reviewers: nh2, bgamari, Phyx, austin, hvr Reviewed By: Phyx Subscribers: rwbarton, thomie GHC Trac Issues: #8684 Differential Revision: https://phabricator.haskell.org/D4120 >--------------------------------------------------------------- 3825b7e222bc1b7d643fce0755cf6b728fb1d854 libraries/base/tests/all.T | 1 - libraries/base/tests/timeout-accurate-pure.hs | 28 ----------------------- libraries/base/tests/timeout-accurate-pure.stdout | 2 -- 3 files changed, 31 deletions(-) diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index a1eba6a..9055bd5 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -190,7 +190,6 @@ test('T8089', [exit_code(99), run_timeout_multiplier(0.01)], compile_and_run, ['']) test('T8684', expect_broken(8684), compile_and_run, ['']) -test('timeout-accurate-pure', normal, compile_and_run, ['']) test('T9826',normal, compile_and_run,['']) test('T9848', [ stats_num_field('bytes allocated', diff --git a/libraries/base/tests/timeout-accurate-pure.hs b/libraries/base/tests/timeout-accurate-pure.hs deleted file mode 100644 index a59e785..0000000 --- a/libraries/base/tests/timeout-accurate-pure.hs +++ /dev/null @@ -1,28 +0,0 @@ -import Control.Concurrent -import Control.Monad -import GHC.Clock -import System.IO -import System.Timeout - -ack :: Integer -> Integer -> Integer -ack 0 n = n + 1 -ack m 0 = ack (m - 1) 1 -ack m n = ack (m - 1) (ack m (n - 1)) - -main :: IO () -main = do - let microsecondsPerSecond = 1000 * 1000 - let timeToSpend = 1 * microsecondsPerSecond -- One second in microseconds - start <- getMonotonicTimeNSec - timeout timeToSpend $ - -- Something that is guaranteed not to be done in 'timeToSpend' - print $ ack 4 2 - end <- getMonotonicTimeNSec - let timeSpentNano = fromIntegral $ end - start -- in nanoseconds - let nanosecondsPerMicrosecond = 1000 - let timeToSpendNano = timeToSpend * nanosecondsPerMicrosecond - let legRoom = 1 * 1000 * nanosecondsPerMicrosecond -- Nanoseconds - let delta = timeSpentNano - timeToSpendNano - -- We can never wait for a shorter amount of time than specified - putStrLn $ "delta > 0: " ++ show (delta > 0) - putStrLn $ "delta < legroom: " ++ show (delta < legRoom) diff --git a/libraries/base/tests/timeout-accurate-pure.stdout b/libraries/base/tests/timeout-accurate-pure.stdout deleted file mode 100644 index 90f4a4c..0000000 --- a/libraries/base/tests/timeout-accurate-pure.stdout +++ /dev/null @@ -1,2 +0,0 @@ -delta > 0: True -delta < legroom: True From git at git.haskell.org Wed Oct 25 07:46:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 07:46:33 +0000 (UTC) Subject: [commit: ghc] master: Revert "Windows: Bump to GCC 7.2 for GHC 8.4" (e888a1f) Message-ID: <20171025074633.955083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e888a1ff4b5657c4243fe04f16db4e703fd601b2/ghc >--------------------------------------------------------------- commit e888a1ff4b5657c4243fe04f16db4e703fd601b2 Author: Tamar Christina Date: Wed Oct 25 08:45:24 2017 +0100 Revert "Windows: Bump to GCC 7.2 for GHC 8.4" This reverts commit b62097d10e0ff490f862661a24e3ca1cc1bba841. >--------------------------------------------------------------- e888a1ff4b5657c4243fe04f16db4e703fd601b2 mk/get-win32-tarballs.sh | 23 ++++++++++---------- mk/win32-tarballs.md5sum | 56 ++++++++++++++++++++++++------------------------ 2 files changed, 40 insertions(+), 39 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e888a1ff4b5657c4243fe04f16db4e703fd601b2 From git at git.haskell.org Wed Oct 25 08:12:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 08:12:38 +0000 (UTC) Subject: [commit: ghc] master: Update Win32 version for GHC 8.4. (561bdca) Message-ID: <20171025081238.DD05F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/561bdca16e2fe88d0b96fc10098955eabca81bba/ghc >--------------------------------------------------------------- commit 561bdca16e2fe88d0b96fc10098955eabca81bba Author: Tamar Christina Date: Wed Oct 25 08:51:00 2017 +0100 Update Win32 version for GHC 8.4. Summary: Update to Win32 2.6 which is the expected version release for 8.4 This bumps the required submodule s as well. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4117 >--------------------------------------------------------------- 561bdca16e2fe88d0b96fc10098955eabca81bba compiler/ghc.cabal.in | 2 +- docs/users_guide/8.4.1-notes.rst | 7 +++++++ ghc/ghc-bin.cabal.in | 2 +- libraries/Cabal | 2 +- libraries/Win32 | 2 +- libraries/directory | 2 +- libraries/process | 2 +- 7 files changed, 13 insertions(+), 6 deletions(-) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index d3cbe95..19e8d1a 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -67,7 +67,7 @@ Library ghci == @ProjectVersionMunged@ if os(windows) - Build-Depends: Win32 >= 2.3 && < 2.6 + Build-Depends: Win32 >= 2.3 && < 2.7 else if flag(terminfo) Build-Depends: terminfo == 0.4.* diff --git a/docs/users_guide/8.4.1-notes.rst b/docs/users_guide/8.4.1-notes.rst index b787e2e..8b11c05 100644 --- a/docs/users_guide/8.4.1-notes.rst +++ b/docs/users_guide/8.4.1-notes.rst @@ -271,3 +271,10 @@ Build system There is currently no explicit dependency between the two in the build system and such there is no way to notify ``base`` that the ``rts`` has been split, or vice versa. (see :ghc-ticket:`5987`). + +Win32 +~~~~~ + +- Version number 2.6.x.x (was 2.5.4.1) + NOTE: This release is a backwards incompatible release which corrects the type of certain APIs. + See issue https://github.com/haskell/win32/issues/24. diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index 5fe7c9d..c94c6f8 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -38,7 +38,7 @@ Executable ghc ghc == @ProjectVersionMunged@ if os(windows) - Build-Depends: Win32 >= 2.3 && < 2.6 + Build-Depends: Win32 >= 2.3 && < 2.7 else Build-Depends: unix == 2.7.* diff --git a/libraries/Cabal b/libraries/Cabal index 082cf20..46c79e1 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 082cf2066b7206d3b12a9f92d832236e2484b4c1 +Subproject commit 46c79e1d8d0ed76b20e8494b697f3057b64aafd5 diff --git a/libraries/Win32 b/libraries/Win32 index 147a0af..0f869f6 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit 147a0af92ac74ec58b209e16aeb1cf03bddf9482 +Subproject commit 0f869f6bf66e227d566947fdbf0886c10291d80d diff --git a/libraries/directory b/libraries/directory index 7e7b3c2..7504d6f 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit 7e7b3c2ae34c52c525270094b625f21829c83576 +Subproject commit 7504d6f94823684846545e48c046322039c64eb1 diff --git a/libraries/process b/libraries/process index 4f6e0a3..2fb7e73 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 4f6e0a336cb9a3517415c7279888667b9284d88f +Subproject commit 2fb7e739771f4a899a12b45f8b392e4874616b89 From git at git.haskell.org Wed Oct 25 08:31:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 08:31:16 +0000 (UTC) Subject: [commit: ghc] master: ghc-cabal: Inline removed function from Cabal. (f744261) Message-ID: <20171025083116.9CF903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f744261ad25942e8a747821fc468f1a21c9c705c/ghc >--------------------------------------------------------------- commit f744261ad25942e8a747821fc468f1a21c9c705c Author: Tamar Christina Date: Wed Oct 25 09:30:52 2017 +0100 ghc-cabal: Inline removed function from Cabal. >--------------------------------------------------------------- f744261ad25942e8a747821fc468f1a21c9c705c utils/ghc-cabal/Main.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index e445520..4ad1187 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -15,9 +15,10 @@ import Distribution.Simple.GHC import Distribution.Simple.Program import Distribution.Simple.Program.HcPkg import Distribution.Simple.Setup (ConfigFlags(configStripLibs), fromFlag, toFlag) -import Distribution.Simple.Utils (defaultPackageDesc, writeFileAtomic, toUTF8) +import Distribution.Simple.Utils (defaultPackageDesc, writeFileAtomic) import Distribution.Simple.Build (writeAutogenFiles) import Distribution.Simple.Register +import Distribution.Utils.String (encodeStringUtf8) import Distribution.Text import Distribution.Types.MungedPackageId import Distribution.Verbosity @@ -27,6 +28,7 @@ import qualified Distribution.Simple.PackageIndex as PackageIndex import Control.Exception (bracket) import Control.Monad import qualified Data.ByteString.Lazy.Char8 as BS +import Data.Char (chr) import Data.List import Data.Maybe import System.IO @@ -456,3 +458,8 @@ generate directory distdir config_args writeFileUtf8 f txt = withFile f WriteMode $ \hdl -> do hSetEncoding hdl utf8 hPutStr hdl txt + +-- | Was removed from Cabal so inline the old definition since +-- there isn't a 1-1 replacement for this. +toUTF8 :: String -> String +toUTF8 = map (chr . fromIntegral) . encodeStringUtf8 From git at git.haskell.org Wed Oct 25 08:59:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 08:59:58 +0000 (UTC) Subject: [commit: ghc] master: Revert "ghc-cabal: Inline removed function ..." (2e16a57) Message-ID: <20171025085958.CA4C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2e16a578e9380ea88792d0f9825b68faf4b81b8f/ghc >--------------------------------------------------------------- commit 2e16a578e9380ea88792d0f9825b68faf4b81b8f Author: Tamar Christina Date: Wed Oct 25 09:53:25 2017 +0100 Revert "ghc-cabal: Inline removed function ..." This reverts commit f744261ad25942e8a747821fc468f1a21c9c705c. >--------------------------------------------------------------- 2e16a578e9380ea88792d0f9825b68faf4b81b8f utils/ghc-cabal/Main.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 4ad1187..e445520 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -15,10 +15,9 @@ import Distribution.Simple.GHC import Distribution.Simple.Program import Distribution.Simple.Program.HcPkg import Distribution.Simple.Setup (ConfigFlags(configStripLibs), fromFlag, toFlag) -import Distribution.Simple.Utils (defaultPackageDesc, writeFileAtomic) +import Distribution.Simple.Utils (defaultPackageDesc, writeFileAtomic, toUTF8) import Distribution.Simple.Build (writeAutogenFiles) import Distribution.Simple.Register -import Distribution.Utils.String (encodeStringUtf8) import Distribution.Text import Distribution.Types.MungedPackageId import Distribution.Verbosity @@ -28,7 +27,6 @@ import qualified Distribution.Simple.PackageIndex as PackageIndex import Control.Exception (bracket) import Control.Monad import qualified Data.ByteString.Lazy.Char8 as BS -import Data.Char (chr) import Data.List import Data.Maybe import System.IO @@ -458,8 +456,3 @@ generate directory distdir config_args writeFileUtf8 f txt = withFile f WriteMode $ \hdl -> do hSetEncoding hdl utf8 hPutStr hdl txt - --- | Was removed from Cabal so inline the old definition since --- there isn't a 1-1 replacement for this. -toUTF8 :: String -> String -toUTF8 = map (chr . fromIntegral) . encodeStringUtf8 From git at git.haskell.org Wed Oct 25 09:00:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 09:00:01 +0000 (UTC) Subject: [commit: ghc] master: Revert "Update Win32 version for GHC 8.4." (b1ad0bb) Message-ID: <20171025090001.94D0B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b1ad0bb3be084f365b351dafed41593176e6ec08/ghc >--------------------------------------------------------------- commit b1ad0bb3be084f365b351dafed41593176e6ec08 Author: Tamar Christina Date: Wed Oct 25 09:53:54 2017 +0100 Revert "Update Win32 version for GHC 8.4." This reverts commit 561bdca16e2fe88d0b96fc10098955eabca81bba. submodule >--------------------------------------------------------------- b1ad0bb3be084f365b351dafed41593176e6ec08 compiler/ghc.cabal.in | 2 +- docs/users_guide/8.4.1-notes.rst | 7 ------- ghc/ghc-bin.cabal.in | 2 +- libraries/Cabal | 2 +- libraries/Win32 | 2 +- libraries/directory | 2 +- libraries/process | 2 +- 7 files changed, 6 insertions(+), 13 deletions(-) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index 19e8d1a..d3cbe95 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -67,7 +67,7 @@ Library ghci == @ProjectVersionMunged@ if os(windows) - Build-Depends: Win32 >= 2.3 && < 2.7 + Build-Depends: Win32 >= 2.3 && < 2.6 else if flag(terminfo) Build-Depends: terminfo == 0.4.* diff --git a/docs/users_guide/8.4.1-notes.rst b/docs/users_guide/8.4.1-notes.rst index 8b11c05..b787e2e 100644 --- a/docs/users_guide/8.4.1-notes.rst +++ b/docs/users_guide/8.4.1-notes.rst @@ -271,10 +271,3 @@ Build system There is currently no explicit dependency between the two in the build system and such there is no way to notify ``base`` that the ``rts`` has been split, or vice versa. (see :ghc-ticket:`5987`). - -Win32 -~~~~~ - -- Version number 2.6.x.x (was 2.5.4.1) - NOTE: This release is a backwards incompatible release which corrects the type of certain APIs. - See issue https://github.com/haskell/win32/issues/24. diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index c94c6f8..5fe7c9d 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -38,7 +38,7 @@ Executable ghc ghc == @ProjectVersionMunged@ if os(windows) - Build-Depends: Win32 >= 2.3 && < 2.7 + Build-Depends: Win32 >= 2.3 && < 2.6 else Build-Depends: unix == 2.7.* diff --git a/libraries/Cabal b/libraries/Cabal index 46c79e1..082cf20 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 46c79e1d8d0ed76b20e8494b697f3057b64aafd5 +Subproject commit 082cf2066b7206d3b12a9f92d832236e2484b4c1 diff --git a/libraries/Win32 b/libraries/Win32 index 0f869f6..147a0af 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit 0f869f6bf66e227d566947fdbf0886c10291d80d +Subproject commit 147a0af92ac74ec58b209e16aeb1cf03bddf9482 diff --git a/libraries/directory b/libraries/directory index 7504d6f..7e7b3c2 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit 7504d6f94823684846545e48c046322039c64eb1 +Subproject commit 7e7b3c2ae34c52c525270094b625f21829c83576 diff --git a/libraries/process b/libraries/process index 2fb7e73..4f6e0a3 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 2fb7e739771f4a899a12b45f8b392e4874616b89 +Subproject commit 4f6e0a336cb9a3517415c7279888667b9284d88f From git at git.haskell.org Wed Oct 25 14:14:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 14:14:26 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (1cce72e) Message-ID: <20171025141426.C32C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/1cce72e96bd01d07955fa7c7177de983bd4dd44c/ghc >--------------------------------------------------------------- commit 1cce72e96bd01d07955fa7c7177de983bd4dd44c Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 The idea is described in #14152, and can be summarized: Float the exit path out of a joinrec, so that the simplifier can do more with it. See the test case for a nice example. The floating goes against what the simplifier usually does, hence we need to be careful not inline them back. The position of exitification in the pipeline was chosen after a small amount of experimentation, but may need to be improved. For example, exitification can allow rewrite rules to fire, but for that it would have to happen before the `simpl_phases`. Together with the next patch, perf.haskell.org reports these nice performance wins: Nofib allocations prev change gain fannkuch-redux 78446688 - 99.92% 64608 k-nucleotide 109466432 - 91.32% 9502064 simple 72424696 - 5.96% 68109560 Nofib instruction counts compress2 573354476 + 3.34% 592476104 k-nucleotide 2310080537 - 5.59% 2180917263 scs 1979135192 - 3.2% 1915880589 simple 670348375 - 4.9% 637507288 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- 1cce72e96bd01d07955fa7c7177de983bd4dd44c compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 403 +++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 9 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + testsuite/tests/simplCore/should_compile/T14152.hs | 22 ++ .../tests/simplCore/should_compile/T14152.stderr | 129 +++++++ .../tests/simplCore/should_compile/T14152a.hs | 1 + .../tests/simplCore/should_compile/T14152a.stderr | 222 ++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 2 + 17 files changed, 826 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1cce72e96bd01d07955fa7c7177de983bd4dd44c From git at git.haskell.org Wed Oct 25 14:14:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 14:14:29 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Really run exitifiation only once (2c2744b) Message-ID: <20171025141429.97E623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/2c2744b5bd3f190f8bbb0ea325392142b51671fd/ghc >--------------------------------------------------------------- commit 2c2744b5bd3f190f8bbb0ea325392142b51671fd Author: Joachim Breitner Date: Wed Oct 25 10:12:40 2017 -0400 Really run exitifiation only once (I thought I did that already… well, let’s measure it) >--------------------------------------------------------------- 2c2744b5bd3f190f8bbb0ea325392142b51671fd compiler/simplCore/SimplCore.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index c805fa8..10115c4 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -312,8 +312,6 @@ getCoreToDo dflags runWhen strictness demand_analyser, - runWhen exitification CoreDoExitify, - runWhen full_laziness $ CoreDoFloatOutwards FloatOutSwitches { floatOutLambdas = floatLamArgs dflags, From git at git.haskell.org Wed Oct 25 14:14:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 14:14:32 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (4e88283) Message-ID: <20171025141432.649403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/4e88283225ce0fe75278b4d0c5b38acd08f1df9b/ghc >--------------------------------------------------------------- commit 4e88283225ce0fe75278b4d0c5b38acd08f1df9b Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration because the extra jump is a bit pointless there. It still increases the number of instructions of `compress2` by 3.82%, so that needs to be investiaged. >--------------------------------------------------------------- 4e88283225ce0fe75278b4d0c5b38acd08f1df9b compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 6 ++++++ compiler/simplCore/SimplCore.hs | 40 +++++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 41 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4e88283225ce0fe75278b4d0c5b38acd08f1df9b From git at git.haskell.org Wed Oct 25 16:48:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 16:48:53 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (c211c11) Message-ID: <20171025164853.D42913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/c211c11fdc798cd59533d7cff7b398ff2ba5950a/ghc >--------------------------------------------------------------- commit c211c11fdc798cd59533d7cff7b398ff2ba5950a Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration because the extra jump is a bit pointless there. It still increases the number of instructions of `compress2` by 3.82%, so that needs to be investiaged. >--------------------------------------------------------------- c211c11fdc798cd59533d7cff7b398ff2ba5950a compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 6 ++++++ compiler/simplCore/SimplCore.hs | 40 +++++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 41 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c211c11fdc798cd59533d7cff7b398ff2ba5950a From git at git.haskell.org Wed Oct 25 16:48:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 16:48:56 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Try exitification after demand analysis (7a929c4) Message-ID: <20171025164856.A33243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/7a929c4fc53ce28ddcd67c8a9b5acc60216015d8/ghc >--------------------------------------------------------------- commit 7a929c4fc53ce28ddcd67c8a9b5acc60216015d8 Author: Joachim Breitner Date: Wed Oct 25 12:44:42 2017 -0400 Try exitification after demand analysis Previous, I was running it twice: * before the main simplifier pass * after demand analysis and the results were a clear win. Removing the second one of these regressed k-nucleotide: allocs/k-nucleotide 9502040 + 3.78% 9861544 bytes instr/k-nucleotide 2172066020 + 18.89% 2582364781 so let's see what happens if I remove the first one of these, and only use the second one. >--------------------------------------------------------------- 7a929c4fc53ce28ddcd67c8a9b5acc60216015d8 compiler/simplCore/SimplCore.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 10115c4..21a5c21 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -284,8 +284,6 @@ getCoreToDo dflags simpl_phases, - runWhen exitification CoreDoExitify, - -- Phase 0: allow all Ids to be inlined now -- This gets foldr inlined before strictness analysis @@ -312,6 +310,8 @@ getCoreToDo dflags runWhen strictness demand_analyser, + runWhen exitification CoreDoExitify, + runWhen full_laziness $ CoreDoFloatOutwards FloatOutSwitches { floatOutLambdas = floatLamArgs dflags, From git at git.haskell.org Wed Oct 25 17:21:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 17:21:31 +0000 (UTC) Subject: [commit: ghc] branch 'wip/D4112' deleted Message-ID: <20171025172131.136BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/D4112 From git at git.haskell.org Wed Oct 25 17:21:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 17:21:33 +0000 (UTC) Subject: [commit: ghc] master: Make language extensions their own category in the documentation (61f1b46) Message-ID: <20171025172133.EC0473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/61f1b46e2a56fcb1e95dd1c4e87fb31940b3412d/ghc >--------------------------------------------------------------- commit 61f1b46e2a56fcb1e95dd1c4e87fb31940b3412d Author: Joachim Breitner Date: Thu Oct 19 14:21:49 2017 -0400 Make language extensions their own category in the documentation I.e. instead of .. ghc-flag:: -XUnboxedTuples :shortdesc: Enable the use of unboxed tuple syntax. :type: dynamic :reverse: -XNoUnboxedTuples :category: one simply writes .. extension:: UnboxedTuples :shortdesc: Enable the use of unboxed tuple syntax. This allows language extensions to be referenced as If :extension:`UnboxedTuples` is enabled, then... This directive still creates the entries for the `-XUnboxedTuples` flag, so in particular, Set :ghc-flag:`-XUnboxedTuples` if you have to. still works, and lists of flags in general (e.g. for the manpage) include these. I also removed lots of links from the shortdesc of the extensions, when this link simply points to the section where the extension is defined. I removed the list of `-X` flags from the flag reference table, but added a table of extension under “10.1. Language options” Lots of text in the manual now refers to “extension `Foo`” rather than “flag `-XFoo`”. I consider `-XFoo` a historic artifact that stems from when language extensions were really just flags. These days, the use of `-XFoo` is (IMHO) deprecated: You should be using `LANGUAGE Foo`, or maybe the appropriate field in a `.cabal` file. See 9278994 which did this change to error messages already. Differential Revision: https://phabricator.haskell.org/D4112 >--------------------------------------------------------------- 61f1b46e2a56fcb1e95dd1c4e87fb31940b3412d docs/users_guide/ffi-chap.rst | 21 +- docs/users_guide/flags.py | 309 +++++- docs/users_guide/flags.rst | 11 - docs/users_guide/ghci.rst | 21 +- docs/users_guide/glasgow_exts.rst | 1397 +++++++++++---------------- docs/users_guide/phases.rst | 7 +- docs/users_guide/safe_haskell.rst | 102 +- docs/users_guide/what_glasgow_exts_does.rst | 62 +- 8 files changed, 925 insertions(+), 1005 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 61f1b46e2a56fcb1e95dd1c4e87fb31940b3412d From git at git.haskell.org Wed Oct 25 19:47:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 19:47:40 +0000 (UTC) Subject: [commit: ghc] master: typecheck: Clarify errors mentioned in #14385 (bf83435) Message-ID: <20171025194740.473673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bf83435b5c62776072977b9b1fc5aba2bffa97b4/ghc >--------------------------------------------------------------- commit bf83435b5c62776072977b9b1fc5aba2bffa97b4 Author: Ben Gamari Date: Tue Oct 24 13:56:29 2017 -0400 typecheck: Clarify errors mentioned in #14385 >--------------------------------------------------------------- bf83435b5c62776072977b9b1fc5aba2bffa97b4 compiler/typecheck/TcTyClsDecls.hs | 12 ++++++------ testsuite/tests/gadt/gadtSyntaxFail001.stderr | 2 +- testsuite/tests/gadt/gadtSyntaxFail002.stderr | 2 +- testsuite/tests/gadt/gadtSyntaxFail003.stderr | 2 +- testsuite/tests/ghci/scripts/T9293.stderr | 6 +++--- testsuite/tests/ghci/scripts/ghci057.stderr | 6 +++--- testsuite/tests/module/mod39.stderr | 2 +- testsuite/tests/parser/should_fail/readFail037.stderr | 8 ++++---- testsuite/tests/parser/should_fail/readFail041.stderr | 8 ++++---- testsuite/tests/typecheck/should_fail/T12083a.stderr | 2 +- testsuite/tests/typecheck/should_fail/TcNoNullaryTC.stderr | 8 ++++---- testsuite/tests/typecheck/should_fail/tcfail150.stderr | 2 +- 12 files changed, 30 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 bf83435b5c62776072977b9b1fc5aba2bffa97b4 From git at git.haskell.org Wed Oct 25 19:47:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 19:47:43 +0000 (UTC) Subject: [commit: ghc] master: Make layLeft and reduceDoc stricter (#7258) (2a4c24e) Message-ID: <20171025194743.098763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a4c24e40462832a4a97cd7a65119542e842de81/ghc >--------------------------------------------------------------- commit 2a4c24e40462832a4a97cd7a65119542e842de81 Author: Tobias Dammers Date: Wed Oct 25 14:17:58 2017 -0400 Make layLeft and reduceDoc stricter (#7258) Making the pretty-printer based assembly output stricter in strategically chosen locations produces a minor performance improvement when compiling large derived Read instance (on the order of 5-10%). Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4111 >--------------------------------------------------------------- 2a4c24e40462832a4a97cd7a65119542e842de81 compiler/utils/Pretty.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/compiler/utils/Pretty.hs b/compiler/utils/Pretty.hs index 78c8e6a..f4987d3 100644 --- a/compiler/utils/Pretty.hs +++ b/compiler/utils/Pretty.hs @@ -433,8 +433,8 @@ maybeParens True = parens -- | Perform some simplification of a built up @GDoc at . reduceDoc :: Doc -> RDoc -reduceDoc (Beside p g q) = beside p g (reduceDoc q) -reduceDoc (Above p g q) = above p g (reduceDoc q) +reduceDoc (Beside p g q) = p `seq` g `seq` (beside p g $! reduceDoc q) +reduceDoc (Above p g q) = p `seq` g `seq` (above p g $! reduceDoc q) reduceDoc p = p -- | List version of '<>'. @@ -1032,11 +1032,11 @@ bufLeftRender b doc = layLeft b (reduceDoc doc) layLeft :: BufHandle -> Doc -> IO () layLeft b _ | b `seq` False = undefined -- make it strict in b layLeft _ NoDoc = error "layLeft: NoDoc" -layLeft b (Union p q) = layLeft b (first p q) -layLeft b (Nest _ p) = layLeft b p +layLeft b (Union p q) = layLeft b $! first p q +layLeft b (Nest _ p) = layLeft b $! p layLeft b Empty = bPutChar b '\n' -layLeft b (NilAbove p) = bPutChar b '\n' >> layLeft b p -layLeft b (TextBeside s _ p) = put b s >> layLeft b p +layLeft b (NilAbove p) = p `seq` (bPutChar b '\n' >> layLeft b p) +layLeft b (TextBeside s _ p) = s `seq` (put b s >> layLeft b p) where put b _ | b `seq` False = undefined put b (Chr c) = bPutChar b c From git at git.haskell.org Wed Oct 25 19:47:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 19:47:45 +0000 (UTC) Subject: [commit: ghc] master: Add info about Github pull requests. (bd53b48) Message-ID: <20171025194745.BF1333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bd53b488d6bf59329f33a5fb6ba2ef0170285298/ghc >--------------------------------------------------------------- commit bd53b488d6bf59329f33a5fb6ba2ef0170285298 Author: AndreasPK Date: Fri Oct 20 23:53:54 2017 +0200 Add info about Github pull requests. >--------------------------------------------------------------- bd53b488d6bf59329f33a5fb6ba2ef0170285298 HACKING.md | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/HACKING.md b/HACKING.md index ecfd35b..cb68889 100644 --- a/HACKING.md +++ b/HACKING.md @@ -61,12 +61,12 @@ newly built compiler. Now, hack on your copy and rebuild (with `make`) as necessary. -Then start by making your commits however you want. When you're done, you'll -need to submit your patch to [Phabricator](https://phabricator.haskell.org/) for -code review. To do so you will need to -[install Arcanist](https://secure.phabricator.com/book/phabricator/article/arcanist/#installing-arcanist), -Phabricator's CLI tool. Once installed, you can submit your work for code review -using `arc diff`. +Then start by making your commits however you want. When you're done, you can submit + a pull request on Github for small changes. For larger changes the patch needs to be + submitted to [Phabricator](https://phabricator.haskell.org/) for code review. + The GHC Trac Wiki has a good summary for the [overall process](https://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/FixingBugs) + as well as a guide on + [how to use Phabricator/arcanist](https://ghc.haskell.org/trac/ghc/wiki/Phabricator). Useful links: From git at git.haskell.org Wed Oct 25 19:47:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 19:47:48 +0000 (UTC) Subject: [commit: ghc] master: Windows: Update the mirror script to generate hashes and use mirror fallback (980e127) Message-ID: <20171025194748.7E8663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/980e1270ed7f681ef666ca36fe291cfb8613348c/ghc >--------------------------------------------------------------- commit 980e1270ed7f681ef666ca36fe291cfb8613348c Author: Tamar Christina Date: Wed Oct 25 14:19:44 2017 -0400 Windows: Update the mirror script to generate hashes and use mirror fallback This fixes the mirror script so it correctly queries haskell.org and if packages aren't found check repo.msys2.org. Also the mirror functionality now generates the md5 hashes after a mirror fetch that can be placed in the md5sums file. Test Plan: mk/get-win32-tarballs.sh fetch mirror and ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4118 >--------------------------------------------------------------- 980e1270ed7f681ef666ca36fe291cfb8613348c mk/get-win32-tarballs.sh | 30 ++++++++++++++++++++++++------ 1 file changed, 24 insertions(+), 6 deletions(-) diff --git a/mk/get-win32-tarballs.sh b/mk/get-win32-tarballs.sh index b3c9e07..a337019 100755 --- a/mk/get-win32-tarballs.sh +++ b/mk/get-win32-tarballs.sh @@ -22,11 +22,11 @@ download_file() { if ! test -f "${dest_file}" then - local curl_cmd="curl -L ${file_url} -o ${dest_file} --create-dirs -# ${extra_curl_opts}" + local curl_cmd="curl -f -L ${file_url} -o ${dest_file} --create-dirs -# ${extra_curl_opts}" if test -n "${backup_url}"; then - local curl_cmd_bnk="curl -L ${backup_url} -o ${dest_file} --create-dirs -# ${extra_curl_opts}" + local curl_cmd_bnk="curl -f -L ${backup_url} -o ${dest_file} --create-dirs -# ${extra_curl_opts}" else - local curl_cmd_bnk="echo 1" + local curl_cmd_bnk="true" fi if test "$download" = "0" @@ -37,9 +37,10 @@ download_file() { return else echo "Downloading ${description} to ${dest_dir}..." - $curl_cmd || $curl_cmd_bnk || { + $curl_cmd || echo "Checking repo.msys2.org instead of Haskell.org..." && $curl_cmd_bnk || { rm -f "${dest_file}" fail "ERROR: Download failed." + exit 1 } fi fi @@ -48,10 +49,16 @@ download_file() { if test "$sigs" = "1" -a ! -f "$sig_file" then echo "Downloading ${description} (signature) to ${dest_dir}..." - local curl_cmd="curl -L ${file_url}.sig -o ${sig_file} --create-dirs -# ${extra_curl_opts}" - $curl_cmd || { + local curl_cmd="curl -f -L ${file_url}.sig -o ${sig_file} --create-dirs -# ${extra_curl_opts}" + if test -n "${backup_url}"; then + local curl_cmd_bnk="curl -f -L ${backup_url} -o ${sig_file} --create-dirs -# ${extra_curl_opts}" + else + local curl_cmd_bnk="true" + fi + $curl_cmd || echo "Checking repo.msys2.org instead of Haskell.org..." && $curl_cmd_bnk || { rm -f "${dest_file}.sig" fail "ERROR: Download failed." + exit 1 } fi @@ -72,6 +79,7 @@ download_mingw() { -e 's/-sources-/-/' \ -e 's/-libwinpthread-git-/-winpthreads-git-/' ` local mingw_url="${mingw_base_url_primary}/${mingw_url_tmp}" + local mingw_url_backup="${mingw_base_url_secondary}/${mingw_url_tmp}" else local mingw_url="${mingw_base_url_primary}/$1" local mingw_url_backup="${mingw_base_url_secondary}/$1" @@ -165,6 +173,10 @@ sync_binaries_and_sources() { done } +show_hashes_for_binaries() { + $FIND ghc-tarballs/ -iname "*.*" | xargs md5sum | grep -v "\.sig" | sed -s "s/\*//" +} + usage() { echo "$0 - Download GHC mingw toolchain tarballs" echo @@ -175,6 +187,7 @@ usage() { echo " download download the necessary tarballs for the given architecture" echo " fetch download the necessary tarballs for the given architecture but doesn't verify their md5." echo " verify verify the existence and correctness of the necessary tarballs" + echo " hash generate md5 hashes for inclusion in win32-tarballs.md5sum" echo " sync upload packages downloaded with 'fetch mirror' to haskell.org" echo "" echo "and is one of i386, x86_64,all or mirror (which includes sources)" @@ -199,6 +212,10 @@ case $1 in verify=0 sync=1 ;; + hash) + show_hashes_for_binaries + exit 1 + ;; *) usage exit 1 @@ -222,6 +239,7 @@ case $2 in download_x86_64 verify=0 download_sources + show_hashes_for_binaries ;; *) if test "$sync" = "1"; then From git at git.haskell.org Wed Oct 25 19:47:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 19:47:51 +0000 (UTC) Subject: [commit: ghc] master: Fix space leak in BinIface.getSymbolTable (1c15d8e) Message-ID: <20171025194751.46B943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c15d8ed112bccf2635d571767733b2a26d8fb21/ghc >--------------------------------------------------------------- commit 1c15d8ed112bccf2635d571767733b2a26d8fb21 Author: Douglas Wilson Date: Wed Oct 25 14:20:06 2017 -0400 Fix space leak in BinIface.getSymbolTable Replace a call to mapAccumR, which uses linear stack space, with a gadget that uses constant space. Remove an unused parameter from fromOnDiskName. The tests T1292_imports and T4239 are now reporting imported names in a different order. I don't completely understand why, but I presume it is because the symbol tables are now read more strictly. The new order seems better in T1792_imports, and equally random in T4239. There are several performance test improvements. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: alexbiehl, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4124 >--------------------------------------------------------------- 1c15d8ed112bccf2635d571767733b2a26d8fb21 compiler/iface/BinIface.hs | 33 +++++++++++++++------- testsuite/tests/perf/compiler/all.T | 6 ++-- .../rename/should_compile/T1792_imports.stdout | 2 +- testsuite/tests/rename/should_compile/T4239.stdout | 2 +- 4 files changed, 29 insertions(+), 14 deletions(-) diff --git a/compiler/iface/BinIface.hs b/compiler/iface/BinIface.hs index 969dc85..8ab2310 100644 --- a/compiler/iface/BinIface.hs +++ b/compiler/iface/BinIface.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE BinaryLiterals, CPP, ScopedTypeVariables #-} +{-# LANGUAGE BinaryLiterals, CPP, ScopedTypeVariables, BangPatterns #-} -- -- (c) The University of Glasgow 2002-2006 @@ -44,14 +44,18 @@ import FastString import Constants import Util +import Data.Array +import Data.Array.ST +import Data.Array.Unsafe import Data.Bits import Data.Char -import Data.List import Data.Word -import Data.Array import Data.IORef +import Data.Foldable import Control.Monad - +import Control.Monad.ST +import Control.Monad.Trans.Class +import qualified Control.Monad.Trans.State.Strict as State -- --------------------------------------------------------------------------- -- Reading and writing binary interface files @@ -261,15 +265,24 @@ getSymbolTable bh ncu = do sz <- get bh od_names <- sequence (replicate sz (get bh)) updateNameCache ncu $ \namecache -> - let arr = listArray (0,sz-1) names - (namecache', names) = - mapAccumR (fromOnDiskName arr) namecache od_names - in (namecache', arr) + runST $ flip State.evalStateT namecache $ do + mut_arr <- lift $ newSTArray_ (0, sz-1) + for_ (zip [0..] od_names) $ \(i, odn) -> do + (nc, !n) <- State.gets $ \nc -> fromOnDiskName nc odn + lift $ writeArray mut_arr i n + State.put nc + arr <- lift $ unsafeFreeze mut_arr + namecache' <- State.get + return (namecache', arr) + where + -- This binding is required because the type of newArray_ cannot be inferred + newSTArray_ :: forall s. (Int, Int) -> ST s (STArray s Int Name) + newSTArray_ = newArray_ type OnDiskName = (UnitId, ModuleName, OccName) -fromOnDiskName :: Array Int Name -> NameCache -> OnDiskName -> (NameCache, Name) -fromOnDiskName _ nc (pid, mod_name, occ) = +fromOnDiskName :: NameCache -> OnDiskName -> (NameCache, Name) +fromOnDiskName nc (pid, mod_name, occ) = let mod = mkModule pid mod_name cache = nsNames nc in case lookupOrigNameCache cache mod occ of diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index b80900d..41b2af8 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -658,7 +658,7 @@ test('T5837', # 2017-02-19 59161648 (x64/Windows) - Unknown # 2017-04-21 54985248 (x64/Windows) - Unknown - (wordsize(64), 56782344, 7)]) + (wordsize(64), 52089424, 7)]) # sample: 3926235424 (amd64/Linux, 15/2/2012) # 2012-10-02 81879216 # 2012-09-20 87254264 amd64/Linux @@ -695,6 +695,7 @@ test('T5837', # 2017-02-28 54151864 amd64/Linux Likely drift due to recent simplifier improvements # 2017-02-25 52625920 amd64/Linux Early inlining patch # 2017-09-06 56782344 amd64/Linux Drift manifest in unrelated LLVM patch + # 2017-10-24 52089424 amd64/linux Fix space leak in BinIface.getSymbolTable ], compile, ['-freduction-depth=50']) @@ -1114,10 +1115,11 @@ test('T12707', test('T12150', [ only_ways(['optasm']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 78300680, 5) + [(wordsize(64), 73769936, 5) # initial: 70773000 # 2017-08-25: 74358208 Refactor the Mighty Simplifier # 2017-08-25: 78300680 Drift + # 2017-10-25: 73769936 amd64/linux Fix space leak in BinIface.getSymbolTable ]), ], compile, diff --git a/testsuite/tests/rename/should_compile/T1792_imports.stdout b/testsuite/tests/rename/should_compile/T1792_imports.stdout index 9c502c6..b497d12 100644 --- a/testsuite/tests/rename/should_compile/T1792_imports.stdout +++ b/testsuite/tests/rename/should_compile/T1792_imports.stdout @@ -1 +1 @@ -import qualified Data.ByteString as B ( readFile, putStr ) +import qualified Data.ByteString as B ( putStr, readFile ) diff --git a/testsuite/tests/rename/should_compile/T4239.stdout b/testsuite/tests/rename/should_compile/T4239.stdout index 6e55a4e..a1f53d2 100644 --- a/testsuite/tests/rename/should_compile/T4239.stdout +++ b/testsuite/tests/rename/should_compile/T4239.stdout @@ -1 +1 @@ -import T4239A ( type (:+++)((:---), X, (:+++)), (·) ) +import T4239A ( (·), type (:+++)((:---), X, (:+++)) ) From git at git.haskell.org Wed Oct 25 20:44:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 20:44:41 +0000 (UTC) Subject: [commit: ghc] master: Performance improvements linear regAlloc (#7258) (df63668) Message-ID: <20171025204441.042F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df636682f3b8299268d189bfaf6de1d672c19a73/ghc >--------------------------------------------------------------- commit df636682f3b8299268d189bfaf6de1d672c19a73 Author: Tobias Dammers Date: Wed Oct 25 15:50:32 2017 -0400 Performance improvements linear regAlloc (#7258) When allocating and potentially spilling registers, we need to check the desired allocations against current allocations to decide where we can spill to, cq. which allocations we can toss and if so, how. Previously, this was done by walking the Cartesian product of the current allocations (`assig`) and the allocations to keep (`keep`), which has quadratic complexity. This patch introduces two improvements: 1. pre-filter the `assig` list, because we are only interested in two types of allocations (in register, and in register+memory), which will only make up a small and constant portion of the list; and 2. use set / map operations instead of lists, which reduces algorithmic complexity. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4109 >--------------------------------------------------------------- df636682f3b8299268d189bfaf6de1d672c19a73 compiler/nativeGen/RegAlloc/Linear/Main.hs | 24 +++++++++++++----------- 1 file changed, 13 insertions(+), 11 deletions(-) diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs index 171ce88..6171d8d 100644 --- a/compiler/nativeGen/RegAlloc/Linear/Main.hs +++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs @@ -809,27 +809,29 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc -- case (3): we need to push something out to free up a register [] -> - do let keep' = map getUnique keep + do let inRegOrBoth (InReg _) = True + inRegOrBoth (InBoth _ _) = True + inRegOrBoth _ = False + let candidates' = + flip delListFromUFM keep $ + filterUFM inRegOrBoth $ + assig + -- This is non-deterministic but we do not + -- currently support deterministic code-generation. + -- See Note [Unique Determinism and code generation] + let candidates = nonDetUFMToList candidates' -- the vregs we could kick out that are already in a slot let candidates_inBoth = [ (temp, reg, mem) - | (temp, InBoth reg mem) <- nonDetUFMToList assig - -- This is non-deterministic but we do not - -- currently support deterministic code-generation. - -- See Note [Unique Determinism and code generation] - , temp `notElem` keep' + | (temp, InBoth reg mem) <- candidates , targetClassOfRealReg platform reg == classOfVirtualReg r ] -- the vregs we could kick out that are only in a reg -- this would require writing the reg to a new slot before using it. let candidates_inReg = [ (temp, reg) - | (temp, InReg reg) <- nonDetUFMToList assig - -- This is non-deterministic but we do not - -- currently support deterministic code-generation. - -- See Note [Unique Determinism and code generation] - , temp `notElem` keep' + | (temp, InReg reg) <- candidates , targetClassOfRealReg platform reg == classOfVirtualReg r ] let result From git at git.haskell.org Wed Oct 25 20:44:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 20:44:44 +0000 (UTC) Subject: [commit: ghc] master: Implement `-Wpartial-fields` warning (#7169) (f7f270e) Message-ID: <20171025204444.A791E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f7f270eb6ba616feda79d370336db7e66f9ab79c/ghc >--------------------------------------------------------------- commit f7f270eb6ba616feda79d370336db7e66f9ab79c Author: Daishi Nakajima Date: Wed Oct 25 15:51:01 2017 -0400 Implement `-Wpartial-fields` warning (#7169) Warning on declaring a partial record selector. However, disable warn with field names that start with underscore. Test Plan: Added 1 test case. Reviewers: austin, bgamari, simonpj Reviewed By: bgamari, simonpj Subscribers: goldfire, simonpj, duog, rwbarton, thomie GHC Trac Issues: #7169 Differential Revision: https://phabricator.haskell.org/D4083 >--------------------------------------------------------------- f7f270eb6ba616feda79d370336db7e66f9ab79c compiler/main/DynFlags.hs | 4 ++- compiler/typecheck/TcTyClsDecls.hs | 42 ++++++++++++++++++++++ docs/users_guide/using-warnings.rst | 19 +++++++++- testsuite/tests/typecheck/should_compile/T7169.hs | 23 ++++++++++++ .../tests/typecheck/should_compile/T7169.stderr | 2 ++ testsuite/tests/typecheck/should_compile/all.T | 1 + 6 files changed, 89 insertions(+), 2 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 4c62a0d..7602b71 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -674,6 +674,7 @@ data WarningFlag = | Opt_WarnCPPUndef -- Since 8.2 | Opt_WarnUnbangedStrictPatterns -- Since 8.2 | Opt_WarnMissingHomeModules -- Since 8.2 + | Opt_WarnPartialFields -- Since 8.4 deriving (Eq, Show, Enum) data Language = Haskell98 | Haskell2010 @@ -3665,7 +3666,8 @@ wWarningFlagsDeps = [ Opt_WarnMissingPatternSynonymSignatures, flagSpec "simplifiable-class-constraints" Opt_WarnSimplifiableClassConstraints, flagSpec "missing-home-modules" Opt_WarnMissingHomeModules, - flagSpec "unrecognised-warning-flags" Opt_WarnUnrecognisedWarningFlags ] + flagSpec "unrecognised-warning-flags" Opt_WarnUnrecognisedWarningFlags, + flagSpec "partial-fields" Opt_WarnPartialFields ] -- | These @-\@ flags can all be reversed with @-no-\@ negatableFlagsDeps :: [(Deprecation, FlagSpec GeneralFlag)] diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index b4b31e3..cf92638 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -2355,6 +2355,7 @@ checkValidTyCon tc ; let ex_ok = existential_ok || gadt_ok -- Data cons can have existential context ; mapM_ (checkValidDataCon dflags ex_ok tc) data_cons + ; mapM_ (checkPartialRecordField data_cons) (tyConFieldLabels tc) -- Check that fields with the same name share a type ; mapM_ check_fields groups }} @@ -2401,6 +2402,29 @@ checkValidTyCon tc (_, _, _, res2) = dataConSig con2 fty2 = dataConFieldType con2 lbl +checkPartialRecordField :: [DataCon] -> FieldLabel -> TcM () +-- Check the partial record field selector, and warns. +-- See Note [Checking partial record field] +checkPartialRecordField all_cons fld + = setSrcSpan loc $ + warnIfFlag Opt_WarnPartialFields + (not is_exhaustive && not (startsWithUnderscore occ_name)) + (sep [text "Use of partial record field selector" <> colon, + nest 2 $ quotes (ppr occ_name)]) + where + sel_name = flSelector fld + loc = getSrcSpan sel_name + occ_name = getOccName sel_name + + (cons_with_field, cons_without_field) = partition has_field all_cons + has_field con = fld `elem` (dataConFieldLabels con) + is_exhaustive = all (dataConCannotMatch inst_tys) cons_without_field + + con1 = ASSERT( not (null cons_with_field) ) head cons_with_field + (univ_tvs, _, eq_spec, _, _, _) = dataConFullSig con1 + eq_subst = mkTvSubstPrs (map eqSpecPair eq_spec) + inst_tys = substTyVars eq_subst univ_tvs + checkFieldCompat :: FieldLabelString -> DataCon -> DataCon -> Type -> Type -> Type -> Type -> TcM () checkFieldCompat fld con1 con2 res1 res2 fty1 fty2 @@ -2958,6 +2982,24 @@ tcSplitSigmaTy. tcSplitNestedSigmaTys will always split any foralls that it sees until it can't go any further, so if you called it on the default type signature for `each`, it would return (a -> f b) -> s -> f t like we desired. +Note [Checking partial record field] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +This check checks the partial record field selector, and warns (Trac #7169). + +For example: + + data T a = A { m1 :: a, m2 :: a } | B { m1 :: a } + +The function 'm2' is partial record field, and will fail when it is applied to +'B'. The warning identifies such partial fields. The check is performed at the +declaration of T, not at the call-sites of m2. + +The warning can be suppressed by prefixing the field-name with an underscore. +For example: + + data T a = A { m1 :: a, _m2 :: a } | B { m1 :: a } + + ************************************************************************ * * Checking role validity diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index 65ffe99..216d7ee 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -78,6 +78,7 @@ The following flags are simple ways to select standard "packages" of warnings: * :ghc-flag:`-Wmissing-home-modules` * :ghc-flag:`-Widentities` * :ghc-flag:`-Wredundant-constraints` + * :ghc-flag:`-Wpartial-fields` .. ghc-flag:: -Weverything :shortdesc: enable all warnings supported by GHC @@ -1464,7 +1465,23 @@ of ``-W(no-)*``. pick up modules, not listed neither in ``exposed-modules``, nor in ``other-modules``. +.. ghc-flag:: -Wpartial-fields + :shortdesc: warn when define partial record field. + :type: dynamic + :reverse: -Wno-partial-fields + :category: + + :since: 8.4 + + The option :ghc-flag:`-Wpartial-fields` warns about record field that could + fail when it is used as a function. The function ``f`` below will fail when + applied to Bar, so the compiler will emit a warning about this when + :ghc-flag:`-Wpartial-fields` is enabled. + + The warning is suppressed if the field name begins with an underscore. :: + + data Foo = Foo { f :: Int } | Bar + If you're feeling really paranoid, the :ghc-flag:`-dcore-lint` option is a good choice. It turns on heavyweight intra-pass sanity-checking within GHC. (It checks GHC's sanity, not yours.) - diff --git a/testsuite/tests/typecheck/should_compile/T7169.hs b/testsuite/tests/typecheck/should_compile/T7169.hs new file mode 100644 index 0000000..ab1a7580 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T7169.hs @@ -0,0 +1,23 @@ +{-#OPTIONS_GHC -Wpartial-fields #-} +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE GADTs #-} + + +module T7196 where + +data T a = A + { m1 :: a + , m2 :: a + , _m3 :: a + } | B + { + m1 :: a + } + +pattern P{x} = x + +data family F a +data instance F a where + F1 :: { f1 :: Int } -> F Int + F2 :: { f2 :: Int } -> F Char diff --git a/testsuite/tests/typecheck/should_compile/T7169.stderr b/testsuite/tests/typecheck/should_compile/T7169.stderr new file mode 100644 index 0000000..0cc82e0 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T7169.stderr @@ -0,0 +1,2 @@ +T7169.hs:11:5: warning: [-Wpartial-fields] + Use of partial record field selector: ‘m2’ diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index a83e41a..e799a45 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -580,3 +580,4 @@ test('T13943', normal, compile, ['-fsolve-constant-dicts']) test('T14333', normal, compile, ['']) test('T14363', normal, compile, ['']) test('T14363a', normal, compile, ['']) +test('T7169', normal, compile, ['']) From git at git.haskell.org Wed Oct 25 20:44:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 20:44:47 +0000 (UTC) Subject: [commit: ghc] master: Fix a bug in 'alexInputPrevChar' (821adee) Message-ID: <20171025204447.C0A923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/821adee12e89dbd0a52fde872b633e4e2e9051dc/ghc >--------------------------------------------------------------- commit 821adee12e89dbd0a52fde872b633e4e2e9051dc Author: Alec Theriault Date: Wed Oct 25 15:52:38 2017 -0400 Fix a bug in 'alexInputPrevChar' The lexer hacks around unicode by squishing any character into a 'Word8' and then storing the actual character in its state. This happens at 'alexGetByte'. That is all and well, but we ought to be careful that the characters we retrieve via 'alexInputPrevChar' also fit this convention. In fact, #13986 exposes nicely what can go wrong: the regex in the left context of the type application rule uses the '$idchar' character set which relies on the unicode hack. However, a left context corresponds to a call to 'alexInputPrevChar', and we end up passing full blown unicode characters to '$idchar', despite it not being equipped to deal with these. Test Plan: Added a regression test case Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13986 Differential Revision: https://phabricator.haskell.org/D4105 >--------------------------------------------------------------- 821adee12e89dbd0a52fde872b633e4e2e9051dc compiler/parser/Lexer.x | 78 +++++++++++++++++-------- testsuite/tests/parser/should_compile/T13986.hs | 5 ++ testsuite/tests/parser/should_compile/all.T | 1 + 3 files changed, 59 insertions(+), 25 deletions(-) diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index 8c17315..3bf249b 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -129,38 +129,38 @@ import ApiAnnotation -- NB: The logic behind these definitions is also reflected in basicTypes/Lexeme.hs -- Any changes here should likely be reflected there. -$unispace = \x05 -- Trick Alex into handling Unicode. See alexGetByte. +$unispace = \x05 -- Trick Alex into handling Unicode. See [Unicode in Alex]. $nl = [\n\r\f] $whitechar = [$nl\v\ $unispace] $white_no_nl = $whitechar # \n -- TODO #8424 $tab = \t $ascdigit = 0-9 -$unidigit = \x03 -- Trick Alex into handling Unicode. See alexGetByte. +$unidigit = \x03 -- Trick Alex into handling Unicode. See [Unicode in Alex]. $decdigit = $ascdigit -- for now, should really be $digit (ToDo) $digit = [$ascdigit $unidigit] $special = [\(\)\,\;\[\]\`\{\}] $ascsymbol = [\!\#\$\%\&\*\+\.\/\<\=\>\?\@\\\^\|\-\~\:] -$unisymbol = \x04 -- Trick Alex into handling Unicode. See alexGetByte. +$unisymbol = \x04 -- Trick Alex into handling Unicode. See [Unicode in Alex]. $symbol = [$ascsymbol $unisymbol] # [$special \_\"\'] -$unilarge = \x01 -- Trick Alex into handling Unicode. See alexGetByte. +$unilarge = \x01 -- Trick Alex into handling Unicode. See [Unicode in Alex]. $asclarge = [A-Z] $large = [$asclarge $unilarge] -$unismall = \x02 -- Trick Alex into handling Unicode. See alexGetByte. +$unismall = \x02 -- Trick Alex into handling Unicode. See [Unicode in Alex]. $ascsmall = [a-z] $small = [$ascsmall $unismall \_] -$unigraphic = \x06 -- Trick Alex into handling Unicode. See alexGetByte. +$unigraphic = \x06 -- Trick Alex into handling Unicode. See [Unicode in Alex]. $graphic = [$small $large $symbol $digit $special $unigraphic \"\'] $binit = 0-1 $octit = 0-7 $hexit = [$decdigit A-F a-f] -$uniidchar = \x07 -- Trick Alex into handling Unicode. See alexGetByte. +$uniidchar = \x07 -- Trick Alex into handling Unicode. See [Unicode in Alex]. $idchar = [$small $large $digit $uniidchar \'] $pragmachar = [$small $large $digit] @@ -1968,27 +1968,29 @@ getLastTk = P $ \s@(PState { last_tk = last_tk }) -> POk s last_tk data AlexInput = AI RealSrcLoc StringBuffer -alexInputPrevChar :: AlexInput -> Char -alexInputPrevChar (AI _ buf) = prevChar buf '\n' +{- +Note [Unicode in Alex] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Although newer versions of Alex support unicode, this grammar is processed with +the old style '--latin1' behaviour. This means that when implementing the +functions --- backwards compatibility for Alex 2.x -alexGetChar :: AlexInput -> Maybe (Char,AlexInput) -alexGetChar inp = case alexGetByte inp of - Nothing -> Nothing - Just (b,i) -> c `seq` Just (c,i) - where c = chr $ fromIntegral b + alexGetByte :: AlexInput -> Maybe (Word8,AlexInput) + alexInputPrevChar :: AlexInput -> Char -alexGetByte :: AlexInput -> Maybe (Word8,AlexInput) -alexGetByte (AI loc s) - | atEnd s = Nothing - | otherwise = byte `seq` loc' `seq` s' `seq` - --trace (show (ord c)) $ - Just (byte, (AI loc' s')) - where (c,s') = nextChar s - loc' = advanceSrcLoc loc c - byte = fromIntegral $ ord adj_c +which Alex uses to to take apart our 'AlexInput', we must + + * return a latin1 character in the 'Word8' that 'alexGetByte' expects + * return a latin1 character in 'alexInputPrevChar'. + +We handle this in 'adjustChar' by squishing entire classes of unicode +characters into single bytes. +-} - non_graphic = '\x00' +{-# INLINE adjustChar #-} +adjustChar :: Char -> Word8 +adjustChar c = fromIntegral $ ord adj_c + where non_graphic = '\x00' upper = '\x01' lower = '\x02' digit = '\x03' @@ -2034,6 +2036,32 @@ alexGetByte (AI loc s) Space -> space _other -> non_graphic +-- Getting the previous 'Char' isn't enough here - we need to convert it into +-- the same format that 'alexGetByte' would have produced. +-- +-- See Note [Unicode in Alex] and #13986. +alexInputPrevChar :: AlexInput -> Char +alexInputPrevChar (AI _ buf) = chr (fromIntegral (adjustChar pc)) + where pc = prevChar buf '\n' + +-- backwards compatibility for Alex 2.x +alexGetChar :: AlexInput -> Maybe (Char,AlexInput) +alexGetChar inp = case alexGetByte inp of + Nothing -> Nothing + Just (b,i) -> c `seq` Just (c,i) + where c = chr $ fromIntegral b + +-- See Note [Unicode in Alex] +alexGetByte :: AlexInput -> Maybe (Word8,AlexInput) +alexGetByte (AI loc s) + | atEnd s = Nothing + | otherwise = byte `seq` loc' `seq` s' `seq` + --trace (show (ord c)) $ + Just (byte, (AI loc' s')) + where (c,s') = nextChar s + loc' = advanceSrcLoc loc c + byte = adjustChar c + -- This version does not squash unicode characters, it is used when -- lexing strings. alexGetChar' :: AlexInput -> Maybe (Char,AlexInput) diff --git a/testsuite/tests/parser/should_compile/T13986.hs b/testsuite/tests/parser/should_compile/T13986.hs new file mode 100644 index 0000000..b1b4882 --- /dev/null +++ b/testsuite/tests/parser/should_compile/T13986.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TypeApplications #-} + +module T13986 where + +foo x₁@True = 10 diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T index c008bd4..e2f68f6 100644 --- a/testsuite/tests/parser/should_compile/all.T +++ b/testsuite/tests/parser/should_compile/all.T @@ -109,3 +109,4 @@ test('DumpRenamedAst', normal, compile, ['-dsuppress-uniques -ddump-rn-ast'] test('DumpTypecheckedAst', normal, compile, ['-dsuppress-uniques -ddump-tc-ast']) test('T13747', normal, compile, ['']) test('T14189', normal, compile, ['-dsuppress-uniques -ddump-rn-ast']) +test('T13986', normal, compile, ['']) From git at git.haskell.org Wed Oct 25 20:44:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 20:44:50 +0000 (UTC) Subject: [commit: ghc] master: user-guide: Clarify default optimization flags (2c23fff) Message-ID: <20171025204450.9D8753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2c23fff2e03e77187dc4d01f325f5f43a0e7cad2/ghc >--------------------------------------------------------------- commit 2c23fff2e03e77187dc4d01f325f5f43a0e7cad2 Author: Ben Gamari Date: Wed Oct 25 15:53:40 2017 -0400 user-guide: Clarify default optimization flags Begins to fix #14214. [skip ci] Test Plan: Read it. Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #14214 Differential Revision: https://phabricator.haskell.org/D4098 >--------------------------------------------------------------- 2c23fff2e03e77187dc4d01f325f5f43a0e7cad2 docs/users_guide/using-optimisation.rst | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst index 763c778..ccf9ac5 100644 --- a/docs/users_guide/using-optimisation.rst +++ b/docs/users_guide/using-optimisation.rst @@ -52,7 +52,6 @@ So, for example, ``ghc -c Foo.hs`` .. ghc-flag:: -O0 :shortdesc: Disable optimisations (default) :type: dynamic - :reverse: -O :category: optimization-levels Means "turn off all optimisation", reverting to the same settings as @@ -584,7 +583,7 @@ by saying ``-fno-wombat``. :type: dynamic :category: - :default: off + :default: coercion optimisation enabled. Turn off the coercion optimiser. @@ -593,7 +592,7 @@ by saying ``-fno-wombat``. :type: dynamic :category: - :default: off + :default: pre-inlining enabled Turn off pre-inlining. @@ -604,7 +603,7 @@ by saying ``-fno-wombat``. :type: dynamic :category: - :default: off + :default: state hack is enabled Turn off the "state hack" whereby any lambda with a ``State#`` token as argument is considered to be single-entry, hence it is considered @@ -617,7 +616,7 @@ by saying ``-fno-wombat``. :reverse: -fno-omit-interface-pragmas :category: - :default: off + :default: Implied by :ghc-flag:`-O0`, otherwise off. Tells GHC to omit all inessential information from the interface file generated for the module being compiled (say M). This means @@ -634,7 +633,7 @@ by saying ``-fno-wombat``. :reverse: -fno-omit-yields :category: - :default: on + :default: yield points enabled Tells GHC to omit heap checks when no allocation is being performed. While this improves binary sizes by about 5%, it @@ -652,6 +651,8 @@ by saying ``-fno-wombat``. :reverse: -fno-pedantic-bottoms :category: + :default: off + Make GHC be more precise about its treatment of bottom (but see also :ghc-flag:`-fno-state-hack`). In particular, stop GHC eta-expanding through a case expression, which is good for performance, but bad if you are From git at git.haskell.org Wed Oct 25 22:04:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 22:04:18 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Try exitifcation after CSE (f68cec7) Message-ID: <20171025220418.05F5D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/f68cec77804d5c47f53a0be6dace5fd23d4a3331/ghc >--------------------------------------------------------------- commit f68cec77804d5c47f53a0be6dace5fd23d4a3331 Author: Joachim Breitner Date: Wed Oct 25 18:02:30 2017 -0400 Try exitifcation after CSE >--------------------------------------------------------------- f68cec77804d5c47f53a0be6dace5fd23d4a3331 compiler/simplCore/SimplCore.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 21a5c21..dc9a5bb 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -310,8 +310,6 @@ getCoreToDo dflags runWhen strictness demand_analyser, - runWhen exitification CoreDoExitify, - runWhen full_laziness $ CoreDoFloatOutwards FloatOutSwitches { floatOutLambdas = floatLamArgs dflags, @@ -330,6 +328,8 @@ getCoreToDo dflags -- succeed in commoning up things floated out by full laziness. -- CSE used to rely on the no-shadowing invariant, but it doesn't any more + runWhen exitification CoreDoExitify, + runWhen do_float_in CoreDoFloatInwards, maybe_rule_check (Phase 0), From git at git.haskell.org Wed Oct 25 22:04:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 22:04:20 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (ff41d0f) Message-ID: <20171025220420.D7F9D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/ff41d0faea2580d008ef6cdf53a7ef66fd25b340/ghc >--------------------------------------------------------------- commit ff41d0faea2580d008ef6cdf53a7ef66fd25b340 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration because the extra jump is a bit pointless there. It still increases the number of instructions of `compress2` by 3.82%, so that needs to be investiaged. >--------------------------------------------------------------- ff41d0faea2580d008ef6cdf53a7ef66fd25b340 compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 6 ++++++ compiler/simplCore/SimplCore.hs | 40 +++++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 41 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ff41d0faea2580d008ef6cdf53a7ef66fd25b340 From git at git.haskell.org Wed Oct 25 22:04:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Oct 2017 22:04:23 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Try exitification before the final simplifier run (12d403d) Message-ID: <20171025220423.8FE2C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/12d403d7594c74813703489b7034b00d979ac113/ghc >--------------------------------------------------------------- commit 12d403d7594c74813703489b7034b00d979ac113 Author: Joachim Breitner Date: Wed Oct 25 18:03:20 2017 -0400 Try exitification before the final simplifier run >--------------------------------------------------------------- 12d403d7594c74813703489b7034b00d979ac113 compiler/simplCore/SimplCore.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index dc9a5bb..a88ed63 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -328,8 +328,6 @@ getCoreToDo dflags -- succeed in commoning up things floated out by full laziness. -- CSE used to rely on the no-shadowing invariant, but it doesn't any more - runWhen exitification CoreDoExitify, - runWhen do_float_in CoreDoFloatInwards, maybe_rule_check (Phase 0), @@ -347,6 +345,8 @@ getCoreToDo dflags maybe_rule_check (Phase 0), + runWhen exitification CoreDoExitify, + -- Final clean-up simplification: simpl_phase 0 ["final"] max_iter, From git at git.haskell.org Thu Oct 26 00:03:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 00:03:11 +0000 (UTC) Subject: [commit: ghc] master: base: Enable listToMaybe to fuse via foldr/build (4c06ccb) Message-ID: <20171026000311.D22263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4c06ccb71737b77a8165e888ad75417a425549dd/ghc >--------------------------------------------------------------- commit 4c06ccb71737b77a8165e888ad75417a425549dd Author: Douglas Wilson Date: Wed Oct 25 19:05:30 2017 -0400 base: Enable listToMaybe to fuse via foldr/build Test Plan: Consider whether this is a good idea. Reviewers: austin, hvr, bgamari, nomeata Reviewed By: bgamari, nomeata Subscribers: nomeata, rwbarton, thomie GHC Trac Issues: #14387 Differential Revision: https://phabricator.haskell.org/D4126 >--------------------------------------------------------------- 4c06ccb71737b77a8165e888ad75417a425549dd libraries/base/Data/Maybe.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs index d8aad53..5f5d5ac 100644 --- a/libraries/base/Data/Maybe.hs +++ b/libraries/base/Data/Maybe.hs @@ -228,9 +228,12 @@ maybeToList (Just x) = [x] -- >>> maybeToList $ listToMaybe [1,2,3] -- [1] -- -listToMaybe :: [a] -> Maybe a -listToMaybe [] = Nothing -listToMaybe (a:_) = Just a +listToMaybe :: [a] -> Maybe a +listToMaybe = foldr (const . Just) Nothing +{-# INLINE listToMaybe #-} +-- We define listToMaybe using foldr so that it can fuse via the foldr/build +-- rule. See #14387 + -- | The 'catMaybes' function takes a list of 'Maybe's and returns -- a list of all the 'Just' values. From git at git.haskell.org Thu Oct 26 00:03:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 00:03:14 +0000 (UTC) Subject: [commit: ghc] master: Factor out readField (#14364) (dbd81f7) Message-ID: <20171026000314.9638B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dbd81f7e86514498218572b9d978373b1699cc5b/ghc >--------------------------------------------------------------- commit dbd81f7e86514498218572b9d978373b1699cc5b Author: Tobias Dammers Date: Wed Oct 25 19:09:03 2017 -0400 Factor out readField (#14364) Improves compiler performance of deriving Read instances, as suggested in the issue. Additionally, we introduce `readSymField`, a companion to `readField` that parses symbol-type fields (where the field name is a symbol, e.g. `(#)`, rather than an alphanumeric identifier. The decision between these two functions is made a compile time, because we already know which one we need based on the field name. Reviewers: austin, hvr, bgamari, RyanGlScott Reviewed By: bgamari Subscribers: RyanGlScott, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4108 >--------------------------------------------------------------- dbd81f7e86514498218572b9d978373b1699cc5b compiler/prelude/PrelNames.hs | 4 ++++ compiler/typecheck/TcGenDeriv.hs | 41 ++++++++++++++++++--------------- libraries/base/GHC/Read.hs | 46 +++++++++++++++++++++++++++++++++++++ testsuite/tests/perf/compiler/all.T | 3 ++- 4 files changed, 75 insertions(+), 19 deletions(-) diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index 760aea5..ae695d4 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -742,6 +742,10 @@ choose_RDR = varQual_RDR gHC_READ (fsLit "choose") lexP_RDR = varQual_RDR gHC_READ (fsLit "lexP") expectP_RDR = varQual_RDR gHC_READ (fsLit "expectP") +readField_RDR, readSymField_RDR :: RdrName +readField_RDR = varQual_RDR gHC_READ (fsLit "readField") +readSymField_RDR = varQual_RDR gHC_READ (fsLit "readSymField") + punc_RDR, ident_RDR, symbol_RDR :: RdrName punc_RDR = dataQual_RDR lEX (fsLit "Punc") ident_RDR = dataQual_RDR lEX (fsLit "Ident") diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index 9e27ad5..70ceb30 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -900,9 +900,7 @@ instance Read T where -- Record construction binds even more tightly than application do expectP (Ident "T1") expectP (Punc '{') - expectP (Ident "f1") - expectP (Punc '=') - x <- ReadP.reset Read.readPrec + x <- Read.readField "f1" (ReadP.reset readPrec) expectP (Punc '}') return (T1 { f1 = x })) +++ @@ -1068,21 +1066,28 @@ gen_Read_binds get_fixity loc tycon read_arg a ty = ASSERT( not (isUnliftedType ty) ) noLoc (mkBindStmt (nlVarPat a) (nlHsVarApps step_RDR [readPrec_RDR])) - read_field lbl a = read_lbl lbl ++ - [read_punc "=", - noLoc (mkBindStmt (nlVarPat a) (nlHsVarApps reset_RDR [readPrec_RDR]))] - - -- When reading field labels we might encounter - -- a = 3 - -- _a = 3 - -- or (#) = 4 - -- Note the parens! - read_lbl lbl | isSym lbl_str - = [read_punc "(", symbol_pat lbl_str, read_punc ")"] - | otherwise - = ident_h_pat lbl_str - where - lbl_str = unpackFS lbl + -- When reading field labels we might encounter + -- a = 3 + -- _a = 3 + -- or (#) = 4 + -- Note the parens! + read_field lbl a = + [noLoc + (mkBindStmt + (nlVarPat a) + (nlHsApps + read_field + [ nlHsLit (mkHsString lbl_str) + , nlHsVarApps reset_RDR [readPrec_RDR] + ] + ) + ) + ] + where + lbl_str = unpackFS lbl + read_field + | isSym lbl_str = readSymField_RDR + | otherwise = readField_RDR {- ************************************************************************ diff --git a/libraries/base/GHC/Read.hs b/libraries/base/GHC/Read.hs index ad29cc5..2d8ee3d 100644 --- a/libraries/base/GHC/Read.hs +++ b/libraries/base/GHC/Read.hs @@ -36,6 +36,8 @@ module GHC.Read , choose , readListDefault, readListPrecDefault , readNumber + , readField + , readSymField -- Temporary , readParen @@ -359,6 +361,50 @@ choose sps = foldr ((+++) . try_one) pfail sps L.Symbol s' | s==s' -> p _other -> pfail } +-- See Note [Why readField] + +-- | 'Read' parser for a record field, of the form @fieldName=value at . The +-- @fieldName@ must be an alphanumeric identifier; for symbols (operator-style) +-- field names, e.g. @(#)@, use 'readSymField'). The second argument is a +-- parser for the field value. +readField :: String -> ReadPrec a -> ReadPrec a +readField fieldName readVal = do + expectP (L.Ident fieldName) + expectP (L.Punc "=") + readVal +{-# NOINLINE readField #-} + +-- See Note [Why readField] + +-- | 'Read' parser for a symbol record field, of the form @(###)=value@ (where +-- @###@ is the field name). The field name must be a symbol (operator-style), +-- e.g. @(#)@. For regular (alphanumeric) field names, use 'readField'. The +-- second argument is a parser for the field value. +readSymField :: String -> ReadPrec a -> ReadPrec a +readSymField fieldName readVal = do + expectP (L.Punc "(") + expectP (L.Symbol fieldName) + expectP (L.Punc ")") + expectP (L.Punc "=") + readVal +{-# NOINLINE readSymField #-} + + +-- Note [Why readField] +-- +-- Previousy, the code for automatically deriving Read instance (in +-- typecheck/TcGenDeriv.hs) would generate inline code for parsing fields; +-- this, however, turned out to produce massive amounts of intermediate code, +-- and produced a considerable performance hit in the code generator. +-- Since Read instances are not generally supposed to be perfomance critical, +-- the readField and readSymField functions have been factored out, and the +-- code generator now just generates calls rather than manually inlining the +-- parsers. For large record types (e.g. 500 fields), this produces a +-- significant performance boost. +-- +-- See also Trac #14364. + + -------------------------------------------------------------- -- Simple instances of Read -------------------------------------------------------------- diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 41b2af8..aa53d98 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -197,7 +197,7 @@ test('T3294', # 2013-11-13: 1478325844 (x86/Windows, 64bit machine) # 2014-01-12: 1565185140 (x86/Linux) # 2013-04-04: 1377050640 (x86/Windows, 64bit machine) - (wordsize(64), 2253557280, 5)]), + (wordsize(64), 1858491504, 5)]), # old: 1357587088 (amd64/Linux) # 29/08/2012: 2961778696 (amd64/Linux) # (^ increase due to new codegen, see #7198) @@ -212,6 +212,7 @@ test('T3294', # 2016-07-11: 2739731144 (Windows) after fix for #12227 (ignoring) # 2017-02-17: 2758641264 (amd64/Linux) (Type indexed Typeable) # 2017-05-14: 2253557280 (amd64/Linux) Two-pass CmmLayoutStack + # 2017-10-24: 1858491504 (amd64/Linux) Improved linear regAlloc conf_3294, # Use `+RTS -G1` for more stable residency measurements. Note [residency]. From git at git.haskell.org Thu Oct 26 13:23:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 13:23:44 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (7970d58) Message-ID: <20171026132344.B50AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/7970d58d4a138bed21ce53a886a20f378e6e4284/ghc >--------------------------------------------------------------- commit 7970d58d4a138bed21ce53a886a20f378e6e4284 Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 The idea is described in #14152, and can be summarized: Float the exit path out of a joinrec, so that the simplifier can do more with it. See the test case for a nice example. The floating goes against what the simplifier usually does, hence we need to be careful not inline them back. The position of exitification in the pipeline was chosen after a small amount of experimentation, but may need to be improved. For example, exitification can allow rewrite rules to fire, but for that it would have to happen before the `simpl_phases`. Together with the next patch, perf.haskell.org reports these nice performance wins: Nofib allocations prev change gain fannkuch-redux 78446688 - 99.92% 64608 k-nucleotide 109466432 - 91.32% 9502064 simple 72424696 - 5.96% 68109560 Nofib instruction counts compress2 573354476 + 3.34% 592476104 k-nucleotide 2310080537 - 5.59% 2180917263 scs 1979135192 - 3.2% 1915880589 simple 670348375 - 4.9% 637507288 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- 7970d58d4a138bed21ce53a886a20f378e6e4284 compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 403 +++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 13 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + testsuite/tests/simplCore/should_compile/T14152.hs | 23 ++ .../tests/simplCore/should_compile/T14152.stderr | 129 +++++++ .../tests/simplCore/should_compile/T14152a.hs | 1 + .../tests/simplCore/should_compile/T14152a.stderr | 222 ++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 2 + 17 files changed, 831 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7970d58d4a138bed21ce53a886a20f378e6e4284 From git at git.haskell.org Thu Oct 26 13:23:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 13:23:50 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Run exitification before the main simplifier (33e13d3) Message-ID: <20171026132350.3F64D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/33e13d34a583715bae40e5216e5697989075d3e8/ghc >--------------------------------------------------------------- commit 33e13d34a583715bae40e5216e5697989075d3e8 Author: Joachim Breitner Date: Thu Oct 26 09:21:20 2017 -0400 Run exitification before the main simplifier (This is series of commit to measure and optimize placement.) >--------------------------------------------------------------- 33e13d34a583715bae40e5216e5697989075d3e8 compiler/simplCore/SimplCore.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 45823d4..10115c4 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -282,10 +282,10 @@ getCoreToDo dflags -- StaticPtrTable. static_ptrs_float_outwards, - runWhen exitification CoreDoExitify, - simpl_phases, + runWhen exitification CoreDoExitify, + -- Phase 0: allow all Ids to be inlined now -- This gets foldr inlined before strictness analysis From git at git.haskell.org Thu Oct 26 13:23:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 13:23:47 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Run exitification only early (e4a830c) Message-ID: <20171026132347.80BD93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/e4a830c43f1855cbbc638866ec2f02dd28e94716/ghc >--------------------------------------------------------------- commit e4a830c43f1855cbbc638866ec2f02dd28e94716 Author: Joachim Breitner Date: Wed Oct 25 10:12:40 2017 -0400 Run exitification only early (This is series of commit to measure and optimize placement.) >--------------------------------------------------------------- e4a830c43f1855cbbc638866ec2f02dd28e94716 compiler/simplCore/SimplCore.hs | 6 ------ 1 file changed, 6 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 5ed5cb0..45823d4 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -286,8 +286,6 @@ getCoreToDo dflags simpl_phases, - runWhen exitification CoreDoExitify, - -- Phase 0: allow all Ids to be inlined now -- This gets foldr inlined before strictness analysis @@ -314,8 +312,6 @@ getCoreToDo dflags runWhen strictness demand_analyser, - runWhen exitification CoreDoExitify, - runWhen full_laziness $ CoreDoFloatOutwards FloatOutSwitches { floatOutLambdas = floatLamArgs dflags, @@ -351,8 +347,6 @@ getCoreToDo dflags maybe_rule_check (Phase 0), - runWhen exitification CoreDoExitify, - -- Final clean-up simplification: simpl_phase 0 ["final"] max_iter, From git at git.haskell.org Thu Oct 26 13:23:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 13:23:58 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (bf671fc) Message-ID: <20171026132358.94FCE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/bf671fcb03d66ace8dd533aa16e230ee123f1610/ghc >--------------------------------------------------------------- commit bf671fcb03d66ace8dd533aa16e230ee123f1610 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration because the extra jump is a bit pointless there. It still increases the number of instructions of `compress2` by 3.82%, so that needs to be investiaged. >--------------------------------------------------------------- bf671fcb03d66ace8dd533aa16e230ee123f1610 compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 6 ++++++ compiler/simplCore/SimplCore.hs | 40 +++++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 41 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bf671fcb03d66ace8dd533aa16e230ee123f1610 From git at git.haskell.org Thu Oct 26 13:23:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 13:23:52 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Run exitification after demand analysis (05d3ddc) Message-ID: <20171026132352.F32B43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/05d3ddcd545d1b36cbf4a9f2781b77a34797059a/ghc >--------------------------------------------------------------- commit 05d3ddcd545d1b36cbf4a9f2781b77a34797059a Author: Joachim Breitner Date: Thu Oct 26 09:21:38 2017 -0400 Run exitification after demand analysis >--------------------------------------------------------------- 05d3ddcd545d1b36cbf4a9f2781b77a34797059a compiler/simplCore/SimplCore.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 10115c4..21a5c21 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -284,8 +284,6 @@ getCoreToDo dflags simpl_phases, - runWhen exitification CoreDoExitify, - -- Phase 0: allow all Ids to be inlined now -- This gets foldr inlined before strictness analysis @@ -312,6 +310,8 @@ getCoreToDo dflags runWhen strictness demand_analyser, + runWhen exitification CoreDoExitify, + runWhen full_laziness $ CoreDoFloatOutwards FloatOutSwitches { floatOutLambdas = floatLamArgs dflags, From git at git.haskell.org Thu Oct 26 13:23:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 13:23:55 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Run exitification before the final simplifier run (e6d5e13) Message-ID: <20171026132355.BC95D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/e6d5e13a1758221628df2daae58f2dcde0c4c3f8/ghc >--------------------------------------------------------------- commit e6d5e13a1758221628df2daae58f2dcde0c4c3f8 Author: Joachim Breitner Date: Thu Oct 26 09:22:06 2017 -0400 Run exitification before the final simplifier run >--------------------------------------------------------------- e6d5e13a1758221628df2daae58f2dcde0c4c3f8 compiler/simplCore/SimplCore.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 21a5c21..a88ed63 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -310,8 +310,6 @@ getCoreToDo dflags runWhen strictness demand_analyser, - runWhen exitification CoreDoExitify, - runWhen full_laziness $ CoreDoFloatOutwards FloatOutSwitches { floatOutLambdas = floatLamArgs dflags, @@ -347,6 +345,8 @@ getCoreToDo dflags maybe_rule_check (Phase 0), + runWhen exitification CoreDoExitify, + -- Final clean-up simplification: simpl_phase 0 ["final"] max_iter, From git at git.haskell.org Thu Oct 26 13:24:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 13:24:00 +0000 (UTC) Subject: [commit: ghc] wip/T14152's head updated: Inline exit join points in the "final" simplifier iteration (bf671fc) Message-ID: <20171026132400.EA2BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14152' now includes: 671b1ed User’s guide: Properly link to RTS flag -V 8843a39 Include usg_file_hash in ghc --show-iface output 3825b7e Remove the 'legroom' part of the timeout-accurate-pure test. b62097d Windows: Bump to GCC 7.2 for GHC 8.4 e888a1f Revert "Windows: Bump to GCC 7.2 for GHC 8.4" 561bdca Update Win32 version for GHC 8.4. f744261 ghc-cabal: Inline removed function from Cabal. 2e16a57 Revert "ghc-cabal: Inline removed function ..." b1ad0bb Revert "Update Win32 version for GHC 8.4." 61f1b46 Make language extensions their own category in the documentation bf83435 typecheck: Clarify errors mentioned in #14385 bd53b48 Add info about Github pull requests. 2a4c24e Make layLeft and reduceDoc stricter (#7258) 980e127 Windows: Update the mirror script to generate hashes and use mirror fallback 1c15d8e Fix space leak in BinIface.getSymbolTable df63668 Performance improvements linear regAlloc (#7258) f7f270e Implement `-Wpartial-fields` warning (#7169) 821adee Fix a bug in 'alexInputPrevChar' 2c23fff user-guide: Clarify default optimization flags 4c06ccb base: Enable listToMaybe to fuse via foldr/build dbd81f7 Factor out readField (#14364) 7970d58 Implement a dedicated exitfication pass #14152 e4a830c Run exitification only early 33e13d3 Run exitification before the main simplifier 05d3ddc Run exitification after demand analysis e6d5e13 Run exitification before the final simplifier run bf671fc Inline exit join points in the "final" simplifier iteration From git at git.haskell.org Thu Oct 26 13:49:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 13:49:00 +0000 (UTC) Subject: [commit: ghc] master: Declare upstram repo location for hsc2hs (d91a6b6) Message-ID: <20171026134900.242573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d91a6b6c1d7699b6e9ace1988974d4453a20dab6/ghc >--------------------------------------------------------------- commit d91a6b6c1d7699b6e9ace1988974d4453a20dab6 Author: Herbert Valerio Riedel Date: Thu Oct 26 15:47:45 2017 +0200 Declare upstram repo location for hsc2hs [skip ci] >--------------------------------------------------------------- d91a6b6c1d7699b6e9ace1988974d4453a20dab6 packages | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/packages b/packages index c72f6f4..69aed70 100644 --- a/packages +++ b/packages @@ -39,7 +39,7 @@ # ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ghc-tarballs windows ghc-tarballs.git - libffi-tarballs - - - -utils/hsc2hs - - - +utils/hsc2hs - - ssh://git at github.com/haskell/hsc2hs.git utils/haddock - - ssh://git at github.com/haskell/haddock.git libraries/array - - - libraries/binary - - https://github.com/kolmodin/binary.git From git at git.haskell.org Thu Oct 26 22:57:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:57:58 +0000 (UTC) Subject: [commit: ghc] branch 'wip/nfs-locking' created Message-ID: <20171026225758.5C8333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/nfs-locking Referencing: 1cd7473f8e800a99e95180579480a0e62e98040b From git at git.haskell.org Thu Oct 26 22:58:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initial commit (013cf0c) Message-ID: <20171026225802.04FBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/013cf0c23c4926b09d6a10c13170d344ed802a01/ghc >--------------------------------------------------------------- commit 013cf0c23c4926b09d6a10c13170d344ed802a01 Author: Andrey Mokhov Date: Tue Dec 23 17:01:44 2014 +0000 Initial commit >--------------------------------------------------------------- 013cf0c23c4926b09d6a10c13170d344ed802a01 README.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README.md b/README.md new file mode 100644 index 0000000..c7c12b3 --- /dev/null +++ b/README.md @@ -0,0 +1,4 @@ +shaking-up-ghc +============== + +Shaking up GHC From git at git.haskell.org Thu Oct 26 22:58:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a brief intro to the project. (bd90cd8) Message-ID: <20171026225805.725773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd90cd8e6436d20d933c9b27142cc83defcbe267/ghc >--------------------------------------------------------------- commit bd90cd8e6436d20d933c9b27142cc83defcbe267 Author: Andrey Mokhov Date: Tue Dec 23 17:06:08 2014 +0000 Add a brief intro to the project. >--------------------------------------------------------------- bd90cd8e6436d20d933c9b27142cc83defcbe267 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index c7c12b3..7167e9a 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -shaking-up-ghc +Shaking up GHC ============== -Shaking up GHC +As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). From git at git.haskell.org Thu Oct 26 22:58:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add .gitignore. (c5c557a) Message-ID: <20171026225808.E36273A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5c557a4fab012d28c8fb5f2b2aacb9f835ef722/ghc >--------------------------------------------------------------- commit c5c557a4fab012d28c8fb5f2b2aacb9f835ef722 Author: Andrey Mokhov Date: Tue Dec 23 17:12:02 2014 +0000 Add .gitignore. >--------------------------------------------------------------- c5c557a4fab012d28c8fb5f2b2aacb9f835ef722 .gitignore | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.gitignore b/.gitignore new file mode 100644 index 0000000..181ccc0 --- /dev/null +++ b/.gitignore @@ -0,0 +1,4 @@ +*.o +*.hi +_shake/ +_build/ From git at git.haskell.org Thu Oct 26 22:58:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Base.hs (basic datatypes and imports for the build system). (4e03b1c) Message-ID: <20171026225819.412753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9/ghc >--------------------------------------------------------------- commit 4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9 Author: Andrey Mokhov Date: Tue Dec 23 17:44:51 2014 +0000 Add Base.hs (basic datatypes and imports for the build system). >--------------------------------------------------------------- 4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9 Base.hs | 45 +++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 45 insertions(+) diff --git a/Base.hs b/Base.hs new file mode 100644 index 0000000..7e130c2 --- /dev/null +++ b/Base.hs @@ -0,0 +1,45 @@ +{-# LANGUAGE FlexibleInstances #-} + +module Base ( + module Development.Shake, + module Development.Shake.FilePath, + module Control.Applicative, + module Data.Monoid, + Stage (..), + Args, arg, Condition, + joinArgs, joinArgsWithSpaces, + filterOut, + ) where + +import Development.Shake hiding ((*>)) +import Development.Shake.FilePath +import Control.Applicative +import Data.Monoid +import Data.List + +data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) + +type Args = Action [String] + +type Condition = Action Bool + +instance Monoid a => Monoid (Action a) where + mempty = return mempty + mappend p q = mappend <$> p <*> q + +arg :: [String] -> Args +arg = return + +intercalateArgs :: String -> Args -> Args +intercalateArgs s args = do + as <- args + return [intercalate s as] + +joinArgsWithSpaces :: Args -> Args +joinArgsWithSpaces = intercalateArgs " " + +joinArgs :: Args -> Args +joinArgs = intercalateArgs "" + +filterOut :: Args -> [String] -> Args +filterOut args list = filter (`notElem` list) <$> args From git at git.haskell.org Thu Oct 26 22:58:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Oracles.hs (configuration infrastructure). (cb701bb) Message-ID: <20171026225826.3F60F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb701bb1c14ea9db25b433778c6a6a05d506dc2f/ghc >--------------------------------------------------------------- commit cb701bb1c14ea9db25b433778c6a6a05d506dc2f Author: Andrey Mokhov Date: Tue Dec 23 17:46:41 2014 +0000 Add Oracles.hs (configuration infrastructure). >--------------------------------------------------------------- cb701bb1c14ea9db25b433778c6a6a05d506dc2f Oracles.hs | 250 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 250 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 cb701bb1c14ea9db25b433778c6a6a05d506dc2f From git at git.haskell.org Thu Oct 26 22:58:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add shake launcher. (cf7b65b) Message-ID: <20171026225812.4EB8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf7b65b5b200048fd0597ee606ccd876848a3b05/ghc >--------------------------------------------------------------- commit cf7b65b5b200048fd0597ee606ccd876848a3b05 Author: Andrey Mokhov Date: Tue Dec 23 17:28:03 2014 +0000 Add shake launcher. >--------------------------------------------------------------- cf7b65b5b200048fd0597ee606ccd876848a3b05 build.bat | 2 ++ 1 file changed, 2 insertions(+) diff --git a/build.bat b/build.bat new file mode 100644 index 0000000..5400131 --- /dev/null +++ b/build.bat @@ -0,0 +1,2 @@ + at mkdir _shake 2> nul + at ghc --make Main.hs -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 22:58:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add top-level build script. (4139a9c) Message-ID: <20171026225815.C40813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4139a9c49da73acb26756a6be7bf564286a32cf1/ghc >--------------------------------------------------------------- commit 4139a9c49da73acb26756a6be7bf564286a32cf1 Author: Andrey Mokhov Date: Tue Dec 23 17:42:13 2014 +0000 Add top-level build script. >--------------------------------------------------------------- 4139a9c49da73acb26756a6be7bf564286a32cf1 Main.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/Main.hs b/Main.hs new file mode 100644 index 0000000..abfd3ab --- /dev/null +++ b/Main.hs @@ -0,0 +1,10 @@ +import Base +import Config +import Oracles +import Package + +main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do + oracleRules + autoconfRules + configureRules + packageRules From git at git.haskell.org Thu Oct 26 22:58:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Config.hs (autoconf and configure rules). (9566d56) Message-ID: <20171026225822.C02E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9566d564272d1762d8f0eca492b17673ca0af55c/ghc >--------------------------------------------------------------- commit 9566d564272d1762d8f0eca492b17673ca0af55c Author: Andrey Mokhov Date: Tue Dec 23 17:45:51 2014 +0000 Add Config.hs (autoconf and configure rules). >--------------------------------------------------------------- 9566d564272d1762d8f0eca492b17673ca0af55c Config.hs | 24 ++++++++++++++++++++++++ 1 file changed, 24 insertions(+) diff --git a/Config.hs b/Config.hs new file mode 100644 index 0000000..a370f38 --- /dev/null +++ b/Config.hs @@ -0,0 +1,24 @@ +module Config ( + autoconfRules, configureRules + ) where + +import Development.Shake +import Development.Shake.Command +import Development.Shake.FilePath +import Development.Shake.Rule +import Control.Applicative +import Control.Monad +import Base +import Oracles + +autoconfRules :: Rules () +autoconfRules = do + "shake/configure" %> \out -> do + need ["shake/configure.ac"] + cmd $ "bash shake/autoconf" + +configureRules :: Rules () +configureRules = do + "shake/default.config" %> \out -> do + need ["shake/default.config.in", "shake/configure"] + cmd $ "bash shake/configure" From git at git.haskell.org Thu Oct 26 22:58:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Packages.hs (package build rules). (c8212ad) Message-ID: <20171026225829.9E8503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8212add0d0e343652406f994b6c2c5ff36a5a37/ghc >--------------------------------------------------------------- commit c8212add0d0e343652406f994b6c2c5ff36a5a37 Author: Andrey Mokhov Date: Tue Dec 23 17:47:37 2014 +0000 Add Packages.hs (package build rules). >--------------------------------------------------------------- c8212add0d0e343652406f994b6c2c5ff36a5a37 Package.hs | 196 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 196 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 c8212add0d0e343652406f994b6c2c5ff36a5a37 From git at git.haskell.org Thu Oct 26 22:58:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Ways.hs (build ways and helper functions). (9a33083) Message-ID: <20171026225833.0D2003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a33083158e13abb252f3787059e8e2cb5da9215/ghc >--------------------------------------------------------------- commit 9a33083158e13abb252f3787059e8e2cb5da9215 Author: Andrey Mokhov Date: Tue Dec 23 17:53:17 2014 +0000 Add Ways.hs (build ways and helper functions). >--------------------------------------------------------------- 9a33083158e13abb252f3787059e8e2cb5da9215 Ways.hs | 96 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 96 insertions(+) diff --git a/Ways.hs b/Ways.hs new file mode 100644 index 0000000..6e186ab --- /dev/null +++ b/Ways.hs @@ -0,0 +1,96 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module Ways ( + WayUnit (..), + Way, tag, + + allWays, defaultWays, + + vanilla, profiling, logging, parallel, granSim, + threaded, threadedProfiling, threadedLogging, + debug, debugProfiling, threadedDebug, threadedDebugProfiling, + dynamic, profilingDynamic, threadedProfilingDynamic, + threadedDynamic, threadedDebugDynamic, debugDynamic, + loggingDynamic, threadedLoggingDynamic, + + hisuf, osuf, hcsuf + ) where + +import Base +import Oracles + +data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dynamic deriving Eq + +data Way = Way + { + tag :: String, -- e.g., "thr_p" + description :: String, -- e.g., "threaded profiled" + units :: [WayUnit] -- e.g., [Threaded, Profiling] + } + deriving Eq + +vanilla = Way "v" "vanilla" [] +profiling = Way "p" "profiling" [Profiling] +logging = Way "l" "event logging" [Logging] +parallel = Way "mp" "parallel" [Parallel] +granSim = Way "gm" "GranSim" [GranSim] + +-- RTS only ways + +threaded = Way "thr" "threaded" [Threaded] +threadedProfiling = Way "thr_p" "threaded profiling" [Threaded, Profiling] +threadedLogging = Way "thr_l" "threaded event logging" [Threaded, Logging] +debug = Way "debug" "debug" [Debug] +debugProfiling = Way "debug_p" "debug profiling" [Debug, Profiling] +threadedDebug = Way "thr_debug" "threaded debug" [Threaded, Debug] +threadedDebugProfiling = Way "thr_debug_p" "threaded debug profiling" [Threaded, Debug, Profiling] +dynamic = Way "dyn" "dyn" [Dynamic] +profilingDynamic = Way "p_dyn" "p_dyn" [Profiling, Dynamic] +threadedProfilingDynamic = Way "thr_p_dyn" "thr_p_dyn" [Threaded, Profiling, Dynamic] +threadedDynamic = Way "thr_dyn" "thr_dyn" [Threaded, Dynamic] +threadedDebugDynamic = Way "thr_debug_dyn" "thr_debug_dyn" [Threaded, Debug, Dynamic] +debugDynamic = Way "debug_dyn" "debug_dyn" [Debug, Dynamic] +loggingDynamic = Way "l_dyn" "event logging dynamic" [Logging, Dynamic] +threadedLoggingDynamic = Way "thr_l_dyn" "threaded event logging dynamic" [Threaded, Logging, Dynamic] + +allWays = [vanilla, profiling, logging, parallel, granSim, + threaded, threadedProfiling, threadedLogging, + debug, debugProfiling, threadedDebug, threadedDebugProfiling, + dynamic, profilingDynamic, threadedProfilingDynamic, + threadedDynamic, threadedDebugDynamic, debugDynamic, + loggingDynamic, threadedLoggingDynamic] + +-- TODO: what are ways 't' and 's'? +-- ALL_WAYS=v p t l s mp mg debug dyn thr thr_l p_dyn debug_dyn thr_dyn thr_p_dyn thr_debug_dyn thr_p thr_debug debug_p thr_debug_p l_dyn thr_l_dyn + +defaultWays :: Stage -> Action [Way] +defaultWays stage = do + sharedLibs <- test PlatformSupportsSharedLibs + return $ [vanilla] + ++ [profiling | stage /= Stage0] + ++ [dynamic | sharedLibs ] + +wayHcOpts :: Way -> Args +wayHcOpts (Way _ _ units) = + mconcat + [ when (Dynamic `notElem` units) $ arg [ "-static" ] + , when (Dynamic `elem` units) $ arg [ "-fPIC", "-dynamic" ] + , when (Threaded `elem` units) $ arg [ "-optc-DTHREADED_RTS" ] + , when (Debug `elem` units) $ arg [ "-optc-DDEBUG" ] + , when (Profiling `elem` units) $ arg [ "-prof" ] + , when (Logging `elem` units) $ arg [ "-eventlog" ] + , when (Parallel `elem` units) $ arg [ "-parallel" ] + , when (GranSim `elem` units) $ arg [ "-gransim" ] + , when (units == [Debug] || units == [Debug, Dynamic]) $ arg [ "-ticky", "-DTICKY_TICKY" ] + ] + +suffix :: FilePath -> Way -> FilePath +suffix base (Way _ _ units) = + concat $ + ["p_" | Profiling `elem` units] ++ + ["dyn_" | Dynamic `elem` units] ++ + [base ] + +hisuf, osuf, hcsuf :: Way -> FilePath +hisuf = suffix "hi" +osuf = suffix "o" +hcsuf = suffix "hc" From git at git.haskell.org Thu Oct 26 22:58:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add docs (mostly progress comments so far). (c816893) Message-ID: <20171026225836.89C8C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8168933901fda238b9cd2cf30eb5414194816a3/ghc >--------------------------------------------------------------- commit c8168933901fda238b9cd2cf30eb5414194816a3 Author: Andrey Mokhov Date: Tue Dec 23 17:54:46 2014 +0000 Add docs (mostly progress comments so far). >--------------------------------------------------------------- c8168933901fda238b9cd2cf30eb5414194816a3 doc/build-package-data.docx | Bin 0 -> 15964 bytes doc/comment-hi-rule.txt | 39 ++++++ doc/deepseq-build-progress.txt | 300 +++++++++++++++++++++++++++++++++++++++++ 3 files changed, 339 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 c8168933901fda238b9cd2cf30eb5414194816a3 From git at git.haskell.org Thu Oct 26 22:58:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comment on where this goes in the GHC source tree. (3c08e17) Message-ID: <20171026225840.0766C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c08e170bf0dfdf23ed34cfbc21a2b0286f0e23d/ghc >--------------------------------------------------------------- commit 3c08e170bf0dfdf23ed34cfbc21a2b0286f0e23d Author: Andrey Mokhov Date: Tue Dec 23 17:58:29 2014 +0000 Comment on where this goes in the GHC source tree. >--------------------------------------------------------------- 3c08e170bf0dfdf23ed34cfbc21a2b0286f0e23d README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 7167e9a..54742ee 100644 --- a/README.md +++ b/README.md @@ -2,3 +2,5 @@ Shaking up GHC ============== As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). + +This is supposed to go into the `shake` directory of the GHC source tree (as a submodule). From git at git.haskell.org Thu Oct 26 22:58:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add configuration files and dummy builders (autoconf, configure) for debugging. (9089a36) Message-ID: <20171026225843.829923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9089a366948907d730e9cc550f209357214be039/ghc >--------------------------------------------------------------- commit 9089a366948907d730e9cc550f209357214be039 Author: Andrey Mokhov Date: Tue Dec 23 18:01:01 2014 +0000 Add configuration files and dummy builders (autoconf, configure) for debugging. >--------------------------------------------------------------- 9089a366948907d730e9cc550f209357214be039 autoconf | 2 ++ configure | 1 + configure.ac | 1 + default.config | 52 ++++++++++++++++++++++++++++++++++++++++++++++++++++ default.config.in | 45 +++++++++++++++++++++++++++++++++++++++++++++ user.config | 1 + 6 files changed, 102 insertions(+) diff --git a/autoconf b/autoconf new file mode 100644 index 0000000..99e5cb3 --- /dev/null +++ b/autoconf @@ -0,0 +1,2 @@ +echo "Running autoconf... (not really)" +echo "$(cat $(dirname $0)/configure.ac) $(date)...\"" > $(dirname $0)/configure diff --git a/configure b/configure new file mode 100644 index 0000000..f51695b --- /dev/null +++ b/configure @@ -0,0 +1 @@ +echo "Running fake configure generated at: Mon, Dec 22, 2014 2:15:52 PM..." diff --git a/configure.ac b/configure.ac new file mode 100644 index 0000000..03184ad --- /dev/null +++ b/configure.ac @@ -0,0 +1 @@ +echo "Running fake configure generated at: diff --git a/default.config b/default.config new file mode 100644 index 0000000..f821e7a --- /dev/null +++ b/default.config @@ -0,0 +1,52 @@ +system-ghc = C:/msys64/usr/local/bin/ghc.exe +system-ghc-pkg = C:/msys64/usr/local/bin/ghc-pkg.exe + +ghc-cabal = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-cabal.exe +ghc-stage1 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage1.exe +ghc-stage2 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage2.exe +ghc-stage3 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage3.exe + +ghc-pkg = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-pkg.exe + +gcc = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/gcc.exe +ld = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ld.exe +ar = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ar.exe +alex = C:/msys64/usr/local/bin/alex.exe +happy = C:/msys64/usr/local/bin/happy.exe +hscolour = + +target-os = mingw32 +target-arch = x86_64 +target-platform-full = x86_64-unknown-mingw32 + +cross-compiling = NO + +conf-cc-args-stage-0 = -fno-stack-protector +conf-cc-args-stage-1 = -fno-stack-protector +conf-cc-args-stage-2 = -fno-stack-protector + +conf-cpp-args-stage-0 = +conf-cpp-args-stage-1 = +conf-cpp-args-stage-2 = + +conf-gcc-linker-args-stage-0 = +conf-gcc-linker-args-stage-1 = +conf-gcc-linker-args-stage-2 = + +conf-ld-linker-args-stage-0 = +conf-ld-linker-args-stage-1 = +conf-ld-linker-args-stage-2 = + +iconv-include-dirs = +iconv-lib-dirs = +gmp-include-dirs = +gmp-lib-dirs = + +lax-dependencies = NO +dynamic-ghc-programs = NO +gcc-is-clang = NO +gcc-lt-46 = NO + + + +host-os-cpp = mingw32 diff --git a/default.config.in b/default.config.in new file mode 100644 index 0000000..4ab5e21 --- /dev/null +++ b/default.config.in @@ -0,0 +1,45 @@ +ghc-cabal = inplace/bin/ghc-cabal at exeext_host@ +ghc = @WithGhc@ +ghc-pkg = @GhcPkgCmd@ +gcc = @WhatGccIsCalled@ +ld = @LdCmd@ +ar = @ArCmd@ +alex = @AlexCmd@ +happy = @HappyCmd@ +hscolour = @HSCOLOUR@ +target-os = @TargetOS_CPP@ +target-arch = @TargetArch_CPP@ +target-platform-full = @TargetPlatformFull@ + +cross-compiling = @CrossCompiling@ + +conf-cc-args-stage-0 = @CONF_CC_OPTS_STAGE0@ +conf-cc-args-stage-1 = @CONF_CC_OPTS_STAGE1@ +conf-cc-args-stage-2 = @CONF_CC_OPTS_STAGE2@ + +conf-cpp-args-stage-0 = @CONF_CPP_OPTS_STAGE0@ +conf-cpp-args-stage-1 = @CONF_CPP_OPTS_STAGE1@ +conf-cpp-args-stage-2 = @CONF_CPP_OPTS_STAGE2@ + +conf-gcc-linker-args-stage-0 = @CONF_GCC_LINKER_OPTS_STAGE0@ +conf-gcc-linker-args-stage-1 = @CONF_GCC_LINKER_OPTS_STAGE1@ +conf-gcc-linker-args-stage-2 = @CONF_GCC_LINKER_OPTS_STAGE2@ + +conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ +conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ +conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ + +iconv-include-dirs = @ICONV_INCLUDE_DIRS@ +iconv-lib-dirs = @ICONV_LIB_DIRS@ + +gmp-include-dirs = @GMP_INCLUDE_DIRS@ +gmp-lib-dirs = @GMP_LIB_DIRS@ + +lax-dependencies = NO +dynamic-ghc-programs = NO +gcc-is-clang = @GccIsClang@ +gcc-lt-46 = @GccLT46@ + + + +host-os-cpp = @HostOS_CPP@ \ No newline at end of file diff --git a/user.config b/user.config new file mode 100644 index 0000000..313d39a --- /dev/null +++ b/user.config @@ -0,0 +1 @@ +lax-dependencies = YES From git at git.haskell.org Thu Oct 26 22:58:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add mk-miner submodule. (8433156) Message-ID: <20171026225846.EB7243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84331560b9ae783af8ce83598b6e4c6ab92d4b8a/ghc >--------------------------------------------------------------- commit 84331560b9ae783af8ce83598b6e4c6ab92d4b8a Author: Andrey Mokhov Date: Wed Dec 24 02:06:09 2014 +0000 Add mk-miner submodule. >--------------------------------------------------------------- 84331560b9ae783af8ce83598b6e4c6ab92d4b8a .gitmodules | 3 +++ mk-miner | 1 + 2 files changed, 4 insertions(+) diff --git a/.gitmodules b/.gitmodules new file mode 100644 index 0000000..8f798aa --- /dev/null +++ b/.gitmodules @@ -0,0 +1,3 @@ +[submodule "mk-miner"] + path = mk-miner + url = https://github.com/snowleopard/mk-miner.git diff --git a/mk-miner b/mk-miner new file mode 160000 index 0000000..566cbc0 --- /dev/null +++ b/mk-miner @@ -0,0 +1 @@ +Subproject commit 566cbc0996a56cdc9297082aca13eb2fd3f64029 From git at git.haskell.org Thu Oct 26 22:58:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve mk-miner submodule. (2a82120) Message-ID: <20171026225850.5A4C03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2a82120c2ec83683eaa273f87d1d2402606dea69/ghc >--------------------------------------------------------------- commit 2a82120c2ec83683eaa273f87d1d2402606dea69 Author: Andrey Mokhov Date: Thu Dec 25 14:41:26 2014 +0000 Improve mk-miner submodule. >--------------------------------------------------------------- 2a82120c2ec83683eaa273f87d1d2402606dea69 mk-miner | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk-miner b/mk-miner index 566cbc0..276425e 160000 --- a/mk-miner +++ b/mk-miner @@ -1 +1 @@ -Subproject commit 566cbc0996a56cdc9297082aca13eb2fd3f64029 +Subproject commit 276425ea44420f49ac34fd942c0dad84b0c0d332 From git at git.haskell.org Thu Oct 26 22:58:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Moved source files to src subdirectory. (6a7c214) Message-ID: <20171026225853.B6A313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a7c2146795131a667ce19c1926fbc0fbbd98ed5/ghc >--------------------------------------------------------------- commit 6a7c2146795131a667ce19c1926fbc0fbbd98ed5 Author: Andrey Mokhov Date: Thu Dec 25 17:51:49 2014 +0000 Moved source files to src subdirectory. >--------------------------------------------------------------- 6a7c2146795131a667ce19c1926fbc0fbbd98ed5 Base.hs => src/Base.hs | 0 Config.hs => src/Config.hs | 0 Main.hs => src/Main.hs | 0 Oracles.hs => src/Oracles.hs | 0 Package.hs => src/Package.hs | 0 Ways.hs => src/Ways.hs | 0 6 files changed, 0 insertions(+), 0 deletions(-) diff --git a/Base.hs b/src/Base.hs similarity index 100% rename from Base.hs rename to src/Base.hs diff --git a/Config.hs b/src/Config.hs similarity index 100% rename from Config.hs rename to src/Config.hs diff --git a/Main.hs b/src/Main.hs similarity index 100% rename from Main.hs rename to src/Main.hs diff --git a/Oracles.hs b/src/Oracles.hs similarity index 100% rename from Oracles.hs rename to src/Oracles.hs diff --git a/Package.hs b/src/Package.hs similarity index 100% rename from Package.hs rename to src/Package.hs diff --git a/Ways.hs b/src/Ways.hs similarity index 100% rename from Ways.hs rename to src/Ways.hs From git at git.haskell.org Thu Oct 26 22:58:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:58:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to source files. (23c7701) Message-ID: <20171026225857.34A563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23c7701c1fab401a45f707c9abac101c6be9ce56/ghc >--------------------------------------------------------------- commit 23c7701c1fab401a45f707c9abac101c6be9ce56 Author: Andrey Mokhov Date: Thu Dec 25 18:13:12 2014 +0000 Fix paths to source files. >--------------------------------------------------------------- 23c7701c1fab401a45f707c9abac101c6be9ce56 build.bat | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 5400131..8e3dba2 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,2 @@ @mkdir _shake 2> nul - at ghc --make Main.hs -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at ghc --make src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 22:59:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove the generated 'configure' script from the repository. (8b10b13) Message-ID: <20171026225900.9595E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8b10b133351866f8fabd033d402c32613209f63f/ghc >--------------------------------------------------------------- commit 8b10b133351866f8fabd033d402c32613209f63f Author: Andrey Mokhov Date: Thu Dec 25 18:18:01 2014 +0000 Remove the generated 'configure' script from the repository. >--------------------------------------------------------------- 8b10b133351866f8fabd033d402c32613209f63f configure | 1 - 1 file changed, 1 deletion(-) diff --git a/configure b/configure deleted file mode 100644 index f51695b..0000000 --- a/configure +++ /dev/null @@ -1 +0,0 @@ -echo "Running fake configure generated at: Mon, Dec 22, 2014 2:15:52 PM..." From git at git.haskell.org Thu Oct 26 22:59:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Stop tracking the generated 'configure' script. (dfd6b21) Message-ID: <20171026225904.0C7E63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfd6b21aefaffea5f1e9f263dd4b115f2ff73094/ghc >--------------------------------------------------------------- commit dfd6b21aefaffea5f1e9f263dd4b115f2ff73094 Author: Andrey Mokhov Date: Thu Dec 25 18:19:49 2014 +0000 Stop tracking the generated 'configure' script. >--------------------------------------------------------------- dfd6b21aefaffea5f1e9f263dd4b115f2ff73094 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 181ccc0..30e2546 100644 --- a/.gitignore +++ b/.gitignore @@ -2,3 +2,4 @@ *.hi _shake/ _build/ +configure From git at git.haskell.org Thu Oct 26 22:59:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove fake autoconf. (232891d) Message-ID: <20171026225907.751F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/232891d32c497c3901495e3a53745dd68c859d38/ghc >--------------------------------------------------------------- commit 232891d32c497c3901495e3a53745dd68c859d38 Author: Andrey Mokhov Date: Fri Dec 26 22:12:42 2014 +0000 Remove fake autoconf. >--------------------------------------------------------------- 232891d32c497c3901495e3a53745dd68c859d38 autoconf | 2 -- 1 file changed, 2 deletions(-) diff --git a/autoconf b/autoconf deleted file mode 100644 index 99e5cb3..0000000 --- a/autoconf +++ /dev/null @@ -1,2 +0,0 @@ -echo "Running autoconf... (not really)" -echo "$(cat $(dirname $0)/configure.ac) $(date)...\"" > $(dirname $0)/configure From git at git.haskell.org Thu Oct 26 22:59:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove fake configure.ac. (42304f9) Message-ID: <20171026225910.EE26E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/42304f98b15301c4a2feaa3ab80eb26399f8c404/ghc >--------------------------------------------------------------- commit 42304f98b15301c4a2feaa3ab80eb26399f8c404 Author: Andrey Mokhov Date: Fri Dec 26 22:34:15 2014 +0000 Remove fake configure.ac. >--------------------------------------------------------------- 42304f98b15301c4a2feaa3ab80eb26399f8c404 cfg/configure.ac | 1053 ++++++++++++++++++++++++++++++ cfg/default.config | 76 +++ cfg/default.config.in | 76 +++ default.config => cfg/default.config.was | 0 user.config => cfg/user.config | 0 configure.ac | 1 - 6 files changed, 1205 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 42304f98b15301c4a2feaa3ab80eb26399f8c404 From git at git.haskell.org Thu Oct 26 22:59:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move config files to cfg subdirectory. (e89924f) Message-ID: <20171026225917.CE0DF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e89924f2e5871fe2b4011b9365ab2ba21083e669/ghc >--------------------------------------------------------------- commit e89924f2e5871fe2b4011b9365ab2ba21083e669 Author: Andrey Mokhov Date: Fri Dec 26 22:36:26 2014 +0000 Move config files to cfg subdirectory. >--------------------------------------------------------------- e89924f2e5871fe2b4011b9365ab2ba21083e669 default.config.in | 45 --------------------------------------------- user.config | 1 - 2 files changed, 46 deletions(-) diff --git a/default.config.in b/default.config.in deleted file mode 100644 index 4ab5e21..0000000 --- a/default.config.in +++ /dev/null @@ -1,45 +0,0 @@ -ghc-cabal = inplace/bin/ghc-cabal at exeext_host@ -ghc = @WithGhc@ -ghc-pkg = @GhcPkgCmd@ -gcc = @WhatGccIsCalled@ -ld = @LdCmd@ -ar = @ArCmd@ -alex = @AlexCmd@ -happy = @HappyCmd@ -hscolour = @HSCOLOUR@ -target-os = @TargetOS_CPP@ -target-arch = @TargetArch_CPP@ -target-platform-full = @TargetPlatformFull@ - -cross-compiling = @CrossCompiling@ - -conf-cc-args-stage-0 = @CONF_CC_OPTS_STAGE0@ -conf-cc-args-stage-1 = @CONF_CC_OPTS_STAGE1@ -conf-cc-args-stage-2 = @CONF_CC_OPTS_STAGE2@ - -conf-cpp-args-stage-0 = @CONF_CPP_OPTS_STAGE0@ -conf-cpp-args-stage-1 = @CONF_CPP_OPTS_STAGE1@ -conf-cpp-args-stage-2 = @CONF_CPP_OPTS_STAGE2@ - -conf-gcc-linker-args-stage-0 = @CONF_GCC_LINKER_OPTS_STAGE0@ -conf-gcc-linker-args-stage-1 = @CONF_GCC_LINKER_OPTS_STAGE1@ -conf-gcc-linker-args-stage-2 = @CONF_GCC_LINKER_OPTS_STAGE2@ - -conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ -conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ -conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ - -iconv-include-dirs = @ICONV_INCLUDE_DIRS@ -iconv-lib-dirs = @ICONV_LIB_DIRS@ - -gmp-include-dirs = @GMP_INCLUDE_DIRS@ -gmp-lib-dirs = @GMP_LIB_DIRS@ - -lax-dependencies = NO -dynamic-ghc-programs = NO -gcc-is-clang = @GccIsClang@ -gcc-lt-46 = @GccLT46@ - - - -host-os-cpp = @HostOS_CPP@ \ No newline at end of file diff --git a/user.config b/user.config deleted file mode 100644 index 313d39a..0000000 --- a/user.config +++ /dev/null @@ -1 +0,0 @@ -lax-dependencies = YES From git at git.haskell.org Thu Oct 26 22:59:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove generated default.config. (e4d24e1) Message-ID: <20171026225914.696563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4d24e1f0360dc8c2afd5614f0d27a98e93024cf/ghc >--------------------------------------------------------------- commit e4d24e1f0360dc8c2afd5614f0d27a98e93024cf Author: Andrey Mokhov Date: Fri Dec 26 22:35:20 2014 +0000 Remove generated default.config. >--------------------------------------------------------------- e4d24e1f0360dc8c2afd5614f0d27a98e93024cf default.config | 52 ---------------------------------------------------- 1 file changed, 52 deletions(-) diff --git a/default.config b/default.config deleted file mode 100644 index f821e7a..0000000 --- a/default.config +++ /dev/null @@ -1,52 +0,0 @@ -system-ghc = C:/msys64/usr/local/bin/ghc.exe -system-ghc-pkg = C:/msys64/usr/local/bin/ghc-pkg.exe - -ghc-cabal = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-cabal.exe -ghc-stage1 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage1.exe -ghc-stage2 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage2.exe -ghc-stage3 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage3.exe - -ghc-pkg = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-pkg.exe - -gcc = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/gcc.exe -ld = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ld.exe -ar = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ar.exe -alex = C:/msys64/usr/local/bin/alex.exe -happy = C:/msys64/usr/local/bin/happy.exe -hscolour = - -target-os = mingw32 -target-arch = x86_64 -target-platform-full = x86_64-unknown-mingw32 - -cross-compiling = NO - -conf-cc-args-stage-0 = -fno-stack-protector -conf-cc-args-stage-1 = -fno-stack-protector -conf-cc-args-stage-2 = -fno-stack-protector - -conf-cpp-args-stage-0 = -conf-cpp-args-stage-1 = -conf-cpp-args-stage-2 = - -conf-gcc-linker-args-stage-0 = -conf-gcc-linker-args-stage-1 = -conf-gcc-linker-args-stage-2 = - -conf-ld-linker-args-stage-0 = -conf-ld-linker-args-stage-1 = -conf-ld-linker-args-stage-2 = - -iconv-include-dirs = -iconv-lib-dirs = -gmp-include-dirs = -gmp-lib-dirs = - -lax-dependencies = NO -dynamic-ghc-programs = NO -gcc-is-clang = NO -gcc-lt-46 = NO - - - -host-os-cpp = mingw32 From git at git.haskell.org Thu Oct 26 22:59:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove generated file. (3dac5a5) Message-ID: <20171026225921.55B6E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3dac5a577f93267315681ba667562d2e5e525c82/ghc >--------------------------------------------------------------- commit 3dac5a577f93267315681ba667562d2e5e525c82 Author: Andrey Mokhov Date: Fri Dec 26 22:37:20 2014 +0000 Remove generated file. >--------------------------------------------------------------- 3dac5a577f93267315681ba667562d2e5e525c82 cfg/default.config | 76 -------------------------------------------------- cfg/default.config.was | 52 ---------------------------------- 2 files changed, 128 deletions(-) diff --git a/cfg/default.config b/cfg/default.config deleted file mode 100644 index 60fa290..0000000 --- a/cfg/default.config +++ /dev/null @@ -1,76 +0,0 @@ -# Paths to builders: -# ================== - -system-ghc = /usr/local/bin/ghc -system-ghc-pkg = /usr/local/bin/ghc-pkg - -ghc-cabal = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-cabal - -ghc-stage1 = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-stage1 -ghc-stage2 = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-stage2 -ghc-stage3 = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-stage3 - -ghc-pkg = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-pkg - -gcc = C:/msys64/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe -ld = C:/msys64/home/chEEtah/ghc/inplace/mingw/bin/ld.exe -ar = /mingw64/bin/ar -alex = /usr/local/bin/alex -happy = /usr/local/bin/happy -hscolour = - -# Information about builders: -#============================ - -gcc-is-clang = -gcc-lt-46 = NO - -# Build options: -#=============== - -lax-dependencies = NO -dynamic-ghc-programs = NO - -# Information about host and target systems: -# ========================================== - -target-os = mingw32 -target-arch = x86_64 -target-platform-full = x86_64-unknown-mingw32 - -host-os-cpp = mingw32 - -cross-compiling = NO - -# Compilation and linking flags: -#=============================== - -conf-cc-args-stage-0 = -fno-stack-protector -conf-cc-args-stage-1 = -fno-stack-protector -conf-cc-args-stage-2 = -fno-stack-protector - -conf-cpp-args-stage-0 = -conf-cpp-args-stage-1 = -conf-cpp-args-stage-2 = - -conf-gcc-linker-args-stage-0 = -conf-gcc-linker-args-stage-1 = -conf-gcc-linker-args-stage-2 = - -conf-ld-linker-args-stage-0 = -conf-ld-linker-args-stage-1 = -conf-ld-linker-args-stage-2 = - -# Include and library directories: -#================================= - -iconv-include-dirs = -iconv-lib-dirs = - -gmp-include-dirs = -gmp-lib-dirs = - - - - - diff --git a/cfg/default.config.was b/cfg/default.config.was deleted file mode 100644 index f821e7a..0000000 --- a/cfg/default.config.was +++ /dev/null @@ -1,52 +0,0 @@ -system-ghc = C:/msys64/usr/local/bin/ghc.exe -system-ghc-pkg = C:/msys64/usr/local/bin/ghc-pkg.exe - -ghc-cabal = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-cabal.exe -ghc-stage1 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage1.exe -ghc-stage2 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage2.exe -ghc-stage3 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage3.exe - -ghc-pkg = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-pkg.exe - -gcc = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/gcc.exe -ld = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ld.exe -ar = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ar.exe -alex = C:/msys64/usr/local/bin/alex.exe -happy = C:/msys64/usr/local/bin/happy.exe -hscolour = - -target-os = mingw32 -target-arch = x86_64 -target-platform-full = x86_64-unknown-mingw32 - -cross-compiling = NO - -conf-cc-args-stage-0 = -fno-stack-protector -conf-cc-args-stage-1 = -fno-stack-protector -conf-cc-args-stage-2 = -fno-stack-protector - -conf-cpp-args-stage-0 = -conf-cpp-args-stage-1 = -conf-cpp-args-stage-2 = - -conf-gcc-linker-args-stage-0 = -conf-gcc-linker-args-stage-1 = -conf-gcc-linker-args-stage-2 = - -conf-ld-linker-args-stage-0 = -conf-ld-linker-args-stage-1 = -conf-ld-linker-args-stage-2 = - -iconv-include-dirs = -iconv-lib-dirs = -gmp-include-dirs = -gmp-lib-dirs = - -lax-dependencies = NO -dynamic-ghc-programs = NO -gcc-is-clang = NO -gcc-lt-46 = NO - - - -host-os-cpp = mingw32 From git at git.haskell.org Thu Oct 26 22:59:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for autoconf/configure chain. (7d90047) Message-ID: <20171026225924.C130A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d90047a4fad755726ba70cc7f9506512008b96f/ghc >--------------------------------------------------------------- commit 7d90047a4fad755726ba70cc7f9506512008b96f Author: Andrey Mokhov Date: Fri Dec 26 22:38:42 2014 +0000 Add support for autoconf/configure chain. >--------------------------------------------------------------- 7d90047a4fad755726ba70cc7f9506512008b96f cfg/default.config.in | 9 ++------- src/Base.hs | 1 + src/Config.hs | 18 ++++++++++-------- src/Oracles.hs | 44 ++++++++++++++++++++++++++++++++++---------- 4 files changed, 47 insertions(+), 25 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index c01bb87..d3617f4 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -1,5 +1,5 @@ # Paths to builders: -# ================== +#=================== system-ghc = @WithGhc@ system-ghc-pkg = @GhcPkgCmd@ @@ -32,7 +32,7 @@ lax-dependencies = NO dynamic-ghc-programs = NO # Information about host and target systems: -# ========================================== +#=========================================== target-os = @TargetOS_CPP@ target-arch = @TargetArch_CPP@ @@ -69,8 +69,3 @@ iconv-lib-dirs = @ICONV_LIB_DIRS@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ - - - - - diff --git a/src/Base.hs b/src/Base.hs index 7e130c2..e44b3bb 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -5,6 +5,7 @@ module Base ( module Development.Shake.FilePath, module Control.Applicative, module Data.Monoid, + module Data.List, Stage (..), Args, arg, Condition, joinArgs, joinArgsWithSpaces, diff --git a/src/Config.hs b/src/Config.hs index a370f38..3d26482 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -1,5 +1,5 @@ module Config ( - autoconfRules, configureRules + autoconfRules, configureRules, cfgPath ) where import Development.Shake @@ -9,16 +9,18 @@ import Development.Shake.Rule import Control.Applicative import Control.Monad import Base -import Oracles + +cfgPath :: FilePath +cfgPath = "shake" "cfg" autoconfRules :: Rules () autoconfRules = do - "shake/configure" %> \out -> do - need ["shake/configure.ac"] - cmd $ "bash shake/autoconf" + "configure" %> \out -> do + copyFile' (cfgPath "configure.ac") "configure.ac" + cmd "bash autoconf" configureRules :: Rules () configureRules = do - "shake/default.config" %> \out -> do - need ["shake/default.config.in", "shake/configure"] - cmd $ "bash shake/configure" + cfgPath "default.config" %> \out -> do + need [cfgPath "default.config.in", "configure"] + cmd "bash configure" diff --git a/src/Oracles.hs b/src/Oracles.hs index 9138780..971d5c6 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -20,7 +20,9 @@ import qualified System.Directory as System import qualified Data.HashMap.Strict as M import qualified Prelude import Prelude hiding (not, (&&), (||)) +import Data.Char import Base +import Config data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage @@ -40,10 +42,18 @@ path builder = do Ghc Stage3 -> "ghc-stage3" GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) - askConfigWithDefault key $ + cfgPath <- askConfigWithDefault key $ error $ "\nCannot find path to '" ++ key ++ "' in configuration files." + let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" + windows <- test WindowsHost + if (windows && "/" `isPrefixOf` cfgPathExe) + then do + root <- option Root + return $ root ++ cfgPathExe + else + return cfgPathExe argPath :: Builder -> Args argPath builder = do @@ -53,7 +63,7 @@ argPath builder = do -- Explain! -- TODO: document change in behaviour (LaxDeps) needBuilder :: Builder -> Action () -needBuilder ghc @ (Ghc _) = do +needBuilder ghc @ (Ghc stage) = do target <- path ghc laxDeps <- test LaxDeps -- TODO: get rid of test? if laxDeps then orderOnly [target] else need [target] @@ -88,9 +98,18 @@ run builder args = do data Option = TargetOS | TargetArch | TargetPlatformFull | ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage | IconvIncludeDirs | IconvLibDirs | GmpIncludeDirs | GmpLibDirs - | HostOsCpp + | HostOsCpp | Root option :: Option -> Action String +option Root = do + windows <- test WindowsHost + if (windows) + then do + Stdout out <- cmd ["cygpath", "-m", "/"] + return $ dropWhileEnd isSpace out + else + return "/" + option opt = askConfig $ case opt of TargetOS -> "target-os" TargetArch -> "target-arch" @@ -112,6 +131,7 @@ argOption opt = do data Flag = LaxDeps | Stage1Only | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs | GccIsClang | GccLt46 | CrossCompiling | Validating | PlatformSupportsSharedLibs + | WindowsHost test :: Flag -> Action Bool test GhcWithInterpreter = do @@ -130,6 +150,10 @@ test HsColourSrcs = do hscolour <- path HsColour return $ hscolour /= "" +test WindowsHost = do + hostOsCpp <- option HostOsCpp + return $ hostOsCpp `elem` ["mingw32", "cygwin32"] + test flag = do (key, defaultValue) <- return $ case flag of LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file @@ -230,19 +254,19 @@ askConfig key = askConfigWithDefault key $ error $ "\nCannot find key '" oracleRules :: Rules () oracleRules = do cfg <- newCache $ \() -> do - unless (doesFileExist "shake/default.config") $ do + unless (doesFileExist $ cfgPath "default.config.in") $ do error $ "\nDefault configuration file '" - ++ "shake/default.config.in" + ++ (cfgPath "default.config.in") ++ "' is missing; unwilling to proceed." return () - need ["shake/default.config"] - cfgDefault <- liftIO $ readConfigFile "shake/default.config" - existsUser <- doesFileExist "shake/user.config" + need [cfgPath "default.config"] + cfgDefault <- liftIO $ readConfigFile $ cfgPath "default.config" + existsUser <- doesFileExist $ cfgPath "user.config" cfgUser <- if existsUser - then liftIO $ readConfigFile "shake/user.config" + then liftIO $ readConfigFile $ cfgPath "user.config" else do putLoud $ "\nUser defined configuration file '" - ++ "shake/user.config" + ++ (cfgPath "user.config") ++ "' is missing; proceeding with default configuration.\n" return M.empty return $ cfgUser `M.union` cfgDefault From git at git.haskell.org Thu Oct 26 22:59:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generated default.config to .gitignore. (371842e) Message-ID: <20171026225928.44D823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/371842eb16a529d8bb1bae756369f5422e011032/ghc >--------------------------------------------------------------- commit 371842eb16a529d8bb1bae756369f5422e011032 Author: Andrey Mokhov Date: Fri Dec 26 22:57:49 2014 +0000 Add generated default.config to .gitignore. >--------------------------------------------------------------- 371842eb16a529d8bb1bae756369f5422e011032 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 30e2546..375b257 100644 --- a/.gitignore +++ b/.gitignore @@ -2,4 +2,4 @@ *.hi _shake/ _build/ -configure +cfg/default.config From git at git.haskell.org Thu Oct 26 22:59:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a comment to user.config explaining its purpose. (ced1860) Message-ID: <20171026225931.C5C163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ced186037fe9c0ad8c5ac1d191318b52d57dfac8/ghc >--------------------------------------------------------------- commit ced186037fe9c0ad8c5ac1d191318b52d57dfac8 Author: Andrey Mokhov Date: Fri Dec 26 22:58:30 2014 +0000 Add a comment to user.config explaining its purpose. >--------------------------------------------------------------- ced186037fe9c0ad8c5ac1d191318b52d57dfac8 cfg/user.config | 3 +++ 1 file changed, 3 insertions(+) diff --git a/cfg/user.config b/cfg/user.config index 313d39a..b72c5b4 100644 --- a/cfg/user.config +++ b/cfg/user.config @@ -1 +1,4 @@ +# Override default settings (stored in default.config file): +#=========================================================== + lax-dependencies = YES From git at git.haskell.org Thu Oct 26 22:59:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant imports, add TODO's. (fe2655b) Message-ID: <20171026225935.322A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fe2655b6cd60d09311e87e1aa8736a3bbd847d9b/ghc >--------------------------------------------------------------- commit fe2655b6cd60d09311e87e1aa8736a3bbd847d9b Author: Andrey Mokhov Date: Fri Dec 26 23:04:07 2014 +0000 Remove redundant imports, add TODO's. >--------------------------------------------------------------- fe2655b6cd60d09311e87e1aa8736a3bbd847d9b src/Config.hs | 10 ++-------- 1 file changed, 2 insertions(+), 8 deletions(-) diff --git a/src/Config.hs b/src/Config.hs index 3d26482..b4f0519 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -2,12 +2,6 @@ module Config ( autoconfRules, configureRules, cfgPath ) where -import Development.Shake -import Development.Shake.Command -import Development.Shake.FilePath -import Development.Shake.Rule -import Control.Applicative -import Control.Monad import Base cfgPath :: FilePath @@ -17,10 +11,10 @@ autoconfRules :: Rules () autoconfRules = do "configure" %> \out -> do copyFile' (cfgPath "configure.ac") "configure.ac" - cmd "bash autoconf" + cmd "bash autoconf" -- TODO: get rid of 'bash' configureRules :: Rules () configureRules = do cfgPath "default.config" %> \out -> do need [cfgPath "default.config.in", "configure"] - cmd "bash configure" + cmd "bash configure" -- TODO: get rid of 'bash' From git at git.haskell.org Thu Oct 26 22:59:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant imports, drop Stage1Only. (428e148) Message-ID: <20171026225938.CB29B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/428e148afb2a043419f3be83c56e05489b4e5efe/ghc >--------------------------------------------------------------- commit 428e148afb2a043419f3be83c56e05489b4e5efe Author: Andrey Mokhov Date: Fri Dec 26 23:05:12 2014 +0000 Remove redundant imports, drop Stage1Only. >--------------------------------------------------------------- 428e148afb2a043419f3be83c56e05489b4e5efe src/Oracles.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 971d5c6..08d668e 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -12,11 +12,10 @@ module Oracles ( oracleRules ) where -import Development.Shake.Config import Development.Shake.Rule +import Development.Shake.Config import Development.Shake.Classes import Control.Monad hiding (when, unless) -import qualified System.Directory as System import qualified Data.HashMap.Strict as M import qualified Prelude import Prelude hiding (not, (&&), (||)) @@ -129,7 +128,7 @@ argOption opt = do opt' <- option opt arg [opt'] -data Flag = LaxDeps | Stage1Only | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs +data Flag = LaxDeps | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs | GccIsClang | GccLt46 | CrossCompiling | Validating | PlatformSupportsSharedLibs | WindowsHost @@ -157,7 +156,6 @@ test WindowsHost = do test flag = do (key, defaultValue) <- return $ case flag of LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file - Stage1Only -> ("stage-1-only" , False) -- TODO: target only DynamicGhcPrograms -> ("dynamic-ghc-programs", False) GccIsClang -> ("gcc-is-clang" , False) GccLt46 -> ("gcc-lt-46" , False) From git at git.haskell.org Thu Oct 26 22:59:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make C:/msys64/ a silent command. (4d2b4bc) Message-ID: <20171026225942.49FC93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4d2b4bcce29e1a476dcbe0055319c7586e75d8ec/ghc >--------------------------------------------------------------- commit 4d2b4bcce29e1a476dcbe0055319c7586e75d8ec Author: Andrey Mokhov Date: Fri Dec 26 23:38:28 2014 +0000 Make C:/msys64/ a silent command. >--------------------------------------------------------------- 4d2b4bcce29e1a476dcbe0055319c7586e75d8ec src/Oracles.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 08d668e..e03d6a3 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -104,7 +104,7 @@ option Root = do windows <- test WindowsHost if (windows) then do - Stdout out <- cmd ["cygpath", "-m", "/"] + Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] return $ dropWhileEnd isSpace out else return "/" From git at git.haskell.org Thu Oct 26 22:59:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update to the latest GHC source tree. (a58a713) Message-ID: <20171026225945.B63F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a58a7132c1bdd47dc79e28a4fef01b090e5a88c0/ghc >--------------------------------------------------------------- commit a58a7132c1bdd47dc79e28a4fef01b090e5a88c0 Author: Andrey Mokhov Date: Sat Dec 27 23:42:56 2014 +0000 Update to the latest GHC source tree. >--------------------------------------------------------------- a58a7132c1bdd47dc79e28a4fef01b090e5a88c0 cfg/configure.ac | 122 ++++++++++++++++++++++++++++++++----------------------- 1 file changed, 71 insertions(+), 51 deletions(-) diff --git a/cfg/configure.ac b/cfg/configure.ac index b31d1b3..125fd49 100644 --- a/cfg/configure.ac +++ b/cfg/configure.ac @@ -13,7 +13,7 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.9], [glasgow-haskell-bugs at haskell.org], [ghc]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.11], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO : ${RELEASE=NO} @@ -187,56 +187,6 @@ AC_SUBST([WithGhc]) dnl ** Without optimization some INLINE trickery fails for GHCi SRC_CC_OPTS="-O" -dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. -dnl Unfortunately we don't know whether the user is going to request a -dnl build with the LLVM backend as this is only given in build.mk. -dnl -dnl Instead, we try to do as much work as possible here, checking -dnl whether -fllvm is the stage 0 compiler's default. If so we -dnl fail. If not, we check whether -fllvm is affected explicitly and -dnl if so set a flag. The build system will later check this flag -dnl after the desired build flags are known. -AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) -echo "main = putStrLn \"%function\"" > conftestghc.hs - -# Check whether LLVM backend is default for this platform -"${WithGhc}" conftestghc.hs 2>&1 >/dev/null -res=`./conftestghc` -if test "x$res" == "x%object" -then - AC_MSG_RESULT(yes) - echo "Buggy bootstrap compiler" - echo "" - echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" - echo "and therefore will miscompile the LLVM backend if -fllvm is" - echo "used." - echo - echo "Please use another bootstrap compiler" - exit 1 -fi - -# -fllvm is not the default, but set a flag so the Makefile can check -# -for it in the build flags later on -"${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null -if test $? == 0 -then - res=`./conftestghc` - if test "x$res" == "x%object" - then - AC_MSG_RESULT(yes) - GHC_LLVM_AFFECTED_BY_9439=1 - elif test "x$res" == "x%function" - then - AC_MSG_RESULT(no) - GHC_LLVM_AFFECTED_BY_9439=0 - else - AC_MSG_WARN(unexpected output $res) - fi -else - AC_MSG_RESULT(failed to compile, assuming no) -fi -AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) - dnl-------------------------------------------------------------------- dnl * Choose host(/target/build) platform dnl-------------------------------------------------------------------- @@ -593,6 +543,59 @@ dnl -------------------------------------------------------------- dnl * General configuration checks dnl -------------------------------------------------------------- +dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. +dnl Unfortunately we don't know whether the user is going to request a +dnl build with the LLVM backend as this is only given in build.mk. +dnl +dnl Instead, we try to do as much work as possible here, checking +dnl whether -fllvm is the stage 0 compiler's default. If so we +dnl fail. If not, we check whether -fllvm is affected explicitly and +dnl if so set a flag. The build system will later check this flag +dnl after the desired build flags are known. +if test -n "$LlcCmd" && test -n "$OptCmd" +then + AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) + echo "main = putStrLn \"%function\"" > conftestghc.hs + + # Check whether LLVM backend is default for this platform + "${WithGhc}" conftestghc.hs 2>&1 >/dev/null + res=`./conftestghc` + if test "x$res" = "x%object" + then + AC_MSG_RESULT(yes) + echo "Buggy bootstrap compiler" + echo "" + echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" + echo "and therefore will miscompile the LLVM backend if -fllvm is" + echo "used." + echo + echo "Please use another bootstrap compiler" + exit 1 + fi + + # -fllvm is not the default, but set a flag so the Makefile can check + # -for it in the build flags later on + "${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null + if test $? = 0 + then + res=`./conftestghc` + if test "x$res" = "x%object" + then + AC_MSG_RESULT(yes) + GHC_LLVM_AFFECTED_BY_9439=1 + elif test "x$res" = "x%function" + then + AC_MSG_RESULT(no) + GHC_LLVM_AFFECTED_BY_9439=0 + else + AC_MSG_WARN(unexpected output $res) + fi + else + AC_MSG_RESULT(failed to compile, assuming no) + fi +fi +AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) + dnl ** Can the unix package be built? dnl -------------------------------------------------------------- @@ -896,6 +899,22 @@ AC_TRY_LINK_FUNC(printf\$LDBLStub, [Define to 1 if we have printf$LDBLStub (Apple Mac OS >= 10.4, PPC).]) ]) +dnl ** pthread_setname_np is a recent addition to glibc, and OS X has +dnl a different single-argument version. +AC_CHECK_LIB(pthread, pthread_setname_np) +AC_MSG_CHECKING(for pthread_setname_np) +AC_TRY_LINK( +[ +#define _GNU_SOURCE +#include +], +[pthread_setname_np(pthread_self(), "name");], + AC_MSG_RESULT(yes) + AC_DEFINE([HAVE_PTHREAD_SETNAME_NP], [1], + [Define to 1 if you have the glibc version of pthread_setname_np]), + AC_MSG_RESULT(no) +) + dnl ** check for eventfd which is needed by the I/O manager AC_CHECK_HEADERS([sys/eventfd.h]) AC_CHECK_FUNCS([eventfd]) @@ -986,6 +1005,7 @@ echo [" Configure completed successfully. Building GHC version : $ProjectVersion + Git commit id : $ProjectGitCommitId Build platform : $BuildPlatform Host platform : $HostPlatform From git at git.haskell.org Thu Oct 26 22:59:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update build-package-data.docx to match Package.hs (8a93116) Message-ID: <20171026225949.4BA023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8a9311684390d4cb8a07d9c1521021769546caff/ghc >--------------------------------------------------------------- commit 8a9311684390d4cb8a07d9c1521021769546caff Author: Andrey Mokhov Date: Sun Dec 28 03:32:49 2014 +0000 Update build-package-data.docx to match Package.hs >--------------------------------------------------------------- 8a9311684390d4cb8a07d9c1521021769546caff doc/build-package-data.docx | Bin 15964 -> 16519 bytes 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/doc/build-package-data.docx b/doc/build-package-data.docx index c2637c9..a2708cc 100644 Binary files a/doc/build-package-data.docx and b/doc/build-package-data.docx differ From git at git.haskell.org Thu Oct 26 22:59:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revisions (add comments, move Condition to Oracles.hs). (618d90d) Message-ID: <20171026225952.BE1053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/618d90dc2bc41256a18c42776d701a9a4fc23d26/ghc >--------------------------------------------------------------- commit 618d90dc2bc41256a18c42776d701a9a4fc23d26 Author: Andrey Mokhov Date: Sun Dec 28 03:33:55 2014 +0000 Minor revisions (add comments, move Condition to Oracles.hs). >--------------------------------------------------------------- 618d90dc2bc41256a18c42776d701a9a4fc23d26 src/Base.hs | 4 +--- src/Oracles.hs | 21 +++++++++++++-------- 2 files changed, 14 insertions(+), 11 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index e44b3bb..b4ea8cb 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,7 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, Condition, + Args, arg, joinArgs, joinArgsWithSpaces, filterOut, ) where @@ -22,8 +22,6 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) type Args = Action [String] -type Condition = Action Bool - instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q diff --git a/src/Oracles.hs b/src/Oracles.hs index e03d6a3..9ceb121 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,5 +1,5 @@ {-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, DeriveGeneric, ConstraintKinds #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} module Oracles ( module Control.Monad, @@ -8,7 +8,7 @@ module Oracles ( Builder (..), Flag (..), Option (..), path, with, run, argPath, option, argOption, - test, when, unless, not, (&&), (||), + Condition, test, when, unless, not, (&&), (||), oracleRules ) where @@ -50,7 +50,7 @@ path builder = do if (windows && "/" `isPrefixOf` cfgPathExe) then do root <- option Root - return $ root ++ cfgPathExe + return $ root ++ (drop 1 $ cfgPathExe) else return cfgPathExe @@ -59,19 +59,22 @@ argPath builder = do path <- path builder arg [path] --- Explain! --- TODO: document change in behaviour (LaxDeps) +-- When LaxDeps flag is set (by adding 'lax-dependencies = YES' to user.config), +-- dependencies on the GHC executable are turned into order-only dependencies to +-- avoid needless recompilation when making changes to GHC's sources. In certain +-- situations this can lead to build failures, in which case you should reset +-- the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do target <- path ghc - laxDeps <- test LaxDeps -- TODO: get rid of test? + laxDeps <- test LaxDeps if laxDeps then orderOnly [target] else need [target] needBuilder builder = do target <- path builder need [target] --- 'with Gcc' generates --with-gcc=/usr/bin/gcc and needs it +-- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder with :: Builder -> Args with builder = do let prefix = case builder of @@ -163,7 +166,7 @@ test flag = do Validating -> ("validating" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ - do putLoud $ "\nFlag '" + do putLoud $ "\nFlag '" -- TODO: Give the warning *only once* per key ++ key ++ "' not set in configuration files. " ++ "Proceeding with default value '" @@ -172,6 +175,8 @@ test flag = do return defaultString return $ value == "YES" +type Condition = Action Bool + class ToCondition a where toCondition :: a -> Condition From git at git.haskell.org Thu Oct 26 22:59:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -fwarn-tabs and -fwarn-unused-imports. (7eb2d38) Message-ID: <20171026225956.4CC833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7eb2d388f236b8759046b1d58e89cbf9088e4940/ghc >--------------------------------------------------------------- commit 7eb2d388f236b8759046b1d58e89cbf9088e4940 Author: Andrey Mokhov Date: Mon Dec 29 21:43:26 2014 +0000 Add -fwarn-tabs and -fwarn-unused-imports. >--------------------------------------------------------------- 7eb2d388f236b8759046b1d58e89cbf9088e4940 build.bat | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 8e3dba2..0e1f581 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,3 @@ @mkdir _shake 2> nul - at ghc --make src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build + at _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 22:59:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 22:59:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build/autogen/Paths_library.hs to ghc-cabal results. (3bbb9fb) Message-ID: <20171026225959.AAE9B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3bbb9fba477a7c84e2e615712a12046fda14d8b9/ghc >--------------------------------------------------------------- commit 3bbb9fba477a7c84e2e615712a12046fda14d8b9 Author: Andrey Mokhov Date: Mon Dec 29 21:51:22 2014 +0000 Add build/autogen/Paths_library.hs to ghc-cabal results. >--------------------------------------------------------------- 3bbb9fba477a7c84e2e615712a12046fda14d8b9 src/Package.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Package.hs b/src/Package.hs index 8d7311b..f5eae9b 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -120,7 +120,8 @@ buildPackageData pkg @ (Package name path todo) (stage, dist, settings) = "haddock-prologue.txt", "inplace-pkg-config", "setup-config", - "build" "autogen" "cabal_macros.h" + "build" "autogen" "cabal_macros.h", + "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? What's up with Paths_cpsa.hs? ] &%> \_ -> do need [path name <.> "cabal"] when (doesFileExist $ path "configure.ac") $ need [path "configure"] From git at git.haskell.org Thu Oct 26 23:00:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add replaceChar helper function. (1fa4aa5) Message-ID: <20171026230003.2D9193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fa4aa517a6e1334b276539204b41367fbff8a51/ghc >--------------------------------------------------------------- commit 1fa4aa517a6e1334b276539204b41367fbff8a51 Author: Andrey Mokhov Date: Tue Dec 30 03:52:56 2014 +0000 Add replaceChar helper function. >--------------------------------------------------------------- 1fa4aa517a6e1334b276539204b41367fbff8a51 src/Base.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index b4ea8cb..eaebaf3 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -10,6 +10,7 @@ module Base ( Args, arg, joinArgs, joinArgsWithSpaces, filterOut, + replaceChar ) where import Development.Shake hiding ((*>)) @@ -42,3 +43,8 @@ joinArgs = intercalateArgs "" filterOut :: Args -> [String] -> Args filterOut args list = filter (`notElem` list) <$> args + +replaceChar :: Char -> Char -> String -> String +replaceChar from to = (go from) . if from == '/' then go '\\' else id + where + go from' = map (\c -> if c == from' then to else c) From git at git.haskell.org Thu Oct 26 23:00:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring && back. (4198a65) Message-ID: <20171026230006.C19AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4198a65a93270c5be30cf99acecc922bd4a4712b/ghc >--------------------------------------------------------------- commit 4198a65a93270c5be30cf99acecc922bd4a4712b Author: Andrey Mokhov Date: Tue Dec 30 03:53:34 2014 +0000 Bring && back. >--------------------------------------------------------------- 4198a65a93270c5be30cf99acecc922bd4a4712b build.bat | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/build.bat b/build.bat index 0e1f581..b6b9a82 100644 --- a/build.bat +++ b/build.bat @@ -1,3 +1,2 @@ @mkdir _shake 2> nul - at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build - at _shake\build --lint --directory ".." %* + at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:00:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track progress. (2d4a29c) Message-ID: <20171026230010.34F4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb/ghc >--------------------------------------------------------------- commit 2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb Author: Andrey Mokhov Date: Tue Dec 30 03:55:34 2014 +0000 Track progress. >--------------------------------------------------------------- 2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb doc/deepseq-build-progress.txt | 359 +++++++++-------------------------------- 1 file changed, 77 insertions(+), 282 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 2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb From git at git.haskell.org Thu Oct 26 23:00:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for parsing package-data.mk files. (a253255) Message-ID: <20171026230013.A86663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a253255970c94138f8c67ed298117d6adac0eef2/ghc >--------------------------------------------------------------- commit a253255970c94138f8c67ed298117d6adac0eef2 Author: Andrey Mokhov Date: Tue Dec 30 03:56:28 2014 +0000 Add support for parsing package-data.mk files. >--------------------------------------------------------------- a253255970c94138f8c67ed298117d6adac0eef2 src/Oracles.hs | 39 +++++++++++++++++++++++++++++++++++++-- 1 file changed, 37 insertions(+), 2 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 9ceb121..6a03a6d 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -9,6 +9,7 @@ module Oracles ( path, with, run, argPath, option, argOption, Condition, test, when, unless, not, (&&), (||), + packagaDataOption, PackageDataKey (..), oracleRules ) where @@ -240,9 +241,10 @@ instance ToCondition a => AndOr Flag a where newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + askConfigWithDefault :: String -> Action String -> Action String askConfigWithDefault key defaultAction = do - maybeValue <- askOracle $ ConfigKey $ key + maybeValue <- askOracle $ ConfigKey key case maybeValue of Just value -> return value Nothing -> do @@ -254,6 +256,32 @@ askConfig key = askConfigWithDefault key $ error $ "\nCannot find key '" ++ key ++ "' in configuration files." +newtype PackageDataPair = PackageDataPair (FilePath, String) + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +packagaDataOptionWithDefault :: FilePath -> String -> Action String -> Action String +packagaDataOptionWithDefault file key defaultAction = do + maybeValue <- askOracle $ PackageDataPair (file, key) + case maybeValue of + Just value -> return value + Nothing -> do + result <- defaultAction + return result + +data PackageDataKey = Modules | SrcDirs + +packagaDataOption :: FilePath -> PackageDataKey -> Action String +packagaDataOption file key = do + let keyName = replaceChar '/' '_' $ takeDirectory file ++ case key of + Modules -> "_MODULES" + SrcDirs -> "_HS_SRC_DIRS" + packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" + ++ keyName + ++ "' in " + ++ file + ++ "." + + oracleRules :: Rules () oracleRules = do cfg <- newCache $ \() -> do @@ -273,5 +301,12 @@ oracleRules = do ++ "' is missing; proceeding with default configuration.\n" return M.empty return $ cfgUser `M.union` cfgDefault - addOracle $ \(ConfigKey x) -> M.lookup x <$> cfg () + + addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () + + pkgData <- newCache $ \file -> do + need [file] + liftIO $ readConfigFile file + + addOracle $ \(PackageDataPair (file, key)) -> M.lookup key <$> pkgData file return () From git at git.haskell.org Thu Oct 26 23:00:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageDeps rule. (9d1a489) Message-ID: <20171026230017.3C0643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d1a489b8faf8f91f6125865a5a74712a8b8a7a8/ghc >--------------------------------------------------------------- commit 9d1a489b8faf8f91f6125865a5a74712a8b8a7a8 Author: Andrey Mokhov Date: Tue Dec 30 03:57:22 2014 +0000 Add buildPackageDeps rule. >--------------------------------------------------------------- 9d1a489b8faf8f91f6125865a5a74712a8b8a7a8 doc/deepseq-build-progress.txt | 41 ++------------------ src/Package.hs | 88 ++++++++++++++++++++++++++++++++++++++++-- 2 files changed, 87 insertions(+), 42 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9d1a489b8faf8f91f6125865a5a74712a8b8a7a8 From git at git.haskell.org Thu Oct 26 23:00:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move generic helper functions to Util.hs. (4e5f1b7) Message-ID: <20171026230020.A82513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e5f1b74b9b5946ad614bc354f01697f953a072b/ghc >--------------------------------------------------------------- commit 4e5f1b74b9b5946ad614bc354f01697f953a072b Author: Andrey Mokhov Date: Tue Dec 30 15:06:13 2014 +0000 Move generic helper functions to Util.hs. >--------------------------------------------------------------- 4e5f1b74b9b5946ad614bc354f01697f953a072b src/Base.hs | 8 +------- src/Oracles.hs | 9 ++++----- src/Package.hs | 5 +++-- src/Util.hs | 16 ++++++++++++++++ 4 files changed, 24 insertions(+), 14 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index eaebaf3..24943e4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -9,8 +9,7 @@ module Base ( Stage (..), Args, arg, joinArgs, joinArgsWithSpaces, - filterOut, - replaceChar + filterOut ) where import Development.Shake hiding ((*>)) @@ -43,8 +42,3 @@ joinArgs = intercalateArgs "" filterOut :: Args -> [String] -> Args filterOut args list = filter (`notElem` list) <$> args - -replaceChar :: Char -> Char -> String -> String -replaceChar from to = (go from) . if from == '/' then go '\\' else id - where - go from' = map (\c -> if c == from' then to else c) diff --git a/src/Oracles.hs b/src/Oracles.hs index 6a03a6d..98321c9 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -20,8 +20,8 @@ import Control.Monad hiding (when, unless) import qualified Data.HashMap.Strict as M import qualified Prelude import Prelude hiding (not, (&&), (||)) -import Data.Char import Base +import Util import Config data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage @@ -241,7 +241,6 @@ instance ToCondition a => AndOr Flag a where newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) - askConfigWithDefault :: String -> Action String -> Action String askConfigWithDefault key defaultAction = do maybeValue <- askOracle $ ConfigKey key @@ -266,20 +265,20 @@ packagaDataOptionWithDefault file key defaultAction = do Just value -> return value Nothing -> do result <- defaultAction - return result + return result -- TODO: simplify data PackageDataKey = Modules | SrcDirs packagaDataOption :: FilePath -> PackageDataKey -> Action String packagaDataOption file key = do - let keyName = replaceChar '/' '_' $ takeDirectory file ++ case key of + let keyName = replaceIf isSlash '_' $ takeDirectory file ++ case key of Modules -> "_MODULES" SrcDirs -> "_HS_SRC_DIRS" packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file - ++ "." + ++ "." -- TODO: Improve formatting oracleRules :: Rules () diff --git a/src/Package.hs b/src/Package.hs index a6df921..8488044 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -4,6 +4,7 @@ module Package ( ) where import Base +import Util import Ways import Oracles @@ -129,7 +130,7 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs let pkgDataFile = path dist "package-data.mk" pkgData <- lines <$> liftIO (readFile pkgDataFile) - length pkgData `seq` writeFileLines pkgDataFile $ map (replaceChar '/' '_') $ filter ('$' `notElem`) pkgData + length pkgData `seq` writeFileLines pkgDataFile $ map (replaceIf isSlash '_') $ filter ('$' `notElem`) pkgData where cabalArgs, ghcPkgArgs :: Args cabalArgs = mconcat @@ -225,7 +226,7 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = autogen = dist "build" "autogen" mods <- words <$> packagaDataOption pkgData Modules src <- getDirectoryFiles "" $ do - start <- map (replaceChar '.' '/') mods + start <- map (replaceEq '.' '/') mods end <- [".hs", ".lhs"] return $ path ++ "//" ++ start ++ end run (Ghc stage) $ mconcat diff --git a/src/Util.hs b/src/Util.hs new file mode 100644 index 0000000..8afd6cb --- /dev/null +++ b/src/Util.hs @@ -0,0 +1,16 @@ +module Util ( + module Data.Char, + isSlash, + replaceIf, replaceEq + ) where + +import Data.Char + +isSlash :: Char -> Bool +isSlash = (`elem` ['/', '\\']) + +replaceIf :: (a -> Bool) -> a -> [a] -> [a] +replaceIf p to = map (\from -> if p from then to else from) + +replaceEq :: Eq a => a -> a -> [a] -> [a] +replaceEq from = replaceIf (== from) From git at git.haskell.org Thu Oct 26 23:00:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Oracles.hs. (e20c4bc) Message-ID: <20171026230024.1E14B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e20c4bc3bec68971837c2808724edbfcbe0b92ab/ghc >--------------------------------------------------------------- commit e20c4bc3bec68971837c2808724edbfcbe0b92ab Author: Andrey Mokhov Date: Tue Dec 30 15:12:40 2014 +0000 Refactor Oracles.hs. >--------------------------------------------------------------- e20c4bc3bec68971837c2808724edbfcbe0b92ab src/Oracles.hs | 21 ++++++--------------- 1 file changed, 6 insertions(+), 15 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 98321c9..75439fb 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -246,14 +246,11 @@ askConfigWithDefault key defaultAction = do maybeValue <- askOracle $ ConfigKey key case maybeValue of Just value -> return value - Nothing -> do - result <- defaultAction - return result + Nothing -> defaultAction askConfig :: String -> Action String -askConfig key = askConfigWithDefault key $ error $ "\nCannot find key '" - ++ key - ++ "' in configuration files." +askConfig key = askConfigWithDefault key $ + error $ "\nCannot find key '" ++ key ++ "' in configuration files." newtype PackageDataPair = PackageDataPair (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -263,9 +260,7 @@ packagaDataOptionWithDefault file key defaultAction = do maybeValue <- askOracle $ PackageDataPair (file, key) case maybeValue of Just value -> return value - Nothing -> do - result <- defaultAction - return result -- TODO: simplify + Nothing -> defaultAction data PackageDataKey = Modules | SrcDirs @@ -274,12 +269,8 @@ packagaDataOption file key = do let keyName = replaceIf isSlash '_' $ takeDirectory file ++ case key of Modules -> "_MODULES" SrcDirs -> "_HS_SRC_DIRS" - packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" - ++ keyName - ++ "' in " - ++ file - ++ "." -- TODO: Improve formatting - + packagaDataOptionWithDefault file keyName $ + error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." oracleRules :: Rules () oracleRules = do From git at git.haskell.org Thu Oct 26 23:00:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting, add TODOs. (d2f3a74) Message-ID: <20171026230027.873143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2f3a74ae4e0ba1218025aca1b2786a35f169cee/ghc >--------------------------------------------------------------- commit d2f3a74ae4e0ba1218025aca1b2786a35f169cee Author: Andrey Mokhov Date: Tue Dec 30 15:20:37 2014 +0000 Fix formatting, add TODOs. >--------------------------------------------------------------- d2f3a74ae4e0ba1218025aca1b2786a35f169cee src/Ways.hs | 21 +++++++++++---------- 1 file changed, 11 insertions(+), 10 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 6e186ab..91cbd4f 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -23,7 +23,7 @@ data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dyn data Way = Way { tag :: String, -- e.g., "thr_p" - description :: String, -- e.g., "threaded profiled" + description :: String, -- e.g., "threaded profiled"; TODO: get rid of this field? units :: [WayUnit] -- e.g., [Threaded, Profiling] } deriving Eq @@ -72,17 +72,18 @@ defaultWays stage = do wayHcOpts :: Way -> Args wayHcOpts (Way _ _ units) = mconcat - [ when (Dynamic `notElem` units) $ arg [ "-static" ] - , when (Dynamic `elem` units) $ arg [ "-fPIC", "-dynamic" ] - , when (Threaded `elem` units) $ arg [ "-optc-DTHREADED_RTS" ] - , when (Debug `elem` units) $ arg [ "-optc-DDEBUG" ] - , when (Profiling `elem` units) $ arg [ "-prof" ] - , when (Logging `elem` units) $ arg [ "-eventlog" ] - , when (Parallel `elem` units) $ arg [ "-parallel" ] - , when (GranSim `elem` units) $ arg [ "-gransim" ] - , when (units == [Debug] || units == [Debug, Dynamic]) $ arg [ "-ticky", "-DTICKY_TICKY" ] + [ when (Dynamic `notElem` units) $ arg ["-static"] + , when (Dynamic `elem` units) $ arg ["-fPIC", "-dynamic"] + , when (Threaded `elem` units) $ arg ["-optc-DTHREADED_RTS"] + , when (Debug `elem` units) $ arg ["-optc-DDEBUG"] + , when (Profiling `elem` units) $ arg ["-prof"] + , when (Logging `elem` units) $ arg ["-eventlog"] + , when (Parallel `elem` units) $ arg ["-parallel"] + , when (GranSim `elem` units) $ arg ["-gransim"] + , when (units == [Debug] || units == [Debug, Dynamic]) $ arg ["-ticky", "-DTICKY_TICKY"] ] +-- TODO: cover other cases suffix :: FilePath -> Way -> FilePath suffix base (Way _ _ units) = concat $ From git at git.haskell.org Thu Oct 26 23:00:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out postProcessPackageData to Util.hs. (c4cc0dc) Message-ID: <20171026230030.F31233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4cc0dc7ab0465a67f9f81e309fa10eaa210b772/ghc >--------------------------------------------------------------- commit c4cc0dc7ab0465a67f9f81e309fa10eaa210b772 Author: Andrey Mokhov Date: Tue Dec 30 15:33:06 2014 +0000 Factor out postProcessPackageData to Util.hs. >--------------------------------------------------------------- c4cc0dc7ab0465a67f9f81e309fa10eaa210b772 src/Package.hs | 6 ++---- src/Util.hs | 12 +++++++++++- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 8488044..24ef85d 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -122,15 +122,13 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = "inplace-pkg-config", "setup-config", "build" "autogen" "cabal_macros.h", - "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? What's up with Paths_cpsa.hs? + "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. ] &%> \_ -> do need [path name <.> "cabal"] when (doesFileExist $ path "configure.ac") $ need [path "configure"] run GhcCabal cabalArgs when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs - let pkgDataFile = path dist "package-data.mk" - pkgData <- lines <$> liftIO (readFile pkgDataFile) - length pkgData `seq` writeFileLines pkgDataFile $ map (replaceIf isSlash '_') $ filter ('$' `notElem`) pkgData + postProcessPackageData $ path dist "package-data.mk" where cabalArgs, ghcPkgArgs :: Args cabalArgs = mconcat diff --git a/src/Util.hs b/src/Util.hs index 8afd6cb..b8a38f4 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,9 +1,11 @@ module Util ( module Data.Char, isSlash, - replaceIf, replaceEq + replaceIf, replaceEq, + postProcessPackageData ) where +import Base import Data.Char isSlash :: Char -> Bool @@ -14,3 +16,11 @@ replaceIf p to = map (\from -> if p from then to else from) replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) + +-- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: +-- 1) Drop lines containing '$' +-- 2) Replace '/' and '\' with '_' +postProcessPackageData :: FilePath -> Action () +postProcessPackageData file = do + pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) + length pkgData `seq` writeFileLines file $ map (replaceIf isSlash '_') pkgData From git at git.haskell.org Thu Oct 26 23:00:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add splitArgs function to Base.hs. (4dd9560) Message-ID: <20171026230034.7FED43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4dd9560e34ded015140a7d5d4d2e22d27e19abb2/ghc >--------------------------------------------------------------- commit 4dd9560e34ded015140a7d5d4d2e22d27e19abb2 Author: Andrey Mokhov Date: Tue Dec 30 17:03:10 2014 +0000 Add splitArgs function to Base.hs. >--------------------------------------------------------------- 4dd9560e34ded015140a7d5d4d2e22d27e19abb2 src/Base.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 24943e4..a0f4303 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -8,7 +8,7 @@ module Base ( module Data.List, Stage (..), Args, arg, - joinArgs, joinArgsWithSpaces, + joinArgs, joinArgsWithSpaces, splitArgs, filterOut ) where @@ -40,5 +40,8 @@ joinArgsWithSpaces = intercalateArgs " " joinArgs :: Args -> Args joinArgs = intercalateArgs "" +splitArgs :: Args -> Args +splitArgs = fmap (concatMap words) + filterOut :: Args -> [String] -> Args filterOut args list = filter (`notElem` list) <$> args From git at git.haskell.org Thu Oct 26 23:00:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add src-hc-opts to configuration files. (5adb8aa) Message-ID: <20171026230037.EEF233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5adb8aa730e9ae9649924f7f8ea59b0e5163876d/ghc >--------------------------------------------------------------- commit 5adb8aa730e9ae9649924f7f8ea59b0e5163876d Author: Andrey Mokhov Date: Tue Dec 30 17:04:28 2014 +0000 Add src-hc-opts to configuration files. >--------------------------------------------------------------- 5adb8aa730e9ae9649924f7f8ea59b0e5163876d cfg/default.config.in | 2 ++ 1 file changed, 2 insertions(+) diff --git a/cfg/default.config.in b/cfg/default.config.in index d3617f4..1a28981 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -61,6 +61,8 @@ conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ +src-hc-opts = -H32m -O + # Include and library directories: #================================= From git at git.haskell.org Thu Oct 26 23:00:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Export wayHcOpts. (980d486) Message-ID: <20171026230041.73D4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/980d48665a5bd7dfb275d403628e34b140bd2567/ghc >--------------------------------------------------------------- commit 980d48665a5bd7dfb275d403628e34b140bd2567 Author: Andrey Mokhov Date: Tue Dec 30 17:06:00 2014 +0000 Export wayHcOpts. >--------------------------------------------------------------- 980d48665a5bd7dfb275d403628e34b140bd2567 src/Ways.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Ways.hs b/src/Ways.hs index 91cbd4f..a0e886a 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -12,6 +12,7 @@ module Ways ( threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic, + wayHcOpts, hisuf, osuf, hcsuf ) where From git at git.haskell.org Thu Oct 26 23:00:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for src-hc-opts configuration option. (9007c90) Message-ID: <20171026230044.EC3923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9007c90cce429df3f0f60737d4a93a127f5e5274/ghc >--------------------------------------------------------------- commit 9007c90cce429df3f0f60737d4a93a127f5e5274 Author: Andrey Mokhov Date: Tue Dec 30 17:06:52 2014 +0000 Add support for src-hc-opts configuration option. >--------------------------------------------------------------- 9007c90cce429df3f0f60737d4a93a127f5e5274 src/Oracles.hs | 2 ++ src/Package.hs | 50 ++++++++++++++++++++++++++------------------------ 2 files changed, 28 insertions(+), 24 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 75439fb..ff4bd95 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -101,6 +101,7 @@ run builder args = do data Option = TargetOS | TargetArch | TargetPlatformFull | ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage | IconvIncludeDirs | IconvLibDirs | GmpIncludeDirs | GmpLibDirs + | SrcHcOpts | HostOsCpp | Root option :: Option -> Action String @@ -125,6 +126,7 @@ option opt = askConfig $ case opt of IconvLibDirs -> "iconv-lib-dirs" GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" + SrcHcOpts -> "src-hc-opts" HostOsCpp -> "host-os-cpp" argOption :: Option -> Args diff --git a/src/Package.hs b/src/Package.hs index 24ef85d..9e60a24 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -163,6 +163,29 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs +-- $1_$2_$3_MOST_DIR_HC_OPTS = \ +-- $$($1_$2_$3_MOST_HC_OPTS) \ +-- -odir $1/$2/build -hidir $1/$2/build -stubdir $1/$2/build + +-- # Some of the Haskell files (e.g. utils/hsc2hs/Main.hs) (directly or +-- # indirectly) include the generated includes files. +-- $$($1_$2_depfile_haskell) : $$(includes_H_CONFIG) $$(includes_H_PLATFORM) +-- +-- $$($1_$2_depfile_haskell) : $$($1_$2_HS_SRCS) $$($1_$2_HS_BOOT_SRCS) $$$$($1_$2_HC_MK_DEPEND_DEP) | $$$$(dir $$$$@)/. +-- $$(call removeFiles,$$@.tmp) +-- ifneq "$$($1_$2_HS_SRCS)" "" +-- "$$($1_$2_HC_MK_DEPEND)" -M \ +-- $$($1_$2_$$(firstword $$($1_$2_WAYS))_MOST_DIR_HC_OPTS) \ +-- $$($1_$2_MKDEPENDHS_FLAGS) \ +-- $$($1_$2_HS_SRCS) +-- endif +-- echo "$1_$2_depfile_haskell_EXISTS = YES" >> $$@.tmp +-- ifneq "$$($1_$2_SLASH_MODS)" "" +-- for dir in $$(sort $$(foreach mod,$$($1_$2_SLASH_MODS),$1/$2/build/$$(dir $$(mod)))); do \ +-- if test ! -d $$$$dir; then mkdir -p $$$$dir; fi \ +-- done +-- endif + -- $1_$2_$3_MOST_HC_OPTS = \ -- $$(WAY_$3_HC_OPTS) \ -- $$(CONF_HC_OPTS) \ @@ -190,31 +213,8 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) - --- $1_$2_$3_MOST_DIR_HC_OPTS = \ --- $$($1_$2_$3_MOST_HC_OPTS) \ --- -odir $1/$2/build -hidir $1/$2/build -stubdir $1/$2/build - --- # Some of the Haskell files (e.g. utils/hsc2hs/Main.hs) (directly or --- # indirectly) include the generated includes files. --- $$($1_$2_depfile_haskell) : $$(includes_H_CONFIG) $$(includes_H_PLATFORM) --- --- $$($1_$2_depfile_haskell) : $$($1_$2_HS_SRCS) $$($1_$2_HS_BOOT_SRCS) $$$$($1_$2_HC_MK_DEPEND_DEP) | $$$$(dir $$$$@)/. --- $$(call removeFiles,$$@.tmp) --- ifneq "$$($1_$2_HS_SRCS)" "" --- "$$($1_$2_HC_MK_DEPEND)" -M \ --- $$($1_$2_$$(firstword $$($1_$2_WAYS))_MOST_DIR_HC_OPTS) \ --- $$($1_$2_MKDEPENDHS_FLAGS) \ --- $$($1_$2_HS_SRCS) --- endif --- echo "$1_$2_depfile_haskell_EXISTS = YES" >> $$@.tmp --- ifneq "$$($1_$2_SLASH_MODS)" "" --- for dir in $$(sort $$(foreach mod,$$($1_$2_SLASH_MODS),$1/$2/build/$$(dir $$(mod)))); do \ --- if test ! -d $$$$dir; then mkdir -p $$$$dir; fi \ --- done --- endif - -- TODO: double-check that ignoring $1_$2_HS_SRC_DIRS is safe +-- Options CONF_HC_OPTS and buildPackageDeps :: Package -> TodoItem -> Rules () buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist @@ -229,6 +229,8 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = return $ path ++ "//" ++ start ++ end run (Ghc stage) $ mconcat [ arg ["-M"] + , wayHcOpts vanilla -- TODO: is this needed? shall we run GHC -M multiple times? + , splitArgs $ argOption SrcHcOpts , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] , arg [unwords src] ] From git at git.haskell.org Thu Oct 26 23:00:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix postProcessPackageData. (bf9edba) Message-ID: <20171026230048.746743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf9edba4364ffc59eb13b6501c11560b71b6e620/ghc >--------------------------------------------------------------- commit bf9edba4364ffc59eb13b6501c11560b71b6e620 Author: Andrey Mokhov Date: Tue Dec 30 17:32:37 2014 +0000 Fix postProcessPackageData. >--------------------------------------------------------------- bf9edba4364ffc59eb13b6501c11560b71b6e620 src/Util.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index b8a38f4..846f547 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -19,8 +19,12 @@ replaceEq from = replaceIf (== from) -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' --- 2) Replace '/' and '\' with '_' +-- 2) Replace '/' and '\' with '_' before '=' postProcessPackageData :: FilePath -> Action () postProcessPackageData file = do pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map (replaceIf isSlash '_') pkgData + length pkgData `seq` writeFileLines file $ map processLine pkgData + where + processLine line = replaceIf isSlash '_' prefix ++ suffix + where + (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:00:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add supports-package-key to configuration files. (96dec4a) Message-ID: <20171026230052.0E6DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/96dec4ae3f1dc8dde6647ecc87a62b87a24589ee/ghc >--------------------------------------------------------------- commit 96dec4ae3f1dc8dde6647ecc87a62b87a24589ee Author: Andrey Mokhov Date: Tue Dec 30 19:34:26 2014 +0000 Add supports-package-key to configuration files. >--------------------------------------------------------------- 96dec4ae3f1dc8dde6647ecc87a62b87a24589ee cfg/default.config.in | 1 + 1 file changed, 1 insertion(+) diff --git a/cfg/default.config.in b/cfg/default.config.in index 1a28981..50c3937 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -30,6 +30,7 @@ gcc-lt-46 = @GccLT46@ lax-dependencies = NO dynamic-ghc-programs = NO +supports-package-key = @SUPPORTS_PACKAGE_KEY@ # Information about host and target systems: #=========================================== From git at git.haskell.org Thu Oct 26 23:00:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement more arguments for ghc -M. (21bfb81) Message-ID: <20171026230055.7C0923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21bfb816a7be0bcd0ef72d562001d5948998565a/ghc >--------------------------------------------------------------- commit 21bfb816a7be0bcd0ef72d562001d5948998565a Author: Andrey Mokhov Date: Tue Dec 30 19:35:13 2014 +0000 Implement more arguments for ghc -M. >--------------------------------------------------------------- 21bfb816a7be0bcd0ef72d562001d5948998565a src/Oracles.hs | 24 +++++++++++++----------- src/Package.hs | 28 ++++++++++++++++++++++------ 2 files changed, 35 insertions(+), 17 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index ff4bd95..9b63c4f 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -136,7 +136,7 @@ argOption opt = do data Flag = LaxDeps | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs | GccIsClang | GccLt46 | CrossCompiling | Validating | PlatformSupportsSharedLibs - | WindowsHost + | WindowsHost | SupportsPackageKey test :: Flag -> Action Bool test GhcWithInterpreter = do @@ -161,12 +161,13 @@ test WindowsHost = do test flag = do (key, defaultValue) <- return $ case flag of - LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file - DynamicGhcPrograms -> ("dynamic-ghc-programs", False) - GccIsClang -> ("gcc-is-clang" , False) - GccLt46 -> ("gcc-lt-46" , False) - CrossCompiling -> ("cross-compiling" , False) - Validating -> ("validating" , False) + LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file + DynamicGhcPrograms -> ("dynamic-ghc-programs" , False) + GccIsClang -> ("gcc-is-clang" , False) + GccLt46 -> ("gcc-lt-46" , False) + CrossCompiling -> ("cross-compiling" , False) + Validating -> ("validating" , False) + SupportsPackageKey -> ("supports-package-key" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ do putLoud $ "\nFlag '" -- TODO: Give the warning *only once* per key @@ -264,13 +265,14 @@ packagaDataOptionWithDefault file key defaultAction = do Just value -> return value Nothing -> defaultAction -data PackageDataKey = Modules | SrcDirs +data PackageDataKey = Modules | SrcDirs | PackageKey packagaDataOption :: FilePath -> PackageDataKey -> Action String packagaDataOption file key = do - let keyName = replaceIf isSlash '_' $ takeDirectory file ++ case key of - Modules -> "_MODULES" - SrcDirs -> "_HS_SRC_DIRS" + let keyName = replaceIf isSlash '_' $ takeDirectory file ++ "_" ++ case key of + Modules -> "MODULES" + SrcDirs -> "HS_SRC_DIRS" -- TODO: add "." as a default? + PackageKey -> "PACKAGE_KEY" packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." diff --git a/src/Package.hs b/src/Package.hs index 9e60a24..ba77bdf 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -161,7 +161,6 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = , arg [path dist "inplace-pkg-config"] ] --- "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs -- $1_$2_$3_MOST_DIR_HC_OPTS = \ -- $$($1_$2_$3_MOST_HC_OPTS) \ @@ -186,6 +185,8 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- done -- endif +-- "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs + -- $1_$2_$3_MOST_HC_OPTS = \ -- $$(WAY_$3_HC_OPTS) \ -- $$(CONF_HC_OPTS) \ @@ -213,24 +214,39 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) --- TODO: double-check that ignoring $1_$2_HS_SRC_DIRS is safe --- Options CONF_HC_OPTS and +-- TODO: double-check that ignoring SrcDirs ($1_$2_HS_SRC_DIRS) is safe +-- TODO: add $1_HC_OPTS +-- TODO: check that the package is not a program ($1_$2_PROG == "") +-- TODO: handle empty $1_PACKAGE +-- Option CONF_HC_OPTS is skipped buildPackageDeps :: Package -> TodoItem -> Rules () buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist in (buildDir "build" name <.> "m") %> \out -> do - let pkgData = buildDir "package-data.mk" - autogen = dist "build" "autogen" - mods <- words <$> packagaDataOption pkgData Modules + let pkgData = buildDir "package-data.mk" + autogen = dist "build" "autogen" + mods <- words <$> packagaDataOption pkgData Modules + srcDirs <- words <$> packagaDataOption pkgData SrcDirs src <- getDirectoryFiles "" $ do start <- map (replaceEq '.' '/') mods end <- [".hs", ".lhs"] return $ path ++ "//" ++ start ++ end + packageKey <- packagaDataOption pkgData PackageKey run (Ghc stage) $ mconcat [ arg ["-M"] , wayHcOpts vanilla -- TODO: is this needed? shall we run GHC -M multiple times? , splitArgs $ argOption SrcHcOpts + , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] + , when (not SupportsPackageKey && stage == Stage0) $ arg ["-package-name"] + , when ( SupportsPackageKey || stage /= Stage0) $ arg ["-this-package-key"] + , arg [packageKey] + , arg ["-hide-all-packages"] + , arg $ map (\d -> "-i" ++ path ++ "/" ++ d) srcDirs + , arg $ do + prefix <- ["-i", "-I"] + suffix <- ["build", "build/autogen"] + return $ prefix ++ path dist suffix , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] , arg [unwords src] ] From git at git.haskell.org Thu Oct 26 23:00:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:00:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace isSlash with standard isPathSeparator. (212e91f) Message-ID: <20171026230058.F319A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/212e91f1a18f71e467ca68e929294b943c2cf171/ghc >--------------------------------------------------------------- commit 212e91f1a18f71e467ca68e929294b943c2cf171 Author: Andrey Mokhov Date: Wed Dec 31 03:50:59 2014 +0000 Replace isSlash with standard isPathSeparator. >--------------------------------------------------------------- 212e91f1a18f71e467ca68e929294b943c2cf171 src/Util.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index 846f547..af23f27 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,5 @@ module Util ( module Data.Char, - isSlash, replaceIf, replaceEq, postProcessPackageData ) where @@ -8,9 +7,6 @@ module Util ( import Base import Data.Char -isSlash :: Char -> Bool -isSlash = (`elem` ['/', '\\']) - replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -25,6 +21,6 @@ postProcessPackageData file = do pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) length pkgData `seq` writeFileLines file $ map processLine pkgData where - processLine line = replaceIf isSlash '_' prefix ++ suffix + processLine line = replaceIf isPathSeparator '_' prefix ++ suffix where (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:01:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add replaceSeparators to Util.hs. (d043ef5) Message-ID: <20171026230102.6D3513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d043ef595a7ee877d8c9659b27e592d361a110c6/ghc >--------------------------------------------------------------- commit d043ef595a7ee877d8c9659b27e592d361a110c6 Author: Andrey Mokhov Date: Wed Dec 31 03:59:10 2014 +0000 Add replaceSeparators to Util.hs. >--------------------------------------------------------------- d043ef595a7ee877d8c9659b27e592d361a110c6 src/Util.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index af23f27..68ed2e5 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,6 @@ module Util ( module Data.Char, - replaceIf, replaceEq, + replaceIf, replaceEq, replaceSeparators, postProcessPackageData ) where @@ -13,6 +13,9 @@ replaceIf p to = map (\from -> if p from then to else from) replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) +replaceSeparators :: String -> String +replaceSeparators = replaceIf isPathSeparator + -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- 2) Replace '/' and '\' with '_' before '=' @@ -21,6 +24,6 @@ postProcessPackageData file = do pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) length pkgData `seq` writeFileLines file $ map processLine pkgData where - processLine line = replaceIf isPathSeparator '_' prefix ++ suffix + processLine line = replaceSeparators '_' prefix ++ suffix where (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:01:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix replaceSeparators in Util.hs. (34696c1) Message-ID: <20171026230105.D5B123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34696c113fedaa2081b179dd4591d6eec8a510e4/ghc >--------------------------------------------------------------- commit 34696c113fedaa2081b179dd4591d6eec8a510e4 Author: Andrey Mokhov Date: Wed Dec 31 04:00:18 2014 +0000 Fix replaceSeparators in Util.hs. >--------------------------------------------------------------- 34696c113fedaa2081b179dd4591d6eec8a510e4 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 68ed2e5..d7e98bd 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -13,7 +13,7 @@ replaceIf p to = map (\from -> if p from then to else from) replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) -replaceSeparators :: String -> String +replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: From git at git.haskell.org Thu Oct 26 23:01:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Complete first working version of buildPackageDeps rule. (d869302) Message-ID: <20171026230109.453803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d869302fcad9a124aa65c6075114a6f1f9c7c61d/ghc >--------------------------------------------------------------- commit d869302fcad9a124aa65c6075114a6f1f9c7c61d Author: Andrey Mokhov Date: Wed Dec 31 04:43:53 2014 +0000 Complete first working version of buildPackageDeps rule. >--------------------------------------------------------------- d869302fcad9a124aa65c6075114a6f1f9c7c61d src/Oracles.hs | 18 +++++++++++------ src/Package.hs | 62 ++++++++++++++++++++++++++++++++++------------------------ 2 files changed, 48 insertions(+), 32 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 9b63c4f..4f4cd78 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -265,16 +265,22 @@ packagaDataOptionWithDefault file key defaultAction = do Just value -> return value Nothing -> defaultAction -data PackageDataKey = Modules | SrcDirs | PackageKey +data PackageDataKey = Modules | SrcDirs | PackageKey | IncludeDirs | Deps | DepKeys + deriving Show packagaDataOption :: FilePath -> PackageDataKey -> Action String packagaDataOption file key = do - let keyName = replaceIf isSlash '_' $ takeDirectory file ++ "_" ++ case key of - Modules -> "MODULES" - SrcDirs -> "HS_SRC_DIRS" -- TODO: add "." as a default? - PackageKey -> "PACKAGE_KEY" - packagaDataOptionWithDefault file keyName $ + let (keyName, ifEmpty) = case key of + Modules -> ("MODULES" , "" ) + SrcDirs -> ("HS_SRC_DIRS" , ".") + PackageKey -> ("PACKAGE_KEY" , "" ) + IncludeDirs -> ("INCLUDE_DIRS", ".") + Deps -> ("DEPS" , "" ) + DepKeys -> ("DEP_KEYS" , "" ) + keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName + res <- packagaDataOptionWithDefault file keyFullName $ error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." + return $ if res == "" then ifEmpty else res oracleRules :: Rules () oracleRules = do diff --git a/src/Package.hs b/src/Package.hs index ba77bdf..98558e9 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -214,42 +214,52 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) --- TODO: double-check that ignoring SrcDirs ($1_$2_HS_SRC_DIRS) is safe +-- TODO: make sure SrcDirs ($1_$2_HS_SRC_DIRS) is not empty ('.' by default) -- TODO: add $1_HC_OPTS -- TODO: check that the package is not a program ($1_$2_PROG == "") --- TODO: handle empty $1_PACKAGE +-- TODO: handle empty $1_PACKAGE (can it be empty?) +-- TODO: $1_$2_INCLUDE appears to be not set. Safe to skip? -- Option CONF_HC_OPTS is skipped buildPackageDeps :: Package -> TodoItem -> Rules () buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist in (buildDir "build" name <.> "m") %> \out -> do - let pkgData = buildDir "package-data.mk" - autogen = dist "build" "autogen" - mods <- words <$> packagaDataOption pkgData Modules - srcDirs <- words <$> packagaDataOption pkgData SrcDirs - src <- getDirectoryFiles "" $ do - start <- map (replaceEq '.' '/') mods - end <- [".hs", ".lhs"] - return $ path ++ "//" ++ start ++ end + let pkgData = buildDir "package-data.mk" + usePackageKey <- SupportsPackageKey || stage /= Stage0 -- TODO: check reasoning (distdir-way-opts) + [mods, srcDirs, includeDirs, deps, depKeys] <- + mapM ((fmap words) . (packagaDataOption pkgData)) + [Modules, SrcDirs, IncludeDirs, Deps, DepKeys] + srcs <- getDirectoryFiles "" $ do + dir <- srcDirs + modPath <- map (replaceEq '.' pathSeparator) mods + extension <- ["hs", "lhs"] + return $ path dir modPath <.> extension packageKey <- packagaDataOption pkgData PackageKey run (Ghc stage) $ mconcat - [ arg ["-M"] - , wayHcOpts vanilla -- TODO: is this needed? shall we run GHC -M multiple times? - , splitArgs $ argOption SrcHcOpts - , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] - , when (not SupportsPackageKey && stage == Stage0) $ arg ["-package-name"] - , when ( SupportsPackageKey || stage /= Stage0) $ arg ["-this-package-key"] - , arg [packageKey] - , arg ["-hide-all-packages"] - , arg $ map (\d -> "-i" ++ path ++ "/" ++ d) srcDirs - , arg $ do - prefix <- ["-i", "-I"] - suffix <- ["build", "build/autogen"] - return $ prefix ++ path dist suffix - , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] - , arg [unwords src] - ] + [ arg ["-M"] + , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? + , splitArgs $ argOption SrcHcOpts + , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] + , arg [if usePackageKey then "-this-package-key" else "-package-name"] + , arg [packageKey] -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg ["-hide-all-packages"] + , arg ["-i"] -- resets the search path to nothing; TODO: check if really needed + , arg $ map (\d -> "-i" ++ path d) srcDirs + , arg $ do + prefix <- ["-i", "-I"] -- 'import' and '#include' search paths + suffix <- ["build", "build/autogen"] + return $ prefix ++ buildDir suffix + , arg $ map (\d -> "-I" ++ path d) $ filter isRelative includeDirs + , arg $ map (\d -> "-I" ++ d) $ filter isAbsolute includeDirs + , arg ["-optP-include"] + , arg ["-optP" ++ buildDir "build/autogen/cabal_macros.h"] + , if usePackageKey + then arg $ concatMap (\d -> ["-package-key", d]) depKeys + else arg $ concatMap (\d -> ["-package" , d]) deps + , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] + , arg $ map normalise srcs + ] -- $1_$2_MKDEPENDHS_FLAGS = -dep-makefile $$($1_$2_depfile_haskell).tmp $$(foreach way,$$($1_$2_WAYS),-dep-suffix "$$(-- patsubst %o,%,$$($$(way)_osuf))") -- $1_$2_MKDEPENDHS_FLAGS += -include-pkg-deps From git at git.haskell.org Thu Oct 26 23:01:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split Oracles.hs module into logical parts. (a2c0e5d) Message-ID: <20171026230112.A830C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123/ghc >--------------------------------------------------------------- commit a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123 Author: Andrey Mokhov Date: Thu Jan 1 22:26:03 2015 +0000 Split Oracles.hs module into logical parts. >--------------------------------------------------------------- a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123 src/Oracles/Base.hs | 26 ++++++++++++ src/Oracles/Builder.hs | 93 ++++++++++++++++++++++++++++++++++++++++ src/Oracles/Flag.hs | 103 +++++++++++++++++++++++++++++++++++++++++++++ src/Oracles/Option.hs | 57 +++++++++++++++++++++++++ src/Oracles/PackageData.hs | 38 +++++++++++++++++ 5 files changed, 317 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 a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123 From git at git.haskell.org Thu Oct 26 23:01:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports. (c5f7958) Message-ID: <20171026230116.1BDA03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5f79581110633e6aeb8f8bb13bcd6fa3e187f05/ghc >--------------------------------------------------------------- commit c5f79581110633e6aeb8f8bb13bcd6fa3e187f05 Author: Andrey Mokhov Date: Thu Jan 1 22:29:39 2015 +0000 Refactor imports. >--------------------------------------------------------------- c5f79581110633e6aeb8f8bb13bcd6fa3e187f05 src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a0f4303..29c1340 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,9 +12,9 @@ module Base ( filterOut ) where -import Development.Shake hiding ((*>)) +import Development.Shake import Development.Shake.FilePath -import Control.Applicative +import Control.Applicative hiding ((*>)) import Data.Monoid import Data.List From git at git.haskell.org Thu Oct 26 23:01:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move most code into src/Oracles/ submodules. (8228615) Message-ID: <20171026230119.9C5E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82286153d41e61c9e5c06488504e64321993f0df/ghc >--------------------------------------------------------------- commit 82286153d41e61c9e5c06488504e64321993f0df Author: Andrey Mokhov Date: Thu Jan 1 22:31:45 2015 +0000 Move most code into src/Oracles/ submodules. >--------------------------------------------------------------- 82286153d41e61c9e5c06488504e64321993f0df src/Oracles.hs | 284 +++------------------------------------------------------ 1 file changed, 11 insertions(+), 273 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 82286153d41e61c9e5c06488504e64321993f0df From git at git.haskell.org Thu Oct 26 23:01:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change computed configuration flags into Conditions. (9d8e3a3) Message-ID: <20171026230123.118E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d8e3a33b4cc3aaf312dc068be9810043c40ff91/ghc >--------------------------------------------------------------- commit 9d8e3a33b4cc3aaf312dc068be9810043c40ff91 Author: Andrey Mokhov Date: Thu Jan 1 22:35:50 2015 +0000 Change computed configuration flags into Conditions. >--------------------------------------------------------------- 9d8e3a33b4cc3aaf312dc068be9810043c40ff91 src/Package.hs | 4 ++-- src/Ways.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 98558e9..4154dc5 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -78,7 +78,7 @@ libraryArgs ways = in mconcat [ argEnable False "library-for-ghci" -- TODO: why always disable? , argEnable (vanilla `elem` ways) "library-vanilla" - , when (GhcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) $ + , when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) $ argEnable True "library-for-ghci" , argEnable (profiling `elem` ways) "library-profiling" , argEnable (dynamic `elem` ways) "shared" @@ -143,7 +143,7 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = , customConfArgs settings , libraryArgs =<< ways settings - , when HsColourSrcs $ with HsColour + , when hsColourSrcs $ with HsColour , configureArgs stage settings , when (stage == Stage0) $ bootPkgConstraints diff --git a/src/Ways.hs b/src/Ways.hs index a0e886a..0a4284a 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -65,7 +65,7 @@ allWays = [vanilla, profiling, logging, parallel, granSim, defaultWays :: Stage -> Action [Way] defaultWays stage = do - sharedLibs <- test PlatformSupportsSharedLibs + sharedLibs <- platformSupportsSharedLibs return $ [vanilla] ++ [profiling | stage /= Stage0] ++ [dynamic | sharedLibs ] From git at git.haskell.org Thu Oct 26 23:01:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant GHC extensions. (a7cc473) Message-ID: <20171026230126.92EAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7cc473154bf0fcc311bb070381f28c444d4de1b/ghc >--------------------------------------------------------------- commit a7cc473154bf0fcc311bb070381f28c444d4de1b Author: Andrey Mokhov Date: Thu Jan 1 22:56:13 2015 +0000 Remove redundant GHC extensions. >--------------------------------------------------------------- a7cc473154bf0fcc311bb070381f28c444d4de1b src/Base.hs | 2 -- src/Oracles.hs | 3 --- src/Oracles/Base.hs | 3 +-- src/Oracles/Builder.hs | 3 +-- src/Oracles/Flag.hs | 3 +-- src/Oracles/Option.hs | 3 --- src/Oracles/PackageData.hs | 3 +-- 7 files changed, 4 insertions(+), 16 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 29c1340..b95cf14 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE FlexibleInstances #-} - module Base ( module Development.Shake, module Development.Shake.FilePath, diff --git a/src/Oracles.hs b/src/Oracles.hs index c9c9601..093f1b8 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,6 +1,3 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, NoImplicitPrelude #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} - module Oracles ( module Oracles.Base, module Oracles.Flag, diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 1e3dec2..1a9cf3e 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.Base ( ConfigKey (..), diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 3d3a0e9..6c37ec0 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, NoImplicitPrelude #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE NoImplicitPrelude #-} module Oracles.Builder ( Builder (..), diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 9245fb2..c8ddc8e 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE TypeFamilies, FlexibleInstances, MultiParamTypeClasses #-} module Oracles.Flag ( module Control.Monad, diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 72d166b..3661b71 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,6 +1,3 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} - module Oracles.Option ( Option (..), option, argOption, diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 3abd7a2..831fec9 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( PackageDataPair (..), From git at git.haskell.org Thu Oct 26 23:01:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Condition to Base.hs. (4166bc7) Message-ID: <20171026230130.7AF4C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4166bc732f9f62a34e0e5597686024e995d98691/ghc >--------------------------------------------------------------- commit 4166bc732f9f62a34e0e5597686024e995d98691 Author: Andrey Mokhov Date: Thu Jan 1 23:13:50 2015 +0000 Move Condition to Base.hs. >--------------------------------------------------------------- 4166bc732f9f62a34e0e5597686024e995d98691 src/Base.hs | 3 +++ src/Oracles/Base.hs | 5 +---- src/Oracles/Flag.hs | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index b95cf14..0a88146 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -6,6 +6,7 @@ module Base ( module Data.List, Stage (..), Args, arg, + Condition (..), joinArgs, joinArgsWithSpaces, splitArgs, filterOut ) where @@ -20,6 +21,8 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) type Args = Action [String] +type Condition = Action Bool + instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 1a9cf3e..f9e5c73 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -2,15 +2,12 @@ module Oracles.Base ( ConfigKey (..), - askConfigWithDefault, askConfig, - Condition (..) + askConfigWithDefault, askConfig ) where import Base import Development.Shake.Classes -type Condition = Action Bool - newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) askConfigWithDefault :: String -> Action String -> Action String diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index c8ddc8e..1958c07 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -4,7 +4,7 @@ module Oracles.Flag ( module Control.Monad, module Prelude, Flag (..), - Condition, test, when, unless, not, (&&), (||) + test, when, unless, not, (&&), (||) ) where import Control.Monad hiding (when, unless) From git at git.haskell.org Thu Oct 26 23:01:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ShowAction typeclass. (64b16d7) Message-ID: <20171026230134.1F3F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64b16d796dc5aa8a889d41eeb08cbead19cba14d/ghc >--------------------------------------------------------------- commit 64b16d796dc5aa8a889d41eeb08cbead19cba14d Author: Andrey Mokhov Date: Thu Jan 1 23:56:12 2015 +0000 Add ShowAction typeclass. >--------------------------------------------------------------- 64b16d796dc5aa8a889d41eeb08cbead19cba14d src/Base.hs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 0a88146..77c2858 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-} + module Base ( module Development.Shake, module Development.Shake.FilePath, @@ -27,8 +29,14 @@ instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q -arg :: [String] -> Args -arg = return +class ShowAction a where + showAction :: a -> Action String + +instance ShowAction String where + showAction = return + +arg :: ShowAction a => [a] -> Args +arg = mapM showAction intercalateArgs :: String -> Args -> Args intercalateArgs s args = do From git at git.haskell.org Thu Oct 26 23:01:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace path with instance ShowAction Builder. (37de3d5) Message-ID: <20171026230137.AB44D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37de3d57c7e35237dea4f11c2cb2016eedeb49c5/ghc >--------------------------------------------------------------- commit 37de3d57c7e35237dea4f11c2cb2016eedeb49c5 Author: Andrey Mokhov Date: Fri Jan 2 02:34:56 2015 +0000 Replace path with instance ShowAction Builder. >--------------------------------------------------------------- 37de3d57c7e35237dea4f11c2cb2016eedeb49c5 src/Oracles/Builder.hs | 73 +++++++++++++++++++++++--------------------------- 1 file changed, 34 insertions(+), 39 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 6c37ec0..3da6f9a 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,7 @@ module Oracles.Builder ( Builder (..), - path, with, run, argPath, + with, run, hsColourSrcs ) where @@ -14,39 +14,34 @@ import Oracles.Option data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage -path :: Builder -> Action FilePath -path builder = do - let key = case builder of - Ar -> "ar" - Ld -> "ld" - Gcc -> "gcc" - Alex -> "alex" - Happy -> "happy" - HsColour -> "hscolour" - GhcCabal -> "ghc-cabal" - Ghc Stage0 -> "system-ghc" -- Ghc Stage0 is the bootstrapping compiler - Ghc Stage1 -> "ghc-stage1" -- Ghc StageN, N > 0, is the one built on stage (N - 1) - Ghc Stage2 -> "ghc-stage2" - Ghc Stage3 -> "ghc-stage3" - GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg - GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) - cfgPath <- askConfigWithDefault key $ - error $ "\nCannot find path to '" - ++ key - ++ "' in configuration files." - let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" - windows <- windowsHost - if (windows && "/" `isPrefixOf` cfgPathExe) - then do - Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] - return $ dropWhileEnd isSpace out ++ drop 1 cfgPathExe - else - return cfgPathExe - -argPath :: Builder -> Args -argPath builder = do - path <- path builder - arg [path] +instance ShowAction Builder where + showAction builder = do + let key = case builder of + Ar -> "ar" + Ld -> "ld" + Gcc -> "gcc" + Alex -> "alex" + Happy -> "happy" + HsColour -> "hscolour" + GhcCabal -> "ghc-cabal" + Ghc Stage0 -> "system-ghc" -- Ghc Stage0 is the bootstrapping compiler + Ghc Stage1 -> "ghc-stage1" -- Ghc StageN, N > 0, is the one built on stage (N - 1) + Ghc Stage2 -> "ghc-stage2" + Ghc Stage3 -> "ghc-stage3" + GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg + GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) + cfgPath <- askConfigWithDefault key $ + error $ "\nCannot find path to '" + ++ key + ++ "' in configuration files." + let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" + windows <- windowsHost + if (windows && "/" `isPrefixOf` cfgPathExe) + then do + Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] + return $ dropWhileEnd isSpace out ++ drop 1 cfgPathExe + else + return cfgPathExe -- When LaxDeps flag is set (by adding 'lax-dependencies = YES' to user.config), -- dependencies on the GHC executable are turned into order-only dependencies to @@ -55,12 +50,12 @@ argPath builder = do -- the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - target <- path ghc + target <- showAction ghc laxDeps <- test LaxDeps if laxDeps then orderOnly [target] else need [target] needBuilder builder = do - target <- path builder + target <- showAction builder need [target] -- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder @@ -75,18 +70,18 @@ with builder = do Happy -> "--with-happy=" GhcPkg _ -> "--with-ghc-pkg=" HsColour -> "--with-hscolour=" - suffix <- path builder + suffix <- showAction builder needBuilder builder return [prefix ++ suffix] run :: Builder -> Args -> Action () run builder args = do needBuilder builder - exe <- path builder + exe <- showAction builder args' <- args cmd [exe :: FilePath] args' hsColourSrcs :: Condition hsColourSrcs = do - hscolour <- path HsColour + hscolour <- showAction HsColour return $ hscolour /= "" From git at git.haskell.org Thu Oct 26 23:01:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace option with instance ShowAction Option. (1495a2d) Message-ID: <20171026230141.5B14D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1495a2d66f0a9cb8082285b68c1e42cf954eb6b8/ghc >--------------------------------------------------------------- commit 1495a2d66f0a9cb8082285b68c1e42cf954eb6b8 Author: Andrey Mokhov Date: Fri Jan 2 02:43:40 2015 +0000 Replace option with instance ShowAction Option. >--------------------------------------------------------------- 1495a2d66f0a9cb8082285b68c1e42cf954eb6b8 src/Oracles/Option.hs | 44 +++++++++++++++++++------------------------- 1 file changed, 19 insertions(+), 25 deletions(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 3661b71..899aec7 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,6 +1,5 @@ module Oracles.Option ( Option (..), - option, argOption, ghcWithInterpreter, platformSupportsSharedLibs, windowsHost ) where @@ -13,31 +12,26 @@ data Option = TargetOS | TargetArch | TargetPlatformFull | SrcHcOpts | HostOsCpp -option :: Option -> Action String -option opt = askConfig $ case opt of - TargetOS -> "target-os" - TargetArch -> "target-arch" - TargetPlatformFull -> "target-platform-full" - ConfCcArgs stage -> "conf-cc-args-stage-" ++ (show . fromEnum) stage - ConfCppArgs stage -> "conf-cpp-args-stage-" ++ (show . fromEnum) stage - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ (show . fromEnum) stage - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ (show . fromEnum) stage - IconvIncludeDirs -> "iconv-include-dirs" - IconvLibDirs -> "iconv-lib-dirs" - GmpIncludeDirs -> "gmp-include-dirs" - GmpLibDirs -> "gmp-lib-dirs" - SrcHcOpts -> "src-hc-opts" - HostOsCpp -> "host-os-cpp" - -argOption :: Option -> Args -argOption opt = do - opt' <- option opt - arg [opt'] +instance ShowAction Option where + showAction opt = askConfig $ case opt of + TargetOS -> "target-os" + TargetArch -> "target-arch" + TargetPlatformFull -> "target-platform-full" + ConfCcArgs stage -> "conf-cc-args-stage-" ++ (show . fromEnum) stage + ConfCppArgs stage -> "conf-cpp-args-stage-" ++ (show . fromEnum) stage + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ (show . fromEnum) stage + ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ (show . fromEnum) stage + IconvIncludeDirs -> "iconv-include-dirs" + IconvLibDirs -> "iconv-lib-dirs" + GmpIncludeDirs -> "gmp-include-dirs" + GmpLibDirs -> "gmp-lib-dirs" + SrcHcOpts -> "src-hc-opts" + HostOsCpp -> "host-os-cpp" ghcWithInterpreter :: Condition ghcWithInterpreter = do - os <- option TargetOS - arch <- option TargetArch + os <- showAction TargetOS + arch <- showAction TargetArch return $ os `elem` ["mingw32", "cygwin32", "linux", "solaris2", "freebsd", "dragonfly", "netbsd", "openbsd", "darwin", "kfreebsdgnu"] && @@ -45,10 +39,10 @@ ghcWithInterpreter = do platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do - platform <- option TargetPlatformFull + platform <- showAction TargetPlatformFull return $ platform `notElem` [ "powerpc-unknown-linux", "x86_64-unknown-mingw32", "i386-unknown-mingw32" ] -- TODO: i386-unknown-solaris2? windowsHost :: Condition windowsHost = do - hostOsCpp <- option HostOsCpp + hostOsCpp <- showAction HostOsCpp return $ hostOsCpp `elem` ["mingw32", "cygwin32"] From git at git.haskell.org Thu Oct 26 23:01:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add args -- a variadic version of arg. (6084342) Message-ID: <20171026230144.D8B5F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/60843423d23b84928c2c1ce2725b5e293cb81061/ghc >--------------------------------------------------------------- commit 60843423d23b84928c2c1ce2725b5e293cb81061 Author: Andrey Mokhov Date: Fri Jan 2 03:03:27 2015 +0000 Add args -- a variadic version of arg. >--------------------------------------------------------------- 60843423d23b84928c2c1ce2725b5e293cb81061 src/Base.hs | 16 +++++++++++++++- 1 file changed, 15 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 77c2858..645d5dc 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,7 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, + Args, arg, args, ShowAction (..), Condition (..), joinArgs, joinArgsWithSpaces, splitArgs, filterOut @@ -38,6 +38,20 @@ instance ShowAction String where arg :: ShowAction a => [a] -> Args arg = mapM showAction +class Collect a where + collect :: Args -> a + +instance Collect Args where + collect = id + +instance (ShowAction a, Collect r) => Collect (a -> r) where + collect prev next = collect $ do + next' <- showAction next + prev <> return [next'] + +args :: Collect a => a +args = collect mempty + intercalateArgs :: String -> Args -> Args intercalateArgs s args = do as <- args From git at git.haskell.org Thu Oct 26 23:01:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement joinArgs and joinArgsWithSpaces as variadic functions. (c6870b2) Message-ID: <20171026230148.697AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6870b2f0e46782ad6a094cff9809150fe2eebf7/ghc >--------------------------------------------------------------- commit c6870b2f0e46782ad6a094cff9809150fe2eebf7 Author: Andrey Mokhov Date: Sat Jan 3 23:57:51 2015 +0000 Implement joinArgs and joinArgsWithSpaces as variadic functions. >--------------------------------------------------------------- c6870b2f0e46782ad6a094cff9809150fe2eebf7 src/Base.hs | 37 ++++++++++++++++++++++--------------- 1 file changed, 22 insertions(+), 15 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 645d5dc..283d62f 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,6 +23,7 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) type Args = Action [String] + type Condition = Action Bool instance Monoid a => Monoid (Action a) where @@ -35,36 +36,42 @@ class ShowAction a where instance ShowAction String where showAction = return +instance ShowAction (Action String) where + showAction = id + arg :: ShowAction a => [a] -> Args arg = mapM showAction +type ArgsCombine = Args -> Args -> Args + class Collect a where - collect :: Args -> a + collect :: ArgsCombine -> Args -> a instance Collect Args where - collect = id + collect = const id instance (ShowAction a, Collect r) => Collect (a -> r) where - collect prev next = collect $ do - next' <- showAction next - prev <> return [next'] + collect combine x = \y -> collect combine $ x `combine` arg [y] + +instance Collect r => Collect (Args -> r) where + collect combine x = \y -> collect combine $ x `combine` y args :: Collect a => a -args = collect mempty +args = collect (<>) mempty -intercalateArgs :: String -> Args -> Args -intercalateArgs s args = do - as <- args - return [intercalate s as] +joinArgs :: Collect a => a +joinArgs = collect (\x y -> intercalateArgs "" x <> y) mempty -joinArgsWithSpaces :: Args -> Args -joinArgsWithSpaces = intercalateArgs " " +joinArgsWithSpaces :: Collect a => a +joinArgsWithSpaces = collect (\x y -> intercalateArgs " " x <> y) mempty -joinArgs :: Args -> Args -joinArgs = intercalateArgs "" +intercalateArgs :: String -> Args -> Args +intercalateArgs s as = do + as' <- as + return [intercalate s as'] splitArgs :: Args -> Args splitArgs = fmap (concatMap words) filterOut :: Args -> [String] -> Args -filterOut args list = filter (`notElem` list) <$> args +filterOut as list = filter (`notElem` list) <$> as From git at git.haskell.org Thu Oct 26 23:01:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor using variadic args. (a4f318f) Message-ID: <20171026230152.052FB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4f318fdf2905dd1ee5be475bfa38fae4a39b869/ghc >--------------------------------------------------------------- commit a4f318fdf2905dd1ee5be475bfa38fae4a39b869 Author: Andrey Mokhov Date: Sun Jan 4 03:30:13 2015 +0000 Refactor using variadic args. >--------------------------------------------------------------- a4f318fdf2905dd1ee5be475bfa38fae4a39b869 src/Base.hs | 36 +++++++++++++++--------------- src/Oracles/Builder.hs | 16 +++++++------- src/Oracles/Flag.hs | 8 +++---- src/Oracles/Option.hs | 10 ++++----- src/Package.hs | 59 ++++++++++++++++++++++---------------------------- 5 files changed, 62 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 a4f318fdf2905dd1ee5be475bfa38fae4a39b869 From git at git.haskell.org Thu Oct 26 23:01:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor changes and comments. (640b38f) Message-ID: <20171026230155.8BBD13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/640b38fbd3857a6c72156f81bd4ba06b8af61ae2/ghc >--------------------------------------------------------------- commit 640b38fbd3857a6c72156f81bd4ba06b8af61ae2 Author: Andrey Mokhov Date: Sun Jan 4 03:35:36 2015 +0000 Minor changes and comments. >--------------------------------------------------------------- 640b38fbd3857a6c72156f81bd4ba06b8af61ae2 src/Base.hs | 2 +- src/Package.hs | 18 +++++++++--------- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 490c031..ea9980c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,7 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, args, ShowAction (..), Collect (..), + Args, arg, args, ShowAction (..), Condition (..), joinArgs, joinArgsSpaced, splitArgs, filterOut diff --git a/src/Package.hs b/src/Package.hs index 5d6fc1e..843f34f 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -230,14 +230,14 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = return $ path dir modPath <.> extension packageKey <- packagaDataOption pkgData PackageKey run (Ghc stage) $ mconcat - [ arg ["-M"] + [ arg "-M" , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - , splitArgs $ arg [SrcHcOpts] - , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] - , arg [if usePackageKey then "-this-package-key" else "-package-name"] - , arg [packageKey] -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) - , arg ["-hide-all-packages"] - , arg ["-i"] -- resets the search path to nothing; TODO: check if really needed + , splitArgs $ arg SrcHcOpts -- TODO: get rid of splitArgs + , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" + , arg $ if usePackageKey then "-this-package-key" else "-package-name" + , arg packageKey -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg "-hide-all-packages" + , arg "-i" -- resets the search path to nothing; TODO: check if really needed , arg $ map (\d -> "-i" ++ path d) srcDirs , arg $ do prefix <- ["-i", "-I"] -- 'import' and '#include' search paths @@ -245,8 +245,8 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = return $ prefix ++ buildDir suffix , arg $ map (\d -> "-I" ++ path d) $ filter isRelative includeDirs , arg $ map (\d -> "-I" ++ d) $ filter isAbsolute includeDirs - , arg ["-optP-include"] - , arg ["-optP" ++ buildDir "build/autogen/cabal_macros.h"] + , arg "-optP-include" + , arg $ "-optP" ++ buildDir "build/autogen/cabal_macros.h" , if usePackageKey then arg $ concatMap (\d -> ["-package-key", d]) depKeys else arg $ concatMap (\d -> ["-package" , d]) deps From git at git.haskell.org Thu Oct 26 23:01:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:01:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Package.hs into logically separate modules. (04cbcbc) Message-ID: <20171026230159.33B643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/04cbcbc9a482ed70872e3f3bc1c6ca9224402b76/ghc >--------------------------------------------------------------- commit 04cbcbc9a482ed70872e3f3bc1c6ca9224402b76 Author: Andrey Mokhov Date: Mon Jan 5 00:40:25 2015 +0000 Decompose Package.hs into logically separate modules. >--------------------------------------------------------------- 04cbcbc9a482ed70872e3f3bc1c6ca9224402b76 src/Package.hs | 284 +------------------------------------------- src/Package/Base.hs | 86 ++++++++++++++ src/Package/Data.hs | 92 ++++++++++++++ src/Package/Dependencies.hs | 108 +++++++++++++++++ 4 files changed, 292 insertions(+), 278 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 04cbcbc9a482ed70872e3f3bc1c6ca9224402b76 From git at git.haskell.org Thu Oct 26 23:02:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track build rule source files initiating incremental rebuilds when code changes. (5a4b172) Message-ID: <20171026230202.ED53A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a4b172667f27d01ae46f6dc7d9bc7097ea06605/ghc >--------------------------------------------------------------- commit 5a4b172667f27d01ae46f6dc7d9bc7097ea06605 Author: Andrey Mokhov Date: Mon Jan 5 00:48:32 2015 +0000 Track build rule source files initiating incremental rebuilds when code changes. >--------------------------------------------------------------- 5a4b172667f27d01ae46f6dc7d9bc7097ea06605 src/Package/Data.hs | 1 + src/Package/Dependencies.hs | 1 + 2 files changed, 2 insertions(+) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 2d7b4b7..c95f8c9 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -56,6 +56,7 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = "build" "autogen" "cabal_macros.h", "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. ] &%> \_ -> do + need ["shake/src/Package/Data.hs"] -- Track changes in this file need [path name <.> "cabal"] when (doesFileExist $ path "configure.ac") $ need [path "configure"] run GhcCabal cabalArgs diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 65c9b1f..99ffc34 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -68,6 +68,7 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist in (buildDir "build" name <.> "m") %> \out -> do + need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file let pkgData = buildDir "package-data.mk" usePackageKey <- SupportsPackageKey || stage /= Stage0 -- TODO: check reasoning (distdir-way-opts) [mods, srcDirs, includeDirs, deps, depKeys] <- From git at git.haskell.org Thu Oct 26 23:02:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add directions to Package submodules. (eeea3ed) Message-ID: <20171026230206.758F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eeea3ed76e1886c34234a4efde6f3c6dc296c2d4/ghc >--------------------------------------------------------------- commit eeea3ed76e1886c34234a4efde6f3c6dc296c2d4 Author: Andrey Mokhov Date: Mon Jan 5 00:57:26 2015 +0000 Add directions to Package submodules. >--------------------------------------------------------------- eeea3ed76e1886c34234a4efde6f3c6dc296c2d4 src/Package.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index ce7a8d5..ea7aae4 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,16 +1,15 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package ( - packageRules - ) where +module Package (packageRules) where import Package.Base import Package.Data import Package.Dependencies -- These are the packages we build +-- See Package.Base for definitions of basic types packages :: [Package] packages = [libraryPackage "deepseq" Stage1 defaultSettings] +-- Rule buildXY is defined in module X.Y buildPackage :: Package -> TodoItem -> Rules () buildPackage pkg todoItem = do buildPackageData pkg todoItem @@ -18,8 +17,7 @@ buildPackage pkg todoItem = do packageRules :: Rules () packageRules = do - - want ["libraries/deepseq/dist-install/build/deepseq.m"] + want ["libraries/deepseq/dist-install/build/deepseq.m"] -- TODO: control targets from commang line arguments forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:02:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant extension. (e384039) Message-ID: <20171026230213.691FC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3840397d0db313e8c22e45782e188e5c7c642dc/ghc >--------------------------------------------------------------- commit e3840397d0db313e8c22e45782e188e5c7c642dc Author: Andrey Mokhov Date: Mon Jan 5 01:08:03 2015 +0000 Remove redundant extension. >--------------------------------------------------------------- e3840397d0db313e8c22e45782e188e5c7c642dc src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index ea9980c..6bef5ba 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-} +{-# LANGUAGE FlexibleInstances #-} module Base ( module Development.Shake, From git at git.haskell.org Thu Oct 26 23:02:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor changes. (500ab74) Message-ID: <20171026230209.E98933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/500ab7440aaf5aca6a11df8c6001a963aeb30fe4/ghc >--------------------------------------------------------------- commit 500ab7440aaf5aca6a11df8c6001a963aeb30fe4 Author: Andrey Mokhov Date: Mon Jan 5 01:03:05 2015 +0000 Minor changes. >--------------------------------------------------------------- 500ab7440aaf5aca6a11df8c6001a963aeb30fe4 src/Package.hs | 3 ++- src/Package/Base.hs | 9 ++++----- src/Package/Data.hs | 4 +--- src/Package/Dependencies.hs | 4 +--- 4 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index ea7aae4..7a5f20e 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -4,8 +4,9 @@ import Package.Base import Package.Data import Package.Dependencies --- These are the packages we build -- See Package.Base for definitions of basic types + +-- These are the packages we build: packages :: [Package] packages = [libraryPackage "deepseq" Stage1 defaultSettings] diff --git a/src/Package/Base.hs b/src/Package/Base.hs index daa5455..896bcb3 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -62,11 +62,10 @@ commonCppArgs :: Args commonCppArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? commonCcWarninigArgs :: Args -commonCcWarninigArgs = when Validating $ mconcat - [ when GccIsClang $ arg "-Wno-unknown-pragmas" - , when (not GccIsClang && not GccLt46) $ arg "-Wno-error=inline" - , when ( GccIsClang && not GccLt46 && windowsHost) $ arg "-Werror=unused-but-set-variable" - ] +commonCcWarninigArgs = when Validating $ + when GccIsClang (arg "-Wno-unknown-pragmas") + <> when (not GccIsClang && not GccLt46) (arg "-Wno-error=inline") + <> when ( GccIsClang && not GccLt46 && windowsHost) (arg "-Werror=unused-but-set-variable" ) bootPkgConstraints :: Args bootPkgConstraints = mempty diff --git a/src/Package/Data.hs b/src/Package/Data.hs index c95f8c9..fe3ec26 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -1,7 +1,5 @@ {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} -module Package.Data ( - buildPackageData - ) where +module Package.Data (buildPackageData) where import Package.Base diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 99ffc34..4327ca6 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -1,7 +1,5 @@ {-# LANGUAGE NoImplicitPrelude #-} -module Package.Dependencies ( - buildPackageDependencies - ) where +module Package.Dependencies (buildPackageDependencies) where import Package.Base From git at git.haskell.org Thu Oct 26 23:02:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove splitArgs. (9133934) Message-ID: <20171026230216.E39F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91339343449600edd26a8e427a246bee2ae63166/ghc >--------------------------------------------------------------- commit 91339343449600edd26a8e427a246bee2ae63166 Author: Andrey Mokhov Date: Tue Jan 6 19:16:50 2015 +0000 Remove splitArgs. >--------------------------------------------------------------- 91339343449600edd26a8e427a246bee2ae63166 src/Base.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 6bef5ba..9868528 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -9,7 +9,7 @@ module Base ( Stage (..), Args, arg, args, ShowAction (..), Condition (..), - joinArgs, joinArgsSpaced, splitArgs, + joinArgs, joinArgsSpaced, filterOut ) where @@ -72,8 +72,5 @@ intercalateArgs s as = do as' <- as return [intercalate s as'] -splitArgs :: Args -> Args -splitArgs = fmap (concatMap words) - filterOut :: Args -> [String] -> Args filterOut as list = filter (`notElem` list) <$> as From git at git.haskell.org Thu Oct 26 23:02:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Support multiword options. (b9c1da8) Message-ID: <20171026230220.7DA073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b9c1da83d8c87ee3f95fa25ed284ce7a12f81caa/ghc >--------------------------------------------------------------- commit b9c1da83d8c87ee3f95fa25ed284ce7a12f81caa Author: Andrey Mokhov Date: Tue Jan 6 19:18:29 2015 +0000 Support multiword options. >--------------------------------------------------------------- b9c1da83d8c87ee3f95fa25ed284ce7a12f81caa src/Oracles/Option.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 365c526..6f05a0e 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -13,7 +13,7 @@ data Option = TargetOS | TargetArch | TargetPlatformFull | HostOsCpp instance ShowAction Option where - showAction opt = showAction $ askConfig $ case opt of + showAction opt = showAction $ fmap words $ askConfig $ case opt of TargetOS -> "target-os" TargetArch -> "target-arch" TargetPlatformFull -> "target-platform-full" From git at git.haskell.org Thu Oct 26 23:02:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle multiword options in build rules. (1a7b657) Message-ID: <20171026230223.E636A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a7b657a0b02d361a5ba69f1c68d772e43b3e47b/ghc >--------------------------------------------------------------- commit 1a7b657a0b02d361a5ba69f1c68d772e43b3e47b Author: Andrey Mokhov Date: Tue Jan 6 19:19:10 2015 +0000 Handle multiword options in build rules. >--------------------------------------------------------------- 1a7b657a0b02d361a5ba69f1c68d772e43b3e47b src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index fe3ec26..b156eaa 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -21,8 +21,8 @@ configureArgs stage settings = argConf key as = joinArgs "--configure-option=" key "=" as argConfWith key opt = do - [value] <- showAction opt - when (value /= "") $ argConf ("--with-" ++ key) $ arg value + opts <- showAction opt + when (opts /= []) $ argConf ("--with-" ++ key) $ arg opts cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) (ConfCcArgs stage) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 4327ca6..ede14bb 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -81,7 +81,7 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = run (Ghc stage) $ mconcat [ arg "-M" , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - , splitArgs $ arg SrcHcOpts -- TODO: get rid of splitArgs + , arg SrcHcOpts -- TODO: get rid of splitArgs , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" , arg $ if usePackageKey then "-this-package-key" else "-package-name" , arg packageKey -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) From git at git.haskell.org Thu Oct 26 23:02:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Ensure that intercalateArgs _ mempty = mempty. (9a24f38) Message-ID: <20171026230227.61E203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a24f3876e945b6927fb0df1da0b373c3c87cba2/ghc >--------------------------------------------------------------- commit 9a24f3876e945b6927fb0df1da0b373c3c87cba2 Author: Andrey Mokhov Date: Wed Jan 7 01:16:43 2015 +0000 Ensure that intercalateArgs _ mempty = mempty. >--------------------------------------------------------------- 9a24f3876e945b6927fb0df1da0b373c3c87cba2 src/Base.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 9868528..8a98a7b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -70,7 +70,9 @@ joinArgsSpaced = collect (\x y -> intercalateArgs " " $ x <> y) mempty intercalateArgs :: String -> Args -> Args intercalateArgs s as = do as' <- as - return [intercalate s as'] + case as' of + [] -> mempty + otherwise -> return [intercalate s as'] filterOut :: Args -> [String] -> Args filterOut as list = filter (`notElem` list) <$> as From git at git.haskell.org Thu Oct 26 23:02:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove argConfWith which became redundant. (86b63df) Message-ID: <20171026230230.E2BA03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86b63df1d036247dc78af9ec2eccb7886d0e9503/ghc >--------------------------------------------------------------- commit 86b63df1d036247dc78af9ec2eccb7886d0e9503 Author: Andrey Mokhov Date: Wed Jan 7 01:18:33 2015 +0000 Remove argConfWith which became redundant. >--------------------------------------------------------------- 86b63df1d036247dc78af9ec2eccb7886d0e9503 src/Package/Base.hs | 2 +- src/Package/Data.hs | 18 +++++++----------- 2 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 896bcb3..a895f5f 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -65,7 +65,7 @@ commonCcWarninigArgs :: Args commonCcWarninigArgs = when Validating $ when GccIsClang (arg "-Wno-unknown-pragmas") <> when (not GccIsClang && not GccLt46) (arg "-Wno-error=inline") - <> when ( GccIsClang && not GccLt46 && windowsHost) (arg "-Werror=unused-but-set-variable" ) + <> when ( GccIsClang && not GccLt46 && windowsHost) (arg "-Werror=unused-but-set-variable") bootPkgConstraints :: Args bootPkgConstraints = mempty diff --git a/src/Package/Data.hs b/src/Package/Data.hs index b156eaa..0fa1322 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -18,11 +18,7 @@ libraryArgs ways = configureArgs :: Stage -> Settings -> Args configureArgs stage settings = let argConf :: String -> Args -> Args - argConf key as = joinArgs "--configure-option=" key "=" as - - argConfWith key opt = do - opts <- showAction opt - when (opts /= []) $ argConf ("--with-" ++ key) $ arg opts + argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" as cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) (ConfCcArgs stage) @@ -36,10 +32,10 @@ configureArgs stage settings = , argConf "LDFLAGS" ldflags , argConf "CPPFLAGS" cppflags , joinArgs "--gcc-options=" cflags " " ldflags - , argConfWith "iconv-includes" IconvIncludeDirs - , argConfWith "iconv-libraries" IconvLibDirs - , argConfWith "gmp-includes" GmpIncludeDirs - , argConfWith "gmp-libraries" GmpLibDirs + , argConf "--with-iconv-includes" $ arg IconvIncludeDirs + , argConf "--with-iconv-libraries" $ arg IconvLibDirs + , argConf "--with-gmp-includes" $ arg GmpIncludeDirs + , argConf "--with-gmp-libraries" $ arg GmpLibDirs , when CrossCompiling $ argConf "--host" $ arg TargetPlatformFull -- TODO: why not host? , argConf "--with-cc" $ arg Gcc ] @@ -66,8 +62,8 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = [ args "configure" path dist -- this is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument - -- * if there are many, we must collapse them into one string argument - , joinArgsSpaced $ customDllArgs settings + -- * if there are many, we must collapse them into one space-separated string + , joinArgsSpaced "" (customDllArgs settings) , with $ Ghc stage -- TODO: used to be stage01 (using max Stage1 GHC) , with $ GhcPkg stage From git at git.haskell.org Thu Oct 26 23:02:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add instance ShowAction PackageData. (7792b9a) Message-ID: <20171026230234.6672F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7792b9a32bbc24e3d3a0fb04f534e7c293ac9ea2/ghc >--------------------------------------------------------------- commit 7792b9a32bbc24e3d3a0fb04f534e7c293ac9ea2 Author: Andrey Mokhov Date: Wed Jan 7 16:30:30 2015 +0000 Add instance ShowAction PackageData. >--------------------------------------------------------------- 7792b9a32bbc24e3d3a0fb04f534e7c293ac9ea2 src/Oracles/PackageData.hs | 37 +++++++++++++++++++------------------ 1 file changed, 19 insertions(+), 18 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 831fec9..2af8e21 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -2,7 +2,7 @@ module Oracles.PackageData ( PackageDataPair (..), - packagaDataOption, PackageDataKey (..) + PackageData (..) ) where import Development.Shake.Classes @@ -12,26 +12,27 @@ import Util newtype PackageDataPair = PackageDataPair (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -packagaDataOptionWithDefault :: FilePath -> String -> Action String -> Action String -packagaDataOptionWithDefault file key defaultAction = do +packagaDataWithDefault :: FilePath -> String -> Action String -> Action String +packagaDataWithDefault file key defaultAction = do maybeValue <- askOracle $ PackageDataPair (file, key) case maybeValue of Just value -> return value Nothing -> defaultAction -data PackageDataKey = Modules | SrcDirs | PackageKey | IncludeDirs | Deps | DepKeys - deriving Show +data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath + | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath + deriving Show -packagaDataOption :: FilePath -> PackageDataKey -> Action String -packagaDataOption file key = do - let (keyName, ifEmpty) = case key of - Modules -> ("MODULES" , "" ) - SrcDirs -> ("HS_SRC_DIRS" , ".") - PackageKey -> ("PACKAGE_KEY" , "" ) - IncludeDirs -> ("INCLUDE_DIRS", ".") - Deps -> ("DEPS" , "" ) - DepKeys -> ("DEP_KEYS" , "" ) - keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName - res <- packagaDataOptionWithDefault file keyFullName $ - error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." - return $ if res == "" then ifEmpty else res +instance ShowAction PackageData where + showAction key = do + let (keyName, file, ifEmpty) = case key of + Modules file -> ("MODULES" , file, "" ) + SrcDirs file -> ("HS_SRC_DIRS" , file, ".") + PackageKey file -> ("PACKAGE_KEY" , file, "" ) + IncludeDirs file -> ("INCLUDE_DIRS", file, ".") + Deps file -> ("DEPS" , file, "" ) + DepKeys file -> ("DEP_KEYS" , file, "" ) + keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName + res <- packagaDataWithDefault file keyFullName $ + error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." + return $ words $ if res == "" then ifEmpty else res From git at git.haskell.org Thu Oct 26 23:02:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code. (f79678a) Message-ID: <20171026230238.069F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f79678a93094e3f6512044bd9f65179ae3f9b12c/ghc >--------------------------------------------------------------- commit f79678a93094e3f6512044bd9f65179ae3f9b12c Author: Andrey Mokhov Date: Wed Jan 7 16:31:30 2015 +0000 Clean up code. >--------------------------------------------------------------- f79678a93094e3f6512044bd9f65179ae3f9b12c src/Package/Data.hs | 3 +-- src/Package/Dependencies.hs | 24 +++++++++--------------- 2 files changed, 10 insertions(+), 17 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 0fa1322..de617f4 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -17,8 +17,7 @@ libraryArgs ways = configureArgs :: Stage -> Settings -> Args configureArgs stage settings = - let argConf :: String -> Args -> Args - argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" as + let argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" (as :: Args) cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) (ConfCcArgs stage) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index ede14bb..ad6705d 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -69,22 +69,16 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file let pkgData = buildDir "package-data.mk" usePackageKey <- SupportsPackageKey || stage /= Stage0 -- TODO: check reasoning (distdir-way-opts) - [mods, srcDirs, includeDirs, deps, depKeys] <- - mapM ((fmap words) . (packagaDataOption pkgData)) - [Modules, SrcDirs, IncludeDirs, Deps, DepKeys] - srcs <- getDirectoryFiles "" $ do - dir <- srcDirs - modPath <- map (replaceEq '.' pathSeparator) mods - extension <- ["hs", "lhs"] - return $ path dir modPath <.> extension - packageKey <- packagaDataOption pkgData PackageKey + mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) + srcDirs <- arg $ SrcDirs pkgData + srcs <- getDirectoryFiles "" $ [path dir mPath <.> ext | dir <- srcDirs, mPath <- mods, ext <- ["hs", "lhs"]] run (Ghc stage) $ mconcat [ arg "-M" , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - , arg SrcHcOpts -- TODO: get rid of splitArgs + , arg SrcHcOpts , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" , arg $ if usePackageKey then "-this-package-key" else "-package-name" - , arg packageKey -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg $ PackageKey pkgData -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) , arg "-hide-all-packages" , arg "-i" -- resets the search path to nothing; TODO: check if really needed , arg $ map (\d -> "-i" ++ path d) srcDirs @@ -92,13 +86,13 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = prefix <- ["-i", "-I"] -- 'import' and '#include' search paths suffix <- ["build", "build/autogen"] return $ prefix ++ buildDir suffix - , arg $ map (\d -> "-I" ++ path d) $ filter isRelative includeDirs - , arg $ map (\d -> "-I" ++ d) $ filter isAbsolute includeDirs + , map (\d -> "-I" ++ path d) <$> filter isRelative <$> arg (IncludeDirs pkgData) + , map (\d -> "-I" ++ d) <$> filter isAbsolute <$> arg (IncludeDirs pkgData) , arg "-optP-include" , arg $ "-optP" ++ buildDir "build/autogen/cabal_macros.h" , if usePackageKey - then arg $ concatMap (\d -> ["-package-key", d]) depKeys - else arg $ concatMap (\d -> ["-package" , d]) deps + then map ("-package-key " ++) <$> arg (DepKeys pkgData) + else map ("-package " ++) <$> arg (Deps pkgData) , args "-dep-makefile" out "-dep-suffix" "" "-include-pkg-deps" , arg $ map normalise srcs ] From git at git.haskell.org Thu Oct 26 23:02:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify PackageData. (2f9338d) Message-ID: <20171026230241.7D3673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f9338d4d263435155047a69b5c802c5f76beba1/ghc >--------------------------------------------------------------- commit 2f9338d4d263435155047a69b5c802c5f76beba1 Author: Andrey Mokhov Date: Wed Jan 7 16:46:10 2015 +0000 Simplify PackageData. >--------------------------------------------------------------- 2f9338d4d263435155047a69b5c802c5f76beba1 src/Oracles.hs | 2 +- src/Oracles/PackageData.hs | 20 +++++++------------- 2 files changed, 8 insertions(+), 14 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 093f1b8..3321610 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -43,5 +43,5 @@ oracleRules = do need [file] liftIO $ readConfigFile file - addOracle $ \(PackageDataPair (file, key)) -> M.lookup key <$> pkgData file + addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 2af8e21..4ec89d7 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( - PackageDataPair (..), + PackageDataKey (..), PackageData (..) ) where @@ -9,19 +9,11 @@ import Development.Shake.Classes import Base import Util -newtype PackageDataPair = PackageDataPair (FilePath, String) +newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -packagaDataWithDefault :: FilePath -> String -> Action String -> Action String -packagaDataWithDefault file key defaultAction = do - maybeValue <- askOracle $ PackageDataPair (file, key) - case maybeValue of - Just value -> return value - Nothing -> defaultAction - data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath - deriving Show instance ShowAction PackageData where showAction key = do @@ -33,6 +25,8 @@ instance ShowAction PackageData where Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName - res <- packagaDataWithDefault file keyFullName $ - error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." - return $ words $ if res == "" then ifEmpty else res + res <- askOracle $ PackageDataKey (file, keyFullName) + return $ words $ case res of + Nothing -> error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." + Just "" -> ifEmpty + Just value -> value From git at git.haskell.org Thu Oct 26 23:02:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generalise and export suffix :: Way -> String. (1ef6a04) Message-ID: <20171026230245.0380A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ef6a045ba067a1f07b4517f11e7bfd2aa066e6e/ghc >--------------------------------------------------------------- commit 1ef6a045ba067a1f07b4517f11e7bfd2aa066e6e Author: Andrey Mokhov Date: Wed Jan 7 17:44:04 2015 +0000 Generalise and export suffix :: Way -> String. >--------------------------------------------------------------- 1ef6a045ba067a1f07b4517f11e7bfd2aa066e6e src/Ways.hs | 19 ++++++++----------- 1 file changed, 8 insertions(+), 11 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 0a4284a..3e7c483 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -13,6 +13,7 @@ module Ways ( loggingDynamic, threadedLoggingDynamic, wayHcOpts, + suffix, hisuf, osuf, hcsuf ) where @@ -84,15 +85,11 @@ wayHcOpts (Way _ _ units) = , when (units == [Debug] || units == [Debug, Dynamic]) $ arg ["-ticky", "-DTICKY_TICKY"] ] --- TODO: cover other cases -suffix :: FilePath -> Way -> FilePath -suffix base (Way _ _ units) = - concat $ - ["p_" | Profiling `elem` units] ++ - ["dyn_" | Dynamic `elem` units] ++ - [base ] +suffix :: Way -> String +suffix way | way == vanilla = "" + | otherwise = tag way ++ "_" -hisuf, osuf, hcsuf :: Way -> FilePath -hisuf = suffix "hi" -osuf = suffix "o" -hcsuf = suffix "hc" +hisuf, osuf, hcsuf :: Way -> String +hisuf = (++ "hi") . suffix +osuf = (++ "o" ) . suffix +hcsuf = (++ "hc") . suffix From git at git.haskell.org Thu Oct 26 23:02:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle multiple way suffices. (2549740) Message-ID: <20171026230248.6CEF83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/254974086689e362b394084f066d14afba9c50be/ghc >--------------------------------------------------------------- commit 254974086689e362b394084f066d14afba9c50be Author: Andrey Mokhov Date: Wed Jan 7 17:44:48 2015 +0000 Handle multiple way suffices. >--------------------------------------------------------------- 254974086689e362b394084f066d14afba9c50be src/Package/Dependencies.hs | 14 +++++++++----- 1 file changed, 9 insertions(+), 5 deletions(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index ad6705d..b3e013f 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -55,7 +55,6 @@ import Package.Base -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) --- TODO: make sure SrcDirs ($1_$2_HS_SRC_DIRS) is not empty ('.' by default) -- TODO: add $1_HC_OPTS -- TODO: check that the package is not a program ($1_$2_PROG == "") -- TODO: handle empty $1_PACKAGE (can it be empty?) @@ -77,8 +76,9 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? , arg SrcHcOpts , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" + -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) , arg $ if usePackageKey then "-this-package-key" else "-package-name" - , arg $ PackageKey pkgData -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg $ PackageKey pkgData , arg "-hide-all-packages" , arg "-i" -- resets the search path to nothing; TODO: check if really needed , arg $ map (\d -> "-i" ++ path d) srcDirs @@ -88,12 +88,16 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = return $ prefix ++ buildDir suffix , map (\d -> "-I" ++ path d) <$> filter isRelative <$> arg (IncludeDirs pkgData) , map (\d -> "-I" ++ d) <$> filter isAbsolute <$> arg (IncludeDirs pkgData) - , arg "-optP-include" - , arg $ "-optP" ++ buildDir "build/autogen/cabal_macros.h" + , args "-optP-include" ("-optP" ++ buildDir "build/autogen/cabal_macros.h") , if usePackageKey then map ("-package-key " ++) <$> arg (DepKeys pkgData) else map ("-package " ++) <$> arg (Deps pkgData) - , args "-dep-makefile" out "-dep-suffix" "" "-include-pkg-deps" + , arg "-no-user-package-db" + , args "-odir" (buildDir "build") + , args "-stubdir" (buildDir "build") + , joinArgsSpaced "-dep-makefile" out + , concatMap (\w -> ["-dep-suffix", suffix w]) <$> ways settings + , arg "-include-pkg-deps" , arg $ map normalise srcs ] From git at git.haskell.org Thu Oct 26 23:02:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor src/Base.hs. (06fd336) Message-ID: <20171026230252.03C2E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/06fd336d441e3a42b3056185ef40742404ec856d/ghc >--------------------------------------------------------------- commit 06fd336d441e3a42b3056185ef40742404ec856d Author: Andrey Mokhov Date: Fri Jan 9 17:07:04 2015 +0000 Refactor src/Base.hs. * Get rid of polyvariadic function for better readability and robustnes. * Eliminate joinArgs and joinArgsSpaced functions. Users are encouraged to use 'unwords <$>' and 'concat <$>' instead. * Generalise filterOut function. * Rename ShowAction to ShowArgs. >--------------------------------------------------------------- 06fd336d441e3a42b3056185ef40742404ec856d src/Base.hs | 65 +++++++++++++++++++++---------------------------------------- 1 file changed, 22 insertions(+), 43 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 8a98a7b..ce2714e 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,9 +7,9 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, args, ShowAction (..), + Args, arg, ShowArgs (..), Condition (..), - joinArgs, joinArgsSpaced, + (<+>), filterOut ) where @@ -29,50 +29,29 @@ instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q -class ShowAction a where - showAction :: a -> Args - showListAction :: [a] -> Args -- the Creators' trick for overlapping String instances - showListAction = mconcat . map showAction +class ShowArgs a where + showArgs :: a -> Args + showListArgs :: [a] -> Args -- the Creators' trick for overlapping String instances + showListArgs = mconcat . map showArgs -instance ShowAction Char where - showAction c = return [[c]] - showListAction s = return [s] +instance ShowArgs Char where + showArgs c = return [[c]] + showListArgs s = return [s] -instance ShowAction a => ShowAction [a] where - showAction = showListAction +instance ShowArgs a => ShowArgs [a] where + showArgs = showListArgs -instance ShowAction a => ShowAction (Action a) where - showAction = (showAction =<<) +instance ShowArgs a => ShowArgs (Action a) where + showArgs = (showArgs =<<) -arg :: ShowAction a => a -> Args -arg = showAction +arg :: ShowArgs a => a -> Args +arg = showArgs -type ArgsCombine = Args -> Args -> Args +-- Combine two heterogeneous ShowArgs values. +(<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args +a <+> b = (<>) <$> showArgs a <*> showArgs b -class Collect a where - collect :: ArgsCombine -> Args -> a - -instance Collect Args where - collect = const id - -instance (ShowAction a, Collect r) => Collect (a -> r) where - collect combine x = \y -> collect combine $ x `combine` arg y - -args :: Collect a => a -args = collect (<>) mempty - -joinArgs :: Collect a => a -joinArgs = collect (\x y -> intercalateArgs "" $ x <> y) mempty - -joinArgsSpaced :: Collect a => a -joinArgsSpaced = collect (\x y -> intercalateArgs " " $ x <> y) mempty - -intercalateArgs :: String -> Args -> Args -intercalateArgs s as = do - as' <- as - case as' of - [] -> mempty - otherwise -> return [intercalate s as'] - -filterOut :: Args -> [String] -> Args -filterOut as list = filter (`notElem` list) <$> as +filterOut :: ShowArgs a => Args -> a -> Args +filterOut as exclude = do + exclude' <- showArgs exclude + filter (`notElem` exclude') <$> as From git at git.haskell.org Thu Oct 26 23:02:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename ShowAction to ShowArgs. (0da6908) Message-ID: <20171026230255.69D9D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0da69088be65109832fa78a93bc0dc21fcd37f09/ghc >--------------------------------------------------------------- commit 0da69088be65109832fa78a93bc0dc21fcd37f09 Author: Andrey Mokhov Date: Fri Jan 9 17:23:32 2015 +0000 Rename ShowAction to ShowArgs. >--------------------------------------------------------------- 0da69088be65109832fa78a93bc0dc21fcd37f09 src/Oracles/Builder.hs | 14 +++++++------- src/Oracles/Option.hs | 12 ++++++------ src/Oracles/PackageData.hs | 4 ++-- 3 files changed, 15 insertions(+), 15 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 84b73b3..d91e5e7 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -14,8 +14,8 @@ import Oracles.Option data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage -instance ShowAction Builder where - showAction builder = showAction $ do +instance ShowArgs Builder where + showArgs builder = showArgs $ do let key = case builder of Ar -> "ar" Ld -> "ld" @@ -50,12 +50,12 @@ instance ShowAction Builder where -- the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - [target] <- showAction ghc + [target] <- showArgs ghc laxDeps <- test LaxDeps if laxDeps then orderOnly [target] else need [target] needBuilder builder = do - [target] <- showAction builder + [target] <- showArgs builder need [target] -- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder @@ -70,18 +70,18 @@ with builder = do Happy -> "--with-happy=" GhcPkg _ -> "--with-ghc-pkg=" HsColour -> "--with-hscolour=" - [suffix] <- showAction builder + [suffix] <- showArgs builder needBuilder builder return [prefix ++ suffix] run :: Builder -> Args -> Action () run builder args = do needBuilder builder - [exe] <- showAction builder + [exe] <- showArgs builder args' <- args cmd [exe] args' hsColourSrcs :: Condition hsColourSrcs = do - [hscolour] <- showAction HsColour + [hscolour] <- showArgs HsColour return $ hscolour /= "" diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 6f05a0e..d08b394 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -12,8 +12,8 @@ data Option = TargetOS | TargetArch | TargetPlatformFull | SrcHcOpts | HostOsCpp -instance ShowAction Option where - showAction opt = showAction $ fmap words $ askConfig $ case opt of +instance ShowArgs Option where + showArgs opt = showArgs $ fmap words $ askConfig $ case opt of TargetOS -> "target-os" TargetArch -> "target-arch" TargetPlatformFull -> "target-platform-full" @@ -30,8 +30,8 @@ instance ShowAction Option where ghcWithInterpreter :: Condition ghcWithInterpreter = do - [os] <- showAction TargetOS - [arch] <- showAction TargetArch + [os] <- showArgs TargetOS + [arch] <- showArgs TargetArch return $ os `elem` ["mingw32", "cygwin32", "linux", "solaris2", "freebsd", "dragonfly", "netbsd", "openbsd", "darwin", "kfreebsdgnu"] && @@ -39,10 +39,10 @@ ghcWithInterpreter = do platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do - [platform] <- showAction TargetPlatformFull + [platform] <- showArgs TargetPlatformFull return $ platform `notElem` [ "powerpc-unknown-linux", "x86_64-unknown-mingw32", "i386-unknown-mingw32" ] -- TODO: i386-unknown-solaris2? windowsHost :: Condition windowsHost = do - [hostOsCpp] <- showAction HostOsCpp + [hostOsCpp] <- showArgs HostOsCpp return $ hostOsCpp `elem` ["mingw32", "cygwin32"] diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 4ec89d7..ba63612 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -15,8 +15,8 @@ newtype PackageDataKey = PackageDataKey (FilePath, String) data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath -instance ShowAction PackageData where - showAction key = do +instance ShowArgs PackageData where + showArgs key = do let (keyName, file, ifEmpty) = case key of Modules file -> ("MODULES" , file, "" ) SrcDirs file -> ("HS_SRC_DIRS" , file, ".") From git at git.haskell.org Thu Oct 26 23:02:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:02:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up build rules. (7661c31) Message-ID: <20171026230258.F26C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7661c319397cbcf02f8b9c4f229ebc8b0c019ad2/ghc >--------------------------------------------------------------- commit 7661c319397cbcf02f8b9c4f229ebc8b0c019ad2 Author: Andrey Mokhov Date: Fri Jan 9 17:24:42 2015 +0000 Clean up build rules. >--------------------------------------------------------------- 7661c319397cbcf02f8b9c4f229ebc8b0c019ad2 src/Package/Base.hs | 2 +- src/Package/Data.hs | 88 +++++++++++++++++++++------------------------ src/Package/Dependencies.hs | 8 ++--- 3 files changed, 45 insertions(+), 53 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index a895f5f..43b4a37 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -53,7 +53,7 @@ libraryPackage name stage settings = )] commonCcArgs :: Args -commonCcArgs = when Validating $ args "-Werror" "-Wall" +commonCcArgs = when Validating $ arg ["-Werror", "-Wall"] commonLdArgs :: Args commonLdArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? diff --git a/src/Package/Data.hs b/src/Package/Data.hs index de617f4..81a7d7f 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -1,43 +1,37 @@ {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} module Package.Data (buildPackageData) where - import Package.Base libraryArgs :: [Way] -> Args libraryArgs ways = - let argEnable x suffix = arg $ (if x then "--enable-" else "--disable-") ++ suffix - in mconcat - [ argEnable False "library-for-ghci" -- TODO: why always disable? - , argEnable (vanilla `elem` ways) "library-vanilla" - , when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) $ - argEnable True "library-for-ghci" - , argEnable (profiling `elem` ways) "library-profiling" - , argEnable (dynamic `elem` ways) "shared" - ] + argEnable False "library-for-ghci" -- TODO: why always disable? + <> argEnable (vanilla `elem` ways) "library-vanilla" + <> when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) (argEnable True "library-for-ghci") + <> argEnable (profiling `elem` ways) "library-profiling" + <> argEnable (dynamic `elem` ways) "shared" + where + argEnable x suffix = arg $ (if x then "--enable-" else "--disable-") ++ suffix configureArgs :: Stage -> Settings -> Args configureArgs stage settings = - let argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" (as :: Args) + let argConf key as = do + s <- unwords <$> arg as + unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) - (ConfCcArgs stage) - (customCcArgs settings) - (commonCcWarninigArgs) - ldflags = joinArgsSpaced commonLdArgs (ConfGccLinkerArgs stage) (customLdArgs settings) - cppflags = joinArgsSpaced commonCppArgs (ConfCppArgs stage) (customCppArgs settings) + cflags = commonCcArgs `filterOut` "-Werror" <+> ConfCcArgs stage <+> customCcArgs settings <+> commonCcWarninigArgs + ldflags = commonLdArgs <+> ConfGccLinkerArgs stage <+> customLdArgs settings + cppflags = commonCppArgs <+> ConfCppArgs stage <+> customCppArgs settings - in mconcat - [ argConf "CFLAGS" cflags - , argConf "LDFLAGS" ldflags - , argConf "CPPFLAGS" cppflags - , joinArgs "--gcc-options=" cflags " " ldflags - , argConf "--with-iconv-includes" $ arg IconvIncludeDirs - , argConf "--with-iconv-libraries" $ arg IconvLibDirs - , argConf "--with-gmp-includes" $ arg GmpIncludeDirs - , argConf "--with-gmp-libraries" $ arg GmpLibDirs - , when CrossCompiling $ argConf "--host" $ arg TargetPlatformFull -- TODO: why not host? - , argConf "--with-cc" $ arg Gcc - ] + in argConf "CFLAGS" cflags + <> argConf "LDFLAGS" ldflags + <> argConf "CPPFLAGS" cppflags + <> arg (concat <$> "--gcc-options=" <+> cflags <+> " " <+> ldflags) + <> argConf "--with-iconv-includes" IconvIncludeDirs + <> argConf "--with-iconv-libraries" IconvLibDirs + <> argConf "--with-gmp-includes" GmpIncludeDirs + <> argConf "--with-gmp-libraries" GmpLibDirs + <> when CrossCompiling (argConf "--host" TargetPlatformFull) -- TODO: why not host? + <> argConf "--with-cc" Gcc buildPackageData :: Package -> TodoItem -> Rules () buildPackageData pkg @ (Package name path _) (stage, dist, settings) = @@ -57,30 +51,28 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = postProcessPackageData $ path dist "package-data.mk" where cabalArgs, ghcPkgArgs :: Args - cabalArgs = mconcat - [ args "configure" path dist + cabalArgs = arg ["configure", path, dist] -- this is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument -- * if there are many, we must collapse them into one space-separated string - , joinArgsSpaced "" (customDllArgs settings) - , with $ Ghc stage -- TODO: used to be stage01 (using max Stage1 GHC) - , with $ GhcPkg stage + <> arg (unwords <$> customDllArgs settings) + <> with (Ghc stage) -- TODO: used to be stage01 (using max Stage1 GHC) + <> with (GhcPkg stage) - , customConfArgs settings - , libraryArgs =<< ways settings + <> customConfArgs settings + <> (libraryArgs =<< ways settings) - , when hsColourSrcs $ with HsColour - , configureArgs stage settings + <> when hsColourSrcs (with HsColour) + <> configureArgs stage settings - , when (stage == Stage0) $ bootPkgConstraints - , with Gcc - , when (stage /= Stage0) $ with Ld + <> when (stage == Stage0) bootPkgConstraints + <> with Gcc + <> when (stage /= Stage0) (with Ld) - , with Ar - , with Alex - , with Happy - ] -- TODO: reorder with's + <> with Ar + <> with Alex + <> with Happy -- TODO: reorder with's - ghcPkgArgs = args "update" "--force" - (when (stage == Stage0) $ arg "--package-db=libraries/bootstrapping.conf") - (path dist "inplace-pkg-config") + ghcPkgArgs = arg ["update", "--force"] + <> when (stage == Stage0) (arg "--package-db=libraries/bootstrapping.conf") + <> arg (path dist "inplace-pkg-config") diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index b3e013f..7ccb7b6 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -88,14 +88,14 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = return $ prefix ++ buildDir suffix , map (\d -> "-I" ++ path d) <$> filter isRelative <$> arg (IncludeDirs pkgData) , map (\d -> "-I" ++ d) <$> filter isAbsolute <$> arg (IncludeDirs pkgData) - , args "-optP-include" ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + , arg ["-optP-include", "-optP" ++ buildDir "build/autogen/cabal_macros.h"] , if usePackageKey then map ("-package-key " ++) <$> arg (DepKeys pkgData) else map ("-package " ++) <$> arg (Deps pkgData) , arg "-no-user-package-db" - , args "-odir" (buildDir "build") - , args "-stubdir" (buildDir "build") - , joinArgsSpaced "-dep-makefile" out + , arg ["-odir" , buildDir "build"] + , arg ["-stubdir", buildDir "build"] + , arg $ "-dep-makefile " ++ out , concatMap (\w -> ["-dep-suffix", suffix w]) <$> ways settings , arg "-include-pkg-deps" , arg $ map normalise srcs From git at git.haskell.org Thu Oct 26 23:03:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set precedence level for <+>. (45208c5) Message-ID: <20171026230302.7DB183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45208c5e1e6059db3b6993f03db0a0439f486377/ghc >--------------------------------------------------------------- commit 45208c5e1e6059db3b6993f03db0a0439f486377 Author: Andrey Mokhov Date: Sat Jan 10 02:13:01 2015 +0000 Set precedence level for <+>. >--------------------------------------------------------------- 45208c5e1e6059db3b6993f03db0a0439f486377 src/Base.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index ce2714e..de0c3d6 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -51,6 +51,8 @@ arg = showArgs (<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args a <+> b = (<>) <$> showArgs a <*> showArgs b +infixr 6 <+> + filterOut :: ShowArgs a => Args -> a -> Args filterOut as exclude = do exclude' <- showArgs exclude From git at git.haskell.org Thu Oct 26 23:03:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (d08651a) Message-ID: <20171026230305.F1EFC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d08651a9b504b04425865eaceaba66f2f74cdaa8/ghc >--------------------------------------------------------------- commit d08651a9b504b04425865eaceaba66f2f74cdaa8 Author: Andrey Mokhov Date: Sat Jan 10 02:14:14 2015 +0000 Clean up. >--------------------------------------------------------------- d08651a9b504b04425865eaceaba66f2f74cdaa8 src/Package/Data.hs | 77 +++++++++++++++++++++++++---------------------------- 1 file changed, 36 insertions(+), 41 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 81a7d7f..7428a87 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -35,44 +35,39 @@ configureArgs stage settings = buildPackageData :: Package -> TodoItem -> Rules () buildPackageData pkg @ (Package name path _) (stage, dist, settings) = - ((path dist) ) <$> - [ "package-data.mk", - "haddock-prologue.txt", - "inplace-pkg-config", - "setup-config", - "build" "autogen" "cabal_macros.h", - "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. - ] &%> \_ -> do - need ["shake/src/Package/Data.hs"] -- Track changes in this file - need [path name <.> "cabal"] - when (doesFileExist $ path "configure.ac") $ need [path "configure"] - run GhcCabal cabalArgs - when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs - postProcessPackageData $ path dist "package-data.mk" - where - cabalArgs, ghcPkgArgs :: Args - cabalArgs = arg ["configure", path, dist] - -- this is a positional argument, hence: - -- * if it is empty, we need to emit one empty string argument - -- * if there are many, we must collapse them into one space-separated string - <> arg (unwords <$> customDllArgs settings) - <> with (Ghc stage) -- TODO: used to be stage01 (using max Stage1 GHC) - <> with (GhcPkg stage) - - <> customConfArgs settings - <> (libraryArgs =<< ways settings) - - <> when hsColourSrcs (with HsColour) - <> configureArgs stage settings - - <> when (stage == Stage0) bootPkgConstraints - <> with Gcc - <> when (stage /= Stage0) (with Ld) - - <> with Ar - <> with Alex - <> with Happy -- TODO: reorder with's - - ghcPkgArgs = arg ["update", "--force"] - <> when (stage == Stage0) (arg "--package-db=libraries/bootstrapping.conf") - <> arg (path dist "inplace-pkg-config") + let buildDir = path dist + cabalArgs = arg ["configure", path, dist] + -- this is a positional argument, hence: + -- * if it is empty, we need to emit one empty string argument + -- * if there are many, we must collapse them into one space-separated string + <> arg (unwords <$> customDllArgs settings) + <> with (Ghc stage) -- TODO: used to be stage01 (using max stage1 GHC) + <> with (GhcPkg stage) + <> customConfArgs settings + <> (libraryArgs =<< ways settings) + <> when hsColourSrcs (with HsColour) + <> configureArgs stage settings + <> when (stage == Stage0) bootPkgConstraints + <> with Gcc + <> when (stage /= Stage0) (with Ld) + <> with Ar + <> with Alex + <> with Happy -- TODO: reorder with's + ghcPkgArgs = arg ["update", "--force"] + <> when (stage == Stage0) (arg "--package-db=libraries/bootstrapping.conf") + <> arg (buildDir "inplace-pkg-config") + in + (buildDir ) <$> + [ "package-data.mk" + , "haddock-prologue.txt" + , "inplace-pkg-config" + , "setup-config" + , "build" "autogen" "cabal_macros.h" + , "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. + ] &%> \_ -> do + need ["shake/src/Package/Data.hs"] -- Track changes in this file + need [path name <.> "cabal"] + when (doesFileExist $ path "configure.ac") $ need [path "configure"] + run GhcCabal cabalArgs + when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs + postProcessPackageData $ buildDir "package-data.mk" From git at git.haskell.org Thu Oct 26 23:03:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor buildPackageDependencies into separate functions. (b70f3d8) Message-ID: <20171026230309.7B5943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b/ghc >--------------------------------------------------------------- commit b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b Author: Andrey Mokhov Date: Sat Jan 10 02:14:55 2015 +0000 Refactor buildPackageDependencies into separate functions. >--------------------------------------------------------------- b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b src/Package/Dependencies.hs | 134 ++++++++++++++------------------------------ 1 file changed, 43 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b From git at git.haskell.org Thu Oct 26 23:03:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add prefixArgs function. (4c715ac) Message-ID: <20171026230312.E635F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4c715acd811aef3c2be59375280c586e22fc0ecc/ghc >--------------------------------------------------------------- commit 4c715acd811aef3c2be59375280c586e22fc0ecc Author: Andrey Mokhov Date: Sat Jan 10 19:13:55 2015 +0000 Add prefixArgs function. >--------------------------------------------------------------- 4c715acd811aef3c2be59375280c586e22fc0ecc src/Base.hs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index de0c3d6..ffb2bbb 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -10,7 +10,8 @@ module Base ( Args, arg, ShowArgs (..), Condition (..), (<+>), - filterOut + filterOut, + prefixArgs ) where import Development.Shake @@ -47,13 +48,20 @@ instance ShowArgs a => ShowArgs (Action a) where arg :: ShowArgs a => a -> Args arg = showArgs --- Combine two heterogeneous ShowArgs values. +-- Combine two heterogeneous ShowArgs values (<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args a <+> b = (<>) <$> showArgs a <*> showArgs b infixr 6 <+> +-- Filter out given arg(s) from a collection filterOut :: ShowArgs a => Args -> a -> Args filterOut as exclude = do exclude' <- showArgs exclude filter (`notElem` exclude') <$> as + +-- Prefix each arg in a collection with a given prefix +prefixArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args +prefixArgs prefix as = do + prefix' <- showArgs prefix + concatMap (\a -> prefix' ++ [a]) <$> showArgs as From git at git.haskell.org Thu Oct 26 23:03:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (3579324) Message-ID: <20171026230316.7BB4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3579324b91abeb130df12d8639b67941c71d80ae/ghc >--------------------------------------------------------------- commit 3579324b91abeb130df12d8639b67941c71d80ae Author: Andrey Mokhov Date: Sat Jan 10 19:14:45 2015 +0000 Clean up. >--------------------------------------------------------------- 3579324b91abeb130df12d8639b67941c71d80ae src/Package.hs | 3 ++- src/Package/Data.hs | 6 +++++- src/Package/Dependencies.hs | 39 ++++++++++++++++++--------------------- 3 files changed, 25 insertions(+), 23 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 7a5f20e..0df8668 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -18,7 +18,8 @@ buildPackage pkg todoItem = do packageRules :: Rules () packageRules = do - want ["libraries/deepseq/dist-install/build/deepseq.m"] -- TODO: control targets from commang line arguments + -- TODO: control targets from commang line arguments + want ["libraries/deepseq/dist-install/build/deepseq.m"] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 7428a87..fd8dd2c 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -1,5 +1,6 @@ {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} module Package.Data (buildPackageData) where + import Package.Base libraryArgs :: [Way] -> Args @@ -18,7 +19,10 @@ configureArgs stage settings = s <- unwords <$> arg as unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = commonCcArgs `filterOut` "-Werror" <+> ConfCcArgs stage <+> customCcArgs settings <+> commonCcWarninigArgs + cflags = commonCcArgs `filterOut` "-Werror" + <+> ConfCcArgs stage + <+> customCcArgs settings + <+> commonCcWarninigArgs ldflags = commonLdArgs <+> ConfGccLinkerArgs stage <+> customLdArgs settings cppflags = commonCppArgs <+> ConfCppArgs stage <+> customCppArgs settings diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 47a7a37..5b10ca1 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -3,18 +3,17 @@ module Package.Dependencies (buildPackageDependencies) where import Package.Base -packageKeyArgs :: Stage -> FilePath -> Args -packageKeyArgs stage pkgData = - arg "-hide-all-packages" <> - (pkgArgs =<< SupportsPackageKey || stage /= Stage0) +packageArgs :: Stage -> FilePath -> Args +packageArgs stage pkgData = do + usePackageKey <- SupportsPackageKey || stage /= Stage0 + arg ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] + <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") + <> keyArgs usePackageKey where - pkgArgs True = "-this-package-key" - <+> PackageKey pkgData - <+> prepend "-package-key " (DepKeys pkgData) - pkgArgs _ = "-package-name" - <+> PackageKey pkgData - <+> prepend "-package " (Deps pkgData) - prepend pref = (map (pref ++) <$>) . arg + keyArgs True = prefixArgs "-this-package-key" (PackageKey pkgData) <> + prefixArgs "-package-key" (DepKeys pkgData) + keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> + prefixArgs "-package" (Deps pkgData) includeArgs :: ShowArgs a => String -> FilePath -> a -> Args includeArgs prefix path as = map includePath <$> arg as @@ -26,7 +25,7 @@ srcArgs :: FilePath -> FilePath -> Args srcArgs path pkgData = do mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) dirs <- arg (SrcDirs pkgData) - srcs <- getDirectoryFiles "" $ + srcs <- getDirectoryFiles "" [path dir mPath <.> ext | dir <- dirs, mPath <- mods, ext <- ["hs", "lhs"]] arg (map normalise srcs) @@ -38,20 +37,18 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = (buildDir "build" name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file run (Ghc stage) $ arg "-M" - <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") - <> packageKeyArgs stage pkgData + <> packageArgs stage pkgData <> arg "-i" <> includeArgs "-i" path (SrcDirs pkgData) <> includeArgs "-i" buildDir ["build", "build/autogen"] <> includeArgs "-I" buildDir ["build", "build/autogen"] <> includeArgs "-I" path (IncludeDirs pkgData) - <> arg ["-optP-include", "-optP" ++ buildDir "build/autogen/cabal_macros.h"] - <> arg "-no-user-package-db" - <> arg ["-odir" , buildDir "build"] - <> arg ["-stubdir", buildDir "build"] - <> arg ("-dep-makefile " ++ out) - <> (concatMap (\w -> ["-dep-suffix", suffix w]) <$> ways settings) - <> arg "-include-pkg-deps" + <> arg "-optP-include" -- TODO: Shall we also add -cpp? + <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + <> arg ["-odir" , buildDir "build"] + <> arg ["-stubdir" , buildDir "build"] + <> arg ["-dep-makefile", out ] + <> prefixArgs "-dep-suffix" (map suffix <$> ways settings) <> srcArgs path pkgData -- <> arg SrcHcOpts -- TODO: Check that skipping all _HC_OPTS is safe. -- <> wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? From git at git.haskell.org Thu Oct 26 23:03:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reexport module Data.Function from Base.hs. (7ad9848) Message-ID: <20171026230319.E43183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ad9848f719e76bb194719984bbf78a926634fe9/ghc >--------------------------------------------------------------- commit 7ad9848f719e76bb194719984bbf78a926634fe9 Author: Andrey Mokhov Date: Sun Jan 11 03:26:13 2015 +0000 Reexport module Data.Function from Base.hs. >--------------------------------------------------------------- 7ad9848f719e76bb194719984bbf78a926634fe9 src/Base.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index ffb2bbb..38790e6 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -4,6 +4,7 @@ module Base ( module Development.Shake, module Development.Shake.FilePath, module Control.Applicative, + module Data.Function, module Data.Monoid, module Data.List, Stage (..), @@ -17,6 +18,7 @@ module Base ( import Development.Shake import Development.Shake.FilePath import Control.Applicative hiding ((*>)) +import Data.Function import Data.Monoid import Data.List From git at git.haskell.org Thu Oct 26 23:03:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove way descriptions, add detectWay function. (94501e5) Message-ID: <20171026230323.5612C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/94501e5a89c6d81df6d1fededaf4a05793ad135f/ghc >--------------------------------------------------------------- commit 94501e5a89c6d81df6d1fededaf4a05793ad135f Author: Andrey Mokhov Date: Sun Jan 11 03:28:17 2015 +0000 Remove way descriptions, add detectWay function. >--------------------------------------------------------------- 94501e5a89c6d81df6d1fededaf4a05793ad135f src/Ways.hs | 61 ++++++++++++++++++++++++++++++++++++------------------------- 1 file changed, 36 insertions(+), 25 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 3e7c483..843383e 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -12,9 +12,10 @@ module Ways ( threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic, - wayHcOpts, + wayHcArgs, suffix, - hisuf, osuf, hcsuf + hisuf, osuf, hcsuf, + detectWay ) where import Base @@ -25,34 +26,36 @@ data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dyn data Way = Way { tag :: String, -- e.g., "thr_p" - description :: String, -- e.g., "threaded profiled"; TODO: get rid of this field? units :: [WayUnit] -- e.g., [Threaded, Profiling] } deriving Eq -vanilla = Way "v" "vanilla" [] -profiling = Way "p" "profiling" [Profiling] -logging = Way "l" "event logging" [Logging] -parallel = Way "mp" "parallel" [Parallel] -granSim = Way "gm" "GranSim" [GranSim] +instance Show Way where + show = tag + +vanilla = Way "v" [] +profiling = Way "p" [Profiling] +logging = Way "l" [Logging] +parallel = Way "mp" [Parallel] +granSim = Way "gm" [GranSim] -- RTS only ways -threaded = Way "thr" "threaded" [Threaded] -threadedProfiling = Way "thr_p" "threaded profiling" [Threaded, Profiling] -threadedLogging = Way "thr_l" "threaded event logging" [Threaded, Logging] -debug = Way "debug" "debug" [Debug] -debugProfiling = Way "debug_p" "debug profiling" [Debug, Profiling] -threadedDebug = Way "thr_debug" "threaded debug" [Threaded, Debug] -threadedDebugProfiling = Way "thr_debug_p" "threaded debug profiling" [Threaded, Debug, Profiling] -dynamic = Way "dyn" "dyn" [Dynamic] -profilingDynamic = Way "p_dyn" "p_dyn" [Profiling, Dynamic] -threadedProfilingDynamic = Way "thr_p_dyn" "thr_p_dyn" [Threaded, Profiling, Dynamic] -threadedDynamic = Way "thr_dyn" "thr_dyn" [Threaded, Dynamic] -threadedDebugDynamic = Way "thr_debug_dyn" "thr_debug_dyn" [Threaded, Debug, Dynamic] -debugDynamic = Way "debug_dyn" "debug_dyn" [Debug, Dynamic] -loggingDynamic = Way "l_dyn" "event logging dynamic" [Logging, Dynamic] -threadedLoggingDynamic = Way "thr_l_dyn" "threaded event logging dynamic" [Threaded, Logging, Dynamic] +threaded = Way "thr" [Threaded] +threadedProfiling = Way "thr_p" [Threaded, Profiling] +threadedLogging = Way "thr_l" [Threaded, Logging] +debug = Way "debug" [Debug] +debugProfiling = Way "debug_p" [Debug, Profiling] +threadedDebug = Way "thr_debug" [Threaded, Debug] +threadedDebugProfiling = Way "thr_debug_p" [Threaded, Debug, Profiling] +dynamic = Way "dyn" [Dynamic] +profilingDynamic = Way "p_dyn" [Profiling, Dynamic] +threadedProfilingDynamic = Way "thr_p_dyn" [Threaded, Profiling, Dynamic] +threadedDynamic = Way "thr_dyn" [Threaded, Dynamic] +threadedDebugDynamic = Way "thr_debug_dyn" [Threaded, Debug, Dynamic] +debugDynamic = Way "debug_dyn" [Debug, Dynamic] +loggingDynamic = Way "l_dyn" [Logging, Dynamic] +threadedLoggingDynamic = Way "thr_l_dyn" [Threaded, Logging, Dynamic] allWays = [vanilla, profiling, logging, parallel, granSim, threaded, threadedProfiling, threadedLogging, @@ -71,8 +74,8 @@ defaultWays stage = do ++ [profiling | stage /= Stage0] ++ [dynamic | sharedLibs ] -wayHcOpts :: Way -> Args -wayHcOpts (Way _ _ units) = +wayHcArgs :: Way -> Args +wayHcArgs (Way _ units) = mconcat [ when (Dynamic `notElem` units) $ arg ["-static"] , when (Dynamic `elem` units) $ arg ["-fPIC", "-dynamic"] @@ -93,3 +96,11 @@ hisuf, osuf, hcsuf :: Way -> String hisuf = (++ "hi") . suffix osuf = (++ "o" ) . suffix hcsuf = (++ "hc") . suffix + +-- Detect way from a given extension. Fail if the result is not unique. +detectWay :: FilePath -> Way +detectWay extension = case solutions of + [way] -> way + otherwise -> error $ "Cannot detect way from extension '" ++ extension ++ "'." + where + solutions = [w | f <- [hisuf, osuf, hcsuf], w <- allWays, f w == extension] From git at git.haskell.org Thu Oct 26 23:03:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move functions ghcOpts, packageArgs, includeArgs, srcArgs. (ccb5848) Message-ID: <20171026230326.C4E553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccb58488381da821a99c95965d7a101d040bfd1f/ghc >--------------------------------------------------------------- commit ccb58488381da821a99c95965d7a101d040bfd1f Author: Andrey Mokhov Date: Sun Jan 11 03:29:44 2015 +0000 Move functions ghcOpts, packageArgs, includeArgs, srcArgs. >--------------------------------------------------------------- ccb58488381da821a99c95965d7a101d040bfd1f src/Package/Base.hs | 33 ++++++++++++++++++++++++++------- 1 file changed, 26 insertions(+), 7 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 43b4a37..4ef03fb 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -7,7 +7,8 @@ module Package.Base ( Package (..), Settings (..), TodoItem (..), defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - bootPkgConstraints, ghcOpts + bootPkgConstraints, + packageArgs, includeArgs, srcArgs ) where import Base @@ -76,10 +77,28 @@ bootPkgConstraints = mempty -- $(foreach p,$(basename $(notdir $(wildcard libraries/$d/*.cabal))),\ -- --constraint "$p == $(shell grep -i "^Version:" libraries/$d/$p.cabal | sed "s/[^0-9.]//g")")) --- TODO: move? -ghcOpts :: Package -> Stage -> Way -> Action [String] -ghcOpts pkg stage way = do - return $ ["-hisuf " ++ hisuf way] - ++ ["-osuf " ++ osuf way] - ++ ["-hcsuf " ++ hcsuf way] +packageArgs :: Stage -> FilePath -> Args +packageArgs stage pkgData = do + usePackageKey <- SupportsPackageKey || stage /= Stage0 + arg ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] + <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") + <> keyArgs usePackageKey + where + keyArgs True = prefixArgs "-this-package-key" (PackageKey pkgData) <> + prefixArgs "-package-key" (DepKeys pkgData) + keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> + prefixArgs "-package" (Deps pkgData) +includeArgs :: ShowArgs a => String -> FilePath -> a -> Args +includeArgs prefix path as = map includePath <$> arg as + where + includePath dir | isRelative dir = prefix ++ path dir + | isAbsolute dir = prefix dir + +srcArgs :: FilePath -> FilePath -> Args +srcArgs path pkgData = do + mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) + dirs <- arg (SrcDirs pkgData) + srcs <- getDirectoryFiles "" + [path dir mPath <.> ext | dir <- dirs, mPath <- mods, ext <- ["hs", "lhs"]] + arg (map normaliseEx srcs) From git at git.haskell.org Thu Oct 26 23:03:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageCompile rule. (c826054) Message-ID: <20171026230330.3AF7E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c826054081b67e094002e47e7635c7d34835f380/ghc >--------------------------------------------------------------- commit c826054081b67e094002e47e7635c7d34835f380 Author: Andrey Mokhov Date: Sun Jan 11 03:31:07 2015 +0000 Add buildPackageCompile rule. >--------------------------------------------------------------- c826054081b67e094002e47e7635c7d34835f380 src/Package.hs | 5 ++++- src/Package/Data.hs | 2 +- src/Package/Dependencies.hs | 28 +--------------------------- 3 files changed, 6 insertions(+), 29 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 0df8668..8f2850d 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -2,6 +2,7 @@ module Package (packageRules) where import Package.Base import Package.Data +import Package.Compile import Package.Dependencies -- See Package.Base for definitions of basic types @@ -15,11 +16,13 @@ buildPackage :: Package -> TodoItem -> Rules () buildPackage pkg todoItem = do buildPackageData pkg todoItem buildPackageDependencies pkg todoItem + buildPackageCompile pkg todoItem packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments - want ["libraries/deepseq/dist-install/build/deepseq.m"] + want [ "libraries/deepseq/dist-install/build/Control/DeepSeq.o" + , "libraries/deepseq/dist-install/build/Control/DeepSeq.p_o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem diff --git a/src/Package/Data.hs b/src/Package/Data.hs index fd8dd2c..919d7a5 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -38,7 +38,7 @@ configureArgs stage settings = <> argConf "--with-cc" Gcc buildPackageData :: Package -> TodoItem -> Rules () -buildPackageData pkg @ (Package name path _) (stage, dist, settings) = +buildPackageData (Package name path _) (stage, dist, settings) = let buildDir = path dist cabalArgs = arg ["configure", path, dist] -- this is a positional argument, hence: diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 5b10ca1..26b154f 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -3,34 +3,8 @@ module Package.Dependencies (buildPackageDependencies) where import Package.Base -packageArgs :: Stage -> FilePath -> Args -packageArgs stage pkgData = do - usePackageKey <- SupportsPackageKey || stage /= Stage0 - arg ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] - <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") - <> keyArgs usePackageKey - where - keyArgs True = prefixArgs "-this-package-key" (PackageKey pkgData) <> - prefixArgs "-package-key" (DepKeys pkgData) - keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> - prefixArgs "-package" (Deps pkgData) - -includeArgs :: ShowArgs a => String -> FilePath -> a -> Args -includeArgs prefix path as = map includePath <$> arg as - where - includePath dir | isRelative dir = prefix ++ path dir - | isAbsolute dir = prefix dir - -srcArgs :: FilePath -> FilePath -> Args -srcArgs path pkgData = do - mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) - dirs <- arg (SrcDirs pkgData) - srcs <- getDirectoryFiles "" - [path dir mPath <.> ext | dir <- dirs, mPath <- mods, ext <- ["hs", "lhs"]] - arg (map normalise srcs) - buildPackageDependencies :: Package -> TodoItem -> Rules () -buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = +buildPackageDependencies (Package name path _) (stage, dist, settings) = let buildDir = path dist pkgData = buildDir "package-data.mk" in From git at git.haskell.org Thu Oct 26 23:03:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add src/Package/Compile.hs. (e315d33) Message-ID: <20171026230333.A363A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e315d3381d2441e5acfc86384fb7eff9575cb006/ghc >--------------------------------------------------------------- commit e315d3381d2441e5acfc86384fb7eff9575cb006 Author: Andrey Mokhov Date: Sun Jan 11 03:31:34 2015 +0000 Add src/Package/Compile.hs. >--------------------------------------------------------------- e315d3381d2441e5acfc86384fb7eff9575cb006 src/Package/Compile.hs | 43 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 43 insertions(+) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs new file mode 100644 index 0000000..0733a46 --- /dev/null +++ b/src/Package/Compile.hs @@ -0,0 +1,43 @@ +{-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} +module Package.Compile (buildPackageCompile) where + +import Package.Base +import Development.Shake.Util + +-- "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.o + +suffixArgs :: Way -> Args +suffixArgs way = arg ["-hisuf", hisuf way, "-osuf", osuf way, "-hcsuf", hcsuf way] + +buildPackageCompile :: Package -> TodoItem -> Rules () +buildPackageCompile (Package name path _) (stage, dist, settings) = + let buildDir = path dist + pkgData = buildDir "package-data.mk" + depFile = buildDir "build" name <.> "m" + in + (buildDir "build//*o") %> \out -> do + let way = detectWay $ tail $ takeExtension out + need ["shake/src/Package/Compile.hs"] -- Track changes in this file + need [depFile] + depContents <- parseMakefile <$> (liftIO $ readFile depFile) + let deps = concat $ snd $ unzip $ filter ((== out) . fst) depContents + srcs = filter ("//*hs" ?==) deps + need deps + run (Ghc stage) $ suffixArgs way + <> wayHcArgs way + <> arg SrcHcOpts + <> packageArgs stage pkgData + <> arg "-i" + <> includeArgs "-i" path (SrcDirs pkgData) + <> includeArgs "-i" buildDir ["build", "build/autogen"] + <> includeArgs "-I" buildDir ["build", "build/autogen"] + <> includeArgs "-I" path (IncludeDirs pkgData) + <> arg "-optP-include" -- TODO: Shall we also add -cpp? + <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + <> arg ["-Wall", "-XHaskell2010", "-O2"] -- TODO: now we have both -O and -O2 + <> arg ["-odir" , buildDir "build"] + <> arg ["-hidir" , buildDir "build"] + <> arg ["-stubdir" , buildDir "build"] + <> arg "-split-objs" + <> arg ("-c":srcs) + <> arg ["-o", out] From git at git.haskell.org Thu Oct 26 23:03:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (89c8f79) Message-ID: <20171026230337.359143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/89c8f7943a320e688f3664b225c6ab21d7685bc2/ghc >--------------------------------------------------------------- commit 89c8f7943a320e688f3664b225c6ab21d7685bc2 Author: Andrey Mokhov Date: Sun Jan 11 13:10:20 2015 +0000 Clean up. >--------------------------------------------------------------- 89c8f7943a320e688f3664b225c6ab21d7685bc2 src/Ways.hs | 28 +++++++++++----------------- 1 file changed, 11 insertions(+), 17 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 843383e..368e449 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -30,9 +30,6 @@ data Way = Way } deriving Eq -instance Show Way where - show = tag - vanilla = Way "v" [] profiling = Way "p" [Profiling] logging = Way "l" [Logging] @@ -40,7 +37,6 @@ parallel = Way "mp" [Parallel] granSim = Way "gm" [GranSim] -- RTS only ways - threaded = Way "thr" [Threaded] threadedProfiling = Way "thr_p" [Threaded, Profiling] threadedLogging = Way "thr_l" [Threaded, Logging] @@ -71,22 +67,20 @@ defaultWays :: Stage -> Action [Way] defaultWays stage = do sharedLibs <- platformSupportsSharedLibs return $ [vanilla] - ++ [profiling | stage /= Stage0] - ++ [dynamic | sharedLibs ] + ++ [profiling | stage /= Stage0] + ++ [dynamic | sharedLibs ] wayHcArgs :: Way -> Args wayHcArgs (Way _ units) = - mconcat - [ when (Dynamic `notElem` units) $ arg ["-static"] - , when (Dynamic `elem` units) $ arg ["-fPIC", "-dynamic"] - , when (Threaded `elem` units) $ arg ["-optc-DTHREADED_RTS"] - , when (Debug `elem` units) $ arg ["-optc-DDEBUG"] - , when (Profiling `elem` units) $ arg ["-prof"] - , when (Logging `elem` units) $ arg ["-eventlog"] - , when (Parallel `elem` units) $ arg ["-parallel"] - , when (GranSim `elem` units) $ arg ["-gransim"] - , when (units == [Debug] || units == [Debug, Dynamic]) $ arg ["-ticky", "-DTICKY_TICKY"] - ] + when (Dynamic `notElem` units) (arg "-static") + <> when (Dynamic `elem` units) (arg ["-fPIC", "-dynamic"]) + <> when (Threaded `elem` units) (arg "-optc-DTHREADED_RTS") + <> when (Debug `elem` units) (arg "-optc-DDEBUG") + <> when (Profiling `elem` units) (arg "-prof") + <> when (Logging `elem` units) (arg "-eventlog") + <> when (Parallel `elem` units) (arg "-parallel") + <> when (GranSim `elem` units) (arg "-gransim") + <> when (units == [Debug] || units == [Debug, Dynamic]) (arg ["-ticky", "-DTICKY_TICKY"]) suffix :: Way -> String suffix way | way == vanilla = "" From git at git.haskell.org Thu Oct 26 23:03:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor duplicated code into pathArgs, outputArgs and includeArgs functions. (9fbf3c8) Message-ID: <20171026230340.A21013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9fbf3c8c37ac973da0574bd4a3dbe7bb2c012a32/ghc >--------------------------------------------------------------- commit 9fbf3c8c37ac973da0574bd4a3dbe7bb2c012a32 Author: Andrey Mokhov Date: Sun Jan 11 13:33:27 2015 +0000 Refactor duplicated code into pathArgs, outputArgs and includeArgs functions. >--------------------------------------------------------------- 9fbf3c8c37ac973da0574bd4a3dbe7bb2c012a32 src/Package/Base.hs | 26 +++++++++++++++++++++----- src/Package/Compile.hs | 14 +++----------- src/Package/Dependencies.hs | 13 +++---------- 3 files changed, 27 insertions(+), 26 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 4ef03fb..d1bf6ac 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -8,6 +8,7 @@ module Package.Base ( defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, bootPkgConstraints, + pathArgs, outputArgs, packageArgs, includeArgs, srcArgs ) where @@ -77,6 +78,15 @@ bootPkgConstraints = mempty -- $(foreach p,$(basename $(notdir $(wildcard libraries/$d/*.cabal))),\ -- --constraint "$p == $(shell grep -i "^Version:" libraries/$d/$p.cabal | sed "s/[^0-9.]//g")")) +pathArgs :: ShowArgs a => String -> FilePath -> a -> Args +pathArgs prefix path as = map includePath <$> arg as + where + includePath dir | isRelative dir = prefix ++ normaliseEx (path dir) + | isAbsolute dir = prefix normaliseEx dir + +outputArgs :: [String] -> FilePath -> Args +outputArgs keys dir = arg $ concatMap (\k -> [k, normaliseEx dir]) keys + packageArgs :: Stage -> FilePath -> Args packageArgs stage pkgData = do usePackageKey <- SupportsPackageKey || stage /= Stage0 @@ -89,11 +99,17 @@ packageArgs stage pkgData = do keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> prefixArgs "-package" (Deps pkgData) -includeArgs :: ShowArgs a => String -> FilePath -> a -> Args -includeArgs prefix path as = map includePath <$> arg as - where - includePath dir | isRelative dir = prefix ++ path dir - | isAbsolute dir = prefix dir +includeArgs :: FilePath -> FilePath -> Args +includeArgs path dist = + let buildDir = path dist + pkgData = buildDir "package-data.mk" + in arg "-i" + <> pathArgs "-i" path (SrcDirs pkgData) + <> pathArgs "-i" buildDir ["build", "build/autogen"] + <> pathArgs "-I" buildDir ["build", "build/autogen"] + <> pathArgs "-I" path (IncludeDirs pkgData) + <> arg "-optP-include" -- TODO: Shall we also add -cpp? + <> pathArgs "-optP" buildDir "build/autogen/cabal_macros.h" srcArgs :: FilePath -> FilePath -> Args srcArgs path pkgData = do diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 0733a46..14296c0 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -21,23 +21,15 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = need [depFile] depContents <- parseMakefile <$> (liftIO $ readFile depFile) let deps = concat $ snd $ unzip $ filter ((== out) . fst) depContents - srcs = filter ("//*hs" ?==) deps + srcs = filter ("//*hs" ?==) deps -- TODO: handle *.c sources need deps run (Ghc stage) $ suffixArgs way <> wayHcArgs way <> arg SrcHcOpts <> packageArgs stage pkgData - <> arg "-i" - <> includeArgs "-i" path (SrcDirs pkgData) - <> includeArgs "-i" buildDir ["build", "build/autogen"] - <> includeArgs "-I" buildDir ["build", "build/autogen"] - <> includeArgs "-I" path (IncludeDirs pkgData) - <> arg "-optP-include" -- TODO: Shall we also add -cpp? - <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + <> includeArgs path dist <> arg ["-Wall", "-XHaskell2010", "-O2"] -- TODO: now we have both -O and -O2 - <> arg ["-odir" , buildDir "build"] - <> arg ["-hidir" , buildDir "build"] - <> arg ["-stubdir" , buildDir "build"] + <> outputArgs ["-odir", "-hidir", "-stubdir"] (buildDir "build") <> arg "-split-objs" <> arg ("-c":srcs) <> arg ["-o", out] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 26b154f..18c2015 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -12,16 +12,9 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file run (Ghc stage) $ arg "-M" <> packageArgs stage pkgData - <> arg "-i" - <> includeArgs "-i" path (SrcDirs pkgData) - <> includeArgs "-i" buildDir ["build", "build/autogen"] - <> includeArgs "-I" buildDir ["build", "build/autogen"] - <> includeArgs "-I" path (IncludeDirs pkgData) - <> arg "-optP-include" -- TODO: Shall we also add -cpp? - <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") - <> arg ["-odir" , buildDir "build"] - <> arg ["-stubdir" , buildDir "build"] - <> arg ["-dep-makefile", out ] + <> includeArgs path dist + <> outputArgs ["-odir", "-stubdir"] (buildDir "build") + <> arg ["-dep-makefile", out] <> prefixArgs "-dep-suffix" (map suffix <$> ways settings) <> srcArgs path pkgData -- <> arg SrcHcOpts -- TODO: Check that skipping all _HC_OPTS is safe. From git at git.haskell.org Thu Oct 26 23:03:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an infix version of when (). (f913c35) Message-ID: <20171026230344.309583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f913c3580b486bf0c0aaf42fdc5090668cb63ab2/ghc >--------------------------------------------------------------- commit f913c3580b486bf0c0aaf42fdc5090668cb63ab2 Author: Andrey Mokhov Date: Sun Jan 11 15:15:29 2015 +0000 Add an infix version of when (). >--------------------------------------------------------------- f913c3580b486bf0c0aaf42fdc5090668cb63ab2 src/Oracles/Flag.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 354b1d7..946c4fb 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -4,7 +4,7 @@ module Oracles.Flag ( module Control.Monad, module Prelude, Flag (..), - test, when, unless, not, (&&), (||) + test, when, unless, not, (&&), (||), () ) where import Control.Monad hiding (when, unless) @@ -60,6 +60,10 @@ unless x act = do bool <- toCondition x if bool then mempty else act +-- Infix version of when +() :: (ToCondition a, Monoid m) => a -> Action m -> Action m +() = when + class Not a where type NotResult a not :: a -> NotResult a From git at git.haskell.org Thu Oct 26 23:03:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add productArgs and concatArgs helper functions. (018f850) Message-ID: <20171026230347.C0E0B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/018f8501c40e1c8b70da99c2b836750e9815f75d/ghc >--------------------------------------------------------------- commit 018f8501c40e1c8b70da99c2b836750e9815f75d Author: Andrey Mokhov Date: Sun Jan 11 17:01:02 2015 +0000 Add productArgs and concatArgs helper functions. >--------------------------------------------------------------- 018f8501c40e1c8b70da99c2b836750e9815f75d src/Base.hs | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 38790e6..b84b48c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,12 +12,12 @@ module Base ( Condition (..), (<+>), filterOut, - prefixArgs + productArgs, concatArgs ) where -import Development.Shake +import Development.Shake hiding ((*>)) import Development.Shake.FilePath -import Control.Applicative hiding ((*>)) +import Control.Applicative import Data.Function import Data.Monoid import Data.List @@ -32,9 +32,10 @@ instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q +-- Using the Creators' trick for overlapping String instances class ShowArgs a where showArgs :: a -> Args - showListArgs :: [a] -> Args -- the Creators' trick for overlapping String instances + showListArgs :: [a] -> Args showListArgs = mconcat . map showArgs instance ShowArgs Char where @@ -62,8 +63,18 @@ filterOut as exclude = do exclude' <- showArgs exclude filter (`notElem` exclude') <$> as --- Prefix each arg in a collection with a given prefix -prefixArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args -prefixArgs prefix as = do - prefix' <- showArgs prefix - concatMap (\a -> prefix' ++ [a]) <$> showArgs as +-- Generate a cross product collection of two argument collections +-- Example: productArgs ["-a", "-b"] "c" = arg ["-a", "c", "-b", "c"] +productArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args +productArgs as bs = do + as' <- showArgs as + bs' <- showArgs bs + return $ concat $ sequence [as', bs'] + +-- Similar to productArgs but concat resulting arguments pairwise +-- Example: concatArgs ["-a", "-b"] "c" = arg ["-ac", "-bc"] +concatArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args +concatArgs as bs = do + as' <- showArgs as + bs' <- showArgs bs + return $ map concat $ sequence [as', bs'] From git at git.haskell.org Thu Oct 26 23:03:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor, limit lines at 80 characters. (128c5ac) Message-ID: <20171026230351.B44723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4/ghc >--------------------------------------------------------------- commit 128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4 Author: Andrey Mokhov Date: Sun Jan 11 17:02:58 2015 +0000 Refactor, limit lines at 80 characters. >--------------------------------------------------------------- 128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4 src/Package/Base.hs | 70 ++++++++++++++++++++++----------------------- src/Package/Compile.hs | 39 +++++++++++++++++++------ src/Package/Data.hs | 39 +++++++++++++++---------- src/Package/Dependencies.hs | 18 ++++++------ 4 files changed, 99 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 128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4 From git at git.haskell.org Thu Oct 26 23:03:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify: Package -> TodoItem -> Rules () is a monoid! (56689f0) Message-ID: <20171026230355.2657C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56689f0356383efb1cb285138cdd6b2a57d0fc11/ghc >--------------------------------------------------------------- commit 56689f0356383efb1cb285138cdd6b2a57d0fc11 Author: Andrey Mokhov Date: Sun Jan 11 19:25:46 2015 +0000 Simplify: Package -> TodoItem -> Rules () is a monoid! >--------------------------------------------------------------- 56689f0356383efb1cb285138cdd6b2a57d0fc11 src/Package.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 8f2850d..2fd10f1 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -11,12 +11,11 @@ import Package.Dependencies packages :: [Package] packages = [libraryPackage "deepseq" Stage1 defaultSettings] --- Rule buildXY is defined in module X.Y +-- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () -buildPackage pkg todoItem = do - buildPackageData pkg todoItem - buildPackageDependencies pkg todoItem - buildPackageCompile pkg todoItem +buildPackage = buildPackageData + <> buildPackageDependencies + <> buildPackageCompile packageRules :: Rules () packageRules = do From git at git.haskell.org Thu Oct 26 23:03:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:03:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters. (d264db1) Message-ID: <20171026230358.B58E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d264db1967999ff34350037afc0440128c7667d2/ghc >--------------------------------------------------------------- commit d264db1967999ff34350037afc0440128c7667d2 Author: Andrey Mokhov Date: Sun Jan 11 19:55:14 2015 +0000 Fit lines into 80 characters. >--------------------------------------------------------------- d264db1967999ff34350037afc0440128c7667d2 src/Ways.hs | 38 ++++++++++++++++++++++---------------- 1 file changed, 22 insertions(+), 16 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 368e449..c6d733c 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -21,7 +21,14 @@ module Ways ( import Base import Oracles -data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dynamic deriving Eq +data WayUnit = Profiling + | Logging + | Parallel + | GranSim + | Threaded + | Debug + | Dynamic + deriving Eq data Way = Way { @@ -36,7 +43,7 @@ logging = Way "l" [Logging] parallel = Way "mp" [Parallel] granSim = Way "gm" [GranSim] --- RTS only ways +-- RTS only ways. TODO: do we need to define these here? threaded = Way "thr" [Threaded] threadedProfiling = Way "thr_p" [Threaded, Profiling] threadedLogging = Way "thr_l" [Threaded, Logging] @@ -60,9 +67,6 @@ allWays = [vanilla, profiling, logging, parallel, granSim, threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic] --- TODO: what are ways 't' and 's'? --- ALL_WAYS=v p t l s mp mg debug dyn thr thr_l p_dyn debug_dyn thr_dyn thr_p_dyn thr_debug_dyn thr_p thr_debug debug_p thr_debug_p l_dyn thr_l_dyn - defaultWays :: Stage -> Action [Way] defaultWays stage = do sharedLibs <- platformSupportsSharedLibs @@ -70,17 +74,19 @@ defaultWays stage = do ++ [profiling | stage /= Stage0] ++ [dynamic | sharedLibs ] +-- TODO: do '-ticky' in all debug ways? wayHcArgs :: Way -> Args wayHcArgs (Way _ units) = - when (Dynamic `notElem` units) (arg "-static") - <> when (Dynamic `elem` units) (arg ["-fPIC", "-dynamic"]) - <> when (Threaded `elem` units) (arg "-optc-DTHREADED_RTS") - <> when (Debug `elem` units) (arg "-optc-DDEBUG") - <> when (Profiling `elem` units) (arg "-prof") - <> when (Logging `elem` units) (arg "-eventlog") - <> when (Parallel `elem` units) (arg "-parallel") - <> when (GranSim `elem` units) (arg "-gransim") - <> when (units == [Debug] || units == [Debug, Dynamic]) (arg ["-ticky", "-DTICKY_TICKY"]) + (Dynamic `notElem` units) arg "-static" + <> (Dynamic `elem` units) arg ["-fPIC", "-dynamic"] + <> (Threaded `elem` units) arg "-optc-DTHREADED_RTS" + <> (Debug `elem` units) arg "-optc-DDEBUG" + <> (Profiling `elem` units) arg "-prof" + <> (Logging `elem` units) arg "-eventlog" + <> (Parallel `elem` units) arg "-parallel" + <> (GranSim `elem` units) arg "-gransim" + <> (units == [Debug] || units == [Debug, Dynamic]) + arg ["-ticky", "-DTICKY_TICKY"] suffix :: Way -> String suffix way | way == vanilla = "" @@ -94,7 +100,7 @@ hcsuf = (++ "hc") . suffix -- Detect way from a given extension. Fail if the result is not unique. detectWay :: FilePath -> Way detectWay extension = case solutions of - [way] -> way - otherwise -> error $ "Cannot detect way from extension '" ++ extension ++ "'." + [way] -> way + _ -> error $ "Cannot detect way from extension '" ++ extension ++ "'." where solutions = [w | f <- [hisuf, osuf, hcsuf], w <- allWays, f w == extension] From git at git.haskell.org Thu Oct 26 23:04:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor oracle rules. (21e48fc) Message-ID: <20171026230402.4945A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21e48fc51345e7294e1dd2a642a1c305230ceb2f/ghc >--------------------------------------------------------------- commit 21e48fc51345e7294e1dd2a642a1c305230ceb2f Author: Andrey Mokhov Date: Sun Jan 11 20:08:00 2015 +0000 Refactor oracle rules. >--------------------------------------------------------------- 21e48fc51345e7294e1dd2a642a1c305230ceb2f src/Oracles.hs | 34 ++++++++++++++++++++++------------ 1 file changed, 22 insertions(+), 12 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 3321610..3a0c430 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -17,31 +17,41 @@ import Oracles.Option import Oracles.Builder import Oracles.PackageData -oracleRules :: Rules () -oracleRules = do +defaultConfig, userConfig :: FilePath +defaultConfig = cfgPath "default.config" +userConfig = cfgPath "user.config" + +-- Oracle for configuration files. +configOracle :: Rules () +configOracle = do cfg <- newCache $ \() -> do - unless (doesFileExist $ cfgPath "default.config.in") $ do + unless (doesFileExist $ defaultConfig <.> "in") $ do error $ "\nDefault configuration file '" - ++ (cfgPath "default.config.in") + ++ (defaultConfig <.> "in") ++ "' is missing; unwilling to proceed." return () - need [cfgPath "default.config"] - cfgDefault <- liftIO $ readConfigFile $ cfgPath "default.config" - existsUser <- doesFileExist $ cfgPath "user.config" + need [defaultConfig] + cfgDefault <- liftIO $ readConfigFile defaultConfig + existsUser <- doesFileExist userConfig cfgUser <- if existsUser - then liftIO $ readConfigFile $ cfgPath "user.config" + then liftIO $ readConfigFile userConfig else do putLoud $ "\nUser defined configuration file '" - ++ (cfgPath "user.config") - ++ "' is missing; proceeding with default configuration.\n" + ++ userConfig ++ "' is missing; " + ++ "proceeding with default configuration.\n" return M.empty return $ cfgUser `M.union` cfgDefault - addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () + return () +-- Oracle for 'package-data.mk' files. +packageDataOracle :: Rules () +packageDataOracle = do pkgData <- newCache $ \file -> do need [file] liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () + +oracleRules :: Rules () +oracleRules = configOracle <> packageDataOracle From git at git.haskell.org Thu Oct 26 23:04:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove postProcessPackageData from Util. (481caa8) Message-ID: <20171026230405.CF30E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/481caa85874e966d8adc82dddde1313187647167/ghc >--------------------------------------------------------------- commit 481caa85874e966d8adc82dddde1313187647167 Author: Andrey Mokhov Date: Sun Jan 11 21:29:13 2015 +0000 Remove postProcessPackageData from Util. >--------------------------------------------------------------- 481caa85874e966d8adc82dddde1313187647167 src/Package/Data.hs | 12 ++++++++++++ src/Util.hs | 14 +------------- 2 files changed, 13 insertions(+), 13 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index e2260fd..eaaa072 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -43,6 +43,18 @@ configureArgs stage settings = <> when CrossCompiling (argConf "--host" TargetPlatformFull) <> argConf "--with-cc" Gcc +-- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: +-- 1) Drop lines containing '$' +-- 2) Replace '/' and '\' with '_' before '=' +postProcessPackageData :: FilePath -> Action () +postProcessPackageData file = do + pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) + length pkgData `seq` writeFileLines file $ map processLine pkgData + where + processLine line = replaceSeparators '_' prefix ++ suffix + where + (prefix, suffix) = break (== '=') line + buildPackageData :: Package -> TodoItem -> Rules () buildPackageData (Package name path _) (stage, dist, settings) = let pathDist = path dist diff --git a/src/Util.hs b/src/Util.hs index d7e98bd..f91ff79 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,7 +1,6 @@ module Util ( module Data.Char, - replaceIf, replaceEq, replaceSeparators, - postProcessPackageData + replaceIf, replaceEq, replaceSeparators ) where import Base @@ -16,14 +15,3 @@ replaceEq from = replaceIf (== from) replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator --- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: --- 1) Drop lines containing '$' --- 2) Replace '/' and '\' with '_' before '=' -postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map processLine pkgData - where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:04:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters. (d956739) Message-ID: <20171026230409.43C1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d956739dd5d551fa4f0259966f2f0b0cce250bcd/ghc >--------------------------------------------------------------- commit d956739dd5d551fa4f0259966f2f0b0cce250bcd Author: Andrey Mokhov Date: Sun Jan 11 21:42:39 2015 +0000 Fit lines into 80 characters. >--------------------------------------------------------------- d956739dd5d551fa4f0259966f2f0b0cce250bcd src/Oracles/PackageData.hs | 20 ++++++++++++-------- 1 file changed, 12 insertions(+), 8 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index ba63612..6bffafd 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -12,21 +12,25 @@ import Util newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath - | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath +data PackageData = Modules FilePath + | SrcDirs FilePath + | PackageKey FilePath + | IncludeDirs FilePath + | Deps FilePath + | DepKeys FilePath instance ShowArgs PackageData where - showArgs key = do - let (keyName, file, ifEmpty) = case key of + showArgs packageData = do + let (key, file, defaultValue) = case packageData of Modules file -> ("MODULES" , file, "" ) SrcDirs file -> ("HS_SRC_DIRS" , file, ".") PackageKey file -> ("PACKAGE_KEY" , file, "" ) IncludeDirs file -> ("INCLUDE_DIRS", file, ".") Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) - keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName - res <- askOracle $ PackageDataKey (file, keyFullName) + fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key + res <- askOracle $ PackageDataKey (file, fullKey) return $ words $ case res of - Nothing -> error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." - Just "" -> ifEmpty + Nothing -> error $ "No key '" ++ key ++ "' in " ++ file ++ "." + Just "" -> defaultValue Just value -> value From git at git.haskell.org Thu Oct 26 23:04:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add instance Show Stage. (d0095df) Message-ID: <20171026230412.B97AD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d0095df621aa39dfbe7f827e073c5b1fb7aa7b89/ghc >--------------------------------------------------------------- commit d0095df621aa39dfbe7f827e073c5b1fb7aa7b89 Author: Andrey Mokhov Date: Sun Jan 11 21:45:31 2015 +0000 Add instance Show Stage. >--------------------------------------------------------------- d0095df621aa39dfbe7f827e073c5b1fb7aa7b89 src/Base.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index b84b48c..169f556 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -24,6 +24,9 @@ import Data.List data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) +instance Show Stage where + show = show . fromEnum + type Args = Action [String] type Condition = Action Bool From git at git.haskell.org Thu Oct 26 23:04:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters. (817ed05) Message-ID: <20171026230416.47B0A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/817ed0570d9b58d3a3220fadcc704cfa7913d90f/ghc >--------------------------------------------------------------- commit 817ed0570d9b58d3a3220fadcc704cfa7913d90f Author: Andrey Mokhov Date: Sun Jan 11 21:50:41 2015 +0000 Fit lines into 80 characters. >--------------------------------------------------------------- 817ed0570d9b58d3a3220fadcc704cfa7913d90f src/Oracles/Option.hs | 32 +++++++++++++++++++++++--------- 1 file changed, 23 insertions(+), 9 deletions(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index d08b394..0a5506d 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -6,9 +6,17 @@ module Oracles.Option ( import Base import Oracles.Base -data Option = TargetOS | TargetArch | TargetPlatformFull - | ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage - | IconvIncludeDirs | IconvLibDirs | GmpIncludeDirs | GmpLibDirs +data Option = TargetOS + | TargetArch + | TargetPlatformFull + | ConfCcArgs Stage + | ConfGccLinkerArgs Stage + | ConfLdLinkerArgs Stage + | ConfCppArgs Stage + | IconvIncludeDirs + | IconvLibDirs + | GmpIncludeDirs + | GmpLibDirs | SrcHcOpts | HostOsCpp @@ -17,10 +25,10 @@ instance ShowArgs Option where TargetOS -> "target-os" TargetArch -> "target-arch" TargetPlatformFull -> "target-platform-full" - ConfCcArgs stage -> "conf-cc-args-stage-" ++ (show . fromEnum) stage - ConfCppArgs stage -> "conf-cpp-args-stage-" ++ (show . fromEnum) stage - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ (show . fromEnum) stage - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ (show . fromEnum) stage + ConfCcArgs stage -> "conf-cc-args-stage-" ++ show stage + ConfCppArgs stage -> "conf-cpp-args-stage-" ++ show stage + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ show stage + ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ show stage IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" GmpIncludeDirs -> "gmp-include-dirs" @@ -33,14 +41,20 @@ ghcWithInterpreter = do [os] <- showArgs TargetOS [arch] <- showArgs TargetArch return $ - os `elem` ["mingw32", "cygwin32", "linux", "solaris2", "freebsd", "dragonfly", "netbsd", "openbsd", "darwin", "kfreebsdgnu"] + os `elem` [ "mingw32", "cygwin32", "linux", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" + , "darwin", "kfreebsdgnu"] && arch `elem` ["i386", "x86_64", "powerpc", "sparc", "sparc64", "arm"] +-- TODO: i386-unknown-solaris2 should be in the list if +-- @SOLARIS_BROKEN_SHLD@ == YES platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do [platform] <- showArgs TargetPlatformFull - return $ platform `notElem` [ "powerpc-unknown-linux", "x86_64-unknown-mingw32", "i386-unknown-mingw32" ] -- TODO: i386-unknown-solaris2? + return $ platform `notElem` [ "powerpc-unknown-linux" + , "x86_64-unknown-mingw32" + , "i386-unknown-mingw32" ] windowsHost :: Condition windowsHost = do From git at git.haskell.org Thu Oct 26 23:04:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for SolarisBrokenShld flag. (e77d98b) Message-ID: <20171026230419.C4E523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e77d98ba7ad9c4eef57f28784267ba6da339d8fe/ghc >--------------------------------------------------------------- commit e77d98ba7ad9c4eef57f28784267ba6da339d8fe Author: Andrey Mokhov Date: Sun Jan 11 23:43:31 2015 +0000 Add support for SolarisBrokenShld flag. >--------------------------------------------------------------- e77d98ba7ad9c4eef57f28784267ba6da339d8fe cfg/default.config.in | 1 + src/Oracles/Flag.hs | 17 ++++++++++++----- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index 50c3937..b1eadd0 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -31,6 +31,7 @@ gcc-lt-46 = @GccLT46@ lax-dependencies = NO dynamic-ghc-programs = NO supports-package-key = @SUPPORTS_PACKAGE_KEY@ +solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ # Information about host and target systems: #=========================================== diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 946c4fb..7a235a4 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -13,23 +13,30 @@ import Prelude hiding (not, (&&), (||)) import Base import Oracles.Base -data Flag = LaxDeps | DynamicGhcPrograms - | GccIsClang | GccLt46 | CrossCompiling | Validating +data Flag = LaxDeps + | DynamicGhcPrograms + | GccIsClang + | GccLt46 + | CrossCompiling + | Validating | SupportsPackageKey + | SolarisBrokenShld +-- TODO: Give the warning *only once* per key test :: Flag -> Action Bool test flag = do (key, defaultValue) <- return $ case flag of - LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file + LaxDeps -> ("lax-dependencies" , False) DynamicGhcPrograms -> ("dynamic-ghc-programs" , False) GccIsClang -> ("gcc-is-clang" , False) GccLt46 -> ("gcc-lt-46" , False) CrossCompiling -> ("cross-compiling" , False) Validating -> ("validating" , False) SupportsPackageKey -> ("supports-package-key" , False) + SolarisBrokenShld -> ("solaris-broken-shld" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ - do putLoud $ "\nFlag '" -- TODO: Give the warning *only once* per key + do putLoud $ "\nFlag '" ++ key ++ "' not set in configuration files. " ++ "Proceeding with default value '" @@ -103,4 +110,4 @@ instance ToCondition a => AndOr Flag a where x && y = toCondition x && y x || y = toCondition x || y - +-- TODO: need one more instance? \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:04:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for SolarisBrokenShld flag. (a5de5a5) Message-ID: <20171026230423.42C023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5de5a592f8b2bdae851e0d0c0a0041414dd1c39/ghc >--------------------------------------------------------------- commit a5de5a592f8b2bdae851e0d0c0a0041414dd1c39 Author: Andrey Mokhov Date: Sun Jan 11 23:44:30 2015 +0000 Add support for SolarisBrokenShld flag. >--------------------------------------------------------------- a5de5a592f8b2bdae851e0d0c0a0041414dd1c39 src/Oracles/Option.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 0a5506d..029b9bd 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,9 +1,11 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Oracles.Option ( Option (..), ghcWithInterpreter, platformSupportsSharedLibs, windowsHost ) where import Base +import Oracles.Flag import Oracles.Base data Option = TargetOS @@ -47,14 +49,15 @@ ghcWithInterpreter = do && arch `elem` ["i386", "x86_64", "powerpc", "sparc", "sparc64", "arm"] --- TODO: i386-unknown-solaris2 should be in the list if --- @SOLARIS_BROKEN_SHLD@ == YES platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do [platform] <- showArgs TargetPlatformFull - return $ platform `notElem` [ "powerpc-unknown-linux" - , "x86_64-unknown-mingw32" - , "i386-unknown-mingw32" ] + solarisBrokenShld <- test SolarisBrokenShld + return $ notElem platform $ + [ "powerpc-unknown-linux" + , "x86_64-unknown-mingw32" + , "i386-unknown-mingw32"] ++ + [ "i386-unknown-solaris2" | solarisBrokenShld ] windowsHost :: Condition windowsHost = do From git at git.haskell.org Thu Oct 26 23:04:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant GHC extentions. (238efc2) Message-ID: <20171026230426.A48F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/238efc2b316f5a8ed2f955af6639e4fa543d2359/ghc >--------------------------------------------------------------- commit 238efc2b316f5a8ed2f955af6639e4fa543d2359 Author: Andrey Mokhov Date: Sun Jan 11 23:45:29 2015 +0000 Remove redundant GHC extentions. >--------------------------------------------------------------- 238efc2b316f5a8ed2f955af6639e4fa543d2359 src/Package/Compile.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index b876482..50cf412 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} +{-# LANGUAGE NoImplicitPrelude #-} module Package.Compile (buildPackageCompile) where import Package.Base From git at git.haskell.org Thu Oct 26 23:04:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (2e29ea9) Message-ID: <20171026230430.10E623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2e29ea968bba4737bbdeb914e90cae4933202c75/ghc >--------------------------------------------------------------- commit 2e29ea968bba4737bbdeb914e90cae4933202c75 Author: Andrey Mokhov Date: Mon Jan 12 00:29:28 2015 +0000 Clean up. >--------------------------------------------------------------- 2e29ea968bba4737bbdeb914e90cae4933202c75 src/Oracles/Base.hs | 3 ++- src/Oracles/Flag.hs | 10 +++++----- 2 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index f9e5c73..c9827a9 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -8,7 +8,8 @@ module Oracles.Base ( import Base import Development.Shake.Classes -newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +newtype ConfigKey = ConfigKey String + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) askConfigWithDefault :: String -> Action String -> Action String askConfigWithDefault key defaultAction = do diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 7a235a4..b93e4ab 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -81,11 +81,11 @@ instance Not Bool where instance Not Condition where type NotResult Condition = Condition - not x = not <$> (toCondition x) + not = fmap not instance Not Flag where type NotResult Flag = Condition - not x = not (toCondition x) + not = not . toCondition class AndOr a b where type AndOrResult a b @@ -102,12 +102,12 @@ instance AndOr Bool Bool where instance ToCondition a => AndOr Condition a where type AndOrResult Condition a = Condition - x && y = (Prelude.&&) <$> toCondition x <*> toCondition y - x || y = (Prelude.||) <$> toCondition x <*> toCondition y + x && y = (&&) <$> x <*> toCondition y + x || y = (||) <$> x <*> toCondition y instance ToCondition a => AndOr Flag a where type AndOrResult Flag a = Condition x && y = toCondition x && y x || y = toCondition x || y --- TODO: need one more instance? \ No newline at end of file +-- TODO: need more instances to handle Bool as first argument of (&&), (||) From git at git.haskell.org Thu Oct 26 23:04:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters, add exists Builder function. (f956bdc) Message-ID: <20171026230433.6CE7B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f956bdcf059fac29eafbfb24e1eb2180e8689009/ghc >--------------------------------------------------------------- commit f956bdcf059fac29eafbfb24e1eb2180e8689009 Author: Andrey Mokhov Date: Mon Jan 12 01:21:37 2015 +0000 Fit lines into 80 characters, add exists Builder function. >--------------------------------------------------------------- f956bdcf059fac29eafbfb24e1eb2180e8689009 src/Oracles/Builder.hs | 76 ++++++++++++++++++++++++++++++-------------------- src/Package/Data.hs | 2 +- 2 files changed, 46 insertions(+), 32 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index d91e5e7..eefa7a2 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,8 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, - hsColourSrcs + with, run, exists ) where import Data.Char @@ -12,10 +11,22 @@ import Oracles.Base import Oracles.Flag import Oracles.Option -data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage +-- Ghc Stage0 is the bootstrapping compiler +-- Ghc StageN, N > 0, is the one built on stage (N - 1) +-- GhcPkg Stage0 is the bootstrapping GhcPkg +-- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) +data Builder = Ar + | Ld + | Gcc + | Alex + | Happy + | HsColour + | GhcCabal + | Ghc Stage + | GhcPkg Stage instance ShowArgs Builder where - showArgs builder = showArgs $ do + showArgs builder = showArgs $ fmap words $ do let key = case builder of Ar -> "ar" Ld -> "ld" @@ -24,16 +35,15 @@ instance ShowArgs Builder where Happy -> "happy" HsColour -> "hscolour" GhcCabal -> "ghc-cabal" - Ghc Stage0 -> "system-ghc" -- Ghc Stage0 is the bootstrapping compiler - Ghc Stage1 -> "ghc-stage1" -- Ghc StageN, N > 0, is the one built on stage (N - 1) + Ghc Stage0 -> "system-ghc" + Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg - GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) + GhcPkg Stage0 -> "system-ghc-pkg" + GhcPkg _ -> "ghc-pkg" cfgPath <- askConfigWithDefault key $ - error $ "\nCannot find path to '" - ++ key - ++ "' in configuration files." + error $ "\nCannot find path to '" ++ key + ++ "' in configuration files." let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" windows <- windowsHost if (windows && "/" `isPrefixOf` cfgPathExe) @@ -43,25 +53,26 @@ instance ShowArgs Builder where else return cfgPathExe --- When LaxDeps flag is set (by adding 'lax-dependencies = YES' to user.config), --- dependencies on the GHC executable are turned into order-only dependencies to --- avoid needless recompilation when making changes to GHC's sources. In certain --- situations this can lead to build failures, in which case you should reset --- the flag (at least temporarily). +-- When LaxDeps flag is set ('lax-dependencies = YES' in user.config), +-- dependencies on the GHC executable are turned into order-only dependencies +-- to avoid needless recompilation when making changes to GHC's sources. In +-- certain situations this can lead to build failures, in which case you +-- should reset the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - [target] <- showArgs ghc - laxDeps <- test LaxDeps - if laxDeps then orderOnly [target] else need [target] + [exe] <- showArgs ghc -- Raise an error if builder is not unique + laxDeps <- test LaxDeps + if laxDeps then orderOnly [exe] else need [exe] needBuilder builder = do - [target] <- showArgs builder - need [target] + [exe] <- showArgs builder + need [exe] --- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder +-- Action 'with Gcc' returns '--with-gcc=/path/to/gcc' and needs Gcc +-- Raises an error if the builder is not uniquely defined in config files with :: Builder -> Args with builder = do - let prefix = case builder of + let key = case builder of Ar -> "--with-ar=" Ld -> "--with-ld=" Gcc -> "--with-gcc=" @@ -70,18 +81,21 @@ with builder = do Happy -> "--with-happy=" GhcPkg _ -> "--with-ghc-pkg=" HsColour -> "--with-hscolour=" - [suffix] <- showArgs builder + [exe] <- showArgs builder needBuilder builder - return [prefix ++ suffix] + arg $ key ++ normaliseEx exe +-- Raises an error if the builder is not uniquely defined in config files run :: Builder -> Args -> Action () run builder args = do needBuilder builder [exe] <- showArgs builder - args' <- args - cmd [exe] args' + cmd [exe] =<< args -hsColourSrcs :: Condition -hsColourSrcs = do - [hscolour] <- showArgs HsColour - return $ hscolour /= "" +-- Check if the builder is uniquely defined in config files +exists :: Builder -> Condition +exists builder = do + exes <- showArgs builder + return $ case exes of + [_] -> True + _ -> False diff --git a/src/Package/Data.hs b/src/Package/Data.hs index eaaa072..f2805b8 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -68,7 +68,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = <> with (GhcPkg stage) <> customConfArgs settings <> (libraryArgs =<< ways settings) - <> when hsColourSrcs (with HsColour) + <> when (exists HsColour) (with HsColour) <> configureArgs stage settings <> when (stage == Stage0) bootPkgConstraints <> with Gcc From git at git.haskell.org Thu Oct 26 23:04:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename exists Builder to specified Builder, add comments. (7c9dfba) Message-ID: <20171026230436.C23273A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c9dfba2978d9dba7050e477938d3f99826d55f2/ghc >--------------------------------------------------------------- commit 7c9dfba2978d9dba7050e477938d3f99826d55f2 Author: Andrey Mokhov Date: Mon Jan 12 15:41:02 2015 +0000 Rename exists Builder to specified Builder, add comments. >--------------------------------------------------------------- 7c9dfba2978d9dba7050e477938d3f99826d55f2 src/Oracles/Builder.hs | 19 ++++++++++++------- src/Package/Data.hs | 2 +- 2 files changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index eefa7a2..16b5da5 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, exists + with, run, specified ) where import Data.Char @@ -46,6 +46,7 @@ instance ShowArgs Builder where ++ "' in configuration files." let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" windows <- windowsHost + -- Note, below is different from FilePath.isAbsolute: if (windows && "/" `isPrefixOf` cfgPathExe) then do Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] @@ -58,9 +59,12 @@ instance ShowArgs Builder where -- to avoid needless recompilation when making changes to GHC's sources. In -- certain situations this can lead to build failures, in which case you -- should reset the flag (at least temporarily). + +-- Make sure the builder exists on the given path and rebuild it if out of date +-- Raise an error if the builder is not uniquely specified in config files needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - [exe] <- showArgs ghc -- Raise an error if builder is not unique + [exe] <- showArgs ghc laxDeps <- test LaxDeps if laxDeps then orderOnly [exe] else need [exe] @@ -69,7 +73,7 @@ needBuilder builder = do need [exe] -- Action 'with Gcc' returns '--with-gcc=/path/to/gcc' and needs Gcc --- Raises an error if the builder is not uniquely defined in config files +-- Raises an error if the builder is not uniquely specified in config files with :: Builder -> Args with builder = do let key = case builder of @@ -85,16 +89,17 @@ with builder = do needBuilder builder arg $ key ++ normaliseEx exe --- Raises an error if the builder is not uniquely defined in config files +-- Run the builder with a given collection of arguments +-- Raises an error if the builder is not uniquely specified in config files run :: Builder -> Args -> Action () run builder args = do needBuilder builder [exe] <- showArgs builder cmd [exe] =<< args --- Check if the builder is uniquely defined in config files -exists :: Builder -> Condition -exists builder = do +-- Check if the builder is uniquely specified in config files +specified :: Builder -> Condition +specified builder = do exes <- showArgs builder return $ case exes of [_] -> True diff --git a/src/Package/Data.hs b/src/Package/Data.hs index f2805b8..7ff0d7d 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -68,7 +68,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = <> with (GhcPkg stage) <> customConfArgs settings <> (libraryArgs =<< ways settings) - <> when (exists HsColour) (with HsColour) + <> when (specified HsColour) (with HsColour) <> configureArgs stage settings <> when (stage == Stage0) bootPkgConstraints <> with Gcc From git at git.haskell.org Thu Oct 26 23:04:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Record new progress. (2840dab) Message-ID: <20171026230443.AF90D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2840dab476a13a6f75463b6c34ec8e756e40cf06/ghc >--------------------------------------------------------------- commit 2840dab476a13a6f75463b6c34ec8e756e40cf06 Author: Andrey Mokhov Date: Tue Jan 13 02:18:57 2015 +0000 Record new progress. >--------------------------------------------------------------- 2840dab476a13a6f75463b6c34ec8e756e40cf06 doc/deepseq-build-progress.txt | 42 ++++++++++++++++++++++++++++-------------- 1 file changed, 28 insertions(+), 14 deletions(-) diff --git a/doc/deepseq-build-progress.txt b/doc/deepseq-build-progress.txt index 07214c6..f951d61 100644 --- a/doc/deepseq-build-progress.txt +++ b/doc/deepseq-build-progress.txt @@ -1,48 +1,62 @@ +# Skipping: "inplace/bin/ghc-cabal.exe" check libraries/deepseq -Skipping. - - +# Done: "inplace/bin/ghc-cabal.exe" configure libraries/deepseq dist-install "" --with-ghc="C:/msys/home/chEEtah/ghc/inplace/bin/ghc-stage1.exe" --with-ghc-pkg="C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe" --disable-library-for-ghci --enable-library-vanilla --enable-library-for-ghci --enable-library-profiling --disable-shared --configure-option=CFLAGS=" -fno-stack-protector " --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc-options=" -fno-stack-protector " --with-gcc="C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe" --with-ld="C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" --configure-option=--with-cc="C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe" --with-ar="/usr/bin/ar" --with-alex="/usr/local/bin/alex" --with-happy="/usr/local/bin/happy" -C:/msys/home/chEEtah/ghc/inplace/bin/ghc-cabal.exe configure libraries\deepseq dist-install --with-ghc= C:/msys/home/chEEtah/ghc/inplace/bin/ghc-stage1.exe --with-ghc-pkg= C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe --disable-library-for-ghci --enable-library-vanilla --enable-library-for-ghci --enable-library-profiling --disable-shared --configure-option=CFLAGS=-fno-stack-protector --configure-option=LDFLAGS= --configure-option=CPPFLAGS= --gcc-options=-fno-stack-protector --with-gcc= C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe --with-ld= C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe --configure-option=--with-cc= C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe --with-ar=C:/msys/usr/bin/ar.exe --with-alex=C:/msys/usr/local/bin/alex.exe --with-happy=C:/msys/usr/local/bin/happy.exe - Configuring deepseq-1.4.0.0... +# Done: "C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe" update --force libraries/deepseq/dist-install/inplace-pkg-config - C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe update --force libraries\deepseq\dist-install\inplace-pkg-config - Reading package info from "libraries/deepseq/dist-install/inplace-pkg-config" ... done. - +# Skipping: "rm" -f libraries/deepseq/dist-install/build/.depend-v-p.c_asm.tmp + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/.depend-v-p.c_asm.bit +# Skipping: echo "libraries/deepseq_dist-install_depfile_c_asm_EXISTS = YES" >> libraries/deepseq/dist-install/build/.depend-v-p.c_asm.tmp + +# Skipping: mv libraries/deepseq/dist-install/build/.depend-v-p.c_asm.tmp libraries/deepseq/dist-install/build/.depend-v-p.c_asm + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp +# Done: "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs +# Skipping: echo "libraries/deepseq_dist-install_depfile_haskell_EXISTS = YES" >> libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp + +# Skipping: for dir in libraries/deepseq/dist-install/build/Control/; do if test ! -d $dir; then mkdir -p $dir; fi done -grep -v ' : [a-zA-Z]:/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp > libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 -sed -e '/hs$/ p' -e '/hs$/ s/o /hi /g' -e '/hs$/ s/:/ : %hi: %o /' -e '/hs$/ s/^/$(eval $(call hi-rule,/' -e '/hs$/ s/$/))/' -e '/hs-boot$/ p' -e '/hs-boot$/ s/o-boot /hi-boot /g' -e '/hs-boot$/ s/:/ : %hi-boot: %o-boot /' -e '/hs-boot$/ s/^/$(eval $(call hi-rule,/' -e '/hs-boot$/ s/$/))/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 > libraries/deepseq/dist-install/build/.depend-v-p.haskell +# Skipping: +grep -v ' : [a-zA-Z]:/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp > libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 +# Skipping: +sed -e '/hs$/ p' -e '/hs$/ s/o /hi /g' -e '/hs$/ s/:/ : %hi: %o /' -e '/hs$/ s/^/$(eval $(call hi-rule,/' -e '/hs$/ s/$/))/' -e '/hs-boot$/ p' -e '/hs-boot$/ s/o-boot /hi-boot /g' -e '/hs-boot$/ s/:/ : %hi-boot: %o-boot /' -e '/hs-boot$/ s/^/$(eval $(call hi-rule,/' -e '/hs-boot$/ s/$/))/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 > libraries/deepseq/dist-install/build/.depend-v-p.haskell +# Done: "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.o - - +# Skipping: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + +# Skipping: /usr/bin/find libraries/deepseq/dist-install/build/Control/DeepSeq_o_split -name '*.o' -print >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + +# Skipping: echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + +# Done: "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents /usr/bin/ar: creating libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents - - +# Done: "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.p_o From git at git.haskell.org Thu Oct 26 23:04:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add options SplitObjectsBroken, GhcUnregisterised, DynamicExtension, ProjectVersion. (b5beba9) Message-ID: <20171026230440.3E5FC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b5beba96f0d4c6ba31e0e97d08ca54502acf8ec7/ghc >--------------------------------------------------------------- commit b5beba96f0d4c6ba31e0e97d08ca54502acf8ec7 Author: Andrey Mokhov Date: Tue Jan 13 02:17:53 2015 +0000 Add options SplitObjectsBroken, GhcUnregisterised, DynamicExtension, ProjectVersion. >--------------------------------------------------------------- b5beba96f0d4c6ba31e0e97d08ca54502acf8ec7 cfg/default.config.in | 6 ++++++ src/Oracles/Flag.hs | 4 ++++ src/Oracles/Option.hs | 34 ++++++++++++++++++++++++++-------- 3 files changed, 36 insertions(+), 8 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index b1eadd0..ac42e24 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -32,6 +32,8 @@ lax-dependencies = NO dynamic-ghc-programs = NO supports-package-key = @SUPPORTS_PACKAGE_KEY@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ +split-objects-broken = @SplitObjsBroken@ +ghc-unregisterised = @Unregisterised@ # Information about host and target systems: #=========================================== @@ -44,6 +46,10 @@ host-os-cpp = @HostOS_CPP@ cross-compiling = @CrossCompiling@ +dynamic-extension = @soext_target@ + +project-version = @ProjectVersion@ + # Compilation and linking flags: #=============================== diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index b93e4ab..e9aace5 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -21,6 +21,8 @@ data Flag = LaxDeps | Validating | SupportsPackageKey | SolarisBrokenShld + | SplitObjectsBroken + | GhcUnregisterised -- TODO: Give the warning *only once* per key test :: Flag -> Action Bool @@ -34,6 +36,8 @@ test flag = do Validating -> ("validating" , False) SupportsPackageKey -> ("supports-package-key" , False) SolarisBrokenShld -> ("solaris-broken-shld" , False) + SplitObjectsBroken -> ("split-objects-broken" , False) + GhcUnregisterised -> ("ghc-unregisterised" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ do putLoud $ "\nFlag '" diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 029b9bd..89192a7 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,13 +1,14 @@ {-# LANGUAGE NoImplicitPrelude #-} module Oracles.Option ( Option (..), - ghcWithInterpreter, platformSupportsSharedLibs, windowsHost + ghcWithInterpreter, platformSupportsSharedLibs, windowsHost, splitObjects ) where import Base import Oracles.Flag import Oracles.Base +-- TODO: separate single string options from multiple string ones. data Option = TargetOS | TargetArch | TargetPlatformFull @@ -21,6 +22,8 @@ data Option = TargetOS | GmpLibDirs | SrcHcOpts | HostOsCpp + | DynamicExtension + | ProjectVersion instance ShowArgs Option where showArgs opt = showArgs $ fmap words $ askConfig $ case opt of @@ -37,15 +40,17 @@ instance ShowArgs Option where GmpLibDirs -> "gmp-lib-dirs" SrcHcOpts -> "src-hc-opts" HostOsCpp -> "host-os-cpp" + DynamicExtension -> "dynamic-extension" + ProjectVersion -> "project-version" ghcWithInterpreter :: Condition ghcWithInterpreter = do [os] <- showArgs TargetOS [arch] <- showArgs TargetArch return $ - os `elem` [ "mingw32", "cygwin32", "linux", "solaris2" - , "freebsd", "dragonfly", "netbsd", "openbsd" - , "darwin", "kfreebsdgnu"] + os `elem` ["mingw32", "cygwin32", "linux", "solaris2", + "freebsd", "dragonfly", "netbsd", "openbsd", + "darwin", "kfreebsdgnu"] && arch `elem` ["i386", "x86_64", "powerpc", "sparc", "sparc64", "arm"] @@ -54,12 +59,25 @@ platformSupportsSharedLibs = do [platform] <- showArgs TargetPlatformFull solarisBrokenShld <- test SolarisBrokenShld return $ notElem platform $ - [ "powerpc-unknown-linux" - , "x86_64-unknown-mingw32" - , "i386-unknown-mingw32"] ++ - [ "i386-unknown-solaris2" | solarisBrokenShld ] + ["powerpc-unknown-linux", + "x86_64-unknown-mingw32", + "i386-unknown-mingw32"] ++ + ["i386-unknown-solaris2" | solarisBrokenShld] windowsHost :: Condition windowsHost = do [hostOsCpp] <- showArgs HostOsCpp return $ hostOsCpp `elem` ["mingw32", "cygwin32"] + +-- TODO: refactor helper Condition functions into a separate file +splitObjects :: Stage -> Condition +splitObjects stage = do + [os] <- showArgs TargetOS + [arch] <- showArgs TargetArch + splitObjectsBroken <- test SplitObjectsBroken + ghcUnregisterised <- test GhcUnregisterised + return $ not splitObjectsBroken && not ghcUnregisterised + && arch `elem` ["i386", "x86_64", "powerpc", "sparc"] + && os `elem` ["mingw32", "cygwin32", "linux", "darwin", + "solaris2", "freebsd", "dragonfly", "netbsd", + "openbsd"] From git at git.haskell.org Thu Oct 26 23:04:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Work on way suffixes. (91ecc02) Message-ID: <20171026230447.253AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91ecc023c94c9a694749024d1973e72ccc8c5336/ghc >--------------------------------------------------------------- commit 91ecc023c94c9a694749024d1973e72ccc8c5336 Author: Andrey Mokhov Date: Tue Jan 13 02:20:39 2015 +0000 Work on way suffixes. >--------------------------------------------------------------- 91ecc023c94c9a694749024d1973e72ccc8c5336 src/Ways.hs | 62 +++++++++++++++++++++++++++++++++++++++++++++++-------------- 1 file changed, 48 insertions(+), 14 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index c6d733c..b478a04 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -13,7 +13,7 @@ module Ways ( loggingDynamic, threadedLoggingDynamic, wayHcArgs, - suffix, + wayPrefix, hisuf, osuf, hcsuf, detectWay ) where @@ -43,7 +43,8 @@ logging = Way "l" [Logging] parallel = Way "mp" [Parallel] granSim = Way "gm" [GranSim] --- RTS only ways. TODO: do we need to define these here? +-- RTS only ways +-- TODO: do we need to define *only* these? Shall we generalise/simplify? threaded = Way "thr" [Threaded] threadedProfiling = Way "thr_p" [Threaded, Profiling] threadedLogging = Way "thr_l" [Threaded, Logging] @@ -88,19 +89,52 @@ wayHcArgs (Way _ units) = <> (units == [Debug] || units == [Debug, Dynamic]) arg ["-ticky", "-DTICKY_TICKY"] -suffix :: Way -> String -suffix way | way == vanilla = "" - | otherwise = tag way ++ "_" +wayPrefix :: Way -> String +wayPrefix way | way == vanilla = "" + | otherwise = tag way ++ "_" -hisuf, osuf, hcsuf :: Way -> String -hisuf = (++ "hi") . suffix -osuf = (++ "o" ) . suffix -hcsuf = (++ "hc") . suffix +hisuf, osuf, hcsuf, obootsuf, ssuf :: Way -> String +osuf = (++ "o" ) . wayPrefix +ssuf = (++ "s" ) . wayPrefix +hisuf = (++ "hi" ) . wayPrefix +hcsuf = (++ "hc" ) . wayPrefix +obootsuf = (++ "o-boot") . wayPrefix + +-- Note: in the previous build system libsuf was mysteriously different +-- from other suffixes. For example, in the profiling way it used to be +-- "_p.a" instead of ".p_a" which is how other suffixes work. I decided +-- to make all suffixes consistent: ".way_extension". +libsuf :: Way -> Action String +libsuf way = do + let staticSuffix = wayPrefix $ dropDynamic way + if Dynamic `notElem` units way + then return $ staticSuffix ++ "a" + else do + [extension] <- showArgs DynamicExtension + [version] <- showArgs ProjectVersion + return $ staticSuffix ++ "-ghc" ++ version ++ extension + +-- TODO: This may be slow -- optimise if overhead is significant. +dropDynamic :: Way -> Way +dropDynamic way + | way == dynamic = vanilla + | way == profilingDynamic = profiling + | way == threadedProfilingDynamic = threadedProfiling + | way == threadedDynamic = threaded + | way == threadedDebugDynamic = threadedDebug + | way == debugDynamic = debug + | way == loggingDynamic = logging + | way == threadedLoggingDynamic = threadedLogging + | otherwise = error $ "Cannot drop Dynamic from way " ++ tag way ++ "." -- Detect way from a given extension. Fail if the result is not unique. +-- TODO: This may be slow -- optimise if overhead is significant. detectWay :: FilePath -> Way -detectWay extension = case solutions of - [way] -> way - _ -> error $ "Cannot detect way from extension '" ++ extension ++ "'." - where - solutions = [w | f <- [hisuf, osuf, hcsuf], w <- allWays, f w == extension] +detectWay extension = + let prefix = reverse $ dropWhile (/= '_') $ reverse extension + result = filter ((== prefix) . wayPrefix) allWays + in + case result of + [way] -> way + _ -> error $ "Cannot detect way from extension '" + ++ extension ++ "'." From git at git.haskell.org Thu Oct 26 23:04:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageLibrary. (a325521) Message-ID: <20171026230450.AF5EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a325521e7db63f1bda2b38f3e7988c364708ce43/ghc >--------------------------------------------------------------- commit a325521e7db63f1bda2b38f3e7988c364708ce43 Author: Andrey Mokhov Date: Tue Jan 13 02:21:14 2015 +0000 Add buildPackageLibrary. >--------------------------------------------------------------- a325521e7db63f1bda2b38f3e7988c364708ce43 src/Package.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 2fd10f1..a3fcf89 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -3,6 +3,7 @@ module Package (packageRules) where import Package.Base import Package.Data import Package.Compile +import Package.Library import Package.Dependencies -- See Package.Base for definitions of basic types @@ -16,12 +17,13 @@ buildPackage :: Package -> TodoItem -> Rules () buildPackage = buildPackageData <> buildPackageDependencies <> buildPackageCompile + <> buildPackageLibrary packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments - want [ "libraries/deepseq/dist-install/build/Control/DeepSeq.o" - , "libraries/deepseq/dist-install/build/Control/DeepSeq.p_o" ] + want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" + , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:04:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement search for *.hs and *.o files for a given package. (750a43f) Message-ID: <20171026230454.3F2793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/750a43fcef635a38485a1a2ecc30412e557e44f0/ghc >--------------------------------------------------------------- commit 750a43fcef635a38485a1a2ecc30412e557e44f0 Author: Andrey Mokhov Date: Tue Jan 13 02:23:01 2015 +0000 Implement search for *.hs and *.o files for a given package. >--------------------------------------------------------------- 750a43fcef635a38485a1a2ecc30412e557e44f0 src/Package/Base.hs | 50 +++++++++++++++++++++++++++++++++++++++----------- 1 file changed, 39 insertions(+), 11 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index d9302b7..a8de80d 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -8,7 +8,8 @@ module Package.Base ( defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, bootPkgConstraints, - pathArgs, packageArgs, includeArgs, srcArgs + pathArgs, packageArgs, includeArgs, pkgHsSources, + pkgDepObjects, pkgLibObjects ) where import Base @@ -108,13 +109,40 @@ includeArgs path dist = <> arg "-optP-include" -- TODO: Shall we also add -cpp? <> concatArgs "-optP" (buildDir "autogen/cabal_macros.h") -srcArgs :: FilePath -> FilePath -> Args -srcArgs path pkgData = do - mods <- arg (Modules pkgData) - dirs <- arg (SrcDirs pkgData) - srcs <- getDirectoryFiles "" $ do - dir <- dirs - modPath <- map (replaceEq '.' pathSeparator) mods - extension <- ["hs", "lhs"] - return $ path dir modPath <.> extension - arg (map normaliseEx srcs) +pkgHsSources :: FilePath -> FilePath -> Action [FilePath] +pkgHsSources path dist = do + let pkgData = path dist "package-data.mk" + dirs <- map (path ) <$> arg (SrcDirs pkgData) + findModuleFiles pkgData dirs [".hs", ".lhs"] + +-- Find objects we depend on (we don't want to depend on split objects) +-- TODO: look for non-hs objects too +pkgDepObjects :: FilePath -> FilePath -> Way -> Action [FilePath] +pkgDepObjects path dist way = do + let pkgData = path dist "package-data.mk" + buildDir = path dist "build" + hs2obj = (buildDir ++) . drop (length path) . (-<.> osuf way) + srcs <- pkgHsSources path dist + return $ map hs2obj srcs + +-- Find objects that go to library +pkgLibObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] +pkgLibObjects path dist stage way = do + let pkgData = path dist "package-data.mk" + buildDir = path dist "build" + split <- splitObjects stage + if split + then do + let suffixes = ["_" ++ osuf way ++ "_split//*"] + findModuleFiles pkgData [buildDir] suffixes + else pkgDepObjects path dist way + +findModuleFiles :: FilePath -> [FilePath] -> [String] -> Action [FilePath] +findModuleFiles pkgData directories suffixes = do + mods <- arg (Modules pkgData) + files <- getDirectoryFiles "" $ do + dir <- directories + modPath <- map (replaceEq '.' pathSeparator) mods + suffix <- suffixes + return $ dir modPath ++ suffix + return $ map normaliseEx files From git at git.haskell.org Thu Oct 26 23:04:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:04:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement terseRun and arArgs functions. (30138cb) Message-ID: <20171026230457.A44F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30138cb17e6a67a6036b8c0077d393134c57edd2/ghc >--------------------------------------------------------------- commit 30138cb17e6a67a6036b8c0077d393134c57edd2 Author: Andrey Mokhov Date: Tue Jan 13 02:27:29 2015 +0000 Implement terseRun and arArgs functions. >--------------------------------------------------------------- 30138cb17e6a67a6036b8c0077d393134c57edd2 src/Oracles/Builder.hs | 35 ++++++++++++++++++++++++++++++++++- 1 file changed, 34 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 16b5da5..e4cd7da 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,8 @@ module Oracles.Builder ( Builder (..), - with, run, specified + with, run, terseRun, specified, + arArgs ) where import Data.Char @@ -24,6 +25,7 @@ data Builder = Ar | GhcCabal | Ghc Stage | GhcPkg Stage + deriving Show instance ShowArgs Builder where showArgs builder = showArgs $ fmap words $ do @@ -97,6 +99,33 @@ run builder args = do [exe] <- showArgs builder cmd [exe] =<< args +-- Run the builder with a given collection of arguments printing out a +-- terse commentary with only 'interesting' info for the builder. +-- Raises an error if the builder is not uniquely specified in config files +terseRun :: Builder -> Args -> Action () +terseRun builder args = do + needBuilder builder + [exe] <- showArgs builder + args' <- args + putNormal $ "--------\nRunning " ++ show builder ++ " with arguments:" + mapM_ (putNormal . (" " ++)) $ interestingInfo builder args' + putNormal "--------" + quietly $ cmd [exe] args' + +interestingInfo :: Builder -> [String] -> [String] +interestingInfo builder ss = case builder of + Ar -> prefixAndSuffix 3 1 ss + Ghc _ -> if head ss == "-M" + then prefixAndSuffix 1 1 ss + else prefixAndSuffix 0 4 ss + GhcPkg _ -> prefixAndSuffix 2 0 ss + GhcCabal -> prefixAndSuffix 3 0 ss + where + prefixAndSuffix n m ss = + if length ss <= n + m + then ss + else take n ss ++ ["..."] ++ drop (length ss - m) ss + -- Check if the builder is uniquely specified in config files specified :: Builder -> Condition specified builder = do @@ -104,3 +133,7 @@ specified builder = do return $ case exes of [_] -> True _ -> False + +-- TODO: generalise for other builders +arArgs :: Args +arArgs = arg "q" From git at git.haskell.org Thu Oct 26 23:05:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use terseRun and new configuration options. (efb5972) Message-ID: <20171026230501.186F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efb59728189c8a5bd9270d1c3f00787ed4b27913/ghc >--------------------------------------------------------------- commit efb59728189c8a5bd9270d1c3f00787ed4b27913 Author: Andrey Mokhov Date: Tue Jan 13 02:29:17 2015 +0000 Use terseRun and new configuration options. >--------------------------------------------------------------- efb59728189c8a5bd9270d1c3f00787ed4b27913 src/Package/Compile.hs | 4 ++-- src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 6 +++--- 3 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 50cf412..6badbb7 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -43,7 +43,7 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = let deps = concat $ snd $ unzip $ filter ((== out) . fst) depContents srcs = filter ("//*hs" ?==) deps -- TODO: handle *.c sources need deps - run (Ghc stage) $ suffixArgs way + terseRun (Ghc stage) $ suffixArgs way <> wayHcArgs way <> arg SrcHcOpts <> packageArgs stage pkgData @@ -51,6 +51,6 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = -- TODO: now we have both -O and -O2 <> arg ["-Wall", "-XHaskell2010", "-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir - <> arg "-split-objs" + <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) <> arg ["-o", out] diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 7ff0d7d..a73a521 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -93,6 +93,6 @@ buildPackageData (Package name path _) (stage, dist, settings) = need ["shake/src/Package/Data.hs"] need [path name <.> "cabal"] when (doesFileExist $ configure <.> "ac") $ need [configure] - run GhcCabal cabalArgs - when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs + terseRun GhcCabal cabalArgs + when (registerPackage settings) $ terseRun (GhcPkg stage) ghcPkgArgs postProcessPackageData $ pathDist "package-data.mk" diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 1cb512d..f3a494b 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -10,13 +10,13 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = in (buildDir name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] - run (Ghc stage) $ arg "-M" + terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData <> includeArgs path dist <> productArgs ["-odir", "-stubdir"] buildDir <> arg ["-dep-makefile", out] - <> productArgs "-dep-suffix" (map suffix <$> ways settings) - <> srcArgs path pkgData + <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) + <> arg (pkgHsSources path dist) -- TODO: Check that skipping all _HC_OPTS is safe. -- <> arg SrcHcOpts -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? From git at git.haskell.org Thu Oct 26 23:05:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement new build rule: buildPackageLibrary. (2143dce) Message-ID: <20171026230504.8ED3D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2143dce721122b3e9e0b08fb4691160305f0ba99/ghc >--------------------------------------------------------------- commit 2143dce721122b3e9e0b08fb4691160305f0ba99 Author: Andrey Mokhov Date: Tue Jan 13 02:30:01 2015 +0000 Implement new build rule: buildPackageLibrary. >--------------------------------------------------------------- 2143dce721122b3e9e0b08fb4691160305f0ba99 src/Package/Library.hs | 25 +++++++++++++++++++++++++ 1 file changed, 25 insertions(+) diff --git a/src/Package/Library.hs b/src/Package/Library.hs new file mode 100644 index 0000000..9598b1a --- /dev/null +++ b/src/Package/Library.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module Package.Library (buildPackageLibrary) where + +import Package.Base + +{- "/usr/bin/ar" q +libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a + at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents +-} + +-- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents +-- AR_OPTS = $(SRC_AR_OPTS) $(WAY$(_way)_AR_OPTS) $(EXTRA_AR_OPTS) + +buildPackageLibrary :: Package -> TodoItem -> Rules () +buildPackageLibrary (Package _ path _) (stage, dist, _) = + let buildDir = path dist "build" + pkgData = path dist "package-data.mk" + in + (buildDir "*a") %> \out -> do + let way = detectWay $ tail $ takeExtension out + need ["shake/src/Package/Library.hs"] + depObjs <- pkgDepObjects path dist way + need depObjs + libObjs <- pkgLibObjects path dist stage way + terseRun Ar $ arArgs <+> out <+> libObjs From git at git.haskell.org Thu Oct 26 23:05:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove old library files before calling Ar. (5aa3add) Message-ID: <20171026230507.F36883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5aa3addc4ed59f1984e040415d707f4067f82007/ghc >--------------------------------------------------------------- commit 5aa3addc4ed59f1984e040415d707f4067f82007 Author: Andrey Mokhov Date: Tue Jan 13 02:45:49 2015 +0000 Remove old library files before calling Ar. >--------------------------------------------------------------- 5aa3addc4ed59f1984e040415d707f4067f82007 src/Package/Library.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 9598b1a..0c2e1f8 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -22,4 +22,5 @@ buildPackageLibrary (Package _ path _) (stage, dist, _) = depObjs <- pkgDepObjects path dist way need depObjs libObjs <- pkgLibObjects path dist stage way + liftIO $ removeFiles "" [out] terseRun Ar $ arArgs <+> out <+> libObjs From git at git.haskell.org Thu Oct 26 23:05:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve terseRun. (4fcb471) Message-ID: <20171026230511.5B9023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fcb471826530ba60abdc40b2ed4304910edf24a/ghc >--------------------------------------------------------------- commit 4fcb471826530ba60abdc40b2ed4304910edf24a Author: Andrey Mokhov Date: Tue Jan 13 03:05:35 2015 +0000 Improve terseRun. >--------------------------------------------------------------- 4fcb471826530ba60abdc40b2ed4304910edf24a src/Oracles/Builder.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index e4cd7da..ffc3cf5 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -122,9 +122,13 @@ interestingInfo builder ss = case builder of GhcCabal -> prefixAndSuffix 3 0 ss where prefixAndSuffix n m ss = - if length ss <= n + m + if length ss <= n + m + 1 then ss - else take n ss ++ ["..."] ++ drop (length ss - m) ss + else take n ss + ++ ["... skipping " + ++ show (length ss - n - m) + ++ " arguments ..."] + ++ drop (length ss - m) ss -- Check if the builder is uniquely specified in config files specified :: Builder -> Condition From git at git.haskell.org Thu Oct 26 23:05:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise buildPackageDependencies rule. (7c45e18) Message-ID: <20171026230514.C35733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c45e18e0d1ef091aac126e9a316ac9cd5f0a2bb/ghc >--------------------------------------------------------------- commit 7c45e18e0d1ef091aac126e9a316ac9cd5f0a2bb Author: Andrey Mokhov Date: Tue Jan 13 03:13:10 2015 +0000 Optimise buildPackageDependencies rule. >--------------------------------------------------------------- 7c45e18e0d1ef091aac126e9a316ac9cd5f0a2bb src/Package/Dependencies.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index f3a494b..7390b2e 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -14,10 +14,13 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = <> packageArgs stage pkgData <> includeArgs path dist <> productArgs ["-odir", "-stubdir"] buildDir - <> arg ["-dep-makefile", out] + <> arg ["-dep-makefile", out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) <> arg (pkgHsSources path dist) -- TODO: Check that skipping all _HC_OPTS is safe. -- <> arg SrcHcOpts -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? -- <> wayHcOpts vanilla + -- Avoid rebuilding dependecies of out if it hasn't changed: + copyFileChanged (out <.> "new") out + removeFilesAfter "." [out <.> "new"] From git at git.haskell.org Thu Oct 26 23:05:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise buildPackageDependencies rule. (1e5c095) Message-ID: <20171026230518.4547A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1e5c0952d044d8c1c16988e221d014443b04fb19/ghc >--------------------------------------------------------------- commit 1e5c0952d044d8c1c16988e221d014443b04fb19 Author: Andrey Mokhov Date: Tue Jan 13 03:30:54 2015 +0000 Optimise buildPackageDependencies rule. >--------------------------------------------------------------- 1e5c0952d044d8c1c16988e221d014443b04fb19 src/Package/Dependencies.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 7390b2e..6339adb 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -22,5 +22,7 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? -- <> wayHcOpts vanilla -- Avoid rebuilding dependecies of out if it hasn't changed: - copyFileChanged (out <.> "new") out + -- Note: cannot use copyFileChanged as it depends on the source file + deps <- liftIO $ readFile $ out <.> "new" + writeFileChanged out deps removeFilesAfter "." [out <.> "new"] From git at git.haskell.org Thu Oct 26 23:05:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Print more diagnostic info. (0ad3af2) Message-ID: <20171026230521.ADD5F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ad3af27554bdaa8ba765353ca53256d4f342f32/ghc >--------------------------------------------------------------- commit 0ad3af27554bdaa8ba765353ca53256d4f342f32 Author: Andrey Mokhov Date: Tue Jan 13 04:05:59 2015 +0000 Print more diagnostic info. >--------------------------------------------------------------- 0ad3af27554bdaa8ba765353ca53256d4f342f32 src/Oracles.hs | 1 + src/Oracles/PackageData.hs | 2 ++ src/Package/Library.hs | 16 ++++++++++++---- 3 files changed, 15 insertions(+), 4 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 3a0c430..5b2ff11 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -49,6 +49,7 @@ packageDataOracle :: Rules () packageDataOracle = do pkgData <- newCache $ \file -> do need [file] + putNormal $ "Parsing " ++ file ++ "..." liftIO $ readConfigFile file addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 6bffafd..66a3f55 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -18,6 +18,7 @@ data PackageData = Modules FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath + | Synopsis FilePath instance ShowArgs PackageData where showArgs packageData = do @@ -28,6 +29,7 @@ instance ShowArgs PackageData where IncludeDirs file -> ("INCLUDE_DIRS", file, ".") Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) + Synopsis file -> ("SYNOPSIS" , file, "" ) fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key res <- askOracle $ PackageDataKey (file, fullKey) return $ words $ case res of diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 0c2e1f8..6660a2f 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -5,14 +5,16 @@ import Package.Base {- "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a - at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a +.contents -} --- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents +-- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) +-- $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents -- AR_OPTS = $(SRC_AR_OPTS) $(WAY$(_way)_AR_OPTS) $(EXTRA_AR_OPTS) buildPackageLibrary :: Package -> TodoItem -> Rules () -buildPackageLibrary (Package _ path _) (stage, dist, _) = +buildPackageLibrary (Package name path _) (stage, dist, _) = let buildDir = path dist "build" pkgData = path dist "package-data.mk" in @@ -22,5 +24,11 @@ buildPackageLibrary (Package _ path _) (stage, dist, _) = depObjs <- pkgDepObjects path dist way need depObjs libObjs <- pkgLibObjects path dist stage way - liftIO $ removeFiles "" [out] + liftIO $ removeFiles "." [out] terseRun Ar $ arArgs <+> out <+> libObjs + when (way == vanilla) $ do + synopsis <- unwords <$> arg (Synopsis pkgData) + putNormal $ "Successfully built library for package " + ++ name ++ "." + putNormal $ "Synopsis: " ++ synopsis ++ "." + From git at git.haskell.org Thu Oct 26 23:05:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add link rule. (7b1964e) Message-ID: <20171026230525.4D72C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b1964efccba7ca2072e41f0e782a4ccfd843244/ghc >--------------------------------------------------------------- commit 7b1964efccba7ca2072e41f0e782a4ccfd843244 Author: Andrey Mokhov Date: Tue Jan 13 04:57:33 2015 +0000 Add link rule. >--------------------------------------------------------------- 7b1964efccba7ca2072e41f0e782a4ccfd843244 doc/deepseq-build-progress.txt | 8 +++++++- src/Oracles/Builder.hs | 8 +++----- src/Package.hs | 3 ++- src/Package/Library.hs | 44 +++++++++++++++++++++++++----------------- 4 files changed, 38 insertions(+), 25 deletions(-) diff --git a/doc/deepseq-build-progress.txt b/doc/deepseq-build-progress.txt index f951d61..0df6c05 100644 --- a/doc/deepseq-build-progress.txt +++ b/doc/deepseq-build-progress.txt @@ -54,14 +54,20 @@ echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0 # Done: "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents /usr/bin/ar: creating libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents # Done: "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.p_o - +# Done: "C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" -r -o libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o libraries/deepseq/dist-install/build/Control/DeepSeq.o + +# Done: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents + +# Skipping: /usr/bin/find libraries/deepseq/dist-install/build/Control/DeepSeq_p_o_split -name '*.p_o' -print >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index ffc3cf5..71f8575 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,8 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, terseRun, specified, - arArgs + with, run, terseRun, specified ) where import Data.Char @@ -115,11 +114,13 @@ terseRun builder args = do interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of Ar -> prefixAndSuffix 3 1 ss + Ld -> prefixAndSuffix 4 0 ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss else prefixAndSuffix 0 4 ss GhcPkg _ -> prefixAndSuffix 2 0 ss GhcCabal -> prefixAndSuffix 3 0 ss + _ -> ss where prefixAndSuffix n m ss = if length ss <= n + m + 1 @@ -138,6 +139,3 @@ specified builder = do [_] -> True _ -> False --- TODO: generalise for other builders -arArgs :: Args -arArgs = arg "q" diff --git a/src/Package.hs b/src/Package.hs index a3fcf89..8b41809 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -23,7 +23,8 @@ packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" - , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" ] + , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" + , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 6660a2f..529d777 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -3,18 +3,8 @@ module Package.Library (buildPackageLibrary) where import Package.Base -{- "/usr/bin/ar" q -libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a - at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a -.contents --} - --- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) --- $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents --- AR_OPTS = $(SRC_AR_OPTS) $(WAY$(_way)_AR_OPTS) $(EXTRA_AR_OPTS) - -buildPackageLibrary :: Package -> TodoItem -> Rules () -buildPackageLibrary (Package name path _) (stage, dist, _) = +arRule :: Package -> TodoItem -> Rules () +arRule (Package _ path _) (stage, dist, _) = let buildDir = path dist "build" pkgData = path dist "package-data.mk" in @@ -25,10 +15,28 @@ buildPackageLibrary (Package name path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] - terseRun Ar $ arArgs <+> out <+> libObjs - when (way == vanilla) $ do - synopsis <- unwords <$> arg (Synopsis pkgData) - putNormal $ "Successfully built library for package " - ++ name ++ "." - putNormal $ "Synopsis: " ++ synopsis ++ "." + terseRun Ar $ "q" <+> out <+> libObjs +{- "C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" -r -o +libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o +libraries/deepseq/dist-install/build/Control/DeepSeq.o +-} + +ldRule :: Package -> TodoItem -> Rules () +ldRule (Package name path _) (stage, dist, _) = + let buildDir = path dist "build" + pkgData = path dist "package-data.mk" + in + priority 2 $ (buildDir "*.o") %> \out -> do + need ["shake/src/Package/Library.hs"] + depObjs <- pkgDepObjects path dist vanilla + need depObjs + terseRun Ld $ arg (ConfLdLinkerArgs stage) + <> arg ["-r", "-o", out] + <> arg depObjs + synopsis <- unwords <$> arg (Synopsis pkgData) + putNormal $ "Successfully built package " ++ name ++ "." + putNormal $ "Package synopsis: " ++ synopsis ++ "." + +buildPackageLibrary :: Package -> TodoItem -> Rules () +buildPackageLibrary = arRule <> ldRule \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:05:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (4863449) Message-ID: <20171026230528.BBE513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4863449633ec90de6607df0d80f4b2a8f40ecdc7/ghc >--------------------------------------------------------------- commit 4863449633ec90de6607df0d80f4b2a8f40ecdc7 Author: Andrey Mokhov Date: Tue Jan 13 05:12:38 2015 +0000 Clean up. >--------------------------------------------------------------- 4863449633ec90de6607df0d80f4b2a8f40ecdc7 doc/deepseq-build-progress.txt | 6 ++++++ src/Oracles.hs | 2 +- src/Oracles/Builder.hs | 2 +- src/Package/Base.hs | 6 +++--- src/Package/Compile.hs | 2 +- src/Package/Data.hs | 2 +- src/Package/Library.hs | 9 ++------- 7 files changed, 15 insertions(+), 14 deletions(-) diff --git a/doc/deepseq-build-progress.txt b/doc/deepseq-build-progress.txt index 0df6c05..84845fe 100644 --- a/doc/deepseq-build-progress.txt +++ b/doc/deepseq-build-progress.txt @@ -70,9 +70,15 @@ echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0 # Skipping: /usr/bin/find libraries/deepseq/dist-install/build/Control/DeepSeq_p_o_split -name '*.p_o' -print >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents + +# Done: "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents /usr/bin/ar: creating libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents + + "inplace/bin/mkdirhier" libraries/deepseq/dist-install/doc/html/deepseq//. "C:/msys/home/chEEtah/ghc/inplace/bin/haddock" --odir="libraries/deepseq/dist-install/doc/html/deepseq" --no-tmp-comp-dir --dump-interface=libraries/deepseq/dist-install/doc/html/deepseq/deepseq.haddock --html --hoogle --title="deepseq-1.4.0.0: Deep evaluation of data structures" --prologue="libraries/deepseq/dist-install/haddock-prologue.txt" --read-interface=../array-0.5.0.1,../array-0.5.0.1/src/%{MODULE/./-}.html\#%{NAME},libraries/array/dist-install/doc/html/array/array.haddock --read-interface=../base-4.8.0.0,../base-4.8.0.0/src/%{MODULE/./-}.html\#%{NAME},libraries/base/dist-install/doc/html/base/base.haddock --read-interface=../ghc-prim-0.3.1.0,../ghc-prim-0.3.1.0/src/%{MODULE/./-}.html\#%{NAME},libraries/ghc-prim/dist-install/doc/html/ghc-prim/ghc-prim.haddock --optghc=-hisuf --optghc=hi --optghc=-osuf --optghc=o --optghc=-hcsuf --optghc=hc --optghc=-static --optghc=-H32m --optghc=-O --optghc=-this-package-key --optghc=deeps_FT5iVCELxOr62eHY0nbvnU --optghc=-hide-all-package s --optghc=-i --optghc=-ilibraries/deepseq/. --optghc=-ilibraries/deepseq/dist-install/build --optghc=-ilibraries/deepseq/dist-install/build/autogen --optghc=-Ilibraries/deepseq/dist-install/build --optghc=-Ilibraries/deepseq/dist-install/build/autogen --optghc=-Ilibraries/deepseq/. --optghc=-optP-include --optghc=-optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h --optghc=-package-key --optghc=array_3w0nMK0JfaFJPpLFn2yWAJ --optghc=-package-key --optghc=base_469rOtLAqwTGFEOGWxSUiQ --optghc=-package-key --optghc=ghcpr_FgrV6cgh2JHBlbcx1OSlwt --optghc=-Wall --optghc=-XHaskell2010 --optghc=-O2 --optghc=-no-user-package-db --optghc=-rtsopts --optghc=-odir --optghc=libraries/deepseq/dist-install/build --optghc=-hidir --optghc=libraries/deepseq/dist-install/build --optghc=-stubdir --optghc=libraries/deepseq/dist-install/build --optghc=-split-objs libraries/deepseq/./Control/DeepSeq.hs +RTS -tlibraries/deepseq/dist-install/doc/html/deepseq/deepseq.haddock.t --machine-reada ble Haddock coverage: diff --git a/src/Oracles.hs b/src/Oracles.hs index 5b2ff11..2fe8430 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -49,7 +49,7 @@ packageDataOracle :: Rules () packageDataOracle = do pkgData <- newCache $ \file -> do need [file] - putNormal $ "Parsing " ++ file ++ "..." + putNormal $ "Parsing " ++ toStandard file ++ "..." liftIO $ readConfigFile file addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 71f8575..8a2c5b2 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -27,7 +27,7 @@ data Builder = Ar deriving Show instance ShowArgs Builder where - showArgs builder = showArgs $ fmap words $ do + showArgs builder = showArgs $ fmap (map toStandard . words) $ do let key = case builder of Ar -> "ar" Ld -> "ld" diff --git a/src/Package/Base.hs b/src/Package/Base.hs index a8de80d..9882900 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -49,7 +49,7 @@ libraryPackage :: String -> Stage -> (Stage -> Settings) -> Package libraryPackage name stage settings = Package name - ("libraries" name) + (toStandard $ "libraries" name) [( stage, if stage == Stage0 then "dist-boot" else "dist-install", @@ -123,7 +123,7 @@ pkgDepObjects path dist way = do buildDir = path dist "build" hs2obj = (buildDir ++) . drop (length path) . (-<.> osuf way) srcs <- pkgHsSources path dist - return $ map hs2obj srcs + return $ map (toStandard . hs2obj) srcs -- Find objects that go to library pkgLibObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] @@ -145,4 +145,4 @@ findModuleFiles pkgData directories suffixes = do modPath <- map (replaceEq '.' pathSeparator) mods suffix <- suffixes return $ dir modPath ++ suffix - return $ map normaliseEx files + return $ map (toStandard . normaliseEx) files diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 6badbb7..760c96f 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -53,4 +53,4 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) - <> arg ["-o", out] + <> arg ["-o", toStandard out] diff --git a/src/Package/Data.hs b/src/Package/Data.hs index a73a521..ef89ed0 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -79,7 +79,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = ghcPkgArgs = arg ["update", "--force"] <> (stage == Stage0) arg "--package-db=libraries/bootstrapping.conf" - <> arg (pathDist "inplace-pkg-config") + <> arg (toStandard $ pathDist "inplace-pkg-config") in (pathDist ) <$> [ "package-data.mk" diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 529d777..9f200e4 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -15,12 +15,7 @@ arRule (Package _ path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] - terseRun Ar $ "q" <+> out <+> libObjs - -{- "C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" -r -o -libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o -libraries/deepseq/dist-install/build/Control/DeepSeq.o --} + terseRun Ar $ "q" <+> toStandard out <+> libObjs ldRule :: Package -> TodoItem -> Rules () ldRule (Package name path _) (stage, dist, _) = @@ -32,7 +27,7 @@ ldRule (Package name path _) (stage, dist, _) = depObjs <- pkgDepObjects path dist vanilla need depObjs terseRun Ld $ arg (ConfLdLinkerArgs stage) - <> arg ["-r", "-o", out] + <> arg ["-r", "-o", toStandard out] <> arg depObjs synopsis <- unwords <$> arg (Synopsis pkgData) putNormal $ "Successfully built package " ++ name ++ "." From git at git.haskell.org Thu Oct 26 23:05:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add array package. (d4aabcd) Message-ID: <20171026230532.22AE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4aabcd7e1e1d3de6302f0b8d436a5bcf4794f5b/ghc >--------------------------------------------------------------- commit d4aabcd7e1e1d3de6302f0b8d436a5bcf4794f5b Author: Andrey Mokhov Date: Tue Jan 13 06:31:37 2015 +0000 Add array package. >--------------------------------------------------------------- d4aabcd7e1e1d3de6302f0b8d436a5bcf4794f5b src/Package.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 8b41809..e29551f 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -10,7 +10,8 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] -packages = [libraryPackage "deepseq" Stage1 defaultSettings] +packages = [libraryPackage "array" Stage1 defaultSettings, + libraryPackage "deepseq" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -24,7 +25,10 @@ packageRules = do -- TODO: control targets from commang line arguments want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" - , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" ] + , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" + , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.a" + , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.p_a" + , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:05:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add hiRule. (fae8451) Message-ID: <20171026230535.A71A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fae8451a106cc2c298154d586201ce8924b9d701/ghc >--------------------------------------------------------------- commit fae8451a106cc2c298154d586201ce8924b9d701 Author: Andrey Mokhov Date: Tue Jan 13 06:32:36 2015 +0000 Add hiRule. >--------------------------------------------------------------- fae8451a106cc2c298154d586201ce8924b9d701 src/Package/Compile.hs | 17 +++++++++++++++-- 1 file changed, 15 insertions(+), 2 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 760c96f..80835f8 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -29,8 +29,8 @@ suffixArgs way = arg ["-hisuf", hisuf way] <> arg [ "-osuf", osuf way] <> arg ["-hcsuf", hcsuf way] -buildPackageCompile :: Package -> TodoItem -> Rules () -buildPackageCompile (Package name path _) (stage, dist, settings) = +oRule :: Package -> TodoItem -> Rules () +oRule (Package name path _) (stage, dist, settings) = let buildDir = path dist "build" pkgData = path dist "package-data.mk" depFile = buildDir name <.> "m" @@ -54,3 +54,16 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) <> arg ["-o", toStandard out] + +-- TODO: This rule looks a bit of a hack... combine it with the above? +hiRule :: Package -> TodoItem -> Rules () +hiRule (Package name path _) (stage, dist, settings) = + let buildDir = path dist "build" + in + (buildDir "*hi") %> \out -> do + let way = detectWay $ tail $ takeExtension out + oFile = out -<.> osuf way + need [oFile] + +buildPackageCompile :: Package -> TodoItem -> Rules () +buildPackageCompile = oRule <> hiRule From git at git.haskell.org Thu Oct 26 23:05:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split Ar arguments into chunks of length 100 at most. (821776b) Message-ID: <20171026230539.1BCDE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/821776b91341b4651f30f56ec08069a17c0d0a2b/ghc >--------------------------------------------------------------- commit 821776b91341b4651f30f56ec08069a17c0d0a2b Author: Andrey Mokhov Date: Tue Jan 13 06:33:44 2015 +0000 Split Ar arguments into chunks of length 100 at most. >--------------------------------------------------------------- 821776b91341b4651f30f56ec08069a17c0d0a2b src/Package/Library.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 9f200e4..ec2b845 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -2,6 +2,7 @@ module Package.Library (buildPackageLibrary) where import Package.Base +import Data.List.Split arRule :: Package -> TodoItem -> Rules () arRule (Package _ path _) (stage, dist, _) = @@ -15,7 +16,8 @@ arRule (Package _ path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] - terseRun Ar $ "q" <+> toStandard out <+> libObjs + forM_ (chunksOf 100 libObjs) $ \os -> do + terseRun Ar $ "q" <+> toStandard out <+> os ldRule :: Package -> TodoItem -> Rules () ldRule (Package name path _) (stage, dist, _) = From git at git.haskell.org Thu Oct 26 23:05:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add toStandard to varios places. (5d2cf2c) Message-ID: <20171026230542.89A953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d2cf2c3163f37cb53d0217eae93582980e211de/ghc >--------------------------------------------------------------- commit 5d2cf2c3163f37cb53d0217eae93582980e211de Author: Andrey Mokhov Date: Tue Jan 13 06:34:24 2015 +0000 Add toStandard to varios places. >--------------------------------------------------------------- 5d2cf2c3163f37cb53d0217eae93582980e211de src/Package/Base.hs | 11 ++++++----- src/Package/Dependencies.hs | 8 ++++---- 2 files changed, 10 insertions(+), 9 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 9882900..f6c70ea 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -84,7 +84,8 @@ bootPkgConstraints = mempty -- sed "s/[^0-9.]//g")")) pathArgs :: ShowArgs a => String -> FilePath -> a -> Args -pathArgs key path as = map (\a -> key ++ normaliseEx (path a)) <$> arg as +pathArgs key path as = + map (\a -> key ++ toStandard (normaliseEx $ path a)) <$> arg as packageArgs :: Stage -> FilePath -> Args packageArgs stage pkgData = do @@ -100,14 +101,14 @@ packageArgs stage pkgData = do includeArgs :: FilePath -> FilePath -> Args includeArgs path dist = - let pkgData = path dist "package-data.mk" - buildDir = path dist "build" + let pkgData = toStandard $ path dist "package-data.mk" + buildDir = toStandard $ path dist "build" in arg "-i" <> pathArgs "-i" path (SrcDirs pkgData) - <> concatArgs ["-i", "-I"] [buildDir, buildDir "autogen"] + <> concatArgs ["-i", "-I"] [buildDir, toStandard $ buildDir "autogen"] <> pathArgs "-I" path (IncludeDirs pkgData) <> arg "-optP-include" -- TODO: Shall we also add -cpp? - <> concatArgs "-optP" (buildDir "autogen/cabal_macros.h") + <> concatArgs "-optP" (toStandard $ buildDir "autogen/cabal_macros.h") pkgHsSources :: FilePath -> FilePath -> Action [FilePath] pkgHsSources path dist = do diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 6339adb..63ed508 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -5,16 +5,16 @@ import Package.Base buildPackageDependencies :: Package -> TodoItem -> Rules () buildPackageDependencies (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" - pkgData = path dist "package-data.mk" + let buildDir = toStandard $ path dist "build" + pkgData = toStandard $ path dist "package-data.mk" in (buildDir name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData <> includeArgs path dist - <> productArgs ["-odir", "-stubdir"] buildDir - <> arg ["-dep-makefile", out <.> "new"] + <> productArgs ["-odir", "-stubdir", "-hidir"] buildDir + <> arg ["-dep-makefile", toStandard $ out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) <> arg (pkgHsSources path dist) -- TODO: Check that skipping all _HC_OPTS is safe. From git at git.haskell.org Thu Oct 26 23:05:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a cool screenshot. (9f89177) Message-ID: <20171026230545.ECF303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9f8917750b4d83c15934a2e9dfbf51edf76d406d/ghc >--------------------------------------------------------------- commit 9f8917750b4d83c15934a2e9dfbf51edf76d406d Author: Andrey Mokhov Date: Tue Jan 13 06:34:54 2015 +0000 Add a cool screenshot. >--------------------------------------------------------------- 9f8917750b4d83c15934a2e9dfbf51edf76d406d doc/boom.png | Bin 0 -> 91102 bytes 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/doc/boom.png b/doc/boom.png new file mode 100644 index 0000000..834e1bb Binary files /dev/null and b/doc/boom.png differ From git at git.haskell.org Thu Oct 26 23:05:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove a (useless?) output from the buildPackageData rule. (90c4840) Message-ID: <20171026230549.6F0F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90c48400bd72d55c030707b62eb3b4eb42eac6b1/ghc >--------------------------------------------------------------- commit 90c48400bd72d55c030707b62eb3b4eb42eac6b1 Author: Andrey Mokhov Date: Tue Jan 13 06:42:45 2015 +0000 Remove a (useless?) output from the buildPackageData rule. >--------------------------------------------------------------- 90c48400bd72d55c030707b62eb3b4eb42eac6b1 src/Package/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index ef89ed0..d3b13a5 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -88,7 +88,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = , "setup-config" , "build" "autogen" "cabal_macros.h" -- TODO: Is this needed? Also check out Paths_cpsa.hs. - , "build" "autogen" ("Paths_" ++ name) <.> "hs" + -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do need ["shake/src/Package/Data.hs"] need [path name <.> "cabal"] From git at git.haskell.org Thu Oct 26 23:05:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add bin-package-db package. (cd02d00) Message-ID: <20171026230552.CE3623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cd02d00639738e151e77288de9d116e286cb83c1/ghc >--------------------------------------------------------------- commit cd02d00639738e151e77288de9d116e286cb83c1 Author: Andrey Mokhov Date: Tue Jan 13 06:43:02 2015 +0000 Add bin-package-db package. >--------------------------------------------------------------- cd02d00639738e151e77288de9d116e286cb83c1 src/Package.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index e29551f..d2fd4db 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -10,8 +10,9 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] -packages = [libraryPackage "array" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings] +packages = [libraryPackage "array" Stage1 defaultSettings, + libraryPackage "deepseq" Stage1 defaultSettings, + libraryPackage "bin-package-db" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -28,7 +29,10 @@ packageRules = do , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.a" , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.p_a" - , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" ] + , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" + , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.a" + , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.p_a" + , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:05:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CppOpts. (316ff4c) Message-ID: <20171026230556.3C97B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/316ff4cb2e421831281e42b09fb90ba5dae2b239/ghc >--------------------------------------------------------------- commit 316ff4cb2e421831281e42b09fb90ba5dae2b239 Author: Andrey Mokhov Date: Tue Jan 13 07:28:48 2015 +0000 Add CppOpts. >--------------------------------------------------------------- 316ff4cb2e421831281e42b09fb90ba5dae2b239 src/Oracles/PackageData.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 66a3f55..bf94713 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -19,6 +19,7 @@ data PackageData = Modules FilePath | Deps FilePath | DepKeys FilePath | Synopsis FilePath + | CppOpts FilePath instance ShowArgs PackageData where showArgs packageData = do @@ -30,6 +31,7 @@ instance ShowArgs PackageData where Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) Synopsis file -> ("SYNOPSIS" , file, "" ) + CppOpts file -> ("CPP_OPTS" , file, "" ) fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key res <- askOracle $ PackageDataKey (file, fullKey) return $ words $ case res of From git at git.haskell.org Thu Oct 26 23:05:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:05:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add binary package. (02297c2) Message-ID: <20171026230559.9729E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02297c23579d7a11d9d99efacda7a328801cbfaa/ghc >--------------------------------------------------------------- commit 02297c23579d7a11d9d99efacda7a328801cbfaa Author: Andrey Mokhov Date: Tue Jan 13 07:29:15 2015 +0000 Add binary package. >--------------------------------------------------------------- 02297c23579d7a11d9d99efacda7a328801cbfaa src/Package.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index d2fd4db..899e48a 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -12,7 +12,8 @@ import Package.Dependencies packages :: [Package] packages = [libraryPackage "array" Stage1 defaultSettings, libraryPackage "deepseq" Stage1 defaultSettings, - libraryPackage "bin-package-db" Stage1 defaultSettings] + libraryPackage "bin-package-db" Stage1 defaultSettings, + libraryPackage "binary" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -32,7 +33,10 @@ packageRules = do , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.a" , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.p_a" - , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" ] + , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" + , "libraries/binary/dist-install/build/HSbinar_8WpSY1EWq5j1AwY619xVVw.o" + , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.a" + , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.p_a" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:06:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing options and pkgDepObjects. (92352f7) Message-ID: <20171026230603.130663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92352f7763115e6a78452b48d9872681a4dca3eb/ghc >--------------------------------------------------------------- commit 92352f7763115e6a78452b48d9872681a4dca3eb Author: Andrey Mokhov Date: Tue Jan 13 07:29:56 2015 +0000 Fix missing options and pkgDepObjects. >--------------------------------------------------------------- 92352f7763115e6a78452b48d9872681a4dca3eb src/Package/Base.hs | 7 ++++--- src/Package/Compile.hs | 3 ++- src/Package/Dependencies.hs | 1 + 3 files changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index f6c70ea..bac6801 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -122,9 +122,10 @@ pkgDepObjects :: FilePath -> FilePath -> Way -> Action [FilePath] pkgDepObjects path dist way = do let pkgData = path dist "package-data.mk" buildDir = path dist "build" - hs2obj = (buildDir ++) . drop (length path) . (-<.> osuf way) - srcs <- pkgHsSources path dist - return $ map (toStandard . hs2obj) srcs + dirs <- map (normaliseEx . (path )) <$> arg (SrcDirs pkgData) + fmap concat $ forM dirs $ \d -> + map (toStandard . (buildDir ++) . (-<.> osuf way) . drop (length d)) + <$> (findModuleFiles pkgData [d] [".hs", ".lhs"]) -- Find objects that go to library pkgLibObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 80835f8..c42d592 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -48,6 +48,7 @@ oRule (Package name path _) (stage, dist, settings) = <> arg SrcHcOpts <> packageArgs stage pkgData <> includeArgs path dist + <> concatArgs ["-optP"] (CppOpts pkgData) -- TODO: now we have both -O and -O2 <> arg ["-Wall", "-XHaskell2010", "-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir @@ -55,7 +56,7 @@ oRule (Package name path _) (stage, dist, settings) = <> arg ("-c":srcs) <> arg ["-o", toStandard out] --- TODO: This rule looks a bit of a hack... combine it with the above? +-- TODO: This rule looks hacky... combine it with the above? hiRule :: Package -> TodoItem -> Rules () hiRule (Package name path _) (stage, dist, settings) = let buildDir = path dist "build" diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 63ed508..fc9f4af 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -13,6 +13,7 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData <> includeArgs path dist + <> concatArgs ["-optP"] (CppOpts pkgData) <> productArgs ["-odir", "-stubdir", "-hidir"] buildDir <> arg ["-dep-makefile", toStandard $ out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) From git at git.haskell.org Thu Oct 26 23:06:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix dropDynamic. (d1ade7d) Message-ID: <20171026230606.765BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1ade7d5917eeea88c2034dc52bb8bf100bfc05a/ghc >--------------------------------------------------------------- commit d1ade7d5917eeea88c2034dc52bb8bf100bfc05a Author: Andrey Mokhov Date: Tue Jan 13 13:01:30 2015 +0000 Fix dropDynamic. >--------------------------------------------------------------- d1ade7d5917eeea88c2034dc52bb8bf100bfc05a src/Ways.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index b478a04..24c1a80 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -14,7 +14,7 @@ module Ways ( wayHcArgs, wayPrefix, - hisuf, osuf, hcsuf, + hisuf, osuf, hcsuf, obootsuf, ssuf, libsuf, detectWay ) where @@ -125,7 +125,7 @@ dropDynamic way | way == debugDynamic = debug | way == loggingDynamic = logging | way == threadedLoggingDynamic = threadedLogging - | otherwise = error $ "Cannot drop Dynamic from way " ++ tag way ++ "." + | otherwise = way -- Detect way from a given extension. Fail if the result is not unique. -- TODO: This may be slow -- optimise if overhead is significant. From git at git.haskell.org Thu Oct 26 23:06:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add toStandard. (fd28d9a) Message-ID: <20171026230609.DA81E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd28d9aa2dc7a212d20685e5541c1e059288c799/ghc >--------------------------------------------------------------- commit fd28d9aa2dc7a212d20685e5541c1e059288c799 Author: Andrey Mokhov Date: Tue Jan 13 13:02:06 2015 +0000 Add toStandard. >--------------------------------------------------------------- fd28d9aa2dc7a212d20685e5541c1e059288c799 src/Package/Compile.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index c42d592..56d168a 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -31,8 +31,8 @@ suffixArgs way = arg ["-hisuf", hisuf way] oRule :: Package -> TodoItem -> Rules () oRule (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" - pkgData = path dist "package-data.mk" + let buildDir = toStandard $ path dist "build" + pkgData = toStandard $ path dist "package-data.mk" depFile = buildDir name <.> "m" in (buildDir "*o") %> \out -> do @@ -59,7 +59,7 @@ oRule (Package name path _) (stage, dist, settings) = -- TODO: This rule looks hacky... combine it with the above? hiRule :: Package -> TodoItem -> Rules () hiRule (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" + let buildDir = toStandard $ path dist "build" in (buildDir "*hi") %> \out -> do let way = detectWay $ tail $ takeExtension out From git at git.haskell.org Thu Oct 26 23:06:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate targets from package list. (5c01b64) Message-ID: <20171026230613.45F333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5c01b64cff13863a0c3dc34a63352b7214245a72/ghc >--------------------------------------------------------------- commit 5c01b64cff13863a0c3dc34a63352b7214245a72 Author: Andrey Mokhov Date: Tue Jan 13 13:03:48 2015 +0000 Generate targets from package list. >--------------------------------------------------------------- 5c01b64cff13863a0c3dc34a63352b7214245a72 src/Package.hs | 30 ++++++++++++++++-------------- 1 file changed, 16 insertions(+), 14 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 899e48a..217c05a 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -25,18 +25,20 @@ buildPackage = buildPackageData packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments - want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" - , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" - , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" - , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.a" - , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.p_a" - , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" - , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.a" - , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.p_a" - , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" - , "libraries/binary/dist-install/build/HSbinar_8WpSY1EWq5j1AwY619xVVw.o" - , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.a" - , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.p_a" ] - forM_ packages $ \pkg -> do - forM_ (pkgTodo pkg) $ \todoItem -> do + forM_ packages $ \pkg @ (Package name path todo) -> do + forM_ todo $ \todoItem @ (stage, dist, settings) -> do + + -- Want top .o and .a files for the pkg/todo combo: + action $ do + let buildDir = path dist "build" + pkgData = path dist "package-data.mk" + [key] <- arg (PackageKey pkgData) + let oFile = buildDir "Hs" ++ key <.> "o" + ways' <- ways settings + aFiles <- forM ways' $ \way -> do + extension <- libsuf way + return $ buildDir "libHs" ++ key <.> extension + need $ [oFile] ++ aFiles + + -- Build rules for the package buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:06:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (7ad0b09) Message-ID: <20171026230616.A71963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ad0b09ddbfd98ec8e026ef146add00e12c35e2f/ghc >--------------------------------------------------------------- commit 7ad0b09ddbfd98ec8e026ef146add00e12c35e2f Author: Andrey Mokhov Date: Tue Jan 13 15:22:31 2015 +0000 Clean up. >--------------------------------------------------------------- 7ad0b09ddbfd98ec8e026ef146add00e12c35e2f src/Base.hs | 2 ++ src/Oracles/Builder.hs | 12 ++++++++---- src/Oracles/Option.hs | 4 ++++ src/Package.hs | 6 +++--- src/Package/Compile.hs | 7 ++++--- src/Package/Dependencies.hs | 2 +- src/Package/Library.hs | 3 ++- 7 files changed, 24 insertions(+), 12 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 169f556..e3f2256 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -27,6 +27,8 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) instance Show Stage where show = show . fromEnum +-- The returned list of strings is a list of arguments +-- to be passed to a Builder type Args = Action [String] type Condition = Action Bool diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 8a2c5b2..5c9d64b 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -11,6 +11,9 @@ import Oracles.Base import Oracles.Flag import Oracles.Option +-- A Builder is an external command invoked in separate process +-- by calling Shake.cmd +-- -- Ghc Stage0 is the bootstrapping compiler -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg @@ -96,7 +99,8 @@ run :: Builder -> Args -> Action () run builder args = do needBuilder builder [exe] <- showArgs builder - cmd [exe] =<< args + args' <- args + cmd [exe] args' -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. @@ -106,9 +110,9 @@ terseRun builder args = do needBuilder builder [exe] <- showArgs builder args' <- args - putNormal $ "--------\nRunning " ++ show builder ++ " with arguments:" - mapM_ (putNormal . (" " ++)) $ interestingInfo builder args' - putNormal "--------" + putNormal $ "|--------\n| Running " ++ show builder ++ " with arguments:" + mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args' + putNormal "|--------" quietly $ cmd [exe] args' interestingInfo :: Builder -> [String] -> [String] diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 89192a7..ee8fb66 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -8,6 +8,10 @@ import Base import Oracles.Flag import Oracles.Base +-- For each Option the files {default.config, user.config} contain +-- a line of the form 'target-os = mingw32'. +-- (showArgs TargetOS) is an action that consults the config files +-- and returns ["mingw32"]. -- TODO: separate single string options from multiple string ones. data Option = TargetOS | TargetArch diff --git a/src/Package.hs b/src/Package.hs index 217c05a..e815c4b 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -11,9 +11,9 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] packages = [libraryPackage "array" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings, libraryPackage "bin-package-db" Stage1 defaultSettings, - libraryPackage "binary" Stage1 defaultSettings] + libraryPackage "binary" Stage1 defaultSettings, + libraryPackage "deepseq" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -24,7 +24,7 @@ buildPackage = buildPackageData packageRules :: Rules () packageRules = do - -- TODO: control targets from commang line arguments + -- TODO: control targets from command line arguments forM_ packages $ \pkg @ (Package name path todo) -> do forM_ todo $ \todoItem @ (stage, dist, settings) -> do diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 56d168a..d701af6 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -32,7 +32,7 @@ suffixArgs way = arg ["-hisuf", hisuf way] oRule :: Package -> TodoItem -> Rules () oRule (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" - pkgData = toStandard $ path dist "package-data.mk" + pkgData = path dist "package-data.mk" depFile = buildDir name <.> "m" in (buildDir "*o") %> \out -> do @@ -49,6 +49,7 @@ oRule (Package name path _) (stage, dist, settings) = <> packageArgs stage pkgData <> includeArgs path dist <> concatArgs ["-optP"] (CppOpts pkgData) + -- TODO: use HC_OPTS from pkgData -- TODO: now we have both -O and -O2 <> arg ["-Wall", "-XHaskell2010", "-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir @@ -59,10 +60,10 @@ oRule (Package name path _) (stage, dist, settings) = -- TODO: This rule looks hacky... combine it with the above? hiRule :: Package -> TodoItem -> Rules () hiRule (Package name path _) (stage, dist, settings) = - let buildDir = toStandard $ path dist "build" + let buildDir = path dist "build" in (buildDir "*hi") %> \out -> do - let way = detectWay $ tail $ takeExtension out + let way = detectWay $ tail $ takeExtension out oFile = out -<.> osuf way need [oFile] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index fc9f4af..e428371 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -6,7 +6,7 @@ import Package.Base buildPackageDependencies :: Package -> TodoItem -> Rules () buildPackageDependencies (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" - pkgData = toStandard $ path dist "package-data.mk" + pkgData = path dist "package-data.mk" in (buildDir name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] diff --git a/src/Package/Library.hs b/src/Package/Library.hs index ec2b845..043977a 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -7,7 +7,6 @@ import Data.List.Split arRule :: Package -> TodoItem -> Rules () arRule (Package _ path _) (stage, dist, _) = let buildDir = path dist "build" - pkgData = path dist "package-data.mk" in (buildDir "*a") %> \out -> do let way = detectWay $ tail $ takeExtension out @@ -16,6 +15,8 @@ arRule (Package _ path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] + -- Splitting argument list into chunks as otherwise Ar chokes up + -- TODO: use simpler list notation for passing arguments forM_ (chunksOf 100 libObjs) $ \os -> do terseRun Ar $ "q" <+> toStandard out <+> os From git at git.haskell.org Thu Oct 26 23:06:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use multiple output rules for *.o and *.hi files. (6ce7cd3) Message-ID: <20171026230620.4C6BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6ce7cd3ac8b3ba4ef0228dec9c8d4741f746a873/ghc >--------------------------------------------------------------- commit 6ce7cd3ac8b3ba4ef0228dec9c8d4741f746a873 Author: Andrey Mokhov Date: Wed Jan 14 03:58:59 2015 +0000 Use multiple output rules for *.o and *.hi files. >--------------------------------------------------------------- 6ce7cd3ac8b3ba4ef0228dec9c8d4741f746a873 src/Package/Compile.hs | 24 ++++++------------------ 1 file changed, 6 insertions(+), 18 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index d701af6..cd91c8e 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -29,13 +29,13 @@ suffixArgs way = arg ["-hisuf", hisuf way] <> arg [ "-osuf", osuf way] <> arg ["-hcsuf", hcsuf way] -oRule :: Package -> TodoItem -> Rules () -oRule (Package name path _) (stage, dist, settings) = +buildPackageCompile :: Package -> TodoItem -> Rules () +buildPackageCompile (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" pkgData = path dist "package-data.mk" - depFile = buildDir name <.> "m" + depFile = buildDir takeBaseName name <.> "m" in - (buildDir "*o") %> \out -> do + [buildDir "*o", buildDir "*hi"] &%> \[out, _] -> do let way = detectWay $ tail $ takeExtension out need ["shake/src/Package/Compile.hs"] need [depFile] @@ -49,23 +49,11 @@ oRule (Package name path _) (stage, dist, settings) = <> packageArgs stage pkgData <> includeArgs path dist <> concatArgs ["-optP"] (CppOpts pkgData) - -- TODO: use HC_OPTS from pkgData + <> arg (HsOpts pkgData) -- TODO: now we have both -O and -O2 - <> arg ["-Wall", "-XHaskell2010", "-O2"] + -- <> arg ["-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) <> arg ["-o", toStandard out] --- TODO: This rule looks hacky... combine it with the above? -hiRule :: Package -> TodoItem -> Rules () -hiRule (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" - in - (buildDir "*hi") %> \out -> do - let way = detectWay $ tail $ takeExtension out - oFile = out -<.> osuf way - need [oFile] - -buildPackageCompile :: Package -> TodoItem -> Rules () -buildPackageCompile = oRule <> hiRule From git at git.haskell.org Thu Oct 26 23:06:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add package data key HsOpts. (1a3f43b) Message-ID: <20171026230623.BCD403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a3f43b55d543e784762cf8f0e9bf40e15820703/ghc >--------------------------------------------------------------- commit 1a3f43b55d543e784762cf8f0e9bf40e15820703 Author: Andrey Mokhov Date: Wed Jan 14 04:00:39 2015 +0000 Add package data key HsOpts. >--------------------------------------------------------------- 1a3f43b55d543e784762cf8f0e9bf40e15820703 src/Oracles/PackageData.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index bf94713..854fb8c 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -20,6 +20,7 @@ data PackageData = Modules FilePath | DepKeys FilePath | Synopsis FilePath | CppOpts FilePath + | HsOpts FilePath instance ShowArgs PackageData where showArgs packageData = do @@ -32,8 +33,10 @@ instance ShowArgs PackageData where DepKeys file -> ("DEP_KEYS" , file, "" ) Synopsis file -> ("SYNOPSIS" , file, "" ) CppOpts file -> ("CPP_OPTS" , file, "" ) + HsOpts file -> ("HC_OPTS" , file, "" ) fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key - res <- askOracle $ PackageDataKey (file, fullKey) + file' = toStandard $ normaliseEx file + res <- askOracle $ PackageDataKey (file', fullKey) return $ words $ case res of Nothing -> error $ "No key '" ++ key ++ "' in " ++ file ++ "." Just "" -> defaultValue From git at git.haskell.org Thu Oct 26 23:06:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Cabal/Cabal to list of packages. (8bdefdd) Message-ID: <20171026230627.366D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8bdefdd7cbb9cd1c558d7f01f05a79ec4ff25a6e/ghc >--------------------------------------------------------------- commit 8bdefdd7cbb9cd1c558d7f01f05a79ec4ff25a6e Author: Andrey Mokhov Date: Wed Jan 14 04:01:55 2015 +0000 Add Cabal/Cabal to list of packages. >--------------------------------------------------------------- 8bdefdd7cbb9cd1c558d7f01f05a79ec4ff25a6e src/Package.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index e815c4b..5d16d22 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -13,7 +13,8 @@ packages :: [Package] packages = [libraryPackage "array" Stage1 defaultSettings, libraryPackage "bin-package-db" Stage1 defaultSettings, libraryPackage "binary" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings] + libraryPackage "deepseq" Stage1 defaultSettings, + libraryPackage "Cabal/Cabal" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -28,7 +29,8 @@ packageRules = do forM_ packages $ \pkg @ (Package name path todo) -> do forM_ todo $ \todoItem @ (stage, dist, settings) -> do - -- Want top .o and .a files for the pkg/todo combo: + -- Want top .o and .a files for the pkg/todo combo + -- TODO: Check BUILD_GHCI_LIB flag to decide if .o is needed action $ do let buildDir = path dist "build" pkgData = path dist "package-data.mk" From git at git.haskell.org Thu Oct 26 23:06:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix file names for package names with slashes (e.g. Cabal/Cabal). (f124e23) Message-ID: <20171026230630.9BF363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f124e23635f6fa05edc945e4b0200acc0e57d8c2/ghc >--------------------------------------------------------------- commit f124e23635f6fa05edc945e4b0200acc0e57d8c2 Author: Andrey Mokhov Date: Wed Jan 14 04:02:44 2015 +0000 Fix file names for package names with slashes (e.g. Cabal/Cabal). >--------------------------------------------------------------- f124e23635f6fa05edc945e4b0200acc0e57d8c2 src/Package/Data.hs | 3 ++- src/Package/Dependencies.hs | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index d3b13a5..c5d3bd2 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -59,6 +59,7 @@ buildPackageData :: Package -> TodoItem -> Rules () buildPackageData (Package name path _) (stage, dist, settings) = let pathDist = path dist configure = path "configure" + cabal = path takeBaseName name <.> "cabal" cabalArgs = arg ["configure", path, dist] -- this is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument @@ -91,7 +92,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do need ["shake/src/Package/Data.hs"] - need [path name <.> "cabal"] + need [cabal] when (doesFileExist $ configure <.> "ac") $ need [configure] terseRun GhcCabal cabalArgs when (registerPackage settings) $ terseRun (GhcPkg stage) ghcPkgArgs diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index e428371..1d3a8d2 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -8,7 +8,7 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" pkgData = path dist "package-data.mk" in - (buildDir name <.> "m") %> \out -> do + (buildDir takeBaseName name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData From git at git.haskell.org Thu Oct 26 23:06:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (f80948c) Message-ID: <20171026230634.21E8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f80948c6655e0c6bf2ba6a10e09647b78e5ee1ab/ghc >--------------------------------------------------------------- commit f80948c6655e0c6bf2ba6a10e09647b78e5ee1ab Author: Andrey Mokhov Date: Wed Jan 14 04:02:49 2015 +0000 Clean up. >--------------------------------------------------------------- f80948c6655e0c6bf2ba6a10e09647b78e5ee1ab src/Oracles/Builder.hs | 8 +++----- src/Package/Base.hs | 11 +++++------ 2 files changed, 8 insertions(+), 11 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 5c9d64b..0fce046 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -107,13 +107,11 @@ run builder args = do -- Raises an error if the builder is not uniquely specified in config files terseRun :: Builder -> Args -> Action () terseRun builder args = do - needBuilder builder - [exe] <- showArgs builder args' <- args - putNormal $ "|--------\n| Running " ++ show builder ++ " with arguments:" + putNormal $ "/--------\n| Running " ++ show builder ++ " with arguments:" mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args' - putNormal "|--------" - quietly $ cmd [exe] args' + putNormal "\\--------" + quietly $ run builder args interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of diff --git a/src/Package/Base.hs b/src/Package/Base.hs index bac6801..9cf8fc8 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -65,13 +65,12 @@ commonLdArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? commonCppArgs :: Args commonCppArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? --- TODO: simplify commonCcWarninigArgs :: Args -commonCcWarninigArgs = when Validating $ - GccIsClang arg "-Wno-unknown-pragmas" - <> (not GccIsClang && not GccLt46) arg "-Wno-error=inline" - <> (GccIsClang && not GccLt46 && windowsHost) - arg "-Werror=unused-but-set-variable" +commonCcWarninigArgs = when Validating $ arg + [ when GccIsClang $ arg "-Wno-unknown-pragmas" + , when (not GccIsClang && not GccLt46) $ arg "-Wno-error=inline" + , when (GccIsClang && not GccLt46 && windowsHost) $ + arg "-Werror=unused-but-set-variable" ] bootPkgConstraints :: Args bootPkgConstraints = mempty From git at git.haskell.org Thu Oct 26 23:06:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add chunksOfSize helper function. (797df55) Message-ID: <20171026230637.872053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/797df55a99ffbe2fe94bae5dc202444b294ae2d0/ghc >--------------------------------------------------------------- commit 797df55a99ffbe2fe94bae5dc202444b294ae2d0 Author: Andrey Mokhov Date: Thu Jan 15 02:02:28 2015 +0000 Add chunksOfSize helper function. >--------------------------------------------------------------- 797df55a99ffbe2fe94bae5dc202444b294ae2d0 src/Util.hs | 17 ++++++++++++++++- 1 file changed, 16 insertions(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index f91ff79..b1ff9e5 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,7 @@ module Util ( module Data.Char, - replaceIf, replaceEq, replaceSeparators + replaceIf, replaceEq, replaceSeparators, + chunksOfSize ) where import Base @@ -15,3 +16,17 @@ replaceEq from = replaceIf (== from) replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator +-- (chunksOfSize size ss) splits a list of strings 'ss' into chunks not +-- exceeding the given 'size'. +chunksOfSize :: Int -> [String] -> [[String]] +chunksOfSize _ [] = [] +chunksOfSize size ss = reverse chunk : chunksOfSize size rest + where + (chunk, rest) = go [] 0 ss + go chunk _ [] = (chunk, []) + go chunk chunkSize (s:ss) = let newSize = chunkSize + length s + (newChunk, rest) = go (s:chunk) newSize ss + in + if newSize > size + then (chunk , s:ss) + else (newChunk, rest) From git at git.haskell.org Thu Oct 26 23:06:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add packages: containers, filepath, hoopl, hpc, parallel, pretty, stm, template-haskell, transformers. (d52b4c9) Message-ID: <20171026230640.F37D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d52b4c94f317bfe4e631432b97a6f23d30dbf14a/ghc >--------------------------------------------------------------- commit d52b4c94f317bfe4e631432b97a6f23d30dbf14a Author: Andrey Mokhov Date: Thu Jan 15 02:03:22 2015 +0000 Add packages: containers, filepath, hoopl, hpc, parallel, pretty, stm, template-haskell, transformers. >--------------------------------------------------------------- d52b4c94f317bfe4e631432b97a6f23d30dbf14a src/Package.hs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 5d16d22..b8de413 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -10,11 +10,20 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] -packages = [libraryPackage "array" Stage1 defaultSettings, - libraryPackage "bin-package-db" Stage1 defaultSettings, - libraryPackage "binary" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings, - libraryPackage "Cabal/Cabal" Stage1 defaultSettings] +packages = [ libraryPackage "array" Stage1 defaultSettings + , libraryPackage "bin-package-db" Stage1 defaultSettings + , libraryPackage "binary" Stage1 defaultSettings + , libraryPackage "deepseq" Stage1 defaultSettings + , libraryPackage "Cabal/Cabal" Stage1 defaultSettings + , libraryPackage "containers" Stage1 defaultSettings + , libraryPackage "filepath" Stage1 defaultSettings + , libraryPackage "hoopl" Stage1 defaultSettings + , libraryPackage "hpc" Stage1 defaultSettings + , libraryPackage "parallel" Stage1 defaultSettings + , libraryPackage "pretty" Stage1 defaultSettings + , libraryPackage "stm" Stage1 defaultSettings + , libraryPackage "template-haskell" Stage1 defaultSettings + , libraryPackage "transformers" Stage1 defaultSettings ] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () From git at git.haskell.org Thu Oct 26 23:06:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add argSizeLimit function (mainly for Ar builder). (cff887e) Message-ID: <20171026230644.7D4653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cff887e3d3e30b187542580e8f5c4671bbe126b9/ghc >--------------------------------------------------------------- commit cff887e3d3e30b187542580e8f5c4671bbe126b9 Author: Andrey Mokhov Date: Thu Jan 15 02:05:05 2015 +0000 Add argSizeLimit function (mainly for Ar builder). >--------------------------------------------------------------- cff887e3d3e30b187542580e8f5c4671bbe126b9 src/Package/Base.hs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 9cf8fc8..a1eab2c 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -9,7 +9,8 @@ module Package.Base ( commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, bootPkgConstraints, pathArgs, packageArgs, includeArgs, pkgHsSources, - pkgDepObjects, pkgLibObjects + pkgDepObjects, pkgLibObjects, + argSizeLimit ) where import Base @@ -147,3 +148,14 @@ findModuleFiles pkgData directories suffixes = do suffix <- suffixes return $ dir modPath ++ suffix return $ map (toStandard . normaliseEx) files + +-- The argument list has a limited size on Windows. Since Windows 7 the limit +-- is 32768 (theoretically). In practice we use 31000 to leave some breathing +-- space for the builder's path & name, auxiliary flags, and other overheads. +-- Use this function to set limits for other operating systems if necessary. +argSizeLimit :: Action Int +argSizeLimit = do + windows <- windowsHost + return $ if windows + then 31000 + else 1048576 -- surely, 1MB should be enough? From git at git.haskell.org Thu Oct 26 23:06:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generalise run and terseRun. (5596b04) Message-ID: <20171026230647.E7BBD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5596b04183c7c55c88c4173d5143803cd93691a4/ghc >--------------------------------------------------------------- commit 5596b04183c7c55c88c4173d5143803cd93691a4 Author: Andrey Mokhov Date: Thu Jan 15 02:05:49 2015 +0000 Generalise run and terseRun. >--------------------------------------------------------------- 5596b04183c7c55c88c4173d5143803cd93691a4 src/Oracles/Builder.hs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 0fce046..b1aca5d 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -95,27 +95,27 @@ with builder = do -- Run the builder with a given collection of arguments -- Raises an error if the builder is not uniquely specified in config files -run :: Builder -> Args -> Action () -run builder args = do +run :: ShowArgs a => Builder -> a -> Action () +run builder as = do needBuilder builder [exe] <- showArgs builder - args' <- args - cmd [exe] args' + args <- showArgs as + cmd [exe] args -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. -- Raises an error if the builder is not uniquely specified in config files -terseRun :: Builder -> Args -> Action () -terseRun builder args = do - args' <- args +terseRun :: ShowArgs a => Builder -> a -> Action () +terseRun builder as = do + args <- showArgs as putNormal $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args' + mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args putNormal "\\--------" - quietly $ run builder args + quietly $ run builder as interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of - Ar -> prefixAndSuffix 3 1 ss + Ar -> prefixAndSuffix 2 1 ss Ld -> prefixAndSuffix 4 0 ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss From git at git.haskell.org Thu Oct 26 23:06:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass HsOpts to ghc -M. (b75a548) Message-ID: <20171026230651.BEBB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b75a548ad3e0c117a11db7cfc3d0ed0e00960612/ghc >--------------------------------------------------------------- commit b75a548ad3e0c117a11db7cfc3d0ed0e00960612 Author: Andrey Mokhov Date: Thu Jan 15 02:06:25 2015 +0000 Pass HsOpts to ghc -M. >--------------------------------------------------------------- b75a548ad3e0c117a11db7cfc3d0ed0e00960612 src/Package/Dependencies.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 1d3a8d2..f296419 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -17,11 +17,8 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = <> productArgs ["-odir", "-stubdir", "-hidir"] buildDir <> arg ["-dep-makefile", toStandard $ out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) + <> arg (HsOpts pkgData) <> arg (pkgHsSources path dist) - -- TODO: Check that skipping all _HC_OPTS is safe. - -- <> arg SrcHcOpts - -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - -- <> wayHcOpts vanilla -- Avoid rebuilding dependecies of out if it hasn't changed: -- Note: cannot use copyFileChanged as it depends on the source file deps <- liftIO $ readFile $ out <.> "new" From git at git.haskell.org Thu Oct 26 23:06:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass arguments as simple lists. (6269a42) Message-ID: <20171026230655.3BF0B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6269a42dc3c1f166f8ab913d5cca4a0ed7000f88/ghc >--------------------------------------------------------------- commit 6269a42dc3c1f166f8ab913d5cca4a0ed7000f88 Author: Andrey Mokhov Date: Thu Jan 15 02:07:53 2015 +0000 Pass arguments as simple lists. >--------------------------------------------------------------- 6269a42dc3c1f166f8ab913d5cca4a0ed7000f88 src/Package/Library.hs | 21 ++++++++++++--------- 1 file changed, 12 insertions(+), 9 deletions(-) diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 043977a..22c9869 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -2,7 +2,6 @@ module Package.Library (buildPackageLibrary) where import Package.Base -import Data.List.Split arRule :: Package -> TodoItem -> Rules () arRule (Package _ path _) (stage, dist, _) = @@ -16,9 +15,11 @@ arRule (Package _ path _) (stage, dist, _) = libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] -- Splitting argument list into chunks as otherwise Ar chokes up - -- TODO: use simpler list notation for passing arguments - forM_ (chunksOf 100 libObjs) $ \os -> do - terseRun Ar $ "q" <+> toStandard out <+> os + maxChunk <- argSizeLimit + forM_ (chunksOfSize maxChunk libObjs) $ \os -> do + terseRun Ar [ arg "q" + , arg $ toStandard out + , arg os ] ldRule :: Package -> TodoItem -> Rules () ldRule (Package name path _) (stage, dist, _) = @@ -29,12 +30,14 @@ ldRule (Package name path _) (stage, dist, _) = need ["shake/src/Package/Library.hs"] depObjs <- pkgDepObjects path dist vanilla need depObjs - terseRun Ld $ arg (ConfLdLinkerArgs stage) - <> arg ["-r", "-o", toStandard out] - <> arg depObjs + terseRun Ld [ arg (ConfLdLinkerArgs stage) + , arg "-r" + , arg "-o" + , arg $ toStandard out + , arg depObjs ] synopsis <- unwords <$> arg (Synopsis pkgData) - putNormal $ "Successfully built package " ++ name ++ "." - putNormal $ "Package synopsis: " ++ synopsis ++ "." + putNormal $ "/--------\nSuccessfully built package " ++ name ++ "." + putNormal $ "Package synopsis: " ++ synopsis ++ ".\n\\--------" buildPackageLibrary :: Package -> TodoItem -> Rules () buildPackageLibrary = arRule <> ldRule From git at git.haskell.org Thu Oct 26 23:06:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:06:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add bin-package-db (stage 0) to packages. (ad6da32) Message-ID: <20171026230658.AC1943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ad6da32754b4c9eea30f344beb36728302e03b8f/ghc >--------------------------------------------------------------- commit ad6da32754b4c9eea30f344beb36728302e03b8f Author: Andrey Mokhov Date: Thu Jan 15 11:46:20 2015 +0000 Add bin-package-db (stage 0) to packages. >--------------------------------------------------------------- ad6da32754b4c9eea30f344beb36728302e03b8f src/Package.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Package.hs b/src/Package.hs index b8de413..881fd21 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -11,6 +11,7 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] packages = [ libraryPackage "array" Stage1 defaultSettings + , libraryPackage "bin-package-db" Stage0 defaultSettings , libraryPackage "bin-package-db" Stage1 defaultSettings , libraryPackage "binary" Stage1 defaultSettings , libraryPackage "deepseq" Stage1 defaultSettings From git at git.haskell.org Thu Oct 26 23:07:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add arg folder. (e86a741) Message-ID: <20171026230702.2EAA93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e86a74150fe51816c2f72094e9c0319638e914e1/ghc >--------------------------------------------------------------- commit e86a74150fe51816c2f72094e9c0319638e914e1 Author: Andrey Mokhov Date: Thu Jan 15 11:47:22 2015 +0000 Add arg folder. >--------------------------------------------------------------- e86a74150fe51816c2f72094e9c0319638e914e1 arg/README.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/arg/README.md b/arg/README.md new file mode 100644 index 0000000..0af8834 --- /dev/null +++ b/arg/README.md @@ -0,0 +1,5 @@ +This folder serves two purposes: + +* Tracking argument lists produced by rules + +* Documentation From git at git.haskell.org Thu Oct 26 23:07:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generated arg/*.txt files to .gitignore. (440aeff) Message-ID: <20171026230705.9F0683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/440aeff3e952f2721e4d82b1609f72b90c332901/ghc >--------------------------------------------------------------- commit 440aeff3e952f2721e4d82b1609f72b90c332901 Author: Andrey Mokhov Date: Thu Jan 15 18:40:14 2015 +0000 Add generated arg/*.txt files to .gitignore. >--------------------------------------------------------------- 440aeff3e952f2721e4d82b1609f72b90c332901 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 375b257..82a6588 100644 --- a/.gitignore +++ b/.gitignore @@ -3,3 +3,4 @@ _shake/ _build/ cfg/default.config +arg/*.txt From git at git.haskell.org Thu Oct 26 23:07:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generated arg/*/*.txt files to .gitignore. (11ad707) Message-ID: <20171026230709.0827E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/11ad7076f72a8c879bed4637318aedb5f6df7b63/ghc >--------------------------------------------------------------- commit 11ad7076f72a8c879bed4637318aedb5f6df7b63 Author: Andrey Mokhov Date: Thu Jan 15 18:41:45 2015 +0000 Add generated arg/*/*.txt files to .gitignore. >--------------------------------------------------------------- 11ad7076f72a8c879bed4637318aedb5f6df7b63 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 82a6588..dad3a3c 100644 --- a/.gitignore +++ b/.gitignore @@ -3,4 +3,4 @@ _shake/ _build/ cfg/default.config -arg/*.txt +arg/*/*.txt From git at git.haskell.org Thu Oct 26 23:07:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix splitObjects function. (1b0bfa6) Message-ID: <20171026230715.F1F303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b0bfa663029117b64bfc84687718dc3579119e8/ghc >--------------------------------------------------------------- commit 1b0bfa663029117b64bfc84687718dc3579119e8 Author: Andrey Mokhov Date: Thu Jan 15 18:43:25 2015 +0000 Fix splitObjects function. >--------------------------------------------------------------- 1b0bfa663029117b64bfc84687718dc3579119e8 src/Oracles/Option.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index ee8fb66..57137ba 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -81,6 +81,7 @@ splitObjects stage = do splitObjectsBroken <- test SplitObjectsBroken ghcUnregisterised <- test GhcUnregisterised return $ not splitObjectsBroken && not ghcUnregisterised + && stage == Stage1 && arch `elem` ["i386", "x86_64", "powerpc", "sparc"] && os `elem` ["mingw32", "cygwin32", "linux", "darwin", "solaris2", "freebsd", "dragonfly", "netbsd", From git at git.haskell.org Thu Oct 26 23:07:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add putColoured. (63d4481) Message-ID: <20171026230712.74D153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/63d4481898a503c5532e39f3b18a60c3518cad57/ghc >--------------------------------------------------------------- commit 63d4481898a503c5532e39f3b18a60c3518cad57 Author: Andrey Mokhov Date: Thu Jan 15 18:42:54 2015 +0000 Add putColoured. >--------------------------------------------------------------- 63d4481898a503c5532e39f3b18a60c3518cad57 src/Oracles/Builder.hs | 9 ++++++--- src/Util.hs | 13 ++++++++++++- 2 files changed, 18 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index b1aca5d..88f9649 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -7,6 +7,7 @@ module Oracles.Builder ( import Data.Char import Base +import Util import Oracles.Base import Oracles.Flag import Oracles.Option @@ -108,9 +109,11 @@ run builder as = do terseRun :: ShowArgs a => Builder -> a -> Action () terseRun builder as = do args <- showArgs as - putNormal $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args - putNormal "\\--------" + putColoured Vivid White $ "/--------\n" ++ + "| Running " ++ show builder ++ " with arguments:" + mapM_ (putColoured Vivid White . ("| " ++)) $ + interestingInfo builder args + putColoured Vivid White $ "\\--------" quietly $ run builder as interestingInfo :: Builder -> [String] -> [String] diff --git a/src/Util.hs b/src/Util.hs index b1ff9e5..e0524df 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,11 +1,15 @@ module Util ( module Data.Char, + module System.Console.ANSI, replaceIf, replaceEq, replaceSeparators, - chunksOfSize + chunksOfSize, + putColoured ) where import Base import Data.Char +import System.Console.ANSI +import System.IO replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -30,3 +34,10 @@ chunksOfSize size ss = reverse chunk : chunksOfSize size rest if newSize > size then (chunk , s:ss) else (newChunk, rest) + +putColoured :: ColorIntensity -> Color -> String -> Action () +putColoured intensity colour msg = do + liftIO $ setSGR [SetColor Foreground intensity colour] + putNormal msg + liftIO $ setSGR [] + liftIO $ hFlush stdout From git at git.haskell.org Thu Oct 26 23:07:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add dependencies on argument lists. (50b8c2f) Message-ID: <20171026230719.736DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b/ghc >--------------------------------------------------------------- commit 50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b Author: Andrey Mokhov Date: Thu Jan 15 18:43:51 2015 +0000 Add dependencies on argument lists. >--------------------------------------------------------------- 50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b src/Package.hs | 29 +++++++++--------- src/Package/Base.hs | 59 +++++++++++++++++++++++++++--------- src/Package/Compile.hs | 72 +++++++++++++++++++++---------------------- src/Package/Data.hs | 74 ++++++++++++++++++++++++++++----------------- src/Package/Dependencies.hs | 43 ++++++++++++++++++-------- src/Package/Library.hs | 62 ++++++++++++++++++++++++++----------- 6 files changed, 217 insertions(+), 122 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b From git at git.haskell.org Thu Oct 26 23:07:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ShowArg for single string options, clean up code. (7412fe3) Message-ID: <20171026230726.654033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7412fe395e6bf6708c7c58667b3f91852ff5bffa/ghc >--------------------------------------------------------------- commit 7412fe395e6bf6708c7c58667b3f91852ff5bffa Author: Andrey Mokhov Date: Fri Jan 16 03:16:59 2015 +0000 Add ShowArg for single string options, clean up code. >--------------------------------------------------------------- 7412fe395e6bf6708c7c58667b3f91852ff5bffa src/Base.hs | 5 ++- src/Config.hs | 5 +++ src/Oracles.hs | 11 +++++-- src/Oracles/Builder.hs | 31 +++++++----------- src/Oracles/Flag.hs | 11 +++---- src/Oracles/Option.hs | 85 +++++++++++++++++++++++++++----------------------- src/Util.hs | 1 + src/Ways.hs | 27 ++++++++-------- 8 files changed, 95 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 7412fe395e6bf6708c7c58667b3f91852ff5bffa From git at git.haskell.org Thu Oct 26 23:07:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename opts to args. (3cbaccc) Message-ID: <20171026230722.EE09E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3cbacccf34dc3da2811e5a2f3e608bdd2a3cac1a/ghc >--------------------------------------------------------------- commit 3cbacccf34dc3da2811e5a2f3e608bdd2a3cac1a Author: Andrey Mokhov Date: Fri Jan 16 03:11:21 2015 +0000 Rename opts to args. >--------------------------------------------------------------- 3cbacccf34dc3da2811e5a2f3e608bdd2a3cac1a cfg/default.config.in | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index ac42e24..10ee7ee 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -34,6 +34,7 @@ supports-package-key = @SUPPORTS_PACKAGE_KEY@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ +validating = NO # Information about host and target systems: #=========================================== @@ -69,7 +70,7 @@ conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ -src-hc-opts = -H32m -O +src-hc-args = -H32m -O # Include and library directories: #================================= From git at git.haskell.org Thu Oct 26 23:07:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Version and DepNames keys to PackageData. (229d5cb) Message-ID: <20171026230730.1F05C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/229d5cbd080a7b581fce325d9cc06a553db93bc9/ghc >--------------------------------------------------------------- commit 229d5cbd080a7b581fce325d9cc06a553db93bc9 Author: Andrey Mokhov Date: Fri Jan 16 03:18:04 2015 +0000 Add Version and DepNames keys to PackageData. >--------------------------------------------------------------- 229d5cbd080a7b581fce325d9cc06a553db93bc9 src/Oracles/PackageData.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 854fb8c..e141120 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -12,12 +12,14 @@ import Util newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -data PackageData = Modules FilePath +data PackageData = Version FilePath + | Modules FilePath | SrcDirs FilePath | PackageKey FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath + | DepNames FilePath | Synopsis FilePath | CppOpts FilePath | HsOpts FilePath @@ -25,12 +27,14 @@ data PackageData = Modules FilePath instance ShowArgs PackageData where showArgs packageData = do let (key, file, defaultValue) = case packageData of + Version file -> ("VERSION" , file, "" ) Modules file -> ("MODULES" , file, "" ) SrcDirs file -> ("HS_SRC_DIRS" , file, ".") PackageKey file -> ("PACKAGE_KEY" , file, "" ) IncludeDirs file -> ("INCLUDE_DIRS", file, ".") Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) + DepNames file -> ("DEP_NAMES" , file, "" ) Synopsis file -> ("SYNOPSIS" , file, "" ) CppOpts file -> ("CPP_OPTS" , file, "" ) HsOpts file -> ("HC_OPTS" , file, "" ) From git at git.haskell.org Thu Oct 26 23:07:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Targets.hs for specifying targets, clean up code. (7ffb294) Message-ID: <20171026230733.8B7B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ffb2940272c99938582846879e2f297215c3211/ghc >--------------------------------------------------------------- commit 7ffb2940272c99938582846879e2f297215c3211 Author: Andrey Mokhov Date: Fri Jan 16 04:02:01 2015 +0000 Add Targets.hs for specifying targets, clean up code. >--------------------------------------------------------------- 7ffb2940272c99938582846879e2f297215c3211 src/Package.hs | 29 +++++----- src/Package/Base.hs | 67 +++++++++++------------ src/Package/Compile.hs | 36 ++++++------- src/Package/Data.hs | 127 +++++++++++++++++++++++++------------------- src/Package/Dependencies.hs | 20 +++---- src/Package/Library.hs | 24 +++++---- src/Targets.hs | 25 +++++++++ 7 files changed, 183 insertions(+), 145 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 7ffb2940272c99938582846879e2f297215c3211 From git at git.haskell.org Thu Oct 26 23:07:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor package-data oracles. (5a9b0a7) Message-ID: <20171026230737.155223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a9b0a741769feacc65bf976ca31d05ac3a58647/ghc >--------------------------------------------------------------- commit 5a9b0a741769feacc65bf976ca31d05ac3a58647 Author: Andrey Mokhov Date: Fri Jan 16 13:59:39 2015 +0000 Refactor package-data oracles. >--------------------------------------------------------------- 5a9b0a741769feacc65bf976ca31d05ac3a58647 src/Oracles/PackageData.hs | 9 +++++---- src/Package.hs | 11 +++-------- src/Package/Base.hs | 42 +++++++++++++++++++++--------------------- src/Package/Compile.hs | 10 +++++----- src/Package/Data.hs | 16 +++++++--------- src/Package/Dependencies.hs | 10 +++++----- src/Package/Library.hs | 6 +++--- 7 files changed, 49 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 5a9b0a741769feacc65bf976ca31d05ac3a58647 From git at git.haskell.org Thu Oct 26 23:07:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make single and multiple string options type safe. (5c1a7e4) Message-ID: <20171026230740.97B363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5c1a7e4ec089b8ce044ca45d03d2305915974ada/ghc >--------------------------------------------------------------- commit 5c1a7e4ec089b8ce044ca45d03d2305915974ada Author: Andrey Mokhov Date: Fri Jan 16 17:05:33 2015 +0000 Make single and multiple string options type safe. >--------------------------------------------------------------- 5c1a7e4ec089b8ce044ca45d03d2305915974ada src/Base.hs | 22 ++++++++++--- src/Oracles/Option.hs | 2 +- src/Oracles/PackageData.hs | 75 +++++++++++++++++++++++++++++---------------- src/Package.hs | 4 +-- src/Package/Base.hs | 59 ++++++++++++++++++----------------- src/Package/Compile.hs | 26 ++++++++-------- src/Package/Data.hs | 65 ++++++++++++++++++++------------------- src/Package/Dependencies.hs | 18 +++++------ src/Package/Library.hs | 16 +++++----- src/Targets.hs | 31 ++++++++++--------- src/Util.hs | 8 ++++- src/Ways.hs | 6 ++-- 12 files changed, 187 insertions(+), 145 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 5c1a7e4ec089b8ce044ca45d03d2305915974ada From git at git.haskell.org Thu Oct 26 23:07:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcSourcePath option. (eac54ff) Message-ID: <20171026230744.33E333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eac54ff6799eeb7824c7a8d1e5bb2bfa662d3189/ghc >--------------------------------------------------------------- commit eac54ff6799eeb7824c7a8d1e5bb2bfa662d3189 Author: Andrey Mokhov Date: Fri Jan 16 18:18:00 2015 +0000 Add GhcSourcePath option. >--------------------------------------------------------------- eac54ff6799eeb7824c7a8d1e5bb2bfa662d3189 cfg/default.config.in | 4 ++++ src/Oracles/Option.hs | 2 ++ 2 files changed, 6 insertions(+) diff --git a/cfg/default.config.in b/cfg/default.config.in index 10ee7ee..7402bd5 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -1,3 +1,6 @@ +# Edit 'user.config' to override these settings. +#=============================================== + # Paths to builders: #=================== @@ -35,6 +38,7 @@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ validating = NO +ghc-source-path = @hardtop@ # Information about host and target systems: #=========================================== diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 667e50e..7dcb9a8 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -22,6 +22,7 @@ data Option = TargetOs | HostOsCpp | DynamicExtension | ProjectVersion + | GhcSourcePath data MultiOption = SrcHcArgs | ConfCcArgs Stage @@ -41,6 +42,7 @@ instance ShowArg Option where HostOsCpp -> "host-os-cpp" DynamicExtension -> "dynamic-extension" ProjectVersion -> "project-version" + GhcSourcePath -> "ghc-source-path" instance ShowArgs MultiOption where showArgs opt = showArgs $ fmap words $ askConfig $ case opt of From git at git.haskell.org Thu Oct 26 23:07:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add bootPackageDb function. (2990db6) Message-ID: <20171026230748.697593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2990db6fa1688f58c252787320a14e800658e6f8/ghc >--------------------------------------------------------------- commit 2990db6fa1688f58c252787320a14e800658e6f8 Author: Andrey Mokhov Date: Fri Jan 16 18:19:12 2015 +0000 Add bootPackageDb function. >--------------------------------------------------------------- 2990db6fa1688f58c252787320a14e800658e6f8 src/Base.hs | 1 + src/Package/Data.hs | 18 ++++++++++++------ src/Targets.hs | 22 ++++++++++++---------- 3 files changed, 25 insertions(+), 16 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index f4edb45..232bca2 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -65,6 +65,7 @@ instance ShowArgs a => ShowArgs [a] where instance ShowArgs a => ShowArgs (Action a) where showArgs = (showArgs =<<) +-- TODO: improve args type safety args :: ShowArgs a => a -> Args args = showArgs diff --git a/src/Package/Data.hs b/src/Package/Data.hs index cfc8b53..b6c28c6 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -73,6 +73,12 @@ bootPkgConstraints = args $ do _ -> redError $ "Cannot determine package version in '" ++ toStandard cabal ++ "'." +bootPackageDb :: Args +bootPackageDb = do + top <- showArg GhcSourcePath + arg $ toStandard + $ "--package-db=" ++ top "libraries/bootstrapping.conf" + cabalArgs :: Package -> TodoItem -> Args cabalArgs pkg @ (Package _ path _) todo @ (stage, dist, settings) = args [ args ["configure", path, dist] @@ -83,6 +89,7 @@ cabalArgs pkg @ (Package _ path _) todo @ (stage, dist, settings) = args , with (Ghc stage) -- TODO: used limited to max stage1 GHC , with (GhcPkg stage) , customConfArgs settings + , when (stage == Stage0) bootPackageDb , libraryArgs =<< ways settings , when (specified HsColour) $ with HsColour , configureArgs stage settings @@ -94,12 +101,11 @@ cabalArgs pkg @ (Package _ path _) todo @ (stage, dist, settings) = args , with Happy ] -- TODO: reorder with's ghcPkgArgs :: Package -> TodoItem -> Args -ghcPkgArgs (Package _ path _) (stage, dist, _) = return $ - [ "update" - , "--force" - , toStandard $ path dist "inplace-pkg-config" ] - ++ - [ "--package-db=libraries/bootstrapping.conf" | stage == Stage0 ] +ghcPkgArgs (Package _ path _) (stage, dist, _) = args $ + [ arg "update" + , arg "--force" + , arg $ toStandard $ path dist "inplace-pkg-config" + , when (stage == Stage0) bootPackageDb ] buildRule :: Package -> TodoItem -> Rules () buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = diff --git a/src/Targets.hs b/src/Targets.hs index 59fdbf1..3895bae 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -12,16 +12,18 @@ libraryPackagesInStage Stage0 = , "hoopl" , "hpc" , "transformers" ] -libraryPackagesInStage Stage1 = [] - --[ "array" - --, "deepseq" - --, "Cabal/Cabal" - --, "containers" - --, "filepath" - --, "parallel" - --, "pretty" - --, "stm" - --, "template-haskell" ] +libraryPackagesInStage Stage1 = + libraryPackagesInStage Stage0 ++ + [ "array" + , "deepseq" + , "Cabal/Cabal" + , "containers" + , "filepath" + , "parallel" + , "pretty" + , "stm" + , "template-haskell" ] + libraryPackagesInStage _ = [] libraryPackages :: [String] From git at git.haskell.org Thu Oct 26 23:07:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up colourisation code. (a5a2fed) Message-ID: <20171026230752.2AD4E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a2fed84493a7afa0942ba28a33b1ae9bc2a804/ghc >--------------------------------------------------------------- commit a5a2fed84493a7afa0942ba28a33b1ae9bc2a804 Author: Andrey Mokhov Date: Sat Jan 17 23:12:02 2015 +0000 Clean up colourisation code. >--------------------------------------------------------------- a5a2fed84493a7afa0942ba28a33b1ae9bc2a804 src/Config.hs | 6 ++---- src/Oracles/Builder.hs | 14 +++++++++----- src/Oracles/Flag.hs | 2 +- src/Util.hs | 16 ++++++++++------ 4 files changed, 22 insertions(+), 16 deletions(-) diff --git a/src/Config.hs b/src/Config.hs index dd5db2a..1a4ef9a 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -11,15 +11,13 @@ cfgPath = "shake" "cfg" autoconfRules :: Rules () autoconfRules = do "configure" %> \out -> do - need ["shake/src/Config.hs"] copyFile' (cfgPath "configure.ac") "configure.ac" - putColoured Vivid White $ "Running autoconf..." + putColoured White $ "Running autoconf..." cmd "bash autoconf" -- TODO: get rid of 'bash' configureRules :: Rules () configureRules = do cfgPath "default.config" %> \out -> do - need ["shake/src/Config.hs"] need [cfgPath "default.config.in", "configure"] - putColoured Vivid White "Running configure..." + putColoured White "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 3386b6f..13b8d7c 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -47,8 +47,8 @@ instance ShowArg Builder where GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" cfgPath <- askConfigWithDefault key $ - error $ "\nCannot find path to '" ++ key - ++ "' in configuration files." + redError $ "\nCannot find path to '" ++ key + ++ "' in configuration files." let cfgPathExe = if null cfgPath then "" else cfgPath -<.> exe windows <- windowsHost -- Note, below is different from FilePath.isAbsolute: @@ -104,20 +104,24 @@ run builder as = do -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. -- Raises an error if the builder is not uniquely specified in config files +-- TODO: make this a default 'run', rename current 'run' to verboseRun terseRun :: ShowArgs a => Builder -> a -> Action () terseRun builder as = do args <- showArgs as - putColoured Vivid White $ "/--------\n" ++ + putColoured White $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" - mapM_ (putColoured Vivid White . ("| " ++)) $ + mapM_ (putColoured White . ("| " ++)) $ interestingInfo builder args - putColoured Vivid White $ "\\--------" + putColoured White $ "\\--------" quietly $ run builder as interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of Ar -> prefixAndSuffix 2 1 ss Ld -> prefixAndSuffix 4 0 ss + Gcc -> if head ss == "-MM" + then prefixAndSuffix 1 1 ss + else ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss else prefixAndSuffix 0 4 ss diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 6339696..fa29415 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -41,7 +41,7 @@ test flag = do GhcUnregisterised -> ("ghc-unregisterised" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ -- TODO: warn just once - do putColoured Dull Red $ "\nFlag '" + do putColoured Red $ "\nFlag '" ++ key ++ "' not set in configuration files. " ++ "Proceeding with default value '" diff --git a/src/Util.hs b/src/Util.hs index 5bec54d..16728ce 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -3,13 +3,14 @@ module Util ( module System.Console.ANSI, replaceIf, replaceEq, replaceSeparators, chunksOfSize, - putColoured, redError + putColoured, redError, redError_ ) where import Base import Data.Char import System.Console.ANSI import System.IO +import Control.Monad replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -36,9 +37,9 @@ chunksOfSize size ss = reverse chunk : chunksOfSize size rest else (newChunk, rest) -- A more colourful version of Shake's putNormal -putColoured :: ColorIntensity -> Color -> String -> Action () -putColoured intensity colour msg = do - liftIO $ setSGR [SetColor Foreground intensity colour] +putColoured :: Color -> String -> Action () +putColoured colour msg = do + liftIO $ setSGR [SetColor Foreground Vivid colour] putNormal msg liftIO $ setSGR [] liftIO $ hFlush stdout @@ -46,5 +47,8 @@ putColoured intensity colour msg = do -- A more colourful version of error redError :: String -> Action a redError msg = do - putColoured Vivid Red msg - return $ error $ "GHC build system error: " ++ msg + putColoured Red msg + error $ "GHC build system error: " ++ msg + +redError_ :: String -> Action () +redError_ = void . redError From git at git.haskell.org Thu Oct 26 23:07:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add DependencyList oracle. (a644c32) Message-ID: <20171026230755.98D2B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a644c3216b42e6a371f61b2e142df74cf457f51c/ghc >--------------------------------------------------------------- commit a644c3216b42e6a371f61b2e142df74cf457f51c Author: Andrey Mokhov Date: Sat Jan 17 23:13:04 2015 +0000 Add DependencyList oracle. >--------------------------------------------------------------- a644c3216b42e6a371f61b2e142df74cf457f51c src/Oracles.hs | 47 +++++++++++++++++++++++++++++++------------ src/Oracles/DependencyList.hs | 20 ++++++++++++++++++ 2 files changed, 54 insertions(+), 13 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 9ac6191..4c6d9e9 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -4,11 +4,14 @@ module Oracles ( module Oracles.Option, module Oracles.Builder, module Oracles.PackageData, + module Oracles.DependencyList, oracleRules ) where import Development.Shake.Config +import Development.Shake.Util import qualified Data.HashMap.Strict as M +import Data.Bifunctor import Base import Util import Config @@ -17,49 +20,67 @@ import Oracles.Flag import Oracles.Option import Oracles.Builder import Oracles.PackageData +import Oracles.DependencyList defaultConfig, userConfig :: FilePath defaultConfig = cfgPath "default.config" userConfig = cfgPath "user.config" --- Oracle for configuration files. +-- Oracle for configuration files configOracle :: Rules () configOracle = do cfg <- newCache $ \() -> do - unless (doesFileExist $ defaultConfig <.> "in") $ do - error $ "\nDefault configuration file '" - ++ (defaultConfig <.> "in") - ++ "' is missing; unwilling to proceed." - return () + unless (doesFileExist $ defaultConfig <.> "in") $ + redError_ $ "\nDefault configuration file '" + ++ (defaultConfig <.> "in") + ++ "' is missing; unwilling to proceed." need [defaultConfig] - putNormal $ "Parsing " ++ toStandard defaultConfig ++ "..." + putOracle $ "Parsing " ++ toStandard defaultConfig ++ "..." cfgDefault <- liftIO $ readConfigFile defaultConfig existsUser <- doesFileExist userConfig cfgUser <- if existsUser then do - putNormal $ "Parsing " + putOracle $ "Parsing " ++ toStandard userConfig ++ "..." liftIO $ readConfigFile userConfig else do - putColoured Dull Red $ + putColoured Red $ "\nUser defined configuration file '" ++ userConfig ++ "' is missing; " ++ "proceeding with default configuration.\n" return M.empty - putColoured Vivid Green $ "Finished processing configuration files." + putColoured Green $ "Finished processing configuration files." return $ cfgUser `M.union` cfgDefault addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () return () --- Oracle for 'package-data.mk' files. +-- Oracle for 'package-data.mk' files packageDataOracle :: Rules () packageDataOracle = do pkgData <- newCache $ \file -> do need [file] - putNormal $ "Parsing " ++ toStandard file ++ "..." + putOracle $ "Parsing " ++ toStandard file ++ "..." liftIO $ readConfigFile file addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () +-- Oracle for 'path/dist/*.deps' files +dependencyOracle :: Rules () +dependencyOracle = do + deps <- newCache $ \depFile -> do + need [depFile] + putOracle $ "Parsing " ++ toStandard depFile ++ "..." + contents <- parseMakefile <$> (liftIO $ readFile depFile) + return $ M.fromList + $ map (bimap head concat . unzip) + $ groupBy ((==) `on` fst) + $ sortBy (compare `on` fst) contents + addOracle $ \(DependencyListKey (file, obj)) -> M.lookup obj <$> deps file + return () + oracleRules :: Rules () -oracleRules = configOracle <> packageDataOracle +oracleRules = configOracle <> packageDataOracle <> dependencyOracle + +-- Make oracle's output more distinguishable +putOracle :: String -> Action () +putOracle = putColoured Blue diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs new file mode 100644 index 0000000..8f4eda1 --- /dev/null +++ b/src/Oracles/DependencyList.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} + +module Oracles.DependencyList ( + DependencyList (..), + DependencyListKey (..) + ) where + +import Development.Shake.Classes +import Base +import Data.Maybe + +data DependencyList = DependencyList FilePath FilePath + +newtype DependencyListKey = DependencyListKey (FilePath, FilePath) + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +instance ShowArgs DependencyList where + showArgs (DependencyList file obj) = do + res <- askOracle $ DependencyListKey (file, obj) + return $ fromMaybe [] res From git at git.haskell.org Thu Oct 26 23:07:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:07:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CcArgs and CSrcs keys to PackageData. (316d98e) Message-ID: <20171026230759.0C11B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/316d98ef5bf6a5e43c649f5a7269661ff304be96/ghc >--------------------------------------------------------------- commit 316d98ef5bf6a5e43c649f5a7269661ff304be96 Author: Andrey Mokhov Date: Sat Jan 17 23:14:03 2015 +0000 Add CcArgs and CSrcs keys to PackageData. >--------------------------------------------------------------- 316d98ef5bf6a5e43c649f5a7269661ff304be96 src/Oracles/PackageData.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 192896c..0581e82 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -31,6 +31,8 @@ data MultiPackageData = Modules FilePath | DepNames FilePath | CppArgs FilePath | HsArgs FilePath + | CcArgs FilePath + | CSrcs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -59,6 +61,8 @@ instance ShowArgs MultiPackageData where DepNames path -> ("DEP_NAMES" , path, "" ) CppArgs path -> ("CPP_OPTS" , path, "" ) HsArgs path -> ("HC_OPTS" , path, "" ) + CcArgs path -> ("CC_OPTS" , path, "" ) + CSrcs path -> ("C_SRCS" , path, "" ) fullKey = replaceSeparators '_' $ path ++ "_" ++ key pkgData = path "package-data.mk" res <- askOracle $ PackageDataKey (pkgData, fullKey) From git at git.haskell.org Thu Oct 26 23:08:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for c source files. (debca7a) Message-ID: <20171026230802.8F82B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/debca7ade35a75b7d5947f0abeb3a9a190d2e0f7/ghc >--------------------------------------------------------------- commit debca7ade35a75b7d5947f0abeb3a9a190d2e0f7 Author: Andrey Mokhov Date: Sat Jan 17 23:14:40 2015 +0000 Add support for c source files. >--------------------------------------------------------------- debca7ade35a75b7d5947f0abeb3a9a190d2e0f7 src/Package/Base.hs | 32 +++++++++++++-------- src/Package/Compile.hs | 49 ++++++++++++++++++++++++------- src/Package/Dependencies.hs | 70 +++++++++++++++++++++++++++++++++++++++------ src/Package/Library.hs | 29 ++++++++++--------- src/Targets.hs | 36 +++++++++++------------ src/Ways.hs | 1 + 6 files changed, 154 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc debca7ade35a75b7d5947f0abeb3a9a190d2e0f7 From git at git.haskell.org Thu Oct 26 23:08:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename includeHcArgs to includeGhcArgs. (734994c) Message-ID: <20171026230806.0FE643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/734994cf18ee377472128ceab7ad6ef1f8773684/ghc >--------------------------------------------------------------- commit 734994cf18ee377472128ceab7ad6ef1f8773684 Author: Andrey Mokhov Date: Sat Jan 17 23:31:52 2015 +0000 Rename includeHcArgs to includeGhcArgs. >--------------------------------------------------------------- 734994cf18ee377472128ceab7ad6ef1f8773684 src/Package/Base.hs | 6 +++--- src/Package/Compile.hs | 2 +- src/Package/Dependencies.hs | 6 +----- 3 files changed, 5 insertions(+), 9 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 0b053e8..9d75e04 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -7,7 +7,7 @@ module Package.Base ( Package (..), Settings (..), TodoItem (..), defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - pathArgs, packageArgs, includeHcArgs, pkgHsSources, + pathArgs, packageArgs, includeGhcArgs, pkgHsSources, pkgDepHsObjects, pkgLibHsObjects, pkgCObjects, argSizeLimit, sourceDependecies, @@ -92,8 +92,8 @@ packageArgs stage pathDist = do else productArgs "-package-name" (arg $ PackageKey pathDist) <> productArgs "-package" (args $ Deps pathDist) ] -includeHcArgs :: FilePath -> FilePath -> Args -includeHcArgs path dist = +includeGhcArgs :: FilePath -> FilePath -> Args +includeGhcArgs path dist = let pathDist = path dist buildDir = toStandard $ pathDist "build" in args [ arg "-i" diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 0c25ae8..8052356 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -18,7 +18,7 @@ ghcArgs (Package _ path _) (stage, dist, _) way srcs result = , wayHcArgs way , args SrcHcArgs , packageArgs stage pathDist - , includeHcArgs path dist + , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist , args $ HsArgs pathDist -- TODO: now we have both -O and -O2 diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 7378f20..7301051 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -13,7 +13,7 @@ ghcArgs (Package name path _) (stage, dist, settings) = depFile = buildDir "haskell.deps" in args [ arg "-M" , packageArgs stage pathDist - , includeHcArgs path dist + , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist , productArgs ["-odir", "-stubdir", "-hidir"] buildDir , args ["-dep-makefile", depFile <.> "new"] @@ -21,10 +21,6 @@ ghcArgs (Package name path _) (stage, dist, settings) = , args $ HsArgs pathDist , args $ pkgHsSources path dist ] --- $(CPP) $($1_$2_MKDEPENDC_OPTS) --- $($1_$2_$(firstword $($1_$2_WAYS))_ALL_CC_OPTS) --- $($(basename $4)_CC_OPTS) -MM -x c $4 -MF $3.bit --- -- $1_$2_$3_ALL_CC_OPTS = \ -- $$(WAY_$3_CC_OPTS) \ -- $$($1_$2_DIST_GCC_CC_OPTS) \ From git at git.haskell.org Thu Oct 26 23:08:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add stage parameter to Gcc builder. Clean up. (d6744a7) Message-ID: <20171026230809.918743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6744a706e0ed263c6f67a3f2a668363ddaa36c5/ghc >--------------------------------------------------------------- commit d6744a706e0ed263c6f67a3f2a668363ddaa36c5 Author: Andrey Mokhov Date: Sun Jan 18 00:09:45 2015 +0000 Add stage parameter to Gcc builder. Clean up. >--------------------------------------------------------------- d6744a706e0ed263c6f67a3f2a668363ddaa36c5 cfg/default.config.in | 33 +++++++++++++++++---------------- src/Oracles/Base.hs | 3 ++- src/Oracles/Builder.hs | 9 +++++---- src/Oracles/Option.hs | 2 +- src/Package/Compile.hs | 10 ++++++++-- src/Package/Data.hs | 8 ++++---- src/Package/Dependencies.hs | 4 ++-- 7 files changed, 39 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 d6744a706e0ed263c6f67a3f2a668363ddaa36c5 From git at git.haskell.org Thu Oct 26 23:08:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up rules related to dependency lists. (7d42fda) Message-ID: <20171026230813.328D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d42fdac5a5574825124b250e3db0287cab8c417/ghc >--------------------------------------------------------------- commit 7d42fdac5a5574825124b250e3db0287cab8c417 Author: Andrey Mokhov Date: Sun Jan 18 12:45:23 2015 +0000 Clean up rules related to dependency lists. >--------------------------------------------------------------- 7d42fdac5a5574825124b250e3db0287cab8c417 src/Package/Compile.hs | 2 +- src/Package/Dependencies.hs | 14 ++++++-------- 2 files changed, 7 insertions(+), 9 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 0cdb62c..1155117 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -48,7 +48,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = let oPattern = "*." ++ osuf way let hiPattern = "*." ++ hisuf way [buildDir oPattern, buildDir hiPattern] |%> \out -> do - need [argListPath argListDir pkg stage, hDepFile, cDepFile] + need [argListPath argListDir pkg stage] let obj = toStandard $ out -<.> osuf way vanillaObj = toStandard $ out -<.> "o" -- TODO: keep only vanilla dependencies in hDepFile diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 08bb9e5..31c8d92 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -16,7 +16,7 @@ ghcArgs (Package name path _) (stage, dist, settings) = , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist , productArgs ["-odir", "-stubdir", "-hidir"] buildDir - , args ["-dep-makefile", depFile <.> "new"] + , args ["-dep-makefile", depFile ] , productArgs "-dep-suffix" $ map wayPrefix <$> ways settings , args $ HsArgs pathDist , args $ pkgHsSources path dist ] @@ -60,19 +60,17 @@ buildRule :: Package -> TodoItem -> Rules () buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do let pathDist = path dist buildDir = pathDist "build" - hDepFile = buildDir "haskell.deps" - cDepFile = buildDir "c.deps" - hDepFile %> \out -> do + (buildDir "haskell.deps") %> \out -> do need [argListPath argListDir pkg stage] terseRun (Ghc stage) $ ghcArgs pkg todo -- Avoid rebuilding dependecies of out if it hasn't changed: -- Note: cannot use copyFileChanged as it depends on the source file - deps <- liftIO $ readFile $ out <.> "new" - writeFileChanged out deps - liftIO $ removeFiles "." [out <.> "new"] + --deps <- liftIO $ readFile $ out <.> "new" + --writeFileChanged out deps + --liftIO $ removeFiles "." [out <.> "new"] - cDepFile %> \out -> do + (buildDir "c.deps") %> \out -> do need [argListPath argListDir pkg stage] srcs <- args $ CSrcs pathDist deps <- fmap concat $ forM srcs $ \src -> do From git at git.haskell.org Thu Oct 26 23:08:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename (run, terseRun) to (verboseRun, run). (9e247b0) Message-ID: <20171026230816.A501F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e247b0618357bdca4b0218de19e2eb7f9f23b63/ghc >--------------------------------------------------------------- commit 9e247b0618357bdca4b0218de19e2eb7f9f23b63 Author: Andrey Mokhov Date: Sun Jan 18 12:50:13 2015 +0000 Rename (run, terseRun) to (verboseRun, run). >--------------------------------------------------------------- 9e247b0618357bdca4b0218de19e2eb7f9f23b63 src/Oracles/Builder.hs | 15 ++++++--------- src/Package/Compile.hs | 4 ++-- src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 9 ++------- src/Package/Library.hs | 4 ++-- 5 files changed, 14 insertions(+), 22 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 1dcc797..e52cc58 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, terseRun, specified + with, run, verboseRun, specified ) where import Data.Char @@ -94,9 +94,8 @@ with builder = do return [key ++ exe] -- Run the builder with a given collection of arguments --- Raises an error if the builder is not uniquely specified in config files -run :: ShowArgs a => Builder -> a -> Action () -run builder as = do +verboseRun :: ShowArgs a => Builder -> a -> Action () +verboseRun builder as = do needBuilder builder exe <- showArg builder args <- showArgs as @@ -104,17 +103,15 @@ run builder as = do -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. --- Raises an error if the builder is not uniquely specified in config files --- TODO: make this a default 'run', rename current 'run' to verboseRun -terseRun :: ShowArgs a => Builder -> a -> Action () -terseRun builder as = do +run :: ShowArgs a => Builder -> a -> Action () +run builder as = do args <- showArgs as putColoured White $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" mapM_ (putColoured White . ("| " ++)) $ interestingInfo builder args putColoured White $ "\\--------" - quietly $ run builder as + quietly $ verboseRun builder as interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 1155117..e0080f9 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -66,9 +66,9 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = -- Build using appropriate compiler need $ hDeps ++ cDeps when (not $ null hSrcs) - $ terseRun (Ghc stage) $ ghcArgs pkg todo way hSrcs obj + $ run (Ghc stage) $ ghcArgs pkg todo way hSrcs obj when (not $ null cSrcs) - $ terseRun (Gcc stage) $ gccArgs pkg todo cSrcs obj + $ run (Gcc stage) $ gccArgs pkg todo cSrcs obj argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, settings) = diff --git a/src/Package/Data.hs b/src/Package/Data.hs index a3f0936..91f0b2d 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -124,9 +124,9 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = ] &%> \_ -> do need [argListPath argListDir pkg stage, cabal] when (doesFileExist $ configure <.> "ac") $ need [configure] - terseRun GhcCabal $ cabalArgs pkg todo + run GhcCabal $ cabalArgs pkg todo when (registerPackage settings) $ - terseRun (GhcPkg stage) $ ghcPkgArgs pkg todo + run (GhcPkg stage) $ ghcPkgArgs pkg todo postProcessPackageData $ pathDist "package-data.mk" argListRule :: Package -> TodoItem -> Rules () diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 31c8d92..d1a8a14 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -63,12 +63,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do (buildDir "haskell.deps") %> \out -> do need [argListPath argListDir pkg stage] - terseRun (Ghc stage) $ ghcArgs pkg todo - -- Avoid rebuilding dependecies of out if it hasn't changed: - -- Note: cannot use copyFileChanged as it depends on the source file - --deps <- liftIO $ readFile $ out <.> "new" - --writeFileChanged out deps - --liftIO $ removeFiles "." [out <.> "new"] + run (Ghc stage) $ ghcArgs pkg todo (buildDir "c.deps") %> \out -> do need [argListPath argListDir pkg stage] @@ -76,7 +71,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do deps <- fmap concat $ forM srcs $ \src -> do let srcPath = path src depFile = buildDir takeFileName src <.> "deps" - terseRun (Gcc stage) $ gccArgs srcPath pkg todo + run (Gcc stage) $ gccArgs srcPath pkg todo liftIO $ readFile depFile writeFileChanged out deps liftIO $ removeFiles buildDir ["*.c.deps"] diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 2b82260..e5fa0b8 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -25,7 +25,7 @@ arRule pkg @ (Package _ path _) todo @ (stage, dist, _) = -- Splitting argument list into chunks as otherwise Ar chokes up maxChunk <- argSizeLimit forM_ (chunksOfSize maxChunk $ libHsObjs ++ cObjs) $ \os -> do - terseRun Ar $ arArgs os $ toStandard out + run Ar $ arArgs os $ toStandard out ldArgs :: Package -> TodoItem -> FilePath -> Args ldArgs (Package _ path _) (stage, dist, _) result = do @@ -45,7 +45,7 @@ ldRule pkg @ (Package name path _) todo @ (stage, dist, _) = in priority 2 $ (buildDir "*.o") %> \out -> do need [argListPath argListDir pkg stage] - terseRun Ld $ ldArgs pkg todo $ toStandard out + run Ld $ ldArgs pkg todo $ toStandard out synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) putColoured Green $ "/--------\n| Successfully built package " ++ name ++ " (stage " ++ show stage ++ ")." From git at git.haskell.org Thu Oct 26 23:08:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split compile rules for {hi, o}, clean up code. (3344cea) Message-ID: <20171026230820.1E0D03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3344ceadaa807de7708c9444b1a71537fa0a7fdd/ghc >--------------------------------------------------------------- commit 3344ceadaa807de7708c9444b1a71537fa0a7fdd Author: Andrey Mokhov Date: Sun Jan 18 13:34:58 2015 +0000 Split compile rules for {hi, o}, clean up code. >--------------------------------------------------------------- 3344ceadaa807de7708c9444b1a71537fa0a7fdd src/Oracles.hs | 12 +++++++----- src/Package/Compile.hs | 15 ++++++++++----- 2 files changed, 17 insertions(+), 10 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 4c6d9e9..215ccb7 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -67,15 +67,17 @@ packageDataOracle = do -- Oracle for 'path/dist/*.deps' files dependencyOracle :: Rules () dependencyOracle = do - deps <- newCache $ \depFile -> do - need [depFile] - putOracle $ "Parsing " ++ toStandard depFile ++ "..." - contents <- parseMakefile <$> (liftIO $ readFile depFile) + deps <- newCache $ \file -> do + need [file] + putOracle $ "Parsing " ++ file ++ "..." + contents <- parseMakefile <$> (liftIO $ readFile file) return $ M.fromList + $ map (bimap toStandard (map toStandard)) $ map (bimap head concat . unzip) $ groupBy ((==) `on` fst) $ sortBy (compare `on` fst) contents - addOracle $ \(DependencyListKey (file, obj)) -> M.lookup obj <$> deps file + addOracle $ \(DependencyListKey (file, obj)) -> + M.lookup (toStandard obj) <$> deps (toStandard file) return () oracleRules :: Rules () diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index e0080f9..762f533 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -47,10 +47,14 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = forM_ allWays $ \way -> do -- TODO: optimise (too many ways in allWays) let oPattern = "*." ++ osuf way let hiPattern = "*." ++ hisuf way - [buildDir oPattern, buildDir hiPattern] |%> \out -> do + + (buildDir hiPattern) %> \out -> do + let obj = out -<.> osuf way + need [obj] + + (buildDir oPattern) %> \obj -> do need [argListPath argListDir pkg stage] - let obj = toStandard $ out -<.> osuf way - vanillaObj = toStandard $ out -<.> "o" + let vanillaObj = obj -<.> "o" -- TODO: keep only vanilla dependencies in hDepFile hDeps <- args $ DependencyList hDepFile obj cDeps <- args $ DependencyList cDepFile $ takeFileName vanillaObj @@ -59,10 +63,10 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = -- Report impossible cases when (null $ hSrcs ++ cSrcs) $ redError_ $ "No source files found for " - ++ toStandard out ++ "." + ++ toStandard obj ++ "." when (not (null hSrcs) && not (null cSrcs)) $ redError_ $ "Both c and Haskell sources found for " - ++ toStandard out ++ "." + ++ toStandard obj ++ "." -- Build using appropriate compiler need $ hDeps ++ cDeps when (not $ null hSrcs) @@ -70,6 +74,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = when (not $ null cSrcs) $ run (Gcc stage) $ gccArgs pkg todo cSrcs obj + argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, settings) = (argListPath argListDir pkg stage) %> \out -> do From git at git.haskell.org Thu Oct 26 23:08:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more targets. (4399476) Message-ID: <20171026230823.8DD653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4399476dfd70a7ce9ad97750873e8b3397deb270/ghc >--------------------------------------------------------------- commit 4399476dfd70a7ce9ad97750873e8b3397deb270 Author: Andrey Mokhov Date: Sun Jan 18 14:27:23 2015 +0000 Add more targets. >--------------------------------------------------------------- 4399476dfd70a7ce9ad97750873e8b3397deb270 src/Targets.hs | 36 +++++++++++++++++++----------------- 1 file changed, 19 insertions(+), 17 deletions(-) diff --git a/src/Targets.hs b/src/Targets.hs index a8c9e68..25a3a0e 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -6,23 +6,25 @@ import Base -- TODO: this should eventually be removed and replaced by the top-level -- target, i.e. GHC (and perhaps, something else) libraryPackagesInStage :: Stage -> [String] -libraryPackagesInStage Stage0 = [] - --[ "bin-package-db" - --, "binary" - --, "hoopl" - --, "hpc" - --, "transformers" ] -libraryPackagesInStage Stage1 = ["directory", "bytestring"] - --libraryPackagesInStage Stage0 ++ - --[ "array" - --, "deepseq" - --, "Cabal/Cabal" - --, "containers" - --, "filepath" - --, "parallel" - --, "pretty" - --, "stm" - --, "template-haskell" ] +libraryPackagesInStage Stage0 = + [ "bin-package-db" + , "binary" + , "hoopl" + , "hpc" + , "transformers" ] +libraryPackagesInStage Stage1 = + libraryPackagesInStage Stage0 ++ + [ "array" + , "bytestring" + , "Cabal/Cabal" + , "containers" + , "deepseq" + , "directory" + , "filepath" + , "parallel" + , "pretty" + , "stm" + , "template-haskell" ] libraryPackagesInStage _ = [] From git at git.haskell.org Thu Oct 26 23:08:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Util/unifyPath function and make sure it is used. (a93823b) Message-ID: <20171026230826.F023C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1/ghc >--------------------------------------------------------------- commit a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1 Author: Andrey Mokhov Date: Sun Jan 18 14:28:04 2015 +0000 Add Util/unifyPath function and make sure it is used. >--------------------------------------------------------------- a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1 src/Oracles.hs | 13 +++++++------ src/Oracles/PackageData.hs | 4 ++-- src/Package/Base.hs | 21 ++++++++++----------- src/Package/Compile.hs | 8 ++++---- src/Package/Data.hs | 7 +++---- src/Package/Dependencies.hs | 6 +++--- src/Package/Library.hs | 10 +++++----- src/Util.hs | 4 ++++ 8 files changed, 38 insertions(+), 35 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 a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1 From git at git.haskell.org Thu Oct 26 23:08:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor rules, clean up code. (a1819f6) Message-ID: <20171026230830.7A33C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e/ghc >--------------------------------------------------------------- commit a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e Author: Andrey Mokhov Date: Sun Jan 18 23:52:09 2015 +0000 Refactor rules, clean up code. >--------------------------------------------------------------- a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e src/Oracles.hs | 8 ++++---- src/Package/Base.hs | 21 ++++++++++++-------- src/Package/Compile.hs | 45 +++++++++++++++++++++---------------------- src/Package/Library.hs | 52 +++++++++++++++++++++++++------------------------- src/Targets.hs | 2 +- src/Ways.hs | 1 - 6 files changed, 66 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e From git at git.haskell.org Thu Oct 26 23:08:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix recursive rules error. (8290198) Message-ID: <20171026230833.F25C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82901986216e56d42623299aaec8ca7d1bddcdca/ghc >--------------------------------------------------------------- commit 82901986216e56d42623299aaec8ca7d1bddcdca Author: Andrey Mokhov Date: Mon Jan 19 03:45:10 2015 +0000 Fix recursive rules error. >--------------------------------------------------------------- 82901986216e56d42623299aaec8ca7d1bddcdca src/Package/Base.hs | 8 +++++--- src/Package/Compile.hs | 12 +++++++++--- src/Package/Data.hs | 4 +++- src/Package/Dependencies.hs | 8 +++++--- src/Package/Library.hs | 8 ++++++-- 5 files changed, 28 insertions(+), 12 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 023b001..cf29e59 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -108,8 +108,9 @@ includeGhcArgs path dist = pkgHsSources :: FilePath -> FilePath -> Action [FilePath] pkgHsSources path dist = do let pathDist = path dist + autogen = pathDist "build/autogen" dirs <- map (path ) <$> args (SrcDirs pathDist) - findModuleFiles pathDist dirs [".hs", ".lhs"] + findModuleFiles pathDist (autogen:dirs) [".hs", ".lhs"] -- TODO: look for non-{hs,c} objects too @@ -136,11 +137,13 @@ pkgLibHsObjects path dist stage way = do let pathDist = path dist buildDir = unifyPath $ pathDist "build" split <- splitObjects stage + depObjs <- pkgDepHsObjects path dist way if split then do + need depObjs -- Otherwise, split objects may not yet be available let suffix = "_" ++ osuf way ++ "_split/*." ++ osuf way findModuleFiles pathDist [buildDir] [suffix] - else pkgDepHsObjects path dist way + else do return depObjs findModuleFiles :: FilePath -> [FilePath] -> [String] -> Action [FilePath] findModuleFiles pathDist directories suffixes = do @@ -153,7 +156,6 @@ findModuleFiles pathDist directories suffixes = do let dir = takeDirectory file dirExists <- liftIO $ S.doesDirectoryExist dir when dirExists $ return file - files <- getDirectoryFiles "" fileList return $ map unifyPath files diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 01659b6..94cf16a 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -49,8 +49,10 @@ compileHaskell pkg @ (Package _ path _) todo @ (stage, dist, _) obj way = do let buildDir = unifyPath $ path dist "build" -- TODO: keep only vanilla dependencies in 'haskell.deps' deps <- args $ DependencyList (buildDir "haskell.deps") obj + let (srcs, his) = partition ("//*hs" ?==) deps + objs = map (-<.> osuf way) his + -- Need *.o files instead of *.hi files to avoid recursive rules need deps - let srcs = filter ("//*hs" ?==) deps run (Ghc stage) $ ghcArgs pkg todo way srcs obj buildRule :: Package -> TodoItem -> Rules () @@ -64,15 +66,19 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = (buildDir hiPattern) %> \hi -> do let obj = hi -<.> osuf way - need [obj] + -- TODO: Understand why 'need [obj]' doesn't work, leading to + -- recursive rules error. Below is a workaround. + -- putColoured Yellow $ "Hi " ++ hi + compileHaskell pkg todo obj way (buildDir oPattern) %> \obj -> do - need [argListPath argListDir pkg stage] let vanillaObjName = takeFileName obj -<.> "o" cDeps <- args $ DependencyList cDepFile vanillaObjName if null cDeps then compileHaskell pkg todo obj way else compileC pkg todo cDeps obj + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, settings) = diff --git a/src/Package/Data.hs b/src/Package/Data.hs index e1afee1..6d01ba5 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -121,12 +121,14 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = -- TODO: Is this needed? Also check out Paths_cpsa.hs. -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do - need [argListPath argListDir pkg stage, cabal] + need [cabal] when (doesFileExist $ configure <.> "ac") $ need [configure] run GhcCabal $ cabalArgs pkg todo when (registerPackage settings) $ run (GhcPkg stage) $ ghcPkgArgs pkg todo postProcessPackageData $ pathDist "package-data.mk" + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, _) = diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 8675c6f..f87580a 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -61,12 +61,12 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do let pathDist = path dist buildDir = pathDist "build" - (buildDir "haskell.deps") %> \out -> do - need [argListPath argListDir pkg stage] + (buildDir "haskell.deps") %> \_ -> do run (Ghc stage) $ ghcArgs pkg todo + -- Finally, record the argument list + need [argListPath argListDir pkg stage] (buildDir "c.deps") %> \out -> do - need [argListPath argListDir pkg stage] srcs <- args $ CSrcs pathDist deps <- fmap concat $ forM srcs $ \src -> do let srcPath = path src @@ -75,6 +75,8 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do liftIO $ readFile depFile writeFileChanged out deps liftIO $ removeFiles buildDir ["*.c.deps"] + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, _) = diff --git a/src/Package/Library.hs b/src/Package/Library.hs index c377bc8..6ad029d 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -26,13 +26,15 @@ arRule pkg @ (Package _ path _) todo @ (stage, dist, _) = let way = detectWay $ tail $ takeExtension out cObjs <- pkgCObjects path dist way hsObjs <- pkgDepHsObjects path dist way - need $ [argListPath argListDir pkg stage] ++ cObjs ++ hsObjs + need $ cObjs ++ hsObjs libHsObjs <- pkgLibHsObjects path dist stage way liftIO $ removeFiles "." [out] -- Splitting argument list into chunks as otherwise Ar chokes up maxChunk <- argSizeLimit forM_ (chunksOfSize maxChunk $ cObjs ++ libHsObjs) $ \objs -> do run Ar $ arArgs objs $ unifyPath out + -- Finally, record the argument list + need [argListPath argListDir pkg stage] ldRule :: Package -> TodoItem -> Rules () ldRule pkg @ (Package name path _) todo @ (stage, dist, _) = @@ -42,13 +44,15 @@ ldRule pkg @ (Package name path _) todo @ (stage, dist, _) = priority 2 $ (buildDir "*.o") %> \out -> do cObjs <- pkgCObjects path dist vanilla hObjs <- pkgDepHsObjects path dist vanilla - need $ [argListPath argListDir pkg stage] ++ cObjs ++ hObjs + need $ cObjs ++ hObjs run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) putColoured Green $ "/--------\n| Successfully built package '" ++ name ++ "' (stage " ++ show stage ++ ")." putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." ++ "\n\\--------" + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg @ (Package _ path _) todo @ (stage, dist, settings) = From git at git.haskell.org Thu Oct 26 23:08:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (20ed2d1) Message-ID: <20171026230837.5BB473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20ed2d1d6d1ce6b612eb607cae447c9646f7be6b/ghc >--------------------------------------------------------------- commit 20ed2d1d6d1ce6b612eb607cae447c9646f7be6b Author: Andrey Mokhov Date: Mon Jan 19 04:13:06 2015 +0000 Clean up. >--------------------------------------------------------------- 20ed2d1d6d1ce6b612eb607cae447c9646f7be6b src/Package/Compile.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 94cf16a..d99e2bf 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -49,9 +49,7 @@ compileHaskell pkg @ (Package _ path _) todo @ (stage, dist, _) obj way = do let buildDir = unifyPath $ path dist "build" -- TODO: keep only vanilla dependencies in 'haskell.deps' deps <- args $ DependencyList (buildDir "haskell.deps") obj - let (srcs, his) = partition ("//*hs" ?==) deps - objs = map (-<.> osuf way) his - -- Need *.o files instead of *.hi files to avoid recursive rules + let srcs = filter ("//*hs" ?==) deps need deps run (Ghc stage) $ ghcArgs pkg todo way srcs obj From git at git.haskell.org Thu Oct 26 23:08:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add DepIncludeDirs package data option. (91a8bab) Message-ID: <20171026230840.BCE1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91a8babed3f640ecd972c7a20fd574e3853250d1/ghc >--------------------------------------------------------------- commit 91a8babed3f640ecd972c7a20fd574e3853250d1 Author: Andrey Mokhov Date: Mon Jan 19 11:49:40 2015 +0000 Add DepIncludeDirs package data option. >--------------------------------------------------------------- 91a8babed3f640ecd972c7a20fd574e3853250d1 src/Oracles/PackageData.hs | 42 ++++++++++++++++++++++-------------------- src/Package/Base.hs | 2 +- src/Package/Compile.hs | 1 + src/Targets.hs | 1 + 4 files changed, 25 insertions(+), 21 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 38accfe..760f47e 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -23,16 +23,17 @@ data PackageData = Version FilePath | PackageKey FilePath | Synopsis FilePath -data MultiPackageData = Modules FilePath - | SrcDirs FilePath - | IncludeDirs FilePath - | Deps FilePath - | DepKeys FilePath - | DepNames FilePath - | CppArgs FilePath - | HsArgs FilePath - | CcArgs FilePath - | CSrcs FilePath +data MultiPackageData = Modules FilePath + | SrcDirs FilePath + | IncludeDirs FilePath + | Deps FilePath + | DepKeys FilePath + | DepNames FilePath + | CppArgs FilePath + | HsArgs FilePath + | CcArgs FilePath + | CSrcs FilePath + | DepIncludeDirs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -53,16 +54,17 @@ instance ShowArg PackageData where instance ShowArgs MultiPackageData where showArgs packageData = do let (key, path, defaultValue) = case packageData of - Modules path -> ("MODULES" , path, "" ) - SrcDirs path -> ("HS_SRC_DIRS" , path, ".") - IncludeDirs path -> ("INCLUDE_DIRS", path, ".") - Deps path -> ("DEPS" , path, "" ) - DepKeys path -> ("DEP_KEYS" , path, "" ) - DepNames path -> ("DEP_NAMES" , path, "" ) - CppArgs path -> ("CPP_OPTS" , path, "" ) - HsArgs path -> ("HC_OPTS" , path, "" ) - CcArgs path -> ("CC_OPTS" , path, "" ) - CSrcs path -> ("C_SRCS" , path, "" ) + Modules path -> ("MODULES" , path, "" ) + SrcDirs path -> ("HS_SRC_DIRS" , path, ".") + IncludeDirs path -> ("INCLUDE_DIRS" , path, ".") + Deps path -> ("DEPS" , path, "" ) + DepKeys path -> ("DEP_KEYS" , path, "" ) + DepNames path -> ("DEP_NAMES" , path, "" ) + CppArgs path -> ("CPP_OPTS" , path, "" ) + HsArgs path -> ("HC_OPTS" , path, "" ) + CcArgs path -> ("CC_OPTS" , path, "" ) + CSrcs path -> ("C_SRCS" , path, "" ) + DepIncludeDirs path -> ("DEP_LIB_REL_DIRS", path, "" ) fullKey = replaceSeparators '_' $ path ++ "_" ++ key pkgData = path "package-data.mk" res <- askOracle $ PackageDataKey (pkgData, fullKey) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index cf29e59..aafc85b 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -155,7 +155,7 @@ findModuleFiles pathDist directories suffixes = do ] $ \file -> do let dir = takeDirectory file dirExists <- liftIO $ S.doesDirectoryExist dir - when dirExists $ return file + when dirExists $ return $ unifyPath file files <- getDirectoryFiles "" fileList return $ map unifyPath files diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index d99e2bf..e98f1a5 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -35,6 +35,7 @@ gccArgs (Package _ path _) (_, dist, _) srcs result = , commonCcArgs , commonCcWarninigArgs , pathArgs "-I" path $ IncludeDirs pathDist + , pathArgs "-I" path $ DepIncludeDirs pathDist , args ("-c":srcs) , args ["-o", result] ] diff --git a/src/Targets.hs b/src/Targets.hs index cf1ceb2..847c1fa 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -21,6 +21,7 @@ libraryPackagesInStage Stage1 = , "deepseq" , "directory" , "filepath" + , "ghc-prim" , "parallel" , "pretty" , "stm" From git at git.haskell.org Thu Oct 26 23:08:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, do minor refactoring. (79bc4c9) Message-ID: <20171026230844.26E553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79bc4c9d2452c1e1621beef3a892c7bdf00199cd/ghc >--------------------------------------------------------------- commit 79bc4c9d2452c1e1621beef3a892c7bdf00199cd Author: Andrey Mokhov Date: Mon Jan 19 16:16:54 2015 +0000 Add comments, do minor refactoring. >--------------------------------------------------------------- 79bc4c9d2452c1e1621beef3a892c7bdf00199cd src/Oracles/PackageData.hs | 6 +++-- src/Package.hs | 23 +++++++------------ src/Package/Base.hs | 11 +++++++-- src/Package/Data.hs | 18 ++++++++++++--- src/Targets.hs | 56 +++++++++++++++++++++++++--------------------- src/Ways.hs | 35 ++++++++++++++++++++--------- 6 files changed, 90 insertions(+), 59 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 79bc4c9d2452c1e1621beef3a892c7bdf00199cd From git at git.haskell.org Thu Oct 26 23:08:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix include paths for Gcc. (2c7003a) Message-ID: <20171026230847.8666C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c7003a009d1205a73430b21bdc05caab23a8d85/ghc >--------------------------------------------------------------- commit 2c7003a009d1205a73430b21bdc05caab23a8d85 Author: Andrey Mokhov Date: Mon Jan 19 17:03:40 2015 +0000 Fix include paths for Gcc. >--------------------------------------------------------------- 2c7003a009d1205a73430b21bdc05caab23a8d85 src/Oracles/Builder.hs | 2 +- src/Package/Base.hs | 9 ++++++++- src/Package/Compile.hs | 3 +-- src/Package/Dependencies.hs | 2 +- 4 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index e52cc58..dc41507 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -119,7 +119,7 @@ interestingInfo builder ss = case builder of Ld -> prefixAndSuffix 4 0 ss Gcc _ -> if head ss == "-MM" then prefixAndSuffix 1 1 ss - else ss + else prefixAndSuffix 0 4 ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss else prefixAndSuffix 0 4 ss diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 8e12f15..e2031b6 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -7,7 +7,8 @@ module Package.Base ( Package (..), Settings (..), TodoItem (..), defaultSettings, libraryPackage, standardLibrary, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - pathArgs, packageArgs, includeGhcArgs, pkgHsSources, + pathArgs, packageArgs, + includeGccArgs, includeGhcArgs, pkgHsSources, pkgDepHsObjects, pkgLibHsObjects, pkgCObjects, argSizeLimit, sourceDependecies, @@ -99,6 +100,12 @@ packageArgs stage pathDist = do else productArgs "-package-name" (arg $ PackageKey pathDist) <> productArgs "-package" (args $ Deps pathDist) ] +includeGccArgs :: FilePath -> FilePath -> Args +includeGccArgs path dist = + let pathDist = path dist + in args [ pathArgs "-I" path $ IncludeDirs pathDist + , pathArgs "-I" path $ DepIncludeDirs pathDist ] + includeGhcArgs :: FilePath -> FilePath -> Args includeGhcArgs path dist = let pathDist = path dist diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index e98f1a5..eb2417f 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -34,8 +34,7 @@ gccArgs (Package _ path _) (_, dist, _) srcs result = in args [ args $ CcArgs pathDist , commonCcArgs , commonCcWarninigArgs - , pathArgs "-I" path $ IncludeDirs pathDist - , pathArgs "-I" path $ DepIncludeDirs pathDist + , includeGccArgs path dist , args ("-c":srcs) , args ["-o", result] ] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index f87580a..abee3f3 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -51,7 +51,7 @@ gccArgs sourceFile (Package _ path _) (stage, dist, _) = , args $ CcArgs pathDist , commonCcArgs , commonCcWarninigArgs - , pathArgs "-I" path $ IncludeDirs pathDist + , includeGccArgs path dist , args ["-MF", unifyPath depFile] , args ["-x", "c"] , arg $ unifyPath sourceFile ] From git at git.haskell.org Thu Oct 26 23:08:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add remaining library packages to Targets.hs. (8a860e6) Message-ID: <20171026230851.08F7A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8a860e62574675274d1d7158503dfd5b4bb21e15/ghc >--------------------------------------------------------------- commit 8a860e62574675274d1d7158503dfd5b4bb21e15 Author: Andrey Mokhov Date: Tue Jan 20 04:39:40 2015 +0000 Add remaining library packages to Targets.hs. >--------------------------------------------------------------- 8a860e62574675274d1d7158503dfd5b4bb21e15 src/Oracles/Builder.hs | 1 + src/Package.hs | 6 +-- src/Package/Base.hs | 61 ++++++++++++++++-------- src/Package/Compile.hs | 8 ++-- src/Package/Data.hs | 17 +++---- src/Package/Dependencies.hs | 8 ++-- src/Package/Library.hs | 6 +-- src/Targets.hs | 112 +++++++++++++++++++++++++++++++++++--------- src/Ways.hs | 3 +- 9 files changed, 157 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8a860e62574675274d1d7158503dfd5b4bb21e15 From git at git.haskell.org Thu Oct 26 23:08:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add base and integer-gmp2 to the list of targets. (2d24ed4) Message-ID: <20171026230854.837753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d24ed4ae03015db98fb7ca1a86fe490b4540d75/ghc >--------------------------------------------------------------- commit 2d24ed4ae03015db98fb7ca1a86fe490b4540d75 Author: Andrey Mokhov Date: Tue Jan 20 16:23:12 2015 +0000 Add base and integer-gmp2 to the list of targets. >--------------------------------------------------------------- 2d24ed4ae03015db98fb7ca1a86fe490b4540d75 src/Package/Base.hs | 4 ++- src/Package/Compile.hs | 3 ++- src/Package/Data.hs | 4 +-- src/Package/Dependencies.hs | 5 ++-- src/Targets.hs | 65 ++++++++++++++++++++++++--------------------- 5 files changed, 45 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 2d24ed4ae03015db98fb7ca1a86fe490b4540d75 From git at git.haskell.org Thu Oct 26 23:08:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:08:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (e809d1c) Message-ID: <20171026230857.F17D03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e809d1c945a36f87fc1c006e8b4b88296b5ea48e/ghc >--------------------------------------------------------------- commit e809d1c945a36f87fc1c006e8b4b88296b5ea48e Author: Andrey Mokhov Date: Tue Jan 20 16:27:51 2015 +0000 Clean up. >--------------------------------------------------------------- e809d1c945a36f87fc1c006e8b4b88296b5ea48e src/Targets.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Targets.hs b/src/Targets.hs index 595c38f..2ff6eae 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -60,7 +60,7 @@ targetPackages = baseConfArgs :: Settings -> Settings baseConfArgs settings = - settings { customConfArgs = arg $ "--flags=" ++ show integerLibrary } + settings { customConfArgs = arg $ "--flags=" ++ integerLibraryName } -- see Note [Cabal package weirdness] cabalTraits :: (String, Settings -> Settings) From git at git.haskell.org Thu Oct 26 23:09:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (7c2279b) Message-ID: <20171026230901.6C4013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c2279b523ce8b71dc0e9492380d8798a8b1b4f2/ghc >--------------------------------------------------------------- commit 7c2279b523ce8b71dc0e9492380d8798a8b1b4f2 Author: Andrey Mokhov Date: Wed Jan 21 23:20:52 2015 +0000 Add comments. >--------------------------------------------------------------- 7c2279b523ce8b71dc0e9492380d8798a8b1b4f2 src/Oracles.hs | 1 + src/Package.hs | 2 +- src/Package/Base.hs | 11 ++++++++--- src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 7 ++++--- src/Targets.hs | 19 +++++++++++++++++++ 6 files changed, 35 insertions(+), 9 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 80e2e60..4e6fe5b 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -11,6 +11,7 @@ module Oracles ( import Development.Shake.Config import Development.Shake.Util import qualified Data.HashMap.Strict as M +-- TODO: get rid of Bifunctor dependency import Data.Bifunctor import Base import Util diff --git a/src/Package.hs b/src/Package.hs index 4d24e2a..1931ea3 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -26,7 +26,7 @@ packageRules = do -- We build *only one* vanilla .o file (not sure why) -- We build .way_a file for each way (or its dynamic version). -- TODO: Check BUILD_GHCI_LIB flag to decide if .o is needed - -- TODO: move this into buildPackage + -- TODO: move this into a separate file (perhaps, to Targets.hs?) action $ when (buildWhen settings) $ do let pathDist = path dist buildDir = pathDist "build" diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 00b4356..88e357f 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -39,9 +39,9 @@ defaultSettings stage = Settings { customConfArgs = mempty, customCcArgs = mempty, - customLdArgs = mempty, - customCppArgs = mempty, - customDllArgs = mempty, + customLdArgs = mempty, -- currently not used + customCppArgs = mempty, -- currently not used + customDllArgs = mempty, -- only for compiler registerPackage = True, ways = defaultWays stage, buildWhen = return True @@ -54,6 +54,11 @@ defaultSettings stage = Settings -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to package.cabal -- Settings may be different for different combinations of Stage & FilePath +-- TODO: the above may be incorrect, settings seem to *only* depend on the +-- stage. In fact Stage seem to define FilePath and Settings, therefore we +-- can drop the TodoItem and replace it by [Stage] and two functions +-- * distDirectory :: Package -> Stage -> FilePath +-- * settings :: Package -> Stage -> Settings type TodoItem = (Stage, FilePath, Settings) -- pkgPath is the path to the source code relative to the root diff --git a/src/Package/Data.hs b/src/Package/Data.hs index b2de8c5..602993e 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -26,8 +26,8 @@ configureArgs stage settings = unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s cflags = [ commonCcArgs `filterOut` "-Werror" , args $ ConfCcArgs stage - -- , customCcArgs settings -- TODO: fix - , commonCcWarninigArgs ] -- TODO: check if cflags are glued + -- , customCcArgs settings -- TODO: bring this back + , commonCcWarninigArgs ] -- TODO: check why cflags are glued ldflags = [ commonLdArgs , args $ ConfGccLinkerArgs stage , customLdArgs settings ] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 604034e..c861707 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -3,6 +3,7 @@ module Package.Dependencies (buildPackageDependencies) where import Package.Base +-- TODO: use oracles instead of arg files. argListDir :: FilePath argListDir = "shake/arg/buildPackageDependencies" @@ -49,9 +50,9 @@ gccArgs sourceFile (Package _ path _ _) (stage, dist, settings) = depFile = buildDir takeFileName sourceFile <.> "deps" in args [ args ["-E", "-MM"] -- TODO: add a Cpp Builder instead , args $ CcArgs pathDist - , commonCcArgs - , customCcArgs settings - , commonCcWarninigArgs + , commonCcArgs -- TODO: remove? + , customCcArgs settings -- TODO: Replace by customCppArgs? + , commonCcWarninigArgs -- TODO: remove? , includeGccArgs path dist , args ["-MF", unifyPath depFile] , args ["-x", "c"] diff --git a/src/Targets.hs b/src/Targets.hs index 2ff6eae..bc4c29d 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -15,12 +15,14 @@ instance Show IntegerLibrary where IntegerGmp2 -> "integer-gmp2" IntegerSimple -> "integer-simple" +-- TODO: keep or move to configuration files? see Note [configuration files] integerLibrary :: IntegerLibrary integerLibrary = IntegerGmp2 integerLibraryName :: String integerLibraryName = show integerLibrary +-- see Note [configuration files] buildHaddock :: Bool buildHaddock = True @@ -107,6 +109,23 @@ targetPackagesInStage stage = filter inStage targetPackages inStage (Package _ _ _ todoItems) = any matchStage todoItems matchStage (todoStage, _, _) = todoStage == stage +-- TODISCUSS -- Note [Cabal package weirdness] -- Find out if we can move the contents to just Cabal/ -- What is Cabal/cabal-install? Do we need it? + +-- TODISCUSS +-- Note [configuration files] +-- In this file we have two configuration options: integerLibrary and +-- buildHaddock. Arguably, their place should be among other configuration +-- options in the config files, however, moving integerLibrary there would +-- actually be quite painful, because it would then be confined to live in +-- the Action monad. +-- In general, shall we keep as many options as possible inside Shake, or +-- leave them in one place -- configuration files? We could try to move +-- everything to Shake which would be great: +-- * type safety and better abstractions +-- * useable outside the Action monad, e.g. for creating rules +-- * recompiling Shake is much faster then re-running configure script +-- * ... no more autoconf/configure and native Windows build?! Sign me up! +-- However, moving everything to Shake seems unfeasible at the moment. From git at git.haskell.org Thu Oct 26 23:09:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Restrict ShowArgs and args to accept only lists. (9c218ad) Message-ID: <20171026230905.0427D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c218adf6e025572ae550302419f0bcc632d3be6/ghc >--------------------------------------------------------------- commit 9c218adf6e025572ae550302419f0bcc632d3be6 Author: Andrey Mokhov Date: Thu Jan 22 23:38:46 2015 +0000 Restrict ShowArgs and args to accept only lists. >--------------------------------------------------------------- 9c218adf6e025572ae550302419f0bcc632d3be6 src/Base.hs | 31 +++++++++++-------------------- src/Package/Base.hs | 14 ++++++++------ src/Package/Compile.hs | 2 +- src/Package/Data.hs | 9 +++++---- src/Package/Dependencies.hs | 6 +++--- 5 files changed, 28 insertions(+), 34 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 232bca2..fa9104a 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,7 +12,6 @@ module Base ( ShowArg (..), ShowArgs (..), arg, args, Condition (..), - (<+>), filterOut, productArgs, concatArgs ) where @@ -49,34 +48,26 @@ instance ShowArg String where instance ShowArg a => ShowArg (Action a) where showArg = (showArg =<<) --- Using the Creators' trick for overlapping String instances class ShowArgs a where - showArgs :: a -> Args - showListArgs :: [a] -> Args - showListArgs = mconcat . map showArgs + showArgs :: a -> Args -instance ShowArgs Char where - showArgs c = return [[c]] - showListArgs s = return [s] +instance ShowArgs [String] where + showArgs = return -instance ShowArgs a => ShowArgs [a] where - showArgs = showListArgs +instance ShowArgs [Arg] where + showArgs = sequence + +instance ShowArgs [Args] where + showArgs = mconcat instance ShowArgs a => ShowArgs (Action a) where showArgs = (showArgs =<<) --- TODO: improve args type safety args :: ShowArgs a => a -> Args args = showArgs arg :: ShowArg a => a -> Args -arg = args . showArg - --- Combine two heterogeneous ShowArgs values -(<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args -a <+> b = (<>) <$> showArgs a <*> showArgs b - -infixr 6 <+> +arg a = args [showArg a] -- Filter out given arg(s) from a collection filterOut :: ShowArgs a => Args -> a -> Args @@ -85,7 +76,7 @@ filterOut as exclude = do filter (`notElem` exclude') <$> as -- Generate a cross product collection of two argument collections --- Example: productArgs ["-a", "-b"] "c" = arg ["-a", "c", "-b", "c"] +-- Example: productArgs ["-a", "-b"] "c" = args ["-a", "c", "-b", "c"] productArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args productArgs as bs = do as' <- showArgs as @@ -93,7 +84,7 @@ productArgs as bs = do return $ concat $ sequence [as', bs'] -- Similar to productArgs but concat resulting arguments pairwise --- Example: concatArgs ["-a", "-b"] "c" = arg ["-ac", "-bc"] +-- Example: concatArgs ["-a", "-b"] "c" = args ["-ac", "-bc"] concatArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args concatArgs as bs = do as' <- showArgs as diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 88e357f..d54320f 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -122,10 +122,11 @@ packageArgs stage pathDist = do , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" , if usePackageKey - then productArgs "-this-package-key" (arg $ PackageKey pathDist) - <> productArgs "-package-key" (args $ DepKeys pathDist) - else productArgs "-package-name" (arg $ PackageKey pathDist) - <> productArgs "-package" (args $ Deps pathDist) ] + then productArgs ["-this-package-key"] [arg $ PackageKey pathDist] + <> productArgs ["-package-key" ] [args $ DepKeys pathDist] + else productArgs ["-package-name" ] [arg $ PackageKey pathDist] + <> productArgs ["-package" ] [args $ Deps pathDist] + ] includeGccArgs :: FilePath -> FilePath -> Args includeGccArgs path dist = @@ -145,8 +146,9 @@ includeGhcArgs path dist = [buildDir, unifyPath $ buildDir "autogen"] , pathArgs "-I" path $ IncludeDirs pathDist , arg "-optP-include" -- TODO: Shall we also add -cpp? - , concatArgs "-optP" $ - unifyPath $ buildDir "autogen/cabal_macros.h" ] + , concatArgs ["-optP"] + [unifyPath $ buildDir "autogen/cabal_macros.h"] + ] pkgHsSources :: FilePath -> FilePath -> Action [FilePath] pkgHsSources path dist = do diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 99aee33..fe9ba73 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -23,7 +23,7 @@ ghcArgs (Package _ path _ _) (stage, dist, _) way srcs result = , args $ HsArgs pathDist -- TODO: now we have both -O and -O2 -- <> arg ["-O2"] - , productArgs ["-odir", "-hidir", "-stubdir"] buildDir + , productArgs ["-odir", "-hidir", "-stubdir"] [buildDir] , when (splitObjects stage) $ arg "-split-objs" , args ("-c":srcs) , args ["-o", result] ] diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 602993e..5373f6e 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -24,7 +24,7 @@ configureArgs stage settings = let conf key as = do s <- unwords <$> args as unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = [ commonCcArgs `filterOut` "-Werror" + cflags = [ commonCcArgs `filterOut` ["-Werror"] , args $ ConfCcArgs stage -- , customCcArgs settings -- TODO: bring this back , commonCcWarninigArgs ] -- TODO: check why cflags are glued @@ -37,7 +37,8 @@ configureArgs stage settings = in args [ conf "CFLAGS" cflags , conf "LDFLAGS" ldflags , conf "CPPFLAGS" cppflags - , arg $ concat <$> "--gcc-options=" <+> cflags <+> " " <+> ldflags + , arg $ concat <$> + arg "--gcc-options=" <> args cflags <> arg " " <> args ldflags , conf "--with-iconv-includes" IconvIncludeDirs , conf "--with-iconv-libraries" IconvLibDirs , conf "--with-gmp-includes" GmpIncludeDirs @@ -73,8 +74,8 @@ bootPkgConstraints = args $ do content <- lines <$> liftIO (readFile cabal) let versionLines = filter (("ersion:" `isPrefixOf`) . drop 1) content case versionLines of - [versionLine] -> args ["--constraint", depName ++ " == " - ++ dropWhile (not . isDigit) versionLine ] + [versionLine] -> return $ "--constraint " ++ depName ++ " == " + ++ dropWhile (not . isDigit) versionLine _ -> redError $ "Cannot determine package version in '" ++ unifyPath cabal ++ "'." diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index c861707..8fb27b2 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -16,9 +16,9 @@ ghcArgs (Package name path _ _) (stage, dist, settings) = , packageArgs stage pathDist , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist - , productArgs ["-odir", "-stubdir", "-hidir"] buildDir - , args ["-dep-makefile", depFile ] - , productArgs "-dep-suffix" $ map wayPrefix <$> ways settings + , productArgs ["-odir", "-stubdir", "-hidir"] [buildDir] + , args ["-dep-makefile", depFile] + , productArgs ["-dep-suffix"] $ map wayPrefix <$> ways settings , args $ HsArgs pathDist , args $ pkgHsSources path dist ] From git at git.haskell.org Thu Oct 26 23:09:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix bootPkgConstraints. (98cfed5) Message-ID: <20171026230908.7A5A43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/98cfed580f1655de01f706761b4c4b56da22e523/ghc >--------------------------------------------------------------- commit 98cfed580f1655de01f706761b4c4b56da22e523 Author: Andrey Mokhov Date: Fri Jan 30 12:47:22 2015 +0000 Fix bootPkgConstraints. >--------------------------------------------------------------- 98cfed580f1655de01f706761b4c4b56da22e523 src/Package/Data.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 5373f6e..6d108aa 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -74,8 +74,8 @@ bootPkgConstraints = args $ do content <- lines <$> liftIO (readFile cabal) let versionLines = filter (("ersion:" `isPrefixOf`) . drop 1) content case versionLines of - [versionLine] -> return $ "--constraint " ++ depName ++ " == " - ++ dropWhile (not . isDigit) versionLine + [versionLine] -> return $ args ["--constraint", depName ++ " == " + ++ dropWhile (not . isDigit) versionLine] _ -> redError $ "Cannot determine package version in '" ++ unifyPath cabal ++ "'." From git at git.haskell.org Thu Oct 26 23:09:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement customise :: Package -> Package function. (eafd5e0) Message-ID: <20171026230912.17AA03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb/ghc >--------------------------------------------------------------- commit eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb Author: Andrey Mokhov Date: Mon Feb 9 14:48:18 2015 +0000 Implement customise :: Package -> Package function. >--------------------------------------------------------------- eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb src/Package/Base.hs | 27 ++++++------ src/Package/Data.hs | 15 +++---- src/Targets.hs | 119 +++++++++++++++++++++++----------------------------- 3 files changed, 74 insertions(+), 87 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 eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb From git at git.haskell.org Thu Oct 26 23:09:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep Haskell-land settings in Settings.hs. (9d35421) Message-ID: <20171026230915.9D8A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d35421d9ba504fb9e412027d574b455b94ff90c/ghc >--------------------------------------------------------------- commit 9d35421d9ba504fb9e412027d574b455b94ff90c Author: Andrey Mokhov Date: Mon Feb 9 14:49:19 2015 +0000 Keep Haskell-land settings in Settings.hs. >--------------------------------------------------------------- 9d35421d9ba504fb9e412027d574b455b94ff90c src/Base.hs | 2 ++ src/Settings.hs | 18 ++++++++++++++++++ 2 files changed, 20 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index fa9104a..923e13d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,6 +7,7 @@ module Base ( module Data.Function, module Data.Monoid, module Data.List, + module Settings, Stage (..), Arg, Args, ShowArg (..), ShowArgs (..), @@ -22,6 +23,7 @@ import Control.Applicative import Data.Function import Data.Monoid import Data.List +import Settings data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) diff --git a/src/Settings.hs b/src/Settings.hs new file mode 100644 index 0000000..6ffc976 --- /dev/null +++ b/src/Settings.hs @@ -0,0 +1,18 @@ +module Settings ( + IntegerLibrary (..), integerLibrary, + buildHaddock + ) where + +data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple + +instance Show IntegerLibrary where + show library = case library of + IntegerGmp -> "integer-gmp" + IntegerGmp2 -> "integer-gmp2" + IntegerSimple -> "integer-simple" + +integerLibrary :: IntegerLibrary +integerLibrary = IntegerGmp2 + +buildHaddock :: Bool +buildHaddock = True From git at git.haskell.org Thu Oct 26 23:09:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix cabalName in libraryPackage. (ba209b9) Message-ID: <20171026230919.0C8763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba209b90b53ff9b6bfe32f4f890fc2911c274122/ghc >--------------------------------------------------------------- commit ba209b90b53ff9b6bfe32f4f890fc2911c274122 Author: Andrey Mokhov Date: Mon Feb 9 15:14:08 2015 +0000 Fix cabalName in libraryPackage. >--------------------------------------------------------------- ba209b90b53ff9b6bfe32f4f890fc2911c274122 src/Package/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 076bc2a..7f310d1 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -84,7 +84,7 @@ libraryPackage name cabalName stages settings = Package name (unifyPath $ "libraries" name) - (unifyPath $ "libraries" name cabalName <.> "cabal") + cabalName [ (stage , if stage == Stage0 then "dist-boot" else "dist-install" , settings stage) From git at git.haskell.org Thu Oct 26 23:09:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix comments. (77766e8) Message-ID: <20171026230922.8293B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/77766e8e875b069d05c9a536811df20796d023c5/ghc >--------------------------------------------------------------- commit 77766e8e875b069d05c9a536811df20796d023c5 Author: Andrey Mokhov Date: Mon Feb 9 15:40:44 2015 +0000 Fix comments. >--------------------------------------------------------------- 77766e8e875b069d05c9a536811df20796d023c5 src/Package/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 7f310d1..2738b83 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -52,7 +52,7 @@ defaultSettings stage = Settings -- The typical structure of that directory is: -- * build/ : contains compiled object code -- * doc/ : produced by haddock --- * package-data.mk : contains output of ghc-cabal applied to package.cabal +-- * package-data.mk : contains output of ghc-cabal applied to pkgCabal.cabal -- Settings may be different for different combinations of Stage & FilePath -- TODO: the above may be incorrect, settings seem to *only* depend on the -- stage. In fact Stage seem to define FilePath and Settings, therefore we From git at git.haskell.org Thu Oct 26 23:09:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (14a236b) Message-ID: <20171026230925.EB5163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14a236b420ac7a03ef68b6a193efe10936dc10b8/ghc >--------------------------------------------------------------- commit 14a236b420ac7a03ef68b6a193efe10936dc10b8 Author: Andrey Mokhov Date: Mon Feb 9 22:25:30 2015 +0000 Clean up. >--------------------------------------------------------------- 14a236b420ac7a03ef68b6a193efe10936dc10b8 src/Base.hs | 2 -- src/Oracles/Flag.hs | 2 +- src/Package/Base.hs | 2 ++ src/Targets.hs | 3 --- 4 files changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 923e13d..fa9104a 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,6 @@ module Base ( module Data.Function, module Data.Monoid, module Data.List, - module Settings, Stage (..), Arg, Args, ShowArg (..), ShowArgs (..), @@ -23,7 +22,6 @@ import Control.Applicative import Data.Function import Data.Monoid import Data.List -import Settings data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index fa29415..8149619 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -7,9 +7,9 @@ module Oracles.Flag ( test, when, unless, not, (&&), (||) ) where -import Control.Monad hiding (when, unless) import qualified Prelude import Prelude hiding (not, (&&), (||)) +import Control.Monad hiding (when, unless) import Base import Util import Oracles.Base diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 2738b83..40d893e 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -4,6 +4,7 @@ module Package.Base ( module Ways, module Util, module Oracles, + module Settings, Package (..), Settings (..), TodoItem (..), defaultSettings, library, customise, updateSettings, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, @@ -20,6 +21,7 @@ import Base import Ways import Util import Oracles +import Settings import qualified System.Directory as S data Settings = Settings diff --git a/src/Targets.hs b/src/Targets.hs index 19cb664..bdfb2ee 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -5,9 +5,6 @@ module Targets ( import Package.Base -integerLibraryName :: String -integerLibraryName = show integerLibrary - -- These are the packages we build: -- TODO: this should eventually be removed and replaced by the top-level -- target, i.e. GHC (and perhaps, something else) From git at git.haskell.org Thu Oct 26 23:09:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Experiment with parameterised graphs. (8f52904) Message-ID: <20171026230929.591A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f52904d2c05f7503b142fa48eb46eb7945e450c/ghc >--------------------------------------------------------------- commit 8f52904d2c05f7503b142fa48eb46eb7945e450c Author: Andrey Mokhov Date: Mon Feb 9 22:25:52 2015 +0000 Experiment with parameterised graphs. >--------------------------------------------------------------- 8f52904d2c05f7503b142fa48eb46eb7945e450c src/Settings.hs | 94 ++++++++++++++++++++++++++++++++++++++++++++++++++++----- 1 file changed, 87 insertions(+), 7 deletions(-) diff --git a/src/Settings.hs b/src/Settings.hs index 6ffc976..42ceed9 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,18 +1,98 @@ +{-# LANGUAGE FlexibleInstances #-} + module Settings ( - IntegerLibrary (..), integerLibrary, + IntegerLibrary (..), integerLibrary, integerLibraryName, buildHaddock ) where -data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple +import Base +import Ways -instance Show IntegerLibrary where - show library = case library of - IntegerGmp -> "integer-gmp" - IntegerGmp2 -> "integer-gmp2" - IntegerSimple -> "integer-simple" +data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple integerLibrary :: IntegerLibrary integerLibrary = IntegerGmp2 +integerLibraryName :: String +integerLibraryName = case integerLibrary of + IntegerGmp -> "integer-gmp" + IntegerGmp2 -> "integer-gmp2" + IntegerSimple -> "integer-simple" + buildHaddock :: Bool buildHaddock = True + +-- A Parameterised Graph datatype for storing argument lists with conditions +data PG a b = Epsilon + | Vertex a + | Overlay (PG a b) (PG a b) + | Sequence (PG a b) (PG a b) + | Condition b (PG a b) + +instance Monoid (PG a b) where + mempty = Epsilon + mappend = Overlay + +type ArgsExpression = PG String Predicate +type WaysExpression = PG Way Predicate + +data Match = MatchPackage FilePath -- Match a Package name + | MatchFile FilePath -- Match a file + | MatchStage Stage -- Match a Stage + | MatchWay Way -- Match a Way + | MatchKeyValue String String -- Match a key with a value (config) + +-- A Matcher takes a Match description and attempts to evaluate it. +-- Returns Nothing if the attempt fails. +type Matcher = Match -> Maybe Bool + +-- A Monoid instance for matchers (returns first successful match) +instance Monoid Matcher where + mempty = const Nothing + p `mappend` q = \m -> getFirst $ First (p m) <> First (q m) + +data Predicate = Evaluated Bool -- Evaluated predicate + | If Match -- Perform a match to evaluate + | Not Predicate -- Negate predicate + | And Predicate Predicate -- Conjunction of two predicates + | Or Predicate Predicate -- Disjunction of two predicates + +match :: Predicate -> Matcher -> Predicate +match p @ (Evaluated _) _ = p +match p @ (If match ) m = case m match of + Just bool -> Evaluated bool + Nothing -> p +match (Not p ) m = match p m +match (And p q) m = And (match p m) (match q m) +match (Or p q) m = Or (match p m) (match q m) + +-- returns Nothing if the given predicate cannot be uniquely evaluated +evalPredicate :: Predicate -> Maybe Bool +evalPredicate (Evaluated bool) = Just bool +evalPredicate (Not p) = not <$> evalPredicate p +evalPredicate (And p q) + | p' == Just False || q' == Just False = Just False + | p' == Just True && q' == Just True = Just True + | otherwise = Nothing + where + p' = evalPredicate p + q' = evalPredicate q +evalPredicate (Or p q) + | p' == Just True || q' == Just True = Just True + | p' == Just False && q' == Just False = Just False + | otherwise = Nothing + where + p' = evalPredicate p + q' = evalPredicate q +evalPredicate (If _) = Nothing + +-- returns Nothing if the given expression cannot be uniquely evaluated +evalPG :: PG a Predicate -> Maybe [a] +evalPG Epsilon = Just [] +evalPG (Vertex v) = Just [v] +evalPG (Overlay p q) = (++) <$> evalPG p <*> evalPG q +evalPG (Sequence p q) = (++) <$> evalPG p <*> evalPG q +evalPG (Condition x p) = case evalPredicate x of + Just True -> evalPG p + Just False -> Just [] + Nothing -> Nothing From git at git.haskell.org Thu Oct 26 23:09:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement basic infrastructure for parameterised expressions. (a5a8d53) Message-ID: <20171026230932.D8F603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a8d53e5cca5cb6a5609bde961d6f560fbb143f/ghc >--------------------------------------------------------------- commit a5a8d53e5cca5cb6a5609bde961d6f560fbb143f Author: Andrey Mokhov Date: Tue Feb 10 02:44:34 2015 +0000 Implement basic infrastructure for parameterised expressions. >--------------------------------------------------------------- a5a8d53e5cca5cb6a5609bde961d6f560fbb143f src/Base.hs | 2 +- src/Settings.hs | 165 +++++++++++++++++++++++++++++++++++++++++--------------- 2 files changed, 122 insertions(+), 45 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fa9104a..49b0fb2 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,7 +16,7 @@ module Base ( productArgs, concatArgs ) where -import Development.Shake hiding ((*>)) +import Development.Shake hiding ((*>), alternatives) import Development.Shake.FilePath import Control.Applicative import Data.Function diff --git a/src/Settings.hs b/src/Settings.hs index 42ceed9..aaec2ab 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -7,6 +7,7 @@ module Settings ( import Base import Ways +import Oracles.Builder data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple @@ -22,52 +23,45 @@ integerLibraryName = case integerLibrary of buildHaddock :: Bool buildHaddock = True --- A Parameterised Graph datatype for storing argument lists with conditions -data PG a b = Epsilon - | Vertex a - | Overlay (PG a b) (PG a b) - | Sequence (PG a b) (PG a b) - | Condition b (PG a b) +-- A generic Parameterised Graph datatype for parameterised argument lists +data PG p v = Epsilon + | Vertex v + | Overlay (PG p v) (PG p v) + | Sequence (PG p v) (PG p v) + | Condition p (PG p v) -instance Monoid (PG a b) where +instance Monoid (PG p v) where mempty = Epsilon mappend = Overlay -type ArgsExpression = PG String Predicate -type WaysExpression = PG Way Predicate +data Predicate a = Evaluated Bool -- Evaluated predicate + | Parameter a -- To be evaluated later + | Not (Predicate a) -- Negate predicate + | And (Predicate a) (Predicate a) -- Conjunction + | Or (Predicate a) (Predicate a) -- Disjunction -data Match = MatchPackage FilePath -- Match a Package name - | MatchFile FilePath -- Match a file - | MatchStage Stage -- Match a Stage - | MatchWay Way -- Match a Way - | MatchKeyValue String String -- Match a key with a value (config) - --- A Matcher takes a Match description and attempts to evaluate it. +-- Evaluator takes a Parameter and attempts to evaluate it. -- Returns Nothing if the attempt fails. -type Matcher = Match -> Maybe Bool +type Evaluator a = a -> Maybe Bool --- A Monoid instance for matchers (returns first successful match) -instance Monoid Matcher where +-- Monoid instance for evaluators (returns first successful evaluation) +instance Monoid (Evaluator a) where mempty = const Nothing - p `mappend` q = \m -> getFirst $ First (p m) <> First (q m) - -data Predicate = Evaluated Bool -- Evaluated predicate - | If Match -- Perform a match to evaluate - | Not Predicate -- Negate predicate - | And Predicate Predicate -- Conjunction of two predicates - | Or Predicate Predicate -- Disjunction of two predicates + e `mappend` f = \p -> getFirst $ First (e p) <> First (f p) -match :: Predicate -> Matcher -> Predicate -match p @ (Evaluated _) _ = p -match p @ (If match ) m = case m match of +-- Apply an evalulator to a predicate (partial evaluation, or projection) +apply :: Evaluator a -> Predicate a -> Predicate a +apply _ p @ (Evaluated _) = p +apply e p @ (Parameter q) = case e q of Just bool -> Evaluated bool Nothing -> p -match (Not p ) m = match p m -match (And p q) m = And (match p m) (match q m) -match (Or p q) m = Or (match p m) (match q m) +apply e (Not p ) = Not (apply e p) +apply e (And p q) = And (apply e p) (apply e q) +apply e (Or p q) = Or (apply e p) (apply e q) --- returns Nothing if the given predicate cannot be uniquely evaluated -evalPredicate :: Predicate -> Maybe Bool +-- Attempt to evaluate a predicate. Returns Nothing if the predicate +-- cannot be uniquely evaluated due to remaining parameters. +evalPredicate :: Predicate a -> Maybe Bool evalPredicate (Evaluated bool) = Just bool evalPredicate (Not p) = not <$> evalPredicate p evalPredicate (And p q) @@ -84,15 +78,98 @@ evalPredicate (Or p q) where p' = evalPredicate p q' = evalPredicate q -evalPredicate (If _) = Nothing - --- returns Nothing if the given expression cannot be uniquely evaluated -evalPG :: PG a Predicate -> Maybe [a] -evalPG Epsilon = Just [] -evalPG (Vertex v) = Just [v] -evalPG (Overlay p q) = (++) <$> evalPG p <*> evalPG q -evalPG (Sequence p q) = (++) <$> evalPG p <*> evalPG q -evalPG (Condition x p) = case evalPredicate x of - Just True -> evalPG p +evalPredicate (Parameter _) = Nothing -- cannot evaluate Parameter + +-- Flatten a PG into a list. Returns Nothing if the given expression +-- cannot be uniquely evaluated due to remaining parameters. +linearise :: PG (Predicate a) v -> Maybe [v] +linearise Epsilon = Just [] +linearise (Vertex v) = Just [v] +linearise (Overlay p q) = (++) <$> linearise p <*> linearise q +linearise (Sequence p q) = (++) <$> linearise p <*> linearise q +linearise (Condition x p) = case evalPredicate x of + Just True -> linearise p Just False -> Just [] Nothing -> Nothing + +(~>) :: PG p v -> PG p v -> PG p v +a ~> b = Sequence a b + +type PGP p v = PG (Predicate p) v + +disjuction :: [a] -> (a -> Predicate p) -> PGP p v -> PGP p v +disjuction [] _ = id +disjuction (a:as) convert = Condition (foldr Or (convert a) $ map convert as) + +-- GHC build specific + +data BuildParameter = WhenPackage FilePath + | WhenBuilder Builder + | WhenStage Stage + | WhenWay Way + | WhenFile FilePath + | WhenKeyValue String String -- from config files + +type Expression a = PGP BuildParameter a + +type Rewrite a = Expression a -> Expression a + +type ArgsExpression = Expression String + +alternatives :: (b -> BuildParameter) -> [b] -> Rewrite a +alternatives p bs = disjuction bs (Parameter . p) + +whenPackages :: [FilePath] -> Rewrite a +whenPackages = alternatives WhenPackage + +whenBuilders :: [Builder] -> Rewrite a +whenBuilders = alternatives WhenBuilder + +whenStages :: [Stage] -> Rewrite a +whenStages = alternatives WhenStage + +unlessStage :: Stage -> Rewrite a +unlessStage stage = Condition (Not $ Parameter $ WhenStage stage) + +whenWays :: [Way] -> Rewrite a +whenWays = alternatives WhenWay + +whenFiles :: [FilePath] -> Rewrite a +whenFiles = alternatives WhenFile + +whenKeyValues :: String -> [String] -> Rewrite a +whenKeyValues key = alternatives (WhenKeyValue key) + +whenKeyValue :: String -> String -> Rewrite a +whenKeyValue key value = whenKeyValues key [value] + +whenPackageKey :: Rewrite a +whenPackageKey = whenKeyValue "supports-package-key" "YES" . unlessStage Stage0 + +--packageArgs = +-- Vertex "-hide-all-packages" +-- ~> +-- Vertex "-no-user-package-db" +-- ~> +-- Vertex "-include-pkg-deps" +-- ~> If (MatchStage Stage0) +-- (Vertex "-package-db libraries/bootstrapping.conf") +-- ~> If usePackageKey +-- ( + +-- ) + +--packageArgs :: Stage -> FilePath -> Args +--packageArgs stage pathDist = do +-- usePackageKey <- SupportsPackageKey || stage /= Stage0 +-- args [ arg "-hide-all-packages" +-- , arg "-no-user-package-db" +-- , arg "-include-pkg-deps" +-- , when (stage == Stage0) $ +-- arg "-package-db libraries/bootstrapping.conf" +-- , if usePackageKey +-- then productArgs ["-this-package-key"] [arg $ PackageKey pathDist] +-- <> productArgs ["-package-key" ] [args $ DepKeys pathDist] +-- else productArgs ["-package-name" ] [arg $ PackageKey pathDist] +-- <> productArgs ["-package" ] [args $ Deps pathDist] +-- ] From git at git.haskell.org Thu Oct 26 23:09:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Eq instances. (27bc02e) Message-ID: <20171026230936.4CC6F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27bc02eb27cefd49c0292a6190b269c5dd2bb4b7/ghc >--------------------------------------------------------------- commit 27bc02eb27cefd49c0292a6190b269c5dd2bb4b7 Author: Andrey Mokhov Date: Wed Feb 11 03:22:35 2015 +0000 Add Eq instances. >--------------------------------------------------------------- 27bc02eb27cefd49c0292a6190b269c5dd2bb4b7 src/Oracles/Builder.hs | 2 +- src/Package/Base.hs | 5 +++-- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 07b1bbd..d538611 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -29,7 +29,7 @@ data Builder = Ar | Gcc Stage | Ghc Stage | GhcPkg Stage - deriving Show + deriving (Show, Eq) instance ShowArg Builder where showArg builder = toStandard <$> do diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 40d893e..e3c38e7 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -4,7 +4,6 @@ module Package.Base ( module Ways, module Util, module Oracles, - module Settings, Package (..), Settings (..), TodoItem (..), defaultSettings, library, customise, updateSettings, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, @@ -21,7 +20,6 @@ import Base import Ways import Util import Oracles -import Settings import qualified System.Directory as S data Settings = Settings @@ -72,6 +70,9 @@ data Package = Package pkgTodo :: [TodoItem] -- [(Stage1, "dist-install", defaultSettings)] } +instance Eq Package where + (==) = (==) `on` pkgName + updateSettings :: (Settings -> Settings) -> Package -> Package updateSettings update (Package name path cabal todo) = Package name path cabal (map updateTodo todo) From git at git.haskell.org Thu Oct 26 23:09:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement predicates and evaluators. (71be3a8) Message-ID: <20171026230939.B7DEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/71be3a823ae81fde9371e93cd9efa9ffbb9a6cea/ghc >--------------------------------------------------------------- commit 71be3a823ae81fde9371e93cd9efa9ffbb9a6cea Author: Andrey Mokhov Date: Wed Feb 11 03:23:27 2015 +0000 Implement predicates and evaluators. >--------------------------------------------------------------- 71be3a823ae81fde9371e93cd9efa9ffbb9a6cea src/Settings.hs | 114 ++++++++++++++++++++++++++++++++++++++++++++------------ src/Targets.hs | 1 + 2 files changed, 92 insertions(+), 23 deletions(-) diff --git a/src/Settings.hs b/src/Settings.hs index aaec2ab..6d25a92 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -7,6 +7,7 @@ module Settings ( import Base import Ways +import Package.Base (Package) import Oracles.Builder data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple @@ -34,23 +35,36 @@ instance Monoid (PG p v) where mempty = Epsilon mappend = Overlay +fromList :: [v] -> PG p v +fromList = foldr Sequence Epsilon . map Vertex + +type RewritePG p v = PG p v -> PG p v + data Predicate a = Evaluated Bool -- Evaluated predicate | Parameter a -- To be evaluated later | Not (Predicate a) -- Negate predicate | And (Predicate a) (Predicate a) -- Conjunction | Or (Predicate a) (Predicate a) -- Disjunction --- Evaluator takes a Parameter and attempts to evaluate it. +multiOr :: [Predicate a] -> RewritePG (Predicate a) v +multiOr = Condition . foldr Or (Evaluated False) + +multiAnd :: [Predicate a] -> RewritePG (Predicate a) v +multiAnd = Condition . foldr And (Evaluated True) + +type RewrtePredicate a = Predicate a -> Predicate a + +-- Evaluator takes an argument and attempts to determine its truth. -- Returns Nothing if the attempt fails. type Evaluator a = a -> Maybe Bool -- Monoid instance for evaluators (returns first successful evaluation) instance Monoid (Evaluator a) where mempty = const Nothing - e `mappend` f = \p -> getFirst $ First (e p) <> First (f p) + p `mappend` q = \a -> getFirst $ First (p a) <> First (q a) --- Apply an evalulator to a predicate (partial evaluation, or projection) -apply :: Evaluator a -> Predicate a -> Predicate a +-- Apply an evalulator to a predicate (partial evaluation, or 'projection'). +apply :: Evaluator a -> RewrtePredicate a apply _ p @ (Evaluated _) = p apply e p @ (Parameter q) = case e q of Just bool -> Evaluated bool @@ -59,8 +73,20 @@ apply e (Not p ) = Not (apply e p) apply e (And p q) = And (apply e p) (apply e q) apply e (Or p q) = Or (apply e p) (apply e q) +-- Map over all PG predicates, e.g., apply an evaluator to a given PG. +mapP :: RewrtePredicate a -> RewritePG (Predicate a) v +mapP _ Epsilon = Epsilon +mapP _ v @ (Vertex _) = v +mapP r (Overlay p q) = Overlay (mapP r p) (mapP r q) +mapP r (Sequence p q) = Sequence (mapP r p) (mapP r q) +mapP r (Condition x p) = Condition (r x) (mapP r p) + +project :: Evaluator a -> RewritePG (Predicate a) v +project = mapP . apply + -- Attempt to evaluate a predicate. Returns Nothing if the predicate -- cannot be uniquely evaluated due to remaining parameters. +-- An alternative type: evalPredicate :: Evaluator (Predicate a) evalPredicate :: Predicate a -> Maybe Bool evalPredicate (Evaluated bool) = Just bool evalPredicate (Not p) = not <$> evalPredicate p @@ -80,46 +106,42 @@ evalPredicate (Or p q) q' = evalPredicate q evalPredicate (Parameter _) = Nothing -- cannot evaluate Parameter --- Flatten a PG into a list. Returns Nothing if the given expression +-- Linearise a PG into a list. Returns Nothing if the given expression -- cannot be uniquely evaluated due to remaining parameters. linearise :: PG (Predicate a) v -> Maybe [v] linearise Epsilon = Just [] linearise (Vertex v) = Just [v] -linearise (Overlay p q) = (++) <$> linearise p <*> linearise q +linearise (Overlay p q) = (++) <$> linearise p <*> linearise q -- TODO: union linearise (Sequence p q) = (++) <$> linearise p <*> linearise q linearise (Condition x p) = case evalPredicate x of Just True -> linearise p Just False -> Just [] Nothing -> Nothing -(~>) :: PG p v -> PG p v -> PG p v -a ~> b = Sequence a b +-- GHC build specific -type PGP p v = PG (Predicate p) v +type Expression a = PG (Predicate BuildParameter) a +type Rewrite a = Expression a -> Expression a -disjuction :: [a] -> (a -> Predicate p) -> PGP p v -> PGP p v -disjuction [] _ = id -disjuction (a:as) convert = Condition (foldr Or (convert a) $ map convert as) +--type ArgsExpression = Expression String +--type Args = Expression String --- GHC build specific +--args :: [String] -> Args +--args = fromList -data BuildParameter = WhenPackage FilePath +data BuildParameter = WhenPackage Package | WhenBuilder Builder | WhenStage Stage | WhenWay Way - | WhenFile FilePath + | WhenFile FilePattern | WhenKeyValue String String -- from config files -type Expression a = PGP BuildParameter a - -type Rewrite a = Expression a -> Expression a - -type ArgsExpression = Expression String +-- Predicates alternatives :: (b -> BuildParameter) -> [b] -> Rewrite a -alternatives p bs = disjuction bs (Parameter . p) +alternatives p = multiOr . map (Parameter . p) -whenPackages :: [FilePath] -> Rewrite a +whenPackages :: [Package] -> Rewrite a whenPackages = alternatives WhenPackage whenBuilders :: [Builder] -> Rewrite a @@ -134,7 +156,7 @@ unlessStage stage = Condition (Not $ Parameter $ WhenStage stage) whenWays :: [Way] -> Rewrite a whenWays = alternatives WhenWay -whenFiles :: [FilePath] -> Rewrite a +whenFiles :: [FilePattern] -> Rewrite a whenFiles = alternatives WhenFile whenKeyValues :: String -> [String] -> Rewrite a @@ -143,6 +165,52 @@ whenKeyValues key = alternatives (WhenKeyValue key) whenKeyValue :: String -> String -> Rewrite a whenKeyValue key value = whenKeyValues key [value] +-- Evaluators + +packageEvaluator :: Package -> Evaluator BuildParameter +packageEvaluator p (WhenPackage p') = Just $ p == p' +packageEvaluator _ _ = Nothing + +builderEvaluator :: Builder -> Evaluator BuildParameter +builderEvaluator b (WhenBuilder b') = Just $ b == b' +builderEvaluator _ _ = Nothing + +stageEvaluator :: Stage -> Evaluator BuildParameter +stageEvaluator s (WhenStage s') = Just $ s == s' +stageEvaluator _ _ = Nothing + +wayEvaluator :: Way -> Evaluator BuildParameter +wayEvaluator w (WhenWay w') = Just $ w == w' +wayEvaluator _ _ = Nothing + +fileEvaluator :: FilePath -> Evaluator BuildParameter +fileEvaluator file (WhenFile pattern) = Just $ pattern ?== file +fileEvaluator _ _ = Nothing + +keyValueEvaluator :: String -> String -> Evaluator BuildParameter +keyValueEvaluator key value (WhenKeyValue key' value') + | key == key' = Just $ value == value' + | otherwise = Nothing +keyValueEvaluator _ _ _ = Nothing + +setPackage :: Package -> Rewrite a +setPackage = project . packageEvaluator + +setBuilder :: Builder -> Rewrite a +setBuilder = project . builderEvaluator + +setStage :: Stage -> Rewrite a +setStage = project . stageEvaluator + +setWay :: Way -> Rewrite a +setWay = project . wayEvaluator + +setFile :: FilePath -> Rewrite a +setFile = project . fileEvaluator + +setKeyValue :: String -> String -> Rewrite a +setKeyValue key = project . keyValueEvaluator key + whenPackageKey :: Rewrite a whenPackageKey = whenKeyValue "supports-package-key" "YES" . unlessStage Stage0 diff --git a/src/Targets.hs b/src/Targets.hs index bdfb2ee..bc50ed9 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -4,6 +4,7 @@ module Targets ( ) where import Package.Base +import Settings -- These are the packages we build: -- TODO: this should eventually be removed and replaced by the top-level From git at git.haskell.org Thu Oct 26 23:09:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor argument expressions. (93e218e) Message-ID: <20171026230943.2650F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/93e218e59d6f0e03ffdcfc691c19548a2e697135/ghc >--------------------------------------------------------------- commit 93e218e59d6f0e03ffdcfc691c19548a2e697135 Author: Andrey Mokhov Date: Wed Apr 8 02:34:02 2015 +0100 Refactor argument expressions. >--------------------------------------------------------------- 93e218e59d6f0e03ffdcfc691c19548a2e697135 src/Expression.hs | 159 ++++++++++++++++++++++++++++++ src/Expression/ArgList.hs | 32 ++++++ src/Expression/PG.hs | 56 +++++++++++ src/Expression/Predicate.hs | 55 +++++++++++ src/Expression/TruthTeller.hs | 16 +++ src/Settings.hs | 220 +++--------------------------------------- 6 files changed, 333 insertions(+), 205 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 93e218e59d6f0e03ffdcfc691c19548a2e697135 From git at git.haskell.org Thu Oct 26 23:09:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename src/Expression.hs -> src/Expression/Base.hs. (35cab30) Message-ID: <20171026230946.80A7D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/35cab3032cf80af4274dfd6563a821bcc34e4618/ghc >--------------------------------------------------------------- commit 35cab3032cf80af4274dfd6563a821bcc34e4618 Author: Andrey Mokhov Date: Wed Apr 8 23:04:19 2015 +0100 Rename src/Expression.hs -> src/Expression/Base.hs. >--------------------------------------------------------------- 35cab3032cf80af4274dfd6563a821bcc34e4618 src/{Expression.hs => Expression/Base.hs} | 0 src/Settings.hs | 5 ++++- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Expression.hs b/src/Expression/Base.hs similarity index 100% rename from src/Expression.hs rename to src/Expression/Base.hs diff --git a/src/Settings.hs b/src/Settings.hs index 2885282..e70e41c 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -22,8 +22,11 @@ integerLibraryName = case integerLibrary of buildHaddock :: Bool buildHaddock = True +supportsPackageKey :: Guard +supportsPackageKey = keyYes "supports-package-key" + whenPackageKey :: Guard -whenPackageKey = keyYes "supports-package-key" <> notStage Stage0 +whenPackageKey = supportsPackageKey <> notStage Stage0 depSettings :: Settings depSettings = From git at git.haskell.org Thu Oct 26 23:09:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Begin translating the code using expressions. (d7cd023) Message-ID: <20171026230949.E7E8D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d7cd023a4cc538bcde70d1872af41e4eafc77248/ghc >--------------------------------------------------------------- commit d7cd023a4cc538bcde70d1872af41e4eafc77248 Author: Andrey Mokhov Date: Thu Apr 9 02:50:25 2015 +0100 Begin translating the code using expressions. >--------------------------------------------------------------- d7cd023a4cc538bcde70d1872af41e4eafc77248 src/Expression/PGPredicate.hs | 62 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 62 insertions(+) diff --git a/src/Expression/PGPredicate.hs b/src/Expression/PGPredicate.hs new file mode 100644 index 0000000..45bb97f --- /dev/null +++ b/src/Expression/PGPredicate.hs @@ -0,0 +1,62 @@ +{-# LANGUAGE FlexibleInstances #-} + +module Expression.PGPredicate ( + module Expression.PG, + module Expression.Predicate, + PGPredicate (..), + fence, (?), ite, + whenExists, + remove, + project, + linearise + ) where + +import Control.Applicative +import Expression.PG +import Expression.Predicate + +type PGPredicate p v = PG (Predicate p) v + +fence :: PGPredicate p v -> PGPredicate p v -> PGPredicate p v +fence = Sequence + +(?) :: Predicate p -> PGPredicate p v -> PGPredicate p v +(?) = Condition + +ite :: Predicate p -> PGPredicate p v -> PGPredicate p v -> PGPredicate p v +ite p t f = Overlay (p ? t) (Not p ? f) + +infixl 7 ? + +whenExists :: Eq v => v -> PGPredicate p v -> Predicate p +whenExists _ Epsilon = Evaluated False +whenExists a (Vertex b) = Evaluated $ a == b +whenExists a (Overlay l r) = Or (whenExists a l) (whenExists a r) +whenExists a (Sequence l r) = Or (whenExists a l) (whenExists a r) +whenExists a (Condition x r) = And x (whenExists a r) + +remove :: Eq v => v -> PGPredicate p v -> PGPredicate p v +remove _ Epsilon = Epsilon +remove a v @ (Vertex b) + | a == b = Epsilon + | otherwise = v +remove a (Overlay l r) = Overlay (remove a l) (remove a r) +remove a (Sequence l r) = Sequence (remove a l) (remove a r) +remove a (Condition x r) = Condition x (remove a r) + +-- Partially evaluate a PG using a truth-teller (compute a 'projection') +project :: TruthTeller p -> PGPredicate p v -> PGPredicate p v +project t = mapP (evaluate t) + +-- Linearise a PG into a list. Returns Nothing if the given expression +-- cannot be uniquely evaluated due to remaining parameters. +-- Overlay subexpressions are evaluated in arbitrary order. +linearise :: PGPredicate p v -> Maybe [v] +linearise Epsilon = Just [] +linearise (Vertex v) = Just [v] +linearise (Overlay l r) = (++) <$> linearise l <*> linearise r -- TODO: union +linearise (Sequence l r) = (++) <$> linearise l <*> linearise r +linearise (Condition x r) = case tellTruth x of + Just True -> linearise r + Just False -> Just [] + Nothing -> Nothing From git at git.haskell.org Thu Oct 26 23:09:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish translation of Data.hs argument lists. (8cf38ba) Message-ID: <20171026230953.614D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8cf38baf8224a14a2fc167bfc0776123d1bd1167/ghc >--------------------------------------------------------------- commit 8cf38baf8224a14a2fc167bfc0776123d1bd1167 Author: Andrey Mokhov Date: Fri Apr 10 02:05:27 2015 +0100 Finish translation of Data.hs argument lists. >--------------------------------------------------------------- 8cf38baf8224a14a2fc167bfc0776123d1bd1167 src/Expression/ArgList.hs | 7 +- src/Expression/Base.hs | 190 ++++++++++++++++++++++++++++++++++++------ src/Expression/PG.hs | 41 ++------- src/Expression/PGPredicate.hs | 18 +--- src/Oracles/Builder.hs | 1 + src/Settings.hs | 129 ++++++++++++++++++++++------ src/Targets.hs | 148 ++++++++++++++++---------------- 7 files changed, 363 insertions(+), 171 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 8cf38baf8224a14a2fc167bfc0776123d1bd1167 From git at git.haskell.org Thu Oct 26 23:09:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:09:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (08136dd) Message-ID: <20171026230956.D8B463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/08136ddd1386ec9b7a4b79779d51f388606fce0b/ghc >--------------------------------------------------------------- commit 08136ddd1386ec9b7a4b79779d51f388606fce0b Author: Andrey Mokhov Date: Sun Apr 12 02:13:23 2015 +0100 Clean up. >--------------------------------------------------------------- 08136ddd1386ec9b7a4b79779d51f388606fce0b src/Expression/ArgList.hs | 37 ---- src/Expression/{Base.hs => Args.hs} | 12 -- src/Expression/Base.hs | 345 ++++++++++-------------------------- src/Expression/Build.hs | 238 +++++++++++++++++++++++++ src/Expression/PG.hs | 31 ++-- src/Expression/PGPredicate.hs | 46 ----- src/Expression/Predicate.hs | 68 ++----- src/Expression/TruthTeller.hs | 16 -- src/Settings.hs | 116 ++++++------ src/Targets.hs | 3 +- 10 files changed, 433 insertions(+), 479 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 08136ddd1386ec9b7a4b79779d51f388606fce0b From git at git.haskell.org Thu Oct 26 23:10:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove old file src/Expression/Args.hs. (21b789e) Message-ID: <20171026231000.617293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21b789ea7729715fe7252099808b062271793e40/ghc >--------------------------------------------------------------- commit 21b789ea7729715fe7252099808b062271793e40 Author: Andrey Mokhov Date: Sun Apr 12 02:14:52 2015 +0100 Remove old file src/Expression/Args.hs. >--------------------------------------------------------------- 21b789ea7729715fe7252099808b062271793e40 src/Expression/Args.hs | 289 ------------------------------------------------- 1 file changed, 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 21b789ea7729715fe7252099808b062271793e40 From git at git.haskell.org Thu Oct 26 23:10:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Continue major refactoring for expression-based build system. (cb2003c) Message-ID: <20171026231004.07DC73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb2003ce5221cf043f77eeb0690d6d8b6bc19dea/ghc >--------------------------------------------------------------- commit cb2003ce5221cf043f77eeb0690d6d8b6bc19dea Author: Andrey Mokhov Date: Wed Apr 15 03:24:09 2015 +0100 Continue major refactoring for expression-based build system. >--------------------------------------------------------------- cb2003ce5221cf043f77eeb0690d6d8b6bc19dea src/Expression/Base.hs | 146 +++++++++++++++++++++--------------- src/Expression/Build.hs | 34 ++++----- src/Expression/PG.hs | 49 +++++++++++- src/Main.hs | 3 +- src/Package.hs | 58 ++++++--------- src/Package/Base.hs | 170 ++++++++++-------------------------------- src/PackageBuild.hs | 67 +++++++++++++++++ src/Settings.hs | 101 ++++++++++++------------- src/Targets.hs | 193 +++++++++++++++++++++++------------------------- 9 files changed, 420 insertions(+), 401 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 cb2003ce5221cf043f77eeb0690d6d8b6bc19dea From git at git.haskell.org Thu Oct 26 23:10:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish Args datatype, propagate changes to related modules. (79ad8ee) Message-ID: <20171026231007.7ADCB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79ad8ee4e0830da7125d6975c6f13790d97f2439/ghc >--------------------------------------------------------------- commit 79ad8ee4e0830da7125d6975c6f13790d97f2439 Author: Andrey Mokhov Date: Thu Apr 16 02:08:59 2015 +0100 Finish Args datatype, propagate changes to related modules. >--------------------------------------------------------------- 79ad8ee4e0830da7125d6975c6f13790d97f2439 src/Expression/Base.hs | 52 ++++++++++++++++++++------- src/Expression/Build.hs | 2 +- src/Main.hs | 1 + src/Settings.hs | 94 ++++++++++++++++++++++++++----------------------- src/Targets.hs | 22 ++++++------ 5 files changed, 102 insertions(+), 69 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 79ad8ee4e0830da7125d6975c6f13790d97f2439 From git at git.haskell.org Thu Oct 26 23:10:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Simplify instances for PG and Predicate. (0fe624f) Message-ID: <20171026231010.EA12E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0fe624fbec4b1eee99bc2e056f662568da0ffa91/ghc >--------------------------------------------------------------- commit 0fe624fbec4b1eee99bc2e056f662568da0ffa91 Author: Andrey Mokhov Date: Fri Apr 17 01:29:08 2015 +0100 Add Simplify instances for PG and Predicate. >--------------------------------------------------------------- 0fe624fbec4b1eee99bc2e056f662568da0ffa91 src/Expression/Base.hs | 14 +++++++--- src/Expression/Build.hs | 63 ++++++++++++++++++++++++++++++------------- src/Expression/PG.hs | 48 ++++++++++++++++++++++++++++++++- src/Expression/Simplify.hs | 6 +++++ src/Main.hs | 6 +++++ src/Package.hs | 3 +++ src/Settings.hs | 67 ++++++++++++++++++++++------------------------ src/Ways.hs | 3 +++ 8 files changed, 152 insertions(+), 58 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 0fe624fbec4b1eee99bc2e056f662568da0ffa91 From git at git.haskell.org Thu Oct 26 23:10:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Work on the top-level build structure. (8bdc64c) Message-ID: <20171026231017.CF2EF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8bdc64ccbf49838c6a90635cb45683bcc609a4b3/ghc >--------------------------------------------------------------- commit 8bdc64ccbf49838c6a90635cb45683bcc609a4b3 Author: Andrey Mokhov Date: Sat Apr 18 01:42:25 2015 +0100 Work on the top-level build structure. >--------------------------------------------------------------- 8bdc64ccbf49838c6a90635cb45683bcc609a4b3 src/Expression/Base.hs | 31 +++++++++---- src/Expression/Resolve.hs | 110 ++++++++++++++++++++++++++++++++-------------- src/Main.hs | 37 ++++++++++------ src/Targets.hs | 2 +- src/Ways.hs | 2 +- 5 files changed, 127 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 8bdc64ccbf49838c6a90635cb45683bcc609a4b3 From git at git.haskell.org Thu Oct 26 23:10:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a draft implementation for resolution of Config variables. (489e385) Message-ID: <20171026231014.62F1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/489e385ab98b0ce8ec0b9ab8248b9bc9adb1f38b/ghc >--------------------------------------------------------------- commit 489e385ab98b0ce8ec0b9ab8248b9bc9adb1f38b Author: Andrey Mokhov Date: Fri Apr 17 22:49:20 2015 +0100 Add a draft implementation for resolution of Config variables. >--------------------------------------------------------------- 489e385ab98b0ce8ec0b9ab8248b9bc9adb1f38b src/Expression/Base.hs | 24 +++++++++---------- src/Expression/Build.hs | 2 +- src/Expression/Resolve.hs | 60 +++++++++++++++++++++++++++++++++++++++++++++++ src/Main.hs | 40 +++++++++++++++++++++++++++++-- src/Targets.hs | 2 +- 5 files changed, 112 insertions(+), 16 deletions(-) diff --git a/src/Expression/Base.hs b/src/Expression/Base.hs index e9316e8..ef6ad72 100644 --- a/src/Expression/Base.hs +++ b/src/Expression/Base.hs @@ -118,7 +118,6 @@ argWithStagedBuilder :: (Stage -> Builder) -> Settings argWithStagedBuilder f = msum $ map (\s -> stage s ? argWithBuilder (f s)) [Stage0 ..] - -- Accessing key value pairs from package-data.mk files argPackageKey :: Settings argPackageKey = return $ PackageData "PACKAGE_KEY" @@ -165,35 +164,36 @@ argPrefix prefix = fmap (Fold Concat . (arg prefix |>) . return) argPrefixPath :: String -> Settings -> Settings argPrefixPath prefix = fmap (Fold ConcatPath . (arg prefix |>) . return) --- Partially evaluate Settings using a truth-teller (compute a 'projection') -project :: (BuildVariable -> Maybe Bool) -> Settings -> Settings +-- Partially evaluate expression using a truth-teller (compute a 'projection') +project :: (BuildVariable -> Maybe Bool) -> BuildExpression v + -> BuildExpression v project _ Epsilon = Epsilon project t (Vertex v) = Vertex v -- TODO: go deeper project t (Overlay l r) = Overlay (project t l) (project t r) project t (Sequence l r) = Sequence (project t l) (project t r) project t (Condition l r) = Condition (evaluate t l) (project t r) --- Partial evaluation of settings - -setPackage :: Package -> Settings -> Settings +-- Partial evaluation of setting +setPackage :: Package -> BuildExpression v -> BuildExpression v setPackage = project . matchPackage -setBuilder :: Builder -> Settings -> Settings +setBuilder :: Builder -> BuildExpression v -> BuildExpression v setBuilder = project . matchBuilder -setBuilderFamily :: (Stage -> Builder) -> Settings -> Settings +setBuilderFamily :: (Stage -> Builder) -> BuildExpression v + -> BuildExpression v setBuilderFamily = project . matchBuilderFamily -setStage :: Stage -> Settings -> Settings +setStage :: Stage -> BuildExpression v -> BuildExpression v setStage = project . matchStage -setWay :: Way -> Settings -> Settings +setWay :: Way -> BuildExpression v -> BuildExpression v setWay = project . matchWay -setFile :: FilePath -> Settings -> Settings +setFile :: FilePath -> BuildExpression v -> BuildExpression v setFile = project . matchFile -setConfig :: String -> String -> Settings -> Settings +setConfig :: String -> String -> BuildExpression v -> BuildExpression v setConfig key = project . matchConfig key --type ArgsTeller = Args -> Maybe [String] diff --git a/src/Expression/Build.hs b/src/Expression/Build.hs index 19ff60e..8a7372d 100644 --- a/src/Expression/Build.hs +++ b/src/Expression/Build.hs @@ -21,8 +21,8 @@ module Expression.Build ( import Control.Applicative import Base import Ways -import Package (Package) import Oracles.Builder +import Package (Package) import Expression.PG -- Build variables that can be used in build predicates diff --git a/src/Expression/Resolve.hs b/src/Expression/Resolve.hs new file mode 100644 index 0000000..4ce4f7b --- /dev/null +++ b/src/Expression/Resolve.hs @@ -0,0 +1,60 @@ +{-# LANGUAGE FlexibleInstances #-} + +module Expression.Resolve ( + ResolveConfig (..) + ) where + +import Base +import Oracles.Base +import Expression.PG +import Expression.Predicate +import Expression.Base +import Expression.Build + +-- Resolve configuration variables +class ResolveConfig a where + resolveConfig :: a -> Action a + -- resolveConfig = return . id + +instance ResolveConfig BuildPredicate where + resolveConfig p @ (Evaluated _) = return p + + resolveConfig (Unevaluated (ConfigVariable key value)) = do + lookup <- askConfig key + return $ Evaluated $ lookup == value + + resolveConfig p @ (Unevaluated _) = return p + + resolveConfig (Not p) = do + p' <- resolveConfig p + return $ Not p' + + resolveConfig (And p q) = do + p' <- resolveConfig p + q' <- resolveConfig q + return $ And p' q' + + resolveConfig (Or p q) = do + p' <- resolveConfig p + q' <- resolveConfig q + return $ Or p' q' + +instance ResolveConfig (BuildExpression v) where + resolveConfig Epsilon = return Epsilon + + resolveConfig v @ (Vertex _) = return v -- TODO: go deeper + + resolveConfig (Overlay l r) = do + l' <- resolveConfig l + r' <- resolveConfig r + return $ Overlay l' r' + + resolveConfig (Sequence l r) = do + l' <- resolveConfig l + r' <- resolveConfig r + return $ Sequence l' r' + + resolveConfig (Condition l r) = do + l' <- resolveConfig l + r' <- resolveConfig r + return $ Condition l' r' diff --git a/src/Main.hs b/src/Main.hs index 4b6349a..bf0e8f7 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -4,7 +4,9 @@ import Oracles import Package import Targets import Settings +import Expression.Base import Expression.Simplify +import Expression.Resolve main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do oracleRules @@ -13,6 +15,40 @@ main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do --packageRules action $ do - putNormal $ "targetPackages = " ++ show (simplify targetPackages) - putNormal $ "\ntargetWays = " ++ show (simplify targetWays) + putNormal $ "\ntargetPackages = " ++ show (simplify targetPackages) + putNormal $ "\n\ntargetWays = " ++ show (simplify targetWays) + putNormal $ "\n\n=============================\n" + -- Read config file + targetPackages' <- resolveConfig targetPackages + targetWays' <- resolveConfig targetWays + + -- Build stages + forM_ [Stage0 ..] $ \stage -> do + putNormal $ "Stage = " ++ show stage + let packages = setStage stage targetPackages' + ways = setStage stage targetWays' + putNormal $ "\n packages = " ++ show (simplify packages) + putNormal $ "\n ways = " ++ show (simplify ways) + + --forM_ targetPackages $ \pkg @ (Package name path _ todo) -> do + -- forM_ todo $ \todoItem @ (stage, dist, settings) -> do + + -- -- Want top .o and .a files for the pkg/todo combo + -- -- We build *only one* vanilla .o file (not sure why) + -- -- We build .way_a file for each way (or its dynamic version). + -- -- TODO: Check BUILD_GHCI_LIB flag to decide if .o is needed + -- -- TODO: move this into a separate file (perhaps, to Targets.hs?) + -- action $ when (buildWhen settings) $ do + -- let pathDist = path dist + -- buildDir = pathDist "build" + -- key <- showArg (PackageKey pathDist) + -- let oFile = buildDir "Hs" ++ key <.> "o" + -- ways' <- ways settings + -- libFiles <- forM ways' $ \way -> do + -- extension <- libsuf way + -- return $ buildDir "libHs" ++ key <.> extension + -- need $ [oFile] ++ libFiles + + -- -- Build rules for the package + -- buildPackage pkg todoItem diff --git a/src/Targets.hs b/src/Targets.hs index 1b7bba2..bc2756a 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -26,7 +26,7 @@ targetPackages = msum packagesStage0 :: Packages packagesStage0 = msum [ fromList [ binPackageDb, binary, cabal, hoopl, hpc, transformers ] - , windowsHost && not (targetOs "ios") ? return terminfo ] + , not windowsHost && not (targetOs "ios") ? return terminfo ] packagesStage1 :: Packages packagesStage1 = msum From git at git.haskell.org Thu Oct 26 23:10:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement buildPackageData rule. (4ad4d41) Message-ID: <20171026231021.5C9913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f/ghc >--------------------------------------------------------------- commit 4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f Author: Andrey Mokhov Date: Mon Apr 20 01:25:09 2015 +0100 Implement buildPackageData rule. >--------------------------------------------------------------- 4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f src/Base.hs | 4 + src/Expression/Args.hs | 179 +++++++++++++++++++++++++++++++++++ src/Expression/Base.hs | 228 +++------------------------------------------ src/Expression/Build.hs | 174 +++------------------------------- src/Expression/PG.hs | 61 +++++------- src/Expression/Project.hs | 133 ++++++++++++++++++++++++++ src/Expression/Resolve.hs | 75 +++++++++------ src/Expression/Simplify.hs | 119 ++++++++++++++++++++++- src/Main.hs | 65 ++----------- src/Oracles/Builder.hs | 61 ++++++------ src/Oracles/PackageData.hs | 11 ++- src/Package.hs | 7 +- src/PackageBuild.hs | 67 ------------- src/Rules.hs | 41 ++++++++ src/Rules/Data.hs | 184 ++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 11 +++ src/Settings.hs | 116 ++--------------------- src/Switches.hs | 78 ++++++++++++++++ src/Targets.hs | 55 +++++------ 19 files changed, 933 insertions(+), 736 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 4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f From git at git.haskell.org Thu Oct 26 23:10:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up Expression package. (51028b8) Message-ID: <20171026231024.C22DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/51028b8d25146dde9cc45d92912acb498388c9d7/ghc >--------------------------------------------------------------- commit 51028b8d25146dde9cc45d92912acb498388c9d7 Author: Andrey Mokhov Date: Sat Apr 25 00:50:55 2015 +0100 Clean up Expression package. >--------------------------------------------------------------- 51028b8d25146dde9cc45d92912acb498388c9d7 src/Expression/Base.hs | 16 ++--- src/Expression/Build.hs | 121 -------------------------------- src/Expression/BuildExpression.hs | 21 ++++++ src/Expression/BuildPredicate.hs | 51 ++++++++++++++ src/Expression/{Args.hs => Derived.hs} | 123 ++++++++++++++++++++------------- src/Expression/Project.hs | 10 +-- src/Expression/Resolve.hs | 6 +- src/Expression/Settings.hs | 55 +++++++++++++++ src/Expression/Simplify.hs | 5 +- src/Targets.hs | 1 - 10 files changed, 222 insertions(+), 187 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 51028b8d25146dde9cc45d92912acb498388c9d7 From git at git.haskell.org Thu Oct 26 23:10:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make PG and BuildPredicate abstract. (353b02b) Message-ID: <20171026231028.26CF43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/353b02bdb3999067523c30436c8a4c3dcbc2b770/ghc >--------------------------------------------------------------- commit 353b02bdb3999067523c30436c8a4c3dcbc2b770 Author: Andrey Mokhov Date: Mon Apr 27 02:36:01 2015 +0100 Make PG and BuildPredicate abstract. >--------------------------------------------------------------- 353b02bdb3999067523c30436c8a4c3dcbc2b770 src/Expression/BuildExpression.hs | 34 ++++++++++++ src/Expression/BuildPredicate.hs | 64 +++++++++++++++++++++- src/Expression/Derived.hs | 4 +- src/Expression/PG.hs | 110 +++++++++++++++++++++---------------- src/Expression/Predicate.hs | 20 ++++++- src/Expression/Project.hs | 112 +------------------------------------- src/Expression/Resolve.hs | 57 ++++++------------- src/Expression/Settings.hs | 44 ++++++++++++++- src/Expression/Simplify.hs | 109 +++++++++++++++++++------------------ src/Rules/Data.hs | 2 +- src/Settings.hs | 2 +- src/Targets.hs | 4 +- 12 files changed, 300 insertions(+), 262 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 353b02bdb3999067523c30436c8a4c3dcbc2b770 From git at git.haskell.org Thu Oct 26 23:10:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: New refactoring started: switching to a shallow embedding. (a827aa5) Message-ID: <20171026231031.911CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a827aa580a188603ec8b0b30f58b254dfef8081e/ghc >--------------------------------------------------------------- commit a827aa580a188603ec8b0b30f58b254dfef8081e Author: Andrey Mokhov Date: Sun May 10 01:32:56 2015 +0100 New refactoring started: switching to a shallow embedding. >--------------------------------------------------------------- a827aa580a188603ec8b0b30f58b254dfef8081e src/Expression.hs | 84 ++++++++++++++++ src/Expression/Base.hs | 21 ---- src/Expression/BuildExpression.hs | 55 ---------- src/Expression/BuildPredicate.hs | 113 --------------------- src/Expression/Derived.hs | 204 -------------------------------------- src/Expression/PG.hs | 132 ------------------------ src/Expression/Predicate.hs | 39 -------- src/Expression/Project.hs | 27 ----- src/Expression/Resolve.hs | 100 ------------------- src/Expression/Settings.hs | 186 +++++++++++++++++----------------- src/Expression/Simplify.hs | 127 ------------------------ 11 files changed, 178 insertions(+), 910 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 a827aa580a188603ec8b0b30f58b254dfef8081e From git at git.haskell.org Thu Oct 26 23:10:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add topLevel function to construct top-level packages like compiler. (f60980a) Message-ID: <20171026231035.308A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f60980a571dc9da77a6718d889faf0b8a9b4b58b/ghc >--------------------------------------------------------------- commit f60980a571dc9da77a6718d889faf0b8a9b4b58b Author: Andrey Mokhov Date: Sun May 10 01:36:35 2015 +0100 Add topLevel function to construct top-level packages like compiler. >--------------------------------------------------------------- f60980a571dc9da77a6718d889faf0b8a9b4b58b src/Package.hs | 15 ++++++--------- 1 file changed, 6 insertions(+), 9 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index e5dc94e..3b2f0ec 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,4 +1,4 @@ -module Package (Package (..), library, setCabal) where +module Package (Package (..), library, topLevel, setCabal) where import Base import Util @@ -20,15 +20,12 @@ instance Eq Package where instance Ord Package where compare = compare `on` pkgName -libraryPackage :: String -> String -> Package -libraryPackage name cabalName = - Package - name - (unifyPath $ "libraries" name) - cabalName - library :: String -> Package -library name = libraryPackage name (name <.> "cabal") +library name = + Package name (unifyPath $ "libraries" name) (name <.> "cabal") + +topLevel :: String -> Package +topLevel name = Package name name (name <.> "cabal") setCabal :: Package -> FilePath -> Package setCabal pkg cabalName = pkg { pkgCabal = cabalName } From git at git.haskell.org Thu Oct 26 23:10:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove TargetDir from Base.hs. (f033f1f) Message-ID: <20171026231038.957963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f033f1ff0b94df3b12dd32d774043522c96f0cac/ghc >--------------------------------------------------------------- commit f033f1ff0b94df3b12dd32d774043522c96f0cac Author: Andrey Mokhov Date: Sun May 10 01:37:24 2015 +0100 Remove TargetDir from Base.hs. >--------------------------------------------------------------- f033f1ff0b94df3b12dd32d774043522c96f0cac src/Base.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 2bd350f..49b0fb2 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -8,7 +8,6 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - TargetDir (..), Arg, Args, ShowArg (..), ShowArgs (..), arg, args, @@ -29,9 +28,6 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) instance Show Stage where show = show . fromEnum --- Need TargetDir and FilePath to be distinct types -newtype TargetDir = TargetDir { fromTargetDir :: FilePath } deriving (Show, Eq) - -- The returned string or list of strings is a part of an argument list -- to be passed to a Builder type Arg = Action String From git at git.haskell.org Thu Oct 26 23:10:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add documentation drafts. (a2de9b0) Message-ID: <20171026231042.0B9F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2de9b043b90ef7fc68fea6b1f16535e9f7a20c8/ghc >--------------------------------------------------------------- commit a2de9b043b90ef7fc68fea6b1f16535e9f7a20c8 Author: Andrey Mokhov Date: Sun May 10 01:39:20 2015 +0100 Add documentation drafts. >--------------------------------------------------------------- a2de9b043b90ef7fc68fea6b1f16535e9f7a20c8 doc/build-expressions.docx | Bin 0 -> 22575 bytes doc/build-expressions.pdf | Bin 0 -> 644843 bytes 2 files changed, 0 insertions(+), 0 deletions(-) diff --git a/doc/build-expressions.docx b/doc/build-expressions.docx new file mode 100644 index 0000000..e4fef75 Binary files /dev/null and b/doc/build-expressions.docx differ diff --git a/doc/build-expressions.pdf b/doc/build-expressions.pdf new file mode 100644 index 0000000..bf70430 Binary files /dev/null and b/doc/build-expressions.pdf differ From git at git.haskell.org Thu Oct 26 23:10:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageDependencies rule. (2be9217) Message-ID: <20171026231045.6EF4B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2be9217deed8466c4aa62ac4120174a354d342c8/ghc >--------------------------------------------------------------- commit 2be9217deed8466c4aa62ac4120174a354d342c8 Author: Andrey Mokhov Date: Sun May 10 01:40:19 2015 +0100 Add buildPackageDependencies rule. >--------------------------------------------------------------- 2be9217deed8466c4aa62ac4120174a354d342c8 src/Rules/Dependencies.hs | 185 ++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 185 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs new file mode 100644 index 0000000..930ba98 --- /dev/null +++ b/src/Rules/Dependencies.hs @@ -0,0 +1,185 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module Rules.Data ( + ghcArgs, gccArgs, buildPackageDependencies + ) where + +import qualified Ways +import Base hiding (arg, args, Args) +import Package +import Expression.Base +import Oracles.Flag (when) +import Oracles.Builder +import Targets +import Switches +import Util + +packageSettings :: Settings +packageSettings = msum + [ args ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] + , stage Stage0 ? + (arg "-package-db" |> argPath "libraries/bootstrapping.conf") + , supportsPackageKey ? notStage Stage0 ?? + ( argPairs "-this-package-key" argPackageKey <|> + argPairs "-package-key" argPackageDepKeys + , argPairs "-package-name" argPackageKey <|> + argPairs "-package" argPackageDeps )] + +ghcArgs :: Settings +ghcArgs = + let pathDist = path dist + buildDir = unifyPath $ pathDist "build" + depFile = buildDir "haskell.deps" + in msum [ arg "-M" + , packageSettings + , includeGhcArgs path dist + , concatArgs ["-optP"] $ CppArgs pathDist + , productArgs ["-odir", "-stubdir", "-hidir"] [buildDir] + , args ["-dep-makefile", depFile] + , productArgs ["-dep-suffix"] $ map wayPrefix <$> ways settings + , args $ HsArgs pathDist + , args $ pkgHsSources path dist ] + +-- $1_$2_$3_ALL_CC_OPTS = \ +-- $$(WAY_$3_CC_OPTS) \ +-- $$($1_$2_DIST_GCC_CC_OPTS) \ +-- $$($1_$2_$3_CC_OPTS) \ +-- $$($$(basename $$<)_CC_OPTS) \ +-- $$($1_$2_EXTRA_CC_OPTS) \ +-- $$(EXTRA_CC_OPTS) +-- +-- $1_$2_DIST_CC_OPTS = \ +-- $$(SRC_CC_OPTS) \ +-- $$($1_CC_OPTS) \ +-- -I$1/$2/build/autogen \ +-- $$(foreach dir,$$(filter-out /%,$$($1_$2_INCLUDE_DIRS)),-I$1/$$(dir)) \ +-- $$(foreach dir,$$(filter /%,$$($1_$2_INCLUDE_DIRS)),-I$$(dir)) \ +-- $$($1_$2_CC_OPTS) \ +-- $$($1_$2_CPP_OPTS) \ +-- $$($1_$2_CC_INC_FLAGS) \ +-- $$($1_$2_DEP_CC_OPTS) \ +-- $$(SRC_CC_WARNING_OPTS) + +-- TODO: handle custom $1_$2_MKDEPENDC_OPTS and +gccArgs :: FilePath -> Package -> TodoItem -> Args +gccArgs sourceFile (Package _ path _ _) (stage, dist, settings) = + let pathDist = path dist + buildDir = pathDist "build" + depFile = buildDir takeFileName sourceFile <.> "deps" + in args [ args ["-E", "-MM"] -- TODO: add a Cpp Builder instead + , args $ CcArgs pathDist + , commonCcArgs -- TODO: remove? + , customCcArgs settings -- TODO: Replace by customCppArgs? + , commonCcWarninigArgs -- TODO: remove? + , includeGccArgs path dist + , args ["-MF", unifyPath depFile] + , args ["-x", "c"] + , arg $ unifyPath sourceFile ] + +buildRule :: Package -> TodoItem -> Rules () +buildRule pkg @ (Package name path _ _) todo @ (stage, dist, settings) = do + let pathDist = path dist + buildDir = pathDist "build" + + (buildDir "haskell.deps") %> \_ -> do + run (Ghc stage) $ ghcArgs pkg todo + -- Finally, record the argument list + need [argListPath argListDir pkg stage] + + (buildDir "c.deps") %> \out -> do + srcs <- args $ CSrcs pathDist + deps <- fmap concat $ forM srcs $ \src -> do + let srcPath = path src + depFile = buildDir takeFileName src <.> "deps" + run (Gcc stage) $ gccArgs srcPath pkg todo + liftIO $ readFile depFile + writeFileChanged out deps + liftIO $ removeFiles buildDir ["*.c.deps"] + -- Finally, record the argument list + need [argListPath argListDir pkg stage] + +argListRule :: Package -> TodoItem -> Rules () +argListRule pkg todo @ (stage, _, _) = + (argListPath argListDir pkg stage) %> \out -> do + need $ ["shake/src/Package/Dependencies.hs"] ++ sourceDependecies + ghcList <- argList (Ghc stage) $ ghcArgs pkg todo + gccList <- argList (Gcc stage) $ gccArgs "source.c" pkg todo + writeFileChanged out $ ghcList ++ "\n" ++ gccList + +buildPackageDependencies :: Package -> TodoItem -> Rules () +buildPackageDependencies = argListRule <> buildRule + + +-- Build package-data.mk by using GhcCabal to process pkgCabal file +buildPackageData :: Stage -> Package -> FilePath -> Ways -> Settings -> Rules () +buildPackageData stage pkg dir ways settings = + (dir ) <$> + [ "package-data.mk" + , "haddock-prologue.txt" + , "inplace-pkg-config" + , "setup-config" + , "build" "autogen" "cabal_macros.h" + -- TODO: Is this needed? Also check out Paths_cpsa.hs. + -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" + ] &%> \_ -> do + let configure = pkgPath pkg "configure" + need [pkgPath pkg pkgCabal pkg] + -- GhcCabal will run the configure script, so we depend on it + -- We still don't know who build the configure script from configure.ac + when (doesFileExist $ configure <.> "ac") $ need [configure] + run' GhcCabal settings + -- TODO: when (registerPackage settings) $ + run' (GhcPkg stage) settings + postProcessPackageData $ dir "package-data.mk" + +run' :: Builder -> Settings -> Action () +run' builder settings = do + settings' <- evaluate (project builder settings) + case fromSettings settings' of + Nothing -> + redError $ "Cannot determine " ++ show builder ++ " settings." + Just args -> do + putColoured Green (show args) + run builder args + +--buildRule :: Package -> TodoItem -> Rules () +--buildRule pkg @ (Package name path cabal _) todo @ (stage, dist, settings) = +-- let pathDist = path dist +-- cabalPath = path cabal +-- configure = path "configure" +-- in +-- -- All these files are produced by a single run of GhcCabal +-- (pathDist ) <$> +-- [ "package-data.mk" +-- , "haddock-prologue.txt" +-- , "inplace-pkg-config" +-- , "setup-config" +-- , "build" "autogen" "cabal_macros.h" +-- -- TODO: Is this needed? Also check out Paths_cpsa.hs. +-- -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" +-- ] &%> \_ -> do +-- need [cabalPath] +-- when (doesFileExist $ configure <.> "ac") $ need [configure] +-- -- GhcCabal will run the configure script, so we depend on it +-- -- We still don't know who build the configure script from configure.ac +-- run GhcCabal $ cabalArgs pkg todo +-- when (registerPackage settings) $ +-- run (GhcPkg stage) $ ghcPkgArgs pkg todo +-- postProcessPackageData $ pathDist "package-data.mk" + +ccSettings :: Settings +ccSettings = msum + [ package integerLibrary ? argPath "-Ilibraries/integer-gmp2/gmp" + , builder GhcCabal ? argStagedConfig "conf-cc-args" + , validating ? msum + [ not (builder GhcCabal) ? arg "-Werror" + , arg "-Wall" + , gccIsClang ?? + ( arg "-Wno-unknown-pragmas" <|> + not gccLt46 ? windowsHost ? arg "-Werror=unused-but-set-variable" + , not gccLt46 ? arg "-Wno-error=inline" )]] + +ldSettings :: Settings +ldSettings = builder GhcCabal ? argStagedConfig "conf-gcc-linker-args" + +cppSettings :: Settings +cppSettings = builder GhcCabal ? argStagedConfig "conf-cpp-args" From git at git.haskell.org Thu Oct 26 23:10:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Continue refactoring. (cf54d1a) Message-ID: <20171026231048.E07963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf54d1aacd927a06a74918de2db479ac6d5ef2a8/ghc >--------------------------------------------------------------- commit cf54d1aacd927a06a74918de2db479ac6d5ef2a8 Author: Andrey Mokhov Date: Sun May 10 01:41:36 2015 +0100 Continue refactoring. >--------------------------------------------------------------- cf54d1aacd927a06a74918de2db479ac6d5ef2a8 src/Rules.hs | 8 ++-- src/Rules/Data.hs | 23 +++++---- src/Rules/Package.hs | 2 +- src/Settings.hs | 11 ----- src/Switches.hs | 95 ++++++++++++++++++------------------ src/Targets.hs | 132 +++++++++++++++++++++++++++------------------------ 6 files changed, 138 insertions(+), 133 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 cf54d1aacd927a06a74918de2db479ac6d5ef2a8 From git at git.haskell.org Thu Oct 26 23:10:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop parameterisation by monad in Expression. (fdb6117) Message-ID: <20171026231052.6946A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fdb6117f21e3bc39ae97bf0f12c0fc3caf10e093/ghc >--------------------------------------------------------------- commit fdb6117f21e3bc39ae97bf0f12c0fc3caf10e093 Author: Andrey Mokhov Date: Mon Jun 8 02:07:09 2015 +0100 Drop parameterisation by monad in Expression. >--------------------------------------------------------------- fdb6117f21e3bc39ae97bf0f12c0fc3caf10e093 src/Expression.hs | 51 ++++++++++++++++++++++++++++----------------------- 1 file changed, 28 insertions(+), 23 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index fc70be1..de5fae9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -2,13 +2,11 @@ module Expression ( module Control.Monad.Reader, Ways, - Packages, - TargetDir, Predicate, Expression, - Environment (..), + Environment (..), defaultEnvironment, interpret, - whenPredicate, (?), stage, notStage, package, + whenPredicate, (?), (??), stage, notStage, builder, notBuilder, package, configKeyValue, configKeyValues, configKeyYes, configKeyNo, configKeyNonEmpty ) where @@ -34,51 +32,58 @@ defaultEnvironment = Environment getPackage = error "Package not set in the environment" } -type Expression m a = ReaderT Environment m a +type Expression a = ReaderT Environment Action a -type Ways m = Expression m [Way] -type Packages m = Expression m [Package] -type Predicate m = Expression m Bool -type TargetDir m = Expression m FilePath +type Ways = Expression [Way] +type Predicate = Expression Bool -instance (Monad m, Monoid a) => Monoid (Expression m a) where +instance Monoid a => Monoid (Expression a) where mempty = return mempty mappend = liftM2 mappend -interpret :: (Monad m, Monoid a) => Expression m a -> Environment -> m a -interpret = runReaderT +interpret :: Environment -> Expression a -> Action a +interpret = flip runReaderT -whenPredicate :: (Monad m, Monoid a) => Predicate m -> Expression m a -> Expression m a +whenPredicate :: Monoid a => Predicate -> Expression a -> Expression a whenPredicate predicate expr = do bool <- predicate if bool then expr else return mempty -(?) :: (Monad m, Monoid a) => Predicate m -> Expression m a -> Expression m a +(?) :: Monoid a => Predicate -> Expression a -> Expression a (?) = whenPredicate +(??) :: Monoid a => Predicate -> (Expression a, Expression a) -> Expression a +p ?? (t, f) = p ? t <> (liftM not p) ? f + infixr 8 ? -stage :: Monad m => Stage -> Predicate m +stage :: Stage -> Predicate stage s = liftM (s ==) (asks getStage) -notStage :: Monad m => Stage -> Predicate m +notStage :: Stage -> Predicate notStage = liftM not . stage -package :: Monad m => Package -> Predicate m +builder :: Builder -> Predicate +builder b = liftM (b ==) (asks getBuilder) + +notBuilder :: Builder -> Predicate +notBuilder = liftM not . builder + +package :: Package -> Predicate package p = liftM (p ==) (asks getPackage) -configKeyValue :: String -> String -> Predicate Action +configKeyValue :: String -> String -> Predicate configKeyValue key value = liftM (value ==) (lift $ askConfig key) -- checks if there is at least one match -configKeyValues :: String -> [String] -> Predicate Action +configKeyValues :: String -> [String] -> Predicate configKeyValues key values = liftM (flip elem $ values) (lift $ askConfig key) -configKeyYes :: String -> Predicate Action +configKeyYes :: String -> Predicate configKeyYes key = configKeyValue key "YES" -configKeyNo :: String -> Predicate Action +configKeyNo :: String -> Predicate configKeyNo key = configKeyValue key "NO" -configKeyNonEmpty :: String -> Predicate Action -configKeyNonEmpty key = configKeyValue key "" +configKeyNonEmpty :: String -> Predicate +configKeyNonEmpty key = liftM not $ configKeyValue key "" From git at git.haskell.org Thu Oct 26 23:10:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish buildPackageData with the Reader approach. (031179a) Message-ID: <20171026231055.D7E4A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/031179a7506ef56897b6316fc83b46fecfb61946/ghc >--------------------------------------------------------------- commit 031179a7506ef56897b6316fc83b46fecfb61946 Author: Andrey Mokhov Date: Mon Jun 8 02:08:57 2015 +0100 Finish buildPackageData with the Reader approach. >--------------------------------------------------------------- 031179a7506ef56897b6316fc83b46fecfb61946 src/Expression/Settings.hs | 15 ++-- src/Rules.hs | 41 ++++----- src/Rules/Data.hs | 202 ++++++++++++++++++++++++++------------------- src/Rules/Package.hs | 1 + src/Settings.hs | 11 +-- src/Switches.hs | 39 +++++---- src/Targets.hs | 70 +++++++++------- 7 files changed, 206 insertions(+), 173 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 031179a7506ef56897b6316fc83b46fecfb61946 From git at git.haskell.org Thu Oct 26 23:10:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:10:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify build rule interfaces. (622d3c1) Message-ID: <20171026231059.623713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/622d3c164d3c36fba97e780a5d3e3b4049e18417/ghc >--------------------------------------------------------------- commit 622d3c164d3c36fba97e780a5d3e3b4049e18417 Author: Andrey Mokhov Date: Sat Jun 13 14:14:03 2015 +0100 Simplify build rule interfaces. >--------------------------------------------------------------- 622d3c164d3c36fba97e780a5d3e3b4049e18417 src/Rules.hs | 4 ++-- src/Rules/Data.hs | 9 ++++++--- src/Rules/Package.hs | 3 +-- 3 files changed, 9 insertions(+), 7 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 8f2825f..dd9e2e0 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -30,5 +30,5 @@ packageRules :: Rules () packageRules = forM_ [Stage0, Stage1] $ \stage -> do forM_ targetPackages $ \pkg -> do - let dir = pkgPath pkg targetDirectory stage pkg - buildPackage stage pkg dir targetWays buildSettings + let env = defaultEnvironment { getStage = stage, getPackage = pkg } + buildPackage env targetWays buildSettings diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 0a1abf1..7447e5e 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -140,8 +140,12 @@ postProcessPackageData file = do -- * otherwise, we must collapse it into one space-separated string -- Build package-data.mk by using GhcCabal to process pkgCabal file -buildPackageData :: Stage -> Package -> FilePath -> Ways -> Settings -> Rules () -buildPackageData stage pkg dir ways settings = +buildPackageData :: Environment -> Ways -> Settings -> Rules () +buildPackageData env ways settings = + let stage = getStage env + pkg = getPackage env + dir = pkgPath pkg targetDirectory stage pkg + in (dir ) <$> [ "package-data.mk" , "haddock-prologue.txt" @@ -152,7 +156,6 @@ buildPackageData stage pkg dir ways settings = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" - env = defaultEnvironment { getStage = stage, getPackage = pkg } need [pkgPath pkg pkgCabal pkg] -- GhcCabal will run the configure script, so we depend on it -- We still don't know who build the configure script from configure.ac diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 5ce0ed9..d56bb30 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -3,10 +3,9 @@ module Rules.Package ( ) where import Base -import Package import Rules.Data import Expression import Expression.Settings -buildPackage :: Stage -> Package -> FilePath -> Ways -> Settings -> Rules () +buildPackage :: Environment -> Ways -> Settings -> Rules () buildPackage = buildPackageData From git at git.haskell.org Thu Oct 26 23:11:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add example UserSettings.hs. (b5bf68d) Message-ID: <20171026231103.0D7A43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b5bf68d5ec49bf888321dc7a55e02c772b073de5/ghc >--------------------------------------------------------------- commit b5bf68d5ec49bf888321dc7a55e02c772b073de5 Author: Andrey Mokhov Date: Sun Jun 14 01:18:49 2015 +0100 Add example UserSettings.hs. >--------------------------------------------------------------- b5bf68d5ec49bf888321dc7a55e02c772b073de5 src/UserSettings.hs | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/src/UserSettings.hs b/src/UserSettings.hs new file mode 100644 index 0000000..0a37159 --- /dev/null +++ b/src/UserSettings.hs @@ -0,0 +1,17 @@ +module UserSettings ( + userSettings + ) where + +import Base hiding (arg, args, Args) +import Rules.Data +import Oracles.Builder +import Expression +import Expression.Settings + +userSettings :: Settings +userSettings = mconcat + [ package compiler ? stage Stage0 ? append ["foo", "bar"] + , builder (Ghc Stage0) ? remove ["-O2"] + , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] + ] + From git at git.haskell.org Thu Oct 26 23:11:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to difference lists. (5b1c215) Message-ID: <20171026231106.7787D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8/ghc >--------------------------------------------------------------- commit 5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8 Author: Andrey Mokhov Date: Sun Jun 14 01:19:19 2015 +0100 Switch to difference lists. >--------------------------------------------------------------- 5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8 src/Expression.hs | 73 ++++++++++++++++++++++++++++++++++-------- src/Expression/Settings.hs | 15 +++++---- src/Rules.hs | 15 ++++----- src/Rules/Data.hs | 76 ++++++++++++++++++++----------------------- src/Targets.hs | 80 +++++++++++++++++++--------------------------- 5 files changed, 142 insertions(+), 117 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 5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8 From git at git.haskell.org Thu Oct 26 23:11:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add userPackages for overriding default targetPackages. (5d6c2d7) Message-ID: <20171026231109.E57203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d6c2d7a48d85f2af6f341ee14bc86de400b4779/ghc >--------------------------------------------------------------- commit 5d6c2d7a48d85f2af6f341ee14bc86de400b4779 Author: Andrey Mokhov Date: Sun Jun 14 14:50:48 2015 +0100 Add userPackages for overriding default targetPackages. >--------------------------------------------------------------- 5d6c2d7a48d85f2af6f341ee14bc86de400b4779 src/Expression.hs | 5 ++++- src/Rules.hs | 2 +- src/UserSettings.hs | 9 ++++++--- 3 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index ac72891..77be4e9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -6,7 +6,7 @@ module Expression ( Ways, Packages, Environment (..), defaultEnvironment, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, - interpret, + interpret, interpretDiff, applyPredicate, (?), (??), stage, notStage, builder, notBuilder, package, configKeyValue, configKeyValues, configKeyYes, configKeyNo, configKeyNonEmpty @@ -89,6 +89,9 @@ interpret = flip runReaderT fromDiff :: Monoid a => DiffExpr a -> Expr a fromDiff = fmap (($ mempty) . appEndo) +interpretDiff :: Environment -> Expr a -> Action a +interpretDiff env = interpret env . fromDiff + applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate diff --git a/src/Rules.hs b/src/Rules.hs index 50fa5e1..2873abf 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -18,7 +18,7 @@ generateTargets :: Rules () generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do let env = defaultEnvironment { getStage = stage } - pkgs <- interpret env $ fromDiff targetPackages + pkgs <- interpretDiff env $ targetPackages <> userPackages forM_ pkgs $ \pkg -> do let dir = targetDirectory stage pkg need [pkgPath pkg dir "package-data.mk"] diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 0a37159..1615d60 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -1,5 +1,5 @@ module UserSettings ( - userSettings + userSettings, userPackages ) where import Base hiding (arg, args, Args) @@ -12,6 +12,9 @@ userSettings :: Settings userSettings = mconcat [ package compiler ? stage Stage0 ? append ["foo", "bar"] , builder (Ghc Stage0) ? remove ["-O2"] - , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] - ] + , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] +userPackages :: Settings +userPackages = mconcat + [ stage Stage1 ? remove [cabal] + , remove [compiler] ] From git at git.haskell.org Thu Oct 26 23:11:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add userPackages for overriding default list of target packages. (f500bd1) Message-ID: <20171026231113.7829B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f500bd171e7d5ca2416876b5477b59fa89e7762e/ghc >--------------------------------------------------------------- commit f500bd171e7d5ca2416876b5477b59fa89e7762e Author: Andrey Mokhov Date: Sun Jun 14 15:02:09 2015 +0100 Add userPackages for overriding default list of target packages. >--------------------------------------------------------------- f500bd171e7d5ca2416876b5477b59fa89e7762e src/Expression.hs | 2 +- src/Rules.hs | 1 + src/Targets.hs | 8 ++++---- src/UserSettings.hs | 4 ++-- 4 files changed, 8 insertions(+), 7 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 77be4e9..ec76244 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -89,7 +89,7 @@ interpret = flip runReaderT fromDiff :: Monoid a => DiffExpr a -> Expr a fromDiff = fmap (($ mempty) . appEndo) -interpretDiff :: Environment -> Expr a -> Action a +interpretDiff :: Monoid a => Environment -> DiffExpr a -> Action a interpretDiff env = interpret env . fromDiff applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a diff --git a/src/Rules.hs b/src/Rules.hs index 2873abf..227eef1 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -10,6 +10,7 @@ import Targets import Settings import Package import Expression +import UserSettings import Rules.Package -- generateTargets needs package-data.mk files of all target packages diff --git a/src/Targets.hs b/src/Targets.hs index 186a321..5929eb8 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -1,10 +1,10 @@ module Targets ( targetWays, targetPackages, targetDirectory, allPackages, customConfigureSettings, - array, base, binPackageDb, binary, bytestring, cabal, containers, deepseq, - directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerLibrary, - parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, - transformers, unix, win32, xhtml + array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, + deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, + integerLibrary, parallel, pretty, primitive, process, stm, templateHaskell, + terminfo, time, transformers, unix, win32, xhtml ) where import Ways hiding (parallel) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 1615d60..b785c7f 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,8 +3,8 @@ module UserSettings ( ) where import Base hiding (arg, args, Args) -import Rules.Data import Oracles.Builder +import Targets import Expression import Expression.Settings @@ -14,7 +14,7 @@ userSettings = mconcat , builder (Ghc Stage0) ? remove ["-O2"] , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] -userPackages :: Settings +userPackages :: Packages userPackages = mconcat [ stage Stage1 ? remove [cabal] , remove [compiler] ] From git at git.haskell.org Thu Oct 26 23:11:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add userWays and make sure all user-specific settings are used. (a1dd39f) Message-ID: <20171026231117.0E1A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1dd39f2b8f32948de4c219a866712dc2eb7884b/ghc >--------------------------------------------------------------- commit a1dd39f2b8f32948de4c219a866712dc2eb7884b Author: Andrey Mokhov Date: Sun Jun 14 15:17:20 2015 +0100 Add userWays and make sure all user-specific settings are used. >--------------------------------------------------------------- a1dd39f2b8f32948de4c219a866712dc2eb7884b src/Rules.hs | 2 +- src/Settings.hs | 6 +++--- src/UserSettings.hs | 23 +++++++++++++++++++---- 3 files changed, 23 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 227eef1..bb68b47 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -31,4 +31,4 @@ packageRules = forM_ [Stage0, Stage1] $ \stage -> do forM_ allPackages $ \pkg -> do let env = defaultEnvironment { getStage = stage, getPackage = pkg } - buildPackage env targetWays buildSettings + buildPackage env (targetWays <> userWays) (settings <> userSettings) diff --git a/src/Settings.hs b/src/Settings.hs index 539ed48..41b31ba 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,7 +1,7 @@ {-# LANGUAGE NoImplicitPrelude, FlexibleInstances #-} module Settings ( - buildSettings + settings ) where import Base hiding (arg, args, Args) @@ -10,8 +10,8 @@ import Oracles.Builder import Expression import Expression.Settings -buildSettings :: Settings -buildSettings = do +settings :: Settings +settings = do stage <- asks getStage mconcat [ builder GhcCabal ? cabalSettings , builder (GhcPkg stage) ? ghcPkgSettings ] diff --git a/src/UserSettings.hs b/src/UserSettings.hs index b785c7f..ccc03f5 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -1,20 +1,35 @@ module UserSettings ( - userSettings, userPackages + userSettings, userPackages, userWays ) where import Base hiding (arg, args, Args) import Oracles.Builder +import Ways import Targets import Expression import Expression.Settings +-- No user-specific settings by default userSettings :: Settings -userSettings = mconcat +userSettings = mempty + +userPackages :: Packages +userPackages = mempty + +userWays :: Ways +userWays = mempty + +-- Examples: +userSettings' :: Settings +userSettings' = mconcat [ package compiler ? stage Stage0 ? append ["foo", "bar"] , builder (Ghc Stage0) ? remove ["-O2"] , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] -userPackages :: Packages -userPackages = mconcat +userPackages' :: Packages +userPackages' = mconcat [ stage Stage1 ? remove [cabal] , remove [compiler] ] + +userWays' :: Ways +userWays' = remove [profiling] From git at git.haskell.org Thu Oct 26 23:11:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix ordering of appends. (95b6614) Message-ID: <20171026231120.9BCED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95b6614a659907ec33afce9bca396a7f7d20a498/ghc >--------------------------------------------------------------- commit 95b6614a659907ec33afce9bca396a7f7d20a498 Author: Andrey Mokhov Date: Sun Jun 14 15:39:21 2015 +0100 Fix ordering of appends. >--------------------------------------------------------------- 95b6614a659907ec33afce9bca396a7f7d20a498 src/Expression.hs | 2 +- src/Rules/Data.hs | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index ec76244..8ae285d 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -45,7 +45,7 @@ instance Monoid a => Monoid (Expr a) where mappend = liftM2 mappend append :: Monoid a => a -> DiffExpr a -append x = return $ Endo (<> x) +append = return . Endo . mappend appendM :: Monoid a => Action a -> DiffExpr a appendM mx = lift mx >>= append diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index c8cb354..4c7e5de 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -148,9 +148,9 @@ buildPackageData env ways settings = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" - need [pkgPath pkg pkgCabal pkg] -- GhcCabal will run the configure script, so we depend on it - -- We still don't know who build the configure script from configure.ac + need [pkgPath pkg pkgCabal pkg] + -- We still don't know who built the configure script from configure.ac when (doesFileExist $ configure <.> "ac") $ need [configure] run' env GhcCabal settings -- TODO: when (registerPackage settings) $ From git at git.haskell.org Thu Oct 26 23:11:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant argument to build rules. (3461e46) Message-ID: <20171026231124.24A043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3461e46ca8f34eebe63f32a5dc76a6afdcb6f294/ghc >--------------------------------------------------------------- commit 3461e46ca8f34eebe63f32a5dc76a6afdcb6f294 Author: Andrey Mokhov Date: Sun Jun 14 16:03:07 2015 +0100 Remove redundant argument to build rules. >--------------------------------------------------------------- 3461e46ca8f34eebe63f32a5dc76a6afdcb6f294 src/Rules.hs | 5 +- src/Rules/Data.hs | 132 +++------------------------------------------- src/Rules/Package.hs | 3 +- src/Settings.hs | 144 +++++++++++++++++++++++++++++++++++++++++++++++++-- src/Targets.hs | 3 +- 5 files changed, 151 insertions(+), 136 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3461e46ca8f34eebe63f32a5dc76a6afdcb6f294 From git at git.haskell.org Thu Oct 26 23:11:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor folder structure. (2f70955) Message-ID: <20171026231127.8023B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f70955b45d2c0e4dad2fd8a606caca094bd7c5c/ghc >--------------------------------------------------------------- commit 2f70955b45d2c0e4dad2fd8a606caca094bd7c5c Author: Andrey Mokhov Date: Sun Jun 14 16:10:48 2015 +0100 Refactor folder structure. >--------------------------------------------------------------- 2f70955b45d2c0e4dad2fd8a606caca094bd7c5c src/Expression.hs | 8 +++++--- src/Settings.hs | 2 +- src/{Expression/Settings.hs => Settings/Util.hs} | 6 +----- src/Targets.hs | 1 - src/UserSettings.hs | 1 - 5 files changed, 7 insertions(+), 11 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 8ae285d..7adbce0 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -3,7 +3,7 @@ module Expression ( module Control.Monad.Reader, Expr, DiffExpr, fromDiff, Predicate, - Ways, Packages, + Settings, Ways, Packages, Environment (..), defaultEnvironment, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, interpret, interpretDiff, @@ -37,8 +37,10 @@ type Expr a = ReaderT Environment Action a type DiffExpr a = Expr (Endo a) type Predicate = Expr Bool -type Ways = DiffExpr [Way] -type Packages = DiffExpr [Package] + +type Settings = DiffExpr [String] +type Ways = DiffExpr [Way] +type Packages = DiffExpr [Package] instance Monoid a => Monoid (Expr a) where mempty = return mempty diff --git a/src/Settings.hs b/src/Settings.hs index ebafbc2..95b88b5 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -14,9 +14,9 @@ import Targets import Package import Switches import Oracles.Base +import Settings.Util import UserSettings import Expression hiding (when, liftIO) -import Expression.Settings settings :: Settings settings = defaultSettings <> userSettings diff --git a/src/Expression/Settings.hs b/src/Settings/Util.hs similarity index 97% rename from src/Expression/Settings.hs rename to src/Settings/Util.hs index 5bc185b..dbd07c0 100644 --- a/src/Expression/Settings.hs +++ b/src/Settings/Util.hs @@ -1,8 +1,6 @@ {-# LANGUAGE NoImplicitPrelude #-} -module Expression.Settings ( - Settings, - +module Settings.Util ( -- Primitive settings elements arg, argM, args, argConfig, argStagedConfig, argConfigList, argStagedConfigList, @@ -18,8 +16,6 @@ import Base hiding (Args, arg, args) import Oracles hiding (not) import Expression -type Settings = DiffExpr [String] - -- A single argument arg :: String -> Settings arg = append . return diff --git a/src/Targets.hs b/src/Targets.hs index b2b52d3..4d3c613 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -13,7 +13,6 @@ import Base hiding (arg, args, Args, TargetDir) import Package import Switches import Expression -import Expression.Settings -- These are the packages we build targetPackages :: Packages diff --git a/src/UserSettings.hs b/src/UserSettings.hs index ccc03f5..4928661 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -7,7 +7,6 @@ import Oracles.Builder import Ways import Targets import Expression -import Expression.Settings -- No user-specific settings by default userSettings :: Settings From git at git.haskell.org Thu Oct 26 23:11:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split Targets.hs and Settings.hs into multiple logically separate files. (062952c) Message-ID: <20171026231131.05C8B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/062952ca22b4c06d96cc0ad601ae3437ea6883dc/ghc >--------------------------------------------------------------- commit 062952ca22b4c06d96cc0ad601ae3437ea6883dc Author: Andrey Mokhov Date: Sun Jun 14 18:03:20 2015 +0100 Split Targets.hs and Settings.hs into multiple logically separate files. >--------------------------------------------------------------- 062952ca22b4c06d96cc0ad601ae3437ea6883dc src/Expression.hs | 2 + src/Rules.hs | 4 +- src/Rules/Data.hs | 2 + src/Settings.hs | 140 +----------------------------- src/{Settings.hs => Settings/GhcCabal.hs} | 89 +++++++------------ src/Settings/GhcPkg.hs | 20 +++++ src/Settings/Packages.hs | 33 +++++++ src/Settings/Ways.hs | 20 +++++ src/Targets.hs | 45 +++------- 9 files changed, 124 insertions(+), 231 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 062952ca22b4c06d96cc0ad601ae3437ea6883dc From git at git.haskell.org Thu Oct 26 23:11:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move derived predicates around. (2bd0715) Message-ID: <20171026231134.6DCBF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2bd0715aa24e153e43707deaa6ef8ca6386105ab/ghc >--------------------------------------------------------------- commit 2bd0715aa24e153e43707deaa6ef8ca6386105ab Author: Andrey Mokhov Date: Sun Jun 14 19:44:05 2015 +0100 Move derived predicates around. >--------------------------------------------------------------- 2bd0715aa24e153e43707deaa6ef8ca6386105ab src/Expression.hs | 8 +------- src/Settings/GhcCabal.hs | 13 +++++++------ src/Settings/GhcPkg.hs | 7 ++++--- src/Settings/Packages.hs | 4 ++-- src/Switches.hs | 27 +++++++++++++++++++-------- src/Targets.hs | 4 +++- src/UserSettings.hs | 20 +++++++++++++++----- 7 files changed, 51 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2bd0715aa24e153e43707deaa6ef8ca6386105ab From git at git.haskell.org Thu Oct 26 23:11:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix argument ordering issues in DiffExpr. (b67db18) Message-ID: <20171026231137.D69CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b67db18e8f9745bd25045f0e09f64cbb5c5b09b5/ghc >--------------------------------------------------------------- commit b67db18e8f9745bd25045f0e09f64cbb5c5b09b5 Author: Andrey Mokhov Date: Sun Jun 14 20:33:13 2015 +0100 Fix argument ordering issues in DiffExpr. >--------------------------------------------------------------- b67db18e8f9745bd25045f0e09f64cbb5c5b09b5 src/Expression.hs | 29 +++++++++++++++-------------- 1 file changed, 15 insertions(+), 14 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index a37bf7c..d147280 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -36,7 +36,7 @@ defaultEnvironment = Environment } type Expr a = ReaderT Environment Action a -type DiffExpr a = Expr (Endo a) +type DiffExpr a = Expr (Dual (Endo a)) type Predicate = Expr Bool @@ -49,49 +49,50 @@ instance Monoid a => Monoid (Expr a) where mappend = liftM2 mappend append :: Monoid a => a -> DiffExpr a -append = return . Endo . mappend +append x = return . Dual . Endo $ (<> x) appendM :: Monoid a => Action a -> DiffExpr a appendM mx = lift mx >>= append remove :: Eq a => [a] -> DiffExpr [a] -remove xs = return . Endo $ filter (`notElem` xs) +remove xs = return . Dual . Endo $ filter (`notElem` xs) -- appendSub appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument -- of the form 'prefix=listOfSubarguments' is appended to the expression. -- Note: nothing is done if the list of sub-arguments is empty. -appendSub :: String -> [String] -> DiffExpr [String] +appendSub :: String -> [String] -> Settings appendSub prefix xs - | xs == [] = mempty - | otherwise = return $ Endo (go False) + | xs' == [] = mempty + | otherwise = return . Dual . Endo $ go False where + xs' = filter (/= "") xs go True [] = [] - go False [] = [prefix ++ "=" ++ unwords xs] + go False [] = [prefix ++ "=" ++ unwords xs'] go found (y:ys) = if prefix `isPrefixOf` y - then unwords (y : xs) : go True ys - else go found ys + then unwords (y : xs') : go True ys + else y : go found ys -- appendSubD is similar to appendSub but it extracts the list of sub-arguments -- from the given DiffExpr. -appendSubD :: String -> DiffExpr [String] -> DiffExpr [String] +appendSubD :: String -> Settings -> Settings appendSubD prefix diffExpr = fromDiff diffExpr >>= appendSub prefix -filterSub :: String -> (String -> Bool) -> DiffExpr [String] -filterSub prefix p = return . Endo $ map filterSubstr +filterSub :: String -> (String -> Bool) -> Settings +filterSub prefix p = return . Dual . Endo $ map filterSubstr where filterSubstr s | prefix `isPrefixOf` s = unwords . filter p . words $ s | otherwise = s -removeSub :: String -> [String] -> DiffExpr [String] +removeSub :: String -> [String] -> Settings removeSub prefix xs = filterSub prefix (`notElem` xs) interpret :: Environment -> Expr a -> Action a interpret = flip runReaderT fromDiff :: Monoid a => DiffExpr a -> Expr a -fromDiff = fmap (($ mempty) . appEndo) +fromDiff = fmap (($ mempty) . appEndo . getDual) interpretDiff :: Monoid a => Environment -> DiffExpr a -> Action a interpretDiff env = interpret env . fromDiff From git at git.haskell.org Thu Oct 26 23:11:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor settings predicates. (463094d) Message-ID: <20171026231141.702773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/463094da9933beec44729dd96ea47430a4e9f2a0/ghc >--------------------------------------------------------------- commit 463094da9933beec44729dd96ea47430a4e9f2a0 Author: Andrey Mokhov Date: Mon Jun 15 00:44:08 2015 +0100 Refactor settings predicates. >--------------------------------------------------------------- 463094da9933beec44729dd96ea47430a4e9f2a0 cfg/default.config.in | 1 - src/Settings.hs | 10 +++++----- src/Settings/GhcCabal.hs | 26 ++++++++++++++------------ src/Settings/GhcPkg.hs | 10 ++++++---- src/Targets.hs | 17 ++++++++--------- 5 files changed, 33 insertions(+), 31 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index 2e65688..f31af13 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -38,7 +38,6 @@ supports-package-key = @SUPPORTS_PACKAGE_KEY@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ -validating = NO ghc-source-path = @hardtop@ # Information about host and target systems: diff --git a/src/Settings.hs b/src/Settings.hs index a9f5cce..cde678e 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,8 +2,8 @@ module Settings ( settings ) where +import Targets import Base hiding (arg, args) -import Oracles.Builder import Settings.GhcPkg import Settings.GhcCabal import UserSettings @@ -13,7 +13,7 @@ settings :: Settings settings = defaultSettings <> userSettings defaultSettings :: Settings -defaultSettings = do - stage <- asks getStage - mconcat [ builder GhcCabal ? cabalSettings - , builder (GhcPkg stage) ? ghcPkgSettings ] +defaultSettings = mconcat + [ cabalSettings + , ghcPkgSettings + , customPackageSettings ] diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index d0f6512..db972ac 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -17,7 +17,7 @@ import Settings.Packages import UserSettings cabalSettings :: Settings -cabalSettings = do +cabalSettings = builder GhcCabal ? do stage <- asks getStage pkg <- asks getPackage mconcat [ arg "configure" @@ -26,7 +26,6 @@ cabalSettings = do , dllSettings , with' $ Ghc stage , with' $ GhcPkg stage - , customConfigureSettings , stage0 ? bootPackageDbSettings , librarySettings , configKeyNonEmpty "hscolour" ? with' HsColour -- TODO: generalise? @@ -59,14 +58,18 @@ librarySettings = do configureSettings :: Settings configureSettings = do - let conf key = appendSubD $ "--configure-option=" ++ key - ccSettings' = ccSettings <> remove ["-Werror"] + let conf key = appendSubD $ "--configure-option=" ++ key + cFlags = mconcat [ ccSettings + , remove ["-Werror"] + , argStagedConfig "conf-cc-args" ] + ldFlags = ldSettings <> argStagedConfig "conf-gcc-linker-args" + cppFlags = cppSettings <> argStagedConfig "conf-cpp-args" stage <- asks getStage mconcat - [ conf "CFLAGS" ccSettings' - , conf "LDFLAGS" ldSettings - , conf "CPPFLAGS" cppSettings - , appendSubD "--gcc-options" $ ccSettings' <> ldSettings + [ conf "CFLAGS" cFlags + , conf "LDFLAGS" ldFlags + , conf "CPPFLAGS" cppFlags + , appendSubD "--gcc-options" $ cFlags <> ldFlags , conf "--with-iconv-includes" $ argConfig "iconv-include-dirs" , conf "--with-iconv-libraries" $ argConfig "iconv-lib-dirs" , conf "--with-gmp-includes" $ argConfig "gmp-include-dirs" @@ -106,9 +109,8 @@ ccSettings = do let gccGe46 = liftM not gccLt46 mconcat [ package integerLibrary ? arg "-Ilibraries/integer-gmp2/gmp" - , builder GhcCabal ? argStagedConfig "conf-cc-args" , validating ? mconcat - [ notBuilder GhcCabal ? arg "-Werror" + [ arg "-Werror" , arg "-Wall" , gccIsClang ?? ( arg "-Wno-unknown-pragmas" <> @@ -117,7 +119,7 @@ ccSettings = do ] ldSettings :: Settings -ldSettings = builder GhcCabal ? argStagedConfig "conf-gcc-linker-args" +ldSettings = mempty cppSettings :: Settings -cppSettings = builder GhcCabal ? argStagedConfig "conf-cpp-args" +cppSettings = mempty diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index b3ba6f9..0e17b02 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -8,6 +8,7 @@ import Targets import Switches import Expression hiding (when, liftIO) import Settings.Util +import Oracles.Builder import Settings.GhcCabal ghcPkgSettings :: Settings @@ -15,7 +16,8 @@ ghcPkgSettings = do pkg <- asks getPackage stage <- asks getStage let dir = pkgPath pkg targetDirectory stage pkg - mconcat [ arg "update" - , arg "--force" - , stage0 ? bootPackageDbSettings - , arg $ dir "inplace-pkg-config" ] + builder (GhcPkg stage) ? mconcat + [ arg "update" + , arg "--force" + , stage0 ? bootPackageDbSettings + , arg $ dir "inplace-pkg-config" ] diff --git a/src/Targets.hs b/src/Targets.hs index 5218909..c8aeb22 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -1,7 +1,7 @@ module Targets ( targetDirectory, knownPackages, - customConfigureSettings, + customPackageSettings, array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerLibrary, parallel, pretty, primitive, process, stm, templateHaskell, @@ -12,6 +12,7 @@ import Base hiding (arg, args) import Package import Switches import Expression +import Oracles.Builder -- Build results will be placed into a target directory with the following -- typical structure: @@ -79,15 +80,13 @@ integerLibraryCabal = case integerLibraryImpl of IntegerGmp2 -> "integer-gmp.cabal" -- Indeed, why make life easier? IntegerSimple -> "integer-simple.cabal" --- Custom configure settings for packages --- TODO: check if '--flag' and '--flags' should be collections of --- sub-arguments or not. -customConfigureSettings :: Settings -customConfigureSettings = mconcat +-- Custom package settings for packages +customPackageSettings :: Settings +customPackageSettings = builder GhcCabal ? mconcat [ package integerLibrary ? - windowsHost ? appendSub "--configure-option" ["--with-intree-gmp"] - , package base ? appendSub "--flags" [integerLibraryName] - , package ghcPrim ? appendSub "--flag" ["include-ghc-prim"] ] + windowsHost ? append ["--configure-option=--with-intree-gmp"] + , package base ? append ["--flags=" ++ integerLibraryName] + , package ghcPrim ? append ["--flag=include-ghc-prim"] ] -- Note [Cabal name weirdness] -- Find out if we can move the contents to just Cabal/ From git at git.haskell.org Thu Oct 26 23:11:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement appendCcArgs abstraction for passing arguments both to Gcc and GhcCabal. (ac4dab0) Message-ID: <20171026231144.DFDD83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ac4dab040a3eaeae26ed20198fce5fa00b0dda30/ghc >--------------------------------------------------------------- commit ac4dab040a3eaeae26ed20198fce5fa00b0dda30 Author: Andrey Mokhov Date: Mon Jun 15 01:47:05 2015 +0100 Implement appendCcArgs abstraction for passing arguments both to Gcc and GhcCabal. >--------------------------------------------------------------- ac4dab040a3eaeae26ed20198fce5fa00b0dda30 src/Settings/GhcCabal.hs | 12 +++++------- src/Settings/Util.hs | 8 ++++++++ src/Switches.hs | 5 ++++- src/Targets.hs | 16 +++++++++++----- 4 files changed, 28 insertions(+), 13 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index db972ac..21ca0e0 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -58,13 +58,13 @@ librarySettings = do configureSettings :: Settings configureSettings = do + stage <- asks getStage let conf key = appendSubD $ "--configure-option=" ++ key cFlags = mconcat [ ccSettings , remove ["-Werror"] , argStagedConfig "conf-cc-args" ] ldFlags = ldSettings <> argStagedConfig "conf-gcc-linker-args" cppFlags = cppSettings <> argStagedConfig "conf-cpp-args" - stage <- asks getStage mconcat [ conf "CFLAGS" cFlags , conf "LDFLAGS" ldFlags @@ -86,6 +86,7 @@ bootPackageDbSettings = do dllSettings :: Settings dllSettings = arg "" +-- TODO: remove with' :: Builder -> Settings with' builder = appendM $ with builder @@ -104,19 +105,16 @@ packageConstraints = do ++ cabal ++ "'." args $ concatMap (\c -> ["--constraint", c]) $ constraints +-- TODO: remove ccSettings :: Settings -ccSettings = do +ccSettings = validating ? do let gccGe46 = liftM not gccLt46 - mconcat - [ package integerLibrary ? arg "-Ilibraries/integer-gmp2/gmp" - , validating ? mconcat - [ arg "-Werror" + mconcat [ arg "-Werror" , arg "-Wall" , gccIsClang ?? ( arg "-Wno-unknown-pragmas" <> gccGe46 ? windowsHost ? arg "-Werror=unused-but-set-variable" , gccGe46 ? arg "-Wno-error=inline" )] - ] ldSettings :: Settings ldSettings = mempty diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index dbd07c0..f73f0f7 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -4,6 +4,7 @@ module Settings.Util ( -- Primitive settings elements arg, argM, args, argConfig, argStagedConfig, argConfigList, argStagedConfigList, + appendCcArgs, -- argBuilderPath, argStagedBuilderPath, -- argPackageKey, argPackageDeps, argPackageDepKeys, argSrcDirs, -- argIncludeDirs, argDepIncludeDirs, @@ -46,6 +47,13 @@ argStagedConfigList key = do stage <- asks getStage argConfigList (stagedKey stage key) +appendCcArgs :: [String] -> Settings +appendCcArgs args = do + stage <- asks getStage + mconcat [ builder (Gcc stage) ? append args + , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args + , builder GhcCabal ? appendSub "--gcc-options" args ] + -- packageData :: Arity -> String -> Settings -- packageData arity key = -- return $ EnvironmentParameter $ PackageData arity key Nothing Nothing diff --git a/src/Switches.hs b/src/Switches.hs index b67d9fc..0433682 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,6 +1,6 @@ module Switches ( IntegerLibraryImpl (..), integerLibraryImpl, - notStage, stage0, stage1, stage2, notBuilder, + notStage, stage0, stage1, stage2, builders, notBuilder, supportsPackageKey, targetPlatforms, targetPlatform, targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, @@ -31,6 +31,9 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 +builders :: [Builder] -> Predicate +builders = liftM or . sequence . map builder + notBuilder :: Builder -> Predicate notBuilder = liftM not . builder diff --git a/src/Targets.hs b/src/Targets.hs index c8aeb22..1839112 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -12,6 +12,7 @@ import Base hiding (arg, args) import Package import Switches import Expression +import Settings.Util import Oracles.Builder -- Build results will be placed into a target directory with the following @@ -80,13 +81,18 @@ integerLibraryCabal = case integerLibraryImpl of IntegerGmp2 -> "integer-gmp.cabal" -- Indeed, why make life easier? IntegerSimple -> "integer-simple.cabal" --- Custom package settings for packages customPackageSettings :: Settings -customPackageSettings = builder GhcCabal ? mconcat +customPackageSettings = mconcat [ package integerLibrary ? - windowsHost ? append ["--configure-option=--with-intree-gmp"] - , package base ? append ["--flags=" ++ integerLibraryName] - , package ghcPrim ? append ["--flag=include-ghc-prim"] ] + mconcat [ windowsHost ? builder GhcCabal ? + append ["--configure-option=--with-intree-gmp"] + , appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] ] + + , package base ? + builder GhcCabal ? append ["--flags=" ++ integerLibraryName] + + , package ghcPrim ? + builder GhcCabal ? append ["--flag=include-ghc-prim"] ] -- Note [Cabal name weirdness] -- Find out if we can move the contents to just Cabal/ From git at git.haskell.org Thu Oct 26 23:11:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused predicates notBuilder and builders. (af8520c) Message-ID: <20171026231148.56CA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/af8520cecee4facafffe20a85da550cb06f32c58/ghc >--------------------------------------------------------------- commit af8520cecee4facafffe20a85da550cb06f32c58 Author: Andrey Mokhov Date: Mon Jun 15 10:48:54 2015 +0100 Drop unused predicates notBuilder and builders. >--------------------------------------------------------------- af8520cecee4facafffe20a85da550cb06f32c58 src/Settings/Util.hs | 4 ++-- src/Switches.hs | 9 +-------- 2 files changed, 3 insertions(+), 10 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index f73f0f7..dba49d5 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -51,8 +51,8 @@ appendCcArgs :: [String] -> Settings appendCcArgs args = do stage <- asks getStage mconcat [ builder (Gcc stage) ? append args - , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args - , builder GhcCabal ? appendSub "--gcc-options" args ] + , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args + , builder GhcCabal ? appendSub "--gcc-options" args ] -- packageData :: Arity -> String -> Settings -- packageData arity key = diff --git a/src/Switches.hs b/src/Switches.hs index 0433682..eada97c 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,6 +1,6 @@ module Switches ( IntegerLibraryImpl (..), integerLibraryImpl, - notStage, stage0, stage1, stage2, builders, notBuilder, + notStage, stage0, stage1, stage2, supportsPackageKey, targetPlatforms, targetPlatform, targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, @@ -9,7 +9,6 @@ module Switches ( ) where import Base -import Oracles.Builder import Expression -- Support for multiple integer library implementations @@ -31,12 +30,6 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 -builders :: [Builder] -> Predicate -builders = liftM or . sequence . map builder - -notBuilder :: Builder -> Predicate -notBuilder = liftM not . builder - -- Predicates based on configuration files supportsPackageKey :: Predicate supportsPackageKey = configKeyYes "supports-package-key" From git at git.haskell.org Thu Oct 26 23:11:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an agenda for the meeting on 16 June 2015. (8f6fe55) Message-ID: <20171026231155.67E5E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f6fe558bf383f83f8cc8aa1d1e1858c25c06765/ghc >--------------------------------------------------------------- commit 8f6fe558bf383f83f8cc8aa1d1e1858c25c06765 Author: Andrey Mokhov Date: Tue Jun 16 01:08:05 2015 +0100 Add an agenda for the meeting on 16 June 2015. >--------------------------------------------------------------- 8f6fe558bf383f83f8cc8aa1d1e1858c25c06765 doc/meeting-16-June-2015.txt | 83 ++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 83 insertions(+) diff --git a/doc/meeting-16-June-2015.txt b/doc/meeting-16-June-2015.txt new file mode 100644 index 0000000..a407bb9 --- /dev/null +++ b/doc/meeting-16-June-2015.txt @@ -0,0 +1,83 @@ +Shaking up GHC (3rd shake) meeting, 16 June 2015 + +Things to discuss: +================================================ + +1. Parameters of the build system that are still not user configurable: + +* targetDirectory (Targets.hs) -- is this important? Can be moved to +UserSettings.hs, but will clutter it (what is the good balance of +what we expose to users?). Can be made into a conditional expression +similar to userWays, userPackages and userSettings, but is it worth it? + +* knownPackages (Targets.hs) -- fix by adding knownUserPackages? A nasty +import cycle is then created between Targets.hs and UserSettings.hs + +* integerLibraryImpl (Switches.hs) -- fix by having three integer library +packages in Targets.hs and choosing which one to build in userPackages, e.g.: + +userPackages = remove [integerGmp2] <> append [integerSimple] + +* In general, should Targets.hs be editable by users as well? Ideally, +there should only be one place for user to look: UserSettings.hs. + +* Any other parameters I missed which should be user configurable? + +================================================ + +2. When predicates are moved from configuration files to UserSettings we +no longer track their state in oracles. This may lead to inconsistent +state of the build system. A more general problem: how do we accurately +track changes in the build systems, specifically in UserSettings.hs? + +================================================ + +3. Discuss if the current design makes recording provenance information +possible. (Should probably be implemented only after the first successful +complete build though.) + +============================================== + +4. I'd like interpret/interpretDiff to be total functions. It should be +possible to check at compile which questions a given environment can +answer and raise an error if an expression needs to know more. + +For example, consider an environment envS that can only answer 'getStage' +question, and environment envSP that can answer questions 'getStage' and +'getPackage'. Now consider two expressions + +exprS = stage0 ? foo + +exprSP = stage0 ? package base ? bar + +Now I'd like the following to produce a compile error: + +interpret envS exprSP + +However, all other combinations should be fine: + +interpret envS exprS +interpret envSP exprS +interpret envSP exprSP + +I played with some possible solutions using type classes, but they all +seem clumsy/heavy. + +Hence, for now I have: + +data Environment = Environment + { + getStage :: Stage, + getBuilder :: Builder, + getPackage :: Package + } + +defaultEnvironment :: Environment +defaultEnvironment = Environment + { + getStage = error "Stage not set in the environment", + getBuilder = error "Builder not set in the environment", + getPackage = error "Package not set in the environment" + } + +which leads to a lot of partial functions all over the build system. \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:11:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, move derived predicates to Switches.hs. (7e62041) Message-ID: <20171026231151.F37EB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e62041bd01856a4920e51028a2f3bbe161374c6/ghc >--------------------------------------------------------------- commit 7e62041bd01856a4920e51028a2f3bbe161374c6 Author: Andrey Mokhov Date: Tue Jun 16 00:00:19 2015 +0100 Add comments, move derived predicates to Switches.hs. >--------------------------------------------------------------- 7e62041bd01856a4920e51028a2f3bbe161374c6 src/Expression.hs | 54 ++++++++++++++++++++++++++++++------------------------ src/Switches.hs | 10 ++++++++++ 2 files changed, 40 insertions(+), 24 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index d147280..81ed26f 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -9,8 +9,7 @@ module Expression ( append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, interpret, interpretDiff, applyPredicate, (?), (??), stage, builder, package, - configKeyValue, configKeyValues, - configKeyYes, configKeyNo, configKeyNonEmpty + configKeyValue, configKeyValues ) where import Base hiding (arg, args, Args, TargetDir) @@ -25,8 +24,11 @@ data Environment = Environment getStage :: Stage, getBuilder :: Builder, getPackage :: Package + -- getWay :: Way, and maybe something else will be useful later } +-- TODO: all readers are currently partial functions. Can use type classes to +-- guarantee these errors never occur. defaultEnvironment :: Environment defaultEnvironment = Environment { @@ -48,15 +50,31 @@ instance Monoid a => Monoid (Expr a) where mempty = return mempty mappend = liftM2 mappend +-- Basic operations on expressions: +-- 1) append something to an expression append :: Monoid a => a -> DiffExpr a append x = return . Dual . Endo $ (<> x) -appendM :: Monoid a => Action a -> DiffExpr a -appendM mx = lift mx >>= append - +-- 2) remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] remove xs = return . Dual . Endo $ filter (`notElem` xs) +-- 3) apply a predicate to an expression +applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a +applyPredicate predicate expr = do + bool <- predicate + if bool then expr else return mempty + +-- A convenient operator for predicate application +(?) :: Monoid a => Predicate -> Expr a -> Expr a +(?) = applyPredicate + +infixr 8 ? + +-- A monadic version of append +appendM :: Monoid a => Action a -> DiffExpr a +appendM mx = lift mx >>= append + -- appendSub appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument -- of the form 'prefix=listOfSubarguments' is appended to the expression. @@ -85,31 +103,28 @@ filterSub prefix p = return . Dual . Endo $ map filterSubstr | prefix `isPrefixOf` s = unwords . filter p . words $ s | otherwise = s +-- remove given elements from a list of sub-arguments with a given prefix +-- Example: removeSub "--configure-option=CFLAGS" ["-Werror"] removeSub :: String -> [String] -> Settings removeSub prefix xs = filterSub prefix (`notElem` xs) +-- Interpret a given expression in a given environment interpret :: Environment -> Expr a -> Action a interpret = flip runReaderT +-- Extract an expression from a difference expression fromDiff :: Monoid a => DiffExpr a -> Expr a fromDiff = fmap (($ mempty) . appEndo . getDual) +-- Interpret a given difference expression in a given environment interpretDiff :: Monoid a => Environment -> DiffExpr a -> Action a interpretDiff env = interpret env . fromDiff -applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a -applyPredicate predicate expr = do - bool <- predicate - if bool then expr else return mempty - -(?) :: Monoid a => Predicate -> Expr a -> Expr a -(?) = applyPredicate - +-- An equivalent of if-then-else for predicates (??) :: Monoid a => Predicate -> (Expr a, Expr a) -> Expr a p ?? (t, f) = p ? t <> (liftM not p) ? f -infixr 8 ? - +-- Basic predicates stage :: Stage -> Predicate stage s = liftM (s ==) (asks getStage) @@ -125,12 +140,3 @@ configKeyValue key value = liftM (value ==) (lift $ askConfig key) -- checks if there is at least one match configKeyValues :: String -> [String] -> Predicate configKeyValues key values = liftM (`elem` values) (lift $ askConfig key) - -configKeyYes :: String -> Predicate -configKeyYes key = configKeyValue key "YES" - -configKeyNo :: String -> Predicate -configKeyNo key = configKeyValue key "NO" - -configKeyNonEmpty :: String -> Predicate -configKeyNonEmpty key = liftM not $ configKeyValue key "" diff --git a/src/Switches.hs b/src/Switches.hs index eada97c..5436d94 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,6 +1,7 @@ module Switches ( IntegerLibraryImpl (..), integerLibraryImpl, notStage, stage0, stage1, stage2, + configKeyYes, configKeyNo, configKeyNonEmpty, supportsPackageKey, targetPlatforms, targetPlatform, targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, @@ -30,6 +31,15 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 +configKeyYes :: String -> Predicate +configKeyYes key = configKeyValue key "YES" + +configKeyNo :: String -> Predicate +configKeyNo key = configKeyValue key "NO" + +configKeyNonEmpty :: String -> Predicate +configKeyNonEmpty key = liftM not $ configKeyValue key "" + -- Predicates based on configuration files supportsPackageKey :: Predicate supportsPackageKey = configKeyYes "supports-package-key" From git at git.haskell.org Thu Oct 26 23:11:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:11:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. Minor refactoring. (acde0ea) Message-ID: <20171026231158.CCEE53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acde0ea23775e06a4cfd2f60974c075e8babdc86/ghc >--------------------------------------------------------------- commit acde0ea23775e06a4cfd2f60974c075e8babdc86 Author: Andrey Mokhov Date: Tue Jun 16 01:09:37 2015 +0100 Add comments. Minor refactoring. >--------------------------------------------------------------- acde0ea23775e06a4cfd2f60974c075e8babdc86 src/Expression.hs | 5 +++-- src/Rules.hs | 3 +-- src/Settings.hs | 1 + src/Settings/GhcCabal.hs | 2 +- src/Settings/Util.hs | 5 +++++ src/Switches.hs | 2 ++ src/Targets.hs | 7 ++++--- src/UserSettings.hs | 7 ++++++- 8 files changed, 23 insertions(+), 9 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 81ed26f..a0c3bf0 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -124,7 +124,7 @@ interpretDiff env = interpret env . fromDiff (??) :: Monoid a => Predicate -> (Expr a, Expr a) -> Expr a p ?? (t, f) = p ? t <> (liftM not p) ? f --- Basic predicates +-- Basic predicates (see Switches.hs for derived predicates) stage :: Stage -> Predicate stage s = liftM (s ==) (asks getStage) @@ -137,6 +137,7 @@ package p = liftM (p ==) (asks getPackage) configKeyValue :: String -> String -> Predicate configKeyValue key value = liftM (value ==) (lift $ askConfig key) --- checks if there is at least one match +-- Check if there is at least one match +-- Example: configKeyValues "host-os-cpp" ["mingw32", "cygwin32"] configKeyValues :: String -> [String] -> Predicate configKeyValues key values = liftM (`elem` values) (lift $ askConfig key) diff --git a/src/Rules.hs b/src/Rules.hs index 5d59ae6..a84f30e 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -13,7 +13,7 @@ import Rules.Package import Settings.Packages -- generateTargets needs package-data.mk files of all target packages --- TODO: make interpret total +-- TODO: make interpretDiff total generateTargets :: Rules () generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do @@ -23,7 +23,6 @@ generateTargets = action $ let dir = targetDirectory stage pkg need [pkgPath pkg dir "package-data.mk"] --- TODO: make interpret total -- TODO: add Stage2 (compiler only?) packageRules :: Rules () packageRules = diff --git a/src/Settings.hs b/src/Settings.hs index cde678e..fb0938a 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -12,6 +12,7 @@ import Expression hiding (when, liftIO) settings :: Settings settings = defaultSettings <> userSettings +-- TODO: add all other settings defaultSettings :: Settings defaultSettings = mconcat [ cabalSettings diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 21ca0e0..4388b17 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -105,7 +105,7 @@ packageConstraints = do ++ cabal ++ "'." args $ concatMap (\c -> ["--constraint", c]) $ constraints --- TODO: remove +-- TODO: should be in a different file ccSettings :: Settings ccSettings = validating ? do let gccGe46 = liftM not gccLt46 diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index dba49d5..74190ec 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -47,6 +47,7 @@ argStagedConfigList key = do stage <- asks getStage argConfigList (stagedKey stage key) +-- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal appendCcArgs :: [String] -> Settings appendCcArgs args = do stage <- asks getStage @@ -54,6 +55,10 @@ appendCcArgs args = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args , builder GhcCabal ? appendSub "--gcc-options" args ] + + + + -- packageData :: Arity -> String -> Settings -- packageData arity key = -- return $ EnvironmentParameter $ PackageData arity key Nothing Nothing diff --git a/src/Switches.hs b/src/Switches.hs index 5436d94..3c6abac 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -12,6 +12,8 @@ module Switches ( import Base import Expression +-- TODO: This setting should be moved to UserSettings.hs +-- TODO: Define three packages for integer library instead of one in Targets.hs -- Support for multiple integer library implementations data IntegerLibraryImpl = IntegerGmp | IntegerGmp2 | IntegerSimple diff --git a/src/Targets.hs b/src/Targets.hs index 1839112..2c61152 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -20,6 +20,7 @@ import Oracles.Builder -- * build/ : contains compiled object code -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal +-- TODO: This is currently not user configurable. Is this right? targetDirectory :: Stage -> Package -> FilePath targetDirectory stage package | package == compiler = "stage" ++ show (fromEnum stage + 1) @@ -85,14 +86,14 @@ customPackageSettings :: Settings customPackageSettings = mconcat [ package integerLibrary ? mconcat [ windowsHost ? builder GhcCabal ? - append ["--configure-option=--with-intree-gmp"] + arg "--configure-option=--with-intree-gmp" , appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] ] , package base ? - builder GhcCabal ? append ["--flags=" ++ integerLibraryName] + builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) , package ghcPrim ? - builder GhcCabal ? append ["--flag=include-ghc-prim"] ] + builder GhcCabal ? arg "--flag=include-ghc-prim" ] -- Note [Cabal name weirdness] -- Find out if we can move the contents to just Cabal/ diff --git a/src/UserSettings.hs b/src/UserSettings.hs index f443659..378db1c 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -10,18 +10,23 @@ import Ways import Targets import Switches import Expression +import Settings.Util -- No user-specific settings by default userSettings :: Settings userSettings = mempty +-- Control conditions of which packages get to be built +-- TODO: adding *new* packages is not possible (see knownPackages in Targets.hs) userPackages :: Packages userPackages = mempty +-- Control which ways are built userWays :: Ways userWays = mempty -- User-defined predicates +-- TODO: migrate more predicates here from configuration files buildHaddock :: Predicate buildHaddock = return True @@ -31,7 +36,7 @@ validating = return False -- Examples: userSettings' :: Settings userSettings' = mconcat - [ package compiler ? stage0 ? append ["foo", "bar"] + [ package compiler ? stage0 ? arg "foo" , builder (Ghc Stage0) ? remove ["-O2"] , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] From git at git.haskell.org Thu Oct 26 23:12:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add getFile and getWay to Environment. (2f373e4) Message-ID: <20171026231202.540C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f373e4ab96d1eab13b9e358c39170684a34fa1e/ghc >--------------------------------------------------------------- commit 2f373e4ab96d1eab13b9e358c39170684a34fa1e Author: Andrey Mokhov Date: Tue Jun 16 07:48:23 2015 +0100 Add getFile and getWay to Environment. >--------------------------------------------------------------- 2f373e4ab96d1eab13b9e358c39170684a34fa1e doc/meeting-16-June-2015.txt | 51 +++++++++++++++++++++++++++++++++----------- src/Expression.hs | 21 ++++++++++++------ src/Targets.hs | 1 + src/UserSettings.hs | 22 +++++++++++++++---- 4 files changed, 72 insertions(+), 23 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 2f373e4ab96d1eab13b9e358c39170684a34fa1e From git at git.haskell.org Thu Oct 26 23:12:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename appendCcArgs to ccArgs. (56cf235) Message-ID: <20171026231205.C4C353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56cf235d4dd89316597abb5024af57756b1fc47e/ghc >--------------------------------------------------------------- commit 56cf235d4dd89316597abb5024af57756b1fc47e Author: Andrey Mokhov Date: Tue Jun 16 07:52:33 2015 +0100 Rename appendCcArgs to ccArgs. >--------------------------------------------------------------- 56cf235d4dd89316597abb5024af57756b1fc47e src/Settings/Util.hs | 6 +++--- src/Targets.hs | 2 +- src/UserSettings.hs | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 74190ec..e9433a2 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -4,7 +4,7 @@ module Settings.Util ( -- Primitive settings elements arg, argM, args, argConfig, argStagedConfig, argConfigList, argStagedConfigList, - appendCcArgs, + ccArgs, -- argBuilderPath, argStagedBuilderPath, -- argPackageKey, argPackageDeps, argPackageDepKeys, argSrcDirs, -- argIncludeDirs, argDepIncludeDirs, @@ -48,8 +48,8 @@ argStagedConfigList key = do argConfigList (stagedKey stage key) -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal -appendCcArgs :: [String] -> Settings -appendCcArgs args = do +ccArgs :: [String] -> Settings +ccArgs args = do stage <- asks getStage mconcat [ builder (Gcc stage) ? append args , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args diff --git a/src/Targets.hs b/src/Targets.hs index 4bbb963..068e767 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -88,7 +88,7 @@ customPackageSettings = mconcat [ package integerLibrary ? mconcat [ windowsHost ? builder GhcCabal ? arg "--configure-option=--with-intree-gmp" - , appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] ] + , ccArgs ["-Ilibraries/integer-gmp2/gmp"] ] , package base ? builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 3cbf136..52d9678 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -38,7 +38,7 @@ userSettings' = mconcat [ package base ? builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) - , package integerLibrary ? appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] + , package integerLibrary ? ccArgs ["-Ilibraries/integer-gmp2/gmp"] , windowsHost ? package integerLibrary ? From git at git.haskell.org Thu Oct 26 23:12:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finalise meeting agenda. (7d53e6b) Message-ID: <20171026231209.3775E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d53e6b43cc5a0280218c12fab1a16bf9fcc2f1c/ghc >--------------------------------------------------------------- commit 7d53e6b43cc5a0280218c12fab1a16bf9fcc2f1c Author: Andrey Mokhov Date: Tue Jun 16 09:53:30 2015 +0100 Finalise meeting agenda. >--------------------------------------------------------------- 7d53e6b43cc5a0280218c12fab1a16bf9fcc2f1c doc/meeting-16-June-2015.txt | 54 ++++++++++++++++++++++++++++++++++++-------- 1 file changed, 44 insertions(+), 10 deletions(-) diff --git a/doc/meeting-16-June-2015.txt b/doc/meeting-16-June-2015.txt index bd2b94f..d58b541 100644 --- a/doc/meeting-16-June-2015.txt +++ b/doc/meeting-16-June-2015.txt @@ -13,45 +13,76 @@ similar to userWays, userPackages and userSettings, but is it worth it? * knownPackages (Targets.hs) -- fix by adding knownUserPackages? A nasty import cycle is then created between Targets.hs and UserSettings.hs. Possible solution: add file Settings/Targets.hs which will actually put two things -together similar to what's done with userWays, userPackages and userSettings. +together similar to how it's done with userWays, userPackages and userSettings. * integerLibraryImpl (Switches.hs) -- fix by having three integer library packages in Targets.hs and choosing which one to build in userPackages, e.g.: userPackages = remove [integerGmp2] <> append [integerSimple] -* In general, should Targets.hs be editable by users as well? Ideally, -there should only be one place for user to look: UserSettings.hs. +(Maybe a useful pattern: replace a b = remove a <> append b.) + +* In general, should Targets.hs (or any other file) be editable by users? +Ideally, there should only be one place for users to look: UserSettings.hs. * Any other parameters I missed which should be user configurable? ================================================ 2. When predicates (e.g. buildHaddock) are moved from configuration files to -UserSettings we no longer track their state in oracles. This may lead to an +UserSettings.hs we no longer track their state in oracles. This may lead to an inconsistent state of the build system. This is a special case of a more general problem: how do we accurately track changes in the build system, specifically in UserSettings.hs? Although in general this is a hard problem, this special -case may be easier to solve: just channel everything exported from +case may be easier to solve: e.g., just channel everything exported from UserSettings.hs through oracles? Another alternative which was discussed previously: pass the final lists of arguments through oracles. Care must -be taken though as final command lines can be as large as 5Mb! +be taken though as final command lines can be as large as 5Mb and may bloat +the Shake database! ================================================ -3. Discuss if the current design makes recording provenance information +3. Discuss if/how the current approach makes recording provenance information possible. (Should probably be implemented only after the first successful complete build though.) ============================================== -4. I'd like interpret/interpretDiff to be total functions. It should be +4. Duplication of information in knownPackages and packages. + +I'd like to enforce the following invariant: whenever a package is used +in userPackages, it must also be placed in knownPackages/knownUserPackages. + +This feels awkward/redundant. The reason for having knownPackages is that I +need a list of packages outside the Action monad for it to be useable in +packageRules (see Rules.hs). The current solution seems to be the cheapest way +to achieve that. An alternative would be to have one additional implementation +of interpret, which would extract the 'support' from a given expression, i.e. +the set of packages that can occur in a given expression, regardless of how +predicates evaluate (without looking up oracles which live in the Action monad). + +For example, + +interpret' (stage0 ? base <> stage1 ? compiler) == [base, compiler] + +This seems to require a lot of extra code though. Hence redundant knownPackages. + +============================================== + +5. (Just realised that the following is trickier than I thought. Maybe not +worth raising at this meeting if not enough time.) + +I'd like interpret/interpretDiff to be total functions. It should be possible to check at compile which questions a given environment can -answer and raise a *compile* error if the expression needs to know more. +answer and raise a *compile* error if the expression needs to know more. Why +is this useful? For example, I'd like to allow only getStage and +platform-specific predicates in userPackages (since nothing else is known at +this point; one can argue that we should even forbid to use such predicates +when constructing expressions of type Packages). For example, consider an environment envS that can only answer 'getStage' question, and environment envSP that can answer questions 'getStage' and -'getPackage'. Now consider two expressions +'getPackage'. Now consider two expressions: exprS = stage0 ? arg "foo" @@ -106,3 +137,6 @@ getPackage, getBuilder, getFile, getWay. Hence, it may be OK to have only 6 combinations of getters in a type constraint, not 2^5, e.g.: empty, GetStage env, (GetStage env, GetPackage env), etc. +============================================== + + From git at git.haskell.org Thu Oct 26 23:12:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make targetDirectory and knownPackages configurable, rename Environment to Target. (418a1cd) Message-ID: <20171026231216.285D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/418a1cd630e1c2eb6e467e502d615ae4307113b7/ghc >--------------------------------------------------------------- commit 418a1cd630e1c2eb6e467e502d615ae4307113b7 Author: Andrey Mokhov Date: Sun Jul 12 23:12:39 2015 +0100 Make targetDirectory and knownPackages configurable, rename Environment to Target. >--------------------------------------------------------------- 418a1cd630e1c2eb6e467e502d615ae4307113b7 doc/meeting-16-June-2015.txt | 22 ++++++++++++- src/Expression.hs | 72 ++++++++++++++++++++++++----------------- src/Package.hs | 1 + src/Rules.hs | 8 ++--- src/Rules/Data.hs | 22 ++++++------- src/Rules/Package.hs | 2 +- src/Settings.hs | 1 - src/Settings/GhcCabal.hs | 20 ++++++++++-- src/Settings/GhcPkg.hs | 2 +- src/Settings/Packages.hs | 18 ++++++++++- src/Settings/TargetDirectory.hs | 11 +++++++ src/Settings/Util.hs | 9 +++--- src/Switches.hs | 9 ------ src/Targets.hs | 59 +++++---------------------------- src/UserSettings.hs | 54 ++++++++++--------------------- 15 files changed, 155 insertions(+), 155 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 418a1cd630e1c2eb6e467e502d615ae4307113b7 From git at git.haskell.org Thu Oct 26 23:12:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (b2b7c5c) Message-ID: <20171026231212.9BC873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2b7c5c53ed5369249ebff39aa8735a897ad86a9/ghc >--------------------------------------------------------------- commit b2b7c5c53ed5369249ebff39aa8735a897ad86a9 Author: Andrey Mokhov Date: Tue Jun 16 09:54:10 2015 +0100 Add comments. >--------------------------------------------------------------- b2b7c5c53ed5369249ebff39aa8735a897ad86a9 src/Expression.hs | 2 +- src/Rules/Data.hs | 70 ++++++++++++++---------------------------------- src/Settings/GhcCabal.hs | 3 +++ 3 files changed, 24 insertions(+), 51 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 9232aed..4809324 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -24,7 +24,7 @@ data Environment = Environment getStage :: Stage, getPackage :: Package, getBuilder :: Builder, - getFile :: FilePath, + getFile :: FilePath, -- TODO: handle multple files? getWay :: Way } diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index aa1ebab..3754cdc 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -13,29 +13,6 @@ import Settings.GhcPkg import Settings.GhcCabal import Util --- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: --- 1) Drop lines containing '$' --- For example, get rid of --- libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ... --- Reason: we don't need them and we can't parse them. --- 2) Replace '/' and '\' with '_' before '=' --- For example libraries/deepseq/dist-install_VERSION = 1.4.0.0 --- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 --- Reason: Shake's built-in makefile parser doesn't recognise slashes - -postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map processLine pkgData - where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line - --- this is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument --- * otherwise, we must collapse it into one space-separated string - -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: Environment -> Rules () buildPackageData env = @@ -53,6 +30,8 @@ buildPackageData env = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" + -- TODO: 1) how to automate this? 2) handle multiple files? + newEnv = env { getFile = dir "package-data.mk" } -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac @@ -62,37 +41,28 @@ buildPackageData env = run' env (GhcPkg stage) postProcessPackageData $ dir "package-data.mk" +-- TODO: This should probably go to Oracles.Builder run' :: Environment -> Builder -> Action () run' env builder = do args <- interpret (env {getBuilder = builder}) $ fromDiff settings putColoured Green (show args) run builder args ---buildRule :: Package -> TodoItem -> Rules () ---buildRule pkg @ (Package name path cabal _) todo @ (stage, dist, settings) = --- let pathDist = path dist --- cabalPath = path cabal --- configure = path "configure" --- in --- -- All these files are produced by a single run of GhcCabal --- (pathDist ) <$> --- [ "package-data.mk" --- , "haddock-prologue.txt" --- , "inplace-pkg-config" --- , "setup-config" --- , "build" "autogen" "cabal_macros.h" --- -- TODO: Is this needed? Also check out Paths_cpsa.hs. --- -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" --- ] &%> \_ -> do --- need [cabalPath] --- when (doesFileExist $ configure <.> "ac") $ need [configure] --- -- GhcCabal will run the configure script, so we depend on it --- -- We still don't know who build the configure script from configure.ac --- run GhcCabal $ cabalArgs pkg todo --- when (registerPackage settings) $ --- run (GhcPkg stage) $ ghcPkgArgs pkg todo --- postProcessPackageData $ pathDist "package-data.mk" - --- buildSettings = + builder Gcc ? ccSettings +-- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: +-- 1) Drop lines containing '$' +-- For example, get rid of +-- libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ... +-- Reason: we don't need them and we can't parse them. +-- 2) Replace '/' and '\' with '_' before '=' +-- For example libraries/deepseq/dist-install_VERSION = 1.4.0.0 +-- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 +-- Reason: Shake's built-in makefile parser doesn't recognise slashes --- builder Gcc ? "-tricky-flag" +postProcessPackageData :: FilePath -> Action () +postProcessPackageData file = do + pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) + length pkgData `seq` writeFileLines file $ map processLine pkgData + where + processLine line = replaceSeparators '_' prefix ++ suffix + where + (prefix, suffix) = break (== '=') line diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 4388b17..4cbb0a3 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -83,6 +83,9 @@ bootPackageDbSettings = do sourcePath <- lift $ askConfig "ghc-source-path" arg $ "--package-db=" ++ sourcePath "libraries/bootstrapping.conf" +-- this is a positional argument, hence: +-- * if it is empty, we need to emit one empty string argument +-- * otherwise, we must collapse it into one space-separated string dllSettings :: Settings dllSettings = arg "" From git at git.haskell.org Thu Oct 26 23:12:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, rename interpretDiff to interpret. (238398a) Message-ID: <20171026231219.A05A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/238398a839967ceb0dfc8f6e013a23f8551d67f5/ghc >--------------------------------------------------------------- commit 238398a839967ceb0dfc8f6e013a23f8551d67f5 Author: Andrey Mokhov Date: Mon Jul 13 16:13:58 2015 +0100 Add comments, rename interpretDiff to interpret. >--------------------------------------------------------------- 238398a839967ceb0dfc8f6e013a23f8551d67f5 src/Expression.hs | 51 +++++++++++++++++++++++++++++++++++---------------- src/Rules.hs | 2 +- src/Rules/Data.hs | 2 +- 3 files changed, 37 insertions(+), 18 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 46b3c40..88561eb 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -7,7 +7,7 @@ module Expression ( Settings, Ways, Packages, Target (..), stageTarget, stagePackageTarget, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, - interpret, interpretDiff, + interpret, interpretExpr, applyPredicate, (?), (??), stage, package, builder, file, way, configKeyValue, configKeyValues ) where @@ -19,6 +19,9 @@ import Package import Data.Monoid import Control.Monad.Reader +-- Target captures parameters relevant to the current build target: Stage and +-- Package being built, Builder that is to be invoked, file(s) that are to +-- be built and the Way they are to be built. data Target = Target { getStage :: Stage, @@ -48,24 +51,40 @@ stagePackageTarget stage package = Target getWay = error "stagePackageTarget: Way not set" } +-- Expr a is a computation that produces a value of type Action a and can read +-- parameters of the current build Target. +type Expr a = ReaderT Target Action a + +-- If values of type a form a Monoid then so do computations of type Expr a: +-- * the empty computation returns the identity element of the underlying type +-- * two computations can be combined by combining their results +instance Monoid a => Monoid (Expr a) where + mempty = return mempty + mappend = liftM2 mappend + +-- Diff a holds functions of type a -> a and is equipped with a Monoid instance. -- We could use Dual (Endo a) instead of Diff a, but the former may look scary. +-- The name comes from "difference lists". newtype Diff a = Diff { fromDiff :: a -> a } +-- DiffExpr a is a computation that builds a difference list (i.e., a function +-- of type Action (a -> a)) and can read parameters of the current build Target. +type DiffExpr a = Expr (Diff a) + +-- Note the reverse order of function composition (y . x), which ensures that +-- when two DiffExpr computations c1 and c2 are combined (c1 <> c2), then c1 is +-- applied first, and c2 is applied second. instance Monoid (Diff a) where mempty = Diff id Diff x `mappend` Diff y = Diff $ y . x -type Expr a = ReaderT Target Action a -type DiffExpr a = Expr (Diff a) - -type Predicate = Expr Bool -type Settings = DiffExpr [String] -- TODO: rename to Args -type Ways = DiffExpr [Way] -type Packages = DiffExpr [Package] - -instance Monoid a => Monoid (Expr a) where - mempty = return mempty - mappend = liftM2 mappend +-- The following expressions are used throughout the build system for +-- specifying conditions (Predicate), lists of arguments (Settings), Ways and +-- Packages. +type Predicate = Expr Bool +type Settings = DiffExpr [String] -- TODO: rename to Args +type Ways = DiffExpr [Way] +type Packages = DiffExpr [Package] -- Basic operations on expressions: -- 1) append something to an expression @@ -126,16 +145,16 @@ removeSub :: String -> [String] -> Settings removeSub prefix xs = filterSub prefix (`notElem` xs) -- Interpret a given expression in a given environment -interpret :: Target -> Expr a -> Action a -interpret = flip runReaderT +interpretExpr :: Target -> Expr a -> Action a +interpretExpr = flip runReaderT -- Extract an expression from a difference expression fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) -- Interpret a given difference expression in a given environment -interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a -interpretDiff target = interpret target . fromDiffExpr +interpret :: Monoid a => Target -> DiffExpr a -> Action a +interpret target = interpretExpr target . fromDiffExpr -- An equivalent of if-then-else for predicates (??) :: Monoid a => Predicate -> (Expr a, Expr a) -> Expr a diff --git a/src/Rules.hs b/src/Rules.hs index 6e1093b..852a6cf 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -17,7 +17,7 @@ import Settings.TargetDirectory generateTargets :: Rules () generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do - pkgs <- interpretDiff (stageTarget stage) packages + pkgs <- interpret (stageTarget stage) packages forM_ pkgs $ \pkg -> do let dir = targetDirectory stage pkg need [pkgPath pkg dir "package-data.mk"] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 20f05f5..d608fea 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -44,7 +44,7 @@ buildPackageData target = -- TODO: This should probably go to Oracles.Builder run' :: Target -> Builder -> Action () run' target builder = do - args <- interpret (target {getBuilder = builder}) $ fromDiffExpr settings + args <- interpret (target {getBuilder = builder}) settings putColoured Green (show args) run builder args From git at git.haskell.org Thu Oct 26 23:12:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add argWith. (cbda822) Message-ID: <20171026231223.0CBCA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbda8225449ac1ed80f64843f4fc58390e113994/ghc >--------------------------------------------------------------- commit cbda8225449ac1ed80f64843f4fc58390e113994 Author: Andrey Mokhov Date: Mon Jul 13 16:42:04 2015 +0100 Add argWith. >--------------------------------------------------------------- cbda8225449ac1ed80f64843f4fc58390e113994 src/Oracles/Builder.hs | 7 +++---- src/Settings/GhcCabal.hs | 20 ++++++++------------ src/Settings/Util.hs | 5 ++++- 3 files changed, 15 insertions(+), 17 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 316217f..1f3e45a 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -12,8 +12,7 @@ import Oracles.Base import Oracles.Flag import Oracles.Option --- A Builder is an external command invoked in separate process --- by calling Shake.cmd +-- A Builder is an external command invoked in separate process using Shake.cmd -- -- Ghc Stage0 is the bootstrapping compiler -- Ghc StageN, N > 0, is the one built on stage (N - 1) @@ -82,11 +81,11 @@ needBuilder builder = do need [exe] -- Action 'with Gcc' returns '--with-gcc=/path/to/gcc' and needs Gcc -with :: Builder -> Args +with :: Builder -> Action String with builder = do exe <- showArg builder needBuilder builder - return [withBuilderKey builder ++ exe] + return $ withBuilderKey builder ++ exe withBuilderKey :: Builder -> String withBuilderKey builder = case builder of diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index d8eda6a..db8fd6e 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -25,18 +25,18 @@ cabalSettings = builder GhcCabal ? do , arg $ pkgPath pkg , arg $ targetDirectory stage pkg , dllSettings - , with' $ Ghc stage - , with' $ GhcPkg stage + , argWith $ Ghc stage + , argWith $ GhcPkg stage , stage0 ? bootPackageDbSettings , librarySettings - , configKeyNonEmpty "hscolour" ? with' HsColour -- TODO: generalise? + , configKeyNonEmpty "hscolour" ? argWith HsColour -- TODO: generalise? , configureSettings , stage0 ? packageConstraints - , with' $ Gcc stage - , notStage Stage0 ? with' Ld - , with' Ar - , with' Alex - , with' Happy ] -- TODO: reorder with's + , argWith $ Gcc stage + , notStage Stage0 ? argWith Ld + , argWith Ar + , argWith Alex + , argWith Happy ] -- TODO: reorder argWiths -- TODO: Isn't vanilla always built? If yes, some conditions are redundant. librarySettings :: Settings @@ -90,10 +90,6 @@ bootPackageDbSettings = do dllSettings :: Settings dllSettings = arg "" --- TODO: remove -with' :: Builder -> Settings -with' builder = appendM $ with builder - packageConstraints :: Settings packageConstraints = do pkgs <- fromDiffExpr packages diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 4b22be4..d7bfa49 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -2,7 +2,7 @@ module Settings.Util ( -- Primitive settings elements - arg, argM, args, + arg, argM, args, argWith, argConfig, argStagedConfig, argConfigList, argStagedConfigList, ccArgs, -- argBuilderPath, argStagedBuilderPath, @@ -28,6 +28,9 @@ argM = appendM . fmap return args :: [String] -> Settings args = append +argWith :: Builder -> Settings +argWith = argM . with + argConfig :: String -> Settings argConfig = appendM . fmap return . askConfig From git at git.haskell.org Thu Oct 26 23:12:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (f62f166) Message-ID: <20171026231226.7349E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f62f166802cf0aa26ce72bb29b073d184897a512/ghc >--------------------------------------------------------------- commit f62f166802cf0aa26ce72bb29b073d184897a512 Author: Andrey Mokhov Date: Mon Jul 13 16:56:48 2015 +0100 Clean up. >--------------------------------------------------------------- f62f166802cf0aa26ce72bb29b073d184897a512 src/Settings/GhcCabal.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index db8fd6e..8e1a8cf 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -10,7 +10,7 @@ import Util import Package import Targets import Switches -import Expression hiding (when, liftIO) +import Expression hiding (liftIO) import Settings.Ways import Settings.Util import Settings.Packages @@ -29,14 +29,14 @@ cabalSettings = builder GhcCabal ? do , argWith $ GhcPkg stage , stage0 ? bootPackageDbSettings , librarySettings - , configKeyNonEmpty "hscolour" ? argWith HsColour -- TODO: generalise? + , configKeyNonEmpty "hscolour" ? argWith HsColour , configureSettings , stage0 ? packageConstraints , argWith $ Gcc stage , notStage Stage0 ? argWith Ld , argWith Ar , argWith Alex - , argWith Happy ] -- TODO: reorder argWiths + , argWith Happy ] -- TODO: Isn't vanilla always built? If yes, some conditions are redundant. librarySettings :: Settings @@ -84,9 +84,9 @@ bootPackageDbSettings = do sourcePath <- lift $ askConfig "ghc-source-path" arg $ "--package-db=" ++ sourcePath "libraries/bootstrapping.conf" --- this is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument --- * otherwise, we must collapse it into one space-separated string +-- This is a positional argument, hence: +-- * if it is empty, we need to emit one empty string argument; +-- * otherwise, we must collapse it into one space-separated string. dllSettings :: Settings dllSettings = arg "" From git at git.haskell.org Thu Oct 26 23:12:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add targetPath. (35d9a07) Message-ID: <20171026231230.1572B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/35d9a0726b9751c29c8f0250bd925f84074cc3b2/ghc >--------------------------------------------------------------- commit 35d9a0726b9751c29c8f0250bd925f84074cc3b2 Author: Andrey Mokhov Date: Mon Jul 13 22:24:50 2015 +0100 Add targetPath. >--------------------------------------------------------------- 35d9a0726b9751c29c8f0250bd925f84074cc3b2 src/Rules.hs | 4 +--- src/Rules/Data.hs | 8 ++++---- src/Settings/GhcCabal.hs | 1 + src/Settings/GhcPkg.hs | 4 +--- src/Settings/TargetDirectory.hs | 6 +++++- 5 files changed, 12 insertions(+), 11 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 852a6cf..ce204ea 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -6,7 +6,6 @@ module Rules ( import Base hiding (arg, args, Args) import Control.Monad -import Package import Expression import Rules.Package import Settings.Packages @@ -19,8 +18,7 @@ generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do pkgs <- interpret (stageTarget stage) packages forM_ pkgs $ \pkg -> do - let dir = targetDirectory stage pkg - need [pkgPath pkg dir "package-data.mk"] + need [targetPath stage pkg "package-data.mk"] -- TODO: add Stage2 (compiler only?) packageRules :: Rules () diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index d608fea..a18a097 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -18,9 +18,9 @@ buildPackageData :: Target -> Rules () buildPackageData target = let stage = getStage target pkg = getPackage target - dir = pkgPath pkg targetDirectory stage pkg + path = targetPath stage pkg in - (dir ) <$> + (path ) <$> [ "package-data.mk" , "haddock-prologue.txt" , "inplace-pkg-config" @@ -31,7 +31,7 @@ buildPackageData target = ] &%> \_ -> do let configure = pkgPath pkg "configure" -- TODO: 1) how to automate this? 2) handle multiple files? - newEnv = target { getFile = dir "package-data.mk" } + newEnv = target { getFile = path "package-data.mk" } -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac @@ -39,7 +39,7 @@ buildPackageData target = run' newEnv GhcCabal -- TODO: when (registerPackage settings) $ run' newEnv (GhcPkg stage) - postProcessPackageData $ dir "package-data.mk" + postProcessPackageData $ path "package-data.mk" -- TODO: This should probably go to Oracles.Builder run' :: Target -> Builder -> Action () diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 8e1a8cf..578c264 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -106,6 +106,7 @@ packageConstraints = do args $ concatMap (\c -> ["--constraint", c]) $ constraints -- TODO: should be in a different file +-- TODO: put all validating options together in one file ccSettings :: Settings ccSettings = validating ? do let gccGe46 = liftM not gccLt46 diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index d5fb21e..601d2b8 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -3,7 +3,6 @@ module Settings.GhcPkg ( ) where import Base hiding (arg, args) -import Package import Switches import Expression hiding (when, liftIO) import Settings.Util @@ -15,9 +14,8 @@ ghcPkgSettings :: Settings ghcPkgSettings = do pkg <- asks getPackage stage <- asks getStage - let dir = pkgPath pkg targetDirectory stage pkg builder (GhcPkg stage) ? mconcat [ arg "update" , arg "--force" , stage0 ? bootPackageDbSettings - , arg $ dir "inplace-pkg-config" ] + , arg $ targetPath stage pkg "inplace-pkg-config" ] diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 83e1d0e..d8eb067 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,5 +1,5 @@ module Settings.TargetDirectory ( - targetDirectory + targetDirectory, targetPath ) where import Base @@ -9,3 +9,7 @@ import UserSettings -- User can override the default target directory settings given below targetDirectory :: Stage -> Package -> FilePath targetDirectory = userTargetDirectory + +-- Path to the target directory from GHC source root +targetPath :: Stage -> Package -> FilePath +targetPath stage pkg = pkgPath pkg targetDirectory stage pkg From git at git.haskell.org Thu Oct 26 23:12:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add argsHashOracle for tracking changes in the build system. (196430d) Message-ID: <20171026231233.6EC0E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/196430d4a0647e7258429e59caad0400151bb8ef/ghc >--------------------------------------------------------------- commit 196430d4a0647e7258429e59caad0400151bb8ef Author: Andrey Mokhov Date: Tue Jul 14 11:16:34 2015 +0100 Add argsHashOracle for tracking changes in the build system. >--------------------------------------------------------------- 196430d4a0647e7258429e59caad0400151bb8ef doc/meeting-16-June-2015.txt | 3 ++- src/Base.hs | 8 +++++++- src/Expression.hs | 16 ++++++++++++++++ src/Main.hs | 4 +--- src/Oracles.hs | 5 +---- src/Oracles/ArgsHash.hs | 22 ++++++++++++++++++++++ src/Oracles/Builder.hs | 8 +++++++- src/Package.hs | 10 ++++++++++ src/Rules.hs | 3 ++- src/Rules/Data.hs | 16 ++++++++++++---- src/Rules/Oracles.hs | 11 +++++++++++ src/Ways.hs | 13 +++++++++++-- 12 files changed, 102 insertions(+), 17 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 196430d4a0647e7258429e59caad0400151bb8ef From git at git.haskell.org Thu Oct 26 23:12:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out build :: Target -> Action () into Rules/Util.hs. (5db0017) Message-ID: <20171026231236.DA8303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5db0017b40d59894d5a6d4d5ba22196f55c47a48/ghc >--------------------------------------------------------------- commit 5db0017b40d59894d5a6d4d5ba22196f55c47a48 Author: Andrey Mokhov Date: Tue Jul 14 11:39:23 2015 +0100 Factor out build :: Target -> Action () into Rules/Util.hs. >--------------------------------------------------------------- 5db0017b40d59894d5a6d4d5ba22196f55c47a48 src/Rules/Data.hs | 21 +++++---------------- src/Rules/Util.hs | 19 +++++++++++++++++++ 2 files changed, 24 insertions(+), 16 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index dabccc1..f3c6064 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -9,11 +9,10 @@ import Package import Expression hiding (when, liftIO) import Oracles.Flag (when) import Oracles.Builder -import Oracles.ArgsHash -import Settings import Settings.GhcPkg import Settings.GhcCabal import Settings.TargetDirectory +import Rules.Util import Util import Ways @@ -35,27 +34,17 @@ buildPackageData target = ] &%> \_ -> do let configure = pkgPath pkg "configure" -- TODO: 1) how to automate this? 2) handle multiple files? - newTarget = target { getFile = path "package-data.mk" } + newTarget = target { getFile = path "package-data.mk" + , getWay = vanilla } -- TODO: think -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac when (doesFileExist $ configure <.> "ac") $ need [configure] - run' newTarget GhcCabal + build $ newTarget { getBuilder = GhcCabal } -- TODO: when (registerPackage settings) $ - run' newTarget (GhcPkg stage) + build $ newTarget { getBuilder = GhcPkg stage } postProcessPackageData $ path "package-data.mk" --- TODO: This should probably go to Oracles.Builder -run' :: Target -> Builder -> Action () -run' target builder = do - let finalTarget = target {getBuilder = builder, getWay = vanilla } - args <- interpret finalTarget settings - putColoured Green (show args) - -- The line below forces the rule to be rerun if the hash has changed - argsHash <- askArgsHash finalTarget - putColoured Yellow (show argsHash) - run builder args - -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- For example, get rid of diff --git a/src/Rules/Util.hs b/src/Rules/Util.hs new file mode 100644 index 0000000..8c9f1c4 --- /dev/null +++ b/src/Rules/Util.hs @@ -0,0 +1,19 @@ +module Rules.Util ( + build + ) where + +import Base +import Util +import Settings +import Expression +import Oracles.Builder +import Oracles.ArgsHash + +build :: Target -> Action () +build target = do + args <- interpret target settings + putColoured Green (show target) + putColoured Green (show args) + -- The line below forces the rule to be rerun if the args hash has changed + argsHash <- askArgsHash target + run (getBuilder target) args From git at git.haskell.org Thu Oct 26 23:12:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactoring: Target is now defined in Target.hs, old Targets.hs is dropped. (92ef777) Message-ID: <20171026231240.5315B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92ef7772b82fe25e48b4f43f752e09cd545d4751/ghc >--------------------------------------------------------------- commit 92ef7772b82fe25e48b4f43f752e09cd545d4751 Author: Andrey Mokhov Date: Tue Jul 14 13:56:52 2015 +0100 Refactoring: Target is now defined in Target.hs, old Targets.hs is dropped. >--------------------------------------------------------------- 92ef7772b82fe25e48b4f43f752e09cd545d4751 src/Expression.hs | 56 +++--------------------------- src/Settings.hs | 2 +- src/{Targets.hs => Settings/Default.hs} | 27 +++++++++++---- src/Settings/GhcCabal.hs | 3 +- src/Settings/Packages.hs | 15 +------- src/Settings/TargetDirectory.hs | 2 +- src/{UserSettings.hs => Settings/User.hs} | 7 ++-- src/Settings/Ways.hs | 2 +- src/Target.hs | 57 +++++++++++++++++++++++++++++++ 9 files changed, 90 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 92ef7772b82fe25e48b4f43f752e09cd545d4751 From git at git.haskell.org Thu Oct 26 23:12:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Settings to Args. Rename old Args defined in Base.hs to ArgList (to be dropped later). (da64dca) Message-ID: <20171026231243.C264B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da64dcaf2d7d2ced1673ed5f57c8801a166215b1/ghc >--------------------------------------------------------------- commit da64dcaf2d7d2ced1673ed5f57c8801a166215b1 Author: Andrey Mokhov Date: Tue Jul 14 14:19:15 2015 +0100 Rename Settings to Args. Rename old Args defined in Base.hs to ArgList (to be dropped later). >--------------------------------------------------------------- da64dcaf2d7d2ced1673ed5f57c8801a166215b1 src/Base.hs | 24 ++++++++----------- src/Expression.hs | 18 +++++++-------- src/Oracles/ArgsHash.hs | 6 ++--- src/Rules.hs | 2 +- src/Rules/Data.hs | 4 ++-- src/Rules/Util.hs | 6 ++--- src/Settings.hs | 18 +++++++-------- src/Settings/GhcCabal.hs | 60 ++++++++++++++++++++++++------------------------ src/Settings/GhcPkg.hs | 10 ++++---- src/Settings/User.hs | 8 +++---- src/Settings/Util.hs | 56 +++++++++++++++++++++----------------------- src/Ways.hs | 41 ++++++++++++++++----------------- 12 files changed, 121 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 da64dcaf2d7d2ced1673ed5f57c8801a166215b1 From git at git.haskell.org Thu Oct 26 23:12:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove unused code from Base and Oracles. (9737176) Message-ID: <20171026231247.33FED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9737176b107f64282a24c9ffd1a3a09fe1b92ed2/ghc >--------------------------------------------------------------- commit 9737176b107f64282a24c9ffd1a3a09fe1b92ed2 Author: Andrey Mokhov Date: Tue Jul 14 15:21:55 2015 +0100 Remove unused code from Base and Oracles. >--------------------------------------------------------------- 9737176b107f64282a24c9ffd1a3a09fe1b92ed2 src/Base.hs | 8 ++---- src/Expression.hs | 9 +++--- src/Oracles.hs | 11 ++------ src/Oracles/ArgsHash.hs | 2 +- src/Oracles/Builder.hs | 7 +++-- src/Oracles/Flag.hs | 72 +----------------------------------------------- src/Oracles/Option.hs | 40 ++------------------------- src/Rules.hs | 1 - src/Rules/Data.hs | 6 ++-- src/Rules/Oracles.hs | 2 +- src/Settings.hs | 4 +-- src/Settings/GhcCabal.hs | 2 +- src/Settings/GhcPkg.hs | 2 +- src/Settings/Util.hs | 7 ++--- src/Settings/Ways.hs | 2 +- src/Switches.hs | 11 ++++++++ src/Target.hs | 2 +- src/Ways.hs | 3 +- 18 files changed, 42 insertions(+), 149 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 9737176b107f64282a24c9ffd1a3a09fe1b92ed2 From git at git.haskell.org Thu Oct 26 23:12:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Distringuish partial Targets using type synonyms. (c319fbb) Message-ID: <20171026231250.9DE4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c319fbbf892b9a8a231676b3ecf9550d4b56a01b/ghc >--------------------------------------------------------------- commit c319fbbf892b9a8a231676b3ecf9550d4b56a01b Author: Andrey Mokhov Date: Tue Jul 14 16:07:42 2015 +0100 Distringuish partial Targets using type synonyms. >--------------------------------------------------------------- c319fbbf892b9a8a231676b3ecf9550d4b56a01b src/Oracles/ArgsHash.hs | 4 ++-- src/Rules/Data.hs | 10 ++++----- src/Rules/Package.hs | 2 +- src/Rules/Util.hs | 2 +- src/Settings/Packages.hs | 5 ++++- src/Target.hs | 55 ++++++++++++++++++++++++++++++++---------------- 6 files changed, 49 insertions(+), 29 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 1586b97..acb3e98 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -9,10 +9,10 @@ import Base import Settings import Expression -newtype ArgsHashKey = ArgsHashKey Target +newtype ArgsHashKey = ArgsHashKey FullTarget deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -askArgsHash :: Target -> Action Int +askArgsHash :: FullTarget -> Action Int askArgsHash = askOracle . ArgsHashKey -- Oracle for storing per-target argument list hashes diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 684cde6..2a40519 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -17,7 +17,7 @@ import Util import Ways -- Build package-data.mk by using GhcCabal to process pkgCabal file -buildPackageData :: Target -> Rules () +buildPackageData :: StagePackageTarget -> Rules () buildPackageData target = let stage = getStage target pkg = getPackage target @@ -33,16 +33,14 @@ buildPackageData target = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" - -- TODO: 1) how to automate this? 2) handle multiple files? - newTarget = target { getFile = path "package-data.mk" - , getWay = vanilla } -- TODO: think -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - build $ newTarget { getBuilder = GhcCabal } + -- TODO: 1) automate? 2) mutliple files 3) vanilla? + build $ fullTarget target (path "package-data.mk") GhcCabal vanilla -- TODO: when (registerPackage settings) $ - build $ newTarget { getBuilder = GhcPkg stage } + build $ fullTarget target (path "package-data.mk") (GhcPkg stage) vanilla postProcessPackageData $ path "package-data.mk" -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index a5a09dd..e316805 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -6,5 +6,5 @@ import Base import Rules.Data import Expression -buildPackage :: Target -> Rules () +buildPackage :: StagePackageTarget -> Rules () buildPackage = buildPackageData diff --git a/src/Rules/Util.hs b/src/Rules/Util.hs index a18e25e..6e1296e 100644 --- a/src/Rules/Util.hs +++ b/src/Rules/Util.hs @@ -9,7 +9,7 @@ import Expression import Oracles.Builder import Oracles.ArgsHash -build :: Target -> Action () +build :: FullTarget -> Action () build target = do argList <- interpret target args putColoured Green (show target) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 7eaa5d5..b1d98de 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -1,4 +1,5 @@ module Settings.Packages ( + module Settings.Default, packages, knownPackages ) where @@ -6,6 +7,7 @@ import Base import Package import Switches import Expression +import Settings.Default import Settings.User -- Combining default list of packages with user modifications @@ -25,7 +27,8 @@ packagesStage0 = mconcat packagesStage1 :: Packages packagesStage1 = mconcat - [ append [ array, base, bytestring, containers, deepseq, directory + [ packagesStage0 + , append [ array, base, bytestring, containers, deepseq, directory , filepath, ghcPrim, haskeline, integerLibrary, parallel , pretty, primitive, process, stm, templateHaskell, time ] , windowsHost ? append [win32] diff --git a/src/Target.hs b/src/Target.hs index 6161db7..0a0ed00 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,6 +1,7 @@ -{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} module Target ( - Target (..), stageTarget, stagePackageTarget + Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), + stageTarget, stagePackageTarget, fullTarget ) where import Base @@ -17,41 +18,59 @@ data Target = Target { getStage :: Stage, getPackage :: Package, - getBuilder :: Builder, getFile :: FilePath, -- TODO: handle multple files? + getBuilder :: Builder, getWay :: Way } deriving (Eq, Generic) --- Shows a target as "package:file at stage (builder, way)" -instance Show Target where - show target = show (getPackage target) - ++ ":" ++ show (getFile target) - ++ "@" ++ show (getStage target) - ++ " (" ++ show (getBuilder target) - ++ ", " ++ show (getWay target) ++ ")" +-- StageTarget is a Target whose field getStage is already assigned +type StageTarget = Target -stageTarget :: Stage -> Target +stageTarget :: Stage -> StageTarget stageTarget stage = Target { getStage = stage, getPackage = error "stageTarget: Package not set", - getBuilder = error "stageTarget: Builder not set", getFile = error "stageTarget: File not set", + getBuilder = error "stageTarget: Builder not set", getWay = error "stageTarget: Way not set" } -stagePackageTarget :: Stage -> Package -> Target +-- StagePackageTarget is a Target whose fields getStage and getPackage are +-- already assigned +type StagePackageTarget = Target + +stagePackageTarget :: Stage -> Package -> StagePackageTarget stagePackageTarget stage package = Target { getStage = stage, getPackage = package, - getBuilder = error "stagePackageTarget: Builder not set", getFile = error "stagePackageTarget: File not set", + getBuilder = error "stagePackageTarget: Builder not set", getWay = error "stagePackageTarget: Way not set" } --- Instances for storing Target in the Shake database -instance Binary Target -instance NFData Target -instance Hashable Target +-- FullTarget is a Target whose fields are all assigned +type FullTarget = Target + +fullTarget :: StagePackageTarget -> FilePath -> Builder -> Way -> FullTarget +fullTarget target file builder way = target + { + getFile = file, + getBuilder = builder, + getWay = way + } + +-- Shows a (full) target as "package:file at stage (builder, way)" +instance Show FullTarget where + show target = show (getPackage target) + ++ ":" ++ getFile target + ++ "@" ++ show (getStage target) + ++ " (" ++ show (getBuilder target) + ++ ", " ++ show (getWay target) ++ ")" + +-- Instances for storing FullTarget in the Shake database +instance Binary FullTarget +instance NFData FullTarget +instance Hashable FullTarget From git at git.haskell.org Thu Oct 26 23:12:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Oracles/Builder.hs. (772ea96) Message-ID: <20171026231254.1B0AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/772ea960e295c90f0052edc7ba0c0ec6a26d33c3/ghc >--------------------------------------------------------------- commit 772ea960e295c90f0052edc7ba0c0ec6a26d33c3 Author: Andrey Mokhov Date: Tue Jul 14 23:27:54 2015 +0100 Refactor Oracles/Builder.hs. >--------------------------------------------------------------- 772ea960e295c90f0052edc7ba0c0ec6a26d33c3 src/Builder.hs | 92 ++++++++++++++++++++++++++++ src/Expression.hs | 4 +- src/Oracles/Builder.hs | 154 ----------------------------------------------- src/Rules/Actions.hs | 62 +++++++++++++++++++ src/Rules/Data.hs | 4 +- src/Rules/Util.hs | 19 ------ src/Settings/GhcCabal.hs | 43 +++++++++---- src/Settings/GhcPkg.hs | 2 +- src/Settings/Util.hs | 7 +-- src/Target.hs | 2 +- 10 files changed, 193 insertions(+), 196 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 772ea960e295c90f0052edc7ba0c0ec6a26d33c3 From git at git.haskell.org Thu Oct 26 23:12:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:12:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up Base. (9bde7d8) Message-ID: <20171026231257.8CC8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9bde7d8668019ed08561c701e3f2ba61ac173d6e/ghc >--------------------------------------------------------------- commit 9bde7d8668019ed08561c701e3f2ba61ac173d6e Author: Andrey Mokhov Date: Tue Jul 14 23:49:13 2015 +0100 Clean up Base. >--------------------------------------------------------------- 9bde7d8668019ed08561c701e3f2ba61ac173d6e src/Base.hs | 13 ------------- 1 file changed, 13 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 026f211..97a22d5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -10,7 +10,6 @@ module Base ( Stage (..), Arg, ArgList, ShowArg (..), ShowArgs (..), - filterOut, productArgs, concatArgs ) where @@ -56,21 +55,9 @@ class ShowArgs a where instance ShowArgs [String] where showArgs = return -instance ShowArgs [Arg] where - showArgs = sequence - -instance ShowArgs [ArgList] where - showArgs = mconcat - instance ShowArgs a => ShowArgs (Action a) where showArgs = (showArgs =<<) --- Filter out given arg(s) from a collection -filterOut :: ShowArgs a => ArgList -> a -> ArgList -filterOut as exclude = do - exclude' <- showArgs exclude - filter (`notElem` exclude') <$> as - -- Generate a cross product collection of two argument collections -- Example: productArgs ["-a", "-b"] "c" = args ["-a", "c", "-b", "c"] productArgs :: (ShowArgs a, ShowArgs b) => a -> b -> ArgList From git at git.haskell.org Thu Oct 26 23:13:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Ways.hs => Way.hs and refactor it. (3726211) Message-ID: <20171026231301.014BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37262111fee905d4d0312c02f80ae3abd8250566/ghc >--------------------------------------------------------------- commit 37262111fee905d4d0312c02f80ae3abd8250566 Author: Andrey Mokhov Date: Wed Jul 15 20:30:52 2015 +0200 Rename Ways.hs => Way.hs and refactor it. >--------------------------------------------------------------- 37262111fee905d4d0312c02f80ae3abd8250566 src/Base.hs | 8 +-- src/Builder.hs | 2 +- src/Expression.hs | 2 +- src/Package.hs | 10 +-- src/Rules/Data.hs | 2 +- src/Settings/GhcCabal.hs | 2 +- src/Settings/Util.hs | 15 +++++ src/Settings/Ways.hs | 2 +- src/Target.hs | 4 +- src/Way.hs | 138 +++++++++++++++++++++++++++++++++++++++ src/Ways.hs | 165 ----------------------------------------------- 11 files changed, 169 insertions(+), 181 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 37262111fee905d4d0312c02f80ae3abd8250566 From git at git.haskell.org Thu Oct 26 23:13:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support to multiple files in Target, implement registerPackage predicate. (c41e156) Message-ID: <20171026231304.9B59D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c41e156c6bee670112d50825040ccc2ebc56a78e/ghc >--------------------------------------------------------------- commit c41e156c6bee670112d50825040ccc2ebc56a78e Author: Andrey Mokhov Date: Wed Jul 15 23:44:30 2015 +0200 Add support to multiple files in Target, implement registerPackage predicate. >--------------------------------------------------------------- c41e156c6bee670112d50825040ccc2ebc56a78e src/Expression.hs | 2 +- src/Rules/Actions.hs | 7 ++++++- src/Rules/Data.hs | 10 ++++------ src/Switches.hs | 7 ++++++- src/Target.hs | 30 ++++++++++++++++++++---------- 5 files changed, 37 insertions(+), 19 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 2f8ea4b..0ee8034 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -140,7 +140,7 @@ builder :: Builder -> Predicate builder b = liftM (b ==) (asks getBuilder) file :: FilePattern -> Predicate -file f = liftM (f ?==) (asks getFile) +file f = liftM (any (f ?==)) (asks getFiles) way :: Way -> Predicate way w = liftM (w ==) (asks getWay) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9010647..d29d486 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,5 +1,5 @@ module Rules.Actions ( - build, run, verboseRun, + build, buildWhen, run, verboseRun, ) where import Base @@ -21,6 +21,11 @@ build target = do argsHash <- askArgsHash target run (getBuilder target) argList +buildWhen :: Predicate -> FullTarget -> Action () +buildWhen predicate target = do + bool <- interpretExpr target predicate + when bool $ build target + -- Run the builder with a given collection of arguments verboseRun :: Builder -> [String] -> Action () verboseRun builder args = do diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index beadd7e..eb34b65 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -4,10 +4,10 @@ module Rules.Data ( cabalArgs, ghcPkgArgs, buildPackageData ) where -import Way import Base import Package import Builder +import Switches import Expression import Control.Monad.Extra import Settings.GhcPkg @@ -31,16 +31,14 @@ buildPackageData target = , "build" "autogen" "cabal_macros.h" -- TODO: Is this needed? Also check out Paths_cpsa.hs. -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" - ] &%> \_ -> do + ] &%> \files -> do let configure = pkgPath pkg "configure" -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - -- TODO: 1) automate? 2) mutliple files 3) vanilla? - build $ fullTarget target (path "package-data.mk") GhcCabal vanilla - -- TODO: when (registerPackage settings) $ - build $ fullTarget target (path "package-data.mk") (GhcPkg stage) vanilla + build $ fullTarget target files GhcCabal + buildWhen registerPackage $ fullTarget target files (GhcPkg stage) postProcessPackageData $ path "package-data.mk" -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: diff --git a/src/Switches.hs b/src/Switches.hs index ce03ade..8ab2de2 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -5,7 +5,8 @@ module Switches ( targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, platformSupportsSharedLibs, crossCompiling, - gccIsClang, gccLt46, windowsHost, notWindowsHost + gccIsClang, gccLt46, windowsHost, notWindowsHost, + registerPackage ) where import Base @@ -91,6 +92,10 @@ windowsHost = configKeyValues "host-os-cpp" ["mingw32", "cygwin32"] notWindowsHost :: Predicate notWindowsHost = liftM not windowsHost +-- TODO: Actually, we don't register compiler in some circumstances -- fix. +registerPackage :: Predicate +registerPackage = return True + -- splitObjects :: Stage -> Condition -- splitObjects stage = do -- arch <- showArg TargetArch diff --git a/src/Target.hs b/src/Target.hs index 198cffc..6b02af9 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} module Target ( Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), - stageTarget, stagePackageTarget, fullTarget + stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay ) where import Way @@ -18,7 +18,7 @@ data Target = Target { getStage :: Stage, getPackage :: Package, - getFile :: FilePath, -- TODO: handle multple files? + getFiles :: [FilePath], getBuilder :: Builder, getWay :: Way } @@ -32,9 +32,9 @@ stageTarget stage = Target { getStage = stage, getPackage = error "stageTarget: Package not set", - getFile = error "stageTarget: File not set", + getFiles = error "stageTarget: Files not set", getBuilder = error "stageTarget: Builder not set", - getWay = error "stageTarget: Way not set" + getWay = vanilla -- most targets are built only one way (vanilla) } -- StagePackageTarget is a Target whose fields getStage and getPackage are @@ -46,18 +46,28 @@ stagePackageTarget stage package = Target { getStage = stage, getPackage = package, - getFile = error "stagePackageTarget: File not set", + getFiles = error "stagePackageTarget: Files not set", getBuilder = error "stagePackageTarget: Builder not set", - getWay = error "stagePackageTarget: Way not set" + getWay = vanilla } -- FullTarget is a Target whose fields are all assigned type FullTarget = Target -fullTarget :: StagePackageTarget -> FilePath -> Builder -> Way -> FullTarget -fullTarget target file builder way = target +-- Most targets are built only one way, vanilla, hence we set it by default. +fullTarget :: StagePackageTarget -> [FilePath] -> Builder -> FullTarget +fullTarget target files builder = target { - getFile = file, + getFiles = files, + getBuilder = builder, + getWay = vanilla + } + +-- Use this function to be explicit about build the way. +fullTargetWithWay :: StagePackageTarget -> [FilePath] -> Builder -> Way -> FullTarget +fullTargetWithWay target files builder way = target + { + getFiles = files, getBuilder = builder, getWay = way } @@ -65,7 +75,7 @@ fullTarget target file builder way = target -- Shows a (full) target as "package:file at stage (builder, way)" instance Show FullTarget where show target = show (getPackage target) - ++ ":" ++ getFile target + ++ ":" ++ show (getFiles target) ++ "@" ++ show (getStage target) ++ " (" ++ show (getBuilder target) ++ ", " ++ show (getWay target) ++ ")" From git at git.haskell.org Thu Oct 26 23:13:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Settings.hs to Settings/Args.hs. (d9b03d3) Message-ID: <20171026231308.190283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9b03d37d49ecbd2db59fd242692727488ef92dd/ghc >--------------------------------------------------------------- commit d9b03d37d49ecbd2db59fd242692727488ef92dd Author: Andrey Mokhov Date: Wed Jul 15 23:49:10 2015 +0200 Rename Settings.hs to Settings/Args.hs. >--------------------------------------------------------------- d9b03d37d49ecbd2db59fd242692727488ef92dd src/Oracles/ArgsHash.hs | 4 ++-- src/Rules/Actions.hs | 2 +- src/{Settings.hs => Settings/Args.hs} | 2 +- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index acb3e98..b930ef6 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -4,10 +4,10 @@ module Oracles.ArgsHash ( ArgsHashKey (..), askArgsHash, argsHashOracle ) where -import Development.Shake.Classes import Base -import Settings import Expression +import Settings.Args +import Development.Shake.Classes newtype ArgsHashKey = ArgsHashKey FullTarget deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d29d486..e4688dc 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -5,8 +5,8 @@ module Rules.Actions ( import Base import Util import Builder -import Settings import Expression +import Settings.Args import Oracles.ArgsHash -- Build a given target using an appropriate builder. Force a rebuilt if the diff --git a/src/Settings.hs b/src/Settings/Args.hs similarity index 92% rename from src/Settings.hs rename to src/Settings/Args.hs index 196f4d7..cc7a22c 100644 --- a/src/Settings.hs +++ b/src/Settings/Args.hs @@ -1,4 +1,4 @@ -module Settings ( +module Settings.Args ( args ) where From git at git.haskell.org Thu Oct 26 23:13:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement argPath that unifies the path argument. (5a4a443) Message-ID: <20171026231311.7DD1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a4a443af1fabc548894ca9d3f75702a4b08cf21/ghc >--------------------------------------------------------------- commit 5a4a443af1fabc548894ca9d3f75702a4b08cf21 Author: Andrey Mokhov Date: Wed Jul 15 23:55:46 2015 +0200 Implement argPath that unifies the path argument. >--------------------------------------------------------------- 5a4a443af1fabc548894ca9d3f75702a4b08cf21 src/Settings/GhcCabal.hs | 4 ++-- src/Settings/GhcPkg.hs | 2 +- src/Settings/Util.hs | 12 +++++++----- 3 files changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 7281b9f..34984b7 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -21,8 +21,8 @@ cabalArgs = builder GhcCabal ? do stage <- asks getStage pkg <- asks getPackage mconcat [ arg "configure" - , arg $ pkgPath pkg - , arg $ targetDirectory stage pkg + , argPath $ pkgPath pkg + , argPath $ targetDirectory stage pkg , dllArgs , with $ Ghc stage , with $ GhcPkg stage diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index 9bf85e7..a75eab7 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -18,4 +18,4 @@ ghcPkgArgs = do [ arg "update" , arg "--force" , stage0 ? bootPackageDbArgs - , arg $ targetPath stage pkg "inplace-pkg-config" ] + , argPath $ targetPath stage pkg "inplace-pkg-config" ] diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index b529376..9ee4986 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -1,6 +1,6 @@ module Settings.Util ( -- Primitive settings elements - arg, argM, + arg, argPath, argM, argConfig, argStagedConfig, argConfigList, argStagedConfigList, appendCcArgs, -- argBuilderPath, argStagedBuilderPath, @@ -12,14 +12,19 @@ module Settings.Util ( ) where import Base +import Util import Builder import Oracles.Base import Expression --- A single argument +-- A single argument. arg :: String -> Args arg = append . return +-- A single path argument. The path gets unified. +argPath :: String -> Args +argPath = append . return . unifyPath + argM :: Action String -> Args argM = appendM . fmap return @@ -50,9 +55,6 @@ appendCcArgs xs = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" xs , builder GhcCabal ? appendSub "--gcc-options" xs ] - - - -- packageData :: Arity -> String -> Args -- packageData arity key = -- return $ EnvironmentParameter $ PackageData arity key Nothing Nothing From git at git.haskell.org Thu Oct 26 23:13:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove user.config file, rename default.config to system.config. (a8cfbde) Message-ID: <20171026231314.DF2003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8cfbde5e0fc9df532d739815a28ac2e022eff0d/ghc >--------------------------------------------------------------- commit a8cfbde5e0fc9df532d739815a28ac2e022eff0d Author: Andrey Mokhov Date: Sun Jul 19 00:15:45 2015 +0100 Remove user.config file, rename default.config to system.config. >--------------------------------------------------------------- a8cfbde5e0fc9df532d739815a28ac2e022eff0d .gitignore | 2 +- cfg/configure.ac | 2 +- cfg/{default.config.in => system.config.in} | 0 cfg/user.config | 4 ---- src/Config.hs | 4 ++-- src/Oracles.hs | 37 ++++++++--------------------- src/Oracles/Option.hs | 4 ++-- 7 files changed, 16 insertions(+), 37 deletions(-) diff --git a/.gitignore b/.gitignore index dad3a3c..94b9664 100644 --- a/.gitignore +++ b/.gitignore @@ -2,5 +2,5 @@ *.hi _shake/ _build/ -cfg/default.config +cfg/system.config arg/*/*.txt diff --git a/cfg/configure.ac b/cfg/configure.ac index 125fd49..687eac7 100644 --- a/cfg/configure.ac +++ b/cfg/configure.ac @@ -978,7 +978,7 @@ if grep ' ' compiler/ghc.cabal.in 2>&1 >/dev/null; then AC_MSG_ERROR([compiler/ghc.cabal.in contains tab characters; please remove them]) fi -AC_CONFIG_FILES([shake/cfg/default.config mk/config.mk mk/install.mk mk/project.mk compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal settings docs/users_guide/ug-book.xml docs/users_guide/ug-ent.xml docs/index.html libraries/prologue.txt distrib/configure.ac]) +AC_CONFIG_FILES([shake/cfg/system.config mk/config.mk mk/install.mk mk/project.mk compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal settings docs/users_guide/ug-book.xml docs/users_guide/ug-ent.xml docs/index.html libraries/prologue.txt distrib/configure.ac]) AC_OUTPUT # We got caught by diff --git a/cfg/default.config.in b/cfg/system.config.in similarity index 100% rename from cfg/default.config.in rename to cfg/system.config.in diff --git a/cfg/user.config b/cfg/user.config deleted file mode 100644 index b72c5b4..0000000 --- a/cfg/user.config +++ /dev/null @@ -1,4 +0,0 @@ -# Override default settings (stored in default.config file): -#=========================================================== - -lax-dependencies = YES diff --git a/src/Config.hs b/src/Config.hs index 1a4ef9a..0dc67a2 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -17,7 +17,7 @@ autoconfRules = do configureRules :: Rules () configureRules = do - cfgPath "default.config" %> \out -> do - need [cfgPath "default.config.in", "configure"] + cfgPath "system.config" %> \out -> do + need [cfgPath "system.config.in", "configure"] putColoured White "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' diff --git a/src/Oracles.hs b/src/Oracles.hs index e6e31f9..cd8c879 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -6,45 +6,25 @@ module Oracles ( import Development.Shake.Config import Development.Shake.Util import qualified Data.HashMap.Strict as M --- TODO: get rid of Bifunctor dependency -import Data.Bifunctor import Base import Util import Config +import Control.Monad.Extra import Oracles.Base import Oracles.PackageData -import Control.Monad.Extra import Oracles.DependencyList -defaultConfig, userConfig :: FilePath -defaultConfig = cfgPath "default.config" -userConfig = cfgPath "user.config" - -- Oracle for configuration files configOracle :: Rules () configOracle = do + let configFile = cfgPath "system.config" cfg <- newCache $ \() -> do - unlessM (doesFileExist $ defaultConfig <.> "in") $ - redError_ $ "\nDefault configuration file '" - ++ (defaultConfig <.> "in") + unlessM (doesFileExist $ configFile <.> "in") $ + redError_ $ "\nConfiguration file '" ++ (configFile <.> "in") ++ "' is missing; unwilling to proceed." - need [defaultConfig] - putOracle $ "Reading " ++ unifyPath defaultConfig ++ "..." - cfgDefault <- liftIO $ readConfigFile defaultConfig - existsUser <- doesFileExist userConfig - cfgUser <- if existsUser - then do - putOracle $ "Reading " - ++ unifyPath userConfig ++ "..." - liftIO $ readConfigFile userConfig - else do - putColoured Red $ - "\nUser defined configuration file '" - ++ userConfig ++ "' is missing; " - ++ "proceeding with default configuration.\n" - return M.empty - putColoured Green $ "Finished processing configuration files." - return $ cfgUser `M.union` cfgDefault + need [configFile] + putOracle $ "Reading " ++ unifyPath configFile ++ "..." + liftIO $ readConfigFile configFile addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () return () @@ -59,6 +39,9 @@ packageDataOracle = do M.lookup key <$> pkgData (unifyPath file) return () +bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) +bimap f g (x, y) = (f x, g y) + -- Oracle for 'path/dist/*.deps' files dependencyOracle :: Rules () dependencyOracle = do diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index f1a35e2..ff0c5fc 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -5,8 +5,8 @@ module Oracles.Option ( import Base import Oracles.Base --- For each Option the files {default.config, user.config} contain --- a line of the form 'target-os = mingw32'. +-- For each Option the file default.config contains a line of the +-- form 'target-os = mingw32'. -- (showArg TargetOs) is an action that consults the config files -- and returns "mingw32". -- From git at git.haskell.org Thu Oct 26 23:13:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor and rename Oracles/Option.hs. (272f100) Message-ID: <20171026231318.4911D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7/ghc >--------------------------------------------------------------- commit 272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7 Author: Andrey Mokhov Date: Sun Jul 19 00:45:35 2015 +0100 Refactor and rename Oracles/Option.hs. >--------------------------------------------------------------- 272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7 src/Base.hs | 3 +-- src/Builder.hs | 3 ++- src/Expression.hs | 1 + src/Oracles.hs | 1 + src/Oracles/Option.hs | 61 ---------------------------------------------- src/Oracles/PackageData.hs | 1 + src/Oracles/Setting.hs | 61 ++++++++++++++++++++++++++++++++++++++++++++++ src/Settings/GhcCabal.hs | 5 ++-- src/Way.hs | 18 +++++++------- 9 files changed, 79 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 272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7 From git at git.haskell.org Thu Oct 26 23:13:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove Base.hs, move Stage definition to Stage.hs. (03f90e7) Message-ID: <20171026231321.B72FB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03f90e74e6d472f26f22baef563c38d088dadb8f/ghc >--------------------------------------------------------------- commit 03f90e74e6d472f26f22baef563c38d088dadb8f Author: Andrey Mokhov Date: Sun Jul 19 01:26:22 2015 +0100 Remove Base.hs, move Stage definition to Stage.hs. >--------------------------------------------------------------- 03f90e74e6d472f26f22baef563c38d088dadb8f src/Base.hs | 74 ---------------------------------- src/Builder.hs | 4 +- src/Config.hs | 3 +- src/Expression.hs | 5 ++- src/Main.hs | 2 +- src/Oracles.hs | 13 +++--- src/Oracles/ArgsHash.hs | 3 +- src/Oracles/Base.hs | 2 +- src/Oracles/DependencyList.hs | 11 ++--- src/Oracles/Flag.hs | 2 +- src/Oracles/PackageData.hs | 89 ++++++++++++++++++++--------------------- src/Oracles/Setting.hs | 17 ++++---- src/Package.hs | 3 +- src/Rules.hs | 5 ++- src/Rules/Actions.hs | 2 +- src/Rules/Data.hs | 8 ++-- src/Rules/Oracles.hs | 3 +- src/Rules/Package.hs | 2 +- src/Settings/Args.hs | 3 +- src/Settings/Default.hs | 2 +- src/Settings/GhcCabal.hs | 7 +++- src/Settings/GhcPkg.hs | 2 +- src/Settings/Packages.hs | 3 +- src/Settings/TargetDirectory.hs | 3 +- src/Settings/User.hs | 4 +- src/Settings/Util.hs | 3 +- src/Settings/Ways.hs | 2 +- src/Stage.hs | 17 ++++++++ src/Switches.hs | 2 +- src/Target.hs | 2 +- src/Util.hs | 7 ++-- src/Way.hs | 3 +- 32 files changed, 135 insertions(+), 173 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 03f90e74e6d472f26f22baef563c38d088dadb8f From git at git.haskell.org Thu Oct 26 23:13:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor oracles, add comments. (49419bc) Message-ID: <20171026231325.2E2373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49419bc553873c21efebe87f4e0aa343013d4bad/ghc >--------------------------------------------------------------- commit 49419bc553873c21efebe87f4e0aa343013d4bad Author: Andrey Mokhov Date: Sun Jul 19 16:38:17 2015 +0100 Refactor oracles, add comments. >--------------------------------------------------------------- 49419bc553873c21efebe87f4e0aa343013d4bad src/Builder.hs | 3 -- src/Expression.hs | 1 - src/Main.hs | 1 - src/Oracles.hs | 67 ------------------------------------------- src/Oracles/ArgsHash.hs | 8 ++++-- src/Oracles/Base.hs | 41 +++++++++++++++++++++++--- src/Oracles/DependencyList.hs | 46 +++++++++++++++++++++-------- src/Oracles/Flag.hs | 1 - src/Oracles/PackageData.hs | 55 ++++++++++++++++++++--------------- src/Oracles/Setting.hs | 43 +++++++++++++-------------- src/Rules.hs | 2 ++ src/{ => Rules}/Config.hs | 16 ++++------- src/Rules/Oracles.hs | 7 +++-- src/Settings/GhcCabal.hs | 2 -- src/Settings/Util.hs | 1 - 15 files changed, 141 insertions(+), 153 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 49419bc553873c21efebe87f4e0aa343013d4bad From git at git.haskell.org Thu Oct 26 23:13:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify Rules.Config. (7dc414c) Message-ID: <20171026231328.8FF6B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7dc414caf7aa55531c2d25f69c785bec30f192c7/ghc >--------------------------------------------------------------- commit 7dc414caf7aa55531c2d25f69c785bec30f192c7 Author: Andrey Mokhov Date: Sun Jul 19 16:55:54 2015 +0100 Simplify Rules.Config. >--------------------------------------------------------------- 7dc414caf7aa55531c2d25f69c785bec30f192c7 src/Main.hs | 3 +-- src/Rules/Config.hs | 18 ++++++++---------- 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 8bd3384..50420af 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -4,6 +4,5 @@ import Development.Shake main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do oracleRules -- see module Rules.Oracles packageRules -- see module Rules - autoconfRules -- see module Config - configureRules -- see module Config + configRules -- see module Rules.Config generateTargets -- see module Rules diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 2aa3988..3fb4c6a 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -1,20 +1,18 @@ module Rules.Config ( - autoconfRules, configureRules + configRules ) where import Util import Oracles.Base -autoconfRules :: Rules () -autoconfRules = do - "configure" %> \out -> do - copyFile' (configPath "configure.ac") "configure.ac" - putColoured White $ "Running autoconf..." - cmd "bash autoconf" -- TODO: get rid of 'bash' - -configureRules :: Rules () -configureRules = do +configRules :: Rules () +configRules = do configPath "system.config" %> \out -> do need [configPath "system.config.in", "configure"] putColoured White "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' + + "configure" %> \out -> do + copyFile' (configPath "configure.ac") "configure.ac" + putColoured White $ "Running autoconf..." + cmd "bash autoconf" -- TODO: get rid of 'bash' From git at git.haskell.org Thu Oct 26 23:13:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix import of IntSet. (6e8416e) Message-ID: <20171026231332.002AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e8416e2117fd487e89e58ab112c3688093a0055/ghc >--------------------------------------------------------------- commit 6e8416e2117fd487e89e58ab112c3688093a0055 Author: Andrey Mokhov Date: Sun Jul 19 16:59:50 2015 +0100 Fix import of IntSet. >--------------------------------------------------------------- 6e8416e2117fd487e89e58ab112c3688093a0055 src/Way.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index dffd050..c0b49e3 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -18,8 +18,9 @@ import Oracles.Setting import Control.Applicative import Development.Shake import Development.Shake.Classes -import Data.List hiding (delete) -import Data.IntSet (IntSet, elems, member, delete, fromList) +import Data.List +import Data.IntSet (IntSet) +import qualified Data.IntSet as Set data WayUnit = Threaded | Debug @@ -46,13 +47,13 @@ instance Read WayUnit where newtype Way = Way IntSet wayFromUnits :: [WayUnit] -> Way -wayFromUnits = Way . fromList . map fromEnum +wayFromUnits = Way . Set.fromList . map fromEnum wayToUnits :: Way -> [WayUnit] -wayToUnits (Way set) = map toEnum . elems $ set +wayToUnits (Way set) = map toEnum . Set.elems $ set wayUnit :: WayUnit -> Way -> Bool -wayUnit unit (Way set) = fromEnum unit `member` set +wayUnit unit (Way set) = fromEnum unit `Set.member` set instance Show Way where show way = if null tag then "v" else tag @@ -120,7 +121,7 @@ libsuf way @ (Way set) = else do extension <- setting DynamicExtension -- e.g., .dll or .so version <- setting ProjectVersion -- e.g., 7.11.20141222 - let prefix = wayPrefix . Way . delete (fromEnum Dynamic) $ set + let prefix = wayPrefix . Way . Set.delete (fromEnum Dynamic) $ set -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension From git at git.haskell.org Thu Oct 26 23:13:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Migrate all user-configurable settings from system.default to Settings/User.hs. (b253397) Message-ID: <20171026231335.644B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b253397966a028a13d39b59c1233bef3007eb857/ghc >--------------------------------------------------------------- commit b253397966a028a13d39b59c1233bef3007eb857 Author: Andrey Mokhov Date: Mon Jul 20 00:09:15 2015 +0100 Migrate all user-configurable settings from system.default to Settings/User.hs. >--------------------------------------------------------------- b253397966a028a13d39b59c1233bef3007eb857 cfg/system.config.in | 4 -- src/Builder.hs | 17 ++------- src/Expression.hs | 39 ++++++++++--------- src/Oracles/Flag.hs | 71 ++++++++++++++++++++-------------- src/Oracles/Setting.hs | 38 ++++++++++++++++++- src/Rules/Actions.hs | 5 +-- src/Settings/GhcCabal.hs | 13 ++++--- src/Settings/Packages.hs | 1 + src/Settings/User.hs | 20 +++++++--- src/Settings/Util.hs | 16 ++++++++ src/Settings/Ways.hs | 1 + src/Switches.hs | 99 +++++++----------------------------------------- 12 files changed, 160 insertions(+), 164 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 b253397966a028a13d39b59c1233bef3007eb857 From git at git.haskell.org Thu Oct 26 23:13:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve performance by caching windows root lookup. (580d397) Message-ID: <20171026231338.CDC333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/580d39722d627eb95eab63d374441d6c92276f9e/ghc >--------------------------------------------------------------- commit 580d39722d627eb95eab63d374441d6c92276f9e Author: Andrey Mokhov Date: Mon Jul 20 10:06:06 2015 +0100 Improve performance by caching windows root lookup. >--------------------------------------------------------------- 580d39722d627eb95eab63d374441d6c92276f9e src/Builder.hs | 6 +++--- src/Oracles/PackageData.hs | 1 + src/Oracles/Setting.hs | 8 +++----- src/Oracles/WindowsRoot.hs | 28 ++++++++++++++++++++++++++++ src/Rules/Oracles.hs | 10 +++++++--- src/Settings/Args.hs | 1 + 6 files changed, 43 insertions(+), 11 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 0001fc4..91c6fa3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -9,6 +9,7 @@ import Stage import Data.List import Oracles.Base import Oracles.Setting +import Oracles.WindowsRoot import GHC.Generics -- A Builder is an external command invoked in separate process using Shake.cmd @@ -58,7 +59,6 @@ builderPath builder = do specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- TODO: get rid of code duplication (windowsHost) -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". fixAbsolutePathOnWindows :: FilePath -> Action FilePath @@ -67,8 +67,8 @@ fixAbsolutePathOnWindows path = do -- Note, below is different from FilePath.isAbsolute: if (windows && "/" `isPrefixOf` path) then do - Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] - return . unifyPath $ dropWhileEnd isSpace out ++ drop 1 path + root <- windowsRoot + return . unifyPath $ root ++ drop 1 path else return path diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index f12b842..3b00cf8 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -39,6 +39,7 @@ data PackageDataList = Modules FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +-- TODO: is this needed? askPackageData :: FilePath -> String -> Action String askPackageData path key = do let fullKey = replaceSeparators '_' $ path ++ "_" ++ key diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 02073e9..9694c00 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -12,8 +12,8 @@ import Oracles.Base -- setting TargetOs looks up the config file and returns "mingw32". -- -- SettingList is used for multiple string values separated by spaces, such --- as 'src-hc-args = -H32m -O'. --- settingList SrcHcArgs therefore returns a list of strings ["-H32", "-O"]. +-- as 'gmp-include-dirs = a b'. +-- settingList GmpIncludeDirs therefore returns a list of strings ["a", "b"]. data Setting = TargetOs | TargetArch | TargetPlatformFull @@ -22,8 +22,7 @@ data Setting = TargetOs | ProjectVersion | GhcSourcePath -data SettingList = SrcHcArgs - | ConfCcArgs Stage +data SettingList = ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage @@ -44,7 +43,6 @@ setting key = askConfig $ case key of settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of - SrcHcArgs -> "src-hc-args" ConfCcArgs stage -> "conf-cc-args-stage" ++ show stage ConfCppArgs stage -> "conf-cpp-args-stage" ++ show stage ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show stage diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs new file mode 100644 index 0000000..261ca93 --- /dev/null +++ b/src/Oracles/WindowsRoot.hs @@ -0,0 +1,28 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} + +module Oracles.WindowsRoot ( + windowsRoot, windowsRootOracle + ) where + +import Util +import Oracles.Base +import Data.List + +newtype WindowsRoot = WindowsRoot () + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +-- Looks up cygwin/msys root on Windows +windowsRoot :: Action String +windowsRoot = askOracle $ WindowsRoot () + +-- Oracle for windowsRoot. This operation requires caching as looking up +-- the root is slow (at least the current implementation). +windowsRootOracle :: Rules () +windowsRootOracle = do + root <- newCache $ \() -> do + Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] + let root = dropWhileEnd isSpace out + putOracle $ "Detected root on Windows: " ++ root + return root + addOracle $ \WindowsRoot{} -> root () + return () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 7c646be..ba15031 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -5,9 +5,13 @@ module Rules.Oracles ( import Oracles.Base import Oracles.ArgsHash import Oracles.PackageData +import Oracles.WindowsRoot import Oracles.DependencyList -import Data.Monoid oracleRules :: Rules () -oracleRules = - configOracle <> packageDataOracle <> dependencyListOracle <> argsHashOracle +oracleRules = do + configOracle -- see Oracles.Base + packageDataOracle -- see Oracles.PackageData + dependencyListOracle -- see Oracles.DependencyList + argsHashOracle -- see Oracles.ArgsHash + windowsRootOracle -- see Oracles.WindowsRoot diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 78b4f3d..3031093 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -11,6 +11,7 @@ args :: Args args = defaultArgs <> userArgs -- TODO: add all other settings +-- TODO: add src-hc-args = -H32m -O defaultArgs :: Args defaultArgs = mconcat [ cabalArgs From git at git.haskell.org Thu Oct 26 23:13:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop stringly-typed configuration keys. (4512f27) Message-ID: <20171026231342.36BE13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4512f2736c3fec57c6e067c760a229915abff307/ghc >--------------------------------------------------------------- commit 4512f2736c3fec57c6e067c760a229915abff307 Author: Andrey Mokhov Date: Fri Jul 24 00:21:19 2015 +0100 Drop stringly-typed configuration keys. >--------------------------------------------------------------- 4512f2736c3fec57c6e067c760a229915abff307 src/Settings/GhcCabal.hs | 21 ++++++++++----------- src/Settings/Util.hs | 29 ++++++++--------------------- src/Switches.hs | 11 +++++++---- 3 files changed, 25 insertions(+), 36 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 0e4db8f..05ec1fc 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -3,7 +3,6 @@ module Settings.GhcCabal ( ) where import Way -import Stage import Builder import Package import Util @@ -36,7 +35,7 @@ cabalArgs = builder GhcCabal ? do , configureArgs , stage0 ? packageConstraints , with $ Gcc stage - , notStage Stage0 ? with Ld + , notStage0 ? with Ld , with Ar , with Alex , with Happy ] @@ -65,25 +64,25 @@ configureArgs = do let conf key = appendSubD $ "--configure-option=" ++ key cFlags = mconcat [ ccArgs , remove ["-Werror"] - , argStagedConfig "conf-cc-args" ] - ldFlags = ldArgs <> argStagedConfig "conf-gcc-linker-args" - cppFlags = cppArgs <> argStagedConfig "conf-cpp-args" + , argSettingList $ ConfCcArgs stage ] + ldFlags = ldArgs <> (argSettingList $ ConfGccLinkerArgs stage) + cppFlags = cppArgs <> (argSettingList $ ConfCppArgs stage) mconcat [ conf "CFLAGS" cFlags , conf "LDFLAGS" ldFlags , conf "CPPFLAGS" cppFlags , appendSubD "--gcc-options" $ cFlags <> ldFlags - , conf "--with-iconv-includes" $ argConfig "iconv-include-dirs" - , conf "--with-iconv-libraries" $ argConfig "iconv-lib-dirs" - , conf "--with-gmp-includes" $ argConfig "gmp-include-dirs" - , conf "--with-gmp-libraries" $ argConfig "gmp-lib-dirs" + , conf "--with-iconv-includes" $ argSettingList IconvIncludeDirs + , conf "--with-iconv-libraries" $ argSettingList IconvLibDirs + , conf "--with-gmp-includes" $ argSettingList GmpIncludeDirs + , conf "--with-gmp-libraries" $ argSettingList GmpLibDirs -- TODO: why TargetPlatformFull and not host? - , crossCompiling ? (conf "--host" $ argConfig "target-platform-full") + , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" . argM . builderPath $ Gcc stage ] bootPackageDbArgs :: Args bootPackageDbArgs = do - sourcePath <- lift $ askConfig "ghc-source-path" + sourcePath <- lift . setting $ GhcSourcePath arg $ "--package-db=" ++ sourcePath "libraries/bootstrapping.conf" -- This is a positional argument, hence: diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 82be349..5f0d035 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -1,7 +1,7 @@ module Settings.Util ( -- Primitive settings elements arg, argPath, argM, - argConfig, argStagedConfig, argConfigList, argStagedConfigList, + argSetting, argSettingList, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -13,11 +13,11 @@ module Settings.Util ( ) where import Util -import Stage import Builder -import Settings.User -import Oracles.Base import Expression +import Oracles.Base +import Oracles.Setting +import Settings.User -- A single argument. arg :: String -> Args @@ -30,24 +30,11 @@ argPath = append . return . unifyPath argM :: Action String -> Args argM = appendM . fmap return -argConfig :: String -> Args -argConfig = appendM . fmap return . askConfig - -argConfigList :: String -> Args -argConfigList = appendM . fmap words . askConfig +argSetting :: Setting -> Args +argSetting = argM . setting -stagedKey :: Stage -> String -> String -stagedKey stage key = key ++ "-stage" ++ show stage - -argStagedConfig :: String -> Args -argStagedConfig key = do - stage <- asks getStage - argConfig (stagedKey stage key) - -argStagedConfigList :: String -> Args -argStagedConfigList key = do - stage <- asks getStage - argConfigList (stagedKey stage key) +argSettingList :: SettingList -> Args +argSettingList = appendM . settingList -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal appendCcArgs :: [String] -> Args diff --git a/src/Switches.hs b/src/Switches.hs index 8d5e124..3a56a5a 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,5 +1,5 @@ module Switches ( - notStage, stage0, stage1, stage2, + stage0, stage1, stage2, notStage, notStage0, registerPackage, splitObjects ) where @@ -9,9 +9,6 @@ import Oracles.Setting import Expression -- Derived predicates -notStage :: Stage -> Predicate -notStage = notP . stage - stage0 :: Predicate stage0 = stage Stage0 @@ -21,6 +18,12 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 +notStage :: Stage -> Predicate +notStage = notP . stage + +notStage0 :: Predicate +notStage0 = notP stage0 + -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate registerPackage = return True From git at git.haskell.org Thu Oct 26 23:13:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop old src/Package/Data.hs. (9b560ce) Message-ID: <20171026231345.91B553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b560ce0d998e7561d8102a0bfe6a18867f5e621/ghc >--------------------------------------------------------------- commit 9b560ce0d998e7561d8102a0bfe6a18867f5e621 Author: Andrey Mokhov Date: Fri Jul 24 00:25:32 2015 +0100 Drop old src/Package/Data.hs. >--------------------------------------------------------------- 9b560ce0d998e7561d8102a0bfe6a18867f5e621 src/Package/Data.hs | 153 ---------------------------------------------------- 1 file changed, 153 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs deleted file mode 100644 index 03195be..0000000 --- a/src/Package/Data.hs +++ /dev/null @@ -1,153 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package.Data (buildPackageData) where - -import Package.Base -import Targets - -argListDir :: FilePath -argListDir = "shake/arg/buildPackageData" - -libraryArgs :: [Way] -> Args -libraryArgs ways = do - let enable x = ((if x then "--enable-" else "--disable-") ++) - libraryForGhci <- ghcWithInterpreter - && not DynamicGhcPrograms - && vanilla `elem` ways - return $ - [ enable (vanilla `elem` ways) "library-vanilla" - , enable libraryForGhci "library-for-ghci" - , enable (profiling `elem` ways) "library-profiling" - , enable (dynamic `elem` ways) "shared" ] - -configureArgs :: Stage -> Settings -> Args -configureArgs stage settings = - let conf key as = do - s <- unwords <$> args as - unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = [ commonCcArgs `filterOut` ["-Werror"] - , args $ ConfCcArgs stage - -- , customCcArgs settings -- TODO: bring this back - , commonCcWarninigArgs ] -- TODO: check why cflags are glued - ldflags = [ commonLdArgs - , args $ ConfGccLinkerArgs stage - , customLdArgs settings ] - cppflags = [ commonCppArgs - , args $ ConfCppArgs stage - , customCppArgs settings ] - in args [ conf "CFLAGS" cflags - , conf "LDFLAGS" ldflags - , conf "CPPFLAGS" cppflags - , arg $ concat <$> - arg "--gcc-options=" <> args cflags <> arg " " <> args ldflags - , conf "--with-iconv-includes" IconvIncludeDirs - , conf "--with-iconv-libraries" IconvLibDirs - , conf "--with-gmp-includes" GmpIncludeDirs - , conf "--with-gmp-libraries" GmpLibDirs - -- TODO: why TargetPlatformFull and not host? - , when CrossCompiling $ conf "--host" $ arg TargetPlatformFull - , conf "--with-cc" $ arg $ Gcc stage ] - --- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: --- 1) Drop lines containing '$' --- For example, get rid of --- libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ... --- Reason: we don't need them and we can't parse them. --- 2) Replace '/' and '\' with '_' before '=' --- For example libraries/deepseq/dist-install_VERSION = 1.4.0.0 --- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 --- Reason: Shake's built-in makefile parser doesn't recognise slashes - -postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map processLine pkgData - where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line - -bootPkgConstraints :: Args -bootPkgConstraints = args $ do - forM (targetPackagesInStage Stage0) $ \pkg @ (Package _ path cabal _) -> do - let cabalPath = path cabal <.> "cabal" - need [cabalPath] - content <- lines <$> liftIO (readFile cabalPath) - let versionLines = filter (("ersion:" `isPrefixOf`) . drop 1) content - case versionLines of - [versionLine] -> return $ args ["--constraint", cabal ++ " == " - ++ dropWhile (not . isDigit) versionLine] - _ -> redError $ "Cannot determine package version in '" - ++ unifyPath cabalPath ++ "'." - -bootPackageDb :: Args -bootPackageDb = do - top <- showArg GhcSourcePath - arg $ unifyPath $ "--package-db=" ++ top "libraries/bootstrapping.conf" - -cabalArgs :: Package -> TodoItem -> Args -cabalArgs pkg @ (Package _ path _ _) todo @ (stage, dist, settings) = args - [ args ["configure", path, dist] - -- this is a positional argument, hence: - -- * if it is empty, we need to emit one empty string argument - -- * otherwise, we must collapse it into one space-separated string - , arg (unwords <$> customDllArgs settings) - , with $ Ghc stage -- TODO: used to be limited to max stage1 GHC - , with $ GhcPkg stage - , customConfArgs settings - , when (stage == Stage0) bootPackageDb - , libraryArgs =<< ways settings - , when (specified HsColour) $ with HsColour - , configureArgs stage settings - , when (stage == Stage0) bootPkgConstraints - , with $ Gcc stage - , when (stage /= Stage0) $ with Ld - , with Ar - , with Alex - , with Happy ] -- TODO: reorder with's - -ghcPkgArgs :: Package -> TodoItem -> Args -ghcPkgArgs (Package _ path _ _) (stage, dist, _) = args $ - [ arg "update" - , arg "--force" - , arg $ unifyPath $ path dist "inplace-pkg-config" - , when (stage == Stage0) bootPackageDb ] - -buildRule :: Package -> TodoItem -> Rules () -buildRule pkg @ (Package name path cabal _) todo @ (stage, dist, settings) = - let pathDist = path dist - cabalPath = path cabal <.> "cabal" - configure = path "configure" - in - -- All these files are produced by a single run of GhcCabal - (pathDist ) <$> - [ "package-data.mk" - , "haddock-prologue.txt" - , "inplace-pkg-config" - , "setup-config" - , "build" "autogen" "cabal_macros.h" - -- TODO: Is this needed? Also check out Paths_cpsa.hs. - -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" - ] &%> \_ -> do - need [cabalPath] - when (doesFileExist $ configure <.> "ac") $ need [configure] - -- GhcCabal will run the configure script, so we depend on it - -- We still don't know who build the configure script from configure.ac - run GhcCabal $ cabalArgs pkg todo - when (registerPackage settings) $ - run (GhcPkg stage) $ ghcPkgArgs pkg todo - postProcessPackageData $ pathDist "package-data.mk" - -- Finally, record the argument list - need [argListPath argListDir pkg stage] - -argListRule :: Package -> TodoItem -> Rules () -argListRule pkg todo @ (stage, _, _) = - (argListPath argListDir pkg stage) %> \out -> do - -- TODO: depend on ALL source files - need $ ["shake/src/Package/Data.hs"] ++ sourceDependecies - cabalList <- argList GhcCabal $ cabalArgs pkg todo - ghcPkgList <- argList (GhcPkg stage) $ ghcPkgArgs pkg todo - writeFileChanged out $ cabalList ++ "\n" ++ ghcPkgList - --- How to build package-data.mk using GhcCabal to process package.cabal -buildPackageData :: Package -> TodoItem -> Rules () -buildPackageData = argListRule <> buildRule From git at git.haskell.org Thu Oct 26 23:13:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcM builder. (d2dfdfa) Message-ID: <20171026231349.013023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2dfdfa91578e2e4ce5b5419986ea08c50b39e74/ghc >--------------------------------------------------------------- commit d2dfdfa91578e2e4ce5b5419986ea08c50b39e74 Author: Andrey Mokhov Date: Fri Jul 24 04:09:40 2015 +0100 Add GhcM builder. >--------------------------------------------------------------- d2dfdfa91578e2e4ce5b5419986ea08c50b39e74 src/Builder.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 91c6fa3..33735d3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -28,6 +28,7 @@ data Builder = Ar | GhcCabal | Gcc Stage | Ghc Stage + | GhcM Stage | GhcPkg Stage deriving (Show, Eq, Generic) @@ -48,6 +49,8 @@ builderKey builder = case builder of Gcc _ -> "gcc" GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" + -- GhcM is currently a synonym for Ghc (to be called with -M flag) + GhcM stage -> builderKey $ Ghc stage builderPath :: Builder -> Action String builderPath builder = do From git at git.haskell.org Thu Oct 26 23:13:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add apply function for transforming expressions. (505302b) Message-ID: <20171026231352.B77383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/505302b7e32640ed8782bbf6cb45c02d0c58fe0f/ghc >--------------------------------------------------------------- commit 505302b7e32640ed8782bbf6cb45c02d0c58fe0f Author: Andrey Mokhov Date: Fri Jul 24 04:10:50 2015 +0100 Add apply function for transforming expressions. >--------------------------------------------------------------- 505302b7e32640ed8782bbf6cb45c02d0c58fe0f src/Expression.hs | 21 +++++++++++++-------- 1 file changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index f33e236..7ac380d 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -6,7 +6,8 @@ module Expression ( Expr, DiffExpr, fromDiffExpr, Predicate, PredicateLike (..), applyPredicate, (??), Args, Ways, Packages, - append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, + apply, append, appendM, remove, + appendSub, appendSubD, filterSub, removeSub, interpret, interpretExpr, stage, package, builder, file, way ) where @@ -57,15 +58,19 @@ type Packages = DiffExpr [Package] type Ways = DiffExpr [Way] -- Basic operations on expressions: --- 1) append something to an expression +-- 1) transform an expression by applying a given function +apply :: (a -> a) -> DiffExpr a +apply = return . Diff + +-- 2) append something to an expression append :: Monoid a => a -> DiffExpr a -append x = return . Diff $ (<> x) +append x = apply (<> x) --- 2) remove given elements from a list expression +-- 3) remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] -remove xs = return . Diff $ filter (`notElem` xs) +remove xs = apply . filter $ (`notElem` xs) --- 3) apply a predicate to an expression +-- 4) apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate @@ -105,7 +110,7 @@ appendM mx = lift mx >>= append appendSub :: String -> [String] -> Args appendSub prefix xs | xs' == [] = mempty - | otherwise = return . Diff $ go False + | otherwise = apply . go $ False where xs' = filter (/= "") xs go True [] = [] @@ -120,7 +125,7 @@ appendSubD :: String -> Args -> Args appendSubD prefix diffExpr = fromDiffExpr diffExpr >>= appendSub prefix filterSub :: String -> (String -> Bool) -> Args -filterSub prefix p = return . Diff $ map filterSubstr +filterSub prefix p = apply . map $ filterSubstr where filterSubstr s | prefix `isPrefixOf` s = unwords . filter p . words $ s From git at git.haskell.org Thu Oct 26 23:13:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (86b0a17) Message-ID: <20171026231356.188F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86b0a17ad6fab8c9dde6f082b291c2d785f957d0/ghc >--------------------------------------------------------------- commit 86b0a17ad6fab8c9dde6f082b291c2d785f957d0 Author: Andrey Mokhov Date: Fri Jul 24 04:12:31 2015 +0100 Clean up. >--------------------------------------------------------------- 86b0a17ad6fab8c9dde6f082b291c2d785f957d0 src/Package.hs | 1 - src/Rules/Data.hs | 1 - src/Settings/GhcPkg.hs | 2 +- src/Util.hs | 1 + 4 files changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 5d2429f..a007b4e 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -6,7 +6,6 @@ import Util import Data.Function import GHC.Generics import Development.Shake.Classes -import Development.Shake.FilePath -- pkgPath is the path to the source code relative to the root data Package = Package diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 3ce7d08..2a2a995 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -16,7 +16,6 @@ import Rules.Actions import Control.Applicative import Control.Monad.Extra import Development.Shake -import Development.Shake.FilePath -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: StagePackageTarget -> Rules () diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index 83bef1d..8e3a287 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -12,8 +12,8 @@ import Development.Shake.FilePath ghcPkgArgs :: Args ghcPkgArgs = do - pkg <- asks getPackage stage <- asks getStage + pkg <- asks getPackage builder (GhcPkg stage) ? mconcat [ arg "update" , arg "--force" diff --git a/src/Util.hs b/src/Util.hs index 4b1a2c6..7cc38ee 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,7 @@ module Util ( module Data.Char, module System.Console.ANSI, + module Development.Shake.FilePath, replaceIf, replaceEq, replaceSeparators, unifyPath, chunksOfSize, From git at git.haskell.org Thu Oct 26 23:13:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:13:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement expression for GhcM builder. (fcb25e6) Message-ID: <20171026231359.9F7093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fcb25e6e86cd2fa82be62cf8541372ef3fb97c34/ghc >--------------------------------------------------------------- commit fcb25e6e86cd2fa82be62cf8541372ef3fb97c34 Author: Andrey Mokhov Date: Fri Jul 24 04:13:30 2015 +0100 Implement expression for GhcM builder. >--------------------------------------------------------------- fcb25e6e86cd2fa82be62cf8541372ef3fb97c34 src/Settings/Args.hs | 2 + src/Settings/GhcM.hs | 158 +++++++++++++++++++++++++++++++++++++++++++++++++++ src/Settings/Util.hs | 17 ++++++ 3 files changed, 177 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 fcb25e6e86cd2fa82be62cf8541372ef3fb97c34 From git at git.haskell.org Thu Oct 26 23:14:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -/- for combining paths with unification of the result. (179d1cd) Message-ID: <20171026231403.50D8C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/179d1cd8a9dbaa304f51bef9cfbba745940ec2db/ghc >--------------------------------------------------------------- commit 179d1cd8a9dbaa304f51bef9cfbba745940ec2db Author: Andrey Mokhov Date: Fri Jul 24 13:10:57 2015 +0100 Add -/- for combining paths with unification of the result. >--------------------------------------------------------------- 179d1cd8a9dbaa304f51bef9cfbba745940ec2db src/Oracles/Base.hs | 8 +++----- src/Oracles/PackageData.hs | 11 +++++------ src/Package.hs | 2 +- src/Rules.hs | 4 ++-- src/Rules/Config.hs | 6 +++--- src/Rules/Data.hs | 12 ++++++------ src/Settings/GhcCabal.hs | 8 ++++---- src/Settings/GhcM.hs | 20 ++++++++++---------- src/Settings/GhcPkg.hs | 4 ++-- src/Settings/TargetDirectory.hs | 4 ++-- src/Settings/Util.hs | 7 +------ src/Util.hs | 9 ++++++++- 12 files changed, 47 insertions(+), 48 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 179d1cd8a9dbaa304f51bef9cfbba745940ec2db From git at git.haskell.org Thu Oct 26 23:14:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename ask* to get* to avoid mixing up oracles with expressions. (d9d1dd9e) Message-ID: <20171026231406.C449C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9d1dd9ef0d2827579f9c7c647e081156a14c8ab/ghc >--------------------------------------------------------------- commit d9d1dd9ef0d2827579f9c7c647e081156a14c8ab Author: Andrey Mokhov Date: Fri Jul 24 13:15:29 2015 +0100 Rename ask* to get* to avoid mixing up oracles with expressions. >--------------------------------------------------------------- d9d1dd9ef0d2827579f9c7c647e081156a14c8ab src/Settings/GhcM.hs | 30 +++++++++++++++--------------- src/Settings/Util.hs | 10 +++++----- 2 files changed, 20 insertions(+), 20 deletions(-) diff --git a/src/Settings/GhcM.hs b/src/Settings/GhcM.hs index 4f792e0..89c4634 100644 --- a/src/Settings/GhcM.hs +++ b/src/Settings/GhcM.hs @@ -19,9 +19,9 @@ ghcMArgs = do stage <- asks getStage builder (GhcM stage) ? do pkg <- asks getPackage - cppArgs <- askPkgDataList CppArgs - hsArgs <- askPkgDataList HsArgs - hsSrcs <- askHsSources + cppArgs <- getPkgDataList CppArgs + hsArgs <- getPkgDataList HsArgs + hsSrcs <- getHsSources ways <- fromDiffExpr Settings.Ways.ways let buildPath = targetPath stage pkg -/- "build" mconcat @@ -41,9 +41,9 @@ packageGhcArgs :: Args packageGhcArgs = do stage <- asks getStage supportsPackageKey <- lift . flag $ SupportsPackageKey - pkgKey <- askPkgData PackageKey - pkgDepKeys <- askPkgDataList DepKeys - pkgDeps <- askPkgDataList Deps + pkgKey <- getPkgData PackageKey + pkgDepKeys <- getPkgDataList DepKeys + pkgDeps <- getPkgDataList Deps mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" @@ -59,8 +59,8 @@ includeGhcArgs :: Args includeGhcArgs = do stage <- asks getStage pkg <- asks getPackage - srcDirs <- askPkgDataList SrcDirs - includeDirs <- askPkgDataList IncludeDirs + srcDirs <- getPkgDataList SrcDirs + includeDirs <- getPkgDataList IncludeDirs let buildPath = targetPath stage pkg -/- "build" autogenPath = buildPath -/- "autogen" mconcat @@ -74,18 +74,18 @@ includeGhcArgs = do , arg "-optP-include" -- TODO: Shall we also add -cpp? , arg $ "-optP" ++ autogenPath -/- "cabal_macros.h" ] -askHsSources :: Expr [FilePath] -askHsSources = do +getHsSources :: Expr [FilePath] +getHsSources = do stage <- asks getStage pkg <- asks getPackage - srcDirs <- askPkgDataList SrcDirs + srcDirs <- getPkgDataList SrcDirs let autogenPath = targetPath stage pkg -/- "build/autogen" dirs = autogenPath : map (pkgPath pkg -/-) srcDirs - askModuleFiles dirs [".hs", ".lhs"] + getModuleFiles dirs [".hs", ".lhs"] -askModuleFiles :: [FilePath] -> [String] -> Expr [FilePath] -askModuleFiles directories suffixes = do - modules <- askPkgDataList Modules +getModuleFiles :: [FilePath] -> [String] -> Expr [FilePath] +getModuleFiles directories suffixes = do + modules <- getPkgDataList Modules let modPaths = map (replaceEq '.' pathSeparator) modules files <- lift $ forM [ dir -/- modPath ++ suffix | dir <- directories diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 4fadcd7..22ffd29 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -2,7 +2,7 @@ module Settings.Util ( -- Primitive settings elements arg, argM, argSetting, argSettingList, - askPkgData, askPkgDataList, + getPkgData, getPkgDataList, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -34,15 +34,15 @@ argSetting = argM . setting argSettingList :: SettingList -> Args argSettingList = appendM . settingList -askPkgData :: (FilePath -> PackageData) -> Expr String -askPkgData key = do +getPkgData :: (FilePath -> PackageData) -> Expr String +getPkgData key = do stage <- asks getStage pkg <- asks getPackage let path = targetPath stage pkg lift . pkgData . key $ path -askPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] -askPkgDataList key = do +getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] +getPkgDataList key = do stage <- asks getStage pkg <- asks getPackage let path = targetPath stage pkg From git at git.haskell.org Thu Oct 26 23:14:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactoring for consistent interface (getters) for expressions. (ff86f40) Message-ID: <20171026231410.307BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894/ghc >--------------------------------------------------------------- commit ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894 Author: Andrey Mokhov Date: Fri Jul 24 14:07:46 2015 +0100 Refactoring for consistent interface (getters) for expressions. >--------------------------------------------------------------- ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894 src/Expression.hs | 31 ++++++++++++++++---- src/Rules/Actions.hs | 3 +- src/Rules/Data.hs | 5 ++-- src/Settings/GhcCabal.hs | 12 ++++---- src/Settings/GhcM.hs | 20 ++++++------- src/Settings/GhcPkg.hs | 4 +-- src/Settings/Packages.hs | 5 +++- src/Settings/Util.hs | 27 ++++++++++++------ src/Settings/Ways.hs | 5 +++- src/Switches.hs | 19 +++++++------ src/Target.hs | 73 ++++++++++++++++++++++++------------------------ 11 files changed, 121 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894 From git at git.haskell.org Thu Oct 26 23:14:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:10 +0000 (UTC) Subject: [commit: ghc] branch 'wip/nfs-locking' created Message-ID: <20171026231410.81FC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/nfs-locking Referencing: 1cd7473f8e800a99e95180579480a0e62e98040b From git at git.haskell.org Thu Oct 26 23:14:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement buildPackageDependencies rule. (65b298b) Message-ID: <20171026231414.1F9803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65b298b0c7fe85fa106bc7d0558096825eb01e09/ghc >--------------------------------------------------------------- commit 65b298b0c7fe85fa106bc7d0558096825eb01e09 Author: Andrey Mokhov Date: Sat Jul 25 02:05:14 2015 +0100 Implement buildPackageDependencies rule. >--------------------------------------------------------------- 65b298b0c7fe85fa106bc7d0558096825eb01e09 src/Builder.hs | 2 + src/Package/Dependencies.hs | 92 ------------------- src/Rules.hs | 3 +- src/Rules/Actions.hs | 10 +-- src/Rules/Data.hs | 8 +- src/Rules/Dependencies.hs | 210 ++++++-------------------------------------- src/Rules/Package.hs | 5 +- src/Settings/Args.hs | 2 + src/Settings/GccM.hs | 41 +++++++++ src/Settings/GhcM.hs | 104 +++++----------------- src/Settings/GhcPkg.hs | 4 +- src/Settings/User.hs | 2 +- src/Settings/Util.hs | 59 +------------ 13 files changed, 108 insertions(+), 434 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 65b298b0c7fe85fa106bc7d0558096825eb01e09 From git at git.haskell.org Thu Oct 26 23:14:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initial commit (013cf0c) Message-ID: <20171026231414.75A673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/013cf0c23c4926b09d6a10c13170d344ed802a01/ghc >--------------------------------------------------------------- commit 013cf0c23c4926b09d6a10c13170d344ed802a01 Author: Andrey Mokhov Date: Tue Dec 23 17:01:44 2014 +0000 Initial commit >--------------------------------------------------------------- 013cf0c23c4926b09d6a10c13170d344ed802a01 README.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README.md b/README.md new file mode 100644 index 0000000..c7c12b3 --- /dev/null +++ b/README.md @@ -0,0 +1,4 @@ +shaking-up-ghc +============== + +Shaking up GHC From git at git.haskell.org Thu Oct 26 23:14:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a draft description of demo. (4bd8812) Message-ID: <20171026231418.06BC53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4bd88123d1eeb16bfb272768b3ec93a4d503003f/ghc >--------------------------------------------------------------- commit 4bd88123d1eeb16bfb272768b3ec93a4d503003f Author: Andrey Mokhov Date: Sat Jul 25 12:33:33 2015 +0100 Add a draft description of demo. >--------------------------------------------------------------- 4bd88123d1eeb16bfb272768b3ec93a4d503003f doc/demo.txt | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/doc/demo.txt b/doc/demo.txt new file mode 100644 index 0000000..4b6b671 --- /dev/null +++ b/doc/demo.txt @@ -0,0 +1,4 @@ +1. Rebuild only when argument list has changed +2. Rebuild only when package-data.mk contents has changed + +* Add to Settings/GhcPkg.hs: package deepseq ? arg "--force" From git at git.haskell.org Thu Oct 26 23:14:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a brief intro to the project. (bd90cd8) Message-ID: <20171026231418.50BD73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd90cd8e6436d20d933c9b27142cc83defcbe267/ghc >--------------------------------------------------------------- commit bd90cd8e6436d20d933c9b27142cc83defcbe267 Author: Andrey Mokhov Date: Tue Dec 23 17:06:08 2014 +0000 Add a brief intro to the project. >--------------------------------------------------------------- bd90cd8e6436d20d933c9b27142cc83defcbe267 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index c7c12b3..7167e9a 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -shaking-up-ghc +Shaking up GHC ============== -Shaking up GHC +As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). From git at git.haskell.org Thu Oct 26 23:14:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (28a8078) Message-ID: <20171026231422.191353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28a807878a86600df0884fc5ee28be02adc52386/ghc >--------------------------------------------------------------- commit 28a807878a86600df0884fc5ee28be02adc52386 Author: Andrey Mokhov Date: Sat Jul 25 12:33:52 2015 +0100 Clean up. >--------------------------------------------------------------- 28a807878a86600df0884fc5ee28be02adc52386 src/Expression.hs | 21 +++++++- src/Package/Base.hs | 138 +++++++++++++++++++++++------------------------ src/Settings/GccM.hs | 48 ++++++++--------- src/Settings/GhcCabal.hs | 35 ++++++------ src/Settings/GhcM.hs | 59 ++++++++++---------- src/Settings/GhcPkg.hs | 15 +++--- src/Settings/Util.hs | 11 ++++ 7 files changed, 173 insertions(+), 154 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 28a807878a86600df0884fc5ee28be02adc52386 From git at git.haskell.org Thu Oct 26 23:14:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add .gitignore. (c5c557a) Message-ID: <20171026231422.533D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5c557a4fab012d28c8fb5f2b2aacb9f835ef722/ghc >--------------------------------------------------------------- commit c5c557a4fab012d28c8fb5f2b2aacb9f835ef722 Author: Andrey Mokhov Date: Tue Dec 23 17:12:02 2014 +0000 Add .gitignore. >--------------------------------------------------------------- c5c557a4fab012d28c8fb5f2b2aacb9f835ef722 .gitignore | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.gitignore b/.gitignore new file mode 100644 index 0000000..181ccc0 --- /dev/null +++ b/.gitignore @@ -0,0 +1,4 @@ +*.o +*.hi +_shake/ +_build/ From git at git.haskell.org Thu Oct 26 23:14:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add dependencies to Target. (4f2fbbb) Message-ID: <20171026231425.B49723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b/ghc >--------------------------------------------------------------- commit 4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b Author: Andrey Mokhov Date: Sat Jul 25 17:08:35 2015 +0100 Add dependencies to Target. >--------------------------------------------------------------- 4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b src/Expression.hs | 15 +++++++++- src/Rules/Actions.hs | 1 + src/Rules/Data.hs | 17 ++++++----- src/Rules/Dependencies.hs | 18 ++++++----- src/Settings/GccM.hs | 5 ++-- src/Settings/GhcCabal.hs | 1 + src/Settings/GhcM.hs | 19 ------------ src/Settings/Util.hs | 21 +++++++++++++ src/Target.hs | 76 +++++++++++++++++++++++------------------------ 9 files changed, 98 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 4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b From git at git.haskell.org Thu Oct 26 23:14:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add shake launcher. (cf7b65b) Message-ID: <20171026231425.E359D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf7b65b5b200048fd0597ee606ccd876848a3b05/ghc >--------------------------------------------------------------- commit cf7b65b5b200048fd0597ee606ccd876848a3b05 Author: Andrey Mokhov Date: Tue Dec 23 17:28:03 2014 +0000 Add shake launcher. >--------------------------------------------------------------- cf7b65b5b200048fd0597ee606ccd876848a3b05 build.bat | 2 ++ 1 file changed, 2 insertions(+) diff --git a/build.bat b/build.bat new file mode 100644 index 0000000..5400131 --- /dev/null +++ b/build.bat @@ -0,0 +1,2 @@ + at mkdir _shake 2> nul + at ghc --make Main.hs -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:14:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add custom settings for compiler and other packages. (096b595) Message-ID: <20171026231429.A3FF73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/096b595bc7b269be01cca98aa567c540d8bce1fd/ghc >--------------------------------------------------------------- commit 096b595bc7b269be01cca98aa567c540d8bce1fd Author: Andrey Mokhov Date: Sun Jul 26 01:31:40 2015 +0100 Add custom settings for compiler and other packages. >--------------------------------------------------------------- 096b595bc7b269be01cca98aa567c540d8bce1fd src/Oracles/Flag.hs | 15 ++++++++++++- src/Oracles/Setting.hs | 6 +++++- src/Package/Base.hs | 28 ------------------------ src/Settings/Args.hs | 7 ++++++ src/Settings/GhcCabal.hs | 56 +++++++++++++++++++++++++++++++++++++----------- src/Settings/GhcM.hs | 8 +++++-- src/Settings/User.hs | 17 ++++++++++++--- src/Settings/Ways.hs | 19 +++++++++++++++- src/Switches.hs | 5 ++++- src/Util.hs | 2 +- 10 files changed, 113 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 096b595bc7b269be01cca98aa567c540d8bce1fd From git at git.haskell.org Thu Oct 26 23:14:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add top-level build script. (4139a9c) Message-ID: <20171026231429.C41793A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4139a9c49da73acb26756a6be7bf564286a32cf1/ghc >--------------------------------------------------------------- commit 4139a9c49da73acb26756a6be7bf564286a32cf1 Author: Andrey Mokhov Date: Tue Dec 23 17:42:13 2014 +0000 Add top-level build script. >--------------------------------------------------------------- 4139a9c49da73acb26756a6be7bf564286a32cf1 Main.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/Main.hs b/Main.hs new file mode 100644 index 0000000..abfd3ab --- /dev/null +++ b/Main.hs @@ -0,0 +1,10 @@ +import Base +import Config +import Oracles +import Package + +main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do + oracleRules + autoconfRules + configureRules + packageRules From git at git.haskell.org Thu Oct 26 23:14:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Parallelise build by collecting targets and then needing them. (9463852) Message-ID: <20171026231433.629C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/946385207cf7691b7baa05e3003ebfa4fdb29082/ghc >--------------------------------------------------------------- commit 946385207cf7691b7baa05e3003ebfa4fdb29082 Author: Andrey Mokhov Date: Sun Jul 26 17:01:03 2015 +0100 Parallelise build by collecting targets and then needing them. >--------------------------------------------------------------- 946385207cf7691b7baa05e3003ebfa4fdb29082 src/Rules.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index f8fd786..b63687f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,7 +1,7 @@ module Rules ( generateTargets, packageRules, oracleRules, - module Rules.Package, module Rules.Config, + module Rules.Package, ) where import Util @@ -17,12 +17,13 @@ import Development.Shake -- generateTargets needs package-data.mk files of all target packages -- TODO: make interpretDiff total generateTargets :: Rules () -generateTargets = action $ - forM_ [Stage0 ..] $ \stage -> do +generateTargets = action $ do + targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpret (stageTarget stage) packages - forM_ pkgs $ \pkg -> do - need [targetPath stage pkg -/- "build/haskell.deps"] - need [targetPath stage pkg -/- "build/c.deps"] + fmap concat . forM pkgs $ \pkg -> return + [ targetPath stage pkg -/- "build/haskell.deps" + , targetPath stage pkg -/- "build/c.deps" ] + need targets -- TODO: add Stage2 (compiler only?) packageRules :: Rules () From git at git.haskell.org Thu Oct 26 23:14:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Base.hs (basic datatypes and imports for the build system). (4e03b1c) Message-ID: <20171026231433.885FB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9/ghc >--------------------------------------------------------------- commit 4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9 Author: Andrey Mokhov Date: Tue Dec 23 17:44:51 2014 +0000 Add Base.hs (basic datatypes and imports for the build system). >--------------------------------------------------------------- 4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9 Base.hs | 45 +++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 45 insertions(+) diff --git a/Base.hs b/Base.hs new file mode 100644 index 0000000..7e130c2 --- /dev/null +++ b/Base.hs @@ -0,0 +1,45 @@ +{-# LANGUAGE FlexibleInstances #-} + +module Base ( + module Development.Shake, + module Development.Shake.FilePath, + module Control.Applicative, + module Data.Monoid, + Stage (..), + Args, arg, Condition, + joinArgs, joinArgsWithSpaces, + filterOut, + ) where + +import Development.Shake hiding ((*>)) +import Development.Shake.FilePath +import Control.Applicative +import Data.Monoid +import Data.List + +data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) + +type Args = Action [String] + +type Condition = Action Bool + +instance Monoid a => Monoid (Action a) where + mempty = return mempty + mappend p q = mappend <$> p <*> q + +arg :: [String] -> Args +arg = return + +intercalateArgs :: String -> Args -> Args +intercalateArgs s args = do + as <- args + return [intercalate s as] + +joinArgsWithSpaces :: Args -> Args +joinArgsWithSpaces = intercalateArgs " " + +joinArgs :: Args -> Args +joinArgs = intercalateArgs "" + +filterOut :: Args -> [String] -> Args +filterOut args list = filter (`notElem` list) <$> args From git at git.haskell.org Thu Oct 26 23:14:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for resources. Limit parallelism of ghc-pkg. (6547fc7) Message-ID: <20171026231436.F18823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6547fc76758720a51f4b0d4819b95128892be459/ghc >--------------------------------------------------------------- commit 6547fc76758720a51f4b0d4819b95128892be459 Author: Andrey Mokhov Date: Sun Jul 26 17:03:36 2015 +0100 Add support for resources. Limit parallelism of ghc-pkg. >--------------------------------------------------------------- 6547fc76758720a51f4b0d4819b95128892be459 src/Rules/Actions.hs | 33 ++++++++++++++++----------------- src/Rules/Data.hs | 39 ++++++++++++++++++++++----------------- src/Target.hs | 5 +++-- 3 files changed, 41 insertions(+), 36 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 055931e..2730c55 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,5 +1,5 @@ module Rules.Actions ( - build, buildWhen, run, verboseRun + build, buildWithResources, run, verboseRun ) where import Util @@ -11,38 +11,37 @@ import Settings.Util import Oracles.ArgsHash import Development.Shake --- Build a given target using an appropriate builder. Force a rebuilt if the --- argument list has changed since the last built (that is, track changes in --- the build system). -build :: FullTarget -> Action () -build target = do +-- Build a given target using an appropriate builder and acquiring necessary +-- resources. Force a rebuilt if the argument list has changed since the last +-- built (that is, track changes in the build system). +buildWithResources :: [(Resource, Int)] -> FullTarget -> Action () +buildWithResources rs target = do need $ Target.dependencies target argList <- interpret target args -- The line below forces the rule to be rerun if the args hash has changed argsHash <- askArgsHash target - run (Target.builder target) argList + run rs (Target.builder target) argList -buildWhen :: Predicate -> FullTarget -> Action () -buildWhen predicate target = do - bool <- interpretExpr target predicate - when bool $ build target +-- Most targets are built without explicitly acquiring resources +build :: FullTarget -> Action () +build = buildWithResources [] -- Run the builder with a given collection of arguments -verboseRun :: Builder -> [String] -> Action () -verboseRun builder args = do +verboseRun :: [(Resource, Int)] -> Builder -> [String] -> Action () +verboseRun rs builder args = do needBuilder builder path <- builderPath builder - cmd [path] args + withResources rs $ cmd [path] args -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. -run :: Builder -> [String] -> Action () -run builder args = do +run :: [(Resource, Int)] -> Builder -> [String] -> Action () +run rs builder args = do putColoured White $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" mapM_ (putColoured White . ("| " ++)) $ interestingInfo builder args putColoured White $ "\\--------" - quietly $ verboseRun builder args + quietly $ verboseRun rs builder args interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index b48ff48..d60dbfa 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -12,31 +12,36 @@ import Control.Applicative import Control.Monad.Extra import Development.Shake +-- TODO: Add ordering between packages? (see ghc.mk) -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: StagePackageTarget -> Rules () -buildPackageData target = +buildPackageData target = do let stage = Target.stage target pkg = Target.package target path = targetPath stage pkg cabal = pkgPath pkg -/- pkgCabal pkg configure = pkgPath pkg -/- "configure" - in + + -- We do not allow parallel invokations of ghc-pkg (they don't work) + ghcPkg <- newResource "ghc-pkg" 1 + (path -/-) <$> - [ "package-data.mk" - , "haddock-prologue.txt" - , "inplace-pkg-config" - , "setup-config" - , "build" -/- "autogen" -/- "cabal_macros.h" - -- TODO: Is this needed? Also check out Paths_cpsa.hs. - -- , "build" -/- "autogen" -/- ("Paths_" ++ name) <.> "hs" - ] &%> \files -> do - -- GhcCabal may run the configure script, so we depend on it - -- We still don't know who built the configure script from configure.ac - whenM (doesFileExist $ configure <.> "ac") $ need [configure] - build $ fullTarget target [cabal] GhcCabal files - buildWhen registerPackage $ - fullTarget target [cabal] (GhcPkg stage) files - postProcessPackageData $ path -/- "package-data.mk" + [ "package-data.mk" + , "haddock-prologue.txt" + , "inplace-pkg-config" + , "setup-config" + , "build" -/- "autogen" -/- "cabal_macros.h" + -- TODO: Is this needed? Also check out Paths_cpsa.hs. + -- , "build" -/- "autogen" -/- ("Paths_" ++ name) <.> "hs" + ] &%> \files -> do + -- GhcCabal may run the configure script, so we depend on it + -- We don't know who built the configure script from configure.ac + whenM (doesFileExist $ configure <.> "ac") $ need [configure] + build $ fullTarget target [cabal] GhcCabal files + whenM (interpretExpr target registerPackage) . + buildWithResources [(ghcPkg, 1)] $ + fullTarget target [cabal] (GhcPkg stage) files + postProcessPackageData $ path -/- "package-data.mk" -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' diff --git a/src/Target.hs b/src/Target.hs index c3b6b93..dc0bde7 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} module Target ( Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), - stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay + stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay, ) where import Way @@ -72,7 +72,8 @@ fullTarget target deps b fs = target } -- Use this function to be explicit about the build way. -fullTargetWithWay :: StagePackageTarget -> [FilePath] -> Builder -> Way -> [FilePath] -> FullTarget +fullTargetWithWay :: StagePackageTarget -> [FilePath] -> Builder -> Way + -> [FilePath] -> FullTarget fullTargetWithWay target deps b w fs = target { dependencies = deps, From git at git.haskell.org Thu Oct 26 23:14:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix custom settings of the compiler package. (3090409) Message-ID: <20171026231441.278823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3090409f9a90cda50892d25f02ea3e3a55f43121/ghc >--------------------------------------------------------------- commit 3090409f9a90cda50892d25f02ea3e3a55f43121 Author: Andrey Mokhov Date: Sun Jul 26 17:04:23 2015 +0100 Fix custom settings of the compiler package. >--------------------------------------------------------------- 3090409f9a90cda50892d25f02ea3e3a55f43121 src/Settings/GhcCabal.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index cba05cc..2c475ab 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -149,6 +149,7 @@ customPackageArgs = do , package compiler ? builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (succ stage) + , arg $ "--flags=stage" ++ show (succ stage) , arg "--disable-library-for-ghci" , targetOs "openbsd" ? arg "--ld-options=-E" , flag GhcUnregisterised ? arg "--ghc-option=-DNO_REGS" @@ -157,7 +158,8 @@ customPackageArgs = do , (threaded `elem` rtsWays) ? notStage0 ? arg "--ghc-option=-optc-DTHREADED_RTS" , ghcWithNativeCodeGen ? arg "--flags=ncg" - , ghcWithInterpreter ? arg "--flags=ghci" + , ghcWithInterpreter ? + notStage0 ? arg "--flags=ghci" , ghcWithInterpreter ? ghcEnableTablesNextToCode ? notP (flag GhcUnregisterised) ? From git at git.haskell.org Thu Oct 26 23:14:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Config.hs (autoconf and configure rules). (9566d56) Message-ID: <20171026231437.2A7183A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9566d564272d1762d8f0eca492b17673ca0af55c/ghc >--------------------------------------------------------------- commit 9566d564272d1762d8f0eca492b17673ca0af55c Author: Andrey Mokhov Date: Tue Dec 23 17:45:51 2014 +0000 Add Config.hs (autoconf and configure rules). >--------------------------------------------------------------- 9566d564272d1762d8f0eca492b17673ca0af55c Config.hs | 24 ++++++++++++++++++++++++ 1 file changed, 24 insertions(+) diff --git a/Config.hs b/Config.hs new file mode 100644 index 0000000..a370f38 --- /dev/null +++ b/Config.hs @@ -0,0 +1,24 @@ +module Config ( + autoconfRules, configureRules + ) where + +import Development.Shake +import Development.Shake.Command +import Development.Shake.FilePath +import Development.Shake.Rule +import Control.Applicative +import Control.Monad +import Base +import Oracles + +autoconfRules :: Rules () +autoconfRules = do + "shake/configure" %> \out -> do + need ["shake/configure.ac"] + cmd $ "bash shake/autoconf" + +configureRules :: Rules () +configureRules = do + "shake/default.config" %> \out -> do + need ["shake/default.config.in", "shake/configure"] + cmd $ "bash shake/configure" From git at git.haskell.org Thu Oct 26 23:14:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Oracles.hs (configuration infrastructure). (cb701bb) Message-ID: <20171026231441.50B283A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb701bb1c14ea9db25b433778c6a6a05d506dc2f/ghc >--------------------------------------------------------------- commit cb701bb1c14ea9db25b433778c6a6a05d506dc2f Author: Andrey Mokhov Date: Tue Dec 23 17:46:41 2014 +0000 Add Oracles.hs (configuration infrastructure). >--------------------------------------------------------------- cb701bb1c14ea9db25b433778c6a6a05d506dc2f Oracles.hs | 250 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 250 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 cb701bb1c14ea9db25b433778c6a6a05d506dc2f From git at git.haskell.org Thu Oct 26 23:14:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add to demo.txt. (140376a) Message-ID: <20171026231444.E55513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/140376acfd4cedd015f436f83ea30abf3aaed848/ghc >--------------------------------------------------------------- commit 140376acfd4cedd015f436f83ea30abf3aaed848 Author: Andrey Mokhov Date: Mon Jul 27 02:03:46 2015 +0100 Add to demo.txt. >--------------------------------------------------------------- 140376acfd4cedd015f436f83ea30abf3aaed848 doc/demo.txt | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/doc/demo.txt b/doc/demo.txt index 4b6b671..cec474a 100644 --- a/doc/demo.txt +++ b/doc/demo.txt @@ -2,3 +2,8 @@ 2. Rebuild only when package-data.mk contents has changed * Add to Settings/GhcPkg.hs: package deepseq ? arg "--force" + +3. Reduce complexity when searching for source files by 40x: + +* compiler, was: 25 dirs (24 source dirs + autogen) x 406 modules x 2 extensions = 20300 candidates +* compiler, now: 25 dirs x 20 module-dirs = 500 candidates \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:14:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Packages.hs (package build rules). (c8212ad) Message-ID: <20171026231445.1DD583A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8212add0d0e343652406f994b6c2c5ff36a5a37/ghc >--------------------------------------------------------------- commit c8212add0d0e343652406f994b6c2c5ff36a5a37 Author: Andrey Mokhov Date: Tue Dec 23 17:47:37 2014 +0000 Add Packages.hs (package build rules). >--------------------------------------------------------------- c8212add0d0e343652406f994b6c2c5ff36a5a37 Package.hs | 196 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 196 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 c8212add0d0e343652406f994b6c2c5ff36a5a37 From git at git.haskell.org Thu Oct 26 23:14:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve performance of getHsSources. (3122d3a) Message-ID: <20171026231448.81B853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3122d3a2b9fe8ed79df55edd09b1cb12b1d9cdba/ghc >--------------------------------------------------------------- commit 3122d3a2b9fe8ed79df55edd09b1cb12b1d9cdba Author: Andrey Mokhov Date: Mon Jul 27 02:04:34 2015 +0100 Improve performance of getHsSources. >--------------------------------------------------------------- 3122d3a2b9fe8ed79df55edd09b1cb12b1d9cdba src/Oracles/DependencyList.hs | 3 --- src/Oracles/PackageData.hs | 2 +- src/Package/Base.hs | 60 ------------------------------------------- src/Rules/Actions.hs | 2 +- src/Settings/Util.hs | 32 +++++++++++++++++++++-- src/Util.hs | 7 ++++- 6 files changed, 38 insertions(+), 68 deletions(-) diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs index 76d7eac..0ad9267 100644 --- a/src/Oracles/DependencyList.hs +++ b/src/Oracles/DependencyList.hs @@ -38,6 +38,3 @@ dependencyListOracle = do addOracle $ \(DependencyListKey (file, obj)) -> Map.lookup (unifyPath obj) <$> deps (unifyPath file) return () - -bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) -bimap f g (x, y) = (f x, g y) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index fd30cc3..579312f 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -90,6 +90,6 @@ packageDataOracle = do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> + addOracle $ \(PackageDataKey (file, key)) -> do Map.lookup key <$> pkgData (unifyPath file) return () diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 3e2eb37..1f9d2c8 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -23,52 +23,6 @@ import Oracles import Settings import qualified System.Directory as S ---pathArgs :: ShowArgs a => String -> FilePath -> a -> Args ---pathArgs key path as = map (\a -> key ++ unifyPath (path a)) <$> args as - --- prefixedPath :: String -> [Settings] -> Settings --- prefixedPath prefix = argPrefix prefix . argConcatPath . sconcat - ---includeGccArgs :: FilePath -> FilePath -> Args ---includeGccArgs path dist = --- let pathDist = path dist --- autogen = pathDist "build/autogen" --- in args [ arg $ "-I" ++ unifyPath autogen --- , pathArgs "-I" path $ IncludeDirs pathDist --- , pathArgs "-I" path $ DepIncludeDirs pathDist ] - - --- includeGccSettings :: Settings --- includeGccSettings = mconcat --- [ prefixedPath "-I" [argBuildPath, argBuildDir, arg "build", arg "autogen"] --- , argPrefix "-I" $ argPaths ... --- , prefixedPath "-I" [argBuildPath, argIncludeDirs ] -- wrong --- , prefixedPath "-I" [argBuildPath, argDepIncludeDirs ]] - --- includeGhcSettings :: Settings --- includeGhcSettings = --- let buildDir = argBuildPath `fence` argSrcDirs --- in arg "-i" `fence` --- mconcat --- [ argPathList "-i" [argBuildPath, argSrcDirs] --- , argPath "-i" buildDir --- , argPath "-I" buildDir --- , argPathList "-i" [buildDir, arg "autogen"] --- , argPathList "-I" [buildDir, arg "autogen"] --- , argPathList "-I" [argBuildPath, argIncludeDirs] --- , arg "-optP-include" -- TODO: Shall we also add -cpp? --- , argPathList "-optP" [buildDir, arg "autogen/cabal_macros.h"] ] - - --- pkgHsSources :: FilePath -> FilePath -> Action [FilePath] --- pkgHsSources path dist = do --- let pathDist = path dist --- autogen = pathDist "build/autogen" --- dirs <- map (path ) <$> args (SrcDirs pathDist) --- findModuleFiles pathDist (autogen:dirs) [".hs", ".lhs"] - --- TODO: look for non-{hs,c} objects too - -- Find Haskell objects we depend on (we don't want to depend on split objects) pkgDepHsObjects :: FilePath -> FilePath -> Way -> Action [FilePath] pkgDepHsObjects path dist way = do @@ -101,20 +55,6 @@ pkgLibHsObjects path dist stage way = do findModuleFiles pathDist [buildDir] [suffix] else do return depObjs --- findModuleFiles :: FilePath -> [FilePath] -> [String] -> Action [FilePath] --- findModuleFiles pathDist directories suffixes = do --- modPaths <- map (replaceEq '.' pathSeparator) <$> args (Modules pathDist) --- fileList <- forM [ dir modPath ++ suffix --- | dir <- directories --- , modPath <- modPaths --- , suffix <- suffixes --- ] $ \file -> do --- let dir = takeDirectory file --- dirExists <- liftIO $ S.doesDirectoryExist dir --- when dirExists $ return $ unifyPath file --- files <- getDirectoryFiles "" fileList --- return $ map unifyPath files - -- The argument list has a limited size on Windows. Since Windows 7 the limit -- is 32768 (theoretically). In practice we use 31000 to leave some breathing -- space for the builder's path & name, auxiliary flags, and other overheads. diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 2730c55..d91cd84 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -50,7 +50,7 @@ interestingInfo builder ss = case builder of Gcc _ -> prefixAndSuffix 0 4 ss GccM _ -> prefixAndSuffix 0 1 ss Ghc _ -> prefixAndSuffix 0 4 ss - GhcM _ -> prefixAndSuffix 1 1 ss + --GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss GhcCabal -> prefixAndSuffix 3 0 ss _ -> ss diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 1e7585e..1901a8c 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -26,6 +26,8 @@ import Oracles.Setting import Oracles.PackageData import Settings.User import Settings.TargetDirectory +import Data.List +import Data.Function -- A single argument. arg :: String -> Args @@ -76,8 +78,34 @@ getHsSources = do path <- getTargetPath pkgPath <- getPackagePath srcDirs <- getPkgDataList SrcDirs - let paths = (path -/- "build/autogen") : map (pkgPath -/-) srcDirs - getSourceFiles paths [".hs", ".lhs"] + modules <- getPkgDataList Modules + let buildPath = path -/- "build" + autogenPath = buildPath -/- "autogen" + dirs = autogenPath : map (pkgPath -/-) srcDirs + decodedMods = sort $ map decodeModule modules + modDirFiles = map (bimap head sort . unzip) + $ groupBy ((==) `on` fst) decodedMods + + result <- lift . fmap concat . forM dirs $ \dir -> do + todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles + forM todo $ \(mDir, mFiles) -> do + let files = [ dir -/- mDir -/- mFile <.> "*hs" | mFile <- mFiles ] + found <- fmap (map unifyPath) $ getDirectoryFiles "" files + return (found, (mDir, map takeBaseName found)) + + let foundSources = concatMap fst result + foundMods = [ (d, f) | (d, fs) <- map snd result, f <- fs ] + leftMods = decodedMods \\ sort foundMods + genSources = map (\(d, f) -> buildPath -/- d -/- f <.> "hs") leftMods + + return $ foundSources ++ genSources + +-- Given a module name extract the directory and file names, e.g.: +-- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +decodeModule :: String -> (FilePath, FilePath) +decodeModule = splitFileName . replaceEq '.' '/' + + -- getSourceFiles paths [".hs", ".lhs"] -- Find all source files in specified paths and with given extensions getSourceFiles :: [FilePath] -> [String] -> Expr [FilePath] diff --git a/src/Util.hs b/src/Util.hs index 7c5f786..fd33e73 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -5,7 +5,8 @@ module Util ( replaceIf, replaceEq, replaceSeparators, unifyPath, (-/-), chunksOfSize, - putColoured, redError, redError_ + putColoured, redError, redError_, + bimap ) where import Data.Char @@ -65,3 +66,7 @@ redError msg = do redError_ :: String -> Action () redError_ = void . redError + +-- Depending on Data.Bifunctor only for this function seems an overkill +bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) +bimap f g (x, y) = (f x, g y) From git at git.haskell.org Thu Oct 26 23:14:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Ways.hs (build ways and helper functions). (9a33083) Message-ID: <20171026231448.B01473A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a33083158e13abb252f3787059e8e2cb5da9215/ghc >--------------------------------------------------------------- commit 9a33083158e13abb252f3787059e8e2cb5da9215 Author: Andrey Mokhov Date: Tue Dec 23 17:53:17 2014 +0000 Add Ways.hs (build ways and helper functions). >--------------------------------------------------------------- 9a33083158e13abb252f3787059e8e2cb5da9215 Ways.hs | 96 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 96 insertions(+) diff --git a/Ways.hs b/Ways.hs new file mode 100644 index 0000000..6e186ab --- /dev/null +++ b/Ways.hs @@ -0,0 +1,96 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module Ways ( + WayUnit (..), + Way, tag, + + allWays, defaultWays, + + vanilla, profiling, logging, parallel, granSim, + threaded, threadedProfiling, threadedLogging, + debug, debugProfiling, threadedDebug, threadedDebugProfiling, + dynamic, profilingDynamic, threadedProfilingDynamic, + threadedDynamic, threadedDebugDynamic, debugDynamic, + loggingDynamic, threadedLoggingDynamic, + + hisuf, osuf, hcsuf + ) where + +import Base +import Oracles + +data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dynamic deriving Eq + +data Way = Way + { + tag :: String, -- e.g., "thr_p" + description :: String, -- e.g., "threaded profiled" + units :: [WayUnit] -- e.g., [Threaded, Profiling] + } + deriving Eq + +vanilla = Way "v" "vanilla" [] +profiling = Way "p" "profiling" [Profiling] +logging = Way "l" "event logging" [Logging] +parallel = Way "mp" "parallel" [Parallel] +granSim = Way "gm" "GranSim" [GranSim] + +-- RTS only ways + +threaded = Way "thr" "threaded" [Threaded] +threadedProfiling = Way "thr_p" "threaded profiling" [Threaded, Profiling] +threadedLogging = Way "thr_l" "threaded event logging" [Threaded, Logging] +debug = Way "debug" "debug" [Debug] +debugProfiling = Way "debug_p" "debug profiling" [Debug, Profiling] +threadedDebug = Way "thr_debug" "threaded debug" [Threaded, Debug] +threadedDebugProfiling = Way "thr_debug_p" "threaded debug profiling" [Threaded, Debug, Profiling] +dynamic = Way "dyn" "dyn" [Dynamic] +profilingDynamic = Way "p_dyn" "p_dyn" [Profiling, Dynamic] +threadedProfilingDynamic = Way "thr_p_dyn" "thr_p_dyn" [Threaded, Profiling, Dynamic] +threadedDynamic = Way "thr_dyn" "thr_dyn" [Threaded, Dynamic] +threadedDebugDynamic = Way "thr_debug_dyn" "thr_debug_dyn" [Threaded, Debug, Dynamic] +debugDynamic = Way "debug_dyn" "debug_dyn" [Debug, Dynamic] +loggingDynamic = Way "l_dyn" "event logging dynamic" [Logging, Dynamic] +threadedLoggingDynamic = Way "thr_l_dyn" "threaded event logging dynamic" [Threaded, Logging, Dynamic] + +allWays = [vanilla, profiling, logging, parallel, granSim, + threaded, threadedProfiling, threadedLogging, + debug, debugProfiling, threadedDebug, threadedDebugProfiling, + dynamic, profilingDynamic, threadedProfilingDynamic, + threadedDynamic, threadedDebugDynamic, debugDynamic, + loggingDynamic, threadedLoggingDynamic] + +-- TODO: what are ways 't' and 's'? +-- ALL_WAYS=v p t l s mp mg debug dyn thr thr_l p_dyn debug_dyn thr_dyn thr_p_dyn thr_debug_dyn thr_p thr_debug debug_p thr_debug_p l_dyn thr_l_dyn + +defaultWays :: Stage -> Action [Way] +defaultWays stage = do + sharedLibs <- test PlatformSupportsSharedLibs + return $ [vanilla] + ++ [profiling | stage /= Stage0] + ++ [dynamic | sharedLibs ] + +wayHcOpts :: Way -> Args +wayHcOpts (Way _ _ units) = + mconcat + [ when (Dynamic `notElem` units) $ arg [ "-static" ] + , when (Dynamic `elem` units) $ arg [ "-fPIC", "-dynamic" ] + , when (Threaded `elem` units) $ arg [ "-optc-DTHREADED_RTS" ] + , when (Debug `elem` units) $ arg [ "-optc-DDEBUG" ] + , when (Profiling `elem` units) $ arg [ "-prof" ] + , when (Logging `elem` units) $ arg [ "-eventlog" ] + , when (Parallel `elem` units) $ arg [ "-parallel" ] + , when (GranSim `elem` units) $ arg [ "-gransim" ] + , when (units == [Debug] || units == [Debug, Dynamic]) $ arg [ "-ticky", "-DTICKY_TICKY" ] + ] + +suffix :: FilePath -> Way -> FilePath +suffix base (Way _ _ units) = + concat $ + ["p_" | Profiling `elem` units] ++ + ["dyn_" | Dynamic `elem` units] ++ + [base ] + +hisuf, osuf, hcsuf :: Way -> FilePath +hisuf = suffix "hi" +osuf = suffix "o" +hcsuf = suffix "hc" From git at git.haskell.org Thu Oct 26 23:14:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add docs (mostly progress comments so far). (c816893) Message-ID: <20171026231452.6C0593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8168933901fda238b9cd2cf30eb5414194816a3/ghc >--------------------------------------------------------------- commit c8168933901fda238b9cd2cf30eb5414194816a3 Author: Andrey Mokhov Date: Tue Dec 23 17:54:46 2014 +0000 Add docs (mostly progress comments so far). >--------------------------------------------------------------- c8168933901fda238b9cd2cf30eb5414194816a3 doc/build-package-data.docx | Bin 0 -> 15964 bytes doc/comment-hi-rule.txt | 39 ++++++ doc/deepseq-build-progress.txt | 300 +++++++++++++++++++++++++++++++++++++++++ 3 files changed, 339 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 c8168933901fda238b9cd2cf30eb5414194816a3 From git at git.haskell.org Thu Oct 26 23:14:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (4364462) Message-ID: <20171026231452.7043D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/436446265ec493014808d9b19dc1f0883bb3e9a8/ghc >--------------------------------------------------------------- commit 436446265ec493014808d9b19dc1f0883bb3e9a8 Author: Andrey Mokhov Date: Tue Jul 28 02:24:04 2015 +0100 Clean up. >--------------------------------------------------------------- 436446265ec493014808d9b19dc1f0883bb3e9a8 src/Oracles/PackageData.hs | 2 +- src/Rules/Actions.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 579312f..fd30cc3 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -90,6 +90,6 @@ packageDataOracle = do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> do + addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> pkgData (unifyPath file) return () diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d91cd84..2730c55 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -50,7 +50,7 @@ interestingInfo builder ss = case builder of Gcc _ -> prefixAndSuffix 0 4 ss GccM _ -> prefixAndSuffix 0 1 ss Ghc _ -> prefixAndSuffix 0 4 ss - --GhcM _ -> prefixAndSuffix 1 1 ss + GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss GhcCabal -> prefixAndSuffix 3 0 ss _ -> ss From git at git.haskell.org Thu Oct 26 23:14:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor findModuleFiles and add comments. (0be1b62) Message-ID: <20171026231455.F0B553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0be1b62e3ca05ce9e4c3da40e972aab9e42f991f/ghc >--------------------------------------------------------------- commit 0be1b62e3ca05ce9e4c3da40e972aab9e42f991f Author: Andrey Mokhov Date: Sat Aug 1 00:19:04 2015 +0100 Refactor findModuleFiles and add comments. >--------------------------------------------------------------- 0be1b62e3ca05ce9e4c3da40e972aab9e42f991f src/Settings/Util.hs | 62 ++++++++++++++++++++++++++++------------------------ src/Util.hs | 11 +++++++++- 2 files changed, 44 insertions(+), 29 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 1901a8c..3ea13e3 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -5,7 +5,7 @@ module Settings.Util ( getFlag, getSetting, getSettingList, getPkgData, getPkgDataList, getPackagePath, getTargetPath, getTargetDirectory, - getHsSources, getSourceFiles, + getHsSources, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -78,44 +78,50 @@ getHsSources = do path <- getTargetPath pkgPath <- getPackagePath srcDirs <- getPkgDataList SrcDirs + + let buildPath = path -/- "build" + dirs = (buildPath -/- "autogen") : map (pkgPath -/-) srcDirs + + (foundSources, missingSources) <- findModuleFiles dirs "*hs" + + -- Generated source files will live in buildPath and have extension "hs" + let generatedSources = map (\f -> buildPath -/- f <.> "hs") missingSources + + return $ foundSources ++ generatedSources + +-- Given a module name extract the directory and file names, e.g.: +-- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +decodeModule :: String -> (FilePath, String) +decodeModule = splitFileName . replaceEq '.' '/' + +-- findModuleFiles scans a list of given directories and finds files matching a +-- given extension pattern (e.g., "*hs") that correspond to modules of the +-- currently built package. Missing module files are returned in a separate +-- list. The returned pair contains the following: +-- * a list of found module files, with paths being relative to one of given +-- directories, e.g. "codeGen/CodeGen/Platform.hs" for the compiler package. +-- * a list of module files that have not been found, with paths being relative +-- to the module directory, e.g. "CodeGen/Platform", and with no extension. +findModuleFiles :: [FilePath] -> FilePattern -> Expr ([FilePath], [FilePath]) +findModuleFiles dirs ext = do modules <- getPkgDataList Modules - let buildPath = path -/- "build" - autogenPath = buildPath -/- "autogen" - dirs = autogenPath : map (pkgPath -/-) srcDirs - decodedMods = sort $ map decodeModule modules + let decodedMods = sort . map decodeModule $ modules modDirFiles = map (bimap head sort . unzip) - $ groupBy ((==) `on` fst) decodedMods + . groupBy ((==) `on` fst) $ decodedMods result <- lift . fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do - let files = [ dir -/- mDir -/- mFile <.> "*hs" | mFile <- mFiles ] + let files = [ dir -/- mDir -/- mFile <.> ext | mFile <- mFiles ] found <- fmap (map unifyPath) $ getDirectoryFiles "" files return (found, (mDir, map takeBaseName found)) - let foundSources = concatMap fst result + let foundFiles = concatMap fst result foundMods = [ (d, f) | (d, fs) <- map snd result, f <- fs ] - leftMods = decodedMods \\ sort foundMods - genSources = map (\(d, f) -> buildPath -/- d -/- f <.> "hs") leftMods - - return $ foundSources ++ genSources - --- Given a module name extract the directory and file names, e.g.: --- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") -decodeModule :: String -> (FilePath, FilePath) -decodeModule = splitFileName . replaceEq '.' '/' + missingMods = decodedMods `minusOrd` sort foundMods + missingFiles = map (uncurry (-/-)) missingMods - -- getSourceFiles paths [".hs", ".lhs"] - --- Find all source files in specified paths and with given extensions -getSourceFiles :: [FilePath] -> [String] -> Expr [FilePath] -getSourceFiles paths exts = do - modules <- getPkgDataList Modules - let modPaths = map (replaceEq '.' '/') modules - candidates = [ p -/- m ++ e | p <- paths, m <- modPaths, e <- exts ] - files <- lift $ filterM (doesDirectoryExist . takeDirectory) candidates - result <- lift $ getDirectoryFiles "" files - return $ map unifyPath result + return (foundFiles, missingFiles) -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal appendCcArgs :: [String] -> Args diff --git a/src/Util.hs b/src/Util.hs index fd33e73..31c0e6a 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -6,7 +6,7 @@ module Util ( unifyPath, (-/-), chunksOfSize, putColoured, redError, redError_, - bimap + bimap, minusOrd ) where import Data.Char @@ -70,3 +70,12 @@ redError_ = void . redError -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) + +-- Depending on Data.List.Ordered only for this function seems an overkill +minusOrd :: Ord a => [a] -> [a] -> [a] +minusOrd [] _ = [] +minusOrd xs [] = xs +minusOrd (x:xs) (y:ys) = case compare x y of + LT -> x : minusOrd xs (y:ys) + EQ -> minusOrd xs ys + GT -> minusOrd (x:xs) ys From git at git.haskell.org Thu Oct 26 23:14:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comment on where this goes in the GHC source tree. (3c08e17) Message-ID: <20171026231456.020FE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c08e170bf0dfdf23ed34cfbc21a2b0286f0e23d/ghc >--------------------------------------------------------------- commit 3c08e170bf0dfdf23ed34cfbc21a2b0286f0e23d Author: Andrey Mokhov Date: Tue Dec 23 17:58:29 2014 +0000 Comment on where this goes in the GHC source tree. >--------------------------------------------------------------- 3c08e170bf0dfdf23ed34cfbc21a2b0286f0e23d README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 7167e9a..54742ee 100644 --- a/README.md +++ b/README.md @@ -2,3 +2,5 @@ Shaking up GHC ============== As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). + +This is supposed to go into the `shake` directory of the GHC source tree (as a submodule). From git at git.haskell.org Thu Oct 26 23:14:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up and optimise performance. (7a936b6) Message-ID: <20171026231459.BF6F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7a936b6313920818057e807b6898390f7c7df2f8/ghc >--------------------------------------------------------------- commit 7a936b6313920818057e807b6898390f7c7df2f8 Author: Andrey Mokhov Date: Sat Aug 1 12:02:45 2015 +0100 Clean up and optimise performance. >--------------------------------------------------------------- 7a936b6313920818057e807b6898390f7c7df2f8 src/Oracles/DependencyList.hs | 12 ++++++------ src/Settings/Util.hs | 19 +++++++++++-------- src/Util.hs | 14 ++++++++++++-- 3 files changed, 29 insertions(+), 16 deletions(-) diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs index 0ad9267..1ffc46d 100644 --- a/src/Oracles/DependencyList.hs +++ b/src/Oracles/DependencyList.hs @@ -21,7 +21,7 @@ newtype DependencyListKey = DependencyListKey (FilePath, FilePath) dependencyList :: FilePath -> FilePath -> Action [FilePath] dependencyList depFile objFile = do res <- askOracle $ DependencyListKey (depFile, objFile) - return $ fromMaybe [] res + return . fromMaybe [] $ res -- Oracle for 'path/dist/*.deps' files dependencyListOracle :: Rules () @@ -30,11 +30,11 @@ dependencyListOracle = do need [file] putOracle $ "Reading " ++ file ++ "..." contents <- parseMakefile <$> (liftIO $ readFile file) - return $ Map.fromList - $ map (bimap unifyPath (map unifyPath)) - $ map (bimap head concat . unzip) - $ groupBy ((==) `on` fst) - $ sortBy (compare `on` fst) contents + return . Map.fromList + . map (bimap unifyPath (map unifyPath)) + . map (bimap head concat . unzip) + . groupBy ((==) `on` fst) + . sortBy (compare `on` fst) $ contents addOracle $ \(DependencyListKey (file, obj)) -> Map.lookup (unifyPath obj) <$> deps (unifyPath file) return () diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 3ea13e3..a9aabba 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -84,7 +84,7 @@ getHsSources = do (foundSources, missingSources) <- findModuleFiles dirs "*hs" - -- Generated source files will live in buildPath and have extension "hs" + -- Generated source files live in buildPath and have extension "hs" let generatedSources = map (\f -> buildPath -/- f <.> "hs") missingSources return $ foundSources ++ generatedSources @@ -103,18 +103,21 @@ decodeModule = splitFileName . replaceEq '.' '/' -- * a list of module files that have not been found, with paths being relative -- to the module directory, e.g. "CodeGen/Platform", and with no extension. findModuleFiles :: [FilePath] -> FilePattern -> Expr ([FilePath], [FilePath]) -findModuleFiles dirs ext = do +findModuleFiles dirs extension = do modules <- getPkgDataList Modules - let decodedMods = sort . map decodeModule $ modules - modDirFiles = map (bimap head sort . unzip) - . groupBy ((==) `on` fst) $ decodedMods + let decodedMods = sort . map decodeModule $ modules + modDirFiles = map (bimap head sort . unzip) + . groupBy ((==) `on` fst) $ decodedMods + matchExtension = (?==) ("*" <.> extension) result <- lift . fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do - let files = [ dir -/- mDir -/- mFile <.> ext | mFile <- mFiles ] - found <- fmap (map unifyPath) $ getDirectoryFiles "" files - return (found, (mDir, map takeBaseName found)) + let fullDir = dir -/- mDir + files <- fmap (filter matchExtension) $ getDirectoryContents fullDir + let cmp fe f = compare (dropExtension fe) f + found = intersectOrd cmp files mFiles + return (map (fullDir -/-) found, (mDir, map dropExtension found)) let foundFiles = concatMap fst result foundMods = [ (d, f) | (d, fs) <- map snd result, f <- fs ] diff --git a/src/Util.hs b/src/Util.hs index 31c0e6a..1c43801 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -6,7 +6,7 @@ module Util ( unifyPath, (-/-), chunksOfSize, putColoured, redError, redError_, - bimap, minusOrd + bimap, minusOrd, intersectOrd ) where import Data.Char @@ -71,7 +71,7 @@ redError_ = void . redError bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) --- Depending on Data.List.Ordered only for this function seems an overkill +-- Depending on Data.List.Ordered only for these two functions seems an overkill minusOrd :: Ord a => [a] -> [a] -> [a] minusOrd [] _ = [] minusOrd xs [] = xs @@ -79,3 +79,13 @@ minusOrd (x:xs) (y:ys) = case compare x y of LT -> x : minusOrd xs (y:ys) EQ -> minusOrd xs ys GT -> minusOrd (x:xs) ys + +intersectOrd :: (a -> b -> Ordering) -> [a] -> [b] -> [a] +intersectOrd cmp = loop + where + loop [] _ = [] + loop _ [] = [] + loop (x:xs) (y:ys) = case cmp x y of + LT -> loop xs (y:ys) + EQ -> x : loop xs ys + GT -> loop (x:xs) ys From git at git.haskell.org Thu Oct 26 23:14:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:14:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add configuration files and dummy builders (autoconf, configure) for debugging. (9089a36) Message-ID: <20171026231459.D57F53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9089a366948907d730e9cc550f209357214be039/ghc >--------------------------------------------------------------- commit 9089a366948907d730e9cc550f209357214be039 Author: Andrey Mokhov Date: Tue Dec 23 18:01:01 2014 +0000 Add configuration files and dummy builders (autoconf, configure) for debugging. >--------------------------------------------------------------- 9089a366948907d730e9cc550f209357214be039 autoconf | 2 ++ configure | 1 + configure.ac | 1 + default.config | 52 ++++++++++++++++++++++++++++++++++++++++++++++++++++ default.config.in | 45 +++++++++++++++++++++++++++++++++++++++++++++ user.config | 1 + 6 files changed, 102 insertions(+) diff --git a/autoconf b/autoconf new file mode 100644 index 0000000..99e5cb3 --- /dev/null +++ b/autoconf @@ -0,0 +1,2 @@ +echo "Running autoconf... (not really)" +echo "$(cat $(dirname $0)/configure.ac) $(date)...\"" > $(dirname $0)/configure diff --git a/configure b/configure new file mode 100644 index 0000000..f51695b --- /dev/null +++ b/configure @@ -0,0 +1 @@ +echo "Running fake configure generated at: Mon, Dec 22, 2014 2:15:52 PM..." diff --git a/configure.ac b/configure.ac new file mode 100644 index 0000000..03184ad --- /dev/null +++ b/configure.ac @@ -0,0 +1 @@ +echo "Running fake configure generated at: diff --git a/default.config b/default.config new file mode 100644 index 0000000..f821e7a --- /dev/null +++ b/default.config @@ -0,0 +1,52 @@ +system-ghc = C:/msys64/usr/local/bin/ghc.exe +system-ghc-pkg = C:/msys64/usr/local/bin/ghc-pkg.exe + +ghc-cabal = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-cabal.exe +ghc-stage1 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage1.exe +ghc-stage2 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage2.exe +ghc-stage3 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage3.exe + +ghc-pkg = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-pkg.exe + +gcc = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/gcc.exe +ld = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ld.exe +ar = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ar.exe +alex = C:/msys64/usr/local/bin/alex.exe +happy = C:/msys64/usr/local/bin/happy.exe +hscolour = + +target-os = mingw32 +target-arch = x86_64 +target-platform-full = x86_64-unknown-mingw32 + +cross-compiling = NO + +conf-cc-args-stage-0 = -fno-stack-protector +conf-cc-args-stage-1 = -fno-stack-protector +conf-cc-args-stage-2 = -fno-stack-protector + +conf-cpp-args-stage-0 = +conf-cpp-args-stage-1 = +conf-cpp-args-stage-2 = + +conf-gcc-linker-args-stage-0 = +conf-gcc-linker-args-stage-1 = +conf-gcc-linker-args-stage-2 = + +conf-ld-linker-args-stage-0 = +conf-ld-linker-args-stage-1 = +conf-ld-linker-args-stage-2 = + +iconv-include-dirs = +iconv-lib-dirs = +gmp-include-dirs = +gmp-lib-dirs = + +lax-dependencies = NO +dynamic-ghc-programs = NO +gcc-is-clang = NO +gcc-lt-46 = NO + + + +host-os-cpp = mingw32 diff --git a/default.config.in b/default.config.in new file mode 100644 index 0000000..4ab5e21 --- /dev/null +++ b/default.config.in @@ -0,0 +1,45 @@ +ghc-cabal = inplace/bin/ghc-cabal at exeext_host@ +ghc = @WithGhc@ +ghc-pkg = @GhcPkgCmd@ +gcc = @WhatGccIsCalled@ +ld = @LdCmd@ +ar = @ArCmd@ +alex = @AlexCmd@ +happy = @HappyCmd@ +hscolour = @HSCOLOUR@ +target-os = @TargetOS_CPP@ +target-arch = @TargetArch_CPP@ +target-platform-full = @TargetPlatformFull@ + +cross-compiling = @CrossCompiling@ + +conf-cc-args-stage-0 = @CONF_CC_OPTS_STAGE0@ +conf-cc-args-stage-1 = @CONF_CC_OPTS_STAGE1@ +conf-cc-args-stage-2 = @CONF_CC_OPTS_STAGE2@ + +conf-cpp-args-stage-0 = @CONF_CPP_OPTS_STAGE0@ +conf-cpp-args-stage-1 = @CONF_CPP_OPTS_STAGE1@ +conf-cpp-args-stage-2 = @CONF_CPP_OPTS_STAGE2@ + +conf-gcc-linker-args-stage-0 = @CONF_GCC_LINKER_OPTS_STAGE0@ +conf-gcc-linker-args-stage-1 = @CONF_GCC_LINKER_OPTS_STAGE1@ +conf-gcc-linker-args-stage-2 = @CONF_GCC_LINKER_OPTS_STAGE2@ + +conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ +conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ +conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ + +iconv-include-dirs = @ICONV_INCLUDE_DIRS@ +iconv-lib-dirs = @ICONV_LIB_DIRS@ + +gmp-include-dirs = @GMP_INCLUDE_DIRS@ +gmp-lib-dirs = @GMP_LIB_DIRS@ + +lax-dependencies = NO +dynamic-ghc-programs = NO +gcc-is-clang = @GccIsClang@ +gcc-lt-46 = @GccLT46@ + + + +host-os-cpp = @HostOS_CPP@ \ No newline at end of file diff --git a/user.config b/user.config new file mode 100644 index 0000000..313d39a --- /dev/null +++ b/user.config @@ -0,0 +1 @@ +lax-dependencies = YES From git at git.haskell.org Thu Oct 26 23:15:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add mk-miner submodule. (8433156) Message-ID: <20171026231503.BDA453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84331560b9ae783af8ce83598b6e4c6ab92d4b8a/ghc >--------------------------------------------------------------- commit 84331560b9ae783af8ce83598b6e4c6ab92d4b8a Author: Andrey Mokhov Date: Wed Dec 24 02:06:09 2014 +0000 Add mk-miner submodule. >--------------------------------------------------------------- 84331560b9ae783af8ce83598b6e4c6ab92d4b8a .gitmodules | 3 +++ mk-miner | 1 + 2 files changed, 4 insertions(+) diff --git a/.gitmodules b/.gitmodules new file mode 100644 index 0000000..8f798aa --- /dev/null +++ b/.gitmodules @@ -0,0 +1,3 @@ +[submodule "mk-miner"] + path = mk-miner + url = https://github.com/snowleopard/mk-miner.git diff --git a/mk-miner b/mk-miner new file mode 160000 index 0000000..566cbc0 --- /dev/null +++ b/mk-miner @@ -0,0 +1 @@ +Subproject commit 566cbc0996a56cdc9297082aca13eb2fd3f64029 From git at git.haskell.org Thu Oct 26 23:15:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Limit parallelism of ghc-cabal. (4e96a03) Message-ID: <20171026231503.C1A513A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e96a03842279f4822ca2b50a7eed7993a3e815a/ghc >--------------------------------------------------------------- commit 4e96a03842279f4822ca2b50a7eed7993a3e815a Author: Andrey Mokhov Date: Sat Aug 1 14:14:42 2015 +0100 Limit parallelism of ghc-cabal. >--------------------------------------------------------------- 4e96a03842279f4822ca2b50a7eed7993a3e815a src/Rules/Data.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index d60dbfa..1114c88 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -37,7 +37,8 @@ buildPackageData target = do -- GhcCabal may run the configure script, so we depend on it -- We don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - build $ fullTarget target [cabal] GhcCabal files + buildWithResources [(ghcPkg, 1)] $ -- GhcCabal calls ghc-pkg too + fullTarget target [cabal] GhcCabal files whenM (interpretExpr target registerPackage) . buildWithResources [(ghcPkg, 1)] $ fullTarget target [cabal] (GhcPkg stage) files From git at git.haskell.org Thu Oct 26 23:15:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve mk-miner submodule. (2a82120) Message-ID: <20171026231507.27D1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2a82120c2ec83683eaa273f87d1d2402606dea69/ghc >--------------------------------------------------------------- commit 2a82120c2ec83683eaa273f87d1d2402606dea69 Author: Andrey Mokhov Date: Thu Dec 25 14:41:26 2014 +0000 Improve mk-miner submodule. >--------------------------------------------------------------- 2a82120c2ec83683eaa273f87d1d2402606dea69 mk-miner | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk-miner b/mk-miner index 566cbc0..276425e 160000 --- a/mk-miner +++ b/mk-miner @@ -1 +1 @@ -Subproject commit 566cbc0996a56cdc9297082aca13eb2fd3f64029 +Subproject commit 276425ea44420f49ac34fd942c0dad84b0c0d332 From git at git.haskell.org Thu Oct 26 23:15:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use fine-grain dependencies in buildPackageDependencies. (4aabd6f) Message-ID: <20171026231507.370173A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4aabd6f2c6818c237b569a4d807e1a29ad72f0f0/ghc >--------------------------------------------------------------- commit 4aabd6f2c6818c237b569a4d807e1a29ad72f0f0 Author: Andrey Mokhov Date: Sat Aug 1 14:16:12 2015 +0100 Use fine-grain dependencies in buildPackageDependencies. >--------------------------------------------------------------- 4aabd6f2c6818c237b569a4d807e1a29ad72f0f0 src/Rules/Dependencies.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 251a233..656e853 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -17,17 +17,17 @@ buildPackageDependencies target = pkg = Target.package target path = targetPath stage pkg buildPath = path -/- "build" + dropBuild = (pkgPath pkg ++) . drop (length buildPath) in do - (buildPath -/- "haskell.deps") %> \file -> do - srcs <- interpretExpr target getHsSources - build $ fullTarget target srcs (GhcM stage) [file] + (buildPath "*.c.deps") %> \depFile -> do + let srcFile = dropBuild . dropExtension $ depFile + build $ fullTarget target [srcFile] (GccM stage) [depFile] (buildPath -/- "c.deps") %> \file -> do srcs <- pkgDataList $ CSrcs path - deps <- forM srcs $ \src -> do - let srcFile = pkgPath pkg -/- src - depFile = buildPath -/- takeFileName src <.> "deps" - build $ fullTarget target [srcFile] (GccM stage) [depFile] - liftIO . readFile $ depFile + deps <- forM srcs $ \src -> readFile' $ buildPath -/- src <.> "deps" writeFileChanged file (concat deps) - liftIO $ removeFiles buildPath ["*.c.deps"] + + (buildPath -/- "haskell.deps") %> \file -> do + srcs <- interpretExpr target getHsSources + build $ fullTarget target srcs (GhcM stage) [file] From git at git.haskell.org Thu Oct 26 23:15:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Moved source files to src subdirectory. (6a7c214) Message-ID: <20171026231511.407753A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a7c2146795131a667ce19c1926fbc0fbbd98ed5/ghc >--------------------------------------------------------------- commit 6a7c2146795131a667ce19c1926fbc0fbbd98ed5 Author: Andrey Mokhov Date: Thu Dec 25 17:51:49 2014 +0000 Moved source files to src subdirectory. >--------------------------------------------------------------- 6a7c2146795131a667ce19c1926fbc0fbbd98ed5 Base.hs => src/Base.hs | 0 Config.hs => src/Config.hs | 0 Main.hs => src/Main.hs | 0 Oracles.hs => src/Oracles.hs | 0 Package.hs => src/Package.hs | 0 Ways.hs => src/Ways.hs | 0 6 files changed, 0 insertions(+), 0 deletions(-) diff --git a/Base.hs b/src/Base.hs similarity index 100% rename from Base.hs rename to src/Base.hs diff --git a/Config.hs b/src/Config.hs similarity index 100% rename from Config.hs rename to src/Config.hs diff --git a/Main.hs b/src/Main.hs similarity index 100% rename from Main.hs rename to src/Main.hs diff --git a/Oracles.hs b/src/Oracles.hs similarity index 100% rename from Oracles.hs rename to src/Oracles.hs diff --git a/Package.hs b/src/Package.hs similarity index 100% rename from Package.hs rename to src/Package.hs diff --git a/Ways.hs b/src/Ways.hs similarity index 100% rename from Ways.hs rename to src/Ways.hs From git at git.haskell.org Thu Oct 26 23:15:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to using Distribution package for parsing cabal files. (f1249da) Message-ID: <20171026231511.34A113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f1249daba280044fc478516d00db75689e128333/ghc >--------------------------------------------------------------- commit f1249daba280044fc478516d00db75689e128333 Author: Andrey Mokhov Date: Sat Aug 1 16:57:13 2015 +0100 Switch to using Distribution package for parsing cabal files. >--------------------------------------------------------------- f1249daba280044fc478516d00db75689e128333 src/Settings/GhcCabal.hs | 28 +++++++++++++++------------- 1 file changed, 15 insertions(+), 13 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 2c475ab..a3d43f7 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -16,8 +16,11 @@ import Settings.User import Settings.Ways import Settings.Util import Settings.Packages -import Data.List -import Control.Applicative +import Data.Version +import qualified Distribution.Package as D +import qualified Distribution.PackageDescription as D +import qualified Distribution.Verbosity as D +import qualified Distribution.PackageDescription.Parse as D cabalArgs :: Args cabalArgs = builder GhcCabal ? do @@ -33,7 +36,7 @@ cabalArgs = builder GhcCabal ? do , libraryArgs , with HsColour , configureArgs - , stage0 ? packageConstraints + , packageConstraints , withStaged Gcc , notStage0 ? with Ld , with Ar @@ -92,20 +95,19 @@ bootPackageDbArgs = do dllArgs :: Args dllArgs = arg "" +-- TODO: speed up by caching the result in Shake database? packageConstraints :: Args -packageConstraints = do +packageConstraints = stage0 ? do pkgs <- getPackages constraints <- lift $ forM pkgs $ \pkg -> do - let cabal = pkgPath pkg -/- pkgCabal pkg - prefix = dropExtension (pkgCabal pkg) ++ " == " + let cabal = pkgPath pkg -/- pkgCabal pkg need [cabal] - content <- lines <$> liftIO (readFile cabal) - let vs = filter (("ersion:" `isPrefixOf`) . drop 1) content - case vs of - [v] -> return $ prefix ++ dropWhile (not . isDigit) v - _ -> redError $ "Cannot determine package version in '" - ++ cabal ++ "'." - append $ concatMap (\c -> ["--constraint", c]) $ constraints + description <- liftIO $ D.readPackageDescription D.silent cabal + let identifier = D.package . D.packageDescription $ description + version = showVersion . D.pkgVersion $ identifier + D.PackageName name = D.pkgName $ identifier + return $ name ++ " == " ++ version + append . concatMap (\c -> ["--constraint", c]) $ constraints -- TODO: should be in a different file -- TODO: put all validating options together in one file From git at git.haskell.org Thu Oct 26 23:15:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to source files. (23c7701) Message-ID: <20171026231514.E0D0E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23c7701c1fab401a45f707c9abac101c6be9ce56/ghc >--------------------------------------------------------------- commit 23c7701c1fab401a45f707c9abac101c6be9ce56 Author: Andrey Mokhov Date: Thu Dec 25 18:13:12 2014 +0000 Fix paths to source files. >--------------------------------------------------------------- 23c7701c1fab401a45f707c9abac101c6be9ce56 build.bat | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 5400131..8e3dba2 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,2 @@ @mkdir _shake 2> nul - at ghc --make Main.hs -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at ghc --make src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:15:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Base.hs with Shake imports and build paths. (44ce571) Message-ID: <20171026231514.E46803A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44ce57199610244416d9c003de42dbca1e1beed0/ghc >--------------------------------------------------------------- commit 44ce57199610244416d9c003de42dbca1e1beed0 Author: Andrey Mokhov Date: Sat Aug 1 17:18:52 2015 +0100 Add Base.hs with Shake imports and build paths. >--------------------------------------------------------------- 44ce57199610244416d9c003de42dbca1e1beed0 src/Base.hs | 20 ++++++++++++++++++++ src/Builder.hs | 1 + src/Expression.hs | 2 +- src/Main.hs | 4 ++-- src/Oracles/ArgsHash.hs | 3 +-- src/Oracles/Base.hs | 13 +------------ src/Oracles/DependencyList.hs | 1 + src/Oracles/Flag.hs | 1 + src/Oracles/PackageData.hs | 1 + src/Oracles/Setting.hs | 1 + src/Oracles/WindowsRoot.hs | 1 + src/Package.hs | 2 +- src/Rules.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Config.hs | 6 ++---- src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Oracles.hs | 1 + src/Rules/Package.hs | 2 +- src/Settings/GhcCabal.hs | 2 +- src/Settings/Util.hs | 2 +- src/Stage.hs | 2 +- src/Target.hs | 2 +- src/Util.hs | 4 +--- src/Way.hs | 5 ++--- 25 files changed, 47 insertions(+), 37 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 44ce57199610244416d9c003de42dbca1e1beed0 From git at git.haskell.org Thu Oct 26 23:15:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Cache computation of boot package constraints in a file. (8e9fe8d) Message-ID: <20171026231518.89B5B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e9fe8d6f6ddbe681073baf1414403a14fe7c8f0/ghc >--------------------------------------------------------------- commit 8e9fe8d6f6ddbe681073baf1414403a14fe7c8f0 Author: Andrey Mokhov Date: Sat Aug 1 18:23:49 2015 +0100 Cache computation of boot package constraints in a file. >--------------------------------------------------------------- 8e9fe8d6f6ddbe681073baf1414403a14fe7c8f0 src/Base.hs | 5 ++++- src/Main.hs | 1 + src/Rules.hs | 5 ++--- src/Rules/Cabal.hs | 29 +++++++++++++++++++++++++++++ src/Rules/Package.hs | 4 +--- src/Settings/Args.hs | 2 +- src/Settings/GhcCabal.hs | 17 +---------------- 7 files changed, 39 insertions(+), 24 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7cf3a4e..5b022e8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,5 +1,5 @@ module Base ( - shakeFilesPath, configPath, + shakeFilesPath, configPath, bootPackageConstraints, module Development.Shake, module Development.Shake.Util, module Development.Shake.Config, @@ -18,3 +18,6 @@ shakeFilesPath = "_build/" configPath :: FilePath configPath = "shake/cfg/" + +bootPackageConstraints :: FilePath +bootPackageConstraints = shakeFilesPath ++ "boot-package-constraints" diff --git a/src/Main.hs b/src/Main.hs index c7e076a..ffbd7c0 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,6 +3,7 @@ import Rules main = shakeArgs shakeOptions{shakeFiles = shakeFilesPath} $ do oracleRules -- see module Rules.Oracles + cabalRules -- see module Rules.Cabal packageRules -- see module Rules configRules -- see module Rules.Config generateTargets -- see module Rules diff --git a/src/Rules.hs b/src/Rules.hs index 6d153e1..002eda2 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,13 +1,12 @@ module Rules ( - generateTargets, packageRules, oracleRules, - module Rules.Config, - module Rules.Package, + oracleRules, cabalRules, configRules, packageRules, generateTargets ) where import Base import Util import Stage import Expression +import Rules.Cabal import Rules.Config import Rules.Package import Rules.Oracles diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs new file mode 100644 index 0000000..adcb57e --- /dev/null +++ b/src/Rules/Cabal.hs @@ -0,0 +1,29 @@ +module Rules.Cabal (cabalRules) where + +import Base +import Util +import Stage +import Package +import Expression +import Settings.Packages +import Data.List +import Data.Version +import qualified Distribution.Package as D +import qualified Distribution.PackageDescription as D +import qualified Distribution.Verbosity as D +import qualified Distribution.PackageDescription.Parse as D + +cabalRules :: Rules () +cabalRules = + -- Cache boot package constraints (to be used in cabalArgs) + bootPackageConstraints %> \file -> do + pkgs <- interpret (stageTarget Stage0) packages + constraints <- forM (sort pkgs) $ \pkg -> do + let cabal = pkgPath pkg -/- pkgCabal pkg + need [cabal] + descr <- liftIO $ D.readPackageDescription D.silent cabal + let identifier = D.package . D.packageDescription $ descr + version = showVersion . D.pkgVersion $ identifier + D.PackageName name = D.pkgName $ identifier + return $ name ++ " == " ++ version + writeFileChanged file . unlines $ constraints diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index a6365e8..ff64832 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -1,6 +1,4 @@ -module Rules.Package ( - buildPackage - ) where +module Rules.Package (buildPackage) where import Base import Expression diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index be6ac42..d698017 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -2,12 +2,12 @@ module Settings.Args ( args ) where +import Expression import Settings.User import Settings.GhcM import Settings.GccM import Settings.GhcPkg import Settings.GhcCabal -import Expression args :: Args args = defaultArgs <> userArgs diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 092f97a..315df12 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -15,12 +15,6 @@ import Oracles.Setting import Settings.User import Settings.Ways import Settings.Util -import Settings.Packages -import Data.Version -import qualified Distribution.Package as D -import qualified Distribution.PackageDescription as D -import qualified Distribution.Verbosity as D -import qualified Distribution.PackageDescription.Parse as D cabalArgs :: Args cabalArgs = builder GhcCabal ? do @@ -95,18 +89,9 @@ bootPackageDbArgs = do dllArgs :: Args dllArgs = arg "" --- TODO: speed up by caching the result in Shake database? packageConstraints :: Args packageConstraints = stage0 ? do - pkgs <- getPackages - constraints <- lift $ forM pkgs $ \pkg -> do - let cabal = pkgPath pkg -/- pkgCabal pkg - need [cabal] - description <- liftIO $ D.readPackageDescription D.silent cabal - let identifier = D.package . D.packageDescription $ description - version = showVersion . D.pkgVersion $ identifier - D.PackageName name = D.pkgName $ identifier - return $ name ++ " == " ++ version + constraints <- lift . readFileLines $ bootPackageConstraints append . concatMap (\c -> ["--constraint", c]) $ constraints -- TODO: should be in a different file From git at git.haskell.org Thu Oct 26 23:15:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove the generated 'configure' script from the repository. (8b10b13) Message-ID: <20171026231518.96AA43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8b10b133351866f8fabd033d402c32613209f63f/ghc >--------------------------------------------------------------- commit 8b10b133351866f8fabd033d402c32613209f63f Author: Andrey Mokhov Date: Thu Dec 25 18:18:01 2014 +0000 Remove the generated 'configure' script from the repository. >--------------------------------------------------------------- 8b10b133351866f8fabd033d402c32613209f63f configure | 1 - 1 file changed, 1 deletion(-) diff --git a/configure b/configure deleted file mode 100644 index f51695b..0000000 --- a/configure +++ /dev/null @@ -1 +0,0 @@ -echo "Running fake configure generated at: Mon, Dec 22, 2014 2:15:52 PM..." From git at git.haskell.org Thu Oct 26 23:15:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Stop tracking the generated 'configure' script. (dfd6b21) Message-ID: <20171026231522.059543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfd6b21aefaffea5f1e9f263dd4b115f2ff73094/ghc >--------------------------------------------------------------- commit dfd6b21aefaffea5f1e9f263dd4b115f2ff73094 Author: Andrey Mokhov Date: Thu Dec 25 18:19:49 2014 +0000 Stop tracking the generated 'configure' script. >--------------------------------------------------------------- dfd6b21aefaffea5f1e9f263dd4b115f2ff73094 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 181ccc0..30e2546 100644 --- a/.gitignore +++ b/.gitignore @@ -2,3 +2,4 @@ *.hi _shake/ _build/ +configure From git at git.haskell.org Thu Oct 26 23:15:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Configure packages in dependency order, refactor resources. (49c3bb1) Message-ID: <20171026231522.122EA3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49c3bb1f7da2677b7ca95ae6db5abee302f2d408/ghc >--------------------------------------------------------------- commit 49c3bb1f7da2677b7ca95ae6db5abee302f2d408 Author: Andrey Mokhov Date: Sun Aug 2 03:28:14 2015 +0100 Configure packages in dependency order, refactor resources. >--------------------------------------------------------------- 49c3bb1f7da2677b7ca95ae6db5abee302f2d408 doc/demo.txt | 5 +++++ src/Base.hs | 6 +++++- src/Main.hs | 1 + src/Oracles/Base.hs | 4 ---- src/Oracles/DependencyList.hs | 1 - src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 33 +++++++++++++++++++++++++++++++++ src/Oracles/WindowsRoot.hs | 1 - src/Rules.hs | 6 ++++-- src/Rules/Actions.hs | 32 ++++++++++++-------------------- src/Rules/Cabal.hs | 40 +++++++++++++++++++++++++++++----------- src/Rules/Data.hs | 29 ++++++++++++++++++++++------- src/Rules/Dependencies.hs | 5 +++-- src/Rules/Oracles.hs | 2 ++ src/Rules/Package.hs | 3 ++- src/Rules/Resources.hs | 20 ++++++++++++++++++++ src/Util.hs | 11 ++++++++++- 17 files changed, 148 insertions(+), 52 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 49c3bb1f7da2677b7ca95ae6db5abee302f2d408 From git at git.haskell.org Thu Oct 26 23:15:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove fake autoconf. (232891d) Message-ID: <20171026231525.C54453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/232891d32c497c3901495e3a53745dd68c859d38/ghc >--------------------------------------------------------------- commit 232891d32c497c3901495e3a53745dd68c859d38 Author: Andrey Mokhov Date: Fri Dec 26 22:12:42 2014 +0000 Remove fake autoconf. >--------------------------------------------------------------- 232891d32c497c3901495e3a53745dd68c859d38 autoconf | 2 -- 1 file changed, 2 deletions(-) diff --git a/autoconf b/autoconf deleted file mode 100644 index 99e5cb3..0000000 --- a/autoconf +++ /dev/null @@ -1,2 +0,0 @@ -echo "Running autoconf... (not really)" -echo "$(cat $(dirname $0)/configure.ac) $(date)...\"" > $(dirname $0)/configure From git at git.haskell.org Thu Oct 26 23:15:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow more parallelism in buildPackageData. (61a085c) Message-ID: <20171026231525.D66A73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/61a085c0310dbd583855319be36faf017fe2aaf5/ghc >--------------------------------------------------------------- commit 61a085c0310dbd583855319be36faf017fe2aaf5 Author: Andrey Mokhov Date: Sun Aug 2 03:39:17 2015 +0100 Allow more parallelism in buildPackageData. >--------------------------------------------------------------- 61a085c0310dbd583855319be36faf017fe2aaf5 src/Rules/Data.hs | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 752cde7..adc31f1 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -35,15 +35,17 @@ buildPackageData (Resources ghcCabal ghcPkg) target = do -- TODO: Is this needed? Also check out Paths_cpsa.hs. -- , "build" -/- "autogen" -/- ("Paths_" ++ name) <.> "hs" ] &%> \files -> do - -- GhcCabal may run the configure script, so we depend on it - -- We don't know who built the configure script from configure.ac - whenM (doesFileExist $ configure <.> "ac") $ need [configure] - -- We configure packages in the order of their dependencies deps <- packageDeps . dropExtension . pkgCabal $ pkg pkgs <- interpret target packages let depPkgs = concatMap (maybeToList . findPackage pkgs) deps - need $ map (\p -> targetPath stage p -/- "package-data.mk") depPkgs + + -- GhcCabal may run the configure script, so we depend on it + -- We don't know who built the configure script from configure.ac + needConfigure <- doesFileExist $ configure <.> "ac" + + need $ [ configure | needConfigure ] ++ + [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] buildWithResources [(ghcCabal, 1)] $ fullTarget target [cabal] GhcCabal files From git at git.haskell.org Thu Oct 26 23:15:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify Package. (c677b04) Message-ID: <20171026231529.6F0DF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c677b049c05d9ebae12c1ae516dc094b622d0d8f/ghc >--------------------------------------------------------------- commit c677b049c05d9ebae12c1ae516dc094b622d0d8f Author: Andrey Mokhov Date: Sun Aug 2 14:17:35 2015 +0100 Simplify Package. >--------------------------------------------------------------- c677b049c05d9ebae12c1ae516dc094b622d0d8f src/Oracles/PackageDeps.hs | 14 ++++++++------ src/Package.hs | 31 +++++++++++++++++++------------ src/Rules/Cabal.hs | 13 ++++++------- src/Rules/Data.hs | 23 ++++++++--------------- src/Settings/Default.hs | 11 +++-------- src/Settings/GhcCabal.hs | 5 +++-- 6 files changed, 47 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c677b049c05d9ebae12c1ae516dc094b622d0d8f From git at git.haskell.org Thu Oct 26 23:15:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove fake configure.ac. (42304f9) Message-ID: <20171026231529.6DB5C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/42304f98b15301c4a2feaa3ab80eb26399f8c404/ghc >--------------------------------------------------------------- commit 42304f98b15301c4a2feaa3ab80eb26399f8c404 Author: Andrey Mokhov Date: Fri Dec 26 22:34:15 2014 +0000 Remove fake configure.ac. >--------------------------------------------------------------- 42304f98b15301c4a2feaa3ab80eb26399f8c404 cfg/configure.ac | 1053 ++++++++++++++++++++++++++++++ cfg/default.config | 76 +++ cfg/default.config.in | 76 +++ default.config => cfg/default.config.was | 0 user.config => cfg/user.config | 0 configure.ac | 1 - 6 files changed, 1205 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 42304f98b15301c4a2feaa3ab80eb26399f8c404 From git at git.haskell.org Thu Oct 26 23:15:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove generated default.config. (e4d24e1) Message-ID: <20171026231532.D28F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4d24e1f0360dc8c2afd5614f0d27a98e93024cf/ghc >--------------------------------------------------------------- commit e4d24e1f0360dc8c2afd5614f0d27a98e93024cf Author: Andrey Mokhov Date: Fri Dec 26 22:35:20 2014 +0000 Remove generated default.config. >--------------------------------------------------------------- e4d24e1f0360dc8c2afd5614f0d27a98e93024cf default.config | 52 ---------------------------------------------------- 1 file changed, 52 deletions(-) diff --git a/default.config b/default.config deleted file mode 100644 index f821e7a..0000000 --- a/default.config +++ /dev/null @@ -1,52 +0,0 @@ -system-ghc = C:/msys64/usr/local/bin/ghc.exe -system-ghc-pkg = C:/msys64/usr/local/bin/ghc-pkg.exe - -ghc-cabal = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-cabal.exe -ghc-stage1 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage1.exe -ghc-stage2 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage2.exe -ghc-stage3 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage3.exe - -ghc-pkg = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-pkg.exe - -gcc = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/gcc.exe -ld = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ld.exe -ar = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ar.exe -alex = C:/msys64/usr/local/bin/alex.exe -happy = C:/msys64/usr/local/bin/happy.exe -hscolour = - -target-os = mingw32 -target-arch = x86_64 -target-platform-full = x86_64-unknown-mingw32 - -cross-compiling = NO - -conf-cc-args-stage-0 = -fno-stack-protector -conf-cc-args-stage-1 = -fno-stack-protector -conf-cc-args-stage-2 = -fno-stack-protector - -conf-cpp-args-stage-0 = -conf-cpp-args-stage-1 = -conf-cpp-args-stage-2 = - -conf-gcc-linker-args-stage-0 = -conf-gcc-linker-args-stage-1 = -conf-gcc-linker-args-stage-2 = - -conf-ld-linker-args-stage-0 = -conf-ld-linker-args-stage-1 = -conf-ld-linker-args-stage-2 = - -iconv-include-dirs = -iconv-lib-dirs = -gmp-include-dirs = -gmp-lib-dirs = - -lax-dependencies = NO -dynamic-ghc-programs = NO -gcc-is-clang = NO -gcc-lt-46 = NO - - - -host-os-cpp = mingw32 From git at git.haskell.org Thu Oct 26 23:15:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up rules. (5f8abc4) Message-ID: <20171026231532.D8E8E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f8abc4b283d401a7d5b5eb341cab21f799fdf63/ghc >--------------------------------------------------------------- commit 5f8abc4b283d401a7d5b5eb341cab21f799fdf63 Author: Andrey Mokhov Date: Sun Aug 2 14:36:36 2015 +0100 Clean up rules. >--------------------------------------------------------------- 5f8abc4b283d401a7d5b5eb341cab21f799fdf63 src/Rules/Config.hs | 4 ++-- src/Rules/Dependencies.hs | 4 +++- src/Util.hs | 1 - 3 files changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 5946bfb..8d886fa 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -7,10 +7,10 @@ configRules :: Rules () configRules = do configPath -/- "system.config" %> \out -> do need [configPath -/- "system.config.in", "configure"] - putColoured White "Running configure..." + putBuild "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' "configure" %> \out -> do copyFile' (configPath -/- "configure.ac") "configure.ac" - putColoured White $ "Running autoconf..." + putBuild "Running autoconf..." cmd "bash autoconf" -- TODO: get rid of 'bash' diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 92664d2..7fab8cf 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -26,7 +26,9 @@ buildPackageDependencies _ target = (buildPath -/- "c.deps") %> \file -> do srcs <- pkgDataList $ CSrcs path - deps <- forM srcs $ \src -> readFile' $ buildPath -/- src <.> "deps" + let depFiles = [ buildPath -/- src <.> "deps" | src <- srcs ] + need depFiles -- increase parallelism by needing all at once + deps <- mapM readFile' depFiles writeFileChanged file (concat deps) (buildPath -/- "haskell.deps") %> \file -> do diff --git a/src/Util.hs b/src/Util.hs index d8a4db7..70de3ec 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -64,7 +64,6 @@ putOracle = putColoured Blue putBuild :: String -> Action () putBuild = putColoured White - -- A more colourful version of error redError :: String -> Action a redError msg = do From git at git.haskell.org Thu Oct 26 23:15:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move config files to cfg subdirectory. (e89924f) Message-ID: <20171026231536.7D3DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e89924f2e5871fe2b4011b9365ab2ba21083e669/ghc >--------------------------------------------------------------- commit e89924f2e5871fe2b4011b9365ab2ba21083e669 Author: Andrey Mokhov Date: Fri Dec 26 22:36:26 2014 +0000 Move config files to cfg subdirectory. >--------------------------------------------------------------- e89924f2e5871fe2b4011b9365ab2ba21083e669 default.config.in | 45 --------------------------------------------- user.config | 1 - 2 files changed, 46 deletions(-) diff --git a/default.config.in b/default.config.in deleted file mode 100644 index 4ab5e21..0000000 --- a/default.config.in +++ /dev/null @@ -1,45 +0,0 @@ -ghc-cabal = inplace/bin/ghc-cabal at exeext_host@ -ghc = @WithGhc@ -ghc-pkg = @GhcPkgCmd@ -gcc = @WhatGccIsCalled@ -ld = @LdCmd@ -ar = @ArCmd@ -alex = @AlexCmd@ -happy = @HappyCmd@ -hscolour = @HSCOLOUR@ -target-os = @TargetOS_CPP@ -target-arch = @TargetArch_CPP@ -target-platform-full = @TargetPlatformFull@ - -cross-compiling = @CrossCompiling@ - -conf-cc-args-stage-0 = @CONF_CC_OPTS_STAGE0@ -conf-cc-args-stage-1 = @CONF_CC_OPTS_STAGE1@ -conf-cc-args-stage-2 = @CONF_CC_OPTS_STAGE2@ - -conf-cpp-args-stage-0 = @CONF_CPP_OPTS_STAGE0@ -conf-cpp-args-stage-1 = @CONF_CPP_OPTS_STAGE1@ -conf-cpp-args-stage-2 = @CONF_CPP_OPTS_STAGE2@ - -conf-gcc-linker-args-stage-0 = @CONF_GCC_LINKER_OPTS_STAGE0@ -conf-gcc-linker-args-stage-1 = @CONF_GCC_LINKER_OPTS_STAGE1@ -conf-gcc-linker-args-stage-2 = @CONF_GCC_LINKER_OPTS_STAGE2@ - -conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ -conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ -conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ - -iconv-include-dirs = @ICONV_INCLUDE_DIRS@ -iconv-lib-dirs = @ICONV_LIB_DIRS@ - -gmp-include-dirs = @GMP_INCLUDE_DIRS@ -gmp-lib-dirs = @GMP_LIB_DIRS@ - -lax-dependencies = NO -dynamic-ghc-programs = NO -gcc-is-clang = @GccIsClang@ -gcc-lt-46 = @GccLT46@ - - - -host-os-cpp = @HostOS_CPP@ \ No newline at end of file diff --git a/user.config b/user.config deleted file mode 100644 index 313d39a..0000000 --- a/user.config +++ /dev/null @@ -1 +0,0 @@ -lax-dependencies = YES From git at git.haskell.org Thu Oct 26 23:15:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid using interpretDiff, use simpler interpret instead. (327b06e) Message-ID: <20171026231536.891413A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/327b06e578a4194368020152bd90b8eb4193dd7a/ghc >--------------------------------------------------------------- commit 327b06e578a4194368020152bd90b8eb4193dd7a Author: Andrey Mokhov Date: Sun Aug 2 15:02:23 2015 +0100 Avoid using interpretDiff, use simpler interpret instead. >--------------------------------------------------------------- 327b06e578a4194368020152bd90b8eb4193dd7a src/Expression.hs | 10 +++++----- src/Oracles/ArgsHash.hs | 2 +- src/Rules.hs | 3 +-- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 4 ++-- src/Rules/Data.hs | 8 ++++---- src/Rules/Dependencies.hs | 2 +- src/Settings/Args.hs | 7 ++++--- src/Settings/Util.hs | 2 +- 9 files changed, 20 insertions(+), 20 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 6ec6ef4..ee8e8f3 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -8,7 +8,7 @@ module Expression ( Args, Ways, Packages, apply, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, - interpret, interpretExpr, + interpret, interpretDiff, getStage, getPackage, getBuilder, getFiles, getFile, getDependencies, getDependency, getWay, stage, package, builder, stagedBuilder, file, way @@ -141,16 +141,16 @@ removeSub :: String -> [String] -> Args removeSub prefix xs = filterSub prefix (`notElem` xs) -- Interpret a given expression in a given environment -interpretExpr :: Target -> Expr a -> Action a -interpretExpr = flip runReaderT +interpret :: Target -> Expr a -> Action a +interpret = flip runReaderT -- Extract an expression from a difference expression fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) -- Interpret a given difference expression in a given environment -interpret :: Monoid a => Target -> DiffExpr a -> Action a -interpret target = interpretExpr target . fromDiffExpr +interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a +interpretDiff target = interpret target . fromDiffExpr -- Convenient getters for target parameters getStage :: Expr Stage diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 1972638..ca0aa6c 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -22,5 +22,5 @@ askArgsHash = askOracle . ArgsHashKey -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () argsHashOracle = do - addOracle $ \(ArgsHashKey target) -> hash <$> interpret target args + addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs return () diff --git a/src/Rules.hs b/src/Rules.hs index e651325..be109f8 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -15,11 +15,10 @@ import Settings.Packages import Settings.TargetDirectory -- generateTargets needs package-data.mk files of all target packages --- TODO: make interpretDiff total generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do - pkgs <- interpret (stageTarget stage) packages + pkgs <- interpret (stageTarget stage) getPackages fmap concat . forM pkgs $ \pkg -> return [ targetPath stage pkg -/- "build/haskell.deps" , targetPath stage pkg -/- "build/c.deps" ] diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 1940a4a..d96157c 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -21,7 +21,7 @@ buildWithResources rs target = do needBuilder builder need deps path <- builderPath builder - argList <- interpret target args + argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed argsHash <- askArgsHash target withResources rs $ do diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 48db356..55d909d 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -16,7 +16,7 @@ cabalRules :: Rules () cabalRules = do -- Cache boot package constraints (to be used in cabalArgs) bootPackageConstraints %> \file -> do - pkgs <- interpret (stageTarget Stage0) packages + pkgs <- interpret (stageTarget Stage0) getPackages constraints <- forM (sort pkgs) $ \pkg -> do let cabal = pkgCabalPath pkg need [cabal] @@ -29,7 +29,7 @@ cabalRules = do -- Cache package dependencies packageDependencies %> \file -> do - pkgs <- interpret (stageTarget Stage1) packages + pkgs <- interpret (stageTarget Stage1) getPackages pkgDeps <- forM (sort pkgs) $ \pkg -> do let cabal = pkgCabalPath pkg need [cabal] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 762115c..8f365e8 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -40,16 +40,16 @@ buildPackageData (Resources ghcCabal ghcPkg) target = do -- We configure packages in the order of their dependencies deps <- packageDeps pkg - pkgs <- interpret target packages - let cmp pkg = compare (pkgName pkg) - depPkgs = intersectOrd cmp (sort pkgs) deps + pkgs <- interpret target getPackages + let cmp pkg name = compare (pkgName pkg) name + depPkgs = intersectOrd cmp (sort pkgs) deps need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] buildWithResources [(ghcCabal, 1)] $ fullTarget target [cabal] GhcCabal files -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg - whenM (interpretExpr target registerPackage) . + whenM (interpret target registerPackage) . buildWithResources [(ghcPkg, 1)] $ fullTarget target [cabal] (GhcPkg stage) files diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 7fab8cf..bee85c6 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -32,5 +32,5 @@ buildPackageDependencies _ target = writeFileChanged file (concat deps) (buildPath -/- "haskell.deps") %> \file -> do - srcs <- interpretExpr target getHsSources + srcs <- interpret target getHsSources build $ fullTarget target srcs (GhcM stage) [file] diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index d698017..4d4dd17 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -1,6 +1,4 @@ -module Settings.Args ( - args - ) where +module Settings.Args (args, getArgs) where import Expression import Settings.User @@ -12,6 +10,9 @@ import Settings.GhcCabal args :: Args args = defaultArgs <> userArgs +getArgs :: Expr [String] +getArgs = fromDiffExpr args + -- TODO: add all other settings -- TODO: add src-hc-args = -H32m -O -- TODO: GhcStage2HcOpts=-O2 unless GhcUnregisterised diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index d2daa0b..d04a12a 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -85,7 +85,7 @@ getHsSources = do (foundSources, missingSources) <- findModuleFiles dirs "*hs" -- Generated source files live in buildPath and have extension "hs" - let generatedSources = map (\f -> buildPath -/- f <.> "hs") missingSources + let generatedSources = [ buildPath -/- s <.> "hs" | s <- missingSources ] return $ foundSources ++ generatedSources From git at git.haskell.org Thu Oct 26 23:15:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename redError(_) to putError(_). (9a6f684) Message-ID: <20171026231539.EA74D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a6f68428bc2ae6ce0ec2188cb43a48938d8ff87/ghc >--------------------------------------------------------------- commit 9a6f68428bc2ae6ce0ec2188cb43a48938d8ff87 Author: Andrey Mokhov Date: Wed Aug 5 22:29:05 2015 +0100 Rename redError(_) to putError(_). >--------------------------------------------------------------- 9a6f68428bc2ae6ce0ec2188cb43a48938d8ff87 src/Builder.hs | 2 +- src/Oracles/Base.hs | 4 ++-- src/Oracles/Flag.hs | 4 ++-- src/Util.hs | 10 +++++----- 4 files changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index a148fc5..b175fac 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -58,7 +58,7 @@ builderKey builder = case builder of builderPath :: Builder -> Action String builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ - redError $ "\nCannot find path to '" ++ (builderKey builder) + putError $ "\nCannot find path to '" ++ (builderKey builder) ++ "' in configuration files." fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 5c2a252..29ec4e4 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -22,7 +22,7 @@ askConfigWithDefault key defaultAction = do Nothing -> defaultAction askConfig :: String -> Action String -askConfig key = askConfigWithDefault key . redError +askConfig key = askConfigWithDefault key . putError $ "Cannot find key '" ++ key ++ "' in configuration files." -- Oracle for configuration files @@ -31,7 +31,7 @@ configOracle = do let configFile = configPath -/- "system.config" cfg <- newCache $ \() -> do unlessM (doesFileExist $ configFile <.> "in") $ - redError_ $ "\nConfiguration file '" ++ (configFile <.> "in") + putError_ $ "\nConfiguration file '" ++ (configFile <.> "in") ++ "' is missing; unwilling to proceed." need [configFile] putOracle $ "Reading " ++ configFile ++ "..." diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index dfa0920..391ed5e 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -28,9 +28,9 @@ flag f = do SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" GhcUnregisterised -> "ghc-unregisterised" - value <- askConfigWithDefault key . redError + value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." - unless (value == "YES" || value == "NO") . redError + unless (value == "YES" || value == "NO") . putError $ "\nFlag '" ++ key ++ "' is set to '" ++ value ++ "' instead of 'YES' or 'NO'." return $ value == "YES" diff --git a/src/Util.hs b/src/Util.hs index 70de3ec..32b6478 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -4,7 +4,7 @@ module Util ( replaceIf, replaceEq, replaceSeparators, unifyPath, (-/-), chunksOfSize, - putColoured, putOracle, putBuild, redError, redError_, + putColoured, putOracle, putBuild, putError, putError_, bimap, minusOrd, intersectOrd ) where @@ -65,13 +65,13 @@ putBuild :: String -> Action () putBuild = putColoured White -- A more colourful version of error -redError :: String -> Action a -redError msg = do +putError :: String -> Action a +putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg -redError_ :: String -> Action () -redError_ = void . redError +putError_ :: String -> Action () +putError_ = void . putError -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) From git at git.haskell.org Thu Oct 26 23:15:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add knownWays and knownRtsWays to Settings.Ways. (12cecf1) Message-ID: <20171026231543.DC64F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12cecf14f5205327b6520f72f8ddcb94a416fba9/ghc >--------------------------------------------------------------- commit 12cecf14f5205327b6520f72f8ddcb94a416fba9 Author: Andrey Mokhov Date: Wed Aug 5 22:31:19 2015 +0100 Add knownWays and knownRtsWays to Settings.Ways. >--------------------------------------------------------------- 12cecf14f5205327b6520f72f8ddcb94a416fba9 src/Settings/GhcCabal.hs | 1 + src/Settings/User.hs | 1 - src/Settings/Ways.hs | 16 ++++++++++++++-- 3 files changed, 15 insertions(+), 3 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index dfcb3df..5f264b2 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -15,6 +15,7 @@ import Oracles.Setting import Settings.User import Settings.Ways import Settings.Util +import Settings.Packages cabalArgs :: Args cabalArgs = builder GhcCabal ? do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 6426e82..572feb4 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,5 +1,4 @@ module Settings.User ( - module Settings.Default, userArgs, userPackages, userWays, userRtsWays, userTargetDirectory, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index c8377eb..ae4bd38 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,6 +1,7 @@ module Settings.Ways ( ways, getWays, - rtsWays, getRtsWays + rtsWays, getRtsWays, + knownWays, knownRtsWays ) where import Way @@ -8,7 +9,7 @@ import Stage import Switches import Expression import Oracles.Flag -import Settings.User +import Settings.User hiding (parallel) -- Combining default ways with user modifications ways :: Ways @@ -39,3 +40,14 @@ defaultRtsWays = do , (dynamic `elem` ways) ? append [ dynamic, debugDynamic, threadedDynamic, threadedDebugDynamic , loggingDynamic, threadedLoggingDynamic ] ] + +-- These are all ways known to the build system +knownWays :: [Way] +knownWays = [vanilla, profiling, logging, parallel, granSim] + +knownRtsWays :: [Way] +knownRtsWays = [ threaded, threadedProfiling, threadedLogging, debug + , debugProfiling, threadedDebug, threadedDebugProfiling, dynamic + , profilingDynamic, threadedProfilingDynamic, threadedDynamic + , threadedDebugDynamic, debugDynamic, loggingDynamic + , threadedLoggingDynamic ] From git at git.haskell.org Thu Oct 26 23:15:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove generated file. (3dac5a5) Message-ID: <20171026231540.0F2373A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3dac5a577f93267315681ba667562d2e5e525c82/ghc >--------------------------------------------------------------- commit 3dac5a577f93267315681ba667562d2e5e525c82 Author: Andrey Mokhov Date: Fri Dec 26 22:37:20 2014 +0000 Remove generated file. >--------------------------------------------------------------- 3dac5a577f93267315681ba667562d2e5e525c82 cfg/default.config | 76 -------------------------------------------------- cfg/default.config.was | 52 ---------------------------------- 2 files changed, 128 deletions(-) diff --git a/cfg/default.config b/cfg/default.config deleted file mode 100644 index 60fa290..0000000 --- a/cfg/default.config +++ /dev/null @@ -1,76 +0,0 @@ -# Paths to builders: -# ================== - -system-ghc = /usr/local/bin/ghc -system-ghc-pkg = /usr/local/bin/ghc-pkg - -ghc-cabal = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-cabal - -ghc-stage1 = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-stage1 -ghc-stage2 = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-stage2 -ghc-stage3 = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-stage3 - -ghc-pkg = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-pkg - -gcc = C:/msys64/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe -ld = C:/msys64/home/chEEtah/ghc/inplace/mingw/bin/ld.exe -ar = /mingw64/bin/ar -alex = /usr/local/bin/alex -happy = /usr/local/bin/happy -hscolour = - -# Information about builders: -#============================ - -gcc-is-clang = -gcc-lt-46 = NO - -# Build options: -#=============== - -lax-dependencies = NO -dynamic-ghc-programs = NO - -# Information about host and target systems: -# ========================================== - -target-os = mingw32 -target-arch = x86_64 -target-platform-full = x86_64-unknown-mingw32 - -host-os-cpp = mingw32 - -cross-compiling = NO - -# Compilation and linking flags: -#=============================== - -conf-cc-args-stage-0 = -fno-stack-protector -conf-cc-args-stage-1 = -fno-stack-protector -conf-cc-args-stage-2 = -fno-stack-protector - -conf-cpp-args-stage-0 = -conf-cpp-args-stage-1 = -conf-cpp-args-stage-2 = - -conf-gcc-linker-args-stage-0 = -conf-gcc-linker-args-stage-1 = -conf-gcc-linker-args-stage-2 = - -conf-ld-linker-args-stage-0 = -conf-ld-linker-args-stage-1 = -conf-ld-linker-args-stage-2 = - -# Include and library directories: -#================================= - -iconv-include-dirs = -iconv-lib-dirs = - -gmp-include-dirs = -gmp-lib-dirs = - - - - - diff --git a/cfg/default.config.was b/cfg/default.config.was deleted file mode 100644 index f821e7a..0000000 --- a/cfg/default.config.was +++ /dev/null @@ -1,52 +0,0 @@ -system-ghc = C:/msys64/usr/local/bin/ghc.exe -system-ghc-pkg = C:/msys64/usr/local/bin/ghc-pkg.exe - -ghc-cabal = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-cabal.exe -ghc-stage1 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage1.exe -ghc-stage2 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage2.exe -ghc-stage3 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage3.exe - -ghc-pkg = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-pkg.exe - -gcc = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/gcc.exe -ld = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ld.exe -ar = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ar.exe -alex = C:/msys64/usr/local/bin/alex.exe -happy = C:/msys64/usr/local/bin/happy.exe -hscolour = - -target-os = mingw32 -target-arch = x86_64 -target-platform-full = x86_64-unknown-mingw32 - -cross-compiling = NO - -conf-cc-args-stage-0 = -fno-stack-protector -conf-cc-args-stage-1 = -fno-stack-protector -conf-cc-args-stage-2 = -fno-stack-protector - -conf-cpp-args-stage-0 = -conf-cpp-args-stage-1 = -conf-cpp-args-stage-2 = - -conf-gcc-linker-args-stage-0 = -conf-gcc-linker-args-stage-1 = -conf-gcc-linker-args-stage-2 = - -conf-ld-linker-args-stage-0 = -conf-ld-linker-args-stage-1 = -conf-ld-linker-args-stage-2 = - -iconv-include-dirs = -iconv-lib-dirs = -gmp-include-dirs = -gmp-lib-dirs = - -lax-dependencies = NO -dynamic-ghc-programs = NO -gcc-is-clang = NO -gcc-lt-46 = NO - - - -host-os-cpp = mingw32 From git at git.haskell.org Thu Oct 26 23:15:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for autoconf/configure chain. (7d90047) Message-ID: <20171026231544.071003A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d90047a4fad755726ba70cc7f9506512008b96f/ghc >--------------------------------------------------------------- commit 7d90047a4fad755726ba70cc7f9506512008b96f Author: Andrey Mokhov Date: Fri Dec 26 22:38:42 2014 +0000 Add support for autoconf/configure chain. >--------------------------------------------------------------- 7d90047a4fad755726ba70cc7f9506512008b96f cfg/default.config.in | 9 ++------- src/Base.hs | 1 + src/Config.hs | 18 ++++++++++-------- src/Oracles.hs | 44 ++++++++++++++++++++++++++++++++++---------- 4 files changed, 47 insertions(+), 25 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index c01bb87..d3617f4 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -1,5 +1,5 @@ # Paths to builders: -# ================== +#=================== system-ghc = @WithGhc@ system-ghc-pkg = @GhcPkgCmd@ @@ -32,7 +32,7 @@ lax-dependencies = NO dynamic-ghc-programs = NO # Information about host and target systems: -# ========================================== +#=========================================== target-os = @TargetOS_CPP@ target-arch = @TargetArch_CPP@ @@ -69,8 +69,3 @@ iconv-lib-dirs = @ICONV_LIB_DIRS@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ - - - - - diff --git a/src/Base.hs b/src/Base.hs index 7e130c2..e44b3bb 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -5,6 +5,7 @@ module Base ( module Development.Shake.FilePath, module Control.Applicative, module Data.Monoid, + module Data.List, Stage (..), Args, arg, Condition, joinArgs, joinArgsWithSpaces, diff --git a/src/Config.hs b/src/Config.hs index a370f38..3d26482 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -1,5 +1,5 @@ module Config ( - autoconfRules, configureRules + autoconfRules, configureRules, cfgPath ) where import Development.Shake @@ -9,16 +9,18 @@ import Development.Shake.Rule import Control.Applicative import Control.Monad import Base -import Oracles + +cfgPath :: FilePath +cfgPath = "shake" "cfg" autoconfRules :: Rules () autoconfRules = do - "shake/configure" %> \out -> do - need ["shake/configure.ac"] - cmd $ "bash shake/autoconf" + "configure" %> \out -> do + copyFile' (cfgPath "configure.ac") "configure.ac" + cmd "bash autoconf" configureRules :: Rules () configureRules = do - "shake/default.config" %> \out -> do - need ["shake/default.config.in", "shake/configure"] - cmd $ "bash shake/configure" + cfgPath "default.config" %> \out -> do + need [cfgPath "default.config.in", "configure"] + cmd "bash configure" diff --git a/src/Oracles.hs b/src/Oracles.hs index 9138780..971d5c6 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -20,7 +20,9 @@ import qualified System.Directory as System import qualified Data.HashMap.Strict as M import qualified Prelude import Prelude hiding (not, (&&), (||)) +import Data.Char import Base +import Config data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage @@ -40,10 +42,18 @@ path builder = do Ghc Stage3 -> "ghc-stage3" GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) - askConfigWithDefault key $ + cfgPath <- askConfigWithDefault key $ error $ "\nCannot find path to '" ++ key ++ "' in configuration files." + let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" + windows <- test WindowsHost + if (windows && "/" `isPrefixOf` cfgPathExe) + then do + root <- option Root + return $ root ++ cfgPathExe + else + return cfgPathExe argPath :: Builder -> Args argPath builder = do @@ -53,7 +63,7 @@ argPath builder = do -- Explain! -- TODO: document change in behaviour (LaxDeps) needBuilder :: Builder -> Action () -needBuilder ghc @ (Ghc _) = do +needBuilder ghc @ (Ghc stage) = do target <- path ghc laxDeps <- test LaxDeps -- TODO: get rid of test? if laxDeps then orderOnly [target] else need [target] @@ -88,9 +98,18 @@ run builder args = do data Option = TargetOS | TargetArch | TargetPlatformFull | ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage | IconvIncludeDirs | IconvLibDirs | GmpIncludeDirs | GmpLibDirs - | HostOsCpp + | HostOsCpp | Root option :: Option -> Action String +option Root = do + windows <- test WindowsHost + if (windows) + then do + Stdout out <- cmd ["cygpath", "-m", "/"] + return $ dropWhileEnd isSpace out + else + return "/" + option opt = askConfig $ case opt of TargetOS -> "target-os" TargetArch -> "target-arch" @@ -112,6 +131,7 @@ argOption opt = do data Flag = LaxDeps | Stage1Only | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs | GccIsClang | GccLt46 | CrossCompiling | Validating | PlatformSupportsSharedLibs + | WindowsHost test :: Flag -> Action Bool test GhcWithInterpreter = do @@ -130,6 +150,10 @@ test HsColourSrcs = do hscolour <- path HsColour return $ hscolour /= "" +test WindowsHost = do + hostOsCpp <- option HostOsCpp + return $ hostOsCpp `elem` ["mingw32", "cygwin32"] + test flag = do (key, defaultValue) <- return $ case flag of LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file @@ -230,19 +254,19 @@ askConfig key = askConfigWithDefault key $ error $ "\nCannot find key '" oracleRules :: Rules () oracleRules = do cfg <- newCache $ \() -> do - unless (doesFileExist "shake/default.config") $ do + unless (doesFileExist $ cfgPath "default.config.in") $ do error $ "\nDefault configuration file '" - ++ "shake/default.config.in" + ++ (cfgPath "default.config.in") ++ "' is missing; unwilling to proceed." return () - need ["shake/default.config"] - cfgDefault <- liftIO $ readConfigFile "shake/default.config" - existsUser <- doesFileExist "shake/user.config" + need [cfgPath "default.config"] + cfgDefault <- liftIO $ readConfigFile $ cfgPath "default.config" + existsUser <- doesFileExist $ cfgPath "user.config" cfgUser <- if existsUser - then liftIO $ readConfigFile "shake/user.config" + then liftIO $ readConfigFile $ cfgPath "user.config" else do putLoud $ "\nUser defined configuration file '" - ++ "shake/user.config" + ++ (cfgPath "user.config") ++ "' is missing; proceeding with default configuration.\n" return M.empty return $ cfgUser `M.union` cfgDefault From git at git.haskell.org Thu Oct 26 23:15:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement compilePackage build rule. (098d9c1) Message-ID: <20171026231547.8D5353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/098d9c1e26a4da698eaea64a3da39bb7b0cd3838/ghc >--------------------------------------------------------------- commit 098d9c1e26a4da698eaea64a3da39bb7b0cd3838 Author: Andrey Mokhov Date: Wed Aug 5 22:31:59 2015 +0100 Implement compilePackage build rule. >--------------------------------------------------------------- 098d9c1e26a4da698eaea64a3da39bb7b0cd3838 src/Package/Compile.hs | 101 --------------------------------------- src/Rules/Compile.hs | 40 ++++++++++++++++ src/Rules/Package.hs | 3 +- src/Settings/{GccM.hs => Gcc.hs} | 26 +++++----- src/Settings/GccM.hs | 13 +---- src/Settings/{GhcM.hs => Ghc.hs} | 46 ++++++++++++------ src/Settings/GhcM.hs | 45 +---------------- src/Settings/Util.hs | 15 ------ 8 files changed, 88 insertions(+), 201 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 098d9c1e26a4da698eaea64a3da39bb7b0cd3838 From git at git.haskell.org Thu Oct 26 23:15:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generated default.config to .gitignore. (371842e) Message-ID: <20171026231547.8CDD63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/371842eb16a529d8bb1bae756369f5422e011032/ghc >--------------------------------------------------------------- commit 371842eb16a529d8bb1bae756369f5422e011032 Author: Andrey Mokhov Date: Fri Dec 26 22:57:49 2014 +0000 Add generated default.config to .gitignore. >--------------------------------------------------------------- 371842eb16a529d8bb1bae756369f5422e011032 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 30e2546..375b257 100644 --- a/.gitignore +++ b/.gitignore @@ -2,4 +2,4 @@ *.hi _shake/ _build/ -configure +cfg/default.config From git at git.haskell.org Thu Oct 26 23:15:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a comment to user.config explaining its purpose. (ced1860) Message-ID: <20171026231551.7C6A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ced186037fe9c0ad8c5ac1d191318b52d57dfac8/ghc >--------------------------------------------------------------- commit ced186037fe9c0ad8c5ac1d191318b52d57dfac8 Author: Andrey Mokhov Date: Fri Dec 26 22:58:30 2014 +0000 Add a comment to user.config explaining its purpose. >--------------------------------------------------------------- ced186037fe9c0ad8c5ac1d191318b52d57dfac8 cfg/user.config | 3 +++ 1 file changed, 3 insertions(+) diff --git a/cfg/user.config b/cfg/user.config index 313d39a..b72c5b4 100644 --- a/cfg/user.config +++ b/cfg/user.config @@ -1 +1,4 @@ +# Override default settings (stored in default.config file): +#=========================================================== + lax-dependencies = YES From git at git.haskell.org Thu Oct 26 23:15:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make detectWay safe, add comments. (7ebd24f) Message-ID: <20171026231555.A74D73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ebd24fe9d9177e65d5823d02a73c6a1776d85b2/ghc >--------------------------------------------------------------- commit 7ebd24fe9d9177e65d5823d02a73c6a1776d85b2 Author: Andrey Mokhov Date: Wed Aug 5 23:24:15 2015 +0100 Make detectWay safe, add comments. >--------------------------------------------------------------- 7ebd24fe9d9177e65d5823d02a73c6a1776d85b2 src/Way.hs | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index b48a29d..912ea63 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -124,11 +124,16 @@ libsuf way @ (Way set) = -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension --- Detect way from a given file extension. Fails if there is no match. -detectWay :: FilePath -> Way -detectWay extension = read prefix +-- Detect way from a given filename. Returns Nothing if there is no match: +-- * detectWay "foo/bar.hi" == Just vanilla +-- * detectWay "baz.thr_p_o" == Just threadedProfiling +-- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +detectWay :: FilePath -> Maybe Way +detectWay file = case reads prefix of + [(way, "")] -> Just way + _ -> Nothing where - prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ extension + prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ takeExtension file -- Instances for storing in the Shake database instance Binary Way where From git at git.haskell.org Thu Oct 26 23:15:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant imports, add TODO's. (fe2655b) Message-ID: <20171026231555.9B2DA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fe2655b6cd60d09311e87e1aa8736a3bbd847d9b/ghc >--------------------------------------------------------------- commit fe2655b6cd60d09311e87e1aa8736a3bbd847d9b Author: Andrey Mokhov Date: Fri Dec 26 23:04:07 2014 +0000 Remove redundant imports, add TODO's. >--------------------------------------------------------------- fe2655b6cd60d09311e87e1aa8736a3bbd847d9b src/Config.hs | 10 ++-------- 1 file changed, 2 insertions(+), 8 deletions(-) diff --git a/src/Config.hs b/src/Config.hs index 3d26482..b4f0519 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -2,12 +2,6 @@ module Config ( autoconfRules, configureRules, cfgPath ) where -import Development.Shake -import Development.Shake.Command -import Development.Shake.FilePath -import Development.Shake.Rule -import Control.Applicative -import Control.Monad import Base cfgPath :: FilePath @@ -17,10 +11,10 @@ autoconfRules :: Rules () autoconfRules = do "configure" %> \out -> do copyFile' (cfgPath "configure.ac") "configure.ac" - cmd "bash autoconf" + cmd "bash autoconf" -- TODO: get rid of 'bash' configureRules :: Rules () configureRules = do cfgPath "default.config" %> \out -> do need [cfgPath "default.config.in", "configure"] - cmd "bash configure" + cmd "bash configure" -- TODO: get rid of 'bash' From git at git.haskell.org Thu Oct 26 23:15:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of redError_. (4fd1732) Message-ID: <20171026231551.8561A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fd17325b1c7921c1278a8da85544960ef07a5af/ghc >--------------------------------------------------------------- commit 4fd17325b1c7921c1278a8da85544960ef07a5af Author: Andrey Mokhov Date: Wed Aug 5 23:23:22 2015 +0100 Get rid of redError_. >--------------------------------------------------------------- 4fd17325b1c7921c1278a8da85544960ef07a5af src/Oracles/Base.hs | 4 ++-- src/Util.hs | 6 +----- 2 files changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 29ec4e4..a6abbfc 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -31,8 +31,8 @@ configOracle = do let configFile = configPath -/- "system.config" cfg <- newCache $ \() -> do unlessM (doesFileExist $ configFile <.> "in") $ - putError_ $ "\nConfiguration file '" ++ (configFile <.> "in") - ++ "' is missing; unwilling to proceed." + putError $ "\nConfiguration file '" ++ (configFile <.> "in") + ++ "' is missing; unwilling to proceed." need [configFile] putOracle $ "Reading " ++ configFile ++ "..." liftIO $ readConfigFile configFile diff --git a/src/Util.hs b/src/Util.hs index 32b6478..f00785f 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -4,13 +4,12 @@ module Util ( replaceIf, replaceEq, replaceSeparators, unifyPath, (-/-), chunksOfSize, - putColoured, putOracle, putBuild, putError, putError_, + putColoured, putOracle, putBuild, putError, bimap, minusOrd, intersectOrd ) where import Base import Data.Char -import Control.Monad import System.IO import System.Console.ANSI @@ -70,9 +69,6 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg -putError_ :: String -> Action () -putError_ = void . putError - -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) From git at git.haskell.org Thu Oct 26 23:15:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant imports, drop Stage1Only. (428e148) Message-ID: <20171026231559.48D123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/428e148afb2a043419f3be83c56e05489b4e5efe/ghc >--------------------------------------------------------------- commit 428e148afb2a043419f3be83c56e05489b4e5efe Author: Andrey Mokhov Date: Fri Dec 26 23:05:12 2014 +0000 Remove redundant imports, drop Stage1Only. >--------------------------------------------------------------- 428e148afb2a043419f3be83c56e05489b4e5efe src/Oracles.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 971d5c6..08d668e 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -12,11 +12,10 @@ module Oracles ( oracleRules ) where -import Development.Shake.Config import Development.Shake.Rule +import Development.Shake.Config import Development.Shake.Classes import Control.Monad hiding (when, unless) -import qualified System.Directory as System import qualified Data.HashMap.Strict as M import qualified Prelude import Prelude hiding (not, (&&), (||)) @@ -129,7 +128,7 @@ argOption opt = do opt' <- option opt arg [opt'] -data Flag = LaxDeps | Stage1Only | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs +data Flag = LaxDeps | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs | GccIsClang | GccLt46 | CrossCompiling | Validating | PlatformSupportsSharedLibs | WindowsHost @@ -157,7 +156,6 @@ test WindowsHost = do test flag = do (key, defaultValue) <- return $ case flag of LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file - Stage1Only -> ("stage-1-only" , False) -- TODO: target only DynamicGhcPrograms -> ("dynamic-ghc-programs", False) GccIsClang -> ("gcc-is-clang" , False) GccLt46 -> ("gcc-lt-46" , False) From git at git.haskell.org Thu Oct 26 23:15:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:15:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop knownWays and knownRtsWays. (be568c0) Message-ID: <20171026231559.60A563A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/be568c02f7ea7af3b916257cbf7656c8f9ad4979/ghc >--------------------------------------------------------------- commit be568c02f7ea7af3b916257cbf7656c8f9ad4979 Author: Andrey Mokhov Date: Wed Aug 5 23:24:47 2015 +0100 Drop knownWays and knownRtsWays. >--------------------------------------------------------------- be568c02f7ea7af3b916257cbf7656c8f9ad4979 src/Settings/Ways.hs | 14 +------------- 1 file changed, 1 insertion(+), 13 deletions(-) diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index ae4bd38..0ea3432 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,7 +1,6 @@ module Settings.Ways ( ways, getWays, - rtsWays, getRtsWays, - knownWays, knownRtsWays + rtsWays, getRtsWays ) where import Way @@ -40,14 +39,3 @@ defaultRtsWays = do , (dynamic `elem` ways) ? append [ dynamic, debugDynamic, threadedDynamic, threadedDebugDynamic , loggingDynamic, threadedLoggingDynamic ] ] - --- These are all ways known to the build system -knownWays :: [Way] -knownWays = [vanilla, profiling, logging, parallel, granSim] - -knownRtsWays :: [Way] -knownRtsWays = [ threaded, threadedProfiling, threadedLogging, debug - , debugProfiling, threadedDebug, threadedDebugProfiling, dynamic - , profilingDynamic, threadedProfilingDynamic, threadedDynamic - , threadedDebugDynamic, debugDynamic, loggingDynamic - , threadedLoggingDynamic ] From git at git.haskell.org Thu Oct 26 23:16:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make C:/msys64/ a silent command. (4d2b4bc) Message-ID: <20171026231602.E85C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4d2b4bcce29e1a476dcbe0055319c7586e75d8ec/ghc >--------------------------------------------------------------- commit 4d2b4bcce29e1a476dcbe0055319c7586e75d8ec Author: Andrey Mokhov Date: Fri Dec 26 23:38:28 2014 +0000 Make C:/msys64/ a silent command. >--------------------------------------------------------------- 4d2b4bcce29e1a476dcbe0055319c7586e75d8ec src/Oracles.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 08d668e..e03d6a3 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -104,7 +104,7 @@ option Root = do windows <- test WindowsHost if (windows) then do - Stdout out <- cmd ["cygpath", "-m", "/"] + Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] return $ dropWhileEnd isSpace out else return "/" From git at git.haskell.org Thu Oct 26 23:16:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise rules by removing a loop over all possible ways. (c204ca9) Message-ID: <20171026231603.05A4B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c204ca9764ac5ffdb141247151e040bd1bffa5d6/ghc >--------------------------------------------------------------- commit c204ca9764ac5ffdb141247151e040bd1bffa5d6 Author: Andrey Mokhov Date: Wed Aug 5 23:26:36 2015 +0100 Optimise rules by removing a loop over all possible ways. >--------------------------------------------------------------- c204ca9764ac5ffdb141247151e040bd1bffa5d6 src/Rules/Compile.hs | 34 +++++++++++++++++++--------------- 1 file changed, 19 insertions(+), 15 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 4b2fe4b..89b60c2 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -7,10 +7,14 @@ import Builder import Expression import qualified Target import Oracles.DependencyList -import Settings.Ways import Settings.TargetDirectory import Rules.Actions import Rules.Resources +import Data.Maybe + +matchBuildResult :: FilePath -> String -> FilePath -> Bool +matchBuildResult buildPath extension file = + (buildPath "*" ++ extension) ?== file && (isJust . detectWay $ file) compilePackage :: Resources -> StagePackageTarget -> Rules () compilePackage _ target = do @@ -21,20 +25,20 @@ compilePackage _ target = do cDepsFile = buildPath -/- "c.deps" hDepsFile = buildPath -/- "haskell.deps" - forM_ knownWays $ \way -> do - (buildPath "*." ++ hisuf way) %> \hi -> do - let obj = hi -<.> osuf way - need [obj] + matchBuildResult buildPath "hi" ?> \hi -> do + let way = fromJust . detectWay $ hi -- fromJust is safe + need [hi -<.> osuf way] - (buildPath "*." ++ osuf way) %> \obj -> do - let vanillaObjName = takeFileName obj -<.> "o" - cDeps <- dependencyList cDepsFile vanillaObjName - hDeps <- dependencyList hDepsFile obj - let hSrcDeps = filter ("//*hs" ?==) hDeps + matchBuildResult buildPath "o" ?> \obj -> do + let way = fromJust . detectWay $ obj -- fromJust is safe + vanillaObj = takeFileName obj -<.> "o" + cDeps <- dependencyList cDepsFile vanillaObj + hDeps <- dependencyList hDepsFile obj + let hSrcDeps = filter ("//*hs" ?==) hDeps - when (null cDeps && null hDeps) $ - putError_ $ "Cannot determine sources for '" ++ obj ++ "'." + when (null cDeps && null hDeps) $ + putError $ "Cannot determine sources for '" ++ obj ++ "'." - if null cDeps - then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] - else build $ fullTarget target cDeps (Gcc stage) [obj] + if null cDeps + then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] + else build $ fullTarget target cDeps (Gcc stage) [obj] From git at git.haskell.org Thu Oct 26 23:16:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update to the latest GHC source tree. (a58a713) Message-ID: <20171026231607.0D6AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a58a7132c1bdd47dc79e28a4fef01b090e5a88c0/ghc >--------------------------------------------------------------- commit a58a7132c1bdd47dc79e28a4fef01b090e5a88c0 Author: Andrey Mokhov Date: Sat Dec 27 23:42:56 2014 +0000 Update to the latest GHC source tree. >--------------------------------------------------------------- a58a7132c1bdd47dc79e28a4fef01b090e5a88c0 cfg/configure.ac | 122 ++++++++++++++++++++++++++++++++----------------------- 1 file changed, 71 insertions(+), 51 deletions(-) diff --git a/cfg/configure.ac b/cfg/configure.ac index b31d1b3..125fd49 100644 --- a/cfg/configure.ac +++ b/cfg/configure.ac @@ -13,7 +13,7 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.9], [glasgow-haskell-bugs at haskell.org], [ghc]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.11], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO : ${RELEASE=NO} @@ -187,56 +187,6 @@ AC_SUBST([WithGhc]) dnl ** Without optimization some INLINE trickery fails for GHCi SRC_CC_OPTS="-O" -dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. -dnl Unfortunately we don't know whether the user is going to request a -dnl build with the LLVM backend as this is only given in build.mk. -dnl -dnl Instead, we try to do as much work as possible here, checking -dnl whether -fllvm is the stage 0 compiler's default. If so we -dnl fail. If not, we check whether -fllvm is affected explicitly and -dnl if so set a flag. The build system will later check this flag -dnl after the desired build flags are known. -AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) -echo "main = putStrLn \"%function\"" > conftestghc.hs - -# Check whether LLVM backend is default for this platform -"${WithGhc}" conftestghc.hs 2>&1 >/dev/null -res=`./conftestghc` -if test "x$res" == "x%object" -then - AC_MSG_RESULT(yes) - echo "Buggy bootstrap compiler" - echo "" - echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" - echo "and therefore will miscompile the LLVM backend if -fllvm is" - echo "used." - echo - echo "Please use another bootstrap compiler" - exit 1 -fi - -# -fllvm is not the default, but set a flag so the Makefile can check -# -for it in the build flags later on -"${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null -if test $? == 0 -then - res=`./conftestghc` - if test "x$res" == "x%object" - then - AC_MSG_RESULT(yes) - GHC_LLVM_AFFECTED_BY_9439=1 - elif test "x$res" == "x%function" - then - AC_MSG_RESULT(no) - GHC_LLVM_AFFECTED_BY_9439=0 - else - AC_MSG_WARN(unexpected output $res) - fi -else - AC_MSG_RESULT(failed to compile, assuming no) -fi -AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) - dnl-------------------------------------------------------------------- dnl * Choose host(/target/build) platform dnl-------------------------------------------------------------------- @@ -593,6 +543,59 @@ dnl -------------------------------------------------------------- dnl * General configuration checks dnl -------------------------------------------------------------- +dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. +dnl Unfortunately we don't know whether the user is going to request a +dnl build with the LLVM backend as this is only given in build.mk. +dnl +dnl Instead, we try to do as much work as possible here, checking +dnl whether -fllvm is the stage 0 compiler's default. If so we +dnl fail. If not, we check whether -fllvm is affected explicitly and +dnl if so set a flag. The build system will later check this flag +dnl after the desired build flags are known. +if test -n "$LlcCmd" && test -n "$OptCmd" +then + AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) + echo "main = putStrLn \"%function\"" > conftestghc.hs + + # Check whether LLVM backend is default for this platform + "${WithGhc}" conftestghc.hs 2>&1 >/dev/null + res=`./conftestghc` + if test "x$res" = "x%object" + then + AC_MSG_RESULT(yes) + echo "Buggy bootstrap compiler" + echo "" + echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" + echo "and therefore will miscompile the LLVM backend if -fllvm is" + echo "used." + echo + echo "Please use another bootstrap compiler" + exit 1 + fi + + # -fllvm is not the default, but set a flag so the Makefile can check + # -for it in the build flags later on + "${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null + if test $? = 0 + then + res=`./conftestghc` + if test "x$res" = "x%object" + then + AC_MSG_RESULT(yes) + GHC_LLVM_AFFECTED_BY_9439=1 + elif test "x$res" = "x%function" + then + AC_MSG_RESULT(no) + GHC_LLVM_AFFECTED_BY_9439=0 + else + AC_MSG_WARN(unexpected output $res) + fi + else + AC_MSG_RESULT(failed to compile, assuming no) + fi +fi +AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) + dnl ** Can the unix package be built? dnl -------------------------------------------------------------- @@ -896,6 +899,22 @@ AC_TRY_LINK_FUNC(printf\$LDBLStub, [Define to 1 if we have printf$LDBLStub (Apple Mac OS >= 10.4, PPC).]) ]) +dnl ** pthread_setname_np is a recent addition to glibc, and OS X has +dnl a different single-argument version. +AC_CHECK_LIB(pthread, pthread_setname_np) +AC_MSG_CHECKING(for pthread_setname_np) +AC_TRY_LINK( +[ +#define _GNU_SOURCE +#include +], +[pthread_setname_np(pthread_self(), "name");], + AC_MSG_RESULT(yes) + AC_DEFINE([HAVE_PTHREAD_SETNAME_NP], [1], + [Define to 1 if you have the glibc version of pthread_setname_np]), + AC_MSG_RESULT(no) +) + dnl ** check for eventfd which is needed by the I/O manager AC_CHECK_HEADERS([sys/eventfd.h]) AC_CHECK_FUNCS([eventfd]) @@ -986,6 +1005,7 @@ echo [" Configure completed successfully. Building GHC version : $ProjectVersion + Git commit id : $ProjectGitCommitId Build platform : $BuildPlatform Host platform : $HostPlatform From git at git.haskell.org Thu Oct 26 23:16:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move matchBuildResult to Way.hs. (1711977) Message-ID: <20171026231607.1959B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1711977649e14d87093d0f4ff0de132d1c044e42/ghc >--------------------------------------------------------------- commit 1711977649e14d87093d0f4ff0de132d1c044e42 Author: Andrey Mokhov Date: Thu Aug 6 01:34:24 2015 +0100 Move matchBuildResult to Way.hs. >--------------------------------------------------------------- 1711977649e14d87093d0f4ff0de132d1c044e42 src/Way.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/src/Way.hs b/src/Way.hs index 912ea63..365a949 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -10,7 +10,7 @@ module Way ( -- TODO: rename to "Way"? loggingDynamic, threadedLoggingDynamic, wayPrefix, hisuf, osuf, hcsuf, obootsuf, ssuf, libsuf, - detectWay + detectWay, matchBuildResult ) where import Base @@ -20,6 +20,7 @@ import Data.List import Data.IntSet (IntSet) import Control.Applicative import qualified Data.IntSet as Set +import Data.Maybe data WayUnit = Threaded | Debug @@ -135,6 +136,13 @@ detectWay file = case reads prefix of where prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ takeExtension file +-- Given a path, an extension suffix, and a file name check if the latter: +-- 1) conforms to pattern 'path//*suffix' +-- 2) has extension prefixed with a known way tag, i.e. detectWay does not fail +matchBuildResult :: FilePath -> String -> FilePath -> Bool +matchBuildResult path suffix file = + (path "*" ++ suffix) ?== file && (isJust . detectWay $ file) + -- Instances for storing in the Shake database instance Binary Way where put = put . show From git at git.haskell.org Thu Oct 26 23:16:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update build-package-data.docx to match Package.hs (8a93116) Message-ID: <20171026231610.AB9AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8a9311684390d4cb8a07d9c1521021769546caff/ghc >--------------------------------------------------------------- commit 8a9311684390d4cb8a07d9c1521021769546caff Author: Andrey Mokhov Date: Sun Dec 28 03:32:49 2014 +0000 Update build-package-data.docx to match Package.hs >--------------------------------------------------------------- 8a9311684390d4cb8a07d9c1521021769546caff doc/build-package-data.docx | Bin 15964 -> 16519 bytes 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/doc/build-package-data.docx b/doc/build-package-data.docx index c2637c9..a2708cc 100644 Binary files a/doc/build-package-data.docx and b/doc/build-package-data.docx differ From git at git.haskell.org Thu Oct 26 23:16:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add cmdLineLengthLimit for detecting command line size limits. (ef14064) Message-ID: <20171026231610.B75603A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef1406494d3dc15ab0b311fcaf7e3c853c2a3a81/ghc >--------------------------------------------------------------- commit ef1406494d3dc15ab0b311fcaf7e3c853c2a3a81 Author: Andrey Mokhov Date: Thu Aug 6 01:35:31 2015 +0100 Add cmdLineLengthLimit for detecting command line size limits. >--------------------------------------------------------------- ef1406494d3dc15ab0b311fcaf7e3c853c2a3a81 src/Oracles/Setting.hs | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 33067b1..20e4376 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -3,7 +3,7 @@ module Oracles.Setting ( setting, settingList, targetPlatform, targetPlatforms, targetOs, targetOss, notTargetOs, targetArchs, windowsHost, notWindowsHost, ghcWithInterpreter, - ghcEnableTablesNextToCode + ghcEnableTablesNextToCode, cmdLineLengthLimit ) where import Base @@ -96,3 +96,14 @@ ghcWithInterpreter = do ghcEnableTablesNextToCode :: Action Bool ghcEnableTablesNextToCode = targetArchs ["ia64", "powerpc64"] + +-- Command lines have limited size on Windows. Since Windows 7 the limit is +-- 32768 characters (theoretically). In practice we use 31000 to leave some +-- breathing space for the builder's path & name, auxiliary flags, and other +-- overheads. Use this function to set limits for other OSs if necessary. +cmdLineLengthLimit :: Action Int +cmdLineLengthLimit = do + windows <- windowsHost + return $ if windows + then 31000 + else 4194304 -- Cabal needs a bit more than 2MB! From git at git.haskell.org Thu Oct 26 23:16:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revisions (add comments, move Condition to Oracles.hs). (618d90d) Message-ID: <20171026231614.1C99C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/618d90dc2bc41256a18c42776d701a9a4fc23d26/ghc >--------------------------------------------------------------- commit 618d90dc2bc41256a18c42776d701a9a4fc23d26 Author: Andrey Mokhov Date: Sun Dec 28 03:33:55 2014 +0000 Minor revisions (add comments, move Condition to Oracles.hs). >--------------------------------------------------------------- 618d90dc2bc41256a18c42776d701a9a4fc23d26 src/Base.hs | 4 +--- src/Oracles.hs | 21 +++++++++++++-------- 2 files changed, 14 insertions(+), 11 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index e44b3bb..b4ea8cb 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,7 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, Condition, + Args, arg, joinArgs, joinArgsWithSpaces, filterOut, ) where @@ -22,8 +22,6 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) type Args = Action [String] -type Condition = Action Bool - instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q diff --git a/src/Oracles.hs b/src/Oracles.hs index e03d6a3..9ceb121 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,5 +1,5 @@ {-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, DeriveGeneric, ConstraintKinds #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} module Oracles ( module Control.Monad, @@ -8,7 +8,7 @@ module Oracles ( Builder (..), Flag (..), Option (..), path, with, run, argPath, option, argOption, - test, when, unless, not, (&&), (||), + Condition, test, when, unless, not, (&&), (||), oracleRules ) where @@ -50,7 +50,7 @@ path builder = do if (windows && "/" `isPrefixOf` cfgPathExe) then do root <- option Root - return $ root ++ cfgPathExe + return $ root ++ (drop 1 $ cfgPathExe) else return cfgPathExe @@ -59,19 +59,22 @@ argPath builder = do path <- path builder arg [path] --- Explain! --- TODO: document change in behaviour (LaxDeps) +-- When LaxDeps flag is set (by adding 'lax-dependencies = YES' to user.config), +-- dependencies on the GHC executable are turned into order-only dependencies to +-- avoid needless recompilation when making changes to GHC's sources. In certain +-- situations this can lead to build failures, in which case you should reset +-- the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do target <- path ghc - laxDeps <- test LaxDeps -- TODO: get rid of test? + laxDeps <- test LaxDeps if laxDeps then orderOnly [target] else need [target] needBuilder builder = do target <- path builder need [target] --- 'with Gcc' generates --with-gcc=/usr/bin/gcc and needs it +-- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder with :: Builder -> Args with builder = do let prefix = case builder of @@ -163,7 +166,7 @@ test flag = do Validating -> ("validating" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ - do putLoud $ "\nFlag '" + do putLoud $ "\nFlag '" -- TODO: Give the warning *only once* per key ++ key ++ "' not set in configuration files. " ++ "Proceeding with default value '" @@ -172,6 +175,8 @@ test flag = do return defaultString return $ value == "YES" +type Condition = Action Bool + class ToCondition a where toCondition :: a -> Condition From git at git.haskell.org Thu Oct 26 23:16:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove unused code. (6c89bd0) Message-ID: <20171026231614.2B3923A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6c89bd01c53fe3ffa0c26499effff7687530711e/ghc >--------------------------------------------------------------- commit 6c89bd01c53fe3ffa0c26499effff7687530711e Author: Andrey Mokhov Date: Thu Aug 6 01:36:39 2015 +0100 Remove unused code. >--------------------------------------------------------------- 6c89bd01c53fe3ffa0c26499effff7687530711e src/Package/Base.hs | 68 -------------------------------------------- src/Package/Library.hs | 76 -------------------------------------------------- 2 files changed, 144 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs deleted file mode 100644 index 1f9d2c8..0000000 --- a/src/Package/Base.hs +++ /dev/null @@ -1,68 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package.Base ( - module Base, - module Ways, - module Util, - module Oracles, - -- Package (..), Settings (..), TodoItem (..), - -- defaultSettings, library, customise, updateSettings, - -- commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - pathArgs, packageArgs, - includeGccArgs, includeGhcArgs, pkgHsSources, - pkgDepHsObjects, pkgLibHsObjects, pkgCObjects, - argSizeLimit, - sourceDependecies, - argList, argListWithComment, - argListPath - ) where - -import Base -import Ways -import Util -import Oracles -import Settings -import qualified System.Directory as S - --- Find Haskell objects we depend on (we don't want to depend on split objects) -pkgDepHsObjects :: FilePath -> FilePath -> Way -> Action [FilePath] -pkgDepHsObjects path dist way = do - let pathDist = path dist - buildDir = pathDist "build" - dirs <- map (dropWhileEnd isPathSeparator . unifyPath . (path )) - <$> args (SrcDirs pathDist) - fmap concat $ forM dirs $ \d -> - map (unifyPath . (buildDir ++) . (-<.> osuf way) . drop (length d)) - <$> (findModuleFiles pathDist [d] [".hs", ".lhs"]) - -pkgCObjects :: FilePath -> FilePath -> Way -> Action [FilePath] -pkgCObjects path dist way = do - let pathDist = path dist - buildDir = pathDist "build" - srcs <- args $ CSrcs pathDist - return $ map (unifyPath . (buildDir ) . (-<.> osuf way)) srcs - --- Find Haskell objects that go to library -pkgLibHsObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] -pkgLibHsObjects path dist stage way = do - let pathDist = path dist - buildDir = unifyPath $ pathDist "build" - split <- splitObjects stage - depObjs <- pkgDepHsObjects path dist way - if split - then do - need depObjs -- Otherwise, split objects may not yet be available - let suffix = "_" ++ osuf way ++ "_split/*." ++ osuf way - findModuleFiles pathDist [buildDir] [suffix] - else do return depObjs - --- The argument list has a limited size on Windows. Since Windows 7 the limit --- is 32768 (theoretically). In practice we use 31000 to leave some breathing --- space for the builder's path & name, auxiliary flags, and other overheads. --- Use this function to set limits for other operating systems if necessary. -argSizeLimit :: Action Int -argSizeLimit = do - windows <- windowsHost - return $ if windows - then 31000 - else 4194304 -- Cabal needs a bit more than 2MB! - diff --git a/src/Package/Library.hs b/src/Package/Library.hs deleted file mode 100644 index 82b1ab8..0000000 --- a/src/Package/Library.hs +++ /dev/null @@ -1,76 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package.Library (buildPackageLibrary) where - -import Package.Base - -argListDir :: FilePath -argListDir = "shake/arg/buildPackageLibrary" - -arArgs :: [FilePath] -> FilePath -> Args -arArgs objs result = args [ arg "q" - , arg result - , args objs ] - -ldArgs :: Stage -> [FilePath] -> FilePath -> Args -ldArgs stage objs result = args [ args $ ConfLdLinkerArgs stage - , arg "-r" - , arg "-o" - , arg result - , args objs ] - -arRule :: Package -> TodoItem -> Rules () -arRule pkg @ (Package _ path _ _) todo @ (stage, dist, _) = - let buildDir = path dist "build" - in - (buildDir "*a") %> \out -> do - let way = detectWay $ tail $ takeExtension out - cObjs <- pkgCObjects path dist way - hsObjs <- pkgDepHsObjects path dist way - need $ cObjs ++ hsObjs - libHsObjs <- pkgLibHsObjects path dist stage way - liftIO $ removeFiles "." [out] - -- Splitting argument list into chunks as otherwise Ar chokes up - maxChunk <- argSizeLimit - forM_ (chunksOfSize maxChunk $ cObjs ++ libHsObjs) $ \objs -> do - run Ar $ arArgs objs $ unifyPath out - -- Finally, record the argument list - need [argListPath argListDir pkg stage] - -ldRule :: Package -> TodoItem -> Rules () -ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) = - let pathDist = path dist - buildDir = pathDist "build" - in - priority 2 $ (buildDir "*.o") %> \out -> do - cObjs <- pkgCObjects path dist vanilla - hObjs <- pkgDepHsObjects path dist vanilla - need $ cObjs ++ hObjs - run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out - synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) - putColoured Green $ "/--------\n| Successfully built package '" - ++ name ++ "' (stage " ++ show stage ++ ")." - putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." - ++ "\n\\--------" - -- Finally, record the argument list - need [argListPath argListDir pkg stage] - -argListRule :: Package -> TodoItem -> Rules () -argListRule pkg @ (Package _ path _ _) todo @ (stage, dist, settings) = - (argListPath argListDir pkg stage) %> \out -> do - need $ ["shake/src/Package/Library.hs"] ++ sourceDependecies - cObjsV <- pkgCObjects path dist vanilla - hsObjsV <- pkgDepHsObjects path dist vanilla - ldList <- argList Ld $ ldArgs stage (cObjsV ++ hsObjsV) "output.o" - ways' <- ways settings - arList <- forM ways' $ \way -> do - cObjs <- pkgCObjects path dist way - hsObjs <- pkgLibHsObjects path dist stage way - suffix <- libsuf way - argListWithComment - ("way '" ++ tag way ++ "'") - Ar - (arArgs (cObjs ++ hsObjs) $ "output" <.> suffix) - writeFileChanged out $ unlines $ [ldList] ++ arList - -buildPackageLibrary :: Package -> TodoItem -> Rules () -buildPackageLibrary = argListRule <> arRule <> ldRule From git at git.haskell.org Thu Oct 26 23:16:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -fwarn-tabs and -fwarn-unused-imports. (7eb2d38) Message-ID: <20171026231617.CBD513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7eb2d388f236b8759046b1d58e89cbf9088e4940/ghc >--------------------------------------------------------------- commit 7eb2d388f236b8759046b1d58e89cbf9088e4940 Author: Andrey Mokhov Date: Mon Dec 29 21:43:26 2014 +0000 Add -fwarn-tabs and -fwarn-unused-imports. >--------------------------------------------------------------- 7eb2d388f236b8759046b1d58e89cbf9088e4940 build.bat | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 8e3dba2..0e1f581 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,3 @@ @mkdir _shake 2> nul - at ghc --make src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build + at _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:16:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for multiple invokations of Ar when argument list is too long. (c02e070) Message-ID: <20171026231617.E10BD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c02e070cb0b05a443a823ef1134415b14d7043df/ghc >--------------------------------------------------------------- commit c02e070cb0b05a443a823ef1134415b14d7043df Author: Andrey Mokhov Date: Thu Aug 6 01:37:32 2015 +0100 Add support for multiple invokations of Ar when argument list is too long. >--------------------------------------------------------------- c02e070cb0b05a443a823ef1134415b14d7043df src/Rules/Actions.hs | 13 +++++++++++-- 1 file changed, 11 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d96157c..50eb87f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -7,9 +7,11 @@ import Util import Builder import Expression import qualified Target +import Oracles.Setting +import Oracles.ArgsHash import Settings.Args import Settings.Util -import Oracles.ArgsHash +import Settings.Builders.Ar -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last @@ -29,7 +31,14 @@ buildWithResources rs target = do ++ show builder ++ " with arguments:" mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList putBuild $ "\\--------" - quietly $ cmd [path] argList + quietly $ if builder /= Ar + then cmd [path] argList + else do -- Split argument list into chunks as otherwise Ar chokes up + maxChunk <- cmdLineLengthLimit + let persistentArgs = take arPersistentArgsCount argList + remainingArgs = drop arPersistentArgsCount argList + forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> + unit . cmd [path] $ persistentArgs ++ argsChunk -- Most targets are built without explicitly acquiring resources build :: FullTarget -> Action () From git at git.haskell.org Thu Oct 26 23:16:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build/autogen/Paths_library.hs to ghc-cabal results. (3bbb9fb) Message-ID: <20171026231621.960253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3bbb9fba477a7c84e2e615712a12046fda14d8b9/ghc >--------------------------------------------------------------- commit 3bbb9fba477a7c84e2e615712a12046fda14d8b9 Author: Andrey Mokhov Date: Mon Dec 29 21:51:22 2014 +0000 Add build/autogen/Paths_library.hs to ghc-cabal results. >--------------------------------------------------------------- 3bbb9fba477a7c84e2e615712a12046fda14d8b9 src/Package.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Package.hs b/src/Package.hs index 8d7311b..f5eae9b 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -120,7 +120,8 @@ buildPackageData pkg @ (Package name path todo) (stage, dist, settings) = "haddock-prologue.txt", "inplace-pkg-config", "setup-config", - "build" "autogen" "cabal_macros.h" + "build" "autogen" "cabal_macros.h", + "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? What's up with Paths_cpsa.hs? ] &%> \_ -> do need [path name <.> "cabal"] when (doesFileExist $ path "configure.ac") $ need [path "configure"] From git at git.haskell.org Thu Oct 26 23:16:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move decodeModule to Util.hs. (c1b296a) Message-ID: <20171026231621.B32303A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1b296ab5dd0d4795ad2c4e86f5a00b2ffa947b7/ghc >--------------------------------------------------------------- commit c1b296ab5dd0d4795ad2c4e86f5a00b2ffa947b7 Author: Andrey Mokhov Date: Thu Aug 6 01:38:54 2015 +0100 Move decodeModule to Util.hs. >--------------------------------------------------------------- c1b296ab5dd0d4795ad2c4e86f5a00b2ffa947b7 src/Settings/Util.hs | 5 ----- src/Util.hs | 7 ++++++- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index c688b5d..13e5be0 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -89,11 +89,6 @@ getHsSources = do return $ foundSources ++ generatedSources --- Given a module name extract the directory and file names, e.g.: --- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") -decodeModule :: String -> (FilePath, String) -decodeModule = splitFileName . replaceEq '.' '/' - -- findModuleFiles scans a list of given directories and finds files matching a -- given extension pattern (e.g., "*hs") that correspond to modules of the -- currently built package. Missing module files are returned in a separate diff --git a/src/Util.hs b/src/Util.hs index f00785f..1c34a87 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,7 +1,7 @@ module Util ( module Data.Char, module System.Console.ANSI, - replaceIf, replaceEq, replaceSeparators, + replaceIf, replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, putColoured, putOracle, putBuild, putError, @@ -22,6 +22,11 @@ replaceEq from = replaceIf (== from) replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator +-- Given a module name extract the directory and file names, e.g.: +-- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +decodeModule :: String -> (FilePath, String) +decodeModule = splitFileName . replaceEq '.' '/' + -- Normalise a path and convert all path separators to /, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx From git at git.haskell.org Thu Oct 26 23:16:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add replaceChar helper function. (1fa4aa5) Message-ID: <20171026231625.1CDB13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fa4aa517a6e1334b276539204b41367fbff8a51/ghc >--------------------------------------------------------------- commit 1fa4aa517a6e1334b276539204b41367fbff8a51 Author: Andrey Mokhov Date: Tue Dec 30 03:52:56 2014 +0000 Add replaceChar helper function. >--------------------------------------------------------------- 1fa4aa517a6e1334b276539204b41367fbff8a51 src/Base.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index b4ea8cb..eaebaf3 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -10,6 +10,7 @@ module Base ( Args, arg, joinArgs, joinArgsWithSpaces, filterOut, + replaceChar ) where import Development.Shake hiding ((*>)) @@ -42,3 +43,8 @@ joinArgs = intercalateArgs "" filterOut :: Args -> [String] -> Args filterOut args list = filter (`notElem` list) <$> args + +replaceChar :: Char -> Char -> String -> String +replaceChar from to = (go from) . if from == '/' then go '\\' else id + where + go from' = map (\c -> if c == from' then to else c) From git at git.haskell.org Thu Oct 26 23:16:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create Settings/Builders/ directory for keeping builder-related settings. (1ac1688) Message-ID: <20171026231625.2A8383A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ac1688ff9c472e99125c1583a7a202946a036b4/ghc >--------------------------------------------------------------- commit 1ac1688ff9c472e99125c1583a7a202946a036b4 Author: Andrey Mokhov Date: Thu Aug 6 01:40:41 2015 +0100 Create Settings/Builders/ directory for keeping builder-related settings. >--------------------------------------------------------------- 1ac1688ff9c472e99125c1583a7a202946a036b4 src/Settings/Args.hs | 14 ++++++++++---- src/Settings/Builders/Ar.hs | 18 ++++++++++++++++++ src/Settings/{ => Builders}/Gcc.hs | 21 ++++++++++++++++++++- src/Settings/{ => Builders}/Ghc.hs | 27 ++++++++++++++++++++++++++- src/Settings/{ => Builders}/GhcCabal.hs | 2 +- src/Settings/{ => Builders}/GhcPkg.hs | 4 ++-- src/Settings/Builders/Ld.hs | 18 ++++++++++++++++++ src/Settings/GccM.hs | 25 ------------------------- src/Settings/GhcM.hs | 33 --------------------------------- 9 files changed, 95 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 1ac1688ff9c472e99125c1583a7a202946a036b4 From git at git.haskell.org Thu Oct 26 23:16:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring && back. (4198a65) Message-ID: <20171026231628.852EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4198a65a93270c5be30cf99acecc922bd4a4712b/ghc >--------------------------------------------------------------- commit 4198a65a93270c5be30cf99acecc922bd4a4712b Author: Andrey Mokhov Date: Tue Dec 30 03:53:34 2014 +0000 Bring && back. >--------------------------------------------------------------- 4198a65a93270c5be30cf99acecc922bd4a4712b build.bat | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/build.bat b/build.bat index 0e1f581..b6b9a82 100644 --- a/build.bat +++ b/build.bat @@ -1,3 +1,2 @@ @mkdir _shake 2> nul - at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build - at _shake\build --lint --directory ".." %* + at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:16:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageLibrary build rule. (3f3134c) Message-ID: <20171026231628.95DE23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3f3134cc10b412afc71b7beb80a77ee779ecc3c1/ghc >--------------------------------------------------------------- commit 3f3134cc10b412afc71b7beb80a77ee779ecc3c1 Author: Andrey Mokhov Date: Thu Aug 6 01:41:25 2015 +0100 Add buildPackageLibrary build rule. >--------------------------------------------------------------- 3f3134cc10b412afc71b7beb80a77ee779ecc3c1 src/Rules/Compile.hs | 4 ---- src/Rules/Library.hs | 63 ++++++++++++++++++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 7 +++++- 3 files changed, 69 insertions(+), 5 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 89b60c2..6f57a81 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,10 +12,6 @@ import Rules.Actions import Rules.Resources import Data.Maybe -matchBuildResult :: FilePath -> String -> FilePath -> Bool -matchBuildResult buildPath extension file = - (buildPath "*" ++ extension) ?== file && (isJust . detectWay $ file) - compilePackage :: Resources -> StagePackageTarget -> Rules () compilePackage _ target = do let stage = Target.stage target diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs new file mode 100644 index 0000000..5bd6551 --- /dev/null +++ b/src/Rules/Library.hs @@ -0,0 +1,63 @@ +module Rules.Library (buildPackageLibrary) where + +import Way +import Base +import Util +import Builder +import Switches +import Expression +import qualified Target +import Oracles.PackageData +import Settings.Util +import Settings.TargetDirectory +import Rules.Actions +import Rules.Resources +import Data.Maybe + +buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () +buildPackageLibrary _ target = do + let stage = Target.stage target + pkg = Target.package target + path = targetPath stage pkg + buildPath = path -/- "build" + + matchBuildResult buildPath "a" ?> \a -> do + liftIO $ removeFiles "." [a] + cSrcs <- interpret target $ getPkgDataList CSrcs + modules <- interpret target $ getPkgDataList Modules + + let way = fromJust . detectWay $ a -- fromJust is safe + hsSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] + hsObjs = [ buildPath -/- src <.> osuf way | src <- hsSrcs ] + + need $ cObjs ++ hsObjs -- this will create split objects if required + + splitObjs <- fmap concat $ forM hsSrcs $ \src -> do + let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" + getDirectoryFiles "" [files] + + split <- interpret target splitObjects + let allObjs = if split + then cObjs ++ hsObjs ++ splitObjs + else cObjs ++ hsObjs + + build $ fullTarget target allObjs Ar [a] + +-- ldRule :: Resources -> StagePackageTarget -> Rules () +-- ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) = +-- let pathDist = path dist +-- buildDir = pathDist "build" +-- in +-- priority 2 $ (buildDir "*.o") %> \out -> do +-- cObjs <- pkgCObjects path dist vanilla +-- hObjs <- pkgDepHsObjects path dist vanilla +-- need $ cObjs ++ hObjs +-- run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out +-- synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) +-- putColoured Green $ "/--------\n| Successfully built package '" +-- ++ name ++ "' (stage " ++ show stage ++ ")." +-- putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." +-- ++ "\n\\--------" +-- -- Finally, record the argument list +-- need [argListPath argListDir pkg stage] diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 572fff6..dbbe5cc 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -4,8 +4,13 @@ import Base import Expression import Rules.Data import Rules.Compile +import Rules.Library import Rules.Resources import Rules.Dependencies buildPackage :: Resources -> StagePackageTarget -> Rules () -buildPackage = buildPackageData <> buildPackageDependencies <> compilePackage +buildPackage = mconcat + [ buildPackageData + , buildPackageDependencies + , compilePackage + , buildPackageLibrary ] From git at git.haskell.org Thu Oct 26 23:16:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track progress. (2d4a29c) Message-ID: <20171026231632.3F5EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb/ghc >--------------------------------------------------------------- commit 2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb Author: Andrey Mokhov Date: Tue Dec 30 03:55:34 2014 +0000 Track progress. >--------------------------------------------------------------- 2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb doc/deepseq-build-progress.txt | 359 +++++++++-------------------------------- 1 file changed, 77 insertions(+), 282 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 2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb From git at git.haskell.org Thu Oct 26 23:16:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle dyamic libraries in detectWay. (83cd6c5) Message-ID: <20171026231632.5A9C63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/83cd6c55ba8eeebe877cc643308435afe3c3d785/ghc >--------------------------------------------------------------- commit 83cd6c55ba8eeebe877cc643308435afe3c3d785 Author: Andrey Mokhov Date: Fri Aug 7 01:07:24 2015 +0100 Handle dyamic libraries in detectWay. >--------------------------------------------------------------- 83cd6c55ba8eeebe877cc643308435afe3c3d785 src/Way.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 365a949..3046867 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -126,15 +126,21 @@ libsuf way @ (Way set) = return $ prefix ++ "ghc" ++ version ++ extension -- Detect way from a given filename. Returns Nothing if there is no match: --- * detectWay "foo/bar.hi" == Just vanilla --- * detectWay "baz.thr_p_o" == Just threadedProfiling --- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +-- * detectWay "foo/bar.hi" == Just vanilla +-- * detectWay "baz.thr_p_o" == Just threadedProfiling +-- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +-- * detectWay "xru.p_ghc7.11.20141222.dll" == Just profiling detectWay :: FilePath -> Maybe Way detectWay file = case reads prefix of [(way, "")] -> Just way _ -> Nothing where - prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ takeExtension file + extension = takeExtension file + prefixed = if extension `notElem` ["so", "dll", "dynlib"] + then extension + else takeExtension . dropExtension . + dropExtension . dropExtension $ file + prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed -- Given a path, an extension suffix, and a file name check if the latter: -- 1) conforms to pattern 'path//*suffix' From git at git.haskell.org Thu Oct 26 23:16:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix detectWay and way parsing. (fafec42) Message-ID: <20171026231635.BBB423A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fafec426576d246a2deedb6875258eefcc55a4ee/ghc >--------------------------------------------------------------- commit fafec426576d246a2deedb6875258eefcc55a4ee Author: Andrey Mokhov Date: Fri Aug 7 02:56:02 2015 +0100 Fix detectWay and way parsing. >--------------------------------------------------------------- fafec426576d246a2deedb6875258eefcc55a4ee src/Way.hs | 21 +++++++++++++-------- 1 file changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 3046867..4d14025 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -29,7 +29,7 @@ data WayUnit = Threaded | Dynamic | Parallel | GranSim - deriving Enum + deriving (Eq, Enum) instance Show WayUnit where show unit = case unit of @@ -61,10 +61,15 @@ instance Show Way where tag = intercalate "_" . map show . wayToUnits $ way instance Read Way where - readsPrec _ s = - if s == "v" - then [(vanilla, "")] - else [(wayFromUnits . map read . words . replaceEq '_' ' ' $ s, "")] + readsPrec _ s = if s == "v" then [(vanilla, "")] else result + where + uniqueReads token = case reads token of + [(unit, "")] -> Just unit + _ -> Nothing + units = map uniqueReads . words . replaceEq '_' ' ' $ s + result = if Nothing `elem` units + then [] + else [(wayFromUnits . map fromJust $ units, "")] instance Eq Way where Way a == Way b = a == b @@ -128,7 +133,7 @@ libsuf way @ (Way set) = -- Detect way from a given filename. Returns Nothing if there is no match: -- * detectWay "foo/bar.hi" == Just vanilla -- * detectWay "baz.thr_p_o" == Just threadedProfiling --- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +-- * detectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") -- * detectWay "xru.p_ghc7.11.20141222.dll" == Just profiling detectWay :: FilePath -> Maybe Way detectWay file = case reads prefix of @@ -136,11 +141,11 @@ detectWay file = case reads prefix of _ -> Nothing where extension = takeExtension file - prefixed = if extension `notElem` ["so", "dll", "dynlib"] + prefixed = if extension `notElem` [".so", ".dll", ".dynlib"] then extension else takeExtension . dropExtension . dropExtension . dropExtension $ file - prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed + prefix = drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed -- Given a path, an extension suffix, and a file name check if the latter: -- 1) conforms to pattern 'path//*suffix' From git at git.haskell.org Thu Oct 26 23:16:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for parsing package-data.mk files. (a253255) Message-ID: <20171026231635.B0A283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a253255970c94138f8c67ed298117d6adac0eef2/ghc >--------------------------------------------------------------- commit a253255970c94138f8c67ed298117d6adac0eef2 Author: Andrey Mokhov Date: Tue Dec 30 03:56:28 2014 +0000 Add support for parsing package-data.mk files. >--------------------------------------------------------------- a253255970c94138f8c67ed298117d6adac0eef2 src/Oracles.hs | 39 +++++++++++++++++++++++++++++++++++++-- 1 file changed, 37 insertions(+), 2 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 9ceb121..6a03a6d 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -9,6 +9,7 @@ module Oracles ( path, with, run, argPath, option, argOption, Condition, test, when, unless, not, (&&), (||), + packagaDataOption, PackageDataKey (..), oracleRules ) where @@ -240,9 +241,10 @@ instance ToCondition a => AndOr Flag a where newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + askConfigWithDefault :: String -> Action String -> Action String askConfigWithDefault key defaultAction = do - maybeValue <- askOracle $ ConfigKey $ key + maybeValue <- askOracle $ ConfigKey key case maybeValue of Just value -> return value Nothing -> do @@ -254,6 +256,32 @@ askConfig key = askConfigWithDefault key $ error $ "\nCannot find key '" ++ key ++ "' in configuration files." +newtype PackageDataPair = PackageDataPair (FilePath, String) + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +packagaDataOptionWithDefault :: FilePath -> String -> Action String -> Action String +packagaDataOptionWithDefault file key defaultAction = do + maybeValue <- askOracle $ PackageDataPair (file, key) + case maybeValue of + Just value -> return value + Nothing -> do + result <- defaultAction + return result + +data PackageDataKey = Modules | SrcDirs + +packagaDataOption :: FilePath -> PackageDataKey -> Action String +packagaDataOption file key = do + let keyName = replaceChar '/' '_' $ takeDirectory file ++ case key of + Modules -> "_MODULES" + SrcDirs -> "_HS_SRC_DIRS" + packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" + ++ keyName + ++ "' in " + ++ file + ++ "." + + oracleRules :: Rules () oracleRules = do cfg <- newCache $ \() -> do @@ -273,5 +301,12 @@ oracleRules = do ++ "' is missing; proceeding with default configuration.\n" return M.empty return $ cfgUser `M.union` cfgDefault - addOracle $ \(ConfigKey x) -> M.lookup x <$> cfg () + + addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () + + pkgData <- newCache $ \file -> do + need [file] + liftIO $ readConfigFile file + + addOracle $ \(PackageDataPair (file, key)) -> M.lookup key <$> pkgData file return () From git at git.haskell.org Thu Oct 26 23:16:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add putSuccess helper function. (a6623ab) Message-ID: <20171026231639.770103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a6623ab5988c2705b22e8a5157db013595f634ce/ghc >--------------------------------------------------------------- commit a6623ab5988c2705b22e8a5157db013595f634ce Author: Andrey Mokhov Date: Fri Aug 7 02:56:33 2015 +0100 Add putSuccess helper function. >--------------------------------------------------------------- a6623ab5988c2705b22e8a5157db013595f634ce src/Util.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 1c34a87..7a68b2a 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -4,7 +4,7 @@ module Util ( replaceIf, replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, - putColoured, putOracle, putBuild, putError, + putColoured, putOracle, putBuild, putSuccess, putError, bimap, minusOrd, intersectOrd ) where @@ -69,6 +69,12 @@ putBuild :: String -> Action () putBuild = putColoured White -- A more colourful version of error +putSuccess :: String -> Action a +putSuccess msg = do + putColoured Green msg + error $ "GHC build system error: " ++ msg + +-- A more colourful version of error putError :: String -> Action a putError msg = do putColoured Red msg From git at git.haskell.org Thu Oct 26 23:16:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageDeps rule. (9d1a489) Message-ID: <20171026231639.7B3103A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d1a489b8faf8f91f6125865a5a74712a8b8a7a8/ghc >--------------------------------------------------------------- commit 9d1a489b8faf8f91f6125865a5a74712a8b8a7a8 Author: Andrey Mokhov Date: Tue Dec 30 03:57:22 2014 +0000 Add buildPackageDeps rule. >--------------------------------------------------------------- 9d1a489b8faf8f91f6125865a5a74712a8b8a7a8 doc/deepseq-build-progress.txt | 41 ++------------------ src/Package.hs | 88 ++++++++++++++++++++++++++++++++++++++++-- 2 files changed, 87 insertions(+), 42 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9d1a489b8faf8f91f6125865a5a74712a8b8a7a8 From git at git.haskell.org Thu Oct 26 23:16:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add library targets. (e3e3c1d) Message-ID: <20171026231643.8CB063A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3e3c1d6e03c1fd46af44afd5e29e7b1a4000093/ghc >--------------------------------------------------------------- commit e3e3c1d6e03c1fd46af44afd5e29e7b1a4000093 Author: Andrey Mokhov Date: Fri Aug 7 02:57:05 2015 +0100 Add library targets. >--------------------------------------------------------------- e3e3c1d6e03c1fd46af44afd5e29e7b1a4000093 src/Rules.hs | 22 +++++++++++++++++++--- 1 file changed, 19 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index be109f8..2509cf7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -2,15 +2,19 @@ module Rules ( oracleRules, cabalRules, configRules, packageRules, generateTargets ) where +import Way import Base import Util import Stage import Expression +import Oracles.PackageData import Rules.Cabal import Rules.Config import Rules.Package import Rules.Oracles import Rules.Resources +import Settings.Ways +import Settings.Util import Settings.Packages import Settings.TargetDirectory @@ -19,9 +23,21 @@ generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpret (stageTarget stage) getPackages - fmap concat . forM pkgs $ \pkg -> return - [ targetPath stage pkg -/- "build/haskell.deps" - , targetPath stage pkg -/- "build/c.deps" ] + fmap concat . forM pkgs $ \pkg -> do + let target = stagePackageTarget stage pkg + buildPath = targetPath stage pkg -/- "build" + buildGhciLib <- interpret target $ getPkgData BuildGhciLib + pkgKey <- interpret target $ getPkgData PackageKey + let ghciLib = [ buildPath -/- "HS" ++ pkgKey <.> "o" + | buildGhciLib == "YES" && stage /= Stage0 ] + + ways <- interpret target getWays + libs <- forM ways $ \way -> do + extension <- libsuf way + return $ buildPath -/- "libHS" ++ pkgKey <.> extension + + return $ ghciLib ++ libs + need targets -- TODO: add Stage2 (compiler only?) From git at git.haskell.org Thu Oct 26 23:16:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move generic helper functions to Util.hs. (4e5f1b7) Message-ID: <20171026231643.8C39E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e5f1b74b9b5946ad614bc354f01697f953a072b/ghc >--------------------------------------------------------------- commit 4e5f1b74b9b5946ad614bc354f01697f953a072b Author: Andrey Mokhov Date: Tue Dec 30 15:06:13 2014 +0000 Move generic helper functions to Util.hs. >--------------------------------------------------------------- 4e5f1b74b9b5946ad614bc354f01697f953a072b src/Base.hs | 8 +------- src/Oracles.hs | 9 ++++----- src/Package.hs | 5 +++-- src/Util.hs | 16 ++++++++++++++++ 4 files changed, 24 insertions(+), 14 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index eaebaf3..24943e4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -9,8 +9,7 @@ module Base ( Stage (..), Args, arg, joinArgs, joinArgsWithSpaces, - filterOut, - replaceChar + filterOut ) where import Development.Shake hiding ((*>)) @@ -43,8 +42,3 @@ joinArgs = intercalateArgs "" filterOut :: Args -> [String] -> Args filterOut args list = filter (`notElem` list) <$> args - -replaceChar :: Char -> Char -> String -> String -replaceChar from to = (go from) . if from == '/' then go '\\' else id - where - go from' = map (\c -> if c == from' then to else c) diff --git a/src/Oracles.hs b/src/Oracles.hs index 6a03a6d..98321c9 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -20,8 +20,8 @@ import Control.Monad hiding (when, unless) import qualified Data.HashMap.Strict as M import qualified Prelude import Prelude hiding (not, (&&), (||)) -import Data.Char import Base +import Util import Config data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage @@ -241,7 +241,6 @@ instance ToCondition a => AndOr Flag a where newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) - askConfigWithDefault :: String -> Action String -> Action String askConfigWithDefault key defaultAction = do maybeValue <- askOracle $ ConfigKey key @@ -266,20 +265,20 @@ packagaDataOptionWithDefault file key defaultAction = do Just value -> return value Nothing -> do result <- defaultAction - return result + return result -- TODO: simplify data PackageDataKey = Modules | SrcDirs packagaDataOption :: FilePath -> PackageDataKey -> Action String packagaDataOption file key = do - let keyName = replaceChar '/' '_' $ takeDirectory file ++ case key of + let keyName = replaceIf isSlash '_' $ takeDirectory file ++ case key of Modules -> "_MODULES" SrcDirs -> "_HS_SRC_DIRS" packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file - ++ "." + ++ "." -- TODO: Improve formatting oracleRules :: Rules () diff --git a/src/Package.hs b/src/Package.hs index a6df921..8488044 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -4,6 +4,7 @@ module Package ( ) where import Base +import Util import Ways import Oracles @@ -129,7 +130,7 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs let pkgDataFile = path dist "package-data.mk" pkgData <- lines <$> liftIO (readFile pkgDataFile) - length pkgData `seq` writeFileLines pkgDataFile $ map (replaceChar '/' '_') $ filter ('$' `notElem`) pkgData + length pkgData `seq` writeFileLines pkgDataFile $ map (replaceIf isSlash '_') $ filter ('$' `notElem`) pkgData where cabalArgs, ghcPkgArgs :: Args cabalArgs = mconcat @@ -225,7 +226,7 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = autogen = dist "build" "autogen" mods <- words <$> packagaDataOption pkgData Modules src <- getDirectoryFiles "" $ do - start <- map (replaceChar '.' '/') mods + start <- map (replaceEq '.' '/') mods end <- [".hs", ".lhs"] return $ path ++ "//" ++ start ++ end run (Ghc stage) $ mconcat diff --git a/src/Util.hs b/src/Util.hs new file mode 100644 index 0000000..8afd6cb --- /dev/null +++ b/src/Util.hs @@ -0,0 +1,16 @@ +module Util ( + module Data.Char, + isSlash, + replaceIf, replaceEq + ) where + +import Data.Char + +isSlash :: Char -> Bool +isSlash = (`elem` ['/', '\\']) + +replaceIf :: (a -> Bool) -> a -> [a] -> [a] +replaceIf p to = map (\from -> if p from then to else from) + +replaceEq :: Eq a => a -> a -> [a] -> [a] +replaceEq from = replaceIf (== from) From git at git.haskell.org Thu Oct 26 23:16:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Oracles.hs. (e20c4bc) Message-ID: <20171026231647.6FC4B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e20c4bc3bec68971837c2808724edbfcbe0b92ab/ghc >--------------------------------------------------------------- commit e20c4bc3bec68971837c2808724edbfcbe0b92ab Author: Andrey Mokhov Date: Tue Dec 30 15:12:40 2014 +0000 Refactor Oracles.hs. >--------------------------------------------------------------- e20c4bc3bec68971837c2808724edbfcbe0b92ab src/Oracles.hs | 21 ++++++--------------- 1 file changed, 6 insertions(+), 15 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 98321c9..75439fb 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -246,14 +246,11 @@ askConfigWithDefault key defaultAction = do maybeValue <- askOracle $ ConfigKey key case maybeValue of Just value -> return value - Nothing -> do - result <- defaultAction - return result + Nothing -> defaultAction askConfig :: String -> Action String -askConfig key = askConfigWithDefault key $ error $ "\nCannot find key '" - ++ key - ++ "' in configuration files." +askConfig key = askConfigWithDefault key $ + error $ "\nCannot find key '" ++ key ++ "' in configuration files." newtype PackageDataPair = PackageDataPair (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -263,9 +260,7 @@ packagaDataOptionWithDefault file key defaultAction = do maybeValue <- askOracle $ PackageDataPair (file, key) case maybeValue of Just value -> return value - Nothing -> do - result <- defaultAction - return result -- TODO: simplify + Nothing -> defaultAction data PackageDataKey = Modules | SrcDirs @@ -274,12 +269,8 @@ packagaDataOption file key = do let keyName = replaceIf isSlash '_' $ takeDirectory file ++ case key of Modules -> "_MODULES" SrcDirs -> "_HS_SRC_DIRS" - packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" - ++ keyName - ++ "' in " - ++ file - ++ "." -- TODO: Improve formatting - + packagaDataOptionWithDefault file keyName $ + error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." oracleRules :: Rules () oracleRules = do From git at git.haskell.org Thu Oct 26 23:16:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for BUILD_GHCI_LIB field of package-data.mk. (85808dd) Message-ID: <20171026231647.798C53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/85808dd149afdb17d34f9e877029bc8c50020b63/ghc >--------------------------------------------------------------- commit 85808dd149afdb17d34f9e877029bc8c50020b63 Author: Andrey Mokhov Date: Fri Aug 7 02:57:44 2015 +0100 Add support for BUILD_GHCI_LIB field of package-data.mk. >--------------------------------------------------------------- 85808dd149afdb17d34f9e877029bc8c50020b63 src/Oracles/PackageData.hs | 14 ++++++++------ 1 file changed, 8 insertions(+), 6 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index c01c87f..de9db7c 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -20,9 +20,10 @@ import qualified Data.HashMap.Strict as Map -- PackageDataList is used for multiple string options separated by spaces, -- such as 'path_MODULES = Data.Array Data.Array.Base ...'. -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] -data PackageData = Version FilePath - | PackageKey FilePath - | Synopsis FilePath +data PackageData = Version FilePath + | PackageKey FilePath + | Synopsis FilePath + | BuildGhciLib FilePath data PackageDataList = Modules FilePath | SrcDirs FilePath @@ -51,9 +52,10 @@ askPackageData path key = do pkgData :: PackageData -> Action String pkgData packageData = do let (key, path) = case packageData of - Version path -> ("VERSION" , path) - PackageKey path -> ("PACKAGE_KEY" , path) - Synopsis path -> ("SYNOPSIS" , path) + Version path -> ("VERSION" , path) + PackageKey path -> ("PACKAGE_KEY" , path) + Synopsis path -> ("SYNOPSIS" , path) + BuildGhciLib path -> ("BUILD_GHCI_LIB", path) fullKey = replaceSeparators '_' $ path ++ "_" ++ key pkgData = path -/- "package-data.mk" res <- askOracle $ PackageDataKey (pkgData, fullKey) From git at git.haskell.org Thu Oct 26 23:16:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting, add TODOs. (d2f3a74) Message-ID: <20171026231651.3BA983A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2f3a74ae4e0ba1218025aca1b2786a35f169cee/ghc >--------------------------------------------------------------- commit d2f3a74ae4e0ba1218025aca1b2786a35f169cee Author: Andrey Mokhov Date: Tue Dec 30 15:20:37 2014 +0000 Fix formatting, add TODOs. >--------------------------------------------------------------- d2f3a74ae4e0ba1218025aca1b2786a35f169cee src/Ways.hs | 21 +++++++++++---------- 1 file changed, 11 insertions(+), 10 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 6e186ab..91cbd4f 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -23,7 +23,7 @@ data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dyn data Way = Way { tag :: String, -- e.g., "thr_p" - description :: String, -- e.g., "threaded profiled" + description :: String, -- e.g., "threaded profiled"; TODO: get rid of this field? units :: [WayUnit] -- e.g., [Threaded, Profiling] } deriving Eq @@ -72,17 +72,18 @@ defaultWays stage = do wayHcOpts :: Way -> Args wayHcOpts (Way _ _ units) = mconcat - [ when (Dynamic `notElem` units) $ arg [ "-static" ] - , when (Dynamic `elem` units) $ arg [ "-fPIC", "-dynamic" ] - , when (Threaded `elem` units) $ arg [ "-optc-DTHREADED_RTS" ] - , when (Debug `elem` units) $ arg [ "-optc-DDEBUG" ] - , when (Profiling `elem` units) $ arg [ "-prof" ] - , when (Logging `elem` units) $ arg [ "-eventlog" ] - , when (Parallel `elem` units) $ arg [ "-parallel" ] - , when (GranSim `elem` units) $ arg [ "-gransim" ] - , when (units == [Debug] || units == [Debug, Dynamic]) $ arg [ "-ticky", "-DTICKY_TICKY" ] + [ when (Dynamic `notElem` units) $ arg ["-static"] + , when (Dynamic `elem` units) $ arg ["-fPIC", "-dynamic"] + , when (Threaded `elem` units) $ arg ["-optc-DTHREADED_RTS"] + , when (Debug `elem` units) $ arg ["-optc-DDEBUG"] + , when (Profiling `elem` units) $ arg ["-prof"] + , when (Logging `elem` units) $ arg ["-eventlog"] + , when (Parallel `elem` units) $ arg ["-parallel"] + , when (GranSim `elem` units) $ arg ["-gransim"] + , when (units == [Debug] || units == [Debug, Dynamic]) $ arg ["-ticky", "-DTICKY_TICKY"] ] +-- TODO: cover other cases suffix :: FilePath -> Way -> FilePath suffix base (Way _ _ units) = concat $ From git at git.haskell.org Thu Oct 26 23:16:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement build rule for GHCI libraries. (020d528) Message-ID: <20171026231651.319C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/020d528e4a296e264bee478f3d89b63d6bb1f0b9/ghc >--------------------------------------------------------------- commit 020d528e4a296e264bee478f3d89b63d6bb1f0b9 Author: Andrey Mokhov Date: Fri Aug 7 02:58:15 2015 +0100 Implement build rule for GHCI libraries. >--------------------------------------------------------------- 020d528e4a296e264bee478f3d89b63d6bb1f0b9 src/Rules/Library.hs | 53 +++++++++++++++++++-------------------- src/Settings/Builders/GhcCabal.hs | 1 + 2 files changed, 27 insertions(+), 27 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 5bd6551..c788edb 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -4,6 +4,7 @@ import Way import Base import Util import Builder +import Package import Switches import Expression import qualified Target @@ -12,6 +13,7 @@ import Settings.Util import Settings.TargetDirectory import Rules.Actions import Rules.Resources +import Data.List import Data.Maybe buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () @@ -21,6 +23,7 @@ buildPackageLibrary _ target = do path = targetPath stage pkg buildPath = path -/- "build" + -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do liftIO $ removeFiles "." [a] cSrcs <- interpret target $ getPkgDataList CSrcs @@ -33,31 +36,27 @@ buildPackageLibrary _ target = do need $ cObjs ++ hsObjs -- this will create split objects if required - splitObjs <- fmap concat $ forM hsSrcs $ \src -> do - let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" - getDirectoryFiles "" [files] - split <- interpret target splitObjects - let allObjs = if split - then cObjs ++ hsObjs ++ splitObjs - else cObjs ++ hsObjs - - build $ fullTarget target allObjs Ar [a] - --- ldRule :: Resources -> StagePackageTarget -> Rules () --- ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) = --- let pathDist = path dist --- buildDir = pathDist "build" --- in --- priority 2 $ (buildDir "*.o") %> \out -> do --- cObjs <- pkgCObjects path dist vanilla --- hObjs <- pkgDepHsObjects path dist vanilla --- need $ cObjs ++ hObjs --- run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out --- synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) --- putColoured Green $ "/--------\n| Successfully built package '" --- ++ name ++ "' (stage " ++ show stage ++ ")." --- putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." --- ++ "\n\\--------" --- -- Finally, record the argument list --- need [argListPath argListDir pkg stage] + splitObjs <- if split + then fmap concat $ forM hsSrcs $ \src -> do + let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" + getDirectoryFiles "" [files] + else return [] + + build $ fullTarget target (cObjs ++ hsObjs ++ splitObjs) Ar [a] + + synopsis <- interpret target $ getPkgData Synopsis + putSuccess $ "/--------\n| Successfully built package '" + ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + putSuccess $ "| Package synopsis: " + ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" + + -- TODO: this looks fragile as haskell objects can match this rule if their + -- names start with "HS" and they are on top of the module hierarchy. + (buildPath -/- "HS*.o") %> \o -> do + cSrcs <- interpret target $ getPkgDataList CSrcs + modules <- interpret target $ getPkgDataList Modules + let hsSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] + hsObjs = [ buildPath -/- src <.> "o" | src <- hsSrcs ] + build $ fullTarget target (cObjs ++ hsObjs) Ld [o] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 301791d..6969aec 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -39,6 +39,7 @@ cabalArgs = builder GhcCabal ? do , with Happy ] -- TODO: Isn't vanilla always built? If yes, some conditions are redundant. +-- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do ways <- getWays From git at git.haskell.org Thu Oct 26 23:16:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out postProcessPackageData to Util.hs. (c4cc0dc) Message-ID: <20171026231654.A330A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4cc0dc7ab0465a67f9f81e309fa10eaa210b772/ghc >--------------------------------------------------------------- commit c4cc0dc7ab0465a67f9f81e309fa10eaa210b772 Author: Andrey Mokhov Date: Tue Dec 30 15:33:06 2014 +0000 Factor out postProcessPackageData to Util.hs. >--------------------------------------------------------------- c4cc0dc7ab0465a67f9f81e309fa10eaa210b772 src/Package.hs | 6 ++---- src/Util.hs | 12 +++++++++++- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 8488044..24ef85d 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -122,15 +122,13 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = "inplace-pkg-config", "setup-config", "build" "autogen" "cabal_macros.h", - "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? What's up with Paths_cpsa.hs? + "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. ] &%> \_ -> do need [path name <.> "cabal"] when (doesFileExist $ path "configure.ac") $ need [path "configure"] run GhcCabal cabalArgs when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs - let pkgDataFile = path dist "package-data.mk" - pkgData <- lines <$> liftIO (readFile pkgDataFile) - length pkgData `seq` writeFileLines pkgDataFile $ map (replaceIf isSlash '_') $ filter ('$' `notElem`) pkgData + postProcessPackageData $ path dist "package-data.mk" where cabalArgs, ghcPkgArgs :: Args cabalArgs = mconcat diff --git a/src/Util.hs b/src/Util.hs index 8afd6cb..b8a38f4 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,9 +1,11 @@ module Util ( module Data.Char, isSlash, - replaceIf, replaceEq + replaceIf, replaceEq, + postProcessPackageData ) where +import Base import Data.Char isSlash :: Char -> Bool @@ -14,3 +16,11 @@ replaceIf p to = map (\from -> if p from then to else from) replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) + +-- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: +-- 1) Drop lines containing '$' +-- 2) Replace '/' and '\' with '_' +postProcessPackageData :: FilePath -> Action () +postProcessPackageData file = do + pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) + length pkgData `seq` writeFileLines file $ map (replaceIf isSlash '_') pkgData From git at git.haskell.org Thu Oct 26 23:16:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove error from putSuccess :-) (9afd164) Message-ID: <20171026231654.A9F693A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9afd164fa76821409208e8a425ccaee625a8ee94/ghc >--------------------------------------------------------------- commit 9afd164fa76821409208e8a425ccaee625a8ee94 Author: Andrey Mokhov Date: Fri Aug 7 12:24:17 2015 +0100 Remove error from putSuccess :-) >--------------------------------------------------------------- 9afd164fa76821409208e8a425ccaee625a8ee94 src/Util.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index 7a68b2a..dd0f2d8 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -69,10 +69,8 @@ putBuild :: String -> Action () putBuild = putColoured White -- A more colourful version of error -putSuccess :: String -> Action a -putSuccess msg = do - putColoured Green msg - error $ "GHC build system error: " ++ msg +putSuccess :: String -> Action () +putSuccess = putColoured Green -- A more colourful version of error putError :: String -> Action a From git at git.haskell.org Thu Oct 26 23:16:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reverse the target list passed to need (otherwise the targets are build in reverse order). (b397bb3) Message-ID: <20171026231658.DB7063A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b397bb360a980c60290df89a6b358b614edce5a9/ghc >--------------------------------------------------------------- commit b397bb360a980c60290df89a6b358b614edce5a9 Author: Andrey Mokhov Date: Fri Aug 7 12:25:28 2015 +0100 Reverse the target list passed to need (otherwise the targets are build in reverse order). >--------------------------------------------------------------- b397bb360a980c60290df89a6b358b614edce5a9 src/Rules.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules.hs b/src/Rules.hs index 2509cf7..43f5922 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -38,7 +38,7 @@ generateTargets = action $ do return $ ghciLib ++ libs - need targets + need $ reverse targets -- TODO: add Stage2 (compiler only?) packageRules :: Rules () From git at git.haskell.org Thu Oct 26 23:16:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:16:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add splitArgs function to Base.hs. (4dd9560) Message-ID: <20171026231658.D8CC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4dd9560e34ded015140a7d5d4d2e22d27e19abb2/ghc >--------------------------------------------------------------- commit 4dd9560e34ded015140a7d5d4d2e22d27e19abb2 Author: Andrey Mokhov Date: Tue Dec 30 17:03:10 2014 +0000 Add splitArgs function to Base.hs. >--------------------------------------------------------------- 4dd9560e34ded015140a7d5d4d2e22d27e19abb2 src/Base.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 24943e4..a0f4303 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -8,7 +8,7 @@ module Base ( module Data.List, Stage (..), Args, arg, - joinArgs, joinArgsWithSpaces, + joinArgs, joinArgsWithSpaces, splitArgs, filterOut ) where @@ -40,5 +40,8 @@ joinArgsWithSpaces = intercalateArgs " " joinArgs :: Args -> Args joinArgs = intercalateArgs "" +splitArgs :: Args -> Args +splitArgs = fmap (concatMap words) + filterOut :: Args -> [String] -> Args filterOut args list = filter (`notElem` list) <$> args From git at git.haskell.org Thu Oct 26 23:17:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add src-hc-opts to configuration files. (5adb8aa) Message-ID: <20171026231702.D940C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5adb8aa730e9ae9649924f7f8ea59b0e5163876d/ghc >--------------------------------------------------------------- commit 5adb8aa730e9ae9649924f7f8ea59b0e5163876d Author: Andrey Mokhov Date: Tue Dec 30 17:04:28 2014 +0000 Add src-hc-opts to configuration files. >--------------------------------------------------------------- 5adb8aa730e9ae9649924f7f8ea59b0e5163876d cfg/default.config.in | 2 ++ 1 file changed, 2 insertions(+) diff --git a/cfg/default.config.in b/cfg/default.config.in index d3617f4..1a28981 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -61,6 +61,8 @@ conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ +src-hc-opts = -H32m -O + # Include and library directories: #================================= From git at git.haskell.org Thu Oct 26 23:17:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop need from build. Add appropriate needs to build rules. (5bb1d7e) Message-ID: <20171026231702.D3DC33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5bb1d7e24f6f51f2d2e570de47b5f554bb990753/ghc >--------------------------------------------------------------- commit 5bb1d7e24f6f51f2d2e570de47b5f554bb990753 Author: Andrey Mokhov Date: Fri Aug 7 12:26:57 2015 +0100 Drop need from build. Add appropriate needs to build rules. >--------------------------------------------------------------- 5bb1d7e24f6f51f2d2e570de47b5f554bb990753 src/Rules/Actions.hs | 2 +- src/Rules/Compile.hs | 5 +++++ src/Rules/Data.hs | 1 + src/Rules/Dependencies.hs | 4 +++- 4 files changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 50eb87f..062a5d5 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -21,7 +21,7 @@ buildWithResources rs target = do let builder = Target.builder target deps = Target.dependencies target needBuilder builder - need deps + -- need deps -- TODO: think if needs could be done here path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 6f57a81..223f9b2 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -35,6 +35,11 @@ compilePackage _ target = do when (null cDeps && null hDeps) $ putError $ "Cannot determine sources for '" ++ obj ++ "'." + when (not (null cDeps) && not (null hDeps)) $ + putError $ "Both .c and .hs sources found for '" ++ obj ++ "'." + + need $ hDeps ++ cDeps + if null cDeps then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] else build $ fullTarget target cDeps (Gcc stage) [obj] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 8f365e8..8b3eb05 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -45,6 +45,7 @@ buildPackageData (Resources ghcCabal ghcPkg) target = do depPkgs = intersectOrd cmp (sort pkgs) deps need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] + need [cabal] buildWithResources [(ghcCabal, 1)] $ fullTarget target [cabal] GhcCabal files diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index bee85c6..ea47241 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -22,15 +22,17 @@ buildPackageDependencies _ target = in do (buildPath "*.c.deps") %> \depFile -> do let srcFile = dropBuild . dropExtension $ depFile + need [srcFile] build $ fullTarget target [srcFile] (GccM stage) [depFile] (buildPath -/- "c.deps") %> \file -> do srcs <- pkgDataList $ CSrcs path let depFiles = [ buildPath -/- src <.> "deps" | src <- srcs ] - need depFiles -- increase parallelism by needing all at once + need depFiles deps <- mapM readFile' depFiles writeFileChanged file (concat deps) (buildPath -/- "haskell.deps") %> \file -> do srcs <- interpret target getHsSources + need srcs build $ fullTarget target srcs (GhcM stage) [file] From git at git.haskell.org Thu Oct 26 23:17:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Export wayHcOpts. (980d486) Message-ID: <20171026231706.491033A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/980d48665a5bd7dfb275d403628e34b140bd2567/ghc >--------------------------------------------------------------- commit 980d48665a5bd7dfb275d403628e34b140bd2567 Author: Andrey Mokhov Date: Tue Dec 30 17:06:00 2014 +0000 Export wayHcOpts. >--------------------------------------------------------------- 980d48665a5bd7dfb275d403628e34b140bd2567 src/Ways.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Ways.hs b/src/Ways.hs index 91cbd4f..a0e886a 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -12,6 +12,7 @@ module Ways ( threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic, + wayHcOpts, hisuf, osuf, hcsuf ) where From git at git.haskell.org Thu Oct 26 23:17:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (036328f) Message-ID: <20171026231706.453DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/036328f08a067c6d8817c1d56d43e4f5b68d9e0f/ghc >--------------------------------------------------------------- commit 036328f08a067c6d8817c1d56d43e4f5b68d9e0f Author: Andrey Mokhov Date: Fri Aug 7 12:28:07 2015 +0100 Clean up. >--------------------------------------------------------------- 036328f08a067c6d8817c1d56d43e4f5b68d9e0f src/Rules/Library.hs | 32 +++++++++++++++++--------------- 1 file changed, 17 insertions(+), 15 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index c788edb..fe0c72d 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -29,34 +29,36 @@ buildPackageLibrary _ target = do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules - let way = fromJust . detectWay $ a -- fromJust is safe - hsSrcs = map (replaceEq '.' '/') modules - cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] - hsObjs = [ buildPath -/- src <.> osuf way | src <- hsSrcs ] + let way = fromJust . detectWay $ a -- fromJust is safe + hSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] + hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] - need $ cObjs ++ hsObjs -- this will create split objects if required + need $ cObjs ++ hObjs -- this will create split objects if required split <- interpret target splitObjects splitObjs <- if split - then fmap concat $ forM hsSrcs $ \src -> do + then fmap concat $ forM hSrcs $ \src -> do let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" - getDirectoryFiles "" [files] + fmap (map unifyPath) $ getDirectoryFiles "" [files] else return [] - build $ fullTarget target (cObjs ++ hsObjs ++ splitObjs) Ar [a] + build $ fullTarget target (cObjs ++ hObjs ++ splitObjs) Ar [a] synopsis <- interpret target $ getPkgData Synopsis - putSuccess $ "/--------\n| Successfully built package '" - ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + putSuccess $ "/--------\n| Successfully built package library '" + ++ pkgName pkg + ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." putSuccess $ "| Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. - (buildPath -/- "HS*.o") %> \o -> do + priority 2 $ (buildPath -/- "HS*.o") %> \o -> do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules - let hsSrcs = map (replaceEq '.' '/') modules - cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] - hsObjs = [ buildPath -/- src <.> "o" | src <- hsSrcs ] - build $ fullTarget target (cObjs ++ hsObjs) Ld [o] + let hSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] + hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] + need $ cObjs ++ hObjs + build $ fullTarget target (cObjs ++ hObjs) Ld [o] From git at git.haskell.org Thu Oct 26 23:17:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add hibootsuf and an unsafe version of safeDetectWay. (c48554d) Message-ID: <20171026231709.C0B693A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c48554d96ebfb9b55c4b6be9fcbc52b23b24ef2d/ghc >--------------------------------------------------------------- commit c48554d96ebfb9b55c4b6be9fcbc52b23b24ef2d Author: Andrey Mokhov Date: Fri Aug 7 22:32:59 2015 +0100 Add hibootsuf and an unsafe version of safeDetectWay. >--------------------------------------------------------------- c48554d96ebfb9b55c4b6be9fcbc52b23b24ef2d src/Way.hs | 39 ++++++++++++++++++++++----------------- 1 file changed, 22 insertions(+), 17 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 4d14025..74d1f26 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -9,8 +9,8 @@ module Way ( -- TODO: rename to "Way"? threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic, - wayPrefix, hisuf, osuf, hcsuf, obootsuf, ssuf, libsuf, - detectWay, matchBuildResult + wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, + safeDetectWay, detectWay, matchBuildResult ) where import Base @@ -103,11 +103,12 @@ wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" hisuf, osuf, hcsuf, obootsuf, ssuf :: Way -> String -osuf = (++ "o" ) . wayPrefix -ssuf = (++ "s" ) . wayPrefix -hisuf = (++ "hi" ) . wayPrefix -hcsuf = (++ "hc" ) . wayPrefix -obootsuf = (++ "o-boot") . wayPrefix +osuf = (++ "o" ) . wayPrefix +ssuf = (++ "s" ) . wayPrefix +hisuf = (++ "hi" ) . wayPrefix +hcsuf = (++ "hc" ) . wayPrefix +obootsuf = (++ "o-boot" ) . wayPrefix +hibootsuf = (++ "hi-boot") . wayPrefix -- Note: in the previous build system libsuf was mysteriously different -- from other suffixes. For example, in the profiling way it used to be @@ -131,12 +132,12 @@ libsuf way @ (Way set) = return $ prefix ++ "ghc" ++ version ++ extension -- Detect way from a given filename. Returns Nothing if there is no match: --- * detectWay "foo/bar.hi" == Just vanilla --- * detectWay "baz.thr_p_o" == Just threadedProfiling --- * detectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") --- * detectWay "xru.p_ghc7.11.20141222.dll" == Just profiling -detectWay :: FilePath -> Maybe Way -detectWay file = case reads prefix of +-- * safeDetectWay "foo/bar.hi" == Just vanilla +-- * safeDetectWay "baz.thr_p_o" == Just threadedProfiling +-- * safeDetectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") +-- * safeDetectWay "xru.p_ghc7.11.20141222.so" == Just profiling +safeDetectWay :: FilePath -> Maybe Way +safeDetectWay file = case reads prefix of [(way, "")] -> Just way _ -> Nothing where @@ -147,12 +148,16 @@ detectWay file = case reads prefix of dropExtension . dropExtension $ file prefix = drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed --- Given a path, an extension suffix, and a file name check if the latter: --- 1) conforms to pattern 'path//*suffix' --- 2) has extension prefixed with a known way tag, i.e. detectWay does not fail +-- Unsafe version of safeDetectWay. Useful when matchBuildResult has succeeded. +detectWay :: FilePath -> Way +detectWay = fromJust . safeDetectWay + +-- Given a path, an extension suffix, and a file name check: +-- 1) the file conforms to pattern 'path//*suffix' +-- 2) file's extension has a valid way tag (i.e., safeDetectWay does not fail) matchBuildResult :: FilePath -> String -> FilePath -> Bool matchBuildResult path suffix file = - (path "*" ++ suffix) ?== file && (isJust . detectWay $ file) + (path "*" ++ suffix) ?== file && isJust (safeDetectWay file) -- Instances for storing in the Shake database instance Binary Way where From git at git.haskell.org Thu Oct 26 23:17:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for src-hc-opts configuration option. (9007c90) Message-ID: <20171026231709.C13A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9007c90cce429df3f0f60737d4a93a127f5e5274/ghc >--------------------------------------------------------------- commit 9007c90cce429df3f0f60737d4a93a127f5e5274 Author: Andrey Mokhov Date: Tue Dec 30 17:06:52 2014 +0000 Add support for src-hc-opts configuration option. >--------------------------------------------------------------- 9007c90cce429df3f0f60737d4a93a127f5e5274 src/Oracles.hs | 2 ++ src/Package.hs | 50 ++++++++++++++++++++++++++------------------------ 2 files changed, 28 insertions(+), 24 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 75439fb..ff4bd95 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -101,6 +101,7 @@ run builder args = do data Option = TargetOS | TargetArch | TargetPlatformFull | ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage | IconvIncludeDirs | IconvLibDirs | GmpIncludeDirs | GmpLibDirs + | SrcHcOpts | HostOsCpp | Root option :: Option -> Action String @@ -125,6 +126,7 @@ option opt = askConfig $ case opt of IconvLibDirs -> "iconv-lib-dirs" GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" + SrcHcOpts -> "src-hc-opts" HostOsCpp -> "host-os-cpp" argOption :: Option -> Args diff --git a/src/Package.hs b/src/Package.hs index 24ef85d..9e60a24 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -163,6 +163,29 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs +-- $1_$2_$3_MOST_DIR_HC_OPTS = \ +-- $$($1_$2_$3_MOST_HC_OPTS) \ +-- -odir $1/$2/build -hidir $1/$2/build -stubdir $1/$2/build + +-- # Some of the Haskell files (e.g. utils/hsc2hs/Main.hs) (directly or +-- # indirectly) include the generated includes files. +-- $$($1_$2_depfile_haskell) : $$(includes_H_CONFIG) $$(includes_H_PLATFORM) +-- +-- $$($1_$2_depfile_haskell) : $$($1_$2_HS_SRCS) $$($1_$2_HS_BOOT_SRCS) $$$$($1_$2_HC_MK_DEPEND_DEP) | $$$$(dir $$$$@)/. +-- $$(call removeFiles,$$@.tmp) +-- ifneq "$$($1_$2_HS_SRCS)" "" +-- "$$($1_$2_HC_MK_DEPEND)" -M \ +-- $$($1_$2_$$(firstword $$($1_$2_WAYS))_MOST_DIR_HC_OPTS) \ +-- $$($1_$2_MKDEPENDHS_FLAGS) \ +-- $$($1_$2_HS_SRCS) +-- endif +-- echo "$1_$2_depfile_haskell_EXISTS = YES" >> $$@.tmp +-- ifneq "$$($1_$2_SLASH_MODS)" "" +-- for dir in $$(sort $$(foreach mod,$$($1_$2_SLASH_MODS),$1/$2/build/$$(dir $$(mod)))); do \ +-- if test ! -d $$$$dir; then mkdir -p $$$$dir; fi \ +-- done +-- endif + -- $1_$2_$3_MOST_HC_OPTS = \ -- $$(WAY_$3_HC_OPTS) \ -- $$(CONF_HC_OPTS) \ @@ -190,31 +213,8 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) - --- $1_$2_$3_MOST_DIR_HC_OPTS = \ --- $$($1_$2_$3_MOST_HC_OPTS) \ --- -odir $1/$2/build -hidir $1/$2/build -stubdir $1/$2/build - --- # Some of the Haskell files (e.g. utils/hsc2hs/Main.hs) (directly or --- # indirectly) include the generated includes files. --- $$($1_$2_depfile_haskell) : $$(includes_H_CONFIG) $$(includes_H_PLATFORM) --- --- $$($1_$2_depfile_haskell) : $$($1_$2_HS_SRCS) $$($1_$2_HS_BOOT_SRCS) $$$$($1_$2_HC_MK_DEPEND_DEP) | $$$$(dir $$$$@)/. --- $$(call removeFiles,$$@.tmp) --- ifneq "$$($1_$2_HS_SRCS)" "" --- "$$($1_$2_HC_MK_DEPEND)" -M \ --- $$($1_$2_$$(firstword $$($1_$2_WAYS))_MOST_DIR_HC_OPTS) \ --- $$($1_$2_MKDEPENDHS_FLAGS) \ --- $$($1_$2_HS_SRCS) --- endif --- echo "$1_$2_depfile_haskell_EXISTS = YES" >> $$@.tmp --- ifneq "$$($1_$2_SLASH_MODS)" "" --- for dir in $$(sort $$(foreach mod,$$($1_$2_SLASH_MODS),$1/$2/build/$$(dir $$(mod)))); do \ --- if test ! -d $$$$dir; then mkdir -p $$$$dir; fi \ --- done --- endif - -- TODO: double-check that ignoring $1_$2_HS_SRC_DIRS is safe +-- Options CONF_HC_OPTS and buildPackageDeps :: Package -> TodoItem -> Rules () buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist @@ -229,6 +229,8 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = return $ path ++ "//" ++ start ++ end run (Ghc stage) $ mconcat [ arg ["-M"] + , wayHcOpts vanilla -- TODO: is this needed? shall we run GHC -M multiple times? + , splitArgs $ argOption SrcHcOpts , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] , arg [unwords src] ] From git at git.haskell.org Thu Oct 26 23:17:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix postProcessPackageData. (bf9edba) Message-ID: <20171026231713.227883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf9edba4364ffc59eb13b6501c11560b71b6e620/ghc >--------------------------------------------------------------- commit bf9edba4364ffc59eb13b6501c11560b71b6e620 Author: Andrey Mokhov Date: Tue Dec 30 17:32:37 2014 +0000 Fix postProcessPackageData. >--------------------------------------------------------------- bf9edba4364ffc59eb13b6501c11560b71b6e620 src/Util.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index b8a38f4..846f547 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -19,8 +19,12 @@ replaceEq from = replaceIf (== from) -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' --- 2) Replace '/' and '\' with '_' +-- 2) Replace '/' and '\' with '_' before '=' postProcessPackageData :: FilePath -> Action () postProcessPackageData file = do pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map (replaceIf isSlash '_') pkgData + length pkgData `seq` writeFileLines file $ map processLine pkgData + where + processLine line = replaceIf isSlash '_' prefix ++ suffix + where + (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:17:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for hs-boot files. (6344510) Message-ID: <20171026231713.27C443A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6344510f3cda3097bf77d62a021e70049407c9ac/ghc >--------------------------------------------------------------- commit 6344510f3cda3097bf77d62a021e70049407c9ac Author: Andrey Mokhov Date: Fri Aug 7 22:33:20 2015 +0100 Add support for hs-boot files. >--------------------------------------------------------------- 6344510f3cda3097bf77d62a021e70049407c9ac src/Rules/Compile.hs | 32 +++++++++++++++++++++++++------- src/Rules/Library.hs | 7 +++---- 2 files changed, 28 insertions(+), 11 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 223f9b2..35c9755 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -10,7 +10,6 @@ import Oracles.DependencyList import Settings.TargetDirectory import Rules.Actions import Rules.Resources -import Data.Maybe compilePackage :: Resources -> StagePackageTarget -> Rules () compilePackage _ target = do @@ -21,14 +20,16 @@ compilePackage _ target = do cDepsFile = buildPath -/- "c.deps" hDepsFile = buildPath -/- "haskell.deps" - matchBuildResult buildPath "hi" ?> \hi -> do - let way = fromJust . detectWay $ hi -- fromJust is safe - need [hi -<.> osuf way] + matchBuildResult buildPath "hi" ?> \hi -> + need [ hi -<.> osuf (detectWay hi) ] + + matchBuildResult buildPath "hi-boot" ?> \hiboot -> + need [ hiboot -<.> obootsuf (detectWay hiboot) ] matchBuildResult buildPath "o" ?> \obj -> do - let way = fromJust . detectWay $ obj -- fromJust is safe - vanillaObj = takeFileName obj -<.> "o" - cDeps <- dependencyList cDepsFile vanillaObj + let way = detectWay obj + cObj = takeFileName obj -<.> "o" + cDeps <- dependencyList cDepsFile cObj hDeps <- dependencyList hDepsFile obj let hSrcDeps = filter ("//*hs" ?==) hDeps @@ -43,3 +44,20 @@ compilePackage _ target = do if null cDeps then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] else build $ fullTarget target cDeps (Gcc stage) [obj] + + matchBuildResult buildPath "o-boot" ?> \obj -> do + let way = detectWay obj + hDeps <- dependencyList hDepsFile obj + let hSrcDeps = filter ("//*hs-boot" ?==) hDeps + + when (null hDeps) $ + putError $ "Cannot determine sources for '" ++ obj ++ "'." + + need hDeps + build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] + +-- TODO: add support for -dyno +-- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot +-- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ +-- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno +-- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index fe0c72d..8fd9b0b 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -14,7 +14,6 @@ import Settings.TargetDirectory import Rules.Actions import Rules.Resources import Data.List -import Data.Maybe buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () buildPackageLibrary _ target = do @@ -29,7 +28,7 @@ buildPackageLibrary _ target = do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules - let way = fromJust . detectWay $ a -- fromJust is safe + let way = detectWay a hSrcs = map (replaceEq '.' '/') modules cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] @@ -54,11 +53,11 @@ buildPackageLibrary _ target = do -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. - priority 2 $ (buildPath -/- "HS*.o") %> \o -> do + priority 2 $ (buildPath -/- "HS*.o") %> \obj -> do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules let hSrcs = map (replaceEq '.' '/') modules cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] need $ cObjs ++ hObjs - build $ fullTarget target (cObjs ++ hObjs) Ld [o] + build $ fullTarget target (cObjs ++ hObjs) Ld [obj] From git at git.haskell.org Thu Oct 26 23:17:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add supports-package-key to configuration files. (96dec4a) Message-ID: <20171026231716.EC0563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/96dec4ae3f1dc8dde6647ecc87a62b87a24589ee/ghc >--------------------------------------------------------------- commit 96dec4ae3f1dc8dde6647ecc87a62b87a24589ee Author: Andrey Mokhov Date: Tue Dec 30 19:34:26 2014 +0000 Add supports-package-key to configuration files. >--------------------------------------------------------------- 96dec4ae3f1dc8dde6647ecc87a62b87a24589ee cfg/default.config.in | 1 + 1 file changed, 1 insertion(+) diff --git a/cfg/default.config.in b/cfg/default.config.in index 1a28981..50c3937 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -30,6 +30,7 @@ gcc-lt-46 = @GccLT46@ lax-dependencies = NO dynamic-ghc-programs = NO +supports-package-key = @SUPPORTS_PACKAGE_KEY@ # Information about host and target systems: #=========================================== From git at git.haskell.org Thu Oct 26 23:17:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to using one dependency file for all objects. (4914709) Message-ID: <20171026231721.156C53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4914709cd864e4f28be22ea9e12d60b8f5945ffc/ghc >--------------------------------------------------------------- commit 4914709cd864e4f28be22ea9e12d60b8f5945ffc Author: Andrey Mokhov Date: Mon Aug 10 01:35:55 2015 +0100 Switch to using one dependency file for all objects. >--------------------------------------------------------------- 4914709cd864e4f28be22ea9e12d60b8f5945ffc src/Oracles/Dependencies.hs | 49 +++++++++++++++++++++++++++++++++++++++++++ src/Oracles/DependencyList.hs | 40 ----------------------------------- src/Rules/Dependencies.hs | 30 ++++++++++++++------------ 3 files changed, 66 insertions(+), 53 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs new file mode 100644 index 0000000..c301547 --- /dev/null +++ b/src/Oracles/Dependencies.hs @@ -0,0 +1,49 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} + +module Oracles.Dependencies ( + dependencies, + dependenciesOracle + ) where + +import Base +import Util +import Data.List +import Data.Function +import qualified Data.HashMap.Strict as Map +import Control.Applicative + +newtype DependenciesKey = DependenciesKey (FilePath, FilePath) + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +-- dependencies path obj is an action that looks up dependencies of an object +-- file in a generated dependecy file 'path/.dependencies'. +-- If the dependencies cannot be determined, an appropriate error is raised. +-- Otherwise, a pair (source, depFiles) is returned, such that obj can be +-- produced by compiling 'source'; the latter can also depend on a number of +-- other dependencies listed in depFiles. +dependencies :: FilePath -> FilePath -> Action (FilePath, [FilePath]) +dependencies path obj = do + let depFile = path -/- ".dependencies" + res1 <- askOracle $ DependenciesKey (depFile, obj) + -- if no dependencies found attempt to drop the way prefix (for *.c sources) + res2 <- case res1 of + Nothing -> askOracle $ DependenciesKey (depFile, obj -<.> "o") + _ -> return res1 + case res2 of + Nothing -> putError $ "No dependencies found for '" ++ obj ++ "'." + Just [] -> putError $ "Empty dependency list for '" ++ obj ++ "'." + Just (src:depFiles) -> return (src, depFiles) + +-- Oracle for 'path/dist/.dependencies' files +dependenciesOracle :: Rules () +dependenciesOracle = do + deps <- newCache $ \file -> do + putOracle $ "Reading dependencies from " ++ file ++ "..." + contents <- parseMakefile <$> readFile' file + return . Map.fromList . map (bimap unifyPath (map unifyPath)) + . map (bimap head concat . unzip) + . groupBy ((==) `on` fst) + . sortBy (compare `on` fst) $ contents + + addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file + return () diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs deleted file mode 100644 index e571f7b..0000000 --- a/src/Oracles/DependencyList.hs +++ /dev/null @@ -1,40 +0,0 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} - -module Oracles.DependencyList ( - dependencyList, - dependencyListOracle - ) where - -import Base -import Util -import Data.List -import Data.Maybe -import Data.Function -import qualified Data.HashMap.Strict as Map -import Control.Applicative - -newtype DependencyListKey = DependencyListKey (FilePath, FilePath) - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) - --- dependencyList depFile objFile is an action that looks up dependencies of an --- object file (objFile) in a generated dependecy file (depFile). -dependencyList :: FilePath -> FilePath -> Action [FilePath] -dependencyList depFile objFile = do - res <- askOracle $ DependencyListKey (depFile, objFile) - return . fromMaybe [] $ res - --- Oracle for 'path/dist/*.deps' files -dependencyListOracle :: Rules () -dependencyListOracle = do - deps <- newCache $ \file -> do - need [file] - putOracle $ "Reading dependencies from " ++ file ++ "..." - contents <- parseMakefile <$> (liftIO $ readFile file) - return . Map.fromList - . map (bimap unifyPath (map unifyPath)) - . map (bimap head concat . unzip) - . groupBy ((==) `on` fst) - . sortBy (compare `on` fst) $ contents - addOracle $ \(DependencyListKey (file, obj)) -> - Map.lookup (unifyPath obj) <$> deps (unifyPath file) - return () diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index ea47241..90c764f 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -19,20 +19,24 @@ buildPackageDependencies _ target = path = targetPath stage pkg buildPath = path -/- "build" dropBuild = (pkgPath pkg ++) . drop (length buildPath) + hDepFile = buildPath -/- ".hs-dependencies" in do - (buildPath "*.c.deps") %> \depFile -> do - let srcFile = dropBuild . dropExtension $ depFile + (buildPath "*.c.deps") %> \file -> do + let srcFile = dropBuild . dropExtension $ file need [srcFile] - build $ fullTarget target [srcFile] (GccM stage) [depFile] + build $ fullTarget target (GccM stage) [srcFile] [file] - (buildPath -/- "c.deps") %> \file -> do - srcs <- pkgDataList $ CSrcs path - let depFiles = [ buildPath -/- src <.> "deps" | src <- srcs ] - need depFiles - deps <- mapM readFile' depFiles - writeFileChanged file (concat deps) - - (buildPath -/- "haskell.deps") %> \file -> do - srcs <- interpret target getHsSources + hDepFile %> \file -> do + srcs <- interpret target getPackageSources need srcs - build $ fullTarget target srcs (GhcM stage) [file] + build $ fullTarget target (GhcM stage) srcs [file] + liftIO $ removeFiles "." [hDepFile <.> "bak"] + + (buildPath -/- ".dependencies") %> \file -> do + cSrcs <- pkgDataList $ CSrcs path + let cDepFiles = [ buildPath -/- src <.> "deps" | src <- cSrcs ] + need $ hDepFile : cDepFiles -- need all for more parallelism + cDeps <- fmap concat $ mapM readFile' cDepFiles + hDeps <- readFile' hDepFile + writeFileChanged file $ cDeps ++ hDeps + From git at git.haskell.org Thu Oct 26 23:17:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve zero build performance. (d2910ba) Message-ID: <20171026231717.0A79B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2910ba1570a2b8a21d83b7ace7d3437c8311b22/ghc >--------------------------------------------------------------- commit d2910ba1570a2b8a21d83b7ace7d3437c8311b22 Author: Andrey Mokhov Date: Sat Aug 8 01:03:26 2015 +0100 Improve zero build performance. >--------------------------------------------------------------- d2910ba1570a2b8a21d83b7ace7d3437c8311b22 src/Oracles/DependencyList.hs | 2 +- src/Rules/Compile.hs | 52 ++++++++++++++++++------------------------- src/Rules/Library.hs | 10 ++++++--- src/Settings/Builders/Ghc.hs | 5 +++++ 4 files changed, 35 insertions(+), 34 deletions(-) diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs index 900b48e..e571f7b 100644 --- a/src/Oracles/DependencyList.hs +++ b/src/Oracles/DependencyList.hs @@ -28,7 +28,7 @@ dependencyListOracle :: Rules () dependencyListOracle = do deps <- newCache $ \file -> do need [file] - putOracle $ "Reading " ++ file ++ "..." + putOracle $ "Reading dependencies from " ++ file ++ "..." contents <- parseMakefile <$> (liftIO $ readFile file) return . Map.fromList . map (bimap unifyPath (map unifyPath)) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 35c9755..66ab73b 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -27,37 +27,29 @@ compilePackage _ target = do need [ hiboot -<.> obootsuf (detectWay hiboot) ] matchBuildResult buildPath "o" ?> \obj -> do - let way = detectWay obj - cObj = takeFileName obj -<.> "o" - cDeps <- dependencyList cDepsFile cObj - hDeps <- dependencyList hDepsFile obj - let hSrcDeps = filter ("//*hs" ?==) hDeps - - when (null cDeps && null hDeps) $ - putError $ "Cannot determine sources for '" ++ obj ++ "'." - - when (not (null cDeps) && not (null hDeps)) $ - putError $ "Both .c and .hs sources found for '" ++ obj ++ "'." - - need $ hDeps ++ cDeps - - if null cDeps - then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] - else build $ fullTarget target cDeps (Gcc stage) [obj] + cDeps <- dependencyList cDepsFile (takeFileName obj -<.> "o") + if not (null cDeps) + then do -- obj is produced from a C source file + need cDeps + build $ fullTarget target cDeps (Gcc stage) [obj] + else do -- obj is produced from a Haskell source file + hDeps <- dependencyList hDepsFile obj + when (null hDeps) . putError $ + "No dependencies found for '" ++ obj ++ "'." + let way = detectWay obj + hSrc = head hDeps + unless ("//*hs" ?== hSrc) . putError $ + "No Haskell source file found for '" ++ obj ++ "'." + need hDeps + build $ fullTargetWithWay target [hSrc] (Ghc stage) way [obj] matchBuildResult buildPath "o-boot" ?> \obj -> do - let way = detectWay obj hDeps <- dependencyList hDepsFile obj - let hSrcDeps = filter ("//*hs-boot" ?==) hDeps - - when (null hDeps) $ - putError $ "Cannot determine sources for '" ++ obj ++ "'." - + when (null hDeps) . putError $ + "No dependencies found for '" ++ obj ++ "'." + let way = detectWay obj + hSrc = head hDeps + unless ("//*.hs-boot" ?== hSrc) . putError $ + "No Haskell source file found for '" ++ obj ++ "'." need hDeps - build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] - --- TODO: add support for -dyno --- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot --- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ --- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno --- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) + build $ fullTargetWithWay target [hSrc] (Ghc stage) way [obj] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 8fd9b0b..d9ce835 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -14,6 +14,7 @@ import Settings.TargetDirectory import Rules.Actions import Rules.Resources import Data.List +import qualified System.Directory as IO buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () buildPackageLibrary _ target = do @@ -33,13 +34,16 @@ buildPackageLibrary _ target = do cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] - need $ cObjs ++ hObjs -- this will create split objects if required + -- This will create split objects if required (we don't track them) + need $ cObjs ++ hObjs split <- interpret target splitObjects splitObjs <- if split then fmap concat $ forM hSrcs $ \src -> do - let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" - fmap (map unifyPath) $ getDirectoryFiles "" [files] + let splitPath = buildPath -/- src ++ "_" ++ osuf way ++ "_split" + contents <- liftIO $ IO.getDirectoryContents splitPath + return . map (splitPath -/-) + . filter (not . all (== '.')) $ contents else return [] build $ fullTarget target (cObjs ++ hObjs ++ splitObjs) Ar [a] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 9c120bc..8ece818 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -11,6 +11,11 @@ import Oracles.PackageData import Settings.Util import Settings.Ways +-- TODO: add support for -dyno +-- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot +-- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ +-- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno +-- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) -- TODO: check code duplication ghcArgs :: Args ghcArgs = stagedBuilder Ghc ? do From git at git.haskell.org Thu Oct 26 23:17:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement more arguments for ghc -M. (21bfb81) Message-ID: <20171026231721.16A8E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21bfb816a7be0bcd0ef72d562001d5948998565a/ghc >--------------------------------------------------------------- commit 21bfb816a7be0bcd0ef72d562001d5948998565a Author: Andrey Mokhov Date: Tue Dec 30 19:35:13 2014 +0000 Implement more arguments for ghc -M. >--------------------------------------------------------------- 21bfb816a7be0bcd0ef72d562001d5948998565a src/Oracles.hs | 24 +++++++++++++----------- src/Package.hs | 28 ++++++++++++++++++++++------ 2 files changed, 35 insertions(+), 17 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index ff4bd95..9b63c4f 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -136,7 +136,7 @@ argOption opt = do data Flag = LaxDeps | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs | GccIsClang | GccLt46 | CrossCompiling | Validating | PlatformSupportsSharedLibs - | WindowsHost + | WindowsHost | SupportsPackageKey test :: Flag -> Action Bool test GhcWithInterpreter = do @@ -161,12 +161,13 @@ test WindowsHost = do test flag = do (key, defaultValue) <- return $ case flag of - LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file - DynamicGhcPrograms -> ("dynamic-ghc-programs", False) - GccIsClang -> ("gcc-is-clang" , False) - GccLt46 -> ("gcc-lt-46" , False) - CrossCompiling -> ("cross-compiling" , False) - Validating -> ("validating" , False) + LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file + DynamicGhcPrograms -> ("dynamic-ghc-programs" , False) + GccIsClang -> ("gcc-is-clang" , False) + GccLt46 -> ("gcc-lt-46" , False) + CrossCompiling -> ("cross-compiling" , False) + Validating -> ("validating" , False) + SupportsPackageKey -> ("supports-package-key" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ do putLoud $ "\nFlag '" -- TODO: Give the warning *only once* per key @@ -264,13 +265,14 @@ packagaDataOptionWithDefault file key defaultAction = do Just value -> return value Nothing -> defaultAction -data PackageDataKey = Modules | SrcDirs +data PackageDataKey = Modules | SrcDirs | PackageKey packagaDataOption :: FilePath -> PackageDataKey -> Action String packagaDataOption file key = do - let keyName = replaceIf isSlash '_' $ takeDirectory file ++ case key of - Modules -> "_MODULES" - SrcDirs -> "_HS_SRC_DIRS" + let keyName = replaceIf isSlash '_' $ takeDirectory file ++ "_" ++ case key of + Modules -> "MODULES" + SrcDirs -> "HS_SRC_DIRS" -- TODO: add "." as a default? + PackageKey -> "PACKAGE_KEY" packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." diff --git a/src/Package.hs b/src/Package.hs index 9e60a24..ba77bdf 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -161,7 +161,6 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = , arg [path dist "inplace-pkg-config"] ] --- "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs -- $1_$2_$3_MOST_DIR_HC_OPTS = \ -- $$($1_$2_$3_MOST_HC_OPTS) \ @@ -186,6 +185,8 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- done -- endif +-- "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs + -- $1_$2_$3_MOST_HC_OPTS = \ -- $$(WAY_$3_HC_OPTS) \ -- $$(CONF_HC_OPTS) \ @@ -213,24 +214,39 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) --- TODO: double-check that ignoring $1_$2_HS_SRC_DIRS is safe --- Options CONF_HC_OPTS and +-- TODO: double-check that ignoring SrcDirs ($1_$2_HS_SRC_DIRS) is safe +-- TODO: add $1_HC_OPTS +-- TODO: check that the package is not a program ($1_$2_PROG == "") +-- TODO: handle empty $1_PACKAGE +-- Option CONF_HC_OPTS is skipped buildPackageDeps :: Package -> TodoItem -> Rules () buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist in (buildDir "build" name <.> "m") %> \out -> do - let pkgData = buildDir "package-data.mk" - autogen = dist "build" "autogen" - mods <- words <$> packagaDataOption pkgData Modules + let pkgData = buildDir "package-data.mk" + autogen = dist "build" "autogen" + mods <- words <$> packagaDataOption pkgData Modules + srcDirs <- words <$> packagaDataOption pkgData SrcDirs src <- getDirectoryFiles "" $ do start <- map (replaceEq '.' '/') mods end <- [".hs", ".lhs"] return $ path ++ "//" ++ start ++ end + packageKey <- packagaDataOption pkgData PackageKey run (Ghc stage) $ mconcat [ arg ["-M"] , wayHcOpts vanilla -- TODO: is this needed? shall we run GHC -M multiple times? , splitArgs $ argOption SrcHcOpts + , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] + , when (not SupportsPackageKey && stage == Stage0) $ arg ["-package-name"] + , when ( SupportsPackageKey || stage /= Stage0) $ arg ["-this-package-key"] + , arg [packageKey] + , arg ["-hide-all-packages"] + , arg $ map (\d -> "-i" ++ path ++ "/" ++ d) srcDirs + , arg $ do + prefix <- ["-i", "-I"] + suffix <- ["build", "build/autogen"] + return $ prefix ++ path dist suffix , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] , arg [unwords src] ] From git at git.haskell.org Thu Oct 26 23:17:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace isSlash with standard isPathSeparator. (212e91f) Message-ID: <20171026231725.350A43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/212e91f1a18f71e467ca68e929294b943c2cf171/ghc >--------------------------------------------------------------- commit 212e91f1a18f71e467ca68e929294b943c2cf171 Author: Andrey Mokhov Date: Wed Dec 31 03:50:59 2014 +0000 Replace isSlash with standard isPathSeparator. >--------------------------------------------------------------- 212e91f1a18f71e467ca68e929294b943c2cf171 src/Util.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index 846f547..af23f27 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,5 @@ module Util ( module Data.Char, - isSlash, replaceIf, replaceEq, postProcessPackageData ) where @@ -8,9 +7,6 @@ module Util ( import Base import Data.Char -isSlash :: Char -> Bool -isSlash = (`elem` ['/', '\\']) - replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -25,6 +21,6 @@ postProcessPackageData file = do pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) length pkgData `seq` writeFileLines file $ map processLine pkgData where - processLine line = replaceIf isSlash '_' prefix ++ suffix + processLine line = replaceIf isPathSeparator '_' prefix ++ suffix where (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:17:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code, do renaming. (d41d5a7) Message-ID: <20171026231725.358173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d41d5a7e0efcad961a2ed77e1aecc10102834b89/ghc >--------------------------------------------------------------- commit d41d5a7e0efcad961a2ed77e1aecc10102834b89 Author: Andrey Mokhov Date: Mon Aug 10 01:38:57 2015 +0100 Clean up code, do renaming. >--------------------------------------------------------------- d41d5a7e0efcad961a2ed77e1aecc10102834b89 src/Expression.hs | 31 +++++++++++----------- src/Rules/Compile.hs | 37 +++++++++----------------- src/Rules/Data.hs | 4 +-- src/Rules/Library.hs | 4 +-- src/Rules/Oracles.hs | 14 +++++----- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Gcc.hs | 8 +++--- src/Settings/Builders/Ghc.hs | 9 ++++--- src/Settings/Builders/Ld.hs | 2 +- src/Target.hs | 63 ++++++++++++++++++++++---------------------- 10 files changed, 81 insertions(+), 93 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d41d5a7e0efcad961a2ed77e1aecc10102834b89 From git at git.haskell.org Thu Oct 26 23:17:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename getHsSources to getPackageSources. (810b1e2) Message-ID: <20171026231729.2FACF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/810b1e224cc0609b74ffae8d3772eb207e256879/ghc >--------------------------------------------------------------- commit 810b1e224cc0609b74ffae8d3772eb207e256879 Author: Andrey Mokhov Date: Mon Aug 10 01:39:47 2015 +0100 Rename getHsSources to getPackageSources. >--------------------------------------------------------------- 810b1e224cc0609b74ffae8d3772eb207e256879 src/Settings/Util.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 13e5be0..675ba1b 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -5,7 +5,7 @@ module Settings.Util ( getFlag, getSetting, getSettingList, getPkgData, getPkgDataList, getPackagePath, getTargetPath, getTargetDirectory, - getHsSources, + getPackageSources, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -73,8 +73,8 @@ getTargetDirectory :: Expr FilePath getTargetDirectory = liftM2 targetDirectory getStage getPackage -- Find all Haskell source files for the current target -getHsSources :: Expr [FilePath] -getHsSources = do +getPackageSources :: Expr [FilePath] +getPackageSources = do path <- getTargetPath pkgPath <- getPackagePath srcDirs <- getPkgDataList SrcDirs From git at git.haskell.org Thu Oct 26 23:17:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add replaceSeparators to Util.hs. (d043ef5) Message-ID: <20171026231729.29C3E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d043ef595a7ee877d8c9659b27e592d361a110c6/ghc >--------------------------------------------------------------- commit d043ef595a7ee877d8c9659b27e592d361a110c6 Author: Andrey Mokhov Date: Wed Dec 31 03:59:10 2014 +0000 Add replaceSeparators to Util.hs. >--------------------------------------------------------------- d043ef595a7ee877d8c9659b27e592d361a110c6 src/Util.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index af23f27..68ed2e5 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,6 @@ module Util ( module Data.Char, - replaceIf, replaceEq, + replaceIf, replaceEq, replaceSeparators, postProcessPackageData ) where @@ -13,6 +13,9 @@ replaceIf p to = map (\from -> if p from then to else from) replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) +replaceSeparators :: String -> String +replaceSeparators = replaceIf isPathSeparator + -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- 2) Replace '/' and '\' with '_' before '=' @@ -21,6 +24,6 @@ postProcessPackageData file = do pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) length pkgData `seq` writeFileLines file $ map processLine pkgData where - processLine line = replaceIf isPathSeparator '_' prefix ++ suffix + processLine line = replaceSeparators '_' prefix ++ suffix where (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:17:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix replaceSeparators in Util.hs. (34696c1) Message-ID: <20171026231732.9F9E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34696c113fedaa2081b179dd4591d6eec8a510e4/ghc >--------------------------------------------------------------- commit 34696c113fedaa2081b179dd4591d6eec8a510e4 Author: Andrey Mokhov Date: Wed Dec 31 04:00:18 2014 +0000 Fix replaceSeparators in Util.hs. >--------------------------------------------------------------- 34696c113fedaa2081b179dd4591d6eec8a510e4 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 68ed2e5..d7e98bd 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -13,7 +13,7 @@ replaceIf p to = map (\from -> if p from then to else from) replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) -replaceSeparators :: String -> String +replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: From git at git.haskell.org Thu Oct 26 23:17:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise ArgsHash oracle improving zero build time. (486a3e5) Message-ID: <20171026231732.B1EC33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/486a3e58a9c323f651f733508492efe9a3e768d0/ghc >--------------------------------------------------------------- commit 486a3e58a9c323f651f733508492efe9a3e768d0 Author: Andrey Mokhov Date: Mon Aug 10 01:40:17 2015 +0100 Optimise ArgsHash oracle improving zero build time. >--------------------------------------------------------------- 486a3e58a9c323f651f733508492efe9a3e768d0 src/Oracles/ArgsHash.hs | 13 ++++++++----- src/Rules/Actions.hs | 4 +--- 2 files changed, 9 insertions(+), 8 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index ca0aa6c..f67f8c4 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -1,23 +1,26 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.ArgsHash ( - askArgsHash, argsHashOracle + checkArgsHash, argsHashOracle ) where import Base +import Target import Expression import Settings.Args import Control.Applicative -newtype ArgsHashKey = ArgsHashKey FullTarget - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +newtype ArgsHashKey = ArgsHashKey Target + deriving (Show, Eq, Typeable, Binary, Hashable, NFData) -- This is an action that given a full target determines the corresponding -- argument list and computes its hash. The resulting value is tracked in a -- Shake oracle, hence initiating rebuilts when the hash is changed (a hash -- change indicates changes in the build system). -askArgsHash :: FullTarget -> Action Int -askArgsHash = askOracle . ArgsHashKey +checkArgsHash :: FullTarget -> Action () +checkArgsHash target = do + tmp <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int + return () -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 062a5d5..2f9ebc6 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -19,13 +19,11 @@ import Settings.Builders.Ar buildWithResources :: [(Resource, Int)] -> FullTarget -> Action () buildWithResources rs target = do let builder = Target.builder target - deps = Target.dependencies target needBuilder builder - -- need deps -- TODO: think if needs could be done here path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed - argsHash <- askArgsHash target + checkArgsHash target withResources rs $ do putBuild $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" From git at git.haskell.org Thu Oct 26 23:17:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Complete first working version of buildPackageDeps rule. (d869302) Message-ID: <20171026231736.CB42E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d869302fcad9a124aa65c6075114a6f1f9c7c61d/ghc >--------------------------------------------------------------- commit d869302fcad9a124aa65c6075114a6f1f9c7c61d Author: Andrey Mokhov Date: Wed Dec 31 04:43:53 2014 +0000 Complete first working version of buildPackageDeps rule. >--------------------------------------------------------------- d869302fcad9a124aa65c6075114a6f1f9c7c61d src/Oracles.hs | 18 +++++++++++------ src/Package.hs | 62 ++++++++++++++++++++++++++++++++++------------------------ 2 files changed, 48 insertions(+), 32 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 9b63c4f..4f4cd78 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -265,16 +265,22 @@ packagaDataOptionWithDefault file key defaultAction = do Just value -> return value Nothing -> defaultAction -data PackageDataKey = Modules | SrcDirs | PackageKey +data PackageDataKey = Modules | SrcDirs | PackageKey | IncludeDirs | Deps | DepKeys + deriving Show packagaDataOption :: FilePath -> PackageDataKey -> Action String packagaDataOption file key = do - let keyName = replaceIf isSlash '_' $ takeDirectory file ++ "_" ++ case key of - Modules -> "MODULES" - SrcDirs -> "HS_SRC_DIRS" -- TODO: add "." as a default? - PackageKey -> "PACKAGE_KEY" - packagaDataOptionWithDefault file keyName $ + let (keyName, ifEmpty) = case key of + Modules -> ("MODULES" , "" ) + SrcDirs -> ("HS_SRC_DIRS" , ".") + PackageKey -> ("PACKAGE_KEY" , "" ) + IncludeDirs -> ("INCLUDE_DIRS", ".") + Deps -> ("DEPS" , "" ) + DepKeys -> ("DEP_KEYS" , "" ) + keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName + res <- packagaDataOptionWithDefault file keyFullName $ error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." + return $ if res == "" then ifEmpty else res oracleRules :: Rules () oracleRules = do diff --git a/src/Package.hs b/src/Package.hs index ba77bdf..98558e9 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -214,42 +214,52 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) --- TODO: double-check that ignoring SrcDirs ($1_$2_HS_SRC_DIRS) is safe +-- TODO: make sure SrcDirs ($1_$2_HS_SRC_DIRS) is not empty ('.' by default) -- TODO: add $1_HC_OPTS -- TODO: check that the package is not a program ($1_$2_PROG == "") --- TODO: handle empty $1_PACKAGE +-- TODO: handle empty $1_PACKAGE (can it be empty?) +-- TODO: $1_$2_INCLUDE appears to be not set. Safe to skip? -- Option CONF_HC_OPTS is skipped buildPackageDeps :: Package -> TodoItem -> Rules () buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist in (buildDir "build" name <.> "m") %> \out -> do - let pkgData = buildDir "package-data.mk" - autogen = dist "build" "autogen" - mods <- words <$> packagaDataOption pkgData Modules - srcDirs <- words <$> packagaDataOption pkgData SrcDirs - src <- getDirectoryFiles "" $ do - start <- map (replaceEq '.' '/') mods - end <- [".hs", ".lhs"] - return $ path ++ "//" ++ start ++ end + let pkgData = buildDir "package-data.mk" + usePackageKey <- SupportsPackageKey || stage /= Stage0 -- TODO: check reasoning (distdir-way-opts) + [mods, srcDirs, includeDirs, deps, depKeys] <- + mapM ((fmap words) . (packagaDataOption pkgData)) + [Modules, SrcDirs, IncludeDirs, Deps, DepKeys] + srcs <- getDirectoryFiles "" $ do + dir <- srcDirs + modPath <- map (replaceEq '.' pathSeparator) mods + extension <- ["hs", "lhs"] + return $ path dir modPath <.> extension packageKey <- packagaDataOption pkgData PackageKey run (Ghc stage) $ mconcat - [ arg ["-M"] - , wayHcOpts vanilla -- TODO: is this needed? shall we run GHC -M multiple times? - , splitArgs $ argOption SrcHcOpts - , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] - , when (not SupportsPackageKey && stage == Stage0) $ arg ["-package-name"] - , when ( SupportsPackageKey || stage /= Stage0) $ arg ["-this-package-key"] - , arg [packageKey] - , arg ["-hide-all-packages"] - , arg $ map (\d -> "-i" ++ path ++ "/" ++ d) srcDirs - , arg $ do - prefix <- ["-i", "-I"] - suffix <- ["build", "build/autogen"] - return $ prefix ++ path dist suffix - , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] - , arg [unwords src] - ] + [ arg ["-M"] + , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? + , splitArgs $ argOption SrcHcOpts + , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] + , arg [if usePackageKey then "-this-package-key" else "-package-name"] + , arg [packageKey] -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg ["-hide-all-packages"] + , arg ["-i"] -- resets the search path to nothing; TODO: check if really needed + , arg $ map (\d -> "-i" ++ path d) srcDirs + , arg $ do + prefix <- ["-i", "-I"] -- 'import' and '#include' search paths + suffix <- ["build", "build/autogen"] + return $ prefix ++ buildDir suffix + , arg $ map (\d -> "-I" ++ path d) $ filter isRelative includeDirs + , arg $ map (\d -> "-I" ++ d) $ filter isAbsolute includeDirs + , arg ["-optP-include"] + , arg ["-optP" ++ buildDir "build/autogen/cabal_macros.h"] + , if usePackageKey + then arg $ concatMap (\d -> ["-package-key", d]) depKeys + else arg $ concatMap (\d -> ["-package" , d]) deps + , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] + , arg $ map normalise srcs + ] -- $1_$2_MKDEPENDHS_FLAGS = -dep-makefile $$($1_$2_depfile_haskell).tmp $$(foreach way,$$($1_$2_WAYS),-dep-suffix "$$(-- patsubst %o,%,$$($$(way)_osuf))") -- $1_$2_MKDEPENDHS_FLAGS += -include-pkg-deps From git at git.haskell.org Thu Oct 26 23:17:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix performance drop due to improper use of removeFiles. (18a779b) Message-ID: <20171026231736.E753D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/18a779b20d3084cc681ce28ff88ca6b97d45903f/ghc >--------------------------------------------------------------- commit 18a779b20d3084cc681ce28ff88ca6b97d45903f Author: Andrey Mokhov Date: Tue Aug 11 00:16:38 2015 +0100 Fix performance drop due to improper use of removeFiles. >--------------------------------------------------------------- 18a779b20d3084cc681ce28ff88ca6b97d45903f src/Rules/Dependencies.hs | 3 ++- src/Rules/Library.hs | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 90c764f..8fb890e 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -11,6 +11,7 @@ import Settings.Util import Settings.TargetDirectory import Rules.Actions import Rules.Resources +import qualified System.Directory as IO buildPackageDependencies :: Resources -> StagePackageTarget -> Rules () buildPackageDependencies _ target = @@ -30,7 +31,7 @@ buildPackageDependencies _ target = srcs <- interpret target getPackageSources need srcs build $ fullTarget target (GhcM stage) srcs [file] - liftIO $ removeFiles "." [hDepFile <.> "bak"] + liftIO . IO.removeFile $ file <.> "bak" (buildPath -/- ".dependencies") %> \file -> do cSrcs <- pkgDataList $ CSrcs path diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 87a37ca..4619651 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -25,7 +25,7 @@ buildPackageLibrary _ target = do -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do - liftIO $ removeFiles "." [a] + liftIO $ IO.removeFile a cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules From git at git.haskell.org Thu Oct 26 23:17:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split Oracles.hs module into logical parts. (a2c0e5d) Message-ID: <20171026231740.D74293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123/ghc >--------------------------------------------------------------- commit a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123 Author: Andrey Mokhov Date: Thu Jan 1 22:26:03 2015 +0000 Split Oracles.hs module into logical parts. >--------------------------------------------------------------- a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123 src/Oracles/Base.hs | 26 ++++++++++++ src/Oracles/Builder.hs | 93 ++++++++++++++++++++++++++++++++++++++++ src/Oracles/Flag.hs | 103 +++++++++++++++++++++++++++++++++++++++++++++ src/Oracles/Option.hs | 57 +++++++++++++++++++++++++ src/Oracles/PackageData.hs | 38 +++++++++++++++++ 5 files changed, 317 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 a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123 From git at git.haskell.org Thu Oct 26 23:17:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (096f602) Message-ID: <20171026231740.EF8E23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/096f6029109bf36ab29f2178942b62fdce884e26/ghc >--------------------------------------------------------------- commit 096f6029109bf36ab29f2178942b62fdce884e26 Author: Andrey Mokhov Date: Tue Aug 11 00:24:24 2015 +0100 Add comments. >--------------------------------------------------------------- 096f6029109bf36ab29f2178942b62fdce884e26 src/Oracles/ArgsHash.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index f67f8c4..422cacd 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -17,6 +17,12 @@ newtype ArgsHashKey = ArgsHashKey Target -- argument list and computes its hash. The resulting value is tracked in a -- Shake oracle, hence initiating rebuilts when the hash is changed (a hash -- change indicates changes in the build system). +-- Note: we replace target sources with ["src"] for performance reasons -- to +-- avoid storing long lists of source files passed to some builders (e.g. Ar) +-- in the Shake database. This optimisation is harmless, because argument list +-- constructors are assumed not to examine target sources, but only append them +-- to argument lists where appropriate. +-- TODO: enforce the above assumption via type trickery? checkArgsHash :: FullTarget -> Action () checkArgsHash target = do tmp <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int From git at git.haskell.org Thu Oct 26 23:17:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports. (c5f7958) Message-ID: <20171026231744.CAEC73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5f79581110633e6aeb8f8bb13bcd6fa3e187f05/ghc >--------------------------------------------------------------- commit c5f79581110633e6aeb8f8bb13bcd6fa3e187f05 Author: Andrey Mokhov Date: Thu Jan 1 22:29:39 2015 +0000 Refactor imports. >--------------------------------------------------------------- c5f79581110633e6aeb8f8bb13bcd6fa3e187f05 src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a0f4303..29c1340 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,9 +12,9 @@ module Base ( filterOut ) where -import Development.Shake hiding ((*>)) +import Development.Shake import Development.Shake.FilePath -import Control.Applicative +import Control.Applicative hiding ((*>)) import Data.Monoid import Data.List From git at git.haskell.org Thu Oct 26 23:17:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move most code into src/Oracles/ submodules. (8228615) Message-ID: <20171026231748.5E8C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82286153d41e61c9e5c06488504e64321993f0df/ghc >--------------------------------------------------------------- commit 82286153d41e61c9e5c06488504e64321993f0df Author: Andrey Mokhov Date: Thu Jan 1 22:31:45 2015 +0000 Move most code into src/Oracles/ submodules. >--------------------------------------------------------------- 82286153d41e61c9e5c06488504e64321993f0df src/Oracles.hs | 284 +++------------------------------------------------------ 1 file changed, 11 insertions(+), 273 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 82286153d41e61c9e5c06488504e64321993f0df From git at git.haskell.org Thu Oct 26 23:17:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add removeFile to Util.hs. (6b0b4ab) Message-ID: <20171026231744.EB3D13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b0b4ab1c3d88df4e67d9ade22f45fcd8369708b/ghc >--------------------------------------------------------------- commit 6b0b4ab1c3d88df4e67d9ade22f45fcd8369708b Author: Andrey Mokhov Date: Tue Aug 11 02:48:11 2015 +0100 Add removeFile to Util.hs. >--------------------------------------------------------------- 6b0b4ab1c3d88df4e67d9ade22f45fcd8369708b src/Rules/Compile.hs | 2 -- src/Rules/Dependencies.hs | 3 +-- src/Rules/Library.hs | 10 +++++----- src/Util.hs | 12 +++++++++++- 4 files changed, 17 insertions(+), 10 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 43659b9..30a77cb 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -17,8 +17,6 @@ compilePackage _ target = do pkg = Target.package target path = targetPath stage pkg buildPath = path -/- "build" - cDepsFile = buildPath -/- "c.deps" - hDepsFile = buildPath -/- "haskell.deps" matchBuildResult buildPath "hi" ?> \hi -> need [ hi -<.> osuf (detectWay hi) ] diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 8fb890e..e63d27d 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -11,7 +11,6 @@ import Settings.Util import Settings.TargetDirectory import Rules.Actions import Rules.Resources -import qualified System.Directory as IO buildPackageDependencies :: Resources -> StagePackageTarget -> Rules () buildPackageDependencies _ target = @@ -31,7 +30,7 @@ buildPackageDependencies _ target = srcs <- interpret target getPackageSources need srcs build $ fullTarget target (GhcM stage) srcs [file] - liftIO . IO.removeFile $ file <.> "bak" + removeFile $ file <.> "bak" (buildPath -/- ".dependencies") %> \file -> do cSrcs <- pkgDataList $ CSrcs path diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 4619651..5956030 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -25,7 +25,7 @@ buildPackageLibrary _ target = do -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do - liftIO $ IO.removeFile a + removeFile a cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules @@ -34,17 +34,17 @@ buildPackageLibrary _ target = do cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] - -- This will create split objects if required (we don't track them) + -- This will create split objects if required (we don't track them + -- explicitly as this would needlessly bloat the Shake database). need $ cObjs ++ hObjs split <- interpret target splitObjects - splitObjs <- if split - then fmap concat $ forM hSrcs $ \src -> do + splitObjs <- if not split then return [] else + fmap concat $ forM hSrcs $ \src -> do let splitPath = buildPath -/- src ++ "_" ++ osuf way ++ "_split" contents <- liftIO $ IO.getDirectoryContents splitPath return . map (splitPath -/-) . filter (not . all (== '.')) $ contents - else return [] build $ fullTarget target Ar (cObjs ++ hObjs ++ splitObjs) [a] diff --git a/src/Util.hs b/src/Util.hs index dd0f2d8..b78592a 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -5,13 +5,16 @@ module Util ( unifyPath, (-/-), chunksOfSize, putColoured, putOracle, putBuild, putSuccess, putError, - bimap, minusOrd, intersectOrd + bimap, minusOrd, intersectOrd, + removeFile ) where import Base import Data.Char +import Control.Monad import System.IO import System.Console.ANSI +import qualified System.Directory as IO replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -100,3 +103,10 @@ intersectOrd cmp = loop LT -> loop xs (y:ys) EQ -> x : loop xs ys GT -> loop (x:xs) ys + +-- Convenient helper function for removing a single file that doesn't +-- necessarily exist. +removeFile :: FilePath -> Action () +removeFile file = do + exists <- liftIO $ IO.doesFileExist file + when exists . liftIO $ IO.removeFile file From git at git.haskell.org Thu Oct 26 23:17:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add trackBuildSystem switch (perhaps, temporarily). (2b2008d) Message-ID: <20171026231748.778233A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2b2008d6048aa691d8ea4f86e89c9ee5c4e2f300/ghc >--------------------------------------------------------------- commit 2b2008d6048aa691d8ea4f86e89c9ee5c4e2f300 Author: Andrey Mokhov Date: Wed Aug 12 01:27:28 2015 +0100 Add trackBuildSystem switch (perhaps, temporarily). >--------------------------------------------------------------- 2b2008d6048aa691d8ea4f86e89c9ee5c4e2f300 src/Rules/Actions.hs | 3 ++- src/Rules/Oracles.hs | 14 ++++++++------ src/Settings/User.hs | 11 +++++++++-- 3 files changed, 19 insertions(+), 9 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 2f9ebc6..9726e2f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -11,6 +11,7 @@ import Oracles.Setting import Oracles.ArgsHash import Settings.Args import Settings.Util +import Settings.User import Settings.Builders.Ar -- Build a given target using an appropriate builder and acquiring necessary @@ -23,7 +24,7 @@ buildWithResources rs target = do path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed - checkArgsHash target + when trackBuildSystem $ checkArgsHash target withResources rs $ do putBuild $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 32938ff..9b6d597 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -9,12 +9,14 @@ import Oracles.PackageData import Oracles.WindowsRoot import Oracles.PackageDeps import Oracles.Dependencies +import Settings.User +import Control.Monad oracleRules :: Rules () oracleRules = do - configOracle -- see Oracles.Base - packageDataOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - dependenciesOracle -- see Oracles.Dependencies - argsHashOracle -- see Oracles.ArgsHash - windowsRootOracle -- see Oracles.WindowsRoot + configOracle -- see Oracles.Base + packageDataOracle -- see Oracles.PackageData + packageDepsOracle -- see Oracles.PackageDeps + dependenciesOracle -- see Oracles.Dependencies + when trackBuildSystem argsHashOracle -- see Oracles.ArgsHash + windowsRootOracle -- see Oracles.WindowsRoot diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 572feb4..8831d65 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,7 +1,7 @@ module Settings.User ( userArgs, userPackages, userWays, userRtsWays, userTargetDirectory, userKnownPackages, integerLibrary, - buildHaddock, validating, ghciWithDebugger, ghcProfiled, + trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, dynamicGhcPrograms, laxDependencies ) where @@ -42,6 +42,14 @@ integerLibrary = integerGmp2 -- * Bool: a plain Boolean flag whose value is known at compile time -- * Action Bool: a flag whose value can depend on the build environment -- * Predicate: a flag depending on the build environment and the current target + +-- Set this to True if you are making any changes in the build system and want +-- appropriate rebuilds to be initiated. Switching this to False speeds things +-- up a little (particularly zero builds). +-- WARNING: changing this setting leads to a complete rebuild. +trackBuildSystem :: Bool +trackBuildSystem = False + validating :: Bool validating = False @@ -59,4 +67,3 @@ laxDependencies = False buildHaddock :: Predicate buildHaddock = return True - From git at git.haskell.org Thu Oct 26 23:17:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change computed configuration flags into Conditions. (9d8e3a3) Message-ID: <20171026231752.C313F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d8e3a33b4cc3aaf312dc068be9810043c40ff91/ghc >--------------------------------------------------------------- commit 9d8e3a33b4cc3aaf312dc068be9810043c40ff91 Author: Andrey Mokhov Date: Thu Jan 1 22:35:50 2015 +0000 Change computed configuration flags into Conditions. >--------------------------------------------------------------- 9d8e3a33b4cc3aaf312dc068be9810043c40ff91 src/Package.hs | 4 ++-- src/Ways.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 98558e9..4154dc5 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -78,7 +78,7 @@ libraryArgs ways = in mconcat [ argEnable False "library-for-ghci" -- TODO: why always disable? , argEnable (vanilla `elem` ways) "library-vanilla" - , when (GhcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) $ + , when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) $ argEnable True "library-for-ghci" , argEnable (profiling `elem` ways) "library-profiling" , argEnable (dynamic `elem` ways) "shared" @@ -143,7 +143,7 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = , customConfArgs settings , libraryArgs =<< ways settings - , when HsColourSrcs $ with HsColour + , when hsColourSrcs $ with HsColour , configureArgs stage settings , when (stage == Stage0) $ bootPkgConstraints diff --git a/src/Ways.hs b/src/Ways.hs index a0e886a..0a4284a 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -65,7 +65,7 @@ allWays = [vanilla, profiling, logging, parallel, granSim, defaultWays :: Stage -> Action [Way] defaultWays stage = do - sharedLibs <- test PlatformSupportsSharedLibs + sharedLibs <- platformSupportsSharedLibs return $ [vanilla] ++ [profiling | stage /= Stage0] ++ [dynamic | sharedLibs ] From git at git.haskell.org Thu Oct 26 23:17:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clarify comment. (f72d396) Message-ID: <20171026231752.E75663A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f72d3961e47c80754c60921b72c52e9e71a2410d/ghc >--------------------------------------------------------------- commit f72d3961e47c80754c60921b72c52e9e71a2410d Author: Andrey Mokhov Date: Wed Aug 12 01:30:38 2015 +0100 Clarify comment. >--------------------------------------------------------------- f72d3961e47c80754c60921b72c52e9e71a2410d src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 8831d65..1ca003b 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -46,7 +46,7 @@ integerLibrary = integerGmp2 -- Set this to True if you are making any changes in the build system and want -- appropriate rebuilds to be initiated. Switching this to False speeds things -- up a little (particularly zero builds). --- WARNING: changing this setting leads to a complete rebuild. +-- WARNING: a complete rebuild is required when changing this setting. trackBuildSystem :: Bool trackBuildSystem = False From git at git.haskell.org Thu Oct 26 23:17:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant GHC extensions. (a7cc473) Message-ID: <20171026231756.82F9A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7cc473154bf0fcc311bb070381f28c444d4de1b/ghc >--------------------------------------------------------------- commit a7cc473154bf0fcc311bb070381f28c444d4de1b Author: Andrey Mokhov Date: Thu Jan 1 22:56:13 2015 +0000 Remove redundant GHC extensions. >--------------------------------------------------------------- a7cc473154bf0fcc311bb070381f28c444d4de1b src/Base.hs | 2 -- src/Oracles.hs | 3 --- src/Oracles/Base.hs | 3 +-- src/Oracles/Builder.hs | 3 +-- src/Oracles/Flag.hs | 3 +-- src/Oracles/Option.hs | 3 --- src/Oracles/PackageData.hs | 3 +-- 7 files changed, 4 insertions(+), 16 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 29c1340..b95cf14 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE FlexibleInstances #-} - module Base ( module Development.Shake, module Development.Shake.FilePath, diff --git a/src/Oracles.hs b/src/Oracles.hs index c9c9601..093f1b8 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,6 +1,3 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, NoImplicitPrelude #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} - module Oracles ( module Oracles.Base, module Oracles.Flag, diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 1e3dec2..1a9cf3e 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.Base ( ConfigKey (..), diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 3d3a0e9..6c37ec0 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, NoImplicitPrelude #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE NoImplicitPrelude #-} module Oracles.Builder ( Builder (..), diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 9245fb2..c8ddc8e 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE TypeFamilies, FlexibleInstances, MultiParamTypeClasses #-} module Oracles.Flag ( module Control.Monad, diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 72d166b..3661b71 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,6 +1,3 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} - module Oracles.Option ( Option (..), option, argOption, diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 3abd7a2..831fec9 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( PackageDataPair (..), From git at git.haskell.org Thu Oct 26 23:17:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add haddock path to cfg/system.config.in. (4e5ab6b) Message-ID: <20171026231756.9CB9B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e5ab6b936082f0c9718447b6dd143ec3785d67b/ghc >--------------------------------------------------------------- commit 4e5ab6b936082f0c9718447b6dd143ec3785d67b Author: Andrey Mokhov Date: Wed Aug 19 02:35:04 2015 +0100 Add haddock path to cfg/system.config.in. >--------------------------------------------------------------- 4e5ab6b936082f0c9718447b6dd143ec3785d67b cfg/system.config.in | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 029a81a..a274e84 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -5,18 +5,20 @@ #=================== system-ghc = @WithGhc@ +system-gcc = @CC_STAGE0@ +system-ghc-pkg = @GhcPkgCmd@ +gcc = @WhatGccIsCalled@ + ghc-stage1 = @hardtop@/inplace/bin/ghc-stage1 ghc-stage2 = @hardtop@/inplace/bin/ghc-stage2 ghc-stage3 = @hardtop@/inplace/bin/ghc-stage3 -system-ghc-pkg = @GhcPkgCmd@ ghc-pkg = @hardtop@/inplace/bin/ghc-pkg -system-gcc = @CC_STAGE0@ -gcc = @WhatGccIsCalled@ - ghc-cabal = @hardtop@/inplace/bin/ghc-cabal +haddock = @hardtop@/inplace/bin/haddock + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ From git at git.haskell.org Thu Oct 26 23:17:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:17:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Condition to Base.hs. (4166bc7) Message-ID: <20171026231759.E78E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4166bc732f9f62a34e0e5597686024e995d98691/ghc >--------------------------------------------------------------- commit 4166bc732f9f62a34e0e5597686024e995d98691 Author: Andrey Mokhov Date: Thu Jan 1 23:13:50 2015 +0000 Move Condition to Base.hs. >--------------------------------------------------------------- 4166bc732f9f62a34e0e5597686024e995d98691 src/Base.hs | 3 +++ src/Oracles/Base.hs | 5 +---- src/Oracles/Flag.hs | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index b95cf14..0a88146 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -6,6 +6,7 @@ module Base ( module Data.List, Stage (..), Args, arg, + Condition (..), joinArgs, joinArgsWithSpaces, splitArgs, filterOut ) where @@ -20,6 +21,8 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) type Args = Action [String] +type Condition = Action Bool + instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 1a9cf3e..f9e5c73 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -2,15 +2,12 @@ module Oracles.Base ( ConfigKey (..), - askConfigWithDefault, askConfig, - Condition (..) + askConfigWithDefault, askConfig ) where import Base import Development.Shake.Classes -type Condition = Action Bool - newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) askConfigWithDefault :: String -> Action String -> Action String diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index c8ddc8e..1958c07 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -4,7 +4,7 @@ module Oracles.Flag ( module Control.Monad, module Prelude, Flag (..), - Condition, test, when, unless, not, (&&), (||) + test, when, unless, not, (&&), (||) ) where import Control.Monad hiding (when, unless) From git at git.haskell.org Thu Oct 26 23:18:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddock builder. (30687f3) Message-ID: <20171026231800.073493A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30687f35a0f3ec3cdd488f2f55c0eaf626211ea2/ghc >--------------------------------------------------------------- commit 30687f35a0f3ec3cdd488f2f55c0eaf626211ea2 Author: Andrey Mokhov Date: Wed Aug 19 02:35:56 2015 +0100 Add Haddock builder. >--------------------------------------------------------------- 30687f35a0f3ec3cdd488f2f55c0eaf626211ea2 src/Builder.hs | 42 ++++++++++++++++++++++++------------------ 1 file changed, 24 insertions(+), 18 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index b175fac..ac184d3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -19,12 +19,13 @@ import GHC.Generics -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) --- TODO: add Cpp and Haddock builders +-- TODO: add Cpp builders -- TODO: rename Gcc to Cc? data Builder = Ar | Ld | Alex | Happy + | Haddock | HsColour | GhcCabal | Gcc Stage @@ -32,28 +33,33 @@ data Builder = Ar | GhcM Stage | GccM Stage | GhcPkg Stage + | GhcCabalHsColour deriving (Show, Eq, Generic) -- Configuration files refer to Builders as follows: +-- TODO: determine paths to utils without looking up configuration files builderKey :: Builder -> String builderKey builder = case builder of - Ar -> "ar" - Ld -> "ld" - Alex -> "alex" - Happy -> "happy" - HsColour -> "hscolour" - GhcCabal -> "ghc-cabal" - Ghc Stage0 -> "system-ghc" - Ghc Stage1 -> "ghc-stage1" - Ghc Stage2 -> "ghc-stage2" - Ghc Stage3 -> "ghc-stage3" - Gcc Stage0 -> "system-gcc" - Gcc _ -> "gcc" - GhcPkg Stage0 -> "system-ghc-pkg" - GhcPkg _ -> "ghc-pkg" - -- GhcM is currently a synonym for Ghc (to be called with -M flag) - GhcM stage -> builderKey $ Ghc stage - GccM stage -> builderKey $ Gcc stage + Ar -> "ar" + Ld -> "ld" + Alex -> "alex" + Happy -> "happy" + Haddock -> "haddock" + HsColour -> "hscolour" + GhcCabal -> "ghc-cabal" + Ghc Stage0 -> "system-ghc" + Ghc Stage1 -> "ghc-stage1" + Ghc Stage2 -> "ghc-stage2" + Ghc Stage3 -> "ghc-stage3" + Gcc Stage0 -> "system-gcc" + Gcc _ -> "gcc" + GhcPkg Stage0 -> "system-ghc-pkg" + GhcPkg _ -> "ghc-pkg" + -- GhcM/GccM are synonyms for Ghc/Gcc (called with -M and -MM flags) + GhcM stage -> builderKey $ Ghc stage + GccM stage -> builderKey $ Gcc stage + -- GhcCabalHsColour is a synonym for GhcCabal (called in hscolour mode) + GhcCabalHsColour -> builderKey $ GhcCabal builderPath :: Builder -> Action String builderPath builder = do From git at git.haskell.org Thu Oct 26 23:18:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ShowAction typeclass. (64b16d7) Message-ID: <20171026231803.7AF193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64b16d796dc5aa8a889d41eeb08cbead19cba14d/ghc >--------------------------------------------------------------- commit 64b16d796dc5aa8a889d41eeb08cbead19cba14d Author: Andrey Mokhov Date: Thu Jan 1 23:56:12 2015 +0000 Add ShowAction typeclass. >--------------------------------------------------------------- 64b16d796dc5aa8a889d41eeb08cbead19cba14d src/Base.hs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 0a88146..77c2858 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-} + module Base ( module Development.Shake, module Development.Shake.FilePath, @@ -27,8 +29,14 @@ instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q -arg :: [String] -> Args -arg = return +class ShowAction a where + showAction :: a -> Action String + +instance ShowAction String where + showAction = return + +arg :: ShowAction a => [a] -> Args +arg = mapM showAction intercalateArgs :: String -> Args -> Args intercalateArgs s args = do From git at git.haskell.org Thu Oct 26 23:18:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add HiddenModules key to PackageData.hs. (3d65807) Message-ID: <20171026231803.9AF383A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d6580728cc485bb8e16d4ee27ed04a8ec8c743e/ghc >--------------------------------------------------------------- commit 3d6580728cc485bb8e16d4ee27ed04a8ec8c743e Author: Andrey Mokhov Date: Wed Aug 19 02:36:33 2015 +0100 Add HiddenModules key to PackageData.hs. >--------------------------------------------------------------- 3d6580728cc485bb8e16d4ee27ed04a8ec8c743e src/Oracles/PackageData.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index de9db7c..4097ac1 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -26,6 +26,7 @@ data PackageData = Version FilePath | BuildGhciLib FilePath data PackageDataList = Modules FilePath + | HiddenModules FilePath | SrcDirs FilePath | IncludeDirs FilePath | Deps FilePath @@ -66,6 +67,7 @@ pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = do let (key, path, defaultValue) = case packageData of Modules path -> ("MODULES" , path, "" ) + HiddenModules path -> ("HIDDEN_MODULES" , path, "" ) SrcDirs path -> ("HS_SRC_DIRS" , path, ".") IncludeDirs path -> ("INCLUDE_DIRS" , path, ".") Deps path -> ("DEPS" , path, "" ) From git at git.haskell.org Thu Oct 26 23:18:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace path with instance ShowAction Builder. (37de3d5) Message-ID: <20171026231806.D73A43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37de3d57c7e35237dea4f11c2cb2016eedeb49c5/ghc >--------------------------------------------------------------- commit 37de3d57c7e35237dea4f11c2cb2016eedeb49c5 Author: Andrey Mokhov Date: Fri Jan 2 02:34:56 2015 +0000 Replace path with instance ShowAction Builder. >--------------------------------------------------------------- 37de3d57c7e35237dea4f11c2cb2016eedeb49c5 src/Oracles/Builder.hs | 73 +++++++++++++++++++++++--------------------------- 1 file changed, 34 insertions(+), 39 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 6c37ec0..3da6f9a 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,7 @@ module Oracles.Builder ( Builder (..), - path, with, run, argPath, + with, run, hsColourSrcs ) where @@ -14,39 +14,34 @@ import Oracles.Option data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage -path :: Builder -> Action FilePath -path builder = do - let key = case builder of - Ar -> "ar" - Ld -> "ld" - Gcc -> "gcc" - Alex -> "alex" - Happy -> "happy" - HsColour -> "hscolour" - GhcCabal -> "ghc-cabal" - Ghc Stage0 -> "system-ghc" -- Ghc Stage0 is the bootstrapping compiler - Ghc Stage1 -> "ghc-stage1" -- Ghc StageN, N > 0, is the one built on stage (N - 1) - Ghc Stage2 -> "ghc-stage2" - Ghc Stage3 -> "ghc-stage3" - GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg - GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) - cfgPath <- askConfigWithDefault key $ - error $ "\nCannot find path to '" - ++ key - ++ "' in configuration files." - let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" - windows <- windowsHost - if (windows && "/" `isPrefixOf` cfgPathExe) - then do - Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] - return $ dropWhileEnd isSpace out ++ drop 1 cfgPathExe - else - return cfgPathExe - -argPath :: Builder -> Args -argPath builder = do - path <- path builder - arg [path] +instance ShowAction Builder where + showAction builder = do + let key = case builder of + Ar -> "ar" + Ld -> "ld" + Gcc -> "gcc" + Alex -> "alex" + Happy -> "happy" + HsColour -> "hscolour" + GhcCabal -> "ghc-cabal" + Ghc Stage0 -> "system-ghc" -- Ghc Stage0 is the bootstrapping compiler + Ghc Stage1 -> "ghc-stage1" -- Ghc StageN, N > 0, is the one built on stage (N - 1) + Ghc Stage2 -> "ghc-stage2" + Ghc Stage3 -> "ghc-stage3" + GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg + GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) + cfgPath <- askConfigWithDefault key $ + error $ "\nCannot find path to '" + ++ key + ++ "' in configuration files." + let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" + windows <- windowsHost + if (windows && "/" `isPrefixOf` cfgPathExe) + then do + Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] + return $ dropWhileEnd isSpace out ++ drop 1 cfgPathExe + else + return cfgPathExe -- When LaxDeps flag is set (by adding 'lax-dependencies = YES' to user.config), -- dependencies on the GHC executable are turned into order-only dependencies to @@ -55,12 +50,12 @@ argPath builder = do -- the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - target <- path ghc + target <- showAction ghc laxDeps <- test LaxDeps if laxDeps then orderOnly [target] else need [target] needBuilder builder = do - target <- path builder + target <- showAction builder need [target] -- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder @@ -75,18 +70,18 @@ with builder = do Happy -> "--with-happy=" GhcPkg _ -> "--with-ghc-pkg=" HsColour -> "--with-hscolour=" - suffix <- path builder + suffix <- showAction builder needBuilder builder return [prefix ++ suffix] run :: Builder -> Args -> Action () run builder args = do needBuilder builder - exe <- path builder + exe <- showAction builder args' <- args cmd [exe :: FilePath] args' hsColourSrcs :: Condition hsColourSrcs = do - hscolour <- path HsColour + hscolour <- showAction HsColour return $ hscolour /= "" From git at git.haskell.org Thu Oct 26 23:18:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add haddock build targets. (d811225) Message-ID: <20171026231807.0E7183A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d811225729618537302bde9cba2d591a2dd54ef4/ghc >--------------------------------------------------------------- commit d811225729618537302bde9cba2d591a2dd54ef4 Author: Andrey Mokhov Date: Wed Aug 19 02:37:30 2015 +0100 Add haddock build targets. >--------------------------------------------------------------- d811225729618537302bde9cba2d591a2dd54ef4 src/Rules.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Rules.hs b/src/Rules.hs index 43f5922..65ae2e4 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -14,6 +14,7 @@ import Rules.Package import Rules.Oracles import Rules.Resources import Settings.Ways +import Settings.User import Settings.Util import Settings.Packages import Settings.TargetDirectory @@ -28,15 +29,17 @@ generateTargets = action $ do buildPath = targetPath stage pkg -/- "build" buildGhciLib <- interpret target $ getPkgData BuildGhciLib pkgKey <- interpret target $ getPkgData PackageKey + buildHaddock <- interpret target $ Settings.User.buildHaddock let ghciLib = [ buildPath -/- "HS" ++ pkgKey <.> "o" | buildGhciLib == "YES" && stage /= Stage0 ] + haddock = [ pkgHaddockPath pkg | buildHaddock ] ways <- interpret target getWays libs <- forM ways $ \way -> do extension <- libsuf way return $ buildPath -/- "libHS" ++ pkgKey <.> extension - return $ ghciLib ++ libs + return $ ghciLib ++ libs ++ haddock need $ reverse targets From git at git.haskell.org Thu Oct 26 23:18:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace option with instance ShowAction Option. (1495a2d) Message-ID: <20171026231810.5EA043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1495a2d66f0a9cb8082285b68c1e42cf954eb6b8/ghc >--------------------------------------------------------------- commit 1495a2d66f0a9cb8082285b68c1e42cf954eb6b8 Author: Andrey Mokhov Date: Fri Jan 2 02:43:40 2015 +0000 Replace option with instance ShowAction Option. >--------------------------------------------------------------- 1495a2d66f0a9cb8082285b68c1e42cf954eb6b8 src/Oracles/Option.hs | 44 +++++++++++++++++++------------------------- 1 file changed, 19 insertions(+), 25 deletions(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 3661b71..899aec7 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,6 +1,5 @@ module Oracles.Option ( Option (..), - option, argOption, ghcWithInterpreter, platformSupportsSharedLibs, windowsHost ) where @@ -13,31 +12,26 @@ data Option = TargetOS | TargetArch | TargetPlatformFull | SrcHcOpts | HostOsCpp -option :: Option -> Action String -option opt = askConfig $ case opt of - TargetOS -> "target-os" - TargetArch -> "target-arch" - TargetPlatformFull -> "target-platform-full" - ConfCcArgs stage -> "conf-cc-args-stage-" ++ (show . fromEnum) stage - ConfCppArgs stage -> "conf-cpp-args-stage-" ++ (show . fromEnum) stage - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ (show . fromEnum) stage - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ (show . fromEnum) stage - IconvIncludeDirs -> "iconv-include-dirs" - IconvLibDirs -> "iconv-lib-dirs" - GmpIncludeDirs -> "gmp-include-dirs" - GmpLibDirs -> "gmp-lib-dirs" - SrcHcOpts -> "src-hc-opts" - HostOsCpp -> "host-os-cpp" - -argOption :: Option -> Args -argOption opt = do - opt' <- option opt - arg [opt'] +instance ShowAction Option where + showAction opt = askConfig $ case opt of + TargetOS -> "target-os" + TargetArch -> "target-arch" + TargetPlatformFull -> "target-platform-full" + ConfCcArgs stage -> "conf-cc-args-stage-" ++ (show . fromEnum) stage + ConfCppArgs stage -> "conf-cpp-args-stage-" ++ (show . fromEnum) stage + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ (show . fromEnum) stage + ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ (show . fromEnum) stage + IconvIncludeDirs -> "iconv-include-dirs" + IconvLibDirs -> "iconv-lib-dirs" + GmpIncludeDirs -> "gmp-include-dirs" + GmpLibDirs -> "gmp-lib-dirs" + SrcHcOpts -> "src-hc-opts" + HostOsCpp -> "host-os-cpp" ghcWithInterpreter :: Condition ghcWithInterpreter = do - os <- option TargetOS - arch <- option TargetArch + os <- showAction TargetOS + arch <- showAction TargetArch return $ os `elem` ["mingw32", "cygwin32", "linux", "solaris2", "freebsd", "dragonfly", "netbsd", "openbsd", "darwin", "kfreebsdgnu"] && @@ -45,10 +39,10 @@ ghcWithInterpreter = do platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do - platform <- option TargetPlatformFull + platform <- showAction TargetPlatformFull return $ platform `notElem` [ "powerpc-unknown-linux", "x86_64-unknown-mingw32", "i386-unknown-mingw32" ] -- TODO: i386-unknown-solaris2? windowsHost :: Condition windowsHost = do - hostOsCpp <- option HostOsCpp + hostOsCpp <- showAction HostOsCpp return $ hostOsCpp `elem` ["mingw32", "cygwin32"] From git at git.haskell.org Thu Oct 26 23:18:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add pkgHaddockPath for finding haddock files. (0aedb12) Message-ID: <20171026231810.8DBC73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0aedb12d7790c167f3550b59c3303f8874c8af3c/ghc >--------------------------------------------------------------- commit 0aedb12d7790c167f3550b59c3303f8874c8af3c Author: Andrey Mokhov Date: Wed Aug 19 02:38:31 2015 +0100 Add pkgHaddockPath for finding haddock files. >--------------------------------------------------------------- 0aedb12d7790c167f3550b59c3303f8874c8af3c src/Settings/TargetDirectory.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 0844d14..10f0f67 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,7 +1,8 @@ module Settings.TargetDirectory ( - targetDirectory, targetPath + targetDirectory, targetPath, pkgHaddockPath ) where +import Base import Util import Stage import Package @@ -14,3 +15,9 @@ targetDirectory = userTargetDirectory -- Path to the target directory from GHC source root targetPath :: Stage -> Package -> FilePath targetPath stage pkg = pkgPath pkg -/- targetDirectory stage pkg + +-- Relative path to a package haddock file, e.g.: +-- "libraries/array/dist-install/doc/html/array/array.haddock" +pkgHaddockPath :: Package -> FilePath +pkgHaddockPath pkg @ (Package name _) = + targetPath Stage1 pkg -/- "doc/html" -/- name -/- name <.> "haddock" From git at git.haskell.org Thu Oct 26 23:18:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add args -- a variadic version of arg. (6084342) Message-ID: <20171026231814.76D763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/60843423d23b84928c2c1ce2725b5e293cb81061/ghc >--------------------------------------------------------------- commit 60843423d23b84928c2c1ce2725b5e293cb81061 Author: Andrey Mokhov Date: Fri Jan 2 03:03:27 2015 +0000 Add args -- a variadic version of arg. >--------------------------------------------------------------- 60843423d23b84928c2c1ce2725b5e293cb81061 src/Base.hs | 16 +++++++++++++++- 1 file changed, 15 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 77c2858..645d5dc 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,7 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, + Args, arg, args, ShowAction (..), Condition (..), joinArgs, joinArgsWithSpaces, splitArgs, filterOut @@ -38,6 +38,20 @@ instance ShowAction String where arg :: ShowAction a => [a] -> Args arg = mapM showAction +class Collect a where + collect :: Args -> a + +instance Collect Args where + collect = id + +instance (ShowAction a, Collect r) => Collect (a -> r) where + collect prev next = collect $ do + next' <- showAction next + prev <> return [next'] + +args :: Collect a => a +args = collect mempty + intercalateArgs :: String -> Args -> Args intercalateArgs s args = do as <- args From git at git.haskell.org Thu Oct 26 23:18:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build haddock only in Stage1. (2520d7f) Message-ID: <20171026231814.A0F4A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2520d7fdb98c537591653f0f753398dd5e58cdb5/ghc >--------------------------------------------------------------- commit 2520d7fdb98c537591653f0f753398dd5e58cdb5 Author: Andrey Mokhov Date: Wed Aug 19 02:39:23 2015 +0100 Build haddock only in Stage1. >--------------------------------------------------------------- 2520d7fdb98c537591653f0f753398dd5e58cdb5 src/Settings/User.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 1ca003b..3646994 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -48,7 +48,7 @@ integerLibrary = integerGmp2 -- up a little (particularly zero builds). -- WARNING: a complete rebuild is required when changing this setting. trackBuildSystem :: Bool -trackBuildSystem = False +trackBuildSystem = True validating :: Bool validating = False @@ -66,4 +66,4 @@ laxDependencies :: Bool laxDependencies = False buildHaddock :: Predicate -buildHaddock = return True +buildHaddock = stage Stage1 From git at git.haskell.org Thu Oct 26 23:18:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement joinArgs and joinArgsWithSpaces as variadic functions. (c6870b2) Message-ID: <20171026231818.1C1AD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6870b2f0e46782ad6a094cff9809150fe2eebf7/ghc >--------------------------------------------------------------- commit c6870b2f0e46782ad6a094cff9809150fe2eebf7 Author: Andrey Mokhov Date: Sat Jan 3 23:57:51 2015 +0000 Implement joinArgs and joinArgsWithSpaces as variadic functions. >--------------------------------------------------------------- c6870b2f0e46782ad6a094cff9809150fe2eebf7 src/Base.hs | 37 ++++++++++++++++++++++--------------- 1 file changed, 22 insertions(+), 15 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 645d5dc..283d62f 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,6 +23,7 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) type Args = Action [String] + type Condition = Action Bool instance Monoid a => Monoid (Action a) where @@ -35,36 +36,42 @@ class ShowAction a where instance ShowAction String where showAction = return +instance ShowAction (Action String) where + showAction = id + arg :: ShowAction a => [a] -> Args arg = mapM showAction +type ArgsCombine = Args -> Args -> Args + class Collect a where - collect :: Args -> a + collect :: ArgsCombine -> Args -> a instance Collect Args where - collect = id + collect = const id instance (ShowAction a, Collect r) => Collect (a -> r) where - collect prev next = collect $ do - next' <- showAction next - prev <> return [next'] + collect combine x = \y -> collect combine $ x `combine` arg [y] + +instance Collect r => Collect (Args -> r) where + collect combine x = \y -> collect combine $ x `combine` y args :: Collect a => a -args = collect mempty +args = collect (<>) mempty -intercalateArgs :: String -> Args -> Args -intercalateArgs s args = do - as <- args - return [intercalate s as] +joinArgs :: Collect a => a +joinArgs = collect (\x y -> intercalateArgs "" x <> y) mempty -joinArgsWithSpaces :: Args -> Args -joinArgsWithSpaces = intercalateArgs " " +joinArgsWithSpaces :: Collect a => a +joinArgsWithSpaces = collect (\x y -> intercalateArgs " " x <> y) mempty -joinArgs :: Args -> Args -joinArgs = intercalateArgs "" +intercalateArgs :: String -> Args -> Args +intercalateArgs s as = do + as' <- as + return [intercalate s as'] splitArgs :: Args -> Args splitArgs = fmap (concatMap words) filterOut :: Args -> [String] -> Args -filterOut args list = filter (`notElem` list) <$> args +filterOut as list = filter (`notElem` list) <$> as From git at git.haskell.org Thu Oct 26 23:18:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Collect all arguments for haddock. (b16ec20) Message-ID: <20171026231818.4B20F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b16ec20251a2f1cee03156062be31fbad0b775dd/ghc >--------------------------------------------------------------- commit b16ec20251a2f1cee03156062be31fbad0b775dd Author: Andrey Mokhov Date: Wed Aug 19 02:41:39 2015 +0100 Collect all arguments for haddock. >--------------------------------------------------------------- b16ec20251a2f1cee03156062be31fbad0b775dd src/Settings/Args.hs | 3 ++ src/Settings/Builders/Ghc.hs | 97 +++++++++++++++++++-------------------- src/Settings/Builders/GhcCabal.hs | 16 +++++-- src/Settings/Builders/Haddock.hs | 69 ++++++++++++++++++++++++++++ src/Settings/Util.hs | 9 ++-- 5 files changed, 137 insertions(+), 57 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b16ec20251a2f1cee03156062be31fbad0b775dd From git at git.haskell.org Thu Oct 26 23:18:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor using variadic args. (a4f318f) Message-ID: <20171026231821.921943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4f318fdf2905dd1ee5be475bfa38fae4a39b869/ghc >--------------------------------------------------------------- commit a4f318fdf2905dd1ee5be475bfa38fae4a39b869 Author: Andrey Mokhov Date: Sun Jan 4 03:30:13 2015 +0000 Refactor using variadic args. >--------------------------------------------------------------- a4f318fdf2905dd1ee5be475bfa38fae4a39b869 src/Base.hs | 36 +++++++++++++++--------------- src/Oracles/Builder.hs | 16 +++++++------- src/Oracles/Flag.hs | 8 +++---- src/Oracles/Option.hs | 10 ++++----- src/Package.hs | 59 ++++++++++++++++++++++---------------------------- 5 files changed, 62 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 a4f318fdf2905dd1ee5be475bfa38fae4a39b869 From git at git.haskell.org Thu Oct 26 23:18:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add findKnownPackage for finding packages by name. (b51e6d9) Message-ID: <20171026231821.C522E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b51e6d97b5f930963687dca5eb64983324baa8b1/ghc >--------------------------------------------------------------- commit b51e6d97b5f930963687dca5eb64983324baa8b1 Author: Andrey Mokhov Date: Wed Aug 19 02:42:15 2015 +0100 Add findKnownPackage for finding packages by name. >--------------------------------------------------------------- b51e6d97b5f930963687dca5eb64983324baa8b1 src/Settings/Packages.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 6e236c9..369879c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -1,6 +1,6 @@ module Settings.Packages ( module Settings.Default, - packages, getPackages, knownPackages + packages, getPackages, knownPackages, findKnownPackage ) where import Package @@ -9,6 +9,7 @@ import Expression import Oracles.Setting import Settings.User import Settings.Default +import Data.List -- Combining default list of packages with user modifications packages :: Packages @@ -40,3 +41,11 @@ packagesStage1 = mconcat knownPackages :: [Package] knownPackages = defaultKnownPackages ++ userKnownPackages + +-- Note: this is slow but we keep it simple as there not too many packages (30) +-- We handle integerLibrary in a special way, because packages integerGmp and +-- integerGmp2 have the same package name -- we return the user-selected one. +findKnownPackage :: PackageName -> Maybe Package +findKnownPackage name + | name == pkgName integerLibrary = Just integerLibrary + | otherwise = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Thu Oct 26 23:18:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor changes and comments. (640b38f) Message-ID: <20171026231825.554BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/640b38fbd3857a6c72156f81bd4ba06b8af61ae2/ghc >--------------------------------------------------------------- commit 640b38fbd3857a6c72156f81bd4ba06b8af61ae2 Author: Andrey Mokhov Date: Sun Jan 4 03:35:36 2015 +0000 Minor changes and comments. >--------------------------------------------------------------- 640b38fbd3857a6c72156f81bd4ba06b8af61ae2 src/Base.hs | 2 +- src/Package.hs | 18 +++++++++--------- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 490c031..ea9980c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,7 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, args, ShowAction (..), Collect (..), + Args, arg, args, ShowAction (..), Condition (..), joinArgs, joinArgsSpaced, splitArgs, filterOut diff --git a/src/Package.hs b/src/Package.hs index 5d6fc1e..843f34f 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -230,14 +230,14 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = return $ path dir modPath <.> extension packageKey <- packagaDataOption pkgData PackageKey run (Ghc stage) $ mconcat - [ arg ["-M"] + [ arg "-M" , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - , splitArgs $ arg [SrcHcOpts] - , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] - , arg [if usePackageKey then "-this-package-key" else "-package-name"] - , arg [packageKey] -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) - , arg ["-hide-all-packages"] - , arg ["-i"] -- resets the search path to nothing; TODO: check if really needed + , splitArgs $ arg SrcHcOpts -- TODO: get rid of splitArgs + , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" + , arg $ if usePackageKey then "-this-package-key" else "-package-name" + , arg packageKey -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg "-hide-all-packages" + , arg "-i" -- resets the search path to nothing; TODO: check if really needed , arg $ map (\d -> "-i" ++ path d) srcDirs , arg $ do prefix <- ["-i", "-I"] -- 'import' and '#include' search paths @@ -245,8 +245,8 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = return $ prefix ++ buildDir suffix , arg $ map (\d -> "-I" ++ path d) $ filter isRelative includeDirs , arg $ map (\d -> "-I" ++ d) $ filter isAbsolute includeDirs - , arg ["-optP-include"] - , arg ["-optP" ++ buildDir "build/autogen/cabal_macros.h"] + , arg "-optP-include" + , arg $ "-optP" ++ buildDir "build/autogen/cabal_macros.h" , if usePackageKey then arg $ concatMap (\d -> ["-package-key", d]) depKeys else arg $ concatMap (\d -> ["-package" , d]) deps From git at git.haskell.org Thu Oct 26 23:18:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement buildPackageDocumentation build rule. (b38d769) Message-ID: <20171026231825.85B383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b38d769b73fa7576c2450c7d6057e5e0dd83b8f0/ghc >--------------------------------------------------------------- commit b38d769b73fa7576c2450c7d6057e5e0dd83b8f0 Author: Andrey Mokhov Date: Wed Aug 19 02:42:50 2015 +0100 Implement buildPackageDocumentation build rule. >--------------------------------------------------------------- b38d769b73fa7576c2450c7d6057e5e0dd83b8f0 src/Rules/Documentation.hs | 53 ++++++++++++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 4 +++- 2 files changed, 56 insertions(+), 1 deletion(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs new file mode 100644 index 0000000..9cde8d1 --- /dev/null +++ b/src/Rules/Documentation.hs @@ -0,0 +1,53 @@ +module Rules.Documentation (buildPackageDocumentation) where + +import Way +import Base +import Stage +import Builder +import Package +import Expression +import Oracles.PackageData +import qualified Target +import Settings.TargetDirectory +import Rules.Actions +import Rules.Resources +import Settings.Util +import Settings.User +import Settings.Packages +import Control.Monad.Extra + +-- Note: this build rule creates plenty of files, not just the .haddock one. +-- All of them go into the 'doc' subdirectory. Pedantically tracking all built +-- files in the Shake databases seems fragile and unnecesarry. +buildPackageDocumentation :: Resources -> StagePackageTarget -> Rules () +buildPackageDocumentation _ target = + let stage = Target.stage target + pkg = Target.package target + name = pkgName pkg + cabal = pkgCabalPath pkg + haddock = pkgHaddockPath pkg + in when (stage == Stage1) $ do + + haddock %> \file -> do + whenM (specified HsColour) $ do + need [cabal] + build $ fullTarget target GhcCabalHsColour [cabal] [] + srcs <- interpret target getPackageSources + deps <- interpret target $ getPkgDataList DepNames + let haddocks = [ pkgHaddockPath depPkg + | Just depPkg <- map findKnownPackage deps ] + need $ srcs ++ haddocks + let haddockWay = if dynamicGhcPrograms then dynamic else vanilla + build $ fullTargetWithWay target Haddock haddockWay srcs [file] + +-- $$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_DEPS = +-- $$(foreach n,$$($1_$2_DEPS) +-- ,$$($$n_HADDOCK_FILE) $$($$n_dist-install_$$(HADDOCK_WAY)_LIB)) + +-- $$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) : +-- $$$$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_DEPS) | $$$$(dir $$$$@)/. + +-- # Make the haddocking depend on the library .a file, to ensure +-- # that we wait until the library is fully built before we haddock it +-- $$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) : $$($1_$2_$$(HADDOCK_WAY)_LIB) +-- endif diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index dbbe5cc..6e5448b 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -7,10 +7,12 @@ import Rules.Compile import Rules.Library import Rules.Resources import Rules.Dependencies +import Rules.Documentation buildPackage :: Resources -> StagePackageTarget -> Rules () buildPackage = mconcat [ buildPackageData , buildPackageDependencies , compilePackage - , buildPackageLibrary ] + , buildPackageLibrary + , buildPackageDocumentation ] From git at git.haskell.org Thu Oct 26 23:18:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Package.hs into logically separate modules. (04cbcbc) Message-ID: <20171026231829.0BBFA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/04cbcbc9a482ed70872e3f3bc1c6ca9224402b76/ghc >--------------------------------------------------------------- commit 04cbcbc9a482ed70872e3f3bc1c6ca9224402b76 Author: Andrey Mokhov Date: Mon Jan 5 00:40:25 2015 +0000 Decompose Package.hs into logically separate modules. >--------------------------------------------------------------- 04cbcbc9a482ed70872e3f3bc1c6ca9224402b76 src/Package.hs | 284 +------------------------------------------- src/Package/Base.hs | 86 ++++++++++++++ src/Package/Data.hs | 92 ++++++++++++++ src/Package/Dependencies.hs | 108 +++++++++++++++++ 4 files changed, 292 insertions(+), 278 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 04cbcbc9a482ed70872e3f3bc1c6ca9224402b76 From git at git.haskell.org Thu Oct 26 23:18:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop mk-miner submodule. (885369f) Message-ID: <20171026231829.388613A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/885369f3c4ae9664bafc328ee191ec5efb090858/ghc >--------------------------------------------------------------- commit 885369f3c4ae9664bafc328ee191ec5efb090858 Author: Andrey Mokhov Date: Wed Aug 19 15:02:19 2015 +0100 Drop mk-miner submodule. >--------------------------------------------------------------- 885369f3c4ae9664bafc328ee191ec5efb090858 .gitmodules | 3 --- 1 file changed, 3 deletions(-) diff --git a/.gitmodules b/.gitmodules deleted file mode 100644 index 8f798aa..0000000 --- a/.gitmodules +++ /dev/null @@ -1,3 +0,0 @@ -[submodule "mk-miner"] - path = mk-miner - url = https://github.com/snowleopard/mk-miner.git From git at git.haskell.org Thu Oct 26 23:18:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track build rule source files initiating incremental rebuilds when code changes. (5a4b172) Message-ID: <20171026231833.0AF283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a4b172667f27d01ae46f6dc7d9bc7097ea06605/ghc >--------------------------------------------------------------- commit 5a4b172667f27d01ae46f6dc7d9bc7097ea06605 Author: Andrey Mokhov Date: Mon Jan 5 00:48:32 2015 +0000 Track build rule source files initiating incremental rebuilds when code changes. >--------------------------------------------------------------- 5a4b172667f27d01ae46f6dc7d9bc7097ea06605 src/Package/Data.hs | 1 + src/Package/Dependencies.hs | 1 + 2 files changed, 2 insertions(+) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 2d7b4b7..c95f8c9 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -56,6 +56,7 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = "build" "autogen" "cabal_macros.h", "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. ] &%> \_ -> do + need ["shake/src/Package/Data.hs"] -- Track changes in this file need [path name <.> "cabal"] when (doesFileExist $ path "configure.ac") $ need [path "configure"] run GhcCabal cabalArgs diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 65c9b1f..99ffc34 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -68,6 +68,7 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist in (buildDir "build" name <.> "m") %> \out -> do + need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file let pkgData = buildDir "package-data.mk" usePackageKey <- SupportsPackageKey || stage /= Stage0 -- TODO: check reasoning (distdir-way-opts) [mods, srcDirs, includeDirs, deps, depKeys] <- From git at git.haskell.org Thu Oct 26 23:18:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove traces of mk-miner submodule. (d56995a) Message-ID: <20171026231833.33B043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d56995a00e2dbf7053bb3fdea357ef6e456b9639/ghc >--------------------------------------------------------------- commit d56995a00e2dbf7053bb3fdea357ef6e456b9639 Author: Andrey Mokhov Date: Wed Aug 19 15:14:52 2015 +0100 Remove traces of mk-miner submodule. >--------------------------------------------------------------- d56995a00e2dbf7053bb3fdea357ef6e456b9639 mk-miner | 1 - 1 file changed, 1 deletion(-) diff --git a/mk-miner b/mk-miner deleted file mode 160000 index 276425e..0000000 --- a/mk-miner +++ /dev/null @@ -1 +0,0 @@ -Subproject commit 276425ea44420f49ac34fd942c0dad84b0c0d332 From git at git.haskell.org Thu Oct 26 23:18:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add directions to Package submodules. (eeea3ed) Message-ID: <20171026231836.BDA3D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eeea3ed76e1886c34234a4efde6f3c6dc296c2d4/ghc >--------------------------------------------------------------- commit eeea3ed76e1886c34234a4efde6f3c6dc296c2d4 Author: Andrey Mokhov Date: Mon Jan 5 00:57:26 2015 +0000 Add directions to Package submodules. >--------------------------------------------------------------- eeea3ed76e1886c34234a4efde6f3c6dc296c2d4 src/Package.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index ce7a8d5..ea7aae4 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,16 +1,15 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package ( - packageRules - ) where +module Package (packageRules) where import Package.Base import Package.Data import Package.Dependencies -- These are the packages we build +-- See Package.Base for definitions of basic types packages :: [Package] packages = [libraryPackage "deepseq" Stage1 defaultSettings] +-- Rule buildXY is defined in module X.Y buildPackage :: Package -> TodoItem -> Rules () buildPackage pkg todoItem = do buildPackageData pkg todoItem @@ -18,8 +17,7 @@ buildPackage pkg todoItem = do packageRules :: Rules () packageRules = do - - want ["libraries/deepseq/dist-install/build/deepseq.m"] + want ["libraries/deepseq/dist-install/build/deepseq.m"] -- TODO: control targets from commang line arguments forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:18:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop custom cfg/configure.ac and instead add an appropriate AC_CONFIG_FILES command directly to the existing configure.ac. (d4f6e48) Message-ID: <20171026231836.DF7293A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50/ghc >--------------------------------------------------------------- commit d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50 Author: Andrey Mokhov Date: Thu Aug 20 23:56:01 2015 +0100 Drop custom cfg/configure.ac and instead add an appropriate AC_CONFIG_FILES command directly to the existing configure.ac. >--------------------------------------------------------------- d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50 cfg/configure.ac | 1073 --------------------------------------------------- src/Rules/Config.hs | 17 +- 2 files changed, 16 insertions(+), 1074 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 d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50 From git at git.haskell.org Thu Oct 26 23:18:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor changes. (500ab74) Message-ID: <20171026231840.7C7553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/500ab7440aaf5aca6a11df8c6001a963aeb30fe4/ghc >--------------------------------------------------------------- commit 500ab7440aaf5aca6a11df8c6001a963aeb30fe4 Author: Andrey Mokhov Date: Mon Jan 5 01:03:05 2015 +0000 Minor changes. >--------------------------------------------------------------- 500ab7440aaf5aca6a11df8c6001a963aeb30fe4 src/Package.hs | 3 ++- src/Package/Base.hs | 9 ++++----- src/Package/Data.hs | 4 +--- src/Package/Dependencies.hs | 4 +--- 4 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index ea7aae4..7a5f20e 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -4,8 +4,9 @@ import Package.Base import Package.Data import Package.Dependencies --- These are the packages we build -- See Package.Base for definitions of basic types + +-- These are the packages we build: packages :: [Package] packages = [libraryPackage "deepseq" Stage1 defaultSettings] diff --git a/src/Package/Base.hs b/src/Package/Base.hs index daa5455..896bcb3 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -62,11 +62,10 @@ commonCppArgs :: Args commonCppArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? commonCcWarninigArgs :: Args -commonCcWarninigArgs = when Validating $ mconcat - [ when GccIsClang $ arg "-Wno-unknown-pragmas" - , when (not GccIsClang && not GccLt46) $ arg "-Wno-error=inline" - , when ( GccIsClang && not GccLt46 && windowsHost) $ arg "-Werror=unused-but-set-variable" - ] +commonCcWarninigArgs = when Validating $ + when GccIsClang (arg "-Wno-unknown-pragmas") + <> when (not GccIsClang && not GccLt46) (arg "-Wno-error=inline") + <> when ( GccIsClang && not GccLt46 && windowsHost) (arg "-Werror=unused-but-set-variable" ) bootPkgConstraints :: Args bootPkgConstraints = mempty diff --git a/src/Package/Data.hs b/src/Package/Data.hs index c95f8c9..fe3ec26 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -1,7 +1,5 @@ {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} -module Package.Data ( - buildPackageData - ) where +module Package.Data (buildPackageData) where import Package.Base diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 99ffc34..4327ca6 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -1,7 +1,5 @@ {-# LANGUAGE NoImplicitPrelude #-} -module Package.Dependencies ( - buildPackageDependencies - ) where +module Package.Dependencies (buildPackageDependencies) where import Package.Base From git at git.haskell.org Thu Oct 26 23:18:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move needBuilder to src/Builder.hs. (7baa070) Message-ID: <20171026231840.AC9BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7baa070bd5bb2b40235bdb362d1f0ec6063f260d/ghc >--------------------------------------------------------------- commit 7baa070bd5bb2b40235bdb362d1f0ec6063f260d Author: Andrey Mokhov Date: Fri Aug 21 16:07:01 2015 +0100 Move needBuilder to src/Builder.hs. >--------------------------------------------------------------- 7baa070bd5bb2b40235bdb362d1f0ec6063f260d src/Builder.hs | 25 +++++++++++++++++-------- 1 file changed, 17 insertions(+), 8 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index ac184d3..bd0ef49 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} module Builder ( - Builder (..), builderKey, builderPath, specified + Builder (..), builderKey, builderPath, specified, needBuilder ) where import Base @@ -61,7 +61,7 @@ builderKey builder = case builder of -- GhcCabalHsColour is a synonym for GhcCabal (called in hscolour mode) GhcCabalHsColour -> builderKey $ GhcCabal -builderPath :: Builder -> Action String +builderPath :: Builder -> Action FilePath builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ putError $ "\nCannot find path to '" ++ (builderKey builder) @@ -71,6 +71,21 @@ builderPath builder = do specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath +-- Make sure a builder exists on the given path and rebuild it if out of date. +-- If laxDependencies is True then we do not rebuild GHC even if it is out of +-- date (can save a lot of build time when changing GHC). +needBuilder :: Bool -> Builder -> Action () +needBuilder laxDependencies builder = do + path <- builderPath builder + if laxDependencies && allowOrderOnlyDependency builder + then orderOnly [path] + else need [path] + where + allowOrderOnlyDependency :: Builder -> Bool + allowOrderOnlyDependency (Ghc _) = True + allowOrderOnlyDependency (GhcM _) = True + allowOrderOnlyDependency _ = False + -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". fixAbsolutePathOnWindows :: FilePath -> Action FilePath @@ -84,12 +99,6 @@ fixAbsolutePathOnWindows path = do else return path --- When LaxDeps flag is set ('lax-dependencies = YES' in user.config), --- dependencies on the GHC executable are turned into order-only dependencies --- to avoid needless recompilation when making changes to GHC's sources. In --- certain situations this can lead to build failures, in which case you --- should reset the flag (at least temporarily). - -- Instances for storing in the Shake database instance Binary Builder instance Hashable Builder From git at git.haskell.org Thu Oct 26 23:18:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant extension. (e384039) Message-ID: <20171026231843.DFBE83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3840397d0db313e8c22e45782e188e5c7c642dc/ghc >--------------------------------------------------------------- commit e3840397d0db313e8c22e45782e188e5c7c642dc Author: Andrey Mokhov Date: Mon Jan 5 01:08:03 2015 +0000 Remove redundant extension. >--------------------------------------------------------------- e3840397d0db313e8c22e45782e188e5c7c642dc src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index ea9980c..6bef5ba 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-} +{-# LANGUAGE FlexibleInstances #-} module Base ( module Development.Shake, From git at git.haskell.org Thu Oct 26 23:18:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move basic predicates to src/Switches.hs. (4d70a1e) Message-ID: <20171026231844.30CFD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4d70a1e6a5f3ed5353fa9d6af2daf013d1dde318/ghc >--------------------------------------------------------------- commit 4d70a1e6a5f3ed5353fa9d6af2daf013d1dde318 Author: Andrey Mokhov Date: Fri Aug 21 16:09:43 2015 +0100 Move basic predicates to src/Switches.hs. >--------------------------------------------------------------- 4d70a1e6a5f3ed5353fa9d6af2daf013d1dde318 src/Expression.hs | 40 ++++------------------------------------ src/Switches.hs | 46 +++++++++++++++++++++++++++++++++++----------- 2 files changed, 39 insertions(+), 47 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 44be38f..d51f434c 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -10,8 +10,7 @@ module Expression ( appendSub, appendSubD, filterSub, removeSub, interpret, interpretDiff, getStage, getPackage, getBuilder, getFiles, getFile, - getSources, getSource, getWay, - stage, package, builder, stagedBuilder, file, way + getSources, getSource, getWay ) where import Way @@ -30,13 +29,6 @@ import Control.Monad.Reader hiding (liftIO) -- parameters of the current build Target. type Expr a = ReaderT Target Action a --- If values of type a form a Monoid then so do computations of type Expr a: --- * the empty computation returns the identity element of the underlying type --- * two computations can be combined by combining their results -instance Monoid a => Monoid (Expr a) where - mempty = return mempty - mappend = liftM2 mappend - -- Diff a holds functions of type a -> a and is equipped with a Monoid instance. -- We could use Dual (Endo a) instead of Diff a, but the former may look scary. -- The name comes from "difference lists". @@ -105,7 +97,7 @@ p ?? (t, f) = p ? t <> notP p ? f -- A monadic version of append appendM :: Monoid a => Action a -> DiffExpr a -appendM mx = lift mx >>= append +appendM = (append =<<) . lift -- appendSub appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument @@ -185,29 +177,5 @@ getFile = do target <- ask files <- getFiles case files of - [file] -> return file - _ -> error $ "Exactly one file expected in target " ++ show target - --- Basic predicates (see Switches.hs for derived predicates) -stage :: Stage -> Predicate -stage s = liftM (s ==) getStage - -package :: Package -> Predicate -package p = liftM (p ==) getPackage - --- For unstaged builders, e.g. GhcCabal -builder :: Builder -> Predicate -builder b = liftM (b ==) getBuilder - --- For staged builders, e.g. Ghc Stage -stagedBuilder :: (Stage -> Builder) -> Predicate -stagedBuilder sb = do - stage <- getStage - builder <- getBuilder - return $ builder == sb stage - -file :: FilePattern -> Predicate -file f = liftM (any (f ?==)) getFiles - -way :: Way -> Predicate -way w = liftM (w ==) getWay + [res] -> return res + _ -> error $ "Exactly one file expected in target " ++ show target diff --git a/src/Switches.hs b/src/Switches.hs index 244c87f..c30a33f 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,15 +1,40 @@ module Switches ( + stage, package, builder, stagedBuilder, file, way, stage0, stage1, stage2, notStage, notStage0, registerPackage, splitObjects ) where +import Way +import Base import Stage +import Package +import Builder import Expression -import Settings.Util import Settings.Default import Oracles.Flag import Oracles.Setting +-- Basic predicates (see Switches.hs for derived predicates) +stage :: Stage -> Predicate +stage s = liftM (s ==) getStage + +package :: Package -> Predicate +package p = liftM (p ==) getPackage + +-- For unstaged builders, e.g. GhcCabal +builder :: Builder -> Predicate +builder b = liftM (b ==) getBuilder + +-- For staged builders, e.g. Ghc Stage +stagedBuilder :: (Stage -> Builder) -> Predicate +stagedBuilder sb = (builder . sb) =<< getStage + +file :: FilePattern -> Predicate +file f = liftM (any (f ?==)) getFiles + +way :: Way -> Predicate +way w = liftM (w ==) getWay + -- Derived predicates stage0 :: Predicate stage0 = stage Stage0 @@ -32,13 +57,12 @@ registerPackage = return True splitObjects :: Predicate splitObjects = do - stage <- getStage -- We don't split bootstrap (stage 0) packages - package <- getPackage -- We don't split compiler - broken <- getFlag SplitObjectsBroken - ghcUnreg <- getFlag GhcUnregisterised - goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] - goodOs <- lift $ targetOss [ "mingw32", "cygwin32", "linux" - , "darwin", "solaris2", "freebsd" - , "dragonfly", "netbsd", "openbsd"] - return $ stage == Stage1 && package /= compiler && not broken - && not ghcUnreg && goodArch && goodOs + goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages + goodPkg <- notP $ package compiler -- We don't split compiler + broken <- lift $ flag SplitObjectsBroken + ghcUnreg <- lift $ flag GhcUnregisterised + goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] + goodOs <- lift $ targetOss [ "mingw32", "cygwin32", "linux", "darwin" + , "solaris2", "freebsd", "dragonfly" + , "netbsd", "openbsd" ] + return $ goodStage && goodPkg && not broken && not ghcUnreg && goodArch && goodOs From git at git.haskell.org Thu Oct 26 23:18:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove splitArgs. (9133934) Message-ID: <20171026231847.4A97E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91339343449600edd26a8e427a246bee2ae63166/ghc >--------------------------------------------------------------- commit 91339343449600edd26a8e427a246bee2ae63166 Author: Andrey Mokhov Date: Tue Jan 6 19:16:50 2015 +0000 Remove splitArgs. >--------------------------------------------------------------- 91339343449600edd26a8e427a246bee2ae63166 src/Base.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 6bef5ba..9868528 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -9,7 +9,7 @@ module Base ( Stage (..), Args, arg, args, ShowAction (..), Condition (..), - joinArgs, joinArgsSpaced, splitArgs, + joinArgs, joinArgsSpaced, filterOut ) where @@ -72,8 +72,5 @@ intercalateArgs s as = do as' <- as return [intercalate s as'] -splitArgs :: Args -> Args -splitArgs = fmap (concatMap words) - filterOut :: Args -> [String] -> Args filterOut as list = filter (`notElem` list) <$> as From git at git.haskell.org Thu Oct 26 23:18:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Monoid (ReaderT Target Action a) instance to src/Target.hs. (95d2949) Message-ID: <20171026231847.A17C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95d2949e9c255d525adfcc6af61f6a7711ae5dab/ghc >--------------------------------------------------------------- commit 95d2949e9c255d525adfcc6af61f6a7711ae5dab Author: Andrey Mokhov Date: Fri Aug 21 16:10:44 2015 +0100 Move Monoid (ReaderT Target Action a) instance to src/Target.hs. >--------------------------------------------------------------- 95d2949e9c255d525adfcc6af61f6a7711ae5dab src/Target.hs | 14 ++++++++++++-- 1 file changed, 12 insertions(+), 2 deletions(-) diff --git a/src/Target.hs b/src/Target.hs index 2ce94bc..1717a87 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,6 +1,6 @@ -{-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} +{-# LANGUAGE DeriveGeneric, FlexibleInstances #-} module Target ( - Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), + Target (..), StageTarget, StagePackageTarget, FullTarget, stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay, ) where @@ -10,6 +10,8 @@ import Stage import Package import Builder import GHC.Generics +import Data.Monoid +import Control.Monad.Reader -- Target captures all parameters relevant to the current build target: -- * Stage and Package being built, @@ -28,6 +30,14 @@ data Target = Target } deriving (Show, Eq, Generic) +-- If values of type 'a' form a Monoid then we can also derive a Monoid instance +-- for values of type 'ReaderT Target Action a': +-- * the empty computation returns the identity element of the underlying type +-- * two computations can be combined by combining their results +instance Monoid a => Monoid (ReaderT Target Action a) where + mempty = return mempty + mappend = liftM2 mappend + -- StageTarget is a partially constructed Target. Only stage is guaranteed to -- be assigned. type StageTarget = Target From git at git.haskell.org Thu Oct 26 23:18:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Support multiword options. (b9c1da8) Message-ID: <20171026231851.0B2F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b9c1da83d8c87ee3f95fa25ed284ce7a12f81caa/ghc >--------------------------------------------------------------- commit b9c1da83d8c87ee3f95fa25ed284ce7a12f81caa Author: Andrey Mokhov Date: Tue Jan 6 19:18:29 2015 +0000 Support multiword options. >--------------------------------------------------------------- b9c1da83d8c87ee3f95fa25ed284ce7a12f81caa src/Oracles/Option.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 365c526..6f05a0e 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -13,7 +13,7 @@ data Option = TargetOS | TargetArch | TargetPlatformFull | HostOsCpp instance ShowAction Option where - showAction opt = showAction $ askConfig $ case opt of + showAction opt = showAction $ fmap words $ askConfig $ case opt of TargetOS -> "target-os" TargetArch -> "target-arch" TargetPlatformFull -> "target-platform-full" From git at git.haskell.org Thu Oct 26 23:18:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (bc4a11c) Message-ID: <20171026231851.7085C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc4a11c9eba6c98e82c2ed8e0f0452c101179660/ghc >--------------------------------------------------------------- commit bc4a11c9eba6c98e82c2ed8e0f0452c101179660 Author: Andrey Mokhov Date: Fri Aug 21 16:11:53 2015 +0100 Clean up. >--------------------------------------------------------------- bc4a11c9eba6c98e82c2ed8e0f0452c101179660 src/Way.hs | 12 +++++++++--- 1 file changed, 9 insertions(+), 3 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 74d1f26..a1df1ce 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,4 +1,4 @@ -module Way ( -- TODO: rename to "Way"? +module Way ( WayUnit (..), Way, wayFromUnits, wayUnit, @@ -13,7 +13,7 @@ module Way ( -- TODO: rename to "Way"? safeDetectWay, detectWay, matchBuildResult ) where -import Base +import Base hiding (unit) import Util import Oracles.Setting import Data.List @@ -74,6 +74,7 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b +vanilla, profiling, logging, parallel, granSim :: Way vanilla = wayFromUnits [] profiling = wayFromUnits [Profiling] logging = wayFromUnits [Logging] @@ -82,6 +83,11 @@ granSim = wayFromUnits [GranSim] -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? +threaded, threadedProfiling, threadedLogging, debug, debugProfiling, + threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, + threadedProfilingDynamic, threadedDynamic, threadedDebugDynamic, + debugDynamic, loggingDynamic, threadedLoggingDynamic :: Way + threaded = wayFromUnits [Threaded] threadedProfiling = wayFromUnits [Threaded, Profiling] threadedLogging = wayFromUnits [Threaded, Logging] @@ -102,7 +108,7 @@ wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" -hisuf, osuf, hcsuf, obootsuf, ssuf :: Way -> String +osuf, ssuf, hisuf, hcsuf, obootsuf, hibootsuf :: Way -> String osuf = (++ "o" ) . wayPrefix ssuf = (++ "s" ) . wayPrefix hisuf = (++ "hi" ) . wayPrefix From git at git.haskell.org Thu Oct 26 23:18:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle multiword options in build rules. (1a7b657) Message-ID: <20171026231854.657F23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a7b657a0b02d361a5ba69f1c68d772e43b3e47b/ghc >--------------------------------------------------------------- commit 1a7b657a0b02d361a5ba69f1c68d772e43b3e47b Author: Andrey Mokhov Date: Tue Jan 6 19:19:10 2015 +0000 Handle multiword options in build rules. >--------------------------------------------------------------- 1a7b657a0b02d361a5ba69f1c68d772e43b3e47b src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index fe3ec26..b156eaa 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -21,8 +21,8 @@ configureArgs stage settings = argConf key as = joinArgs "--configure-option=" key "=" as argConfWith key opt = do - [value] <- showAction opt - when (value /= "") $ argConf ("--with-" ++ key) $ arg value + opts <- showAction opt + when (opts /= []) $ argConf ("--with-" ++ key) $ arg opts cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) (ConfCcArgs stage) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 4327ca6..ede14bb 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -81,7 +81,7 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = run (Ghc stage) $ mconcat [ arg "-M" , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - , splitArgs $ arg SrcHcOpts -- TODO: get rid of splitArgs + , arg SrcHcOpts -- TODO: get rid of splitArgs , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" , arg $ if usePackageKey then "-this-package-key" else "-package-name" , arg packageKey -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) From git at git.haskell.org Thu Oct 26 23:18:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop integerGmp2 and clean up. (efe9d6f) Message-ID: <20171026231854.DA0053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efe9d6fa2c26d2befc6dcd97eadef5474f94c6e7/ghc >--------------------------------------------------------------- commit efe9d6fa2c26d2befc6dcd97eadef5474f94c6e7 Author: Andrey Mokhov Date: Fri Aug 21 16:12:27 2015 +0100 Drop integerGmp2 and clean up. >--------------------------------------------------------------- efe9d6fa2c26d2befc6dcd97eadef5474f94c6e7 src/Settings/Default.hs | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 5a021e7..71698da 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -3,8 +3,8 @@ module Settings.Default ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, - integerGmp2, integerSimple, parallel, pretty, primitive, process, stm, - templateHaskell, terminfo, time, transformers, unix, win32, xhtml + integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, + terminfo, time, transformers, unix, win32, xhtml ) where import Stage @@ -29,12 +29,16 @@ defaultTargetDirectory stage package defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghcPrim, haskeline - , hoopl, hpc, integerGmp, integerGmp2, integerSimple, parallel - , pretty, primitive, process, stm, templateHaskell, terminfo, time - , transformers, unix, win32, xhtml ] + , containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc + , integerGmp, integerSimple, parallel, pretty, primitive, process, stm + , templateHaskell, terminfo, time, transformers, unix, win32, xhtml ] -- Package definitions +array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, + deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, + integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, + terminfo, time, transformers, unix, win32, xhtml :: Package + array = library "array" base = library "base" binPackageDb = library "bin-package-db" @@ -51,7 +55,6 @@ haskeline = library "haskeline" hoopl = library "hoopl" hpc = library "hpc" integerGmp = library "integer-gmp" -integerGmp2 = library "integer-gmp" `setPath` "libraries/integer-gmp2" integerSimple = library "integer-simple" parallel = library "parallel" pretty = library "pretty" From git at git.haskell.org Thu Oct 26 23:18:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Ensure that intercalateArgs _ mempty = mempty. (9a24f38) Message-ID: <20171026231858.0B97E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a24f3876e945b6927fb0df1da0b373c3c87cba2/ghc >--------------------------------------------------------------- commit 9a24f3876e945b6927fb0df1da0b373c3c87cba2 Author: Andrey Mokhov Date: Wed Jan 7 01:16:43 2015 +0000 Ensure that intercalateArgs _ mempty = mempty. >--------------------------------------------------------------- 9a24f3876e945b6927fb0df1da0b373c3c87cba2 src/Base.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 9868528..8a98a7b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -70,7 +70,9 @@ joinArgsSpaced = collect (\x y -> intercalateArgs " " $ x <> y) mempty intercalateArgs :: String -> Args -> Args intercalateArgs s as = do as' <- as - return [intercalate s as'] + case as' of + [] -> mempty + otherwise -> return [intercalate s as'] filterOut :: Args -> [String] -> Args filterOut as list = filter (`notElem` list) <$> as From git at git.haskell.org Thu Oct 26 23:18:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:18:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, fix -Wall warnings. (4238fb7) Message-ID: <20171026231858.905E73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4238fb77e4db131ddb1cb938a76f0dbe2b03a798/ghc >--------------------------------------------------------------- commit 4238fb77e4db131ddb1cb938a76f0dbe2b03a798 Author: Andrey Mokhov Date: Fri Aug 21 16:28:03 2015 +0100 Clean up, fix -Wall warnings. >--------------------------------------------------------------- 4238fb77e4db131ddb1cb938a76f0dbe2b03a798 src/Main.hs | 1 + src/Oracles/ArgsHash.hs | 4 +-- src/Oracles/Base.hs | 2 +- src/Oracles/Dependencies.hs | 2 +- src/Oracles/Flag.hs | 5 +-- src/Oracles/PackageDeps.hs | 2 +- src/Oracles/WindowsRoot.hs | 2 +- src/Package.hs | 6 ++-- src/Rules.hs | 14 ++++---- src/Rules/Actions.hs | 15 ++++---- src/Rules/Cabal.hs | 24 ++++++------- src/Rules/Config.hs | 5 +-- src/Rules/Data.hs | 22 ++++++------ src/Rules/Dependencies.hs | 6 ++-- src/Rules/Documentation.hs | 17 +++++---- src/Rules/Resources.hs | 7 ++-- src/Settings/Builders/Ar.hs | 1 + src/Settings/Builders/Gcc.hs | 27 +++++++------- src/Settings/Builders/Ghc.hs | 14 ++++---- src/Settings/Builders/GhcCabal.hs | 40 +++++++++++---------- src/Settings/Builders/Haddock.hs | 5 +-- src/Settings/Builders/Ld.hs | 12 +++---- src/Settings/TargetDirectory.hs | 6 ++-- src/Settings/User.hs | 7 +++- src/Settings/Util.hs | 74 +++++++++++++++------------------------ src/Settings/Ways.hs | 17 +++------ src/Util.hs | 18 +++++----- 27 files changed, 162 insertions(+), 193 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4238fb77e4db131ddb1cb938a76f0dbe2b03a798 From git at git.haskell.org Thu Oct 26 23:19:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove argConfWith which became redundant. (86b63df) Message-ID: <20171026231901.9C5A93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86b63df1d036247dc78af9ec2eccb7886d0e9503/ghc >--------------------------------------------------------------- commit 86b63df1d036247dc78af9ec2eccb7886d0e9503 Author: Andrey Mokhov Date: Wed Jan 7 01:18:33 2015 +0000 Remove argConfWith which became redundant. >--------------------------------------------------------------- 86b63df1d036247dc78af9ec2eccb7886d0e9503 src/Package/Base.hs | 2 +- src/Package/Data.hs | 18 +++++++----------- 2 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 896bcb3..a895f5f 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -65,7 +65,7 @@ commonCcWarninigArgs :: Args commonCcWarninigArgs = when Validating $ when GccIsClang (arg "-Wno-unknown-pragmas") <> when (not GccIsClang && not GccLt46) (arg "-Wno-error=inline") - <> when ( GccIsClang && not GccLt46 && windowsHost) (arg "-Werror=unused-but-set-variable" ) + <> when ( GccIsClang && not GccLt46 && windowsHost) (arg "-Werror=unused-but-set-variable") bootPkgConstraints :: Args bootPkgConstraints = mempty diff --git a/src/Package/Data.hs b/src/Package/Data.hs index b156eaa..0fa1322 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -18,11 +18,7 @@ libraryArgs ways = configureArgs :: Stage -> Settings -> Args configureArgs stage settings = let argConf :: String -> Args -> Args - argConf key as = joinArgs "--configure-option=" key "=" as - - argConfWith key opt = do - opts <- showAction opt - when (opts /= []) $ argConf ("--with-" ++ key) $ arg opts + argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" as cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) (ConfCcArgs stage) @@ -36,10 +32,10 @@ configureArgs stage settings = , argConf "LDFLAGS" ldflags , argConf "CPPFLAGS" cppflags , joinArgs "--gcc-options=" cflags " " ldflags - , argConfWith "iconv-includes" IconvIncludeDirs - , argConfWith "iconv-libraries" IconvLibDirs - , argConfWith "gmp-includes" GmpIncludeDirs - , argConfWith "gmp-libraries" GmpLibDirs + , argConf "--with-iconv-includes" $ arg IconvIncludeDirs + , argConf "--with-iconv-libraries" $ arg IconvLibDirs + , argConf "--with-gmp-includes" $ arg GmpIncludeDirs + , argConf "--with-gmp-libraries" $ arg GmpLibDirs , when CrossCompiling $ argConf "--host" $ arg TargetPlatformFull -- TODO: why not host? , argConf "--with-cc" $ arg Gcc ] @@ -66,8 +62,8 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = [ args "configure" path dist -- this is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument - -- * if there are many, we must collapse them into one string argument - , joinArgsSpaced $ customDllArgs settings + -- * if there are many, we must collapse them into one space-separated string + , joinArgsSpaced "" (customDllArgs settings) , with $ Ghc stage -- TODO: used to be stage01 (using max Stage1 GHC) , with $ GhcPkg stage From git at git.haskell.org Thu Oct 26 23:19:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop DepKeys, add DepId, clean up code. (49574e6) Message-ID: <20171026231902.4E5BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49574e62cd65023a3d4c6c145bbac86c16c73d69/ghc >--------------------------------------------------------------- commit 49574e62cd65023a3d4c6c145bbac86c16c73d69 Author: Andrey Mokhov Date: Fri Aug 21 16:29:01 2015 +0100 Drop DepKeys, add DepId, clean up code. >--------------------------------------------------------------- 49574e62cd65023a3d4c6c145bbac86c16c73d69 src/Oracles/PackageData.hs | 74 +++++++++++++++++++--------------------------- 1 file changed, 31 insertions(+), 43 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 4097ac1..c873601 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -8,7 +8,6 @@ module Oracles.PackageData ( import Base import Util import Data.List -import Data.Maybe import Control.Applicative import qualified Data.HashMap.Strict as Map @@ -22,6 +21,7 @@ import qualified Data.HashMap.Strict as Map -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] data PackageData = Version FilePath | PackageKey FilePath + | LibName FilePath | Synopsis FilePath | BuildGhciLib FilePath @@ -30,7 +30,7 @@ data PackageDataList = Modules FilePath | SrcDirs FilePath | IncludeDirs FilePath | Deps FilePath - | DepKeys FilePath + | DepIds FilePath | DepNames FilePath | CppArgs FilePath | HsArgs FilePath @@ -41,59 +41,47 @@ data PackageDataList = Modules FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) --- TODO: is this needed? askPackageData :: FilePath -> String -> Action String askPackageData path key = do let fullKey = replaceSeparators '_' $ path ++ "_" ++ key - pkgData = path -/- "package-data.mk" - value <- askOracle $ PackageDataKey (pkgData, fullKey) - return $ fromMaybe - (error $ "No key '" ++ key ++ "' in " ++ pkgData ++ ".") value + file = path -/- "package-data.mk" + maybeValue <- askOracle $ PackageDataKey (file, fullKey) + case maybeValue of + Nothing -> putError $ "No key '" ++ key ++ "' in " ++ file ++ "." + Just value -> return value pkgData :: PackageData -> Action String -pkgData packageData = do - let (key, path) = case packageData of - Version path -> ("VERSION" , path) - PackageKey path -> ("PACKAGE_KEY" , path) - Synopsis path -> ("SYNOPSIS" , path) - BuildGhciLib path -> ("BUILD_GHCI_LIB", path) - fullKey = replaceSeparators '_' $ path ++ "_" ++ key - pkgData = path -/- "package-data.mk" - res <- askOracle $ PackageDataKey (pkgData, fullKey) - return $ fromMaybe - (error $ "No key '" ++ key ++ "' in " ++ pkgData ++ ".") res +pkgData packageData = case packageData of + Version path -> askPackageData path "VERSION" + PackageKey path -> askPackageData path "PACKAGE_KEY" + LibName path -> askPackageData path "LIB_NAME" + Synopsis path -> askPackageData path "SYNOPSIS" + BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" pkgDataList :: PackageDataList -> Action [String] -pkgDataList packageData = do - let (key, path, defaultValue) = case packageData of - Modules path -> ("MODULES" , path, "" ) - HiddenModules path -> ("HIDDEN_MODULES" , path, "" ) - SrcDirs path -> ("HS_SRC_DIRS" , path, ".") - IncludeDirs path -> ("INCLUDE_DIRS" , path, ".") - Deps path -> ("DEPS" , path, "" ) - DepKeys path -> ("DEP_KEYS" , path, "" ) - DepNames path -> ("DEP_NAMES" , path, "" ) - CppArgs path -> ("CPP_OPTS" , path, "" ) - HsArgs path -> ("HC_OPTS" , path, "" ) - CcArgs path -> ("CC_OPTS" , path, "" ) - CSrcs path -> ("C_SRCS" , path, "" ) - DepIncludeDirs path -> ("DEP_INCLUDE_DIRS_SINGLE_QUOTED", path, "" ) - fullKey = replaceSeparators '_' $ path ++ "_" ++ key - pkgData = path -/- "package-data.mk" - unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') - res <- askOracle $ PackageDataKey (pkgData, fullKey) - return $ map unquote $ words $ case res of - Nothing -> error $ "No key '" ++ key ++ "' in " ++ pkgData ++ "." - Just "" -> defaultValue - Just value -> value +pkgDataList packageData = fmap (map unquote . words) $ case packageData of + Modules path -> askPackageData path "MODULES" + HiddenModules path -> askPackageData path "HIDDEN_MODULES" + SrcDirs path -> askPackageData path "HS_SRC_DIRS" + IncludeDirs path -> askPackageData path "INCLUDE_DIRS" + Deps path -> askPackageData path "DEPS" + DepIds path -> askPackageData path "DEP_IPIDS" + DepNames path -> askPackageData path "DEP_NAMES" + CppArgs path -> askPackageData path "CPP_OPTS" + HsArgs path -> askPackageData path "HC_OPTS" + CcArgs path -> askPackageData path "CC_OPTS" + CSrcs path -> askPackageData path "C_SRCS" + DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" + where + unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') -- Oracle for 'package-data.mk' files packageDataOracle :: Rules () packageDataOracle = do - pkgData <- newCache $ \file -> do + pkgDataContents <- newCache $ \file -> do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> - Map.lookup key <$> pkgData (unifyPath file) + _ <- addOracle $ \(PackageDataKey (file, key)) -> + Map.lookup key <$> pkgDataContents file return () From git at git.haskell.org Thu Oct 26 23:19:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add instance ShowAction PackageData. (7792b9a) Message-ID: <20171026231905.40E613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7792b9a32bbc24e3d3a0fb04f534e7c293ac9ea2/ghc >--------------------------------------------------------------- commit 7792b9a32bbc24e3d3a0fb04f534e7c293ac9ea2 Author: Andrey Mokhov Date: Wed Jan 7 16:30:30 2015 +0000 Add instance ShowAction PackageData. >--------------------------------------------------------------- 7792b9a32bbc24e3d3a0fb04f534e7c293ac9ea2 src/Oracles/PackageData.hs | 37 +++++++++++++++++++------------------ 1 file changed, 19 insertions(+), 18 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 831fec9..2af8e21 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -2,7 +2,7 @@ module Oracles.PackageData ( PackageDataPair (..), - packagaDataOption, PackageDataKey (..) + PackageData (..) ) where import Development.Shake.Classes @@ -12,26 +12,27 @@ import Util newtype PackageDataPair = PackageDataPair (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -packagaDataOptionWithDefault :: FilePath -> String -> Action String -> Action String -packagaDataOptionWithDefault file key defaultAction = do +packagaDataWithDefault :: FilePath -> String -> Action String -> Action String +packagaDataWithDefault file key defaultAction = do maybeValue <- askOracle $ PackageDataPair (file, key) case maybeValue of Just value -> return value Nothing -> defaultAction -data PackageDataKey = Modules | SrcDirs | PackageKey | IncludeDirs | Deps | DepKeys - deriving Show +data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath + | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath + deriving Show -packagaDataOption :: FilePath -> PackageDataKey -> Action String -packagaDataOption file key = do - let (keyName, ifEmpty) = case key of - Modules -> ("MODULES" , "" ) - SrcDirs -> ("HS_SRC_DIRS" , ".") - PackageKey -> ("PACKAGE_KEY" , "" ) - IncludeDirs -> ("INCLUDE_DIRS", ".") - Deps -> ("DEPS" , "" ) - DepKeys -> ("DEP_KEYS" , "" ) - keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName - res <- packagaDataOptionWithDefault file keyFullName $ - error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." - return $ if res == "" then ifEmpty else res +instance ShowAction PackageData where + showAction key = do + let (keyName, file, ifEmpty) = case key of + Modules file -> ("MODULES" , file, "" ) + SrcDirs file -> ("HS_SRC_DIRS" , file, ".") + PackageKey file -> ("PACKAGE_KEY" , file, "" ) + IncludeDirs file -> ("INCLUDE_DIRS", file, ".") + Deps file -> ("DEPS" , file, "" ) + DepKeys file -> ("DEP_KEYS" , file, "" ) + keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName + res <- packagaDataWithDefault file keyFullName $ + error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." + return $ words $ if res == "" then ifEmpty else res From git at git.haskell.org Thu Oct 26 23:19:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove parallel, stm, random, primitive, vector and dph from Stage1 packages, drop integerGmp2 support. (228da6f) Message-ID: <20171026231905.D1E153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/228da6fe168616b0aeca8d462eab345cef5b7e48/ghc >--------------------------------------------------------------- commit 228da6fe168616b0aeca8d462eab345cef5b7e48 Author: Andrey Mokhov Date: Fri Aug 21 16:30:17 2015 +0100 Remove parallel, stm, random, primitive, vector and dph from Stage1 packages, drop integerGmp2 support. >--------------------------------------------------------------- 228da6fe168616b0aeca8d462eab345cef5b7e48 src/Settings/Packages.hs | 11 ++++------- 1 file changed, 4 insertions(+), 7 deletions(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 369879c..5820e0c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -29,12 +29,13 @@ packagesStage0 = mconcat [ append [binPackageDb, binary, cabal, compiler, hoopl, hpc, transformers] , notWindowsHost ? notTargetOs "ios" ? append [terminfo] ] +-- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory - , filepath, ghcPrim, haskeline, integerLibrary, parallel - , pretty, primitive, process, stm, templateHaskell, time ] + , filepath, ghcPrim, haskeline, integerLibrary, pretty, process + , templateHaskell, time ] , windowsHost ? append [win32] , notWindowsHost ? append [unix] , buildHaddock ? append [xhtml] ] @@ -43,9 +44,5 @@ knownPackages :: [Package] knownPackages = defaultKnownPackages ++ userKnownPackages -- Note: this is slow but we keep it simple as there not too many packages (30) --- We handle integerLibrary in a special way, because packages integerGmp and --- integerGmp2 have the same package name -- we return the user-selected one. findKnownPackage :: PackageName -> Maybe Package -findKnownPackage name - | name == pkgName integerLibrary = Just integerLibrary - | otherwise = find (\pkg -> pkgName pkg == name) knownPackages +findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Thu Oct 26 23:19:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code. (f79678a) Message-ID: <20171026231908.C347B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f79678a93094e3f6512044bd9f65179ae3f9b12c/ghc >--------------------------------------------------------------- commit f79678a93094e3f6512044bd9f65179ae3f9b12c Author: Andrey Mokhov Date: Wed Jan 7 16:31:30 2015 +0000 Clean up code. >--------------------------------------------------------------- f79678a93094e3f6512044bd9f65179ae3f9b12c src/Package/Data.hs | 3 +-- src/Package/Dependencies.hs | 24 +++++++++--------------- 2 files changed, 10 insertions(+), 17 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 0fa1322..de617f4 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -17,8 +17,7 @@ libraryArgs ways = configureArgs :: Stage -> Settings -> Args configureArgs stage settings = - let argConf :: String -> Args -> Args - argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" as + let argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" (as :: Args) cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) (ConfCcArgs stage) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index ede14bb..ad6705d 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -69,22 +69,16 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file let pkgData = buildDir "package-data.mk" usePackageKey <- SupportsPackageKey || stage /= Stage0 -- TODO: check reasoning (distdir-way-opts) - [mods, srcDirs, includeDirs, deps, depKeys] <- - mapM ((fmap words) . (packagaDataOption pkgData)) - [Modules, SrcDirs, IncludeDirs, Deps, DepKeys] - srcs <- getDirectoryFiles "" $ do - dir <- srcDirs - modPath <- map (replaceEq '.' pathSeparator) mods - extension <- ["hs", "lhs"] - return $ path dir modPath <.> extension - packageKey <- packagaDataOption pkgData PackageKey + mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) + srcDirs <- arg $ SrcDirs pkgData + srcs <- getDirectoryFiles "" $ [path dir mPath <.> ext | dir <- srcDirs, mPath <- mods, ext <- ["hs", "lhs"]] run (Ghc stage) $ mconcat [ arg "-M" , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - , arg SrcHcOpts -- TODO: get rid of splitArgs + , arg SrcHcOpts , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" , arg $ if usePackageKey then "-this-package-key" else "-package-name" - , arg packageKey -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg $ PackageKey pkgData -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) , arg "-hide-all-packages" , arg "-i" -- resets the search path to nothing; TODO: check if really needed , arg $ map (\d -> "-i" ++ path d) srcDirs @@ -92,13 +86,13 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = prefix <- ["-i", "-I"] -- 'import' and '#include' search paths suffix <- ["build", "build/autogen"] return $ prefix ++ buildDir suffix - , arg $ map (\d -> "-I" ++ path d) $ filter isRelative includeDirs - , arg $ map (\d -> "-I" ++ d) $ filter isAbsolute includeDirs + , map (\d -> "-I" ++ path d) <$> filter isRelative <$> arg (IncludeDirs pkgData) + , map (\d -> "-I" ++ d) <$> filter isAbsolute <$> arg (IncludeDirs pkgData) , arg "-optP-include" , arg $ "-optP" ++ buildDir "build/autogen/cabal_macros.h" , if usePackageKey - then arg $ concatMap (\d -> ["-package-key", d]) depKeys - else arg $ concatMap (\d -> ["-package" , d]) deps + then map ("-package-key " ++) <$> arg (DepKeys pkgData) + else map ("-package " ++) <$> arg (Deps pkgData) , args "-dep-makefile" out "-dep-suffix" "" "-include-pkg-deps" , arg $ map normalise srcs ] From git at git.haskell.org Thu Oct 26 23:19:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add PartialTarget, handle GHC.Prim module in a special way. (aabc5a6) Message-ID: <20171026231909.66BF83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aabc5a6ef5968dd14eb67c5cce6d50257c1288ae/ghc >--------------------------------------------------------------- commit aabc5a6ef5968dd14eb67c5cce6d50257c1288ae Author: Andrey Mokhov Date: Fri Aug 21 22:14:48 2015 +0100 Add PartialTarget, handle GHC.Prim module in a special way. >--------------------------------------------------------------- aabc5a6ef5968dd14eb67c5cce6d50257c1288ae src/Expression.hs | 47 ++++++++++++++++++++-------------- src/Oracles/ArgsHash.hs | 2 +- src/Rules.hs | 19 +++++++------- src/Rules/Actions.hs | 11 ++++---- src/Rules/Cabal.hs | 4 +-- src/Rules/Compile.hs | 11 +++----- src/Rules/Data.hs | 14 +++++------ src/Rules/Dependencies.hs | 12 ++++----- src/Rules/Documentation.hs | 14 +++++------ src/Rules/Library.hs | 39 +++++++++++++++------------- src/Rules/Package.hs | 3 ++- src/Target.hs | 63 ++++++++++++++++------------------------------ 12 files changed, 112 insertions(+), 127 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 aabc5a6ef5968dd14eb67c5cce6d50257c1288ae From git at git.haskell.org Thu Oct 26 23:19:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify PackageData. (2f9338d) Message-ID: <20171026231912.346D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f9338d4d263435155047a69b5c802c5f76beba1/ghc >--------------------------------------------------------------- commit 2f9338d4d263435155047a69b5c802c5f76beba1 Author: Andrey Mokhov Date: Wed Jan 7 16:46:10 2015 +0000 Simplify PackageData. >--------------------------------------------------------------- 2f9338d4d263435155047a69b5c802c5f76beba1 src/Oracles.hs | 2 +- src/Oracles/PackageData.hs | 20 +++++++------------- 2 files changed, 8 insertions(+), 14 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 093f1b8..3321610 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -43,5 +43,5 @@ oracleRules = do need [file] liftIO $ readConfigFile file - addOracle $ \(PackageDataPair (file, key)) -> M.lookup key <$> pkgData file + addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 2af8e21..4ec89d7 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( - PackageDataPair (..), + PackageDataKey (..), PackageData (..) ) where @@ -9,19 +9,11 @@ import Development.Shake.Classes import Base import Util -newtype PackageDataPair = PackageDataPair (FilePath, String) +newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -packagaDataWithDefault :: FilePath -> String -> Action String -> Action String -packagaDataWithDefault file key defaultAction = do - maybeValue <- askOracle $ PackageDataPair (file, key) - case maybeValue of - Just value -> return value - Nothing -> defaultAction - data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath - deriving Show instance ShowAction PackageData where showAction key = do @@ -33,6 +25,8 @@ instance ShowAction PackageData where Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName - res <- packagaDataWithDefault file keyFullName $ - error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." - return $ words $ if res == "" then ifEmpty else res + res <- askOracle $ PackageDataKey (file, keyFullName) + return $ words $ case res of + Nothing -> error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." + Just "" -> ifEmpty + Just value -> value From git at git.haskell.org Thu Oct 26 23:19:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Switches.hs to Predicates.hs. (47764c0) Message-ID: <20171026231912.D84C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47764c0eaedab75e54c0209ef117ddb0280d05b2/ghc >--------------------------------------------------------------- commit 47764c0eaedab75e54c0209ef117ddb0280d05b2 Author: Andrey Mokhov Date: Fri Aug 21 22:23:05 2015 +0100 Rename Switches.hs to Predicates.hs. >--------------------------------------------------------------- 47764c0eaedab75e54c0209ef117ddb0280d05b2 src/{Switches.hs => Predicates.hs} | 2 +- src/Rules/Data.hs | 2 +- src/Rules/Library.hs | 2 +- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Gcc.hs | 2 +- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Builders/Ld.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/User.hs | 2 +- src/Settings/Util.hs | 2 +- src/Settings/Ways.hs | 2 +- 14 files changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Switches.hs b/src/Predicates.hs similarity index 98% rename from src/Switches.hs rename to src/Predicates.hs index c30a33f..0dfa8db 100644 --- a/src/Switches.hs +++ b/src/Predicates.hs @@ -1,4 +1,4 @@ -module Switches ( +module Predicates ( stage, package, builder, stagedBuilder, file, way, stage0, stage1, stage2, notStage, notStage0, registerPackage, splitObjects diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index e64938f..d481a67 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -5,8 +5,8 @@ import Util import Target (PartialTarget (..), fullTarget) import Package import Builder -import Switches (registerPackage) import Expression +import Predicates (registerPackage) import Oracles.PackageDeps import Settings.Packages import Settings.TargetDirectory diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 4f5e787..4ff15c3 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -6,8 +6,8 @@ import Util import Target (PartialTarget (..), fullTarget) import Builder import Package -import Switches (splitObjects) import Expression +import Predicates (splitObjects) import Oracles.PackageData import Settings.Util import Settings.TargetDirectory diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index ec8b6ac..4bde3f8 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,8 +1,8 @@ module Settings.Builders.Ar (arArgs, arPersistentArgsCount) where import Builder -import Switches (builder) import Expression +import Predicates (builder) import Settings.Util arArgs :: Args diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index 748e544..20867f7 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -3,8 +3,8 @@ module Settings.Builders.Gcc (gccArgs, gccMArgs) where import Base import Util import Builder -import Switches (stagedBuilder) import Expression +import Predicates (stagedBuilder) import Oracles.PackageData import Settings.Util diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index af20c7a..e48be86 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -4,8 +4,8 @@ import Way import Util import Stage import Builder -import Switches (stagedBuilder, splitObjects, stage0) import Expression +import Predicates (stagedBuilder, splitObjects, stage0) import Oracles.Flag import Oracles.PackageData import Settings.Util diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 623110b..4862e9f 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -9,8 +9,8 @@ import Util import Stage import Builder import Package -import Switches import Expression +import Predicates import Oracles.Flag import Oracles.Setting import Settings.User diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index b2bab83..64981c6 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -2,8 +2,8 @@ module Settings.Builders.GhcPkg (ghcPkgArgs) where import Util import Builder -import Switches import Expression +import Predicates import Settings.Util import Settings.Builders.GhcCabal diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 94a1669..19c1979 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -4,8 +4,8 @@ import Base import Util import Builder import Package -import Switches (builder, package, stage1) import Expression +import Predicates (builder, package, stage1) import Oracles.PackageData import Settings.Util import Settings.Packages diff --git a/src/Settings/Builders/Ld.hs b/src/Settings/Builders/Ld.hs index e21a262..6a17ca7 100644 --- a/src/Settings/Builders/Ld.hs +++ b/src/Settings/Builders/Ld.hs @@ -1,8 +1,8 @@ module Settings.Builders.Ld (ldArgs) where import Builder -import Switches (builder) import Expression +import Predicates (builder) import Oracles.Setting import Settings.Util diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 5820e0c..b84bb5b 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -4,8 +4,8 @@ module Settings.Packages ( ) where import Package -import Switches import Expression +import Predicates import Oracles.Setting import Settings.User import Settings.Default diff --git a/src/Settings/User.hs b/src/Settings/User.hs index e67afc3..cdf2840 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -7,8 +7,8 @@ module Settings.User ( import Stage import Package -import Switches import Expression +import Predicates import Settings.Default -- No user-specific settings by default diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 81b7b69..1ab4308 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -13,8 +13,8 @@ import Util import Stage import Builder import Package -import Switches import Expression +import Predicates import Oracles.Flag import Oracles.Setting import Oracles.PackageData diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index d6e541e..183068a 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -2,8 +2,8 @@ module Settings.Ways (getWays, getRtsWays) where import Way import Stage -import Switches import Expression +import Predicates import Oracles.Flag import Settings.User From git at git.haskell.org Thu Oct 26 23:19:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generalise and export suffix :: Way -> String. (1ef6a04) Message-ID: <20171026231915.A5E5D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ef6a045ba067a1f07b4517f11e7bfd2aa066e6e/ghc >--------------------------------------------------------------- commit 1ef6a045ba067a1f07b4517f11e7bfd2aa066e6e Author: Andrey Mokhov Date: Wed Jan 7 17:44:04 2015 +0000 Generalise and export suffix :: Way -> String. >--------------------------------------------------------------- 1ef6a045ba067a1f07b4517f11e7bfd2aa066e6e src/Ways.hs | 19 ++++++++----------- 1 file changed, 8 insertions(+), 11 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 0a4284a..3e7c483 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -13,6 +13,7 @@ module Ways ( loggingDynamic, threadedLoggingDynamic, wayHcOpts, + suffix, hisuf, osuf, hcsuf ) where @@ -84,15 +85,11 @@ wayHcOpts (Way _ _ units) = , when (units == [Debug] || units == [Debug, Dynamic]) $ arg ["-ticky", "-DTICKY_TICKY"] ] --- TODO: cover other cases -suffix :: FilePath -> Way -> FilePath -suffix base (Way _ _ units) = - concat $ - ["p_" | Profiling `elem` units] ++ - ["dyn_" | Dynamic `elem` units] ++ - [base ] +suffix :: Way -> String +suffix way | way == vanilla = "" + | otherwise = tag way ++ "_" -hisuf, osuf, hcsuf :: Way -> FilePath -hisuf = suffix "hi" -osuf = suffix "o" -hcsuf = suffix "hc" +hisuf, osuf, hcsuf :: Way -> String +hisuf = (++ "hi") . suffix +osuf = (++ "o" ) . suffix +hcsuf = (++ "hc") . suffix From git at git.haskell.org Thu Oct 26 23:19:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix infinite loop bug in chunksOfSize. (1d27a44) Message-ID: <20171026231916.5D9BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1d27a444cc91ce912bbff440507170cc14729961/ghc >--------------------------------------------------------------- commit 1d27a444cc91ce912bbff440507170cc14729961 Author: Andrey Mokhov Date: Fri Aug 21 23:39:06 2015 +0100 Fix infinite loop bug in chunksOfSize. >--------------------------------------------------------------- 1d27a444cc91ce912bbff440507170cc14729961 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index b39fc6c..51b5ccb 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -49,7 +49,7 @@ chunksOfSize size strings = reverse chunk : chunksOfSize size rest (chunk, rest) = go [] 0 strings go res _ [] = (res, []) go res chunkSize (s:ss) = - if newSize > size then (chunk, s:ss) else go (s:res) newSize ss + if newSize > size then (res, s:ss) else go (s:res) newSize ss where newSize = chunkSize + length s From git at git.haskell.org Thu Oct 26 23:19:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle multiple way suffices. (2549740) Message-ID: <20171026231919.49FAF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/254974086689e362b394084f066d14afba9c50be/ghc >--------------------------------------------------------------- commit 254974086689e362b394084f066d14afba9c50be Author: Andrey Mokhov Date: Wed Jan 7 17:44:48 2015 +0000 Handle multiple way suffices. >--------------------------------------------------------------- 254974086689e362b394084f066d14afba9c50be src/Package/Dependencies.hs | 14 +++++++++----- 1 file changed, 9 insertions(+), 5 deletions(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index ad6705d..b3e013f 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -55,7 +55,6 @@ import Package.Base -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) --- TODO: make sure SrcDirs ($1_$2_HS_SRC_DIRS) is not empty ('.' by default) -- TODO: add $1_HC_OPTS -- TODO: check that the package is not a program ($1_$2_PROG == "") -- TODO: handle empty $1_PACKAGE (can it be empty?) @@ -77,8 +76,9 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? , arg SrcHcOpts , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" + -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) , arg $ if usePackageKey then "-this-package-key" else "-package-name" - , arg $ PackageKey pkgData -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg $ PackageKey pkgData , arg "-hide-all-packages" , arg "-i" -- resets the search path to nothing; TODO: check if really needed , arg $ map (\d -> "-i" ++ path d) srcDirs @@ -88,12 +88,16 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = return $ prefix ++ buildDir suffix , map (\d -> "-I" ++ path d) <$> filter isRelative <$> arg (IncludeDirs pkgData) , map (\d -> "-I" ++ d) <$> filter isAbsolute <$> arg (IncludeDirs pkgData) - , arg "-optP-include" - , arg $ "-optP" ++ buildDir "build/autogen/cabal_macros.h" + , args "-optP-include" ("-optP" ++ buildDir "build/autogen/cabal_macros.h") , if usePackageKey then map ("-package-key " ++) <$> arg (DepKeys pkgData) else map ("-package " ++) <$> arg (Deps pkgData) - , args "-dep-makefile" out "-dep-suffix" "" "-include-pkg-deps" + , arg "-no-user-package-db" + , args "-odir" (buildDir "build") + , args "-stubdir" (buildDir "build") + , joinArgsSpaced "-dep-makefile" out + , concatMap (\w -> ["-dep-suffix", suffix w]) <$> ways settings + , arg "-include-pkg-deps" , arg $ map normalise srcs ] From git at git.haskell.org Thu Oct 26 23:19:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement interestingInfo for Haddock. (c6b59ef) Message-ID: <20171026231920.024D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6b59ef5c98617955b4c4c98742cc99b68371fd6/ghc >--------------------------------------------------------------- commit c6b59ef5c98617955b4c4c98742cc99b68371fd6 Author: Andrey Mokhov Date: Fri Aug 21 23:39:40 2015 +0100 Implement interestingInfo for Haddock. >--------------------------------------------------------------- c6b59ef5c98617955b4c4c98742cc99b68371fd6 src/Rules/Actions.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d73c6a7..e58669a 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -50,6 +50,7 @@ interestingInfo builder ss = case builder of Ghc _ -> prefixAndSuffix 0 4 ss GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss + Haddock -> prefixAndSuffix 1 0 ss GhcCabal -> prefixAndSuffix 3 0 ss _ -> ss where From git at git.haskell.org Thu Oct 26 23:19:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor src/Base.hs. (06fd336) Message-ID: <20171026231922.F1CDA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/06fd336d441e3a42b3056185ef40742404ec856d/ghc >--------------------------------------------------------------- commit 06fd336d441e3a42b3056185ef40742404ec856d Author: Andrey Mokhov Date: Fri Jan 9 17:07:04 2015 +0000 Refactor src/Base.hs. * Get rid of polyvariadic function for better readability and robustnes. * Eliminate joinArgs and joinArgsSpaced functions. Users are encouraged to use 'unwords <$>' and 'concat <$>' instead. * Generalise filterOut function. * Rename ShowAction to ShowArgs. >--------------------------------------------------------------- 06fd336d441e3a42b3056185ef40742404ec856d src/Base.hs | 65 +++++++++++++++++++++---------------------------------------- 1 file changed, 22 insertions(+), 43 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 8a98a7b..ce2714e 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,9 +7,9 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, args, ShowAction (..), + Args, arg, ShowArgs (..), Condition (..), - joinArgs, joinArgsSpaced, + (<+>), filterOut ) where @@ -29,50 +29,29 @@ instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q -class ShowAction a where - showAction :: a -> Args - showListAction :: [a] -> Args -- the Creators' trick for overlapping String instances - showListAction = mconcat . map showAction +class ShowArgs a where + showArgs :: a -> Args + showListArgs :: [a] -> Args -- the Creators' trick for overlapping String instances + showListArgs = mconcat . map showArgs -instance ShowAction Char where - showAction c = return [[c]] - showListAction s = return [s] +instance ShowArgs Char where + showArgs c = return [[c]] + showListArgs s = return [s] -instance ShowAction a => ShowAction [a] where - showAction = showListAction +instance ShowArgs a => ShowArgs [a] where + showArgs = showListArgs -instance ShowAction a => ShowAction (Action a) where - showAction = (showAction =<<) +instance ShowArgs a => ShowArgs (Action a) where + showArgs = (showArgs =<<) -arg :: ShowAction a => a -> Args -arg = showAction +arg :: ShowArgs a => a -> Args +arg = showArgs -type ArgsCombine = Args -> Args -> Args +-- Combine two heterogeneous ShowArgs values. +(<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args +a <+> b = (<>) <$> showArgs a <*> showArgs b -class Collect a where - collect :: ArgsCombine -> Args -> a - -instance Collect Args where - collect = const id - -instance (ShowAction a, Collect r) => Collect (a -> r) where - collect combine x = \y -> collect combine $ x `combine` arg y - -args :: Collect a => a -args = collect (<>) mempty - -joinArgs :: Collect a => a -joinArgs = collect (\x y -> intercalateArgs "" $ x <> y) mempty - -joinArgsSpaced :: Collect a => a -joinArgsSpaced = collect (\x y -> intercalateArgs " " $ x <> y) mempty - -intercalateArgs :: String -> Args -> Args -intercalateArgs s as = do - as' <- as - case as' of - [] -> mempty - otherwise -> return [intercalate s as'] - -filterOut :: Args -> [String] -> Args -filterOut as list = filter (`notElem` list) <$> as +filterOut :: ShowArgs a => Args -> a -> Args +filterOut as exclude = do + exclude' <- showArgs exclude + filter (`notElem` exclude') <$> as From git at git.haskell.org Thu Oct 26 23:19:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Haddock arguments. (bf86f0e) Message-ID: <20171026231923.A19033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf86f0ec66186df924ba0e173ba606fe39ddbf1b/ghc >--------------------------------------------------------------- commit bf86f0ec66186df924ba0e173ba606fe39ddbf1b Author: Andrey Mokhov Date: Sat Aug 22 00:26:44 2015 +0100 Fix Haddock arguments. >--------------------------------------------------------------- bf86f0ec66186df924ba0e173ba606fe39ddbf1b src/Settings/Builders/Haddock.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 19c1979..0e839ce 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -26,6 +26,7 @@ haddockArgs = builder Haddock ? do ghcOpts <- fromDiffExpr commonGhcArgs mconcat [ arg $ "--odir=" ++ takeDirectory file + , arg "--verbosity=0" , arg "--no-tmp-comp-dir" , arg $ "--dump-interface=" ++ file , arg "--html" @@ -39,12 +40,14 @@ haddockArgs = builder Haddock ? do | (dep, depName) <- zip deps depNames , Just depPkg <- [findKnownPackage depName] ] , append [ "--optghc=" ++ opt | opt <- ghcOpts ] - , arg "--source-module=src/%{MODULE/./-}.html" - , arg "--source-entity=src/%{MODULE/./-}.html\\#%{NAME}" + , specified HsColour ? + arg "--source-module=src/%{MODULE/./-}.html" + , specified HsColour ? + arg "--source-entity=src/%{MODULE/./-}.html\\#%{NAME}" , customPackageArgs , append srcs , arg "+RTS" - , arg $ "-t" ++ file <.> "t" + , arg $ "-t" ++ path "haddock.t" , arg "--machine-readable" ] customPackageArgs :: Args From git at git.haskell.org Thu Oct 26 23:19:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename ShowAction to ShowArgs. (0da6908) Message-ID: <20171026231926.A33663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0da69088be65109832fa78a93bc0dc21fcd37f09/ghc >--------------------------------------------------------------- commit 0da69088be65109832fa78a93bc0dc21fcd37f09 Author: Andrey Mokhov Date: Fri Jan 9 17:23:32 2015 +0000 Rename ShowAction to ShowArgs. >--------------------------------------------------------------- 0da69088be65109832fa78a93bc0dc21fcd37f09 src/Oracles/Builder.hs | 14 +++++++------- src/Oracles/Option.hs | 12 ++++++------ src/Oracles/PackageData.hs | 4 ++-- 3 files changed, 15 insertions(+), 15 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 84b73b3..d91e5e7 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -14,8 +14,8 @@ import Oracles.Option data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage -instance ShowAction Builder where - showAction builder = showAction $ do +instance ShowArgs Builder where + showArgs builder = showArgs $ do let key = case builder of Ar -> "ar" Ld -> "ld" @@ -50,12 +50,12 @@ instance ShowAction Builder where -- the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - [target] <- showAction ghc + [target] <- showArgs ghc laxDeps <- test LaxDeps if laxDeps then orderOnly [target] else need [target] needBuilder builder = do - [target] <- showAction builder + [target] <- showArgs builder need [target] -- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder @@ -70,18 +70,18 @@ with builder = do Happy -> "--with-happy=" GhcPkg _ -> "--with-ghc-pkg=" HsColour -> "--with-hscolour=" - [suffix] <- showAction builder + [suffix] <- showArgs builder needBuilder builder return [prefix ++ suffix] run :: Builder -> Args -> Action () run builder args = do needBuilder builder - [exe] <- showAction builder + [exe] <- showArgs builder args' <- args cmd [exe] args' hsColourSrcs :: Condition hsColourSrcs = do - [hscolour] <- showAction HsColour + [hscolour] <- showArgs HsColour return $ hscolour /= "" diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 6f05a0e..d08b394 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -12,8 +12,8 @@ data Option = TargetOS | TargetArch | TargetPlatformFull | SrcHcOpts | HostOsCpp -instance ShowAction Option where - showAction opt = showAction $ fmap words $ askConfig $ case opt of +instance ShowArgs Option where + showArgs opt = showArgs $ fmap words $ askConfig $ case opt of TargetOS -> "target-os" TargetArch -> "target-arch" TargetPlatformFull -> "target-platform-full" @@ -30,8 +30,8 @@ instance ShowAction Option where ghcWithInterpreter :: Condition ghcWithInterpreter = do - [os] <- showAction TargetOS - [arch] <- showAction TargetArch + [os] <- showArgs TargetOS + [arch] <- showArgs TargetArch return $ os `elem` ["mingw32", "cygwin32", "linux", "solaris2", "freebsd", "dragonfly", "netbsd", "openbsd", "darwin", "kfreebsdgnu"] && @@ -39,10 +39,10 @@ ghcWithInterpreter = do platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do - [platform] <- showAction TargetPlatformFull + [platform] <- showArgs TargetPlatformFull return $ platform `notElem` [ "powerpc-unknown-linux", "x86_64-unknown-mingw32", "i386-unknown-mingw32" ] -- TODO: i386-unknown-solaris2? windowsHost :: Condition windowsHost = do - [hostOsCpp] <- showAction HostOsCpp + [hostOsCpp] <- showArgs HostOsCpp return $ hostOsCpp `elem` ["mingw32", "cygwin32"] diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 4ec89d7..ba63612 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -15,8 +15,8 @@ newtype PackageDataKey = PackageDataKey (FilePath, String) data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath -instance ShowAction PackageData where - showAction key = do +instance ShowArgs PackageData where + showArgs key = do let (keyName, file, ifEmpty) = case key of Modules file -> ("MODULES" , file, "" ) SrcDirs file -> ("HS_SRC_DIRS" , file, ".") From git at git.haskell.org Thu Oct 26 23:19:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add runghcid.bat. (14c35b5) Message-ID: <20171026231927.494AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14c35b529b90f9b5578c086a603c4c496c7b5c07/ghc >--------------------------------------------------------------- commit 14c35b529b90f9b5578c086a603c4c496c7b5c07 Author: Andrey Mokhov Date: Sat Aug 22 17:59:18 2015 +0100 Add runghcid.bat. >--------------------------------------------------------------- 14c35b529b90f9b5578c086a603c4c496c7b5c07 runghcid.bat | 1 + 1 file changed, 1 insertion(+) diff --git a/runghcid.bat b/runghcid.bat new file mode 100644 index 0000000..f2f8ddc --- /dev/null +++ b/runghcid.bat @@ -0,0 +1 @@ +ghcid --height=8 --topmost "--command=ghci -isrc -Wall src/Main.hs" From git at git.haskell.org Thu Oct 26 23:19:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up build rules. (7661c31) Message-ID: <20171026231930.3D2E83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7661c319397cbcf02f8b9c4f229ebc8b0c019ad2/ghc >--------------------------------------------------------------- commit 7661c319397cbcf02f8b9c4f229ebc8b0c019ad2 Author: Andrey Mokhov Date: Fri Jan 9 17:24:42 2015 +0000 Clean up build rules. >--------------------------------------------------------------- 7661c319397cbcf02f8b9c4f229ebc8b0c019ad2 src/Package/Base.hs | 2 +- src/Package/Data.hs | 88 +++++++++++++++++++++------------------------ src/Package/Dependencies.hs | 8 ++--- 3 files changed, 45 insertions(+), 53 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index a895f5f..43b4a37 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -53,7 +53,7 @@ libraryPackage name stage settings = )] commonCcArgs :: Args -commonCcArgs = when Validating $ args "-Werror" "-Wall" +commonCcArgs = when Validating $ arg ["-Werror", "-Wall"] commonLdArgs :: Args commonLdArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? diff --git a/src/Package/Data.hs b/src/Package/Data.hs index de617f4..81a7d7f 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -1,43 +1,37 @@ {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} module Package.Data (buildPackageData) where - import Package.Base libraryArgs :: [Way] -> Args libraryArgs ways = - let argEnable x suffix = arg $ (if x then "--enable-" else "--disable-") ++ suffix - in mconcat - [ argEnable False "library-for-ghci" -- TODO: why always disable? - , argEnable (vanilla `elem` ways) "library-vanilla" - , when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) $ - argEnable True "library-for-ghci" - , argEnable (profiling `elem` ways) "library-profiling" - , argEnable (dynamic `elem` ways) "shared" - ] + argEnable False "library-for-ghci" -- TODO: why always disable? + <> argEnable (vanilla `elem` ways) "library-vanilla" + <> when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) (argEnable True "library-for-ghci") + <> argEnable (profiling `elem` ways) "library-profiling" + <> argEnable (dynamic `elem` ways) "shared" + where + argEnable x suffix = arg $ (if x then "--enable-" else "--disable-") ++ suffix configureArgs :: Stage -> Settings -> Args configureArgs stage settings = - let argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" (as :: Args) + let argConf key as = do + s <- unwords <$> arg as + unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) - (ConfCcArgs stage) - (customCcArgs settings) - (commonCcWarninigArgs) - ldflags = joinArgsSpaced commonLdArgs (ConfGccLinkerArgs stage) (customLdArgs settings) - cppflags = joinArgsSpaced commonCppArgs (ConfCppArgs stage) (customCppArgs settings) + cflags = commonCcArgs `filterOut` "-Werror" <+> ConfCcArgs stage <+> customCcArgs settings <+> commonCcWarninigArgs + ldflags = commonLdArgs <+> ConfGccLinkerArgs stage <+> customLdArgs settings + cppflags = commonCppArgs <+> ConfCppArgs stage <+> customCppArgs settings - in mconcat - [ argConf "CFLAGS" cflags - , argConf "LDFLAGS" ldflags - , argConf "CPPFLAGS" cppflags - , joinArgs "--gcc-options=" cflags " " ldflags - , argConf "--with-iconv-includes" $ arg IconvIncludeDirs - , argConf "--with-iconv-libraries" $ arg IconvLibDirs - , argConf "--with-gmp-includes" $ arg GmpIncludeDirs - , argConf "--with-gmp-libraries" $ arg GmpLibDirs - , when CrossCompiling $ argConf "--host" $ arg TargetPlatformFull -- TODO: why not host? - , argConf "--with-cc" $ arg Gcc - ] + in argConf "CFLAGS" cflags + <> argConf "LDFLAGS" ldflags + <> argConf "CPPFLAGS" cppflags + <> arg (concat <$> "--gcc-options=" <+> cflags <+> " " <+> ldflags) + <> argConf "--with-iconv-includes" IconvIncludeDirs + <> argConf "--with-iconv-libraries" IconvLibDirs + <> argConf "--with-gmp-includes" GmpIncludeDirs + <> argConf "--with-gmp-libraries" GmpLibDirs + <> when CrossCompiling (argConf "--host" TargetPlatformFull) -- TODO: why not host? + <> argConf "--with-cc" Gcc buildPackageData :: Package -> TodoItem -> Rules () buildPackageData pkg @ (Package name path _) (stage, dist, settings) = @@ -57,30 +51,28 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = postProcessPackageData $ path dist "package-data.mk" where cabalArgs, ghcPkgArgs :: Args - cabalArgs = mconcat - [ args "configure" path dist + cabalArgs = arg ["configure", path, dist] -- this is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument -- * if there are many, we must collapse them into one space-separated string - , joinArgsSpaced "" (customDllArgs settings) - , with $ Ghc stage -- TODO: used to be stage01 (using max Stage1 GHC) - , with $ GhcPkg stage + <> arg (unwords <$> customDllArgs settings) + <> with (Ghc stage) -- TODO: used to be stage01 (using max Stage1 GHC) + <> with (GhcPkg stage) - , customConfArgs settings - , libraryArgs =<< ways settings + <> customConfArgs settings + <> (libraryArgs =<< ways settings) - , when hsColourSrcs $ with HsColour - , configureArgs stage settings + <> when hsColourSrcs (with HsColour) + <> configureArgs stage settings - , when (stage == Stage0) $ bootPkgConstraints - , with Gcc - , when (stage /= Stage0) $ with Ld + <> when (stage == Stage0) bootPkgConstraints + <> with Gcc + <> when (stage /= Stage0) (with Ld) - , with Ar - , with Alex - , with Happy - ] -- TODO: reorder with's + <> with Ar + <> with Alex + <> with Happy -- TODO: reorder with's - ghcPkgArgs = args "update" "--force" - (when (stage == Stage0) $ arg "--package-db=libraries/bootstrapping.conf") - (path dist "inplace-pkg-config") + ghcPkgArgs = arg ["update", "--force"] + <> when (stage == Stage0) (arg "--package-db=libraries/bootstrapping.conf") + <> arg (path dist "inplace-pkg-config") diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index b3e013f..7ccb7b6 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -88,14 +88,14 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = return $ prefix ++ buildDir suffix , map (\d -> "-I" ++ path d) <$> filter isRelative <$> arg (IncludeDirs pkgData) , map (\d -> "-I" ++ d) <$> filter isAbsolute <$> arg (IncludeDirs pkgData) - , args "-optP-include" ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + , arg ["-optP-include", "-optP" ++ buildDir "build/autogen/cabal_macros.h"] , if usePackageKey then map ("-package-key " ++) <$> arg (DepKeys pkgData) else map ("-package " ++) <$> arg (Deps pkgData) , arg "-no-user-package-db" - , args "-odir" (buildDir "build") - , args "-stubdir" (buildDir "build") - , joinArgsSpaced "-dep-makefile" out + , arg ["-odir" , buildDir "build"] + , arg ["-stubdir", buildDir "build"] + , arg $ "-dep-makefile " ++ out , concatMap (\w -> ["-dep-suffix", suffix w]) <$> ways settings , arg "-include-pkg-deps" , arg $ map normalise srcs From git at git.haskell.org Thu Oct 26 23:19:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use -Wall when compiling the build system. (134cac9) Message-ID: <20171026231930.D792F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/134cac9ab3a450be48cadce39a0faac00be227fb/ghc >--------------------------------------------------------------- commit 134cac9ab3a450be48cadce39a0faac00be227fb Author: Andrey Mokhov Date: Sat Aug 22 17:59:54 2015 +0100 Use -Wall when compiling the build system. >--------------------------------------------------------------- 134cac9ab3a450be48cadce39a0faac00be227fb build.bat | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.bat b/build.bat index b6b9a82..b45bdde 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,2 @@ @mkdir _shake 2> nul - at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:19:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set precedence level for <+>. (45208c5) Message-ID: <20171026231934.009FB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45208c5e1e6059db3b6993f03db0a0439f486377/ghc >--------------------------------------------------------------- commit 45208c5e1e6059db3b6993f03db0a0439f486377 Author: Andrey Mokhov Date: Sat Jan 10 02:13:01 2015 +0000 Set precedence level for <+>. >--------------------------------------------------------------- 45208c5e1e6059db3b6993f03db0a0439f486377 src/Base.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index ce2714e..de0c3d6 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -51,6 +51,8 @@ arg = showArgs (<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args a <+> b = (<>) <$> showArgs a <*> showArgs b +infixr 6 <+> + filterOut :: ShowArgs a => Args -> a -> Args filterOut as exclude = do exclude' <- showArgs exclude From git at git.haskell.org Thu Oct 26 23:19:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports. (c125896) Message-ID: <20171026231934.911E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1258966f7b34115402c8d4f2243cc2e75cb1deb/ghc >--------------------------------------------------------------- commit c1258966f7b34115402c8d4f2243cc2e75cb1deb Author: Andrey Mokhov Date: Sat Aug 22 18:00:14 2015 +0100 Refactor imports. >--------------------------------------------------------------- c1258966f7b34115402c8d4f2243cc2e75cb1deb src/Base.hs | 15 +++++++-------- src/Builder.hs | 11 +++-------- src/Expression.hs | 20 +++++++++++--------- src/Main.hs | 10 ++++++---- src/Oracles/Base.hs | 17 +++++++++-------- src/Oracles/Dependencies.hs | 2 -- src/Oracles/Flag.hs | 3 --- src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 3 --- src/Oracles/Setting.hs | 1 - src/Oracles/WindowsRoot.hs | 1 - src/Package.hs | 8 +++----- src/Predicates.hs | 6 +----- src/Rules.hs | 19 +++++-------------- src/Rules/Cabal.hs | 1 - src/Rules/Config.hs | 2 -- src/Rules/Data.hs | 7 ++----- src/Rules/Dependencies.hs | 3 +-- src/Rules/Documentation.hs | 1 - src/Rules/Library.hs | 20 +++++++------------- src/Rules/Oracles.hs | 11 ++++------- src/Rules/Package.hs | 8 ++++---- src/Rules/Resources.hs | 6 ++---- src/Settings/Builders/Gcc.hs | 11 +++++------ src/Settings/Builders/Ghc.hs | 9 +++------ src/Settings/Builders/Haddock.hs | 1 - src/Settings/Packages.hs | 1 - src/Settings/Util.hs | 4 +--- src/Stage.hs | 10 ++++------ src/Target.hs | 12 ++++++------ src/Util.hs | 37 +++++++++++++++++++++---------------- src/Way.hs | 14 +++++--------- 32 files changed, 110 insertions(+), 165 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c1258966f7b34115402c8d4f2243cc2e75cb1deb From git at git.haskell.org Thu Oct 26 23:19:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (d08651a) Message-ID: <20171026231937.7576A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d08651a9b504b04425865eaceaba66f2f74cdaa8/ghc >--------------------------------------------------------------- commit d08651a9b504b04425865eaceaba66f2f74cdaa8 Author: Andrey Mokhov Date: Sat Jan 10 02:14:14 2015 +0000 Clean up. >--------------------------------------------------------------- d08651a9b504b04425865eaceaba66f2f74cdaa8 src/Package/Data.hs | 77 +++++++++++++++++++++++++---------------------------- 1 file changed, 36 insertions(+), 41 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 81a7d7f..7428a87 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -35,44 +35,39 @@ configureArgs stage settings = buildPackageData :: Package -> TodoItem -> Rules () buildPackageData pkg @ (Package name path _) (stage, dist, settings) = - ((path dist) ) <$> - [ "package-data.mk", - "haddock-prologue.txt", - "inplace-pkg-config", - "setup-config", - "build" "autogen" "cabal_macros.h", - "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. - ] &%> \_ -> do - need ["shake/src/Package/Data.hs"] -- Track changes in this file - need [path name <.> "cabal"] - when (doesFileExist $ path "configure.ac") $ need [path "configure"] - run GhcCabal cabalArgs - when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs - postProcessPackageData $ path dist "package-data.mk" - where - cabalArgs, ghcPkgArgs :: Args - cabalArgs = arg ["configure", path, dist] - -- this is a positional argument, hence: - -- * if it is empty, we need to emit one empty string argument - -- * if there are many, we must collapse them into one space-separated string - <> arg (unwords <$> customDllArgs settings) - <> with (Ghc stage) -- TODO: used to be stage01 (using max Stage1 GHC) - <> with (GhcPkg stage) - - <> customConfArgs settings - <> (libraryArgs =<< ways settings) - - <> when hsColourSrcs (with HsColour) - <> configureArgs stage settings - - <> when (stage == Stage0) bootPkgConstraints - <> with Gcc - <> when (stage /= Stage0) (with Ld) - - <> with Ar - <> with Alex - <> with Happy -- TODO: reorder with's - - ghcPkgArgs = arg ["update", "--force"] - <> when (stage == Stage0) (arg "--package-db=libraries/bootstrapping.conf") - <> arg (path dist "inplace-pkg-config") + let buildDir = path dist + cabalArgs = arg ["configure", path, dist] + -- this is a positional argument, hence: + -- * if it is empty, we need to emit one empty string argument + -- * if there are many, we must collapse them into one space-separated string + <> arg (unwords <$> customDllArgs settings) + <> with (Ghc stage) -- TODO: used to be stage01 (using max stage1 GHC) + <> with (GhcPkg stage) + <> customConfArgs settings + <> (libraryArgs =<< ways settings) + <> when hsColourSrcs (with HsColour) + <> configureArgs stage settings + <> when (stage == Stage0) bootPkgConstraints + <> with Gcc + <> when (stage /= Stage0) (with Ld) + <> with Ar + <> with Alex + <> with Happy -- TODO: reorder with's + ghcPkgArgs = arg ["update", "--force"] + <> when (stage == Stage0) (arg "--package-db=libraries/bootstrapping.conf") + <> arg (buildDir "inplace-pkg-config") + in + (buildDir ) <$> + [ "package-data.mk" + , "haddock-prologue.txt" + , "inplace-pkg-config" + , "setup-config" + , "build" "autogen" "cabal_macros.h" + , "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. + ] &%> \_ -> do + need ["shake/src/Package/Data.hs"] -- Track changes in this file + need [path name <.> "cabal"] + when (doesFileExist $ path "configure.ac") $ need [path "configure"] + run GhcCabal cabalArgs + when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs + postProcessPackageData $ buildDir "package-data.mk" From git at git.haskell.org Thu Oct 26 23:19:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Oracles. (d4a438f) Message-ID: <20171026231938.04B9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf/ghc >--------------------------------------------------------------- commit d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf Author: Andrey Mokhov Date: Sat Aug 22 18:47:04 2015 +0100 Refactor Oracles. >--------------------------------------------------------------- d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf src/Builder.hs | 7 +++---- src/Oracles.hs | 17 +++++++++++++++++ src/Oracles/ArgsHash.hs | 4 ++-- src/Oracles/{Base.hs => Config.hs} | 9 +-------- src/Oracles/{ => Config}/Flag.hs | 8 +++++--- src/Oracles/{ => Config}/Setting.hs | 5 +++-- src/Oracles/Dependencies.hs | 1 - src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 3 ++- src/Predicates.hs | 3 +-- src/Rules/Actions.hs | 2 +- src/Rules/Oracles.hs | 19 +++++++------------ src/Settings/Builders/Ghc.hs | 3 +-- src/Settings/Builders/GhcCabal.hs | 3 +-- src/Settings/Builders/Ld.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/Util.hs | 4 +--- src/Settings/Ways.hs | 2 +- src/Util.hs | 2 ++ src/Way.hs | 2 +- 20 files changed, 51 insertions(+), 48 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 d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf From git at git.haskell.org Thu Oct 26 23:19:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor buildPackageDependencies into separate functions. (b70f3d8) Message-ID: <20171026231940.DEFB23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b/ghc >--------------------------------------------------------------- commit b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b Author: Andrey Mokhov Date: Sat Jan 10 02:14:55 2015 +0000 Refactor buildPackageDependencies into separate functions. >--------------------------------------------------------------- b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b src/Package/Dependencies.hs | 134 ++++++++++++++------------------------------ 1 file changed, 43 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b From git at git.haskell.org Thu Oct 26 23:19:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Settings/Default.hs to GHC.hs, add Settings.hs. (f68d70f) Message-ID: <20171026231941.697EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f68d70f07527618af262cf45d84c5ca898b166b7/ghc >--------------------------------------------------------------- commit f68d70f07527618af262cf45d84c5ca898b166b7 Author: Andrey Mokhov Date: Sat Aug 22 19:20:11 2015 +0100 Move Settings/Default.hs to GHC.hs, add Settings.hs. >--------------------------------------------------------------- f68d70f07527618af262cf45d84c5ca898b166b7 src/{Settings/Default.hs => GHC.hs} | 32 ++++++++++++++++---------------- src/Oracles/ArgsHash.hs | 2 +- src/Predicates.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 9 ++++----- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 5 +---- src/Rules/Library.hs | 2 +- src/Settings.hs | 13 +++++++++++++ src/Settings/Args.hs | 3 +-- src/Settings/Builders/Ghc.hs | 3 +-- src/Settings/Builders/GhcCabal.hs | 5 +---- src/Settings/Packages.hs | 14 +++++--------- src/Settings/User.hs | 4 +--- 16 files changed, 50 insertions(+), 52 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 f68d70f07527618af262cf45d84c5ca898b166b7 From git at git.haskell.org Thu Oct 26 23:19:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add prefixArgs function. (4c715ac) Message-ID: <20171026231944.850733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4c715acd811aef3c2be59375280c586e22fc0ecc/ghc >--------------------------------------------------------------- commit 4c715acd811aef3c2be59375280c586e22fc0ecc Author: Andrey Mokhov Date: Sat Jan 10 19:13:55 2015 +0000 Add prefixArgs function. >--------------------------------------------------------------- 4c715acd811aef3c2be59375280c586e22fc0ecc src/Base.hs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index de0c3d6..ffb2bbb 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -10,7 +10,8 @@ module Base ( Args, arg, ShowArgs (..), Condition (..), (<+>), - filterOut + filterOut, + prefixArgs ) where import Development.Shake @@ -47,13 +48,20 @@ instance ShowArgs a => ShowArgs (Action a) where arg :: ShowArgs a => a -> Args arg = showArgs --- Combine two heterogeneous ShowArgs values. +-- Combine two heterogeneous ShowArgs values (<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args a <+> b = (<>) <$> showArgs a <*> showArgs b infixr 6 <+> +-- Filter out given arg(s) from a collection filterOut :: ShowArgs a => Args -> a -> Args filterOut as exclude = do exclude' <- showArgs exclude filter (`notElem` exclude') <$> as + +-- Prefix each arg in a collection with a given prefix +prefixArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args +prefixArgs prefix as = do + prefix' <- showArgs prefix + concatMap (\a -> prefix' ++ [a]) <$> showArgs as From git at git.haskell.org Thu Oct 26 23:19:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge Base.hs and Util.hs. (190f3fd) Message-ID: <20171026231945.2FCDE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/190f3fde35a3230bbdfe50afce81dd5e10590c24/ghc >--------------------------------------------------------------- commit 190f3fde35a3230bbdfe50afce81dd5e10590c24 Author: Andrey Mokhov Date: Sat Aug 22 21:03:38 2015 +0100 Merge Base.hs and Util.hs. >--------------------------------------------------------------- 190f3fde35a3230bbdfe50afce81dd5e10590c24 src/Base.hs | 119 +++++++++++++++++++++++++++++++++++++- src/Builder.hs | 1 - src/Expression.hs | 3 +- src/Oracles/ArgsHash.hs | 2 - src/Oracles/Config.hs | 1 - src/Oracles/Config/Flag.hs | 1 - src/Oracles/Dependencies.hs | 1 - src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 1 - src/Oracles/WindowsRoot.hs | 1 - src/Package.hs | 1 - src/Predicates.hs | 1 - src/Rules.hs | 6 +- src/Rules/Actions.hs | 3 - src/Rules/Cabal.hs | 1 - src/Rules/Compile.hs | 1 - src/Rules/Config.hs | 1 - src/Rules/Data.hs | 2 - src/Rules/Dependencies.hs | 2 - src/Rules/Documentation.hs | 1 - src/Rules/Library.hs | 7 +-- src/Rules/Package.hs | 1 - src/Rules/Resources.hs | 1 - src/Settings/Args.hs | 2 +- src/Settings/Builders/Gcc.hs | 2 - src/Settings/Builders/Ghc.hs | 1 - src/Settings/Builders/GhcCabal.hs | 2 - src/Settings/Builders/GhcPkg.hs | 1 - src/Settings/Builders/Haddock.hs | 2 - src/Settings/TargetDirectory.hs | 1 - src/Settings/Util.hs | 1 - src/Settings/Ways.hs | 1 - src/Target.hs | 1 - src/Util.hs | 117 ------------------------------------- src/Way.hs | 3 +- 35 files changed, 124 insertions(+), 169 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 190f3fde35a3230bbdfe50afce81dd5e10590c24 From git at git.haskell.org Thu Oct 26 23:19:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (3579324) Message-ID: <20171026231948.101463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3579324b91abeb130df12d8639b67941c71d80ae/ghc >--------------------------------------------------------------- commit 3579324b91abeb130df12d8639b67941c71d80ae Author: Andrey Mokhov Date: Sat Jan 10 19:14:45 2015 +0000 Clean up. >--------------------------------------------------------------- 3579324b91abeb130df12d8639b67941c71d80ae src/Package.hs | 3 ++- src/Package/Data.hs | 6 +++++- src/Package/Dependencies.hs | 39 ++++++++++++++++++--------------------- 3 files changed, 25 insertions(+), 23 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 7a5f20e..0df8668 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -18,7 +18,8 @@ buildPackage pkg todoItem = do packageRules :: Rules () packageRules = do - want ["libraries/deepseq/dist-install/build/deepseq.m"] -- TODO: control targets from commang line arguments + -- TODO: control targets from commang line arguments + want ["libraries/deepseq/dist-install/build/deepseq.m"] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 7428a87..fd8dd2c 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -1,5 +1,6 @@ {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} module Package.Data (buildPackageData) where + import Package.Base libraryArgs :: [Way] -> Args @@ -18,7 +19,10 @@ configureArgs stage settings = s <- unwords <$> arg as unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = commonCcArgs `filterOut` "-Werror" <+> ConfCcArgs stage <+> customCcArgs settings <+> commonCcWarninigArgs + cflags = commonCcArgs `filterOut` "-Werror" + <+> ConfCcArgs stage + <+> customCcArgs settings + <+> commonCcWarninigArgs ldflags = commonLdArgs <+> ConfGccLinkerArgs stage <+> customLdArgs settings cppflags = commonCppArgs <+> ConfCppArgs stage <+> customCppArgs settings diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 47a7a37..5b10ca1 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -3,18 +3,17 @@ module Package.Dependencies (buildPackageDependencies) where import Package.Base -packageKeyArgs :: Stage -> FilePath -> Args -packageKeyArgs stage pkgData = - arg "-hide-all-packages" <> - (pkgArgs =<< SupportsPackageKey || stage /= Stage0) +packageArgs :: Stage -> FilePath -> Args +packageArgs stage pkgData = do + usePackageKey <- SupportsPackageKey || stage /= Stage0 + arg ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] + <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") + <> keyArgs usePackageKey where - pkgArgs True = "-this-package-key" - <+> PackageKey pkgData - <+> prepend "-package-key " (DepKeys pkgData) - pkgArgs _ = "-package-name" - <+> PackageKey pkgData - <+> prepend "-package " (Deps pkgData) - prepend pref = (map (pref ++) <$>) . arg + keyArgs True = prefixArgs "-this-package-key" (PackageKey pkgData) <> + prefixArgs "-package-key" (DepKeys pkgData) + keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> + prefixArgs "-package" (Deps pkgData) includeArgs :: ShowArgs a => String -> FilePath -> a -> Args includeArgs prefix path as = map includePath <$> arg as @@ -26,7 +25,7 @@ srcArgs :: FilePath -> FilePath -> Args srcArgs path pkgData = do mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) dirs <- arg (SrcDirs pkgData) - srcs <- getDirectoryFiles "" $ + srcs <- getDirectoryFiles "" [path dir mPath <.> ext | dir <- dirs, mPath <- mods, ext <- ["hs", "lhs"]] arg (map normalise srcs) @@ -38,20 +37,18 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = (buildDir "build" name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file run (Ghc stage) $ arg "-M" - <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") - <> packageKeyArgs stage pkgData + <> packageArgs stage pkgData <> arg "-i" <> includeArgs "-i" path (SrcDirs pkgData) <> includeArgs "-i" buildDir ["build", "build/autogen"] <> includeArgs "-I" buildDir ["build", "build/autogen"] <> includeArgs "-I" path (IncludeDirs pkgData) - <> arg ["-optP-include", "-optP" ++ buildDir "build/autogen/cabal_macros.h"] - <> arg "-no-user-package-db" - <> arg ["-odir" , buildDir "build"] - <> arg ["-stubdir", buildDir "build"] - <> arg ("-dep-makefile " ++ out) - <> (concatMap (\w -> ["-dep-suffix", suffix w]) <$> ways settings) - <> arg "-include-pkg-deps" + <> arg "-optP-include" -- TODO: Shall we also add -cpp? + <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + <> arg ["-odir" , buildDir "build"] + <> arg ["-stubdir" , buildDir "build"] + <> arg ["-dep-makefile", out ] + <> prefixArgs "-dep-suffix" (map suffix <$> ways settings) <> srcArgs path pkgData -- <> arg SrcHcOpts -- TODO: Check that skipping all _HC_OPTS is safe. -- <> wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? From git at git.haskell.org Thu Oct 26 23:19:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (c928f2c) Message-ID: <20171026231948.A1CEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c928f2ce774091b7a6345c5c3cbdf05782bb2d23/ghc >--------------------------------------------------------------- commit c928f2ce774091b7a6345c5c3cbdf05782bb2d23 Author: Andrey Mokhov Date: Sat Aug 22 21:08:19 2015 +0100 Add comments. >--------------------------------------------------------------- c928f2ce774091b7a6345c5c3cbdf05782bb2d23 src/Base.hs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 862c46b..13483ce 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -50,15 +50,17 @@ packageDependencies :: FilePath packageDependencies = shakeFilesPath ++ "package-dependencies" -- Utility functions -replaceIf :: (a -> Bool) -> a -> [a] -> [a] -replaceIf p to = map (\from -> if p from then to else from) - +-- Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) +-- Find and replace all occurrences of path separators in a String with a Char replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator +replaceIf :: (a -> Bool) -> a -> [a] -> [a] +replaceIf p to = map (\from -> if p from then to else from) + -- Given a module name extract the directory and file names, e.g.: -- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") decodeModule :: String -> (FilePath, String) From git at git.haskell.org Thu Oct 26 23:19:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reexport module Data.Function from Base.hs. (7ad9848) Message-ID: <20171026231951.D25613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ad9848f719e76bb194719984bbf78a926634fe9/ghc >--------------------------------------------------------------- commit 7ad9848f719e76bb194719984bbf78a926634fe9 Author: Andrey Mokhov Date: Sun Jan 11 03:26:13 2015 +0000 Reexport module Data.Function from Base.hs. >--------------------------------------------------------------- 7ad9848f719e76bb194719984bbf78a926634fe9 src/Base.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index ffb2bbb..38790e6 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -4,6 +4,7 @@ module Base ( module Development.Shake, module Development.Shake.FilePath, module Control.Applicative, + module Data.Function, module Data.Monoid, module Data.List, Stage (..), @@ -17,6 +18,7 @@ module Base ( import Development.Shake import Development.Shake.FilePath import Control.Applicative hiding ((*>)) +import Data.Function import Data.Monoid import Data.List From git at git.haskell.org Thu Oct 26 23:19:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, order Builder alphabetically. (a4c1eba) Message-ID: <20171026231952.2ABE43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4c1ebabfc62d83ec7d717210db4ae56ca900205/ghc >--------------------------------------------------------------- commit a4c1ebabfc62d83ec7d717210db4ae56ca900205 Author: Andrey Mokhov Date: Sat Aug 22 21:18:28 2015 +0100 Add comments, order Builder alphabetically. >--------------------------------------------------------------- a4c1ebabfc62d83ec7d717210db4ae56ca900205 src/Builder.hs | 47 ++++++++++++++++++++++------------------------- 1 file changed, 22 insertions(+), 25 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 5d60035..dde37c1 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -11,48 +11,45 @@ import Stage -- Ghc Stage0 is the bootstrapping compiler -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg --- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) +-- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) -- TODO: add Cpp builders -- TODO: rename Gcc to Cc? -data Builder = Ar - | Ld - | Alex - | Happy - | Haddock - | HsColour - | GhcCabal +data Builder = Alex + | Ar | Gcc Stage + | GccM Stage | Ghc Stage + | GhcCabal + | GhcCabalHsColour | GhcM Stage - | GccM Stage | GhcPkg Stage - | GhcCabalHsColour + | Haddock + | Happy + | HsColour + | Ld deriving (Show, Eq, Generic) -- Configuration files refer to Builders as follows: --- TODO: determine paths to utils without looking up configuration files builderKey :: Builder -> String builderKey builder = case builder of - Ar -> "ar" - Ld -> "ld" Alex -> "alex" - Happy -> "happy" - Haddock -> "haddock" - HsColour -> "hscolour" - GhcCabal -> "ghc-cabal" + Ar -> "ar" + Gcc Stage0 -> "system-gcc" + Gcc _ -> "gcc" + GccM stage -> builderKey $ Gcc stage -- Synonym for 'Gcc -MM' Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - Gcc Stage0 -> "system-gcc" - Gcc _ -> "gcc" + GhcM stage -> builderKey $ Ghc stage -- Synonym for 'Ghc -M' + GhcCabal -> "ghc-cabal" + GhcCabalHsColour -> builderKey $ GhcCabal -- Synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" - -- GhcM/GccM are synonyms for Ghc/Gcc (called with -M and -MM flags) - GhcM stage -> builderKey $ Ghc stage - GccM stage -> builderKey $ Gcc stage - -- GhcCabalHsColour is a synonym for GhcCabal (called in hscolour mode) - GhcCabalHsColour -> builderKey $ GhcCabal + Happy -> "happy" + Haddock -> "haddock" + HsColour -> "hscolour" + Ld -> "ld" builderPath :: Builder -> Action FilePath builderPath builder = do @@ -77,7 +74,7 @@ needBuilder laxDependencies builder = do allowOrderOnlyDependency :: Builder -> Bool allowOrderOnlyDependency (Ghc _) = True allowOrderOnlyDependency (GhcM _) = True - allowOrderOnlyDependency _ = False + allowOrderOnlyDependency _ = False -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". From git at git.haskell.org Thu Oct 26 23:19:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove way descriptions, add detectWay function. (94501e5) Message-ID: <20171026231955.6A5FF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/94501e5a89c6d81df6d1fededaf4a05793ad135f/ghc >--------------------------------------------------------------- commit 94501e5a89c6d81df6d1fededaf4a05793ad135f Author: Andrey Mokhov Date: Sun Jan 11 03:28:17 2015 +0000 Remove way descriptions, add detectWay function. >--------------------------------------------------------------- 94501e5a89c6d81df6d1fededaf4a05793ad135f src/Ways.hs | 61 ++++++++++++++++++++++++++++++++++++------------------------- 1 file changed, 36 insertions(+), 25 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 3e7c483..843383e 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -12,9 +12,10 @@ module Ways ( threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic, - wayHcOpts, + wayHcArgs, suffix, - hisuf, osuf, hcsuf + hisuf, osuf, hcsuf, + detectWay ) where import Base @@ -25,34 +26,36 @@ data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dyn data Way = Way { tag :: String, -- e.g., "thr_p" - description :: String, -- e.g., "threaded profiled"; TODO: get rid of this field? units :: [WayUnit] -- e.g., [Threaded, Profiling] } deriving Eq -vanilla = Way "v" "vanilla" [] -profiling = Way "p" "profiling" [Profiling] -logging = Way "l" "event logging" [Logging] -parallel = Way "mp" "parallel" [Parallel] -granSim = Way "gm" "GranSim" [GranSim] +instance Show Way where + show = tag + +vanilla = Way "v" [] +profiling = Way "p" [Profiling] +logging = Way "l" [Logging] +parallel = Way "mp" [Parallel] +granSim = Way "gm" [GranSim] -- RTS only ways -threaded = Way "thr" "threaded" [Threaded] -threadedProfiling = Way "thr_p" "threaded profiling" [Threaded, Profiling] -threadedLogging = Way "thr_l" "threaded event logging" [Threaded, Logging] -debug = Way "debug" "debug" [Debug] -debugProfiling = Way "debug_p" "debug profiling" [Debug, Profiling] -threadedDebug = Way "thr_debug" "threaded debug" [Threaded, Debug] -threadedDebugProfiling = Way "thr_debug_p" "threaded debug profiling" [Threaded, Debug, Profiling] -dynamic = Way "dyn" "dyn" [Dynamic] -profilingDynamic = Way "p_dyn" "p_dyn" [Profiling, Dynamic] -threadedProfilingDynamic = Way "thr_p_dyn" "thr_p_dyn" [Threaded, Profiling, Dynamic] -threadedDynamic = Way "thr_dyn" "thr_dyn" [Threaded, Dynamic] -threadedDebugDynamic = Way "thr_debug_dyn" "thr_debug_dyn" [Threaded, Debug, Dynamic] -debugDynamic = Way "debug_dyn" "debug_dyn" [Debug, Dynamic] -loggingDynamic = Way "l_dyn" "event logging dynamic" [Logging, Dynamic] -threadedLoggingDynamic = Way "thr_l_dyn" "threaded event logging dynamic" [Threaded, Logging, Dynamic] +threaded = Way "thr" [Threaded] +threadedProfiling = Way "thr_p" [Threaded, Profiling] +threadedLogging = Way "thr_l" [Threaded, Logging] +debug = Way "debug" [Debug] +debugProfiling = Way "debug_p" [Debug, Profiling] +threadedDebug = Way "thr_debug" [Threaded, Debug] +threadedDebugProfiling = Way "thr_debug_p" [Threaded, Debug, Profiling] +dynamic = Way "dyn" [Dynamic] +profilingDynamic = Way "p_dyn" [Profiling, Dynamic] +threadedProfilingDynamic = Way "thr_p_dyn" [Threaded, Profiling, Dynamic] +threadedDynamic = Way "thr_dyn" [Threaded, Dynamic] +threadedDebugDynamic = Way "thr_debug_dyn" [Threaded, Debug, Dynamic] +debugDynamic = Way "debug_dyn" [Debug, Dynamic] +loggingDynamic = Way "l_dyn" [Logging, Dynamic] +threadedLoggingDynamic = Way "thr_l_dyn" [Threaded, Logging, Dynamic] allWays = [vanilla, profiling, logging, parallel, granSim, threaded, threadedProfiling, threadedLogging, @@ -71,8 +74,8 @@ defaultWays stage = do ++ [profiling | stage /= Stage0] ++ [dynamic | sharedLibs ] -wayHcOpts :: Way -> Args -wayHcOpts (Way _ _ units) = +wayHcArgs :: Way -> Args +wayHcArgs (Way _ units) = mconcat [ when (Dynamic `notElem` units) $ arg ["-static"] , when (Dynamic `elem` units) $ arg ["-fPIC", "-dynamic"] @@ -93,3 +96,11 @@ hisuf, osuf, hcsuf :: Way -> String hisuf = (++ "hi") . suffix osuf = (++ "o" ) . suffix hcsuf = (++ "hc") . suffix + +-- Detect way from a given extension. Fail if the result is not unique. +detectWay :: FilePath -> Way +detectWay extension = case solutions of + [way] -> way + otherwise -> error $ "Cannot detect way from extension '" ++ extension ++ "'." + where + solutions = [w | f <- [hisuf, osuf, hcsuf], w <- allWays, f w == extension] From git at git.haskell.org Thu Oct 26 23:19:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove notP and (??) Predicate functions. (88fa774) Message-ID: <20171026231955.ACCB33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88fa774add49f09b3ccac966c85c49458275a5c6/ghc >--------------------------------------------------------------- commit 88fa774add49f09b3ccac966c85c49458275a5c6 Author: Andrey Mokhov Date: Sat Aug 22 21:40:24 2015 +0100 Remove notP and (??) Predicate functions. >--------------------------------------------------------------- 88fa774add49f09b3ccac966c85c49458275a5c6 src/Expression.hs | 12 ++++-------- src/Predicates.hs | 6 +++--- src/Settings/Builders/GhcCabal.hs | 15 +++++++-------- 3 files changed, 14 insertions(+), 19 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index e62acf0..d84fb2c 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -7,7 +7,7 @@ module Expression ( module Stage, module Way, Expr, DiffExpr, fromDiffExpr, - Predicate, (?), (??), notP, applyPredicate, + Predicate, (?), applyPredicate, Args, Ways, Packages, apply, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, @@ -63,7 +63,7 @@ append x = apply (<> x) -- 3) remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] -remove xs = apply . filter $ (`notElem` xs) +remove xs = apply $ filter (`notElem` xs) -- 4) apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a @@ -74,25 +74,21 @@ applyPredicate predicate expr = do -- A convenient operator for predicate application class PredicateLike a where (?) :: Monoid m => a -> Expr m -> Expr m - notP :: a -> Predicate infixr 8 ? instance PredicateLike Predicate where (?) = applyPredicate - notP = liftM not instance PredicateLike Bool where (?) = applyPredicate . return - notP = return . not instance PredicateLike (Action Bool) where (?) = applyPredicate . lift - notP = lift . fmap not -- An equivalent of if-then-else for predicates -(??) :: (PredicateLike a, Monoid m) => a -> (Expr m, Expr m) -> Expr m -p ?? (t, f) = p ? t <> notP p ? f +-- (??) :: (PredicateLike a, Monoid m) => a -> (Expr m, Expr m) -> Expr m +-- p ?? (t, f) = p ? t <> notP p ? f -- A monadic version of append appendM :: Monoid a => Action a -> DiffExpr a diff --git a/src/Predicates.hs b/src/Predicates.hs index 8743881..5bc0aed 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -40,10 +40,10 @@ stage2 :: Predicate stage2 = stage Stage2 notStage :: Stage -> Predicate -notStage = notP . stage +notStage = liftM not . stage notStage0 :: Predicate -notStage0 = notP stage0 +notStage0 = liftM not stage0 -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate @@ -52,7 +52,7 @@ registerPackage = return True splitObjects :: Predicate splitObjects = do goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages - goodPkg <- notP $ package compiler -- We don't split compiler + goodPkg <- liftM not $ package compiler -- We don't split compiler broken <- lift $ flag SplitObjectsBroken ghcUnreg <- lift $ flag GhcUnregisterised goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 11529bf..1925daf 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -102,13 +102,12 @@ packageConstraints = stage0 ? do -- TODO: put all validating options together in one file ccArgs :: Args ccArgs = validating ? do - let gccGe46 = notP gccLt46 + let notClang = fmap not gccIsClang mconcat [ arg "-Werror" , arg "-Wall" - , gccIsClang ?? - ( arg "-Wno-unknown-pragmas" <> - gccGe46 ? windowsHost ? arg "-Werror=unused-but-set-variable" - , gccGe46 ? arg "-Wno-error=inline" )] + , gccIsClang ? arg "-Wno-unknown-pragmas" + , notClang ? gccGe46 ? notWindowsHost ? arg "-Werror=unused-but-set-variable" + , notClang ? gccGe46 ? arg "-Wno-error=inline" ] ldArgs :: Args ldArgs = mempty @@ -151,8 +150,8 @@ customPackageArgs = do , arg "--disable-library-for-ghci" , targetOs "openbsd" ? arg "--ld-options=-E" , flag GhcUnregisterised ? arg "--ghc-option=-DNO_REGS" - , notP ghcWithSMP ? arg "--ghc-option=-DNOSMP" - , notP ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" + , fmap not ghcWithSMP ? arg "--ghc-option=-DNOSMP" + , fmap not ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" , (threaded `elem` rtsWays) ? notStage0 ? arg "--ghc-option=-optc-DTHREADED_RTS" , ghcWithNativeCodeGen ? arg "--flags=ncg" @@ -160,7 +159,7 @@ customPackageArgs = do notStage0 ? arg "--flags=ghci" , ghcWithInterpreter ? ghcEnableTablesNextToCode ? - notP (flag GhcUnregisterised) ? + fmap not (flag GhcUnregisterised) ? notStage0 ? arg "--ghc-option=-DGHCI_TABLES_NEXT_TO_CODE" , ghcWithInterpreter ? ghciWithDebugger ? From git at git.haskell.org Thu Oct 26 23:19:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move functions ghcOpts, packageArgs, includeArgs, srcArgs. (ccb5848) Message-ID: <20171026231959.08BE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccb58488381da821a99c95965d7a101d040bfd1f/ghc >--------------------------------------------------------------- commit ccb58488381da821a99c95965d7a101d040bfd1f Author: Andrey Mokhov Date: Sun Jan 11 03:29:44 2015 +0000 Move functions ghcOpts, packageArgs, includeArgs, srcArgs. >--------------------------------------------------------------- ccb58488381da821a99c95965d7a101d040bfd1f src/Package/Base.hs | 33 ++++++++++++++++++++++++++------- 1 file changed, 26 insertions(+), 7 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 43b4a37..4ef03fb 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -7,7 +7,8 @@ module Package.Base ( Package (..), Settings (..), TodoItem (..), defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - bootPkgConstraints, ghcOpts + bootPkgConstraints, + packageArgs, includeArgs, srcArgs ) where import Base @@ -76,10 +77,28 @@ bootPkgConstraints = mempty -- $(foreach p,$(basename $(notdir $(wildcard libraries/$d/*.cabal))),\ -- --constraint "$p == $(shell grep -i "^Version:" libraries/$d/$p.cabal | sed "s/[^0-9.]//g")")) --- TODO: move? -ghcOpts :: Package -> Stage -> Way -> Action [String] -ghcOpts pkg stage way = do - return $ ["-hisuf " ++ hisuf way] - ++ ["-osuf " ++ osuf way] - ++ ["-hcsuf " ++ hcsuf way] +packageArgs :: Stage -> FilePath -> Args +packageArgs stage pkgData = do + usePackageKey <- SupportsPackageKey || stage /= Stage0 + arg ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] + <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") + <> keyArgs usePackageKey + where + keyArgs True = prefixArgs "-this-package-key" (PackageKey pkgData) <> + prefixArgs "-package-key" (DepKeys pkgData) + keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> + prefixArgs "-package" (Deps pkgData) +includeArgs :: ShowArgs a => String -> FilePath -> a -> Args +includeArgs prefix path as = map includePath <$> arg as + where + includePath dir | isRelative dir = prefix ++ path dir + | isAbsolute dir = prefix dir + +srcArgs :: FilePath -> FilePath -> Args +srcArgs path pkgData = do + mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) + dirs <- arg (SrcDirs pkgData) + srcs <- getDirectoryFiles "" + [path dir mPath <.> ext | dir <- dirs, mPath <- mods, ext <- ["hs", "lhs"]] + arg (map normaliseEx srcs) From git at git.haskell.org Thu Oct 26 23:19:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:19:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace GccLt46 with gccGe46 as the former was always used negated. (aff7b3c) Message-ID: <20171026231959.6737D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aff7b3c9ee5a06b7c7070f14cecf941ba1c2820d/ghc >--------------------------------------------------------------- commit aff7b3c9ee5a06b7c7070f14cecf941ba1c2820d Author: Andrey Mokhov Date: Sat Aug 22 21:41:21 2015 +0100 Replace GccLt46 with gccGe46 as the former was always used negated. >--------------------------------------------------------------- aff7b3c9ee5a06b7c7070f14cecf941ba1c2820d src/Oracles/Config/Flag.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 737af97..80d8c6a 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -1,6 +1,6 @@ module Oracles.Config.Flag ( Flag (..), flag, - crossCompiling, gccIsClang, gccLt46, + crossCompiling, gccIsClang, gccGe46, platformSupportsSharedLibs, ghcWithSMP, ghcWithNativeCodeGen ) where @@ -39,8 +39,8 @@ crossCompiling = flag CrossCompiling gccIsClang :: Action Bool gccIsClang = flag GccIsClang -gccLt46 :: Action Bool -gccLt46 = flag GccLt46 +gccGe46 :: Action Bool +gccGe46 = fmap not $ flag GccLt46 platformSupportsSharedLibs :: Action Bool platformSupportsSharedLibs = do From git at git.haskell.org Thu Oct 26 23:20:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageCompile rule. (c826054) Message-ID: <20171026232002.DB3033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c826054081b67e094002e47e7635c7d34835f380/ghc >--------------------------------------------------------------- commit c826054081b67e094002e47e7635c7d34835f380 Author: Andrey Mokhov Date: Sun Jan 11 03:31:07 2015 +0000 Add buildPackageCompile rule. >--------------------------------------------------------------- c826054081b67e094002e47e7635c7d34835f380 src/Package.hs | 5 ++++- src/Package/Data.hs | 2 +- src/Package/Dependencies.hs | 28 +--------------------------- 3 files changed, 6 insertions(+), 29 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 0df8668..8f2850d 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -2,6 +2,7 @@ module Package (packageRules) where import Package.Base import Package.Data +import Package.Compile import Package.Dependencies -- See Package.Base for definitions of basic types @@ -15,11 +16,13 @@ buildPackage :: Package -> TodoItem -> Rules () buildPackage pkg todoItem = do buildPackageData pkg todoItem buildPackageDependencies pkg todoItem + buildPackageCompile pkg todoItem packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments - want ["libraries/deepseq/dist-install/build/deepseq.m"] + want [ "libraries/deepseq/dist-install/build/Control/DeepSeq.o" + , "libraries/deepseq/dist-install/build/Control/DeepSeq.p_o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem diff --git a/src/Package/Data.hs b/src/Package/Data.hs index fd8dd2c..919d7a5 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -38,7 +38,7 @@ configureArgs stage settings = <> argConf "--with-cc" Gcc buildPackageData :: Package -> TodoItem -> Rules () -buildPackageData pkg @ (Package name path _) (stage, dist, settings) = +buildPackageData (Package name path _) (stage, dist, settings) = let buildDir = path dist cabalArgs = arg ["configure", path, dist] -- this is a positional argument, hence: diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 5b10ca1..26b154f 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -3,34 +3,8 @@ module Package.Dependencies (buildPackageDependencies) where import Package.Base -packageArgs :: Stage -> FilePath -> Args -packageArgs stage pkgData = do - usePackageKey <- SupportsPackageKey || stage /= Stage0 - arg ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] - <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") - <> keyArgs usePackageKey - where - keyArgs True = prefixArgs "-this-package-key" (PackageKey pkgData) <> - prefixArgs "-package-key" (DepKeys pkgData) - keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> - prefixArgs "-package" (Deps pkgData) - -includeArgs :: ShowArgs a => String -> FilePath -> a -> Args -includeArgs prefix path as = map includePath <$> arg as - where - includePath dir | isRelative dir = prefix ++ path dir - | isAbsolute dir = prefix dir - -srcArgs :: FilePath -> FilePath -> Args -srcArgs path pkgData = do - mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) - dirs <- arg (SrcDirs pkgData) - srcs <- getDirectoryFiles "" - [path dir mPath <.> ext | dir <- dirs, mPath <- mods, ext <- ["hs", "lhs"]] - arg (map normalise srcs) - buildPackageDependencies :: Package -> TodoItem -> Rules () -buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = +buildPackageDependencies (Package name path _) (stage, dist, settings) = let buildDir = path dist pkgData = buildDir "package-data.mk" in From git at git.haskell.org Thu Oct 26 23:20:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports, add comments. (5603275) Message-ID: <20171026232003.3876B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5603275f1aeeb2b3469307859daabcd6f957d8c9/ghc >--------------------------------------------------------------- commit 5603275f1aeeb2b3469307859daabcd6f957d8c9 Author: Andrey Mokhov Date: Sat Aug 22 22:18:14 2015 +0100 Refactor imports, add comments. >--------------------------------------------------------------- 5603275f1aeeb2b3469307859daabcd6f957d8c9 src/Expression.hs | 7 ++----- src/GHC.hs | 13 +++++++------ src/Main.hs | 12 ++++++------ src/Package.hs | 21 ++++++++++----------- src/Rules.hs | 3 +-- src/Rules/Actions.hs | 4 +--- src/Rules/Cabal.hs | 7 +++---- src/Rules/Compile.hs | 9 +++------ src/Rules/Data.hs | 7 ++----- src/Rules/Dependencies.hs | 7 ++----- src/Rules/Documentation.hs | 7 +------ src/Rules/Library.hs | 3 +-- src/Target.hs | 3 +-- src/Way.hs | 2 ++ 14 files changed, 42 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5603275f1aeeb2b3469307859daabcd6f957d8c9 From git at git.haskell.org Thu Oct 26 23:20:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add src/Package/Compile.hs. (e315d33) Message-ID: <20171026232006.983DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e315d3381d2441e5acfc86384fb7eff9575cb006/ghc >--------------------------------------------------------------- commit e315d3381d2441e5acfc86384fb7eff9575cb006 Author: Andrey Mokhov Date: Sun Jan 11 03:31:34 2015 +0000 Add src/Package/Compile.hs. >--------------------------------------------------------------- e315d3381d2441e5acfc86384fb7eff9575cb006 src/Package/Compile.hs | 43 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 43 insertions(+) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs new file mode 100644 index 0000000..0733a46 --- /dev/null +++ b/src/Package/Compile.hs @@ -0,0 +1,43 @@ +{-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} +module Package.Compile (buildPackageCompile) where + +import Package.Base +import Development.Shake.Util + +-- "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.o + +suffixArgs :: Way -> Args +suffixArgs way = arg ["-hisuf", hisuf way, "-osuf", osuf way, "-hcsuf", hcsuf way] + +buildPackageCompile :: Package -> TodoItem -> Rules () +buildPackageCompile (Package name path _) (stage, dist, settings) = + let buildDir = path dist + pkgData = buildDir "package-data.mk" + depFile = buildDir "build" name <.> "m" + in + (buildDir "build//*o") %> \out -> do + let way = detectWay $ tail $ takeExtension out + need ["shake/src/Package/Compile.hs"] -- Track changes in this file + need [depFile] + depContents <- parseMakefile <$> (liftIO $ readFile depFile) + let deps = concat $ snd $ unzip $ filter ((== out) . fst) depContents + srcs = filter ("//*hs" ?==) deps + need deps + run (Ghc stage) $ suffixArgs way + <> wayHcArgs way + <> arg SrcHcOpts + <> packageArgs stage pkgData + <> arg "-i" + <> includeArgs "-i" path (SrcDirs pkgData) + <> includeArgs "-i" buildDir ["build", "build/autogen"] + <> includeArgs "-I" buildDir ["build", "build/autogen"] + <> includeArgs "-I" path (IncludeDirs pkgData) + <> arg "-optP-include" -- TODO: Shall we also add -cpp? + <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + <> arg ["-Wall", "-XHaskell2010", "-O2"] -- TODO: now we have both -O and -O2 + <> arg ["-odir" , buildDir "build"] + <> arg ["-hidir" , buildDir "build"] + <> arg ["-stubdir" , buildDir "build"] + <> arg "-split-objs" + <> arg ("-c":srcs) + <> arg ["-o", out] From git at git.haskell.org Thu Oct 26 23:20:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code, add comments. (b04c769) Message-ID: <20171026232006.AA5013A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b04c76947514b996239afde8b7b460c7bbadfea1/ghc >--------------------------------------------------------------- commit b04c76947514b996239afde8b7b460c7bbadfea1 Author: Andrey Mokhov Date: Sun Aug 23 00:04:55 2015 +0100 Clean up code, add comments. >--------------------------------------------------------------- b04c76947514b996239afde8b7b460c7bbadfea1 src/Base.hs | 2 + src/Expression.hs | 20 +++--- src/Oracles/ArgsHash.hs | 6 +- src/Oracles/Config/Flag.hs | 19 +++--- src/Oracles/Config/Setting.hs | 8 ++- src/Oracles/Dependencies.hs | 6 +- src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 6 +- src/Oracles/WindowsRoot.hs | 5 +- src/Predicates.hs | 32 +++++----- src/Rules.hs | 12 ++-- src/Rules/Actions.hs | 1 + src/Rules/Dependencies.hs | 1 - src/Rules/Documentation.hs | 12 +--- src/Settings.hs | 72 +++++++++++++++++++++- src/Settings/Args.hs | 9 +-- src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Gcc.hs | 40 ++++++------ src/Settings/Builders/Ghc.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 41 +++++++++---- src/Settings/Builders/GhcPkg.hs | 3 +- src/Settings/Builders/Haddock.hs | 9 +-- src/Settings/Builders/Ld.hs | 5 +- src/Settings/Packages.hs | 5 +- src/Settings/TargetDirectory.hs | 4 +- src/Settings/User.hs | 3 +- src/Settings/Util.hs | 125 -------------------------------------- src/Settings/Ways.hs | 4 +- src/Target.hs | 2 +- 29 files changed, 190 insertions(+), 268 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b04c76947514b996239afde8b7b460c7bbadfea1 From git at git.haskell.org Thu Oct 26 23:20:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (89c8f79) Message-ID: <20171026232010.084783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/89c8f7943a320e688f3664b225c6ab21d7685bc2/ghc >--------------------------------------------------------------- commit 89c8f7943a320e688f3664b225c6ab21d7685bc2 Author: Andrey Mokhov Date: Sun Jan 11 13:10:20 2015 +0000 Clean up. >--------------------------------------------------------------- 89c8f7943a320e688f3664b225c6ab21d7685bc2 src/Ways.hs | 28 +++++++++++----------------- 1 file changed, 11 insertions(+), 17 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 843383e..368e449 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -30,9 +30,6 @@ data Way = Way } deriving Eq -instance Show Way where - show = tag - vanilla = Way "v" [] profiling = Way "p" [Profiling] logging = Way "l" [Logging] @@ -40,7 +37,6 @@ parallel = Way "mp" [Parallel] granSim = Way "gm" [GranSim] -- RTS only ways - threaded = Way "thr" [Threaded] threadedProfiling = Way "thr_p" [Threaded, Profiling] threadedLogging = Way "thr_l" [Threaded, Logging] @@ -71,22 +67,20 @@ defaultWays :: Stage -> Action [Way] defaultWays stage = do sharedLibs <- platformSupportsSharedLibs return $ [vanilla] - ++ [profiling | stage /= Stage0] - ++ [dynamic | sharedLibs ] + ++ [profiling | stage /= Stage0] + ++ [dynamic | sharedLibs ] wayHcArgs :: Way -> Args wayHcArgs (Way _ units) = - mconcat - [ when (Dynamic `notElem` units) $ arg ["-static"] - , when (Dynamic `elem` units) $ arg ["-fPIC", "-dynamic"] - , when (Threaded `elem` units) $ arg ["-optc-DTHREADED_RTS"] - , when (Debug `elem` units) $ arg ["-optc-DDEBUG"] - , when (Profiling `elem` units) $ arg ["-prof"] - , when (Logging `elem` units) $ arg ["-eventlog"] - , when (Parallel `elem` units) $ arg ["-parallel"] - , when (GranSim `elem` units) $ arg ["-gransim"] - , when (units == [Debug] || units == [Debug, Dynamic]) $ arg ["-ticky", "-DTICKY_TICKY"] - ] + when (Dynamic `notElem` units) (arg "-static") + <> when (Dynamic `elem` units) (arg ["-fPIC", "-dynamic"]) + <> when (Threaded `elem` units) (arg "-optc-DTHREADED_RTS") + <> when (Debug `elem` units) (arg "-optc-DDEBUG") + <> when (Profiling `elem` units) (arg "-prof") + <> when (Logging `elem` units) (arg "-eventlog") + <> when (Parallel `elem` units) (arg "-parallel") + <> when (GranSim `elem` units) (arg "-gransim") + <> when (units == [Debug] || units == [Debug, Dynamic]) (arg ["-ticky", "-DTICKY_TICKY"]) suffix :: Way -> String suffix way | way == vanilla = "" From git at git.haskell.org Thu Oct 26 23:20:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Ghc/GhcM arguments. (3039df4) Message-ID: <20171026232010.17FFA3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3039df428add9752791ecba96a9bef8fc41980f3/ghc >--------------------------------------------------------------- commit 3039df428add9752791ecba96a9bef8fc41980f3 Author: Andrey Mokhov Date: Sun Aug 23 00:33:01 2015 +0100 Fix Ghc/GhcM arguments. >--------------------------------------------------------------- 3039df428add9752791ecba96a9bef8fc41980f3 src/Settings/Builders/Ghc.hs | 35 +++++++++++++++++++---------------- 1 file changed, 19 insertions(+), 16 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 6ecc26d..5ab520e 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,7 +2,7 @@ module Settings.Builders.Ghc (ghcArgs, ghcMArgs, commonGhcArgs) where import Expression import Oracles -import Predicates (stagedBuilder, splitObjects, stage0) +import Predicates (stagedBuilder, splitObjects, stage0, notStage0) import Settings -- TODO: add support for -dyno @@ -15,6 +15,12 @@ ghcArgs = stagedBuilder Ghc ? do file <- getFile srcs <- getSources mconcat [ commonGhcArgs + , arg "-H32m" + , stage0 ? arg "-O" + , notStage0 ? arg "-O2" + , arg "-Wall" + , arg "-fwarn-tabs" + , splitObjects ? arg "-split-objs" , arg "-c", append srcs , arg "-o", arg file ] @@ -25,6 +31,7 @@ ghcMArgs = stagedBuilder GhcM ? do srcs <- getSources mconcat [ arg "-M" , commonGhcArgs + , arg "-include-pkg-deps" , arg "-dep-makefile", arg file , append $ concat [ ["-dep-suffix", wayPrefix w] | w <- ways ] , append srcs ] @@ -46,10 +53,9 @@ commonGhcArgs = do , append hsArgs , append $ map ("-optP" ++) cppArgs , arg "-odir" , arg buildPath - , arg "-stubdir" , arg buildPath , arg "-hidir" , arg buildPath - , splitObjects ? arg "-split-objs" - , arg "-rtsopts" ] -- TODO: is this needed? + , arg "-stubdir" , arg buildPath + , arg "-rtsopts" ] -- TODO: ifeq "$(HC_VERSION_GE_6_13)" "YES" -- TODO: do '-ticky' in all debug ways? wayGhcArgs :: Args @@ -76,7 +82,6 @@ packageGhcArgs = do mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" - , arg "-include-pkg-deps" , stage0 ? arg "-package-db libraries/bootstrapping.conf" , if supportsPackageKey || stage /= Stage0 then arg $ "-this-package-key " ++ pkgKey @@ -89,19 +94,17 @@ includeGhcArgs = do path <- getTargetPath srcDirs <- getPkgDataList SrcDirs incDirs <- getPkgDataList IncludeDirs - cppArgs <- getPkgDataList CppArgs let buildPath = path -/- "build" autogenPath = buildPath -/- "autogen" - mconcat - [ arg "-i" - , arg $ "-i" ++ buildPath - , arg $ "-i" ++ autogenPath - , arg $ "-I" ++ buildPath - , arg $ "-I" ++ autogenPath - , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] - , arg "-optP-include", arg $ "-optP" ++ autogenPath -/- "cabal_macros.h" - , append $ map ("-optP" ++) cppArgs ] + mconcat [ arg "-i" + , arg $ "-i" ++ buildPath + , arg $ "-i" ++ autogenPath + , arg $ "-I" ++ buildPath + , arg $ "-I" ++ autogenPath + , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] + , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] + , arg "-optP-include" + , arg $ "-optP" ++ autogenPath -/- "cabal_macros.h" ] -- TODO: see ghc.mk -- # And then we strip it out again before building the package: From git at git.haskell.org Thu Oct 26 23:20:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor duplicated code into pathArgs, outputArgs and includeArgs functions. (9fbf3c8) Message-ID: <20171026232013.6C0C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9fbf3c8c37ac973da0574bd4a3dbe7bb2c012a32/ghc >--------------------------------------------------------------- commit 9fbf3c8c37ac973da0574bd4a3dbe7bb2c012a32 Author: Andrey Mokhov Date: Sun Jan 11 13:33:27 2015 +0000 Refactor duplicated code into pathArgs, outputArgs and includeArgs functions. >--------------------------------------------------------------- 9fbf3c8c37ac973da0574bd4a3dbe7bb2c012a32 src/Package/Base.hs | 26 +++++++++++++++++++++----- src/Package/Compile.hs | 14 +++----------- src/Package/Dependencies.hs | 13 +++---------- 3 files changed, 27 insertions(+), 26 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 4ef03fb..d1bf6ac 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -8,6 +8,7 @@ module Package.Base ( defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, bootPkgConstraints, + pathArgs, outputArgs, packageArgs, includeArgs, srcArgs ) where @@ -77,6 +78,15 @@ bootPkgConstraints = mempty -- $(foreach p,$(basename $(notdir $(wildcard libraries/$d/*.cabal))),\ -- --constraint "$p == $(shell grep -i "^Version:" libraries/$d/$p.cabal | sed "s/[^0-9.]//g")")) +pathArgs :: ShowArgs a => String -> FilePath -> a -> Args +pathArgs prefix path as = map includePath <$> arg as + where + includePath dir | isRelative dir = prefix ++ normaliseEx (path dir) + | isAbsolute dir = prefix normaliseEx dir + +outputArgs :: [String] -> FilePath -> Args +outputArgs keys dir = arg $ concatMap (\k -> [k, normaliseEx dir]) keys + packageArgs :: Stage -> FilePath -> Args packageArgs stage pkgData = do usePackageKey <- SupportsPackageKey || stage /= Stage0 @@ -89,11 +99,17 @@ packageArgs stage pkgData = do keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> prefixArgs "-package" (Deps pkgData) -includeArgs :: ShowArgs a => String -> FilePath -> a -> Args -includeArgs prefix path as = map includePath <$> arg as - where - includePath dir | isRelative dir = prefix ++ path dir - | isAbsolute dir = prefix dir +includeArgs :: FilePath -> FilePath -> Args +includeArgs path dist = + let buildDir = path dist + pkgData = buildDir "package-data.mk" + in arg "-i" + <> pathArgs "-i" path (SrcDirs pkgData) + <> pathArgs "-i" buildDir ["build", "build/autogen"] + <> pathArgs "-I" buildDir ["build", "build/autogen"] + <> pathArgs "-I" path (IncludeDirs pkgData) + <> arg "-optP-include" -- TODO: Shall we also add -cpp? + <> pathArgs "-optP" buildDir "build/autogen/cabal_macros.h" srcArgs :: FilePath -> FilePath -> Args srcArgs path pkgData = do diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 0733a46..14296c0 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -21,23 +21,15 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = need [depFile] depContents <- parseMakefile <$> (liftIO $ readFile depFile) let deps = concat $ snd $ unzip $ filter ((== out) . fst) depContents - srcs = filter ("//*hs" ?==) deps + srcs = filter ("//*hs" ?==) deps -- TODO: handle *.c sources need deps run (Ghc stage) $ suffixArgs way <> wayHcArgs way <> arg SrcHcOpts <> packageArgs stage pkgData - <> arg "-i" - <> includeArgs "-i" path (SrcDirs pkgData) - <> includeArgs "-i" buildDir ["build", "build/autogen"] - <> includeArgs "-I" buildDir ["build", "build/autogen"] - <> includeArgs "-I" path (IncludeDirs pkgData) - <> arg "-optP-include" -- TODO: Shall we also add -cpp? - <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + <> includeArgs path dist <> arg ["-Wall", "-XHaskell2010", "-O2"] -- TODO: now we have both -O and -O2 - <> arg ["-odir" , buildDir "build"] - <> arg ["-hidir" , buildDir "build"] - <> arg ["-stubdir" , buildDir "build"] + <> outputArgs ["-odir", "-hidir", "-stubdir"] (buildDir "build") <> arg "-split-objs" <> arg ("-c":srcs) <> arg ["-o", out] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 26b154f..18c2015 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -12,16 +12,9 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file run (Ghc stage) $ arg "-M" <> packageArgs stage pkgData - <> arg "-i" - <> includeArgs "-i" path (SrcDirs pkgData) - <> includeArgs "-i" buildDir ["build", "build/autogen"] - <> includeArgs "-I" buildDir ["build", "build/autogen"] - <> includeArgs "-I" path (IncludeDirs pkgData) - <> arg "-optP-include" -- TODO: Shall we also add -cpp? - <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") - <> arg ["-odir" , buildDir "build"] - <> arg ["-stubdir" , buildDir "build"] - <> arg ["-dep-makefile", out ] + <> includeArgs path dist + <> outputArgs ["-odir", "-stubdir"] (buildDir "build") + <> arg ["-dep-makefile", out] <> prefixArgs "-dep-suffix" (map suffix <$> ways settings) <> srcArgs path pkgData -- <> arg SrcHcOpts -- TODO: Check that skipping all _HC_OPTS is safe. From git at git.haskell.org Thu Oct 26 23:20:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate only one rule for Haddock (Stage1). (cdf208c) Message-ID: <20171026232013.8740E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cdf208c342c346b48f848e06b9ffc8a089326254/ghc >--------------------------------------------------------------- commit cdf208c342c346b48f848e06b9ffc8a089326254 Author: Andrey Mokhov Date: Sun Aug 23 01:04:55 2015 +0100 Generate only one rule for Haddock (Stage1). >--------------------------------------------------------------- cdf208c342c346b48f848e06b9ffc8a089326254 src/Rules/Documentation.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 81e3140..5978cfd 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -10,10 +10,10 @@ import Settings -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. buildPackageDocumentation :: Resources -> PartialTarget -> Rules () -buildPackageDocumentation _ target @ (PartialTarget _ pkg) = +buildPackageDocumentation _ target @ (PartialTarget stage pkg) = let cabalFile = pkgCabalFile pkg haddockFile = pkgHaddockFile pkg - in do + in when (stage == Stage1) $ do haddockFile %> \file -> do whenM (specified HsColour) $ do need [cabalFile] From git at git.haskell.org Thu Oct 26 23:20:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an infix version of when (). (f913c35) Message-ID: <20171026232017.336A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f913c3580b486bf0c0aaf42fdc5090668cb63ab2/ghc >--------------------------------------------------------------- commit f913c3580b486bf0c0aaf42fdc5090668cb63ab2 Author: Andrey Mokhov Date: Sun Jan 11 15:15:29 2015 +0000 Add an infix version of when (). >--------------------------------------------------------------- f913c3580b486bf0c0aaf42fdc5090668cb63ab2 src/Oracles/Flag.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 354b1d7..946c4fb 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -4,7 +4,7 @@ module Oracles.Flag ( module Control.Monad, module Prelude, Flag (..), - test, when, unless, not, (&&), (||) + test, when, unless, not, (&&), (||), () ) where import Control.Monad hiding (when, unless) @@ -60,6 +60,10 @@ unless x act = do bool <- toCondition x if bool then mempty else act +-- Infix version of when +() :: (ToCondition a, Monoid m) => a -> Action m -> Action m +() = when + class Not a where type NotResult a not :: a -> NotResult a From git at git.haskell.org Thu Oct 26 23:20:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (a9adcf3) Message-ID: <20171026232017.48B2B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9adcf31d5daf441cfa4efc5ac4012a3836c9b19/ghc >--------------------------------------------------------------- commit a9adcf31d5daf441cfa4efc5ac4012a3836c9b19 Author: Andrey Mokhov Date: Sat Sep 19 00:04:02 2015 +0100 Clean up. >--------------------------------------------------------------- a9adcf31d5daf441cfa4efc5ac4012a3836c9b19 arg/README.md | 5 ----- src/Builder.hs | 13 +++++++------ src/Oracles/Config/Setting.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Rules/Cabal.hs | 4 ++-- src/Settings/Args.hs | 8 ++++---- src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Packages.hs | 4 +--- src/Stage.hs | 2 +- 10 files changed, 18 insertions(+), 25 deletions(-) diff --git a/arg/README.md b/arg/README.md deleted file mode 100644 index 0af8834..0000000 --- a/arg/README.md +++ /dev/null @@ -1,5 +0,0 @@ -This folder serves two purposes: - -* Tracking argument lists produced by rules - -* Documentation diff --git a/src/Builder.hs b/src/Builder.hs index dde37c1..8e5f639 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -36,14 +36,14 @@ builderKey builder = case builder of Ar -> "ar" Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" - GccM stage -> builderKey $ Gcc stage -- Synonym for 'Gcc -MM' + GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - GhcM stage -> builderKey $ Ghc stage -- Synonym for 'Ghc -M' + GhcM stage -> builderKey $ Ghc stage -- synonym for 'Ghc -M' GhcCabal -> "ghc-cabal" - GhcCabalHsColour -> builderKey $ GhcCabal -- Synonym for 'GhcCabal hscolour' + GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" Happy -> "happy" @@ -72,9 +72,10 @@ needBuilder laxDependencies builder = do else need [path] where allowOrderOnlyDependency :: Builder -> Bool - allowOrderOnlyDependency (Ghc _) = True - allowOrderOnlyDependency (GhcM _) = True - allowOrderOnlyDependency _ = False + allowOrderOnlyDependency b = case b of + Ghc _ -> True + GhcM _ -> True + _ -> False -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 27b2d89..f0f7fb7 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -7,8 +7,8 @@ module Oracles.Config.Setting ( ) where import Base -import Stage import Oracles.Config +import Stage -- Each Setting comes from the system.config file, e.g. 'target-os = mingw32'. -- setting TargetOs looks up the config file and returns "mingw32". diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 1898d21..0d1a0b4 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -2,8 +2,8 @@ module Oracles.PackageDeps (packageDeps, packageDepsOracle) where import Base -import Package import qualified Data.HashMap.Strict as Map +import Package newtype PackageDepsKey = PackageDepsKey PackageName deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index b958db4..aac8ab2 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,11 +1,11 @@ module Rules.Cabal (cabalRules) where +import Expression import Data.Version import Distribution.Package -import Distribution.Verbosity import Distribution.PackageDescription import Distribution.PackageDescription.Parse -import Expression +import Distribution.Verbosity import Package hiding (library) import Settings diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 4e55a3d..5a8c63a 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -1,14 +1,14 @@ module Settings.Args (getArgs) where import Expression -import Settings.User import Settings.Builders.Ar -import Settings.Builders.Ld -import Settings.Builders.Ghc import Settings.Builders.Gcc +import Settings.Builders.Ghc +import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg import Settings.Builders.Haddock -import Settings.Builders.GhcCabal +import Settings.Builders.Ld +import Settings.User getArgs :: Expr [String] getArgs = fromDiffExpr $ defaultArgs <> userArgs diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 617d4e1..082cbaf 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,6 +1,5 @@ module Settings.Builders.Ar (arArgs, arPersistentArgsCount) where -import Builder import Expression import Predicates (builder) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index bc6622c..2cd26d0 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -1,8 +1,8 @@ module Settings.Builders.Haddock (haddockArgs) where import Expression -import Predicates hiding (file) import Oracles +import Predicates hiding (file) import Settings import Settings.Builders.Ghc diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 7f2a64b..87f293d 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -1,6 +1,4 @@ -module Settings.Packages ( - getPackages, knownPackages, findKnownPackage - ) where +module Settings.Packages (getPackages, knownPackages, findKnownPackage) where import Expression import Predicates diff --git a/src/Stage.hs b/src/Stage.hs index 50a273b..edddb6f 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -4,7 +4,7 @@ module Stage (Stage (..)) where import Base import GHC.Generics (Generic) --- TODO: rename to something more meaningful, e.g. Stage0 -> Boot. +-- TODO: rename to something more meaningful, e.g. 'Stage0' -> 'Boot'. data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum, Generic) instance Show Stage where From git at git.haskell.org Thu Oct 26 23:20:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add productArgs and concatArgs helper functions. (018f850) Message-ID: <20171026232021.405093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/018f8501c40e1c8b70da99c2b836750e9815f75d/ghc >--------------------------------------------------------------- commit 018f8501c40e1c8b70da99c2b836750e9815f75d Author: Andrey Mokhov Date: Sun Jan 11 17:01:02 2015 +0000 Add productArgs and concatArgs helper functions. >--------------------------------------------------------------- 018f8501c40e1c8b70da99c2b836750e9815f75d src/Base.hs | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 38790e6..b84b48c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,12 +12,12 @@ module Base ( Condition (..), (<+>), filterOut, - prefixArgs + productArgs, concatArgs ) where -import Development.Shake +import Development.Shake hiding ((*>)) import Development.Shake.FilePath -import Control.Applicative hiding ((*>)) +import Control.Applicative import Data.Function import Data.Monoid import Data.List @@ -32,9 +32,10 @@ instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q +-- Using the Creators' trick for overlapping String instances class ShowArgs a where showArgs :: a -> Args - showListArgs :: [a] -> Args -- the Creators' trick for overlapping String instances + showListArgs :: [a] -> Args showListArgs = mconcat . map showArgs instance ShowArgs Char where @@ -62,8 +63,18 @@ filterOut as exclude = do exclude' <- showArgs exclude filter (`notElem` exclude') <$> as --- Prefix each arg in a collection with a given prefix -prefixArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args -prefixArgs prefix as = do - prefix' <- showArgs prefix - concatMap (\a -> prefix' ++ [a]) <$> showArgs as +-- Generate a cross product collection of two argument collections +-- Example: productArgs ["-a", "-b"] "c" = arg ["-a", "c", "-b", "c"] +productArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args +productArgs as bs = do + as' <- showArgs as + bs' <- showArgs bs + return $ concat $ sequence [as', bs'] + +-- Similar to productArgs but concat resulting arguments pairwise +-- Example: concatArgs ["-a", "-b"] "c" = arg ["-ac", "-bc"] +concatArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args +concatArgs as bs = do + as' <- showArgs as + bs' <- showArgs bs + return $ map concat $ sequence [as', bs'] From git at git.haskell.org Thu Oct 26 23:20:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generatePackageCode rule, alexArgs, happyArgs and Hsc2Hs builder. (fdbc3fb) Message-ID: <20171026232021.43E913A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fdbc3fba223a2d437954bd0908fdb839fe836ac8/ghc >--------------------------------------------------------------- commit fdbc3fba223a2d437954bd0908fdb839fe836ac8 Author: Andrey Mokhov Date: Sun Sep 20 02:22:46 2015 +0100 Add generatePackageCode rule, alexArgs, happyArgs and Hsc2Hs builder. >--------------------------------------------------------------- fdbc3fba223a2d437954bd0908fdb839fe836ac8 cfg/system.config.in | 2 ++ doc/demo.txt | 5 ++++ src/Builder.hs | 2 ++ src/Rules/Documentation.hs | 6 ++--- src/Rules/Generate.hs | 55 ++++++++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 2 ++ src/Settings/Args.hs | 20 +++++++++------ src/Settings/Builders/Alex.hs | 14 +++++++++++ src/Settings/Builders/Happy.hs | 13 ++++++++++ 9 files changed, 108 insertions(+), 11 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index a274e84..b92b6ba 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -19,6 +19,8 @@ ghc-cabal = @hardtop@/inplace/bin/ghc-cabal haddock = @hardtop@/inplace/bin/haddock +hsc2hs = @hardtop@/inplace/bin/hsc2hs + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ diff --git a/doc/demo.txt b/doc/demo.txt index 7acd27d..28b3689 100644 --- a/doc/demo.txt +++ b/doc/demo.txt @@ -12,3 +12,8 @@ * https://mail.haskell.org/pipermail/ghc-commits/2013-May/001712.html * see ghc.mk, comment about parallel ghc-pkg invokations + +5. Discovered dead code in the old build system, e.g: + +* Alex3 variable not needed as Alex 3.1 is required. +* There are no generated *.y/*.ly files, hence they can never be in the build directory. \ No newline at end of file diff --git a/src/Builder.hs b/src/Builder.hs index 8e5f639..3a24df3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -26,6 +26,7 @@ data Builder = Alex | Haddock | Happy | HsColour + | Hsc2Hs | Ld deriving (Show, Eq, Generic) @@ -49,6 +50,7 @@ builderKey builder = case builder of Happy -> "happy" Haddock -> "haddock" HsColour -> "hscolour" + Hsc2Hs -> "hsc2hs" Ld -> "ld" builderPath :: Builder -> Action FilePath diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 5978cfd..2ebaa59 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -10,9 +10,9 @@ import Settings -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. buildPackageDocumentation :: Resources -> PartialTarget -> Rules () -buildPackageDocumentation _ target @ (PartialTarget stage pkg) = - let cabalFile = pkgCabalFile pkg - haddockFile = pkgHaddockFile pkg +buildPackageDocumentation _ target @ (PartialTarget stage package) = + let cabalFile = pkgCabalFile package + haddockFile = pkgHaddockFile package in when (stage == Stage1) $ do haddockFile %> \file -> do whenM (specified HsColour) $ do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs new file mode 100644 index 0000000..055dccb --- /dev/null +++ b/src/Rules/Generate.hs @@ -0,0 +1,55 @@ +module Rules.Generate (generatePackageCode) where + +import Expression +import Oracles +import Rules.Actions +import Rules.Resources +import Settings + +-- The following generators and corresponding source extensions are supported: +knownGenerators :: [ (Builder, String) ] +knownGenerators = [ (Alex , ".x" ) + , (Happy , ".y" ) + , (Happy , ".ly" ) + , (Hsc2Hs , ".hsc") ] + +determineBuilder :: FilePath -> Maybe Builder +determineBuilder file = fmap fst $ find (\(_, e) -> e == ext) knownGenerators + where + ext = takeExtension file + +generatePackageCode :: Resources -> PartialTarget -> Rules () +generatePackageCode _ target @ (PartialTarget stage package) = + let path = targetPath stage package + packagePath = pkgPath package + buildPath = path -/- "build" + in do + buildPath "*.hs" %> \file -> do + dirs <- interpretPartial target $ getPkgDataList SrcDirs + files <- getDirectoryFiles "" $ + [ packagePath d takeBaseName file <.> "*" | d <- dirs ] + let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] + (src, builder) = head gens + when (length gens /= 1) . putError $ + "Exactly one generator expected for " ++ file + ++ "(found: " ++ show gens ++ ")." + need [src] + build $ fullTarget target builder [src] [file] + +-- $1/$2/build/%.hs : $1/$3/%.ly | $$$$(dir $$$$@)/. +-- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ + +-- $1/$2/build/%.hs : $1/$3/%.y | $$$$(dir $$$$@)/. +-- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ + +-- $1/$2/build/%_hsc.c $1/$2/build/%_hsc.h $1/$2/build/%.hs : $1/$3/%.hsc $$$$(hsc2hs_INPLACE) | $$$$(dir $$$$@)/. +-- $$(call cmd,hsc2hs_INPLACE) $$($1_$2_ALL_HSC2HS_OPTS) $$< -o $$@ + +-- # Now the rules for hs-boot files. + +-- $1/$2/build/%.hs-boot : $1/$3/%.hs-boot +-- "$$(CP)" $$< $$@ + +-- $1/$2/build/%.lhs-boot : $1/$3/%.lhs-boot +-- "$$(CP)" $$< $$@ + diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index dfc15e8..9da4f8b 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -5,6 +5,7 @@ import Rules.Compile import Rules.Data import Rules.Dependencies import Rules.Documentation +import Rules.Generate import Rules.Library import Rules.Resources import Target @@ -13,6 +14,7 @@ buildPackage :: Resources -> PartialTarget -> Rules () buildPackage = mconcat [ buildPackageData , buildPackageDependencies + , generatePackageCode , compilePackage , buildPackageLibrary , buildPackageDocumentation ] diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 5a8c63a..2e2f379 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -1,12 +1,14 @@ module Settings.Args (getArgs) where import Expression +import Settings.Builders.Alex import Settings.Builders.Ar import Settings.Builders.Gcc import Settings.Builders.Ghc import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg import Settings.Builders.Haddock +import Settings.Builders.Happy import Settings.Builders.Ld import Settings.User @@ -23,14 +25,16 @@ getArgs = fromDiffExpr $ defaultArgs <> userArgs -- TODO: is GhcHcOpts=-Rghc-timing needed? defaultArgs :: Args defaultArgs = mconcat - [ cabalArgs - , ghcPkgArgs - , ghcMArgs - , gccMArgs - , ghcArgs - , gccArgs + [ alexArgs , arArgs - , ldArgs + , cabalArgs + , customPackageArgs + , ghcArgs , ghcCabalHsColourArgs + , ghcMArgs + , ghcPkgArgs + , gccArgs + , gccMArgs , haddockArgs - , customPackageArgs ] + , happyArgs + , ldArgs ] diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs new file mode 100644 index 0000000..6aedcdb --- /dev/null +++ b/src/Settings/Builders/Alex.hs @@ -0,0 +1,14 @@ +module Settings.Builders.Alex (alexArgs) where + +import Expression +import GHC (compiler) +import Predicates (builder, package) + +alexArgs :: Args +alexArgs = builder Alex ? do + file <- getFile + src <- getSource + mconcat [ arg "-g" + , package compiler ? arg "--latin1" + , arg src + , arg "-o", arg file ] diff --git a/src/Settings/Builders/Happy.hs b/src/Settings/Builders/Happy.hs new file mode 100644 index 0000000..fcd962a --- /dev/null +++ b/src/Settings/Builders/Happy.hs @@ -0,0 +1,13 @@ +module Settings.Builders.Happy (happyArgs) where + +import Expression +import Predicates (builder) + +happyArgs :: Args +happyArgs = builder Happy ? do + file <- getFile + src <- getSource + mconcat [ arg "-agc" + , arg "--strict" + , arg src + , arg "-o", arg file ] From git at git.haskell.org Thu Oct 26 23:20:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor, limit lines at 80 characters. (128c5ac) Message-ID: <20171026232025.3B7263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4/ghc >--------------------------------------------------------------- commit 128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4 Author: Andrey Mokhov Date: Sun Jan 11 17:02:58 2015 +0000 Refactor, limit lines at 80 characters. >--------------------------------------------------------------- 128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4 src/Package/Base.hs | 70 ++++++++++++++++++++++----------------------- src/Package/Compile.hs | 39 +++++++++++++++++++------ src/Package/Data.hs | 39 +++++++++++++++---------- src/Package/Dependencies.hs | 18 ++++++------ 4 files changed, 99 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 128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4 From git at git.haskell.org Thu Oct 26 23:20:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Collect arguments for Hsc2Hs builder. (f225aed) Message-ID: <20171026232025.493973A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f225aedc18efa02b48f99ee84d0794eb4aa94368/ghc >--------------------------------------------------------------- commit f225aedc18efa02b48f99ee84d0794eb4aa94368 Author: Andrey Mokhov Date: Mon Sep 21 00:54:29 2015 +0100 Collect arguments for Hsc2Hs builder. >--------------------------------------------------------------- f225aedc18efa02b48f99ee84d0794eb4aa94368 src/Settings/Builders/Hsc2Hs.hs | 70 +++++++++++++++++++++++++++++++++++++++++ 1 file changed, 70 insertions(+) diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs new file mode 100644 index 0000000..fae7c1f --- /dev/null +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -0,0 +1,70 @@ +module Settings.Builders.Hsc2Hs (hsc2HsArgs) where + +import Expression +import Oracles +import Predicates (builder, stage0, notStage0) +import Settings +import Settings.Builders.GhcCabal + +hsc2HsArgs :: Args +hsc2HsArgs = builder Hsc2Hs ? do + stage <- getStage + src <- getSource + file <- getFile + ccPath <- lift . builderPath $ Gcc stage + gmpDirs <- getSettingList GmpIncludeDirs + cFlags <- getCFlags + lFlags <- getLFlags + hArch <- getSetting HostArch + hOs <- getSetting HostOs + tArch <- getSetting TargetArch + tOs <- getSetting TargetOs + version <- if stage == Stage0 + then lift $ ghcCanonVersion + else getSetting ProjectVersionInt + mconcat [ arg $ "--cc=" ++ ccPath + , arg $ "--ld=" ++ ccPath + , notWindowsHost ? arg "--cross-safe" + , append $ map ("-I" ++) gmpDirs + , append $ map ("--cflag=" ++) cFlags + , append $ map ("--lflag=" ++) lFlags + , notStage0 ? crossCompiling ? arg "--cross-compile" + , stage0 ? arg ("--cflag=-D" ++ hArch ++ "_HOST_ARCH=1") + , stage0 ? arg ("--cflag=-D" ++ hOs ++ "_HOST_OS=1" ) + , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") + , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) + , arg ("--cflag=-D__GLASGOW_HASKELL__=" ++ version) + , arg src + , arg "-o", arg file ] + +getCFlags :: Expr [String] +getCFlags = fromDiffExpr $ do + pkg <- getPackage + path <- getTargetPath + iDirs <- getPkgDataList IncludeDirs + dDirs <- getPkgDataList DepIncludeDirs + cppArgs <- getPkgDataList CppArgs + depCcArgs <- getPkgDataList DepCcArgs + mconcat [ ccArgs + , argStagedSettingList ConfCcArgs + , remove ["-O"] + , argStagedSettingList ConfCppArgs + , arg $ "-I" ++ path -/- "build/autogen" + , append [ "-I" ++ pkgPath pkg -/- dir | dir <- iDirs ++ dDirs ] + , append cppArgs + , append depCcArgs + , ccWarnings + , arg "-include", arg $ path -/- "build/autogen/cabal_macros.h" ] + +getLFlags :: Expr [String] +getLFlags = fromDiffExpr $ do + ldArgs <- getPkgDataList LdArgs + libDirs <- getPkgDataList DepLibDirs + extraLibs <- getPkgDataList DepExtraLibs + depLdArgs <- getPkgDataList DepLdArgs + mconcat [ argStagedSettingList ConfGccLinkerArgs + --, ldArgs -- TODO: resolve name conflict (ldArgs is currently empty) + , append ldArgs + , append $ [ "-L" ++ unifyPath dir | dir <- libDirs ] + , append $ [ "-l" ++ unifyPath dir | dir <- extraLibs ] + , append depLdArgs ] From git at git.haskell.org Thu Oct 26 23:20:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify: Package -> TodoItem -> Rules () is a monoid! (56689f0) Message-ID: <20171026232028.E5FB53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56689f0356383efb1cb285138cdd6b2a57d0fc11/ghc >--------------------------------------------------------------- commit 56689f0356383efb1cb285138cdd6b2a57d0fc11 Author: Andrey Mokhov Date: Sun Jan 11 19:25:46 2015 +0000 Simplify: Package -> TodoItem -> Rules () is a monoid! >--------------------------------------------------------------- 56689f0356383efb1cb285138cdd6b2a57d0fc11 src/Package.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 8f2850d..2fd10f1 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -11,12 +11,11 @@ import Package.Dependencies packages :: [Package] packages = [libraryPackage "deepseq" Stage1 defaultSettings] --- Rule buildXY is defined in module X.Y +-- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () -buildPackage pkg todoItem = do - buildPackageData pkg todoItem - buildPackageDependencies pkg todoItem - buildPackageCompile pkg todoItem +buildPackage = buildPackageData + <> buildPackageDependencies + <> buildPackageCompile packageRules :: Rules () packageRules = do From git at git.haskell.org Thu Oct 26 23:20:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more configuration flags. (b2928a3) Message-ID: <20171026232029.02CB43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2928a32abf293f02f4ebe8efe6349e6fb73bc4a/ghc >--------------------------------------------------------------- commit b2928a32abf293f02f4ebe8efe6349e6fb73bc4a Author: Andrey Mokhov Date: Mon Sep 21 00:55:17 2015 +0100 Add more configuration flags. >--------------------------------------------------------------- b2928a32abf293f02f4ebe8efe6349e6fb73bc4a cfg/system.config.in | 16 +++++++++++----- 1 file changed, 11 insertions(+), 5 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index b92b6ba..6bfb20d 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -5,14 +5,14 @@ #=================== system-ghc = @WithGhc@ -system-gcc = @CC_STAGE0@ -system-ghc-pkg = @GhcPkgCmd@ -gcc = @WhatGccIsCalled@ - ghc-stage1 = @hardtop@/inplace/bin/ghc-stage1 ghc-stage2 = @hardtop@/inplace/bin/ghc-stage2 ghc-stage3 = @hardtop@/inplace/bin/ghc-stage3 +system-gcc = @CC_STAGE0@ +gcc = @WhatGccIsCalled@ + +system-ghc-pkg = @GhcPkgCmd@ ghc-pkg = @hardtop@/inplace/bin/ghc-pkg ghc-cabal = @hardtop@/inplace/bin/ghc-cabal @@ -49,13 +49,19 @@ target-os = @TargetOS_CPP@ target-arch = @TargetArch_CPP@ target-platform-full = @TargetPlatformFull@ -host-os-cpp = @HostOS_CPP@ +host-os = @HostOS_CPP@ +host-arch = @HostArch_CPP@ cross-compiling = @CrossCompiling@ dynamic-extension = @soext_target@ +ghc-major-version = @GhcMajVersion@ +ghc-minor-version = @GhcMinVersion@ +ghc-patch-level = @GhcPatchLevel@ + project-version = @ProjectVersion@ +project-version-int = @ProjectVersionInt@ # Compilation and linking flags: #=============================== From git at git.haskell.org Thu Oct 26 23:20:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on dead/duplicated code. (e68f4ed) Message-ID: <20171026232032.926F23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e68f4ed4d3fbba7228a5eb9c9419ec00ca93c8f5/ghc >--------------------------------------------------------------- commit e68f4ed4d3fbba7228a5eb9c9419ec00ca93c8f5 Author: Andrey Mokhov Date: Mon Sep 21 00:56:55 2015 +0100 Add a note on dead/duplicated code. >--------------------------------------------------------------- e68f4ed4d3fbba7228a5eb9c9419ec00ca93c8f5 doc/demo.txt | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/doc/demo.txt b/doc/demo.txt index 28b3689..2c8bf75 100644 --- a/doc/demo.txt +++ b/doc/demo.txt @@ -13,7 +13,9 @@ * https://mail.haskell.org/pipermail/ghc-commits/2013-May/001712.html * see ghc.mk, comment about parallel ghc-pkg invokations -5. Discovered dead code in the old build system, e.g: +5. Discovered dead & duplicated code in the old build system, e.g: -* Alex3 variable not needed as Alex 3.1 is required. -* There are no generated *.y/*.ly files, hence they can never be in the build directory. \ No newline at end of file +* Alex3 variable not needed as Alex 3.1 is required +* There are no generated *.y/*.ly files, hence they can never be in the build directory +* hsc2hs gets multuple "--cflag=-I$1/$2/build/autogen" flags in one invokation +* No generated Haskell files actually require copying of *.(l)hs-boot files \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:20:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters. (d264db1) Message-ID: <20171026232032.8F47D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d264db1967999ff34350037afc0440128c7667d2/ghc >--------------------------------------------------------------- commit d264db1967999ff34350037afc0440128c7667d2 Author: Andrey Mokhov Date: Sun Jan 11 19:55:14 2015 +0000 Fit lines into 80 characters. >--------------------------------------------------------------- d264db1967999ff34350037afc0440128c7667d2 src/Ways.hs | 38 ++++++++++++++++++++++---------------- 1 file changed, 22 insertions(+), 16 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 368e449..c6d733c 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -21,7 +21,14 @@ module Ways ( import Base import Oracles -data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dynamic deriving Eq +data WayUnit = Profiling + | Logging + | Parallel + | GranSim + | Threaded + | Debug + | Dynamic + deriving Eq data Way = Way { @@ -36,7 +43,7 @@ logging = Way "l" [Logging] parallel = Way "mp" [Parallel] granSim = Way "gm" [GranSim] --- RTS only ways +-- RTS only ways. TODO: do we need to define these here? threaded = Way "thr" [Threaded] threadedProfiling = Way "thr_p" [Threaded, Profiling] threadedLogging = Way "thr_l" [Threaded, Logging] @@ -60,9 +67,6 @@ allWays = [vanilla, profiling, logging, parallel, granSim, threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic] --- TODO: what are ways 't' and 's'? --- ALL_WAYS=v p t l s mp mg debug dyn thr thr_l p_dyn debug_dyn thr_dyn thr_p_dyn thr_debug_dyn thr_p thr_debug debug_p thr_debug_p l_dyn thr_l_dyn - defaultWays :: Stage -> Action [Way] defaultWays stage = do sharedLibs <- platformSupportsSharedLibs @@ -70,17 +74,19 @@ defaultWays stage = do ++ [profiling | stage /= Stage0] ++ [dynamic | sharedLibs ] +-- TODO: do '-ticky' in all debug ways? wayHcArgs :: Way -> Args wayHcArgs (Way _ units) = - when (Dynamic `notElem` units) (arg "-static") - <> when (Dynamic `elem` units) (arg ["-fPIC", "-dynamic"]) - <> when (Threaded `elem` units) (arg "-optc-DTHREADED_RTS") - <> when (Debug `elem` units) (arg "-optc-DDEBUG") - <> when (Profiling `elem` units) (arg "-prof") - <> when (Logging `elem` units) (arg "-eventlog") - <> when (Parallel `elem` units) (arg "-parallel") - <> when (GranSim `elem` units) (arg "-gransim") - <> when (units == [Debug] || units == [Debug, Dynamic]) (arg ["-ticky", "-DTICKY_TICKY"]) + (Dynamic `notElem` units) arg "-static" + <> (Dynamic `elem` units) arg ["-fPIC", "-dynamic"] + <> (Threaded `elem` units) arg "-optc-DTHREADED_RTS" + <> (Debug `elem` units) arg "-optc-DDEBUG" + <> (Profiling `elem` units) arg "-prof" + <> (Logging `elem` units) arg "-eventlog" + <> (Parallel `elem` units) arg "-parallel" + <> (GranSim `elem` units) arg "-gransim" + <> (units == [Debug] || units == [Debug, Dynamic]) + arg ["-ticky", "-DTICKY_TICKY"] suffix :: Way -> String suffix way | way == vanilla = "" @@ -94,7 +100,7 @@ hcsuf = (++ "hc") . suffix -- Detect way from a given extension. Fail if the result is not unique. detectWay :: FilePath -> Way detectWay extension = case solutions of - [way] -> way - otherwise -> error $ "Cannot detect way from extension '" ++ extension ++ "'." + [way] -> way + _ -> error $ "Cannot detect way from extension '" ++ extension ++ "'." where solutions = [w | f <- [hisuf, osuf, hcsuf], w <- allWays, f w == extension] From git at git.haskell.org Thu Oct 26 23:20:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor oracle rules. (21e48fc) Message-ID: <20171026232036.96CA53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21e48fc51345e7294e1dd2a642a1c305230ceb2f/ghc >--------------------------------------------------------------- commit 21e48fc51345e7294e1dd2a642a1c305230ceb2f Author: Andrey Mokhov Date: Sun Jan 11 20:08:00 2015 +0000 Refactor oracle rules. >--------------------------------------------------------------- 21e48fc51345e7294e1dd2a642a1c305230ceb2f src/Oracles.hs | 34 ++++++++++++++++++++++------------ 1 file changed, 22 insertions(+), 12 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 3321610..3a0c430 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -17,31 +17,41 @@ import Oracles.Option import Oracles.Builder import Oracles.PackageData -oracleRules :: Rules () -oracleRules = do +defaultConfig, userConfig :: FilePath +defaultConfig = cfgPath "default.config" +userConfig = cfgPath "user.config" + +-- Oracle for configuration files. +configOracle :: Rules () +configOracle = do cfg <- newCache $ \() -> do - unless (doesFileExist $ cfgPath "default.config.in") $ do + unless (doesFileExist $ defaultConfig <.> "in") $ do error $ "\nDefault configuration file '" - ++ (cfgPath "default.config.in") + ++ (defaultConfig <.> "in") ++ "' is missing; unwilling to proceed." return () - need [cfgPath "default.config"] - cfgDefault <- liftIO $ readConfigFile $ cfgPath "default.config" - existsUser <- doesFileExist $ cfgPath "user.config" + need [defaultConfig] + cfgDefault <- liftIO $ readConfigFile defaultConfig + existsUser <- doesFileExist userConfig cfgUser <- if existsUser - then liftIO $ readConfigFile $ cfgPath "user.config" + then liftIO $ readConfigFile userConfig else do putLoud $ "\nUser defined configuration file '" - ++ (cfgPath "user.config") - ++ "' is missing; proceeding with default configuration.\n" + ++ userConfig ++ "' is missing; " + ++ "proceeding with default configuration.\n" return M.empty return $ cfgUser `M.union` cfgDefault - addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () + return () +-- Oracle for 'package-data.mk' files. +packageDataOracle :: Rules () +packageDataOracle = do pkgData <- newCache $ \file -> do need [file] liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () + +oracleRules :: Rules () +oracleRules = configOracle <> packageDataOracle From git at git.haskell.org Thu Oct 26 23:20:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for empty YES/NO flags (treat empty as NO). (8b1feb5) Message-ID: <20171026232036.A39573A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8b1feb5b13fc1c9848f2f0e39f271e5c1fb39c27/ghc >--------------------------------------------------------------- commit 8b1feb5b13fc1c9848f2f0e39f271e5c1fb39c27 Author: Andrey Mokhov Date: Mon Sep 21 00:57:40 2015 +0100 Add support for empty YES/NO flags (treat empty as NO). >--------------------------------------------------------------- 8b1feb5b13fc1c9848f2f0e39f271e5c1fb39c27 src/Oracles/Config/Flag.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index b73a687..d520a85 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -16,6 +16,8 @@ data Flag = CrossCompiling | SplitObjectsBroken | SupportsPackageKey +-- Note, if a flag is set to empty string we treat it as set to NO. This seems +-- fragile, but some flags do behave like this, e.g. GccIsClang. flag :: Flag -> Action Bool flag f = do key <- return $ case f of @@ -28,7 +30,7 @@ flag f = do SupportsPackageKey -> "supports-package-key" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." - unless (value == "YES" || value == "NO") . putError + unless (value == "YES" || value == "NO" || value == "") . putError $ "\nFlag '" ++ key ++ "' is set to '" ++ value ++ "' instead of 'YES' or 'NO'." return $ value == "YES" From git at git.haskell.org Thu Oct 26 23:20:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove postProcessPackageData from Util. (481caa8) Message-ID: <20171026232040.006093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/481caa85874e966d8adc82dddde1313187647167/ghc >--------------------------------------------------------------- commit 481caa85874e966d8adc82dddde1313187647167 Author: Andrey Mokhov Date: Sun Jan 11 21:29:13 2015 +0000 Remove postProcessPackageData from Util. >--------------------------------------------------------------- 481caa85874e966d8adc82dddde1313187647167 src/Package/Data.hs | 12 ++++++++++++ src/Util.hs | 14 +------------- 2 files changed, 13 insertions(+), 13 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index e2260fd..eaaa072 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -43,6 +43,18 @@ configureArgs stage settings = <> when CrossCompiling (argConf "--host" TargetPlatformFull) <> argConf "--with-cc" Gcc +-- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: +-- 1) Drop lines containing '$' +-- 2) Replace '/' and '\' with '_' before '=' +postProcessPackageData :: FilePath -> Action () +postProcessPackageData file = do + pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) + length pkgData `seq` writeFileLines file $ map processLine pkgData + where + processLine line = replaceSeparators '_' prefix ++ suffix + where + (prefix, suffix) = break (== '=') line + buildPackageData :: Package -> TodoItem -> Rules () buildPackageData (Package name path _) (stage, dist, settings) = let pathDist = path dist diff --git a/src/Util.hs b/src/Util.hs index d7e98bd..f91ff79 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,7 +1,6 @@ module Util ( module Data.Char, - replaceIf, replaceEq, replaceSeparators, - postProcessPackageData + replaceIf, replaceEq, replaceSeparators ) where import Base @@ -16,14 +15,3 @@ replaceEq from = replaceIf (== from) replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator --- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: --- 1) Drop lines containing '$' --- 2) Replace '/' and '\' with '_' before '=' -postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map processLine pkgData - where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:20:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for Alex, Happy and Hsc2Hs builders. (1e13a6e) Message-ID: <20171026232040.274D03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1e13a6e1021c8354a86af9ea4cba7e3c2ce1bc65/ghc >--------------------------------------------------------------- commit 1e13a6e1021c8354a86af9ea4cba7e3c2ce1bc65 Author: Andrey Mokhov Date: Mon Sep 21 00:58:19 2015 +0100 Add support for Alex, Happy and Hsc2Hs builders. >--------------------------------------------------------------- 1e13a6e1021c8354a86af9ea4cba7e3c2ce1bc65 src/Rules/Actions.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 4285831..f261b4f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -39,15 +39,18 @@ build = buildWithResources [] interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of + Alex -> prefixAndSuffix 0 3 ss Ar -> prefixAndSuffix 2 1 ss - Ld -> prefixAndSuffix 4 0 ss Gcc _ -> prefixAndSuffix 0 4 ss GccM _ -> prefixAndSuffix 0 1 ss Ghc _ -> prefixAndSuffix 0 4 ss + GhcCabal -> prefixAndSuffix 3 0 ss GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss Haddock -> prefixAndSuffix 1 0 ss - GhcCabal -> prefixAndSuffix 3 0 ss + Happy -> prefixAndSuffix 0 3 ss + Hsc2Hs -> prefixAndSuffix 0 3 ss + Ld -> prefixAndSuffix 4 0 ss _ -> ss where prefixAndSuffix n m list = From git at git.haskell.org Thu Oct 26 23:20:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters. (d956739) Message-ID: <20171026232043.8303C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d956739dd5d551fa4f0259966f2f0b0cce250bcd/ghc >--------------------------------------------------------------- commit d956739dd5d551fa4f0259966f2f0b0cce250bcd Author: Andrey Mokhov Date: Sun Jan 11 21:42:39 2015 +0000 Fit lines into 80 characters. >--------------------------------------------------------------- d956739dd5d551fa4f0259966f2f0b0cce250bcd src/Oracles/PackageData.hs | 20 ++++++++++++-------- 1 file changed, 12 insertions(+), 8 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index ba63612..6bffafd 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -12,21 +12,25 @@ import Util newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath - | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath +data PackageData = Modules FilePath + | SrcDirs FilePath + | PackageKey FilePath + | IncludeDirs FilePath + | Deps FilePath + | DepKeys FilePath instance ShowArgs PackageData where - showArgs key = do - let (keyName, file, ifEmpty) = case key of + showArgs packageData = do + let (key, file, defaultValue) = case packageData of Modules file -> ("MODULES" , file, "" ) SrcDirs file -> ("HS_SRC_DIRS" , file, ".") PackageKey file -> ("PACKAGE_KEY" , file, "" ) IncludeDirs file -> ("INCLUDE_DIRS", file, ".") Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) - keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName - res <- askOracle $ PackageDataKey (file, keyFullName) + fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key + res <- askOracle $ PackageDataKey (file, fullKey) return $ words $ case res of - Nothing -> error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." - Just "" -> ifEmpty + Nothing -> error $ "No key '" ++ key ++ "' in " ++ file ++ "." + Just "" -> defaultValue Just value -> value From git at git.haskell.org Thu Oct 26 23:20:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add hsc2HsArgs to global settings. (330dcdb) Message-ID: <20171026232043.B2A733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/330dcdbf2b5f84e658fbbe4c540492c7b03c6951/ghc >--------------------------------------------------------------- commit 330dcdbf2b5f84e658fbbe4c540492c7b03c6951 Author: Andrey Mokhov Date: Mon Sep 21 00:58:57 2015 +0100 Add hsc2HsArgs to global settings. >--------------------------------------------------------------- 330dcdbf2b5f84e658fbbe4c540492c7b03c6951 src/Settings/Args.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 2e2f379..97933fa 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -9,6 +9,7 @@ import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg import Settings.Builders.Haddock import Settings.Builders.Happy +import Settings.Builders.Hsc2Hs import Settings.Builders.Ld import Settings.User @@ -37,4 +38,5 @@ defaultArgs = mconcat , gccMArgs , haddockArgs , happyArgs + , hsc2HsArgs , ldArgs ] From git at git.haskell.org Thu Oct 26 23:20:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add instance Show Stage. (d0095df) Message-ID: <20171026232047.495A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d0095df621aa39dfbe7f827e073c5b1fb7aa7b89/ghc >--------------------------------------------------------------- commit d0095df621aa39dfbe7f827e073c5b1fb7aa7b89 Author: Andrey Mokhov Date: Sun Jan 11 21:45:31 2015 +0000 Add instance Show Stage. >--------------------------------------------------------------- d0095df621aa39dfbe7f827e073c5b1fb7aa7b89 src/Base.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index b84b48c..169f556 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -24,6 +24,9 @@ import Data.List data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) +instance Show Stage where + show = show . fromEnum + type Args = Action [String] type Condition = Action Bool From git at git.haskell.org Thu Oct 26 23:20:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify paths of sources and files in a target. (00de798) Message-ID: <20171026232047.6DED93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/00de798905ba76aaa6f034b0b7110fe1c4be3acb/ghc >--------------------------------------------------------------- commit 00de798905ba76aaa6f034b0b7110fe1c4be3acb Author: Andrey Mokhov Date: Mon Sep 21 00:59:34 2015 +0100 Unify paths of sources and files in a target. >--------------------------------------------------------------- 00de798905ba76aaa6f034b0b7110fe1c4be3acb src/Target.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Target.hs b/src/Target.hs index 2901ffe..8e2a44e 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -60,8 +60,8 @@ fullTarget (PartialTarget s p) b srcs fs = Target package = p, builder = b, way = vanilla, - sources = srcs, - files = fs + sources = map unifyPath srcs, + files = map unifyPath fs } -- Use this function to be explicit about the build way. From git at git.haskell.org Thu Oct 26 23:20:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters. (817ed05) Message-ID: <20171026232050.B608A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/817ed0570d9b58d3a3220fadcc704cfa7913d90f/ghc >--------------------------------------------------------------- commit 817ed0570d9b58d3a3220fadcc704cfa7913d90f Author: Andrey Mokhov Date: Sun Jan 11 21:50:41 2015 +0000 Fit lines into 80 characters. >--------------------------------------------------------------- 817ed0570d9b58d3a3220fadcc704cfa7913d90f src/Oracles/Option.hs | 32 +++++++++++++++++++++++--------- 1 file changed, 23 insertions(+), 9 deletions(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index d08b394..0a5506d 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -6,9 +6,17 @@ module Oracles.Option ( import Base import Oracles.Base -data Option = TargetOS | TargetArch | TargetPlatformFull - | ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage - | IconvIncludeDirs | IconvLibDirs | GmpIncludeDirs | GmpLibDirs +data Option = TargetOS + | TargetArch + | TargetPlatformFull + | ConfCcArgs Stage + | ConfGccLinkerArgs Stage + | ConfLdLinkerArgs Stage + | ConfCppArgs Stage + | IconvIncludeDirs + | IconvLibDirs + | GmpIncludeDirs + | GmpLibDirs | SrcHcOpts | HostOsCpp @@ -17,10 +25,10 @@ instance ShowArgs Option where TargetOS -> "target-os" TargetArch -> "target-arch" TargetPlatformFull -> "target-platform-full" - ConfCcArgs stage -> "conf-cc-args-stage-" ++ (show . fromEnum) stage - ConfCppArgs stage -> "conf-cpp-args-stage-" ++ (show . fromEnum) stage - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ (show . fromEnum) stage - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ (show . fromEnum) stage + ConfCcArgs stage -> "conf-cc-args-stage-" ++ show stage + ConfCppArgs stage -> "conf-cpp-args-stage-" ++ show stage + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ show stage + ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ show stage IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" GmpIncludeDirs -> "gmp-include-dirs" @@ -33,14 +41,20 @@ ghcWithInterpreter = do [os] <- showArgs TargetOS [arch] <- showArgs TargetArch return $ - os `elem` ["mingw32", "cygwin32", "linux", "solaris2", "freebsd", "dragonfly", "netbsd", "openbsd", "darwin", "kfreebsdgnu"] + os `elem` [ "mingw32", "cygwin32", "linux", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" + , "darwin", "kfreebsdgnu"] && arch `elem` ["i386", "x86_64", "powerpc", "sparc", "sparc64", "arm"] +-- TODO: i386-unknown-solaris2 should be in the list if +-- @SOLARIS_BROKEN_SHLD@ == YES platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do [platform] <- showArgs TargetPlatformFull - return $ platform `notElem` [ "powerpc-unknown-linux", "x86_64-unknown-mingw32", "i386-unknown-mingw32" ] -- TODO: i386-unknown-solaris2? + return $ platform `notElem` [ "powerpc-unknown-linux" + , "x86_64-unknown-mingw32" + , "i386-unknown-mingw32" ] windowsHost :: Condition windowsHost = do From git at git.haskell.org Thu Oct 26 23:20:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (738bac8) Message-ID: <20171026232051.08D7C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/738bac8ccaa266a76a1a21ccb1ff1f8cbe785a70/ghc >--------------------------------------------------------------- commit 738bac8ccaa266a76a1a21ccb1ff1f8cbe785a70 Author: Andrey Mokhov Date: Mon Sep 21 01:00:48 2015 +0100 Clean up. >--------------------------------------------------------------- 738bac8ccaa266a76a1a21ccb1ff1f8cbe785a70 src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 10 ++++++++-- src/Settings/Builders/Happy.hs | 2 +- 3 files changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs index 6aedcdb..1e0f87b 100644 --- a/src/Settings/Builders/Alex.hs +++ b/src/Settings/Builders/Alex.hs @@ -6,8 +6,8 @@ import Predicates (builder, package) alexArgs :: Args alexArgs = builder Alex ? do - file <- getFile src <- getSource + file <- getFile mconcat [ arg "-g" , package compiler ? arg "--latin1" , arg src diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index dd54097..ab65a51 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,5 +1,6 @@ module Settings.Builders.GhcCabal ( - cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs + cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, + ccArgs, ccWarnings, argStagedSettingList ) where import Expression @@ -54,6 +55,7 @@ libraryArgs = do then "--enable-shared" else "--disable-shared" ] +-- TODO: LD_OPTS? configureArgs :: Args configureArgs = do let conf key = appendSubD $ "--configure-option=" ++ key @@ -94,7 +96,11 @@ packageConstraints = stage0 ? do -- TODO: should be in a different file -- TODO: put all validating options together in one file ccArgs :: Args -ccArgs = validating ? do +ccArgs = validating ? ccWarnings + +-- TODO: should be in a different file +ccWarnings :: Args +ccWarnings = do let notClang = fmap not gccIsClang mconcat [ arg "-Werror" , arg "-Wall" diff --git a/src/Settings/Builders/Happy.hs b/src/Settings/Builders/Happy.hs index fcd962a..685c30d 100644 --- a/src/Settings/Builders/Happy.hs +++ b/src/Settings/Builders/Happy.hs @@ -5,8 +5,8 @@ import Predicates (builder) happyArgs :: Args happyArgs = builder Happy ? do - file <- getFile src <- getSource + file <- getFile mconcat [ arg "-agc" , arg "--strict" , arg src From git at git.haskell.org Thu Oct 26 23:20:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for SolarisBrokenShld flag. (e77d98b) Message-ID: <20171026232054.240E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e77d98ba7ad9c4eef57f28784267ba6da339d8fe/ghc >--------------------------------------------------------------- commit e77d98ba7ad9c4eef57f28784267ba6da339d8fe Author: Andrey Mokhov Date: Sun Jan 11 23:43:31 2015 +0000 Add support for SolarisBrokenShld flag. >--------------------------------------------------------------- e77d98ba7ad9c4eef57f28784267ba6da339d8fe cfg/default.config.in | 1 + src/Oracles/Flag.hs | 17 ++++++++++++----- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index 50c3937..b1eadd0 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -31,6 +31,7 @@ gcc-lt-46 = @GccLT46@ lax-dependencies = NO dynamic-ghc-programs = NO supports-package-key = @SUPPORTS_PACKAGE_KEY@ +solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ # Information about host and target systems: #=========================================== diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 946c4fb..7a235a4 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -13,23 +13,30 @@ import Prelude hiding (not, (&&), (||)) import Base import Oracles.Base -data Flag = LaxDeps | DynamicGhcPrograms - | GccIsClang | GccLt46 | CrossCompiling | Validating +data Flag = LaxDeps + | DynamicGhcPrograms + | GccIsClang + | GccLt46 + | CrossCompiling + | Validating | SupportsPackageKey + | SolarisBrokenShld +-- TODO: Give the warning *only once* per key test :: Flag -> Action Bool test flag = do (key, defaultValue) <- return $ case flag of - LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file + LaxDeps -> ("lax-dependencies" , False) DynamicGhcPrograms -> ("dynamic-ghc-programs" , False) GccIsClang -> ("gcc-is-clang" , False) GccLt46 -> ("gcc-lt-46" , False) CrossCompiling -> ("cross-compiling" , False) Validating -> ("validating" , False) SupportsPackageKey -> ("supports-package-key" , False) + SolarisBrokenShld -> ("solaris-broken-shld" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ - do putLoud $ "\nFlag '" -- TODO: Give the warning *only once* per key + do putLoud $ "\nFlag '" ++ key ++ "' not set in configuration files. " ++ "Proceeding with default value '" @@ -103,4 +110,4 @@ instance ToCondition a => AndOr Flag a where x && y = toCondition x && y x || y = toCondition x || y - +-- TODO: need one more instance? \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:20:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track generated sources. (44f7b51) Message-ID: <20171026232054.6A9CA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44f7b51095e7d4c151eef50c6f6180b27efa4aa1/ghc >--------------------------------------------------------------- commit 44f7b51095e7d4c151eef50c6f6180b27efa4aa1 Author: Andrey Mokhov Date: Mon Sep 21 01:01:13 2015 +0100 Track generated sources. >--------------------------------------------------------------- 44f7b51095e7d4c151eef50c6f6180b27efa4aa1 src/Rules/Compile.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 3940d64..90712ce 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -19,7 +19,7 @@ compilePackage _ target @ (PartialTarget stage package) = do matchBuildResult buildPath "o" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need deps + need $ src : deps if ("//*.c" ?== src) then build $ fullTarget target (Gcc stage) [src] [obj] else do @@ -28,6 +28,6 @@ compilePackage _ target @ (PartialTarget stage package) = do matchBuildResult buildPath "o-boot" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need deps + need $ src : deps let way = detectWay obj build $ fullTargetWithWay target (Ghc stage) way [src] [obj] From git at git.haskell.org Thu Oct 26 23:20:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for SolarisBrokenShld flag. (a5de5a5) Message-ID: <20171026232057.858BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5de5a592f8b2bdae851e0d0c0a0041414dd1c39/ghc >--------------------------------------------------------------- commit a5de5a592f8b2bdae851e0d0c0a0041414dd1c39 Author: Andrey Mokhov Date: Sun Jan 11 23:44:30 2015 +0000 Add support for SolarisBrokenShld flag. >--------------------------------------------------------------- a5de5a592f8b2bdae851e0d0c0a0041414dd1c39 src/Oracles/Option.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 0a5506d..029b9bd 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,9 +1,11 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Oracles.Option ( Option (..), ghcWithInterpreter, platformSupportsSharedLibs, windowsHost ) where import Base +import Oracles.Flag import Oracles.Base data Option = TargetOS @@ -47,14 +49,15 @@ ghcWithInterpreter = do && arch `elem` ["i386", "x86_64", "powerpc", "sparc", "sparc64", "arm"] --- TODO: i386-unknown-solaris2 should be in the list if --- @SOLARIS_BROKEN_SHLD@ == YES platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do [platform] <- showArgs TargetPlatformFull - return $ platform `notElem` [ "powerpc-unknown-linux" - , "x86_64-unknown-mingw32" - , "i386-unknown-mingw32" ] + solarisBrokenShld <- test SolarisBrokenShld + return $ notElem platform $ + [ "powerpc-unknown-linux" + , "x86_64-unknown-mingw32" + , "i386-unknown-mingw32"] ++ + [ "i386-unknown-solaris2" | solarisBrokenShld ] windowsHost :: Condition windowsHost = do From git at git.haskell.org Thu Oct 26 23:20:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:20:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for new keys in package-data files. (13708d7) Message-ID: <20171026232057.D6CF23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13708d7313bb91ea60e4129d2e6b0f2bcec4ad8e/ghc >--------------------------------------------------------------- commit 13708d7313bb91ea60e4129d2e6b0f2bcec4ad8e Author: Andrey Mokhov Date: Mon Sep 21 01:01:59 2015 +0100 Add support for new keys in package-data files. >--------------------------------------------------------------- 13708d7313bb91ea60e4129d2e6b0f2bcec4ad8e src/Oracles/PackageData.hs | 58 +++++++++++++++++++++++++++------------------- 1 file changed, 34 insertions(+), 24 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index e3c1eb5..22031b1 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -15,24 +15,29 @@ import qualified Data.HashMap.Strict as Map -- PackageDataList is used for multiple string options separated by spaces, -- such as 'path_MODULES = Data.Array Data.Array.Base ...'. -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] -data PackageData = Version FilePath - | PackageKey FilePath +data PackageData = BuildGhciLib FilePath | LibName FilePath + | PackageKey FilePath | Synopsis FilePath - | BuildGhciLib FilePath + | Version FilePath -data PackageDataList = Modules FilePath - | HiddenModules FilePath - | SrcDirs FilePath - | IncludeDirs FilePath - | Deps FilePath +data PackageDataList = CcArgs FilePath + | CSrcs FilePath + | CppArgs FilePath + | DepCcArgs FilePath + | DepExtraLibs FilePath | DepIds FilePath + | DepIncludeDirs FilePath + | DepLdArgs FilePath + | DepLibDirs FilePath | DepNames FilePath - | CppArgs FilePath + | Deps FilePath + | HiddenModules FilePath | HsArgs FilePath - | CcArgs FilePath - | CSrcs FilePath - | DepIncludeDirs FilePath + | IncludeDirs FilePath + | LdArgs FilePath + | Modules FilePath + | SrcDirs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -48,26 +53,31 @@ askPackageData path key = do pkgData :: PackageData -> Action String pkgData packageData = case packageData of - Version path -> askPackageData path "VERSION" - PackageKey path -> askPackageData path "PACKAGE_KEY" + BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" LibName path -> askPackageData path "LIB_NAME" + PackageKey path -> askPackageData path "PACKAGE_KEY" Synopsis path -> askPackageData path "SYNOPSIS" - BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" + Version path -> askPackageData path "VERSION" pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = fmap (map unquote . words) $ case packageData of - Modules path -> askPackageData path "MODULES" - HiddenModules path -> askPackageData path "HIDDEN_MODULES" - SrcDirs path -> askPackageData path "HS_SRC_DIRS" - IncludeDirs path -> askPackageData path "INCLUDE_DIRS" - Deps path -> askPackageData path "DEPS" - DepIds path -> askPackageData path "DEP_IPIDS" - DepNames path -> askPackageData path "DEP_NAMES" - CppArgs path -> askPackageData path "CPP_OPTS" - HsArgs path -> askPackageData path "HC_OPTS" CcArgs path -> askPackageData path "CC_OPTS" CSrcs path -> askPackageData path "C_SRCS" + CppArgs path -> askPackageData path "CPP_OPTS" + DepCcArgs path -> askPackageData path "DEP_CC_OPTS" + DepExtraLibs path -> askPackageData path "DEP_EXTRA_LIBS" + DepIds path -> askPackageData path "DEP_IPIDS" DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" + DepLibDirs path -> askPackageData path "DEP_LIB_DIRS_SINGLE_QUOTED" + DepLdArgs path -> askPackageData path "DEP_LD_OPTS" + DepNames path -> askPackageData path "DEP_NAMES" + Deps path -> askPackageData path "DEPS" + HiddenModules path -> askPackageData path "HIDDEN_MODULES" + HsArgs path -> askPackageData path "HC_OPTS" + IncludeDirs path -> askPackageData path "INCLUDE_DIRS" + LdArgs path -> askPackageData path "LD_OPTS" + Modules path -> askPackageData path "MODULES" + SrcDirs path -> askPackageData path "HS_SRC_DIRS" where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') From git at git.haskell.org Thu Oct 26 23:21:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant GHC extentions. (238efc2) Message-ID: <20171026232100.F30993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/238efc2b316f5a8ed2f955af6639e4fa543d2359/ghc >--------------------------------------------------------------- commit 238efc2b316f5a8ed2f955af6639e4fa543d2359 Author: Andrey Mokhov Date: Sun Jan 11 23:45:29 2015 +0000 Remove redundant GHC extentions. >--------------------------------------------------------------- 238efc2b316f5a8ed2f955af6639e4fa543d2359 src/Package/Compile.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index b876482..50cf412 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} +{-# LANGUAGE NoImplicitPrelude #-} module Package.Compile (buildPackageCompile) where import Package.Base From git at git.haskell.org Thu Oct 26 23:21:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for new configuration flags. (8e74ca7) Message-ID: <20171026232101.481563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e74ca7b158cb0a3fd7413b1b6646fa2cdbcb1a7/ghc >--------------------------------------------------------------- commit 8e74ca7b158cb0a3fd7413b1b6646fa2cdbcb1a7 Author: Andrey Mokhov Date: Mon Sep 21 01:02:39 2015 +0100 Add support for new configuration flags. >--------------------------------------------------------------- 8e74ca7b158cb0a3fd7413b1b6646fa2cdbcb1a7 src/Oracles/Config/Setting.hs | 55 ++++++++++++++++++++++++++++--------------- 1 file changed, 36 insertions(+), 19 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index f0f7fb7..a01a7fa 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -3,7 +3,7 @@ module Oracles.Config.Setting ( setting, settingList, getSetting, getSettingList, targetPlatform, targetPlatforms, targetOs, targetOss, notTargetOs, targetArchs, windowsHost, notWindowsHost, ghcWithInterpreter, - ghcEnableTablesNextToCode, cmdLineLengthLimit + ghcEnableTablesNextToCode, ghcCanonVersion, cmdLineLengthLimit ) where import Base @@ -16,32 +16,42 @@ import Stage -- SettingList is used for multiple string values separated by spaces, such -- as 'gmp-include-dirs = a b'. -- settingList GmpIncludeDirs therefore returns a list of strings ["a", "b"]. -data Setting = TargetOs +data Setting = DynamicExtension + | GhcMajorVersion + | GhcMinorVersion + | GhcPatchLevel + | GhcSourcePath + | HostArch + | HostOs + | ProjectVersion + | ProjectVersionInt | TargetArch + | TargetOs | TargetPlatformFull - | HostOsCpp - | DynamicExtension - | ProjectVersion - | GhcSourcePath data SettingList = ConfCcArgs Stage + | ConfCppArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage - | ConfCppArgs Stage - | IconvIncludeDirs - | IconvLibDirs | GmpIncludeDirs | GmpLibDirs + | IconvIncludeDirs + | IconvLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of - TargetOs -> "target-os" - TargetArch -> "target-arch" - TargetPlatformFull -> "target-platform-full" - HostOsCpp -> "host-os-cpp" DynamicExtension -> "dynamic-extension" - ProjectVersion -> "project-version" + GhcMajorVersion -> "ghc-major-version" + GhcMinorVersion -> "ghc-minor-version" + GhcPatchLevel -> "ghc-patch-level" GhcSourcePath -> "ghc-source-path" + HostArch -> "host-arch" + HostOs -> "host-os" + ProjectVersion -> "project-version" + ProjectVersionInt -> "project-version-int" + TargetArch -> "target-arch" + TargetOs -> "target-os" + TargetPlatformFull -> "target-platform-full" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -49,10 +59,10 @@ settingList key = fmap words $ askConfig $ case key of ConfCppArgs stage -> "conf-cpp-args-stage" ++ show stage ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show stage ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show stage - IconvIncludeDirs -> "iconv-include-dirs" - IconvLibDirs -> "iconv-lib-dirs" GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" + IconvIncludeDirs -> "iconv-include-dirs" + IconvLibDirs -> "iconv-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting @@ -84,9 +94,7 @@ targetArchs :: [String] -> Action Bool targetArchs = matchSetting TargetArch windowsHost :: Action Bool -windowsHost = do - hostOsCpp <- setting HostOsCpp - return $ hostOsCpp `elem` ["mingw32", "cygwin32"] +windowsHost = matchSetting HostOs ["mingw32", "cygwin32"] notWindowsHost :: Action Bool notWindowsHost = fmap not windowsHost @@ -103,6 +111,15 @@ ghcWithInterpreter = do ghcEnableTablesNextToCode :: Action Bool ghcEnableTablesNextToCode = targetArchs ["ia64", "powerpc64"] +-- Canonicalised GHC version number, used for integer version comparisons. We +-- expand GhcMinorVersion to two digits by adding a leading zero if necessary. +ghcCanonVersion :: Action String +ghcCanonVersion = do + ghcMajorVersion <- setting GhcMajorVersion + ghcMinorVersion <- setting GhcMinorVersion + let leadingZero = [ '0' | length ghcMinorVersion == 1 ] + return $ ghcMajorVersion ++ leadingZero ++ ghcMinorVersion + -- Command lines have limited size on Windows. Since Windows 7 the limit is -- 32768 characters (theoretically). In practice we use 31000 to leave some -- breathing space for the builder's path & name, auxiliary flags, and other From git at git.haskell.org Thu Oct 26 23:21:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (2e29ea9) Message-ID: <20171026232104.8F3043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2e29ea968bba4737bbdeb914e90cae4933202c75/ghc >--------------------------------------------------------------- commit 2e29ea968bba4737bbdeb914e90cae4933202c75 Author: Andrey Mokhov Date: Mon Jan 12 00:29:28 2015 +0000 Clean up. >--------------------------------------------------------------- 2e29ea968bba4737bbdeb914e90cae4933202c75 src/Oracles/Base.hs | 3 ++- src/Oracles/Flag.hs | 10 +++++----- 2 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index f9e5c73..c9827a9 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -8,7 +8,8 @@ module Oracles.Base ( import Base import Development.Shake.Classes -newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +newtype ConfigKey = ConfigKey String + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) askConfigWithDefault :: String -> Action String -> Action String askConfigWithDefault key defaultAction = do diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 7a235a4..b93e4ab 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -81,11 +81,11 @@ instance Not Bool where instance Not Condition where type NotResult Condition = Condition - not x = not <$> (toCondition x) + not = fmap not instance Not Flag where type NotResult Flag = Condition - not x = not (toCondition x) + not = not . toCondition class AndOr a b where type AndOrResult a b @@ -102,12 +102,12 @@ instance AndOr Bool Bool where instance ToCondition a => AndOr Condition a where type AndOrResult Condition a = Condition - x && y = (Prelude.&&) <$> toCondition x <*> toCondition y - x || y = (Prelude.||) <$> toCondition x <*> toCondition y + x && y = (&&) <$> x <*> toCondition y + x || y = (||) <$> x <*> toCondition y instance ToCondition a => AndOr Flag a where type AndOrResult Flag a = Condition x && y = toCondition x && y x || y = toCondition x || y --- TODO: need one more instance? \ No newline at end of file +-- TODO: need more instances to handle Bool as first argument of (&&), (||) From git at git.haskell.org Thu Oct 26 23:21:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish Generate rule. (f7ee775) Message-ID: <20171026232104.E87DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f7ee77565aa3b16f2911f99b7ef14059c16f9534/ghc >--------------------------------------------------------------- commit f7ee77565aa3b16f2911f99b7ef14059c16f9534 Author: Andrey Mokhov Date: Mon Sep 21 01:03:02 2015 +0100 Finish Generate rule. >--------------------------------------------------------------- f7ee77565aa3b16f2911f99b7ef14059c16f9534 src/Rules/Generate.hs | 22 ++-------------------- 1 file changed, 2 insertions(+), 20 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 055dccb..535f99b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -23,33 +23,15 @@ generatePackageCode _ target @ (PartialTarget stage package) = let path = targetPath stage package packagePath = pkgPath package buildPath = path -/- "build" - in do + in do -- TODO: do we need to copy *.(l)hs-boot files here? Never happens? buildPath "*.hs" %> \file -> do dirs <- interpretPartial target $ getPkgDataList SrcDirs files <- getDirectoryFiles "" $ [ packagePath d takeBaseName file <.> "*" | d <- dirs ] let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] - (src, builder) = head gens when (length gens /= 1) . putError $ "Exactly one generator expected for " ++ file ++ "(found: " ++ show gens ++ ")." + let (src, builder) = head gens need [src] build $ fullTarget target builder [src] [file] - --- $1/$2/build/%.hs : $1/$3/%.ly | $$$$(dir $$$$@)/. --- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ - --- $1/$2/build/%.hs : $1/$3/%.y | $$$$(dir $$$$@)/. --- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ - --- $1/$2/build/%_hsc.c $1/$2/build/%_hsc.h $1/$2/build/%.hs : $1/$3/%.hsc $$$$(hsc2hs_INPLACE) | $$$$(dir $$$$@)/. --- $$(call cmd,hsc2hs_INPLACE) $$($1_$2_ALL_HSC2HS_OPTS) $$< -o $$@ - --- # Now the rules for hs-boot files. - --- $1/$2/build/%.hs-boot : $1/$3/%.hs-boot --- "$$(CP)" $$< $$@ - --- $1/$2/build/%.lhs-boot : $1/$3/%.lhs-boot --- "$$(CP)" $$< $$@ - From git at git.haskell.org Thu Oct 26 23:21:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters, add exists Builder function. (f956bdc) Message-ID: <20171026232108.971DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f956bdcf059fac29eafbfb24e1eb2180e8689009/ghc >--------------------------------------------------------------- commit f956bdcf059fac29eafbfb24e1eb2180e8689009 Author: Andrey Mokhov Date: Mon Jan 12 01:21:37 2015 +0000 Fit lines into 80 characters, add exists Builder function. >--------------------------------------------------------------- f956bdcf059fac29eafbfb24e1eb2180e8689009 src/Oracles/Builder.hs | 76 ++++++++++++++++++++++++++++++-------------------- src/Package/Data.hs | 2 +- 2 files changed, 46 insertions(+), 32 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index d91e5e7..eefa7a2 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,8 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, - hsColourSrcs + with, run, exists ) where import Data.Char @@ -12,10 +11,22 @@ import Oracles.Base import Oracles.Flag import Oracles.Option -data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage +-- Ghc Stage0 is the bootstrapping compiler +-- Ghc StageN, N > 0, is the one built on stage (N - 1) +-- GhcPkg Stage0 is the bootstrapping GhcPkg +-- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) +data Builder = Ar + | Ld + | Gcc + | Alex + | Happy + | HsColour + | GhcCabal + | Ghc Stage + | GhcPkg Stage instance ShowArgs Builder where - showArgs builder = showArgs $ do + showArgs builder = showArgs $ fmap words $ do let key = case builder of Ar -> "ar" Ld -> "ld" @@ -24,16 +35,15 @@ instance ShowArgs Builder where Happy -> "happy" HsColour -> "hscolour" GhcCabal -> "ghc-cabal" - Ghc Stage0 -> "system-ghc" -- Ghc Stage0 is the bootstrapping compiler - Ghc Stage1 -> "ghc-stage1" -- Ghc StageN, N > 0, is the one built on stage (N - 1) + Ghc Stage0 -> "system-ghc" + Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg - GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) + GhcPkg Stage0 -> "system-ghc-pkg" + GhcPkg _ -> "ghc-pkg" cfgPath <- askConfigWithDefault key $ - error $ "\nCannot find path to '" - ++ key - ++ "' in configuration files." + error $ "\nCannot find path to '" ++ key + ++ "' in configuration files." let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" windows <- windowsHost if (windows && "/" `isPrefixOf` cfgPathExe) @@ -43,25 +53,26 @@ instance ShowArgs Builder where else return cfgPathExe --- When LaxDeps flag is set (by adding 'lax-dependencies = YES' to user.config), --- dependencies on the GHC executable are turned into order-only dependencies to --- avoid needless recompilation when making changes to GHC's sources. In certain --- situations this can lead to build failures, in which case you should reset --- the flag (at least temporarily). +-- When LaxDeps flag is set ('lax-dependencies = YES' in user.config), +-- dependencies on the GHC executable are turned into order-only dependencies +-- to avoid needless recompilation when making changes to GHC's sources. In +-- certain situations this can lead to build failures, in which case you +-- should reset the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - [target] <- showArgs ghc - laxDeps <- test LaxDeps - if laxDeps then orderOnly [target] else need [target] + [exe] <- showArgs ghc -- Raise an error if builder is not unique + laxDeps <- test LaxDeps + if laxDeps then orderOnly [exe] else need [exe] needBuilder builder = do - [target] <- showArgs builder - need [target] + [exe] <- showArgs builder + need [exe] --- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder +-- Action 'with Gcc' returns '--with-gcc=/path/to/gcc' and needs Gcc +-- Raises an error if the builder is not uniquely defined in config files with :: Builder -> Args with builder = do - let prefix = case builder of + let key = case builder of Ar -> "--with-ar=" Ld -> "--with-ld=" Gcc -> "--with-gcc=" @@ -70,18 +81,21 @@ with builder = do Happy -> "--with-happy=" GhcPkg _ -> "--with-ghc-pkg=" HsColour -> "--with-hscolour=" - [suffix] <- showArgs builder + [exe] <- showArgs builder needBuilder builder - return [prefix ++ suffix] + arg $ key ++ normaliseEx exe +-- Raises an error if the builder is not uniquely defined in config files run :: Builder -> Args -> Action () run builder args = do needBuilder builder [exe] <- showArgs builder - args' <- args - cmd [exe] args' + cmd [exe] =<< args -hsColourSrcs :: Condition -hsColourSrcs = do - [hscolour] <- showArgs HsColour - return $ hscolour /= "" +-- Check if the builder is uniquely defined in config files +exists :: Builder -> Condition +exists builder = do + exes <- showArgs builder + return $ case exes of + [_] -> True + _ -> False diff --git a/src/Package/Data.hs b/src/Package/Data.hs index eaaa072..f2805b8 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -68,7 +68,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = <> with (GhcPkg stage) <> customConfArgs settings <> (libraryArgs =<< ways settings) - <> when hsColourSrcs (with HsColour) + <> when (exists HsColour) (with HsColour) <> configureArgs stage settings <> when (stage == Stage0) bootPkgConstraints <> with Gcc From git at git.haskell.org Thu Oct 26 23:21:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new configuration flags for generating Config.hs. (7ae3a52) Message-ID: <20171026232108.E5EA13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ae3a52e7f4ea090e99ad98988951067b45e1397/ghc >--------------------------------------------------------------- commit 7ae3a52e7f4ea090e99ad98988951067b45e1397 Author: Andrey Mokhov Date: Wed Sep 23 02:06:28 2015 +0100 Add new configuration flags for generating Config.hs. >--------------------------------------------------------------- 7ae3a52e7f4ea090e99ad98988951067b45e1397 cfg/system.config.in | 33 +++++++++++++++++++++------------ 1 file changed, 21 insertions(+), 12 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 6bfb20d..2bfe449 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -21,6 +21,8 @@ haddock = @hardtop@/inplace/bin/haddock hsc2hs = @hardtop@/inplace/bin/hsc2hs +genprimopcode = @hardtop@/inplace/bin/genprimopcode + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ @@ -45,23 +47,30 @@ ghc-source-path = @hardtop@ # Information about host and target systems: #=========================================== -target-os = @TargetOS_CPP@ -target-arch = @TargetArch_CPP@ -target-platform-full = @TargetPlatformFull@ +target-os = @TargetOS_CPP@ +target-arch = @TargetArch_CPP@ +target-platform-full = @TargetPlatformFull@ + +host-os = @HostOS_CPP@ +host-arch = @HostArch_CPP@ -host-os = @HostOS_CPP@ -host-arch = @HostArch_CPP@ +cross-compiling = @CrossCompiling@ -cross-compiling = @CrossCompiling@ +dynamic-extension = @soext_target@ -dynamic-extension = @soext_target@ +ghc-version = @GhcVersion@ +ghc-major-version = @GhcMajVersion@ +ghc-minor-version = @GhcMinVersion@ +ghc-patch-level = @GhcPatchLevel@ -ghc-major-version = @GhcMajVersion@ -ghc-minor-version = @GhcMinVersion@ -ghc-patch-level = @GhcPatchLevel@ +project-name = @ProjectName@ +project-version = @ProjectVersion@ +project-version-int = @ProjectVersionInt@ +project-patch-level = @ProjectPatchLevel@ +project-patch-level1 = @ProjectPatchLevel1@ +project-patch-level2 = @ProjectPatchLevel2@ +project-git-commit-id = @ProjectGitCommitId@ -project-version = @ProjectVersion@ -project-version-int = @ProjectVersionInt@ # Compilation and linking flags: #=============================== From git at git.haskell.org Thu Oct 26 23:21:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename exists Builder to specified Builder, add comments. (7c9dfba) Message-ID: <20171026232112.001BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c9dfba2978d9dba7050e477938d3f99826d55f2/ghc >--------------------------------------------------------------- commit 7c9dfba2978d9dba7050e477938d3f99826d55f2 Author: Andrey Mokhov Date: Mon Jan 12 15:41:02 2015 +0000 Rename exists Builder to specified Builder, add comments. >--------------------------------------------------------------- 7c9dfba2978d9dba7050e477938d3f99826d55f2 src/Oracles/Builder.hs | 19 ++++++++++++------- src/Package/Data.hs | 2 +- 2 files changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index eefa7a2..16b5da5 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, exists + with, run, specified ) where import Data.Char @@ -46,6 +46,7 @@ instance ShowArgs Builder where ++ "' in configuration files." let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" windows <- windowsHost + -- Note, below is different from FilePath.isAbsolute: if (windows && "/" `isPrefixOf` cfgPathExe) then do Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] @@ -58,9 +59,12 @@ instance ShowArgs Builder where -- to avoid needless recompilation when making changes to GHC's sources. In -- certain situations this can lead to build failures, in which case you -- should reset the flag (at least temporarily). + +-- Make sure the builder exists on the given path and rebuild it if out of date +-- Raise an error if the builder is not uniquely specified in config files needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - [exe] <- showArgs ghc -- Raise an error if builder is not unique + [exe] <- showArgs ghc laxDeps <- test LaxDeps if laxDeps then orderOnly [exe] else need [exe] @@ -69,7 +73,7 @@ needBuilder builder = do need [exe] -- Action 'with Gcc' returns '--with-gcc=/path/to/gcc' and needs Gcc --- Raises an error if the builder is not uniquely defined in config files +-- Raises an error if the builder is not uniquely specified in config files with :: Builder -> Args with builder = do let key = case builder of @@ -85,16 +89,17 @@ with builder = do needBuilder builder arg $ key ++ normaliseEx exe --- Raises an error if the builder is not uniquely defined in config files +-- Run the builder with a given collection of arguments +-- Raises an error if the builder is not uniquely specified in config files run :: Builder -> Args -> Action () run builder args = do needBuilder builder [exe] <- showArgs builder cmd [exe] =<< args --- Check if the builder is uniquely defined in config files -exists :: Builder -> Condition -exists builder = do +-- Check if the builder is uniquely specified in config files +specified :: Builder -> Condition +specified builder = do exes <- showArgs builder return $ case exes of [_] -> True diff --git a/src/Package/Data.hs b/src/Package/Data.hs index f2805b8..7ff0d7d 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -68,7 +68,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = <> with (GhcPkg stage) <> customConfArgs settings <> (libraryArgs =<< ways settings) - <> when (exists HsColour) (with HsColour) + <> when (specified HsColour) (with HsColour) <> configureArgs stage settings <> when (stage == Stage0) bootPkgConstraints <> with Gcc From git at git.haskell.org Thu Oct 26 23:21:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GenPrimopCode builder. (702ce42) Message-ID: <20171026232112.5EC533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/702ce42a9324375c294d8a3e0a49ce0c8a44bc62/ghc >--------------------------------------------------------------- commit 702ce42a9324375c294d8a3e0a49ce0c8a44bc62 Author: Andrey Mokhov Date: Wed Sep 23 02:06:48 2015 +0100 Add GenPrimopCode builder. >--------------------------------------------------------------- 702ce42a9324375c294d8a3e0a49ce0c8a44bc62 src/Builder.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 3a24df3..9448ed2 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -18,6 +18,7 @@ data Builder = Alex | Ar | Gcc Stage | GccM Stage + | GenPrimopCode | Ghc Stage | GhcCabal | GhcCabalHsColour @@ -38,6 +39,7 @@ builderKey builder = case builder of Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' + GenPrimopCode -> "genprimopcode" Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" From git at git.haskell.org Thu Oct 26 23:21:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle GenPrimopCode builder in a special way. (17087d7) Message-ID: <20171026232115.C4C403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/17087d74a371ab996b81e8436f07839294a21cf8/ghc >--------------------------------------------------------------- commit 17087d74a371ab996b81e8436f07839294a21cf8 Author: Andrey Mokhov Date: Wed Sep 23 02:07:17 2015 +0100 Handle GenPrimopCode builder in a special way. >--------------------------------------------------------------- 17087d74a371ab996b81e8436f07839294a21cf8 src/Rules/Actions.hs | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index f261b4f..1e0472a 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -24,15 +24,23 @@ buildWithResources rs target = do ++ show builder ++ " with arguments:" mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList putBuild $ "\\--------" - quietly $ if builder /= Ar - then cmd [path] argList - else do -- Split argument list into chunks as otherwise Ar chokes up + quietly $ case builder of + Ar -> do -- Split argument list into chunks as otherwise Ar chokes up maxChunk <- cmdLineLengthLimit let persistentArgs = take arPersistentArgsCount argList remainingArgs = drop arPersistentArgsCount argList forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> unit . cmd [path] $ persistentArgs ++ argsChunk + GenPrimopCode -> do + let src = head $ Target.sources target -- TODO: ugly + file = head $ Target.files target + input <- readFile' src + Stdout output <- cmd (Stdin input) [path] argList + writeFileChanged file output + + _ -> cmd [path] argList + -- Most targets are built without explicitly acquiring resources build :: Target -> Action () build = buildWithResources [] From git at git.haskell.org Thu Oct 26 23:21:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add options SplitObjectsBroken, GhcUnregisterised, DynamicExtension, ProjectVersion. (b5beba9) Message-ID: <20171026232115.6A4363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b5beba96f0d4c6ba31e0e97d08ca54502acf8ec7/ghc >--------------------------------------------------------------- commit b5beba96f0d4c6ba31e0e97d08ca54502acf8ec7 Author: Andrey Mokhov Date: Tue Jan 13 02:17:53 2015 +0000 Add options SplitObjectsBroken, GhcUnregisterised, DynamicExtension, ProjectVersion. >--------------------------------------------------------------- b5beba96f0d4c6ba31e0e97d08ca54502acf8ec7 cfg/default.config.in | 6 ++++++ src/Oracles/Flag.hs | 4 ++++ src/Oracles/Option.hs | 34 ++++++++++++++++++++++++++-------- 3 files changed, 36 insertions(+), 8 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index b1eadd0..ac42e24 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -32,6 +32,8 @@ lax-dependencies = NO dynamic-ghc-programs = NO supports-package-key = @SUPPORTS_PACKAGE_KEY@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ +split-objects-broken = @SplitObjsBroken@ +ghc-unregisterised = @Unregisterised@ # Information about host and target systems: #=========================================== @@ -44,6 +46,10 @@ host-os-cpp = @HostOS_CPP@ cross-compiling = @CrossCompiling@ +dynamic-extension = @soext_target@ + +project-version = @ProjectVersion@ + # Compilation and linking flags: #=============================== diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index b93e4ab..e9aace5 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -21,6 +21,8 @@ data Flag = LaxDeps | Validating | SupportsPackageKey | SolarisBrokenShld + | SplitObjectsBroken + | GhcUnregisterised -- TODO: Give the warning *only once* per key test :: Flag -> Action Bool @@ -34,6 +36,8 @@ test flag = do Validating -> ("validating" , False) SupportsPackageKey -> ("supports-package-key" , False) SolarisBrokenShld -> ("solaris-broken-shld" , False) + SplitObjectsBroken -> ("split-objects-broken" , False) + GhcUnregisterised -> ("ghc-unregisterised" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ do putLoud $ "\nFlag '" diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 029b9bd..89192a7 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,13 +1,14 @@ {-# LANGUAGE NoImplicitPrelude #-} module Oracles.Option ( Option (..), - ghcWithInterpreter, platformSupportsSharedLibs, windowsHost + ghcWithInterpreter, platformSupportsSharedLibs, windowsHost, splitObjects ) where import Base import Oracles.Flag import Oracles.Base +-- TODO: separate single string options from multiple string ones. data Option = TargetOS | TargetArch | TargetPlatformFull @@ -21,6 +22,8 @@ data Option = TargetOS | GmpLibDirs | SrcHcOpts | HostOsCpp + | DynamicExtension + | ProjectVersion instance ShowArgs Option where showArgs opt = showArgs $ fmap words $ askConfig $ case opt of @@ -37,15 +40,17 @@ instance ShowArgs Option where GmpLibDirs -> "gmp-lib-dirs" SrcHcOpts -> "src-hc-opts" HostOsCpp -> "host-os-cpp" + DynamicExtension -> "dynamic-extension" + ProjectVersion -> "project-version" ghcWithInterpreter :: Condition ghcWithInterpreter = do [os] <- showArgs TargetOS [arch] <- showArgs TargetArch return $ - os `elem` [ "mingw32", "cygwin32", "linux", "solaris2" - , "freebsd", "dragonfly", "netbsd", "openbsd" - , "darwin", "kfreebsdgnu"] + os `elem` ["mingw32", "cygwin32", "linux", "solaris2", + "freebsd", "dragonfly", "netbsd", "openbsd", + "darwin", "kfreebsdgnu"] && arch `elem` ["i386", "x86_64", "powerpc", "sparc", "sparc64", "arm"] @@ -54,12 +59,25 @@ platformSupportsSharedLibs = do [platform] <- showArgs TargetPlatformFull solarisBrokenShld <- test SolarisBrokenShld return $ notElem platform $ - [ "powerpc-unknown-linux" - , "x86_64-unknown-mingw32" - , "i386-unknown-mingw32"] ++ - [ "i386-unknown-solaris2" | solarisBrokenShld ] + ["powerpc-unknown-linux", + "x86_64-unknown-mingw32", + "i386-unknown-mingw32"] ++ + ["i386-unknown-solaris2" | solarisBrokenShld] windowsHost :: Condition windowsHost = do [hostOsCpp] <- showArgs HostOsCpp return $ hostOsCpp `elem` ["mingw32", "cygwin32"] + +-- TODO: refactor helper Condition functions into a separate file +splitObjects :: Stage -> Condition +splitObjects stage = do + [os] <- showArgs TargetOS + [arch] <- showArgs TargetArch + splitObjectsBroken <- test SplitObjectsBroken + ghcUnregisterised <- test GhcUnregisterised + return $ not splitObjectsBroken && not ghcUnregisterised + && arch `elem` ["i386", "x86_64", "powerpc", "sparc"] + && os `elem` ["mingw32", "cygwin32", "linux", "darwin", + "solaris2", "freebsd", "dragonfly", "netbsd", + "openbsd"] From git at git.haskell.org Thu Oct 26 23:21:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Record new progress. (2840dab) Message-ID: <20171026232118.E130B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2840dab476a13a6f75463b6c34ec8e756e40cf06/ghc >--------------------------------------------------------------- commit 2840dab476a13a6f75463b6c34ec8e756e40cf06 Author: Andrey Mokhov Date: Tue Jan 13 02:18:57 2015 +0000 Record new progress. >--------------------------------------------------------------- 2840dab476a13a6f75463b6c34ec8e756e40cf06 doc/deepseq-build-progress.txt | 42 ++++++++++++++++++++++++++++-------------- 1 file changed, 28 insertions(+), 14 deletions(-) diff --git a/doc/deepseq-build-progress.txt b/doc/deepseq-build-progress.txt index 07214c6..f951d61 100644 --- a/doc/deepseq-build-progress.txt +++ b/doc/deepseq-build-progress.txt @@ -1,48 +1,62 @@ +# Skipping: "inplace/bin/ghc-cabal.exe" check libraries/deepseq -Skipping. - - +# Done: "inplace/bin/ghc-cabal.exe" configure libraries/deepseq dist-install "" --with-ghc="C:/msys/home/chEEtah/ghc/inplace/bin/ghc-stage1.exe" --with-ghc-pkg="C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe" --disable-library-for-ghci --enable-library-vanilla --enable-library-for-ghci --enable-library-profiling --disable-shared --configure-option=CFLAGS=" -fno-stack-protector " --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc-options=" -fno-stack-protector " --with-gcc="C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe" --with-ld="C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" --configure-option=--with-cc="C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe" --with-ar="/usr/bin/ar" --with-alex="/usr/local/bin/alex" --with-happy="/usr/local/bin/happy" -C:/msys/home/chEEtah/ghc/inplace/bin/ghc-cabal.exe configure libraries\deepseq dist-install --with-ghc= C:/msys/home/chEEtah/ghc/inplace/bin/ghc-stage1.exe --with-ghc-pkg= C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe --disable-library-for-ghci --enable-library-vanilla --enable-library-for-ghci --enable-library-profiling --disable-shared --configure-option=CFLAGS=-fno-stack-protector --configure-option=LDFLAGS= --configure-option=CPPFLAGS= --gcc-options=-fno-stack-protector --with-gcc= C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe --with-ld= C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe --configure-option=--with-cc= C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe --with-ar=C:/msys/usr/bin/ar.exe --with-alex=C:/msys/usr/local/bin/alex.exe --with-happy=C:/msys/usr/local/bin/happy.exe - Configuring deepseq-1.4.0.0... +# Done: "C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe" update --force libraries/deepseq/dist-install/inplace-pkg-config - C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe update --force libraries\deepseq\dist-install\inplace-pkg-config - Reading package info from "libraries/deepseq/dist-install/inplace-pkg-config" ... done. - +# Skipping: "rm" -f libraries/deepseq/dist-install/build/.depend-v-p.c_asm.tmp + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/.depend-v-p.c_asm.bit +# Skipping: echo "libraries/deepseq_dist-install_depfile_c_asm_EXISTS = YES" >> libraries/deepseq/dist-install/build/.depend-v-p.c_asm.tmp + +# Skipping: mv libraries/deepseq/dist-install/build/.depend-v-p.c_asm.tmp libraries/deepseq/dist-install/build/.depend-v-p.c_asm + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp +# Done: "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs +# Skipping: echo "libraries/deepseq_dist-install_depfile_haskell_EXISTS = YES" >> libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp + +# Skipping: for dir in libraries/deepseq/dist-install/build/Control/; do if test ! -d $dir; then mkdir -p $dir; fi done -grep -v ' : [a-zA-Z]:/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp > libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 -sed -e '/hs$/ p' -e '/hs$/ s/o /hi /g' -e '/hs$/ s/:/ : %hi: %o /' -e '/hs$/ s/^/$(eval $(call hi-rule,/' -e '/hs$/ s/$/))/' -e '/hs-boot$/ p' -e '/hs-boot$/ s/o-boot /hi-boot /g' -e '/hs-boot$/ s/:/ : %hi-boot: %o-boot /' -e '/hs-boot$/ s/^/$(eval $(call hi-rule,/' -e '/hs-boot$/ s/$/))/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 > libraries/deepseq/dist-install/build/.depend-v-p.haskell +# Skipping: +grep -v ' : [a-zA-Z]:/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp > libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 +# Skipping: +sed -e '/hs$/ p' -e '/hs$/ s/o /hi /g' -e '/hs$/ s/:/ : %hi: %o /' -e '/hs$/ s/^/$(eval $(call hi-rule,/' -e '/hs$/ s/$/))/' -e '/hs-boot$/ p' -e '/hs-boot$/ s/o-boot /hi-boot /g' -e '/hs-boot$/ s/:/ : %hi-boot: %o-boot /' -e '/hs-boot$/ s/^/$(eval $(call hi-rule,/' -e '/hs-boot$/ s/$/))/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 > libraries/deepseq/dist-install/build/.depend-v-p.haskell +# Done: "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.o - - +# Skipping: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + +# Skipping: /usr/bin/find libraries/deepseq/dist-install/build/Control/DeepSeq_o_split -name '*.o' -print >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + +# Skipping: echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + +# Done: "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents /usr/bin/ar: creating libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents - - +# Done: "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.p_o From git at git.haskell.org Thu Oct 26 23:21:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new configuration flags for generating Config.hs. (b8d04a6) Message-ID: <20171026232119.42D7E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b8d04a663c092320d5b0fe2556349557d72ae373/ghc >--------------------------------------------------------------- commit b8d04a663c092320d5b0fe2556349557d72ae373 Author: Andrey Mokhov Date: Wed Sep 23 02:07:52 2015 +0100 Add new configuration flags for generating Config.hs. >--------------------------------------------------------------- b8d04a663c092320d5b0fe2556349557d72ae373 src/Oracles/Config/Setting.hs | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index a01a7fa..8ee4752 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -20,11 +20,17 @@ data Setting = DynamicExtension | GhcMajorVersion | GhcMinorVersion | GhcPatchLevel + | GhcVersion | GhcSourcePath | HostArch | HostOs + | ProjectGitCommitId + | ProjectName | ProjectVersion | ProjectVersionInt + | ProjectPatchLevel + | ProjectPatchLevel1 + | ProjectPatchLevel2 | TargetArch | TargetOs | TargetPlatformFull @@ -44,11 +50,17 @@ setting key = askConfig $ case key of GhcMajorVersion -> "ghc-major-version" GhcMinorVersion -> "ghc-minor-version" GhcPatchLevel -> "ghc-patch-level" + GhcVersion -> "ghc-version" GhcSourcePath -> "ghc-source-path" HostArch -> "host-arch" HostOs -> "host-os" + ProjectGitCommitId -> "project-git-commit-id" + ProjectName -> "project-name" ProjectVersion -> "project-version" ProjectVersionInt -> "project-version-int" + ProjectPatchLevel -> "project-patch-level" + ProjectPatchLevel1 -> "project-patch-level1" + ProjectPatchLevel2 -> "project-patch-level2" TargetArch -> "target-arch" TargetOs -> "target-os" TargetPlatformFull -> "target-platform-full" From git at git.haskell.org Thu Oct 26 23:21:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Work on way suffixes. (91ecc02) Message-ID: <20171026232122.560243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91ecc023c94c9a694749024d1973e72ccc8c5336/ghc >--------------------------------------------------------------- commit 91ecc023c94c9a694749024d1973e72ccc8c5336 Author: Andrey Mokhov Date: Tue Jan 13 02:20:39 2015 +0000 Work on way suffixes. >--------------------------------------------------------------- 91ecc023c94c9a694749024d1973e72ccc8c5336 src/Ways.hs | 62 +++++++++++++++++++++++++++++++++++++++++++++++-------------- 1 file changed, 48 insertions(+), 14 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index c6d733c..b478a04 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -13,7 +13,7 @@ module Ways ( loggingDynamic, threadedLoggingDynamic, wayHcArgs, - suffix, + wayPrefix, hisuf, osuf, hcsuf, detectWay ) where @@ -43,7 +43,8 @@ logging = Way "l" [Logging] parallel = Way "mp" [Parallel] granSim = Way "gm" [GranSim] --- RTS only ways. TODO: do we need to define these here? +-- RTS only ways +-- TODO: do we need to define *only* these? Shall we generalise/simplify? threaded = Way "thr" [Threaded] threadedProfiling = Way "thr_p" [Threaded, Profiling] threadedLogging = Way "thr_l" [Threaded, Logging] @@ -88,19 +89,52 @@ wayHcArgs (Way _ units) = <> (units == [Debug] || units == [Debug, Dynamic]) arg ["-ticky", "-DTICKY_TICKY"] -suffix :: Way -> String -suffix way | way == vanilla = "" - | otherwise = tag way ++ "_" +wayPrefix :: Way -> String +wayPrefix way | way == vanilla = "" + | otherwise = tag way ++ "_" -hisuf, osuf, hcsuf :: Way -> String -hisuf = (++ "hi") . suffix -osuf = (++ "o" ) . suffix -hcsuf = (++ "hc") . suffix +hisuf, osuf, hcsuf, obootsuf, ssuf :: Way -> String +osuf = (++ "o" ) . wayPrefix +ssuf = (++ "s" ) . wayPrefix +hisuf = (++ "hi" ) . wayPrefix +hcsuf = (++ "hc" ) . wayPrefix +obootsuf = (++ "o-boot") . wayPrefix + +-- Note: in the previous build system libsuf was mysteriously different +-- from other suffixes. For example, in the profiling way it used to be +-- "_p.a" instead of ".p_a" which is how other suffixes work. I decided +-- to make all suffixes consistent: ".way_extension". +libsuf :: Way -> Action String +libsuf way = do + let staticSuffix = wayPrefix $ dropDynamic way + if Dynamic `notElem` units way + then return $ staticSuffix ++ "a" + else do + [extension] <- showArgs DynamicExtension + [version] <- showArgs ProjectVersion + return $ staticSuffix ++ "-ghc" ++ version ++ extension + +-- TODO: This may be slow -- optimise if overhead is significant. +dropDynamic :: Way -> Way +dropDynamic way + | way == dynamic = vanilla + | way == profilingDynamic = profiling + | way == threadedProfilingDynamic = threadedProfiling + | way == threadedDynamic = threaded + | way == threadedDebugDynamic = threadedDebug + | way == debugDynamic = debug + | way == loggingDynamic = logging + | way == threadedLoggingDynamic = threadedLogging + | otherwise = error $ "Cannot drop Dynamic from way " ++ tag way ++ "." -- Detect way from a given extension. Fail if the result is not unique. +-- TODO: This may be slow -- optimise if overhead is significant. detectWay :: FilePath -> Way -detectWay extension = case solutions of - [way] -> way - _ -> error $ "Cannot detect way from extension '" ++ extension ++ "'." - where - solutions = [w | f <- [hisuf, osuf, hcsuf], w <- allWays, f w == extension] +detectWay extension = + let prefix = reverse $ dropWhile (/= '_') $ reverse extension + result = filter ((== prefix) . wayPrefix) allWays + in + case result of + [way] -> way + _ -> error $ "Cannot detect way from extension '" + ++ extension ++ "'." From git at git.haskell.org Thu Oct 26 23:21:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add genPrimopCodeArgs to defaultArgs. (f406d36) Message-ID: <20171026232122.A7D403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f406d36fead05bbfd323aafc85d836c2fdb6ae89/ghc >--------------------------------------------------------------- commit f406d36fead05bbfd323aafc85d836c2fdb6ae89 Author: Andrey Mokhov Date: Wed Sep 23 02:08:22 2015 +0100 Add genPrimopCodeArgs to defaultArgs. >--------------------------------------------------------------- f406d36fead05bbfd323aafc85d836c2fdb6ae89 src/Settings/Args.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 97933fa..349668a 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -4,6 +4,7 @@ import Expression import Settings.Builders.Alex import Settings.Builders.Ar import Settings.Builders.Gcc +import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg @@ -30,12 +31,13 @@ defaultArgs = mconcat , arArgs , cabalArgs , customPackageArgs + , gccArgs + , gccMArgs + , genPrimopCodeArgs , ghcArgs , ghcCabalHsColourArgs , ghcMArgs , ghcPkgArgs - , gccArgs - , gccMArgs , haddockArgs , happyArgs , hsc2HsArgs From git at git.haskell.org Thu Oct 26 23:21:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageLibrary. (a325521) Message-ID: <20171026232126.5E7A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a325521e7db63f1bda2b38f3e7988c364708ce43/ghc >--------------------------------------------------------------- commit a325521e7db63f1bda2b38f3e7988c364708ce43 Author: Andrey Mokhov Date: Tue Jan 13 02:21:14 2015 +0000 Add buildPackageLibrary. >--------------------------------------------------------------- a325521e7db63f1bda2b38f3e7988c364708ce43 src/Package.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 2fd10f1..a3fcf89 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -3,6 +3,7 @@ module Package (packageRules) where import Package.Base import Package.Data import Package.Compile +import Package.Library import Package.Dependencies -- See Package.Base for definitions of basic types @@ -16,12 +17,13 @@ buildPackage :: Package -> TodoItem -> Rules () buildPackage = buildPackageData <> buildPackageDependencies <> buildPackageCompile + <> buildPackageLibrary packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments - want [ "libraries/deepseq/dist-install/build/Control/DeepSeq.o" - , "libraries/deepseq/dist-install/build/Control/DeepSeq.p_o" ] + want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" + , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:21:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add next meeting discusion agenda. (395f3ce) Message-ID: <20171026232126.A5FA93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/395f3ce523108018dc1ffaefc2daa3318fbcf4bd/ghc >--------------------------------------------------------------- commit 395f3ce523108018dc1ffaefc2daa3318fbcf4bd Author: Andrey Mokhov Date: Wed Sep 23 02:08:56 2015 +0100 Add next meeting discusion agenda. >--------------------------------------------------------------- 395f3ce523108018dc1ffaefc2daa3318fbcf4bd doc/meeting-25-September-2015.txt | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt new file mode 100644 index 0000000..6ee4297 --- /dev/null +++ b/doc/meeting-25-September-2015.txt @@ -0,0 +1,35 @@ +Shaking up GHC meeting, 25 September 2015 + +Things to discuss: +================================================ + +1. Better names for build stages + +* Currently we have Stage0, Stage1, etc. It is not particularly clear +from the names what they stand for. We no longer need to stick to +numbers and can pick more helpful names, for example: + +Stage0 -> Boot +Stage1 -> Interim +Stage2 -> Install +Stage3 -> Selftest + + + + +i. Unclear abstractions Builder/BuildRule... + +ii. Limits to build parallelism: GHC crashes during parallel builds. Also ghc-pkg and ghc-cabal are apparently not thread-safe, so I had to use Shake resources to limit the parallelism... + + +2. Do we need a name for the new build system? + +* At least we need a name for the folder in the GHC tree + +* If we call it 'shake' there may be a confusion with the Shake library. + +* In future discussions/announcements/etc. calling it 'the new shake-based + build system' is overly verbose. Calling it 'shake' is confusing. + +* I haven't thought about any names yet, just checking whether we want to. + From git at git.haskell.org Thu Oct 26 23:21:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement search for *.hs and *.o files for a given package. (750a43f) Message-ID: <20171026232129.D35C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/750a43fcef635a38485a1a2ecc30412e557e44f0/ghc >--------------------------------------------------------------- commit 750a43fcef635a38485a1a2ecc30412e557e44f0 Author: Andrey Mokhov Date: Tue Jan 13 02:23:01 2015 +0000 Implement search for *.hs and *.o files for a given package. >--------------------------------------------------------------- 750a43fcef635a38485a1a2ecc30412e557e44f0 src/Package/Base.hs | 50 +++++++++++++++++++++++++++++++++++++++----------- 1 file changed, 39 insertions(+), 11 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index d9302b7..a8de80d 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -8,7 +8,8 @@ module Package.Base ( defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, bootPkgConstraints, - pathArgs, packageArgs, includeArgs, srcArgs + pathArgs, packageArgs, includeArgs, pkgHsSources, + pkgDepObjects, pkgLibObjects ) where import Base @@ -108,13 +109,40 @@ includeArgs path dist = <> arg "-optP-include" -- TODO: Shall we also add -cpp? <> concatArgs "-optP" (buildDir "autogen/cabal_macros.h") -srcArgs :: FilePath -> FilePath -> Args -srcArgs path pkgData = do - mods <- arg (Modules pkgData) - dirs <- arg (SrcDirs pkgData) - srcs <- getDirectoryFiles "" $ do - dir <- dirs - modPath <- map (replaceEq '.' pathSeparator) mods - extension <- ["hs", "lhs"] - return $ path dir modPath <.> extension - arg (map normaliseEx srcs) +pkgHsSources :: FilePath -> FilePath -> Action [FilePath] +pkgHsSources path dist = do + let pkgData = path dist "package-data.mk" + dirs <- map (path ) <$> arg (SrcDirs pkgData) + findModuleFiles pkgData dirs [".hs", ".lhs"] + +-- Find objects we depend on (we don't want to depend on split objects) +-- TODO: look for non-hs objects too +pkgDepObjects :: FilePath -> FilePath -> Way -> Action [FilePath] +pkgDepObjects path dist way = do + let pkgData = path dist "package-data.mk" + buildDir = path dist "build" + hs2obj = (buildDir ++) . drop (length path) . (-<.> osuf way) + srcs <- pkgHsSources path dist + return $ map hs2obj srcs + +-- Find objects that go to library +pkgLibObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] +pkgLibObjects path dist stage way = do + let pkgData = path dist "package-data.mk" + buildDir = path dist "build" + split <- splitObjects stage + if split + then do + let suffixes = ["_" ++ osuf way ++ "_split//*"] + findModuleFiles pkgData [buildDir] suffixes + else pkgDepObjects path dist way + +findModuleFiles :: FilePath -> [FilePath] -> [String] -> Action [FilePath] +findModuleFiles pkgData directories suffixes = do + mods <- arg (Modules pkgData) + files <- getDirectoryFiles "" $ do + dir <- directories + modPath <- map (replaceEq '.' pathSeparator) mods + suffix <- suffixes + return $ dir modPath ++ suffix + return $ map normaliseEx files From git at git.haskell.org Thu Oct 26 23:21:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Draft GenPrimopCode argument list. (ed20ac4) Message-ID: <20171026232130.20CE23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ed20ac498137f4c2e3f297e6312da93dab64be6d/ghc >--------------------------------------------------------------- commit ed20ac498137f4c2e3f297e6312da93dab64be6d Author: Andrey Mokhov Date: Wed Sep 23 02:09:29 2015 +0100 Draft GenPrimopCode argument list. >--------------------------------------------------------------- ed20ac498137f4c2e3f297e6312da93dab64be6d src/Settings/Builders/GenPrimopCode.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/src/Settings/Builders/GenPrimopCode.hs b/src/Settings/Builders/GenPrimopCode.hs new file mode 100644 index 0000000..711aa80 --- /dev/null +++ b/src/Settings/Builders/GenPrimopCode.hs @@ -0,0 +1,8 @@ +module Settings.Builders.GenPrimopCode (genPrimopCodeArgs) where + +import Expression +import Predicates (builder) + +-- Stdin/stdout are handled in a special way. See Rules/Actions.hs. +genPrimopCodeArgs :: Args +genPrimopCodeArgs = builder GenPrimopCode ? arg "--make-haskell-wrappers" From git at git.haskell.org Thu Oct 26 23:21:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement terseRun and arArgs functions. (30138cb) Message-ID: <20171026232133.639173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30138cb17e6a67a6036b8c0077d393134c57edd2/ghc >--------------------------------------------------------------- commit 30138cb17e6a67a6036b8c0077d393134c57edd2 Author: Andrey Mokhov Date: Tue Jan 13 02:27:29 2015 +0000 Implement terseRun and arArgs functions. >--------------------------------------------------------------- 30138cb17e6a67a6036b8c0077d393134c57edd2 src/Oracles/Builder.hs | 35 ++++++++++++++++++++++++++++++++++- 1 file changed, 34 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 16b5da5..e4cd7da 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,8 @@ module Oracles.Builder ( Builder (..), - with, run, specified + with, run, terseRun, specified, + arArgs ) where import Data.Char @@ -24,6 +25,7 @@ data Builder = Ar | GhcCabal | Ghc Stage | GhcPkg Stage + deriving Show instance ShowArgs Builder where showArgs builder = showArgs $ fmap words $ do @@ -97,6 +99,33 @@ run builder args = do [exe] <- showArgs builder cmd [exe] =<< args +-- Run the builder with a given collection of arguments printing out a +-- terse commentary with only 'interesting' info for the builder. +-- Raises an error if the builder is not uniquely specified in config files +terseRun :: Builder -> Args -> Action () +terseRun builder args = do + needBuilder builder + [exe] <- showArgs builder + args' <- args + putNormal $ "--------\nRunning " ++ show builder ++ " with arguments:" + mapM_ (putNormal . (" " ++)) $ interestingInfo builder args' + putNormal "--------" + quietly $ cmd [exe] args' + +interestingInfo :: Builder -> [String] -> [String] +interestingInfo builder ss = case builder of + Ar -> prefixAndSuffix 3 1 ss + Ghc _ -> if head ss == "-M" + then prefixAndSuffix 1 1 ss + else prefixAndSuffix 0 4 ss + GhcPkg _ -> prefixAndSuffix 2 0 ss + GhcCabal -> prefixAndSuffix 3 0 ss + where + prefixAndSuffix n m ss = + if length ss <= n + m + then ss + else take n ss ++ ["..."] ++ drop (length ss - m) ss + -- Check if the builder is uniquely specified in config files specified :: Builder -> Condition specified builder = do @@ -104,3 +133,7 @@ specified builder = do return $ case exes of [_] -> True _ -> False + +-- TODO: generalise for other builders +arArgs :: Args +arArgs = arg "q" From git at git.haskell.org Thu Oct 26 23:21:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement generation of PrimopWrappers.hs. Work on generating Config.hs. (7e4f903) Message-ID: <20171026232133.9BE593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e4f9033115b8f0591b3a1e4541b8dd6a4c9d633/ghc >--------------------------------------------------------------- commit 7e4f9033115b8f0591b3a1e4541b8dd6a4c9d633 Author: Andrey Mokhov Date: Wed Sep 23 02:10:25 2015 +0100 Implement generation of PrimopWrappers.hs. Work on generating Config.hs. >--------------------------------------------------------------- 7e4f9033115b8f0591b3a1e4541b8dd6a4c9d633 src/Rules/Generate.hs | 93 ++++++++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 92 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 535f99b..a12f6a8 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -6,6 +6,9 @@ import Rules.Actions import Rules.Resources import Settings +primops :: FilePath +primops = "compiler/stage1/build/primops.txt" + -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] knownGenerators = [ (Alex , ".x" ) @@ -31,7 +34,95 @@ generatePackageCode _ target @ (PartialTarget stage package) = let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ "Exactly one generator expected for " ++ file - ++ "(found: " ++ show gens ++ ")." + ++ " (found: " ++ show gens ++ ")." let (src, builder) = head gens need [src] build $ fullTarget target builder [src] [file] + + path -/- "build/GHC/PrimopWrappers.hs" %> \file -> do + need [primops] + build $ fullTarget target GenPrimopCode [primops] [file] + + priority 2.0 $ path -/- "build/Config.hs" %> \file -> do + config <- generateConfig + writeFileChanged file config + +generateConfig :: Action String +generateConfig = do + cProjectName <- setting ProjectName + cProjectGitCommitId <- setting ProjectGitCommitId + cProjectVersion <- setting ProjectVersion + cProjectVersionInt <- setting ProjectVersionInt + cProjectPatchLevel <- setting ProjectPatchLevel + cProjectPatchLevel1 <- setting ProjectPatchLevel1 + cProjectPatchLevel2 <- setting ProjectPatchLevel2 + cBooterVersion <- setting GhcVersion + cIntegerLibraryType <- case integerLibrary of + integerGmp -> return "IntegerGMP" + integerSimple -> return "IntegerSimple" + _ -> putError $ "Unknown integer library: " ++ integerLibrary ++ "." + cSupportsSplitObjs <- yesNo splitObjects + return "{-# LANGUAGE CPP #-}\n" + ++ "module Config where\n" + ++ "\n" + ++ "#include \"ghc_boot_platform.h\"\n" + ++ "\n" + ++ "data IntegerLibrary = IntegerGMP\n" + ++ " | IntegerSimple\n" + ++ " deriving Eq\n" + ++ "\n" + ++ "cBuildPlatformString :: String\n" + ++ "cBuildPlatformString = BuildPlatform_NAME\n" + ++ "cHostPlatformString :: String\n" + ++ "cHostPlatformString = HostPlatform_NAME\n" + ++ "cTargetPlatformString :: String\n" + ++ "cTargetPlatformString = TargetPlatform_NAME\n" + ++ "\n" + ++ "cProjectName :: String\n" + ++ "cProjectName = " ++ cProjectName ++ "\n" + ++ "cProjectGitCommitId :: String\n" + ++ "cProjectGitCommitId = " ++ cProjectGitCommitId ++ "\n" + ++ "cProjectVersion :: String\n" + ++ "cProjectVersion = " ++ cProjectVersion ++ "\n" + ++ "cProjectVersionInt :: String\n" + ++ "cProjectVersionInt = " ++ cProjectVersionInt ++ "\n" + ++ "cProjectPatchLevel :: String\n" + ++ "cProjectPatchLevel = " ++ cProjectPatchLevel ++ "\n" + ++ "cProjectPatchLevel1 :: String\n" + ++ "cProjectPatchLevel1 = " ++ cProjectPatchLevel1 ++ "\n" + ++ "cProjectPatchLevel2 :: String\n" + ++ "cProjectPatchLevel2 = " ++ cProjectPatchLevel2 ++ "\n" + ++ "cBooterVersion :: String\n" + ++ "cBooterVersion = " ++ cBooterVersion ++ "\n" + ++ "cStage :: String\n" + ++ "cStage = show (STAGE :: Int)\n" + ++ "cIntegerLibrary :: String\n" + ++ "cIntegerLibrary = " ++ pkgName integerLibrary ++ "\n" + ++ "cIntegerLibraryType :: IntegerLibrary\n" + ++ "cIntegerLibraryType = " ++ cIntegerLibraryType ++ "\n" + ++ "cSupportsSplitObjs :: String\n" + ++ "cSupportsSplitObjs = " ++ cSupportsSplitObjs ++ "\n" + ++ "cGhcWithInterpreter :: String\n" + ++ "cGhcWithInterpreter = "YES"\n" + ++ "cGhcWithNativeCodeGen :: String\n" + ++ "cGhcWithNativeCodeGen = "YES"\n" + ++ "cGhcWithSMP :: String\n" + ++ "cGhcWithSMP = "YES"\n" + ++ "cGhcRTSWays :: String\n" + ++ "cGhcRTSWays = "l debug thr thr_debug thr_l thr_p "\n" + ++ "cGhcEnableTablesNextToCode :: String\n" + ++ "cGhcEnableTablesNextToCode = "YES"\n" + ++ "cLeadingUnderscore :: String\n" + ++ "cLeadingUnderscore = "NO"\n" + ++ "cGHC_UNLIT_PGM :: String\n" + ++ "cGHC_UNLIT_PGM = "unlit.exe"\n" + ++ "cGHC_SPLIT_PGM :: String\n" + ++ "cGHC_SPLIT_PGM = "ghc-split"\n" + ++ "cLibFFI :: Bool\n" + ++ "cLibFFI = False\n" + ++ "cGhcThreaded :: Bool\n" + ++ "cGhcThreaded = True\n" + ++ "cGhcDebugged :: Bool\n" + ++ "cGhcDebugged = False\n" + + From git at git.haskell.org Thu Oct 26 23:21:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use terseRun and new configuration options. (efb5972) Message-ID: <20171026232136.E1BCE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efb59728189c8a5bd9270d1c3f00787ed4b27913/ghc >--------------------------------------------------------------- commit efb59728189c8a5bd9270d1c3f00787ed4b27913 Author: Andrey Mokhov Date: Tue Jan 13 02:29:17 2015 +0000 Use terseRun and new configuration options. >--------------------------------------------------------------- efb59728189c8a5bd9270d1c3f00787ed4b27913 src/Package/Compile.hs | 4 ++-- src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 6 +++--- 3 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 50cf412..6badbb7 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -43,7 +43,7 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = let deps = concat $ snd $ unzip $ filter ((== out) . fst) depContents srcs = filter ("//*hs" ?==) deps -- TODO: handle *.c sources need deps - run (Ghc stage) $ suffixArgs way + terseRun (Ghc stage) $ suffixArgs way <> wayHcArgs way <> arg SrcHcOpts <> packageArgs stage pkgData @@ -51,6 +51,6 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = -- TODO: now we have both -O and -O2 <> arg ["-Wall", "-XHaskell2010", "-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir - <> arg "-split-objs" + <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) <> arg ["-o", out] diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 7ff0d7d..a73a521 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -93,6 +93,6 @@ buildPackageData (Package name path _) (stage, dist, settings) = need ["shake/src/Package/Data.hs"] need [path name <.> "cabal"] when (doesFileExist $ configure <.> "ac") $ need [configure] - run GhcCabal cabalArgs - when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs + terseRun GhcCabal cabalArgs + when (registerPackage settings) $ terseRun (GhcPkg stage) ghcPkgArgs postProcessPackageData $ pathDist "package-data.mk" diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 1cb512d..f3a494b 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -10,13 +10,13 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = in (buildDir name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] - run (Ghc stage) $ arg "-M" + terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData <> includeArgs path dist <> productArgs ["-odir", "-stubdir"] buildDir <> arg ["-dep-makefile", out] - <> productArgs "-dep-suffix" (map suffix <$> ways settings) - <> srcArgs path pkgData + <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) + <> arg (pkgHsSources path dist) -- TODO: Check that skipping all _HC_OPTS is safe. -- <> arg SrcHcOpts -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? From git at git.haskell.org Thu Oct 26 23:21:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcSplit and Unlit builders. (47c7ab1) Message-ID: <20171026232137.3188A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47c7ab173f636eb0c636765b412c523bdb3e7fb3/ghc >--------------------------------------------------------------- commit 47c7ab173f636eb0c636765b412c523bdb3e7fb3 Author: Andrey Mokhov Date: Thu Sep 24 05:43:05 2015 +0100 Add GhcSplit and Unlit builders. >--------------------------------------------------------------- 47c7ab173f636eb0c636765b412c523bdb3e7fb3 cfg/system.config.in | 4 ++++ src/Builder.hs | 11 ++++++++++- 2 files changed, 14 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 2bfe449..87d2b93 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -23,6 +23,9 @@ hsc2hs = @hardtop@/inplace/bin/hsc2hs genprimopcode = @hardtop@/inplace/bin/genprimopcode +unlit = @hardtop@/inplace/lib/unlit +ghc-split = @hardtop@/inplace/lib/ghc-split + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ @@ -43,6 +46,7 @@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ ghc-source-path = @hardtop@ +leading-underscore = @LeadingUnderscore@ # Information about host and target systems: #=========================================== diff --git a/src/Builder.hs b/src/Builder.hs index 9448ed2..a6521a1 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,5 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} -module Builder (Builder (..), builderPath, specified, needBuilder) where +module Builder ( + Builder (..), builderPath, getBuilderPath, specified, needBuilder + ) where import Base import GHC.Generics (Generic) @@ -24,11 +26,13 @@ data Builder = Alex | GhcCabalHsColour | GhcM Stage | GhcPkg Stage + | GhcSplit | Haddock | Happy | HsColour | Hsc2Hs | Ld + | Unlit deriving (Show, Eq, Generic) -- Configuration files refer to Builders as follows: @@ -49,11 +53,13 @@ builderKey builder = case builder of GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" + GhcSplit -> "ghc-split" Happy -> "happy" Haddock -> "haddock" HsColour -> "hscolour" Hsc2Hs -> "hsc2hs" Ld -> "ld" + Unlit -> "unlit" builderPath :: Builder -> Action FilePath builderPath builder = do @@ -62,6 +68,9 @@ builderPath builder = do ++ "' in configuration files." fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe +getBuilderPath :: Builder -> ReaderT a Action FilePath +getBuilderPath = lift . builderPath + specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath From git at git.haskell.org Thu Oct 26 23:21:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement new build rule: buildPackageLibrary. (2143dce) Message-ID: <20171026232140.5AB143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2143dce721122b3e9e0b08fb4691160305f0ba99/ghc >--------------------------------------------------------------- commit 2143dce721122b3e9e0b08fb4691160305f0ba99 Author: Andrey Mokhov Date: Tue Jan 13 02:30:01 2015 +0000 Implement new build rule: buildPackageLibrary. >--------------------------------------------------------------- 2143dce721122b3e9e0b08fb4691160305f0ba99 src/Package/Library.hs | 25 +++++++++++++++++++++++++ 1 file changed, 25 insertions(+) diff --git a/src/Package/Library.hs b/src/Package/Library.hs new file mode 100644 index 0000000..9598b1a --- /dev/null +++ b/src/Package/Library.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module Package.Library (buildPackageLibrary) where + +import Package.Base + +{- "/usr/bin/ar" q +libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a + at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents +-} + +-- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents +-- AR_OPTS = $(SRC_AR_OPTS) $(WAY$(_way)_AR_OPTS) $(EXTRA_AR_OPTS) + +buildPackageLibrary :: Package -> TodoItem -> Rules () +buildPackageLibrary (Package _ path _) (stage, dist, _) = + let buildDir = path dist "build" + pkgData = path dist "package-data.mk" + in + (buildDir "*a") %> \out -> do + let way = detectWay $ tail $ takeExtension out + need ["shake/src/Package/Library.hs"] + depObjs <- pkgDepObjects path dist way + need depObjs + libObjs <- pkgLibObjects path dist stage way + terseRun Ar $ arArgs <+> out <+> libObjs From git at git.haskell.org Thu Oct 26 23:21:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove old library files before calling Ar. (5aa3add) Message-ID: <20171026232144.08CA03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5aa3addc4ed59f1984e040415d707f4067f82007/ghc >--------------------------------------------------------------- commit 5aa3addc4ed59f1984e040415d707f4067f82007 Author: Andrey Mokhov Date: Tue Jan 13 02:45:49 2015 +0000 Remove old library files before calling Ar. >--------------------------------------------------------------- 5aa3addc4ed59f1984e040415d707f4067f82007 src/Package/Library.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 9598b1a..0c2e1f8 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -22,4 +22,5 @@ buildPackageLibrary (Package _ path _) (stage, dist, _) = depObjs <- pkgDepObjects path dist way need depObjs libObjs <- pkgLibObjects path dist stage way + liftIO $ removeFiles "" [out] terseRun Ar $ arArgs <+> out <+> libObjs From git at git.haskell.org Thu Oct 26 23:21:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix ghcEnableTablesNextToCode, refactor code. (aecfdda) Message-ID: <20171026232140.A09D33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aecfddac1536bf6f565df227acff0ab37ce534a8/ghc >--------------------------------------------------------------- commit aecfddac1536bf6f565df227acff0ab37ce534a8 Author: Andrey Mokhov Date: Thu Sep 24 05:45:34 2015 +0100 Fix ghcEnableTablesNextToCode, refactor code. >--------------------------------------------------------------- aecfddac1536bf6f565df227acff0ab37ce534a8 src/Oracles/Config/Flag.hs | 35 ++++++++++++++++------------- src/Oracles/Config/Setting.hs | 52 ++++++++++++++++++------------------------- 2 files changed, 42 insertions(+), 45 deletions(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index d520a85..69d4884 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -1,7 +1,7 @@ module Oracles.Config.Flag ( Flag (..), flag, getFlag, - crossCompiling, gccIsClang, gccGe46, - platformSupportsSharedLibs, ghcWithSMP, ghcWithNativeCodeGen + crossCompiling, platformSupportsSharedLibs, ghcWithSMP, + ghcWithNativeCodeGen, supportsSplitObjects ) where import Base @@ -12,6 +12,7 @@ data Flag = CrossCompiling | GccIsClang | GccLt46 | GhcUnregisterised + | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken | SupportsPackageKey @@ -25,6 +26,7 @@ flag f = do GccIsClang -> "gcc-is-clang" GccLt46 -> "gcc-lt-46" GhcUnregisterised -> "ghc-unregisterised" + LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" SupportsPackageKey -> "supports-package-key" @@ -41,30 +43,33 @@ getFlag = lift . flag crossCompiling :: Action Bool crossCompiling = flag CrossCompiling -gccIsClang :: Action Bool -gccIsClang = flag GccIsClang - -gccGe46 :: Action Bool -gccGe46 = fmap not $ flag GccLt46 - platformSupportsSharedLibs :: Action Bool platformSupportsSharedLibs = do - badPlatform <- targetPlatforms [ "powerpc-unknown-linux" - , "x86_64-unknown-mingw32" - , "i386-unknown-mingw32" ] - solaris <- targetPlatform "i386-unknown-solaris2" + badPlatform <- anyTargetPlatform [ "powerpc-unknown-linux" + , "x86_64-unknown-mingw32" + , "i386-unknown-mingw32" ] + solaris <- anyTargetPlatform [ "i386-unknown-solaris2" ] solarisBroken <- flag SolarisBrokenShld return $ not (badPlatform || solaris && solarisBroken) ghcWithSMP :: Action Bool ghcWithSMP = do - goodArch <- targetArchs ["i386", "x86_64", "sparc", "powerpc", "arm"] + goodArch <- anyTargetArch ["i386", "x86_64", "sparc", "powerpc", "arm"] ghcUnreg <- flag GhcUnregisterised return $ goodArch && not ghcUnreg ghcWithNativeCodeGen :: Action Bool ghcWithNativeCodeGen = do - goodArch <- targetArchs ["i386", "x86_64", "sparc", "powerpc"] - badOs <- targetOss ["ios", "aix"] + goodArch <- anyTargetArch ["i386", "x86_64", "sparc", "powerpc"] + badOs <- anyTargetOs ["ios", "aix"] ghcUnreg <- flag GhcUnregisterised return $ goodArch && not badOs && not ghcUnreg + +supportsSplitObjects :: Action Bool +supportsSplitObjects = do + broken <- flag SplitObjectsBroken + ghcUnreg <- flag GhcUnregisterised + goodArch <- anyTargetArch [ "i386", "x86_64", "powerpc", "sparc" ] + goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "darwin", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" ] + return $ not broken && not ghcUnreg && goodArch && goodOs diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 8ee4752..e1dfefa 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -1,9 +1,9 @@ module Oracles.Config.Setting ( Setting (..), SettingList (..), setting, settingList, getSetting, getSettingList, - targetPlatform, targetPlatforms, targetOs, targetOss, notTargetOs, - targetArchs, windowsHost, notWindowsHost, ghcWithInterpreter, - ghcEnableTablesNextToCode, ghcCanonVersion, cmdLineLengthLimit + anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, windowsHost, + ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, + ghcCanonVersion, cmdLineLengthLimit ) where import Base @@ -83,45 +83,37 @@ getSettingList :: SettingList -> ReaderT a Action [String] getSettingList = lift . settingList matchSetting :: Setting -> [String] -> Action Bool -matchSetting key values = do - value <- setting key - return $ value `elem` values +matchSetting key values = fmap (`elem` values) $ setting key -targetPlatforms :: [String] -> Action Bool -targetPlatforms = matchSetting TargetPlatformFull +anyTargetPlatform :: [String] -> Action Bool +anyTargetPlatform = matchSetting TargetPlatformFull -targetPlatform :: String -> Action Bool -targetPlatform s = targetPlatforms [s] +anyTargetOs :: [String] -> Action Bool +anyTargetOs = matchSetting TargetOs -targetOss :: [String] -> Action Bool -targetOss = matchSetting TargetOs +anyTargetArch :: [String] -> Action Bool +anyTargetArch = matchSetting TargetArch -targetOs :: String -> Action Bool -targetOs s = targetOss [s] - -notTargetOs :: String -> Action Bool -notTargetOs = fmap not . targetOs - -targetArchs :: [String] -> Action Bool -targetArchs = matchSetting TargetArch +anyHostOs :: [String] -> Action Bool +anyHostOs = matchSetting HostOs windowsHost :: Action Bool -windowsHost = matchSetting HostOs ["mingw32", "cygwin32"] - -notWindowsHost :: Action Bool -notWindowsHost = fmap not windowsHost +windowsHost = anyHostOs ["mingw32", "cygwin32"] ghcWithInterpreter :: Action Bool ghcWithInterpreter = do - goodOs <- targetOss [ "mingw32", "cygwin32", "linux", "solaris2" - , "freebsd", "dragonfly", "netbsd", "openbsd" - , "darwin", "kfreebsdgnu" ] - goodArch <- targetArchs [ "i386", "x86_64", "powerpc", "sparc" - , "sparc64", "arm" ] + goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" + , "darwin", "kfreebsdgnu" ] + goodArch <- anyTargetArch [ "i386", "x86_64", "powerpc", "sparc" + , "sparc64", "arm" ] return $ goodOs && goodArch ghcEnableTablesNextToCode :: Action Bool -ghcEnableTablesNextToCode = targetArchs ["ia64", "powerpc64"] +ghcEnableTablesNextToCode = notM $ anyTargetArch ["ia64", "powerpc64", "powerpc64le"] + +useLibFFIForAdjustors :: Action Bool +useLibFFIForAdjustors = notM $ anyTargetArch ["i386", "x86_64"] -- Canonicalised GHC version number, used for integer version comparisons. We -- expand GhcMinorVersion to two digits by adding a leading zero if necessary. From git at git.haskell.org Thu Oct 26 23:21:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix GhcPrim path in getPackageSources. (c7f9f7c) Message-ID: <20171026232144.451013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7f9f7c349b0498f9a42b4a2c2dbc02082d03645/ghc >--------------------------------------------------------------- commit c7f9f7c349b0498f9a42b4a2c2dbc02082d03645 Author: Andrey Mokhov Date: Thu Sep 24 05:46:13 2015 +0100 Fix GhcPrim path in getPackageSources. >--------------------------------------------------------------- c7f9f7c349b0498f9a42b4a2c2dbc02082d03645 src/Settings.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/src/Settings.hs b/src/Settings.hs index 1a35a94..dab73ed 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -37,14 +37,17 @@ getPackageSources = do srcDirs <- getPkgDataList SrcDirs let buildPath = path -/- "build" - dirs = (buildPath -/- "autogen") : map (packagePath -/-) srcDirs + autogen = buildPath -/- "autogen" + dirs = autogen : map (packagePath -/-) srcDirs (foundSources, missingSources) <- findModuleFiles dirs "*hs" - -- Generated source files live in buildPath and have extension "hs" + -- Generated source files live in buildPath and have extension "hs"... let generatedSources = [ buildPath -/- s <.> "hs" | s <- missingSources ] + -- ...except that GHC/Prim.hs lives in autogen. TODO: fix? + fixGhcPrim = replaceEq (buildPath -/- "GHC/Prim.hs") (autogen -/- "GHC/Prim.hs") - return $ foundSources ++ generatedSources + return $ foundSources ++ fixGhcPrim generatedSources -- findModuleFiles scans a list of given directories and finds files matching a -- given extension pattern (e.g., "*hs") that correspond to modules of the From git at git.haskell.org Thu Oct 26 23:21:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve terseRun. (4fcb471) Message-ID: <20171026232147.691283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fcb471826530ba60abdc40b2ed4304910edf24a/ghc >--------------------------------------------------------------- commit 4fcb471826530ba60abdc40b2ed4304910edf24a Author: Andrey Mokhov Date: Tue Jan 13 03:05:35 2015 +0000 Improve terseRun. >--------------------------------------------------------------- 4fcb471826530ba60abdc40b2ed4304910edf24a src/Oracles/Builder.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index e4cd7da..ffc3cf5 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -122,9 +122,13 @@ interestingInfo builder ss = case builder of GhcCabal -> prefixAndSuffix 3 0 ss where prefixAndSuffix n m ss = - if length ss <= n + m + if length ss <= n + m + 1 then ss - else take n ss ++ ["..."] ++ drop (length ss - m) ss + else take n ss + ++ ["... skipping " + ++ show (length ss - n - m) + ++ " arguments ..."] + ++ drop (length ss - m) ss -- Check if the builder is uniquely specified in config files specified :: Builder -> Condition From git at git.haskell.org Thu Oct 26 23:21:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code. (28e3a26) Message-ID: <20171026232147.A96A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28e3a26cbaa18b6efc353d543843efd1efb311f0/ghc >--------------------------------------------------------------- commit 28e3a26cbaa18b6efc353d543843efd1efb311f0 Author: Andrey Mokhov Date: Thu Sep 24 05:47:46 2015 +0100 Clean up code. >--------------------------------------------------------------- 28e3a26cbaa18b6efc353d543843efd1efb311f0 src/Predicates.hs | 15 +++++---------- src/Settings/Builders/GhcCabal.hs | 18 +++++++++--------- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages.hs | 8 ++++---- 4 files changed, 19 insertions(+), 24 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 00c12ca..13482b7 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -43,7 +43,7 @@ stage2 :: Predicate stage2 = stage Stage2 notStage0 :: Predicate -notStage0 = fmap not stage0 +notStage0 = notM stage0 -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate @@ -51,12 +51,7 @@ registerPackage = return True splitObjects :: Predicate splitObjects = do - goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages - goodPkg <- fmap not $ package compiler -- We don't split compiler - broken <- getFlag SplitObjectsBroken - ghcUnreg <- getFlag GhcUnregisterised - goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] - goodOs <- lift $ targetOss [ "mingw32", "cygwin32", "linux", "darwin" - , "solaris2", "freebsd", "dragonfly" - , "netbsd", "openbsd" ] - return $ goodStage && goodPkg && not broken && not ghcUnreg && goodArch && goodOs + goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages + goodPackage <- notM $ package compiler -- We don't split compiler + supported <- lift supportsSplitObjects + return $ goodStage && goodPackage && supported diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index ab65a51..54452d8 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -101,12 +101,12 @@ ccArgs = validating ? ccWarnings -- TODO: should be in a different file ccWarnings :: Args ccWarnings = do - let notClang = fmap not gccIsClang + let gccGe46 = notM $ (flag GccIsClang ||^ flag GccLt46) mconcat [ arg "-Werror" , arg "-Wall" - , gccIsClang ? arg "-Wno-unknown-pragmas" - , notClang ? gccGe46 ? notWindowsHost ? arg "-Werror=unused-but-set-variable" - , notClang ? gccGe46 ? arg "-Wno-error=inline" ] + , flag GccIsClang ? arg "-Wno-unknown-pragmas" + , gccGe46 ? notM windowsHost ? arg "-Werror=unused-but-set-variable" + , gccGe46 ? arg "-Wno-error=inline" ] ldArgs :: Args ldArgs = mempty @@ -147,10 +147,10 @@ customPackageArgs = do mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show nextStage , arg $ "--flags=stage" ++ show nextStage , arg "--disable-library-for-ghci" - , targetOs "openbsd" ? arg "--ld-options=-E" + , anyTargetOs ["openbsd"] ? arg "--ld-options=-E" , flag GhcUnregisterised ? arg "--ghc-option=-DNO_REGS" - , fmap not ghcWithSMP ? arg "--ghc-option=-DNOSMP" - , fmap not ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" + , notM ghcWithSMP ? arg "--ghc-option=-DNOSMP" + , notM ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" , (threaded `elem` rtsWays) ? notStage0 ? arg "--ghc-option=-optc-DTHREADED_RTS" , ghcWithNativeCodeGen ? arg "--flags=ncg" @@ -158,7 +158,7 @@ customPackageArgs = do notStage0 ? arg "--flags=ghci" , ghcWithInterpreter ? ghcEnableTablesNextToCode ? - fmap not (flag GhcUnregisterised) ? + notM (flag GhcUnregisterised) ? notStage0 ? arg "--ghc-option=-DGHCI_TABLES_NEXT_TO_CODE" , ghcWithInterpreter ? ghciWithDebugger ? @@ -183,7 +183,7 @@ withBuilderKey b = case b of -- Expression 'with Gcc' appends "--with-gcc=/path/to/gcc" and needs Gcc. with :: Builder -> Args with b = specified b ? do - path <- lift $ builderPath b + path <- getBuilderPath b lift $ needBuilder laxDependencies b append [withBuilderKey b ++ path] diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index fae7c1f..7dfe286 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -24,7 +24,7 @@ hsc2HsArgs = builder Hsc2Hs ? do else getSetting ProjectVersionInt mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath - , notWindowsHost ? arg "--cross-safe" + , notM windowsHost ? arg "--cross-safe" , append $ map ("-I" ++) gmpDirs , append $ map ("--cflag=" ++) cFlags , append $ map ("--lflag=" ++) lFlags diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 87f293d..dee0c95 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -17,7 +17,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binPackageDb, binary, cabal, compiler, hoopl, hpc, transformers ] - , notWindowsHost ? notTargetOs "ios" ? append [terminfo] ] + , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages @@ -26,9 +26,9 @@ packagesStage1 = mconcat , append [ array, base, bytestring, containers, deepseq, directory , filepath, ghcPrim, haskeline, integerLibrary, pretty, process , templateHaskell, time ] - , windowsHost ? append [win32] - , notWindowsHost ? append [unix] - , buildHaddock ? append [xhtml] ] + , windowsHost ? append [win32] + , notM windowsHost ? append [unix] + , buildHaddock ? append [xhtml] ] knownPackages :: [Package] knownPackages = defaultKnownPackages ++ userKnownPackages From git at git.haskell.org Thu Oct 26 23:21:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise buildPackageDependencies rule. (7c45e18) Message-ID: <20171026232151.AA9BD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c45e18e0d1ef091aac126e9a316ac9cd5f0a2bb/ghc >--------------------------------------------------------------- commit 7c45e18e0d1ef091aac126e9a316ac9cd5f0a2bb Author: Andrey Mokhov Date: Tue Jan 13 03:13:10 2015 +0000 Optimise buildPackageDependencies rule. >--------------------------------------------------------------- 7c45e18e0d1ef091aac126e9a316ac9cd5f0a2bb src/Package/Dependencies.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index f3a494b..7390b2e 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -14,10 +14,13 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = <> packageArgs stage pkgData <> includeArgs path dist <> productArgs ["-odir", "-stubdir"] buildDir - <> arg ["-dep-makefile", out] + <> arg ["-dep-makefile", out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) <> arg (pkgHsSources path dist) -- TODO: Check that skipping all _HC_OPTS is safe. -- <> arg SrcHcOpts -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? -- <> wayHcOpts vanilla + -- Avoid rebuilding dependecies of out if it hasn't changed: + copyFileChanged (out <.> "new") out + removeFilesAfter "." [out <.> "new"] From git at git.haskell.org Thu Oct 26 23:21:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add getLibWays to capture context-less ways. (cc3113d) Message-ID: <20171026232151.DD63D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cc3113db2263c179a4e91440a9369f44a2825980/ghc >--------------------------------------------------------------- commit cc3113db2263c179a4e91440a9369f44a2825980 Author: Andrey Mokhov Date: Thu Sep 24 05:49:11 2015 +0100 Add getLibWays to capture context-less ways. >--------------------------------------------------------------- cc3113db2263c179a4e91440a9369f44a2825980 src/Settings/User.hs | 14 +++++++++----- src/Settings/Ways.hs | 17 ++++++++++------- 2 files changed, 19 insertions(+), 12 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index f9a430c..5b62e39 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,8 +1,8 @@ module Settings.User ( - userArgs, userPackages, userWays, userRtsWays, userTargetDirectory, + userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - dynamicGhcPrograms, laxDependencies + ghcDebugged, dynamicGhcPrograms, laxDependencies ) where import Expression @@ -21,9 +21,9 @@ userPackages = mempty userKnownPackages :: [Package] userKnownPackages = [] --- Control which ways are built -userWays :: Ways -userWays = mempty +-- Control which ways libraries and rts are built +userLibWays :: Ways +userLibWays = mempty userRtsWays :: Ways userRtsWays = mempty @@ -60,6 +60,10 @@ ghciWithDebugger = False ghcProfiled :: Bool ghcProfiled = False +-- TODO: do we need to be able to set this from command line? +ghcDebugged :: Bool +ghcDebugged = False + -- When laxDependencies flag is set to True, dependencies on the GHC executable -- are turned into order-only dependencies to avoid needless recompilation when -- making changes to GHC's sources. In certain situations this can lead to build diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index cafed64..ad42cea 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,26 +1,29 @@ -module Settings.Ways (getWays, getRtsWays) where +module Settings.Ways (getWays, getLibWays, getRtsWays) where import Expression import Predicates import Settings.User -- Combining default ways with user modifications +getLibWays :: Expr [Way] +getLibWays = fromDiffExpr $ defaultLibWays <> userLibWays + +-- In Stage0 we only build vanilla getWays :: Expr [Way] -getWays = fromDiffExpr $ defaultWays <> userWays +getWays = mconcat [ stage0 ? return [vanilla], notStage0 ? getLibWays ] getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays -- These are default ways -defaultWays :: Ways -defaultWays = mconcat - [ append [vanilla] -- always build vanilla - , notStage0 ? append [profiling] +defaultLibWays :: Ways +defaultLibWays = mconcat + [ append [vanilla, profiling] , platformSupportsSharedLibs ? append [dynamic] ] defaultRtsWays :: Ways defaultRtsWays = do - ways <- getWays + ways <- getLibWays mconcat [ append [ logging, debug, threaded, threadedDebug, threadedLogging ] , (profiling `elem` ways) ? append [threadedProfiling] From git at git.haskell.org Thu Oct 26 23:21:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise buildPackageDependencies rule. (1e5c095) Message-ID: <20171026232155.1F5303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1e5c0952d044d8c1c16988e221d014443b04fb19/ghc >--------------------------------------------------------------- commit 1e5c0952d044d8c1c16988e221d014443b04fb19 Author: Andrey Mokhov Date: Tue Jan 13 03:30:54 2015 +0000 Optimise buildPackageDependencies rule. >--------------------------------------------------------------- 1e5c0952d044d8c1c16988e221d014443b04fb19 src/Package/Dependencies.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 7390b2e..6339adb 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -22,5 +22,7 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? -- <> wayHcOpts vanilla -- Avoid rebuilding dependecies of out if it hasn't changed: - copyFileChanged (out <.> "new") out + -- Note: cannot use copyFileChanged as it depends on the source file + deps <- liftIO $ readFile $ out <.> "new" + writeFileChanged out deps removeFilesAfter "." [out <.> "new"] From git at git.haskell.org Thu Oct 26 23:21:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement all modes of GenPrimopCode builder. (1a17fee) Message-ID: <20171026232155.5D1D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a17fee2b8dc82a4b4778cf1f3219fdad584db8d/ghc >--------------------------------------------------------------- commit 1a17fee2b8dc82a4b4778cf1f3219fdad584db8d Author: Andrey Mokhov Date: Thu Sep 24 05:49:39 2015 +0100 Implement all modes of GenPrimopCode builder. >--------------------------------------------------------------- 1a17fee2b8dc82a4b4778cf1f3219fdad584db8d src/Settings/Builders/GenPrimopCode.hs | 23 +++++++++++++++++++++-- 1 file changed, 21 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/GenPrimopCode.hs b/src/Settings/Builders/GenPrimopCode.hs index 711aa80..6de1f47 100644 --- a/src/Settings/Builders/GenPrimopCode.hs +++ b/src/Settings/Builders/GenPrimopCode.hs @@ -1,8 +1,27 @@ module Settings.Builders.GenPrimopCode (genPrimopCodeArgs) where import Expression -import Predicates (builder) +import Predicates (builder, file) -- Stdin/stdout are handled in a special way. See Rules/Actions.hs. +-- TODO: Do we want to keep "--usage"? It seems to be unused. genPrimopCodeArgs :: Args -genPrimopCodeArgs = builder GenPrimopCode ? arg "--make-haskell-wrappers" +genPrimopCodeArgs = builder GenPrimopCode ? mconcat + [ file "//PrimopWrappers.hs" ? arg "--make-haskell-wrappers" + , file "//Prim.hs" ? arg "--make-haskell-source" + , file "//primop-data-decl.hs-incl" ? arg "--data-decl" + , file "//primop-tag.hs-incl" ? arg "--primop-tag" + , file "//primop-list.hs-incl" ? arg "--primop-list" + , file "//primop-has-side-effects.hs-incl" ? arg "--has-side-effects" + , file "//primop-out-of-line.hs-incl" ? arg "--out-of-line" + , file "//primop-commutable.hs-incl" ? arg "--commutable" + , file "//primop-code-size.hs-incl" ? arg "--code-size" + , file "//primop-can-fail.hs-incl" ? arg "--can-fail" + , file "//primop-strictness.hs-incl" ? arg "--strictness" + , file "//primop-fixity.hs-incl" ? arg "--fixity" + , file "//primop-primop-info.hs-incl" ? arg "--primop-primop-info" + , file "//primop-vector-uniques.hs-incl" ? arg "--primop-vector-uniques" + , file "//primop-vector-tys.hs-incl" ? arg "--primop-vector-tys" + , file "//primop-vector-tys-exports.hs-incl" ? arg "--primop-vector-tys-exports" + , file "//primop-vector-tycons.hs-incl" ? arg "--primop-vector-tycons" + , file "//primop-usage.hs-incl" ? arg "--usage" ] From git at git.haskell.org Thu Oct 26 23:21:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Print more diagnostic info. (0ad3af2) Message-ID: <20171026232158.C2CB23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ad3af27554bdaa8ba765353ca53256d4f342f32/ghc >--------------------------------------------------------------- commit 0ad3af27554bdaa8ba765353ca53256d4f342f32 Author: Andrey Mokhov Date: Tue Jan 13 04:05:59 2015 +0000 Print more diagnostic info. >--------------------------------------------------------------- 0ad3af27554bdaa8ba765353ca53256d4f342f32 src/Oracles.hs | 1 + src/Oracles/PackageData.hs | 2 ++ src/Package/Library.hs | 16 ++++++++++++---- 3 files changed, 15 insertions(+), 4 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 3a0c430..5b2ff11 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -49,6 +49,7 @@ packageDataOracle :: Rules () packageDataOracle = do pkgData <- newCache $ \file -> do need [file] + putNormal $ "Parsing " ++ file ++ "..." liftIO $ readConfigFile file addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 6bffafd..66a3f55 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -18,6 +18,7 @@ data PackageData = Modules FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath + | Synopsis FilePath instance ShowArgs PackageData where showArgs packageData = do @@ -28,6 +29,7 @@ instance ShowArgs PackageData where IncludeDirs file -> ("INCLUDE_DIRS", file, ".") Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) + Synopsis file -> ("SYNOPSIS" , file, "" ) fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key res <- askOracle $ PackageDataKey (file, fullKey) return $ words $ case res of diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 0c2e1f8..6660a2f 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -5,14 +5,16 @@ import Package.Base {- "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a - at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a +.contents -} --- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents +-- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) +-- $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents -- AR_OPTS = $(SRC_AR_OPTS) $(WAY$(_way)_AR_OPTS) $(EXTRA_AR_OPTS) buildPackageLibrary :: Package -> TodoItem -> Rules () -buildPackageLibrary (Package _ path _) (stage, dist, _) = +buildPackageLibrary (Package name path _) (stage, dist, _) = let buildDir = path dist "build" pkgData = path dist "package-data.mk" in @@ -22,5 +24,11 @@ buildPackageLibrary (Package _ path _) (stage, dist, _) = depObjs <- pkgDepObjects path dist way need depObjs libObjs <- pkgLibObjects path dist stage way - liftIO $ removeFiles "" [out] + liftIO $ removeFiles "." [out] terseRun Ar $ arArgs <+> out <+> libObjs + when (way == vanilla) $ do + synopsis <- unwords <$> arg (Synopsis pkgData) + putNormal $ "Successfully built library for package " + ++ name ++ "." + putNormal $ "Synopsis: " ++ synopsis ++ "." + From git at git.haskell.org Thu Oct 26 23:21:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:21:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix untracked .hs-incl dependencies. (9b9f7d2) Message-ID: <20171026232159.0FB493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b9f7d2fd05b4bb146d794bd9fd1e67ba8311cb2/ghc >--------------------------------------------------------------- commit 9b9f7d2fd05b4bb146d794bd9fd1e67ba8311cb2 Author: Andrey Mokhov Date: Thu Sep 24 05:50:17 2015 +0100 Fix untracked .hs-incl dependencies. >--------------------------------------------------------------- 9b9f7d2fd05b4bb146d794bd9fd1e67ba8311cb2 src/Rules/Dependencies.hs | 22 +++++++++++++++++++++- 1 file changed, 21 insertions(+), 1 deletion(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index c9b5b89..8fd9ca8 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -1,6 +1,7 @@ module Rules.Dependencies (buildPackageDependencies) where import Expression +import GHC import Oracles import Rules.Actions import Rules.Resources @@ -30,4 +31,23 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need $ hDepFile : cDepFiles -- need all for more parallelism cDeps <- fmap concat $ mapM readFile' cDepFiles hDeps <- readFile' hDepFile - writeFileChanged file $ cDeps ++ hDeps + -- TODO: very ugly and fragile + let hsIncl hs incl = buildPath -/- hs <.> "o" ++ " : " + ++ buildPath -/- incl ++ "\n" + extraDeps = if pkg /= compiler then [] else + hsIncl "PrelNames" "primop-vector-uniques.hs-incl" + ++ hsIncl "PrimOp" "primop-data-decl.hs-incl" + ++ hsIncl "PrimOp" "primop-tag.hs-incl" + ++ hsIncl "PrimOp" "primop-list.hs-incl" + ++ hsIncl "PrimOp" "primop-strictness.hs-incl" + ++ hsIncl "PrimOp" "primop-fixity.hs-incl" + ++ hsIncl "PrimOp" "primop-primop-info.hs-incl" + ++ hsIncl "PrimOp" "primop-out-of-line.hs-incl" + ++ hsIncl "PrimOp" "primop-has-side-effects.hs-incl" + ++ hsIncl "PrimOp" "primop-can-fail.hs-incl" + ++ hsIncl "PrimOp" "primop-code-size.hs-incl" + ++ hsIncl "PrimOp" "primop-commutable.hs-incl" + ++ hsIncl "TysPrim" "primop-vector-tys-exports.hs-incl" + ++ hsIncl "TysPrim" "primop-vector-tycons.hs-incl" + ++ hsIncl "TysPrim" "primop-vector-tys.hs-incl" + writeFileChanged file $ cDeps ++ hDeps ++ extraDeps From git at git.haskell.org Thu Oct 26 23:22:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add link rule. (7b1964e) Message-ID: <20171026232202.4FC473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b1964efccba7ca2072e41f0e782a4ccfd843244/ghc >--------------------------------------------------------------- commit 7b1964efccba7ca2072e41f0e782a4ccfd843244 Author: Andrey Mokhov Date: Tue Jan 13 04:57:33 2015 +0000 Add link rule. >--------------------------------------------------------------- 7b1964efccba7ca2072e41f0e782a4ccfd843244 doc/deepseq-build-progress.txt | 8 +++++++- src/Oracles/Builder.hs | 8 +++----- src/Package.hs | 3 ++- src/Package/Library.hs | 44 +++++++++++++++++++++++++----------------- 4 files changed, 38 insertions(+), 25 deletions(-) diff --git a/doc/deepseq-build-progress.txt b/doc/deepseq-build-progress.txt index f951d61..0df6c05 100644 --- a/doc/deepseq-build-progress.txt +++ b/doc/deepseq-build-progress.txt @@ -54,14 +54,20 @@ echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0 # Done: "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents /usr/bin/ar: creating libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents # Done: "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.p_o - +# Done: "C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" -r -o libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o libraries/deepseq/dist-install/build/Control/DeepSeq.o + +# Done: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents + +# Skipping: /usr/bin/find libraries/deepseq/dist-install/build/Control/DeepSeq_p_o_split -name '*.p_o' -print >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index ffc3cf5..71f8575 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,8 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, terseRun, specified, - arArgs + with, run, terseRun, specified ) where import Data.Char @@ -115,11 +114,13 @@ terseRun builder args = do interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of Ar -> prefixAndSuffix 3 1 ss + Ld -> prefixAndSuffix 4 0 ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss else prefixAndSuffix 0 4 ss GhcPkg _ -> prefixAndSuffix 2 0 ss GhcCabal -> prefixAndSuffix 3 0 ss + _ -> ss where prefixAndSuffix n m ss = if length ss <= n + m + 1 @@ -138,6 +139,3 @@ specified builder = do [_] -> True _ -> False --- TODO: generalise for other builders -arArgs :: Args -arArgs = arg "q" diff --git a/src/Package.hs b/src/Package.hs index a3fcf89..8b41809 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -23,7 +23,8 @@ packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" - , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" ] + , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" + , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 6660a2f..529d777 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -3,18 +3,8 @@ module Package.Library (buildPackageLibrary) where import Package.Base -{- "/usr/bin/ar" q -libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a - at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a -.contents --} - --- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) --- $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents --- AR_OPTS = $(SRC_AR_OPTS) $(WAY$(_way)_AR_OPTS) $(EXTRA_AR_OPTS) - -buildPackageLibrary :: Package -> TodoItem -> Rules () -buildPackageLibrary (Package name path _) (stage, dist, _) = +arRule :: Package -> TodoItem -> Rules () +arRule (Package _ path _) (stage, dist, _) = let buildDir = path dist "build" pkgData = path dist "package-data.mk" in @@ -25,10 +15,28 @@ buildPackageLibrary (Package name path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] - terseRun Ar $ arArgs <+> out <+> libObjs - when (way == vanilla) $ do - synopsis <- unwords <$> arg (Synopsis pkgData) - putNormal $ "Successfully built library for package " - ++ name ++ "." - putNormal $ "Synopsis: " ++ synopsis ++ "." + terseRun Ar $ "q" <+> out <+> libObjs +{- "C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" -r -o +libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o +libraries/deepseq/dist-install/build/Control/DeepSeq.o +-} + +ldRule :: Package -> TodoItem -> Rules () +ldRule (Package name path _) (stage, dist, _) = + let buildDir = path dist "build" + pkgData = path dist "package-data.mk" + in + priority 2 $ (buildDir "*.o") %> \out -> do + need ["shake/src/Package/Library.hs"] + depObjs <- pkgDepObjects path dist vanilla + need depObjs + terseRun Ld $ arg (ConfLdLinkerArgs stage) + <> arg ["-r", "-o", out] + <> arg depObjs + synopsis <- unwords <$> arg (Synopsis pkgData) + putNormal $ "Successfully built package " ++ name ++ "." + putNormal $ "Package synopsis: " ++ synopsis ++ "." + +buildPackageLibrary :: Package -> TodoItem -> Rules () +buildPackageLibrary = arRule <> ldRule \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:22:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement new generate rules. (90301e1) Message-ID: <20171026232202.922DA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90301e1bd2143ed9f04a1385024de60ff4a68009/ghc >--------------------------------------------------------------- commit 90301e1bd2143ed9f04a1385024de60ff4a68009 Author: Andrey Mokhov Date: Thu Sep 24 05:50:46 2015 +0100 Implement new generate rules. >--------------------------------------------------------------- 90301e1bd2143ed9f04a1385024de60ff4a68009 src/Rules/Generate.hs | 104 +++++++++++++++++++++++++++++--------------------- 1 file changed, 60 insertions(+), 44 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 90301e1bd2143ed9f04a1385024de60ff4a68009 From git at git.haskell.org Thu Oct 26 23:22:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (4863449) Message-ID: <20171026232205.BEF013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4863449633ec90de6607df0d80f4b2a8f40ecdc7/ghc >--------------------------------------------------------------- commit 4863449633ec90de6607df0d80f4b2a8f40ecdc7 Author: Andrey Mokhov Date: Tue Jan 13 05:12:38 2015 +0000 Clean up. >--------------------------------------------------------------- 4863449633ec90de6607df0d80f4b2a8f40ecdc7 doc/deepseq-build-progress.txt | 6 ++++++ src/Oracles.hs | 2 +- src/Oracles/Builder.hs | 2 +- src/Package/Base.hs | 6 +++--- src/Package/Compile.hs | 2 +- src/Package/Data.hs | 2 +- src/Package/Library.hs | 9 ++------- 7 files changed, 15 insertions(+), 14 deletions(-) diff --git a/doc/deepseq-build-progress.txt b/doc/deepseq-build-progress.txt index 0df6c05..84845fe 100644 --- a/doc/deepseq-build-progress.txt +++ b/doc/deepseq-build-progress.txt @@ -70,9 +70,15 @@ echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0 # Skipping: /usr/bin/find libraries/deepseq/dist-install/build/Control/DeepSeq_p_o_split -name '*.p_o' -print >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents + +# Done: "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents /usr/bin/ar: creating libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents + + "inplace/bin/mkdirhier" libraries/deepseq/dist-install/doc/html/deepseq//. "C:/msys/home/chEEtah/ghc/inplace/bin/haddock" --odir="libraries/deepseq/dist-install/doc/html/deepseq" --no-tmp-comp-dir --dump-interface=libraries/deepseq/dist-install/doc/html/deepseq/deepseq.haddock --html --hoogle --title="deepseq-1.4.0.0: Deep evaluation of data structures" --prologue="libraries/deepseq/dist-install/haddock-prologue.txt" --read-interface=../array-0.5.0.1,../array-0.5.0.1/src/%{MODULE/./-}.html\#%{NAME},libraries/array/dist-install/doc/html/array/array.haddock --read-interface=../base-4.8.0.0,../base-4.8.0.0/src/%{MODULE/./-}.html\#%{NAME},libraries/base/dist-install/doc/html/base/base.haddock --read-interface=../ghc-prim-0.3.1.0,../ghc-prim-0.3.1.0/src/%{MODULE/./-}.html\#%{NAME},libraries/ghc-prim/dist-install/doc/html/ghc-prim/ghc-prim.haddock --optghc=-hisuf --optghc=hi --optghc=-osuf --optghc=o --optghc=-hcsuf --optghc=hc --optghc=-static --optghc=-H32m --optghc=-O --optghc=-this-package-key --optghc=deeps_FT5iVCELxOr62eHY0nbvnU --optghc=-hide-all-package s --optghc=-i --optghc=-ilibraries/deepseq/. --optghc=-ilibraries/deepseq/dist-install/build --optghc=-ilibraries/deepseq/dist-install/build/autogen --optghc=-Ilibraries/deepseq/dist-install/build --optghc=-Ilibraries/deepseq/dist-install/build/autogen --optghc=-Ilibraries/deepseq/. --optghc=-optP-include --optghc=-optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h --optghc=-package-key --optghc=array_3w0nMK0JfaFJPpLFn2yWAJ --optghc=-package-key --optghc=base_469rOtLAqwTGFEOGWxSUiQ --optghc=-package-key --optghc=ghcpr_FgrV6cgh2JHBlbcx1OSlwt --optghc=-Wall --optghc=-XHaskell2010 --optghc=-O2 --optghc=-no-user-package-db --optghc=-rtsopts --optghc=-odir --optghc=libraries/deepseq/dist-install/build --optghc=-hidir --optghc=libraries/deepseq/dist-install/build --optghc=-stubdir --optghc=libraries/deepseq/dist-install/build --optghc=-split-objs libraries/deepseq/./Control/DeepSeq.hs +RTS -tlibraries/deepseq/dist-install/doc/html/deepseq/deepseq.haddock.t --machine-reada ble Haddock coverage: diff --git a/src/Oracles.hs b/src/Oracles.hs index 5b2ff11..2fe8430 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -49,7 +49,7 @@ packageDataOracle :: Rules () packageDataOracle = do pkgData <- newCache $ \file -> do need [file] - putNormal $ "Parsing " ++ file ++ "..." + putNormal $ "Parsing " ++ toStandard file ++ "..." liftIO $ readConfigFile file addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 71f8575..8a2c5b2 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -27,7 +27,7 @@ data Builder = Ar deriving Show instance ShowArgs Builder where - showArgs builder = showArgs $ fmap words $ do + showArgs builder = showArgs $ fmap (map toStandard . words) $ do let key = case builder of Ar -> "ar" Ld -> "ld" diff --git a/src/Package/Base.hs b/src/Package/Base.hs index a8de80d..9882900 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -49,7 +49,7 @@ libraryPackage :: String -> Stage -> (Stage -> Settings) -> Package libraryPackage name stage settings = Package name - ("libraries" name) + (toStandard $ "libraries" name) [( stage, if stage == Stage0 then "dist-boot" else "dist-install", @@ -123,7 +123,7 @@ pkgDepObjects path dist way = do buildDir = path dist "build" hs2obj = (buildDir ++) . drop (length path) . (-<.> osuf way) srcs <- pkgHsSources path dist - return $ map hs2obj srcs + return $ map (toStandard . hs2obj) srcs -- Find objects that go to library pkgLibObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] @@ -145,4 +145,4 @@ findModuleFiles pkgData directories suffixes = do modPath <- map (replaceEq '.' pathSeparator) mods suffix <- suffixes return $ dir modPath ++ suffix - return $ map normaliseEx files + return $ map (toStandard . normaliseEx) files diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 6badbb7..760c96f 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -53,4 +53,4 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) - <> arg ["-o", out] + <> arg ["-o", toStandard out] diff --git a/src/Package/Data.hs b/src/Package/Data.hs index a73a521..ef89ed0 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -79,7 +79,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = ghcPkgArgs = arg ["update", "--force"] <> (stage == Stage0) arg "--package-db=libraries/bootstrapping.conf" - <> arg (pathDist "inplace-pkg-config") + <> arg (toStandard $ pathDist "inplace-pkg-config") in (pathDist ) <$> [ "package-data.mk" diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 529d777..9f200e4 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -15,12 +15,7 @@ arRule (Package _ path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] - terseRun Ar $ "q" <+> out <+> libObjs - -{- "C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" -r -o -libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o -libraries/deepseq/dist-install/build/Control/DeepSeq.o --} + terseRun Ar $ "q" <+> toStandard out <+> libObjs ldRule :: Package -> TodoItem -> Rules () ldRule (Package name path _) (stage, dist, _) = @@ -32,7 +27,7 @@ ldRule (Package name path _) (stage, dist, _) = depObjs <- pkgDepObjects path dist vanilla need depObjs terseRun Ld $ arg (ConfLdLinkerArgs stage) - <> arg ["-r", "-o", out] + <> arg ["-r", "-o", toStandard out] <> arg depObjs synopsis <- unwords <$> arg (Synopsis pkgData) putNormal $ "Successfully built package " ++ name ++ "." From git at git.haskell.org Thu Oct 26 23:22:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new builder HsCpp. (45d41a5) Message-ID: <20171026232206.1A9E93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45d41a568b324f37d992fdcd616726959d4c439d/ghc >--------------------------------------------------------------- commit 45d41a568b324f37d992fdcd616726959d4c439d Author: Andrey Mokhov Date: Thu Sep 24 12:44:38 2015 +0100 Add new builder HsCpp. >--------------------------------------------------------------- 45d41a568b324f37d992fdcd616726959d4c439d cfg/system.config.in | 2 ++ src/Builder.hs | 2 ++ src/Rules/Actions.hs | 5 +++++ src/Settings/Args.hs | 2 ++ src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/HsCpp.hs | 17 +++++++++++++++++ src/Settings/Builders/Hsc2Hs.hs | 2 +- 7 files changed, 30 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 87d2b93..e85788b 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -23,6 +23,8 @@ hsc2hs = @hardtop@/inplace/bin/hsc2hs genprimopcode = @hardtop@/inplace/bin/genprimopcode +hs-cpp = @HaskellCPPCmd@ @HaskellCPPArgs@ + unlit = @hardtop@/inplace/lib/unlit ghc-split = @hardtop@/inplace/lib/ghc-split diff --git a/src/Builder.hs b/src/Builder.hs index a6521a1..e1c69be 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -30,6 +30,7 @@ data Builder = Alex | Haddock | Happy | HsColour + | HsCpp | Hsc2Hs | Ld | Unlit @@ -58,6 +59,7 @@ builderKey builder = case builder of Haddock -> "haddock" HsColour -> "hscolour" Hsc2Hs -> "hsc2hs" + HsCpp -> "hs-cpp" Ld -> "ld" Unlit -> "unlit" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 1e0472a..8214112 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -32,6 +32,11 @@ buildWithResources rs target = do forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> unit . cmd [path] $ persistentArgs ++ argsChunk + HsCpp -> do + let file = head $ Target.files target -- TODO: ugly + Stdout output <- cmd [path] argList + writeFileChanged file output + GenPrimopCode -> do let src = head $ Target.sources target -- TODO: ugly file = head $ Target.files target diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 349668a..231f5ed 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -11,6 +11,7 @@ import Settings.Builders.GhcPkg import Settings.Builders.Haddock import Settings.Builders.Happy import Settings.Builders.Hsc2Hs +import Settings.Builders.HsCpp import Settings.Builders.Ld import Settings.User @@ -41,4 +42,5 @@ defaultArgs = mconcat , haddockArgs , happyArgs , hsc2HsArgs + , hsCppArgs , ldArgs ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 54452d8..b68da27 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,6 +1,6 @@ module Settings.Builders.GhcCabal ( cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, - ccArgs, ccWarnings, argStagedSettingList + ccArgs, cppArgs, ccWarnings, argStagedSettingList ) where import Expression diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs new file mode 100644 index 0000000..da104cc --- /dev/null +++ b/src/Settings/Builders/HsCpp.hs @@ -0,0 +1,17 @@ +module Settings.Builders.HsCpp (hsCppArgs) where + +import Expression +import Predicates (builder) +import Settings.Builders.GhcCabal + +-- TODO: why process the result with grep -v '^#pragma GCC'? No such lines! +hsCppArgs :: Args +hsCppArgs = builder HsCpp ? do + stage <- getStage + src <- getSource + mconcat [ arg "-P" + , cppArgs + , arg $ "-Icompiler/stage" ++ show stage + , arg "-x" + , arg "c" + , arg src ] diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 7dfe286..dcf44fc 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -4,7 +4,7 @@ import Expression import Oracles import Predicates (builder, stage0, notStage0) import Settings -import Settings.Builders.GhcCabal +import Settings.Builders.GhcCabal hiding (cppArgs) hsc2HsArgs :: Args hsc2HsArgs = builder Hsc2Hs ? do From git at git.haskell.org Thu Oct 26 23:22:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add array package. (d4aabcd) Message-ID: <20171026232209.96BCE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4aabcd7e1e1d3de6302f0b8d436a5bcf4794f5b/ghc >--------------------------------------------------------------- commit d4aabcd7e1e1d3de6302f0b8d436a5bcf4794f5b Author: Andrey Mokhov Date: Tue Jan 13 06:31:37 2015 +0000 Add array package. >--------------------------------------------------------------- d4aabcd7e1e1d3de6302f0b8d436a5bcf4794f5b src/Package.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 8b41809..e29551f 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -10,7 +10,8 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] -packages = [libraryPackage "deepseq" Stage1 defaultSettings] +packages = [libraryPackage "array" Stage1 defaultSettings, + libraryPackage "deepseq" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -24,7 +25,10 @@ packageRules = do -- TODO: control targets from commang line arguments want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" - , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" ] + , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" + , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.a" + , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.p_a" + , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:22:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more thoughts. (14e4942) Message-ID: <20171026232209.EA9973A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14e49425f1760d8425ab518c0a49644e415c8173/ghc >--------------------------------------------------------------- commit 14e49425f1760d8425ab518c0a49644e415c8173 Author: Andrey Mokhov Date: Thu Sep 24 12:44:59 2015 +0100 Add more thoughts. >--------------------------------------------------------------- 14e49425f1760d8425ab518c0a49644e415c8173 doc/meeting-25-September-2015.txt | 19 +++++++++++++++++-- 1 file changed, 17 insertions(+), 2 deletions(-) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt index 6ee4297..caf0e8e 100644 --- a/doc/meeting-25-September-2015.txt +++ b/doc/meeting-25-September-2015.txt @@ -3,7 +3,20 @@ Shaking up GHC meeting, 25 September 2015 Things to discuss: ================================================ -1. Better names for build stages +1. Progress report + + +++ Dealing with seemingly dead-code artefacts of the old build systems. I used to carefully migrate all code to the new build system, but it is getting more in the way of readability. New proposal: drop all such suspicious instances and bring them back only if things break. Example: + +C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe -E -undef -traditional -P -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -Icompiler/stage2 -x c compiler/prelude/primops.txt.pp | grep -v '^#pragma GCC' > compiler/stage2/build/primops.txt + +But primops.txt.pp has no lines containing #pragma GCC! Dead code? + +++ Zero build is 7 seconds + +++ .hs-incl includes are currently not tracked properly (e.g. ghc -MM does not list them). See Dependencies.hs + +++ Better names for build stages * Currently we have Stage0, Stage1, etc. It is not particularly clear from the names what they stand for. We no longer need to stick to @@ -21,8 +34,10 @@ i. Unclear abstractions Builder/BuildRule... ii. Limits to build parallelism: GHC crashes during parallel builds. Also ghc-pkg and ghc-cabal are apparently not thread-safe, so I had to use Shake resources to limit the parallelism... +iii. Discuss the need for command line options, e.g. make GhcDebugged=YES. This is a bit annoying to implement since Settings.User seems fairly readable, but recompiling the build systems for changing a flag may be annoying too. + -2. Do we need a name for the new build system? +iv. Do we need a name for the new build system? * At least we need a name for the folder in the GHC tree From git at git.haskell.org Thu Oct 26 23:22:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add hiRule. (fae8451) Message-ID: <20171026232213.3D4C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fae8451a106cc2c298154d586201ce8924b9d701/ghc >--------------------------------------------------------------- commit fae8451a106cc2c298154d586201ce8924b9d701 Author: Andrey Mokhov Date: Tue Jan 13 06:32:36 2015 +0000 Add hiRule. >--------------------------------------------------------------- fae8451a106cc2c298154d586201ce8924b9d701 src/Package/Compile.hs | 17 +++++++++++++++-- 1 file changed, 15 insertions(+), 2 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 760c96f..80835f8 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -29,8 +29,8 @@ suffixArgs way = arg ["-hisuf", hisuf way] <> arg [ "-osuf", osuf way] <> arg ["-hcsuf", hcsuf way] -buildPackageCompile :: Package -> TodoItem -> Rules () -buildPackageCompile (Package name path _) (stage, dist, settings) = +oRule :: Package -> TodoItem -> Rules () +oRule (Package name path _) (stage, dist, settings) = let buildDir = path dist "build" pkgData = path dist "package-data.mk" depFile = buildDir name <.> "m" @@ -54,3 +54,16 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) <> arg ["-o", toStandard out] + +-- TODO: This rule looks a bit of a hack... combine it with the above? +hiRule :: Package -> TodoItem -> Rules () +hiRule (Package name path _) (stage, dist, settings) = + let buildDir = path dist "build" + in + (buildDir "*hi") %> \out -> do + let way = detectWay $ tail $ takeExtension out + oFile = out -<.> osuf way + need [oFile] + +buildPackageCompile :: Package -> TodoItem -> Rules () +buildPackageCompile = oRule <> hiRule From git at git.haskell.org Thu Oct 26 23:22:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ArSupportsAtFile, BuildPlatform, HostPlatform, TargetPlatform flags. (f164cdc) Message-ID: <20171026232213.948903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f164cdc5a83432f5f4c156be4a1d518650cb1045/ghc >--------------------------------------------------------------- commit f164cdc5a83432f5f4c156be4a1d518650cb1045 Author: Andrey Mokhov Date: Thu Sep 24 23:41:37 2015 +0100 Add ArSupportsAtFile, BuildPlatform, HostPlatform, TargetPlatform flags. >--------------------------------------------------------------- f164cdc5a83432f5f4c156be4a1d518650cb1045 cfg/system.config.in | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index e85788b..09ea1fa 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -23,7 +23,8 @@ hsc2hs = @hardtop@/inplace/bin/hsc2hs genprimopcode = @hardtop@/inplace/bin/genprimopcode -hs-cpp = @HaskellCPPCmd@ @HaskellCPPArgs@ +hs-cpp = @HaskellCPPCmd@ +hs-cpp-args = @HaskellCPPArgs@ unlit = @hardtop@/inplace/lib/unlit ghc-split = @hardtop@/inplace/lib/ghc-split @@ -37,8 +38,9 @@ hscolour = @HSCOLOUR@ # Information about builders: #============================ -gcc-is-clang = @GccIsClang@ -gcc-lt-46 = @GccLT46@ +gcc-is-clang = @GccIsClang@ +gcc-lt-46 = @GccLT46@ +ar-supports-at-file = @ArSupportsAtFile@ # Build options: #=============== @@ -50,15 +52,24 @@ ghc-unregisterised = @Unregisterised@ ghc-source-path = @hardtop@ leading-underscore = @LeadingUnderscore@ -# Information about host and target systems: -#=========================================== +# Information about build, host and target systems: +#================================================== -target-os = @TargetOS_CPP@ -target-arch = @TargetArch_CPP@ -target-platform-full = @TargetPlatformFull@ +build-platform = @BuildPlatform@ +build-arch = @BuildArch_CPP@ +build-os = @BuildOS_CPP@ +build-vendor = @BuildVendor_CPP@ -host-os = @HostOS_CPP@ +host-platform = @HostPlatform@ host-arch = @HostArch_CPP@ +host-os = @HostOS_CPP@ +host-vendor = @HostVendor_CPP@ + +target-platform = @TargetPlatform@ +target-platform-full = @TargetPlatformFull@ +target-arch = @TargetArch_CPP@ +target-os = @TargetOS_CPP@ +target-vendor = @TargetVendor_CPP@ cross-compiling = @CrossCompiling@ From git at git.haskell.org Thu Oct 26 23:22:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split Ar arguments into chunks of length 100 at most. (821776b) Message-ID: <20171026232216.BEC633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/821776b91341b4651f30f56ec08069a17c0d0a2b/ghc >--------------------------------------------------------------- commit 821776b91341b4651f30f56ec08069a17c0d0a2b Author: Andrey Mokhov Date: Tue Jan 13 06:33:44 2015 +0000 Split Ar arguments into chunks of length 100 at most. >--------------------------------------------------------------- 821776b91341b4651f30f56ec08069a17c0d0a2b src/Package/Library.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 9f200e4..ec2b845 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -2,6 +2,7 @@ module Package.Library (buildPackageLibrary) where import Package.Base +import Data.List.Split arRule :: Package -> TodoItem -> Rules () arRule (Package _ path _) (stage, dist, _) = @@ -15,7 +16,8 @@ arRule (Package _ path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] - terseRun Ar $ "q" <+> toStandard out <+> libObjs + forM_ (chunksOf 100 libObjs) $ \os -> do + terseRun Ar $ "q" <+> toStandard out <+> os ldRule :: Package -> TodoItem -> Rules () ldRule (Package name path _) (stage, dist, _) = From git at git.haskell.org Thu Oct 26 23:22:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ArSupportsAtFile flag. (093c1a9) Message-ID: <20171026232217.28DAF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/093c1a95e1e29df19985840d22138b798744da3c/ghc >--------------------------------------------------------------- commit 093c1a95e1e29df19985840d22138b798744da3c Author: Andrey Mokhov Date: Thu Sep 24 23:42:10 2015 +0100 Add ArSupportsAtFile flag. >--------------------------------------------------------------- 093c1a95e1e29df19985840d22138b798744da3c src/Oracles/Config/Flag.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 69d4884..f352ae3 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -8,7 +8,8 @@ import Base import Oracles.Config import Oracles.Config.Setting -data Flag = CrossCompiling +data Flag = ArSupportsAtFile + | CrossCompiling | GccIsClang | GccLt46 | GhcUnregisterised @@ -22,6 +23,7 @@ data Flag = CrossCompiling flag :: Flag -> Action Bool flag f = do key <- return $ case f of + ArSupportsAtFile -> "ar-supports-at-file" CrossCompiling -> "cross-compiling" GccIsClang -> "gcc-is-clang" GccLt46 -> "gcc-lt-46" From git at git.haskell.org Thu Oct 26 23:22:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add toStandard to varios places. (5d2cf2c) Message-ID: <20171026232220.34B1F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d2cf2c3163f37cb53d0217eae93582980e211de/ghc >--------------------------------------------------------------- commit 5d2cf2c3163f37cb53d0217eae93582980e211de Author: Andrey Mokhov Date: Tue Jan 13 06:34:24 2015 +0000 Add toStandard to varios places. >--------------------------------------------------------------- 5d2cf2c3163f37cb53d0217eae93582980e211de src/Package/Base.hs | 11 ++++++----- src/Package/Dependencies.hs | 8 ++++---- 2 files changed, 10 insertions(+), 9 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 9882900..f6c70ea 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -84,7 +84,8 @@ bootPkgConstraints = mempty -- sed "s/[^0-9.]//g")")) pathArgs :: ShowArgs a => String -> FilePath -> a -> Args -pathArgs key path as = map (\a -> key ++ normaliseEx (path a)) <$> arg as +pathArgs key path as = + map (\a -> key ++ toStandard (normaliseEx $ path a)) <$> arg as packageArgs :: Stage -> FilePath -> Args packageArgs stage pkgData = do @@ -100,14 +101,14 @@ packageArgs stage pkgData = do includeArgs :: FilePath -> FilePath -> Args includeArgs path dist = - let pkgData = path dist "package-data.mk" - buildDir = path dist "build" + let pkgData = toStandard $ path dist "package-data.mk" + buildDir = toStandard $ path dist "build" in arg "-i" <> pathArgs "-i" path (SrcDirs pkgData) - <> concatArgs ["-i", "-I"] [buildDir, buildDir "autogen"] + <> concatArgs ["-i", "-I"] [buildDir, toStandard $ buildDir "autogen"] <> pathArgs "-I" path (IncludeDirs pkgData) <> arg "-optP-include" -- TODO: Shall we also add -cpp? - <> concatArgs "-optP" (buildDir "autogen/cabal_macros.h") + <> concatArgs "-optP" (toStandard $ buildDir "autogen/cabal_macros.h") pkgHsSources :: FilePath -> FilePath -> Action [FilePath] pkgHsSources path dist = do diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 6339adb..63ed508 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -5,16 +5,16 @@ import Package.Base buildPackageDependencies :: Package -> TodoItem -> Rules () buildPackageDependencies (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" - pkgData = path dist "package-data.mk" + let buildDir = toStandard $ path dist "build" + pkgData = toStandard $ path dist "package-data.mk" in (buildDir name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData <> includeArgs path dist - <> productArgs ["-odir", "-stubdir"] buildDir - <> arg ["-dep-makefile", out <.> "new"] + <> productArgs ["-odir", "-stubdir", "-hidir"] buildDir + <> arg ["-dep-makefile", toStandard $ out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) <> arg (pkgHsSources path dist) -- TODO: Check that skipping all _HC_OPTS is safe. From git at git.haskell.org Thu Oct 26 23:22:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new setting keys. (2ed0b04) Message-ID: <20171026232220.9AAFB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ed0b0414b2cd247808ea3c5e94b27e0556bc9ab/ghc >--------------------------------------------------------------- commit 2ed0b0414b2cd247808ea3c5e94b27e0556bc9ab Author: Andrey Mokhov Date: Thu Sep 24 23:42:47 2015 +0100 Add new setting keys. >--------------------------------------------------------------- 2ed0b0414b2cd247808ea3c5e94b27e0556bc9ab src/Oracles/Config/Setting.hs | 21 ++++++++++++++++++++- 1 file changed, 20 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index e1dfefa..fa62f97 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -10,13 +10,18 @@ import Base import Oracles.Config import Stage +-- TODO: reduce the variety of similar flags (e.g. CPP and non-CPP versions). -- Each Setting comes from the system.config file, e.g. 'target-os = mingw32'. -- setting TargetOs looks up the config file and returns "mingw32". -- -- SettingList is used for multiple string values separated by spaces, such -- as 'gmp-include-dirs = a b'. -- settingList GmpIncludeDirs therefore returns a list of strings ["a", "b"]. -data Setting = DynamicExtension +data Setting = BuildArch + | BuildOs + | BuildPlatform + | BuildVendor + | DynamicExtension | GhcMajorVersion | GhcMinorVersion | GhcPatchLevel @@ -24,6 +29,8 @@ data Setting = DynamicExtension | GhcSourcePath | HostArch | HostOs + | HostPlatform + | HostVendor | ProjectGitCommitId | ProjectName | ProjectVersion @@ -33,7 +40,9 @@ data Setting = DynamicExtension | ProjectPatchLevel2 | TargetArch | TargetOs + | TargetPlatform | TargetPlatformFull + | TargetVendor data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -41,11 +50,16 @@ data SettingList = ConfCcArgs Stage | ConfLdLinkerArgs Stage | GmpIncludeDirs | GmpLibDirs + | HsCppArgs | IconvIncludeDirs | IconvLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of + BuildArch -> "build-arch" + BuildOs -> "build-os" + BuildPlatform -> "build-platform" + BuildVendor -> "build-vendor" DynamicExtension -> "dynamic-extension" GhcMajorVersion -> "ghc-major-version" GhcMinorVersion -> "ghc-minor-version" @@ -54,6 +68,8 @@ setting key = askConfig $ case key of GhcSourcePath -> "ghc-source-path" HostArch -> "host-arch" HostOs -> "host-os" + HostPlatform -> "host-platform" + HostVendor -> "host-vendor" ProjectGitCommitId -> "project-git-commit-id" ProjectName -> "project-name" ProjectVersion -> "project-version" @@ -63,7 +79,9 @@ setting key = askConfig $ case key of ProjectPatchLevel2 -> "project-patch-level2" TargetArch -> "target-arch" TargetOs -> "target-os" + TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" + TargetVendor -> "target-vendor" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -73,6 +91,7 @@ settingList key = fmap words $ askConfig $ case key of ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show stage GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" + HsCppArgs -> "hs-cpp-args" IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" From git at git.haskell.org Thu Oct 26 23:22:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a cool screenshot. (9f89177) Message-ID: <20171026232223.A9CD33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9f8917750b4d83c15934a2e9dfbf51edf76d406d/ghc >--------------------------------------------------------------- commit 9f8917750b4d83c15934a2e9dfbf51edf76d406d Author: Andrey Mokhov Date: Tue Jan 13 06:34:54 2015 +0000 Add a cool screenshot. >--------------------------------------------------------------- 9f8917750b4d83c15934a2e9dfbf51edf76d406d doc/boom.png | Bin 0 -> 91102 bytes 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/doc/boom.png b/doc/boom.png new file mode 100644 index 0000000..834e1bb Binary files /dev/null and b/doc/boom.png differ From git at git.haskell.org Thu Oct 26 23:22:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new mode for Ar builder: useAtFile (big performance increase). (6cde985) Message-ID: <20171026232224.230413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6cde9851e61a88b0773e07346752279129c87d41/ghc >--------------------------------------------------------------- commit 6cde9851e61a88b0773e07346752279129c87d41 Author: Andrey Mokhov Date: Thu Sep 24 23:44:34 2015 +0100 Add new mode for Ar builder: useAtFile (big performance increase). >--------------------------------------------------------------- 6cde9851e61a88b0773e07346752279129c87d41 src/Rules/Actions.hs | 23 ++++++++--------------- src/Settings/Builders/Ar.hs | 31 ++++++++++++++++++++++++++++--- 2 files changed, 36 insertions(+), 18 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 8214112..5f15f3d 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,7 +1,6 @@ module Rules.Actions (build, buildWithResources) where import Expression -import Oracles import Oracles.ArgsHash import Settings import Settings.Args @@ -18,19 +17,13 @@ buildWithResources rs target = do path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed - when trackBuildSystem $ checkArgsHash target + checkArgsHash target withResources rs $ do - putBuild $ "/--------\n" ++ "| Running " - ++ show builder ++ " with arguments:" + putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList putBuild $ "\\--------" quietly $ case builder of - Ar -> do -- Split argument list into chunks as otherwise Ar chokes up - maxChunk <- cmdLineLengthLimit - let persistentArgs = take arPersistentArgsCount argList - remainingArgs = drop arPersistentArgsCount argList - forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> - unit . cmd [path] $ persistentArgs ++ argsChunk + Ar -> arCmd path argList HsCpp -> do let file = head $ Target.files target -- TODO: ugly @@ -63,14 +56,14 @@ interestingInfo builder ss = case builder of Haddock -> prefixAndSuffix 1 0 ss Happy -> prefixAndSuffix 0 3 ss Hsc2Hs -> prefixAndSuffix 0 3 ss + HsCpp -> prefixAndSuffix 0 1 ss Ld -> prefixAndSuffix 4 0 ss _ -> ss where prefixAndSuffix n m list = - if length list <= n + m + 1 + let len = length list in + if len <= n + m + 1 then list else take n list - ++ ["... skipping " - ++ show (length list - n - m) - ++ " arguments ..."] - ++ drop (length list - m) list + ++ ["... skipping " ++ show (len - n - m) ++ " arguments ..."] + ++ drop (len - m) list diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 082cbaf..7b6eb59 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,6 +1,7 @@ -module Settings.Builders.Ar (arArgs, arPersistentArgsCount) where +module Settings.Builders.Ar (arArgs, arCmd) where import Expression +import Oracles import Predicates (builder) arArgs :: Args @@ -13,5 +14,29 @@ arArgs = builder Ar ? do -- This count includes arg "q" and arg file parameters in arArgs (see above). -- Update this value appropriately when changing arArgs. -arPersistentArgsCount :: Int -arPersistentArgsCount = 2 +arFlagsCount :: Int +arFlagsCount = 2 + +-- Ar needs to be invoked in a special way: we pass the list of files to be +-- archived via a temporary file as otherwise Ar (or rather Windows command +-- line) chokes up. Alternatively, we split argument list into chunks and call +-- ar multiple times (when passing files via a separate file is not supported). +arCmd :: FilePath -> [String] -> Action () +arCmd path argList = do + arSupportsAtFile <- flag ArSupportsAtFile + let flagArgs = take arFlagsCount argList + fileArgs = drop arFlagsCount argList + if arSupportsAtFile + then useAtFile path flagArgs fileArgs + else useSuccessiveInvokations path flagArgs fileArgs + +useAtFile :: FilePath -> [String] -> [String] -> Action () +useAtFile path flagArgs fileArgs = withTempFile $ \tmp -> do + writeFile' tmp $ unwords fileArgs + cmd [path] flagArgs ('@' : tmp) + +useSuccessiveInvokations :: FilePath -> [String] -> [String] -> Action () +useSuccessiveInvokations path flagArgs fileArgs = do + maxChunk <- cmdLineLengthLimit + forM_ (chunksOfSize maxChunk fileArgs) $ \argsChunk -> + unit . cmd [path] $ flagArgs ++ argsChunk From git at git.haskell.org Thu Oct 26 23:22:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove a (useless?) output from the buildPackageData rule. (90c4840) Message-ID: <20171026232227.6C1553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90c48400bd72d55c030707b62eb3b4eb42eac6b1/ghc >--------------------------------------------------------------- commit 90c48400bd72d55c030707b62eb3b4eb42eac6b1 Author: Andrey Mokhov Date: Tue Jan 13 06:42:45 2015 +0000 Remove a (useless?) output from the buildPackageData rule. >--------------------------------------------------------------- 90c48400bd72d55c030707b62eb3b4eb42eac6b1 src/Package/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index ef89ed0..d3b13a5 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -88,7 +88,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = , "setup-config" , "build" "autogen" "cabal_macros.h" -- TODO: Is this needed? Also check out Paths_cpsa.hs. - , "build" "autogen" ("Paths_" ++ name) <.> "hs" + -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do need ["shake/src/Package/Data.hs"] need [path name <.> "cabal"] From git at git.haskell.org Thu Oct 26 23:22:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix HsCpp argument list. (555265c) Message-ID: <20171026232227.D76723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/555265ce0686be733a2a3f66abbab1bc8771d237/ghc >--------------------------------------------------------------- commit 555265ce0686be733a2a3f66abbab1bc8771d237 Author: Andrey Mokhov Date: Thu Sep 24 23:45:01 2015 +0100 Fix HsCpp argument list. >--------------------------------------------------------------- 555265ce0686be733a2a3f66abbab1bc8771d237 src/Settings/Builders/HsCpp.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs index da104cc..cad2897 100644 --- a/src/Settings/Builders/HsCpp.hs +++ b/src/Settings/Builders/HsCpp.hs @@ -1,6 +1,7 @@ module Settings.Builders.HsCpp (hsCppArgs) where import Expression +import Oracles import Predicates (builder) import Settings.Builders.GhcCabal @@ -9,9 +10,11 @@ hsCppArgs :: Args hsCppArgs = builder HsCpp ? do stage <- getStage src <- getSource - mconcat [ arg "-P" + args <- getSettingList HsCppArgs + mconcat [ append args + , arg "-P" , cppArgs - , arg $ "-Icompiler/stage" ++ show stage + , arg $ "-Icompiler/stage" ++ show (succ stage) , arg "-x" , arg "c" , arg src ] From git at git.haskell.org Thu Oct 26 23:22:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add bin-package-db package. (cd02d00) Message-ID: <20171026232231.48BF93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cd02d00639738e151e77288de9d116e286cb83c1/ghc >--------------------------------------------------------------- commit cd02d00639738e151e77288de9d116e286cb83c1 Author: Andrey Mokhov Date: Tue Jan 13 06:43:02 2015 +0000 Add bin-package-db package. >--------------------------------------------------------------- cd02d00639738e151e77288de9d116e286cb83c1 src/Package.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index e29551f..d2fd4db 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -10,8 +10,9 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] -packages = [libraryPackage "array" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings] +packages = [libraryPackage "array" Stage1 defaultSettings, + libraryPackage "deepseq" Stage1 defaultSettings, + libraryPackage "bin-package-db" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -28,7 +29,10 @@ packageRules = do , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.a" , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.p_a" - , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" ] + , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" + , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.a" + , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.p_a" + , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:22:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve Generate rule: clean up code, more accurate dependencies. (9253049) Message-ID: <20171026232231.B329D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/925304968b4da8050e618b004cfdccfe0cb895e6/ghc >--------------------------------------------------------------- commit 925304968b4da8050e618b004cfdccfe0cb895e6 Author: Andrey Mokhov Date: Thu Sep 24 23:46:24 2015 +0100 Improve Generate rule: clean up code, more accurate dependencies. >--------------------------------------------------------------- 925304968b4da8050e618b004cfdccfe0cb895e6 src/Rules/Dependencies.hs | 3 + src/Rules/Generate.hs | 217 ++++++++++++++++++++++++++++++---------------- 2 files changed, 146 insertions(+), 74 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 925304968b4da8050e618b004cfdccfe0cb895e6 From git at git.haskell.org Thu Oct 26 23:22:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CppOpts. (316ff4c) Message-ID: <20171026232234.D9F453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/316ff4cb2e421831281e42b09fb90ba5dae2b239/ghc >--------------------------------------------------------------- commit 316ff4cb2e421831281e42b09fb90ba5dae2b239 Author: Andrey Mokhov Date: Tue Jan 13 07:28:48 2015 +0000 Add CppOpts. >--------------------------------------------------------------- 316ff4cb2e421831281e42b09fb90ba5dae2b239 src/Oracles/PackageData.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 66a3f55..bf94713 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -19,6 +19,7 @@ data PackageData = Modules FilePath | Deps FilePath | DepKeys FilePath | Synopsis FilePath + | CppOpts FilePath instance ShowArgs PackageData where showArgs packageData = do @@ -30,6 +31,7 @@ instance ShowArgs PackageData where Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) Synopsis file -> ("SYNOPSIS" , file, "" ) + CppOpts file -> ("CPP_OPTS" , file, "" ) fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key res <- askOracle $ PackageDataKey (file, fullKey) return $ words $ case res of From git at git.haskell.org Thu Oct 26 23:22:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghc-bin package. (6a0c30f) Message-ID: <20171026232235.3F2753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a0c30ff7dad21754967ab9178e7ad3b88c1598d/ghc >--------------------------------------------------------------- commit 6a0c30ff7dad21754967ab9178e7ad3b88c1598d Author: Andrey Mokhov Date: Thu Sep 24 23:47:18 2015 +0100 Add ghc-bin package. >--------------------------------------------------------------- 6a0c30ff7dad21754967ab9178e7ad3b88c1598d src/GHC.hs | 18 ++++++++++-------- src/Settings/Builders/GhcCabal.hs | 6 ++++++ src/Settings/Packages.hs | 6 +++--- src/Settings/User.hs | 2 +- 4 files changed, 20 insertions(+), 12 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 8f25c7c..c277c6a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,8 +1,8 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, - integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, - terminfo, time, transformers, unix, win32, xhtml, + deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + integerGmp, integerSimple, parallel, pretty, primitive, process, stm, + templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory ) where @@ -18,15 +18,15 @@ import Stage defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc - , integerGmp, integerSimple, parallel, pretty, primitive, process, stm + , containers, deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl + , hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm , templateHaskell, terminfo, time, transformers, unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, - integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, - terminfo, time, transformers, unix, win32, xhtml :: Package + deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + integerGmp, integerSimple, parallel, pretty, primitive, process, stm, + templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -39,6 +39,7 @@ containers = library "containers" deepseq = library "deepseq" directory = library "directory" filepath = library "filepath" +ghc = topLevel "ghc-bin" `setPath` "ghc" ghcPrim = library "ghc-prim" haskeline = library "haskeline" hoopl = library "hoopl" @@ -67,5 +68,6 @@ xhtml = library "xhtml" defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage package | package == compiler = "stage" ++ show (fromEnum stage + 1) + | package == ghc = "stage" ++ show (fromEnum stage + 1) | stage == Stage0 = "dist-boot" | otherwise = "dist-install" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index b68da27..582a56c 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -166,6 +166,12 @@ customPackageArgs = do , ghcProfiled ? notStage0 ? arg "--ghc-pkg-option=--force" ] + , package ghc ? + builder GhcCabal ? + mconcat [ arg $ "--flags=stage" ++ show nextStage + , ghcWithInterpreter ? + notStage0 ? arg "--flags=ghci" + ] ] withBuilderKey :: Builder -> String diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index dee0c95..8b913f5 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -16,7 +16,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, hoopl, hpc, transformers ] + [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? @@ -24,8 +24,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory - , filepath, ghcPrim, haskeline, integerLibrary, pretty, process - , templateHaskell, time ] + , filepath, ghc, ghcPrim, haskeline, integerLibrary, pretty + , process, templateHaskell, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 5b62e39..9a71ac2 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -15,7 +15,7 @@ userArgs = mempty -- Control which packages get to be built userPackages :: Packages -userPackages = mempty +userPackages = remove [ghc] -- Add new user-defined packages userKnownPackages :: [Package] From git at git.haskell.org Thu Oct 26 23:22:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add binary package. (02297c2) Message-ID: <20171026232238.B9E7A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02297c23579d7a11d9d99efacda7a328801cbfaa/ghc >--------------------------------------------------------------- commit 02297c23579d7a11d9d99efacda7a328801cbfaa Author: Andrey Mokhov Date: Tue Jan 13 07:29:15 2015 +0000 Add binary package. >--------------------------------------------------------------- 02297c23579d7a11d9d99efacda7a328801cbfaa src/Package.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index d2fd4db..899e48a 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -12,7 +12,8 @@ import Package.Dependencies packages :: [Package] packages = [libraryPackage "array" Stage1 defaultSettings, libraryPackage "deepseq" Stage1 defaultSettings, - libraryPackage "bin-package-db" Stage1 defaultSettings] + libraryPackage "bin-package-db" Stage1 defaultSettings, + libraryPackage "binary" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -32,7 +33,10 @@ packageRules = do , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.a" , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.p_a" - , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" ] + , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" + , "libraries/binary/dist-install/build/HSbinar_8WpSY1EWq5j1AwY619xVVw.o" + , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.a" + , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.p_a" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:22:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Put when trackBuildSystem conditional more precisely. (9f99e24) Message-ID: <20171026232239.0CD1F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9f99e240df6f3c5ad8597e2dafd9a73220dd87d3/ghc >--------------------------------------------------------------- commit 9f99e240df6f3c5ad8597e2dafd9a73220dd87d3 Author: Andrey Mokhov Date: Thu Sep 24 23:48:02 2015 +0100 Put when trackBuildSystem conditional more precisely. >--------------------------------------------------------------- 9f99e240df6f3c5ad8597e2dafd9a73220dd87d3 src/Oracles/ArgsHash.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index bc29031..402923b 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -20,12 +20,12 @@ newtype ArgsHashKey = ArgsHashKey Target -- to argument lists where appropriate. -- TODO: enforce the above assumption via type trickery? checkArgsHash :: Target -> Action () -checkArgsHash target = do +checkArgsHash target = when trackBuildSystem $ do _ <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int return () -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () -argsHashOracle = when trackBuildSystem $ do +argsHashOracle = do _ <- addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs return () From git at git.haskell.org Thu Oct 26 23:22:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing options and pkgDepObjects. (92352f7) Message-ID: <20171026232242.503013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92352f7763115e6a78452b48d9872681a4dca3eb/ghc >--------------------------------------------------------------- commit 92352f7763115e6a78452b48d9872681a4dca3eb Author: Andrey Mokhov Date: Tue Jan 13 07:29:56 2015 +0000 Fix missing options and pkgDepObjects. >--------------------------------------------------------------- 92352f7763115e6a78452b48d9872681a4dca3eb src/Package/Base.hs | 7 ++++--- src/Package/Compile.hs | 3 ++- src/Package/Dependencies.hs | 1 + 3 files changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index f6c70ea..bac6801 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -122,9 +122,10 @@ pkgDepObjects :: FilePath -> FilePath -> Way -> Action [FilePath] pkgDepObjects path dist way = do let pkgData = path dist "package-data.mk" buildDir = path dist "build" - hs2obj = (buildDir ++) . drop (length path) . (-<.> osuf way) - srcs <- pkgHsSources path dist - return $ map (toStandard . hs2obj) srcs + dirs <- map (normaliseEx . (path )) <$> arg (SrcDirs pkgData) + fmap concat $ forM dirs $ \d -> + map (toStandard . (buildDir ++) . (-<.> osuf way) . drop (length d)) + <$> (findModuleFiles pkgData [d] [".hs", ".lhs"]) -- Find objects that go to library pkgLibObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 80835f8..c42d592 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -48,6 +48,7 @@ oRule (Package name path _) (stage, dist, settings) = <> arg SrcHcOpts <> packageArgs stage pkgData <> includeArgs path dist + <> concatArgs ["-optP"] (CppOpts pkgData) -- TODO: now we have both -O and -O2 <> arg ["-Wall", "-XHaskell2010", "-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir @@ -55,7 +56,7 @@ oRule (Package name path _) (stage, dist, settings) = <> arg ("-c":srcs) <> arg ["-o", toStandard out] --- TODO: This rule looks a bit of a hack... combine it with the above? +-- TODO: This rule looks hacky... combine it with the above? hiRule :: Package -> TodoItem -> Rules () hiRule (Package name path _) (stage, dist, settings) = let buildDir = path dist "build" diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 63ed508..fc9f4af 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -13,6 +13,7 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData <> includeArgs path dist + <> concatArgs ["-optP"] (CppOpts pkgData) <> productArgs ["-odir", "-stubdir", "-hidir"] buildDir <> arg ["-dep-makefile", toStandard $ out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) From git at git.haskell.org Thu Oct 26 23:22:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, add comments. (55fd868) Message-ID: <20171026232242.9D9EB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/55fd868e521ea500e3b5e8a6f55890e632e07174/ghc >--------------------------------------------------------------- commit 55fd868e521ea500e3b5e8a6f55890e632e07174 Author: Andrey Mokhov Date: Fri Sep 25 02:52:16 2015 +0100 Clean up, add comments. >--------------------------------------------------------------- 55fd868e521ea500e3b5e8a6f55890e632e07174 src/Builder.hs | 1 + src/Oracles/ArgsHash.hs | 1 + src/Rules/Cabal.hs | 6 ++++-- 3 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index e1c69be..c0ffee0 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -16,6 +16,7 @@ import Stage -- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) -- TODO: add Cpp builders -- TODO: rename Gcc to Cc? +-- TODO: do we really need staged builders? data Builder = Alex | Ar | Gcc Stage diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 402923b..ab4993b 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -19,6 +19,7 @@ newtype ArgsHashKey = ArgsHashKey Target -- constructors are assumed not to examine target sources, but only append them -- to argument lists where appropriate. -- TODO: enforce the above assumption via type trickery? +-- TODO: Hash Target to improve accuracy and performance. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do _ <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index aac8ab2..7ccb1b8 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -2,7 +2,7 @@ module Rules.Cabal (cabalRules) where import Expression import Data.Version -import Distribution.Package +import Distribution.Package hiding (Package) import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Verbosity @@ -29,7 +29,9 @@ cabalRules = do pkgDeps <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - let deps = collectDeps . condLibrary $ pd + let depsLib = collectDeps $ condLibrary pd + depsExes = map (collectDeps . Just . snd) $ condExecutables pd + deps = concat $ depsLib : depsExes depNames = [ name | Dependency (PackageName name) _ <- deps ] return . unwords $ Package.pkgName pkg : sort depNames writeFileChanged out . unlines $ pkgDeps From git at git.haskell.org Thu Oct 26 23:22:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix dropDynamic. (d1ade7d) Message-ID: <20171026232246.187C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1ade7d5917eeea88c2034dc52bb8bf100bfc05a/ghc >--------------------------------------------------------------- commit d1ade7d5917eeea88c2034dc52bb8bf100bfc05a Author: Andrey Mokhov Date: Tue Jan 13 13:01:30 2015 +0000 Fix dropDynamic. >--------------------------------------------------------------- d1ade7d5917eeea88c2034dc52bb8bf100bfc05a src/Ways.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index b478a04..24c1a80 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -14,7 +14,7 @@ module Ways ( wayHcArgs, wayPrefix, - hisuf, osuf, hcsuf, + hisuf, osuf, hcsuf, obootsuf, ssuf, libsuf, detectWay ) where @@ -125,7 +125,7 @@ dropDynamic way | way == debugDynamic = debug | way == loggingDynamic = logging | way == threadedLoggingDynamic = threadedLogging - | otherwise = error $ "Cannot drop Dynamic from way " ++ tag way ++ "." + | otherwise = way -- Detect way from a given extension. Fail if the result is not unique. -- TODO: This may be slow -- optimise if overhead is significant. From git at git.haskell.org Thu Oct 26 23:22:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finalise meeting agenda. (07dbd29) Message-ID: <20171026232246.6757B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/07dbd2918f9099fb98986f9cc91b51b52a94d5f8/ghc >--------------------------------------------------------------- commit 07dbd2918f9099fb98986f9cc91b51b52a94d5f8 Author: Andrey Mokhov Date: Fri Sep 25 02:52:32 2015 +0100 Finalise meeting agenda. >--------------------------------------------------------------- 07dbd2918f9099fb98986f9cc91b51b52a94d5f8 doc/meeting-25-September-2015.txt | 67 ++++++++++++++++++++++++++++----------- 1 file changed, 49 insertions(+), 18 deletions(-) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt index caf0e8e..dde2e45 100644 --- a/doc/meeting-25-September-2015.txt +++ b/doc/meeting-25-September-2015.txt @@ -4,42 +4,74 @@ Things to discuss: ================================================ 1. Progress report +------------------ +Done: +* Build all libraries and compiler +* Generate code (alex, happy, hsc2hs, genprimopcode, Config.hs, ghc_boot_platform.h) +* Track changes in the build system +* Extract accurate package dependencies from .cabal files +* Improve complexity when searching for module files (40x) -++ Dealing with seemingly dead-code artefacts of the old build systems. I used to carefully migrate all code to the new build system, but it is getting more in the way of readability. New proposal: drop all such suspicious instances and bring them back only if things break. Example: +Todo: Target: +* Build utils, rts October +* Better dependencies (.hs-incl etc.) November +* Support command line options December +* Validate November-December (GHC 8.0?) +* Documentation December-January + +Notes: +* Zero build: under 7 seconds +* Full build (when compilation not required): under 12 minutes on 4 cores +* Limited parallelism: ghc-cabal/ghc-pkg not thread-safe, ghc fails on > 4 cores +* Codebase growing: 50 files + + +2. Seemingly dead-code +---------------------- + +I used to carefully migrate all code to the new build system even when it seemed dead, but this is often getting in the way of readability. New proposal: drop all such suspicious instances and bring them back only if/when things break. + +Example (generating primops.txt): C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe -E -undef -traditional -P -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -Icompiler/stage2 -x c compiler/prelude/primops.txt.pp | grep -v '^#pragma GCC' > compiler/stage2/build/primops.txt -But primops.txt.pp has no lines containing #pragma GCC! Dead code? +But primops.txt.pp has no lines containing #pragma GCC. Dead code? -++ Zero build is 7 seconds +Another example (generating ghc_boot_platform.h): -++ .hs-incl includes are currently not tracked properly (e.g. ghc -MM does not list them). See Dependencies.hs +ifeq "$(TargetOS_CPP)" "irix" + @echo "#ifndef $(IRIX_MAJOR)_TARGET_OS" >> $@ + @echo "#define $(IRIX_MAJOR)_TARGET_OS 1" >> $@ + @echo "#endif" >> $@ +endif -++ Better names for build stages +But IRIX_MAJOR is never set anywhere in the build system. Dead code? -* Currently we have Stage0, Stage1, etc. It is not particularly clear -from the names what they stand for. We no longer need to stick to -numbers and can pick more helpful names, for example: -Stage0 -> Boot -Stage1 -> Interim -Stage2 -> Install -Stage3 -> Selftest +3. Command line options +----------------------- +Discuss the need for command line options, e.g. 'make GhcDebugged=YES'. Do we need to support all options as in the old build system? +Settings.User is fairly readable, so perhaps some options may be changeable only by editing this file and recompiling the build system (typically takes negligible time compared to building). This will simplify things. Can we come up with a must-have list for command line options? -i. Unclear abstractions Builder/BuildRule... +4. Better names for build stages +-------------------------------- -ii. Limits to build parallelism: GHC crashes during parallel builds. Also ghc-pkg and ghc-cabal are apparently not thread-safe, so I had to use Shake resources to limit the parallelism... +Currently we have Stage0, Stage1, etc. It is not particularly clear from the names what they stand for (as a newcomer to the build system I used to look up what these numbers stand for all the time). Shall we use this opportunity to pick more helpful names, for example: -iii. Discuss the need for command line options, e.g. make GhcDebugged=YES. This is a bit annoying to implement since Settings.User seems fairly readable, but recompiling the build systems for changing a flag may be annoying too. +Stage0 -> Boot +Stage1 -> Interim +Stage2 -> Install +Stage3 -> Selftest -iv. Do we need a name for the new build system? +5. Do we need a name for the new build system? +---------------------------------------------- -* At least we need a name for the folder in the GHC tree +* At least we need a name for the folder in the GHC tree. * If we call it 'shake' there may be a confusion with the Shake library. @@ -47,4 +79,3 @@ iv. Do we need a name for the new build system? build system' is overly verbose. Calling it 'shake' is confusing. * I haven't thought about any names yet, just checking whether we want to. - From git at git.haskell.org Thu Oct 26 23:22:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add toStandard. (fd28d9a) Message-ID: <20171026232250.046F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd28d9aa2dc7a212d20685e5541c1e059288c799/ghc >--------------------------------------------------------------- commit fd28d9aa2dc7a212d20685e5541c1e059288c799 Author: Andrey Mokhov Date: Tue Jan 13 13:02:06 2015 +0000 Add toStandard. >--------------------------------------------------------------- fd28d9aa2dc7a212d20685e5541c1e059288c799 src/Package/Compile.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index c42d592..56d168a 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -31,8 +31,8 @@ suffixArgs way = arg ["-hisuf", hisuf way] oRule :: Package -> TodoItem -> Rules () oRule (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" - pkgData = path dist "package-data.mk" + let buildDir = toStandard $ path dist "build" + pkgData = toStandard $ path dist "package-data.mk" depFile = buildDir name <.> "m" in (buildDir "*o") %> \out -> do @@ -59,7 +59,7 @@ oRule (Package name path _) (stage, dist, settings) = -- TODO: This rule looks hacky... combine it with the above? hiRule :: Package -> TodoItem -> Rules () hiRule (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" + let buildDir = toStandard $ path dist "build" in (buildDir "*hi") %> \out -> do let way = detectWay $ tail $ takeExtension out From git at git.haskell.org Thu Oct 26 23:22:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for non-library packages. (c488f65) Message-ID: <20171026232250.5EA713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c488f65dd9a894af75e633c5bd78220d7b60cc84/ghc >--------------------------------------------------------------- commit c488f65dd9a894af75e633c5bd78220d7b60cc84 Author: Andrey Mokhov Date: Fri Sep 25 02:53:37 2015 +0100 Add support for non-library packages. >--------------------------------------------------------------- c488f65dd9a894af75e633c5bd78220d7b60cc84 src/GHC.hs | 21 +++++++++++++++------ src/Rules.hs | 7 ++++++- src/Rules/Data.hs | 4 ++-- src/Settings.hs | 8 +++++++- src/Settings/Packages.hs | 8 ++++---- src/Settings/TargetDirectory.hs | 2 ++ src/Settings/User.hs | 10 +++++++--- 7 files changed, 43 insertions(+), 17 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index c277c6a..668cf48 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,9 +4,10 @@ module GHC ( integerGmp, integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, - defaultKnownPackages, defaultTargetDirectory + defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where +import Base import Package import Stage @@ -66,8 +67,16 @@ xhtml = library "xhtml" -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal -- TODO: simplify to just 'show stage'? defaultTargetDirectory :: Stage -> Package -> FilePath -defaultTargetDirectory stage package - | package == compiler = "stage" ++ show (fromEnum stage + 1) - | package == ghc = "stage" ++ show (fromEnum stage + 1) - | stage == Stage0 = "dist-boot" - | otherwise = "dist-install" +defaultTargetDirectory stage pkg + | pkg == compiler = "stage" ++ show (fromEnum stage + 1) + | pkg == ghc = "stage" ++ show (fromEnum stage + 1) + | stage == Stage0 = "dist-boot" + | otherwise = "dist-install" + +defaultProgramPath :: Stage -> Package -> Maybe FilePath +defaultProgramPath stage pkg + | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) + | otherwise = Nothing + where + program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg + -/- "build/tmp" -/- name <.> exe diff --git a/src/Rules.hs b/src/Rules.hs index 26e57bd..e615c64 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -11,7 +11,8 @@ generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpretWithStage stage getPackages - fmap concat . forM pkgs $ \pkg -> do + let (libPkgs, programPkgs) = partition isLibrary pkgs + libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg buildPath = targetPath stage pkg -/- "build" libName <- interpretPartial target $ getPkgData LibName @@ -28,6 +29,10 @@ generateTargets = action $ do ++ [ haddock | needHaddock && stage == Stage1 ] ++ libs + let programTargets = map (fromJust . programPath stage) programPkgs + + return $ libTargets ++ programTargets + need $ reverse targets -- TODO: add Stage2 (compiler only?) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 3622918..1085f8f 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -17,7 +17,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fmap (path -/-) [ "package-data.mk" , "haddock-prologue.txt" - , "inplace-pkg-config" , "setup-config" , "build" -/- "autogen" -/- "cabal_macros.h" -- TODO: Is this needed? Also check out Paths_cpsa.hs. @@ -39,7 +38,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fullTarget target GhcCabal [cabalFile] outs -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg - whenM (interpretPartial target registerPackage) . + when (isLibrary pkg) . + whenM (interpretPartial target registerPackage) . buildWithResources [(ghcPkg rs, 1)] $ fullTarget target (GhcPkg stage) [cabalFile] outs diff --git a/src/Settings.hs b/src/Settings.hs index dab73ed..d16c5cd 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -3,7 +3,7 @@ module Settings ( module Settings.TargetDirectory, module Settings.User, module Settings.Ways, - getPkgData, getPkgDataList, + getPkgData, getPkgDataList, programPath, isLibrary, getPackagePath, getTargetDirectory, getTargetPath, getPackageSources, ) where @@ -29,6 +29,12 @@ getPkgData key = lift . pkgData . key =<< getTargetPath getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getTargetPath +programPath :: Stage -> Package -> Maybe FilePath +programPath = userProgramPath + +isLibrary :: Package -> Bool +isLibrary pkg = programPath Stage0 pkg == Nothing + -- Find all Haskell source files for the current target. TODO: simplify. getPackageSources :: Expr [FilePath] getPackageSources = do diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 8b913f5..1fe70dc 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -16,16 +16,16 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc, transformers ] + [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc + , templateHaskell, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 - , append [ array, base, bytestring, containers, deepseq, directory - , filepath, ghc, ghcPrim, haskeline, integerLibrary, pretty - , process, templateHaskell, time ] + , append [ array, base, bytestring, containers, deepseq, directory, filepath + , ghcPrim, haskeline, integerLibrary, pretty, process, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 58f2d51..b84d03d 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -5,6 +5,8 @@ module Settings.TargetDirectory ( import Expression import Settings.User +-- TODO: move to Settings.hs? + -- User can override the default target directory settings given below targetDirectory :: Stage -> Package -> FilePath targetDirectory = userTargetDirectory diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 9a71ac2..d841028 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,6 +1,6 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, - userKnownPackages, integerLibrary, + userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies ) where @@ -15,7 +15,7 @@ userArgs = mempty -- Control which packages get to be built userPackages :: Packages -userPackages = remove [ghc] +userPackages = mempty -- Add new user-defined packages userKnownPackages :: [Package] @@ -28,10 +28,14 @@ userLibWays = mempty userRtsWays :: Ways userRtsWays = mempty --- Control where build results go (see Settings.Default for an example) +-- Control where build results go (see GHC.hs for defaults) userTargetDirectory :: Stage -> Package -> FilePath userTargetDirectory = defaultTargetDirectory +-- Control how built programs are called (see GHC.hs for defaults) +userProgramPath :: Stage -> Package -> Maybe FilePath +userProgramPath = defaultProgramPath + -- Choose integer library: integerGmp, integerGmp2 or integerSimple integerLibrary :: Package integerLibrary = integerGmp From git at git.haskell.org Thu Oct 26 23:22:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate targets from package list. (5c01b64) Message-ID: <20171026232253.D5BB93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5c01b64cff13863a0c3dc34a63352b7214245a72/ghc >--------------------------------------------------------------- commit 5c01b64cff13863a0c3dc34a63352b7214245a72 Author: Andrey Mokhov Date: Tue Jan 13 13:03:48 2015 +0000 Generate targets from package list. >--------------------------------------------------------------- 5c01b64cff13863a0c3dc34a63352b7214245a72 src/Package.hs | 30 ++++++++++++++++-------------- 1 file changed, 16 insertions(+), 14 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 899e48a..217c05a 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -25,18 +25,20 @@ buildPackage = buildPackageData packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments - want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" - , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" - , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" - , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.a" - , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.p_a" - , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" - , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.a" - , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.p_a" - , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" - , "libraries/binary/dist-install/build/HSbinar_8WpSY1EWq5j1AwY619xVVw.o" - , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.a" - , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.p_a" ] - forM_ packages $ \pkg -> do - forM_ (pkgTodo pkg) $ \todoItem -> do + forM_ packages $ \pkg @ (Package name path todo) -> do + forM_ todo $ \todoItem @ (stage, dist, settings) -> do + + -- Want top .o and .a files for the pkg/todo combo: + action $ do + let buildDir = path dist "build" + pkgData = path dist "package-data.mk" + [key] <- arg (PackageKey pkgData) + let oFile = buildDir "Hs" ++ key <.> "o" + ways' <- ways settings + aFiles <- forM ways' $ \way -> do + extension <- libsuf way + return $ buildDir "libHs" ++ key <.> extension + need $ [oFile] ++ aFiles + + -- Build rules for the package buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:22:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments/todos. (5e0734b) Message-ID: <20171026232254.2EEE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e0734bc2bfafc15e6b2de692a5b1f22a73217ec/ghc >--------------------------------------------------------------- commit 5e0734bc2bfafc15e6b2de692a5b1f22a73217ec Author: Andrey Mokhov Date: Sat Sep 26 22:56:01 2015 +0100 Add comments/todos. >--------------------------------------------------------------- 5e0734bc2bfafc15e6b2de692a5b1f22a73217ec doc/meeting-25-September-2015.txt | 23 ++++++++++++++++++++--- src/Settings/Builders/Alex.hs | 7 +++++++ src/Stage.hs | 1 + src/Target.hs | 4 ++-- 4 files changed, 30 insertions(+), 5 deletions(-) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt index dde2e45..166c3d8 100644 --- a/doc/meeting-25-September-2015.txt +++ b/doc/meeting-25-September-2015.txt @@ -14,11 +14,12 @@ Done: * Improve complexity when searching for module files (40x) Todo: Target: -* Build utils, rts October +* Build utils, rts & put in GHC tree October * Better dependencies (.hs-incl etc.) November * Support command line options December -* Validate November-December (GHC 8.0?) +* Validate November-December * Documentation December-January +* Journal paper + provenance December-February Notes: * Zero build: under 7 seconds @@ -26,6 +27,14 @@ Notes: * Limited parallelism: ghc-cabal/ghc-pkg not thread-safe, ghc fails on > 4 cores * Codebase growing: 50 files +Things to do: +-- Use OrderOnly for ordering ghc-cabal's +-- Fix parallel invokations of ghc-cabal +-- Fix GHC -M to handle .hs-incl (--make already knows how to do that) instead of writing a new parser. Maybe already done -- find a flag! +-- Rename files -> outputs, sources -> inputs +-- Start separating general bits from GHC bits. A separate package for Args maybe +-- Look up Bazel and Buck +-- Decompose args into builder-specific and package-specific 2. Seemingly dead-code ---------------------- @@ -46,7 +55,7 @@ ifeq "$(TargetOS_CPP)" "irix" @echo "#endif" >> $@ endif -But IRIX_MAJOR is never set anywhere in the build system. Dead code? +But IRIX_MAJOR is never set anywhere in the build system. Dead code? YES 3. Command line options @@ -56,6 +65,12 @@ Discuss the need for command line options, e.g. 'make GhcDebugged=YES'. Do we ne Settings.User is fairly readable, so perhaps some options may be changeable only by editing this file and recompiling the build system (typically takes negligible time compared to building). This will simplify things. Can we come up with a must-have list for command line options? +-- Try to support these first: +* EXTRA_HC_OPTS = file "asd" ? arg ".." +* EXTRA_CC_OPTS +* GhcDebugged = True +* make 2 + 4. Better names for build stages -------------------------------- @@ -79,3 +94,5 @@ Stage3 -> Selftest build system' is overly verbose. Calling it 'shake' is confusing. * I haven't thought about any names yet, just checking whether we want to. + +-- Use mk2 \ No newline at end of file diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs index 1e0f87b..257fd58 100644 --- a/src/Settings/Builders/Alex.hs +++ b/src/Settings/Builders/Alex.hs @@ -12,3 +12,10 @@ alexArgs = builder Alex ? do , package compiler ? arg "--latin1" , arg src , arg "-o", arg file ] + +-- TODO: +-- compilierArgs = package compiler ? builder Alex ? arg "awe" + +-- args = mconcat +-- [ alexArgs +-- , compilerArgs ] diff --git a/src/Stage.hs b/src/Stage.hs index edddb6f..e0a6124 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -5,6 +5,7 @@ import Base import GHC.Generics (Generic) -- TODO: rename to something more meaningful, e.g. 'Stage0' -> 'Boot'. +-- TODO: explain stages data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum, Generic) instance Show Stage where diff --git a/src/Target.hs b/src/Target.hs index 8e2a44e..257a896 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -22,8 +22,8 @@ data Target = Target package :: Package, builder :: Builder, way :: Way, - sources :: [FilePath], - files :: [FilePath] + sources :: [FilePath], -- input + files :: [FilePath] -- output } deriving (Show, Eq, Generic) From git at git.haskell.org Thu Oct 26 23:22:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (7ad0b09) Message-ID: <20171026232257.A9E073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ad0b09ddbfd98ec8e026ef146add00e12c35e2f/ghc >--------------------------------------------------------------- commit 7ad0b09ddbfd98ec8e026ef146add00e12c35e2f Author: Andrey Mokhov Date: Tue Jan 13 15:22:31 2015 +0000 Clean up. >--------------------------------------------------------------- 7ad0b09ddbfd98ec8e026ef146add00e12c35e2f src/Base.hs | 2 ++ src/Oracles/Builder.hs | 12 ++++++++---- src/Oracles/Option.hs | 4 ++++ src/Package.hs | 6 +++--- src/Package/Compile.hs | 7 ++++--- src/Package/Dependencies.hs | 2 +- src/Package/Library.hs | 3 ++- 7 files changed, 24 insertions(+), 12 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 169f556..e3f2256 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -27,6 +27,8 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) instance Show Stage where show = show . fromEnum +-- The returned list of strings is a list of arguments +-- to be passed to a Builder type Args = Action [String] type Condition = Action Bool diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 8a2c5b2..5c9d64b 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -11,6 +11,9 @@ import Oracles.Base import Oracles.Flag import Oracles.Option +-- A Builder is an external command invoked in separate process +-- by calling Shake.cmd +-- -- Ghc Stage0 is the bootstrapping compiler -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg @@ -96,7 +99,8 @@ run :: Builder -> Args -> Action () run builder args = do needBuilder builder [exe] <- showArgs builder - cmd [exe] =<< args + args' <- args + cmd [exe] args' -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. @@ -106,9 +110,9 @@ terseRun builder args = do needBuilder builder [exe] <- showArgs builder args' <- args - putNormal $ "--------\nRunning " ++ show builder ++ " with arguments:" - mapM_ (putNormal . (" " ++)) $ interestingInfo builder args' - putNormal "--------" + putNormal $ "|--------\n| Running " ++ show builder ++ " with arguments:" + mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args' + putNormal "|--------" quietly $ cmd [exe] args' interestingInfo :: Builder -> [String] -> [String] diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 89192a7..ee8fb66 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -8,6 +8,10 @@ import Base import Oracles.Flag import Oracles.Base +-- For each Option the files {default.config, user.config} contain +-- a line of the form 'target-os = mingw32'. +-- (showArgs TargetOS) is an action that consults the config files +-- and returns ["mingw32"]. -- TODO: separate single string options from multiple string ones. data Option = TargetOS | TargetArch diff --git a/src/Package.hs b/src/Package.hs index 217c05a..e815c4b 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -11,9 +11,9 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] packages = [libraryPackage "array" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings, libraryPackage "bin-package-db" Stage1 defaultSettings, - libraryPackage "binary" Stage1 defaultSettings] + libraryPackage "binary" Stage1 defaultSettings, + libraryPackage "deepseq" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -24,7 +24,7 @@ buildPackage = buildPackageData packageRules :: Rules () packageRules = do - -- TODO: control targets from commang line arguments + -- TODO: control targets from command line arguments forM_ packages $ \pkg @ (Package name path todo) -> do forM_ todo $ \todoItem @ (stage, dist, settings) -> do diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 56d168a..d701af6 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -32,7 +32,7 @@ suffixArgs way = arg ["-hisuf", hisuf way] oRule :: Package -> TodoItem -> Rules () oRule (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" - pkgData = toStandard $ path dist "package-data.mk" + pkgData = path dist "package-data.mk" depFile = buildDir name <.> "m" in (buildDir "*o") %> \out -> do @@ -49,6 +49,7 @@ oRule (Package name path _) (stage, dist, settings) = <> packageArgs stage pkgData <> includeArgs path dist <> concatArgs ["-optP"] (CppOpts pkgData) + -- TODO: use HC_OPTS from pkgData -- TODO: now we have both -O and -O2 <> arg ["-Wall", "-XHaskell2010", "-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir @@ -59,10 +60,10 @@ oRule (Package name path _) (stage, dist, settings) = -- TODO: This rule looks hacky... combine it with the above? hiRule :: Package -> TodoItem -> Rules () hiRule (Package name path _) (stage, dist, settings) = - let buildDir = toStandard $ path dist "build" + let buildDir = path dist "build" in (buildDir "*hi") %> \out -> do - let way = detectWay $ tail $ takeExtension out + let way = detectWay $ tail $ takeExtension out oFile = out -<.> osuf way need [oFile] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index fc9f4af..e428371 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -6,7 +6,7 @@ import Package.Base buildPackageDependencies :: Package -> TodoItem -> Rules () buildPackageDependencies (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" - pkgData = toStandard $ path dist "package-data.mk" + pkgData = path dist "package-data.mk" in (buildDir name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] diff --git a/src/Package/Library.hs b/src/Package/Library.hs index ec2b845..043977a 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -7,7 +7,6 @@ import Data.List.Split arRule :: Package -> TodoItem -> Rules () arRule (Package _ path _) (stage, dist, _) = let buildDir = path dist "build" - pkgData = path dist "package-data.mk" in (buildDir "*a") %> \out -> do let way = detectWay $ tail $ takeExtension out @@ -16,6 +15,8 @@ arRule (Package _ path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] + -- Splitting argument list into chunks as otherwise Ar chokes up + -- TODO: use simpler list notation for passing arguments forM_ (chunksOf 100 libObjs) $ \os -> do terseRun Ar $ "q" <+> toStandard out <+> os From git at git.haskell.org Thu Oct 26 23:22:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:22:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Target fields: sources -> inputs, files -> outputs. (5a162b2) Message-ID: <20171026232257.ED9BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a162b2a13746eb5ab90108323bbc6d416bd435a/ghc >--------------------------------------------------------------- commit 5a162b2a13746eb5ab90108323bbc6d416bd435a Author: Andrey Mokhov Date: Sat Sep 26 23:35:57 2015 +0100 Rename Target fields: sources -> inputs, files -> outputs. >--------------------------------------------------------------- 5a162b2a13746eb5ab90108323bbc6d416bd435a doc/demo.txt | 2 ++ src/Expression.hs | 32 ++++++++++++++++---------------- src/Oracles/ArgsHash.hs | 2 +- src/Predicates.hs | 2 +- src/Rules/Actions.hs | 6 +++--- src/Settings/Builders/Alex.hs | 13 +++++-------- src/Settings/Builders/Ar.hs | 9 +++------ src/Settings/Builders/Gcc.hs | 20 +++++++------------- src/Settings/Builders/Ghc.hs | 27 +++++++++++---------------- src/Settings/Builders/Haddock.hs | 9 ++++----- src/Settings/Builders/Happy.hs | 11 ++++------- src/Settings/Builders/HsCpp.hs | 7 ++----- src/Settings/Builders/Hsc2Hs.hs | 6 ++---- src/Settings/Builders/Ld.hs | 6 ++---- src/Stage.hs | 1 - src/Target.hs | 12 ++++++------ 16 files changed, 69 insertions(+), 96 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5a162b2a13746eb5ab90108323bbc6d416bd435a From git at git.haskell.org Thu Oct 26 23:23:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use multiple output rules for *.o and *.hi files. (6ce7cd3) Message-ID: <20171026232301.4EF2A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6ce7cd3ac8b3ba4ef0228dec9c8d4741f746a873/ghc >--------------------------------------------------------------- commit 6ce7cd3ac8b3ba4ef0228dec9c8d4741f746a873 Author: Andrey Mokhov Date: Wed Jan 14 03:58:59 2015 +0000 Use multiple output rules for *.o and *.hi files. >--------------------------------------------------------------- 6ce7cd3ac8b3ba4ef0228dec9c8d4741f746a873 src/Package/Compile.hs | 24 ++++++------------------ 1 file changed, 6 insertions(+), 18 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index d701af6..cd91c8e 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -29,13 +29,13 @@ suffixArgs way = arg ["-hisuf", hisuf way] <> arg [ "-osuf", osuf way] <> arg ["-hcsuf", hcsuf way] -oRule :: Package -> TodoItem -> Rules () -oRule (Package name path _) (stage, dist, settings) = +buildPackageCompile :: Package -> TodoItem -> Rules () +buildPackageCompile (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" pkgData = path dist "package-data.mk" - depFile = buildDir name <.> "m" + depFile = buildDir takeBaseName name <.> "m" in - (buildDir "*o") %> \out -> do + [buildDir "*o", buildDir "*hi"] &%> \[out, _] -> do let way = detectWay $ tail $ takeExtension out need ["shake/src/Package/Compile.hs"] need [depFile] @@ -49,23 +49,11 @@ oRule (Package name path _) (stage, dist, settings) = <> packageArgs stage pkgData <> includeArgs path dist <> concatArgs ["-optP"] (CppOpts pkgData) - -- TODO: use HC_OPTS from pkgData + <> arg (HsOpts pkgData) -- TODO: now we have both -O and -O2 - <> arg ["-Wall", "-XHaskell2010", "-O2"] + -- <> arg ["-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) <> arg ["-o", toStandard out] --- TODO: This rule looks hacky... combine it with the above? -hiRule :: Package -> TodoItem -> Rules () -hiRule (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" - in - (buildDir "*hi") %> \out -> do - let way = detectWay $ tail $ takeExtension out - oFile = out -<.> osuf way - need [oFile] - -buildPackageCompile :: Package -> TodoItem -> Rules () -buildPackageCompile = oRule <> hiRule From git at git.haskell.org Thu Oct 26 23:23:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for compiling programs with Ghc builder. (d7b3d34) Message-ID: <20171026232301.85CF43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d7b3d34b16e2519f2fa2d1eae96dd469d29e5824/ghc >--------------------------------------------------------------- commit d7b3d34b16e2519f2fa2d1eae96dd469d29e5824 Author: Andrey Mokhov Date: Mon Dec 7 01:42:30 2015 +0000 Add support for compiling programs with Ghc builder. >--------------------------------------------------------------- d7b3d34b16e2519f2fa2d1eae96dd469d29e5824 src/Settings/Builders/Ghc.hs | 32 +++++++++++++++++++++----------- 1 file changed, 21 insertions(+), 11 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index ad34e19..8ab4357 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,24 +2,32 @@ module Settings.Builders.Ghc (ghcArgs, ghcMArgs, commonGhcArgs) where import Expression import Oracles -import Predicates (stagedBuilder, splitObjects, stage0, notStage0) +import GHC +import Predicates (package, stagedBuilder, splitObjects, stage0, notStage0) import Settings -- TODO: add support for -dyno +-- TODO: consider adding a new builder for programs (e.g. GhcLink?) -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ -- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) ghcArgs :: Args -ghcArgs = stagedBuilder Ghc ? mconcat [ commonGhcArgs - , arg "-H32m" - , stage0 ? arg "-O" - , notStage0 ? arg "-O2" - , arg "-Wall" - , arg "-fwarn-tabs" - , splitObjects ? arg "-split-objs" - , arg "-c", append =<< getInputs - , arg "-o", arg =<< getOutput ] +ghcArgs = stagedBuilder Ghc ? do + output <- getOutput + way <- getWay + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + mconcat [ commonGhcArgs + , arg "-H32m" + , stage0 ? arg "-O" + , notStage0 ? arg "-O2" + , arg "-Wall" + , arg "-fwarn-tabs" + , buildObj ? splitObjects ? arg "-split-objs" + , package ghc ? arg "-no-hs-main" + , buildObj ? arg "-c" + , append =<< getInputs + , arg "-o", arg =<< getOutput ] ghcMArgs :: Args ghcMArgs = stagedBuilder GhcM ? do @@ -71,6 +79,7 @@ wayGhcArgs = do packageGhcArgs :: Args packageGhcArgs = do stage <- getStage + pkg <- getPackage supportsPackageKey <- getFlag SupportsPackageKey pkgKey <- getPkgData PackageKey pkgDepIds <- getPkgDataList DepIds @@ -78,7 +87,8 @@ packageGhcArgs = do [ arg "-hide-all-packages" , arg "-no-user-package-db" , stage0 ? arg "-package-db libraries/bootstrapping.conf" - , if supportsPackageKey || stage /= Stage0 + , isLibrary pkg ? + if supportsPackageKey || stage /= Stage0 then arg $ "-this-package-key " ++ pkgKey else arg $ "-package-name " ++ pkgKey , append $ map ("-package-id " ++) pkgDepIds ] From git at git.haskell.org Thu Oct 26 23:23:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add package data key HsOpts. (1a3f43b) Message-ID: <20171026232304.EA51C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a3f43b55d543e784762cf8f0e9bf40e15820703/ghc >--------------------------------------------------------------- commit 1a3f43b55d543e784762cf8f0e9bf40e15820703 Author: Andrey Mokhov Date: Wed Jan 14 04:00:39 2015 +0000 Add package data key HsOpts. >--------------------------------------------------------------- 1a3f43b55d543e784762cf8f0e9bf40e15820703 src/Oracles/PackageData.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index bf94713..854fb8c 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -20,6 +20,7 @@ data PackageData = Modules FilePath | DepKeys FilePath | Synopsis FilePath | CppOpts FilePath + | HsOpts FilePath instance ShowArgs PackageData where showArgs packageData = do @@ -32,8 +33,10 @@ instance ShowArgs PackageData where DepKeys file -> ("DEP_KEYS" , file, "" ) Synopsis file -> ("SYNOPSIS" , file, "" ) CppOpts file -> ("CPP_OPTS" , file, "" ) + HsOpts file -> ("HC_OPTS" , file, "" ) fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key - res <- askOracle $ PackageDataKey (file, fullKey) + file' = toStandard $ normaliseEx file + res <- askOracle $ PackageDataKey (file', fullKey) return $ words $ case res of Nothing -> error $ "No key '" ++ key ++ "' in " ++ file ++ "." Just "" -> defaultValue From git at git.haskell.org Thu Oct 26 23:23:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove duplicates from library archives. (3cd6a3b) Message-ID: <20171026232305.2912B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3cd6a3b7e70f658db663251037a6f034e3ab89f0/ghc >--------------------------------------------------------------- commit 3cd6a3b7e70f658db663251037a6f034e3ab89f0 Author: Andrey Mokhov Date: Mon Dec 7 01:43:51 2015 +0000 Remove duplicates from library archives. >--------------------------------------------------------------- 3cd6a3b7e70f658db663251037a6f034e3ab89f0 src/Rules/Library.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b1c3f3c..d51e2ad 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,4 +1,4 @@ -module Rules.Library (buildPackageLibrary) where +module Rules.Library (buildPackageLibrary, cSources, hSources) where import Expression hiding (splitPath) import Oracles @@ -19,7 +19,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do cSrcs <- cSources target hSrcs <- hSources target - let way = detectWay a + let way = detectWay a -- TODO: eliminate differences below cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] @@ -28,14 +28,14 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do need $ cObjs ++ hObjs split <- interpretPartial target splitObjects - splitObjs <- if not split then return [] else + splitObjs <- if not split then return hObjs else -- TODO: make clearer! fmap concat $ forM hSrcs $ \src -> do let splitPath = buildPath -/- src ++ "_" ++ osuf way ++ "_split" contents <- liftIO $ IO.getDirectoryContents splitPath return . map (splitPath -/-) . filter (not . all (== '.')) $ contents - build $ fullTarget target Ar (cObjs ++ hObjs ++ splitObjs) [a] + build $ fullTarget target Ar (cObjs ++ splitObjs) [a] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built package library '" From git at git.haskell.org Thu Oct 26 23:23:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Cabal/Cabal to list of packages. (8bdefdd) Message-ID: <20171026232308.AD7933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8bdefdd7cbb9cd1c558d7f01f05a79ec4ff25a6e/ghc >--------------------------------------------------------------- commit 8bdefdd7cbb9cd1c558d7f01f05a79ec4ff25a6e Author: Andrey Mokhov Date: Wed Jan 14 04:01:55 2015 +0000 Add Cabal/Cabal to list of packages. >--------------------------------------------------------------- 8bdefdd7cbb9cd1c558d7f01f05a79ec4ff25a6e src/Package.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index e815c4b..5d16d22 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -13,7 +13,8 @@ packages :: [Package] packages = [libraryPackage "array" Stage1 defaultSettings, libraryPackage "bin-package-db" Stage1 defaultSettings, libraryPackage "binary" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings] + libraryPackage "deepseq" Stage1 defaultSettings, + libraryPackage "Cabal/Cabal" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -28,7 +29,8 @@ packageRules = do forM_ packages $ \pkg @ (Package name path todo) -> do forM_ todo $ \todoItem @ (stage, dist, settings) -> do - -- Want top .o and .a files for the pkg/todo combo: + -- Want top .o and .a files for the pkg/todo combo + -- TODO: Check BUILD_GHCI_LIB flag to decide if .o is needed action $ do let buildDir = path dist "build" pkgData = path dist "package-data.mk" From git at git.haskell.org Thu Oct 26 23:23:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildProgram rule. (3ceca89) Message-ID: <20171026232308.F097C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ceca89902487a91a337e5a75f7f1de8b5bd4add/ghc >--------------------------------------------------------------- commit 3ceca89902487a91a337e5a75f7f1de8b5bd4add Author: Andrey Mokhov Date: Mon Dec 7 01:44:10 2015 +0000 Add buildProgram rule. >--------------------------------------------------------------- 3ceca89902487a91a337e5a75f7f1de8b5bd4add src/Rules/Package.hs | 4 +++- src/Rules/Program.hs | 29 +++++++++++++++++++++++++++++ 2 files changed, 32 insertions(+), 1 deletion(-) diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 9da4f8b..7a7d854 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -7,6 +7,7 @@ import Rules.Dependencies import Rules.Documentation import Rules.Generate import Rules.Library +import Rules.Program import Rules.Resources import Target @@ -17,4 +18,5 @@ buildPackage = mconcat , generatePackageCode , compilePackage , buildPackageLibrary - , buildPackageDocumentation ] + , buildPackageDocumentation + , buildProgram ] diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs new file mode 100644 index 0000000..14cbea0 --- /dev/null +++ b/src/Rules/Program.hs @@ -0,0 +1,29 @@ +module Rules.Program (buildProgram) where + +import Expression hiding (splitPath) +import Oracles +import Rules.Actions +import Rules.Library +import Rules.Resources +import Settings + +buildProgram :: Resources -> PartialTarget -> Rules () +buildProgram _ target @ (PartialTarget stage pkg) = do + let path = targetPath stage pkg + buildPath = path -/- "build" + program = programPath stage pkg + + (\f -> program == Just f) ?> \bin -> do + cSrcs <- cSources target -- TODO: remove code duplication (Library.hs) + hSrcs <- hSources target + let cObjs = [ buildPath -/- src -<.> osuf vanilla | src <- cSrcs ] + hObjs = [ buildPath -/- src <.> osuf vanilla | src <- hSrcs ] + objs = cObjs ++ hObjs + need objs + build $ fullTargetWithWay target (Ghc stage) vanilla objs [bin] + synopsis <- interpretPartial target $ getPkgData Synopsis + putSuccess $ "/--------\n| Successfully built program '" + ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + putSuccess $ "| Executable: " ++ bin + putSuccess $ "| Package synopsis: " + ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" From git at git.haskell.org Thu Oct 26 23:23:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix file names for package names with slashes (e.g. Cabal/Cabal). (f124e23) Message-ID: <20171026232312.787843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f124e23635f6fa05edc945e4b0200acc0e57d8c2/ghc >--------------------------------------------------------------- commit f124e23635f6fa05edc945e4b0200acc0e57d8c2 Author: Andrey Mokhov Date: Wed Jan 14 04:02:44 2015 +0000 Fix file names for package names with slashes (e.g. Cabal/Cabal). >--------------------------------------------------------------- f124e23635f6fa05edc945e4b0200acc0e57d8c2 src/Package/Data.hs | 3 ++- src/Package/Dependencies.hs | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index d3b13a5..c5d3bd2 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -59,6 +59,7 @@ buildPackageData :: Package -> TodoItem -> Rules () buildPackageData (Package name path _) (stage, dist, settings) = let pathDist = path dist configure = path "configure" + cabal = path takeBaseName name <.> "cabal" cabalArgs = arg ["configure", path, dist] -- this is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument @@ -91,7 +92,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do need ["shake/src/Package/Data.hs"] - need [path name <.> "cabal"] + need [cabal] when (doesFileExist $ configure <.> "ac") $ need [configure] terseRun GhcCabal cabalArgs when (registerPackage settings) $ terseRun (GhcPkg stage) ghcPkgArgs diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index e428371..1d3a8d2 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -8,7 +8,7 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" pkgData = path dist "package-data.mk" in - (buildDir name <.> "m") %> \out -> do + (buildDir takeBaseName name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData From git at git.haskell.org Thu Oct 26 23:23:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass dll0 modules to ghc-cabal for the compiler package. (1c09363) Message-ID: <20171026232312.CA0133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c09363fd8631cd43a885bb8399455b02fc026d1/ghc >--------------------------------------------------------------- commit 1c09363fd8631cd43a885bb8399455b02fc026d1 Author: Andrey Mokhov Date: Mon Dec 7 02:27:38 2015 +0000 Pass dll0 modules to ghc-cabal for the compiler package. >--------------------------------------------------------------- 1c09363fd8631cd43a885bb8399455b02fc026d1 src/Settings/Builders/GhcCabal.hs | 193 +++++++++++++++++++++++++++++++++++--- 1 file changed, 181 insertions(+), 12 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 582a56c..df4af2b 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -4,7 +4,7 @@ module Settings.Builders.GhcCabal ( ) where import Expression -import Predicates +import Predicates hiding (stage) import Settings cabalArgs :: Args @@ -14,7 +14,7 @@ cabalArgs = builder GhcCabal ? do mconcat [ arg "configure" , arg path , arg dir - , dllArgs + , dll0Args , withStaged Ghc , withStaged GhcPkg , stage0 ? bootPackageDbArgs @@ -40,12 +40,12 @@ ghcCabalHsColourArgs = builder GhcCabalHsColour ? do -- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do - ways <- getWays - ghcInt <- lift $ ghcWithInterpreter + ways <- getWays + ghci <- lift ghcWithInterpreter append [ if vanilla `elem` ways then "--enable-library-vanilla" else "--disable-library-vanilla" - , if vanilla `elem` ways && ghcInt && not dynamicGhcPrograms + , if vanilla `elem` ways && ghci && not dynamicGhcPrograms then "--enable-library-for-ghci" else "--disable-library-for-ghci" , if profiling `elem` ways @@ -81,13 +81,6 @@ bootPackageDbArgs = do path <- getSetting GhcSourcePath arg $ "--package-db=" ++ path -/- "libraries/bootstrapping.conf" --- This is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument; --- * otherwise, we must collapse it into one space-separated string. --- TODO: should be non-empty for compiler -dllArgs :: Args -dllArgs = arg "" - packageConstraints :: Args packageConstraints = stage0 ? do constraints <- lift . readFileLines $ bootPackageConstraints @@ -219,3 +212,179 @@ appendCcArgs xs = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" xs , builder GhcCabal ? appendSub "--gcc-options" xs ] +-- This is a positional argument, hence: +-- * if it is empty, we need to emit one empty string argument; +-- * otherwise, we must collapse it into one space-separated string. +dll0Args :: Args +dll0Args = do + windows <- lift windowsHost + pkg <- getPackage + stage <- getStage + let needDll0Args = windows && pkg == compiler && stage == Stage1 + ghci <- lift ghcWithInterpreter + arg . unwords . concat $ [ modules | needDll0Args ] + ++ [ ghciModules | needDll0Args && ghci ] -- see #9552 + where + modules = [ "Annotations" + , "ApiAnnotation" + , "Avail" + , "Bag" + , "BasicTypes" + , "Binary" + , "BooleanFormula" + , "BreakArray" + , "BufWrite" + , "Class" + , "CmdLineParser" + , "CmmType" + , "CoAxiom" + , "ConLike" + , "Coercion" + , "Config" + , "Constants" + , "CoreArity" + , "CoreFVs" + , "CoreSubst" + , "CoreSyn" + , "CoreTidy" + , "CoreUnfold" + , "CoreUtils" + , "CoreSeq" + , "CoreStats" + , "CostCentre" + , "Ctype" + , "DataCon" + , "Demand" + , "Digraph" + , "DriverPhases" + , "DynFlags" + , "Encoding" + , "ErrUtils" + , "Exception" + , "ExtsCompat46" + , "FamInstEnv" + , "FastFunctions" + , "FastMutInt" + , "FastString" + , "FastTypes" + , "Fingerprint" + , "FiniteMap" + , "ForeignCall" + , "Hooks" + , "HsBinds" + , "HsDecls" + , "HsDoc" + , "HsExpr" + , "HsImpExp" + , "HsLit" + , "PlaceHolder" + , "HsPat" + , "HsSyn" + , "HsTypes" + , "HsUtils" + , "HscTypes" + , "IOEnv" + , "Id" + , "IdInfo" + , "IfaceSyn" + , "IfaceType" + , "InstEnv" + , "Kind" + , "Lexeme" + , "Lexer" + , "ListSetOps" + , "Literal" + , "Maybes" + , "MkCore" + , "MkId" + , "Module" + , "MonadUtils" + , "Name" + , "NameEnv" + , "NameSet" + , "OccName" + , "OccurAnal" + , "OptCoercion" + , "OrdList" + , "Outputable" + , "PackageConfig" + , "Packages" + , "Pair" + , "Panic" + , "PatSyn" + , "PipelineMonad" + , "Platform" + , "PlatformConstants" + , "PprCore" + , "PrelNames" + , "PrelRules" + , "Pretty" + , "PrimOp" + , "RdrName" + , "Rules" + , "Serialized" + , "SrcLoc" + , "StaticFlags" + , "StringBuffer" + , "TcEvidence" + , "TcRnTypes" + , "TcType" + , "TrieMap" + , "TyCon" + , "Type" + , "TypeRep" + , "TysPrim" + , "TysWiredIn" + , "Unify" + , "UniqFM" + , "UniqSet" + , "UniqSupply" + , "Unique" + , "Util" + , "Var" + , "VarEnv" + , "VarSet" ] + ghciModules = [ "Bitmap" + , "BlockId" + , "ByteCodeAsm" + , "ByteCodeInstr" + , "ByteCodeItbls" + , "CLabel" + , "Cmm" + , "CmmCallConv" + , "CmmExpr" + , "CmmInfo" + , "CmmMachOp" + , "CmmNode" + , "CmmSwitch" + , "CmmUtils" + , "CodeGen.Platform" + , "CodeGen.Platform.ARM" + , "CodeGen.Platform.ARM64" + , "CodeGen.Platform.NoRegs" + , "CodeGen.Platform.PPC" + , "CodeGen.Platform.PPC_Darwin" + , "CodeGen.Platform.SPARC" + , "CodeGen.Platform.X86" + , "CodeGen.Platform.X86_64" + , "FastBool" + , "Hoopl" + , "Hoopl.Dataflow" + , "InteractiveEvalTypes" + , "MkGraph" + , "PprCmm" + , "PprCmmDecl" + , "PprCmmExpr" + , "Reg" + , "RegClass" + , "SMRep" + , "StgCmmArgRep" + , "StgCmmClosure" + , "StgCmmEnv" + , "StgCmmLayout" + , "StgCmmMonad" + , "StgCmmProf" + , "StgCmmTicky" + , "StgCmmUtils" + , "StgSyn" + , "Stream" ] From git at git.haskell.org Thu Oct 26 23:23:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (f80948c) Message-ID: <20171026232316.172983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f80948c6655e0c6bf2ba6a10e09647b78e5ee1ab/ghc >--------------------------------------------------------------- commit f80948c6655e0c6bf2ba6a10e09647b78e5ee1ab Author: Andrey Mokhov Date: Wed Jan 14 04:02:49 2015 +0000 Clean up. >--------------------------------------------------------------- f80948c6655e0c6bf2ba6a10e09647b78e5ee1ab src/Oracles/Builder.hs | 8 +++----- src/Package/Base.hs | 11 +++++------ 2 files changed, 8 insertions(+), 11 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 5c9d64b..0fce046 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -107,13 +107,11 @@ run builder args = do -- Raises an error if the builder is not uniquely specified in config files terseRun :: Builder -> Args -> Action () terseRun builder args = do - needBuilder builder - [exe] <- showArgs builder args' <- args - putNormal $ "|--------\n| Running " ++ show builder ++ " with arguments:" + putNormal $ "/--------\n| Running " ++ show builder ++ " with arguments:" mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args' - putNormal "|--------" - quietly $ cmd [exe] args' + putNormal "\\--------" + quietly $ run builder args interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of diff --git a/src/Package/Base.hs b/src/Package/Base.hs index bac6801..9cf8fc8 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -65,13 +65,12 @@ commonLdArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? commonCppArgs :: Args commonCppArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? --- TODO: simplify commonCcWarninigArgs :: Args -commonCcWarninigArgs = when Validating $ - GccIsClang arg "-Wno-unknown-pragmas" - <> (not GccIsClang && not GccLt46) arg "-Wno-error=inline" - <> (GccIsClang && not GccLt46 && windowsHost) - arg "-Werror=unused-but-set-variable" +commonCcWarninigArgs = when Validating $ arg + [ when GccIsClang $ arg "-Wno-unknown-pragmas" + , when (not GccIsClang && not GccLt46) $ arg "-Wno-error=inline" + , when (GccIsClang && not GccLt46 && windowsHost) $ + arg "-Werror=unused-but-set-variable" ] bootPkgConstraints :: Args bootPkgConstraints = mempty From git at git.haskell.org Thu Oct 26 23:23:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcLink builder. (49dfde7) Message-ID: <20171026232316.659383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49dfde799495f1d8bfdc2a891bc6e930879a855e/ghc >--------------------------------------------------------------- commit 49dfde799495f1d8bfdc2a891bc6e930879a855e Author: Andrey Mokhov Date: Wed Dec 9 01:57:52 2015 +0000 Add GhcLink builder. >--------------------------------------------------------------- 49dfde799495f1d8bfdc2a891bc6e930879a855e src/Builder.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index c0ffee0..67be69f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -25,6 +25,7 @@ data Builder = Alex | Ghc Stage | GhcCabal | GhcCabalHsColour + | GhcLink Stage | GhcM Stage | GhcPkg Stage | GhcSplit @@ -50,6 +51,7 @@ builderKey builder = case builder of Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" + GhcLink stage -> builderKey $ Ghc stage -- using Ghc as linker GhcM stage -> builderKey $ Ghc stage -- synonym for 'Ghc -M' GhcCabal -> "ghc-cabal" GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' From git at git.haskell.org Thu Oct 26 23:23:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add chunksOfSize helper function. (797df55) Message-ID: <20171026232319.7BF393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/797df55a99ffbe2fe94bae5dc202444b294ae2d0/ghc >--------------------------------------------------------------- commit 797df55a99ffbe2fe94bae5dc202444b294ae2d0 Author: Andrey Mokhov Date: Thu Jan 15 02:02:28 2015 +0000 Add chunksOfSize helper function. >--------------------------------------------------------------- 797df55a99ffbe2fe94bae5dc202444b294ae2d0 src/Util.hs | 17 ++++++++++++++++- 1 file changed, 16 insertions(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index f91ff79..b1ff9e5 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,7 @@ module Util ( module Data.Char, - replaceIf, replaceEq, replaceSeparators + replaceIf, replaceEq, replaceSeparators, + chunksOfSize ) where import Base @@ -15,3 +16,17 @@ replaceEq from = replaceIf (== from) replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator +-- (chunksOfSize size ss) splits a list of strings 'ss' into chunks not +-- exceeding the given 'size'. +chunksOfSize :: Int -> [String] -> [[String]] +chunksOfSize _ [] = [] +chunksOfSize size ss = reverse chunk : chunksOfSize size rest + where + (chunk, rest) = go [] 0 ss + go chunk _ [] = (chunk, []) + go chunk chunkSize (s:ss) = let newSize = chunkSize + length s + (newChunk, rest) = go (s:chunk) newSize ss + in + if newSize > size + then (chunk , s:ss) + else (newChunk, rest) From git at git.haskell.org Thu Oct 26 23:23:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add basic support for -0 libraries. (3e82d46) Message-ID: <20171026232319.C47083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e82d460ba762334e7d52be121a1fa698dda42e4/ghc >--------------------------------------------------------------- commit 3e82d460ba762334e7d52be121a1fa698dda42e4 Author: Andrey Mokhov Date: Wed Dec 9 01:58:53 2015 +0000 Add basic support for -0 libraries. >--------------------------------------------------------------- 3e82d460ba762334e7d52be121a1fa698dda42e4 src/Rules.hs | 8 ++++++-- src/Rules/Library.hs | 5 ++++- 2 files changed, 10 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index e615c64..2e2963f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,6 +5,7 @@ import Oracles import Rules.Package import Rules.Resources import Settings +import Settings.Builders.GhcCabal -- generateTargets needs top-level build targets generateTargets :: Rules () @@ -21,9 +22,12 @@ generateTargets = action $ do ways <- interpretPartial target getWays let ghciLib = buildPath -/- "HS" ++ libName <.> "o" haddock = pkgHaddockFile pkg - libs <- forM ways $ \way -> do + libs <- fmap concat . forM ways $ \way -> do extension <- libsuf way - return $ buildPath -/- "libHS" ++ libName <.> extension + let name = buildPath -/- "libHS" ++ libName + dll0 <- needDll0 stage pkg + return $ [ name <.> extension ] + ++ [ name ++ "-0" <.> extension | dll0 ] return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] ++ [ haddock | needHaddock && stage == Stage1 ] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index d51e2ad..9e4f7d5 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -15,6 +15,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do + removeFileIfExists a cSrcs <- cSources target hSrcs <- hSources target @@ -35,7 +36,9 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do return . map (splitPath -/-) . filter (not . all (== '.')) $ contents - build $ fullTarget target Ar (cObjs ++ splitObjs) [a] + if "//*-0.*" ?== a + then build $ fullTarget target Ar [] [a] + else build $ fullTarget target Ar (cObjs ++ splitObjs) [a] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built package library '" From git at git.haskell.org Thu Oct 26 23:23:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add packages: containers, filepath, hoopl, hpc, parallel, pretty, stm, template-haskell, transformers. (d52b4c9) Message-ID: <20171026232323.693F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d52b4c94f317bfe4e631432b97a6f23d30dbf14a/ghc >--------------------------------------------------------------- commit d52b4c94f317bfe4e631432b97a6f23d30dbf14a Author: Andrey Mokhov Date: Thu Jan 15 02:03:22 2015 +0000 Add packages: containers, filepath, hoopl, hpc, parallel, pretty, stm, template-haskell, transformers. >--------------------------------------------------------------- d52b4c94f317bfe4e631432b97a6f23d30dbf14a src/Package.hs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 5d16d22..b8de413 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -10,11 +10,20 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] -packages = [libraryPackage "array" Stage1 defaultSettings, - libraryPackage "bin-package-db" Stage1 defaultSettings, - libraryPackage "binary" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings, - libraryPackage "Cabal/Cabal" Stage1 defaultSettings] +packages = [ libraryPackage "array" Stage1 defaultSettings + , libraryPackage "bin-package-db" Stage1 defaultSettings + , libraryPackage "binary" Stage1 defaultSettings + , libraryPackage "deepseq" Stage1 defaultSettings + , libraryPackage "Cabal/Cabal" Stage1 defaultSettings + , libraryPackage "containers" Stage1 defaultSettings + , libraryPackage "filepath" Stage1 defaultSettings + , libraryPackage "hoopl" Stage1 defaultSettings + , libraryPackage "hpc" Stage1 defaultSettings + , libraryPackage "parallel" Stage1 defaultSettings + , libraryPackage "pretty" Stage1 defaultSettings + , libraryPackage "stm" Stage1 defaultSettings + , libraryPackage "template-haskell" Stage1 defaultSettings + , libraryPackage "transformers" Stage1 defaultSettings ] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () From git at git.haskell.org Thu Oct 26 23:23:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Work on command lines for compiling stage 2 GHC. (159903e) Message-ID: <20171026232323.AE9A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/159903e948cb8d3497235e4dd2c0f2c1ddde3227/ghc >--------------------------------------------------------------- commit 159903e948cb8d3497235e4dd2c0f2c1ddde3227 Author: Andrey Mokhov Date: Wed Dec 9 02:00:09 2015 +0000 Work on command lines for compiling stage 2 GHC. >--------------------------------------------------------------- 159903e948cb8d3497235e4dd2c0f2c1ddde3227 src/Settings/Builders/Ghc.hs | 108 +++++++++++++++++++++++++++++++++++++- src/Settings/Builders/GhcCabal.hs | 20 ++++--- 2 files changed, 119 insertions(+), 9 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 8ab4357..8d1a30f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,10 +1,13 @@ -module Settings.Builders.Ghc (ghcArgs, ghcMArgs, commonGhcArgs) where +module Settings.Builders.Ghc ( + ghcArgs, ghcMArgs, ghcLinkArgs, commonGhcArgs + ) where import Expression import Oracles import GHC import Predicates (package, stagedBuilder, splitObjects, stage0, notStage0) import Settings +import Settings.Builders.GhcCabal -- TODO: add support for -dyno -- TODO: consider adding a new builder for programs (e.g. GhcLink?) @@ -17,6 +20,8 @@ ghcArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + libs <- getPkgDataList DepExtraLibs + libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -25,6 +30,9 @@ ghcArgs = stagedBuilder Ghc ? do , arg "-fwarn-tabs" , buildObj ? splitObjects ? arg "-split-objs" , package ghc ? arg "-no-hs-main" + , not buildObj ? arg "-no-auto-link-packages" + , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ] + , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" , append =<< getInputs , arg "-o", arg =<< getOutput ] @@ -116,3 +124,101 @@ includeGhcArgs = do -- define libraries/ghc-prim_PACKAGE_MAGIC -- libraries/ghc-prim_dist-install_MODULES := $$(filter-out GHC.Prim,$$(libraries/ghc-prim_dist-install_MODULES)) -- endef + + +-- # Options for passing to plain ld +-- $1_$2_$3_ALL_LD_OPTS = \ +-- $$(WAY_$3_LD_OPTS) \ +-- $$($1_$2_DIST_LD_OPTS) \ +-- $$($1_$2_$3_LD_OPTS) \ +-- $$($1_$2_EXTRA_LD_OPTS) \ +-- $$(EXTRA_LD_OPTS) + +-- # Options for passing to GHC when we use it for linking +-- $1_$2_$3_GHC_LD_OPTS = \ +-- $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ +-- $$($1_$2_$3_MOST_HC_OPTS) + +-- TODO: add support for TargetElf and darwin +-- ifeq "$3" "dyn" +-- ifneq "$4" "0" +-- ifeq "$$(TargetElf)" "YES" +-- $1_$2_$3_GHC_LD_OPTS += \ +-- -fno-use-rpaths \ +-- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'$$$$ORIGIN/../$$d') -optl-Wl,-zorigin +-- else ifeq "$$(TargetOS_CPP)" "darwin" +-- $1_$2_$3_GHC_LD_OPTS += \ +-- -fno-use-rpaths \ +-- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') + +-- ifeq "$$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS)" "" +-- # We don't want to link the GHC RTS into C-only programs. There's no +-- # point, and it confuses the test that all GHC-compiled programs +-- # were compiled with the right GHC. +-- $1_$2_$$($1_$2_PROGRAM_WAY)_GHC_LD_OPTS += -no-auto-link-packages -no-hs-main +-- endif + +ghcLinkArgs :: Args +ghcLinkArgs = mempty + -- way <- getRtsWays + -- path <- getTargetPath + -- mconcat [ commonGhcArgs + -- , (way == dynamic) ? needDll0Args ? + -- arg $ "-dll-split " ++ path -/- "dll-split" + -- , appendSubD "-optl" (getSettingList . ConfLdLinkerArgs =<< getStage) + -- , appendSubD "-optl-L" (lift $ pkgDataList DepLibDirs) + -- , appendSubD "-optl-l" (lift $ pkgDataList DepExtraLibs) + -- , splitObjects ? arg "-split-objs" + -- , package ghc ? arg "-no-hs-main" + -- , append =<< getInputs + -- , arg "-o", arg =<< getOutput ] + + +-- # Link a dynamic library +-- # On windows we have to supply the extra libs this one links to when building it. +-- ifeq "$$(HostOS_CPP)" "mingw32" +-- $$($1_$2_$3_LIB) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) +-- ifneq "$$($1_$2_$3_LIB0)" "" +-- $$(call build-dll,$1,$2,$3, +-- -L$1/$2/build -l$$($1_$2_$3_LIB0_ROOT), +-- $$(filter-out $$($1_$2_dll0_HS_OBJS),$$($1_$2_$3_HS_OBJS)) +-- $$($1_$2_$3_NON_HS_OBJS),$$@) +-- else +-- $$(call build-dll,$1,$2,$3,,$$($1_$2_$3_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$@) +-- endif + +-- ifneq "$$($1_$2_$3_LIB0)" "" +-- $$($1_$2_$3_LIB) : $$($1_$2_$3_LIB0) +-- $$($1_$2_$3_LIB0) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) +-- $$(call build-dll,$1,$2,$3,,$$($1_$2_dll0_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$($1_$2_$3_LIB0)) +-- endif + + + +-- # $1 = dir +-- # $2 = distdir +-- # $3 = way +-- # $4 = extra flags +-- # $5 = object files to link +-- # $6 = output filename +-- define build-dll +-- $(call cmd,$1_$2_HC) $($1_$2_$3_ALL_HC_OPTS) $($1_$2_$3_GHC_LD_OPTS) $4 $5 \ +-- -shared -dynamic -dynload deploy \ +-- $(addprefix -l,$($1_$2_EXTRA_LIBRARIES)) \ +-- -no-auto-link-packages \ +-- -o $6 +-- # Now check that the DLL doesn't have too many symbols. See trac #5987. +-- SYMBOLS=`$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail -n +2 | wc -l`; echo "Number of symbols in $6: $$SYMBOLS" +-- case `$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | grep "\[ *0\]" | wc -l` in 1) echo DLL $6 OK;; 0) echo No symbols in DLL $6; exit 1;; [0-9]*) echo Too many symbols in DLL $6; $(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail; exit 1;; *) echo bad DLL $6; exit 1;; esac +-- endef + + + +-- TODO: add -dynamic-too? +-- # $1_$2_$3_ALL_HC_OPTS: this is all the options we will pass to GHC +-- # for a given ($1,$2,$3). +-- $1_$2_$3_ALL_HC_OPTS = \ +-- -hisuf $$($3_hisuf) -osuf $$($3_osuf) -hcsuf $$($3_hcsuf) \ +-- $$($1_$2_$3_MOST_DIR_HC_OPTS) \ +-- $$(if $$(findstring YES,$$($1_$2_SplitObjs)),$$(if $$(findstring dyn,$3),,-split-objs),) \ +-- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),$$(if $$(findstring v,$3),-dynamic-too)) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index df4af2b..793a7f7 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,6 +1,6 @@ module Settings.Builders.GhcCabal ( cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, - ccArgs, cppArgs, ccWarnings, argStagedSettingList + ccArgs, cppArgs, ccWarnings, argStagedSettingList, needDll0 ) where import Expression @@ -212,18 +212,22 @@ appendCcArgs xs = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" xs , builder GhcCabal ? appendSub "--gcc-options" xs ] +needDll0 :: Stage -> Package -> Action Bool +needDll0 stage pkg = do + windows <- windowsHost + return $ windows && pkg == compiler && stage == Stage1 + -- This is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument; -- * otherwise, we must collapse it into one space-separated string. dll0Args :: Args dll0Args = do - windows <- lift windowsHost - pkg <- getPackage - stage <- getStage - let needDll0Args = windows && pkg == compiler && stage == Stage1 - ghci <- lift ghcWithInterpreter - arg . unwords . concat $ [ modules | needDll0Args ] - ++ [ ghciModules | needDll0Args && ghci ] -- see #9552 + stage <- getStage + pkg <- getPackage + dll0 <- lift $ needDll0 stage pkg + ghci <- lift ghcWithInterpreter + arg . unwords . concat $ [ modules | dll0 ] + ++ [ ghciModules | dll0 && ghci ] -- see #9552 where modules = [ "Annotations" , "ApiAnnotation" From git at git.haskell.org Thu Oct 26 23:23:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add argSizeLimit function (mainly for Ar builder). (cff887e) Message-ID: <20171026232327.47EEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cff887e3d3e30b187542580e8f5c4671bbe126b9/ghc >--------------------------------------------------------------- commit cff887e3d3e30b187542580e8f5c4671bbe126b9 Author: Andrey Mokhov Date: Thu Jan 15 02:05:05 2015 +0000 Add argSizeLimit function (mainly for Ar builder). >--------------------------------------------------------------- cff887e3d3e30b187542580e8f5c4671bbe126b9 src/Package/Base.hs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 9cf8fc8..a1eab2c 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -9,7 +9,8 @@ module Package.Base ( commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, bootPkgConstraints, pathArgs, packageArgs, includeArgs, pkgHsSources, - pkgDepObjects, pkgLibObjects + pkgDepObjects, pkgLibObjects, + argSizeLimit ) where import Base @@ -147,3 +148,14 @@ findModuleFiles pkgData directories suffixes = do suffix <- suffixes return $ dir modPath ++ suffix return $ map (toStandard . normaliseEx) files + +-- The argument list has a limited size on Windows. Since Windows 7 the limit +-- is 32768 (theoretically). In practice we use 31000 to leave some breathing +-- space for the builder's path & name, auxiliary flags, and other overheads. +-- Use this function to set limits for other operating systems if necessary. +argSizeLimit :: Action Int +argSizeLimit = do + windows <- windowsHost + return $ if windows + then 31000 + else 1048576 -- surely, 1MB should be enough? From git at git.haskell.org Thu Oct 26 23:23:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add extra objects into integerGmp library. (9439336) Message-ID: <20171026232327.8DBD03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9439336c258c9e1d93b1da57cde1d89e8800fbf0/ghc >--------------------------------------------------------------- commit 9439336c258c9e1d93b1da57cde1d89e8800fbf0 Author: Andrey Mokhov Date: Thu Dec 10 00:28:42 2015 +0000 Add extra objects into integerGmp library. >--------------------------------------------------------------- 9439336c258c9e1d93b1da57cde1d89e8800fbf0 src/Rules/Library.hs | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 9e4f7d5..b0afdc6 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,6 +1,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Expression hiding (splitPath) +import GHC import Oracles import Predicates (splitObjects) import Rules.Actions @@ -36,9 +37,12 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do return . map (splitPath -/-) . filter (not . all (== '.')) $ contents + eObjs <- extraObjects target + let objs = cObjs ++ splitObjs ++ eObjs + if "//*-0.*" ?== a - then build $ fullTarget target Ar [] [a] - else build $ fullTarget target Ar (cObjs ++ splitObjs) [a] + then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls + else build $ fullTarget target Ar objs [a] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built package library '" @@ -65,3 +69,10 @@ hSources target = do modules <- interpretPartial target $ getPkgDataList Modules -- GHC.Prim is special: we do not build it return . map (replaceEq '.' '/') . filter (/= "GHC.Prim") $ modules + +extraObjects :: PartialTarget -> Action [FilePath] +extraObjects (PartialTarget _ pkg) = do + gmpObjs <- getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] + if pkg == integerGmp + then return gmpObjs + else return [] From git at git.haskell.org Thu Oct 26 23:23:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generalise run and terseRun. (5596b04) Message-ID: <20171026232331.24D213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5596b04183c7c55c88c4173d5143803cd93691a4/ghc >--------------------------------------------------------------- commit 5596b04183c7c55c88c4173d5143803cd93691a4 Author: Andrey Mokhov Date: Thu Jan 15 02:05:49 2015 +0000 Generalise run and terseRun. >--------------------------------------------------------------- 5596b04183c7c55c88c4173d5143803cd93691a4 src/Oracles/Builder.hs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 0fce046..b1aca5d 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -95,27 +95,27 @@ with builder = do -- Run the builder with a given collection of arguments -- Raises an error if the builder is not uniquely specified in config files -run :: Builder -> Args -> Action () -run builder args = do +run :: ShowArgs a => Builder -> a -> Action () +run builder as = do needBuilder builder [exe] <- showArgs builder - args' <- args - cmd [exe] args' + args <- showArgs as + cmd [exe] args -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. -- Raises an error if the builder is not uniquely specified in config files -terseRun :: Builder -> Args -> Action () -terseRun builder args = do - args' <- args +terseRun :: ShowArgs a => Builder -> a -> Action () +terseRun builder as = do + args <- showArgs as putNormal $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args' + mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args putNormal "\\--------" - quietly $ run builder args + quietly $ run builder as interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of - Ar -> prefixAndSuffix 3 1 ss + Ar -> prefixAndSuffix 2 1 ss Ld -> prefixAndSuffix 4 0 ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss From git at git.haskell.org Thu Oct 26 23:23:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for utility packages. (2f1eda7) Message-ID: <20171026232331.5D81D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f1eda773f2d11e11e9f46591078e50be94e458b/ghc >--------------------------------------------------------------- commit 2f1eda773f2d11e11e9f46591078e50be94e458b Author: Andrey Mokhov Date: Thu Dec 10 01:42:07 2015 +0000 Add support for utility packages. >--------------------------------------------------------------- 2f1eda773f2d11e11e9f46591078e50be94e458b src/GHC.hs | 18 +++++++++++------- src/Package.hs | 9 ++++++--- src/Rules/Library.hs | 8 +++----- src/Settings/Builders/Ghc.hs | 3 +-- src/Settings/Packages.hs | 3 ++- 5 files changed, 23 insertions(+), 18 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 668cf48..de482f4 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,6 +1,6 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, @@ -19,13 +19,14 @@ import Stage defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl - , hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm - , templateHaskell, terminfo, time, transformers, unix, win32, xhtml ] + , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPrim + , haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty + , primitive, process, stm, templateHaskell, terminfo, time, transformers + , unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package @@ -41,6 +42,7 @@ deepseq = library "deepseq" directory = library "directory" filepath = library "filepath" ghc = topLevel "ghc-bin" `setPath` "ghc" +ghcCabal = utility "ghc-cabal" ghcPrim = library "ghc-prim" haskeline = library "haskeline" hoopl = library "hoopl" @@ -60,6 +62,7 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" + -- GHC build results will be placed into target directories with the following -- typical structure: -- * build/ : contains compiled object code @@ -75,8 +78,9 @@ defaultTargetDirectory stage pkg defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg - | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) - | otherwise = Nothing + | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) + | pkg == ghcCabal = program $ pkgName pkg + | otherwise = Nothing where program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg -/- "build/tmp" -/- name <.> exe diff --git a/src/Package.hs b/src/Package.hs index fba192c..85fbd13 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} module Package ( - Package (..), PackageName, pkgCabalFile, setPath, library, topLevel + Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility ) where import Base @@ -21,11 +21,14 @@ data Package = Package pkgCabalFile :: Package -> FilePath pkgCabalFile pkg = pkgPath pkg -/- pkgName pkg <.> "cabal" +topLevel :: PackageName -> Package +topLevel name = Package name name + library :: PackageName -> Package library name = Package name ("libraries" -/- name) -topLevel :: PackageName -> Package -topLevel name = Package name name +utility :: PackageName -> Package +utility name = Package name ("utils" -/- name) setPath :: Package -> FilePath -> Package setPath pkg path = pkg { pkgPath = path } diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b0afdc6..1bf668d 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -71,8 +71,6 @@ hSources target = do return . map (replaceEq '.' '/') . filter (/= "GHC.Prim") $ modules extraObjects :: PartialTarget -> Action [FilePath] -extraObjects (PartialTarget _ pkg) = do - gmpObjs <- getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] - if pkg == integerGmp - then return gmpObjs - else return [] +extraObjects (PartialTarget _ pkg) + | pkg == integerGmp = getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] + | otherwise = return [] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 8d1a30f..15944f3 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -7,7 +7,6 @@ import Oracles import GHC import Predicates (package, stagedBuilder, splitObjects, stage0, notStage0) import Settings -import Settings.Builders.GhcCabal -- TODO: add support for -dyno -- TODO: consider adding a new builder for programs (e.g. GhcLink?) @@ -30,7 +29,7 @@ ghcArgs = stagedBuilder Ghc ? do , arg "-fwarn-tabs" , buildObj ? splitObjects ? arg "-split-objs" , package ghc ? arg "-no-hs-main" - , not buildObj ? arg "-no-auto-link-packages" + -- , not buildObj ? arg "-no-auto-link-packages" , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ] , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 1fe70dc..5ac9c6e 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -25,7 +25,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory, filepath - , ghcPrim, haskeline, integerLibrary, pretty, process, time ] + , ghcCabal, ghcPrim, haskeline, integerLibrary, pretty, process + , time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] From git at git.haskell.org Thu Oct 26 23:23:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass HsOpts to ghc -M. (b75a548) Message-ID: <20171026232334.DE9C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b75a548ad3e0c117a11db7cfc3d0ed0e00960612/ghc >--------------------------------------------------------------- commit b75a548ad3e0c117a11db7cfc3d0ed0e00960612 Author: Andrey Mokhov Date: Thu Jan 15 02:06:25 2015 +0000 Pass HsOpts to ghc -M. >--------------------------------------------------------------- b75a548ad3e0c117a11db7cfc3d0ed0e00960612 src/Package/Dependencies.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 1d3a8d2..f296419 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -17,11 +17,8 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = <> productArgs ["-odir", "-stubdir", "-hidir"] buildDir <> arg ["-dep-makefile", toStandard $ out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) + <> arg (HsOpts pkgData) <> arg (pkgHsSources path dist) - -- TODO: Check that skipping all _HC_OPTS is safe. - -- <> arg SrcHcOpts - -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - -- <> wayHcOpts vanilla -- Avoid rebuilding dependecies of out if it hasn't changed: -- Note: cannot use copyFileChanged as it depends on the source file deps <- liftIO $ readFile $ out <.> "new" From git at git.haskell.org Thu Oct 26 23:23:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix a poor pattern for detecting -0 library files. (b0424dc) Message-ID: <20171026232335.055323A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b0424dc9bb4c9035c1239d9d14bc720d4b6db9ad/ghc >--------------------------------------------------------------- commit b0424dc9bb4c9035c1239d9d14bc720d4b6db9ad Author: Andrey Mokhov Date: Fri Dec 11 00:23:25 2015 +0000 Fix a poor pattern for detecting -0 library files. >--------------------------------------------------------------- b0424dc9bb4c9035c1239d9d14bc720d4b6db9ad src/Rules/Library.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 1bf668d..a2cf010 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -40,7 +40,8 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do eObjs <- extraObjects target let objs = cObjs ++ splitObjs ++ eObjs - if "//*-0.*" ?== a + asuf <- libsuf way + if ("//*-0" <.> asuf) ?== a then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls else build $ fullTarget target Ar objs [a] From git at git.haskell.org Thu Oct 26 23:23:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass arguments as simple lists. (6269a42) Message-ID: <20171026232338.79B8D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6269a42dc3c1f166f8ab913d5cca4a0ed7000f88/ghc >--------------------------------------------------------------- commit 6269a42dc3c1f166f8ab913d5cca4a0ed7000f88 Author: Andrey Mokhov Date: Thu Jan 15 02:07:53 2015 +0000 Pass arguments as simple lists. >--------------------------------------------------------------- 6269a42dc3c1f166f8ab913d5cca4a0ed7000f88 src/Package/Library.hs | 21 ++++++++++++--------- 1 file changed, 12 insertions(+), 9 deletions(-) diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 043977a..22c9869 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -2,7 +2,6 @@ module Package.Library (buildPackageLibrary) where import Package.Base -import Data.List.Split arRule :: Package -> TodoItem -> Rules () arRule (Package _ path _) (stage, dist, _) = @@ -16,9 +15,11 @@ arRule (Package _ path _) (stage, dist, _) = libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] -- Splitting argument list into chunks as otherwise Ar chokes up - -- TODO: use simpler list notation for passing arguments - forM_ (chunksOf 100 libObjs) $ \os -> do - terseRun Ar $ "q" <+> toStandard out <+> os + maxChunk <- argSizeLimit + forM_ (chunksOfSize maxChunk libObjs) $ \os -> do + terseRun Ar [ arg "q" + , arg $ toStandard out + , arg os ] ldRule :: Package -> TodoItem -> Rules () ldRule (Package name path _) (stage, dist, _) = @@ -29,12 +30,14 @@ ldRule (Package name path _) (stage, dist, _) = need ["shake/src/Package/Library.hs"] depObjs <- pkgDepObjects path dist vanilla need depObjs - terseRun Ld $ arg (ConfLdLinkerArgs stage) - <> arg ["-r", "-o", toStandard out] - <> arg depObjs + terseRun Ld [ arg (ConfLdLinkerArgs stage) + , arg "-r" + , arg "-o" + , arg $ toStandard out + , arg depObjs ] synopsis <- unwords <$> arg (Synopsis pkgData) - putNormal $ "Successfully built package " ++ name ++ "." - putNormal $ "Package synopsis: " ++ synopsis ++ "." + putNormal $ "/--------\nSuccessfully built package " ++ name ++ "." + putNormal $ "Package synopsis: " ++ synopsis ++ ".\n\\--------" buildPackageLibrary :: Package -> TodoItem -> Rules () buildPackageLibrary = arRule <> ldRule From git at git.haskell.org Thu Oct 26 23:23:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass __GLASGOW_HASKELL__ to gcc when compiling directory.c (098c9ec) Message-ID: <20171026232338.788FB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/098c9ece49564542cc180a6cba06577695243c7e/ghc >--------------------------------------------------------------- commit 098c9ece49564542cc180a6cba06577695243c7e Author: Andrey Mokhov Date: Fri Dec 11 00:24:01 2015 +0000 Pass __GLASGOW_HASKELL__ to gcc when compiling directory.c >--------------------------------------------------------------- 098c9ece49564542cc180a6cba06577695243c7e src/Settings/Builders/Gcc.hs | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index 6a45740..3437a6c 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -1,14 +1,21 @@ module Settings.Builders.Gcc (gccArgs, gccMArgs) where import Expression +import GHC import Oracles -import Predicates (stagedBuilder) +import Predicates (package, stagedBuilder) import Settings +-- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is +-- effectively empty. I presume it was expected that GHC will be used for +-- compiling all C files, but I don't know why. It seems that directory.c is the +-- only file which requires special treatment when using GCC. gccArgs :: Args -gccArgs = stagedBuilder Gcc ? mconcat [ commonGccArgs - , arg "-c", arg =<< getInput - , arg "-o", arg =<< getOutput ] +gccArgs = stagedBuilder Gcc ? + mconcat [ commonGccArgs + , package directory ? arg "-D__GLASGOW_HASKELL__" + , arg "-c", arg =<< getInput + , arg "-o", arg =<< getOutput ] -- TODO: handle custom $1_$2_MKDEPENDC_OPTS and gccMArgs :: Args From git at git.haskell.org Thu Oct 26 23:23:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add bin-package-db (stage 0) to packages. (ad6da32) Message-ID: <20171026232342.136B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ad6da32754b4c9eea30f344beb36728302e03b8f/ghc >--------------------------------------------------------------- commit ad6da32754b4c9eea30f344beb36728302e03b8f Author: Andrey Mokhov Date: Thu Jan 15 11:46:20 2015 +0000 Add bin-package-db (stage 0) to packages. >--------------------------------------------------------------- ad6da32754b4c9eea30f344beb36728302e03b8f src/Package.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Package.hs b/src/Package.hs index b8de413..881fd21 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -11,6 +11,7 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] packages = [ libraryPackage "array" Stage1 defaultSettings + , libraryPackage "bin-package-db" Stage0 defaultSettings , libraryPackage "bin-package-db" Stage1 defaultSettings , libraryPackage "binary" Stage1 defaultSettings , libraryPackage "deepseq" Stage1 defaultSettings From git at git.haskell.org Thu Oct 26 23:23:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generator for ghc-pkg//Version.hs. (3021dbe) Message-ID: <20171026232342.166693A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3021dbebbbc22acc67880f62a067417dcc9b486b/ghc >--------------------------------------------------------------- commit 3021dbebbbc22acc67880f62a067417dcc9b486b Author: Andrey Mokhov Date: Sat Dec 12 00:41:26 2015 +0000 Add generator for ghc-pkg//Version.hs. >--------------------------------------------------------------- 3021dbebbbc22acc67880f62a067417dcc9b486b src/Rules/Generate.hs | 20 +++++++++++++++++++- 1 file changed, 19 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 6f45dbd..97fb81f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -4,7 +4,7 @@ import Expression import GHC import Oracles import Rules.Actions -import Rules.Resources +import Rules.Resources (Resources) import Settings primopsSource :: FilePath @@ -65,6 +65,12 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = writeFileChanged file contents putBuild $ "| Successfully generated '" ++ file ++ "'." + priority 2.0 $ + when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do + contents <- interpretPartial target generateGhcPkgVersionHs + writeFileChanged file contents + putBuild $ "| Successfully generated '" ++ file ++ "'." + quote :: String -> String quote s = "\"" ++ s ++ "\"" @@ -211,3 +217,15 @@ generatePlatformH = do , "#define TARGET_VENDOR " ++ quote targetVendor , "" , "#endif /* __PLATFORM_H__ */" ] + +generateGhcPkgVersionHs :: Expr String +generateGhcPkgVersionHs = do + projectVersion <- getSetting ProjectVersion + targetOs <- getSetting TargetOs + targetArch <- getSetting TargetArch + return $ unlines + [ "module Version where" + , "version, targetOS, targetARCH :: String" + , "version = " ++ quote projectVersion + , "targetOS = " ++ quote targetOs + , "targetARCH = " ++ quote targetArch ] From git at git.haskell.org Thu Oct 26 23:23:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add arg folder. (e86a741) Message-ID: <20171026232345.E094C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e86a74150fe51816c2f72094e9c0319638e914e1/ghc >--------------------------------------------------------------- commit e86a74150fe51816c2f72094e9c0319638e914e1 Author: Andrey Mokhov Date: Thu Jan 15 11:47:22 2015 +0000 Add arg folder. >--------------------------------------------------------------- e86a74150fe51816c2f72094e9c0319638e914e1 arg/README.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/arg/README.md b/arg/README.md new file mode 100644 index 0000000..0af8834 --- /dev/null +++ b/arg/README.md @@ -0,0 +1,5 @@ +This folder serves two purposes: + +* Tracking argument lists produced by rules + +* Documentation From git at git.haskell.org Thu Oct 26 23:23:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for building ghc-pkg. (bbc6e4a) Message-ID: <20171026232345.E829D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbc6e4a216c7853c6275757fe1a84bf0e5721281/ghc >--------------------------------------------------------------- commit bbc6e4a216c7853c6275757fe1a84bf0e5721281 Author: Andrey Mokhov Date: Sat Dec 12 00:41:49 2015 +0000 Add support for building ghc-pkg. >--------------------------------------------------------------- bbc6e4a216c7853c6275757fe1a84bf0e5721281 src/GHC.hs | 16 +++++++++------- src/Settings/Packages.hs | 4 ++-- 2 files changed, 11 insertions(+), 9 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index de482f4..eff2334 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,8 +1,8 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, - integerGmp, integerSimple, parallel, pretty, primitive, process, stm, - templateHaskell, terminfo, time, transformers, unix, win32, xhtml, + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, + hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, + stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -19,16 +19,16 @@ import Stage defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPrim + , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim , haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty , primitive, process, stm, templateHaskell, terminfo, time, transformers , unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, - integerGmp, integerSimple, parallel, pretty, primitive, process, stm, - templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, + hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, + stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -43,6 +43,7 @@ directory = library "directory" filepath = library "filepath" ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" +ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" haskeline = library "haskeline" hoopl = library "hoopl" @@ -80,6 +81,7 @@ defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == ghcCabal = program $ pkgName pkg + | pkg == ghcPkg = program $ pkgName pkg | otherwise = Nothing where program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 5ac9c6e..9fbe936 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -25,8 +25,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory, filepath - , ghcCabal, ghcPrim, haskeline, integerLibrary, pretty, process - , time ] + , ghcCabal, ghcPkg, ghcPrim, haskeline, integerLibrary, pretty + , process, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] From git at git.haskell.org Thu Oct 26 23:23:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generated arg/*.txt files to .gitignore. (440aeff) Message-ID: <20171026232349.978ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/440aeff3e952f2721e4d82b1609f72b90c332901/ghc >--------------------------------------------------------------- commit 440aeff3e952f2721e4d82b1609f72b90c332901 Author: Andrey Mokhov Date: Thu Jan 15 18:40:14 2015 +0000 Add generated arg/*.txt files to .gitignore. >--------------------------------------------------------------- 440aeff3e952f2721e4d82b1609f72b90c332901 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 375b257..82a6588 100644 --- a/.gitignore +++ b/.gitignore @@ -3,3 +3,4 @@ _shake/ _build/ cfg/default.config +arg/*.txt From git at git.haskell.org Thu Oct 26 23:23:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghc-pkg and ghc-cabal in stage 0. (a0e932a) Message-ID: <20171026232349.AAE543A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a0e932ab5e73ccf062cacea3f6e8b15ca3d15463/ghc >--------------------------------------------------------------- commit a0e932ab5e73ccf062cacea3f6e8b15ca3d15463 Author: Andrey Mokhov Date: Sat Dec 12 00:50:27 2015 +0000 Build ghc-pkg and ghc-cabal in stage 0. >--------------------------------------------------------------- a0e932ab5e73ccf062cacea3f6e8b15ca3d15463 src/GHC.hs | 2 ++ src/Settings/Packages.hs | 4 ++-- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index eff2334..2482854 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -70,6 +70,8 @@ xhtml = library "xhtml" -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal -- TODO: simplify to just 'show stage'? +-- TODO: we divert from the previous convention for ghc-cabal and ghc-pkg, +-- which used to store stage0 build results in 'dist' folder defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage pkg | pkg == compiler = "stage" ++ show (fromEnum stage + 1) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 9fbe936..23ee7e4 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -16,8 +16,8 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc - , templateHaskell, transformers ] + [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg + , hoopl, hpc, templateHaskell, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? From git at git.haskell.org Thu Oct 26 23:23:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generated arg/*/*.txt files to .gitignore. (11ad707) Message-ID: <20171026232353.580D23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/11ad7076f72a8c879bed4637318aedb5f6df7b63/ghc >--------------------------------------------------------------- commit 11ad7076f72a8c879bed4637318aedb5f6df7b63 Author: Andrey Mokhov Date: Thu Jan 15 18:41:45 2015 +0000 Add generated arg/*/*.txt files to .gitignore. >--------------------------------------------------------------- 11ad7076f72a8c879bed4637318aedb5f6df7b63 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 82a6588..dad3a3c 100644 --- a/.gitignore +++ b/.gitignore @@ -3,4 +3,4 @@ _shake/ _build/ cfg/default.config -arg/*.txt +arg/*/*.txt From git at git.haskell.org Thu Oct 26 23:23:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghc-pwd. (f659a18) Message-ID: <20171026232353.65C833A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f659a18291a9e4f1a8b8d7f2e22744923effcac0/ghc >--------------------------------------------------------------- commit f659a18291a9e4f1a8b8d7f2e22744923effcac0 Author: Andrey Mokhov Date: Sat Dec 12 00:53:49 2015 +0000 Build ghc-pwd. >--------------------------------------------------------------- f659a18291a9e4f1a8b8d7f2e22744923effcac0 src/GHC.hs | 18 +++++++++++------- src/Settings/Packages.hs | 6 +++--- 2 files changed, 14 insertions(+), 10 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 2482854..d1fb30a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,8 +1,9 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, - hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, - stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, + haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, + primitive, process, stm, templateHaskell, terminfo, time, transformers, + unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -20,15 +21,16 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim - , haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty + , ghcPwd, haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty , primitive, process, stm, templateHaskell, terminfo, time, transformers , unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, - hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, - stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, + haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, + primitive, process, stm, templateHaskell, terminfo, time, transformers, + unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -45,6 +47,7 @@ ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" +ghcPwd = utility "ghc-pwd" haskeline = library "haskeline" hoopl = library "hoopl" hpc = library "hpc" @@ -84,6 +87,7 @@ defaultProgramPath stage pkg | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == ghcCabal = program $ pkgName pkg | pkg == ghcPkg = program $ pkgName pkg + | pkg == ghcPwd = program $ pkgName pkg | otherwise = Nothing where program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 23ee7e4..b2636d5 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -17,7 +17,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg - , hoopl, hpc, templateHaskell, transformers ] + , ghcPwd, hoopl, hpc, templateHaskell, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? @@ -25,8 +25,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory, filepath - , ghcCabal, ghcPkg, ghcPrim, haskeline, integerLibrary, pretty - , process, time ] + , ghcCabal, ghcPkg, ghcPrim, ghcPwd, haskeline, integerLibrary + , pretty, process, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] From git at git.haskell.org Thu Oct 26 23:23:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build all utils that use cabal files. (f3199c1) Message-ID: <20171026232357.2BEB63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f3199c17a1f010017eabd4845df7533c62abfde5/ghc >--------------------------------------------------------------- commit f3199c17a1f010017eabd4845df7533c62abfde5 Author: Andrey Mokhov Date: Sat Dec 12 02:13:35 2015 +0000 Build all utils that use cabal files. >--------------------------------------------------------------- f3199c17a1f010017eabd4845df7533c62abfde5 src/GHC.hs | 52 +++++++++++++++++++++++++++++--------------- src/Rules/Generate.hs | 5 +++++ src/Rules/Library.hs | 3 ++- src/Rules/Program.hs | 7 ++++-- src/Settings/Builders/Ghc.hs | 5 ++++- src/Settings/Packages.hs | 9 ++++---- 6 files changed, 56 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f3199c17a1f010017eabd4845df7533c62abfde5 From git at git.haskell.org Thu Oct 26 23:23:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:23:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add putColoured. (63d4481) Message-ID: <20171026232357.1A2533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/63d4481898a503c5532e39f3b18a60c3518cad57/ghc >--------------------------------------------------------------- commit 63d4481898a503c5532e39f3b18a60c3518cad57 Author: Andrey Mokhov Date: Thu Jan 15 18:42:54 2015 +0000 Add putColoured. >--------------------------------------------------------------- 63d4481898a503c5532e39f3b18a60c3518cad57 src/Oracles/Builder.hs | 9 ++++++--- src/Util.hs | 13 ++++++++++++- 2 files changed, 18 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index b1aca5d..88f9649 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -7,6 +7,7 @@ module Oracles.Builder ( import Data.Char import Base +import Util import Oracles.Base import Oracles.Flag import Oracles.Option @@ -108,9 +109,11 @@ run builder as = do terseRun :: ShowArgs a => Builder -> a -> Action () terseRun builder as = do args <- showArgs as - putNormal $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args - putNormal "\\--------" + putColoured Vivid White $ "/--------\n" ++ + "| Running " ++ show builder ++ " with arguments:" + mapM_ (putColoured Vivid White . ("| " ++)) $ + interestingInfo builder args + putColoured Vivid White $ "\\--------" quietly $ run builder as interestingInfo :: Builder -> [String] -> [String] diff --git a/src/Util.hs b/src/Util.hs index b1ff9e5..e0524df 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,11 +1,15 @@ module Util ( module Data.Char, + module System.Console.ANSI, replaceIf, replaceEq, replaceSeparators, - chunksOfSize + chunksOfSize, + putColoured ) where import Base import Data.Char +import System.Console.ANSI +import System.IO replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -30,3 +34,10 @@ chunksOfSize size ss = reverse chunk : chunksOfSize size rest if newSize > size then (chunk , s:ss) else (newChunk, rest) + +putColoured :: ColorIntensity -> Color -> String -> Action () +putColoured intensity colour msg = do + liftIO $ setSGR [SetColor Foreground intensity colour] + putNormal msg + liftIO $ setSGR [] + liftIO $ hFlush stdout From git at git.haskell.org Thu Oct 26 23:24:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix splitObjects function. (1b0bfa6) Message-ID: <20171026232400.BE7683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b0bfa663029117b64bfc84687718dc3579119e8/ghc >--------------------------------------------------------------- commit 1b0bfa663029117b64bfc84687718dc3579119e8 Author: Andrey Mokhov Date: Thu Jan 15 18:43:25 2015 +0000 Fix splitObjects function. >--------------------------------------------------------------- 1b0bfa663029117b64bfc84687718dc3579119e8 src/Oracles/Option.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index ee8fb66..57137ba 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -81,6 +81,7 @@ splitObjects stage = do splitObjectsBroken <- test SplitObjectsBroken ghcUnregisterised <- test GhcUnregisterised return $ not splitObjectsBroken && not ghcUnregisterised + && stage == Stage1 && arch `elem` ["i386", "x86_64", "powerpc", "sparc"] && os `elem` ["mingw32", "cygwin32", "linux", "darwin", "solaris2", "freebsd", "dragonfly", "netbsd", From git at git.haskell.org Thu Oct 26 23:24:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build haddock. (6b14363) Message-ID: <20171026232400.D26413A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5/ghc >--------------------------------------------------------------- commit 6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5 Author: Andrey Mokhov Date: Sun Dec 13 02:30:44 2015 +0000 Build haddock. >--------------------------------------------------------------- 6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5 src/GHC.hs | 15 ++++++++++++--- src/Rules.hs | 2 +- src/Rules/Compile.hs | 1 + src/Rules/Program.hs | 7 ++++--- src/Settings/Builders/Ghc.hs | 5 +++-- src/Settings/Builders/GhcCabal.hs | 2 ++ src/Settings/Packages.hs | 12 +++++++++--- 7 files changed, 32 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5 From git at git.haskell.org Thu Oct 26 23:24:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add dependencies on argument lists. (50b8c2f) Message-ID: <20171026232404.63BE03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b/ghc >--------------------------------------------------------------- commit 50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b Author: Andrey Mokhov Date: Thu Jan 15 18:43:51 2015 +0000 Add dependencies on argument lists. >--------------------------------------------------------------- 50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b src/Package.hs | 29 +++++++++--------- src/Package/Base.hs | 59 +++++++++++++++++++++++++++--------- src/Package/Compile.hs | 72 +++++++++++++++++++++---------------------- src/Package/Data.hs | 74 ++++++++++++++++++++++++++++----------------- src/Package/Dependencies.hs | 43 ++++++++++++++++++-------- src/Package/Library.hs | 62 ++++++++++++++++++++++++++----------- 6 files changed, 217 insertions(+), 122 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b From git at git.haskell.org Thu Oct 26 23:24:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build deriveConstants utility. (bbdaa7e) Message-ID: <20171026232404.898753A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbdaa7eab8d8ebe4c5e21646cd172d53d741872e/ghc >--------------------------------------------------------------- commit bbdaa7eab8d8ebe4c5e21646cd172d53d741872e Author: Andrey Mokhov Date: Sun Dec 13 03:54:05 2015 +0000 Build deriveConstants utility. >--------------------------------------------------------------- bbdaa7eab8d8ebe4c5e21646cd172d53d741872e src/GHC.hs | 10 ++++++---- src/Oracles/PackageData.hs | 3 ++- src/Predicates.hs | 5 ++++- src/Rules/Compile.hs | 10 ++++++++-- src/Rules/Data.hs | 11 +++++++++++ src/Settings/Builders/Ghc.hs | 7 ++++--- src/Settings/Packages.hs | 1 + 7 files changed, 36 insertions(+), 11 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 bbdaa7eab8d8ebe4c5e21646cd172d53d741872e From git at git.haskell.org Thu Oct 26 23:24:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename opts to args. (3cbaccc) Message-ID: <20171026232408.23B1D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3cbacccf34dc3da2811e5a2f3e608bdd2a3cac1a/ghc >--------------------------------------------------------------- commit 3cbacccf34dc3da2811e5a2f3e608bdd2a3cac1a Author: Andrey Mokhov Date: Fri Jan 16 03:11:21 2015 +0000 Rename opts to args. >--------------------------------------------------------------- 3cbacccf34dc3da2811e5a2f3e608bdd2a3cac1a cfg/default.config.in | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index ac42e24..10ee7ee 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -34,6 +34,7 @@ supports-package-key = @SUPPORTS_PACKAGE_KEY@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ +validating = NO # Information about host and target systems: #=========================================== @@ -69,7 +70,7 @@ conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ -src-hc-opts = -H32m -O +src-hc-args = -H32m -O # Include and library directories: #================================= From git at git.haskell.org Thu Oct 26 23:24:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build genapply utility. (e99bd28) Message-ID: <20171026232408.4799D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e99bd28a549c2c362bf8bef7dde9f13ca05a2510/ghc >--------------------------------------------------------------- commit e99bd28a549c2c362bf8bef7dde9f13ca05a2510 Author: Andrey Mokhov Date: Sun Dec 13 19:19:18 2015 +0000 Build genapply utility. >--------------------------------------------------------------- e99bd28a549c2c362bf8bef7dde9f13ca05a2510 src/GHC.hs | 15 +++++++++------ src/Rules/Compile.hs | 7 ++++++- src/Rules/Data.hs | 16 +++++++++++++++- src/Settings/Builders/Ghc.hs | 9 ++++++--- src/Settings/Packages.hs | 2 +- 5 files changed, 37 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e99bd28a549c2c362bf8bef7dde9f13ca05a2510 From git at git.haskell.org Thu Oct 26 23:24:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ShowArg for single string options, clean up code. (7412fe3) Message-ID: <20171026232411.DEF1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7412fe395e6bf6708c7c58667b3f91852ff5bffa/ghc >--------------------------------------------------------------- commit 7412fe395e6bf6708c7c58667b3f91852ff5bffa Author: Andrey Mokhov Date: Fri Jan 16 03:16:59 2015 +0000 Add ShowArg for single string options, clean up code. >--------------------------------------------------------------- 7412fe395e6bf6708c7c58667b3f91852ff5bffa src/Base.hs | 5 ++- src/Config.hs | 5 +++ src/Oracles.hs | 11 +++++-- src/Oracles/Builder.hs | 31 +++++++----------- src/Oracles/Flag.hs | 11 +++---- src/Oracles/Option.hs | 85 +++++++++++++++++++++++++++----------------------- src/Util.hs | 1 + src/Ways.hs | 27 ++++++++-------- 8 files changed, 95 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 7412fe395e6bf6708c7c58667b3f91852ff5bffa From git at git.haskell.org Thu Oct 26 23:24:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build genprimopcode utility. (6f2b78b) Message-ID: <20171026232412.087113A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6f2b78bb0f063be5ff5a8abc346f765c6729621e/ghc >--------------------------------------------------------------- commit 6f2b78bb0f063be5ff5a8abc346f765c6729621e Author: Andrey Mokhov Date: Sun Dec 13 19:25:30 2015 +0000 Build genprimopcode utility. >--------------------------------------------------------------- 6f2b78bb0f063be5ff5a8abc346f765c6729621e src/GHC.hs | 10 ++++++---- src/Rules/Data.hs | 12 +++++++++++- src/Settings/Builders/Ghc.hs | 4 ++-- src/Settings/Packages.hs | 3 ++- 4 files changed, 21 insertions(+), 8 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 3821518..ff5a106 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,7 +1,7 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, ghc, ghcCabal, ghcPkg, ghcPrim, + genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hpc, hpcBin, integerGmp, integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, @@ -23,7 +23,7 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, ghc, ghcCabal, ghcPkg, ghcPrim + , filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hpc, hpcBin, integerGmp, integerSimple , mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo , time, transformers, unix, win32, xhtml ] @@ -31,7 +31,7 @@ defaultKnownPackages = -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, + genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hpc, hpcBin, integerGmp, integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, @@ -52,6 +52,7 @@ directory = library "directory" dllSplit = utility "dll-split" filepath = library "filepath" genapply = utility "genapply" +genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" ghcPkg = utility "ghc-pkg" @@ -81,7 +82,7 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" --- TODO: genprimocode, hp2ps +-- TODO: hp2ps -- TODO: The following utils are not included into the build system because -- they seem to be unused or unrelated to the build process: chechUniques, @@ -110,6 +111,7 @@ defaultProgramPath stage pkg | pkg == deriveConstants = program $ pkgName pkg | pkg == dllSplit = program $ pkgName pkg | pkg == genapply = program $ pkgName pkg + | pkg == genprimopcode = program $ pkgName pkg | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == ghcCabal = program $ pkgName pkg | pkg == ghcPkg = program $ pkgName pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 9fbc6ec..c47c6a3 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (deriveConstants, genapply) +import GHC (deriveConstants, genapply, genprimopcode) import Oracles import Predicates (registerPackage) import Rules.Actions @@ -70,6 +70,16 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do , "utils_genapply_dist-boot_HC_OPTS = " ++ hcOpts ] writeFileChanged mk contents + priority 2.0 $ + when (pkg == genprimopcode) $ path -/- "package-data.mk" %> \mk -> do + let contents = unlines + [ "utils_genprimopcode_dist-boot_MODULES = Lexer Main ParserM Parser Syntax" + , "utils_genprimopcode_dist-boot_PROGNAME = genprimopcode" + , "utils_genprimopcode_dist-boot_HS_SRC_DIRS = ." + , "utils_genprimopcode_dist-boot_INSTALL_INPLACE = YES" + , "utils_genprimopcode_dist-boot_HC_OPTS = -package array" ] + writeFileChanged mk contents + -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- For example, get rid of diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a22bee5..3d3e224 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -96,7 +96,7 @@ packageGhcArgs = do pkgKey <- getPkgData PackageKey pkgDepIds <- getPkgDataList DepIds mconcat - [ not (pkg == deriveConstants || pkg == genapply) ? + [ not (pkg == deriveConstants || pkg == genapply || pkg == genprimopcode) ? arg "-hide-all-packages" , arg "-no-user-package-db" , stage0 ? arg "-package-db libraries/bootstrapping.conf" @@ -122,7 +122,7 @@ includeGhcArgs = do , arg $ "-I" ++ autogenPath , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] - , not (pkg == deriveConstants || pkg == genapply) ? + , not (pkg == deriveConstants || pkg == genapply || pkg == genprimopcode) ? append [ "-optP-include" , "-optP" ++ autogenPath -/- "cabal_macros.h" ] ] diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 1475e40..5f1e55e 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -9,6 +9,7 @@ getPackages :: Expr [Package] getPackages = fromDiffExpr $ defaultPackages <> userPackages -- These are the packages we build by default +-- TODO: simplify defaultPackages :: Packages defaultPackages = mconcat [ stage0 ? packagesStage0 @@ -19,7 +20,7 @@ packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] - , stage0 ? append [deriveConstants, genapply] -- TODO: simplify + , stage0 ? append [deriveConstants, genapply, genprimopcode] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? From git at git.haskell.org Thu Oct 26 23:24:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Version and DepNames keys to PackageData. (229d5cb) Message-ID: <20171026232415.DA2C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/229d5cbd080a7b581fce325d9cc06a553db93bc9/ghc >--------------------------------------------------------------- commit 229d5cbd080a7b581fce325d9cc06a553db93bc9 Author: Andrey Mokhov Date: Fri Jan 16 03:18:04 2015 +0000 Add Version and DepNames keys to PackageData. >--------------------------------------------------------------- 229d5cbd080a7b581fce325d9cc06a553db93bc9 src/Oracles/PackageData.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 854fb8c..e141120 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -12,12 +12,14 @@ import Util newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -data PackageData = Modules FilePath +data PackageData = Version FilePath + | Modules FilePath | SrcDirs FilePath | PackageKey FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath + | DepNames FilePath | Synopsis FilePath | CppOpts FilePath | HsOpts FilePath @@ -25,12 +27,14 @@ data PackageData = Modules FilePath instance ShowArgs PackageData where showArgs packageData = do let (key, file, defaultValue) = case packageData of + Version file -> ("VERSION" , file, "" ) Modules file -> ("MODULES" , file, "" ) SrcDirs file -> ("HS_SRC_DIRS" , file, ".") PackageKey file -> ("PACKAGE_KEY" , file, "" ) IncludeDirs file -> ("INCLUDE_DIRS", file, ".") Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) + DepNames file -> ("DEP_NAMES" , file, "" ) Synopsis file -> ("SYNOPSIS" , file, "" ) CppOpts file -> ("CPP_OPTS" , file, "" ) HsOpts file -> ("HC_OPTS" , file, "" ) From git at git.haskell.org Thu Oct 26 23:24:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build hp2ps utility. (1057ef3) Message-ID: <20171026232416.0EF623A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1057ef38cea541d0b31b075bd9936a619f23f4fa/ghc >--------------------------------------------------------------- commit 1057ef38cea541d0b31b075bd9936a619f23f4fa Author: Andrey Mokhov Date: Sun Dec 13 22:18:45 2015 +0000 Build hp2ps utility. >--------------------------------------------------------------- 1057ef38cea541d0b31b075bd9936a619f23f4fa src/GHC.hs | 27 +++++++++++++-------------- src/Rules/Data.hs | 22 +++++++++++++++++++++- src/Rules/Dependencies.hs | 7 +++++-- src/Rules/Program.hs | 1 + src/Settings/Builders/Ghc.hs | 9 ++++++--- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Packages.hs | 2 +- 7 files changed, 49 insertions(+), 23 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 1057ef38cea541d0b31b075bd9936a619f23f4fa From git at git.haskell.org Thu Oct 26 23:24:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Targets.hs for specifying targets, clean up code. (7ffb294) Message-ID: <20171026232419.750C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ffb2940272c99938582846879e2f297215c3211/ghc >--------------------------------------------------------------- commit 7ffb2940272c99938582846879e2f297215c3211 Author: Andrey Mokhov Date: Fri Jan 16 04:02:01 2015 +0000 Add Targets.hs for specifying targets, clean up code. >--------------------------------------------------------------- 7ffb2940272c99938582846879e2f297215c3211 src/Package.hs | 29 +++++----- src/Package/Base.hs | 67 +++++++++++------------ src/Package/Compile.hs | 36 ++++++------- src/Package/Data.hs | 127 +++++++++++++++++++++++++------------------- src/Package/Dependencies.hs | 20 +++---- src/Package/Library.hs | 24 +++++---- src/Targets.hs | 25 +++++++++ 7 files changed, 183 insertions(+), 145 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 7ffb2940272c99938582846879e2f297215c3211 From git at git.haskell.org Thu Oct 26 23:24:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (0678e10) Message-ID: <20171026232419.A5EEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0678e1030e5f90b55dedcf2d72adc431f0995de5/ghc >--------------------------------------------------------------- commit 0678e1030e5f90b55dedcf2d72adc431f0995de5 Author: Andrey Mokhov Date: Mon Dec 14 02:43:00 2015 +0000 Clean up. >--------------------------------------------------------------- 0678e1030e5f90b55dedcf2d72adc431f0995de5 src/GHC.hs | 2 +- src/Package.hs | 3 +++ 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index 355ed71..ea48014 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -28,7 +28,7 @@ defaultKnownPackages = , process, runghc, stm, templateHaskell, terminfo, time, transformers, unix , win32, xhtml ] --- Package definitions +-- Package definitions (see Package.hs) array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, diff --git a/src/Package.hs b/src/Package.hs index 85fbd13..a490cb9 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -9,11 +9,14 @@ import GHC.Generics (Generic) -- It is helpful to distinguish package names from strings. type PackageName = String +-- type PackageType = Program | Library + -- pkgPath is the path to the source code relative to the root data Package = Package { pkgName :: PackageName, -- Examples: "ghc", "Cabal" pkgPath :: FilePath -- "compiler", "libraries/Cabal/Cabal" + -- pkgType :: PackageType -- TopLevel, Library } deriving Generic From git at git.haskell.org Thu Oct 26 23:24:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor package-data oracles. (5a9b0a7) Message-ID: <20171026232423.932EB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a9b0a741769feacc65bf976ca31d05ac3a58647/ghc >--------------------------------------------------------------- commit 5a9b0a741769feacc65bf976ca31d05ac3a58647 Author: Andrey Mokhov Date: Fri Jan 16 13:59:39 2015 +0000 Refactor package-data oracles. >--------------------------------------------------------------- 5a9b0a741769feacc65bf976ca31d05ac3a58647 src/Oracles/PackageData.hs | 9 +++++---- src/Package.hs | 11 +++-------- src/Package/Base.hs | 42 +++++++++++++++++++++--------------------- src/Package/Compile.hs | 10 +++++----- src/Package/Data.hs | 16 +++++++--------- src/Package/Dependencies.hs | 10 +++++----- src/Package/Library.hs | 6 +++--- 7 files changed, 49 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 5a9b0a741769feacc65bf976ca31d05ac3a58647 From git at git.haskell.org Thu Oct 26 23:24:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: No need to modify configure.ac any more. See https://phabricator.haskell.org/D1638 (5e7de75) Message-ID: <20171026232423.BC6A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e7de75760b6b44eb7d9caaae3dc805c44bb6604/ghc >--------------------------------------------------------------- commit 5e7de75760b6b44eb7d9caaae3dc805c44bb6604 Author: Andrey Mokhov Date: Wed Dec 16 22:49:27 2015 +0000 No need to modify configure.ac any more. See https://phabricator.haskell.org/D1638 >--------------------------------------------------------------- 5e7de75760b6b44eb7d9caaae3dc805c44bb6604 src/Rules/Config.hs | 15 --------------- 1 file changed, 15 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 4987fcc..bb4866d 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -2,11 +2,6 @@ module Rules.Config (configRules) where import Base --- We add the following line to 'configure.ac' in order to produce configuration --- file "system.config" from "system.config.in" by running 'configure' script. -configCommand :: String -configCommand = "AC_CONFIG_FILES([" ++ configPath ++ "system.config])" - configRules :: Rules () configRules = do configPath -/- "system.config" %> \_ -> do @@ -14,16 +9,6 @@ configRules = do putBuild "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' - -- TODO: this rule won't rebuild if configure.ac is changed. Worth fixing? "configure" %> \_ -> do - -- Make sure 'configure.ac' script contains a line with configCommand - script <- fmap lines . liftIO $ readFile "configure.ac" - when (configCommand `notElem` script) $ do - putBuild $ "Adding '" ++ configCommand ++ "' to configure.ac..." - let (before, rest) = break ("AC_CONFIG_FILES" `isPrefixOf`) script - when (null rest) $ do - putError "No AC_CONFIG_FILES command in configure.ac!" - let newScript = unlines $ before ++ [configCommand] ++ rest - length newScript `seq` liftIO (writeFile "configure.ac" newScript) putBuild "Running autoconf..." cmd "bash autoconf" -- TODO: get rid of 'bash' From git at git.haskell.org Thu Oct 26 23:24:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't build system.config by default. (8ef67ed) Message-ID: <20171026232427.3F5AD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ef67edb699b18ca41ed535069f7183a15a98cf3/ghc >--------------------------------------------------------------- commit 8ef67edb699b18ca41ed535069f7183a15a98cf3 Author: Andrey Mokhov Date: Wed Dec 16 23:07:44 2015 +0000 Don't build system.config by default. >--------------------------------------------------------------- 8ef67edb699b18ca41ed535069f7183a15a98cf3 src/Rules/Config.hs | 3 ++- src/Settings/User.hs | 5 ++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index bb4866d..50471d5 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -1,9 +1,10 @@ module Rules.Config (configRules) where import Base +import Settings.User configRules :: Rules () -configRules = do +configRules = when buildSystemConfigFile $ do configPath -/- "system.config" %> \_ -> do need [configPath -/- "system.config.in", "configure"] putBuild "Running configure..." diff --git a/src/Settings/User.hs b/src/Settings/User.hs index d841028..5159bce 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -2,7 +2,7 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - ghcDebugged, dynamicGhcPrograms, laxDependencies + ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile ) where import Expression @@ -77,3 +77,6 @@ laxDependencies = False buildHaddock :: Predicate buildHaddock = return True + +buildSystemConfigFile :: Bool +buildSystemConfigFile = False From git at git.haskell.org Thu Oct 26 23:24:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make single and multiple string options type safe. (5c1a7e4) Message-ID: <20171026232427.187623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5c1a7e4ec089b8ce044ca45d03d2305915974ada/ghc >--------------------------------------------------------------- commit 5c1a7e4ec089b8ce044ca45d03d2305915974ada Author: Andrey Mokhov Date: Fri Jan 16 17:05:33 2015 +0000 Make single and multiple string options type safe. >--------------------------------------------------------------- 5c1a7e4ec089b8ce044ca45d03d2305915974ada src/Base.hs | 22 ++++++++++--- src/Oracles/Option.hs | 2 +- src/Oracles/PackageData.hs | 75 +++++++++++++++++++++++++++++---------------- src/Package.hs | 4 +-- src/Package/Base.hs | 59 ++++++++++++++++++----------------- src/Package/Compile.hs | 26 ++++++++-------- src/Package/Data.hs | 65 ++++++++++++++++++++------------------- src/Package/Dependencies.hs | 18 +++++------ src/Package/Library.hs | 16 +++++----- src/Targets.hs | 31 ++++++++++--------- src/Util.hs | 8 ++++- src/Ways.hs | 6 ++-- 12 files changed, 187 insertions(+), 145 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 5c1a7e4ec089b8ce044ca45d03d2305915974ada From git at git.haskell.org Thu Oct 26 23:24:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcSourcePath option. (eac54ff) Message-ID: <20171026232430.996003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eac54ff6799eeb7824c7a8d1e5bb2bfa662d3189/ghc >--------------------------------------------------------------- commit eac54ff6799eeb7824c7a8d1e5bb2bfa662d3189 Author: Andrey Mokhov Date: Fri Jan 16 18:18:00 2015 +0000 Add GhcSourcePath option. >--------------------------------------------------------------- eac54ff6799eeb7824c7a8d1e5bb2bfa662d3189 cfg/default.config.in | 4 ++++ src/Oracles/Option.hs | 2 ++ 2 files changed, 6 insertions(+) diff --git a/cfg/default.config.in b/cfg/default.config.in index 10ee7ee..7402bd5 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -1,3 +1,6 @@ +# Edit 'user.config' to override these settings. +#=============================================== + # Paths to builders: #=================== @@ -35,6 +38,7 @@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ validating = NO +ghc-source-path = @hardtop@ # Information about host and target systems: #=========================================== diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 667e50e..7dcb9a8 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -22,6 +22,7 @@ data Option = TargetOs | HostOsCpp | DynamicExtension | ProjectVersion + | GhcSourcePath data MultiOption = SrcHcArgs | ConfCcArgs Stage @@ -41,6 +42,7 @@ instance ShowArg Option where HostOsCpp -> "host-os-cpp" DynamicExtension -> "dynamic-extension" ProjectVersion -> "project-version" + GhcSourcePath -> "ghc-source-path" instance ShowArgs MultiOption where showArgs opt = showArgs $ fmap words $ askConfig $ case opt of From git at git.haskell.org Thu Oct 26 23:24:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (850863e) Message-ID: <20171026232430.C2F683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/850863e56cf2c4d798cac7701e271c85d6bac2de/ghc >--------------------------------------------------------------- commit 850863e56cf2c4d798cac7701e271c85d6bac2de Author: Andrey Mokhov Date: Thu Dec 17 19:42:44 2015 +0000 Update README.md >--------------------------------------------------------------- 850863e56cf2c4d798cac7701e271c85d6bac2de README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 54742ee..faf3155 100644 --- a/README.md +++ b/README.md @@ -3,4 +3,4 @@ Shaking up GHC As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). -This is supposed to go into the `shake` directory of the GHC source tree (as a submodule). +This is supposed to go into the `build` directory of the GHC source tree. From git at git.haskell.org Thu Oct 26 23:24:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add bootPackageDb function. (2990db6) Message-ID: <20171026232434.878ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2990db6fa1688f58c252787320a14e800658e6f8/ghc >--------------------------------------------------------------- commit 2990db6fa1688f58c252787320a14e800658e6f8 Author: Andrey Mokhov Date: Fri Jan 16 18:19:12 2015 +0000 Add bootPackageDb function. >--------------------------------------------------------------- 2990db6fa1688f58c252787320a14e800658e6f8 src/Base.hs | 1 + src/Package/Data.hs | 18 ++++++++++++------ src/Targets.hs | 22 ++++++++++++---------- 3 files changed, 25 insertions(+), 16 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index f4edb45..232bca2 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -65,6 +65,7 @@ instance ShowArgs a => ShowArgs [a] where instance ShowArgs a => ShowArgs (Action a) where showArgs = (showArgs =<<) +-- TODO: improve args type safety args :: ShowArgs a => a -> Args args = showArgs diff --git a/src/Package/Data.hs b/src/Package/Data.hs index cfc8b53..b6c28c6 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -73,6 +73,12 @@ bootPkgConstraints = args $ do _ -> redError $ "Cannot determine package version in '" ++ toStandard cabal ++ "'." +bootPackageDb :: Args +bootPackageDb = do + top <- showArg GhcSourcePath + arg $ toStandard + $ "--package-db=" ++ top "libraries/bootstrapping.conf" + cabalArgs :: Package -> TodoItem -> Args cabalArgs pkg @ (Package _ path _) todo @ (stage, dist, settings) = args [ args ["configure", path, dist] @@ -83,6 +89,7 @@ cabalArgs pkg @ (Package _ path _) todo @ (stage, dist, settings) = args , with (Ghc stage) -- TODO: used limited to max stage1 GHC , with (GhcPkg stage) , customConfArgs settings + , when (stage == Stage0) bootPackageDb , libraryArgs =<< ways settings , when (specified HsColour) $ with HsColour , configureArgs stage settings @@ -94,12 +101,11 @@ cabalArgs pkg @ (Package _ path _) todo @ (stage, dist, settings) = args , with Happy ] -- TODO: reorder with's ghcPkgArgs :: Package -> TodoItem -> Args -ghcPkgArgs (Package _ path _) (stage, dist, _) = return $ - [ "update" - , "--force" - , toStandard $ path dist "inplace-pkg-config" ] - ++ - [ "--package-db=libraries/bootstrapping.conf" | stage == Stage0 ] +ghcPkgArgs (Package _ path _) (stage, dist, _) = args $ + [ arg "update" + , arg "--force" + , arg $ toStandard $ path dist "inplace-pkg-config" + , when (stage == Stage0) bootPackageDb ] buildRule :: Package -> TodoItem -> Rules () buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = diff --git a/src/Targets.hs b/src/Targets.hs index 59fdbf1..3895bae 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -12,16 +12,18 @@ libraryPackagesInStage Stage0 = , "hoopl" , "hpc" , "transformers" ] -libraryPackagesInStage Stage1 = [] - --[ "array" - --, "deepseq" - --, "Cabal/Cabal" - --, "containers" - --, "filepath" - --, "parallel" - --, "pretty" - --, "stm" - --, "template-haskell" ] +libraryPackagesInStage Stage1 = + libraryPackagesInStage Stage0 ++ + [ "array" + , "deepseq" + , "Cabal/Cabal" + , "containers" + , "filepath" + , "parallel" + , "pretty" + , "stm" + , "template-haskell" ] + libraryPackagesInStage _ = [] libraryPackages :: [String] From git at git.haskell.org Thu Oct 26 23:24:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add NFData instances (bf75f42) Message-ID: <20171026232434.B60123A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf75f422b738ae95fb7d3b814d9335c77ef6d6cd/ghc >--------------------------------------------------------------- commit bf75f422b738ae95fb7d3b814d9335c77ef6d6cd Author: Ben Gamari Date: Wed Dec 16 01:27:04 2015 +0100 Add NFData instances >--------------------------------------------------------------- bf75f422b738ae95fb7d3b814d9335c77ef6d6cd src/Builder.hs | 1 + src/Package.hs | 1 + src/Stage.hs | 1 + src/Way.hs | 3 +++ 4 files changed, 6 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 67be69f..007dae3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -111,3 +111,4 @@ fixAbsolutePathOnWindows path = do -- Instances for storing in the Shake database instance Binary Builder instance Hashable Builder +instance NFData Builder diff --git a/src/Package.hs b/src/Package.hs index a490cb9..f64daee 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -49,3 +49,4 @@ instance Ord Package where instance Binary Package instance Hashable Package where hashWithSalt salt = hashWithSalt salt . show +instance NFData Package diff --git a/src/Stage.hs b/src/Stage.hs index f4e39b0..3aca206 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -13,3 +13,4 @@ instance Show Stage where -- Instances for storing in the Shake database instance Binary Stage instance Hashable Stage +instance NFData Stage diff --git a/src/Way.hs b/src/Way.hs index 7f1ca31..095bd52 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -169,3 +169,6 @@ instance Binary Way where instance Hashable Way where hashWithSalt salt = hashWithSalt salt . show + +instance NFData Way where + rnf (Way s) = s `seq` () From git at git.haskell.org Thu Oct 26 23:24:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build.sh for building on Posix platforms (525f966) Message-ID: <20171026232438.838C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/525f9668125f368584aa62a0d47e6bc8df23d8b4/ghc >--------------------------------------------------------------- commit 525f9668125f368584aa62a0d47e6bc8df23d8b4 Author: Ben Gamari Date: Wed Dec 16 01:28:13 2015 +0100 Add build.sh for building on Posix platforms >--------------------------------------------------------------- 525f9668125f368584aa62a0d47e6bc8df23d8b4 build.sh | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/build.sh b/build.sh new file mode 100755 index 0000000..cf217bd --- /dev/null +++ b/build.sh @@ -0,0 +1,6 @@ +#!/bin/bash -e + +root=`dirname $0` +mkdir -p $root/_shake +ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/_shake -o $root/_shake/build +$root/_shake/build --lint --directory $root/.. $@ From git at git.haskell.org Thu Oct 26 23:24:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up colourisation code. (a5a2fed) Message-ID: <20171026232438.277FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a2fed84493a7afa0942ba28a33b1ae9bc2a804/ghc >--------------------------------------------------------------- commit a5a2fed84493a7afa0942ba28a33b1ae9bc2a804 Author: Andrey Mokhov Date: Sat Jan 17 23:12:02 2015 +0000 Clean up colourisation code. >--------------------------------------------------------------- a5a2fed84493a7afa0942ba28a33b1ae9bc2a804 src/Config.hs | 6 ++---- src/Oracles/Builder.hs | 14 +++++++++----- src/Oracles/Flag.hs | 2 +- src/Util.hs | 16 ++++++++++------ 4 files changed, 22 insertions(+), 16 deletions(-) diff --git a/src/Config.hs b/src/Config.hs index dd5db2a..1a4ef9a 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -11,15 +11,13 @@ cfgPath = "shake" "cfg" autoconfRules :: Rules () autoconfRules = do "configure" %> \out -> do - need ["shake/src/Config.hs"] copyFile' (cfgPath "configure.ac") "configure.ac" - putColoured Vivid White $ "Running autoconf..." + putColoured White $ "Running autoconf..." cmd "bash autoconf" -- TODO: get rid of 'bash' configureRules :: Rules () configureRules = do cfgPath "default.config" %> \out -> do - need ["shake/src/Config.hs"] need [cfgPath "default.config.in", "configure"] - putColoured Vivid White "Running configure..." + putColoured White "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 3386b6f..13b8d7c 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -47,8 +47,8 @@ instance ShowArg Builder where GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" cfgPath <- askConfigWithDefault key $ - error $ "\nCannot find path to '" ++ key - ++ "' in configuration files." + redError $ "\nCannot find path to '" ++ key + ++ "' in configuration files." let cfgPathExe = if null cfgPath then "" else cfgPath -<.> exe windows <- windowsHost -- Note, below is different from FilePath.isAbsolute: @@ -104,20 +104,24 @@ run builder as = do -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. -- Raises an error if the builder is not uniquely specified in config files +-- TODO: make this a default 'run', rename current 'run' to verboseRun terseRun :: ShowArgs a => Builder -> a -> Action () terseRun builder as = do args <- showArgs as - putColoured Vivid White $ "/--------\n" ++ + putColoured White $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" - mapM_ (putColoured Vivid White . ("| " ++)) $ + mapM_ (putColoured White . ("| " ++)) $ interestingInfo builder args - putColoured Vivid White $ "\\--------" + putColoured White $ "\\--------" quietly $ run builder as interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of Ar -> prefixAndSuffix 2 1 ss Ld -> prefixAndSuffix 4 0 ss + Gcc -> if head ss == "-MM" + then prefixAndSuffix 1 1 ss + else ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss else prefixAndSuffix 0 4 ss diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 6339696..fa29415 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -41,7 +41,7 @@ test flag = do GhcUnregisterised -> ("ghc-unregisterised" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ -- TODO: warn just once - do putColoured Dull Red $ "\nFlag '" + do putColoured Red $ "\nFlag '" ++ key ++ "' not set in configuration files. " ++ "Proceeding with default value '" diff --git a/src/Util.hs b/src/Util.hs index 5bec54d..16728ce 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -3,13 +3,14 @@ module Util ( module System.Console.ANSI, replaceIf, replaceEq, replaceSeparators, chunksOfSize, - putColoured, redError + putColoured, redError, redError_ ) where import Base import Data.Char import System.Console.ANSI import System.IO +import Control.Monad replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -36,9 +37,9 @@ chunksOfSize size ss = reverse chunk : chunksOfSize size rest else (newChunk, rest) -- A more colourful version of Shake's putNormal -putColoured :: ColorIntensity -> Color -> String -> Action () -putColoured intensity colour msg = do - liftIO $ setSGR [SetColor Foreground intensity colour] +putColoured :: Color -> String -> Action () +putColoured colour msg = do + liftIO $ setSGR [SetColor Foreground Vivid colour] putNormal msg liftIO $ setSGR [] liftIO $ hFlush stdout @@ -46,5 +47,8 @@ putColoured intensity colour msg = do -- A more colourful version of error redError :: String -> Action a redError msg = do - putColoured Vivid Red msg - return $ error $ "GHC build system error: " ++ msg + putColoured Red msg + error $ "GHC build system error: " ++ msg + +redError_ :: String -> Action () +redError_ = void . redError From git at git.haskell.org Thu Oct 26 23:24:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add DependencyList oracle. (a644c32) Message-ID: <20171026232441.917FF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a644c3216b42e6a371f61b2e142df74cf457f51c/ghc >--------------------------------------------------------------- commit a644c3216b42e6a371f61b2e142df74cf457f51c Author: Andrey Mokhov Date: Sat Jan 17 23:13:04 2015 +0000 Add DependencyList oracle. >--------------------------------------------------------------- a644c3216b42e6a371f61b2e142df74cf457f51c src/Oracles.hs | 47 +++++++++++++++++++++++++++++++------------ src/Oracles/DependencyList.hs | 20 ++++++++++++++++++ 2 files changed, 54 insertions(+), 13 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 9ac6191..4c6d9e9 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -4,11 +4,14 @@ module Oracles ( module Oracles.Option, module Oracles.Builder, module Oracles.PackageData, + module Oracles.DependencyList, oracleRules ) where import Development.Shake.Config +import Development.Shake.Util import qualified Data.HashMap.Strict as M +import Data.Bifunctor import Base import Util import Config @@ -17,49 +20,67 @@ import Oracles.Flag import Oracles.Option import Oracles.Builder import Oracles.PackageData +import Oracles.DependencyList defaultConfig, userConfig :: FilePath defaultConfig = cfgPath "default.config" userConfig = cfgPath "user.config" --- Oracle for configuration files. +-- Oracle for configuration files configOracle :: Rules () configOracle = do cfg <- newCache $ \() -> do - unless (doesFileExist $ defaultConfig <.> "in") $ do - error $ "\nDefault configuration file '" - ++ (defaultConfig <.> "in") - ++ "' is missing; unwilling to proceed." - return () + unless (doesFileExist $ defaultConfig <.> "in") $ + redError_ $ "\nDefault configuration file '" + ++ (defaultConfig <.> "in") + ++ "' is missing; unwilling to proceed." need [defaultConfig] - putNormal $ "Parsing " ++ toStandard defaultConfig ++ "..." + putOracle $ "Parsing " ++ toStandard defaultConfig ++ "..." cfgDefault <- liftIO $ readConfigFile defaultConfig existsUser <- doesFileExist userConfig cfgUser <- if existsUser then do - putNormal $ "Parsing " + putOracle $ "Parsing " ++ toStandard userConfig ++ "..." liftIO $ readConfigFile userConfig else do - putColoured Dull Red $ + putColoured Red $ "\nUser defined configuration file '" ++ userConfig ++ "' is missing; " ++ "proceeding with default configuration.\n" return M.empty - putColoured Vivid Green $ "Finished processing configuration files." + putColoured Green $ "Finished processing configuration files." return $ cfgUser `M.union` cfgDefault addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () return () --- Oracle for 'package-data.mk' files. +-- Oracle for 'package-data.mk' files packageDataOracle :: Rules () packageDataOracle = do pkgData <- newCache $ \file -> do need [file] - putNormal $ "Parsing " ++ toStandard file ++ "..." + putOracle $ "Parsing " ++ toStandard file ++ "..." liftIO $ readConfigFile file addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () +-- Oracle for 'path/dist/*.deps' files +dependencyOracle :: Rules () +dependencyOracle = do + deps <- newCache $ \depFile -> do + need [depFile] + putOracle $ "Parsing " ++ toStandard depFile ++ "..." + contents <- parseMakefile <$> (liftIO $ readFile depFile) + return $ M.fromList + $ map (bimap head concat . unzip) + $ groupBy ((==) `on` fst) + $ sortBy (compare `on` fst) contents + addOracle $ \(DependencyListKey (file, obj)) -> M.lookup obj <$> deps file + return () + oracleRules :: Rules () -oracleRules = configOracle <> packageDataOracle +oracleRules = configOracle <> packageDataOracle <> dependencyOracle + +-- Make oracle's output more distinguishable +putOracle :: String -> Action () +putOracle = putColoured Blue diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs new file mode 100644 index 0000000..8f4eda1 --- /dev/null +++ b/src/Oracles/DependencyList.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} + +module Oracles.DependencyList ( + DependencyList (..), + DependencyListKey (..) + ) where + +import Development.Shake.Classes +import Base +import Data.Maybe + +data DependencyList = DependencyList FilePath FilePath + +newtype DependencyListKey = DependencyListKey (FilePath, FilePath) + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +instance ShowArgs DependencyList where + showArgs (DependencyList file obj) = do + res <- askOracle $ DependencyListKey (file, obj) + return $ fromMaybe [] res From git at git.haskell.org Thu Oct 26 23:24:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: deriveConstants now has a Cabal file (c0f3b67) Message-ID: <20171026232441.EAF3A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c0f3b6709468744f8192171b94ab08d2c1010959/ghc >--------------------------------------------------------------- commit c0f3b6709468744f8192171b94ab08d2c1010959 Author: Ben Gamari Date: Wed Dec 16 02:19:26 2015 +0100 deriveConstants now has a Cabal file Since 314395e00be10e6343840c215a4779aeec2542df >--------------------------------------------------------------- c0f3b6709468744f8192171b94ab08d2c1010959 src/Rules/Compile.hs | 5 ----- src/Rules/Data.hs | 12 +----------- 2 files changed, 1 insertion(+), 16 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 60123ef..9f718eb 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -28,11 +28,6 @@ compilePackage _ target @ (PartialTarget stage pkg) = do build $ fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases - priority 2.0 $ buildPath -/- "DeriveConstants.o" %> \obj -> do - let src = pkgPath pkg -/- "DeriveConstants.hs" - need [src] - build $ fullTargetWithWay target (Ghc stage) vanilla [src] [obj] - priority 2.0 $ buildPath -/- "GenApply.o" %> \obj -> do let src = pkgPath pkg -/- "GenApply.hs" need [src] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index cba8b69..2898257 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (deriveConstants, genapply, genprimopcode, hp2ps) +import GHC (genapply, genprimopcode, hp2ps) import Oracles import Predicates (registerPackage) import Rules.Actions @@ -50,16 +50,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- TODO: Track dependency on this generated file -- TODO: Use a cabal file instead of manual hacks? priority 2.0 $ - when (pkg == deriveConstants) $ path -/- "package-data.mk" %> \mk -> do - let contents = unlines - [ "utils_deriveConstants_dist-boot_MODULES = DeriveConstants" - , "utils_deriveConstants_dist-boot_PROGNAME = deriveConstants" - , "utils_deriveConstants_dist-boot_HS_SRC_DIRS = ." - , "utils_deriveConstants_dist-boot_INSTALL_INPLACE = YES" - , "utils_deriveConstants_dist-boot_HC_OPTS = -package process -package containers" ] - writeFileChanged mk contents - - priority 2.0 $ when (pkg == genapply) $ path -/- "package-data.mk" %> \mk -> do ghcUnreg <- flag GhcUnregisterised let hcOpts = "-package pretty" ++ if ghcUnreg then " -DNO_REGS" else "" From git at git.haskell.org Thu Oct 26 23:24:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CcArgs and CSrcs keys to PackageData. (316d98e) Message-ID: <20171026232445.21C263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/316d98ef5bf6a5e43c649f5a7269661ff304be96/ghc >--------------------------------------------------------------- commit 316d98ef5bf6a5e43c649f5a7269661ff304be96 Author: Andrey Mokhov Date: Sat Jan 17 23:14:03 2015 +0000 Add CcArgs and CSrcs keys to PackageData. >--------------------------------------------------------------- 316d98ef5bf6a5e43c649f5a7269661ff304be96 src/Oracles/PackageData.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 192896c..0581e82 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -31,6 +31,8 @@ data MultiPackageData = Modules FilePath | DepNames FilePath | CppArgs FilePath | HsArgs FilePath + | CcArgs FilePath + | CSrcs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -59,6 +61,8 @@ instance ShowArgs MultiPackageData where DepNames path -> ("DEP_NAMES" , path, "" ) CppArgs path -> ("CPP_OPTS" , path, "" ) HsArgs path -> ("HC_OPTS" , path, "" ) + CcArgs path -> ("CC_OPTS" , path, "" ) + CSrcs path -> ("C_SRCS" , path, "" ) fullKey = replaceSeparators '_' $ path ++ "_" ++ key pkgData = path "package-data.mk" res <- askOracle $ PackageDataKey (pkgData, fullKey) From git at git.haskell.org Thu Oct 26 23:24:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: LIB_NAME, PACKAGE_KEY are now COMPONENT_ID (4758a21) Message-ID: <20171026232445.65D1D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4758a21d2a9441d5dadf9b40b578c2c8e55773e8/ghc >--------------------------------------------------------------- commit 4758a21d2a9441d5dadf9b40b578c2c8e55773e8 Author: Ben Gamari Date: Wed Dec 16 01:56:05 2015 +0100 LIB_NAME, PACKAGE_KEY are now COMPONENT_ID Since GHC commit 6338a1cc6df2c7fd8a62eeb4c5240dd90ee74a6c. >--------------------------------------------------------------- 4758a21d2a9441d5dadf9b40b578c2c8e55773e8 cfg/system.config.in | 12 ++++++------ src/Oracles/Config/Flag.hs | 4 ++-- src/Oracles/PackageData.hs | 6 ++---- src/Rules.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 16 ++++++++-------- 5 files changed, 21 insertions(+), 23 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 09ea1fa..60dae28 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -45,12 +45,12 @@ ar-supports-at-file = @ArSupportsAtFile@ # Build options: #=============== -supports-package-key = @SUPPORTS_PACKAGE_KEY@ -solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ -split-objects-broken = @SplitObjsBroken@ -ghc-unregisterised = @Unregisterised@ -ghc-source-path = @hardtop@ -leading-underscore = @LeadingUnderscore@ +supports-component-id = @SUPPORTS_COMPONENT_ID@ +solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ +split-objects-broken = @SplitObjsBroken@ +ghc-unregisterised = @Unregisterised@ +ghc-source-path = @hardtop@ +leading-underscore = @LeadingUnderscore@ # Information about build, host and target systems: #================================================== diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index f352ae3..631a6fc 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -16,7 +16,7 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken - | SupportsPackageKey + | SupportsComponentId -- Note, if a flag is set to empty string we treat it as set to NO. This seems -- fragile, but some flags do behave like this, e.g. GccIsClang. @@ -31,7 +31,7 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" - SupportsPackageKey -> "supports-package-key" + SupportsComponentId -> "supports-component-id" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." unless (value == "YES" || value == "NO" || value == "") . putError diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index e4aae0a..8a067b9 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -16,8 +16,7 @@ import qualified Data.HashMap.Strict as Map -- such as 'path_MODULES = Data.Array Data.Array.Base ...'. -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] data PackageData = BuildGhciLib FilePath - | LibName FilePath - | PackageKey FilePath + | ComponentId FilePath | Synopsis FilePath | Version FilePath @@ -55,8 +54,7 @@ askPackageData path key = do pkgData :: PackageData -> Action String pkgData packageData = case packageData of BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" - LibName path -> askPackageData path "LIB_NAME" - PackageKey path -> askPackageData path "PACKAGE_KEY" + ComponentId path -> askPackageData path "COMPONENT_ID" Synopsis path -> askPackageData path "SYNOPSIS" Version path -> askPackageData path "VERSION" diff --git a/src/Rules.hs b/src/Rules.hs index 2a6bd59..90769c1 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -16,15 +16,15 @@ generateTargets = action $ do libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg buildPath = targetPath stage pkg -/- "build" - libName <- interpretPartial target $ getPkgData LibName + compId <- interpretPartial target $ getPkgData ComponentId needGhciLib <- interpretPartial target $ getPkgData BuildGhciLib needHaddock <- interpretPartial target buildHaddock ways <- interpretPartial target getWays - let ghciLib = buildPath -/- "HS" ++ libName <.> "o" + let ghciLib = buildPath -/- "HS" ++ compId <.> "o" haddock = pkgHaddockFile pkg libs <- fmap concat . forM ways $ \way -> do extension <- libsuf way - let name = buildPath -/- "libHS" ++ libName + let name = buildPath -/- "libHS" ++ compId dll0 <- needDll0 stage pkg return $ [ name <.> extension ] ++ [ name ++ "-0" <.> extension | dll0 ] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 247a114..50973c0 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -91,11 +91,11 @@ wayGhcArgs = do -- TODO: Improve handling of "-hide-all-packages" packageGhcArgs :: Args packageGhcArgs = do - stage <- getStage - pkg <- getPackage - supportsPackageKey <- getFlag SupportsPackageKey - pkgKey <- getPkgData PackageKey - pkgDepIds <- getPkgDataList DepIds + stage <- getStage + pkg <- getPackage + supportsComponentId <- getFlag SupportsComponentId + compId <- getPkgData ComponentId + pkgDepIds <- getPkgDataList DepIds mconcat [ not (pkg == deriveConstants || pkg == genapply || pkg == genprimopcode || pkg == hp2ps) ? @@ -103,9 +103,9 @@ packageGhcArgs = do , arg "-no-user-package-db" , stage0 ? arg "-package-db libraries/bootstrapping.conf" , isLibrary pkg ? - if supportsPackageKey || stage /= Stage0 - then arg $ "-this-package-key " ++ pkgKey - else arg $ "-package-name " ++ pkgKey + if supportsComponentId || stage /= Stage0 + then arg $ "-this-package-key " ++ compId + else arg $ "-package-name " ++ compId , append $ map ("-package-id " ++) pkgDepIds ] -- TODO: Improve handling of "cabal_macros.h" From git at git.haskell.org Thu Oct 26 23:24:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for c source files. (debca7a) Message-ID: <20171026232448.BAC0B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/debca7ade35a75b7d5947f0abeb3a9a190d2e0f7/ghc >--------------------------------------------------------------- commit debca7ade35a75b7d5947f0abeb3a9a190d2e0f7 Author: Andrey Mokhov Date: Sat Jan 17 23:14:40 2015 +0000 Add support for c source files. >--------------------------------------------------------------- debca7ade35a75b7d5947f0abeb3a9a190d2e0f7 src/Package/Base.hs | 32 +++++++++++++-------- src/Package/Compile.hs | 49 ++++++++++++++++++++++++------- src/Package/Dependencies.hs | 70 +++++++++++++++++++++++++++++++++++++++------ src/Package/Library.hs | 29 ++++++++++--------- src/Targets.hs | 36 +++++++++++------------ src/Ways.hs | 1 + 6 files changed, 154 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc debca7ade35a75b7d5947f0abeb3a9a190d2e0f7 From git at git.haskell.org Thu Oct 26 23:24:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add configuration for libdw (96d66f0) Message-ID: <20171026232448.ED80A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/96d66f0c27df839072ee01555fa98529e3be6ef9/ghc >--------------------------------------------------------------- commit 96d66f0c27df839072ee01555fa98529e3be6ef9 Author: Ben Gamari Date: Wed Dec 16 02:42:11 2015 +0100 Add configuration for libdw >--------------------------------------------------------------- 96d66f0c27df839072ee01555fa98529e3be6ef9 cfg/system.config.in | 6 ++++++ src/Oracles/Config/Flag.hs | 2 ++ src/Rules/Generate.hs | 5 ++++- 3 files changed, 12 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 60dae28..9de3166 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -116,3 +116,9 @@ iconv-lib-dirs = @ICONV_LIB_DIRS@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ + + +# Optional Dependencies: +#======================= + +with-libdw = @HaveLibdw@ diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 631a6fc..47ea75d 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -17,6 +17,7 @@ data Flag = ArSupportsAtFile | SolarisBrokenShld | SplitObjectsBroken | SupportsComponentId + | WithLibdw -- Note, if a flag is set to empty string we treat it as set to NO. This seems -- fragile, but some flags do behave like this, e.g. GccIsClang. @@ -32,6 +33,7 @@ flag f = do SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" SupportsComponentId -> "supports-component-id" + WithLibdw -> "with-libdw" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." unless (value == "YES" || value == "NO" || value == "") . putError diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 069d88f..53b7dd6 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -106,6 +106,7 @@ generateConfigHs = do cGHC_SPLIT_PGM <- fmap takeBaseName $ getBuilderPath GhcSplit cLibFFI <- lift useLibFFIForAdjustors rtsWays <- getRtsWays + cGhcRtsWithLibdw <- getFlag WithLibdw let cGhcRTSWays = unwords $ map show rtsWays return $ unlines [ "{-# LANGUAGE CPP #-}" @@ -169,7 +170,9 @@ generateConfigHs = do , "cGhcThreaded :: Bool" , "cGhcThreaded = " ++ show (threaded `elem` rtsWays) , "cGhcDebugged :: Bool" - , "cGhcDebugged = " ++ show ghcDebugged ] + , "cGhcDebugged = " ++ show ghcDebugged + , "cGhcRtsWithLibdw :: Bool" + , "cGhcRtsWithLibdw = " ++ show cGhcRtsWithLibdw ] generatePlatformH :: Expr String generatePlatformH = do From git at git.haskell.org Thu Oct 26 23:24:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename includeHcArgs to includeGhcArgs. (734994c) Message-ID: <20171026232452.920CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/734994cf18ee377472128ceab7ad6ef1f8773684/ghc >--------------------------------------------------------------- commit 734994cf18ee377472128ceab7ad6ef1f8773684 Author: Andrey Mokhov Date: Sat Jan 17 23:31:52 2015 +0000 Rename includeHcArgs to includeGhcArgs. >--------------------------------------------------------------- 734994cf18ee377472128ceab7ad6ef1f8773684 src/Package/Base.hs | 6 +++--- src/Package/Compile.hs | 2 +- src/Package/Dependencies.hs | 6 +----- 3 files changed, 5 insertions(+), 9 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 0b053e8..9d75e04 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -7,7 +7,7 @@ module Package.Base ( Package (..), Settings (..), TodoItem (..), defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - pathArgs, packageArgs, includeHcArgs, pkgHsSources, + pathArgs, packageArgs, includeGhcArgs, pkgHsSources, pkgDepHsObjects, pkgLibHsObjects, pkgCObjects, argSizeLimit, sourceDependecies, @@ -92,8 +92,8 @@ packageArgs stage pathDist = do else productArgs "-package-name" (arg $ PackageKey pathDist) <> productArgs "-package" (args $ Deps pathDist) ] -includeHcArgs :: FilePath -> FilePath -> Args -includeHcArgs path dist = +includeGhcArgs :: FilePath -> FilePath -> Args +includeGhcArgs path dist = let pathDist = path dist buildDir = toStandard $ pathDist "build" in args [ arg "-i" diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 0c25ae8..8052356 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -18,7 +18,7 @@ ghcArgs (Package _ path _) (stage, dist, _) way srcs result = , wayHcArgs way , args SrcHcArgs , packageArgs stage pathDist - , includeHcArgs path dist + , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist , args $ HsArgs pathDist -- TODO: now we have both -O and -O2 diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 7378f20..7301051 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -13,7 +13,7 @@ ghcArgs (Package name path _) (stage, dist, settings) = depFile = buildDir "haskell.deps" in args [ arg "-M" , packageArgs stage pathDist - , includeHcArgs path dist + , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist , productArgs ["-odir", "-stubdir", "-hidir"] buildDir , args ["-dep-makefile", depFile <.> "new"] @@ -21,10 +21,6 @@ ghcArgs (Package name path _) (stage, dist, settings) = , args $ HsArgs pathDist , args $ pkgHsSources path dist ] --- $(CPP) $($1_$2_MKDEPENDC_OPTS) --- $($1_$2_$(firstword $($1_$2_WAYS))_ALL_CC_OPTS) --- $($(basename $4)_CC_OPTS) -MM -x c $4 -MF $3.bit --- -- $1_$2_$3_ALL_CC_OPTS = \ -- $$(WAY_$3_CC_OPTS) \ -- $$($1_$2_DIST_GCC_CC_OPTS) \ From git at git.haskell.org Thu Oct 26 23:24:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GHC: bin-package-db is now ghc-boot (73b4605) Message-ID: <20171026232452.BC8BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73b460528b96ce7c6c056d25dee9c7e50924f59c/ghc >--------------------------------------------------------------- commit 73b460528b96ce7c6c056d25dee9c7e50924f59c Author: Ben Gamari Date: Wed Dec 16 01:32:59 2015 +0100 GHC: bin-package-db is now ghc-boot >--------------------------------------------------------------- 73b460528b96ce7c6c056d25dee9c7e50924f59c src/GHC.hs | 8 ++++---- src/Settings/Packages.hs | 2 +- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index ea48014..30414db 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,5 +1,5 @@ module GHC ( - array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, + array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, @@ -20,7 +20,7 @@ import Stage -- which can be overridden in Settings/User.hs. defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, binPackageDb, binary, bytestring, cabal, compiler + [ array, base, ghcBoot, binary, bytestring, cabal, compiler , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit , filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin @@ -29,7 +29,7 @@ defaultKnownPackages = , win32, xhtml ] -- Package definitions (see Package.hs) -array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, +array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, @@ -38,7 +38,7 @@ array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, array = library "array" base = library "base" -binPackageDb = library "bin-package-db" +ghcBoot = library "ghc-boot" binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 80fc202..febb254 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -18,7 +18,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg + [ append [ ghcBoot, binary, cabal, compiler, ghc, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] , stage0 ? append [deriveConstants, genapply, genprimopcode, hp2ps] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] From git at git.haskell.org Thu Oct 26 23:24:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add stage parameter to Gcc builder. Clean up. (d6744a7) Message-ID: <20171026232456.6938E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6744a706e0ed263c6f67a3f2a668363ddaa36c5/ghc >--------------------------------------------------------------- commit d6744a706e0ed263c6f67a3f2a668363ddaa36c5 Author: Andrey Mokhov Date: Sun Jan 18 00:09:45 2015 +0000 Add stage parameter to Gcc builder. Clean up. >--------------------------------------------------------------- d6744a706e0ed263c6f67a3f2a668363ddaa36c5 cfg/default.config.in | 33 +++++++++++++++++---------------- src/Oracles/Base.hs | 3 ++- src/Oracles/Builder.hs | 9 +++++---- src/Oracles/Option.hs | 2 +- src/Package/Compile.hs | 10 ++++++++-- src/Package/Data.hs | 8 ++++---- src/Package/Dependencies.hs | 4 ++-- 7 files changed, 39 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 d6744a706e0ed263c6f67a3f2a668363ddaa36c5 From git at git.haskell.org Thu Oct 26 23:24:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Dependencies: Use msum instead of explicit pattern matching (1c8539d) Message-ID: <20171026232456.862083A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c8539dfd3761a3a69d9514d58e3e196127661a3/ghc >--------------------------------------------------------------- commit 1c8539dfd3761a3a69d9514d58e3e196127661a3 Author: Ben Gamari Date: Wed Dec 16 16:35:24 2015 +0100 Dependencies: Use msum instead of explicit pattern matching >--------------------------------------------------------------- 1c8539dfd3761a3a69d9514d58e3e196127661a3 src/Oracles/Dependencies.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index d0f926d..c27c2cc 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -2,6 +2,7 @@ module Oracles.Dependencies (dependencies, dependenciesOracle) where import Base +import Control.Monad.Trans.Maybe import qualified Data.HashMap.Strict as Map newtype DependenciesKey = DependenciesKey (FilePath, FilePath) @@ -16,12 +17,11 @@ newtype DependenciesKey = DependenciesKey (FilePath, FilePath) dependencies :: FilePath -> FilePath -> Action (FilePath, [FilePath]) dependencies path obj = do let depFile = path -/- ".dependencies" - res1 <- askOracle $ DependenciesKey (depFile, obj) - -- if no dependencies found attempt to drop the way prefix (for *.c sources) - res2 <- case res1 of - Nothing -> askOracle $ DependenciesKey (depFile, obj -<.> "o") - _ -> return res1 - case res2 of + -- if no dependencies found then attempt to drop the way prefix (for *.c sources) + res <- runMaybeT $ msum + $ map (\obj' -> MaybeT $ askOracle $ DependenciesKey (depFile, obj')) + [obj, obj -<.> "o"] + case res of Nothing -> putError $ "No dependencies found for '" ++ obj ++ "'." Just [] -> putError $ "Empty dependency list for '" ++ obj ++ "'." Just (src:depFiles) -> return (src, depFiles) From git at git.haskell.org Thu Oct 26 23:24:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:24:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up rules related to dependency lists. (7d42fda) Message-ID: <20171026232459.F22B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d42fdac5a5574825124b250e3db0287cab8c417/ghc >--------------------------------------------------------------- commit 7d42fdac5a5574825124b250e3db0287cab8c417 Author: Andrey Mokhov Date: Sun Jan 18 12:45:23 2015 +0000 Clean up rules related to dependency lists. >--------------------------------------------------------------- 7d42fdac5a5574825124b250e3db0287cab8c417 src/Package/Compile.hs | 2 +- src/Package/Dependencies.hs | 14 ++++++-------- 2 files changed, 7 insertions(+), 9 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 0cdb62c..1155117 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -48,7 +48,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = let oPattern = "*." ++ osuf way let hiPattern = "*." ++ hisuf way [buildDir oPattern, buildDir hiPattern] |%> \out -> do - need [argListPath argListDir pkg stage, hDepFile, cDepFile] + need [argListPath argListDir pkg stage] let obj = toStandard $ out -<.> osuf way vanillaObj = toStandard $ out -<.> "o" -- TODO: keep only vanilla dependencies in hDepFile diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 08bb9e5..31c8d92 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -16,7 +16,7 @@ ghcArgs (Package name path _) (stage, dist, settings) = , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist , productArgs ["-odir", "-stubdir", "-hidir"] buildDir - , args ["-dep-makefile", depFile <.> "new"] + , args ["-dep-makefile", depFile ] , productArgs "-dep-suffix" $ map wayPrefix <$> ways settings , args $ HsArgs pathDist , args $ pkgHsSources path dist ] @@ -60,19 +60,17 @@ buildRule :: Package -> TodoItem -> Rules () buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do let pathDist = path dist buildDir = pathDist "build" - hDepFile = buildDir "haskell.deps" - cDepFile = buildDir "c.deps" - hDepFile %> \out -> do + (buildDir "haskell.deps") %> \out -> do need [argListPath argListDir pkg stage] terseRun (Ghc stage) $ ghcArgs pkg todo -- Avoid rebuilding dependecies of out if it hasn't changed: -- Note: cannot use copyFileChanged as it depends on the source file - deps <- liftIO $ readFile $ out <.> "new" - writeFileChanged out deps - liftIO $ removeFiles "." [out <.> "new"] + --deps <- liftIO $ readFile $ out <.> "new" + --writeFileChanged out deps + --liftIO $ removeFiles "." [out <.> "new"] - cDepFile %> \out -> do + (buildDir "c.deps") %> \out -> do need [argListPath argListDir pkg stage] srcs <- args $ CSrcs pathDist deps <- fmap concat $ forM srcs $ \src -> do From git at git.haskell.org Thu Oct 26 23:25:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: genprimopcode also has a Cabal file (5ff0907) Message-ID: <20171026232500.25C153A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ff090768598e587c5ab617e25844911944e79ad/ghc >--------------------------------------------------------------- commit 5ff090768598e587c5ab617e25844911944e79ad Author: Ben Gamari Date: Wed Dec 16 03:17:23 2015 +0100 genprimopcode also has a Cabal file As of GHC commit 314395e00be10e6343840c215a4779aeec2542df. >--------------------------------------------------------------- 5ff090768598e587c5ab617e25844911944e79ad src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 363d804..95ac426 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (genprimopcode, hp2ps) +import GHC (hp2ps) import Oracles import Predicates (registerPackage) import Rules.Actions From git at git.haskell.org Thu Oct 26 23:25:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename (run, terseRun) to (verboseRun, run). (9e247b0) Message-ID: <20171026232503.CE6293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e247b0618357bdca4b0218de19e2eb7f9f23b63/ghc >--------------------------------------------------------------- commit 9e247b0618357bdca4b0218de19e2eb7f9f23b63 Author: Andrey Mokhov Date: Sun Jan 18 12:50:13 2015 +0000 Rename (run, terseRun) to (verboseRun, run). >--------------------------------------------------------------- 9e247b0618357bdca4b0218de19e2eb7f9f23b63 src/Oracles/Builder.hs | 15 ++++++--------- src/Package/Compile.hs | 4 ++-- src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 9 ++------- src/Package/Library.hs | 4 ++-- 5 files changed, 14 insertions(+), 22 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 1dcc797..e52cc58 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, terseRun, specified + with, run, verboseRun, specified ) where import Data.Char @@ -94,9 +94,8 @@ with builder = do return [key ++ exe] -- Run the builder with a given collection of arguments --- Raises an error if the builder is not uniquely specified in config files -run :: ShowArgs a => Builder -> a -> Action () -run builder as = do +verboseRun :: ShowArgs a => Builder -> a -> Action () +verboseRun builder as = do needBuilder builder exe <- showArg builder args <- showArgs as @@ -104,17 +103,15 @@ run builder as = do -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. --- Raises an error if the builder is not uniquely specified in config files --- TODO: make this a default 'run', rename current 'run' to verboseRun -terseRun :: ShowArgs a => Builder -> a -> Action () -terseRun builder as = do +run :: ShowArgs a => Builder -> a -> Action () +run builder as = do args <- showArgs as putColoured White $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" mapM_ (putColoured White . ("| " ++)) $ interestingInfo builder args putColoured White $ "\\--------" - quietly $ run builder as + quietly $ verboseRun builder as interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 1155117..e0080f9 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -66,9 +66,9 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = -- Build using appropriate compiler need $ hDeps ++ cDeps when (not $ null hSrcs) - $ terseRun (Ghc stage) $ ghcArgs pkg todo way hSrcs obj + $ run (Ghc stage) $ ghcArgs pkg todo way hSrcs obj when (not $ null cSrcs) - $ terseRun (Gcc stage) $ gccArgs pkg todo cSrcs obj + $ run (Gcc stage) $ gccArgs pkg todo cSrcs obj argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, settings) = diff --git a/src/Package/Data.hs b/src/Package/Data.hs index a3f0936..91f0b2d 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -124,9 +124,9 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = ] &%> \_ -> do need [argListPath argListDir pkg stage, cabal] when (doesFileExist $ configure <.> "ac") $ need [configure] - terseRun GhcCabal $ cabalArgs pkg todo + run GhcCabal $ cabalArgs pkg todo when (registerPackage settings) $ - terseRun (GhcPkg stage) $ ghcPkgArgs pkg todo + run (GhcPkg stage) $ ghcPkgArgs pkg todo postProcessPackageData $ pathDist "package-data.mk" argListRule :: Package -> TodoItem -> Rules () diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 31c8d92..d1a8a14 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -63,12 +63,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do (buildDir "haskell.deps") %> \out -> do need [argListPath argListDir pkg stage] - terseRun (Ghc stage) $ ghcArgs pkg todo - -- Avoid rebuilding dependecies of out if it hasn't changed: - -- Note: cannot use copyFileChanged as it depends on the source file - --deps <- liftIO $ readFile $ out <.> "new" - --writeFileChanged out deps - --liftIO $ removeFiles "." [out <.> "new"] + run (Ghc stage) $ ghcArgs pkg todo (buildDir "c.deps") %> \out -> do need [argListPath argListDir pkg stage] @@ -76,7 +71,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do deps <- fmap concat $ forM srcs $ \src -> do let srcPath = path src depFile = buildDir takeFileName src <.> "deps" - terseRun (Gcc stage) $ gccArgs srcPath pkg todo + run (Gcc stage) $ gccArgs srcPath pkg todo liftIO $ readFile depFile writeFileChanged out deps liftIO $ removeFiles buildDir ["*.c.deps"] diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 2b82260..e5fa0b8 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -25,7 +25,7 @@ arRule pkg @ (Package _ path _) todo @ (stage, dist, _) = -- Splitting argument list into chunks as otherwise Ar chokes up maxChunk <- argSizeLimit forM_ (chunksOfSize maxChunk $ libHsObjs ++ cObjs) $ \os -> do - terseRun Ar $ arArgs os $ toStandard out + run Ar $ arArgs os $ toStandard out ldArgs :: Package -> TodoItem -> FilePath -> Args ldArgs (Package _ path _) (stage, dist, _) result = do @@ -45,7 +45,7 @@ ldRule pkg @ (Package name path _) todo @ (stage, dist, _) = in priority 2 $ (buildDir "*.o") %> \out -> do need [argListPath argListDir pkg stage] - terseRun Ld $ ldArgs pkg todo $ toStandard out + run Ld $ ldArgs pkg todo $ toStandard out synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) putColoured Green $ "/--------\n| Successfully built package " ++ name ++ " (stage " ++ show stage ++ ")." From git at git.haskell.org Thu Oct 26 23:25:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: genapply now has a Cabal build (c525470) Message-ID: <20171026232504.0E06A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5254701040d51590fd9f26cbff566be49ee3d58/ghc >--------------------------------------------------------------- commit c5254701040d51590fd9f26cbff566be49ee3d58 Author: Ben Gamari Date: Wed Dec 16 03:13:51 2015 +0100 genapply now has a Cabal build >--------------------------------------------------------------- c5254701040d51590fd9f26cbff566be49ee3d58 src/Rules/Compile.hs | 5 ----- src/Rules/Data.hs | 26 +------------------------- 2 files changed, 1 insertion(+), 30 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 9f718eb..6b81a47 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -28,11 +28,6 @@ compilePackage _ target @ (PartialTarget stage pkg) = do build $ fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases - priority 2.0 $ buildPath -/- "GenApply.o" %> \obj -> do - let src = pkgPath pkg -/- "GenApply.hs" - need [src] - build $ fullTargetWithWay target (Ghc stage) vanilla [src] [obj] - matchBuildResult buildPath "o-boot" ?> \obj -> do (src, deps) <- dependencies buildPath obj need $ src : deps diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 2898257..363d804 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (genapply, genprimopcode, hp2ps) +import GHC (genprimopcode, hp2ps) import Oracles import Predicates (registerPackage) import Rules.Actions @@ -47,30 +47,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do postProcessPackageData $ path -/- "package-data.mk" - -- TODO: Track dependency on this generated file - -- TODO: Use a cabal file instead of manual hacks? - priority 2.0 $ - when (pkg == genapply) $ path -/- "package-data.mk" %> \mk -> do - ghcUnreg <- flag GhcUnregisterised - let hcOpts = "-package pretty" ++ if ghcUnreg then " -DNO_REGS" else "" - contents = unlines - [ "utils_genapply_dist-boot_MODULES = GenApply" - , "utils_genapply_dist-boot_PROGNAME = genapply" - , "utils_genapply_dist-boot_HS_SRC_DIRS = ." - , "utils_genapply_dist-boot_INSTALL_INPLACE = YES" - , "utils_genapply_dist-boot_HC_OPTS = " ++ hcOpts ] - writeFileChanged mk contents - - priority 2.0 $ - when (pkg == genprimopcode) $ path -/- "package-data.mk" %> \mk -> do - let contents = unlines - [ "utils_genprimopcode_dist-boot_MODULES = Lexer Main ParserM Parser Syntax" - , "utils_genprimopcode_dist-boot_PROGNAME = genprimopcode" - , "utils_genprimopcode_dist-boot_HS_SRC_DIRS = ." - , "utils_genprimopcode_dist-boot_INSTALL_INPLACE = YES" - , "utils_genprimopcode_dist-boot_HC_OPTS = -package array" ] - writeFileChanged mk contents - -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps -- TODO: code duplication around ghcIncludeDirs -- TODO: now using DEP_EXTRA_LIBS instead of EXTRA_LIBRARIES From git at git.haskell.org Thu Oct 26 23:25:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split compile rules for {hi, o}, clean up code. (3344cea) Message-ID: <20171026232508.0E4CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3344ceadaa807de7708c9444b1a71537fa0a7fdd/ghc >--------------------------------------------------------------- commit 3344ceadaa807de7708c9444b1a71537fa0a7fdd Author: Andrey Mokhov Date: Sun Jan 18 13:34:58 2015 +0000 Split compile rules for {hi, o}, clean up code. >--------------------------------------------------------------- 3344ceadaa807de7708c9444b1a71537fa0a7fdd src/Oracles.hs | 12 +++++++----- src/Package/Compile.hs | 15 ++++++++++----- 2 files changed, 17 insertions(+), 10 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 4c6d9e9..215ccb7 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -67,15 +67,17 @@ packageDataOracle = do -- Oracle for 'path/dist/*.deps' files dependencyOracle :: Rules () dependencyOracle = do - deps <- newCache $ \depFile -> do - need [depFile] - putOracle $ "Parsing " ++ toStandard depFile ++ "..." - contents <- parseMakefile <$> (liftIO $ readFile depFile) + deps <- newCache $ \file -> do + need [file] + putOracle $ "Parsing " ++ file ++ "..." + contents <- parseMakefile <$> (liftIO $ readFile file) return $ M.fromList + $ map (bimap toStandard (map toStandard)) $ map (bimap head concat . unzip) $ groupBy ((==) `on` fst) $ sortBy (compare `on` fst) contents - addOracle $ \(DependencyListKey (file, obj)) -> M.lookup obj <$> deps file + addOracle $ \(DependencyListKey (file, obj)) -> + M.lookup (toStandard obj) <$> deps (toStandard file) return () oracleRules :: Rules () diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index e0080f9..762f533 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -47,10 +47,14 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = forM_ allWays $ \way -> do -- TODO: optimise (too many ways in allWays) let oPattern = "*." ++ osuf way let hiPattern = "*." ++ hisuf way - [buildDir oPattern, buildDir hiPattern] |%> \out -> do + + (buildDir hiPattern) %> \out -> do + let obj = out -<.> osuf way + need [obj] + + (buildDir oPattern) %> \obj -> do need [argListPath argListDir pkg stage] - let obj = toStandard $ out -<.> osuf way - vanillaObj = toStandard $ out -<.> "o" + let vanillaObj = obj -<.> "o" -- TODO: keep only vanilla dependencies in hDepFile hDeps <- args $ DependencyList hDepFile obj cDeps <- args $ DependencyList cDepFile $ takeFileName vanillaObj @@ -59,10 +63,10 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = -- Report impossible cases when (null $ hSrcs ++ cSrcs) $ redError_ $ "No source files found for " - ++ toStandard out ++ "." + ++ toStandard obj ++ "." when (not (null hSrcs) && not (null cSrcs)) $ redError_ $ "Both c and Haskell sources found for " - ++ toStandard out ++ "." + ++ toStandard obj ++ "." -- Build using appropriate compiler need $ hDeps ++ cDeps when (not $ null hSrcs) @@ -70,6 +74,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = when (not $ null cSrcs) $ run (Gcc stage) $ gccArgs pkg todo cSrcs obj + argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, settings) = (argListPath argListDir pkg stage) %> \out -> do From git at git.haskell.org Thu Oct 26 23:25:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add remote GHCi libraries (0afdf64) Message-ID: <20171026232508.33B793A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0afdf642a4a9209c578ddd8dd84cd2886bcd6e77/ghc >--------------------------------------------------------------- commit 0afdf642a4a9209c578ddd8dd84cd2886bcd6e77 Author: Ben Gamari Date: Fri Dec 18 12:27:16 2015 +0100 Add remote GHCi libraries See GHC commit 4905b83a2d448c65ccced385343d4e8124548a3b. >--------------------------------------------------------------- 0afdf642a4a9209c578ddd8dd84cd2886bcd6e77 src/GHC.hs | 14 ++++++++------ src/Settings/Packages.hs | 3 ++- 2 files changed, 10 insertions(+), 7 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 30414db..06140b1 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,9 +1,9 @@ module GHC ( array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, + genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, + integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath @@ -22,11 +22,11 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, ghcBoot, binary, bytestring, cabal, compiler , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim + , filepath, genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin - , integerGmp, integerSimple, mkUserGuidePart, parallel, pretty, primitive - , process, runghc, stm, templateHaskell, terminfo, time, transformers, unix - , win32, xhtml ] + , integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty + , primitive , process, runghc, stm, templateHaskell, terminfo, time + , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, @@ -54,6 +54,7 @@ genapply = utility "genapply" genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" +ghci = library "ghci" `setPath` "libraries/ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" ghcPwd = utility "ghc-pwd" @@ -67,6 +68,7 @@ hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" integerGmp = library "integer-gmp" integerSimple = library "integer-simple" +iservBin = topLevel "iserv-bin" `setPath` "iserv" mkUserGuidePart = utility "mkUserGuidePart" parallel = library "parallel" pretty = library "pretty" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index febb254..718b8de 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -29,10 +29,11 @@ packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq , directory, dllSplit, filepath - , ghcPrim, ghcPwd, haskeline, hpcBin, integerLibrary + , ghci, ghcPrim, ghcPwd, haskeline, hpcBin, integerLibrary , mkUserGuidePart, pretty, process, runghc, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] + , notM windowsHost ? append [iservBin] , buildHaddock ? append [xhtml] ] packagesStage2 :: Packages From git at git.haskell.org Thu Oct 26 23:25:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more targets. (4399476) Message-ID: <20171026232511.749F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4399476dfd70a7ce9ad97750873e8b3397deb270/ghc >--------------------------------------------------------------- commit 4399476dfd70a7ce9ad97750873e8b3397deb270 Author: Andrey Mokhov Date: Sun Jan 18 14:27:23 2015 +0000 Add more targets. >--------------------------------------------------------------- 4399476dfd70a7ce9ad97750873e8b3397deb270 src/Targets.hs | 36 +++++++++++++++++++----------------- 1 file changed, 19 insertions(+), 17 deletions(-) diff --git a/src/Targets.hs b/src/Targets.hs index a8c9e68..25a3a0e 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -6,23 +6,25 @@ import Base -- TODO: this should eventually be removed and replaced by the top-level -- target, i.e. GHC (and perhaps, something else) libraryPackagesInStage :: Stage -> [String] -libraryPackagesInStage Stage0 = [] - --[ "bin-package-db" - --, "binary" - --, "hoopl" - --, "hpc" - --, "transformers" ] -libraryPackagesInStage Stage1 = ["directory", "bytestring"] - --libraryPackagesInStage Stage0 ++ - --[ "array" - --, "deepseq" - --, "Cabal/Cabal" - --, "containers" - --, "filepath" - --, "parallel" - --, "pretty" - --, "stm" - --, "template-haskell" ] +libraryPackagesInStage Stage0 = + [ "bin-package-db" + , "binary" + , "hoopl" + , "hpc" + , "transformers" ] +libraryPackagesInStage Stage1 = + libraryPackagesInStage Stage0 ++ + [ "array" + , "bytestring" + , "Cabal/Cabal" + , "containers" + , "deepseq" + , "directory" + , "filepath" + , "parallel" + , "pretty" + , "stm" + , "template-haskell" ] libraryPackagesInStage _ = [] From git at git.haskell.org Thu Oct 26 23:25:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: The new build system will live in `shake-build`. (bd2a394) Message-ID: <20171026232511.95C473A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd2a394ec33a93d17d74db243dc8182d2f13de31/ghc >--------------------------------------------------------------- commit bd2a394ec33a93d17d74db243dc8182d2f13de31 Author: Andrey Mokhov Date: Fri Dec 18 21:18:10 2015 +0000 The new build system will live in `shake-build`. >--------------------------------------------------------------- bd2a394ec33a93d17d74db243dc8182d2f13de31 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index faf3155..05f3352 100644 --- a/README.md +++ b/README.md @@ -3,4 +3,4 @@ Shaking up GHC As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). -This is supposed to go into the `build` directory of the GHC source tree. +This is supposed to go into the `shake-build` directory of the GHC source tree. From git at git.haskell.org Thu Oct 26 23:25:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Util/unifyPath function and make sure it is used. (a93823b) Message-ID: <20171026232515.327763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1/ghc >--------------------------------------------------------------- commit a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1 Author: Andrey Mokhov Date: Sun Jan 18 14:28:04 2015 +0000 Add Util/unifyPath function and make sure it is used. >--------------------------------------------------------------- a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1 src/Oracles.hs | 13 +++++++------ src/Oracles/PackageData.hs | 4 ++-- src/Package/Base.hs | 21 ++++++++++----------- src/Package/Compile.hs | 8 ++++---- src/Package/Data.hs | 7 +++---- src/Package/Dependencies.hs | 6 +++--- src/Package/Library.hs | 10 +++++----- src/Util.hs | 4 ++++ 8 files changed, 38 insertions(+), 35 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 a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1 From git at git.haskell.org Thu Oct 26 23:25:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #2 from bgamari/master (c937606) Message-ID: <20171026232515.4E0B73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c937606629a97188500bac159d2c8882ccbac3e9/ghc >--------------------------------------------------------------- commit c937606629a97188500bac159d2c8882ccbac3e9 Merge: bd2a394 0afdf64 Author: Andrey Mokhov Date: Fri Dec 18 23:16:30 2015 +0000 Merge pull request #2 from bgamari/master Various fixes >--------------------------------------------------------------- c937606629a97188500bac159d2c8882ccbac3e9 build.sh | 6 ++++++ cfg/system.config.in | 18 ++++++++++++------ src/Builder.hs | 1 + src/GHC.hs | 22 ++++++++++++---------- src/Oracles/Config/Flag.hs | 6 ++++-- src/Oracles/Dependencies.hs | 12 ++++++------ src/Oracles/PackageData.hs | 6 ++---- src/Package.hs | 1 + src/Rules.hs | 6 +++--- src/Rules/Compile.hs | 10 ---------- src/Rules/Data.hs | 36 +----------------------------------- src/Rules/Generate.hs | 5 ++++- src/Settings/Builders/Ghc.hs | 16 ++++++++-------- src/Settings/Packages.hs | 5 +++-- src/Stage.hs | 1 + src/Way.hs | 3 +++ 16 files changed, 67 insertions(+), 87 deletions(-) From git at git.haskell.org Thu Oct 26 23:25:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move to shake-build subdirectory. (6961517) Message-ID: <20171026232519.183093A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/69615175a302d90a4e8b76d419124282d0b861e6/ghc >--------------------------------------------------------------- commit 69615175a302d90a4e8b76d419124282d0b861e6 Author: Andrey Mokhov Date: Sat Dec 19 01:04:20 2015 +0000 Move to shake-build subdirectory. >--------------------------------------------------------------- 69615175a302d90a4e8b76d419124282d0b861e6 src/Base.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 896ddc9..bfa7730 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -39,11 +39,14 @@ import qualified System.Directory as IO import System.IO -- Build system files and paths +shakePath :: FilePath +shakePath = "shake-build" + shakeFilesPath :: FilePath -shakeFilesPath = "_build/" +shakeFilesPath = shakeFilesPath -/- ".db" configPath :: FilePath -configPath = "shake/cfg/" +configPath = shakePath -/- "cfg" bootPackageConstraints :: FilePath bootPackageConstraints = shakeFilesPath ++ "boot-package-constraints" From git at git.haskell.org Thu Oct 26 23:25:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor rules, clean up code. (a1819f6) Message-ID: <20171026232519.1696F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e/ghc >--------------------------------------------------------------- commit a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e Author: Andrey Mokhov Date: Sun Jan 18 23:52:09 2015 +0000 Refactor rules, clean up code. >--------------------------------------------------------------- a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e src/Oracles.hs | 8 ++++---- src/Package/Base.hs | 21 ++++++++++++-------- src/Package/Compile.hs | 45 +++++++++++++++++++++---------------------- src/Package/Library.hs | 52 +++++++++++++++++++++++++------------------------- src/Targets.hs | 2 +- src/Ways.hs | 1 - 6 files changed, 66 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e From git at git.haskell.org Thu Oct 26 23:25:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set shakeFilesPath to shake-build/.db (1203444) Message-ID: <20171026232522.D9BC03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12034445640aadd319ee7639c303b524c1d6df80/ghc >--------------------------------------------------------------- commit 12034445640aadd319ee7639c303b524c1d6df80 Author: Andrey Mokhov Date: Sat Dec 19 01:06:14 2015 +0000 Set shakeFilesPath to shake-build/.db >--------------------------------------------------------------- 12034445640aadd319ee7639c303b524c1d6df80 src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index bfa7730..e95aa94 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -43,7 +43,7 @@ shakePath :: FilePath shakePath = "shake-build" shakeFilesPath :: FilePath -shakeFilesPath = shakeFilesPath -/- ".db" +shakeFilesPath = shakePath -/- ".db" configPath :: FilePath configPath = shakePath -/- "cfg" From git at git.haskell.org Thu Oct 26 23:25:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix recursive rules error. (8290198) Message-ID: <20171026232523.09E8A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82901986216e56d42623299aaec8ca7d1bddcdca/ghc >--------------------------------------------------------------- commit 82901986216e56d42623299aaec8ca7d1bddcdca Author: Andrey Mokhov Date: Mon Jan 19 03:45:10 2015 +0000 Fix recursive rules error. >--------------------------------------------------------------- 82901986216e56d42623299aaec8ca7d1bddcdca src/Package/Base.hs | 8 +++++--- src/Package/Compile.hs | 12 +++++++++--- src/Package/Data.hs | 4 +++- src/Package/Dependencies.hs | 8 +++++--- src/Package/Library.hs | 8 ++++++-- 5 files changed, 28 insertions(+), 12 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 023b001..cf29e59 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -108,8 +108,9 @@ includeGhcArgs path dist = pkgHsSources :: FilePath -> FilePath -> Action [FilePath] pkgHsSources path dist = do let pathDist = path dist + autogen = pathDist "build/autogen" dirs <- map (path ) <$> args (SrcDirs pathDist) - findModuleFiles pathDist dirs [".hs", ".lhs"] + findModuleFiles pathDist (autogen:dirs) [".hs", ".lhs"] -- TODO: look for non-{hs,c} objects too @@ -136,11 +137,13 @@ pkgLibHsObjects path dist stage way = do let pathDist = path dist buildDir = unifyPath $ pathDist "build" split <- splitObjects stage + depObjs <- pkgDepHsObjects path dist way if split then do + need depObjs -- Otherwise, split objects may not yet be available let suffix = "_" ++ osuf way ++ "_split/*." ++ osuf way findModuleFiles pathDist [buildDir] [suffix] - else pkgDepHsObjects path dist way + else do return depObjs findModuleFiles :: FilePath -> [FilePath] -> [String] -> Action [FilePath] findModuleFiles pathDist directories suffixes = do @@ -153,7 +156,6 @@ findModuleFiles pathDist directories suffixes = do let dir = takeDirectory file dirExists <- liftIO $ S.doesDirectoryExist dir when dirExists $ return file - files <- getDirectoryFiles "" fileList return $ map unifyPath files diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 01659b6..94cf16a 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -49,8 +49,10 @@ compileHaskell pkg @ (Package _ path _) todo @ (stage, dist, _) obj way = do let buildDir = unifyPath $ path dist "build" -- TODO: keep only vanilla dependencies in 'haskell.deps' deps <- args $ DependencyList (buildDir "haskell.deps") obj + let (srcs, his) = partition ("//*hs" ?==) deps + objs = map (-<.> osuf way) his + -- Need *.o files instead of *.hi files to avoid recursive rules need deps - let srcs = filter ("//*hs" ?==) deps run (Ghc stage) $ ghcArgs pkg todo way srcs obj buildRule :: Package -> TodoItem -> Rules () @@ -64,15 +66,19 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = (buildDir hiPattern) %> \hi -> do let obj = hi -<.> osuf way - need [obj] + -- TODO: Understand why 'need [obj]' doesn't work, leading to + -- recursive rules error. Below is a workaround. + -- putColoured Yellow $ "Hi " ++ hi + compileHaskell pkg todo obj way (buildDir oPattern) %> \obj -> do - need [argListPath argListDir pkg stage] let vanillaObjName = takeFileName obj -<.> "o" cDeps <- args $ DependencyList cDepFile vanillaObjName if null cDeps then compileHaskell pkg todo obj way else compileC pkg todo cDeps obj + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, settings) = diff --git a/src/Package/Data.hs b/src/Package/Data.hs index e1afee1..6d01ba5 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -121,12 +121,14 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = -- TODO: Is this needed? Also check out Paths_cpsa.hs. -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do - need [argListPath argListDir pkg stage, cabal] + need [cabal] when (doesFileExist $ configure <.> "ac") $ need [configure] run GhcCabal $ cabalArgs pkg todo when (registerPackage settings) $ run (GhcPkg stage) $ ghcPkgArgs pkg todo postProcessPackageData $ pathDist "package-data.mk" + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, _) = diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 8675c6f..f87580a 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -61,12 +61,12 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do let pathDist = path dist buildDir = pathDist "build" - (buildDir "haskell.deps") %> \out -> do - need [argListPath argListDir pkg stage] + (buildDir "haskell.deps") %> \_ -> do run (Ghc stage) $ ghcArgs pkg todo + -- Finally, record the argument list + need [argListPath argListDir pkg stage] (buildDir "c.deps") %> \out -> do - need [argListPath argListDir pkg stage] srcs <- args $ CSrcs pathDist deps <- fmap concat $ forM srcs $ \src -> do let srcPath = path src @@ -75,6 +75,8 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do liftIO $ readFile depFile writeFileChanged out deps liftIO $ removeFiles buildDir ["*.c.deps"] + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, _) = diff --git a/src/Package/Library.hs b/src/Package/Library.hs index c377bc8..6ad029d 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -26,13 +26,15 @@ arRule pkg @ (Package _ path _) todo @ (stage, dist, _) = let way = detectWay $ tail $ takeExtension out cObjs <- pkgCObjects path dist way hsObjs <- pkgDepHsObjects path dist way - need $ [argListPath argListDir pkg stage] ++ cObjs ++ hsObjs + need $ cObjs ++ hsObjs libHsObjs <- pkgLibHsObjects path dist stage way liftIO $ removeFiles "." [out] -- Splitting argument list into chunks as otherwise Ar chokes up maxChunk <- argSizeLimit forM_ (chunksOfSize maxChunk $ cObjs ++ libHsObjs) $ \objs -> do run Ar $ arArgs objs $ unifyPath out + -- Finally, record the argument list + need [argListPath argListDir pkg stage] ldRule :: Package -> TodoItem -> Rules () ldRule pkg @ (Package name path _) todo @ (stage, dist, _) = @@ -42,13 +44,15 @@ ldRule pkg @ (Package name path _) todo @ (stage, dist, _) = priority 2 $ (buildDir "*.o") %> \out -> do cObjs <- pkgCObjects path dist vanilla hObjs <- pkgDepHsObjects path dist vanilla - need $ [argListPath argListDir pkg stage] ++ cObjs ++ hObjs + need $ cObjs ++ hObjs run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) putColoured Green $ "/--------\n| Successfully built package '" ++ name ++ "' (stage " ++ show stage ++ ")." putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." ++ "\n\\--------" + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg @ (Package _ path _) todo @ (stage, dist, settings) = From git at git.haskell.org Thu Oct 26 23:25:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Shake database to shake-build/.db, rename _shake to .shake for consistency. (ddfe5bc) Message-ID: <20171026232526.51CD53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ddfe5bcdfaf7147bee73d790e42584c78485127c/ghc >--------------------------------------------------------------- commit ddfe5bcdfaf7147bee73d790e42584c78485127c Author: Andrey Mokhov Date: Sun Dec 20 04:04:07 2015 +0000 Move Shake database to shake-build/.db, rename _shake to .shake for consistency. >--------------------------------------------------------------- ddfe5bcdfaf7147bee73d790e42584c78485127c .gitignore | 7 ++----- build.bat | 4 ++-- build.sh | 6 +++--- src/Base.hs | 4 ++-- 4 files changed, 9 insertions(+), 12 deletions(-) diff --git a/.gitignore b/.gitignore index 94b9664..74a0c27 100644 --- a/.gitignore +++ b/.gitignore @@ -1,6 +1,3 @@ -*.o -*.hi -_shake/ -_build/ +.shake/ +.db/ cfg/system.config -arg/*/*.txt diff --git a/build.bat b/build.bat index b45bdde..ab26e07 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,2 @@ - at mkdir _shake 2> nul - at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at mkdir .shake 2> nul + at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=.shake -o .shake/build && .shake\build --lint --directory ".." %* diff --git a/build.sh b/build.sh index cf217bd..d350779 100755 --- a/build.sh +++ b/build.sh @@ -1,6 +1,6 @@ #!/bin/bash -e root=`dirname $0` -mkdir -p $root/_shake -ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/_shake -o $root/_shake/build -$root/_shake/build --lint --directory $root/.. $@ +mkdir -p $root/.shake +ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/.shake -o $root/.shake/build +$root/.shake/build --lint --directory $root/.. $@ diff --git a/src/Base.hs b/src/Base.hs index e95aa94..33b01bd 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -49,10 +49,10 @@ configPath :: FilePath configPath = shakePath -/- "cfg" bootPackageConstraints :: FilePath -bootPackageConstraints = shakeFilesPath ++ "boot-package-constraints" +bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" packageDependencies :: FilePath -packageDependencies = shakeFilesPath ++ "package-dependencies" +packageDependencies = shakeFilesPath -/- "package-dependencies" -- Utility functions -- Find and replace all occurrences of a value in a list From git at git.haskell.org Thu Oct 26 23:25:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (20ed2d1) Message-ID: <20171026232526.954213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20ed2d1d6d1ce6b612eb607cae447c9646f7be6b/ghc >--------------------------------------------------------------- commit 20ed2d1d6d1ce6b612eb607cae447c9646f7be6b Author: Andrey Mokhov Date: Mon Jan 19 04:13:06 2015 +0000 Clean up. >--------------------------------------------------------------- 20ed2d1d6d1ce6b612eb607cae447c9646f7be6b src/Package/Compile.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 94cf16a..d99e2bf 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -49,9 +49,7 @@ compileHaskell pkg @ (Package _ path _) todo @ (stage, dist, _) obj way = do let buildDir = unifyPath $ path dist "build" -- TODO: keep only vanilla dependencies in 'haskell.deps' deps <- args $ DependencyList (buildDir "haskell.deps") obj - let (srcs, his) = partition ("//*hs" ?==) deps - objs = map (-<.> osuf way) his - -- Need *.o files instead of *.hi files to avoid recursive rules + let srcs = filter ("//*hs" ?==) deps need deps run (Ghc stage) $ ghcArgs pkg todo way srcs obj From git at git.haskell.org Thu Oct 26 23:25:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (5975b50) Message-ID: <20171026232530.739FE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5975b50e948df0c680b56c077494f55599131fa1/ghc >--------------------------------------------------------------- commit 5975b50e948df0c680b56c077494f55599131fa1 Author: Andrey Mokhov Date: Sun Dec 20 04:04:28 2015 +0000 Clean up. >--------------------------------------------------------------- 5975b50e948df0c680b56c077494f55599131fa1 src/GHC.hs | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 06140b1..0279197 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,7 +1,7 @@ module GHC ( - array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, - compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, + array, base, binary, bytestring, cabal, compiler, containers, compareSizes, + deepseq, deriveConstants, directory, dllSplit, filepath, genapply, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, @@ -20,25 +20,24 @@ import Stage -- which can be overridden in Settings/User.hs. defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, ghcBoot, binary, bytestring, cabal, compiler - , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim + [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes + , deepseq, deriveConstants, directory, dllSplit, filepath, genapply + , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin , integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty , primitive , process, runghc, stm, templateHaskell, terminfo, time , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) -array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, - compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, +array, base, binary, bytestring, cabal, compiler, containers, compareSizes, + deepseq, deriveConstants, directory, dllSplit, filepath, genapply, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, + integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" -ghcBoot = library "ghc-boot" binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" @@ -53,8 +52,9 @@ filepath = library "filepath" genapply = utility "genapply" genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" +ghcBoot = library "ghc-boot" ghcCabal = utility "ghc-cabal" -ghci = library "ghci" `setPath` "libraries/ghci" +ghci = library "ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" ghcPwd = utility "ghc-pwd" From git at git.haskell.org Thu Oct 26 23:25:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add DepIncludeDirs package data option. (91a8bab) Message-ID: <20171026232530.8D39A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91a8babed3f640ecd972c7a20fd574e3853250d1/ghc >--------------------------------------------------------------- commit 91a8babed3f640ecd972c7a20fd574e3853250d1 Author: Andrey Mokhov Date: Mon Jan 19 11:49:40 2015 +0000 Add DepIncludeDirs package data option. >--------------------------------------------------------------- 91a8babed3f640ecd972c7a20fd574e3853250d1 src/Oracles/PackageData.hs | 42 ++++++++++++++++++++++-------------------- src/Package/Base.hs | 2 +- src/Package/Compile.hs | 1 + src/Targets.hs | 1 + 4 files changed, 25 insertions(+), 21 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 38accfe..760f47e 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -23,16 +23,17 @@ data PackageData = Version FilePath | PackageKey FilePath | Synopsis FilePath -data MultiPackageData = Modules FilePath - | SrcDirs FilePath - | IncludeDirs FilePath - | Deps FilePath - | DepKeys FilePath - | DepNames FilePath - | CppArgs FilePath - | HsArgs FilePath - | CcArgs FilePath - | CSrcs FilePath +data MultiPackageData = Modules FilePath + | SrcDirs FilePath + | IncludeDirs FilePath + | Deps FilePath + | DepKeys FilePath + | DepNames FilePath + | CppArgs FilePath + | HsArgs FilePath + | CcArgs FilePath + | CSrcs FilePath + | DepIncludeDirs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -53,16 +54,17 @@ instance ShowArg PackageData where instance ShowArgs MultiPackageData where showArgs packageData = do let (key, path, defaultValue) = case packageData of - Modules path -> ("MODULES" , path, "" ) - SrcDirs path -> ("HS_SRC_DIRS" , path, ".") - IncludeDirs path -> ("INCLUDE_DIRS", path, ".") - Deps path -> ("DEPS" , path, "" ) - DepKeys path -> ("DEP_KEYS" , path, "" ) - DepNames path -> ("DEP_NAMES" , path, "" ) - CppArgs path -> ("CPP_OPTS" , path, "" ) - HsArgs path -> ("HC_OPTS" , path, "" ) - CcArgs path -> ("CC_OPTS" , path, "" ) - CSrcs path -> ("C_SRCS" , path, "" ) + Modules path -> ("MODULES" , path, "" ) + SrcDirs path -> ("HS_SRC_DIRS" , path, ".") + IncludeDirs path -> ("INCLUDE_DIRS" , path, ".") + Deps path -> ("DEPS" , path, "" ) + DepKeys path -> ("DEP_KEYS" , path, "" ) + DepNames path -> ("DEP_NAMES" , path, "" ) + CppArgs path -> ("CPP_OPTS" , path, "" ) + HsArgs path -> ("HC_OPTS" , path, "" ) + CcArgs path -> ("CC_OPTS" , path, "" ) + CSrcs path -> ("C_SRCS" , path, "" ) + DepIncludeDirs path -> ("DEP_LIB_REL_DIRS", path, "" ) fullKey = replaceSeparators '_' $ path ++ "_" ++ key pkgData = path "package-data.mk" res <- askOracle $ PackageDataKey (pkgData, fullKey) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index cf29e59..aafc85b 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -155,7 +155,7 @@ findModuleFiles pathDist directories suffixes = do ] $ \file -> do let dir = takeDirectory file dirExists <- liftIO $ S.doesDirectoryExist dir - when dirExists $ return file + when dirExists $ return $ unifyPath file files <- getDirectoryFiles "" fileList return $ map unifyPath files diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index d99e2bf..e98f1a5 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -35,6 +35,7 @@ gccArgs (Package _ path _) (_, dist, _) srcs result = , commonCcArgs , commonCcWarninigArgs , pathArgs "-I" path $ IncludeDirs pathDist + , pathArgs "-I" path $ DepIncludeDirs pathDist , args ("-c":srcs) , args ["-o", result] ] diff --git a/src/Targets.hs b/src/Targets.hs index cf1ceb2..847c1fa 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -21,6 +21,7 @@ libraryPackagesInStage Stage1 = , "deepseq" , "directory" , "filepath" + , "ghc-prim" , "parallel" , "pretty" , "stm" From git at git.haskell.org Thu Oct 26 23:25:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable profiling and dynamic ways temporarily. (f4fb52d) Message-ID: <20171026232534.4A3A03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4fb52d17a91d97b37ac5352beb32153a8345f45/ghc >--------------------------------------------------------------- commit f4fb52d17a91d97b37ac5352beb32153a8345f45 Author: Andrey Mokhov Date: Sun Dec 20 04:06:07 2015 +0000 Disable profiling and dynamic ways temporarily. >--------------------------------------------------------------- f4fb52d17a91d97b37ac5352beb32153a8345f45 src/Settings/User.hs | 3 ++- src/Settings/Ways.hs | 3 +++ 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 5159bce..0dffbfd 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -22,8 +22,9 @@ userKnownPackages :: [Package] userKnownPackages = [] -- Control which ways libraries and rts are built +-- TODO: skip profiling for speed, skip dynamic since it's currently broken userLibWays :: Ways -userLibWays = mempty +userLibWays = remove [profiling, dynamic] userRtsWays :: Ways userRtsWays = mempty diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index ad42cea..7788242 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -4,6 +4,9 @@ import Expression import Predicates import Settings.User +-- TODO: use a single expression Ways parameterised by package instead of +-- expressions libWays and rtsWays + -- Combining default ways with user modifications getLibWays :: Expr [Way] getLibWays = fromDiffExpr $ defaultLibWays <> userLibWays From git at git.haskell.org Thu Oct 26 23:25:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, do minor refactoring. (79bc4c9) Message-ID: <20171026232534.4A9F83A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79bc4c9d2452c1e1621beef3a892c7bdf00199cd/ghc >--------------------------------------------------------------- commit 79bc4c9d2452c1e1621beef3a892c7bdf00199cd Author: Andrey Mokhov Date: Mon Jan 19 16:16:54 2015 +0000 Add comments, do minor refactoring. >--------------------------------------------------------------- 79bc4c9d2452c1e1621beef3a892c7bdf00199cd src/Oracles/PackageData.hs | 6 +++-- src/Package.hs | 23 +++++++------------ src/Package/Base.hs | 11 +++++++-- src/Package/Data.hs | 18 ++++++++++++--- src/Targets.hs | 56 +++++++++++++++++++++++++--------------------- src/Ways.hs | 35 ++++++++++++++++++++--------- 6 files changed, 90 insertions(+), 59 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 79bc4c9d2452c1e1621beef3a892c7bdf00199cd From git at git.haskell.org Thu Oct 26 23:25:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix include paths for Gcc. (2c7003a) Message-ID: <20171026232537.BE5263A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c7003a009d1205a73430b21bdc05caab23a8d85/ghc >--------------------------------------------------------------- commit 2c7003a009d1205a73430b21bdc05caab23a8d85 Author: Andrey Mokhov Date: Mon Jan 19 17:03:40 2015 +0000 Fix include paths for Gcc. >--------------------------------------------------------------- 2c7003a009d1205a73430b21bdc05caab23a8d85 src/Oracles/Builder.hs | 2 +- src/Package/Base.hs | 9 ++++++++- src/Package/Compile.hs | 3 +-- src/Package/Dependencies.hs | 2 +- 4 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index e52cc58..dc41507 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -119,7 +119,7 @@ interestingInfo builder ss = case builder of Ld -> prefixAndSuffix 4 0 ss Gcc _ -> if head ss == "-MM" then prefixAndSuffix 1 1 ss - else ss + else prefixAndSuffix 0 4 ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss else prefixAndSuffix 0 4 ss diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 8e12f15..e2031b6 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -7,7 +7,8 @@ module Package.Base ( Package (..), Settings (..), TodoItem (..), defaultSettings, libraryPackage, standardLibrary, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - pathArgs, packageArgs, includeGhcArgs, pkgHsSources, + pathArgs, packageArgs, + includeGccArgs, includeGhcArgs, pkgHsSources, pkgDepHsObjects, pkgLibHsObjects, pkgCObjects, argSizeLimit, sourceDependecies, @@ -99,6 +100,12 @@ packageArgs stage pathDist = do else productArgs "-package-name" (arg $ PackageKey pathDist) <> productArgs "-package" (args $ Deps pathDist) ] +includeGccArgs :: FilePath -> FilePath -> Args +includeGccArgs path dist = + let pathDist = path dist + in args [ pathArgs "-I" path $ IncludeDirs pathDist + , pathArgs "-I" path $ DepIncludeDirs pathDist ] + includeGhcArgs :: FilePath -> FilePath -> Args includeGhcArgs path dist = let pathDist = path dist diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index e98f1a5..eb2417f 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -34,8 +34,7 @@ gccArgs (Package _ path _) (_, dist, _) srcs result = in args [ args $ CcArgs pathDist , commonCcArgs , commonCcWarninigArgs - , pathArgs "-I" path $ IncludeDirs pathDist - , pathArgs "-I" path $ DepIncludeDirs pathDist + , includeGccArgs path dist , args ("-c":srcs) , args ["-o", result] ] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index f87580a..abee3f3 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -51,7 +51,7 @@ gccArgs sourceFile (Package _ path _) (stage, dist, _) = , args $ CcArgs pathDist , commonCcArgs , commonCcWarninigArgs - , pathArgs "-I" path $ IncludeDirs pathDist + , includeGccArgs path dist , args ["-MF", unifyPath depFile] , args ["-x", "c"] , arg $ unifyPath sourceFile ] From git at git.haskell.org Thu Oct 26 23:25:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (a66be35) Message-ID: <20171026232537.B8BFD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a66be35210083bbc2646b38df3a224a77f37dbf1/ghc >--------------------------------------------------------------- commit a66be35210083bbc2646b38df3a224a77f37dbf1 Author: Andrey Mokhov Date: Sun Dec 20 04:09:14 2015 +0000 Clean up. >--------------------------------------------------------------- a66be35210083bbc2646b38df3a224a77f37dbf1 src/Rules/Dependencies.hs | 1 - src/Settings/Builders/GhcCabal.hs | 18 +++++++++--------- 2 files changed, 9 insertions(+), 10 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 1def1ac..996d927 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -24,7 +24,6 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = hDepFile %> \file -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) $ need [platformH] - putBuild $ "srcs = " ++ show srcs need srcs if srcs == [] then writeFileChanged file "" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 01b061e..151cd5f 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -40,12 +40,12 @@ ghcCabalHsColourArgs = builder GhcCabalHsColour ? do -- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do - ways <- getWays - ghci <- lift ghcWithInterpreter + ways <- getWays + withGhci <- lift ghcWithInterpreter append [ if vanilla `elem` ways then "--enable-library-vanilla" else "--disable-library-vanilla" - , if vanilla `elem` ways && ghci && not dynamicGhcPrograms + , if vanilla `elem` ways && withGhci && not dynamicGhcPrograms then "--enable-library-for-ghci" else "--disable-library-for-ghci" , if profiling `elem` ways @@ -224,12 +224,12 @@ needDll0 stage pkg = do -- * otherwise, we must collapse it into one space-separated string. dll0Args :: Args dll0Args = do - stage <- getStage - pkg <- getPackage - dll0 <- lift $ needDll0 stage pkg - ghci <- lift ghcWithInterpreter - arg . unwords . concat $ [ modules | dll0 ] - ++ [ ghciModules | dll0 && ghci ] -- see #9552 + stage <- getStage + pkg <- getPackage + dll0 <- lift $ needDll0 stage pkg + withGhci <- lift ghcWithInterpreter + arg . unwords . concat $ [ modules | dll0 ] + ++ [ ghciModules | dll0 && withGhci ] -- see #9552 where modules = [ "Annotations" , "ApiAnnotation" From git at git.haskell.org Thu Oct 26 23:25:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add remaining library packages to Targets.hs. (8a860e6) Message-ID: <20171026232541.4C7403A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8a860e62574675274d1d7158503dfd5b4bb21e15/ghc >--------------------------------------------------------------- commit 8a860e62574675274d1d7158503dfd5b4bb21e15 Author: Andrey Mokhov Date: Tue Jan 20 04:39:40 2015 +0000 Add remaining library packages to Targets.hs. >--------------------------------------------------------------- 8a860e62574675274d1d7158503dfd5b4bb21e15 src/Oracles/Builder.hs | 1 + src/Package.hs | 6 +-- src/Package/Base.hs | 61 ++++++++++++++++-------- src/Package/Compile.hs | 8 ++-- src/Package/Data.hs | 17 +++---- src/Package/Dependencies.hs | 8 ++-- src/Package/Library.hs | 6 +-- src/Targets.hs | 112 +++++++++++++++++++++++++++++++++++--------- src/Ways.hs | 3 +- 9 files changed, 157 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8a860e62574675274d1d7158503dfd5b4bb21e15 From git at git.haskell.org Thu Oct 26 23:25:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add matchPackageNames to match packages and package names. (341f711) Message-ID: <20171026232541.43AB03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/341f711761e2ec9680613e81ad65335e61713f08/ghc >--------------------------------------------------------------- commit 341f711761e2ec9680613e81ad65335e61713f08 Author: Andrey Mokhov Date: Sun Dec 20 04:11:35 2015 +0000 Add matchPackageNames to match packages and package names. >--------------------------------------------------------------- 341f711761e2ec9680613e81ad65335e61713f08 src/Package.hs | 8 +++++++- src/Rules/Data.hs | 3 +-- src/Settings/Packages.hs | 7 ++++--- 3 files changed, 12 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index f64daee..8415bf1 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,6 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} module Package ( - Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility + Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility, + matchPackageNames ) where import Base @@ -45,6 +46,11 @@ instance Eq Package where instance Ord Package where compare = compare `on` pkgName +-- Given a sorted list of packages and a sorted list of package names, returns +-- packages whose names appear in the list of names +matchPackageNames :: [Package] -> [PackageName] -> [Package] +matchPackageNames = intersectOrd (\pkg name -> compare (pkgName pkg) name) + -- Instances for storing in the Shake database instance Binary Package instance Hashable Package where diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 95ac426..b6925d0 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -31,8 +31,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- We configure packages in the order of their dependencies deps <- packageDeps pkg pkgs <- interpretPartial target getPackages - let cmp p name = compare (pkgName p) name - depPkgs = intersectOrd cmp (sort pkgs) deps + let depPkgs = matchPackageNames (sort pkgs) deps need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] need [cabalFile] diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 718b8de..df52715 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -18,7 +18,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ ghcBoot, binary, cabal, compiler, ghc, ghcCabal, ghcPkg + [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] , stage0 ? append [deriveConstants, genapply, genprimopcode, hp2ps] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] @@ -41,9 +41,10 @@ packagesStage2 = mconcat [ append [ghcTags] , buildHaddock ? append [haddock] ] +-- TODO: switch to Set Package as the order of packages should not matter? knownPackages :: [Package] -knownPackages = defaultKnownPackages ++ userKnownPackages +knownPackages = sort $ defaultKnownPackages ++ userKnownPackages --- Note: this is slow but we keep it simple as there not too many packages (30) +-- Note: this is slow but we keep it simple as there are just ~50 packages findKnownPackage :: PackageName -> Maybe Package findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Thu Oct 26 23:25:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix boot package constraints. (3ee9ae2) Message-ID: <20171026232545.7B4303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ee9ae25495416fa212741f062e56016c7c573c4/ghc >--------------------------------------------------------------- commit 3ee9ae25495416fa212741f062e56016c7c573c4 Author: Andrey Mokhov Date: Sun Dec 20 04:12:21 2015 +0000 Fix boot package constraints. >--------------------------------------------------------------- 3ee9ae25495416fa212741f062e56016c7c573c4 src/Rules/Cabal.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 7ccb1b8..d8e557b 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,11 +1,12 @@ module Rules.Cabal (cabalRules) where -import Expression import Data.Version import Distribution.Package hiding (Package) import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Verbosity +import Expression +import GHC import Package hiding (library) import Settings @@ -13,7 +14,8 @@ cabalRules :: Rules () cabalRules = do -- Cache boot package constraints (to be used in cabalArgs) bootPackageConstraints %> \out -> do - pkgs <- interpretWithStage Stage0 getPackages + bootPkgs <- interpretWithStage Stage0 getPackages + let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg From git at git.haskell.org Thu Oct 26 23:25:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add base and integer-gmp2 to the list of targets. (2d24ed4) Message-ID: <20171026232545.8F8193A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d24ed4ae03015db98fb7ca1a86fe490b4540d75/ghc >--------------------------------------------------------------- commit 2d24ed4ae03015db98fb7ca1a86fe490b4540d75 Author: Andrey Mokhov Date: Tue Jan 20 16:23:12 2015 +0000 Add base and integer-gmp2 to the list of targets. >--------------------------------------------------------------- 2d24ed4ae03015db98fb7ca1a86fe490b4540d75 src/Package/Base.hs | 4 ++- src/Package/Compile.hs | 3 ++- src/Package/Data.hs | 4 +-- src/Package/Dependencies.hs | 5 ++-- src/Targets.hs | 65 ++++++++++++++++++++++++--------------------- 5 files changed, 45 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 2d24ed4ae03015db98fb7ca1a86fe490b4540d75 From git at git.haskell.org Thu Oct 26 23:25:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix broken parallel build: track dependencies due to -package-id flags. (361c3c2) Message-ID: <20171026232549.90B753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/361c3c2b250bd016ec16494b6f89b4971241e41e/ghc >--------------------------------------------------------------- commit 361c3c2b250bd016ec16494b6f89b4971241e41e Author: Andrey Mokhov Date: Sun Dec 20 04:13:38 2015 +0000 Fix broken parallel build: track dependencies due to -package-id flags. >--------------------------------------------------------------- 361c3c2b250bd016ec16494b6f89b4971241e41e src/Rules.hs | 24 ++---------------------- src/Rules/Program.hs | 26 +++++++++++++++++++++++--- src/Settings/TargetDirectory.hs | 17 ++++++++++++++++- 3 files changed, 41 insertions(+), 26 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 90769c1..505b8a5 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,11 +1,9 @@ module Rules (generateTargets, packageRules) where import Expression -import Oracles import Rules.Package import Rules.Resources import Settings -import Settings.Builders.GhcCabal -- generateTargets needs top-level build targets generateTargets :: Rules () @@ -14,29 +12,11 @@ generateTargets = action $ do pkgs <- interpretWithStage stage getPackages let (libPkgs, programPkgs) = partition isLibrary pkgs libTargets <- fmap concat . forM libPkgs $ \pkg -> do - let target = PartialTarget stage pkg - buildPath = targetPath stage pkg -/- "build" - compId <- interpretPartial target $ getPkgData ComponentId - needGhciLib <- interpretPartial target $ getPkgData BuildGhciLib + let target = PartialTarget stage pkg needHaddock <- interpretPartial target buildHaddock - ways <- interpretPartial target getWays - let ghciLib = buildPath -/- "HS" ++ compId <.> "o" - haddock = pkgHaddockFile pkg - libs <- fmap concat . forM ways $ \way -> do - extension <- libsuf way - let name = buildPath -/- "libHS" ++ compId - dll0 <- needDll0 stage pkg - return $ [ name <.> extension ] - ++ [ name ++ "-0" <.> extension | dll0 ] - - return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] - ++ [ haddock | needHaddock && stage == Stage1 ] - ++ libs - + return $ [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] let programTargets = map (fromJust . programPath stage) programPkgs - return $ libTargets ++ programTargets - need $ reverse targets -- TODO: use stage 2 compiler for building stage 2 packages (instead of stage 1) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index afe2738..8e3ec77 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -1,20 +1,26 @@ module Rules.Program (buildProgram) where import Expression hiding (splitPath) -import GHC +import GHC (hsc2hs, haddock) import Oracles import Rules.Actions import Rules.Library import Rules.Resources import Settings +import Settings.Builders.GhcCabal -- TODO: Get rid of the Paths_hsc2hs.o hack. +-- TODO: Do we need to consider other ways when building programs? buildProgram :: Resources -> PartialTarget -> Rules () buildProgram _ target @ (PartialTarget stage pkg) = do let path = targetPath stage pkg buildPath = path -/- "build" program = programPath stage pkg + -- return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] + -- ++ [ haddock | needHaddock && stage == Stage1 ] + -- ++ libs + (\f -> program == Just f) ?> \bin -> do cSrcs <- cSources target -- TODO: remove code duplication (Library.hs) hSrcs <- hSources target @@ -23,8 +29,22 @@ buildProgram _ target @ (PartialTarget stage pkg) = do ++ [ buildPath -/- "Paths_hsc2hs.o" | pkg == hsc2hs ] ++ [ buildPath -/- "Paths_haddock.o" | pkg == haddock ] objs = cObjs ++ hObjs - putBuild $ "objs = " ++ show objs - need objs + pkgs <- interpretPartial target getPackages + ways <- interpretPartial target getWays + depNames <- interpretPartial target $ getPkgDataList DepNames + ghciFlag <- interpretPartial target $ getPkgData BuildGhciLib + let deps = matchPackageNames (sort pkgs) (sort depNames) + ghci = ghciFlag == "YES" && stage == Stage1 + libs <- fmap concat . forM deps $ \dep -> do + let depTarget = PartialTarget stage dep + compId <- interpretPartial depTarget $ getPkgData ComponentId + libFiles <- fmap concat . forM ways $ \way -> do + libFile <- pkgLibraryFile stage dep compId way + lib0File <- pkgLibraryFile stage dep (compId ++ "-0") way + dll0 <- needDll0 stage dep + return $ [ libFile ] ++ [ lib0File | dll0 ] + return $ libFiles ++ [ pkgGhciLibraryFile stage dep compId | ghci ] + need $ objs ++ libs build $ fullTargetWithWay target (Ghc stage) vanilla objs [bin] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built program '" diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index b84d03d..6bcec88 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,5 +1,5 @@ module Settings.TargetDirectory ( - targetDirectory, targetPath, pkgHaddockFile + targetDirectory, targetPath, pkgHaddockFile, pkgLibraryFile, pkgGhciLibraryFile ) where import Expression @@ -20,3 +20,18 @@ targetPath stage pkg = pkgPath pkg -/- targetDirectory stage pkg pkgHaddockFile :: Package -> FilePath pkgHaddockFile pkg @ (Package name _) = targetPath Stage1 pkg -/- "doc/html" -/- name -/- name <.> "haddock" + +-- Relative path to a package library file, e.g.: +-- "libraries/array/dist-install/build/libHSarray-0.5.1.0.a" +-- TODO: remove code duplication for computing buildPath +pkgLibraryFile :: Stage -> Package -> String -> Way -> Action FilePath +pkgLibraryFile stage pkg componentId way = do + extension <- libsuf way + let buildPath = targetPath stage pkg -/- "build" + return $ buildPath -/- "libHS" ++ componentId <.> extension + +-- Relative path to a package ghci library file, e.g.: +-- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" +pkgGhciLibraryFile :: Stage -> Package -> String -> FilePath +pkgGhciLibraryFile stage pkg componentId = + targetPath stage pkg -/- "build" -/- "HS" ++ componentId <.> "o" From git at git.haskell.org Thu Oct 26 23:25:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (e809d1c) Message-ID: <20171026232549.98C423A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e809d1c945a36f87fc1c006e8b4b88296b5ea48e/ghc >--------------------------------------------------------------- commit e809d1c945a36f87fc1c006e8b4b88296b5ea48e Author: Andrey Mokhov Date: Tue Jan 20 16:27:51 2015 +0000 Clean up. >--------------------------------------------------------------- e809d1c945a36f87fc1c006e8b4b88296b5ea48e src/Targets.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Targets.hs b/src/Targets.hs index 595c38f..2ff6eae 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -60,7 +60,7 @@ targetPackages = baseConfArgs :: Settings -> Settings baseConfArgs settings = - settings { customConfArgs = arg $ "--flags=" ++ show integerLibrary } + settings { customConfArgs = arg $ "--flags=" ++ integerLibraryName } -- see Note [Cabal package weirdness] cabalTraits :: (String, Settings -> Settings) From git at git.haskell.org Thu Oct 26 23:25:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (7c2279b) Message-ID: <20171026232553.ABEB03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c2279b523ce8b71dc0e9492380d8798a8b1b4f2/ghc >--------------------------------------------------------------- commit 7c2279b523ce8b71dc0e9492380d8798a8b1b4f2 Author: Andrey Mokhov Date: Wed Jan 21 23:20:52 2015 +0000 Add comments. >--------------------------------------------------------------- 7c2279b523ce8b71dc0e9492380d8798a8b1b4f2 src/Oracles.hs | 1 + src/Package.hs | 2 +- src/Package/Base.hs | 11 ++++++++--- src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 7 ++++--- src/Targets.hs | 19 +++++++++++++++++++ 6 files changed, 35 insertions(+), 9 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 80e2e60..4e6fe5b 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -11,6 +11,7 @@ module Oracles ( import Development.Shake.Config import Development.Shake.Util import qualified Data.HashMap.Strict as M +-- TODO: get rid of Bifunctor dependency import Data.Bifunctor import Base import Util diff --git a/src/Package.hs b/src/Package.hs index 4d24e2a..1931ea3 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -26,7 +26,7 @@ packageRules = do -- We build *only one* vanilla .o file (not sure why) -- We build .way_a file for each way (or its dynamic version). -- TODO: Check BUILD_GHCI_LIB flag to decide if .o is needed - -- TODO: move this into buildPackage + -- TODO: move this into a separate file (perhaps, to Targets.hs?) action $ when (buildWhen settings) $ do let pathDist = path dist buildDir = pathDist "build" diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 00b4356..88e357f 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -39,9 +39,9 @@ defaultSettings stage = Settings { customConfArgs = mempty, customCcArgs = mempty, - customLdArgs = mempty, - customCppArgs = mempty, - customDllArgs = mempty, + customLdArgs = mempty, -- currently not used + customCppArgs = mempty, -- currently not used + customDllArgs = mempty, -- only for compiler registerPackage = True, ways = defaultWays stage, buildWhen = return True @@ -54,6 +54,11 @@ defaultSettings stage = Settings -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to package.cabal -- Settings may be different for different combinations of Stage & FilePath +-- TODO: the above may be incorrect, settings seem to *only* depend on the +-- stage. In fact Stage seem to define FilePath and Settings, therefore we +-- can drop the TodoItem and replace it by [Stage] and two functions +-- * distDirectory :: Package -> Stage -> FilePath +-- * settings :: Package -> Stage -> Settings type TodoItem = (Stage, FilePath, Settings) -- pkgPath is the path to the source code relative to the root diff --git a/src/Package/Data.hs b/src/Package/Data.hs index b2de8c5..602993e 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -26,8 +26,8 @@ configureArgs stage settings = unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s cflags = [ commonCcArgs `filterOut` "-Werror" , args $ ConfCcArgs stage - -- , customCcArgs settings -- TODO: fix - , commonCcWarninigArgs ] -- TODO: check if cflags are glued + -- , customCcArgs settings -- TODO: bring this back + , commonCcWarninigArgs ] -- TODO: check why cflags are glued ldflags = [ commonLdArgs , args $ ConfGccLinkerArgs stage , customLdArgs settings ] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 604034e..c861707 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -3,6 +3,7 @@ module Package.Dependencies (buildPackageDependencies) where import Package.Base +-- TODO: use oracles instead of arg files. argListDir :: FilePath argListDir = "shake/arg/buildPackageDependencies" @@ -49,9 +50,9 @@ gccArgs sourceFile (Package _ path _ _) (stage, dist, settings) = depFile = buildDir takeFileName sourceFile <.> "deps" in args [ args ["-E", "-MM"] -- TODO: add a Cpp Builder instead , args $ CcArgs pathDist - , commonCcArgs - , customCcArgs settings - , commonCcWarninigArgs + , commonCcArgs -- TODO: remove? + , customCcArgs settings -- TODO: Replace by customCppArgs? + , commonCcWarninigArgs -- TODO: remove? , includeGccArgs path dist , args ["-MF", unifyPath depFile] , args ["-x", "c"] diff --git a/src/Targets.hs b/src/Targets.hs index 2ff6eae..bc4c29d 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -15,12 +15,14 @@ instance Show IntegerLibrary where IntegerGmp2 -> "integer-gmp2" IntegerSimple -> "integer-simple" +-- TODO: keep or move to configuration files? see Note [configuration files] integerLibrary :: IntegerLibrary integerLibrary = IntegerGmp2 integerLibraryName :: String integerLibraryName = show integerLibrary +-- see Note [configuration files] buildHaddock :: Bool buildHaddock = True @@ -107,6 +109,23 @@ targetPackagesInStage stage = filter inStage targetPackages inStage (Package _ _ _ todoItems) = any matchStage todoItems matchStage (todoStage, _, _) = todoStage == stage +-- TODISCUSS -- Note [Cabal package weirdness] -- Find out if we can move the contents to just Cabal/ -- What is Cabal/cabal-install? Do we need it? + +-- TODISCUSS +-- Note [configuration files] +-- In this file we have two configuration options: integerLibrary and +-- buildHaddock. Arguably, their place should be among other configuration +-- options in the config files, however, moving integerLibrary there would +-- actually be quite painful, because it would then be confined to live in +-- the Action monad. +-- In general, shall we keep as many options as possible inside Shake, or +-- leave them in one place -- configuration files? We could try to move +-- everything to Shake which would be great: +-- * type safety and better abstractions +-- * useable outside the Action monad, e.g. for creating rules +-- * recompiling Shake is much faster then re-running configure script +-- * ... no more autoconf/configure and native Windows build?! Sign me up! +-- However, moving everything to Shake seems unfeasible at the moment. From git at git.haskell.org Thu Oct 26 23:25:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix absolute paths starting with /c/ on Windows. (30d3d63) Message-ID: <20171026232553.AA9683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30d3d63bf7423e7da637981810dd62261868d7d2/ghc >--------------------------------------------------------------- commit 30d3d63bf7423e7da637981810dd62261868d7d2 Author: Andrey Mokhov Date: Sun Dec 20 15:18:44 2015 +0000 Fix absolute paths starting with /c/ on Windows. >--------------------------------------------------------------- 30d3d63bf7423e7da637981810dd62261868d7d2 src/Builder.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 007dae3..f15054d 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -95,16 +95,22 @@ needBuilder laxDependencies builder = do GhcM _ -> True _ -> False --- On Windows: if the path starts with "/", prepend it with the correct path to --- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". +-- TODO: this is fragile, e.g. we currently only handle C: drive +-- On Windows: +-- * if the path starts with "/c/" change the prefix to "C:/" +-- * otherwise, if the path starts with "/", prepend it with the correct path +-- to the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe" fixAbsolutePathOnWindows :: FilePath -> Action FilePath fixAbsolutePathOnWindows path = do windows <- windowsHost -- Note, below is different from FilePath.isAbsolute: if (windows && "/" `isPrefixOf` path) then do - root <- windowsRoot - return . unifyPath $ root ++ drop 1 path + if ("/c/" `isPrefixOf` path) + then return $ "C:" ++ drop 2 path + else do + root <- windowsRoot + return . unifyPath $ root ++ drop 1 path else return path From git at git.haskell.org Thu Oct 26 23:25:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Restrict ShowArgs and args to accept only lists. (9c218ad) Message-ID: <20171026232557.3EAEF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c218adf6e025572ae550302419f0bcc632d3be6/ghc >--------------------------------------------------------------- commit 9c218adf6e025572ae550302419f0bcc632d3be6 Author: Andrey Mokhov Date: Thu Jan 22 23:38:46 2015 +0000 Restrict ShowArgs and args to accept only lists. >--------------------------------------------------------------- 9c218adf6e025572ae550302419f0bcc632d3be6 src/Base.hs | 31 +++++++++++-------------------- src/Package/Base.hs | 14 ++++++++------ src/Package/Compile.hs | 2 +- src/Package/Data.hs | 9 +++++---- src/Package/Dependencies.hs | 6 +++--- 5 files changed, 28 insertions(+), 34 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 232bca2..fa9104a 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,7 +12,6 @@ module Base ( ShowArg (..), ShowArgs (..), arg, args, Condition (..), - (<+>), filterOut, productArgs, concatArgs ) where @@ -49,34 +48,26 @@ instance ShowArg String where instance ShowArg a => ShowArg (Action a) where showArg = (showArg =<<) --- Using the Creators' trick for overlapping String instances class ShowArgs a where - showArgs :: a -> Args - showListArgs :: [a] -> Args - showListArgs = mconcat . map showArgs + showArgs :: a -> Args -instance ShowArgs Char where - showArgs c = return [[c]] - showListArgs s = return [s] +instance ShowArgs [String] where + showArgs = return -instance ShowArgs a => ShowArgs [a] where - showArgs = showListArgs +instance ShowArgs [Arg] where + showArgs = sequence + +instance ShowArgs [Args] where + showArgs = mconcat instance ShowArgs a => ShowArgs (Action a) where showArgs = (showArgs =<<) --- TODO: improve args type safety args :: ShowArgs a => a -> Args args = showArgs arg :: ShowArg a => a -> Args -arg = args . showArg - --- Combine two heterogeneous ShowArgs values -(<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args -a <+> b = (<>) <$> showArgs a <*> showArgs b - -infixr 6 <+> +arg a = args [showArg a] -- Filter out given arg(s) from a collection filterOut :: ShowArgs a => Args -> a -> Args @@ -85,7 +76,7 @@ filterOut as exclude = do filter (`notElem` exclude') <$> as -- Generate a cross product collection of two argument collections --- Example: productArgs ["-a", "-b"] "c" = arg ["-a", "c", "-b", "c"] +-- Example: productArgs ["-a", "-b"] "c" = args ["-a", "c", "-b", "c"] productArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args productArgs as bs = do as' <- showArgs as @@ -93,7 +84,7 @@ productArgs as bs = do return $ concat $ sequence [as', bs'] -- Similar to productArgs but concat resulting arguments pairwise --- Example: concatArgs ["-a", "-b"] "c" = arg ["-ac", "-bc"] +-- Example: concatArgs ["-a", "-b"] "c" = args ["-ac", "-bc"] concatArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args concatArgs as bs = do as' <- showArgs as diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 88e357f..d54320f 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -122,10 +122,11 @@ packageArgs stage pathDist = do , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" , if usePackageKey - then productArgs "-this-package-key" (arg $ PackageKey pathDist) - <> productArgs "-package-key" (args $ DepKeys pathDist) - else productArgs "-package-name" (arg $ PackageKey pathDist) - <> productArgs "-package" (args $ Deps pathDist) ] + then productArgs ["-this-package-key"] [arg $ PackageKey pathDist] + <> productArgs ["-package-key" ] [args $ DepKeys pathDist] + else productArgs ["-package-name" ] [arg $ PackageKey pathDist] + <> productArgs ["-package" ] [args $ Deps pathDist] + ] includeGccArgs :: FilePath -> FilePath -> Args includeGccArgs path dist = @@ -145,8 +146,9 @@ includeGhcArgs path dist = [buildDir, unifyPath $ buildDir "autogen"] , pathArgs "-I" path $ IncludeDirs pathDist , arg "-optP-include" -- TODO: Shall we also add -cpp? - , concatArgs "-optP" $ - unifyPath $ buildDir "autogen/cabal_macros.h" ] + , concatArgs ["-optP"] + [unifyPath $ buildDir "autogen/cabal_macros.h"] + ] pkgHsSources :: FilePath -> FilePath -> Action [FilePath] pkgHsSources path dist = do diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 99aee33..fe9ba73 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -23,7 +23,7 @@ ghcArgs (Package _ path _ _) (stage, dist, _) way srcs result = , args $ HsArgs pathDist -- TODO: now we have both -O and -O2 -- <> arg ["-O2"] - , productArgs ["-odir", "-hidir", "-stubdir"] buildDir + , productArgs ["-odir", "-hidir", "-stubdir"] [buildDir] , when (splitObjects stage) $ arg "-split-objs" , args ("-c":srcs) , args ["-o", result] ] diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 602993e..5373f6e 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -24,7 +24,7 @@ configureArgs stage settings = let conf key as = do s <- unwords <$> args as unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = [ commonCcArgs `filterOut` "-Werror" + cflags = [ commonCcArgs `filterOut` ["-Werror"] , args $ ConfCcArgs stage -- , customCcArgs settings -- TODO: bring this back , commonCcWarninigArgs ] -- TODO: check why cflags are glued @@ -37,7 +37,8 @@ configureArgs stage settings = in args [ conf "CFLAGS" cflags , conf "LDFLAGS" ldflags , conf "CPPFLAGS" cppflags - , arg $ concat <$> "--gcc-options=" <+> cflags <+> " " <+> ldflags + , arg $ concat <$> + arg "--gcc-options=" <> args cflags <> arg " " <> args ldflags , conf "--with-iconv-includes" IconvIncludeDirs , conf "--with-iconv-libraries" IconvLibDirs , conf "--with-gmp-includes" GmpIncludeDirs @@ -73,8 +74,8 @@ bootPkgConstraints = args $ do content <- lines <$> liftIO (readFile cabal) let versionLines = filter (("ersion:" `isPrefixOf`) . drop 1) content case versionLines of - [versionLine] -> args ["--constraint", depName ++ " == " - ++ dropWhile (not . isDigit) versionLine ] + [versionLine] -> return $ "--constraint " ++ depName ++ " == " + ++ dropWhile (not . isDigit) versionLine _ -> redError $ "Cannot determine package version in '" ++ unifyPath cabal ++ "'." diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index c861707..8fb27b2 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -16,9 +16,9 @@ ghcArgs (Package name path _ _) (stage, dist, settings) = , packageArgs stage pathDist , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist - , productArgs ["-odir", "-stubdir", "-hidir"] buildDir - , args ["-dep-makefile", depFile ] - , productArgs "-dep-suffix" $ map wayPrefix <$> ways settings + , productArgs ["-odir", "-stubdir", "-hidir"] [buildDir] + , args ["-dep-makefile", depFile] + , productArgs ["-dep-suffix"] $ map wayPrefix <$> ways settings , args $ HsArgs pathDist , args $ pkgHsSources path dist ] From git at git.haskell.org Thu Oct 26 23:25:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:25:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add pkgDataFile to look up the path to package-data.mk of a particular stage/package combination. (304b099) Message-ID: <20171026232557.78BA03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/304b0999ea6282dc3a86e2923bb361a889c5acff/ghc >--------------------------------------------------------------- commit 304b0999ea6282dc3a86e2923bb361a889c5acff Author: Andrey Mokhov Date: Sun Dec 20 18:30:24 2015 +0000 Add pkgDataFile to look up the path to package-data.mk of a particular stage/package combination. >--------------------------------------------------------------- 304b0999ea6282dc3a86e2923bb361a889c5acff src/Rules/Data.hs | 2 +- src/Settings/TargetDirectory.hs | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index b6925d0..b68a1f6 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -32,7 +32,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] + need $ map (pkgDataFile stage) depPkgs need [cabalFile] buildWithResources [(ghcCabal rs, 1)] $ diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 6bcec88..286670b 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,5 +1,6 @@ module Settings.TargetDirectory ( - targetDirectory, targetPath, pkgHaddockFile, pkgLibraryFile, pkgGhciLibraryFile + targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, + pkgGhciLibraryFile ) where import Expression @@ -15,6 +16,9 @@ targetDirectory = userTargetDirectory targetPath :: Stage -> Package -> FilePath targetPath stage pkg = pkgPath pkg -/- targetDirectory stage pkg +pkgDataFile :: Stage -> Package -> FilePath +pkgDataFile stage pkg = targetPath stage pkg -/- "package-data.mk" + -- Relative path to a package haddock file, e.g.: -- "libraries/array/dist-install/doc/html/array/array.haddock" pkgHaddockFile :: Package -> FilePath From git at git.haskell.org Thu Oct 26 23:26:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix bootPkgConstraints. (98cfed5) Message-ID: <20171026232600.A8A6D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/98cfed580f1655de01f706761b4c4b56da22e523/ghc >--------------------------------------------------------------- commit 98cfed580f1655de01f706761b4c4b56da22e523 Author: Andrey Mokhov Date: Fri Jan 30 12:47:22 2015 +0000 Fix bootPkgConstraints. >--------------------------------------------------------------- 98cfed580f1655de01f706761b4c4b56da22e523 src/Package/Data.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 5373f6e..6d108aa 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -74,8 +74,8 @@ bootPkgConstraints = args $ do content <- lines <$> liftIO (readFile cabal) let versionLines = filter (("ersion:" `isPrefixOf`) . drop 1) content case versionLines of - [versionLine] -> return $ "--constraint " ++ depName ++ " == " - ++ dropWhile (not . isDigit) versionLine + [versionLine] -> return $ args ["--constraint", depName ++ " == " + ++ dropWhile (not . isDigit) versionLine] _ -> redError $ "Cannot determine package version in '" ++ unifyPath cabal ++ "'." From git at git.haskell.org Thu Oct 26 23:26:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add verboseCommands predicate to show executed commands in full when needed. (f48da18) Message-ID: <20171026232600.F07393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f48da1844187e9dab91be2038d0675b6d1eb90b8/ghc >--------------------------------------------------------------- commit f48da1844187e9dab91be2038d0675b6d1eb90b8 Author: Andrey Mokhov Date: Sun Dec 20 18:41:44 2015 +0000 Add verboseCommands predicate to show executed commands in full when needed. >--------------------------------------------------------------- f48da1844187e9dab91be2038d0675b6d1eb90b8 src/Rules/Actions.hs | 11 +++++++---- src/Settings/User.hs | 9 ++++++++- 2 files changed, 15 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index cdc2e17..805c771 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -16,13 +16,16 @@ buildWithResources rs target = do needBuilder laxDependencies builder path <- builderPath builder argList <- interpret target getArgs + verbose <- interpret target verboseCommands + let quitelyUnlessVerbose = if verbose then withVerbosity Loud else quietly -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do - putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList - putBuild $ "\\--------" - quietly $ case builder of + unless verbose $ do + putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" + mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList + putBuild $ "\\--------" + quitelyUnlessVerbose $ case builder of Ar -> arCmd path argList HsCpp -> do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 0dffbfd..4c7a5f4 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -2,7 +2,8 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile + ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, + verboseCommands ) where import Expression @@ -81,3 +82,9 @@ buildHaddock = return True buildSystemConfigFile :: Bool buildSystemConfigFile = False + +-- Set to True to print full command lines during the build process. Note, this +-- is a Predicate, hence you can enable verbose output for a chosen package +-- only, e.g.: verboseCommands = package ghcPrim +verboseCommands :: Predicate +verboseCommands = return False From git at git.haskell.org Thu Oct 26 23:26:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement customise :: Package -> Package function. (eafd5e0) Message-ID: <20171026232604.1DB083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb/ghc >--------------------------------------------------------------- commit eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb Author: Andrey Mokhov Date: Mon Feb 9 14:48:18 2015 +0000 Implement customise :: Package -> Package function. >--------------------------------------------------------------- eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb src/Package/Base.hs | 27 ++++++------ src/Package/Data.hs | 15 +++---- src/Targets.hs | 119 +++++++++++++++++++++++----------------------------- 3 files changed, 74 insertions(+), 87 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 eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb From git at git.haskell.org Thu Oct 26 23:26:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: README: Add basic instructions for Linux (5211197) Message-ID: <20171026232604.63AC33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/52111971658afeafdcd3e3f13fecd29e672549e8/ghc >--------------------------------------------------------------- commit 52111971658afeafdcd3e3f13fecd29e672549e8 Author: Ben Gamari Date: Sun Dec 20 14:04:05 2015 +0100 README: Add basic instructions for Linux >--------------------------------------------------------------- 52111971658afeafdcd3e3f13fecd29e672549e8 README.md | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/README.md b/README.md index 05f3352..63673e3 100644 --- a/README.md +++ b/README.md @@ -4,3 +4,18 @@ Shaking up GHC As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). This is supposed to go into the `shake-build` directory of the GHC source tree. + +Trying it +--------- + +On Linux, +``` +$ git clone git://git.haskell.org/ghc +$ cd ghc +$ git submodule update --init +$ git clone git://github.com/snowleopard/shaking-up-ghc shake-build +$ ./boot +$ ./configure +$ make inplace/bin/ghc-cabal # This needs to be fixed +$ shake-build/build.sh +``` From git at git.haskell.org Thu Oct 26 23:26:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep Haskell-land settings in Settings.hs. (9d35421) Message-ID: <20171026232607.834503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d35421d9ba504fb9e412027d574b455b94ff90c/ghc >--------------------------------------------------------------- commit 9d35421d9ba504fb9e412027d574b455b94ff90c Author: Andrey Mokhov Date: Mon Feb 9 14:49:19 2015 +0000 Keep Haskell-land settings in Settings.hs. >--------------------------------------------------------------- 9d35421d9ba504fb9e412027d574b455b94ff90c src/Base.hs | 2 ++ src/Settings.hs | 18 ++++++++++++++++++ 2 files changed, 20 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index fa9104a..923e13d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,6 +7,7 @@ module Base ( module Data.Function, module Data.Monoid, module Data.List, + module Settings, Stage (..), Arg, Args, ShowArg (..), ShowArgs (..), @@ -22,6 +23,7 @@ import Control.Applicative import Data.Function import Data.Monoid import Data.List +import Settings data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) diff --git a/src/Settings.hs b/src/Settings.hs new file mode 100644 index 0000000..6ffc976 --- /dev/null +++ b/src/Settings.hs @@ -0,0 +1,18 @@ +module Settings ( + IntegerLibrary (..), integerLibrary, + buildHaddock + ) where + +data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple + +instance Show IntegerLibrary where + show library = case library of + IntegerGmp -> "integer-gmp" + IntegerGmp2 -> "integer-gmp2" + IntegerSimple -> "integer-simple" + +integerLibrary :: IntegerLibrary +integerLibrary = IntegerGmp2 + +buildHaddock :: Bool +buildHaddock = True From git at git.haskell.org Thu Oct 26 23:26:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Documentation: Move HsColour invocation to after `need` (8e8cc53) Message-ID: <20171026232607.C50553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e8cc532db9c18fb9b3867b3ceb0e730a93493ff/ghc >--------------------------------------------------------------- commit 8e8cc532db9c18fb9b3867b3ceb0e730a93493ff Author: Ben Gamari Date: Sun Dec 20 16:43:12 2015 +0100 Documentation: Move HsColour invocation to after `need` HsColour also depends upon the sources existing. Fixes #6. >--------------------------------------------------------------- 8e8cc532db9c18fb9b3867b3ceb0e730a93493ff src/Rules/Documentation.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 2ebaa59..495a16c 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -15,14 +15,18 @@ buildPackageDocumentation _ target @ (PartialTarget stage package) = haddockFile = pkgHaddockFile package in when (stage == Stage1) $ do haddockFile %> \file -> do - whenM (specified HsColour) $ do - need [cabalFile] - build $ fullTarget target GhcCabalHsColour [cabalFile] [] srcs <- interpretPartial target getPackageSources deps <- interpretPartial target $ getPkgDataList DepNames let haddocks = [ pkgHaddockFile depPkg | Just depPkg <- map findKnownPackage deps ] need $ srcs ++ haddocks + + -- HsColour sources + whenM (specified HsColour) $ do + need [cabalFile] + build $ fullTarget target GhcCabalHsColour [cabalFile] [] + + -- Build Haddock documentation let haddockWay = if dynamicGhcPrograms then dynamic else vanilla build $ fullTargetWithWay target Haddock haddockWay srcs [file] From git at git.haskell.org Thu Oct 26 23:26:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix cabalName in libraryPackage. (ba209b9) Message-ID: <20171026232611.87EA83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba209b90b53ff9b6bfe32f4f890fc2911c274122/ghc >--------------------------------------------------------------- commit ba209b90b53ff9b6bfe32f4f890fc2911c274122 Author: Andrey Mokhov Date: Mon Feb 9 15:14:08 2015 +0000 Fix cabalName in libraryPackage. >--------------------------------------------------------------- ba209b90b53ff9b6bfe32f4f890fc2911c274122 src/Package/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 076bc2a..7f310d1 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -84,7 +84,7 @@ libraryPackage name cabalName stages settings = Package name (unifyPath $ "libraries" name) - (unifyPath $ "libraries" name cabalName <.> "cabal") + cabalName [ (stage , if stage == Stage0 then "dist-boot" else "dist-install" , settings stage) From git at git.haskell.org Thu Oct 26 23:26:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Actions: Factor out box drawing (9d2868b) Message-ID: <20171026232611.C74F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d2868b107cce0af8445ec6ce8471ba1d45e3042/ghc >--------------------------------------------------------------- commit 9d2868b107cce0af8445ec6ce8471ba1d45e3042 Author: Ben Gamari Date: Sun Dec 20 17:21:47 2015 +0100 Actions: Factor out box drawing Also add (currently broken) Unicode support although this is broken by Shake, the console output interface of which is badly broken (see Shake #364) >--------------------------------------------------------------- 9d2868b107cce0af8445ec6ce8471ba1d45e3042 src/Rules/Actions.hs | 25 ++++++++++++++++++++----- 1 file changed, 20 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 805c771..775524a 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -7,6 +7,22 @@ import Settings.Args import Settings.Builders.Ar import qualified Target +insideBox :: [String] -> String +insideBox ls = + unlines $ [begin] ++ map (bar++) ls ++ [end] + where + (begin,bar,end) + | useUnicode = ( "╭──────────" + , "│ " + , "╰──────────" + ) + | otherwise = ( "/----------" + , "| " + , "\\----------" + ) + -- FIXME: See Shake #364. + useUnicode = False + -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last -- built (that is, track changes in the build system). @@ -17,15 +33,14 @@ buildWithResources rs target = do path <- builderPath builder argList <- interpret target getArgs verbose <- interpret target verboseCommands - let quitelyUnlessVerbose = if verbose then withVerbosity Loud else quietly + let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do unless verbose $ do - putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList - putBuild $ "\\--------" - quitelyUnlessVerbose $ case builder of + putBuild $ insideBox $ [ "Running " ++ show builder ++ " with arguments:" ] + ++ map (" "++) (interestingInfo builder argList) + quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList HsCpp -> do From git at git.haskell.org Thu Oct 26 23:26:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix comments. (77766e8) Message-ID: <20171026232615.66B793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/77766e8e875b069d05c9a536811df20796d023c5/ghc >--------------------------------------------------------------- commit 77766e8e875b069d05c9a536811df20796d023c5 Author: Andrey Mokhov Date: Mon Feb 9 15:40:44 2015 +0000 Fix comments. >--------------------------------------------------------------- 77766e8e875b069d05c9a536811df20796d023c5 src/Package/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 7f310d1..2738b83 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -52,7 +52,7 @@ defaultSettings stage = Settings -- The typical structure of that directory is: -- * build/ : contains compiled object code -- * doc/ : produced by haddock --- * package-data.mk : contains output of ghc-cabal applied to package.cabal +-- * package-data.mk : contains output of ghc-cabal applied to pkgCabal.cabal -- Settings may be different for different combinations of Stage & FilePath -- TODO: the above may be incorrect, settings seem to *only* depend on the -- stage. In fact Stage seem to define FilePath and Settings, therefore we From git at git.haskell.org Thu Oct 26 23:26:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix detection of libraries (86ed4e3) Message-ID: <20171026232615.A6E5A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86ed4e32b39b0ab57e64fbd93cccfb8113d162b7/ghc >--------------------------------------------------------------- commit 86ed4e32b39b0ab57e64fbd93cccfb8113d162b7 Author: Ben Gamari Date: Sun Dec 20 20:23:34 2015 +0100 Fix detection of libraries Previously a very fragile heuristic was used. Now we explicitly declare this. Perhaps a better option in the future would be to instead emit this information from `ghc-cabal` and pick it up from `package-data.mk`. Fixes #9. >--------------------------------------------------------------- 86ed4e32b39b0ab57e64fbd93cccfb8113d162b7 src/GHC.hs | 2 +- src/Package.hs | 37 ++++++++++++++++++++++++++----------- src/Rules/Data.hs | 3 ++- src/Settings.hs | 3 ++- src/Settings/TargetDirectory.hs | 2 +- 5 files changed, 32 insertions(+), 15 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0279197..c38af04 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -51,7 +51,7 @@ dllSplit = utility "dll-split" filepath = library "filepath" genapply = utility "genapply" genprimopcode = utility "genprimopcode" -ghc = topLevel "ghc-bin" `setPath` "ghc" +ghc = topLevel "ghc-bin" `setPath` "ghc" `setPkgType` Program ghcBoot = library "ghc-boot" ghcCabal = utility "ghc-cabal" ghci = library "ghci" diff --git a/src/Package.hs b/src/Package.hs index 8415bf1..6273a62 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,23 +1,31 @@ {-# LANGUAGE DeriveGeneric #-} module Package ( - Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility, - matchPackageNames + Package (..), PackageName, PackageType (..), + -- * Queries + pkgCabalFile, + matchPackageNames, + -- * Helpers for constructing 'Package's + setPath, topLevel, library, utility, setPkgType ) where import Base import GHC.Generics (Generic) --- It is helpful to distinguish package names from strings. +-- | It is helpful to distinguish package names from strings. type PackageName = String --- type PackageType = Program | Library +-- | We regard packages as either being libraries or programs. This is +-- bit of a convenient lie as Cabal packages can be both, but it works +-- for now. +data PackageType = Program | Library + deriving Generic --- pkgPath is the path to the source code relative to the root data Package = Package { - pkgName :: PackageName, -- Examples: "ghc", "Cabal" - pkgPath :: FilePath -- "compiler", "libraries/Cabal/Cabal" - -- pkgType :: PackageType -- TopLevel, Library + pkgName :: PackageName, -- ^ Examples: "ghc", "Cabal" + pkgPath :: FilePath, -- ^ pkgPath is the path to the source code relative to the root. + -- e.g. "compiler", "libraries/Cabal/Cabal" + pkgType :: PackageType } deriving Generic @@ -26,17 +34,20 @@ pkgCabalFile :: Package -> FilePath pkgCabalFile pkg = pkgPath pkg -/- pkgName pkg <.> "cabal" topLevel :: PackageName -> Package -topLevel name = Package name name +topLevel name = Package name name Library library :: PackageName -> Package -library name = Package name ("libraries" -/- name) +library name = Package name ("libraries" -/- name) Library utility :: PackageName -> Package -utility name = Package name ("utils" -/- name) +utility name = Package name ("utils" -/- name) Program setPath :: Package -> FilePath -> Package setPath pkg path = pkg { pkgPath = path } +setPkgType :: Package -> PackageType -> Package +setPkgType pkg ty = pkg { pkgType = ty } + instance Show Package where show = pkgName @@ -56,3 +67,7 @@ instance Binary Package instance Hashable Package where hashWithSalt salt = hashWithSalt salt . show instance NFData Package + +instance Binary PackageType +instance Hashable PackageType +instance NFData PackageType diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index b68a1f6..fdbe21d 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -38,7 +38,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do buildWithResources [(ghcCabal rs, 1)] $ fullTarget target GhcCabal [cabalFile] outs - -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg + -- ghc-pkg produces inplace-pkg-config when run on packages with + -- library components only when (isLibrary pkg) . whenM (interpretPartial target registerPackage) . buildWithResources [(ghcPkg rs, 1)] $ diff --git a/src/Settings.hs b/src/Settings.hs index d16c5cd..7a1ab72 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -33,7 +33,8 @@ programPath :: Stage -> Package -> Maybe FilePath programPath = userProgramPath isLibrary :: Package -> Bool -isLibrary pkg = programPath Stage0 pkg == Nothing +isLibrary (Package {pkgType=Library}) = True +isLibrary _ = False -- Find all Haskell source files for the current target. TODO: simplify. getPackageSources :: Expr [FilePath] diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 286670b..a4301f4 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -22,7 +22,7 @@ pkgDataFile stage pkg = targetPath stage pkg -/- "package-data.mk" -- Relative path to a package haddock file, e.g.: -- "libraries/array/dist-install/doc/html/array/array.haddock" pkgHaddockFile :: Package -> FilePath -pkgHaddockFile pkg @ (Package name _) = +pkgHaddockFile pkg @ (Package name _ _) = targetPath Stage1 pkg -/- "doc/html" -/- name -/- name <.> "haddock" -- Relative path to a package library file, e.g.: From git at git.haskell.org Thu Oct 26 23:26:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (14a236b) Message-ID: <20171026232619.231733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14a236b420ac7a03ef68b6a193efe10936dc10b8/ghc >--------------------------------------------------------------- commit 14a236b420ac7a03ef68b6a193efe10936dc10b8 Author: Andrey Mokhov Date: Mon Feb 9 22:25:30 2015 +0000 Clean up. >--------------------------------------------------------------- 14a236b420ac7a03ef68b6a193efe10936dc10b8 src/Base.hs | 2 -- src/Oracles/Flag.hs | 2 +- src/Package/Base.hs | 2 ++ src/Targets.hs | 3 --- 4 files changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 923e13d..fa9104a 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,6 @@ module Base ( module Data.Function, module Data.Monoid, module Data.List, - module Settings, Stage (..), Arg, Args, ShowArg (..), ShowArgs (..), @@ -23,7 +22,6 @@ import Control.Applicative import Data.Function import Data.Monoid import Data.List -import Settings data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index fa29415..8149619 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -7,9 +7,9 @@ module Oracles.Flag ( test, when, unless, not, (&&), (||) ) where -import Control.Monad hiding (when, unless) import qualified Prelude import Prelude hiding (not, (&&), (||)) +import Control.Monad hiding (when, unless) import Base import Util import Oracles.Base diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 2738b83..40d893e 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -4,6 +4,7 @@ module Package.Base ( module Ways, module Util, module Oracles, + module Settings, Package (..), Settings (..), TodoItem (..), defaultSettings, library, customise, updateSettings, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, @@ -20,6 +21,7 @@ import Base import Ways import Util import Oracles +import Settings import qualified System.Directory as S data Settings = Settings diff --git a/src/Targets.hs b/src/Targets.hs index 19cb664..bdfb2ee 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -5,9 +5,6 @@ module Targets ( import Package.Base -integerLibraryName :: String -integerLibraryName = show integerLibrary - -- These are the packages we build: -- TODO: this should eventually be removed and replaced by the top-level -- target, i.e. GHC (and perhaps, something else) From git at git.haskell.org Thu Oct 26 23:26:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #8 from bgamari/master (821d9e9) Message-ID: <20171026232619.6F5183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/821d9e9c6b81381c1dff2c78755a525f4d3543a1/ghc >--------------------------------------------------------------- commit 821d9e9c6b81381c1dff2c78755a525f4d3543a1 Merge: f48da18 86ed4e3 Author: Andrey Mokhov Date: Sun Dec 20 19:34:47 2015 +0000 Merge pull request #8 from bgamari/master Miscellany >--------------------------------------------------------------- 821d9e9c6b81381c1dff2c78755a525f4d3543a1 README.md | 15 +++++++++++++++ src/GHC.hs | 2 +- src/Package.hs | 37 ++++++++++++++++++++++++++----------- src/Rules/Actions.hs | 25 ++++++++++++++++++++----- src/Rules/Data.hs | 3 ++- src/Rules/Documentation.hs | 10 +++++++--- src/Settings.hs | 3 ++- src/Settings/TargetDirectory.hs | 2 +- 8 files changed, 74 insertions(+), 23 deletions(-) From git at git.haskell.org Thu Oct 26 23:26:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Experiment with parameterised graphs. (8f52904) Message-ID: <20171026232622.B463D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f52904d2c05f7503b142fa48eb46eb7945e450c/ghc >--------------------------------------------------------------- commit 8f52904d2c05f7503b142fa48eb46eb7945e450c Author: Andrey Mokhov Date: Mon Feb 9 22:25:52 2015 +0000 Experiment with parameterised graphs. >--------------------------------------------------------------- 8f52904d2c05f7503b142fa48eb46eb7945e450c src/Settings.hs | 94 ++++++++++++++++++++++++++++++++++++++++++++++++++++----- 1 file changed, 87 insertions(+), 7 deletions(-) diff --git a/src/Settings.hs b/src/Settings.hs index 6ffc976..42ceed9 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,18 +1,98 @@ +{-# LANGUAGE FlexibleInstances #-} + module Settings ( - IntegerLibrary (..), integerLibrary, + IntegerLibrary (..), integerLibrary, integerLibraryName, buildHaddock ) where -data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple +import Base +import Ways -instance Show IntegerLibrary where - show library = case library of - IntegerGmp -> "integer-gmp" - IntegerGmp2 -> "integer-gmp2" - IntegerSimple -> "integer-simple" +data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple integerLibrary :: IntegerLibrary integerLibrary = IntegerGmp2 +integerLibraryName :: String +integerLibraryName = case integerLibrary of + IntegerGmp -> "integer-gmp" + IntegerGmp2 -> "integer-gmp2" + IntegerSimple -> "integer-simple" + buildHaddock :: Bool buildHaddock = True + +-- A Parameterised Graph datatype for storing argument lists with conditions +data PG a b = Epsilon + | Vertex a + | Overlay (PG a b) (PG a b) + | Sequence (PG a b) (PG a b) + | Condition b (PG a b) + +instance Monoid (PG a b) where + mempty = Epsilon + mappend = Overlay + +type ArgsExpression = PG String Predicate +type WaysExpression = PG Way Predicate + +data Match = MatchPackage FilePath -- Match a Package name + | MatchFile FilePath -- Match a file + | MatchStage Stage -- Match a Stage + | MatchWay Way -- Match a Way + | MatchKeyValue String String -- Match a key with a value (config) + +-- A Matcher takes a Match description and attempts to evaluate it. +-- Returns Nothing if the attempt fails. +type Matcher = Match -> Maybe Bool + +-- A Monoid instance for matchers (returns first successful match) +instance Monoid Matcher where + mempty = const Nothing + p `mappend` q = \m -> getFirst $ First (p m) <> First (q m) + +data Predicate = Evaluated Bool -- Evaluated predicate + | If Match -- Perform a match to evaluate + | Not Predicate -- Negate predicate + | And Predicate Predicate -- Conjunction of two predicates + | Or Predicate Predicate -- Disjunction of two predicates + +match :: Predicate -> Matcher -> Predicate +match p @ (Evaluated _) _ = p +match p @ (If match ) m = case m match of + Just bool -> Evaluated bool + Nothing -> p +match (Not p ) m = match p m +match (And p q) m = And (match p m) (match q m) +match (Or p q) m = Or (match p m) (match q m) + +-- returns Nothing if the given predicate cannot be uniquely evaluated +evalPredicate :: Predicate -> Maybe Bool +evalPredicate (Evaluated bool) = Just bool +evalPredicate (Not p) = not <$> evalPredicate p +evalPredicate (And p q) + | p' == Just False || q' == Just False = Just False + | p' == Just True && q' == Just True = Just True + | otherwise = Nothing + where + p' = evalPredicate p + q' = evalPredicate q +evalPredicate (Or p q) + | p' == Just True || q' == Just True = Just True + | p' == Just False && q' == Just False = Just False + | otherwise = Nothing + where + p' = evalPredicate p + q' = evalPredicate q +evalPredicate (If _) = Nothing + +-- returns Nothing if the given expression cannot be uniquely evaluated +evalPG :: PG a Predicate -> Maybe [a] +evalPG Epsilon = Just [] +evalPG (Vertex v) = Just [v] +evalPG (Overlay p q) = (++) <$> evalPG p <*> evalPG q +evalPG (Sequence p q) = (++) <$> evalPG p <*> evalPG q +evalPG (Condition x p) = case evalPredicate x of + Just True -> evalPG p + Just False -> Just [] + Nothing -> Nothing From git at git.haskell.org Thu Oct 26 23:26:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rules: Refactor generateTargets (c84445f) Message-ID: <20171026232623.11EC23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c84445f81aafbe4089d860ae4a3e0c020a38b118/ghc >--------------------------------------------------------------- commit c84445f81aafbe4089d860ae4a3e0c020a38b118 Author: Ben Gamari Date: Sun Dec 20 20:49:29 2015 +0100 Rules: Refactor generateTargets This previously used `fromJust`, which bottomed due to the recent `isLibrary` change. >--------------------------------------------------------------- c84445f81aafbe4089d860ae4a3e0c020a38b118 src/Rules.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 505b8a5..55ff066 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -10,12 +10,12 @@ generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpretWithStage stage getPackages - let (libPkgs, programPkgs) = partition isLibrary pkgs + let libPkgs = filter isLibrary pkgs libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg needHaddock <- interpretPartial target buildHaddock - return $ [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] - let programTargets = map (fromJust . programPath stage) programPkgs + return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] + let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] return $ libTargets ++ programTargets need $ reverse targets From git at git.haskell.org Thu Oct 26 23:26:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement basic infrastructure for parameterised expressions. (a5a8d53) Message-ID: <20171026232626.28B453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a8d53e5cca5cb6a5609bde961d6f560fbb143f/ghc >--------------------------------------------------------------- commit a5a8d53e5cca5cb6a5609bde961d6f560fbb143f Author: Andrey Mokhov Date: Tue Feb 10 02:44:34 2015 +0000 Implement basic infrastructure for parameterised expressions. >--------------------------------------------------------------- a5a8d53e5cca5cb6a5609bde961d6f560fbb143f src/Base.hs | 2 +- src/Settings.hs | 165 +++++++++++++++++++++++++++++++++++++++++--------------- 2 files changed, 122 insertions(+), 45 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fa9104a..49b0fb2 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,7 +16,7 @@ module Base ( productArgs, concatArgs ) where -import Development.Shake hiding ((*>)) +import Development.Shake hiding ((*>), alternatives) import Development.Shake.FilePath import Control.Applicative import Data.Function diff --git a/src/Settings.hs b/src/Settings.hs index 42ceed9..aaec2ab 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -7,6 +7,7 @@ module Settings ( import Base import Ways +import Oracles.Builder data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple @@ -22,52 +23,45 @@ integerLibraryName = case integerLibrary of buildHaddock :: Bool buildHaddock = True --- A Parameterised Graph datatype for storing argument lists with conditions -data PG a b = Epsilon - | Vertex a - | Overlay (PG a b) (PG a b) - | Sequence (PG a b) (PG a b) - | Condition b (PG a b) +-- A generic Parameterised Graph datatype for parameterised argument lists +data PG p v = Epsilon + | Vertex v + | Overlay (PG p v) (PG p v) + | Sequence (PG p v) (PG p v) + | Condition p (PG p v) -instance Monoid (PG a b) where +instance Monoid (PG p v) where mempty = Epsilon mappend = Overlay -type ArgsExpression = PG String Predicate -type WaysExpression = PG Way Predicate +data Predicate a = Evaluated Bool -- Evaluated predicate + | Parameter a -- To be evaluated later + | Not (Predicate a) -- Negate predicate + | And (Predicate a) (Predicate a) -- Conjunction + | Or (Predicate a) (Predicate a) -- Disjunction -data Match = MatchPackage FilePath -- Match a Package name - | MatchFile FilePath -- Match a file - | MatchStage Stage -- Match a Stage - | MatchWay Way -- Match a Way - | MatchKeyValue String String -- Match a key with a value (config) - --- A Matcher takes a Match description and attempts to evaluate it. +-- Evaluator takes a Parameter and attempts to evaluate it. -- Returns Nothing if the attempt fails. -type Matcher = Match -> Maybe Bool +type Evaluator a = a -> Maybe Bool --- A Monoid instance for matchers (returns first successful match) -instance Monoid Matcher where +-- Monoid instance for evaluators (returns first successful evaluation) +instance Monoid (Evaluator a) where mempty = const Nothing - p `mappend` q = \m -> getFirst $ First (p m) <> First (q m) - -data Predicate = Evaluated Bool -- Evaluated predicate - | If Match -- Perform a match to evaluate - | Not Predicate -- Negate predicate - | And Predicate Predicate -- Conjunction of two predicates - | Or Predicate Predicate -- Disjunction of two predicates + e `mappend` f = \p -> getFirst $ First (e p) <> First (f p) -match :: Predicate -> Matcher -> Predicate -match p @ (Evaluated _) _ = p -match p @ (If match ) m = case m match of +-- Apply an evalulator to a predicate (partial evaluation, or projection) +apply :: Evaluator a -> Predicate a -> Predicate a +apply _ p @ (Evaluated _) = p +apply e p @ (Parameter q) = case e q of Just bool -> Evaluated bool Nothing -> p -match (Not p ) m = match p m -match (And p q) m = And (match p m) (match q m) -match (Or p q) m = Or (match p m) (match q m) +apply e (Not p ) = Not (apply e p) +apply e (And p q) = And (apply e p) (apply e q) +apply e (Or p q) = Or (apply e p) (apply e q) --- returns Nothing if the given predicate cannot be uniquely evaluated -evalPredicate :: Predicate -> Maybe Bool +-- Attempt to evaluate a predicate. Returns Nothing if the predicate +-- cannot be uniquely evaluated due to remaining parameters. +evalPredicate :: Predicate a -> Maybe Bool evalPredicate (Evaluated bool) = Just bool evalPredicate (Not p) = not <$> evalPredicate p evalPredicate (And p q) @@ -84,15 +78,98 @@ evalPredicate (Or p q) where p' = evalPredicate p q' = evalPredicate q -evalPredicate (If _) = Nothing - --- returns Nothing if the given expression cannot be uniquely evaluated -evalPG :: PG a Predicate -> Maybe [a] -evalPG Epsilon = Just [] -evalPG (Vertex v) = Just [v] -evalPG (Overlay p q) = (++) <$> evalPG p <*> evalPG q -evalPG (Sequence p q) = (++) <$> evalPG p <*> evalPG q -evalPG (Condition x p) = case evalPredicate x of - Just True -> evalPG p +evalPredicate (Parameter _) = Nothing -- cannot evaluate Parameter + +-- Flatten a PG into a list. Returns Nothing if the given expression +-- cannot be uniquely evaluated due to remaining parameters. +linearise :: PG (Predicate a) v -> Maybe [v] +linearise Epsilon = Just [] +linearise (Vertex v) = Just [v] +linearise (Overlay p q) = (++) <$> linearise p <*> linearise q +linearise (Sequence p q) = (++) <$> linearise p <*> linearise q +linearise (Condition x p) = case evalPredicate x of + Just True -> linearise p Just False -> Just [] Nothing -> Nothing + +(~>) :: PG p v -> PG p v -> PG p v +a ~> b = Sequence a b + +type PGP p v = PG (Predicate p) v + +disjuction :: [a] -> (a -> Predicate p) -> PGP p v -> PGP p v +disjuction [] _ = id +disjuction (a:as) convert = Condition (foldr Or (convert a) $ map convert as) + +-- GHC build specific + +data BuildParameter = WhenPackage FilePath + | WhenBuilder Builder + | WhenStage Stage + | WhenWay Way + | WhenFile FilePath + | WhenKeyValue String String -- from config files + +type Expression a = PGP BuildParameter a + +type Rewrite a = Expression a -> Expression a + +type ArgsExpression = Expression String + +alternatives :: (b -> BuildParameter) -> [b] -> Rewrite a +alternatives p bs = disjuction bs (Parameter . p) + +whenPackages :: [FilePath] -> Rewrite a +whenPackages = alternatives WhenPackage + +whenBuilders :: [Builder] -> Rewrite a +whenBuilders = alternatives WhenBuilder + +whenStages :: [Stage] -> Rewrite a +whenStages = alternatives WhenStage + +unlessStage :: Stage -> Rewrite a +unlessStage stage = Condition (Not $ Parameter $ WhenStage stage) + +whenWays :: [Way] -> Rewrite a +whenWays = alternatives WhenWay + +whenFiles :: [FilePath] -> Rewrite a +whenFiles = alternatives WhenFile + +whenKeyValues :: String -> [String] -> Rewrite a +whenKeyValues key = alternatives (WhenKeyValue key) + +whenKeyValue :: String -> String -> Rewrite a +whenKeyValue key value = whenKeyValues key [value] + +whenPackageKey :: Rewrite a +whenPackageKey = whenKeyValue "supports-package-key" "YES" . unlessStage Stage0 + +--packageArgs = +-- Vertex "-hide-all-packages" +-- ~> +-- Vertex "-no-user-package-db" +-- ~> +-- Vertex "-include-pkg-deps" +-- ~> If (MatchStage Stage0) +-- (Vertex "-package-db libraries/bootstrapping.conf") +-- ~> If usePackageKey +-- ( + +-- ) + +--packageArgs :: Stage -> FilePath -> Args +--packageArgs stage pathDist = do +-- usePackageKey <- SupportsPackageKey || stage /= Stage0 +-- args [ arg "-hide-all-packages" +-- , arg "-no-user-package-db" +-- , arg "-include-pkg-deps" +-- , when (stage == Stage0) $ +-- arg "-package-db libraries/bootstrapping.conf" +-- , if usePackageKey +-- then productArgs ["-this-package-key"] [arg $ PackageKey pathDist] +-- <> productArgs ["-package-key" ] [args $ DepKeys pathDist] +-- else productArgs ["-package-name" ] [arg $ PackageKey pathDist] +-- <> productArgs ["-package" ] [args $ Deps pathDist] +-- ] From git at git.haskell.org Thu Oct 26 23:26:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GHC: Set PackageType of iservBin (139d90d) Message-ID: <20171026232626.72FB23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/139d90d43b6a8fb125ea05136531848cebb96096/ghc >--------------------------------------------------------------- commit 139d90d43b6a8fb125ea05136531848cebb96096 Author: Ben Gamari Date: Sun Dec 20 20:45:05 2015 +0100 GHC: Set PackageType of iservBin >--------------------------------------------------------------- 139d90d43b6a8fb125ea05136531848cebb96096 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index c38af04..29db671 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -68,7 +68,7 @@ hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" integerGmp = library "integer-gmp" integerSimple = library "integer-simple" -iservBin = topLevel "iserv-bin" `setPath` "iserv" +iservBin = topLevel "iserv-bin" `setPath` "iserv" `setPkgType` Program mkUserGuidePart = utility "mkUserGuidePart" parallel = library "parallel" pretty = library "pretty" From git at git.haskell.org Thu Oct 26 23:26:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Eq instances. (27bc02e) Message-ID: <20171026232629.908703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27bc02eb27cefd49c0292a6190b269c5dd2bb4b7/ghc >--------------------------------------------------------------- commit 27bc02eb27cefd49c0292a6190b269c5dd2bb4b7 Author: Andrey Mokhov Date: Wed Feb 11 03:22:35 2015 +0000 Add Eq instances. >--------------------------------------------------------------- 27bc02eb27cefd49c0292a6190b269c5dd2bb4b7 src/Oracles/Builder.hs | 2 +- src/Package/Base.hs | 5 +++-- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 07b1bbd..d538611 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -29,7 +29,7 @@ data Builder = Ar | Gcc Stage | Ghc Stage | GhcPkg Stage - deriving Show + deriving (Show, Eq) instance ShowArg Builder where showArg builder = toStandard <$> do diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 40d893e..e3c38e7 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -4,7 +4,6 @@ module Package.Base ( module Ways, module Util, module Oracles, - module Settings, Package (..), Settings (..), TodoItem (..), defaultSettings, library, customise, updateSettings, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, @@ -21,7 +20,6 @@ import Base import Ways import Util import Oracles -import Settings import qualified System.Directory as S data Settings = Settings @@ -72,6 +70,9 @@ data Package = Package pkgTodo :: [TodoItem] -- [(Stage1, "dist-install", defaultSettings)] } +instance Eq Package where + (==) = (==) `on` pkgName + updateSettings :: (Settings -> Settings) -> Package -> Package updateSettings update (Package name path cabal todo) = Package name path cabal (map updateTodo todo) From git at git.haskell.org Thu Oct 26 23:26:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #11 from bgamari/master (5c42b58) Message-ID: <20171026232629.D5A4B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5c42b582cb8c05741cc5be87dd3ec2f935997f56/ghc >--------------------------------------------------------------- commit 5c42b582cb8c05741cc5be87dd3ec2f935997f56 Merge: 821d9e9 c84445f Author: Andrey Mokhov Date: Sun Dec 20 20:15:12 2015 +0000 Merge pull request #11 from bgamari/master Fix fallout from previous refactoring >--------------------------------------------------------------- 5c42b582cb8c05741cc5be87dd3ec2f935997f56 src/GHC.hs | 2 +- src/Rules.hs | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) From git at git.haskell.org Thu Oct 26 23:26:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement predicates and evaluators. (71be3a8) Message-ID: <20171026232633.A56D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/71be3a823ae81fde9371e93cd9efa9ffbb9a6cea/ghc >--------------------------------------------------------------- commit 71be3a823ae81fde9371e93cd9efa9ffbb9a6cea Author: Andrey Mokhov Date: Wed Feb 11 03:23:27 2015 +0000 Implement predicates and evaluators. >--------------------------------------------------------------- 71be3a823ae81fde9371e93cd9efa9ffbb9a6cea src/Settings.hs | 114 ++++++++++++++++++++++++++++++++++++++++++++------------ src/Targets.hs | 1 + 2 files changed, 92 insertions(+), 23 deletions(-) diff --git a/src/Settings.hs b/src/Settings.hs index aaec2ab..6d25a92 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -7,6 +7,7 @@ module Settings ( import Base import Ways +import Package.Base (Package) import Oracles.Builder data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple @@ -34,23 +35,36 @@ instance Monoid (PG p v) where mempty = Epsilon mappend = Overlay +fromList :: [v] -> PG p v +fromList = foldr Sequence Epsilon . map Vertex + +type RewritePG p v = PG p v -> PG p v + data Predicate a = Evaluated Bool -- Evaluated predicate | Parameter a -- To be evaluated later | Not (Predicate a) -- Negate predicate | And (Predicate a) (Predicate a) -- Conjunction | Or (Predicate a) (Predicate a) -- Disjunction --- Evaluator takes a Parameter and attempts to evaluate it. +multiOr :: [Predicate a] -> RewritePG (Predicate a) v +multiOr = Condition . foldr Or (Evaluated False) + +multiAnd :: [Predicate a] -> RewritePG (Predicate a) v +multiAnd = Condition . foldr And (Evaluated True) + +type RewrtePredicate a = Predicate a -> Predicate a + +-- Evaluator takes an argument and attempts to determine its truth. -- Returns Nothing if the attempt fails. type Evaluator a = a -> Maybe Bool -- Monoid instance for evaluators (returns first successful evaluation) instance Monoid (Evaluator a) where mempty = const Nothing - e `mappend` f = \p -> getFirst $ First (e p) <> First (f p) + p `mappend` q = \a -> getFirst $ First (p a) <> First (q a) --- Apply an evalulator to a predicate (partial evaluation, or projection) -apply :: Evaluator a -> Predicate a -> Predicate a +-- Apply an evalulator to a predicate (partial evaluation, or 'projection'). +apply :: Evaluator a -> RewrtePredicate a apply _ p @ (Evaluated _) = p apply e p @ (Parameter q) = case e q of Just bool -> Evaluated bool @@ -59,8 +73,20 @@ apply e (Not p ) = Not (apply e p) apply e (And p q) = And (apply e p) (apply e q) apply e (Or p q) = Or (apply e p) (apply e q) +-- Map over all PG predicates, e.g., apply an evaluator to a given PG. +mapP :: RewrtePredicate a -> RewritePG (Predicate a) v +mapP _ Epsilon = Epsilon +mapP _ v @ (Vertex _) = v +mapP r (Overlay p q) = Overlay (mapP r p) (mapP r q) +mapP r (Sequence p q) = Sequence (mapP r p) (mapP r q) +mapP r (Condition x p) = Condition (r x) (mapP r p) + +project :: Evaluator a -> RewritePG (Predicate a) v +project = mapP . apply + -- Attempt to evaluate a predicate. Returns Nothing if the predicate -- cannot be uniquely evaluated due to remaining parameters. +-- An alternative type: evalPredicate :: Evaluator (Predicate a) evalPredicate :: Predicate a -> Maybe Bool evalPredicate (Evaluated bool) = Just bool evalPredicate (Not p) = not <$> evalPredicate p @@ -80,46 +106,42 @@ evalPredicate (Or p q) q' = evalPredicate q evalPredicate (Parameter _) = Nothing -- cannot evaluate Parameter --- Flatten a PG into a list. Returns Nothing if the given expression +-- Linearise a PG into a list. Returns Nothing if the given expression -- cannot be uniquely evaluated due to remaining parameters. linearise :: PG (Predicate a) v -> Maybe [v] linearise Epsilon = Just [] linearise (Vertex v) = Just [v] -linearise (Overlay p q) = (++) <$> linearise p <*> linearise q +linearise (Overlay p q) = (++) <$> linearise p <*> linearise q -- TODO: union linearise (Sequence p q) = (++) <$> linearise p <*> linearise q linearise (Condition x p) = case evalPredicate x of Just True -> linearise p Just False -> Just [] Nothing -> Nothing -(~>) :: PG p v -> PG p v -> PG p v -a ~> b = Sequence a b +-- GHC build specific -type PGP p v = PG (Predicate p) v +type Expression a = PG (Predicate BuildParameter) a +type Rewrite a = Expression a -> Expression a -disjuction :: [a] -> (a -> Predicate p) -> PGP p v -> PGP p v -disjuction [] _ = id -disjuction (a:as) convert = Condition (foldr Or (convert a) $ map convert as) +--type ArgsExpression = Expression String +--type Args = Expression String --- GHC build specific +--args :: [String] -> Args +--args = fromList -data BuildParameter = WhenPackage FilePath +data BuildParameter = WhenPackage Package | WhenBuilder Builder | WhenStage Stage | WhenWay Way - | WhenFile FilePath + | WhenFile FilePattern | WhenKeyValue String String -- from config files -type Expression a = PGP BuildParameter a - -type Rewrite a = Expression a -> Expression a - -type ArgsExpression = Expression String +-- Predicates alternatives :: (b -> BuildParameter) -> [b] -> Rewrite a -alternatives p bs = disjuction bs (Parameter . p) +alternatives p = multiOr . map (Parameter . p) -whenPackages :: [FilePath] -> Rewrite a +whenPackages :: [Package] -> Rewrite a whenPackages = alternatives WhenPackage whenBuilders :: [Builder] -> Rewrite a @@ -134,7 +156,7 @@ unlessStage stage = Condition (Not $ Parameter $ WhenStage stage) whenWays :: [Way] -> Rewrite a whenWays = alternatives WhenWay -whenFiles :: [FilePath] -> Rewrite a +whenFiles :: [FilePattern] -> Rewrite a whenFiles = alternatives WhenFile whenKeyValues :: String -> [String] -> Rewrite a @@ -143,6 +165,52 @@ whenKeyValues key = alternatives (WhenKeyValue key) whenKeyValue :: String -> String -> Rewrite a whenKeyValue key value = whenKeyValues key [value] +-- Evaluators + +packageEvaluator :: Package -> Evaluator BuildParameter +packageEvaluator p (WhenPackage p') = Just $ p == p' +packageEvaluator _ _ = Nothing + +builderEvaluator :: Builder -> Evaluator BuildParameter +builderEvaluator b (WhenBuilder b') = Just $ b == b' +builderEvaluator _ _ = Nothing + +stageEvaluator :: Stage -> Evaluator BuildParameter +stageEvaluator s (WhenStage s') = Just $ s == s' +stageEvaluator _ _ = Nothing + +wayEvaluator :: Way -> Evaluator BuildParameter +wayEvaluator w (WhenWay w') = Just $ w == w' +wayEvaluator _ _ = Nothing + +fileEvaluator :: FilePath -> Evaluator BuildParameter +fileEvaluator file (WhenFile pattern) = Just $ pattern ?== file +fileEvaluator _ _ = Nothing + +keyValueEvaluator :: String -> String -> Evaluator BuildParameter +keyValueEvaluator key value (WhenKeyValue key' value') + | key == key' = Just $ value == value' + | otherwise = Nothing +keyValueEvaluator _ _ _ = Nothing + +setPackage :: Package -> Rewrite a +setPackage = project . packageEvaluator + +setBuilder :: Builder -> Rewrite a +setBuilder = project . builderEvaluator + +setStage :: Stage -> Rewrite a +setStage = project . stageEvaluator + +setWay :: Way -> Rewrite a +setWay = project . wayEvaluator + +setFile :: FilePath -> Rewrite a +setFile = project . fileEvaluator + +setKeyValue :: String -> String -> Rewrite a +setKeyValue key = project . keyValueEvaluator key + whenPackageKey :: Rewrite a whenPackageKey = whenKeyValue "supports-package-key" "YES" . unlessStage Stage0 diff --git a/src/Targets.hs b/src/Targets.hs index bdfb2ee..bc50ed9 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -4,6 +4,7 @@ module Targets ( ) where import Package.Base +import Settings -- These are the packages we build: -- TODO: this should eventually be removed and replaced by the top-level From git at git.haskell.org Thu Oct 26 23:26:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hide `parallel` from shake (aad2247) Message-ID: <20171026232633.E70723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aad2247ecc85160af1d27f7c4e3bb227a754630f/ghc >--------------------------------------------------------------- commit aad2247ecc85160af1d27f7c4e3bb227a754630f Author: Ben Gamari Date: Sun Dec 20 21:41:07 2015 +0100 Hide `parallel` from shake Shake `master` branch exports a symbol called `parallel` which overlaps with ours. >--------------------------------------------------------------- aad2247ecc85160af1d27f7c4e3bb227a754630f src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 1c72fd8..7edae37 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -38,7 +38,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>)) +import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes import Development.Shake.Config import Development.Shake.FilePath From git at git.haskell.org Thu Oct 26 23:26:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor argument expressions. (93e218e) Message-ID: <20171026232637.14FB33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/93e218e59d6f0e03ffdcfc691c19548a2e697135/ghc >--------------------------------------------------------------- commit 93e218e59d6f0e03ffdcfc691c19548a2e697135 Author: Andrey Mokhov Date: Wed Apr 8 02:34:02 2015 +0100 Refactor argument expressions. >--------------------------------------------------------------- 93e218e59d6f0e03ffdcfc691c19548a2e697135 src/Expression.hs | 159 ++++++++++++++++++++++++++++++ src/Expression/ArgList.hs | 32 ++++++ src/Expression/PG.hs | 56 +++++++++++ src/Expression/Predicate.hs | 55 +++++++++++ src/Expression/TruthTeller.hs | 16 +++ src/Settings.hs | 220 +++--------------------------------------- 6 files changed, 333 insertions(+), 205 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 93e218e59d6f0e03ffdcfc691c19548a2e697135 From git at git.haskell.org Thu Oct 26 23:26:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Use proper Haddock syntax (ecd1e7d) Message-ID: <20171026232637.6B8A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ecd1e7db540b6cf31cc884b5dccba1bf9e01de70/ghc >--------------------------------------------------------------- commit ecd1e7db540b6cf31cc884b5dccba1bf9e01de70 Author: Ben Gamari Date: Sun Dec 20 21:40:53 2015 +0100 Base: Use proper Haddock syntax >--------------------------------------------------------------- ecd1e7db540b6cf31cc884b5dccba1bf9e01de70 src/Base.hs | 44 +++++++++++++++++++++++++++----------------- 1 file changed, 27 insertions(+), 17 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 33b01bd..1c72fd8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,5 @@ module Base ( + -- * General utilities module Control.Applicative, module Control.Monad.Extra, module Control.Monad.Reader, @@ -7,18 +8,26 @@ module Base ( module Data.List, module Data.Maybe, module Data.Monoid, + + -- * Shake module Development.Shake, module Development.Shake.Classes, module Development.Shake.Config, module Development.Shake.FilePath, module Development.Shake.Util, - module System.Console.ANSI, + + -- * Paths shakeFilesPath, configPath, bootPackageConstraints, packageDependencies, - replaceEq, replaceSeparators, decodeModule, - unifyPath, (-/-), chunksOfSize, + + -- * Output putColoured, putOracle, putBuild, putSuccess, putError, + module System.Console.ANSI, + + -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, - removeFileIfExists + removeFileIfExists, + replaceEq, replaceSeparators, decodeModule, + unifyPath, (-/-), chunksOfSize, ) where import Control.Applicative @@ -55,34 +64,35 @@ packageDependencies :: FilePath packageDependencies = shakeFilesPath -/- "package-dependencies" -- Utility functions --- Find and replace all occurrences of a value in a list +-- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) --- Find and replace all occurrences of path separators in a String with a Char +-- | Find and replace all occurrences of path separators in a String with a Char replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) --- Given a module name extract the directory and file names, e.g.: --- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +-- | Given a module name extract the directory and file names, e.g.: +-- +-- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") decodeModule :: String -> (FilePath, String) decodeModule = splitFileName . replaceEq '.' '/' --- Normalise a path and convert all path separators to /, even on Windows. +-- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx --- Combine paths using and apply unifyPath to the result +-- | Combine paths using '' and apply 'unifyPath' to the result (-/-) :: FilePath -> FilePath -> FilePath a -/- b = unifyPath $ a b infixr 6 -/- --- (chunksOfSize size strings) splits a given list of strings into chunks not --- exceeding the given 'size'. +-- | @chunksOfSize size strings@ splits a given list of strings into chunks not +-- exceeding the given @size at . chunksOfSize :: Int -> [String] -> [[String]] chunksOfSize _ [] = [] chunksOfSize size strings = reverse chunk : chunksOfSize size rest @@ -94,7 +104,7 @@ chunksOfSize size strings = reverse chunk : chunksOfSize size rest where newSize = chunkSize + length s --- A more colourful version of Shake's putNormal +-- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do liftIO $ setSGR [SetColor Foreground Vivid colour] @@ -102,19 +112,19 @@ putColoured colour msg = do liftIO $ setSGR [] liftIO $ hFlush stdout --- Make oracle output more distinguishable +-- | Make oracle output more distinguishable putOracle :: String -> Action () putOracle = putColoured Blue --- Make build output more distinguishable +-- | Make build output more distinguishable putBuild :: String -> Action () putBuild = putColoured White --- A more colourful version of success message +-- | A more colourful version of success message putSuccess :: String -> Action () putSuccess = putColoured Green --- A more colourful version of error message +-- | A more colourful version of error message putError :: String -> Action a putError msg = do putColoured Red msg From git at git.haskell.org Thu Oct 26 23:26:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename src/Expression.hs -> src/Expression/Base.hs. (35cab30) Message-ID: <20171026232640.AF24F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/35cab3032cf80af4274dfd6563a821bcc34e4618/ghc >--------------------------------------------------------------- commit 35cab3032cf80af4274dfd6563a821bcc34e4618 Author: Andrey Mokhov Date: Wed Apr 8 23:04:19 2015 +0100 Rename src/Expression.hs -> src/Expression/Base.hs. >--------------------------------------------------------------- 35cab3032cf80af4274dfd6563a821bcc34e4618 src/{Expression.hs => Expression/Base.hs} | 0 src/Settings.hs | 5 ++++- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Expression.hs b/src/Expression/Base.hs similarity index 100% rename from src/Expression.hs rename to src/Expression/Base.hs diff --git a/src/Settings.hs b/src/Settings.hs index 2885282..e70e41c 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -22,8 +22,11 @@ integerLibraryName = case integerLibrary of buildHaddock :: Bool buildHaddock = True +supportsPackageKey :: Guard +supportsPackageKey = keyYes "supports-package-key" + whenPackageKey :: Guard -whenPackageKey = keyYes "supports-package-key" <> notStage Stage0 +whenPackageKey = supportsPackageKey <> notStage Stage0 depSettings :: Settings depSettings = From git at git.haskell.org Thu Oct 26 23:26:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Library: Use renderBox (c7a0c19) Message-ID: <20171026232641.19ED43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7a0c197ec98a64089af06a9efd0a8f41bfddead/ghc >--------------------------------------------------------------- commit c7a0c197ec98a64089af06a9efd0a8f41bfddead Author: Ben Gamari Date: Sun Dec 20 21:46:19 2015 +0100 Library: Use renderBox >--------------------------------------------------------------- c7a0c197ec98a64089af06a9efd0a8f41bfddead src/Rules/Library.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 088ac8d..134e2be 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -46,11 +46,12 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do else build $ fullTarget target Ar objs [a] synopsis <- interpretPartial target $ getPkgData Synopsis - putSuccess $ "/--------\n| Successfully built package library '" - ++ pkgName pkg - ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." - putSuccess $ "| Package synopsis: " - ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" + putSuccess $ renderBox + [ "Successfully built package library '" + ++ pkgName pkg + ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." + , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." + ] -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. From git at git.haskell.org Thu Oct 26 23:26:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Begin translating the code using expressions. (d7cd023) Message-ID: <20171026232644.21B723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d7cd023a4cc538bcde70d1872af41e4eafc77248/ghc >--------------------------------------------------------------- commit d7cd023a4cc538bcde70d1872af41e4eafc77248 Author: Andrey Mokhov Date: Thu Apr 9 02:50:25 2015 +0100 Begin translating the code using expressions. >--------------------------------------------------------------- d7cd023a4cc538bcde70d1872af41e4eafc77248 src/Expression/PGPredicate.hs | 62 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 62 insertions(+) diff --git a/src/Expression/PGPredicate.hs b/src/Expression/PGPredicate.hs new file mode 100644 index 0000000..45bb97f --- /dev/null +++ b/src/Expression/PGPredicate.hs @@ -0,0 +1,62 @@ +{-# LANGUAGE FlexibleInstances #-} + +module Expression.PGPredicate ( + module Expression.PG, + module Expression.Predicate, + PGPredicate (..), + fence, (?), ite, + whenExists, + remove, + project, + linearise + ) where + +import Control.Applicative +import Expression.PG +import Expression.Predicate + +type PGPredicate p v = PG (Predicate p) v + +fence :: PGPredicate p v -> PGPredicate p v -> PGPredicate p v +fence = Sequence + +(?) :: Predicate p -> PGPredicate p v -> PGPredicate p v +(?) = Condition + +ite :: Predicate p -> PGPredicate p v -> PGPredicate p v -> PGPredicate p v +ite p t f = Overlay (p ? t) (Not p ? f) + +infixl 7 ? + +whenExists :: Eq v => v -> PGPredicate p v -> Predicate p +whenExists _ Epsilon = Evaluated False +whenExists a (Vertex b) = Evaluated $ a == b +whenExists a (Overlay l r) = Or (whenExists a l) (whenExists a r) +whenExists a (Sequence l r) = Or (whenExists a l) (whenExists a r) +whenExists a (Condition x r) = And x (whenExists a r) + +remove :: Eq v => v -> PGPredicate p v -> PGPredicate p v +remove _ Epsilon = Epsilon +remove a v @ (Vertex b) + | a == b = Epsilon + | otherwise = v +remove a (Overlay l r) = Overlay (remove a l) (remove a r) +remove a (Sequence l r) = Sequence (remove a l) (remove a r) +remove a (Condition x r) = Condition x (remove a r) + +-- Partially evaluate a PG using a truth-teller (compute a 'projection') +project :: TruthTeller p -> PGPredicate p v -> PGPredicate p v +project t = mapP (evaluate t) + +-- Linearise a PG into a list. Returns Nothing if the given expression +-- cannot be uniquely evaluated due to remaining parameters. +-- Overlay subexpressions are evaluated in arbitrary order. +linearise :: PGPredicate p v -> Maybe [v] +linearise Epsilon = Just [] +linearise (Vertex v) = Just [v] +linearise (Overlay l r) = (++) <$> linearise l <*> linearise r -- TODO: union +linearise (Sequence l r) = (++) <$> linearise l <*> linearise r +linearise (Condition x r) = case tellTruth x of + Just True -> linearise r + Just False -> Just [] + Nothing -> Nothing From git at git.haskell.org Thu Oct 26 23:26:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Program: Use renderBox (cbd6aef) Message-ID: <20171026232644.818063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbd6aef9b8d6697da710d119deb05277822c5e31/ghc >--------------------------------------------------------------- commit cbd6aef9b8d6697da710d119deb05277822c5e31 Author: Ben Gamari Date: Sun Dec 20 21:43:28 2015 +0100 Program: Use renderBox >--------------------------------------------------------------- cbd6aef9b8d6697da710d119deb05277822c5e31 src/Rules/Program.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 8e3ec77..2ff5ef0 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -47,8 +47,9 @@ buildProgram _ target @ (PartialTarget stage pkg) = do need $ objs ++ libs build $ fullTargetWithWay target (Ghc stage) vanilla objs [bin] synopsis <- interpretPartial target $ getPkgData Synopsis - putSuccess $ "/--------\n| Successfully built program '" - ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." - putSuccess $ "| Executable: " ++ bin - putSuccess $ "| Package synopsis: " - ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" + putSuccess $ renderBox + [ "Successfully built program '" + ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + , "Executable: " ++ bin + , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." + ] From git at git.haskell.org Thu Oct 26 23:26:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish translation of Data.hs argument lists. (8cf38ba) Message-ID: <20171026232647.DB48F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8cf38baf8224a14a2fc167bfc0776123d1bd1167/ghc >--------------------------------------------------------------- commit 8cf38baf8224a14a2fc167bfc0776123d1bd1167 Author: Andrey Mokhov Date: Fri Apr 10 02:05:27 2015 +0100 Finish translation of Data.hs argument lists. >--------------------------------------------------------------- 8cf38baf8224a14a2fc167bfc0776123d1bd1167 src/Expression/ArgList.hs | 7 +- src/Expression/Base.hs | 190 ++++++++++++++++++++++++++++++++++++------ src/Expression/PG.hs | 41 ++------- src/Expression/PGPredicate.hs | 18 +--- src/Oracles/Builder.hs | 1 + src/Settings.hs | 129 ++++++++++++++++++++++------ src/Targets.hs | 148 ++++++++++++++++---------------- 7 files changed, 363 insertions(+), 171 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 8cf38baf8224a14a2fc167bfc0776123d1bd1167 From git at git.haskell.org Thu Oct 26 23:26:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move `renderBox` to `Base` (26e64ed) Message-ID: <20171026232648.3B6A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/26e64ed57d5b0d85e740baedd529e845002103e9/ghc >--------------------------------------------------------------- commit 26e64ed57d5b0d85e740baedd529e845002103e9 Author: Ben Gamari Date: Sun Dec 20 21:41:36 2015 +0100 Move `renderBox` to `Base` >--------------------------------------------------------------- 26e64ed57d5b0d85e740baedd529e845002103e9 src/Base.hs | 18 ++++++++++++++++++ src/Rules/Actions.hs | 20 ++------------------ 2 files changed, 20 insertions(+), 18 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7edae37..fb3b5e1 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -21,6 +21,7 @@ module Base ( -- * Output putColoured, putOracle, putBuild, putSuccess, putError, + renderBox, module System.Console.ANSI, -- * Miscellaneous utilities @@ -130,6 +131,23 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg +-- | Render the given set of lines in a ASCII box +renderBox :: [String] -> String +renderBox ls = + unlines $ [begin] ++ map (bar++) ls ++ [end] + where + (begin,bar,end) + | useUnicode = ( "╭──────────" + , "│ " + , "╰──────────" + ) + | otherwise = ( "/----------" + , "| " + , "\\----------" + ) + -- FIXME: See Shake #364. + useUnicode = False + -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 775524a..5a3d113 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -7,22 +7,6 @@ import Settings.Args import Settings.Builders.Ar import qualified Target -insideBox :: [String] -> String -insideBox ls = - unlines $ [begin] ++ map (bar++) ls ++ [end] - where - (begin,bar,end) - | useUnicode = ( "╭──────────" - , "│ " - , "╰──────────" - ) - | otherwise = ( "/----------" - , "| " - , "\\----------" - ) - -- FIXME: See Shake #364. - useUnicode = False - -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last -- built (that is, track changes in the build system). @@ -38,8 +22,8 @@ buildWithResources rs target = do checkArgsHash target withResources rs $ do unless verbose $ do - putBuild $ insideBox $ [ "Running " ++ show builder ++ " with arguments:" ] - ++ map (" "++) (interestingInfo builder argList) + putBuild $ renderBox $ [ "Running " ++ show builder ++ " with arguments:" ] + ++ map (" "++) (interestingInfo builder argList) quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList From git at git.haskell.org Thu Oct 26 23:26:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (08136dd) Message-ID: <20171026232651.A8C3E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/08136ddd1386ec9b7a4b79779d51f388606fce0b/ghc >--------------------------------------------------------------- commit 08136ddd1386ec9b7a4b79779d51f388606fce0b Author: Andrey Mokhov Date: Sun Apr 12 02:13:23 2015 +0100 Clean up. >--------------------------------------------------------------- 08136ddd1386ec9b7a4b79779d51f388606fce0b src/Expression/ArgList.hs | 37 ---- src/Expression/{Base.hs => Args.hs} | 12 -- src/Expression/Base.hs | 345 ++++++++++-------------------------- src/Expression/Build.hs | 238 +++++++++++++++++++++++++ src/Expression/PG.hs | 31 ++-- src/Expression/PGPredicate.hs | 46 ----- src/Expression/Predicate.hs | 68 ++----- src/Expression/TruthTeller.hs | 16 -- src/Settings.hs | 116 ++++++------ src/Targets.hs | 3 +- 10 files changed, 433 insertions(+), 479 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 08136ddd1386ec9b7a4b79779d51f388606fce0b From git at git.haskell.org Thu Oct 26 23:26:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an explicit dependency on pkgDataFile to make sure GhcCabal hscolour is run after GhcCabal configure. (0c9d7d8) Message-ID: <20171026232652.1EC4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c9d7d887552956816e5acee725dbc79f591b18d/ghc >--------------------------------------------------------------- commit 0c9d7d887552956816e5acee725dbc79f591b18d Author: Andrey Mokhov Date: Sun Dec 20 20:58:10 2015 +0000 Add an explicit dependency on pkgDataFile to make sure GhcCabal hscolour is run after GhcCabal configure. >--------------------------------------------------------------- 0c9d7d887552956816e5acee725dbc79f591b18d src/Rules/Documentation.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 495a16c..463552f 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -10,9 +10,9 @@ import Settings -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. buildPackageDocumentation :: Resources -> PartialTarget -> Rules () -buildPackageDocumentation _ target @ (PartialTarget stage package) = - let cabalFile = pkgCabalFile package - haddockFile = pkgHaddockFile package +buildPackageDocumentation _ target @ (PartialTarget stage pkg) = + let cabalFile = pkgCabalFile pkg + haddockFile = pkgHaddockFile pkg in when (stage == Stage1) $ do haddockFile %> \file -> do srcs <- interpretPartial target getPackageSources @@ -23,7 +23,7 @@ buildPackageDocumentation _ target @ (PartialTarget stage package) = -- HsColour sources whenM (specified HsColour) $ do - need [cabalFile] + need [cabalFile, pkgDataFile stage pkg ] build $ fullTarget target GhcCabalHsColour [cabalFile] [] -- Build Haddock documentation From git at git.haskell.org Thu Oct 26 23:26:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove old file src/Expression/Args.hs. (21b789e) Message-ID: <20171026232655.340303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21b789ea7729715fe7252099808b062271793e40/ghc >--------------------------------------------------------------- commit 21b789ea7729715fe7252099808b062271793e40 Author: Andrey Mokhov Date: Sun Apr 12 02:14:52 2015 +0100 Remove old file src/Expression/Args.hs. >--------------------------------------------------------------- 21b789ea7729715fe7252099808b062271793e40 src/Expression/Args.hs | 289 ------------------------------------------------- 1 file changed, 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 21b789ea7729715fe7252099808b062271793e40 From git at git.haskell.org Thu Oct 26 23:26:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #13 from bgamari/master (e801ee0) Message-ID: <20171026232655.A56893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e801ee01698baa20d7a56e57768104f74ac35ffa/ghc >--------------------------------------------------------------- commit e801ee01698baa20d7a56e57768104f74ac35ffa Merge: 0c9d7d8 c7a0c19 Author: Andrey Mokhov Date: Sun Dec 20 21:04:59 2015 +0000 Merge pull request #13 from bgamari/master Consolidate box pretty-printing >--------------------------------------------------------------- e801ee01698baa20d7a56e57768104f74ac35ffa src/Base.hs | 64 +++++++++++++++++++++++++++++++++++++--------------- src/Rules/Actions.hs | 20 ++-------------- src/Rules/Library.hs | 11 +++++---- src/Rules/Program.hs | 11 +++++---- 4 files changed, 60 insertions(+), 46 deletions(-) From git at git.haskell.org Thu Oct 26 23:26:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Continue major refactoring for expression-based build system. (cb2003c) Message-ID: <20171026232658.A91BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb2003ce5221cf043f77eeb0690d6d8b6bc19dea/ghc >--------------------------------------------------------------- commit cb2003ce5221cf043f77eeb0690d6d8b6bc19dea Author: Andrey Mokhov Date: Wed Apr 15 03:24:09 2015 +0100 Continue major refactoring for expression-based build system. >--------------------------------------------------------------- cb2003ce5221cf043f77eeb0690d6d8b6bc19dea src/Expression/Base.hs | 146 +++++++++++++++++++++--------------- src/Expression/Build.hs | 34 ++++----- src/Expression/PG.hs | 49 +++++++++++- src/Main.hs | 3 +- src/Package.hs | 58 ++++++--------- src/Package/Base.hs | 170 ++++++++++-------------------------------- src/PackageBuild.hs | 67 +++++++++++++++++ src/Settings.hs | 101 ++++++++++++------------- src/Targets.hs | 193 +++++++++++++++++++++++------------------------- 9 files changed, 420 insertions(+), 401 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 cb2003ce5221cf043f77eeb0690d6d8b6bc19dea From git at git.haskell.org Thu Oct 26 23:26:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:26:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, make naming consistent: setPkgType -> setType. (f5d4e7b) Message-ID: <20171026232659.217BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5d4e7b91aff5a8a0c1e8368173d6c999a01d4b4/ghc >--------------------------------------------------------------- commit f5d4e7b91aff5a8a0c1e8368173d6c999a01d4b4 Author: Andrey Mokhov Date: Sun Dec 20 21:19:02 2015 +0000 Clean up, make naming consistent: setPkgType -> setType. >--------------------------------------------------------------- f5d4e7b91aff5a8a0c1e8368173d6c999a01d4b4 src/Base.hs | 6 ++---- src/GHC.hs | 4 ++-- src/Package.hs | 6 +++--- src/Rules/Program.hs | 4 ---- 4 files changed, 7 insertions(+), 13 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fb3b5e1..009e197 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -20,15 +20,13 @@ module Base ( shakeFilesPath, configPath, bootPackageConstraints, packageDependencies, -- * Output - putColoured, putOracle, putBuild, putSuccess, putError, - renderBox, + putColoured, putOracle, putBuild, putSuccess, putError, renderBox, module System.Console.ANSI, -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, removeFileIfExists, - replaceEq, replaceSeparators, decodeModule, - unifyPath, (-/-), chunksOfSize, + replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, ) where import Control.Applicative diff --git a/src/GHC.hs b/src/GHC.hs index 29db671..923fdf1 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -51,7 +51,7 @@ dllSplit = utility "dll-split" filepath = library "filepath" genapply = utility "genapply" genprimopcode = utility "genprimopcode" -ghc = topLevel "ghc-bin" `setPath` "ghc" `setPkgType` Program +ghc = topLevel "ghc-bin" `setPath` "ghc" `setType` Program ghcBoot = library "ghc-boot" ghcCabal = utility "ghc-cabal" ghci = library "ghci" @@ -68,7 +68,7 @@ hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" integerGmp = library "integer-gmp" integerSimple = library "integer-simple" -iservBin = topLevel "iserv-bin" `setPath` "iserv" `setPkgType` Program +iservBin = topLevel "iserv-bin" `setPath` "iserv" `setType` Program mkUserGuidePart = utility "mkUserGuidePart" parallel = library "parallel" pretty = library "pretty" diff --git a/src/Package.hs b/src/Package.hs index 6273a62..574f01a 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -5,7 +5,7 @@ module Package ( pkgCabalFile, matchPackageNames, -- * Helpers for constructing 'Package's - setPath, topLevel, library, utility, setPkgType + setPath, topLevel, library, utility, setType ) where import Base @@ -45,8 +45,8 @@ utility name = Package name ("utils" -/- name) Program setPath :: Package -> FilePath -> Package setPath pkg path = pkg { pkgPath = path } -setPkgType :: Package -> PackageType -> Package -setPkgType pkg ty = pkg { pkgType = ty } +setType :: Package -> PackageType -> Package +setType pkg ty = pkg { pkgType = ty } instance Show Package where show = pkgName diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 2ff5ef0..9ca36d6 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -17,10 +17,6 @@ buildProgram _ target @ (PartialTarget stage pkg) = do buildPath = path -/- "build" program = programPath stage pkg - -- return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] - -- ++ [ haddock | needHaddock && stage == Stage1 ] - -- ++ libs - (\f -> program == Just f) ?> \bin -> do cSrcs <- cSources target -- TODO: remove code duplication (Library.hs) hSrcs <- hSources target From git at git.haskell.org Thu Oct 26 23:27:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish Args datatype, propagate changes to related modules. (79ad8ee) Message-ID: <20171026232702.F15BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79ad8ee4e0830da7125d6975c6f13790d97f2439/ghc >--------------------------------------------------------------- commit 79ad8ee4e0830da7125d6975c6f13790d97f2439 Author: Andrey Mokhov Date: Thu Apr 16 02:08:59 2015 +0100 Finish Args datatype, propagate changes to related modules. >--------------------------------------------------------------- 79ad8ee4e0830da7125d6975c6f13790d97f2439 src/Expression/Base.hs | 52 ++++++++++++++++++++------- src/Expression/Build.hs | 2 +- src/Main.hs | 1 + src/Settings.hs | 94 ++++++++++++++++++++++++++----------------------- src/Targets.hs | 22 ++++++------ 5 files changed, 102 insertions(+), 69 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 79ad8ee4e0830da7125d6975c6f13790d97f2439 From git at git.haskell.org Thu Oct 26 23:27:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build program executables directly in inplace/bin. (663ad01) Message-ID: <20171026232703.468033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/663ad019699389006a2c99e9f17c92bd53ea4e22/ghc >--------------------------------------------------------------- commit 663ad019699389006a2c99e9f17c92bd53ea4e22 Author: Andrey Mokhov Date: Mon Dec 21 02:56:49 2015 +0000 Build program executables directly in inplace/bin. >--------------------------------------------------------------- 663ad019699389006a2c99e9f17c92bd53ea4e22 cfg/system.config.in | 20 ++++++++++---------- src/Base.hs | 7 ++++++- src/Builder.hs | 1 + src/GHC.hs | 30 ++++++++++++------------------ src/Rules.hs | 5 +++-- src/Settings/Builders/GhcCabal.hs | 3 ++- 6 files changed, 34 insertions(+), 32 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 9de3166..6c21f6e 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -5,29 +5,29 @@ #=================== system-ghc = @WithGhc@ -ghc-stage1 = @hardtop@/inplace/bin/ghc-stage1 -ghc-stage2 = @hardtop@/inplace/bin/ghc-stage2 -ghc-stage3 = @hardtop@/inplace/bin/ghc-stage3 +ghc-stage1 = inplace/bin/ghc-stage1 +ghc-stage2 = inplace/bin/ghc-stage2 +ghc-stage3 = inplace/bin/ghc-stage3 system-gcc = @CC_STAGE0@ gcc = @WhatGccIsCalled@ system-ghc-pkg = @GhcPkgCmd@ -ghc-pkg = @hardtop@/inplace/bin/ghc-pkg +ghc-pkg = inplace/bin/ghc-pkg -ghc-cabal = @hardtop@/inplace/bin/ghc-cabal +ghc-cabal = inplace/bin/ghc-cabal -haddock = @hardtop@/inplace/bin/haddock +haddock = inplace/bin/haddock -hsc2hs = @hardtop@/inplace/bin/hsc2hs +hsc2hs = inplace/bin/hsc2hs -genprimopcode = @hardtop@/inplace/bin/genprimopcode +genprimopcode = inplace/bin/genprimopcode hs-cpp = @HaskellCPPCmd@ hs-cpp-args = @HaskellCPPArgs@ -unlit = @hardtop@/inplace/lib/unlit -ghc-split = @hardtop@/inplace/lib/ghc-split +unlit = inplace/lib/unlit +ghc-split = inplace/lib/ghc-split ld = @LdCmd@ ar = @ArCmd@ diff --git a/src/Base.hs b/src/Base.hs index 009e197..834f589 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -17,7 +17,8 @@ module Base ( module Development.Shake.Util, -- * Paths - shakeFilesPath, configPath, bootPackageConstraints, packageDependencies, + shakeFilesPath, configPath, programInplacePath, + bootPackageConstraints, packageDependencies, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, @@ -56,6 +57,10 @@ shakeFilesPath = shakePath -/- ".db" configPath :: FilePath configPath = shakePath -/- "cfg" +-- TODO: shall we read this from system.config instead? +programInplacePath :: FilePath +programInplacePath = "inplace/bin" + bootPackageConstraints :: FilePath bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" diff --git a/src/Builder.hs b/src/Builder.hs index f15054d..4d41d0a 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -66,6 +66,7 @@ builderKey builder = case builder of Ld -> "ld" Unlit -> "unlit" +-- TODO: Paths to some builders should be determined using defaultProgramPath builderPath :: Builder -> Action FilePath builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ diff --git a/src/GHC.hs b/src/GHC.hs index 923fdf1..f47242a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -105,25 +105,19 @@ defaultTargetDirectory stage pkg | stage == Stage0 = "dist-boot" | otherwise = "dist-install" +-- TODO: simplify +-- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg - | pkg == compareSizes = program $ pkgName pkg - | pkg == deriveConstants = program $ pkgName pkg - | pkg == dllSplit = program $ pkgName pkg - | pkg == genapply = program $ pkgName pkg - | pkg == genprimopcode = program $ pkgName pkg - | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) - | pkg == ghcCabal = program $ pkgName pkg - | pkg == ghcPkg = program $ pkgName pkg - | pkg == ghcPwd = program $ pkgName pkg - | pkg == ghcTags = program $ pkgName pkg - | pkg == haddock = program $ pkgName pkg - | pkg == hsc2hs = program $ pkgName pkg - | pkg == hp2ps = program $ pkgName pkg - | pkg == hpcBin = program $ pkgName pkg - | pkg == mkUserGuidePart = program $ pkgName pkg - | pkg == runghc = program $ pkgName pkg - | otherwise = Nothing + | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) + | pkg == haddock = case stage of + Stage2 -> Just . inplaceProgram $ pkgName pkg + _ -> Nothing + | isProgram pkg = case stage of + Stage0 -> Just . inplaceProgram $ pkgName pkg + _ -> Just . installProgram $ pkgName pkg + | otherwise = Nothing where - program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg + inplaceProgram name = programInplacePath -/- name <.> exe + installProgram name = pkgPath pkg -/- defaultTargetDirectory stage pkg -/- "build/tmp" -/- name <.> exe diff --git a/src/Rules.hs b/src/Rules.hs index 55ff066..7d88de8 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,7 +5,8 @@ import Rules.Package import Rules.Resources import Settings --- generateTargets needs top-level build targets +-- TODO: not all program targets should be needed explicitly +-- | generateTargets needs top-level build targets generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do @@ -17,7 +18,7 @@ generateTargets = action $ do return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] return $ libTargets ++ programTargets - need $ reverse targets + need targets -- TODO: use stage 2 compiler for building stage 2 packages (instead of stage 1) packageRules :: Rules () diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 151cd5f..66f9239 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -184,9 +184,10 @@ withBuilderKey b = case b of -- Expression 'with Gcc' appends "--with-gcc=/path/to/gcc" and needs Gcc. with :: Builder -> Args with b = specified b ? do + top <- getSetting GhcSourcePath path <- getBuilderPath b lift $ needBuilder laxDependencies b - append [withBuilderKey b ++ path] + append [withBuilderKey b ++ top -/- path] withStaged :: (Stage -> Builder) -> Args withStaged sb = (with . sb) =<< getStage From git at git.haskell.org Thu Oct 26 23:27:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Simplify instances for PG and Predicate. (0fe624f) Message-ID: <20171026232706.D070C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0fe624fbec4b1eee99bc2e056f662568da0ffa91/ghc >--------------------------------------------------------------- commit 0fe624fbec4b1eee99bc2e056f662568da0ffa91 Author: Andrey Mokhov Date: Fri Apr 17 01:29:08 2015 +0100 Add Simplify instances for PG and Predicate. >--------------------------------------------------------------- 0fe624fbec4b1eee99bc2e056f662568da0ffa91 src/Expression/Base.hs | 14 +++++++--- src/Expression/Build.hs | 63 ++++++++++++++++++++++++++++++------------- src/Expression/PG.hs | 48 ++++++++++++++++++++++++++++++++- src/Expression/Simplify.hs | 6 +++++ src/Main.hs | 6 +++++ src/Package.hs | 3 +++ src/Settings.hs | 67 ++++++++++++++++++++++------------------------ src/Ways.hs | 3 +++ 8 files changed, 152 insertions(+), 58 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 0fe624fbec4b1eee99bc2e056f662568da0ffa91 From git at git.haskell.org Thu Oct 26 23:27:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bootstrap ghc-cabal. (c98eebc) Message-ID: <20171026232707.1EC0C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c98eebc43418a33618df317cd92472ac801618b2/ghc >--------------------------------------------------------------- commit c98eebc43418a33618df317cd92472ac801618b2 Author: Andrey Mokhov Date: Mon Dec 21 03:00:14 2015 +0000 Bootstrap ghc-cabal. >--------------------------------------------------------------- c98eebc43418a33618df317cd92472ac801618b2 src/Base.hs | 1 - src/Rules/Data.hs | 93 ++++++++++++++++++++++++-------------------- src/Rules/Program.hs | 22 ++++++----- src/Rules/Resources.hs | 4 +- src/Settings/Builders/Ghc.hs | 51 ++++++++++-------------- 5 files changed, 85 insertions(+), 86 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c98eebc43418a33618df317cd92472ac801618b2 From git at git.haskell.org Thu Oct 26 23:27:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a draft implementation for resolution of Config variables. (489e385) Message-ID: <20171026232710.75DB53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/489e385ab98b0ce8ec0b9ab8248b9bc9adb1f38b/ghc >--------------------------------------------------------------- commit 489e385ab98b0ce8ec0b9ab8248b9bc9adb1f38b Author: Andrey Mokhov Date: Fri Apr 17 22:49:20 2015 +0100 Add a draft implementation for resolution of Config variables. >--------------------------------------------------------------- 489e385ab98b0ce8ec0b9ab8248b9bc9adb1f38b src/Expression/Base.hs | 24 +++++++++---------- src/Expression/Build.hs | 2 +- src/Expression/Resolve.hs | 60 +++++++++++++++++++++++++++++++++++++++++++++++ src/Main.hs | 40 +++++++++++++++++++++++++++++-- src/Targets.hs | 2 +- 5 files changed, 112 insertions(+), 16 deletions(-) diff --git a/src/Expression/Base.hs b/src/Expression/Base.hs index e9316e8..ef6ad72 100644 --- a/src/Expression/Base.hs +++ b/src/Expression/Base.hs @@ -118,7 +118,6 @@ argWithStagedBuilder :: (Stage -> Builder) -> Settings argWithStagedBuilder f = msum $ map (\s -> stage s ? argWithBuilder (f s)) [Stage0 ..] - -- Accessing key value pairs from package-data.mk files argPackageKey :: Settings argPackageKey = return $ PackageData "PACKAGE_KEY" @@ -165,35 +164,36 @@ argPrefix prefix = fmap (Fold Concat . (arg prefix |>) . return) argPrefixPath :: String -> Settings -> Settings argPrefixPath prefix = fmap (Fold ConcatPath . (arg prefix |>) . return) --- Partially evaluate Settings using a truth-teller (compute a 'projection') -project :: (BuildVariable -> Maybe Bool) -> Settings -> Settings +-- Partially evaluate expression using a truth-teller (compute a 'projection') +project :: (BuildVariable -> Maybe Bool) -> BuildExpression v + -> BuildExpression v project _ Epsilon = Epsilon project t (Vertex v) = Vertex v -- TODO: go deeper project t (Overlay l r) = Overlay (project t l) (project t r) project t (Sequence l r) = Sequence (project t l) (project t r) project t (Condition l r) = Condition (evaluate t l) (project t r) --- Partial evaluation of settings - -setPackage :: Package -> Settings -> Settings +-- Partial evaluation of setting +setPackage :: Package -> BuildExpression v -> BuildExpression v setPackage = project . matchPackage -setBuilder :: Builder -> Settings -> Settings +setBuilder :: Builder -> BuildExpression v -> BuildExpression v setBuilder = project . matchBuilder -setBuilderFamily :: (Stage -> Builder) -> Settings -> Settings +setBuilderFamily :: (Stage -> Builder) -> BuildExpression v + -> BuildExpression v setBuilderFamily = project . matchBuilderFamily -setStage :: Stage -> Settings -> Settings +setStage :: Stage -> BuildExpression v -> BuildExpression v setStage = project . matchStage -setWay :: Way -> Settings -> Settings +setWay :: Way -> BuildExpression v -> BuildExpression v setWay = project . matchWay -setFile :: FilePath -> Settings -> Settings +setFile :: FilePath -> BuildExpression v -> BuildExpression v setFile = project . matchFile -setConfig :: String -> String -> Settings -> Settings +setConfig :: String -> String -> BuildExpression v -> BuildExpression v setConfig key = project . matchConfig key --type ArgsTeller = Args -> Maybe [String] diff --git a/src/Expression/Build.hs b/src/Expression/Build.hs index 19ff60e..8a7372d 100644 --- a/src/Expression/Build.hs +++ b/src/Expression/Build.hs @@ -21,8 +21,8 @@ module Expression.Build ( import Control.Applicative import Base import Ways -import Package (Package) import Oracles.Builder +import Package (Package) import Expression.PG -- Build variables that can be used in build predicates diff --git a/src/Expression/Resolve.hs b/src/Expression/Resolve.hs new file mode 100644 index 0000000..4ce4f7b --- /dev/null +++ b/src/Expression/Resolve.hs @@ -0,0 +1,60 @@ +{-# LANGUAGE FlexibleInstances #-} + +module Expression.Resolve ( + ResolveConfig (..) + ) where + +import Base +import Oracles.Base +import Expression.PG +import Expression.Predicate +import Expression.Base +import Expression.Build + +-- Resolve configuration variables +class ResolveConfig a where + resolveConfig :: a -> Action a + -- resolveConfig = return . id + +instance ResolveConfig BuildPredicate where + resolveConfig p @ (Evaluated _) = return p + + resolveConfig (Unevaluated (ConfigVariable key value)) = do + lookup <- askConfig key + return $ Evaluated $ lookup == value + + resolveConfig p @ (Unevaluated _) = return p + + resolveConfig (Not p) = do + p' <- resolveConfig p + return $ Not p' + + resolveConfig (And p q) = do + p' <- resolveConfig p + q' <- resolveConfig q + return $ And p' q' + + resolveConfig (Or p q) = do + p' <- resolveConfig p + q' <- resolveConfig q + return $ Or p' q' + +instance ResolveConfig (BuildExpression v) where + resolveConfig Epsilon = return Epsilon + + resolveConfig v @ (Vertex _) = return v -- TODO: go deeper + + resolveConfig (Overlay l r) = do + l' <- resolveConfig l + r' <- resolveConfig r + return $ Overlay l' r' + + resolveConfig (Sequence l r) = do + l' <- resolveConfig l + r' <- resolveConfig r + return $ Sequence l' r' + + resolveConfig (Condition l r) = do + l' <- resolveConfig l + r' <- resolveConfig r + return $ Condition l' r' diff --git a/src/Main.hs b/src/Main.hs index 4b6349a..bf0e8f7 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -4,7 +4,9 @@ import Oracles import Package import Targets import Settings +import Expression.Base import Expression.Simplify +import Expression.Resolve main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do oracleRules @@ -13,6 +15,40 @@ main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do --packageRules action $ do - putNormal $ "targetPackages = " ++ show (simplify targetPackages) - putNormal $ "\ntargetWays = " ++ show (simplify targetWays) + putNormal $ "\ntargetPackages = " ++ show (simplify targetPackages) + putNormal $ "\n\ntargetWays = " ++ show (simplify targetWays) + putNormal $ "\n\n=============================\n" + -- Read config file + targetPackages' <- resolveConfig targetPackages + targetWays' <- resolveConfig targetWays + + -- Build stages + forM_ [Stage0 ..] $ \stage -> do + putNormal $ "Stage = " ++ show stage + let packages = setStage stage targetPackages' + ways = setStage stage targetWays' + putNormal $ "\n packages = " ++ show (simplify packages) + putNormal $ "\n ways = " ++ show (simplify ways) + + --forM_ targetPackages $ \pkg @ (Package name path _ todo) -> do + -- forM_ todo $ \todoItem @ (stage, dist, settings) -> do + + -- -- Want top .o and .a files for the pkg/todo combo + -- -- We build *only one* vanilla .o file (not sure why) + -- -- We build .way_a file for each way (or its dynamic version). + -- -- TODO: Check BUILD_GHCI_LIB flag to decide if .o is needed + -- -- TODO: move this into a separate file (perhaps, to Targets.hs?) + -- action $ when (buildWhen settings) $ do + -- let pathDist = path dist + -- buildDir = pathDist "build" + -- key <- showArg (PackageKey pathDist) + -- let oFile = buildDir "Hs" ++ key <.> "o" + -- ways' <- ways settings + -- libFiles <- forM ways' $ \way -> do + -- extension <- libsuf way + -- return $ buildDir "libHs" ++ key <.> extension + -- need $ [oFile] ++ libFiles + + -- -- Build rules for the package + -- buildPackage pkg todoItem diff --git a/src/Targets.hs b/src/Targets.hs index 1b7bba2..bc2756a 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -26,7 +26,7 @@ targetPackages = msum packagesStage0 :: Packages packagesStage0 = msum [ fromList [ binPackageDb, binary, cabal, hoopl, hpc, transformers ] - , windowsHost && not (targetOs "ios") ? return terminfo ] + , not windowsHost && not (targetOs "ios") ? return terminfo ] packagesStage1 :: Packages packagesStage1 = msum From git at git.haskell.org Thu Oct 26 23:27:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move isLibrary to src/Package.hs, add isProgram. (5980218) Message-ID: <20171026232710.C53A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/598021809c6822f8c30b13ad0f75719a465a1c27/ghc >--------------------------------------------------------------- commit 598021809c6822f8c30b13ad0f75719a465a1c27 Author: Andrey Mokhov Date: Mon Dec 21 03:00:38 2015 +0000 Move isLibrary to src/Package.hs, add isProgram. >--------------------------------------------------------------- 598021809c6822f8c30b13ad0f75719a465a1c27 src/Package.hs | 12 ++++++++++-- src/Settings.hs | 4 ---- 2 files changed, 10 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 574f01a..5b04b6d 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -4,8 +4,8 @@ module Package ( -- * Queries pkgCabalFile, matchPackageNames, - -- * Helpers for constructing 'Package's - setPath, topLevel, library, utility, setType + -- * Helpers for constructing and using 'Package's + setPath, topLevel, library, utility, setType, isLibrary, isProgram ) where import Base @@ -48,6 +48,14 @@ setPath pkg path = pkg { pkgPath = path } setType :: Package -> PackageType -> Package setType pkg ty = pkg { pkgType = ty } +isLibrary :: Package -> Bool +isLibrary (Package {pkgType=Library}) = True +isLibrary _ = False + +isProgram :: Package -> Bool +isProgram (Package {pkgType=Program}) = True +isProgram _ = False + instance Show Package where show = pkgName diff --git a/src/Settings.hs b/src/Settings.hs index 7a1ab72..fd7c14c 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -32,10 +32,6 @@ getPkgDataList key = lift . pkgDataList . key =<< getTargetPath programPath :: Stage -> Package -> Maybe FilePath programPath = userProgramPath -isLibrary :: Package -> Bool -isLibrary (Package {pkgType=Library}) = True -isLibrary _ = False - -- Find all Haskell source files for the current target. TODO: simplify. getPackageSources :: Expr [FilePath] getPackageSources = do From git at git.haskell.org Thu Oct 26 23:27:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Work on the top-level build structure. (8bdc64c) Message-ID: <20171026232713.D98A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8bdc64ccbf49838c6a90635cb45683bcc609a4b3/ghc >--------------------------------------------------------------- commit 8bdc64ccbf49838c6a90635cb45683bcc609a4b3 Author: Andrey Mokhov Date: Sat Apr 18 01:42:25 2015 +0100 Work on the top-level build structure. >--------------------------------------------------------------- 8bdc64ccbf49838c6a90635cb45683bcc609a4b3 src/Expression/Base.hs | 31 +++++++++---- src/Expression/Resolve.hs | 110 ++++++++++++++++++++++++++++++++-------------- src/Main.hs | 37 ++++++++++------ src/Targets.hs | 2 +- src/Ways.hs | 2 +- 5 files changed, 127 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 8bdc64ccbf49838c6a90635cb45683bcc609a4b3 From git at git.haskell.org Thu Oct 26 23:27:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix parallel build, clean up code. (6b358c3) Message-ID: <20171026232714.3B1793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b358c3d68e5643d684e9a645160cb829948de47/ghc >--------------------------------------------------------------- commit 6b358c3d68e5643d684e9a645160cb829948de47 Author: Andrey Mokhov Date: Mon Dec 21 03:57:02 2015 +0000 Fix parallel build, clean up code. >--------------------------------------------------------------- 6b358c3d68e5643d684e9a645160cb829948de47 src/Oracles/PackageData.hs | 70 ++++++++++++++++++++++++---------------------- src/Rules/Data.hs | 3 +- src/Rules/Program.hs | 6 ++-- src/Settings/Packages.hs | 7 ++--- 4 files changed, 43 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 6b358c3d68e5643d684e9a645160cb829948de47 From git at git.haskell.org Thu Oct 26 23:27:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement buildPackageData rule. (4ad4d41) Message-ID: <20171026232717.61CDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f/ghc >--------------------------------------------------------------- commit 4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f Author: Andrey Mokhov Date: Mon Apr 20 01:25:09 2015 +0100 Implement buildPackageData rule. >--------------------------------------------------------------- 4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f src/Base.hs | 4 + src/Expression/Args.hs | 179 +++++++++++++++++++++++++++++++++++ src/Expression/Base.hs | 228 +++------------------------------------------ src/Expression/Build.hs | 174 +++------------------------------- src/Expression/PG.hs | 61 +++++------- src/Expression/Project.hs | 133 ++++++++++++++++++++++++++ src/Expression/Resolve.hs | 75 +++++++++------ src/Expression/Simplify.hs | 119 ++++++++++++++++++++++- src/Main.hs | 65 ++----------- src/Oracles/Builder.hs | 61 ++++++------ src/Oracles/PackageData.hs | 11 ++- src/Package.hs | 7 +- src/PackageBuild.hs | 67 ------------- src/Rules.hs | 41 ++++++++ src/Rules/Data.hs | 184 ++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 11 +++ src/Settings.hs | 116 ++--------------------- src/Switches.hs | 78 ++++++++++++++++ src/Targets.hs | 55 +++++------ 19 files changed, 933 insertions(+), 736 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 4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f From git at git.haskell.org Thu Oct 26 23:27:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build haddock and ghcTags in stage1 temporarily until stage2 is fixed. (c720083) Message-ID: <20171026232717.A727A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c720083bc93c9b22719f2b94a3861598c594572c/ghc >--------------------------------------------------------------- commit c720083bc93c9b22719f2b94a3861598c594572c Author: Andrey Mokhov Date: Mon Dec 21 12:00:32 2015 +0000 Build haddock and ghcTags in stage1 temporarily until stage2 is fixed. >--------------------------------------------------------------- c720083bc93c9b22719f2b94a3861598c594572c src/GHC.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/GHC.hs b/src/GHC.hs index f47242a..f528052 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -106,11 +106,17 @@ defaultTargetDirectory stage pkg | otherwise = "dist-install" -- TODO: simplify +-- TODO: haddock and ghtTags should be built in stage2 only -- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == haddock = case stage of + Stage1 -> Just . inplaceProgram $ pkgName pkg + Stage2 -> Just . inplaceProgram $ pkgName pkg + _ -> Nothing + | pkg == ghcTags = case stage of + Stage1 -> Just . inplaceProgram $ pkgName pkg Stage2 -> Just . inplaceProgram $ pkgName pkg _ -> Nothing | isProgram pkg = case stage of From git at git.haskell.org Thu Oct 26 23:27:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up Expression package. (51028b8) Message-ID: <20171026232720.CAA983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/51028b8d25146dde9cc45d92912acb498388c9d7/ghc >--------------------------------------------------------------- commit 51028b8d25146dde9cc45d92912acb498388c9d7 Author: Andrey Mokhov Date: Sat Apr 25 00:50:55 2015 +0100 Clean up Expression package. >--------------------------------------------------------------- 51028b8d25146dde9cc45d92912acb498388c9d7 src/Expression/Base.hs | 16 ++--- src/Expression/Build.hs | 121 -------------------------------- src/Expression/BuildExpression.hs | 21 ++++++ src/Expression/BuildPredicate.hs | 51 ++++++++++++++ src/Expression/{Args.hs => Derived.hs} | 123 ++++++++++++++++++++------------- src/Expression/Project.hs | 10 +-- src/Expression/Resolve.hs | 6 +- src/Expression/Settings.hs | 55 +++++++++++++++ src/Expression/Simplify.hs | 5 +- src/Targets.hs | 1 - 10 files changed, 222 insertions(+), 187 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 51028b8d25146dde9cc45d92912acb498388c9d7 From git at git.haskell.org Thu Oct 26 23:27:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Windows instructions (f2d3eb5) Message-ID: <20171026232721.2F27E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f2d3eb55eb6b2c1aaf6ccc995c03de0c3a330917/ghc >--------------------------------------------------------------- commit f2d3eb55eb6b2c1aaf6ccc995c03de0c3a330917 Author: Andrey Mokhov Date: Mon Dec 21 12:11:45 2015 +0000 Add Windows instructions >--------------------------------------------------------------- f2d3eb55eb6b2c1aaf6ccc995c03de0c3a330917 README.md | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/README.md b/README.md index 63673e3..8c81c13 100644 --- a/README.md +++ b/README.md @@ -19,3 +19,15 @@ $ ./configure $ make inplace/bin/ghc-cabal # This needs to be fixed $ shake-build/build.sh ``` + +On Windows, +``` +$ git clone --recursive git://git.haskell.org/ghc.git +$ cd ghc +$ git clone git://github.com/snowleopard/shaking-up-ghc shake-build +$ ./boot +$ ./configure --enable-tarballs-autodownload +$ make inplace/bin/ghc-cabal # This needs to be fixed +$ shake-build/build.bat +``` +Also see the Building GHC on Windows guide: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows. From git at git.haskell.org Thu Oct 26 23:27:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make PG and BuildPredicate abstract. (353b02b) Message-ID: <20171026232724.6D6873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/353b02bdb3999067523c30436c8a4c3dcbc2b770/ghc >--------------------------------------------------------------- commit 353b02bdb3999067523c30436c8a4c3dcbc2b770 Author: Andrey Mokhov Date: Mon Apr 27 02:36:01 2015 +0100 Make PG and BuildPredicate abstract. >--------------------------------------------------------------- 353b02bdb3999067523c30436c8a4c3dcbc2b770 src/Expression/BuildExpression.hs | 34 ++++++++++++ src/Expression/BuildPredicate.hs | 64 +++++++++++++++++++++- src/Expression/Derived.hs | 4 +- src/Expression/PG.hs | 110 +++++++++++++++++++++---------------- src/Expression/Predicate.hs | 20 ++++++- src/Expression/Project.hs | 112 +------------------------------------- src/Expression/Resolve.hs | 57 ++++++------------- src/Expression/Settings.hs | 44 ++++++++++++++- src/Expression/Simplify.hs | 109 +++++++++++++++++++------------------ src/Rules/Data.hs | 2 +- src/Settings.hs | 2 +- src/Targets.hs | 4 +- 12 files changed, 300 insertions(+), 262 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 353b02bdb3999067523c30436c8a4c3dcbc2b770 From git at git.haskell.org Thu Oct 26 23:27:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a section on how to contribute (552f617) Message-ID: <20171026232724.D37BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/552f6170baba7c06c500ed913d36a89dfec12262/ghc >--------------------------------------------------------------- commit 552f6170baba7c06c500ed913d36a89dfec12262 Author: Andrey Mokhov Date: Mon Dec 21 12:25:40 2015 +0000 Add a section on how to contribute >--------------------------------------------------------------- 552f6170baba7c06c500ed913d36a89dfec12262 README.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README.md b/README.md index 8c81c13..5d87bc4 100644 --- a/README.md +++ b/README.md @@ -31,3 +31,7 @@ $ make inplace/bin/ghc-cabal # This needs to be fixed $ shake-build/build.bat ``` Also see the Building GHC on Windows guide: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows. + +How to contribute +----------------- +The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note the codebase is very unstable at present and we expect a lot of further refactoring. Before attempting to fix any issue do make sure no one else is already working on it. The documentation is currently non-existent, but we will start addressing this once the codebase stabilises. From git at git.haskell.org Thu Oct 26 23:27:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: New refactoring started: switching to a shallow embedding. (a827aa5) Message-ID: <20171026232728.40F2C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a827aa580a188603ec8b0b30f58b254dfef8081e/ghc >--------------------------------------------------------------- commit a827aa580a188603ec8b0b30f58b254dfef8081e Author: Andrey Mokhov Date: Sun May 10 01:32:56 2015 +0100 New refactoring started: switching to a shallow embedding. >--------------------------------------------------------------- a827aa580a188603ec8b0b30f58b254dfef8081e src/Expression.hs | 84 ++++++++++++++++ src/Expression/Base.hs | 21 ---- src/Expression/BuildExpression.hs | 55 ---------- src/Expression/BuildPredicate.hs | 113 --------------------- src/Expression/Derived.hs | 204 -------------------------------------- src/Expression/PG.hs | 132 ------------------------ src/Expression/Predicate.hs | 39 -------- src/Expression/Project.hs | 27 ----- src/Expression/Resolve.hs | 100 ------------------- src/Expression/Settings.hs | 186 +++++++++++++++++----------------- src/Expression/Simplify.hs | 127 ------------------------ 11 files changed, 178 insertions(+), 910 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 a827aa580a188603ec8b0b30f58b254dfef8081e From git at git.haskell.org Thu Oct 26 23:27:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Show instances. (31d8890) Message-ID: <20171026232728.A167F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31d88906c1b734a5d2d0dd39b79415547a6affea/ghc >--------------------------------------------------------------- commit 31d88906c1b734a5d2d0dd39b79415547a6affea Author: Andrey Mokhov Date: Tue Dec 22 04:59:02 2015 +0000 Fix Show instances. >--------------------------------------------------------------- 31d88906c1b734a5d2d0dd39b79415547a6affea src/Oracles/Config/Setting.hs | 8 ++++---- src/Stage.hs | 6 ++---- src/Target.hs | 2 +- src/Way.hs | 1 + 4 files changed, 8 insertions(+), 9 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index fa62f97..8f0b1df 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -85,10 +85,10 @@ setting key = askConfig $ case key of settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of - ConfCcArgs stage -> "conf-cc-args-stage" ++ show stage - ConfCppArgs stage -> "conf-cpp-args-stage" ++ show stage - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show stage - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show stage + ConfCcArgs stage -> "conf-cc-args-stage" ++ show (fromEnum stage) + ConfCppArgs stage -> "conf-cpp-args-stage" ++ show (fromEnum stage) + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show (fromEnum stage) + ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show (fromEnum stage) GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" HsCppArgs -> "hs-cpp-args" diff --git a/src/Stage.hs b/src/Stage.hs index 3aca206..d474557 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -5,10 +5,8 @@ import Base import GHC.Generics (Generic) -- TODO: explain stages -data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum, Generic) - -instance Show Stage where - show = show . fromEnum +data Stage = Stage0 | Stage1 | Stage2 | Stage3 + deriving (Show, Eq, Ord, Enum, Generic) -- Instances for storing in the Shake database instance Binary Stage diff --git a/src/Target.hs b/src/Target.hs index c70790d..2060d04 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -37,7 +37,7 @@ instance Monoid a => Monoid (ReaderT Target Action a) where -- PartialTarget is a partially constructed Target with fields Stage and -- Package only. PartialTarget's are used for generating build rules. -data PartialTarget = PartialTarget Stage Package +data PartialTarget = PartialTarget Stage Package deriving Show -- Convert PartialTarget to Target assuming that unknown fields won't be used. fromPartial :: PartialTarget -> Target diff --git a/src/Way.hs b/src/Way.hs index 095bd52..28d1365 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -28,6 +28,7 @@ data WayUnit = Threaded | GranSim deriving (Eq, Enum) +-- TODO: get rid of non-derived Show instances instance Show WayUnit where show unit = case unit of Threaded -> "thr" From git at git.haskell.org Thu Oct 26 23:27:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add topLevel function to construct top-level packages like compiler. (f60980a) Message-ID: <20171026232731.9A14E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f60980a571dc9da77a6718d889faf0b8a9b4b58b/ghc >--------------------------------------------------------------- commit f60980a571dc9da77a6718d889faf0b8a9b4b58b Author: Andrey Mokhov Date: Sun May 10 01:36:35 2015 +0100 Add topLevel function to construct top-level packages like compiler. >--------------------------------------------------------------- f60980a571dc9da77a6718d889faf0b8a9b4b58b src/Package.hs | 15 ++++++--------- 1 file changed, 6 insertions(+), 9 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index e5dc94e..3b2f0ec 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,4 +1,4 @@ -module Package (Package (..), library, setCabal) where +module Package (Package (..), library, topLevel, setCabal) where import Base import Util @@ -20,15 +20,12 @@ instance Eq Package where instance Ord Package where compare = compare `on` pkgName -libraryPackage :: String -> String -> Package -libraryPackage name cabalName = - Package - name - (unifyPath $ "libraries" name) - cabalName - library :: String -> Package -library name = libraryPackage name (name <.> "cabal") +library name = + Package name (unifyPath $ "libraries" name) (name <.> "cabal") + +topLevel :: String -> Package +topLevel name = Package name name (name <.> "cabal") setCabal :: Package -> FilePath -> Package setCabal pkg cabalName = pkg { pkgCabal = cabalName } From git at git.haskell.org Thu Oct 26 23:27:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for turnWarningsIntoErrors in Settings/User.hs. (3d90d06) Message-ID: <20171026232732.257F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d90d06aa59af43da7edb79dbd930d6fa34c5b9f/ghc >--------------------------------------------------------------- commit 3d90d06aa59af43da7edb79dbd930d6fa34c5b9f Author: Andrey Mokhov Date: Tue Dec 22 05:00:31 2015 +0000 Add support for turnWarningsIntoErrors in Settings/User.hs. >--------------------------------------------------------------- 3d90d06aa59af43da7edb79dbd930d6fa34c5b9f src/Settings/User.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 4c7a5f4..e16fb27 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands + verboseCommands, turnWarningsIntoErrors ) where import Expression @@ -88,3 +88,7 @@ buildSystemConfigFile = False -- only, e.g.: verboseCommands = package ghcPrim verboseCommands :: Predicate verboseCommands = return False + +-- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. +turnWarningsIntoErrors :: Predicate +turnWarningsIntoErrors = return False From git at git.haskell.org Thu Oct 26 23:27:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove TargetDir from Base.hs. (f033f1f) Message-ID: <20171026232735.1FBBA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f033f1ff0b94df3b12dd32d774043522c96f0cac/ghc >--------------------------------------------------------------- commit f033f1ff0b94df3b12dd32d774043522c96f0cac Author: Andrey Mokhov Date: Sun May 10 01:37:24 2015 +0100 Remove TargetDir from Base.hs. >--------------------------------------------------------------- f033f1ff0b94df3b12dd32d774043522c96f0cac src/Base.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 2bd350f..49b0fb2 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -8,7 +8,6 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - TargetDir (..), Arg, Args, ShowArg (..), ShowArgs (..), arg, args, @@ -29,9 +28,6 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) instance Show Stage where show = show . fromEnum --- Need TargetDir and FilePath to be distinct types -newtype TargetDir = TargetDir { fromTargetDir :: FilePath } deriving (Show, Eq) - -- The returned string or list of strings is a part of an argument list -- to be passed to a Builder type Arg = Action String From git at git.haskell.org Thu Oct 26 23:27:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve naming convention for build directories: always use stageN. (52ecf6c) Message-ID: <20171026232735.928BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/52ecf6cb909644928ed754f5b111034ecb9dafc3/ghc >--------------------------------------------------------------- commit 52ecf6cb909644928ed754f5b111034ecb9dafc3 Author: Andrey Mokhov Date: Tue Dec 22 05:05:11 2015 +0000 Improve naming convention for build directories: always use stageN. >--------------------------------------------------------------- 52ecf6cb909644928ed754f5b111034ecb9dafc3 src/GHC.hs | 18 ++---------------- src/Rules.hs | 3 +-- src/Rules/Data.hs | 20 ++++++++++---------- src/Rules/Program.hs | 18 ++++++++++-------- src/Settings/Builders/Ghc.hs | 2 ++ src/Settings/Builders/GhcCabal.hs | 23 ++++++++++------------- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Packages.hs | 2 ++ 8 files changed, 38 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 52ecf6cb909644928ed754f5b111034ecb9dafc3 From git at git.haskell.org Thu Oct 26 23:27:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add documentation drafts. (a2de9b0) Message-ID: <20171026232738.F087E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2de9b043b90ef7fc68fea6b1f16535e9f7a20c8/ghc >--------------------------------------------------------------- commit a2de9b043b90ef7fc68fea6b1f16535e9f7a20c8 Author: Andrey Mokhov Date: Sun May 10 01:39:20 2015 +0100 Add documentation drafts. >--------------------------------------------------------------- a2de9b043b90ef7fc68fea6b1f16535e9f7a20c8 doc/build-expressions.docx | Bin 0 -> 22575 bytes doc/build-expressions.pdf | Bin 0 -> 644843 bytes 2 files changed, 0 insertions(+), 0 deletions(-) diff --git a/doc/build-expressions.docx b/doc/build-expressions.docx new file mode 100644 index 0000000..e4fef75 Binary files /dev/null and b/doc/build-expressions.docx differ diff --git a/doc/build-expressions.pdf b/doc/build-expressions.pdf new file mode 100644 index 0000000..bf70430 Binary files /dev/null and b/doc/build-expressions.pdf differ From git at git.haskell.org Thu Oct 26 23:27:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (eda28da) Message-ID: <20171026232739.61E4A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eda28da9f239b66ea1791d0ac9850cfae1232248/ghc >--------------------------------------------------------------- commit eda28da9f239b66ea1791d0ac9850cfae1232248 Author: Andrey Mokhov Date: Tue Dec 22 05:07:32 2015 +0000 Clean up. >--------------------------------------------------------------- eda28da9f239b66ea1791d0ac9850cfae1232248 src/Rules/Library.hs | 2 +- src/Settings.hs | 11 +++++------ 2 files changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 134e2be..ff5ce63 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -49,7 +49,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do putSuccess $ renderBox [ "Successfully built package library '" ++ pkgName pkg - ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." + ++ "' (" ++ show stage ++ ", way "++ show way ++ ")." , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." ] diff --git a/src/Settings.hs b/src/Settings.hs index fd7c14c..9a0e07d 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -53,26 +53,25 @@ getPackageSources = do return $ foundSources ++ fixGhcPrim generatedSources -- findModuleFiles scans a list of given directories and finds files matching a --- given extension pattern (e.g., "*hs") that correspond to modules of the --- currently built package. Missing module files are returned in a separate --- list. The returned pair contains the following: +-- given pattern (e.g., "*hs") that correspond to modules of the currently built +-- package. Missing module files are returned in a separate list. The returned +-- pair contains the following: -- * a list of found module files, with paths being relative to one of given -- directories, e.g. "codeGen/CodeGen/Platform.hs" for the compiler package. -- * a list of module files that have not been found, with paths being relative -- to the module directory, e.g. "CodeGen/Platform", and with no extension. findModuleFiles :: [FilePath] -> FilePattern -> Expr ([FilePath], [FilePath]) -findModuleFiles dirs extension = do +findModuleFiles dirs pattern = do modules <- getPkgDataList Modules let decodedMods = sort . map decodeModule $ modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedMods - matchExtension = (?==) ("*" <.> extension) result <- lift . fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do let fullDir = dir -/- mDir - files <- fmap (filter matchExtension) $ getDirectoryContents fullDir + files <- getDirectoryFiles fullDir [pattern] let cmp fe f = compare (dropExtension fe) f found = intersectOrd cmp files mFiles return (map (fullDir -/-) found, (mDir, map dropExtension found)) From git at git.haskell.org Thu Oct 26 23:27:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageDependencies rule. (2be9217) Message-ID: <20171026232742.6CBC13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2be9217deed8466c4aa62ac4120174a354d342c8/ghc >--------------------------------------------------------------- commit 2be9217deed8466c4aa62ac4120174a354d342c8 Author: Andrey Mokhov Date: Sun May 10 01:40:19 2015 +0100 Add buildPackageDependencies rule. >--------------------------------------------------------------- 2be9217deed8466c4aa62ac4120174a354d342c8 src/Rules/Dependencies.hs | 185 ++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 185 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs new file mode 100644 index 0000000..930ba98 --- /dev/null +++ b/src/Rules/Dependencies.hs @@ -0,0 +1,185 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module Rules.Data ( + ghcArgs, gccArgs, buildPackageDependencies + ) where + +import qualified Ways +import Base hiding (arg, args, Args) +import Package +import Expression.Base +import Oracles.Flag (when) +import Oracles.Builder +import Targets +import Switches +import Util + +packageSettings :: Settings +packageSettings = msum + [ args ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] + , stage Stage0 ? + (arg "-package-db" |> argPath "libraries/bootstrapping.conf") + , supportsPackageKey ? notStage Stage0 ?? + ( argPairs "-this-package-key" argPackageKey <|> + argPairs "-package-key" argPackageDepKeys + , argPairs "-package-name" argPackageKey <|> + argPairs "-package" argPackageDeps )] + +ghcArgs :: Settings +ghcArgs = + let pathDist = path dist + buildDir = unifyPath $ pathDist "build" + depFile = buildDir "haskell.deps" + in msum [ arg "-M" + , packageSettings + , includeGhcArgs path dist + , concatArgs ["-optP"] $ CppArgs pathDist + , productArgs ["-odir", "-stubdir", "-hidir"] [buildDir] + , args ["-dep-makefile", depFile] + , productArgs ["-dep-suffix"] $ map wayPrefix <$> ways settings + , args $ HsArgs pathDist + , args $ pkgHsSources path dist ] + +-- $1_$2_$3_ALL_CC_OPTS = \ +-- $$(WAY_$3_CC_OPTS) \ +-- $$($1_$2_DIST_GCC_CC_OPTS) \ +-- $$($1_$2_$3_CC_OPTS) \ +-- $$($$(basename $$<)_CC_OPTS) \ +-- $$($1_$2_EXTRA_CC_OPTS) \ +-- $$(EXTRA_CC_OPTS) +-- +-- $1_$2_DIST_CC_OPTS = \ +-- $$(SRC_CC_OPTS) \ +-- $$($1_CC_OPTS) \ +-- -I$1/$2/build/autogen \ +-- $$(foreach dir,$$(filter-out /%,$$($1_$2_INCLUDE_DIRS)),-I$1/$$(dir)) \ +-- $$(foreach dir,$$(filter /%,$$($1_$2_INCLUDE_DIRS)),-I$$(dir)) \ +-- $$($1_$2_CC_OPTS) \ +-- $$($1_$2_CPP_OPTS) \ +-- $$($1_$2_CC_INC_FLAGS) \ +-- $$($1_$2_DEP_CC_OPTS) \ +-- $$(SRC_CC_WARNING_OPTS) + +-- TODO: handle custom $1_$2_MKDEPENDC_OPTS and +gccArgs :: FilePath -> Package -> TodoItem -> Args +gccArgs sourceFile (Package _ path _ _) (stage, dist, settings) = + let pathDist = path dist + buildDir = pathDist "build" + depFile = buildDir takeFileName sourceFile <.> "deps" + in args [ args ["-E", "-MM"] -- TODO: add a Cpp Builder instead + , args $ CcArgs pathDist + , commonCcArgs -- TODO: remove? + , customCcArgs settings -- TODO: Replace by customCppArgs? + , commonCcWarninigArgs -- TODO: remove? + , includeGccArgs path dist + , args ["-MF", unifyPath depFile] + , args ["-x", "c"] + , arg $ unifyPath sourceFile ] + +buildRule :: Package -> TodoItem -> Rules () +buildRule pkg @ (Package name path _ _) todo @ (stage, dist, settings) = do + let pathDist = path dist + buildDir = pathDist "build" + + (buildDir "haskell.deps") %> \_ -> do + run (Ghc stage) $ ghcArgs pkg todo + -- Finally, record the argument list + need [argListPath argListDir pkg stage] + + (buildDir "c.deps") %> \out -> do + srcs <- args $ CSrcs pathDist + deps <- fmap concat $ forM srcs $ \src -> do + let srcPath = path src + depFile = buildDir takeFileName src <.> "deps" + run (Gcc stage) $ gccArgs srcPath pkg todo + liftIO $ readFile depFile + writeFileChanged out deps + liftIO $ removeFiles buildDir ["*.c.deps"] + -- Finally, record the argument list + need [argListPath argListDir pkg stage] + +argListRule :: Package -> TodoItem -> Rules () +argListRule pkg todo @ (stage, _, _) = + (argListPath argListDir pkg stage) %> \out -> do + need $ ["shake/src/Package/Dependencies.hs"] ++ sourceDependecies + ghcList <- argList (Ghc stage) $ ghcArgs pkg todo + gccList <- argList (Gcc stage) $ gccArgs "source.c" pkg todo + writeFileChanged out $ ghcList ++ "\n" ++ gccList + +buildPackageDependencies :: Package -> TodoItem -> Rules () +buildPackageDependencies = argListRule <> buildRule + + +-- Build package-data.mk by using GhcCabal to process pkgCabal file +buildPackageData :: Stage -> Package -> FilePath -> Ways -> Settings -> Rules () +buildPackageData stage pkg dir ways settings = + (dir ) <$> + [ "package-data.mk" + , "haddock-prologue.txt" + , "inplace-pkg-config" + , "setup-config" + , "build" "autogen" "cabal_macros.h" + -- TODO: Is this needed? Also check out Paths_cpsa.hs. + -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" + ] &%> \_ -> do + let configure = pkgPath pkg "configure" + need [pkgPath pkg pkgCabal pkg] + -- GhcCabal will run the configure script, so we depend on it + -- We still don't know who build the configure script from configure.ac + when (doesFileExist $ configure <.> "ac") $ need [configure] + run' GhcCabal settings + -- TODO: when (registerPackage settings) $ + run' (GhcPkg stage) settings + postProcessPackageData $ dir "package-data.mk" + +run' :: Builder -> Settings -> Action () +run' builder settings = do + settings' <- evaluate (project builder settings) + case fromSettings settings' of + Nothing -> + redError $ "Cannot determine " ++ show builder ++ " settings." + Just args -> do + putColoured Green (show args) + run builder args + +--buildRule :: Package -> TodoItem -> Rules () +--buildRule pkg @ (Package name path cabal _) todo @ (stage, dist, settings) = +-- let pathDist = path dist +-- cabalPath = path cabal +-- configure = path "configure" +-- in +-- -- All these files are produced by a single run of GhcCabal +-- (pathDist ) <$> +-- [ "package-data.mk" +-- , "haddock-prologue.txt" +-- , "inplace-pkg-config" +-- , "setup-config" +-- , "build" "autogen" "cabal_macros.h" +-- -- TODO: Is this needed? Also check out Paths_cpsa.hs. +-- -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" +-- ] &%> \_ -> do +-- need [cabalPath] +-- when (doesFileExist $ configure <.> "ac") $ need [configure] +-- -- GhcCabal will run the configure script, so we depend on it +-- -- We still don't know who build the configure script from configure.ac +-- run GhcCabal $ cabalArgs pkg todo +-- when (registerPackage settings) $ +-- run (GhcPkg stage) $ ghcPkgArgs pkg todo +-- postProcessPackageData $ pathDist "package-data.mk" + +ccSettings :: Settings +ccSettings = msum + [ package integerLibrary ? argPath "-Ilibraries/integer-gmp2/gmp" + , builder GhcCabal ? argStagedConfig "conf-cc-args" + , validating ? msum + [ not (builder GhcCabal) ? arg "-Werror" + , arg "-Wall" + , gccIsClang ?? + ( arg "-Wno-unknown-pragmas" <|> + not gccLt46 ? windowsHost ? arg "-Werror=unused-but-set-variable" + , not gccLt46 ? arg "-Wno-error=inline" )]] + +ldSettings :: Settings +ldSettings = builder GhcCabal ? argStagedConfig "conf-gcc-linker-args" + +cppSettings :: Settings +cppSettings = builder GhcCabal ? argStagedConfig "conf-cpp-args" From git at git.haskell.org Thu Oct 26 23:27:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix tracking of *.hs-incl files. (363b227) Message-ID: <20171026232742.C1BC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/363b227e1e310561018c1991249cbf21bf28be57/ghc >--------------------------------------------------------------- commit 363b227e1e310561018c1991249cbf21bf28be57 Author: Andrey Mokhov Date: Tue Dec 22 05:09:27 2015 +0000 Fix tracking of *.hs-incl files. >--------------------------------------------------------------- 363b227e1e310561018c1991249cbf21bf28be57 src/Rules/Dependencies.hs | 40 +++++++++++++++++++--------------------- 1 file changed, 19 insertions(+), 21 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 996d927..47e6c6d 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -24,7 +24,24 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = hDepFile %> \file -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) $ need [platformH] - need srcs + -- TODO: very ugly and fragile; use gcc -MM instead? + let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] + need $ srcs ++ extraDeps if srcs == [] then writeFileChanged file "" else build $ fullTarget target (GhcM stage) srcs [file] @@ -36,23 +53,4 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need $ hDepFile : cDepFiles -- need all for more parallelism cDeps <- fmap concat $ mapM readFile' cDepFiles hDeps <- readFile' hDepFile - -- TODO: very ugly and fragile; use gcc -MM instead? - let hsIncl hs incl = buildPath -/- hs <.> "o" ++ " : " - ++ buildPath -/- incl ++ "\n" - extraDeps = if pkg /= compiler then [] else - hsIncl "PrelNames" "primop-vector-uniques.hs-incl" - ++ hsIncl "PrimOp" "primop-data-decl.hs-incl" - ++ hsIncl "PrimOp" "primop-tag.hs-incl" - ++ hsIncl "PrimOp" "primop-list.hs-incl" - ++ hsIncl "PrimOp" "primop-strictness.hs-incl" - ++ hsIncl "PrimOp" "primop-fixity.hs-incl" - ++ hsIncl "PrimOp" "primop-primop-info.hs-incl" - ++ hsIncl "PrimOp" "primop-out-of-line.hs-incl" - ++ hsIncl "PrimOp" "primop-has-side-effects.hs-incl" - ++ hsIncl "PrimOp" "primop-can-fail.hs-incl" - ++ hsIncl "PrimOp" "primop-code-size.hs-incl" - ++ hsIncl "PrimOp" "primop-commutable.hs-incl" - ++ hsIncl "TysPrim" "primop-vector-tys-exports.hs-incl" - ++ hsIncl "TysPrim" "primop-vector-tycons.hs-incl" - ++ hsIncl "TysPrim" "primop-vector-tys.hs-incl" - writeFileChanged file $ cDeps ++ hDeps ++ extraDeps + writeFileChanged file $ cDeps ++ hDeps From git at git.haskell.org Thu Oct 26 23:27:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Continue refactoring. (cf54d1a) Message-ID: <20171026232746.7B92A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf54d1aacd927a06a74918de2db479ac6d5ef2a8/ghc >--------------------------------------------------------------- commit cf54d1aacd927a06a74918de2db479ac6d5ef2a8 Author: Andrey Mokhov Date: Sun May 10 01:41:36 2015 +0100 Continue refactoring. >--------------------------------------------------------------- cf54d1aacd927a06a74918de2db479ac6d5ef2a8 src/Rules.hs | 8 ++-- src/Rules/Data.hs | 23 +++++---- src/Rules/Package.hs | 2 +- src/Settings.hs | 11 ----- src/Switches.hs | 95 ++++++++++++++++++------------------ src/Targets.hs | 132 +++++++++++++++++++++++++++------------------------ 6 files changed, 138 insertions(+), 133 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 cf54d1aacd927a06a74918de2db479ac6d5ef2a8 From git at git.haskell.org Thu Oct 26 23:27:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy *.hs-boot files of generated sources. (4e2f6c5) Message-ID: <20171026232746.C4A713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e2f6c504a541f7a6eab6eb072bae265d67e5bff/ghc >--------------------------------------------------------------- commit 4e2f6c504a541f7a6eab6eb072bae265d67e5bff Author: Andrey Mokhov Date: Tue Dec 22 05:10:46 2015 +0000 Copy *.hs-boot files of generated sources. >--------------------------------------------------------------- 4e2f6c504a541f7a6eab6eb072bae265d67e5bff src/Rules/Generate.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 53b7dd6..10a4e6b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -29,11 +29,12 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = buildPath = path -/- "build" primopsTxt = targetPath stage compiler -/- "build/primops.txt" platformH = targetPath stage compiler -/- "ghc_boot_platform.h" - in do -- TODO: do we need to copy *.(l)hs-boot files here? Never happens? - buildPath -/- "*.hs" %> \file -> do + generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) + in do + generated ?> \file -> do dirs <- interpretPartial target $ getPkgDataList SrcDirs files <- getDirectoryFiles "" $ - [ packagePath -/- d -/- takeBaseName file <.> "*" | d <- dirs ] + [ packagePath -/- d ++ "//" ++ takeBaseName file <.> "*" | d <- dirs ] let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ "Exactly one generator expected for " ++ file @@ -41,6 +42,9 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = let (src, builder) = head gens need [src] build $ fullTarget target builder [src] [file] + let srcBoot = src -<.> "hs-boot" + whenM (doesFileExist srcBoot) $ + copyFileChanged srcBoot $ file -<.> "hs-boot" when (pkg == compiler) $ primopsTxt %> \file -> do need [platformH, primopsSource] @@ -80,7 +84,7 @@ quote :: String -> String quote s = "\"" ++ s ++ "\"" -- TODO: do we need ghc-split? Always or is it platform specific? --- TODO: add tracking +-- TODO: add tracking by moving these functions to separate tracked files generateConfigHs :: Expr String generateConfigHs = do cProjectName <- getSetting ProjectName From git at git.haskell.org Thu Oct 26 23:27:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop parameterisation by monad in Expression. (fdb6117) Message-ID: <20171026232749.E26E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fdb6117f21e3bc39ae97bf0f12c0fc3caf10e093/ghc >--------------------------------------------------------------- commit fdb6117f21e3bc39ae97bf0f12c0fc3caf10e093 Author: Andrey Mokhov Date: Mon Jun 8 02:07:09 2015 +0100 Drop parameterisation by monad in Expression. >--------------------------------------------------------------- fdb6117f21e3bc39ae97bf0f12c0fc3caf10e093 src/Expression.hs | 51 ++++++++++++++++++++++++++++----------------------- 1 file changed, 28 insertions(+), 23 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index fc70be1..de5fae9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -2,13 +2,11 @@ module Expression ( module Control.Monad.Reader, Ways, - Packages, - TargetDir, Predicate, Expression, - Environment (..), + Environment (..), defaultEnvironment, interpret, - whenPredicate, (?), stage, notStage, package, + whenPredicate, (?), (??), stage, notStage, builder, notBuilder, package, configKeyValue, configKeyValues, configKeyYes, configKeyNo, configKeyNonEmpty ) where @@ -34,51 +32,58 @@ defaultEnvironment = Environment getPackage = error "Package not set in the environment" } -type Expression m a = ReaderT Environment m a +type Expression a = ReaderT Environment Action a -type Ways m = Expression m [Way] -type Packages m = Expression m [Package] -type Predicate m = Expression m Bool -type TargetDir m = Expression m FilePath +type Ways = Expression [Way] +type Predicate = Expression Bool -instance (Monad m, Monoid a) => Monoid (Expression m a) where +instance Monoid a => Monoid (Expression a) where mempty = return mempty mappend = liftM2 mappend -interpret :: (Monad m, Monoid a) => Expression m a -> Environment -> m a -interpret = runReaderT +interpret :: Environment -> Expression a -> Action a +interpret = flip runReaderT -whenPredicate :: (Monad m, Monoid a) => Predicate m -> Expression m a -> Expression m a +whenPredicate :: Monoid a => Predicate -> Expression a -> Expression a whenPredicate predicate expr = do bool <- predicate if bool then expr else return mempty -(?) :: (Monad m, Monoid a) => Predicate m -> Expression m a -> Expression m a +(?) :: Monoid a => Predicate -> Expression a -> Expression a (?) = whenPredicate +(??) :: Monoid a => Predicate -> (Expression a, Expression a) -> Expression a +p ?? (t, f) = p ? t <> (liftM not p) ? f + infixr 8 ? -stage :: Monad m => Stage -> Predicate m +stage :: Stage -> Predicate stage s = liftM (s ==) (asks getStage) -notStage :: Monad m => Stage -> Predicate m +notStage :: Stage -> Predicate notStage = liftM not . stage -package :: Monad m => Package -> Predicate m +builder :: Builder -> Predicate +builder b = liftM (b ==) (asks getBuilder) + +notBuilder :: Builder -> Predicate +notBuilder = liftM not . builder + +package :: Package -> Predicate package p = liftM (p ==) (asks getPackage) -configKeyValue :: String -> String -> Predicate Action +configKeyValue :: String -> String -> Predicate configKeyValue key value = liftM (value ==) (lift $ askConfig key) -- checks if there is at least one match -configKeyValues :: String -> [String] -> Predicate Action +configKeyValues :: String -> [String] -> Predicate configKeyValues key values = liftM (flip elem $ values) (lift $ askConfig key) -configKeyYes :: String -> Predicate Action +configKeyYes :: String -> Predicate configKeyYes key = configKeyValue key "YES" -configKeyNo :: String -> Predicate Action +configKeyNo :: String -> Predicate configKeyNo key = configKeyValue key "NO" -configKeyNonEmpty :: String -> Predicate Action -configKeyNonEmpty key = configKeyValue key "" +configKeyNonEmpty :: String -> Predicate +configKeyNonEmpty key = liftM not $ configKeyValue key "" From git at git.haskell.org Thu Oct 26 23:27:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove a duplicate success message when building Lib0. (bfe72a5) Message-ID: <20171026232750.4C01F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bfe72a5f9fa4aa31bf9e83ad690aef6b8741f8e6/ghc >--------------------------------------------------------------- commit bfe72a5f9fa4aa31bf9e83ad690aef6b8741f8e6 Author: Andrey Mokhov Date: Tue Dec 22 05:25:01 2015 +0000 Remove a duplicate success message when building Lib0. >--------------------------------------------------------------- bfe72a5f9fa4aa31bf9e83ad690aef6b8741f8e6 src/Rules/Library.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index ff5ce63..12102c0 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -41,17 +41,17 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do let objs = cObjs ++ splitObjs ++ eObjs asuf <- libsuf way - if ("//*-0" <.> asuf) ?== a + let isLib0 = ("//*-0" <.> asuf) ?== a + if isLib0 then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls else build $ fullTarget target Ar objs [a] synopsis <- interpretPartial target $ getPkgData Synopsis - putSuccess $ renderBox + unless isLib0 . putSuccess $ renderBox [ "Successfully built package library '" ++ pkgName pkg ++ "' (" ++ show stage ++ ", way "++ show way ++ ")." - , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." - ] + , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." ] -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. From git at git.haskell.org Thu Oct 26 23:27:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish buildPackageData with the Reader approach. (031179a) Message-ID: <20171026232753.CB8703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/031179a7506ef56897b6316fc83b46fecfb61946/ghc >--------------------------------------------------------------- commit 031179a7506ef56897b6316fc83b46fecfb61946 Author: Andrey Mokhov Date: Mon Jun 8 02:08:57 2015 +0100 Finish buildPackageData with the Reader approach. >--------------------------------------------------------------- 031179a7506ef56897b6316fc83b46fecfb61946 src/Expression/Settings.hs | 15 ++-- src/Rules.hs | 41 ++++----- src/Rules/Data.hs | 202 ++++++++++++++++++++++++++------------------- src/Rules/Package.hs | 1 + src/Settings.hs | 11 +-- src/Switches.hs | 39 +++++---- src/Targets.hs | 70 +++++++++------- 7 files changed, 206 insertions(+), 173 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 031179a7506ef56897b6316fc83b46fecfb61946 From git at git.haskell.org Thu Oct 26 23:27:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement encodeModule -- the inverse for decodeModule. (ba41ded) Message-ID: <20171026232754.320E83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba41dedc0c632836dff3c3ce55f7210d344e44e7/ghc >--------------------------------------------------------------- commit ba41dedc0c632836dff3c3ce55f7210d344e44e7 Author: Andrey Mokhov Date: Wed Dec 23 06:12:19 2015 +0000 Implement encodeModule -- the inverse for decodeModule. >--------------------------------------------------------------- ba41dedc0c632836dff3c3ce55f7210d344e44e7 src/Base.hs | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index ac457ad..79ce119 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -25,9 +25,8 @@ module Base ( module System.Console.ANSI, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, - removeFileIfExists, - replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, + bimap, minusOrd, intersectOrd, removeFileIfExists, replaceEq, chunksOfSize, + replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-) ) where import Control.Applicative @@ -78,12 +77,18 @@ replaceSeparators = replaceIf isPathSeparator replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) --- | Given a module name extract the directory and file names, e.g.: +-- | Given a module name extract the directory and file name, e.g.: -- -- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") decodeModule :: String -> (FilePath, String) decodeModule = splitFileName . replaceEq '.' '/' +-- | Given the directory and file name find the corresponding module name, e.g.: +-- +-- > encodeModule "Data/Functor/" "Identity.hs" = "Data.Functor.Identity" +encodeModule :: FilePath -> String -> String +encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file + -- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx From git at git.haskell.org Thu Oct 26 23:27:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify build rule interfaces. (622d3c1) Message-ID: <20171026232757.373233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/622d3c164d3c36fba97e780a5d3e3b4049e18417/ghc >--------------------------------------------------------------- commit 622d3c164d3c36fba97e780a5d3e3b4049e18417 Author: Andrey Mokhov Date: Sat Jun 13 14:14:03 2015 +0100 Simplify build rule interfaces. >--------------------------------------------------------------- 622d3c164d3c36fba97e780a5d3e3b4049e18417 src/Rules.hs | 4 ++-- src/Rules/Data.hs | 9 ++++++--- src/Rules/Package.hs | 3 +-- 3 files changed, 9 insertions(+), 7 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 8f2825f..dd9e2e0 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -30,5 +30,5 @@ packageRules :: Rules () packageRules = forM_ [Stage0, Stage1] $ \stage -> do forM_ targetPackages $ \pkg -> do - let dir = pkgPath pkg targetDirectory stage pkg - buildPackage stage pkg dir targetWays buildSettings + let env = defaultEnvironment { getStage = stage, getPackage = pkg } + buildPackage env targetWays buildSettings diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 0a1abf1..7447e5e 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -140,8 +140,12 @@ postProcessPackageData file = do -- * otherwise, we must collapse it into one space-separated string -- Build package-data.mk by using GhcCabal to process pkgCabal file -buildPackageData :: Stage -> Package -> FilePath -> Ways -> Settings -> Rules () -buildPackageData stage pkg dir ways settings = +buildPackageData :: Environment -> Ways -> Settings -> Rules () +buildPackageData env ways settings = + let stage = getStage env + pkg = getPackage env + dir = pkgPath pkg targetDirectory stage pkg + in (dir ) <$> [ "package-data.mk" , "haddock-prologue.txt" @@ -152,7 +156,6 @@ buildPackageData stage pkg dir ways settings = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" - env = defaultEnvironment { getStage = stage, getPackage = pkg } need [pkgPath pkg pkgCabal pkg] -- GhcCabal will run the configure script, so we depend on it -- We still don't know who build the configure script from configure.ac diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 5ce0ed9..d56bb30 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -3,10 +3,9 @@ module Rules.Package ( ) where import Base -import Package import Rules.Data import Expression import Expression.Settings -buildPackage :: Stage -> Package -> FilePath -> Ways -> Settings -> Rules () +buildPackage :: Environment -> Ways -> Settings -> Rules () buildPackage = buildPackageData From git at git.haskell.org Thu Oct 26 23:27:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:27:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (ecdeae7) Message-ID: <20171026232757.97EBA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ecdeae76f0a89eec2f95a5285f174ef6ef107329/ghc >--------------------------------------------------------------- commit ecdeae76f0a89eec2f95a5285f174ef6ef107329 Author: Andrey Mokhov Date: Wed Dec 23 06:13:11 2015 +0000 Clean up. >--------------------------------------------------------------- ecdeae76f0a89eec2f95a5285f174ef6ef107329 src/Oracles/WindowsRoot.hs | 2 +- src/Rules/Data.hs | 26 +++++++++++++------------- 2 files changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 51cb516..2ec13c7 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -14,7 +14,7 @@ windowsRoot = askOracle $ WindowsRoot () -- the root is slow (at least the current implementation). windowsRootOracle :: Rules () windowsRootOracle = do - root <- newCache $ \() -> do + root <- newCache $ \_ -> do Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] let root = dropWhileEnd isSpace out putOracle $ "Detected root on Windows: " ++ root diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 96deed9..26755ca 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -44,19 +44,19 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- TODO: code duplication around ghcIncludeDirs priority 2.0 $ do when (pkg == hp2ps) $ dataFile %> \mk -> do - let cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" - , "Reorder.c", "TopTwenty.c", "AuxFile.c", "Deviation.c" - , "HpFile.c", "Marks.c", "Scale.c", "TraceElement.c" - , "Axes.c", "Dimensions.c", "Key.c", "PsFile.c" - , "Shade.c", "Utilities.c" ] - contents = unlines - [ "utils_hp2ps_stage0_PROGNAME = hp2ps" - , "utils_hp2ps_stage0_C_SRCS = " ++ unwords cSrcs - , "utils_hp2ps_stage0_INSTALL = YES" - , "utils_hp2ps_stage0_INSTALL_INPLACE = YES" - , "utils_hp2ps_stage0_DEP_EXTRA_LIBS = m" - , "utils_hp2ps_stage0_CC_OPTS = " - ++ unwords (map ("-I"++) ghcIncludeDirs) ] + let prefix = "utils_hp2ps_stage" ++ show (fromEnum stage) ++ "_" + cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" + , "Reorder.c", "TopTwenty.c", "AuxFile.c" + , "Deviation.c", "HpFile.c", "Marks.c", "Scale.c" + , "TraceElement.c", "Axes.c", "Dimensions.c", "Key.c" + , "PsFile.c", "Shade.c", "Utilities.c" ] + contents = unlines $ map (prefix++) + [ "PROGNAME = hp2ps" + , "C_SRCS = " ++ unwords cSrcs + , "INSTALL = YES" + , "INSTALL_INPLACE = YES" + , "DEP_EXTRA_LIBS = m" + , "CC_OPTS = " ++ unwords (map ("-I"++) ghcIncludeDirs) ] writeFileChanged mk contents putBuild $ "| Successfully generated '" ++ mk ++ "'." From git at git.haskell.org Thu Oct 26 23:28:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add example UserSettings.hs. (b5bf68d) Message-ID: <20171026232800.EFA8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b5bf68d5ec49bf888321dc7a55e02c772b073de5/ghc >--------------------------------------------------------------- commit b5bf68d5ec49bf888321dc7a55e02c772b073de5 Author: Andrey Mokhov Date: Sun Jun 14 01:18:49 2015 +0100 Add example UserSettings.hs. >--------------------------------------------------------------- b5bf68d5ec49bf888321dc7a55e02c772b073de5 src/UserSettings.hs | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/src/UserSettings.hs b/src/UserSettings.hs new file mode 100644 index 0000000..0a37159 --- /dev/null +++ b/src/UserSettings.hs @@ -0,0 +1,17 @@ +module UserSettings ( + userSettings + ) where + +import Base hiding (arg, args, Args) +import Rules.Data +import Oracles.Builder +import Expression +import Expression.Settings + +userSettings :: Settings +userSettings = mconcat + [ package compiler ? stage Stage0 ? append ["foo", "bar"] + , builder (Ghc Stage0) ? remove ["-O2"] + , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] + ] + From git at git.haskell.org Thu Oct 26 23:28:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement ModuleFiles oracle for caching the search of module files of a package. (cf825fe) Message-ID: <20171026232801.5E82E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf825feba28b287a8e3eee00eee543d4c5b5e8fe/ghc >--------------------------------------------------------------- commit cf825feba28b287a8e3eee00eee543d4c5b5e8fe Author: Andrey Mokhov Date: Wed Dec 23 06:14:11 2015 +0000 Implement ModuleFiles oracle for caching the search of module files of a package. >--------------------------------------------------------------- cf825feba28b287a8e3eee00eee543d4c5b5e8fe src/Oracles/ModuleFiles.hs | 96 ++++++++++++++++++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 7 ++-- src/Rules/Oracles.hs | 6 ++- src/Settings.hs | 55 +++++--------------------- 4 files changed, 113 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 cf825feba28b287a8e3eee00eee543d4c5b5e8fe From git at git.haskell.org Thu Oct 26 23:28:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to difference lists. (5b1c215) Message-ID: <20171026232804.E36DB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8/ghc >--------------------------------------------------------------- commit 5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8 Author: Andrey Mokhov Date: Sun Jun 14 01:19:19 2015 +0100 Switch to difference lists. >--------------------------------------------------------------- 5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8 src/Expression.hs | 73 ++++++++++++++++++++++++++++++++++-------- src/Expression/Settings.hs | 15 +++++---- src/Rules.hs | 15 ++++----- src/Rules/Data.hs | 76 ++++++++++++++++++++----------------------- src/Targets.hs | 80 +++++++++++++++++++--------------------------- 5 files changed, 142 insertions(+), 117 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 5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8 From git at git.haskell.org Thu Oct 26 23:28:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (a5a12ec) Message-ID: <20171026232805.53F7D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a12ec621ad8461cf80cf91fcbf583919358d70/ghc >--------------------------------------------------------------- commit a5a12ec621ad8461cf80cf91fcbf583919358d70 Author: Moritz Angermann Date: Wed Dec 23 14:59:44 2015 +0800 Update README.md Adding missing prerequisites. These are probably installed if you build ghc often or use shake, but if not, these are missing. >--------------------------------------------------------------- a5a12ec621ad8461cf80cf91fcbf583919358d70 README.md | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/README.md b/README.md index 5d87bc4..05e247e 100644 --- a/README.md +++ b/README.md @@ -8,6 +8,12 @@ This is supposed to go into the `shake-build` directory of the GHC source tree. Trying it --------- +Prerequisits +``` +$ cabal install alex +$ cabal install shake +``` + On Linux, ``` $ git clone git://git.haskell.org/ghc From git at git.haskell.org Thu Oct 26 23:28:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add userPackages for overriding default targetPackages. (5d6c2d7) Message-ID: <20171026232808.7FE873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d6c2d7a48d85f2af6f341ee14bc86de400b4779/ghc >--------------------------------------------------------------- commit 5d6c2d7a48d85f2af6f341ee14bc86de400b4779 Author: Andrey Mokhov Date: Sun Jun 14 14:50:48 2015 +0100 Add userPackages for overriding default targetPackages. >--------------------------------------------------------------- 5d6c2d7a48d85f2af6f341ee14bc86de400b4779 src/Expression.hs | 5 ++++- src/Rules.hs | 2 +- src/UserSettings.hs | 9 ++++++--- 3 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index ac72891..77be4e9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -6,7 +6,7 @@ module Expression ( Ways, Packages, Environment (..), defaultEnvironment, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, - interpret, + interpret, interpretDiff, applyPredicate, (?), (??), stage, notStage, builder, notBuilder, package, configKeyValue, configKeyValues, configKeyYes, configKeyNo, configKeyNonEmpty @@ -89,6 +89,9 @@ interpret = flip runReaderT fromDiff :: Monoid a => DiffExpr a -> Expr a fromDiff = fmap (($ mempty) . appEndo) +interpretDiff :: Environment -> Expr a -> Action a +interpretDiff env = interpret env . fromDiff + applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate diff --git a/src/Rules.hs b/src/Rules.hs index 50fa5e1..2873abf 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -18,7 +18,7 @@ generateTargets :: Rules () generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do let env = defaultEnvironment { getStage = stage } - pkgs <- interpret env $ fromDiff targetPackages + pkgs <- interpretDiff env $ targetPackages <> userPackages forM_ pkgs $ \pkg -> do let dir = targetDirectory stage pkg need [pkgPath pkg dir "package-data.mk"] diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 0a37159..1615d60 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -1,5 +1,5 @@ module UserSettings ( - userSettings + userSettings, userPackages ) where import Base hiding (arg, args, Args) @@ -12,6 +12,9 @@ userSettings :: Settings userSettings = mconcat [ package compiler ? stage Stage0 ? append ["foo", "bar"] , builder (Ghc Stage0) ? remove ["-O2"] - , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] - ] + , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] +userPackages :: Settings +userPackages = mconcat + [ stage Stage1 ? remove [cabal] + , remove [compiler] ] From git at git.haskell.org Thu Oct 26 23:28:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #25 from angerman/patch-1 (0153864) Message-ID: <20171026232808.DCEFD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0153864864ac88a314b3fbfb4e681e0ea6ab1451/ghc >--------------------------------------------------------------- commit 0153864864ac88a314b3fbfb4e681e0ea6ab1451 Merge: cf825fe a5a12ec Author: Andrey Mokhov Date: Wed Dec 23 11:26:34 2015 +0000 Merge pull request #25 from angerman/patch-1 Update README.md >--------------------------------------------------------------- 0153864864ac88a314b3fbfb4e681e0ea6ab1451 README.md | 6 ++++++ 1 file changed, 6 insertions(+) From git at git.haskell.org Thu Oct 26 23:28:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add userPackages for overriding default list of target packages. (f500bd1) Message-ID: <20171026232812.425983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f500bd171e7d5ca2416876b5477b59fa89e7762e/ghc >--------------------------------------------------------------- commit f500bd171e7d5ca2416876b5477b59fa89e7762e Author: Andrey Mokhov Date: Sun Jun 14 15:02:09 2015 +0100 Add userPackages for overriding default list of target packages. >--------------------------------------------------------------- f500bd171e7d5ca2416876b5477b59fa89e7762e src/Expression.hs | 2 +- src/Rules.hs | 1 + src/Targets.hs | 8 ++++---- src/UserSettings.hs | 4 ++-- 4 files changed, 8 insertions(+), 7 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 77be4e9..ec76244 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -89,7 +89,7 @@ interpret = flip runReaderT fromDiff :: Monoid a => DiffExpr a -> Expr a fromDiff = fmap (($ mempty) . appEndo) -interpretDiff :: Environment -> Expr a -> Action a +interpretDiff :: Monoid a => Environment -> DiffExpr a -> Action a interpretDiff env = interpret env . fromDiff applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a diff --git a/src/Rules.hs b/src/Rules.hs index 2873abf..227eef1 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -10,6 +10,7 @@ import Targets import Settings import Package import Expression +import UserSettings import Rules.Package -- generateTargets needs package-data.mk files of all target packages diff --git a/src/Targets.hs b/src/Targets.hs index 186a321..5929eb8 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -1,10 +1,10 @@ module Targets ( targetWays, targetPackages, targetDirectory, allPackages, customConfigureSettings, - array, base, binPackageDb, binary, bytestring, cabal, containers, deepseq, - directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerLibrary, - parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, - transformers, unix, win32, xhtml + array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, + deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, + integerLibrary, parallel, pretty, primitive, process, stm, templateHaskell, + terminfo, time, transformers, unix, win32, xhtml ) where import Ways hiding (parallel) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 1615d60..b785c7f 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,8 +3,8 @@ module UserSettings ( ) where import Base hiding (arg, args, Args) -import Rules.Data import Oracles.Builder +import Targets import Expression import Expression.Settings @@ -14,7 +14,7 @@ userSettings = mconcat , builder (Ghc Stage0) ? remove ["-O2"] , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] -userPackages :: Settings +userPackages :: Packages userPackages = mconcat [ stage Stage1 ? remove [cabal] , remove [compiler] ] From git at git.haskell.org Thu Oct 26 23:28:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create LICENSE (d12e733) Message-ID: <20171026232812.A6B873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d12e733ba6fd831157ee436dbfac6e9f2aa8579a/ghc >--------------------------------------------------------------- commit d12e733ba6fd831157ee436dbfac6e9f2aa8579a Author: Andrey Mokhov Date: Wed Dec 23 12:42:57 2015 +0000 Create LICENSE >--------------------------------------------------------------- d12e733ba6fd831157ee436dbfac6e9f2aa8579a LICENSE | 27 +++++++++++++++++++++++++++ 1 file changed, 27 insertions(+) diff --git a/LICENSE b/LICENSE new file mode 100644 index 0000000..20d201e --- /dev/null +++ b/LICENSE @@ -0,0 +1,27 @@ +Copyright (c) 2015, Andrey Mokhov +All rights reserved. + +Redistribution and use in source and binary forms, with or without +modification, are permitted provided that the following conditions are met: + +* Redistributions of source code must retain the above copyright notice, this + list of conditions and the following disclaimer. + +* Redistributions in binary form must reproduce the above copyright notice, + this list of conditions and the following disclaimer in the documentation + and/or other materials provided with the distribution. + +* Neither the name of shaking-up-ghc nor the names of its + contributors may be used to endorse or promote products derived from + this software without specific prior written permission. + +THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" +AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE +DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE +FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. From git at git.haskell.org Thu Oct 26 23:28:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add userWays and make sure all user-specific settings are used. (a1dd39f) Message-ID: <20171026232816.13D263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1dd39f2b8f32948de4c219a866712dc2eb7884b/ghc >--------------------------------------------------------------- commit a1dd39f2b8f32948de4c219a866712dc2eb7884b Author: Andrey Mokhov Date: Sun Jun 14 15:17:20 2015 +0100 Add userWays and make sure all user-specific settings are used. >--------------------------------------------------------------- a1dd39f2b8f32948de4c219a866712dc2eb7884b src/Rules.hs | 2 +- src/Settings.hs | 6 +++--- src/UserSettings.hs | 23 +++++++++++++++++++---- 3 files changed, 23 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 227eef1..bb68b47 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -31,4 +31,4 @@ packageRules = forM_ [Stage0, Stage1] $ \stage -> do forM_ allPackages $ \pkg -> do let env = defaultEnvironment { getStage = stage, getPackage = pkg } - buildPackage env targetWays buildSettings + buildPackage env (targetWays <> userWays) (settings <> userSettings) diff --git a/src/Settings.hs b/src/Settings.hs index 539ed48..41b31ba 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,7 +1,7 @@ {-# LANGUAGE NoImplicitPrelude, FlexibleInstances #-} module Settings ( - buildSettings + settings ) where import Base hiding (arg, args, Args) @@ -10,8 +10,8 @@ import Oracles.Builder import Expression import Expression.Settings -buildSettings :: Settings -buildSettings = do +settings :: Settings +settings = do stage <- asks getStage mconcat [ builder GhcCabal ? cabalSettings , builder (GhcPkg stage) ? ghcPkgSettings ] diff --git a/src/UserSettings.hs b/src/UserSettings.hs index b785c7f..ccc03f5 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -1,20 +1,35 @@ module UserSettings ( - userSettings, userPackages + userSettings, userPackages, userWays ) where import Base hiding (arg, args, Args) import Oracles.Builder +import Ways import Targets import Expression import Expression.Settings +-- No user-specific settings by default userSettings :: Settings -userSettings = mconcat +userSettings = mempty + +userPackages :: Packages +userPackages = mempty + +userWays :: Ways +userWays = mempty + +-- Examples: +userSettings' :: Settings +userSettings' = mconcat [ package compiler ? stage Stage0 ? append ["foo", "bar"] , builder (Ghc Stage0) ? remove ["-O2"] , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] -userPackages :: Packages -userPackages = mconcat +userPackages' :: Packages +userPackages' = mconcat [ stage Stage1 ? remove [cabal] , remove [compiler] ] + +userWays' :: Ways +userWays' = remove [profiling] From git at git.haskell.org Thu Oct 26 23:28:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename "shaking-up-ghc" to "Shaking up GHC" (02dfa6d) Message-ID: <20171026232816.8A15E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02dfa6dc8e89cf450baf01b4541ab33bbaffebda/ghc >--------------------------------------------------------------- commit 02dfa6dc8e89cf450baf01b4541ab33bbaffebda Author: Andrey Mokhov Date: Wed Dec 23 13:11:40 2015 +0000 Rename "shaking-up-ghc" to "Shaking up GHC" >--------------------------------------------------------------- 02dfa6dc8e89cf450baf01b4541ab33bbaffebda LICENSE | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/LICENSE b/LICENSE index 20d201e..a78df02 100644 --- a/LICENSE +++ b/LICENSE @@ -11,7 +11,7 @@ modification, are permitted provided that the following conditions are met: this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. -* Neither the name of shaking-up-ghc nor the names of its +* Neither the name of Shaking up GHC nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. From git at git.haskell.org Thu Oct 26 23:28:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix ordering of appends. (95b6614) Message-ID: <20171026232819.7D7BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95b6614a659907ec33afce9bca396a7f7d20a498/ghc >--------------------------------------------------------------- commit 95b6614a659907ec33afce9bca396a7f7d20a498 Author: Andrey Mokhov Date: Sun Jun 14 15:39:21 2015 +0100 Fix ordering of appends. >--------------------------------------------------------------- 95b6614a659907ec33afce9bca396a7f7d20a498 src/Expression.hs | 2 +- src/Rules/Data.hs | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index ec76244..8ae285d 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -45,7 +45,7 @@ instance Monoid a => Monoid (Expr a) where mappend = liftM2 mappend append :: Monoid a => a -> DiffExpr a -append x = return $ Endo (<> x) +append = return . Endo . mappend appendM :: Monoid a => Action a -> DiffExpr a appendM mx = lift mx >>= append diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index c8cb354..4c7e5de 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -148,9 +148,9 @@ buildPackageData env ways settings = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" - need [pkgPath pkg pkgCabal pkg] -- GhcCabal will run the configure script, so we depend on it - -- We still don't know who build the configure script from configure.ac + need [pkgPath pkg pkgCabal pkg] + -- We still don't know who built the configure script from configure.ac when (doesFileExist $ configure <.> "ac") $ need [configure] run' env GhcCabal settings -- TODO: when (registerPackage settings) $ From git at git.haskell.org Thu Oct 26 23:28:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make PackageName into a proper newtype (7e65227) Message-ID: <20171026232820.0E2383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e6522794e13767080c1add1e304fce960f0e1cd/ghc >--------------------------------------------------------------- commit 7e6522794e13767080c1add1e304fce960f0e1cd Author: Ben Gamari Date: Fri Dec 18 18:05:20 2015 +0100 Make PackageName into a proper newtype >--------------------------------------------------------------- 7e6522794e13767080c1add1e304fce960f0e1cd src/GHC.hs | 7 ++++--- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Package.hs | 30 +++++++++++++++++++++--------- src/Rules/Cabal.hs | 12 ++++++------ src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 4 ++-- src/Settings/TargetDirectory.hs | 3 ++- 11 files changed, 42 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 7e6522794e13767080c1add1e304fce960f0e1cd From git at git.haskell.org Thu Oct 26 23:28:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant argument to build rules. (3461e46) Message-ID: <20171026232823.1B0343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3461e46ca8f34eebe63f32a5dc76a6afdcb6f294/ghc >--------------------------------------------------------------- commit 3461e46ca8f34eebe63f32a5dc76a6afdcb6f294 Author: Andrey Mokhov Date: Sun Jun 14 16:03:07 2015 +0100 Remove redundant argument to build rules. >--------------------------------------------------------------- 3461e46ca8f34eebe63f32a5dc76a6afdcb6f294 src/Rules.hs | 5 +- src/Rules/Data.hs | 132 +++------------------------------------------- src/Rules/Package.hs | 3 +- src/Settings.hs | 144 +++++++++++++++++++++++++++++++++++++++++++++++++-- src/Targets.hs | 3 +- 5 files changed, 151 insertions(+), 136 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3461e46ca8f34eebe63f32a5dc76a6afdcb6f294 From git at git.haskell.org Thu Oct 26 23:28:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Parallelize+optimize compilation of build system (-j -O) (bfd3d32) Message-ID: <20171026232823.96D953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bfd3d3240107fe70cc0ca806aafab1398c9e25ee/ghc >--------------------------------------------------------------- commit bfd3d3240107fe70cc0ca806aafab1398c9e25ee Author: David Luposchainsky Date: Tue Dec 22 08:54:35 2015 +0100 Parallelize+optimize compilation of build system (-j -O) >--------------------------------------------------------------- bfd3d3240107fe70cc0ca806aafab1398c9e25ee build.sh | 1 + 1 file changed, 1 insertion(+) diff --git a/build.sh b/build.sh index 1918cdd..f09c30c 100755 --- a/build.sh +++ b/build.sh @@ -13,6 +13,7 @@ ghc \ -rtsopts \ -with-rtsopts=-I0 \ -outputdir="$root/.shake" \ + -j -O \ -o "$root/.shake/build" "$root/.shake/build" \ From git at git.haskell.org Thu Oct 26 23:28:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor folder structure. (2f70955) Message-ID: <20171026232826.A4A143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f70955b45d2c0e4dad2fd8a606caca094bd7c5c/ghc >--------------------------------------------------------------- commit 2f70955b45d2c0e4dad2fd8a606caca094bd7c5c Author: Andrey Mokhov Date: Sun Jun 14 16:10:48 2015 +0100 Refactor folder structure. >--------------------------------------------------------------- 2f70955b45d2c0e4dad2fd8a606caca094bd7c5c src/Expression.hs | 8 +++++--- src/Settings.hs | 2 +- src/{Expression/Settings.hs => Settings/Util.hs} | 6 +----- src/Targets.hs | 1 - src/UserSettings.hs | 1 - 5 files changed, 7 insertions(+), 11 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 8ae285d..7adbce0 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -3,7 +3,7 @@ module Expression ( module Control.Monad.Reader, Expr, DiffExpr, fromDiff, Predicate, - Ways, Packages, + Settings, Ways, Packages, Environment (..), defaultEnvironment, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, interpret, interpretDiff, @@ -37,8 +37,10 @@ type Expr a = ReaderT Environment Action a type DiffExpr a = Expr (Endo a) type Predicate = Expr Bool -type Ways = DiffExpr [Way] -type Packages = DiffExpr [Package] + +type Settings = DiffExpr [String] +type Ways = DiffExpr [Way] +type Packages = DiffExpr [Package] instance Monoid a => Monoid (Expr a) where mempty = return mempty diff --git a/src/Settings.hs b/src/Settings.hs index ebafbc2..95b88b5 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -14,9 +14,9 @@ import Targets import Package import Switches import Oracles.Base +import Settings.Util import UserSettings import Expression hiding (when, liftIO) -import Expression.Settings settings :: Settings settings = defaultSettings <> userSettings diff --git a/src/Expression/Settings.hs b/src/Settings/Util.hs similarity index 97% rename from src/Expression/Settings.hs rename to src/Settings/Util.hs index 5bc185b..dbd07c0 100644 --- a/src/Expression/Settings.hs +++ b/src/Settings/Util.hs @@ -1,8 +1,6 @@ {-# LANGUAGE NoImplicitPrelude #-} -module Expression.Settings ( - Settings, - +module Settings.Util ( -- Primitive settings elements arg, argM, args, argConfig, argStagedConfig, argConfigList, argStagedConfigList, @@ -18,8 +16,6 @@ import Base hiding (Args, arg, args) import Oracles hiding (not) import Expression -type Settings = DiffExpr [String] - -- A single argument arg :: String -> Settings arg = append . return diff --git a/src/Targets.hs b/src/Targets.hs index b2b52d3..4d3c613 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -13,7 +13,6 @@ import Base hiding (arg, args, Args, TargetDir) import Package import Switches import Expression -import Expression.Settings -- These are the packages we build targetPackages :: Packages diff --git a/src/UserSettings.hs b/src/UserSettings.hs index ccc03f5..4928661 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -7,7 +7,6 @@ import Oracles.Builder import Ways import Targets import Expression -import Expression.Settings -- No user-specific settings by default userSettings :: Settings From git at git.haskell.org Thu Oct 26 23:28:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid common shell scripting pitfalls (828bc3a) Message-ID: <20171026232827.1D4673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/828bc3a27a26a02e1bad68ef0c25d7d3a1ce64fd/ghc >--------------------------------------------------------------- commit 828bc3a27a26a02e1bad68ef0c25d7d3a1ce64fd Author: David Luposchainsky Date: Mon Dec 21 13:46:03 2015 +0100 Avoid common shell scripting pitfalls - Get bash from $PATH instead of reading it from /bin/bash (useful for e.g. NixOS) - set -euo pipefail: "strict bash mode" - Quote all paths to be whitespace compatible - GHC uses --make mode automatically >--------------------------------------------------------------- 828bc3a27a26a02e1bad68ef0c25d7d3a1ce64fd build.sh | 26 +++++++++++++++++++++----- 1 file changed, 21 insertions(+), 5 deletions(-) diff --git a/build.sh b/build.sh index d350779..1918cdd 100755 --- a/build.sh +++ b/build.sh @@ -1,6 +1,22 @@ -#!/bin/bash -e +#!/usr/bin/env bash -root=`dirname $0` -mkdir -p $root/.shake -ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/.shake -o $root/.shake/build -$root/.shake/build --lint --directory $root/.. $@ +set -euo pipefail + +root="$(dirname "$0")" + +mkdir -p "$root/.shake" + +ghc \ + "$root/src/Main.hs" \ + -Wall \ + -i"$root/src" \ + -rtsopts \ + -with-rtsopts=-I0 \ + -outputdir="$root/.shake" \ + -o "$root/.shake/build" + +"$root/.shake/build" \ + --lint \ + --directory "$root/.." \ + --colour \ + "$@" From git at git.haskell.org Thu Oct 26 23:28:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split Targets.hs and Settings.hs into multiple logically separate files. (062952c) Message-ID: <20171026232830.2DFD43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/062952ca22b4c06d96cc0ad601ae3437ea6883dc/ghc >--------------------------------------------------------------- commit 062952ca22b4c06d96cc0ad601ae3437ea6883dc Author: Andrey Mokhov Date: Sun Jun 14 18:03:20 2015 +0100 Split Targets.hs and Settings.hs into multiple logically separate files. >--------------------------------------------------------------- 062952ca22b4c06d96cc0ad601ae3437ea6883dc src/Expression.hs | 2 + src/Rules.hs | 4 +- src/Rules/Data.hs | 2 + src/Settings.hs | 140 +----------------------------- src/{Settings.hs => Settings/GhcCabal.hs} | 89 +++++++------------ src/Settings/GhcPkg.hs | 20 +++++ src/Settings/Packages.hs | 33 +++++++ src/Settings/Ways.hs | 20 +++++ src/Targets.hs | 45 +++------- 9 files changed, 124 insertions(+), 231 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 062952ca22b4c06d96cc0ad601ae3437ea6883dc From git at git.haskell.org Thu Oct 26 23:28:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Show simple shake progress and timings (0e19611) Message-ID: <20171026232830.BD72A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0e196114ceb61cfb03e24216203f868a10d294b9/ghc >--------------------------------------------------------------- commit 0e196114ceb61cfb03e24216203f868a10d294b9 Author: David Luposchainsky Date: Mon Dec 21 14:15:16 2015 +0100 Show simple shake progress and timings >--------------------------------------------------------------- 0e196114ceb61cfb03e24216203f868a10d294b9 src/Main.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index aae1d5e..7a0205d 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -5,9 +5,14 @@ import Rules.Config import Rules.Oracles main :: IO () -main = shakeArgs shakeOptions { shakeFiles = shakeFilesPath } $ do +main = shakeArgs options $ do generateTargets -- see Rules packageRules -- see Rules cabalRules -- see Rules.Cabal configRules -- see Rules.Config oracleRules -- see Rules.Oracles + where + options = shakeOptions + { shakeFiles = shakeFilesPath + , shakeProgress = progressSimple + , shakeTimings = True } From git at git.haskell.org Thu Oct 26 23:28:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move derived predicates around. (2bd0715) Message-ID: <20171026232833.D540A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2bd0715aa24e153e43707deaa6ef8ca6386105ab/ghc >--------------------------------------------------------------- commit 2bd0715aa24e153e43707deaa6ef8ca6386105ab Author: Andrey Mokhov Date: Sun Jun 14 19:44:05 2015 +0100 Move derived predicates around. >--------------------------------------------------------------- 2bd0715aa24e153e43707deaa6ef8ca6386105ab src/Expression.hs | 8 +------- src/Settings/GhcCabal.hs | 13 +++++++------ src/Settings/GhcPkg.hs | 7 ++++--- src/Settings/Packages.hs | 4 ++-- src/Switches.hs | 27 +++++++++++++++++++-------- src/Targets.hs | 4 +++- src/UserSettings.hs | 20 +++++++++++++++----- 7 files changed, 51 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2bd0715aa24e153e43707deaa6ef8ca6386105ab From git at git.haskell.org Thu Oct 26 23:28:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #17 from bgamari/types (3783b0d) Message-ID: <20171026232834.532493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3783b0d0eab89fdbc0b6ec4dd2ba78423fc79dc1/ghc >--------------------------------------------------------------- commit 3783b0d0eab89fdbc0b6ec4dd2ba78423fc79dc1 Merge: 02dfa6d 7e65227 Author: Andrey Mokhov Date: Wed Dec 23 20:06:00 2015 +0000 Merge pull request #17 from bgamari/types [WIP] Make better use of types >--------------------------------------------------------------- 3783b0d0eab89fdbc0b6ec4dd2ba78423fc79dc1 src/GHC.hs | 7 ++++--- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Package.hs | 30 +++++++++++++++++++++--------- src/Rules/Cabal.hs | 12 ++++++------ src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 4 ++-- src/Settings/TargetDirectory.hs | 3 ++- 11 files changed, 42 insertions(+), 28 deletions(-) From git at git.haskell.org Thu Oct 26 23:28:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix argument ordering issues in DiffExpr. (b67db18) Message-ID: <20171026232837.614F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b67db18e8f9745bd25045f0e09f64cbb5c5b09b5/ghc >--------------------------------------------------------------- commit b67db18e8f9745bd25045f0e09f64cbb5c5b09b5 Author: Andrey Mokhov Date: Sun Jun 14 20:33:13 2015 +0100 Fix argument ordering issues in DiffExpr. >--------------------------------------------------------------- b67db18e8f9745bd25045f0e09f64cbb5c5b09b5 src/Expression.hs | 29 +++++++++++++++-------------- 1 file changed, 15 insertions(+), 14 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index a37bf7c..d147280 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -36,7 +36,7 @@ defaultEnvironment = Environment } type Expr a = ReaderT Environment Action a -type DiffExpr a = Expr (Endo a) +type DiffExpr a = Expr (Dual (Endo a)) type Predicate = Expr Bool @@ -49,49 +49,50 @@ instance Monoid a => Monoid (Expr a) where mappend = liftM2 mappend append :: Monoid a => a -> DiffExpr a -append = return . Endo . mappend +append x = return . Dual . Endo $ (<> x) appendM :: Monoid a => Action a -> DiffExpr a appendM mx = lift mx >>= append remove :: Eq a => [a] -> DiffExpr [a] -remove xs = return . Endo $ filter (`notElem` xs) +remove xs = return . Dual . Endo $ filter (`notElem` xs) -- appendSub appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument -- of the form 'prefix=listOfSubarguments' is appended to the expression. -- Note: nothing is done if the list of sub-arguments is empty. -appendSub :: String -> [String] -> DiffExpr [String] +appendSub :: String -> [String] -> Settings appendSub prefix xs - | xs == [] = mempty - | otherwise = return $ Endo (go False) + | xs' == [] = mempty + | otherwise = return . Dual . Endo $ go False where + xs' = filter (/= "") xs go True [] = [] - go False [] = [prefix ++ "=" ++ unwords xs] + go False [] = [prefix ++ "=" ++ unwords xs'] go found (y:ys) = if prefix `isPrefixOf` y - then unwords (y : xs) : go True ys - else go found ys + then unwords (y : xs') : go True ys + else y : go found ys -- appendSubD is similar to appendSub but it extracts the list of sub-arguments -- from the given DiffExpr. -appendSubD :: String -> DiffExpr [String] -> DiffExpr [String] +appendSubD :: String -> Settings -> Settings appendSubD prefix diffExpr = fromDiff diffExpr >>= appendSub prefix -filterSub :: String -> (String -> Bool) -> DiffExpr [String] -filterSub prefix p = return . Endo $ map filterSubstr +filterSub :: String -> (String -> Bool) -> Settings +filterSub prefix p = return . Dual . Endo $ map filterSubstr where filterSubstr s | prefix `isPrefixOf` s = unwords . filter p . words $ s | otherwise = s -removeSub :: String -> [String] -> DiffExpr [String] +removeSub :: String -> [String] -> Settings removeSub prefix xs = filterSub prefix (`notElem` xs) interpret :: Environment -> Expr a -> Action a interpret = flip runReaderT fromDiff :: Monoid a => DiffExpr a -> Expr a -fromDiff = fmap (($ mempty) . appEndo) +fromDiff = fmap (($ mempty) . appEndo . getDual) interpretDiff :: Monoid a => Environment -> DiffExpr a -> Action a interpretDiff env = interpret env . fromDiff From git at git.haskell.org Thu Oct 26 23:28:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #29 from quchen/script-refactoring (f354291) Message-ID: <20171026232837.C82F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f354291e941d1653bb8d3ae6825f588e82372b0a/ghc >--------------------------------------------------------------- commit f354291e941d1653bb8d3ae6825f588e82372b0a Merge: 3783b0d bfd3d32 Author: Andrey Mokhov Date: Wed Dec 23 20:14:46 2015 +0000 Merge pull request #29 from quchen/script-refactoring Show Shake statistics, refactor direct Linux build script >--------------------------------------------------------------- f354291e941d1653bb8d3ae6825f588e82372b0a build.sh | 27 ++++++++++++++++++++++----- src/Main.hs | 7 ++++++- 2 files changed, 28 insertions(+), 6 deletions(-) From git at git.haskell.org Thu Oct 26 23:28:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor settings predicates. (463094d) Message-ID: <20171026232840.CE72B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/463094da9933beec44729dd96ea47430a4e9f2a0/ghc >--------------------------------------------------------------- commit 463094da9933beec44729dd96ea47430a4e9f2a0 Author: Andrey Mokhov Date: Mon Jun 15 00:44:08 2015 +0100 Refactor settings predicates. >--------------------------------------------------------------- 463094da9933beec44729dd96ea47430a4e9f2a0 cfg/default.config.in | 1 - src/Settings.hs | 10 +++++----- src/Settings/GhcCabal.hs | 26 ++++++++++++++------------ src/Settings/GhcPkg.hs | 10 ++++++---- src/Targets.hs | 17 ++++++++--------- 5 files changed, 33 insertions(+), 31 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index 2e65688..f31af13 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -38,7 +38,6 @@ supports-package-key = @SUPPORTS_PACKAGE_KEY@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ -validating = NO ghc-source-path = @hardtop@ # Information about host and target systems: diff --git a/src/Settings.hs b/src/Settings.hs index a9f5cce..cde678e 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,8 +2,8 @@ module Settings ( settings ) where +import Targets import Base hiding (arg, args) -import Oracles.Builder import Settings.GhcPkg import Settings.GhcCabal import UserSettings @@ -13,7 +13,7 @@ settings :: Settings settings = defaultSettings <> userSettings defaultSettings :: Settings -defaultSettings = do - stage <- asks getStage - mconcat [ builder GhcCabal ? cabalSettings - , builder (GhcPkg stage) ? ghcPkgSettings ] +defaultSettings = mconcat + [ cabalSettings + , ghcPkgSettings + , customPackageSettings ] diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index d0f6512..db972ac 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -17,7 +17,7 @@ import Settings.Packages import UserSettings cabalSettings :: Settings -cabalSettings = do +cabalSettings = builder GhcCabal ? do stage <- asks getStage pkg <- asks getPackage mconcat [ arg "configure" @@ -26,7 +26,6 @@ cabalSettings = do , dllSettings , with' $ Ghc stage , with' $ GhcPkg stage - , customConfigureSettings , stage0 ? bootPackageDbSettings , librarySettings , configKeyNonEmpty "hscolour" ? with' HsColour -- TODO: generalise? @@ -59,14 +58,18 @@ librarySettings = do configureSettings :: Settings configureSettings = do - let conf key = appendSubD $ "--configure-option=" ++ key - ccSettings' = ccSettings <> remove ["-Werror"] + let conf key = appendSubD $ "--configure-option=" ++ key + cFlags = mconcat [ ccSettings + , remove ["-Werror"] + , argStagedConfig "conf-cc-args" ] + ldFlags = ldSettings <> argStagedConfig "conf-gcc-linker-args" + cppFlags = cppSettings <> argStagedConfig "conf-cpp-args" stage <- asks getStage mconcat - [ conf "CFLAGS" ccSettings' - , conf "LDFLAGS" ldSettings - , conf "CPPFLAGS" cppSettings - , appendSubD "--gcc-options" $ ccSettings' <> ldSettings + [ conf "CFLAGS" cFlags + , conf "LDFLAGS" ldFlags + , conf "CPPFLAGS" cppFlags + , appendSubD "--gcc-options" $ cFlags <> ldFlags , conf "--with-iconv-includes" $ argConfig "iconv-include-dirs" , conf "--with-iconv-libraries" $ argConfig "iconv-lib-dirs" , conf "--with-gmp-includes" $ argConfig "gmp-include-dirs" @@ -106,9 +109,8 @@ ccSettings = do let gccGe46 = liftM not gccLt46 mconcat [ package integerLibrary ? arg "-Ilibraries/integer-gmp2/gmp" - , builder GhcCabal ? argStagedConfig "conf-cc-args" , validating ? mconcat - [ notBuilder GhcCabal ? arg "-Werror" + [ arg "-Werror" , arg "-Wall" , gccIsClang ?? ( arg "-Wno-unknown-pragmas" <> @@ -117,7 +119,7 @@ ccSettings = do ] ldSettings :: Settings -ldSettings = builder GhcCabal ? argStagedConfig "conf-gcc-linker-args" +ldSettings = mempty cppSettings :: Settings -cppSettings = builder GhcCabal ? argStagedConfig "conf-cpp-args" +cppSettings = mempty diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index b3ba6f9..0e17b02 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -8,6 +8,7 @@ import Targets import Switches import Expression hiding (when, liftIO) import Settings.Util +import Oracles.Builder import Settings.GhcCabal ghcPkgSettings :: Settings @@ -15,7 +16,8 @@ ghcPkgSettings = do pkg <- asks getPackage stage <- asks getStage let dir = pkgPath pkg targetDirectory stage pkg - mconcat [ arg "update" - , arg "--force" - , stage0 ? bootPackageDbSettings - , arg $ dir "inplace-pkg-config" ] + builder (GhcPkg stage) ? mconcat + [ arg "update" + , arg "--force" + , stage0 ? bootPackageDbSettings + , arg $ dir "inplace-pkg-config" ] diff --git a/src/Targets.hs b/src/Targets.hs index 5218909..c8aeb22 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -1,7 +1,7 @@ module Targets ( targetDirectory, knownPackages, - customConfigureSettings, + customPackageSettings, array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerLibrary, parallel, pretty, primitive, process, stm, templateHaskell, @@ -12,6 +12,7 @@ import Base hiding (arg, args) import Package import Switches import Expression +import Oracles.Builder -- Build results will be placed into a target directory with the following -- typical structure: @@ -79,15 +80,13 @@ integerLibraryCabal = case integerLibraryImpl of IntegerGmp2 -> "integer-gmp.cabal" -- Indeed, why make life easier? IntegerSimple -> "integer-simple.cabal" --- Custom configure settings for packages --- TODO: check if '--flag' and '--flags' should be collections of --- sub-arguments or not. -customConfigureSettings :: Settings -customConfigureSettings = mconcat +-- Custom package settings for packages +customPackageSettings :: Settings +customPackageSettings = builder GhcCabal ? mconcat [ package integerLibrary ? - windowsHost ? appendSub "--configure-option" ["--with-intree-gmp"] - , package base ? appendSub "--flags" [integerLibraryName] - , package ghcPrim ? appendSub "--flag" ["include-ghc-prim"] ] + windowsHost ? append ["--configure-option=--with-intree-gmp"] + , package base ? append ["--flags=" ++ integerLibraryName] + , package ghcPrim ? append ["--flag=include-ghc-prim"] ] -- Note [Cabal name weirdness] -- Find out if we can move the contents to just Cabal/ From git at git.haskell.org Thu Oct 26 23:28:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix haddockArgs, clean up code. (1c8a0e7) Message-ID: <20171026232841.3CB963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c8a0e7aa5f3a11561bdb3b45426f319c83291a8/ghc >--------------------------------------------------------------- commit 1c8a0e7aa5f3a11561bdb3b45426f319c83291a8 Author: Andrey Mokhov Date: Thu Dec 24 01:28:50 2015 +0000 Fix haddockArgs, clean up code. >--------------------------------------------------------------- 1c8a0e7aa5f3a11561bdb3b45426f319c83291a8 src/Base.hs | 10 ++++++++-- src/Package.hs | 7 +++---- src/Rules/Cabal.hs | 3 +-- src/Settings/Builders/Haddock.hs | 4 +++- 4 files changed, 15 insertions(+), 9 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 79ce119..7730bf5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -26,7 +26,7 @@ module Base ( -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, removeFileIfExists, replaceEq, chunksOfSize, - replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-) + replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt ) where import Control.Applicative @@ -37,7 +37,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>), parallel) +import Development.Shake hiding (unit, (*>)) import Development.Shake.Classes import Development.Shake.Config import Development.Shake.FilePath @@ -77,6 +77,12 @@ replaceSeparators = replaceIf isPathSeparator replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) +-- | Given a version string such as "2.16.2" produce an integer equivalent +versionToInt :: String -> Int +versionToInt s = major * 1000 + minor * 10 + patch + where + [major, minor, patch] = map read . words $ replaceEq '.' ' ' s + -- | Given a module name extract the directory and file name, e.g.: -- -- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") diff --git a/src/Package.hs b/src/Package.hs index a956c6a..536a16f39 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,8 +1,7 @@ -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving, DeriveDataTypeable #-} module Package ( - Package (..), PackageName(..), PackageType (..), + Package (..), PackageName (..), PackageType (..), -- * Queries pkgNameString, pkgCabalFile, @@ -18,7 +17,7 @@ import Data.String -- | The name of a Cabal package newtype PackageName = PackageName { getPackageName :: String } deriving ( Eq, Ord, IsString, Generic, Binary, Hashable - , NFData) + , Typeable, NFData) instance Show PackageName where show (PackageName name) = name diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 74a2468..ce52388 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,13 +1,12 @@ module Rules.Cabal (cabalRules) where import Data.Version -import Distribution.Package as DP hiding (Package) +import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Verbosity import Expression import GHC -import Package hiding (library) import Settings cabalRules :: Rules () diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 4cc8683..0663d04 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -16,6 +16,7 @@ haddockArgs = builder Haddock ? do hidden <- getPkgDataList HiddenModules deps <- getPkgDataList Deps depNames <- getPkgDataList DepNames + hVersion <- lift . pkgData . Version $ targetPath Stage2 haddock ghcOpts <- fromDiffExpr commonGhcArgs mconcat [ arg $ "--odir=" ++ takeDirectory output @@ -26,6 +27,7 @@ haddockArgs = builder Haddock ? do , arg "--hoogle" , arg $ "--title=" ++ pkgNameString pkg ++ "-" ++ version ++ ": " ++ synopsis , arg $ "--prologue=" ++ path -/- "haddock-prologue.txt" + , arg $ "--optghc=-D__HADDOCK_VERSION__=" ++ show (versionToInt hVersion) , append $ map ("--hide=" ++) hidden , append $ [ "--read-interface=../" ++ dep ++ ",../" ++ dep ++ "/src/%{MODULE/./-}.html\\#%{NAME}," @@ -40,7 +42,7 @@ haddockArgs = builder Haddock ? do , customPackageArgs , append =<< getInputs , arg "+RTS" - , arg $ "-t" ++ path "haddock.t" + , arg $ "-t" ++ path -/- "haddock.t" , arg "--machine-readable" ] customPackageArgs :: Args From git at git.haskell.org Thu Oct 26 23:28:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement appendCcArgs abstraction for passing arguments both to Gcc and GhcCabal. (ac4dab0) Message-ID: <20171026232844.4D6993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ac4dab040a3eaeae26ed20198fce5fa00b0dda30/ghc >--------------------------------------------------------------- commit ac4dab040a3eaeae26ed20198fce5fa00b0dda30 Author: Andrey Mokhov Date: Mon Jun 15 01:47:05 2015 +0100 Implement appendCcArgs abstraction for passing arguments both to Gcc and GhcCabal. >--------------------------------------------------------------- ac4dab040a3eaeae26ed20198fce5fa00b0dda30 src/Settings/GhcCabal.hs | 12 +++++------- src/Settings/Util.hs | 8 ++++++++ src/Switches.hs | 5 ++++- src/Targets.hs | 16 +++++++++++----- 4 files changed, 28 insertions(+), 13 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index db972ac..21ca0e0 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -58,13 +58,13 @@ librarySettings = do configureSettings :: Settings configureSettings = do + stage <- asks getStage let conf key = appendSubD $ "--configure-option=" ++ key cFlags = mconcat [ ccSettings , remove ["-Werror"] , argStagedConfig "conf-cc-args" ] ldFlags = ldSettings <> argStagedConfig "conf-gcc-linker-args" cppFlags = cppSettings <> argStagedConfig "conf-cpp-args" - stage <- asks getStage mconcat [ conf "CFLAGS" cFlags , conf "LDFLAGS" ldFlags @@ -86,6 +86,7 @@ bootPackageDbSettings = do dllSettings :: Settings dllSettings = arg "" +-- TODO: remove with' :: Builder -> Settings with' builder = appendM $ with builder @@ -104,19 +105,16 @@ packageConstraints = do ++ cabal ++ "'." args $ concatMap (\c -> ["--constraint", c]) $ constraints +-- TODO: remove ccSettings :: Settings -ccSettings = do +ccSettings = validating ? do let gccGe46 = liftM not gccLt46 - mconcat - [ package integerLibrary ? arg "-Ilibraries/integer-gmp2/gmp" - , validating ? mconcat - [ arg "-Werror" + mconcat [ arg "-Werror" , arg "-Wall" , gccIsClang ?? ( arg "-Wno-unknown-pragmas" <> gccGe46 ? windowsHost ? arg "-Werror=unused-but-set-variable" , gccGe46 ? arg "-Wno-error=inline" )] - ] ldSettings :: Settings ldSettings = mempty diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index dbd07c0..f73f0f7 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -4,6 +4,7 @@ module Settings.Util ( -- Primitive settings elements arg, argM, args, argConfig, argStagedConfig, argConfigList, argStagedConfigList, + appendCcArgs, -- argBuilderPath, argStagedBuilderPath, -- argPackageKey, argPackageDeps, argPackageDepKeys, argSrcDirs, -- argIncludeDirs, argDepIncludeDirs, @@ -46,6 +47,13 @@ argStagedConfigList key = do stage <- asks getStage argConfigList (stagedKey stage key) +appendCcArgs :: [String] -> Settings +appendCcArgs args = do + stage <- asks getStage + mconcat [ builder (Gcc stage) ? append args + , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args + , builder GhcCabal ? appendSub "--gcc-options" args ] + -- packageData :: Arity -> String -> Settings -- packageData arity key = -- return $ EnvironmentParameter $ PackageData arity key Nothing Nothing diff --git a/src/Switches.hs b/src/Switches.hs index b67d9fc..0433682 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,6 +1,6 @@ module Switches ( IntegerLibraryImpl (..), integerLibraryImpl, - notStage, stage0, stage1, stage2, notBuilder, + notStage, stage0, stage1, stage2, builders, notBuilder, supportsPackageKey, targetPlatforms, targetPlatform, targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, @@ -31,6 +31,9 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 +builders :: [Builder] -> Predicate +builders = liftM or . sequence . map builder + notBuilder :: Builder -> Predicate notBuilder = liftM not . builder diff --git a/src/Targets.hs b/src/Targets.hs index c8aeb22..1839112 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -12,6 +12,7 @@ import Base hiding (arg, args) import Package import Switches import Expression +import Settings.Util import Oracles.Builder -- Build results will be placed into a target directory with the following @@ -80,13 +81,18 @@ integerLibraryCabal = case integerLibraryImpl of IntegerGmp2 -> "integer-gmp.cabal" -- Indeed, why make life easier? IntegerSimple -> "integer-simple.cabal" --- Custom package settings for packages customPackageSettings :: Settings -customPackageSettings = builder GhcCabal ? mconcat +customPackageSettings = mconcat [ package integerLibrary ? - windowsHost ? append ["--configure-option=--with-intree-gmp"] - , package base ? append ["--flags=" ++ integerLibraryName] - , package ghcPrim ? append ["--flag=include-ghc-prim"] ] + mconcat [ windowsHost ? builder GhcCabal ? + append ["--configure-option=--with-intree-gmp"] + , appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] ] + + , package base ? + builder GhcCabal ? append ["--flags=" ++ integerLibraryName] + + , package ghcPrim ? + builder GhcCabal ? append ["--flag=include-ghc-prim"] ] -- Note [Cabal name weirdness] -- Find out if we can move the contents to just Cabal/ From git at git.haskell.org Thu Oct 26 23:28:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (95d594c) Message-ID: <20171026232844.ADFB03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95d594c1836993c98fea985f475df4bbc959fa38/ghc >--------------------------------------------------------------- commit 95d594c1836993c98fea985f475df4bbc959fa38 Author: Andrey Mokhov Date: Thu Dec 24 02:51:44 2015 +0000 Clean up. >--------------------------------------------------------------- 95d594c1836993c98fea985f475df4bbc959fa38 src/Package.hs | 6 ++---- src/Settings/Packages.hs | 6 ++++-- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 536a16f39..9a64fa8 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -16,8 +16,7 @@ import Data.String -- | The name of a Cabal package newtype PackageName = PackageName { getPackageName :: String } - deriving ( Eq, Ord, IsString, Generic, Binary, Hashable - , Typeable, NFData) + deriving (Eq, Ord, IsString, Generic, Binary, Hashable, Typeable, NFData) instance Show PackageName where show (PackageName name) = name @@ -25,8 +24,7 @@ instance Show PackageName where -- | We regard packages as either being libraries or programs. This is -- bit of a convenient lie as Cabal packages can be both, but it works -- for now. -data PackageType = Program | Library - deriving Generic +data PackageType = Program | Library deriving Generic data Package = Package { diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index ee37b07..32d12a5 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -20,10 +20,10 @@ packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] + -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] --- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 @@ -35,7 +35,7 @@ packagesStage1 = mconcat , notM windowsHost ? append [iservBin] , buildHaddock ? append [xhtml] ] --- TODO: currently there is an unchecked assumption that we only build programs +-- TODO: currently there is an unchecked assumption that we build only programs -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages packagesStage2 = mconcat @@ -43,9 +43,11 @@ packagesStage2 = mconcat , buildHaddock ? append [haddock] ] -- TODO: switch to Set Package as the order of packages should not matter? +-- Otherwise we have to keep remembering to sort packages from time to time. knownPackages :: [Package] knownPackages = sort $ defaultKnownPackages ++ userKnownPackages -- Note: this is slow but we keep it simple as there are just ~50 packages +-- TODO: speed up? findKnownPackage :: PackageName -> Maybe Package findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Thu Oct 26 23:28:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused predicates notBuilder and builders. (af8520c) Message-ID: <20171026232848.04C5B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/af8520cecee4facafffe20a85da550cb06f32c58/ghc >--------------------------------------------------------------- commit af8520cecee4facafffe20a85da550cb06f32c58 Author: Andrey Mokhov Date: Mon Jun 15 10:48:54 2015 +0100 Drop unused predicates notBuilder and builders. >--------------------------------------------------------------- af8520cecee4facafffe20a85da550cb06f32c58 src/Settings/Util.hs | 4 ++-- src/Switches.hs | 9 +-------- 2 files changed, 3 insertions(+), 10 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index f73f0f7..dba49d5 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -51,8 +51,8 @@ appendCcArgs :: [String] -> Settings appendCcArgs args = do stage <- asks getStage mconcat [ builder (Gcc stage) ? append args - , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args - , builder GhcCabal ? appendSub "--gcc-options" args ] + , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args + , builder GhcCabal ? appendSub "--gcc-options" args ] -- packageData :: Arity -> String -> Settings -- packageData arity key = diff --git a/src/Switches.hs b/src/Switches.hs index 0433682..eada97c 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,6 +1,6 @@ module Switches ( IntegerLibraryImpl (..), integerLibraryImpl, - notStage, stage0, stage1, stage2, builders, notBuilder, + notStage, stage0, stage1, stage2, supportsPackageKey, targetPlatforms, targetPlatform, targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, @@ -9,7 +9,6 @@ module Switches ( ) where import Base -import Oracles.Builder import Expression -- Support for multiple integer library implementations @@ -31,12 +30,6 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 -builders :: [Builder] -> Predicate -builders = liftM or . sequence . map builder - -notBuilder :: Builder -> Predicate -notBuilder = liftM not . builder - -- Predicates based on configuration files supportsPackageKey :: Predicate supportsPackageKey = configKeyYes "supports-package-key" From git at git.haskell.org Thu Oct 26 23:28:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove runghcid.bat. (920b393) Message-ID: <20171026232848.5C30E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/920b3938e452548bdf1d9e24ef7e1971acb1c76e/ghc >--------------------------------------------------------------- commit 920b3938e452548bdf1d9e24ef7e1971acb1c76e Author: Andrey Mokhov Date: Thu Dec 24 03:28:07 2015 +0000 Remove runghcid.bat. >--------------------------------------------------------------- 920b3938e452548bdf1d9e24ef7e1971acb1c76e runghcid.bat | 1 - 1 file changed, 1 deletion(-) diff --git a/runghcid.bat b/runghcid.bat deleted file mode 100644 index f2f8ddc..0000000 --- a/runghcid.bat +++ /dev/null @@ -1 +0,0 @@ -ghcid --height=8 --topmost "--command=ghci -isrc -Wall src/Main.hs" From git at git.haskell.org Thu Oct 26 23:28:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, move derived predicates to Switches.hs. (7e62041) Message-ID: <20171026232851.9CBA03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e62041bd01856a4920e51028a2f3bbe161374c6/ghc >--------------------------------------------------------------- commit 7e62041bd01856a4920e51028a2f3bbe161374c6 Author: Andrey Mokhov Date: Tue Jun 16 00:00:19 2015 +0100 Add comments, move derived predicates to Switches.hs. >--------------------------------------------------------------- 7e62041bd01856a4920e51028a2f3bbe161374c6 src/Expression.hs | 54 ++++++++++++++++++++++++++++++------------------------ src/Switches.hs | 10 ++++++++++ 2 files changed, 40 insertions(+), 24 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index d147280..81ed26f 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -9,8 +9,7 @@ module Expression ( append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, interpret, interpretDiff, applyPredicate, (?), (??), stage, builder, package, - configKeyValue, configKeyValues, - configKeyYes, configKeyNo, configKeyNonEmpty + configKeyValue, configKeyValues ) where import Base hiding (arg, args, Args, TargetDir) @@ -25,8 +24,11 @@ data Environment = Environment getStage :: Stage, getBuilder :: Builder, getPackage :: Package + -- getWay :: Way, and maybe something else will be useful later } +-- TODO: all readers are currently partial functions. Can use type classes to +-- guarantee these errors never occur. defaultEnvironment :: Environment defaultEnvironment = Environment { @@ -48,15 +50,31 @@ instance Monoid a => Monoid (Expr a) where mempty = return mempty mappend = liftM2 mappend +-- Basic operations on expressions: +-- 1) append something to an expression append :: Monoid a => a -> DiffExpr a append x = return . Dual . Endo $ (<> x) -appendM :: Monoid a => Action a -> DiffExpr a -appendM mx = lift mx >>= append - +-- 2) remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] remove xs = return . Dual . Endo $ filter (`notElem` xs) +-- 3) apply a predicate to an expression +applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a +applyPredicate predicate expr = do + bool <- predicate + if bool then expr else return mempty + +-- A convenient operator for predicate application +(?) :: Monoid a => Predicate -> Expr a -> Expr a +(?) = applyPredicate + +infixr 8 ? + +-- A monadic version of append +appendM :: Monoid a => Action a -> DiffExpr a +appendM mx = lift mx >>= append + -- appendSub appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument -- of the form 'prefix=listOfSubarguments' is appended to the expression. @@ -85,31 +103,28 @@ filterSub prefix p = return . Dual . Endo $ map filterSubstr | prefix `isPrefixOf` s = unwords . filter p . words $ s | otherwise = s +-- remove given elements from a list of sub-arguments with a given prefix +-- Example: removeSub "--configure-option=CFLAGS" ["-Werror"] removeSub :: String -> [String] -> Settings removeSub prefix xs = filterSub prefix (`notElem` xs) +-- Interpret a given expression in a given environment interpret :: Environment -> Expr a -> Action a interpret = flip runReaderT +-- Extract an expression from a difference expression fromDiff :: Monoid a => DiffExpr a -> Expr a fromDiff = fmap (($ mempty) . appEndo . getDual) +-- Interpret a given difference expression in a given environment interpretDiff :: Monoid a => Environment -> DiffExpr a -> Action a interpretDiff env = interpret env . fromDiff -applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a -applyPredicate predicate expr = do - bool <- predicate - if bool then expr else return mempty - -(?) :: Monoid a => Predicate -> Expr a -> Expr a -(?) = applyPredicate - +-- An equivalent of if-then-else for predicates (??) :: Monoid a => Predicate -> (Expr a, Expr a) -> Expr a p ?? (t, f) = p ? t <> (liftM not p) ? f -infixr 8 ? - +-- Basic predicates stage :: Stage -> Predicate stage s = liftM (s ==) (asks getStage) @@ -125,12 +140,3 @@ configKeyValue key value = liftM (value ==) (lift $ askConfig key) -- checks if there is at least one match configKeyValues :: String -> [String] -> Predicate configKeyValues key values = liftM (`elem` values) (lift $ askConfig key) - -configKeyYes :: String -> Predicate -configKeyYes key = configKeyValue key "YES" - -configKeyNo :: String -> Predicate -configKeyNo key = configKeyValue key "NO" - -configKeyNonEmpty :: String -> Predicate -configKeyNonEmpty key = liftM not $ configKeyValue key "" diff --git a/src/Switches.hs b/src/Switches.hs index eada97c..5436d94 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,6 +1,7 @@ module Switches ( IntegerLibraryImpl (..), integerLibraryImpl, notStage, stage0, stage1, stage2, + configKeyYes, configKeyNo, configKeyNonEmpty, supportsPackageKey, targetPlatforms, targetPlatform, targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, @@ -30,6 +31,15 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 +configKeyYes :: String -> Predicate +configKeyYes key = configKeyValue key "YES" + +configKeyNo :: String -> Predicate +configKeyNo key = configKeyValue key "NO" + +configKeyNonEmpty :: String -> Predicate +configKeyNonEmpty key = liftM not $ configKeyValue key "" + -- Predicates based on configuration files supportsPackageKey :: Predicate supportsPackageKey = configKeyYes "supports-package-key" From git at git.haskell.org Thu Oct 26 23:28:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split the batch file into multiple lines, add missing flags (-j -O). (5bb30bc) Message-ID: <20171026232851.CEF6F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5bb30bc25f693652432ff72150a40ceb558f36e3/ghc >--------------------------------------------------------------- commit 5bb30bc25f693652432ff72150a40ceb558f36e3 Author: Andrey Mokhov Date: Thu Dec 24 03:29:32 2015 +0000 Split the batch file into multiple lines, add missing flags (-j -O). >--------------------------------------------------------------- 5bb30bc25f693652432ff72150a40ceb558f36e3 build.bat | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/build.bat b/build.bat index ab26e07..a4e2548 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,19 @@ @mkdir .shake 2> nul - at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=.shake -o .shake/build && .shake\build --lint --directory ".." %* + + at set ghcArgs=--make ^ + -Wall ^ + src/Main.hs ^ + -isrc ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=.shake ^ + -j ^ + -O ^ + -o .shake/build + + at set shakeArgs=--lint ^ + --directory ^ + ".." ^ + %* + + at ghc %ghcArgs% && .shake\build %shakeArgs% From git at git.haskell.org Thu Oct 26 23:28:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an agenda for the meeting on 16 June 2015. (8f6fe55) Message-ID: <20171026232855.04EFE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f6fe558bf383f83f8cc8aa1d1e1858c25c06765/ghc >--------------------------------------------------------------- commit 8f6fe558bf383f83f8cc8aa1d1e1858c25c06765 Author: Andrey Mokhov Date: Tue Jun 16 01:08:05 2015 +0100 Add an agenda for the meeting on 16 June 2015. >--------------------------------------------------------------- 8f6fe558bf383f83f8cc8aa1d1e1858c25c06765 doc/meeting-16-June-2015.txt | 83 ++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 83 insertions(+) diff --git a/doc/meeting-16-June-2015.txt b/doc/meeting-16-June-2015.txt new file mode 100644 index 0000000..a407bb9 --- /dev/null +++ b/doc/meeting-16-June-2015.txt @@ -0,0 +1,83 @@ +Shaking up GHC (3rd shake) meeting, 16 June 2015 + +Things to discuss: +================================================ + +1. Parameters of the build system that are still not user configurable: + +* targetDirectory (Targets.hs) -- is this important? Can be moved to +UserSettings.hs, but will clutter it (what is the good balance of +what we expose to users?). Can be made into a conditional expression +similar to userWays, userPackages and userSettings, but is it worth it? + +* knownPackages (Targets.hs) -- fix by adding knownUserPackages? A nasty +import cycle is then created between Targets.hs and UserSettings.hs + +* integerLibraryImpl (Switches.hs) -- fix by having three integer library +packages in Targets.hs and choosing which one to build in userPackages, e.g.: + +userPackages = remove [integerGmp2] <> append [integerSimple] + +* In general, should Targets.hs be editable by users as well? Ideally, +there should only be one place for user to look: UserSettings.hs. + +* Any other parameters I missed which should be user configurable? + +================================================ + +2. When predicates are moved from configuration files to UserSettings we +no longer track their state in oracles. This may lead to inconsistent +state of the build system. A more general problem: how do we accurately +track changes in the build systems, specifically in UserSettings.hs? + +================================================ + +3. Discuss if the current design makes recording provenance information +possible. (Should probably be implemented only after the first successful +complete build though.) + +============================================== + +4. I'd like interpret/interpretDiff to be total functions. It should be +possible to check at compile which questions a given environment can +answer and raise an error if an expression needs to know more. + +For example, consider an environment envS that can only answer 'getStage' +question, and environment envSP that can answer questions 'getStage' and +'getPackage'. Now consider two expressions + +exprS = stage0 ? foo + +exprSP = stage0 ? package base ? bar + +Now I'd like the following to produce a compile error: + +interpret envS exprSP + +However, all other combinations should be fine: + +interpret envS exprS +interpret envSP exprS +interpret envSP exprSP + +I played with some possible solutions using type classes, but they all +seem clumsy/heavy. + +Hence, for now I have: + +data Environment = Environment + { + getStage :: Stage, + getBuilder :: Builder, + getPackage :: Package + } + +defaultEnvironment :: Environment +defaultEnvironment = Environment + { + getStage = error "Stage not set in the environment", + getBuilder = error "Builder not set in the environment", + getPackage = error "Package not set in the environment" + } + +which leads to a lot of partial functions all over the build system. \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:28:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify src/Oracles/ModuleFiles.hs, improve performance. (013fa90) Message-ID: <20171026232855.3D4A73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/013fa902ee243621eff3778d94b0f1af37f3de51/ghc >--------------------------------------------------------------- commit 013fa902ee243621eff3778d94b0f1af37f3de51 Author: Andrey Mokhov Date: Thu Dec 24 04:36:07 2015 +0000 Simplify src/Oracles/ModuleFiles.hs, improve performance. >--------------------------------------------------------------- 013fa902ee243621eff3778d94b0f1af37f3de51 src/Oracles/ModuleFiles.hs | 78 ++++++++++++---------------------------------- 1 file changed, 20 insertions(+), 58 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 535d2be..832deef 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,76 +1,44 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} module Oracles.ModuleFiles (moduleFiles, haskellModuleFiles, moduleFilesOracle) where -import Base hiding (exe) -import Distribution.ModuleName -import Distribution.PackageDescription -import Distribution.PackageDescription.Parse -import Distribution.Verbosity -import GHC +import Base import Oracles.PackageData -import Package hiding (library) +import Package import Stage import Settings.TargetDirectory -newtype ModuleFilesKey = ModuleFilesKey (Package, [FilePath]) +newtype ModuleFilesKey = ModuleFilesKey ([String], [FilePath]) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) moduleFiles :: Stage -> Package -> Action [FilePath] moduleFiles stage pkg = do let path = targetPath stage pkg + srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - (found, _ :: [FilePath]) <- askOracle $ ModuleFilesKey (pkg, []) - let cmp (m1, _) m2 = compare m1 m2 - foundFiles = map snd $ intersectOrd cmp found modules - return foundFiles + let dirs = [ pkgPath pkg -/- dir | dir <- srcDirs ] + found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (modules, dirs) + return $ map snd found haskellModuleFiles :: Stage -> Package -> Action ([FilePath], [String]) haskellModuleFiles stage pkg = do let path = targetPath stage pkg autogen = path -/- "build/autogen" + srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - (found, missingMods) <- askOracle $ ModuleFilesKey (pkg, [autogen]) - let cmp (m1, _) m2 = compare m1 m2 - foundFiles = map snd $ intersectOrd cmp found modules + let dirs = [ pkgPath pkg -/- dir | dir <- srcDirs ] + foundSrcDirs <- askOracle $ ModuleFilesKey (modules, dirs ) + foundAutogen <- askOracle $ ModuleFilesKey (modules, [autogen]) + + let found = foundSrcDirs ++ foundAutogen + missingMods = modules `minusOrd` (sort $ map fst found) otherMods = map (replaceEq '/' '.' . dropExtension) otherFiles - (haskellFiles, otherFiles) = partition ("//*hs" ?==) foundFiles + (haskellFiles, otherFiles) = partition ("//*hs" ?==) (map snd found) return (haskellFiles, missingMods ++ otherMods) -extract :: Monoid a => Maybe (CondTree v c a) -> a -extract Nothing = mempty -extract (Just (CondNode leaf _ ifs)) = leaf <> mconcat (map f ifs) - where - f (_, t, mt) = extract (Just t) <> extract mt - --- Look up Haskell source directories and module names of a package -packageInfo :: Package -> Action ([FilePath], [ModuleName]) -packageInfo pkg - | pkg == hp2ps = return (["."], []) - | otherwise = do - need [pkgCabalFile pkg] - pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - - let lib = extract $ condLibrary pd - exe = extract . Just . snd . head $ condExecutables pd - - let (srcDirs, modules) = if lib /= mempty - then ( hsSourceDirs $ libBuildInfo lib, libModules lib) - else ( hsSourceDirs $ buildInfo exe - , [fromString . dropExtension $ modulePath exe] - ++ exeModules exe) - - return (if null srcDirs then ["."] else srcDirs, modules) - moduleFilesOracle :: Rules () moduleFilesOracle = do - answer <- newCache $ \(pkg, extraDirs) -> do - putOracle $ "Searching module files of package " ++ pkgNameString pkg ++ "..." - unless (null extraDirs) $ putOracle $ "Extra directory = " ++ show extraDirs - - (srcDirs, modules) <- packageInfo pkg - - let dirs = extraDirs ++ [ pkgPath pkg -/- dir | dir <- srcDirs ] - decodedPairs = sort $ map (splitFileName . toFilePath) modules + answer <- newCache $ \(modules, dirs) -> do + let decodedPairs = map decodeModule modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedPairs @@ -79,18 +47,12 @@ moduleFilesOracle = do forM todo $ \(mDir, mFiles) -> do let fullDir = dir -/- mDir files <- getDirectoryFiles fullDir ["*"] - let noBoot = filter (not . (isSuffixOf "-boot")) files + let noBoot = filter (not . (isSuffixOf "-boot")) files cmp fe f = compare (dropExtension fe) f found = intersectOrd cmp noBoot mFiles - return (map (fullDir -/-) found, (mDir, map dropExtension found)) - - let foundFiles = sort [ (encodeModule d f, f) - | (fs, (d, _)) <- result, f <- fs ] - foundPairs = [ (d, f) | (d, fs) <- map snd result, f <- fs ] - missingPairs = decodedPairs `minusOrd` sort foundPairs - missingMods = map (uncurry encodeModule) missingPairs + return (map (fullDir -/-) found, mDir) - return (foundFiles, missingMods) + return $ sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] _ <- addOracle $ \(ModuleFilesKey query) -> answer query return () From git at git.haskell.org Thu Oct 26 23:28:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Cabal support for sandboxed build system building (5da933f) Message-ID: <20171026232859.183C83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5da933f768926b7be7e591d22b47a86809c21398/ghc >--------------------------------------------------------------- commit 5da933f768926b7be7e591d22b47a86809c21398 Author: David Luposchainsky Date: Tue Dec 22 20:54:26 2015 +0100 Add Cabal support for sandboxed build system building >--------------------------------------------------------------- 5da933f768926b7be7e591d22b47a86809c21398 .gitignore | 3 ++ README.md | 70 +++++++++++++++++++++++++++++----------- build.cabal.sh | 20 ++++++++++++ shaking-up-ghc.cabal | 91 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 165 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5da933f768926b7be7e591d22b47a86809c21398 From git at git.haskell.org Thu Oct 26 23:28:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:28:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. Minor refactoring. (acde0ea) Message-ID: <20171026232858.D78583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acde0ea23775e06a4cfd2f60974c075e8babdc86/ghc >--------------------------------------------------------------- commit acde0ea23775e06a4cfd2f60974c075e8babdc86 Author: Andrey Mokhov Date: Tue Jun 16 01:09:37 2015 +0100 Add comments. Minor refactoring. >--------------------------------------------------------------- acde0ea23775e06a4cfd2f60974c075e8babdc86 src/Expression.hs | 5 +++-- src/Rules.hs | 3 +-- src/Settings.hs | 1 + src/Settings/GhcCabal.hs | 2 +- src/Settings/Util.hs | 5 +++++ src/Switches.hs | 2 ++ src/Targets.hs | 7 ++++--- src/UserSettings.hs | 7 ++++++- 8 files changed, 23 insertions(+), 9 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 81ed26f..a0c3bf0 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -124,7 +124,7 @@ interpretDiff env = interpret env . fromDiff (??) :: Monoid a => Predicate -> (Expr a, Expr a) -> Expr a p ?? (t, f) = p ? t <> (liftM not p) ? f --- Basic predicates +-- Basic predicates (see Switches.hs for derived predicates) stage :: Stage -> Predicate stage s = liftM (s ==) (asks getStage) @@ -137,6 +137,7 @@ package p = liftM (p ==) (asks getPackage) configKeyValue :: String -> String -> Predicate configKeyValue key value = liftM (value ==) (lift $ askConfig key) --- checks if there is at least one match +-- Check if there is at least one match +-- Example: configKeyValues "host-os-cpp" ["mingw32", "cygwin32"] configKeyValues :: String -> [String] -> Predicate configKeyValues key values = liftM (`elem` values) (lift $ askConfig key) diff --git a/src/Rules.hs b/src/Rules.hs index 5d59ae6..a84f30e 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -13,7 +13,7 @@ import Rules.Package import Settings.Packages -- generateTargets needs package-data.mk files of all target packages --- TODO: make interpret total +-- TODO: make interpretDiff total generateTargets :: Rules () generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do @@ -23,7 +23,6 @@ generateTargets = action $ let dir = targetDirectory stage pkg need [pkgPath pkg dir "package-data.mk"] --- TODO: make interpret total -- TODO: add Stage2 (compiler only?) packageRules :: Rules () packageRules = diff --git a/src/Settings.hs b/src/Settings.hs index cde678e..fb0938a 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -12,6 +12,7 @@ import Expression hiding (when, liftIO) settings :: Settings settings = defaultSettings <> userSettings +-- TODO: add all other settings defaultSettings :: Settings defaultSettings = mconcat [ cabalSettings diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 21ca0e0..4388b17 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -105,7 +105,7 @@ packageConstraints = do ++ cabal ++ "'." args $ concatMap (\c -> ["--constraint", c]) $ constraints --- TODO: remove +-- TODO: should be in a different file ccSettings :: Settings ccSettings = validating ? do let gccGe46 = liftM not gccLt46 diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index dba49d5..74190ec 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -47,6 +47,7 @@ argStagedConfigList key = do stage <- asks getStage argConfigList (stagedKey stage key) +-- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal appendCcArgs :: [String] -> Settings appendCcArgs args = do stage <- asks getStage @@ -54,6 +55,10 @@ appendCcArgs args = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args , builder GhcCabal ? appendSub "--gcc-options" args ] + + + + -- packageData :: Arity -> String -> Settings -- packageData arity key = -- return $ EnvironmentParameter $ PackageData arity key Nothing Nothing diff --git a/src/Switches.hs b/src/Switches.hs index 5436d94..3c6abac 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -12,6 +12,8 @@ module Switches ( import Base import Expression +-- TODO: This setting should be moved to UserSettings.hs +-- TODO: Define three packages for integer library instead of one in Targets.hs -- Support for multiple integer library implementations data IntegerLibraryImpl = IntegerGmp | IntegerGmp2 | IntegerSimple diff --git a/src/Targets.hs b/src/Targets.hs index 1839112..2c61152 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -20,6 +20,7 @@ import Oracles.Builder -- * build/ : contains compiled object code -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal +-- TODO: This is currently not user configurable. Is this right? targetDirectory :: Stage -> Package -> FilePath targetDirectory stage package | package == compiler = "stage" ++ show (fromEnum stage + 1) @@ -85,14 +86,14 @@ customPackageSettings :: Settings customPackageSettings = mconcat [ package integerLibrary ? mconcat [ windowsHost ? builder GhcCabal ? - append ["--configure-option=--with-intree-gmp"] + arg "--configure-option=--with-intree-gmp" , appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] ] , package base ? - builder GhcCabal ? append ["--flags=" ++ integerLibraryName] + builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) , package ghcPrim ? - builder GhcCabal ? append ["--flag=include-ghc-prim"] ] + builder GhcCabal ? arg "--flag=include-ghc-prim" ] -- Note [Cabal name weirdness] -- Find out if we can move the contents to just Cabal/ diff --git a/src/UserSettings.hs b/src/UserSettings.hs index f443659..378db1c 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -10,18 +10,23 @@ import Ways import Targets import Switches import Expression +import Settings.Util -- No user-specific settings by default userSettings :: Settings userSettings = mempty +-- Control conditions of which packages get to be built +-- TODO: adding *new* packages is not possible (see knownPackages in Targets.hs) userPackages :: Packages userPackages = mempty +-- Control which ways are built userWays :: Ways userWays = mempty -- User-defined predicates +-- TODO: migrate more predicates here from configuration files buildHaddock :: Predicate buildHaddock = return True @@ -31,7 +36,7 @@ validating = return False -- Examples: userSettings' :: Settings userSettings' = mconcat - [ package compiler ? stage0 ? append ["foo", "bar"] + [ package compiler ? stage0 ? arg "foo" , builder (Ghc Stage0) ? remove ["-O2"] , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] From git at git.haskell.org Thu Oct 26 23:29:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add getFile and getWay to Environment. (2f373e4) Message-ID: <20171026232902.ED6D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f373e4ab96d1eab13b9e358c39170684a34fa1e/ghc >--------------------------------------------------------------- commit 2f373e4ab96d1eab13b9e358c39170684a34fa1e Author: Andrey Mokhov Date: Tue Jun 16 07:48:23 2015 +0100 Add getFile and getWay to Environment. >--------------------------------------------------------------- 2f373e4ab96d1eab13b9e358c39170684a34fa1e doc/meeting-16-June-2015.txt | 51 +++++++++++++++++++++++++++++++++----------- src/Expression.hs | 21 ++++++++++++------ src/Targets.hs | 1 + src/UserSettings.hs | 22 +++++++++++++++---- 4 files changed, 72 insertions(+), 23 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 2f373e4ab96d1eab13b9e358c39170684a34fa1e From git at git.haskell.org Thu Oct 26 23:29:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename appendCcArgs to ccArgs. (56cf235) Message-ID: <20171026232906.8522D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56cf235d4dd89316597abb5024af57756b1fc47e/ghc >--------------------------------------------------------------- commit 56cf235d4dd89316597abb5024af57756b1fc47e Author: Andrey Mokhov Date: Tue Jun 16 07:52:33 2015 +0100 Rename appendCcArgs to ccArgs. >--------------------------------------------------------------- 56cf235d4dd89316597abb5024af57756b1fc47e src/Settings/Util.hs | 6 +++--- src/Targets.hs | 2 +- src/UserSettings.hs | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 74190ec..e9433a2 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -4,7 +4,7 @@ module Settings.Util ( -- Primitive settings elements arg, argM, args, argConfig, argStagedConfig, argConfigList, argStagedConfigList, - appendCcArgs, + ccArgs, -- argBuilderPath, argStagedBuilderPath, -- argPackageKey, argPackageDeps, argPackageDepKeys, argSrcDirs, -- argIncludeDirs, argDepIncludeDirs, @@ -48,8 +48,8 @@ argStagedConfigList key = do argConfigList (stagedKey stage key) -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal -appendCcArgs :: [String] -> Settings -appendCcArgs args = do +ccArgs :: [String] -> Settings +ccArgs args = do stage <- asks getStage mconcat [ builder (Gcc stage) ? append args , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args diff --git a/src/Targets.hs b/src/Targets.hs index 4bbb963..068e767 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -88,7 +88,7 @@ customPackageSettings = mconcat [ package integerLibrary ? mconcat [ windowsHost ? builder GhcCabal ? arg "--configure-option=--with-intree-gmp" - , appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] ] + , ccArgs ["-Ilibraries/integer-gmp2/gmp"] ] , package base ? builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 3cbf136..52d9678 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -38,7 +38,7 @@ userSettings' = mconcat [ package base ? builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) - , package integerLibrary ? appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] + , package integerLibrary ? ccArgs ["-Ilibraries/integer-gmp2/gmp"] , windowsHost ? package integerLibrary ? From git at git.haskell.org Thu Oct 26 23:29:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Expression: Add Haddocks (263fc63) Message-ID: <20171026232903.2DB1B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/263fc63fb084de713ef67608581d93ff52d2b04b/ghc >--------------------------------------------------------------- commit 263fc63fb084de713ef67608581d93ff52d2b04b Author: Ben Gamari Date: Thu Dec 24 12:34:07 2015 +0100 Expression: Add Haddocks >--------------------------------------------------------------- 263fc63fb084de713ef67608581d93ff52d2b04b src/Expression.hs | 88 ++++++++++++++++++++++++++++++++----------------------- 1 file changed, 52 insertions(+), 36 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 208566c..fa3959d 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -1,37 +1,48 @@ {-# LANGUAGE FlexibleInstances #-} module Expression ( - module Base, - module Builder, - module Package, - module Stage, - module Way, + -- * Expressions Expr, DiffExpr, fromDiffExpr, - Predicate, (?), applyPredicate, Args, Ways, Packages, - Target, PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay, + -- ** Operators apply, append, arg, remove, appendSub, appendSubD, filterSub, removeSub, + -- ** Evaluation interpret, interpretPartial, interpretWithStage, interpretDiff, + -- ** Predicates + Predicate, (?), applyPredicate, + -- ** Common expressions + Args, Ways, Packages, + -- ** Targets + Target, PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay, + + -- * Convenient accessors getStage, getPackage, getBuilder, getOutputs, getInputs, getWay, - getInput, getOutput + getInput, getOutput, + + -- * Re-exports + module Base, + module Builder, + module Package, + module Stage, + module Way ) where import Base -import Builder import Package +import Builder import Stage import Target import Way --- Expr a is a computation that produces a value of type Action a and can read --- parameters of the current build Target. +-- | @Expr a@ is a computation that produces a value of type @Action a@ and can read +-- parameters of the current build 'Target'. type Expr a = ReaderT Target Action a --- Diff a holds functions of type a -> a and is equipped with a Monoid instance. --- We could use Dual (Endo a) instead of Diff a, but the former may look scary. --- The name comes from "difference lists". +-- | @Diff a@ is a /difference list/ containing values of type @a at . A difference +-- list is a list with efficient concatenation, encoded as a value @a -> a at . +-- We could use @Dual (Endo a)@ instead of @Diff a@, but the former may look scary. newtype Diff a = Diff { fromDiff :: a -> a } --- DiffExpr a is a computation that builds a difference list (i.e., a function --- of type Action (a -> a)) and can read parameters of the current build Target. +-- | @DiffExpr a@ is a computation that builds a difference list (i.e., a function +-- of type @'Action' (a -> a)@) and can read parameters of the current build ''Target'. type DiffExpr a = Expr (Diff a) -- Note the reverse order of function composition (y . x), which ensures that @@ -41,38 +52,38 @@ instance Monoid (Diff a) where mempty = Diff id Diff x `mappend` Diff y = Diff $ y . x --- The following expressions are used throughout the build system for --- specifying conditions (Predicate), lists of arguments (Args), Ways and --- Packages. +-- | The following expressions are used throughout the build system for +-- specifying conditions ('Predicate'), lists of arguments ('Args'), 'Ways' +-- and 'Packages'. type Predicate = Expr Bool type Args = DiffExpr [String] type Packages = DiffExpr [Package] type Ways = DiffExpr [Way] -- Basic operations on expressions: --- 1) transform an expression by applying a given function +-- | Transform an expression by applying a given function apply :: (a -> a) -> DiffExpr a apply = return . Diff --- 2) append something to an expression +-- | Append something to an expression append :: Monoid a => a -> DiffExpr a append x = apply (<> x) --- 3) remove given elements from a list expression +-- | Remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] remove xs = apply $ filter (`notElem` xs) --- 4) apply a predicate to an expression +-- | Apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate if bool then expr else return mempty --- Add a single String argument to Args +-- | Add a single argument to 'Args' arg :: String -> Args arg = append . return --- A convenient operator for predicate application +-- | A convenient operator for predicate application class PredicateLike a where (?) :: Monoid m => a -> Expr m -> Expr m @@ -87,9 +98,9 @@ instance PredicateLike Bool where instance PredicateLike (Action Bool) where (?) = applyPredicate . lift --- appendSub appends a list of sub-arguments to all arguments starting with a +-- | @appendSub@ appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument --- of the form 'prefix=listOfSubarguments' is appended to the expression. +-- of the form @prefix=listOfSubarguments@ is appended to the expression. -- Note: nothing is done if the list of sub-arguments is empty. appendSub :: String -> [String] -> Args appendSub prefix xs @@ -103,8 +114,8 @@ appendSub prefix xs then unwords (y : xs') : go True ys else y : go found ys --- appendSubD is similar to appendSub but it extracts the list of sub-arguments --- from the given DiffExpr. +-- | @appendSubD@ is similar to 'appendSub' but it extracts the list of sub-arguments +-- from the given 'DiffExpr'. appendSubD :: String -> Args -> Args appendSubD prefix diffExpr = fromDiffExpr diffExpr >>= appendSub prefix @@ -115,12 +126,12 @@ filterSub prefix p = apply $ map filterSubstr | prefix `isPrefixOf` s = unwords . filter p . words $ s | otherwise = s --- Remove given elements from a list of sub-arguments with a given prefix +-- | Remove given elements from a list of sub-arguments with a given prefix -- Example: removeSub "--configure-option=CFLAGS" ["-Werror"] removeSub :: String -> [String] -> Args removeSub prefix xs = filterSub prefix (`notElem` xs) --- Interpret a given expression in a given environment +-- | Interpret a given expression in a given environment interpret :: Target -> Expr a -> Action a interpret = flip runReaderT @@ -131,41 +142,46 @@ interpretWithStage :: Stage -> Expr a -> Action a interpretWithStage s = interpretPartial $ PartialTarget s (error "interpretWithStage: package not set") --- Extract an expression from a difference expression +-- | Extract an expression from a difference expression fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) --- Interpret a given difference expression in a given environment +-- | Interpret a given difference expression in a given environment interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a interpretDiff target = interpret target . fromDiffExpr --- Convenient getters for target parameters +-- | Convenient getters for target parameters getStage :: Expr Stage getStage = asks stage +-- | Get the 'Package' of the current 'Target' getPackage :: Expr Package getPackage = asks package +-- | Get the 'Builder' for the current 'Target' getBuilder :: Expr Builder getBuilder = asks builder +-- | Get the 'Way' of the current 'Target' getWay :: Expr Way getWay = asks way +-- | Get the input files of the current 'Target' getInputs :: Expr [FilePath] getInputs = asks inputs --- Run getInputs and check that the result contains a single input file only +-- | Run 'getInputs' and check that the result contains a single input file only getInput :: Expr FilePath getInput = do target <- ask getSingleton getInputs $ "getInput: exactly one input file expected in target " ++ show target +-- | Get the files produced by the current 'Target' getOutputs :: Expr [FilePath] getOutputs = asks outputs --- Run getOutputs and check that the result contains a output file only +-- | Run 'getOutputs' and check that the result contains a output file only getOutput :: Expr FilePath getOutput = do target <- ask From git at git.haskell.org Thu Oct 26 23:29:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #34 from bgamari/master (20b4c08) Message-ID: <20171026232906.97EC23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20b4c080dedd0fd6c1ce6a7d9b8543b8c97cf82e/ghc >--------------------------------------------------------------- commit 20b4c080dedd0fd6c1ce6a7d9b8543b8c97cf82e Merge: 013fa90 263fc63 Author: Andrey Mokhov Date: Thu Dec 24 12:33:42 2015 +0000 Merge pull request #34 from bgamari/master Expression: Add Haddocks >--------------------------------------------------------------- 20b4c080dedd0fd6c1ce6a7d9b8543b8c97cf82e src/Expression.hs | 88 ++++++++++++++++++++++++++++++++----------------------- 1 file changed, 52 insertions(+), 36 deletions(-) From git at git.haskell.org Thu Oct 26 23:29:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finalise meeting agenda. (7d53e6b) Message-ID: <20171026232909.E72023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d53e6b43cc5a0280218c12fab1a16bf9fcc2f1c/ghc >--------------------------------------------------------------- commit 7d53e6b43cc5a0280218c12fab1a16bf9fcc2f1c Author: Andrey Mokhov Date: Tue Jun 16 09:53:30 2015 +0100 Finalise meeting agenda. >--------------------------------------------------------------- 7d53e6b43cc5a0280218c12fab1a16bf9fcc2f1c doc/meeting-16-June-2015.txt | 54 ++++++++++++++++++++++++++++++++++++-------- 1 file changed, 44 insertions(+), 10 deletions(-) diff --git a/doc/meeting-16-June-2015.txt b/doc/meeting-16-June-2015.txt index bd2b94f..d58b541 100644 --- a/doc/meeting-16-June-2015.txt +++ b/doc/meeting-16-June-2015.txt @@ -13,45 +13,76 @@ similar to userWays, userPackages and userSettings, but is it worth it? * knownPackages (Targets.hs) -- fix by adding knownUserPackages? A nasty import cycle is then created between Targets.hs and UserSettings.hs. Possible solution: add file Settings/Targets.hs which will actually put two things -together similar to what's done with userWays, userPackages and userSettings. +together similar to how it's done with userWays, userPackages and userSettings. * integerLibraryImpl (Switches.hs) -- fix by having three integer library packages in Targets.hs and choosing which one to build in userPackages, e.g.: userPackages = remove [integerGmp2] <> append [integerSimple] -* In general, should Targets.hs be editable by users as well? Ideally, -there should only be one place for user to look: UserSettings.hs. +(Maybe a useful pattern: replace a b = remove a <> append b.) + +* In general, should Targets.hs (or any other file) be editable by users? +Ideally, there should only be one place for users to look: UserSettings.hs. * Any other parameters I missed which should be user configurable? ================================================ 2. When predicates (e.g. buildHaddock) are moved from configuration files to -UserSettings we no longer track their state in oracles. This may lead to an +UserSettings.hs we no longer track their state in oracles. This may lead to an inconsistent state of the build system. This is a special case of a more general problem: how do we accurately track changes in the build system, specifically in UserSettings.hs? Although in general this is a hard problem, this special -case may be easier to solve: just channel everything exported from +case may be easier to solve: e.g., just channel everything exported from UserSettings.hs through oracles? Another alternative which was discussed previously: pass the final lists of arguments through oracles. Care must -be taken though as final command lines can be as large as 5Mb! +be taken though as final command lines can be as large as 5Mb and may bloat +the Shake database! ================================================ -3. Discuss if the current design makes recording provenance information +3. Discuss if/how the current approach makes recording provenance information possible. (Should probably be implemented only after the first successful complete build though.) ============================================== -4. I'd like interpret/interpretDiff to be total functions. It should be +4. Duplication of information in knownPackages and packages. + +I'd like to enforce the following invariant: whenever a package is used +in userPackages, it must also be placed in knownPackages/knownUserPackages. + +This feels awkward/redundant. The reason for having knownPackages is that I +need a list of packages outside the Action monad for it to be useable in +packageRules (see Rules.hs). The current solution seems to be the cheapest way +to achieve that. An alternative would be to have one additional implementation +of interpret, which would extract the 'support' from a given expression, i.e. +the set of packages that can occur in a given expression, regardless of how +predicates evaluate (without looking up oracles which live in the Action monad). + +For example, + +interpret' (stage0 ? base <> stage1 ? compiler) == [base, compiler] + +This seems to require a lot of extra code though. Hence redundant knownPackages. + +============================================== + +5. (Just realised that the following is trickier than I thought. Maybe not +worth raising at this meeting if not enough time.) + +I'd like interpret/interpretDiff to be total functions. It should be possible to check at compile which questions a given environment can -answer and raise a *compile* error if the expression needs to know more. +answer and raise a *compile* error if the expression needs to know more. Why +is this useful? For example, I'd like to allow only getStage and +platform-specific predicates in userPackages (since nothing else is known at +this point; one can argue that we should even forbid to use such predicates +when constructing expressions of type Packages). For example, consider an environment envS that can only answer 'getStage' question, and environment envSP that can answer questions 'getStage' and -'getPackage'. Now consider two expressions +'getPackage'. Now consider two expressions: exprS = stage0 ? arg "foo" @@ -106,3 +137,6 @@ getPackage, getBuilder, getFile, getWay. Hence, it may be OK to have only 6 combinations of getters in a type constraint, not 2^5, e.g.: empty, GetStage env, (GetStage env, GetPackage env), etc. +============================================== + + From git at git.haskell.org Thu Oct 26 23:29:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #28 from quchen/cabalify (b053270) Message-ID: <20171026232910.03E203A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b053270c04df9aa94b97ced51704cdc676793745/ghc >--------------------------------------------------------------- commit b053270c04df9aa94b97ced51704cdc676793745 Merge: 20b4c08 5da933f Author: Andrey Mokhov Date: Thu Dec 24 12:35:37 2015 +0000 Merge pull request #28 from quchen/cabalify Add Cabal sandboxed build script >--------------------------------------------------------------- b053270c04df9aa94b97ced51704cdc676793745 .gitignore | 3 ++ README.md | 70 +++++++++++++++++++++++++++++----------- build.cabal.sh | 20 ++++++++++++ shaking-up-ghc.cabal | 91 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 165 insertions(+), 19 deletions(-) From git at git.haskell.org Thu Oct 26 23:29:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (b2b7c5c) Message-ID: <20171026232913.5BFA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2b7c5c53ed5369249ebff39aa8735a897ad86a9/ghc >--------------------------------------------------------------- commit b2b7c5c53ed5369249ebff39aa8735a897ad86a9 Author: Andrey Mokhov Date: Tue Jun 16 09:54:10 2015 +0100 Add comments. >--------------------------------------------------------------- b2b7c5c53ed5369249ebff39aa8735a897ad86a9 src/Expression.hs | 2 +- src/Rules/Data.hs | 70 ++++++++++++++---------------------------------- src/Settings/GhcCabal.hs | 3 +++ 3 files changed, 24 insertions(+), 51 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 9232aed..4809324 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -24,7 +24,7 @@ data Environment = Environment getStage :: Stage, getPackage :: Package, getBuilder :: Builder, - getFile :: FilePath, + getFile :: FilePath, -- TODO: handle multple files? getWay :: Way } diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index aa1ebab..3754cdc 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -13,29 +13,6 @@ import Settings.GhcPkg import Settings.GhcCabal import Util --- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: --- 1) Drop lines containing '$' --- For example, get rid of --- libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ... --- Reason: we don't need them and we can't parse them. --- 2) Replace '/' and '\' with '_' before '=' --- For example libraries/deepseq/dist-install_VERSION = 1.4.0.0 --- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 --- Reason: Shake's built-in makefile parser doesn't recognise slashes - -postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map processLine pkgData - where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line - --- this is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument --- * otherwise, we must collapse it into one space-separated string - -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: Environment -> Rules () buildPackageData env = @@ -53,6 +30,8 @@ buildPackageData env = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" + -- TODO: 1) how to automate this? 2) handle multiple files? + newEnv = env { getFile = dir "package-data.mk" } -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac @@ -62,37 +41,28 @@ buildPackageData env = run' env (GhcPkg stage) postProcessPackageData $ dir "package-data.mk" +-- TODO: This should probably go to Oracles.Builder run' :: Environment -> Builder -> Action () run' env builder = do args <- interpret (env {getBuilder = builder}) $ fromDiff settings putColoured Green (show args) run builder args ---buildRule :: Package -> TodoItem -> Rules () ---buildRule pkg @ (Package name path cabal _) todo @ (stage, dist, settings) = --- let pathDist = path dist --- cabalPath = path cabal --- configure = path "configure" --- in --- -- All these files are produced by a single run of GhcCabal --- (pathDist ) <$> --- [ "package-data.mk" --- , "haddock-prologue.txt" --- , "inplace-pkg-config" --- , "setup-config" --- , "build" "autogen" "cabal_macros.h" --- -- TODO: Is this needed? Also check out Paths_cpsa.hs. --- -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" --- ] &%> \_ -> do --- need [cabalPath] --- when (doesFileExist $ configure <.> "ac") $ need [configure] --- -- GhcCabal will run the configure script, so we depend on it --- -- We still don't know who build the configure script from configure.ac --- run GhcCabal $ cabalArgs pkg todo --- when (registerPackage settings) $ --- run (GhcPkg stage) $ ghcPkgArgs pkg todo --- postProcessPackageData $ pathDist "package-data.mk" - --- buildSettings = + builder Gcc ? ccSettings +-- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: +-- 1) Drop lines containing '$' +-- For example, get rid of +-- libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ... +-- Reason: we don't need them and we can't parse them. +-- 2) Replace '/' and '\' with '_' before '=' +-- For example libraries/deepseq/dist-install_VERSION = 1.4.0.0 +-- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 +-- Reason: Shake's built-in makefile parser doesn't recognise slashes --- builder Gcc ? "-tricky-flag" +postProcessPackageData :: FilePath -> Action () +postProcessPackageData file = do + pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) + length pkgData `seq` writeFileLines file $ map processLine pkgData + where + processLine line = replaceSeparators '_' prefix ++ suffix + where + (prefix, suffix) = break (== '=') line diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 4388b17..4cbb0a3 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -83,6 +83,9 @@ bootPackageDbSettings = do sourcePath <- lift $ askConfig "ghc-source-path" arg $ "--package-db=" ++ sourcePath "libraries/bootstrapping.conf" +-- this is a positional argument, hence: +-- * if it is empty, we need to emit one empty string argument +-- * otherwise, we must collapse it into one space-separated string dllSettings :: Settings dllSettings = arg "" From git at git.haskell.org Thu Oct 26 23:29:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove `make inplace/bin/ghc-cabal` (see #23) (c1802dc) Message-ID: <20171026232913.6C4903A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1802dc7290cf3b694fefa3e338b49a3b39956d4/ghc >--------------------------------------------------------------- commit c1802dc7290cf3b694fefa3e338b49a3b39956d4 Author: Andrey Mokhov Date: Thu Dec 24 13:00:08 2015 +0000 Remove `make inplace/bin/ghc-cabal` (see #23) >--------------------------------------------------------------- c1802dc7290cf3b694fefa3e338b49a3b39956d4 README.md | 2 -- 1 file changed, 2 deletions(-) diff --git a/README.md b/README.md index 3c42074..4fab178 100644 --- a/README.md +++ b/README.md @@ -25,7 +25,6 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure -make inplace/bin/ghc-cabal # This needs to be fixed ``` Now you have a couple of options: @@ -45,7 +44,6 @@ $ cd ghc $ git clone git://github.com/snowleopard/shaking-up-ghc shake-build $ ./boot $ ./configure --enable-tarballs-autodownload -$ make inplace/bin/ghc-cabal # This needs to be fixed $ shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. From git at git.haskell.org Thu Oct 26 23:29:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make targetDirectory and knownPackages configurable, rename Environment to Target. (418a1cd) Message-ID: <20171026232917.64ACB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/418a1cd630e1c2eb6e467e502d615ae4307113b7/ghc >--------------------------------------------------------------- commit 418a1cd630e1c2eb6e467e502d615ae4307113b7 Author: Andrey Mokhov Date: Sun Jul 12 23:12:39 2015 +0100 Make targetDirectory and knownPackages configurable, rename Environment to Target. >--------------------------------------------------------------- 418a1cd630e1c2eb6e467e502d615ae4307113b7 doc/meeting-16-June-2015.txt | 22 ++++++++++++- src/Expression.hs | 72 ++++++++++++++++++++++++----------------- src/Package.hs | 1 + src/Rules.hs | 8 ++--- src/Rules/Data.hs | 22 ++++++------- src/Rules/Package.hs | 2 +- src/Settings.hs | 1 - src/Settings/GhcCabal.hs | 20 ++++++++++-- src/Settings/GhcPkg.hs | 2 +- src/Settings/Packages.hs | 18 ++++++++++- src/Settings/TargetDirectory.hs | 11 +++++++ src/Settings/Util.hs | 9 +++--- src/Switches.hs | 9 ------ src/Targets.hs | 59 +++++---------------------------- src/UserSettings.hs | 54 ++++++++++--------------------- 15 files changed, 155 insertions(+), 155 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 418a1cd630e1c2eb6e467e502d615ae4307113b7 From git at git.haskell.org Thu Oct 26 23:29:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add the author's email. (3f55a9e) Message-ID: <20171026232917.7FC123A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3f55a9ed5d25f9f6310b76db5a0befe1b66aa19d/ghc >--------------------------------------------------------------- commit 3f55a9ed5d25f9f6310b76db5a0befe1b66aa19d Author: Andrey Mokhov Date: Thu Dec 24 19:50:10 2015 +0000 Add the author's email. >--------------------------------------------------------------- 3f55a9ed5d25f9f6310b76db5a0befe1b66aa19d shaking-up-ghc.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 4cfb30d..f1a3f10 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -3,9 +3,9 @@ version: 0.1.0.0 synopsis: GHC build system license: BSD3 license-file: LICENSE -author: Andrey Mokhov, Github: @snowleopard -maintainer: Andrey Mokhov, Github: @snowleopard -copyright: Andrey Mokhov, Github: @snowleopard +author: Andrey Mokhov , github: @snowleopard +maintainer: Andrey Mokhov , github: @snowleopard +copyright: Andrey Mokhov 2014-2015 category: Development build-type: Simple cabal-version: >=1.10 From git at git.haskell.org Thu Oct 26 23:29:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move OverloadedStrings to other-extensions. (b56b886) Message-ID: <20171026232921.1E0683A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b56b88616e82fb652c49ea9f6c087dd76e950a42/ghc >--------------------------------------------------------------- commit b56b88616e82fb652c49ea9f6c087dd76e950a42 Author: Andrey Mokhov Date: Thu Dec 24 20:24:14 2015 +0000 Move OverloadedStrings to other-extensions. >--------------------------------------------------------------- b56b88616e82fb652c49ea9f6c087dd76e950a42 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f1a3f10..098d8b2 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -72,11 +72,11 @@ executable ghc-shake default-extensions: BangPatterns , LambdaCase , MultiWayIf - , OverloadedStrings , TupleSections other-extensions: DeriveDataTypeable , DeriveGeneric , FlexibleInstances + , OverloadedStrings build-depends: base , ansi-terminal >= 0.6 , Cabal >= 1.22 From git at git.haskell.org Thu Oct 26 23:29:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, rename interpretDiff to interpret. (238398a) Message-ID: <20171026232921.1AE563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/238398a839967ceb0dfc8f6e013a23f8551d67f5/ghc >--------------------------------------------------------------- commit 238398a839967ceb0dfc8f6e013a23f8551d67f5 Author: Andrey Mokhov Date: Mon Jul 13 16:13:58 2015 +0100 Add comments, rename interpretDiff to interpret. >--------------------------------------------------------------- 238398a839967ceb0dfc8f6e013a23f8551d67f5 src/Expression.hs | 51 +++++++++++++++++++++++++++++++++++---------------- src/Rules.hs | 2 +- src/Rules/Data.hs | 2 +- 3 files changed, 37 insertions(+), 18 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 46b3c40..88561eb 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -7,7 +7,7 @@ module Expression ( Settings, Ways, Packages, Target (..), stageTarget, stagePackageTarget, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, - interpret, interpretDiff, + interpret, interpretExpr, applyPredicate, (?), (??), stage, package, builder, file, way, configKeyValue, configKeyValues ) where @@ -19,6 +19,9 @@ import Package import Data.Monoid import Control.Monad.Reader +-- Target captures parameters relevant to the current build target: Stage and +-- Package being built, Builder that is to be invoked, file(s) that are to +-- be built and the Way they are to be built. data Target = Target { getStage :: Stage, @@ -48,24 +51,40 @@ stagePackageTarget stage package = Target getWay = error "stagePackageTarget: Way not set" } +-- Expr a is a computation that produces a value of type Action a and can read +-- parameters of the current build Target. +type Expr a = ReaderT Target Action a + +-- If values of type a form a Monoid then so do computations of type Expr a: +-- * the empty computation returns the identity element of the underlying type +-- * two computations can be combined by combining their results +instance Monoid a => Monoid (Expr a) where + mempty = return mempty + mappend = liftM2 mappend + +-- Diff a holds functions of type a -> a and is equipped with a Monoid instance. -- We could use Dual (Endo a) instead of Diff a, but the former may look scary. +-- The name comes from "difference lists". newtype Diff a = Diff { fromDiff :: a -> a } +-- DiffExpr a is a computation that builds a difference list (i.e., a function +-- of type Action (a -> a)) and can read parameters of the current build Target. +type DiffExpr a = Expr (Diff a) + +-- Note the reverse order of function composition (y . x), which ensures that +-- when two DiffExpr computations c1 and c2 are combined (c1 <> c2), then c1 is +-- applied first, and c2 is applied second. instance Monoid (Diff a) where mempty = Diff id Diff x `mappend` Diff y = Diff $ y . x -type Expr a = ReaderT Target Action a -type DiffExpr a = Expr (Diff a) - -type Predicate = Expr Bool -type Settings = DiffExpr [String] -- TODO: rename to Args -type Ways = DiffExpr [Way] -type Packages = DiffExpr [Package] - -instance Monoid a => Monoid (Expr a) where - mempty = return mempty - mappend = liftM2 mappend +-- The following expressions are used throughout the build system for +-- specifying conditions (Predicate), lists of arguments (Settings), Ways and +-- Packages. +type Predicate = Expr Bool +type Settings = DiffExpr [String] -- TODO: rename to Args +type Ways = DiffExpr [Way] +type Packages = DiffExpr [Package] -- Basic operations on expressions: -- 1) append something to an expression @@ -126,16 +145,16 @@ removeSub :: String -> [String] -> Settings removeSub prefix xs = filterSub prefix (`notElem` xs) -- Interpret a given expression in a given environment -interpret :: Target -> Expr a -> Action a -interpret = flip runReaderT +interpretExpr :: Target -> Expr a -> Action a +interpretExpr = flip runReaderT -- Extract an expression from a difference expression fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) -- Interpret a given difference expression in a given environment -interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a -interpretDiff target = interpret target . fromDiffExpr +interpret :: Monoid a => Target -> DiffExpr a -> Action a +interpret target = interpretExpr target . fromDiffExpr -- An equivalent of if-then-else for predicates (??) :: Monoid a => Predicate -> (Expr a, Expr a) -> Expr a diff --git a/src/Rules.hs b/src/Rules.hs index 6e1093b..852a6cf 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -17,7 +17,7 @@ import Settings.TargetDirectory generateTargets :: Rules () generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do - pkgs <- interpretDiff (stageTarget stage) packages + pkgs <- interpret (stageTarget stage) packages forM_ pkgs $ \pkg -> do let dir = targetDirectory stage pkg need [pkgPath pkg dir "package-data.mk"] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 20f05f5..d608fea 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -44,7 +44,7 @@ buildPackageData target = -- TODO: This should probably go to Oracles.Builder run' :: Target -> Builder -> Action () run' target builder = do - args <- interpret (target {getBuilder = builder}) $ fromDiffExpr settings + args <- interpret (target {getBuilder = builder}) settings putColoured Green (show args) run builder args From git at git.haskell.org Thu Oct 26 23:29:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add argWith. (cbda822) Message-ID: <20171026232924.9DA133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbda8225449ac1ed80f64843f4fc58390e113994/ghc >--------------------------------------------------------------- commit cbda8225449ac1ed80f64843f4fc58390e113994 Author: Andrey Mokhov Date: Mon Jul 13 16:42:04 2015 +0100 Add argWith. >--------------------------------------------------------------- cbda8225449ac1ed80f64843f4fc58390e113994 src/Oracles/Builder.hs | 7 +++---- src/Settings/GhcCabal.hs | 20 ++++++++------------ src/Settings/Util.hs | 5 ++++- 3 files changed, 15 insertions(+), 17 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 316217f..1f3e45a 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -12,8 +12,7 @@ import Oracles.Base import Oracles.Flag import Oracles.Option --- A Builder is an external command invoked in separate process --- by calling Shake.cmd +-- A Builder is an external command invoked in separate process using Shake.cmd -- -- Ghc Stage0 is the bootstrapping compiler -- Ghc StageN, N > 0, is the one built on stage (N - 1) @@ -82,11 +81,11 @@ needBuilder builder = do need [exe] -- Action 'with Gcc' returns '--with-gcc=/path/to/gcc' and needs Gcc -with :: Builder -> Args +with :: Builder -> Action String with builder = do exe <- showArg builder needBuilder builder - return [withBuilderKey builder ++ exe] + return $ withBuilderKey builder ++ exe withBuilderKey :: Builder -> String withBuilderKey builder = case builder of diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index d8eda6a..db8fd6e 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -25,18 +25,18 @@ cabalSettings = builder GhcCabal ? do , arg $ pkgPath pkg , arg $ targetDirectory stage pkg , dllSettings - , with' $ Ghc stage - , with' $ GhcPkg stage + , argWith $ Ghc stage + , argWith $ GhcPkg stage , stage0 ? bootPackageDbSettings , librarySettings - , configKeyNonEmpty "hscolour" ? with' HsColour -- TODO: generalise? + , configKeyNonEmpty "hscolour" ? argWith HsColour -- TODO: generalise? , configureSettings , stage0 ? packageConstraints - , with' $ Gcc stage - , notStage Stage0 ? with' Ld - , with' Ar - , with' Alex - , with' Happy ] -- TODO: reorder with's + , argWith $ Gcc stage + , notStage Stage0 ? argWith Ld + , argWith Ar + , argWith Alex + , argWith Happy ] -- TODO: reorder argWiths -- TODO: Isn't vanilla always built? If yes, some conditions are redundant. librarySettings :: Settings @@ -90,10 +90,6 @@ bootPackageDbSettings = do dllSettings :: Settings dllSettings = arg "" --- TODO: remove -with' :: Builder -> Settings -with' builder = appendM $ with builder - packageConstraints :: Settings packageConstraints = do pkgs <- fromDiffExpr packages diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 4b22be4..d7bfa49 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -2,7 +2,7 @@ module Settings.Util ( -- Primitive settings elements - arg, argM, args, + arg, argM, args, argWith, argConfig, argStagedConfig, argConfigList, argStagedConfigList, ccArgs, -- argBuilderPath, argStagedBuilderPath, @@ -28,6 +28,9 @@ argM = appendM . fmap return args :: [String] -> Settings args = append +argWith :: Builder -> Settings +argWith = argM . with + argConfig :: String -> Settings argConfig = appendM . fmap return . askConfig From git at git.haskell.org Thu Oct 26 23:29:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move parseMakefile from dependenciesOracle to Rules.Dependencies (for better performance) (8fe9fa6) Message-ID: <20171026232924.BE04D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1/ghc >--------------------------------------------------------------- commit 8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1 Author: Andrey Mokhov Date: Fri Dec 25 01:19:50 2015 +0000 Move parseMakefile from dependenciesOracle to Rules.Dependencies (for better performance) >--------------------------------------------------------------- 8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1 src/Oracles/Dependencies.hs | 7 ++----- src/Rules/Dependencies.hs | 19 +++++++++++++------ 2 files changed, 15 insertions(+), 11 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index c27c2cc..8895758 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -31,11 +31,8 @@ dependenciesOracle :: Rules () dependenciesOracle = do deps <- newCache $ \file -> do putOracle $ "Reading dependencies from " ++ file ++ "..." - contents <- parseMakefile <$> readFile' file - return . Map.fromList . map (bimap unifyPath (map unifyPath)) - . map (bimap head concat . unzip) - . groupBy ((==) `on` fst) - . sortBy (compare `on` fst) $ contents + contents <- map words <$> readFileLines file + return . Map.fromList $ map (\(x:xs) -> (x, xs)) contents _ <- addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file return () diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 47e6c6d..907c4d3 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -21,7 +21,7 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] - hDepFile %> \file -> do + hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) $ need [platformH] -- TODO: very ugly and fragile; use gcc -MM instead? @@ -43,14 +43,21 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = , "primop-vector-tys.hs-incl" ] need $ srcs ++ extraDeps if srcs == [] - then writeFileChanged file "" - else build $ fullTarget target (GhcM stage) srcs [file] - removeFileIfExists $ file <.> "bak" + then writeFileChanged out "" + else build $ fullTarget target (GhcM stage) srcs [out] + removeFileIfExists $ out <.> "bak" - (buildPath -/- ".dependencies") %> \file -> do + (buildPath -/- ".dependencies") %> \out -> do cSrcs <- pkgDataList $ CSrcs path let cDepFiles = [ buildPath -/- src <.> "deps" | src <- cSrcs ] need $ hDepFile : cDepFiles -- need all for more parallelism cDeps <- fmap concat $ mapM readFile' cDepFiles hDeps <- readFile' hDepFile - writeFileChanged file $ cDeps ++ hDeps + let result = unlines + . map (\(src, deps) -> unwords $ src : deps) + . map (bimap unifyPath (map unifyPath)) + . map (bimap head concat . unzip) + . groupBy ((==) `on` fst) + . sortBy (compare `on` fst) + . parseMakefile $ cDeps ++ hDeps + writeFileChanged out result From git at git.haskell.org Thu Oct 26 23:29:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (f62f166) Message-ID: <20171026232928.4978A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f62f166802cf0aa26ce72bb29b073d184897a512/ghc >--------------------------------------------------------------- commit f62f166802cf0aa26ce72bb29b073d184897a512 Author: Andrey Mokhov Date: Mon Jul 13 16:56:48 2015 +0100 Clean up. >--------------------------------------------------------------- f62f166802cf0aa26ce72bb29b073d184897a512 src/Settings/GhcCabal.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index db8fd6e..8e1a8cf 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -10,7 +10,7 @@ import Util import Package import Targets import Switches -import Expression hiding (when, liftIO) +import Expression hiding (liftIO) import Settings.Ways import Settings.Util import Settings.Packages @@ -29,14 +29,14 @@ cabalSettings = builder GhcCabal ? do , argWith $ GhcPkg stage , stage0 ? bootPackageDbSettings , librarySettings - , configKeyNonEmpty "hscolour" ? argWith HsColour -- TODO: generalise? + , configKeyNonEmpty "hscolour" ? argWith HsColour , configureSettings , stage0 ? packageConstraints , argWith $ Gcc stage , notStage Stage0 ? argWith Ld , argWith Ar , argWith Alex - , argWith Happy ] -- TODO: reorder argWiths + , argWith Happy ] -- TODO: Isn't vanilla always built? If yes, some conditions are redundant. librarySettings :: Settings @@ -84,9 +84,9 @@ bootPackageDbSettings = do sourcePath <- lift $ askConfig "ghc-source-path" arg $ "--package-db=" ++ sourcePath "libraries/bootstrapping.conf" --- this is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument --- * otherwise, we must collapse it into one space-separated string +-- This is a positional argument, hence: +-- * if it is empty, we need to emit one empty string argument; +-- * otherwise, we must collapse it into one space-separated string. dllSettings :: Settings dllSettings = arg "" From git at git.haskell.org Thu Oct 26 23:29:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a section on resetting the build (#32) (86ee9f6) Message-ID: <20171026232928.75BCF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86ee9f68057e7ab1a9f09a6d006cddb488c16c02/ghc >--------------------------------------------------------------- commit 86ee9f68057e7ab1a9f09a6d006cddb488c16c02 Author: Andrey Mokhov Date: Fri Dec 25 14:12:35 2015 +0000 Add a section on resetting the build (#32) >--------------------------------------------------------------- 86ee9f68057e7ab1a9f09a6d006cddb488c16c02 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 4fab178..c415ee4 100644 --- a/README.md +++ b/README.md @@ -49,7 +49,9 @@ $ shake-build/build.bat Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. +### Resetting the build +To reset the new build system delete the `shake-build/.db` directory which stores the Shake database. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). How to contribute From git at git.haskell.org Thu Oct 26 23:29:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add targetPath. (35d9a07) Message-ID: <20171026232931.B8DE23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/35d9a0726b9751c29c8f0250bd925f84074cc3b2/ghc >--------------------------------------------------------------- commit 35d9a0726b9751c29c8f0250bd925f84074cc3b2 Author: Andrey Mokhov Date: Mon Jul 13 22:24:50 2015 +0100 Add targetPath. >--------------------------------------------------------------- 35d9a0726b9751c29c8f0250bd925f84074cc3b2 src/Rules.hs | 4 +--- src/Rules/Data.hs | 8 ++++---- src/Settings/GhcCabal.hs | 1 + src/Settings/GhcPkg.hs | 4 +--- src/Settings/TargetDirectory.hs | 6 +++++- 5 files changed, 12 insertions(+), 11 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 852a6cf..ce204ea 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -6,7 +6,6 @@ module Rules ( import Base hiding (arg, args, Args) import Control.Monad -import Package import Expression import Rules.Package import Settings.Packages @@ -19,8 +18,7 @@ generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do pkgs <- interpret (stageTarget stage) packages forM_ pkgs $ \pkg -> do - let dir = targetDirectory stage pkg - need [pkgPath pkg dir "package-data.mk"] + need [targetPath stage pkg "package-data.mk"] -- TODO: add Stage2 (compiler only?) packageRules :: Rules () diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index d608fea..a18a097 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -18,9 +18,9 @@ buildPackageData :: Target -> Rules () buildPackageData target = let stage = getStage target pkg = getPackage target - dir = pkgPath pkg targetDirectory stage pkg + path = targetPath stage pkg in - (dir ) <$> + (path ) <$> [ "package-data.mk" , "haddock-prologue.txt" , "inplace-pkg-config" @@ -31,7 +31,7 @@ buildPackageData target = ] &%> \_ -> do let configure = pkgPath pkg "configure" -- TODO: 1) how to automate this? 2) handle multiple files? - newEnv = target { getFile = dir "package-data.mk" } + newEnv = target { getFile = path "package-data.mk" } -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac @@ -39,7 +39,7 @@ buildPackageData target = run' newEnv GhcCabal -- TODO: when (registerPackage settings) $ run' newEnv (GhcPkg stage) - postProcessPackageData $ dir "package-data.mk" + postProcessPackageData $ path "package-data.mk" -- TODO: This should probably go to Oracles.Builder run' :: Target -> Builder -> Action () diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 8e1a8cf..578c264 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -106,6 +106,7 @@ packageConstraints = do args $ concatMap (\c -> ["--constraint", c]) $ constraints -- TODO: should be in a different file +-- TODO: put all validating options together in one file ccSettings :: Settings ccSettings = validating ? do let gccGe46 = liftM not gccLt46 diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index d5fb21e..601d2b8 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -3,7 +3,6 @@ module Settings.GhcPkg ( ) where import Base hiding (arg, args) -import Package import Switches import Expression hiding (when, liftIO) import Settings.Util @@ -15,9 +14,8 @@ ghcPkgSettings :: Settings ghcPkgSettings = do pkg <- asks getPackage stage <- asks getStage - let dir = pkgPath pkg targetDirectory stage pkg builder (GhcPkg stage) ? mconcat [ arg "update" , arg "--force" , stage0 ? bootPackageDbSettings - , arg $ dir "inplace-pkg-config" ] + , arg $ targetPath stage pkg "inplace-pkg-config" ] diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 83e1d0e..d8eb067 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,5 +1,5 @@ module Settings.TargetDirectory ( - targetDirectory + targetDirectory, targetPath ) where import Base @@ -9,3 +9,7 @@ import UserSettings -- User can override the default target directory settings given below targetDirectory :: Stage -> Package -> FilePath targetDirectory = userTargetDirectory + +-- Path to the target directory from GHC source root +targetPath :: Stage -> Package -> FilePath +targetPath stage pkg = pkgPath pkg targetDirectory stage pkg From git at git.haskell.org Thu Oct 26 23:29:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use `-B` flag to reset the build (bdb88c6) Message-ID: <20171026232931.DF27B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bdb88c61e4e0761a2ad80904f26d2443fecf7fd4/ghc >--------------------------------------------------------------- commit bdb88c61e4e0761a2ad80904f26d2443fecf7fd4 Author: Andrey Mokhov Date: Fri Dec 25 22:49:45 2015 +0000 Use `-B` flag to reset the build >--------------------------------------------------------------- bdb88c61e4e0761a2ad80904f26d2443fecf7fd4 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index c415ee4..6d27b25 100644 --- a/README.md +++ b/README.md @@ -51,7 +51,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system delete the `shake-build/.db` directory which stores the Shake database. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). +To reset the new build system run the build script with `-B` flag. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). How to contribute From git at git.haskell.org Thu Oct 26 23:29:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add argsHashOracle for tracking changes in the build system. (196430d) Message-ID: <20171026232935.267D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/196430d4a0647e7258429e59caad0400151bb8ef/ghc >--------------------------------------------------------------- commit 196430d4a0647e7258429e59caad0400151bb8ef Author: Andrey Mokhov Date: Tue Jul 14 11:16:34 2015 +0100 Add argsHashOracle for tracking changes in the build system. >--------------------------------------------------------------- 196430d4a0647e7258429e59caad0400151bb8ef doc/meeting-16-June-2015.txt | 3 ++- src/Base.hs | 8 +++++++- src/Expression.hs | 16 ++++++++++++++++ src/Main.hs | 4 +--- src/Oracles.hs | 5 +---- src/Oracles/ArgsHash.hs | 22 ++++++++++++++++++++++ src/Oracles/Builder.hs | 8 +++++++- src/Package.hs | 10 ++++++++++ src/Rules.hs | 3 ++- src/Rules/Data.hs | 16 ++++++++++++---- src/Rules/Oracles.hs | 11 +++++++++++ src/Ways.hs | 13 +++++++++++-- 12 files changed, 102 insertions(+), 17 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 196430d4a0647e7258429e59caad0400151bb8ef From git at git.haskell.org Thu Oct 26 23:29:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move generators to a dedicated directory, and track their changes. (8c3022d) Message-ID: <20171026232935.52D963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c3022df66c07b7c1f78a59d60bb154868b591da/ghc >--------------------------------------------------------------- commit 8c3022df66c07b7c1f78a59d60bb154868b591da Author: Andrey Mokhov Date: Sat Dec 26 00:24:07 2015 +0000 Move generators to a dedicated directory, and track their changes. >--------------------------------------------------------------- 8c3022df66c07b7c1f78a59d60bb154868b591da shaking-up-ghc.cabal | 3 + src/Base.hs | 16 ++- src/Rules/Generate.hs | 166 +------------------------------- src/Rules/Generators/ConfigHs.hs | 102 ++++++++++++++++++++ src/Rules/Generators/GhcPkgVersionHs.hs | 17 ++++ src/Rules/Generators/PlatformH.hs | 57 +++++++++++ 6 files changed, 195 insertions(+), 166 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 8c3022df66c07b7c1f78a59d60bb154868b591da From git at git.haskell.org Thu Oct 26 23:29:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out build :: Target -> Action () into Rules/Util.hs. (5db0017) Message-ID: <20171026232938.8261B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5db0017b40d59894d5a6d4d5ba22196f55c47a48/ghc >--------------------------------------------------------------- commit 5db0017b40d59894d5a6d4d5ba22196f55c47a48 Author: Andrey Mokhov Date: Tue Jul 14 11:39:23 2015 +0100 Factor out build :: Target -> Action () into Rules/Util.hs. >--------------------------------------------------------------- 5db0017b40d59894d5a6d4d5ba22196f55c47a48 src/Rules/Data.hs | 21 +++++---------------- src/Rules/Util.hs | 19 +++++++++++++++++++ 2 files changed, 24 insertions(+), 16 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index dabccc1..f3c6064 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -9,11 +9,10 @@ import Package import Expression hiding (when, liftIO) import Oracles.Flag (when) import Oracles.Builder -import Oracles.ArgsHash -import Settings import Settings.GhcPkg import Settings.GhcCabal import Settings.TargetDirectory +import Rules.Util import Util import Ways @@ -35,27 +34,17 @@ buildPackageData target = ] &%> \_ -> do let configure = pkgPath pkg "configure" -- TODO: 1) how to automate this? 2) handle multiple files? - newTarget = target { getFile = path "package-data.mk" } + newTarget = target { getFile = path "package-data.mk" + , getWay = vanilla } -- TODO: think -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac when (doesFileExist $ configure <.> "ac") $ need [configure] - run' newTarget GhcCabal + build $ newTarget { getBuilder = GhcCabal } -- TODO: when (registerPackage settings) $ - run' newTarget (GhcPkg stage) + build $ newTarget { getBuilder = GhcPkg stage } postProcessPackageData $ path "package-data.mk" --- TODO: This should probably go to Oracles.Builder -run' :: Target -> Builder -> Action () -run' target builder = do - let finalTarget = target {getBuilder = builder, getWay = vanilla } - args <- interpret finalTarget settings - putColoured Green (show args) - -- The line below forces the rule to be rerun if the hash has changed - argsHash <- askArgsHash finalTarget - putColoured Yellow (show argsHash) - run builder args - -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- For example, get rid of diff --git a/src/Rules/Util.hs b/src/Rules/Util.hs new file mode 100644 index 0000000..8c9f1c4 --- /dev/null +++ b/src/Rules/Util.hs @@ -0,0 +1,19 @@ +module Rules.Util ( + build + ) where + +import Base +import Util +import Settings +import Expression +import Oracles.Builder +import Oracles.ArgsHash + +build :: Target -> Action () +build target = do + args <- interpret target settings + putColoured Green (show target) + putColoured Green (show args) + -- The line below forces the rule to be rerun if the args hash has changed + argsHash <- askArgsHash target + run (getBuilder target) args From git at git.haskell.org Thu Oct 26 23:29:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename GhcPkgVersionHs.hs to VersionHs.hs, refactor src/Rules/Generate.hs. (641eb2d) Message-ID: <20171026232938.B4CD73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/641eb2d33053d8011be52b68ef28e4c44ddf34e5/ghc >--------------------------------------------------------------- commit 641eb2d33053d8011be52b68ef28e4c44ddf34e5 Author: Andrey Mokhov Date: Sat Dec 26 02:03:09 2015 +0000 Rename GhcPkgVersionHs.hs to VersionHs.hs, refactor src/Rules/Generate.hs. >--------------------------------------------------------------- 641eb2d33053d8011be52b68ef28e4c44ddf34e5 shaking-up-ghc.cabal | 2 +- src/Rules/Generate.hs | 27 ++++++++++------------ .../{GhcPkgVersionHs.hs => VersionHs.hs} | 8 +++---- 3 files changed, 17 insertions(+), 20 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 3f09043..d233327 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -43,7 +43,7 @@ executable ghc-shake , Rules.Documentation , Rules.Generate , Rules.Generators.ConfigHs - , Rules.Generators.GhcPkgVersionHs + , Rules.Generators.VersionHs , Rules.Generators.PlatformH , Rules.Library , Rules.Oracles diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index fd22926..13d149e1 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -3,7 +3,7 @@ module Rules.Generate (generatePackageCode) where import Expression import GHC import Rules.Generators.ConfigHs -import Rules.Generators.GhcPkgVersionHs +import Rules.Generators.VersionHs import Rules.Generators.PlatformH import Oracles.ModuleFiles import Rules.Actions @@ -32,6 +32,10 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = primopsTxt = targetPath stage compiler -/- "build/primops.txt" platformH = targetPath stage compiler -/- "ghc_boot_platform.h" generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) + generate file expr = do + contents <- interpretPartial target expr + writeFileChanged file contents + putBuild $ "| Successfully generated '" ++ file ++ "'." in do generated ?> \file -> do let pattern = "//" ++ takeBaseName file <.> "*" @@ -60,23 +64,16 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = need [primopsTxt] build $ fullTarget target GenPrimopCode [primopsTxt] [file] - priority 2.0 $ buildPath -/- "Config.hs" %> \file -> do - contents <- interpretPartial target generateConfigHs - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." + priority 2.0 $ do + when (pkg == ghcPkg) $ buildPath -/- "Config.hs" %> \file -> do + generate file generateConfigHs - when (pkg == compiler) $ platformH %> \file -> do - contents <- interpretPartial target generatePlatformH - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." - - priority 2.0 $ when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do - contents <- interpretPartial target generateGhcPkgVersionHs - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." + generate file generateVersionHs + + when (pkg == compiler) $ platformH %> \file -> do + generate file generatePlatformH - priority 2.0 $ when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putBuild $ "| Successfully generated '" ++ file ++ "'." diff --git a/src/Rules/Generators/GhcPkgVersionHs.hs b/src/Rules/Generators/VersionHs.hs similarity index 66% rename from src/Rules/Generators/GhcPkgVersionHs.hs rename to src/Rules/Generators/VersionHs.hs index f29ee97..ea6501a 100644 --- a/src/Rules/Generators/GhcPkgVersionHs.hs +++ b/src/Rules/Generators/VersionHs.hs @@ -1,11 +1,11 @@ -module Rules.Generators.GhcPkgVersionHs (generateGhcPkgVersionHs) where +module Rules.Generators.VersionHs (generateVersionHs) where import Expression import Oracles -generateGhcPkgVersionHs :: Expr String -generateGhcPkgVersionHs = do - lift $ need [sourcePath -/- "Rules/Generators/GhcPkgVersionHs.hs"] +generateVersionHs :: Expr String +generateVersionHs = do + lift $ need [sourcePath -/- "Rules/Generators/VersionHs.hs"] projectVersion <- getSetting ProjectVersion targetOs <- getSetting TargetOs targetArch <- getSetting TargetArch From git at git.haskell.org Thu Oct 26 23:29:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactoring: Target is now defined in Target.hs, old Targets.hs is dropped. (92ef777) Message-ID: <20171026232942.1F6823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92ef7772b82fe25e48b4f43f752e09cd545d4751/ghc >--------------------------------------------------------------- commit 92ef7772b82fe25e48b4f43f752e09cd545d4751 Author: Andrey Mokhov Date: Tue Jul 14 13:56:52 2015 +0100 Refactoring: Target is now defined in Target.hs, old Targets.hs is dropped. >--------------------------------------------------------------- 92ef7772b82fe25e48b4f43f752e09cd545d4751 src/Expression.hs | 56 +++--------------------------- src/Settings.hs | 2 +- src/{Targets.hs => Settings/Default.hs} | 27 +++++++++++---- src/Settings/GhcCabal.hs | 3 +- src/Settings/Packages.hs | 15 +------- src/Settings/TargetDirectory.hs | 2 +- src/{UserSettings.hs => Settings/User.hs} | 7 ++-- src/Settings/Ways.hs | 2 +- src/Target.hs | 57 +++++++++++++++++++++++++++++++ 9 files changed, 90 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 92ef7772b82fe25e48b4f43f752e09cd545d4751 From git at git.haskell.org Thu Oct 26 23:29:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CcClangBackend and CcLlvmBackend settings. (27d45f1) Message-ID: <20171026232942.572CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27d45f1b334d4af9e8ff18c159c2effa7b45d0c0/ghc >--------------------------------------------------------------- commit 27d45f1b334d4af9e8ff18c159c2effa7b45d0c0 Author: Andrey Mokhov Date: Sat Dec 26 02:58:50 2015 +0000 Add CcClangBackend and CcLlvmBackend settings. >--------------------------------------------------------------- 27d45f1b334d4af9e8ff18c159c2effa7b45d0c0 cfg/system.config.in | 2 ++ src/Oracles/Config/Setting.hs | 4 ++++ 2 files changed, 6 insertions(+) diff --git a/cfg/system.config.in b/cfg/system.config.in index 6c21f6e..12ddeed 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -41,6 +41,8 @@ hscolour = @HSCOLOUR@ gcc-is-clang = @GccIsClang@ gcc-lt-46 = @GccLT46@ ar-supports-at-file = @ArSupportsAtFile@ +cc-llvm-backend = @CC_LLVM_BACKEND@ +cc-clang-backend = @CC_CLANG_BACKEND@ # Build options: #=============== diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 8f0b1df..81e2924 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -21,6 +21,8 @@ data Setting = BuildArch | BuildOs | BuildPlatform | BuildVendor + | CcClangBackend + | CcLlvmBackend | DynamicExtension | GhcMajorVersion | GhcMinorVersion @@ -60,6 +62,8 @@ setting key = askConfig $ case key of BuildOs -> "build-os" BuildPlatform -> "build-platform" BuildVendor -> "build-vendor" + CcClangBackend -> "cc-clang-backend" + CcLlvmBackend -> "cc-llvm-backend" DynamicExtension -> "dynamic-extension" GhcMajorVersion -> "ghc-major-version" GhcMinorVersion -> "ghc-minor-version" From git at git.haskell.org Thu Oct 26 23:29:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Settings to Args. Rename old Args defined in Base.hs to ArgList (to be dropped later). (da64dca) Message-ID: <20171026232946.253B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da64dcaf2d7d2ced1673ed5f57c8801a166215b1/ghc >--------------------------------------------------------------- commit da64dcaf2d7d2ced1673ed5f57c8801a166215b1 Author: Andrey Mokhov Date: Tue Jul 14 14:19:15 2015 +0100 Rename Settings to Args. Rename old Args defined in Base.hs to ArgList (to be dropped later). >--------------------------------------------------------------- da64dcaf2d7d2ced1673ed5f57c8801a166215b1 src/Base.hs | 24 ++++++++----------- src/Expression.hs | 18 +++++++-------- src/Oracles/ArgsHash.hs | 6 ++--- src/Rules.hs | 2 +- src/Rules/Data.hs | 4 ++-- src/Rules/Util.hs | 6 ++--- src/Settings.hs | 18 +++++++-------- src/Settings/GhcCabal.hs | 60 ++++++++++++++++++++++++------------------------ src/Settings/GhcPkg.hs | 10 ++++---- src/Settings/User.hs | 8 +++---- src/Settings/Util.hs | 56 +++++++++++++++++++++----------------------- src/Ways.hs | 41 ++++++++++++++++----------------- 12 files changed, 121 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 da64dcaf2d7d2ced1673ed5f57c8801a166215b1 From git at git.haskell.org Thu Oct 26 23:29:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate includes/ghcautoconf.h, refactor Rules/Generate.hs. (6b7b9cc) Message-ID: <20171026232946.5F8573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b7b9cc86e963a4bc200ff45fe16e26b72f372dd/ghc >--------------------------------------------------------------- commit 6b7b9cc86e963a4bc200ff45fe16e26b72f372dd Author: Andrey Mokhov Date: Sat Dec 26 03:00:03 2015 +0000 Generate includes/ghcautoconf.h, refactor Rules/Generate.hs. >--------------------------------------------------------------- 6b7b9cc86e963a4bc200ff45fe16e26b72f372dd src/Main.hs | 6 ++++-- src/Rules/Generate.hs | 33 +++++++++++++++++++++++++-------- src/Rules/Generators/GhcAutoconfH.hs | 34 ++++++++++++++++++++++++++++++++++ 3 files changed, 63 insertions(+), 10 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 7a0205d..0dc8d96 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,15 +2,17 @@ import Base import Rules import Rules.Cabal import Rules.Config +import Rules.Generate import Rules.Oracles main :: IO () main = shakeArgs options $ do - generateTargets -- see Rules - packageRules -- see Rules cabalRules -- see Rules.Cabal configRules -- see Rules.Config + generateTargets -- see Rules + generateRules -- see Rules.Generate oracleRules -- see Rules.Oracles + packageRules -- see Rules where options = shakeOptions { shakeFiles = shakeFilesPath diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 13d149e1..8f60dd0 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,8 +1,9 @@ -module Rules.Generate (generatePackageCode) where +module Rules.Generate (generatePackageCode, generateRules) where import Expression import GHC import Rules.Generators.ConfigHs +import Rules.Generators.GhcAutoconfH import Rules.Generators.VersionHs import Rules.Generators.PlatformH import Oracles.ModuleFiles @@ -25,6 +26,13 @@ determineBuilder file = fmap fst $ find (\(_, e) -> e == ext) knownGenerators where ext = takeExtension file +generate :: FilePath -> PartialTarget -> Expr String -> Action () +generate file target expr = do + contents <- interpretPartial target expr + writeFileChanged file contents + putBuild $ "| Successfully generated '" ++ file ++ "'." + + generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let path = targetPath stage pkg @@ -32,10 +40,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = primopsTxt = targetPath stage compiler -/- "build/primops.txt" platformH = targetPath stage compiler -/- "ghc_boot_platform.h" generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) - generate file expr = do - contents <- interpretPartial target expr - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." + file <~ gen = generate file target gen in do generated ?> \file -> do let pattern = "//" ++ takeBaseName file <.> "*" @@ -66,14 +71,26 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = priority 2.0 $ do when (pkg == ghcPkg) $ buildPath -/- "Config.hs" %> \file -> do - generate file generateConfigHs + file <~ generateConfigHs when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do - generate file generateVersionHs + file <~ generateVersionHs when (pkg == compiler) $ platformH %> \file -> do - generate file generatePlatformH + file <~ generatePlatformH when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putBuild $ "| Successfully generated '" ++ file ++ "'." + +generateRules :: Rules () +generateRules = do + "includes/ghcautoconf.h" <~ generateGhcAutoconfH + where + file <~ gen = file %> \out -> generate out fakeTarget gen + +-- TODO: Use the Types, Luke! (drop partial function) +fakeTarget :: PartialTarget +fakeTarget = PartialTarget (error "fakeTarget: unknown stage") + (error "fakeTarget: unknown package") + diff --git a/src/Rules/Generators/GhcAutoconfH.hs b/src/Rules/Generators/GhcAutoconfH.hs new file mode 100644 index 0000000..6d49603 --- /dev/null +++ b/src/Rules/Generators/GhcAutoconfH.hs @@ -0,0 +1,34 @@ +module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH) where + +import Expression +import Oracles + +-- TODO: change `mk/config.h` to `shake-build/cfg/config.h` +configH :: FilePath +configH = "mk/config.h" + +undefinePackage :: String -> String +undefinePackage s + | "#define PACKAGE_" `isPrefixOf` s + = "/* #undef " ++ takeWhile (/=' ') (drop 8 s) ++ " */" + | otherwise = s + +generateGhcAutoconfH :: Expr String +generateGhcAutoconfH = do + lift $ need [sourcePath -/- "Rules/Generators/GhcAutoconfH.hs"] + configHContents <- lift $ map undefinePackage <$> readFileLines configH + tablesNextToCode <- lift $ ghcEnableTablesNextToCode + ghcUnreg <- getFlag GhcUnregisterised + ccLlvmBackend <- getSetting CcLlvmBackend + ccClangBackend <- getSetting CcClangBackend + return . unlines $ + [ "#ifndef __GHCAUTOCONF_H__" + , "#define __GHCAUTOCONF_H__" ] + ++ configHContents ++ + [ "\n#define TABLES_NEXT_TO_CODE 1" | tablesNextToCode && not ghcUnreg ] + ++ + [ "\n#define llvm_CC_FLAVOR 1" | ccLlvmBackend == "1" ] + ++ + [ "\n#define clang_CC_FLAVOR 1" | ccClangBackend == "1" ] + ++ + [ "#endif /* __GHCAUTOCONF_H__ */" ] From git at git.haskell.org Thu Oct 26 23:29:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove unused code from Base and Oracles. (9737176) Message-ID: <20171026232949.BCF3F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9737176b107f64282a24c9ffd1a3a09fe1b92ed2/ghc >--------------------------------------------------------------- commit 9737176b107f64282a24c9ffd1a3a09fe1b92ed2 Author: Andrey Mokhov Date: Tue Jul 14 15:21:55 2015 +0100 Remove unused code from Base and Oracles. >--------------------------------------------------------------- 9737176b107f64282a24c9ffd1a3a09fe1b92ed2 src/Base.hs | 8 ++---- src/Expression.hs | 9 +++--- src/Oracles.hs | 11 ++------ src/Oracles/ArgsHash.hs | 2 +- src/Oracles/Builder.hs | 7 +++-- src/Oracles/Flag.hs | 72 +----------------------------------------------- src/Oracles/Option.hs | 40 ++------------------------- src/Rules.hs | 1 - src/Rules/Data.hs | 6 ++-- src/Rules/Oracles.hs | 2 +- src/Settings.hs | 4 +-- src/Settings/GhcCabal.hs | 2 +- src/Settings/GhcPkg.hs | 2 +- src/Settings/Util.hs | 7 ++--- src/Settings/Ways.hs | 2 +- src/Switches.hs | 11 ++++++++ src/Target.hs | 2 +- src/Ways.hs | 3 +- 18 files changed, 42 insertions(+), 149 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 9737176b107f64282a24c9ffd1a3a09fe1b92ed2 From git at git.haskell.org Thu Oct 26 23:29:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add config.h.in to shake-build/cfg. This file is needed for Rules.Generators.GhcAutoconfH. (47529e5) Message-ID: <20171026232949.F05743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47529e5ee25f3caa958f566f6eb85e62d86235ee/ghc >--------------------------------------------------------------- commit 47529e5ee25f3caa958f566f6eb85e62d86235ee Author: Andrey Mokhov Date: Sat Dec 26 03:01:26 2015 +0000 Add config.h.in to shake-build/cfg. This file is needed for Rules.Generators.GhcAutoconfH. >--------------------------------------------------------------- 47529e5ee25f3caa958f566f6eb85e62d86235ee cfg/config.h.in | 463 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 463 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 47529e5ee25f3caa958f566f6eb85e62d86235ee From git at git.haskell.org Thu Oct 26 23:29:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Distringuish partial Targets using type synonyms. (c319fbb) Message-ID: <20171026232953.2FA483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c319fbbf892b9a8a231676b3ecf9550d4b56a01b/ghc >--------------------------------------------------------------- commit c319fbbf892b9a8a231676b3ecf9550d4b56a01b Author: Andrey Mokhov Date: Tue Jul 14 16:07:42 2015 +0100 Distringuish partial Targets using type synonyms. >--------------------------------------------------------------- c319fbbf892b9a8a231676b3ecf9550d4b56a01b src/Oracles/ArgsHash.hs | 4 ++-- src/Rules/Data.hs | 10 ++++----- src/Rules/Package.hs | 2 +- src/Rules/Util.hs | 2 +- src/Settings/Packages.hs | 5 ++++- src/Target.hs | 55 ++++++++++++++++++++++++++++++++---------------- 6 files changed, 49 insertions(+), 29 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 1586b97..acb3e98 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -9,10 +9,10 @@ import Base import Settings import Expression -newtype ArgsHashKey = ArgsHashKey Target +newtype ArgsHashKey = ArgsHashKey FullTarget deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -askArgsHash :: Target -> Action Int +askArgsHash :: FullTarget -> Action Int askArgsHash = askOracle . ArgsHashKey -- Oracle for storing per-target argument list hashes diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 684cde6..2a40519 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -17,7 +17,7 @@ import Util import Ways -- Build package-data.mk by using GhcCabal to process pkgCabal file -buildPackageData :: Target -> Rules () +buildPackageData :: StagePackageTarget -> Rules () buildPackageData target = let stage = getStage target pkg = getPackage target @@ -33,16 +33,14 @@ buildPackageData target = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" - -- TODO: 1) how to automate this? 2) handle multiple files? - newTarget = target { getFile = path "package-data.mk" - , getWay = vanilla } -- TODO: think -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - build $ newTarget { getBuilder = GhcCabal } + -- TODO: 1) automate? 2) mutliple files 3) vanilla? + build $ fullTarget target (path "package-data.mk") GhcCabal vanilla -- TODO: when (registerPackage settings) $ - build $ newTarget { getBuilder = GhcPkg stage } + build $ fullTarget target (path "package-data.mk") (GhcPkg stage) vanilla postProcessPackageData $ path "package-data.mk" -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index a5a09dd..e316805 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -6,5 +6,5 @@ import Base import Rules.Data import Expression -buildPackage :: Target -> Rules () +buildPackage :: StagePackageTarget -> Rules () buildPackage = buildPackageData diff --git a/src/Rules/Util.hs b/src/Rules/Util.hs index a18e25e..6e1296e 100644 --- a/src/Rules/Util.hs +++ b/src/Rules/Util.hs @@ -9,7 +9,7 @@ import Expression import Oracles.Builder import Oracles.ArgsHash -build :: Target -> Action () +build :: FullTarget -> Action () build target = do argList <- interpret target args putColoured Green (show target) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 7eaa5d5..b1d98de 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -1,4 +1,5 @@ module Settings.Packages ( + module Settings.Default, packages, knownPackages ) where @@ -6,6 +7,7 @@ import Base import Package import Switches import Expression +import Settings.Default import Settings.User -- Combining default list of packages with user modifications @@ -25,7 +27,8 @@ packagesStage0 = mconcat packagesStage1 :: Packages packagesStage1 = mconcat - [ append [ array, base, bytestring, containers, deepseq, directory + [ packagesStage0 + , append [ array, base, bytestring, containers, deepseq, directory , filepath, ghcPrim, haskeline, integerLibrary, parallel , pretty, primitive, process, stm, templateHaskell, time ] , windowsHost ? append [win32] diff --git a/src/Target.hs b/src/Target.hs index 6161db7..0a0ed00 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,6 +1,7 @@ -{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} module Target ( - Target (..), stageTarget, stagePackageTarget + Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), + stageTarget, stagePackageTarget, fullTarget ) where import Base @@ -17,41 +18,59 @@ data Target = Target { getStage :: Stage, getPackage :: Package, - getBuilder :: Builder, getFile :: FilePath, -- TODO: handle multple files? + getBuilder :: Builder, getWay :: Way } deriving (Eq, Generic) --- Shows a target as "package:file at stage (builder, way)" -instance Show Target where - show target = show (getPackage target) - ++ ":" ++ show (getFile target) - ++ "@" ++ show (getStage target) - ++ " (" ++ show (getBuilder target) - ++ ", " ++ show (getWay target) ++ ")" +-- StageTarget is a Target whose field getStage is already assigned +type StageTarget = Target -stageTarget :: Stage -> Target +stageTarget :: Stage -> StageTarget stageTarget stage = Target { getStage = stage, getPackage = error "stageTarget: Package not set", - getBuilder = error "stageTarget: Builder not set", getFile = error "stageTarget: File not set", + getBuilder = error "stageTarget: Builder not set", getWay = error "stageTarget: Way not set" } -stagePackageTarget :: Stage -> Package -> Target +-- StagePackageTarget is a Target whose fields getStage and getPackage are +-- already assigned +type StagePackageTarget = Target + +stagePackageTarget :: Stage -> Package -> StagePackageTarget stagePackageTarget stage package = Target { getStage = stage, getPackage = package, - getBuilder = error "stagePackageTarget: Builder not set", getFile = error "stagePackageTarget: File not set", + getBuilder = error "stagePackageTarget: Builder not set", getWay = error "stagePackageTarget: Way not set" } --- Instances for storing Target in the Shake database -instance Binary Target -instance NFData Target -instance Hashable Target +-- FullTarget is a Target whose fields are all assigned +type FullTarget = Target + +fullTarget :: StagePackageTarget -> FilePath -> Builder -> Way -> FullTarget +fullTarget target file builder way = target + { + getFile = file, + getBuilder = builder, + getWay = way + } + +-- Shows a (full) target as "package:file at stage (builder, way)" +instance Show FullTarget where + show target = show (getPackage target) + ++ ":" ++ getFile target + ++ "@" ++ show (getStage target) + ++ " (" ++ show (getBuilder target) + ++ ", " ++ show (getWay target) ++ ")" + +-- Instances for storing FullTarget in the Shake database +instance Binary FullTarget +instance NFData FullTarget +instance Hashable FullTarget From git at git.haskell.org Thu Oct 26 23:29:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate includes/ghcplatform.h (8c32f2c) Message-ID: <20171026232953.664DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c32f2c931d68e1f847cfefb8f4d514886217873/ghc >--------------------------------------------------------------- commit 8c32f2c931d68e1f847cfefb8f4d514886217873 Author: Andrey Mokhov Date: Sat Dec 26 03:39:41 2015 +0000 Generate includes/ghcplatform.h >--------------------------------------------------------------- 8c32f2c931d68e1f847cfefb8f4d514886217873 shaking-up-ghc.cabal | 4 +- src/Rules/Generate.hs | 8 ++-- .../{PlatformH.hs => GhcBootPlatformH.hs} | 8 ++-- src/Rules/Generators/GhcPlatformH.hs | 55 ++++++++++++++++++++++ 4 files changed, 67 insertions(+), 8 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index d233327..1e0fbbf 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -43,8 +43,10 @@ executable ghc-shake , Rules.Documentation , Rules.Generate , Rules.Generators.ConfigHs + , Rules.Generators.GhcAutoconfH + , Rules.Generators.GhcBootPlatformH + , Rules.Generators.GhcPlatformH , Rules.Generators.VersionHs - , Rules.Generators.PlatformH , Rules.Library , Rules.Oracles , Rules.Package diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8f60dd0..f9c1e0b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -4,8 +4,9 @@ import Expression import GHC import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH +import Rules.Generators.GhcBootPlatformH +import Rules.Generators.GhcPlatformH import Rules.Generators.VersionHs -import Rules.Generators.PlatformH import Oracles.ModuleFiles import Rules.Actions import Rules.Resources (Resources) @@ -56,12 +57,12 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = whenM (doesFileExist srcBoot) $ copyFileChanged srcBoot $ file -<.> "hs-boot" + -- TODO: needing platformH is ugly and fragile when (pkg == compiler) $ primopsTxt %> \file -> do need [platformH, primopsSource] build $ fullTarget target HsCpp [primopsSource] [file] -- TODO: why different folders for generated files? - -- TODO: needing platformH is ugly and fragile fmap (buildPath -/-) [ "GHC/PrimopWrappers.hs" , "autogen/GHC/Prim.hs" @@ -77,7 +78,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = file <~ generateVersionHs when (pkg == compiler) $ platformH %> \file -> do - file <~ generatePlatformH + file <~ generateGhcBootPlatformH when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file @@ -86,6 +87,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = generateRules :: Rules () generateRules = do "includes/ghcautoconf.h" <~ generateGhcAutoconfH + "includes/ghcplatform.h" <~ generateGhcPlatformH where file <~ gen = file %> \out -> generate out fakeTarget gen diff --git a/src/Rules/Generators/PlatformH.hs b/src/Rules/Generators/GhcBootPlatformH.hs similarity index 91% rename from src/Rules/Generators/PlatformH.hs rename to src/Rules/Generators/GhcBootPlatformH.hs index cc29a1b..93b953b 100644 --- a/src/Rules/Generators/PlatformH.hs +++ b/src/Rules/Generators/GhcBootPlatformH.hs @@ -1,11 +1,11 @@ -module Rules.Generators.PlatformH (generatePlatformH) where +module Rules.Generators.GhcBootPlatformH (generateGhcBootPlatformH) where import Expression import Oracles -generatePlatformH :: Expr String -generatePlatformH = do - lift $ need [sourcePath -/- "Rules/Generators/PlatformH.hs"] +generateGhcBootPlatformH :: Expr String +generateGhcBootPlatformH = do + lift $ need [sourcePath -/- "Rules/Generators/GhcBootPlatformH.hs"] stage <- getStage let cppify = replaceEq '-' '_' . replaceEq '.' '_' chooseSetting x y = getSetting $ if stage == Stage0 then x else y diff --git a/src/Rules/Generators/GhcPlatformH.hs b/src/Rules/Generators/GhcPlatformH.hs new file mode 100644 index 0000000..2bdf5d4 --- /dev/null +++ b/src/Rules/Generators/GhcPlatformH.hs @@ -0,0 +1,55 @@ +module Rules.Generators.GhcPlatformH (generateGhcPlatformH) where + +import Expression +import Oracles + +generateGhcPlatformH :: Expr String +generateGhcPlatformH = do + lift $ need [sourcePath -/- "Rules/Generators/GhcPlatformH.hs"] + let cppify = replaceEq '-' '_' . replaceEq '.' '_' + hostPlatform <- getSetting HostPlatform + hostArch <- getSetting HostArch + hostOs <- getSetting HostOs + hostVendor <- getSetting HostVendor + targetPlatform <- getSetting TargetPlatform + targetArch <- getSetting TargetArch + targetOs <- getSetting TargetOs + targetVendor <- getSetting TargetVendor + ghcUnreg <- getFlag GhcUnregisterised + return . unlines $ + [ "#ifndef __GHCPLATFORM_H__" + , "#define __GHCPLATFORM_H__" + , "" + , "#define BuildPlatform_TYPE " ++ cppify hostPlatform + , "#define HostPlatform_TYPE " ++ cppify targetPlatform + , "" + , "#define " ++ cppify hostPlatform ++ "_BUILD 1" + , "#define " ++ cppify targetPlatform ++ "_HOST 1" + , "" + , "#define " ++ hostArch ++ "_BUILD_ARCH 1" + , "#define " ++ targetArch ++ "_HOST_ARCH 1" + , "#define BUILD_ARCH " ++ quote hostArch + , "#define HOST_ARCH " ++ quote targetArch + , "" + , "#define " ++ hostOs ++ "_BUILD_OS 1" + , "#define " ++ targetOs ++ "_HOST_OS 1" + , "#define BUILD_OS " ++ quote hostOs + , "#define HOST_OS " ++ quote targetOs + , "" + , "#define " ++ hostVendor ++ "_BUILD_VENDOR 1" + , "#define " ++ targetVendor ++ "_HOST_VENDOR 1" + , "#define BUILD_VENDOR " ++ quote hostVendor + , "#define HOST_VENDOR " ++ quote targetVendor + , "" + , "/* These TARGET macros are for backwards compatibility... DO NOT USE! */" + , "#define TargetPlatform_TYPE " ++ cppify targetPlatform + , "#define " ++ cppify targetPlatform ++ "_TARGET 1" + , "#define " ++ targetArch ++ "_TARGET_ARCH 1" + , "#define TARGET_ARCH " ++ quote targetArch + , "#define " ++ targetOs ++ "_TARGET_OS 1" + , "#define TARGET_OS " ++ quote targetOs + , "#define " ++ targetVendor ++ "_TARGET_VENDOR 1" ] + ++ + [ "#define UnregisterisedCompiler 1" | ghcUnreg ] + ++ + [ "\n#endif /* __GHCPLATFORM_H__ */" ] From git at git.haskell.org Thu Oct 26 23:29:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Oracles/Builder.hs. (772ea96) Message-ID: <20171026232957.337C53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/772ea960e295c90f0052edc7ba0c0ec6a26d33c3/ghc >--------------------------------------------------------------- commit 772ea960e295c90f0052edc7ba0c0ec6a26d33c3 Author: Andrey Mokhov Date: Tue Jul 14 23:27:54 2015 +0100 Refactor Oracles/Builder.hs. >--------------------------------------------------------------- 772ea960e295c90f0052edc7ba0c0ec6a26d33c3 src/Builder.hs | 92 ++++++++++++++++++++++++++++ src/Expression.hs | 4 +- src/Oracles/Builder.hs | 154 ----------------------------------------------- src/Rules/Actions.hs | 62 +++++++++++++++++++ src/Rules/Data.hs | 4 +- src/Rules/Util.hs | 19 ------ src/Settings/GhcCabal.hs | 43 +++++++++---- src/Settings/GhcPkg.hs | 2 +- src/Settings/Util.hs | 7 +-- src/Target.hs | 2 +- 10 files changed, 193 insertions(+), 196 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 772ea960e295c90f0052edc7ba0c0ec6a26d33c3 From git at git.haskell.org Thu Oct 26 23:29:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:29:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add "--template" and "-I" arguments to hsc2HsArgs (efbe44f) Message-ID: <20171026232957.637C03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efbe44f845b88e3885e1c63adcf66c57c5af1f77/ghc >--------------------------------------------------------------- commit efbe44f845b88e3885e1c63adcf66c57c5af1f77 Author: Moritz Angermann Date: Sat Dec 26 17:38:05 2015 +0800 Add "--template" and "-I" arguments to hsc2HsArgs This should fix #35. To have this fully working, #44 needs to be solved as well. >--------------------------------------------------------------- efbe44f845b88e3885e1c63adcf66c57c5af1f77 src/Settings/Builders/Hsc2Hs.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 0e31b4f..0c6172d 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -13,6 +13,7 @@ hsc2HsArgs = builder Hsc2Hs ? do gmpDirs <- getSettingList GmpIncludeDirs cFlags <- getCFlags lFlags <- getLFlags + top <- getSetting GhcSourcePath hArch <- getSetting HostArch hOs <- getSetting HostOs tArch <- getSetting TargetArch @@ -32,6 +33,8 @@ hsc2HsArgs = builder Hsc2Hs ? do , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) , arg ("--cflag=-D__GLASGOW_HASKELL__=" ++ version) + , arg $ "--template=" ++ top -/- "inplace/lib/template-hsc.h" + , arg $ "-I" ++ top -/- "inplace/lib/include/" , arg =<< getInput , arg "-o", arg =<< getOutput ] From git at git.haskell.org Thu Oct 26 23:30:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up Base. (9bde7d8) Message-ID: <20171026233000.B2C453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9bde7d8668019ed08561c701e3f2ba61ac173d6e/ghc >--------------------------------------------------------------- commit 9bde7d8668019ed08561c701e3f2ba61ac173d6e Author: Andrey Mokhov Date: Tue Jul 14 23:49:13 2015 +0100 Clean up Base. >--------------------------------------------------------------- 9bde7d8668019ed08561c701e3f2ba61ac173d6e src/Base.hs | 13 ------------- 1 file changed, 13 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 026f211..97a22d5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -10,7 +10,6 @@ module Base ( Stage (..), Arg, ArgList, ShowArg (..), ShowArgs (..), - filterOut, productArgs, concatArgs ) where @@ -56,21 +55,9 @@ class ShowArgs a where instance ShowArgs [String] where showArgs = return -instance ShowArgs [Arg] where - showArgs = sequence - -instance ShowArgs [ArgList] where - showArgs = mconcat - instance ShowArgs a => ShowArgs (Action a) where showArgs = (showArgs =<<) --- Filter out given arg(s) from a collection -filterOut :: ShowArgs a => ArgList -> a -> ArgList -filterOut as exclude = do - exclude' <- showArgs exclude - filter (`notElem` exclude') <$> as - -- Generate a cross product collection of two argument collections -- Example: productArgs ["-a", "-b"] "c" = args ["-a", "c", "-b", "c"] productArgs :: (ShowArgs a, ShowArgs b) => a -> b -> ArgList From git at git.haskell.org Thu Oct 26 23:30:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds OS X Section to Readme (1046838) Message-ID: <20171026233000.E5FB43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1046838060dfdacbdf7cdf8e2994edf71e5c0a5f/ghc >--------------------------------------------------------------- commit 1046838060dfdacbdf7cdf8e2994edf71e5c0a5f Author: Moritz Angermann Date: Sat Dec 26 18:06:27 2015 +0800 Adds OS X Section to Readme Still fails at #47 >--------------------------------------------------------------- 1046838060dfdacbdf7cdf8e2994edf71e5c0a5f README.md | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/README.md b/README.md index 6d27b25..9844bf6 100644 --- a/README.md +++ b/README.md @@ -48,6 +48,22 @@ $ shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. +### Mac OS X + +```bash +git clone git://git.haskell.org/ghc +cd ghc +git submodule update --init +git clone git://github.com/snowleopard/shaking-up-ghc shake-build +./boot +./configure --with-gcc=$(which clang) # See #26 +./shake-build/build.sh includes/ghcautoconf.h # See #48 +./shake-build/build.sh includes/ghcplatform.h # See #48 +cp utils/hsc2hs/template-hsc.h inplace/lib/template-hsc.h # See #44 +./shake-build/build.sh +``` + +See the Linux section for running in a Cabal sandbox. ### Resetting the build From git at git.haskell.org Thu Oct 26 23:30:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Ways.hs => Way.hs and refactor it. (3726211) Message-ID: <20171026233004.347BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37262111fee905d4d0312c02f80ae3abd8250566/ghc >--------------------------------------------------------------- commit 37262111fee905d4d0312c02f80ae3abd8250566 Author: Andrey Mokhov Date: Wed Jul 15 20:30:52 2015 +0200 Rename Ways.hs => Way.hs and refactor it. >--------------------------------------------------------------- 37262111fee905d4d0312c02f80ae3abd8250566 src/Base.hs | 8 +-- src/Builder.hs | 2 +- src/Expression.hs | 2 +- src/Package.hs | 10 +-- src/Rules/Data.hs | 2 +- src/Settings/GhcCabal.hs | 2 +- src/Settings/Util.hs | 15 +++++ src/Settings/Ways.hs | 2 +- src/Target.hs | 4 +- src/Way.hs | 138 +++++++++++++++++++++++++++++++++++++++ src/Ways.hs | 165 ----------------------------------------------- 11 files changed, 169 insertions(+), 181 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 37262111fee905d4d0312c02f80ae3abd8250566 From git at git.haskell.org Thu Oct 26 23:30:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #46 from angerman/feature/fix-hsc2hs (9d1952f) Message-ID: <20171026233004.5820B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d1952faa145acb44725465cf738dd9448e0892e/ghc >--------------------------------------------------------------- commit 9d1952faa145acb44725465cf738dd9448e0892e Merge: 8c32f2c efbe44f Author: Andrey Mokhov Date: Sat Dec 26 11:50:27 2015 +0000 Merge pull request #46 from angerman/feature/fix-hsc2hs Add "--template" and "-I" arguments to hsc2HsArgs >--------------------------------------------------------------- 9d1952faa145acb44725465cf738dd9448e0892e src/Settings/Builders/Hsc2Hs.hs | 3 +++ 1 file changed, 3 insertions(+) From git at git.haskell.org Thu Oct 26 23:30:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support to multiple files in Target, implement registerPackage predicate. (c41e156) Message-ID: <20171026233007.98B8B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c41e156c6bee670112d50825040ccc2ebc56a78e/ghc >--------------------------------------------------------------- commit c41e156c6bee670112d50825040ccc2ebc56a78e Author: Andrey Mokhov Date: Wed Jul 15 23:44:30 2015 +0200 Add support to multiple files in Target, implement registerPackage predicate. >--------------------------------------------------------------- c41e156c6bee670112d50825040ccc2ebc56a78e src/Expression.hs | 2 +- src/Rules/Actions.hs | 7 ++++++- src/Rules/Data.hs | 10 ++++------ src/Switches.hs | 7 ++++++- src/Target.hs | 30 ++++++++++++++++++++---------- 5 files changed, 37 insertions(+), 19 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 2f8ea4b..0ee8034 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -140,7 +140,7 @@ builder :: Builder -> Predicate builder b = liftM (b ==) (asks getBuilder) file :: FilePattern -> Predicate -file f = liftM (f ?==) (asks getFile) +file f = liftM (any (f ?==)) (asks getFiles) way :: Way -> Predicate way w = liftM (w ==) (asks getWay) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9010647..d29d486 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,5 +1,5 @@ module Rules.Actions ( - build, run, verboseRun, + build, buildWhen, run, verboseRun, ) where import Base @@ -21,6 +21,11 @@ build target = do argsHash <- askArgsHash target run (getBuilder target) argList +buildWhen :: Predicate -> FullTarget -> Action () +buildWhen predicate target = do + bool <- interpretExpr target predicate + when bool $ build target + -- Run the builder with a given collection of arguments verboseRun :: Builder -> [String] -> Action () verboseRun builder args = do diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index beadd7e..eb34b65 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -4,10 +4,10 @@ module Rules.Data ( cabalArgs, ghcPkgArgs, buildPackageData ) where -import Way import Base import Package import Builder +import Switches import Expression import Control.Monad.Extra import Settings.GhcPkg @@ -31,16 +31,14 @@ buildPackageData target = , "build" "autogen" "cabal_macros.h" -- TODO: Is this needed? Also check out Paths_cpsa.hs. -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" - ] &%> \_ -> do + ] &%> \files -> do let configure = pkgPath pkg "configure" -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - -- TODO: 1) automate? 2) mutliple files 3) vanilla? - build $ fullTarget target (path "package-data.mk") GhcCabal vanilla - -- TODO: when (registerPackage settings) $ - build $ fullTarget target (path "package-data.mk") (GhcPkg stage) vanilla + build $ fullTarget target files GhcCabal + buildWhen registerPackage $ fullTarget target files (GhcPkg stage) postProcessPackageData $ path "package-data.mk" -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: diff --git a/src/Switches.hs b/src/Switches.hs index ce03ade..8ab2de2 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -5,7 +5,8 @@ module Switches ( targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, platformSupportsSharedLibs, crossCompiling, - gccIsClang, gccLt46, windowsHost, notWindowsHost + gccIsClang, gccLt46, windowsHost, notWindowsHost, + registerPackage ) where import Base @@ -91,6 +92,10 @@ windowsHost = configKeyValues "host-os-cpp" ["mingw32", "cygwin32"] notWindowsHost :: Predicate notWindowsHost = liftM not windowsHost +-- TODO: Actually, we don't register compiler in some circumstances -- fix. +registerPackage :: Predicate +registerPackage = return True + -- splitObjects :: Stage -> Condition -- splitObjects stage = do -- arch <- showArg TargetArch diff --git a/src/Target.hs b/src/Target.hs index 198cffc..6b02af9 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} module Target ( Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), - stageTarget, stagePackageTarget, fullTarget + stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay ) where import Way @@ -18,7 +18,7 @@ data Target = Target { getStage :: Stage, getPackage :: Package, - getFile :: FilePath, -- TODO: handle multple files? + getFiles :: [FilePath], getBuilder :: Builder, getWay :: Way } @@ -32,9 +32,9 @@ stageTarget stage = Target { getStage = stage, getPackage = error "stageTarget: Package not set", - getFile = error "stageTarget: File not set", + getFiles = error "stageTarget: Files not set", getBuilder = error "stageTarget: Builder not set", - getWay = error "stageTarget: Way not set" + getWay = vanilla -- most targets are built only one way (vanilla) } -- StagePackageTarget is a Target whose fields getStage and getPackage are @@ -46,18 +46,28 @@ stagePackageTarget stage package = Target { getStage = stage, getPackage = package, - getFile = error "stagePackageTarget: File not set", + getFiles = error "stagePackageTarget: Files not set", getBuilder = error "stagePackageTarget: Builder not set", - getWay = error "stagePackageTarget: Way not set" + getWay = vanilla } -- FullTarget is a Target whose fields are all assigned type FullTarget = Target -fullTarget :: StagePackageTarget -> FilePath -> Builder -> Way -> FullTarget -fullTarget target file builder way = target +-- Most targets are built only one way, vanilla, hence we set it by default. +fullTarget :: StagePackageTarget -> [FilePath] -> Builder -> FullTarget +fullTarget target files builder = target { - getFile = file, + getFiles = files, + getBuilder = builder, + getWay = vanilla + } + +-- Use this function to be explicit about build the way. +fullTargetWithWay :: StagePackageTarget -> [FilePath] -> Builder -> Way -> FullTarget +fullTargetWithWay target files builder way = target + { + getFiles = files, getBuilder = builder, getWay = way } @@ -65,7 +75,7 @@ fullTarget target file builder way = target -- Shows a (full) target as "package:file at stage (builder, way)" instance Show FullTarget where show target = show (getPackage target) - ++ ":" ++ getFile target + ++ ":" ++ show (getFiles target) ++ "@" ++ show (getStage target) ++ " (" ++ show (getBuilder target) ++ ", " ++ show (getWay target) ++ ")" From git at git.haskell.org Thu Oct 26 23:30:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #49 from angerman/feature/readme-osx (eb02aa4) Message-ID: <20171026233007.D93823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eb02aa4ae236230b9aa83e18017be779371bdbc7/ghc >--------------------------------------------------------------- commit eb02aa4ae236230b9aa83e18017be779371bdbc7 Merge: 9d1952f 1046838 Author: Andrey Mokhov Date: Sat Dec 26 11:53:40 2015 +0000 Merge pull request #49 from angerman/feature/readme-osx Feature/readme osx >--------------------------------------------------------------- eb02aa4ae236230b9aa83e18017be779371bdbc7 README.md | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) From git at git.haskell.org Thu Oct 26 23:30:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Settings.hs to Settings/Args.hs. (d9b03d3) Message-ID: <20171026233011.561CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9b03d37d49ecbd2db59fd242692727488ef92dd/ghc >--------------------------------------------------------------- commit d9b03d37d49ecbd2db59fd242692727488ef92dd Author: Andrey Mokhov Date: Wed Jul 15 23:49:10 2015 +0200 Rename Settings.hs to Settings/Args.hs. >--------------------------------------------------------------- d9b03d37d49ecbd2db59fd242692727488ef92dd src/Oracles/ArgsHash.hs | 4 ++-- src/Rules/Actions.hs | 2 +- src/{Settings.hs => Settings/Args.hs} | 2 +- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index acb3e98..b930ef6 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -4,10 +4,10 @@ module Oracles.ArgsHash ( ArgsHashKey (..), askArgsHash, argsHashOracle ) where -import Development.Shake.Classes import Base -import Settings import Expression +import Settings.Args +import Development.Shake.Classes newtype ArgsHashKey = ArgsHashKey FullTarget deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d29d486..e4688dc 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -5,8 +5,8 @@ module Rules.Actions ( import Base import Util import Builder -import Settings import Expression +import Settings.Args import Oracles.ArgsHash -- Build a given target using an appropriate builder. Force a rebuilt if the diff --git a/src/Settings.hs b/src/Settings/Args.hs similarity index 92% rename from src/Settings.hs rename to src/Settings/Args.hs index 196f4d7..cc7a22c 100644 --- a/src/Settings.hs +++ b/src/Settings/Args.hs @@ -1,4 +1,4 @@ -module Settings ( +module Settings.Args ( args ) where From git at git.haskell.org Thu Oct 26 23:30:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up Windows script (8ed92e9) Message-ID: <20171026233011.9F6F43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ed92e90674c9078ebe08fdd5f1edd758f48f7f7/ghc >--------------------------------------------------------------- commit 8ed92e90674c9078ebe08fdd5f1edd758f48f7f7 Author: Andrey Mokhov Date: Sat Dec 26 12:33:59 2015 +0000 Clean up Windows script >--------------------------------------------------------------- 8ed92e90674c9078ebe08fdd5f1edd758f48f7f7 README.md | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 9844bf6..a93ed9a 100644 --- a/README.md +++ b/README.md @@ -38,13 +38,13 @@ Now you have a couple of options: ### Windows -``` -$ git clone --recursive git://git.haskell.org/ghc.git -$ cd ghc -$ git clone git://github.com/snowleopard/shaking-up-ghc shake-build -$ ./boot -$ ./configure --enable-tarballs-autodownload -$ shake-build/build.bat +```bash +git clone --recursive git://git.haskell.org/ghc.git +cd ghc +git clone git://github.com/snowleopard/shaking-up-ghc shake-build +./boot +./configure --enable-tarballs-autodownload +shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. From git at git.haskell.org Thu Oct 26 23:30:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement argPath that unifies the path argument. (5a4a443) Message-ID: <20171026233015.3C5093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a4a443af1fabc548894ca9d3f75702a4b08cf21/ghc >--------------------------------------------------------------- commit 5a4a443af1fabc548894ca9d3f75702a4b08cf21 Author: Andrey Mokhov Date: Wed Jul 15 23:55:46 2015 +0200 Implement argPath that unifies the path argument. >--------------------------------------------------------------- 5a4a443af1fabc548894ca9d3f75702a4b08cf21 src/Settings/GhcCabal.hs | 4 ++-- src/Settings/GhcPkg.hs | 2 +- src/Settings/Util.hs | 12 +++++++----- 3 files changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 7281b9f..34984b7 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -21,8 +21,8 @@ cabalArgs = builder GhcCabal ? do stage <- asks getStage pkg <- asks getPackage mconcat [ arg "configure" - , arg $ pkgPath pkg - , arg $ targetDirectory stage pkg + , argPath $ pkgPath pkg + , argPath $ targetDirectory stage pkg , dllArgs , with $ Ghc stage , with $ GhcPkg stage diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index 9bf85e7..a75eab7 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -18,4 +18,4 @@ ghcPkgArgs = do [ arg "update" , arg "--force" , stage0 ? bootPackageDbArgs - , arg $ targetPath stage pkg "inplace-pkg-config" ] + , argPath $ targetPath stage pkg "inplace-pkg-config" ] diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index b529376..9ee4986 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -1,6 +1,6 @@ module Settings.Util ( -- Primitive settings elements - arg, argM, + arg, argPath, argM, argConfig, argStagedConfig, argConfigList, argStagedConfigList, appendCcArgs, -- argBuilderPath, argStagedBuilderPath, @@ -12,14 +12,19 @@ module Settings.Util ( ) where import Base +import Util import Builder import Oracles.Base import Expression --- A single argument +-- A single argument. arg :: String -> Args arg = append . return +-- A single path argument. The path gets unified. +argPath :: String -> Args +argPath = append . return . unifyPath + argM :: Action String -> Args argM = appendM . fmap return @@ -50,9 +55,6 @@ appendCcArgs xs = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" xs , builder GhcCabal ? appendSub "--gcc-options" xs ] - - - -- packageData :: Arity -> String -> Args -- packageData arity key = -- return $ EnvironmentParameter $ PackageData arity key Nothing Nothing From git at git.haskell.org Thu Oct 26 23:30:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add IRC to README.md (bf060f8) Message-ID: <20171026233015.519C23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf060f88c69ebdfb2c9a673a101b2b18c4f3c3e5/ghc >--------------------------------------------------------------- commit bf060f88c69ebdfb2c9a673a101b2b18c4f3c3e5 Author: Moritz Angermann Date: Sat Dec 26 22:17:12 2015 +0800 Add IRC to README.md add's a link (to what ever systems support `irc://`), everyone else, will hopefully know what to do :) >--------------------------------------------------------------- bf060f88c69ebdfb2c9a673a101b2b18c4f3c3e5 README.md | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/README.md b/README.md index a93ed9a..ca1e5fb 100644 --- a/README.md +++ b/README.md @@ -9,9 +9,7 @@ on the [wiki page][ghc-shake-wiki] and in this [blog post][shake-blog-post]. This is supposed to go into the `shake-build` directory of the GHC source tree. - - - +[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc) Trying it --------- From git at git.haskell.org Thu Oct 26 23:30:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #51 from snowleopard/angerman-patch-1 (ec44701) Message-ID: <20171026233018.BF59B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ec447012e50b62b6f96dde134514505ed9795156/ghc >--------------------------------------------------------------- commit ec447012e50b62b6f96dde134514505ed9795156 Merge: 8ed92e9 bf060f8 Author: Andrey Mokhov Date: Sat Dec 26 14:23:16 2015 +0000 Merge pull request #51 from snowleopard/angerman-patch-1 Add IRC to README.md >--------------------------------------------------------------- ec447012e50b62b6f96dde134514505ed9795156 README.md | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:30:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove user.config file, rename default.config to system.config. (a8cfbde) Message-ID: <20171026233018.C93C03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8cfbde5e0fc9df532d739815a28ac2e022eff0d/ghc >--------------------------------------------------------------- commit a8cfbde5e0fc9df532d739815a28ac2e022eff0d Author: Andrey Mokhov Date: Sun Jul 19 00:15:45 2015 +0100 Remove user.config file, rename default.config to system.config. >--------------------------------------------------------------- a8cfbde5e0fc9df532d739815a28ac2e022eff0d .gitignore | 2 +- cfg/configure.ac | 2 +- cfg/{default.config.in => system.config.in} | 0 cfg/user.config | 4 ---- src/Config.hs | 4 ++-- src/Oracles.hs | 37 ++++++++--------------------- src/Oracles/Option.hs | 4 ++-- 7 files changed, 16 insertions(+), 37 deletions(-) diff --git a/.gitignore b/.gitignore index dad3a3c..94b9664 100644 --- a/.gitignore +++ b/.gitignore @@ -2,5 +2,5 @@ *.hi _shake/ _build/ -cfg/default.config +cfg/system.config arg/*/*.txt diff --git a/cfg/configure.ac b/cfg/configure.ac index 125fd49..687eac7 100644 --- a/cfg/configure.ac +++ b/cfg/configure.ac @@ -978,7 +978,7 @@ if grep ' ' compiler/ghc.cabal.in 2>&1 >/dev/null; then AC_MSG_ERROR([compiler/ghc.cabal.in contains tab characters; please remove them]) fi -AC_CONFIG_FILES([shake/cfg/default.config mk/config.mk mk/install.mk mk/project.mk compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal settings docs/users_guide/ug-book.xml docs/users_guide/ug-ent.xml docs/index.html libraries/prologue.txt distrib/configure.ac]) +AC_CONFIG_FILES([shake/cfg/system.config mk/config.mk mk/install.mk mk/project.mk compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal settings docs/users_guide/ug-book.xml docs/users_guide/ug-ent.xml docs/index.html libraries/prologue.txt distrib/configure.ac]) AC_OUTPUT # We got caught by diff --git a/cfg/default.config.in b/cfg/system.config.in similarity index 100% rename from cfg/default.config.in rename to cfg/system.config.in diff --git a/cfg/user.config b/cfg/user.config deleted file mode 100644 index b72c5b4..0000000 --- a/cfg/user.config +++ /dev/null @@ -1,4 +0,0 @@ -# Override default settings (stored in default.config file): -#=========================================================== - -lax-dependencies = YES diff --git a/src/Config.hs b/src/Config.hs index 1a4ef9a..0dc67a2 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -17,7 +17,7 @@ autoconfRules = do configureRules :: Rules () configureRules = do - cfgPath "default.config" %> \out -> do - need [cfgPath "default.config.in", "configure"] + cfgPath "system.config" %> \out -> do + need [cfgPath "system.config.in", "configure"] putColoured White "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' diff --git a/src/Oracles.hs b/src/Oracles.hs index e6e31f9..cd8c879 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -6,45 +6,25 @@ module Oracles ( import Development.Shake.Config import Development.Shake.Util import qualified Data.HashMap.Strict as M --- TODO: get rid of Bifunctor dependency -import Data.Bifunctor import Base import Util import Config +import Control.Monad.Extra import Oracles.Base import Oracles.PackageData -import Control.Monad.Extra import Oracles.DependencyList -defaultConfig, userConfig :: FilePath -defaultConfig = cfgPath "default.config" -userConfig = cfgPath "user.config" - -- Oracle for configuration files configOracle :: Rules () configOracle = do + let configFile = cfgPath "system.config" cfg <- newCache $ \() -> do - unlessM (doesFileExist $ defaultConfig <.> "in") $ - redError_ $ "\nDefault configuration file '" - ++ (defaultConfig <.> "in") + unlessM (doesFileExist $ configFile <.> "in") $ + redError_ $ "\nConfiguration file '" ++ (configFile <.> "in") ++ "' is missing; unwilling to proceed." - need [defaultConfig] - putOracle $ "Reading " ++ unifyPath defaultConfig ++ "..." - cfgDefault <- liftIO $ readConfigFile defaultConfig - existsUser <- doesFileExist userConfig - cfgUser <- if existsUser - then do - putOracle $ "Reading " - ++ unifyPath userConfig ++ "..." - liftIO $ readConfigFile userConfig - else do - putColoured Red $ - "\nUser defined configuration file '" - ++ userConfig ++ "' is missing; " - ++ "proceeding with default configuration.\n" - return M.empty - putColoured Green $ "Finished processing configuration files." - return $ cfgUser `M.union` cfgDefault + need [configFile] + putOracle $ "Reading " ++ unifyPath configFile ++ "..." + liftIO $ readConfigFile configFile addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () return () @@ -59,6 +39,9 @@ packageDataOracle = do M.lookup key <$> pkgData (unifyPath file) return () +bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) +bimap f g (x, y) = (f x, g y) + -- Oracle for 'path/dist/*.deps' files dependencyOracle :: Rules () dependencyOracle = do diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index f1a35e2..ff0c5fc 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -5,8 +5,8 @@ module Oracles.Option ( import Base import Oracles.Base --- For each Option the files {default.config, user.config} contain --- a line of the form 'target-os = mingw32'. +-- For each Option the file default.config contains a line of the +-- form 'target-os = mingw32'. -- (showArg TargetOs) is an action that consults the config files -- and returns "mingw32". -- From git at git.haskell.org Thu Oct 26 23:30:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor and rename Oracles/Option.hs. (272f100) Message-ID: <20171026233022.ECF8D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7/ghc >--------------------------------------------------------------- commit 272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7 Author: Andrey Mokhov Date: Sun Jul 19 00:45:35 2015 +0100 Refactor and rename Oracles/Option.hs. >--------------------------------------------------------------- 272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7 src/Base.hs | 3 +-- src/Builder.hs | 3 ++- src/Expression.hs | 1 + src/Oracles.hs | 1 + src/Oracles/Option.hs | 61 ---------------------------------------------- src/Oracles/PackageData.hs | 1 + src/Oracles/Setting.hs | 61 ++++++++++++++++++++++++++++++++++++++++++++++ src/Settings/GhcCabal.hs | 5 ++-- src/Way.hs | 18 +++++++------- 9 files changed, 79 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 272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7 From git at git.haskell.org Thu Oct 26 23:30:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update LICENSE (e4e72d8) Message-ID: <20171026233022.ED5CE3A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4e72d888288f7fb40c94fc13bc6e3a7d9d3bd52/ghc >--------------------------------------------------------------- commit e4e72d888288f7fb40c94fc13bc6e3a7d9d3bd52 Author: Moritz Angermann Date: Sat Dec 26 22:23:31 2015 +0800 Update LICENSE Be explicit about the license. Prevent others from having to lookup the license that matches this text. >--------------------------------------------------------------- e4e72d888288f7fb40c94fc13bc6e3a7d9d3bd52 LICENSE | 2 ++ 1 file changed, 2 insertions(+) diff --git a/LICENSE b/LICENSE index a78df02..9ee6e34 100644 --- a/LICENSE +++ b/LICENSE @@ -1,3 +1,5 @@ +BSD License + Copyright (c) 2015, Andrey Mokhov All rights reserved. From git at git.haskell.org Thu Oct 26 23:30:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #52 from snowleopard/angerman-patch-2 (b6f3045) Message-ID: <20171026233027.07D2D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6f30456f0c67d0e9393ad4a42f1b99126899e70/ghc >--------------------------------------------------------------- commit b6f30456f0c67d0e9393ad4a42f1b99126899e70 Merge: ec44701 e4e72d8 Author: Andrey Mokhov Date: Sat Dec 26 14:25:47 2015 +0000 Merge pull request #52 from snowleopard/angerman-patch-2 Update LICENSE >--------------------------------------------------------------- b6f30456f0c67d0e9393ad4a42f1b99126899e70 LICENSE | 2 ++ 1 file changed, 2 insertions(+) From git at git.haskell.org Thu Oct 26 23:30:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove Base.hs, move Stage definition to Stage.hs. (03f90e7) Message-ID: <20171026233027.04E4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03f90e74e6d472f26f22baef563c38d088dadb8f/ghc >--------------------------------------------------------------- commit 03f90e74e6d472f26f22baef563c38d088dadb8f Author: Andrey Mokhov Date: Sun Jul 19 01:26:22 2015 +0100 Remove Base.hs, move Stage definition to Stage.hs. >--------------------------------------------------------------- 03f90e74e6d472f26f22baef563c38d088dadb8f src/Base.hs | 74 ---------------------------------- src/Builder.hs | 4 +- src/Config.hs | 3 +- src/Expression.hs | 5 ++- src/Main.hs | 2 +- src/Oracles.hs | 13 +++--- src/Oracles/ArgsHash.hs | 3 +- src/Oracles/Base.hs | 2 +- src/Oracles/DependencyList.hs | 11 ++--- src/Oracles/Flag.hs | 2 +- src/Oracles/PackageData.hs | 89 ++++++++++++++++++++--------------------- src/Oracles/Setting.hs | 17 ++++---- src/Package.hs | 3 +- src/Rules.hs | 5 ++- src/Rules/Actions.hs | 2 +- src/Rules/Data.hs | 8 ++-- src/Rules/Oracles.hs | 3 +- src/Rules/Package.hs | 2 +- src/Settings/Args.hs | 3 +- src/Settings/Default.hs | 2 +- src/Settings/GhcCabal.hs | 7 +++- src/Settings/GhcPkg.hs | 2 +- src/Settings/Packages.hs | 3 +- src/Settings/TargetDirectory.hs | 3 +- src/Settings/User.hs | 4 +- src/Settings/Util.hs | 3 +- src/Settings/Ways.hs | 2 +- src/Stage.hs | 17 ++++++++ src/Switches.hs | 2 +- src/Target.hs | 2 +- src/Util.hs | 7 ++-- src/Way.hs | 3 +- 32 files changed, 135 insertions(+), 173 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 03f90e74e6d472f26f22baef563c38d088dadb8f From git at git.haskell.org Thu Oct 26 23:30:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to Config.hs (#47). (44d81b0) Message-ID: <20171026233030.6F8413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44d81b0961073c172630fd52b76985fa9a6601b3/ghc >--------------------------------------------------------------- commit 44d81b0961073c172630fd52b76985fa9a6601b3 Author: Andrey Mokhov Date: Sat Dec 26 14:42:49 2015 +0000 Fix path to Config.hs (#47). >--------------------------------------------------------------- 44d81b0961073c172630fd52b76985fa9a6601b3 src/Rules/Generate.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index f9c1e0b..bf0afa0 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -71,15 +71,15 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = build $ fullTarget target GenPrimopCode [primopsTxt] [file] priority 2.0 $ do - when (pkg == ghcPkg) $ buildPath -/- "Config.hs" %> \file -> do + when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs - when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do - file <~ generateVersionHs - when (pkg == compiler) $ platformH %> \file -> do file <~ generateGhcBootPlatformH + when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do + file <~ generateVersionHs + when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putBuild $ "| Successfully generated '" ++ file ++ "'." From git at git.haskell.org Thu Oct 26 23:30:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor oracles, add comments. (49419bc) Message-ID: <20171026233030.7A0333A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49419bc553873c21efebe87f4e0aa343013d4bad/ghc >--------------------------------------------------------------- commit 49419bc553873c21efebe87f4e0aa343013d4bad Author: Andrey Mokhov Date: Sun Jul 19 16:38:17 2015 +0100 Refactor oracles, add comments. >--------------------------------------------------------------- 49419bc553873c21efebe87f4e0aa343013d4bad src/Builder.hs | 3 -- src/Expression.hs | 1 - src/Main.hs | 1 - src/Oracles.hs | 67 ------------------------------------------- src/Oracles/ArgsHash.hs | 8 ++++-- src/Oracles/Base.hs | 41 +++++++++++++++++++++++--- src/Oracles/DependencyList.hs | 46 +++++++++++++++++++++-------- src/Oracles/Flag.hs | 1 - src/Oracles/PackageData.hs | 55 ++++++++++++++++++++--------------- src/Oracles/Setting.hs | 43 +++++++++++++-------------- src/Rules.hs | 2 ++ src/{ => Rules}/Config.hs | 16 ++++------- src/Rules/Oracles.hs | 7 +++-- src/Settings/GhcCabal.hs | 2 -- src/Settings/Util.hs | 1 - 15 files changed, 141 insertions(+), 153 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 49419bc553873c21efebe87f4e0aa343013d4bad From git at git.haskell.org Thu Oct 26 23:30:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify Rules.Config. (7dc414c) Message-ID: <20171026233034.3366A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7dc414caf7aa55531c2d25f69c785bec30f192c7/ghc >--------------------------------------------------------------- commit 7dc414caf7aa55531c2d25f69c785bec30f192c7 Author: Andrey Mokhov Date: Sun Jul 19 16:55:54 2015 +0100 Simplify Rules.Config. >--------------------------------------------------------------- 7dc414caf7aa55531c2d25f69c785bec30f192c7 src/Main.hs | 3 +-- src/Rules/Config.hs | 18 ++++++++---------- 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 8bd3384..50420af 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -4,6 +4,5 @@ import Development.Shake main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do oracleRules -- see module Rules.Oracles packageRules -- see module Rules - autoconfRules -- see module Config - configureRules -- see module Config + configRules -- see module Rules.Config generateTargets -- see module Rules diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 2aa3988..3fb4c6a 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -1,20 +1,18 @@ module Rules.Config ( - autoconfRules, configureRules + configRules ) where import Util import Oracles.Base -autoconfRules :: Rules () -autoconfRules = do - "configure" %> \out -> do - copyFile' (configPath "configure.ac") "configure.ac" - putColoured White $ "Running autoconf..." - cmd "bash autoconf" -- TODO: get rid of 'bash' - -configureRules :: Rules () -configureRules = do +configRules :: Rules () +configRules = do configPath "system.config" %> \out -> do need [configPath "system.config.in", "configure"] putColoured White "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' + + "configure" %> \out -> do + copyFile' (configPath "configure.ac") "configure.ac" + putColoured White $ "Running autoconf..." + cmd "bash autoconf" -- TODO: get rid of 'bash' From git at git.haskell.org Thu Oct 26 23:30:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (382ecb4) Message-ID: <20171026233034.33DB83A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/382ecb4b36b9e06dc5f3875a7cc8aeb287623696/ghc >--------------------------------------------------------------- commit 382ecb4b36b9e06dc5f3875a7cc8aeb287623696 Merge: 44d81b0 b6f3045 Author: Andrey Mokhov Date: Sat Dec 26 14:43:49 2015 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 382ecb4b36b9e06dc5f3875a7cc8aeb287623696 LICENSE | 2 ++ README.md | 4 +--- 2 files changed, 3 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:30:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix import of IntSet. (6e8416e) Message-ID: <20171026233037.99A663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e8416e2117fd487e89e58ab112c3688093a0055/ghc >--------------------------------------------------------------- commit 6e8416e2117fd487e89e58ab112c3688093a0055 Author: Andrey Mokhov Date: Sun Jul 19 16:59:50 2015 +0100 Fix import of IntSet. >--------------------------------------------------------------- 6e8416e2117fd487e89e58ab112c3688093a0055 src/Way.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index dffd050..c0b49e3 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -18,8 +18,9 @@ import Oracles.Setting import Control.Applicative import Development.Shake import Development.Shake.Classes -import Data.List hiding (delete) -import Data.IntSet (IntSet, elems, member, delete, fromList) +import Data.List +import Data.IntSet (IntSet) +import qualified Data.IntSet as Set data WayUnit = Threaded | Debug @@ -46,13 +47,13 @@ instance Read WayUnit where newtype Way = Way IntSet wayFromUnits :: [WayUnit] -> Way -wayFromUnits = Way . fromList . map fromEnum +wayFromUnits = Way . Set.fromList . map fromEnum wayToUnits :: Way -> [WayUnit] -wayToUnits (Way set) = map toEnum . elems $ set +wayToUnits (Way set) = map toEnum . Set.elems $ set wayUnit :: WayUnit -> Way -> Bool -wayUnit unit (Way set) = fromEnum unit `member` set +wayUnit unit (Way set) = fromEnum unit `Set.member` set instance Show Way where show way = if null tag then "v" else tag @@ -120,7 +121,7 @@ libsuf way @ (Way set) = else do extension <- setting DynamicExtension -- e.g., .dll or .so version <- setting ProjectVersion -- e.g., 7.11.20141222 - let prefix = wayPrefix . Way . delete (fromEnum Dynamic) $ set + let prefix = wayPrefix . Way . Set.delete (fromEnum Dynamic) $ set -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension From git at git.haskell.org Thu Oct 26 23:30:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop doc directory (no useful docs there anyway), fix #54. (7f8db60) Message-ID: <20171026233037.B03B93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7f8db6059059fbeffe0519bcb60cfac235fa10b2/ghc >--------------------------------------------------------------- commit 7f8db6059059fbeffe0519bcb60cfac235fa10b2 Author: Andrey Mokhov Date: Sat Dec 26 15:23:08 2015 +0000 Drop doc directory (no useful docs there anyway), fix #54. >--------------------------------------------------------------- 7f8db6059059fbeffe0519bcb60cfac235fa10b2 doc/boom.png | Bin 91102 -> 0 bytes doc/build-expressions.docx | Bin 22575 -> 0 bytes doc/build-expressions.pdf | Bin 644843 -> 0 bytes doc/build-package-data.docx | Bin 16519 -> 0 bytes doc/comment-hi-rule.txt | 39 --------- doc/deepseq-build-progress.txt | 86 -------------------- doc/demo.txt | 23 ------ doc/meeting-16-June-2015.txt | 163 -------------------------------------- doc/meeting-25-September-2015.txt | 98 ----------------------- 9 files changed, 409 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 7f8db6059059fbeffe0519bcb60cfac235fa10b2 From git at git.haskell.org Thu Oct 26 23:30:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Migrate all user-configurable settings from system.default to Settings/User.hs. (b253397) Message-ID: <20171026233041.2879E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b253397966a028a13d39b59c1233bef3007eb857/ghc >--------------------------------------------------------------- commit b253397966a028a13d39b59c1233bef3007eb857 Author: Andrey Mokhov Date: Mon Jul 20 00:09:15 2015 +0100 Migrate all user-configurable settings from system.default to Settings/User.hs. >--------------------------------------------------------------- b253397966a028a13d39b59c1233bef3007eb857 cfg/system.config.in | 4 -- src/Builder.hs | 17 ++------- src/Expression.hs | 39 ++++++++++--------- src/Oracles/Flag.hs | 71 ++++++++++++++++++++-------------- src/Oracles/Setting.hs | 38 ++++++++++++++++++- src/Rules/Actions.hs | 5 +-- src/Settings/GhcCabal.hs | 13 ++++--- src/Settings/Packages.hs | 1 + src/Settings/User.hs | 20 +++++++--- src/Settings/Util.hs | 16 ++++++++ src/Settings/Ways.hs | 1 + src/Switches.hs | 99 +++++++----------------------------------------- 12 files changed, 160 insertions(+), 164 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 b253397966a028a13d39b59c1233bef3007eb857 From git at git.haskell.org Thu Oct 26 23:30:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need . (6d4720c) Message-ID: <20171026233041.3D1563A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d4720c1e65d2b4a6cc88152f4547915aebcce42/ghc >--------------------------------------------------------------- commit 6d4720c1e65d2b4a6cc88152f4547915aebcce42 Author: Andrey Mokhov Date: Sat Dec 26 16:25:14 2015 +0000 Don't need . >--------------------------------------------------------------- 6d4720c1e65d2b4a6cc88152f4547915aebcce42 src/Oracles/Config.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index 5a163a6..e8333b6 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -7,6 +7,9 @@ import qualified Data.HashMap.Strict as Map newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +configFile :: FilePath +configFile = configPath -/- "system.config" + askConfig :: String -> Action String askConfig key = askConfigWithDefault key . putError $ "Cannot find key '" ++ key ++ "' in configuration files." @@ -21,11 +24,7 @@ askConfigWithDefault key defaultAction = do -- Oracle for configuration files configOracle :: Rules () configOracle = do - let configFile = configPath -/- "system.config" cfg <- newCache $ \() -> do - unlessM (doesFileExist $ configFile <.> "in") $ - putError $ "\nConfiguration file '" ++ (configFile <.> "in") - ++ "' is missing; unwilling to proceed." need [configFile] putOracle $ "Reading " ++ configFile ++ "..." liftIO $ readConfigFile configFile From git at git.haskell.org Thu Oct 26 23:30:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve performance by caching windows root lookup. (580d397) Message-ID: <20171026233044.EF0E73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/580d39722d627eb95eab63d374441d6c92276f9e/ghc >--------------------------------------------------------------- commit 580d39722d627eb95eab63d374441d6c92276f9e Author: Andrey Mokhov Date: Mon Jul 20 10:06:06 2015 +0100 Improve performance by caching windows root lookup. >--------------------------------------------------------------- 580d39722d627eb95eab63d374441d6c92276f9e src/Builder.hs | 6 +++--- src/Oracles/PackageData.hs | 1 + src/Oracles/Setting.hs | 8 +++----- src/Oracles/WindowsRoot.hs | 28 ++++++++++++++++++++++++++++ src/Rules/Oracles.hs | 10 +++++++--- src/Settings/Args.hs | 1 + 6 files changed, 43 insertions(+), 11 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 0001fc4..91c6fa3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -9,6 +9,7 @@ import Stage import Data.List import Oracles.Base import Oracles.Setting +import Oracles.WindowsRoot import GHC.Generics -- A Builder is an external command invoked in separate process using Shake.cmd @@ -58,7 +59,6 @@ builderPath builder = do specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- TODO: get rid of code duplication (windowsHost) -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". fixAbsolutePathOnWindows :: FilePath -> Action FilePath @@ -67,8 +67,8 @@ fixAbsolutePathOnWindows path = do -- Note, below is different from FilePath.isAbsolute: if (windows && "/" `isPrefixOf` path) then do - Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] - return . unifyPath $ dropWhileEnd isSpace out ++ drop 1 path + root <- windowsRoot + return . unifyPath $ root ++ drop 1 path else return path diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index f12b842..3b00cf8 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -39,6 +39,7 @@ data PackageDataList = Modules FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +-- TODO: is this needed? askPackageData :: FilePath -> String -> Action String askPackageData path key = do let fullKey = replaceSeparators '_' $ path ++ "_" ++ key diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 02073e9..9694c00 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -12,8 +12,8 @@ import Oracles.Base -- setting TargetOs looks up the config file and returns "mingw32". -- -- SettingList is used for multiple string values separated by spaces, such --- as 'src-hc-args = -H32m -O'. --- settingList SrcHcArgs therefore returns a list of strings ["-H32", "-O"]. +-- as 'gmp-include-dirs = a b'. +-- settingList GmpIncludeDirs therefore returns a list of strings ["a", "b"]. data Setting = TargetOs | TargetArch | TargetPlatformFull @@ -22,8 +22,7 @@ data Setting = TargetOs | ProjectVersion | GhcSourcePath -data SettingList = SrcHcArgs - | ConfCcArgs Stage +data SettingList = ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage @@ -44,7 +43,6 @@ setting key = askConfig $ case key of settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of - SrcHcArgs -> "src-hc-args" ConfCcArgs stage -> "conf-cc-args-stage" ++ show stage ConfCppArgs stage -> "conf-cpp-args-stage" ++ show stage ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show stage diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs new file mode 100644 index 0000000..261ca93 --- /dev/null +++ b/src/Oracles/WindowsRoot.hs @@ -0,0 +1,28 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} + +module Oracles.WindowsRoot ( + windowsRoot, windowsRootOracle + ) where + +import Util +import Oracles.Base +import Data.List + +newtype WindowsRoot = WindowsRoot () + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +-- Looks up cygwin/msys root on Windows +windowsRoot :: Action String +windowsRoot = askOracle $ WindowsRoot () + +-- Oracle for windowsRoot. This operation requires caching as looking up +-- the root is slow (at least the current implementation). +windowsRootOracle :: Rules () +windowsRootOracle = do + root <- newCache $ \() -> do + Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] + let root = dropWhileEnd isSpace out + putOracle $ "Detected root on Windows: " ++ root + return root + addOracle $ \WindowsRoot{} -> root () + return () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 7c646be..ba15031 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -5,9 +5,13 @@ module Rules.Oracles ( import Oracles.Base import Oracles.ArgsHash import Oracles.PackageData +import Oracles.WindowsRoot import Oracles.DependencyList -import Data.Monoid oracleRules :: Rules () -oracleRules = - configOracle <> packageDataOracle <> dependencyListOracle <> argsHashOracle +oracleRules = do + configOracle -- see Oracles.Base + packageDataOracle -- see Oracles.PackageData + dependencyListOracle -- see Oracles.DependencyList + argsHashOracle -- see Oracles.ArgsHash + windowsRootOracle -- see Oracles.WindowsRoot diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 78b4f3d..3031093 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -11,6 +11,7 @@ args :: Args args = defaultArgs <> userArgs -- TODO: add all other settings +-- TODO: add src-hc-args = -H32m -O defaultArgs :: Args defaultArgs = mconcat [ cabalArgs From git at git.haskell.org Thu Oct 26 23:30:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement build rule for template-hsc.h, fix #44. (6863e5e) Message-ID: <20171026233045.58C1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6863e5e13c4182976f330a14696109504d1e59b2/ghc >--------------------------------------------------------------- commit 6863e5e13c4182976f330a14696109504d1e59b2 Author: Andrey Mokhov Date: Sat Dec 26 18:31:46 2015 +0000 Implement build rule for template-hsc.h, fix #44. >--------------------------------------------------------------- 6863e5e13c4182976f330a14696109504d1e59b2 shaking-up-ghc.cabal | 1 + src/Main.hs | 2 ++ src/Rules/Install.hs | 11 +++++++++++ src/Settings/Builders/Hsc2Hs.hs | 6 +++++- 4 files changed, 19 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 1e0fbbf..941651b 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -47,6 +47,7 @@ executable ghc-shake , Rules.Generators.GhcBootPlatformH , Rules.Generators.GhcPlatformH , Rules.Generators.VersionHs + , Rules.Install , Rules.Library , Rules.Oracles , Rules.Package diff --git a/src/Main.hs b/src/Main.hs index 0dc8d96..fdc43cd 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,12 +3,14 @@ import Rules import Rules.Cabal import Rules.Config import Rules.Generate +import Rules.Install import Rules.Oracles main :: IO () main = shakeArgs options $ do cabalRules -- see Rules.Cabal configRules -- see Rules.Config + installRules -- see Rules.Install generateTargets -- see Rules generateRules -- see Rules.Generate oracleRules -- see Rules.Oracles diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs new file mode 100644 index 0000000..b592728 --- /dev/null +++ b/src/Rules/Install.hs @@ -0,0 +1,11 @@ +module Rules.Install (installRules) where + +import Expression +import GHC + +installRules :: Rules () +installRules = do + "inplace/lib/template-hsc.h" %> \out -> do + let source = pkgPath hsc2hs -/- "template-hsc.h" + putBuild $ "| Copying " ++ source ++ " -> " ++ out + copyFileChanged source out diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 0c6172d..6721aaf 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -6,6 +6,9 @@ import Predicates (builder, stage0, notStage0) import Settings import Settings.Builders.GhcCabal hiding (cppArgs) +templateHsc :: FilePath +templateHsc = "inplace/lib/template-hsc.h" + hsc2HsArgs :: Args hsc2HsArgs = builder Hsc2Hs ? do stage <- getStage @@ -21,6 +24,7 @@ hsc2HsArgs = builder Hsc2Hs ? do version <- if stage == Stage0 then lift $ ghcCanonVersion else getSetting ProjectVersionInt + lift $ need [templateHsc] mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" @@ -33,7 +37,7 @@ hsc2HsArgs = builder Hsc2Hs ? do , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) , arg ("--cflag=-D__GLASGOW_HASKELL__=" ++ version) - , arg $ "--template=" ++ top -/- "inplace/lib/template-hsc.h" + , arg $ "--template=" ++ top -/- templateHsc , arg $ "-I" ++ top -/- "inplace/lib/include/" , arg =<< getInput , arg "-o", arg =<< getOutput ] From git at git.haskell.org Thu Oct 26 23:30:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop stringly-typed configuration keys. (4512f27) Message-ID: <20171026233048.A8EF43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4512f2736c3fec57c6e067c760a229915abff307/ghc >--------------------------------------------------------------- commit 4512f2736c3fec57c6e067c760a229915abff307 Author: Andrey Mokhov Date: Fri Jul 24 00:21:19 2015 +0100 Drop stringly-typed configuration keys. >--------------------------------------------------------------- 4512f2736c3fec57c6e067c760a229915abff307 src/Settings/GhcCabal.hs | 21 ++++++++++----------- src/Settings/Util.hs | 29 ++++++++--------------------- src/Switches.hs | 11 +++++++---- 3 files changed, 25 insertions(+), 36 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 0e4db8f..05ec1fc 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -3,7 +3,6 @@ module Settings.GhcCabal ( ) where import Way -import Stage import Builder import Package import Util @@ -36,7 +35,7 @@ cabalArgs = builder GhcCabal ? do , configureArgs , stage0 ? packageConstraints , with $ Gcc stage - , notStage Stage0 ? with Ld + , notStage0 ? with Ld , with Ar , with Alex , with Happy ] @@ -65,25 +64,25 @@ configureArgs = do let conf key = appendSubD $ "--configure-option=" ++ key cFlags = mconcat [ ccArgs , remove ["-Werror"] - , argStagedConfig "conf-cc-args" ] - ldFlags = ldArgs <> argStagedConfig "conf-gcc-linker-args" - cppFlags = cppArgs <> argStagedConfig "conf-cpp-args" + , argSettingList $ ConfCcArgs stage ] + ldFlags = ldArgs <> (argSettingList $ ConfGccLinkerArgs stage) + cppFlags = cppArgs <> (argSettingList $ ConfCppArgs stage) mconcat [ conf "CFLAGS" cFlags , conf "LDFLAGS" ldFlags , conf "CPPFLAGS" cppFlags , appendSubD "--gcc-options" $ cFlags <> ldFlags - , conf "--with-iconv-includes" $ argConfig "iconv-include-dirs" - , conf "--with-iconv-libraries" $ argConfig "iconv-lib-dirs" - , conf "--with-gmp-includes" $ argConfig "gmp-include-dirs" - , conf "--with-gmp-libraries" $ argConfig "gmp-lib-dirs" + , conf "--with-iconv-includes" $ argSettingList IconvIncludeDirs + , conf "--with-iconv-libraries" $ argSettingList IconvLibDirs + , conf "--with-gmp-includes" $ argSettingList GmpIncludeDirs + , conf "--with-gmp-libraries" $ argSettingList GmpLibDirs -- TODO: why TargetPlatformFull and not host? - , crossCompiling ? (conf "--host" $ argConfig "target-platform-full") + , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" . argM . builderPath $ Gcc stage ] bootPackageDbArgs :: Args bootPackageDbArgs = do - sourcePath <- lift $ askConfig "ghc-source-path" + sourcePath <- lift . setting $ GhcSourcePath arg $ "--package-db=" ++ sourcePath "libraries/bootstrapping.conf" -- This is a positional argument, hence: diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 82be349..5f0d035 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -1,7 +1,7 @@ module Settings.Util ( -- Primitive settings elements arg, argPath, argM, - argConfig, argStagedConfig, argConfigList, argStagedConfigList, + argSetting, argSettingList, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -13,11 +13,11 @@ module Settings.Util ( ) where import Util -import Stage import Builder -import Settings.User -import Oracles.Base import Expression +import Oracles.Base +import Oracles.Setting +import Settings.User -- A single argument. arg :: String -> Args @@ -30,24 +30,11 @@ argPath = append . return . unifyPath argM :: Action String -> Args argM = appendM . fmap return -argConfig :: String -> Args -argConfig = appendM . fmap return . askConfig - -argConfigList :: String -> Args -argConfigList = appendM . fmap words . askConfig +argSetting :: Setting -> Args +argSetting = argM . setting -stagedKey :: Stage -> String -> String -stagedKey stage key = key ++ "-stage" ++ show stage - -argStagedConfig :: String -> Args -argStagedConfig key = do - stage <- asks getStage - argConfig (stagedKey stage key) - -argStagedConfigList :: String -> Args -argStagedConfigList key = do - stage <- asks getStage - argConfigList (stagedKey stage key) +argSettingList :: SettingList -> Args +argSettingList = appendM . settingList -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal appendCcArgs :: [String] -> Args diff --git a/src/Switches.hs b/src/Switches.hs index 8d5e124..3a56a5a 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,5 +1,5 @@ module Switches ( - notStage, stage0, stage1, stage2, + stage0, stage1, stage2, notStage, notStage0, registerPackage, splitObjects ) where @@ -9,9 +9,6 @@ import Oracles.Setting import Expression -- Derived predicates -notStage :: Stage -> Predicate -notStage = notP . stage - stage0 :: Predicate stage0 = stage Stage0 @@ -21,6 +18,12 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 +notStage :: Stage -> Predicate +notStage = notP . stage + +notStage0 :: Predicate +notStage0 = notP stage0 + -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate registerPackage = return True From git at git.haskell.org Thu Oct 26 23:30:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use existing target input instead of made up 'src' (f80dd4c) Message-ID: <20171026233049.03D753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f80dd4cc253afd4178f794e20aac9b0379b8d036/ghc >--------------------------------------------------------------- commit f80dd4cc253afd4178f794e20aac9b0379b8d036 Author: Andrey Mokhov Date: Sat Dec 26 21:53:37 2015 +0000 Use existing target input instead of made up 'src' >--------------------------------------------------------------- f80dd4cc253afd4178f794e20aac9b0379b8d036 src/Oracles/ArgsHash.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 1f4c584..65bfc8a 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -13,7 +13,7 @@ newtype ArgsHashKey = ArgsHashKey Target -- argument list and computes its hash. The resulting value is tracked in a -- Shake oracle, hence initiating rebuilts when the hash is changed (a hash -- change indicates changes in the build system). --- Note: we replace target sources with ["src"] for performance reasons -- to +-- Note: we keep only the first target input for performance reasons -- to -- avoid storing long lists of source files passed to some builders (e.g. Ar) -- in the Shake database. This optimisation is harmless, because argument list -- constructors are assumed not to examine target sources, but only append them @@ -22,7 +22,8 @@ newtype ArgsHashKey = ArgsHashKey Target -- TODO: Hash Target to improve accuracy and performance. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do - _ <- askOracle . ArgsHashKey $ target { inputs = ["src"] } :: Action Int + let firstInput = take 1 $ inputs target + _ <- askOracle . ArgsHashKey $ target { inputs = firstInput } :: Action Int return () -- Oracle for storing per-target argument list hashes From git at git.haskell.org Thu Oct 26 23:30:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop old src/Package/Data.hs. (9b560ce) Message-ID: <20171026233052.C45823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b560ce0d998e7561d8102a0bfe6a18867f5e621/ghc >--------------------------------------------------------------- commit 9b560ce0d998e7561d8102a0bfe6a18867f5e621 Author: Andrey Mokhov Date: Fri Jul 24 00:25:32 2015 +0100 Drop old src/Package/Data.hs. >--------------------------------------------------------------- 9b560ce0d998e7561d8102a0bfe6a18867f5e621 src/Package/Data.hs | 153 ---------------------------------------------------- 1 file changed, 153 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs deleted file mode 100644 index 03195be..0000000 --- a/src/Package/Data.hs +++ /dev/null @@ -1,153 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package.Data (buildPackageData) where - -import Package.Base -import Targets - -argListDir :: FilePath -argListDir = "shake/arg/buildPackageData" - -libraryArgs :: [Way] -> Args -libraryArgs ways = do - let enable x = ((if x then "--enable-" else "--disable-") ++) - libraryForGhci <- ghcWithInterpreter - && not DynamicGhcPrograms - && vanilla `elem` ways - return $ - [ enable (vanilla `elem` ways) "library-vanilla" - , enable libraryForGhci "library-for-ghci" - , enable (profiling `elem` ways) "library-profiling" - , enable (dynamic `elem` ways) "shared" ] - -configureArgs :: Stage -> Settings -> Args -configureArgs stage settings = - let conf key as = do - s <- unwords <$> args as - unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = [ commonCcArgs `filterOut` ["-Werror"] - , args $ ConfCcArgs stage - -- , customCcArgs settings -- TODO: bring this back - , commonCcWarninigArgs ] -- TODO: check why cflags are glued - ldflags = [ commonLdArgs - , args $ ConfGccLinkerArgs stage - , customLdArgs settings ] - cppflags = [ commonCppArgs - , args $ ConfCppArgs stage - , customCppArgs settings ] - in args [ conf "CFLAGS" cflags - , conf "LDFLAGS" ldflags - , conf "CPPFLAGS" cppflags - , arg $ concat <$> - arg "--gcc-options=" <> args cflags <> arg " " <> args ldflags - , conf "--with-iconv-includes" IconvIncludeDirs - , conf "--with-iconv-libraries" IconvLibDirs - , conf "--with-gmp-includes" GmpIncludeDirs - , conf "--with-gmp-libraries" GmpLibDirs - -- TODO: why TargetPlatformFull and not host? - , when CrossCompiling $ conf "--host" $ arg TargetPlatformFull - , conf "--with-cc" $ arg $ Gcc stage ] - --- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: --- 1) Drop lines containing '$' --- For example, get rid of --- libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ... --- Reason: we don't need them and we can't parse them. --- 2) Replace '/' and '\' with '_' before '=' --- For example libraries/deepseq/dist-install_VERSION = 1.4.0.0 --- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 --- Reason: Shake's built-in makefile parser doesn't recognise slashes - -postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map processLine pkgData - where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line - -bootPkgConstraints :: Args -bootPkgConstraints = args $ do - forM (targetPackagesInStage Stage0) $ \pkg @ (Package _ path cabal _) -> do - let cabalPath = path cabal <.> "cabal" - need [cabalPath] - content <- lines <$> liftIO (readFile cabalPath) - let versionLines = filter (("ersion:" `isPrefixOf`) . drop 1) content - case versionLines of - [versionLine] -> return $ args ["--constraint", cabal ++ " == " - ++ dropWhile (not . isDigit) versionLine] - _ -> redError $ "Cannot determine package version in '" - ++ unifyPath cabalPath ++ "'." - -bootPackageDb :: Args -bootPackageDb = do - top <- showArg GhcSourcePath - arg $ unifyPath $ "--package-db=" ++ top "libraries/bootstrapping.conf" - -cabalArgs :: Package -> TodoItem -> Args -cabalArgs pkg @ (Package _ path _ _) todo @ (stage, dist, settings) = args - [ args ["configure", path, dist] - -- this is a positional argument, hence: - -- * if it is empty, we need to emit one empty string argument - -- * otherwise, we must collapse it into one space-separated string - , arg (unwords <$> customDllArgs settings) - , with $ Ghc stage -- TODO: used to be limited to max stage1 GHC - , with $ GhcPkg stage - , customConfArgs settings - , when (stage == Stage0) bootPackageDb - , libraryArgs =<< ways settings - , when (specified HsColour) $ with HsColour - , configureArgs stage settings - , when (stage == Stage0) bootPkgConstraints - , with $ Gcc stage - , when (stage /= Stage0) $ with Ld - , with Ar - , with Alex - , with Happy ] -- TODO: reorder with's - -ghcPkgArgs :: Package -> TodoItem -> Args -ghcPkgArgs (Package _ path _ _) (stage, dist, _) = args $ - [ arg "update" - , arg "--force" - , arg $ unifyPath $ path dist "inplace-pkg-config" - , when (stage == Stage0) bootPackageDb ] - -buildRule :: Package -> TodoItem -> Rules () -buildRule pkg @ (Package name path cabal _) todo @ (stage, dist, settings) = - let pathDist = path dist - cabalPath = path cabal <.> "cabal" - configure = path "configure" - in - -- All these files are produced by a single run of GhcCabal - (pathDist ) <$> - [ "package-data.mk" - , "haddock-prologue.txt" - , "inplace-pkg-config" - , "setup-config" - , "build" "autogen" "cabal_macros.h" - -- TODO: Is this needed? Also check out Paths_cpsa.hs. - -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" - ] &%> \_ -> do - need [cabalPath] - when (doesFileExist $ configure <.> "ac") $ need [configure] - -- GhcCabal will run the configure script, so we depend on it - -- We still don't know who build the configure script from configure.ac - run GhcCabal $ cabalArgs pkg todo - when (registerPackage settings) $ - run (GhcPkg stage) $ ghcPkgArgs pkg todo - postProcessPackageData $ pathDist "package-data.mk" - -- Finally, record the argument list - need [argListPath argListDir pkg stage] - -argListRule :: Package -> TodoItem -> Rules () -argListRule pkg todo @ (stage, _, _) = - (argListPath argListDir pkg stage) %> \out -> do - -- TODO: depend on ALL source files - need $ ["shake/src/Package/Data.hs"] ++ sourceDependecies - cabalList <- argList GhcCabal $ cabalArgs pkg todo - ghcPkgList <- argList (GhcPkg stage) $ ghcPkgArgs pkg todo - writeFileChanged out $ cabalList ++ "\n" ++ ghcPkgList - --- How to build package-data.mk using GhcCabal to process package.cabal -buildPackageData :: Package -> TodoItem -> Rules () -buildPackageData = argListRule <> buildRule From git at git.haskell.org Thu Oct 26 23:30:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initialise bootstrapping.conf (fix #42). (20037b1) Message-ID: <20171026233053.0EA633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20037b1e711c2e90ed09bd1c6543cc3f05ac7407/ghc >--------------------------------------------------------------- commit 20037b1e711c2e90ed09bd1c6543cc3f05ac7407 Author: Andrey Mokhov Date: Sat Dec 26 21:58:17 2015 +0000 Initialise bootstrapping.conf (fix #42). >--------------------------------------------------------------- 20037b1e711c2e90ed09bd1c6543cc3f05ac7407 src/Base.hs | 20 ++++++++++++++++---- src/Rules/Cabal.hs | 13 +++++++++++++ src/Rules/Data.hs | 8 ++++---- src/Rules/Generate.hs | 15 ++++++++------- src/Settings/Builders/Ghc.hs | 3 ++- src/Settings/Builders/GhcCabal.hs | 9 ++++++--- src/Settings/Builders/GhcPkg.hs | 12 ++++++++++-- 7 files changed, 59 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 20037b1e711c2e90ed09bd1c6543cc3f05ac7407 From git at git.haskell.org Thu Oct 26 23:30:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcM builder. (d2dfdfa) Message-ID: <20171026233056.843763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2dfdfa91578e2e4ce5b5419986ea08c50b39e74/ghc >--------------------------------------------------------------- commit d2dfdfa91578e2e4ce5b5419986ea08c50b39e74 Author: Andrey Mokhov Date: Fri Jul 24 04:09:40 2015 +0100 Add GhcM builder. >--------------------------------------------------------------- d2dfdfa91578e2e4ce5b5419986ea08c50b39e74 src/Builder.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 91c6fa3..33735d3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -28,6 +28,7 @@ data Builder = Ar | GhcCabal | Gcc Stage | Ghc Stage + | GhcM Stage | GhcPkg Stage deriving (Show, Eq, Generic) @@ -48,6 +49,8 @@ builderKey builder = case builder of Gcc _ -> "gcc" GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" + -- GhcM is currently a synonym for Ghc (to be called with -M flag) + GhcM stage -> builderKey $ Ghc stage builderPath :: Builder -> Action String builderPath builder = do From git at git.haskell.org Thu Oct 26 23:30:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:30:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use ||^ for OR-ing Predicates. (2d221a4) Message-ID: <20171026233056.C55CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d221a4c3d8b79d3a88f8faa90b884aef5d160ea/ghc >--------------------------------------------------------------- commit 2d221a4c3d8b79d3a88f8faa90b884aef5d160ea Author: Andrey Mokhov Date: Sat Dec 26 22:00:44 2015 +0000 Use ||^ for OR-ing Predicates. >--------------------------------------------------------------- 2d221a4c3d8b79d3a88f8faa90b884aef5d160ea src/Settings/Builders/GhcCabal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 17b1725..80c4f4c 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -80,7 +80,7 @@ bootPackageDbArgs :: Args bootPackageDbArgs = stage0 ? do path <- getSetting GhcSourcePath lift $ need [bootstrappingConfInitialised] - isGhc <- (||) <$> stagedBuilder Ghc <*> stagedBuilder GhcM + isGhc <- stagedBuilder Ghc ||^ stagedBuilder GhcM let prefix = if isGhc then "-package-db " else "--package-db=" arg $ prefix ++ path -/- bootstrappingConf From git at git.haskell.org Thu Oct 26 23:31:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add apply function for transforming expressions. (505302b) Message-ID: <20171026233100.34A0C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/505302b7e32640ed8782bbf6cb45c02d0c58fe0f/ghc >--------------------------------------------------------------- commit 505302b7e32640ed8782bbf6cb45c02d0c58fe0f Author: Andrey Mokhov Date: Fri Jul 24 04:10:50 2015 +0100 Add apply function for transforming expressions. >--------------------------------------------------------------- 505302b7e32640ed8782bbf6cb45c02d0c58fe0f src/Expression.hs | 21 +++++++++++++-------- 1 file changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index f33e236..7ac380d 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -6,7 +6,8 @@ module Expression ( Expr, DiffExpr, fromDiffExpr, Predicate, PredicateLike (..), applyPredicate, (??), Args, Ways, Packages, - append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, + apply, append, appendM, remove, + appendSub, appendSubD, filterSub, removeSub, interpret, interpretExpr, stage, package, builder, file, way ) where @@ -57,15 +58,19 @@ type Packages = DiffExpr [Package] type Ways = DiffExpr [Way] -- Basic operations on expressions: --- 1) append something to an expression +-- 1) transform an expression by applying a given function +apply :: (a -> a) -> DiffExpr a +apply = return . Diff + +-- 2) append something to an expression append :: Monoid a => a -> DiffExpr a -append x = return . Diff $ (<> x) +append x = apply (<> x) --- 2) remove given elements from a list expression +-- 3) remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] -remove xs = return . Diff $ filter (`notElem` xs) +remove xs = apply . filter $ (`notElem` xs) --- 3) apply a predicate to an expression +-- 4) apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate @@ -105,7 +110,7 @@ appendM mx = lift mx >>= append appendSub :: String -> [String] -> Args appendSub prefix xs | xs' == [] = mempty - | otherwise = return . Diff $ go False + | otherwise = apply . go $ False where xs' = filter (/= "") xs go True [] = [] @@ -120,7 +125,7 @@ appendSubD :: String -> Args -> Args appendSubD prefix diffExpr = fromDiffExpr diffExpr >>= appendSub prefix filterSub :: String -> (String -> Bool) -> Args -filterSub prefix p = return . Diff $ map filterSubstr +filterSub prefix p = apply . map $ filterSubstr where filterSubstr s | prefix `isPrefixOf` s = unwords . filter p . words $ s From git at git.haskell.org Thu Oct 26 23:31:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add builders: DeriveConstants, Nm, Objdump. (6001acb) Message-ID: <20171026233100.6CA793A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6001acb394a70a14e333dd17a8f65b89115dfa52/ghc >--------------------------------------------------------------- commit 6001acb394a70a14e333dd17a8f65b89115dfa52 Author: Andrey Mokhov Date: Sun Dec 27 01:51:33 2015 +0000 Add builders: DeriveConstants, Nm, Objdump. >--------------------------------------------------------------- 6001acb394a70a14e333dd17a8f65b89115dfa52 cfg/system.config.in | 45 ++++++++++++++++++++++++--------------------- src/Builder.hs | 6 ++++++ 2 files changed, 30 insertions(+), 21 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 12ddeed..a2cfef3 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -4,36 +4,39 @@ # Paths to builders: #=================== -system-ghc = @WithGhc@ -ghc-stage1 = inplace/bin/ghc-stage1 -ghc-stage2 = inplace/bin/ghc-stage2 -ghc-stage3 = inplace/bin/ghc-stage3 +system-ghc = @WithGhc@ +ghc-stage1 = inplace/bin/ghc-stage1 +ghc-stage2 = inplace/bin/ghc-stage2 +ghc-stage3 = inplace/bin/ghc-stage3 -system-gcc = @CC_STAGE0@ -gcc = @WhatGccIsCalled@ +system-gcc = @CC_STAGE0@ +gcc = @WhatGccIsCalled@ -system-ghc-pkg = @GhcPkgCmd@ -ghc-pkg = inplace/bin/ghc-pkg +system-ghc-pkg = @GhcPkgCmd@ +ghc-pkg = inplace/bin/ghc-pkg -ghc-cabal = inplace/bin/ghc-cabal +ghc-cabal = inplace/bin/ghc-cabal -haddock = inplace/bin/haddock +haddock = inplace/bin/haddock -hsc2hs = inplace/bin/hsc2hs +hsc2hs = inplace/bin/hsc2hs -genprimopcode = inplace/bin/genprimopcode +genprimopcode = inplace/bin/genprimopcode +derive-constants = inplace/bin/deriveConstants -hs-cpp = @HaskellCPPCmd@ -hs-cpp-args = @HaskellCPPArgs@ +hs-cpp = @HaskellCPPCmd@ +hs-cpp-args = @HaskellCPPArgs@ -unlit = inplace/lib/unlit -ghc-split = inplace/lib/ghc-split +unlit = inplace/lib/unlit +ghc-split = inplace/lib/ghc-split -ld = @LdCmd@ -ar = @ArCmd@ -alex = @AlexCmd@ -happy = @HappyCmd@ -hscolour = @HSCOLOUR@ +alex = @AlexCmd@ +ar = @ArCmd@ +happy = @HappyCmd@ +hscolour = @HSCOLOUR@ +ld = @LdCmd@ +nm = @NmCmd@ +objdump = @ObjdumpCmd@ # Information about builders: #============================ diff --git a/src/Builder.hs b/src/Builder.hs index 4d41d0a..b58d701 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -19,6 +19,7 @@ import Stage -- TODO: do we really need staged builders? data Builder = Alex | Ar + | DeriveConstants | Gcc Stage | GccM Stage | GenPrimopCode @@ -35,6 +36,8 @@ data Builder = Alex | HsCpp | Hsc2Hs | Ld + | Nm + | Objdump | Unlit deriving (Show, Eq, Generic) @@ -43,6 +46,7 @@ builderKey :: Builder -> String builderKey builder = case builder of Alex -> "alex" Ar -> "ar" + DeriveConstants -> "derive-constants" Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' @@ -64,6 +68,8 @@ builderKey builder = case builder of Hsc2Hs -> "hsc2hs" HsCpp -> "hs-cpp" Ld -> "ld" + Nm -> "nm" + Objdump -> "objdump" Unlit -> "unlit" -- TODO: Paths to some builders should be determined using defaultProgramPath From git at git.haskell.org Thu Oct 26 23:31:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (86b0a17) Message-ID: <20171026233103.D43303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86b0a17ad6fab8c9dde6f082b291c2d785f957d0/ghc >--------------------------------------------------------------- commit 86b0a17ad6fab8c9dde6f082b291c2d785f957d0 Author: Andrey Mokhov Date: Fri Jul 24 04:12:31 2015 +0100 Clean up. >--------------------------------------------------------------- 86b0a17ad6fab8c9dde6f082b291c2d785f957d0 src/Package.hs | 1 - src/Rules/Data.hs | 1 - src/Settings/GhcPkg.hs | 2 +- src/Util.hs | 1 + 4 files changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 5d2429f..a007b4e 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -6,7 +6,6 @@ import Util import Data.Function import GHC.Generics import Development.Shake.Classes -import Development.Shake.FilePath -- pkgPath is the path to the source code relative to the root data Package = Package diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 3ce7d08..2a2a995 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -16,7 +16,6 @@ import Rules.Actions import Control.Applicative import Control.Monad.Extra import Development.Shake -import Development.Shake.FilePath -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: StagePackageTarget -> Rules () diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index 83bef1d..8e3a287 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -12,8 +12,8 @@ import Development.Shake.FilePath ghcPkgArgs :: Args ghcPkgArgs = do - pkg <- asks getPackage stage <- asks getStage + pkg <- asks getPackage builder (GhcPkg stage) ? mconcat [ arg "update" , arg "--force" diff --git a/src/Util.hs b/src/Util.hs index 4b1a2c6..7cc38ee 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,7 @@ module Util ( module Data.Char, module System.Console.ANSI, + module Development.Shake.FilePath, replaceIf, replaceEq, replaceSeparators, unifyPath, chunksOfSize, From git at git.haskell.org Thu Oct 26 23:31:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate files with DeriveConstants (#39). (c6cfb36) Message-ID: <20171026233104.232A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6cfb36c2d7ca4f76d3da54d06b40fb86890e7ef/ghc >--------------------------------------------------------------- commit c6cfb36c2d7ca4f76d3da54d06b40fb86890e7ef Author: Andrey Mokhov Date: Sun Dec 27 01:53:52 2015 +0000 Generate files with DeriveConstants (#39). >--------------------------------------------------------------- c6cfb36c2d7ca4f76d3da54d06b40fb86890e7ef src/Rules/Actions.hs | 29 +++++++++++---------- src/Rules/Generate.hs | 22 ++++++++++++++-- src/Settings/Args.hs | 2 ++ src/Settings/Builders/DeriveConstants.hs | 44 ++++++++++++++++++++++++++++++++ src/Settings/Builders/GhcCabal.hs | 1 + 5 files changed, 82 insertions(+), 16 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5a3d113..30ae742 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -47,20 +47,21 @@ build = buildWithResources [] interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of - Alex -> prefixAndSuffix 0 3 ss - Ar -> prefixAndSuffix 2 1 ss - Gcc _ -> prefixAndSuffix 0 4 ss - GccM _ -> prefixAndSuffix 0 1 ss - Ghc _ -> prefixAndSuffix 0 4 ss - GhcCabal -> prefixAndSuffix 3 0 ss - GhcM _ -> prefixAndSuffix 1 1 ss - GhcPkg _ -> prefixAndSuffix 3 0 ss - Haddock -> prefixAndSuffix 1 0 ss - Happy -> prefixAndSuffix 0 3 ss - Hsc2Hs -> prefixAndSuffix 0 3 ss - HsCpp -> prefixAndSuffix 0 1 ss - Ld -> prefixAndSuffix 4 0 ss - _ -> ss + Alex -> prefixAndSuffix 0 3 ss + Ar -> prefixAndSuffix 2 1 ss + DeriveConstants -> prefixAndSuffix 3 0 ss + Gcc _ -> prefixAndSuffix 0 4 ss + GccM _ -> prefixAndSuffix 0 1 ss + Ghc _ -> prefixAndSuffix 0 4 ss + GhcCabal -> prefixAndSuffix 3 0 ss + GhcM _ -> prefixAndSuffix 1 1 ss + GhcPkg _ -> prefixAndSuffix 3 0 ss + Haddock -> prefixAndSuffix 1 0 ss + Happy -> prefixAndSuffix 0 3 ss + Hsc2Hs -> prefixAndSuffix 0 3 ss + HsCpp -> prefixAndSuffix 0 1 ss + Ld -> prefixAndSuffix 4 0 ss + _ -> ss where prefixAndSuffix n m list = let len = length list in diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index e427dfd..2121a9c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,4 +1,6 @@ -module Rules.Generate (generatePackageCode, generateRules) where +module Rules.Generate ( + generatePackageCode, generateRules, includesDependencies + ) where import Expression import GHC @@ -15,6 +17,19 @@ import Settings primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" +derivedConstantsPath :: FilePath +derivedConstantsPath = "includes/dist-derivedconstants/header" + +-- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? +includesDependencies :: [FilePath] +includesDependencies = + [ "includes/ghcautoconf.h" + , "includes/ghcplatform.h" + , derivedConstantsPath -/- "DerivedConstants.h" + , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" ] + -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] knownGenerators = [ (Alex , ".x" ) @@ -33,7 +48,6 @@ generate file target expr = do writeFileChanged file contents putSuccess $ "| Successfully generated '" ++ file ++ "'." - generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let path = targetPath stage pkg @@ -71,6 +85,10 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = build $ fullTarget target GenPrimopCode [primopsTxt] [file] priority 2.0 $ do + when (pkg == compiler && stage == Stage1) $ + derivedConstantsPath ++ "//*" %> \file -> do + build $ fullTarget target DeriveConstants [] [file] + when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 231f5ed..5419f51 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -3,6 +3,7 @@ module Settings.Args (getArgs) where import Expression import Settings.Builders.Alex import Settings.Builders.Ar +import Settings.Builders.DeriveConstants import Settings.Builders.Gcc import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc @@ -32,6 +33,7 @@ defaultArgs = mconcat , arArgs , cabalArgs , customPackageArgs + , deriveConstantsArgs , gccArgs , gccMArgs , genPrimopCodeArgs diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs new file mode 100644 index 0000000..4353875 --- /dev/null +++ b/src/Settings/Builders/DeriveConstants.hs @@ -0,0 +1,44 @@ +module Settings.Builders.DeriveConstants ( + derivedConstantsPath, deriveConstantsArgs + ) where + +import Expression +import Oracles.Config.Flag +import Oracles.Config.Setting +import Predicates (builder, file) +import Settings.Builders.GhcCabal + +derivedConstantsPath :: FilePath +derivedConstantsPath = "includes/dist-derivedconstants/header" + +-- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? +deriveConstantsArgs :: Args +deriveConstantsArgs = builder DeriveConstants ? do + cFlags <- fromDiffExpr includeCcArgs + mconcat + [ file "//DerivedConstants.h" ? arg "--gen-header" + , file "//GHCConstantsHaskellType.hs" ? arg "--gen-haskell-type" + , file "//platformConstants" ? arg "--gen-haskell-value" + , file "//GHCConstantsHaskellWrappers.hs" ? arg "--gen-haskell-wrappers" + , file "//GHCConstantsHaskellExports.hs" ? arg "--gen-haskell-exports" + , arg "-o", arg =<< getOutput + , arg "--tmpdir", arg derivedConstantsPath + , arg "--gcc-program", arg =<< getBuilderPath (Gcc Stage1) + , append . concat $ map (\a -> ["--gcc-flag", a]) cFlags + , arg "--nm-program", arg =<< getBuilderPath Nm + , specified Objdump ? mconcat [ arg "--objdump-program" + , arg =<< getBuilderPath Objdump ] + , arg "--target-os", arg =<< getSetting TargetOs ] + +includeCcArgs :: Args +includeCcArgs = do + confCcArgs <- lift . settingList $ ConfCcArgs Stage1 + mconcat + [ ccArgs + , ccWarnings + , append confCcArgs + , flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER" + , append $ map ("-I" ++) ghcIncludeDirs -- TODO: fix code duplication + , arg "-Irts" + , notM ghcWithSMP ? arg "-DNOSMP" + , arg "-fcommon" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 80c4f4c..cec876a 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -208,6 +208,7 @@ argStagedBuilderPath :: (Stage -> Builder) -> Args argStagedBuilderPath sb = (argM . builderPath . sb) =<< getStage -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal +-- TODO: simplify appendCcArgs :: [String] -> Args appendCcArgs xs = do mconcat [ stagedBuilder Gcc ? append xs From git at git.haskell.org Thu Oct 26 23:31:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement expression for GhcM builder. (fcb25e6) Message-ID: <20171026233107.7104B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fcb25e6e86cd2fa82be62cf8541372ef3fb97c34/ghc >--------------------------------------------------------------- commit fcb25e6e86cd2fa82be62cf8541372ef3fb97c34 Author: Andrey Mokhov Date: Fri Jul 24 04:13:30 2015 +0100 Implement expression for GhcM builder. >--------------------------------------------------------------- fcb25e6e86cd2fa82be62cf8541372ef3fb97c34 src/Settings/Args.hs | 2 + src/Settings/GhcM.hs | 158 +++++++++++++++++++++++++++++++++++++++++++++++++++ src/Settings/Util.hs | 17 ++++++ 3 files changed, 177 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 fcb25e6e86cd2fa82be62cf8541372ef3fb97c34 From git at git.haskell.org Thu Oct 26 23:31:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add explicit dependencies on includes/ generated files (fix #48). (1fcb025) Message-ID: <20171026233107.B7CF23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fcb025a9405f6b2970d1efdaf47558b300de1a9/ghc >--------------------------------------------------------------- commit 1fcb025a9405f6b2970d1efdaf47558b300de1a9 Author: Andrey Mokhov Date: Sun Dec 27 01:55:29 2015 +0000 Add explicit dependencies on includes/ generated files (fix #48). >--------------------------------------------------------------- 1fcb025a9405f6b2970d1efdaf47558b300de1a9 src/Rules/Dependencies.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 907c4d3..5d08df1 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -4,6 +4,7 @@ import Expression import GHC import Oracles import Rules.Actions +import Rules.Generate import Rules.Resources import Settings @@ -17,13 +18,13 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do (buildPath "*.c.deps") %> \out -> do let srcFile = dropBuild . dropExtension $ out - when (pkg == compiler) $ need [platformH] + when (pkg == compiler) . need $ platformH : includesDependencies need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - when (pkg == compiler) $ need [platformH] + when (pkg == compiler) . need $ platformH : includesDependencies -- TODO: very ugly and fragile; use gcc -MM instead? let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) [ "primop-vector-uniques.hs-incl" From git at git.haskell.org Thu Oct 26 23:31:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -/- for combining paths with unification of the result. (179d1cd) Message-ID: <20171026233111.63E1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/179d1cd8a9dbaa304f51bef9cfbba745940ec2db/ghc >--------------------------------------------------------------- commit 179d1cd8a9dbaa304f51bef9cfbba745940ec2db Author: Andrey Mokhov Date: Fri Jul 24 13:10:57 2015 +0100 Add -/- for combining paths with unification of the result. >--------------------------------------------------------------- 179d1cd8a9dbaa304f51bef9cfbba745940ec2db src/Oracles/Base.hs | 8 +++----- src/Oracles/PackageData.hs | 11 +++++------ src/Package.hs | 2 +- src/Rules.hs | 4 ++-- src/Rules/Config.hs | 6 +++--- src/Rules/Data.hs | 12 ++++++------ src/Settings/GhcCabal.hs | 8 ++++---- src/Settings/GhcM.hs | 20 ++++++++++---------- src/Settings/GhcPkg.hs | 4 ++-- src/Settings/TargetDirectory.hs | 4 ++-- src/Settings/Util.hs | 7 +------ src/Util.hs | 9 ++++++++- 12 files changed, 47 insertions(+), 48 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 179d1cd8a9dbaa304f51bef9cfbba745940ec2db From git at git.haskell.org Thu Oct 26 23:31:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add install targets, install inplace/lib/platformConstants. (43b6cc3) Message-ID: <20171026233111.A33803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/43b6cc390adbf439e8b98c19eb8b9196f0a58bfb/ghc >--------------------------------------------------------------- commit 43b6cc390adbf439e8b98c19eb8b9196f0a58bfb Author: Andrey Mokhov Date: Sun Dec 27 02:13:55 2015 +0000 Add install targets, install inplace/lib/platformConstants. >--------------------------------------------------------------- 43b6cc390adbf439e8b98c19eb8b9196f0a58bfb src/Rules.hs | 4 +++- src/Rules/Generate.hs | 3 ++- src/Rules/Install.hs | 16 ++++++++++++---- 3 files changed, 17 insertions(+), 6 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 5516c33..a9ac3e4 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,6 +1,7 @@ module Rules (generateTargets, packageRules) where import Expression +import Rules.Install import Rules.Package import Rules.Resources import Settings @@ -18,7 +19,8 @@ generateTargets = action $ do return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] return $ libTargets ++ programTargets - need targets + + need $ targets ++ installTargets packageRules :: Rules () packageRules = do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 2121a9c..ccd059f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,5 +1,6 @@ module Rules.Generate ( - generatePackageCode, generateRules, includesDependencies + generatePackageCode, generateRules, + derivedConstantsPath, includesDependencies ) where import Expression diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index b592728..fca88fe 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -1,11 +1,19 @@ -module Rules.Install (installRules) where +module Rules.Install (installTargets, installRules) where import Expression import GHC +import Rules.Generate + +installTargets :: [FilePath] +installTargets = [ "inplace/lib/template-hsc.h" + , "inplace/lib/platformConstants" ] installRules :: Rules () installRules = do - "inplace/lib/template-hsc.h" %> \out -> do - let source = pkgPath hsc2hs -/- "template-hsc.h" - putBuild $ "| Copying " ++ source ++ " -> " ++ out + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs + "inplace/lib/platformConstants" <~ derivedConstantsPath + where + file <~ dir = file %> \out -> do + let source = dir -/- takeFileName out copyFileChanged source out + putSuccess $ "| Installed " ++ source ++ " -> " ++ out From git at git.haskell.org Thu Oct 26 23:31:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename ask* to get* to avoid mixing up oracles with expressions. (d9d1dd9e) Message-ID: <20171026233115.1AC493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9d1dd9ef0d2827579f9c7c647e081156a14c8ab/ghc >--------------------------------------------------------------- commit d9d1dd9ef0d2827579f9c7c647e081156a14c8ab Author: Andrey Mokhov Date: Fri Jul 24 13:15:29 2015 +0100 Rename ask* to get* to avoid mixing up oracles with expressions. >--------------------------------------------------------------- d9d1dd9ef0d2827579f9c7c647e081156a14c8ab src/Settings/GhcM.hs | 30 +++++++++++++++--------------- src/Settings/Util.hs | 10 +++++----- 2 files changed, 20 insertions(+), 20 deletions(-) diff --git a/src/Settings/GhcM.hs b/src/Settings/GhcM.hs index 4f792e0..89c4634 100644 --- a/src/Settings/GhcM.hs +++ b/src/Settings/GhcM.hs @@ -19,9 +19,9 @@ ghcMArgs = do stage <- asks getStage builder (GhcM stage) ? do pkg <- asks getPackage - cppArgs <- askPkgDataList CppArgs - hsArgs <- askPkgDataList HsArgs - hsSrcs <- askHsSources + cppArgs <- getPkgDataList CppArgs + hsArgs <- getPkgDataList HsArgs + hsSrcs <- getHsSources ways <- fromDiffExpr Settings.Ways.ways let buildPath = targetPath stage pkg -/- "build" mconcat @@ -41,9 +41,9 @@ packageGhcArgs :: Args packageGhcArgs = do stage <- asks getStage supportsPackageKey <- lift . flag $ SupportsPackageKey - pkgKey <- askPkgData PackageKey - pkgDepKeys <- askPkgDataList DepKeys - pkgDeps <- askPkgDataList Deps + pkgKey <- getPkgData PackageKey + pkgDepKeys <- getPkgDataList DepKeys + pkgDeps <- getPkgDataList Deps mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" @@ -59,8 +59,8 @@ includeGhcArgs :: Args includeGhcArgs = do stage <- asks getStage pkg <- asks getPackage - srcDirs <- askPkgDataList SrcDirs - includeDirs <- askPkgDataList IncludeDirs + srcDirs <- getPkgDataList SrcDirs + includeDirs <- getPkgDataList IncludeDirs let buildPath = targetPath stage pkg -/- "build" autogenPath = buildPath -/- "autogen" mconcat @@ -74,18 +74,18 @@ includeGhcArgs = do , arg "-optP-include" -- TODO: Shall we also add -cpp? , arg $ "-optP" ++ autogenPath -/- "cabal_macros.h" ] -askHsSources :: Expr [FilePath] -askHsSources = do +getHsSources :: Expr [FilePath] +getHsSources = do stage <- asks getStage pkg <- asks getPackage - srcDirs <- askPkgDataList SrcDirs + srcDirs <- getPkgDataList SrcDirs let autogenPath = targetPath stage pkg -/- "build/autogen" dirs = autogenPath : map (pkgPath pkg -/-) srcDirs - askModuleFiles dirs [".hs", ".lhs"] + getModuleFiles dirs [".hs", ".lhs"] -askModuleFiles :: [FilePath] -> [String] -> Expr [FilePath] -askModuleFiles directories suffixes = do - modules <- askPkgDataList Modules +getModuleFiles :: [FilePath] -> [String] -> Expr [FilePath] +getModuleFiles directories suffixes = do + modules <- getPkgDataList Modules let modPaths = map (replaceEq '.' pathSeparator) modules files <- lift $ forM [ dir -/- modPath ++ suffix | dir <- directories diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 4fadcd7..22ffd29 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -2,7 +2,7 @@ module Settings.Util ( -- Primitive settings elements arg, argM, argSetting, argSettingList, - askPkgData, askPkgDataList, + getPkgData, getPkgDataList, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -34,15 +34,15 @@ argSetting = argM . setting argSettingList :: SettingList -> Args argSettingList = appendM . settingList -askPkgData :: (FilePath -> PackageData) -> Expr String -askPkgData key = do +getPkgData :: (FilePath -> PackageData) -> Expr String +getPkgData key = do stage <- asks getStage pkg <- asks getPackage let path = targetPath stage pkg lift . pkgData . key $ path -askPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] -askPkgDataList key = do +getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] +getPkgDataList key = do stage <- asks getStage pkg <- asks getPackage let path = targetPath stage pkg From git at git.haskell.org Thu Oct 26 23:31:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate includes/ghcversion.h (66f18be) Message-ID: <20171026233115.627C03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/66f18bec2737a73fc1b2387726e22a35ef6edd8a/ghc >--------------------------------------------------------------- commit 66f18bec2737a73fc1b2387726e22a35ef6edd8a Author: Moritz Angermann Date: Sun Dec 27 14:27:55 2015 +0800 Generate includes/ghcversion.h This should be the final commit to fix #39. >--------------------------------------------------------------- 66f18bec2737a73fc1b2387726e22a35ef6edd8a shaking-up-ghc.cabal | 1 + src/Rules/Generate.hs | 2 ++ src/Rules/Generators/GhcVersionH.hs | 33 +++++++++++++++++++++++++++++++++ 3 files changed, 36 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 941651b..0e60637 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -46,6 +46,7 @@ executable ghc-shake , Rules.Generators.GhcAutoconfH , Rules.Generators.GhcBootPlatformH , Rules.Generators.GhcPlatformH + , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs , Rules.Install , Rules.Library diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index ccd059f..bc0089c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -9,6 +9,7 @@ import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH import Rules.Generators.GhcBootPlatformH import Rules.Generators.GhcPlatformH +import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles import Rules.Actions @@ -107,6 +108,7 @@ generateRules :: Rules () generateRules = do "includes/ghcautoconf.h" <~ generateGhcAutoconfH "includes/ghcplatform.h" <~ generateGhcPlatformH + "includes/ghcversion.h" <~ generateGhcVersionH where file <~ gen = file %> \out -> generate out emptyTarget gen diff --git a/src/Rules/Generators/GhcVersionH.hs b/src/Rules/Generators/GhcVersionH.hs new file mode 100644 index 0000000..a45df55 --- /dev/null +++ b/src/Rules/Generators/GhcVersionH.hs @@ -0,0 +1,33 @@ +module Rules.Generators.GhcVersionH (generateGhcVersionH) where + +import Expression +import Oracles + +generateGhcVersionH :: Expr String +generateGhcVersionH = do + version <- getSetting ProjectVersionInt + patchLevel1 <- getSetting ProjectPatchLevel1 + patchLevel2 <- getSetting ProjectPatchLevel2 + return . unlines $ + [ "#ifndef __GHCVERSION_H__" + , "#define __GHCVERSION_H__" + , "" + , "#ifndef __GLASGOW_HASKELL__" + , "# define __GLASGOW_HASKELL__ " ++ version + , "#endif" + , ""] + ++ + [ "#define __GLASGOW_HASKELL_PATCHLEVEL1__ " ++ patchLevel1 | patchLevel1 /= "" ] + ++ + [ "#define __GLASGOW_HASKELL_PATCHLEVEL2__ " ++ patchLevel2 | patchLevel2 /= "" ] + ++ + [ "" + , "#define MIN_VERSION_GLASGOW_HASKELL(ma,mi,pl1,pl2) (\\" + , " ((ma)*100+(mi)) < __GLASGOW_HASKELL__ || \\" + , " ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \\" + , " && (pl1) < __GLASGOW_HASKELL_PATCHLEVEL1__ || \\" + , " ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \\" + , " && (pl1) == __GLASGOW_HASKELL_PATCHLEVEL1__ \\" + , " && (pl2) <= __GLASGOW_HASKELL_PATCHLEVEL2__ )" + , "" + , "#endif /* __GHCVERSION_H__ */" ] From git at git.haskell.org Thu Oct 26 23:31:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactoring for consistent interface (getters) for expressions. (ff86f40) Message-ID: <20171026233118.9D8EF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894/ghc >--------------------------------------------------------------- commit ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894 Author: Andrey Mokhov Date: Fri Jul 24 14:07:46 2015 +0100 Refactoring for consistent interface (getters) for expressions. >--------------------------------------------------------------- ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894 src/Expression.hs | 31 ++++++++++++++++---- src/Rules/Actions.hs | 3 +- src/Rules/Data.hs | 5 ++-- src/Settings/GhcCabal.hs | 12 ++++---- src/Settings/GhcM.hs | 20 ++++++------- src/Settings/GhcPkg.hs | 4 +-- src/Settings/Packages.hs | 5 +++- src/Settings/Util.hs | 27 ++++++++++++------ src/Settings/Ways.hs | 5 +++- src/Switches.hs | 19 +++++++------ src/Target.hs | 73 ++++++++++++++++++++++++------------------------ 11 files changed, 121 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894 From git at git.haskell.org Thu Oct 26 23:31:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds ghcautoconf and ghcplatform as dependencies to hp2ps. (456d2bd) Message-ID: <20171026233118.DBEB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/456d2bdadab272bc40d63f166e0eeaaf0a13ca02/ghc >--------------------------------------------------------------- commit 456d2bdadab272bc40d63f166e0eeaaf0a13ca02 Author: Moritz Angermann Date: Sun Dec 27 14:41:23 2015 +0800 Adds ghcautoconf and ghcplatform as dependencies to hp2ps. 1fcb025 added includes to the dependencies for the `compiler` package, but `hp2ps` already requires them and is built prior to the `compiler` package. This should fix #48 for good. Also updates the README.md to reflect the closure of #44. >--------------------------------------------------------------- 456d2bdadab272bc40d63f166e0eeaaf0a13ca02 README.md | 3 --- src/Rules/Dependencies.hs | 2 ++ 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index ca1e5fb..93674a1 100644 --- a/README.md +++ b/README.md @@ -55,9 +55,6 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure --with-gcc=$(which clang) # See #26 -./shake-build/build.sh includes/ghcautoconf.h # See #48 -./shake-build/build.sh includes/ghcplatform.h # See #48 -cp utils/hsc2hs/template-hsc.h inplace/lib/template-hsc.h # See #44 ./shake-build/build.sh ``` diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 5d08df1..197fa64 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -19,12 +19,14 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = (buildPath "*.c.deps") %> \out -> do let srcFile = dropBuild . dropExtension $ out when (pkg == compiler) . need $ platformH : includesDependencies + when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) . need $ platformH : includesDependencies + when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] -- TODO: very ugly and fragile; use gcc -MM instead? let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) [ "primop-vector-uniques.hs-incl" From git at git.haskell.org Thu Oct 26 23:31:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement buildPackageDependencies rule. (65b298b) Message-ID: <20171026233122.2E0D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65b298b0c7fe85fa106bc7d0558096825eb01e09/ghc >--------------------------------------------------------------- commit 65b298b0c7fe85fa106bc7d0558096825eb01e09 Author: Andrey Mokhov Date: Sat Jul 25 02:05:14 2015 +0100 Implement buildPackageDependencies rule. >--------------------------------------------------------------- 65b298b0c7fe85fa106bc7d0558096825eb01e09 src/Builder.hs | 2 + src/Package/Dependencies.hs | 92 ------------------- src/Rules.hs | 3 +- src/Rules/Actions.hs | 10 +-- src/Rules/Data.hs | 8 +- src/Rules/Dependencies.hs | 210 ++++++-------------------------------------- src/Rules/Package.hs | 5 +- src/Settings/Args.hs | 2 + src/Settings/GccM.hs | 41 +++++++++ src/Settings/GhcM.hs | 104 +++++----------------- src/Settings/GhcPkg.hs | 4 +- src/Settings/User.hs | 2 +- src/Settings/Util.hs | 59 +------------ 13 files changed, 108 insertions(+), 434 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 65b298b0c7fe85fa106bc7d0558096825eb01e09 From git at git.haskell.org Thu Oct 26 23:31:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #58 from angerman/feature/ghcversion (b45902d) Message-ID: <20171026233122.6B04C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b45902dd36889637607dd1611272c93d4fcab4fd/ghc >--------------------------------------------------------------- commit b45902dd36889637607dd1611272c93d4fcab4fd Merge: 43b6cc3 66f18be Author: Andrey Mokhov Date: Sun Dec 27 09:35:33 2015 +0000 Merge pull request #58 from angerman/feature/ghcversion Generate includes/ghcversion.h >--------------------------------------------------------------- b45902dd36889637607dd1611272c93d4fcab4fd shaking-up-ghc.cabal | 1 + src/Rules/Generate.hs | 2 ++ src/Rules/Generators/GhcVersionH.hs | 33 +++++++++++++++++++++++++++++++++ 3 files changed, 36 insertions(+) From git at git.haskell.org Thu Oct 26 23:31:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a draft description of demo. (4bd8812) Message-ID: <20171026233126.124E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4bd88123d1eeb16bfb272768b3ec93a4d503003f/ghc >--------------------------------------------------------------- commit 4bd88123d1eeb16bfb272768b3ec93a4d503003f Author: Andrey Mokhov Date: Sat Jul 25 12:33:33 2015 +0100 Add a draft description of demo. >--------------------------------------------------------------- 4bd88123d1eeb16bfb272768b3ec93a4d503003f doc/demo.txt | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/doc/demo.txt b/doc/demo.txt new file mode 100644 index 0000000..4b6b671 --- /dev/null +++ b/doc/demo.txt @@ -0,0 +1,4 @@ +1. Rebuild only when argument list has changed +2. Rebuild only when package-data.mk contents has changed + +* Add to Settings/GhcPkg.hs: package deepseq ? arg "--force" From git at git.haskell.org Thu Oct 26 23:31:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #59 from angerman/feature/hp2ps-deps (3b1b4df) Message-ID: <20171026233126.4E3663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b1b4df56ef0ec92bd88f53eceb13cff11e4130d/ghc >--------------------------------------------------------------- commit 3b1b4df56ef0ec92bd88f53eceb13cff11e4130d Merge: b45902d 456d2bd Author: Andrey Mokhov Date: Sun Dec 27 09:36:49 2015 +0000 Merge pull request #59 from angerman/feature/hp2ps-deps Adds ghcautoconf and ghcplatform as dependencies to hp2ps. >--------------------------------------------------------------- 3b1b4df56ef0ec92bd88f53eceb13cff11e4130d README.md | 3 --- src/Rules/Dependencies.hs | 2 ++ 2 files changed, 2 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:31:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (28a8078) Message-ID: <20171026233129.838FE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28a807878a86600df0884fc5ee28be02adc52386/ghc >--------------------------------------------------------------- commit 28a807878a86600df0884fc5ee28be02adc52386 Author: Andrey Mokhov Date: Sat Jul 25 12:33:52 2015 +0100 Clean up. >--------------------------------------------------------------- 28a807878a86600df0884fc5ee28be02adc52386 src/Expression.hs | 21 +++++++- src/Package/Base.hs | 138 +++++++++++++++++++++++------------------------ src/Settings/GccM.hs | 48 ++++++++--------- src/Settings/GhcCabal.hs | 35 ++++++------ src/Settings/GhcM.hs | 59 ++++++++++---------- src/Settings/GhcPkg.hs | 15 +++--- src/Settings/Util.hs | 11 ++++ 7 files changed, 173 insertions(+), 154 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 28a807878a86600df0884fc5ee28be02adc52386 From git at git.haskell.org Thu Oct 26 23:31:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (b27b177) Message-ID: <20171026233129.D078F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b27b177a5657e7c8a9088ace440f73074ab4f2d7/ghc >--------------------------------------------------------------- commit b27b177a5657e7c8a9088ace440f73074ab4f2d7 Author: Andrey Mokhov Date: Mon Dec 28 03:01:15 2015 +0000 Clean up. >--------------------------------------------------------------- b27b177a5657e7c8a9088ace440f73074ab4f2d7 src/Builder.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index b58d701..b6fd228 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -14,9 +14,10 @@ import Stage -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg -- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) --- TODO: add Cpp builders --- TODO: rename Gcc to Cc? --- TODO: do we really need staged builders? +-- TODO: Do we really need HsCpp builder? Can't we use a generic Cpp +-- builder instead? It would also be used instead of GccM. +-- TODO: rename Gcc to CCompiler? We sometimes use gcc and sometimes clang. +-- TODO: why are Gcc/GccM staged? data Builder = Alex | Ar | DeriveConstants @@ -26,7 +27,6 @@ data Builder = Alex | Ghc Stage | GhcCabal | GhcCabalHsColour - | GhcLink Stage | GhcM Stage | GhcPkg Stage | GhcSplit @@ -55,7 +55,6 @@ builderKey builder = case builder of Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - GhcLink stage -> builderKey $ Ghc stage -- using Ghc as linker GhcM stage -> builderKey $ Ghc stage -- synonym for 'Ghc -M' GhcCabal -> "ghc-cabal" GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' From git at git.haskell.org Thu Oct 26 23:31:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add dependencies to Target. (4f2fbbb) Message-ID: <20171026233133.0290E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b/ghc >--------------------------------------------------------------- commit 4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b Author: Andrey Mokhov Date: Sat Jul 25 17:08:35 2015 +0100 Add dependencies to Target. >--------------------------------------------------------------- 4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b src/Expression.hs | 15 +++++++++- src/Rules/Actions.hs | 1 + src/Rules/Data.hs | 17 ++++++----- src/Rules/Dependencies.hs | 18 ++++++----- src/Settings/GccM.hs | 5 ++-- src/Settings/GhcCabal.hs | 1 + src/Settings/GhcM.hs | 19 ------------ src/Settings/Util.hs | 21 +++++++++++++ src/Target.hs | 76 +++++++++++++++++++++++------------------------ 9 files changed, 98 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 4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b From git at git.haskell.org Thu Oct 26 23:31:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to generated Haskell files. (7274771) Message-ID: <20171026233133.4FB0E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7274771087702c22c23b94c27560de1199cb005f/ghc >--------------------------------------------------------------- commit 7274771087702c22c23b94c27560de1199cb005f Author: Andrey Mokhov Date: Mon Dec 28 03:02:08 2015 +0000 Fix paths to generated Haskell files. >--------------------------------------------------------------- 7274771087702c22c23b94c27560de1199cb005f src/Oracles/ModuleFiles.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 832deef..33f6138 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -21,8 +21,9 @@ moduleFiles stage pkg = do haskellModuleFiles :: Stage -> Package -> Action ([FilePath], [String]) haskellModuleFiles stage pkg = do - let path = targetPath stage pkg - autogen = path -/- "build/autogen" + let path = targetPath stage pkg + autogen = path -/- "build/autogen" + dropPkgPath = drop $ length (pkgPath pkg) + 1 srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath pkg -/- dir | dir <- srcDirs ] @@ -31,9 +32,10 @@ haskellModuleFiles stage pkg = do let found = foundSrcDirs ++ foundAutogen missingMods = modules `minusOrd` (sort $ map fst found) - otherMods = map (replaceEq '/' '.' . dropExtension) otherFiles + otherFileToMod = replaceEq '/' '.' . dropExtension . dropPkgPath (haskellFiles, otherFiles) = partition ("//*hs" ?==) (map snd found) - return (haskellFiles, missingMods ++ otherMods) + + return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) moduleFilesOracle :: Rules () moduleFilesOracle = do From git at git.haskell.org Thu Oct 26 23:31:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add custom settings for compiler and other packages. (096b595) Message-ID: <20171026233137.068303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/096b595bc7b269be01cca98aa567c540d8bce1fd/ghc >--------------------------------------------------------------- commit 096b595bc7b269be01cca98aa567c540d8bce1fd Author: Andrey Mokhov Date: Sun Jul 26 01:31:40 2015 +0100 Add custom settings for compiler and other packages. >--------------------------------------------------------------- 096b595bc7b269be01cca98aa567c540d8bce1fd src/Oracles/Flag.hs | 15 ++++++++++++- src/Oracles/Setting.hs | 6 +++++- src/Package/Base.hs | 28 ------------------------ src/Settings/Args.hs | 7 ++++++ src/Settings/GhcCabal.hs | 56 +++++++++++++++++++++++++++++++++++++----------- src/Settings/GhcM.hs | 8 +++++-- src/Settings/User.hs | 17 ++++++++++++--- src/Settings/Ways.hs | 19 +++++++++++++++- src/Switches.hs | 5 ++++- src/Util.hs | 2 +- 10 files changed, 113 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 096b595bc7b269be01cca98aa567c540d8bce1fd From git at git.haskell.org Thu Oct 26 23:31:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use orderOnly dependencies for generated headers, see #48 (e7f3ae8) Message-ID: <20171026233137.4C1BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7f3ae8418552a145dc192ff5127d2e84bf1fa76/ghc >--------------------------------------------------------------- commit e7f3ae8418552a145dc192ff5127d2e84bf1fa76 Author: Andrey Mokhov Date: Mon Dec 28 03:03:26 2015 +0000 Use orderOnly dependencies for generated headers, see #48 >--------------------------------------------------------------- e7f3ae8418552a145dc192ff5127d2e84bf1fa76 src/Rules/Dependencies.hs | 27 +++------------------ src/Rules/Generate.hs | 62 +++++++++++++++++++++++++++++++++-------------- 2 files changed, 47 insertions(+), 42 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 197fa64..dc43071 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -1,7 +1,6 @@ module Rules.Dependencies (buildPackageDependencies) where import Expression -import GHC import Oracles import Rules.Actions import Rules.Generate @@ -14,37 +13,17 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = buildPath = path -/- "build" dropBuild = (pkgPath pkg ++) . drop (length buildPath) hDepFile = buildPath -/- ".hs-dependencies" - platformH = targetPath stage compiler -/- "ghc_boot_platform.h" in do (buildPath "*.c.deps") %> \out -> do let srcFile = dropBuild . dropExtension $ out - when (pkg == compiler) . need $ platformH : includesDependencies - when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] + orderOnly $ generatedDependencies stage pkg need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - when (pkg == compiler) . need $ platformH : includesDependencies - when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] - -- TODO: very ugly and fragile; use gcc -MM instead? - let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) - [ "primop-vector-uniques.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" - , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] - need $ srcs ++ extraDeps + orderOnly $ generatedDependencies stage pkg + need srcs if srcs == [] then writeFileChanged out "" else build $ fullTarget target (GhcM stage) srcs [out] diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index bc0089c..c7d13d6 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( generatePackageCode, generateRules, - derivedConstantsPath, includesDependencies + derivedConstantsPath, generatedDependencies ) where import Expression @@ -19,18 +19,47 @@ import Settings primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" +primopsTxt :: Stage -> FilePath +primopsTxt stage = targetPath stage compiler -/- "build/primops.txt" + +platformH :: Stage -> FilePath +platformH stage = targetPath stage compiler -/- "ghc_boot_platform.h" + derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" -- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? -includesDependencies :: [FilePath] -includesDependencies = - [ "includes/ghcautoconf.h" - , "includes/ghcplatform.h" - , derivedConstantsPath -/- "DerivedConstants.h" - , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" ] +generatedDependencies :: Stage -> Package -> [FilePath] +generatedDependencies stage pkg + | pkg == hp2ps = [ "includes/ghcautoconf.h" + , "includes/ghcplatform.h" ] + | pkg == compiler = let buildPath = targetPath stage compiler -/- "build" + in + [ "includes/ghcautoconf.h" + , "includes/ghcplatform.h" + , derivedConstantsPath -/- "DerivedConstants.h" + , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" + , platformH stage ] + ++ + fmap (buildPath -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] + | otherwise = [] -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] @@ -52,10 +81,7 @@ generate file target expr = do generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = - let path = targetPath stage pkg - buildPath = path -/- "build" - primopsTxt = targetPath stage compiler -/- "build/primops.txt" - platformH = targetPath stage compiler -/- "ghc_boot_platform.h" + let buildPath = targetPath stage pkg -/- "build" generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) file <~ gen = generate file target gen in do @@ -74,8 +100,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = copyFileChanged srcBoot $ file -<.> "hs-boot" -- TODO: needing platformH is ugly and fragile - when (pkg == compiler) $ primopsTxt %> \file -> do - need [platformH, primopsSource] + when (pkg == compiler) $ primopsTxt stage %> \file -> do + need [platformH stage, primopsSource] build $ fullTarget target HsCpp [primopsSource] [file] -- TODO: why different folders for generated files? @@ -83,8 +109,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = [ "GHC/PrimopWrappers.hs" , "autogen/GHC/Prim.hs" , "*.hs-incl" ] |%> \file -> do - need [primopsTxt] - build $ fullTarget target GenPrimopCode [primopsTxt] [file] + need [primopsTxt stage] + build $ fullTarget target GenPrimopCode [primopsTxt stage] [file] priority 2.0 $ do when (pkg == compiler && stage == Stage1) $ @@ -94,7 +120,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs - when (pkg == compiler) $ platformH %> \file -> do + when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do From git at git.haskell.org Thu Oct 26 23:31:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Parallelise build by collecting targets and then needing them. (9463852) Message-ID: <20171026233141.071F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/946385207cf7691b7baa05e3003ebfa4fdb29082/ghc >--------------------------------------------------------------- commit 946385207cf7691b7baa05e3003ebfa4fdb29082 Author: Andrey Mokhov Date: Sun Jul 26 17:01:03 2015 +0100 Parallelise build by collecting targets and then needing them. >--------------------------------------------------------------- 946385207cf7691b7baa05e3003ebfa4fdb29082 src/Rules.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index f8fd786..b63687f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,7 +1,7 @@ module Rules ( generateTargets, packageRules, oracleRules, - module Rules.Package, module Rules.Config, + module Rules.Package, ) where import Util @@ -17,12 +17,13 @@ import Development.Shake -- generateTargets needs package-data.mk files of all target packages -- TODO: make interpretDiff total generateTargets :: Rules () -generateTargets = action $ - forM_ [Stage0 ..] $ \stage -> do +generateTargets = action $ do + targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpret (stageTarget stage) packages - forM_ pkgs $ \pkg -> do - need [targetPath stage pkg -/- "build/haskell.deps"] - need [targetPath stage pkg -/- "build/c.deps"] + fmap concat . forM pkgs $ \pkg -> return + [ targetPath stage pkg -/- "build/haskell.deps" + , targetPath stage pkg -/- "build/c.deps" ] + need targets -- TODO: add Stage2 (compiler only?) packageRules :: Rules () From git at git.haskell.org Thu Oct 26 23:31:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a TODO note for unlit and driver/ghc-split utils. (58d7fcc) Message-ID: <20171026233141.4DF1F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/58d7fccf59da038f038446c41901fa086ae4a40c/ghc >--------------------------------------------------------------- commit 58d7fccf59da038f038446c41901fa086ae4a40c Author: Andrey Mokhov Date: Mon Dec 28 12:44:13 2015 +0000 Add a TODO note for unlit and driver/ghc-split utils. >--------------------------------------------------------------- 58d7fccf59da038f038446c41901fa086ae4a40c src/GHC.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 281f15e..859bec4 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -85,10 +85,11 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" +-- TODO: The following utils are not implemented yet: unlit, driver/ghc-split -- TODO: The following utils are not included into the build system because --- they seem to be unused or unrelated to the build process: chechUniques, +-- they seem to be unused or unrelated to the build process: checkUniques, -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, --- lndir, mkdirhier, testremove, touchy, unlit, vagrant +-- lndir, mkdirhier, testremove, touchy, vagrant -- GHC build results will be placed into target directories with the following -- typical structure: From git at git.haskell.org Thu Oct 26 23:31:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for resources. Limit parallelism of ghc-pkg. (6547fc7) Message-ID: <20171026233144.64E543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6547fc76758720a51f4b0d4819b95128892be459/ghc >--------------------------------------------------------------- commit 6547fc76758720a51f4b0d4819b95128892be459 Author: Andrey Mokhov Date: Sun Jul 26 17:03:36 2015 +0100 Add support for resources. Limit parallelism of ghc-pkg. >--------------------------------------------------------------- 6547fc76758720a51f4b0d4819b95128892be459 src/Rules/Actions.hs | 33 ++++++++++++++++----------------- src/Rules/Data.hs | 39 ++++++++++++++++++++++----------------- src/Target.hs | 5 +++-- 3 files changed, 41 insertions(+), 36 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 055931e..2730c55 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,5 +1,5 @@ module Rules.Actions ( - build, buildWhen, run, verboseRun + build, buildWithResources, run, verboseRun ) where import Util @@ -11,38 +11,37 @@ import Settings.Util import Oracles.ArgsHash import Development.Shake --- Build a given target using an appropriate builder. Force a rebuilt if the --- argument list has changed since the last built (that is, track changes in --- the build system). -build :: FullTarget -> Action () -build target = do +-- Build a given target using an appropriate builder and acquiring necessary +-- resources. Force a rebuilt if the argument list has changed since the last +-- built (that is, track changes in the build system). +buildWithResources :: [(Resource, Int)] -> FullTarget -> Action () +buildWithResources rs target = do need $ Target.dependencies target argList <- interpret target args -- The line below forces the rule to be rerun if the args hash has changed argsHash <- askArgsHash target - run (Target.builder target) argList + run rs (Target.builder target) argList -buildWhen :: Predicate -> FullTarget -> Action () -buildWhen predicate target = do - bool <- interpretExpr target predicate - when bool $ build target +-- Most targets are built without explicitly acquiring resources +build :: FullTarget -> Action () +build = buildWithResources [] -- Run the builder with a given collection of arguments -verboseRun :: Builder -> [String] -> Action () -verboseRun builder args = do +verboseRun :: [(Resource, Int)] -> Builder -> [String] -> Action () +verboseRun rs builder args = do needBuilder builder path <- builderPath builder - cmd [path] args + withResources rs $ cmd [path] args -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. -run :: Builder -> [String] -> Action () -run builder args = do +run :: [(Resource, Int)] -> Builder -> [String] -> Action () +run rs builder args = do putColoured White $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" mapM_ (putColoured White . ("| " ++)) $ interestingInfo builder args putColoured White $ "\\--------" - quietly $ verboseRun builder args + quietly $ verboseRun rs builder args interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index b48ff48..d60dbfa 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -12,31 +12,36 @@ import Control.Applicative import Control.Monad.Extra import Development.Shake +-- TODO: Add ordering between packages? (see ghc.mk) -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: StagePackageTarget -> Rules () -buildPackageData target = +buildPackageData target = do let stage = Target.stage target pkg = Target.package target path = targetPath stage pkg cabal = pkgPath pkg -/- pkgCabal pkg configure = pkgPath pkg -/- "configure" - in + + -- We do not allow parallel invokations of ghc-pkg (they don't work) + ghcPkg <- newResource "ghc-pkg" 1 + (path -/-) <$> - [ "package-data.mk" - , "haddock-prologue.txt" - , "inplace-pkg-config" - , "setup-config" - , "build" -/- "autogen" -/- "cabal_macros.h" - -- TODO: Is this needed? Also check out Paths_cpsa.hs. - -- , "build" -/- "autogen" -/- ("Paths_" ++ name) <.> "hs" - ] &%> \files -> do - -- GhcCabal may run the configure script, so we depend on it - -- We still don't know who built the configure script from configure.ac - whenM (doesFileExist $ configure <.> "ac") $ need [configure] - build $ fullTarget target [cabal] GhcCabal files - buildWhen registerPackage $ - fullTarget target [cabal] (GhcPkg stage) files - postProcessPackageData $ path -/- "package-data.mk" + [ "package-data.mk" + , "haddock-prologue.txt" + , "inplace-pkg-config" + , "setup-config" + , "build" -/- "autogen" -/- "cabal_macros.h" + -- TODO: Is this needed? Also check out Paths_cpsa.hs. + -- , "build" -/- "autogen" -/- ("Paths_" ++ name) <.> "hs" + ] &%> \files -> do + -- GhcCabal may run the configure script, so we depend on it + -- We don't know who built the configure script from configure.ac + whenM (doesFileExist $ configure <.> "ac") $ need [configure] + build $ fullTarget target [cabal] GhcCabal files + whenM (interpretExpr target registerPackage) . + buildWithResources [(ghcPkg, 1)] $ + fullTarget target [cabal] (GhcPkg stage) files + postProcessPackageData $ path -/- "package-data.mk" -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' diff --git a/src/Target.hs b/src/Target.hs index c3b6b93..dc0bde7 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} module Target ( Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), - stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay + stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay, ) where import Way @@ -72,7 +72,8 @@ fullTarget target deps b fs = target } -- Use this function to be explicit about the build way. -fullTargetWithWay :: StagePackageTarget -> [FilePath] -> Builder -> Way -> [FilePath] -> FullTarget +fullTargetWithWay :: StagePackageTarget -> [FilePath] -> Builder -> Way + -> [FilePath] -> FullTarget fullTargetWithWay target deps b w fs = target { dependencies = deps, From git at git.haskell.org Thu Oct 26 23:31:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport Data.Char (a9aa2ac) Message-ID: <20171026233144.B86443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9aa2ac5825514967ea60f28473ec1a6d435c1a4/ghc >--------------------------------------------------------------- commit a9aa2ac5825514967ea60f28473ec1a6d435c1a4 Author: Ben Gamari Date: Thu Dec 24 14:02:38 2015 +0100 Base: Don't reexport Data.Char It's really not used often enough to warrant special treatment >--------------------------------------------------------------- a9aa2ac5825514967ea60f28473ec1a6d435c1a4 src/Base.hs | 2 -- src/Oracles/WindowsRoot.hs | 1 + src/Rules/Library.hs | 2 ++ src/Rules/Program.hs | 2 ++ 4 files changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 47a4285..3c62ed5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -3,7 +3,6 @@ module Base ( module Control.Applicative, module Control.Monad.Extra, module Control.Monad.Reader, - module Data.Char, module Data.Function, module Data.List, module Data.Maybe, @@ -34,7 +33,6 @@ module Base ( import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader -import Data.Char import Data.Function import Data.List import Data.Maybe diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 2ec13c7..89dd011 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -1,6 +1,7 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.WindowsRoot (windowsRoot, windowsRootOracle) where +import Data.Char (isSpace) import Base newtype WindowsRoot = WindowsRoot () diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 1df83a8..db1624b 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,5 +1,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where +import Data.Char + import Expression hiding (splitPath) import GHC import Oracles diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index a24fcdc..962ce1d 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -1,5 +1,7 @@ module Rules.Program (buildProgram) where +import Data.Char + import Expression hiding (splitPath) import GHC hiding (ghci) import Oracles From git at git.haskell.org Thu Oct 26 23:31:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix custom settings of the compiler package. (3090409) Message-ID: <20171026233148.3C5853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3090409f9a90cda50892d25f02ea3e3a55f43121/ghc >--------------------------------------------------------------- commit 3090409f9a90cda50892d25f02ea3e3a55f43121 Author: Andrey Mokhov Date: Sun Jul 26 17:04:23 2015 +0100 Fix custom settings of the compiler package. >--------------------------------------------------------------- 3090409f9a90cda50892d25f02ea3e3a55f43121 src/Settings/GhcCabal.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index cba05cc..2c475ab 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -149,6 +149,7 @@ customPackageArgs = do , package compiler ? builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (succ stage) + , arg $ "--flags=stage" ++ show (succ stage) , arg "--disable-library-for-ghci" , targetOs "openbsd" ? arg "--ld-options=-E" , flag GhcUnregisterised ? arg "--ghc-option=-DNO_REGS" @@ -157,7 +158,8 @@ customPackageArgs = do , (threaded `elem` rtsWays) ? notStage0 ? arg "--ghc-option=-optc-DTHREADED_RTS" , ghcWithNativeCodeGen ? arg "--flags=ncg" - , ghcWithInterpreter ? arg "--flags=ghci" + , ghcWithInterpreter ? + notStage0 ? arg "--flags=ghci" , ghcWithInterpreter ? ghcEnableTablesNextToCode ? notP (flag GhcUnregisterised) ? From git at git.haskell.org Thu Oct 26 23:31:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Hide `parallel` (ef0386c) Message-ID: <20171026233148.91EF93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef0386c76790b582cb180d5db224d0b4681ae4ba/ghc >--------------------------------------------------------------- commit ef0386c76790b582cb180d5db224d0b4681ae4ba Author: Ben Gamari Date: Thu Dec 24 14:17:54 2015 +0100 Base: Hide `parallel` Otherwise it is shadowed by `GHC.parallel` >--------------------------------------------------------------- ef0386c76790b582cb180d5db224d0b4681ae4ba src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 55c1a9e..47a4285 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -39,7 +39,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>)) +import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes import Development.Shake.Config import Development.Shake.FilePath From git at git.haskell.org Thu Oct 26 23:31:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add to demo.txt. (140376a) Message-ID: <20171026233151.C0E0D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/140376acfd4cedd015f436f83ea30abf3aaed848/ghc >--------------------------------------------------------------- commit 140376acfd4cedd015f436f83ea30abf3aaed848 Author: Andrey Mokhov Date: Mon Jul 27 02:03:46 2015 +0100 Add to demo.txt. >--------------------------------------------------------------- 140376acfd4cedd015f436f83ea30abf3aaed848 doc/demo.txt | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/doc/demo.txt b/doc/demo.txt index 4b6b671..cec474a 100644 --- a/doc/demo.txt +++ b/doc/demo.txt @@ -2,3 +2,8 @@ 2. Rebuild only when package-data.mk contents has changed * Add to Settings/GhcPkg.hs: package deepseq ? arg "--force" + +3. Reduce complexity when searching for source files by 40x: + +* compiler, was: 25 dirs (24 source dirs + autogen) x 406 modules x 2 extensions = 20300 candidates +* compiler, now: 25 dirs x 20 module-dirs = 500 candidates \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:31:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport Development.Shake.Config (1405953) Message-ID: <20171026233152.168243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14059539b1fa2b5e79e38c34266636c60dfb40f4/ghc >--------------------------------------------------------------- commit 14059539b1fa2b5e79e38c34266636c60dfb40f4 Author: Ben Gamari Date: Thu Dec 24 14:37:49 2015 +0100 Base: Don't reexport Development.Shake.Config >--------------------------------------------------------------- 14059539b1fa2b5e79e38c34266636c60dfb40f4 src/Base.hs | 2 -- src/Oracles/Config.hs | 1 + src/Oracles/PackageData.hs | 1 + 3 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fb0eed7..1012d4e 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -11,7 +11,6 @@ module Base ( -- * Shake module Development.Shake, module Development.Shake.Classes, - module Development.Shake.Config, module Development.Shake.FilePath, module Development.Shake.Util, @@ -38,7 +37,6 @@ import Data.Maybe import Data.Monoid import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes -import Development.Shake.Config import Development.Shake.FilePath import Development.Shake.Util import System.Console.ANSI diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index e8333b6..cde2383 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -3,6 +3,7 @@ module Oracles.Config (askConfig, askConfigWithDefault, configOracle) where import Base import qualified Data.HashMap.Strict as Map +import Development.Shake.Config newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 4e3d306..d176839 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -4,6 +4,7 @@ module Oracles.PackageData ( pkgData, pkgDataList, packageDataOracle ) where +import Development.Shake.Config import Base import qualified Data.HashMap.Strict as Map From git at git.haskell.org Thu Oct 26 23:31:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve performance of getHsSources. (3122d3a) Message-ID: <20171026233155.6A81E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3122d3a2b9fe8ed79df55edd09b1cb12b1d9cdba/ghc >--------------------------------------------------------------- commit 3122d3a2b9fe8ed79df55edd09b1cb12b1d9cdba Author: Andrey Mokhov Date: Mon Jul 27 02:04:34 2015 +0100 Improve performance of getHsSources. >--------------------------------------------------------------- 3122d3a2b9fe8ed79df55edd09b1cb12b1d9cdba src/Oracles/DependencyList.hs | 3 --- src/Oracles/PackageData.hs | 2 +- src/Package/Base.hs | 60 ------------------------------------------- src/Rules/Actions.hs | 2 +- src/Settings/Util.hs | 32 +++++++++++++++++++++-- src/Util.hs | 7 ++++- 6 files changed, 38 insertions(+), 68 deletions(-) diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs index 76d7eac..0ad9267 100644 --- a/src/Oracles/DependencyList.hs +++ b/src/Oracles/DependencyList.hs @@ -38,6 +38,3 @@ dependencyListOracle = do addOracle $ \(DependencyListKey (file, obj)) -> Map.lookup (unifyPath obj) <$> deps (unifyPath file) return () - -bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) -bimap f g (x, y) = (f x, g y) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index fd30cc3..579312f 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -90,6 +90,6 @@ packageDataOracle = do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> + addOracle $ \(PackageDataKey (file, key)) -> do Map.lookup key <$> pkgData (unifyPath file) return () diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 3e2eb37..1f9d2c8 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -23,52 +23,6 @@ import Oracles import Settings import qualified System.Directory as S ---pathArgs :: ShowArgs a => String -> FilePath -> a -> Args ---pathArgs key path as = map (\a -> key ++ unifyPath (path a)) <$> args as - --- prefixedPath :: String -> [Settings] -> Settings --- prefixedPath prefix = argPrefix prefix . argConcatPath . sconcat - ---includeGccArgs :: FilePath -> FilePath -> Args ---includeGccArgs path dist = --- let pathDist = path dist --- autogen = pathDist "build/autogen" --- in args [ arg $ "-I" ++ unifyPath autogen --- , pathArgs "-I" path $ IncludeDirs pathDist --- , pathArgs "-I" path $ DepIncludeDirs pathDist ] - - --- includeGccSettings :: Settings --- includeGccSettings = mconcat --- [ prefixedPath "-I" [argBuildPath, argBuildDir, arg "build", arg "autogen"] --- , argPrefix "-I" $ argPaths ... --- , prefixedPath "-I" [argBuildPath, argIncludeDirs ] -- wrong --- , prefixedPath "-I" [argBuildPath, argDepIncludeDirs ]] - --- includeGhcSettings :: Settings --- includeGhcSettings = --- let buildDir = argBuildPath `fence` argSrcDirs --- in arg "-i" `fence` --- mconcat --- [ argPathList "-i" [argBuildPath, argSrcDirs] --- , argPath "-i" buildDir --- , argPath "-I" buildDir --- , argPathList "-i" [buildDir, arg "autogen"] --- , argPathList "-I" [buildDir, arg "autogen"] --- , argPathList "-I" [argBuildPath, argIncludeDirs] --- , arg "-optP-include" -- TODO: Shall we also add -cpp? --- , argPathList "-optP" [buildDir, arg "autogen/cabal_macros.h"] ] - - --- pkgHsSources :: FilePath -> FilePath -> Action [FilePath] --- pkgHsSources path dist = do --- let pathDist = path dist --- autogen = pathDist "build/autogen" --- dirs <- map (path ) <$> args (SrcDirs pathDist) --- findModuleFiles pathDist (autogen:dirs) [".hs", ".lhs"] - --- TODO: look for non-{hs,c} objects too - -- Find Haskell objects we depend on (we don't want to depend on split objects) pkgDepHsObjects :: FilePath -> FilePath -> Way -> Action [FilePath] pkgDepHsObjects path dist way = do @@ -101,20 +55,6 @@ pkgLibHsObjects path dist stage way = do findModuleFiles pathDist [buildDir] [suffix] else do return depObjs --- findModuleFiles :: FilePath -> [FilePath] -> [String] -> Action [FilePath] --- findModuleFiles pathDist directories suffixes = do --- modPaths <- map (replaceEq '.' pathSeparator) <$> args (Modules pathDist) --- fileList <- forM [ dir modPath ++ suffix --- | dir <- directories --- , modPath <- modPaths --- , suffix <- suffixes --- ] $ \file -> do --- let dir = takeDirectory file --- dirExists <- liftIO $ S.doesDirectoryExist dir --- when dirExists $ return $ unifyPath file --- files <- getDirectoryFiles "" fileList --- return $ map unifyPath files - -- The argument list has a limited size on Windows. Since Windows 7 the limit -- is 32768 (theoretically). In practice we use 31000 to leave some breathing -- space for the builder's path & name, auxiliary flags, and other overheads. diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 2730c55..d91cd84 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -50,7 +50,7 @@ interestingInfo builder ss = case builder of Gcc _ -> prefixAndSuffix 0 4 ss GccM _ -> prefixAndSuffix 0 1 ss Ghc _ -> prefixAndSuffix 0 4 ss - GhcM _ -> prefixAndSuffix 1 1 ss + --GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss GhcCabal -> prefixAndSuffix 3 0 ss _ -> ss diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 1e7585e..1901a8c 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -26,6 +26,8 @@ import Oracles.Setting import Oracles.PackageData import Settings.User import Settings.TargetDirectory +import Data.List +import Data.Function -- A single argument. arg :: String -> Args @@ -76,8 +78,34 @@ getHsSources = do path <- getTargetPath pkgPath <- getPackagePath srcDirs <- getPkgDataList SrcDirs - let paths = (path -/- "build/autogen") : map (pkgPath -/-) srcDirs - getSourceFiles paths [".hs", ".lhs"] + modules <- getPkgDataList Modules + let buildPath = path -/- "build" + autogenPath = buildPath -/- "autogen" + dirs = autogenPath : map (pkgPath -/-) srcDirs + decodedMods = sort $ map decodeModule modules + modDirFiles = map (bimap head sort . unzip) + $ groupBy ((==) `on` fst) decodedMods + + result <- lift . fmap concat . forM dirs $ \dir -> do + todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles + forM todo $ \(mDir, mFiles) -> do + let files = [ dir -/- mDir -/- mFile <.> "*hs" | mFile <- mFiles ] + found <- fmap (map unifyPath) $ getDirectoryFiles "" files + return (found, (mDir, map takeBaseName found)) + + let foundSources = concatMap fst result + foundMods = [ (d, f) | (d, fs) <- map snd result, f <- fs ] + leftMods = decodedMods \\ sort foundMods + genSources = map (\(d, f) -> buildPath -/- d -/- f <.> "hs") leftMods + + return $ foundSources ++ genSources + +-- Given a module name extract the directory and file names, e.g.: +-- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +decodeModule :: String -> (FilePath, FilePath) +decodeModule = splitFileName . replaceEq '.' '/' + + -- getSourceFiles paths [".hs", ".lhs"] -- Find all source files in specified paths and with given extensions getSourceFiles :: [FilePath] -> [String] -> Expr [FilePath] diff --git a/src/Util.hs b/src/Util.hs index 7c5f786..fd33e73 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -5,7 +5,8 @@ module Util ( replaceIf, replaceEq, replaceSeparators, unifyPath, (-/-), chunksOfSize, - putColoured, redError, redError_ + putColoured, redError, redError_, + bimap ) where import Data.Char @@ -65,3 +66,7 @@ redError msg = do redError_ :: String -> Action () redError_ = void . redError + +-- Depending on Data.Bifunctor only for this function seems an overkill +bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) +bimap f g (x, y) = (f x, g y) From git at git.haskell.org Thu Oct 26 23:31:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (4364462) Message-ID: <20171026233158.EE0AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/436446265ec493014808d9b19dc1f0883bb3e9a8/ghc >--------------------------------------------------------------- commit 436446265ec493014808d9b19dc1f0883bb3e9a8 Author: Andrey Mokhov Date: Tue Jul 28 02:24:04 2015 +0100 Clean up. >--------------------------------------------------------------- 436446265ec493014808d9b19dc1f0883bb3e9a8 src/Oracles/PackageData.hs | 2 +- src/Rules/Actions.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 579312f..fd30cc3 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -90,6 +90,6 @@ packageDataOracle = do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> do + addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> pkgData (unifyPath file) return () diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d91cd84..2730c55 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -50,7 +50,7 @@ interestingInfo builder ss = case builder of Gcc _ -> prefixAndSuffix 0 4 ss GccM _ -> prefixAndSuffix 0 1 ss Ghc _ -> prefixAndSuffix 0 4 ss - --GhcM _ -> prefixAndSuffix 1 1 ss + GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss GhcCabal -> prefixAndSuffix 3 0 ss _ -> ss From git at git.haskell.org Thu Oct 26 23:31:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport Development.Shake.Util (062e6b2) Message-ID: <20171026233155.AD7973A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/062e6b2ad5dc4be679f14f9b5a8ecbd99febc54b/ghc >--------------------------------------------------------------- commit 062e6b2ad5dc4be679f14f9b5a8ecbd99febc54b Author: Ben Gamari Date: Thu Dec 24 14:38:53 2015 +0100 Base: Don't reexport Development.Shake.Util >--------------------------------------------------------------- 062e6b2ad5dc4be679f14f9b5a8ecbd99febc54b src/Base.hs | 2 -- src/Rules/Dependencies.hs | 1 + 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 1012d4e..25a69df 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,7 +12,6 @@ module Base ( module Development.Shake, module Development.Shake.Classes, module Development.Shake.FilePath, - module Development.Shake.Util, -- * Paths shakeFilesPath, configPath, sourcePath, programInplacePath, @@ -38,7 +37,6 @@ import Data.Monoid import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes import Development.Shake.FilePath -import Development.Shake.Util import System.Console.ANSI import qualified System.Directory as IO import System.IO diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index a2f5aa2..88e97b2 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -7,6 +7,7 @@ import Rules.Actions import Rules.Generate import Rules.Resources import Settings +import Development.Shake.Util (parseMakefile) buildPackageDependencies :: Resources -> PartialTarget -> Rules () buildPackageDependencies _ target @ (PartialTarget stage pkg) = From git at git.haskell.org Thu Oct 26 23:31:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:31:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Reexport `MonadTrans` instead of `Reader` (6472042) Message-ID: <20171026233159.3209D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6472042ba8fddbc721b1bc6ae322a58212b5fe32/ghc >--------------------------------------------------------------- commit 6472042ba8fddbc721b1bc6ae322a58212b5fe32 Author: Ben Gamari Date: Thu Dec 24 14:35:31 2015 +0100 Base: Reexport `MonadTrans` instead of `Reader` The former is much more common than the latter. >--------------------------------------------------------------- 6472042ba8fddbc721b1bc6ae322a58212b5fe32 src/Base.hs | 2 +- src/Builder.hs | 2 ++ src/Expression.hs | 2 ++ src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 2 ++ src/Target.hs | 2 ++ 6 files changed, 11 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index aa9861b..fb0eed7 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -2,11 +2,11 @@ module Base ( -- * General utilities module Control.Applicative, module Control.Monad.Extra, - module Control.Monad.Reader, module Data.Function, module Data.List, module Data.Maybe, module Data.Monoid, + MonadTrans(lift), -- * Shake module Development.Shake, diff --git a/src/Builder.hs b/src/Builder.hs index b6fd228..78f8376 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -3,6 +3,8 @@ module Builder ( Builder (..), builderPath, getBuilderPath, specified, needBuilder ) where +import Control.Monad.Trans.Reader + import Base import GHC.Generics (Generic) import Oracles diff --git a/src/Expression.hs b/src/Expression.hs index 0d47314..a83ea15 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -24,6 +24,8 @@ module Expression ( module Way ) where +import Control.Monad.Trans.Reader + import Base import Package import Builder diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 47ea75d..d40b762 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -4,6 +4,8 @@ module Oracles.Config.Flag ( ghcWithNativeCodeGen, supportsSplitObjects ) where +import Control.Monad.Trans.Reader + import Base import Oracles.Config import Oracles.Config.Setting diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 81e2924..b0c6da3 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -6,6 +6,8 @@ module Oracles.Config.Setting ( ghcCanonVersion, cmdLineLengthLimit ) where +import Control.Monad.Trans.Reader + import Base import Oracles.Config import Stage diff --git a/src/Target.hs b/src/Target.hs index 2060d04..25967b4 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -3,6 +3,8 @@ module Target ( Target (..), PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay ) where +import Control.Monad.Trans.Reader + import Base import Builder import GHC.Generics (Generic) From git at git.haskell.org Thu Oct 26 23:32:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor findModuleFiles and add comments. (0be1b62) Message-ID: <20171026233203.062353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0be1b62e3ca05ce9e4c3da40e972aab9e42f991f/ghc >--------------------------------------------------------------- commit 0be1b62e3ca05ce9e4c3da40e972aab9e42f991f Author: Andrey Mokhov Date: Sat Aug 1 00:19:04 2015 +0100 Refactor findModuleFiles and add comments. >--------------------------------------------------------------- 0be1b62e3ca05ce9e4c3da40e972aab9e42f991f src/Settings/Util.hs | 62 ++++++++++++++++++++++++++++------------------------ src/Util.hs | 11 +++++++++- 2 files changed, 44 insertions(+), 29 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 1901a8c..3ea13e3 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -5,7 +5,7 @@ module Settings.Util ( getFlag, getSetting, getSettingList, getPkgData, getPkgDataList, getPackagePath, getTargetPath, getTargetDirectory, - getHsSources, getSourceFiles, + getHsSources, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -78,44 +78,50 @@ getHsSources = do path <- getTargetPath pkgPath <- getPackagePath srcDirs <- getPkgDataList SrcDirs + + let buildPath = path -/- "build" + dirs = (buildPath -/- "autogen") : map (pkgPath -/-) srcDirs + + (foundSources, missingSources) <- findModuleFiles dirs "*hs" + + -- Generated source files will live in buildPath and have extension "hs" + let generatedSources = map (\f -> buildPath -/- f <.> "hs") missingSources + + return $ foundSources ++ generatedSources + +-- Given a module name extract the directory and file names, e.g.: +-- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +decodeModule :: String -> (FilePath, String) +decodeModule = splitFileName . replaceEq '.' '/' + +-- findModuleFiles scans a list of given directories and finds files matching a +-- given extension pattern (e.g., "*hs") that correspond to modules of the +-- currently built package. Missing module files are returned in a separate +-- list. The returned pair contains the following: +-- * a list of found module files, with paths being relative to one of given +-- directories, e.g. "codeGen/CodeGen/Platform.hs" for the compiler package. +-- * a list of module files that have not been found, with paths being relative +-- to the module directory, e.g. "CodeGen/Platform", and with no extension. +findModuleFiles :: [FilePath] -> FilePattern -> Expr ([FilePath], [FilePath]) +findModuleFiles dirs ext = do modules <- getPkgDataList Modules - let buildPath = path -/- "build" - autogenPath = buildPath -/- "autogen" - dirs = autogenPath : map (pkgPath -/-) srcDirs - decodedMods = sort $ map decodeModule modules + let decodedMods = sort . map decodeModule $ modules modDirFiles = map (bimap head sort . unzip) - $ groupBy ((==) `on` fst) decodedMods + . groupBy ((==) `on` fst) $ decodedMods result <- lift . fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do - let files = [ dir -/- mDir -/- mFile <.> "*hs" | mFile <- mFiles ] + let files = [ dir -/- mDir -/- mFile <.> ext | mFile <- mFiles ] found <- fmap (map unifyPath) $ getDirectoryFiles "" files return (found, (mDir, map takeBaseName found)) - let foundSources = concatMap fst result + let foundFiles = concatMap fst result foundMods = [ (d, f) | (d, fs) <- map snd result, f <- fs ] - leftMods = decodedMods \\ sort foundMods - genSources = map (\(d, f) -> buildPath -/- d -/- f <.> "hs") leftMods - - return $ foundSources ++ genSources - --- Given a module name extract the directory and file names, e.g.: --- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") -decodeModule :: String -> (FilePath, FilePath) -decodeModule = splitFileName . replaceEq '.' '/' + missingMods = decodedMods `minusOrd` sort foundMods + missingFiles = map (uncurry (-/-)) missingMods - -- getSourceFiles paths [".hs", ".lhs"] - --- Find all source files in specified paths and with given extensions -getSourceFiles :: [FilePath] -> [String] -> Expr [FilePath] -getSourceFiles paths exts = do - modules <- getPkgDataList Modules - let modPaths = map (replaceEq '.' '/') modules - candidates = [ p -/- m ++ e | p <- paths, m <- modPaths, e <- exts ] - files <- lift $ filterM (doesDirectoryExist . takeDirectory) candidates - result <- lift $ getDirectoryFiles "" files - return $ map unifyPath result + return (foundFiles, missingFiles) -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal appendCcArgs :: [String] -> Args diff --git a/src/Util.hs b/src/Util.hs index fd33e73..31c0e6a 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -6,7 +6,7 @@ module Util ( unifyPath, (-/-), chunksOfSize, putColoured, redError, redError_, - bimap + bimap, minusOrd ) where import Data.Char @@ -70,3 +70,12 @@ redError_ = void . redError -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) + +-- Depending on Data.List.Ordered only for this function seems an overkill +minusOrd :: Ord a => [a] -> [a] -> [a] +minusOrd [] _ = [] +minusOrd xs [] = xs +minusOrd (x:xs) (y:ys) = case compare x y of + LT -> x : minusOrd xs (y:ys) + EQ -> minusOrd xs ys + GT -> minusOrd (x:xs) ys From git at git.haskell.org Thu Oct 26 23:32:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport `System.Console.ANSI` (f05d78d) Message-ID: <20171026233203.3DBF33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f05d78d92e3fde319e2963806406074868a0a4f0/ghc >--------------------------------------------------------------- commit f05d78d92e3fde319e2963806406074868a0a4f0 Author: Ben Gamari Date: Thu Dec 24 14:32:38 2015 +0100 Base: Don't reexport `System.Console.ANSI` This wasn't even used it seems >--------------------------------------------------------------- f05d78d92e3fde319e2963806406074868a0a4f0 src/Base.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 3c62ed5..aa9861b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,7 +22,6 @@ module Base ( -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, - module System.Console.ANSI, -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, quote, chunksOfSize, From git at git.haskell.org Thu Oct 26 23:32:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up and optimise performance. (7a936b6) Message-ID: <20171026233206.7A38F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7a936b6313920818057e807b6898390f7c7df2f8/ghc >--------------------------------------------------------------- commit 7a936b6313920818057e807b6898390f7c7df2f8 Author: Andrey Mokhov Date: Sat Aug 1 12:02:45 2015 +0100 Clean up and optimise performance. >--------------------------------------------------------------- 7a936b6313920818057e807b6898390f7c7df2f8 src/Oracles/DependencyList.hs | 12 ++++++------ src/Settings/Util.hs | 19 +++++++++++-------- src/Util.hs | 14 ++++++++++++-- 3 files changed, 29 insertions(+), 16 deletions(-) diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs index 0ad9267..1ffc46d 100644 --- a/src/Oracles/DependencyList.hs +++ b/src/Oracles/DependencyList.hs @@ -21,7 +21,7 @@ newtype DependencyListKey = DependencyListKey (FilePath, FilePath) dependencyList :: FilePath -> FilePath -> Action [FilePath] dependencyList depFile objFile = do res <- askOracle $ DependencyListKey (depFile, objFile) - return $ fromMaybe [] res + return . fromMaybe [] $ res -- Oracle for 'path/dist/*.deps' files dependencyListOracle :: Rules () @@ -30,11 +30,11 @@ dependencyListOracle = do need [file] putOracle $ "Reading " ++ file ++ "..." contents <- parseMakefile <$> (liftIO $ readFile file) - return $ Map.fromList - $ map (bimap unifyPath (map unifyPath)) - $ map (bimap head concat . unzip) - $ groupBy ((==) `on` fst) - $ sortBy (compare `on` fst) contents + return . Map.fromList + . map (bimap unifyPath (map unifyPath)) + . map (bimap head concat . unzip) + . groupBy ((==) `on` fst) + . sortBy (compare `on` fst) $ contents addOracle $ \(DependencyListKey (file, obj)) -> Map.lookup (unifyPath obj) <$> deps (unifyPath file) return () diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 3ea13e3..a9aabba 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -84,7 +84,7 @@ getHsSources = do (foundSources, missingSources) <- findModuleFiles dirs "*hs" - -- Generated source files will live in buildPath and have extension "hs" + -- Generated source files live in buildPath and have extension "hs" let generatedSources = map (\f -> buildPath -/- f <.> "hs") missingSources return $ foundSources ++ generatedSources @@ -103,18 +103,21 @@ decodeModule = splitFileName . replaceEq '.' '/' -- * a list of module files that have not been found, with paths being relative -- to the module directory, e.g. "CodeGen/Platform", and with no extension. findModuleFiles :: [FilePath] -> FilePattern -> Expr ([FilePath], [FilePath]) -findModuleFiles dirs ext = do +findModuleFiles dirs extension = do modules <- getPkgDataList Modules - let decodedMods = sort . map decodeModule $ modules - modDirFiles = map (bimap head sort . unzip) - . groupBy ((==) `on` fst) $ decodedMods + let decodedMods = sort . map decodeModule $ modules + modDirFiles = map (bimap head sort . unzip) + . groupBy ((==) `on` fst) $ decodedMods + matchExtension = (?==) ("*" <.> extension) result <- lift . fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do - let files = [ dir -/- mDir -/- mFile <.> ext | mFile <- mFiles ] - found <- fmap (map unifyPath) $ getDirectoryFiles "" files - return (found, (mDir, map takeBaseName found)) + let fullDir = dir -/- mDir + files <- fmap (filter matchExtension) $ getDirectoryContents fullDir + let cmp fe f = compare (dropExtension fe) f + found = intersectOrd cmp files mFiles + return (map (fullDir -/-) found, (mDir, map dropExtension found)) let foundFiles = concatMap fst result foundMods = [ (d, f) | (d, fs) <- map snd result, f <- fs ] diff --git a/src/Util.hs b/src/Util.hs index 31c0e6a..1c43801 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -6,7 +6,7 @@ module Util ( unifyPath, (-/-), chunksOfSize, putColoured, redError, redError_, - bimap, minusOrd + bimap, minusOrd, intersectOrd ) where import Data.Char @@ -71,7 +71,7 @@ redError_ = void . redError bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) --- Depending on Data.List.Ordered only for this function seems an overkill +-- Depending on Data.List.Ordered only for these two functions seems an overkill minusOrd :: Ord a => [a] -> [a] -> [a] minusOrd [] _ = [] minusOrd xs [] = xs @@ -79,3 +79,13 @@ minusOrd (x:xs) (y:ys) = case compare x y of LT -> x : minusOrd xs (y:ys) EQ -> minusOrd xs ys GT -> minusOrd (x:xs) ys + +intersectOrd :: (a -> b -> Ordering) -> [a] -> [b] -> [a] +intersectOrd cmp = loop + where + loop [] _ = [] + loop _ [] = [] + loop (x:xs) (y:ys) = case cmp x y of + LT -> loop xs (y:ys) + EQ -> x : loop xs ys + GT -> loop (x:xs) ys From git at git.haskell.org Thu Oct 26 23:32:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Eliminate re-exports from `Predicates` (74fb3f9) Message-ID: <20171026233206.A9E193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/74fb3f9e869300335ba2b8ed831b792a64696877/ghc >--------------------------------------------------------------- commit 74fb3f9e869300335ba2b8ed831b792a64696877 Author: Ben Gamari Date: Thu Dec 24 14:31:07 2015 +0100 Eliminate re-exports from `Predicates` >--------------------------------------------------------------- 74fb3f9e869300335ba2b8ed831b792a64696877 src/Predicates.hs | 5 +---- src/Rules/Library.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 1 + src/Settings/Packages.hs | 2 ++ src/Settings/User.hs | 2 +- src/Settings/Ways.hs | 1 + 6 files changed, 8 insertions(+), 7 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index abaa4be..28dd51a 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,7 +1,5 @@ +-- | Convenient predicates module Predicates ( - module GHC, - module Oracles.Config.Flag, - module Oracles.Config.Setting, stage, package, builder, stagedBuilder, file, way, stage0, stage1, stage2, notStage0, notPackage, registerPackage, splitObjects ) where @@ -10,7 +8,6 @@ import Base import Expression import GHC import Oracles.Config.Flag -import Oracles.Config.Setting -- Basic predicates stage :: Stage -> Predicate diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index eeef3ab..76fe872 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -2,8 +2,8 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Data.Char -import Base -import Expression hiding (splitPath) +import Base hiding (splitPath) +import Expression import GHC import Oracles import Predicates (splitObjects) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index ead473e..c8226fc 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -2,6 +2,7 @@ module Settings.Builders.Haddock (haddockArgs) where import Development.Shake.FilePath import Base +import GHC import Package import Expression import Oracles diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index cd856b8..61457cb 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -2,7 +2,9 @@ module Settings.Packages (getPackages, knownPackages, findKnownPackage) where import Base import Expression +import GHC import Predicates +import Oracles.Config.Setting import Settings.User -- Combining default list of packages with user modifications diff --git a/src/Settings/User.hs b/src/Settings/User.hs index e16fb27..cad2578 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -6,8 +6,8 @@ module Settings.User ( verboseCommands, turnWarningsIntoErrors ) where +import GHC import Expression -import Predicates -- No user-specific settings by default -- TODO: rename to userArgs diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 8484575..8376213 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -4,6 +4,7 @@ import Data.Monoid import Expression import Predicates import Settings.User +import Oracles.Config.Flag -- TODO: use a single expression Ways parameterised by package instead of -- expressions libWays and rtsWays From git at git.haskell.org Thu Oct 26 23:32:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Limit parallelism of ghc-cabal. (4e96a03) Message-ID: <20171026233210.5E6173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e96a03842279f4822ca2b50a7eed7993a3e815a/ghc >--------------------------------------------------------------- commit 4e96a03842279f4822ca2b50a7eed7993a3e815a Author: Andrey Mokhov Date: Sat Aug 1 14:14:42 2015 +0100 Limit parallelism of ghc-cabal. >--------------------------------------------------------------- 4e96a03842279f4822ca2b50a7eed7993a3e815a src/Rules/Data.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index d60dbfa..1114c88 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -37,7 +37,8 @@ buildPackageData target = do -- GhcCabal may run the configure script, so we depend on it -- We don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - build $ fullTarget target [cabal] GhcCabal files + buildWithResources [(ghcPkg, 1)] $ -- GhcCabal calls ghc-pkg too + fullTarget target [cabal] GhcCabal files whenM (interpretExpr target registerPackage) . buildWithResources [(ghcPkg, 1)] $ fullTarget target [cabal] (GhcPkg stage) files From git at git.haskell.org Thu Oct 26 23:32:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Expression: Don't re-export Base (ac5040d) Message-ID: <20171026233210.761903A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ac5040d2125aa94ecc25ba04dcda443e74a7d232/ghc >--------------------------------------------------------------- commit ac5040d2125aa94ecc25ba04dcda443e74a7d232 Author: Ben Gamari Date: Thu Dec 24 14:11:57 2015 +0100 Expression: Don't re-export Base The beginning of a long journey towards minimal re-exports >--------------------------------------------------------------- ac5040d2125aa94ecc25ba04dcda443e74a7d232 src/Expression.hs | 1 - src/Oracles/ArgsHash.hs | 1 + src/Predicates.hs | 1 + src/Rules.hs | 1 + src/Rules/Actions.hs | 1 + src/Rules/Cabal.hs | 1 + src/Rules/Compile.hs | 1 + src/Rules/Data.hs | 1 + src/Rules/Dependencies.hs | 1 + src/Rules/Documentation.hs | 1 + src/Rules/Generate.hs | 1 + src/Rules/Generators/ConfigHs.hs | 1 + src/Rules/Generators/GhcAutoconfH.hs | 1 + src/Rules/Generators/GhcBootPlatformH.hs | 1 + src/Rules/Generators/GhcPlatformH.hs | 1 + src/Rules/Generators/VersionHs.hs | 1 + src/Rules/Install.hs | 1 + src/Rules/Library.hs | 1 + src/Rules/Program.hs | 1 + src/Settings.hs | 7 ++++--- src/Settings/Args.hs | 2 ++ src/Settings/Builders/Ar.hs | 1 + src/Settings/Builders/DeriveConstants.hs | 1 + src/Settings/Builders/Gcc.hs | 2 ++ src/Settings/Builders/Ghc.hs | 1 + src/Settings/Builders/GhcCabal.hs | 14 ++++++++++++++ src/Settings/Builders/GhcPkg.hs | 2 ++ src/Settings/Builders/Haddock.hs | 3 +++ src/Settings/Builders/Hsc2Hs.hs | 4 ++++ src/Settings/Packages.hs | 1 + src/Settings/TargetDirectory.hs | 1 + src/Settings/Ways.hs | 1 + 32 files changed, 55 insertions(+), 4 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ac5040d2125aa94ecc25ba04dcda443e74a7d232 From git at git.haskell.org Thu Oct 26 23:32:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use fine-grain dependencies in buildPackageDependencies. (4aabd6f) Message-ID: <20171026233214.5E2A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4aabd6f2c6818c237b569a4d807e1a29ad72f0f0/ghc >--------------------------------------------------------------- commit 4aabd6f2c6818c237b569a4d807e1a29ad72f0f0 Author: Andrey Mokhov Date: Sat Aug 1 14:16:12 2015 +0100 Use fine-grain dependencies in buildPackageDependencies. >--------------------------------------------------------------- 4aabd6f2c6818c237b569a4d807e1a29ad72f0f0 src/Rules/Dependencies.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 251a233..656e853 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -17,17 +17,17 @@ buildPackageDependencies target = pkg = Target.package target path = targetPath stage pkg buildPath = path -/- "build" + dropBuild = (pkgPath pkg ++) . drop (length buildPath) in do - (buildPath -/- "haskell.deps") %> \file -> do - srcs <- interpretExpr target getHsSources - build $ fullTarget target srcs (GhcM stage) [file] + (buildPath "*.c.deps") %> \depFile -> do + let srcFile = dropBuild . dropExtension $ depFile + build $ fullTarget target [srcFile] (GccM stage) [depFile] (buildPath -/- "c.deps") %> \file -> do srcs <- pkgDataList $ CSrcs path - deps <- forM srcs $ \src -> do - let srcFile = pkgPath pkg -/- src - depFile = buildPath -/- takeFileName src <.> "deps" - build $ fullTarget target [srcFile] (GccM stage) [depFile] - liftIO . readFile $ depFile + deps <- forM srcs $ \src -> readFile' $ buildPath -/- src <.> "deps" writeFileChanged file (concat deps) - liftIO $ removeFiles buildPath ["*.c.deps"] + + (buildPath -/- "haskell.deps") %> \file -> do + srcs <- interpretExpr target getHsSources + build $ fullTarget target srcs (GhcM stage) [file] From git at git.haskell.org Thu Oct 26 23:32:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Builder: Add haddocks (30484e2) Message-ID: <20171026233214.72F4B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30484e290251d2b765f409fb2498fd770b987bc6/ghc >--------------------------------------------------------------- commit 30484e290251d2b765f409fb2498fd770b987bc6 Author: Ben Gamari Date: Thu Dec 24 14:47:19 2015 +0100 Builder: Add haddocks >--------------------------------------------------------------- 30484e290251d2b765f409fb2498fd770b987bc6 src/Builder.hs | 17 +++++++++-------- 1 file changed, 9 insertions(+), 8 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 78f8376..0174dad 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -10,12 +10,12 @@ import GHC.Generics (Generic) import Oracles import Stage --- A Builder is an external command invoked in separate process using Shake.cmd +-- | A 'Builder' is an external command invoked in separate process using 'Shake.cmd' -- --- Ghc Stage0 is the bootstrapping compiler --- Ghc StageN, N > 0, is the one built on stage (N - 1) --- GhcPkg Stage0 is the bootstrapping GhcPkg --- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) +-- @Ghc Stage0@ is the bootstrapping compiler +-- @Ghc StageN@, N > 0, is the one built on stage (N - 1) +-- @GhcPkg Stage0@ is the bootstrapping @GhcPkg@ +-- @GhcPkg StageN@, N > 0, is the one built in Stage0 (TODO: need only Stage1?) -- TODO: Do we really need HsCpp builder? Can't we use a generic Cpp -- builder instead? It would also be used instead of GccM. -- TODO: rename Gcc to CCompiler? We sometimes use gcc and sometimes clang. @@ -73,7 +73,8 @@ builderKey builder = case builder of Objdump -> "objdump" Unlit -> "unlit" --- TODO: Paths to some builders should be determined using defaultProgramPath +-- | Determine the location of a 'Builder' +-- TODO: Paths to some builders should be determined using 'defaultProgramPath' builderPath :: Builder -> Action FilePath builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ @@ -87,8 +88,8 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- Make sure a builder exists on the given path and rebuild it if out of date. --- If laxDependencies is True then we do not rebuild GHC even if it is out of +-- | Make sure a builder exists on the given path and rebuild it if out of date. +-- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). needBuilder :: Bool -> Builder -> Action () needBuilder laxDependencies builder = do From git at git.haskell.org Thu Oct 26 23:32:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to using Distribution package for parsing cabal files. (f1249da) Message-ID: <20171026233217.D5C4E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f1249daba280044fc478516d00db75689e128333/ghc >--------------------------------------------------------------- commit f1249daba280044fc478516d00db75689e128333 Author: Andrey Mokhov Date: Sat Aug 1 16:57:13 2015 +0100 Switch to using Distribution package for parsing cabal files. >--------------------------------------------------------------- f1249daba280044fc478516d00db75689e128333 src/Settings/GhcCabal.hs | 28 +++++++++++++++------------- 1 file changed, 15 insertions(+), 13 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 2c475ab..a3d43f7 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -16,8 +16,11 @@ import Settings.User import Settings.Ways import Settings.Util import Settings.Packages -import Data.List -import Control.Applicative +import Data.Version +import qualified Distribution.Package as D +import qualified Distribution.PackageDescription as D +import qualified Distribution.Verbosity as D +import qualified Distribution.PackageDescription.Parse as D cabalArgs :: Args cabalArgs = builder GhcCabal ? do @@ -33,7 +36,7 @@ cabalArgs = builder GhcCabal ? do , libraryArgs , with HsColour , configureArgs - , stage0 ? packageConstraints + , packageConstraints , withStaged Gcc , notStage0 ? with Ld , with Ar @@ -92,20 +95,19 @@ bootPackageDbArgs = do dllArgs :: Args dllArgs = arg "" +-- TODO: speed up by caching the result in Shake database? packageConstraints :: Args -packageConstraints = do +packageConstraints = stage0 ? do pkgs <- getPackages constraints <- lift $ forM pkgs $ \pkg -> do - let cabal = pkgPath pkg -/- pkgCabal pkg - prefix = dropExtension (pkgCabal pkg) ++ " == " + let cabal = pkgPath pkg -/- pkgCabal pkg need [cabal] - content <- lines <$> liftIO (readFile cabal) - let vs = filter (("ersion:" `isPrefixOf`) . drop 1) content - case vs of - [v] -> return $ prefix ++ dropWhile (not . isDigit) v - _ -> redError $ "Cannot determine package version in '" - ++ cabal ++ "'." - append $ concatMap (\c -> ["--constraint", c]) $ constraints + description <- liftIO $ D.readPackageDescription D.silent cabal + let identifier = D.package . D.packageDescription $ description + version = showVersion . D.pkgVersion $ identifier + D.PackageName name = D.pkgName $ identifier + return $ name ++ " == " ++ version + append . concatMap (\c -> ["--constraint", c]) $ constraints -- TODO: should be in a different file -- TODO: put all validating options together in one file From git at git.haskell.org Thu Oct 26 23:32:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GhcCabal: Simplify imports (0be2c4b) Message-ID: <20171026233218.0381E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0be2c4bb4b02cb74322191e72b042688603af5b4/ghc >--------------------------------------------------------------- commit 0be2c4bb4b02cb74322191e72b042688603af5b4 Author: Ben Gamari Date: Thu Dec 24 14:44:16 2015 +0100 GhcCabal: Simplify imports >--------------------------------------------------------------- 0be2c4bb4b02cb74322191e72b042688603af5b4 src/Settings/Builders/GhcCabal.hs | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 7905a2c..bd95cfc 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -3,13 +3,7 @@ module Settings.Builders.GhcCabal ( customPackageArgs, ccArgs, cppArgs, ccWarnings, argStagedSettingList, needDll0 ) where -import Data.Monoid -import Control.Monad.Trans.Class -import Control.Monad.Extra - -import Development.Shake -import Development.Shake.FilePath -import Base ((-/-), bootPackageConstraints) +import Base import Oracles.Config.Setting import Oracles.Config.Flag import GHC From git at git.haskell.org Thu Oct 26 23:32:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Base.hs with Shake imports and build paths. (44ce571) Message-ID: <20171026233221.5770F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44ce57199610244416d9c003de42dbca1e1beed0/ghc >--------------------------------------------------------------- commit 44ce57199610244416d9c003de42dbca1e1beed0 Author: Andrey Mokhov Date: Sat Aug 1 17:18:52 2015 +0100 Add Base.hs with Shake imports and build paths. >--------------------------------------------------------------- 44ce57199610244416d9c003de42dbca1e1beed0 src/Base.hs | 20 ++++++++++++++++++++ src/Builder.hs | 1 + src/Expression.hs | 2 +- src/Main.hs | 4 ++-- src/Oracles/ArgsHash.hs | 3 +-- src/Oracles/Base.hs | 13 +------------ src/Oracles/DependencyList.hs | 1 + src/Oracles/Flag.hs | 1 + src/Oracles/PackageData.hs | 1 + src/Oracles/Setting.hs | 1 + src/Oracles/WindowsRoot.hs | 1 + src/Package.hs | 2 +- src/Rules.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Config.hs | 6 ++---- src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Oracles.hs | 1 + src/Rules/Package.hs | 2 +- src/Settings/GhcCabal.hs | 2 +- src/Settings/Util.hs | 2 +- src/Stage.hs | 2 +- src/Target.hs | 2 +- src/Util.hs | 4 +--- src/Way.hs | 5 ++--- 25 files changed, 47 insertions(+), 37 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 44ce57199610244416d9c003de42dbca1e1beed0 From git at git.haskell.org Thu Oct 26 23:32:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #36 from bgamari/reexport (84af166) Message-ID: <20171026233221.737533A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84af1661707ed82d1b378d02ce712ecc212535f5/ghc >--------------------------------------------------------------- commit 84af1661707ed82d1b378d02ce712ecc212535f5 Merge: 58d7fcc 30484e2 Author: Andrey Mokhov Date: Mon Dec 28 13:09:27 2015 +0000 Merge pull request #36 from bgamari/reexport Begin paring down reexports >--------------------------------------------------------------- 84af1661707ed82d1b378d02ce712ecc212535f5 src/Base.hs | 11 ++--------- src/Builder.hs | 19 +++++++++++-------- src/Expression.hs | 3 ++- src/Oracles/ArgsHash.hs | 1 + src/Oracles/Config.hs | 1 + src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 2 ++ src/Oracles/PackageData.hs | 1 + src/Oracles/WindowsRoot.hs | 1 + src/Predicates.hs | 6 ++---- src/Rules.hs | 1 + src/Rules/Actions.hs | 1 + src/Rules/Cabal.hs | 1 + src/Rules/Compile.hs | 1 + src/Rules/Data.hs | 1 + src/Rules/Dependencies.hs | 2 ++ src/Rules/Documentation.hs | 1 + src/Rules/Generate.hs | 1 + src/Rules/Generators/ConfigHs.hs | 1 + src/Rules/Generators/GhcAutoconfH.hs | 1 + src/Rules/Generators/GhcBootPlatformH.hs | 1 + src/Rules/Generators/GhcPlatformH.hs | 1 + src/Rules/Generators/VersionHs.hs | 1 + src/Rules/Install.hs | 1 + src/Rules/Library.hs | 5 ++++- src/Rules/Program.hs | 3 +++ src/Settings.hs | 7 ++++--- src/Settings/Args.hs | 2 ++ src/Settings/Builders/Ar.hs | 1 + src/Settings/Builders/DeriveConstants.hs | 1 + src/Settings/Builders/Gcc.hs | 2 ++ src/Settings/Builders/Ghc.hs | 1 + src/Settings/Builders/GhcCabal.hs | 8 ++++++++ src/Settings/Builders/GhcPkg.hs | 2 ++ src/Settings/Builders/Haddock.hs | 4 ++++ src/Settings/Builders/Hsc2Hs.hs | 4 ++++ src/Settings/Packages.hs | 3 +++ src/Settings/TargetDirectory.hs | 1 + src/Settings/User.hs | 2 +- src/Settings/Ways.hs | 2 ++ src/Target.hs | 2 ++ 41 files changed, 85 insertions(+), 27 deletions(-) From git at git.haskell.org Thu Oct 26 23:32:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Cache computation of boot package constraints in a file. (8e9fe8d) Message-ID: <20171026233225.084EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e9fe8d6f6ddbe681073baf1414403a14fe7c8f0/ghc >--------------------------------------------------------------- commit 8e9fe8d6f6ddbe681073baf1414403a14fe7c8f0 Author: Andrey Mokhov Date: Sat Aug 1 18:23:49 2015 +0100 Cache computation of boot package constraints in a file. >--------------------------------------------------------------- 8e9fe8d6f6ddbe681073baf1414403a14fe7c8f0 src/Base.hs | 5 ++++- src/Main.hs | 1 + src/Rules.hs | 5 ++--- src/Rules/Cabal.hs | 29 +++++++++++++++++++++++++++++ src/Rules/Package.hs | 4 +--- src/Settings/Args.hs | 2 +- src/Settings/GhcCabal.hs | 17 +---------------- 7 files changed, 39 insertions(+), 24 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7cf3a4e..5b022e8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,5 +1,5 @@ module Base ( - shakeFilesPath, configPath, + shakeFilesPath, configPath, bootPackageConstraints, module Development.Shake, module Development.Shake.Util, module Development.Shake.Config, @@ -18,3 +18,6 @@ shakeFilesPath = "_build/" configPath :: FilePath configPath = "shake/cfg/" + +bootPackageConstraints :: FilePath +bootPackageConstraints = shakeFilesPath ++ "boot-package-constraints" diff --git a/src/Main.hs b/src/Main.hs index c7e076a..ffbd7c0 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,6 +3,7 @@ import Rules main = shakeArgs shakeOptions{shakeFiles = shakeFilesPath} $ do oracleRules -- see module Rules.Oracles + cabalRules -- see module Rules.Cabal packageRules -- see module Rules configRules -- see module Rules.Config generateTargets -- see module Rules diff --git a/src/Rules.hs b/src/Rules.hs index 6d153e1..002eda2 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,13 +1,12 @@ module Rules ( - generateTargets, packageRules, oracleRules, - module Rules.Config, - module Rules.Package, + oracleRules, cabalRules, configRules, packageRules, generateTargets ) where import Base import Util import Stage import Expression +import Rules.Cabal import Rules.Config import Rules.Package import Rules.Oracles diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs new file mode 100644 index 0000000..adcb57e --- /dev/null +++ b/src/Rules/Cabal.hs @@ -0,0 +1,29 @@ +module Rules.Cabal (cabalRules) where + +import Base +import Util +import Stage +import Package +import Expression +import Settings.Packages +import Data.List +import Data.Version +import qualified Distribution.Package as D +import qualified Distribution.PackageDescription as D +import qualified Distribution.Verbosity as D +import qualified Distribution.PackageDescription.Parse as D + +cabalRules :: Rules () +cabalRules = + -- Cache boot package constraints (to be used in cabalArgs) + bootPackageConstraints %> \file -> do + pkgs <- interpret (stageTarget Stage0) packages + constraints <- forM (sort pkgs) $ \pkg -> do + let cabal = pkgPath pkg -/- pkgCabal pkg + need [cabal] + descr <- liftIO $ D.readPackageDescription D.silent cabal + let identifier = D.package . D.packageDescription $ descr + version = showVersion . D.pkgVersion $ identifier + D.PackageName name = D.pkgName $ identifier + return $ name ++ " == " ++ version + writeFileChanged file . unlines $ constraints diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index a6365e8..ff64832 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -1,6 +1,4 @@ -module Rules.Package ( - buildPackage - ) where +module Rules.Package (buildPackage) where import Base import Expression diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index be6ac42..d698017 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -2,12 +2,12 @@ module Settings.Args ( args ) where +import Expression import Settings.User import Settings.GhcM import Settings.GccM import Settings.GhcPkg import Settings.GhcCabal -import Expression args :: Args args = defaultArgs <> userArgs diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 092f97a..315df12 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -15,12 +15,6 @@ import Oracles.Setting import Settings.User import Settings.Ways import Settings.Util -import Settings.Packages -import Data.Version -import qualified Distribution.Package as D -import qualified Distribution.PackageDescription as D -import qualified Distribution.Verbosity as D -import qualified Distribution.PackageDescription.Parse as D cabalArgs :: Args cabalArgs = builder GhcCabal ? do @@ -95,18 +89,9 @@ bootPackageDbArgs = do dllArgs :: Args dllArgs = arg "" --- TODO: speed up by caching the result in Shake database? packageConstraints :: Args packageConstraints = stage0 ? do - pkgs <- getPackages - constraints <- lift $ forM pkgs $ \pkg -> do - let cabal = pkgPath pkg -/- pkgCabal pkg - need [cabal] - description <- liftIO $ D.readPackageDescription D.silent cabal - let identifier = D.package . D.packageDescription $ description - version = showVersion . D.pkgVersion $ identifier - D.PackageName name = D.pkgName $ identifier - return $ name ++ " == " ++ version + constraints <- lift . readFileLines $ bootPackageConstraints append . concatMap (\c -> ["--constraint", c]) $ constraints -- TODO: should be in a different file From git at git.haskell.org Thu Oct 26 23:32:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export Data.Monoid from Expression. (024b562) Message-ID: <20171026233225.154C43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/024b5625e53789755a0af096b7a9438e8e33cc8c/ghc >--------------------------------------------------------------- commit 024b5625e53789755a0af096b7a9438e8e33cc8c Author: Andrey Mokhov Date: Mon Dec 28 14:28:36 2015 +0000 Re-export Data.Monoid from Expression. >--------------------------------------------------------------- 024b5625e53789755a0af096b7a9438e8e33cc8c src/Expression.hs | 2 ++ src/Rules/Program.hs | 2 +- 2 files changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Expression.hs b/src/Expression.hs index a83ea15..2b7ef9a 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -18,6 +18,7 @@ module Expression ( getInput, getOutput, -- * Re-exports + module Data.Monoid, module Builder, module Package, module Stage, @@ -25,6 +26,7 @@ module Expression ( ) where import Control.Monad.Trans.Reader +import Data.Monoid import Base import Package diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 781231f..0199071 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -3,7 +3,7 @@ module Rules.Program (buildProgram) where import Data.Char import Base -import Expression hiding (splitPath) +import Expression import GHC hiding (ghci) import Oracles import Rules.Actions From git at git.haskell.org Thu Oct 26 23:32:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Configure packages in dependency order, refactor resources. (49c3bb1) Message-ID: <20171026233228.CD18E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49c3bb1f7da2677b7ca95ae6db5abee302f2d408/ghc >--------------------------------------------------------------- commit 49c3bb1f7da2677b7ca95ae6db5abee302f2d408 Author: Andrey Mokhov Date: Sun Aug 2 03:28:14 2015 +0100 Configure packages in dependency order, refactor resources. >--------------------------------------------------------------- 49c3bb1f7da2677b7ca95ae6db5abee302f2d408 doc/demo.txt | 5 +++++ src/Base.hs | 6 +++++- src/Main.hs | 1 + src/Oracles/Base.hs | 4 ---- src/Oracles/DependencyList.hs | 1 - src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 33 +++++++++++++++++++++++++++++++++ src/Oracles/WindowsRoot.hs | 1 - src/Rules.hs | 6 ++++-- src/Rules/Actions.hs | 32 ++++++++++++-------------------- src/Rules/Cabal.hs | 40 +++++++++++++++++++++++++++++----------- src/Rules/Data.hs | 29 ++++++++++++++++++++++------- src/Rules/Dependencies.hs | 5 +++-- src/Rules/Oracles.hs | 2 ++ src/Rules/Package.hs | 3 ++- src/Rules/Resources.hs | 20 ++++++++++++++++++++ src/Util.hs | 11 ++++++++++- 17 files changed, 148 insertions(+), 52 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 49c3bb1f7da2677b7ca95ae6db5abee302f2d408 From git at git.haskell.org Thu Oct 26 23:32:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use orderOnly dependencies for ordering ghc-cabal invocations (avoids unnecessary rebuilds). (804a5e2) Message-ID: <20171026233228.CD8F73A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/804a5e2ccc8a844f30b897fbe743b424b0cc7efb/ghc >--------------------------------------------------------------- commit 804a5e2ccc8a844f30b897fbe743b424b0cc7efb Author: Andrey Mokhov Date: Mon Dec 28 14:56:44 2015 +0000 Use orderOnly dependencies for ordering ghc-cabal invocations (avoids unnecessary rebuilds). >--------------------------------------------------------------- 804a5e2ccc8a844f30b897fbe743b424b0cc7efb src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index e0a6239..879dc1e 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -26,7 +26,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - need $ map (pkgDataFile stage) depPkgs + orderOnly $ map (pkgDataFile stage) depPkgs need [cabalFile] buildWithResources [(resGhcCabal rs, 1)] $ From git at git.haskell.org Thu Oct 26 23:32:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: First step towards #60. (3e2cdc9) Message-ID: <20171026233232.44DBC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e2cdc9ff449c85d96de67238835e0159b5b3724/ghc >--------------------------------------------------------------- commit 3e2cdc9ff449c85d96de67238835e0159b5b3724 Author: Andrey Mokhov Date: Mon Dec 28 15:58:06 2015 +0000 First step towards #60. >--------------------------------------------------------------- 3e2cdc9ff449c85d96de67238835e0159b5b3724 src/Settings/Args.hs | 13 ++++++++----- src/Settings/Builders/Alex.hs | 11 +---------- src/Settings/Packages/Compiler.hs | 9 +++++++++ 3 files changed, 18 insertions(+), 15 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 8aa0268..6715680 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -16,21 +16,20 @@ import Settings.Builders.Happy import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld +import Settings.Packages.Compiler import Settings.User getArgs :: Expr [String] -getArgs = fromDiffExpr $ defaultArgs <> userArgs +getArgs = fromDiffExpr $ defaultBuilderArgs <> defaultPackageArgs <> userArgs --- TODO: add all other settings -- TODO: add src-hc-args = -H32m -O -- TODO: GhcStage2HcOpts=-O2 unless GhcUnregisterised -- TODO: compiler/stage1/build/Parser_HC_OPTS += -O0 -fno-ignore-interface-pragmas -- TODO: compiler/main/GhcMake_HC_OPTS += -auto-all --- TODO: compiler_stage2_HADDOCK_OPTS += --optghc=-DSTAGE=2 -- TODO: compiler/prelude/PrimOp_HC_OPTS += -fforce-recomp -- TODO: is GhcHcOpts=-Rghc-timing needed? -defaultArgs :: Args -defaultArgs = mconcat +defaultBuilderArgs :: Args +defaultBuilderArgs = mconcat [ alexArgs , arArgs , cabalArgs @@ -48,3 +47,7 @@ defaultArgs = mconcat , hsc2HsArgs , hsCppArgs , ldArgs ] + +defaultPackageArgs :: Args +defaultPackageArgs = mconcat + [ compilerArgs ] diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs index 239ae85..086bf1b 100644 --- a/src/Settings/Builders/Alex.hs +++ b/src/Settings/Builders/Alex.hs @@ -1,18 +1,9 @@ module Settings.Builders.Alex (alexArgs) where import Expression -import GHC (compiler) -import Predicates (builder, package) +import Predicates (builder) alexArgs :: Args alexArgs = builder Alex ? mconcat [ arg "-g" - , package compiler ? arg "--latin1" , arg =<< getInput , arg "-o", arg =<< getOutput ] - --- TODO: separate arguments into builder-specific and package-specific --- compilierArgs = package compiler ? builder Alex ? arg "awe" - --- args = mconcat --- [ alexArgs --- , compilerArgs ] diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs new file mode 100644 index 0000000..2ade082 --- /dev/null +++ b/src/Settings/Packages/Compiler.hs @@ -0,0 +1,9 @@ +module Settings.Packages.Compiler (compilerArgs) where + +import Expression +import GHC (compiler) +import Predicates (builder, package) + +compilerArgs :: Args +compilerArgs = package compiler ? + mconcat [ builder Alex ? arg "--latin1" ] From git at git.haskell.org Thu Oct 26 23:32:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow more parallelism in buildPackageData. (61a085c) Message-ID: <20171026233232.368A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/61a085c0310dbd583855319be36faf017fe2aaf5/ghc >--------------------------------------------------------------- commit 61a085c0310dbd583855319be36faf017fe2aaf5 Author: Andrey Mokhov Date: Sun Aug 2 03:39:17 2015 +0100 Allow more parallelism in buildPackageData. >--------------------------------------------------------------- 61a085c0310dbd583855319be36faf017fe2aaf5 src/Rules/Data.hs | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 752cde7..adc31f1 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -35,15 +35,17 @@ buildPackageData (Resources ghcCabal ghcPkg) target = do -- TODO: Is this needed? Also check out Paths_cpsa.hs. -- , "build" -/- "autogen" -/- ("Paths_" ++ name) <.> "hs" ] &%> \files -> do - -- GhcCabal may run the configure script, so we depend on it - -- We don't know who built the configure script from configure.ac - whenM (doesFileExist $ configure <.> "ac") $ need [configure] - -- We configure packages in the order of their dependencies deps <- packageDeps . dropExtension . pkgCabal $ pkg pkgs <- interpret target packages let depPkgs = concatMap (maybeToList . findPackage pkgs) deps - need $ map (\p -> targetPath stage p -/- "package-data.mk") depPkgs + + -- GhcCabal may run the configure script, so we depend on it + -- We don't know who built the configure script from configure.ac + needConfigure <- doesFileExist $ configure <.> "ac" + + need $ [ configure | needConfigure ] ++ + [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] buildWithResources [(ghcCabal, 1)] $ fullTarget target [cabal] GhcCabal files From git at git.haskell.org Thu Oct 26 23:32:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify Package. (c677b04) Message-ID: <20171026233236.5FFDD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c677b049c05d9ebae12c1ae516dc094b622d0d8f/ghc >--------------------------------------------------------------- commit c677b049c05d9ebae12c1ae516dc094b622d0d8f Author: Andrey Mokhov Date: Sun Aug 2 14:17:35 2015 +0100 Simplify Package. >--------------------------------------------------------------- c677b049c05d9ebae12c1ae516dc094b622d0d8f src/Oracles/PackageDeps.hs | 14 ++++++++------ src/Package.hs | 31 +++++++++++++++++++------------ src/Rules/Cabal.hs | 13 ++++++------- src/Rules/Data.hs | 23 ++++++++--------------- src/Settings/Default.hs | 11 +++-------- src/Settings/GhcCabal.hs | 5 +++-- 6 files changed, 47 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c677b049c05d9ebae12c1ae516dc094b622d0d8f From git at git.haskell.org Thu Oct 26 23:32:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Target fields for printing out relevant build information. (f415ad1) Message-ID: <20171026233236.6DE2E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f415ad1d528c29d0a1708e2406c4fabd99484e31/ghc >--------------------------------------------------------------- commit f415ad1d528c29d0a1708e2406c4fabd99484e31 Author: Andrey Mokhov Date: Tue Dec 29 15:39:52 2015 +0000 Use Target fields for printing out relevant build information. >--------------------------------------------------------------- f415ad1d528c29d0a1708e2406c4fabd99484e31 shaking-up-ghc.cabal | 1 + src/Builder.hs | 10 +++++++++- src/Rules/Actions.hs | 44 +++++++++++++++++--------------------------- 3 files changed, 27 insertions(+), 28 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 0e60637..f530894 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -84,6 +84,7 @@ executable ghc-shake , DeriveGeneric , FlexibleInstances , OverloadedStrings + , RecordWildCards build-depends: base , ansi-terminal >= 0.6 , Cabal >= 1.22 diff --git a/src/Builder.hs b/src/Builder.hs index 0174dad..b4b01c3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} module Builder ( - Builder (..), builderPath, getBuilderPath, specified, needBuilder + Builder (..), isStaged, builderPath, getBuilderPath, specified, needBuilder ) where import Control.Monad.Trans.Reader @@ -43,6 +43,14 @@ data Builder = Alex | Unlit deriving (Show, Eq, Generic) +isStaged :: Builder -> Bool +isStaged (Gcc _) = True +isStaged (GccM _) = True +isStaged (Ghc _) = True +isStaged (GhcM _) = True +isStaged (GhcPkg _) = True +isStaged _ = False + -- Configuration files refer to Builders as follows: builderKey :: Builder -> String builderKey builder = case builder of diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 086cb8e..8b243eb 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE RecordWildCards #-} module Rules.Actions (build, buildWithResources) where import Base @@ -22,9 +23,7 @@ buildWithResources rs target = do -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do - unless verbose $ do - putBuild $ renderBox $ [ "Running " ++ show builder ++ " with arguments:" ] - ++ map (" "++) (interestingInfo builder argList) + unless verbose $ putInfo target quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList @@ -46,28 +45,19 @@ buildWithResources rs target = do build :: Target -> Action () build = buildWithResources [] -interestingInfo :: Builder -> [String] -> [String] -interestingInfo builder ss = case builder of - Alex -> prefixAndSuffix 0 3 ss - Ar -> prefixAndSuffix 2 1 ss - DeriveConstants -> prefixAndSuffix 3 0 ss - Gcc _ -> prefixAndSuffix 0 4 ss - GccM _ -> prefixAndSuffix 0 1 ss - Ghc _ -> prefixAndSuffix 0 4 ss - GhcCabal -> prefixAndSuffix 3 0 ss - GhcM _ -> prefixAndSuffix 1 1 ss - GhcPkg _ -> prefixAndSuffix 3 0 ss - Haddock -> prefixAndSuffix 1 0 ss - Happy -> prefixAndSuffix 0 3 ss - Hsc2Hs -> prefixAndSuffix 0 3 ss - HsCpp -> prefixAndSuffix 0 1 ss - Ld -> prefixAndSuffix 4 0 ss - _ -> ss +-- Print out key information about the command being executed +putInfo :: Target.Target -> Action () +putInfo (Target.Target {..}) = putBuild $ renderBox $ + [ "Running " ++ show builder + ++ " (" ++ stageInfo + ++ "package = " ++ pkgNameString package + ++ wayInfo ++ "):" + , " input: " ++ digest inputs + , "=> output: " ++ digest outputs ] where - prefixAndSuffix n m list = - let len = length list in - if len <= n + m + 1 - then list - else take n list - ++ ["... skipping " ++ show (len - n - m) ++ " arguments ..."] - ++ drop (len - m) list + stageInfo = if isStaged builder then "" else "stage = " ++ show stage ++ ", " + wayInfo = if way == vanilla then "" else ", way = " ++ show way + digest list = case list of + [] -> "none" + [x] -> x + xs -> head xs ++ " (and " ++ show (length xs - 1) ++ " more)" From git at git.haskell.org Thu Oct 26 23:32:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Settings/Builders/Common.hs for storing common Args, refactor code. (0c9571a) Message-ID: <20171026233239.E51E73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c9571aac4cf2d4f5c84d6d2bcbf9a029e52c2ef/ghc >--------------------------------------------------------------- commit 0c9571aac4cf2d4f5c84d6d2bcbf9a029e52c2ef Author: Andrey Mokhov Date: Tue Dec 29 18:47:48 2015 +0000 Add Settings/Builders/Common.hs for storing common Args, refactor code. >--------------------------------------------------------------- 0c9571aac4cf2d4f5c84d6d2bcbf9a029e52c2ef src/Rules/Data.hs | 6 +++--- src/Settings/Builders/Ar.hs | 6 +++--- src/Settings/Builders/Common.hs | 9 +++++++++ src/Settings/Builders/DeriveConstants.hs | 3 ++- src/Settings/Builders/GhcCabal.hs | 10 +++------- 5 files changed, 20 insertions(+), 14 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 879dc1e..70c8e8a 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -8,7 +8,7 @@ import Predicates (registerPackage) import Rules.Actions import Rules.Resources import Settings -import Settings.Builders.GhcCabal +import Settings.Builders.Common -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: Resources -> PartialTarget -> Rules () @@ -42,9 +42,9 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do postProcessPackageData dataFile -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps - -- TODO: code duplication around ghcIncludeDirs priority 2.0 $ do when (pkg == hp2ps) $ dataFile %> \mk -> do + includes <- interpretPartial target $ fromDiffExpr includesArgs let prefix = "utils_hp2ps_stage" ++ show (fromEnum stage) ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" , "Reorder.c", "TopTwenty.c", "AuxFile.c" @@ -57,7 +57,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do , "INSTALL = YES" , "INSTALL_INPLACE = YES" , "DEP_EXTRA_LIBS = m" - , "CC_OPTS = " ++ unwords (map ("-I"++) ghcIncludeDirs) ] + , "CC_OPTS = " ++ unwords includes ] writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 662d5fe..dae4a82 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -26,15 +26,15 @@ arCmd path argList = do fileArgs = drop arFlagsCount argList if arSupportsAtFile then useAtFile path flagArgs fileArgs - else useSuccessiveInvokations path flagArgs fileArgs + else useSuccessiveInvocations path flagArgs fileArgs useAtFile :: FilePath -> [String] -> [String] -> Action () useAtFile path flagArgs fileArgs = withTempFile $ \tmp -> do writeFile' tmp $ unwords fileArgs cmd [path] flagArgs ('@' : tmp) -useSuccessiveInvokations :: FilePath -> [String] -> [String] -> Action () -useSuccessiveInvokations path flagArgs fileArgs = do +useSuccessiveInvocations :: FilePath -> [String] -> [String] -> Action () +useSuccessiveInvocations path flagArgs fileArgs = do maxChunk <- cmdLineLengthLimit forM_ (chunksOfSize maxChunk fileArgs) $ \argsChunk -> unit . cmd [path] $ flagArgs ++ argsChunk diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs new file mode 100644 index 0000000..fc3ed53 --- /dev/null +++ b/src/Settings/Builders/Common.hs @@ -0,0 +1,9 @@ +module Settings.Builders.Common (includesArgs) where + +import Expression + +includes :: [FilePath] +includes = [ "includes", "includes/dist-derivedconstants/header" ] + +includesArgs :: Args +includesArgs = append $ map ("-I" ++) includes diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 1f42243..ee07d34 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -7,6 +7,7 @@ import Expression import Oracles.Config.Flag import Oracles.Config.Setting import Predicates (builder, file) +import Settings.Builders.Common import Settings.Builders.GhcCabal derivedConstantsPath :: FilePath @@ -39,7 +40,7 @@ includeCcArgs = do , ccWarnings , append confCcArgs , flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER" - , append $ map ("-I" ++) ghcIncludeDirs -- TODO: fix code duplication + , includesArgs , arg "-Irts" , notM ghcWithSMP ? arg "-DNOSMP" , arg "-fcommon" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index bd95cfc..61da725 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,5 +1,5 @@ module Settings.Builders.GhcCabal ( - cabalArgs, ghcCabalHsColourArgs, ghcIncludeDirs, bootPackageDbArgs, + cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, ccArgs, cppArgs, ccWarnings, argStagedSettingList, needDll0 ) where @@ -14,6 +14,7 @@ import Stage import Expression import Predicates hiding (stage) import Settings +import Settings.Builders.Common cabalArgs :: Args cabalArgs = builder GhcCabal ? do @@ -115,13 +116,8 @@ ccWarnings = do ldArgs :: Args ldArgs = mempty -ghcIncludeDirs :: [FilePath] -ghcIncludeDirs = [ "includes", "includes/dist" - , "includes/dist-derivedconstants/header" - , "includes/dist-ghcconstants/header" ] - cppArgs :: Args -cppArgs = append $ map ("-I" ++) ghcIncludeDirs +cppArgs = includesArgs -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" From git at git.haskell.org Thu Oct 26 23:32:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up rules. (5f8abc4) Message-ID: <20171026233239.DDD983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f8abc4b283d401a7d5b5eb341cab21f799fdf63/ghc >--------------------------------------------------------------- commit 5f8abc4b283d401a7d5b5eb341cab21f799fdf63 Author: Andrey Mokhov Date: Sun Aug 2 14:36:36 2015 +0100 Clean up rules. >--------------------------------------------------------------- 5f8abc4b283d401a7d5b5eb341cab21f799fdf63 src/Rules/Config.hs | 4 ++-- src/Rules/Dependencies.hs | 4 +++- src/Util.hs | 1 - 3 files changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 5946bfb..8d886fa 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -7,10 +7,10 @@ configRules :: Rules () configRules = do configPath -/- "system.config" %> \out -> do need [configPath -/- "system.config.in", "configure"] - putColoured White "Running configure..." + putBuild "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' "configure" %> \out -> do copyFile' (configPath -/- "configure.ac") "configure.ac" - putColoured White $ "Running autoconf..." + putBuild "Running autoconf..." cmd "bash autoconf" -- TODO: get rid of 'bash' diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 92664d2..7fab8cf 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -26,7 +26,9 @@ buildPackageDependencies _ target = (buildPath -/- "c.deps") %> \file -> do srcs <- pkgDataList $ CSrcs path - deps <- forM srcs $ \src -> readFile' $ buildPath -/- src <.> "deps" + let depFiles = [ buildPath -/- src <.> "deps" | src <- srcs ] + need depFiles -- increase parallelism by needing all at once + deps <- mapM readFile' depFiles writeFileChanged file (concat deps) (buildPath -/- "haskell.deps") %> \file -> do diff --git a/src/Util.hs b/src/Util.hs index d8a4db7..70de3ec 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -64,7 +64,6 @@ putOracle = putColoured Blue putBuild :: String -> Action () putBuild = putColoured White - -- A more colourful version of error redError :: String -> Action a redError msg = do From git at git.haskell.org Thu Oct 26 23:32:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid using interpretDiff, use simpler interpret instead. (327b06e) Message-ID: <20171026233243.A9B1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/327b06e578a4194368020152bd90b8eb4193dd7a/ghc >--------------------------------------------------------------- commit 327b06e578a4194368020152bd90b8eb4193dd7a Author: Andrey Mokhov Date: Sun Aug 2 15:02:23 2015 +0100 Avoid using interpretDiff, use simpler interpret instead. >--------------------------------------------------------------- 327b06e578a4194368020152bd90b8eb4193dd7a src/Expression.hs | 10 +++++----- src/Oracles/ArgsHash.hs | 2 +- src/Rules.hs | 3 +-- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 4 ++-- src/Rules/Data.hs | 8 ++++---- src/Rules/Dependencies.hs | 2 +- src/Settings/Args.hs | 7 ++++--- src/Settings/Util.hs | 2 +- 9 files changed, 20 insertions(+), 20 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 6ec6ef4..ee8e8f3 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -8,7 +8,7 @@ module Expression ( Args, Ways, Packages, apply, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, - interpret, interpretExpr, + interpret, interpretDiff, getStage, getPackage, getBuilder, getFiles, getFile, getDependencies, getDependency, getWay, stage, package, builder, stagedBuilder, file, way @@ -141,16 +141,16 @@ removeSub :: String -> [String] -> Args removeSub prefix xs = filterSub prefix (`notElem` xs) -- Interpret a given expression in a given environment -interpretExpr :: Target -> Expr a -> Action a -interpretExpr = flip runReaderT +interpret :: Target -> Expr a -> Action a +interpret = flip runReaderT -- Extract an expression from a difference expression fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) -- Interpret a given difference expression in a given environment -interpret :: Monoid a => Target -> DiffExpr a -> Action a -interpret target = interpretExpr target . fromDiffExpr +interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a +interpretDiff target = interpret target . fromDiffExpr -- Convenient getters for target parameters getStage :: Expr Stage diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 1972638..ca0aa6c 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -22,5 +22,5 @@ askArgsHash = askOracle . ArgsHashKey -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () argsHashOracle = do - addOracle $ \(ArgsHashKey target) -> hash <$> interpret target args + addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs return () diff --git a/src/Rules.hs b/src/Rules.hs index e651325..be109f8 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -15,11 +15,10 @@ import Settings.Packages import Settings.TargetDirectory -- generateTargets needs package-data.mk files of all target packages --- TODO: make interpretDiff total generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do - pkgs <- interpret (stageTarget stage) packages + pkgs <- interpret (stageTarget stage) getPackages fmap concat . forM pkgs $ \pkg -> return [ targetPath stage pkg -/- "build/haskell.deps" , targetPath stage pkg -/- "build/c.deps" ] diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 1940a4a..d96157c 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -21,7 +21,7 @@ buildWithResources rs target = do needBuilder builder need deps path <- builderPath builder - argList <- interpret target args + argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed argsHash <- askArgsHash target withResources rs $ do diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 48db356..55d909d 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -16,7 +16,7 @@ cabalRules :: Rules () cabalRules = do -- Cache boot package constraints (to be used in cabalArgs) bootPackageConstraints %> \file -> do - pkgs <- interpret (stageTarget Stage0) packages + pkgs <- interpret (stageTarget Stage0) getPackages constraints <- forM (sort pkgs) $ \pkg -> do let cabal = pkgCabalPath pkg need [cabal] @@ -29,7 +29,7 @@ cabalRules = do -- Cache package dependencies packageDependencies %> \file -> do - pkgs <- interpret (stageTarget Stage1) packages + pkgs <- interpret (stageTarget Stage1) getPackages pkgDeps <- forM (sort pkgs) $ \pkg -> do let cabal = pkgCabalPath pkg need [cabal] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 762115c..8f365e8 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -40,16 +40,16 @@ buildPackageData (Resources ghcCabal ghcPkg) target = do -- We configure packages in the order of their dependencies deps <- packageDeps pkg - pkgs <- interpret target packages - let cmp pkg = compare (pkgName pkg) - depPkgs = intersectOrd cmp (sort pkgs) deps + pkgs <- interpret target getPackages + let cmp pkg name = compare (pkgName pkg) name + depPkgs = intersectOrd cmp (sort pkgs) deps need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] buildWithResources [(ghcCabal, 1)] $ fullTarget target [cabal] GhcCabal files -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg - whenM (interpretExpr target registerPackage) . + whenM (interpret target registerPackage) . buildWithResources [(ghcPkg, 1)] $ fullTarget target [cabal] (GhcPkg stage) files diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 7fab8cf..bee85c6 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -32,5 +32,5 @@ buildPackageDependencies _ target = writeFileChanged file (concat deps) (buildPath -/- "haskell.deps") %> \file -> do - srcs <- interpretExpr target getHsSources + srcs <- interpret target getHsSources build $ fullTarget target srcs (GhcM stage) [file] diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index d698017..4d4dd17 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -1,6 +1,4 @@ -module Settings.Args ( - args - ) where +module Settings.Args (args, getArgs) where import Expression import Settings.User @@ -12,6 +10,9 @@ import Settings.GhcCabal args :: Args args = defaultArgs <> userArgs +getArgs :: Expr [String] +getArgs = fromDiffExpr args + -- TODO: add all other settings -- TODO: add src-hc-args = -H32m -O -- TODO: GhcStage2HcOpts=-O2 unless GhcUnregisterised diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index d2daa0b..d04a12a 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -85,7 +85,7 @@ getHsSources = do (foundSources, missingSources) <- findModuleFiles dirs "*hs" -- Generated source files live in buildPath and have extension "hs" - let generatedSources = map (\f -> buildPath -/- f <.> "hs") missingSources + let generatedSources = [ buildPath -/- s <.> "hs" | s <- missingSources ] return $ foundSources ++ generatedSources From git at git.haskell.org Thu Oct 26 23:32:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose src/Settings/Builders/Gcc.hs, factor out cIncludeArgs into src/Settings/Builders/Common.hs. (bf70983) Message-ID: <20171026233243.BED7E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf70983e38c76138bf5819a2dff9109181a1f2aa/ghc >--------------------------------------------------------------- commit bf70983e38c76138bf5819a2dff9109181a1f2aa Author: Andrey Mokhov Date: Tue Dec 29 21:46:04 2015 +0000 Decompose src/Settings/Builders/Gcc.hs, factor out cIncludeArgs into src/Settings/Builders/Common.hs. >--------------------------------------------------------------- bf70983e38c76138bf5819a2dff9109181a1f2aa src/Settings/Args.hs | 4 +++- src/Settings/Builders/Common.hs | 17 ++++++++++++++++- src/Settings/Builders/Gcc.hs | 21 ++++----------------- src/Settings/Builders/Ghc.hs | 6 ++---- src/Settings/Builders/Hsc2Hs.hs | 7 ++----- src/Settings/Packages/Directory.hs | 13 +++++++++++++ 6 files changed, 40 insertions(+), 28 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 6715680..f474f8f 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -17,6 +17,7 @@ import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld import Settings.Packages.Compiler +import Settings.Packages.Directory import Settings.User getArgs :: Expr [String] @@ -50,4 +51,5 @@ defaultBuilderArgs = mconcat defaultPackageArgs :: Args defaultPackageArgs = mconcat - [ compilerArgs ] + [ compilerArgs + , directoryArgs ] diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index fc3ed53..9ed6efd 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -1,9 +1,24 @@ -module Settings.Builders.Common (includesArgs) where +module Settings.Builders.Common (includesArgs, cIncludeArgs) where +import Base import Expression +import Oracles.PackageData +import Settings includes :: [FilePath] includes = [ "includes", "includes/dist-derivedconstants/header" ] includesArgs :: Args includesArgs = append $ map ("-I" ++) includes + +cIncludeArgs :: Args +cIncludeArgs = do + stage <- getStage + pkg <- getPackage + incDirs <- getPkgDataList IncludeDirs + depDirs <- getPkgDataList DepIncludeDirs + let buildPath = targetPath stage pkg -/- "build" + mconcat [ arg $ "-I" ++ buildPath + , arg $ "-I" ++ buildPath -/- "autogen" + , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] + , append [ "-I" ++ dir | dir <- depDirs ] ] diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index fab5104..8a6b087 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -2,20 +2,14 @@ module Settings.Builders.Gcc (gccArgs, gccMArgs) where import Development.Shake.FilePath import Expression -import GHC import Oracles -import Base ((-/-)) -import Predicates (package, stagedBuilder) +import Predicates (stagedBuilder) import Settings +import Settings.Builders.Common (cIncludeArgs) --- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is --- effectively empty. I presume it was expected that GHC will be used for --- compiling all C files, but I don't know why. It seems that directory.c is the --- only file which requires special treatment when using GCC. gccArgs :: Args gccArgs = stagedBuilder Gcc ? mconcat [ commonGccArgs - , package directory ? arg "-D__GLASGOW_HASKELL__" , arg "-c", arg =<< getInput , arg "-o", arg =<< getOutput ] @@ -35,12 +29,5 @@ gccMArgs = stagedBuilder GccM ? do , arg =<< getInput ] commonGccArgs :: Args -commonGccArgs = do - pkg <- getPackage - path <- getTargetPath - iDirs <- getPkgDataList IncludeDirs - dDirs <- getPkgDataList DepIncludeDirs - ccArgs <- getPkgDataList CcArgs - mconcat [ append ccArgs - , arg $ "-I" ++ path -/- "build/autogen" - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- iDirs ++ dDirs ]] +commonGccArgs = mconcat [ append =<< getPkgDataList CcArgs + , cIncludeArgs ] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index f354458..593f0e0 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -7,6 +7,7 @@ import GHC import Predicates hiding (way, stage) import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) +import Settings.Builders.Common (cIncludeArgs) -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot @@ -114,16 +115,13 @@ includeGhcArgs = do pkg <- getPackage path <- getTargetPath srcDirs <- getPkgDataList SrcDirs - incDirs <- getPkgDataList IncludeDirs let buildPath = path -/- "build" autogenPath = buildPath -/- "autogen" mconcat [ arg "-i" , arg $ "-i" ++ buildPath , arg $ "-i" ++ autogenPath - , arg $ "-I" ++ buildPath - , arg $ "-I" ++ autogenPath , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] + , cIncludeArgs , (pkg == compiler || pkg == ghc) ? arg ("-I" ++ pkgPath compiler -/- "stage" ++ show (fromEnum stage)) , not (pkg == hp2ps || pkg == ghcCabal && stage == Stage0) ? diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 90abc82..c89caf0 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -9,6 +9,7 @@ import Oracles import Predicates (builder, stage0, notStage0) import Settings import Settings.Builders.GhcCabal hiding (cppArgs) +import Settings.Builders.Common (cIncludeArgs) templateHsc :: FilePath templateHsc = "inplace/lib/template-hsc.h" @@ -48,18 +49,14 @@ hsc2HsArgs = builder Hsc2Hs ? do getCFlags :: Expr [String] getCFlags = fromDiffExpr $ do - pkg <- getPackage path <- getTargetPath - iDirs <- getPkgDataList IncludeDirs - dDirs <- getPkgDataList DepIncludeDirs cppArgs <- getPkgDataList CppArgs depCcArgs <- getPkgDataList DepCcArgs mconcat [ ccArgs , argStagedSettingList ConfCcArgs , remove ["-O"] , argStagedSettingList ConfCppArgs - , arg $ "-I" ++ path -/- "build/autogen" - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- iDirs ++ dDirs ] + , cIncludeArgs , append cppArgs , append depCcArgs , ccWarnings diff --git a/src/Settings/Packages/Directory.hs b/src/Settings/Packages/Directory.hs new file mode 100644 index 0000000..3ff69ce --- /dev/null +++ b/src/Settings/Packages/Directory.hs @@ -0,0 +1,13 @@ +module Settings.Packages.Directory (directoryArgs) where + +import Expression +import GHC (directory) +import Predicates (stagedBuilder, package) + +-- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is +-- effectively empty. I presume it was expected that GHC will be used for +-- compiling all C files, but I don't know why. It seems that directory.c is the +-- only file which requires special treatment when using GCC. +directoryArgs :: Args +directoryArgs = package directory ? + stagedBuilder Gcc ? arg "-D__GLASGOW_HASKELL__" From git at git.haskell.org Thu Oct 26 23:32:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new source files. (73d198b) Message-ID: <20171026233247.8189D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73d198b03cc64d2200e4bcdad4a6da51d419e43a/ghc >--------------------------------------------------------------- commit 73d198b03cc64d2200e4bcdad4a6da51d419e43a Author: Andrey Mokhov Date: Wed Dec 30 01:19:36 2015 +0000 Add new source files. >--------------------------------------------------------------- 73d198b03cc64d2200e4bcdad4a6da51d419e43a shaking-up-ghc.cabal | 3 +++ 1 file changed, 3 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f530894..5ad614e 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -58,6 +58,7 @@ executable ghc-shake , Settings.Args , Settings.Builders.Alex , Settings.Builders.Ar + , Settings.Builders.Common , Settings.Builders.Gcc , Settings.Builders.GenPrimopCode , Settings.Builders.Ghc @@ -69,6 +70,8 @@ executable ghc-shake , Settings.Builders.HsCpp , Settings.Builders.Ld , Settings.Packages + , Settings.Packages.Compiler + , Settings.Packages.Directory , Settings.TargetDirectory , Settings.User , Settings.Ways From git at git.haskell.org Thu Oct 26 23:32:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename redError(_) to putError(_). (9a6f684) Message-ID: <20171026233247.6EF083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a6f68428bc2ae6ce0ec2188cb43a48938d8ff87/ghc >--------------------------------------------------------------- commit 9a6f68428bc2ae6ce0ec2188cb43a48938d8ff87 Author: Andrey Mokhov Date: Wed Aug 5 22:29:05 2015 +0100 Rename redError(_) to putError(_). >--------------------------------------------------------------- 9a6f68428bc2ae6ce0ec2188cb43a48938d8ff87 src/Builder.hs | 2 +- src/Oracles/Base.hs | 4 ++-- src/Oracles/Flag.hs | 4 ++-- src/Util.hs | 10 +++++----- 4 files changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index a148fc5..b175fac 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -58,7 +58,7 @@ builderKey builder = case builder of builderPath :: Builder -> Action String builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ - redError $ "\nCannot find path to '" ++ (builderKey builder) + putError $ "\nCannot find path to '" ++ (builderKey builder) ++ "' in configuration files." fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 5c2a252..29ec4e4 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -22,7 +22,7 @@ askConfigWithDefault key defaultAction = do Nothing -> defaultAction askConfig :: String -> Action String -askConfig key = askConfigWithDefault key . redError +askConfig key = askConfigWithDefault key . putError $ "Cannot find key '" ++ key ++ "' in configuration files." -- Oracle for configuration files @@ -31,7 +31,7 @@ configOracle = do let configFile = configPath -/- "system.config" cfg <- newCache $ \() -> do unlessM (doesFileExist $ configFile <.> "in") $ - redError_ $ "\nConfiguration file '" ++ (configFile <.> "in") + putError_ $ "\nConfiguration file '" ++ (configFile <.> "in") ++ "' is missing; unwilling to proceed." need [configFile] putOracle $ "Reading " ++ configFile ++ "..." diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index dfa0920..391ed5e 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -28,9 +28,9 @@ flag f = do SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" GhcUnregisterised -> "ghc-unregisterised" - value <- askConfigWithDefault key . redError + value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." - unless (value == "YES" || value == "NO") . redError + unless (value == "YES" || value == "NO") . putError $ "\nFlag '" ++ key ++ "' is set to '" ++ value ++ "' instead of 'YES' or 'NO'." return $ value == "YES" diff --git a/src/Util.hs b/src/Util.hs index 70de3ec..32b6478 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -4,7 +4,7 @@ module Util ( replaceIf, replaceEq, replaceSeparators, unifyPath, (-/-), chunksOfSize, - putColoured, putOracle, putBuild, redError, redError_, + putColoured, putOracle, putBuild, putError, putError_, bimap, minusOrd, intersectOrd ) where @@ -65,13 +65,13 @@ putBuild :: String -> Action () putBuild = putColoured White -- A more colourful version of error -redError :: String -> Action a -redError msg = do +putError :: String -> Action a +putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg -redError_ :: String -> Action () -redError_ = void . redError +putError_ :: String -> Action () +putError_ = void . putError -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) From git at git.haskell.org Thu Oct 26 23:32:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add knownWays and knownRtsWays to Settings.Ways. (12cecf1) Message-ID: <20171026233251.4393E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12cecf14f5205327b6520f72f8ddcb94a416fba9/ghc >--------------------------------------------------------------- commit 12cecf14f5205327b6520f72f8ddcb94a416fba9 Author: Andrey Mokhov Date: Wed Aug 5 22:31:19 2015 +0100 Add knownWays and knownRtsWays to Settings.Ways. >--------------------------------------------------------------- 12cecf14f5205327b6520f72f8ddcb94a416fba9 src/Settings/GhcCabal.hs | 1 + src/Settings/User.hs | 1 - src/Settings/Ways.hs | 16 ++++++++++++++-- 3 files changed, 15 insertions(+), 3 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index dfcb3df..5f264b2 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -15,6 +15,7 @@ import Oracles.Setting import Settings.User import Settings.Ways import Settings.Util +import Settings.Packages cabalArgs :: Args cabalArgs = builder GhcCabal ? do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 6426e82..572feb4 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,5 +1,4 @@ module Settings.User ( - module Settings.Default, userArgs, userPackages, userWays, userRtsWays, userTargetDirectory, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index c8377eb..ae4bd38 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,6 +1,7 @@ module Settings.Ways ( ways, getWays, - rtsWays, getRtsWays + rtsWays, getRtsWays, + knownWays, knownRtsWays ) where import Way @@ -8,7 +9,7 @@ import Stage import Switches import Expression import Oracles.Flag -import Settings.User +import Settings.User hiding (parallel) -- Combining default ways with user modifications ways :: Ways @@ -39,3 +40,14 @@ defaultRtsWays = do , (dynamic `elem` ways) ? append [ dynamic, debugDynamic, threadedDynamic, threadedDebugDynamic , loggingDynamic, threadedLoggingDynamic ] ] + +-- These are all ways known to the build system +knownWays :: [Way] +knownWays = [vanilla, profiling, logging, parallel, granSim] + +knownRtsWays :: [Way] +knownRtsWays = [ threaded, threadedProfiling, threadedLogging, debug + , debugProfiling, threadedDebug, threadedDebugProfiling, dynamic + , profilingDynamic, threadedProfilingDynamic, threadedDynamic + , threadedDebugDynamic, debugDynamic, loggingDynamic + , threadedLoggingDynamic ] From git at git.haskell.org Thu Oct 26 23:32:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Stage.stageString, rename runghc -> runGhc. (9e2ddcb) Message-ID: <20171026233251.4FAF23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e2ddcb188ecf614edbaeca9404d0adb77f125b3/ghc >--------------------------------------------------------------- commit 9e2ddcb188ecf614edbaeca9404d0adb77f125b3 Author: Andrey Mokhov Date: Wed Dec 30 03:02:27 2015 +0000 Add Stage.stageString, rename runghc -> runGhc. >--------------------------------------------------------------- 9e2ddcb188ecf614edbaeca9404d0adb77f125b3 src/GHC.hs | 14 +++++++------- src/Oracles/Config/Setting.hs | 8 ++++---- src/Rules/Data.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Stage.hs | 5 ++++- 6 files changed, 18 insertions(+), 15 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 859bec4..f93d92a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -5,7 +5,7 @@ module GHC ( genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, - runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, + runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -26,7 +26,7 @@ defaultKnownPackages = , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin , integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty - , primitive , process, runghc, stm, templateHaskell, terminfo, time + , primitive , process, runGhc, stm, templateHaskell, terminfo, time , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) @@ -35,7 +35,7 @@ array, base, binary, bytestring, cabal, compiler, containers, compareSizes, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, - runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package + runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -75,7 +75,7 @@ parallel = library "parallel" pretty = library "pretty" primitive = library "primitive" process = library "process" -runghc = utility "runghc" +runGhc = utility "runGhc" stm = library "stm" templateHaskell = library "template-haskell" terminfo = library "terminfo" @@ -97,17 +97,17 @@ xhtml = library "xhtml" -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal defaultTargetDirectory :: Stage -> Package -> FilePath -defaultTargetDirectory stage _ = "stage" ++ show (fromEnum stage) +defaultTargetDirectory stage _ = stageString stage -- TODO: simplify -- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg - | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) + | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing - | isProgram pkg = case stage of + | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg | otherwise = Nothing diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index b0c6da3..ace9158 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -91,10 +91,10 @@ setting key = askConfig $ case key of settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of - ConfCcArgs stage -> "conf-cc-args-stage" ++ show (fromEnum stage) - ConfCppArgs stage -> "conf-cpp-args-stage" ++ show (fromEnum stage) - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show (fromEnum stage) - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show (fromEnum stage) + ConfCcArgs stage -> "conf-cc-args-" ++ stageString stage + ConfCppArgs stage -> "conf-cpp-args-" ++ stageString stage + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-" ++ stageString stage + ConfLdLinkerArgs stage -> "conf-ld-linker-args-" ++ stageString stage GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" HsCppArgs -> "hs-cpp-args" diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 70c8e8a..a863968 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -45,7 +45,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do priority 2.0 $ do when (pkg == hp2ps) $ dataFile %> \mk -> do includes <- interpretPartial target $ fromDiffExpr includesArgs - let prefix = "utils_hp2ps_stage" ++ show (fromEnum stage) ++ "_" + let prefix = "utils_hp2ps_" ++ stageString stage ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" , "Reorder.c", "TopTwenty.c", "AuxFile.c" , "Deviation.c", "HpFile.c", "Marks.c", "Scale.c" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index ea5ed63..fd101a1 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -127,7 +127,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do file <~ generateVersionHs - when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do + when (pkg == runGhc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putSuccess $ "| Successfully generated '" ++ file ++ "'." diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 61457cb..308fb8c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -32,7 +32,7 @@ packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq , directory, filepath, ghci, ghcPrim, ghcPwd, haskeline, hpcBin - , integerLibrary, mkUserGuidePart, pretty, process, runghc, time ] + , integerLibrary, mkUserGuidePart, pretty, process, runGhc, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , notM windowsHost ? append [iservBin] diff --git a/src/Stage.hs b/src/Stage.hs index d474557..70fe6ba 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DeriveGeneric #-} -module Stage (Stage (..)) where +module Stage (Stage (..), stageString) where import Base import GHC.Generics (Generic) @@ -8,6 +8,9 @@ import GHC.Generics (Generic) data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Show, Eq, Ord, Enum, Generic) +stageString :: Stage -> String +stageString stage = "stage" ++ show (fromEnum stage) + -- Instances for storing in the Shake database instance Binary Stage instance Hashable Stage From git at git.haskell.org Thu Oct 26 23:32:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement compilePackage build rule. (098d9c1) Message-ID: <20171026233254.A90B53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/098d9c1e26a4da698eaea64a3da39bb7b0cd3838/ghc >--------------------------------------------------------------- commit 098d9c1e26a4da698eaea64a3da39bb7b0cd3838 Author: Andrey Mokhov Date: Wed Aug 5 22:31:59 2015 +0100 Implement compilePackage build rule. >--------------------------------------------------------------- 098d9c1e26a4da698eaea64a3da39bb7b0cd3838 src/Package/Compile.hs | 101 --------------------------------------- src/Rules/Compile.hs | 40 ++++++++++++++++ src/Rules/Package.hs | 3 +- src/Settings/{GccM.hs => Gcc.hs} | 26 +++++----- src/Settings/GccM.hs | 13 +---- src/Settings/{GhcM.hs => Ghc.hs} | 46 ++++++++++++------ src/Settings/GhcM.hs | 45 +---------------- src/Settings/Util.hs | 15 ------ 8 files changed, 88 insertions(+), 201 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 098d9c1e26a4da698eaea64a3da39bb7b0cd3838 From git at git.haskell.org Thu Oct 26 23:32:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Expressions.removePair function to remove pairs of arguments. (9140548) Message-ID: <20171026233254.C06073A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9140548b75f96d17e9888a21bf32a2f46d447cbe/ghc >--------------------------------------------------------------- commit 9140548b75f96d17e9888a21bf32a2f46d447cbe Author: Andrey Mokhov Date: Wed Dec 30 03:03:26 2015 +0000 Add Expressions.removePair function to remove pairs of arguments. >--------------------------------------------------------------- 9140548b75f96d17e9888a21bf32a2f46d447cbe src/Expression.hs | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/src/Expression.hs b/src/Expression.hs index 2b7ef9a..a2eaea9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -3,7 +3,8 @@ module Expression ( -- * Expressions Expr, DiffExpr, fromDiffExpr, -- ** Operators - apply, append, arg, remove, appendSub, appendSubD, filterSub, removeSub, + apply, append, arg, remove, removePair, + appendSub, appendSubD, filterSub, removeSub, -- ** Evaluation interpret, interpretPartial, interpretWithStage, interpretDiff, -- ** Predicates @@ -76,6 +77,16 @@ append x = apply (<> x) remove :: Eq a => [a] -> DiffExpr [a] remove xs = apply $ filter (`notElem` xs) +-- | Remove given pair of elements from a list expression +-- Example: removePair "-flag" "b" ["-flag", "a", "-flag", "b"] = ["-flag", "a"] +removePair :: Eq a => a -> a -> DiffExpr [a] +removePair x y = apply filterPair + where + filterPair (z1 : z2 : zs) = if x == z1 && y == z2 + then filterPair zs + else z1 : filterPair (z2 : zs) + filterPair zs = zs + -- | Apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do From git at git.haskell.org Thu Oct 26 23:32:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of redError_. (4fd1732) Message-ID: <20171026233258.C35813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fd17325b1c7921c1278a8da85544960ef07a5af/ghc >--------------------------------------------------------------- commit 4fd17325b1c7921c1278a8da85544960ef07a5af Author: Andrey Mokhov Date: Wed Aug 5 23:23:22 2015 +0100 Get rid of redError_. >--------------------------------------------------------------- 4fd17325b1c7921c1278a8da85544960ef07a5af src/Oracles/Base.hs | 4 ++-- src/Util.hs | 6 +----- 2 files changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 29ec4e4..a6abbfc 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -31,8 +31,8 @@ configOracle = do let configFile = configPath -/- "system.config" cfg <- newCache $ \() -> do unlessM (doesFileExist $ configFile <.> "in") $ - putError_ $ "\nConfiguration file '" ++ (configFile <.> "in") - ++ "' is missing; unwilling to proceed." + putError $ "\nConfiguration file '" ++ (configFile <.> "in") + ++ "' is missing; unwilling to proceed." need [configFile] putOracle $ "Reading " ++ configFile ++ "..." liftIO $ readConfigFile configFile diff --git a/src/Util.hs b/src/Util.hs index 32b6478..f00785f 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -4,13 +4,12 @@ module Util ( replaceIf, replaceEq, replaceSeparators, unifyPath, (-/-), chunksOfSize, - putColoured, putOracle, putBuild, putError, putError_, + putColoured, putOracle, putBuild, putError, bimap, minusOrd, intersectOrd ) where import Base import Data.Char -import Control.Monad import System.IO import System.Console.ANSI @@ -70,9 +69,6 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg -putError_ :: String -> Action () -putError_ = void . putError - -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) From git at git.haskell.org Thu Oct 26 23:32:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:32:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add custom predicate builderGhc for Ghc/GhcM builders. (7ca8be7) Message-ID: <20171026233258.DC69E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ca8be77837fed2ebb05d369996edd6ee5d72b8e/ghc >--------------------------------------------------------------- commit 7ca8be77837fed2ebb05d369996edd6ee5d72b8e Author: Andrey Mokhov Date: Wed Dec 30 03:04:12 2015 +0000 Add custom predicate builderGhc for Ghc/GhcM builders. >--------------------------------------------------------------- 7ca8be77837fed2ebb05d369996edd6ee5d72b8e src/Predicates.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 28dd51a..7f590f4 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,6 +1,6 @@ -- | Convenient predicates module Predicates ( - stage, package, builder, stagedBuilder, file, way, + stage, package, builder, stagedBuilder, builderGhc, file, way, stage0, stage1, stage2, notStage0, notPackage, registerPackage, splitObjects ) where @@ -24,6 +24,9 @@ builder b = fmap (b ==) getBuilder stagedBuilder :: (Stage -> Builder) -> Predicate stagedBuilder sb = (builder . sb) =<< getStage +builderGhc :: Predicate +builderGhc = stagedBuilder Ghc ||^ stagedBuilder GhcM + file :: FilePattern -> Predicate file f = fmap (any (f ?==)) getOutputs From git at git.haskell.org Thu Oct 26 23:33:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make detectWay safe, add comments. (7ebd24f) Message-ID: <20171026233302.D17723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ebd24fe9d9177e65d5823d02a73c6a1776d85b2/ghc >--------------------------------------------------------------- commit 7ebd24fe9d9177e65d5823d02a73c6a1776d85b2 Author: Andrey Mokhov Date: Wed Aug 5 23:24:15 2015 +0100 Make detectWay safe, add comments. >--------------------------------------------------------------- 7ebd24fe9d9177e65d5823d02a73c6a1776d85b2 src/Way.hs | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index b48a29d..912ea63 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -124,11 +124,16 @@ libsuf way @ (Way set) = -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension --- Detect way from a given file extension. Fails if there is no match. -detectWay :: FilePath -> Way -detectWay extension = read prefix +-- Detect way from a given filename. Returns Nothing if there is no match: +-- * detectWay "foo/bar.hi" == Just vanilla +-- * detectWay "baz.thr_p_o" == Just threadedProfiling +-- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +detectWay :: FilePath -> Maybe Way +detectWay file = case reads prefix of + [(way, "")] -> Just way + _ -> Nothing where - prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ extension + prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ takeExtension file -- Instances for storing in the Shake database instance Binary Way where From git at git.haskell.org Thu Oct 26 23:33:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Settings/Builders/Ghc.hs (see #60). (8ba5827) Message-ID: <20171026233303.0115B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ba5827108393cf6c37fff802db0126500e2bd0a/ghc >--------------------------------------------------------------- commit 8ba5827108393cf6c37fff802db0126500e2bd0a Author: Andrey Mokhov Date: Wed Dec 30 03:07:45 2015 +0000 Decompose Settings/Builders/Ghc.hs (see #60). >--------------------------------------------------------------- 8ba5827108393cf6c37fff802db0126500e2bd0a shaking-up-ghc.cabal | 4 ++++ src/Settings/Args.hs | 12 ++++++++++-- src/Settings/Builders/GenPrimopCode.hs | 1 - src/Settings/Builders/Ghc.hs | 35 ++++------------------------------ src/Settings/Builders/GhcCabal.hs | 3 +-- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Packages/Compiler.hs | 14 +++++++++----- src/Settings/Packages/Directory.hs | 6 +++--- src/Settings/Packages/Ghc.hs | 13 +++++++++++++ src/Settings/Packages/GhcCabal.hs | 34 +++++++++++++++++++++++++++++++++ src/Settings/Packages/Hp2ps.hs | 16 ++++++++++++++++ src/Settings/Packages/RunGhc.hs | 13 +++++++++++++ 12 files changed, 108 insertions(+), 45 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 8ba5827108393cf6c37fff802db0126500e2bd0a From git at git.haskell.org Thu Oct 26 23:33:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop knownWays and knownRtsWays. (be568c0) Message-ID: <20171026233306.3EFDC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/be568c02f7ea7af3b916257cbf7656c8f9ad4979/ghc >--------------------------------------------------------------- commit be568c02f7ea7af3b916257cbf7656c8f9ad4979 Author: Andrey Mokhov Date: Wed Aug 5 23:24:47 2015 +0100 Drop knownWays and knownRtsWays. >--------------------------------------------------------------- be568c02f7ea7af3b916257cbf7656c8f9ad4979 src/Settings/Ways.hs | 14 +------------- 1 file changed, 1 insertion(+), 13 deletions(-) diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index ae4bd38..0ea3432 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,7 +1,6 @@ module Settings.Ways ( ways, getWays, - rtsWays, getRtsWays, - knownWays, knownRtsWays + rtsWays, getRtsWays ) where import Way @@ -40,14 +39,3 @@ defaultRtsWays = do , (dynamic `elem` ways) ? append [ dynamic, debugDynamic, threadedDynamic, threadedDebugDynamic , loggingDynamic, threadedLoggingDynamic ] ] - --- These are all ways known to the build system -knownWays :: [Way] -knownWays = [vanilla, profiling, logging, parallel, granSim] - -knownRtsWays :: [Way] -knownRtsWays = [ threaded, threadedProfiling, threadedLogging, debug - , debugProfiling, threadedDebug, threadedDebugProfiling, dynamic - , profilingDynamic, threadedProfilingDynamic, threadedDynamic - , threadedDebugDynamic, debugDynamic, loggingDynamic - , threadedLoggingDynamic ] From git at git.haskell.org Thu Oct 26 23:33:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a build rule for inplace/lib/settings. (0ceae64) Message-ID: <20171026233306.7860E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ceae64327289b2cb79041cb75ec1e7c92af8546/ghc >--------------------------------------------------------------- commit 0ceae64327289b2cb79041cb75ec1e7c92af8546 Author: Andrey Mokhov Date: Wed Dec 30 15:16:18 2015 +0000 Add a build rule for inplace/lib/settings. >--------------------------------------------------------------- 0ceae64327289b2cb79041cb75ec1e7c92af8546 src/Rules/Install.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 13a0e00..2e74bd3 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -7,12 +7,14 @@ import Rules.Generate installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" - , "inplace/lib/platformConstants" ] + , "inplace/lib/platformConstants" + , "inplace/lib/settings" ] installRules :: Rules () installRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." where file <~ dir = file %> \out -> do let source = dir -/- takeFileName out From git at git.haskell.org Thu Oct 26 23:33:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise rules by removing a loop over all possible ways. (c204ca9) Message-ID: <20171026233310.0329D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c204ca9764ac5ffdb141247151e040bd1bffa5d6/ghc >--------------------------------------------------------------- commit c204ca9764ac5ffdb141247151e040bd1bffa5d6 Author: Andrey Mokhov Date: Wed Aug 5 23:26:36 2015 +0100 Optimise rules by removing a loop over all possible ways. >--------------------------------------------------------------- c204ca9764ac5ffdb141247151e040bd1bffa5d6 src/Rules/Compile.hs | 34 +++++++++++++++++++--------------- 1 file changed, 19 insertions(+), 15 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 4b2fe4b..89b60c2 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -7,10 +7,14 @@ import Builder import Expression import qualified Target import Oracles.DependencyList -import Settings.Ways import Settings.TargetDirectory import Rules.Actions import Rules.Resources +import Data.Maybe + +matchBuildResult :: FilePath -> String -> FilePath -> Bool +matchBuildResult buildPath extension file = + (buildPath "*" ++ extension) ?== file && (isJust . detectWay $ file) compilePackage :: Resources -> StagePackageTarget -> Rules () compilePackage _ target = do @@ -21,20 +25,20 @@ compilePackage _ target = do cDepsFile = buildPath -/- "c.deps" hDepsFile = buildPath -/- "haskell.deps" - forM_ knownWays $ \way -> do - (buildPath "*." ++ hisuf way) %> \hi -> do - let obj = hi -<.> osuf way - need [obj] + matchBuildResult buildPath "hi" ?> \hi -> do + let way = fromJust . detectWay $ hi -- fromJust is safe + need [hi -<.> osuf way] - (buildPath "*." ++ osuf way) %> \obj -> do - let vanillaObjName = takeFileName obj -<.> "o" - cDeps <- dependencyList cDepsFile vanillaObjName - hDeps <- dependencyList hDepsFile obj - let hSrcDeps = filter ("//*hs" ?==) hDeps + matchBuildResult buildPath "o" ?> \obj -> do + let way = fromJust . detectWay $ obj -- fromJust is safe + vanillaObj = takeFileName obj -<.> "o" + cDeps <- dependencyList cDepsFile vanillaObj + hDeps <- dependencyList hDepsFile obj + let hSrcDeps = filter ("//*hs" ?==) hDeps - when (null cDeps && null hDeps) $ - putError_ $ "Cannot determine sources for '" ++ obj ++ "'." + when (null cDeps && null hDeps) $ + putError $ "Cannot determine sources for '" ++ obj ++ "'." - if null cDeps - then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] - else build $ fullTarget target cDeps (Gcc stage) [obj] + if null cDeps + then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] + else build $ fullTarget target cDeps (Gcc stage) [obj] From git at git.haskell.org Thu Oct 26 23:33:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for wrappers. (a1eab18) Message-ID: <20171026233310.3D7983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1eab187eb929d2d82d2f093d4768849978973a4/ghc >--------------------------------------------------------------- commit a1eab187eb929d2d82d2f093d4768849978973a4 Author: Andrey Mokhov Date: Thu Dec 31 00:41:00 2015 +0000 Add support for wrappers. >--------------------------------------------------------------- a1eab187eb929d2d82d2f093d4768849978973a4 src/Rules/Program.hs | 120 ++++++++++++++++++++++++++++++---------------- src/Rules/Wrappers/Ghc.hs | 14 ++++++ src/Target.hs | 2 +- 3 files changed, 94 insertions(+), 42 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a1eab187eb929d2d82d2f093d4768849978973a4 From git at git.haskell.org Thu Oct 26 23:33:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move matchBuildResult to Way.hs. (1711977) Message-ID: <20171026233313.6AA053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1711977649e14d87093d0f4ff0de132d1c044e42/ghc >--------------------------------------------------------------- commit 1711977649e14d87093d0f4ff0de132d1c044e42 Author: Andrey Mokhov Date: Thu Aug 6 01:34:24 2015 +0100 Move matchBuildResult to Way.hs. >--------------------------------------------------------------- 1711977649e14d87093d0f4ff0de132d1c044e42 src/Way.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/src/Way.hs b/src/Way.hs index 912ea63..365a949 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -10,7 +10,7 @@ module Way ( -- TODO: rename to "Way"? loggingDynamic, threadedLoggingDynamic, wayPrefix, hisuf, osuf, hcsuf, obootsuf, ssuf, libsuf, - detectWay + detectWay, matchBuildResult ) where import Base @@ -20,6 +20,7 @@ import Data.List import Data.IntSet (IntSet) import Control.Applicative import qualified Data.IntSet as Set +import Data.Maybe data WayUnit = Threaded | Debug @@ -135,6 +136,13 @@ detectWay file = case reads prefix of where prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ takeExtension file +-- Given a path, an extension suffix, and a file name check if the latter: +-- 1) conforms to pattern 'path//*suffix' +-- 2) has extension prefixed with a known way tag, i.e. detectWay does not fail +matchBuildResult :: FilePath -> String -> FilePath -> Bool +matchBuildResult path suffix file = + (path "*" ++ suffix) ?== file && (isJust . detectWay $ file) + -- Instances for storing in the Shake database instance Binary Way where put = put . show From git at git.haskell.org Thu Oct 26 23:33:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing sources. (109a6f8) Message-ID: <20171026233313.A31F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/109a6f843864def992865b81b0fea462e0fad7b4/ghc >--------------------------------------------------------------- commit 109a6f843864def992865b81b0fea462e0fad7b4 Author: Andrey Mokhov Date: Thu Dec 31 01:08:26 2015 +0000 Add missing sources. >--------------------------------------------------------------- 109a6f843864def992865b81b0fea462e0fad7b4 shaking-up-ghc.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index b60bf46..e7c3e28 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -54,6 +54,7 @@ executable ghc-shake , Rules.Package , Rules.Program , Rules.Resources + , Rules.Wrappers.Ghc , Settings , Settings.Args , Settings.Builders.Alex From git at git.haskell.org Thu Oct 26 23:33:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add cmdLineLengthLimit for detecting command line size limits. (ef14064) Message-ID: <20171026233317.5AAB03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef1406494d3dc15ab0b311fcaf7e3c853c2a3a81/ghc >--------------------------------------------------------------- commit ef1406494d3dc15ab0b311fcaf7e3c853c2a3a81 Author: Andrey Mokhov Date: Thu Aug 6 01:35:31 2015 +0100 Add cmdLineLengthLimit for detecting command line size limits. >--------------------------------------------------------------- ef1406494d3dc15ab0b311fcaf7e3c853c2a3a81 src/Oracles/Setting.hs | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 33067b1..20e4376 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -3,7 +3,7 @@ module Oracles.Setting ( setting, settingList, targetPlatform, targetPlatforms, targetOs, targetOss, notTargetOs, targetArchs, windowsHost, notWindowsHost, ghcWithInterpreter, - ghcEnableTablesNextToCode + ghcEnableTablesNextToCode, cmdLineLengthLimit ) where import Base @@ -96,3 +96,14 @@ ghcWithInterpreter = do ghcEnableTablesNextToCode :: Action Bool ghcEnableTablesNextToCode = targetArchs ["ia64", "powerpc64"] + +-- Command lines have limited size on Windows. Since Windows 7 the limit is +-- 32768 characters (theoretically). In practice we use 31000 to leave some +-- breathing space for the builder's path & name, auxiliary flags, and other +-- overheads. Use this function to set limits for other OSs if necessary. +cmdLineLengthLimit :: Action Int +cmdLineLengthLimit = do + windows <- windowsHost + return $ if windows + then 31000 + else 4194304 -- Cabal needs a bit more than 2MB! From git at git.haskell.org Thu Oct 26 23:33:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Settings/Builders/GhcCabal.hs (see #60). (7cf7210) Message-ID: <20171026233317.7FE1D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7cf7210ecee07729579f630ee93fa694e8e16635/ghc >--------------------------------------------------------------- commit 7cf7210ecee07729579f630ee93fa694e8e16635 Author: Andrey Mokhov Date: Thu Dec 31 02:20:32 2015 +0000 Decompose Settings/Builders/GhcCabal.hs (see #60). >--------------------------------------------------------------- 7cf7210ecee07729579f630ee93fa694e8e16635 shaking-up-ghc.cabal | 5 ++ src/Settings/Args.hs | 13 +++- src/Settings/Builders/Common.hs | 36 ++++++++++- src/Settings/Builders/DeriveConstants.hs | 7 +-- src/Settings/Builders/GhcCabal.hs | 102 ++----------------------------- src/Settings/Builders/Hsc2Hs.hs | 7 +-- src/Settings/Packages/Base.hs | 11 ++++ src/Settings/Packages/Compiler.hs | 32 +++++++++- src/Settings/Packages/Ghc.hs | 12 ++-- src/Settings/Packages/GhcPrim.hs | 9 +++ src/Settings/Packages/Haddock.hs | 9 +++ src/Settings/Packages/IntegerGmp.hs | 19 ++++++ 12 files changed, 145 insertions(+), 117 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 7cf7210ecee07729579f630ee93fa694e8e16635 From git at git.haskell.org Thu Oct 26 23:33:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove unused code. (6c89bd0) Message-ID: <20171026233320.BA6593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6c89bd01c53fe3ffa0c26499effff7687530711e/ghc >--------------------------------------------------------------- commit 6c89bd01c53fe3ffa0c26499effff7687530711e Author: Andrey Mokhov Date: Thu Aug 6 01:36:39 2015 +0100 Remove unused code. >--------------------------------------------------------------- 6c89bd01c53fe3ffa0c26499effff7687530711e src/Package/Base.hs | 68 -------------------------------------------- src/Package/Library.hs | 76 -------------------------------------------------- 2 files changed, 144 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs deleted file mode 100644 index 1f9d2c8..0000000 --- a/src/Package/Base.hs +++ /dev/null @@ -1,68 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package.Base ( - module Base, - module Ways, - module Util, - module Oracles, - -- Package (..), Settings (..), TodoItem (..), - -- defaultSettings, library, customise, updateSettings, - -- commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - pathArgs, packageArgs, - includeGccArgs, includeGhcArgs, pkgHsSources, - pkgDepHsObjects, pkgLibHsObjects, pkgCObjects, - argSizeLimit, - sourceDependecies, - argList, argListWithComment, - argListPath - ) where - -import Base -import Ways -import Util -import Oracles -import Settings -import qualified System.Directory as S - --- Find Haskell objects we depend on (we don't want to depend on split objects) -pkgDepHsObjects :: FilePath -> FilePath -> Way -> Action [FilePath] -pkgDepHsObjects path dist way = do - let pathDist = path dist - buildDir = pathDist "build" - dirs <- map (dropWhileEnd isPathSeparator . unifyPath . (path )) - <$> args (SrcDirs pathDist) - fmap concat $ forM dirs $ \d -> - map (unifyPath . (buildDir ++) . (-<.> osuf way) . drop (length d)) - <$> (findModuleFiles pathDist [d] [".hs", ".lhs"]) - -pkgCObjects :: FilePath -> FilePath -> Way -> Action [FilePath] -pkgCObjects path dist way = do - let pathDist = path dist - buildDir = pathDist "build" - srcs <- args $ CSrcs pathDist - return $ map (unifyPath . (buildDir ) . (-<.> osuf way)) srcs - --- Find Haskell objects that go to library -pkgLibHsObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] -pkgLibHsObjects path dist stage way = do - let pathDist = path dist - buildDir = unifyPath $ pathDist "build" - split <- splitObjects stage - depObjs <- pkgDepHsObjects path dist way - if split - then do - need depObjs -- Otherwise, split objects may not yet be available - let suffix = "_" ++ osuf way ++ "_split/*." ++ osuf way - findModuleFiles pathDist [buildDir] [suffix] - else do return depObjs - --- The argument list has a limited size on Windows. Since Windows 7 the limit --- is 32768 (theoretically). In practice we use 31000 to leave some breathing --- space for the builder's path & name, auxiliary flags, and other overheads. --- Use this function to set limits for other operating systems if necessary. -argSizeLimit :: Action Int -argSizeLimit = do - windows <- windowsHost - return $ if windows - then 31000 - else 4194304 -- Cabal needs a bit more than 2MB! - diff --git a/src/Package/Library.hs b/src/Package/Library.hs deleted file mode 100644 index 82b1ab8..0000000 --- a/src/Package/Library.hs +++ /dev/null @@ -1,76 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package.Library (buildPackageLibrary) where - -import Package.Base - -argListDir :: FilePath -argListDir = "shake/arg/buildPackageLibrary" - -arArgs :: [FilePath] -> FilePath -> Args -arArgs objs result = args [ arg "q" - , arg result - , args objs ] - -ldArgs :: Stage -> [FilePath] -> FilePath -> Args -ldArgs stage objs result = args [ args $ ConfLdLinkerArgs stage - , arg "-r" - , arg "-o" - , arg result - , args objs ] - -arRule :: Package -> TodoItem -> Rules () -arRule pkg @ (Package _ path _ _) todo @ (stage, dist, _) = - let buildDir = path dist "build" - in - (buildDir "*a") %> \out -> do - let way = detectWay $ tail $ takeExtension out - cObjs <- pkgCObjects path dist way - hsObjs <- pkgDepHsObjects path dist way - need $ cObjs ++ hsObjs - libHsObjs <- pkgLibHsObjects path dist stage way - liftIO $ removeFiles "." [out] - -- Splitting argument list into chunks as otherwise Ar chokes up - maxChunk <- argSizeLimit - forM_ (chunksOfSize maxChunk $ cObjs ++ libHsObjs) $ \objs -> do - run Ar $ arArgs objs $ unifyPath out - -- Finally, record the argument list - need [argListPath argListDir pkg stage] - -ldRule :: Package -> TodoItem -> Rules () -ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) = - let pathDist = path dist - buildDir = pathDist "build" - in - priority 2 $ (buildDir "*.o") %> \out -> do - cObjs <- pkgCObjects path dist vanilla - hObjs <- pkgDepHsObjects path dist vanilla - need $ cObjs ++ hObjs - run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out - synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) - putColoured Green $ "/--------\n| Successfully built package '" - ++ name ++ "' (stage " ++ show stage ++ ")." - putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." - ++ "\n\\--------" - -- Finally, record the argument list - need [argListPath argListDir pkg stage] - -argListRule :: Package -> TodoItem -> Rules () -argListRule pkg @ (Package _ path _ _) todo @ (stage, dist, settings) = - (argListPath argListDir pkg stage) %> \out -> do - need $ ["shake/src/Package/Library.hs"] ++ sourceDependecies - cObjsV <- pkgCObjects path dist vanilla - hsObjsV <- pkgDepHsObjects path dist vanilla - ldList <- argList Ld $ ldArgs stage (cObjsV ++ hsObjsV) "output.o" - ways' <- ways settings - arList <- forM ways' $ \way -> do - cObjs <- pkgCObjects path dist way - hsObjs <- pkgLibHsObjects path dist stage way - suffix <- libsuf way - argListWithComment - ("way '" ++ tag way ++ "'") - Ar - (arArgs (cObjs ++ hsObjs) $ "output" <.> suffix) - writeFileChanged out $ unlines $ [ldList] ++ arList - -buildPackageLibrary :: Package -> TodoItem -> Rules () -buildPackageLibrary = argListRule <> arRule <> ldRule From git at git.haskell.org Thu Oct 26 23:33:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track wrapped binary. (49521c0) Message-ID: <20171026233320.F24943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49521c02bdd181b57713c8f3e2bf111416b0df37/ghc >--------------------------------------------------------------- commit 49521c02bdd181b57713c8f3e2bf111416b0df37 Author: Andrey Mokhov Date: Thu Dec 31 02:28:23 2015 +0000 Track wrapped binary. >--------------------------------------------------------------- 49521c02bdd181b57713c8f3e2bf111416b0df37 src/Rules/Program.hs | 18 ++++++++++++------ 1 file changed, 12 insertions(+), 6 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 93c6a97..a1aaa2f 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -29,6 +29,11 @@ buildProgram _ target @ (PartialTarget stage pkg) = do let match file = case programPath stage pkg of Nothing -> False Just program -> program == file + matchWrapped file = case programPath stage pkg of + Nothing -> False + Just program -> case computeWrappedPath program of + Nothing -> False + Just wrappedProgram -> wrappedProgram == file match ?> \bin -> do windows <- windowsHost @@ -37,15 +42,16 @@ buildProgram _ target @ (PartialTarget stage pkg) = do else case find ((== target) . fst) wrappers of Nothing -> buildBinary target bin -- No wrapper found Just (_, wrapper) -> do - wrappedBin <- moveToLib bin - buildBinary target wrappedBin + let Just wrappedBin = computeWrappedPath bin + need [wrappedBin] buildWrapper target wrapper bin wrappedBin + matchWrapped ?> \bin -> buildBinary target bin + -- Replace programInplacePath with programInplaceLibPath in a given path -moveToLib :: FilePath -> Action FilePath -moveToLib path = case stripPrefix programInplacePath path of - Just suffix -> return $ programInplaceLibPath ++ suffix - Nothing -> putError $ "moveToLib: cannot move " ++ path +computeWrappedPath :: FilePath -> Maybe FilePath +computeWrappedPath = + fmap (programInplaceLibPath ++) . stripPrefix programInplacePath buildWrapper :: PartialTarget -> Wrapper -> FilePath -> FilePath -> Action () buildWrapper target @ (PartialTarget stage pkg) wrapper wrapperPath binPath = do From git at git.haskell.org Thu Oct 26 23:33:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for multiple invokations of Ar when argument list is too long. (c02e070) Message-ID: <20171026233324.673DB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c02e070cb0b05a443a823ef1134415b14d7043df/ghc >--------------------------------------------------------------- commit c02e070cb0b05a443a823ef1134415b14d7043df Author: Andrey Mokhov Date: Thu Aug 6 01:37:32 2015 +0100 Add support for multiple invokations of Ar when argument list is too long. >--------------------------------------------------------------- c02e070cb0b05a443a823ef1134415b14d7043df src/Rules/Actions.hs | 13 +++++++++++-- 1 file changed, 11 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d96157c..50eb87f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -7,9 +7,11 @@ import Util import Builder import Expression import qualified Target +import Oracles.Setting +import Oracles.ArgsHash import Settings.Args import Settings.Util -import Oracles.ArgsHash +import Settings.Builders.Ar -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last @@ -29,7 +31,14 @@ buildWithResources rs target = do ++ show builder ++ " with arguments:" mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList putBuild $ "\\--------" - quietly $ cmd [path] argList + quietly $ if builder /= Ar + then cmd [path] argList + else do -- Split argument list into chunks as otherwise Ar chokes up + maxChunk <- cmdLineLengthLimit + let persistentArgs = take arPersistentArgsCount argList + remainingArgs = drop arPersistentArgsCount argList + forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> + unit . cmd [path] $ persistentArgs ++ argsChunk -- Most targets are built without explicitly acquiring resources build :: FullTarget -> Action () From git at git.haskell.org Thu Oct 26 23:33:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fixes the -B path for the ghcWrapper. (d9d00b8) Message-ID: <20171026233324.B26C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9d00b86b79d998a288c5a2ffd2520d01b9c72e5/ghc >--------------------------------------------------------------- commit d9d00b86b79d998a288c5a2ffd2520d01b9c72e5 Author: Moritz Angermann Date: Thu Dec 31 10:40:37 2015 +0800 Fixes the -B path for the ghcWrapper. >--------------------------------------------------------------- d9d00b86b79d998a288c5a2ffd2520d01b9c72e5 src/Rules/Wrappers/Ghc.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Wrappers/Ghc.hs b/src/Rules/Wrappers/Ghc.hs index 93ceba0..c24bb70 100644 --- a/src/Rules/Wrappers/Ghc.hs +++ b/src/Rules/Wrappers/Ghc.hs @@ -11,4 +11,4 @@ ghcWrapper program = do return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) - ++ " -B" ++ (top -/- takeDirectory program) ++ " ${1+\"$@\"}" ] + ++ " -B" ++ (top -/- "inplace" -/- "lib") ++ " ${1+\"$@\"}" ] From git at git.haskell.org Thu Oct 26 23:33:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move decodeModule to Util.hs. (c1b296a) Message-ID: <20171026233328.119273A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1b296ab5dd0d4795ad2c4e86f5a00b2ffa947b7/ghc >--------------------------------------------------------------- commit c1b296ab5dd0d4795ad2c4e86f5a00b2ffa947b7 Author: Andrey Mokhov Date: Thu Aug 6 01:38:54 2015 +0100 Move decodeModule to Util.hs. >--------------------------------------------------------------- c1b296ab5dd0d4795ad2c4e86f5a00b2ffa947b7 src/Settings/Util.hs | 5 ----- src/Util.hs | 7 ++++++- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index c688b5d..13e5be0 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -89,11 +89,6 @@ getHsSources = do return $ foundSources ++ generatedSources --- Given a module name extract the directory and file names, e.g.: --- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") -decodeModule :: String -> (FilePath, String) -decodeModule = splitFileName . replaceEq '.' '/' - -- findModuleFiles scans a list of given directories and finds files matching a -- given extension pattern (e.g., "*hs") that correspond to modules of the -- currently built package. Missing module files are returned in a separate diff --git a/src/Util.hs b/src/Util.hs index f00785f..1c34a87 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,7 +1,7 @@ module Util ( module Data.Char, module System.Console.ANSI, - replaceIf, replaceEq, replaceSeparators, + replaceIf, replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, putColoured, putOracle, putBuild, putError, @@ -22,6 +22,11 @@ replaceEq from = replaceIf (== from) replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator +-- Given a module name extract the directory and file names, e.g.: +-- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +decodeModule :: String -> (FilePath, String) +decodeModule = splitFileName . replaceEq '.' '/' + -- Normalise a path and convert all path separators to /, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx From git at git.haskell.org Thu Oct 26 23:33:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Settings/Builders/Haddock.hs (see #60). (4ade862) Message-ID: <20171026233328.58D6A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ade862d347dd04e9e61abcd0aa96a6864cb5962/ghc >--------------------------------------------------------------- commit 4ade862d347dd04e9e61abcd0aa96a6864cb5962 Author: Andrey Mokhov Date: Thu Dec 31 02:53:36 2015 +0000 Decompose Settings/Builders/Haddock.hs (see #60). >--------------------------------------------------------------- 4ade862d347dd04e9e61abcd0aa96a6864cb5962 src/Settings/Builders/Haddock.hs | 12 ++---------- src/Settings/Packages/Compiler.hs | 6 ++++-- 2 files changed, 6 insertions(+), 12 deletions(-) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index c8226fc..d626f26 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -43,19 +43,11 @@ haddockArgs = builder Haddock ? do arg "--source-module=src/%{MODULE/./-}.html" , specified HsColour ? arg "--source-entity=src/%{MODULE/./-}.html\\#%{NAME}" - , customPackageArgs , append =<< getInputs , arg "+RTS" , arg $ "-t" ++ path -/- "haddock.t" - , arg "--machine-readable" ] - -customPackageArgs :: Args -customPackageArgs = mconcat - [ package compiler ? stage1 ? - arg "--optghc=-DSTAGE=2" ] - -- TODO: move to getPackageSources - -- , package ghcPrim ? stage1 ? - -- arg "libraries/ghc-prim/dist-install/build/autogen/GHC/Prim.hs" ] + , arg "--machine-readable" + , arg "-RTS" ] -- From ghc.mk: -- # ----------------------------------------------- diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 88ccf2a..0dd7551 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -5,7 +5,7 @@ import Expression import GHC (compiler) import Oracles.Config.Setting import Oracles.Config.Flag -import Predicates (builder, builderGhc, package, notStage0) +import Predicates (builder, builderGhc, package, notStage0, stage1) import Settings compilerPackageArgs :: Args @@ -36,4 +36,6 @@ compilerPackageArgs = package compiler ? do ghciWithDebugger ? notStage0 ? arg "--ghc-option=-DDEBUGGER" , ghcProfiled ? - notStage0 ? arg "--ghc-pkg-option=--force" ] ] + notStage0 ? arg "--ghc-pkg-option=--force" ] + + , builder Haddock ? stage1 ? arg "--optghc=-DSTAGE=2" ] From git at git.haskell.org Thu Oct 26 23:33:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create Settings/Builders/ directory for keeping builder-related settings. (1ac1688) Message-ID: <20171026233331.98FDF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ac1688ff9c472e99125c1583a7a202946a036b4/ghc >--------------------------------------------------------------- commit 1ac1688ff9c472e99125c1583a7a202946a036b4 Author: Andrey Mokhov Date: Thu Aug 6 01:40:41 2015 +0100 Create Settings/Builders/ directory for keeping builder-related settings. >--------------------------------------------------------------- 1ac1688ff9c472e99125c1583a7a202946a036b4 src/Settings/Args.hs | 14 ++++++++++---- src/Settings/Builders/Ar.hs | 18 ++++++++++++++++++ src/Settings/{ => Builders}/Gcc.hs | 21 ++++++++++++++++++++- src/Settings/{ => Builders}/Ghc.hs | 27 ++++++++++++++++++++++++++- src/Settings/{ => Builders}/GhcCabal.hs | 2 +- src/Settings/{ => Builders}/GhcPkg.hs | 4 ++-- src/Settings/Builders/Ld.hs | 18 ++++++++++++++++++ src/Settings/GccM.hs | 25 ------------------------- src/Settings/GhcM.hs | 33 --------------------------------- 9 files changed, 95 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 1ac1688ff9c472e99125c1583a7a202946a036b4 From git at git.haskell.org Thu Oct 26 23:33:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #65 from angerman/fix-B (75ebcfb) Message-ID: <20171026233331.D410D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/75ebcfb2b778e71b4ec920a63804fe09597e8f17/ghc >--------------------------------------------------------------- commit 75ebcfb2b778e71b4ec920a63804fe09597e8f17 Merge: 4ade862 d9d00b8 Author: Andrey Mokhov Date: Thu Dec 31 02:54:19 2015 +0000 Merge pull request #65 from angerman/fix-B Fixes the -B path for the ghcWrapper. >--------------------------------------------------------------- 75ebcfb2b778e71b4ec920a63804fe09597e8f17 src/Rules/Wrappers/Ghc.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:33:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageLibrary build rule. (3f3134c) Message-ID: <20171026233335.6FD323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3f3134cc10b412afc71b7beb80a77ee779ecc3c1/ghc >--------------------------------------------------------------- commit 3f3134cc10b412afc71b7beb80a77ee779ecc3c1 Author: Andrey Mokhov Date: Thu Aug 6 01:41:25 2015 +0100 Add buildPackageLibrary build rule. >--------------------------------------------------------------- 3f3134cc10b412afc71b7beb80a77ee779ecc3c1 src/Rules/Compile.hs | 4 ---- src/Rules/Library.hs | 63 ++++++++++++++++++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 7 +++++- 3 files changed, 69 insertions(+), 5 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 89b60c2..6f57a81 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,10 +12,6 @@ import Rules.Actions import Rules.Resources import Data.Maybe -matchBuildResult :: FilePath -> String -> FilePath -> Bool -matchBuildResult buildPath extension file = - (buildPath "*" ++ extension) ?== file && (isJust . detectWay $ file) - compilePackage :: Resources -> StagePackageTarget -> Rules () compilePackage _ target = do let stage = Target.stage target diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs new file mode 100644 index 0000000..5bd6551 --- /dev/null +++ b/src/Rules/Library.hs @@ -0,0 +1,63 @@ +module Rules.Library (buildPackageLibrary) where + +import Way +import Base +import Util +import Builder +import Switches +import Expression +import qualified Target +import Oracles.PackageData +import Settings.Util +import Settings.TargetDirectory +import Rules.Actions +import Rules.Resources +import Data.Maybe + +buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () +buildPackageLibrary _ target = do + let stage = Target.stage target + pkg = Target.package target + path = targetPath stage pkg + buildPath = path -/- "build" + + matchBuildResult buildPath "a" ?> \a -> do + liftIO $ removeFiles "." [a] + cSrcs <- interpret target $ getPkgDataList CSrcs + modules <- interpret target $ getPkgDataList Modules + + let way = fromJust . detectWay $ a -- fromJust is safe + hsSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] + hsObjs = [ buildPath -/- src <.> osuf way | src <- hsSrcs ] + + need $ cObjs ++ hsObjs -- this will create split objects if required + + splitObjs <- fmap concat $ forM hsSrcs $ \src -> do + let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" + getDirectoryFiles "" [files] + + split <- interpret target splitObjects + let allObjs = if split + then cObjs ++ hsObjs ++ splitObjs + else cObjs ++ hsObjs + + build $ fullTarget target allObjs Ar [a] + +-- ldRule :: Resources -> StagePackageTarget -> Rules () +-- ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) = +-- let pathDist = path dist +-- buildDir = pathDist "build" +-- in +-- priority 2 $ (buildDir "*.o") %> \out -> do +-- cObjs <- pkgCObjects path dist vanilla +-- hObjs <- pkgDepHsObjects path dist vanilla +-- need $ cObjs ++ hObjs +-- run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out +-- synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) +-- putColoured Green $ "/--------\n| Successfully built package '" +-- ++ name ++ "' (stage " ++ show stage ++ ")." +-- putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." +-- ++ "\n\\--------" +-- -- Finally, record the argument list +-- need [argListPath argListDir pkg stage] diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 572fff6..dbbe5cc 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -4,8 +4,13 @@ import Base import Expression import Rules.Data import Rules.Compile +import Rules.Library import Rules.Resources import Rules.Dependencies buildPackage :: Resources -> StagePackageTarget -> Rules () -buildPackage = buildPackageData <> buildPackageDependencies <> compilePackage +buildPackage = mconcat + [ buildPackageData + , buildPackageDependencies + , compilePackage + , buildPackageLibrary ] From git at git.haskell.org Thu Oct 26 23:33:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix compilerPackageArgs (Haddock builder). (02b0d75) Message-ID: <20171026233335.B95803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02b0d758636e8b9cf79845d7cf786c3154bfad28/ghc >--------------------------------------------------------------- commit 02b0d758636e8b9cf79845d7cf786c3154bfad28 Author: Andrey Mokhov Date: Thu Dec 31 12:15:02 2015 +0000 Fix compilerPackageArgs (Haddock builder). >--------------------------------------------------------------- 02b0d758636e8b9cf79845d7cf786c3154bfad28 src/Settings/Packages/Compiler.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 0dd7551..c2f31e6 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -5,16 +5,17 @@ import Expression import GHC (compiler) import Oracles.Config.Setting import Oracles.Config.Flag -import Predicates (builder, builderGhc, package, notStage0, stage1) +import Predicates (builder, builderGhc, package, notStage0) import Settings compilerPackageArgs :: Args compilerPackageArgs = package compiler ? do stage <- getStage rtsWays <- getRtsWays + path <- getTargetPath mconcat [ builder Alex ? arg "--latin1" - , builderGhc ? arg ("-I" ++ pkgPath compiler -/- stageString stage) + , builderGhc ? arg ("-I" ++ path) , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) @@ -38,4 +39,4 @@ compilerPackageArgs = package compiler ? do , ghcProfiled ? notStage0 ? arg "--ghc-pkg-option=--force" ] - , builder Haddock ? stage1 ? arg "--optghc=-DSTAGE=2" ] + , builder Haddock ? arg ("--optghc=-I" ++ path) ] From git at git.haskell.org Thu Oct 26 23:33:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle dyamic libraries in detectWay. (83cd6c5) Message-ID: <20171026233339.41ADD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/83cd6c55ba8eeebe877cc643308435afe3c3d785/ghc >--------------------------------------------------------------- commit 83cd6c55ba8eeebe877cc643308435afe3c3d785 Author: Andrey Mokhov Date: Fri Aug 7 01:07:24 2015 +0100 Handle dyamic libraries in detectWay. >--------------------------------------------------------------- 83cd6c55ba8eeebe877cc643308435afe3c3d785 src/Way.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 365a949..3046867 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -126,15 +126,21 @@ libsuf way @ (Way set) = return $ prefix ++ "ghc" ++ version ++ extension -- Detect way from a given filename. Returns Nothing if there is no match: --- * detectWay "foo/bar.hi" == Just vanilla --- * detectWay "baz.thr_p_o" == Just threadedProfiling --- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +-- * detectWay "foo/bar.hi" == Just vanilla +-- * detectWay "baz.thr_p_o" == Just threadedProfiling +-- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +-- * detectWay "xru.p_ghc7.11.20141222.dll" == Just profiling detectWay :: FilePath -> Maybe Way detectWay file = case reads prefix of [(way, "")] -> Just way _ -> Nothing where - prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ takeExtension file + extension = takeExtension file + prefixed = if extension `notElem` ["so", "dll", "dynlib"] + then extension + else takeExtension . dropExtension . + dropExtension . dropExtension $ file + prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed -- Given a path, an extension suffix, and a file name check if the latter: -- 1) conforms to pattern 'path//*suffix' From git at git.haskell.org Thu Oct 26 23:33:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: ghcPkg Wrapper (aee3088) Message-ID: <20171026233339.871B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aee308892e923e8f2ba24d912fc3197599ef47a8/ghc >--------------------------------------------------------------- commit aee308892e923e8f2ba24d912fc3197599ef47a8 Author: Moritz Angermann Date: Thu Dec 31 20:21:13 2015 +0800 ghcPkg Wrapper >--------------------------------------------------------------- aee308892e923e8f2ba24d912fc3197599ef47a8 shaking-up-ghc.cabal | 1 + src/Rules/Program.hs | 4 +++- src/Rules/Wrappers/GhcPkg.hs | 20 ++++++++++++++++++++ 3 files changed, 24 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index cfa55ff..2c75566 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -55,6 +55,7 @@ executable ghc-shake , Rules.Program , Rules.Resources , Rules.Wrappers.Ghc + , Rules.Wrappers.GhcPkg , Settings , Settings.Args , Settings.Builders.Alex diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index a1aaa2f..75314c3 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -10,6 +10,7 @@ import Rules.Actions import Rules.Library import Rules.Resources import Rules.Wrappers.Ghc +import Rules.Wrappers.GhcPkg import Settings import Settings.Builders.GhcCabal @@ -22,7 +23,8 @@ type Wrapper = FilePath -> Expr String -- List of wrappers we build wrappers :: [(PartialTarget, Wrapper)] -wrappers = [(PartialTarget Stage0 ghc, ghcWrapper)] +wrappers = [ (PartialTarget Stage0 ghc, ghcWrapper) + , (PartialTarget Stage0 ghcPkg, ghcPkgWrapper)] buildProgram :: Resources -> PartialTarget -> Rules () buildProgram _ target @ (PartialTarget stage pkg) = do diff --git a/src/Rules/Wrappers/GhcPkg.hs b/src/Rules/Wrappers/GhcPkg.hs new file mode 100644 index 0000000..7edc43c --- /dev/null +++ b/src/Rules/Wrappers/GhcPkg.hs @@ -0,0 +1,20 @@ +module Rules.Wrappers.GhcPkg (ghcPkgWrapper) where + +import Base +import Expression +import Oracles + +-- Note about wrapper: +-- bindir is usually GhcSourcePath / inplace / bin +-- topdir is usually GhcSourcePath / inplace / lib +-- datadir is usually the same as topdir + +ghcPkgWrapper :: FilePath -> Expr String +ghcPkgWrapper program = do + lift $ need [sourcePath -/- "Rules/Wrappers/GhcPkg.hs"] + top <- getSetting GhcSourcePath + let pkgConf = top -/- "inplace" -/- "lib" -/- "package.conf.d" + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (top -/- program) + ++ " --global-package-db " ++ pkgConf ++ " ${1+\"$@\"}" ] From git at git.haskell.org Thu Oct 26 23:33:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix detectWay and way parsing. (fafec42) Message-ID: <20171026233342.A6BB03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fafec426576d246a2deedb6875258eefcc55a4ee/ghc >--------------------------------------------------------------- commit fafec426576d246a2deedb6875258eefcc55a4ee Author: Andrey Mokhov Date: Fri Aug 7 02:56:02 2015 +0100 Fix detectWay and way parsing. >--------------------------------------------------------------- fafec426576d246a2deedb6875258eefcc55a4ee src/Way.hs | 21 +++++++++++++-------- 1 file changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 3046867..4d14025 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -29,7 +29,7 @@ data WayUnit = Threaded | Dynamic | Parallel | GranSim - deriving Enum + deriving (Eq, Enum) instance Show WayUnit where show unit = case unit of @@ -61,10 +61,15 @@ instance Show Way where tag = intercalate "_" . map show . wayToUnits $ way instance Read Way where - readsPrec _ s = - if s == "v" - then [(vanilla, "")] - else [(wayFromUnits . map read . words . replaceEq '_' ' ' $ s, "")] + readsPrec _ s = if s == "v" then [(vanilla, "")] else result + where + uniqueReads token = case reads token of + [(unit, "")] -> Just unit + _ -> Nothing + units = map uniqueReads . words . replaceEq '_' ' ' $ s + result = if Nothing `elem` units + then [] + else [(wayFromUnits . map fromJust $ units, "")] instance Eq Way where Way a == Way b = a == b @@ -128,7 +133,7 @@ libsuf way @ (Way set) = -- Detect way from a given filename. Returns Nothing if there is no match: -- * detectWay "foo/bar.hi" == Just vanilla -- * detectWay "baz.thr_p_o" == Just threadedProfiling --- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +-- * detectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") -- * detectWay "xru.p_ghc7.11.20141222.dll" == Just profiling detectWay :: FilePath -> Maybe Way detectWay file = case reads prefix of @@ -136,11 +141,11 @@ detectWay file = case reads prefix of _ -> Nothing where extension = takeExtension file - prefixed = if extension `notElem` ["so", "dll", "dynlib"] + prefixed = if extension `notElem` [".so", ".dll", ".dynlib"] then extension else takeExtension . dropExtension . dropExtension . dropExtension $ file - prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed + prefix = drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed -- Given a path, an extension suffix, and a file name check if the latter: -- 1) conforms to pattern 'path//*suffix' From git at git.haskell.org Thu Oct 26 23:33:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #68 from angerman/wrapper/ghc-pkg (c720603) Message-ID: <20171026233342.E9F3B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7206034ba32d2a14e583c03580826ddb28a0aa4/ghc >--------------------------------------------------------------- commit c7206034ba32d2a14e583c03580826ddb28a0aa4 Merge: 02b0d75 aee3088 Author: Andrey Mokhov Date: Thu Dec 31 12:27:30 2015 +0000 Merge pull request #68 from angerman/wrapper/ghc-pkg ghcPkg Wrapper >--------------------------------------------------------------- c7206034ba32d2a14e583c03580826ddb28a0aa4 shaking-up-ghc.cabal | 1 + src/Rules/Program.hs | 4 +++- src/Rules/Wrappers/GhcPkg.hs | 20 ++++++++++++++++++++ 3 files changed, 24 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:33:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add putSuccess helper function. (a6623ab) Message-ID: <20171026233346.495963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a6623ab5988c2705b22e8a5157db013595f634ce/ghc >--------------------------------------------------------------- commit a6623ab5988c2705b22e8a5157db013595f634ce Author: Andrey Mokhov Date: Fri Aug 7 02:56:33 2015 +0100 Add putSuccess helper function. >--------------------------------------------------------------- a6623ab5988c2705b22e8a5157db013595f634ce src/Util.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 1c34a87..7a68b2a 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -4,7 +4,7 @@ module Util ( replaceIf, replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, - putColoured, putOracle, putBuild, putError, + putColoured, putOracle, putBuild, putSuccess, putError, bimap, minusOrd, intersectOrd ) where @@ -69,6 +69,12 @@ putBuild :: String -> Action () putBuild = putColoured White -- A more colourful version of error +putSuccess :: String -> Action a +putSuccess msg = do + putColoured Green msg + error $ "GHC build system error: " ++ msg + +-- A more colourful version of error putError :: String -> Action a putError msg = do putColoured Red msg From git at git.haskell.org Thu Oct 26 23:33:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initialise inplace/lib/package.conf.d, fix #66. (84704cf) Message-ID: <20171026233346.90D423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84704cf2cf9324a09153b65f667581d03671e6ed/ghc >--------------------------------------------------------------- commit 84704cf2cf9324a09153b65f667581d03671e6ed Author: Andrey Mokhov Date: Thu Dec 31 13:53:29 2015 +0000 Initialise inplace/lib/package.conf.d, fix #66. >--------------------------------------------------------------- 84704cf2cf9324a09153b65f667581d03671e6ed src/Base.hs | 15 ++++++++++----- src/Rules/Cabal.hs | 20 +++++++++++--------- src/Rules/Wrappers/GhcPkg.hs | 5 +++-- src/Settings/Builders/GhcCabal.hs | 12 +++++++----- src/Settings/Builders/GhcPkg.hs | 7 +++++-- src/Stage.hs | 2 +- 6 files changed, 37 insertions(+), 24 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 25a69df..a127299 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,7 +16,7 @@ module Base ( -- * Paths shakeFilesPath, configPath, sourcePath, programInplacePath, bootPackageConstraints, packageDependencies, - bootstrappingConf, bootstrappingConfInitialised, + packageConfiguration, packageConfigurationInitialised, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, @@ -41,6 +41,9 @@ import System.Console.ANSI import qualified System.Directory as IO import System.IO +-- TODO: reexport Stage, etc.? +import Stage + -- Build system files and paths shakePath :: FilePath shakePath = "shake-build" @@ -65,11 +68,13 @@ bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" packageDependencies :: FilePath packageDependencies = shakeFilesPath -/- "package-dependencies" -bootstrappingConf :: FilePath -bootstrappingConf = "libraries/bootstrapping.conf" +packageConfiguration :: Stage -> FilePath +packageConfiguration Stage0 = "libraries/bootstrapping.conf" +packageConfiguration _ = "inplace/lib/package.conf.d" -bootstrappingConfInitialised :: FilePath -bootstrappingConfInitialised = shakeFilesPath -/- "bootstrapping-conf-initialised" +packageConfigurationInitialised :: Stage -> FilePath +packageConfigurationInitialised stage = + shakeFilesPath -/- "package-configuration-initialised-" ++ stageString stage -- Utility functions -- | Find and replace all occurrences of a value in a list diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 9239e67..ab7622c 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -39,17 +39,19 @@ cabalRules = do return . unwords $ pkgNameString pkg : sort depNames writeFileChanged out . unlines $ pkgDeps - -- When the file exists, the bootstrappingConf has been initialised + -- When the file exists, the packageConfiguration has been initialised -- TODO: get rid of an extra file? - bootstrappingConfInitialised %> \out -> do - removeDirectoryIfExists bootstrappingConf - -- TODO: can we get rid of this fake target? - let target = PartialTarget Stage0 cabal - build $ fullTarget target (GhcPkg Stage0) [] [bootstrappingConf] - let message = "Successfully initialised " ++ bootstrappingConf - writeFileChanged out message - putSuccess message + forM_ [Stage0 ..] $ \stage -> + packageConfigurationInitialised stage %> \out -> do + let target = PartialTarget stage cabal + pkgConf = packageConfiguration stage + removeDirectoryIfExists pkgConf + -- TODO: can we get rid of this fake target? + build $ fullTarget target (GhcPkg stage) [] [pkgConf] + let message = "Successfully initialised " ++ pkgConf + writeFileChanged out message + putSuccess message collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] diff --git a/src/Rules/Wrappers/GhcPkg.hs b/src/Rules/Wrappers/GhcPkg.hs index 7edc43c..3f70617 100644 --- a/src/Rules/Wrappers/GhcPkg.hs +++ b/src/Rules/Wrappers/GhcPkg.hs @@ -12,8 +12,9 @@ import Oracles ghcPkgWrapper :: FilePath -> Expr String ghcPkgWrapper program = do lift $ need [sourcePath -/- "Rules/Wrappers/GhcPkg.hs"] - top <- getSetting GhcSourcePath - let pkgConf = top -/- "inplace" -/- "lib" -/- "package.conf.d" + top <- getSetting GhcSourcePath + stage <- getStage + let pkgConf = top -/- packageConfiguration stage return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 597f591..06b2a63 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -85,11 +85,13 @@ configureArgs = do , conf "--with-cc" $ argStagedBuilderPath Gcc ] bootPackageDbArgs :: Args -bootPackageDbArgs = stage0 ? do - path <- getSetting GhcSourcePath - lift $ need [bootstrappingConfInitialised] - prefix <- ifM builderGhc (return "-package-db ") (return "--package-db=") - arg $ prefix ++ path -/- bootstrappingConf +bootPackageDbArgs = do + stage <- getStage + lift $ need [packageConfigurationInitialised stage] + stage0 ? do + path <- getSetting GhcSourcePath + prefix <- ifM builderGhc (return "-package-db ") (return "--package-db=") + arg $ prefix ++ path -/- packageConfiguration Stage0 packageConstraints :: Args packageConstraints = stage0 ? do diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index e79a360..c8e25ff 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -10,13 +10,16 @@ import Settings.Builders.GhcCabal ghcPkgArgs :: Args ghcPkgArgs = stagedBuilder GhcPkg ? (initArgs <> updateArgs) +initPredicate :: Predicate +initPredicate = orM $ map (file . packageConfiguration) [Stage0 ..] + initArgs :: Args -initArgs = file bootstrappingConf ? do +initArgs = initPredicate ? do mconcat [ arg "init" , arg =<< getOutput ] updateArgs :: Args -updateArgs = notM (file bootstrappingConf) ? do +updateArgs = notM initPredicate ? do path <- getTargetPath mconcat [ arg "update" , arg "--force" diff --git a/src/Stage.hs b/src/Stage.hs index 70fe6ba..144aa29 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} module Stage (Stage (..), stageString) where -import Base +import Development.Shake.Classes import GHC.Generics (Generic) -- TODO: explain stages From git at git.haskell.org Thu Oct 26 23:33:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add library targets. (e3e3c1d) Message-ID: <20171026233349.AAB033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3e3c1d6e03c1fd46af44afd5e29e7b1a4000093/ghc >--------------------------------------------------------------- commit e3e3c1d6e03c1fd46af44afd5e29e7b1a4000093 Author: Andrey Mokhov Date: Fri Aug 7 02:57:05 2015 +0100 Add library targets. >--------------------------------------------------------------- e3e3c1d6e03c1fd46af44afd5e29e7b1a4000093 src/Rules.hs | 22 +++++++++++++++++++--- 1 file changed, 19 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index be109f8..2509cf7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -2,15 +2,19 @@ module Rules ( oracleRules, cabalRules, configRules, packageRules, generateTargets ) where +import Way import Base import Util import Stage import Expression +import Oracles.PackageData import Rules.Cabal import Rules.Config import Rules.Package import Rules.Oracles import Rules.Resources +import Settings.Ways +import Settings.Util import Settings.Packages import Settings.TargetDirectory @@ -19,9 +23,21 @@ generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpret (stageTarget stage) getPackages - fmap concat . forM pkgs $ \pkg -> return - [ targetPath stage pkg -/- "build/haskell.deps" - , targetPath stage pkg -/- "build/c.deps" ] + fmap concat . forM pkgs $ \pkg -> do + let target = stagePackageTarget stage pkg + buildPath = targetPath stage pkg -/- "build" + buildGhciLib <- interpret target $ getPkgData BuildGhciLib + pkgKey <- interpret target $ getPkgData PackageKey + let ghciLib = [ buildPath -/- "HS" ++ pkgKey <.> "o" + | buildGhciLib == "YES" && stage /= Stage0 ] + + ways <- interpret target getWays + libs <- forM ways $ \way -> do + extension <- libsuf way + return $ buildPath -/- "libHS" ++ pkgKey <.> extension + + return $ ghciLib ++ libs + need targets -- TODO: add Stage2 (compiler only?) From git at git.haskell.org Thu Oct 26 23:33:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't re-initialise packageConfiguration in Stage2, see #66. (e2fb954) Message-ID: <20171026233350.015D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2fb95438402a6a76eff23be687020255a5cc218/ghc >--------------------------------------------------------------- commit e2fb95438402a6a76eff23be687020255a5cc218 Author: Andrey Mokhov Date: Thu Dec 31 14:06:07 2015 +0000 Don't re-initialise packageConfiguration in Stage2, see #66. >--------------------------------------------------------------- e2fb95438402a6a76eff23be687020255a5cc218 src/Base.hs | 4 +++- src/Rules/Cabal.hs | 2 +- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a127299..6f3b6d6 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -72,9 +72,11 @@ packageConfiguration :: Stage -> FilePath packageConfiguration Stage0 = "libraries/bootstrapping.conf" packageConfiguration _ = "inplace/lib/package.conf.d" +-- StageN, N > 0, share the same packageConfiguration (see above) packageConfigurationInitialised :: Stage -> FilePath packageConfigurationInitialised stage = - shakeFilesPath -/- "package-configuration-initialised-" ++ stageString stage + shakeFilesPath -/- "package-configuration-initialised-" + ++ stageString (min stage Stage1) -- Utility functions -- | Find and replace all occurrences of a value in a list diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index ab7622c..bf4c8f6 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -42,7 +42,7 @@ cabalRules = do -- When the file exists, the packageConfiguration has been initialised -- TODO: get rid of an extra file? - forM_ [Stage0 ..] $ \stage -> + forM_ [Stage0, Stage1] $ \stage -> packageConfigurationInitialised stage %> \out -> do let target = PartialTarget stage cabal pkgConf = packageConfiguration stage From git at git.haskell.org Thu Oct 26 23:33:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for BUILD_GHCI_LIB field of package-data.mk. (85808dd) Message-ID: <20171026233353.1A6473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/85808dd149afdb17d34f9e877029bc8c50020b63/ghc >--------------------------------------------------------------- commit 85808dd149afdb17d34f9e877029bc8c50020b63 Author: Andrey Mokhov Date: Fri Aug 7 02:57:44 2015 +0100 Add support for BUILD_GHCI_LIB field of package-data.mk. >--------------------------------------------------------------- 85808dd149afdb17d34f9e877029bc8c50020b63 src/Oracles/PackageData.hs | 14 ++++++++------ 1 file changed, 8 insertions(+), 6 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index c01c87f..de9db7c 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -20,9 +20,10 @@ import qualified Data.HashMap.Strict as Map -- PackageDataList is used for multiple string options separated by spaces, -- such as 'path_MODULES = Data.Array Data.Array.Base ...'. -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] -data PackageData = Version FilePath - | PackageKey FilePath - | Synopsis FilePath +data PackageData = Version FilePath + | PackageKey FilePath + | Synopsis FilePath + | BuildGhciLib FilePath data PackageDataList = Modules FilePath | SrcDirs FilePath @@ -51,9 +52,10 @@ askPackageData path key = do pkgData :: PackageData -> Action String pkgData packageData = do let (key, path) = case packageData of - Version path -> ("VERSION" , path) - PackageKey path -> ("PACKAGE_KEY" , path) - Synopsis path -> ("SYNOPSIS" , path) + Version path -> ("VERSION" , path) + PackageKey path -> ("PACKAGE_KEY" , path) + Synopsis path -> ("SYNOPSIS" , path) + BuildGhciLib path -> ("BUILD_GHCI_LIB", path) fullKey = replaceSeparators '_' $ path ++ "_" ++ key pkgData = path -/- "package-data.mk" res <- askOracle $ PackageDataKey (pkgData, fullKey) From git at git.haskell.org Thu Oct 26 23:33:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (79ceb45) Message-ID: <20171026233353.70C5D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79ceb456ffb5511e630ace24ed409782119ddf5d/ghc >--------------------------------------------------------------- commit 79ceb456ffb5511e630ace24ed409782119ddf5d Author: Moritz Angermann Date: Fri Jan 1 01:20:06 2016 +0800 Update README.md Roll Linux / OS X into one section. This should fix #37. >--------------------------------------------------------------- 79ceb456ffb5511e630ace24ed409782119ddf5d README.md | 29 +++++++++++------------------ 1 file changed, 11 insertions(+), 18 deletions(-) diff --git a/README.md b/README.md index 93674a1..f26cc49 100644 --- a/README.md +++ b/README.md @@ -14,7 +14,13 @@ This is supposed to go into the `shake-build` directory of the GHC source tree. Trying it --------- -### Linux +Please see the [Preparation][ghc-preparation] on the haskell wiki +for general preparation. The preparation steps for the `shake` build system are +identical to those for the `make` build system. This means that you don't need +to adjust anything if you are already familiar with building ghc using the `make` +build system. + +### Linux / Mac OS X ```bash git clone git://git.haskell.org/ghc @@ -23,6 +29,9 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure +# or if you want to use clang (e.g. building on OS X) +./configure --with-gcc=$(which clang) # See #26 + ``` Now you have a couple of options: @@ -46,20 +55,6 @@ shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. -### Mac OS X - -```bash -git clone git://git.haskell.org/ghc -cd ghc -git submodule update --init -git clone git://github.com/snowleopard/shaking-up-ghc shake-build -./boot -./configure --with-gcc=$(which clang) # See #26 -./shake-build/build.sh -``` - -See the Linux section for running in a Cabal sandbox. - ### Resetting the build To reset the new build system run the build script with `-B` flag. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). @@ -76,10 +71,8 @@ documentation is currently non-existent, but we will start addressing this once the codebase stabilises. - - - [ghc-shake-wiki]: https://ghc.haskell.org/trac/ghc/wiki/Building/Shake +[ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-building-guide]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows [ghc]: https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler [shake-blog-post]: https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc From git at git.haskell.org Thu Oct 26 23:33:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement build rule for GHCI libraries. (020d528) Message-ID: <20171026233356.E0E4B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/020d528e4a296e264bee478f3d89b63d6bb1f0b9/ghc >--------------------------------------------------------------- commit 020d528e4a296e264bee478f3d89b63d6bb1f0b9 Author: Andrey Mokhov Date: Fri Aug 7 02:58:15 2015 +0100 Implement build rule for GHCI libraries. >--------------------------------------------------------------- 020d528e4a296e264bee478f3d89b63d6bb1f0b9 src/Rules/Library.hs | 53 +++++++++++++++++++-------------------- src/Settings/Builders/GhcCabal.hs | 1 + 2 files changed, 27 insertions(+), 27 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 5bd6551..c788edb 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -4,6 +4,7 @@ import Way import Base import Util import Builder +import Package import Switches import Expression import qualified Target @@ -12,6 +13,7 @@ import Settings.Util import Settings.TargetDirectory import Rules.Actions import Rules.Resources +import Data.List import Data.Maybe buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () @@ -21,6 +23,7 @@ buildPackageLibrary _ target = do path = targetPath stage pkg buildPath = path -/- "build" + -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do liftIO $ removeFiles "." [a] cSrcs <- interpret target $ getPkgDataList CSrcs @@ -33,31 +36,27 @@ buildPackageLibrary _ target = do need $ cObjs ++ hsObjs -- this will create split objects if required - splitObjs <- fmap concat $ forM hsSrcs $ \src -> do - let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" - getDirectoryFiles "" [files] - split <- interpret target splitObjects - let allObjs = if split - then cObjs ++ hsObjs ++ splitObjs - else cObjs ++ hsObjs - - build $ fullTarget target allObjs Ar [a] - --- ldRule :: Resources -> StagePackageTarget -> Rules () --- ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) = --- let pathDist = path dist --- buildDir = pathDist "build" --- in --- priority 2 $ (buildDir "*.o") %> \out -> do --- cObjs <- pkgCObjects path dist vanilla --- hObjs <- pkgDepHsObjects path dist vanilla --- need $ cObjs ++ hObjs --- run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out --- synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) --- putColoured Green $ "/--------\n| Successfully built package '" --- ++ name ++ "' (stage " ++ show stage ++ ")." --- putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." --- ++ "\n\\--------" --- -- Finally, record the argument list --- need [argListPath argListDir pkg stage] + splitObjs <- if split + then fmap concat $ forM hsSrcs $ \src -> do + let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" + getDirectoryFiles "" [files] + else return [] + + build $ fullTarget target (cObjs ++ hsObjs ++ splitObjs) Ar [a] + + synopsis <- interpret target $ getPkgData Synopsis + putSuccess $ "/--------\n| Successfully built package '" + ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + putSuccess $ "| Package synopsis: " + ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" + + -- TODO: this looks fragile as haskell objects can match this rule if their + -- names start with "HS" and they are on top of the module hierarchy. + (buildPath -/- "HS*.o") %> \o -> do + cSrcs <- interpret target $ getPkgDataList CSrcs + modules <- interpret target $ getPkgDataList Modules + let hsSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] + hsObjs = [ buildPath -/- src <.> "o" | src <- hsSrcs ] + build $ fullTarget target (cObjs ++ hsObjs) Ld [o] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 301791d..6969aec 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -39,6 +39,7 @@ cabalArgs = builder GhcCabal ? do , with Happy ] -- TODO: Isn't vanilla always built? If yes, some conditions are redundant. +-- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do ways <- getWays From git at git.haskell.org Thu Oct 26 23:33:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:33:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #72 from snowleopard/angerman-patch-4 (e97d689) Message-ID: <20171026233357.424CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e97d6892c70c570c2425d7e49f8b5158f0e584cf/ghc >--------------------------------------------------------------- commit e97d6892c70c570c2425d7e49f8b5158f0e584cf Merge: e2fb954 79ceb45 Author: Andrey Mokhov Date: Thu Dec 31 18:42:46 2015 +0000 Merge pull request #72 from snowleopard/angerman-patch-4 Update README.md >--------------------------------------------------------------- e97d6892c70c570c2425d7e49f8b5158f0e584cf README.md | 29 +++++++++++------------------ 1 file changed, 11 insertions(+), 18 deletions(-) From git at git.haskell.org Thu Oct 26 23:34:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove error from putSuccess :-) (9afd164) Message-ID: <20171026233400.446AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9afd164fa76821409208e8a425ccaee625a8ee94/ghc >--------------------------------------------------------------- commit 9afd164fa76821409208e8a425ccaee625a8ee94 Author: Andrey Mokhov Date: Fri Aug 7 12:24:17 2015 +0100 Remove error from putSuccess :-) >--------------------------------------------------------------- 9afd164fa76821409208e8a425ccaee625a8ee94 src/Util.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index 7a68b2a..dd0f2d8 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -69,10 +69,8 @@ putBuild :: String -> Action () putBuild = putColoured White -- A more colourful version of error -putSuccess :: String -> Action a -putSuccess msg = do - putColoured Green msg - error $ "GHC build system error: " ++ msg +putSuccess :: String -> Action () +putSuccess = putColoured Green -- A more colourful version of error putError :: String -> Action a From git at git.haskell.org Thu Oct 26 23:34:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Match generator sources exactly, see #69 and #70. (6c80bd8) Message-ID: <20171026233400.A65D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6c80bd874eb2d4ca9607009dcf33eedbe011d5cd/ghc >--------------------------------------------------------------- commit 6c80bd874eb2d4ca9607009dcf33eedbe011d5cd Author: Andrey Mokhov Date: Thu Dec 31 19:01:38 2015 +0000 Match generator sources exactly, see #69 and #70. >--------------------------------------------------------------- 6c80bd874eb2d4ca9607009dcf33eedbe011d5cd src/Rules/Generate.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index fd101a1..b53b2b8 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -83,11 +83,13 @@ generate file target expr = do generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let buildPath = targetPath stage pkg -/- "build" + dropBuild = drop (length buildPath + 1) generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) file <~ gen = generate file target gen in do generated ?> \file -> do - let pattern = "//" ++ takeBaseName file <.> "*" + let srcFile = dropBuild file + pattern = "//" ++ srcFile <.> "*" files <- fmap (filter (pattern ?==)) $ moduleFiles stage pkg let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ From git at git.haskell.org Thu Oct 26 23:34:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reverse the target list passed to need (otherwise the targets are build in reverse order). (b397bb3) Message-ID: <20171026233403.CB0903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b397bb360a980c60290df89a6b358b614edce5a9/ghc >--------------------------------------------------------------- commit b397bb360a980c60290df89a6b358b614edce5a9 Author: Andrey Mokhov Date: Fri Aug 7 12:25:28 2015 +0100 Reverse the target list passed to need (otherwise the targets are build in reverse order). >--------------------------------------------------------------- b397bb360a980c60290df89a6b358b614edce5a9 src/Rules.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules.hs b/src/Rules.hs index 2509cf7..43f5922 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -38,7 +38,7 @@ generateTargets = action $ do return $ ghciLib ++ libs - need targets + need $ reverse targets -- TODO: add Stage2 (compiler only?) packageRules :: Rules () From git at git.haskell.org Thu Oct 26 23:34:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix extention, see #69 and #70. (26cd11f) Message-ID: <20171026233404.2FA503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/26cd11fb2e334f7a09e53bcd0d0e1dbc4cb646fe/ghc >--------------------------------------------------------------- commit 26cd11fb2e334f7a09e53bcd0d0e1dbc4cb646fe Author: Andrey Mokhov Date: Thu Dec 31 19:12:39 2015 +0000 Fix extention, see #69 and #70. >--------------------------------------------------------------- 26cd11fb2e334f7a09e53bcd0d0e1dbc4cb646fe src/Rules/Generate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index b53b2b8..d8f7129 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -89,7 +89,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = in do generated ?> \file -> do let srcFile = dropBuild file - pattern = "//" ++ srcFile <.> "*" + pattern = "//" ++ srcFile -<.> "*" files <- fmap (filter (pattern ?==)) $ moduleFiles stage pkg let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ From git at git.haskell.org Thu Oct 26 23:34:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop need from build. Add appropriate needs to build rules. (5bb1d7e) Message-ID: <20171026233407.8D3983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5bb1d7e24f6f51f2d2e570de47b5f554bb990753/ghc >--------------------------------------------------------------- commit 5bb1d7e24f6f51f2d2e570de47b5f554bb990753 Author: Andrey Mokhov Date: Fri Aug 7 12:26:57 2015 +0100 Drop need from build. Add appropriate needs to build rules. >--------------------------------------------------------------- 5bb1d7e24f6f51f2d2e570de47b5f554bb990753 src/Rules/Actions.hs | 2 +- src/Rules/Compile.hs | 5 +++++ src/Rules/Data.hs | 1 + src/Rules/Dependencies.hs | 4 +++- 4 files changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 50eb87f..062a5d5 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -21,7 +21,7 @@ buildWithResources rs target = do let builder = Target.builder target deps = Target.dependencies target needBuilder builder - need deps + -- need deps -- TODO: think if needs could be done here path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 6f57a81..223f9b2 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -35,6 +35,11 @@ compilePackage _ target = do when (null cDeps && null hDeps) $ putError $ "Cannot determine sources for '" ++ obj ++ "'." + when (not (null cDeps) && not (null hDeps)) $ + putError $ "Both .c and .hs sources found for '" ++ obj ++ "'." + + need $ hDeps ++ cDeps + if null cDeps then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] else build $ fullTarget target cDeps (Gcc stage) [obj] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 8f365e8..8b3eb05 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -45,6 +45,7 @@ buildPackageData (Resources ghcCabal ghcPkg) target = do depPkgs = intersectOrd cmp (sort pkgs) deps need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] + need [cabal] buildWithResources [(ghcCabal, 1)] $ fullTarget target [cabal] GhcCabal files diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index bee85c6..ea47241 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -22,15 +22,17 @@ buildPackageDependencies _ target = in do (buildPath "*.c.deps") %> \depFile -> do let srcFile = dropBuild . dropExtension $ depFile + need [srcFile] build $ fullTarget target [srcFile] (GccM stage) [depFile] (buildPath -/- "c.deps") %> \file -> do srcs <- pkgDataList $ CSrcs path let depFiles = [ buildPath -/- src <.> "deps" | src <- srcs ] - need depFiles -- increase parallelism by needing all at once + need depFiles deps <- mapM readFile' depFiles writeFileChanged file (concat deps) (buildPath -/- "haskell.deps") %> \file -> do srcs <- interpret target getHsSources + need srcs build $ fullTarget target srcs (GhcM stage) [file] From git at git.haskell.org Thu Oct 26 23:34:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename builder arguments, fix #60. (56705eb) Message-ID: <20171026233407.D2D7E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56705eb7ed074516a370054db7e3b81bae1afca4/ghc >--------------------------------------------------------------- commit 56705eb7ed074516a370054db7e3b81bae1afca4 Author: Andrey Mokhov Date: Fri Jan 1 01:23:21 2016 +0000 Rename builder arguments, fix #60. >--------------------------------------------------------------- 56705eb7ed074516a370054db7e3b81bae1afca4 src/Settings/Args.hs | 32 ++++++++++++++++---------------- src/Settings/Builders/Alex.hs | 10 +++++----- src/Settings/Builders/Ar.hs | 14 +++++++------- src/Settings/Builders/DeriveConstants.hs | 6 +++--- src/Settings/Builders/Gcc.hs | 10 +++++----- src/Settings/Builders/GenPrimopCode.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 12 ++++++------ src/Settings/Builders/GhcCabal.hs | 11 ++++++----- src/Settings/Builders/GhcPkg.hs | 6 +++--- src/Settings/Builders/Haddock.hs | 6 +++--- src/Settings/Builders/Happy.hs | 12 ++++++------ src/Settings/Builders/HsCpp.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 6 +++--- src/Settings/Builders/Ld.hs | 6 +++--- 14 files changed, 72 insertions(+), 71 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 56705eb7ed074516a370054db7e3b81bae1afca4 From git at git.haskell.org Thu Oct 26 23:34:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (036328f) Message-ID: <20171026233411.700323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/036328f08a067c6d8817c1d56d43e4f5b68d9e0f/ghc >--------------------------------------------------------------- commit 036328f08a067c6d8817c1d56d43e4f5b68d9e0f Author: Andrey Mokhov Date: Fri Aug 7 12:28:07 2015 +0100 Clean up. >--------------------------------------------------------------- 036328f08a067c6d8817c1d56d43e4f5b68d9e0f src/Rules/Library.hs | 32 +++++++++++++++++--------------- 1 file changed, 17 insertions(+), 15 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index c788edb..fe0c72d 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -29,34 +29,36 @@ buildPackageLibrary _ target = do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules - let way = fromJust . detectWay $ a -- fromJust is safe - hsSrcs = map (replaceEq '.' '/') modules - cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] - hsObjs = [ buildPath -/- src <.> osuf way | src <- hsSrcs ] + let way = fromJust . detectWay $ a -- fromJust is safe + hSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] + hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] - need $ cObjs ++ hsObjs -- this will create split objects if required + need $ cObjs ++ hObjs -- this will create split objects if required split <- interpret target splitObjects splitObjs <- if split - then fmap concat $ forM hsSrcs $ \src -> do + then fmap concat $ forM hSrcs $ \src -> do let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" - getDirectoryFiles "" [files] + fmap (map unifyPath) $ getDirectoryFiles "" [files] else return [] - build $ fullTarget target (cObjs ++ hsObjs ++ splitObjs) Ar [a] + build $ fullTarget target (cObjs ++ hObjs ++ splitObjs) Ar [a] synopsis <- interpret target $ getPkgData Synopsis - putSuccess $ "/--------\n| Successfully built package '" - ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + putSuccess $ "/--------\n| Successfully built package library '" + ++ pkgName pkg + ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." putSuccess $ "| Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. - (buildPath -/- "HS*.o") %> \o -> do + priority 2 $ (buildPath -/- "HS*.o") %> \o -> do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules - let hsSrcs = map (replaceEq '.' '/') modules - cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] - hsObjs = [ buildPath -/- src <.> "o" | src <- hsSrcs ] - build $ fullTarget target (cObjs ++ hsObjs) Ld [o] + let hSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] + hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] + need $ cObjs ++ hObjs + build $ fullTarget target (cObjs ++ hObjs) Ld [o] From git at git.haskell.org Thu Oct 26 23:34:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update GhcPkg.hs (6dbe055) Message-ID: <20171026233411.B9A063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6dbe055462a3d943ade75da94f3e1d8f42d23d0d/ghc >--------------------------------------------------------------- commit 6dbe055462a3d943ade75da94f3e1d8f42d23d0d Author: Moritz Angermann Date: Fri Jan 1 14:31:07 2016 +0800 Update GhcPkg.hs - Fix package conf path. - Adds comment - Drops the left over comments from previous. >--------------------------------------------------------------- 6dbe055462a3d943ade75da94f3e1d8f42d23d0d src/Rules/Wrappers/GhcPkg.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Rules/Wrappers/GhcPkg.hs b/src/Rules/Wrappers/GhcPkg.hs index 3f70617..3e077ac 100644 --- a/src/Rules/Wrappers/GhcPkg.hs +++ b/src/Rules/Wrappers/GhcPkg.hs @@ -4,17 +4,14 @@ import Base import Expression import Oracles --- Note about wrapper: --- bindir is usually GhcSourcePath / inplace / bin --- topdir is usually GhcSourcePath / inplace / lib --- datadir is usually the same as topdir - ghcPkgWrapper :: FilePath -> Expr String ghcPkgWrapper program = do lift $ need [sourcePath -/- "Rules/Wrappers/GhcPkg.hs"] top <- getSetting GhcSourcePath stage <- getStage - let pkgConf = top -/- packageConfiguration stage + -- Use the package configuration for the next stage in the wrapper. + -- The wrapper is generated in StageN, but used in StageN+1. + let pkgConf = top -/- packageConfiguration (succ stage) return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) From git at git.haskell.org Thu Oct 26 23:34:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add hibootsuf and an unsafe version of safeDetectWay. (c48554d) Message-ID: <20171026233414.E24423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c48554d96ebfb9b55c4b6be9fcbc52b23b24ef2d/ghc >--------------------------------------------------------------- commit c48554d96ebfb9b55c4b6be9fcbc52b23b24ef2d Author: Andrey Mokhov Date: Fri Aug 7 22:32:59 2015 +0100 Add hibootsuf and an unsafe version of safeDetectWay. >--------------------------------------------------------------- c48554d96ebfb9b55c4b6be9fcbc52b23b24ef2d src/Way.hs | 39 ++++++++++++++++++++++----------------- 1 file changed, 22 insertions(+), 17 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 4d14025..74d1f26 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -9,8 +9,8 @@ module Way ( -- TODO: rename to "Way"? threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic, - wayPrefix, hisuf, osuf, hcsuf, obootsuf, ssuf, libsuf, - detectWay, matchBuildResult + wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, + safeDetectWay, detectWay, matchBuildResult ) where import Base @@ -103,11 +103,12 @@ wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" hisuf, osuf, hcsuf, obootsuf, ssuf :: Way -> String -osuf = (++ "o" ) . wayPrefix -ssuf = (++ "s" ) . wayPrefix -hisuf = (++ "hi" ) . wayPrefix -hcsuf = (++ "hc" ) . wayPrefix -obootsuf = (++ "o-boot") . wayPrefix +osuf = (++ "o" ) . wayPrefix +ssuf = (++ "s" ) . wayPrefix +hisuf = (++ "hi" ) . wayPrefix +hcsuf = (++ "hc" ) . wayPrefix +obootsuf = (++ "o-boot" ) . wayPrefix +hibootsuf = (++ "hi-boot") . wayPrefix -- Note: in the previous build system libsuf was mysteriously different -- from other suffixes. For example, in the profiling way it used to be @@ -131,12 +132,12 @@ libsuf way @ (Way set) = return $ prefix ++ "ghc" ++ version ++ extension -- Detect way from a given filename. Returns Nothing if there is no match: --- * detectWay "foo/bar.hi" == Just vanilla --- * detectWay "baz.thr_p_o" == Just threadedProfiling --- * detectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") --- * detectWay "xru.p_ghc7.11.20141222.dll" == Just profiling -detectWay :: FilePath -> Maybe Way -detectWay file = case reads prefix of +-- * safeDetectWay "foo/bar.hi" == Just vanilla +-- * safeDetectWay "baz.thr_p_o" == Just threadedProfiling +-- * safeDetectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") +-- * safeDetectWay "xru.p_ghc7.11.20141222.so" == Just profiling +safeDetectWay :: FilePath -> Maybe Way +safeDetectWay file = case reads prefix of [(way, "")] -> Just way _ -> Nothing where @@ -147,12 +148,16 @@ detectWay file = case reads prefix of dropExtension . dropExtension $ file prefix = drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed --- Given a path, an extension suffix, and a file name check if the latter: --- 1) conforms to pattern 'path//*suffix' --- 2) has extension prefixed with a known way tag, i.e. detectWay does not fail +-- Unsafe version of safeDetectWay. Useful when matchBuildResult has succeeded. +detectWay :: FilePath -> Way +detectWay = fromJust . safeDetectWay + +-- Given a path, an extension suffix, and a file name check: +-- 1) the file conforms to pattern 'path//*suffix' +-- 2) file's extension has a valid way tag (i.e., safeDetectWay does not fail) matchBuildResult :: FilePath -> String -> FilePath -> Bool matchBuildResult path suffix file = - (path "*" ++ suffix) ?== file && (isJust . detectWay $ file) + (path "*" ++ suffix) ?== file && isJust (safeDetectWay file) -- Instances for storing in the Shake database instance Binary Way where From git at git.haskell.org Thu Oct 26 23:34:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #74 from snowleopard/angerman-patch-5 (77655b7) Message-ID: <20171026233415.5370C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/77655b7c31c2e37c83bbe36937d4ca65dee74701/ghc >--------------------------------------------------------------- commit 77655b7c31c2e37c83bbe36937d4ca65dee74701 Merge: 56705eb 6dbe055 Author: Andrey Mokhov Date: Fri Jan 1 09:55:54 2016 +0000 Merge pull request #74 from snowleopard/angerman-patch-5 Update GhcPkg.hs >--------------------------------------------------------------- 77655b7c31c2e37c83bbe36937d4ca65dee74701 src/Rules/Wrappers/GhcPkg.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) From git at git.haskell.org Thu Oct 26 23:34:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for hs-boot files. (6344510) Message-ID: <20171026233418.52A3B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6344510f3cda3097bf77d62a021e70049407c9ac/ghc >--------------------------------------------------------------- commit 6344510f3cda3097bf77d62a021e70049407c9ac Author: Andrey Mokhov Date: Fri Aug 7 22:33:20 2015 +0100 Add support for hs-boot files. >--------------------------------------------------------------- 6344510f3cda3097bf77d62a021e70049407c9ac src/Rules/Compile.hs | 32 +++++++++++++++++++++++++------- src/Rules/Library.hs | 7 +++---- 2 files changed, 28 insertions(+), 11 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 223f9b2..35c9755 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -10,7 +10,6 @@ import Oracles.DependencyList import Settings.TargetDirectory import Rules.Actions import Rules.Resources -import Data.Maybe compilePackage :: Resources -> StagePackageTarget -> Rules () compilePackage _ target = do @@ -21,14 +20,16 @@ compilePackage _ target = do cDepsFile = buildPath -/- "c.deps" hDepsFile = buildPath -/- "haskell.deps" - matchBuildResult buildPath "hi" ?> \hi -> do - let way = fromJust . detectWay $ hi -- fromJust is safe - need [hi -<.> osuf way] + matchBuildResult buildPath "hi" ?> \hi -> + need [ hi -<.> osuf (detectWay hi) ] + + matchBuildResult buildPath "hi-boot" ?> \hiboot -> + need [ hiboot -<.> obootsuf (detectWay hiboot) ] matchBuildResult buildPath "o" ?> \obj -> do - let way = fromJust . detectWay $ obj -- fromJust is safe - vanillaObj = takeFileName obj -<.> "o" - cDeps <- dependencyList cDepsFile vanillaObj + let way = detectWay obj + cObj = takeFileName obj -<.> "o" + cDeps <- dependencyList cDepsFile cObj hDeps <- dependencyList hDepsFile obj let hSrcDeps = filter ("//*hs" ?==) hDeps @@ -43,3 +44,20 @@ compilePackage _ target = do if null cDeps then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] else build $ fullTarget target cDeps (Gcc stage) [obj] + + matchBuildResult buildPath "o-boot" ?> \obj -> do + let way = detectWay obj + hDeps <- dependencyList hDepsFile obj + let hSrcDeps = filter ("//*hs-boot" ?==) hDeps + + when (null hDeps) $ + putError $ "Cannot determine sources for '" ++ obj ++ "'." + + need hDeps + build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] + +-- TODO: add support for -dyno +-- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot +-- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ +-- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno +-- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index fe0c72d..8fd9b0b 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -14,7 +14,6 @@ import Settings.TargetDirectory import Rules.Actions import Rules.Resources import Data.List -import Data.Maybe buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () buildPackageLibrary _ target = do @@ -29,7 +28,7 @@ buildPackageLibrary _ target = do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules - let way = fromJust . detectWay $ a -- fromJust is safe + let way = detectWay a hSrcs = map (replaceEq '.' '/') modules cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] @@ -54,11 +53,11 @@ buildPackageLibrary _ target = do -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. - priority 2 $ (buildPath -/- "HS*.o") %> \o -> do + priority 2 $ (buildPath -/- "HS*.o") %> \obj -> do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules let hSrcs = map (replaceEq '.' '/') modules cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] need $ cObjs ++ hObjs - build $ fullTarget target (cObjs ++ hObjs) Ld [o] + build $ fullTarget target (cObjs ++ hObjs) Ld [obj] From git at git.haskell.org Thu Oct 26 23:34:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GenApply builder, #22. (4b70d6e) Message-ID: <20171026233418.D38D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b70d6e8c474ba0a7789be0b3009e625c1a27820/ghc >--------------------------------------------------------------- commit 4b70d6e8c474ba0a7789be0b3009e625c1a27820 Author: Andrey Mokhov Date: Sat Jan 2 02:09:27 2016 +0000 Add GenApply builder, #22. >--------------------------------------------------------------- 4b70d6e8c474ba0a7789be0b3009e625c1a27820 cfg/system.config.in | 1 + shaking-up-ghc.cabal | 4 +++- src/Builder.hs | 2 ++ src/Rules/Actions.hs | 16 ++++++++++------ src/Settings/Args.hs | 4 ++++ src/Settings/Builders/GenApply.hs | 8 ++++++++ 6 files changed, 28 insertions(+), 7 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index a2cfef3..c5808c7 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -22,6 +22,7 @@ haddock = inplace/bin/haddock hsc2hs = inplace/bin/hsc2hs genprimopcode = inplace/bin/genprimopcode +genapply = inplace/bin/genapply derive-constants = inplace/bin/deriveConstants hs-cpp = @HaskellCPPCmd@ diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 2c75566..48dd0b8 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -38,6 +38,7 @@ executable ghc-shake , Rules.Cabal , Rules.Compile , Rules.Config + , Rules.Copy , Rules.Data , Rules.Dependencies , Rules.Documentation @@ -48,7 +49,6 @@ executable ghc-shake , Rules.Generators.GhcPlatformH , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs - , Rules.Install , Rules.Library , Rules.Oracles , Rules.Package @@ -63,6 +63,7 @@ executable ghc-shake , Settings.Builders.Common , Settings.Builders.DeriveConstants , Settings.Builders.Gcc + , Settings.Builders.GenApply , Settings.Builders.GenPrimopCode , Settings.Builders.Ghc , Settings.Builders.GhcCabal @@ -82,6 +83,7 @@ executable ghc-shake , Settings.Packages.Haddock , Settings.Packages.Hp2ps , Settings.Packages.IntegerGmp + , Settings.Packages.Rts , Settings.Packages.RunGhc , Settings.TargetDirectory , Settings.User diff --git a/src/Builder.hs b/src/Builder.hs index b4b01c3..c8e3f6e 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -25,6 +25,7 @@ data Builder = Alex | DeriveConstants | Gcc Stage | GccM Stage + | GenApply | GenPrimopCode | Ghc Stage | GhcCabal @@ -60,6 +61,7 @@ builderKey builder = case builder of Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' + GenApply -> "genapply" GenPrimopCode -> "genprimopcode" Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 8b243eb..e930b52 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -27,14 +27,12 @@ buildWithResources rs target = do quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList - HsCpp -> do - let file = head $ Target.outputs target -- TODO: ugly - Stdout output <- cmd [path] argList - writeFileChanged file output + HsCpp -> captureStdout target path argList + GenApply -> captureStdout target path argList GenPrimopCode -> do - let src = head $ Target.inputs target -- TODO: ugly - file = head $ Target.outputs target + src <- interpret target getInput + file <- interpret target getOutput input <- readFile' src Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output @@ -45,6 +43,12 @@ buildWithResources rs target = do build :: Target -> Action () build = buildWithResources [] +captureStdout :: Target -> FilePath -> [String] -> Action () +captureStdout target path argList = do + file <- interpret target getOutput + Stdout output <- cmd [path] argList + writeFileChanged file output + -- Print out key information about the command being executed putInfo :: Target.Target -> Action () putInfo (Target.Target {..}) = putBuild $ renderBox $ diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 8066e81..c4c919c 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -7,6 +7,7 @@ import Settings.Builders.Alex import Settings.Builders.Ar import Settings.Builders.DeriveConstants import Settings.Builders.Gcc +import Settings.Builders.GenApply import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc import Settings.Builders.GhcCabal @@ -25,6 +26,7 @@ import Settings.Packages.GhcPrim import Settings.Packages.Haddock import Settings.Packages.Hp2ps import Settings.Packages.IntegerGmp +import Settings.Packages.Rts import Settings.Packages.RunGhc import Settings.User @@ -44,6 +46,7 @@ defaultBuilderArgs = mconcat , deriveConstantsBuilderArgs , gccBuilderArgs , gccMBuilderArgs + , genApplyBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs , ghcCabalBuilderArgs @@ -67,4 +70,5 @@ defaultPackageArgs = mconcat , haddockPackageArgs , hp2psPackageArgs , integerGmpPackageArgs + , rtsPackageArgs , runGhcPackageArgs ] diff --git a/src/Settings/Builders/GenApply.hs b/src/Settings/Builders/GenApply.hs new file mode 100644 index 0000000..2d8140a --- /dev/null +++ b/src/Settings/Builders/GenApply.hs @@ -0,0 +1,8 @@ +module Settings.Builders.GenApply (genApplyBuilderArgs) where + +import Expression + +-- Stdin/stdout are handled in a special way. See Rules/Actions.hs. +-- TODO: Dead code? ifeq "$(GhcUnregisterised)" "YES" GENAPPLY_OPTS = -u +genApplyBuilderArgs :: Args +genApplyBuilderArgs = mempty From git at git.haskell.org Thu Oct 26 23:34:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve zero build performance. (d2910ba) Message-ID: <20171026233422.0DADB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2910ba1570a2b8a21d83b7ace7d3437c8311b22/ghc >--------------------------------------------------------------- commit d2910ba1570a2b8a21d83b7ace7d3437c8311b22 Author: Andrey Mokhov Date: Sat Aug 8 01:03:26 2015 +0100 Improve zero build performance. >--------------------------------------------------------------- d2910ba1570a2b8a21d83b7ace7d3437c8311b22 src/Oracles/DependencyList.hs | 2 +- src/Rules/Compile.hs | 52 ++++++++++++++++++------------------------- src/Rules/Library.hs | 10 ++++++--- src/Settings/Builders/Ghc.hs | 5 +++++ 4 files changed, 35 insertions(+), 34 deletions(-) diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs index 900b48e..e571f7b 100644 --- a/src/Oracles/DependencyList.hs +++ b/src/Oracles/DependencyList.hs @@ -28,7 +28,7 @@ dependencyListOracle :: Rules () dependencyListOracle = do deps <- newCache $ \file -> do need [file] - putOracle $ "Reading " ++ file ++ "..." + putOracle $ "Reading dependencies from " ++ file ++ "..." contents <- parseMakefile <$> (liftIO $ readFile file) return . Map.fromList . map (bimap unifyPath (map unifyPath)) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 35c9755..66ab73b 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -27,37 +27,29 @@ compilePackage _ target = do need [ hiboot -<.> obootsuf (detectWay hiboot) ] matchBuildResult buildPath "o" ?> \obj -> do - let way = detectWay obj - cObj = takeFileName obj -<.> "o" - cDeps <- dependencyList cDepsFile cObj - hDeps <- dependencyList hDepsFile obj - let hSrcDeps = filter ("//*hs" ?==) hDeps - - when (null cDeps && null hDeps) $ - putError $ "Cannot determine sources for '" ++ obj ++ "'." - - when (not (null cDeps) && not (null hDeps)) $ - putError $ "Both .c and .hs sources found for '" ++ obj ++ "'." - - need $ hDeps ++ cDeps - - if null cDeps - then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] - else build $ fullTarget target cDeps (Gcc stage) [obj] + cDeps <- dependencyList cDepsFile (takeFileName obj -<.> "o") + if not (null cDeps) + then do -- obj is produced from a C source file + need cDeps + build $ fullTarget target cDeps (Gcc stage) [obj] + else do -- obj is produced from a Haskell source file + hDeps <- dependencyList hDepsFile obj + when (null hDeps) . putError $ + "No dependencies found for '" ++ obj ++ "'." + let way = detectWay obj + hSrc = head hDeps + unless ("//*hs" ?== hSrc) . putError $ + "No Haskell source file found for '" ++ obj ++ "'." + need hDeps + build $ fullTargetWithWay target [hSrc] (Ghc stage) way [obj] matchBuildResult buildPath "o-boot" ?> \obj -> do - let way = detectWay obj hDeps <- dependencyList hDepsFile obj - let hSrcDeps = filter ("//*hs-boot" ?==) hDeps - - when (null hDeps) $ - putError $ "Cannot determine sources for '" ++ obj ++ "'." - + when (null hDeps) . putError $ + "No dependencies found for '" ++ obj ++ "'." + let way = detectWay obj + hSrc = head hDeps + unless ("//*.hs-boot" ?== hSrc) . putError $ + "No Haskell source file found for '" ++ obj ++ "'." need hDeps - build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] - --- TODO: add support for -dyno --- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot --- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ --- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno --- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) + build $ fullTargetWithWay target [hSrc] (Ghc stage) way [obj] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 8fd9b0b..d9ce835 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -14,6 +14,7 @@ import Settings.TargetDirectory import Rules.Actions import Rules.Resources import Data.List +import qualified System.Directory as IO buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () buildPackageLibrary _ target = do @@ -33,13 +34,16 @@ buildPackageLibrary _ target = do cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] - need $ cObjs ++ hObjs -- this will create split objects if required + -- This will create split objects if required (we don't track them) + need $ cObjs ++ hObjs split <- interpret target splitObjects splitObjs <- if split then fmap concat $ forM hSrcs $ \src -> do - let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" - fmap (map unifyPath) $ getDirectoryFiles "" [files] + let splitPath = buildPath -/- src ++ "_" ++ osuf way ++ "_split" + contents <- liftIO $ IO.getDirectoryContents splitPath + return . map (splitPath -/-) + . filter (not . all (== '.')) $ contents else return [] build $ fullTarget target (cObjs ++ hObjs ++ splitObjs) Ar [a] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 9c120bc..8ece818 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -11,6 +11,11 @@ import Oracles.PackageData import Settings.Util import Settings.Ways +-- TODO: add support for -dyno +-- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot +-- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ +-- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno +-- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) -- TODO: check code duplication ghcArgs :: Args ghcArgs = stagedBuilder Ghc ? do From git at git.haskell.org Thu Oct 26 23:34:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename installRules into copyRules and add copy rules for ffi*.h files, #22. (3872f96) Message-ID: <20171026233422.945B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3872f96896f53e4967674a7e4839dfd0fe1700b7/ghc >--------------------------------------------------------------- commit 3872f96896f53e4967674a7e4839dfd0fe1700b7 Author: Andrey Mokhov Date: Sat Jan 2 02:12:02 2016 +0000 Rename installRules into copyRules and add copy rules for ffi*.h files, #22. >--------------------------------------------------------------- 3872f96896f53e4967674a7e4839dfd0fe1700b7 src/Main.hs | 4 ++-- src/Rules/Copy.hs | 32 ++++++++++++++++++++++++++++++++ src/Rules/Install.hs | 22 ---------------------- 3 files changed, 34 insertions(+), 24 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index fdc43cd..b2c5340 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,14 +3,14 @@ import Rules import Rules.Cabal import Rules.Config import Rules.Generate -import Rules.Install +import Rules.Copy import Rules.Oracles main :: IO () main = shakeArgs options $ do cabalRules -- see Rules.Cabal configRules -- see Rules.Config - installRules -- see Rules.Install + copyRules -- see Rules.Copy generateTargets -- see Rules generateRules -- see Rules.Generate oracleRules -- see Rules.Oracles diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs new file mode 100644 index 0000000..47d6f02 --- /dev/null +++ b/src/Rules/Copy.hs @@ -0,0 +1,32 @@ +module Rules.Copy (installTargets, copyRules) where + +import Base +import Expression +import GHC +import Rules.Generate +import Settings.TargetDirectory + +installTargets :: [FilePath] +installTargets = [ "inplace/lib/template-hsc.h" + , "inplace/lib/platformConstants" + , "inplace/lib/settings" ] + +copyRules :: Rules () +copyRules = do + targetPath Stage1 rts -/- "build/ffi*.h" %> \ffih -> do + ffiHPaths <- getDirectoryFiles "" ["libffi/build/inst/lib/*/include/ffi.h"] + when (length ffiHPaths /= 1) $ + putError "copyRules: cannot determine location of ffi.h" + let ffiHPath = takeDirectory $ head ffiHPaths + copy ffih ffiHPath + + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs + "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." + where + file <~ dir = file %> \_ -> copy file dir + + copy file dir = do + let source = dir -/- takeFileName file + copyFileChanged source file + putBuild $ "| Copy " ++ source ++ " -> " ++ file diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs deleted file mode 100644 index 2e74bd3..0000000 --- a/src/Rules/Install.hs +++ /dev/null @@ -1,22 +0,0 @@ -module Rules.Install (installTargets, installRules) where - -import Base -import Expression -import GHC -import Rules.Generate - -installTargets :: [FilePath] -installTargets = [ "inplace/lib/template-hsc.h" - , "inplace/lib/platformConstants" - , "inplace/lib/settings" ] - -installRules :: Rules () -installRules = do - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs - "inplace/lib/platformConstants" <~ derivedConstantsPath - "inplace/lib/settings" <~ "." - where - file <~ dir = file %> \out -> do - let source = dir -/- takeFileName out - copyFileChanged source out - putSuccess $ "| Installed " ++ source ++ " -> " ++ out From git at git.haskell.org Thu Oct 26 23:34:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to using one dependency file for all objects. (4914709) Message-ID: <20171026233425.910963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4914709cd864e4f28be22ea9e12d60b8f5945ffc/ghc >--------------------------------------------------------------- commit 4914709cd864e4f28be22ea9e12d60b8f5945ffc Author: Andrey Mokhov Date: Mon Aug 10 01:35:55 2015 +0100 Switch to using one dependency file for all objects. >--------------------------------------------------------------- 4914709cd864e4f28be22ea9e12d60b8f5945ffc src/Oracles/Dependencies.hs | 49 +++++++++++++++++++++++++++++++++++++++++++ src/Oracles/DependencyList.hs | 40 ----------------------------------- src/Rules/Dependencies.hs | 30 ++++++++++++++------------ 3 files changed, 66 insertions(+), 53 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs new file mode 100644 index 0000000..c301547 --- /dev/null +++ b/src/Oracles/Dependencies.hs @@ -0,0 +1,49 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} + +module Oracles.Dependencies ( + dependencies, + dependenciesOracle + ) where + +import Base +import Util +import Data.List +import Data.Function +import qualified Data.HashMap.Strict as Map +import Control.Applicative + +newtype DependenciesKey = DependenciesKey (FilePath, FilePath) + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +-- dependencies path obj is an action that looks up dependencies of an object +-- file in a generated dependecy file 'path/.dependencies'. +-- If the dependencies cannot be determined, an appropriate error is raised. +-- Otherwise, a pair (source, depFiles) is returned, such that obj can be +-- produced by compiling 'source'; the latter can also depend on a number of +-- other dependencies listed in depFiles. +dependencies :: FilePath -> FilePath -> Action (FilePath, [FilePath]) +dependencies path obj = do + let depFile = path -/- ".dependencies" + res1 <- askOracle $ DependenciesKey (depFile, obj) + -- if no dependencies found attempt to drop the way prefix (for *.c sources) + res2 <- case res1 of + Nothing -> askOracle $ DependenciesKey (depFile, obj -<.> "o") + _ -> return res1 + case res2 of + Nothing -> putError $ "No dependencies found for '" ++ obj ++ "'." + Just [] -> putError $ "Empty dependency list for '" ++ obj ++ "'." + Just (src:depFiles) -> return (src, depFiles) + +-- Oracle for 'path/dist/.dependencies' files +dependenciesOracle :: Rules () +dependenciesOracle = do + deps <- newCache $ \file -> do + putOracle $ "Reading dependencies from " ++ file ++ "..." + contents <- parseMakefile <$> readFile' file + return . Map.fromList . map (bimap unifyPath (map unifyPath)) + . map (bimap head concat . unzip) + . groupBy ((==) `on` fst) + . sortBy (compare `on` fst) $ contents + + addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file + return () diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs deleted file mode 100644 index e571f7b..0000000 --- a/src/Oracles/DependencyList.hs +++ /dev/null @@ -1,40 +0,0 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} - -module Oracles.DependencyList ( - dependencyList, - dependencyListOracle - ) where - -import Base -import Util -import Data.List -import Data.Maybe -import Data.Function -import qualified Data.HashMap.Strict as Map -import Control.Applicative - -newtype DependencyListKey = DependencyListKey (FilePath, FilePath) - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) - --- dependencyList depFile objFile is an action that looks up dependencies of an --- object file (objFile) in a generated dependecy file (depFile). -dependencyList :: FilePath -> FilePath -> Action [FilePath] -dependencyList depFile objFile = do - res <- askOracle $ DependencyListKey (depFile, objFile) - return . fromMaybe [] $ res - --- Oracle for 'path/dist/*.deps' files -dependencyListOracle :: Rules () -dependencyListOracle = do - deps <- newCache $ \file -> do - need [file] - putOracle $ "Reading dependencies from " ++ file ++ "..." - contents <- parseMakefile <$> (liftIO $ readFile file) - return . Map.fromList - . map (bimap unifyPath (map unifyPath)) - . map (bimap head concat . unzip) - . groupBy ((==) `on` fst) - . sortBy (compare `on` fst) $ contents - addOracle $ \(DependencyListKey (file, obj)) -> - Map.lookup (unifyPath obj) <$> deps (unifyPath file) - return () diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index ea47241..90c764f 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -19,20 +19,24 @@ buildPackageDependencies _ target = path = targetPath stage pkg buildPath = path -/- "build" dropBuild = (pkgPath pkg ++) . drop (length buildPath) + hDepFile = buildPath -/- ".hs-dependencies" in do - (buildPath "*.c.deps") %> \depFile -> do - let srcFile = dropBuild . dropExtension $ depFile + (buildPath "*.c.deps") %> \file -> do + let srcFile = dropBuild . dropExtension $ file need [srcFile] - build $ fullTarget target [srcFile] (GccM stage) [depFile] + build $ fullTarget target (GccM stage) [srcFile] [file] - (buildPath -/- "c.deps") %> \file -> do - srcs <- pkgDataList $ CSrcs path - let depFiles = [ buildPath -/- src <.> "deps" | src <- srcs ] - need depFiles - deps <- mapM readFile' depFiles - writeFileChanged file (concat deps) - - (buildPath -/- "haskell.deps") %> \file -> do - srcs <- interpret target getHsSources + hDepFile %> \file -> do + srcs <- interpret target getPackageSources need srcs - build $ fullTarget target srcs (GhcM stage) [file] + build $ fullTarget target (GhcM stage) srcs [file] + liftIO $ removeFiles "." [hDepFile <.> "bak"] + + (buildPath -/- ".dependencies") %> \file -> do + cSrcs <- pkgDataList $ CSrcs path + let cDepFiles = [ buildPath -/- src <.> "deps" | src <- cSrcs ] + need $ hDepFile : cDepFiles -- need all for more parallelism + cDeps <- fmap concat $ mapM readFile' cDepFiles + hDeps <- readFile' hDepFile + writeFileChanged file $ cDeps ++ hDeps + From git at git.haskell.org Thu Oct 26 23:34:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add basic support for rts package, #22. (34488df) Message-ID: <20171026233426.200253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34488dfe235c8793012a53a407359dcf0dff80b4/ghc >--------------------------------------------------------------- commit 34488dfe235c8793012a53a407359dcf0dff80b4 Author: Andrey Mokhov Date: Sat Jan 2 02:12:49 2016 +0000 Add basic support for rts package, #22. >--------------------------------------------------------------- 34488dfe235c8793012a53a407359dcf0dff80b4 src/GHC.hs | 17 ++-- src/Predicates.hs | 12 ++- src/Rules.hs | 8 +- src/Rules/Cabal.hs | 2 +- src/Rules/Data.hs | 18 +++++ src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 4 +- src/Rules/Generate.hs | 18 +++-- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Builders/Haddock.hs | 3 +- src/Settings/Packages.hs | 3 +- src/Settings/Packages/Rts.hs | 165 +++++++++++++++++++++++++++++++++++++++ 12 files changed, 228 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 34488dfe235c8793012a53a407359dcf0dff80b4 From git at git.haskell.org Thu Oct 26 23:34:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code, do renaming. (d41d5a7) Message-ID: <20171026233429.044603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d41d5a7e0efcad961a2ed77e1aecc10102834b89/ghc >--------------------------------------------------------------- commit d41d5a7e0efcad961a2ed77e1aecc10102834b89 Author: Andrey Mokhov Date: Mon Aug 10 01:38:57 2015 +0100 Clean up code, do renaming. >--------------------------------------------------------------- d41d5a7e0efcad961a2ed77e1aecc10102834b89 src/Expression.hs | 31 +++++++++++----------- src/Rules/Compile.hs | 37 +++++++++----------------- src/Rules/Data.hs | 4 +-- src/Rules/Library.hs | 4 +-- src/Rules/Oracles.hs | 14 +++++----- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Gcc.hs | 8 +++--- src/Settings/Builders/Ghc.hs | 9 ++++--- src/Settings/Builders/Ld.hs | 2 +- src/Target.hs | 63 ++++++++++++++++++++++---------------------- 10 files changed, 81 insertions(+), 93 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d41d5a7e0efcad961a2ed77e1aecc10102834b89 From git at git.haskell.org Thu Oct 26 23:34:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Ranlib and Tar builders. (d06dabc) Message-ID: <20171026233429.88A3D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d06dabcb601c169ad1f8742e318d899891b380e3/ghc >--------------------------------------------------------------- commit d06dabcb601c169ad1f8742e318d899891b380e3 Author: Andrey Mokhov Date: Sun Jan 3 01:09:34 2016 +0000 Add Ranlib and Tar builders. >--------------------------------------------------------------- d06dabcb601c169ad1f8742e318d899891b380e3 cfg/system.config.in | 2 ++ src/Builder.hs | 4 ++++ src/Settings/Args.hs | 4 +++- src/Settings/Builders/Tar.hs | 10 ++++++++++ 4 files changed, 19 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index c5808c7..7f9b8de 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -38,6 +38,8 @@ hscolour = @HSCOLOUR@ ld = @LdCmd@ nm = @NmCmd@ objdump = @ObjdumpCmd@ +ranlib = @REAL_RANLIB_CMD@ +tar = @TarCmd@ # Information about builders: #============================ diff --git a/src/Builder.hs b/src/Builder.hs index c8e3f6e..ad7c9f0 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -41,6 +41,8 @@ data Builder = Alex | Ld | Nm | Objdump + | Ranlib + | Tar | Unlit deriving (Show, Eq, Generic) @@ -81,6 +83,8 @@ builderKey builder = case builder of Ld -> "ld" Nm -> "nm" Objdump -> "objdump" + Ranlib -> "ranlib" + Tar -> "tar" Unlit -> "unlit" -- | Determine the location of a 'Builder' diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index c4c919c..a677c80 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -17,6 +17,7 @@ import Settings.Builders.Happy import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld +import Settings.Builders.Tar import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Directory @@ -57,7 +58,8 @@ defaultBuilderArgs = mconcat , happyBuilderArgs , hsc2hsBuilderArgs , hsCppBuilderArgs - , ldBuilderArgs ] + , ldBuilderArgs + , tarBuilderArgs ] defaultPackageArgs :: Args defaultPackageArgs = mconcat diff --git a/src/Settings/Builders/Tar.hs b/src/Settings/Builders/Tar.hs new file mode 100644 index 0000000..1f9f0ba --- /dev/null +++ b/src/Settings/Builders/Tar.hs @@ -0,0 +1,10 @@ +module Settings.Builders.Tar (tarBuilderArgs) where + +import Expression +import Predicates (builder) + +tarBuilderArgs :: Args +tarBuilderArgs = builder Tar ? do + mconcat [ arg "-xzf" + , arg =<< getInput + , arg "-C", arg =<< getOutput ] From git at git.haskell.org Thu Oct 26 23:34:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename getHsSources to getPackageSources. (810b1e2) Message-ID: <20171026233432.6A5DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/810b1e224cc0609b74ffae8d3772eb207e256879/ghc >--------------------------------------------------------------- commit 810b1e224cc0609b74ffae8d3772eb207e256879 Author: Andrey Mokhov Date: Mon Aug 10 01:39:47 2015 +0100 Rename getHsSources to getPackageSources. >--------------------------------------------------------------- 810b1e224cc0609b74ffae8d3772eb207e256879 src/Settings/Util.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 13e5be0..675ba1b 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -5,7 +5,7 @@ module Settings.Util ( getFlag, getSetting, getSettingList, getPkgData, getPkgDataList, getPackagePath, getTargetPath, getTargetDirectory, - getHsSources, + getPackageSources, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -73,8 +73,8 @@ getTargetDirectory :: Expr FilePath getTargetDirectory = liftM2 targetDirectory getStage getPackage -- Find all Haskell source files for the current target -getHsSources :: Expr [FilePath] -getHsSources = do +getPackageSources :: Expr [FilePath] +getPackageSources = do path <- getTargetPath pkgPath <- getPackagePath srcDirs <- getPkgDataList SrcDirs From git at git.haskell.org Thu Oct 26 23:34:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add COMPONENT_ID field to rts package-data.mk (#22). (d3eef6d) Message-ID: <20171026233433.06F2B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3eef6dc2e2c2ae8b6727f17b610bb058f45282d/ghc >--------------------------------------------------------------- commit d3eef6dc2e2c2ae8b6727f17b610bb058f45282d Author: Andrey Mokhov Date: Sun Jan 3 01:11:16 2016 +0000 Add COMPONENT_ID field to rts package-data.mk (#22). >--------------------------------------------------------------- d3eef6dc2e2c2ae8b6727f17b610bb058f45282d src/Rules/Data.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index c2a186f..b24bb85 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -87,7 +87,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do includes <- interpretPartial target $ fromDiffExpr includesArgs let contents = unlines $ map (prefix++) [ "C_SRCS = " ++ unwords (cSrcs ++ cmmSrcs ++ extraSrcs) - , "CC_OPTS = " ++ unwords includes ] + , "CC_OPTS = " ++ unwords includes + , "COMPONENT_ID = " ++ "rts" ] writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." From git at git.haskell.org Thu Oct 26 23:34:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise ArgsHash oracle improving zero build time. (486a3e5) Message-ID: <20171026233435.C4B653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/486a3e58a9c323f651f733508492efe9a3e768d0/ghc >--------------------------------------------------------------- commit 486a3e58a9c323f651f733508492efe9a3e768d0 Author: Andrey Mokhov Date: Mon Aug 10 01:40:17 2015 +0100 Optimise ArgsHash oracle improving zero build time. >--------------------------------------------------------------- 486a3e58a9c323f651f733508492efe9a3e768d0 src/Oracles/ArgsHash.hs | 13 ++++++++----- src/Rules/Actions.hs | 4 +--- 2 files changed, 9 insertions(+), 8 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index ca0aa6c..f67f8c4 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -1,23 +1,26 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.ArgsHash ( - askArgsHash, argsHashOracle + checkArgsHash, argsHashOracle ) where import Base +import Target import Expression import Settings.Args import Control.Applicative -newtype ArgsHashKey = ArgsHashKey FullTarget - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +newtype ArgsHashKey = ArgsHashKey Target + deriving (Show, Eq, Typeable, Binary, Hashable, NFData) -- This is an action that given a full target determines the corresponding -- argument list and computes its hash. The resulting value is tracked in a -- Shake oracle, hence initiating rebuilts when the hash is changed (a hash -- change indicates changes in the build system). -askArgsHash :: FullTarget -> Action Int -askArgsHash = askOracle . ArgsHashKey +checkArgsHash :: FullTarget -> Action () +checkArgsHash target = do + tmp <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int + return () -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 062a5d5..2f9ebc6 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -19,13 +19,11 @@ import Settings.Builders.Ar buildWithResources :: [(Resource, Int)] -> FullTarget -> Action () buildWithResources rs target = do let builder = Target.builder target - deps = Target.dependencies target needBuilder builder - -- need deps -- TODO: think if needs could be done here path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed - argsHash <- askArgsHash target + checkArgsHash target withResources rs $ do putBuild $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" From git at git.haskell.org Thu Oct 26 23:34:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build libffi library, fix #75. (3b8aa92) Message-ID: <20171026233436.7CA573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b8aa92730ff232c16a6fa0da54b6e9c4fe47381/ghc >--------------------------------------------------------------- commit 3b8aa92730ff232c16a6fa0da54b6e9c4fe47381 Author: Andrey Mokhov Date: Sun Jan 3 01:12:26 2016 +0000 Build libffi library, fix #75. >--------------------------------------------------------------- 3b8aa92730ff232c16a6fa0da54b6e9c4fe47381 shaking-up-ghc.cabal | 2 + src/GHC.hs | 19 +++--- src/Main.hs | 2 + src/Rules.hs | 2 +- src/Rules/Cabal.hs | 19 +++--- src/Rules/Copy.hs | 5 +- src/Rules/Libffi.hs | 119 ++++++++++++++++++++++++++++++++++++++ src/Rules/Library.hs | 4 +- src/Rules/Program.hs | 2 +- src/Settings/Builders/Common.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 3 - src/Settings/Builders/Hsc2Hs.hs | 6 +- 12 files changed, 159 insertions(+), 29 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3b8aa92730ff232c16a6fa0da54b6e9c4fe47381 From git at git.haskell.org Thu Oct 26 23:34:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix performance drop due to improper use of removeFiles. (18a779b) Message-ID: <20171026233439.3DBB03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/18a779b20d3084cc681ce28ff88ca6b97d45903f/ghc >--------------------------------------------------------------- commit 18a779b20d3084cc681ce28ff88ca6b97d45903f Author: Andrey Mokhov Date: Tue Aug 11 00:16:38 2015 +0100 Fix performance drop due to improper use of removeFiles. >--------------------------------------------------------------- 18a779b20d3084cc681ce28ff88ca6b97d45903f src/Rules/Dependencies.hs | 3 ++- src/Rules/Library.hs | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 90c764f..8fb890e 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -11,6 +11,7 @@ import Settings.Util import Settings.TargetDirectory import Rules.Actions import Rules.Resources +import qualified System.Directory as IO buildPackageDependencies :: Resources -> StagePackageTarget -> Rules () buildPackageDependencies _ target = @@ -30,7 +31,7 @@ buildPackageDependencies _ target = srcs <- interpret target getPackageSources need srcs build $ fullTarget target (GhcM stage) srcs [file] - liftIO $ removeFiles "." [hDepFile <.> "bak"] + liftIO . IO.removeFile $ file <.> "bak" (buildPath -/- ".dependencies") %> \file -> do cSrcs <- pkgDataList $ CSrcs path diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 87a37ca..4619651 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -25,7 +25,7 @@ buildPackageLibrary _ target = do -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do - liftIO $ removeFiles "." [a] + liftIO $ IO.removeFile a cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules From git at git.haskell.org Thu Oct 26 23:34:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Register rts package, see #22 and #67. (9be3f7e) Message-ID: <20171026233439.ECF063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9be3f7e7f4de05897602959de5ee5025a10d7a8b/ghc >--------------------------------------------------------------- commit 9be3f7e7f4de05897602959de5ee5025a10d7a8b Author: Andrey Mokhov Date: Sun Jan 3 02:45:41 2016 +0000 Register rts package, see #22 and #67. >--------------------------------------------------------------- 9be3f7e7f4de05897602959de5ee5025a10d7a8b src/Base.hs | 13 +++++++++- src/Rules/Data.hs | 52 ++++++++++++++++++++++++-------------- src/Rules/Libffi.hs | 10 -------- src/Settings/Packages/Rts.hs | 59 ++++++++++++++++++++++++++++++++++++++++---- 4 files changed, 99 insertions(+), 35 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 9be3f7e7f4de05897602959de5ee5025a10d7a8b From git at git.haskell.org Thu Oct 26 23:34:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (096f602) Message-ID: <20171026233442.B46673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/096f6029109bf36ab29f2178942b62fdce884e26/ghc >--------------------------------------------------------------- commit 096f6029109bf36ab29f2178942b62fdce884e26 Author: Andrey Mokhov Date: Tue Aug 11 00:24:24 2015 +0100 Add comments. >--------------------------------------------------------------- 096f6029109bf36ab29f2178942b62fdce884e26 src/Oracles/ArgsHash.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index f67f8c4..422cacd 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -17,6 +17,12 @@ newtype ArgsHashKey = ArgsHashKey Target -- argument list and computes its hash. The resulting value is tracked in a -- Shake oracle, hence initiating rebuilts when the hash is changed (a hash -- change indicates changes in the build system). +-- Note: we replace target sources with ["src"] for performance reasons -- to +-- avoid storing long lists of source files passed to some builders (e.g. Ar) +-- in the Shake database. This optimisation is harmless, because argument list +-- constructors are assumed not to examine target sources, but only append them +-- to argument lists where appropriate. +-- TODO: enforce the above assumption via type trickery? checkArgsHash :: FullTarget -> Action () checkArgsHash target = do tmp <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int From git at git.haskell.org Thu Oct 26 23:34:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghcautoconf, ghcplatform as rtsConf dependencies (122a01d) Message-ID: <20171026233443.7C8C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/122a01d4350e0c8888a0bc0007f2edfccaf87f47/ghc >--------------------------------------------------------------- commit 122a01d4350e0c8888a0bc0007f2edfccaf87f47 Author: Moritz Angermann Date: Sun Jan 3 12:41:28 2016 +0800 Add ghcautoconf, ghcplatform as rtsConf dependencies This fixes #76. >--------------------------------------------------------------- 122a01d4350e0c8888a0bc0007f2edfccaf87f47 src/Rules/Data.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 00f6368..84ac619 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -99,7 +99,9 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fullTarget target (GhcPkg stage) [rtsConf] [] rtsConf %> \_ -> do - need [rtsConfIn] + need [rtsConfIn + , "includes/ghcautoconf.h" + , "includes/ghcplatform.h" ] build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] old <- liftIO $ readFile rtsConf let new = unlines . map (replace "\"\"" "") From git at git.haskell.org Thu Oct 26 23:34:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds ghcversion and derivedconstants to rts (25b2408) Message-ID: <20171026233446.DC0903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/25b2408edd914c06d2e25f16bde711e54a548f2c/ghc >--------------------------------------------------------------- commit 25b2408edd914c06d2e25f16bde711e54a548f2c Author: Moritz Angermann Date: Sun Jan 3 12:42:27 2016 +0800 Adds ghcversion and derivedconstants to rts Fixes #77 and fixes #76 (ghcverison). >--------------------------------------------------------------- 25b2408edd914c06d2e25f16bde711e54a548f2c src/Rules/Generate.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index e14b941..299f79a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -62,6 +62,9 @@ generatedDependencies stage pkg , "includes/ghcplatform.h" ] | pkg == rts = let buildPath = targetPath stage rts -/- "build" in + [ "includes/ghcversion.h" -- missing only in stage1. See #76 + , derivedConstantsPath -/- "DerivedConstants.h" ] + ++ fmap (buildPath -/-) ["ffi.h", "ffitarget.h"] | otherwise = [] From git at git.haskell.org Thu Oct 26 23:34:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add removeFile to Util.hs. (6b0b4ab) Message-ID: <20171026233446.394D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b0b4ab1c3d88df4e67d9ade22f45fcd8369708b/ghc >--------------------------------------------------------------- commit 6b0b4ab1c3d88df4e67d9ade22f45fcd8369708b Author: Andrey Mokhov Date: Tue Aug 11 02:48:11 2015 +0100 Add removeFile to Util.hs. >--------------------------------------------------------------- 6b0b4ab1c3d88df4e67d9ade22f45fcd8369708b src/Rules/Compile.hs | 2 -- src/Rules/Dependencies.hs | 3 +-- src/Rules/Library.hs | 10 +++++----- src/Util.hs | 12 +++++++++++- 4 files changed, 17 insertions(+), 10 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 43659b9..30a77cb 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -17,8 +17,6 @@ compilePackage _ target = do pkg = Target.package target path = targetPath stage pkg buildPath = path -/- "build" - cDepsFile = buildPath -/- "c.deps" - hDepsFile = buildPath -/- "haskell.deps" matchBuildResult buildPath "hi" ?> \hi -> need [ hi -<.> osuf (detectWay hi) ] diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 8fb890e..e63d27d 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -11,7 +11,6 @@ import Settings.Util import Settings.TargetDirectory import Rules.Actions import Rules.Resources -import qualified System.Directory as IO buildPackageDependencies :: Resources -> StagePackageTarget -> Rules () buildPackageDependencies _ target = @@ -31,7 +30,7 @@ buildPackageDependencies _ target = srcs <- interpret target getPackageSources need srcs build $ fullTarget target (GhcM stage) srcs [file] - liftIO . IO.removeFile $ file <.> "bak" + removeFile $ file <.> "bak" (buildPath -/- ".dependencies") %> \file -> do cSrcs <- pkgDataList $ CSrcs path diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 4619651..5956030 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -25,7 +25,7 @@ buildPackageLibrary _ target = do -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do - liftIO $ IO.removeFile a + removeFile a cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules @@ -34,17 +34,17 @@ buildPackageLibrary _ target = do cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] - -- This will create split objects if required (we don't track them) + -- This will create split objects if required (we don't track them + -- explicitly as this would needlessly bloat the Shake database). need $ cObjs ++ hObjs split <- interpret target splitObjects - splitObjs <- if split - then fmap concat $ forM hSrcs $ \src -> do + splitObjs <- if not split then return [] else + fmap concat $ forM hSrcs $ \src -> do let splitPath = buildPath -/- src ++ "_" ++ osuf way ++ "_split" contents <- liftIO $ IO.getDirectoryContents splitPath return . map (splitPath -/-) . filter (not . all (== '.')) $ contents - else return [] build $ fullTarget target Ar (cObjs ++ hObjs ++ splitObjs) [a] diff --git a/src/Util.hs b/src/Util.hs index dd0f2d8..b78592a 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -5,13 +5,16 @@ module Util ( unifyPath, (-/-), chunksOfSize, putColoured, putOracle, putBuild, putSuccess, putError, - bimap, minusOrd, intersectOrd + bimap, minusOrd, intersectOrd, + removeFile ) where import Base import Data.Char +import Control.Monad import System.IO import System.Console.ANSI +import qualified System.Directory as IO replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -100,3 +103,10 @@ intersectOrd cmp = loop LT -> loop xs (y:ys) EQ -> x : loop xs ys GT -> loop (x:xs) ys + +-- Convenient helper function for removing a single file that doesn't +-- necessarily exist. +removeFile :: FilePath -> Action () +removeFile file = do + exists <- liftIO $ IO.doesFileExist file + when exists . liftIO $ IO.removeFile file From git at git.haskell.org Thu Oct 26 23:34:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add trackBuildSystem switch (perhaps, temporarily). (2b2008d) Message-ID: <20171026233449.C41303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2b2008d6048aa691d8ea4f86e89c9ee5c4e2f300/ghc >--------------------------------------------------------------- commit 2b2008d6048aa691d8ea4f86e89c9ee5c4e2f300 Author: Andrey Mokhov Date: Wed Aug 12 01:27:28 2015 +0100 Add trackBuildSystem switch (perhaps, temporarily). >--------------------------------------------------------------- 2b2008d6048aa691d8ea4f86e89c9ee5c4e2f300 src/Rules/Actions.hs | 3 ++- src/Rules/Oracles.hs | 14 ++++++++------ src/Settings/User.hs | 11 +++++++++-- 3 files changed, 19 insertions(+), 9 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 2f9ebc6..9726e2f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -11,6 +11,7 @@ import Oracles.Setting import Oracles.ArgsHash import Settings.Args import Settings.Util +import Settings.User import Settings.Builders.Ar -- Build a given target using an appropriate builder and acquiring necessary @@ -23,7 +24,7 @@ buildWithResources rs target = do path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed - checkArgsHash target + when trackBuildSystem $ checkArgsHash target withResources rs $ do putBuild $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 32938ff..9b6d597 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -9,12 +9,14 @@ import Oracles.PackageData import Oracles.WindowsRoot import Oracles.PackageDeps import Oracles.Dependencies +import Settings.User +import Control.Monad oracleRules :: Rules () oracleRules = do - configOracle -- see Oracles.Base - packageDataOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - dependenciesOracle -- see Oracles.Dependencies - argsHashOracle -- see Oracles.ArgsHash - windowsRootOracle -- see Oracles.WindowsRoot + configOracle -- see Oracles.Base + packageDataOracle -- see Oracles.PackageData + packageDepsOracle -- see Oracles.PackageDeps + dependenciesOracle -- see Oracles.Dependencies + when trackBuildSystem argsHashOracle -- see Oracles.ArgsHash + windowsRootOracle -- see Oracles.WindowsRoot diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 572feb4..8831d65 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,7 +1,7 @@ module Settings.User ( userArgs, userPackages, userWays, userRtsWays, userTargetDirectory, userKnownPackages, integerLibrary, - buildHaddock, validating, ghciWithDebugger, ghcProfiled, + trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, dynamicGhcPrograms, laxDependencies ) where @@ -42,6 +42,14 @@ integerLibrary = integerGmp2 -- * Bool: a plain Boolean flag whose value is known at compile time -- * Action Bool: a flag whose value can depend on the build environment -- * Predicate: a flag depending on the build environment and the current target + +-- Set this to True if you are making any changes in the build system and want +-- appropriate rebuilds to be initiated. Switching this to False speeds things +-- up a little (particularly zero builds). +-- WARNING: changing this setting leads to a complete rebuild. +trackBuildSystem :: Bool +trackBuildSystem = False + validating :: Bool validating = False @@ -59,4 +67,3 @@ laxDependencies = False buildHaddock :: Predicate buildHaddock = return True - From git at git.haskell.org Thu Oct 26 23:34:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Rules for IntegerGmp (94f5e79) Message-ID: <20171026233450.8172C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/94f5e79a5947dca7fa4719f79f8892fa18d88f33/ghc >--------------------------------------------------------------- commit 94f5e79a5947dca7fa4719f79f8892fa18d88f33 Author: Moritz Angermann Date: Sun Jan 3 18:48:04 2016 +0800 Adds Rules for IntegerGmp This should fix #71. We build the integer-gmp library similary to libffi now. >--------------------------------------------------------------- 94f5e79a5947dca7fa4719f79f8892fa18d88f33 shaking-up-ghc.cabal | 1 + src/Main.hs | 2 + src/Rules/IntegerGmp.hs | 112 ++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 115 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 3f91f30..334cd59 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -49,6 +49,7 @@ executable ghc-shake , Rules.Generators.GhcPlatformH , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs + , Rules.IntegerGmp , Rules.Libffi , Rules.Library , Rules.Oracles diff --git a/src/Main.hs b/src/Main.hs index 82f0072..043e173 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -5,6 +5,7 @@ import Rules.Config import Rules.Generate import Rules.Copy import Rules.Libffi +import Rules.IntegerGmp import Rules.Oracles main :: IO () @@ -15,6 +16,7 @@ main = shakeArgs options $ do generateTargets -- see Rules generateRules -- see Rules.Generate libffiRules -- see Rules.Libffi + integerGmpRules -- see Rules.IntegerGmp oracleRules -- see Rules.Oracles packageRules -- see Rules where diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs new file mode 100644 index 0000000..443b912 --- /dev/null +++ b/src/Rules/IntegerGmp.hs @@ -0,0 +1,112 @@ +module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where + +import System.Directory + +import Base +import Expression +import GHC +import Oracles.Config.Setting +import Rules.Actions + +integerGmpBase :: FilePath +integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp" + +integerGmpBuild :: FilePath +integerGmpBuild = integerGmpBase -/- "gmpbuild" + +integerGmpLibrary :: FilePath +integerGmpLibrary = integerGmpBase -/- "libgmp.a" + +-- relative to integerGmpBuild +integerGmpPatch :: FilePath +integerGmpPatch = ".." -/- "tarball" -/- "gmp-5.0.4.patch" + +target :: PartialTarget +target = PartialTarget Stage0 integerGmp + +-- TODO: See Libffi.hs about removing code duplication. +configureEnvironment :: Action [CmdOption] +configureEnvironment = do + sequence [ builderEnv "CC" $ Gcc Stage1 + , builderEnv "CXX" $ Gcc Stage1 + , builderEnv "AR" Ar + , builderEnv "NM" Nm] + where + builderEnv var builder = do + needBuilder False builder + path <- builderPath builder + return $ AddEnv var path + +configureArguments :: Action [String] +configureArguments = do + hostPlatform <- setting HostPlatform + buildPlatform <- setting BuildPlatform + return [ "--enable-shared=no" + , "--host=" ++ hostPlatform + , "--build=" ++ buildPlatform] + +-- TODO: we rebuild integer-gmp every time. +integerGmpRules :: Rules () +integerGmpRules = do + integerGmpLibrary %> \_ -> do + need [sourcePath -/- "Rules" -/- "integerGmp.hs"] + + -- remove the old build folder, if it exists. + liftIO $ removeFiles integerGmpBuild ["//*"] + + -- unpack the gmp tarball. + -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is + -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. + -- That's because the doc/ directory contents are under the GFDL, + -- which causes problems for Debian. + tarballs <- getDirectoryFiles "" [integerGmpBase -/- "tarball/gmp*.tar.bz2"] + when (length tarballs /= 1) $ + putError $ "integerGmpRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + let filename = dropExtension . dropExtension . takeFileName $ head tarballs + let suffix = "-nodoc-patched" + unless (suffix `isSuffixOf` filename) $ + putError $ "integerGmpRules: expected suffix " ++ suffix + ++ " (found: " ++ filename ++ ")." + let libname = take (length filename - length suffix) filename + + need tarballs + build $ fullTarget target Tar tarballs [integerGmpBase] + + -- move gmp- to gmpbuild + let integerGmpExtracted = integerGmpBase -/- libname + liftIO $ renameDirectory integerGmpExtracted integerGmpBuild + putBuild $ "| Move " ++ integerGmpExtracted ++ " -> " ++ integerGmpBuild + + -- apply patches + -- TODO: replace "patch" with PATCH_CMD + unit $ cmd Shell [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch" + unit $ cmd Shell [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch] + putBuild $ "| Applied gmpsrc.patch and " ++ takeFileName integerGmpPatch + + -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? + + -- ./configure + putBuild "| Running libffi configure..." + envs <- configureEnvironment + args <- configureArguments + unit $ cmd Shell [Cwd integerGmpBuild] "bash configure" envs args + + -- make + putBuild "| Running make..." + unit $ cmd Shell "make" ["-C", integerGmpBuild, "MAKEFLAGS="] + + -- copy library and header + forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> do + let file' = integerGmpBase -/- takeFileName file + copyFileChanged (integerGmpBuild -/- file) file' + putBuild $ "| Copy " ++ file ++ " -> " ++ file' + + -- TODO: do we need these as well? + -- mkdir integerGmpBase -/- objs + -- unit $ cmd Shell [Cwd integerGmpBase -/- "objs"] "$AR_STAGE1 x ../libgmp.a" + -- $RANLIB_CMD integerGmpBase -/- "libgmp.a" + + putSuccess "| Successfully build custom library 'integer-gmp'" + + "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary] From git at git.haskell.org Thu Oct 26 23:34:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clarify comment. (f72d396) Message-ID: <20171026233453.6E2193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f72d3961e47c80754c60921b72c52e9e71a2410d/ghc >--------------------------------------------------------------- commit f72d3961e47c80754c60921b72c52e9e71a2410d Author: Andrey Mokhov Date: Wed Aug 12 01:30:38 2015 +0100 Clarify comment. >--------------------------------------------------------------- f72d3961e47c80754c60921b72c52e9e71a2410d src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 8831d65..1ca003b 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -46,7 +46,7 @@ integerLibrary = integerGmp2 -- Set this to True if you are making any changes in the build system and want -- appropriate rebuilds to be initiated. Switching this to False speeds things -- up a little (particularly zero builds). --- WARNING: changing this setting leads to a complete rebuild. +-- WARNING: a complete rebuild is required when changing this setting. trackBuildSystem :: Bool trackBuildSystem = False From git at git.haskell.org Thu Oct 26 23:34:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #78 from angerman/feature/dependencies (a4893ad) Message-ID: <20171026233454.171913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4893ad7be1b199ba407fa74b53c49f15eb152cf/ghc >--------------------------------------------------------------- commit a4893ad7be1b199ba407fa74b53c49f15eb152cf Merge: 9be3f7e 25b2408 Author: Andrey Mokhov Date: Sun Jan 3 12:11:40 2016 +0000 Merge pull request #78 from angerman/feature/dependencies Feature/dependencies >--------------------------------------------------------------- a4893ad7be1b199ba407fa74b53c49f15eb152cf src/Rules/Data.hs | 4 +++- src/Rules/Generate.hs | 3 +++ 2 files changed, 6 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:34:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add haddock path to cfg/system.config.in. (4e5ab6b) Message-ID: <20171026233456.D7BBC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e5ab6b936082f0c9718447b6dd143ec3785d67b/ghc >--------------------------------------------------------------- commit 4e5ab6b936082f0c9718447b6dd143ec3785d67b Author: Andrey Mokhov Date: Wed Aug 19 02:35:04 2015 +0100 Add haddock path to cfg/system.config.in. >--------------------------------------------------------------- 4e5ab6b936082f0c9718447b6dd143ec3785d67b cfg/system.config.in | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 029a81a..a274e84 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -5,18 +5,20 @@ #=================== system-ghc = @WithGhc@ +system-gcc = @CC_STAGE0@ +system-ghc-pkg = @GhcPkgCmd@ +gcc = @WhatGccIsCalled@ + ghc-stage1 = @hardtop@/inplace/bin/ghc-stage1 ghc-stage2 = @hardtop@/inplace/bin/ghc-stage2 ghc-stage3 = @hardtop@/inplace/bin/ghc-stage3 -system-ghc-pkg = @GhcPkgCmd@ ghc-pkg = @hardtop@/inplace/bin/ghc-pkg -system-gcc = @CC_STAGE0@ -gcc = @WhatGccIsCalled@ - ghc-cabal = @hardtop@/inplace/bin/ghc-cabal +haddock = @hardtop@/inplace/bin/haddock + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ From git at git.haskell.org Thu Oct 26 23:34:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:34:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #79 from angerman/feature/integer-gmp (ee639c7) Message-ID: <20171026233457.7933E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee639c7de4ae1861255953daa8f7b65d4a374c1f/ghc >--------------------------------------------------------------- commit ee639c7de4ae1861255953daa8f7b65d4a374c1f Merge: a4893ad 94f5e79 Author: Andrey Mokhov Date: Sun Jan 3 12:13:05 2016 +0000 Merge pull request #79 from angerman/feature/integer-gmp Adds Rules for IntegerGmp >--------------------------------------------------------------- ee639c7de4ae1861255953daa8f7b65d4a374c1f shaking-up-ghc.cabal | 1 + src/Main.hs | 2 + src/Rules/IntegerGmp.hs | 112 ++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 115 insertions(+) From git at git.haskell.org Thu Oct 26 23:35:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddock builder. (30687f3) Message-ID: <20171026233500.873F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30687f35a0f3ec3cdd488f2f55c0eaf626211ea2/ghc >--------------------------------------------------------------- commit 30687f35a0f3ec3cdd488f2f55c0eaf626211ea2 Author: Andrey Mokhov Date: Wed Aug 19 02:35:56 2015 +0100 Add Haddock builder. >--------------------------------------------------------------- 30687f35a0f3ec3cdd488f2f55c0eaf626211ea2 src/Builder.hs | 42 ++++++++++++++++++++++++------------------ 1 file changed, 24 insertions(+), 18 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index b175fac..ac184d3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -19,12 +19,13 @@ import GHC.Generics -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) --- TODO: add Cpp and Haddock builders +-- TODO: add Cpp builders -- TODO: rename Gcc to Cc? data Builder = Ar | Ld | Alex | Happy + | Haddock | HsColour | GhcCabal | Gcc Stage @@ -32,28 +33,33 @@ data Builder = Ar | GhcM Stage | GccM Stage | GhcPkg Stage + | GhcCabalHsColour deriving (Show, Eq, Generic) -- Configuration files refer to Builders as follows: +-- TODO: determine paths to utils without looking up configuration files builderKey :: Builder -> String builderKey builder = case builder of - Ar -> "ar" - Ld -> "ld" - Alex -> "alex" - Happy -> "happy" - HsColour -> "hscolour" - GhcCabal -> "ghc-cabal" - Ghc Stage0 -> "system-ghc" - Ghc Stage1 -> "ghc-stage1" - Ghc Stage2 -> "ghc-stage2" - Ghc Stage3 -> "ghc-stage3" - Gcc Stage0 -> "system-gcc" - Gcc _ -> "gcc" - GhcPkg Stage0 -> "system-ghc-pkg" - GhcPkg _ -> "ghc-pkg" - -- GhcM is currently a synonym for Ghc (to be called with -M flag) - GhcM stage -> builderKey $ Ghc stage - GccM stage -> builderKey $ Gcc stage + Ar -> "ar" + Ld -> "ld" + Alex -> "alex" + Happy -> "happy" + Haddock -> "haddock" + HsColour -> "hscolour" + GhcCabal -> "ghc-cabal" + Ghc Stage0 -> "system-ghc" + Ghc Stage1 -> "ghc-stage1" + Ghc Stage2 -> "ghc-stage2" + Ghc Stage3 -> "ghc-stage3" + Gcc Stage0 -> "system-gcc" + Gcc _ -> "gcc" + GhcPkg Stage0 -> "system-ghc-pkg" + GhcPkg _ -> "ghc-pkg" + -- GhcM/GccM are synonyms for Ghc/Gcc (called with -M and -MM flags) + GhcM stage -> builderKey $ Ghc stage + GccM stage -> builderKey $ Gcc stage + -- GhcCabalHsColour is a synonym for GhcCabal (called in hscolour mode) + GhcCabalHsColour -> builderKey $ GhcCabal builderPath :: Builder -> Action String builderPath builder = do From git at git.haskell.org Thu Oct 26 23:35:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds integer gmp path to the Gcc builder. (8cea200) Message-ID: <20171026233501.068483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8cea2007b3449adb88c35cbdbeaf2407b658c4ae/ghc >--------------------------------------------------------------- commit 8cea2007b3449adb88c35cbdbeaf2407b658c4ae Author: Moritz Angermann Date: Sun Jan 3 20:56:24 2016 +0800 Adds integer gmp path to the Gcc builder. This fixes the isse mentioned in #79, where `gmp.h` could not be found. >--------------------------------------------------------------- 8cea2007b3449adb88c35cbdbeaf2407b658c4ae src/Settings/Packages/IntegerGmp.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 1c8ed13..6d1b2b6 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -3,7 +3,7 @@ module Settings.Packages.IntegerGmp (integerGmpPackageArgs) where import Base import Expression import GHC (integerGmp) -import Predicates (builder, package) +import Predicates (builder, builderGcc, package) -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" @@ -11,9 +11,12 @@ import Predicates (builder, package) -- endif integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? - builder GhcCabal ? mconcat - [ arg "--configure-option=--with-intree-gmp" - , appendSub "--configure-option=CFLAGS" includeGmp - , appendSub "--gcc-options" includeGmp ] + mconcat + [ builder GhcCabal ? mconcat + [ arg "--configure-option=--with-intree-gmp" + , appendSub "--configure-option=CFLAGS" includeGmp + , appendSub "--gcc-options" includeGmp ] + , builderGcc ? ( arg $ "-I" ++ pkgPath integerGmp -/- "gmp" ) + ] where includeGmp = ["-I" ++ pkgPath integerGmp -/- "gmp"] From git at git.haskell.org Thu Oct 26 23:35:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add HiddenModules key to PackageData.hs. (3d65807) Message-ID: <20171026233504.1A2753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d6580728cc485bb8e16d4ee27ed04a8ec8c743e/ghc >--------------------------------------------------------------- commit 3d6580728cc485bb8e16d4ee27ed04a8ec8c743e Author: Andrey Mokhov Date: Wed Aug 19 02:36:33 2015 +0100 Add HiddenModules key to PackageData.hs. >--------------------------------------------------------------- 3d6580728cc485bb8e16d4ee27ed04a8ec8c743e src/Oracles/PackageData.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index de9db7c..4097ac1 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -26,6 +26,7 @@ data PackageData = Version FilePath | BuildGhciLib FilePath data PackageDataList = Modules FilePath + | HiddenModules FilePath | SrcDirs FilePath | IncludeDirs FilePath | Deps FilePath @@ -66,6 +67,7 @@ pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = do let (key, path, defaultValue) = case packageData of Modules path -> ("MODULES" , path, "" ) + HiddenModules path -> ("HIDDEN_MODULES" , path, "" ) SrcDirs path -> ("HS_SRC_DIRS" , path, ".") IncludeDirs path -> ("INCLUDE_DIRS" , path, ".") Deps path -> ("DEPS" , path, "" ) From git at git.haskell.org Thu Oct 26 23:35:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #80 from angerman/feature/integerGmpIncludePath (80d3477) Message-ID: <20171026233504.B877A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/80d34775cae65bfa0fbd26942a99cd546bcadfa0/ghc >--------------------------------------------------------------- commit 80d34775cae65bfa0fbd26942a99cd546bcadfa0 Merge: ee639c7 8cea200 Author: Andrey Mokhov Date: Sun Jan 3 13:17:44 2016 +0000 Merge pull request #80 from angerman/feature/integerGmpIncludePath Adds integer gmp path to the Gcc builder. >--------------------------------------------------------------- 80d34775cae65bfa0fbd26942a99cd546bcadfa0 src/Settings/Packages/IntegerGmp.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) From git at git.haskell.org Thu Oct 26 23:35:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add haddock build targets. (d811225) Message-ID: <20171026233507.92A1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d811225729618537302bde9cba2d591a2dd54ef4/ghc >--------------------------------------------------------------- commit d811225729618537302bde9cba2d591a2dd54ef4 Author: Andrey Mokhov Date: Wed Aug 19 02:37:30 2015 +0100 Add haddock build targets. >--------------------------------------------------------------- d811225729618537302bde9cba2d591a2dd54ef4 src/Rules.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Rules.hs b/src/Rules.hs index 43f5922..65ae2e4 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -14,6 +14,7 @@ import Rules.Package import Rules.Oracles import Rules.Resources import Settings.Ways +import Settings.User import Settings.Util import Settings.Packages import Settings.TargetDirectory @@ -28,15 +29,17 @@ generateTargets = action $ do buildPath = targetPath stage pkg -/- "build" buildGhciLib <- interpret target $ getPkgData BuildGhciLib pkgKey <- interpret target $ getPkgData PackageKey + buildHaddock <- interpret target $ Settings.User.buildHaddock let ghciLib = [ buildPath -/- "HS" ++ pkgKey <.> "o" | buildGhciLib == "YES" && stage /= Stage0 ] + haddock = [ pkgHaddockPath pkg | buildHaddock ] ways <- interpret target getWays libs <- forM ways $ \way -> do extension <- libsuf way return $ buildPath -/- "libHS" ++ pkgKey <.> extension - return $ ghciLib ++ libs + return $ ghciLib ++ libs ++ haddock need $ reverse targets From git at git.haskell.org Thu Oct 26 23:35:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split libgmp.a (d3d5b11) Message-ID: <20171026233508.38C3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3d5b11ab21eaee5e7dcdca007acc05131d512be/ghc >--------------------------------------------------------------- commit d3d5b11ab21eaee5e7dcdca007acc05131d512be Author: Moritz Angermann Date: Sun Jan 3 23:01:17 2016 +0800 Split libgmp.a Fixes the issue mentioned in #83 ``` * utils/hpc/stage1/build/tmp/hpc-bin * libraries/integer-gmp/stage1/build/libHSinteger-gmp-1.0.0.0.a * getDirectoryFiles [libraries/integer-gmp/gmp/objs/*.o] libraries/integer-gmp/gmp/objs: getDirectoryContents: does not exist (No such file or directory) ``` >--------------------------------------------------------------- d3d5b11ab21eaee5e7dcdca007acc05131d512be src/Rules/IntegerGmp.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 443b912..1f50dc0 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -53,6 +53,7 @@ integerGmpRules = do -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] + liftIO $ removeFiles (integerGmpBase -/- "objs") ["//*"] -- unpack the gmp tarball. -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is @@ -102,10 +103,13 @@ integerGmpRules = do copyFileChanged (integerGmpBuild -/- file) file' putBuild $ "| Copy " ++ file ++ " -> " ++ file' - -- TODO: do we need these as well? - -- mkdir integerGmpBase -/- objs - -- unit $ cmd Shell [Cwd integerGmpBase -/- "objs"] "$AR_STAGE1 x ../libgmp.a" - -- $RANLIB_CMD integerGmpBase -/- "libgmp.a" + ar <- builderPath Ar + ran <- builderPath Ranlib + -- unpack libgmp.a + putBuild "| Unpacking libgmp.a..." + unit $ cmd Shell [Cwd integerGmpBase] "mkdir -p objs" + unit $ cmd Shell [Cwd (integerGmpBase -/- "objs")] [ar] " x ../libgmp.a" + unit $ cmd Shell [Cwd integerGmpBase] [ran] " libgmp.a" putSuccess "| Successfully build custom library 'integer-gmp'" From git at git.haskell.org Thu Oct 26 23:35:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add pkgHaddockPath for finding haddock files. (0aedb12) Message-ID: <20171026233511.D0BEA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0aedb12d7790c167f3550b59c3303f8874c8af3c/ghc >--------------------------------------------------------------- commit 0aedb12d7790c167f3550b59c3303f8874c8af3c Author: Andrey Mokhov Date: Wed Aug 19 02:38:31 2015 +0100 Add pkgHaddockPath for finding haddock files. >--------------------------------------------------------------- 0aedb12d7790c167f3550b59c3303f8874c8af3c src/Settings/TargetDirectory.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 0844d14..10f0f67 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,7 +1,8 @@ module Settings.TargetDirectory ( - targetDirectory, targetPath + targetDirectory, targetPath, pkgHaddockPath ) where +import Base import Util import Stage import Package @@ -14,3 +15,9 @@ targetDirectory = userTargetDirectory -- Path to the target directory from GHC source root targetPath :: Stage -> Package -> FilePath targetPath stage pkg = pkgPath pkg -/- targetDirectory stage pkg + +-- Relative path to a package haddock file, e.g.: +-- "libraries/array/dist-install/doc/html/array/array.haddock" +pkgHaddockPath :: Package -> FilePath +pkgHaddockPath pkg @ (Package name _) = + targetPath Stage1 pkg -/- "doc/html" -/- name -/- name <.> "haddock" From git at git.haskell.org Thu Oct 26 23:35:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #85 from angerman/feature/fix-integer-gmp (d271649) Message-ID: <20171026233512.34C593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d27164938eff42d2622d416d5f81d7dd0833a32f/ghc >--------------------------------------------------------------- commit d27164938eff42d2622d416d5f81d7dd0833a32f Merge: 80d3477 d3d5b11 Author: Andrey Mokhov Date: Sun Jan 3 15:09:45 2016 +0000 Merge pull request #85 from angerman/feature/fix-integer-gmp Split libgmp.a >--------------------------------------------------------------- d27164938eff42d2622d416d5f81d7dd0833a32f src/Rules/IntegerGmp.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) From git at git.haskell.org Thu Oct 26 23:35:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build haddock only in Stage1. (2520d7f) Message-ID: <20171026233515.3F02F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2520d7fdb98c537591653f0f753398dd5e58cdb5/ghc >--------------------------------------------------------------- commit 2520d7fdb98c537591653f0f753398dd5e58cdb5 Author: Andrey Mokhov Date: Wed Aug 19 02:39:23 2015 +0100 Build haddock only in Stage1. >--------------------------------------------------------------- 2520d7fdb98c537591653f0f753398dd5e58cdb5 src/Settings/User.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 1ca003b..3646994 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -48,7 +48,7 @@ integerLibrary = integerGmp2 -- up a little (particularly zero builds). -- WARNING: a complete rebuild is required when changing this setting. trackBuildSystem :: Bool -trackBuildSystem = False +trackBuildSystem = True validating :: Bool validating = False @@ -66,4 +66,4 @@ laxDependencies :: Bool laxDependencies = False buildHaddock :: Predicate -buildHaddock = return True +buildHaddock = stage Stage1 From git at git.haskell.org Thu Oct 26 23:35:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for both *.gz and *.bz2 archives, see #79. (fd3a1f8) Message-ID: <20171026233515.9A6EF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd3a1f89719fb551ed3f6579ef978ab304abe66c/ghc >--------------------------------------------------------------- commit fd3a1f89719fb551ed3f6579ef978ab304abe66c Author: Andrey Mokhov Date: Sun Jan 3 18:16:59 2016 +0000 Add support for both *.gz and *.bz2 archives, see #79. >--------------------------------------------------------------- fd3a1f89719fb551ed3f6579ef978ab304abe66c src/Settings/Builders/Tar.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/Tar.hs b/src/Settings/Builders/Tar.hs index 1f9f0ba..f59b1cf 100644 --- a/src/Settings/Builders/Tar.hs +++ b/src/Settings/Builders/Tar.hs @@ -1,10 +1,14 @@ module Settings.Builders.Tar (tarBuilderArgs) where +import Base import Expression import Predicates (builder) tarBuilderArgs :: Args tarBuilderArgs = builder Tar ? do - mconcat [ arg "-xzf" - , arg =<< getInput + input <- getInput + mconcat [ arg "-xf" + , ("*.gz" ?== input) ? arg "--gzip" + , ("*.bz2" ?== input) ? arg "--bzip2" + , arg input , arg "-C", arg =<< getOutput ] From git at git.haskell.org Thu Oct 26 23:35:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Collect all arguments for haddock. (b16ec20) Message-ID: <20171026233518.BBF803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b16ec20251a2f1cee03156062be31fbad0b775dd/ghc >--------------------------------------------------------------- commit b16ec20251a2f1cee03156062be31fbad0b775dd Author: Andrey Mokhov Date: Wed Aug 19 02:41:39 2015 +0100 Collect all arguments for haddock. >--------------------------------------------------------------- b16ec20251a2f1cee03156062be31fbad0b775dd src/Settings/Args.hs | 3 ++ src/Settings/Builders/Ghc.hs | 97 +++++++++++++++++++-------------------- src/Settings/Builders/GhcCabal.hs | 16 +++++-- src/Settings/Builders/Haddock.hs | 69 ++++++++++++++++++++++++++++ src/Settings/Util.hs | 9 ++-- 5 files changed, 137 insertions(+), 57 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b16ec20251a2f1cee03156062be31fbad0b775dd From git at git.haskell.org Thu Oct 26 23:35:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add findKnownPackage for finding packages by name. (b51e6d9) Message-ID: <20171026233522.B116B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b51e6d97b5f930963687dca5eb64983324baa8b1/ghc >--------------------------------------------------------------- commit b51e6d97b5f930963687dca5eb64983324baa8b1 Author: Andrey Mokhov Date: Wed Aug 19 02:42:15 2015 +0100 Add findKnownPackage for finding packages by name. >--------------------------------------------------------------- b51e6d97b5f930963687dca5eb64983324baa8b1 src/Settings/Packages.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 6e236c9..369879c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -1,6 +1,6 @@ module Settings.Packages ( module Settings.Default, - packages, getPackages, knownPackages + packages, getPackages, knownPackages, findKnownPackage ) where import Package @@ -9,6 +9,7 @@ import Expression import Oracles.Setting import Settings.User import Settings.Default +import Data.List -- Combining default list of packages with user modifications packages :: Packages @@ -40,3 +41,11 @@ packagesStage1 = mconcat knownPackages :: [Package] knownPackages = defaultKnownPackages ++ userKnownPackages + +-- Note: this is slow but we keep it simple as there not too many packages (30) +-- We handle integerLibrary in a special way, because packages integerGmp and +-- integerGmp2 have the same package name -- we return the user-selected one. +findKnownPackage :: PackageName -> Maybe Package +findKnownPackage name + | name == pkgName integerLibrary = Just integerLibrary + | otherwise = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Thu Oct 26 23:35:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor our common build actions into src/Rules/Actions.hs (498939a) Message-ID: <20171026233519.104483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/498939a9b2942c4d95cc59b45721579a59a36f97/ghc >--------------------------------------------------------------- commit 498939a9b2942c4d95cc59b45721579a59a36f97 Author: Andrey Mokhov Date: Mon Jan 4 01:32:11 2016 +0000 Factor our common build actions into src/Rules/Actions.hs >--------------------------------------------------------------- 498939a9b2942c4d95cc59b45721579a59a36f97 src/Base.hs | 2 +- src/Rules/Actions.hs | 72 ++++++++++++++++++++++++++++++++++++++++++++++++---- src/Rules/Copy.hs | 11 +++----- src/Rules/Data.hs | 11 ++++---- src/Rules/Program.hs | 2 +- 5 files changed, 77 insertions(+), 21 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index acbd3c3..8733282 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -175,7 +175,7 @@ putError msg = do -- | Render the given set of lines in a ASCII box renderBox :: [String] -> String renderBox ls = - unlines $ [begin] ++ map (bar++) ls ++ [end] + unlines ([begin] ++ map (bar++) ls) ++ end where (begin,bar,end) | useUnicode = ( "╭──────────" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index e930b52..2a4fc80 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,9 +1,15 @@ {-# LANGUAGE RecordWildCards #-} -module Rules.Actions (build, buildWithResources) where +module Rules.Actions ( + build, buildWithResources, copyFile, createDirectory, moveDirectory, + fixFile, runConfigure, runMake, runBuilder + ) where + +import qualified System.Directory as IO import Base import Expression import Oracles.ArgsHash +import Oracles.Config.Setting import Settings import Settings.Args import Settings.Builders.Ar @@ -25,7 +31,14 @@ buildWithResources rs target = do withResources rs $ do unless verbose $ putInfo target quietlyUnlessVerbose $ case builder of - Ar -> arCmd path argList + Ar -> do + output <- interpret target getOutput + if "//*.a" ?== output + then arCmd path argList + else do + input <- interpret target getInput + top <- setting GhcSourcePath + cmd [path] [Cwd output] "x" (top -/- input) HsCpp -> captureStdout target path argList GenApply -> captureStdout target path argList @@ -49,13 +62,62 @@ captureStdout target path argList = do Stdout output <- cmd [path] argList writeFileChanged file output +copyFile :: FilePath -> FilePath -> Action () +copyFile source target = do + putBuild $ renderBox [ "Copy file" + , " input: " ++ source + , "=> output: " ++ target ] + copyFileChanged source target + +createDirectory :: FilePath -> Action () +createDirectory dir = do + putBuild $ "| Create directory " ++ dir + liftIO $ IO.createDirectoryIfMissing True dir + +-- Note, the source directory is untracked +moveDirectory :: FilePath -> FilePath -> Action () +moveDirectory source target = do + putBuild $ renderBox [ "Move directory" + , " input: " ++ source + , "=> output: " ++ target ] + liftIO $ IO.renameDirectory source target + +-- Transform a given file by applying a function to its contents +fixFile :: FilePath -> (String -> String) -> Action () +fixFile file f = do + putBuild $ "| Fix " ++ file + old <- liftIO $ readFile file + let new = f old + length new `seq` liftIO $ writeFile file new + +runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () +runConfigure dir opts args = do + need [dir -/- "configure"] + putBuild $ "| Run configure in " ++ dir ++ "..." + quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args + +runMake :: FilePath -> [String] -> Action () +runMake dir args = do + need [dir -/- "Makefile"] + let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." + quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args + +runBuilder :: Builder -> [String] -> Action () +runBuilder builder args = do + needBuilder laxDependencies builder + path <- builderPath builder + let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + putBuild $ "| Run " ++ show builder ++ note + quietly $ cmd [path] args + -- Print out key information about the command being executed putInfo :: Target.Target -> Action () -putInfo (Target.Target {..}) = putBuild $ renderBox $ - [ "Running " ++ show builder +putInfo (Target.Target {..}) = putBuild $ renderBox + [ "Run " ++ show builder ++ " (" ++ stageInfo ++ "package = " ++ pkgNameString package - ++ wayInfo ++ "):" + ++ wayInfo ++ ")" , " input: " ++ digest inputs , "=> output: " ++ digest outputs ] where diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index 766e865..3a385b8 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -3,6 +3,7 @@ module Rules.Copy (installTargets, copyRules) where import Base import Expression import GHC +import Rules.Actions import Rules.Generate import Rules.Libffi import Settings.TargetDirectory @@ -20,16 +21,10 @@ copyRules = do when (length ffiHPaths /= 1) $ putError $ "copyRules: exactly one ffi.h header expected" ++ "(found: " ++ show ffiHPaths ++ ")." - let ffiHPath = takeDirectory $ head ffiHPaths - copy ffih ffiHPath + copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." where - file <~ dir = file %> \_ -> copy file dir - - copy file dir = do - let source = dir -/- takeFileName file - copyFileChanged source file - putBuild $ "| Copy " ++ source ++ " -> " ++ file + file <~ dir = file %> \_ -> copyFile (dir -/- file) file diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 84ac619..274092b 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -118,10 +118,9 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 -- Reason: Shake's built-in makefile parser doesn't recognise slashes postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - contents <- fmap (filter ('$' `notElem`) . lines) . liftIO $ readFile file - length contents `seq` writeFileLines file $ map processLine contents +postProcessPackageData file = fixFile file fixPackageData + where + fixPackageData = unlines . map processLine . filter ('$' `notElem`) . lines + processLine line = replaceSeparators '_' prefix ++ suffix where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line + (prefix, suffix) = break (== '=') line diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index b2840dd..fe55005 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -59,7 +59,7 @@ buildWrapper :: PartialTarget -> Wrapper -> FilePath -> FilePath -> Action () buildWrapper target @ (PartialTarget stage pkg) wrapper wrapperPath binPath = do contents <- interpretPartial target $ wrapper binPath writeFileChanged wrapperPath contents - () <- cmd "chmod +x " [wrapperPath] + unit $ cmd "chmod +x " [wrapperPath] putSuccess $ "| Successfully created wrapper for '" ++ pkgNameString pkg ++ "' (" ++ show stage ++ ")." From git at git.haskell.org Thu Oct 26 23:35:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Respect trackBuildSystem user setting (4ce3206) Message-ID: <20171026233522.F25473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ce32069c4b46822dae309002fcbece8b62627ea/ghc >--------------------------------------------------------------- commit 4ce32069c4b46822dae309002fcbece8b62627ea Author: Andrey Mokhov Date: Mon Jan 4 01:33:45 2016 +0000 Respect trackBuildSystem user setting >--------------------------------------------------------------- 4ce32069c4b46822dae309002fcbece8b62627ea src/Rules/Generators/ConfigHs.hs | 3 ++- src/Rules/Generators/GhcAutoconfH.hs | 4 +++- src/Rules/Generators/GhcBootPlatformH.hs | 4 +++- src/Rules/Generators/GhcPlatformH.hs | 4 +++- src/Rules/Generators/GhcVersionH.hs | 4 ++++ src/Rules/Generators/VersionHs.hs | 4 +++- 6 files changed, 18 insertions(+), 5 deletions(-) diff --git a/src/Rules/Generators/ConfigHs.hs b/src/Rules/Generators/ConfigHs.hs index 1ec96e9..547670a 100644 --- a/src/Rules/Generators/ConfigHs.hs +++ b/src/Rules/Generators/ConfigHs.hs @@ -10,7 +10,8 @@ import Settings -- TODO: add tracking by moving these functions to separate tracked files generateConfigHs :: Expr String generateConfigHs = do - lift $ need [sourcePath -/- "Rules/Generators/ConfigHs.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/ConfigHs.hs"] cProjectName <- getSetting ProjectName cProjectGitCommitId <- getSetting ProjectGitCommitId cProjectVersion <- getSetting ProjectVersion diff --git a/src/Rules/Generators/GhcAutoconfH.hs b/src/Rules/Generators/GhcAutoconfH.hs index 67ec731..f5f89c6 100644 --- a/src/Rules/Generators/GhcAutoconfH.hs +++ b/src/Rules/Generators/GhcAutoconfH.hs @@ -3,6 +3,7 @@ module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH) where import Base import Expression import Oracles +import Settings.User -- TODO: change `mk/config.h` to `shake-build/cfg/config.h` configH :: FilePath @@ -16,7 +17,8 @@ undefinePackage s generateGhcAutoconfH :: Expr String generateGhcAutoconfH = do - lift $ need [sourcePath -/- "Rules/Generators/GhcAutoconfH.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcAutoconfH.hs"] configHContents <- lift $ map undefinePackage <$> readFileLines configH tablesNextToCode <- lift $ ghcEnableTablesNextToCode ghcUnreg <- getFlag GhcUnregisterised diff --git a/src/Rules/Generators/GhcBootPlatformH.hs b/src/Rules/Generators/GhcBootPlatformH.hs index 7416d24..6c111c2 100644 --- a/src/Rules/Generators/GhcBootPlatformH.hs +++ b/src/Rules/Generators/GhcBootPlatformH.hs @@ -3,10 +3,12 @@ module Rules.Generators.GhcBootPlatformH (generateGhcBootPlatformH) where import Base import Expression import Oracles +import Settings.User generateGhcBootPlatformH :: Expr String generateGhcBootPlatformH = do - lift $ need [sourcePath -/- "Rules/Generators/GhcBootPlatformH.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcBootPlatformH.hs"] stage <- getStage let cppify = replaceEq '-' '_' . replaceEq '.' '_' chooseSetting x y = getSetting $ if stage == Stage0 then x else y diff --git a/src/Rules/Generators/GhcPlatformH.hs b/src/Rules/Generators/GhcPlatformH.hs index 8652382..1deee3d 100644 --- a/src/Rules/Generators/GhcPlatformH.hs +++ b/src/Rules/Generators/GhcPlatformH.hs @@ -3,10 +3,12 @@ module Rules.Generators.GhcPlatformH (generateGhcPlatformH) where import Base import Expression import Oracles +import Settings.User generateGhcPlatformH :: Expr String generateGhcPlatformH = do - lift $ need [sourcePath -/- "Rules/Generators/GhcPlatformH.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcPlatformH.hs"] let cppify = replaceEq '-' '_' . replaceEq '.' '_' hostPlatform <- getSetting HostPlatform hostArch <- getSetting HostArch diff --git a/src/Rules/Generators/GhcVersionH.hs b/src/Rules/Generators/GhcVersionH.hs index a45df55..278813f 100644 --- a/src/Rules/Generators/GhcVersionH.hs +++ b/src/Rules/Generators/GhcVersionH.hs @@ -1,10 +1,14 @@ module Rules.Generators.GhcVersionH (generateGhcVersionH) where +import Base import Expression import Oracles +import Settings.User generateGhcVersionH :: Expr String generateGhcVersionH = do + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcVersionH.hs"] version <- getSetting ProjectVersionInt patchLevel1 <- getSetting ProjectPatchLevel1 patchLevel2 <- getSetting ProjectPatchLevel2 diff --git a/src/Rules/Generators/VersionHs.hs b/src/Rules/Generators/VersionHs.hs index 3023fc9..33b62193d 100644 --- a/src/Rules/Generators/VersionHs.hs +++ b/src/Rules/Generators/VersionHs.hs @@ -3,10 +3,12 @@ module Rules.Generators.VersionHs (generateVersionHs) where import Base import Expression import Oracles +import Settings.User generateVersionHs :: Expr String generateVersionHs = do - lift $ need [sourcePath -/- "Rules/Generators/VersionHs.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/VersionHs.hs"] projectVersion <- getSetting ProjectVersion targetOs <- getSetting TargetOs targetArch <- getSetting TargetArch From git at git.haskell.org Thu Oct 26 23:35:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement buildPackageDocumentation build rule. (b38d769) Message-ID: <20171026233526.3DE683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b38d769b73fa7576c2450c7d6057e5e0dd83b8f0/ghc >--------------------------------------------------------------- commit b38d769b73fa7576c2450c7d6057e5e0dd83b8f0 Author: Andrey Mokhov Date: Wed Aug 19 02:42:50 2015 +0100 Implement buildPackageDocumentation build rule. >--------------------------------------------------------------- b38d769b73fa7576c2450c7d6057e5e0dd83b8f0 src/Rules/Documentation.hs | 53 ++++++++++++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 4 +++- 2 files changed, 56 insertions(+), 1 deletion(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs new file mode 100644 index 0000000..9cde8d1 --- /dev/null +++ b/src/Rules/Documentation.hs @@ -0,0 +1,53 @@ +module Rules.Documentation (buildPackageDocumentation) where + +import Way +import Base +import Stage +import Builder +import Package +import Expression +import Oracles.PackageData +import qualified Target +import Settings.TargetDirectory +import Rules.Actions +import Rules.Resources +import Settings.Util +import Settings.User +import Settings.Packages +import Control.Monad.Extra + +-- Note: this build rule creates plenty of files, not just the .haddock one. +-- All of them go into the 'doc' subdirectory. Pedantically tracking all built +-- files in the Shake databases seems fragile and unnecesarry. +buildPackageDocumentation :: Resources -> StagePackageTarget -> Rules () +buildPackageDocumentation _ target = + let stage = Target.stage target + pkg = Target.package target + name = pkgName pkg + cabal = pkgCabalPath pkg + haddock = pkgHaddockPath pkg + in when (stage == Stage1) $ do + + haddock %> \file -> do + whenM (specified HsColour) $ do + need [cabal] + build $ fullTarget target GhcCabalHsColour [cabal] [] + srcs <- interpret target getPackageSources + deps <- interpret target $ getPkgDataList DepNames + let haddocks = [ pkgHaddockPath depPkg + | Just depPkg <- map findKnownPackage deps ] + need $ srcs ++ haddocks + let haddockWay = if dynamicGhcPrograms then dynamic else vanilla + build $ fullTargetWithWay target Haddock haddockWay srcs [file] + +-- $$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_DEPS = +-- $$(foreach n,$$($1_$2_DEPS) +-- ,$$($$n_HADDOCK_FILE) $$($$n_dist-install_$$(HADDOCK_WAY)_LIB)) + +-- $$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) : +-- $$$$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_DEPS) | $$$$(dir $$$$@)/. + +-- # Make the haddocking depend on the library .a file, to ensure +-- # that we wait until the library is fully built before we haddock it +-- $$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) : $$($1_$2_$$(HADDOCK_WAY)_LIB) +-- endif diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index dbbe5cc..6e5448b 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -7,10 +7,12 @@ import Rules.Compile import Rules.Library import Rules.Resources import Rules.Dependencies +import Rules.Documentation buildPackage :: Resources -> StagePackageTarget -> Rules () buildPackage = mconcat [ buildPackageData , buildPackageDependencies , compilePackage - , buildPackageLibrary ] + , buildPackageLibrary + , buildPackageDocumentation ] From git at git.haskell.org Thu Oct 26 23:35:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up build rules for custom packages. (1c3c9f3) Message-ID: <20171026233526.767553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c3c9f3438f0fbd80ff476f63e253ecf0355920a/ghc >--------------------------------------------------------------- commit 1c3c9f3438f0fbd80ff476f63e253ecf0355920a Author: Andrey Mokhov Date: Mon Jan 4 01:34:17 2016 +0000 Clean up build rules for custom packages. >--------------------------------------------------------------- 1c3c9f3438f0fbd80ff476f63e253ecf0355920a src/Rules/IntegerGmp.hs | 64 +++++++++++++++++++++---------------------------- src/Rules/Libffi.hs | 31 ++++++++---------------- 2 files changed, 37 insertions(+), 58 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 1f50dc0..4e19b9d 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,12 +1,11 @@ module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where -import System.Directory - import Base import Expression import GHC import Oracles.Config.Setting import Rules.Actions +import Settings.User integerGmpBase :: FilePath integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp" @@ -28,9 +27,8 @@ target = PartialTarget Stage0 integerGmp configureEnvironment :: Action [CmdOption] configureEnvironment = do sequence [ builderEnv "CC" $ Gcc Stage1 - , builderEnv "CXX" $ Gcc Stage1 , builderEnv "AR" Ar - , builderEnv "NM" Nm] + , builderEnv "NM" Nm ] where builderEnv var builder = do needBuilder False builder @@ -49,7 +47,7 @@ configureArguments = do integerGmpRules :: Rules () integerGmpRules = do integerGmpLibrary %> \_ -> do - need [sourcePath -/- "Rules" -/- "integerGmp.hs"] + when trackBuildSystem $ need [sourcePath -/- "Rules" -/- "integerGmp.hs"] -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] @@ -64,53 +62,45 @@ integerGmpRules = do when (length tarballs /= 1) $ putError $ "integerGmpRules: exactly one tarball expected" ++ "(found: " ++ show tarballs ++ ")." - let filename = dropExtension . dropExtension . takeFileName $ head tarballs - let suffix = "-nodoc-patched" - unless (suffix `isSuffixOf` filename) $ - putError $ "integerGmpRules: expected suffix " ++ suffix - ++ " (found: " ++ filename ++ ")." - let libname = take (length filename - length suffix) filename need tarballs build $ fullTarget target Tar tarballs [integerGmpBase] -- move gmp- to gmpbuild - let integerGmpExtracted = integerGmpBase -/- libname - liftIO $ renameDirectory integerGmpExtracted integerGmpBuild - putBuild $ "| Move " ++ integerGmpExtracted ++ " -> " ++ integerGmpBuild + let filename = dropExtension . dropExtension . takeFileName $ head tarballs + suffix = "-nodoc-patched" + unless (suffix `isSuffixOf` filename) $ + putError $ "integerGmpRules: expected suffix " ++ suffix + ++ " (found: " ++ filename ++ ")." + let libname = take (length filename - length suffix) filename + moveDirectory (integerGmpBase -/- libname) integerGmpBuild -- apply patches -- TODO: replace "patch" with PATCH_CMD - unit $ cmd Shell [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch" - unit $ cmd Shell [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch] - putBuild $ "| Applied gmpsrc.patch and " ++ takeFileName integerGmpPatch + unit . quietly $ cmd Shell (EchoStdout False) [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch" + putBuild $ "| Apply " ++ (integerGmpBase -/- "gmpsrc.patch") + unit . quietly $ cmd Shell (EchoStdout False) [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch] + putBuild $ "| Apply " ++ (integerGmpBase -/- integerGmpPatch) -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? - -- ./configure - putBuild "| Running libffi configure..." envs <- configureEnvironment args <- configureArguments - unit $ cmd Shell [Cwd integerGmpBuild] "bash configure" envs args + runConfigure integerGmpBuild envs args - -- make - putBuild "| Running make..." - unit $ cmd Shell "make" ["-C", integerGmpBuild, "MAKEFLAGS="] + runMake integerGmpBuild [] -- copy library and header - forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> do - let file' = integerGmpBase -/- takeFileName file - copyFileChanged (integerGmpBuild -/- file) file' - putBuild $ "| Copy " ++ file ++ " -> " ++ file' - - ar <- builderPath Ar - ran <- builderPath Ranlib - -- unpack libgmp.a - putBuild "| Unpacking libgmp.a..." - unit $ cmd Shell [Cwd integerGmpBase] "mkdir -p objs" - unit $ cmd Shell [Cwd (integerGmpBase -/- "objs")] [ar] " x ../libgmp.a" - unit $ cmd Shell [Cwd integerGmpBase] [ran] " libgmp.a" - - putSuccess "| Successfully build custom library 'integer-gmp'" + -- TODO: why copy library, can we move it instead? + forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> + copyFile (integerGmpBuild -/- file) (integerGmpBase -/- takeFileName file) + + let objsDir = integerGmpBase -/- "objs" + createDirectory objsDir + build $ fullTarget target Ar [integerGmpLibrary] [objsDir] + + runBuilder Ranlib [integerGmpLibrary] + + putSuccess "| Successfully built custom library 'integer-gmp'" "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary] diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index f5f2668..93a20ab 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,13 +1,12 @@ module Rules.Libffi (libffiRules, libffiLibrary) where -import System.Directory - import Base import Expression import GHC import Oracles.Config.Setting import Rules.Actions import Settings.Builders.Common +import Settings.User -- We use this file to track the whole libffi library libffiLibrary :: FilePath @@ -63,40 +62,30 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiLibrary %> \_ -> do - need [sourcePath -/- "Rules/Libffi.hs"] + when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] when (length tarballs /= 1) $ putError $ "libffiRules: exactly one libffi tarball expected" ++ "(found: " ++ show tarballs ++ ")." - let libname = dropExtension . dropExtension . takeFileName $ head tarballs need tarballs build $ fullTarget target Tar tarballs ["libffi-tarballs"] - let libffiExtracted = "libffi-tarballs" -/- libname - liftIO $ renameDirectory libffiExtracted libffiBuild - putBuild $ "| Move " ++ libffiExtracted ++ " -> " ++ libffiBuild + let libname = dropExtension . dropExtension . takeFileName $ head tarballs + moveDirectory ("libffi-tarballs" -/- libname) libffiBuild - old <- liftIO $ readFile libffiMakefile - let new = fixLibffiMakefile old - length new `seq` liftIO $ writeFile libffiMakefile new - putBuild $ "| Fix " ++ libffiMakefile + fixFile libffiMakefile fixLibffiMakefile - forM_ ["config.guess", "config.sub"] $ \file -> do - copyFileChanged file $ libffiBuild -/- file - putBuild $ "| Copy " ++ file ++ " -> " ++ (libffiBuild -/- file) + forM_ ["config.guess", "config.sub"] $ \file -> + copyFile file (libffiBuild -/- file) - putBuild $ "| Running libffi configure..." envs <- configureEnvironment args <- configureArguments - unit $ cmd Shell [Cwd libffiBuild] "bash configure" envs args - - putBuild $ "| Running make..." - unit $ cmd Shell "make" ["-C", libffiBuild, "MAKEFLAGS="] + runConfigure libffiBuild envs args - putBuild $ "| Running make install..." - unit $ cmd Shell "make" ["-C", libffiBuild, "MAKEFLAGS= install"] + runMake libffiBuild [] + runMake libffiBuild ["install"] putSuccess $ "| Successfully built custom library 'libffi'" From git at git.haskell.org Thu Oct 26 23:35:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop mk-miner submodule. (885369f) Message-ID: <20171026233530.211323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/885369f3c4ae9664bafc328ee191ec5efb090858/ghc >--------------------------------------------------------------- commit 885369f3c4ae9664bafc328ee191ec5efb090858 Author: Andrey Mokhov Date: Wed Aug 19 15:02:19 2015 +0100 Drop mk-miner submodule. >--------------------------------------------------------------- 885369f3c4ae9664bafc328ee191ec5efb090858 .gitmodules | 3 --- 1 file changed, 3 deletions(-) diff --git a/.gitmodules b/.gitmodules deleted file mode 100644 index 8f798aa..0000000 --- a/.gitmodules +++ /dev/null @@ -1,3 +0,0 @@ -[submodule "mk-miner"] - path = mk-miner - url = https://github.com/snowleopard/mk-miner.git From git at git.haskell.org Thu Oct 26 23:35:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix #87. (563307b) Message-ID: <20171026233530.5A2123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/563307bd23206aafe88c74088411ff55fa7bfb5a/ghc >--------------------------------------------------------------- commit 563307bd23206aafe88c74088411ff55fa7bfb5a Author: Andrey Mokhov Date: Mon Jan 4 01:45:12 2016 +0000 Fix #87. >--------------------------------------------------------------- 563307bd23206aafe88c74088411ff55fa7bfb5a src/Rules/Copy.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index 3a385b8..3f33d9c 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -27,4 +27,4 @@ copyRules = do "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." where - file <~ dir = file %> \_ -> copyFile (dir -/- file) file + file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file From git at git.haskell.org Thu Oct 26 23:35:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove traces of mk-miner submodule. (d56995a) Message-ID: <20171026233533.AA2CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d56995a00e2dbf7053bb3fdea357ef6e456b9639/ghc >--------------------------------------------------------------- commit d56995a00e2dbf7053bb3fdea357ef6e456b9639 Author: Andrey Mokhov Date: Wed Aug 19 15:14:52 2015 +0100 Remove traces of mk-miner submodule. >--------------------------------------------------------------- d56995a00e2dbf7053bb3fdea357ef6e456b9639 mk-miner | 1 - 1 file changed, 1 deletion(-) diff --git a/mk-miner b/mk-miner deleted file mode 160000 index 276425e..0000000 --- a/mk-miner +++ /dev/null @@ -1 +0,0 @@ -Subproject commit 276425ea44420f49ac34fd942c0dad84b0c0d332 From git at git.haskell.org Thu Oct 26 23:35:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build rts in stage1 instead of dist (c4c7a7f) Message-ID: <20171026233533.EBF5F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4c7a7f8d710c1a02ff68456f7ee9cb8fd5aa3a3/ghc >--------------------------------------------------------------- commit c4c7a7f8d710c1a02ff68456f7ee9cb8fd5aa3a3 Author: Moritz Angermann Date: Mon Jan 4 20:26:14 2016 +0800 Build rts in stage1 instead of dist `rts/dist` is hardcoded, while the shake build system builds in `rts/stage1`. Fixes #86 >--------------------------------------------------------------- c4c7a7f8d710c1a02ff68456f7ee9cb8fd5aa3a3 src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 274092b..b68f1c7 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -104,7 +104,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do , "includes/ghcplatform.h" ] build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] old <- liftIO $ readFile rtsConf - let new = unlines . map (replace "\"\"" "") + let new = unlines . map (replace "\"\"" "" . replace "rts/dist/build" "rts/stage1/build") . filter (not . null) $ lines old liftIO $ length new `seq` writeFile rtsConf new From git at git.haskell.org Thu Oct 26 23:35:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop custom cfg/configure.ac and instead add an appropriate AC_CONFIG_FILES command directly to the existing configure.ac. (d4f6e48) Message-ID: <20171026233537.227403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50/ghc >--------------------------------------------------------------- commit d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50 Author: Andrey Mokhov Date: Thu Aug 20 23:56:01 2015 +0100 Drop custom cfg/configure.ac and instead add an appropriate AC_CONFIG_FILES command directly to the existing configure.ac. >--------------------------------------------------------------- d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50 cfg/configure.ac | 1073 --------------------------------------------------- src/Rules/Config.hs | 17 +- 2 files changed, 16 insertions(+), 1074 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 d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50 From git at git.haskell.org Thu Oct 26 23:35:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy libffi into place (6d36942) Message-ID: <20171026233537.58E663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d369421eee990adb0f97e087dfc357fd7093262/ghc >--------------------------------------------------------------- commit 6d369421eee990adb0f97e087dfc357fd7093262 Author: Moritz Angermann Date: Mon Jan 4 20:27:15 2016 +0800 Copy libffi into place rts needs libffi as libCff in rts/stage1/build. This fixes #89 >--------------------------------------------------------------- 6d369421eee990adb0f97e087dfc357fd7093262 src/Rules/Copy.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index 3f33d9c..bcd1f1e 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -21,7 +21,9 @@ copyRules = do when (length ffiHPaths /= 1) $ putError $ "copyRules: exactly one ffi.h header expected" ++ "(found: " ++ show ffiHPaths ++ ")." + copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih + copyFile libffiLibrary (targetPath Stage1 rts -/- "build" -/- "libCffi.a") "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath From git at git.haskell.org Thu Oct 26 23:35:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move needBuilder to src/Builder.hs. (7baa070) Message-ID: <20171026233540.C2E153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7baa070bd5bb2b40235bdb362d1f0ec6063f260d/ghc >--------------------------------------------------------------- commit 7baa070bd5bb2b40235bdb362d1f0ec6063f260d Author: Andrey Mokhov Date: Fri Aug 21 16:07:01 2015 +0100 Move needBuilder to src/Builder.hs. >--------------------------------------------------------------- 7baa070bd5bb2b40235bdb362d1f0ec6063f260d src/Builder.hs | 25 +++++++++++++++++-------- 1 file changed, 17 insertions(+), 8 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index ac184d3..bd0ef49 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} module Builder ( - Builder (..), builderKey, builderPath, specified + Builder (..), builderKey, builderPath, specified, needBuilder ) where import Base @@ -61,7 +61,7 @@ builderKey builder = case builder of -- GhcCabalHsColour is a synonym for GhcCabal (called in hscolour mode) GhcCabalHsColour -> builderKey $ GhcCabal -builderPath :: Builder -> Action String +builderPath :: Builder -> Action FilePath builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ putError $ "\nCannot find path to '" ++ (builderKey builder) @@ -71,6 +71,21 @@ builderPath builder = do specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath +-- Make sure a builder exists on the given path and rebuild it if out of date. +-- If laxDependencies is True then we do not rebuild GHC even if it is out of +-- date (can save a lot of build time when changing GHC). +needBuilder :: Bool -> Builder -> Action () +needBuilder laxDependencies builder = do + path <- builderPath builder + if laxDependencies && allowOrderOnlyDependency builder + then orderOnly [path] + else need [path] + where + allowOrderOnlyDependency :: Builder -> Bool + allowOrderOnlyDependency (Ghc _) = True + allowOrderOnlyDependency (GhcM _) = True + allowOrderOnlyDependency _ = False + -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". fixAbsolutePathOnWindows :: FilePath -> Action FilePath @@ -84,12 +99,6 @@ fixAbsolutePathOnWindows path = do else return path --- When LaxDeps flag is set ('lax-dependencies = YES' in user.config), --- dependencies on the GHC executable are turned into order-only dependencies --- to avoid needless recompilation when making changes to GHC's sources. In --- certain situations this can lead to build failures, in which case you --- should reset the flag (at least temporarily). - -- Instances for storing in the Shake database instance Binary Builder instance Hashable Builder From git at git.haskell.org Thu Oct 26 23:35:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds integerGmpLibraryH to Rules.IntegerGmp (d40050f) Message-ID: <20171026233541.03B963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d40050fb1554db54db683f7d26a55bc3fb0868df/ghc >--------------------------------------------------------------- commit d40050fb1554db54db683f7d26a55bc3fb0868df Author: Moritz Angermann Date: Mon Jan 4 20:50:58 2016 +0800 Adds integerGmpLibraryH to Rules.IntegerGmp This is, so we can use integerGmpLibraryH, without having to use the path outside of the Rules.IntegerGmp module. >--------------------------------------------------------------- d40050fb1554db54db683f7d26a55bc3fb0868df src/Rules/IntegerGmp.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 4e19b9d..f927102 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,4 +1,4 @@ -module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where +module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary, integerGmpLibraryH) where import Base import Expression @@ -16,6 +16,9 @@ integerGmpBuild = integerGmpBase -/- "gmpbuild" integerGmpLibrary :: FilePath integerGmpLibrary = integerGmpBase -/- "libgmp.a" +integerGmpLibraryH :: FilePath +integerGmpLibraryH = integerGmpBase -/- "gmp.h" + -- relative to integerGmpBuild integerGmpPatch :: FilePath integerGmpPatch = ".." -/- "tarball" -/- "gmp-5.0.4.patch" @@ -103,4 +106,4 @@ integerGmpRules = do putSuccess "| Successfully built custom library 'integer-gmp'" - "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary] + integerGmpLibraryH %> \_ -> need [integerGmpLibrary] From git at git.haskell.org Thu Oct 26 23:35:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move basic predicates to src/Switches.hs. (4d70a1e) Message-ID: <20171026233544.4428A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4d70a1e6a5f3ed5353fa9d6af2daf013d1dde318/ghc >--------------------------------------------------------------- commit 4d70a1e6a5f3ed5353fa9d6af2daf013d1dde318 Author: Andrey Mokhov Date: Fri Aug 21 16:09:43 2015 +0100 Move basic predicates to src/Switches.hs. >--------------------------------------------------------------- 4d70a1e6a5f3ed5353fa9d6af2daf013d1dde318 src/Expression.hs | 40 ++++------------------------------------ src/Switches.hs | 46 +++++++++++++++++++++++++++++++++++----------- 2 files changed, 39 insertions(+), 47 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 44be38f..d51f434c 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -10,8 +10,7 @@ module Expression ( appendSub, appendSubD, filterSub, removeSub, interpret, interpretDiff, getStage, getPackage, getBuilder, getFiles, getFile, - getSources, getSource, getWay, - stage, package, builder, stagedBuilder, file, way + getSources, getSource, getWay ) where import Way @@ -30,13 +29,6 @@ import Control.Monad.Reader hiding (liftIO) -- parameters of the current build Target. type Expr a = ReaderT Target Action a --- If values of type a form a Monoid then so do computations of type Expr a: --- * the empty computation returns the identity element of the underlying type --- * two computations can be combined by combining their results -instance Monoid a => Monoid (Expr a) where - mempty = return mempty - mappend = liftM2 mappend - -- Diff a holds functions of type a -> a and is equipped with a Monoid instance. -- We could use Dual (Endo a) instead of Diff a, but the former may look scary. -- The name comes from "difference lists". @@ -105,7 +97,7 @@ p ?? (t, f) = p ? t <> notP p ? f -- A monadic version of append appendM :: Monoid a => Action a -> DiffExpr a -appendM mx = lift mx >>= append +appendM = (append =<<) . lift -- appendSub appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument @@ -185,29 +177,5 @@ getFile = do target <- ask files <- getFiles case files of - [file] -> return file - _ -> error $ "Exactly one file expected in target " ++ show target - --- Basic predicates (see Switches.hs for derived predicates) -stage :: Stage -> Predicate -stage s = liftM (s ==) getStage - -package :: Package -> Predicate -package p = liftM (p ==) getPackage - --- For unstaged builders, e.g. GhcCabal -builder :: Builder -> Predicate -builder b = liftM (b ==) getBuilder - --- For staged builders, e.g. Ghc Stage -stagedBuilder :: (Stage -> Builder) -> Predicate -stagedBuilder sb = do - stage <- getStage - builder <- getBuilder - return $ builder == sb stage - -file :: FilePattern -> Predicate -file f = liftM (any (f ?==)) getFiles - -way :: Way -> Predicate -way w = liftM (w ==) getWay + [res] -> return res + _ -> error $ "Exactly one file expected in target " ++ show target diff --git a/src/Switches.hs b/src/Switches.hs index 244c87f..c30a33f 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,15 +1,40 @@ module Switches ( + stage, package, builder, stagedBuilder, file, way, stage0, stage1, stage2, notStage, notStage0, registerPackage, splitObjects ) where +import Way +import Base import Stage +import Package +import Builder import Expression -import Settings.Util import Settings.Default import Oracles.Flag import Oracles.Setting +-- Basic predicates (see Switches.hs for derived predicates) +stage :: Stage -> Predicate +stage s = liftM (s ==) getStage + +package :: Package -> Predicate +package p = liftM (p ==) getPackage + +-- For unstaged builders, e.g. GhcCabal +builder :: Builder -> Predicate +builder b = liftM (b ==) getBuilder + +-- For staged builders, e.g. Ghc Stage +stagedBuilder :: (Stage -> Builder) -> Predicate +stagedBuilder sb = (builder . sb) =<< getStage + +file :: FilePattern -> Predicate +file f = liftM (any (f ?==)) getFiles + +way :: Way -> Predicate +way w = liftM (w ==) getWay + -- Derived predicates stage0 :: Predicate stage0 = stage Stage0 @@ -32,13 +57,12 @@ registerPackage = return True splitObjects :: Predicate splitObjects = do - stage <- getStage -- We don't split bootstrap (stage 0) packages - package <- getPackage -- We don't split compiler - broken <- getFlag SplitObjectsBroken - ghcUnreg <- getFlag GhcUnregisterised - goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] - goodOs <- lift $ targetOss [ "mingw32", "cygwin32", "linux" - , "darwin", "solaris2", "freebsd" - , "dragonfly", "netbsd", "openbsd"] - return $ stage == Stage1 && package /= compiler && not broken - && not ghcUnreg && goodArch && goodOs + goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages + goodPkg <- notP $ package compiler -- We don't split compiler + broken <- lift $ flag SplitObjectsBroken + ghcUnreg <- lift $ flag GhcUnregisterised + goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] + goodOs <- lift $ targetOss [ "mingw32", "cygwin32", "linux", "darwin" + , "solaris2", "freebsd", "dragonfly" + , "netbsd", "openbsd" ] + return $ goodStage && goodPkg && not broken && not ghcUnreg && goodArch && goodOs From git at git.haskell.org Thu Oct 26 23:35:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Integer Gmp Library to IntegerGmp (a228d2b) Message-ID: <20171026233544.7F6123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a228d2b44c75b4899f12a3700b98f181e3b408ec/ghc >--------------------------------------------------------------- commit a228d2b44c75b4899f12a3700b98f181e3b408ec Author: Moritz Angermann Date: Mon Jan 4 21:05:42 2016 +0800 Adds Integer Gmp Library to IntegerGmp This should fix #88 >--------------------------------------------------------------- a228d2b44c75b4899f12a3700b98f181e3b408ec src/Rules/Dependencies.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index d604488..3a3c49a 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -2,9 +2,11 @@ module Rules.Dependencies (buildPackageDependencies) where import Base import Expression +import GHC import Oracles import Rules.Actions import Rules.Generate +import Rules.IntegerGmp import Rules.Resources import Settings import Development.Shake.Util (parseMakefile) @@ -17,6 +19,9 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = hDepFile = buildPath -/- ".hs-dependencies" in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do + -- integerGmp (cbits/wrappers.c) depends on the integerGmp library, + -- which provides gmp.h + when (pkg == integerGmp) $ need [integerGmpLibraryH] let srcFile = dropBuild . dropExtension $ out orderOnly $ generatedDependencies stage pkg need [srcFile] From git at git.haskell.org Thu Oct 26 23:35:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Monoid (ReaderT Target Action a) instance to src/Target.hs. (95d2949) Message-ID: <20171026233547.A95093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95d2949e9c255d525adfcc6af61f6a7711ae5dab/ghc >--------------------------------------------------------------- commit 95d2949e9c255d525adfcc6af61f6a7711ae5dab Author: Andrey Mokhov Date: Fri Aug 21 16:10:44 2015 +0100 Move Monoid (ReaderT Target Action a) instance to src/Target.hs. >--------------------------------------------------------------- 95d2949e9c255d525adfcc6af61f6a7711ae5dab src/Target.hs | 14 ++++++++++++-- 1 file changed, 12 insertions(+), 2 deletions(-) diff --git a/src/Target.hs b/src/Target.hs index 2ce94bc..1717a87 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,6 +1,6 @@ -{-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} +{-# LANGUAGE DeriveGeneric, FlexibleInstances #-} module Target ( - Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), + Target (..), StageTarget, StagePackageTarget, FullTarget, stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay, ) where @@ -10,6 +10,8 @@ import Stage import Package import Builder import GHC.Generics +import Data.Monoid +import Control.Monad.Reader -- Target captures all parameters relevant to the current build target: -- * Stage and Package being built, @@ -28,6 +30,14 @@ data Target = Target } deriving (Show, Eq, Generic) +-- If values of type 'a' form a Monoid then we can also derive a Monoid instance +-- for values of type 'ReaderT Target Action a': +-- * the empty computation returns the identity element of the underlying type +-- * two computations can be combined by combining their results +instance Monoid a => Monoid (ReaderT Target Action a) where + mempty = return mempty + mappend = liftM2 mappend + -- StageTarget is a partially constructed Target. Only stage is guaranteed to -- be assigned. type StageTarget = Target From git at git.haskell.org Thu Oct 26 23:35:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop SUPPORTS_COMPONENT_ID which is no longer provided by configure. (72ed36f) Message-ID: <20171026233547.E87883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72ed36f9bfb99fc239d84026945e2b47446005ed/ghc >--------------------------------------------------------------- commit 72ed36f9bfb99fc239d84026945e2b47446005ed Author: Andrey Mokhov Date: Mon Jan 4 13:14:51 2016 +0000 Drop SUPPORTS_COMPONENT_ID which is no longer provided by configure. >--------------------------------------------------------------- 72ed36f9bfb99fc239d84026945e2b47446005ed cfg/system.config.in | 1 - src/Oracles/Config/Flag.hs | 2 -- src/Settings/Builders/Ghc.hs | 13 ++++--------- 3 files changed, 4 insertions(+), 12 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 7f9b8de..292d91f 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -53,7 +53,6 @@ cc-clang-backend = @CC_CLANG_BACKEND@ # Build options: #=============== -supports-component-id = @SUPPORTS_COMPONENT_ID@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index d40b762..44e8a17 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -18,7 +18,6 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken - | SupportsComponentId | WithLibdw -- Note, if a flag is set to empty string we treat it as set to NO. This seems @@ -34,7 +33,6 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" - SupportsComponentId -> "supports-component-id" WithLibdw -> "with-libdw" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a0f2678..9a07fc2 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -84,19 +84,14 @@ wayGhcArgs = do -- TODO: Improve handling of "-hide-all-packages" packageGhcArgs :: Args packageGhcArgs = do - stage <- getStage - pkg <- getPackage - supportsComponentId <- getFlag SupportsComponentId - compId <- getPkgData ComponentId - pkgDepIds <- getPkgDataList DepIds + pkg <- getPackage + compId <- getPkgData ComponentId + pkgDepIds <- getPkgDataList DepIds mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" , bootPackageDbArgs - , isLibrary pkg ? - if supportsComponentId || stage /= Stage0 - then arg $ "-this-package-key " ++ compId - else arg $ "-package-name " ++ compId + , isLibrary pkg ? (arg $ "-this-package-key " ++ compId) , append $ map ("-package-id " ++) pkgDepIds ] -- TODO: Improve handling of "cabal_macros.h" From git at git.haskell.org Thu Oct 26 23:35:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (bc4a11c) Message-ID: <20171026233551.AFA273A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc4a11c9eba6c98e82c2ed8e0f0452c101179660/ghc >--------------------------------------------------------------- commit bc4a11c9eba6c98e82c2ed8e0f0452c101179660 Author: Andrey Mokhov Date: Fri Aug 21 16:11:53 2015 +0100 Clean up. >--------------------------------------------------------------- bc4a11c9eba6c98e82c2ed8e0f0452c101179660 src/Way.hs | 12 +++++++++--- 1 file changed, 9 insertions(+), 3 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 74d1f26..a1df1ce 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,4 +1,4 @@ -module Way ( -- TODO: rename to "Way"? +module Way ( WayUnit (..), Way, wayFromUnits, wayUnit, @@ -13,7 +13,7 @@ module Way ( -- TODO: rename to "Way"? safeDetectWay, detectWay, matchBuildResult ) where -import Base +import Base hiding (unit) import Util import Oracles.Setting import Data.List @@ -74,6 +74,7 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b +vanilla, profiling, logging, parallel, granSim :: Way vanilla = wayFromUnits [] profiling = wayFromUnits [Profiling] logging = wayFromUnits [Logging] @@ -82,6 +83,11 @@ granSim = wayFromUnits [GranSim] -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? +threaded, threadedProfiling, threadedLogging, debug, debugProfiling, + threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, + threadedProfilingDynamic, threadedDynamic, threadedDebugDynamic, + debugDynamic, loggingDynamic, threadedLoggingDynamic :: Way + threaded = wayFromUnits [Threaded] threadedProfiling = wayFromUnits [Threaded, Profiling] threadedLogging = wayFromUnits [Threaded, Logging] @@ -102,7 +108,7 @@ wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" -hisuf, osuf, hcsuf, obootsuf, ssuf :: Way -> String +osuf, ssuf, hisuf, hcsuf, obootsuf, hibootsuf :: Way -> String osuf = (++ "o" ) . wayPrefix ssuf = (++ "s" ) . wayPrefix hisuf = (++ "hi" ) . wayPrefix From git at git.haskell.org Thu Oct 26 23:35:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #91 from angerman/feature/div (bee905c) Message-ID: <20171026233551.C14953A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bee905cfbb2d0fcc048b2c7837ef307e6447acae/ghc >--------------------------------------------------------------- commit bee905cfbb2d0fcc048b2c7837ef307e6447acae Merge: 72ed36f a228d2b Author: Andrey Mokhov Date: Mon Jan 4 13:31:32 2016 +0000 Merge pull request #91 from angerman/feature/div Feature/div >--------------------------------------------------------------- bee905cfbb2d0fcc048b2c7837ef307e6447acae src/Rules/Copy.hs | 2 ++ src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 5 +++++ src/Rules/IntegerGmp.hs | 7 +++++-- 4 files changed, 13 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:35:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop integerGmp2 and clean up. (efe9d6f) Message-ID: <20171026233555.3DA7A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efe9d6fa2c26d2befc6dcd97eadef5474f94c6e7/ghc >--------------------------------------------------------------- commit efe9d6fa2c26d2befc6dcd97eadef5474f94c6e7 Author: Andrey Mokhov Date: Fri Aug 21 16:12:27 2015 +0100 Drop integerGmp2 and clean up. >--------------------------------------------------------------- efe9d6fa2c26d2befc6dcd97eadef5474f94c6e7 src/Settings/Default.hs | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 5a021e7..71698da 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -3,8 +3,8 @@ module Settings.Default ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, - integerGmp2, integerSimple, parallel, pretty, primitive, process, stm, - templateHaskell, terminfo, time, transformers, unix, win32, xhtml + integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, + terminfo, time, transformers, unix, win32, xhtml ) where import Stage @@ -29,12 +29,16 @@ defaultTargetDirectory stage package defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghcPrim, haskeline - , hoopl, hpc, integerGmp, integerGmp2, integerSimple, parallel - , pretty, primitive, process, stm, templateHaskell, terminfo, time - , transformers, unix, win32, xhtml ] + , containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc + , integerGmp, integerSimple, parallel, pretty, primitive, process, stm + , templateHaskell, terminfo, time, transformers, unix, win32, xhtml ] -- Package definitions +array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, + deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, + integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, + terminfo, time, transformers, unix, win32, xhtml :: Package + array = library "array" base = library "base" binPackageDb = library "bin-package-db" @@ -51,7 +55,6 @@ haskeline = library "haskeline" hoopl = library "hoopl" hpc = library "hpc" integerGmp = library "integer-gmp" -integerGmp2 = library "integer-gmp" `setPath` "libraries/integer-gmp2" integerSimple = library "integer-simple" parallel = library "parallel" pretty = library "pretty" From git at git.haskell.org Thu Oct 26 23:35:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make output boxes prettier by closing them on the right (8235f15) Message-ID: <20171026233555.5391F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8235f157b7dc6debca50cce96905ab3327b6fee1/ghc >--------------------------------------------------------------- commit 8235f157b7dc6debca50cce96905ab3327b6fee1 Author: David Luposchainsky Date: Mon Jan 4 14:38:07 2016 +0100 Make output boxes prettier by closing them on the right >--------------------------------------------------------------- 8235f157b7dc6debca50cce96905ab3327b6fee1 src/Base.hs | 42 ++++++++++++++++++++++++++++++------------ 1 file changed, 30 insertions(+), 12 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 8733282..69904c4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -172,23 +172,41 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg --- | Render the given set of lines in a ASCII box +-- | Render the given set of lines in a nice box of ASCII renderBox :: [String] -> String -renderBox ls = - unlines ([begin] ++ map (bar++) ls) ++ end +renderBox ls = concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) where - (begin,bar,end) - | useUnicode = ( "╭──────────" - , "│ " - , "╰──────────" - ) - | otherwise = ( "/----------" - , "| " - , "\\----------" - ) + -- Minimum total width of the box in characters + minimumBoxWidth = 32 + -- FIXME: See Shake #364. useUnicode = False + -- Characters to draw the box + (dash, pipe, topLeft, topRight, botLeft, botRight, padding) + | useUnicode = ('─', '│', '╭', '╮', '╰', '╯', ' ') + | otherwise = ('-', '|', '/', '\\', '\\', '/', ' ') + + -- Box width, taking minimum desired length and content into account. + -- The -4 is for the beginning and end pipe/padding symbols, as + -- in "| xxx |". + boxContentWidth = (minimumBoxWidth - 4) `max` maxContentLength + where + maxContentLength = maximum (map length ls) + + renderLine l = concat + [ [pipe, padding] + , padToLengthWith boxContentWidth padding l + , [padding, pipe] ] + where + padToLengthWith n filler x = x ++ replicate (n - length x) filler + + (boxTop, boxBot) = ( topLeft : dashes ++ [topRight] + , botLeft : dashes ++ [botRight] ) + where + -- +1 for each non-dash (= corner) char + dashes = replicate (boxContentWidth + 2) dash + -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) From git at git.haskell.org Thu Oct 26 23:35:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #92 from quchen/closed-box (a2e9fb9) Message-ID: <20171026233558.BC8E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2e9fb9ef1192b41f732797f444bd9ad33c5eaf3/ghc >--------------------------------------------------------------- commit a2e9fb9ef1192b41f732797f444bd9ad33c5eaf3 Merge: bee905c 8235f15 Author: Andrey Mokhov Date: Mon Jan 4 14:18:51 2016 +0000 Merge pull request #92 from quchen/closed-box Make output boxes prettier by closing them on the right >--------------------------------------------------------------- a2e9fb9ef1192b41f732797f444bd9ad33c5eaf3 src/Base.hs | 42 ++++++++++++++++++++++++++++++------------ 1 file changed, 30 insertions(+), 12 deletions(-) From git at git.haskell.org Thu Oct 26 23:35:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:35:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, fix -Wall warnings. (4238fb7) Message-ID: <20171026233558.F01B23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4238fb77e4db131ddb1cb938a76f0dbe2b03a798/ghc >--------------------------------------------------------------- commit 4238fb77e4db131ddb1cb938a76f0dbe2b03a798 Author: Andrey Mokhov Date: Fri Aug 21 16:28:03 2015 +0100 Clean up, fix -Wall warnings. >--------------------------------------------------------------- 4238fb77e4db131ddb1cb938a76f0dbe2b03a798 src/Main.hs | 1 + src/Oracles/ArgsHash.hs | 4 +-- src/Oracles/Base.hs | 2 +- src/Oracles/Dependencies.hs | 2 +- src/Oracles/Flag.hs | 5 +-- src/Oracles/PackageDeps.hs | 2 +- src/Oracles/WindowsRoot.hs | 2 +- src/Package.hs | 6 ++-- src/Rules.hs | 14 ++++---- src/Rules/Actions.hs | 15 ++++---- src/Rules/Cabal.hs | 24 ++++++------- src/Rules/Config.hs | 5 +-- src/Rules/Data.hs | 22 ++++++------ src/Rules/Dependencies.hs | 6 ++-- src/Rules/Documentation.hs | 17 +++++---- src/Rules/Resources.hs | 7 ++-- src/Settings/Builders/Ar.hs | 1 + src/Settings/Builders/Gcc.hs | 27 +++++++------- src/Settings/Builders/Ghc.hs | 14 ++++---- src/Settings/Builders/GhcCabal.hs | 40 +++++++++++---------- src/Settings/Builders/Haddock.hs | 5 +-- src/Settings/Builders/Ld.hs | 12 +++---- src/Settings/TargetDirectory.hs | 6 ++-- src/Settings/User.hs | 7 +++- src/Settings/Util.hs | 74 +++++++++++++++------------------------ src/Settings/Ways.hs | 17 +++------ src/Util.hs | 18 +++++----- 27 files changed, 162 insertions(+), 193 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4238fb77e4db131ddb1cb938a76f0dbe2b03a798 From git at git.haskell.org Thu Oct 26 23:36:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename runGhc => runghc (e12516f) Message-ID: <20171026233603.3DE013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e12516f4af9047152c7faad88635787b33d6d602/ghc >--------------------------------------------------------------- commit e12516f4af9047152c7faad88635787b33d6d602 Author: Andrey Mokhov Date: Mon Jan 4 14:41:34 2016 +0000 Rename runGhc => runghc >--------------------------------------------------------------- e12516f4af9047152c7faad88635787b33d6d602 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index 1ea0e7f..75f4305 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -79,7 +79,7 @@ pretty = library "pretty" primitive = library "primitive" process = library "process" rts = topLevel "rts" -runGhc = utility "runGhc" +runGhc = utility "runghc" stm = library "stm" templateHaskell = library "template-haskell" terminfo = library "terminfo" From git at git.haskell.org Thu Oct 26 23:36:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop DepKeys, add DepId, clean up code. (49574e6) Message-ID: <20171026233603.762AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49574e62cd65023a3d4c6c145bbac86c16c73d69/ghc >--------------------------------------------------------------- commit 49574e62cd65023a3d4c6c145bbac86c16c73d69 Author: Andrey Mokhov Date: Fri Aug 21 16:29:01 2015 +0100 Drop DepKeys, add DepId, clean up code. >--------------------------------------------------------------- 49574e62cd65023a3d4c6c145bbac86c16c73d69 src/Oracles/PackageData.hs | 74 +++++++++++++++++++--------------------------- 1 file changed, 31 insertions(+), 43 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 4097ac1..c873601 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -8,7 +8,6 @@ module Oracles.PackageData ( import Base import Util import Data.List -import Data.Maybe import Control.Applicative import qualified Data.HashMap.Strict as Map @@ -22,6 +21,7 @@ import qualified Data.HashMap.Strict as Map -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] data PackageData = Version FilePath | PackageKey FilePath + | LibName FilePath | Synopsis FilePath | BuildGhciLib FilePath @@ -30,7 +30,7 @@ data PackageDataList = Modules FilePath | SrcDirs FilePath | IncludeDirs FilePath | Deps FilePath - | DepKeys FilePath + | DepIds FilePath | DepNames FilePath | CppArgs FilePath | HsArgs FilePath @@ -41,59 +41,47 @@ data PackageDataList = Modules FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) --- TODO: is this needed? askPackageData :: FilePath -> String -> Action String askPackageData path key = do let fullKey = replaceSeparators '_' $ path ++ "_" ++ key - pkgData = path -/- "package-data.mk" - value <- askOracle $ PackageDataKey (pkgData, fullKey) - return $ fromMaybe - (error $ "No key '" ++ key ++ "' in " ++ pkgData ++ ".") value + file = path -/- "package-data.mk" + maybeValue <- askOracle $ PackageDataKey (file, fullKey) + case maybeValue of + Nothing -> putError $ "No key '" ++ key ++ "' in " ++ file ++ "." + Just value -> return value pkgData :: PackageData -> Action String -pkgData packageData = do - let (key, path) = case packageData of - Version path -> ("VERSION" , path) - PackageKey path -> ("PACKAGE_KEY" , path) - Synopsis path -> ("SYNOPSIS" , path) - BuildGhciLib path -> ("BUILD_GHCI_LIB", path) - fullKey = replaceSeparators '_' $ path ++ "_" ++ key - pkgData = path -/- "package-data.mk" - res <- askOracle $ PackageDataKey (pkgData, fullKey) - return $ fromMaybe - (error $ "No key '" ++ key ++ "' in " ++ pkgData ++ ".") res +pkgData packageData = case packageData of + Version path -> askPackageData path "VERSION" + PackageKey path -> askPackageData path "PACKAGE_KEY" + LibName path -> askPackageData path "LIB_NAME" + Synopsis path -> askPackageData path "SYNOPSIS" + BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" pkgDataList :: PackageDataList -> Action [String] -pkgDataList packageData = do - let (key, path, defaultValue) = case packageData of - Modules path -> ("MODULES" , path, "" ) - HiddenModules path -> ("HIDDEN_MODULES" , path, "" ) - SrcDirs path -> ("HS_SRC_DIRS" , path, ".") - IncludeDirs path -> ("INCLUDE_DIRS" , path, ".") - Deps path -> ("DEPS" , path, "" ) - DepKeys path -> ("DEP_KEYS" , path, "" ) - DepNames path -> ("DEP_NAMES" , path, "" ) - CppArgs path -> ("CPP_OPTS" , path, "" ) - HsArgs path -> ("HC_OPTS" , path, "" ) - CcArgs path -> ("CC_OPTS" , path, "" ) - CSrcs path -> ("C_SRCS" , path, "" ) - DepIncludeDirs path -> ("DEP_INCLUDE_DIRS_SINGLE_QUOTED", path, "" ) - fullKey = replaceSeparators '_' $ path ++ "_" ++ key - pkgData = path -/- "package-data.mk" - unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') - res <- askOracle $ PackageDataKey (pkgData, fullKey) - return $ map unquote $ words $ case res of - Nothing -> error $ "No key '" ++ key ++ "' in " ++ pkgData ++ "." - Just "" -> defaultValue - Just value -> value +pkgDataList packageData = fmap (map unquote . words) $ case packageData of + Modules path -> askPackageData path "MODULES" + HiddenModules path -> askPackageData path "HIDDEN_MODULES" + SrcDirs path -> askPackageData path "HS_SRC_DIRS" + IncludeDirs path -> askPackageData path "INCLUDE_DIRS" + Deps path -> askPackageData path "DEPS" + DepIds path -> askPackageData path "DEP_IPIDS" + DepNames path -> askPackageData path "DEP_NAMES" + CppArgs path -> askPackageData path "CPP_OPTS" + HsArgs path -> askPackageData path "HC_OPTS" + CcArgs path -> askPackageData path "CC_OPTS" + CSrcs path -> askPackageData path "C_SRCS" + DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" + where + unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') -- Oracle for 'package-data.mk' files packageDataOracle :: Rules () packageDataOracle = do - pkgData <- newCache $ \file -> do + pkgDataContents <- newCache $ \file -> do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> - Map.lookup key <$> pkgData (unifyPath file) + _ <- addOracle $ \(PackageDataKey (file, key)) -> + Map.lookup key <$> pkgDataContents file return () From git at git.haskell.org Thu Oct 26 23:36:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to src/Rules/IntegerGmp.hs. (c4cbb3a) Message-ID: <20171026233606.DE68B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4cbb3a8691851628159ae8f7058efed9f5f8a0a/ghc >--------------------------------------------------------------- commit c4cbb3a8691851628159ae8f7058efed9f5f8a0a Author: Andrey Mokhov Date: Mon Jan 4 16:25:47 2016 +0000 Fix path to src/Rules/IntegerGmp.hs. >--------------------------------------------------------------- c4cbb3a8691851628159ae8f7058efed9f5f8a0a src/Rules/IntegerGmp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index f927102..9bbf482 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -50,7 +50,7 @@ configureArguments = do integerGmpRules :: Rules () integerGmpRules = do integerGmpLibrary %> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules" -/- "integerGmp.hs"] + when trackBuildSystem $ need [sourcePath -/- "Rules/IntegerGmp.hs"] -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] From git at git.haskell.org Thu Oct 26 23:36:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve handling of generated dependencies, clean up code. (87568c1) Message-ID: <20171026233610.A6A1D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/87568c1d948f9c588419b48146bec38a909eb99b/ghc >--------------------------------------------------------------- commit 87568c1d948f9c588419b48146bec38a909eb99b Author: Andrey Mokhov Date: Mon Jan 4 17:26:20 2016 +0000 Improve handling of generated dependencies, clean up code. >--------------------------------------------------------------- 87568c1d948f9c588419b48146bec38a909eb99b src/Rules/Data.hs | 15 ++++++--- src/Rules/Dependencies.hs | 6 +--- src/Rules/Generate.hs | 81 ++++++++++++++++++++++++----------------------- src/Rules/Library.hs | 5 ++- 4 files changed, 56 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 87568c1d948f9c588419b48146bec38a909eb99b From git at git.haskell.org Thu Oct 26 23:36:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove parallel, stm, random, primitive, vector and dph from Stage1 packages, drop integerGmp2 support. (228da6f) Message-ID: <20171026233607.26B113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/228da6fe168616b0aeca8d462eab345cef5b7e48/ghc >--------------------------------------------------------------- commit 228da6fe168616b0aeca8d462eab345cef5b7e48 Author: Andrey Mokhov Date: Fri Aug 21 16:30:17 2015 +0100 Remove parallel, stm, random, primitive, vector and dph from Stage1 packages, drop integerGmp2 support. >--------------------------------------------------------------- 228da6fe168616b0aeca8d462eab345cef5b7e48 src/Settings/Packages.hs | 11 ++++------- 1 file changed, 4 insertions(+), 7 deletions(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 369879c..5820e0c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -29,12 +29,13 @@ packagesStage0 = mconcat [ append [binPackageDb, binary, cabal, compiler, hoopl, hpc, transformers] , notWindowsHost ? notTargetOs "ios" ? append [terminfo] ] +-- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory - , filepath, ghcPrim, haskeline, integerLibrary, parallel - , pretty, primitive, process, stm, templateHaskell, time ] + , filepath, ghcPrim, haskeline, integerLibrary, pretty, process + , templateHaskell, time ] , windowsHost ? append [win32] , notWindowsHost ? append [unix] , buildHaddock ? append [xhtml] ] @@ -43,9 +44,5 @@ knownPackages :: [Package] knownPackages = defaultKnownPackages ++ userKnownPackages -- Note: this is slow but we keep it simple as there not too many packages (30) --- We handle integerLibrary in a special way, because packages integerGmp and --- integerGmp2 have the same package name -- we return the user-selected one. findKnownPackage :: PackageName -> Maybe Package -findKnownPackage name - | name == pkgName integerLibrary = Just integerLibrary - | otherwise = find (\pkg -> pkgName pkg == name) knownPackages +findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Thu Oct 26 23:36:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add PartialTarget, handle GHC.Prim module in a special way. (aabc5a6) Message-ID: <20171026233610.DC1B43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aabc5a6ef5968dd14eb67c5cce6d50257c1288ae/ghc >--------------------------------------------------------------- commit aabc5a6ef5968dd14eb67c5cce6d50257c1288ae Author: Andrey Mokhov Date: Fri Aug 21 22:14:48 2015 +0100 Add PartialTarget, handle GHC.Prim module in a special way. >--------------------------------------------------------------- aabc5a6ef5968dd14eb67c5cce6d50257c1288ae src/Expression.hs | 47 ++++++++++++++++++++-------------- src/Oracles/ArgsHash.hs | 2 +- src/Rules.hs | 19 +++++++------- src/Rules/Actions.hs | 11 ++++---- src/Rules/Cabal.hs | 4 +-- src/Rules/Compile.hs | 11 +++----- src/Rules/Data.hs | 14 +++++------ src/Rules/Dependencies.hs | 12 ++++----- src/Rules/Documentation.hs | 14 +++++------ src/Rules/Library.hs | 39 +++++++++++++++------------- src/Rules/Package.hs | 3 ++- src/Target.hs | 63 ++++++++++++++++------------------------------ 12 files changed, 112 insertions(+), 127 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 aabc5a6ef5968dd14eb67c5cce6d50257c1288ae From git at git.haskell.org Thu Oct 26 23:36:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Travis support (64da998) Message-ID: <20171026233614.85FDD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64da99895a240d9af031ac9357b0bedcb215ac02/ghc >--------------------------------------------------------------- commit 64da99895a240d9af031ac9357b0bedcb215ac02 Author: David Luposchainsky Date: Mon Jan 4 18:20:23 2016 +0100 Add Travis support >--------------------------------------------------------------- 64da99895a240d9af031ac9357b0bedcb215ac02 .travis.yml | 32 ++++++++++++++++++++++++++++++++ .travis/install-cabal-happy-alex.sh | 18 ++++++++++++++++++ .travis/install-ghc-shake.sh | 16 ++++++++++++++++ .travis/install-ghc.sh | 15 +++++++++++++++ .travis/print-env.sh | 9 +++++++++ .travis/run-ghc-shake.sh | 9 +++++++++ README.md | 2 ++ 7 files changed, 101 insertions(+) diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..5e169fa --- /dev/null +++ b/.travis.yml @@ -0,0 +1,32 @@ +sudo: false + +matrix: + include: + - env: CABALVER=1.22 GHCVER=7.10.3 + addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.3,zlib1g-dev,terminfo-dev], sources: [hvr-ghc]}} + +before_install: + + - PATH="$HOME/.cabal/bin:$PATH" + - PATH="/opt/ghc/$GHCVER/bin:$PATH" + - PATH="/opt/cabal/$CABALVER/bin:$PATH" + - export PATH + + - .travis/print-env.sh + +install: + - .travis/install-cabal-happy-alex.sh + - .travis/install-ghc.sh + - .travis/install-ghc-shake.sh + +script: + - .travis/run-ghc-shake.sh + +cache: + directories: + - $HOME/.cabal + # - ghc/shake-build/.cabal-sandbox + # - ghc/shake-build/cabal.sandbox.config + +# before_cache: +# - rm -rf ghc/shake-build diff --git a/.travis/install-cabal-happy-alex.sh b/.travis/install-cabal-happy-alex.sh new file mode 100755 index 0000000..93df460 --- /dev/null +++ b/.travis/install-cabal-happy-alex.sh @@ -0,0 +1,18 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[32m" # Green +RESET="\e[m" + +echo -e "${COLOR}GHC version:${RESET}" +ghc --version + +echo -e "${COLOR}Cabal version:${RESET}" +cabal --version + +echo -e "${COLOR}Update Cabal${RESET}" +cabal update + +echo -e "${COLOR}Install Alex+Happy${RESET}" +cabal install alex happy diff --git a/.travis/install-ghc-shake.sh b/.travis/install-ghc-shake.sh new file mode 100755 index 0000000..2dc0392 --- /dev/null +++ b/.travis/install-ghc-shake.sh @@ -0,0 +1,16 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[31m" # Red, because this file is serious business +RESET="\e[m" + +echo -e "${COLOR}Brutally hacking GHC-Shake to its proper location${RESET}" +SHAKEDIR="ghc/shake-build" +mkdir -p "$SHAKEDIR" +mv .git "$SHAKEDIR/" +( cd "$SHAKEDIR" && git reset --hard HEAD ) + +echo -e "${COLOR}Installing deps into sandbox${RESET}" +( cd "$SHAKEDIR" && cabal sandbox init ) +( cd "$SHAKEDIR" && cabal install --only-dependencies . ) diff --git a/.travis/install-ghc.sh b/.travis/install-ghc.sh new file mode 100755 index 0000000..126cbe2 --- /dev/null +++ b/.travis/install-ghc.sh @@ -0,0 +1,15 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[34m" # Blue +RESET="\e[m" + +echo -e "${COLOR}Clone GHC source${RESET}" +git clone git://git.haskell.org/ghc + +echo -e "${COLOR}Initialize GHC submodules${RESET}" +( cd ghc && git submodule update --init ) + +echo -e "${COLOR}GHC boot/configure${RESET}" +( cd ghc && ./boot && ./configure) diff --git a/.travis/print-env.sh b/.travis/print-env.sh new file mode 100755 index 0000000..c09c11f --- /dev/null +++ b/.travis/print-env.sh @@ -0,0 +1,9 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[32m" # Green +RESET="\e[m" + +echo -e "${COLOR}Environment:${RESET}" +env diff --git a/.travis/run-ghc-shake.sh b/.travis/run-ghc-shake.sh new file mode 100755 index 0000000..7b867b7 --- /dev/null +++ b/.travis/run-ghc-shake.sh @@ -0,0 +1,9 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[32m" # Green +RESET="\e[m" + +echo -e "${COLOR}Running Shake build system${RESET}" +( cd ghc && ./shake-build/build.cabal.sh ) diff --git a/README.md b/README.md index f26cc49..43b74be 100644 --- a/README.md +++ b/README.md @@ -1,6 +1,8 @@ Shaking up GHC ============== +[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) + As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC][ghc] build system based on standard `make` into a new and (hopefully) better one based on From git at git.haskell.org Thu Oct 26 23:36:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Switches.hs to Predicates.hs. (47764c0) Message-ID: <20171026233614.B08D63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47764c0eaedab75e54c0209ef117ddb0280d05b2/ghc >--------------------------------------------------------------- commit 47764c0eaedab75e54c0209ef117ddb0280d05b2 Author: Andrey Mokhov Date: Fri Aug 21 22:23:05 2015 +0100 Rename Switches.hs to Predicates.hs. >--------------------------------------------------------------- 47764c0eaedab75e54c0209ef117ddb0280d05b2 src/{Switches.hs => Predicates.hs} | 2 +- src/Rules/Data.hs | 2 +- src/Rules/Library.hs | 2 +- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Gcc.hs | 2 +- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Builders/Ld.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/User.hs | 2 +- src/Settings/Util.hs | 2 +- src/Settings/Ways.hs | 2 +- 14 files changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Switches.hs b/src/Predicates.hs similarity index 98% rename from src/Switches.hs rename to src/Predicates.hs index c30a33f..0dfa8db 100644 --- a/src/Switches.hs +++ b/src/Predicates.hs @@ -1,4 +1,4 @@ -module Switches ( +module Predicates ( stage, package, builder, stagedBuilder, file, way, stage0, stage1, stage2, notStage, notStage0, registerPackage, splitObjects diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index e64938f..d481a67 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -5,8 +5,8 @@ import Util import Target (PartialTarget (..), fullTarget) import Package import Builder -import Switches (registerPackage) import Expression +import Predicates (registerPackage) import Oracles.PackageDeps import Settings.Packages import Settings.TargetDirectory diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 4f5e787..4ff15c3 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -6,8 +6,8 @@ import Util import Target (PartialTarget (..), fullTarget) import Builder import Package -import Switches (splitObjects) import Expression +import Predicates (splitObjects) import Oracles.PackageData import Settings.Util import Settings.TargetDirectory diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index ec8b6ac..4bde3f8 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,8 +1,8 @@ module Settings.Builders.Ar (arArgs, arPersistentArgsCount) where import Builder -import Switches (builder) import Expression +import Predicates (builder) import Settings.Util arArgs :: Args diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index 748e544..20867f7 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -3,8 +3,8 @@ module Settings.Builders.Gcc (gccArgs, gccMArgs) where import Base import Util import Builder -import Switches (stagedBuilder) import Expression +import Predicates (stagedBuilder) import Oracles.PackageData import Settings.Util diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index af20c7a..e48be86 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -4,8 +4,8 @@ import Way import Util import Stage import Builder -import Switches (stagedBuilder, splitObjects, stage0) import Expression +import Predicates (stagedBuilder, splitObjects, stage0) import Oracles.Flag import Oracles.PackageData import Settings.Util diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 623110b..4862e9f 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -9,8 +9,8 @@ import Util import Stage import Builder import Package -import Switches import Expression +import Predicates import Oracles.Flag import Oracles.Setting import Settings.User diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index b2bab83..64981c6 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -2,8 +2,8 @@ module Settings.Builders.GhcPkg (ghcPkgArgs) where import Util import Builder -import Switches import Expression +import Predicates import Settings.Util import Settings.Builders.GhcCabal diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 94a1669..19c1979 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -4,8 +4,8 @@ import Base import Util import Builder import Package -import Switches (builder, package, stage1) import Expression +import Predicates (builder, package, stage1) import Oracles.PackageData import Settings.Util import Settings.Packages diff --git a/src/Settings/Builders/Ld.hs b/src/Settings/Builders/Ld.hs index e21a262..6a17ca7 100644 --- a/src/Settings/Builders/Ld.hs +++ b/src/Settings/Builders/Ld.hs @@ -1,8 +1,8 @@ module Settings.Builders.Ld (ldArgs) where import Builder -import Switches (builder) import Expression +import Predicates (builder) import Oracles.Setting import Settings.Util diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 5820e0c..b84bb5b 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -4,8 +4,8 @@ module Settings.Packages ( ) where import Package -import Switches import Expression +import Predicates import Oracles.Setting import Settings.User import Settings.Default diff --git a/src/Settings/User.hs b/src/Settings/User.hs index e67afc3..cdf2840 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -7,8 +7,8 @@ module Settings.User ( import Stage import Package -import Switches import Expression +import Predicates import Settings.Default -- No user-specific settings by default diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 81b7b69..1ab4308 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -13,8 +13,8 @@ import Util import Stage import Builder import Package -import Switches import Expression +import Predicates import Oracles.Flag import Oracles.Setting import Oracles.PackageData diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index d6e541e..183068a 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -2,8 +2,8 @@ module Settings.Ways (getWays, getRtsWays) where import Way import Stage -import Switches import Expression +import Predicates import Oracles.Flag import Settings.User From git at git.haskell.org Thu Oct 26 23:36:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #93 from quchen/travis-ci (45c731c) Message-ID: <20171026233618.0A1033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45c731c4105f0eb7daf2975cb9073f6879587042/ghc >--------------------------------------------------------------- commit 45c731c4105f0eb7daf2975cb9073f6879587042 Merge: 87568c1 64da998 Author: Andrey Mokhov Date: Mon Jan 4 18:51:30 2016 +0000 Merge pull request #93 from quchen/travis-ci Travis CI using dirty tricks >--------------------------------------------------------------- 45c731c4105f0eb7daf2975cb9073f6879587042 .travis.yml | 32 ++++++++++++++++++++++++++++++++ .travis/install-cabal-happy-alex.sh | 18 ++++++++++++++++++ .travis/install-ghc-shake.sh | 16 ++++++++++++++++ .travis/install-ghc.sh | 15 +++++++++++++++ .travis/print-env.sh | 9 +++++++++ .travis/run-ghc-shake.sh | 9 +++++++++ README.md | 2 ++ 7 files changed, 101 insertions(+) From git at git.haskell.org Thu Oct 26 23:36:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix infinite loop bug in chunksOfSize. (1d27a44) Message-ID: <20171026233618.2A77D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1d27a444cc91ce912bbff440507170cc14729961/ghc >--------------------------------------------------------------- commit 1d27a444cc91ce912bbff440507170cc14729961 Author: Andrey Mokhov Date: Fri Aug 21 23:39:06 2015 +0100 Fix infinite loop bug in chunksOfSize. >--------------------------------------------------------------- 1d27a444cc91ce912bbff440507170cc14729961 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index b39fc6c..51b5ccb 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -49,7 +49,7 @@ chunksOfSize size strings = reverse chunk : chunksOfSize size rest (chunk, rest) = go [] 0 strings go res _ [] = (res, []) go res chunkSize (s:ss) = - if newSize > size then (chunk, s:ss) else go (s:res) newSize ss + if newSize > size then (res, s:ss) else go (s:res) newSize ss where newSize = chunkSize + length s From git at git.haskell.org Thu Oct 26 23:36:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Continue refactoring of generated dependencies. (64f9350) Message-ID: <20171026233621.875C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64f93509197b23722bf14928ce50c5a3930b4d27/ghc >--------------------------------------------------------------- commit 64f93509197b23722bf14928ce50c5a3930b4d27 Author: Andrey Mokhov Date: Mon Jan 4 19:59:27 2016 +0000 Continue refactoring of generated dependencies. >--------------------------------------------------------------- 64f93509197b23722bf14928ce50c5a3930b4d27 src/Rules/Dependencies.hs | 4 +-- src/Rules/Generate.hs | 87 ++++++++++++++++++++++++++--------------------- 2 files changed, 50 insertions(+), 41 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 5b51c1d..b0dd474 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -18,13 +18,13 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do let srcFile = dropBuild . dropExtension $ out - orderOnly $ generatedDependencies stage pkg + orderOnly $ generatedDependencies stage need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - orderOnly $ generatedDependencies stage pkg + orderOnly $ generatedDependencies stage need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 21c197b..140c978 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -16,6 +16,7 @@ import Oracles.ModuleFiles import Rules.Actions import Rules.Resources (Resources) import Settings +import Settings.Builders.DeriveConstants primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -26,47 +27,55 @@ primopsTxt stage = targetPath stage compiler -/- "build/primops.txt" platformH :: Stage -> FilePath platformH stage = targetPath stage compiler -/- "ghc_boot_platform.h" -derivedConstantsPath :: FilePath -derivedConstantsPath = "includes/dist-derivedconstants/header" - -defaultGeneratedDependencies :: [FilePath] -defaultGeneratedDependencies = - [ "includes/ghcautoconf.h" - , "includes/ghcplatform.h" - , derivedConstantsPath -/- "DerivedConstants.h" - , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" - , targetPath Stage1 rts -/- "build/ffi.h" - , targetPath Stage1 rts -/- "build/ffitarget.h" ] +includesDependencies :: [FilePath] +includesDependencies = ("includes" -/-) <$> + [ "ghcautoconf.h" + , "ghcplatform.h" + , "ghcversion.h" ] + +derivedConstantsDependencies :: [FilePath] +derivedConstantsDependencies = (derivedConstantsPath -/-) <$> [] + -- [ "DerivedConstants.h" + -- , "GHCConstantsHaskellType.hs" + -- , "GHCConstantsHaskellWrappers.hs" + -- , "GHCConstantsHaskellExports.hs" ] + +libffiDependencies :: [FilePath] +libffiDependencies = (targetPath Stage1 rts -/-) <$> + [ "build/ffi.h" + , "build/ffitarget.h" ] + +defaultDependencies :: [FilePath] +defaultDependencies = + includesDependencies ++ derivedConstantsDependencies ++ libffiDependencies + +compilerDependencies :: Stage -> [FilePath] +compilerDependencies stage = + [ platformH stage ] + ++ + fmap ((targetPath stage compiler -/- "build") -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] -- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? -generatedDependencies :: Stage -> Package -> [FilePath] -generatedDependencies stage pkg = - defaultGeneratedDependencies ++ extraGeneratedDependencies - where - extraGeneratedDependencies - | pkg == compiler = let buildPath = targetPath stage compiler -/- "build" - in - [ platformH stage ] - ++ - fmap (buildPath -/-) - [ "primop-vector-uniques.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" - , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] - | otherwise = [] +-- TODO: improve +generatedDependencies :: Stage -> [FilePath] +generatedDependencies stage + | stage == Stage1 = defaultDependencies ++ compilerDependencies stage + | otherwise = [] -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] From git at git.haskell.org Thu Oct 26 23:36:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement interestingInfo for Haddock. (c6b59ef) Message-ID: <20171026233621.9C96F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6b59ef5c98617955b4c4c98742cc99b68371fd6/ghc >--------------------------------------------------------------- commit c6b59ef5c98617955b4c4c98742cc99b68371fd6 Author: Andrey Mokhov Date: Fri Aug 21 23:39:40 2015 +0100 Implement interestingInfo for Haddock. >--------------------------------------------------------------- c6b59ef5c98617955b4c4c98742cc99b68371fd6 src/Rules/Actions.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d73c6a7..e58669a 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -50,6 +50,7 @@ interestingInfo builder ss = case builder of Ghc _ -> prefixAndSuffix 0 4 ss GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss + Haddock -> prefixAndSuffix 1 0 ss GhcCabal -> prefixAndSuffix 3 0 ss _ -> ss where From git at git.haskell.org Thu Oct 26 23:36:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix libCffi name on Windows (fix #89). (19310e7) Message-ID: <20171026233625.65E913A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/19310e7fbaf16190f0e206564f45f76cb6e20b61/ghc >--------------------------------------------------------------- commit 19310e7fbaf16190f0e206564f45f76cb6e20b61 Author: Andrey Mokhov Date: Mon Jan 4 20:09:33 2016 +0000 Fix libCffi name on Windows (fix #89). >--------------------------------------------------------------- 19310e7fbaf16190f0e206564f45f76cb6e20b61 src/Rules/Copy.hs | 4 +++- src/Settings/Packages/Rts.hs | 14 ++++++++++---- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index bcd1f1e..b1f9760 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -6,6 +6,7 @@ import GHC import Rules.Actions import Rules.Generate import Rules.Libffi +import Settings.Packages.Rts import Settings.TargetDirectory installTargets :: [FilePath] @@ -23,7 +24,8 @@ copyRules = do ++ "(found: " ++ show ffiHPaths ++ ")." copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih - copyFile libffiLibrary (targetPath Stage1 rts -/- "build" -/- "libCffi.a") + libffiName <- rtsLibffiLibraryName + copyFile libffiLibrary (targetPath Stage1 rts -/- "build/lib" ++ libffiName <.> "a") "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 56b0cf8..421d7f7 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,4 +1,6 @@ -module Settings.Packages.Rts (rtsPackageArgs, rtsConfIn, rtsConf) where +module Settings.Packages.Rts ( + rtsPackageArgs, rtsConfIn, rtsConf, rtsLibffiLibraryName + ) where import Base import Expression @@ -15,6 +17,11 @@ rtsConfIn = pkgPath rts -/- "package.conf.in" rtsConf :: FilePath rtsConf = targetPath Stage1 rts -/- "package.conf.inplace" +rtsLibffiLibraryName :: Action FilePath +rtsLibffiLibraryName = do + windows <- windowsHost + return $ if windows then "Cffi-6" else "Cffi" + rtsPackageArgs :: Args rtsPackageArgs = package rts ? do let yesNo = lift . fmap (\x -> if x then "YES" else "NO") @@ -36,8 +43,7 @@ rtsPackageArgs = package rts ? do way <- getWay path <- getTargetPath top <- getSetting GhcSourcePath - windows <- lift $ windowsHost - let libffiName = if windows then "ffi-6" else "ffi" + libffiName <- lift $ rtsLibffiLibraryName mconcat [ builderGcc ? mconcat [ arg "-Irts" @@ -74,7 +80,7 @@ rtsPackageArgs = package rts ? do [ arg ("-DTOP=" ++ quote top) , arg "-DFFI_INCLUDE_DIR=" , arg "-DFFI_LIB_DIR=" - , arg $ "-DFFI_LIB=" ++ quote ("C" ++ libffiName) ] ] + , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] -- #----------------------------------------------------------------------------- -- # Use system provided libffi From git at git.haskell.org Thu Oct 26 23:36:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Haddock arguments. (bf86f0e) Message-ID: <20171026233625.664E13A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf86f0ec66186df924ba0e173ba606fe39ddbf1b/ghc >--------------------------------------------------------------- commit bf86f0ec66186df924ba0e173ba606fe39ddbf1b Author: Andrey Mokhov Date: Sat Aug 22 00:26:44 2015 +0100 Fix Haddock arguments. >--------------------------------------------------------------- bf86f0ec66186df924ba0e173ba606fe39ddbf1b src/Settings/Builders/Haddock.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 19c1979..0e839ce 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -26,6 +26,7 @@ haddockArgs = builder Haddock ? do ghcOpts <- fromDiffExpr commonGhcArgs mconcat [ arg $ "--odir=" ++ takeDirectory file + , arg "--verbosity=0" , arg "--no-tmp-comp-dir" , arg $ "--dump-interface=" ++ file , arg "--html" @@ -39,12 +40,14 @@ haddockArgs = builder Haddock ? do | (dep, depName) <- zip deps depNames , Just depPkg <- [findKnownPackage depName] ] , append [ "--optghc=" ++ opt | opt <- ghcOpts ] - , arg "--source-module=src/%{MODULE/./-}.html" - , arg "--source-entity=src/%{MODULE/./-}.html\\#%{NAME}" + , specified HsColour ? + arg "--source-module=src/%{MODULE/./-}.html" + , specified HsColour ? + arg "--source-entity=src/%{MODULE/./-}.html\\#%{NAME}" , customPackageArgs , append srcs , arg "+RTS" - , arg $ "-t" ++ file <.> "t" + , arg $ "-t" ++ path "haddock.t" , arg "--machine-readable" ] customPackageArgs :: Args From git at git.haskell.org Thu Oct 26 23:36:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add runghcid.bat. (14c35b5) Message-ID: <20171026233629.20E703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14c35b529b90f9b5578c086a603c4c496c7b5c07/ghc >--------------------------------------------------------------- commit 14c35b529b90f9b5578c086a603c4c496c7b5c07 Author: Andrey Mokhov Date: Sat Aug 22 17:59:18 2015 +0100 Add runghcid.bat. >--------------------------------------------------------------- 14c35b529b90f9b5578c086a603c4c496c7b5c07 runghcid.bat | 1 + 1 file changed, 1 insertion(+) diff --git a/runghcid.bat b/runghcid.bat new file mode 100644 index 0000000..f2f8ddc --- /dev/null +++ b/runghcid.bat @@ -0,0 +1 @@ +ghcid --height=8 --topmost "--command=ghci -isrc -Wall src/Main.hs" From git at git.haskell.org Thu Oct 26 23:36:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add topDirectory function instead of less reliable GhcSourcePath. (5bc7a0a) Message-ID: <20171026233629.29D3E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5bc7a0ae097f038f3b04227b214a985a0c60cfbc/ghc >--------------------------------------------------------------- commit 5bc7a0ae097f038f3b04227b214a985a0c60cfbc Author: Andrey Mokhov Date: Tue Jan 5 00:53:11 2016 +0000 Add topDirectory function instead of less reliable GhcSourcePath. >--------------------------------------------------------------- 5bc7a0ae097f038f3b04227b214a985a0c60cfbc src/Builder.hs | 19 ------------------- src/Oracles/WindowsRoot.hs | 29 ++++++++++++++++++++++++++++- src/Rules/Actions.hs | 4 ++-- src/Rules/Libffi.hs | 4 ++-- src/Rules/Wrappers/Ghc.hs | 4 ++-- src/Rules/Wrappers/GhcPkg.hs | 4 ++-- src/Settings.hs | 5 ++++- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- 10 files changed, 44 insertions(+), 33 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 5bc7a0ae097f038f3b04227b214a985a0c60cfbc From git at git.haskell.org Thu Oct 26 23:36:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop ghcPwd package, we no longer build it. (9050f37) Message-ID: <20171026233632.8D1533A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9050f373671103cd80336e19880a7c14fd7920ab/ghc >--------------------------------------------------------------- commit 9050f373671103cd80336e19880a7c14fd7920ab Author: Andrey Mokhov Date: Tue Jan 5 00:56:31 2016 +0000 Drop ghcPwd package, we no longer build it. >--------------------------------------------------------------- 9050f373671103cd80336e19880a7c14fd7920ab src/GHC.hs | 17 ++++++++--------- src/Settings/Packages.hs | 2 +- 2 files changed, 9 insertions(+), 10 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 75f4305..d4d5511 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -2,8 +2,8 @@ module GHC ( array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, - ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, + haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, @@ -25,16 +25,16 @@ defaultKnownPackages = [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes , deepseq, deriveConstants, directory, dllSplit, filepath, genapply , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim - , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin - , integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel - , pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo - , time, transformers, unix, win32, xhtml ] + , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp + , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty + , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time + , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, - ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, + haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package @@ -60,7 +60,6 @@ ghcCabal = utility "ghc-cabal" ghci = library "ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" -ghcPwd = utility "ghc-pwd" ghcTags = utility "ghctags" haddock = utility "haddock" haskeline = library "haskeline" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 10ed9e1..dba4054 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -31,7 +31,7 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq - , directory, filepath, ghci, ghcPrim, ghcPwd, haskeline, hpcBin + , directory, filepath, ghci, ghcPrim, haskeline, hpcBin , integerLibrary, mkUserGuidePart, pretty, process, rts, runGhc , time ] , windowsHost ? append [win32] From git at git.haskell.org Thu Oct 26 23:36:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use -Wall when compiling the build system. (134cac9) Message-ID: <20171026233632.855543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/134cac9ab3a450be48cadce39a0faac00be227fb/ghc >--------------------------------------------------------------- commit 134cac9ab3a450be48cadce39a0faac00be227fb Author: Andrey Mokhov Date: Sat Aug 22 17:59:54 2015 +0100 Use -Wall when compiling the build system. >--------------------------------------------------------------- 134cac9ab3a450be48cadce39a0faac00be227fb build.bat | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.bat b/build.bat index b6b9a82..b45bdde 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,2 @@ @mkdir _shake 2> nul - at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:36:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports. (c125896) Message-ID: <20171026233636.C7A1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1258966f7b34115402c8d4f2243cc2e75cb1deb/ghc >--------------------------------------------------------------- commit c1258966f7b34115402c8d4f2243cc2e75cb1deb Author: Andrey Mokhov Date: Sat Aug 22 18:00:14 2015 +0100 Refactor imports. >--------------------------------------------------------------- c1258966f7b34115402c8d4f2243cc2e75cb1deb src/Base.hs | 15 +++++++-------- src/Builder.hs | 11 +++-------- src/Expression.hs | 20 +++++++++++--------- src/Main.hs | 10 ++++++---- src/Oracles/Base.hs | 17 +++++++++-------- src/Oracles/Dependencies.hs | 2 -- src/Oracles/Flag.hs | 3 --- src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 3 --- src/Oracles/Setting.hs | 1 - src/Oracles/WindowsRoot.hs | 1 - src/Package.hs | 8 +++----- src/Predicates.hs | 6 +----- src/Rules.hs | 19 +++++-------------- src/Rules/Cabal.hs | 1 - src/Rules/Config.hs | 2 -- src/Rules/Data.hs | 7 ++----- src/Rules/Dependencies.hs | 3 +-- src/Rules/Documentation.hs | 1 - src/Rules/Library.hs | 20 +++++++------------- src/Rules/Oracles.hs | 11 ++++------- src/Rules/Package.hs | 8 ++++---- src/Rules/Resources.hs | 6 ++---- src/Settings/Builders/Gcc.hs | 11 +++++------ src/Settings/Builders/Ghc.hs | 9 +++------ src/Settings/Builders/Haddock.hs | 1 - src/Settings/Packages.hs | 1 - src/Settings/Util.hs | 4 +--- src/Stage.hs | 10 ++++------ src/Target.hs | 12 ++++++------ src/Util.hs | 37 +++++++++++++++++++++---------------- src/Way.hs | 14 +++++--------- 32 files changed, 110 insertions(+), 165 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c1258966f7b34115402c8d4f2243cc2e75cb1deb From git at git.haskell.org Thu Oct 26 23:36:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix a loop in generated dependencies. (e651350) Message-ID: <20171026233636.D7B3E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e6513507c7e75050ba93724d8d7e79ecf6adf146/ghc >--------------------------------------------------------------- commit e6513507c7e75050ba93724d8d7e79ecf6adf146 Author: Andrey Mokhov Date: Tue Jan 5 01:26:02 2016 +0000 Fix a loop in generated dependencies. >--------------------------------------------------------------- e6513507c7e75050ba93724d8d7e79ecf6adf146 src/Rules/Dependencies.hs | 4 ++-- src/Rules/Generate.hs | 31 ++++++++++++++++++------------- src/Settings/Builders/DeriveConstants.hs | 2 +- 3 files changed, 21 insertions(+), 16 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index b0dd474..5b51c1d 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -18,13 +18,13 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do let srcFile = dropBuild . dropExtension $ out - orderOnly $ generatedDependencies stage + orderOnly $ generatedDependencies stage pkg need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - orderOnly $ generatedDependencies stage + orderOnly $ generatedDependencies stage pkg need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 140c978..13d5806 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -33,21 +33,20 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -derivedConstantsDependencies :: [FilePath] -derivedConstantsDependencies = (derivedConstantsPath -/-) <$> [] - -- [ "DerivedConstants.h" - -- , "GHCConstantsHaskellType.hs" - -- , "GHCConstantsHaskellWrappers.hs" - -- , "GHCConstantsHaskellExports.hs" ] - libffiDependencies :: [FilePath] libffiDependencies = (targetPath Stage1 rts -/-) <$> [ "build/ffi.h" , "build/ffitarget.h" ] defaultDependencies :: [FilePath] -defaultDependencies = - includesDependencies ++ derivedConstantsDependencies ++ libffiDependencies +defaultDependencies = includesDependencies ++ libffiDependencies + +derivedConstantsDependencies :: [FilePath] +derivedConstantsDependencies = (derivedConstantsPath -/-) <$> + [ "DerivedConstants.h" + , "GHCConstantsHaskellType.hs" + , "GHCConstantsHaskellWrappers.hs" + , "GHCConstantsHaskellExports.hs" ] compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = @@ -69,12 +68,18 @@ compilerDependencies stage = , "primop-vector-tys-exports.hs-incl" , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] + ++ + if stage == Stage0 + then defaultDependencies ++ derivedConstantsDependencies + else [] + -- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? --- TODO: improve -generatedDependencies :: Stage -> [FilePath] -generatedDependencies stage - | stage == Stage1 = defaultDependencies ++ compilerDependencies stage +generatedDependencies :: Stage -> Package -> [FilePath] +generatedDependencies stage pkg + | pkg == compiler = compilerDependencies stage + | stage == Stage0 = defaultDependencies + | stage == Stage1 = derivedConstantsDependencies | otherwise = [] -- The following generators and corresponding source extensions are supported: diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 65c6c53..6f4828a 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -33,7 +33,7 @@ deriveConstantsBuilderArgs = builder DeriveConstants ? do includeCcArgs :: Args includeCcArgs = do - confCcArgs <- lift . settingList $ ConfCcArgs Stage1 + confCcArgs <- getSettingList $ ConfCcArgs Stage1 mconcat [ cArgs , cWarnings From git at git.haskell.org Thu Oct 26 23:36:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Another tweak of generated dependencies. (ba41ec6) Message-ID: <20171026233640.922593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba41ec6a9b2db3708b1076fef2c4391d4887875d/ghc >--------------------------------------------------------------- commit ba41ec6a9b2db3708b1076fef2c4391d4887875d Author: Andrey Mokhov Date: Tue Jan 5 01:54:50 2016 +0000 Another tweak of generated dependencies. >--------------------------------------------------------------- ba41ec6a9b2db3708b1076fef2c4391d4887875d src/Rules/Generate.hs | 43 ++++++++++++++++++------------------------- 1 file changed, 18 insertions(+), 25 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 13d5806..6a4270b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -51,35 +51,28 @@ derivedConstantsDependencies = (derivedConstantsPath -/-) <$> compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = [ platformH stage ] - ++ - fmap ((targetPath stage compiler -/- "build") -/-) - [ "primop-vector-uniques.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" - , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] - ++ - if stage == Stage0 - then defaultDependencies ++ derivedConstantsDependencies - else [] - - --- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? + ++ defaultDependencies ++ derivedConstantsDependencies + ++ fmap ((targetPath stage compiler -/- "build") -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] + generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | stage == Stage0 = defaultDependencies - | stage == Stage1 = derivedConstantsDependencies | otherwise = [] -- The following generators and corresponding source extensions are supported: From git at git.haskell.org Thu Oct 26 23:36:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Oracles. (d4a438f) Message-ID: <20171026233640.BE54D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf/ghc >--------------------------------------------------------------- commit d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf Author: Andrey Mokhov Date: Sat Aug 22 18:47:04 2015 +0100 Refactor Oracles. >--------------------------------------------------------------- d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf src/Builder.hs | 7 +++---- src/Oracles.hs | 17 +++++++++++++++++ src/Oracles/ArgsHash.hs | 4 ++-- src/Oracles/{Base.hs => Config.hs} | 9 +-------- src/Oracles/{ => Config}/Flag.hs | 8 +++++--- src/Oracles/{ => Config}/Setting.hs | 5 +++-- src/Oracles/Dependencies.hs | 1 - src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 3 ++- src/Predicates.hs | 3 +-- src/Rules/Actions.hs | 2 +- src/Rules/Oracles.hs | 19 +++++++------------ src/Settings/Builders/Ghc.hs | 3 +-- src/Settings/Builders/GhcCabal.hs | 3 +-- src/Settings/Builders/Ld.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/Util.hs | 4 +--- src/Settings/Ways.hs | 2 +- src/Util.hs | 2 ++ src/Way.hs | 2 +- 20 files changed, 51 insertions(+), 48 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 d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf From git at git.haskell.org Thu Oct 26 23:36:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds derivedConstantsDependencies for rts (2565fc3) Message-ID: <20171026233644.7143A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2565fc354a241ff9f6137c5202949a6f8f46bff9/ghc >--------------------------------------------------------------- commit 2565fc354a241ff9f6137c5202949a6f8f46bff9 Author: Moritz Angermann Date: Tue Jan 5 11:14:20 2016 +0800 Adds derivedConstantsDependencies for rts Building rts depends on derived constants, as we can not rely on the compiler to be build prior to rts, as we build rts with gcc, and hence do not depend on ghc, we need to have rts depend on the derived constants. This fixes #94. However, if we are going to build rts with the stage1 ghc, this should not be an issue anymore (see #90), as derived constants would be build then anyway. Yet I do not see any problem with explicilty noting down the derived constants dependency for rts. >--------------------------------------------------------------- 2565fc354a241ff9f6137c5202949a6f8f46bff9 src/Rules/Generate.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 6a4270b..65c0abf 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -72,6 +72,7 @@ compilerDependencies stage = generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage + | pkg == rts = derivedConstantsDependencies | stage == Stage0 = defaultDependencies | otherwise = [] From git at git.haskell.org Thu Oct 26 23:36:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Settings/Default.hs to GHC.hs, add Settings.hs. (f68d70f) Message-ID: <20171026233644.8460B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f68d70f07527618af262cf45d84c5ca898b166b7/ghc >--------------------------------------------------------------- commit f68d70f07527618af262cf45d84c5ca898b166b7 Author: Andrey Mokhov Date: Sat Aug 22 19:20:11 2015 +0100 Move Settings/Default.hs to GHC.hs, add Settings.hs. >--------------------------------------------------------------- f68d70f07527618af262cf45d84c5ca898b166b7 src/{Settings/Default.hs => GHC.hs} | 32 ++++++++++++++++---------------- src/Oracles/ArgsHash.hs | 2 +- src/Predicates.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 9 ++++----- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 5 +---- src/Rules/Library.hs | 2 +- src/Settings.hs | 13 +++++++++++++ src/Settings/Args.hs | 3 +-- src/Settings/Builders/Ghc.hs | 3 +-- src/Settings/Builders/GhcCabal.hs | 5 +---- src/Settings/Packages.hs | 14 +++++--------- src/Settings/User.hs | 4 +--- 16 files changed, 50 insertions(+), 52 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 f68d70f07527618af262cf45d84c5ca898b166b7 From git at git.haskell.org Thu Oct 26 23:36:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds gmp.h to the integerGmp dependencies. (6fd807b) Message-ID: <20171026233648.1A3C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6fd807ba05023634fb7f6082ef2369b9f7f90f6b/ghc >--------------------------------------------------------------- commit 6fd807ba05023634fb7f6082ef2369b9f7f90f6b Author: Moritz Angermann Date: Tue Jan 5 13:05:18 2016 +0800 Adds gmp.h to the integerGmp dependencies. Fix #88. is imported by libraries/integer-gmp/cbits/wrappers.c, hence the dependency generation with GccM, requires gmp.h to be available. We therefore add it to the generated dependencies. >--------------------------------------------------------------- 6fd807ba05023634fb7f6082ef2369b9f7f90f6b src/Rules/Generate.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 65c0abf..921c672 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -69,10 +69,15 @@ compilerDependencies stage = , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] +integerGmpDependencies :: [FilePath] +integerGmpDependencies = ((pkgPath integerGmp -/- "gmp") -/-) <$> + [ "gmp.h" ] -- identical to integerGmpLibraryH, but doesn't require the import. + generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == rts = derivedConstantsDependencies + | pkg == integerGmp = integerGmpDependencies | stage == Stage0 = defaultDependencies | otherwise = [] From git at git.haskell.org Thu Oct 26 23:36:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge Base.hs and Util.hs. (190f3fd) Message-ID: <20171026233648.288023A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/190f3fde35a3230bbdfe50afce81dd5e10590c24/ghc >--------------------------------------------------------------- commit 190f3fde35a3230bbdfe50afce81dd5e10590c24 Author: Andrey Mokhov Date: Sat Aug 22 21:03:38 2015 +0100 Merge Base.hs and Util.hs. >--------------------------------------------------------------- 190f3fde35a3230bbdfe50afce81dd5e10590c24 src/Base.hs | 119 +++++++++++++++++++++++++++++++++++++- src/Builder.hs | 1 - src/Expression.hs | 3 +- src/Oracles/ArgsHash.hs | 2 - src/Oracles/Config.hs | 1 - src/Oracles/Config/Flag.hs | 1 - src/Oracles/Dependencies.hs | 1 - src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 1 - src/Oracles/WindowsRoot.hs | 1 - src/Package.hs | 1 - src/Predicates.hs | 1 - src/Rules.hs | 6 +- src/Rules/Actions.hs | 3 - src/Rules/Cabal.hs | 1 - src/Rules/Compile.hs | 1 - src/Rules/Config.hs | 1 - src/Rules/Data.hs | 2 - src/Rules/Dependencies.hs | 2 - src/Rules/Documentation.hs | 1 - src/Rules/Library.hs | 7 +-- src/Rules/Package.hs | 1 - src/Rules/Resources.hs | 1 - src/Settings/Args.hs | 2 +- src/Settings/Builders/Gcc.hs | 2 - src/Settings/Builders/Ghc.hs | 1 - src/Settings/Builders/GhcCabal.hs | 2 - src/Settings/Builders/GhcPkg.hs | 1 - src/Settings/Builders/Haddock.hs | 2 - src/Settings/TargetDirectory.hs | 1 - src/Settings/Util.hs | 1 - src/Settings/Ways.hs | 1 - src/Target.hs | 1 - src/Util.hs | 117 ------------------------------------- src/Way.hs | 3 +- 35 files changed, 124 insertions(+), 169 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 190f3fde35a3230bbdfe50afce81dd5e10590c24 From git at git.haskell.org Thu Oct 26 23:36:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compile rts with -O2 (8e3e9bc) Message-ID: <20171026233651.EACF33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e3e9bcf2c7fc37423a5b19ac314fe23447610ad/ghc >--------------------------------------------------------------- commit 8e3e9bcf2c7fc37423a5b19ac314fe23447610ad Author: Moritz Angermann Date: Tue Jan 5 13:57:35 2016 +0800 Compile rts with -O2 Fixes #90. We need to force inlining for rts to compile and not end up with missing symbols. >--------------------------------------------------------------- 8e3e9bcf2c7fc37423a5b19ac314fe23447610ad src/Settings/Packages/Rts.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 36476a0..eb74eea 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -49,6 +49,13 @@ rtsPackageArgs = package rts ? do [ arg "-Irts" , arg $ "-I" ++ path -/- "build" , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" + -- rts **must** be compiled with optimizations. The INLINE_HEADER macro, + -- requires that functions are inlined to work as expected. Inlining + -- only happens for optimized builds. Otherwise we can assume that + -- there is a non-inlined variant to use instead. But rts does not + -- provide non-inlined alternatives and hence needs the function to + -- be inlined. See also Issue #90 + , arg $ "-O2" , (file "//RtsMessages.*" ||^ file "//Trace.*") ? arg ("-DProjectVersion=" ++ quote projectVersion) From git at git.haskell.org Thu Oct 26 23:36:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (c928f2c) Message-ID: <20171026233651.F17313A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c928f2ce774091b7a6345c5c3cbdf05782bb2d23/ghc >--------------------------------------------------------------- commit c928f2ce774091b7a6345c5c3cbdf05782bb2d23 Author: Andrey Mokhov Date: Sat Aug 22 21:08:19 2015 +0100 Add comments. >--------------------------------------------------------------- c928f2ce774091b7a6345c5c3cbdf05782bb2d23 src/Base.hs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 862c46b..13483ce 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -50,15 +50,17 @@ packageDependencies :: FilePath packageDependencies = shakeFilesPath ++ "package-dependencies" -- Utility functions -replaceIf :: (a -> Bool) -> a -> [a] -> [a] -replaceIf p to = map (\from -> if p from then to else from) - +-- Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) +-- Find and replace all occurrences of path separators in a String with a Char replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator +replaceIf :: (a -> Bool) -> a -> [a] -> [a] +replaceIf p to = map (\from -> if p from then to else from) + -- Given a module name extract the directory and file names, e.g.: -- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") decodeModule :: String -> (FilePath, String) From git at git.haskell.org Thu Oct 26 23:36:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Wrap ghc-stage2 (04fc52c) Message-ID: <20171026233655.7620D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/04fc52cd10d23e480ca4de402eb545b4269bdcb1/ghc >--------------------------------------------------------------- commit 04fc52cd10d23e480ca4de402eb545b4269bdcb1 Author: Moritz Angermann Date: Tue Jan 5 14:06:23 2016 +0800 Wrap ghc-stage2 Fix #96 (c.f. #57 for stage1) >--------------------------------------------------------------- 04fc52cd10d23e480ca4de402eb545b4269bdcb1 src/Rules/Program.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index fe55005..547fb86 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -24,6 +24,7 @@ type Wrapper = FilePath -> Expr String -- List of wrappers we build wrappers :: [(PartialTarget, Wrapper)] wrappers = [ (PartialTarget Stage0 ghc, ghcWrapper) + , (PartialTarget Stage1 ghc, ghcWrapper) , (PartialTarget Stage0 ghcPkg, ghcPkgWrapper)] buildProgram :: Resources -> PartialTarget -> Rules () From git at git.haskell.org Thu Oct 26 23:36:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, order Builder alphabetically. (a4c1eba) Message-ID: <20171026233655.7EA423A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4c1ebabfc62d83ec7d717210db4ae56ca900205/ghc >--------------------------------------------------------------- commit a4c1ebabfc62d83ec7d717210db4ae56ca900205 Author: Andrey Mokhov Date: Sat Aug 22 21:18:28 2015 +0100 Add comments, order Builder alphabetically. >--------------------------------------------------------------- a4c1ebabfc62d83ec7d717210db4ae56ca900205 src/Builder.hs | 47 ++++++++++++++++++++++------------------------- 1 file changed, 22 insertions(+), 25 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 5d60035..dde37c1 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -11,48 +11,45 @@ import Stage -- Ghc Stage0 is the bootstrapping compiler -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg --- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) +-- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) -- TODO: add Cpp builders -- TODO: rename Gcc to Cc? -data Builder = Ar - | Ld - | Alex - | Happy - | Haddock - | HsColour - | GhcCabal +data Builder = Alex + | Ar | Gcc Stage + | GccM Stage | Ghc Stage + | GhcCabal + | GhcCabalHsColour | GhcM Stage - | GccM Stage | GhcPkg Stage - | GhcCabalHsColour + | Haddock + | Happy + | HsColour + | Ld deriving (Show, Eq, Generic) -- Configuration files refer to Builders as follows: --- TODO: determine paths to utils without looking up configuration files builderKey :: Builder -> String builderKey builder = case builder of - Ar -> "ar" - Ld -> "ld" Alex -> "alex" - Happy -> "happy" - Haddock -> "haddock" - HsColour -> "hscolour" - GhcCabal -> "ghc-cabal" + Ar -> "ar" + Gcc Stage0 -> "system-gcc" + Gcc _ -> "gcc" + GccM stage -> builderKey $ Gcc stage -- Synonym for 'Gcc -MM' Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - Gcc Stage0 -> "system-gcc" - Gcc _ -> "gcc" + GhcM stage -> builderKey $ Ghc stage -- Synonym for 'Ghc -M' + GhcCabal -> "ghc-cabal" + GhcCabalHsColour -> builderKey $ GhcCabal -- Synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" - -- GhcM/GccM are synonyms for Ghc/Gcc (called with -M and -MM flags) - GhcM stage -> builderKey $ Ghc stage - GccM stage -> builderKey $ Gcc stage - -- GhcCabalHsColour is a synonym for GhcCabal (called in hscolour mode) - GhcCabalHsColour -> builderKey $ GhcCabal + Happy -> "happy" + Haddock -> "haddock" + HsColour -> "hscolour" + Ld -> "ld" builderPath :: Builder -> Action FilePath builderPath builder = do @@ -77,7 +74,7 @@ needBuilder laxDependencies builder = do allowOrderOnlyDependency :: Builder -> Bool allowOrderOnlyDependency (Ghc _) = True allowOrderOnlyDependency (GhcM _) = True - allowOrderOnlyDependency _ = False + allowOrderOnlyDependency _ = False -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". From git at git.haskell.org Thu Oct 26 23:36:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove notP and (??) Predicate functions. (88fa774) Message-ID: <20171026233658.EC9A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88fa774add49f09b3ccac966c85c49458275a5c6/ghc >--------------------------------------------------------------- commit 88fa774add49f09b3ccac966c85c49458275a5c6 Author: Andrey Mokhov Date: Sat Aug 22 21:40:24 2015 +0100 Remove notP and (??) Predicate functions. >--------------------------------------------------------------- 88fa774add49f09b3ccac966c85c49458275a5c6 src/Expression.hs | 12 ++++-------- src/Predicates.hs | 6 +++--- src/Settings/Builders/GhcCabal.hs | 15 +++++++-------- 3 files changed, 14 insertions(+), 19 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index e62acf0..d84fb2c 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -7,7 +7,7 @@ module Expression ( module Stage, module Way, Expr, DiffExpr, fromDiffExpr, - Predicate, (?), (??), notP, applyPredicate, + Predicate, (?), applyPredicate, Args, Ways, Packages, apply, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, @@ -63,7 +63,7 @@ append x = apply (<> x) -- 3) remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] -remove xs = apply . filter $ (`notElem` xs) +remove xs = apply $ filter (`notElem` xs) -- 4) apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a @@ -74,25 +74,21 @@ applyPredicate predicate expr = do -- A convenient operator for predicate application class PredicateLike a where (?) :: Monoid m => a -> Expr m -> Expr m - notP :: a -> Predicate infixr 8 ? instance PredicateLike Predicate where (?) = applyPredicate - notP = liftM not instance PredicateLike Bool where (?) = applyPredicate . return - notP = return . not instance PredicateLike (Action Bool) where (?) = applyPredicate . lift - notP = lift . fmap not -- An equivalent of if-then-else for predicates -(??) :: (PredicateLike a, Monoid m) => a -> (Expr m, Expr m) -> Expr m -p ?? (t, f) = p ? t <> notP p ? f +-- (??) :: (PredicateLike a, Monoid m) => a -> (Expr m, Expr m) -> Expr m +-- p ?? (t, f) = p ? t <> notP p ? f -- A monadic version of append appendM :: Monoid a => Action a -> DiffExpr a diff --git a/src/Predicates.hs b/src/Predicates.hs index 8743881..5bc0aed 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -40,10 +40,10 @@ stage2 :: Predicate stage2 = stage Stage2 notStage :: Stage -> Predicate -notStage = notP . stage +notStage = liftM not . stage notStage0 :: Predicate -notStage0 = notP stage0 +notStage0 = liftM not stage0 -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate @@ -52,7 +52,7 @@ registerPackage = return True splitObjects :: Predicate splitObjects = do goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages - goodPkg <- notP $ package compiler -- We don't split compiler + goodPkg <- liftM not $ package compiler -- We don't split compiler broken <- lift $ flag SplitObjectsBroken ghcUnreg <- lift $ flag GhcUnregisterised goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 11529bf..1925daf 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -102,13 +102,12 @@ packageConstraints = stage0 ? do -- TODO: put all validating options together in one file ccArgs :: Args ccArgs = validating ? do - let gccGe46 = notP gccLt46 + let notClang = fmap not gccIsClang mconcat [ arg "-Werror" , arg "-Wall" - , gccIsClang ?? - ( arg "-Wno-unknown-pragmas" <> - gccGe46 ? windowsHost ? arg "-Werror=unused-but-set-variable" - , gccGe46 ? arg "-Wno-error=inline" )] + , gccIsClang ? arg "-Wno-unknown-pragmas" + , notClang ? gccGe46 ? notWindowsHost ? arg "-Werror=unused-but-set-variable" + , notClang ? gccGe46 ? arg "-Wno-error=inline" ] ldArgs :: Args ldArgs = mempty @@ -151,8 +150,8 @@ customPackageArgs = do , arg "--disable-library-for-ghci" , targetOs "openbsd" ? arg "--ld-options=-E" , flag GhcUnregisterised ? arg "--ghc-option=-DNO_REGS" - , notP ghcWithSMP ? arg "--ghc-option=-DNOSMP" - , notP ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" + , fmap not ghcWithSMP ? arg "--ghc-option=-DNOSMP" + , fmap not ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" , (threaded `elem` rtsWays) ? notStage0 ? arg "--ghc-option=-optc-DTHREADED_RTS" , ghcWithNativeCodeGen ? arg "--flags=ncg" @@ -160,7 +159,7 @@ customPackageArgs = do notStage0 ? arg "--flags=ghci" , ghcWithInterpreter ? ghcEnableTablesNextToCode ? - notP (flag GhcUnregisterised) ? + fmap not (flag GhcUnregisterised) ? notStage0 ? arg "--ghc-option=-DGHCI_TABLES_NEXT_TO_CODE" , ghcWithInterpreter ? ghciWithDebugger ? From git at git.haskell.org Thu Oct 26 23:36:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:36:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #95 from angerman/feature/fix-rts-deps (ccf4030) Message-ID: <20171026233659.1BB103A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccf4030baa2739d1ce03a273f764a532fb3428c9/ghc >--------------------------------------------------------------- commit ccf4030baa2739d1ce03a273f764a532fb3428c9 Merge: ba41ec6 8e3e9bc Author: Andrey Mokhov Date: Tue Jan 5 09:27:42 2016 +0000 Merge pull request #95 from angerman/feature/fix-rts-deps Adds derivedConstantsDependencies for rts >--------------------------------------------------------------- ccf4030baa2739d1ce03a273f764a532fb3428c9 src/Rules/Generate.hs | 6 ++++++ src/Settings/Packages/Rts.hs | 7 +++++++ 2 files changed, 13 insertions(+) From git at git.haskell.org Thu Oct 26 23:37:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace GccLt46 with gccGe46 as the former was always used negated. (aff7b3c) Message-ID: <20171026233703.4E4E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aff7b3c9ee5a06b7c7070f14cecf941ba1c2820d/ghc >--------------------------------------------------------------- commit aff7b3c9ee5a06b7c7070f14cecf941ba1c2820d Author: Andrey Mokhov Date: Sat Aug 22 21:41:21 2015 +0100 Replace GccLt46 with gccGe46 as the former was always used negated. >--------------------------------------------------------------- aff7b3c9ee5a06b7c7070f14cecf941ba1c2820d src/Oracles/Config/Flag.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 737af97..80d8c6a 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -1,6 +1,6 @@ module Oracles.Config.Flag ( Flag (..), flag, - crossCompiling, gccIsClang, gccLt46, + crossCompiling, gccIsClang, gccGe46, platformSupportsSharedLibs, ghcWithSMP, ghcWithNativeCodeGen ) where @@ -39,8 +39,8 @@ crossCompiling = flag CrossCompiling gccIsClang :: Action Bool gccIsClang = flag GccIsClang -gccLt46 :: Action Bool -gccLt46 = flag GccLt46 +gccGe46 :: Action Bool +gccGe46 = fmap not $ flag GccLt46 platformSupportsSharedLibs :: Action Bool platformSupportsSharedLibs = do From git at git.haskell.org Thu Oct 26 23:37:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #97 from angerman/feature/ghc-stage2-wrapper (9e1ef6a) Message-ID: <20171026233703.5CEBE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e1ef6ab9ce326638528140be935e05793f4ea16/ghc >--------------------------------------------------------------- commit 9e1ef6ab9ce326638528140be935e05793f4ea16 Merge: ccf4030 04fc52c Author: Andrey Mokhov Date: Tue Jan 5 09:28:26 2016 +0000 Merge pull request #97 from angerman/feature/ghc-stage2-wrapper Wrap ghc-stage2 >--------------------------------------------------------------- 9e1ef6ab9ce326638528140be935e05793f4ea16 src/Rules/Program.hs | 1 + 1 file changed, 1 insertion(+) From git at git.haskell.org Thu Oct 26 23:37:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports, add comments. (5603275) Message-ID: <20171026233707.530203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5603275f1aeeb2b3469307859daabcd6f957d8c9/ghc >--------------------------------------------------------------- commit 5603275f1aeeb2b3469307859daabcd6f957d8c9 Author: Andrey Mokhov Date: Sat Aug 22 22:18:14 2015 +0100 Refactor imports, add comments. >--------------------------------------------------------------- 5603275f1aeeb2b3469307859daabcd6f957d8c9 src/Expression.hs | 7 ++----- src/GHC.hs | 13 +++++++------ src/Main.hs | 12 ++++++------ src/Package.hs | 21 ++++++++++----------- src/Rules.hs | 3 +-- src/Rules/Actions.hs | 4 +--- src/Rules/Cabal.hs | 7 +++---- src/Rules/Compile.hs | 9 +++------ src/Rules/Data.hs | 7 ++----- src/Rules/Dependencies.hs | 7 ++----- src/Rules/Documentation.hs | 7 +------ src/Rules/Library.hs | 3 +-- src/Target.hs | 3 +-- src/Way.hs | 2 ++ 14 files changed, 42 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5603275f1aeeb2b3469307859daabcd6f957d8c9 From git at git.haskell.org Thu Oct 26 23:37:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix travis script: configure after shake-build is in place. (b978e17) Message-ID: <20171026233707.7560B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b978e17552d87de8973a5bdd0255da5d1baa7d51/ghc >--------------------------------------------------------------- commit b978e17552d87de8973a5bdd0255da5d1baa7d51 Author: Andrey Mokhov Date: Tue Jan 5 10:29:08 2016 +0000 Fix travis script: configure after shake-build is in place. >--------------------------------------------------------------- b978e17552d87de8973a5bdd0255da5d1baa7d51 .travis/install-ghc-shake.sh | 3 +++ .travis/install-ghc.sh | 3 --- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis/install-ghc-shake.sh b/.travis/install-ghc-shake.sh index 2dc0392..c2b8774 100755 --- a/.travis/install-ghc-shake.sh +++ b/.travis/install-ghc-shake.sh @@ -14,3 +14,6 @@ mv .git "$SHAKEDIR/" echo -e "${COLOR}Installing deps into sandbox${RESET}" ( cd "$SHAKEDIR" && cabal sandbox init ) ( cd "$SHAKEDIR" && cabal install --only-dependencies . ) + +echo -e "${COLOR}GHC boot/configure${RESET}" +( cd ghc && ./boot && ./configure) diff --git a/.travis/install-ghc.sh b/.travis/install-ghc.sh index 126cbe2..fc34ea4 100755 --- a/.travis/install-ghc.sh +++ b/.travis/install-ghc.sh @@ -10,6 +10,3 @@ git clone git://git.haskell.org/ghc echo -e "${COLOR}Initialize GHC submodules${RESET}" ( cd ghc && git submodule update --init ) - -echo -e "${COLOR}GHC boot/configure${RESET}" -( cd ghc && ./boot && ./configure) From git at git.haskell.org Thu Oct 26 23:37:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code, add comments. (b04c769) Message-ID: <20171026233711.73FCD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b04c76947514b996239afde8b7b460c7bbadfea1/ghc >--------------------------------------------------------------- commit b04c76947514b996239afde8b7b460c7bbadfea1 Author: Andrey Mokhov Date: Sun Aug 23 00:04:55 2015 +0100 Clean up code, add comments. >--------------------------------------------------------------- b04c76947514b996239afde8b7b460c7bbadfea1 src/Base.hs | 2 + src/Expression.hs | 20 +++--- src/Oracles/ArgsHash.hs | 6 +- src/Oracles/Config/Flag.hs | 19 +++--- src/Oracles/Config/Setting.hs | 8 ++- src/Oracles/Dependencies.hs | 6 +- src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 6 +- src/Oracles/WindowsRoot.hs | 5 +- src/Predicates.hs | 32 +++++----- src/Rules.hs | 12 ++-- src/Rules/Actions.hs | 1 + src/Rules/Dependencies.hs | 1 - src/Rules/Documentation.hs | 12 +--- src/Settings.hs | 72 +++++++++++++++++++++- src/Settings/Args.hs | 9 +-- src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Gcc.hs | 40 ++++++------ src/Settings/Builders/Ghc.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 41 +++++++++---- src/Settings/Builders/GhcPkg.hs | 3 +- src/Settings/Builders/Haddock.hs | 9 +-- src/Settings/Builders/Ld.hs | 5 +- src/Settings/Packages.hs | 5 +- src/Settings/TargetDirectory.hs | 4 +- src/Settings/User.hs | 3 +- src/Settings/Util.hs | 125 -------------------------------------- src/Settings/Ways.hs | 4 +- src/Target.hs | 2 +- 29 files changed, 190 insertions(+), 268 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b04c76947514b996239afde8b7b460c7bbadfea1 From git at git.haskell.org Thu Oct 26 23:37:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (d4e44fb) Message-ID: <20171026233711.913673A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4e44fb28e3487c00fb375e4a528f97cab720c53/ghc >--------------------------------------------------------------- commit d4e44fb28e3487c00fb375e4a528f97cab720c53 Author: Andrey Mokhov Date: Tue Jan 5 10:29:30 2016 +0000 Add comments. >--------------------------------------------------------------- d4e44fb28e3487c00fb375e4a528f97cab720c53 src/Settings/Packages/Rts.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index eb74eea..d300e5a 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -89,6 +89,14 @@ rtsPackageArgs = package rts ? do , arg "-DFFI_LIB_DIR=" , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] + +-- # If we're compiling on windows, enforce that we only support XP+ +-- # Adding this here means it doesn't have to be done in individual .c files +-- # and also centralizes the versioning. +-- ifeq "$$(TargetOS_CPP)" "mingw32" +-- rts_dist_$1_CC_OPTS += -DWINVER=$(rts_WINVER) +-- endif + -- #----------------------------------------------------------------------------- -- # Use system provided libffi From git at git.haskell.org Thu Oct 26 23:37:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Ghc/GhcM arguments. (3039df4) Message-ID: <20171026233714.E59523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3039df428add9752791ecba96a9bef8fc41980f3/ghc >--------------------------------------------------------------- commit 3039df428add9752791ecba96a9bef8fc41980f3 Author: Andrey Mokhov Date: Sun Aug 23 00:33:01 2015 +0100 Fix Ghc/GhcM arguments. >--------------------------------------------------------------- 3039df428add9752791ecba96a9bef8fc41980f3 src/Settings/Builders/Ghc.hs | 35 +++++++++++++++++++---------------- 1 file changed, 19 insertions(+), 16 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 6ecc26d..5ab520e 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,7 +2,7 @@ module Settings.Builders.Ghc (ghcArgs, ghcMArgs, commonGhcArgs) where import Expression import Oracles -import Predicates (stagedBuilder, splitObjects, stage0) +import Predicates (stagedBuilder, splitObjects, stage0, notStage0) import Settings -- TODO: add support for -dyno @@ -15,6 +15,12 @@ ghcArgs = stagedBuilder Ghc ? do file <- getFile srcs <- getSources mconcat [ commonGhcArgs + , arg "-H32m" + , stage0 ? arg "-O" + , notStage0 ? arg "-O2" + , arg "-Wall" + , arg "-fwarn-tabs" + , splitObjects ? arg "-split-objs" , arg "-c", append srcs , arg "-o", arg file ] @@ -25,6 +31,7 @@ ghcMArgs = stagedBuilder GhcM ? do srcs <- getSources mconcat [ arg "-M" , commonGhcArgs + , arg "-include-pkg-deps" , arg "-dep-makefile", arg file , append $ concat [ ["-dep-suffix", wayPrefix w] | w <- ways ] , append srcs ] @@ -46,10 +53,9 @@ commonGhcArgs = do , append hsArgs , append $ map ("-optP" ++) cppArgs , arg "-odir" , arg buildPath - , arg "-stubdir" , arg buildPath , arg "-hidir" , arg buildPath - , splitObjects ? arg "-split-objs" - , arg "-rtsopts" ] -- TODO: is this needed? + , arg "-stubdir" , arg buildPath + , arg "-rtsopts" ] -- TODO: ifeq "$(HC_VERSION_GE_6_13)" "YES" -- TODO: do '-ticky' in all debug ways? wayGhcArgs :: Args @@ -76,7 +82,6 @@ packageGhcArgs = do mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" - , arg "-include-pkg-deps" , stage0 ? arg "-package-db libraries/bootstrapping.conf" , if supportsPackageKey || stage /= Stage0 then arg $ "-this-package-key " ++ pkgKey @@ -89,19 +94,17 @@ includeGhcArgs = do path <- getTargetPath srcDirs <- getPkgDataList SrcDirs incDirs <- getPkgDataList IncludeDirs - cppArgs <- getPkgDataList CppArgs let buildPath = path -/- "build" autogenPath = buildPath -/- "autogen" - mconcat - [ arg "-i" - , arg $ "-i" ++ buildPath - , arg $ "-i" ++ autogenPath - , arg $ "-I" ++ buildPath - , arg $ "-I" ++ autogenPath - , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] - , arg "-optP-include", arg $ "-optP" ++ autogenPath -/- "cabal_macros.h" - , append $ map ("-optP" ++) cppArgs ] + mconcat [ arg "-i" + , arg $ "-i" ++ buildPath + , arg $ "-i" ++ autogenPath + , arg $ "-I" ++ buildPath + , arg $ "-I" ++ autogenPath + , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] + , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] + , arg "-optP-include" + , arg $ "-optP" ++ autogenPath -/- "cabal_macros.h" ] -- TODO: see ghc.mk -- # And then we strip it out again before building the package: From git at git.haskell.org Thu Oct 26 23:37:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow splitObjects to be controlled in Settings/User.hs, see #84. (b18f0e3) Message-ID: <20171026233715.5F8BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b18f0e3f79ee051e9d384b508f0ca3eaa902d80b/ghc >--------------------------------------------------------------- commit b18f0e3f79ee051e9d384b508f0ca3eaa902d80b Author: Andrey Mokhov Date: Tue Jan 5 11:08:20 2016 +0000 Allow splitObjects to be controlled in Settings/User.hs, see #84. >--------------------------------------------------------------- b18f0e3f79ee051e9d384b508f0ca3eaa902d80b shaking-up-ghc.cabal | 1 + src/Predicates.hs | 12 +----------- src/Rules/Library.hs | 1 - src/Settings/Default.hs | 15 +++++++++++++++ src/Settings/User.hs | 6 +++++- 5 files changed, 22 insertions(+), 13 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 334cd59..2eb9f72 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -76,6 +76,7 @@ executable ghc-shake , Settings.Builders.HsCpp , Settings.Builders.Ld , Settings.Builders.Tar + , Settings.Default , Settings.Packages , Settings.Packages.Base , Settings.Packages.Compiler diff --git a/src/Predicates.hs b/src/Predicates.hs index 7b788fe..ad63598 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,13 +1,11 @@ -- | Convenient predicates module Predicates ( stage, package, builder, stagedBuilder, builderGcc, builderGhc, file, way, - stage0, stage1, stage2, notStage0, notPackage, registerPackage, splitObjects + stage0, stage1, stage2, notStage0, notPackage, registerPackage ) where import Base import Expression -import GHC -import Oracles.Config.Flag -- Basic predicates stage :: Stage -> Predicate @@ -55,11 +53,3 @@ notPackage = notM . package -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate registerPackage = return True - -splitObjects :: Predicate -splitObjects = do - goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages - pkg <- getPackage - supported <- lift supportsSplitObjects - let goodPackage = isLibrary pkg && pkg /= compiler && pkg /= rts - return $ goodStage && goodPackage && supported diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 8633c69..d9a1a48 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -6,7 +6,6 @@ import Base hiding (splitPath) import Expression import GHC import Oracles -import Predicates (splitObjects) import Rules.Actions import Rules.IntegerGmp import Rules.Resources diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs new file mode 100644 index 0000000..93b647a --- /dev/null +++ b/src/Settings/Default.hs @@ -0,0 +1,15 @@ +module Settings.Default (defaultSplitObjects) where + +import Base +import Expression +import GHC +import Oracles.Config.Flag +import Predicates + +defaultSplitObjects :: Predicate +defaultSplitObjects = do + goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages + pkg <- getPackage + supported <- lift supportsSplitObjects + let goodPackage = isLibrary pkg && pkg /= compiler && pkg /= rts + return $ goodStage && goodPackage && supported diff --git a/src/Settings/User.hs b/src/Settings/User.hs index cad2578..6107f6f 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors + verboseCommands, turnWarningsIntoErrors, splitObjects ) where import GHC @@ -57,6 +57,10 @@ trackBuildSystem = True validating :: Bool validating = False +-- To switch off split objects change to 'return False' +splitObjects :: Predicate +splitObjects = return False -- FIXME: should be defaultSplitObjects, see #84. + dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Thu Oct 26 23:37:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate only one rule for Haddock (Stage1). (cdf208c) Message-ID: <20171026233718.9F6483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cdf208c342c346b48f848e06b9ffc8a089326254/ghc >--------------------------------------------------------------- commit cdf208c342c346b48f848e06b9ffc8a089326254 Author: Andrey Mokhov Date: Sun Aug 23 01:04:55 2015 +0100 Generate only one rule for Haddock (Stage1). >--------------------------------------------------------------- cdf208c342c346b48f848e06b9ffc8a089326254 src/Rules/Documentation.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 81e3140..5978cfd 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -10,10 +10,10 @@ import Settings -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. buildPackageDocumentation :: Resources -> PartialTarget -> Rules () -buildPackageDocumentation _ target @ (PartialTarget _ pkg) = +buildPackageDocumentation _ target @ (PartialTarget stage pkg) = let cabalFile = pkgCabalFile pkg haddockFile = pkgHaddockFile pkg - in do + in when (stage == Stage1) $ do haddockFile %> \file -> do whenM (specified HsColour) $ do need [cabalFile] From git at git.haskell.org Thu Oct 26 23:37:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rework Travis CI script (d0ffc1f) Message-ID: <20171026233719.18D7D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d0ffc1f8d7e109511b08c0a70a4956188718a911/ghc >--------------------------------------------------------------- commit d0ffc1f8d7e109511b08c0a70a4956188718a911 Author: David Luposchainsky Date: Tue Jan 5 09:50:08 2016 +0100 Rework Travis CI script - Move all .travis/*.sh functionality directly into .travis.yml - Install Alex/Happy from PPA instead of compiling them by hand - Skip Shake progress indicators, as they're rather useless on clean-slate Travis builds, and clutter up the log - Don't use a Cabal sandbox for building so Travis can share $HOME/.cabal - boot/configure only after the Shake build system is in place, otherwise some required *.in files are not converted, and Shake fails >--------------------------------------------------------------- d0ffc1f8d7e109511b08c0a70a4956188718a911 .travis.yml | 52 +++++++++++++++++++++++++++---------- .travis/install-cabal-happy-alex.sh | 18 ------------- .travis/install-ghc-shake.sh | 19 -------------- .travis/install-ghc.sh | 12 --------- .travis/print-env.sh | 9 ------- .travis/run-ghc-shake.sh | 9 ------- build.cabal.sh | 3 ++- build.sh | 2 +- 8 files changed, 42 insertions(+), 82 deletions(-) diff --git a/.travis.yml b/.travis.yml index 5e169fa..9079fa9 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,9 +1,23 @@ sudo: false matrix: - include: - - env: CABALVER=1.22 GHCVER=7.10.3 - addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.3,zlib1g-dev,terminfo-dev], sources: [hvr-ghc]}} + include: + - env: + CABALVER=1.22 + GHCVER=7.10.3 + + addons: { + apt: { + packages: [ + ghc-7.10.3, + alex-3.1.4, + happy-1.19.5, + cabal-install-1.22, + zlib1g-dev + ], + sources: [hvr-ghc] + } + } before_install: @@ -12,21 +26,33 @@ before_install: - PATH="/opt/cabal/$CABALVER/bin:$PATH" - export PATH - - .travis/print-env.sh + - env + - ghc --version + - cabal --version + - alex --version + - happy --version + - cabal update install: - - .travis/install-cabal-happy-alex.sh - - .travis/install-ghc.sh - - .travis/install-ghc-shake.sh + + - travis_retry git clone git://git.haskell.org/ghc --recurse-submodules + + # Travis clones the project into ".", but we need it as a child directory + # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake + # ".git" directory into the appropriate location, and perform a hard reset + # in order to regenerate the GHC-Shake files. + - mkdir ghc/shake-build + - mv .git ghc/shake-build + - ( cd ghc/shake-build && git reset --hard HEAD ) + + - ( cd ghc/shake-build && cabal install --only-dependencies ) + + - ( cd ghc && ./boot ) + - ( cd ghc && ./configure ) script: - - .travis/run-ghc-shake.sh + - ./ghc/shake-build/build.sh -j --no-progress cache: directories: - $HOME/.cabal - # - ghc/shake-build/.cabal-sandbox - # - ghc/shake-build/cabal.sandbox.config - -# before_cache: -# - rm -rf ghc/shake-build diff --git a/.travis/install-cabal-happy-alex.sh b/.travis/install-cabal-happy-alex.sh deleted file mode 100755 index 93df460..0000000 --- a/.travis/install-cabal-happy-alex.sh +++ /dev/null @@ -1,18 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[32m" # Green -RESET="\e[m" - -echo -e "${COLOR}GHC version:${RESET}" -ghc --version - -echo -e "${COLOR}Cabal version:${RESET}" -cabal --version - -echo -e "${COLOR}Update Cabal${RESET}" -cabal update - -echo -e "${COLOR}Install Alex+Happy${RESET}" -cabal install alex happy diff --git a/.travis/install-ghc-shake.sh b/.travis/install-ghc-shake.sh deleted file mode 100755 index c2b8774..0000000 --- a/.travis/install-ghc-shake.sh +++ /dev/null @@ -1,19 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[31m" # Red, because this file is serious business -RESET="\e[m" - -echo -e "${COLOR}Brutally hacking GHC-Shake to its proper location${RESET}" -SHAKEDIR="ghc/shake-build" -mkdir -p "$SHAKEDIR" -mv .git "$SHAKEDIR/" -( cd "$SHAKEDIR" && git reset --hard HEAD ) - -echo -e "${COLOR}Installing deps into sandbox${RESET}" -( cd "$SHAKEDIR" && cabal sandbox init ) -( cd "$SHAKEDIR" && cabal install --only-dependencies . ) - -echo -e "${COLOR}GHC boot/configure${RESET}" -( cd ghc && ./boot && ./configure) diff --git a/.travis/install-ghc.sh b/.travis/install-ghc.sh deleted file mode 100755 index fc34ea4..0000000 --- a/.travis/install-ghc.sh +++ /dev/null @@ -1,12 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[34m" # Blue -RESET="\e[m" - -echo -e "${COLOR}Clone GHC source${RESET}" -git clone git://git.haskell.org/ghc - -echo -e "${COLOR}Initialize GHC submodules${RESET}" -( cd ghc && git submodule update --init ) diff --git a/.travis/print-env.sh b/.travis/print-env.sh deleted file mode 100755 index c09c11f..0000000 --- a/.travis/print-env.sh +++ /dev/null @@ -1,9 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[32m" # Green -RESET="\e[m" - -echo -e "${COLOR}Environment:${RESET}" -env diff --git a/.travis/run-ghc-shake.sh b/.travis/run-ghc-shake.sh deleted file mode 100755 index 7b867b7..0000000 --- a/.travis/run-ghc-shake.sh +++ /dev/null @@ -1,9 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[32m" # Green -RESET="\e[m" - -echo -e "${COLOR}Running Shake build system${RESET}" -( cd ghc && ./shake-build/build.cabal.sh ) diff --git a/build.cabal.sh b/build.cabal.sh index 65da82b..cf165b8 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -6,9 +6,10 @@ absoltueRoot="$(dirname "$(readlink -f "$0")")" cd "$absoltueRoot" # Initialize sandbox if necessary -if ! $(cabal sandbox hc-pkg list 2>&1 > /dev/null); then +if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then cabal sandbox init cabal install \ + --dependencies-only \ --disable-library-profiling \ --disable-shared fi diff --git a/build.sh b/build.sh index f09c30c..82cbb93 100755 --- a/build.sh +++ b/build.sh @@ -2,7 +2,7 @@ set -euo pipefail -root="$(dirname "$0")" +root="$(dirname "$(readlink -f "$0")")" mkdir -p "$root/.shake" From git at git.haskell.org Thu Oct 26 23:37:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (a9adcf3) Message-ID: <20171026233722.B4E673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9adcf31d5daf441cfa4efc5ac4012a3836c9b19/ghc >--------------------------------------------------------------- commit a9adcf31d5daf441cfa4efc5ac4012a3836c9b19 Author: Andrey Mokhov Date: Sat Sep 19 00:04:02 2015 +0100 Clean up. >--------------------------------------------------------------- a9adcf31d5daf441cfa4efc5ac4012a3836c9b19 arg/README.md | 5 ----- src/Builder.hs | 13 +++++++------ src/Oracles/Config/Setting.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Rules/Cabal.hs | 4 ++-- src/Settings/Args.hs | 8 ++++---- src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Packages.hs | 4 +--- src/Stage.hs | 2 +- 10 files changed, 18 insertions(+), 25 deletions(-) diff --git a/arg/README.md b/arg/README.md deleted file mode 100644 index 0af8834..0000000 --- a/arg/README.md +++ /dev/null @@ -1,5 +0,0 @@ -This folder serves two purposes: - -* Tracking argument lists produced by rules - -* Documentation diff --git a/src/Builder.hs b/src/Builder.hs index dde37c1..8e5f639 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -36,14 +36,14 @@ builderKey builder = case builder of Ar -> "ar" Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" - GccM stage -> builderKey $ Gcc stage -- Synonym for 'Gcc -MM' + GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - GhcM stage -> builderKey $ Ghc stage -- Synonym for 'Ghc -M' + GhcM stage -> builderKey $ Ghc stage -- synonym for 'Ghc -M' GhcCabal -> "ghc-cabal" - GhcCabalHsColour -> builderKey $ GhcCabal -- Synonym for 'GhcCabal hscolour' + GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" Happy -> "happy" @@ -72,9 +72,10 @@ needBuilder laxDependencies builder = do else need [path] where allowOrderOnlyDependency :: Builder -> Bool - allowOrderOnlyDependency (Ghc _) = True - allowOrderOnlyDependency (GhcM _) = True - allowOrderOnlyDependency _ = False + allowOrderOnlyDependency b = case b of + Ghc _ -> True + GhcM _ -> True + _ -> False -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 27b2d89..f0f7fb7 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -7,8 +7,8 @@ module Oracles.Config.Setting ( ) where import Base -import Stage import Oracles.Config +import Stage -- Each Setting comes from the system.config file, e.g. 'target-os = mingw32'. -- setting TargetOs looks up the config file and returns "mingw32". diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 1898d21..0d1a0b4 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -2,8 +2,8 @@ module Oracles.PackageDeps (packageDeps, packageDepsOracle) where import Base -import Package import qualified Data.HashMap.Strict as Map +import Package newtype PackageDepsKey = PackageDepsKey PackageName deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index b958db4..aac8ab2 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,11 +1,11 @@ module Rules.Cabal (cabalRules) where +import Expression import Data.Version import Distribution.Package -import Distribution.Verbosity import Distribution.PackageDescription import Distribution.PackageDescription.Parse -import Expression +import Distribution.Verbosity import Package hiding (library) import Settings diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 4e55a3d..5a8c63a 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -1,14 +1,14 @@ module Settings.Args (getArgs) where import Expression -import Settings.User import Settings.Builders.Ar -import Settings.Builders.Ld -import Settings.Builders.Ghc import Settings.Builders.Gcc +import Settings.Builders.Ghc +import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg import Settings.Builders.Haddock -import Settings.Builders.GhcCabal +import Settings.Builders.Ld +import Settings.User getArgs :: Expr [String] getArgs = fromDiffExpr $ defaultArgs <> userArgs diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 617d4e1..082cbaf 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,6 +1,5 @@ module Settings.Builders.Ar (arArgs, arPersistentArgsCount) where -import Builder import Expression import Predicates (builder) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index bc6622c..2cd26d0 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -1,8 +1,8 @@ module Settings.Builders.Haddock (haddockArgs) where import Expression -import Predicates hiding (file) import Oracles +import Predicates hiding (file) import Settings import Settings.Builders.Ghc diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 7f2a64b..87f293d 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -1,6 +1,4 @@ -module Settings.Packages ( - getPackages, knownPackages, findKnownPackage - ) where +module Settings.Packages (getPackages, knownPackages, findKnownPackage) where import Expression import Predicates diff --git a/src/Stage.hs b/src/Stage.hs index 50a273b..edddb6f 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -4,7 +4,7 @@ module Stage (Stage (..)) where import Base import GHC.Generics (Generic) --- TODO: rename to something more meaningful, e.g. Stage0 -> Boot. +-- TODO: rename to something more meaningful, e.g. 'Stage0' -> 'Boot'. data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum, Generic) instance Show Stage where From git at git.haskell.org Thu Oct 26 23:37:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #101 from quchen/master (0d43a40) Message-ID: <20171026233723.0F11C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0d43a40a2b42a3332e41e7e096b2d0834dffeb53/ghc >--------------------------------------------------------------- commit 0d43a40a2b42a3332e41e7e096b2d0834dffeb53 Merge: b18f0e3 d0ffc1f Author: Andrey Mokhov Date: Tue Jan 5 11:31:03 2016 +0000 Merge pull request #101 from quchen/master Rework Travis CI script >--------------------------------------------------------------- 0d43a40a2b42a3332e41e7e096b2d0834dffeb53 .travis.yml | 52 +++++++++++++++++++++++++++---------- .travis/install-cabal-happy-alex.sh | 18 ------------- .travis/install-ghc-shake.sh | 19 -------------- .travis/install-ghc.sh | 12 --------- .travis/print-env.sh | 9 ------- .travis/run-ghc-shake.sh | 9 ------- build.cabal.sh | 3 ++- build.sh | 2 +- 8 files changed, 42 insertions(+), 82 deletions(-) From git at git.haskell.org Thu Oct 26 23:37:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generatePackageCode rule, alexArgs, happyArgs and Hsc2Hs builder. (fdbc3fb) Message-ID: <20171026233726.D85093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fdbc3fba223a2d437954bd0908fdb839fe836ac8/ghc >--------------------------------------------------------------- commit fdbc3fba223a2d437954bd0908fdb839fe836ac8 Author: Andrey Mokhov Date: Sun Sep 20 02:22:46 2015 +0100 Add generatePackageCode rule, alexArgs, happyArgs and Hsc2Hs builder. >--------------------------------------------------------------- fdbc3fba223a2d437954bd0908fdb839fe836ac8 cfg/system.config.in | 2 ++ doc/demo.txt | 5 ++++ src/Builder.hs | 2 ++ src/Rules/Documentation.hs | 6 ++--- src/Rules/Generate.hs | 55 ++++++++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 2 ++ src/Settings/Args.hs | 20 +++++++++------ src/Settings/Builders/Alex.hs | 14 +++++++++++ src/Settings/Builders/Happy.hs | 13 ++++++++++ 9 files changed, 108 insertions(+), 11 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index a274e84..b92b6ba 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -19,6 +19,8 @@ ghc-cabal = @hardtop@/inplace/bin/ghc-cabal haddock = @hardtop@/inplace/bin/haddock +hsc2hs = @hardtop@/inplace/bin/hsc2hs + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ diff --git a/doc/demo.txt b/doc/demo.txt index 7acd27d..28b3689 100644 --- a/doc/demo.txt +++ b/doc/demo.txt @@ -12,3 +12,8 @@ * https://mail.haskell.org/pipermail/ghc-commits/2013-May/001712.html * see ghc.mk, comment about parallel ghc-pkg invokations + +5. Discovered dead code in the old build system, e.g: + +* Alex3 variable not needed as Alex 3.1 is required. +* There are no generated *.y/*.ly files, hence they can never be in the build directory. \ No newline at end of file diff --git a/src/Builder.hs b/src/Builder.hs index 8e5f639..3a24df3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -26,6 +26,7 @@ data Builder = Alex | Haddock | Happy | HsColour + | Hsc2Hs | Ld deriving (Show, Eq, Generic) @@ -49,6 +50,7 @@ builderKey builder = case builder of Happy -> "happy" Haddock -> "haddock" HsColour -> "hscolour" + Hsc2Hs -> "hsc2hs" Ld -> "ld" builderPath :: Builder -> Action FilePath diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 5978cfd..2ebaa59 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -10,9 +10,9 @@ import Settings -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. buildPackageDocumentation :: Resources -> PartialTarget -> Rules () -buildPackageDocumentation _ target @ (PartialTarget stage pkg) = - let cabalFile = pkgCabalFile pkg - haddockFile = pkgHaddockFile pkg +buildPackageDocumentation _ target @ (PartialTarget stage package) = + let cabalFile = pkgCabalFile package + haddockFile = pkgHaddockFile package in when (stage == Stage1) $ do haddockFile %> \file -> do whenM (specified HsColour) $ do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs new file mode 100644 index 0000000..055dccb --- /dev/null +++ b/src/Rules/Generate.hs @@ -0,0 +1,55 @@ +module Rules.Generate (generatePackageCode) where + +import Expression +import Oracles +import Rules.Actions +import Rules.Resources +import Settings + +-- The following generators and corresponding source extensions are supported: +knownGenerators :: [ (Builder, String) ] +knownGenerators = [ (Alex , ".x" ) + , (Happy , ".y" ) + , (Happy , ".ly" ) + , (Hsc2Hs , ".hsc") ] + +determineBuilder :: FilePath -> Maybe Builder +determineBuilder file = fmap fst $ find (\(_, e) -> e == ext) knownGenerators + where + ext = takeExtension file + +generatePackageCode :: Resources -> PartialTarget -> Rules () +generatePackageCode _ target @ (PartialTarget stage package) = + let path = targetPath stage package + packagePath = pkgPath package + buildPath = path -/- "build" + in do + buildPath "*.hs" %> \file -> do + dirs <- interpretPartial target $ getPkgDataList SrcDirs + files <- getDirectoryFiles "" $ + [ packagePath d takeBaseName file <.> "*" | d <- dirs ] + let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] + (src, builder) = head gens + when (length gens /= 1) . putError $ + "Exactly one generator expected for " ++ file + ++ "(found: " ++ show gens ++ ")." + need [src] + build $ fullTarget target builder [src] [file] + +-- $1/$2/build/%.hs : $1/$3/%.ly | $$$$(dir $$$$@)/. +-- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ + +-- $1/$2/build/%.hs : $1/$3/%.y | $$$$(dir $$$$@)/. +-- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ + +-- $1/$2/build/%_hsc.c $1/$2/build/%_hsc.h $1/$2/build/%.hs : $1/$3/%.hsc $$$$(hsc2hs_INPLACE) | $$$$(dir $$$$@)/. +-- $$(call cmd,hsc2hs_INPLACE) $$($1_$2_ALL_HSC2HS_OPTS) $$< -o $$@ + +-- # Now the rules for hs-boot files. + +-- $1/$2/build/%.hs-boot : $1/$3/%.hs-boot +-- "$$(CP)" $$< $$@ + +-- $1/$2/build/%.lhs-boot : $1/$3/%.lhs-boot +-- "$$(CP)" $$< $$@ + diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index dfc15e8..9da4f8b 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -5,6 +5,7 @@ import Rules.Compile import Rules.Data import Rules.Dependencies import Rules.Documentation +import Rules.Generate import Rules.Library import Rules.Resources import Target @@ -13,6 +14,7 @@ buildPackage :: Resources -> PartialTarget -> Rules () buildPackage = mconcat [ buildPackageData , buildPackageDependencies + , generatePackageCode , compilePackage , buildPackageLibrary , buildPackageDocumentation ] diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 5a8c63a..2e2f379 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -1,12 +1,14 @@ module Settings.Args (getArgs) where import Expression +import Settings.Builders.Alex import Settings.Builders.Ar import Settings.Builders.Gcc import Settings.Builders.Ghc import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg import Settings.Builders.Haddock +import Settings.Builders.Happy import Settings.Builders.Ld import Settings.User @@ -23,14 +25,16 @@ getArgs = fromDiffExpr $ defaultArgs <> userArgs -- TODO: is GhcHcOpts=-Rghc-timing needed? defaultArgs :: Args defaultArgs = mconcat - [ cabalArgs - , ghcPkgArgs - , ghcMArgs - , gccMArgs - , ghcArgs - , gccArgs + [ alexArgs , arArgs - , ldArgs + , cabalArgs + , customPackageArgs + , ghcArgs , ghcCabalHsColourArgs + , ghcMArgs + , ghcPkgArgs + , gccArgs + , gccMArgs , haddockArgs - , customPackageArgs ] + , happyArgs + , ldArgs ] diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs new file mode 100644 index 0000000..6aedcdb --- /dev/null +++ b/src/Settings/Builders/Alex.hs @@ -0,0 +1,14 @@ +module Settings.Builders.Alex (alexArgs) where + +import Expression +import GHC (compiler) +import Predicates (builder, package) + +alexArgs :: Args +alexArgs = builder Alex ? do + file <- getFile + src <- getSource + mconcat [ arg "-g" + , package compiler ? arg "--latin1" + , arg src + , arg "-o", arg file ] diff --git a/src/Settings/Builders/Happy.hs b/src/Settings/Builders/Happy.hs new file mode 100644 index 0000000..fcd962a --- /dev/null +++ b/src/Settings/Builders/Happy.hs @@ -0,0 +1,13 @@ +module Settings.Builders.Happy (happyArgs) where + +import Expression +import Predicates (builder) + +happyArgs :: Args +happyArgs = builder Happy ? do + file <- getFile + src <- getSource + mconcat [ arg "-agc" + , arg "--strict" + , arg src + , arg "-o", arg file ] From git at git.haskell.org Thu Oct 26 23:37:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Temporarily disable haddock, see #98. (2d1efa2) Message-ID: <20171026233727.4982F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d1efa2110af8b0aa2b5aa641e61f8c906e02d38/ghc >--------------------------------------------------------------- commit 2d1efa2110af8b0aa2b5aa641e61f8c906e02d38 Author: Andrey Mokhov Date: Tue Jan 5 11:39:38 2016 +0000 Temporarily disable haddock, see #98. >--------------------------------------------------------------- 2d1efa2110af8b0aa2b5aa641e61f8c906e02d38 src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 6107f6f..aba4a48 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -82,7 +82,7 @@ laxDependencies :: Bool laxDependencies = False buildHaddock :: Predicate -buildHaddock = return True +buildHaddock = return False -- FIXME: should be return True, see #98 buildSystemConfigFile :: Bool buildSystemConfigFile = False From git at git.haskell.org Thu Oct 26 23:37:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Collect arguments for Hsc2Hs builder. (f225aed) Message-ID: <20171026233730.96C073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f225aedc18efa02b48f99ee84d0794eb4aa94368/ghc >--------------------------------------------------------------- commit f225aedc18efa02b48f99ee84d0794eb4aa94368 Author: Andrey Mokhov Date: Mon Sep 21 00:54:29 2015 +0100 Collect arguments for Hsc2Hs builder. >--------------------------------------------------------------- f225aedc18efa02b48f99ee84d0794eb4aa94368 src/Settings/Builders/Hsc2Hs.hs | 70 +++++++++++++++++++++++++++++++++++++++++ 1 file changed, 70 insertions(+) diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs new file mode 100644 index 0000000..fae7c1f --- /dev/null +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -0,0 +1,70 @@ +module Settings.Builders.Hsc2Hs (hsc2HsArgs) where + +import Expression +import Oracles +import Predicates (builder, stage0, notStage0) +import Settings +import Settings.Builders.GhcCabal + +hsc2HsArgs :: Args +hsc2HsArgs = builder Hsc2Hs ? do + stage <- getStage + src <- getSource + file <- getFile + ccPath <- lift . builderPath $ Gcc stage + gmpDirs <- getSettingList GmpIncludeDirs + cFlags <- getCFlags + lFlags <- getLFlags + hArch <- getSetting HostArch + hOs <- getSetting HostOs + tArch <- getSetting TargetArch + tOs <- getSetting TargetOs + version <- if stage == Stage0 + then lift $ ghcCanonVersion + else getSetting ProjectVersionInt + mconcat [ arg $ "--cc=" ++ ccPath + , arg $ "--ld=" ++ ccPath + , notWindowsHost ? arg "--cross-safe" + , append $ map ("-I" ++) gmpDirs + , append $ map ("--cflag=" ++) cFlags + , append $ map ("--lflag=" ++) lFlags + , notStage0 ? crossCompiling ? arg "--cross-compile" + , stage0 ? arg ("--cflag=-D" ++ hArch ++ "_HOST_ARCH=1") + , stage0 ? arg ("--cflag=-D" ++ hOs ++ "_HOST_OS=1" ) + , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") + , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) + , arg ("--cflag=-D__GLASGOW_HASKELL__=" ++ version) + , arg src + , arg "-o", arg file ] + +getCFlags :: Expr [String] +getCFlags = fromDiffExpr $ do + pkg <- getPackage + path <- getTargetPath + iDirs <- getPkgDataList IncludeDirs + dDirs <- getPkgDataList DepIncludeDirs + cppArgs <- getPkgDataList CppArgs + depCcArgs <- getPkgDataList DepCcArgs + mconcat [ ccArgs + , argStagedSettingList ConfCcArgs + , remove ["-O"] + , argStagedSettingList ConfCppArgs + , arg $ "-I" ++ path -/- "build/autogen" + , append [ "-I" ++ pkgPath pkg -/- dir | dir <- iDirs ++ dDirs ] + , append cppArgs + , append depCcArgs + , ccWarnings + , arg "-include", arg $ path -/- "build/autogen/cabal_macros.h" ] + +getLFlags :: Expr [String] +getLFlags = fromDiffExpr $ do + ldArgs <- getPkgDataList LdArgs + libDirs <- getPkgDataList DepLibDirs + extraLibs <- getPkgDataList DepExtraLibs + depLdArgs <- getPkgDataList DepLdArgs + mconcat [ argStagedSettingList ConfGccLinkerArgs + --, ldArgs -- TODO: resolve name conflict (ldArgs is currently empty) + , append ldArgs + , append $ [ "-L" ++ unifyPath dir | dir <- libDirs ] + , append $ [ "-l" ++ unifyPath dir | dir <- extraLibs ] + , append depLdArgs ] From git at git.haskell.org Thu Oct 26 23:37:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix readlink for os x. (0b0e1d6) Message-ID: <20171026233730.EC3553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b0e1d68b1e58b23c2dff0edd0c4135e0cb3a583/ghc >--------------------------------------------------------------- commit 0b0e1d68b1e58b23c2dff0edd0c4135e0cb3a583 Author: Moritz Angermann Date: Tue Jan 5 20:43:29 2016 +0800 Fix readlink for os x. This should fix #104. >--------------------------------------------------------------- 0b0e1d68b1e58b23c2dff0edd0c4135e0cb3a583 build.sh | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 82cbb93..de9b9d7 100755 --- a/build.sh +++ b/build.sh @@ -1,8 +1,34 @@ #!/usr/bin/env bash +# readlink on os x, doesn't support -f, to prevent the +# need of installing coreutils (e.g. through brew, just +# for readlink, we use the follownig substitute. +# +# source: http://stackoverflow.com/a/1116890 +function rl { + TARGET_FILE=$1 + + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE=$(basename "$TARGET_FILE") + + # Iterate down a (possible) chain of symlinks + while [ -L "$TARGET_FILE" ] + do + TARGET_FILE=$(readlink "$TARGET_FILE") + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE=$(basename "$TARGET_FILE") + done + + # Compute the canonicalized name by finding the physical path + # for the directory we're in and appending the target file. + PHYS_DIR=`pwd -P` + RESULT=$PHYS_DIR/$TARGET_FILE + echo $RESULT +} + set -euo pipefail -root="$(dirname "$(readlink -f "$0")")" +root="$(dirname "$(rl "$0")")" mkdir -p "$root/.shake" From git at git.haskell.org Thu Oct 26 23:37:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more configuration flags. (b2928a3) Message-ID: <20171026233734.6E0DF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2928a32abf293f02f4ebe8efe6349e6fb73bc4a/ghc >--------------------------------------------------------------- commit b2928a32abf293f02f4ebe8efe6349e6fb73bc4a Author: Andrey Mokhov Date: Mon Sep 21 00:55:17 2015 +0100 Add more configuration flags. >--------------------------------------------------------------- b2928a32abf293f02f4ebe8efe6349e6fb73bc4a cfg/system.config.in | 16 +++++++++++----- 1 file changed, 11 insertions(+), 5 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index b92b6ba..6bfb20d 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -5,14 +5,14 @@ #=================== system-ghc = @WithGhc@ -system-gcc = @CC_STAGE0@ -system-ghc-pkg = @GhcPkgCmd@ -gcc = @WhatGccIsCalled@ - ghc-stage1 = @hardtop@/inplace/bin/ghc-stage1 ghc-stage2 = @hardtop@/inplace/bin/ghc-stage2 ghc-stage3 = @hardtop@/inplace/bin/ghc-stage3 +system-gcc = @CC_STAGE0@ +gcc = @WhatGccIsCalled@ + +system-ghc-pkg = @GhcPkgCmd@ ghc-pkg = @hardtop@/inplace/bin/ghc-pkg ghc-cabal = @hardtop@/inplace/bin/ghc-cabal @@ -49,13 +49,19 @@ target-os = @TargetOS_CPP@ target-arch = @TargetArch_CPP@ target-platform-full = @TargetPlatformFull@ -host-os-cpp = @HostOS_CPP@ +host-os = @HostOS_CPP@ +host-arch = @HostArch_CPP@ cross-compiling = @CrossCompiling@ dynamic-extension = @soext_target@ +ghc-major-version = @GhcMajVersion@ +ghc-minor-version = @GhcMinVersion@ +ghc-patch-level = @GhcPatchLevel@ + project-version = @ProjectVersion@ +project-version-int = @ProjectVersionInt@ # Compilation and linking flags: #=============================== From git at git.haskell.org Thu Oct 26 23:37:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds -no-hs-main to iservBin (8718da8) Message-ID: <20171026233734.ACF1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8718da8fe567d0ab9fa3b0f85726d73c9ed04cb3/ghc >--------------------------------------------------------------- commit 8718da8fe567d0ab9fa3b0f85726d73c9ed04cb3 Author: Moritz Angermann Date: Tue Jan 5 20:44:55 2016 +0800 Adds -no-hs-main to iservBin Fixes #102. But does not *yet* include the generation of the wrapper script. >--------------------------------------------------------------- 8718da8fe567d0ab9fa3b0f85726d73c9ed04cb3 shaking-up-ghc.cabal | 1 + src/Settings/Args.hs | 2 ++ src/Settings/Packages/IservBin.hs | 10 ++++++++++ 3 files changed, 13 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 2eb9f72..00fb408 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -87,6 +87,7 @@ executable ghc-shake , Settings.Packages.Haddock , Settings.Packages.Hp2ps , Settings.Packages.IntegerGmp + , Settings.Packages.IservBin , Settings.Packages.Rts , Settings.Packages.RunGhc , Settings.TargetDirectory diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index a677c80..fb121ed 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -27,6 +27,7 @@ import Settings.Packages.GhcPrim import Settings.Packages.Haddock import Settings.Packages.Hp2ps import Settings.Packages.IntegerGmp +import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc import Settings.User @@ -72,5 +73,6 @@ defaultPackageArgs = mconcat , haddockPackageArgs , hp2psPackageArgs , integerGmpPackageArgs + , iservBinPackageArgs , rtsPackageArgs , runGhcPackageArgs ] diff --git a/src/Settings/Packages/IservBin.hs b/src/Settings/Packages/IservBin.hs new file mode 100644 index 0000000..5ad3bd5 --- /dev/null +++ b/src/Settings/Packages/IservBin.hs @@ -0,0 +1,10 @@ +module Settings.Packages.IservBin (iservBinPackageArgs) where + +import Expression +import GHC (iservBin) +import Predicates (builderGhc, package) + +iservBinPackageArgs :: Args +iservBinPackageArgs = package iservBin ? do + mconcat [ builderGhc ? + mconcat [ arg "-no-hs-main" ]] From git at git.haskell.org Thu Oct 26 23:37:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on dead/duplicated code. (e68f4ed) Message-ID: <20171026233737.D288A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e68f4ed4d3fbba7228a5eb9c9419ec00ca93c8f5/ghc >--------------------------------------------------------------- commit e68f4ed4d3fbba7228a5eb9c9419ec00ca93c8f5 Author: Andrey Mokhov Date: Mon Sep 21 00:56:55 2015 +0100 Add a note on dead/duplicated code. >--------------------------------------------------------------- e68f4ed4d3fbba7228a5eb9c9419ec00ca93c8f5 doc/demo.txt | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/doc/demo.txt b/doc/demo.txt index 28b3689..2c8bf75 100644 --- a/doc/demo.txt +++ b/doc/demo.txt @@ -13,7 +13,9 @@ * https://mail.haskell.org/pipermail/ghc-commits/2013-May/001712.html * see ghc.mk, comment about parallel ghc-pkg invokations -5. Discovered dead code in the old build system, e.g: +5. Discovered dead & duplicated code in the old build system, e.g: -* Alex3 variable not needed as Alex 3.1 is required. -* There are no generated *.y/*.ly files, hence they can never be in the build directory. \ No newline at end of file +* Alex3 variable not needed as Alex 3.1 is required +* There are no generated *.y/*.ly files, hence they can never be in the build directory +* hsc2hs gets multuple "--cflag=-I$1/$2/build/autogen" flags in one invokation +* No generated Haskell files actually require copying of *.(l)hs-boot files \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:37:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #107 from angerman/feature/iserv (f4ef847) Message-ID: <20171026233738.2E7933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4ef847b4f4ea44ff8ceeefcdbe7fdb5dcaac336/ghc >--------------------------------------------------------------- commit f4ef847b4f4ea44ff8ceeefcdbe7fdb5dcaac336 Merge: 2d1efa2 8718da8 Author: Andrey Mokhov Date: Tue Jan 5 12:52:41 2016 +0000 Merge pull request #107 from angerman/feature/iserv Adds -no-hs-main to iservBin >--------------------------------------------------------------- f4ef847b4f4ea44ff8ceeefcdbe7fdb5dcaac336 shaking-up-ghc.cabal | 1 + src/Settings/Args.hs | 2 ++ src/Settings/Packages/IservBin.hs | 10 ++++++++++ 3 files changed, 13 insertions(+) From git at git.haskell.org Thu Oct 26 23:37:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for empty YES/NO flags (treat empty as NO). (8b1feb5) Message-ID: <20171026233741.50F7F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8b1feb5b13fc1c9848f2f0e39f271e5c1fb39c27/ghc >--------------------------------------------------------------- commit 8b1feb5b13fc1c9848f2f0e39f271e5c1fb39c27 Author: Andrey Mokhov Date: Mon Sep 21 00:57:40 2015 +0100 Add support for empty YES/NO flags (treat empty as NO). >--------------------------------------------------------------- 8b1feb5b13fc1c9848f2f0e39f271e5c1fb39c27 src/Oracles/Config/Flag.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index b73a687..d520a85 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -16,6 +16,8 @@ data Flag = CrossCompiling | SplitObjectsBroken | SupportsPackageKey +-- Note, if a flag is set to empty string we treat it as set to NO. This seems +-- fragile, but some flags do behave like this, e.g. GccIsClang. flag :: Flag -> Action Bool flag f = do key <- return $ case f of @@ -28,7 +30,7 @@ flag f = do SupportsPackageKey -> "supports-package-key" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." - unless (value == "YES" || value == "NO") . putError + unless (value == "YES" || value == "NO" || value == "") . putError $ "\nFlag '" ++ key ++ "' is set to '" ++ value ++ "' instead of 'YES' or 'NO'." return $ value == "YES" From git at git.haskell.org Thu Oct 26 23:37:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds quotes. (a1f3c8d) Message-ID: <20171026233741.A35003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1f3c8df8f27422eef777f4b9ff4e6a844c88532/ghc >--------------------------------------------------------------- commit a1f3c8df8f27422eef777f4b9ff4e6a844c88532 Author: Moritz Angermann Date: Tue Jan 5 20:54:18 2016 +0800 Adds quotes. >--------------------------------------------------------------- a1f3c8df8f27422eef777f4b9ff4e6a844c88532 build.sh | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/build.sh b/build.sh index de9b9d7..a3f0bf5 100755 --- a/build.sh +++ b/build.sh @@ -1,33 +1,33 @@ #!/usr/bin/env bash +set -euo pipefail + # readlink on os x, doesn't support -f, to prevent the # need of installing coreutils (e.g. through brew, just # for readlink, we use the follownig substitute. # # source: http://stackoverflow.com/a/1116890 function rl { - TARGET_FILE=$1 + TARGET_FILE="$1" cd "$(dirname "$TARGET_FILE")" - TARGET_FILE=$(basename "$TARGET_FILE") + TARGET_FILE="$(basename "$TARGET_FILE")" # Iterate down a (possible) chain of symlinks while [ -L "$TARGET_FILE" ] do - TARGET_FILE=$(readlink "$TARGET_FILE") + TARGET_FILE="$(readlink "$TARGET_FILE")" cd "$(dirname "$TARGET_FILE")" - TARGET_FILE=$(basename "$TARGET_FILE") + TARGET_FILE="$(basename "$TARGET_FILE")" done # Compute the canonicalized name by finding the physical path # for the directory we're in and appending the target file. - PHYS_DIR=`pwd -P` - RESULT=$PHYS_DIR/$TARGET_FILE - echo $RESULT + PHYS_DIR="$(pwd -P)" + RESULT="$PHYS_DIR/$TARGET_FILE" + echo "$RESULT" } -set -euo pipefail - root="$(dirname "$(rl "$0")")" mkdir -p "$root/.shake" From git at git.haskell.org Thu Oct 26 23:37:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for Alex, Happy and Hsc2Hs builders. (1e13a6e) Message-ID: <20171026233744.B70753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1e13a6e1021c8354a86af9ea4cba7e3c2ce1bc65/ghc >--------------------------------------------------------------- commit 1e13a6e1021c8354a86af9ea4cba7e3c2ce1bc65 Author: Andrey Mokhov Date: Mon Sep 21 00:58:19 2015 +0100 Add support for Alex, Happy and Hsc2Hs builders. >--------------------------------------------------------------- 1e13a6e1021c8354a86af9ea4cba7e3c2ce1bc65 src/Rules/Actions.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 4285831..f261b4f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -39,15 +39,18 @@ build = buildWithResources [] interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of + Alex -> prefixAndSuffix 0 3 ss Ar -> prefixAndSuffix 2 1 ss - Ld -> prefixAndSuffix 4 0 ss Gcc _ -> prefixAndSuffix 0 4 ss GccM _ -> prefixAndSuffix 0 1 ss Ghc _ -> prefixAndSuffix 0 4 ss + GhcCabal -> prefixAndSuffix 3 0 ss GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss Haddock -> prefixAndSuffix 1 0 ss - GhcCabal -> prefixAndSuffix 3 0 ss + Happy -> prefixAndSuffix 0 3 ss + Hsc2Hs -> prefixAndSuffix 0 3 ss + Ld -> prefixAndSuffix 4 0 ss _ -> ss where prefixAndSuffix n m list = From git at git.haskell.org Thu Oct 26 23:37:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add hsc2HsArgs to global settings. (330dcdb) Message-ID: <20171026233748.23EEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/330dcdbf2b5f84e658fbbe4c540492c7b03c6951/ghc >--------------------------------------------------------------- commit 330dcdbf2b5f84e658fbbe4c540492c7b03c6951 Author: Andrey Mokhov Date: Mon Sep 21 00:58:57 2015 +0100 Add hsc2HsArgs to global settings. >--------------------------------------------------------------- 330dcdbf2b5f84e658fbbe4c540492c7b03c6951 src/Settings/Args.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 2e2f379..97933fa 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -9,6 +9,7 @@ import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg import Settings.Builders.Haddock import Settings.Builders.Happy +import Settings.Builders.Hsc2Hs import Settings.Builders.Ld import Settings.User @@ -37,4 +38,5 @@ defaultArgs = mconcat , gccMArgs , haddockArgs , happyArgs + , hsc2HsArgs , ldArgs ] From git at git.haskell.org Thu Oct 26 23:37:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add rl function to the cabal build file as well. (2c635d5) Message-ID: <20171026233745.126BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c635d55d07ddeb2f827dd5d3007fc9b362b043a/ghc >--------------------------------------------------------------- commit 2c635d55d07ddeb2f827dd5d3007fc9b362b043a Author: Moritz Angermann Date: Tue Jan 5 20:58:07 2016 +0800 Add rl function to the cabal build file as well. >--------------------------------------------------------------- 2c635d55d07ddeb2f827dd5d3007fc9b362b043a build.cabal.sh | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index cf165b8..8add516 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -2,7 +2,33 @@ set -euo pipefail -absoltueRoot="$(dirname "$(readlink -f "$0")")" +# readlink on os x, doesn't support -f, to prevent the +# need of installing coreutils (e.g. through brew, just +# for readlink, we use the follownig substitute. +# +# source: http://stackoverflow.com/a/1116890 +function rl { + TARGET_FILE="$1" + + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE="$(basename "$TARGET_FILE")" + + # Iterate down a (possible) chain of symlinks + while [ -L "$TARGET_FILE" ] + do + TARGET_FILE="$(readlink "$TARGET_FILE")" + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE="$(basename "$TARGET_FILE")" + done + + # Compute the canonicalized name by finding the physical path + # for the directory we're in and appending the target file. + PHYS_DIR="$(pwd -P)" + RESULT="$PHYS_DIR/$TARGET_FILE" + echo "$RESULT" +} + +absoltueRoot="$(dirname "$(rl "$0")")" cd "$absoltueRoot" # Initialize sandbox if necessary From git at git.haskell.org Thu Oct 26 23:37:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: -Augenkrebs (e17f0e6) Message-ID: <20171026233748.70F8E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e17f0e6575bf53cc23e966e343b32e0fc4705c86/ghc >--------------------------------------------------------------- commit e17f0e6575bf53cc23e966e343b32e0fc4705c86 Author: Moritz Angermann Date: Tue Jan 5 20:58:38 2016 +0800 -Augenkrebs >--------------------------------------------------------------- e17f0e6575bf53cc23e966e343b32e0fc4705c86 build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index a3f0bf5..719e85e 100755 --- a/build.sh +++ b/build.sh @@ -39,7 +39,7 @@ ghc \ -rtsopts \ -with-rtsopts=-I0 \ -outputdir="$root/.shake" \ - -j -O \ + -j -O \ -o "$root/.shake/build" "$root/.shake/build" \ From git at git.haskell.org Thu Oct 26 23:37:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify paths of sources and files in a target. (00de798) Message-ID: <20171026233752.46FED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/00de798905ba76aaa6f034b0b7110fe1c4be3acb/ghc >--------------------------------------------------------------- commit 00de798905ba76aaa6f034b0b7110fe1c4be3acb Author: Andrey Mokhov Date: Mon Sep 21 00:59:34 2015 +0100 Unify paths of sources and files in a target. >--------------------------------------------------------------- 00de798905ba76aaa6f034b0b7110fe1c4be3acb src/Target.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Target.hs b/src/Target.hs index 2901ffe..8e2a44e 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -60,8 +60,8 @@ fullTarget (PartialTarget s p) b srcs fs = Target package = p, builder = b, way = vanilla, - sources = srcs, - files = fs + sources = map unifyPath srcs, + files = map unifyPath fs } -- Use this function to be explicit about the build way. From git at git.haskell.org Thu Oct 26 23:37:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #106 from angerman/feature/broken-osx-readlink (5517cb0) Message-ID: <20171026233752.761803A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5517cb05c724c86d04f526c933e94c6a54ba2e18/ghc >--------------------------------------------------------------- commit 5517cb05c724c86d04f526c933e94c6a54ba2e18 Merge: f4ef847 e17f0e6 Author: Andrey Mokhov Date: Tue Jan 5 13:02:14 2016 +0000 Merge pull request #106 from angerman/feature/broken-osx-readlink Fix readlink for os x [skip ci] >--------------------------------------------------------------- 5517cb05c724c86d04f526c933e94c6a54ba2e18 build.cabal.sh | 28 +++++++++++++++++++++++++++- build.sh | 30 ++++++++++++++++++++++++++++-- 2 files changed, 55 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:37:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (738bac8) Message-ID: <20171026233755.D0FCD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/738bac8ccaa266a76a1a21ccb1ff1f8cbe785a70/ghc >--------------------------------------------------------------- commit 738bac8ccaa266a76a1a21ccb1ff1f8cbe785a70 Author: Andrey Mokhov Date: Mon Sep 21 01:00:48 2015 +0100 Clean up. >--------------------------------------------------------------- 738bac8ccaa266a76a1a21ccb1ff1f8cbe785a70 src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 10 ++++++++-- src/Settings/Builders/Happy.hs | 2 +- 3 files changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs index 6aedcdb..1e0f87b 100644 --- a/src/Settings/Builders/Alex.hs +++ b/src/Settings/Builders/Alex.hs @@ -6,8 +6,8 @@ import Predicates (builder, package) alexArgs :: Args alexArgs = builder Alex ? do - file <- getFile src <- getSource + file <- getFile mconcat [ arg "-g" , package compiler ? arg "--latin1" , arg src diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index dd54097..ab65a51 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,5 +1,6 @@ module Settings.Builders.GhcCabal ( - cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs + cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, + ccArgs, ccWarnings, argStagedSettingList ) where import Expression @@ -54,6 +55,7 @@ libraryArgs = do then "--enable-shared" else "--disable-shared" ] +-- TODO: LD_OPTS? configureArgs :: Args configureArgs = do let conf key = appendSubD $ "--configure-option=" ++ key @@ -94,7 +96,11 @@ packageConstraints = stage0 ? do -- TODO: should be in a different file -- TODO: put all validating options together in one file ccArgs :: Args -ccArgs = validating ? do +ccArgs = validating ? ccWarnings + +-- TODO: should be in a different file +ccWarnings :: Args +ccWarnings = do let notClang = fmap not gccIsClang mconcat [ arg "-Werror" , arg "-Wall" diff --git a/src/Settings/Builders/Happy.hs b/src/Settings/Builders/Happy.hs index fcd962a..685c30d 100644 --- a/src/Settings/Builders/Happy.hs +++ b/src/Settings/Builders/Happy.hs @@ -5,8 +5,8 @@ import Predicates (builder) happyArgs :: Args happyArgs = builder Happy ? do - file <- getFile src <- getSource + file <- getFile mconcat [ arg "-agc" , arg "--strict" , arg src From git at git.haskell.org Thu Oct 26 23:37:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make ghc-cabal build parallel [skip ci]. (83c73a2) Message-ID: <20171026233756.125903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/83c73a2bd507915d2a655e5c6148ec92c8a9e9a5/ghc >--------------------------------------------------------------- commit 83c73a2bd507915d2a655e5c6148ec92c8a9e9a5 Author: Andrey Mokhov Date: Tue Jan 5 14:02:21 2016 +0000 Make ghc-cabal build parallel [skip ci]. >--------------------------------------------------------------- 83c73a2bd507915d2a655e5c6148ec92c8a9e9a5 src/Settings/Packages/GhcCabal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 67fa5b4..f1a7373 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -23,6 +23,7 @@ ghcCabalBootArgs = stage0 ? do [ remove ["-hide-all-packages"] , removePair "-optP-include" $ "-optP" ++ cabalMacros , arg "--make" + , arg "-j" , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" , arg "-DGENERICS" From git at git.haskell.org Thu Oct 26 23:37:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track generated sources. (44f7b51) Message-ID: <20171026233759.99FD03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44f7b51095e7d4c151eef50c6f6180b27efa4aa1/ghc >--------------------------------------------------------------- commit 44f7b51095e7d4c151eef50c6f6180b27efa4aa1 Author: Andrey Mokhov Date: Mon Sep 21 01:01:13 2015 +0100 Track generated sources. >--------------------------------------------------------------- 44f7b51095e7d4c151eef50c6f6180b27efa4aa1 src/Rules/Compile.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 3940d64..90712ce 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -19,7 +19,7 @@ compilePackage _ target @ (PartialTarget stage package) = do matchBuildResult buildPath "o" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need deps + need $ src : deps if ("//*.c" ?== src) then build $ fullTarget target (Gcc stage) [src] [obj] else do @@ -28,6 +28,6 @@ compilePackage _ target @ (PartialTarget stage package) = do matchBuildResult buildPath "o-boot" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need deps + need $ src : deps let way = detectWay obj build $ fullTargetWithWay target (Ghc stage) way [src] [obj] From git at git.haskell.org Thu Oct 26 23:37:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:37:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Separate build messages with a newline. (ff676fc) Message-ID: <20171026233759.C6C013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff676fcbb1e7f1956d94de28bd3fba9ddce40312/ghc >--------------------------------------------------------------- commit ff676fcbb1e7f1956d94de28bd3fba9ddce40312 Author: Andrey Mokhov Date: Tue Jan 5 16:59:41 2016 +0000 Separate build messages with a newline. >--------------------------------------------------------------- ff676fcbb1e7f1956d94de28bd3fba9ddce40312 src/Rules/Actions.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 6f116b5..d567747 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -71,7 +71,7 @@ copyFile source target = do createDirectory :: FilePath -> Action () createDirectory dir = do - putBuild $ "| Create directory " ++ dir + putBuild $ "\n| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir -- Note, the source directory is untracked @@ -85,7 +85,7 @@ moveDirectory source target = do -- Transform a given file by applying a function to its contents fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do - putBuild $ "| Fix " ++ file + putBuild $ "\n| Fix " ++ file old <- liftIO $ readFile file let new = f old length new `seq` liftIO $ writeFile file new @@ -93,14 +93,14 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] - putBuild $ "| Run configure in " ++ dir ++ "..." + putBuild $ "\n| Run configure in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." + putBuild $ "\n| Run make" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args runBuilder :: Builder -> [String] -> Action () @@ -108,7 +108,7 @@ runBuilder builder args = do needBuilder laxDependencies builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "| Run " ++ show builder ++ note + putBuild $ "\n| Run " ++ show builder ++ note quietly $ cmd [path] args -- Print out key information about the command being executed From git at git.haskell.org Thu Oct 26 23:38:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for new keys in package-data files. (13708d7) Message-ID: <20171026233803.C6E153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13708d7313bb91ea60e4129d2e6b0f2bcec4ad8e/ghc >--------------------------------------------------------------- commit 13708d7313bb91ea60e4129d2e6b0f2bcec4ad8e Author: Andrey Mokhov Date: Mon Sep 21 01:01:59 2015 +0100 Add support for new keys in package-data files. >--------------------------------------------------------------- 13708d7313bb91ea60e4129d2e6b0f2bcec4ad8e src/Oracles/PackageData.hs | 58 +++++++++++++++++++++++++++------------------- 1 file changed, 34 insertions(+), 24 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index e3c1eb5..22031b1 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -15,24 +15,29 @@ import qualified Data.HashMap.Strict as Map -- PackageDataList is used for multiple string options separated by spaces, -- such as 'path_MODULES = Data.Array Data.Array.Base ...'. -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] -data PackageData = Version FilePath - | PackageKey FilePath +data PackageData = BuildGhciLib FilePath | LibName FilePath + | PackageKey FilePath | Synopsis FilePath - | BuildGhciLib FilePath + | Version FilePath -data PackageDataList = Modules FilePath - | HiddenModules FilePath - | SrcDirs FilePath - | IncludeDirs FilePath - | Deps FilePath +data PackageDataList = CcArgs FilePath + | CSrcs FilePath + | CppArgs FilePath + | DepCcArgs FilePath + | DepExtraLibs FilePath | DepIds FilePath + | DepIncludeDirs FilePath + | DepLdArgs FilePath + | DepLibDirs FilePath | DepNames FilePath - | CppArgs FilePath + | Deps FilePath + | HiddenModules FilePath | HsArgs FilePath - | CcArgs FilePath - | CSrcs FilePath - | DepIncludeDirs FilePath + | IncludeDirs FilePath + | LdArgs FilePath + | Modules FilePath + | SrcDirs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -48,26 +53,31 @@ askPackageData path key = do pkgData :: PackageData -> Action String pkgData packageData = case packageData of - Version path -> askPackageData path "VERSION" - PackageKey path -> askPackageData path "PACKAGE_KEY" + BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" LibName path -> askPackageData path "LIB_NAME" + PackageKey path -> askPackageData path "PACKAGE_KEY" Synopsis path -> askPackageData path "SYNOPSIS" - BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" + Version path -> askPackageData path "VERSION" pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = fmap (map unquote . words) $ case packageData of - Modules path -> askPackageData path "MODULES" - HiddenModules path -> askPackageData path "HIDDEN_MODULES" - SrcDirs path -> askPackageData path "HS_SRC_DIRS" - IncludeDirs path -> askPackageData path "INCLUDE_DIRS" - Deps path -> askPackageData path "DEPS" - DepIds path -> askPackageData path "DEP_IPIDS" - DepNames path -> askPackageData path "DEP_NAMES" - CppArgs path -> askPackageData path "CPP_OPTS" - HsArgs path -> askPackageData path "HC_OPTS" CcArgs path -> askPackageData path "CC_OPTS" CSrcs path -> askPackageData path "C_SRCS" + CppArgs path -> askPackageData path "CPP_OPTS" + DepCcArgs path -> askPackageData path "DEP_CC_OPTS" + DepExtraLibs path -> askPackageData path "DEP_EXTRA_LIBS" + DepIds path -> askPackageData path "DEP_IPIDS" DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" + DepLibDirs path -> askPackageData path "DEP_LIB_DIRS_SINGLE_QUOTED" + DepLdArgs path -> askPackageData path "DEP_LD_OPTS" + DepNames path -> askPackageData path "DEP_NAMES" + Deps path -> askPackageData path "DEPS" + HiddenModules path -> askPackageData path "HIDDEN_MODULES" + HsArgs path -> askPackageData path "HC_OPTS" + IncludeDirs path -> askPackageData path "INCLUDE_DIRS" + LdArgs path -> askPackageData path "LD_OPTS" + Modules path -> askPackageData path "MODULES" + SrcDirs path -> askPackageData path "HS_SRC_DIRS" where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') From git at git.haskell.org Thu Oct 26 23:38:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor libffi rules. (709026d) Message-ID: <20171026233804.4250A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/709026de4920d45ad83a9e6a98153b9328533d1a/ghc >--------------------------------------------------------------- commit 709026de4920d45ad83a9e6a98153b9328533d1a Author: Andrey Mokhov Date: Tue Jan 5 17:00:37 2016 +0000 Refactor libffi rules. >--------------------------------------------------------------- 709026de4920d45ad83a9e6a98153b9328533d1a src/Rules/Copy.hs | 14 -------------- src/Rules/Libffi.hs | 26 +++++++++++++++++++------- 2 files changed, 19 insertions(+), 21 deletions(-) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index b1f9760..7454fd9 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -5,9 +5,6 @@ import Expression import GHC import Rules.Actions import Rules.Generate -import Rules.Libffi -import Settings.Packages.Rts -import Settings.TargetDirectory installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" @@ -16,17 +13,6 @@ installTargets = [ "inplace/lib/template-hsc.h" copyRules :: Rules () copyRules = do - targetPath Stage1 rts -/- "build/ffi*.h" %> \ffih -> do - need [libffiLibrary] - ffiHPaths <- getDirectoryFiles "" ["libffi/build/inst/lib/*/include/ffi.h"] - when (length ffiHPaths /= 1) $ - putError $ "copyRules: exactly one ffi.h header expected" - ++ "(found: " ++ show ffiHPaths ++ ")." - - copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih - libffiName <- rtsLibffiLibraryName - copyFile libffiLibrary (targetPath Stage1 rts -/- "build/lib" ++ libffiName <.> "a") - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 603b35f..041650f 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,4 +1,4 @@ -module Rules.Libffi (libffiRules, libffiLibrary) where +module Rules.Libffi (libffiRules, libffiDependencies) where import Base import Expression @@ -6,15 +6,22 @@ import GHC import Oracles import Rules.Actions import Settings.Builders.Common +import Settings.Packages.Rts +import Settings.TargetDirectory import Settings.User --- We use this file to track the whole libffi library -libffiLibrary :: FilePath -libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" +rtsBuildPath :: FilePath +rtsBuildPath = targetPath Stage1 rts -/- "build" + +libffiDependencies :: [FilePath] +libffiDependencies = (rtsBuildPath -/-) <$> [ "ffi.h", "ffitarget.h" ] libffiBuild :: FilePath libffiBuild = "libffi/build" +libffiLibrary :: FilePath +libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" + libffiMakefile :: FilePath libffiMakefile = libffiBuild -/- "Makefile.in" @@ -61,7 +68,7 @@ configureArguments = do libffiRules :: Rules () libffiRules = do - libffiLibrary %> \_ -> do + libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] @@ -87,9 +94,14 @@ libffiRules = do runMake libffiBuild [] runMake libffiBuild ["install"] - putSuccess $ "| Successfully built custom library 'libffi'" + forM_ ["ffi.h", "ffitarget.h"] $ \file -> do + let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file + copyFile src (rtsBuildPath -/- file) - "libffi/build/inst/lib/*/include/*.h" %> \_ -> need [libffiLibrary] + libffiName <- rtsLibffiLibraryName + copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") + + putSuccess $ "| Successfully built custom library 'libffi'" -- chmod +x libffi/ln -- # wc on OS X has spaces in its output, which libffi's Makefile From git at git.haskell.org Thu Oct 26 23:38:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for new configuration flags. (8e74ca7) Message-ID: <20171026233807.A2DE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e74ca7b158cb0a3fd7413b1b6646fa2cdbcb1a7/ghc >--------------------------------------------------------------- commit 8e74ca7b158cb0a3fd7413b1b6646fa2cdbcb1a7 Author: Andrey Mokhov Date: Mon Sep 21 01:02:39 2015 +0100 Add support for new configuration flags. >--------------------------------------------------------------- 8e74ca7b158cb0a3fd7413b1b6646fa2cdbcb1a7 src/Oracles/Config/Setting.hs | 55 ++++++++++++++++++++++++++++--------------- 1 file changed, 36 insertions(+), 19 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index f0f7fb7..a01a7fa 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -3,7 +3,7 @@ module Oracles.Config.Setting ( setting, settingList, getSetting, getSettingList, targetPlatform, targetPlatforms, targetOs, targetOss, notTargetOs, targetArchs, windowsHost, notWindowsHost, ghcWithInterpreter, - ghcEnableTablesNextToCode, cmdLineLengthLimit + ghcEnableTablesNextToCode, ghcCanonVersion, cmdLineLengthLimit ) where import Base @@ -16,32 +16,42 @@ import Stage -- SettingList is used for multiple string values separated by spaces, such -- as 'gmp-include-dirs = a b'. -- settingList GmpIncludeDirs therefore returns a list of strings ["a", "b"]. -data Setting = TargetOs +data Setting = DynamicExtension + | GhcMajorVersion + | GhcMinorVersion + | GhcPatchLevel + | GhcSourcePath + | HostArch + | HostOs + | ProjectVersion + | ProjectVersionInt | TargetArch + | TargetOs | TargetPlatformFull - | HostOsCpp - | DynamicExtension - | ProjectVersion - | GhcSourcePath data SettingList = ConfCcArgs Stage + | ConfCppArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage - | ConfCppArgs Stage - | IconvIncludeDirs - | IconvLibDirs | GmpIncludeDirs | GmpLibDirs + | IconvIncludeDirs + | IconvLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of - TargetOs -> "target-os" - TargetArch -> "target-arch" - TargetPlatformFull -> "target-platform-full" - HostOsCpp -> "host-os-cpp" DynamicExtension -> "dynamic-extension" - ProjectVersion -> "project-version" + GhcMajorVersion -> "ghc-major-version" + GhcMinorVersion -> "ghc-minor-version" + GhcPatchLevel -> "ghc-patch-level" GhcSourcePath -> "ghc-source-path" + HostArch -> "host-arch" + HostOs -> "host-os" + ProjectVersion -> "project-version" + ProjectVersionInt -> "project-version-int" + TargetArch -> "target-arch" + TargetOs -> "target-os" + TargetPlatformFull -> "target-platform-full" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -49,10 +59,10 @@ settingList key = fmap words $ askConfig $ case key of ConfCppArgs stage -> "conf-cpp-args-stage" ++ show stage ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show stage ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show stage - IconvIncludeDirs -> "iconv-include-dirs" - IconvLibDirs -> "iconv-lib-dirs" GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" + IconvIncludeDirs -> "iconv-include-dirs" + IconvLibDirs -> "iconv-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting @@ -84,9 +94,7 @@ targetArchs :: [String] -> Action Bool targetArchs = matchSetting TargetArch windowsHost :: Action Bool -windowsHost = do - hostOsCpp <- setting HostOsCpp - return $ hostOsCpp `elem` ["mingw32", "cygwin32"] +windowsHost = matchSetting HostOs ["mingw32", "cygwin32"] notWindowsHost :: Action Bool notWindowsHost = fmap not windowsHost @@ -103,6 +111,15 @@ ghcWithInterpreter = do ghcEnableTablesNextToCode :: Action Bool ghcEnableTablesNextToCode = targetArchs ["ia64", "powerpc64"] +-- Canonicalised GHC version number, used for integer version comparisons. We +-- expand GhcMinorVersion to two digits by adding a leading zero if necessary. +ghcCanonVersion :: Action String +ghcCanonVersion = do + ghcMajorVersion <- setting GhcMajorVersion + ghcMinorVersion <- setting GhcMinorVersion + let leadingZero = [ '0' | length ghcMinorVersion == 1 ] + return $ ghcMajorVersion ++ leadingZero ++ ghcMinorVersion + -- Command lines have limited size on Windows. Since Windows 7 the limit is -- 32768 characters (theoretically). In practice we use 31000 to leave some -- breathing space for the builder's path & name, auxiliary flags, and other From git at git.haskell.org Thu Oct 26 23:38:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix integer-gmp problem on Travis, see #103. (ae6f58d) Message-ID: <20171026233808.17C293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8/ghc >--------------------------------------------------------------- commit ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8 Author: Andrey Mokhov Date: Tue Jan 5 17:02:55 2016 +0000 Attempt to fix integer-gmp problem on Travis, see #103. >--------------------------------------------------------------- ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8 src/Rules/Generate.hs | 16 ++++++---------- src/Rules/IntegerGmp.hs | 48 ++++++++++++++++++++++++++++++++---------------- src/Rules/Library.hs | 8 ++++++-- 3 files changed, 44 insertions(+), 28 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 921c672..2b33a53 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -14,6 +14,8 @@ import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles import Rules.Actions +import Rules.IntegerGmp +import Rules.Libffi import Rules.Resources (Resources) import Settings import Settings.Builders.DeriveConstants @@ -33,13 +35,12 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -libffiDependencies :: [FilePath] -libffiDependencies = (targetPath Stage1 rts -/-) <$> - [ "build/ffi.h" - , "build/ffitarget.h" ] +integerGmpDependencies :: [FilePath] +integerGmpDependencies = [integerGmpLibraryH] defaultDependencies :: [FilePath] -defaultDependencies = includesDependencies ++ libffiDependencies +defaultDependencies = + includesDependencies ++ libffiDependencies ++ integerGmpDependencies derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = (derivedConstantsPath -/-) <$> @@ -69,15 +70,10 @@ compilerDependencies stage = , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] -integerGmpDependencies :: [FilePath] -integerGmpDependencies = ((pkgPath integerGmp -/- "gmp") -/-) <$> - [ "gmp.h" ] -- identical to integerGmpLibraryH, but doesn't require the import. - generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == rts = derivedConstantsDependencies - | pkg == integerGmp = integerGmpDependencies | stage == Stage0 = defaultDependencies | otherwise = [] diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 9bbf482..91ca074 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,4 +1,4 @@ -module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary, integerGmpLibraryH) where +module Rules.IntegerGmp (integerGmpRules, integerGmpObjects, integerGmpLibraryH) where import Base import Expression @@ -8,16 +8,25 @@ import Rules.Actions import Settings.User integerGmpBase :: FilePath -integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp" +integerGmpBase = "libraries/integer-gmp/gmp" integerGmpBuild :: FilePath integerGmpBuild = integerGmpBase -/- "gmpbuild" +integerGmpObjects :: FilePath +integerGmpObjects = integerGmpBase -/- "objs" + integerGmpLibrary :: FilePath integerGmpLibrary = integerGmpBase -/- "libgmp.a" +integerGmpLibraryInTreeH :: FilePath +integerGmpLibraryInTreeH = integerGmpBase -/- "gmp.h" + integerGmpLibraryH :: FilePath -integerGmpLibraryH = integerGmpBase -/- "gmp.h" +integerGmpLibraryH = pkgPath integerGmp -/- "include/ghc-gmp.h" + +integerGmpLibraryFakeH :: FilePath +integerGmpLibraryFakeH = integerGmpBase -/- "ghc-gmp.h" -- relative to integerGmpBuild integerGmpPatch :: FilePath @@ -49,12 +58,14 @@ configureArguments = do -- TODO: we rebuild integer-gmp every time. integerGmpRules :: Rules () integerGmpRules = do - integerGmpLibrary %> \_ -> do + + -- TODO: split into multiple rules + integerGmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/IntegerGmp.hs"] -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] - liftIO $ removeFiles (integerGmpBase -/- "objs") ["//*"] + liftIO $ removeFiles (integerGmpObjects) ["//*"] -- unpack the gmp tarball. -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is @@ -91,19 +102,24 @@ integerGmpRules = do args <- configureArguments runConfigure integerGmpBuild envs args - runMake integerGmpBuild [] + -- check whether we need to build in tree gmp + -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` + configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" + if "HaveFrameworkGMP = YES" `isInfixOf` configMk + then do + putBuild "\n| GMP framework detected and will be used" + copyFile integerGmpLibraryFakeH integerGmpLibraryH + else do + putBuild "\n| No GMP framework detected" + runMake integerGmpBuild [] - -- copy library and header - -- TODO: why copy library, can we move it instead? - forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> - copyFile (integerGmpBuild -/- file) (integerGmpBase -/- takeFileName file) + copyFile integerGmpLibraryInTreeH integerGmpLibraryH + -- TODO: why copy library, can we move it instead? + copyFile (integerGmpBuild -/- ".libs/libgmp.a") integerGmpLibrary - let objsDir = integerGmpBase -/- "objs" - createDirectory objsDir - build $ fullTarget target Ar [integerGmpLibrary] [objsDir] + createDirectory integerGmpObjects + build $ fullTarget target Ar [integerGmpLibrary] [integerGmpObjects] - runBuilder Ranlib [integerGmpLibrary] + runBuilder Ranlib [integerGmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" - - integerGmpLibraryH %> \_ -> need [integerGmpLibrary] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index d9a1a48..41e7b3d 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -79,6 +79,10 @@ hSources target = do extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do - need [integerGmpLibrary] - getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] + need [integerGmpLibraryH] + objsExist <- doesDirectoryExist integerGmpObjects + putBuild $ "objsExist = " ++ show objsExist + if objsExist + then getDirectoryFiles "" [integerGmpObjects -/- "*.o"] + else return [] | otherwise = return [] From git at git.haskell.org Thu Oct 26 23:38:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish Generate rule. (f7ee775) Message-ID: <20171026233811.1418D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f7ee77565aa3b16f2911f99b7ef14059c16f9534/ghc >--------------------------------------------------------------- commit f7ee77565aa3b16f2911f99b7ef14059c16f9534 Author: Andrey Mokhov Date: Mon Sep 21 01:03:02 2015 +0100 Finish Generate rule. >--------------------------------------------------------------- f7ee77565aa3b16f2911f99b7ef14059c16f9534 src/Rules/Generate.hs | 22 ++-------------------- 1 file changed, 2 insertions(+), 20 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 055dccb..535f99b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -23,33 +23,15 @@ generatePackageCode _ target @ (PartialTarget stage package) = let path = targetPath stage package packagePath = pkgPath package buildPath = path -/- "build" - in do + in do -- TODO: do we need to copy *.(l)hs-boot files here? Never happens? buildPath "*.hs" %> \file -> do dirs <- interpretPartial target $ getPkgDataList SrcDirs files <- getDirectoryFiles "" $ [ packagePath d takeBaseName file <.> "*" | d <- dirs ] let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] - (src, builder) = head gens when (length gens /= 1) . putError $ "Exactly one generator expected for " ++ file ++ "(found: " ++ show gens ++ ")." + let (src, builder) = head gens need [src] build $ fullTarget target builder [src] [file] - --- $1/$2/build/%.hs : $1/$3/%.ly | $$$$(dir $$$$@)/. --- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ - --- $1/$2/build/%.hs : $1/$3/%.y | $$$$(dir $$$$@)/. --- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ - --- $1/$2/build/%_hsc.c $1/$2/build/%_hsc.h $1/$2/build/%.hs : $1/$3/%.hsc $$$$(hsc2hs_INPLACE) | $$$$(dir $$$$@)/. --- $$(call cmd,hsc2hs_INPLACE) $$($1_$2_ALL_HSC2HS_OPTS) $$< -o $$@ - --- # Now the rules for hs-boot files. - --- $1/$2/build/%.hs-boot : $1/$3/%.hs-boot --- "$$(CP)" $$< $$@ - --- $1/$2/build/%.lhs-boot : $1/$3/%.lhs-boot --- "$$(CP)" $$< $$@ - From git at git.haskell.org Thu Oct 26 23:38:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Force integerGmp package to be configured before reading config.mk file, see #103. (a33ab01) Message-ID: <20171026233811.871403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a33ab012f0e9e997035d7bd6c3ce0535cc9cbed2/ghc >--------------------------------------------------------------- commit a33ab012f0e9e997035d7bd6c3ce0535cc9cbed2 Author: Andrey Mokhov Date: Tue Jan 5 19:35:34 2016 +0000 Force integerGmp package to be configured before reading config.mk file, see #103. >--------------------------------------------------------------- a33ab012f0e9e997035d7bd6c3ce0535cc9cbed2 src/Rules/IntegerGmp.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 91ca074..f86371c 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -6,6 +6,7 @@ import GHC import Oracles.Config.Setting import Rules.Actions import Settings.User +import Settings.TargetDirectory integerGmpBase :: FilePath integerGmpBase = "libraries/integer-gmp/gmp" @@ -104,6 +105,7 @@ integerGmpRules = do -- check whether we need to build in tree gmp -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` + need [pkgDataFile Stage1 integerGmp] configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk then do From git at git.haskell.org Thu Oct 26 23:38:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new configuration flags for generating Config.hs. (7ae3a52) Message-ID: <20171026233814.A1E533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ae3a52e7f4ea090e99ad98988951067b45e1397/ghc >--------------------------------------------------------------- commit 7ae3a52e7f4ea090e99ad98988951067b45e1397 Author: Andrey Mokhov Date: Wed Sep 23 02:06:28 2015 +0100 Add new configuration flags for generating Config.hs. >--------------------------------------------------------------- 7ae3a52e7f4ea090e99ad98988951067b45e1397 cfg/system.config.in | 33 +++++++++++++++++++++------------ 1 file changed, 21 insertions(+), 12 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 6bfb20d..2bfe449 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -21,6 +21,8 @@ haddock = @hardtop@/inplace/bin/haddock hsc2hs = @hardtop@/inplace/bin/hsc2hs +genprimopcode = @hardtop@/inplace/bin/genprimopcode + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ @@ -45,23 +47,30 @@ ghc-source-path = @hardtop@ # Information about host and target systems: #=========================================== -target-os = @TargetOS_CPP@ -target-arch = @TargetArch_CPP@ -target-platform-full = @TargetPlatformFull@ +target-os = @TargetOS_CPP@ +target-arch = @TargetArch_CPP@ +target-platform-full = @TargetPlatformFull@ + +host-os = @HostOS_CPP@ +host-arch = @HostArch_CPP@ -host-os = @HostOS_CPP@ -host-arch = @HostArch_CPP@ +cross-compiling = @CrossCompiling@ -cross-compiling = @CrossCompiling@ +dynamic-extension = @soext_target@ -dynamic-extension = @soext_target@ +ghc-version = @GhcVersion@ +ghc-major-version = @GhcMajVersion@ +ghc-minor-version = @GhcMinVersion@ +ghc-patch-level = @GhcPatchLevel@ -ghc-major-version = @GhcMajVersion@ -ghc-minor-version = @GhcMinVersion@ -ghc-patch-level = @GhcPatchLevel@ +project-name = @ProjectName@ +project-version = @ProjectVersion@ +project-version-int = @ProjectVersionInt@ +project-patch-level = @ProjectPatchLevel@ +project-patch-level1 = @ProjectPatchLevel1@ +project-patch-level2 = @ProjectPatchLevel2@ +project-git-commit-id = @ProjectGitCommitId@ -project-version = @ProjectVersion@ -project-version-int = @ProjectVersionInt@ # Compilation and linking flags: #=============================== From git at git.haskell.org Thu Oct 26 23:38:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid cyclic dependencies, see #103. (50dbdd4) Message-ID: <20171026233815.1B5073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/50dbdd4040e45284fc4cc53115469fe3a882ac5a/ghc >--------------------------------------------------------------- commit 50dbdd4040e45284fc4cc53115469fe3a882ac5a Author: Andrey Mokhov Date: Tue Jan 5 21:30:58 2016 +0000 Avoid cyclic dependencies, see #103. >--------------------------------------------------------------- 50dbdd4040e45284fc4cc53115469fe3a882ac5a src/Rules/IntegerGmp.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index f86371c..0d5da26 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -105,7 +105,9 @@ integerGmpRules = do -- check whether we need to build in tree gmp -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` - need [pkgDataFile Stage1 integerGmp] + + runConfigure (pkgPath integerGmp) [] [] + configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk then do From git at git.haskell.org Thu Oct 26 23:38:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GenPrimopCode builder. (702ce42) Message-ID: <20171026233818.480C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/702ce42a9324375c294d8a3e0a49ce0c8a44bc62/ghc >--------------------------------------------------------------- commit 702ce42a9324375c294d8a3e0a49ce0c8a44bc62 Author: Andrey Mokhov Date: Wed Sep 23 02:06:48 2015 +0100 Add GenPrimopCode builder. >--------------------------------------------------------------- 702ce42a9324375c294d8a3e0a49ce0c8a44bc62 src/Builder.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 3a24df3..9448ed2 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -18,6 +18,7 @@ data Builder = Alex | Ar | Gcc Stage | GccM Stage + | GenPrimopCode | Ghc Stage | GhcCabal | GhcCabalHsColour @@ -38,6 +39,7 @@ builderKey builder = case builder of Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' + GenPrimopCode -> "genprimopcode" Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" From git at git.haskell.org Thu Oct 26 23:38:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't separate build commands with an empty line.\n\nThis allows to fit more commands on screen. (412009d) Message-ID: <20171026233818.C6CF33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/412009d52e693f3f67b86a71de4e7f359cd3b2a8/ghc >--------------------------------------------------------------- commit 412009d52e693f3f67b86a71de4e7f359cd3b2a8 Author: Andrey Mokhov Date: Tue Jan 5 23:21:54 2016 +0000 Don't separate build commands with an empty line.\n\nThis allows to fit more commands on screen. >--------------------------------------------------------------- 412009d52e693f3f67b86a71de4e7f359cd3b2a8 src/Base.hs | 2 +- src/Rules/Actions.hs | 10 +++++----- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 69904c4..36f2eb9 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -174,7 +174,7 @@ putError msg = do -- | Render the given set of lines in a nice box of ASCII renderBox :: [String] -> String -renderBox ls = concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) +renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) where -- Minimum total width of the box in characters minimumBoxWidth = 32 diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d567747..6f116b5 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -71,7 +71,7 @@ copyFile source target = do createDirectory :: FilePath -> Action () createDirectory dir = do - putBuild $ "\n| Create directory " ++ dir + putBuild $ "| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir -- Note, the source directory is untracked @@ -85,7 +85,7 @@ moveDirectory source target = do -- Transform a given file by applying a function to its contents fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do - putBuild $ "\n| Fix " ++ file + putBuild $ "| Fix " ++ file old <- liftIO $ readFile file let new = f old length new `seq` liftIO $ writeFile file new @@ -93,14 +93,14 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] - putBuild $ "\n| Run configure in " ++ dir ++ "..." + putBuild $ "| Run configure in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "\n| Run make" ++ note ++ " in " ++ dir ++ "..." + putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args runBuilder :: Builder -> [String] -> Action () @@ -108,7 +108,7 @@ runBuilder builder args = do needBuilder laxDependencies builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "\n| Run " ++ show builder ++ note + putBuild $ "| Run " ++ show builder ++ note quietly $ cmd [path] args -- Print out key information about the command being executed From git at git.haskell.org Thu Oct 26 23:38:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle GenPrimopCode builder in a special way. (17087d7) Message-ID: <20171026233822.2D3023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/17087d74a371ab996b81e8436f07839294a21cf8/ghc >--------------------------------------------------------------- commit 17087d74a371ab996b81e8436f07839294a21cf8 Author: Andrey Mokhov Date: Wed Sep 23 02:07:17 2015 +0100 Handle GenPrimopCode builder in a special way. >--------------------------------------------------------------- 17087d74a371ab996b81e8436f07839294a21cf8 src/Rules/Actions.hs | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index f261b4f..1e0472a 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -24,15 +24,23 @@ buildWithResources rs target = do ++ show builder ++ " with arguments:" mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList putBuild $ "\\--------" - quietly $ if builder /= Ar - then cmd [path] argList - else do -- Split argument list into chunks as otherwise Ar chokes up + quietly $ case builder of + Ar -> do -- Split argument list into chunks as otherwise Ar chokes up maxChunk <- cmdLineLengthLimit let persistentArgs = take arPersistentArgsCount argList remainingArgs = drop arPersistentArgsCount argList forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> unit . cmd [path] $ persistentArgs ++ argsChunk + GenPrimopCode -> do + let src = head $ Target.sources target -- TODO: ugly + file = head $ Target.files target + input <- readFile' src + Stdout output <- cmd (Stdin input) [path] argList + writeFileChanged file output + + _ -> cmd [path] argList + -- Most targets are built without explicitly acquiring resources build :: Target -> Action () build = buildWithResources [] From git at git.haskell.org Thu Oct 26 23:38:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to invoke libtool via bash. (9e731d6) Message-ID: <20171026233822.A92943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e731d6d7d730b14e805886ca34df7f0bfbac745/ghc >--------------------------------------------------------------- commit 9e731d6d7d730b14e805886ca34df7f0bfbac745 Author: Andrey Mokhov Date: Tue Jan 5 23:43:25 2016 +0000 Try to invoke libtool via bash. See #103. >--------------------------------------------------------------- 9e731d6d7d730b14e805886ca34df7f0bfbac745 src/Rules/IntegerGmp.hs | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 0d5da26..193b43d 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -6,7 +6,6 @@ import GHC import Oracles.Config.Setting import Rules.Actions import Settings.User -import Settings.TargetDirectory integerGmpBase :: FilePath integerGmpBase = "libraries/integer-gmp/gmp" @@ -103,19 +102,19 @@ integerGmpRules = do args <- configureArguments runConfigure integerGmpBuild envs args - -- check whether we need to build in tree gmp - -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` - + -- TODO: currently we configure integerGmp package twice -- optimise runConfigure (pkgPath integerGmp) [] [] + -- check whether we need to build in tree gmp + -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk then do - putBuild "\n| GMP framework detected and will be used" + putBuild "| GMP framework detected and will be used" copyFile integerGmpLibraryFakeH integerGmpLibraryH else do - putBuild "\n| No GMP framework detected" - runMake integerGmpBuild [] + putBuild "| No GMP framework detected; in tree GMP will be built" + runMake integerGmpBuild ["LIBTOOL=\"bash libtool\""] copyFile integerGmpLibraryInTreeH integerGmpLibraryH -- TODO: why copy library, can we move it instead? From git at git.haskell.org Thu Oct 26 23:38:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new configuration flags for generating Config.hs. (b8d04a6) Message-ID: <20171026233825.B9CE23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b8d04a663c092320d5b0fe2556349557d72ae373/ghc >--------------------------------------------------------------- commit b8d04a663c092320d5b0fe2556349557d72ae373 Author: Andrey Mokhov Date: Wed Sep 23 02:07:52 2015 +0100 Add new configuration flags for generating Config.hs. >--------------------------------------------------------------- b8d04a663c092320d5b0fe2556349557d72ae373 src/Oracles/Config/Setting.hs | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index a01a7fa..8ee4752 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -20,11 +20,17 @@ data Setting = DynamicExtension | GhcMajorVersion | GhcMinorVersion | GhcPatchLevel + | GhcVersion | GhcSourcePath | HostArch | HostOs + | ProjectGitCommitId + | ProjectName | ProjectVersion | ProjectVersionInt + | ProjectPatchLevel + | ProjectPatchLevel1 + | ProjectPatchLevel2 | TargetArch | TargetOs | TargetPlatformFull @@ -44,11 +50,17 @@ setting key = askConfig $ case key of GhcMajorVersion -> "ghc-major-version" GhcMinorVersion -> "ghc-minor-version" GhcPatchLevel -> "ghc-patch-level" + GhcVersion -> "ghc-version" GhcSourcePath -> "ghc-source-path" HostArch -> "host-arch" HostOs -> "host-os" + ProjectGitCommitId -> "project-git-commit-id" + ProjectName -> "project-name" ProjectVersion -> "project-version" ProjectVersionInt -> "project-version-int" + ProjectPatchLevel -> "project-patch-level" + ProjectPatchLevel1 -> "project-patch-level1" + ProjectPatchLevel2 -> "project-patch-level2" TargetArch -> "target-arch" TargetOs -> "target-os" TargetPlatformFull -> "target-platform-full" From git at git.haskell.org Thu Oct 26 23:38:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Another attempt to invoke libtool via bash, see #103. (375d41e) Message-ID: <20171026233826.34D3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/375d41e7658d6b4f91c15eaf1ac74ce37b720f1b/ghc >--------------------------------------------------------------- commit 375d41e7658d6b4f91c15eaf1ac74ce37b720f1b Author: Andrey Mokhov Date: Wed Jan 6 00:51:54 2016 +0000 Another attempt to invoke libtool via bash, see #103. >--------------------------------------------------------------- 375d41e7658d6b4f91c15eaf1ac74ce37b720f1b src/Rules/Actions.hs | 6 +++--- src/Rules/IntegerGmp.hs | 2 +- src/Rules/Libffi.hs | 4 ++-- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 6f116b5..9250357 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -99,15 +99,15 @@ runConfigure dir opts args = do runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] - let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args + quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir] args runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do needBuilder laxDependencies builder path <- builderPath builder - let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ show builder ++ note quietly $ cmd [path] args diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 193b43d..142a9c6 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -114,7 +114,7 @@ integerGmpRules = do copyFile integerGmpLibraryFakeH integerGmpLibraryH else do putBuild "| No GMP framework detected; in tree GMP will be built" - runMake integerGmpBuild ["LIBTOOL=\"bash libtool\""] + runMake integerGmpBuild ["MAKEFLAGS='LIBTOOL=bash\\ libtool'"] copyFile integerGmpLibraryInTreeH integerGmpLibraryH -- TODO: why copy library, can we move it instead? diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 041650f..9d77814 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -91,8 +91,8 @@ libffiRules = do args <- configureArguments runConfigure libffiBuild envs args - runMake libffiBuild [] - runMake libffiBuild ["install"] + runMake libffiBuild ["MAKEFLAGS="] + runMake libffiBuild ["MAKEFLAGS=", "install"] forM_ ["ffi.h", "ffitarget.h"] $ \file -> do let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file From git at git.haskell.org Thu Oct 26 23:38:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add genPrimopCodeArgs to defaultArgs. (f406d36) Message-ID: <20171026233829.2EDF33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f406d36fead05bbfd323aafc85d836c2fdb6ae89/ghc >--------------------------------------------------------------- commit f406d36fead05bbfd323aafc85d836c2fdb6ae89 Author: Andrey Mokhov Date: Wed Sep 23 02:08:22 2015 +0100 Add genPrimopCodeArgs to defaultArgs. >--------------------------------------------------------------- f406d36fead05bbfd323aafc85d836c2fdb6ae89 src/Settings/Args.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 97933fa..349668a 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -4,6 +4,7 @@ import Expression import Settings.Builders.Alex import Settings.Builders.Ar import Settings.Builders.Gcc +import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg @@ -30,12 +31,13 @@ defaultArgs = mconcat , arArgs , cabalArgs , customPackageArgs + , gccArgs + , gccMArgs + , genPrimopCodeArgs , ghcArgs , ghcCabalHsColourArgs , ghcMArgs , ghcPkgArgs - , gccArgs - , gccMArgs , haddockArgs , happyArgs , hsc2HsArgs From git at git.haskell.org Thu Oct 26 23:38:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (da61b39) Message-ID: <20171026233829.A1CBC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da61b39228f39feb4d201d9505bd1ef02dc6518e/ghc >--------------------------------------------------------------- commit da61b39228f39feb4d201d9505bd1ef02dc6518e Author: Andrey Mokhov Date: Wed Jan 6 01:20:21 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- da61b39228f39feb4d201d9505bd1ef02dc6518e README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 43b74be..90f6422 100644 --- a/README.md +++ b/README.md @@ -59,7 +59,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system run the build script with `-B` flag. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). +To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). How to contribute From git at git.haskell.org Thu Oct 26 23:38:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add next meeting discusion agenda. (395f3ce) Message-ID: <20171026233832.9EF1F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/395f3ce523108018dc1ffaefc2daa3318fbcf4bd/ghc >--------------------------------------------------------------- commit 395f3ce523108018dc1ffaefc2daa3318fbcf4bd Author: Andrey Mokhov Date: Wed Sep 23 02:08:56 2015 +0100 Add next meeting discusion agenda. >--------------------------------------------------------------- 395f3ce523108018dc1ffaefc2daa3318fbcf4bd doc/meeting-25-September-2015.txt | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt new file mode 100644 index 0000000..6ee4297 --- /dev/null +++ b/doc/meeting-25-September-2015.txt @@ -0,0 +1,35 @@ +Shaking up GHC meeting, 25 September 2015 + +Things to discuss: +================================================ + +1. Better names for build stages + +* Currently we have Stage0, Stage1, etc. It is not particularly clear +from the names what they stand for. We no longer need to stick to +numbers and can pick more helpful names, for example: + +Stage0 -> Boot +Stage1 -> Interim +Stage2 -> Install +Stage3 -> Selftest + + + + +i. Unclear abstractions Builder/BuildRule... + +ii. Limits to build parallelism: GHC crashes during parallel builds. Also ghc-pkg and ghc-cabal are apparently not thread-safe, so I had to use Shake resources to limit the parallelism... + + +2. Do we need a name for the new build system? + +* At least we need a name for the folder in the GHC tree + +* If we call it 'shake' there may be a confusion with the Shake library. + +* In future discussions/announcements/etc. calling it 'the new shake-based + build system' is overly verbose. Calling it 'shake' is confusing. + +* I haven't thought about any names yet, just checking whether we want to. + From git at git.haskell.org Thu Oct 26 23:38:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a rule for libraries/integer-gmp/gmp/gmp.h, see #103. (d716ae5) Message-ID: <20171026233833.2645F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d716ae544c182207ba70b3becdb11bcc3aca5a73/ghc >--------------------------------------------------------------- commit d716ae544c182207ba70b3becdb11bcc3aca5a73 Author: Andrey Mokhov Date: Wed Jan 6 01:50:10 2016 +0000 Add a rule for libraries/integer-gmp/gmp/gmp.h, see #103. >--------------------------------------------------------------- d716ae544c182207ba70b3becdb11bcc3aca5a73 src/Rules/IntegerGmp.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 142a9c6..2b9bbd9 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -116,7 +116,8 @@ integerGmpRules = do putBuild "| No GMP framework detected; in tree GMP will be built" runMake integerGmpBuild ["MAKEFLAGS='LIBTOOL=bash\\ libtool'"] - copyFile integerGmpLibraryInTreeH integerGmpLibraryH + copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryInTreeH + copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryH -- TODO: why copy library, can we move it instead? copyFile (integerGmpBuild -/- ".libs/libgmp.a") integerGmpLibrary @@ -126,3 +127,5 @@ integerGmpRules = do runBuilder Ranlib [integerGmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" + + integerGmpLibraryInTreeH %> \_ -> need [integerGmpLibraryH] From git at git.haskell.org Thu Oct 26 23:38:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Draft GenPrimopCode argument list. (ed20ac4) Message-ID: <20171026233836.095143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ed20ac498137f4c2e3f297e6312da93dab64be6d/ghc >--------------------------------------------------------------- commit ed20ac498137f4c2e3f297e6312da93dab64be6d Author: Andrey Mokhov Date: Wed Sep 23 02:09:29 2015 +0100 Draft GenPrimopCode argument list. >--------------------------------------------------------------- ed20ac498137f4c2e3f297e6312da93dab64be6d src/Settings/Builders/GenPrimopCode.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/src/Settings/Builders/GenPrimopCode.hs b/src/Settings/Builders/GenPrimopCode.hs new file mode 100644 index 0000000..711aa80 --- /dev/null +++ b/src/Settings/Builders/GenPrimopCode.hs @@ -0,0 +1,8 @@ +module Settings.Builders.GenPrimopCode (genPrimopCodeArgs) where + +import Expression +import Predicates (builder) + +-- Stdin/stdout are handled in a special way. See Rules/Actions.hs. +genPrimopCodeArgs :: Args +genPrimopCodeArgs = builder GenPrimopCode ? arg "--make-haskell-wrappers" From git at git.haskell.org Thu Oct 26 23:38:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds osx to the list of operatin systems in the travis.yml (f466624) Message-ID: <20171026233836.918AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4666240df45766aa8d8e38af4a0d88d50e9325c/ghc >--------------------------------------------------------------- commit f4666240df45766aa8d8e38af4a0d88d50e9325c Author: Moritz Angermann Date: Wed Jan 6 11:50:02 2016 +0800 Adds osx to the list of operatin systems in the travis.yml This should fix #111. >--------------------------------------------------------------- f4666240df45766aa8d8e38af4a0d88d50e9325c .travis.yml | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.travis.yml b/.travis.yml index 9079fa9..58e23cd 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,5 +1,9 @@ sudo: false +os: + - linux + - osx + matrix: include: - env: From git at git.haskell.org Thu Oct 26 23:38:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement generation of PrimopWrappers.hs. Work on generating Config.hs. (7e4f903) Message-ID: <20171026233839.95C743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e4f9033115b8f0591b3a1e4541b8dd6a4c9d633/ghc >--------------------------------------------------------------- commit 7e4f9033115b8f0591b3a1e4541b8dd6a4c9d633 Author: Andrey Mokhov Date: Wed Sep 23 02:10:25 2015 +0100 Implement generation of PrimopWrappers.hs. Work on generating Config.hs. >--------------------------------------------------------------- 7e4f9033115b8f0591b3a1e4541b8dd6a4c9d633 src/Rules/Generate.hs | 93 ++++++++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 92 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 535f99b..a12f6a8 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -6,6 +6,9 @@ import Rules.Actions import Rules.Resources import Settings +primops :: FilePath +primops = "compiler/stage1/build/primops.txt" + -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] knownGenerators = [ (Alex , ".x" ) @@ -31,7 +34,95 @@ generatePackageCode _ target @ (PartialTarget stage package) = let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ "Exactly one generator expected for " ++ file - ++ "(found: " ++ show gens ++ ")." + ++ " (found: " ++ show gens ++ ")." let (src, builder) = head gens need [src] build $ fullTarget target builder [src] [file] + + path -/- "build/GHC/PrimopWrappers.hs" %> \file -> do + need [primops] + build $ fullTarget target GenPrimopCode [primops] [file] + + priority 2.0 $ path -/- "build/Config.hs" %> \file -> do + config <- generateConfig + writeFileChanged file config + +generateConfig :: Action String +generateConfig = do + cProjectName <- setting ProjectName + cProjectGitCommitId <- setting ProjectGitCommitId + cProjectVersion <- setting ProjectVersion + cProjectVersionInt <- setting ProjectVersionInt + cProjectPatchLevel <- setting ProjectPatchLevel + cProjectPatchLevel1 <- setting ProjectPatchLevel1 + cProjectPatchLevel2 <- setting ProjectPatchLevel2 + cBooterVersion <- setting GhcVersion + cIntegerLibraryType <- case integerLibrary of + integerGmp -> return "IntegerGMP" + integerSimple -> return "IntegerSimple" + _ -> putError $ "Unknown integer library: " ++ integerLibrary ++ "." + cSupportsSplitObjs <- yesNo splitObjects + return "{-# LANGUAGE CPP #-}\n" + ++ "module Config where\n" + ++ "\n" + ++ "#include \"ghc_boot_platform.h\"\n" + ++ "\n" + ++ "data IntegerLibrary = IntegerGMP\n" + ++ " | IntegerSimple\n" + ++ " deriving Eq\n" + ++ "\n" + ++ "cBuildPlatformString :: String\n" + ++ "cBuildPlatformString = BuildPlatform_NAME\n" + ++ "cHostPlatformString :: String\n" + ++ "cHostPlatformString = HostPlatform_NAME\n" + ++ "cTargetPlatformString :: String\n" + ++ "cTargetPlatformString = TargetPlatform_NAME\n" + ++ "\n" + ++ "cProjectName :: String\n" + ++ "cProjectName = " ++ cProjectName ++ "\n" + ++ "cProjectGitCommitId :: String\n" + ++ "cProjectGitCommitId = " ++ cProjectGitCommitId ++ "\n" + ++ "cProjectVersion :: String\n" + ++ "cProjectVersion = " ++ cProjectVersion ++ "\n" + ++ "cProjectVersionInt :: String\n" + ++ "cProjectVersionInt = " ++ cProjectVersionInt ++ "\n" + ++ "cProjectPatchLevel :: String\n" + ++ "cProjectPatchLevel = " ++ cProjectPatchLevel ++ "\n" + ++ "cProjectPatchLevel1 :: String\n" + ++ "cProjectPatchLevel1 = " ++ cProjectPatchLevel1 ++ "\n" + ++ "cProjectPatchLevel2 :: String\n" + ++ "cProjectPatchLevel2 = " ++ cProjectPatchLevel2 ++ "\n" + ++ "cBooterVersion :: String\n" + ++ "cBooterVersion = " ++ cBooterVersion ++ "\n" + ++ "cStage :: String\n" + ++ "cStage = show (STAGE :: Int)\n" + ++ "cIntegerLibrary :: String\n" + ++ "cIntegerLibrary = " ++ pkgName integerLibrary ++ "\n" + ++ "cIntegerLibraryType :: IntegerLibrary\n" + ++ "cIntegerLibraryType = " ++ cIntegerLibraryType ++ "\n" + ++ "cSupportsSplitObjs :: String\n" + ++ "cSupportsSplitObjs = " ++ cSupportsSplitObjs ++ "\n" + ++ "cGhcWithInterpreter :: String\n" + ++ "cGhcWithInterpreter = "YES"\n" + ++ "cGhcWithNativeCodeGen :: String\n" + ++ "cGhcWithNativeCodeGen = "YES"\n" + ++ "cGhcWithSMP :: String\n" + ++ "cGhcWithSMP = "YES"\n" + ++ "cGhcRTSWays :: String\n" + ++ "cGhcRTSWays = "l debug thr thr_debug thr_l thr_p "\n" + ++ "cGhcEnableTablesNextToCode :: String\n" + ++ "cGhcEnableTablesNextToCode = "YES"\n" + ++ "cLeadingUnderscore :: String\n" + ++ "cLeadingUnderscore = "NO"\n" + ++ "cGHC_UNLIT_PGM :: String\n" + ++ "cGHC_UNLIT_PGM = "unlit.exe"\n" + ++ "cGHC_SPLIT_PGM :: String\n" + ++ "cGHC_SPLIT_PGM = "ghc-split"\n" + ++ "cLibFFI :: Bool\n" + ++ "cLibFFI = False\n" + ++ "cGhcThreaded :: Bool\n" + ++ "cGhcThreaded = True\n" + ++ "cGhcDebugged :: Bool\n" + ++ "cGhcDebugged = False\n" + + From git at git.haskell.org Thu Oct 26 23:38:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do we need tabs? (d705676) Message-ID: <20171026233840.0D2AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d705676ac7aee5a5bf153ad0c9d44696ce127d70/ghc >--------------------------------------------------------------- commit d705676ac7aee5a5bf153ad0c9d44696ce127d70 Author: Moritz Angermann Date: Wed Jan 6 11:57:30 2016 +0800 Do we need tabs? >--------------------------------------------------------------- d705676ac7aee5a5bf153ad0c9d44696ce127d70 .travis.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 58e23cd..0a85228 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,8 +1,8 @@ sudo: false os: - - linux - - osx + - linux + - osx matrix: include: From git at git.haskell.org Thu Oct 26 23:38:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcSplit and Unlit builders. (47c7ab1) Message-ID: <20171026233843.27AEC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47c7ab173f636eb0c636765b412c523bdb3e7fb3/ghc >--------------------------------------------------------------- commit 47c7ab173f636eb0c636765b412c523bdb3e7fb3 Author: Andrey Mokhov Date: Thu Sep 24 05:43:05 2015 +0100 Add GhcSplit and Unlit builders. >--------------------------------------------------------------- 47c7ab173f636eb0c636765b412c523bdb3e7fb3 cfg/system.config.in | 4 ++++ src/Builder.hs | 11 ++++++++++- 2 files changed, 14 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 2bfe449..87d2b93 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -23,6 +23,9 @@ hsc2hs = @hardtop@/inplace/bin/hsc2hs genprimopcode = @hardtop@/inplace/bin/genprimopcode +unlit = @hardtop@/inplace/lib/unlit +ghc-split = @hardtop@/inplace/lib/ghc-split + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ @@ -43,6 +46,7 @@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ ghc-source-path = @hardtop@ +leading-underscore = @LeadingUnderscore@ # Information about host and target systems: #=========================================== diff --git a/src/Builder.hs b/src/Builder.hs index 9448ed2..a6521a1 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,5 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} -module Builder (Builder (..), builderPath, specified, needBuilder) where +module Builder ( + Builder (..), builderPath, getBuilderPath, specified, needBuilder + ) where import Base import GHC.Generics (Generic) @@ -24,11 +26,13 @@ data Builder = Alex | GhcCabalHsColour | GhcM Stage | GhcPkg Stage + | GhcSplit | Haddock | Happy | HsColour | Hsc2Hs | Ld + | Unlit deriving (Show, Eq, Generic) -- Configuration files refer to Builders as follows: @@ -49,11 +53,13 @@ builderKey builder = case builder of GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" + GhcSplit -> "ghc-split" Happy -> "happy" Haddock -> "haddock" HsColour -> "hscolour" Hsc2Hs -> "hsc2hs" Ld -> "ld" + Unlit -> "unlit" builderPath :: Builder -> Action FilePath builderPath builder = do @@ -62,6 +68,9 @@ builderPath builder = do ++ "' in configuration files." fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe +getBuilderPath :: Builder -> ReaderT a Action FilePath +getBuilderPath = lift . builderPath + specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath From git at git.haskell.org Thu Oct 26 23:38:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: env for all, apt only for linux (a7610e0) Message-ID: <20171026233843.8A69A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7610e09f39b37e683848a161121f52ce01555df/ghc >--------------------------------------------------------------- commit a7610e09f39b37e683848a161121f52ce01555df Author: Moritz Angermann Date: Wed Jan 6 12:15:00 2016 +0800 env for all, apt only for linux >--------------------------------------------------------------- a7610e09f39b37e683848a161121f52ce01555df .travis.yml | 32 ++++++++++++++------------------ 1 file changed, 14 insertions(+), 18 deletions(-) diff --git a/.travis.yml b/.travis.yml index 0a85228..0a8f49a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -4,24 +4,20 @@ os: - linux - osx -matrix: - include: - - env: - CABALVER=1.22 - GHCVER=7.10.3 - - addons: { - apt: { - packages: [ - ghc-7.10.3, - alex-3.1.4, - happy-1.19.5, - cabal-install-1.22, - zlib1g-dev - ], - sources: [hvr-ghc] - } - } +env: + - CABALVER=1.22 + - GHCVER=7.10.3 + +addons: + linux: + apt: + packages: + - ghc-7.10.3, + - alex-3.1.4, + - happy-1.19.5, + - cabal-install-1.22, + - zlib1g-dev + sources: hvr-ghc before_install: From git at git.haskell.org Thu Oct 26 23:38:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix ghcEnableTablesNextToCode, refactor code. (aecfdda) Message-ID: <20171026233846.8FA413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aecfddac1536bf6f565df227acff0ab37ce534a8/ghc >--------------------------------------------------------------- commit aecfddac1536bf6f565df227acff0ab37ce534a8 Author: Andrey Mokhov Date: Thu Sep 24 05:45:34 2015 +0100 Fix ghcEnableTablesNextToCode, refactor code. >--------------------------------------------------------------- aecfddac1536bf6f565df227acff0ab37ce534a8 src/Oracles/Config/Flag.hs | 35 ++++++++++++++++------------- src/Oracles/Config/Setting.hs | 52 ++++++++++++++++++------------------------- 2 files changed, 42 insertions(+), 45 deletions(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index d520a85..69d4884 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -1,7 +1,7 @@ module Oracles.Config.Flag ( Flag (..), flag, getFlag, - crossCompiling, gccIsClang, gccGe46, - platformSupportsSharedLibs, ghcWithSMP, ghcWithNativeCodeGen + crossCompiling, platformSupportsSharedLibs, ghcWithSMP, + ghcWithNativeCodeGen, supportsSplitObjects ) where import Base @@ -12,6 +12,7 @@ data Flag = CrossCompiling | GccIsClang | GccLt46 | GhcUnregisterised + | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken | SupportsPackageKey @@ -25,6 +26,7 @@ flag f = do GccIsClang -> "gcc-is-clang" GccLt46 -> "gcc-lt-46" GhcUnregisterised -> "ghc-unregisterised" + LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" SupportsPackageKey -> "supports-package-key" @@ -41,30 +43,33 @@ getFlag = lift . flag crossCompiling :: Action Bool crossCompiling = flag CrossCompiling -gccIsClang :: Action Bool -gccIsClang = flag GccIsClang - -gccGe46 :: Action Bool -gccGe46 = fmap not $ flag GccLt46 - platformSupportsSharedLibs :: Action Bool platformSupportsSharedLibs = do - badPlatform <- targetPlatforms [ "powerpc-unknown-linux" - , "x86_64-unknown-mingw32" - , "i386-unknown-mingw32" ] - solaris <- targetPlatform "i386-unknown-solaris2" + badPlatform <- anyTargetPlatform [ "powerpc-unknown-linux" + , "x86_64-unknown-mingw32" + , "i386-unknown-mingw32" ] + solaris <- anyTargetPlatform [ "i386-unknown-solaris2" ] solarisBroken <- flag SolarisBrokenShld return $ not (badPlatform || solaris && solarisBroken) ghcWithSMP :: Action Bool ghcWithSMP = do - goodArch <- targetArchs ["i386", "x86_64", "sparc", "powerpc", "arm"] + goodArch <- anyTargetArch ["i386", "x86_64", "sparc", "powerpc", "arm"] ghcUnreg <- flag GhcUnregisterised return $ goodArch && not ghcUnreg ghcWithNativeCodeGen :: Action Bool ghcWithNativeCodeGen = do - goodArch <- targetArchs ["i386", "x86_64", "sparc", "powerpc"] - badOs <- targetOss ["ios", "aix"] + goodArch <- anyTargetArch ["i386", "x86_64", "sparc", "powerpc"] + badOs <- anyTargetOs ["ios", "aix"] ghcUnreg <- flag GhcUnregisterised return $ goodArch && not badOs && not ghcUnreg + +supportsSplitObjects :: Action Bool +supportsSplitObjects = do + broken <- flag SplitObjectsBroken + ghcUnreg <- flag GhcUnregisterised + goodArch <- anyTargetArch [ "i386", "x86_64", "powerpc", "sparc" ] + goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "darwin", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" ] + return $ not broken && not ghcUnreg && goodArch && goodOs diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 8ee4752..e1dfefa 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -1,9 +1,9 @@ module Oracles.Config.Setting ( Setting (..), SettingList (..), setting, settingList, getSetting, getSettingList, - targetPlatform, targetPlatforms, targetOs, targetOss, notTargetOs, - targetArchs, windowsHost, notWindowsHost, ghcWithInterpreter, - ghcEnableTablesNextToCode, ghcCanonVersion, cmdLineLengthLimit + anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, windowsHost, + ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, + ghcCanonVersion, cmdLineLengthLimit ) where import Base @@ -83,45 +83,37 @@ getSettingList :: SettingList -> ReaderT a Action [String] getSettingList = lift . settingList matchSetting :: Setting -> [String] -> Action Bool -matchSetting key values = do - value <- setting key - return $ value `elem` values +matchSetting key values = fmap (`elem` values) $ setting key -targetPlatforms :: [String] -> Action Bool -targetPlatforms = matchSetting TargetPlatformFull +anyTargetPlatform :: [String] -> Action Bool +anyTargetPlatform = matchSetting TargetPlatformFull -targetPlatform :: String -> Action Bool -targetPlatform s = targetPlatforms [s] +anyTargetOs :: [String] -> Action Bool +anyTargetOs = matchSetting TargetOs -targetOss :: [String] -> Action Bool -targetOss = matchSetting TargetOs +anyTargetArch :: [String] -> Action Bool +anyTargetArch = matchSetting TargetArch -targetOs :: String -> Action Bool -targetOs s = targetOss [s] - -notTargetOs :: String -> Action Bool -notTargetOs = fmap not . targetOs - -targetArchs :: [String] -> Action Bool -targetArchs = matchSetting TargetArch +anyHostOs :: [String] -> Action Bool +anyHostOs = matchSetting HostOs windowsHost :: Action Bool -windowsHost = matchSetting HostOs ["mingw32", "cygwin32"] - -notWindowsHost :: Action Bool -notWindowsHost = fmap not windowsHost +windowsHost = anyHostOs ["mingw32", "cygwin32"] ghcWithInterpreter :: Action Bool ghcWithInterpreter = do - goodOs <- targetOss [ "mingw32", "cygwin32", "linux", "solaris2" - , "freebsd", "dragonfly", "netbsd", "openbsd" - , "darwin", "kfreebsdgnu" ] - goodArch <- targetArchs [ "i386", "x86_64", "powerpc", "sparc" - , "sparc64", "arm" ] + goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" + , "darwin", "kfreebsdgnu" ] + goodArch <- anyTargetArch [ "i386", "x86_64", "powerpc", "sparc" + , "sparc64", "arm" ] return $ goodOs && goodArch ghcEnableTablesNextToCode :: Action Bool -ghcEnableTablesNextToCode = targetArchs ["ia64", "powerpc64"] +ghcEnableTablesNextToCode = notM $ anyTargetArch ["ia64", "powerpc64", "powerpc64le"] + +useLibFFIForAdjustors :: Action Bool +useLibFFIForAdjustors = notM $ anyTargetArch ["i386", "x86_64"] -- Canonicalised GHC version number, used for integer version comparisons. We -- expand GhcMinorVersion to two digits by adding a leading zero if necessary. From git at git.haskell.org Thu Oct 26 23:38:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: collapse env, addons wihout linux (fb5ed14) Message-ID: <20171026233846.EE7353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fb5ed14f7d95b0ea65e925c15e04ed766fad9247/ghc >--------------------------------------------------------------- commit fb5ed14f7d95b0ea65e925c15e04ed766fad9247 Author: Moritz Angermann Date: Wed Jan 6 12:16:48 2016 +0800 collapse env, addons wihout linux >--------------------------------------------------------------- fb5ed14f7d95b0ea65e925c15e04ed766fad9247 .travis.yml | 20 +++++++++----------- 1 file changed, 9 insertions(+), 11 deletions(-) diff --git a/.travis.yml b/.travis.yml index 0a8f49a..09ed050 100644 --- a/.travis.yml +++ b/.travis.yml @@ -5,19 +5,17 @@ os: - osx env: - - CABALVER=1.22 - - GHCVER=7.10.3 + - CABALVER=1.22 GHCVER=7.10.3 addons: - linux: - apt: - packages: - - ghc-7.10.3, - - alex-3.1.4, - - happy-1.19.5, - - cabal-install-1.22, - - zlib1g-dev - sources: hvr-ghc + apt: + packages: + - ghc-7.10.3, + - alex-3.1.4, + - happy-1.19.5, + - cabal-install-1.22, + - zlib1g-dev + sources: hvr-ghc before_install: From git at git.haskell.org Thu Oct 26 23:38:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix GhcPrim path in getPackageSources. (c7f9f7c) Message-ID: <20171026233850.35A713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7f9f7c349b0498f9a42b4a2c2dbc02082d03645/ghc >--------------------------------------------------------------- commit c7f9f7c349b0498f9a42b4a2c2dbc02082d03645 Author: Andrey Mokhov Date: Thu Sep 24 05:46:13 2015 +0100 Fix GhcPrim path in getPackageSources. >--------------------------------------------------------------- c7f9f7c349b0498f9a42b4a2c2dbc02082d03645 src/Settings.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/src/Settings.hs b/src/Settings.hs index 1a35a94..dab73ed 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -37,14 +37,17 @@ getPackageSources = do srcDirs <- getPkgDataList SrcDirs let buildPath = path -/- "build" - dirs = (buildPath -/- "autogen") : map (packagePath -/-) srcDirs + autogen = buildPath -/- "autogen" + dirs = autogen : map (packagePath -/-) srcDirs (foundSources, missingSources) <- findModuleFiles dirs "*hs" - -- Generated source files live in buildPath and have extension "hs" + -- Generated source files live in buildPath and have extension "hs"... let generatedSources = [ buildPath -/- s <.> "hs" | s <- missingSources ] + -- ...except that GHC/Prim.hs lives in autogen. TODO: fix? + fixGhcPrim = replaceEq (buildPath -/- "GHC/Prim.hs") (autogen -/- "GHC/Prim.hs") - return $ foundSources ++ generatedSources + return $ foundSources ++ fixGhcPrim generatedSources -- findModuleFiles scans a list of given directories and finds files matching a -- given extension pattern (e.g., "*hs") that correspond to modules of the From git at git.haskell.org Thu Oct 26 23:38:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop commas (35d0909) Message-ID: <20171026233850.86AF93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/35d09097edef38416909648fd04a50836d39e485/ghc >--------------------------------------------------------------- commit 35d09097edef38416909648fd04a50836d39e485 Author: Moritz Angermann Date: Wed Jan 6 12:20:58 2016 +0800 Drop commas >--------------------------------------------------------------- 35d09097edef38416909648fd04a50836d39e485 .travis.yml | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 09ed050..13a70d2 100644 --- a/.travis.yml +++ b/.travis.yml @@ -10,10 +10,10 @@ env: addons: apt: packages: - - ghc-7.10.3, - - alex-3.1.4, - - happy-1.19.5, - - cabal-install-1.22, + - ghc-7.10.3 + - alex-3.1.4 + - happy-1.19.5 + - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc From git at git.haskell.org Thu Oct 26 23:38:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code. (28e3a26) Message-ID: <20171026233854.116C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28e3a26cbaa18b6efc353d543843efd1efb311f0/ghc >--------------------------------------------------------------- commit 28e3a26cbaa18b6efc353d543843efd1efb311f0 Author: Andrey Mokhov Date: Thu Sep 24 05:47:46 2015 +0100 Clean up code. >--------------------------------------------------------------- 28e3a26cbaa18b6efc353d543843efd1efb311f0 src/Predicates.hs | 15 +++++---------- src/Settings/Builders/GhcCabal.hs | 18 +++++++++--------- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages.hs | 8 ++++---- 4 files changed, 19 insertions(+), 24 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 00c12ca..13482b7 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -43,7 +43,7 @@ stage2 :: Predicate stage2 = stage Stage2 notStage0 :: Predicate -notStage0 = fmap not stage0 +notStage0 = notM stage0 -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate @@ -51,12 +51,7 @@ registerPackage = return True splitObjects :: Predicate splitObjects = do - goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages - goodPkg <- fmap not $ package compiler -- We don't split compiler - broken <- getFlag SplitObjectsBroken - ghcUnreg <- getFlag GhcUnregisterised - goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] - goodOs <- lift $ targetOss [ "mingw32", "cygwin32", "linux", "darwin" - , "solaris2", "freebsd", "dragonfly" - , "netbsd", "openbsd" ] - return $ goodStage && goodPkg && not broken && not ghcUnreg && goodArch && goodOs + goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages + goodPackage <- notM $ package compiler -- We don't split compiler + supported <- lift supportsSplitObjects + return $ goodStage && goodPackage && supported diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index ab65a51..54452d8 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -101,12 +101,12 @@ ccArgs = validating ? ccWarnings -- TODO: should be in a different file ccWarnings :: Args ccWarnings = do - let notClang = fmap not gccIsClang + let gccGe46 = notM $ (flag GccIsClang ||^ flag GccLt46) mconcat [ arg "-Werror" , arg "-Wall" - , gccIsClang ? arg "-Wno-unknown-pragmas" - , notClang ? gccGe46 ? notWindowsHost ? arg "-Werror=unused-but-set-variable" - , notClang ? gccGe46 ? arg "-Wno-error=inline" ] + , flag GccIsClang ? arg "-Wno-unknown-pragmas" + , gccGe46 ? notM windowsHost ? arg "-Werror=unused-but-set-variable" + , gccGe46 ? arg "-Wno-error=inline" ] ldArgs :: Args ldArgs = mempty @@ -147,10 +147,10 @@ customPackageArgs = do mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show nextStage , arg $ "--flags=stage" ++ show nextStage , arg "--disable-library-for-ghci" - , targetOs "openbsd" ? arg "--ld-options=-E" + , anyTargetOs ["openbsd"] ? arg "--ld-options=-E" , flag GhcUnregisterised ? arg "--ghc-option=-DNO_REGS" - , fmap not ghcWithSMP ? arg "--ghc-option=-DNOSMP" - , fmap not ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" + , notM ghcWithSMP ? arg "--ghc-option=-DNOSMP" + , notM ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" , (threaded `elem` rtsWays) ? notStage0 ? arg "--ghc-option=-optc-DTHREADED_RTS" , ghcWithNativeCodeGen ? arg "--flags=ncg" @@ -158,7 +158,7 @@ customPackageArgs = do notStage0 ? arg "--flags=ghci" , ghcWithInterpreter ? ghcEnableTablesNextToCode ? - fmap not (flag GhcUnregisterised) ? + notM (flag GhcUnregisterised) ? notStage0 ? arg "--ghc-option=-DGHCI_TABLES_NEXT_TO_CODE" , ghcWithInterpreter ? ghciWithDebugger ? @@ -183,7 +183,7 @@ withBuilderKey b = case b of -- Expression 'with Gcc' appends "--with-gcc=/path/to/gcc" and needs Gcc. with :: Builder -> Args with b = specified b ? do - path <- lift $ builderPath b + path <- getBuilderPath b lift $ needBuilder laxDependencies b append [withBuilderKey b ++ path] diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index fae7c1f..7dfe286 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -24,7 +24,7 @@ hsc2HsArgs = builder Hsc2Hs ? do else getSetting ProjectVersionInt mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath - , notWindowsHost ? arg "--cross-safe" + , notM windowsHost ? arg "--cross-safe" , append $ map ("-I" ++) gmpDirs , append $ map ("--cflag=" ++) cFlags , append $ map ("--lflag=" ++) lFlags diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 87f293d..dee0c95 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -17,7 +17,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binPackageDb, binary, cabal, compiler, hoopl, hpc, transformers ] - , notWindowsHost ? notTargetOs "ios" ? append [terminfo] ] + , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages @@ -26,9 +26,9 @@ packagesStage1 = mconcat , append [ array, base, bytestring, containers, deepseq, directory , filepath, ghcPrim, haskeline, integerLibrary, pretty, process , templateHaskell, time ] - , windowsHost ? append [win32] - , notWindowsHost ? append [unix] - , buildHaddock ? append [xhtml] ] + , windowsHost ? append [win32] + , notM windowsHost ? append [unix] + , buildHaddock ? append [xhtml] ] knownPackages :: [Package] knownPackages = defaultKnownPackages ++ userKnownPackages From git at git.haskell.org Thu Oct 26 23:38:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Can we install ghc and cabal through homebrew on os x? (3ea7037) Message-ID: <20171026233854.6876B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ea7037adc5e9b0592df20d44d4269097706fe5e/ghc >--------------------------------------------------------------- commit 3ea7037adc5e9b0592df20d44d4269097706fe5e Author: Moritz Angermann Date: Wed Jan 6 12:26:12 2016 +0800 Can we install ghc and cabal through homebrew on os x? >--------------------------------------------------------------- 3ea7037adc5e9b0592df20d44d4269097706fe5e .travis.yml | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.travis.yml b/.travis.yml index 13a70d2..33c4c3e 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,6 +18,10 @@ addons: sources: hvr-ghc before_install: + osx: + - brew update + - brew outdated ghc || brew upgrade ghc + - brew outdated cabal-install || brew upgrade cabal-install - PATH="$HOME/.cabal/bin:$PATH" - PATH="/opt/ghc/$GHCVER/bin:$PATH" From git at git.haskell.org Thu Oct 26 23:38:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add getLibWays to capture context-less ways. (cc3113d) Message-ID: <20171026233857.81F3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cc3113db2263c179a4e91440a9369f44a2825980/ghc >--------------------------------------------------------------- commit cc3113db2263c179a4e91440a9369f44a2825980 Author: Andrey Mokhov Date: Thu Sep 24 05:49:11 2015 +0100 Add getLibWays to capture context-less ways. >--------------------------------------------------------------- cc3113db2263c179a4e91440a9369f44a2825980 src/Settings/User.hs | 14 +++++++++----- src/Settings/Ways.hs | 17 ++++++++++------- 2 files changed, 19 insertions(+), 12 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index f9a430c..5b62e39 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,8 +1,8 @@ module Settings.User ( - userArgs, userPackages, userWays, userRtsWays, userTargetDirectory, + userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - dynamicGhcPrograms, laxDependencies + ghcDebugged, dynamicGhcPrograms, laxDependencies ) where import Expression @@ -21,9 +21,9 @@ userPackages = mempty userKnownPackages :: [Package] userKnownPackages = [] --- Control which ways are built -userWays :: Ways -userWays = mempty +-- Control which ways libraries and rts are built +userLibWays :: Ways +userLibWays = mempty userRtsWays :: Ways userRtsWays = mempty @@ -60,6 +60,10 @@ ghciWithDebugger = False ghcProfiled :: Bool ghcProfiled = False +-- TODO: do we need to be able to set this from command line? +ghcDebugged :: Bool +ghcDebugged = False + -- When laxDependencies flag is set to True, dependencies on the GHC executable -- are turned into order-only dependencies to avoid needless recompilation when -- making changes to GHC's sources. In certain situations this can lead to build diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index cafed64..ad42cea 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,26 +1,29 @@ -module Settings.Ways (getWays, getRtsWays) where +module Settings.Ways (getWays, getLibWays, getRtsWays) where import Expression import Predicates import Settings.User -- Combining default ways with user modifications +getLibWays :: Expr [Way] +getLibWays = fromDiffExpr $ defaultLibWays <> userLibWays + +-- In Stage0 we only build vanilla getWays :: Expr [Way] -getWays = fromDiffExpr $ defaultWays <> userWays +getWays = mconcat [ stage0 ? return [vanilla], notStage0 ? getLibWays ] getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays -- These are default ways -defaultWays :: Ways -defaultWays = mconcat - [ append [vanilla] -- always build vanilla - , notStage0 ? append [profiling] +defaultLibWays :: Ways +defaultLibWays = mconcat + [ append [vanilla, profiling] , platformSupportsSharedLibs ? append [dynamic] ] defaultRtsWays :: Ways defaultRtsWays = do - ways <- getWays + ways <- getLibWays mconcat [ append [ logging, debug, threaded, threadedDebug, threadedLogging ] , (profiling `elem` ways) ? append [threadedProfiling] From git at git.haskell.org Thu Oct 26 23:38:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:38:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: This should work, I guess. (019b513) Message-ID: <20171026233857.C17D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/019b51376ee25ec0d73931f3bd946bf2d3c23e71/ghc >--------------------------------------------------------------- commit 019b51376ee25ec0d73931f3bd946bf2d3c23e71 Author: Moritz Angermann Date: Wed Jan 6 12:38:22 2016 +0800 This should work, I guess. >--------------------------------------------------------------- 019b51376ee25ec0d73931f3bd946bf2d3c23e71 .travis.yml | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 33c4c3e..4a2179d 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,10 +18,9 @@ addons: sources: hvr-ghc before_install: - osx: - - brew update - - brew outdated ghc || brew upgrade ghc - - brew outdated cabal-install || brew upgrade cabal-install + - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi + - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated ghc || brew upgrade ghc; fi + - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated cabal-install || brew upgrade cabal-install; fi - PATH="$HOME/.cabal/bin:$PATH" - PATH="/opt/ghc/$GHCVER/bin:$PATH" From git at git.haskell.org Thu Oct 26 23:39:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement all modes of GenPrimopCode builder. (1a17fee) Message-ID: <20171026233900.F08B73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a17fee2b8dc82a4b4778cf1f3219fdad584db8d/ghc >--------------------------------------------------------------- commit 1a17fee2b8dc82a4b4778cf1f3219fdad584db8d Author: Andrey Mokhov Date: Thu Sep 24 05:49:39 2015 +0100 Implement all modes of GenPrimopCode builder. >--------------------------------------------------------------- 1a17fee2b8dc82a4b4778cf1f3219fdad584db8d src/Settings/Builders/GenPrimopCode.hs | 23 +++++++++++++++++++++-- 1 file changed, 21 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/GenPrimopCode.hs b/src/Settings/Builders/GenPrimopCode.hs index 711aa80..6de1f47 100644 --- a/src/Settings/Builders/GenPrimopCode.hs +++ b/src/Settings/Builders/GenPrimopCode.hs @@ -1,8 +1,27 @@ module Settings.Builders.GenPrimopCode (genPrimopCodeArgs) where import Expression -import Predicates (builder) +import Predicates (builder, file) -- Stdin/stdout are handled in a special way. See Rules/Actions.hs. +-- TODO: Do we want to keep "--usage"? It seems to be unused. genPrimopCodeArgs :: Args -genPrimopCodeArgs = builder GenPrimopCode ? arg "--make-haskell-wrappers" +genPrimopCodeArgs = builder GenPrimopCode ? mconcat + [ file "//PrimopWrappers.hs" ? arg "--make-haskell-wrappers" + , file "//Prim.hs" ? arg "--make-haskell-source" + , file "//primop-data-decl.hs-incl" ? arg "--data-decl" + , file "//primop-tag.hs-incl" ? arg "--primop-tag" + , file "//primop-list.hs-incl" ? arg "--primop-list" + , file "//primop-has-side-effects.hs-incl" ? arg "--has-side-effects" + , file "//primop-out-of-line.hs-incl" ? arg "--out-of-line" + , file "//primop-commutable.hs-incl" ? arg "--commutable" + , file "//primop-code-size.hs-incl" ? arg "--code-size" + , file "//primop-can-fail.hs-incl" ? arg "--can-fail" + , file "//primop-strictness.hs-incl" ? arg "--strictness" + , file "//primop-fixity.hs-incl" ? arg "--fixity" + , file "//primop-primop-info.hs-incl" ? arg "--primop-primop-info" + , file "//primop-vector-uniques.hs-incl" ? arg "--primop-vector-uniques" + , file "//primop-vector-tys.hs-incl" ? arg "--primop-vector-tys" + , file "//primop-vector-tys-exports.hs-incl" ? arg "--primop-vector-tys-exports" + , file "//primop-vector-tycons.hs-incl" ? arg "--primop-vector-tycons" + , file "//primop-usage.hs-incl" ? arg "--usage" ] From git at git.haskell.org Thu Oct 26 23:39:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use install. (59c09b8) Message-ID: <20171026233901.4B22D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59c09b8be58c2f1fd8e75788d9bccf63e9ff1458/ghc >--------------------------------------------------------------- commit 59c09b8be58c2f1fd8e75788d9bccf63e9ff1458 Author: Moritz Angermann Date: Wed Jan 6 12:43:17 2016 +0800 Use install. >--------------------------------------------------------------- 59c09b8be58c2f1fd8e75788d9bccf63e9ff1458 .travis.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4a2179d..6e1bf5b 100644 --- a/.travis.yml +++ b/.travis.yml @@ -19,8 +19,7 @@ addons: before_install: - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated ghc || brew upgrade ghc; fi - - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated cabal-install || brew upgrade cabal-install; fi + - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi - PATH="$HOME/.cabal/bin:$PATH" - PATH="/opt/ghc/$GHCVER/bin:$PATH" From git at git.haskell.org Thu Oct 26 23:39:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix untracked .hs-incl dependencies. (9b9f7d2) Message-ID: <20171026233904.984D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b9f7d2fd05b4bb146d794bd9fd1e67ba8311cb2/ghc >--------------------------------------------------------------- commit 9b9f7d2fd05b4bb146d794bd9fd1e67ba8311cb2 Author: Andrey Mokhov Date: Thu Sep 24 05:50:17 2015 +0100 Fix untracked .hs-incl dependencies. >--------------------------------------------------------------- 9b9f7d2fd05b4bb146d794bd9fd1e67ba8311cb2 src/Rules/Dependencies.hs | 22 +++++++++++++++++++++- 1 file changed, 21 insertions(+), 1 deletion(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index c9b5b89..8fd9ca8 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -1,6 +1,7 @@ module Rules.Dependencies (buildPackageDependencies) where import Expression +import GHC import Oracles import Rules.Actions import Rules.Resources @@ -30,4 +31,23 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need $ hDepFile : cDepFiles -- need all for more parallelism cDeps <- fmap concat $ mapM readFile' cDepFiles hDeps <- readFile' hDepFile - writeFileChanged file $ cDeps ++ hDeps + -- TODO: very ugly and fragile + let hsIncl hs incl = buildPath -/- hs <.> "o" ++ " : " + ++ buildPath -/- incl ++ "\n" + extraDeps = if pkg /= compiler then [] else + hsIncl "PrelNames" "primop-vector-uniques.hs-incl" + ++ hsIncl "PrimOp" "primop-data-decl.hs-incl" + ++ hsIncl "PrimOp" "primop-tag.hs-incl" + ++ hsIncl "PrimOp" "primop-list.hs-incl" + ++ hsIncl "PrimOp" "primop-strictness.hs-incl" + ++ hsIncl "PrimOp" "primop-fixity.hs-incl" + ++ hsIncl "PrimOp" "primop-primop-info.hs-incl" + ++ hsIncl "PrimOp" "primop-out-of-line.hs-incl" + ++ hsIncl "PrimOp" "primop-has-side-effects.hs-incl" + ++ hsIncl "PrimOp" "primop-can-fail.hs-incl" + ++ hsIncl "PrimOp" "primop-code-size.hs-incl" + ++ hsIncl "PrimOp" "primop-commutable.hs-incl" + ++ hsIncl "TysPrim" "primop-vector-tys-exports.hs-incl" + ++ hsIncl "TysPrim" "primop-vector-tycons.hs-incl" + ++ hsIncl "TysPrim" "primop-vector-tys.hs-incl" + writeFileChanged file $ cDeps ++ hDeps ++ extraDeps From git at git.haskell.org Thu Oct 26 23:39:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install alex, happy; adjust path only on ghc/cabal path only on linux. (17306dc) Message-ID: <20171026233904.E462B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/17306dc5a8e5ff70b3a0b973915fc6e6ec5cc3b7/ghc >--------------------------------------------------------------- commit 17306dc5a8e5ff70b3a0b973915fc6e6ec5cc3b7 Author: Moritz Angermann Date: Wed Jan 6 12:50:09 2016 +0800 Install alex, happy; adjust path only on ghc/cabal path only on linux. >--------------------------------------------------------------- 17306dc5a8e5ff70b3a0b973915fc6e6ec5cc3b7 .travis.yml | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 6e1bf5b..64e8597 100644 --- a/.travis.yml +++ b/.travis.yml @@ -5,7 +5,9 @@ os: - osx env: - - CABALVER=1.22 GHCVER=7.10.3 + matrix: + linux: + - CABALVER=1.22 GHCVER=7.10.3 addons: apt: @@ -20,10 +22,10 @@ addons: before_install: - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi - + - if [ $TRAVIS_OS_NAME == osx ]; then cabal install alex happy; fi + - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/ghc/$GHCVER/bin:$PATH"; fi + - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/cabal/$CABALVER/bin:$PATH"; fi - PATH="$HOME/.cabal/bin:$PATH" - - PATH="/opt/ghc/$GHCVER/bin:$PATH" - - PATH="/opt/cabal/$CABALVER/bin:$PATH" - export PATH - env From git at git.haskell.org Thu Oct 26 23:39:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement new generate rules. (90301e1) Message-ID: <20171026233908.4BFB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90301e1bd2143ed9f04a1385024de60ff4a68009/ghc >--------------------------------------------------------------- commit 90301e1bd2143ed9f04a1385024de60ff4a68009 Author: Andrey Mokhov Date: Thu Sep 24 05:50:46 2015 +0100 Implement new generate rules. >--------------------------------------------------------------- 90301e1bd2143ed9f04a1385024de60ff4a68009 src/Rules/Generate.hs | 104 +++++++++++++++++++++++++++++--------------------- 1 file changed, 60 insertions(+), 44 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 90301e1bd2143ed9f04a1385024de60ff4a68009 From git at git.haskell.org Thu Oct 26 23:39:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reorder os and env (9ff8773) Message-ID: <20171026233908.9156B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ff8773943c628ec660bd59de0e48e1eb9dd2e22/ghc >--------------------------------------------------------------- commit 9ff8773943c628ec660bd59de0e48e1eb9dd2e22 Author: Moritz Angermann Date: Wed Jan 6 12:55:34 2016 +0800 Reorder os and env >--------------------------------------------------------------- 9ff8773943c628ec660bd59de0e48e1eb9dd2e22 .travis.yml | 13 +++++-------- 1 file changed, 5 insertions(+), 8 deletions(-) diff --git a/.travis.yml b/.travis.yml index 64e8597..72e2f80 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,13 +1,10 @@ sudo: false -os: - - linux - - osx - -env: - matrix: - linux: - - CABALVER=1.22 GHCVER=7.10.3 +matrix: + include: + - os: linux + env: CABALVER=1.22 GHCVER=7.10.3 + - os: osx addons: apt: From git at git.haskell.org Thu Oct 26 23:39:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new builder HsCpp. (45d41a5) Message-ID: <20171026233911.AAD483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45d41a568b324f37d992fdcd616726959d4c439d/ghc >--------------------------------------------------------------- commit 45d41a568b324f37d992fdcd616726959d4c439d Author: Andrey Mokhov Date: Thu Sep 24 12:44:38 2015 +0100 Add new builder HsCpp. >--------------------------------------------------------------- 45d41a568b324f37d992fdcd616726959d4c439d cfg/system.config.in | 2 ++ src/Builder.hs | 2 ++ src/Rules/Actions.hs | 5 +++++ src/Settings/Args.hs | 2 ++ src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/HsCpp.hs | 17 +++++++++++++++++ src/Settings/Builders/Hsc2Hs.hs | 2 +- 7 files changed, 30 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 87d2b93..e85788b 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -23,6 +23,8 @@ hsc2hs = @hardtop@/inplace/bin/hsc2hs genprimopcode = @hardtop@/inplace/bin/genprimopcode +hs-cpp = @HaskellCPPCmd@ @HaskellCPPArgs@ + unlit = @hardtop@/inplace/lib/unlit ghc-split = @hardtop@/inplace/lib/ghc-split diff --git a/src/Builder.hs b/src/Builder.hs index a6521a1..e1c69be 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -30,6 +30,7 @@ data Builder = Alex | Haddock | Happy | HsColour + | HsCpp | Hsc2Hs | Ld | Unlit @@ -58,6 +59,7 @@ builderKey builder = case builder of Haddock -> "haddock" HsColour -> "hscolour" Hsc2Hs -> "hsc2hs" + HsCpp -> "hs-cpp" Ld -> "ld" Unlit -> "unlit" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 1e0472a..8214112 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -32,6 +32,11 @@ buildWithResources rs target = do forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> unit . cmd [path] $ persistentArgs ++ argsChunk + HsCpp -> do + let file = head $ Target.files target -- TODO: ugly + Stdout output <- cmd [path] argList + writeFileChanged file output + GenPrimopCode -> do let src = head $ Target.sources target -- TODO: ugly file = head $ Target.files target diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 349668a..231f5ed 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -11,6 +11,7 @@ import Settings.Builders.GhcPkg import Settings.Builders.Haddock import Settings.Builders.Happy import Settings.Builders.Hsc2Hs +import Settings.Builders.HsCpp import Settings.Builders.Ld import Settings.User @@ -41,4 +42,5 @@ defaultArgs = mconcat , haddockArgs , happyArgs , hsc2HsArgs + , hsCppArgs , ldArgs ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 54452d8..b68da27 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,6 +1,6 @@ module Settings.Builders.GhcCabal ( cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, - ccArgs, ccWarnings, argStagedSettingList + ccArgs, cppArgs, ccWarnings, argStagedSettingList ) where import Expression diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs new file mode 100644 index 0000000..da104cc --- /dev/null +++ b/src/Settings/Builders/HsCpp.hs @@ -0,0 +1,17 @@ +module Settings.Builders.HsCpp (hsCppArgs) where + +import Expression +import Predicates (builder) +import Settings.Builders.GhcCabal + +-- TODO: why process the result with grep -v '^#pragma GCC'? No such lines! +hsCppArgs :: Args +hsCppArgs = builder HsCpp ? do + stage <- getStage + src <- getSource + mconcat [ arg "-P" + , cppArgs + , arg $ "-Icompiler/stage" ++ show stage + , arg "-x" + , arg "c" + , arg src ] diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 7dfe286..dcf44fc 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -4,7 +4,7 @@ import Expression import Oracles import Predicates (builder, stage0, notStage0) import Settings -import Settings.Builders.GhcCabal +import Settings.Builders.GhcCabal hiding (cppArgs) hsc2HsArgs :: Args hsc2HsArgs = builder Hsc2Hs ? do From git at git.haskell.org Thu Oct 26 23:39:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: run cabal update (e18abef) Message-ID: <20171026233912.0AF4A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e18abefe7f05cda6f758eb3b46f283e431aaa590/ghc >--------------------------------------------------------------- commit e18abefe7f05cda6f758eb3b46f283e431aaa590 Author: Moritz Angermann Date: Wed Jan 6 12:55:41 2016 +0800 run cabal update >--------------------------------------------------------------- e18abefe7f05cda6f758eb3b46f283e431aaa590 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 72e2f80..b21b89e 100644 --- a/.travis.yml +++ b/.travis.yml @@ -19,6 +19,7 @@ addons: before_install: - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi + - if [ $TRAVIS_OS_NAME == osx ]; then cabal update; fi - if [ $TRAVIS_OS_NAME == osx ]; then cabal install alex happy; fi - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/ghc/$GHCVER/bin:$PATH"; fi - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/cabal/$CABALVER/bin:$PATH"; fi From git at git.haskell.org Thu Oct 26 23:39:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more thoughts. (14e4942) Message-ID: <20171026233915.A62263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14e49425f1760d8425ab518c0a49644e415c8173/ghc >--------------------------------------------------------------- commit 14e49425f1760d8425ab518c0a49644e415c8173 Author: Andrey Mokhov Date: Thu Sep 24 12:44:59 2015 +0100 Add more thoughts. >--------------------------------------------------------------- 14e49425f1760d8425ab518c0a49644e415c8173 doc/meeting-25-September-2015.txt | 19 +++++++++++++++++-- 1 file changed, 17 insertions(+), 2 deletions(-) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt index 6ee4297..caf0e8e 100644 --- a/doc/meeting-25-September-2015.txt +++ b/doc/meeting-25-September-2015.txt @@ -3,7 +3,20 @@ Shaking up GHC meeting, 25 September 2015 Things to discuss: ================================================ -1. Better names for build stages +1. Progress report + + +++ Dealing with seemingly dead-code artefacts of the old build systems. I used to carefully migrate all code to the new build system, but it is getting more in the way of readability. New proposal: drop all such suspicious instances and bring them back only if things break. Example: + +C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe -E -undef -traditional -P -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -Icompiler/stage2 -x c compiler/prelude/primops.txt.pp | grep -v '^#pragma GCC' > compiler/stage2/build/primops.txt + +But primops.txt.pp has no lines containing #pragma GCC! Dead code? + +++ Zero build is 7 seconds + +++ .hs-incl includes are currently not tracked properly (e.g. ghc -MM does not list them). See Dependencies.hs + +++ Better names for build stages * Currently we have Stage0, Stage1, etc. It is not particularly clear from the names what they stand for. We no longer need to stick to @@ -21,8 +34,10 @@ i. Unclear abstractions Builder/BuildRule... ii. Limits to build parallelism: GHC crashes during parallel builds. Also ghc-pkg and ghc-cabal are apparently not thread-safe, so I had to use Shake resources to limit the parallelism... +iii. Discuss the need for command line options, e.g. make GhcDebugged=YES. This is a bit annoying to implement since Settings.User seems fairly readable, but recompiling the build systems for changing a flag may be annoying too. + -2. Do we need a name for the new build system? +iv. Do we need a name for the new build system? * At least we need a name for the folder in the GHC tree From git at git.haskell.org Thu Oct 26 23:39:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Can we put addons and before_install into the include? (a5aa58f) Message-ID: <20171026233915.E6A3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5aa58f81ceab822e035cb17f25bc05dec8dc092/ghc >--------------------------------------------------------------- commit a5aa58f81ceab822e035cb17f25bc05dec8dc092 Author: Moritz Angermann Date: Wed Jan 6 13:03:06 2016 +0800 Can we put addons and before_install into the include? >--------------------------------------------------------------- a5aa58f81ceab822e035cb17f25bc05dec8dc092 .travis.yml | 40 +++++++++++++++++++++------------------- 1 file changed, 21 insertions(+), 19 deletions(-) diff --git a/.travis.yml b/.travis.yml index b21b89e..5c5708c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -4,28 +4,30 @@ matrix: include: - os: linux env: CABALVER=1.22 GHCVER=7.10.3 + addons: + apt: + packages: + - ghc-7.10.3 + - alex-3.1.4 + - happy-1.19.5 + - cabal-install-1.22 + - zlib1g-dev + sources: hvr-ghc + before_install: + - PATH="/opt/ghc/$GHCVER/bin:$PATH" + - PATH="/opt/cabal/$CABALVER/bin:$PATH" + - PATH="$HOME/.cabal/bin:$PATH" + - export PATH - os: osx - -addons: - apt: - packages: - - ghc-7.10.3 - - alex-3.1.4 - - happy-1.19.5 - - cabal-install-1.22 - - zlib1g-dev - sources: hvr-ghc + before_install: + - brew update + - brew install ghc cabal-install + - cabal update + - cabal install alex happy + - PATH="$HOME/.cabal/bin:$PATH" + - export PATH before_install: - - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi - - if [ $TRAVIS_OS_NAME == osx ]; then cabal update; fi - - if [ $TRAVIS_OS_NAME == osx ]; then cabal install alex happy; fi - - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/ghc/$GHCVER/bin:$PATH"; fi - - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/cabal/$CABALVER/bin:$PATH"; fi - - PATH="$HOME/.cabal/bin:$PATH" - - export PATH - - env - ghc --version - cabal --version From git at git.haskell.org Thu Oct 26 23:39:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ArSupportsAtFile, BuildPlatform, HostPlatform, TargetPlatform flags. (f164cdc) Message-ID: <20171026233919.BFBCF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f164cdc5a83432f5f4c156be4a1d518650cb1045/ghc >--------------------------------------------------------------- commit f164cdc5a83432f5f4c156be4a1d518650cb1045 Author: Andrey Mokhov Date: Thu Sep 24 23:41:37 2015 +0100 Add ArSupportsAtFile, BuildPlatform, HostPlatform, TargetPlatform flags. >--------------------------------------------------------------- f164cdc5a83432f5f4c156be4a1d518650cb1045 cfg/system.config.in | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index e85788b..09ea1fa 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -23,7 +23,8 @@ hsc2hs = @hardtop@/inplace/bin/hsc2hs genprimopcode = @hardtop@/inplace/bin/genprimopcode -hs-cpp = @HaskellCPPCmd@ @HaskellCPPArgs@ +hs-cpp = @HaskellCPPCmd@ +hs-cpp-args = @HaskellCPPArgs@ unlit = @hardtop@/inplace/lib/unlit ghc-split = @hardtop@/inplace/lib/ghc-split @@ -37,8 +38,9 @@ hscolour = @HSCOLOUR@ # Information about builders: #============================ -gcc-is-clang = @GccIsClang@ -gcc-lt-46 = @GccLT46@ +gcc-is-clang = @GccIsClang@ +gcc-lt-46 = @GccLT46@ +ar-supports-at-file = @ArSupportsAtFile@ # Build options: #=============== @@ -50,15 +52,24 @@ ghc-unregisterised = @Unregisterised@ ghc-source-path = @hardtop@ leading-underscore = @LeadingUnderscore@ -# Information about host and target systems: -#=========================================== +# Information about build, host and target systems: +#================================================== -target-os = @TargetOS_CPP@ -target-arch = @TargetArch_CPP@ -target-platform-full = @TargetPlatformFull@ +build-platform = @BuildPlatform@ +build-arch = @BuildArch_CPP@ +build-os = @BuildOS_CPP@ +build-vendor = @BuildVendor_CPP@ -host-os = @HostOS_CPP@ +host-platform = @HostPlatform@ host-arch = @HostArch_CPP@ +host-os = @HostOS_CPP@ +host-vendor = @HostVendor_CPP@ + +target-platform = @TargetPlatform@ +target-platform-full = @TargetPlatformFull@ +target-arch = @TargetArch_CPP@ +target-os = @TargetOS_CPP@ +target-vendor = @TargetVendor_CPP@ cross-compiling = @CrossCompiling@ From git at git.haskell.org Thu Oct 26 23:39:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: before_install steps don't merge (12c433c) Message-ID: <20171026233920.081FD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12c433c197e3e1db24d535aae5c7d07a6dc50e8a/ghc >--------------------------------------------------------------- commit 12c433c197e3e1db24d535aae5c7d07a6dc50e8a Author: Moritz Angermann Date: Wed Jan 6 13:11:19 2016 +0800 before_install steps don't merge Moved the validation of before_install into install. >--------------------------------------------------------------- 12c433c197e3e1db24d535aae5c7d07a6dc50e8a .travis.yml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 5c5708c..1bcd7fd 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,6 +18,8 @@ matrix: - PATH="/opt/cabal/$CABALVER/bin:$PATH" - PATH="$HOME/.cabal/bin:$PATH" - export PATH + - cabal update + - os: osx before_install: - brew update @@ -27,15 +29,14 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH -before_install: + +install: + - env - ghc --version - cabal --version - alex --version - happy --version - - cabal update - -install: - travis_retry git clone git://git.haskell.org/ghc --recurse-submodules From git at git.haskell.org Thu Oct 26 23:39:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ArSupportsAtFile flag. (093c1a9) Message-ID: <20171026233923.30B423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/093c1a95e1e29df19985840d22138b798744da3c/ghc >--------------------------------------------------------------- commit 093c1a95e1e29df19985840d22138b798744da3c Author: Andrey Mokhov Date: Thu Sep 24 23:42:10 2015 +0100 Add ArSupportsAtFile flag. >--------------------------------------------------------------- 093c1a95e1e29df19985840d22138b798744da3c src/Oracles/Config/Flag.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 69d4884..f352ae3 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -8,7 +8,8 @@ import Base import Oracles.Config import Oracles.Config.Setting -data Flag = CrossCompiling +data Flag = ArSupportsAtFile + | CrossCompiling | GccIsClang | GccLt46 | GhcUnregisterised @@ -22,6 +23,7 @@ data Flag = CrossCompiling flag :: Flag -> Action Bool flag f = do key <- return $ case f of + ArSupportsAtFile -> "ar-supports-at-file" CrossCompiling -> "cross-compiling" GccIsClang -> "gcc-is-clang" GccLt46 -> "gcc-lt-46" From git at git.haskell.org Thu Oct 26 23:39:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set CONFIG_SHELL, such that libtool obtains the bash header. (cb74ce8) Message-ID: <20171026233923.6FCCC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb74ce8f2ca00bc2cfac8b003c4c7adade5734af/ghc >--------------------------------------------------------------- commit cb74ce8f2ca00bc2cfac8b003c4c7adade5734af Author: Moritz Angermann Date: Wed Jan 6 14:37:10 2016 +0800 Set CONFIG_SHELL, such that libtool obtains the bash header. This improves on #103 and fixes #114, hopefully. >--------------------------------------------------------------- cb74ce8f2ca00bc2cfac8b003c4c7adade5734af src/Rules/Actions.hs | 6 +++++- src/Rules/IntegerGmp.hs | 2 +- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9250357..e32a42f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -94,7 +94,11 @@ runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] putBuild $ "| Run configure in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args + quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args + where + -- Always configure with bash. + -- This also injects /bin/bash into `libtool`, instead of /bin/sh + opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] runMake :: FilePath -> [String] -> Action () runMake dir args = do diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 2b9bbd9..7ef124f 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -114,7 +114,7 @@ integerGmpRules = do copyFile integerGmpLibraryFakeH integerGmpLibraryH else do putBuild "| No GMP framework detected; in tree GMP will be built" - runMake integerGmpBuild ["MAKEFLAGS='LIBTOOL=bash\\ libtool'"] + runMake integerGmpBuild [] copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryInTreeH copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryH From git at git.haskell.org Thu Oct 26 23:39:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new setting keys. (2ed0b04) Message-ID: <20171026233926.E9D673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ed0b0414b2cd247808ea3c5e94b27e0556bc9ab/ghc >--------------------------------------------------------------- commit 2ed0b0414b2cd247808ea3c5e94b27e0556bc9ab Author: Andrey Mokhov Date: Thu Sep 24 23:42:47 2015 +0100 Add new setting keys. >--------------------------------------------------------------- 2ed0b0414b2cd247808ea3c5e94b27e0556bc9ab src/Oracles/Config/Setting.hs | 21 ++++++++++++++++++++- 1 file changed, 20 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index e1dfefa..fa62f97 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -10,13 +10,18 @@ import Base import Oracles.Config import Stage +-- TODO: reduce the variety of similar flags (e.g. CPP and non-CPP versions). -- Each Setting comes from the system.config file, e.g. 'target-os = mingw32'. -- setting TargetOs looks up the config file and returns "mingw32". -- -- SettingList is used for multiple string values separated by spaces, such -- as 'gmp-include-dirs = a b'. -- settingList GmpIncludeDirs therefore returns a list of strings ["a", "b"]. -data Setting = DynamicExtension +data Setting = BuildArch + | BuildOs + | BuildPlatform + | BuildVendor + | DynamicExtension | GhcMajorVersion | GhcMinorVersion | GhcPatchLevel @@ -24,6 +29,8 @@ data Setting = DynamicExtension | GhcSourcePath | HostArch | HostOs + | HostPlatform + | HostVendor | ProjectGitCommitId | ProjectName | ProjectVersion @@ -33,7 +40,9 @@ data Setting = DynamicExtension | ProjectPatchLevel2 | TargetArch | TargetOs + | TargetPlatform | TargetPlatformFull + | TargetVendor data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -41,11 +50,16 @@ data SettingList = ConfCcArgs Stage | ConfLdLinkerArgs Stage | GmpIncludeDirs | GmpLibDirs + | HsCppArgs | IconvIncludeDirs | IconvLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of + BuildArch -> "build-arch" + BuildOs -> "build-os" + BuildPlatform -> "build-platform" + BuildVendor -> "build-vendor" DynamicExtension -> "dynamic-extension" GhcMajorVersion -> "ghc-major-version" GhcMinorVersion -> "ghc-minor-version" @@ -54,6 +68,8 @@ setting key = askConfig $ case key of GhcSourcePath -> "ghc-source-path" HostArch -> "host-arch" HostOs -> "host-os" + HostPlatform -> "host-platform" + HostVendor -> "host-vendor" ProjectGitCommitId -> "project-git-commit-id" ProjectName -> "project-name" ProjectVersion -> "project-version" @@ -63,7 +79,9 @@ setting key = askConfig $ case key of ProjectPatchLevel2 -> "project-patch-level2" TargetArch -> "target-arch" TargetOs -> "target-os" + TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" + TargetVendor -> "target-vendor" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -73,6 +91,7 @@ settingList key = fmap words $ askConfig $ case key of ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show stage GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" + HsCppArgs -> "hs-cpp-args" IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" From git at git.haskell.org Thu Oct 26 23:39:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove -Wall and -fwarn-tabs, fix #116. (f8d9ddc) Message-ID: <20171026233927.41D813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8d9ddc5a43872f248d60e7fcdb1f0c5be580cc1/ghc >--------------------------------------------------------------- commit f8d9ddc5a43872f248d60e7fcdb1f0c5be580cc1 Author: Andrey Mokhov Date: Wed Jan 6 10:41:19 2016 +0000 Remove -Wall and -fwarn-tabs, fix #116. >--------------------------------------------------------------- f8d9ddc5a43872f248d60e7fcdb1f0c5be580cc1 src/Settings/User.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index aba4a48..7a877ce 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -8,11 +8,11 @@ module Settings.User ( import GHC import Expression +import Predicates --- No user-specific settings by default --- TODO: rename to userArgs +-- Control user-specific settings userArgs :: Args -userArgs = mempty +userArgs = builderGhc ? remove ["-Wall", "-fwarn-tabs"] -- Control which packages get to be built userPackages :: Packages From git at git.haskell.org Thu Oct 26 23:39:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new mode for Ar builder: useAtFile (big performance increase). (6cde985) Message-ID: <20171026233930.E73F43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6cde9851e61a88b0773e07346752279129c87d41/ghc >--------------------------------------------------------------- commit 6cde9851e61a88b0773e07346752279129c87d41 Author: Andrey Mokhov Date: Thu Sep 24 23:44:34 2015 +0100 Add new mode for Ar builder: useAtFile (big performance increase). >--------------------------------------------------------------- 6cde9851e61a88b0773e07346752279129c87d41 src/Rules/Actions.hs | 23 ++++++++--------------- src/Settings/Builders/Ar.hs | 31 ++++++++++++++++++++++++++++--- 2 files changed, 36 insertions(+), 18 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 8214112..5f15f3d 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,7 +1,6 @@ module Rules.Actions (build, buildWithResources) where import Expression -import Oracles import Oracles.ArgsHash import Settings import Settings.Args @@ -18,19 +17,13 @@ buildWithResources rs target = do path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed - when trackBuildSystem $ checkArgsHash target + checkArgsHash target withResources rs $ do - putBuild $ "/--------\n" ++ "| Running " - ++ show builder ++ " with arguments:" + putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList putBuild $ "\\--------" quietly $ case builder of - Ar -> do -- Split argument list into chunks as otherwise Ar chokes up - maxChunk <- cmdLineLengthLimit - let persistentArgs = take arPersistentArgsCount argList - remainingArgs = drop arPersistentArgsCount argList - forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> - unit . cmd [path] $ persistentArgs ++ argsChunk + Ar -> arCmd path argList HsCpp -> do let file = head $ Target.files target -- TODO: ugly @@ -63,14 +56,14 @@ interestingInfo builder ss = case builder of Haddock -> prefixAndSuffix 1 0 ss Happy -> prefixAndSuffix 0 3 ss Hsc2Hs -> prefixAndSuffix 0 3 ss + HsCpp -> prefixAndSuffix 0 1 ss Ld -> prefixAndSuffix 4 0 ss _ -> ss where prefixAndSuffix n m list = - if length list <= n + m + 1 + let len = length list in + if len <= n + m + 1 then list else take n list - ++ ["... skipping " - ++ show (length list - n - m) - ++ " arguments ..."] - ++ drop (length list - m) list + ++ ["... skipping " ++ show (len - n - m) ++ " arguments ..."] + ++ drop (len - m) list diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 082cbaf..7b6eb59 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,6 +1,7 @@ -module Settings.Builders.Ar (arArgs, arPersistentArgsCount) where +module Settings.Builders.Ar (arArgs, arCmd) where import Expression +import Oracles import Predicates (builder) arArgs :: Args @@ -13,5 +14,29 @@ arArgs = builder Ar ? do -- This count includes arg "q" and arg file parameters in arArgs (see above). -- Update this value appropriately when changing arArgs. -arPersistentArgsCount :: Int -arPersistentArgsCount = 2 +arFlagsCount :: Int +arFlagsCount = 2 + +-- Ar needs to be invoked in a special way: we pass the list of files to be +-- archived via a temporary file as otherwise Ar (or rather Windows command +-- line) chokes up. Alternatively, we split argument list into chunks and call +-- ar multiple times (when passing files via a separate file is not supported). +arCmd :: FilePath -> [String] -> Action () +arCmd path argList = do + arSupportsAtFile <- flag ArSupportsAtFile + let flagArgs = take arFlagsCount argList + fileArgs = drop arFlagsCount argList + if arSupportsAtFile + then useAtFile path flagArgs fileArgs + else useSuccessiveInvokations path flagArgs fileArgs + +useAtFile :: FilePath -> [String] -> [String] -> Action () +useAtFile path flagArgs fileArgs = withTempFile $ \tmp -> do + writeFile' tmp $ unwords fileArgs + cmd [path] flagArgs ('@' : tmp) + +useSuccessiveInvokations :: FilePath -> [String] -> [String] -> Action () +useSuccessiveInvokations path flagArgs fileArgs = do + maxChunk <- cmdLineLengthLimit + forM_ (chunksOfSize maxChunk fileArgs) $ \argsChunk -> + unit . cmd [path] $ flagArgs ++ argsChunk From git at git.haskell.org Thu Oct 26 23:39:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds "MAKEFLAGS=" back in. (7b5c5bf) Message-ID: <20171026233931.345F73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b5c5bf2250f088bac663c2d2773b32d5e1b756b/ghc >--------------------------------------------------------------- commit 7b5c5bf2250f088bac663c2d2773b32d5e1b756b Author: Moritz Angermann Date: Wed Jan 6 18:48:56 2016 +0800 Adds "MAKEFLAGS=" back in. >--------------------------------------------------------------- 7b5c5bf2250f088bac663c2d2773b32d5e1b756b src/Rules/IntegerGmp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 7ef124f..b82dcbb 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -114,7 +114,7 @@ integerGmpRules = do copyFile integerGmpLibraryFakeH integerGmpLibraryH else do putBuild "| No GMP framework detected; in tree GMP will be built" - runMake integerGmpBuild [] + runMake integerGmpBuild ["MAKEFLAGS="] copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryInTreeH copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryH From git at git.haskell.org Thu Oct 26 23:39:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix HsCpp argument list. (555265c) Message-ID: <20171026233934.8C1393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/555265ce0686be733a2a3f66abbab1bc8771d237/ghc >--------------------------------------------------------------- commit 555265ce0686be733a2a3f66abbab1bc8771d237 Author: Andrey Mokhov Date: Thu Sep 24 23:45:01 2015 +0100 Fix HsCpp argument list. >--------------------------------------------------------------- 555265ce0686be733a2a3f66abbab1bc8771d237 src/Settings/Builders/HsCpp.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs index da104cc..cad2897 100644 --- a/src/Settings/Builders/HsCpp.hs +++ b/src/Settings/Builders/HsCpp.hs @@ -1,6 +1,7 @@ module Settings.Builders.HsCpp (hsCppArgs) where import Expression +import Oracles import Predicates (builder) import Settings.Builders.GhcCabal @@ -9,9 +10,11 @@ hsCppArgs :: Args hsCppArgs = builder HsCpp ? do stage <- getStage src <- getSource - mconcat [ arg "-P" + args <- getSettingList HsCppArgs + mconcat [ append args + , arg "-P" , cppArgs - , arg $ "-Icompiler/stage" ++ show stage + , arg $ "-Icompiler/stage" ++ show (succ stage) , arg "-x" , arg "c" , arg src ] From git at git.haskell.org Thu Oct 26 23:39:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve Generate rule: clean up code, more accurate dependencies. (9253049) Message-ID: <20171026233937.F35B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/925304968b4da8050e618b004cfdccfe0cb895e6/ghc >--------------------------------------------------------------- commit 925304968b4da8050e618b004cfdccfe0cb895e6 Author: Andrey Mokhov Date: Thu Sep 24 23:46:24 2015 +0100 Improve Generate rule: clean up code, more accurate dependencies. >--------------------------------------------------------------- 925304968b4da8050e618b004cfdccfe0cb895e6 src/Rules/Dependencies.hs | 3 + src/Rules/Generate.hs | 217 ++++++++++++++++++++++++++++++---------------- 2 files changed, 146 insertions(+), 74 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 925304968b4da8050e618b004cfdccfe0cb895e6 From git at git.haskell.org Thu Oct 26 23:39:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #115 from angerman/feature/libtool (2f52d19) Message-ID: <20171026233934.B81FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f52d196dbd5cd3f1da25286deef5cb3cd17c142/ghc >--------------------------------------------------------------- commit 2f52d196dbd5cd3f1da25286deef5cb3cd17c142 Merge: f8d9ddc 7b5c5bf Author: Andrey Mokhov Date: Wed Jan 6 10:51:29 2016 +0000 Merge pull request #115 from angerman/feature/libtool Set CONFIG_SHELL, such that libtool obtains the bash header. >--------------------------------------------------------------- 2f52d196dbd5cd3f1da25286deef5cb3cd17c142 src/Rules/Actions.hs | 6 +++++- src/Rules/IntegerGmp.hs | 2 +- 2 files changed, 6 insertions(+), 2 deletions(-) From git at git.haskell.org Thu Oct 26 23:39:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #112 from angerman/feature/osx-ci (6095058) Message-ID: <20171026233938.2D1E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/609505834ca4a9178b8263b00208ec651318c8c1/ghc >--------------------------------------------------------------- commit 609505834ca4a9178b8263b00208ec651318c8c1 Merge: 2f52d19 12c433c Author: Andrey Mokhov Date: Wed Jan 6 10:56:48 2016 +0000 Merge pull request #112 from angerman/feature/osx-ci Adds osx to the list of operatin systems in the travis.yml >--------------------------------------------------------------- 609505834ca4a9178b8263b00208ec651318c8c1 .travis.yml | 55 +++++++++++++++++++++++++++++-------------------------- 1 file changed, 29 insertions(+), 26 deletions(-) From git at git.haskell.org Thu Oct 26 23:39:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghc-bin package. (6a0c30f) Message-ID: <20171026233941.79AC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a0c30ff7dad21754967ab9178e7ad3b88c1598d/ghc >--------------------------------------------------------------- commit 6a0c30ff7dad21754967ab9178e7ad3b88c1598d Author: Andrey Mokhov Date: Thu Sep 24 23:47:18 2015 +0100 Add ghc-bin package. >--------------------------------------------------------------- 6a0c30ff7dad21754967ab9178e7ad3b88c1598d src/GHC.hs | 18 ++++++++++-------- src/Settings/Builders/GhcCabal.hs | 6 ++++++ src/Settings/Packages.hs | 6 +++--- src/Settings/User.hs | 2 +- 4 files changed, 20 insertions(+), 12 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 8f25c7c..c277c6a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,8 +1,8 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, - integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, - terminfo, time, transformers, unix, win32, xhtml, + deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + integerGmp, integerSimple, parallel, pretty, primitive, process, stm, + templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory ) where @@ -18,15 +18,15 @@ import Stage defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc - , integerGmp, integerSimple, parallel, pretty, primitive, process, stm + , containers, deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl + , hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm , templateHaskell, terminfo, time, transformers, unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, - integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, - terminfo, time, transformers, unix, win32, xhtml :: Package + deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + integerGmp, integerSimple, parallel, pretty, primitive, process, stm, + templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -39,6 +39,7 @@ containers = library "containers" deepseq = library "deepseq" directory = library "directory" filepath = library "filepath" +ghc = topLevel "ghc-bin" `setPath` "ghc" ghcPrim = library "ghc-prim" haskeline = library "haskeline" hoopl = library "hoopl" @@ -67,5 +68,6 @@ xhtml = library "xhtml" defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage package | package == compiler = "stage" ++ show (fromEnum stage + 1) + | package == ghc = "stage" ++ show (fromEnum stage + 1) | stage == Stage0 = "dist-boot" | otherwise = "dist-install" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index b68da27..582a56c 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -166,6 +166,12 @@ customPackageArgs = do , ghcProfiled ? notStage0 ? arg "--ghc-pkg-option=--force" ] + , package ghc ? + builder GhcCabal ? + mconcat [ arg $ "--flags=stage" ++ show nextStage + , ghcWithInterpreter ? + notStage0 ? arg "--flags=ghci" + ] ] withBuilderKey :: Builder -> String diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index dee0c95..8b913f5 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -16,7 +16,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, hoopl, hpc, transformers ] + [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? @@ -24,8 +24,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory - , filepath, ghcPrim, haskeline, integerLibrary, pretty, process - , templateHaskell, time ] + , filepath, ghc, ghcPrim, haskeline, integerLibrary, pretty + , process, templateHaskell, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 5b62e39..9a71ac2 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -15,7 +15,7 @@ userArgs = mempty -- Control which packages get to be built userPackages :: Packages -userPackages = mempty +userPackages = remove [ghc] -- Add new user-defined packages userKnownPackages :: [Package] From git at git.haskell.org Thu Oct 26 23:39:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify extraObjects in src/Rules/Library.hs, see #117. (ce8ffdb) Message-ID: <20171026233941.9E6293A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ce8ffdbbb7d477d022f5df20e77467413f80349b/ghc >--------------------------------------------------------------- commit ce8ffdbbb7d477d022f5df20e77467413f80349b Author: Andrey Mokhov Date: Wed Jan 6 11:10:49 2016 +0000 Simplify extraObjects in src/Rules/Library.hs, see #117. >--------------------------------------------------------------- ce8ffdbbb7d477d022f5df20e77467413f80349b src/Rules/Library.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 41e7b3d..46f3971 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -80,9 +80,5 @@ extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do need [integerGmpLibraryH] - objsExist <- doesDirectoryExist integerGmpObjects - putBuild $ "objsExist = " ++ show objsExist - if objsExist - then getDirectoryFiles "" [integerGmpObjects -/- "*.o"] - else return [] + getDirectoryFiles "" [integerGmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Thu Oct 26 23:39:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Put when trackBuildSystem conditional more precisely. (9f99e24) Message-ID: <20171026233945.3E7A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9f99e240df6f3c5ad8597e2dafd9a73220dd87d3/ghc >--------------------------------------------------------------- commit 9f99e240df6f3c5ad8597e2dafd9a73220dd87d3 Author: Andrey Mokhov Date: Thu Sep 24 23:48:02 2015 +0100 Put when trackBuildSystem conditional more precisely. >--------------------------------------------------------------- 9f99e240df6f3c5ad8597e2dafd9a73220dd87d3 src/Oracles/ArgsHash.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index bc29031..402923b 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -20,12 +20,12 @@ newtype ArgsHashKey = ArgsHashKey Target -- to argument lists where appropriate. -- TODO: enforce the above assumption via type trickery? checkArgsHash :: Target -> Action () -checkArgsHash target = do +checkArgsHash target = when trackBuildSystem $ do _ <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int return () -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () -argsHashOracle = when trackBuildSystem $ do +argsHashOracle = do _ <- addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs return () From git at git.haskell.org Thu Oct 26 23:39:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor generated dependencies (41ecfdc) Message-ID: <20171026233945.647FF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/41ecfdc70602aed5335f7205a092c336c090ec90/ghc >--------------------------------------------------------------- commit 41ecfdc70602aed5335f7205a092c336c090ec90 Author: Andrey Mokhov Date: Wed Jan 6 11:56:22 2016 +0000 Refactor generated dependencies Do not proceed with building a package until all its generated dependencies are in place. List generated files in ghcPrim package, see #117. >--------------------------------------------------------------- 41ecfdc70602aed5335f7205a092c336c090ec90 src/Rules/Data.hs | 5 +++++ src/Rules/Dependencies.hs | 3 --- src/Rules/Generate.hs | 17 ++++++++++------- src/Rules/IntegerGmp.hs | 7 ++++++- 4 files changed, 21 insertions(+), 11 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 42fb2a6..29f8d3d 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -6,6 +6,7 @@ import GHC import Oracles import Predicates (registerPackage) import Rules.Actions +import Rules.Generate import Rules.Resources import Settings import Settings.Builders.Common @@ -19,6 +20,10 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do dataFile = pkgDataFile stage pkg dataFile %> \mk -> do + -- The first thing we do with any package is make sure all generated + -- dependencies are in place before proceeding. + orderOnly $ generatedDependencies stage pkg + -- GhcCabal may run the configure script, so we depend on it -- We don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 5b51c1d..79bcdb2 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -4,7 +4,6 @@ import Base import Expression import Oracles import Rules.Actions -import Rules.Generate import Rules.Resources import Settings import Development.Shake.Util (parseMakefile) @@ -18,13 +17,11 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do let srcFile = dropBuild . dropExtension $ out - orderOnly $ generatedDependencies stage pkg need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - orderOnly $ generatedDependencies stage pkg need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 2b33a53..3eb1231 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -35,13 +35,15 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -integerGmpDependencies :: [FilePath] -integerGmpDependencies = [integerGmpLibraryH] - defaultDependencies :: [FilePath] defaultDependencies = includesDependencies ++ libffiDependencies ++ integerGmpDependencies +ghcPrimDependencies :: Stage -> [FilePath] +ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> + [ "GHC/PrimopWrappers.hs" + , "autogen/GHC/Prim.hs" ] + derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = (derivedConstantsPath -/-) <$> [ "DerivedConstants.h" @@ -72,10 +74,11 @@ compilerDependencies stage = generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage - | pkg == rts = derivedConstantsDependencies - | stage == Stage0 = defaultDependencies - | otherwise = [] + | pkg == compiler = compilerDependencies stage + | pkg == ghcPrim = ghcPrimDependencies stage + | pkg == rts = derivedConstantsDependencies + | stage == Stage0 = defaultDependencies + | otherwise = [] -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index b82dcbb..b796c6c 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,4 +1,6 @@ -module Rules.IntegerGmp (integerGmpRules, integerGmpObjects, integerGmpLibraryH) where +module Rules.IntegerGmp ( + integerGmpRules, integerGmpObjects, integerGmpLibraryH, integerGmpDependencies + ) where import Base import Expression @@ -28,6 +30,9 @@ integerGmpLibraryH = pkgPath integerGmp -/- "include/ghc-gmp.h" integerGmpLibraryFakeH :: FilePath integerGmpLibraryFakeH = integerGmpBase -/- "ghc-gmp.h" +integerGmpDependencies :: [FilePath] +integerGmpDependencies = [integerGmpLibraryH] + -- relative to integerGmpBuild integerGmpPatch :: FilePath integerGmpPatch = ".." -/- "tarball" -/- "gmp-5.0.4.patch" From git at git.haskell.org Thu Oct 26 23:39:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, add comments. (55fd868) Message-ID: <20171026233948.E3F8C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/55fd868e521ea500e3b5e8a6f55890e632e07174/ghc >--------------------------------------------------------------- commit 55fd868e521ea500e3b5e8a6f55890e632e07174 Author: Andrey Mokhov Date: Fri Sep 25 02:52:16 2015 +0100 Clean up, add comments. >--------------------------------------------------------------- 55fd868e521ea500e3b5e8a6f55890e632e07174 src/Builder.hs | 1 + src/Oracles/ArgsHash.hs | 1 + src/Rules/Cabal.hs | 6 ++++-- 3 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index e1c69be..c0ffee0 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -16,6 +16,7 @@ import Stage -- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) -- TODO: add Cpp builders -- TODO: rename Gcc to Cc? +-- TODO: do we really need staged builders? data Builder = Alex | Ar | Gcc Stage diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 402923b..ab4993b 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -19,6 +19,7 @@ newtype ArgsHashKey = ArgsHashKey Target -- constructors are assumed not to examine target sources, but only append them -- to argument lists where appropriate. -- TODO: enforce the above assumption via type trickery? +-- TODO: Hash Target to improve accuracy and performance. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do _ <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index aac8ab2..7ccb1b8 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -2,7 +2,7 @@ module Rules.Cabal (cabalRules) where import Expression import Data.Version -import Distribution.Package +import Distribution.Package hiding (Package) import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Verbosity @@ -29,7 +29,9 @@ cabalRules = do pkgDeps <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - let deps = collectDeps . condLibrary $ pd + let depsLib = collectDeps $ condLibrary pd + depsExes = map (collectDeps . Just . snd) $ condExecutables pd + deps = concat $ depsLib : depsExes depNames = [ name | Dependency (PackageName name) _ <- deps ] return . unwords $ Package.pkgName pkg : sort depNames writeFileChanged out . unlines $ pkgDeps From git at git.haskell.org Thu Oct 26 23:39:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Cache $HOME/.ghc as well (9784dfb) Message-ID: <20171026233949.19A5F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9784dfb75fdbafb1aa16422eee0bde40ce0ace13/ghc >--------------------------------------------------------------- commit 9784dfb75fdbafb1aa16422eee0bde40ce0ace13 Author: David Luposchainsky Date: Tue Jan 5 16:45:41 2016 +0100 Cache $HOME/.ghc as well >--------------------------------------------------------------- 9784dfb75fdbafb1aa16422eee0bde40ce0ace13 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 68e843c..055edd5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,6 +59,7 @@ script: cache: directories: - $HOME/.cabal + - $HOME/.ghc notifications: irc: From git at git.haskell.org Thu Oct 26 23:39:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finalise meeting agenda. (07dbd29) Message-ID: <20171026233952.EAE493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/07dbd2918f9099fb98986f9cc91b51b52a94d5f8/ghc >--------------------------------------------------------------- commit 07dbd2918f9099fb98986f9cc91b51b52a94d5f8 Author: Andrey Mokhov Date: Fri Sep 25 02:52:32 2015 +0100 Finalise meeting agenda. >--------------------------------------------------------------- 07dbd2918f9099fb98986f9cc91b51b52a94d5f8 doc/meeting-25-September-2015.txt | 67 ++++++++++++++++++++++++++++----------- 1 file changed, 49 insertions(+), 18 deletions(-) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt index caf0e8e..dde2e45 100644 --- a/doc/meeting-25-September-2015.txt +++ b/doc/meeting-25-September-2015.txt @@ -4,42 +4,74 @@ Things to discuss: ================================================ 1. Progress report +------------------ +Done: +* Build all libraries and compiler +* Generate code (alex, happy, hsc2hs, genprimopcode, Config.hs, ghc_boot_platform.h) +* Track changes in the build system +* Extract accurate package dependencies from .cabal files +* Improve complexity when searching for module files (40x) -++ Dealing with seemingly dead-code artefacts of the old build systems. I used to carefully migrate all code to the new build system, but it is getting more in the way of readability. New proposal: drop all such suspicious instances and bring them back only if things break. Example: +Todo: Target: +* Build utils, rts October +* Better dependencies (.hs-incl etc.) November +* Support command line options December +* Validate November-December (GHC 8.0?) +* Documentation December-January + +Notes: +* Zero build: under 7 seconds +* Full build (when compilation not required): under 12 minutes on 4 cores +* Limited parallelism: ghc-cabal/ghc-pkg not thread-safe, ghc fails on > 4 cores +* Codebase growing: 50 files + + +2. Seemingly dead-code +---------------------- + +I used to carefully migrate all code to the new build system even when it seemed dead, but this is often getting in the way of readability. New proposal: drop all such suspicious instances and bring them back only if/when things break. + +Example (generating primops.txt): C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe -E -undef -traditional -P -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -Icompiler/stage2 -x c compiler/prelude/primops.txt.pp | grep -v '^#pragma GCC' > compiler/stage2/build/primops.txt -But primops.txt.pp has no lines containing #pragma GCC! Dead code? +But primops.txt.pp has no lines containing #pragma GCC. Dead code? -++ Zero build is 7 seconds +Another example (generating ghc_boot_platform.h): -++ .hs-incl includes are currently not tracked properly (e.g. ghc -MM does not list them). See Dependencies.hs +ifeq "$(TargetOS_CPP)" "irix" + @echo "#ifndef $(IRIX_MAJOR)_TARGET_OS" >> $@ + @echo "#define $(IRIX_MAJOR)_TARGET_OS 1" >> $@ + @echo "#endif" >> $@ +endif -++ Better names for build stages +But IRIX_MAJOR is never set anywhere in the build system. Dead code? -* Currently we have Stage0, Stage1, etc. It is not particularly clear -from the names what they stand for. We no longer need to stick to -numbers and can pick more helpful names, for example: -Stage0 -> Boot -Stage1 -> Interim -Stage2 -> Install -Stage3 -> Selftest +3. Command line options +----------------------- +Discuss the need for command line options, e.g. 'make GhcDebugged=YES'. Do we need to support all options as in the old build system? +Settings.User is fairly readable, so perhaps some options may be changeable only by editing this file and recompiling the build system (typically takes negligible time compared to building). This will simplify things. Can we come up with a must-have list for command line options? -i. Unclear abstractions Builder/BuildRule... +4. Better names for build stages +-------------------------------- -ii. Limits to build parallelism: GHC crashes during parallel builds. Also ghc-pkg and ghc-cabal are apparently not thread-safe, so I had to use Shake resources to limit the parallelism... +Currently we have Stage0, Stage1, etc. It is not particularly clear from the names what they stand for (as a newcomer to the build system I used to look up what these numbers stand for all the time). Shall we use this opportunity to pick more helpful names, for example: -iii. Discuss the need for command line options, e.g. make GhcDebugged=YES. This is a bit annoying to implement since Settings.User seems fairly readable, but recompiling the build systems for changing a flag may be annoying too. +Stage0 -> Boot +Stage1 -> Interim +Stage2 -> Install +Stage3 -> Selftest -iv. Do we need a name for the new build system? +5. Do we need a name for the new build system? +---------------------------------------------- -* At least we need a name for the folder in the GHC tree +* At least we need a name for the folder in the GHC tree. * If we call it 'shake' there may be a confusion with the Shake library. @@ -47,4 +79,3 @@ iv. Do we need a name for the new build system? build system' is overly verbose. Calling it 'shake' is confusing. * I haven't thought about any names yet, just checking whether we want to. - From git at git.haskell.org Thu Oct 26 23:39:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add IRC notifications (2e4f060) Message-ID: <20171026233953.232573A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2e4f060ee78c68726cb6434796d208075d4394a7/ghc >--------------------------------------------------------------- commit 2e4f060ee78c68726cb6434796d208075d4394a7 Author: David Luposchainsky Date: Tue Jan 5 16:07:39 2016 +0100 Add IRC notifications >--------------------------------------------------------------- 2e4f060ee78c68726cb6434796d208075d4394a7 .travis.yml | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/.travis.yml b/.travis.yml index 1bcd7fd..68e843c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,3 +59,15 @@ script: cache: directories: - $HOME/.cabal + +notifications: + irc: + on_success: always # always/never/change + on_failure: always + channels: + - "chat.freenode.net#shaking-up-ghc" + template: + - "#%{build_number} finished in %{duration}. %{message}" + - "Repo: %{repository_slug}, branch: %{branch}" + - "%{author}: %{commit_subject}" + - "Build details: %{build_url}" From git at git.haskell.org Thu Oct 26 23:39:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #120 from quchen/irc-notifications (31fdc6b) Message-ID: <20171026233956.916073A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31fdc6b713e90aa8a2b14ce7157bef811836028d/ghc >--------------------------------------------------------------- commit 31fdc6b713e90aa8a2b14ce7157bef811836028d Merge: 41ecfdc 9784dfb Author: Andrey Mokhov Date: Wed Jan 6 13:10:12 2016 +0000 Merge pull request #120 from quchen/irc-notifications Add IRC notifications >--------------------------------------------------------------- 31fdc6b713e90aa8a2b14ce7157bef811836028d .travis.yml | 13 +++++++++++++ 1 file changed, 13 insertions(+) From git at git.haskell.org Thu Oct 26 23:39:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for non-library packages. (c488f65) Message-ID: <20171026233956.6C8DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c488f65dd9a894af75e633c5bd78220d7b60cc84/ghc >--------------------------------------------------------------- commit c488f65dd9a894af75e633c5bd78220d7b60cc84 Author: Andrey Mokhov Date: Fri Sep 25 02:53:37 2015 +0100 Add support for non-library packages. >--------------------------------------------------------------- c488f65dd9a894af75e633c5bd78220d7b60cc84 src/GHC.hs | 21 +++++++++++++++------ src/Rules.hs | 7 ++++++- src/Rules/Data.hs | 4 ++-- src/Settings.hs | 8 +++++++- src/Settings/Packages.hs | 8 ++++---- src/Settings/TargetDirectory.hs | 2 ++ src/Settings/User.hs | 10 +++++++--- 7 files changed, 43 insertions(+), 17 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index c277c6a..668cf48 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,9 +4,10 @@ module GHC ( integerGmp, integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, - defaultKnownPackages, defaultTargetDirectory + defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where +import Base import Package import Stage @@ -66,8 +67,16 @@ xhtml = library "xhtml" -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal -- TODO: simplify to just 'show stage'? defaultTargetDirectory :: Stage -> Package -> FilePath -defaultTargetDirectory stage package - | package == compiler = "stage" ++ show (fromEnum stage + 1) - | package == ghc = "stage" ++ show (fromEnum stage + 1) - | stage == Stage0 = "dist-boot" - | otherwise = "dist-install" +defaultTargetDirectory stage pkg + | pkg == compiler = "stage" ++ show (fromEnum stage + 1) + | pkg == ghc = "stage" ++ show (fromEnum stage + 1) + | stage == Stage0 = "dist-boot" + | otherwise = "dist-install" + +defaultProgramPath :: Stage -> Package -> Maybe FilePath +defaultProgramPath stage pkg + | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) + | otherwise = Nothing + where + program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg + -/- "build/tmp" -/- name <.> exe diff --git a/src/Rules.hs b/src/Rules.hs index 26e57bd..e615c64 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -11,7 +11,8 @@ generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpretWithStage stage getPackages - fmap concat . forM pkgs $ \pkg -> do + let (libPkgs, programPkgs) = partition isLibrary pkgs + libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg buildPath = targetPath stage pkg -/- "build" libName <- interpretPartial target $ getPkgData LibName @@ -28,6 +29,10 @@ generateTargets = action $ do ++ [ haddock | needHaddock && stage == Stage1 ] ++ libs + let programTargets = map (fromJust . programPath stage) programPkgs + + return $ libTargets ++ programTargets + need $ reverse targets -- TODO: add Stage2 (compiler only?) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 3622918..1085f8f 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -17,7 +17,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fmap (path -/-) [ "package-data.mk" , "haddock-prologue.txt" - , "inplace-pkg-config" , "setup-config" , "build" -/- "autogen" -/- "cabal_macros.h" -- TODO: Is this needed? Also check out Paths_cpsa.hs. @@ -39,7 +38,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fullTarget target GhcCabal [cabalFile] outs -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg - whenM (interpretPartial target registerPackage) . + when (isLibrary pkg) . + whenM (interpretPartial target registerPackage) . buildWithResources [(ghcPkg rs, 1)] $ fullTarget target (GhcPkg stage) [cabalFile] outs diff --git a/src/Settings.hs b/src/Settings.hs index dab73ed..d16c5cd 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -3,7 +3,7 @@ module Settings ( module Settings.TargetDirectory, module Settings.User, module Settings.Ways, - getPkgData, getPkgDataList, + getPkgData, getPkgDataList, programPath, isLibrary, getPackagePath, getTargetDirectory, getTargetPath, getPackageSources, ) where @@ -29,6 +29,12 @@ getPkgData key = lift . pkgData . key =<< getTargetPath getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getTargetPath +programPath :: Stage -> Package -> Maybe FilePath +programPath = userProgramPath + +isLibrary :: Package -> Bool +isLibrary pkg = programPath Stage0 pkg == Nothing + -- Find all Haskell source files for the current target. TODO: simplify. getPackageSources :: Expr [FilePath] getPackageSources = do diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 8b913f5..1fe70dc 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -16,16 +16,16 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc, transformers ] + [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc + , templateHaskell, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 - , append [ array, base, bytestring, containers, deepseq, directory - , filepath, ghc, ghcPrim, haskeline, integerLibrary, pretty - , process, templateHaskell, time ] + , append [ array, base, bytestring, containers, deepseq, directory, filepath + , ghcPrim, haskeline, integerLibrary, pretty, process, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 58f2d51..b84d03d 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -5,6 +5,8 @@ module Settings.TargetDirectory ( import Expression import Settings.User +-- TODO: move to Settings.hs? + -- User can override the default target directory settings given below targetDirectory :: Stage -> Package -> FilePath targetDirectory = userTargetDirectory diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 9a71ac2..d841028 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,6 +1,6 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, - userKnownPackages, integerLibrary, + userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies ) where @@ -15,7 +15,7 @@ userArgs = mempty -- Control which packages get to be built userPackages :: Packages -userPackages = remove [ghc] +userPackages = mempty -- Add new user-defined packages userKnownPackages :: [Package] @@ -28,10 +28,14 @@ userLibWays = mempty userRtsWays :: Ways userRtsWays = mempty --- Control where build results go (see Settings.Default for an example) +-- Control where build results go (see GHC.hs for defaults) userTargetDirectory :: Stage -> Package -> FilePath userTargetDirectory = defaultTargetDirectory +-- Control how built programs are called (see GHC.hs for defaults) +userProgramPath :: Stage -> Package -> Maybe FilePath +userProgramPath = defaultProgramPath + -- Choose integer library: integerGmp, integerGmp2 or integerSimple integerLibrary :: Package integerLibrary = integerGmp From git at git.haskell.org Thu Oct 26 23:39:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:39:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments/todos. (5e0734b) Message-ID: <20171026233959.EBCE83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e0734bc2bfafc15e6b2de692a5b1f22a73217ec/ghc >--------------------------------------------------------------- commit 5e0734bc2bfafc15e6b2de692a5b1f22a73217ec Author: Andrey Mokhov Date: Sat Sep 26 22:56:01 2015 +0100 Add comments/todos. >--------------------------------------------------------------- 5e0734bc2bfafc15e6b2de692a5b1f22a73217ec doc/meeting-25-September-2015.txt | 23 ++++++++++++++++++++--- src/Settings/Builders/Alex.hs | 7 +++++++ src/Stage.hs | 1 + src/Target.hs | 4 ++-- 4 files changed, 30 insertions(+), 5 deletions(-) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt index dde2e45..166c3d8 100644 --- a/doc/meeting-25-September-2015.txt +++ b/doc/meeting-25-September-2015.txt @@ -14,11 +14,12 @@ Done: * Improve complexity when searching for module files (40x) Todo: Target: -* Build utils, rts October +* Build utils, rts & put in GHC tree October * Better dependencies (.hs-incl etc.) November * Support command line options December -* Validate November-December (GHC 8.0?) +* Validate November-December * Documentation December-January +* Journal paper + provenance December-February Notes: * Zero build: under 7 seconds @@ -26,6 +27,14 @@ Notes: * Limited parallelism: ghc-cabal/ghc-pkg not thread-safe, ghc fails on > 4 cores * Codebase growing: 50 files +Things to do: +-- Use OrderOnly for ordering ghc-cabal's +-- Fix parallel invokations of ghc-cabal +-- Fix GHC -M to handle .hs-incl (--make already knows how to do that) instead of writing a new parser. Maybe already done -- find a flag! +-- Rename files -> outputs, sources -> inputs +-- Start separating general bits from GHC bits. A separate package for Args maybe +-- Look up Bazel and Buck +-- Decompose args into builder-specific and package-specific 2. Seemingly dead-code ---------------------- @@ -46,7 +55,7 @@ ifeq "$(TargetOS_CPP)" "irix" @echo "#endif" >> $@ endif -But IRIX_MAJOR is never set anywhere in the build system. Dead code? +But IRIX_MAJOR is never set anywhere in the build system. Dead code? YES 3. Command line options @@ -56,6 +65,12 @@ Discuss the need for command line options, e.g. 'make GhcDebugged=YES'. Do we ne Settings.User is fairly readable, so perhaps some options may be changeable only by editing this file and recompiling the build system (typically takes negligible time compared to building). This will simplify things. Can we come up with a must-have list for command line options? +-- Try to support these first: +* EXTRA_HC_OPTS = file "asd" ? arg ".." +* EXTRA_CC_OPTS +* GhcDebugged = True +* make 2 + 4. Better names for build stages -------------------------------- @@ -79,3 +94,5 @@ Stage3 -> Selftest build system' is overly verbose. Calling it 'shake' is confusing. * I haven't thought about any names yet, just checking whether we want to. + +-- Use mk2 \ No newline at end of file diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs index 1e0f87b..257fd58 100644 --- a/src/Settings/Builders/Alex.hs +++ b/src/Settings/Builders/Alex.hs @@ -12,3 +12,10 @@ alexArgs = builder Alex ? do , package compiler ? arg "--latin1" , arg src , arg "-o", arg file ] + +-- TODO: +-- compilierArgs = package compiler ? builder Alex ? arg "awe" + +-- args = mconcat +-- [ alexArgs +-- , compilerArgs ] diff --git a/src/Stage.hs b/src/Stage.hs index edddb6f..e0a6124 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -5,6 +5,7 @@ import Base import GHC.Generics (Generic) -- TODO: rename to something more meaningful, e.g. 'Stage0' -> 'Boot'. +-- TODO: explain stages data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum, Generic) instance Show Stage where diff --git a/src/Target.hs b/src/Target.hs index 8e2a44e..257a896 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -22,8 +22,8 @@ data Target = Target package :: Package, builder :: Builder, way :: Way, - sources :: [FilePath], - files :: [FilePath] + sources :: [FilePath], -- input + files :: [FilePath] -- output } deriving (Show, Eq, Generic) From git at git.haskell.org Thu Oct 26 23:40:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Let's try the stupid --with-gcc fix for os x. (7d55b36) Message-ID: <20171026234000.1FFF23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d55b36149cf7f5896d9920c8dbd53ac3a8a787d/ghc >--------------------------------------------------------------- commit 7d55b36149cf7f5896d9920c8dbd53ac3a8a787d Author: Moritz Angermann Date: Wed Jan 6 21:43:38 2016 +0800 Let's try the stupid --with-gcc fix for os x. See #111 >--------------------------------------------------------------- 7d55b36149cf7f5896d9920c8dbd53ac3a8a787d .travis.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 055edd5..e096ddf 100644 --- a/.travis.yml +++ b/.travis.yml @@ -51,7 +51,8 @@ install: - ( cd ghc/shake-build && cabal install --only-dependencies ) - ( cd ghc && ./boot ) - - ( cd ghc && ./configure ) + - if [ $TRAVIS_OS_NAME == osx ]; then ( cd ghc && ./configure --with-gcc="$(which clang)"); fi + - if [ $TRAVIS_OS_NAME == linux ]; then ( cd ghc && ./configure ); fi script: - ./ghc/shake-build/build.sh -j --no-progress From git at git.haskell.org Thu Oct 26 23:40:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Target fields: sources -> inputs, files -> outputs. (5a162b2) Message-ID: <20171026234003.A5A883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a162b2a13746eb5ab90108323bbc6d416bd435a/ghc >--------------------------------------------------------------- commit 5a162b2a13746eb5ab90108323bbc6d416bd435a Author: Andrey Mokhov Date: Sat Sep 26 23:35:57 2015 +0100 Rename Target fields: sources -> inputs, files -> outputs. >--------------------------------------------------------------- 5a162b2a13746eb5ab90108323bbc6d416bd435a doc/demo.txt | 2 ++ src/Expression.hs | 32 ++++++++++++++++---------------- src/Oracles/ArgsHash.hs | 2 +- src/Predicates.hs | 2 +- src/Rules/Actions.hs | 6 +++--- src/Settings/Builders/Alex.hs | 13 +++++-------- src/Settings/Builders/Ar.hs | 9 +++------ src/Settings/Builders/Gcc.hs | 20 +++++++------------- src/Settings/Builders/Ghc.hs | 27 +++++++++++---------------- src/Settings/Builders/Haddock.hs | 9 ++++----- src/Settings/Builders/Happy.hs | 11 ++++------- src/Settings/Builders/HsCpp.hs | 7 ++----- src/Settings/Builders/Hsc2Hs.hs | 6 ++---- src/Settings/Builders/Ld.hs | 6 ++---- src/Stage.hs | 1 - src/Target.hs | 12 ++++++------ 16 files changed, 69 insertions(+), 96 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5a162b2a13746eb5ab90108323bbc6d416bd435a From git at git.haskell.org Thu Oct 26 23:40:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #121 from angerman/feature/fix-osx-ci (0fee526) Message-ID: <20171026234003.E5BBD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0fee526aa68cff1b10d733ba4257fb3435276c66/ghc >--------------------------------------------------------------- commit 0fee526aa68cff1b10d733ba4257fb3435276c66 Merge: 31fdc6b 7d55b36 Author: Andrey Mokhov Date: Wed Jan 6 13:47:24 2016 +0000 Merge pull request #121 from angerman/feature/fix-osx-ci Let's try the stupid --with-gcc fix for os x. >--------------------------------------------------------------- 0fee526aa68cff1b10d733ba4257fb3435276c66 .travis.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:40:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for compiling programs with Ghc builder. (d7b3d34) Message-ID: <20171026234007.4198C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d7b3d34b16e2519f2fa2d1eae96dd469d29e5824/ghc >--------------------------------------------------------------- commit d7b3d34b16e2519f2fa2d1eae96dd469d29e5824 Author: Andrey Mokhov Date: Mon Dec 7 01:42:30 2015 +0000 Add support for compiling programs with Ghc builder. >--------------------------------------------------------------- d7b3d34b16e2519f2fa2d1eae96dd469d29e5824 src/Settings/Builders/Ghc.hs | 32 +++++++++++++++++++++----------- 1 file changed, 21 insertions(+), 11 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index ad34e19..8ab4357 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,24 +2,32 @@ module Settings.Builders.Ghc (ghcArgs, ghcMArgs, commonGhcArgs) where import Expression import Oracles -import Predicates (stagedBuilder, splitObjects, stage0, notStage0) +import GHC +import Predicates (package, stagedBuilder, splitObjects, stage0, notStage0) import Settings -- TODO: add support for -dyno +-- TODO: consider adding a new builder for programs (e.g. GhcLink?) -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ -- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) ghcArgs :: Args -ghcArgs = stagedBuilder Ghc ? mconcat [ commonGhcArgs - , arg "-H32m" - , stage0 ? arg "-O" - , notStage0 ? arg "-O2" - , arg "-Wall" - , arg "-fwarn-tabs" - , splitObjects ? arg "-split-objs" - , arg "-c", append =<< getInputs - , arg "-o", arg =<< getOutput ] +ghcArgs = stagedBuilder Ghc ? do + output <- getOutput + way <- getWay + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + mconcat [ commonGhcArgs + , arg "-H32m" + , stage0 ? arg "-O" + , notStage0 ? arg "-O2" + , arg "-Wall" + , arg "-fwarn-tabs" + , buildObj ? splitObjects ? arg "-split-objs" + , package ghc ? arg "-no-hs-main" + , buildObj ? arg "-c" + , append =<< getInputs + , arg "-o", arg =<< getOutput ] ghcMArgs :: Args ghcMArgs = stagedBuilder GhcM ? do @@ -71,6 +79,7 @@ wayGhcArgs = do packageGhcArgs :: Args packageGhcArgs = do stage <- getStage + pkg <- getPackage supportsPackageKey <- getFlag SupportsPackageKey pkgKey <- getPkgData PackageKey pkgDepIds <- getPkgDataList DepIds @@ -78,7 +87,8 @@ packageGhcArgs = do [ arg "-hide-all-packages" , arg "-no-user-package-db" , stage0 ? arg "-package-db libraries/bootstrapping.conf" - , if supportsPackageKey || stage /= Stage0 + , isLibrary pkg ? + if supportsPackageKey || stage /= Stage0 then arg $ "-this-package-key " ++ pkgKey else arg $ "-package-name " ++ pkgKey , append $ map ("-package-id " ++) pkgDepIds ] From git at git.haskell.org Thu Oct 26 23:40:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Lookup builder in PATH if they are given without path. (4478851) Message-ID: <20171026234007.72CA83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44788518cb14c59788fdf320b9ca2d11e11509ca/ghc >--------------------------------------------------------------- commit 44788518cb14c59788fdf320b9ca2d11e11509ca Author: Moritz Angermann Date: Wed Jan 6 23:22:43 2016 +0800 Lookup builder in PATH if they are given without path. `system-gcc` may be given without path (e.g. `clang`), this patch adds lookup using `which` for those commands. Also drops calling `fixAbsolutePathOnWindows` on non window hosts. Fixes #26 >--------------------------------------------------------------- 44788518cb14c59788fdf320b9ca2d11e11509ca src/Builder.hs | 4 +++- src/Oracles/WindowsRoot.hs | 11 ++++++++++- 2 files changed, 13 insertions(+), 2 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 5ed9e1d..6e4dba5 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -94,7 +94,9 @@ builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ putError $ "\nCannot find path to '" ++ (builderKey builder) ++ "' in configuration files." - fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe + windows <- windowsHost + let path' = if null path then "" else path -<.> exe in + (if windows then fixAbsolutePathOnWindows else lookupInPath) path' getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 413f289..195f591 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.WindowsRoot ( - windowsRoot, fixAbsolutePathOnWindows, topDirectory, windowsRootOracle + windowsRoot, fixAbsolutePathOnWindows, lookupInPath, topDirectory, windowsRootOracle ) where import Data.Char (isSpace) @@ -38,6 +38,15 @@ fixAbsolutePathOnWindows path = do else return path +-- | Lookup a @command@ in @PATH@ environment. +lookupInPath :: FilePath -> Action FilePath +lookupInPath command + | command /= takeFileName command = return command + | otherwise = do + Stdout out <- quietly $ cmd ["which", command] + let path = dropWhileEnd isSpace out + return path + -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). windowsRootOracle :: Rules () From git at git.haskell.org Thu Oct 26 23:40:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove duplicates from library archives. (3cd6a3b) Message-ID: <20171026234011.3936D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3cd6a3b7e70f658db663251037a6f034e3ab89f0/ghc >--------------------------------------------------------------- commit 3cd6a3b7e70f658db663251037a6f034e3ab89f0 Author: Andrey Mokhov Date: Mon Dec 7 01:43:51 2015 +0000 Remove duplicates from library archives. >--------------------------------------------------------------- 3cd6a3b7e70f658db663251037a6f034e3ab89f0 src/Rules/Library.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b1c3f3c..d51e2ad 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,4 +1,4 @@ -module Rules.Library (buildPackageLibrary) where +module Rules.Library (buildPackageLibrary, cSources, hSources) where import Expression hiding (splitPath) import Oracles @@ -19,7 +19,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do cSrcs <- cSources target hSrcs <- hSources target - let way = detectWay a + let way = detectWay a -- TODO: eliminate differences below cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] @@ -28,14 +28,14 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do need $ cObjs ++ hObjs split <- interpretPartial target splitObjects - splitObjs <- if not split then return [] else + splitObjs <- if not split then return hObjs else -- TODO: make clearer! fmap concat $ forM hSrcs $ \src -> do let splitPath = buildPath -/- src ++ "_" ++ osuf way ++ "_split" contents <- liftIO $ IO.getDirectoryContents splitPath return . map (splitPath -/-) . filter (not . all (== '.')) $ contents - build $ fullTarget target Ar (cObjs ++ hObjs ++ splitObjs) [a] + build $ fullTarget target Ar (cObjs ++ splitObjs) [a] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built package library '" From git at git.haskell.org Thu Oct 26 23:40:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Updates travis and README to reflect fixing #26 (f3a1eb7) Message-ID: <20171026234011.611CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f3a1eb726e550d458476764d99ad68fe042de81b/ghc >--------------------------------------------------------------- commit f3a1eb726e550d458476764d99ad68fe042de81b Author: Moritz Angermann Date: Wed Jan 6 23:24:22 2016 +0800 Updates travis and README to reflect fixing #26 >--------------------------------------------------------------- f3a1eb726e550d458476764d99ad68fe042de81b .travis.yml | 3 +-- README.md | 3 --- 2 files changed, 1 insertion(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index e096ddf..055edd5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -51,8 +51,7 @@ install: - ( cd ghc/shake-build && cabal install --only-dependencies ) - ( cd ghc && ./boot ) - - if [ $TRAVIS_OS_NAME == osx ]; then ( cd ghc && ./configure --with-gcc="$(which clang)"); fi - - if [ $TRAVIS_OS_NAME == linux ]; then ( cd ghc && ./configure ); fi + - ( cd ghc && ./configure ) script: - ./ghc/shake-build/build.sh -j --no-progress diff --git a/README.md b/README.md index 90f6422..45789e3 100644 --- a/README.md +++ b/README.md @@ -31,9 +31,6 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure -# or if you want to use clang (e.g. building on OS X) -./configure --with-gcc=$(which clang) # See #26 - ``` Now you have a couple of options: From git at git.haskell.org Thu Oct 26 23:40:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildProgram rule. (3ceca89) Message-ID: <20171026234014.A97463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ceca89902487a91a337e5a75f7f1de8b5bd4add/ghc >--------------------------------------------------------------- commit 3ceca89902487a91a337e5a75f7f1de8b5bd4add Author: Andrey Mokhov Date: Mon Dec 7 01:44:10 2015 +0000 Add buildProgram rule. >--------------------------------------------------------------- 3ceca89902487a91a337e5a75f7f1de8b5bd4add src/Rules/Package.hs | 4 +++- src/Rules/Program.hs | 29 +++++++++++++++++++++++++++++ 2 files changed, 32 insertions(+), 1 deletion(-) diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 9da4f8b..7a7d854 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -7,6 +7,7 @@ import Rules.Dependencies import Rules.Documentation import Rules.Generate import Rules.Library +import Rules.Program import Rules.Resources import Target @@ -17,4 +18,5 @@ buildPackage = mconcat , generatePackageCode , compilePackage , buildPackageLibrary - , buildPackageDocumentation ] + , buildPackageDocumentation + , buildProgram ] diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs new file mode 100644 index 0000000..14cbea0 --- /dev/null +++ b/src/Rules/Program.hs @@ -0,0 +1,29 @@ +module Rules.Program (buildProgram) where + +import Expression hiding (splitPath) +import Oracles +import Rules.Actions +import Rules.Library +import Rules.Resources +import Settings + +buildProgram :: Resources -> PartialTarget -> Rules () +buildProgram _ target @ (PartialTarget stage pkg) = do + let path = targetPath stage pkg + buildPath = path -/- "build" + program = programPath stage pkg + + (\f -> program == Just f) ?> \bin -> do + cSrcs <- cSources target -- TODO: remove code duplication (Library.hs) + hSrcs <- hSources target + let cObjs = [ buildPath -/- src -<.> osuf vanilla | src <- cSrcs ] + hObjs = [ buildPath -/- src <.> osuf vanilla | src <- hSrcs ] + objs = cObjs ++ hObjs + need objs + build $ fullTargetWithWay target (Ghc stage) vanilla objs [bin] + synopsis <- interpretPartial target $ getPkgData Synopsis + putSuccess $ "/--------\n| Successfully built program '" + ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + putSuccess $ "| Executable: " ++ bin + putSuccess $ "| Package synopsis: " + ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" From git at git.haskell.org Thu Oct 26 23:40:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a test appveyor script, see #110. (290e990) Message-ID: <20171026234014.E70213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/290e990dd8500de9728d83506a0bacd143619def/ghc >--------------------------------------------------------------- commit 290e990dd8500de9728d83506a0bacd143619def Author: Andrey Mokhov Date: Wed Jan 6 17:48:41 2016 +0000 Add a test appveyor script, see #110. >--------------------------------------------------------------- 290e990dd8500de9728d83506a0bacd143619def .appveyor.yml | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/.appveyor.yml b/.appveyor.yml new file mode 100644 index 0000000..25df24b --- /dev/null +++ b/.appveyor.yml @@ -0,0 +1,8 @@ +install: + - set PATH=C:\msys64\usr\bin;%PATH% + - bash "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" + +build_script: + - echo "test" + +test: off From git at git.haskell.org Thu Oct 26 23:40:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass dll0 modules to ghc-cabal for the compiler package. (1c09363) Message-ID: <20171026234018.7D0DB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c09363fd8631cd43a885bb8399455b02fc026d1/ghc >--------------------------------------------------------------- commit 1c09363fd8631cd43a885bb8399455b02fc026d1 Author: Andrey Mokhov Date: Mon Dec 7 02:27:38 2015 +0000 Pass dll0 modules to ghc-cabal for the compiler package. >--------------------------------------------------------------- 1c09363fd8631cd43a885bb8399455b02fc026d1 src/Settings/Builders/GhcCabal.hs | 193 +++++++++++++++++++++++++++++++++++--- 1 file changed, 181 insertions(+), 12 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 582a56c..df4af2b 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -4,7 +4,7 @@ module Settings.Builders.GhcCabal ( ) where import Expression -import Predicates +import Predicates hiding (stage) import Settings cabalArgs :: Args @@ -14,7 +14,7 @@ cabalArgs = builder GhcCabal ? do mconcat [ arg "configure" , arg path , arg dir - , dllArgs + , dll0Args , withStaged Ghc , withStaged GhcPkg , stage0 ? bootPackageDbArgs @@ -40,12 +40,12 @@ ghcCabalHsColourArgs = builder GhcCabalHsColour ? do -- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do - ways <- getWays - ghcInt <- lift $ ghcWithInterpreter + ways <- getWays + ghci <- lift ghcWithInterpreter append [ if vanilla `elem` ways then "--enable-library-vanilla" else "--disable-library-vanilla" - , if vanilla `elem` ways && ghcInt && not dynamicGhcPrograms + , if vanilla `elem` ways && ghci && not dynamicGhcPrograms then "--enable-library-for-ghci" else "--disable-library-for-ghci" , if profiling `elem` ways @@ -81,13 +81,6 @@ bootPackageDbArgs = do path <- getSetting GhcSourcePath arg $ "--package-db=" ++ path -/- "libraries/bootstrapping.conf" --- This is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument; --- * otherwise, we must collapse it into one space-separated string. --- TODO: should be non-empty for compiler -dllArgs :: Args -dllArgs = arg "" - packageConstraints :: Args packageConstraints = stage0 ? do constraints <- lift . readFileLines $ bootPackageConstraints @@ -219,3 +212,179 @@ appendCcArgs xs = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" xs , builder GhcCabal ? appendSub "--gcc-options" xs ] +-- This is a positional argument, hence: +-- * if it is empty, we need to emit one empty string argument; +-- * otherwise, we must collapse it into one space-separated string. +dll0Args :: Args +dll0Args = do + windows <- lift windowsHost + pkg <- getPackage + stage <- getStage + let needDll0Args = windows && pkg == compiler && stage == Stage1 + ghci <- lift ghcWithInterpreter + arg . unwords . concat $ [ modules | needDll0Args ] + ++ [ ghciModules | needDll0Args && ghci ] -- see #9552 + where + modules = [ "Annotations" + , "ApiAnnotation" + , "Avail" + , "Bag" + , "BasicTypes" + , "Binary" + , "BooleanFormula" + , "BreakArray" + , "BufWrite" + , "Class" + , "CmdLineParser" + , "CmmType" + , "CoAxiom" + , "ConLike" + , "Coercion" + , "Config" + , "Constants" + , "CoreArity" + , "CoreFVs" + , "CoreSubst" + , "CoreSyn" + , "CoreTidy" + , "CoreUnfold" + , "CoreUtils" + , "CoreSeq" + , "CoreStats" + , "CostCentre" + , "Ctype" + , "DataCon" + , "Demand" + , "Digraph" + , "DriverPhases" + , "DynFlags" + , "Encoding" + , "ErrUtils" + , "Exception" + , "ExtsCompat46" + , "FamInstEnv" + , "FastFunctions" + , "FastMutInt" + , "FastString" + , "FastTypes" + , "Fingerprint" + , "FiniteMap" + , "ForeignCall" + , "Hooks" + , "HsBinds" + , "HsDecls" + , "HsDoc" + , "HsExpr" + , "HsImpExp" + , "HsLit" + , "PlaceHolder" + , "HsPat" + , "HsSyn" + , "HsTypes" + , "HsUtils" + , "HscTypes" + , "IOEnv" + , "Id" + , "IdInfo" + , "IfaceSyn" + , "IfaceType" + , "InstEnv" + , "Kind" + , "Lexeme" + , "Lexer" + , "ListSetOps" + , "Literal" + , "Maybes" + , "MkCore" + , "MkId" + , "Module" + , "MonadUtils" + , "Name" + , "NameEnv" + , "NameSet" + , "OccName" + , "OccurAnal" + , "OptCoercion" + , "OrdList" + , "Outputable" + , "PackageConfig" + , "Packages" + , "Pair" + , "Panic" + , "PatSyn" + , "PipelineMonad" + , "Platform" + , "PlatformConstants" + , "PprCore" + , "PrelNames" + , "PrelRules" + , "Pretty" + , "PrimOp" + , "RdrName" + , "Rules" + , "Serialized" + , "SrcLoc" + , "StaticFlags" + , "StringBuffer" + , "TcEvidence" + , "TcRnTypes" + , "TcType" + , "TrieMap" + , "TyCon" + , "Type" + , "TypeRep" + , "TysPrim" + , "TysWiredIn" + , "Unify" + , "UniqFM" + , "UniqSet" + , "UniqSupply" + , "Unique" + , "Util" + , "Var" + , "VarEnv" + , "VarSet" ] + ghciModules = [ "Bitmap" + , "BlockId" + , "ByteCodeAsm" + , "ByteCodeInstr" + , "ByteCodeItbls" + , "CLabel" + , "Cmm" + , "CmmCallConv" + , "CmmExpr" + , "CmmInfo" + , "CmmMachOp" + , "CmmNode" + , "CmmSwitch" + , "CmmUtils" + , "CodeGen.Platform" + , "CodeGen.Platform.ARM" + , "CodeGen.Platform.ARM64" + , "CodeGen.Platform.NoRegs" + , "CodeGen.Platform.PPC" + , "CodeGen.Platform.PPC_Darwin" + , "CodeGen.Platform.SPARC" + , "CodeGen.Platform.X86" + , "CodeGen.Platform.X86_64" + , "FastBool" + , "Hoopl" + , "Hoopl.Dataflow" + , "InteractiveEvalTypes" + , "MkGraph" + , "PprCmm" + , "PprCmmDecl" + , "PprCmmExpr" + , "Reg" + , "RegClass" + , "SMRep" + , "StgCmmArgRep" + , "StgCmmClosure" + , "StgCmmEnv" + , "StgCmmLayout" + , "StgCmmMonad" + , "StgCmmProf" + , "StgCmmTicky" + , "StgCmmUtils" + , "StgSyn" + , "Stream" ] From git at git.haskell.org Thu Oct 26 23:40:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix test script, see #110. (8bf936f) Message-ID: <20171026234018.BF59B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8bf936f4942a51bbfbd4c561a1dbfb89300bcdff/ghc >--------------------------------------------------------------- commit 8bf936f4942a51bbfbd4c561a1dbfb89300bcdff Author: Andrey Mokhov Date: Wed Jan 6 18:11:05 2016 +0000 Fix test script, see #110. >--------------------------------------------------------------- 8bf936f4942a51bbfbd4c561a1dbfb89300bcdff .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 25df24b..b5faf11 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,6 +1,7 @@ install: - - set PATH=C:\msys64\usr\bin;%PATH% - - bash "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" + - set MSYSTEM=MINGW64 + - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% + - bash -lc "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" build_script: - echo "test" From git at git.haskell.org Thu Oct 26 23:40:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcLink builder. (49dfde7) Message-ID: <20171026234022.88E8D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49dfde799495f1d8bfdc2a891bc6e930879a855e/ghc >--------------------------------------------------------------- commit 49dfde799495f1d8bfdc2a891bc6e930879a855e Author: Andrey Mokhov Date: Wed Dec 9 01:57:52 2015 +0000 Add GhcLink builder. >--------------------------------------------------------------- 49dfde799495f1d8bfdc2a891bc6e930879a855e src/Builder.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index c0ffee0..67be69f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -25,6 +25,7 @@ data Builder = Alex | Ghc Stage | GhcCabal | GhcCabalHsColour + | GhcLink Stage | GhcM Stage | GhcPkg Stage | GhcSplit @@ -50,6 +51,7 @@ builderKey builder = case builder of Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" + GhcLink stage -> builderKey $ Ghc stage -- using Ghc as linker GhcM stage -> builderKey $ Ghc stage -- synonym for 'Ghc -M' GhcCabal -> "ghc-cabal" GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' From git at git.haskell.org Thu Oct 26 23:40:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install prerequisites for Windows build. (584fd8a) Message-ID: <20171026234022.C57CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/584fd8a9811592d04c7c1d43c37778410b8d6590/ghc >--------------------------------------------------------------- commit 584fd8a9811592d04c7c1d43c37778410b8d6590 Author: Andrey Mokhov Date: Wed Jan 6 18:19:24 2016 +0000 Install prerequisites for Windows build. See #110. [skip ci] >--------------------------------------------------------------- 584fd8a9811592d04c7c1d43c37778410b8d6590 .appveyor.yml | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index b5faf11..2b710e0 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,7 +1,11 @@ install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - bash -lc "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" + - bash -lc "pacman -S --noconfirm git binutils p7zip gcc mingw-w64-$(uname -m)-python3-sphinx" + - bash -lc "curl -L http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" + - bash -lc "curl -L https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + - bash -lc "cabal update" + - bash -lc "cabal install -j --prefix=/usr/local alex happy" build_script: - echo "test" From git at git.haskell.org Thu Oct 26 23:40:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add basic support for -0 libraries. (3e82d46) Message-ID: <20171026234026.0A0CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e82d460ba762334e7d52be121a1fa698dda42e4/ghc >--------------------------------------------------------------- commit 3e82d460ba762334e7d52be121a1fa698dda42e4 Author: Andrey Mokhov Date: Wed Dec 9 01:58:53 2015 +0000 Add basic support for -0 libraries. >--------------------------------------------------------------- 3e82d460ba762334e7d52be121a1fa698dda42e4 src/Rules.hs | 8 ++++++-- src/Rules/Library.hs | 5 ++++- 2 files changed, 10 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index e615c64..2e2963f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,6 +5,7 @@ import Oracles import Rules.Package import Rules.Resources import Settings +import Settings.Builders.GhcCabal -- generateTargets needs top-level build targets generateTargets :: Rules () @@ -21,9 +22,12 @@ generateTargets = action $ do ways <- interpretPartial target getWays let ghciLib = buildPath -/- "HS" ++ libName <.> "o" haddock = pkgHaddockFile pkg - libs <- forM ways $ \way -> do + libs <- fmap concat . forM ways $ \way -> do extension <- libsuf way - return $ buildPath -/- "libHS" ++ libName <.> extension + let name = buildPath -/- "libHS" ++ libName + dll0 <- needDll0 stage pkg + return $ [ name <.> extension ] + ++ [ name ++ "-0" <.> extension | dll0 ] return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] ++ [ haddock | needHaddock && stage == Stage1 ] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index d51e2ad..9e4f7d5 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -15,6 +15,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do + removeFileIfExists a cSrcs <- cSources target hSrcs <- hSources target @@ -35,7 +36,9 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do return . map (splitPath -/-) . filter (not . all (== '.')) $ contents - build $ fullTarget target Ar (cObjs ++ splitObjs) [a] + if "//*-0.*" ?== a + then build $ fullTarget target Ar [] [a] + else build $ fullTarget target Ar (cObjs ++ splitObjs) [a] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built package library '" From git at git.haskell.org Thu Oct 26 23:40:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create /usr/local/bin, silence curl. (1731a15) Message-ID: <20171026234026.521493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1731a15422f2be3eb09b612426900801ea3b294f/ghc >--------------------------------------------------------------- commit 1731a15422f2be3eb09b612426900801ea3b294f Author: Andrey Mokhov Date: Wed Jan 6 18:33:03 2016 +0000 Create /usr/local/bin, silence curl. See #110. [skip ci] >--------------------------------------------------------------- 1731a15422f2be3eb09b612426900801ea3b294f .appveyor.yml | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 2b710e0..f8ce40a 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -2,8 +2,10 @@ install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc mingw-w64-$(uname -m)-python3-sphinx" - - bash -lc "curl -L http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "curl -L https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" + - bash -lc "mkdir /usr/local" + - bash -lc "mkdir /usr/local/bin" + - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" From git at git.haskell.org Thu Oct 26 23:40:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Work on command lines for compiling stage 2 GHC. (159903e) Message-ID: <20171026234029.885133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/159903e948cb8d3497235e4dd2c0f2c1ddde3227/ghc >--------------------------------------------------------------- commit 159903e948cb8d3497235e4dd2c0f2c1ddde3227 Author: Andrey Mokhov Date: Wed Dec 9 02:00:09 2015 +0000 Work on command lines for compiling stage 2 GHC. >--------------------------------------------------------------- 159903e948cb8d3497235e4dd2c0f2c1ddde3227 src/Settings/Builders/Ghc.hs | 108 +++++++++++++++++++++++++++++++++++++- src/Settings/Builders/GhcCabal.hs | 20 ++++--- 2 files changed, 119 insertions(+), 9 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 8ab4357..8d1a30f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,10 +1,13 @@ -module Settings.Builders.Ghc (ghcArgs, ghcMArgs, commonGhcArgs) where +module Settings.Builders.Ghc ( + ghcArgs, ghcMArgs, ghcLinkArgs, commonGhcArgs + ) where import Expression import Oracles import GHC import Predicates (package, stagedBuilder, splitObjects, stage0, notStage0) import Settings +import Settings.Builders.GhcCabal -- TODO: add support for -dyno -- TODO: consider adding a new builder for programs (e.g. GhcLink?) @@ -17,6 +20,8 @@ ghcArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + libs <- getPkgDataList DepExtraLibs + libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -25,6 +30,9 @@ ghcArgs = stagedBuilder Ghc ? do , arg "-fwarn-tabs" , buildObj ? splitObjects ? arg "-split-objs" , package ghc ? arg "-no-hs-main" + , not buildObj ? arg "-no-auto-link-packages" + , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ] + , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" , append =<< getInputs , arg "-o", arg =<< getOutput ] @@ -116,3 +124,101 @@ includeGhcArgs = do -- define libraries/ghc-prim_PACKAGE_MAGIC -- libraries/ghc-prim_dist-install_MODULES := $$(filter-out GHC.Prim,$$(libraries/ghc-prim_dist-install_MODULES)) -- endef + + +-- # Options for passing to plain ld +-- $1_$2_$3_ALL_LD_OPTS = \ +-- $$(WAY_$3_LD_OPTS) \ +-- $$($1_$2_DIST_LD_OPTS) \ +-- $$($1_$2_$3_LD_OPTS) \ +-- $$($1_$2_EXTRA_LD_OPTS) \ +-- $$(EXTRA_LD_OPTS) + +-- # Options for passing to GHC when we use it for linking +-- $1_$2_$3_GHC_LD_OPTS = \ +-- $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ +-- $$($1_$2_$3_MOST_HC_OPTS) + +-- TODO: add support for TargetElf and darwin +-- ifeq "$3" "dyn" +-- ifneq "$4" "0" +-- ifeq "$$(TargetElf)" "YES" +-- $1_$2_$3_GHC_LD_OPTS += \ +-- -fno-use-rpaths \ +-- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'$$$$ORIGIN/../$$d') -optl-Wl,-zorigin +-- else ifeq "$$(TargetOS_CPP)" "darwin" +-- $1_$2_$3_GHC_LD_OPTS += \ +-- -fno-use-rpaths \ +-- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') + +-- ifeq "$$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS)" "" +-- # We don't want to link the GHC RTS into C-only programs. There's no +-- # point, and it confuses the test that all GHC-compiled programs +-- # were compiled with the right GHC. +-- $1_$2_$$($1_$2_PROGRAM_WAY)_GHC_LD_OPTS += -no-auto-link-packages -no-hs-main +-- endif + +ghcLinkArgs :: Args +ghcLinkArgs = mempty + -- way <- getRtsWays + -- path <- getTargetPath + -- mconcat [ commonGhcArgs + -- , (way == dynamic) ? needDll0Args ? + -- arg $ "-dll-split " ++ path -/- "dll-split" + -- , appendSubD "-optl" (getSettingList . ConfLdLinkerArgs =<< getStage) + -- , appendSubD "-optl-L" (lift $ pkgDataList DepLibDirs) + -- , appendSubD "-optl-l" (lift $ pkgDataList DepExtraLibs) + -- , splitObjects ? arg "-split-objs" + -- , package ghc ? arg "-no-hs-main" + -- , append =<< getInputs + -- , arg "-o", arg =<< getOutput ] + + +-- # Link a dynamic library +-- # On windows we have to supply the extra libs this one links to when building it. +-- ifeq "$$(HostOS_CPP)" "mingw32" +-- $$($1_$2_$3_LIB) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) +-- ifneq "$$($1_$2_$3_LIB0)" "" +-- $$(call build-dll,$1,$2,$3, +-- -L$1/$2/build -l$$($1_$2_$3_LIB0_ROOT), +-- $$(filter-out $$($1_$2_dll0_HS_OBJS),$$($1_$2_$3_HS_OBJS)) +-- $$($1_$2_$3_NON_HS_OBJS),$$@) +-- else +-- $$(call build-dll,$1,$2,$3,,$$($1_$2_$3_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$@) +-- endif + +-- ifneq "$$($1_$2_$3_LIB0)" "" +-- $$($1_$2_$3_LIB) : $$($1_$2_$3_LIB0) +-- $$($1_$2_$3_LIB0) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) +-- $$(call build-dll,$1,$2,$3,,$$($1_$2_dll0_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$($1_$2_$3_LIB0)) +-- endif + + + +-- # $1 = dir +-- # $2 = distdir +-- # $3 = way +-- # $4 = extra flags +-- # $5 = object files to link +-- # $6 = output filename +-- define build-dll +-- $(call cmd,$1_$2_HC) $($1_$2_$3_ALL_HC_OPTS) $($1_$2_$3_GHC_LD_OPTS) $4 $5 \ +-- -shared -dynamic -dynload deploy \ +-- $(addprefix -l,$($1_$2_EXTRA_LIBRARIES)) \ +-- -no-auto-link-packages \ +-- -o $6 +-- # Now check that the DLL doesn't have too many symbols. See trac #5987. +-- SYMBOLS=`$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail -n +2 | wc -l`; echo "Number of symbols in $6: $$SYMBOLS" +-- case `$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | grep "\[ *0\]" | wc -l` in 1) echo DLL $6 OK;; 0) echo No symbols in DLL $6; exit 1;; [0-9]*) echo Too many symbols in DLL $6; $(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail; exit 1;; *) echo bad DLL $6; exit 1;; esac +-- endef + + + +-- TODO: add -dynamic-too? +-- # $1_$2_$3_ALL_HC_OPTS: this is all the options we will pass to GHC +-- # for a given ($1,$2,$3). +-- $1_$2_$3_ALL_HC_OPTS = \ +-- -hisuf $$($3_hisuf) -osuf $$($3_osuf) -hcsuf $$($3_hcsuf) \ +-- $$($1_$2_$3_MOST_DIR_HC_OPTS) \ +-- $$(if $$(findstring YES,$$($1_$2_SplitObjs)),$$(if $$(findstring dyn,$3),,-split-objs),) \ +-- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),$$(if $$(findstring v,$3),-dynamic-too)) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index df4af2b..793a7f7 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,6 +1,6 @@ module Settings.Builders.GhcCabal ( cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, - ccArgs, cppArgs, ccWarnings, argStagedSettingList + ccArgs, cppArgs, ccWarnings, argStagedSettingList, needDll0 ) where import Expression @@ -212,18 +212,22 @@ appendCcArgs xs = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" xs , builder GhcCabal ? appendSub "--gcc-options" xs ] +needDll0 :: Stage -> Package -> Action Bool +needDll0 stage pkg = do + windows <- windowsHost + return $ windows && pkg == compiler && stage == Stage1 + -- This is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument; -- * otherwise, we must collapse it into one space-separated string. dll0Args :: Args dll0Args = do - windows <- lift windowsHost - pkg <- getPackage - stage <- getStage - let needDll0Args = windows && pkg == compiler && stage == Stage1 - ghci <- lift ghcWithInterpreter - arg . unwords . concat $ [ modules | needDll0Args ] - ++ [ ghciModules | needDll0Args && ghci ] -- see #9552 + stage <- getStage + pkg <- getPackage + dll0 <- lift $ needDll0 stage pkg + ghci <- lift ghcWithInterpreter + arg . unwords . concat $ [ modules | dll0 ] + ++ [ ghciModules | dll0 && ghci ] -- see #9552 where modules = [ "Annotations" , "ApiAnnotation" From git at git.haskell.org Thu Oct 26 23:40:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add extra objects into integerGmp library. (9439336) Message-ID: <20171026234033.1A6833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9439336c258c9e1d93b1da57cde1d89e8800fbf0/ghc >--------------------------------------------------------------- commit 9439336c258c9e1d93b1da57cde1d89e8800fbf0 Author: Andrey Mokhov Date: Thu Dec 10 00:28:42 2015 +0000 Add extra objects into integerGmp library. >--------------------------------------------------------------- 9439336c258c9e1d93b1da57cde1d89e8800fbf0 src/Rules/Library.hs | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 9e4f7d5..b0afdc6 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,6 +1,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Expression hiding (splitPath) +import GHC import Oracles import Predicates (splitObjects) import Rules.Actions @@ -36,9 +37,12 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do return . map (splitPath -/-) . filter (not . all (== '.')) $ contents + eObjs <- extraObjects target + let objs = cObjs ++ splitObjs ++ eObjs + if "//*-0.*" ?== a - then build $ fullTarget target Ar [] [a] - else build $ fullTarget target Ar (cObjs ++ splitObjs) [a] + then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls + else build $ fullTarget target Ar objs [a] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built package library '" @@ -65,3 +69,10 @@ hSources target = do modules <- interpretPartial target $ getPkgDataList Modules -- GHC.Prim is special: we do not build it return . map (replaceEq '.' '/') . filter (/= "GHC.Prim") $ modules + +extraObjects :: PartialTarget -> Action [FilePath] +extraObjects (PartialTarget _ pkg) = do + gmpObjs <- getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] + if pkg == integerGmp + then return gmpObjs + else return [] From git at git.haskell.org Thu Oct 26 23:40:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop heavy python dependency, change project folder. (907af3f) Message-ID: <20171026234029.CD4D43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/907af3f12f842ca7598854e5707d6398f48fd93e/ghc >--------------------------------------------------------------- commit 907af3f12f842ca7598854e5707d6398f48fd93e Author: Andrey Mokhov Date: Wed Jan 6 18:51:55 2016 +0000 Drop heavy python dependency, change project folder. See #110. [skip ci] >--------------------------------------------------------------- 907af3f12f842ca7598854e5707d6398f48fd93e .appveyor.yml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f8ce40a..f9f938d 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,7 +1,9 @@ +clone_folder: "C:\msys64\home\ghc\shake-build" + install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - bash -lc "pacman -S --noconfirm git binutils p7zip gcc mingw-w64-$(uname -m)-python3-sphinx" + - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - bash -lc "mkdir /usr/local" - bash -lc "mkdir /usr/local/bin" From git at git.haskell.org Thu Oct 26 23:40:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to clone folder. (dfc34f1) Message-ID: <20171026234033.5E64D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfc34f1fb0d7aec2392cd700eaa91d10a6c87835/ghc >--------------------------------------------------------------- commit dfc34f1fb0d7aec2392cd700eaa91d10a6c87835 Author: Andrey Mokhov Date: Wed Jan 6 18:53:37 2016 +0000 Fix path to clone folder. See #110. [skip ci] >--------------------------------------------------------------- dfc34f1fb0d7aec2392cd700eaa91d10a6c87835 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f9f938d..fa03afe 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,4 +1,4 @@ -clone_folder: "C:\msys64\home\ghc\shake-build" +clone_folder: "C:\\msys64\\home\\ghc\\shake-build" install: - set MSYSTEM=MINGW64 From git at git.haskell.org Thu Oct 26 23:40:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for utility packages. (2f1eda7) Message-ID: <20171026234036.C60363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f1eda773f2d11e11e9f46591078e50be94e458b/ghc >--------------------------------------------------------------- commit 2f1eda773f2d11e11e9f46591078e50be94e458b Author: Andrey Mokhov Date: Thu Dec 10 01:42:07 2015 +0000 Add support for utility packages. >--------------------------------------------------------------- 2f1eda773f2d11e11e9f46591078e50be94e458b src/GHC.hs | 18 +++++++++++------- src/Package.hs | 9 ++++++--- src/Rules/Library.hs | 8 +++----- src/Settings/Builders/Ghc.hs | 3 +-- src/Settings/Packages.hs | 3 ++- 5 files changed, 23 insertions(+), 18 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 668cf48..de482f4 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,6 +1,6 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, @@ -19,13 +19,14 @@ import Stage defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl - , hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm - , templateHaskell, terminfo, time, transformers, unix, win32, xhtml ] + , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPrim + , haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty + , primitive, process, stm, templateHaskell, terminfo, time, transformers + , unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package @@ -41,6 +42,7 @@ deepseq = library "deepseq" directory = library "directory" filepath = library "filepath" ghc = topLevel "ghc-bin" `setPath` "ghc" +ghcCabal = utility "ghc-cabal" ghcPrim = library "ghc-prim" haskeline = library "haskeline" hoopl = library "hoopl" @@ -60,6 +62,7 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" + -- GHC build results will be placed into target directories with the following -- typical structure: -- * build/ : contains compiled object code @@ -75,8 +78,9 @@ defaultTargetDirectory stage pkg defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg - | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) - | otherwise = Nothing + | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) + | pkg == ghcCabal = program $ pkgName pkg + | otherwise = Nothing where program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg -/- "build/tmp" -/- name <.> exe diff --git a/src/Package.hs b/src/Package.hs index fba192c..85fbd13 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} module Package ( - Package (..), PackageName, pkgCabalFile, setPath, library, topLevel + Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility ) where import Base @@ -21,11 +21,14 @@ data Package = Package pkgCabalFile :: Package -> FilePath pkgCabalFile pkg = pkgPath pkg -/- pkgName pkg <.> "cabal" +topLevel :: PackageName -> Package +topLevel name = Package name name + library :: PackageName -> Package library name = Package name ("libraries" -/- name) -topLevel :: PackageName -> Package -topLevel name = Package name name +utility :: PackageName -> Package +utility name = Package name ("utils" -/- name) setPath :: Package -> FilePath -> Package setPath pkg path = pkg { pkgPath = path } diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b0afdc6..1bf668d 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -71,8 +71,6 @@ hSources target = do return . map (replaceEq '.' '/') . filter (/= "GHC.Prim") $ modules extraObjects :: PartialTarget -> Action [FilePath] -extraObjects (PartialTarget _ pkg) = do - gmpObjs <- getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] - if pkg == integerGmp - then return gmpObjs - else return [] +extraObjects (PartialTarget _ pkg) + | pkg == integerGmp = getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] + | otherwise = return [] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 8d1a30f..15944f3 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -7,7 +7,6 @@ import Oracles import GHC import Predicates (package, stagedBuilder, splitObjects, stage0, notStage0) import Settings -import Settings.Builders.GhcCabal -- TODO: add support for -dyno -- TODO: consider adding a new builder for programs (e.g. GhcLink?) @@ -30,7 +29,7 @@ ghcArgs = stagedBuilder Ghc ? do , arg "-fwarn-tabs" , buildObj ? splitObjects ? arg "-split-objs" , package ghc ? arg "-no-hs-main" - , not buildObj ? arg "-no-auto-link-packages" + -- , not buildObj ? arg "-no-auto-link-packages" , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ] , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 1fe70dc..5ac9c6e 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -25,7 +25,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory, filepath - , ghcPrim, haskeline, integerLibrary, pretty, process, time ] + , ghcCabal, ghcPrim, haskeline, integerLibrary, pretty, process + , time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] From git at git.haskell.org Thu Oct 26 23:40:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename cabal, add build script. (da29ac9) Message-ID: <20171026234037.282B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da29ac914723944acd7c65709fa93c0dce198571/ghc >--------------------------------------------------------------- commit da29ac914723944acd7c65709fa93c0dce198571 Author: Andrey Mokhov Date: Wed Jan 6 19:21:43 2016 +0000 Rename cabal, add build script. See #110. [skip ci] >--------------------------------------------------------------- da29ac914723944acd7c65709fa93c0dce198571 .appveyor.yml | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index fa03afe..93375e0 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,10 +8,14 @@ install: - bash -lc "mkdir /usr/local" - bash -lc "mkdir /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + - ren C:\msys64\usr\local\bin\cabal-1.22.0.0-i386-unknown-mingw32.exe C:\msys64\usr\local\bin\cabal.exe - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" + - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" build_script: - - echo "test" + - bash -lc "cd /home/ghc && ./boot" + - bash -lc "cd /home/ghc && ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && ./shake-build/build.bat" test: off From git at git.haskell.org Thu Oct 26 23:40:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix a poor pattern for detecting -0 library files. (b0424dc) Message-ID: <20171026234040.4EDA83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b0424dc9bb4c9035c1239d9d14bc720d4b6db9ad/ghc >--------------------------------------------------------------- commit b0424dc9bb4c9035c1239d9d14bc720d4b6db9ad Author: Andrey Mokhov Date: Fri Dec 11 00:23:25 2015 +0000 Fix a poor pattern for detecting -0 library files. >--------------------------------------------------------------- b0424dc9bb4c9035c1239d9d14bc720d4b6db9ad src/Rules/Library.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 1bf668d..a2cf010 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -40,7 +40,8 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do eObjs <- extraObjects target let objs = cObjs ++ splitObjs ++ eObjs - if "//*-0.*" ?== a + asuf <- libsuf way + if ("//*-0" <.> asuf) ?== a then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls else build $ fullTarget target Ar objs [a] From git at git.haskell.org Thu Oct 26 23:40:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install project dependencies, pass -j --no-progress to build.bat (5afac8a) Message-ID: <20171026234040.A37113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5afac8aceaa4a656231fbd03b61a03a38327ee78/ghc >--------------------------------------------------------------- commit 5afac8aceaa4a656231fbd03b61a03a38327ee78 Author: Andrey Mokhov Date: Wed Jan 6 19:35:18 2016 +0000 Install project dependencies, pass -j --no-progress to build.bat See #110. [skip ci] >--------------------------------------------------------------- 5afac8aceaa4a656231fbd03b61a03a38327ee78 .appveyor.yml | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 93375e0..47210eb 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -12,10 +12,9 @@ install: - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" + - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" - bash -lc "cd /home/ghc && ./configure --enable-tarballs-autodownload" - - bash -lc "cd /home/ghc && ./shake-build/build.bat" - -test: off + - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:40:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass __GLASGOW_HASKELL__ to gcc when compiling directory.c (098c9ec) Message-ID: <20171026234044.15D013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/098c9ece49564542cc180a6cba06577695243c7e/ghc >--------------------------------------------------------------- commit 098c9ece49564542cc180a6cba06577695243c7e Author: Andrey Mokhov Date: Fri Dec 11 00:24:01 2015 +0000 Pass __GLASGOW_HASKELL__ to gcc when compiling directory.c >--------------------------------------------------------------- 098c9ece49564542cc180a6cba06577695243c7e src/Settings/Builders/Gcc.hs | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index 6a45740..3437a6c 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -1,14 +1,21 @@ module Settings.Builders.Gcc (gccArgs, gccMArgs) where import Expression +import GHC import Oracles -import Predicates (stagedBuilder) +import Predicates (package, stagedBuilder) import Settings +-- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is +-- effectively empty. I presume it was expected that GHC will be used for +-- compiling all C files, but I don't know why. It seems that directory.c is the +-- only file which requires special treatment when using GCC. gccArgs :: Args -gccArgs = stagedBuilder Gcc ? mconcat [ commonGccArgs - , arg "-c", arg =<< getInput - , arg "-o", arg =<< getOutput ] +gccArgs = stagedBuilder Gcc ? + mconcat [ commonGccArgs + , package directory ? arg "-D__GLASGOW_HASKELL__" + , arg "-c", arg =<< getInput + , arg "-o", arg =<< getOutput ] -- TODO: handle custom $1_$2_MKDEPENDC_OPTS and gccMArgs :: Args From git at git.haskell.org Thu Oct 26 23:40:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix cabal rename error. (e008f71) Message-ID: <20171026234044.715873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e008f71950c8197157e3da6274b12d410bce81f9/ghc >--------------------------------------------------------------- commit e008f71950c8197157e3da6274b12d410bce81f9 Author: Andrey Mokhov Date: Wed Jan 6 20:30:11 2016 +0000 Fix cabal rename error. See #110. [skip ci] >--------------------------------------------------------------- e008f71950c8197157e3da6274b12d410bce81f9 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 47210eb..8bb6c15 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,7 +8,7 @@ install: - bash -lc "mkdir /usr/local" - bash -lc "mkdir /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - - ren C:\msys64\usr\local\bin\cabal-1.22.0.0-i386-unknown-mingw32.exe C:\msys64\usr\local\bin\cabal.exe + - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" From git at git.haskell.org Thu Oct 26 23:40:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generator for ghc-pkg//Version.hs. (3021dbe) Message-ID: <20171026234047.972AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3021dbebbbc22acc67880f62a067417dcc9b486b/ghc >--------------------------------------------------------------- commit 3021dbebbbc22acc67880f62a067417dcc9b486b Author: Andrey Mokhov Date: Sat Dec 12 00:41:26 2015 +0000 Add generator for ghc-pkg//Version.hs. >--------------------------------------------------------------- 3021dbebbbc22acc67880f62a067417dcc9b486b src/Rules/Generate.hs | 20 +++++++++++++++++++- 1 file changed, 19 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 6f45dbd..97fb81f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -4,7 +4,7 @@ import Expression import GHC import Oracles import Rules.Actions -import Rules.Resources +import Rules.Resources (Resources) import Settings primopsSource :: FilePath @@ -65,6 +65,12 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = writeFileChanged file contents putBuild $ "| Successfully generated '" ++ file ++ "'." + priority 2.0 $ + when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do + contents <- interpretPartial target generateGhcPkgVersionHs + writeFileChanged file contents + putBuild $ "| Successfully generated '" ++ file ++ "'." + quote :: String -> String quote s = "\"" ++ s ++ "\"" @@ -211,3 +217,15 @@ generatePlatformH = do , "#define TARGET_VENDOR " ++ quote targetVendor , "" , "#endif /* __PLATFORM_H__ */" ] + +generateGhcPkgVersionHs :: Expr String +generateGhcPkgVersionHs = do + projectVersion <- getSetting ProjectVersion + targetOs <- getSetting TargetOs + targetArch <- getSetting TargetArch + return $ unlines + [ "module Version where" + , "version, targetOS, targetARCH :: String" + , "version = " ++ quote projectVersion + , "targetOS = " ++ quote targetOs + , "targetARCH = " ++ quote targetArch ] From git at git.haskell.org Thu Oct 26 23:40:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change cabal config path and cache it. (a4447be) Message-ID: <20171026234047.EF7473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4447bef24be3eebef8413d27f34aec113d73b4f/ghc >--------------------------------------------------------------- commit a4447bef24be3eebef8413d27f34aec113d73b4f Author: Andrey Mokhov Date: Wed Jan 6 22:07:41 2016 +0000 Change cabal config path and cache it. See #110. [skip ci] >--------------------------------------------------------------- a4447bef24be3eebef8413d27f34aec113d73b4f .appveyor.yml | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 8bb6c15..f70a821 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,5 +1,8 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" +cache: + - "C:\\msys64\home\cabal" + install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% @@ -9,10 +12,10 @@ install: - bash -lc "mkdir /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal update" - - bash -lc "cabal install -j --prefix=/usr/local alex happy" + - bash -lc "cabal --config-file=/home/cabal update" + - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:40:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for building ghc-pkg. (bbc6e4a) Message-ID: <20171026234051.BD5253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbc6e4a216c7853c6275757fe1a84bf0e5721281/ghc >--------------------------------------------------------------- commit bbc6e4a216c7853c6275757fe1a84bf0e5721281 Author: Andrey Mokhov Date: Sat Dec 12 00:41:49 2015 +0000 Add support for building ghc-pkg. >--------------------------------------------------------------- bbc6e4a216c7853c6275757fe1a84bf0e5721281 src/GHC.hs | 16 +++++++++------- src/Settings/Packages.hs | 4 ++-- 2 files changed, 11 insertions(+), 9 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index de482f4..eff2334 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,8 +1,8 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, - integerGmp, integerSimple, parallel, pretty, primitive, process, stm, - templateHaskell, terminfo, time, transformers, unix, win32, xhtml, + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, + hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, + stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -19,16 +19,16 @@ import Stage defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPrim + , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim , haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty , primitive, process, stm, templateHaskell, terminfo, time, transformers , unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, - integerGmp, integerSimple, parallel, pretty, primitive, process, stm, - templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, + hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, + stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -43,6 +43,7 @@ directory = library "directory" filepath = library "filepath" ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" +ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" haskeline = library "haskeline" hoopl = library "hoopl" @@ -80,6 +81,7 @@ defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == ghcCabal = program $ pkgName pkg + | pkg == ghcPkg = program $ pkgName pkg | otherwise = Nothing where program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 5ac9c6e..9fbe936 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -25,8 +25,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory, filepath - , ghcCabal, ghcPrim, haskeline, integerLibrary, pretty, process - , time ] + , ghcCabal, ghcPkg, ghcPrim, haskeline, integerLibrary, pretty + , process, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] From git at git.haskell.org Thu Oct 26 23:40:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix cabal path, create directory for cabal if it does not exist. (3e42d47) Message-ID: <20171026234052.152AD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e42d47e05153bee9fe430e8e91e58c0bea12ea0/ghc >--------------------------------------------------------------- commit 3e42d47e05153bee9fe430e8e91e58c0bea12ea0 Author: Andrey Mokhov Date: Wed Jan 6 22:11:00 2016 +0000 Fix cabal path, create directory for cabal if it does not exist. See #110. [skip ci] >--------------------------------------------------------------- 3e42d47e05153bee9fe430e8e91e58c0bea12ea0 .appveyor.yml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f70a821..eb57bd8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,21 +1,22 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" cache: - - "C:\\msys64\home\cabal" + - "C:\\msys64\\home\\cabal" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir /usr/local" - - bash -lc "mkdir /usr/local/bin" + - bash -lc "mkdir -p /home/cabal" + - bash -lc "mkdir -p /usr/local" + - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - bash -lc "cabal --config-file=/home/cabal update" - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal \install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:40:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghc-pkg and ghc-cabal in stage 0. (a0e932a) Message-ID: <20171026234055.810053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a0e932ab5e73ccf062cacea3f6e8b15ca3d15463/ghc >--------------------------------------------------------------- commit a0e932ab5e73ccf062cacea3f6e8b15ca3d15463 Author: Andrey Mokhov Date: Sat Dec 12 00:50:27 2015 +0000 Build ghc-pkg and ghc-cabal in stage 0. >--------------------------------------------------------------- a0e932ab5e73ccf062cacea3f6e8b15ca3d15463 src/GHC.hs | 2 ++ src/Settings/Packages.hs | 4 ++-- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index eff2334..2482854 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -70,6 +70,8 @@ xhtml = library "xhtml" -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal -- TODO: simplify to just 'show stage'? +-- TODO: we divert from the previous convention for ghc-cabal and ghc-pkg, +-- which used to store stage0 build results in 'dist' folder defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage pkg | pkg == compiler = "stage" ++ show (fromEnum stage + 1) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 9fbe936..23ee7e4 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -16,8 +16,8 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc - , templateHaskell, transformers ] + [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg + , hoopl, hpc, templateHaskell, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? From git at git.haskell.org Thu Oct 26 23:40:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move cabal folder inside /home/ghc. (3008453) Message-ID: <20171026234056.16B913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3008453094756facfea0d45fcc0b5823c1c54b01/ghc >--------------------------------------------------------------- commit 3008453094756facfea0d45fcc0b5823c1c54b01 Author: Andrey Mokhov Date: Wed Jan 6 22:32:46 2016 +0000 Move cabal folder inside /home/ghc. See #110. [skip ci] >--------------------------------------------------------------- 3008453094756facfea0d45fcc0b5823c1c54b01 .appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index eb57bd8..a3dd1ef 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,22 +1,22 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" cache: - - "C:\\msys64\\home\\cabal" + - "C:\\msys64\\home\\ghc\\.cabal" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /home/cabal" + - bash -lc "mkdir -p /home/ghc/.cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal --config-file=/home/cabal update" - - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" + - bash -lc "cabal --config-file=/home/ghc/.cabal update" + - bash -lc "cabal --config-file=/home/ghc/.cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal \install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/ghc/.cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:40:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep experimenting with cabal folder. (d913235) Message-ID: <20171026234059.C76773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d913235b1f6e907a63ee8974e1f09c20b711bf0a/ghc >--------------------------------------------------------------- commit d913235b1f6e907a63ee8974e1f09c20b711bf0a Author: Andrey Mokhov Date: Wed Jan 6 22:44:46 2016 +0000 Keep experimenting with cabal folder. See #110. [skip ci] >--------------------------------------------------------------- d913235b1f6e907a63ee8974e1f09c20b711bf0a .appveyor.yml | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index a3dd1ef..751bc1f 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,22 +1,23 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" cache: - - "C:\\msys64\\home\\ghc\\.cabal" + - "C:\\msys64\\home\\cabal" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /home/ghc/.cabal" + - bash -lc "mkdir -p /home/cabal" + - bash -lc "chmod -R 777 /home/cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal --config-file=/home/ghc/.cabal update" - - bash -lc "cabal --config-file=/home/ghc/.cabal install -j --prefix=/usr/local alex happy" + - bash -lc "cabal --config-file=/home/cabal update" + - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/ghc/.cabal install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:40:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:40:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghc-pwd. (f659a18) Message-ID: <20171026234059.4B31B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f659a18291a9e4f1a8b8d7f2e22744923effcac0/ghc >--------------------------------------------------------------- commit f659a18291a9e4f1a8b8d7f2e22744923effcac0 Author: Andrey Mokhov Date: Sat Dec 12 00:53:49 2015 +0000 Build ghc-pwd. >--------------------------------------------------------------- f659a18291a9e4f1a8b8d7f2e22744923effcac0 src/GHC.hs | 18 +++++++++++------- src/Settings/Packages.hs | 6 +++--- 2 files changed, 14 insertions(+), 10 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 2482854..d1fb30a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,8 +1,9 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, - hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, - stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, + haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, + primitive, process, stm, templateHaskell, terminfo, time, transformers, + unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -20,15 +21,16 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim - , haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty + , ghcPwd, haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty , primitive, process, stm, templateHaskell, terminfo, time, transformers , unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, - hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, - stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, + haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, + primitive, process, stm, templateHaskell, terminfo, time, transformers, + unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -45,6 +47,7 @@ ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" +ghcPwd = utility "ghc-pwd" haskeline = library "haskeline" hoopl = library "hoopl" hpc = library "hpc" @@ -84,6 +87,7 @@ defaultProgramPath stage pkg | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == ghcCabal = program $ pkgName pkg | pkg == ghcPkg = program $ pkgName pkg + | pkg == ghcPwd = program $ pkgName pkg | otherwise = Nothing where program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 23ee7e4..b2636d5 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -17,7 +17,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg - , hoopl, hpc, templateHaskell, transformers ] + , ghcPwd, hoopl, hpc, templateHaskell, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? @@ -25,8 +25,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory, filepath - , ghcCabal, ghcPkg, ghcPrim, haskeline, integerLibrary, pretty - , process, time ] + , ghcCabal, ghcPkg, ghcPrim, ghcPwd, haskeline, integerLibrary + , pretty, process, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] From git at git.haskell.org Thu Oct 26 23:41:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build all utils that use cabal files. (f3199c1) Message-ID: <20171026234102.F37B53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f3199c17a1f010017eabd4845df7533c62abfde5/ghc >--------------------------------------------------------------- commit f3199c17a1f010017eabd4845df7533c62abfde5 Author: Andrey Mokhov Date: Sat Dec 12 02:13:35 2015 +0000 Build all utils that use cabal files. >--------------------------------------------------------------- f3199c17a1f010017eabd4845df7533c62abfde5 src/GHC.hs | 52 +++++++++++++++++++++++++++++--------------- src/Rules/Generate.hs | 5 +++++ src/Rules/Library.hs | 3 ++- src/Rules/Program.hs | 7 ++++-- src/Settings/Builders/Ghc.hs | 5 ++++- src/Settings/Packages.hs | 9 ++++---- 6 files changed, 56 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f3199c17a1f010017eabd4845df7533c62abfde5 From git at git.haskell.org Thu Oct 26 23:41:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run cabal outside bash. (f419f64) Message-ID: <20171026234103.957523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f419f6430ff16818513a33fd802b2c09488c5311/ghc >--------------------------------------------------------------- commit f419f6430ff16818513a33fd802b2c09488c5311 Author: Andrey Mokhov Date: Wed Jan 6 23:12:14 2016 +0000 Run cabal outside bash. See #110. [skip ci] >--------------------------------------------------------------- f419f6430ff16818513a33fd802b2c09488c5311 .appveyor.yml | 15 ++++++++------- 1 file changed, 8 insertions(+), 7 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 751bc1f..d8bb09d 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,7 +1,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -cache: - - "C:\\msys64\\home\\cabal" +# cache: +# - "C:\\msys64\\home\\cabal" install: - set MSYSTEM=MINGW64 @@ -9,15 +9,16 @@ install: - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - bash -lc "mkdir -p /home/cabal" - - bash -lc "chmod -R 777 /home/cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal --config-file=/home/cabal update" - - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" + - cabal update -v + - cabal install -j --prefix=/usr/local alex happy + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - cd C:\msys64\mingw64\home\ghc\shake-build + - cabal install --only-dependencies build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:41:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build haddock. (6b14363) Message-ID: <20171026234106.E5C673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5/ghc >--------------------------------------------------------------- commit 6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5 Author: Andrey Mokhov Date: Sun Dec 13 02:30:44 2015 +0000 Build haddock. >--------------------------------------------------------------- 6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5 src/GHC.hs | 15 ++++++++++++--- src/Rules.hs | 2 +- src/Rules/Compile.hs | 1 + src/Rules/Program.hs | 7 ++++--- src/Settings/Builders/Ghc.hs | 5 +++-- src/Settings/Builders/GhcCabal.hs | 2 ++ src/Settings/Packages.hs | 12 +++++++++--- 7 files changed, 32 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5 From git at git.haskell.org Thu Oct 26 23:41:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run cabal in -v3 mode to reveal the problem. (accce20) Message-ID: <20171026234107.8624A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/accce2015d2e61fd949885866f014026a4a69049/ghc >--------------------------------------------------------------- commit accce2015d2e61fd949885866f014026a4a69049 Author: Andrey Mokhov Date: Wed Jan 6 23:36:07 2016 +0000 Run cabal in -v3 mode to reveal the problem. See #110. [skip ci] >--------------------------------------------------------------- accce2015d2e61fd949885866f014026a4a69049 .appveyor.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index d8bb09d..0b90efa 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,12 +8,11 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /home/cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - cabal update -v + - cabal update -v3 - cabal install -j --prefix=/usr/local alex happy - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Thu Oct 26 23:41:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build deriveConstants utility. (bbdaa7e) Message-ID: <20171026234110.7B9D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbdaa7eab8d8ebe4c5e21646cd172d53d741872e/ghc >--------------------------------------------------------------- commit bbdaa7eab8d8ebe4c5e21646cd172d53d741872e Author: Andrey Mokhov Date: Sun Dec 13 03:54:05 2015 +0000 Build deriveConstants utility. >--------------------------------------------------------------- bbdaa7eab8d8ebe4c5e21646cd172d53d741872e src/GHC.hs | 10 ++++++---- src/Oracles/PackageData.hs | 3 ++- src/Predicates.hs | 5 ++++- src/Rules/Compile.hs | 10 ++++++++-- src/Rules/Data.hs | 11 +++++++++++ src/Settings/Builders/Ghc.hs | 7 ++++--- src/Settings/Packages.hs | 1 + 7 files changed, 36 insertions(+), 11 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 bbdaa7eab8d8ebe4c5e21646cd172d53d741872e From git at git.haskell.org Thu Oct 26 23:41:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run cabal in -v3 mode in bash. (351c39f) Message-ID: <20171026234111.18A223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/351c39f38b709a6304e8085cae52fe90d23a2cd9/ghc >--------------------------------------------------------------- commit 351c39f38b709a6304e8085cae52fe90d23a2cd9 Author: Andrey Mokhov Date: Wed Jan 6 23:56:24 2016 +0000 Run cabal in -v3 mode in bash. See #110. [skip ci] >--------------------------------------------------------------- 351c39f38b709a6304e8085cae52fe90d23a2cd9 .appveyor.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 0b90efa..19236d4 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -12,12 +12,12 @@ install: - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - cabal update -v3 - - cabal install -j --prefix=/usr/local alex happy + - bash -lc "cabal update -v3" + - bash -lc "cabal install -j --prefix=/usr/local alex happy" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build - - cabal install --only-dependencies + - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:41:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build genapply utility. (e99bd28) Message-ID: <20171026234113.E7ADD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e99bd28a549c2c362bf8bef7dde9f13ca05a2510/ghc >--------------------------------------------------------------- commit e99bd28a549c2c362bf8bef7dde9f13ca05a2510 Author: Andrey Mokhov Date: Sun Dec 13 19:19:18 2015 +0000 Build genapply utility. >--------------------------------------------------------------- e99bd28a549c2c362bf8bef7dde9f13ca05a2510 src/GHC.hs | 15 +++++++++------ src/Rules/Compile.hs | 7 ++++++- src/Rules/Data.hs | 16 +++++++++++++++- src/Settings/Builders/Ghc.hs | 9 ++++++--- src/Settings/Packages.hs | 2 +- 5 files changed, 37 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e99bd28a549c2c362bf8bef7dde9f13ca05a2510 From git at git.haskell.org Thu Oct 26 23:41:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to use an older cabal version. (05b4a6e) Message-ID: <20171026234114.8C9843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/05b4a6e3c481e08317678edf8e5aa21e7f658271/ghc >--------------------------------------------------------------- commit 05b4a6e3c481e08317678edf8e5aa21e7f658271 Author: Andrey Mokhov Date: Thu Jan 7 01:01:32 2016 +0000 Try to use an older cabal version. See #110. [skip ci] >--------------------------------------------------------------- 05b4a6e3c481e08317678edf8e5aa21e7f658271 .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 19236d4..4d54924 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -10,8 +10,9 @@ install: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" + # - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + # - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" + - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.20.0.3/cabal-1.20.0.3-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "cabal update -v3" - bash -lc "cabal install -j --prefix=/usr/local alex happy" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp From git at git.haskell.org Thu Oct 26 23:41:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build genprimopcode utility. (6f2b78b) Message-ID: <20171026234117.769E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6f2b78bb0f063be5ff5a8abc346f765c6729621e/ghc >--------------------------------------------------------------- commit 6f2b78bb0f063be5ff5a8abc346f765c6729621e Author: Andrey Mokhov Date: Sun Dec 13 19:25:30 2015 +0000 Build genprimopcode utility. >--------------------------------------------------------------- 6f2b78bb0f063be5ff5a8abc346f765c6729621e src/GHC.hs | 10 ++++++---- src/Rules/Data.hs | 12 +++++++++++- src/Settings/Builders/Ghc.hs | 4 ++-- src/Settings/Packages.hs | 3 ++- 4 files changed, 21 insertions(+), 8 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 3821518..ff5a106 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,7 +1,7 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, ghc, ghcCabal, ghcPkg, ghcPrim, + genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hpc, hpcBin, integerGmp, integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, @@ -23,7 +23,7 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, ghc, ghcCabal, ghcPkg, ghcPrim + , filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hpc, hpcBin, integerGmp, integerSimple , mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo , time, transformers, unix, win32, xhtml ] @@ -31,7 +31,7 @@ defaultKnownPackages = -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, + genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hpc, hpcBin, integerGmp, integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, @@ -52,6 +52,7 @@ directory = library "directory" dllSplit = utility "dll-split" filepath = library "filepath" genapply = utility "genapply" +genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" ghcPkg = utility "ghc-pkg" @@ -81,7 +82,7 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" --- TODO: genprimocode, hp2ps +-- TODO: hp2ps -- TODO: The following utils are not included into the build system because -- they seem to be unused or unrelated to the build process: chechUniques, @@ -110,6 +111,7 @@ defaultProgramPath stage pkg | pkg == deriveConstants = program $ pkgName pkg | pkg == dllSplit = program $ pkgName pkg | pkg == genapply = program $ pkgName pkg + | pkg == genprimopcode = program $ pkgName pkg | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == ghcCabal = program $ pkgName pkg | pkg == ghcPkg = program $ pkgName pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 9fbc6ec..c47c6a3 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (deriveConstants, genapply) +import GHC (deriveConstants, genapply, genprimopcode) import Oracles import Predicates (registerPackage) import Rules.Actions @@ -70,6 +70,16 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do , "utils_genapply_dist-boot_HC_OPTS = " ++ hcOpts ] writeFileChanged mk contents + priority 2.0 $ + when (pkg == genprimopcode) $ path -/- "package-data.mk" %> \mk -> do + let contents = unlines + [ "utils_genprimopcode_dist-boot_MODULES = Lexer Main ParserM Parser Syntax" + , "utils_genprimopcode_dist-boot_PROGNAME = genprimopcode" + , "utils_genprimopcode_dist-boot_HS_SRC_DIRS = ." + , "utils_genprimopcode_dist-boot_INSTALL_INPLACE = YES" + , "utils_genprimopcode_dist-boot_HC_OPTS = -package array" ] + writeFileChanged mk contents + -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- For example, get rid of diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a22bee5..3d3e224 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -96,7 +96,7 @@ packageGhcArgs = do pkgKey <- getPkgData PackageKey pkgDepIds <- getPkgDataList DepIds mconcat - [ not (pkg == deriveConstants || pkg == genapply) ? + [ not (pkg == deriveConstants || pkg == genapply || pkg == genprimopcode) ? arg "-hide-all-packages" , arg "-no-user-package-db" , stage0 ? arg "-package-db libraries/bootstrapping.conf" @@ -122,7 +122,7 @@ includeGhcArgs = do , arg $ "-I" ++ autogenPath , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] - , not (pkg == deriveConstants || pkg == genapply) ? + , not (pkg == deriveConstants || pkg == genapply || pkg == genprimopcode) ? append [ "-optP-include" , "-optP" ++ autogenPath -/- "cabal_macros.h" ] ] diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 1475e40..5f1e55e 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -9,6 +9,7 @@ getPackages :: Expr [Package] getPackages = fromDiffExpr $ defaultPackages <> userPackages -- These are the packages we build by default +-- TODO: simplify defaultPackages :: Packages defaultPackages = mconcat [ stage0 ? packagesStage0 @@ -19,7 +20,7 @@ packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] - , stage0 ? append [deriveConstants, genapply] -- TODO: simplify + , stage0 ? append [deriveConstants, genapply, genprimopcode] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? From git at git.haskell.org Thu Oct 26 23:41:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to use stack instead of cabal. (d314d4f) Message-ID: <20171026234118.1AEE43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d314d4f902566fe3cd14e6426ba985226f1df49e/ghc >--------------------------------------------------------------- commit d314d4f902566fe3cd14e6426ba985226f1df49e Author: Andrey Mokhov Date: Thu Jan 7 01:34:53 2016 +0000 Try to use stack instead of cabal. See #110. [skip ci] >--------------------------------------------------------------- d314d4f902566fe3cd14e6426ba985226f1df49e .appveyor.yml | 17 +++++------------ 1 file changed, 5 insertions(+), 12 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 4d54924..7410a5e 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,24 +1,17 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -# cache: -# - "C:\\msys64\\home\\cabal" - install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" + - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 + - 7z x stack.zip stack.exe + - stack exec -- pacman -S --noconfirm gcc binutils p7zip git + - stack install -v3 -j --prefix=/usr/local alex happy - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /usr/local" - - bash -lc "mkdir -p /usr/local/bin" - # - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - # - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.20.0.3/cabal-1.20.0.3-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - - bash -lc "cabal update -v3" - - bash -lc "cabal install -j --prefix=/usr/local alex happy" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build - - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" + - stack install --only-dependencies build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:41:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build hp2ps utility. (1057ef3) Message-ID: <20171026234120.F200A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1057ef38cea541d0b31b075bd9936a619f23f4fa/ghc >--------------------------------------------------------------- commit 1057ef38cea541d0b31b075bd9936a619f23f4fa Author: Andrey Mokhov Date: Sun Dec 13 22:18:45 2015 +0000 Build hp2ps utility. >--------------------------------------------------------------- 1057ef38cea541d0b31b075bd9936a619f23f4fa src/GHC.hs | 27 +++++++++++++-------------- src/Rules/Data.hs | 22 +++++++++++++++++++++- src/Rules/Dependencies.hs | 7 +++++-- src/Rules/Program.hs | 1 + src/Settings/Builders/Ghc.hs | 9 ++++++--- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Packages.hs | 2 +- 7 files changed, 49 insertions(+), 23 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 1057ef38cea541d0b31b075bd9936a619f23f4fa From git at git.haskell.org Thu Oct 26 23:41:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install ghc-7.10.3 before using stack. (ccf97ae) Message-ID: <20171026234121.D8B593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccf97ae74f3cbfaaa0484d12af82231832e2620f/ghc >--------------------------------------------------------------- commit ccf97ae74f3cbfaaa0484d12af82231832e2620f Author: Andrey Mokhov Date: Thu Jan 7 01:40:09 2016 +0000 Install ghc-7.10.3 before using stack. See #110. [skip ci] >--------------------------------------------------------------- ccf97ae74f3cbfaaa0484d12af82231832e2620f .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7410a5e..f282d5b 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -5,9 +5,9 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 - 7z x stack.zip stack.exe + - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - stack install -v3 -j --prefix=/usr/local alex happy - - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build From git at git.haskell.org Thu Oct 26 23:41:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (0678e10) Message-ID: <20171026234124.6DC8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0678e1030e5f90b55dedcf2d72adc431f0995de5/ghc >--------------------------------------------------------------- commit 0678e1030e5f90b55dedcf2d72adc431f0995de5 Author: Andrey Mokhov Date: Mon Dec 14 02:43:00 2015 +0000 Clean up. >--------------------------------------------------------------- 0678e1030e5f90b55dedcf2d72adc431f0995de5 src/GHC.hs | 2 +- src/Package.hs | 3 +++ 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index 355ed71..ea48014 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -28,7 +28,7 @@ defaultKnownPackages = , process, runghc, stm, templateHaskell, terminfo, time, transformers, unix , win32, xhtml ] --- Package definitions +-- Package definitions (see Package.hs) array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, diff --git a/src/Package.hs b/src/Package.hs index 85fbd13..a490cb9 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -9,11 +9,14 @@ import GHC.Generics (Generic) -- It is helpful to distinguish package names from strings. type PackageName = String +-- type PackageType = Program | Library + -- pkgPath is the path to the source code relative to the root data Package = Package { pkgName :: PackageName, -- Examples: "ghc", "Cabal" pkgPath :: FilePath -- "compiler", "libraries/Cabal/Cabal" + -- pkgType :: PackageType -- TopLevel, Library } deriving Generic From git at git.haskell.org Thu Oct 26 23:41:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to stack/windows-x86_64. (280b6fa) Message-ID: <20171026234125.584093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/280b6fa49b1e3541de7a1bc242a9b953bc00cec1/ghc >--------------------------------------------------------------- commit 280b6fa49b1e3541de7a1bc242a9b953bc00cec1 Author: Andrey Mokhov Date: Thu Jan 7 01:49:02 2016 +0000 Switch to stack/windows-x86_64. See #110. [skip ci] >--------------------------------------------------------------- 280b6fa49b1e3541de7a1bc242a9b953bc00cec1 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f282d5b..a78c02c 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -3,7 +3,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 + - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git From git at git.haskell.org Thu Oct 26 23:41:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: No need to modify configure.ac any more. See https://phabricator.haskell.org/D1638 (5e7de75) Message-ID: <20171026234127.E03E23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e7de75760b6b44eb7d9caaae3dc805c44bb6604/ghc >--------------------------------------------------------------- commit 5e7de75760b6b44eb7d9caaae3dc805c44bb6604 Author: Andrey Mokhov Date: Wed Dec 16 22:49:27 2015 +0000 No need to modify configure.ac any more. See https://phabricator.haskell.org/D1638 >--------------------------------------------------------------- 5e7de75760b6b44eb7d9caaae3dc805c44bb6604 src/Rules/Config.hs | 15 --------------- 1 file changed, 15 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 4987fcc..bb4866d 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -2,11 +2,6 @@ module Rules.Config (configRules) where import Base --- We add the following line to 'configure.ac' in order to produce configuration --- file "system.config" from "system.config.in" by running 'configure' script. -configCommand :: String -configCommand = "AC_CONFIG_FILES([" ++ configPath ++ "system.config])" - configRules :: Rules () configRules = do configPath -/- "system.config" %> \_ -> do @@ -14,16 +9,6 @@ configRules = do putBuild "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' - -- TODO: this rule won't rebuild if configure.ac is changed. Worth fixing? "configure" %> \_ -> do - -- Make sure 'configure.ac' script contains a line with configCommand - script <- fmap lines . liftIO $ readFile "configure.ac" - when (configCommand `notElem` script) $ do - putBuild $ "Adding '" ++ configCommand ++ "' to configure.ac..." - let (before, rest) = break ("AC_CONFIG_FILES" `isPrefixOf`) script - when (null rest) $ do - putError "No AC_CONFIG_FILES command in configure.ac!" - let newScript = unlines $ before ++ [configCommand] ++ rest - length newScript `seq` liftIO (writeFile "configure.ac" newScript) putBuild "Running autoconf..." cmd "bash autoconf" -- TODO: get rid of 'bash' From git at git.haskell.org Thu Oct 26 23:41:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop extra flags to stack install. (78fee43) Message-ID: <20171026234128.EB37B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/78fee435f395b30199947fd7eefd32bbb25d5804/ghc >--------------------------------------------------------------- commit 78fee435f395b30199947fd7eefd32bbb25d5804 Author: Andrey Mokhov Date: Thu Jan 7 01:59:39 2016 +0000 Drop extra flags to stack install. See #110. [skip ci] >--------------------------------------------------------------- 78fee435f395b30199947fd7eefd32bbb25d5804 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index a78c02c..1b5e3bc 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,7 +7,7 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - stack install -v3 -j --prefix=/usr/local alex happy + - stack install alex happy - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build From git at git.haskell.org Thu Oct 26 23:41:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't build system.config by default. (8ef67ed) Message-ID: <20171026234131.A32CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ef67edb699b18ca41ed535069f7183a15a98cf3/ghc >--------------------------------------------------------------- commit 8ef67edb699b18ca41ed535069f7183a15a98cf3 Author: Andrey Mokhov Date: Wed Dec 16 23:07:44 2015 +0000 Don't build system.config by default. >--------------------------------------------------------------- 8ef67edb699b18ca41ed535069f7183a15a98cf3 src/Rules/Config.hs | 3 ++- src/Settings/User.hs | 5 ++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index bb4866d..50471d5 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -1,9 +1,10 @@ module Rules.Config (configRules) where import Base +import Settings.User configRules :: Rules () -configRules = do +configRules = when buildSystemConfigFile $ do configPath -/- "system.config" %> \_ -> do need [configPath -/- "system.config.in", "configure"] putBuild "Running configure..." diff --git a/src/Settings/User.hs b/src/Settings/User.hs index d841028..5159bce 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -2,7 +2,7 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - ghcDebugged, dynamicGhcPrograms, laxDependencies + ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile ) where import Expression @@ -77,3 +77,6 @@ laxDependencies = False buildHaddock :: Predicate buildHaddock = return True + +buildSystemConfigFile :: Bool +buildSystemConfigFile = False From git at git.haskell.org Thu Oct 26 23:41:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create /home/ghc/tmp, add stack install dir to PATH. (3ecd105) Message-ID: <20171026234132.886FB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ecd10554246bfe2d69153807248881f22d50a6d/ghc >--------------------------------------------------------------- commit 3ecd10554246bfe2d69153807248881f22d50a6d Author: Andrey Mokhov Date: Thu Jan 7 02:10:08 2016 +0000 Create /home/ghc/tmp, add stack install dir to PATH. See #110. [skip ci] >--------------------------------------------------------------- 3ecd10554246bfe2d69153807248881f22d50a6d .appveyor.yml | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.appveyor.yml b/.appveyor.yml index 1b5e3bc..011b327 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,6 +8,8 @@ install: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - stack install alex happy + - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ + - bash -lc "mkdir /home/ghc/tmp" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build From git at git.haskell.org Thu Oct 26 23:41:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (850863e) Message-ID: <20171026234135.1A3F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/850863e56cf2c4d798cac7701e271c85d6bac2de/ghc >--------------------------------------------------------------- commit 850863e56cf2c4d798cac7701e271c85d6bac2de Author: Andrey Mokhov Date: Thu Dec 17 19:42:44 2015 +0000 Update README.md >--------------------------------------------------------------- 850863e56cf2c4d798cac7701e271c85d6bac2de README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 54742ee..faf3155 100644 --- a/README.md +++ b/README.md @@ -3,4 +3,4 @@ Shaking up GHC As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). -This is supposed to go into the `shake` directory of the GHC source tree (as a submodule). +This is supposed to go into the `build` directory of the GHC source tree. From git at git.haskell.org Thu Oct 26 23:41:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add appveyor badge (152f4da) Message-ID: <20171026234135.E7CB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/152f4dae7932519935f4615f305505027fbd5159/ghc >--------------------------------------------------------------- commit 152f4dae7932519935f4615f305505027fbd5159 Author: Andrey Mokhov Date: Thu Jan 7 02:21:18 2016 +0000 Add appveyor badge See #110. [skip ci] >--------------------------------------------------------------- 152f4dae7932519935f4615f305505027fbd5159 README.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 90f6422..1347ee5 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,8 @@ Shaking up GHC ============== -[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) +[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Build status](https://ci.appveyor.com/api/projects/status/9er74sbnrkco98gb?svg=true&pendingText=Windows&passingText=Windows&failingText=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) + As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC][ghc] build system From git at git.haskell.org Thu Oct 26 23:41:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add NFData instances (bf75f42) Message-ID: <20171026234138.827F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf75f422b738ae95fb7d3b814d9335c77ef6d6cd/ghc >--------------------------------------------------------------- commit bf75f422b738ae95fb7d3b814d9335c77ef6d6cd Author: Ben Gamari Date: Wed Dec 16 01:27:04 2015 +0100 Add NFData instances >--------------------------------------------------------------- bf75f422b738ae95fb7d3b814d9335c77ef6d6cd src/Builder.hs | 1 + src/Package.hs | 1 + src/Stage.hs | 1 + src/Way.hs | 3 +++ 4 files changed, 6 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 67be69f..007dae3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -111,3 +111,4 @@ fixAbsolutePathOnWindows path = do -- Instances for storing in the Shake database instance Binary Builder instance Hashable Builder +instance NFData Builder diff --git a/src/Package.hs b/src/Package.hs index a490cb9..f64daee 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -49,3 +49,4 @@ instance Ord Package where instance Binary Package instance Hashable Package where hashWithSalt salt = hashWithSalt salt . show +instance NFData Package diff --git a/src/Stage.hs b/src/Stage.hs index f4e39b0..3aca206 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -13,3 +13,4 @@ instance Show Stage where -- Instances for storing in the Shake database instance Binary Stage instance Hashable Stage +instance NFData Stage diff --git a/src/Way.hs b/src/Way.hs index 7f1ca31..095bd52 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -169,3 +169,6 @@ instance Binary Way where instance Hashable Way where hashWithSalt salt = hashWithSalt salt . show + +instance NFData Way where + rnf (Way s) = s `seq` () From git at git.haskell.org Thu Oct 26 23:41:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths. (a599895) Message-ID: <20171026234139.64CE43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5998956f9b8cc5b9042379fd298d7b823dbdaf9/ghc >--------------------------------------------------------------- commit a5998956f9b8cc5b9042379fd298d7b823dbdaf9 Author: Andrey Mokhov Date: Thu Jan 7 02:23:41 2016 +0000 Fix paths. See #110. [skip ci] >--------------------------------------------------------------- a5998956f9b8cc5b9042379fd298d7b823dbdaf9 .appveyor.yml | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 011b327..991ef0a 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -9,10 +9,9 @@ install: - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - stack install alex happy - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - - bash -lc "mkdir /home/ghc/tmp" - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - cd C:\msys64\mingw64\home\ghc\shake-build + - cd C:\msys64\home\ghc\shake-build - stack install --only-dependencies build_script: From git at git.haskell.org Thu Oct 26 23:41:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build.sh for building on Posix platforms (525f966) Message-ID: <20171026234141.EA7AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/525f9668125f368584aa62a0d47e6bc8df23d8b4/ghc >--------------------------------------------------------------- commit 525f9668125f368584aa62a0d47e6bc8df23d8b4 Author: Ben Gamari Date: Wed Dec 16 01:28:13 2015 +0100 Add build.sh for building on Posix platforms >--------------------------------------------------------------- 525f9668125f368584aa62a0d47e6bc8df23d8b4 build.sh | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/build.sh b/build.sh new file mode 100755 index 0000000..cf217bd --- /dev/null +++ b/build.sh @@ -0,0 +1,6 @@ +#!/bin/bash -e + +root=`dirname $0` +mkdir -p $root/_shake +ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/_shake -o $root/_shake/build +$root/_shake/build --lint --directory $root/.. $@ From git at git.haskell.org Thu Oct 26 23:41:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install shake, mtl and ansi-terminal. (f514cc4) Message-ID: <20171026234142.EA1073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f514cc4d9b216c6dae5cb69f406f911fb3959718/ghc >--------------------------------------------------------------- commit f514cc4d9b216c6dae5cb69f406f911fb3959718 Author: Andrey Mokhov Date: Thu Jan 7 02:40:43 2016 +0000 Install shake, mtl and ansi-terminal. See #110. [skip ci] >--------------------------------------------------------------- f514cc4d9b216c6dae5cb69f406f911fb3959718 .appveyor.yml | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 991ef0a..7bcda85 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,12 +7,10 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - stack install alex happy + - stack install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - cd C:\msys64\home\ghc\shake-build - - stack install --only-dependencies build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:41:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: deriveConstants now has a Cabal file (c0f3b67) Message-ID: <20171026234145.68CCF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c0f3b6709468744f8192171b94ab08d2c1010959/ghc >--------------------------------------------------------------- commit c0f3b6709468744f8192171b94ab08d2c1010959 Author: Ben Gamari Date: Wed Dec 16 02:19:26 2015 +0100 deriveConstants now has a Cabal file Since 314395e00be10e6343840c215a4779aeec2542df >--------------------------------------------------------------- c0f3b6709468744f8192171b94ab08d2c1010959 src/Rules/Compile.hs | 5 ----- src/Rules/Data.hs | 12 +----------- 2 files changed, 1 insertion(+), 16 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 60123ef..9f718eb 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -28,11 +28,6 @@ compilePackage _ target @ (PartialTarget stage pkg) = do build $ fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases - priority 2.0 $ buildPath -/- "DeriveConstants.o" %> \obj -> do - let src = pkgPath pkg -/- "DeriveConstants.hs" - need [src] - build $ fullTargetWithWay target (Ghc stage) vanilla [src] [obj] - priority 2.0 $ buildPath -/- "GenApply.o" %> \obj -> do let src = pkgPath pkg -/- "GenApply.hs" need [src] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index cba8b69..2898257 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (deriveConstants, genapply, genprimopcode, hp2ps) +import GHC (genapply, genprimopcode, hp2ps) import Oracles import Predicates (registerPackage) import Rules.Actions @@ -50,16 +50,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- TODO: Track dependency on this generated file -- TODO: Use a cabal file instead of manual hacks? priority 2.0 $ - when (pkg == deriveConstants) $ path -/- "package-data.mk" %> \mk -> do - let contents = unlines - [ "utils_deriveConstants_dist-boot_MODULES = DeriveConstants" - , "utils_deriveConstants_dist-boot_PROGNAME = deriveConstants" - , "utils_deriveConstants_dist-boot_HS_SRC_DIRS = ." - , "utils_deriveConstants_dist-boot_INSTALL_INPLACE = YES" - , "utils_deriveConstants_dist-boot_HC_OPTS = -package process -package containers" ] - writeFileChanged mk contents - - priority 2.0 $ when (pkg == genapply) $ path -/- "package-data.mk" %> \mk -> do ghcUnreg <- flag GhcUnregisterised let hcOpts = "-package pretty" ++ if ghcUnreg then " -DNO_REGS" else "" From git at git.haskell.org Thu Oct 26 23:41:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Take 2 (a7da5e0) Message-ID: <20171026234146.55A553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7da5e01637652109a75b05371b5e5864df8e836/ghc >--------------------------------------------------------------- commit a7da5e01637652109a75b05371b5e5864df8e836 Author: Moritz Angermann Date: Thu Jan 7 11:06:37 2016 +0800 Take 2 >--------------------------------------------------------------- a7da5e01637652109a75b05371b5e5864df8e836 shaking-up-ghc.cabal | 1 + src/Oracles/WindowsRoot.hs | 12 +++++++----- 2 files changed, 8 insertions(+), 5 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 00fb408..f9990e9 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -114,6 +114,7 @@ executable ghc-shake , extra >= 1.4 , mtl >= 2.2 , shake >= 0.15 + , split >= 0.2 , transformers >= 0.4 , unordered-containers >= 0.2 default-language: Haskell2010 diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 195f591..473a235 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -4,6 +4,7 @@ module Oracles.WindowsRoot ( ) where import Data.Char (isSpace) +import Data.List.Split (splitOn) import Base import Oracles.Config.Setting @@ -40,12 +41,13 @@ fixAbsolutePathOnWindows path = do -- | Lookup a @command@ in @PATH@ environment. lookupInPath :: FilePath -> Action FilePath -lookupInPath command - | command /= takeFileName command = return command +lookupInPath c + | c /= takeFileName c = return c | otherwise = do - Stdout out <- quietly $ cmd ["which", command] - let path = dropWhileEnd isSpace out - return path + envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" + let candidates = map (-/- c) envPaths in + -- this will crash if we do not find any valid candidate. + head <$> filterM doesFileExist candidates -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). From git at git.haskell.org Thu Oct 26 23:41:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: LIB_NAME, PACKAGE_KEY are now COMPONENT_ID (4758a21) Message-ID: <20171026234148.D66A43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4758a21d2a9441d5dadf9b40b578c2c8e55773e8/ghc >--------------------------------------------------------------- commit 4758a21d2a9441d5dadf9b40b578c2c8e55773e8 Author: Ben Gamari Date: Wed Dec 16 01:56:05 2015 +0100 LIB_NAME, PACKAGE_KEY are now COMPONENT_ID Since GHC commit 6338a1cc6df2c7fd8a62eeb4c5240dd90ee74a6c. >--------------------------------------------------------------- 4758a21d2a9441d5dadf9b40b578c2c8e55773e8 cfg/system.config.in | 12 ++++++------ src/Oracles/Config/Flag.hs | 4 ++-- src/Oracles/PackageData.hs | 6 ++---- src/Rules.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 16 ++++++++-------- 5 files changed, 21 insertions(+), 23 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 09ea1fa..60dae28 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -45,12 +45,12 @@ ar-supports-at-file = @ArSupportsAtFile@ # Build options: #=============== -supports-package-key = @SUPPORTS_PACKAGE_KEY@ -solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ -split-objects-broken = @SplitObjsBroken@ -ghc-unregisterised = @Unregisterised@ -ghc-source-path = @hardtop@ -leading-underscore = @LeadingUnderscore@ +supports-component-id = @SUPPORTS_COMPONENT_ID@ +solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ +split-objects-broken = @SplitObjsBroken@ +ghc-unregisterised = @Unregisterised@ +ghc-source-path = @hardtop@ +leading-underscore = @LeadingUnderscore@ # Information about build, host and target systems: #================================================== diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index f352ae3..631a6fc 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -16,7 +16,7 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken - | SupportsPackageKey + | SupportsComponentId -- Note, if a flag is set to empty string we treat it as set to NO. This seems -- fragile, but some flags do behave like this, e.g. GccIsClang. @@ -31,7 +31,7 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" - SupportsPackageKey -> "supports-package-key" + SupportsComponentId -> "supports-component-id" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." unless (value == "YES" || value == "NO" || value == "") . putError diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index e4aae0a..8a067b9 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -16,8 +16,7 @@ import qualified Data.HashMap.Strict as Map -- such as 'path_MODULES = Data.Array Data.Array.Base ...'. -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] data PackageData = BuildGhciLib FilePath - | LibName FilePath - | PackageKey FilePath + | ComponentId FilePath | Synopsis FilePath | Version FilePath @@ -55,8 +54,7 @@ askPackageData path key = do pkgData :: PackageData -> Action String pkgData packageData = case packageData of BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" - LibName path -> askPackageData path "LIB_NAME" - PackageKey path -> askPackageData path "PACKAGE_KEY" + ComponentId path -> askPackageData path "COMPONENT_ID" Synopsis path -> askPackageData path "SYNOPSIS" Version path -> askPackageData path "VERSION" diff --git a/src/Rules.hs b/src/Rules.hs index 2a6bd59..90769c1 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -16,15 +16,15 @@ generateTargets = action $ do libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg buildPath = targetPath stage pkg -/- "build" - libName <- interpretPartial target $ getPkgData LibName + compId <- interpretPartial target $ getPkgData ComponentId needGhciLib <- interpretPartial target $ getPkgData BuildGhciLib needHaddock <- interpretPartial target buildHaddock ways <- interpretPartial target getWays - let ghciLib = buildPath -/- "HS" ++ libName <.> "o" + let ghciLib = buildPath -/- "HS" ++ compId <.> "o" haddock = pkgHaddockFile pkg libs <- fmap concat . forM ways $ \way -> do extension <- libsuf way - let name = buildPath -/- "libHS" ++ libName + let name = buildPath -/- "libHS" ++ compId dll0 <- needDll0 stage pkg return $ [ name <.> extension ] ++ [ name ++ "-0" <.> extension | dll0 ] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 247a114..50973c0 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -91,11 +91,11 @@ wayGhcArgs = do -- TODO: Improve handling of "-hide-all-packages" packageGhcArgs :: Args packageGhcArgs = do - stage <- getStage - pkg <- getPackage - supportsPackageKey <- getFlag SupportsPackageKey - pkgKey <- getPkgData PackageKey - pkgDepIds <- getPkgDataList DepIds + stage <- getStage + pkg <- getPackage + supportsComponentId <- getFlag SupportsComponentId + compId <- getPkgData ComponentId + pkgDepIds <- getPkgDataList DepIds mconcat [ not (pkg == deriveConstants || pkg == genapply || pkg == genprimopcode || pkg == hp2ps) ? @@ -103,9 +103,9 @@ packageGhcArgs = do , arg "-no-user-package-db" , stage0 ? arg "-package-db libraries/bootstrapping.conf" , isLibrary pkg ? - if supportsPackageKey || stage /= Stage0 - then arg $ "-this-package-key " ++ pkgKey - else arg $ "-package-name " ++ pkgKey + if supportsComponentId || stage /= Stage0 + then arg $ "-this-package-key " ++ compId + else arg $ "-package-name " ++ compId , append $ map ("-package-id " ++) pkgDepIds ] -- TODO: Improve handling of "cabal_macros.h" From git at git.haskell.org Thu Oct 26 23:41:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Show the candidates. (e4ed614) Message-ID: <20171026234149.D81D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4ed614de3a98ec374536032946802a37b96e85d/ghc >--------------------------------------------------------------- commit e4ed614de3a98ec374536032946802a37b96e85d Author: Moritz Angermann Date: Thu Jan 7 11:30:05 2016 +0800 Show the candidates. >--------------------------------------------------------------- e4ed614de3a98ec374536032946802a37b96e85d src/Oracles/WindowsRoot.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 473a235..0c45230 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -46,8 +46,9 @@ lookupInPath c | otherwise = do envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths in - -- this will crash if we do not find any valid candidate. - head <$> filterM doesFileExist candidates + mapM_ putStrLn candidates + -- this will crash if we do not find any valid candidate. + head <$> filterM doesFileExist candidates -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). From git at git.haskell.org Thu Oct 26 23:41:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add configuration for libdw (96d66f0) Message-ID: <20171026234152.6C0E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/96d66f0c27df839072ee01555fa98529e3be6ef9/ghc >--------------------------------------------------------------- commit 96d66f0c27df839072ee01555fa98529e3be6ef9 Author: Ben Gamari Date: Wed Dec 16 02:42:11 2015 +0100 Add configuration for libdw >--------------------------------------------------------------- 96d66f0c27df839072ee01555fa98529e3be6ef9 cfg/system.config.in | 6 ++++++ src/Oracles/Config/Flag.hs | 2 ++ src/Rules/Generate.hs | 5 ++++- 3 files changed, 12 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 60dae28..9de3166 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -116,3 +116,9 @@ iconv-lib-dirs = @ICONV_LIB_DIRS@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ + + +# Optional Dependencies: +#======================= + +with-libdw = @HaveLibdw@ diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 631a6fc..47ea75d 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -17,6 +17,7 @@ data Flag = ArSupportsAtFile | SolarisBrokenShld | SplitObjectsBroken | SupportsComponentId + | WithLibdw -- Note, if a flag is set to empty string we treat it as set to NO. This seems -- fragile, but some flags do behave like this, e.g. GccIsClang. @@ -32,6 +33,7 @@ flag f = do SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" SupportsComponentId -> "supports-component-id" + WithLibdw -> "with-libdw" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." unless (value == "YES" || value == "NO" || value == "") . putError diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 069d88f..53b7dd6 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -106,6 +106,7 @@ generateConfigHs = do cGHC_SPLIT_PGM <- fmap takeBaseName $ getBuilderPath GhcSplit cLibFFI <- lift useLibFFIForAdjustors rtsWays <- getRtsWays + cGhcRtsWithLibdw <- getFlag WithLibdw let cGhcRTSWays = unwords $ map show rtsWays return $ unlines [ "{-# LANGUAGE CPP #-}" @@ -169,7 +170,9 @@ generateConfigHs = do , "cGhcThreaded :: Bool" , "cGhcThreaded = " ++ show (threaded `elem` rtsWays) , "cGhcDebugged :: Bool" - , "cGhcDebugged = " ++ show ghcDebugged ] + , "cGhcDebugged = " ++ show ghcDebugged + , "cGhcRtsWithLibdw :: Bool" + , "cGhcRtsWithLibdw = " ++ show cGhcRtsWithLibdw ] generatePlatformH :: Expr String generatePlatformH = do From git at git.haskell.org Thu Oct 26 23:41:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: :( (0fa71d1) Message-ID: <20171026234153.73DA03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0fa71d10277a13d26c0f441745993f0a45ad5dc3/ghc >--------------------------------------------------------------- commit 0fa71d10277a13d26c0f441745993f0a45ad5dc3 Author: Moritz Angermann Date: Thu Jan 7 13:02:51 2016 +0800 :( >--------------------------------------------------------------- 0fa71d10277a13d26c0f441745993f0a45ad5dc3 src/Oracles/WindowsRoot.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 0c45230..6def89c 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -45,8 +45,8 @@ lookupInPath c | c /= takeFileName c = return c | otherwise = do envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" - let candidates = map (-/- c) envPaths in - mapM_ putStrLn candidates + let candidates = map (-/- c) envPaths + liftIO $ mapM_ putStrLn candidates -- this will crash if we do not find any valid candidate. head <$> filterM doesFileExist candidates From git at git.haskell.org Thu Oct 26 23:41:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GHC: bin-package-db is now ghc-boot (73b4605) Message-ID: <20171026234155.DB8A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73b460528b96ce7c6c056d25dee9c7e50924f59c/ghc >--------------------------------------------------------------- commit 73b460528b96ce7c6c056d25dee9c7e50924f59c Author: Ben Gamari Date: Wed Dec 16 01:32:59 2015 +0100 GHC: bin-package-db is now ghc-boot >--------------------------------------------------------------- 73b460528b96ce7c6c056d25dee9c7e50924f59c src/GHC.hs | 8 ++++---- src/Settings/Packages.hs | 2 +- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index ea48014..30414db 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,5 +1,5 @@ module GHC ( - array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, + array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, @@ -20,7 +20,7 @@ import Stage -- which can be overridden in Settings/User.hs. defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, binPackageDb, binary, bytestring, cabal, compiler + [ array, base, ghcBoot, binary, bytestring, cabal, compiler , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit , filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin @@ -29,7 +29,7 @@ defaultKnownPackages = , win32, xhtml ] -- Package definitions (see Package.hs) -array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, +array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, @@ -38,7 +38,7 @@ array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, array = library "array" base = library "base" -binPackageDb = library "bin-package-db" +ghcBoot = library "ghc-boot" binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 80fc202..febb254 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -18,7 +18,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg + [ append [ ghcBoot, binary, cabal, compiler, ghc, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] , stage0 ? append [deriveConstants, genapply, genprimopcode, hp2ps] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] From git at git.haskell.org Thu Oct 26 23:41:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: :+1: (b47bd51) Message-ID: <20171026234156.E3D253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b47bd516326d7d9652a1ba6d37352e01766390f2/ghc >--------------------------------------------------------------- commit b47bd516326d7d9652a1ba6d37352e01766390f2 Author: Moritz Angermann Date: Thu Jan 7 13:51:30 2016 +0800 :+1: >--------------------------------------------------------------- b47bd516326d7d9652a1ba6d37352e01766390f2 src/Builder.hs | 6 ++++-- src/Oracles/WindowsRoot.hs | 1 - 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 6e4dba5..0613452 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -95,8 +95,10 @@ builderPath builder = do putError $ "\nCannot find path to '" ++ (builderKey builder) ++ "' in configuration files." windows <- windowsHost - let path' = if null path then "" else path -<.> exe in - (if windows then fixAbsolutePathOnWindows else lookupInPath) path' + case (path, windows) of + ("", _) -> return path + (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) + (p, False) -> lookupInPath (p -<.> exe) getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 6def89c..4186700 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -46,7 +46,6 @@ lookupInPath c | otherwise = do envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths - liftIO $ mapM_ putStrLn candidates -- this will crash if we do not find any valid candidate. head <$> filterM doesFileExist candidates From git at git.haskell.org Thu Oct 26 23:41:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:41:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Dependencies: Use msum instead of explicit pattern matching (1c8539d) Message-ID: <20171026234159.51EE63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c8539dfd3761a3a69d9514d58e3e196127661a3/ghc >--------------------------------------------------------------- commit 1c8539dfd3761a3a69d9514d58e3e196127661a3 Author: Ben Gamari Date: Wed Dec 16 16:35:24 2015 +0100 Dependencies: Use msum instead of explicit pattern matching >--------------------------------------------------------------- 1c8539dfd3761a3a69d9514d58e3e196127661a3 src/Oracles/Dependencies.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index d0f926d..c27c2cc 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -2,6 +2,7 @@ module Oracles.Dependencies (dependencies, dependenciesOracle) where import Base +import Control.Monad.Trans.Maybe import qualified Data.HashMap.Strict as Map newtype DependenciesKey = DependenciesKey (FilePath, FilePath) @@ -16,12 +17,11 @@ newtype DependenciesKey = DependenciesKey (FilePath, FilePath) dependencies :: FilePath -> FilePath -> Action (FilePath, [FilePath]) dependencies path obj = do let depFile = path -/- ".dependencies" - res1 <- askOracle $ DependenciesKey (depFile, obj) - -- if no dependencies found attempt to drop the way prefix (for *.c sources) - res2 <- case res1 of - Nothing -> askOracle $ DependenciesKey (depFile, obj -<.> "o") - _ -> return res1 - case res2 of + -- if no dependencies found then attempt to drop the way prefix (for *.c sources) + res <- runMaybeT $ msum + $ map (\obj' -> MaybeT $ askOracle $ DependenciesKey (depFile, obj')) + [obj, obj -<.> "o"] + case res of Nothing -> putError $ "No dependencies found for '" ++ obj ++ "'." Just [] -> putError $ "Empty dependency list for '" ++ obj ++ "'." Just (src:depFiles) -> return (src, depFiles) From git at git.haskell.org Thu Oct 26 23:42:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix the old-time issue. (909ed08) Message-ID: <20171026234200.5D9133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/909ed08eea7d843c5fb6c022349b3afc10946b60/ghc >--------------------------------------------------------------- commit 909ed08eea7d843c5fb6c022349b3afc10946b60 Author: Andrey Mokhov Date: Thu Jan 7 09:24:05 2016 +0000 Fix the old-time issue. See #110. [skip ci] >--------------------------------------------------------------- 909ed08eea7d843c5fb6c022349b3afc10946b60 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7bcda85..da02948 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,7 +7,7 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - stack install alex happy shake ansi-terminal mtl + - echo "" | stack --no-terminal alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Thu Oct 26 23:42:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: genprimopcode also has a Cabal file (5ff0907) Message-ID: <20171026234202.E2A413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ff090768598e587c5ab617e25844911944e79ad/ghc >--------------------------------------------------------------- commit 5ff090768598e587c5ab617e25844911944e79ad Author: Ben Gamari Date: Wed Dec 16 03:17:23 2015 +0100 genprimopcode also has a Cabal file As of GHC commit 314395e00be10e6343840c215a4779aeec2542df. >--------------------------------------------------------------- 5ff090768598e587c5ab617e25844911944e79ad src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 363d804..95ac426 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (genprimopcode, hp2ps) +import GHC (hp2ps) import Oracles import Predicates (registerPackage) import Rules.Actions From git at git.haskell.org Thu Oct 26 23:42:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Restore install argument to stack. (2ad773b) Message-ID: <20171026234203.CEB5B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ad773b62f0558f6a83b585b543e3a0a847c2911/ghc >--------------------------------------------------------------- commit 2ad773b62f0558f6a83b585b543e3a0a847c2911 Author: Andrey Mokhov Date: Thu Jan 7 09:37:20 2016 +0000 Restore install argument to stack. See #110. [skip ci] >--------------------------------------------------------------- 2ad773b62f0558f6a83b585b543e3a0a847c2911 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index da02948..8f2e278 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,7 +7,7 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - echo "" | stack --no-terminal alex happy shake ansi-terminal mtl + - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Thu Oct 26 23:42:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: genapply now has a Cabal build (c525470) Message-ID: <20171026234206.58C113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5254701040d51590fd9f26cbff566be49ee3d58/ghc >--------------------------------------------------------------- commit c5254701040d51590fd9f26cbff566be49ee3d58 Author: Ben Gamari Date: Wed Dec 16 03:13:51 2015 +0100 genapply now has a Cabal build >--------------------------------------------------------------- c5254701040d51590fd9f26cbff566be49ee3d58 src/Rules/Compile.hs | 5 ----- src/Rules/Data.hs | 26 +------------------------- 2 files changed, 1 insertion(+), 30 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 9f718eb..6b81a47 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -28,11 +28,6 @@ compilePackage _ target @ (PartialTarget stage pkg) = do build $ fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases - priority 2.0 $ buildPath -/- "GenApply.o" %> \obj -> do - let src = pkgPath pkg -/- "GenApply.hs" - need [src] - build $ fullTargetWithWay target (Ghc stage) vanilla [src] [obj] - matchBuildResult buildPath "o-boot" ?> \obj -> do (src, deps) <- dependencies buildPath obj need $ src : deps diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 2898257..363d804 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (genapply, genprimopcode, hp2ps) +import GHC (genprimopcode, hp2ps) import Oracles import Predicates (registerPackage) import Rules.Actions @@ -47,30 +47,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do postProcessPackageData $ path -/- "package-data.mk" - -- TODO: Track dependency on this generated file - -- TODO: Use a cabal file instead of manual hacks? - priority 2.0 $ - when (pkg == genapply) $ path -/- "package-data.mk" %> \mk -> do - ghcUnreg <- flag GhcUnregisterised - let hcOpts = "-package pretty" ++ if ghcUnreg then " -DNO_REGS" else "" - contents = unlines - [ "utils_genapply_dist-boot_MODULES = GenApply" - , "utils_genapply_dist-boot_PROGNAME = genapply" - , "utils_genapply_dist-boot_HS_SRC_DIRS = ." - , "utils_genapply_dist-boot_INSTALL_INPLACE = YES" - , "utils_genapply_dist-boot_HC_OPTS = " ++ hcOpts ] - writeFileChanged mk contents - - priority 2.0 $ - when (pkg == genprimopcode) $ path -/- "package-data.mk" %> \mk -> do - let contents = unlines - [ "utils_genprimopcode_dist-boot_MODULES = Lexer Main ParserM Parser Syntax" - , "utils_genprimopcode_dist-boot_PROGNAME = genprimopcode" - , "utils_genprimopcode_dist-boot_HS_SRC_DIRS = ." - , "utils_genprimopcode_dist-boot_INSTALL_INPLACE = YES" - , "utils_genprimopcode_dist-boot_HC_OPTS = -package array" ] - writeFileChanged mk contents - -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps -- TODO: code duplication around ghcIncludeDirs -- TODO: now using DEP_EXTRA_LIBS instead of EXTRA_LIBRARIES From git at git.haskell.org Thu Oct 26 23:42:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve needBuilder, see #124. (360a4c3) Message-ID: <20171026234207.5597B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/360a4c37f4060254157d19443a3b3c95b8c5b1c7/ghc >--------------------------------------------------------------- commit 360a4c37f4060254157d19443a3b3c95b8c5b1c7 Author: Andrey Mokhov Date: Thu Jan 7 09:37:52 2016 +0000 Improve needBuilder, see #124. >--------------------------------------------------------------- 360a4c37f4060254157d19443a3b3c95b8c5b1c7 src/Builder.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Builder.hs b/src/Builder.hs index 5ed9e1d..e4d8221 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -106,7 +106,7 @@ specified = fmap (not . null) . builderPath -- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). needBuilder :: Bool -> Builder -> Action () -needBuilder laxDependencies builder = do +needBuilder laxDependencies builder = whenM (specified builder) $ do path <- builderPath builder if laxDependencies && allowOrderOnlyDependency builder then orderOnly [path] From git at git.haskell.org Thu Oct 26 23:42:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add remote GHCi libraries (0afdf64) Message-ID: <20171026234209.CE65F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0afdf642a4a9209c578ddd8dd84cd2886bcd6e77/ghc >--------------------------------------------------------------- commit 0afdf642a4a9209c578ddd8dd84cd2886bcd6e77 Author: Ben Gamari Date: Fri Dec 18 12:27:16 2015 +0100 Add remote GHCi libraries See GHC commit 4905b83a2d448c65ccced385343d4e8124548a3b. >--------------------------------------------------------------- 0afdf642a4a9209c578ddd8dd84cd2886bcd6e77 src/GHC.hs | 14 ++++++++------ src/Settings/Packages.hs | 3 ++- 2 files changed, 10 insertions(+), 7 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 30414db..06140b1 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,9 +1,9 @@ module GHC ( array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, + genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, + integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath @@ -22,11 +22,11 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, ghcBoot, binary, bytestring, cabal, compiler , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim + , filepath, genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin - , integerGmp, integerSimple, mkUserGuidePart, parallel, pretty, primitive - , process, runghc, stm, templateHaskell, terminfo, time, transformers, unix - , win32, xhtml ] + , integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty + , primitive , process, runghc, stm, templateHaskell, terminfo, time + , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, @@ -54,6 +54,7 @@ genapply = utility "genapply" genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" +ghci = library "ghci" `setPath` "libraries/ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" ghcPwd = utility "ghc-pwd" @@ -67,6 +68,7 @@ hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" integerGmp = library "integer-gmp" integerSimple = library "integer-simple" +iservBin = topLevel "iserv-bin" `setPath` "iserv" mkUserGuidePart = utility "mkUserGuidePart" parallel = library "parallel" pretty = library "pretty" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index febb254..718b8de 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -29,10 +29,11 @@ packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq , directory, dllSplit, filepath - , ghcPrim, ghcPwd, haskeline, hpcBin, integerLibrary + , ghci, ghcPrim, ghcPwd, haskeline, hpcBin, integerLibrary , mkUserGuidePart, pretty, process, runghc, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] + , notM windowsHost ? append [iservBin] , buildHaddock ? append [xhtml] ] packagesStage2 :: Packages From git at git.haskell.org Thu Oct 26 23:42:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Prepend to configure. (39c3486) Message-ID: <20171026234210.D5E8B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39c34860df442efeb8e4c185d92549d828255191/ghc >--------------------------------------------------------------- commit 39c34860df442efeb8e4c185d92549d828255191 Author: Andrey Mokhov Date: Thu Jan 7 10:12:13 2016 +0000 Prepend to configure. See #110. [skip ci] >--------------------------------------------------------------- 39c34860df442efeb8e4c185d92549d828255191 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 8f2e278..a5763cc 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,5 +14,5 @@ install: build_script: - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload" - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:42:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: The new build system will live in `shake-build`. (bd2a394) Message-ID: <20171026234213.428463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd2a394ec33a93d17d74db243dc8182d2f13de31/ghc >--------------------------------------------------------------- commit bd2a394ec33a93d17d74db243dc8182d2f13de31 Author: Andrey Mokhov Date: Fri Dec 18 21:18:10 2015 +0000 The new build system will live in `shake-build`. >--------------------------------------------------------------- bd2a394ec33a93d17d74db243dc8182d2f13de31 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index faf3155..05f3352 100644 --- a/README.md +++ b/README.md @@ -3,4 +3,4 @@ Shaking up GHC As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). -This is supposed to go into the `build` directory of the GHC source tree. +This is supposed to go into the `shake-build` directory of the GHC source tree. From git at git.haskell.org Thu Oct 26 23:42:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Oracle (aff54c8) Message-ID: <20171026234214.61BB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aff54c850f52d875105564d9ef2ec5662cc6c5b2/ghc >--------------------------------------------------------------- commit aff54c850f52d875105564d9ef2ec5662cc6c5b2 Author: Moritz Angermann Date: Thu Jan 7 18:47:46 2016 +0800 Adds Oracle >--------------------------------------------------------------- aff54c850f52d875105564d9ef2ec5662cc6c5b2 shaking-up-ghc.cabal | 2 +- src/Oracles.hs | 2 ++ src/Oracles/AbsoluteCommand.hs | 40 ++++++++++++++++++++++++++++++++++++++++ src/Oracles/WindowsRoot.hs | 13 +------------ src/Rules/Oracles.hs | 15 ++++++++------- 5 files changed, 52 insertions(+), 20 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f9990e9..96efe57 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -22,6 +22,7 @@ executable ghc-shake , Expression , GHC , Oracles + , Oracles.AbsoluteCommand , Oracles.ArgsHash , Oracles.Config , Oracles.Config.Flag @@ -114,7 +115,6 @@ executable ghc-shake , extra >= 1.4 , mtl >= 2.2 , shake >= 0.15 - , split >= 0.2 , transformers >= 0.4 , unordered-containers >= 0.2 default-language: Haskell2010 diff --git a/src/Oracles.hs b/src/Oracles.hs index b77a786..07e92f2 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,4 +1,5 @@ module Oracles ( + module Oracles.AbsoluteCommand, module Oracles.Config, module Oracles.Config.Flag, module Oracles.Config.Setting, @@ -8,6 +9,7 @@ module Oracles ( module Oracles.WindowsRoot ) where +import Oracles.AbsoluteCommand import Oracles.Config import Oracles.Config.Flag import Oracles.Config.Setting diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/AbsoluteCommand.hs new file mode 100644 index 0000000..23de6ff --- /dev/null +++ b/src/Oracles/AbsoluteCommand.hs @@ -0,0 +1,40 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +module Oracles.AbsoluteCommand ( + lookupInPath, absoluteCommandOracle + ) where + +import Base + +newtype AbsoluteCommand = AbsoluteCommand String + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +absoluteCommand :: String -> Action String +absoluteCommand = askOracle . AbsoluteCommand + +-- | Lookup a @command@ in @PATH@ environment. +lookupInPath :: FilePath -> Action FilePath +lookupInPath c + | c /= takeFileName c = return c + | otherwise = absoluteCommand c + +-- | Split function. Splits a string @s@ into chunks +-- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 +wordsWhen :: (Char -> Bool) -> String -> [String] +wordsWhen p s = + case dropWhile p s of + "" -> [] + s' -> w : wordsWhen p s'' + where (w, s'') = break p s' + + +absoluteCommandOracle :: Rules () +absoluteCommandOracle = do + o <- newCache $ \c -> do + envPaths <- wordsWhen (== ':') <$> getEnvWithDefault "" "PATH" + let candidates = map (-/- c) envPaths + -- this will crash if we do not find any valid candidate. + fullCommand <- head <$> filterM doesFileExist candidates + putOracle $ "Found '" ++ c ++ "' at " ++ "'" ++ fullCommand ++ "'" + return fullCommand + _ <- addOracle $ \(AbsoluteCommand c) -> o c + return () diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 4186700..413f289 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -1,10 +1,9 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.WindowsRoot ( - windowsRoot, fixAbsolutePathOnWindows, lookupInPath, topDirectory, windowsRootOracle + windowsRoot, fixAbsolutePathOnWindows, topDirectory, windowsRootOracle ) where import Data.Char (isSpace) -import Data.List.Split (splitOn) import Base import Oracles.Config.Setting @@ -39,16 +38,6 @@ fixAbsolutePathOnWindows path = do else return path --- | Lookup a @command@ in @PATH@ environment. -lookupInPath :: FilePath -> Action FilePath -lookupInPath c - | c /= takeFileName c = return c - | otherwise = do - envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" - let candidates = map (-/- c) envPaths - -- this will crash if we do not find any valid candidate. - head <$> filterM doesFileExist candidates - -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). windowsRootOracle :: Rules () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 92e8a40..a4d6c70 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -7,10 +7,11 @@ import Oracles.ModuleFiles oracleRules :: Rules () oracleRules = do - argsHashOracle -- see Oracles.ArgsHash - configOracle -- see Oracles.Config - dependenciesOracle -- see Oracles.Dependencies - moduleFilesOracle -- see Oracles.ModuleFiles - packageDataOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - windowsRootOracle -- see Oracles.WindowsRoot + absoluteCommandOracle -- see Oracles.WindowsRoot + argsHashOracle -- see Oracles.ArgsHash + configOracle -- see Oracles.Config + dependenciesOracle -- see Oracles.Dependencies + moduleFilesOracle -- see Oracles.ModuleFiles + packageDataOracle -- see Oracles.PackageData + packageDepsOracle -- see Oracles.PackageDeps + windowsRootOracle -- see Oracles.WindowsRoot From git at git.haskell.org Thu Oct 26 23:42:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #2 from bgamari/master (c937606) Message-ID: <20171026234216.CD8A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c937606629a97188500bac159d2c8882ccbac3e9/ghc >--------------------------------------------------------------- commit c937606629a97188500bac159d2c8882ccbac3e9 Merge: bd2a394 0afdf64 Author: Andrey Mokhov Date: Fri Dec 18 23:16:30 2015 +0000 Merge pull request #2 from bgamari/master Various fixes >--------------------------------------------------------------- c937606629a97188500bac159d2c8882ccbac3e9 build.sh | 6 ++++++ cfg/system.config.in | 18 ++++++++++++------ src/Builder.hs | 1 + src/GHC.hs | 22 ++++++++++++---------- src/Oracles/Config/Flag.hs | 6 ++++-- src/Oracles/Dependencies.hs | 12 ++++++------ src/Oracles/PackageData.hs | 6 ++---- src/Package.hs | 1 + src/Rules.hs | 6 +++--- src/Rules/Compile.hs | 10 ---------- src/Rules/Data.hs | 36 +----------------------------------- src/Rules/Generate.hs | 5 ++++- src/Settings/Builders/Ghc.hs | 16 ++++++++-------- src/Settings/Packages.hs | 5 +++-- src/Stage.hs | 1 + src/Way.hs | 3 +++ 16 files changed, 67 insertions(+), 87 deletions(-) From git at git.haskell.org Thu Oct 26 23:42:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Escape echo quotes. (9024712) Message-ID: <20171026234217.E359D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/902471256bf5aee2974afb968f0cf5bdbd8cae78/ghc >--------------------------------------------------------------- commit 902471256bf5aee2974afb968f0cf5bdbd8cae78 Author: Andrey Mokhov Date: Thu Jan 7 10:54:09 2016 +0000 Escape echo quotes. See #110. [skip ci] >--------------------------------------------------------------- 902471256bf5aee2974afb968f0cf5bdbd8cae78 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index a5763cc..f74c459 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,5 +14,5 @@ install: build_script: - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:42:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Call bash with single quotes. (b54121d) Message-ID: <20171026234221.5BAD63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b54121d141b55b7b81d5be6e4a2571ab27756fd3/ghc >--------------------------------------------------------------- commit b54121d141b55b7b81d5be6e4a2571ab27756fd3 Author: Andrey Mokhov Date: Thu Jan 7 11:15:24 2016 +0000 Call bash with single quotes. See #110. [skip ci] >--------------------------------------------------------------- b54121d141b55b7b81d5be6e4a2571ab27756fd3 .appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f74c459..c3c4869 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -5,14 +5,14 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" + - bash -lc 'curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1' - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - bash -lc 'mv /home/ghc/tmp/* /home/ghc' build_script: - - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" - - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" + - bash -lc 'cd /home/ghc && ./boot' + - bash -lc 'cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload' + - bash -lc 'cd /home/ghc && ./shake-build/build.bat -j --no-progress' From git at git.haskell.org Thu Oct 26 23:42:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move to shake-build subdirectory. (6961517) Message-ID: <20171026234220.3FDEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/69615175a302d90a4e8b76d419124282d0b861e6/ghc >--------------------------------------------------------------- commit 69615175a302d90a4e8b76d419124282d0b861e6 Author: Andrey Mokhov Date: Sat Dec 19 01:04:20 2015 +0000 Move to shake-build subdirectory. >--------------------------------------------------------------- 69615175a302d90a4e8b76d419124282d0b861e6 src/Base.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 896ddc9..bfa7730 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -39,11 +39,14 @@ import qualified System.Directory as IO import System.IO -- Build system files and paths +shakePath :: FilePath +shakePath = "shake-build" + shakeFilesPath :: FilePath -shakeFilesPath = "_build/" +shakeFilesPath = shakeFilesPath -/- ".db" configPath :: FilePath -configPath = "shake/cfg/" +configPath = shakePath -/- "cfg" bootPackageConstraints :: FilePath bootPackageConstraints = shakeFilesPath ++ "boot-package-constraints" From git at git.haskell.org Thu Oct 26 23:42:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set shakeFilesPath to shake-build/.db (1203444) Message-ID: <20171026234223.A468E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12034445640aadd319ee7639c303b524c1d6df80/ghc >--------------------------------------------------------------- commit 12034445640aadd319ee7639c303b524c1d6df80 Author: Andrey Mokhov Date: Sat Dec 19 01:06:14 2015 +0000 Set shakeFilesPath to shake-build/.db >--------------------------------------------------------------- 12034445640aadd319ee7639c303b524c1d6df80 src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index bfa7730..e95aa94 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -43,7 +43,7 @@ shakePath :: FilePath shakePath = "shake-build" shakeFilesPath :: FilePath -shakeFilesPath = shakeFilesPath -/- ".db" +shakeFilesPath = shakePath -/- ".db" configPath :: FilePath configPath = shakePath -/- "cfg" From git at git.haskell.org Thu Oct 26 23:42:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing generated dependencies for rts, see #123. (f187ca8) Message-ID: <20171026234224.C52123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f187ca8af97a2a45a3a1d09b87dbdc12d4819987/ghc >--------------------------------------------------------------- commit f187ca8af97a2a45a3a1d09b87dbdc12d4819987 Author: Andrey Mokhov Date: Thu Jan 7 11:20:36 2016 +0000 Fix missing generated dependencies for rts, see #123. >--------------------------------------------------------------- f187ca8af97a2a45a3a1d09b87dbdc12d4819987 src/Rules/Data.hs | 5 ++--- src/Rules/Generate.hs | 2 +- 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 29f8d3d..ee15c19 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -104,9 +104,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fullTarget target (GhcPkg stage) [rtsConf] [] rtsConf %> \_ -> do - need [ rtsConfIn - , "includes/ghcautoconf.h" - , "includes/ghcplatform.h" ] + orderOnly $ generatedDependencies stage pkg + need [ rtsConfIn ] build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] let fixRtsConf = unlines diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 3eb1231..8ca7b94 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -76,7 +76,7 @@ generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == ghcPrim = ghcPrimDependencies stage - | pkg == rts = derivedConstantsDependencies + | pkg == rts = includesDependencies ++ derivedConstantsDependencies | stage == Stage0 = defaultDependencies | otherwise = [] From git at git.haskell.org Thu Oct 26 23:42:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Shake database to shake-build/.db, rename _shake to .shake for consistency. (ddfe5bc) Message-ID: <20171026234227.124613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ddfe5bcdfaf7147bee73d790e42584c78485127c/ghc >--------------------------------------------------------------- commit ddfe5bcdfaf7147bee73d790e42584c78485127c Author: Andrey Mokhov Date: Sun Dec 20 04:04:07 2015 +0000 Move Shake database to shake-build/.db, rename _shake to .shake for consistency. >--------------------------------------------------------------- ddfe5bcdfaf7147bee73d790e42584c78485127c .gitignore | 7 ++----- build.bat | 4 ++-- build.sh | 6 +++--- src/Base.hs | 4 ++-- 4 files changed, 9 insertions(+), 12 deletions(-) diff --git a/.gitignore b/.gitignore index 94b9664..74a0c27 100644 --- a/.gitignore +++ b/.gitignore @@ -1,6 +1,3 @@ -*.o -*.hi -_shake/ -_build/ +.shake/ +.db/ cfg/system.config -arg/*/*.txt diff --git a/build.bat b/build.bat index b45bdde..ab26e07 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,2 @@ - at mkdir _shake 2> nul - at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at mkdir .shake 2> nul + at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=.shake -o .shake/build && .shake\build --lint --directory ".." %* diff --git a/build.sh b/build.sh index cf217bd..d350779 100755 --- a/build.sh +++ b/build.sh @@ -1,6 +1,6 @@ #!/bin/bash -e root=`dirname $0` -mkdir -p $root/_shake -ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/_shake -o $root/_shake/build -$root/_shake/build --lint --directory $root/.. $@ +mkdir -p $root/.shake +ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/.shake -o $root/.shake/build +$root/.shake/build --lint --directory $root/.. $@ diff --git a/src/Base.hs b/src/Base.hs index e95aa94..33b01bd 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -49,10 +49,10 @@ configPath :: FilePath configPath = shakePath -/- "cfg" bootPackageConstraints :: FilePath -bootPackageConstraints = shakeFilesPath ++ "boot-package-constraints" +bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" packageDependencies :: FilePath -packageDependencies = shakeFilesPath ++ "package-dependencies" +packageDependencies = shakeFilesPath -/- "package-dependencies" -- Utility functions -- Find and replace all occurrences of a value in a list From git at git.haskell.org Thu Oct 26 23:42:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring bash quoting back. (2d333d5) Message-ID: <20171026234228.3CF793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d333d5fdf2b85180eb03a59764d73ff3477ea19/ghc >--------------------------------------------------------------- commit 2d333d5fdf2b85180eb03a59764d73ff3477ea19 Author: Andrey Mokhov Date: Thu Jan 7 12:17:15 2016 +0000 Bring bash quoting back. See #110. [skip ci] >--------------------------------------------------------------- 2d333d5fdf2b85180eb03a59764d73ff3477ea19 .appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index c3c4869..f74c459 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -5,14 +5,14 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - - bash -lc 'curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1' + - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - - bash -lc 'mv /home/ghc/tmp/* /home/ghc' + - bash -lc "mv /home/ghc/tmp/* /home/ghc" build_script: - - bash -lc 'cd /home/ghc && ./boot' - - bash -lc 'cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload' - - bash -lc 'cd /home/ghc && ./shake-build/build.bat -j --no-progress' + - bash -lc "cd /home/ghc && ./boot" + - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:42:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (5975b50) Message-ID: <20171026234230.7B0E13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5975b50e948df0c680b56c077494f55599131fa1/ghc >--------------------------------------------------------------- commit 5975b50e948df0c680b56c077494f55599131fa1 Author: Andrey Mokhov Date: Sun Dec 20 04:04:28 2015 +0000 Clean up. >--------------------------------------------------------------- 5975b50e948df0c680b56c077494f55599131fa1 src/GHC.hs | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 06140b1..0279197 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,7 +1,7 @@ module GHC ( - array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, - compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, + array, base, binary, bytestring, cabal, compiler, containers, compareSizes, + deepseq, deriveConstants, directory, dllSplit, filepath, genapply, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, @@ -20,25 +20,24 @@ import Stage -- which can be overridden in Settings/User.hs. defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, ghcBoot, binary, bytestring, cabal, compiler - , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim + [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes + , deepseq, deriveConstants, directory, dllSplit, filepath, genapply + , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin , integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty , primitive , process, runghc, stm, templateHaskell, terminfo, time , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) -array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, - compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, +array, base, binary, bytestring, cabal, compiler, containers, compareSizes, + deepseq, deriveConstants, directory, dllSplit, filepath, genapply, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, + integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" -ghcBoot = library "ghc-boot" binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" @@ -53,8 +52,9 @@ filepath = library "filepath" genapply = utility "genapply" genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" +ghcBoot = library "ghc-boot" ghcCabal = utility "ghc-cabal" -ghci = library "ghci" `setPath` "libraries/ghci" +ghci = library "ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" ghcPwd = utility "ghc-pwd" From git at git.haskell.org Thu Oct 26 23:42:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Moves wordsWhen into Base, and adjusts names and types to be more descriptive. (1d3de4c) Message-ID: <20171026234231.A236F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1d3de4cf66717bd5c10dda3b10b305aa736abddb/ghc >--------------------------------------------------------------- commit 1d3de4cf66717bd5c10dda3b10b305aa736abddb Author: Moritz Angermann Date: Thu Jan 7 20:17:23 2016 +0800 Moves wordsWhen into Base, and adjusts names and types to be more descriptive. >--------------------------------------------------------------- 1d3de4cf66717bd5c10dda3b10b305aa736abddb src/Base.hs | 11 ++++++++++- src/Builder.hs | 2 +- src/Oracles/AbsoluteCommand.hs | 20 ++++++-------------- 3 files changed, 17 insertions(+), 16 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 36f2eb9..8830a7c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -24,7 +24,7 @@ module Base ( -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, replace, quote, chunksOfSize, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), - versionToInt, removeFileIfExists, removeDirectoryIfExists + versionToInt, removeFileIfExists, removeDirectoryIfExists, wordsWhen ) where import Control.Applicative @@ -238,3 +238,12 @@ removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f removeDirectoryIfExists :: FilePath -> Action () removeDirectoryIfExists d = liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d + +-- | Split function. Splits a string @s@ into chunks +-- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 +wordsWhen :: (Char -> Bool) -> String -> [String] +wordsWhen p s = + case dropWhile p s of + "" -> [] + s' -> w : wordsWhen p s'' + where (w, s'') = break p s' diff --git a/src/Builder.hs b/src/Builder.hs index 0613452..743c956 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -98,7 +98,7 @@ builderPath builder = do case (path, windows) of ("", _) -> return path (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) - (p, False) -> lookupInPath (p -<.> exe) + (p, False) -> lookupInPathOracle (p -<.> exe) getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/AbsoluteCommand.hs index 23de6ff..c60f429 100644 --- a/src/Oracles/AbsoluteCommand.hs +++ b/src/Oracles/AbsoluteCommand.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.AbsoluteCommand ( - lookupInPath, absoluteCommandOracle + lookupInPathOracle, absoluteCommandOracle ) where import Base @@ -8,25 +8,17 @@ import Base newtype AbsoluteCommand = AbsoluteCommand String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -absoluteCommand :: String -> Action String +-- | Fetches the absolute FilePath to a given FilePath from the +-- Oracle. +absoluteCommand :: FilePath -> Action FilePath absoluteCommand = askOracle . AbsoluteCommand -- | Lookup a @command@ in @PATH@ environment. -lookupInPath :: FilePath -> Action FilePath -lookupInPath c +lookupInPathOracle :: FilePath -> Action FilePath +lookupInPathOracle c | c /= takeFileName c = return c | otherwise = absoluteCommand c --- | Split function. Splits a string @s@ into chunks --- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 -wordsWhen :: (Char -> Bool) -> String -> [String] -wordsWhen p s = - case dropWhile p s of - "" -> [] - s' -> w : wordsWhen p s'' - where (w, s'') = break p s' - - absoluteCommandOracle :: Rules () absoluteCommandOracle = do o <- newCache $ \c -> do From git at git.haskell.org Thu Oct 26 23:42:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable profiling and dynamic ways temporarily. (f4fb52d) Message-ID: <20171026234234.0B1C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4fb52d17a91d97b37ac5352beb32153a8345f45/ghc >--------------------------------------------------------------- commit f4fb52d17a91d97b37ac5352beb32153a8345f45 Author: Andrey Mokhov Date: Sun Dec 20 04:06:07 2015 +0000 Disable profiling and dynamic ways temporarily. >--------------------------------------------------------------- f4fb52d17a91d97b37ac5352beb32153a8345f45 src/Settings/User.hs | 3 ++- src/Settings/Ways.hs | 3 +++ 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 5159bce..0dffbfd 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -22,8 +22,9 @@ userKnownPackages :: [Package] userKnownPackages = [] -- Control which ways libraries and rts are built +-- TODO: skip profiling for speed, skip dynamic since it's currently broken userLibWays :: Ways -userLibWays = mempty +userLibWays = remove [profiling, dynamic] userRtsWays :: Ways userRtsWays = mempty diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index ad42cea..7788242 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -4,6 +4,9 @@ import Expression import Predicates import Settings.User +-- TODO: use a single expression Ways parameterised by package instead of +-- expressions libWays and rtsWays + -- Combining default ways with user modifications getLibWays :: Expr [Way] getLibWays = fromDiffExpr $ defaultLibWays <> userLibWays From git at git.haskell.org Thu Oct 26 23:42:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Renames absoluteCommand to lookupInPath (6f88557) Message-ID: <20171026234235.34CD13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6f88557b1fa263bf22f698ec3384a0ab37ed3447/ghc >--------------------------------------------------------------- commit 6f88557b1fa263bf22f698ec3384a0ab37ed3447 Author: Moritz Angermann Date: Thu Jan 7 20:37:59 2016 +0800 Renames absoluteCommand to lookupInPath >--------------------------------------------------------------- 6f88557b1fa263bf22f698ec3384a0ab37ed3447 shaking-up-ghc.cabal | 2 +- src/Builder.hs | 2 +- src/Oracles.hs | 4 ++-- .../{AbsoluteCommand.hs => LookupInPath.hs} | 22 +++++++++++----------- src/Rules/Oracles.hs | 16 ++++++++-------- 5 files changed, 23 insertions(+), 23 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 96efe57..c680b85 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -22,12 +22,12 @@ executable ghc-shake , Expression , GHC , Oracles - , Oracles.AbsoluteCommand , Oracles.ArgsHash , Oracles.Config , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies + , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData , Oracles.PackageDeps diff --git a/src/Builder.hs b/src/Builder.hs index 743c956..0613452 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -98,7 +98,7 @@ builderPath builder = do case (path, windows) of ("", _) -> return path (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) - (p, False) -> lookupInPathOracle (p -<.> exe) + (p, False) -> lookupInPath (p -<.> exe) getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles.hs b/src/Oracles.hs index 07e92f2..564c7bb 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,19 +1,19 @@ module Oracles ( - module Oracles.AbsoluteCommand, module Oracles.Config, module Oracles.Config.Flag, module Oracles.Config.Setting, module Oracles.Dependencies, + module Oracles.LookupInPath, module Oracles.PackageData, module Oracles.PackageDeps, module Oracles.WindowsRoot ) where -import Oracles.AbsoluteCommand import Oracles.Config import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Dependencies +import Oracles.LookupInPath import Oracles.PackageData import Oracles.PackageDeps import Oracles.WindowsRoot diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/LookupInPath.hs similarity index 61% rename from src/Oracles/AbsoluteCommand.hs rename to src/Oracles/LookupInPath.hs index c60f429..c2a05e2 100644 --- a/src/Oracles/AbsoluteCommand.hs +++ b/src/Oracles/LookupInPath.hs @@ -1,26 +1,26 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} -module Oracles.AbsoluteCommand ( - lookupInPathOracle, absoluteCommandOracle +module Oracles.LookupInPath ( + lookupInPath, lookupInPathOracle ) where import Base -newtype AbsoluteCommand = AbsoluteCommand String +newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- | Fetches the absolute FilePath to a given FilePath from the -- Oracle. -absoluteCommand :: FilePath -> Action FilePath -absoluteCommand = askOracle . AbsoluteCommand +commandPath :: FilePath -> Action FilePath +commandPath = askOracle . LookupInPath -- | Lookup a @command@ in @PATH@ environment. -lookupInPathOracle :: FilePath -> Action FilePath -lookupInPathOracle c +lookupInPath :: FilePath -> Action FilePath +lookupInPath c | c /= takeFileName c = return c - | otherwise = absoluteCommand c + | otherwise = commandPath c -absoluteCommandOracle :: Rules () -absoluteCommandOracle = do +lookupInPathOracle :: Rules () +lookupInPathOracle = do o <- newCache $ \c -> do envPaths <- wordsWhen (== ':') <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths @@ -28,5 +28,5 @@ absoluteCommandOracle = do fullCommand <- head <$> filterM doesFileExist candidates putOracle $ "Found '" ++ c ++ "' at " ++ "'" ++ fullCommand ++ "'" return fullCommand - _ <- addOracle $ \(AbsoluteCommand c) -> o c + _ <- addOracle $ \(LookupInPath c) -> o c return () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index a4d6c70..f44b4ad 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -7,11 +7,11 @@ import Oracles.ModuleFiles oracleRules :: Rules () oracleRules = do - absoluteCommandOracle -- see Oracles.WindowsRoot - argsHashOracle -- see Oracles.ArgsHash - configOracle -- see Oracles.Config - dependenciesOracle -- see Oracles.Dependencies - moduleFilesOracle -- see Oracles.ModuleFiles - packageDataOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - windowsRootOracle -- see Oracles.WindowsRoot + argsHashOracle -- see Oracles.ArgsHash + configOracle -- see Oracles.Config + dependenciesOracle -- see Oracles.Dependencies + lookupInPathOracle -- see Oracles.LookupInPath + moduleFilesOracle -- see Oracles.ModuleFiles + packageDataOracle -- see Oracles.PackageData + packageDepsOracle -- see Oracles.PackageDeps + windowsRootOracle -- see Oracles.WindowsRoot From git at git.haskell.org Thu Oct 26 23:42:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (a66be35) Message-ID: <20171026234237.9C65F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a66be35210083bbc2646b38df3a224a77f37dbf1/ghc >--------------------------------------------------------------- commit a66be35210083bbc2646b38df3a224a77f37dbf1 Author: Andrey Mokhov Date: Sun Dec 20 04:09:14 2015 +0000 Clean up. >--------------------------------------------------------------- a66be35210083bbc2646b38df3a224a77f37dbf1 src/Rules/Dependencies.hs | 1 - src/Settings/Builders/GhcCabal.hs | 18 +++++++++--------- 2 files changed, 9 insertions(+), 10 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 1def1ac..996d927 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -24,7 +24,6 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = hDepFile %> \file -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) $ need [platformH] - putBuild $ "srcs = " ++ show srcs need srcs if srcs == [] then writeFileChanged file "" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 01b061e..151cd5f 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -40,12 +40,12 @@ ghcCabalHsColourArgs = builder GhcCabalHsColour ? do -- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do - ways <- getWays - ghci <- lift ghcWithInterpreter + ways <- getWays + withGhci <- lift ghcWithInterpreter append [ if vanilla `elem` ways then "--enable-library-vanilla" else "--disable-library-vanilla" - , if vanilla `elem` ways && ghci && not dynamicGhcPrograms + , if vanilla `elem` ways && withGhci && not dynamicGhcPrograms then "--enable-library-for-ghci" else "--disable-library-for-ghci" , if profiling `elem` ways @@ -224,12 +224,12 @@ needDll0 stage pkg = do -- * otherwise, we must collapse it into one space-separated string. dll0Args :: Args dll0Args = do - stage <- getStage - pkg <- getPackage - dll0 <- lift $ needDll0 stage pkg - ghci <- lift ghcWithInterpreter - arg . unwords . concat $ [ modules | dll0 ] - ++ [ ghciModules | dll0 && ghci ] -- see #9552 + stage <- getStage + pkg <- getPackage + dll0 <- lift $ needDll0 stage pkg + withGhci <- lift ghcWithInterpreter + arg . unwords . concat $ [ modules | dll0 ] + ++ [ ghciModules | dll0 && withGhci ] -- see #9552 where modules = [ "Annotations" , "ApiAnnotation" From git at git.haskell.org Thu Oct 26 23:42:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Makes wordsWhen more generic. (5ccd03c) Message-ID: <20171026234238.B21DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ccd03cac69896ef8ff2df7a8601aa1baa110c98/ghc >--------------------------------------------------------------- commit 5ccd03cac69896ef8ff2df7a8601aa1baa110c98 Author: Moritz Angermann Date: Thu Jan 7 20:38:11 2016 +0800 Makes wordsWhen more generic. >--------------------------------------------------------------- 5ccd03cac69896ef8ff2df7a8601aa1baa110c98 src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 8830a7c..86ddbf5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -241,9 +241,9 @@ removeDirectoryIfExists d = -- | Split function. Splits a string @s@ into chunks -- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 -wordsWhen :: (Char -> Bool) -> String -> [String] +wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] wordsWhen p s = case dropWhile p s of - "" -> [] + [] -> [] s' -> w : wordsWhen p s'' where (w, s'') = break p s' From git at git.haskell.org Thu Oct 26 23:42:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add matchPackageNames to match packages and package names. (341f711) Message-ID: <20171026234241.03CFF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/341f711761e2ec9680613e81ad65335e61713f08/ghc >--------------------------------------------------------------- commit 341f711761e2ec9680613e81ad65335e61713f08 Author: Andrey Mokhov Date: Sun Dec 20 04:11:35 2015 +0000 Add matchPackageNames to match packages and package names. >--------------------------------------------------------------- 341f711761e2ec9680613e81ad65335e61713f08 src/Package.hs | 8 +++++++- src/Rules/Data.hs | 3 +-- src/Settings/Packages.hs | 7 ++++--- 3 files changed, 12 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index f64daee..8415bf1 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,6 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} module Package ( - Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility + Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility, + matchPackageNames ) where import Base @@ -45,6 +46,11 @@ instance Eq Package where instance Ord Package where compare = compare `on` pkgName +-- Given a sorted list of packages and a sorted list of package names, returns +-- packages whose names appear in the list of names +matchPackageNames :: [Package] -> [PackageName] -> [Package] +matchPackageNames = intersectOrd (\pkg name -> compare (pkgName pkg) name) + -- Instances for storing in the Shake database instance Binary Package instance Hashable Package where diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 95ac426..b6925d0 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -31,8 +31,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- We configure packages in the order of their dependencies deps <- packageDeps pkg pkgs <- interpretPartial target getPackages - let cmp p name = compare (pkgName p) name - depPkgs = intersectOrd cmp (sort pkgs) deps + let depPkgs = matchPackageNames (sort pkgs) deps need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] need [cabalFile] diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 718b8de..df52715 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -18,7 +18,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ ghcBoot, binary, cabal, compiler, ghc, ghcCabal, ghcPkg + [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] , stage0 ? append [deriveConstants, genapply, genprimopcode, hp2ps] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] @@ -41,9 +41,10 @@ packagesStage2 = mconcat [ append [ghcTags] , buildHaddock ? append [haddock] ] +-- TODO: switch to Set Package as the order of packages should not matter? knownPackages :: [Package] -knownPackages = defaultKnownPackages ++ userKnownPackages +knownPackages = sort $ defaultKnownPackages ++ userKnownPackages --- Note: this is slow but we keep it simple as there not too many packages (30) +-- Note: this is slow but we keep it simple as there are just ~50 packages findKnownPackage :: PackageName -> Maybe Package findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Thu Oct 26 23:42:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build touchy, fix #125. (fee02d9) Message-ID: <20171026234242.339BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3/ghc >--------------------------------------------------------------- commit fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3 Author: Andrey Mokhov Date: Thu Jan 7 12:59:47 2016 +0000 Build touchy, fix #125. >--------------------------------------------------------------- fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3 src/GHC.hs | 14 +++++++++----- src/Rules/Data.hs | 8 ++++++++ src/Settings/Args.hs | 4 +++- src/Settings/Packages.hs | 3 ++- src/Settings/Packages/{Hp2ps.hs => Touchy.hs} | 8 ++++---- 5 files changed, 26 insertions(+), 11 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index d4d5511..6e3a477 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -6,7 +6,7 @@ module GHC ( haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - transformers, unix, win32, xhtml, + touchy, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -28,7 +28,7 @@ defaultKnownPackages = , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time - , transformers, unix, win32, xhtml ] + , touchy, transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) array, base, binary, bytestring, cabal, compiler, containers, compareSizes, @@ -37,7 +37,7 @@ array, base, binary, bytestring, cabal, compiler, containers, compareSizes, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - transformers, unix, win32, xhtml :: Package + touchy, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -83,6 +83,7 @@ stm = library "stm" templateHaskell = library "template-haskell" terminfo = library "terminfo" time = library "time" +touchy = utility "touchy" transformers = library "transformers" unix = library "unix" win32 = library "Win32" @@ -92,7 +93,7 @@ xhtml = library "xhtml" -- TODO: The following utils are not included into the build system because -- they seem to be unused or unrelated to the build process: checkUniques, -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, --- lndir, mkdirhier, testremove, touchy, vagrant +-- lndir, mkdirhier, testremove, vagrant -- GHC build results will be placed into target directories with the following -- typical structure: @@ -102,7 +103,7 @@ xhtml = library "xhtml" defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage _ = stageString stage --- TODO: simplify +-- TODO: simplify, add programInplaceLibPath -- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg @@ -110,6 +111,9 @@ defaultProgramPath stage pkg | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing + | pkg == touchy = case stage of + Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe + _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index ee15c19..46072ce 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -67,6 +67,14 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." + when (pkg == touchy) $ dataFile %> \mk -> do + let prefix = "utils_touchy_" ++ stageString stage ++ "_" + contents = unlines $ map (prefix++) + [ "PROGNAME = touchy" + , "C_SRCS = touchy.c" ] + writeFileChanged mk contents + putSuccess $ "| Successfully generated '" ++ mk ++ "'." + -- Bootstrapping `ghcCabal`: although `ghcCabal` is a proper cabal -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index fb121ed..f2b30fa 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -30,6 +30,7 @@ import Settings.Packages.IntegerGmp import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc +import Settings.Packages.Touchy import Settings.User getArgs :: Expr [String] @@ -75,4 +76,5 @@ defaultPackageArgs = mconcat , integerGmpPackageArgs , iservBinPackageArgs , rtsPackageArgs - , runGhcPackageArgs ] + , runGhcPackageArgs + , touchyPackageArgs ] diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index dba4054..f80f0d0 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -24,7 +24,8 @@ packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] + , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode + , hp2ps, touchy ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] packagesStage1 :: Packages diff --git a/src/Settings/Packages/Hp2ps.hs b/src/Settings/Packages/Touchy.hs similarity index 72% copy from src/Settings/Packages/Hp2ps.hs copy to src/Settings/Packages/Touchy.hs index 26518c6..8345449 100644 --- a/src/Settings/Packages/Hp2ps.hs +++ b/src/Settings/Packages/Touchy.hs @@ -1,13 +1,13 @@ -module Settings.Packages.Hp2ps (hp2psPackageArgs) where +module Settings.Packages.Touchy (touchyPackageArgs) where import Base import Expression -import GHC (hp2ps) +import GHC (touchy) import Predicates (builderGhc, package) import Settings -hp2psPackageArgs :: Args -hp2psPackageArgs = package hp2ps ? do +touchyPackageArgs :: Args +touchyPackageArgs = package touchy ? do path <- getTargetPath let cabalMacros = path -/- "build/autogen/cabal_macros.h" mconcat [ builderGhc ? From git at git.haskell.org Thu Oct 26 23:42:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix boot package constraints. (3ee9ae2) Message-ID: <20171026234244.65BB03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ee9ae25495416fa212741f062e56016c7c573c4/ghc >--------------------------------------------------------------- commit 3ee9ae25495416fa212741f062e56016c7c573c4 Author: Andrey Mokhov Date: Sun Dec 20 04:12:21 2015 +0000 Fix boot package constraints. >--------------------------------------------------------------- 3ee9ae25495416fa212741f062e56016c7c573c4 src/Rules/Cabal.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 7ccb1b8..d8e557b 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,11 +1,12 @@ module Rules.Cabal (cabalRules) where -import Expression import Data.Version import Distribution.Package hiding (Package) import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Verbosity +import Expression +import GHC import Package hiding (library) import Settings @@ -13,7 +14,8 @@ cabalRules :: Rules () cabalRules = do -- Cache boot package constraints (to be used in cabalArgs) bootPackageConstraints %> \out -> do - pkgs <- interpretWithStage Stage0 getPackages + bootPkgs <- interpretWithStage Stage0 getPackages + let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg From git at git.haskell.org Thu Oct 26 23:42:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Download ghc-tarballs manually. (79a0bf3) Message-ID: <20171026234245.A09C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79a0bf31e51d12dbc6209b4ea5c0492530667c4e/ghc >--------------------------------------------------------------- commit 79a0bf31e51d12dbc6209b4ea5c0492530667c4e Author: Andrey Mokhov Date: Thu Jan 7 13:11:16 2016 +0000 Download ghc-tarballs manually. See #110. [skip ci] >--------------------------------------------------------------- 79a0bf31e51d12dbc6209b4ea5c0492530667c4e .appveyor.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f74c459..6821abf 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -11,8 +11,9 @@ install: - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - bash -lc "cd /home/ghc && ./mk/get-win32-tarballs.sh download x86_64" build_script: - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && echo \"\" | ./configure" - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:42:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix broken parallel build: track dependencies due to -package-id flags. (361c3c2) Message-ID: <20171026234247.D47FC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/361c3c2b250bd016ec16494b6f89b4971241e41e/ghc >--------------------------------------------------------------- commit 361c3c2b250bd016ec16494b6f89b4971241e41e Author: Andrey Mokhov Date: Sun Dec 20 04:13:38 2015 +0000 Fix broken parallel build: track dependencies due to -package-id flags. >--------------------------------------------------------------- 361c3c2b250bd016ec16494b6f89b4971241e41e src/Rules.hs | 24 ++---------------------- src/Rules/Program.hs | 26 +++++++++++++++++++++++--- src/Settings/TargetDirectory.hs | 17 ++++++++++++++++- 3 files changed, 41 insertions(+), 26 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 90769c1..505b8a5 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,11 +1,9 @@ module Rules (generateTargets, packageRules) where import Expression -import Oracles import Rules.Package import Rules.Resources import Settings -import Settings.Builders.GhcCabal -- generateTargets needs top-level build targets generateTargets :: Rules () @@ -14,29 +12,11 @@ generateTargets = action $ do pkgs <- interpretWithStage stage getPackages let (libPkgs, programPkgs) = partition isLibrary pkgs libTargets <- fmap concat . forM libPkgs $ \pkg -> do - let target = PartialTarget stage pkg - buildPath = targetPath stage pkg -/- "build" - compId <- interpretPartial target $ getPkgData ComponentId - needGhciLib <- interpretPartial target $ getPkgData BuildGhciLib + let target = PartialTarget stage pkg needHaddock <- interpretPartial target buildHaddock - ways <- interpretPartial target getWays - let ghciLib = buildPath -/- "HS" ++ compId <.> "o" - haddock = pkgHaddockFile pkg - libs <- fmap concat . forM ways $ \way -> do - extension <- libsuf way - let name = buildPath -/- "libHS" ++ compId - dll0 <- needDll0 stage pkg - return $ [ name <.> extension ] - ++ [ name ++ "-0" <.> extension | dll0 ] - - return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] - ++ [ haddock | needHaddock && stage == Stage1 ] - ++ libs - + return $ [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] let programTargets = map (fromJust . programPath stage) programPkgs - return $ libTargets ++ programTargets - need $ reverse targets -- TODO: use stage 2 compiler for building stage 2 packages (instead of stage 1) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index afe2738..8e3ec77 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -1,20 +1,26 @@ module Rules.Program (buildProgram) where import Expression hiding (splitPath) -import GHC +import GHC (hsc2hs, haddock) import Oracles import Rules.Actions import Rules.Library import Rules.Resources import Settings +import Settings.Builders.GhcCabal -- TODO: Get rid of the Paths_hsc2hs.o hack. +-- TODO: Do we need to consider other ways when building programs? buildProgram :: Resources -> PartialTarget -> Rules () buildProgram _ target @ (PartialTarget stage pkg) = do let path = targetPath stage pkg buildPath = path -/- "build" program = programPath stage pkg + -- return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] + -- ++ [ haddock | needHaddock && stage == Stage1 ] + -- ++ libs + (\f -> program == Just f) ?> \bin -> do cSrcs <- cSources target -- TODO: remove code duplication (Library.hs) hSrcs <- hSources target @@ -23,8 +29,22 @@ buildProgram _ target @ (PartialTarget stage pkg) = do ++ [ buildPath -/- "Paths_hsc2hs.o" | pkg == hsc2hs ] ++ [ buildPath -/- "Paths_haddock.o" | pkg == haddock ] objs = cObjs ++ hObjs - putBuild $ "objs = " ++ show objs - need objs + pkgs <- interpretPartial target getPackages + ways <- interpretPartial target getWays + depNames <- interpretPartial target $ getPkgDataList DepNames + ghciFlag <- interpretPartial target $ getPkgData BuildGhciLib + let deps = matchPackageNames (sort pkgs) (sort depNames) + ghci = ghciFlag == "YES" && stage == Stage1 + libs <- fmap concat . forM deps $ \dep -> do + let depTarget = PartialTarget stage dep + compId <- interpretPartial depTarget $ getPkgData ComponentId + libFiles <- fmap concat . forM ways $ \way -> do + libFile <- pkgLibraryFile stage dep compId way + lib0File <- pkgLibraryFile stage dep (compId ++ "-0") way + dll0 <- needDll0 stage dep + return $ [ libFile ] ++ [ lib0File | dll0 ] + return $ libFiles ++ [ pkgGhciLibraryFile stage dep compId | ghci ] + need $ objs ++ libs build $ fullTargetWithWay target (Ghc stage) vanilla objs [bin] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built program '" diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index b84d03d..6bcec88 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,5 +1,5 @@ module Settings.TargetDirectory ( - targetDirectory, targetPath, pkgHaddockFile + targetDirectory, targetPath, pkgHaddockFile, pkgLibraryFile, pkgGhciLibraryFile ) where import Expression @@ -20,3 +20,18 @@ targetPath stage pkg = pkgPath pkg -/- targetDirectory stage pkg pkgHaddockFile :: Package -> FilePath pkgHaddockFile pkg @ (Package name _) = targetPath Stage1 pkg -/- "doc/html" -/- name -/- name <.> "haddock" + +-- Relative path to a package library file, e.g.: +-- "libraries/array/dist-install/build/libHSarray-0.5.1.0.a" +-- TODO: remove code duplication for computing buildPath +pkgLibraryFile :: Stage -> Package -> String -> Way -> Action FilePath +pkgLibraryFile stage pkg componentId way = do + extension <- libsuf way + let buildPath = targetPath stage pkg -/- "build" + return $ buildPath -/- "libHS" ++ componentId <.> extension + +-- Relative path to a package ghci library file, e.g.: +-- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" +pkgGhciLibraryFile :: Stage -> Package -> String -> FilePath +pkgGhciLibraryFile stage pkg componentId = + targetPath stage pkg -/- "build" -/- "HS" ++ componentId <.> "o" From git at git.haskell.org Thu Oct 26 23:42:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #123 from angerman/feature/fix-clang (4c75d3f) Message-ID: <20171026234249.1939D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4c75d3ff0040645fe7107d244ce64b88dbf7010b/ghc >--------------------------------------------------------------- commit 4c75d3ff0040645fe7107d244ce64b88dbf7010b Merge: 79a0bf3 5ccd03c Author: Andrey Mokhov Date: Thu Jan 7 13:14:07 2016 +0000 Merge pull request #123 from angerman/feature/fix-clang Feature/fix clang >--------------------------------------------------------------- 4c75d3ff0040645fe7107d244ce64b88dbf7010b .travis.yml | 3 +-- README.md | 3 --- shaking-up-ghc.cabal | 1 + src/Base.hs | 11 ++++++++++- src/Builder.hs | 6 +++++- src/Oracles.hs | 2 ++ src/Oracles/LookupInPath.hs | 32 ++++++++++++++++++++++++++++++++ src/Rules/Oracles.hs | 1 + 8 files changed, 52 insertions(+), 7 deletions(-) From git at git.haskell.org Thu Oct 26 23:42:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix absolute paths starting with /c/ on Windows. (30d3d63) Message-ID: <20171026234251.6783F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30d3d63bf7423e7da637981810dd62261868d7d2/ghc >--------------------------------------------------------------- commit 30d3d63bf7423e7da637981810dd62261868d7d2 Author: Andrey Mokhov Date: Sun Dec 20 15:18:44 2015 +0000 Fix absolute paths starting with /c/ on Windows. >--------------------------------------------------------------- 30d3d63bf7423e7da637981810dd62261868d7d2 src/Builder.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 007dae3..f15054d 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -95,16 +95,22 @@ needBuilder laxDependencies builder = do GhcM _ -> True _ -> False --- On Windows: if the path starts with "/", prepend it with the correct path to --- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". +-- TODO: this is fragile, e.g. we currently only handle C: drive +-- On Windows: +-- * if the path starts with "/c/" change the prefix to "C:/" +-- * otherwise, if the path starts with "/", prepend it with the correct path +-- to the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe" fixAbsolutePathOnWindows :: FilePath -> Action FilePath fixAbsolutePathOnWindows path = do windows <- windowsHost -- Note, below is different from FilePath.isAbsolute: if (windows && "/" `isPrefixOf` path) then do - root <- windowsRoot - return . unifyPath $ root ++ drop 1 path + if ("/c/" `isPrefixOf` path) + then return $ "C:" ++ drop 2 path + else do + root <- windowsRoot + return . unifyPath $ root ++ drop 1 path else return path From git at git.haskell.org Thu Oct 26 23:42:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build touchy only on Windows, see #125. (bcb7894) Message-ID: <20171026234252.958143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bcb7894c282280861014f8f6fd0bb6bb3c0f4a02/ghc >--------------------------------------------------------------- commit bcb7894c282280861014f8f6fd0bb6bb3c0f4a02 Author: Andrey Mokhov Date: Thu Jan 7 13:35:09 2016 +0000 Build touchy only on Windows, see #125. >--------------------------------------------------------------- bcb7894c282280861014f8f6fd0bb6bb3c0f4a02 src/Settings/Packages.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index f80f0d0..3f4f661 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -24,8 +24,8 @@ packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode - , hp2ps, touchy ] + , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] + , stage0 ? windowsHost ? append [touchy] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] packagesStage1 :: Packages From git at git.haskell.org Thu Oct 26 23:42:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add pkgDataFile to look up the path to package-data.mk of a particular stage/package combination. (304b099) Message-ID: <20171026234254.D43363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/304b0999ea6282dc3a86e2923bb361a889c5acff/ghc >--------------------------------------------------------------- commit 304b0999ea6282dc3a86e2923bb361a889c5acff Author: Andrey Mokhov Date: Sun Dec 20 18:30:24 2015 +0000 Add pkgDataFile to look up the path to package-data.mk of a particular stage/package combination. >--------------------------------------------------------------- 304b0999ea6282dc3a86e2923bb361a889c5acff src/Rules/Data.hs | 2 +- src/Settings/TargetDirectory.hs | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index b6925d0..b68a1f6 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -32,7 +32,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] + need $ map (pkgDataFile stage) depPkgs need [cabalFile] buildWithResources [(ghcCabal rs, 1)] $ diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 6bcec88..286670b 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,5 +1,6 @@ module Settings.TargetDirectory ( - targetDirectory, targetPath, pkgHaddockFile, pkgLibraryFile, pkgGhciLibraryFile + targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, + pkgGhciLibraryFile ) where import Expression @@ -15,6 +16,9 @@ targetDirectory = userTargetDirectory targetPath :: Stage -> Package -> FilePath targetPath stage pkg = pkgPath pkg -/- targetDirectory stage pkg +pkgDataFile :: Stage -> Package -> FilePath +pkgDataFile stage pkg = targetPath stage pkg -/- "package-data.mk" + -- Relative path to a package haddock file, e.g.: -- "libraries/array/dist-install/doc/html/array/array.haddock" pkgHaddockFile :: Package -> FilePath From git at git.haskell.org Thu Oct 26 23:42:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (53784f5) Message-ID: <20171026234256.1B6F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/53784f526f5ee88136966f5f9c8328459334436b/ghc >--------------------------------------------------------------- commit 53784f526f5ee88136966f5f9c8328459334436b Author: Moritz Angermann Date: Thu Jan 7 21:37:46 2016 +0800 Update README.md - Trying to unify Linux / OS X / Windows build steps. - Added note about `src/Settings/User.hs`. [skip ci] >--------------------------------------------------------------- 53784f526f5ee88136966f5f9c8328459334436b README.md | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) diff --git a/README.md b/README.md index 9f9de91..6a89dc6 100644 --- a/README.md +++ b/README.md @@ -23,36 +23,30 @@ identical to those for the `make` build system. This means that you don't need to adjust anything if you are already familiar with building ghc using the `make` build system. -### Linux / Mac OS X +### Getting the source and configuring GHC ```bash -git clone git://git.haskell.org/ghc +git clone --recursive git://git.haskell.org/ghc.git cd ghc -git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot -./configure +./configure # on linux / os x +./configure --enable-tarballs-autodownload # on windows ``` -Now you have a couple of options: - -- `./shake-build/build.sh` to run the script directly. You'll need to have - `shake` installed globally. -- `./shake-build/build.cabal.sh` to install the build system in a Cabal sandbox - and then run it. +### Configuring the build process +`ghc` uses `mk/build.mk` to configure the build process. `shaking-up-ghc` +uses `src/Settings/User.hs` for build specification. - -### Windows +### Building GHC using `shaking-up-ghc` ```bash -git clone --recursive git://git.haskell.org/ghc.git -cd ghc -git clone git://github.com/snowleopard/shaking-up-ghc shake-build -./boot -./configure --enable-tarballs-autodownload -shake-build/build.bat +./shake-build/build.sh # linux / os x: to run the script directly. You'll need to have `shake` installed globally. +./shake-build/build.cabal.sh # linux / os x: OR to install the build system in a Cabal sandbox and then run it. +shake-build/build.bat # windows ``` + Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build From git at git.haskell.org Thu Oct 26 23:42:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add verboseCommands predicate to show executed commands in full when needed. (f48da18) Message-ID: <20171026234258.5035D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f48da1844187e9dab91be2038d0675b6d1eb90b8/ghc >--------------------------------------------------------------- commit f48da1844187e9dab91be2038d0675b6d1eb90b8 Author: Andrey Mokhov Date: Sun Dec 20 18:41:44 2015 +0000 Add verboseCommands predicate to show executed commands in full when needed. >--------------------------------------------------------------- f48da1844187e9dab91be2038d0675b6d1eb90b8 src/Rules/Actions.hs | 11 +++++++---- src/Settings/User.hs | 9 ++++++++- 2 files changed, 15 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index cdc2e17..805c771 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -16,13 +16,16 @@ buildWithResources rs target = do needBuilder laxDependencies builder path <- builderPath builder argList <- interpret target getArgs + verbose <- interpret target verboseCommands + let quitelyUnlessVerbose = if verbose then withVerbosity Loud else quietly -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do - putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList - putBuild $ "\\--------" - quietly $ case builder of + unless verbose $ do + putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" + mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList + putBuild $ "\\--------" + quitelyUnlessVerbose $ case builder of Ar -> arCmd path argList HsCpp -> do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 0dffbfd..4c7a5f4 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -2,7 +2,8 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile + ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, + verboseCommands ) where import Expression @@ -81,3 +82,9 @@ buildHaddock = return True buildSystemConfigFile :: Bool buildSystemConfigFile = False + +-- Set to True to print full command lines during the build process. Note, this +-- is a Predicate, hence you can enable verbose output for a chosen package +-- only, e.g.: verboseCommands = package ghcPrim +verboseCommands :: Predicate +verboseCommands = return False From git at git.haskell.org Thu Oct 26 23:42:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:42:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (fff8d58) Message-ID: <20171026234259.8F7923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fff8d58cbbf23090752b897768bf4eac8af5f819/ghc >--------------------------------------------------------------- commit fff8d58cbbf23090752b897768bf4eac8af5f819 Author: Moritz Angermann Date: Thu Jan 7 21:48:28 2016 +0800 Update README.md Drop `shake` requirement, as it applies to windows as well and is not exhaustive. [skip ci] >--------------------------------------------------------------- fff8d58cbbf23090752b897768bf4eac8af5f819 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 6a89dc6..2259c0b 100644 --- a/README.md +++ b/README.md @@ -42,7 +42,7 @@ uses `src/Settings/User.hs` for build specification. ### Building GHC using `shaking-up-ghc` ```bash -./shake-build/build.sh # linux / os x: to run the script directly. You'll need to have `shake` installed globally. +./shake-build/build.sh # linux / os x: to run the script directly. ./shake-build/build.cabal.sh # linux / os x: OR to install the build system in a Cabal sandbox and then run it. shake-build/build.bat # windows ``` From git at git.haskell.org Thu Oct 26 23:43:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: README: Add basic instructions for Linux (5211197) Message-ID: <20171026234301.B60CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/52111971658afeafdcd3e3f13fecd29e672549e8/ghc >--------------------------------------------------------------- commit 52111971658afeafdcd3e3f13fecd29e672549e8 Author: Ben Gamari Date: Sun Dec 20 14:04:05 2015 +0100 README: Add basic instructions for Linux >--------------------------------------------------------------- 52111971658afeafdcd3e3f13fecd29e672549e8 README.md | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/README.md b/README.md index 05f3352..63673e3 100644 --- a/README.md +++ b/README.md @@ -4,3 +4,18 @@ Shaking up GHC As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). This is supposed to go into the `shake-build` directory of the GHC source tree. + +Trying it +--------- + +On Linux, +``` +$ git clone git://git.haskell.org/ghc +$ cd ghc +$ git submodule update --init +$ git clone git://github.com/snowleopard/shaking-up-ghc shake-build +$ ./boot +$ ./configure +$ make inplace/bin/ghc-cabal # This needs to be fixed +$ shake-build/build.sh +``` From git at git.haskell.org Thu Oct 26 23:43:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #129 from snowleopard/angerman-patch-2 (6df7616) Message-ID: <20171026234303.038BD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6df7616bbc76029bafaa2493ea8d75e28ca03a60/ghc >--------------------------------------------------------------- commit 6df7616bbc76029bafaa2493ea8d75e28ca03a60 Merge: bcb7894 fff8d58 Author: Andrey Mokhov Date: Thu Jan 7 13:52:04 2016 +0000 Merge pull request #129 from snowleopard/angerman-patch-2 Update README.md [skip ci] >--------------------------------------------------------------- 6df7616bbc76029bafaa2493ea8d75e28ca03a60 README.md | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) From git at git.haskell.org Thu Oct 26 23:43:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Documentation: Move HsColour invocation to after `need` (8e8cc53) Message-ID: <20171026234305.2A32F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e8cc532db9c18fb9b3867b3ceb0e730a93493ff/ghc >--------------------------------------------------------------- commit 8e8cc532db9c18fb9b3867b3ceb0e730a93493ff Author: Ben Gamari Date: Sun Dec 20 16:43:12 2015 +0100 Documentation: Move HsColour invocation to after `need` HsColour also depends upon the sources existing. Fixes #6. >--------------------------------------------------------------- 8e8cc532db9c18fb9b3867b3ceb0e730a93493ff src/Rules/Documentation.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 2ebaa59..495a16c 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -15,14 +15,18 @@ buildPackageDocumentation _ target @ (PartialTarget stage package) = haddockFile = pkgHaddockFile package in when (stage == Stage1) $ do haddockFile %> \file -> do - whenM (specified HsColour) $ do - need [cabalFile] - build $ fullTarget target GhcCabalHsColour [cabalFile] [] srcs <- interpretPartial target getPackageSources deps <- interpretPartial target $ getPkgDataList DepNames let haddocks = [ pkgHaddockFile depPkg | Just depPkg <- map findKnownPackage deps ] need $ srcs ++ haddocks + + -- HsColour sources + whenM (specified HsColour) $ do + need [cabalFile] + build $ fullTarget target GhcCabalHsColour [cabalFile] [] + + -- Build Haddock documentation let haddockWay = if dynamicGhcPrograms then dynamic else vanilla build $ fullTargetWithWay target Haddock haddockWay srcs [file] From git at git.haskell.org Thu Oct 26 23:43:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build only stage1 base library to fit into Travis 50 min limit for OSX. (b67f727) Message-ID: <20171026234306.8EC4B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b67f727b982025b1039994cdb7731fc2a47f2119/ghc >--------------------------------------------------------------- commit b67f727b982025b1039994cdb7731fc2a47f2119 Author: Andrey Mokhov Date: Thu Jan 7 15:43:14 2016 +0000 Build only stage1 base library to fit into Travis 50 min limit for OSX. >--------------------------------------------------------------- b67f727b982025b1039994cdb7731fc2a47f2119 .travis.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 055edd5..4cc0396 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: false matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 + env: CABALVER=1.22 GHCVER=7.10.3 TARGET= addons: apt: packages: @@ -21,6 +21,7 @@ matrix: - cabal update - os: osx + env: TARGET=libraries/base/stage1/build/libHSbase-4.9.0.0.a before_install: - brew update - brew install ghc cabal-install @@ -54,7 +55,7 @@ install: - ( cd ghc && ./configure ) script: - - ./ghc/shake-build/build.sh -j --no-progress + - ./ghc/shake-build/build.sh -j --no-progress $TARGET cache: directories: From git at git.haskell.org Thu Oct 26 23:43:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Actions: Factor out box drawing (9d2868b) Message-ID: <20171026234308.901953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d2868b107cce0af8445ec6ce8471ba1d45e3042/ghc >--------------------------------------------------------------- commit 9d2868b107cce0af8445ec6ce8471ba1d45e3042 Author: Ben Gamari Date: Sun Dec 20 17:21:47 2015 +0100 Actions: Factor out box drawing Also add (currently broken) Unicode support although this is broken by Shake, the console output interface of which is badly broken (see Shake #364) >--------------------------------------------------------------- 9d2868b107cce0af8445ec6ce8471ba1d45e3042 src/Rules/Actions.hs | 25 ++++++++++++++++++++----- 1 file changed, 20 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 805c771..775524a 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -7,6 +7,22 @@ import Settings.Args import Settings.Builders.Ar import qualified Target +insideBox :: [String] -> String +insideBox ls = + unlines $ [begin] ++ map (bar++) ls ++ [end] + where + (begin,bar,end) + | useUnicode = ( "╭──────────" + , "│ " + , "╰──────────" + ) + | otherwise = ( "/----------" + , "| " + , "\\----------" + ) + -- FIXME: See Shake #364. + useUnicode = False + -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last -- built (that is, track changes in the build system). @@ -17,15 +33,14 @@ buildWithResources rs target = do path <- builderPath builder argList <- interpret target getArgs verbose <- interpret target verboseCommands - let quitelyUnlessVerbose = if verbose then withVerbosity Loud else quietly + let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do unless verbose $ do - putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList - putBuild $ "\\--------" - quitelyUnlessVerbose $ case builder of + putBuild $ insideBox $ [ "Running " ++ show builder ++ " with arguments:" ] + ++ map (" "++) (interestingInfo builder argList) + quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList HsCpp -> do From git at git.haskell.org Thu Oct 26 23:43:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create ghc-tarballs folder. (45eefc0) Message-ID: <20171026234310.039063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45eefc07e8d5820ca0640a7ecb398dcb717aa35a/ghc >--------------------------------------------------------------- commit 45eefc07e8d5820ca0640a7ecb398dcb717aa35a Author: Andrey Mokhov Date: Thu Jan 7 16:35:01 2016 +0000 Create ghc-tarballs folder. See #110. [skip ci] >--------------------------------------------------------------- 45eefc07e8d5820ca0640a7ecb398dcb717aa35a .appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.appveyor.yml b/.appveyor.yml index 6821abf..7d5a0f8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -11,6 +11,7 @@ install: - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - bash -lc "mkdir -p /home/ghc/ghc-tarballs" - bash -lc "cd /home/ghc && ./mk/get-win32-tarballs.sh download x86_64" build_script: From git at git.haskell.org Thu Oct 26 23:43:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:10 +0000 (UTC) Subject: [commit: ghc] branch 'wip/nfs-locking' created Message-ID: <20171026234310.26F4C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/nfs-locking Referencing: 1cd7473f8e800a99e95180579480a0e62e98040b From git at git.haskell.org Thu Oct 26 23:43:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix detection of libraries (86ed4e3) Message-ID: <20171026234311.F2A6F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86ed4e32b39b0ab57e64fbd93cccfb8113d162b7/ghc >--------------------------------------------------------------- commit 86ed4e32b39b0ab57e64fbd93cccfb8113d162b7 Author: Ben Gamari Date: Sun Dec 20 20:23:34 2015 +0100 Fix detection of libraries Previously a very fragile heuristic was used. Now we explicitly declare this. Perhaps a better option in the future would be to instead emit this information from `ghc-cabal` and pick it up from `package-data.mk`. Fixes #9. >--------------------------------------------------------------- 86ed4e32b39b0ab57e64fbd93cccfb8113d162b7 src/GHC.hs | 2 +- src/Package.hs | 37 ++++++++++++++++++++++++++----------- src/Rules/Data.hs | 3 ++- src/Settings.hs | 3 ++- src/Settings/TargetDirectory.hs | 2 +- 5 files changed, 32 insertions(+), 15 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0279197..c38af04 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -51,7 +51,7 @@ dllSplit = utility "dll-split" filepath = library "filepath" genapply = utility "genapply" genprimopcode = utility "genprimopcode" -ghc = topLevel "ghc-bin" `setPath` "ghc" +ghc = topLevel "ghc-bin" `setPath` "ghc" `setPkgType` Program ghcBoot = library "ghc-boot" ghcCabal = utility "ghc-cabal" ghci = library "ghci" diff --git a/src/Package.hs b/src/Package.hs index 8415bf1..6273a62 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,23 +1,31 @@ {-# LANGUAGE DeriveGeneric #-} module Package ( - Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility, - matchPackageNames + Package (..), PackageName, PackageType (..), + -- * Queries + pkgCabalFile, + matchPackageNames, + -- * Helpers for constructing 'Package's + setPath, topLevel, library, utility, setPkgType ) where import Base import GHC.Generics (Generic) --- It is helpful to distinguish package names from strings. +-- | It is helpful to distinguish package names from strings. type PackageName = String --- type PackageType = Program | Library +-- | We regard packages as either being libraries or programs. This is +-- bit of a convenient lie as Cabal packages can be both, but it works +-- for now. +data PackageType = Program | Library + deriving Generic --- pkgPath is the path to the source code relative to the root data Package = Package { - pkgName :: PackageName, -- Examples: "ghc", "Cabal" - pkgPath :: FilePath -- "compiler", "libraries/Cabal/Cabal" - -- pkgType :: PackageType -- TopLevel, Library + pkgName :: PackageName, -- ^ Examples: "ghc", "Cabal" + pkgPath :: FilePath, -- ^ pkgPath is the path to the source code relative to the root. + -- e.g. "compiler", "libraries/Cabal/Cabal" + pkgType :: PackageType } deriving Generic @@ -26,17 +34,20 @@ pkgCabalFile :: Package -> FilePath pkgCabalFile pkg = pkgPath pkg -/- pkgName pkg <.> "cabal" topLevel :: PackageName -> Package -topLevel name = Package name name +topLevel name = Package name name Library library :: PackageName -> Package -library name = Package name ("libraries" -/- name) +library name = Package name ("libraries" -/- name) Library utility :: PackageName -> Package -utility name = Package name ("utils" -/- name) +utility name = Package name ("utils" -/- name) Program setPath :: Package -> FilePath -> Package setPath pkg path = pkg { pkgPath = path } +setPkgType :: Package -> PackageType -> Package +setPkgType pkg ty = pkg { pkgType = ty } + instance Show Package where show = pkgName @@ -56,3 +67,7 @@ instance Binary Package instance Hashable Package where hashWithSalt salt = hashWithSalt salt . show instance NFData Package + +instance Binary PackageType +instance Hashable PackageType +instance NFData PackageType diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index b68a1f6..fdbe21d 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -38,7 +38,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do buildWithResources [(ghcCabal rs, 1)] $ fullTarget target GhcCabal [cabalFile] outs - -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg + -- ghc-pkg produces inplace-pkg-config when run on packages with + -- library components only when (isLibrary pkg) . whenM (interpretPartial target registerPackage) . buildWithResources [(ghcPkg rs, 1)] $ diff --git a/src/Settings.hs b/src/Settings.hs index d16c5cd..7a1ab72 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -33,7 +33,8 @@ programPath :: Stage -> Package -> Maybe FilePath programPath = userProgramPath isLibrary :: Package -> Bool -isLibrary pkg = programPath Stage0 pkg == Nothing +isLibrary (Package {pkgType=Library}) = True +isLibrary _ = False -- Find all Haskell source files for the current target. TODO: simplify. getPackageSources :: Expr [FilePath] diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 286670b..a4301f4 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -22,7 +22,7 @@ pkgDataFile stage pkg = targetPath stage pkg -/- "package-data.mk" -- Relative path to a package haddock file, e.g.: -- "libraries/array/dist-install/doc/html/array/array.haddock" pkgHaddockFile :: Package -> FilePath -pkgHaddockFile pkg @ (Package name _) = +pkgHaddockFile pkg @ (Package name _ _) = targetPath Stage1 pkg -/- "doc/html" -/- name -/- name <.> "haddock" -- Relative path to a package library file, e.g.: From git at git.haskell.org Thu Oct 26 23:43:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename replaceIf -> replaceWhen to match wordsWhen, clean up. (f7cd3ae) Message-ID: <20171026234313.C98B23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f7cd3aeef421946ef3f1ff1e9916b19ac8ddf9d4/ghc >--------------------------------------------------------------- commit f7cd3aeef421946ef3f1ff1e9916b19ac8ddf9d4 Author: Andrey Mokhov Date: Thu Jan 7 16:52:25 2016 +0000 Rename replaceIf -> replaceWhen to match wordsWhen, clean up. [skip ci] >--------------------------------------------------------------- f7cd3aeef421946ef3f1ff1e9916b19ac8ddf9d4 src/Base.hs | 51 +++++++++++++++++++++++++-------------------------- 1 file changed, 25 insertions(+), 26 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 86ddbf5..a116892 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -81,14 +81,14 @@ packageConfigurationInitialised stage = -- Utility functions -- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] -replaceEq from = replaceIf (== from) +replaceEq from = replaceWhen (== from) -- | Find and replace all occurrences of path separators in a String with a Char replaceSeparators :: Char -> String -> String -replaceSeparators = replaceIf isPathSeparator +replaceSeparators = replaceWhen isPathSeparator -replaceIf :: (a -> Bool) -> a -> [a] -> [a] -replaceIf p to = map (\from -> if p from then to else from) +replaceWhen :: (a -> Bool) -> a -> [a] -> [a] +replaceWhen p to = map (\from -> if p from then to else from) -- | Find all occurrences of substring 'from' and replace them to 'to' in a -- given string. Not very efficient, but simple and fast enough for our purposes @@ -101,6 +101,27 @@ replace from to = go | from `isPrefixOf` s = to ++ go (skipFrom s) | otherwise = x : go xs +-- | Split a list into chunks in places where the predicate @p@ holds. +-- See: http://stackoverflow.com/a/4981265 +wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] +wordsWhen p list = + case dropWhile p list of + [] -> [] + l -> w : wordsWhen p rest where (w, rest) = break p l + +-- | @chunksOfSize size strings@ splits a given list of strings into chunks not +-- exceeding the given @size at . +chunksOfSize :: Int -> [String] -> [[String]] +chunksOfSize _ [] = [] +chunksOfSize size strings = reverse chunk : chunksOfSize size rest + where + (chunk, rest) = go [] 0 strings + go res _ [] = (res, []) + go res chunkSize (s:ss) = + if newSize > size then (res, s:ss) else go (s:res) newSize ss + where + newSize = chunkSize + length s + -- | Add quotes to a String quote :: String -> String quote s = "\"" ++ s ++ "\"" @@ -133,19 +154,6 @@ a -/- b = unifyPath $ a b infixr 6 -/- --- | @chunksOfSize size strings@ splits a given list of strings into chunks not --- exceeding the given @size at . -chunksOfSize :: Int -> [String] -> [[String]] -chunksOfSize _ [] = [] -chunksOfSize size strings = reverse chunk : chunksOfSize size rest - where - (chunk, rest) = go [] 0 strings - go res _ [] = (res, []) - go res chunkSize (s:ss) = - if newSize > size then (res, s:ss) else go (s:res) newSize ss - where - newSize = chunkSize + length s - -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do @@ -238,12 +246,3 @@ removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f removeDirectoryIfExists :: FilePath -> Action () removeDirectoryIfExists d = liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d - --- | Split function. Splits a string @s@ into chunks --- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 -wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] -wordsWhen p s = - case dropWhile p s of - [] -> [] - s' -> w : wordsWhen p s'' - where (w, s'') = break p s' From git at git.haskell.org Thu Oct 26 23:43:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initial commit (013cf0c) Message-ID: <20171026234313.EEA523A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/013cf0c23c4926b09d6a10c13170d344ed802a01/ghc >--------------------------------------------------------------- commit 013cf0c23c4926b09d6a10c13170d344ed802a01 Author: Andrey Mokhov Date: Tue Dec 23 17:01:44 2014 +0000 Initial commit >--------------------------------------------------------------- 013cf0c23c4926b09d6a10c13170d344ed802a01 README.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README.md b/README.md new file mode 100644 index 0000000..c7c12b3 --- /dev/null +++ b/README.md @@ -0,0 +1,4 @@ +shaking-up-ghc +============== + +Shaking up GHC From git at git.haskell.org Thu Oct 26 23:43:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #8 from bgamari/master (821d9e9) Message-ID: <20171026234315.77A573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/821d9e9c6b81381c1dff2c78755a525f4d3543a1/ghc >--------------------------------------------------------------- commit 821d9e9c6b81381c1dff2c78755a525f4d3543a1 Merge: f48da18 86ed4e3 Author: Andrey Mokhov Date: Sun Dec 20 19:34:47 2015 +0000 Merge pull request #8 from bgamari/master Miscellany >--------------------------------------------------------------- 821d9e9c6b81381c1dff2c78755a525f4d3543a1 README.md | 15 +++++++++++++++ src/GHC.hs | 2 +- src/Package.hs | 37 ++++++++++++++++++++++++++----------- src/Rules/Actions.hs | 25 ++++++++++++++++++++----- src/Rules/Data.hs | 3 ++- src/Rules/Documentation.hs | 10 +++++++--- src/Settings.hs | 3 ++- src/Settings/TargetDirectory.hs | 2 +- 8 files changed, 74 insertions(+), 23 deletions(-) From git at git.haskell.org Thu Oct 26 23:43:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move copyRules to Rules/Generate.hs, add missing generated dependencies. (03b3379) Message-ID: <20171026234317.831303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03b33797d88b27291c6a05f6141fac18be30efc4/ghc >--------------------------------------------------------------- commit 03b33797d88b27291c6a05f6141fac18be30efc4 Author: Andrey Mokhov Date: Thu Jan 7 17:02:35 2016 +0000 Move copyRules to Rules/Generate.hs, add missing generated dependencies. >--------------------------------------------------------------- 03b33797d88b27291c6a05f6141fac18be30efc4 shaking-up-ghc.cabal | 1 - src/Main.hs | 3 +-- src/Rules.hs | 2 +- src/Rules/Copy.hs | 20 -------------------- src/Rules/Generate.hs | 18 ++++++++++++++++-- 5 files changed, 18 insertions(+), 26 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index c680b85..9f2c80c 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -39,7 +39,6 @@ executable ghc-shake , Rules.Cabal , Rules.Compile , Rules.Config - , Rules.Copy , Rules.Data , Rules.Dependencies , Rules.Documentation diff --git a/src/Main.hs b/src/Main.hs index 043e173..07f14ea 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,7 +3,6 @@ import Rules import Rules.Cabal import Rules.Config import Rules.Generate -import Rules.Copy import Rules.Libffi import Rules.IntegerGmp import Rules.Oracles @@ -12,7 +11,7 @@ main :: IO () main = shakeArgs options $ do cabalRules -- see Rules.Cabal configRules -- see Rules.Config - copyRules -- see Rules.Copy + copyRules -- see Rules.Generate generateTargets -- see Rules generateRules -- see Rules.Generate libffiRules -- see Rules.Libffi diff --git a/src/Rules.hs b/src/Rules.hs index 9933225..22c5230 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -3,7 +3,7 @@ module Rules (generateTargets, packageRules) where import Base import Expression import GHC -import Rules.Copy +import Rules.Generate import Rules.Package import Rules.Resources import Settings diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs deleted file mode 100644 index 7454fd9..0000000 --- a/src/Rules/Copy.hs +++ /dev/null @@ -1,20 +0,0 @@ -module Rules.Copy (installTargets, copyRules) where - -import Base -import Expression -import GHC -import Rules.Actions -import Rules.Generate - -installTargets :: [FilePath] -installTargets = [ "inplace/lib/template-hsc.h" - , "inplace/lib/platformConstants" - , "inplace/lib/settings" ] - -copyRules :: Rules () -copyRules = do - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs - "inplace/lib/platformConstants" <~ derivedConstantsPath - "inplace/lib/settings" <~ "." - where - file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8ca7b94..71d88b1 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,7 @@ module Rules.Generate ( generatePackageCode, generateRules, - derivedConstantsPath, generatedDependencies + derivedConstantsPath, generatedDependencies, + installTargets, copyRules ) where import Base @@ -20,6 +21,11 @@ import Rules.Resources (Resources) import Settings import Settings.Builders.DeriveConstants +installTargets :: [FilePath] +installTargets = [ "inplace/lib/template-hsc.h" + , "inplace/lib/platformConstants" + , "inplace/lib/settings" ] + primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -45,7 +51,7 @@ ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> , "autogen/GHC/Prim.hs" ] derivedConstantsDependencies :: [FilePath] -derivedConstantsDependencies = (derivedConstantsPath -/-) <$> +derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) [ "DerivedConstants.h" , "GHCConstantsHaskellType.hs" , "GHCConstantsHaskellWrappers.hs" @@ -150,6 +156,14 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = copyFileChanged (pkgPath pkg -/- "runghc.hs") file putSuccess $ "| Successfully generated '" ++ file ++ "'." +copyRules :: Rules () +copyRules = do + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs + "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." + where + file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file + generateRules :: Rules () generateRules = do "includes/ghcautoconf.h" <~ generateGhcAutoconfH From git at git.haskell.org Thu Oct 26 23:43:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a brief intro to the project. (bd90cd8) Message-ID: <20171026234317.8AACE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd90cd8e6436d20d933c9b27142cc83defcbe267/ghc >--------------------------------------------------------------- commit bd90cd8e6436d20d933c9b27142cc83defcbe267 Author: Andrey Mokhov Date: Tue Dec 23 17:06:08 2014 +0000 Add a brief intro to the project. >--------------------------------------------------------------- bd90cd8e6436d20d933c9b27142cc83defcbe267 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index c7c12b3..7167e9a 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -shaking-up-ghc +Shaking up GHC ============== -Shaking up GHC +As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). From git at git.haskell.org Thu Oct 26 23:43:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rules: Refactor generateTargets (c84445f) Message-ID: <20171026234318.E3E693A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c84445f81aafbe4089d860ae4a3e0c020a38b118/ghc >--------------------------------------------------------------- commit c84445f81aafbe4089d860ae4a3e0c020a38b118 Author: Ben Gamari Date: Sun Dec 20 20:49:29 2015 +0100 Rules: Refactor generateTargets This previously used `fromJust`, which bottomed due to the recent `isLibrary` change. >--------------------------------------------------------------- c84445f81aafbe4089d860ae4a3e0c020a38b118 src/Rules.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 505b8a5..55ff066 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -10,12 +10,12 @@ generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpretWithStage stage getPackages - let (libPkgs, programPkgs) = partition isLibrary pkgs + let libPkgs = filter isLibrary pkgs libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg needHaddock <- interpretPartial target buildHaddock - return $ [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] - let programTargets = map (fromJust . programPath stage) programPkgs + return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] + let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] return $ libTargets ++ programTargets need $ reverse targets From git at git.haskell.org Thu Oct 26 23:43:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddock comments in Predicates.hs (de634da) Message-ID: <20171026234321.446F03A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de634dadaf365799b3e0b8945ec812b2bec37c74/ghc >--------------------------------------------------------------- commit de634dadaf365799b3e0b8945ec812b2bec37c74 Author: David Luposchainsky Date: Wed Jan 6 14:31:37 2016 +0100 Add Haddock comments in Predicates.hs >--------------------------------------------------------------- de634dadaf365799b3e0b8945ec812b2bec37c74 src/Predicates.hs | 23 +++++++++++++++++------ 1 file changed, 17 insertions(+), 6 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index ad63598..b5ce0cb 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -7,49 +7,60 @@ module Predicates ( import Base import Expression --- Basic predicates +-- | Is the build currently in the provided stage? stage :: Stage -> Predicate stage s = fmap (s ==) getStage +-- | Is a particular package being built? package :: Package -> Predicate package p = fmap (p ==) getPackage --- For unstaged builders, e.g. GhcCabal +-- | Is an unstaged builder is being used such as /GhcCabal/? builder :: Builder -> Predicate builder b = fmap (b ==) getBuilder --- For staged builders, e.g. Ghc Stage +-- | Is a certain builder used in the current stage? stagedBuilder :: (Stage -> Builder) -> Predicate -stagedBuilder sb = (builder . sb) =<< getStage +stagedBuilder stageBuilder = do + s <- getStage + builder (stageBuilder s) +-- | Are we building with GCC? builderGcc :: Predicate builderGcc = stagedBuilder Gcc ||^ stagedBuilder GccM +-- | Are we building with GHC? builderGhc :: Predicate builderGhc = stagedBuilder Ghc ||^ stagedBuilder GhcM +-- | Does any of the output files match a given pattern? file :: FilePattern -> Predicate file f = fmap (any (f ?==)) getOutputs +-- | Is the current build 'Way' equal to a certain value? way :: Way -> Predicate way w = fmap (w ==) getWay --- Derived predicates +-- | Is the build currently in stage 0? stage0 :: Predicate stage0 = stage Stage0 +-- | Is the build currently in stage 1? stage1 :: Predicate stage1 = stage Stage1 +-- | Is the build currently in stage 2? stage2 :: Predicate stage2 = stage Stage2 +-- | Is the build /not/ in stage 0 right now? notStage0 :: Predicate notStage0 = notM stage0 +-- | Is a certain package /not/ built right now? notPackage :: Package -> Predicate notPackage = notM . package --- TODO: Actually, we don't register compiler in some circumstances -- fix. +-- | TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate registerPackage = return True From git at git.haskell.org Thu Oct 26 23:43:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add .gitignore. (c5c557a) Message-ID: <20171026234321.43F8B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5c557a4fab012d28c8fb5f2b2aacb9f835ef722/ghc >--------------------------------------------------------------- commit c5c557a4fab012d28c8fb5f2b2aacb9f835ef722 Author: Andrey Mokhov Date: Tue Dec 23 17:12:02 2014 +0000 Add .gitignore. >--------------------------------------------------------------- c5c557a4fab012d28c8fb5f2b2aacb9f835ef722 .gitignore | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.gitignore b/.gitignore new file mode 100644 index 0000000..181ccc0 --- /dev/null +++ b/.gitignore @@ -0,0 +1,4 @@ +*.o +*.hi +_shake/ +_build/ From git at git.haskell.org Thu Oct 26 23:43:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GHC: Set PackageType of iservBin (139d90d) Message-ID: <20171026234322.611893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/139d90d43b6a8fb125ea05136531848cebb96096/ghc >--------------------------------------------------------------- commit 139d90d43b6a8fb125ea05136531848cebb96096 Author: Ben Gamari Date: Sun Dec 20 20:45:05 2015 +0100 GHC: Set PackageType of iservBin >--------------------------------------------------------------- 139d90d43b6a8fb125ea05136531848cebb96096 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index c38af04..29db671 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -68,7 +68,7 @@ hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" integerGmp = library "integer-gmp" integerSimple = library "integer-simple" -iservBin = topLevel "iserv-bin" `setPath` "iserv" +iservBin = topLevel "iserv-bin" `setPath` "iserv" `setPkgType` Program mkUserGuidePart = utility "mkUserGuidePart" parallel = library "parallel" pretty = library "pretty" From git at git.haskell.org Thu Oct 26 23:43:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add shake launcher. (cf7b65b) Message-ID: <20171026234324.B97903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf7b65b5b200048fd0597ee606ccd876848a3b05/ghc >--------------------------------------------------------------- commit cf7b65b5b200048fd0597ee606ccd876848a3b05 Author: Andrey Mokhov Date: Tue Dec 23 17:28:03 2014 +0000 Add shake launcher. >--------------------------------------------------------------- cf7b65b5b200048fd0597ee606ccd876848a3b05 build.bat | 2 ++ 1 file changed, 2 insertions(+) diff --git a/build.bat b/build.bat new file mode 100644 index 0000000..5400131 --- /dev/null +++ b/build.bat @@ -0,0 +1,2 @@ + at mkdir _shake 2> nul + at ghc --make Main.hs -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:43:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make value sources more explicit (921dcce) Message-ID: <20171026234324.BE6943A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/921dcce1ab2e0cc1e6df25df98bb24f134fe0742/ghc >--------------------------------------------------------------- commit 921dcce1ab2e0cc1e6df25df98bb24f134fe0742 Author: David Luposchainsky Date: Tue Jan 5 16:44:06 2016 +0100 Make value sources more explicit [skip ci] Rather than relying on comments, move the documentation into the source, so it's checked by the compiler automatically >--------------------------------------------------------------- 921dcce1ab2e0cc1e6df25df98bb24f134fe0742 src/Main.hs | 40 ++++++++++++++++++++++------------------ 1 file changed, 22 insertions(+), 18 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 07f14ea..bacc8f1 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,24 +1,28 @@ -import Base -import Rules -import Rules.Cabal -import Rules.Config -import Rules.Generate -import Rules.Libffi -import Rules.IntegerGmp -import Rules.Oracles +module Main (main) where + +import qualified Base as B +import qualified Rules as R +import qualified Rules.Cabal as RCabal +import qualified Rules.Config as RConfig +import qualified Rules.Copy as RCopy +import qualified Rules.Generate as RGen +import qualified Rules.IntegerGmp as RInt +import qualified Rules.Libffi as RFfi +import qualified Rules.Oracles as ROracle main :: IO () -main = shakeArgs options $ do - cabalRules -- see Rules.Cabal - configRules -- see Rules.Config - copyRules -- see Rules.Generate - generateTargets -- see Rules - generateRules -- see Rules.Generate - libffiRules -- see Rules.Libffi - integerGmpRules -- see Rules.IntegerGmp - oracleRules -- see Rules.Oracles - packageRules -- see Rules +main = shakeArgs options rules where + rules = mconcat + [ RCabal.cabalRules + , RConfig.configRules + , RCopy.copyRules + , R.generateTargets + , RGen.generateRules + , RFfi.libffiRules + , RInt.integerGmpRules + , ROracle.oracleRules + , R.packageRules ] options = shakeOptions { shakeFiles = shakeFilesPath , shakeProgress = progressSimple From git at git.haskell.org Thu Oct 26 23:43:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #11 from bgamari/master (5c42b58) Message-ID: <20171026234325.CB5543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5c42b582cb8c05741cc5be87dd3ec2f935997f56/ghc >--------------------------------------------------------------- commit 5c42b582cb8c05741cc5be87dd3ec2f935997f56 Merge: 821d9e9 c84445f Author: Andrey Mokhov Date: Sun Dec 20 20:15:12 2015 +0000 Merge pull request #11 from bgamari/master Fix fallout from previous refactoring >--------------------------------------------------------------- 5c42b582cb8c05741cc5be87dd3ec2f935997f56 src/GHC.hs | 2 +- src/Rules.hs | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) From git at git.haskell.org Thu Oct 26 23:43:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add top-level build script. (4139a9c) Message-ID: <20171026234328.1FF303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4139a9c49da73acb26756a6be7bf564286a32cf1/ghc >--------------------------------------------------------------- commit 4139a9c49da73acb26756a6be7bf564286a32cf1 Author: Andrey Mokhov Date: Tue Dec 23 17:42:13 2014 +0000 Add top-level build script. >--------------------------------------------------------------- 4139a9c49da73acb26756a6be7bf564286a32cf1 Main.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/Main.hs b/Main.hs new file mode 100644 index 0000000..abfd3ab --- /dev/null +++ b/Main.hs @@ -0,0 +1,10 @@ +import Base +import Config +import Oracles +import Package + +main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do + oracleRules + autoconfRules + configureRules + packageRules From git at git.haskell.org Thu Oct 26 23:43:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split up definitions in Rules.hs (20381e5) Message-ID: <20171026234328.345293A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20381e58208ca2693f034566e450f5b0b28674b4/ghc >--------------------------------------------------------------- commit 20381e58208ca2693f034566e450f5b0b28674b4 Author: David Luposchainsky Date: Wed Jan 6 14:49:58 2016 +0100 Split up definitions in Rules.hs >--------------------------------------------------------------- 20381e58208ca2693f034566e450f5b0b28674b4 src/Rules.hs | 33 ++++++++++++++++++++------------- 1 file changed, 20 insertions(+), 13 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 22c5230..f8b2810 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,6 +1,8 @@ module Rules (generateTargets, packageRules) where import Base +import Data.Foldable +import Data.Traversable import Expression import GHC import Rules.Generate @@ -8,26 +10,31 @@ import Rules.Package import Rules.Resources import Settings +allStages :: [Stage] +allStages = [Stage0 ..] + -- TODO: not all program targets should be needed explicitly --- | generateTargets needs top-level build targets +-- | 'need' all top-level build targets generateTargets :: Rules () generateTargets = action $ do - targets <- fmap concat . forM [Stage0 ..] $ \stage -> do - pkgs <- interpretWithStage stage getPackages - let libPkgs = filter isLibrary pkgs \\ [rts, libffi] - libTargets <- fmap concat . forM libPkgs $ \pkg -> do - let target = PartialTarget stage pkg - needHaddock <- interpretPartial target buildHaddock - return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] - let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] - return $ libTargets ++ programTargets - + targets <- fmap concat (traverse targetsForStage allStages) rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla need $ targets ++ installTargets ++ [ rtsLib ] +targetsForStage :: Stage -> Action [String] +targetsForStage stage = do + pkgs <- interpretWithStage stage getPackages + let libPkgs = filter isLibrary pkgs \\ [rts, libffi] + libTargets <- fmap concat . for libPkgs $ \pkg -> do + let target = PartialTarget stage pkg + needHaddock <- interpretPartial target buildHaddock + return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] + let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] + return (libTargets ++ programTargets) + packageRules :: Rules () packageRules = do resources <- resourceRules - forM_ [Stage0 ..] $ \stage -> - forM_ knownPackages $ \pkg -> + for allStages $ \stage -> + for_ knownPackages $ \pkg -> buildPackage resources $ PartialTarget stage pkg From git at git.haskell.org Thu Oct 26 23:43:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hide `parallel` from shake (aad2247) Message-ID: <20171026234329.401FB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aad2247ecc85160af1d27f7c4e3bb227a754630f/ghc >--------------------------------------------------------------- commit aad2247ecc85160af1d27f7c4e3bb227a754630f Author: Ben Gamari Date: Sun Dec 20 21:41:07 2015 +0100 Hide `parallel` from shake Shake `master` branch exports a symbol called `parallel` which overlaps with ours. >--------------------------------------------------------------- aad2247ecc85160af1d27f7c4e3bb227a754630f src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 1c72fd8..7edae37 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -38,7 +38,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>)) +import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes import Development.Shake.Config import Development.Shake.FilePath From git at git.haskell.org Thu Oct 26 23:43:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Base.hs (basic datatypes and imports for the build system). (4e03b1c) Message-ID: <20171026234331.8B9613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9/ghc >--------------------------------------------------------------- commit 4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9 Author: Andrey Mokhov Date: Tue Dec 23 17:44:51 2014 +0000 Add Base.hs (basic datatypes and imports for the build system). >--------------------------------------------------------------- 4e03b1c45d2be172e017d3ec5d8dfff5ab8354d9 Base.hs | 45 +++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 45 insertions(+) diff --git a/Base.hs b/Base.hs new file mode 100644 index 0000000..7e130c2 --- /dev/null +++ b/Base.hs @@ -0,0 +1,45 @@ +{-# LANGUAGE FlexibleInstances #-} + +module Base ( + module Development.Shake, + module Development.Shake.FilePath, + module Control.Applicative, + module Data.Monoid, + Stage (..), + Args, arg, Condition, + joinArgs, joinArgsWithSpaces, + filterOut, + ) where + +import Development.Shake hiding ((*>)) +import Development.Shake.FilePath +import Control.Applicative +import Data.Monoid +import Data.List + +data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) + +type Args = Action [String] + +type Condition = Action Bool + +instance Monoid a => Monoid (Action a) where + mempty = return mempty + mappend p q = mappend <$> p <*> q + +arg :: [String] -> Args +arg = return + +intercalateArgs :: String -> Args -> Args +intercalateArgs s args = do + as <- args + return [intercalate s as] + +joinArgsWithSpaces :: Args -> Args +joinArgsWithSpaces = intercalateArgs " " + +joinArgs :: Args -> Args +joinArgs = intercalateArgs "" + +filterOut :: Args -> [String] -> Args +filterOut args list = filter (`notElem` list) <$> args From git at git.haskell.org Thu Oct 26 23:43:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddocks to Target.hs (1b013b0) Message-ID: <20171026234331.992E43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b013b0886e59cdd0ff2bd7a182e874d21899961/ghc >--------------------------------------------------------------- commit 1b013b0886e59cdd0ff2bd7a182e874d21899961 Author: David Luposchainsky Date: Wed Jan 6 15:14:08 2016 +0100 Add Haddocks to Target.hs >--------------------------------------------------------------- 1b013b0886e59cdd0ff2bd7a182e874d21899961 src/Expression.hs | 4 +-- src/Target.hs | 75 ++++++++++++++++++++++++++++++++----------------------- 2 files changed, 46 insertions(+), 33 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index a2eaea9..6e2a225 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -12,7 +12,7 @@ module Expression ( -- ** Common expressions Args, Ways, Packages, -- ** Targets - Target, PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay, + Target, PartialTarget (..), unsafeFromPartial, fullTarget, fullTargetWithWay, -- * Convenient accessors getStage, getPackage, getBuilder, getOutputs, getInputs, getWay, @@ -150,7 +150,7 @@ interpret :: Target -> Expr a -> Action a interpret = flip runReaderT interpretPartial :: PartialTarget -> Expr a -> Action a -interpretPartial = interpret . fromPartial +interpretPartial = interpret . unsafeFromPartial interpretWithStage :: Stage -> Expr a -> Action a interpretWithStage s = interpretPartial $ diff --git a/src/Target.hs b/src/Target.hs index cd22f48..152de3d 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,7 +1,11 @@ {-# LANGUAGE DeriveGeneric, FlexibleInstances #-} module Target ( - Target (..), PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay - ) where + Target (..) + , PartialTarget (..) + , unsafeFromPartial + , fullTarget + , fullTargetWithWay +) where import Control.Monad.Trans.Reader @@ -12,50 +16,53 @@ import Package import Stage import Way --- Target captures all parameters relevant to the current build target: --- * Stage and Package being built, --- * Builder to be invoked, --- * Way to be built (set to vanilla for most targets), --- * source file(s) to be passed to Builder, --- * file(s) to be produced. +-- | Parameters relevant to the current build target. data Target = Target { - stage :: Stage, - package :: Package, - builder :: Builder, - way :: Way, - inputs :: [FilePath], - outputs :: [FilePath] + stage :: Stage, -- ^ Stage being built + package :: Package, -- ^ Package being built + builder :: Builder, -- ^ Builder to be invoked + way :: Way, -- ^ Way to build (set to vanilla for most targets) + inputs :: [FilePath], -- ^ Source files passed to the builder + outputs :: [FilePath] -- ^ Files to be produced } deriving (Show, Eq, Generic) --- If values of type 'a' form a Monoid then we can also derive a Monoid instance --- for values of type 'ReaderT Target Action a': --- * the empty computation returns the identity element of the underlying type +-- | If values of type @a@ form a 'Monoid' then we can also derive a 'Monoid' +-- instance for values of type @'ReaderT' 'Target' 'Action' a@: +-- +-- * the empty computation is the identity element of the underlying type -- * two computations can be combined by combining their results instance Monoid a => Monoid (ReaderT Target Action a) where mempty = return mempty mappend = liftM2 mappend --- PartialTarget is a partially constructed Target with fields Stage and --- Package only. PartialTarget's are used for generating build rules. +-- A partially constructed Target with fields 'Stage' and 'Package' only. +-- 'PartialTarget's are used for generating build rules. data PartialTarget = PartialTarget Stage Package deriving (Eq, Show) --- Convert PartialTarget to Target assuming that unknown fields won't be used. -fromPartial :: PartialTarget -> Target -fromPartial (PartialTarget s p) = Target +-- | Convert 'PartialTarget' to a 'Target' assuming that unknown fields won't +-- be used. +unsafeFromPartial :: PartialTarget -> Target +unsafeFromPartial (PartialTarget s p) = Target { stage = s, package = p, - builder = error "fromPartial: builder not set", - way = error "fromPartial: way not set", - inputs = error "fromPartial: inputs not set", - outputs = error "fromPartial: outputs not set" + builder = error "unsafeFromPartial: builder not set", + way = error "unsafeFromPartial: way not set", + inputs = error "unsafeFromPartial: inputs not set", + outputs = error "unsafeFromPartial: outputs not set" } --- Construct a full target by augmenting a PartialTarget with missing fields. --- Most targets are built only one way, vanilla, hence we set it by default. -fullTarget :: PartialTarget -> Builder -> [FilePath] -> [FilePath] -> Target +-- | Construct a full 'Target' by augmenting a 'PartialTarget' with missing +-- fields. Most targets are built only one way, 'vanilla', hence it is set by +-- default. Use 'fullTargetWithWay' otherwise. +fullTarget :: + PartialTarget + -> Builder + -> [FilePath] -- ^ Source files + -> [FilePath] -- ^ Produced files + -> Target fullTarget (PartialTarget s p) b srcs fs = Target { stage = s, @@ -66,8 +73,14 @@ fullTarget (PartialTarget s p) b srcs fs = Target outputs = map unifyPath fs } --- Use this function to be explicit about the build way. -fullTargetWithWay :: PartialTarget -> Builder -> Way -> [FilePath] -> [FilePath] -> Target +-- | Like 'fullTarget', but allows an explicit 'Way' parameter. +fullTargetWithWay :: + PartialTarget + -> Builder + -> Way + -> [FilePath] -- ^ Source files + -> [FilePath] -- ^ Produced files + -> Target fullTargetWithWay pt b w srcs fs = (fullTarget pt b srcs fs) { way = w } -- Instances for storing in the Shake database From git at git.haskell.org Thu Oct 26 23:43:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Use proper Haddock syntax (ecd1e7d) Message-ID: <20171026234332.C62263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ecd1e7db540b6cf31cc884b5dccba1bf9e01de70/ghc >--------------------------------------------------------------- commit ecd1e7db540b6cf31cc884b5dccba1bf9e01de70 Author: Ben Gamari Date: Sun Dec 20 21:40:53 2015 +0100 Base: Use proper Haddock syntax >--------------------------------------------------------------- ecd1e7db540b6cf31cc884b5dccba1bf9e01de70 src/Base.hs | 44 +++++++++++++++++++++++++++----------------- 1 file changed, 27 insertions(+), 17 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 33b01bd..1c72fd8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,5 @@ module Base ( + -- * General utilities module Control.Applicative, module Control.Monad.Extra, module Control.Monad.Reader, @@ -7,18 +8,26 @@ module Base ( module Data.List, module Data.Maybe, module Data.Monoid, + + -- * Shake module Development.Shake, module Development.Shake.Classes, module Development.Shake.Config, module Development.Shake.FilePath, module Development.Shake.Util, - module System.Console.ANSI, + + -- * Paths shakeFilesPath, configPath, bootPackageConstraints, packageDependencies, - replaceEq, replaceSeparators, decodeModule, - unifyPath, (-/-), chunksOfSize, + + -- * Output putColoured, putOracle, putBuild, putSuccess, putError, + module System.Console.ANSI, + + -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, - removeFileIfExists + removeFileIfExists, + replaceEq, replaceSeparators, decodeModule, + unifyPath, (-/-), chunksOfSize, ) where import Control.Applicative @@ -55,34 +64,35 @@ packageDependencies :: FilePath packageDependencies = shakeFilesPath -/- "package-dependencies" -- Utility functions --- Find and replace all occurrences of a value in a list +-- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) --- Find and replace all occurrences of path separators in a String with a Char +-- | Find and replace all occurrences of path separators in a String with a Char replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) --- Given a module name extract the directory and file names, e.g.: --- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +-- | Given a module name extract the directory and file names, e.g.: +-- +-- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") decodeModule :: String -> (FilePath, String) decodeModule = splitFileName . replaceEq '.' '/' --- Normalise a path and convert all path separators to /, even on Windows. +-- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx --- Combine paths using and apply unifyPath to the result +-- | Combine paths using '' and apply 'unifyPath' to the result (-/-) :: FilePath -> FilePath -> FilePath a -/- b = unifyPath $ a b infixr 6 -/- --- (chunksOfSize size strings) splits a given list of strings into chunks not --- exceeding the given 'size'. +-- | @chunksOfSize size strings@ splits a given list of strings into chunks not +-- exceeding the given @size at . chunksOfSize :: Int -> [String] -> [[String]] chunksOfSize _ [] = [] chunksOfSize size strings = reverse chunk : chunksOfSize size rest @@ -94,7 +104,7 @@ chunksOfSize size strings = reverse chunk : chunksOfSize size rest where newSize = chunkSize + length s --- A more colourful version of Shake's putNormal +-- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do liftIO $ setSGR [SetColor Foreground Vivid colour] @@ -102,19 +112,19 @@ putColoured colour msg = do liftIO $ setSGR [] liftIO $ hFlush stdout --- Make oracle output more distinguishable +-- | Make oracle output more distinguishable putOracle :: String -> Action () putOracle = putColoured Blue --- Make build output more distinguishable +-- | Make build output more distinguishable putBuild :: String -> Action () putBuild = putColoured White --- A more colourful version of success message +-- | A more colourful version of success message putSuccess :: String -> Action () putSuccess = putColoured Green --- A more colourful version of error message +-- | A more colourful version of error message putError :: String -> Action a putError msg = do putColoured Red msg From git at git.haskell.org Thu Oct 26 23:43:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Config.hs (autoconf and configure rules). (9566d56) Message-ID: <20171026234335.5DFF93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9566d564272d1762d8f0eca492b17673ca0af55c/ghc >--------------------------------------------------------------- commit 9566d564272d1762d8f0eca492b17673ca0af55c Author: Andrey Mokhov Date: Tue Dec 23 17:45:51 2014 +0000 Add Config.hs (autoconf and configure rules). >--------------------------------------------------------------- 9566d564272d1762d8f0eca492b17673ca0af55c Config.hs | 24 ++++++++++++++++++++++++ 1 file changed, 24 insertions(+) diff --git a/Config.hs b/Config.hs new file mode 100644 index 0000000..a370f38 --- /dev/null +++ b/Config.hs @@ -0,0 +1,24 @@ +module Config ( + autoconfRules, configureRules + ) where + +import Development.Shake +import Development.Shake.Command +import Development.Shake.FilePath +import Development.Shake.Rule +import Control.Applicative +import Control.Monad +import Base +import Oracles + +autoconfRules :: Rules () +autoconfRules = do + "shake/configure" %> \out -> do + need ["shake/configure.ac"] + cmd $ "bash shake/autoconf" + +configureRules :: Rules () +configureRules = do + "shake/default.config" %> \out -> do + need ["shake/default.config.in", "shake/configure"] + cmd $ "bash shake/configure" From git at git.haskell.org Thu Oct 26 23:43:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Explain stages (bee9cee) Message-ID: <20171026234335.8B98D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bee9ceed2f9e196b1d7adcc02c74246ec8c89f82/ghc >--------------------------------------------------------------- commit bee9ceed2f9e196b1d7adcc02c74246ec8c89f82 Author: David Luposchainsky Date: Wed Jan 6 15:05:37 2016 +0100 Explain stages >--------------------------------------------------------------- bee9ceed2f9e196b1d7adcc02c74246ec8c89f82 src/Stage.hs | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/src/Stage.hs b/src/Stage.hs index 144aa29..2e581c4 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -4,10 +4,27 @@ module Stage (Stage (..), stageString) where import Development.Shake.Classes import GHC.Generics (Generic) --- TODO: explain stages +-- | A stage refers to a certain compiler in GHC's build process. +-- +-- * Stage 0 is the bootstrapping compiler, i.e. the one already installed on +-- the user's system. +-- +-- * Stage 1 is built using the stage 0 compiler, using GHC's source code. +-- The result is a compiler that was built by the bootstrapping compiler, +-- with all the features of the new compiler. +-- +-- * Stage 2 is built using the stage 1 compiler and GHC's source code. The +-- result is a compiler "built by itself", commonly referred to as +-- /bootstrapping/. +-- +-- * Stage 3 uses stage 2 to build from source again. The result should have +-- the same object code as stage 2, which is a good test for the compiler. +-- Since it serves no other purpose than that, the stage 3 build is usually +-- omitted in the build process. data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Show, Eq, Ord, Enum, Generic) +-- | Prettyprint a 'Stage'. stageString :: Stage -> String stageString stage = "stage" ++ show (fromEnum stage) From git at git.haskell.org Thu Oct 26 23:43:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Library: Use renderBox (c7a0c19) Message-ID: <20171026234336.629D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7a0c197ec98a64089af06a9efd0a8f41bfddead/ghc >--------------------------------------------------------------- commit c7a0c197ec98a64089af06a9efd0a8f41bfddead Author: Ben Gamari Date: Sun Dec 20 21:46:19 2015 +0100 Library: Use renderBox >--------------------------------------------------------------- c7a0c197ec98a64089af06a9efd0a8f41bfddead src/Rules/Library.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 088ac8d..134e2be 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -46,11 +46,12 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do else build $ fullTarget target Ar objs [a] synopsis <- interpretPartial target $ getPkgData Synopsis - putSuccess $ "/--------\n| Successfully built package library '" - ++ pkgName pkg - ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." - putSuccess $ "| Package synopsis: " - ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" + putSuccess $ renderBox + [ "Successfully built package library '" + ++ pkgName pkg + ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." + , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." + ] -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. From git at git.haskell.org Thu Oct 26 23:43:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Oracles.hs (configuration infrastructure). (cb701bb) Message-ID: <20171026234338.CFDC73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb701bb1c14ea9db25b433778c6a6a05d506dc2f/ghc >--------------------------------------------------------------- commit cb701bb1c14ea9db25b433778c6a6a05d506dc2f Author: Andrey Mokhov Date: Tue Dec 23 17:46:41 2014 +0000 Add Oracles.hs (configuration infrastructure). >--------------------------------------------------------------- cb701bb1c14ea9db25b433778c6a6a05d506dc2f Oracles.hs | 250 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 250 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 cb701bb1c14ea9db25b433778c6a6a05d506dc2f From git at git.haskell.org Thu Oct 26 23:43:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add cabal configure to CI (5f4a8f6) Message-ID: <20171026234339.2AC2E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f4a8f61707469c736f79b8da372e5ef4beb081a/ghc >--------------------------------------------------------------- commit 5f4a8f61707469c736f79b8da372e5ef4beb081a Author: David Luposchainsky Date: Wed Jan 6 15:39:33 2016 +0100 Add cabal configure to CI >--------------------------------------------------------------- 5f4a8f61707469c736f79b8da372e5ef4beb081a .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index a28a979..6413818 100644 --- a/.travis.yml +++ b/.travis.yml @@ -50,6 +50,7 @@ install: - ( cd ghc/shake-build && git reset --hard HEAD ) - ( cd ghc/shake-build && cabal install --only-dependencies ) + - ( cd ghc/shake-build && cabal configure ) - ( cd ghc && ./boot ) - ( cd ghc && ./configure ) From git at git.haskell.org Thu Oct 26 23:43:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Program: Use renderBox (cbd6aef) Message-ID: <20171026234339.F3A6E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbd6aef9b8d6697da710d119deb05277822c5e31/ghc >--------------------------------------------------------------- commit cbd6aef9b8d6697da710d119deb05277822c5e31 Author: Ben Gamari Date: Sun Dec 20 21:43:28 2015 +0100 Program: Use renderBox >--------------------------------------------------------------- cbd6aef9b8d6697da710d119deb05277822c5e31 src/Rules/Program.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 8e3ec77..2ff5ef0 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -47,8 +47,9 @@ buildProgram _ target @ (PartialTarget stage pkg) = do need $ objs ++ libs build $ fullTargetWithWay target (Ghc stage) vanilla objs [bin] synopsis <- interpretPartial target $ getPkgData Synopsis - putSuccess $ "/--------\n| Successfully built program '" - ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." - putSuccess $ "| Executable: " ++ bin - putSuccess $ "| Package synopsis: " - ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" + putSuccess $ renderBox + [ "Successfully built program '" + ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + , "Executable: " ++ bin + , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." + ] From git at git.haskell.org Thu Oct 26 23:43:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Packages.hs (package build rules). (c8212ad) Message-ID: <20171026234343.067D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8212add0d0e343652406f994b6c2c5ff36a5a37/ghc >--------------------------------------------------------------- commit c8212add0d0e343652406f994b6c2c5ff36a5a37 Author: Andrey Mokhov Date: Tue Dec 23 17:47:37 2014 +0000 Add Packages.hs (package build rules). >--------------------------------------------------------------- c8212add0d0e343652406f994b6c2c5ff36a5a37 Package.hs | 196 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 196 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 c8212add0d0e343652406f994b6c2c5ff36a5a37 From git at git.haskell.org Thu Oct 26 23:43:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddock build to CI (db5e646) Message-ID: <20171026234343.90B683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db5e646e6fedd351caeed52ecdb8ce4946eb4613/ghc >--------------------------------------------------------------- commit db5e646e6fedd351caeed52ecdb8ce4946eb4613 Author: David Luposchainsky Date: Wed Jan 6 15:01:20 2016 +0100 Add Haddock build to CI >--------------------------------------------------------------- db5e646e6fedd351caeed52ecdb8ce4946eb4613 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 4cc0396..a28a979 100644 --- a/.travis.yml +++ b/.travis.yml @@ -55,6 +55,7 @@ install: - ( cd ghc && ./configure ) script: + - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh -j --no-progress $TARGET cache: From git at git.haskell.org Thu Oct 26 23:43:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move `renderBox` to `Base` (26e64ed) Message-ID: <20171026234344.18B393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/26e64ed57d5b0d85e740baedd529e845002103e9/ghc >--------------------------------------------------------------- commit 26e64ed57d5b0d85e740baedd529e845002103e9 Author: Ben Gamari Date: Sun Dec 20 21:41:36 2015 +0100 Move `renderBox` to `Base` >--------------------------------------------------------------- 26e64ed57d5b0d85e740baedd529e845002103e9 src/Base.hs | 18 ++++++++++++++++++ src/Rules/Actions.hs | 20 ++------------------ 2 files changed, 20 insertions(+), 18 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7edae37..fb3b5e1 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -21,6 +21,7 @@ module Base ( -- * Output putColoured, putOracle, putBuild, putSuccess, putError, + renderBox, module System.Console.ANSI, -- * Miscellaneous utilities @@ -130,6 +131,23 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg +-- | Render the given set of lines in a ASCII box +renderBox :: [String] -> String +renderBox ls = + unlines $ [begin] ++ map (bar++) ls ++ [end] + where + (begin,bar,end) + | useUnicode = ( "╭──────────" + , "│ " + , "╰──────────" + ) + | otherwise = ( "/----------" + , "| " + , "\\----------" + ) + -- FIXME: See Shake #364. + useUnicode = False + -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 775524a..5a3d113 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -7,22 +7,6 @@ import Settings.Args import Settings.Builders.Ar import qualified Target -insideBox :: [String] -> String -insideBox ls = - unlines $ [begin] ++ map (bar++) ls ++ [end] - where - (begin,bar,end) - | useUnicode = ( "╭──────────" - , "│ " - , "╰──────────" - ) - | otherwise = ( "/----------" - , "| " - , "\\----------" - ) - -- FIXME: See Shake #364. - useUnicode = False - -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last -- built (that is, track changes in the build system). @@ -38,8 +22,8 @@ buildWithResources rs target = do checkArgsHash target withResources rs $ do unless verbose $ do - putBuild $ insideBox $ [ "Running " ++ show builder ++ " with arguments:" ] - ++ map (" "++) (interestingInfo builder argList) + putBuild $ renderBox $ [ "Running " ++ show builder ++ " with arguments:" ] + ++ map (" "++) (interestingInfo builder argList) quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList From git at git.haskell.org Thu Oct 26 23:43:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Ways.hs (build ways and helper functions). (9a33083) Message-ID: <20171026234347.4198F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a33083158e13abb252f3787059e8e2cb5da9215/ghc >--------------------------------------------------------------- commit 9a33083158e13abb252f3787059e8e2cb5da9215 Author: Andrey Mokhov Date: Tue Dec 23 17:53:17 2014 +0000 Add Ways.hs (build ways and helper functions). >--------------------------------------------------------------- 9a33083158e13abb252f3787059e8e2cb5da9215 Ways.hs | 96 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 96 insertions(+) diff --git a/Ways.hs b/Ways.hs new file mode 100644 index 0000000..6e186ab --- /dev/null +++ b/Ways.hs @@ -0,0 +1,96 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module Ways ( + WayUnit (..), + Way, tag, + + allWays, defaultWays, + + vanilla, profiling, logging, parallel, granSim, + threaded, threadedProfiling, threadedLogging, + debug, debugProfiling, threadedDebug, threadedDebugProfiling, + dynamic, profilingDynamic, threadedProfilingDynamic, + threadedDynamic, threadedDebugDynamic, debugDynamic, + loggingDynamic, threadedLoggingDynamic, + + hisuf, osuf, hcsuf + ) where + +import Base +import Oracles + +data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dynamic deriving Eq + +data Way = Way + { + tag :: String, -- e.g., "thr_p" + description :: String, -- e.g., "threaded profiled" + units :: [WayUnit] -- e.g., [Threaded, Profiling] + } + deriving Eq + +vanilla = Way "v" "vanilla" [] +profiling = Way "p" "profiling" [Profiling] +logging = Way "l" "event logging" [Logging] +parallel = Way "mp" "parallel" [Parallel] +granSim = Way "gm" "GranSim" [GranSim] + +-- RTS only ways + +threaded = Way "thr" "threaded" [Threaded] +threadedProfiling = Way "thr_p" "threaded profiling" [Threaded, Profiling] +threadedLogging = Way "thr_l" "threaded event logging" [Threaded, Logging] +debug = Way "debug" "debug" [Debug] +debugProfiling = Way "debug_p" "debug profiling" [Debug, Profiling] +threadedDebug = Way "thr_debug" "threaded debug" [Threaded, Debug] +threadedDebugProfiling = Way "thr_debug_p" "threaded debug profiling" [Threaded, Debug, Profiling] +dynamic = Way "dyn" "dyn" [Dynamic] +profilingDynamic = Way "p_dyn" "p_dyn" [Profiling, Dynamic] +threadedProfilingDynamic = Way "thr_p_dyn" "thr_p_dyn" [Threaded, Profiling, Dynamic] +threadedDynamic = Way "thr_dyn" "thr_dyn" [Threaded, Dynamic] +threadedDebugDynamic = Way "thr_debug_dyn" "thr_debug_dyn" [Threaded, Debug, Dynamic] +debugDynamic = Way "debug_dyn" "debug_dyn" [Debug, Dynamic] +loggingDynamic = Way "l_dyn" "event logging dynamic" [Logging, Dynamic] +threadedLoggingDynamic = Way "thr_l_dyn" "threaded event logging dynamic" [Threaded, Logging, Dynamic] + +allWays = [vanilla, profiling, logging, parallel, granSim, + threaded, threadedProfiling, threadedLogging, + debug, debugProfiling, threadedDebug, threadedDebugProfiling, + dynamic, profilingDynamic, threadedProfilingDynamic, + threadedDynamic, threadedDebugDynamic, debugDynamic, + loggingDynamic, threadedLoggingDynamic] + +-- TODO: what are ways 't' and 's'? +-- ALL_WAYS=v p t l s mp mg debug dyn thr thr_l p_dyn debug_dyn thr_dyn thr_p_dyn thr_debug_dyn thr_p thr_debug debug_p thr_debug_p l_dyn thr_l_dyn + +defaultWays :: Stage -> Action [Way] +defaultWays stage = do + sharedLibs <- test PlatformSupportsSharedLibs + return $ [vanilla] + ++ [profiling | stage /= Stage0] + ++ [dynamic | sharedLibs ] + +wayHcOpts :: Way -> Args +wayHcOpts (Way _ _ units) = + mconcat + [ when (Dynamic `notElem` units) $ arg [ "-static" ] + , when (Dynamic `elem` units) $ arg [ "-fPIC", "-dynamic" ] + , when (Threaded `elem` units) $ arg [ "-optc-DTHREADED_RTS" ] + , when (Debug `elem` units) $ arg [ "-optc-DDEBUG" ] + , when (Profiling `elem` units) $ arg [ "-prof" ] + , when (Logging `elem` units) $ arg [ "-eventlog" ] + , when (Parallel `elem` units) $ arg [ "-parallel" ] + , when (GranSim `elem` units) $ arg [ "-gransim" ] + , when (units == [Debug] || units == [Debug, Dynamic]) $ arg [ "-ticky", "-DTICKY_TICKY" ] + ] + +suffix :: FilePath -> Way -> FilePath +suffix base (Way _ _ units) = + concat $ + ["p_" | Profiling `elem` units] ++ + ["dyn_" | Dynamic `elem` units] ++ + [base ] + +hisuf, osuf, hcsuf :: Way -> FilePath +hisuf = suffix "hi" +osuf = suffix "o" +hcsuf = suffix "hc" From git at git.haskell.org Thu Oct 26 23:43:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Haddocks for Way.hs (997ce25) Message-ID: <20171026234348.2ED513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/997ce259b41f6e60b7d4906292b920a00c799bfd/ghc >--------------------------------------------------------------- commit 997ce259b41f6e60b7d4906292b920a00c799bfd Author: David Luposchainsky Date: Wed Jan 6 15:31:55 2016 +0100 Haddocks for Way.hs >--------------------------------------------------------------- 997ce259b41f6e60b7d4906292b920a00c799bfd src/Rules.hs | 2 +- src/Stage.hs | 2 +- src/Way.hs | 37 +++++++++++++++++++++++++++++-------- 3 files changed, 31 insertions(+), 10 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index f8b2810..c24b354 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -11,7 +11,7 @@ import Rules.Resources import Settings allStages :: [Stage] -allStages = [Stage0 ..] +allStages = [minBound ..] -- TODO: not all program targets should be needed explicitly -- | 'need' all top-level build targets diff --git a/src/Stage.hs b/src/Stage.hs index 2e581c4..af6d2df 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -22,7 +22,7 @@ import GHC.Generics (Generic) -- Since it serves no other purpose than that, the stage 3 build is usually -- omitted in the build process. data Stage = Stage0 | Stage1 | Stage2 | Stage3 - deriving (Show, Eq, Ord, Enum, Generic) + deriving (Show, Eq, Ord, Enum, Generic, Bounded) -- | Prettyprint a 'Stage'. stageString :: Stage -> String diff --git a/src/Way.hs b/src/Way.hs index 28d1365..9f7f12a 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -19,6 +19,8 @@ import Oracles -- Note: order of constructors is important for compatibility with the old build -- system, e.g. we want "thr_p", not "p_thr" (see instance Show Way). +-- | A 'WayUnit' is a single way of building source code, for example with +-- profiling enabled, or dynamically linked. data WayUnit = Threaded | Debug | Profiling @@ -26,7 +28,7 @@ data WayUnit = Threaded | Dynamic | Parallel | GranSim - deriving (Eq, Enum) + deriving (Eq, Enum, Bounded) -- TODO: get rid of non-derived Show instances instance Show WayUnit where @@ -40,16 +42,22 @@ instance Show WayUnit where GranSim -> "gm" instance Read WayUnit where - readsPrec _ s = [(unit, "") | unit <- [Threaded ..], show unit == s] + readsPrec _ s = [(unit, "") | unit <- [minBound ..], show unit == s] +-- | Collection of 'WayUnit's that stands for the different ways source code +-- is to be built. newtype Way = Way IntSet +-- | Construct a 'Way' from multiple 'WayUnit's. Inverse of 'wayToUnits'. wayFromUnits :: [WayUnit] -> Way wayFromUnits = Way . Set.fromList . map fromEnum +-- | Split a 'Way' into its 'WayUnit' building blocks. +-- Inverse of 'wayFromUnits'. wayToUnits :: Way -> [WayUnit] wayToUnits (Way set) = map toEnum . Set.elems $ set +-- | Check whether a 'Way' contains a certain 'WayUnit'. wayUnit :: WayUnit -> Way -> Bool wayUnit unit (Way set) = fromEnum unit `Set.member` set @@ -72,11 +80,23 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b -vanilla, profiling, logging, parallel, granSim :: Way +-- | Build with no 'WayUnit's at all. +vanilla :: Way vanilla = wayFromUnits [] + +-- | Build with profiling. +profiling :: Way profiling = wayFromUnits [Profiling] + +-- | Build with logging. +logging :: Way logging = wayFromUnits [Logging] + +-- | Build in parallel. +parallel :: Way parallel = wayFromUnits [Parallel] + +granSim :: Way granSim = wayFromUnits [GranSim] -- RTS only ways @@ -135,11 +155,12 @@ libsuf way @ (Way set) = -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension --- Detect way from a given filename. Returns Nothing if there is no match: --- * safeDetectWay "foo/bar.hi" == Just vanilla --- * safeDetectWay "baz.thr_p_o" == Just threadedProfiling --- * safeDetectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") --- * safeDetectWay "xru.p_ghc7.11.20141222.so" == Just profiling +-- | Detect way from a given 'FilePath'. Returns 'Nothing' if there is no match. +-- +-- * @'safeDetectWay' "foo/bar.hi" '==' 'Just' vanilla@ +-- * @'safeDetectWay' "baz.thr_p_o" '==' 'Just' threadedProfiling@ +-- * @'safeDetectWay' "qwe.ph_i" '==' 'Nothing' (expected "qwe.p_hi")@ +-- * @'safeDetectWay' "xru.p_ghc7.11.123.so" '==' 'Just' profiling@ safeDetectWay :: FilePath -> Maybe Way safeDetectWay file = case reads prefix of [(way, "")] -> Just way From git at git.haskell.org Thu Oct 26 23:43:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an explicit dependency on pkgDataFile to make sure GhcCabal hscolour is run after GhcCabal configure. (0c9d7d8) Message-ID: <20171026234348.6BE8A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c9d7d887552956816e5acee725dbc79f591b18d/ghc >--------------------------------------------------------------- commit 0c9d7d887552956816e5acee725dbc79f591b18d Author: Andrey Mokhov Date: Sun Dec 20 20:58:10 2015 +0000 Add an explicit dependency on pkgDataFile to make sure GhcCabal hscolour is run after GhcCabal configure. >--------------------------------------------------------------- 0c9d7d887552956816e5acee725dbc79f591b18d src/Rules/Documentation.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 495a16c..463552f 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -10,9 +10,9 @@ import Settings -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. buildPackageDocumentation :: Resources -> PartialTarget -> Rules () -buildPackageDocumentation _ target @ (PartialTarget stage package) = - let cabalFile = pkgCabalFile package - haddockFile = pkgHaddockFile package +buildPackageDocumentation _ target @ (PartialTarget stage pkg) = + let cabalFile = pkgCabalFile pkg + haddockFile = pkgHaddockFile pkg in when (stage == Stage1) $ do haddockFile %> \file -> do srcs <- interpretPartial target getPackageSources @@ -23,7 +23,7 @@ buildPackageDocumentation _ target @ (PartialTarget stage package) = -- HsColour sources whenM (specified HsColour) $ do - need [cabalFile] + need [cabalFile, pkgDataFile stage pkg ] build $ fullTarget target GhcCabalHsColour [cabalFile] [] -- Build Haddock documentation From git at git.haskell.org Thu Oct 26 23:43:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add docs (mostly progress comments so far). (c816893) Message-ID: <20171026234350.C00C53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8168933901fda238b9cd2cf30eb5414194816a3/ghc >--------------------------------------------------------------- commit c8168933901fda238b9cd2cf30eb5414194816a3 Author: Andrey Mokhov Date: Tue Dec 23 17:54:46 2014 +0000 Add docs (mostly progress comments so far). >--------------------------------------------------------------- c8168933901fda238b9cd2cf30eb5414194816a3 doc/build-package-data.docx | Bin 0 -> 15964 bytes doc/comment-hi-rule.txt | 39 ++++++ doc/deepseq-build-progress.txt | 300 +++++++++++++++++++++++++++++++++++++++++ 3 files changed, 339 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 c8168933901fda238b9cd2cf30eb5414194816a3 From git at git.haskell.org Thu Oct 26 23:43:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix type error (ffc151c) Message-ID: <20171026234352.238BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffc151c004163822f9e5d131b9556b0c42a3be44/ghc >--------------------------------------------------------------- commit ffc151c004163822f9e5d131b9556b0c42a3be44 Author: David Luposchainsky Date: Wed Jan 6 15:35:22 2016 +0100 Fix type error >--------------------------------------------------------------- ffc151c004163822f9e5d131b9556b0c42a3be44 src/Rules.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules.hs b/src/Rules.hs index c24b354..fe8242b 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -35,6 +35,6 @@ targetsForStage stage = do packageRules :: Rules () packageRules = do resources <- resourceRules - for allStages $ \stage -> + for_ allStages $ \stage -> for_ knownPackages $ \pkg -> buildPackage resources $ PartialTarget stage pkg From git at git.haskell.org Thu Oct 26 23:43:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #13 from bgamari/master (e801ee0) Message-ID: <20171026234352.501703A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e801ee01698baa20d7a56e57768104f74ac35ffa/ghc >--------------------------------------------------------------- commit e801ee01698baa20d7a56e57768104f74ac35ffa Merge: 0c9d7d8 c7a0c19 Author: Andrey Mokhov Date: Sun Dec 20 21:04:59 2015 +0000 Merge pull request #13 from bgamari/master Consolidate box pretty-printing >--------------------------------------------------------------- e801ee01698baa20d7a56e57768104f74ac35ffa src/Base.hs | 64 +++++++++++++++++++++++++++++++++++++--------------- src/Rules/Actions.hs | 20 ++-------------- src/Rules/Library.hs | 11 +++++---- src/Rules/Program.hs | 11 +++++---- 4 files changed, 60 insertions(+), 46 deletions(-) From git at git.haskell.org Thu Oct 26 23:43:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comment on where this goes in the GHC source tree. (3c08e17) Message-ID: <20171026234354.35AB83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c08e170bf0dfdf23ed34cfbc21a2b0286f0e23d/ghc >--------------------------------------------------------------- commit 3c08e170bf0dfdf23ed34cfbc21a2b0286f0e23d Author: Andrey Mokhov Date: Tue Dec 23 17:58:29 2014 +0000 Comment on where this goes in the GHC source tree. >--------------------------------------------------------------- 3c08e170bf0dfdf23ed34cfbc21a2b0286f0e23d README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 7167e9a..54742ee 100644 --- a/README.md +++ b/README.md @@ -2,3 +2,5 @@ Shaking up GHC ============== As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). + +This is supposed to go into the `shake` directory of the GHC source tree (as a submodule). From git at git.haskell.org Thu Oct 26 23:43:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix bad imports (302c1df) Message-ID: <20171026234356.587663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/302c1dfb07284855bafd93d8a0cfb34bcbb50847/ghc >--------------------------------------------------------------- commit 302c1dfb07284855bafd93d8a0cfb34bcbb50847 Author: David Luposchainsky Date: Wed Jan 6 15:45:34 2016 +0100 Fix bad imports >--------------------------------------------------------------- 302c1dfb07284855bafd93d8a0cfb34bcbb50847 src/Main.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index bacc8f1..b30b38e 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,5 +1,7 @@ module Main (main) where +import Development.Shake + import qualified Base as B import qualified Rules as R import qualified Rules.Cabal as RCabal @@ -24,6 +26,6 @@ main = shakeArgs options rules , ROracle.oracleRules , R.packageRules ] options = shakeOptions - { shakeFiles = shakeFilesPath + { shakeFiles = B.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Thu Oct 26 23:43:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, make naming consistent: setPkgType -> setType. (f5d4e7b) Message-ID: <20171026234356.795CB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5d4e7b91aff5a8a0c1e8368173d6c999a01d4b4/ghc >--------------------------------------------------------------- commit f5d4e7b91aff5a8a0c1e8368173d6c999a01d4b4 Author: Andrey Mokhov Date: Sun Dec 20 21:19:02 2015 +0000 Clean up, make naming consistent: setPkgType -> setType. >--------------------------------------------------------------- f5d4e7b91aff5a8a0c1e8368173d6c999a01d4b4 src/Base.hs | 6 ++---- src/GHC.hs | 4 ++-- src/Package.hs | 6 +++--- src/Rules/Program.hs | 4 ---- 4 files changed, 7 insertions(+), 13 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fb3b5e1..009e197 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -20,15 +20,13 @@ module Base ( shakeFilesPath, configPath, bootPackageConstraints, packageDependencies, -- * Output - putColoured, putOracle, putBuild, putSuccess, putError, - renderBox, + putColoured, putOracle, putBuild, putSuccess, putError, renderBox, module System.Console.ANSI, -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, removeFileIfExists, - replaceEq, replaceSeparators, decodeModule, - unifyPath, (-/-), chunksOfSize, + replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, ) where import Control.Applicative diff --git a/src/GHC.hs b/src/GHC.hs index 29db671..923fdf1 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -51,7 +51,7 @@ dllSplit = utility "dll-split" filepath = library "filepath" genapply = utility "genapply" genprimopcode = utility "genprimopcode" -ghc = topLevel "ghc-bin" `setPath` "ghc" `setPkgType` Program +ghc = topLevel "ghc-bin" `setPath` "ghc" `setType` Program ghcBoot = library "ghc-boot" ghcCabal = utility "ghc-cabal" ghci = library "ghci" @@ -68,7 +68,7 @@ hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" integerGmp = library "integer-gmp" integerSimple = library "integer-simple" -iservBin = topLevel "iserv-bin" `setPath` "iserv" `setPkgType` Program +iservBin = topLevel "iserv-bin" `setPath` "iserv" `setType` Program mkUserGuidePart = utility "mkUserGuidePart" parallel = library "parallel" pretty = library "pretty" diff --git a/src/Package.hs b/src/Package.hs index 6273a62..574f01a 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -5,7 +5,7 @@ module Package ( pkgCabalFile, matchPackageNames, -- * Helpers for constructing 'Package's - setPath, topLevel, library, utility, setPkgType + setPath, topLevel, library, utility, setType ) where import Base @@ -45,8 +45,8 @@ utility name = Package name ("utils" -/- name) Program setPath :: Package -> FilePath -> Package setPath pkg path = pkg { pkgPath = path } -setPkgType :: Package -> PackageType -> Package -setPkgType pkg ty = pkg { pkgType = ty } +setType :: Package -> PackageType -> Package +setType pkg ty = pkg { pkgType = ty } instance Show Package where show = pkgName diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 2ff5ef0..9ca36d6 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -17,10 +17,6 @@ buildProgram _ target @ (PartialTarget stage pkg) = do buildPath = path -/- "build" program = programPath stage pkg - -- return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] - -- ++ [ haddock | needHaddock && stage == Stage1 ] - -- ++ libs - (\f -> program == Just f) ?> \bin -> do cSrcs <- cSources target -- TODO: remove code duplication (Library.hs) hSrcs <- hSources target From git at git.haskell.org Thu Oct 26 23:44:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddocks to GHC.hs (9dd9ae0) Message-ID: <20171026234400.0BDC53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dd9ae02b8bae0ead318594555929727960aee6a/ghc >--------------------------------------------------------------- commit 9dd9ae02b8bae0ead318594555929727960aee6a Author: David Luposchainsky Date: Wed Jan 6 15:45:48 2016 +0100 Add Haddocks to GHC.hs >--------------------------------------------------------------- 9dd9ae02b8bae0ead318594555929727960aee6a src/GHC.hs | 23 ++++++++++++----------- 1 file changed, 12 insertions(+), 11 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 6e3a477..3d99e63 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -15,11 +15,11 @@ import Base import Package import Stage --- These are all GHC packages we know about. Build rules will be generated for +-- | These are all GHC packages we know about. Build rules will be generated for -- all of them. However, not all of these packages will be built. For example, --- package 'win32' is built only on Windows. --- Settings/Packages.hs defines default conditions for building each package, --- which can be overridden in Settings/User.hs. +-- package /win32/ is built only on Windows. +-- "Packages" defines default conditions for building each package, which can +-- be overridden in "User". defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes @@ -30,7 +30,7 @@ defaultKnownPackages = , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time , touchy, transformers, unix, win32, xhtml ] --- Package definitions (see Package.hs) +-- Package definitions (see "Package") array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, @@ -95,16 +95,17 @@ xhtml = library "xhtml" -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, -- lndir, mkdirhier, testremove, vagrant --- GHC build results will be placed into target directories with the following --- typical structure: --- * build/ : contains compiled object code --- * doc/ : produced by haddock --- * package-data.mk : contains output of ghc-cabal applied to pkgCabal +-- | GHC build results will be placed into target directories with the +-- following typical structure: + +-- * @build/@ contains compiled object code +-- * @doc/@ is produced by haddock +-- * @package-data.mk@ contains output of ghc-cabal applied to pkgCabal defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage _ = stageString stage -- TODO: simplify, add programInplaceLibPath --- | Returns a relative path to the program executable +-- | The relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) From git at git.haskell.org Thu Oct 26 23:43:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:43:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add configuration files and dummy builders (autoconf, configure) for debugging. (9089a36) Message-ID: <20171026234357.A0F8A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9089a366948907d730e9cc550f209357214be039/ghc >--------------------------------------------------------------- commit 9089a366948907d730e9cc550f209357214be039 Author: Andrey Mokhov Date: Tue Dec 23 18:01:01 2014 +0000 Add configuration files and dummy builders (autoconf, configure) for debugging. >--------------------------------------------------------------- 9089a366948907d730e9cc550f209357214be039 autoconf | 2 ++ configure | 1 + configure.ac | 1 + default.config | 52 ++++++++++++++++++++++++++++++++++++++++++++++++++++ default.config.in | 45 +++++++++++++++++++++++++++++++++++++++++++++ user.config | 1 + 6 files changed, 102 insertions(+) diff --git a/autoconf b/autoconf new file mode 100644 index 0000000..99e5cb3 --- /dev/null +++ b/autoconf @@ -0,0 +1,2 @@ +echo "Running autoconf... (not really)" +echo "$(cat $(dirname $0)/configure.ac) $(date)...\"" > $(dirname $0)/configure diff --git a/configure b/configure new file mode 100644 index 0000000..f51695b --- /dev/null +++ b/configure @@ -0,0 +1 @@ +echo "Running fake configure generated at: Mon, Dec 22, 2014 2:15:52 PM..." diff --git a/configure.ac b/configure.ac new file mode 100644 index 0000000..03184ad --- /dev/null +++ b/configure.ac @@ -0,0 +1 @@ +echo "Running fake configure generated at: diff --git a/default.config b/default.config new file mode 100644 index 0000000..f821e7a --- /dev/null +++ b/default.config @@ -0,0 +1,52 @@ +system-ghc = C:/msys64/usr/local/bin/ghc.exe +system-ghc-pkg = C:/msys64/usr/local/bin/ghc-pkg.exe + +ghc-cabal = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-cabal.exe +ghc-stage1 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage1.exe +ghc-stage2 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage2.exe +ghc-stage3 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage3.exe + +ghc-pkg = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-pkg.exe + +gcc = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/gcc.exe +ld = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ld.exe +ar = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ar.exe +alex = C:/msys64/usr/local/bin/alex.exe +happy = C:/msys64/usr/local/bin/happy.exe +hscolour = + +target-os = mingw32 +target-arch = x86_64 +target-platform-full = x86_64-unknown-mingw32 + +cross-compiling = NO + +conf-cc-args-stage-0 = -fno-stack-protector +conf-cc-args-stage-1 = -fno-stack-protector +conf-cc-args-stage-2 = -fno-stack-protector + +conf-cpp-args-stage-0 = +conf-cpp-args-stage-1 = +conf-cpp-args-stage-2 = + +conf-gcc-linker-args-stage-0 = +conf-gcc-linker-args-stage-1 = +conf-gcc-linker-args-stage-2 = + +conf-ld-linker-args-stage-0 = +conf-ld-linker-args-stage-1 = +conf-ld-linker-args-stage-2 = + +iconv-include-dirs = +iconv-lib-dirs = +gmp-include-dirs = +gmp-lib-dirs = + +lax-dependencies = NO +dynamic-ghc-programs = NO +gcc-is-clang = NO +gcc-lt-46 = NO + + + +host-os-cpp = mingw32 diff --git a/default.config.in b/default.config.in new file mode 100644 index 0000000..4ab5e21 --- /dev/null +++ b/default.config.in @@ -0,0 +1,45 @@ +ghc-cabal = inplace/bin/ghc-cabal at exeext_host@ +ghc = @WithGhc@ +ghc-pkg = @GhcPkgCmd@ +gcc = @WhatGccIsCalled@ +ld = @LdCmd@ +ar = @ArCmd@ +alex = @AlexCmd@ +happy = @HappyCmd@ +hscolour = @HSCOLOUR@ +target-os = @TargetOS_CPP@ +target-arch = @TargetArch_CPP@ +target-platform-full = @TargetPlatformFull@ + +cross-compiling = @CrossCompiling@ + +conf-cc-args-stage-0 = @CONF_CC_OPTS_STAGE0@ +conf-cc-args-stage-1 = @CONF_CC_OPTS_STAGE1@ +conf-cc-args-stage-2 = @CONF_CC_OPTS_STAGE2@ + +conf-cpp-args-stage-0 = @CONF_CPP_OPTS_STAGE0@ +conf-cpp-args-stage-1 = @CONF_CPP_OPTS_STAGE1@ +conf-cpp-args-stage-2 = @CONF_CPP_OPTS_STAGE2@ + +conf-gcc-linker-args-stage-0 = @CONF_GCC_LINKER_OPTS_STAGE0@ +conf-gcc-linker-args-stage-1 = @CONF_GCC_LINKER_OPTS_STAGE1@ +conf-gcc-linker-args-stage-2 = @CONF_GCC_LINKER_OPTS_STAGE2@ + +conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ +conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ +conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ + +iconv-include-dirs = @ICONV_INCLUDE_DIRS@ +iconv-lib-dirs = @ICONV_LIB_DIRS@ + +gmp-include-dirs = @GMP_INCLUDE_DIRS@ +gmp-lib-dirs = @GMP_LIB_DIRS@ + +lax-dependencies = NO +dynamic-ghc-programs = NO +gcc-is-clang = @GccIsClang@ +gcc-lt-46 = @GccLT46@ + + + +host-os-cpp = @HostOS_CPP@ \ No newline at end of file diff --git a/user.config b/user.config new file mode 100644 index 0000000..313d39a --- /dev/null +++ b/user.config @@ -0,0 +1 @@ +lax-dependencies = YES From git at git.haskell.org Thu Oct 26 23:44:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build program executables directly in inplace/bin. (663ad01) Message-ID: <20171026234400.5A8693A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/663ad019699389006a2c99e9f17c92bd53ea4e22/ghc >--------------------------------------------------------------- commit 663ad019699389006a2c99e9f17c92bd53ea4e22 Author: Andrey Mokhov Date: Mon Dec 21 02:56:49 2015 +0000 Build program executables directly in inplace/bin. >--------------------------------------------------------------- 663ad019699389006a2c99e9f17c92bd53ea4e22 cfg/system.config.in | 20 ++++++++++---------- src/Base.hs | 7 ++++++- src/Builder.hs | 1 + src/GHC.hs | 30 ++++++++++++------------------ src/Rules.hs | 5 +++-- src/Settings/Builders/GhcCabal.hs | 3 ++- 6 files changed, 34 insertions(+), 32 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 9de3166..6c21f6e 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -5,29 +5,29 @@ #=================== system-ghc = @WithGhc@ -ghc-stage1 = @hardtop@/inplace/bin/ghc-stage1 -ghc-stage2 = @hardtop@/inplace/bin/ghc-stage2 -ghc-stage3 = @hardtop@/inplace/bin/ghc-stage3 +ghc-stage1 = inplace/bin/ghc-stage1 +ghc-stage2 = inplace/bin/ghc-stage2 +ghc-stage3 = inplace/bin/ghc-stage3 system-gcc = @CC_STAGE0@ gcc = @WhatGccIsCalled@ system-ghc-pkg = @GhcPkgCmd@ -ghc-pkg = @hardtop@/inplace/bin/ghc-pkg +ghc-pkg = inplace/bin/ghc-pkg -ghc-cabal = @hardtop@/inplace/bin/ghc-cabal +ghc-cabal = inplace/bin/ghc-cabal -haddock = @hardtop@/inplace/bin/haddock +haddock = inplace/bin/haddock -hsc2hs = @hardtop@/inplace/bin/hsc2hs +hsc2hs = inplace/bin/hsc2hs -genprimopcode = @hardtop@/inplace/bin/genprimopcode +genprimopcode = inplace/bin/genprimopcode hs-cpp = @HaskellCPPCmd@ hs-cpp-args = @HaskellCPPArgs@ -unlit = @hardtop@/inplace/lib/unlit -ghc-split = @hardtop@/inplace/lib/ghc-split +unlit = inplace/lib/unlit +ghc-split = inplace/lib/ghc-split ld = @LdCmd@ ar = @ArCmd@ diff --git a/src/Base.hs b/src/Base.hs index 009e197..834f589 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -17,7 +17,8 @@ module Base ( module Development.Shake.Util, -- * Paths - shakeFilesPath, configPath, bootPackageConstraints, packageDependencies, + shakeFilesPath, configPath, programInplacePath, + bootPackageConstraints, packageDependencies, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, @@ -56,6 +57,10 @@ shakeFilesPath = shakePath -/- ".db" configPath :: FilePath configPath = shakePath -/- "cfg" +-- TODO: shall we read this from system.config instead? +programInplacePath :: FilePath +programInplacePath = "inplace/bin" + bootPackageConstraints :: FilePath bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" diff --git a/src/Builder.hs b/src/Builder.hs index f15054d..4d41d0a 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -66,6 +66,7 @@ builderKey builder = case builder of Ld -> "ld" Unlit -> "unlit" +-- TODO: Paths to some builders should be determined using defaultProgramPath builderPath :: Builder -> Action FilePath builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ diff --git a/src/GHC.hs b/src/GHC.hs index 923fdf1..f47242a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -105,25 +105,19 @@ defaultTargetDirectory stage pkg | stage == Stage0 = "dist-boot" | otherwise = "dist-install" +-- TODO: simplify +-- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg - | pkg == compareSizes = program $ pkgName pkg - | pkg == deriveConstants = program $ pkgName pkg - | pkg == dllSplit = program $ pkgName pkg - | pkg == genapply = program $ pkgName pkg - | pkg == genprimopcode = program $ pkgName pkg - | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) - | pkg == ghcCabal = program $ pkgName pkg - | pkg == ghcPkg = program $ pkgName pkg - | pkg == ghcPwd = program $ pkgName pkg - | pkg == ghcTags = program $ pkgName pkg - | pkg == haddock = program $ pkgName pkg - | pkg == hsc2hs = program $ pkgName pkg - | pkg == hp2ps = program $ pkgName pkg - | pkg == hpcBin = program $ pkgName pkg - | pkg == mkUserGuidePart = program $ pkgName pkg - | pkg == runghc = program $ pkgName pkg - | otherwise = Nothing + | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) + | pkg == haddock = case stage of + Stage2 -> Just . inplaceProgram $ pkgName pkg + _ -> Nothing + | isProgram pkg = case stage of + Stage0 -> Just . inplaceProgram $ pkgName pkg + _ -> Just . installProgram $ pkgName pkg + | otherwise = Nothing where - program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg + inplaceProgram name = programInplacePath -/- name <.> exe + installProgram name = pkgPath pkg -/- defaultTargetDirectory stage pkg -/- "build/tmp" -/- name <.> exe diff --git a/src/Rules.hs b/src/Rules.hs index 55ff066..7d88de8 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,7 +5,8 @@ import Rules.Package import Rules.Resources import Settings --- generateTargets needs top-level build targets +-- TODO: not all program targets should be needed explicitly +-- | generateTargets needs top-level build targets generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do @@ -17,7 +18,7 @@ generateTargets = action $ do return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] return $ libTargets ++ programTargets - need $ reverse targets + need targets -- TODO: use stage 2 compiler for building stage 2 packages (instead of stage 1) packageRules :: Rules () diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 151cd5f..66f9239 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -184,9 +184,10 @@ withBuilderKey b = case b of -- Expression 'with Gcc' appends "--with-gcc=/path/to/gcc" and needs Gcc. with :: Builder -> Args with b = specified b ? do + top <- getSetting GhcSourcePath path <- getBuilderPath b lift $ needBuilder laxDependencies b - append [withBuilderKey b ++ path] + append [withBuilderKey b ++ top -/- path] withStaged :: (Stage -> Builder) -> Args withStaged sb = (with . sb) =<< getStage From git at git.haskell.org Thu Oct 26 23:44:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add mk-miner submodule. (8433156) Message-ID: <20171026234401.36AC63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84331560b9ae783af8ce83598b6e4c6ab92d4b8a/ghc >--------------------------------------------------------------- commit 84331560b9ae783af8ce83598b6e4c6ab92d4b8a Author: Andrey Mokhov Date: Wed Dec 24 02:06:09 2014 +0000 Add mk-miner submodule. >--------------------------------------------------------------- 84331560b9ae783af8ce83598b6e4c6ab92d4b8a .gitmodules | 3 +++ mk-miner | 1 + 2 files changed, 4 insertions(+) diff --git a/.gitmodules b/.gitmodules new file mode 100644 index 0000000..8f798aa --- /dev/null +++ b/.gitmodules @@ -0,0 +1,3 @@ +[submodule "mk-miner"] + path = mk-miner + url = https://github.com/snowleopard/mk-miner.git diff --git a/mk-miner b/mk-miner new file mode 160000 index 0000000..566cbc0 --- /dev/null +++ b/mk-miner @@ -0,0 +1 @@ +Subproject commit 566cbc0996a56cdc9297082aca13eb2fd3f64029 From git at git.haskell.org Thu Oct 26 23:44:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddocks to Base.hs (5a82579) Message-ID: <20171026234403.93B553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a8257902248c32409835ab47b89c3e1a38be2b1/ghc >--------------------------------------------------------------- commit 5a8257902248c32409835ab47b89c3e1a38be2b1 Author: David Luposchainsky Date: Wed Jan 6 16:00:06 2016 +0100 Add Haddocks to Base.hs >--------------------------------------------------------------- 5a8257902248c32409835ab47b89c3e1a38be2b1 src/Base.hs | 19 ++++++++++++++++--- 1 file changed, 16 insertions(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a116892..05686e0 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -180,7 +180,16 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg --- | Render the given set of lines in a nice box of ASCII +-- | Render the given set of lines in a nice box of ASCII. +-- +-- The minimum width and whether to use Unicode symbols are hardcoded in the +-- function's body. +-- +-- >>> renderBox (words "lorem ipsum") +-- /----------\ +-- | lorem | +-- | ipsum | +-- \----------/ renderBox :: [String] -> String renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) where @@ -215,11 +224,13 @@ renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot] -- +1 for each non-dash (= corner) char dashes = replicate (boxContentWidth + 2) dash --- Depending on Data.Bifunctor only for this function seems an overkill +-- Explicit definition to avoid dependency on Data.Bifunctor +-- | Bifunctor bimap. bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) --- Depending on Data.List.Ordered only for these two functions seems an overkill +-- Explicit definition to avoid dependency on Data.List.Ordered +-- | Difference of two ordered lists. minusOrd :: Ord a => [a] -> [a] -> [a] minusOrd [] _ = [] minusOrd xs [] = xs @@ -228,6 +239,8 @@ minusOrd (x:xs) (y:ys) = case compare x y of EQ -> minusOrd xs ys GT -> minusOrd (x:xs) ys +-- Explicit definition to avoid dependency on Data.List.Ordered +-- | Intersection of two ordered lists by a predicate. intersectOrd :: (a -> b -> Ordering) -> [a] -> [b] -> [a] intersectOrd cmp = loop where From git at git.haskell.org Thu Oct 26 23:44:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bootstrap ghc-cabal. (c98eebc) Message-ID: <20171026234404.863F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c98eebc43418a33618df317cd92472ac801618b2/ghc >--------------------------------------------------------------- commit c98eebc43418a33618df317cd92472ac801618b2 Author: Andrey Mokhov Date: Mon Dec 21 03:00:14 2015 +0000 Bootstrap ghc-cabal. >--------------------------------------------------------------- c98eebc43418a33618df317cd92472ac801618b2 src/Base.hs | 1 - src/Rules/Data.hs | 93 ++++++++++++++++++++++++-------------------- src/Rules/Program.hs | 22 ++++++----- src/Rules/Resources.hs | 4 +- src/Settings/Builders/Ghc.hs | 51 ++++++++++-------------- 5 files changed, 85 insertions(+), 86 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c98eebc43418a33618df317cd92472ac801618b2 From git at git.haskell.org Thu Oct 26 23:44:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve mk-miner submodule. (2a82120) Message-ID: <20171026234404.C91423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2a82120c2ec83683eaa273f87d1d2402606dea69/ghc >--------------------------------------------------------------- commit 2a82120c2ec83683eaa273f87d1d2402606dea69 Author: Andrey Mokhov Date: Thu Dec 25 14:41:26 2014 +0000 Improve mk-miner submodule. >--------------------------------------------------------------- 2a82120c2ec83683eaa273f87d1d2402606dea69 mk-miner | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk-miner b/mk-miner index 566cbc0..276425e 160000 --- a/mk-miner +++ b/mk-miner @@ -1 +1 @@ -Subproject commit 566cbc0996a56cdc9297082aca13eb2fd3f64029 +Subproject commit 276425ea44420f49ac34fd942c0dad84b0c0d332 From git at git.haskell.org Thu Oct 26 23:44:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing Haddock header (6cf7902) Message-ID: <20171026234407.00CA23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6cf79029f6b1f6a1014a3be1d75a7360373c35b3/ghc >--------------------------------------------------------------- commit 6cf79029f6b1f6a1014a3be1d75a7360373c35b3 Author: David Luposchainsky Date: Thu Jan 7 18:19:18 2016 +0100 Add missing Haddock header >--------------------------------------------------------------- 6cf79029f6b1f6a1014a3be1d75a7360373c35b3 src/Target.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Target.hs b/src/Target.hs index 152de3d..3992ce2 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -37,7 +37,7 @@ instance Monoid a => Monoid (ReaderT Target Action a) where mempty = return mempty mappend = liftM2 mappend --- A partially constructed Target with fields 'Stage' and 'Package' only. +-- | A partially constructed Target with fields 'Stage' and 'Package' only. -- 'PartialTarget's are used for generating build rules. data PartialTarget = PartialTarget Stage Package deriving (Eq, Show) @@ -83,7 +83,6 @@ fullTargetWithWay :: -> Target fullTargetWithWay pt b w srcs fs = (fullTarget pt b srcs fs) { way = w } --- Instances for storing in the Shake database instance Binary Target instance NFData Target instance Hashable Target From git at git.haskell.org Thu Oct 26 23:44:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move isLibrary to src/Package.hs, add isProgram. (5980218) Message-ID: <20171026234408.34FFC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/598021809c6822f8c30b13ad0f75719a465a1c27/ghc >--------------------------------------------------------------- commit 598021809c6822f8c30b13ad0f75719a465a1c27 Author: Andrey Mokhov Date: Mon Dec 21 03:00:38 2015 +0000 Move isLibrary to src/Package.hs, add isProgram. >--------------------------------------------------------------- 598021809c6822f8c30b13ad0f75719a465a1c27 src/Package.hs | 12 ++++++++++-- src/Settings.hs | 4 ---- 2 files changed, 10 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 574f01a..5b04b6d 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -4,8 +4,8 @@ module Package ( -- * Queries pkgCabalFile, matchPackageNames, - -- * Helpers for constructing 'Package's - setPath, topLevel, library, utility, setType + -- * Helpers for constructing and using 'Package's + setPath, topLevel, library, utility, setType, isLibrary, isProgram ) where import Base @@ -48,6 +48,14 @@ setPath pkg path = pkg { pkgPath = path } setType :: Package -> PackageType -> Package setType pkg ty = pkg { pkgType = ty } +isLibrary :: Package -> Bool +isLibrary (Package {pkgType=Library}) = True +isLibrary _ = False + +isProgram :: Package -> Bool +isProgram (Package {pkgType=Program}) = True +isProgram _ = False + instance Show Package where show = pkgName diff --git a/src/Settings.hs b/src/Settings.hs index 7a1ab72..fd7c14c 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -32,10 +32,6 @@ getPkgDataList key = lift . pkgDataList . key =<< getTargetPath programPath :: Stage -> Package -> Maybe FilePath programPath = userProgramPath -isLibrary :: Package -> Bool -isLibrary (Package {pkgType=Library}) = True -isLibrary _ = False - -- Find all Haskell source files for the current target. TODO: simplify. getPackageSources :: Expr [FilePath] getPackageSources = do From git at git.haskell.org Thu Oct 26 23:44:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Moved source files to src subdirectory. (6a7c214) Message-ID: <20171026234408.55B843A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a7c2146795131a667ce19c1926fbc0fbbd98ed5/ghc >--------------------------------------------------------------- commit 6a7c2146795131a667ce19c1926fbc0fbbd98ed5 Author: Andrey Mokhov Date: Thu Dec 25 17:51:49 2014 +0000 Moved source files to src subdirectory. >--------------------------------------------------------------- 6a7c2146795131a667ce19c1926fbc0fbbd98ed5 Base.hs => src/Base.hs | 0 Config.hs => src/Config.hs | 0 Main.hs => src/Main.hs | 0 Oracles.hs => src/Oracles.hs | 0 Package.hs => src/Package.hs | 0 Ways.hs => src/Ways.hs | 0 6 files changed, 0 insertions(+), 0 deletions(-) diff --git a/Base.hs b/src/Base.hs similarity index 100% rename from Base.hs rename to src/Base.hs diff --git a/Config.hs b/src/Config.hs similarity index 100% rename from Config.hs rename to src/Config.hs diff --git a/Main.hs b/src/Main.hs similarity index 100% rename from Main.hs rename to src/Main.hs diff --git a/Oracles.hs b/src/Oracles.hs similarity index 100% rename from Oracles.hs rename to src/Oracles.hs diff --git a/Package.hs b/src/Package.hs similarity index 100% rename from Package.hs rename to src/Package.hs diff --git a/Ways.hs b/src/Ways.hs similarity index 100% rename from Ways.hs rename to src/Ways.hs From git at git.haskell.org Thu Oct 26 23:44:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make imports fully qualified (2ba641b) Message-ID: <20171026234410.7EE923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ba641b3d7d4aa8a84ab96a847208a7e79760496/ghc >--------------------------------------------------------------- commit 2ba641b3d7d4aa8a84ab96a847208a7e79760496 Author: David Luposchainsky Date: Thu Jan 7 19:12:17 2016 +0100 Make imports fully qualified >--------------------------------------------------------------- 2ba641b3d7d4aa8a84ab96a847208a7e79760496 src/Main.hs | 37 ++++++++++++++++++------------------- 1 file changed, 18 insertions(+), 19 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index b30b38e..1710b39 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,30 +2,29 @@ module Main (main) where import Development.Shake -import qualified Base as B -import qualified Rules as R -import qualified Rules.Cabal as RCabal -import qualified Rules.Config as RConfig -import qualified Rules.Copy as RCopy -import qualified Rules.Generate as RGen -import qualified Rules.IntegerGmp as RInt -import qualified Rules.Libffi as RFfi -import qualified Rules.Oracles as ROracle +import qualified Base +import qualified Rules +import qualified Rules.Cabal +import qualified Rules.Config +import qualified Rules.Generate +import qualified Rules.IntegerGmp +import qualified Rules.Libffi +import qualified Rules.Oracles main :: IO () main = shakeArgs options rules where rules = mconcat - [ RCabal.cabalRules - , RConfig.configRules - , RCopy.copyRules - , R.generateTargets - , RGen.generateRules - , RFfi.libffiRules - , RInt.integerGmpRules - , ROracle.oracleRules - , R.packageRules ] + [ Rules.Cabal.cabalRules + , Rules.Config.configRules + , Rules.Generate.copyRules + , Rules.Generate.generateRules + , Rules.generateTargets + , Rules.IntegerGmp.integerGmpRules + , Rules.Libffi.libffiRules + , Rules.Oracles.oracleRules + , Rules.packageRules ] options = shakeOptions - { shakeFiles = B.shakeFilesPath + { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Thu Oct 26 23:44:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to source files. (23c7701) Message-ID: <20171026234412.548FB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23c7701c1fab401a45f707c9abac101c6be9ce56/ghc >--------------------------------------------------------------- commit 23c7701c1fab401a45f707c9abac101c6be9ce56 Author: Andrey Mokhov Date: Thu Dec 25 18:13:12 2014 +0000 Fix paths to source files. >--------------------------------------------------------------- 23c7701c1fab401a45f707c9abac101c6be9ce56 build.bat | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 5400131..8e3dba2 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,2 @@ @mkdir _shake 2> nul - at ghc --make Main.hs -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at ghc --make src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:44:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Document the provenance of the Main functions in the code rather than in comments (c573af0) Message-ID: <20171026234414.5622E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c573af06514bb073cb76918343303b9a2c043160/ghc >--------------------------------------------------------------- commit c573af06514bb073cb76918343303b9a2c043160 Author: Neil Mitchell Date: Thu Jan 7 18:30:03 2016 +0000 Document the provenance of the Main functions in the code rather than in comments >--------------------------------------------------------------- c573af06514bb073cb76918343303b9a2c043160 src/Main.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 07f14ea..0fe2ee3 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -9,15 +9,15 @@ import Rules.Oracles main :: IO () main = shakeArgs options $ do - cabalRules -- see Rules.Cabal - configRules -- see Rules.Config - copyRules -- see Rules.Generate - generateTargets -- see Rules - generateRules -- see Rules.Generate - libffiRules -- see Rules.Libffi - integerGmpRules -- see Rules.IntegerGmp - oracleRules -- see Rules.Oracles - packageRules -- see Rules + Rules.Cabal.cabalRules + Rules.Config.configRules + Rules.Generate.copyRules + Rules.generateTargets + Rules.Generate.generateRules + Rules.Libffi.libffiRules + Rules.IntegerGmp.integerGmpRules + Rules.Oracles.oracleRules + Rules.packageRules where options = shakeOptions { shakeFiles = shakeFilesPath From git at git.haskell.org Thu Oct 26 23:44:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove the generated 'configure' script from the repository. (8b10b13) Message-ID: <20171026234415.C2B6B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8b10b133351866f8fabd033d402c32613209f63f/ghc >--------------------------------------------------------------- commit 8b10b133351866f8fabd033d402c32613209f63f Author: Andrey Mokhov Date: Thu Dec 25 18:18:01 2014 +0000 Remove the generated 'configure' script from the repository. >--------------------------------------------------------------- 8b10b133351866f8fabd033d402c32613209f63f configure | 1 - 1 file changed, 1 deletion(-) diff --git a/configure b/configure deleted file mode 100644 index f51695b..0000000 --- a/configure +++ /dev/null @@ -1 +0,0 @@ -echo "Running fake configure generated at: Mon, Dec 22, 2014 2:15:52 PM..." From git at git.haskell.org Thu Oct 26 23:44:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build haddock and ghcTags in stage1 temporarily until stage2 is fixed. (c720083) Message-ID: <20171026234415.E79D33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c720083bc93c9b22719f2b94a3861598c594572c/ghc >--------------------------------------------------------------- commit c720083bc93c9b22719f2b94a3861598c594572c Author: Andrey Mokhov Date: Mon Dec 21 12:00:32 2015 +0000 Build haddock and ghcTags in stage1 temporarily until stage2 is fixed. >--------------------------------------------------------------- c720083bc93c9b22719f2b94a3861598c594572c src/GHC.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/GHC.hs b/src/GHC.hs index f47242a..f528052 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -106,11 +106,17 @@ defaultTargetDirectory stage pkg | otherwise = "dist-install" -- TODO: simplify +-- TODO: haddock and ghtTags should be built in stage2 only -- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == haddock = case stage of + Stage1 -> Just . inplaceProgram $ pkgName pkg + Stage2 -> Just . inplaceProgram $ pkgName pkg + _ -> Nothing + | pkg == ghcTags = case stage of + Stage1 -> Just . inplaceProgram $ pkgName pkg Stage2 -> Just . inplaceProgram $ pkgName pkg _ -> Nothing | isProgram pkg = case stage of From git at git.haskell.org Thu Oct 26 23:44:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert "Document the provenance of the Main functions in the code rather than in comments" (619f31e) Message-ID: <20171026234417.E61963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/619f31ec9fb5d7dac00582129d8722f514a54f3b/ghc >--------------------------------------------------------------- commit 619f31ec9fb5d7dac00582129d8722f514a54f3b Author: Andrey Mokhov Date: Thu Jan 7 20:16:57 2016 +0000 Revert "Document the provenance of the Main functions in the code rather than in comments" This reverts commit c573af06514bb073cb76918343303b9a2c043160. >--------------------------------------------------------------- 619f31ec9fb5d7dac00582129d8722f514a54f3b src/Main.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 0fe2ee3..07f14ea 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -9,15 +9,15 @@ import Rules.Oracles main :: IO () main = shakeArgs options $ do - Rules.Cabal.cabalRules - Rules.Config.configRules - Rules.Generate.copyRules - Rules.generateTargets - Rules.Generate.generateRules - Rules.Libffi.libffiRules - Rules.IntegerGmp.integerGmpRules - Rules.Oracles.oracleRules - Rules.packageRules + cabalRules -- see Rules.Cabal + configRules -- see Rules.Config + copyRules -- see Rules.Generate + generateTargets -- see Rules + generateRules -- see Rules.Generate + libffiRules -- see Rules.Libffi + integerGmpRules -- see Rules.IntegerGmp + oracleRules -- see Rules.Oracles + packageRules -- see Rules where options = shakeOptions { shakeFiles = shakeFilesPath From git at git.haskell.org Thu Oct 26 23:44:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix parallel build, clean up code. (6b358c3) Message-ID: <20171026234412.656023A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b358c3d68e5643d684e9a645160cb829948de47/ghc >--------------------------------------------------------------- commit 6b358c3d68e5643d684e9a645160cb829948de47 Author: Andrey Mokhov Date: Mon Dec 21 03:57:02 2015 +0000 Fix parallel build, clean up code. >--------------------------------------------------------------- 6b358c3d68e5643d684e9a645160cb829948de47 src/Oracles/PackageData.hs | 70 ++++++++++++++++++++++++---------------------- src/Rules/Data.hs | 3 +- src/Rules/Program.hs | 6 ++-- src/Settings/Packages.hs | 7 ++--- 4 files changed, 43 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 6b358c3d68e5643d684e9a645160cb829948de47 From git at git.haskell.org Thu Oct 26 23:44:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Stop tracking the generated 'configure' script. (dfd6b21) Message-ID: <20171026234419.73C883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfd6b21aefaffea5f1e9f263dd4b115f2ff73094/ghc >--------------------------------------------------------------- commit dfd6b21aefaffea5f1e9f263dd4b115f2ff73094 Author: Andrey Mokhov Date: Thu Dec 25 18:19:49 2014 +0000 Stop tracking the generated 'configure' script. >--------------------------------------------------------------- dfd6b21aefaffea5f1e9f263dd4b115f2ff73094 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 181ccc0..30e2546 100644 --- a/.gitignore +++ b/.gitignore @@ -2,3 +2,4 @@ *.hi _shake/ _build/ +configure From git at git.haskell.org Thu Oct 26 23:44:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Windows instructions (f2d3eb5) Message-ID: <20171026234419.8F30E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f2d3eb55eb6b2c1aaf6ccc995c03de0c3a330917/ghc >--------------------------------------------------------------- commit f2d3eb55eb6b2c1aaf6ccc995c03de0c3a330917 Author: Andrey Mokhov Date: Mon Dec 21 12:11:45 2015 +0000 Add Windows instructions >--------------------------------------------------------------- f2d3eb55eb6b2c1aaf6ccc995c03de0c3a330917 README.md | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/README.md b/README.md index 63673e3..8c81c13 100644 --- a/README.md +++ b/README.md @@ -19,3 +19,15 @@ $ ./configure $ make inplace/bin/ghc-cabal # This needs to be fixed $ shake-build/build.sh ``` + +On Windows, +``` +$ git clone --recursive git://git.haskell.org/ghc.git +$ cd ghc +$ git clone git://github.com/snowleopard/shaking-up-ghc shake-build +$ ./boot +$ ./configure --enable-tarballs-autodownload +$ make inplace/bin/ghc-cabal # This needs to be fixed +$ shake-build/build.bat +``` +Also see the Building GHC on Windows guide: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows. From git at git.haskell.org Thu Oct 26 23:44:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #122 from quchen/housekeeping (1690e0f) Message-ID: <20171026234421.5BEB13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1690e0fc7b5168c2a80079dd3c3822a27ded9841/ghc >--------------------------------------------------------------- commit 1690e0fc7b5168c2a80079dd3c3822a27ded9841 Merge: 619f31e 2ba641b Author: Andrey Mokhov Date: Thu Jan 7 20:17:40 2016 +0000 Merge pull request #122 from quchen/housekeeping Add documentation, small refactorings >--------------------------------------------------------------- 1690e0fc7b5168c2a80079dd3c3822a27ded9841 .travis.yml | 2 ++ src/Base.hs | 19 +++++++++++--- src/Expression.hs | 4 +-- src/GHC.hs | 23 +++++++++-------- src/Main.hs | 43 +++++++++++++++++-------------- src/Predicates.hs | 23 ++++++++++++----- src/Rules.hs | 33 ++++++++++++++---------- src/Stage.hs | 21 +++++++++++++-- src/Target.hs | 76 ++++++++++++++++++++++++++++++++----------------------- src/Way.hs | 37 +++++++++++++++++++++------ 10 files changed, 185 insertions(+), 96 deletions(-) From git at git.haskell.org Thu Oct 26 23:44:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove fake autoconf. (232891d) Message-ID: <20171026234422.D4A8D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/232891d32c497c3901495e3a53745dd68c859d38/ghc >--------------------------------------------------------------- commit 232891d32c497c3901495e3a53745dd68c859d38 Author: Andrey Mokhov Date: Fri Dec 26 22:12:42 2014 +0000 Remove fake autoconf. >--------------------------------------------------------------- 232891d32c497c3901495e3a53745dd68c859d38 autoconf | 2 -- 1 file changed, 2 deletions(-) diff --git a/autoconf b/autoconf deleted file mode 100644 index 99e5cb3..0000000 --- a/autoconf +++ /dev/null @@ -1,2 +0,0 @@ -echo "Running autoconf... (not really)" -echo "$(cat $(dirname $0)/configure.ac) $(date)...\"" > $(dirname $0)/configure From git at git.haskell.org Thu Oct 26 23:44:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a section on how to contribute (552f617) Message-ID: <20171026234422.EC30E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/552f6170baba7c06c500ed913d36a89dfec12262/ghc >--------------------------------------------------------------- commit 552f6170baba7c06c500ed913d36a89dfec12262 Author: Andrey Mokhov Date: Mon Dec 21 12:25:40 2015 +0000 Add a section on how to contribute >--------------------------------------------------------------- 552f6170baba7c06c500ed913d36a89dfec12262 README.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README.md b/README.md index 8c81c13..5d87bc4 100644 --- a/README.md +++ b/README.md @@ -31,3 +31,7 @@ $ make inplace/bin/ghc-cabal # This needs to be fixed $ shake-build/build.bat ``` Also see the Building GHC on Windows guide: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows. + +How to contribute +----------------- +The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note the codebase is very unstable at present and we expect a lot of further refactoring. Before attempting to fix any issue do make sure no one else is already working on it. The documentation is currently non-existent, but we will start addressing this once the codebase stabilises. From git at git.haskell.org Thu Oct 26 23:44:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing package Settings.Packages.Touchy. (39e1756) Message-ID: <20171026234424.C91363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39e17562d9f76f92cd63242a8c960ce1a9143f3f/ghc >--------------------------------------------------------------- commit 39e17562d9f76f92cd63242a8c960ce1a9143f3f Author: Andrey Mokhov Date: Thu Jan 7 22:31:45 2016 +0000 Add missing package Settings.Packages.Touchy. See #125. [skip ci] >--------------------------------------------------------------- 39e17562d9f76f92cd63242a8c960ce1a9143f3f shaking-up-ghc.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 9f2c80c..ab9f7bc 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -90,6 +90,7 @@ executable ghc-shake , Settings.Packages.IservBin , Settings.Packages.Rts , Settings.Packages.RunGhc + , Settings.Packages.Touchy , Settings.TargetDirectory , Settings.User , Settings.Ways From git at git.haskell.org Thu Oct 26 23:44:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Show instances. (31d8890) Message-ID: <20171026234426.E03383A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31d88906c1b734a5d2d0dd39b79415547a6affea/ghc >--------------------------------------------------------------- commit 31d88906c1b734a5d2d0dd39b79415547a6affea Author: Andrey Mokhov Date: Tue Dec 22 04:59:02 2015 +0000 Fix Show instances. >--------------------------------------------------------------- 31d88906c1b734a5d2d0dd39b79415547a6affea src/Oracles/Config/Setting.hs | 8 ++++---- src/Stage.hs | 6 ++---- src/Target.hs | 2 +- src/Way.hs | 1 + 4 files changed, 8 insertions(+), 9 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index fa62f97..8f0b1df 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -85,10 +85,10 @@ setting key = askConfig $ case key of settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of - ConfCcArgs stage -> "conf-cc-args-stage" ++ show stage - ConfCppArgs stage -> "conf-cpp-args-stage" ++ show stage - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show stage - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show stage + ConfCcArgs stage -> "conf-cc-args-stage" ++ show (fromEnum stage) + ConfCppArgs stage -> "conf-cpp-args-stage" ++ show (fromEnum stage) + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show (fromEnum stage) + ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show (fromEnum stage) GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" HsCppArgs -> "hs-cpp-args" diff --git a/src/Stage.hs b/src/Stage.hs index 3aca206..d474557 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -5,10 +5,8 @@ import Base import GHC.Generics (Generic) -- TODO: explain stages -data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum, Generic) - -instance Show Stage where - show = show . fromEnum +data Stage = Stage0 | Stage1 | Stage2 | Stage3 + deriving (Show, Eq, Ord, Enum, Generic) -- Instances for storing in the Shake database instance Binary Stage diff --git a/src/Target.hs b/src/Target.hs index c70790d..2060d04 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -37,7 +37,7 @@ instance Monoid a => Monoid (ReaderT Target Action a) where -- PartialTarget is a partially constructed Target with fields Stage and -- Package only. PartialTarget's are used for generating build rules. -data PartialTarget = PartialTarget Stage Package +data PartialTarget = PartialTarget Stage Package deriving Show -- Convert PartialTarget to Target assuming that unknown fields won't be used. fromPartial :: PartialTarget -> Target diff --git a/src/Way.hs b/src/Way.hs index 095bd52..28d1365 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -28,6 +28,7 @@ data WayUnit = Threaded | GranSim deriving (Eq, Enum) +-- TODO: get rid of non-derived Show instances instance Show WayUnit where show unit = case unit of Threaded -> "thr" From git at git.haskell.org Thu Oct 26 23:44:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove fake configure.ac. (42304f9) Message-ID: <20171026234426.CD3B53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/42304f98b15301c4a2feaa3ab80eb26399f8c404/ghc >--------------------------------------------------------------- commit 42304f98b15301c4a2feaa3ab80eb26399f8c404 Author: Andrey Mokhov Date: Fri Dec 26 22:34:15 2014 +0000 Remove fake configure.ac. >--------------------------------------------------------------- 42304f98b15301c4a2feaa3ab80eb26399f8c404 cfg/configure.ac | 1053 ++++++++++++++++++++++++++++++ cfg/default.config | 76 +++ cfg/default.config.in | 76 +++ default.config => cfg/default.config.was | 0 user.config => cfg/user.config | 0 configure.ac | 1 - 6 files changed, 1205 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 42304f98b15301c4a2feaa3ab80eb26399f8c404 From git at git.haskell.org Thu Oct 26 23:44:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (comments, whitespace). (cedbb79) Message-ID: <20171026234428.35C193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cedbb7953afda4348a27cdd0b96af895e84e34e6/ghc >--------------------------------------------------------------- commit cedbb7953afda4348a27cdd0b96af895e84e34e6 Author: Andrey Mokhov Date: Thu Jan 7 22:52:46 2016 +0000 Minor revision (comments, whitespace). [skip ci] >--------------------------------------------------------------- cedbb7953afda4348a27cdd0b96af895e84e34e6 src/Predicates.hs | 4 +++- src/Way.hs | 8 ++++---- 2 files changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index b5ce0cb..497fca5 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -61,6 +61,8 @@ notStage0 = notM stage0 notPackage :: Package -> Predicate notPackage = notM . package --- | TODO: Actually, we don't register compiler in some circumstances -- fix. +-- TODO: Actually, we don't register compiler in some circumstances -- fix. +-- | Do we need to run @ghc-pkg update@ on the currently built package? +-- See "Rules.Data". registerPackage :: Predicate registerPackage = return True diff --git a/src/Way.hs b/src/Way.hs index 9f7f12a..3b1f6c0 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -82,7 +82,7 @@ instance Eq Way where -- | Build with no 'WayUnit's at all. vanilla :: Way -vanilla = wayFromUnits [] +vanilla = wayFromUnits [] -- | Build with profiling. profiling :: Way @@ -90,14 +90,14 @@ profiling = wayFromUnits [Profiling] -- | Build with logging. logging :: Way -logging = wayFromUnits [Logging] +logging = wayFromUnits [Logging] -- | Build in parallel. parallel :: Way -parallel = wayFromUnits [Parallel] +parallel = wayFromUnits [Parallel] granSim :: Way -granSim = wayFromUnits [GranSim] +granSim = wayFromUnits [GranSim] -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? From git at git.haskell.org Thu Oct 26 23:44:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove generated default.config. (e4d24e1) Message-ID: <20171026234430.4D7983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4d24e1f0360dc8c2afd5614f0d27a98e93024cf/ghc >--------------------------------------------------------------- commit e4d24e1f0360dc8c2afd5614f0d27a98e93024cf Author: Andrey Mokhov Date: Fri Dec 26 22:35:20 2014 +0000 Remove generated default.config. >--------------------------------------------------------------- e4d24e1f0360dc8c2afd5614f0d27a98e93024cf default.config | 52 ---------------------------------------------------- 1 file changed, 52 deletions(-) diff --git a/default.config b/default.config deleted file mode 100644 index f821e7a..0000000 --- a/default.config +++ /dev/null @@ -1,52 +0,0 @@ -system-ghc = C:/msys64/usr/local/bin/ghc.exe -system-ghc-pkg = C:/msys64/usr/local/bin/ghc-pkg.exe - -ghc-cabal = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-cabal.exe -ghc-stage1 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage1.exe -ghc-stage2 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage2.exe -ghc-stage3 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage3.exe - -ghc-pkg = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-pkg.exe - -gcc = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/gcc.exe -ld = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ld.exe -ar = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ar.exe -alex = C:/msys64/usr/local/bin/alex.exe -happy = C:/msys64/usr/local/bin/happy.exe -hscolour = - -target-os = mingw32 -target-arch = x86_64 -target-platform-full = x86_64-unknown-mingw32 - -cross-compiling = NO - -conf-cc-args-stage-0 = -fno-stack-protector -conf-cc-args-stage-1 = -fno-stack-protector -conf-cc-args-stage-2 = -fno-stack-protector - -conf-cpp-args-stage-0 = -conf-cpp-args-stage-1 = -conf-cpp-args-stage-2 = - -conf-gcc-linker-args-stage-0 = -conf-gcc-linker-args-stage-1 = -conf-gcc-linker-args-stage-2 = - -conf-ld-linker-args-stage-0 = -conf-ld-linker-args-stage-1 = -conf-ld-linker-args-stage-2 = - -iconv-include-dirs = -iconv-lib-dirs = -gmp-include-dirs = -gmp-lib-dirs = - -lax-dependencies = NO -dynamic-ghc-programs = NO -gcc-is-clang = NO -gcc-lt-46 = NO - - - -host-os-cpp = mingw32 From git at git.haskell.org Thu Oct 26 23:44:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for turnWarningsIntoErrors in Settings/User.hs. (3d90d06) Message-ID: <20171026234430.6D89A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d90d06aa59af43da7edb79dbd930d6fa34c5b9f/ghc >--------------------------------------------------------------- commit 3d90d06aa59af43da7edb79dbd930d6fa34c5b9f Author: Andrey Mokhov Date: Tue Dec 22 05:00:31 2015 +0000 Add support for turnWarningsIntoErrors in Settings/User.hs. >--------------------------------------------------------------- 3d90d06aa59af43da7edb79dbd930d6fa34c5b9f src/Settings/User.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 4c7a5f4..e16fb27 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands + verboseCommands, turnWarningsIntoErrors ) where import Expression @@ -88,3 +88,7 @@ buildSystemConfigFile = False -- only, e.g.: verboseCommands = package ghcPrim verboseCommands :: Predicate verboseCommands = return False + +-- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. +turnWarningsIntoErrors :: Predicate +turnWarningsIntoErrors = return False From git at git.haskell.org Thu Oct 26 23:44:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build badges more informative (bf18da2) Message-ID: <20171026234431.996213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf18da2ffa30040b3a51949f8cf75f2fef09d2cd/ghc >--------------------------------------------------------------- commit bf18da2ffa30040b3a51949f8cf75f2fef09d2cd Author: Andrey Mokhov Date: Thu Jan 7 23:13:16 2016 +0000 Make build badges more informative [skip ci] >--------------------------------------------------------------- bf18da2ffa30040b3a51949f8cf75f2fef09d2cd README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 2259c0b..fe6a909 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Shaking up GHC ============== -[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Build status](https://ci.appveyor.com/api/projects/status/9er74sbnrkco98gb?svg=true&pendingText=Windows&passingText=Windows&failingText=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) As part of my 6-month research secondment to Microsoft Research in Cambridge From git at git.haskell.org Thu Oct 26 23:44:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move config files to cfg subdirectory. (e89924f) Message-ID: <20171026234434.5C9793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e89924f2e5871fe2b4011b9365ab2ba21083e669/ghc >--------------------------------------------------------------- commit e89924f2e5871fe2b4011b9365ab2ba21083e669 Author: Andrey Mokhov Date: Fri Dec 26 22:36:26 2014 +0000 Move config files to cfg subdirectory. >--------------------------------------------------------------- e89924f2e5871fe2b4011b9365ab2ba21083e669 default.config.in | 45 --------------------------------------------- user.config | 1 - 2 files changed, 46 deletions(-) diff --git a/default.config.in b/default.config.in deleted file mode 100644 index 4ab5e21..0000000 --- a/default.config.in +++ /dev/null @@ -1,45 +0,0 @@ -ghc-cabal = inplace/bin/ghc-cabal at exeext_host@ -ghc = @WithGhc@ -ghc-pkg = @GhcPkgCmd@ -gcc = @WhatGccIsCalled@ -ld = @LdCmd@ -ar = @ArCmd@ -alex = @AlexCmd@ -happy = @HappyCmd@ -hscolour = @HSCOLOUR@ -target-os = @TargetOS_CPP@ -target-arch = @TargetArch_CPP@ -target-platform-full = @TargetPlatformFull@ - -cross-compiling = @CrossCompiling@ - -conf-cc-args-stage-0 = @CONF_CC_OPTS_STAGE0@ -conf-cc-args-stage-1 = @CONF_CC_OPTS_STAGE1@ -conf-cc-args-stage-2 = @CONF_CC_OPTS_STAGE2@ - -conf-cpp-args-stage-0 = @CONF_CPP_OPTS_STAGE0@ -conf-cpp-args-stage-1 = @CONF_CPP_OPTS_STAGE1@ -conf-cpp-args-stage-2 = @CONF_CPP_OPTS_STAGE2@ - -conf-gcc-linker-args-stage-0 = @CONF_GCC_LINKER_OPTS_STAGE0@ -conf-gcc-linker-args-stage-1 = @CONF_GCC_LINKER_OPTS_STAGE1@ -conf-gcc-linker-args-stage-2 = @CONF_GCC_LINKER_OPTS_STAGE2@ - -conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ -conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ -conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ - -iconv-include-dirs = @ICONV_INCLUDE_DIRS@ -iconv-lib-dirs = @ICONV_LIB_DIRS@ - -gmp-include-dirs = @GMP_INCLUDE_DIRS@ -gmp-lib-dirs = @GMP_LIB_DIRS@ - -lax-dependencies = NO -dynamic-ghc-programs = NO -gcc-is-clang = @GccIsClang@ -gcc-lt-46 = @GccLT46@ - - - -host-os-cpp = @HostOS_CPP@ \ No newline at end of file diff --git a/user.config b/user.config deleted file mode 100644 index 313d39a..0000000 --- a/user.config +++ /dev/null @@ -1 +0,0 @@ -lax-dependencies = YES From git at git.haskell.org Thu Oct 26 23:44:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try fetching ghc-tarballs via stack exec. (ee94a7c) Message-ID: <20171026234435.0653F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee94a7ce968d9a5fe1674018af8d7a2f52e8bb12/ghc >--------------------------------------------------------------- commit ee94a7ce968d9a5fe1674018af8d7a2f52e8bb12 Author: Andrey Mokhov Date: Thu Jan 7 23:23:10 2016 +0000 Try fetching ghc-tarballs via stack exec. See #110. [skip ci] >--------------------------------------------------------------- ee94a7ce968d9a5fe1674018af8d7a2f52e8bb12 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7d5a0f8..79f3369 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -11,8 +11,8 @@ install: - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - bash -lc "mkdir -p /home/ghc/ghc-tarballs" - - bash -lc "cd /home/ghc && ./mk/get-win32-tarballs.sh download x86_64" + - cd C:\msys64\home\ghc + - stack exec -- mk/get-win32-tarballs.sh download x86_64 build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:44:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (eda28da) Message-ID: <20171026234438.2FC393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eda28da9f239b66ea1791d0ac9850cfae1232248/ghc >--------------------------------------------------------------- commit eda28da9f239b66ea1791d0ac9850cfae1232248 Author: Andrey Mokhov Date: Tue Dec 22 05:07:32 2015 +0000 Clean up. >--------------------------------------------------------------- eda28da9f239b66ea1791d0ac9850cfae1232248 src/Rules/Library.hs | 2 +- src/Settings.hs | 11 +++++------ 2 files changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 134e2be..ff5ce63 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -49,7 +49,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do putSuccess $ renderBox [ "Successfully built package library '" ++ pkgName pkg - ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." + ++ "' (" ++ show stage ++ ", way "++ show way ++ ")." , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." ] diff --git a/src/Settings.hs b/src/Settings.hs index fd7c14c..9a0e07d 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -53,26 +53,25 @@ getPackageSources = do return $ foundSources ++ fixGhcPrim generatedSources -- findModuleFiles scans a list of given directories and finds files matching a --- given extension pattern (e.g., "*hs") that correspond to modules of the --- currently built package. Missing module files are returned in a separate --- list. The returned pair contains the following: +-- given pattern (e.g., "*hs") that correspond to modules of the currently built +-- package. Missing module files are returned in a separate list. The returned +-- pair contains the following: -- * a list of found module files, with paths being relative to one of given -- directories, e.g. "codeGen/CodeGen/Platform.hs" for the compiler package. -- * a list of module files that have not been found, with paths being relative -- to the module directory, e.g. "CodeGen/Platform", and with no extension. findModuleFiles :: [FilePath] -> FilePattern -> Expr ([FilePath], [FilePath]) -findModuleFiles dirs extension = do +findModuleFiles dirs pattern = do modules <- getPkgDataList Modules let decodedMods = sort . map decodeModule $ modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedMods - matchExtension = (?==) ("*" <.> extension) result <- lift . fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do let fullDir = dir -/- mDir - files <- fmap (filter matchExtension) $ getDirectoryContents fullDir + files <- getDirectoryFiles fullDir [pattern] let cmp fe f = compare (dropExtension fe) f found = intersectOrd cmp files mFiles return (map (fullDir -/-) found, (mDir, map dropExtension found)) From git at git.haskell.org Thu Oct 26 23:44:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove generated file. (3dac5a5) Message-ID: <20171026234438.C0A8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3dac5a577f93267315681ba667562d2e5e525c82/ghc >--------------------------------------------------------------- commit 3dac5a577f93267315681ba667562d2e5e525c82 Author: Andrey Mokhov Date: Fri Dec 26 22:37:20 2014 +0000 Remove generated file. >--------------------------------------------------------------- 3dac5a577f93267315681ba667562d2e5e525c82 cfg/default.config | 76 -------------------------------------------------- cfg/default.config.was | 52 ---------------------------------- 2 files changed, 128 deletions(-) diff --git a/cfg/default.config b/cfg/default.config deleted file mode 100644 index 60fa290..0000000 --- a/cfg/default.config +++ /dev/null @@ -1,76 +0,0 @@ -# Paths to builders: -# ================== - -system-ghc = /usr/local/bin/ghc -system-ghc-pkg = /usr/local/bin/ghc-pkg - -ghc-cabal = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-cabal - -ghc-stage1 = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-stage1 -ghc-stage2 = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-stage2 -ghc-stage3 = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-stage3 - -ghc-pkg = C:/msys64/home/chEEtah/ghc/inplace/bin/ghc-pkg - -gcc = C:/msys64/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe -ld = C:/msys64/home/chEEtah/ghc/inplace/mingw/bin/ld.exe -ar = /mingw64/bin/ar -alex = /usr/local/bin/alex -happy = /usr/local/bin/happy -hscolour = - -# Information about builders: -#============================ - -gcc-is-clang = -gcc-lt-46 = NO - -# Build options: -#=============== - -lax-dependencies = NO -dynamic-ghc-programs = NO - -# Information about host and target systems: -# ========================================== - -target-os = mingw32 -target-arch = x86_64 -target-platform-full = x86_64-unknown-mingw32 - -host-os-cpp = mingw32 - -cross-compiling = NO - -# Compilation and linking flags: -#=============================== - -conf-cc-args-stage-0 = -fno-stack-protector -conf-cc-args-stage-1 = -fno-stack-protector -conf-cc-args-stage-2 = -fno-stack-protector - -conf-cpp-args-stage-0 = -conf-cpp-args-stage-1 = -conf-cpp-args-stage-2 = - -conf-gcc-linker-args-stage-0 = -conf-gcc-linker-args-stage-1 = -conf-gcc-linker-args-stage-2 = - -conf-ld-linker-args-stage-0 = -conf-ld-linker-args-stage-1 = -conf-ld-linker-args-stage-2 = - -# Include and library directories: -#================================= - -iconv-include-dirs = -iconv-lib-dirs = - -gmp-include-dirs = -gmp-lib-dirs = - - - - - diff --git a/cfg/default.config.was b/cfg/default.config.was deleted file mode 100644 index f821e7a..0000000 --- a/cfg/default.config.was +++ /dev/null @@ -1,52 +0,0 @@ -system-ghc = C:/msys64/usr/local/bin/ghc.exe -system-ghc-pkg = C:/msys64/usr/local/bin/ghc-pkg.exe - -ghc-cabal = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-cabal.exe -ghc-stage1 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage1.exe -ghc-stage2 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage2.exe -ghc-stage3 = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-stage3.exe - -ghc-pkg = C:/msys64/home/b-anmokh/ghc/inplace/bin/ghc-pkg.exe - -gcc = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/gcc.exe -ld = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ld.exe -ar = C:/msys64/home/b-anmokh/ghc/inplace/mingw/bin/ar.exe -alex = C:/msys64/usr/local/bin/alex.exe -happy = C:/msys64/usr/local/bin/happy.exe -hscolour = - -target-os = mingw32 -target-arch = x86_64 -target-platform-full = x86_64-unknown-mingw32 - -cross-compiling = NO - -conf-cc-args-stage-0 = -fno-stack-protector -conf-cc-args-stage-1 = -fno-stack-protector -conf-cc-args-stage-2 = -fno-stack-protector - -conf-cpp-args-stage-0 = -conf-cpp-args-stage-1 = -conf-cpp-args-stage-2 = - -conf-gcc-linker-args-stage-0 = -conf-gcc-linker-args-stage-1 = -conf-gcc-linker-args-stage-2 = - -conf-ld-linker-args-stage-0 = -conf-ld-linker-args-stage-1 = -conf-ld-linker-args-stage-2 = - -iconv-include-dirs = -iconv-lib-dirs = -gmp-include-dirs = -gmp-lib-dirs = - -lax-dependencies = NO -dynamic-ghc-programs = NO -gcc-is-clang = NO -gcc-lt-46 = NO - - - -host-os-cpp = mingw32 From git at git.haskell.org Thu Oct 26 23:44:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build rules for *.S sources, add rts/*.S files. (b6bb19c) Message-ID: <20171026234439.503433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6bb19c87edc0e36e1322af12622493a61f48386/ghc >--------------------------------------------------------------- commit b6bb19c87edc0e36e1322af12622493a61f48386 Author: Andrey Mokhov Date: Thu Jan 7 23:53:44 2016 +0000 Add build rules for *.S sources, add rts/*.S files. See #126. >--------------------------------------------------------------- b6bb19c87edc0e36e1322af12622493a61f48386 src/Rules/Data.hs | 11 ++++++++--- src/Rules/Dependencies.hs | 9 +++++---- 2 files changed, 13 insertions(+), 7 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 46072ce..de4f8c0 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -95,13 +95,18 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do ++ [ "posix" | not windows ] ++ [ "win32" | windows ] -- TODO: rts/dist/build/sm/Evac_thr.c, rts/dist/build/sm/Scav_thr.c - -- TODO: adding cmm sources to C_SRCS is a hack; rethink after #18 + -- TODO: adding cmm/S sources to C_SRCS is a hack; rethink after #18 cSrcs <- getDirectoryFiles (pkgPath pkg) (map (-/- "*.c") dirs) cmmSrcs <- getDirectoryFiles (pkgPath pkg) ["*.cmm"] - let extraSrcs = [ targetDirectory Stage1 rts -/- "build/AutoApply.cmm" ] + buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] + buildStgCRunAsm <- anyTargetArch ["powerpc64le"] + let sSrcs = [ "AdjustorAsm.S" | buildAdjustor ] + ++ [ "StgCRunAsm.S" | buildStgCRunAsm ] + extraSrcs = [ targetDirectory Stage1 rts -/- "build/AutoApply.cmm" ] includes <- interpretPartial target $ fromDiffExpr includesArgs let contents = unlines $ map (prefix++) - [ "C_SRCS = " ++ unwords (cSrcs ++ cmmSrcs ++ extraSrcs) + [ "C_SRCS = " + ++ unwords (cSrcs ++ cmmSrcs ++ sSrcs ++ extraSrcs) , "CC_OPTS = " ++ unwords includes , "COMPONENT_ID = " ++ "rts" ] writeFileChanged mk contents diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 79bcdb2..2da9549 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -15,10 +15,11 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = dropBuild = (pkgPath pkg ++) . drop (length buildPath) hDepFile = buildPath -/- ".hs-dependencies" in do - [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do - let srcFile = dropBuild . dropExtension $ out - need [srcFile] - build $ fullTarget target (GccM stage) [srcFile] [out] + fmap (buildPath++) + [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do + let srcFile = dropBuild . dropExtension $ out + need [srcFile] + build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources From git at git.haskell.org Thu Oct 26 23:44:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix tracking of *.hs-incl files. (363b227) Message-ID: <20171026234441.ADA953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/363b227e1e310561018c1991249cbf21bf28be57/ghc >--------------------------------------------------------------- commit 363b227e1e310561018c1991249cbf21bf28be57 Author: Andrey Mokhov Date: Tue Dec 22 05:09:27 2015 +0000 Fix tracking of *.hs-incl files. >--------------------------------------------------------------- 363b227e1e310561018c1991249cbf21bf28be57 src/Rules/Dependencies.hs | 40 +++++++++++++++++++--------------------- 1 file changed, 19 insertions(+), 21 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 996d927..47e6c6d 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -24,7 +24,24 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = hDepFile %> \file -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) $ need [platformH] - need srcs + -- TODO: very ugly and fragile; use gcc -MM instead? + let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] + need $ srcs ++ extraDeps if srcs == [] then writeFileChanged file "" else build $ fullTarget target (GhcM stage) srcs [file] @@ -36,23 +53,4 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need $ hDepFile : cDepFiles -- need all for more parallelism cDeps <- fmap concat $ mapM readFile' cDepFiles hDeps <- readFile' hDepFile - -- TODO: very ugly and fragile; use gcc -MM instead? - let hsIncl hs incl = buildPath -/- hs <.> "o" ++ " : " - ++ buildPath -/- incl ++ "\n" - extraDeps = if pkg /= compiler then [] else - hsIncl "PrelNames" "primop-vector-uniques.hs-incl" - ++ hsIncl "PrimOp" "primop-data-decl.hs-incl" - ++ hsIncl "PrimOp" "primop-tag.hs-incl" - ++ hsIncl "PrimOp" "primop-list.hs-incl" - ++ hsIncl "PrimOp" "primop-strictness.hs-incl" - ++ hsIncl "PrimOp" "primop-fixity.hs-incl" - ++ hsIncl "PrimOp" "primop-primop-info.hs-incl" - ++ hsIncl "PrimOp" "primop-out-of-line.hs-incl" - ++ hsIncl "PrimOp" "primop-has-side-effects.hs-incl" - ++ hsIncl "PrimOp" "primop-can-fail.hs-incl" - ++ hsIncl "PrimOp" "primop-code-size.hs-incl" - ++ hsIncl "PrimOp" "primop-commutable.hs-incl" - ++ hsIncl "TysPrim" "primop-vector-tys-exports.hs-incl" - ++ hsIncl "TysPrim" "primop-vector-tycons.hs-incl" - ++ hsIncl "TysPrim" "primop-vector-tys.hs-incl" - writeFileChanged file $ cDeps ++ hDeps ++ extraDeps + writeFileChanged file $ cDeps ++ hDeps From git at git.haskell.org Thu Oct 26 23:44:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve naming convention for build directories: always use stageN. (52ecf6c) Message-ID: <20171026234434.881A73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/52ecf6cb909644928ed754f5b111034ecb9dafc3/ghc >--------------------------------------------------------------- commit 52ecf6cb909644928ed754f5b111034ecb9dafc3 Author: Andrey Mokhov Date: Tue Dec 22 05:05:11 2015 +0000 Improve naming convention for build directories: always use stageN. >--------------------------------------------------------------- 52ecf6cb909644928ed754f5b111034ecb9dafc3 src/GHC.hs | 18 ++---------------- src/Rules.hs | 3 +-- src/Rules/Data.hs | 20 ++++++++++---------- src/Rules/Program.hs | 18 ++++++++++-------- src/Settings/Builders/Ghc.hs | 2 ++ src/Settings/Builders/GhcCabal.hs | 23 ++++++++++------------- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Packages.hs | 2 ++ 8 files changed, 38 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 52ecf6cb909644928ed754f5b111034ecb9dafc3 From git at git.haskell.org Thu Oct 26 23:44:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Specify path to stack. (9ad20c9) Message-ID: <20171026234443.043C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ad20c9a77dd8655d53bc1e0f512794876df8741/ghc >--------------------------------------------------------------- commit 9ad20c9a77dd8655d53bc1e0f512794876df8741 Author: Andrey Mokhov Date: Thu Jan 7 23:57:57 2016 +0000 Specify path to stack. See #110. [skip ci] >--------------------------------------------------------------- 9ad20c9a77dd8655d53bc1e0f512794876df8741 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 79f3369..9e1ed1e 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -12,7 +12,7 @@ install: - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - - stack exec -- mk/get-win32-tarballs.sh download x86_64 + - C:\stack exec -- mk/get-win32-tarballs.sh download x86_64 build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:44:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for autoconf/configure chain. (7d90047) Message-ID: <20171026234442.7B71D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d90047a4fad755726ba70cc7f9506512008b96f/ghc >--------------------------------------------------------------- commit 7d90047a4fad755726ba70cc7f9506512008b96f Author: Andrey Mokhov Date: Fri Dec 26 22:38:42 2014 +0000 Add support for autoconf/configure chain. >--------------------------------------------------------------- 7d90047a4fad755726ba70cc7f9506512008b96f cfg/default.config.in | 9 ++------- src/Base.hs | 1 + src/Config.hs | 18 ++++++++++-------- src/Oracles.hs | 44 ++++++++++++++++++++++++++++++++++---------- 4 files changed, 47 insertions(+), 25 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index c01bb87..d3617f4 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -1,5 +1,5 @@ # Paths to builders: -# ================== +#=================== system-ghc = @WithGhc@ system-ghc-pkg = @GhcPkgCmd@ @@ -32,7 +32,7 @@ lax-dependencies = NO dynamic-ghc-programs = NO # Information about host and target systems: -# ========================================== +#=========================================== target-os = @TargetOS_CPP@ target-arch = @TargetArch_CPP@ @@ -69,8 +69,3 @@ iconv-lib-dirs = @ICONV_LIB_DIRS@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ - - - - - diff --git a/src/Base.hs b/src/Base.hs index 7e130c2..e44b3bb 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -5,6 +5,7 @@ module Base ( module Development.Shake.FilePath, module Control.Applicative, module Data.Monoid, + module Data.List, Stage (..), Args, arg, Condition, joinArgs, joinArgsWithSpaces, diff --git a/src/Config.hs b/src/Config.hs index a370f38..3d26482 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -1,5 +1,5 @@ module Config ( - autoconfRules, configureRules + autoconfRules, configureRules, cfgPath ) where import Development.Shake @@ -9,16 +9,18 @@ import Development.Shake.Rule import Control.Applicative import Control.Monad import Base -import Oracles + +cfgPath :: FilePath +cfgPath = "shake" "cfg" autoconfRules :: Rules () autoconfRules = do - "shake/configure" %> \out -> do - need ["shake/configure.ac"] - cmd $ "bash shake/autoconf" + "configure" %> \out -> do + copyFile' (cfgPath "configure.ac") "configure.ac" + cmd "bash autoconf" configureRules :: Rules () configureRules = do - "shake/default.config" %> \out -> do - need ["shake/default.config.in", "shake/configure"] - cmd $ "bash shake/configure" + cfgPath "default.config" %> \out -> do + need [cfgPath "default.config.in", "configure"] + cmd "bash configure" diff --git a/src/Oracles.hs b/src/Oracles.hs index 9138780..971d5c6 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -20,7 +20,9 @@ import qualified System.Directory as System import qualified Data.HashMap.Strict as M import qualified Prelude import Prelude hiding (not, (&&), (||)) +import Data.Char import Base +import Config data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage @@ -40,10 +42,18 @@ path builder = do Ghc Stage3 -> "ghc-stage3" GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) - askConfigWithDefault key $ + cfgPath <- askConfigWithDefault key $ error $ "\nCannot find path to '" ++ key ++ "' in configuration files." + let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" + windows <- test WindowsHost + if (windows && "/" `isPrefixOf` cfgPathExe) + then do + root <- option Root + return $ root ++ cfgPathExe + else + return cfgPathExe argPath :: Builder -> Args argPath builder = do @@ -53,7 +63,7 @@ argPath builder = do -- Explain! -- TODO: document change in behaviour (LaxDeps) needBuilder :: Builder -> Action () -needBuilder ghc @ (Ghc _) = do +needBuilder ghc @ (Ghc stage) = do target <- path ghc laxDeps <- test LaxDeps -- TODO: get rid of test? if laxDeps then orderOnly [target] else need [target] @@ -88,9 +98,18 @@ run builder args = do data Option = TargetOS | TargetArch | TargetPlatformFull | ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage | IconvIncludeDirs | IconvLibDirs | GmpIncludeDirs | GmpLibDirs - | HostOsCpp + | HostOsCpp | Root option :: Option -> Action String +option Root = do + windows <- test WindowsHost + if (windows) + then do + Stdout out <- cmd ["cygpath", "-m", "/"] + return $ dropWhileEnd isSpace out + else + return "/" + option opt = askConfig $ case opt of TargetOS -> "target-os" TargetArch -> "target-arch" @@ -112,6 +131,7 @@ argOption opt = do data Flag = LaxDeps | Stage1Only | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs | GccIsClang | GccLt46 | CrossCompiling | Validating | PlatformSupportsSharedLibs + | WindowsHost test :: Flag -> Action Bool test GhcWithInterpreter = do @@ -130,6 +150,10 @@ test HsColourSrcs = do hscolour <- path HsColour return $ hscolour /= "" +test WindowsHost = do + hostOsCpp <- option HostOsCpp + return $ hostOsCpp `elem` ["mingw32", "cygwin32"] + test flag = do (key, defaultValue) <- return $ case flag of LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file @@ -230,19 +254,19 @@ askConfig key = askConfigWithDefault key $ error $ "\nCannot find key '" oracleRules :: Rules () oracleRules = do cfg <- newCache $ \() -> do - unless (doesFileExist "shake/default.config") $ do + unless (doesFileExist $ cfgPath "default.config.in") $ do error $ "\nDefault configuration file '" - ++ "shake/default.config.in" + ++ (cfgPath "default.config.in") ++ "' is missing; unwilling to proceed." return () - need ["shake/default.config"] - cfgDefault <- liftIO $ readConfigFile "shake/default.config" - existsUser <- doesFileExist "shake/user.config" + need [cfgPath "default.config"] + cfgDefault <- liftIO $ readConfigFile $ cfgPath "default.config" + existsUser <- doesFileExist $ cfgPath "user.config" cfgUser <- if existsUser - then liftIO $ readConfigFile "shake/user.config" + then liftIO $ readConfigFile $ cfgPath "user.config" else do putLoud $ "\nUser defined configuration file '" - ++ "shake/user.config" + ++ (cfgPath "user.config") ++ "' is missing; proceeding with default configuration.\n" return M.empty return $ cfgUser `M.union` cfgDefault From git at git.haskell.org Thu Oct 26 23:44:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy *.hs-boot files of generated sources. (4e2f6c5) Message-ID: <20171026234445.6B5FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e2f6c504a541f7a6eab6eb072bae265d67e5bff/ghc >--------------------------------------------------------------- commit 4e2f6c504a541f7a6eab6eb072bae265d67e5bff Author: Andrey Mokhov Date: Tue Dec 22 05:10:46 2015 +0000 Copy *.hs-boot files of generated sources. >--------------------------------------------------------------- 4e2f6c504a541f7a6eab6eb072bae265d67e5bff src/Rules/Generate.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 53b7dd6..10a4e6b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -29,11 +29,12 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = buildPath = path -/- "build" primopsTxt = targetPath stage compiler -/- "build/primops.txt" platformH = targetPath stage compiler -/- "ghc_boot_platform.h" - in do -- TODO: do we need to copy *.(l)hs-boot files here? Never happens? - buildPath -/- "*.hs" %> \file -> do + generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) + in do + generated ?> \file -> do dirs <- interpretPartial target $ getPkgDataList SrcDirs files <- getDirectoryFiles "" $ - [ packagePath -/- d -/- takeBaseName file <.> "*" | d <- dirs ] + [ packagePath -/- d ++ "//" ++ takeBaseName file <.> "*" | d <- dirs ] let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ "Exactly one generator expected for " ++ file @@ -41,6 +42,9 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = let (src, builder) = head gens need [src] build $ fullTarget target builder [src] [file] + let srcBoot = src -<.> "hs-boot" + whenM (doesFileExist srcBoot) $ + copyFileChanged srcBoot $ file -<.> "hs-boot" when (pkg == compiler) $ primopsTxt %> \file -> do need [platformH, primopsSource] @@ -80,7 +84,7 @@ quote :: String -> String quote s = "\"" ++ s ++ "\"" -- TODO: do we need ghc-split? Always or is it platform specific? --- TODO: add tracking +-- TODO: add tracking by moving these functions to separate tracked files generateConfigHs :: Expr String generateConfigHs = do cProjectName <- getSetting ProjectName From git at git.haskell.org Thu Oct 26 23:44:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generated default.config to .gitignore. (371842e) Message-ID: <20171026234446.50FB03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/371842eb16a529d8bb1bae756369f5422e011032/ghc >--------------------------------------------------------------- commit 371842eb16a529d8bb1bae756369f5422e011032 Author: Andrey Mokhov Date: Fri Dec 26 22:57:49 2014 +0000 Add generated default.config to .gitignore. >--------------------------------------------------------------- 371842eb16a529d8bb1bae756369f5422e011032 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 30e2546..375b257 100644 --- a/.gitignore +++ b/.gitignore @@ -2,4 +2,4 @@ *.hi _shake/ _build/ -configure +cfg/default.config From git at git.haskell.org Thu Oct 26 23:44:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add init script, fix path to stak. (23ef499) Message-ID: <20171026234446.D9B6E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23ef49931f9e0970746cd603c46e4a996438d27e/ghc >--------------------------------------------------------------- commit 23ef49931f9e0970746cd603c46e4a996438d27e Author: Andrey Mokhov Date: Fri Jan 8 01:18:48 2016 +0000 Add init script, fix path to stak. See #110. [skip ci] >--------------------------------------------------------------- 23ef49931f9e0970746cd603c46e4a996438d27e .appveyor.yml | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 9e1ed1e..5ad5f0b 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,6 +1,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -install: +init: + - cd - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 @@ -9,12 +10,13 @@ install: - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc + +install: - cd C:\msys64\home\ghc - - C:\stack exec -- mk/get-win32-tarballs.sh download x86_64 + - shake-build\stack.exe exec -- mk/get-win32-tarballs.sh download x86_64 build_script: - - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo \"\" | ./configure" - - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" + - bash -lc "./boot" + - bash -lc "echo \"\" | ./configure" + - bash -lc "./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:44:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove a duplicate success message when building Lib0. (bfe72a5) Message-ID: <20171026234448.EE5BD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bfe72a5f9fa4aa31bf9e83ad690aef6b8741f8e6/ghc >--------------------------------------------------------------- commit bfe72a5f9fa4aa31bf9e83ad690aef6b8741f8e6 Author: Andrey Mokhov Date: Tue Dec 22 05:25:01 2015 +0000 Remove a duplicate success message when building Lib0. >--------------------------------------------------------------- bfe72a5f9fa4aa31bf9e83ad690aef6b8741f8e6 src/Rules/Library.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index ff5ce63..12102c0 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -41,17 +41,17 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do let objs = cObjs ++ splitObjs ++ eObjs asuf <- libsuf way - if ("//*-0" <.> asuf) ?== a + let isLib0 = ("//*-0" <.> asuf) ?== a + if isLib0 then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls else build $ fullTarget target Ar objs [a] synopsis <- interpretPartial target $ getPkgData Synopsis - putSuccess $ renderBox + unless isLib0 . putSuccess $ renderBox [ "Successfully built package library '" ++ pkgName pkg ++ "' (" ++ show stage ++ ", way "++ show way ++ ")." - , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." - ] + , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." ] -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. From git at git.haskell.org Thu Oct 26 23:44:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a comment to user.config explaining its purpose. (ced1860) Message-ID: <20171026234449.C651D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ced186037fe9c0ad8c5ac1d191318b52d57dfac8/ghc >--------------------------------------------------------------- commit ced186037fe9c0ad8c5ac1d191318b52d57dfac8 Author: Andrey Mokhov Date: Fri Dec 26 22:58:30 2014 +0000 Add a comment to user.config explaining its purpose. >--------------------------------------------------------------- ced186037fe9c0ad8c5ac1d191318b52d57dfac8 cfg/user.config | 3 +++ 1 file changed, 3 insertions(+) diff --git a/cfg/user.config b/cfg/user.config index 313d39a..b72c5b4 100644 --- a/cfg/user.config +++ b/cfg/user.config @@ -1 +1,4 @@ +# Override default settings (stored in default.config file): +#=========================================================== + lax-dependencies = YES From git at git.haskell.org Thu Oct 26 23:44:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add APPVEYOR_BUILD_FOLDER to PATH, show versions of key binaries. (782e998) Message-ID: <20171026234450.5A06F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/782e99878b0a669aaa585b84531a089e68502f26/ghc >--------------------------------------------------------------- commit 782e99878b0a669aaa585b84531a089e68502f26 Author: Andrey Mokhov Date: Fri Jan 8 01:31:18 2016 +0000 Add APPVEYOR_BUILD_FOLDER to PATH, show versions of key binaries. See #110. [skip ci] >--------------------------------------------------------------- 782e99878b0a669aaa585b84531a089e68502f26 .appveyor.yml | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 5ad5f0b..136bee6 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -9,12 +9,16 @@ init: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ + - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc install: - cd C:\msys64\home\ghc - - shake-build\stack.exe exec -- mk/get-win32-tarballs.sh download x86_64 + - stack exec -- mk/get-win32-tarballs.sh download x86_64 + - ghc --version + - stack --version + - alex --version + - happy --version build_script: - bash -lc "./boot" From git at git.haskell.org Thu Oct 26 23:44:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement encodeModule -- the inverse for decodeModule. (ba41ded) Message-ID: <20171026234452.CFB413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba41dedc0c632836dff3c3ce55f7210d344e44e7/ghc >--------------------------------------------------------------- commit ba41dedc0c632836dff3c3ce55f7210d344e44e7 Author: Andrey Mokhov Date: Wed Dec 23 06:12:19 2015 +0000 Implement encodeModule -- the inverse for decodeModule. >--------------------------------------------------------------- ba41dedc0c632836dff3c3ce55f7210d344e44e7 src/Base.hs | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index ac457ad..79ce119 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -25,9 +25,8 @@ module Base ( module System.Console.ANSI, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, - removeFileIfExists, - replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, + bimap, minusOrd, intersectOrd, removeFileIfExists, replaceEq, chunksOfSize, + replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-) ) where import Control.Applicative @@ -78,12 +77,18 @@ replaceSeparators = replaceIf isPathSeparator replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) --- | Given a module name extract the directory and file names, e.g.: +-- | Given a module name extract the directory and file name, e.g.: -- -- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") decodeModule :: String -> (FilePath, String) decodeModule = splitFileName . replaceEq '.' '/' +-- | Given the directory and file name find the corresponding module name, e.g.: +-- +-- > encodeModule "Data/Functor/" "Identity.hs" = "Data.Functor.Identity" +encodeModule :: FilePath -> String -> String +encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file + -- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx From git at git.haskell.org Thu Oct 26 23:44:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant imports, add TODO's. (fe2655b) Message-ID: <20171026234453.AC0153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fe2655b6cd60d09311e87e1aa8736a3bbd847d9b/ghc >--------------------------------------------------------------- commit fe2655b6cd60d09311e87e1aa8736a3bbd847d9b Author: Andrey Mokhov Date: Fri Dec 26 23:04:07 2014 +0000 Remove redundant imports, add TODO's. >--------------------------------------------------------------- fe2655b6cd60d09311e87e1aa8736a3bbd847d9b src/Config.hs | 10 ++-------- 1 file changed, 2 insertions(+), 8 deletions(-) diff --git a/src/Config.hs b/src/Config.hs index 3d26482..b4f0519 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -2,12 +2,6 @@ module Config ( autoconfRules, configureRules, cfgPath ) where -import Development.Shake -import Development.Shake.Command -import Development.Shake.FilePath -import Development.Shake.Rule -import Control.Applicative -import Control.Monad import Base cfgPath :: FilePath @@ -17,10 +11,10 @@ autoconfRules :: Rules () autoconfRules = do "configure" %> \out -> do copyFile' (cfgPath "configure.ac") "configure.ac" - cmd "bash autoconf" + cmd "bash autoconf" -- TODO: get rid of 'bash' configureRules :: Rules () configureRules = do cfgPath "default.config" %> \out -> do need [cfgPath "default.config.in", "configure"] - cmd "bash configure" + cmd "bash configure" -- TODO: get rid of 'bash' From git at git.haskell.org Thu Oct 26 23:44:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clone ghc into ghc/tmp. (2fd5c6e) Message-ID: <20171026234454.3398D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2fd5c6e03952155a73d39fbfe925606d8d99fbfe/ghc >--------------------------------------------------------------- commit 2fd5c6e03952155a73d39fbfe925606d8d99fbfe Author: Andrey Mokhov Date: Fri Jan 8 01:58:26 2016 +0000 Clone ghc into ghc/tmp. See #110. [skip ci] >--------------------------------------------------------------- 2fd5c6e03952155a73d39fbfe925606d8d99fbfe .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 136bee6..ef66eb7 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -4,13 +4,14 @@ init: - cd - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% + - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" install: - cd C:\msys64\home\ghc From git at git.haskell.org Thu Oct 26 23:44:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (ecdeae7) Message-ID: <20171026234456.550723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ecdeae76f0a89eec2f95a5285f174ef6ef107329/ghc >--------------------------------------------------------------- commit ecdeae76f0a89eec2f95a5285f174ef6ef107329 Author: Andrey Mokhov Date: Wed Dec 23 06:13:11 2015 +0000 Clean up. >--------------------------------------------------------------- ecdeae76f0a89eec2f95a5285f174ef6ef107329 src/Oracles/WindowsRoot.hs | 2 +- src/Rules/Data.hs | 26 +++++++++++++------------- 2 files changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 51cb516..2ec13c7 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -14,7 +14,7 @@ windowsRoot = askOracle $ WindowsRoot () -- the root is slow (at least the current implementation). windowsRootOracle :: Rules () windowsRootOracle = do - root <- newCache $ \() -> do + root <- newCache $ \_ -> do Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] let root = dropWhileEnd isSpace out putOracle $ "Detected root on Windows: " ++ root diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 96deed9..26755ca 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -44,19 +44,19 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- TODO: code duplication around ghcIncludeDirs priority 2.0 $ do when (pkg == hp2ps) $ dataFile %> \mk -> do - let cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" - , "Reorder.c", "TopTwenty.c", "AuxFile.c", "Deviation.c" - , "HpFile.c", "Marks.c", "Scale.c", "TraceElement.c" - , "Axes.c", "Dimensions.c", "Key.c", "PsFile.c" - , "Shade.c", "Utilities.c" ] - contents = unlines - [ "utils_hp2ps_stage0_PROGNAME = hp2ps" - , "utils_hp2ps_stage0_C_SRCS = " ++ unwords cSrcs - , "utils_hp2ps_stage0_INSTALL = YES" - , "utils_hp2ps_stage0_INSTALL_INPLACE = YES" - , "utils_hp2ps_stage0_DEP_EXTRA_LIBS = m" - , "utils_hp2ps_stage0_CC_OPTS = " - ++ unwords (map ("-I"++) ghcIncludeDirs) ] + let prefix = "utils_hp2ps_stage" ++ show (fromEnum stage) ++ "_" + cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" + , "Reorder.c", "TopTwenty.c", "AuxFile.c" + , "Deviation.c", "HpFile.c", "Marks.c", "Scale.c" + , "TraceElement.c", "Axes.c", "Dimensions.c", "Key.c" + , "PsFile.c", "Shade.c", "Utilities.c" ] + contents = unlines $ map (prefix++) + [ "PROGNAME = hp2ps" + , "C_SRCS = " ++ unwords cSrcs + , "INSTALL = YES" + , "INSTALL_INPLACE = YES" + , "DEP_EXTRA_LIBS = m" + , "CC_OPTS = " ++ unwords (map ("-I"++) ghcIncludeDirs) ] writeFileChanged mk contents putBuild $ "| Successfully generated '" ++ mk ++ "'." From git at git.haskell.org Thu Oct 26 23:44:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant imports, drop Stage1Only. (428e148) Message-ID: <20171026234457.28E143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/428e148afb2a043419f3be83c56e05489b4e5efe/ghc >--------------------------------------------------------------- commit 428e148afb2a043419f3be83c56e05489b4e5efe Author: Andrey Mokhov Date: Fri Dec 26 23:05:12 2014 +0000 Remove redundant imports, drop Stage1Only. >--------------------------------------------------------------- 428e148afb2a043419f3be83c56e05489b4e5efe src/Oracles.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 971d5c6..08d668e 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -12,11 +12,10 @@ module Oracles ( oracleRules ) where -import Development.Shake.Config import Development.Shake.Rule +import Development.Shake.Config import Development.Shake.Classes import Control.Monad hiding (when, unless) -import qualified System.Directory as System import qualified Data.HashMap.Strict as M import qualified Prelude import Prelude hiding (not, (&&), (||)) @@ -129,7 +128,7 @@ argOption opt = do opt' <- option opt arg [opt'] -data Flag = LaxDeps | Stage1Only | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs +data Flag = LaxDeps | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs | GccIsClang | GccLt46 | CrossCompiling | Validating | PlatformSupportsSharedLibs | WindowsHost @@ -157,7 +156,6 @@ test WindowsHost = do test flag = do (key, defaultValue) <- return $ case flag of LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file - Stage1Only -> ("stage-1-only" , False) -- TODO: target only DynamicGhcPrograms -> ("dynamic-ghc-programs", False) GccIsClang -> ("gcc-is-clang" , False) GccLt46 -> ("gcc-lt-46" , False) From git at git.haskell.org Thu Oct 26 23:44:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:44:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop init script. (cd567f7) Message-ID: <20171026234457.B96A93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cd567f71ec9ba2b0eb0b3232b4b375df23557354/ghc >--------------------------------------------------------------- commit cd567f71ec9ba2b0eb0b3232b4b375df23557354 Author: Andrey Mokhov Date: Fri Jan 8 02:22:05 2016 +0000 Drop init script. See #110. [skip ci] >--------------------------------------------------------------- cd567f71ec9ba2b0eb0b3232b4b375df23557354 .appveyor.yml | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index ef66eb7..f663d96 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,6 +1,6 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -init: +install: - cd - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% @@ -12,9 +12,6 @@ init: - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - -install: - - cd C:\msys64\home\ghc - stack exec -- mk/get-win32-tarballs.sh download x86_64 - ghc --version - stack --version From git at git.haskell.org Thu Oct 26 23:45:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement ModuleFiles oracle for caching the search of module files of a package. (cf825fe) Message-ID: <20171026234500.13F763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf825feba28b287a8e3eee00eee543d4c5b5e8fe/ghc >--------------------------------------------------------------- commit cf825feba28b287a8e3eee00eee543d4c5b5e8fe Author: Andrey Mokhov Date: Wed Dec 23 06:14:11 2015 +0000 Implement ModuleFiles oracle for caching the search of module files of a package. >--------------------------------------------------------------- cf825feba28b287a8e3eee00eee543d4c5b5e8fe src/Oracles/ModuleFiles.hs | 96 ++++++++++++++++++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 7 ++-- src/Rules/Oracles.hs | 6 ++- src/Settings.hs | 55 +++++--------------------- 4 files changed, 113 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 cf825feba28b287a8e3eee00eee543d4c5b5e8fe From git at git.haskell.org Thu Oct 26 23:45:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make C:/msys64/ a silent command. (4d2b4bc) Message-ID: <20171026234501.101603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4d2b4bcce29e1a476dcbe0055319c7586e75d8ec/ghc >--------------------------------------------------------------- commit 4d2b4bcce29e1a476dcbe0055319c7586e75d8ec Author: Andrey Mokhov Date: Fri Dec 26 23:38:28 2014 +0000 Make C:/msys64/ a silent command. >--------------------------------------------------------------- 4d2b4bcce29e1a476dcbe0055319c7586e75d8ec src/Oracles.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 08d668e..e03d6a3 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -104,7 +104,7 @@ option Root = do windows <- test WindowsHost if (windows) then do - Stdout out <- cmd ["cygpath", "-m", "/"] + Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] return $ dropWhileEnd isSpace out else return "/" From git at git.haskell.org Thu Oct 26 23:45:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot & configure via stack exec. (8c9544a) Message-ID: <20171026234501.8440E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c9544add5c72545c98e7b5cb43aa7d0db35590d/ghc >--------------------------------------------------------------- commit 8c9544add5c72545c98e7b5cb43aa7d0db35590d Author: Andrey Mokhov Date: Fri Jan 8 02:51:51 2016 +0000 Run boot & configure via stack exec. See #110. [skip ci] >--------------------------------------------------------------- 8c9544add5c72545c98e7b5cb43aa7d0db35590d .appveyor.yml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f663d96..8333761 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,17 +8,18 @@ install: - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - stack exec -- pacman -S --noconfirm gcc binutils p7zip git + - stack exec -- pacman -S --noconfirm perl gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - stack exec -- mk/get-win32-tarballs.sh download x86_64 + - cd C:\msys64\home\ghc + - stack exec -- perl boot + - stack exec -- configure --enable-tarballs-autodownload - ghc --version - stack --version - alex --version - happy --version build_script: - - bash -lc "./boot" - - bash -lc "echo \"\" | ./configure" + - cd - bash -lc "./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:45:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (a5a12ec) Message-ID: <20171026234503.8FDEC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a12ec621ad8461cf80cf91fcbf583919358d70/ghc >--------------------------------------------------------------- commit a5a12ec621ad8461cf80cf91fcbf583919358d70 Author: Moritz Angermann Date: Wed Dec 23 14:59:44 2015 +0800 Update README.md Adding missing prerequisites. These are probably installed if you build ghc often or use shake, but if not, these are missing. >--------------------------------------------------------------- a5a12ec621ad8461cf80cf91fcbf583919358d70 README.md | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/README.md b/README.md index 5d87bc4..05e247e 100644 --- a/README.md +++ b/README.md @@ -8,6 +8,12 @@ This is supposed to go into the `shake-build` directory of the GHC source tree. Trying it --------- +Prerequisits +``` +$ cabal install alex +$ cabal install shake +``` + On Linux, ``` $ git clone git://git.haskell.org/ghc From git at git.haskell.org Thu Oct 26 23:45:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update to the latest GHC source tree. (a58a713) Message-ID: <20171026234504.AED123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a58a7132c1bdd47dc79e28a4fef01b090e5a88c0/ghc >--------------------------------------------------------------- commit a58a7132c1bdd47dc79e28a4fef01b090e5a88c0 Author: Andrey Mokhov Date: Sat Dec 27 23:42:56 2014 +0000 Update to the latest GHC source tree. >--------------------------------------------------------------- a58a7132c1bdd47dc79e28a4fef01b090e5a88c0 cfg/configure.ac | 122 ++++++++++++++++++++++++++++++++----------------------- 1 file changed, 71 insertions(+), 51 deletions(-) diff --git a/cfg/configure.ac b/cfg/configure.ac index b31d1b3..125fd49 100644 --- a/cfg/configure.ac +++ b/cfg/configure.ac @@ -13,7 +13,7 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.9], [glasgow-haskell-bugs at haskell.org], [ghc]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.11], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO : ${RELEASE=NO} @@ -187,56 +187,6 @@ AC_SUBST([WithGhc]) dnl ** Without optimization some INLINE trickery fails for GHCi SRC_CC_OPTS="-O" -dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. -dnl Unfortunately we don't know whether the user is going to request a -dnl build with the LLVM backend as this is only given in build.mk. -dnl -dnl Instead, we try to do as much work as possible here, checking -dnl whether -fllvm is the stage 0 compiler's default. If so we -dnl fail. If not, we check whether -fllvm is affected explicitly and -dnl if so set a flag. The build system will later check this flag -dnl after the desired build flags are known. -AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) -echo "main = putStrLn \"%function\"" > conftestghc.hs - -# Check whether LLVM backend is default for this platform -"${WithGhc}" conftestghc.hs 2>&1 >/dev/null -res=`./conftestghc` -if test "x$res" == "x%object" -then - AC_MSG_RESULT(yes) - echo "Buggy bootstrap compiler" - echo "" - echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" - echo "and therefore will miscompile the LLVM backend if -fllvm is" - echo "used." - echo - echo "Please use another bootstrap compiler" - exit 1 -fi - -# -fllvm is not the default, but set a flag so the Makefile can check -# -for it in the build flags later on -"${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null -if test $? == 0 -then - res=`./conftestghc` - if test "x$res" == "x%object" - then - AC_MSG_RESULT(yes) - GHC_LLVM_AFFECTED_BY_9439=1 - elif test "x$res" == "x%function" - then - AC_MSG_RESULT(no) - GHC_LLVM_AFFECTED_BY_9439=0 - else - AC_MSG_WARN(unexpected output $res) - fi -else - AC_MSG_RESULT(failed to compile, assuming no) -fi -AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) - dnl-------------------------------------------------------------------- dnl * Choose host(/target/build) platform dnl-------------------------------------------------------------------- @@ -593,6 +543,59 @@ dnl -------------------------------------------------------------- dnl * General configuration checks dnl -------------------------------------------------------------- +dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. +dnl Unfortunately we don't know whether the user is going to request a +dnl build with the LLVM backend as this is only given in build.mk. +dnl +dnl Instead, we try to do as much work as possible here, checking +dnl whether -fllvm is the stage 0 compiler's default. If so we +dnl fail. If not, we check whether -fllvm is affected explicitly and +dnl if so set a flag. The build system will later check this flag +dnl after the desired build flags are known. +if test -n "$LlcCmd" && test -n "$OptCmd" +then + AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) + echo "main = putStrLn \"%function\"" > conftestghc.hs + + # Check whether LLVM backend is default for this platform + "${WithGhc}" conftestghc.hs 2>&1 >/dev/null + res=`./conftestghc` + if test "x$res" = "x%object" + then + AC_MSG_RESULT(yes) + echo "Buggy bootstrap compiler" + echo "" + echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" + echo "and therefore will miscompile the LLVM backend if -fllvm is" + echo "used." + echo + echo "Please use another bootstrap compiler" + exit 1 + fi + + # -fllvm is not the default, but set a flag so the Makefile can check + # -for it in the build flags later on + "${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null + if test $? = 0 + then + res=`./conftestghc` + if test "x$res" = "x%object" + then + AC_MSG_RESULT(yes) + GHC_LLVM_AFFECTED_BY_9439=1 + elif test "x$res" = "x%function" + then + AC_MSG_RESULT(no) + GHC_LLVM_AFFECTED_BY_9439=0 + else + AC_MSG_WARN(unexpected output $res) + fi + else + AC_MSG_RESULT(failed to compile, assuming no) + fi +fi +AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) + dnl ** Can the unix package be built? dnl -------------------------------------------------------------- @@ -896,6 +899,22 @@ AC_TRY_LINK_FUNC(printf\$LDBLStub, [Define to 1 if we have printf$LDBLStub (Apple Mac OS >= 10.4, PPC).]) ]) +dnl ** pthread_setname_np is a recent addition to glibc, and OS X has +dnl a different single-argument version. +AC_CHECK_LIB(pthread, pthread_setname_np) +AC_MSG_CHECKING(for pthread_setname_np) +AC_TRY_LINK( +[ +#define _GNU_SOURCE +#include +], +[pthread_setname_np(pthread_self(), "name");], + AC_MSG_RESULT(yes) + AC_DEFINE([HAVE_PTHREAD_SETNAME_NP], [1], + [Define to 1 if you have the glibc version of pthread_setname_np]), + AC_MSG_RESULT(no) +) + dnl ** check for eventfd which is needed by the I/O manager AC_CHECK_HEADERS([sys/eventfd.h]) AC_CHECK_FUNCS([eventfd]) @@ -986,6 +1005,7 @@ echo [" Configure completed successfully. Building GHC version : $ProjectVersion + Git commit id : $ProjectGitCommitId Build platform : $BuildPlatform Host platform : $HostPlatform From git at git.haskell.org Thu Oct 26 23:45:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't reinstall perl. (efeb163) Message-ID: <20171026234505.CB7F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efeb163633b8e2f9c2e551da13fff7b7c750578c/ghc >--------------------------------------------------------------- commit efeb163633b8e2f9c2e551da13fff7b7c750578c Author: Andrey Mokhov Date: Fri Jan 8 02:55:38 2016 +0000 Don't reinstall perl. See #110. [skip ci] >--------------------------------------------------------------- efeb163633b8e2f9c2e551da13fff7b7c750578c .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 8333761..2a4a628 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,7 +8,7 @@ install: - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - stack exec -- pacman -S --noconfirm perl gcc binutils p7zip git + - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Thu Oct 26 23:45:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #25 from angerman/patch-1 (0153864) Message-ID: <20171026234507.2019A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0153864864ac88a314b3fbfb4e681e0ea6ab1451/ghc >--------------------------------------------------------------- commit 0153864864ac88a314b3fbfb4e681e0ea6ab1451 Merge: cf825fe a5a12ec Author: Andrey Mokhov Date: Wed Dec 23 11:26:34 2015 +0000 Merge pull request #25 from angerman/patch-1 Update README.md >--------------------------------------------------------------- 0153864864ac88a314b3fbfb4e681e0ea6ab1451 README.md | 6 ++++++ 1 file changed, 6 insertions(+) From git at git.haskell.org Thu Oct 26 23:45:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update build-package-data.docx to match Package.hs (8a93116) Message-ID: <20171026234508.50E813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8a9311684390d4cb8a07d9c1521021769546caff/ghc >--------------------------------------------------------------- commit 8a9311684390d4cb8a07d9c1521021769546caff Author: Andrey Mokhov Date: Sun Dec 28 03:32:49 2014 +0000 Update build-package-data.docx to match Package.hs >--------------------------------------------------------------- 8a9311684390d4cb8a07d9c1521021769546caff doc/build-package-data.docx | Bin 15964 -> 16519 bytes 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/doc/build-package-data.docx b/doc/build-package-data.docx index c2637c9..a2708cc 100644 Binary files a/doc/build-package-data.docx and b/doc/build-package-data.docx differ From git at git.haskell.org Thu Oct 26 23:45:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to configure. (c6d3c5e) Message-ID: <20171026234509.6E9C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6d3c5eedbd3257c75b5fbd31fe8cea3dcfa0c05/ghc >--------------------------------------------------------------- commit c6d3c5eedbd3257c75b5fbd31fe8cea3dcfa0c05 Author: Andrey Mokhov Date: Fri Jan 8 03:23:31 2016 +0000 Fix path to configure. See #110. [skip ci] >--------------------------------------------------------------- c6d3c5eedbd3257c75b5fbd31fe8cea3dcfa0c05 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 2a4a628..82cdce4 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,7 +14,7 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - stack exec -- configure --enable-tarballs-autodownload + - stack exec -- ./configure --enable-tarballs-autodownload - ghc --version - stack --version - alex --version From git at git.haskell.org Thu Oct 26 23:45:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revisions (add comments, move Condition to Oracles.hs). (618d90d) Message-ID: <20171026234511.EC0633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/618d90dc2bc41256a18c42776d701a9a4fc23d26/ghc >--------------------------------------------------------------- commit 618d90dc2bc41256a18c42776d701a9a4fc23d26 Author: Andrey Mokhov Date: Sun Dec 28 03:33:55 2014 +0000 Minor revisions (add comments, move Condition to Oracles.hs). >--------------------------------------------------------------- 618d90dc2bc41256a18c42776d701a9a4fc23d26 src/Base.hs | 4 +--- src/Oracles.hs | 21 +++++++++++++-------- 2 files changed, 14 insertions(+), 11 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index e44b3bb..b4ea8cb 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,7 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, Condition, + Args, arg, joinArgs, joinArgsWithSpaces, filterOut, ) where @@ -22,8 +22,6 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) type Args = Action [String] -type Condition = Action Bool - instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q diff --git a/src/Oracles.hs b/src/Oracles.hs index e03d6a3..9ceb121 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,5 +1,5 @@ {-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, DeriveGeneric, ConstraintKinds #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} module Oracles ( module Control.Monad, @@ -8,7 +8,7 @@ module Oracles ( Builder (..), Flag (..), Option (..), path, with, run, argPath, option, argOption, - test, when, unless, not, (&&), (||), + Condition, test, when, unless, not, (&&), (||), oracleRules ) where @@ -50,7 +50,7 @@ path builder = do if (windows && "/" `isPrefixOf` cfgPathExe) then do root <- option Root - return $ root ++ cfgPathExe + return $ root ++ (drop 1 $ cfgPathExe) else return cfgPathExe @@ -59,19 +59,22 @@ argPath builder = do path <- path builder arg [path] --- Explain! --- TODO: document change in behaviour (LaxDeps) +-- When LaxDeps flag is set (by adding 'lax-dependencies = YES' to user.config), +-- dependencies on the GHC executable are turned into order-only dependencies to +-- avoid needless recompilation when making changes to GHC's sources. In certain +-- situations this can lead to build failures, in which case you should reset +-- the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do target <- path ghc - laxDeps <- test LaxDeps -- TODO: get rid of test? + laxDeps <- test LaxDeps if laxDeps then orderOnly [target] else need [target] needBuilder builder = do target <- path builder need [target] --- 'with Gcc' generates --with-gcc=/usr/bin/gcc and needs it +-- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder with :: Builder -> Args with builder = do let prefix = case builder of @@ -163,7 +166,7 @@ test flag = do Validating -> ("validating" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ - do putLoud $ "\nFlag '" + do putLoud $ "\nFlag '" -- TODO: Give the warning *only once* per key ++ key ++ "' not set in configuration files. " ++ "Proceeding with default value '" @@ -172,6 +175,8 @@ test flag = do return defaultString return $ value == "YES" +type Condition = Action Bool + class ToCondition a where toCondition :: a -> Condition From git at git.haskell.org Thu Oct 26 23:45:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try bash within stack to run configure. (01b7eed) Message-ID: <20171026234513.075423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/01b7eed7be12304e71952ce3345b8244f1c6bd8e/ghc >--------------------------------------------------------------- commit 01b7eed7be12304e71952ce3345b8244f1c6bd8e Author: Andrey Mokhov Date: Fri Jan 8 03:49:14 2016 +0000 Try bash within stack to run configure. See #110. [skip ci] >--------------------------------------------------------------- 01b7eed7be12304e71952ce3345b8244f1c6bd8e .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 82cdce4..c9ec4fd 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,7 +14,7 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - stack exec -- ./configure --enable-tarballs-autodownload + - stack exec -- bash -lc "./configure --enable-tarballs-autodownload" - ghc --version - stack --version - alex --version From git at git.haskell.org Thu Oct 26 23:45:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename "shaking-up-ghc" to "Shaking up GHC" (02dfa6d) Message-ID: <20171026234514.429113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02dfa6dc8e89cf450baf01b4541ab33bbaffebda/ghc >--------------------------------------------------------------- commit 02dfa6dc8e89cf450baf01b4541ab33bbaffebda Author: Andrey Mokhov Date: Wed Dec 23 13:11:40 2015 +0000 Rename "shaking-up-ghc" to "Shaking up GHC" >--------------------------------------------------------------- 02dfa6dc8e89cf450baf01b4541ab33bbaffebda LICENSE | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/LICENSE b/LICENSE index 20d201e..a78df02 100644 --- a/LICENSE +++ b/LICENSE @@ -11,7 +11,7 @@ modification, are permitted provided that the following conditions are met: this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. -* Neither the name of shaking-up-ghc nor the names of its +* Neither the name of Shaking up GHC nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. From git at git.haskell.org Thu Oct 26 23:45:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -fwarn-tabs and -fwarn-unused-imports. (7eb2d38) Message-ID: <20171026234515.559F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7eb2d388f236b8759046b1d58e89cbf9088e4940/ghc >--------------------------------------------------------------- commit 7eb2d388f236b8759046b1d58e89cbf9088e4940 Author: Andrey Mokhov Date: Mon Dec 29 21:43:26 2014 +0000 Add -fwarn-tabs and -fwarn-unused-imports. >--------------------------------------------------------------- 7eb2d388f236b8759046b1d58e89cbf9088e4940 build.bat | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 8e3dba2..0e1f581 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,3 @@ @mkdir _shake 2> nul - at ghc --make src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build + at _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:45:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring bash configure back. (29ce56c) Message-ID: <20171026234516.7F3D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/29ce56c97cc414b2a3e66e4b44dff829a8660a47/ghc >--------------------------------------------------------------- commit 29ce56c97cc414b2a3e66e4b44dff829a8660a47 Author: Andrey Mokhov Date: Fri Jan 8 04:13:50 2016 +0000 Bring bash configure back. See #110. [skip ci] >--------------------------------------------------------------- 29ce56c97cc414b2a3e66e4b44dff829a8660a47 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index c9ec4fd..bb01556 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,7 +14,7 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - stack exec -- bash -lc "./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e6522794e13767080c1add1e304fce960f0e1cd/ghc >--------------------------------------------------------------- commit 7e6522794e13767080c1add1e304fce960f0e1cd Author: Ben Gamari Date: Fri Dec 18 18:05:20 2015 +0100 Make PackageName into a proper newtype >--------------------------------------------------------------- 7e6522794e13767080c1add1e304fce960f0e1cd src/GHC.hs | 7 ++++--- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Package.hs | 30 +++++++++++++++++++++--------- src/Rules/Cabal.hs | 12 ++++++------ src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 4 ++-- src/Settings/TargetDirectory.hs | 3 ++- 11 files changed, 42 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 7e6522794e13767080c1add1e304fce960f0e1cd From git at git.haskell.org Thu Oct 26 23:45:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build/autogen/Paths_library.hs to ghc-cabal results. (3bbb9fb) Message-ID: <20171026234518.BF19E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3bbb9fba477a7c84e2e615712a12046fda14d8b9/ghc >--------------------------------------------------------------- commit 3bbb9fba477a7c84e2e615712a12046fda14d8b9 Author: Andrey Mokhov Date: Mon Dec 29 21:51:22 2014 +0000 Add build/autogen/Paths_library.hs to ghc-cabal results. >--------------------------------------------------------------- 3bbb9fba477a7c84e2e615712a12046fda14d8b9 src/Package.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Package.hs b/src/Package.hs index 8d7311b..f5eae9b 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -120,7 +120,8 @@ buildPackageData pkg @ (Package name path todo) (stage, dist, settings) = "haddock-prologue.txt", "inplace-pkg-config", "setup-config", - "build" "autogen" "cabal_macros.h" + "build" "autogen" "cabal_macros.h", + "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? What's up with Paths_cpsa.hs? ] &%> \_ -> do need [path name <.> "cabal"] when (doesFileExist $ path "configure.ac") $ need [path "configure"] From git at git.haskell.org Thu Oct 26 23:45:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use mingw64_shell.bat for running scripts. (75063f0) Message-ID: <20171026234520.0815A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/75063f04ab2d93494366e80cbc17d02094ac1703/ghc >--------------------------------------------------------------- commit 75063f04ab2d93494366e80cbc17d02094ac1703 Author: Andrey Mokhov Date: Fri Jan 8 16:47:17 2016 +0000 Use mingw64_shell.bat for running scripts. See #110. [skip ci] >--------------------------------------------------------------- 75063f04ab2d93494366e80cbc17d02094ac1703 .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index bb01556..1d4bb53 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -3,7 +3,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" install: - cd - set MSYSTEM=MINGW64 - - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% + - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\bin;C:\msys64;%PATH% - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe @@ -14,7 +14,8 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bfd3d3240107fe70cc0ca806aafab1398c9e25ee/ghc >--------------------------------------------------------------- commit bfd3d3240107fe70cc0ca806aafab1398c9e25ee Author: David Luposchainsky Date: Tue Dec 22 08:54:35 2015 +0100 Parallelize+optimize compilation of build system (-j -O) >--------------------------------------------------------------- bfd3d3240107fe70cc0ca806aafab1398c9e25ee build.sh | 1 + 1 file changed, 1 insertion(+) diff --git a/build.sh b/build.sh index 1918cdd..f09c30c 100755 --- a/build.sh +++ b/build.sh @@ -13,6 +13,7 @@ ghc \ -rtsopts \ -with-rtsopts=-I0 \ -outputdir="$root/.shake" \ + -j -O \ -o "$root/.shake/build" "$root/.shake/build" \ From git at git.haskell.org Thu Oct 26 23:45:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add replaceChar helper function. (1fa4aa5) Message-ID: <20171026234522.3A2963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fa4aa517a6e1334b276539204b41367fbff8a51/ghc >--------------------------------------------------------------- commit 1fa4aa517a6e1334b276539204b41367fbff8a51 Author: Andrey Mokhov Date: Tue Dec 30 03:52:56 2014 +0000 Add replaceChar helper function. >--------------------------------------------------------------- 1fa4aa517a6e1334b276539204b41367fbff8a51 src/Base.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index b4ea8cb..eaebaf3 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -10,6 +10,7 @@ module Base ( Args, arg, joinArgs, joinArgsWithSpaces, filterOut, + replaceChar ) where import Development.Shake hiding ((*>)) @@ -42,3 +43,8 @@ joinArgs = intercalateArgs "" filterOut :: Args -> [String] -> Args filterOut args list = filter (`notElem` list) <$> args + +replaceChar :: Char -> Char -> String -> String +replaceChar from to = (go from) . if from == '/' then go '\\' else id + where + go from' = map (\c -> if c == from' then to else c) From git at git.haskell.org Thu Oct 26 23:45:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to use get-win32-tarballs.sh. (4a625f8) Message-ID: <20171026234523.7AA803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a625f8aa2358597281a6b2633fdb40f9f8c2707/ghc >--------------------------------------------------------------- commit 4a625f8aa2358597281a6b2633fdb40f9f8c2707 Author: Andrey Mokhov Date: Fri Jan 8 17:03:55 2016 +0000 Try to use get-win32-tarballs.sh. See #110. [skip ci] >--------------------------------------------------------------- 4a625f8aa2358597281a6b2633fdb40f9f8c2707 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 1d4bb53..f0014e3 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,8 +14,8 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - mingw64_shell.bat "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/828bc3a27a26a02e1bad68ef0c25d7d3a1ce64fd/ghc >--------------------------------------------------------------- commit 828bc3a27a26a02e1bad68ef0c25d7d3a1ce64fd Author: David Luposchainsky Date: Mon Dec 21 13:46:03 2015 +0100 Avoid common shell scripting pitfalls - Get bash from $PATH instead of reading it from /bin/bash (useful for e.g. NixOS) - set -euo pipefail: "strict bash mode" - Quote all paths to be whitespace compatible - GHC uses --make mode automatically >--------------------------------------------------------------- 828bc3a27a26a02e1bad68ef0c25d7d3a1ce64fd build.sh | 26 +++++++++++++++++++++----- 1 file changed, 21 insertions(+), 5 deletions(-) diff --git a/build.sh b/build.sh index d350779..1918cdd 100755 --- a/build.sh +++ b/build.sh @@ -1,6 +1,22 @@ -#!/bin/bash -e +#!/usr/bin/env bash -root=`dirname $0` -mkdir -p $root/.shake -ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/.shake -o $root/.shake/build -$root/.shake/build --lint --directory $root/.. $@ +set -euo pipefail + +root="$(dirname "$0")" + +mkdir -p "$root/.shake" + +ghc \ + "$root/src/Main.hs" \ + -Wall \ + -i"$root/src" \ + -rtsopts \ + -with-rtsopts=-I0 \ + -outputdir="$root/.shake" \ + -o "$root/.shake/build" + +"$root/.shake/build" \ + --lint \ + --directory "$root/.." \ + --colour \ + "$@" From git at git.haskell.org Thu Oct 26 23:45:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring && back. (4198a65) Message-ID: <20171026234525.BF61A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4198a65a93270c5be30cf99acecc922bd4a4712b/ghc >--------------------------------------------------------------- commit 4198a65a93270c5be30cf99acecc922bd4a4712b Author: Andrey Mokhov Date: Tue Dec 30 03:53:34 2014 +0000 Bring && back. >--------------------------------------------------------------- 4198a65a93270c5be30cf99acecc922bd4a4712b build.bat | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/build.bat b/build.bat index 0e1f581..b6b9a82 100644 --- a/build.bat +++ b/build.bat @@ -1,3 +1,2 @@ @mkdir _shake 2> nul - at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build - at _shake\build --lint --directory ".." %* + at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Thu Oct 26 23:45:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create LICENSE (d12e733) Message-ID: <20171026234510.BB0DF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d12e733ba6fd831157ee436dbfac6e9f2aa8579a/ghc >--------------------------------------------------------------- commit d12e733ba6fd831157ee436dbfac6e9f2aa8579a Author: Andrey Mokhov Date: Wed Dec 23 12:42:57 2015 +0000 Create LICENSE >--------------------------------------------------------------- d12e733ba6fd831157ee436dbfac6e9f2aa8579a LICENSE | 27 +++++++++++++++++++++++++++ 1 file changed, 27 insertions(+) diff --git a/LICENSE b/LICENSE new file mode 100644 index 0000000..20d201e --- /dev/null +++ b/LICENSE @@ -0,0 +1,27 @@ +Copyright (c) 2015, Andrey Mokhov +All rights reserved. + +Redistribution and use in source and binary forms, with or without +modification, are permitted provided that the following conditions are met: + +* Redistributions of source code must retain the above copyright notice, this + list of conditions and the following disclaimer. + +* Redistributions in binary form must reproduce the above copyright notice, + this list of conditions and the following disclaimer in the documentation + and/or other materials provided with the distribution. + +* Neither the name of shaking-up-ghc nor the names of its + contributors may be used to endorse or promote products derived from + this software without specific prior written permission. + +THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" +AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE +DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE +FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. From git at git.haskell.org Thu Oct 26 23:45:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create ghc-tarballs/mingw-w64/x86_64/ directory. (b3382b9) Message-ID: <20171026234526.E817D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3382b95c0fc6385df7c33a6e84fa62b207b75ab/ghc >--------------------------------------------------------------- commit b3382b95c0fc6385df7c33a6e84fa62b207b75ab Author: Andrey Mokhov Date: Fri Jan 8 17:12:33 2016 +0000 Create ghc-tarballs/mingw-w64/x86_64/ directory. See #110. [skip ci] >--------------------------------------------------------------- b3382b95c0fc6385df7c33a6e84fa62b207b75ab .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f0014e3..1d3b7c5 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,8 +14,8 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - bash -lc "cd /home/ghc; ./mk/get-win32-tarballs.sh download x86_64" - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0e196114ceb61cfb03e24216203f868a10d294b9/ghc >--------------------------------------------------------------- commit 0e196114ceb61cfb03e24216203f868a10d294b9 Author: David Luposchainsky Date: Mon Dec 21 14:15:16 2015 +0100 Show simple shake progress and timings >--------------------------------------------------------------- 0e196114ceb61cfb03e24216203f868a10d294b9 src/Main.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index aae1d5e..7a0205d 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -5,9 +5,14 @@ import Rules.Config import Rules.Oracles main :: IO () -main = shakeArgs shakeOptions { shakeFiles = shakeFilesPath } $ do +main = shakeArgs options $ do generateTargets -- see Rules packageRules -- see Rules cabalRules -- see Rules.Cabal configRules -- see Rules.Config oracleRules -- see Rules.Oracles + where + options = shakeOptions + { shakeFiles = shakeFilesPath + , shakeProgress = progressSimple + , shakeTimings = True } From git at git.haskell.org Thu Oct 26 23:45:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track progress. (2d4a29c) Message-ID: <20171026234529.4F5183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb/ghc >--------------------------------------------------------------- commit 2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb Author: Andrey Mokhov Date: Tue Dec 30 03:55:34 2014 +0000 Track progress. >--------------------------------------------------------------- 2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb doc/deepseq-build-progress.txt | 359 +++++++++-------------------------------- 1 file changed, 77 insertions(+), 282 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 2d4a29c8c0b60eb974c7426ffc87b2e0c3be90bb From git at git.haskell.org Thu Oct 26 23:45:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix unnecessary import hiding (988dabb) Message-ID: <20171026234530.7BEA03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/988dabb35a239fa8dd799de5951acf55786bc0ee/ghc >--------------------------------------------------------------- commit 988dabb35a239fa8dd799de5951acf55786bc0ee Author: David Luposchainsky Date: Fri Jan 8 18:23:46 2016 +0100 Fix unnecessary import hiding >--------------------------------------------------------------- 988dabb35a239fa8dd799de5951acf55786bc0ee src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 05686e0..925c427 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -34,7 +34,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>), parallel) +import Development.Shake hiding (unit, (*>)) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Thu Oct 26 23:45:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #17 from bgamari/types (3783b0d) Message-ID: <20171026234531.A2DD53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3783b0d0eab89fdbc0b6ec4dd2ba78423fc79dc1/ghc >--------------------------------------------------------------- commit 3783b0d0eab89fdbc0b6ec4dd2ba78423fc79dc1 Merge: 02dfa6d 7e65227 Author: Andrey Mokhov Date: Wed Dec 23 20:06:00 2015 +0000 Merge pull request #17 from bgamari/types [WIP] Make better use of types >--------------------------------------------------------------- 3783b0d0eab89fdbc0b6ec4dd2ba78423fc79dc1 src/GHC.hs | 7 ++++--- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Package.hs | 30 +++++++++++++++++++++--------- src/Rules/Cabal.hs | 12 ++++++------ src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 4 ++-- src/Settings/TargetDirectory.hs | 3 ++- 11 files changed, 42 insertions(+), 28 deletions(-) From git at git.haskell.org Thu Oct 26 23:45:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for parsing package-data.mk files. (a253255) Message-ID: <20171026234532.CDD883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a253255970c94138f8c67ed298117d6adac0eef2/ghc >--------------------------------------------------------------- commit a253255970c94138f8c67ed298117d6adac0eef2 Author: Andrey Mokhov Date: Tue Dec 30 03:56:28 2014 +0000 Add support for parsing package-data.mk files. >--------------------------------------------------------------- a253255970c94138f8c67ed298117d6adac0eef2 src/Oracles.hs | 39 +++++++++++++++++++++++++++++++++++++-- 1 file changed, 37 insertions(+), 2 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 9ceb121..6a03a6d 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -9,6 +9,7 @@ module Oracles ( path, with, run, argPath, option, argOption, Condition, test, when, unless, not, (&&), (||), + packagaDataOption, PackageDataKey (..), oracleRules ) where @@ -240,9 +241,10 @@ instance ToCondition a => AndOr Flag a where newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + askConfigWithDefault :: String -> Action String -> Action String askConfigWithDefault key defaultAction = do - maybeValue <- askOracle $ ConfigKey $ key + maybeValue <- askOracle $ ConfigKey key case maybeValue of Just value -> return value Nothing -> do @@ -254,6 +256,32 @@ askConfig key = askConfigWithDefault key $ error $ "\nCannot find key '" ++ key ++ "' in configuration files." +newtype PackageDataPair = PackageDataPair (FilePath, String) + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +packagaDataOptionWithDefault :: FilePath -> String -> Action String -> Action String +packagaDataOptionWithDefault file key defaultAction = do + maybeValue <- askOracle $ PackageDataPair (file, key) + case maybeValue of + Just value -> return value + Nothing -> do + result <- defaultAction + return result + +data PackageDataKey = Modules | SrcDirs + +packagaDataOption :: FilePath -> PackageDataKey -> Action String +packagaDataOption file key = do + let keyName = replaceChar '/' '_' $ takeDirectory file ++ case key of + Modules -> "_MODULES" + SrcDirs -> "_HS_SRC_DIRS" + packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" + ++ keyName + ++ "' in " + ++ file + ++ "." + + oracleRules :: Rules () oracleRules = do cfg <- newCache $ \() -> do @@ -273,5 +301,12 @@ oracleRules = do ++ "' is missing; proceeding with default configuration.\n" return M.empty return $ cfgUser `M.union` cfgDefault - addOracle $ \(ConfigKey x) -> M.lookup x <$> cfg () + + addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () + + pkgData <- newCache $ \file -> do + need [file] + liftIO $ readConfigFile file + + addOracle $ \(PackageDataPair (file, key)) -> M.lookup key <$> pkgData file return () From git at git.haskell.org Thu Oct 26 23:45:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #136 from quchen/redundant-hiding (4116dbd) Message-ID: <20171026234533.E81D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4116dbdd0c3407fac56a101e2592240411108c86/ghc >--------------------------------------------------------------- commit 4116dbdd0c3407fac56a101e2592240411108c86 Merge: b3382b9 988dabb Author: Andrey Mokhov Date: Fri Jan 8 17:29:30 2016 +0000 Merge pull request #136 from quchen/redundant-hiding Fix unnecessary import hiding of "parallel" [skip ci] >--------------------------------------------------------------- 4116dbdd0c3407fac56a101e2592240411108c86 src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:45:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #29 from quchen/script-refactoring (f354291) Message-ID: <20171026234535.252A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f354291e941d1653bb8d3ae6825f588e82372b0a/ghc >--------------------------------------------------------------- commit f354291e941d1653bb8d3ae6825f588e82372b0a Merge: 3783b0d bfd3d32 Author: Andrey Mokhov Date: Wed Dec 23 20:14:46 2015 +0000 Merge pull request #29 from quchen/script-refactoring Show Shake statistics, refactor direct Linux build script >--------------------------------------------------------------- f354291e941d1653bb8d3ae6825f588e82372b0a build.sh | 27 ++++++++++++++++++++++----- src/Main.hs | 7 ++++++- 2 files changed, 28 insertions(+), 6 deletions(-) From git at git.haskell.org Thu Oct 26 23:45:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageDeps rule. (9d1a489) Message-ID: <20171026234536.532B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d1a489b8faf8f91f6125865a5a74712a8b8a7a8/ghc >--------------------------------------------------------------- commit 9d1a489b8faf8f91f6125865a5a74712a8b8a7a8 Author: Andrey Mokhov Date: Tue Dec 30 03:57:22 2014 +0000 Add buildPackageDeps rule. >--------------------------------------------------------------- 9d1a489b8faf8f91f6125865a5a74712a8b8a7a8 doc/deepseq-build-progress.txt | 41 ++------------------ src/Package.hs | 88 ++++++++++++++++++++++++++++++++++++++++-- 2 files changed, 87 insertions(+), 42 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9d1a489b8faf8f91f6125865a5a74712a8b8a7a8 From git at git.haskell.org Thu Oct 26 23:45:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create ghc-tarballs/perl folder. (eab9a54) Message-ID: <20171026234537.54E4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eab9a54f888dba48e8975bca1140c5f6dbdef3e2/ghc >--------------------------------------------------------------- commit eab9a54f888dba48e8975bca1140c5f6dbdef3e2 Author: Andrey Mokhov Date: Fri Jan 8 18:32:47 2016 +0000 Create ghc-tarballs/perl folder. See #110. [skip ci] >--------------------------------------------------------------- eab9a54f888dba48e8975bca1140c5f6dbdef3e2 .appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.appveyor.yml b/.appveyor.yml index 1d3b7c5..7c724b8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -15,6 +15,7 @@ install: - cd C:\msys64\home\ghc - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" + - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c8a0e7aa5f3a11561bdb3b45426f319c83291a8/ghc >--------------------------------------------------------------- commit 1c8a0e7aa5f3a11561bdb3b45426f319c83291a8 Author: Andrey Mokhov Date: Thu Dec 24 01:28:50 2015 +0000 Fix haddockArgs, clean up code. >--------------------------------------------------------------- 1c8a0e7aa5f3a11561bdb3b45426f319c83291a8 src/Base.hs | 10 ++++++++-- src/Package.hs | 7 +++---- src/Rules/Cabal.hs | 3 +-- src/Settings/Builders/Haddock.hs | 4 +++- 4 files changed, 15 insertions(+), 9 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 79ce119..7730bf5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -26,7 +26,7 @@ module Base ( -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, removeFileIfExists, replaceEq, chunksOfSize, - replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-) + replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt ) where import Control.Applicative @@ -37,7 +37,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>), parallel) +import Development.Shake hiding (unit, (*>)) import Development.Shake.Classes import Development.Shake.Config import Development.Shake.FilePath @@ -77,6 +77,12 @@ replaceSeparators = replaceIf isPathSeparator replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) +-- | Given a version string such as "2.16.2" produce an integer equivalent +versionToInt :: String -> Int +versionToInt s = major * 1000 + minor * 10 + patch + where + [major, minor, patch] = map read . words $ replaceEq '.' ' ' s + -- | Given a module name extract the directory and file name, e.g.: -- -- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") diff --git a/src/Package.hs b/src/Package.hs index a956c6a..536a16f39 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,8 +1,7 @@ -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving, DeriveDataTypeable #-} module Package ( - Package (..), PackageName(..), PackageType (..), + Package (..), PackageName (..), PackageType (..), -- * Queries pkgNameString, pkgCabalFile, @@ -18,7 +17,7 @@ import Data.String -- | The name of a Cabal package newtype PackageName = PackageName { getPackageName :: String } deriving ( Eq, Ord, IsString, Generic, Binary, Hashable - , NFData) + , Typeable, NFData) instance Show PackageName where show (PackageName name) = name diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 74a2468..ce52388 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,13 +1,12 @@ module Rules.Cabal (cabalRules) where import Data.Version -import Distribution.Package as DP hiding (Package) +import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Verbosity import Expression import GHC -import Package hiding (library) import Settings cabalRules :: Rules () diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 4cc8683..0663d04 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -16,6 +16,7 @@ haddockArgs = builder Haddock ? do hidden <- getPkgDataList HiddenModules deps <- getPkgDataList Deps depNames <- getPkgDataList DepNames + hVersion <- lift . pkgData . Version $ targetPath Stage2 haddock ghcOpts <- fromDiffExpr commonGhcArgs mconcat [ arg $ "--odir=" ++ takeDirectory output @@ -26,6 +27,7 @@ haddockArgs = builder Haddock ? do , arg "--hoogle" , arg $ "--title=" ++ pkgNameString pkg ++ "-" ++ version ++ ": " ++ synopsis , arg $ "--prologue=" ++ path -/- "haddock-prologue.txt" + , arg $ "--optghc=-D__HADDOCK_VERSION__=" ++ show (versionToInt hVersion) , append $ map ("--hide=" ++) hidden , append $ [ "--read-interface=../" ++ dep ++ ",../" ++ dep ++ "/src/%{MODULE/./-}.html\\#%{NAME}," @@ -40,7 +42,7 @@ haddockArgs = builder Haddock ? do , customPackageArgs , append =<< getInputs , arg "+RTS" - , arg $ "-t" ++ path "haddock.t" + , arg $ "-t" ++ path -/- "haddock.t" , arg "--machine-readable" ] customPackageArgs :: Args From git at git.haskell.org Thu Oct 26 23:45:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move generic helper functions to Util.hs. (4e5f1b7) Message-ID: <20171026234539.CED843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e5f1b74b9b5946ad614bc354f01697f953a072b/ghc >--------------------------------------------------------------- commit 4e5f1b74b9b5946ad614bc354f01697f953a072b Author: Andrey Mokhov Date: Tue Dec 30 15:06:13 2014 +0000 Move generic helper functions to Util.hs. >--------------------------------------------------------------- 4e5f1b74b9b5946ad614bc354f01697f953a072b src/Base.hs | 8 +------- src/Oracles.hs | 9 ++++----- src/Package.hs | 5 +++-- src/Util.hs | 16 ++++++++++++++++ 4 files changed, 24 insertions(+), 14 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index eaebaf3..24943e4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -9,8 +9,7 @@ module Base ( Stage (..), Args, arg, joinArgs, joinArgsWithSpaces, - filterOut, - replaceChar + filterOut ) where import Development.Shake hiding ((*>)) @@ -43,8 +42,3 @@ joinArgs = intercalateArgs "" filterOut :: Args -> [String] -> Args filterOut args list = filter (`notElem` list) <$> args - -replaceChar :: Char -> Char -> String -> String -replaceChar from to = (go from) . if from == '/' then go '\\' else id - where - go from' = map (\c -> if c == from' then to else c) diff --git a/src/Oracles.hs b/src/Oracles.hs index 6a03a6d..98321c9 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -20,8 +20,8 @@ import Control.Monad hiding (when, unless) import qualified Data.HashMap.Strict as M import qualified Prelude import Prelude hiding (not, (&&), (||)) -import Data.Char import Base +import Util import Config data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage @@ -241,7 +241,6 @@ instance ToCondition a => AndOr Flag a where newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) - askConfigWithDefault :: String -> Action String -> Action String askConfigWithDefault key defaultAction = do maybeValue <- askOracle $ ConfigKey key @@ -266,20 +265,20 @@ packagaDataOptionWithDefault file key defaultAction = do Just value -> return value Nothing -> do result <- defaultAction - return result + return result -- TODO: simplify data PackageDataKey = Modules | SrcDirs packagaDataOption :: FilePath -> PackageDataKey -> Action String packagaDataOption file key = do - let keyName = replaceChar '/' '_' $ takeDirectory file ++ case key of + let keyName = replaceIf isSlash '_' $ takeDirectory file ++ case key of Modules -> "_MODULES" SrcDirs -> "_HS_SRC_DIRS" packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file - ++ "." + ++ "." -- TODO: Improve formatting oracleRules :: Rules () diff --git a/src/Package.hs b/src/Package.hs index a6df921..8488044 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -4,6 +4,7 @@ module Package ( ) where import Base +import Util import Ways import Oracles @@ -129,7 +130,7 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs let pkgDataFile = path dist "package-data.mk" pkgData <- lines <$> liftIO (readFile pkgDataFile) - length pkgData `seq` writeFileLines pkgDataFile $ map (replaceChar '/' '_') $ filter ('$' `notElem`) pkgData + length pkgData `seq` writeFileLines pkgDataFile $ map (replaceIf isSlash '_') $ filter ('$' `notElem`) pkgData where cabalArgs, ghcPkgArgs :: Args cabalArgs = mconcat @@ -225,7 +226,7 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = autogen = dist "build" "autogen" mods <- words <$> packagaDataOption pkgData Modules src <- getDirectoryFiles "" $ do - start <- map (replaceChar '.' '/') mods + start <- map (replaceEq '.' '/') mods end <- [".hs", ".lhs"] return $ path ++ "//" ++ start ++ end run (Ghc stage) $ mconcat diff --git a/src/Util.hs b/src/Util.hs new file mode 100644 index 0000000..8afd6cb --- /dev/null +++ b/src/Util.hs @@ -0,0 +1,16 @@ +module Util ( + module Data.Char, + isSlash, + replaceIf, replaceEq + ) where + +import Data.Char + +isSlash :: Char -> Bool +isSlash = (`elem` ['/', '\\']) + +replaceIf :: (a -> Bool) -> a -> [a] -> [a] +replaceIf p to = map (\from -> if p from then to else from) + +replaceEq :: Eq a => a -> a -> [a] -> [a] +replaceEq from = replaceIf (== from) From git at git.haskell.org Thu Oct 26 23:45:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix shake script path. (192fd13) Message-ID: <20171026234540.C6E593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/192fd13c7e9a8e71940513a78816f701b89ea87a/ghc >--------------------------------------------------------------- commit 192fd13c7e9a8e71940513a78816f701b89ea87a Author: Andrey Mokhov Date: Fri Jan 8 19:21:00 2016 +0000 Fix shake script path. See #110. [skip ci] >--------------------------------------------------------------- 192fd13c7e9a8e71940513a78816f701b89ea87a .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7c724b8..ef571b3 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd - - bash -lc "./shake-build/build.bat -j --no-progress" + - bash -lc "cd /home/ghc; ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:45:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (95d594c) Message-ID: <20171026234542.1CAA33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95d594c1836993c98fea985f475df4bbc959fa38/ghc >--------------------------------------------------------------- commit 95d594c1836993c98fea985f475df4bbc959fa38 Author: Andrey Mokhov Date: Thu Dec 24 02:51:44 2015 +0000 Clean up. >--------------------------------------------------------------- 95d594c1836993c98fea985f475df4bbc959fa38 src/Package.hs | 6 ++---- src/Settings/Packages.hs | 6 ++++-- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 536a16f39..9a64fa8 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -16,8 +16,7 @@ import Data.String -- | The name of a Cabal package newtype PackageName = PackageName { getPackageName :: String } - deriving ( Eq, Ord, IsString, Generic, Binary, Hashable - , Typeable, NFData) + deriving (Eq, Ord, IsString, Generic, Binary, Hashable, Typeable, NFData) instance Show PackageName where show (PackageName name) = name @@ -25,8 +24,7 @@ instance Show PackageName where -- | We regard packages as either being libraries or programs. This is -- bit of a convenient lie as Cabal packages can be both, but it works -- for now. -data PackageType = Program | Library - deriving Generic +data PackageType = Program | Library deriving Generic data Package = Package { diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index ee37b07..32d12a5 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -20,10 +20,10 @@ packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] + -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] --- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 @@ -35,7 +35,7 @@ packagesStage1 = mconcat , notM windowsHost ? append [iservBin] , buildHaddock ? append [xhtml] ] --- TODO: currently there is an unchecked assumption that we only build programs +-- TODO: currently there is an unchecked assumption that we build only programs -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages packagesStage2 = mconcat @@ -43,9 +43,11 @@ packagesStage2 = mconcat , buildHaddock ? append [haddock] ] -- TODO: switch to Set Package as the order of packages should not matter? +-- Otherwise we have to keep remembering to sort packages from time to time. knownPackages :: [Package] knownPackages = sort $ defaultKnownPackages ++ userKnownPackages -- Note: this is slow but we keep it simple as there are just ~50 packages +-- TODO: speed up? findKnownPackage :: PackageName -> Maybe Package findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Thu Oct 26 23:45:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Oracles.hs. (e20c4bc) Message-ID: <20171026234543.74F2B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e20c4bc3bec68971837c2808724edbfcbe0b92ab/ghc >--------------------------------------------------------------- commit e20c4bc3bec68971837c2808724edbfcbe0b92ab Author: Andrey Mokhov Date: Tue Dec 30 15:12:40 2014 +0000 Refactor Oracles.hs. >--------------------------------------------------------------- e20c4bc3bec68971837c2808724edbfcbe0b92ab src/Oracles.hs | 21 ++++++--------------- 1 file changed, 6 insertions(+), 15 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 98321c9..75439fb 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -246,14 +246,11 @@ askConfigWithDefault key defaultAction = do maybeValue <- askOracle $ ConfigKey key case maybeValue of Just value -> return value - Nothing -> do - result <- defaultAction - return result + Nothing -> defaultAction askConfig :: String -> Action String -askConfig key = askConfigWithDefault key $ error $ "\nCannot find key '" - ++ key - ++ "' in configuration files." +askConfig key = askConfigWithDefault key $ + error $ "\nCannot find key '" ++ key ++ "' in configuration files." newtype PackageDataPair = PackageDataPair (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -263,9 +260,7 @@ packagaDataOptionWithDefault file key defaultAction = do maybeValue <- askOracle $ PackageDataPair (file, key) case maybeValue of Just value -> return value - Nothing -> do - result <- defaultAction - return result -- TODO: simplify + Nothing -> defaultAction data PackageDataKey = Modules | SrcDirs @@ -274,12 +269,8 @@ packagaDataOption file key = do let keyName = replaceIf isSlash '_' $ takeDirectory file ++ case key of Modules -> "_MODULES" SrcDirs -> "_HS_SRC_DIRS" - packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" - ++ keyName - ++ "' in " - ++ file - ++ "." -- TODO: Improve formatting - + packagaDataOptionWithDefault file keyName $ + error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." oracleRules :: Rules () oracleRules = do From git at git.haskell.org Thu Oct 26 23:45:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script from shake-build. (8d1c201) Message-ID: <20171026234544.466AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8d1c201b7fcea98907fa54419f91f3fdfc3007fd/ghc >--------------------------------------------------------------- commit 8d1c201b7fcea98907fa54419f91f3fdfc3007fd Author: Andrey Mokhov Date: Fri Jan 8 20:11:52 2016 +0000 Run shake script from shake-build. See #110. [skip ci] >--------------------------------------------------------------- 8d1c201b7fcea98907fa54419f91f3fdfc3007fd .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index ef571b3..0e62796 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd - - bash -lc "cd /home/ghc; ./shake-build/build.bat -j --no-progress" + - bash -lc "cd /home/ghc/shake-build; ./build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:45:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove runghcid.bat. (920b393) Message-ID: <20171026234545.7F0003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/920b3938e452548bdf1d9e24ef7e1971acb1c76e/ghc >--------------------------------------------------------------- commit 920b3938e452548bdf1d9e24ef7e1971acb1c76e Author: Andrey Mokhov Date: Thu Dec 24 03:28:07 2015 +0000 Remove runghcid.bat. >--------------------------------------------------------------- 920b3938e452548bdf1d9e24ef7e1971acb1c76e runghcid.bat | 1 - 1 file changed, 1 deletion(-) diff --git a/runghcid.bat b/runghcid.bat deleted file mode 100644 index f2f8ddc..0000000 --- a/runghcid.bat +++ /dev/null @@ -1 +0,0 @@ -ghcid --height=8 --topmost "--command=ghci -isrc -Wall src/Main.hs" From git at git.haskell.org Thu Oct 26 23:45:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting, add TODOs. (d2f3a74) Message-ID: <20171026234547.2AE3E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2f3a74ae4e0ba1218025aca1b2786a35f169cee/ghc >--------------------------------------------------------------- commit d2f3a74ae4e0ba1218025aca1b2786a35f169cee Author: Andrey Mokhov Date: Tue Dec 30 15:20:37 2014 +0000 Fix formatting, add TODOs. >--------------------------------------------------------------- d2f3a74ae4e0ba1218025aca1b2786a35f169cee src/Ways.hs | 21 +++++++++++---------- 1 file changed, 11 insertions(+), 10 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 6e186ab..91cbd4f 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -23,7 +23,7 @@ data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dyn data Way = Way { tag :: String, -- e.g., "thr_p" - description :: String, -- e.g., "threaded profiled" + description :: String, -- e.g., "threaded profiled"; TODO: get rid of this field? units :: [WayUnit] -- e.g., [Threaded, Profiling] } deriving Eq @@ -72,17 +72,18 @@ defaultWays stage = do wayHcOpts :: Way -> Args wayHcOpts (Way _ _ units) = mconcat - [ when (Dynamic `notElem` units) $ arg [ "-static" ] - , when (Dynamic `elem` units) $ arg [ "-fPIC", "-dynamic" ] - , when (Threaded `elem` units) $ arg [ "-optc-DTHREADED_RTS" ] - , when (Debug `elem` units) $ arg [ "-optc-DDEBUG" ] - , when (Profiling `elem` units) $ arg [ "-prof" ] - , when (Logging `elem` units) $ arg [ "-eventlog" ] - , when (Parallel `elem` units) $ arg [ "-parallel" ] - , when (GranSim `elem` units) $ arg [ "-gransim" ] - , when (units == [Debug] || units == [Debug, Dynamic]) $ arg [ "-ticky", "-DTICKY_TICKY" ] + [ when (Dynamic `notElem` units) $ arg ["-static"] + , when (Dynamic `elem` units) $ arg ["-fPIC", "-dynamic"] + , when (Threaded `elem` units) $ arg ["-optc-DTHREADED_RTS"] + , when (Debug `elem` units) $ arg ["-optc-DDEBUG"] + , when (Profiling `elem` units) $ arg ["-prof"] + , when (Logging `elem` units) $ arg ["-eventlog"] + , when (Parallel `elem` units) $ arg ["-parallel"] + , when (GranSim `elem` units) $ arg ["-gransim"] + , when (units == [Debug] || units == [Debug, Dynamic]) $ arg ["-ticky", "-DTICKY_TICKY"] ] +-- TODO: cover other cases suffix :: FilePath -> Way -> FilePath suffix base (Way _ _ units) = concat $ From git at git.haskell.org Thu Oct 26 23:45:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script outside bash. (a5763fa) Message-ID: <20171026234547.E70C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5763fa0dca8a35fb15e5ef6c991c24e2bc04c28/ghc >--------------------------------------------------------------- commit a5763fa0dca8a35fb15e5ef6c991c24e2bc04c28 Author: Andrey Mokhov Date: Fri Jan 8 20:52:02 2016 +0000 Run shake script outside bash. See #110. [skip ci] >--------------------------------------------------------------- a5763fa0dca8a35fb15e5ef6c991c24e2bc04c28 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 0e62796..b6b5ecb 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,5 +23,5 @@ install: - happy --version build_script: - - cd - - bash -lc "cd /home/ghc/shake-build; ./build.bat -j --no-progress" + - cd C:\msys64\home\ghc\shake-build + - ./build.bat -j --no-progress From git at git.haskell.org Thu Oct 26 23:45:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split the batch file into multiple lines, add missing flags (-j -O). (5bb30bc) Message-ID: <20171026234548.E60E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5bb30bc25f693652432ff72150a40ceb558f36e3/ghc >--------------------------------------------------------------- commit 5bb30bc25f693652432ff72150a40ceb558f36e3 Author: Andrey Mokhov Date: Thu Dec 24 03:29:32 2015 +0000 Split the batch file into multiple lines, add missing flags (-j -O). >--------------------------------------------------------------- 5bb30bc25f693652432ff72150a40ceb558f36e3 build.bat | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/build.bat b/build.bat index ab26e07..a4e2548 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,19 @@ @mkdir .shake 2> nul - at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=.shake -o .shake/build && .shake\build --lint --directory ".." %* + + at set ghcArgs=--make ^ + -Wall ^ + src/Main.hs ^ + -isrc ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=.shake ^ + -j ^ + -O ^ + -o .shake/build + + at set shakeArgs=--lint ^ + --directory ^ + ".." ^ + %* + + at ghc %ghcArgs% && .shake\build %shakeArgs% From git at git.haskell.org Thu Oct 26 23:45:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out postProcessPackageData to Util.hs. (c4cc0dc) Message-ID: <20171026234550.E6B4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4cc0dc7ab0465a67f9f81e309fa10eaa210b772/ghc >--------------------------------------------------------------- commit c4cc0dc7ab0465a67f9f81e309fa10eaa210b772 Author: Andrey Mokhov Date: Tue Dec 30 15:33:06 2014 +0000 Factor out postProcessPackageData to Util.hs. >--------------------------------------------------------------- c4cc0dc7ab0465a67f9f81e309fa10eaa210b772 src/Package.hs | 6 ++---- src/Util.hs | 12 +++++++++++- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 8488044..24ef85d 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -122,15 +122,13 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = "inplace-pkg-config", "setup-config", "build" "autogen" "cabal_macros.h", - "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? What's up with Paths_cpsa.hs? + "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. ] &%> \_ -> do need [path name <.> "cabal"] when (doesFileExist $ path "configure.ac") $ need [path "configure"] run GhcCabal cabalArgs when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs - let pkgDataFile = path dist "package-data.mk" - pkgData <- lines <$> liftIO (readFile pkgDataFile) - length pkgData `seq` writeFileLines pkgDataFile $ map (replaceIf isSlash '_') $ filter ('$' `notElem`) pkgData + postProcessPackageData $ path dist "package-data.mk" where cabalArgs, ghcPkgArgs :: Args cabalArgs = mconcat diff --git a/src/Util.hs b/src/Util.hs index 8afd6cb..b8a38f4 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,9 +1,11 @@ module Util ( module Data.Char, isSlash, - replaceIf, replaceEq + replaceIf, replaceEq, + postProcessPackageData ) where +import Base import Data.Char isSlash :: Char -> Bool @@ -14,3 +16,11 @@ replaceIf p to = map (\from -> if p from then to else from) replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) + +-- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: +-- 1) Drop lines containing '$' +-- 2) Replace '/' and '\' with '_' +postProcessPackageData :: FilePath -> Action () +postProcessPackageData file = do + pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) + length pkgData `seq` writeFileLines file $ map (replaceIf isSlash '_') pkgData From git at git.haskell.org Thu Oct 26 23:45:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script via stack. (f4ece5b) Message-ID: <20171026234552.0EDBA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4ece5be780b194845548d9e1ab46a916b22b4f5/ghc >--------------------------------------------------------------- commit f4ece5be780b194845548d9e1ab46a916b22b4f5 Author: Andrey Mokhov Date: Fri Jan 8 21:34:15 2016 +0000 Run shake script via stack. See #110. [skip ci] >--------------------------------------------------------------- f4ece5be780b194845548d9e1ab46a916b22b4f5 .appveyor.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index b6b5ecb..14c6521 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,5 +23,4 @@ install: - happy --version build_script: - - cd C:\msys64\home\ghc\shake-build - - ./build.bat -j --no-progress + - stack exec -- C:\msys64\home\ghc\shake-build\build.bat -j --no-progress From git at git.haskell.org Thu Oct 26 23:45:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify src/Oracles/ModuleFiles.hs, improve performance. (013fa90) Message-ID: <20171026234552.AC79D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/013fa902ee243621eff3778d94b0f1af37f3de51/ghc >--------------------------------------------------------------- commit 013fa902ee243621eff3778d94b0f1af37f3de51 Author: Andrey Mokhov Date: Thu Dec 24 04:36:07 2015 +0000 Simplify src/Oracles/ModuleFiles.hs, improve performance. >--------------------------------------------------------------- 013fa902ee243621eff3778d94b0f1af37f3de51 src/Oracles/ModuleFiles.hs | 78 ++++++++++++---------------------------------- 1 file changed, 20 insertions(+), 58 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 535d2be..832deef 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,76 +1,44 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} module Oracles.ModuleFiles (moduleFiles, haskellModuleFiles, moduleFilesOracle) where -import Base hiding (exe) -import Distribution.ModuleName -import Distribution.PackageDescription -import Distribution.PackageDescription.Parse -import Distribution.Verbosity -import GHC +import Base import Oracles.PackageData -import Package hiding (library) +import Package import Stage import Settings.TargetDirectory -newtype ModuleFilesKey = ModuleFilesKey (Package, [FilePath]) +newtype ModuleFilesKey = ModuleFilesKey ([String], [FilePath]) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) moduleFiles :: Stage -> Package -> Action [FilePath] moduleFiles stage pkg = do let path = targetPath stage pkg + srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - (found, _ :: [FilePath]) <- askOracle $ ModuleFilesKey (pkg, []) - let cmp (m1, _) m2 = compare m1 m2 - foundFiles = map snd $ intersectOrd cmp found modules - return foundFiles + let dirs = [ pkgPath pkg -/- dir | dir <- srcDirs ] + found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (modules, dirs) + return $ map snd found haskellModuleFiles :: Stage -> Package -> Action ([FilePath], [String]) haskellModuleFiles stage pkg = do let path = targetPath stage pkg autogen = path -/- "build/autogen" + srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - (found, missingMods) <- askOracle $ ModuleFilesKey (pkg, [autogen]) - let cmp (m1, _) m2 = compare m1 m2 - foundFiles = map snd $ intersectOrd cmp found modules + let dirs = [ pkgPath pkg -/- dir | dir <- srcDirs ] + foundSrcDirs <- askOracle $ ModuleFilesKey (modules, dirs ) + foundAutogen <- askOracle $ ModuleFilesKey (modules, [autogen]) + + let found = foundSrcDirs ++ foundAutogen + missingMods = modules `minusOrd` (sort $ map fst found) otherMods = map (replaceEq '/' '.' . dropExtension) otherFiles - (haskellFiles, otherFiles) = partition ("//*hs" ?==) foundFiles + (haskellFiles, otherFiles) = partition ("//*hs" ?==) (map snd found) return (haskellFiles, missingMods ++ otherMods) -extract :: Monoid a => Maybe (CondTree v c a) -> a -extract Nothing = mempty -extract (Just (CondNode leaf _ ifs)) = leaf <> mconcat (map f ifs) - where - f (_, t, mt) = extract (Just t) <> extract mt - --- Look up Haskell source directories and module names of a package -packageInfo :: Package -> Action ([FilePath], [ModuleName]) -packageInfo pkg - | pkg == hp2ps = return (["."], []) - | otherwise = do - need [pkgCabalFile pkg] - pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - - let lib = extract $ condLibrary pd - exe = extract . Just . snd . head $ condExecutables pd - - let (srcDirs, modules) = if lib /= mempty - then ( hsSourceDirs $ libBuildInfo lib, libModules lib) - else ( hsSourceDirs $ buildInfo exe - , [fromString . dropExtension $ modulePath exe] - ++ exeModules exe) - - return (if null srcDirs then ["."] else srcDirs, modules) - moduleFilesOracle :: Rules () moduleFilesOracle = do - answer <- newCache $ \(pkg, extraDirs) -> do - putOracle $ "Searching module files of package " ++ pkgNameString pkg ++ "..." - unless (null extraDirs) $ putOracle $ "Extra directory = " ++ show extraDirs - - (srcDirs, modules) <- packageInfo pkg - - let dirs = extraDirs ++ [ pkgPath pkg -/- dir | dir <- srcDirs ] - decodedPairs = sort $ map (splitFileName . toFilePath) modules + answer <- newCache $ \(modules, dirs) -> do + let decodedPairs = map decodeModule modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedPairs @@ -79,18 +47,12 @@ moduleFilesOracle = do forM todo $ \(mDir, mFiles) -> do let fullDir = dir -/- mDir files <- getDirectoryFiles fullDir ["*"] - let noBoot = filter (not . (isSuffixOf "-boot")) files + let noBoot = filter (not . (isSuffixOf "-boot")) files cmp fe f = compare (dropExtension fe) f found = intersectOrd cmp noBoot mFiles - return (map (fullDir -/-) found, (mDir, map dropExtension found)) - - let foundFiles = sort [ (encodeModule d f, f) - | (fs, (d, _)) <- result, f <- fs ] - foundPairs = [ (d, f) | (d, fs) <- map snd result, f <- fs ] - missingPairs = decodedPairs `minusOrd` sort foundPairs - missingMods = map (uncurry encodeModule) missingPairs + return (map (fullDir -/-) found, mDir) - return (foundFiles, missingMods) + return $ sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] _ <- addOracle $ \(ModuleFilesKey query) -> answer query return () From git at git.haskell.org Thu Oct 26 23:45:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add splitArgs function to Base.hs. (4dd9560) Message-ID: <20171026234554.5EF3F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4dd9560e34ded015140a7d5d4d2e22d27e19abb2/ghc >--------------------------------------------------------------- commit 4dd9560e34ded015140a7d5d4d2e22d27e19abb2 Author: Andrey Mokhov Date: Tue Dec 30 17:03:10 2014 +0000 Add splitArgs function to Base.hs. >--------------------------------------------------------------- 4dd9560e34ded015140a7d5d4d2e22d27e19abb2 src/Base.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 24943e4..a0f4303 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -8,7 +8,7 @@ module Base ( module Data.List, Stage (..), Args, arg, - joinArgs, joinArgsWithSpaces, + joinArgs, joinArgsWithSpaces, splitArgs, filterOut ) where @@ -40,5 +40,8 @@ joinArgsWithSpaces = intercalateArgs " " joinArgs :: Args -> Args joinArgs = intercalateArgs "" +splitArgs :: Args -> Args +splitArgs = fmap (concatMap words) + filterOut :: Args -> [String] -> Args filterOut args list = filter (`notElem` list) <$> args From git at git.haskell.org Thu Oct 26 23:45:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script via stack from shake-build folder. (ffc5d73) Message-ID: <20171026234555.8ADEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffc5d73536fc68b3abcc1eb8b2dc375fcea33f1d/ghc >--------------------------------------------------------------- commit ffc5d73536fc68b3abcc1eb8b2dc375fcea33f1d Author: Andrey Mokhov Date: Sat Jan 9 02:19:18 2016 +0000 Run shake script via stack from shake-build folder. See #110. [skip ci] >--------------------------------------------------------------- ffc5d73536fc68b3abcc1eb8b2dc375fcea33f1d .appveyor.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 14c6521..1ecaaef 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,4 +23,5 @@ install: - happy --version build_script: - - stack exec -- C:\msys64\home\ghc\shake-build\build.bat -j --no-progress + - cd C:\msys64\home\ghc\shake-build + - stack exec -- build.bat -j --no-progress From git at git.haskell.org Thu Oct 26 23:45:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Cabal support for sandboxed build system building (5da933f) Message-ID: <20171026234556.489C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5da933f768926b7be7e591d22b47a86809c21398/ghc >--------------------------------------------------------------- commit 5da933f768926b7be7e591d22b47a86809c21398 Author: David Luposchainsky Date: Tue Dec 22 20:54:26 2015 +0100 Add Cabal support for sandboxed build system building >--------------------------------------------------------------- 5da933f768926b7be7e591d22b47a86809c21398 .gitignore | 3 ++ README.md | 70 +++++++++++++++++++++++++++++----------- build.cabal.sh | 20 ++++++++++++ shaking-up-ghc.cabal | 91 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 165 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5da933f768926b7be7e591d22b47a86809c21398 From git at git.haskell.org Thu Oct 26 23:45:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add src-hc-opts to configuration files. (5adb8aa) Message-ID: <20171026234557.DC9523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5adb8aa730e9ae9649924f7f8ea59b0e5163876d/ghc >--------------------------------------------------------------- commit 5adb8aa730e9ae9649924f7f8ea59b0e5163876d Author: Andrey Mokhov Date: Tue Dec 30 17:04:28 2014 +0000 Add src-hc-opts to configuration files. >--------------------------------------------------------------- 5adb8aa730e9ae9649924f7f8ea59b0e5163876d cfg/default.config.in | 2 ++ 1 file changed, 2 insertions(+) diff --git a/cfg/default.config.in b/cfg/default.config.in index d3617f4..1a28981 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -61,6 +61,8 @@ conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ +src-hc-opts = -H32m -O + # Include and library directories: #================================= From git at git.haskell.org Thu Oct 26 23:45:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix terminal issue, build stage1 ghc only. (a64efa9) Message-ID: <20171026234559.36F123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a64efa96c9b19edcf801b675685619292a1f878f/ghc >--------------------------------------------------------------- commit a64efa96c9b19edcf801b675685619292a1f878f Author: Andrey Mokhov Date: Sat Jan 9 02:53:36 2016 +0000 Fix terminal issue, build stage1 ghc only. See #110. [skip ci] >--------------------------------------------------------------- a64efa96c9b19edcf801b675685619292a1f878f .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 1ecaaef..99196db 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - stack exec -- build.bat -j --no-progress + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Thu Oct 26 23:45:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:45:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Expression: Add Haddocks (263fc63) Message-ID: <20171026234559.E41783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/263fc63fb084de713ef67608581d93ff52d2b04b/ghc >--------------------------------------------------------------- commit 263fc63fb084de713ef67608581d93ff52d2b04b Author: Ben Gamari Date: Thu Dec 24 12:34:07 2015 +0100 Expression: Add Haddocks >--------------------------------------------------------------- 263fc63fb084de713ef67608581d93ff52d2b04b src/Expression.hs | 88 ++++++++++++++++++++++++++++++++----------------------- 1 file changed, 52 insertions(+), 36 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 208566c..fa3959d 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -1,37 +1,48 @@ {-# LANGUAGE FlexibleInstances #-} module Expression ( - module Base, - module Builder, - module Package, - module Stage, - module Way, + -- * Expressions Expr, DiffExpr, fromDiffExpr, - Predicate, (?), applyPredicate, Args, Ways, Packages, - Target, PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay, + -- ** Operators apply, append, arg, remove, appendSub, appendSubD, filterSub, removeSub, + -- ** Evaluation interpret, interpretPartial, interpretWithStage, interpretDiff, + -- ** Predicates + Predicate, (?), applyPredicate, + -- ** Common expressions + Args, Ways, Packages, + -- ** Targets + Target, PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay, + + -- * Convenient accessors getStage, getPackage, getBuilder, getOutputs, getInputs, getWay, - getInput, getOutput + getInput, getOutput, + + -- * Re-exports + module Base, + module Builder, + module Package, + module Stage, + module Way ) where import Base -import Builder import Package +import Builder import Stage import Target import Way --- Expr a is a computation that produces a value of type Action a and can read --- parameters of the current build Target. +-- | @Expr a@ is a computation that produces a value of type @Action a@ and can read +-- parameters of the current build 'Target'. type Expr a = ReaderT Target Action a --- Diff a holds functions of type a -> a and is equipped with a Monoid instance. --- We could use Dual (Endo a) instead of Diff a, but the former may look scary. --- The name comes from "difference lists". +-- | @Diff a@ is a /difference list/ containing values of type @a at . A difference +-- list is a list with efficient concatenation, encoded as a value @a -> a at . +-- We could use @Dual (Endo a)@ instead of @Diff a@, but the former may look scary. newtype Diff a = Diff { fromDiff :: a -> a } --- DiffExpr a is a computation that builds a difference list (i.e., a function --- of type Action (a -> a)) and can read parameters of the current build Target. +-- | @DiffExpr a@ is a computation that builds a difference list (i.e., a function +-- of type @'Action' (a -> a)@) and can read parameters of the current build ''Target'. type DiffExpr a = Expr (Diff a) -- Note the reverse order of function composition (y . x), which ensures that @@ -41,38 +52,38 @@ instance Monoid (Diff a) where mempty = Diff id Diff x `mappend` Diff y = Diff $ y . x --- The following expressions are used throughout the build system for --- specifying conditions (Predicate), lists of arguments (Args), Ways and --- Packages. +-- | The following expressions are used throughout the build system for +-- specifying conditions ('Predicate'), lists of arguments ('Args'), 'Ways' +-- and 'Packages'. type Predicate = Expr Bool type Args = DiffExpr [String] type Packages = DiffExpr [Package] type Ways = DiffExpr [Way] -- Basic operations on expressions: --- 1) transform an expression by applying a given function +-- | Transform an expression by applying a given function apply :: (a -> a) -> DiffExpr a apply = return . Diff --- 2) append something to an expression +-- | Append something to an expression append :: Monoid a => a -> DiffExpr a append x = apply (<> x) --- 3) remove given elements from a list expression +-- | Remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] remove xs = apply $ filter (`notElem` xs) --- 4) apply a predicate to an expression +-- | Apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate if bool then expr else return mempty --- Add a single String argument to Args +-- | Add a single argument to 'Args' arg :: String -> Args arg = append . return --- A convenient operator for predicate application +-- | A convenient operator for predicate application class PredicateLike a where (?) :: Monoid m => a -> Expr m -> Expr m @@ -87,9 +98,9 @@ instance PredicateLike Bool where instance PredicateLike (Action Bool) where (?) = applyPredicate . lift --- appendSub appends a list of sub-arguments to all arguments starting with a +-- | @appendSub@ appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument --- of the form 'prefix=listOfSubarguments' is appended to the expression. +-- of the form @prefix=listOfSubarguments@ is appended to the expression. -- Note: nothing is done if the list of sub-arguments is empty. appendSub :: String -> [String] -> Args appendSub prefix xs @@ -103,8 +114,8 @@ appendSub prefix xs then unwords (y : xs') : go True ys else y : go found ys --- appendSubD is similar to appendSub but it extracts the list of sub-arguments --- from the given DiffExpr. +-- | @appendSubD@ is similar to 'appendSub' but it extracts the list of sub-arguments +-- from the given 'DiffExpr'. appendSubD :: String -> Args -> Args appendSubD prefix diffExpr = fromDiffExpr diffExpr >>= appendSub prefix @@ -115,12 +126,12 @@ filterSub prefix p = apply $ map filterSubstr | prefix `isPrefixOf` s = unwords . filter p . words $ s | otherwise = s --- Remove given elements from a list of sub-arguments with a given prefix +-- | Remove given elements from a list of sub-arguments with a given prefix -- Example: removeSub "--configure-option=CFLAGS" ["-Werror"] removeSub :: String -> [String] -> Args removeSub prefix xs = filterSub prefix (`notElem` xs) --- Interpret a given expression in a given environment +-- | Interpret a given expression in a given environment interpret :: Target -> Expr a -> Action a interpret = flip runReaderT @@ -131,41 +142,46 @@ interpretWithStage :: Stage -> Expr a -> Action a interpretWithStage s = interpretPartial $ PartialTarget s (error "interpretWithStage: package not set") --- Extract an expression from a difference expression +-- | Extract an expression from a difference expression fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) --- Interpret a given difference expression in a given environment +-- | Interpret a given difference expression in a given environment interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a interpretDiff target = interpret target . fromDiffExpr --- Convenient getters for target parameters +-- | Convenient getters for target parameters getStage :: Expr Stage getStage = asks stage +-- | Get the 'Package' of the current 'Target' getPackage :: Expr Package getPackage = asks package +-- | Get the 'Builder' for the current 'Target' getBuilder :: Expr Builder getBuilder = asks builder +-- | Get the 'Way' of the current 'Target' getWay :: Expr Way getWay = asks way +-- | Get the input files of the current 'Target' getInputs :: Expr [FilePath] getInputs = asks inputs --- Run getInputs and check that the result contains a single input file only +-- | Run 'getInputs' and check that the result contains a single input file only getInput :: Expr FilePath getInput = do target <- ask getSingleton getInputs $ "getInput: exactly one input file expected in target " ++ show target +-- | Get the files produced by the current 'Target' getOutputs :: Expr [FilePath] getOutputs = asks outputs --- Run getOutputs and check that the result contains a output file only +-- | Run 'getOutputs' and check that the result contains a output file only getOutput :: Expr FilePath getOutput = do target <- ask From git at git.haskell.org Thu Oct 26 23:46:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix postProcessPackageData. (bf9edba) Message-ID: <20171026234608.832723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf9edba4364ffc59eb13b6501c11560b71b6e620/ghc >--------------------------------------------------------------- commit bf9edba4364ffc59eb13b6501c11560b71b6e620 Author: Andrey Mokhov Date: Tue Dec 30 17:32:37 2014 +0000 Fix postProcessPackageData. >--------------------------------------------------------------- bf9edba4364ffc59eb13b6501c11560b71b6e620 src/Util.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index b8a38f4..846f547 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -19,8 +19,12 @@ replaceEq from = replaceIf (== from) -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' --- 2) Replace '/' and '\' with '_' +-- 2) Replace '/' and '\' with '_' before '=' postProcessPackageData :: FilePath -> Action () postProcessPackageData file = do pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map (replaceIf isSlash '_') pkgData + length pkgData `seq` writeFileLines file $ map processLine pkgData + where + processLine line = replaceIf isSlash '_' prefix ++ suffix + where + (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:46:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds ghc-split generator, generateScripts and re-enables SplitObjects (7470e5d) Message-ID: <20171026234610.7519E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7470e5d6f71ef5a662e8b0b1791683a03cbbebb8/ghc >--------------------------------------------------------------- commit 7470e5d6f71ef5a662e8b0b1791683a03cbbebb8 Author: Moritz Angermann Date: Sat Jan 9 14:39:14 2016 +0800 Adds ghc-split generator, generateScripts and re-enables SplitObjects Fixes #84. >--------------------------------------------------------------- 7470e5d6f71ef5a662e8b0b1791683a03cbbebb8 shaking-up-ghc.cabal | 1 + src/Main.hs | 1 + src/Rules/Generate.hs | 37 +++++++++++++++++++++++++++++++++++-- src/Rules/Generators/GhcSplit.hs | 25 +++++++++++++++++++++++++ src/Settings/User.hs | 3 ++- 5 files changed, 64 insertions(+), 3 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 066b9e7..bd6e31f 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -47,6 +47,7 @@ executable ghc-shake , Rules.Generators.GhcAutoconfH , Rules.Generators.GhcBootPlatformH , Rules.Generators.GhcPlatformH + , Rules.Generators.GhcSplit , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs , Rules.IntegerGmp diff --git a/src/Main.hs b/src/Main.hs index 1710b39..a56f9ed 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -19,6 +19,7 @@ main = shakeArgs options rules , Rules.Config.configRules , Rules.Generate.copyRules , Rules.Generate.generateRules + , Rules.Generate.generateScripts , Rules.generateTargets , Rules.IntegerGmp.integerGmpRules , Rules.Libffi.libffiRules diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 71d88b1..3b6dfdc 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,5 +1,5 @@ module Rules.Generate ( - generatePackageCode, generateRules, + generatePackageCode, generateRules, generateScripts, derivedConstantsPath, generatedDependencies, installTargets, copyRules ) where @@ -11,6 +11,7 @@ import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH import Rules.Generators.GhcBootPlatformH import Rules.Generators.GhcPlatformH +import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles @@ -80,7 +81,7 @@ compilerDependencies stage = generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage + | pkg == compiler = compilerDependencies stage ++ ["inplace/lib/bin/ghc-split"] | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = includesDependencies ++ derivedConstantsDependencies | stage == Stage0 = defaultDependencies @@ -104,6 +105,13 @@ generate file target expr = do writeFileChanged file contents putSuccess $ "| Successfully generated '" ++ file ++ "'." +-- | Generates @file@ for @target@ and marks it as executable. +generateExec :: FilePath -> PartialTarget -> Expr String -> Action () +generateExec file target expr = do + generate file target expr + unit $ cmd "chmod +x " [file] + putSuccess $ "| Made '" ++ file ++ "' executable." + generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let buildPath = targetPath stage pkg -/- "build" @@ -177,6 +185,31 @@ generateRules = do where file <~ gen = file %> \out -> generate out emptyTarget gen +-- | Generate scripts the build system requires. For now we generate the +-- @ghc-split@ script from it's literate perl source. +generateScripts :: Rules () +generateScripts = do + -- how to translate literate perl to perl. + -- this is a hack :-/ + "//*.prl" %> \out -> do + let src = out -<.> "lprl" + path <- builderPath Unlit + need [path] + unit $ cmd [path] [src] [out] + + -- ghc-split is only a perl script. + let ghcSplit = "inplace/lib/ghc-split" -- See system.config + let ghcSplitBin = "inplace/lib/bin/ghc-split" -- See ConfigHs.hs + + ghcSplit <~ generateGhcSplit + + ghcSplitBin %> \out -> do + need [ghcSplit] + copyFileChanged ghcSplit out + + where + file <~ gen = file %> \out -> generateExec out emptyTarget gen + -- TODO: Use the Types, Luke! (drop partial function) -- We sometimes need to evaluate expressions that do not require knowing all -- information about the target. In this case, we don't want to know anything. diff --git a/src/Rules/Generators/GhcSplit.hs b/src/Rules/Generators/GhcSplit.hs new file mode 100644 index 0000000..77cd49f --- /dev/null +++ b/src/Rules/Generators/GhcSplit.hs @@ -0,0 +1,25 @@ +module Rules.Generators.GhcSplit (generateGhcSplit) where + +import Base +import Expression +import Oracles +import Settings.User + +generateGhcSplit :: Expr String +generateGhcSplit = do + let yesNo = lift . fmap (\x -> if x then "YES" else "NO") + perl <- getBuilderPath Perl + let script = "driver" -/- "split" -/- "ghc-split.prl" + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules" -/- "Generators" -/- "GhcSplit.hs"] + lift $ need [script] + targetPlatform <- getSetting TargetPlatform + ghcEnableTNC <- yesNo ghcEnableTablesNextToCode + contents <- lift $ readFileLines script + return . unlines $ + [ "#!" ++ perl + , "$TARGETPLATFORM = \"" ++ targetPlatform ++ "\";" + -- I don't see where the ghc-split tool uses TNC, but + -- it's in the build-perl macro. + , "$TABLES_NEXT_TO_CODE = \"" ++ ghcEnableTNC ++ "\";" + ] ++ contents diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 7a877ce..6ba7155 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -9,6 +9,7 @@ module Settings.User ( import GHC import Expression import Predicates +import Settings.Default -- Control user-specific settings userArgs :: Args @@ -59,7 +60,7 @@ validating = False -- To switch off split objects change to 'return False' splitObjects :: Predicate -splitObjects = return False -- FIXME: should be defaultSplitObjects, see #84. +splitObjects = defaultSplitObjects dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Thu Oct 26 23:46:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove `make inplace/bin/ghc-cabal` (see #23) (c1802dc) Message-ID: <20171026234611.38A8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1802dc7290cf3b694fefa3e338b49a3b39956d4/ghc >--------------------------------------------------------------- commit c1802dc7290cf3b694fefa3e338b49a3b39956d4 Author: Andrey Mokhov Date: Thu Dec 24 13:00:08 2015 +0000 Remove `make inplace/bin/ghc-cabal` (see #23) >--------------------------------------------------------------- c1802dc7290cf3b694fefa3e338b49a3b39956d4 README.md | 2 -- 1 file changed, 2 deletions(-) diff --git a/README.md b/README.md index 3c42074..4fab178 100644 --- a/README.md +++ b/README.md @@ -25,7 +25,6 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure -make inplace/bin/ghc-cabal # This needs to be fixed ``` Now you have a couple of options: @@ -45,7 +44,6 @@ $ cd ghc $ git clone git://github.com/snowleopard/shaking-up-ghc shake-build $ ./boot $ ./configure --enable-tarballs-autodownload -$ make inplace/bin/ghc-cabal # This needs to be fixed $ shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. From git at git.haskell.org Thu Oct 26 23:46:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add supports-package-key to configuration files. (96dec4a) Message-ID: <20171026234612.0AA123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/96dec4ae3f1dc8dde6647ecc87a62b87a24589ee/ghc >--------------------------------------------------------------- commit 96dec4ae3f1dc8dde6647ecc87a62b87a24589ee Author: Andrey Mokhov Date: Tue Dec 30 19:34:26 2014 +0000 Add supports-package-key to configuration files. >--------------------------------------------------------------- 96dec4ae3f1dc8dde6647ecc87a62b87a24589ee cfg/default.config.in | 1 + 1 file changed, 1 insertion(+) diff --git a/cfg/default.config.in b/cfg/default.config.in index 1a28981..50c3937 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -30,6 +30,7 @@ gcc-lt-46 = @GccLT46@ lax-dependencies = NO dynamic-ghc-programs = NO +supports-package-key = @SUPPORTS_PACKAGE_KEY@ # Information about host and target systems: #=========================================== From git at git.haskell.org Thu Oct 26 23:46:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add the author's email. (3f55a9e) Message-ID: <20171026234614.C84D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3f55a9ed5d25f9f6310b76db5a0befe1b66aa19d/ghc >--------------------------------------------------------------- commit 3f55a9ed5d25f9f6310b76db5a0befe1b66aa19d Author: Andrey Mokhov Date: Thu Dec 24 19:50:10 2015 +0000 Add the author's email. >--------------------------------------------------------------- 3f55a9ed5d25f9f6310b76db5a0befe1b66aa19d shaking-up-ghc.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 4cfb30d..f1a3f10 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -3,9 +3,9 @@ version: 0.1.0.0 synopsis: GHC build system license: BSD3 license-file: LICENSE -author: Andrey Mokhov, Github: @snowleopard -maintainer: Andrey Mokhov, Github: @snowleopard -copyright: Andrey Mokhov, Github: @snowleopard +author: Andrey Mokhov , github: @snowleopard +maintainer: Andrey Mokhov , github: @snowleopard +copyright: Andrey Mokhov 2014-2015 category: Development build-type: Simple cabal-version: >=1.10 From git at git.haskell.org Thu Oct 26 23:46:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Extra library (693a66c) Message-ID: <20171026234613.E960F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/693a66cafe77e0ea2449e9f7b4bc51145c97ab38/ghc >--------------------------------------------------------------- commit 693a66cafe77e0ea2449e9f7b4bc51145c97ab38 Author: Moritz Angermann Date: Sat Jan 9 17:04:58 2016 +0800 Use Extra library - replaces `wordsWhen` with `wordsBy` - replaces `replace` with `replace` Fixes #130 >--------------------------------------------------------------- 693a66cafe77e0ea2449e9f7b4bc51145c97ab38 src/Base.hs | 23 ++--------------------- src/Oracles/LookupInPath.hs | 3 ++- src/Rules/Data.hs | 1 + src/Rules/Libffi.hs | 1 + 4 files changed, 6 insertions(+), 22 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 925c427..fb33907 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,9 +22,9 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, renderBox, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, replaceEq, replace, quote, chunksOfSize, + bimap, minusOrd, intersectOrd, replaceEq, quote, chunksOfSize, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), - versionToInt, removeFileIfExists, removeDirectoryIfExists, wordsWhen + versionToInt, removeFileIfExists, removeDirectoryIfExists ) where import Control.Applicative @@ -90,25 +90,6 @@ replaceSeparators = replaceWhen isPathSeparator replaceWhen :: (a -> Bool) -> a -> [a] -> [a] replaceWhen p to = map (\from -> if p from then to else from) --- | Find all occurrences of substring 'from' and replace them to 'to' in a --- given string. Not very efficient, but simple and fast enough for our purposes -replace :: Eq a => [a] -> [a] -> [a] -> [a] -replace from to = go - where - skipFrom = drop $ length from - go [] = [] - go s @ (x : xs) - | from `isPrefixOf` s = to ++ go (skipFrom s) - | otherwise = x : go xs - --- | Split a list into chunks in places where the predicate @p@ holds. --- See: http://stackoverflow.com/a/4981265 -wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] -wordsWhen p list = - case dropWhile p list of - [] -> [] - l -> w : wordsWhen p rest where (w, rest) = break p l - -- | @chunksOfSize size strings@ splits a given list of strings into chunks not -- exceeding the given @size at . chunksOfSize :: Int -> [String] -> [[String]] diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index c2a05e2..2532cb9 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -4,6 +4,7 @@ module Oracles.LookupInPath ( ) where import Base +import Extra (wordsBy) newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -22,7 +23,7 @@ lookupInPath c lookupInPathOracle :: Rules () lookupInPathOracle = do o <- newCache $ \c -> do - envPaths <- wordsWhen (== ':') <$> getEnvWithDefault "" "PATH" + envPaths <- wordsBy (== ':') <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths -- this will crash if we do not find any valid candidate. fullCommand <- head <$> filterM doesFileExist candidates diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index de4f8c0..b2c5878 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -2,6 +2,7 @@ module Rules.Data (buildPackageData) where import Base import Expression +import Extra (replace) import GHC import Oracles import Predicates (registerPackage) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 9d77814..31f249b 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -2,6 +2,7 @@ module Rules.Libffi (libffiRules, libffiDependencies) where import Base import Expression +import Extra (replace) import GHC import Oracles import Rules.Actions From git at git.haskell.org Thu Oct 26 23:46:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement more arguments for ghc -M. (21bfb81) Message-ID: <20171026234615.6FA2D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21bfb816a7be0bcd0ef72d562001d5948998565a/ghc >--------------------------------------------------------------- commit 21bfb816a7be0bcd0ef72d562001d5948998565a Author: Andrey Mokhov Date: Tue Dec 30 19:35:13 2014 +0000 Implement more arguments for ghc -M. >--------------------------------------------------------------- 21bfb816a7be0bcd0ef72d562001d5948998565a src/Oracles.hs | 24 +++++++++++++----------- src/Package.hs | 28 ++++++++++++++++++++++------ 2 files changed, 35 insertions(+), 17 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index ff4bd95..9b63c4f 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -136,7 +136,7 @@ argOption opt = do data Flag = LaxDeps | DynamicGhcPrograms | GhcWithInterpreter | HsColourSrcs | GccIsClang | GccLt46 | CrossCompiling | Validating | PlatformSupportsSharedLibs - | WindowsHost + | WindowsHost | SupportsPackageKey test :: Flag -> Action Bool test GhcWithInterpreter = do @@ -161,12 +161,13 @@ test WindowsHost = do test flag = do (key, defaultValue) <- return $ case flag of - LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file - DynamicGhcPrograms -> ("dynamic-ghc-programs", False) - GccIsClang -> ("gcc-is-clang" , False) - GccLt46 -> ("gcc-lt-46" , False) - CrossCompiling -> ("cross-compiling" , False) - Validating -> ("validating" , False) + LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file + DynamicGhcPrograms -> ("dynamic-ghc-programs" , False) + GccIsClang -> ("gcc-is-clang" , False) + GccLt46 -> ("gcc-lt-46" , False) + CrossCompiling -> ("cross-compiling" , False) + Validating -> ("validating" , False) + SupportsPackageKey -> ("supports-package-key" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ do putLoud $ "\nFlag '" -- TODO: Give the warning *only once* per key @@ -264,13 +265,14 @@ packagaDataOptionWithDefault file key defaultAction = do Just value -> return value Nothing -> defaultAction -data PackageDataKey = Modules | SrcDirs +data PackageDataKey = Modules | SrcDirs | PackageKey packagaDataOption :: FilePath -> PackageDataKey -> Action String packagaDataOption file key = do - let keyName = replaceIf isSlash '_' $ takeDirectory file ++ case key of - Modules -> "_MODULES" - SrcDirs -> "_HS_SRC_DIRS" + let keyName = replaceIf isSlash '_' $ takeDirectory file ++ "_" ++ case key of + Modules -> "MODULES" + SrcDirs -> "HS_SRC_DIRS" -- TODO: add "." as a default? + PackageKey -> "PACKAGE_KEY" packagaDataOptionWithDefault file keyName $ error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." diff --git a/src/Package.hs b/src/Package.hs index 9e60a24..ba77bdf 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -161,7 +161,6 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = , arg [path dist "inplace-pkg-config"] ] --- "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs -- $1_$2_$3_MOST_DIR_HC_OPTS = \ -- $$($1_$2_$3_MOST_HC_OPTS) \ @@ -186,6 +185,8 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- done -- endif +-- "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs + -- $1_$2_$3_MOST_HC_OPTS = \ -- $$(WAY_$3_HC_OPTS) \ -- $$(CONF_HC_OPTS) \ @@ -213,24 +214,39 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) --- TODO: double-check that ignoring $1_$2_HS_SRC_DIRS is safe --- Options CONF_HC_OPTS and +-- TODO: double-check that ignoring SrcDirs ($1_$2_HS_SRC_DIRS) is safe +-- TODO: add $1_HC_OPTS +-- TODO: check that the package is not a program ($1_$2_PROG == "") +-- TODO: handle empty $1_PACKAGE +-- Option CONF_HC_OPTS is skipped buildPackageDeps :: Package -> TodoItem -> Rules () buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist in (buildDir "build" name <.> "m") %> \out -> do - let pkgData = buildDir "package-data.mk" - autogen = dist "build" "autogen" - mods <- words <$> packagaDataOption pkgData Modules + let pkgData = buildDir "package-data.mk" + autogen = dist "build" "autogen" + mods <- words <$> packagaDataOption pkgData Modules + srcDirs <- words <$> packagaDataOption pkgData SrcDirs src <- getDirectoryFiles "" $ do start <- map (replaceEq '.' '/') mods end <- [".hs", ".lhs"] return $ path ++ "//" ++ start ++ end + packageKey <- packagaDataOption pkgData PackageKey run (Ghc stage) $ mconcat [ arg ["-M"] , wayHcOpts vanilla -- TODO: is this needed? shall we run GHC -M multiple times? , splitArgs $ argOption SrcHcOpts + , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] + , when (not SupportsPackageKey && stage == Stage0) $ arg ["-package-name"] + , when ( SupportsPackageKey || stage /= Stage0) $ arg ["-this-package-key"] + , arg [packageKey] + , arg ["-hide-all-packages"] + , arg $ map (\d -> "-i" ++ path ++ "/" ++ d) srcDirs + , arg $ do + prefix <- ["-i", "-I"] + suffix <- ["build", "build/autogen"] + return $ prefix ++ path dist suffix , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] , arg [unwords src] ] From git at git.haskell.org Thu Oct 26 23:46:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #140 from snowleopard/feature/use-extra (8c2a30d) Message-ID: <20171026234617.876543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c2a30db05a56cd1e1c33c34acbe3a794a7b00d7/ghc >--------------------------------------------------------------- commit 8c2a30db05a56cd1e1c33c34acbe3a794a7b00d7 Merge: a64efa9 693a66c Author: Andrey Mokhov Date: Sat Jan 9 12:15:46 2016 +0000 Merge pull request #140 from snowleopard/feature/use-extra Use Extra library >--------------------------------------------------------------- 8c2a30db05a56cd1e1c33c34acbe3a794a7b00d7 src/Base.hs | 23 ++--------------------- src/Oracles/LookupInPath.hs | 3 ++- src/Rules/Data.hs | 1 + src/Rules/Libffi.hs | 1 + 4 files changed, 6 insertions(+), 22 deletions(-) From git at git.haskell.org Thu Oct 26 23:46:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move OverloadedStrings to other-extensions. (b56b886) Message-ID: <20171026234618.5A7AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b56b88616e82fb652c49ea9f6c087dd76e950a42/ghc >--------------------------------------------------------------- commit b56b88616e82fb652c49ea9f6c087dd76e950a42 Author: Andrey Mokhov Date: Thu Dec 24 20:24:14 2015 +0000 Move OverloadedStrings to other-extensions. >--------------------------------------------------------------- b56b88616e82fb652c49ea9f6c087dd76e950a42 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f1a3f10..098d8b2 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -72,11 +72,11 @@ executable ghc-shake default-extensions: BangPatterns , LambdaCase , MultiWayIf - , OverloadedStrings , TupleSections other-extensions: DeriveDataTypeable , DeriveGeneric , FlexibleInstances + , OverloadedStrings build-depends: base , ansi-terminal >= 0.6 , Cabal >= 1.22 From git at git.haskell.org Thu Oct 26 23:46:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace isSlash with standard isPathSeparator. (212e91f) Message-ID: <20171026234619.07E2E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/212e91f1a18f71e467ca68e929294b943c2cf171/ghc >--------------------------------------------------------------- commit 212e91f1a18f71e467ca68e929294b943c2cf171 Author: Andrey Mokhov Date: Wed Dec 31 03:50:59 2014 +0000 Replace isSlash with standard isPathSeparator. >--------------------------------------------------------------- 212e91f1a18f71e467ca68e929294b943c2cf171 src/Util.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index 846f547..af23f27 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,5 @@ module Util ( module Data.Char, - isSlash, replaceIf, replaceEq, postProcessPackageData ) where @@ -8,9 +7,6 @@ module Util ( import Base import Data.Char -isSlash :: Char -> Bool -isSlash = (`elem` ['/', '\\']) - replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -25,6 +21,6 @@ postProcessPackageData file = do pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) length pkgData `seq` writeFileLines file $ map processLine pkgData where - processLine line = replaceIf isSlash '_' prefix ++ suffix + processLine line = replaceIf isPathSeparator '_' prefix ++ suffix where (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:46:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Export wayHcOpts. (980d486) Message-ID: <20171026234601.8DBE03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/980d48665a5bd7dfb275d403628e34b140bd2567/ghc >--------------------------------------------------------------- commit 980d48665a5bd7dfb275d403628e34b140bd2567 Author: Andrey Mokhov Date: Tue Dec 30 17:06:00 2014 +0000 Export wayHcOpts. >--------------------------------------------------------------- 980d48665a5bd7dfb275d403628e34b140bd2567 src/Ways.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Ways.hs b/src/Ways.hs index 91cbd4f..a0e886a 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -12,6 +12,7 @@ module Ways ( threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic, + wayHcOpts, hisuf, osuf, hcsuf ) where From git at git.haskell.org Thu Oct 26 23:46:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #34 from bgamari/master (20b4c08) Message-ID: <20171026234603.A68A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20b4c080dedd0fd6c1ce6a7d9b8543b8c97cf82e/ghc >--------------------------------------------------------------- commit 20b4c080dedd0fd6c1ce6a7d9b8543b8c97cf82e Merge: 013fa90 263fc63 Author: Andrey Mokhov Date: Thu Dec 24 12:33:42 2015 +0000 Merge pull request #34 from bgamari/master Expression: Add Haddocks >--------------------------------------------------------------- 20b4c080dedd0fd6c1ce6a7d9b8543b8c97cf82e src/Expression.hs | 88 ++++++++++++++++++++++++++++++++----------------------- 1 file changed, 52 insertions(+), 36 deletions(-) From git at git.haskell.org Thu Oct 26 23:46:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Unlit utility (cce8759) Message-ID: <20171026234602.EEDE43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cce8759fdf3eed5988013cea4d2810457e8272a0/ghc >--------------------------------------------------------------- commit cce8759fdf3eed5988013cea4d2810457e8272a0 Author: Moritz Angermann Date: Fri Jan 8 18:21:31 2016 +0800 Adds Unlit utility Adds the unlit utility to turn literate files into unliterate files. Fixes #83 >--------------------------------------------------------------- cce8759fdf3eed5988013cea4d2810457e8272a0 shaking-up-ghc.cabal | 1 + src/GHC.hs | 14 +++++++++----- src/Rules/Data.hs | 11 +++++++++++ src/Settings/Args.hs | 4 +++- src/Settings/Packages/{Hp2ps.hs => Unlit.hs} | 10 +++++----- 5 files changed, 29 insertions(+), 11 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index ab9f7bc..066b9e7 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -91,6 +91,7 @@ executable ghc-shake , Settings.Packages.Rts , Settings.Packages.RunGhc , Settings.Packages.Touchy + , Settings.Packages.Unlit , Settings.TargetDirectory , Settings.User , Settings.Ways diff --git a/src/GHC.hs b/src/GHC.hs index 3d99e63..c26f552 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -6,7 +6,7 @@ module GHC ( haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unix, win32, xhtml, + touchy, transformers, unlit, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -28,7 +28,7 @@ defaultKnownPackages = , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time - , touchy, transformers, unix, win32, xhtml ] + , touchy, transformers, unlit, unix, win32, xhtml ] -- Package definitions (see "Package") array, base, binary, bytestring, cabal, compiler, containers, compareSizes, @@ -37,7 +37,7 @@ array, base, binary, bytestring, cabal, compiler, containers, compareSizes, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unix, win32, xhtml :: Package + touchy, transformers, unlit, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -85,11 +85,12 @@ terminfo = library "terminfo" time = library "time" touchy = utility "touchy" transformers = library "transformers" +unlit = utility "unlit" unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" --- TODO: The following utils are not implemented yet: unlit, driver/ghc-split +-- TODO: The following utils are not implemented yet: driver/ghc-split -- TODO: The following utils are not included into the build system because -- they seem to be unused or unrelated to the build process: checkUniques, -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, @@ -112,9 +113,12 @@ defaultProgramPath stage pkg | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing - | pkg == touchy = case stage of + | pkg == touchy = case stage of Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe _ -> Nothing + | pkg == unlit = case stage of + Stage0 -> Just $ "inplace/lib" -/- pkgNameString pkg <.> exe + _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index de4f8c0..8b21fc7 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -67,6 +67,17 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." + when (pkg == unlit) $ dataFile %> \mk -> do + let prefix = "utils_unlit_" ++ stageString stage ++ "_" + contents = unlines $ map (prefix++) + [ "PROGNAME = unlit" + , "C_SRCS = unlit.c" + , "INSTALL = YES" + , "INSTALL_INPLACE = YES" + , "SYNOPSIS = Literate script filter." ] + writeFileChanged mk contents + putSuccess $ "| Successfully generated '" ++ mk ++ "'." + when (pkg == touchy) $ dataFile %> \mk -> do let prefix = "utils_touchy_" ++ stageString stage ++ "_" contents = unlines $ map (prefix++) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index f2b30fa..3bd32d7 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -31,6 +31,7 @@ import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc import Settings.Packages.Touchy +import Settings.Packages.Unlit import Settings.User getArgs :: Expr [String] @@ -77,4 +78,5 @@ defaultPackageArgs = mconcat , iservBinPackageArgs , rtsPackageArgs , runGhcPackageArgs - , touchyPackageArgs ] + , touchyPackageArgs + , unlitPackageArgs ] diff --git a/src/Settings/Packages/Hp2ps.hs b/src/Settings/Packages/Unlit.hs similarity index 68% copy from src/Settings/Packages/Hp2ps.hs copy to src/Settings/Packages/Unlit.hs index 26518c6..e654a66 100644 --- a/src/Settings/Packages/Hp2ps.hs +++ b/src/Settings/Packages/Unlit.hs @@ -1,13 +1,13 @@ -module Settings.Packages.Hp2ps (hp2psPackageArgs) where +module Settings.Packages.Unlit (unlitPackageArgs) where import Base import Expression -import GHC (hp2ps) +import GHC (unlit) import Predicates (builderGhc, package) -import Settings +import Settings (getTargetPath) -hp2psPackageArgs :: Args -hp2psPackageArgs = package hp2ps ? do +unlitPackageArgs :: Args +unlitPackageArgs = package unlit ? do path <- getTargetPath let cabalMacros = path -/- "build/autogen/cabal_macros.h" mconcat [ builderGhc ? From git at git.haskell.org Thu Oct 26 23:46:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for src-hc-opts configuration option. (9007c90) Message-ID: <20171026234605.19E5E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9007c90cce429df3f0f60737d4a93a127f5e5274/ghc >--------------------------------------------------------------- commit 9007c90cce429df3f0f60737d4a93a127f5e5274 Author: Andrey Mokhov Date: Tue Dec 30 17:06:52 2014 +0000 Add support for src-hc-opts configuration option. >--------------------------------------------------------------- 9007c90cce429df3f0f60737d4a93a127f5e5274 src/Oracles.hs | 2 ++ src/Package.hs | 50 ++++++++++++++++++++++++++------------------------ 2 files changed, 28 insertions(+), 24 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 75439fb..ff4bd95 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -101,6 +101,7 @@ run builder args = do data Option = TargetOS | TargetArch | TargetPlatformFull | ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage | IconvIncludeDirs | IconvLibDirs | GmpIncludeDirs | GmpLibDirs + | SrcHcOpts | HostOsCpp | Root option :: Option -> Action String @@ -125,6 +126,7 @@ option opt = askConfig $ case opt of IconvLibDirs -> "iconv-lib-dirs" GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" + SrcHcOpts -> "src-hc-opts" HostOsCpp -> "host-os-cpp" argOption :: Option -> Args diff --git a/src/Package.hs b/src/Package.hs index 24ef85d..9e60a24 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -163,6 +163,29 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs +-- $1_$2_$3_MOST_DIR_HC_OPTS = \ +-- $$($1_$2_$3_MOST_HC_OPTS) \ +-- -odir $1/$2/build -hidir $1/$2/build -stubdir $1/$2/build + +-- # Some of the Haskell files (e.g. utils/hsc2hs/Main.hs) (directly or +-- # indirectly) include the generated includes files. +-- $$($1_$2_depfile_haskell) : $$(includes_H_CONFIG) $$(includes_H_PLATFORM) +-- +-- $$($1_$2_depfile_haskell) : $$($1_$2_HS_SRCS) $$($1_$2_HS_BOOT_SRCS) $$$$($1_$2_HC_MK_DEPEND_DEP) | $$$$(dir $$$$@)/. +-- $$(call removeFiles,$$@.tmp) +-- ifneq "$$($1_$2_HS_SRCS)" "" +-- "$$($1_$2_HC_MK_DEPEND)" -M \ +-- $$($1_$2_$$(firstword $$($1_$2_WAYS))_MOST_DIR_HC_OPTS) \ +-- $$($1_$2_MKDEPENDHS_FLAGS) \ +-- $$($1_$2_HS_SRCS) +-- endif +-- echo "$1_$2_depfile_haskell_EXISTS = YES" >> $$@.tmp +-- ifneq "$$($1_$2_SLASH_MODS)" "" +-- for dir in $$(sort $$(foreach mod,$$($1_$2_SLASH_MODS),$1/$2/build/$$(dir $$(mod)))); do \ +-- if test ! -d $$$$dir; then mkdir -p $$$$dir; fi \ +-- done +-- endif + -- $1_$2_$3_MOST_HC_OPTS = \ -- $$(WAY_$3_HC_OPTS) \ -- $$(CONF_HC_OPTS) \ @@ -190,31 +213,8 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) - --- $1_$2_$3_MOST_DIR_HC_OPTS = \ --- $$($1_$2_$3_MOST_HC_OPTS) \ --- -odir $1/$2/build -hidir $1/$2/build -stubdir $1/$2/build - --- # Some of the Haskell files (e.g. utils/hsc2hs/Main.hs) (directly or --- # indirectly) include the generated includes files. --- $$($1_$2_depfile_haskell) : $$(includes_H_CONFIG) $$(includes_H_PLATFORM) --- --- $$($1_$2_depfile_haskell) : $$($1_$2_HS_SRCS) $$($1_$2_HS_BOOT_SRCS) $$$$($1_$2_HC_MK_DEPEND_DEP) | $$$$(dir $$$$@)/. --- $$(call removeFiles,$$@.tmp) --- ifneq "$$($1_$2_HS_SRCS)" "" --- "$$($1_$2_HC_MK_DEPEND)" -M \ --- $$($1_$2_$$(firstword $$($1_$2_WAYS))_MOST_DIR_HC_OPTS) \ --- $$($1_$2_MKDEPENDHS_FLAGS) \ --- $$($1_$2_HS_SRCS) --- endif --- echo "$1_$2_depfile_haskell_EXISTS = YES" >> $$@.tmp --- ifneq "$$($1_$2_SLASH_MODS)" "" --- for dir in $$(sort $$(foreach mod,$$($1_$2_SLASH_MODS),$1/$2/build/$$(dir $$(mod)))); do \ --- if test ! -d $$$$dir; then mkdir -p $$$$dir; fi \ --- done --- endif - -- TODO: double-check that ignoring $1_$2_HS_SRC_DIRS is safe +-- Options CONF_HC_OPTS and buildPackageDeps :: Package -> TodoItem -> Rules () buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist @@ -229,6 +229,8 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = return $ path ++ "//" ++ start ++ end run (Ghc stage) $ mconcat [ arg ["-M"] + , wayHcOpts vanilla -- TODO: is this needed? shall we run GHC -M multiple times? + , splitArgs $ argOption SrcHcOpts , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] , arg [unwords src] ] From git at git.haskell.org Thu Oct 26 23:46:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds knowledge about Perl (bd5bc65) Message-ID: <20171026234606.A56EC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd5bc6544a5594bc69027d96b7e30da720812922/ghc >--------------------------------------------------------------- commit bd5bc6544a5594bc69027d96b7e30da720812922 Author: Moritz Angermann Date: Sat Jan 9 14:38:18 2016 +0800 Adds knowledge about Perl Fixes #82. Let's hope this is only a stop gap measure until we get rid of ghc-split as a perl script. >--------------------------------------------------------------- bd5bc6544a5594bc69027d96b7e30da720812922 cfg/system.config.in | 1 + src/Builder.hs | 2 ++ 2 files changed, 3 insertions(+) diff --git a/cfg/system.config.in b/cfg/system.config.in index 292d91f..6338e33 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -40,6 +40,7 @@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ tar = @TarCmd@ +perl = @PerlCmd@ # Information about builders: #============================ diff --git a/src/Builder.hs b/src/Builder.hs index fedcb8a..5450815 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -41,6 +41,7 @@ data Builder = Alex | Ld | Nm | Objdump + | Perl | Ranlib | Tar | Unlit @@ -83,6 +84,7 @@ builderKey builder = case builder of Ld -> "ld" Nm -> "nm" Objdump -> "objdump" + Perl -> "perl" Ranlib -> "ranlib" Tar -> "tar" Unlit -> "unlit" From git at git.haskell.org Thu Oct 26 23:46:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #28 from quchen/cabalify (b053270) Message-ID: <20171026234607.4E5743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b053270c04df9aa94b97ced51704cdc676793745/ghc >--------------------------------------------------------------- commit b053270c04df9aa94b97ced51704cdc676793745 Merge: 20b4c08 5da933f Author: Andrey Mokhov Date: Thu Dec 24 12:35:37 2015 +0000 Merge pull request #28 from quchen/cabalify Add Cabal sandboxed build script >--------------------------------------------------------------- b053270c04df9aa94b97ced51704cdc676793745 .gitignore | 3 ++ README.md | 70 +++++++++++++++++++++++++++++----------- build.cabal.sh | 20 ++++++++++++ shaking-up-ghc.cabal | 91 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 165 insertions(+), 19 deletions(-) From git at git.haskell.org Thu Oct 26 23:46:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Include PR Comments (423c5dd) Message-ID: <20171026234628.613CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/423c5dd10b51f3251d59fec64c68b7bc07019dbf/ghc >--------------------------------------------------------------- commit 423c5dd10b51f3251d59fec64c68b7bc07019dbf Author: Moritz Angermann Date: Sat Jan 9 21:44:23 2016 +0800 Include PR Comments >--------------------------------------------------------------- 423c5dd10b51f3251d59fec64c68b7bc07019dbf shaking-up-ghc.cabal | 1 + src/GHC.hs | 5 +---- src/Main.hs | 3 ++- src/Rules/Generate.hs | 33 ++++----------------------------- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Perl.hs | 25 +++++++++++++++++++++++++ 6 files changed, 34 insertions(+), 35 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index bd6e31f..a5b4c57 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -55,6 +55,7 @@ executable ghc-shake , Rules.Library , Rules.Oracles , Rules.Package + , Rules.Perl , Rules.Program , Rules.Resources , Rules.Wrappers.Ghc diff --git a/src/GHC.hs b/src/GHC.hs index c26f552..3b58bbe 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -113,12 +113,9 @@ defaultProgramPath stage pkg | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing - | pkg == touchy = case stage of + | pkg `elem` [touchy, unlit] = case stage of Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe _ -> Nothing - | pkg == unlit = case stage of - Stage0 -> Just $ "inplace/lib" -/- pkgNameString pkg <.> exe - _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg diff --git a/src/Main.hs b/src/Main.hs index a56f9ed..9f223a8 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -10,6 +10,7 @@ import qualified Rules.Generate import qualified Rules.IntegerGmp import qualified Rules.Libffi import qualified Rules.Oracles +import qualified Rules.Perl main :: IO () main = shakeArgs options rules @@ -19,7 +20,7 @@ main = shakeArgs options rules , Rules.Config.configRules , Rules.Generate.copyRules , Rules.Generate.generateRules - , Rules.Generate.generateScripts + , Rules.Perl.perlScriptRules , Rules.generateTargets , Rules.IntegerGmp.integerGmpRules , Rules.Libffi.libffiRules diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 3b6dfdc..2b2962b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( - generatePackageCode, generateRules, generateScripts, - derivedConstantsPath, generatedDependencies, + generate, generateExec, generatePackageCode, generateRules, + derivedConstantsPath, emptyTarget, generatedDependencies, installTargets, copyRules ) where @@ -11,7 +11,6 @@ import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH import Rules.Generators.GhcBootPlatformH import Rules.Generators.GhcPlatformH -import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles @@ -78,10 +77,11 @@ compilerDependencies stage = , "primop-vector-tys-exports.hs-incl" , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] + ++ ["inplace/lib/bin/ghc-split"] generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage ++ ["inplace/lib/bin/ghc-split"] + | pkg == compiler = compilerDependencies stage | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = includesDependencies ++ derivedConstantsDependencies | stage == Stage0 = defaultDependencies @@ -185,31 +185,6 @@ generateRules = do where file <~ gen = file %> \out -> generate out emptyTarget gen --- | Generate scripts the build system requires. For now we generate the --- @ghc-split@ script from it's literate perl source. -generateScripts :: Rules () -generateScripts = do - -- how to translate literate perl to perl. - -- this is a hack :-/ - "//*.prl" %> \out -> do - let src = out -<.> "lprl" - path <- builderPath Unlit - need [path] - unit $ cmd [path] [src] [out] - - -- ghc-split is only a perl script. - let ghcSplit = "inplace/lib/ghc-split" -- See system.config - let ghcSplitBin = "inplace/lib/bin/ghc-split" -- See ConfigHs.hs - - ghcSplit <~ generateGhcSplit - - ghcSplitBin %> \out -> do - need [ghcSplit] - copyFileChanged ghcSplit out - - where - file <~ gen = file %> \out -> generateExec out emptyTarget gen - -- TODO: Use the Types, Luke! (drop partial function) -- We sometimes need to evaluate expressions that do not require knowing all -- information about the target. In this case, we don't want to know anything. diff --git a/src/Rules/Generators/GhcSplit.hs b/src/Rules/Generators/GhcSplit.hs index 77cd49f..a2bd8b2 100644 --- a/src/Rules/Generators/GhcSplit.hs +++ b/src/Rules/Generators/GhcSplit.hs @@ -9,7 +9,7 @@ generateGhcSplit :: Expr String generateGhcSplit = do let yesNo = lift . fmap (\x -> if x then "YES" else "NO") perl <- getBuilderPath Perl - let script = "driver" -/- "split" -/- "ghc-split.prl" + let script = "driver/split/ghc-split.prl" when trackBuildSystem . lift $ need [sourcePath -/- "Rules" -/- "Generators" -/- "GhcSplit.hs"] lift $ need [script] diff --git a/src/Rules/Perl.hs b/src/Rules/Perl.hs new file mode 100644 index 0000000..c1e5ba8 --- /dev/null +++ b/src/Rules/Perl.hs @@ -0,0 +1,25 @@ +module Rules.Perl (perlScriptRules) where + +import Base +import Expression +import Rules.Actions (runBuilder) +import Rules.Generate (generateExec, emptyTarget) +import Rules.Generators.GhcSplit (generateGhcSplit) + +-- | Generate scripts the build system requires. For now we generate the +-- @ghc-split@ script from it's literate perl source. +perlScriptRules :: Rules () +perlScriptRules = do + -- how to translate literate perl to perl. + -- this is a hack :-/ + "//*.prl" %> \out -> do + let src = out -<.> "lprl" + runBuilder Unlit [src, out] + + -- ghc-split is only a perl script. + let ghcSplit = "inplace/lib/bin/ghc-split" + + ghcSplit <~ generateGhcSplit + + where + file <~ gen = file %> \out -> generateExec out emptyTarget gen From git at git.haskell.org Thu Oct 26 23:46:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Shallow clone GHC from Github instead of Haskell.org (c43d07d) Message-ID: <20171026234621.2ABF93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c43d07d967b7a7876e6a7733a343934d35d0d616/ghc >--------------------------------------------------------------- commit c43d07d967b7a7876e6a7733a343934d35d0d616 Author: David Luposchainsky Date: Sat Jan 9 14:01:33 2016 +0100 Shallow clone GHC from Github instead of Haskell.org >--------------------------------------------------------------- c43d07d967b7a7876e6a7733a343934d35d0d616 .travis.yml | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 6413818..ca51b6f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -39,7 +39,12 @@ install: - alex --version - happy --version - - travis_retry git clone git://git.haskell.org/ghc --recurse-submodules + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ + - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ + - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ + - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ + - travis_retry git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 # Travis clones the project into ".", but we need it as a child directory # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake From git at git.haskell.org Thu Oct 26 23:46:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move parseMakefile from dependenciesOracle to Rules.Dependencies (for better performance) (8fe9fa6) Message-ID: <20171026234621.D3DE83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1/ghc >--------------------------------------------------------------- commit 8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1 Author: Andrey Mokhov Date: Fri Dec 25 01:19:50 2015 +0000 Move parseMakefile from dependenciesOracle to Rules.Dependencies (for better performance) >--------------------------------------------------------------- 8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1 src/Oracles/Dependencies.hs | 7 ++----- src/Rules/Dependencies.hs | 19 +++++++++++++------ 2 files changed, 15 insertions(+), 11 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index c27c2cc..8895758 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -31,11 +31,8 @@ dependenciesOracle :: Rules () dependenciesOracle = do deps <- newCache $ \file -> do putOracle $ "Reading dependencies from " ++ file ++ "..." - contents <- parseMakefile <$> readFile' file - return . Map.fromList . map (bimap unifyPath (map unifyPath)) - . map (bimap head concat . unzip) - . groupBy ((==) `on` fst) - . sortBy (compare `on` fst) $ contents + contents <- map words <$> readFileLines file + return . Map.fromList $ map (\(x:xs) -> (x, xs)) contents _ <- addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file return () diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 47e6c6d..907c4d3 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -21,7 +21,7 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] - hDepFile %> \file -> do + hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) $ need [platformH] -- TODO: very ugly and fragile; use gcc -MM instead? @@ -43,14 +43,21 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = , "primop-vector-tys.hs-incl" ] need $ srcs ++ extraDeps if srcs == [] - then writeFileChanged file "" - else build $ fullTarget target (GhcM stage) srcs [file] - removeFileIfExists $ file <.> "bak" + then writeFileChanged out "" + else build $ fullTarget target (GhcM stage) srcs [out] + removeFileIfExists $ out <.> "bak" - (buildPath -/- ".dependencies") %> \file -> do + (buildPath -/- ".dependencies") %> \out -> do cSrcs <- pkgDataList $ CSrcs path let cDepFiles = [ buildPath -/- src <.> "deps" | src <- cSrcs ] need $ hDepFile : cDepFiles -- need all for more parallelism cDeps <- fmap concat $ mapM readFile' cDepFiles hDeps <- readFile' hDepFile - writeFileChanged file $ cDeps ++ hDeps + let result = unlines + . map (\(src, deps) -> unwords $ src : deps) + . map (bimap unifyPath (map unifyPath)) + . map (bimap head concat . unzip) + . groupBy ((==) `on` fst) + . sortBy (compare `on` fst) + . parseMakefile $ cDeps ++ hDeps + writeFileChanged out result From git at git.haskell.org Thu Oct 26 23:46:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add replaceSeparators to Util.hs. (d043ef5) Message-ID: <20171026234622.993DE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d043ef595a7ee877d8c9659b27e592d361a110c6/ghc >--------------------------------------------------------------- commit d043ef595a7ee877d8c9659b27e592d361a110c6 Author: Andrey Mokhov Date: Wed Dec 31 03:59:10 2014 +0000 Add replaceSeparators to Util.hs. >--------------------------------------------------------------- d043ef595a7ee877d8c9659b27e592d361a110c6 src/Util.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index af23f27..68ed2e5 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,6 @@ module Util ( module Data.Char, - replaceIf, replaceEq, + replaceIf, replaceEq, replaceSeparators, postProcessPackageData ) where @@ -13,6 +13,9 @@ replaceIf p to = map (\from -> if p from then to else from) replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) +replaceSeparators :: String -> String +replaceSeparators = replaceIf isPathSeparator + -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- 2) Replace '/' and '\' with '_' before '=' @@ -21,6 +24,6 @@ postProcessPackageData file = do pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) length pkgData `seq` writeFileLines file $ map processLine pkgData where - processLine line = replaceIf isPathSeparator '_' prefix ++ suffix + processLine line = replaceSeparators '_' prefix ++ suffix where (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:46:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop "ghs-split" builder (b214918) Message-ID: <20171026234624.C92993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b214918b34ab1ab5131457391dbdb4d023ea46e0/ghc >--------------------------------------------------------------- commit b214918b34ab1ab5131457391dbdb4d023ea46e0 Author: Moritz Angermann Date: Sat Jan 9 21:16:20 2016 +0800 Drop "ghs-split" builder >--------------------------------------------------------------- b214918b34ab1ab5131457391dbdb4d023ea46e0 cfg/system.config.in | 3 +-- src/Builder.hs | 2 -- src/Rules/Generators/ConfigHs.hs | 2 +- 3 files changed, 2 insertions(+), 5 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 6338e33..498f78c 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -28,8 +28,7 @@ derive-constants = inplace/bin/deriveConstants hs-cpp = @HaskellCPPCmd@ hs-cpp-args = @HaskellCPPArgs@ -unlit = inplace/lib/unlit -ghc-split = inplace/lib/ghc-split +unlit = inplace/lib/bin/unlit alex = @AlexCmd@ ar = @ArCmd@ diff --git a/src/Builder.hs b/src/Builder.hs index 5450815..efc3216 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -32,7 +32,6 @@ data Builder = Alex | GhcCabalHsColour | GhcM Stage | GhcPkg Stage - | GhcSplit | Haddock | Happy | HsColour @@ -75,7 +74,6 @@ builderKey builder = case builder of GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" - GhcSplit -> "ghc-split" Happy -> "happy" Haddock -> "haddock" HsColour -> "hscolour" diff --git a/src/Rules/Generators/ConfigHs.hs b/src/Rules/Generators/ConfigHs.hs index 547670a..5cdfc3f 100644 --- a/src/Rules/Generators/ConfigHs.hs +++ b/src/Rules/Generators/ConfigHs.hs @@ -32,7 +32,7 @@ generateConfigHs = do cGhcEnableTablesNextToCode <- yesNo ghcEnableTablesNextToCode cLeadingUnderscore <- yesNo $ flag LeadingUnderscore cGHC_UNLIT_PGM <- fmap takeFileName $ getBuilderPath Unlit - cGHC_SPLIT_PGM <- fmap takeBaseName $ getBuilderPath GhcSplit + let cGHC_SPLIT_PGM = "ghc-split" cLibFFI <- lift useLibFFIForAdjustors rtsWays <- getRtsWays cGhcRtsWithLibdw <- getFlag WithLibdw From git at git.haskell.org Thu Oct 26 23:46:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a section on resetting the build (#32) (86ee9f6) Message-ID: <20171026234625.7E1AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86ee9f68057e7ab1a9f09a6d006cddb488c16c02/ghc >--------------------------------------------------------------- commit 86ee9f68057e7ab1a9f09a6d006cddb488c16c02 Author: Andrey Mokhov Date: Fri Dec 25 14:12:35 2015 +0000 Add a section on resetting the build (#32) >--------------------------------------------------------------- 86ee9f68057e7ab1a9f09a6d006cddb488c16c02 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 4fab178..c415ee4 100644 --- a/README.md +++ b/README.md @@ -49,7 +49,9 @@ $ shake-build/build.bat Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. +### Resetting the build +To reset the new build system delete the `shake-build/.db` directory which stores the Shake database. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). How to contribute From git at git.haskell.org Thu Oct 26 23:46:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix replaceSeparators in Util.hs. (34696c1) Message-ID: <20171026234626.23C753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34696c113fedaa2081b179dd4591d6eec8a510e4/ghc >--------------------------------------------------------------- commit 34696c113fedaa2081b179dd4591d6eec8a510e4 Author: Andrey Mokhov Date: Wed Dec 31 04:00:18 2014 +0000 Fix replaceSeparators in Util.hs. >--------------------------------------------------------------- 34696c113fedaa2081b179dd4591d6eec8a510e4 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 68ed2e5..d7e98bd 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -13,7 +13,7 @@ replaceIf p to = map (\from -> if p from then to else from) replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) -replaceSeparators :: String -> String +replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: From git at git.haskell.org Thu Oct 26 23:46:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use `-B` flag to reset the build (bdb88c6) Message-ID: <20171026234629.3CF4C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bdb88c61e4e0761a2ad80904f26d2443fecf7fd4/ghc >--------------------------------------------------------------- commit bdb88c61e4e0761a2ad80904f26d2443fecf7fd4 Author: Andrey Mokhov Date: Fri Dec 25 22:49:45 2015 +0000 Use `-B` flag to reset the build >--------------------------------------------------------------- bdb88c61e4e0761a2ad80904f26d2443fecf7fd4 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index c415ee4..6d27b25 100644 --- a/README.md +++ b/README.md @@ -51,7 +51,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system delete the `shake-build/.db` directory which stores the Shake database. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). +To reset the new build system run the build script with `-B` flag. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). How to contribute From git at git.haskell.org Thu Oct 26 23:46:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Complete first working version of buildPackageDeps rule. (d869302) Message-ID: <20171026234629.B59573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d869302fcad9a124aa65c6075114a6f1f9c7c61d/ghc >--------------------------------------------------------------- commit d869302fcad9a124aa65c6075114a6f1f9c7c61d Author: Andrey Mokhov Date: Wed Dec 31 04:43:53 2014 +0000 Complete first working version of buildPackageDeps rule. >--------------------------------------------------------------- d869302fcad9a124aa65c6075114a6f1f9c7c61d src/Oracles.hs | 18 +++++++++++------ src/Package.hs | 62 ++++++++++++++++++++++++++++++++++------------------------ 2 files changed, 48 insertions(+), 32 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 9b63c4f..4f4cd78 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -265,16 +265,22 @@ packagaDataOptionWithDefault file key defaultAction = do Just value -> return value Nothing -> defaultAction -data PackageDataKey = Modules | SrcDirs | PackageKey +data PackageDataKey = Modules | SrcDirs | PackageKey | IncludeDirs | Deps | DepKeys + deriving Show packagaDataOption :: FilePath -> PackageDataKey -> Action String packagaDataOption file key = do - let keyName = replaceIf isSlash '_' $ takeDirectory file ++ "_" ++ case key of - Modules -> "MODULES" - SrcDirs -> "HS_SRC_DIRS" -- TODO: add "." as a default? - PackageKey -> "PACKAGE_KEY" - packagaDataOptionWithDefault file keyName $ + let (keyName, ifEmpty) = case key of + Modules -> ("MODULES" , "" ) + SrcDirs -> ("HS_SRC_DIRS" , ".") + PackageKey -> ("PACKAGE_KEY" , "" ) + IncludeDirs -> ("INCLUDE_DIRS", ".") + Deps -> ("DEPS" , "" ) + DepKeys -> ("DEP_KEYS" , "" ) + keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName + res <- packagaDataOptionWithDefault file keyFullName $ error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." + return $ if res == "" then ifEmpty else res oracleRules :: Rules () oracleRules = do diff --git a/src/Package.hs b/src/Package.hs index ba77bdf..98558e9 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -214,42 +214,52 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) --- TODO: double-check that ignoring SrcDirs ($1_$2_HS_SRC_DIRS) is safe +-- TODO: make sure SrcDirs ($1_$2_HS_SRC_DIRS) is not empty ('.' by default) -- TODO: add $1_HC_OPTS -- TODO: check that the package is not a program ($1_$2_PROG == "") --- TODO: handle empty $1_PACKAGE +-- TODO: handle empty $1_PACKAGE (can it be empty?) +-- TODO: $1_$2_INCLUDE appears to be not set. Safe to skip? -- Option CONF_HC_OPTS is skipped buildPackageDeps :: Package -> TodoItem -> Rules () buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist in (buildDir "build" name <.> "m") %> \out -> do - let pkgData = buildDir "package-data.mk" - autogen = dist "build" "autogen" - mods <- words <$> packagaDataOption pkgData Modules - srcDirs <- words <$> packagaDataOption pkgData SrcDirs - src <- getDirectoryFiles "" $ do - start <- map (replaceEq '.' '/') mods - end <- [".hs", ".lhs"] - return $ path ++ "//" ++ start ++ end + let pkgData = buildDir "package-data.mk" + usePackageKey <- SupportsPackageKey || stage /= Stage0 -- TODO: check reasoning (distdir-way-opts) + [mods, srcDirs, includeDirs, deps, depKeys] <- + mapM ((fmap words) . (packagaDataOption pkgData)) + [Modules, SrcDirs, IncludeDirs, Deps, DepKeys] + srcs <- getDirectoryFiles "" $ do + dir <- srcDirs + modPath <- map (replaceEq '.' pathSeparator) mods + extension <- ["hs", "lhs"] + return $ path dir modPath <.> extension packageKey <- packagaDataOption pkgData PackageKey run (Ghc stage) $ mconcat - [ arg ["-M"] - , wayHcOpts vanilla -- TODO: is this needed? shall we run GHC -M multiple times? - , splitArgs $ argOption SrcHcOpts - , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] - , when (not SupportsPackageKey && stage == Stage0) $ arg ["-package-name"] - , when ( SupportsPackageKey || stage /= Stage0) $ arg ["-this-package-key"] - , arg [packageKey] - , arg ["-hide-all-packages"] - , arg $ map (\d -> "-i" ++ path ++ "/" ++ d) srcDirs - , arg $ do - prefix <- ["-i", "-I"] - suffix <- ["build", "build/autogen"] - return $ prefix ++ path dist suffix - , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] - , arg [unwords src] - ] + [ arg ["-M"] + , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? + , splitArgs $ argOption SrcHcOpts + , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] + , arg [if usePackageKey then "-this-package-key" else "-package-name"] + , arg [packageKey] -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg ["-hide-all-packages"] + , arg ["-i"] -- resets the search path to nothing; TODO: check if really needed + , arg $ map (\d -> "-i" ++ path d) srcDirs + , arg $ do + prefix <- ["-i", "-I"] -- 'import' and '#include' search paths + suffix <- ["build", "build/autogen"] + return $ prefix ++ buildDir suffix + , arg $ map (\d -> "-I" ++ path d) $ filter isRelative includeDirs + , arg $ map (\d -> "-I" ++ d) $ filter isAbsolute includeDirs + , arg ["-optP-include"] + , arg ["-optP" ++ buildDir "build/autogen/cabal_macros.h"] + , if usePackageKey + then arg $ concatMap (\d -> ["-package-key", d]) depKeys + else arg $ concatMap (\d -> ["-package" , d]) deps + , arg ["-dep-makefile", out, "-dep-suffix", "", "-include-pkg-deps"] + , arg $ map normalise srcs + ] -- $1_$2_MKDEPENDHS_FLAGS = -dep-makefile $$($1_$2_depfile_haskell).tmp $$(foreach way,$$($1_$2_WAYS),-dep-suffix "$$(-- patsubst %o,%,$$($$(way)_osuf))") -- $1_$2_MKDEPENDHS_FLAGS += -include-pkg-deps From git at git.haskell.org Thu Oct 26 23:46:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adjust cmdLineLengthLimit for OS X (e3d96ff) Message-ID: <20171026234631.DC67D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3d96ff27fb0967053043b0d30c0fb4112889613/ghc >--------------------------------------------------------------- commit e3d96ff27fb0967053043b0d30c0fb4112889613 Author: Moritz Angermann Date: Sat Jan 9 21:45:08 2016 +0800 Adjust cmdLineLengthLimit for OS X This should fix #141. >--------------------------------------------------------------- e3d96ff27fb0967053043b0d30c0fb4112889613 src/Oracles/Config/Setting.hs | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index ace9158..58f508b 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -3,7 +3,7 @@ module Oracles.Config.Setting ( setting, settingList, getSetting, getSettingList, anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, windowsHost, ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, - ghcCanonVersion, cmdLineLengthLimit + ghcCanonVersion, cmdLineLengthLimit, osxHost ) where import Control.Monad.Trans.Reader @@ -125,6 +125,9 @@ anyHostOs = matchSetting HostOs windowsHost :: Action Bool windowsHost = anyHostOs ["mingw32", "cygwin32"] +osxHost :: Action Bool +osxHost = anyHostOs ["darwin"] + ghcWithInterpreter :: Action Bool ghcWithInterpreter = do goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "solaris2" @@ -156,6 +159,10 @@ ghcCanonVersion = do cmdLineLengthLimit :: Action Int cmdLineLengthLimit = do windows <- windowsHost - return $ if windows - then 31000 - else 4194304 -- Cabal needs a bit more than 2MB! + osx <- osxHost + return $ case (windows, osx) of + -- windows + (True, False) -> 31000 + -- osx 262144 is ARG_MAX, 33166 experimentally determined + (False, True) -> 262144 - 33166 + _ -> 4194304 -- Cabal needs a bit more than 2MB! From git at git.haskell.org Thu Oct 26 23:46:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move generators to a dedicated directory, and track their changes. (8c3022d) Message-ID: <20171026234632.EEF5D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c3022df66c07b7c1f78a59d60bb154868b591da/ghc >--------------------------------------------------------------- commit 8c3022df66c07b7c1f78a59d60bb154868b591da Author: Andrey Mokhov Date: Sat Dec 26 00:24:07 2015 +0000 Move generators to a dedicated directory, and track their changes. >--------------------------------------------------------------- 8c3022df66c07b7c1f78a59d60bb154868b591da shaking-up-ghc.cabal | 3 + src/Base.hs | 16 ++- src/Rules/Generate.hs | 166 +------------------------------- src/Rules/Generators/ConfigHs.hs | 102 ++++++++++++++++++++ src/Rules/Generators/GhcPkgVersionHs.hs | 17 ++++ src/Rules/Generators/PlatformH.hs | 57 +++++++++++ 6 files changed, 195 insertions(+), 166 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 8c3022df66c07b7c1f78a59d60bb154868b591da From git at git.haskell.org Thu Oct 26 23:46:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split Oracles.hs module into logical parts. (a2c0e5d) Message-ID: <20171026234633.448753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123/ghc >--------------------------------------------------------------- commit a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123 Author: Andrey Mokhov Date: Thu Jan 1 22:26:03 2015 +0000 Split Oracles.hs module into logical parts. >--------------------------------------------------------------- a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123 src/Oracles/Base.hs | 26 ++++++++++++ src/Oracles/Builder.hs | 93 ++++++++++++++++++++++++++++++++++++++++ src/Oracles/Flag.hs | 103 +++++++++++++++++++++++++++++++++++++++++++++ src/Oracles/Option.hs | 57 +++++++++++++++++++++++++ src/Oracles/PackageData.hs | 38 +++++++++++++++++ 5 files changed, 317 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 a2c0e5d1aae53b6f3dbcd20aa7f8081092e10123 From git at git.haskell.org Thu Oct 26 23:46:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add config.h.in to shake-build/cfg. This file is needed for Rules.Generators.GhcAutoconfH. (47529e5) Message-ID: <20171026234647.5F8183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47529e5ee25f3caa958f566f6eb85e62d86235ee/ghc >--------------------------------------------------------------- commit 47529e5ee25f3caa958f566f6eb85e62d86235ee Author: Andrey Mokhov Date: Sat Dec 26 03:01:26 2015 +0000 Add config.h.in to shake-build/cfg. This file is needed for Rules.Generators.GhcAutoconfH. >--------------------------------------------------------------- 47529e5ee25f3caa958f566f6eb85e62d86235ee cfg/config.h.in | 463 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 463 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 47529e5ee25f3caa958f566f6eb85e62d86235ee From git at git.haskell.org Thu Oct 26 23:46:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant GHC extensions. (a7cc473) Message-ID: <20171026234647.A1AF63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7cc473154bf0fcc311bb070381f28c444d4de1b/ghc >--------------------------------------------------------------- commit a7cc473154bf0fcc311bb070381f28c444d4de1b Author: Andrey Mokhov Date: Thu Jan 1 22:56:13 2015 +0000 Remove redundant GHC extensions. >--------------------------------------------------------------- a7cc473154bf0fcc311bb070381f28c444d4de1b src/Base.hs | 2 -- src/Oracles.hs | 3 --- src/Oracles/Base.hs | 3 +-- src/Oracles/Builder.hs | 3 +-- src/Oracles/Flag.hs | 3 +-- src/Oracles/Option.hs | 3 --- src/Oracles/PackageData.hs | 3 +-- 7 files changed, 4 insertions(+), 16 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 29c1340..b95cf14 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE FlexibleInstances #-} - module Base ( module Development.Shake, module Development.Shake.FilePath, diff --git a/src/Oracles.hs b/src/Oracles.hs index c9c9601..093f1b8 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,6 +1,3 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, NoImplicitPrelude #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} - module Oracles ( module Oracles.Base, module Oracles.Flag, diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 1e3dec2..1a9cf3e 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.Base ( ConfigKey (..), diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 3d3a0e9..6c37ec0 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, NoImplicitPrelude #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE NoImplicitPrelude #-} module Oracles.Builder ( Builder (..), diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 9245fb2..c8ddc8e 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE TypeFamilies, FlexibleInstances, MultiParamTypeClasses #-} module Oracles.Flag ( module Control.Monad, diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 72d166b..3661b71 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,6 +1,3 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} - module Oracles.Option ( Option (..), option, argOption, diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 3abd7a2..831fec9 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses #-} -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ConstraintKinds #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( PackageDataPair (..), From git at git.haskell.org Thu Oct 26 23:46:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unset GHC_PACKAGE_PATH before building. (6200ac8) Message-ID: <20171026234649.710303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6200ac8589190682a03b32258686a9b452908a9f/ghc >--------------------------------------------------------------- commit 6200ac8589190682a03b32258686a9b452908a9f Author: Andrey Mokhov Date: Sat Jan 9 16:33:13 2016 +0000 Unset GHC_PACKAGE_PATH before building. See #110. [skip ci] >--------------------------------------------------------------- 6200ac8589190682a03b32258686a9b452908a9f .appveyor.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 99196db..9cb8bcb 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,5 +23,6 @@ install: - happy --version build_script: + - unset GHC_PACKAGE_PATH - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress From git at git.haskell.org Thu Oct 26 23:46:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Condition to Base.hs. (4166bc7) Message-ID: <20171026234651.991A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4166bc732f9f62a34e0e5597686024e995d98691/ghc >--------------------------------------------------------------- commit 4166bc732f9f62a34e0e5597686024e995d98691 Author: Andrey Mokhov Date: Thu Jan 1 23:13:50 2015 +0000 Move Condition to Base.hs. >--------------------------------------------------------------- 4166bc732f9f62a34e0e5597686024e995d98691 src/Base.hs | 3 +++ src/Oracles/Base.hs | 5 +---- src/Oracles/Flag.hs | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index b95cf14..0a88146 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -6,6 +6,7 @@ module Base ( module Data.List, Stage (..), Args, arg, + Condition (..), joinArgs, joinArgsWithSpaces, splitArgs, filterOut ) where @@ -20,6 +21,8 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) type Args = Action [String] +type Condition = Action Bool + instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 1a9cf3e..f9e5c73 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -2,15 +2,12 @@ module Oracles.Base ( ConfigKey (..), - askConfigWithDefault, askConfig, - Condition (..) + askConfigWithDefault, askConfig ) where import Base import Development.Shake.Classes -type Condition = Action Bool - newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) askConfigWithDefault :: String -> Action String -> Action String diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index c8ddc8e..1958c07 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -4,7 +4,7 @@ module Oracles.Flag ( module Control.Monad, module Prelude, Flag (..), - Condition, test, when, unless, not, (&&), (||) + test, when, unless, not, (&&), (||) ) where import Control.Monad hiding (when, unless) From git at git.haskell.org Thu Oct 26 23:46:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #138 from snowleopard/feature/UtilUnlit (883d929) Message-ID: <20171026234635.7FCC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/883d92982c8de5abb8ee22f42f82eba94ed05566/ghc >--------------------------------------------------------------- commit 883d92982c8de5abb8ee22f42f82eba94ed05566 Merge: 8c2a30d e3d96ff Author: Andrey Mokhov Date: Sat Jan 9 14:08:26 2016 +0000 Merge pull request #138 from snowleopard/feature/UtilUnlit Add support for ghc-split, unlit and perl script rules. >--------------------------------------------------------------- 883d92982c8de5abb8ee22f42f82eba94ed05566 cfg/system.config.in | 4 ++-- shaking-up-ghc.cabal | 3 +++ src/Builder.hs | 4 ++-- src/GHC.hs | 11 ++++++----- src/Main.hs | 2 ++ src/Oracles/Config/Setting.hs | 15 +++++++++++---- src/Rules/Data.hs | 11 +++++++++++ src/Rules/Generate.hs | 12 ++++++++++-- src/Rules/Generators/ConfigHs.hs | 2 +- src/Rules/Generators/GhcSplit.hs | 25 +++++++++++++++++++++++++ src/Rules/Perl.hs | 25 +++++++++++++++++++++++++ src/Settings/Args.hs | 4 +++- src/Settings/Packages/{Hp2ps.hs => Unlit.hs} | 10 +++++----- src/Settings/User.hs | 3 ++- 14 files changed, 108 insertions(+), 23 deletions(-) From git at git.haskell.org Thu Oct 26 23:46:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename GhcPkgVersionHs.hs to VersionHs.hs, refactor src/Rules/Generate.hs. (641eb2d) Message-ID: <20171026234636.882653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/641eb2d33053d8011be52b68ef28e4c44ddf34e5/ghc >--------------------------------------------------------------- commit 641eb2d33053d8011be52b68ef28e4c44ddf34e5 Author: Andrey Mokhov Date: Sat Dec 26 02:03:09 2015 +0000 Rename GhcPkgVersionHs.hs to VersionHs.hs, refactor src/Rules/Generate.hs. >--------------------------------------------------------------- 641eb2d33053d8011be52b68ef28e4c44ddf34e5 shaking-up-ghc.cabal | 2 +- src/Rules/Generate.hs | 27 ++++++++++------------ .../{GhcPkgVersionHs.hs => VersionHs.hs} | 8 +++---- 3 files changed, 17 insertions(+), 20 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 3f09043..d233327 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -43,7 +43,7 @@ executable ghc-shake , Rules.Documentation , Rules.Generate , Rules.Generators.ConfigHs - , Rules.Generators.GhcPkgVersionHs + , Rules.Generators.VersionHs , Rules.Generators.PlatformH , Rules.Library , Rules.Oracles diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index fd22926..13d149e1 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -3,7 +3,7 @@ module Rules.Generate (generatePackageCode) where import Expression import GHC import Rules.Generators.ConfigHs -import Rules.Generators.GhcPkgVersionHs +import Rules.Generators.VersionHs import Rules.Generators.PlatformH import Oracles.ModuleFiles import Rules.Actions @@ -32,6 +32,10 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = primopsTxt = targetPath stage compiler -/- "build/primops.txt" platformH = targetPath stage compiler -/- "ghc_boot_platform.h" generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) + generate file expr = do + contents <- interpretPartial target expr + writeFileChanged file contents + putBuild $ "| Successfully generated '" ++ file ++ "'." in do generated ?> \file -> do let pattern = "//" ++ takeBaseName file <.> "*" @@ -60,23 +64,16 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = need [primopsTxt] build $ fullTarget target GenPrimopCode [primopsTxt] [file] - priority 2.0 $ buildPath -/- "Config.hs" %> \file -> do - contents <- interpretPartial target generateConfigHs - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." + priority 2.0 $ do + when (pkg == ghcPkg) $ buildPath -/- "Config.hs" %> \file -> do + generate file generateConfigHs - when (pkg == compiler) $ platformH %> \file -> do - contents <- interpretPartial target generatePlatformH - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." - - priority 2.0 $ when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do - contents <- interpretPartial target generateGhcPkgVersionHs - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." + generate file generateVersionHs + + when (pkg == compiler) $ platformH %> \file -> do + generate file generatePlatformH - priority 2.0 $ when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putBuild $ "| Successfully generated '" ++ file ++ "'." diff --git a/src/Rules/Generators/GhcPkgVersionHs.hs b/src/Rules/Generators/VersionHs.hs similarity index 66% rename from src/Rules/Generators/GhcPkgVersionHs.hs rename to src/Rules/Generators/VersionHs.hs index f29ee97..ea6501a 100644 --- a/src/Rules/Generators/GhcPkgVersionHs.hs +++ b/src/Rules/Generators/VersionHs.hs @@ -1,11 +1,11 @@ -module Rules.Generators.GhcPkgVersionHs (generateGhcPkgVersionHs) where +module Rules.Generators.VersionHs (generateVersionHs) where import Expression import Oracles -generateGhcPkgVersionHs :: Expr String -generateGhcPkgVersionHs = do - lift $ need [sourcePath -/- "Rules/Generators/GhcPkgVersionHs.hs"] +generateVersionHs :: Expr String +generateVersionHs = do + lift $ need [sourcePath -/- "Rules/Generators/VersionHs.hs"] projectVersion <- getSetting ProjectVersion targetOs <- getSetting TargetOs targetArch <- getSetting TargetArch From git at git.haskell.org Thu Oct 26 23:46:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports. (c5f7958) Message-ID: <20171026234636.ADC5C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5f79581110633e6aeb8f8bb13bcd6fa3e187f05/ghc >--------------------------------------------------------------- commit c5f79581110633e6aeb8f8bb13bcd6fa3e187f05 Author: Andrey Mokhov Date: Thu Jan 1 22:29:39 2015 +0000 Refactor imports. >--------------------------------------------------------------- c5f79581110633e6aeb8f8bb13bcd6fa3e187f05 src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a0f4303..29c1340 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,9 +12,9 @@ module Base ( filterOut ) where -import Development.Shake hiding ((*>)) +import Development.Shake import Development.Shake.FilePath -import Control.Applicative +import Control.Applicative hiding ((*>)) import Data.Monoid import Data.List From git at git.haskell.org Thu Oct 26 23:46:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add iosHost function. (e7fc568) Message-ID: <20171026234639.060283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7fc5681234fb897f2014194c81b64450811c543/ghc >--------------------------------------------------------------- commit e7fc5681234fb897f2014194c81b64450811c543 Author: Andrey Mokhov Date: Sat Jan 9 14:33:51 2016 +0000 Add iosHost function. See #138. [skip ci] >--------------------------------------------------------------- e7fc5681234fb897f2014194c81b64450811c543 src/Oracles/Config/Setting.hs | 11 +++++++---- src/Settings/Packages.hs | 2 +- 2 files changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 58f508b..0047f03 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -1,9 +1,9 @@ module Oracles.Config.Setting ( Setting (..), SettingList (..), setting, settingList, getSetting, getSettingList, - anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, windowsHost, + anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, - ghcCanonVersion, cmdLineLengthLimit, osxHost + ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost ) where import Control.Monad.Trans.Reader @@ -122,12 +122,15 @@ anyTargetArch = matchSetting TargetArch anyHostOs :: [String] -> Action Bool anyHostOs = matchSetting HostOs -windowsHost :: Action Bool -windowsHost = anyHostOs ["mingw32", "cygwin32"] +iosHost :: Action Bool +iosHost = anyHostOs ["ios"] osxHost :: Action Bool osxHost = anyHostOs ["darwin"] +windowsHost :: Action Bool +windowsHost = anyHostOs ["mingw32", "cygwin32"] + ghcWithInterpreter :: Action Bool ghcWithInterpreter = do goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "solaris2" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 3f4f661..4d2f76c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -26,7 +26,7 @@ packagesStage0 = mconcat -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] , stage0 ? windowsHost ? append [touchy] - , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] + , notM windowsHost ? iosHost ? append [terminfo] ] packagesStage1 :: Packages packagesStage1 = mconcat From git at git.haskell.org Thu Oct 26 23:46:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CcClangBackend and CcLlvmBackend settings. (27d45f1) Message-ID: <20171026234640.62AFF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27d45f1b334d4af9e8ff18c159c2effa7b45d0c0/ghc >--------------------------------------------------------------- commit 27d45f1b334d4af9e8ff18c159c2effa7b45d0c0 Author: Andrey Mokhov Date: Sat Dec 26 02:58:50 2015 +0000 Add CcClangBackend and CcLlvmBackend settings. >--------------------------------------------------------------- 27d45f1b334d4af9e8ff18c159c2effa7b45d0c0 cfg/system.config.in | 2 ++ src/Oracles/Config/Setting.hs | 4 ++++ 2 files changed, 6 insertions(+) diff --git a/cfg/system.config.in b/cfg/system.config.in index 6c21f6e..12ddeed 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -41,6 +41,8 @@ hscolour = @HSCOLOUR@ gcc-is-clang = @GccIsClang@ gcc-lt-46 = @GccLT46@ ar-supports-at-file = @ArSupportsAtFile@ +cc-llvm-backend = @CC_LLVM_BACKEND@ +cc-clang-backend = @CC_CLANG_BACKEND@ # Build options: #=============== diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 8f0b1df..81e2924 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -21,6 +21,8 @@ data Setting = BuildArch | BuildOs | BuildPlatform | BuildVendor + | CcClangBackend + | CcLlvmBackend | DynamicExtension | GhcMajorVersion | GhcMinorVersion @@ -60,6 +62,8 @@ setting key = askConfig $ case key of BuildOs -> "build-os" BuildPlatform -> "build-platform" BuildVendor -> "build-vendor" + CcClangBackend -> "cc-clang-backend" + CcLlvmBackend -> "cc-llvm-backend" DynamicExtension -> "dynamic-extension" GhcMajorVersion -> "ghc-major-version" GhcMinorVersion -> "ghc-minor-version" From git at git.haskell.org Thu Oct 26 23:46:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move most code into src/Oracles/ submodules. (8228615) Message-ID: <20171026234640.86E8B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82286153d41e61c9e5c06488504e64321993f0df/ghc >--------------------------------------------------------------- commit 82286153d41e61c9e5c06488504e64321993f0df Author: Andrey Mokhov Date: Thu Jan 1 22:31:45 2015 +0000 Move most code into src/Oracles/ submodules. >--------------------------------------------------------------- 82286153d41e61c9e5c06488504e64321993f0df src/Oracles.hs | 284 +++------------------------------------------------------ 1 file changed, 11 insertions(+), 273 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 82286153d41e61c9e5c06488504e64321993f0df From git at git.haskell.org Thu Oct 26 23:46:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix iosHost condition. (f8660c8) Message-ID: <20171026234642.840133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8660c804c827eb8c0f9f29af2de57e5eca908f1/ghc >--------------------------------------------------------------- commit f8660c804c827eb8c0f9f29af2de57e5eca908f1 Author: Andrey Mokhov Date: Sat Jan 9 14:35:43 2016 +0000 Fix iosHost condition. See #138. [skip ci] >--------------------------------------------------------------- f8660c804c827eb8c0f9f29af2de57e5eca908f1 src/Settings/Packages.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 4d2f76c..b7e2dac 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -26,7 +26,7 @@ packagesStage0 = mconcat -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] , stage0 ? windowsHost ? append [touchy] - , notM windowsHost ? iosHost ? append [terminfo] ] + , notM windowsHost ? notM iosHost ? append [terminfo] ] packagesStage1 :: Packages packagesStage1 = mconcat From git at git.haskell.org Thu Oct 26 23:46:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate includes/ghcautoconf.h, refactor Rules/Generate.hs. (6b7b9cc) Message-ID: <20171026234643.E61253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b7b9cc86e963a4bc200ff45fe16e26b72f372dd/ghc >--------------------------------------------------------------- commit 6b7b9cc86e963a4bc200ff45fe16e26b72f372dd Author: Andrey Mokhov Date: Sat Dec 26 03:00:03 2015 +0000 Generate includes/ghcautoconf.h, refactor Rules/Generate.hs. >--------------------------------------------------------------- 6b7b9cc86e963a4bc200ff45fe16e26b72f372dd src/Main.hs | 6 ++++-- src/Rules/Generate.hs | 33 +++++++++++++++++++++++++-------- src/Rules/Generators/GhcAutoconfH.hs | 34 ++++++++++++++++++++++++++++++++++ 3 files changed, 63 insertions(+), 10 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 7a0205d..0dc8d96 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,15 +2,17 @@ import Base import Rules import Rules.Cabal import Rules.Config +import Rules.Generate import Rules.Oracles main :: IO () main = shakeArgs options $ do - generateTargets -- see Rules - packageRules -- see Rules cabalRules -- see Rules.Cabal configRules -- see Rules.Config + generateTargets -- see Rules + generateRules -- see Rules.Generate oracleRules -- see Rules.Oracles + packageRules -- see Rules where options = shakeOptions { shakeFiles = shakeFilesPath diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 13d149e1..8f60dd0 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,8 +1,9 @@ -module Rules.Generate (generatePackageCode) where +module Rules.Generate (generatePackageCode, generateRules) where import Expression import GHC import Rules.Generators.ConfigHs +import Rules.Generators.GhcAutoconfH import Rules.Generators.VersionHs import Rules.Generators.PlatformH import Oracles.ModuleFiles @@ -25,6 +26,13 @@ determineBuilder file = fmap fst $ find (\(_, e) -> e == ext) knownGenerators where ext = takeExtension file +generate :: FilePath -> PartialTarget -> Expr String -> Action () +generate file target expr = do + contents <- interpretPartial target expr + writeFileChanged file contents + putBuild $ "| Successfully generated '" ++ file ++ "'." + + generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let path = targetPath stage pkg @@ -32,10 +40,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = primopsTxt = targetPath stage compiler -/- "build/primops.txt" platformH = targetPath stage compiler -/- "ghc_boot_platform.h" generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) - generate file expr = do - contents <- interpretPartial target expr - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." + file <~ gen = generate file target gen in do generated ?> \file -> do let pattern = "//" ++ takeBaseName file <.> "*" @@ -66,14 +71,26 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = priority 2.0 $ do when (pkg == ghcPkg) $ buildPath -/- "Config.hs" %> \file -> do - generate file generateConfigHs + file <~ generateConfigHs when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do - generate file generateVersionHs + file <~ generateVersionHs when (pkg == compiler) $ platformH %> \file -> do - generate file generatePlatformH + file <~ generatePlatformH when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putBuild $ "| Successfully generated '" ++ file ++ "'." + +generateRules :: Rules () +generateRules = do + "includes/ghcautoconf.h" <~ generateGhcAutoconfH + where + file <~ gen = file %> \out -> generate out fakeTarget gen + +-- TODO: Use the Types, Luke! (drop partial function) +fakeTarget :: PartialTarget +fakeTarget = PartialTarget (error "fakeTarget: unknown stage") + (error "fakeTarget: unknown package") + diff --git a/src/Rules/Generators/GhcAutoconfH.hs b/src/Rules/Generators/GhcAutoconfH.hs new file mode 100644 index 0000000..6d49603 --- /dev/null +++ b/src/Rules/Generators/GhcAutoconfH.hs @@ -0,0 +1,34 @@ +module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH) where + +import Expression +import Oracles + +-- TODO: change `mk/config.h` to `shake-build/cfg/config.h` +configH :: FilePath +configH = "mk/config.h" + +undefinePackage :: String -> String +undefinePackage s + | "#define PACKAGE_" `isPrefixOf` s + = "/* #undef " ++ takeWhile (/=' ') (drop 8 s) ++ " */" + | otherwise = s + +generateGhcAutoconfH :: Expr String +generateGhcAutoconfH = do + lift $ need [sourcePath -/- "Rules/Generators/GhcAutoconfH.hs"] + configHContents <- lift $ map undefinePackage <$> readFileLines configH + tablesNextToCode <- lift $ ghcEnableTablesNextToCode + ghcUnreg <- getFlag GhcUnregisterised + ccLlvmBackend <- getSetting CcLlvmBackend + ccClangBackend <- getSetting CcClangBackend + return . unlines $ + [ "#ifndef __GHCAUTOCONF_H__" + , "#define __GHCAUTOCONF_H__" ] + ++ configHContents ++ + [ "\n#define TABLES_NEXT_TO_CODE 1" | tablesNextToCode && not ghcUnreg ] + ++ + [ "\n#define llvm_CC_FLAVOR 1" | ccLlvmBackend == "1" ] + ++ + [ "\n#define clang_CC_FLAVOR 1" | ccClangBackend == "1" ] + ++ + [ "#endif /* __GHCAUTOCONF_H__ */" ] From git at git.haskell.org Thu Oct 26 23:46:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change computed configuration flags into Conditions. (9d8e3a3) Message-ID: <20171026234644.0B6823A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d8e3a33b4cc3aaf312dc068be9810043c40ff91/ghc >--------------------------------------------------------------- commit 9d8e3a33b4cc3aaf312dc068be9810043c40ff91 Author: Andrey Mokhov Date: Thu Jan 1 22:35:50 2015 +0000 Change computed configuration flags into Conditions. >--------------------------------------------------------------- 9d8e3a33b4cc3aaf312dc068be9810043c40ff91 src/Package.hs | 4 ++-- src/Ways.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 98558e9..4154dc5 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -78,7 +78,7 @@ libraryArgs ways = in mconcat [ argEnable False "library-for-ghci" -- TODO: why always disable? , argEnable (vanilla `elem` ways) "library-vanilla" - , when (GhcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) $ + , when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) $ argEnable True "library-for-ghci" , argEnable (profiling `elem` ways) "library-profiling" , argEnable (dynamic `elem` ways) "shared" @@ -143,7 +143,7 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = , customConfArgs settings , libraryArgs =<< ways settings - , when HsColourSrcs $ with HsColour + , when hsColourSrcs $ with HsColour , configureArgs stage settings , when (stage == Stage0) $ bootPkgConstraints diff --git a/src/Ways.hs b/src/Ways.hs index a0e886a..0a4284a 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -65,7 +65,7 @@ allWays = [vanilla, profiling, logging, parallel, granSim, defaultWays :: Stage -> Action [Way] defaultWays stage = do - sharedLibs <- test PlatformSupportsSharedLibs + sharedLibs <- platformSupportsSharedLibs return $ [vanilla] ++ [profiling | stage /= Stage0] ++ [dynamic | sharedLibs ] From git at git.haskell.org Thu Oct 26 23:46:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #142 from quchen/clone-from-github (a012ac6) Message-ID: <20171026234645.E771A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a012ac65bc12d0ec8afb6bc746eac1246e8da9ea/ghc >--------------------------------------------------------------- commit a012ac65bc12d0ec8afb6bc746eac1246e8da9ea Merge: f8660c8 c43d07d Author: Andrey Mokhov Date: Sat Jan 9 14:40:58 2016 +0000 Merge pull request #142 from quchen/clone-from-github CI: Shallow clone GHC from Github instead of Haskell.org >--------------------------------------------------------------- a012ac65bc12d0ec8afb6bc746eac1246e8da9ea .travis.yml | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:46:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate includes/ghcplatform.h (8c32f2c) Message-ID: <20171026234651.A5AEF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c32f2c931d68e1f847cfefb8f4d514886217873/ghc >--------------------------------------------------------------- commit 8c32f2c931d68e1f847cfefb8f4d514886217873 Author: Andrey Mokhov Date: Sat Dec 26 03:39:41 2015 +0000 Generate includes/ghcplatform.h >--------------------------------------------------------------- 8c32f2c931d68e1f847cfefb8f4d514886217873 shaking-up-ghc.cabal | 4 +- src/Rules/Generate.hs | 8 ++-- .../{PlatformH.hs => GhcBootPlatformH.hs} | 8 ++-- src/Rules/Generators/GhcPlatformH.hs | 55 ++++++++++++++++++++++ 4 files changed, 67 insertions(+), 8 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index d233327..1e0fbbf 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -43,8 +43,10 @@ executable ghc-shake , Rules.Documentation , Rules.Generate , Rules.Generators.ConfigHs + , Rules.Generators.GhcAutoconfH + , Rules.Generators.GhcBootPlatformH + , Rules.Generators.GhcPlatformH , Rules.Generators.VersionHs - , Rules.Generators.PlatformH , Rules.Library , Rules.Oracles , Rules.Package diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8f60dd0..f9c1e0b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -4,8 +4,9 @@ import Expression import GHC import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH +import Rules.Generators.GhcBootPlatformH +import Rules.Generators.GhcPlatformH import Rules.Generators.VersionHs -import Rules.Generators.PlatformH import Oracles.ModuleFiles import Rules.Actions import Rules.Resources (Resources) @@ -56,12 +57,12 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = whenM (doesFileExist srcBoot) $ copyFileChanged srcBoot $ file -<.> "hs-boot" + -- TODO: needing platformH is ugly and fragile when (pkg == compiler) $ primopsTxt %> \file -> do need [platformH, primopsSource] build $ fullTarget target HsCpp [primopsSource] [file] -- TODO: why different folders for generated files? - -- TODO: needing platformH is ugly and fragile fmap (buildPath -/-) [ "GHC/PrimopWrappers.hs" , "autogen/GHC/Prim.hs" @@ -77,7 +78,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = file <~ generateVersionHs when (pkg == compiler) $ platformH %> \file -> do - file <~ generatePlatformH + file <~ generateGhcBootPlatformH when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file @@ -86,6 +87,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = generateRules :: Rules () generateRules = do "includes/ghcautoconf.h" <~ generateGhcAutoconfH + "includes/ghcplatform.h" <~ generateGhcPlatformH where file <~ gen = file %> \out -> generate out fakeTarget gen diff --git a/src/Rules/Generators/PlatformH.hs b/src/Rules/Generators/GhcBootPlatformH.hs similarity index 91% rename from src/Rules/Generators/PlatformH.hs rename to src/Rules/Generators/GhcBootPlatformH.hs index cc29a1b..93b953b 100644 --- a/src/Rules/Generators/PlatformH.hs +++ b/src/Rules/Generators/GhcBootPlatformH.hs @@ -1,11 +1,11 @@ -module Rules.Generators.PlatformH (generatePlatformH) where +module Rules.Generators.GhcBootPlatformH (generateGhcBootPlatformH) where import Expression import Oracles -generatePlatformH :: Expr String -generatePlatformH = do - lift $ need [sourcePath -/- "Rules/Generators/PlatformH.hs"] +generateGhcBootPlatformH :: Expr String +generateGhcBootPlatformH = do + lift $ need [sourcePath -/- "Rules/Generators/GhcBootPlatformH.hs"] stage <- getStage let cppify = replaceEq '-' '_' . replaceEq '.' '_' chooseSetting x y = getSetting $ if stage == Stage0 then x else y diff --git a/src/Rules/Generators/GhcPlatformH.hs b/src/Rules/Generators/GhcPlatformH.hs new file mode 100644 index 0000000..2bdf5d4 --- /dev/null +++ b/src/Rules/Generators/GhcPlatformH.hs @@ -0,0 +1,55 @@ +module Rules.Generators.GhcPlatformH (generateGhcPlatformH) where + +import Expression +import Oracles + +generateGhcPlatformH :: Expr String +generateGhcPlatformH = do + lift $ need [sourcePath -/- "Rules/Generators/GhcPlatformH.hs"] + let cppify = replaceEq '-' '_' . replaceEq '.' '_' + hostPlatform <- getSetting HostPlatform + hostArch <- getSetting HostArch + hostOs <- getSetting HostOs + hostVendor <- getSetting HostVendor + targetPlatform <- getSetting TargetPlatform + targetArch <- getSetting TargetArch + targetOs <- getSetting TargetOs + targetVendor <- getSetting TargetVendor + ghcUnreg <- getFlag GhcUnregisterised + return . unlines $ + [ "#ifndef __GHCPLATFORM_H__" + , "#define __GHCPLATFORM_H__" + , "" + , "#define BuildPlatform_TYPE " ++ cppify hostPlatform + , "#define HostPlatform_TYPE " ++ cppify targetPlatform + , "" + , "#define " ++ cppify hostPlatform ++ "_BUILD 1" + , "#define " ++ cppify targetPlatform ++ "_HOST 1" + , "" + , "#define " ++ hostArch ++ "_BUILD_ARCH 1" + , "#define " ++ targetArch ++ "_HOST_ARCH 1" + , "#define BUILD_ARCH " ++ quote hostArch + , "#define HOST_ARCH " ++ quote targetArch + , "" + , "#define " ++ hostOs ++ "_BUILD_OS 1" + , "#define " ++ targetOs ++ "_HOST_OS 1" + , "#define BUILD_OS " ++ quote hostOs + , "#define HOST_OS " ++ quote targetOs + , "" + , "#define " ++ hostVendor ++ "_BUILD_VENDOR 1" + , "#define " ++ targetVendor ++ "_HOST_VENDOR 1" + , "#define BUILD_VENDOR " ++ quote hostVendor + , "#define HOST_VENDOR " ++ quote targetVendor + , "" + , "/* These TARGET macros are for backwards compatibility... DO NOT USE! */" + , "#define TargetPlatform_TYPE " ++ cppify targetPlatform + , "#define " ++ cppify targetPlatform ++ "_TARGET 1" + , "#define " ++ targetArch ++ "_TARGET_ARCH 1" + , "#define TARGET_ARCH " ++ quote targetArch + , "#define " ++ targetOs ++ "_TARGET_OS 1" + , "#define TARGET_OS " ++ quote targetOs + , "#define " ++ targetVendor ++ "_TARGET_VENDOR 1" ] + ++ + [ "#define UnregisterisedCompiler 1" | ghcUnreg ] + ++ + [ "\n#endif /* __GHCPLATFORM_H__ */" ] From git at git.haskell.org Thu Oct 26 23:46:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move chunksOfSize to Settings/Builders/Ar.hs, add comments. (5e3f91f) Message-ID: <20171026234652.F17963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e3f91f9d050c91f8fd842b9548093c0d8d8e532/ghc >--------------------------------------------------------------- commit 5e3f91f9d050c91f8fd842b9548093c0d8d8e532 Author: Andrey Mokhov Date: Sat Jan 9 16:57:49 2016 +0000 Move chunksOfSize to Settings/Builders/Ar.hs, add comments. See #130. [skip ci] >--------------------------------------------------------------- 5e3f91f9d050c91f8fd842b9548093c0d8d8e532 src/Base.hs | 19 +++---------------- src/Settings/Builders/Ar.hs | 28 ++++++++++++++++++++++++---- 2 files changed, 27 insertions(+), 20 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fb33907..65a2d1d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,9 +22,9 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, renderBox, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, replaceEq, quote, chunksOfSize, - replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), - versionToInt, removeFileIfExists, removeDirectoryIfExists + bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, + decodeModule, encodeModule, unifyPath, (-/-), versionToInt, + removeFileIfExists, removeDirectoryIfExists ) where import Control.Applicative @@ -90,19 +90,6 @@ replaceSeparators = replaceWhen isPathSeparator replaceWhen :: (a -> Bool) -> a -> [a] -> [a] replaceWhen p to = map (\from -> if p from then to else from) --- | @chunksOfSize size strings@ splits a given list of strings into chunks not --- exceeding the given @size at . -chunksOfSize :: Int -> [String] -> [[String]] -chunksOfSize _ [] = [] -chunksOfSize size strings = reverse chunk : chunksOfSize size rest - where - (chunk, rest) = go [] 0 strings - go res _ [] = (res, []) - go res chunkSize (s:ss) = - if newSize > size then (res, s:ss) else go (s:res) newSize ss - where - newSize = chunkSize + length s - -- | Add quotes to a String quote :: String -> String quote s = "\"" ++ s ++ "\"" diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 18ce802..86f4310 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -5,6 +5,7 @@ import Expression import Oracles import Predicates (builder) +-- | Default arguments for 'Ar' builder arBuilderArgs :: Args arBuilderArgs = builder Ar ? mconcat [ arg "q" , arg =<< getOutput @@ -15,10 +16,15 @@ arBuilderArgs = builder Ar ? mconcat [ arg "q" arFlagsCount :: Int arFlagsCount = 2 --- Ar needs to be invoked in a special way: we pass the list of files to be --- archived via a temporary file as otherwise Ar (or rather Windows command --- line) chokes up. Alternatively, we split argument list into chunks and call --- ar multiple times (when passing files via a separate file is not supported). +-- | Invoke 'Ar' builder given a path to it and a list of arguments. Take care +-- not to exceed the limit on command line length, which differs across +-- supported operating systems (see 'cmdLineLengthLimit'). 'Ar' needs to be +-- handled in a special way because we sometimes need to archive __a lot__ of +-- files (in Cabal package, for example, command line length can reach 2MB!). +-- To work around the limit on the command line length we pass the list of files +-- to be archived via a temporary file, or alternatively, we split argument list +-- into chunks and call 'Ar' multiple times (when passing arguments via a +-- temporary file is not supported). arCmd :: FilePath -> [String] -> Action () arCmd path argList = do arSupportsAtFile <- flag ArSupportsAtFile @@ -38,3 +44,17 @@ useSuccessiveInvocations path flagArgs fileArgs = do maxChunk <- cmdLineLengthLimit forM_ (chunksOfSize maxChunk fileArgs) $ \argsChunk -> unit . cmd [path] $ flagArgs ++ argsChunk + +-- | @chunksOfSize size strings@ splits a given list of strings into chunks not +-- exceeding the given @size at . +chunksOfSize :: Int -> [String] -> [[String]] +chunksOfSize _ [] = [] +chunksOfSize size strings = reverse chunk : chunksOfSize size rest + where + (chunk, rest) = go [] 0 strings + go res _ [] = (res, []) + go res chunkSize (s:ss) = + if newSize > size then (res, s:ss) else go (s:res) newSize ss + where + newSize = chunkSize + length s + From git at git.haskell.org Thu Oct 26 23:46:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ShowAction typeclass. (64b16d7) Message-ID: <20171026234655.277943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64b16d796dc5aa8a889d41eeb08cbead19cba14d/ghc >--------------------------------------------------------------- commit 64b16d796dc5aa8a889d41eeb08cbead19cba14d Author: Andrey Mokhov Date: Thu Jan 1 23:56:12 2015 +0000 Add ShowAction typeclass. >--------------------------------------------------------------- 64b16d796dc5aa8a889d41eeb08cbead19cba14d src/Base.hs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 0a88146..77c2858 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-} + module Base ( module Development.Shake, module Development.Shake.FilePath, @@ -27,8 +29,14 @@ instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q -arg :: [String] -> Args -arg = return +class ShowAction a where + showAction :: a -> Action String + +instance ShowAction String where + showAction = return + +arg :: ShowAction a => [a] -> Args +arg = mapM showAction intercalateArgs :: String -> Args -> Args intercalateArgs s args = do From git at git.haskell.org Thu Oct 26 23:46:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add "--template" and "-I" arguments to hsc2HsArgs (efbe44f) Message-ID: <20171026234655.463A03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efbe44f845b88e3885e1c63adcf66c57c5af1f77/ghc >--------------------------------------------------------------- commit efbe44f845b88e3885e1c63adcf66c57c5af1f77 Author: Moritz Angermann Date: Sat Dec 26 17:38:05 2015 +0800 Add "--template" and "-I" arguments to hsc2HsArgs This should fix #35. To have this fully working, #44 needs to be solved as well. >--------------------------------------------------------------- efbe44f845b88e3885e1c63adcf66c57c5af1f77 src/Settings/Builders/Hsc2Hs.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 0e31b4f..0c6172d 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -13,6 +13,7 @@ hsc2HsArgs = builder Hsc2Hs ? do gmpDirs <- getSettingList GmpIncludeDirs cFlags <- getCFlags lFlags <- getLFlags + top <- getSetting GhcSourcePath hArch <- getSetting HostArch hOs <- getSetting HostOs tArch <- getSetting TargetArch @@ -32,6 +33,8 @@ hsc2HsArgs = builder Hsc2Hs ? do , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) , arg ("--cflag=-D__GLASGOW_HASKELL__=" ++ version) + , arg $ "--template=" ++ top -/- "inplace/lib/template-hsc.h" + , arg $ "-I" ++ top -/- "inplace/lib/include/" , arg =<< getInput , arg "-o", arg =<< getOutput ] From git at git.haskell.org Thu Oct 26 23:46:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (2nd try). (901105e) Message-ID: <20171026234656.686553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/901105e56574df051615b59db337bb7ec856ef9a/ghc >--------------------------------------------------------------- commit 901105e56574df051615b59db337bb7ec856ef9a Author: Andrey Mokhov Date: Sat Jan 9 17:06:20 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (2nd try). See #110. [skip ci] >--------------------------------------------------------------- 901105e56574df051615b59db337bb7ec856ef9a .appveyor.yml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 9cb8bcb..e382140 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,6 +23,8 @@ install: - happy --version build_script: - - unset GHC_PACKAGE_PATH + - set GHC_PACKAGE_PATH + - set GHC_PACKAGE_PATH= + - set GHC_PACKAGE_PATH - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat -j --no-progress From git at git.haskell.org Thu Oct 26 23:46:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace path with instance ShowAction Builder. (37de3d5) Message-ID: <20171026234658.82D473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37de3d57c7e35237dea4f11c2cb2016eedeb49c5/ghc >--------------------------------------------------------------- commit 37de3d57c7e35237dea4f11c2cb2016eedeb49c5 Author: Andrey Mokhov Date: Fri Jan 2 02:34:56 2015 +0000 Replace path with instance ShowAction Builder. >--------------------------------------------------------------- 37de3d57c7e35237dea4f11c2cb2016eedeb49c5 src/Oracles/Builder.hs | 73 +++++++++++++++++++++++--------------------------- 1 file changed, 34 insertions(+), 39 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 6c37ec0..3da6f9a 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,7 @@ module Oracles.Builder ( Builder (..), - path, with, run, argPath, + with, run, hsColourSrcs ) where @@ -14,39 +14,34 @@ import Oracles.Option data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage -path :: Builder -> Action FilePath -path builder = do - let key = case builder of - Ar -> "ar" - Ld -> "ld" - Gcc -> "gcc" - Alex -> "alex" - Happy -> "happy" - HsColour -> "hscolour" - GhcCabal -> "ghc-cabal" - Ghc Stage0 -> "system-ghc" -- Ghc Stage0 is the bootstrapping compiler - Ghc Stage1 -> "ghc-stage1" -- Ghc StageN, N > 0, is the one built on stage (N - 1) - Ghc Stage2 -> "ghc-stage2" - Ghc Stage3 -> "ghc-stage3" - GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg - GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) - cfgPath <- askConfigWithDefault key $ - error $ "\nCannot find path to '" - ++ key - ++ "' in configuration files." - let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" - windows <- windowsHost - if (windows && "/" `isPrefixOf` cfgPathExe) - then do - Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] - return $ dropWhileEnd isSpace out ++ drop 1 cfgPathExe - else - return cfgPathExe - -argPath :: Builder -> Args -argPath builder = do - path <- path builder - arg [path] +instance ShowAction Builder where + showAction builder = do + let key = case builder of + Ar -> "ar" + Ld -> "ld" + Gcc -> "gcc" + Alex -> "alex" + Happy -> "happy" + HsColour -> "hscolour" + GhcCabal -> "ghc-cabal" + Ghc Stage0 -> "system-ghc" -- Ghc Stage0 is the bootstrapping compiler + Ghc Stage1 -> "ghc-stage1" -- Ghc StageN, N > 0, is the one built on stage (N - 1) + Ghc Stage2 -> "ghc-stage2" + Ghc Stage3 -> "ghc-stage3" + GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg + GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) + cfgPath <- askConfigWithDefault key $ + error $ "\nCannot find path to '" + ++ key + ++ "' in configuration files." + let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" + windows <- windowsHost + if (windows && "/" `isPrefixOf` cfgPathExe) + then do + Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] + return $ dropWhileEnd isSpace out ++ drop 1 cfgPathExe + else + return cfgPathExe -- When LaxDeps flag is set (by adding 'lax-dependencies = YES' to user.config), -- dependencies on the GHC executable are turned into order-only dependencies to @@ -55,12 +50,12 @@ argPath builder = do -- the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - target <- path ghc + target <- showAction ghc laxDeps <- test LaxDeps if laxDeps then orderOnly [target] else need [target] needBuilder builder = do - target <- path builder + target <- showAction builder need [target] -- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder @@ -75,18 +70,18 @@ with builder = do Happy -> "--with-happy=" GhcPkg _ -> "--with-ghc-pkg=" HsColour -> "--with-hscolour=" - suffix <- path builder + suffix <- showAction builder needBuilder builder return [prefix ++ suffix] run :: Builder -> Args -> Action () run builder args = do needBuilder builder - exe <- path builder + exe <- showAction builder args' <- args cmd [exe :: FilePath] args' hsColourSrcs :: Condition hsColourSrcs = do - hscolour <- path HsColour + hscolour <- showAction HsColour return $ hscolour /= "" From git at git.haskell.org Thu Oct 26 23:46:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds OS X Section to Readme (1046838) Message-ID: <20171026234658.C44953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1046838060dfdacbdf7cdf8e2994edf71e5c0a5f/ghc >--------------------------------------------------------------- commit 1046838060dfdacbdf7cdf8e2994edf71e5c0a5f Author: Moritz Angermann Date: Sat Dec 26 18:06:27 2015 +0800 Adds OS X Section to Readme Still fails at #47 >--------------------------------------------------------------- 1046838060dfdacbdf7cdf8e2994edf71e5c0a5f README.md | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/README.md b/README.md index 6d27b25..9844bf6 100644 --- a/README.md +++ b/README.md @@ -48,6 +48,22 @@ $ shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. +### Mac OS X + +```bash +git clone git://git.haskell.org/ghc +cd ghc +git submodule update --init +git clone git://github.com/snowleopard/shaking-up-ghc shake-build +./boot +./configure --with-gcc=$(which clang) # See #26 +./shake-build/build.sh includes/ghcautoconf.h # See #48 +./shake-build/build.sh includes/ghcplatform.h # See #48 +cp utils/hsc2hs/template-hsc.h inplace/lib/template-hsc.h # See #44 +./shake-build/build.sh +``` + +See the Linux section for running in a Cabal sandbox. ### Resetting the build From git at git.haskell.org Thu Oct 26 23:46:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:46:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on ghc-split only when building with split objects. (9580d01) Message-ID: <20171026234659.DAA223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9580d01895bb231dd38f8000eb7ad1929ee75962/ghc >--------------------------------------------------------------- commit 9580d01895bb231dd38f8000eb7ad1929ee75962 Author: Andrey Mokhov Date: Sat Jan 9 17:09:03 2016 +0000 Depend on ghc-split only when building with split objects. See #81. [skip ci] >--------------------------------------------------------------- 9580d01895bb231dd38f8000eb7ad1929ee75962 src/Rules/Generate.hs | 7 ++++--- src/Settings/Builders/Ghc.hs | 7 ++++++- 2 files changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 2b2962b..b7a360a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -42,8 +42,10 @@ includesDependencies = ("includes" -/-) <$> , "ghcversion.h" ] defaultDependencies :: [FilePath] -defaultDependencies = - includesDependencies ++ libffiDependencies ++ integerGmpDependencies +defaultDependencies = concat + [ includesDependencies + , libffiDependencies + , integerGmpDependencies ] ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> @@ -77,7 +79,6 @@ compilerDependencies stage = , "primop-vector-tys-exports.hs-incl" , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] - ++ ["inplace/lib/bin/ghc-split"] generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 9a07fc2..bc37a04 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -26,7 +26,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , notStage0 ? arg "-O2" , arg "-Wall" , arg "-fwarn-tabs" - , splitObjects ? arg "-split-objs" + , splitObjectsArgs , not buildObj ? arg "-no-auto-link-packages" , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ] , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] @@ -34,6 +34,11 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , append =<< getInputs , arg "-o", arg =<< getOutput ] +splitObjectsArgs :: Args +splitObjectsArgs = splitObjects ? do + lift $ need ["inplace/lib/bin/ghc-split"] + arg "-split-objs" + ghcMBuilderArgs :: Args ghcMBuilderArgs = stagedBuilder GhcM ? do ways <- getWays From git at git.haskell.org Thu Oct 26 23:47:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #46 from angerman/feature/fix-hsc2hs (9d1952f) Message-ID: <20171026234703.34B603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d1952faa145acb44725465cf738dd9448e0892e/ghc >--------------------------------------------------------------- commit 9d1952faa145acb44725465cf738dd9448e0892e Merge: 8c32f2c efbe44f Author: Andrey Mokhov Date: Sat Dec 26 11:50:27 2015 +0000 Merge pull request #46 from angerman/feature/fix-hsc2hs Add "--template" and "-I" arguments to hsc2HsArgs >--------------------------------------------------------------- 9d1952faa145acb44725465cf738dd9448e0892e src/Settings/Builders/Hsc2Hs.hs | 3 +++ 1 file changed, 3 insertions(+) From git at git.haskell.org Thu Oct 26 23:47:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace option with instance ShowAction Option. (1495a2d) Message-ID: <20171026234702.DFCA63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1495a2d66f0a9cb8082285b68c1e42cf954eb6b8/ghc >--------------------------------------------------------------- commit 1495a2d66f0a9cb8082285b68c1e42cf954eb6b8 Author: Andrey Mokhov Date: Fri Jan 2 02:43:40 2015 +0000 Replace option with instance ShowAction Option. >--------------------------------------------------------------- 1495a2d66f0a9cb8082285b68c1e42cf954eb6b8 src/Oracles/Option.hs | 44 +++++++++++++++++++------------------------- 1 file changed, 19 insertions(+), 25 deletions(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 3661b71..899aec7 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,6 +1,5 @@ module Oracles.Option ( Option (..), - option, argOption, ghcWithInterpreter, platformSupportsSharedLibs, windowsHost ) where @@ -13,31 +12,26 @@ data Option = TargetOS | TargetArch | TargetPlatformFull | SrcHcOpts | HostOsCpp -option :: Option -> Action String -option opt = askConfig $ case opt of - TargetOS -> "target-os" - TargetArch -> "target-arch" - TargetPlatformFull -> "target-platform-full" - ConfCcArgs stage -> "conf-cc-args-stage-" ++ (show . fromEnum) stage - ConfCppArgs stage -> "conf-cpp-args-stage-" ++ (show . fromEnum) stage - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ (show . fromEnum) stage - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ (show . fromEnum) stage - IconvIncludeDirs -> "iconv-include-dirs" - IconvLibDirs -> "iconv-lib-dirs" - GmpIncludeDirs -> "gmp-include-dirs" - GmpLibDirs -> "gmp-lib-dirs" - SrcHcOpts -> "src-hc-opts" - HostOsCpp -> "host-os-cpp" - -argOption :: Option -> Args -argOption opt = do - opt' <- option opt - arg [opt'] +instance ShowAction Option where + showAction opt = askConfig $ case opt of + TargetOS -> "target-os" + TargetArch -> "target-arch" + TargetPlatformFull -> "target-platform-full" + ConfCcArgs stage -> "conf-cc-args-stage-" ++ (show . fromEnum) stage + ConfCppArgs stage -> "conf-cpp-args-stage-" ++ (show . fromEnum) stage + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ (show . fromEnum) stage + ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ (show . fromEnum) stage + IconvIncludeDirs -> "iconv-include-dirs" + IconvLibDirs -> "iconv-lib-dirs" + GmpIncludeDirs -> "gmp-include-dirs" + GmpLibDirs -> "gmp-lib-dirs" + SrcHcOpts -> "src-hc-opts" + HostOsCpp -> "host-os-cpp" ghcWithInterpreter :: Condition ghcWithInterpreter = do - os <- option TargetOS - arch <- option TargetArch + os <- showAction TargetOS + arch <- showAction TargetArch return $ os `elem` ["mingw32", "cygwin32", "linux", "solaris2", "freebsd", "dragonfly", "netbsd", "openbsd", "darwin", "kfreebsdgnu"] && @@ -45,10 +39,10 @@ ghcWithInterpreter = do platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do - platform <- option TargetPlatformFull + platform <- showAction TargetPlatformFull return $ platform `notElem` [ "powerpc-unknown-linux", "x86_64-unknown-mingw32", "i386-unknown-mingw32" ] -- TODO: i386-unknown-solaris2? windowsHost :: Condition windowsHost = do - hostOsCpp <- option HostOsCpp + hostOsCpp <- showAction HostOsCpp return $ hostOsCpp `elem` ["mingw32", "cygwin32"] From git at git.haskell.org Thu Oct 26 23:47:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (3rd try). (de13770) Message-ID: <20171026234703.91DB23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de13770f7941733a8af2fbd6daeef6fb916b6a11/ghc >--------------------------------------------------------------- commit de13770f7941733a8af2fbd6daeef6fb916b6a11 Author: Andrey Mokhov Date: Sat Jan 9 18:07:22 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (3rd try). See #110. [skip ci] >--------------------------------------------------------------- de13770f7941733a8af2fbd6daeef6fb916b6a11 .appveyor.yml | 3 --- build.bat | 3 +++ 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index e382140..16de309 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,8 +23,5 @@ install: - happy --version build_script: - - set GHC_PACKAGE_PATH - - set GHC_PACKAGE_PATH= - - set GHC_PACKAGE_PATH - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat -j --no-progress diff --git a/build.bat b/build.bat index a4e2548..4cbbc42 100644 --- a/build.bat +++ b/build.bat @@ -16,4 +16,7 @@ ".." ^ %* + at rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains + at if defined GHC_PACKAGE_PATH ( set GHC_PACKAGE_PATH ) + @ghc %ghcArgs% && .shake\build %shakeArgs% From git at git.haskell.org Thu Oct 26 23:47:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add args -- a variadic version of arg. (6084342) Message-ID: <20171026234706.849913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/60843423d23b84928c2c1ce2725b5e293cb81061/ghc >--------------------------------------------------------------- commit 60843423d23b84928c2c1ce2725b5e293cb81061 Author: Andrey Mokhov Date: Fri Jan 2 03:03:27 2015 +0000 Add args -- a variadic version of arg. >--------------------------------------------------------------- 60843423d23b84928c2c1ce2725b5e293cb81061 src/Base.hs | 16 +++++++++++++++- 1 file changed, 15 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 77c2858..645d5dc 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,7 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, + Args, arg, args, ShowAction (..), Condition (..), joinArgs, joinArgsWithSpaces, splitArgs, filterOut @@ -38,6 +38,20 @@ instance ShowAction String where arg :: ShowAction a => [a] -> Args arg = mapM showAction +class Collect a where + collect :: Args -> a + +instance Collect Args where + collect = id + +instance (ShowAction a, Collect r) => Collect (a -> r) where + collect prev next = collect $ do + next' <- showAction next + prev <> return [next'] + +args :: Collect a => a +args = collect mempty + intercalateArgs :: String -> Args -> Args intercalateArgs s args = do as <- args From git at git.haskell.org Thu Oct 26 23:47:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #49 from angerman/feature/readme-osx (eb02aa4) Message-ID: <20171026234707.4D8423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eb02aa4ae236230b9aa83e18017be779371bdbc7/ghc >--------------------------------------------------------------- commit eb02aa4ae236230b9aa83e18017be779371bdbc7 Merge: 9d1952f 1046838 Author: Andrey Mokhov Date: Sat Dec 26 11:53:40 2015 +0000 Merge pull request #49 from angerman/feature/readme-osx Feature/readme osx >--------------------------------------------------------------- eb02aa4ae236230b9aa83e18017be779371bdbc7 README.md | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) From git at git.haskell.org Thu Oct 26 23:47:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (4th try). (b183504) Message-ID: <20171026234707.7F7CA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b1835045bfffcbc23d170b7675bf4156bc02e215/ghc >--------------------------------------------------------------- commit b1835045bfffcbc23d170b7675bf4156bc02e215 Author: Andrey Mokhov Date: Sat Jan 9 18:15:23 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (4th try). See #110. [skip ci] >--------------------------------------------------------------- b1835045bfffcbc23d170b7675bf4156bc02e215 build.bat | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 4cbbc42..2901686 100644 --- a/build.bat +++ b/build.bat @@ -17,6 +17,6 @@ %* @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains - at if defined GHC_PACKAGE_PATH ( set GHC_PACKAGE_PATH ) + at set GHC_PACKAGE_PATH= @ghc %ghcArgs% && .shake\build %shakeArgs% From git at git.haskell.org Thu Oct 26 23:47:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement joinArgs and joinArgsWithSpaces as variadic functions. (c6870b2) Message-ID: <20171026234710.40A4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6870b2f0e46782ad6a094cff9809150fe2eebf7/ghc >--------------------------------------------------------------- commit c6870b2f0e46782ad6a094cff9809150fe2eebf7 Author: Andrey Mokhov Date: Sat Jan 3 23:57:51 2015 +0000 Implement joinArgs and joinArgsWithSpaces as variadic functions. >--------------------------------------------------------------- c6870b2f0e46782ad6a094cff9809150fe2eebf7 src/Base.hs | 37 ++++++++++++++++++++++--------------- 1 file changed, 22 insertions(+), 15 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 645d5dc..283d62f 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,6 +23,7 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) type Args = Action [String] + type Condition = Action Bool instance Monoid a => Monoid (Action a) where @@ -35,36 +36,42 @@ class ShowAction a where instance ShowAction String where showAction = return +instance ShowAction (Action String) where + showAction = id + arg :: ShowAction a => [a] -> Args arg = mapM showAction +type ArgsCombine = Args -> Args -> Args + class Collect a where - collect :: Args -> a + collect :: ArgsCombine -> Args -> a instance Collect Args where - collect = id + collect = const id instance (ShowAction a, Collect r) => Collect (a -> r) where - collect prev next = collect $ do - next' <- showAction next - prev <> return [next'] + collect combine x = \y -> collect combine $ x `combine` arg [y] + +instance Collect r => Collect (Args -> r) where + collect combine x = \y -> collect combine $ x `combine` y args :: Collect a => a -args = collect mempty +args = collect (<>) mempty -intercalateArgs :: String -> Args -> Args -intercalateArgs s args = do - as <- args - return [intercalate s as] +joinArgs :: Collect a => a +joinArgs = collect (\x y -> intercalateArgs "" x <> y) mempty -joinArgsWithSpaces :: Args -> Args -joinArgsWithSpaces = intercalateArgs " " +joinArgsWithSpaces :: Collect a => a +joinArgsWithSpaces = collect (\x y -> intercalateArgs " " x <> y) mempty -joinArgs :: Args -> Args -joinArgs = intercalateArgs "" +intercalateArgs :: String -> Args -> Args +intercalateArgs s as = do + as' <- as + return [intercalate s as'] splitArgs :: Args -> Args splitArgs = fmap (concatMap words) filterOut :: Args -> [String] -> Args -filterOut args list = filter (`notElem` list) <$> args +filterOut as list = filter (`notElem` list) <$> as From git at git.haskell.org Thu Oct 26 23:47:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up Windows script (8ed92e9) Message-ID: <20171026234711.2C1CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ed92e90674c9078ebe08fdd5f1edd758f48f7f7/ghc >--------------------------------------------------------------- commit 8ed92e90674c9078ebe08fdd5f1edd758f48f7f7 Author: Andrey Mokhov Date: Sat Dec 26 12:33:59 2015 +0000 Clean up Windows script >--------------------------------------------------------------- 8ed92e90674c9078ebe08fdd5f1edd758f48f7f7 README.md | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 9844bf6..a93ed9a 100644 --- a/README.md +++ b/README.md @@ -38,13 +38,13 @@ Now you have a couple of options: ### Windows -``` -$ git clone --recursive git://git.haskell.org/ghc.git -$ cd ghc -$ git clone git://github.com/snowleopard/shaking-up-ghc shake-build -$ ./boot -$ ./configure --enable-tarballs-autodownload -$ shake-build/build.bat +```bash +git clone --recursive git://git.haskell.org/ghc.git +cd ghc +git clone git://github.com/snowleopard/shaking-up-ghc shake-build +./boot +./configure --enable-tarballs-autodownload +shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. From git at git.haskell.org Thu Oct 26 23:47:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (5th try). (9ba5daa) Message-ID: <20171026234711.8B4A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ba5daa863d59d5b2a7bd8fabdd9caa0b8fe4521/ghc >--------------------------------------------------------------- commit 9ba5daa863d59d5b2a7bd8fabdd9caa0b8fe4521 Author: Andrey Mokhov Date: Sat Jan 9 19:10:44 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (5th try). See #110. >--------------------------------------------------------------- 9ba5daa863d59d5b2a7bd8fabdd9caa0b8fe4521 build.bat | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/build.bat b/build.bat index 2901686..07e355a 100644 --- a/build.bat +++ b/build.bat @@ -16,7 +16,11 @@ ".." ^ %* - at rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains - at set GHC_PACKAGE_PATH= - at ghc %ghcArgs% && .shake\build %shakeArgs% + at ghc %ghcArgs% + + at if %ERRORLEVEL% EQU 0 ( + @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains + @set GHC_PACKAGE_PATH= + @.shake\build %shakeArgs% +) From git at git.haskell.org Thu Oct 26 23:47:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor using variadic args. (a4f318f) Message-ID: <20171026234713.B370C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4f318fdf2905dd1ee5be475bfa38fae4a39b869/ghc >--------------------------------------------------------------- commit a4f318fdf2905dd1ee5be475bfa38fae4a39b869 Author: Andrey Mokhov Date: Sun Jan 4 03:30:13 2015 +0000 Refactor using variadic args. >--------------------------------------------------------------- a4f318fdf2905dd1ee5be475bfa38fae4a39b869 src/Base.hs | 36 +++++++++++++++--------------- src/Oracles/Builder.hs | 16 +++++++------- src/Oracles/Flag.hs | 8 +++---- src/Oracles/Option.hs | 10 ++++----- src/Package.hs | 59 ++++++++++++++++++++++---------------------------- 5 files changed, 62 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 a4f318fdf2905dd1ee5be475bfa38fae4a39b869 From git at git.haskell.org Thu Oct 26 23:47:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add IRC to README.md (bf060f8) Message-ID: <20171026234715.067DB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf060f88c69ebdfb2c9a673a101b2b18c4f3c3e5/ghc >--------------------------------------------------------------- commit bf060f88c69ebdfb2c9a673a101b2b18c4f3c3e5 Author: Moritz Angermann Date: Sat Dec 26 22:17:12 2015 +0800 Add IRC to README.md add's a link (to what ever systems support `irc://`), everyone else, will hopefully know what to do :) >--------------------------------------------------------------- bf060f88c69ebdfb2c9a673a101b2b18c4f3c3e5 README.md | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/README.md b/README.md index a93ed9a..ca1e5fb 100644 --- a/README.md +++ b/README.md @@ -9,9 +9,7 @@ on the [wiki page][ghc-shake-wiki] and in this [blog post][shake-blog-post]. This is supposed to go into the `shake-build` directory of the GHC source tree. - - - +[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc) Trying it --------- From git at git.haskell.org Thu Oct 26 23:47:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor generators, add makeExecutable action. (3dff957) Message-ID: <20171026234715.7B95C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3dff95749258bfaa8a21ad0e2588a391ade36649/ghc >--------------------------------------------------------------- commit 3dff95749258bfaa8a21ad0e2588a391ade36649 Author: Andrey Mokhov Date: Sat Jan 9 20:09:51 2016 +0000 Refactor generators, add makeExecutable action. >--------------------------------------------------------------- 3dff95749258bfaa8a21ad0e2588a391ade36649 src/GHC.hs | 8 ++++++-- src/Rules/Actions.hs | 7 ++++++- src/Rules/Generate.hs | 17 +++++++---------- src/Rules/Generators/Common.hs | 20 ++++++++++++++++++++ src/Rules/Generators/ConfigHs.hs | 10 +++------- src/Rules/Generators/GhcAutoconfH.hs | 5 ++--- src/Rules/Generators/GhcBootPlatformH.hs | 8 +++----- src/Rules/Generators/GhcPlatformH.hs | 6 ++---- src/Rules/Generators/GhcSplit.hs | 21 ++++++++++----------- src/Rules/Generators/GhcVersionH.hs | 6 ++---- src/Rules/Generators/VersionHs.hs | 5 ++--- src/Rules/Perl.hs | 17 +++-------------- src/Rules/Program.hs | 2 +- 13 files changed, 67 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3dff95749258bfaa8a21ad0e2588a391ade36649 From git at git.haskell.org Thu Oct 26 23:47:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor changes and comments. (640b38f) Message-ID: <20171026234717.26EED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/640b38fbd3857a6c72156f81bd4ba06b8af61ae2/ghc >--------------------------------------------------------------- commit 640b38fbd3857a6c72156f81bd4ba06b8af61ae2 Author: Andrey Mokhov Date: Sun Jan 4 03:35:36 2015 +0000 Minor changes and comments. >--------------------------------------------------------------- 640b38fbd3857a6c72156f81bd4ba06b8af61ae2 src/Base.hs | 2 +- src/Package.hs | 18 +++++++++--------- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 490c031..ea9980c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,7 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, args, ShowAction (..), Collect (..), + Args, arg, args, ShowAction (..), Condition (..), joinArgs, joinArgsSpaced, splitArgs, filterOut diff --git a/src/Package.hs b/src/Package.hs index 5d6fc1e..843f34f 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -230,14 +230,14 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = return $ path dir modPath <.> extension packageKey <- packagaDataOption pkgData PackageKey run (Ghc stage) $ mconcat - [ arg ["-M"] + [ arg "-M" , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - , splitArgs $ arg [SrcHcOpts] - , when (stage == Stage0) $ arg ["-package-db libraries/bootstrapping.conf"] - , arg [if usePackageKey then "-this-package-key" else "-package-name"] - , arg [packageKey] -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) - , arg ["-hide-all-packages"] - , arg ["-i"] -- resets the search path to nothing; TODO: check if really needed + , splitArgs $ arg SrcHcOpts -- TODO: get rid of splitArgs + , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" + , arg $ if usePackageKey then "-this-package-key" else "-package-name" + , arg packageKey -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg "-hide-all-packages" + , arg "-i" -- resets the search path to nothing; TODO: check if really needed , arg $ map (\d -> "-i" ++ path d) srcDirs , arg $ do prefix <- ["-i", "-I"] -- 'import' and '#include' search paths @@ -245,8 +245,8 @@ buildPackageDeps pkg @ (Package name path _) (stage, dist, settings) = return $ prefix ++ buildDir suffix , arg $ map (\d -> "-I" ++ path d) $ filter isRelative includeDirs , arg $ map (\d -> "-I" ++ d) $ filter isAbsolute includeDirs - , arg ["-optP-include"] - , arg ["-optP" ++ buildDir "build/autogen/cabal_macros.h"] + , arg "-optP-include" + , arg $ "-optP" ++ buildDir "build/autogen/cabal_macros.h" , if usePackageKey then arg $ concatMap (\d -> ["-package-key", d]) depKeys else arg $ concatMap (\d -> ["-package" , d]) deps From git at git.haskell.org Thu Oct 26 23:47:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #51 from snowleopard/angerman-patch-1 (ec44701) Message-ID: <20171026234718.98ACE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ec447012e50b62b6f96dde134514505ed9795156/ghc >--------------------------------------------------------------- commit ec447012e50b62b6f96dde134514505ed9795156 Merge: 8ed92e9 bf060f8 Author: Andrey Mokhov Date: Sat Dec 26 14:23:16 2015 +0000 Merge pull request #51 from snowleopard/angerman-patch-1 Add IRC to README.md >--------------------------------------------------------------- ec447012e50b62b6f96dde134514505ed9795156 README.md | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:47:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build stage1 GHC only on appveyor to fit into the time limit. (4745578) Message-ID: <20171026234719.11E983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4745578604163225043051c6963284c0a52affef/ghc >--------------------------------------------------------------- commit 4745578604163225043051c6963284c0a52affef Author: Andrey Mokhov Date: Sat Jan 9 20:14:31 2016 +0000 Build stage1 GHC only on appveyor to fit into the time limit. See #110. [skip ci] >--------------------------------------------------------------- 4745578604163225043051c6963284c0a52affef .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 16de309..99196db 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Thu Oct 26 23:47:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Package.hs into logically separate modules. (04cbcbc) Message-ID: <20171026234720.B3CCA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/04cbcbc9a482ed70872e3f3bc1c6ca9224402b76/ghc >--------------------------------------------------------------- commit 04cbcbc9a482ed70872e3f3bc1c6ca9224402b76 Author: Andrey Mokhov Date: Mon Jan 5 00:40:25 2015 +0000 Decompose Package.hs into logically separate modules. >--------------------------------------------------------------- 04cbcbc9a482ed70872e3f3bc1c6ca9224402b76 src/Package.hs | 284 +------------------------------------------- src/Package/Base.hs | 86 ++++++++++++++ src/Package/Data.hs | 92 ++++++++++++++ src/Package/Dependencies.hs | 108 +++++++++++++++++ 4 files changed, 292 insertions(+), 278 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 04cbcbc9a482ed70872e3f3bc1c6ca9224402b76 From git at git.haskell.org Thu Oct 26 23:47:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update LICENSE (e4e72d8) Message-ID: <20171026234722.4C4883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4e72d888288f7fb40c94fc13bc6e3a7d9d3bd52/ghc >--------------------------------------------------------------- commit e4e72d888288f7fb40c94fc13bc6e3a7d9d3bd52 Author: Moritz Angermann Date: Sat Dec 26 22:23:31 2015 +0800 Update LICENSE Be explicit about the license. Prevent others from having to lookup the license that matches this text. >--------------------------------------------------------------- e4e72d888288f7fb40c94fc13bc6e3a7d9d3bd52 LICENSE | 2 ++ 1 file changed, 2 insertions(+) diff --git a/LICENSE b/LICENSE index a78df02..9ee6e34 100644 --- a/LICENSE +++ b/LICENSE @@ -1,3 +1,5 @@ +BSD License + Copyright (c) 2015, Andrey Mokhov All rights reserved. From git at git.haskell.org Thu Oct 26 23:47:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing source Settings.Builders.Common (1ad387d) Message-ID: <20171026234722.DB80E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ad387d0ac1af354fff93b384251fab482eee49d/ghc >--------------------------------------------------------------- commit 1ad387d0ac1af354fff93b384251fab482eee49d Author: Andrey Mokhov Date: Sat Jan 9 20:21:27 2016 +0000 Add missing source Settings.Builders.Common [skip ci] >--------------------------------------------------------------- 1ad387d0ac1af354fff93b384251fab482eee49d shaking-up-ghc.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index a5b4c57..9c40f46 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -43,6 +43,7 @@ executable ghc-shake , Rules.Dependencies , Rules.Documentation , Rules.Generate + , Rules.Generators.Common , Rules.Generators.ConfigHs , Rules.Generators.GhcAutoconfH , Rules.Generators.GhcBootPlatformH From git at git.haskell.org Thu Oct 26 23:47:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track build rule source files initiating incremental rebuilds when code changes. (5a4b172) Message-ID: <20171026234724.23E493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a4b172667f27d01ae46f6dc7d9bc7097ea06605/ghc >--------------------------------------------------------------- commit 5a4b172667f27d01ae46f6dc7d9bc7097ea06605 Author: Andrey Mokhov Date: Mon Jan 5 00:48:32 2015 +0000 Track build rule source files initiating incremental rebuilds when code changes. >--------------------------------------------------------------- 5a4b172667f27d01ae46f6dc7d9bc7097ea06605 src/Package/Data.hs | 1 + src/Package/Dependencies.hs | 1 + 2 files changed, 2 insertions(+) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 2d7b4b7..c95f8c9 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -56,6 +56,7 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = "build" "autogen" "cabal_macros.h", "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. ] &%> \_ -> do + need ["shake/src/Package/Data.hs"] -- Track changes in this file need [path name <.> "cabal"] when (doesFileExist $ path "configure.ac") $ need [path "configure"] run GhcCabal cabalArgs diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 65c9b1f..99ffc34 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -68,6 +68,7 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = let buildDir = path dist in (buildDir "build" name <.> "m") %> \out -> do + need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file let pkgData = buildDir "package-data.mk" usePackageKey <- SupportsPackageKey || stage /= Stage0 -- TODO: check reasoning (distdir-way-opts) [mods, srcDirs, includeDirs, deps, depKeys] <- From git at git.haskell.org Thu Oct 26 23:47:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #52 from snowleopard/angerman-patch-2 (b6f3045) Message-ID: <20171026234725.C5B1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6f30456f0c67d0e9393ad4a42f1b99126899e70/ghc >--------------------------------------------------------------- commit b6f30456f0c67d0e9393ad4a42f1b99126899e70 Merge: ec44701 e4e72d8 Author: Andrey Mokhov Date: Sat Dec 26 14:25:47 2015 +0000 Merge pull request #52 from snowleopard/angerman-patch-2 Update LICENSE >--------------------------------------------------------------- b6f30456f0c67d0e9393ad4a42f1b99126899e70 LICENSE | 2 ++ 1 file changed, 2 insertions(+) From git at git.haskell.org Thu Oct 26 23:47:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build stage1 GHC only to fit into OS X time limit on Travis. (db5dce0) Message-ID: <20171026234726.5AE013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db5dce0cb5d252e1a0576ec9731a758b98385fdc/ghc >--------------------------------------------------------------- commit db5dce0cb5d252e1a0576ec9731a758b98385fdc Author: Andrey Mokhov Date: Sat Jan 9 20:23:41 2016 +0000 Build stage1 GHC only to fit into OS X time limit on Travis. >--------------------------------------------------------------- db5dce0cb5d252e1a0576ec9731a758b98385fdc .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index ca51b6f..3c5f522 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - cabal update - os: osx - env: TARGET=libraries/base/stage1/build/libHSbase-4.9.0.0.a + env: TARGET=inplace/bin/ghc-stage1.exe before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Thu Oct 26 23:47:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add directions to Package submodules. (eeea3ed) Message-ID: <20171026234727.A8E423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eeea3ed76e1886c34234a4efde6f3c6dc296c2d4/ghc >--------------------------------------------------------------- commit eeea3ed76e1886c34234a4efde6f3c6dc296c2d4 Author: Andrey Mokhov Date: Mon Jan 5 00:57:26 2015 +0000 Add directions to Package submodules. >--------------------------------------------------------------- eeea3ed76e1886c34234a4efde6f3c6dc296c2d4 src/Package.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index ce7a8d5..ea7aae4 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,16 +1,15 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package ( - packageRules - ) where +module Package (packageRules) where import Package.Base import Package.Data import Package.Dependencies -- These are the packages we build +-- See Package.Base for definitions of basic types packages :: [Package] packages = [libraryPackage "deepseq" Stage1 defaultSettings] +-- Rule buildXY is defined in module X.Y buildPackage :: Package -> TodoItem -> Rules () buildPackage pkg todoItem = do buildPackageData pkg todoItem @@ -18,8 +17,7 @@ buildPackage pkg todoItem = do packageRules :: Rules () packageRules = do - - want ["libraries/deepseq/dist-install/build/deepseq.m"] + want ["libraries/deepseq/dist-install/build/deepseq.m"] -- TODO: control targets from commang line arguments forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:47:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rewrite digest, avoid using list (to avoid a shadow warning), and avoid using head (partial function) (02ec50d) Message-ID: <20171026234744.F0C763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02ec50d957a3ebd736ccb631795489eec971d528/ghc >--------------------------------------------------------------- commit 02ec50d957a3ebd736ccb631795489eec971d528 Author: Neil Mitchell Date: Sat Jan 9 21:46:36 2016 +0000 Rewrite digest, avoid using list (to avoid a shadow warning), and avoid using head (partial function) >--------------------------------------------------------------- 02ec50d957a3ebd736ccb631795489eec971d528 src/Rules/Actions.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 51f7625..338bec3 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -132,7 +132,6 @@ putInfo (Target.Target {..}) = putBuild $ renderBox where stageInfo = if isStaged builder then "" else "stage = " ++ show stage ++ ", " wayInfo = if way == vanilla then "" else ", way = " ++ show way - digest list = case list of - [] -> "none" - [x] -> x - xs -> head xs ++ " (and " ++ show (length xs - 1) ++ " more)" + digest [] = "none" + digest [x] = x + digest (x:xs) = x ++ " (and " ++ show (length xs) ++ " more)" From git at git.haskell.org Thu Oct 26 23:47:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle multiword options in build rules. (1a7b657) Message-ID: <20171026234745.8C2F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a7b657a0b02d361a5ba69f1c68d772e43b3e47b/ghc >--------------------------------------------------------------- commit 1a7b657a0b02d361a5ba69f1c68d772e43b3e47b Author: Andrey Mokhov Date: Tue Jan 6 19:19:10 2015 +0000 Handle multiword options in build rules. >--------------------------------------------------------------- 1a7b657a0b02d361a5ba69f1c68d772e43b3e47b src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index fe3ec26..b156eaa 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -21,8 +21,8 @@ configureArgs stage settings = argConf key as = joinArgs "--configure-option=" key "=" as argConfWith key opt = do - [value] <- showAction opt - when (value /= "") $ argConf ("--with-" ++ key) $ arg value + opts <- showAction opt + when (opts /= []) $ argConf ("--with-" ++ key) $ arg opts cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) (ConfCcArgs stage) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 4327ca6..ede14bb 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -81,7 +81,7 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = run (Ghc stage) $ mconcat [ arg "-M" , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - , splitArgs $ arg SrcHcOpts -- TODO: get rid of splitArgs + , arg SrcHcOpts -- TODO: get rid of splitArgs , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" , arg $ if usePackageKey then "-this-package-key" else "-package-name" , arg packageKey -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) From git at git.haskell.org Thu Oct 26 23:47:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use existing target input instead of made up 'src' (f80dd4c) Message-ID: <20171026234747.D88193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f80dd4cc253afd4178f794e20aac9b0379b8d036/ghc >--------------------------------------------------------------- commit f80dd4cc253afd4178f794e20aac9b0379b8d036 Author: Andrey Mokhov Date: Sat Dec 26 21:53:37 2015 +0000 Use existing target input instead of made up 'src' >--------------------------------------------------------------- f80dd4cc253afd4178f794e20aac9b0379b8d036 src/Oracles/ArgsHash.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 1f4c584..65bfc8a 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -13,7 +13,7 @@ newtype ArgsHashKey = ArgsHashKey Target -- argument list and computes its hash. The resulting value is tracked in a -- Shake oracle, hence initiating rebuilts when the hash is changed (a hash -- change indicates changes in the build system). --- Note: we replace target sources with ["src"] for performance reasons -- to +-- Note: we keep only the first target input for performance reasons -- to -- avoid storing long lists of source files passed to some builders (e.g. Ar) -- in the Shake database. This optimisation is harmless, because argument list -- constructors are assumed not to examine target sources, but only append them @@ -22,7 +22,8 @@ newtype ArgsHashKey = ArgsHashKey Target -- TODO: Hash Target to improve accuracy and performance. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do - _ <- askOracle . ArgsHashKey $ target { inputs = ["src"] } :: Action Int + let firstInput = take 1 $ inputs target + _ <- askOracle . ArgsHashKey $ target { inputs = firstInput } :: Action Int return () -- Oracle for storing per-target argument list hashes From git at git.haskell.org Thu Oct 26 23:47:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid using Traversable to get at forM (eda5882) Message-ID: <20171026234748.A5D713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eda5882a83ad353eb636b4249439095d237e331f/ghc >--------------------------------------------------------------- commit eda5882a83ad353eb636b4249439095d237e331f Author: Neil Mitchell Date: Sat Jan 9 21:46:52 2016 +0000 Avoid using Traversable to get at forM >--------------------------------------------------------------- eda5882a83ad353eb636b4249439095d237e331f src/Rules.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index fe8242b..7af1556 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -2,7 +2,6 @@ module Rules (generateTargets, packageRules) where import Base import Data.Foldable -import Data.Traversable import Expression import GHC import Rules.Generate @@ -25,7 +24,7 @@ targetsForStage :: Stage -> Action [String] targetsForStage stage = do pkgs <- interpretWithStage stage getPackages let libPkgs = filter isLibrary pkgs \\ [rts, libffi] - libTargets <- fmap concat . for libPkgs $ \pkg -> do + libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg needHaddock <- interpretPartial target buildHaddock return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] From git at git.haskell.org Thu Oct 26 23:47:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Ensure that intercalateArgs _ mempty = mempty. (9a24f38) Message-ID: <20171026234749.2FDD13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a24f3876e945b6927fb0df1da0b373c3c87cba2/ghc >--------------------------------------------------------------- commit 9a24f3876e945b6927fb0df1da0b373c3c87cba2 Author: Andrey Mokhov Date: Wed Jan 7 01:16:43 2015 +0000 Ensure that intercalateArgs _ mempty = mempty. >--------------------------------------------------------------- 9a24f3876e945b6927fb0df1da0b373c3c87cba2 src/Base.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 9868528..8a98a7b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -70,7 +70,9 @@ joinArgsSpaced = collect (\x y -> intercalateArgs " " $ x <> y) mempty intercalateArgs :: String -> Args -> Args intercalateArgs s as = do as' <- as - return [intercalate s as'] + case as' of + [] -> mempty + otherwise -> return [intercalate s as'] filterOut :: Args -> [String] -> Args filterOut as list = filter (`notElem` list) <$> as From git at git.haskell.org Thu Oct 26 23:47:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initialise bootstrapping.conf (fix #42). (20037b1) Message-ID: <20171026234751.CF1023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20037b1e711c2e90ed09bd1c6543cc3f05ac7407/ghc >--------------------------------------------------------------- commit 20037b1e711c2e90ed09bd1c6543cc3f05ac7407 Author: Andrey Mokhov Date: Sat Dec 26 21:58:17 2015 +0000 Initialise bootstrapping.conf (fix #42). >--------------------------------------------------------------- 20037b1e711c2e90ed09bd1c6543cc3f05ac7407 src/Base.hs | 20 ++++++++++++++++---- src/Rules/Cabal.hs | 13 +++++++++++++ src/Rules/Data.hs | 8 ++++---- src/Rules/Generate.hs | 15 ++++++++------- src/Settings/Builders/Ghc.hs | 3 ++- src/Settings/Builders/GhcCabal.hs | 9 ++++++--- src/Settings/Builders/GhcPkg.hs | 12 ++++++++++-- 7 files changed, 59 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 20037b1e711c2e90ed09bd1c6543cc3f05ac7407 From git at git.haskell.org Thu Oct 26 23:47:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to Config.hs (#47). (44d81b0) Message-ID: <20171026234729.7D6903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44d81b0961073c172630fd52b76985fa9a6601b3/ghc >--------------------------------------------------------------- commit 44d81b0961073c172630fd52b76985fa9a6601b3 Author: Andrey Mokhov Date: Sat Dec 26 14:42:49 2015 +0000 Fix path to Config.hs (#47). >--------------------------------------------------------------- 44d81b0961073c172630fd52b76985fa9a6601b3 src/Rules/Generate.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index f9c1e0b..bf0afa0 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -71,15 +71,15 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = build $ fullTarget target GenPrimopCode [primopsTxt] [file] priority 2.0 $ do - when (pkg == ghcPkg) $ buildPath -/- "Config.hs" %> \file -> do + when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs - when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do - file <~ generateVersionHs - when (pkg == compiler) $ platformH %> \file -> do file <~ generateGhcBootPlatformH + when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do + file <~ generateVersionHs + when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putBuild $ "| Successfully generated '" ++ file ++ "'." From git at git.haskell.org Thu Oct 26 23:47:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop exe extension. (ef6ddf9) Message-ID: <20171026234730.011F23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef6ddf94b8cd9d3ca0f3054dc163d04996838839/ghc >--------------------------------------------------------------- commit ef6ddf94b8cd9d3ca0f3054dc163d04996838839 Author: Andrey Mokhov Date: Sat Jan 9 20:38:42 2016 +0000 Drop exe extension. >--------------------------------------------------------------- ef6ddf94b8cd9d3ca0f3054dc163d04996838839 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 3c5f522..dd3bd12 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - cabal update - os: osx - env: TARGET=inplace/bin/ghc-stage1.exe + env: TARGET=inplace/bin/ghc-stage1 before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Thu Oct 26 23:47:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor changes. (500ab74) Message-ID: <20171026234731.1E84B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/500ab7440aaf5aca6a11df8c6001a963aeb30fe4/ghc >--------------------------------------------------------------- commit 500ab7440aaf5aca6a11df8c6001a963aeb30fe4 Author: Andrey Mokhov Date: Mon Jan 5 01:03:05 2015 +0000 Minor changes. >--------------------------------------------------------------- 500ab7440aaf5aca6a11df8c6001a963aeb30fe4 src/Package.hs | 3 ++- src/Package/Base.hs | 9 ++++----- src/Package/Data.hs | 4 +--- src/Package/Dependencies.hs | 4 +--- 4 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index ea7aae4..7a5f20e 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -4,8 +4,9 @@ import Package.Base import Package.Data import Package.Dependencies --- These are the packages we build -- See Package.Base for definitions of basic types + +-- These are the packages we build: packages :: [Package] packages = [libraryPackage "deepseq" Stage1 defaultSettings] diff --git a/src/Package/Base.hs b/src/Package/Base.hs index daa5455..896bcb3 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -62,11 +62,10 @@ commonCppArgs :: Args commonCppArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? commonCcWarninigArgs :: Args -commonCcWarninigArgs = when Validating $ mconcat - [ when GccIsClang $ arg "-Wno-unknown-pragmas" - , when (not GccIsClang && not GccLt46) $ arg "-Wno-error=inline" - , when ( GccIsClang && not GccLt46 && windowsHost) $ arg "-Werror=unused-but-set-variable" - ] +commonCcWarninigArgs = when Validating $ + when GccIsClang (arg "-Wno-unknown-pragmas") + <> when (not GccIsClang && not GccLt46) (arg "-Wno-error=inline") + <> when ( GccIsClang && not GccLt46 && windowsHost) (arg "-Werror=unused-but-set-variable" ) bootPkgConstraints :: Args bootPkgConstraints = mempty diff --git a/src/Package/Data.hs b/src/Package/Data.hs index c95f8c9..fe3ec26 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -1,7 +1,5 @@ {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} -module Package.Data ( - buildPackageData - ) where +module Package.Data (buildPackageData) where import Package.Base diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 99ffc34..4327ca6 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -1,7 +1,5 @@ {-# LANGUAGE NoImplicitPrelude #-} -module Package.Dependencies ( - buildPackageDependencies - ) where +module Package.Dependencies (buildPackageDependencies) where import Package.Base From git at git.haskell.org Thu Oct 26 23:47:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (382ecb4) Message-ID: <20171026234733.298713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/382ecb4b36b9e06dc5f3875a7cc8aeb287623696/ghc >--------------------------------------------------------------- commit 382ecb4b36b9e06dc5f3875a7cc8aeb287623696 Merge: 44d81b0 b6f3045 Author: Andrey Mokhov Date: Sat Dec 26 14:43:49 2015 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 382ecb4b36b9e06dc5f3875a7cc8aeb287623696 LICENSE | 2 ++ README.md | 4 +--- 2 files changed, 3 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:47:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't conflict with parallel in the latest Shake, provides a warning free way to be forward and backward compatible with Shake (albeit not pretty) (8efb43d) Message-ID: <20171026234733.B5B553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8efb43dd384111a0f724924507aac59a655b382d/ghc >--------------------------------------------------------------- commit 8efb43dd384111a0f724924507aac59a655b382d Author: Neil Mitchell Date: Sat Jan 9 21:33:02 2016 +0000 Don't conflict with parallel in the latest Shake, provides a warning free way to be forward and backward compatible with Shake (albeit not pretty) >--------------------------------------------------------------- 8efb43dd384111a0f724924507aac59a655b382d src/GHC.hs | 4 ++-- src/Way.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index f967263..1574ec3 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,7 +4,7 @@ module GHC ( deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, + integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, @@ -26,7 +26,7 @@ defaultKnownPackages = , deepseq, deriveConstants, directory, dllSplit, filepath, genapply , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp - , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty + , integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time , touchy, transformers, unlit, unix, win32, xhtml ] diff --git a/src/Way.hs b/src/Way.hs index 3b1f6c0..94a3bcc 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, - vanilla, profiling, logging, parallel, granSim, + vanilla, profiling, logging, Way.parallel, granSim, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, From git at git.haskell.org Thu Oct 26 23:47:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant extension. (e384039) Message-ID: <20171026234734.8E49E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3840397d0db313e8c22e45782e188e5c7c642dc/ghc >--------------------------------------------------------------- commit e3840397d0db313e8c22e45782e188e5c7c642dc Author: Andrey Mokhov Date: Mon Jan 5 01:08:03 2015 +0000 Remove redundant extension. >--------------------------------------------------------------- e3840397d0db313e8c22e45782e188e5c7c642dc src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index ea9980c..6bef5ba 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-} +{-# LANGUAGE FlexibleInstances #-} module Base ( module Development.Shake, From git at git.haskell.org Thu Oct 26 23:47:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop doc directory (no useful docs there anyway), fix #54. (7f8db60) Message-ID: <20171026234736.ADFE93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7f8db6059059fbeffe0519bcb60cfac235fa10b2/ghc >--------------------------------------------------------------- commit 7f8db6059059fbeffe0519bcb60cfac235fa10b2 Author: Andrey Mokhov Date: Sat Dec 26 15:23:08 2015 +0000 Drop doc directory (no useful docs there anyway), fix #54. >--------------------------------------------------------------- 7f8db6059059fbeffe0519bcb60cfac235fa10b2 doc/boom.png | Bin 91102 -> 0 bytes doc/build-expressions.docx | Bin 22575 -> 0 bytes doc/build-expressions.pdf | Bin 644843 -> 0 bytes doc/build-package-data.docx | Bin 16519 -> 0 bytes doc/comment-hi-rule.txt | 39 --------- doc/deepseq-build-progress.txt | 86 -------------------- doc/demo.txt | 23 ------ doc/meeting-16-June-2015.txt | 163 -------------------------------------- doc/meeting-25-September-2015.txt | 98 ----------------------- 9 files changed, 409 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 7f8db6059059fbeffe0519bcb60cfac235fa10b2 From git at git.haskell.org Thu Oct 26 23:47:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a .ghci file, useful for experimenting and using ghcid (4444fa4) Message-ID: <20171026234737.5B5063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4444fa437e6a36908414924a707ff538841f17a1/ghc >--------------------------------------------------------------- commit 4444fa437e6a36908414924a707ff538841f17a1 Author: Neil Mitchell Date: Sat Jan 9 21:33:21 2016 +0000 Add a .ghci file, useful for experimenting and using ghcid >--------------------------------------------------------------- 4444fa437e6a36908414924a707ff538841f17a1 .ghci | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.ghci b/.ghci new file mode 100644 index 0000000..1fe85b3 --- /dev/null +++ b/.ghci @@ -0,0 +1,2 @@ +:set -Wall -isrc +:load Main From git at git.haskell.org Thu Oct 26 23:47:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove splitArgs. (9133934) Message-ID: <20171026234738.273393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91339343449600edd26a8e427a246bee2ae63166/ghc >--------------------------------------------------------------- commit 91339343449600edd26a8e427a246bee2ae63166 Author: Andrey Mokhov Date: Tue Jan 6 19:16:50 2015 +0000 Remove splitArgs. >--------------------------------------------------------------- 91339343449600edd26a8e427a246bee2ae63166 src/Base.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 6bef5ba..9868528 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -9,7 +9,7 @@ module Base ( Stage (..), Args, arg, args, ShowAction (..), Condition (..), - joinArgs, joinArgsSpaced, splitArgs, + joinArgs, joinArgsSpaced, filterOut ) where @@ -72,8 +72,5 @@ intercalateArgs s as = do as' <- as return [intercalate s as'] -splitArgs :: Args -> Args -splitArgs = fmap (concatMap words) - filterOut :: Args -> [String] -> Args filterOut as list = filter (`notElem` list) <$> as From git at git.haskell.org Thu Oct 26 23:47:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need . (6d4720c) Message-ID: <20171026234740.AAD153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d4720c1e65d2b4a6cc88152f4547915aebcce42/ghc >--------------------------------------------------------------- commit 6d4720c1e65d2b4a6cc88152f4547915aebcce42 Author: Andrey Mokhov Date: Sat Dec 26 16:25:14 2015 +0000 Don't need . >--------------------------------------------------------------- 6d4720c1e65d2b4a6cc88152f4547915aebcce42 src/Oracles/Config.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index 5a163a6..e8333b6 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -7,6 +7,9 @@ import qualified Data.HashMap.Strict as Map newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +configFile :: FilePath +configFile = configPath -/- "system.config" + askConfig :: String -> Action String askConfig key = askConfigWithDefault key . putError $ "Cannot find key '" ++ key ++ "' in configuration files." @@ -21,11 +24,7 @@ askConfigWithDefault key defaultAction = do -- Oracle for configuration files configOracle :: Rules () configOracle = do - let configFile = configPath -/- "system.config" cfg <- newCache $ \() -> do - unlessM (doesFileExist $ configFile <.> "in") $ - putError $ "\nConfiguration file '" ++ (configFile <.> "in") - ++ "' is missing; unwilling to proceed." need [configFile] putOracle $ "Reading " ++ configFile ++ "..." liftIO $ readConfigFile configFile From git at git.haskell.org Thu Oct 26 23:47:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor getSingleton to avoid using list, otherwise an import of Data.Extra.List causes shadowing issues (dbe8c1e) Message-ID: <20171026234741.396FF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dbe8c1e0f387f98c7edaaaf2f5dfda1ed25a9b2a/ghc >--------------------------------------------------------------- commit dbe8c1e0f387f98c7edaaaf2f5dfda1ed25a9b2a Author: Neil Mitchell Date: Sat Jan 9 21:45:53 2016 +0000 Refactor getSingleton to avoid using list, otherwise an import of Data.Extra.List causes shadowing issues >--------------------------------------------------------------- dbe8c1e0f387f98c7edaaaf2f5dfda1ed25a9b2a src/Expression.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 6e2a225..932ed80 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -204,7 +204,7 @@ getOutput = do getSingleton :: Expr [a] -> String -> Expr a getSingleton expr msg = do - list <- expr - case list of + xs <- expr + case xs of [res] -> return res _ -> lift $ putError msg From git at git.haskell.org Thu Oct 26 23:47:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Support multiword options. (b9c1da8) Message-ID: <20171026234742.019AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b9c1da83d8c87ee3f95fa25ed284ce7a12f81caa/ghc >--------------------------------------------------------------- commit b9c1da83d8c87ee3f95fa25ed284ce7a12f81caa Author: Andrey Mokhov Date: Tue Jan 6 19:18:29 2015 +0000 Support multiword options. >--------------------------------------------------------------- b9c1da83d8c87ee3f95fa25ed284ce7a12f81caa src/Oracles/Option.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 365c526..6f05a0e 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -13,7 +13,7 @@ data Option = TargetOS | TargetArch | TargetPlatformFull | HostOsCpp instance ShowAction Option where - showAction opt = showAction $ askConfig $ case opt of + showAction opt = showAction $ fmap words $ askConfig $ case opt of TargetOS -> "target-os" TargetArch -> "target-arch" TargetPlatformFull -> "target-platform-full" From git at git.haskell.org Thu Oct 26 23:47:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement build rule for template-hsc.h, fix #44. (6863e5e) Message-ID: <20171026234744.3D0A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6863e5e13c4182976f330a14696109504d1e59b2/ghc >--------------------------------------------------------------- commit 6863e5e13c4182976f330a14696109504d1e59b2 Author: Andrey Mokhov Date: Sat Dec 26 18:31:46 2015 +0000 Implement build rule for template-hsc.h, fix #44. >--------------------------------------------------------------- 6863e5e13c4182976f330a14696109504d1e59b2 shaking-up-ghc.cabal | 1 + src/Main.hs | 2 ++ src/Rules/Install.hs | 11 +++++++++++ src/Settings/Builders/Hsc2Hs.hs | 6 +++++- 4 files changed, 19 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 1e0fbbf..941651b 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -47,6 +47,7 @@ executable ghc-shake , Rules.Generators.GhcBootPlatformH , Rules.Generators.GhcPlatformH , Rules.Generators.VersionHs + , Rules.Install , Rules.Library , Rules.Oracles , Rules.Package diff --git a/src/Main.hs b/src/Main.hs index 0dc8d96..fdc43cd 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,12 +3,14 @@ import Rules import Rules.Cabal import Rules.Config import Rules.Generate +import Rules.Install import Rules.Oracles main :: IO () main = shakeArgs options $ do cabalRules -- see Rules.Cabal configRules -- see Rules.Config + installRules -- see Rules.Install generateTargets -- see Rules generateRules -- see Rules.Generate oracleRules -- see Rules.Oracles diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs new file mode 100644 index 0000000..b592728 --- /dev/null +++ b/src/Rules/Install.hs @@ -0,0 +1,11 @@ +module Rules.Install (installRules) where + +import Expression +import GHC + +installRules :: Rules () +installRules = do + "inplace/lib/template-hsc.h" %> \out -> do + let source = pkgPath hsc2hs -/- "template-hsc.h" + putBuild $ "| Copying " ++ source ++ " -> " ++ out + copyFileChanged source out diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 0c6172d..6721aaf 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -6,6 +6,9 @@ import Predicates (builder, stage0, notStage0) import Settings import Settings.Builders.GhcCabal hiding (cppArgs) +templateHsc :: FilePath +templateHsc = "inplace/lib/template-hsc.h" + hsc2HsArgs :: Args hsc2HsArgs = builder Hsc2Hs ? do stage <- getStage @@ -21,6 +24,7 @@ hsc2HsArgs = builder Hsc2Hs ? do version <- if stage == Stage0 then lift $ ghcCanonVersion else getSetting ProjectVersionInt + lift $ need [templateHsc] mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" @@ -33,7 +37,7 @@ hsc2HsArgs = builder Hsc2Hs ? do , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) , arg ("--cflag=-D__GLASGOW_HASKELL__=" ++ version) - , arg $ "--template=" ++ top -/- "inplace/lib/template-hsc.h" + , arg $ "--template=" ++ top -/- templateHsc , arg $ "-I" ++ top -/- "inplace/lib/include/" , arg =<< getInput , arg "-o", arg =<< getOutput ] From git at git.haskell.org Thu Oct 26 23:47:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Export Data.List.Extra from Base, rather than importing Extra in each module (seems to fit with the general style) (b9c6d43) Message-ID: <20171026234752.787803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b9c6d43718f66950024abb1212bb7fb0de1e8090/ghc >--------------------------------------------------------------- commit b9c6d43718f66950024abb1212bb7fb0de1e8090 Author: Neil Mitchell Date: Sat Jan 9 21:47:34 2016 +0000 Export Data.List.Extra from Base, rather than importing Extra in each module (seems to fit with the general style) >--------------------------------------------------------------- b9c6d43718f66950024abb1212bb7fb0de1e8090 src/Base.hs | 4 ++-- src/Oracles/LookupInPath.hs | 1 - src/Rules/Data.hs | 1 - src/Rules/Libffi.hs | 1 - src/Rules/Library.hs | 2 +- 5 files changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 65a2d1d..a428c2c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -3,7 +3,7 @@ module Base ( module Control.Applicative, module Control.Monad.Extra, module Data.Function, - module Data.List, + module Data.List.Extra, module Data.Maybe, module Data.Monoid, MonadTrans(lift), @@ -31,7 +31,7 @@ import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader import Data.Function -import Data.List +import Data.List.Extra import Data.Maybe import Data.Monoid import Development.Shake hiding (unit, (*>)) diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 2532cb9..d573fd7 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -4,7 +4,6 @@ module Oracles.LookupInPath ( ) where import Base -import Extra (wordsBy) newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index d6f46a6..8b21fc7 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -2,7 +2,6 @@ module Rules.Data (buildPackageData) where import Base import Expression -import Extra (replace) import GHC import Oracles import Predicates (registerPackage) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 31f249b..9d77814 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -2,7 +2,6 @@ module Rules.Libffi (libffiRules, libffiDependencies) where import Base import Expression -import Extra (replace) import GHC import Oracles import Rules.Actions diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 46f3971..ba20034 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -2,7 +2,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Data.Char -import Base hiding (splitPath) +import Base hiding (splitPath, split) import Expression import GHC import Oracles From git at git.haskell.org Thu Oct 26 23:47:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove argConfWith which became redundant. (86b63df) Message-ID: <20171026234752.AF5253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86b63df1d036247dc78af9ec2eccb7886d0e9503/ghc >--------------------------------------------------------------- commit 86b63df1d036247dc78af9ec2eccb7886d0e9503 Author: Andrey Mokhov Date: Wed Jan 7 01:18:33 2015 +0000 Remove argConfWith which became redundant. >--------------------------------------------------------------- 86b63df1d036247dc78af9ec2eccb7886d0e9503 src/Package/Base.hs | 2 +- src/Package/Data.hs | 18 +++++++----------- 2 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 896bcb3..a895f5f 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -65,7 +65,7 @@ commonCcWarninigArgs :: Args commonCcWarninigArgs = when Validating $ when GccIsClang (arg "-Wno-unknown-pragmas") <> when (not GccIsClang && not GccLt46) (arg "-Wno-error=inline") - <> when ( GccIsClang && not GccLt46 && windowsHost) (arg "-Werror=unused-but-set-variable" ) + <> when ( GccIsClang && not GccLt46 && windowsHost) (arg "-Werror=unused-but-set-variable") bootPkgConstraints :: Args bootPkgConstraints = mempty diff --git a/src/Package/Data.hs b/src/Package/Data.hs index b156eaa..0fa1322 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -18,11 +18,7 @@ libraryArgs ways = configureArgs :: Stage -> Settings -> Args configureArgs stage settings = let argConf :: String -> Args -> Args - argConf key as = joinArgs "--configure-option=" key "=" as - - argConfWith key opt = do - opts <- showAction opt - when (opts /= []) $ argConf ("--with-" ++ key) $ arg opts + argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" as cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) (ConfCcArgs stage) @@ -36,10 +32,10 @@ configureArgs stage settings = , argConf "LDFLAGS" ldflags , argConf "CPPFLAGS" cppflags , joinArgs "--gcc-options=" cflags " " ldflags - , argConfWith "iconv-includes" IconvIncludeDirs - , argConfWith "iconv-libraries" IconvLibDirs - , argConfWith "gmp-includes" GmpIncludeDirs - , argConfWith "gmp-libraries" GmpLibDirs + , argConf "--with-iconv-includes" $ arg IconvIncludeDirs + , argConf "--with-iconv-libraries" $ arg IconvLibDirs + , argConf "--with-gmp-includes" $ arg GmpIncludeDirs + , argConf "--with-gmp-libraries" $ arg GmpLibDirs , when CrossCompiling $ argConf "--host" $ arg TargetPlatformFull -- TODO: why not host? , argConf "--with-cc" $ arg Gcc ] @@ -66,8 +62,8 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = [ args "configure" path dist -- this is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument - -- * if there are many, we must collapse them into one string argument - , joinArgsSpaced $ customDllArgs settings + -- * if there are many, we must collapse them into one space-separated string + , joinArgsSpaced "" (customDllArgs settings) , with $ Ghc stage -- TODO: used to be stage01 (using max Stage1 GHC) , with $ GhcPkg stage From git at git.haskell.org Thu Oct 26 23:47:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use ||^ for OR-ing Predicates. (2d221a4) Message-ID: <20171026234755.628203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d221a4c3d8b79d3a88f8faa90b884aef5d160ea/ghc >--------------------------------------------------------------- commit 2d221a4c3d8b79d3a88f8faa90b884aef5d160ea Author: Andrey Mokhov Date: Sat Dec 26 22:00:44 2015 +0000 Use ||^ for OR-ing Predicates. >--------------------------------------------------------------- 2d221a4c3d8b79d3a88f8faa90b884aef5d160ea src/Settings/Builders/GhcCabal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 17b1725..80c4f4c 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -80,7 +80,7 @@ bootPackageDbArgs :: Args bootPackageDbArgs = stage0 ? do path <- getSetting GhcSourcePath lift $ need [bootstrappingConfInitialised] - isGhc <- (||) <$> stagedBuilder Ghc <*> stagedBuilder GhcM + isGhc <- stagedBuilder Ghc ||^ stagedBuilder GhcM let prefix = if isGhc then "-package-db " else "--package-db=" arg $ prefix ++ path -/- bootstrappingConf From git at git.haskell.org Thu Oct 26 23:47:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use splitOn to parse the Way (9ae96f4) Message-ID: <20171026234756.3CA2C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ae96f4017f3d11da5684a15b0a6b4e10c182dd9/ghc >--------------------------------------------------------------- commit 9ae96f4017f3d11da5684a15b0a6b4e10c182dd9 Author: Neil Mitchell Date: Sat Jan 9 21:47:47 2016 +0000 Use splitOn to parse the Way >--------------------------------------------------------------- 9ae96f4017f3d11da5684a15b0a6b4e10c182dd9 src/Way.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Way.hs b/src/Way.hs index 94a3bcc..5b24662 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -72,7 +72,7 @@ instance Read Way where uniqueReads token = case reads token of [(unit, "")] -> Just unit _ -> Nothing - units = map uniqueReads . words . replaceEq '_' ' ' $ s + units = map uniqueReads . splitOn "_" $ s result = if Nothing `elem` units then [] else [(wayFromUnits . map fromJust $ units, "")] From git at git.haskell.org Thu Oct 26 23:47:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add instance ShowAction PackageData. (7792b9a) Message-ID: <20171026234756.5CCD33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7792b9a32bbc24e3d3a0fb04f534e7c293ac9ea2/ghc >--------------------------------------------------------------- commit 7792b9a32bbc24e3d3a0fb04f534e7c293ac9ea2 Author: Andrey Mokhov Date: Wed Jan 7 16:30:30 2015 +0000 Add instance ShowAction PackageData. >--------------------------------------------------------------- 7792b9a32bbc24e3d3a0fb04f534e7c293ac9ea2 src/Oracles/PackageData.hs | 37 +++++++++++++++++++------------------ 1 file changed, 19 insertions(+), 18 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 831fec9..2af8e21 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -2,7 +2,7 @@ module Oracles.PackageData ( PackageDataPair (..), - packagaDataOption, PackageDataKey (..) + PackageData (..) ) where import Development.Shake.Classes @@ -12,26 +12,27 @@ import Util newtype PackageDataPair = PackageDataPair (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -packagaDataOptionWithDefault :: FilePath -> String -> Action String -> Action String -packagaDataOptionWithDefault file key defaultAction = do +packagaDataWithDefault :: FilePath -> String -> Action String -> Action String +packagaDataWithDefault file key defaultAction = do maybeValue <- askOracle $ PackageDataPair (file, key) case maybeValue of Just value -> return value Nothing -> defaultAction -data PackageDataKey = Modules | SrcDirs | PackageKey | IncludeDirs | Deps | DepKeys - deriving Show +data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath + | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath + deriving Show -packagaDataOption :: FilePath -> PackageDataKey -> Action String -packagaDataOption file key = do - let (keyName, ifEmpty) = case key of - Modules -> ("MODULES" , "" ) - SrcDirs -> ("HS_SRC_DIRS" , ".") - PackageKey -> ("PACKAGE_KEY" , "" ) - IncludeDirs -> ("INCLUDE_DIRS", ".") - Deps -> ("DEPS" , "" ) - DepKeys -> ("DEP_KEYS" , "" ) - keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName - res <- packagaDataOptionWithDefault file keyFullName $ - error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." - return $ if res == "" then ifEmpty else res +instance ShowAction PackageData where + showAction key = do + let (keyName, file, ifEmpty) = case key of + Modules file -> ("MODULES" , file, "" ) + SrcDirs file -> ("HS_SRC_DIRS" , file, ".") + PackageKey file -> ("PACKAGE_KEY" , file, "" ) + IncludeDirs file -> ("INCLUDE_DIRS", file, ".") + Deps file -> ("DEPS" , file, "" ) + DepKeys file -> ("DEP_KEYS" , file, "" ) + keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName + res <- packagaDataWithDefault file keyFullName $ + error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." + return $ words $ if res == "" then ifEmpty else res From git at git.haskell.org Thu Oct 26 23:47:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:47:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add builders: DeriveConstants, Nm, Objdump. (6001acb) Message-ID: <20171026234758.DD7CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6001acb394a70a14e333dd17a8f65b89115dfa52/ghc >--------------------------------------------------------------- commit 6001acb394a70a14e333dd17a8f65b89115dfa52 Author: Andrey Mokhov Date: Sun Dec 27 01:51:33 2015 +0000 Add builders: DeriveConstants, Nm, Objdump. >--------------------------------------------------------------- 6001acb394a70a14e333dd17a8f65b89115dfa52 cfg/system.config.in | 45 ++++++++++++++++++++++++--------------------- src/Builder.hs | 6 ++++++ 2 files changed, 30 insertions(+), 21 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 12ddeed..a2cfef3 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -4,36 +4,39 @@ # Paths to builders: #=================== -system-ghc = @WithGhc@ -ghc-stage1 = inplace/bin/ghc-stage1 -ghc-stage2 = inplace/bin/ghc-stage2 -ghc-stage3 = inplace/bin/ghc-stage3 +system-ghc = @WithGhc@ +ghc-stage1 = inplace/bin/ghc-stage1 +ghc-stage2 = inplace/bin/ghc-stage2 +ghc-stage3 = inplace/bin/ghc-stage3 -system-gcc = @CC_STAGE0@ -gcc = @WhatGccIsCalled@ +system-gcc = @CC_STAGE0@ +gcc = @WhatGccIsCalled@ -system-ghc-pkg = @GhcPkgCmd@ -ghc-pkg = inplace/bin/ghc-pkg +system-ghc-pkg = @GhcPkgCmd@ +ghc-pkg = inplace/bin/ghc-pkg -ghc-cabal = inplace/bin/ghc-cabal +ghc-cabal = inplace/bin/ghc-cabal -haddock = inplace/bin/haddock +haddock = inplace/bin/haddock -hsc2hs = inplace/bin/hsc2hs +hsc2hs = inplace/bin/hsc2hs -genprimopcode = inplace/bin/genprimopcode +genprimopcode = inplace/bin/genprimopcode +derive-constants = inplace/bin/deriveConstants -hs-cpp = @HaskellCPPCmd@ -hs-cpp-args = @HaskellCPPArgs@ +hs-cpp = @HaskellCPPCmd@ +hs-cpp-args = @HaskellCPPArgs@ -unlit = inplace/lib/unlit -ghc-split = inplace/lib/ghc-split +unlit = inplace/lib/unlit +ghc-split = inplace/lib/ghc-split -ld = @LdCmd@ -ar = @ArCmd@ -alex = @AlexCmd@ -happy = @HappyCmd@ -hscolour = @HSCOLOUR@ +alex = @AlexCmd@ +ar = @ArCmd@ +happy = @HappyCmd@ +hscolour = @HSCOLOUR@ +ld = @LdCmd@ +nm = @NmCmd@ +objdump = @ObjdumpCmd@ # Information about builders: #============================ diff --git a/src/Builder.hs b/src/Builder.hs index 4d41d0a..b58d701 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -19,6 +19,7 @@ import Stage -- TODO: do we really need staged builders? data Builder = Alex | Ar + | DeriveConstants | Gcc Stage | GccM Stage | GenPrimopCode @@ -35,6 +36,8 @@ data Builder = Alex | HsCpp | Hsc2Hs | Ld + | Nm + | Objdump | Unlit deriving (Show, Eq, Generic) @@ -43,6 +46,7 @@ builderKey :: Builder -> String builderKey builder = case builder of Alex -> "alex" Ar -> "ar" + DeriveConstants -> "derive-constants" Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' @@ -64,6 +68,8 @@ builderKey builder = case builder of Hsc2Hs -> "hsc2hs" HsCpp -> "hs-cpp" Ld -> "ld" + Nm -> "nm" + Objdump -> "objdump" Unlit -> "unlit" -- TODO: Paths to some builders should be determined using defaultProgramPath From git at git.haskell.org Thu Oct 26 23:48:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghc-cabal only, add cache. (9dbd805) Message-ID: <20171026234800.51AF73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dbd805af4dcc0f90f80b33a74cb1f0c1c49f861/ghc >--------------------------------------------------------------- commit 9dbd805af4dcc0f90f80b33a74cb1f0c1c49f861 Author: Andrey Mokhov Date: Sat Jan 9 23:35:04 2016 +0000 Build ghc-cabal only, add cache. See #110. [skip ci] >--------------------------------------------------------------- 9dbd805af4dcc0f90f80b33a74cb1f0c1c49f861 .appveyor.yml | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 99196db..e7cf731 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,4 +1,10 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" +environment: + global: + STACK_ROOT: "c:\\sr" + +cache: + - c:\\sr install: - cd @@ -24,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-cabal.exe From git at git.haskell.org Thu Oct 26 23:48:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code. (f79678a) Message-ID: <20171026234800.787DE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f79678a93094e3f6512044bd9f65179ae3f9b12c/ghc >--------------------------------------------------------------- commit f79678a93094e3f6512044bd9f65179ae3f9b12c Author: Andrey Mokhov Date: Wed Jan 7 16:31:30 2015 +0000 Clean up code. >--------------------------------------------------------------- f79678a93094e3f6512044bd9f65179ae3f9b12c src/Package/Data.hs | 3 +-- src/Package/Dependencies.hs | 24 +++++++++--------------- 2 files changed, 10 insertions(+), 17 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 0fa1322..de617f4 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -17,8 +17,7 @@ libraryArgs ways = configureArgs :: Stage -> Settings -> Args configureArgs stage settings = - let argConf :: String -> Args -> Args - argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" as + let argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" (as :: Args) cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) (ConfCcArgs stage) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index ede14bb..ad6705d 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -69,22 +69,16 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file let pkgData = buildDir "package-data.mk" usePackageKey <- SupportsPackageKey || stage /= Stage0 -- TODO: check reasoning (distdir-way-opts) - [mods, srcDirs, includeDirs, deps, depKeys] <- - mapM ((fmap words) . (packagaDataOption pkgData)) - [Modules, SrcDirs, IncludeDirs, Deps, DepKeys] - srcs <- getDirectoryFiles "" $ do - dir <- srcDirs - modPath <- map (replaceEq '.' pathSeparator) mods - extension <- ["hs", "lhs"] - return $ path dir modPath <.> extension - packageKey <- packagaDataOption pkgData PackageKey + mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) + srcDirs <- arg $ SrcDirs pkgData + srcs <- getDirectoryFiles "" $ [path dir mPath <.> ext | dir <- srcDirs, mPath <- mods, ext <- ["hs", "lhs"]] run (Ghc stage) $ mconcat [ arg "-M" , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - , arg SrcHcOpts -- TODO: get rid of splitArgs + , arg SrcHcOpts , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" , arg $ if usePackageKey then "-this-package-key" else "-package-name" - , arg packageKey -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg $ PackageKey pkgData -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) , arg "-hide-all-packages" , arg "-i" -- resets the search path to nothing; TODO: check if really needed , arg $ map (\d -> "-i" ++ path d) srcDirs @@ -92,13 +86,13 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = prefix <- ["-i", "-I"] -- 'import' and '#include' search paths suffix <- ["build", "build/autogen"] return $ prefix ++ buildDir suffix - , arg $ map (\d -> "-I" ++ path d) $ filter isRelative includeDirs - , arg $ map (\d -> "-I" ++ d) $ filter isAbsolute includeDirs + , map (\d -> "-I" ++ path d) <$> filter isRelative <$> arg (IncludeDirs pkgData) + , map (\d -> "-I" ++ d) <$> filter isAbsolute <$> arg (IncludeDirs pkgData) , arg "-optP-include" , arg $ "-optP" ++ buildDir "build/autogen/cabal_macros.h" , if usePackageKey - then arg $ concatMap (\d -> ["-package-key", d]) depKeys - else arg $ concatMap (\d -> ["-package" , d]) deps + then map ("-package-key " ++) <$> arg (DepKeys pkgData) + else map ("-package " ++) <$> arg (Deps pkgData) , args "-dep-makefile" out "-dep-suffix" "" "-include-pkg-deps" , arg $ map normalise srcs ] From git at git.haskell.org Thu Oct 26 23:48:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate files with DeriveConstants (#39). (c6cfb36) Message-ID: <20171026234802.BDAA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6cfb36c2d7ca4f76d3da54d06b40fb86890e7ef/ghc >--------------------------------------------------------------- commit c6cfb36c2d7ca4f76d3da54d06b40fb86890e7ef Author: Andrey Mokhov Date: Sun Dec 27 01:53:52 2015 +0000 Generate files with DeriveConstants (#39). >--------------------------------------------------------------- c6cfb36c2d7ca4f76d3da54d06b40fb86890e7ef src/Rules/Actions.hs | 29 +++++++++++---------- src/Rules/Generate.hs | 22 ++++++++++++++-- src/Settings/Args.hs | 2 ++ src/Settings/Builders/DeriveConstants.hs | 44 ++++++++++++++++++++++++++++++++ src/Settings/Builders/GhcCabal.hs | 1 + 5 files changed, 82 insertions(+), 16 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5a3d113..30ae742 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -47,20 +47,21 @@ build = buildWithResources [] interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of - Alex -> prefixAndSuffix 0 3 ss - Ar -> prefixAndSuffix 2 1 ss - Gcc _ -> prefixAndSuffix 0 4 ss - GccM _ -> prefixAndSuffix 0 1 ss - Ghc _ -> prefixAndSuffix 0 4 ss - GhcCabal -> prefixAndSuffix 3 0 ss - GhcM _ -> prefixAndSuffix 1 1 ss - GhcPkg _ -> prefixAndSuffix 3 0 ss - Haddock -> prefixAndSuffix 1 0 ss - Happy -> prefixAndSuffix 0 3 ss - Hsc2Hs -> prefixAndSuffix 0 3 ss - HsCpp -> prefixAndSuffix 0 1 ss - Ld -> prefixAndSuffix 4 0 ss - _ -> ss + Alex -> prefixAndSuffix 0 3 ss + Ar -> prefixAndSuffix 2 1 ss + DeriveConstants -> prefixAndSuffix 3 0 ss + Gcc _ -> prefixAndSuffix 0 4 ss + GccM _ -> prefixAndSuffix 0 1 ss + Ghc _ -> prefixAndSuffix 0 4 ss + GhcCabal -> prefixAndSuffix 3 0 ss + GhcM _ -> prefixAndSuffix 1 1 ss + GhcPkg _ -> prefixAndSuffix 3 0 ss + Haddock -> prefixAndSuffix 1 0 ss + Happy -> prefixAndSuffix 0 3 ss + Hsc2Hs -> prefixAndSuffix 0 3 ss + HsCpp -> prefixAndSuffix 0 1 ss + Ld -> prefixAndSuffix 4 0 ss + _ -> ss where prefixAndSuffix n m list = let len = length list in diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index e427dfd..2121a9c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,4 +1,6 @@ -module Rules.Generate (generatePackageCode, generateRules) where +module Rules.Generate ( + generatePackageCode, generateRules, includesDependencies + ) where import Expression import GHC @@ -15,6 +17,19 @@ import Settings primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" +derivedConstantsPath :: FilePath +derivedConstantsPath = "includes/dist-derivedconstants/header" + +-- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? +includesDependencies :: [FilePath] +includesDependencies = + [ "includes/ghcautoconf.h" + , "includes/ghcplatform.h" + , derivedConstantsPath -/- "DerivedConstants.h" + , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" ] + -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] knownGenerators = [ (Alex , ".x" ) @@ -33,7 +48,6 @@ generate file target expr = do writeFileChanged file contents putSuccess $ "| Successfully generated '" ++ file ++ "'." - generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let path = targetPath stage pkg @@ -71,6 +85,10 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = build $ fullTarget target GenPrimopCode [primopsTxt] [file] priority 2.0 $ do + when (pkg == compiler && stage == Stage1) $ + derivedConstantsPath ++ "//*" %> \file -> do + build $ fullTarget target DeriveConstants [] [file] + when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 231f5ed..5419f51 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -3,6 +3,7 @@ module Settings.Args (getArgs) where import Expression import Settings.Builders.Alex import Settings.Builders.Ar +import Settings.Builders.DeriveConstants import Settings.Builders.Gcc import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc @@ -32,6 +33,7 @@ defaultArgs = mconcat , arArgs , cabalArgs , customPackageArgs + , deriveConstantsArgs , gccArgs , gccMArgs , genPrimopCodeArgs diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs new file mode 100644 index 0000000..4353875 --- /dev/null +++ b/src/Settings/Builders/DeriveConstants.hs @@ -0,0 +1,44 @@ +module Settings.Builders.DeriveConstants ( + derivedConstantsPath, deriveConstantsArgs + ) where + +import Expression +import Oracles.Config.Flag +import Oracles.Config.Setting +import Predicates (builder, file) +import Settings.Builders.GhcCabal + +derivedConstantsPath :: FilePath +derivedConstantsPath = "includes/dist-derivedconstants/header" + +-- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? +deriveConstantsArgs :: Args +deriveConstantsArgs = builder DeriveConstants ? do + cFlags <- fromDiffExpr includeCcArgs + mconcat + [ file "//DerivedConstants.h" ? arg "--gen-header" + , file "//GHCConstantsHaskellType.hs" ? arg "--gen-haskell-type" + , file "//platformConstants" ? arg "--gen-haskell-value" + , file "//GHCConstantsHaskellWrappers.hs" ? arg "--gen-haskell-wrappers" + , file "//GHCConstantsHaskellExports.hs" ? arg "--gen-haskell-exports" + , arg "-o", arg =<< getOutput + , arg "--tmpdir", arg derivedConstantsPath + , arg "--gcc-program", arg =<< getBuilderPath (Gcc Stage1) + , append . concat $ map (\a -> ["--gcc-flag", a]) cFlags + , arg "--nm-program", arg =<< getBuilderPath Nm + , specified Objdump ? mconcat [ arg "--objdump-program" + , arg =<< getBuilderPath Objdump ] + , arg "--target-os", arg =<< getSetting TargetOs ] + +includeCcArgs :: Args +includeCcArgs = do + confCcArgs <- lift . settingList $ ConfCcArgs Stage1 + mconcat + [ ccArgs + , ccWarnings + , append confCcArgs + , flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER" + , append $ map ("-I" ++) ghcIncludeDirs -- TODO: fix code duplication + , arg "-Irts" + , notM ghcWithSMP ? arg "-DNOSMP" + , arg "-fcommon" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 80c4f4c..cec876a 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -208,6 +208,7 @@ argStagedBuilderPath :: (Stage -> Builder) -> Args argStagedBuilderPath sb = (argM . builderPath . sb) =<< getStage -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal +-- TODO: simplify appendCcArgs :: [String] -> Args appendCcArgs xs = do mconcat [ stagedBuilder Gcc ? append xs From git at git.haskell.org Thu Oct 26 23:48:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify PackageData. (2f9338d) Message-ID: <20171026234804.6F5B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f9338d4d263435155047a69b5c802c5f76beba1/ghc >--------------------------------------------------------------- commit 2f9338d4d263435155047a69b5c802c5f76beba1 Author: Andrey Mokhov Date: Wed Jan 7 16:46:10 2015 +0000 Simplify PackageData. >--------------------------------------------------------------- 2f9338d4d263435155047a69b5c802c5f76beba1 src/Oracles.hs | 2 +- src/Oracles/PackageData.hs | 20 +++++++------------- 2 files changed, 8 insertions(+), 14 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 093f1b8..3321610 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -43,5 +43,5 @@ oracleRules = do need [file] liftIO $ readConfigFile file - addOracle $ \(PackageDataPair (file, key)) -> M.lookup key <$> pkgData file + addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 2af8e21..4ec89d7 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( - PackageDataPair (..), + PackageDataKey (..), PackageData (..) ) where @@ -9,19 +9,11 @@ import Development.Shake.Classes import Base import Util -newtype PackageDataPair = PackageDataPair (FilePath, String) +newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -packagaDataWithDefault :: FilePath -> String -> Action String -> Action String -packagaDataWithDefault file key defaultAction = do - maybeValue <- askOracle $ PackageDataPair (file, key) - case maybeValue of - Just value -> return value - Nothing -> defaultAction - data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath - deriving Show instance ShowAction PackageData where showAction key = do @@ -33,6 +25,8 @@ instance ShowAction PackageData where Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName - res <- packagaDataWithDefault file keyFullName $ - error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." - return $ words $ if res == "" then ifEmpty else res + res <- askOracle $ PackageDataKey (file, keyFullName) + return $ words $ case res of + Nothing -> error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." + Just "" -> ifEmpty + Just value -> value From git at git.haskell.org Thu Oct 26 23:48:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to a more ambitious build target. (f168dc4) Message-ID: <20171026234804.715453A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f168dc4eaef267ce321821088dba79d961617a88/ghc >--------------------------------------------------------------- commit f168dc4eaef267ce321821088dba79d961617a88 Author: Andrey Mokhov Date: Sun Jan 10 00:30:03 2016 +0000 Switch to a more ambitious build target. See #110. [skip ci] >--------------------------------------------------------------- f168dc4eaef267ce321821088dba79d961617a88 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index e7cf731..b2f27af 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-cabal.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/libHSghc-boot-8.1.a From git at git.haskell.org Thu Oct 26 23:48:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add explicit dependencies on includes/ generated files (fix #48). (1fcb025) Message-ID: <20171026234806.2651A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fcb025a9405f6b2970d1efdaf47558b300de1a9/ghc >--------------------------------------------------------------- commit 1fcb025a9405f6b2970d1efdaf47558b300de1a9 Author: Andrey Mokhov Date: Sun Dec 27 01:55:29 2015 +0000 Add explicit dependencies on includes/ generated files (fix #48). >--------------------------------------------------------------- 1fcb025a9405f6b2970d1efdaf47558b300de1a9 src/Rules/Dependencies.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 907c4d3..5d08df1 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -4,6 +4,7 @@ import Expression import GHC import Oracles import Rules.Actions +import Rules.Generate import Rules.Resources import Settings @@ -17,13 +18,13 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do (buildPath "*.c.deps") %> \out -> do let srcFile = dropBuild . dropExtension $ out - when (pkg == compiler) $ need [platformH] + when (pkg == compiler) . need $ platformH : includesDependencies need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - when (pkg == compiler) $ need [platformH] + when (pkg == compiler) . need $ platformH : includesDependencies -- TODO: very ugly and fragile; use gcc -MM instead? let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) [ "primop-vector-uniques.hs-incl" From git at git.haskell.org Thu Oct 26 23:48:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generalise and export suffix :: Way -> String. (1ef6a04) Message-ID: <20171026234808.7465D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ef6a045ba067a1f07b4517f11e7bfd2aa066e6e/ghc >--------------------------------------------------------------- commit 1ef6a045ba067a1f07b4517f11e7bfd2aa066e6e Author: Andrey Mokhov Date: Wed Jan 7 17:44:04 2015 +0000 Generalise and export suffix :: Way -> String. >--------------------------------------------------------------- 1ef6a045ba067a1f07b4517f11e7bfd2aa066e6e src/Ways.hs | 19 ++++++++----------- 1 file changed, 8 insertions(+), 11 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 0a4284a..3e7c483 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -13,6 +13,7 @@ module Ways ( loggingDynamic, threadedLoggingDynamic, wayHcOpts, + suffix, hisuf, osuf, hcsuf ) where @@ -84,15 +85,11 @@ wayHcOpts (Way _ _ units) = , when (units == [Debug] || units == [Debug, Dynamic]) $ arg ["-ticky", "-DTICKY_TICKY"] ] --- TODO: cover other cases -suffix :: FilePath -> Way -> FilePath -suffix base (Way _ _ units) = - concat $ - ["p_" | Profiling `elem` units] ++ - ["dyn_" | Dynamic `elem` units] ++ - [base ] +suffix :: Way -> String +suffix way | way == vanilla = "" + | otherwise = tag way ++ "_" -hisuf, osuf, hcsuf :: Way -> FilePath -hisuf = suffix "hi" -osuf = suffix "o" -hcsuf = suffix "hc" +hisuf, osuf, hcsuf :: Way -> String +hisuf = (++ "hi") . suffix +osuf = (++ "o" ) . suffix +hcsuf = (++ "hc") . suffix From git at git.haskell.org Thu Oct 26 23:48:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Quote cache path. (1b36ea9) Message-ID: <20171026234808.E00DB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b36ea956be80db55406fffc868cb676de5ce100/ghc >--------------------------------------------------------------- commit 1b36ea956be80db55406fffc868cb676de5ce100 Author: Andrey Mokhov Date: Sun Jan 10 00:42:55 2016 +0000 Quote cache path. See #110. [skip ci] >--------------------------------------------------------------- 1b36ea956be80db55406fffc868cb676de5ce100 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index b2f27af..176fb2a 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -4,7 +4,7 @@ environment: STACK_ROOT: "c:\\sr" cache: - - c:\\sr + - "c:\\sr" install: - cd @@ -30,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/libHSghc-boot-8.1.a + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/build/libHSghc-boot-8.1.a From git at git.haskell.org Thu Oct 26 23:48:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add install targets, install inplace/lib/platformConstants. (43b6cc3) Message-ID: <20171026234809.D320F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/43b6cc390adbf439e8b98c19eb8b9196f0a58bfb/ghc >--------------------------------------------------------------- commit 43b6cc390adbf439e8b98c19eb8b9196f0a58bfb Author: Andrey Mokhov Date: Sun Dec 27 02:13:55 2015 +0000 Add install targets, install inplace/lib/platformConstants. >--------------------------------------------------------------- 43b6cc390adbf439e8b98c19eb8b9196f0a58bfb src/Rules.hs | 4 +++- src/Rules/Generate.hs | 3 ++- src/Rules/Install.hs | 16 ++++++++++++---- 3 files changed, 17 insertions(+), 6 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 5516c33..a9ac3e4 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,6 +1,7 @@ module Rules (generateTargets, packageRules) where import Expression +import Rules.Install import Rules.Package import Rules.Resources import Settings @@ -18,7 +19,8 @@ generateTargets = action $ do return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] return $ libTargets ++ programTargets - need targets + + need $ targets ++ installTargets packageRules :: Rules () packageRules = do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 2121a9c..ccd059f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,5 +1,6 @@ module Rules.Generate ( - generatePackageCode, generateRules, includesDependencies + generatePackageCode, generateRules, + derivedConstantsPath, includesDependencies ) where import Expression diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index b592728..fca88fe 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -1,11 +1,19 @@ -module Rules.Install (installRules) where +module Rules.Install (installTargets, installRules) where import Expression import GHC +import Rules.Generate + +installTargets :: [FilePath] +installTargets = [ "inplace/lib/template-hsc.h" + , "inplace/lib/platformConstants" ] installRules :: Rules () installRules = do - "inplace/lib/template-hsc.h" %> \out -> do - let source = pkgPath hsc2hs -/- "template-hsc.h" - putBuild $ "| Copying " ++ source ++ " -> " ++ out + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs + "inplace/lib/platformConstants" <~ derivedConstantsPath + where + file <~ dir = file %> \out -> do + let source = dir -/- takeFileName out copyFileChanged source out + putSuccess $ "| Installed " ++ source ++ " -> " ++ out From git at git.haskell.org Thu Oct 26 23:48:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle multiple way suffices. (2549740) Message-ID: <20171026234812.553433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/254974086689e362b394084f066d14afba9c50be/ghc >--------------------------------------------------------------- commit 254974086689e362b394084f066d14afba9c50be Author: Andrey Mokhov Date: Wed Jan 7 17:44:48 2015 +0000 Handle multiple way suffices. >--------------------------------------------------------------- 254974086689e362b394084f066d14afba9c50be src/Package/Dependencies.hs | 14 +++++++++----- 1 file changed, 9 insertions(+), 5 deletions(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index ad6705d..b3e013f 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -55,7 +55,6 @@ import Package.Base -- $$(SRC_HC_WARNING_OPTS) \ -- $$(EXTRA_HC_OPTS) --- TODO: make sure SrcDirs ($1_$2_HS_SRC_DIRS) is not empty ('.' by default) -- TODO: add $1_HC_OPTS -- TODO: check that the package is not a program ($1_$2_PROG == "") -- TODO: handle empty $1_PACKAGE (can it be empty?) @@ -77,8 +76,9 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = , wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? , arg SrcHcOpts , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" + -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) , arg $ if usePackageKey then "-this-package-key" else "-package-name" - , arg $ PackageKey pkgData -- TODO: check reasoning ($$($4_THIS_PACKAGE_KEY) $$($1_$2_PACKAGE_KEY)) + , arg $ PackageKey pkgData , arg "-hide-all-packages" , arg "-i" -- resets the search path to nothing; TODO: check if really needed , arg $ map (\d -> "-i" ++ path d) srcDirs @@ -88,12 +88,16 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = return $ prefix ++ buildDir suffix , map (\d -> "-I" ++ path d) <$> filter isRelative <$> arg (IncludeDirs pkgData) , map (\d -> "-I" ++ d) <$> filter isAbsolute <$> arg (IncludeDirs pkgData) - , arg "-optP-include" - , arg $ "-optP" ++ buildDir "build/autogen/cabal_macros.h" + , args "-optP-include" ("-optP" ++ buildDir "build/autogen/cabal_macros.h") , if usePackageKey then map ("-package-key " ++) <$> arg (DepKeys pkgData) else map ("-package " ++) <$> arg (Deps pkgData) - , args "-dep-makefile" out "-dep-suffix" "" "-include-pkg-deps" + , arg "-no-user-package-db" + , args "-odir" (buildDir "build") + , args "-stubdir" (buildDir "build") + , joinArgsSpaced "-dep-makefile" out + , concatMap (\w -> ["-dep-suffix", suffix w]) <$> ways settings + , arg "-include-pkg-deps" , arg $ map normalise srcs ] From git at git.haskell.org Thu Oct 26 23:48:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to build stage1 GHC. (c217881) Message-ID: <20171026234812.B2E013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c217881e59c759dc519e56f246ccb9ab56a6e7d4/ghc >--------------------------------------------------------------- commit c217881e59c759dc519e56f246ccb9ab56a6e7d4 Author: Andrey Mokhov Date: Sun Jan 10 02:20:00 2016 +0000 Attempt to build stage1 GHC. See #110. [skip ci] >--------------------------------------------------------------- c217881e59c759dc519e56f246ccb9ab56a6e7d4 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 176fb2a..f4f1d83 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/build/libHSghc-boot-8.1.a + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Thu Oct 26 23:48:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate includes/ghcversion.h (66f18be) Message-ID: <20171026234813.6A09F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/66f18bec2737a73fc1b2387726e22a35ef6edd8a/ghc >--------------------------------------------------------------- commit 66f18bec2737a73fc1b2387726e22a35ef6edd8a Author: Moritz Angermann Date: Sun Dec 27 14:27:55 2015 +0800 Generate includes/ghcversion.h This should be the final commit to fix #39. >--------------------------------------------------------------- 66f18bec2737a73fc1b2387726e22a35ef6edd8a shaking-up-ghc.cabal | 1 + src/Rules/Generate.hs | 2 ++ src/Rules/Generators/GhcVersionH.hs | 33 +++++++++++++++++++++++++++++++++ 3 files changed, 36 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 941651b..0e60637 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -46,6 +46,7 @@ executable ghc-shake , Rules.Generators.GhcAutoconfH , Rules.Generators.GhcBootPlatformH , Rules.Generators.GhcPlatformH + , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs , Rules.Install , Rules.Library diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index ccd059f..bc0089c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -9,6 +9,7 @@ import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH import Rules.Generators.GhcBootPlatformH import Rules.Generators.GhcPlatformH +import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles import Rules.Actions @@ -107,6 +108,7 @@ generateRules :: Rules () generateRules = do "includes/ghcautoconf.h" <~ generateGhcAutoconfH "includes/ghcplatform.h" <~ generateGhcPlatformH + "includes/ghcversion.h" <~ generateGhcVersionH where file <~ gen = file %> \out -> generate out emptyTarget gen diff --git a/src/Rules/Generators/GhcVersionH.hs b/src/Rules/Generators/GhcVersionH.hs new file mode 100644 index 0000000..a45df55 --- /dev/null +++ b/src/Rules/Generators/GhcVersionH.hs @@ -0,0 +1,33 @@ +module Rules.Generators.GhcVersionH (generateGhcVersionH) where + +import Expression +import Oracles + +generateGhcVersionH :: Expr String +generateGhcVersionH = do + version <- getSetting ProjectVersionInt + patchLevel1 <- getSetting ProjectPatchLevel1 + patchLevel2 <- getSetting ProjectPatchLevel2 + return . unlines $ + [ "#ifndef __GHCVERSION_H__" + , "#define __GHCVERSION_H__" + , "" + , "#ifndef __GLASGOW_HASKELL__" + , "# define __GLASGOW_HASKELL__ " ++ version + , "#endif" + , ""] + ++ + [ "#define __GLASGOW_HASKELL_PATCHLEVEL1__ " ++ patchLevel1 | patchLevel1 /= "" ] + ++ + [ "#define __GLASGOW_HASKELL_PATCHLEVEL2__ " ++ patchLevel2 | patchLevel2 /= "" ] + ++ + [ "" + , "#define MIN_VERSION_GLASGOW_HASKELL(ma,mi,pl1,pl2) (\\" + , " ((ma)*100+(mi)) < __GLASGOW_HASKELL__ || \\" + , " ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \\" + , " && (pl1) < __GLASGOW_HASKELL_PATCHLEVEL1__ || \\" + , " ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \\" + , " && (pl1) == __GLASGOW_HASKELL_PATCHLEVEL1__ \\" + , " && (pl2) <= __GLASGOW_HASKELL_PATCHLEVEL2__ )" + , "" + , "#endif /* __GHCVERSION_H__ */" ] From git at git.haskell.org Thu Oct 26 23:48:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor src/Base.hs. (06fd336) Message-ID: <20171026234815.D28BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/06fd336d441e3a42b3056185ef40742404ec856d/ghc >--------------------------------------------------------------- commit 06fd336d441e3a42b3056185ef40742404ec856d Author: Andrey Mokhov Date: Fri Jan 9 17:07:04 2015 +0000 Refactor src/Base.hs. * Get rid of polyvariadic function for better readability and robustnes. * Eliminate joinArgs and joinArgsSpaced functions. Users are encouraged to use 'unwords <$>' and 'concat <$>' instead. * Generalise filterOut function. * Rename ShowAction to ShowArgs. >--------------------------------------------------------------- 06fd336d441e3a42b3056185ef40742404ec856d src/Base.hs | 65 +++++++++++++++++++++---------------------------------------- 1 file changed, 22 insertions(+), 43 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 8a98a7b..ce2714e 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,9 +7,9 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - Args, arg, args, ShowAction (..), + Args, arg, ShowArgs (..), Condition (..), - joinArgs, joinArgsSpaced, + (<+>), filterOut ) where @@ -29,50 +29,29 @@ instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q -class ShowAction a where - showAction :: a -> Args - showListAction :: [a] -> Args -- the Creators' trick for overlapping String instances - showListAction = mconcat . map showAction +class ShowArgs a where + showArgs :: a -> Args + showListArgs :: [a] -> Args -- the Creators' trick for overlapping String instances + showListArgs = mconcat . map showArgs -instance ShowAction Char where - showAction c = return [[c]] - showListAction s = return [s] +instance ShowArgs Char where + showArgs c = return [[c]] + showListArgs s = return [s] -instance ShowAction a => ShowAction [a] where - showAction = showListAction +instance ShowArgs a => ShowArgs [a] where + showArgs = showListArgs -instance ShowAction a => ShowAction (Action a) where - showAction = (showAction =<<) +instance ShowArgs a => ShowArgs (Action a) where + showArgs = (showArgs =<<) -arg :: ShowAction a => a -> Args -arg = showAction +arg :: ShowArgs a => a -> Args +arg = showArgs -type ArgsCombine = Args -> Args -> Args +-- Combine two heterogeneous ShowArgs values. +(<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args +a <+> b = (<>) <$> showArgs a <*> showArgs b -class Collect a where - collect :: ArgsCombine -> Args -> a - -instance Collect Args where - collect = const id - -instance (ShowAction a, Collect r) => Collect (a -> r) where - collect combine x = \y -> collect combine $ x `combine` arg y - -args :: Collect a => a -args = collect (<>) mempty - -joinArgs :: Collect a => a -joinArgs = collect (\x y -> intercalateArgs "" $ x <> y) mempty - -joinArgsSpaced :: Collect a => a -joinArgsSpaced = collect (\x y -> intercalateArgs " " $ x <> y) mempty - -intercalateArgs :: String -> Args -> Args -intercalateArgs s as = do - as' <- as - case as' of - [] -> mempty - otherwise -> return [intercalate s as'] - -filterOut :: Args -> [String] -> Args -filterOut as list = filter (`notElem` list) <$> as +filterOut :: ShowArgs a => Args -> a -> Args +filterOut as exclude = do + exclude' <- showArgs exclude + filter (`notElem` exclude') <$> as From git at git.haskell.org Thu Oct 26 23:48:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move build artefacts to .build/ directory. (eda85ff) Message-ID: <20171026234816.4DE703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eda85ffd9bca4b43667b9a172fc5a4b888f018cd/ghc >--------------------------------------------------------------- commit eda85ffd9bca4b43667b9a172fc5a4b888f018cd Author: Andrey Mokhov Date: Sun Jan 10 05:02:18 2016 +0000 Move build artefacts to .build/ directory. See #113. >--------------------------------------------------------------- eda85ffd9bca4b43667b9a172fc5a4b888f018cd src/Base.hs | 2 ++ src/GHC.hs | 33 +--------------------- src/Oracles/LookupInPath.hs | 15 ++++------ src/Oracles/PackageDeps.hs | 4 +-- src/Rules/Compile.hs | 3 +- src/Rules/Config.hs | 1 + src/Rules/Data.hs | 62 ++++++++++++++++++++++++++--------------- src/Rules/Dependencies.hs | 10 +++++-- src/Rules/Generate.hs | 6 ++-- src/Rules/IntegerGmp.hs | 1 + src/Rules/Libffi.hs | 10 ++++--- src/Rules/Library.hs | 13 ++++++--- src/Rules/Program.hs | 4 +-- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Builders/GhcPkg.hs | 6 ++-- src/Settings/Default.hs | 36 ++++++++++++++++++++++-- src/Settings/Packages/Rts.hs | 5 ++-- src/Settings/TargetDirectory.hs | 4 +-- src/Settings/User.hs | 26 +++++++++-------- 19 files changed, 143 insertions(+), 101 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 eda85ffd9bca4b43667b9a172fc5a4b888f018cd From git at git.haskell.org Thu Oct 26 23:48:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds ghcautoconf and ghcplatform as dependencies to hp2ps. (456d2bd) Message-ID: <20171026234816.D50A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/456d2bdadab272bc40d63f166e0eeaaf0a13ca02/ghc >--------------------------------------------------------------- commit 456d2bdadab272bc40d63f166e0eeaaf0a13ca02 Author: Moritz Angermann Date: Sun Dec 27 14:41:23 2015 +0800 Adds ghcautoconf and ghcplatform as dependencies to hp2ps. 1fcb025 added includes to the dependencies for the `compiler` package, but `hp2ps` already requires them and is built prior to the `compiler` package. This should fix #48 for good. Also updates the README.md to reflect the closure of #44. >--------------------------------------------------------------- 456d2bdadab272bc40d63f166e0eeaaf0a13ca02 README.md | 3 --- src/Rules/Dependencies.hs | 2 ++ 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index ca1e5fb..93674a1 100644 --- a/README.md +++ b/README.md @@ -55,9 +55,6 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure --with-gcc=$(which clang) # See #26 -./shake-build/build.sh includes/ghcautoconf.h # See #48 -./shake-build/build.sh includes/ghcplatform.h # See #48 -cp utils/hsc2hs/template-hsc.h inplace/lib/template-hsc.h # See #44 ./shake-build/build.sh ``` diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 5d08df1..197fa64 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -19,12 +19,14 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = (buildPath "*.c.deps") %> \out -> do let srcFile = dropBuild . dropExtension $ out when (pkg == compiler) . need $ platformH : includesDependencies + when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) . need $ platformH : includesDependencies + when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] -- TODO: very ugly and fragile; use gcc -MM instead? let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) [ "primop-vector-uniques.hs-incl" From git at git.haskell.org Thu Oct 26 23:48:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename ShowAction to ShowArgs. (0da6908) Message-ID: <20171026234819.7A0613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0da69088be65109832fa78a93bc0dc21fcd37f09/ghc >--------------------------------------------------------------- commit 0da69088be65109832fa78a93bc0dc21fcd37f09 Author: Andrey Mokhov Date: Fri Jan 9 17:23:32 2015 +0000 Rename ShowAction to ShowArgs. >--------------------------------------------------------------- 0da69088be65109832fa78a93bc0dc21fcd37f09 src/Oracles/Builder.hs | 14 +++++++------- src/Oracles/Option.hs | 12 ++++++------ src/Oracles/PackageData.hs | 4 ++-- 3 files changed, 15 insertions(+), 15 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 84b73b3..d91e5e7 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -14,8 +14,8 @@ import Oracles.Option data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage -instance ShowAction Builder where - showAction builder = showAction $ do +instance ShowArgs Builder where + showArgs builder = showArgs $ do let key = case builder of Ar -> "ar" Ld -> "ld" @@ -50,12 +50,12 @@ instance ShowAction Builder where -- the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - [target] <- showAction ghc + [target] <- showArgs ghc laxDeps <- test LaxDeps if laxDeps then orderOnly [target] else need [target] needBuilder builder = do - [target] <- showAction builder + [target] <- showArgs builder need [target] -- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder @@ -70,18 +70,18 @@ with builder = do Happy -> "--with-happy=" GhcPkg _ -> "--with-ghc-pkg=" HsColour -> "--with-hscolour=" - [suffix] <- showAction builder + [suffix] <- showArgs builder needBuilder builder return [prefix ++ suffix] run :: Builder -> Args -> Action () run builder args = do needBuilder builder - [exe] <- showAction builder + [exe] <- showArgs builder args' <- args cmd [exe] args' hsColourSrcs :: Condition hsColourSrcs = do - [hscolour] <- showAction HsColour + [hscolour] <- showArgs HsColour return $ hscolour /= "" diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 6f05a0e..d08b394 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -12,8 +12,8 @@ data Option = TargetOS | TargetArch | TargetPlatformFull | SrcHcOpts | HostOsCpp -instance ShowAction Option where - showAction opt = showAction $ fmap words $ askConfig $ case opt of +instance ShowArgs Option where + showArgs opt = showArgs $ fmap words $ askConfig $ case opt of TargetOS -> "target-os" TargetArch -> "target-arch" TargetPlatformFull -> "target-platform-full" @@ -30,8 +30,8 @@ instance ShowAction Option where ghcWithInterpreter :: Condition ghcWithInterpreter = do - [os] <- showAction TargetOS - [arch] <- showAction TargetArch + [os] <- showArgs TargetOS + [arch] <- showArgs TargetArch return $ os `elem` ["mingw32", "cygwin32", "linux", "solaris2", "freebsd", "dragonfly", "netbsd", "openbsd", "darwin", "kfreebsdgnu"] && @@ -39,10 +39,10 @@ ghcWithInterpreter = do platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do - [platform] <- showAction TargetPlatformFull + [platform] <- showArgs TargetPlatformFull return $ platform `notElem` [ "powerpc-unknown-linux", "x86_64-unknown-mingw32", "i386-unknown-mingw32" ] -- TODO: i386-unknown-solaris2? windowsHost :: Condition windowsHost = do - [hostOsCpp] <- showAction HostOsCpp + [hostOsCpp] <- showArgs HostOsCpp return $ hostOsCpp `elem` ["mingw32", "cygwin32"] diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 4ec89d7..ba63612 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -15,8 +15,8 @@ newtype PackageDataKey = PackageDataKey (FilePath, String) data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath -instance ShowAction PackageData where - showAction key = do +instance ShowArgs PackageData where + showArgs key = do let (keyName, file, ifEmpty) = case key of Modules file -> ("MODULES" , file, "" ) SrcDirs file -> ("HS_SRC_DIRS" , file, ".") From git at git.haskell.org Thu Oct 26 23:48:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix include paths. (1d18a74) Message-ID: <20171026234820.4E1F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1d18a749606d4c093b00e8f4823b89597dae4c9a/ghc >--------------------------------------------------------------- commit 1d18a749606d4c093b00e8f4823b89597dae4c9a Author: Andrey Mokhov Date: Sun Jan 10 12:11:11 2016 +0000 Fix include paths. See #145. >--------------------------------------------------------------- 1d18a749606d4c093b00e8f4823b89597dae4c9a src/Settings/Builders/HsCpp.hs | 4 +++- src/Settings/Packages/Ghc.hs | 4 ++-- src/Settings/Packages/IntegerGmp.hs | 1 + src/Settings/Packages/IservBin.hs | 3 +-- 4 files changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs index 89980ee..43b9455 100644 --- a/src/Settings/Builders/HsCpp.hs +++ b/src/Settings/Builders/HsCpp.hs @@ -1,9 +1,11 @@ module Settings.Builders.HsCpp (hsCppBuilderArgs) where import Expression +import GHC import Oracles import Predicates (builder) import Settings.Builders.GhcCabal +import Settings.TargetDirectory hsCppBuilderArgs :: Args hsCppBuilderArgs = builder HsCpp ? do @@ -11,7 +13,7 @@ hsCppBuilderArgs = builder HsCpp ? do mconcat [ append =<< getSettingList HsCppArgs , arg "-P" , cppArgs - , arg $ "-Icompiler/" ++ stageString stage + , arg $ "-I" ++ targetPath stage compiler , arg "-x" , arg "c" , arg =<< getInput ] diff --git a/src/Settings/Packages/Ghc.hs b/src/Settings/Packages/Ghc.hs index efc059d..0830cb6 100644 --- a/src/Settings/Packages/Ghc.hs +++ b/src/Settings/Packages/Ghc.hs @@ -1,16 +1,16 @@ module Settings.Packages.Ghc (ghcPackageArgs) where -import Base import Expression import GHC (ghc, compiler) import Oracles.Config.Setting import Predicates (builder, builderGhc, package, notStage0) +import Settings.TargetDirectory ghcPackageArgs :: Args ghcPackageArgs = package ghc ? do stage <- getStage mconcat [ builderGhc ? mconcat - [ arg ("-I" ++ pkgPath compiler -/- stageString stage) + [ arg $ "-I" ++ targetPath stage compiler , arg "-no-hs-main" ] , builder GhcCabal ? diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 6d1b2b6..c679bf3 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -5,6 +5,7 @@ import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) +-- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" -- libraries/integer-gmp_CONFIGURE_OPTS += --with-gmp-framework-preferred diff --git a/src/Settings/Packages/IservBin.hs b/src/Settings/Packages/IservBin.hs index 5ad3bd5..a662d1c 100644 --- a/src/Settings/Packages/IservBin.hs +++ b/src/Settings/Packages/IservBin.hs @@ -6,5 +6,4 @@ import Predicates (builderGhc, package) iservBinPackageArgs :: Args iservBinPackageArgs = package iservBin ? do - mconcat [ builderGhc ? - mconcat [ arg "-no-hs-main" ]] + mconcat [ builderGhc ? arg "-no-hs-main" ] From git at git.haskell.org Thu Oct 26 23:48:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #58 from angerman/feature/ghcversion (b45902d) Message-ID: <20171026234820.A78933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b45902dd36889637607dd1611272c93d4fcab4fd/ghc >--------------------------------------------------------------- commit b45902dd36889637607dd1611272c93d4fcab4fd Merge: 43b6cc3 66f18be Author: Andrey Mokhov Date: Sun Dec 27 09:35:33 2015 +0000 Merge pull request #58 from angerman/feature/ghcversion Generate includes/ghcversion.h >--------------------------------------------------------------- b45902dd36889637607dd1611272c93d4fcab4fd shaking-up-ghc.cabal | 1 + src/Rules/Generate.hs | 2 ++ src/Rules/Generators/GhcVersionH.hs | 33 +++++++++++++++++++++++++++++++++ 3 files changed, 36 insertions(+) From git at git.haskell.org Thu Oct 26 23:48:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Postprocess inplace-pkg-config files. (f84ee22) Message-ID: <20171026234824.2353F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f84ee22ff9c333ccd1625f06931e339b23e6e7cf/ghc >--------------------------------------------------------------- commit f84ee22ff9c333ccd1625f06931e339b23e6e7cf Author: Andrey Mokhov Date: Sun Jan 10 14:24:58 2016 +0000 Postprocess inplace-pkg-config files. See #113 and #148. >--------------------------------------------------------------- f84ee22ff9c333ccd1625f06931e339b23e6e7cf src/Rules/Data.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 9aeb7b3..4428b35 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -54,7 +54,17 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- ghc-pkg produces inplace-pkg-config when run on packages with -- library components only when (isLibrary pkg) . - whenM (interpretPartial target registerPackage) . + whenM (interpretPartial target registerPackage) $ do + + -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 + let fixPkgConf = unlines + . map (replace oldPath (targetPath stage pkg) + . replace (replaceSeparators '\\' $ oldPath) + (targetPath stage pkg) ) + . lines + + fixFile (oldPath -/- "inplace-pkg-config") fixPkgConf + buildWithResources [(resGhcPkg rs, 1)] $ fullTarget target (GhcPkg stage) [cabalFile] [] From git at git.haskell.org Thu Oct 26 23:48:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up build rules. (7661c31) Message-ID: <20171026234823.0AF8B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7661c319397cbcf02f8b9c4f229ebc8b0c019ad2/ghc >--------------------------------------------------------------- commit 7661c319397cbcf02f8b9c4f229ebc8b0c019ad2 Author: Andrey Mokhov Date: Fri Jan 9 17:24:42 2015 +0000 Clean up build rules. >--------------------------------------------------------------- 7661c319397cbcf02f8b9c4f229ebc8b0c019ad2 src/Package/Base.hs | 2 +- src/Package/Data.hs | 88 +++++++++++++++++++++------------------------ src/Package/Dependencies.hs | 8 ++--- 3 files changed, 45 insertions(+), 53 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index a895f5f..43b4a37 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -53,7 +53,7 @@ libraryPackage name stage settings = )] commonCcArgs :: Args -commonCcArgs = when Validating $ args "-Werror" "-Wall" +commonCcArgs = when Validating $ arg ["-Werror", "-Wall"] commonLdArgs :: Args commonLdArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? diff --git a/src/Package/Data.hs b/src/Package/Data.hs index de617f4..81a7d7f 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -1,43 +1,37 @@ {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} module Package.Data (buildPackageData) where - import Package.Base libraryArgs :: [Way] -> Args libraryArgs ways = - let argEnable x suffix = arg $ (if x then "--enable-" else "--disable-") ++ suffix - in mconcat - [ argEnable False "library-for-ghci" -- TODO: why always disable? - , argEnable (vanilla `elem` ways) "library-vanilla" - , when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) $ - argEnable True "library-for-ghci" - , argEnable (profiling `elem` ways) "library-profiling" - , argEnable (dynamic `elem` ways) "shared" - ] + argEnable False "library-for-ghci" -- TODO: why always disable? + <> argEnable (vanilla `elem` ways) "library-vanilla" + <> when (ghcWithInterpreter && not DynamicGhcPrograms && vanilla `elem` ways) (argEnable True "library-for-ghci") + <> argEnable (profiling `elem` ways) "library-profiling" + <> argEnable (dynamic `elem` ways) "shared" + where + argEnable x suffix = arg $ (if x then "--enable-" else "--disable-") ++ suffix configureArgs :: Stage -> Settings -> Args configureArgs stage settings = - let argConf key as = unless (null <$> as) $ joinArgs "--configure-option=" key "=" (as :: Args) + let argConf key as = do + s <- unwords <$> arg as + unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = joinArgsSpaced (commonCcArgs `filterOut` ["-Werror"]) - (ConfCcArgs stage) - (customCcArgs settings) - (commonCcWarninigArgs) - ldflags = joinArgsSpaced commonLdArgs (ConfGccLinkerArgs stage) (customLdArgs settings) - cppflags = joinArgsSpaced commonCppArgs (ConfCppArgs stage) (customCppArgs settings) + cflags = commonCcArgs `filterOut` "-Werror" <+> ConfCcArgs stage <+> customCcArgs settings <+> commonCcWarninigArgs + ldflags = commonLdArgs <+> ConfGccLinkerArgs stage <+> customLdArgs settings + cppflags = commonCppArgs <+> ConfCppArgs stage <+> customCppArgs settings - in mconcat - [ argConf "CFLAGS" cflags - , argConf "LDFLAGS" ldflags - , argConf "CPPFLAGS" cppflags - , joinArgs "--gcc-options=" cflags " " ldflags - , argConf "--with-iconv-includes" $ arg IconvIncludeDirs - , argConf "--with-iconv-libraries" $ arg IconvLibDirs - , argConf "--with-gmp-includes" $ arg GmpIncludeDirs - , argConf "--with-gmp-libraries" $ arg GmpLibDirs - , when CrossCompiling $ argConf "--host" $ arg TargetPlatformFull -- TODO: why not host? - , argConf "--with-cc" $ arg Gcc - ] + in argConf "CFLAGS" cflags + <> argConf "LDFLAGS" ldflags + <> argConf "CPPFLAGS" cppflags + <> arg (concat <$> "--gcc-options=" <+> cflags <+> " " <+> ldflags) + <> argConf "--with-iconv-includes" IconvIncludeDirs + <> argConf "--with-iconv-libraries" IconvLibDirs + <> argConf "--with-gmp-includes" GmpIncludeDirs + <> argConf "--with-gmp-libraries" GmpLibDirs + <> when CrossCompiling (argConf "--host" TargetPlatformFull) -- TODO: why not host? + <> argConf "--with-cc" Gcc buildPackageData :: Package -> TodoItem -> Rules () buildPackageData pkg @ (Package name path _) (stage, dist, settings) = @@ -57,30 +51,28 @@ buildPackageData pkg @ (Package name path _) (stage, dist, settings) = postProcessPackageData $ path dist "package-data.mk" where cabalArgs, ghcPkgArgs :: Args - cabalArgs = mconcat - [ args "configure" path dist + cabalArgs = arg ["configure", path, dist] -- this is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument -- * if there are many, we must collapse them into one space-separated string - , joinArgsSpaced "" (customDllArgs settings) - , with $ Ghc stage -- TODO: used to be stage01 (using max Stage1 GHC) - , with $ GhcPkg stage + <> arg (unwords <$> customDllArgs settings) + <> with (Ghc stage) -- TODO: used to be stage01 (using max Stage1 GHC) + <> with (GhcPkg stage) - , customConfArgs settings - , libraryArgs =<< ways settings + <> customConfArgs settings + <> (libraryArgs =<< ways settings) - , when hsColourSrcs $ with HsColour - , configureArgs stage settings + <> when hsColourSrcs (with HsColour) + <> configureArgs stage settings - , when (stage == Stage0) $ bootPkgConstraints - , with Gcc - , when (stage /= Stage0) $ with Ld + <> when (stage == Stage0) bootPkgConstraints + <> with Gcc + <> when (stage /= Stage0) (with Ld) - , with Ar - , with Alex - , with Happy - ] -- TODO: reorder with's + <> with Ar + <> with Alex + <> with Happy -- TODO: reorder with's - ghcPkgArgs = args "update" "--force" - (when (stage == Stage0) $ arg "--package-db=libraries/bootstrapping.conf") - (path dist "inplace-pkg-config") + ghcPkgArgs = arg ["update", "--force"] + <> when (stage == Stage0) (arg "--package-db=libraries/bootstrapping.conf") + <> arg (path dist "inplace-pkg-config") diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index b3e013f..7ccb7b6 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -88,14 +88,14 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = return $ prefix ++ buildDir suffix , map (\d -> "-I" ++ path d) <$> filter isRelative <$> arg (IncludeDirs pkgData) , map (\d -> "-I" ++ d) <$> filter isAbsolute <$> arg (IncludeDirs pkgData) - , args "-optP-include" ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + , arg ["-optP-include", "-optP" ++ buildDir "build/autogen/cabal_macros.h"] , if usePackageKey then map ("-package-key " ++) <$> arg (DepKeys pkgData) else map ("-package " ++) <$> arg (Deps pkgData) , arg "-no-user-package-db" - , args "-odir" (buildDir "build") - , args "-stubdir" (buildDir "build") - , joinArgsSpaced "-dep-makefile" out + , arg ["-odir" , buildDir "build"] + , arg ["-stubdir", buildDir "build"] + , arg $ "-dep-makefile " ++ out , concatMap (\w -> ["-dep-suffix", suffix w]) <$> ways settings , arg "-include-pkg-deps" , arg $ map normalise srcs From git at git.haskell.org Thu Oct 26 23:48:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #59 from angerman/feature/hp2ps-deps (3b1b4df) Message-ID: <20171026234824.7F19A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b1b4df56ef0ec92bd88f53eceb13cff11e4130d/ghc >--------------------------------------------------------------- commit 3b1b4df56ef0ec92bd88f53eceb13cff11e4130d Merge: b45902d 456d2bd Author: Andrey Mokhov Date: Sun Dec 27 09:36:49 2015 +0000 Merge pull request #59 from angerman/feature/hp2ps-deps Adds ghcautoconf and ghcplatform as dependencies to hp2ps. >--------------------------------------------------------------- 3b1b4df56ef0ec92bd88f53eceb13cff11e4130d README.md | 3 --- src/Rules/Dependencies.hs | 2 ++ 2 files changed, 2 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:48:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set precedence level for <+>. (45208c5) Message-ID: <20171026234826.7C7613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45208c5e1e6059db3b6993f03db0a0439f486377/ghc >--------------------------------------------------------------- commit 45208c5e1e6059db3b6993f03db0a0439f486377 Author: Andrey Mokhov Date: Sat Jan 10 02:13:01 2015 +0000 Set precedence level for <+>. >--------------------------------------------------------------- 45208c5e1e6059db3b6993f03db0a0439f486377 src/Base.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index ce2714e..de0c3d6 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -51,6 +51,8 @@ arg = showArgs (<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args a <+> b = (<>) <$> showArgs a <*> showArgs b +infixr 6 <+> + filterOut :: ShowArgs a => Args -> a -> Args filterOut as exclude = do exclude' <- showArgs exclude From git at git.haskell.org Thu Oct 26 23:48:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/snowleopard/shaking-up-ghc (c96b1e9) Message-ID: <20171026234828.1EE1B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c96b1e9f8ffdd430787ee8cd2f016d3474ffba9a/ghc >--------------------------------------------------------------- commit c96b1e9f8ffdd430787ee8cd2f016d3474ffba9a Merge: 9ae96f4 f84ee22 Author: Neil Mitchell Date: Sun Jan 10 20:28:45 2016 +0000 Merge branch 'master' of https://github.com/snowleopard/shaking-up-ghc >--------------------------------------------------------------- c96b1e9f8ffdd430787ee8cd2f016d3474ffba9a .appveyor.yml | 6 +++ src/Base.hs | 2 + src/GHC.hs | 33 +---------------- src/Oracles/LookupInPath.hs | 15 +++----- src/Oracles/PackageDeps.hs | 4 +- src/Rules/Compile.hs | 3 +- src/Rules/Config.hs | 1 + src/Rules/Data.hs | 74 +++++++++++++++++++++++++------------ src/Rules/Dependencies.hs | 10 ++++- src/Rules/Generate.hs | 6 ++- src/Rules/IntegerGmp.hs | 1 + src/Rules/Libffi.hs | 10 +++-- src/Rules/Library.hs | 13 +++++-- src/Rules/Program.hs | 4 +- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Builders/GhcPkg.hs | 6 ++- src/Settings/Builders/HsCpp.hs | 4 +- src/Settings/Default.hs | 36 +++++++++++++++++- src/Settings/Packages/Ghc.hs | 4 +- src/Settings/Packages/IntegerGmp.hs | 1 + src/Settings/Packages/IservBin.hs | 3 +- src/Settings/Packages/Rts.hs | 5 ++- src/Settings/TargetDirectory.hs | 4 +- src/Settings/User.hs | 26 +++++++------ 24 files changed, 167 insertions(+), 107 deletions(-) diff --cc src/Oracles/LookupInPath.hs index d573fd7,e75a80d..a9dc995 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@@ -1,9 -1,8 +1,7 @@@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} - module Oracles.LookupInPath ( - lookupInPath, lookupInPathOracle - ) where + module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where import Base -import Extra (wordsBy) newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) From git at git.haskell.org Thu Oct 26 23:48:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (b27b177) Message-ID: <20171026234828.6C6EC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b27b177a5657e7c8a9088ace440f73074ab4f2d7/ghc >--------------------------------------------------------------- commit b27b177a5657e7c8a9088ace440f73074ab4f2d7 Author: Andrey Mokhov Date: Mon Dec 28 03:01:15 2015 +0000 Clean up. >--------------------------------------------------------------- b27b177a5657e7c8a9088ace440f73074ab4f2d7 src/Builder.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index b58d701..b6fd228 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -14,9 +14,10 @@ import Stage -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg -- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) --- TODO: add Cpp builders --- TODO: rename Gcc to Cc? --- TODO: do we really need staged builders? +-- TODO: Do we really need HsCpp builder? Can't we use a generic Cpp +-- builder instead? It would also be used instead of GccM. +-- TODO: rename Gcc to CCompiler? We sometimes use gcc and sometimes clang. +-- TODO: why are Gcc/GccM staged? data Builder = Alex | Ar | DeriveConstants @@ -26,7 +27,6 @@ data Builder = Alex | Ghc Stage | GhcCabal | GhcCabalHsColour - | GhcLink Stage | GhcM Stage | GhcPkg Stage | GhcSplit @@ -55,7 +55,6 @@ builderKey builder = case builder of Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - GhcLink stage -> builderKey $ Ghc stage -- using Ghc as linker GhcM stage -> builderKey $ Ghc stage -- synonym for 'Ghc -M' GhcCabal -> "ghc-cabal" GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' From git at git.haskell.org Thu Oct 26 23:48:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hide parallel when importing from Development.Shake (6c81e9a) Message-ID: <20171026234831.EC60B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6c81e9aef6f0eaa626f27ceb6ed4a3d2af269a43/ghc >--------------------------------------------------------------- commit 6c81e9aef6f0eaa626f27ceb6ed4a3d2af269a43 Author: Neil Mitchell Date: Sun Jan 10 20:31:24 2016 +0000 Hide parallel when importing from Development.Shake >--------------------------------------------------------------- 6c81e9aef6f0eaa626f27ceb6ed4a3d2af269a43 src/Base.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 6d80a72..54f2f99 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,3 +1,5 @@ +{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} + module Base ( -- * General utilities module Control.Applicative, @@ -34,7 +36,7 @@ import Data.Function import Data.List.Extra import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>)) +import Development.Shake hiding (parallel, unit, (*>)) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Thu Oct 26 23:48:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (d08651a) Message-ID: <20171026234829.F2DF13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d08651a9b504b04425865eaceaba66f2f74cdaa8/ghc >--------------------------------------------------------------- commit d08651a9b504b04425865eaceaba66f2f74cdaa8 Author: Andrey Mokhov Date: Sat Jan 10 02:14:14 2015 +0000 Clean up. >--------------------------------------------------------------- d08651a9b504b04425865eaceaba66f2f74cdaa8 src/Package/Data.hs | 77 +++++++++++++++++++++++++---------------------------- 1 file changed, 36 insertions(+), 41 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 81a7d7f..7428a87 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -35,44 +35,39 @@ configureArgs stage settings = buildPackageData :: Package -> TodoItem -> Rules () buildPackageData pkg @ (Package name path _) (stage, dist, settings) = - ((path dist) ) <$> - [ "package-data.mk", - "haddock-prologue.txt", - "inplace-pkg-config", - "setup-config", - "build" "autogen" "cabal_macros.h", - "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. - ] &%> \_ -> do - need ["shake/src/Package/Data.hs"] -- Track changes in this file - need [path name <.> "cabal"] - when (doesFileExist $ path "configure.ac") $ need [path "configure"] - run GhcCabal cabalArgs - when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs - postProcessPackageData $ path dist "package-data.mk" - where - cabalArgs, ghcPkgArgs :: Args - cabalArgs = arg ["configure", path, dist] - -- this is a positional argument, hence: - -- * if it is empty, we need to emit one empty string argument - -- * if there are many, we must collapse them into one space-separated string - <> arg (unwords <$> customDllArgs settings) - <> with (Ghc stage) -- TODO: used to be stage01 (using max Stage1 GHC) - <> with (GhcPkg stage) - - <> customConfArgs settings - <> (libraryArgs =<< ways settings) - - <> when hsColourSrcs (with HsColour) - <> configureArgs stage settings - - <> when (stage == Stage0) bootPkgConstraints - <> with Gcc - <> when (stage /= Stage0) (with Ld) - - <> with Ar - <> with Alex - <> with Happy -- TODO: reorder with's - - ghcPkgArgs = arg ["update", "--force"] - <> when (stage == Stage0) (arg "--package-db=libraries/bootstrapping.conf") - <> arg (path dist "inplace-pkg-config") + let buildDir = path dist + cabalArgs = arg ["configure", path, dist] + -- this is a positional argument, hence: + -- * if it is empty, we need to emit one empty string argument + -- * if there are many, we must collapse them into one space-separated string + <> arg (unwords <$> customDllArgs settings) + <> with (Ghc stage) -- TODO: used to be stage01 (using max stage1 GHC) + <> with (GhcPkg stage) + <> customConfArgs settings + <> (libraryArgs =<< ways settings) + <> when hsColourSrcs (with HsColour) + <> configureArgs stage settings + <> when (stage == Stage0) bootPkgConstraints + <> with Gcc + <> when (stage /= Stage0) (with Ld) + <> with Ar + <> with Alex + <> with Happy -- TODO: reorder with's + ghcPkgArgs = arg ["update", "--force"] + <> when (stage == Stage0) (arg "--package-db=libraries/bootstrapping.conf") + <> arg (buildDir "inplace-pkg-config") + in + (buildDir ) <$> + [ "package-data.mk" + , "haddock-prologue.txt" + , "inplace-pkg-config" + , "setup-config" + , "build" "autogen" "cabal_macros.h" + , "build" "autogen" ("Paths_" ++ name) <.> "hs" -- TODO: Is this needed? Also check out Paths_cpsa.hs. + ] &%> \_ -> do + need ["shake/src/Package/Data.hs"] -- Track changes in this file + need [path name <.> "cabal"] + when (doesFileExist $ path "configure.ac") $ need [path "configure"] + run GhcCabal cabalArgs + when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs + postProcessPackageData $ buildDir "package-data.mk" From git at git.haskell.org Thu Oct 26 23:48:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to generated Haskell files. (7274771) Message-ID: <20171026234832.40F913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7274771087702c22c23b94c27560de1199cb005f/ghc >--------------------------------------------------------------- commit 7274771087702c22c23b94c27560de1199cb005f Author: Andrey Mokhov Date: Mon Dec 28 03:02:08 2015 +0000 Fix paths to generated Haskell files. >--------------------------------------------------------------- 7274771087702c22c23b94c27560de1199cb005f src/Oracles/ModuleFiles.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 832deef..33f6138 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -21,8 +21,9 @@ moduleFiles stage pkg = do haskellModuleFiles :: Stage -> Package -> Action ([FilePath], [String]) haskellModuleFiles stage pkg = do - let path = targetPath stage pkg - autogen = path -/- "build/autogen" + let path = targetPath stage pkg + autogen = path -/- "build/autogen" + dropPkgPath = drop $ length (pkgPath pkg) + 1 srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath pkg -/- dir | dir <- srcDirs ] @@ -31,9 +32,10 @@ haskellModuleFiles stage pkg = do let found = foundSrcDirs ++ foundAutogen missingMods = modules `minusOrd` (sort $ map fst found) - otherMods = map (replaceEq '/' '.' . dropExtension) otherFiles + otherFileToMod = replaceEq '/' '.' . dropExtension . dropPkgPath (haskellFiles, otherFiles) = partition ("//*hs" ?==) (map snd found) - return (haskellFiles, missingMods ++ otherMods) + + return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) moduleFilesOracle :: Rules () moduleFilesOracle = do From git at git.haskell.org Thu Oct 26 23:48:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor buildPackageDependencies into separate functions. (b70f3d8) Message-ID: <20171026234833.7FC3E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b/ghc >--------------------------------------------------------------- commit b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b Author: Andrey Mokhov Date: Sat Jan 10 02:14:55 2015 +0000 Refactor buildPackageDependencies into separate functions. >--------------------------------------------------------------- b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b src/Package/Dependencies.hs | 134 ++++++++++++++------------------------------ 1 file changed, 43 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b70f3d8be2922c6e81c762bc9cf51cfc8decbc4b From git at git.haskell.org Thu Oct 26 23:48:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove qualification on parallel identifiers (aaf934d) Message-ID: <20171026234836.2EFD03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aaf934d0677ddd675918e2bd075c0a1015a4d7bf/ghc >--------------------------------------------------------------- commit aaf934d0677ddd675918e2bd075c0a1015a4d7bf Author: Neil Mitchell Date: Sun Jan 10 20:31:37 2016 +0000 Remove qualification on parallel identifiers >--------------------------------------------------------------- aaf934d0677ddd675918e2bd075c0a1015a4d7bf src/GHC.hs | 4 ++-- src/Way.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 54f94d9..c0013ad 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,7 +4,7 @@ module GHC ( deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty, + integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, @@ -24,7 +24,7 @@ defaultKnownPackages = , deepseq, deriveConstants, directory, dllSplit, filepath, genapply , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp - , integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty + , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time , touchy, transformers, unlit, unix, win32, xhtml ] diff --git a/src/Way.hs b/src/Way.hs index 5b24662..974314c 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, - vanilla, profiling, logging, Way.parallel, granSim, + vanilla, profiling, logging, parallel, granSim, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, From git at git.haskell.org Thu Oct 26 23:48:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use orderOnly dependencies for generated headers, see #48 (e7f3ae8) Message-ID: <20171026234836.6E9263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7f3ae8418552a145dc192ff5127d2e84bf1fa76/ghc >--------------------------------------------------------------- commit e7f3ae8418552a145dc192ff5127d2e84bf1fa76 Author: Andrey Mokhov Date: Mon Dec 28 03:03:26 2015 +0000 Use orderOnly dependencies for generated headers, see #48 >--------------------------------------------------------------- e7f3ae8418552a145dc192ff5127d2e84bf1fa76 src/Rules/Dependencies.hs | 27 +++------------------ src/Rules/Generate.hs | 62 +++++++++++++++++++++++++++++++++-------------- 2 files changed, 47 insertions(+), 42 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 197fa64..dc43071 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -1,7 +1,6 @@ module Rules.Dependencies (buildPackageDependencies) where import Expression -import GHC import Oracles import Rules.Actions import Rules.Generate @@ -14,37 +13,17 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = buildPath = path -/- "build" dropBuild = (pkgPath pkg ++) . drop (length buildPath) hDepFile = buildPath -/- ".hs-dependencies" - platformH = targetPath stage compiler -/- "ghc_boot_platform.h" in do (buildPath "*.c.deps") %> \out -> do let srcFile = dropBuild . dropExtension $ out - when (pkg == compiler) . need $ platformH : includesDependencies - when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] + orderOnly $ generatedDependencies stage pkg need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - when (pkg == compiler) . need $ platformH : includesDependencies - when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] - -- TODO: very ugly and fragile; use gcc -MM instead? - let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) - [ "primop-vector-uniques.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" - , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] - need $ srcs ++ extraDeps + orderOnly $ generatedDependencies stage pkg + need srcs if srcs == [] then writeFileChanged out "" else build $ fullTarget target (GhcM stage) srcs [out] diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index bc0089c..c7d13d6 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( generatePackageCode, generateRules, - derivedConstantsPath, includesDependencies + derivedConstantsPath, generatedDependencies ) where import Expression @@ -19,18 +19,47 @@ import Settings primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" +primopsTxt :: Stage -> FilePath +primopsTxt stage = targetPath stage compiler -/- "build/primops.txt" + +platformH :: Stage -> FilePath +platformH stage = targetPath stage compiler -/- "ghc_boot_platform.h" + derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" -- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? -includesDependencies :: [FilePath] -includesDependencies = - [ "includes/ghcautoconf.h" - , "includes/ghcplatform.h" - , derivedConstantsPath -/- "DerivedConstants.h" - , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" ] +generatedDependencies :: Stage -> Package -> [FilePath] +generatedDependencies stage pkg + | pkg == hp2ps = [ "includes/ghcautoconf.h" + , "includes/ghcplatform.h" ] + | pkg == compiler = let buildPath = targetPath stage compiler -/- "build" + in + [ "includes/ghcautoconf.h" + , "includes/ghcplatform.h" + , derivedConstantsPath -/- "DerivedConstants.h" + , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" + , platformH stage ] + ++ + fmap (buildPath -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] + | otherwise = [] -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] @@ -52,10 +81,7 @@ generate file target expr = do generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = - let path = targetPath stage pkg - buildPath = path -/- "build" - primopsTxt = targetPath stage compiler -/- "build/primops.txt" - platformH = targetPath stage compiler -/- "ghc_boot_platform.h" + let buildPath = targetPath stage pkg -/- "build" generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) file <~ gen = generate file target gen in do @@ -74,8 +100,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = copyFileChanged srcBoot $ file -<.> "hs-boot" -- TODO: needing platformH is ugly and fragile - when (pkg == compiler) $ primopsTxt %> \file -> do - need [platformH, primopsSource] + when (pkg == compiler) $ primopsTxt stage %> \file -> do + need [platformH stage, primopsSource] build $ fullTarget target HsCpp [primopsSource] [file] -- TODO: why different folders for generated files? @@ -83,8 +109,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = [ "GHC/PrimopWrappers.hs" , "autogen/GHC/Prim.hs" , "*.hs-incl" ] |%> \file -> do - need [primopsTxt] - build $ fullTarget target GenPrimopCode [primopsTxt] [file] + need [primopsTxt stage] + build $ fullTarget target GenPrimopCode [primopsTxt stage] [file] priority 2.0 $ do when (pkg == compiler && stage == Stage1) $ @@ -94,7 +120,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs - when (pkg == compiler) $ platformH %> \file -> do + when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do From git at git.haskell.org Thu Oct 26 23:48:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comment as to why we disable a warning (02c75e7) Message-ID: <20171026234839.A38FF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02c75e7600d4208151f8ff1949f05fc0c339f1ff/ghc >--------------------------------------------------------------- commit 02c75e7600d4208151f8ff1949f05fc0c339f1ff Author: Neil Mitchell Date: Sun Jan 10 20:32:04 2016 +0000 Comment as to why we disable a warning >--------------------------------------------------------------- 02c75e7600d4208151f8ff1949f05fc0c339f1ff src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 54f2f99..4b6ad10 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,4 @@ -{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} +{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel module Base ( -- * General utilities From git at git.haskell.org Thu Oct 26 23:48:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add prefixArgs function. (4c715ac) Message-ID: <20171026234837.5270A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4c715acd811aef3c2be59375280c586e22fc0ecc/ghc >--------------------------------------------------------------- commit 4c715acd811aef3c2be59375280c586e22fc0ecc Author: Andrey Mokhov Date: Sat Jan 10 19:13:55 2015 +0000 Add prefixArgs function. >--------------------------------------------------------------- 4c715acd811aef3c2be59375280c586e22fc0ecc src/Base.hs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index de0c3d6..ffb2bbb 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -10,7 +10,8 @@ module Base ( Args, arg, ShowArgs (..), Condition (..), (<+>), - filterOut + filterOut, + prefixArgs ) where import Development.Shake @@ -47,13 +48,20 @@ instance ShowArgs a => ShowArgs (Action a) where arg :: ShowArgs a => a -> Args arg = showArgs --- Combine two heterogeneous ShowArgs values. +-- Combine two heterogeneous ShowArgs values (<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args a <+> b = (<>) <$> showArgs a <*> showArgs b infixr 6 <+> +-- Filter out given arg(s) from a collection filterOut :: ShowArgs a => Args -> a -> Args filterOut as exclude = do exclude' <- showArgs exclude filter (`notElem` exclude') <$> as + +-- Prefix each arg in a collection with a given prefix +prefixArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args +prefixArgs prefix as = do + prefix' <- showArgs prefix + concatMap (\a -> prefix' ++ [a]) <$> showArgs as From git at git.haskell.org Thu Oct 26 23:48:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a TODO note for unlit and driver/ghc-split utils. (58d7fcc) Message-ID: <20171026234840.1BE443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/58d7fccf59da038f038446c41901fa086ae4a40c/ghc >--------------------------------------------------------------- commit 58d7fccf59da038f038446c41901fa086ae4a40c Author: Andrey Mokhov Date: Mon Dec 28 12:44:13 2015 +0000 Add a TODO note for unlit and driver/ghc-split utils. >--------------------------------------------------------------- 58d7fccf59da038f038446c41901fa086ae4a40c src/GHC.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 281f15e..859bec4 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -85,10 +85,11 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" +-- TODO: The following utils are not implemented yet: unlit, driver/ghc-split -- TODO: The following utils are not included into the build system because --- they seem to be unused or unrelated to the build process: chechUniques, +-- they seem to be unused or unrelated to the build process: checkUniques, -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, --- lndir, mkdirhier, testremove, touchy, unlit, vagrant +-- lndir, mkdirhier, testremove, touchy, vagrant -- GHC build results will be placed into target directories with the following -- typical structure: From git at git.haskell.org Thu Oct 26 23:48:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (3579324) Message-ID: <20171026234840.CCB173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3579324b91abeb130df12d8639b67941c71d80ae/ghc >--------------------------------------------------------------- commit 3579324b91abeb130df12d8639b67941c71d80ae Author: Andrey Mokhov Date: Sat Jan 10 19:14:45 2015 +0000 Clean up. >--------------------------------------------------------------- 3579324b91abeb130df12d8639b67941c71d80ae src/Package.hs | 3 ++- src/Package/Data.hs | 6 +++++- src/Package/Dependencies.hs | 39 ++++++++++++++++++--------------------- 3 files changed, 25 insertions(+), 23 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 7a5f20e..0df8668 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -18,7 +18,8 @@ buildPackage pkg todoItem = do packageRules :: Rules () packageRules = do - want ["libraries/deepseq/dist-install/build/deepseq.m"] -- TODO: control targets from commang line arguments + -- TODO: control targets from commang line arguments + want ["libraries/deepseq/dist-install/build/deepseq.m"] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 7428a87..fd8dd2c 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -1,5 +1,6 @@ {-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} module Package.Data (buildPackageData) where + import Package.Base libraryArgs :: [Way] -> Args @@ -18,7 +19,10 @@ configureArgs stage settings = s <- unwords <$> arg as unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = commonCcArgs `filterOut` "-Werror" <+> ConfCcArgs stage <+> customCcArgs settings <+> commonCcWarninigArgs + cflags = commonCcArgs `filterOut` "-Werror" + <+> ConfCcArgs stage + <+> customCcArgs settings + <+> commonCcWarninigArgs ldflags = commonLdArgs <+> ConfGccLinkerArgs stage <+> customLdArgs settings cppflags = commonCppArgs <+> ConfCppArgs stage <+> customCppArgs settings diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 47a7a37..5b10ca1 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -3,18 +3,17 @@ module Package.Dependencies (buildPackageDependencies) where import Package.Base -packageKeyArgs :: Stage -> FilePath -> Args -packageKeyArgs stage pkgData = - arg "-hide-all-packages" <> - (pkgArgs =<< SupportsPackageKey || stage /= Stage0) +packageArgs :: Stage -> FilePath -> Args +packageArgs stage pkgData = do + usePackageKey <- SupportsPackageKey || stage /= Stage0 + arg ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] + <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") + <> keyArgs usePackageKey where - pkgArgs True = "-this-package-key" - <+> PackageKey pkgData - <+> prepend "-package-key " (DepKeys pkgData) - pkgArgs _ = "-package-name" - <+> PackageKey pkgData - <+> prepend "-package " (Deps pkgData) - prepend pref = (map (pref ++) <$>) . arg + keyArgs True = prefixArgs "-this-package-key" (PackageKey pkgData) <> + prefixArgs "-package-key" (DepKeys pkgData) + keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> + prefixArgs "-package" (Deps pkgData) includeArgs :: ShowArgs a => String -> FilePath -> a -> Args includeArgs prefix path as = map includePath <$> arg as @@ -26,7 +25,7 @@ srcArgs :: FilePath -> FilePath -> Args srcArgs path pkgData = do mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) dirs <- arg (SrcDirs pkgData) - srcs <- getDirectoryFiles "" $ + srcs <- getDirectoryFiles "" [path dir mPath <.> ext | dir <- dirs, mPath <- mods, ext <- ["hs", "lhs"]] arg (map normalise srcs) @@ -38,20 +37,18 @@ buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = (buildDir "build" name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file run (Ghc stage) $ arg "-M" - <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") - <> packageKeyArgs stage pkgData + <> packageArgs stage pkgData <> arg "-i" <> includeArgs "-i" path (SrcDirs pkgData) <> includeArgs "-i" buildDir ["build", "build/autogen"] <> includeArgs "-I" buildDir ["build", "build/autogen"] <> includeArgs "-I" path (IncludeDirs pkgData) - <> arg ["-optP-include", "-optP" ++ buildDir "build/autogen/cabal_macros.h"] - <> arg "-no-user-package-db" - <> arg ["-odir" , buildDir "build"] - <> arg ["-stubdir", buildDir "build"] - <> arg ("-dep-makefile " ++ out) - <> (concatMap (\w -> ["-dep-suffix", suffix w]) <$> ways settings) - <> arg "-include-pkg-deps" + <> arg "-optP-include" -- TODO: Shall we also add -cpp? + <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + <> arg ["-odir" , buildDir "build"] + <> arg ["-stubdir" , buildDir "build"] + <> arg ["-dep-makefile", out ] + <> prefixArgs "-dep-suffix" (map suffix <$> ways settings) <> srcArgs path pkgData -- <> arg SrcHcOpts -- TODO: Check that skipping all _HC_OPTS is safe. -- <> wayHcOpts vanilla -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? From git at git.haskell.org Thu Oct 26 23:48:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #143, turn of name shadowing warning (f89a75f) Message-ID: <20171026234843.344983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f89a75f6730f643acc7002ee940803d01f1bda56/ghc >--------------------------------------------------------------- commit f89a75f6730f643acc7002ee940803d01f1bda56 Author: Neil Mitchell Date: Sun Jan 10 20:34:15 2016 +0000 #143, turn of name shadowing warning >--------------------------------------------------------------- f89a75f6730f643acc7002ee940803d01f1bda56 .ghci | 2 +- build.bat | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 1fe85b3..2f24ebe 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,2 @@ -:set -Wall -isrc +:set -Wall -fno-warn-name-shadowing -isrc :load Main diff --git a/build.bat b/build.bat index 07e355a..41b7877 100644 --- a/build.bat +++ b/build.bat @@ -2,6 +2,7 @@ @set ghcArgs=--make ^ -Wall ^ + -fno-warn-name-shadowing ^ src/Main.hs ^ -isrc ^ -rtsopts ^ From git at git.haskell.org Thu Oct 26 23:48:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport Data.Char (a9aa2ac) Message-ID: <20171026234844.00B223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9aa2ac5825514967ea60f28473ec1a6d435c1a4/ghc >--------------------------------------------------------------- commit a9aa2ac5825514967ea60f28473ec1a6d435c1a4 Author: Ben Gamari Date: Thu Dec 24 14:02:38 2015 +0100 Base: Don't reexport Data.Char It's really not used often enough to warrant special treatment >--------------------------------------------------------------- a9aa2ac5825514967ea60f28473ec1a6d435c1a4 src/Base.hs | 2 -- src/Oracles/WindowsRoot.hs | 1 + src/Rules/Library.hs | 2 ++ src/Rules/Program.hs | 2 ++ 4 files changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 47a4285..3c62ed5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -3,7 +3,6 @@ module Base ( module Control.Applicative, module Control.Monad.Extra, module Control.Monad.Reader, - module Data.Char, module Data.Function, module Data.List, module Data.Maybe, @@ -34,7 +33,6 @@ module Base ( import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader -import Data.Char import Data.Function import Data.List import Data.Maybe diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 2ec13c7..89dd011 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -1,6 +1,7 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.WindowsRoot (windowsRoot, windowsRootOracle) where +import Data.Char (isSpace) import Base newtype WindowsRoot = WindowsRoot () diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 1df83a8..db1624b 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,5 +1,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where +import Data.Char + import Expression hiding (splitPath) import GHC import Oracles diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index a24fcdc..962ce1d 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -1,5 +1,7 @@ module Rules.Program (buildProgram) where +import Data.Char + import Expression hiding (splitPath) import GHC hiding (ghci) import Oracles From git at git.haskell.org Thu Oct 26 23:48:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reexport module Data.Function from Base.hs. (7ad9848) Message-ID: <20171026234844.BB05D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ad9848f719e76bb194719984bbf78a926634fe9/ghc >--------------------------------------------------------------- commit 7ad9848f719e76bb194719984bbf78a926634fe9 Author: Andrey Mokhov Date: Sun Jan 11 03:26:13 2015 +0000 Reexport module Data.Function from Base.hs. >--------------------------------------------------------------- 7ad9848f719e76bb194719984bbf78a926634fe9 src/Base.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index ffb2bbb..38790e6 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -4,6 +4,7 @@ module Base ( module Development.Shake, module Development.Shake.FilePath, module Control.Applicative, + module Data.Function, module Data.Monoid, module Data.List, Stage (..), @@ -17,6 +18,7 @@ module Base ( import Development.Shake import Development.Shake.FilePath import Control.Applicative hiding ((*>)) +import Data.Function import Data.Monoid import Data.List From git at git.haskell.org Thu Oct 26 23:48:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove an unnecessary hiding after disabling name shadow warning (6e1511f) Message-ID: <20171026234846.A37EB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e1511f9d48bb5198ab6feb4f9a2e6039df5b67f/ghc >--------------------------------------------------------------- commit 6e1511f9d48bb5198ab6feb4f9a2e6039df5b67f Author: Neil Mitchell Date: Sun Jan 10 20:34:32 2016 +0000 Remove an unnecessary hiding after disabling name shadow warning >--------------------------------------------------------------- 6e1511f9d48bb5198ab6feb4f9a2e6039df5b67f src/Rules/Library.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 03f91aa..788deb6 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -2,7 +2,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Data.Char -import Base hiding (splitPath, split) +import Base hiding (splitPath) import Expression import GHC import Oracles From git at git.haskell.org Thu Oct 26 23:48:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Hide `parallel` (ef0386c) Message-ID: <20171026234847.971AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef0386c76790b582cb180d5db224d0b4681ae4ba/ghc >--------------------------------------------------------------- commit ef0386c76790b582cb180d5db224d0b4681ae4ba Author: Ben Gamari Date: Thu Dec 24 14:17:54 2015 +0100 Base: Hide `parallel` Otherwise it is shadowed by `GHC.parallel` >--------------------------------------------------------------- ef0386c76790b582cb180d5db224d0b4681ae4ba src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 55c1a9e..47a4285 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -39,7 +39,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>)) +import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes import Development.Shake.Config import Development.Shake.FilePath From git at git.haskell.org Thu Oct 26 23:48:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove way descriptions, add detectWay function. (94501e5) Message-ID: <20171026234848.453163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/94501e5a89c6d81df6d1fededaf4a05793ad135f/ghc >--------------------------------------------------------------- commit 94501e5a89c6d81df6d1fededaf4a05793ad135f Author: Andrey Mokhov Date: Sun Jan 11 03:28:17 2015 +0000 Remove way descriptions, add detectWay function. >--------------------------------------------------------------- 94501e5a89c6d81df6d1fededaf4a05793ad135f src/Ways.hs | 61 ++++++++++++++++++++++++++++++++++++------------------------- 1 file changed, 36 insertions(+), 25 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 3e7c483..843383e 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -12,9 +12,10 @@ module Ways ( threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic, - wayHcOpts, + wayHcArgs, suffix, - hisuf, osuf, hcsuf + hisuf, osuf, hcsuf, + detectWay ) where import Base @@ -25,34 +26,36 @@ data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dyn data Way = Way { tag :: String, -- e.g., "thr_p" - description :: String, -- e.g., "threaded profiled"; TODO: get rid of this field? units :: [WayUnit] -- e.g., [Threaded, Profiling] } deriving Eq -vanilla = Way "v" "vanilla" [] -profiling = Way "p" "profiling" [Profiling] -logging = Way "l" "event logging" [Logging] -parallel = Way "mp" "parallel" [Parallel] -granSim = Way "gm" "GranSim" [GranSim] +instance Show Way where + show = tag + +vanilla = Way "v" [] +profiling = Way "p" [Profiling] +logging = Way "l" [Logging] +parallel = Way "mp" [Parallel] +granSim = Way "gm" [GranSim] -- RTS only ways -threaded = Way "thr" "threaded" [Threaded] -threadedProfiling = Way "thr_p" "threaded profiling" [Threaded, Profiling] -threadedLogging = Way "thr_l" "threaded event logging" [Threaded, Logging] -debug = Way "debug" "debug" [Debug] -debugProfiling = Way "debug_p" "debug profiling" [Debug, Profiling] -threadedDebug = Way "thr_debug" "threaded debug" [Threaded, Debug] -threadedDebugProfiling = Way "thr_debug_p" "threaded debug profiling" [Threaded, Debug, Profiling] -dynamic = Way "dyn" "dyn" [Dynamic] -profilingDynamic = Way "p_dyn" "p_dyn" [Profiling, Dynamic] -threadedProfilingDynamic = Way "thr_p_dyn" "thr_p_dyn" [Threaded, Profiling, Dynamic] -threadedDynamic = Way "thr_dyn" "thr_dyn" [Threaded, Dynamic] -threadedDebugDynamic = Way "thr_debug_dyn" "thr_debug_dyn" [Threaded, Debug, Dynamic] -debugDynamic = Way "debug_dyn" "debug_dyn" [Debug, Dynamic] -loggingDynamic = Way "l_dyn" "event logging dynamic" [Logging, Dynamic] -threadedLoggingDynamic = Way "thr_l_dyn" "threaded event logging dynamic" [Threaded, Logging, Dynamic] +threaded = Way "thr" [Threaded] +threadedProfiling = Way "thr_p" [Threaded, Profiling] +threadedLogging = Way "thr_l" [Threaded, Logging] +debug = Way "debug" [Debug] +debugProfiling = Way "debug_p" [Debug, Profiling] +threadedDebug = Way "thr_debug" [Threaded, Debug] +threadedDebugProfiling = Way "thr_debug_p" [Threaded, Debug, Profiling] +dynamic = Way "dyn" [Dynamic] +profilingDynamic = Way "p_dyn" [Profiling, Dynamic] +threadedProfilingDynamic = Way "thr_p_dyn" [Threaded, Profiling, Dynamic] +threadedDynamic = Way "thr_dyn" [Threaded, Dynamic] +threadedDebugDynamic = Way "thr_debug_dyn" [Threaded, Debug, Dynamic] +debugDynamic = Way "debug_dyn" [Debug, Dynamic] +loggingDynamic = Way "l_dyn" [Logging, Dynamic] +threadedLoggingDynamic = Way "thr_l_dyn" [Threaded, Logging, Dynamic] allWays = [vanilla, profiling, logging, parallel, granSim, threaded, threadedProfiling, threadedLogging, @@ -71,8 +74,8 @@ defaultWays stage = do ++ [profiling | stage /= Stage0] ++ [dynamic | sharedLibs ] -wayHcOpts :: Way -> Args -wayHcOpts (Way _ _ units) = +wayHcArgs :: Way -> Args +wayHcArgs (Way _ units) = mconcat [ when (Dynamic `notElem` units) $ arg ["-static"] , when (Dynamic `elem` units) $ arg ["-fPIC", "-dynamic"] @@ -93,3 +96,11 @@ hisuf, osuf, hcsuf :: Way -> String hisuf = (++ "hi") . suffix osuf = (++ "o" ) . suffix hcsuf = (++ "hc") . suffix + +-- Detect way from a given extension. Fail if the result is not unique. +detectWay :: FilePath -> Way +detectWay extension = case solutions of + [way] -> way + otherwise -> error $ "Cannot detect way from extension '" ++ extension ++ "'." + where + solutions = [w | f <- [hisuf, osuf, hcsuf], w <- allWays, f w == extension] From git at git.haskell.org Thu Oct 26 23:48:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build.bat work regardless of your current directory, so you can invoke it from the root directory (4be2130) Message-ID: <20171026234850.407453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4be213017f9d2a64ae1413c1e73678ead571d7e9/ghc >--------------------------------------------------------------- commit 4be213017f9d2a64ae1413c1e73678ead571d7e9 Author: Neil Mitchell Date: Sun Jan 10 22:31:38 2016 +0000 Make build.bat work regardless of your current directory, so you can invoke it from the root directory >--------------------------------------------------------------- 4be213017f9d2a64ae1413c1e73678ead571d7e9 build.bat | 1 + 1 file changed, 1 insertion(+) diff --git a/build.bat b/build.bat index 41b7877..0cf778a 100644 --- a/build.bat +++ b/build.bat @@ -1,3 +1,4 @@ + at cd %~dp0 @mkdir .shake 2> nul @set ghcArgs=--make ^ From git at git.haskell.org Thu Oct 26 23:48:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport Development.Shake.Config (1405953) Message-ID: <20171026234851.E11EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14059539b1fa2b5e79e38c34266636c60dfb40f4/ghc >--------------------------------------------------------------- commit 14059539b1fa2b5e79e38c34266636c60dfb40f4 Author: Ben Gamari Date: Thu Dec 24 14:37:49 2015 +0100 Base: Don't reexport Development.Shake.Config >--------------------------------------------------------------- 14059539b1fa2b5e79e38c34266636c60dfb40f4 src/Base.hs | 2 -- src/Oracles/Config.hs | 1 + src/Oracles/PackageData.hs | 1 + 3 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fb0eed7..1012d4e 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -11,7 +11,6 @@ module Base ( -- * Shake module Development.Shake, module Development.Shake.Classes, - module Development.Shake.Config, module Development.Shake.FilePath, module Development.Shake.Util, @@ -38,7 +37,6 @@ import Data.Maybe import Data.Monoid import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes -import Development.Shake.Config import Development.Shake.FilePath import Development.Shake.Util import System.Console.ANSI diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index e8333b6..cde2383 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -3,6 +3,7 @@ module Oracles.Config (askConfig, askConfigWithDefault, configOracle) where import Base import qualified Data.HashMap.Strict as Map +import Development.Shake.Config newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 4e3d306..d176839 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -4,6 +4,7 @@ module Oracles.PackageData ( pkgData, pkgDataList, packageDataOracle ) where +import Development.Shake.Config import Base import qualified Data.HashMap.Strict as Map From git at git.haskell.org Thu Oct 26 23:48:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move functions ghcOpts, packageArgs, includeArgs, srcArgs. (ccb5848) Message-ID: <20171026234852.5E1EC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccb58488381da821a99c95965d7a101d040bfd1f/ghc >--------------------------------------------------------------- commit ccb58488381da821a99c95965d7a101d040bfd1f Author: Andrey Mokhov Date: Sun Jan 11 03:29:44 2015 +0000 Move functions ghcOpts, packageArgs, includeArgs, srcArgs. >--------------------------------------------------------------- ccb58488381da821a99c95965d7a101d040bfd1f src/Package/Base.hs | 33 ++++++++++++++++++++++++++------- 1 file changed, 26 insertions(+), 7 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 43b4a37..4ef03fb 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -7,7 +7,8 @@ module Package.Base ( Package (..), Settings (..), TodoItem (..), defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - bootPkgConstraints, ghcOpts + bootPkgConstraints, + packageArgs, includeArgs, srcArgs ) where import Base @@ -76,10 +77,28 @@ bootPkgConstraints = mempty -- $(foreach p,$(basename $(notdir $(wildcard libraries/$d/*.cabal))),\ -- --constraint "$p == $(shell grep -i "^Version:" libraries/$d/$p.cabal | sed "s/[^0-9.]//g")")) --- TODO: move? -ghcOpts :: Package -> Stage -> Way -> Action [String] -ghcOpts pkg stage way = do - return $ ["-hisuf " ++ hisuf way] - ++ ["-osuf " ++ osuf way] - ++ ["-hcsuf " ++ hcsuf way] +packageArgs :: Stage -> FilePath -> Args +packageArgs stage pkgData = do + usePackageKey <- SupportsPackageKey || stage /= Stage0 + arg ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] + <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") + <> keyArgs usePackageKey + where + keyArgs True = prefixArgs "-this-package-key" (PackageKey pkgData) <> + prefixArgs "-package-key" (DepKeys pkgData) + keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> + prefixArgs "-package" (Deps pkgData) +includeArgs :: ShowArgs a => String -> FilePath -> a -> Args +includeArgs prefix path as = map includePath <$> arg as + where + includePath dir | isRelative dir = prefix ++ path dir + | isAbsolute dir = prefix dir + +srcArgs :: FilePath -> FilePath -> Args +srcArgs path pkgData = do + mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) + dirs <- arg (SrcDirs pkgData) + srcs <- getDirectoryFiles "" + [path dir mPath <.> ext | dir <- dirs, mPath <- mods, ext <- ["hs", "lhs"]] + arg (map normaliseEx srcs) From git at git.haskell.org Thu Oct 26 23:48:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move gmp build results to buildRootPath. (a850455) Message-ID: <20171026234853.CCAC53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a850455e1402e79b01bd65cbb0a7e0571969170a/ghc >--------------------------------------------------------------- commit a850455e1402e79b01bd65cbb0a7e0571969170a Author: Andrey Mokhov Date: Sun Jan 10 22:52:19 2016 +0000 Move gmp build results to buildRootPath. See #113. >--------------------------------------------------------------- a850455e1402e79b01bd65cbb0a7e0571969170a shaking-up-ghc.cabal | 2 +- src/Main.hs | 4 +- src/Rules/Data.hs | 10 +-- src/Rules/Generate.hs | 4 +- src/Rules/Gmp.hs | 134 +++++++++++++++++++++++++++++++++++ src/Rules/IntegerGmp.hs | 137 ------------------------------------ src/Rules/Libffi.hs | 24 ++++--- src/Rules/Library.hs | 6 +- src/Settings/Packages/IntegerGmp.hs | 25 ++++--- src/Settings/TargetDirectory.hs | 2 +- 10 files changed, 178 insertions(+), 170 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 a850455e1402e79b01bd65cbb0a7e0571969170a From git at git.haskell.org Thu Oct 26 23:48:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageCompile rule. (c826054) Message-ID: <20171026234855.C6F6E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c826054081b67e094002e47e7635c7d34835f380/ghc >--------------------------------------------------------------- commit c826054081b67e094002e47e7635c7d34835f380 Author: Andrey Mokhov Date: Sun Jan 11 03:31:07 2015 +0000 Add buildPackageCompile rule. >--------------------------------------------------------------- c826054081b67e094002e47e7635c7d34835f380 src/Package.hs | 5 ++++- src/Package/Data.hs | 2 +- src/Package/Dependencies.hs | 28 +--------------------------- 3 files changed, 6 insertions(+), 29 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 0df8668..8f2850d 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -2,6 +2,7 @@ module Package (packageRules) where import Package.Base import Package.Data +import Package.Compile import Package.Dependencies -- See Package.Base for definitions of basic types @@ -15,11 +16,13 @@ buildPackage :: Package -> TodoItem -> Rules () buildPackage pkg todoItem = do buildPackageData pkg todoItem buildPackageDependencies pkg todoItem + buildPackageCompile pkg todoItem packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments - want ["libraries/deepseq/dist-install/build/deepseq.m"] + want [ "libraries/deepseq/dist-install/build/Control/DeepSeq.o" + , "libraries/deepseq/dist-install/build/Control/DeepSeq.p_o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem diff --git a/src/Package/Data.hs b/src/Package/Data.hs index fd8dd2c..919d7a5 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -38,7 +38,7 @@ configureArgs stage settings = <> argConf "--with-cc" Gcc buildPackageData :: Package -> TodoItem -> Rules () -buildPackageData pkg @ (Package name path _) (stage, dist, settings) = +buildPackageData (Package name path _) (stage, dist, settings) = let buildDir = path dist cabalArgs = arg ["configure", path, dist] -- this is a positional argument, hence: diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 5b10ca1..26b154f 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -3,34 +3,8 @@ module Package.Dependencies (buildPackageDependencies) where import Package.Base -packageArgs :: Stage -> FilePath -> Args -packageArgs stage pkgData = do - usePackageKey <- SupportsPackageKey || stage /= Stage0 - arg ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] - <> when (stage == Stage0) (arg "-package-db libraries/bootstrapping.conf") - <> keyArgs usePackageKey - where - keyArgs True = prefixArgs "-this-package-key" (PackageKey pkgData) <> - prefixArgs "-package-key" (DepKeys pkgData) - keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> - prefixArgs "-package" (Deps pkgData) - -includeArgs :: ShowArgs a => String -> FilePath -> a -> Args -includeArgs prefix path as = map includePath <$> arg as - where - includePath dir | isRelative dir = prefix ++ path dir - | isAbsolute dir = prefix dir - -srcArgs :: FilePath -> FilePath -> Args -srcArgs path pkgData = do - mods <- map (replaceEq '.' pathSeparator) <$> arg (Modules pkgData) - dirs <- arg (SrcDirs pkgData) - srcs <- getDirectoryFiles "" - [path dir mPath <.> ext | dir <- dirs, mPath <- mods, ext <- ["hs", "lhs"]] - arg (map normalise srcs) - buildPackageDependencies :: Package -> TodoItem -> Rules () -buildPackageDependencies pkg @ (Package name path _) (stage, dist, settings) = +buildPackageDependencies (Package name path _) (stage, dist, settings) = let buildDir = path dist pkgData = buildDir "package-data.mk" in From git at git.haskell.org Thu Oct 26 23:48:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #144 from ndmitchell/master (ef27c7c) Message-ID: <20171026234857.576763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef27c7c14f589fdd585c8c9bb2d6264db92a73d0/ghc >--------------------------------------------------------------- commit ef27c7c14f589fdd585c8c9bb2d6264db92a73d0 Merge: a850455 4be2130 Author: Andrey Mokhov Date: Sun Jan 10 22:54:19 2016 +0000 Merge pull request #144 from ndmitchell/master General refactorings >--------------------------------------------------------------- ef27c7c14f589fdd585c8c9bb2d6264db92a73d0 .ghci | 2 ++ build.bat | 2 ++ src/Base.hs | 8 +++++--- src/Expression.hs | 4 ++-- src/Oracles/LookupInPath.hs | 1 - src/Rules.hs | 3 +-- src/Rules/Actions.hs | 7 +++---- src/Rules/Data.hs | 1 - src/Rules/Libffi.hs | 1 - src/Way.hs | 2 +- 10 files changed, 16 insertions(+), 15 deletions(-) diff --cc src/Rules/Data.hs index 5cd2e50,99334f4..fbe22db --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@@ -1,10 -1,7 +1,9 @@@ module Rules.Data (buildPackageData) where +import qualified System.Directory as IO + import Base import Expression - import Extra (replace) import GHC import Oracles import Predicates (registerPackage) From git at git.haskell.org Thu Oct 26 23:48:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport Development.Shake.Util (062e6b2) Message-ID: <20171026234855.63A2C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/062e6b2ad5dc4be679f14f9b5a8ecbd99febc54b/ghc >--------------------------------------------------------------- commit 062e6b2ad5dc4be679f14f9b5a8ecbd99febc54b Author: Ben Gamari Date: Thu Dec 24 14:38:53 2015 +0100 Base: Don't reexport Development.Shake.Util >--------------------------------------------------------------- 062e6b2ad5dc4be679f14f9b5a8ecbd99febc54b src/Base.hs | 2 -- src/Rules/Dependencies.hs | 1 + 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 1012d4e..25a69df 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,7 +12,6 @@ module Base ( module Development.Shake, module Development.Shake.Classes, module Development.Shake.FilePath, - module Development.Shake.Util, -- * Paths shakeFilesPath, configPath, sourcePath, programInplacePath, @@ -38,7 +37,6 @@ import Data.Monoid import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes import Development.Shake.FilePath -import Development.Shake.Util import System.Console.ANSI import qualified System.Directory as IO import System.IO diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index a2f5aa2..88e97b2 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -7,6 +7,7 @@ import Rules.Actions import Rules.Generate import Rules.Resources import Settings +import Development.Shake.Util (parseMakefile) buildPackageDependencies :: Resources -> PartialTarget -> Rules () buildPackageDependencies _ target @ (PartialTarget stage pkg) = From git at git.haskell.org Thu Oct 26 23:48:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Reexport `MonadTrans` instead of `Reader` (6472042) Message-ID: <20171026234859.69C4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6472042ba8fddbc721b1bc6ae322a58212b5fe32/ghc >--------------------------------------------------------------- commit 6472042ba8fddbc721b1bc6ae322a58212b5fe32 Author: Ben Gamari Date: Thu Dec 24 14:35:31 2015 +0100 Base: Reexport `MonadTrans` instead of `Reader` The former is much more common than the latter. >--------------------------------------------------------------- 6472042ba8fddbc721b1bc6ae322a58212b5fe32 src/Base.hs | 2 +- src/Builder.hs | 2 ++ src/Expression.hs | 2 ++ src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 2 ++ src/Target.hs | 2 ++ 6 files changed, 11 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index aa9861b..fb0eed7 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -2,11 +2,11 @@ module Base ( -- * General utilities module Control.Applicative, module Control.Monad.Extra, - module Control.Monad.Reader, module Data.Function, module Data.List, module Data.Maybe, module Data.Monoid, + MonadTrans(lift), -- * Shake module Development.Shake, diff --git a/src/Builder.hs b/src/Builder.hs index b6fd228..78f8376 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -3,6 +3,8 @@ module Builder ( Builder (..), builderPath, getBuilderPath, specified, needBuilder ) where +import Control.Monad.Trans.Reader + import Base import GHC.Generics (Generic) import Oracles diff --git a/src/Expression.hs b/src/Expression.hs index 0d47314..a83ea15 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -24,6 +24,8 @@ module Expression ( module Way ) where +import Control.Monad.Trans.Reader + import Base import Package import Builder diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 47ea75d..d40b762 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -4,6 +4,8 @@ module Oracles.Config.Flag ( ghcWithNativeCodeGen, supportsSplitObjects ) where +import Control.Monad.Trans.Reader + import Base import Oracles.Config import Oracles.Config.Setting diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 81e2924..b0c6da3 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -6,6 +6,8 @@ module Oracles.Config.Setting ( ghcCanonVersion, cmdLineLengthLimit ) where +import Control.Monad.Trans.Reader + import Base import Oracles.Config import Stage diff --git a/src/Target.hs b/src/Target.hs index 2060d04..25967b4 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -3,6 +3,8 @@ module Target ( Target (..), PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay ) where +import Control.Monad.Trans.Reader + import Base import Builder import GHC.Generics (Generic) From git at git.haskell.org Thu Oct 26 23:48:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:48:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add src/Package/Compile.hs. (e315d33) Message-ID: <20171026234859.B4EA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e315d3381d2441e5acfc86384fb7eff9575cb006/ghc >--------------------------------------------------------------- commit e315d3381d2441e5acfc86384fb7eff9575cb006 Author: Andrey Mokhov Date: Sun Jan 11 03:31:34 2015 +0000 Add src/Package/Compile.hs. >--------------------------------------------------------------- e315d3381d2441e5acfc86384fb7eff9575cb006 src/Package/Compile.hs | 43 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 43 insertions(+) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs new file mode 100644 index 0000000..0733a46 --- /dev/null +++ b/src/Package/Compile.hs @@ -0,0 +1,43 @@ +{-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} +module Package.Compile (buildPackageCompile) where + +import Package.Base +import Development.Shake.Util + +-- "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.o + +suffixArgs :: Way -> Args +suffixArgs way = arg ["-hisuf", hisuf way, "-osuf", osuf way, "-hcsuf", hcsuf way] + +buildPackageCompile :: Package -> TodoItem -> Rules () +buildPackageCompile (Package name path _) (stage, dist, settings) = + let buildDir = path dist + pkgData = buildDir "package-data.mk" + depFile = buildDir "build" name <.> "m" + in + (buildDir "build//*o") %> \out -> do + let way = detectWay $ tail $ takeExtension out + need ["shake/src/Package/Compile.hs"] -- Track changes in this file + need [depFile] + depContents <- parseMakefile <$> (liftIO $ readFile depFile) + let deps = concat $ snd $ unzip $ filter ((== out) . fst) depContents + srcs = filter ("//*hs" ?==) deps + need deps + run (Ghc stage) $ suffixArgs way + <> wayHcArgs way + <> arg SrcHcOpts + <> packageArgs stage pkgData + <> arg "-i" + <> includeArgs "-i" path (SrcDirs pkgData) + <> includeArgs "-i" buildDir ["build", "build/autogen"] + <> includeArgs "-I" buildDir ["build", "build/autogen"] + <> includeArgs "-I" path (IncludeDirs pkgData) + <> arg "-optP-include" -- TODO: Shall we also add -cpp? + <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + <> arg ["-Wall", "-XHaskell2010", "-O2"] -- TODO: now we have both -O and -O2 + <> arg ["-odir" , buildDir "build"] + <> arg ["-hidir" , buildDir "build"] + <> arg ["-stubdir" , buildDir "build"] + <> arg "-split-objs" + <> arg ("-c":srcs) + <> arg ["-o", out] From git at git.haskell.org Thu Oct 26 23:49:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert changes in Way.hs from #144. (697cba53) Message-ID: <20171026234900.E5E983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/697cba53396690ff295c15b09e03520d2fc07cd5/ghc >--------------------------------------------------------------- commit 697cba53396690ff295c15b09e03520d2fc07cd5 Author: Andrey Mokhov Date: Sun Jan 10 23:34:10 2016 +0000 Revert changes in Way.hs from #144. >--------------------------------------------------------------- 697cba53396690ff295c15b09e03520d2fc07cd5 src/Way.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Way.hs b/src/Way.hs index 974314c..3b1f6c0 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -72,7 +72,7 @@ instance Read Way where uniqueReads token = case reads token of [(unit, "")] -> Just unit _ -> Nothing - units = map uniqueReads . splitOn "_" $ s + units = map uniqueReads . words . replaceEq '_' ' ' $ s result = if Nothing `elem` units then [] else [(wayFromUnits . map fromJust $ units, "")] From git at git.haskell.org Thu Oct 26 23:49:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport `System.Console.ANSI` (f05d78d) Message-ID: <20171026234903.8C0603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f05d78d92e3fde319e2963806406074868a0a4f0/ghc >--------------------------------------------------------------- commit f05d78d92e3fde319e2963806406074868a0a4f0 Author: Ben Gamari Date: Thu Dec 24 14:32:38 2015 +0100 Base: Don't reexport `System.Console.ANSI` This wasn't even used it seems >--------------------------------------------------------------- f05d78d92e3fde319e2963806406074868a0a4f0 src/Base.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 3c62ed5..aa9861b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,7 +22,6 @@ module Base ( -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, - module System.Console.ANSI, -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, quote, chunksOfSize, From git at git.haskell.org Thu Oct 26 23:49:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (89c8f79) Message-ID: <20171026234904.0F3CE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/89c8f7943a320e688f3664b225c6ab21d7685bc2/ghc >--------------------------------------------------------------- commit 89c8f7943a320e688f3664b225c6ab21d7685bc2 Author: Andrey Mokhov Date: Sun Jan 11 13:10:20 2015 +0000 Clean up. >--------------------------------------------------------------- 89c8f7943a320e688f3664b225c6ab21d7685bc2 src/Ways.hs | 28 +++++++++++----------------- 1 file changed, 11 insertions(+), 17 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 843383e..368e449 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -30,9 +30,6 @@ data Way = Way } deriving Eq -instance Show Way where - show = tag - vanilla = Way "v" [] profiling = Way "p" [Profiling] logging = Way "l" [Logging] @@ -40,7 +37,6 @@ parallel = Way "mp" [Parallel] granSim = Way "gm" [GranSim] -- RTS only ways - threaded = Way "thr" [Threaded] threadedProfiling = Way "thr_p" [Threaded, Profiling] threadedLogging = Way "thr_l" [Threaded, Logging] @@ -71,22 +67,20 @@ defaultWays :: Stage -> Action [Way] defaultWays stage = do sharedLibs <- platformSupportsSharedLibs return $ [vanilla] - ++ [profiling | stage /= Stage0] - ++ [dynamic | sharedLibs ] + ++ [profiling | stage /= Stage0] + ++ [dynamic | sharedLibs ] wayHcArgs :: Way -> Args wayHcArgs (Way _ units) = - mconcat - [ when (Dynamic `notElem` units) $ arg ["-static"] - , when (Dynamic `elem` units) $ arg ["-fPIC", "-dynamic"] - , when (Threaded `elem` units) $ arg ["-optc-DTHREADED_RTS"] - , when (Debug `elem` units) $ arg ["-optc-DDEBUG"] - , when (Profiling `elem` units) $ arg ["-prof"] - , when (Logging `elem` units) $ arg ["-eventlog"] - , when (Parallel `elem` units) $ arg ["-parallel"] - , when (GranSim `elem` units) $ arg ["-gransim"] - , when (units == [Debug] || units == [Debug, Dynamic]) $ arg ["-ticky", "-DTICKY_TICKY"] - ] + when (Dynamic `notElem` units) (arg "-static") + <> when (Dynamic `elem` units) (arg ["-fPIC", "-dynamic"]) + <> when (Threaded `elem` units) (arg "-optc-DTHREADED_RTS") + <> when (Debug `elem` units) (arg "-optc-DDEBUG") + <> when (Profiling `elem` units) (arg "-prof") + <> when (Logging `elem` units) (arg "-eventlog") + <> when (Parallel `elem` units) (arg "-parallel") + <> when (GranSim `elem` units) (arg "-gransim") + <> when (units == [Debug] || units == [Debug, Dynamic]) (arg ["-ticky", "-DTICKY_TICKY"]) suffix :: Way -> String suffix way | way == vanilla = "" From git at git.haskell.org Thu Oct 26 23:49:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting. (016a71f) Message-ID: <20171026234904.E3F3A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/016a71fbb371e2e726ec13e665510bf680dce5cb/ghc >--------------------------------------------------------------- commit 016a71fbb371e2e726ec13e665510bf680dce5cb Author: Andrey Mokhov Date: Sun Jan 10 23:37:20 2016 +0000 Fix formatting. >--------------------------------------------------------------- 016a71fbb371e2e726ec13e665510bf680dce5cb build.bat | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/build.bat b/build.bat index 0cf778a..348537d 100644 --- a/build.bat +++ b/build.bat @@ -1,16 +1,16 @@ @cd %~dp0 @mkdir .shake 2> nul - at set ghcArgs=--make ^ - -Wall ^ + at set ghcArgs=--make ^ + -Wall ^ -fno-warn-name-shadowing ^ - src/Main.hs ^ - -isrc ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=.shake ^ - -j ^ - -O ^ + src/Main.hs ^ + -isrc ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=.shake ^ + -j ^ + -O ^ -o .shake/build @set shakeArgs=--lint ^ From git at git.haskell.org Thu Oct 26 23:49:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Eliminate re-exports from `Predicates` (74fb3f9) Message-ID: <20171026234908.0180F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/74fb3f9e869300335ba2b8ed831b792a64696877/ghc >--------------------------------------------------------------- commit 74fb3f9e869300335ba2b8ed831b792a64696877 Author: Ben Gamari Date: Thu Dec 24 14:31:07 2015 +0100 Eliminate re-exports from `Predicates` >--------------------------------------------------------------- 74fb3f9e869300335ba2b8ed831b792a64696877 src/Predicates.hs | 5 +---- src/Rules/Library.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 1 + src/Settings/Packages.hs | 2 ++ src/Settings/User.hs | 2 +- src/Settings/Ways.hs | 1 + 6 files changed, 8 insertions(+), 7 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index abaa4be..28dd51a 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,7 +1,5 @@ +-- | Convenient predicates module Predicates ( - module GHC, - module Oracles.Config.Flag, - module Oracles.Config.Setting, stage, package, builder, stagedBuilder, file, way, stage0, stage1, stage2, notStage0, notPackage, registerPackage, splitObjects ) where @@ -10,7 +8,6 @@ import Base import Expression import GHC import Oracles.Config.Flag -import Oracles.Config.Setting -- Basic predicates stage :: Stage -> Predicate diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index eeef3ab..76fe872 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -2,8 +2,8 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Data.Char -import Base -import Expression hiding (splitPath) +import Base hiding (splitPath) +import Expression import GHC import Oracles import Predicates (splitObjects) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index ead473e..c8226fc 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -2,6 +2,7 @@ module Settings.Builders.Haddock (haddockArgs) where import Development.Shake.FilePath import Base +import GHC import Package import Expression import Oracles diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index cd856b8..61457cb 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -2,7 +2,9 @@ module Settings.Packages (getPackages, knownPackages, findKnownPackage) where import Base import Expression +import GHC import Predicates +import Oracles.Config.Setting import Settings.User -- Combining default list of packages with user modifications diff --git a/src/Settings/User.hs b/src/Settings/User.hs index e16fb27..cad2578 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -6,8 +6,8 @@ module Settings.User ( verboseCommands, turnWarningsIntoErrors ) where +import GHC import Expression -import Predicates -- No user-specific settings by default -- TODO: rename to userArgs diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 8484575..8376213 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -4,6 +4,7 @@ import Data.Monoid import Expression import Predicates import Settings.User +import Oracles.Config.Flag -- TODO: use a single expression Ways parameterised by package instead of -- expressions libWays and rtsWays From git at git.haskell.org Thu Oct 26 23:49:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor duplicated code into pathArgs, outputArgs and includeArgs functions. (9fbf3c8) Message-ID: <20171026234907.F40563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9fbf3c8c37ac973da0574bd4a3dbe7bb2c012a32/ghc >--------------------------------------------------------------- commit 9fbf3c8c37ac973da0574bd4a3dbe7bb2c012a32 Author: Andrey Mokhov Date: Sun Jan 11 13:33:27 2015 +0000 Refactor duplicated code into pathArgs, outputArgs and includeArgs functions. >--------------------------------------------------------------- 9fbf3c8c37ac973da0574bd4a3dbe7bb2c012a32 src/Package/Base.hs | 26 +++++++++++++++++++++----- src/Package/Compile.hs | 14 +++----------- src/Package/Dependencies.hs | 13 +++---------- 3 files changed, 27 insertions(+), 26 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 4ef03fb..d1bf6ac 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -8,6 +8,7 @@ module Package.Base ( defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, bootPkgConstraints, + pathArgs, outputArgs, packageArgs, includeArgs, srcArgs ) where @@ -77,6 +78,15 @@ bootPkgConstraints = mempty -- $(foreach p,$(basename $(notdir $(wildcard libraries/$d/*.cabal))),\ -- --constraint "$p == $(shell grep -i "^Version:" libraries/$d/$p.cabal | sed "s/[^0-9.]//g")")) +pathArgs :: ShowArgs a => String -> FilePath -> a -> Args +pathArgs prefix path as = map includePath <$> arg as + where + includePath dir | isRelative dir = prefix ++ normaliseEx (path dir) + | isAbsolute dir = prefix normaliseEx dir + +outputArgs :: [String] -> FilePath -> Args +outputArgs keys dir = arg $ concatMap (\k -> [k, normaliseEx dir]) keys + packageArgs :: Stage -> FilePath -> Args packageArgs stage pkgData = do usePackageKey <- SupportsPackageKey || stage /= Stage0 @@ -89,11 +99,17 @@ packageArgs stage pkgData = do keyArgs False = prefixArgs "-package-name" (PackageKey pkgData) <> prefixArgs "-package" (Deps pkgData) -includeArgs :: ShowArgs a => String -> FilePath -> a -> Args -includeArgs prefix path as = map includePath <$> arg as - where - includePath dir | isRelative dir = prefix ++ path dir - | isAbsolute dir = prefix dir +includeArgs :: FilePath -> FilePath -> Args +includeArgs path dist = + let buildDir = path dist + pkgData = buildDir "package-data.mk" + in arg "-i" + <> pathArgs "-i" path (SrcDirs pkgData) + <> pathArgs "-i" buildDir ["build", "build/autogen"] + <> pathArgs "-I" buildDir ["build", "build/autogen"] + <> pathArgs "-I" path (IncludeDirs pkgData) + <> arg "-optP-include" -- TODO: Shall we also add -cpp? + <> pathArgs "-optP" buildDir "build/autogen/cabal_macros.h" srcArgs :: FilePath -> FilePath -> Args srcArgs path pkgData = do diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 0733a46..14296c0 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -21,23 +21,15 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = need [depFile] depContents <- parseMakefile <$> (liftIO $ readFile depFile) let deps = concat $ snd $ unzip $ filter ((== out) . fst) depContents - srcs = filter ("//*hs" ?==) deps + srcs = filter ("//*hs" ?==) deps -- TODO: handle *.c sources need deps run (Ghc stage) $ suffixArgs way <> wayHcArgs way <> arg SrcHcOpts <> packageArgs stage pkgData - <> arg "-i" - <> includeArgs "-i" path (SrcDirs pkgData) - <> includeArgs "-i" buildDir ["build", "build/autogen"] - <> includeArgs "-I" buildDir ["build", "build/autogen"] - <> includeArgs "-I" path (IncludeDirs pkgData) - <> arg "-optP-include" -- TODO: Shall we also add -cpp? - <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") + <> includeArgs path dist <> arg ["-Wall", "-XHaskell2010", "-O2"] -- TODO: now we have both -O and -O2 - <> arg ["-odir" , buildDir "build"] - <> arg ["-hidir" , buildDir "build"] - <> arg ["-stubdir" , buildDir "build"] + <> outputArgs ["-odir", "-hidir", "-stubdir"] (buildDir "build") <> arg "-split-objs" <> arg ("-c":srcs) <> arg ["-o", out] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 26b154f..18c2015 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -12,16 +12,9 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = need ["shake/src/Package/Dependencies.hs"] -- Track changes in this file run (Ghc stage) $ arg "-M" <> packageArgs stage pkgData - <> arg "-i" - <> includeArgs "-i" path (SrcDirs pkgData) - <> includeArgs "-i" buildDir ["build", "build/autogen"] - <> includeArgs "-I" buildDir ["build", "build/autogen"] - <> includeArgs "-I" path (IncludeDirs pkgData) - <> arg "-optP-include" -- TODO: Shall we also add -cpp? - <> arg ("-optP" ++ buildDir "build/autogen/cabal_macros.h") - <> arg ["-odir" , buildDir "build"] - <> arg ["-stubdir" , buildDir "build"] - <> arg ["-dep-makefile", out ] + <> includeArgs path dist + <> outputArgs ["-odir", "-stubdir"] (buildDir "build") + <> arg ["-dep-makefile", out] <> prefixArgs "-dep-suffix" (map suffix <$> ways settings) <> srcArgs path pkgData -- <> arg SrcHcOpts -- TODO: Check that skipping all _HC_OPTS is safe. From git at git.haskell.org Thu Oct 26 23:49:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -fno-warn-name-shadowing to cabal file. (91622d3) Message-ID: <20171026234908.EEC3A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91622d38572cd63c4c94e11f81cff321f01a83d3/ghc >--------------------------------------------------------------- commit 91622d38572cd63c4c94e11f81cff321f01a83d3 Author: Andrey Mokhov Date: Mon Jan 11 00:49:50 2016 +0000 Add -fno-warn-name-shadowing to cabal file. See #143. [skip ci] >--------------------------------------------------------------- 91622d38572cd63c4c94e11f81cff321f01a83d3 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 1f7cfc1..a7b3352 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -122,4 +122,4 @@ executable ghc-shake , transformers >= 0.4 , unordered-containers >= 0.2 default-language: Haskell2010 - ghc-options: -Wall -rtsopts -with-rtsopts=-I0 -j + ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j From git at git.haskell.org Thu Oct 26 23:49:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an infix version of when (). (f913c35) Message-ID: <20171026234911.B27A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f913c3580b486bf0c0aaf42fdc5090668cb63ab2/ghc >--------------------------------------------------------------- commit f913c3580b486bf0c0aaf42fdc5090668cb63ab2 Author: Andrey Mokhov Date: Sun Jan 11 15:15:29 2015 +0000 Add an infix version of when (). >--------------------------------------------------------------- f913c3580b486bf0c0aaf42fdc5090668cb63ab2 src/Oracles/Flag.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 354b1d7..946c4fb 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -4,7 +4,7 @@ module Oracles.Flag ( module Control.Monad, module Prelude, Flag (..), - test, when, unless, not, (&&), (||) + test, when, unless, not, (&&), (||), () ) where import Control.Monad hiding (when, unless) @@ -60,6 +60,10 @@ unless x act = do bool <- toCondition x if bool then mempty else act +-- Infix version of when +() :: (ToCondition a, Monoid m) => a -> Action m -> Action m +() = when + class Not a where type NotResult a not :: a -> NotResult a From git at git.haskell.org Thu Oct 26 23:49:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Expression: Don't re-export Base (ac5040d) Message-ID: <20171026234911.D7F353A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ac5040d2125aa94ecc25ba04dcda443e74a7d232/ghc >--------------------------------------------------------------- commit ac5040d2125aa94ecc25ba04dcda443e74a7d232 Author: Ben Gamari Date: Thu Dec 24 14:11:57 2015 +0100 Expression: Don't re-export Base The beginning of a long journey towards minimal re-exports >--------------------------------------------------------------- ac5040d2125aa94ecc25ba04dcda443e74a7d232 src/Expression.hs | 1 - src/Oracles/ArgsHash.hs | 1 + src/Predicates.hs | 1 + src/Rules.hs | 1 + src/Rules/Actions.hs | 1 + src/Rules/Cabal.hs | 1 + src/Rules/Compile.hs | 1 + src/Rules/Data.hs | 1 + src/Rules/Dependencies.hs | 1 + src/Rules/Documentation.hs | 1 + src/Rules/Generate.hs | 1 + src/Rules/Generators/ConfigHs.hs | 1 + src/Rules/Generators/GhcAutoconfH.hs | 1 + src/Rules/Generators/GhcBootPlatformH.hs | 1 + src/Rules/Generators/GhcPlatformH.hs | 1 + src/Rules/Generators/VersionHs.hs | 1 + src/Rules/Install.hs | 1 + src/Rules/Library.hs | 1 + src/Rules/Program.hs | 1 + src/Settings.hs | 7 ++++--- src/Settings/Args.hs | 2 ++ src/Settings/Builders/Ar.hs | 1 + src/Settings/Builders/DeriveConstants.hs | 1 + src/Settings/Builders/Gcc.hs | 2 ++ src/Settings/Builders/Ghc.hs | 1 + src/Settings/Builders/GhcCabal.hs | 14 ++++++++++++++ src/Settings/Builders/GhcPkg.hs | 2 ++ src/Settings/Builders/Haddock.hs | 3 +++ src/Settings/Builders/Hsc2Hs.hs | 4 ++++ src/Settings/Packages.hs | 1 + src/Settings/TargetDirectory.hs | 1 + src/Settings/Ways.hs | 1 + 32 files changed, 55 insertions(+), 4 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ac5040d2125aa94ecc25ba04dcda443e74a7d232 From git at git.haskell.org Thu Oct 26 23:49:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add productArgs and concatArgs helper functions. (018f850) Message-ID: <20171026234915.A64293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/018f8501c40e1c8b70da99c2b836750e9815f75d/ghc >--------------------------------------------------------------- commit 018f8501c40e1c8b70da99c2b836750e9815f75d Author: Andrey Mokhov Date: Sun Jan 11 17:01:02 2015 +0000 Add productArgs and concatArgs helper functions. >--------------------------------------------------------------- 018f8501c40e1c8b70da99c2b836750e9815f75d src/Base.hs | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 38790e6..b84b48c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,12 +12,12 @@ module Base ( Condition (..), (<+>), filterOut, - prefixArgs + productArgs, concatArgs ) where -import Development.Shake +import Development.Shake hiding ((*>)) import Development.Shake.FilePath -import Control.Applicative hiding ((*>)) +import Control.Applicative import Data.Function import Data.Monoid import Data.List @@ -32,9 +32,10 @@ instance Monoid a => Monoid (Action a) where mempty = return mempty mappend p q = mappend <$> p <*> q +-- Using the Creators' trick for overlapping String instances class ShowArgs a where showArgs :: a -> Args - showListArgs :: [a] -> Args -- the Creators' trick for overlapping String instances + showListArgs :: [a] -> Args showListArgs = mconcat . map showArgs instance ShowArgs Char where @@ -62,8 +63,18 @@ filterOut as exclude = do exclude' <- showArgs exclude filter (`notElem` exclude') <$> as --- Prefix each arg in a collection with a given prefix -prefixArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args -prefixArgs prefix as = do - prefix' <- showArgs prefix - concatMap (\a -> prefix' ++ [a]) <$> showArgs as +-- Generate a cross product collection of two argument collections +-- Example: productArgs ["-a", "-b"] "c" = arg ["-a", "c", "-b", "c"] +productArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args +productArgs as bs = do + as' <- showArgs as + bs' <- showArgs bs + return $ concat $ sequence [as', bs'] + +-- Similar to productArgs but concat resulting arguments pairwise +-- Example: concatArgs ["-a", "-b"] "c" = arg ["-ac", "-bc"] +concatArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args +concatArgs as bs = do + as' <- showArgs as + bs' <- showArgs bs + return $ map concat $ sequence [as', bs'] From git at git.haskell.org Thu Oct 26 23:49:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Builder: Add haddocks (30484e2) Message-ID: <20171026234915.E87153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30484e290251d2b765f409fb2498fd770b987bc6/ghc >--------------------------------------------------------------- commit 30484e290251d2b765f409fb2498fd770b987bc6 Author: Ben Gamari Date: Thu Dec 24 14:47:19 2015 +0100 Builder: Add haddocks >--------------------------------------------------------------- 30484e290251d2b765f409fb2498fd770b987bc6 src/Builder.hs | 17 +++++++++-------- 1 file changed, 9 insertions(+), 8 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 78f8376..0174dad 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -10,12 +10,12 @@ import GHC.Generics (Generic) import Oracles import Stage --- A Builder is an external command invoked in separate process using Shake.cmd +-- | A 'Builder' is an external command invoked in separate process using 'Shake.cmd' -- --- Ghc Stage0 is the bootstrapping compiler --- Ghc StageN, N > 0, is the one built on stage (N - 1) --- GhcPkg Stage0 is the bootstrapping GhcPkg --- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) +-- @Ghc Stage0@ is the bootstrapping compiler +-- @Ghc StageN@, N > 0, is the one built on stage (N - 1) +-- @GhcPkg Stage0@ is the bootstrapping @GhcPkg@ +-- @GhcPkg StageN@, N > 0, is the one built in Stage0 (TODO: need only Stage1?) -- TODO: Do we really need HsCpp builder? Can't we use a generic Cpp -- builder instead? It would also be used instead of GccM. -- TODO: rename Gcc to CCompiler? We sometimes use gcc and sometimes clang. @@ -73,7 +73,8 @@ builderKey builder = case builder of Objdump -> "objdump" Unlit -> "unlit" --- TODO: Paths to some builders should be determined using defaultProgramPath +-- | Determine the location of a 'Builder' +-- TODO: Paths to some builders should be determined using 'defaultProgramPath' builderPath :: Builder -> Action FilePath builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ @@ -87,8 +88,8 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- Make sure a builder exists on the given path and rebuild it if out of date. --- If laxDependencies is True then we do not rebuild GHC even if it is out of +-- | Make sure a builder exists on the given path and rebuild it if out of date. +-- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). needBuilder :: Bool -> Builder -> Action () needBuilder laxDependencies builder = do From git at git.haskell.org Thu Oct 26 23:49:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move bootstrapping.conf to .build. (24e6c28) Message-ID: <20171026234912.9A81D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/24e6c28e5884d49fbd408fe81fad9ca48c1f7f94/ghc >--------------------------------------------------------------- commit 24e6c28e5884d49fbd408fe81fad9ca48c1f7f94 Author: Andrey Mokhov Date: Mon Jan 11 01:29:35 2016 +0000 Move bootstrapping.conf to .build. See #113. >--------------------------------------------------------------- 24e6c28e5884d49fbd408fe81fad9ca48c1f7f94 shaking-up-ghc.cabal | 2 +- src/Base.hs | 13 ------------- src/Oracles/ModuleFiles.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Settings.hs | 4 ++-- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/{TargetDirectory.hs => Paths.hs} | 17 +++++++++++++---- 8 files changed, 20 insertions(+), 24 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index a7b3352..a091020 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -95,7 +95,7 @@ executable ghc-shake , Settings.Packages.RunGhc , Settings.Packages.Touchy , Settings.Packages.Unlit - , Settings.TargetDirectory + , Settings.Paths , Settings.User , Settings.Ways , Stage diff --git a/src/Base.hs b/src/Base.hs index 4b6ad10..8786c26 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -18,7 +18,6 @@ module Base ( -- * Paths shakeFilesPath, configPath, sourcePath, programInplacePath, bootPackageConstraints, packageDependencies, - packageConfiguration, packageConfigurationInitialised, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, @@ -44,7 +43,6 @@ import qualified System.Directory as IO import System.IO -- TODO: reexport Stage, etc.? -import Stage -- Build system files and paths shakePath :: FilePath @@ -71,17 +69,6 @@ bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" packageDependencies :: FilePath packageDependencies = shakeFilesPath -/- "package-dependencies" --- TODO: move to buildRootPath, see #113 -packageConfiguration :: Stage -> FilePath -packageConfiguration Stage0 = "libraries/bootstrapping.conf" -packageConfiguration _ = "inplace/lib/package.conf.d" - --- StageN, N > 0, share the same packageConfiguration (see above) -packageConfigurationInitialised :: Stage -> FilePath -packageConfigurationInitialised stage = - shakeFilesPath -/- "package-configuration-initialised-" - ++ stageString (min stage Stage1) - -- Utility functions -- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 33f6138..391990e 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -5,7 +5,7 @@ import Base import Oracles.PackageData import Package import Stage -import Settings.TargetDirectory +import Settings.Paths newtype ModuleFilesKey = ModuleFilesKey ([String], [FilePath]) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 93a121b..7e811ba 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -7,7 +7,7 @@ import Oracles import Rules.Actions import Settings.Builders.Common import Settings.Packages.Rts -import Settings.TargetDirectory +import Settings.Paths import Settings.User -- TODO: this should be moved elsewhere diff --git a/src/Settings.hs b/src/Settings.hs index 229a2f9..12830ca 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,6 +1,6 @@ module Settings ( module Settings.Packages, - module Settings.TargetDirectory, + module Settings.Paths, module Settings.User, module Settings.Ways, getPkgData, getPkgDataList, getTopDirectory, programPath, isLibrary, @@ -12,7 +12,7 @@ import Expression import Oracles import Oracles.ModuleFiles import Settings.Packages -import Settings.TargetDirectory +import Settings.Paths import Settings.User import Settings.Ways diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs index 43b9455..c1f1435 100644 --- a/src/Settings/Builders/HsCpp.hs +++ b/src/Settings/Builders/HsCpp.hs @@ -5,7 +5,7 @@ import GHC import Oracles import Predicates (builder) import Settings.Builders.GhcCabal -import Settings.TargetDirectory +import Settings.Paths hsCppBuilderArgs :: Args hsCppBuilderArgs = builder HsCpp ? do diff --git a/src/Settings/Packages/Ghc.hs b/src/Settings/Packages/Ghc.hs index 0830cb6..a7936e9 100644 --- a/src/Settings/Packages/Ghc.hs +++ b/src/Settings/Packages/Ghc.hs @@ -4,7 +4,7 @@ import Expression import GHC (ghc, compiler) import Oracles.Config.Setting import Predicates (builder, builderGhc, package, notStage0) -import Settings.TargetDirectory +import Settings.Paths ghcPackageArgs :: Args ghcPackageArgs = package ghc ? do diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/Paths.hs similarity index 73% rename from src/Settings/TargetDirectory.hs rename to src/Settings/Paths.hs index 6bbef72..bec143b 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/Paths.hs @@ -1,14 +1,12 @@ -module Settings.TargetDirectory ( +module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgGhciLibraryFile + pkgGhciLibraryFile, packageConfiguration, packageConfigurationInitialised ) where import Base import Expression import Settings.User --- TODO: rename to Settings.Paths as part of #113 - -- User can override the default target directory settings given below targetDirectory :: Stage -> Package -> FilePath targetDirectory = userTargetDirectory @@ -41,3 +39,14 @@ pkgLibraryFile stage pkg componentId way = do pkgGhciLibraryFile :: Stage -> Package -> String -> FilePath pkgGhciLibraryFile stage pkg componentId = targetPath stage pkg -/- "build" -/- "HS" ++ componentId <.> "o" + +-- TODO: move to buildRootPath, see #113 +packageConfiguration :: Stage -> FilePath +packageConfiguration Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" +packageConfiguration _ = "inplace/lib/package.conf.d" + +-- StageN, N > 0, share the same packageConfiguration (see above) +packageConfigurationInitialised :: Stage -> FilePath +packageConfigurationInitialised stage = + shakeFilesPath -/- "package-configuration-initialised-" + ++ stageString (min stage Stage1) From git at git.haskell.org Thu Oct 26 23:49:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update Setting.hs (55b0d41) Message-ID: <20171026234916.494E63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/55b0d414555297fc845a3ed0196accd5ab454890/ghc >--------------------------------------------------------------- commit 55b0d414555297fc845a3ed0196accd5ab454890 Author: Moritz Angermann Date: Mon Jan 11 11:19:18 2016 +0800 Update Setting.hs Set a sensible default `cmdLineLengthLimit` for os x. >--------------------------------------------------------------- 55b0d414555297fc845a3ed0196accd5ab454890 src/Oracles/Config/Setting.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 0047f03..46d0d33 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -166,6 +166,9 @@ cmdLineLengthLimit = do return $ case (windows, osx) of -- windows (True, False) -> 31000 - -- osx 262144 is ARG_MAX, 33166 experimentally determined - (False, True) -> 262144 - 33166 + -- osx 262144 is ARG_MAX + -- yet when using `xargs` on osx this is reduced by over 20 000. + -- 200 000 seems like a sensible limit. + (False, True) -> 200000 + -- On all other systems, we try this: _ -> 4194304 -- Cabal needs a bit more than 2MB! From git at git.haskell.org Thu Oct 26 23:49:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor, limit lines at 80 characters. (128c5ac) Message-ID: <20171026234919.BA1E83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4/ghc >--------------------------------------------------------------- commit 128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4 Author: Andrey Mokhov Date: Sun Jan 11 17:02:58 2015 +0000 Refactor, limit lines at 80 characters. >--------------------------------------------------------------- 128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4 src/Package/Base.hs | 70 ++++++++++++++++++++++----------------------- src/Package/Compile.hs | 39 +++++++++++++++++++------ src/Package/Data.hs | 39 +++++++++++++++---------- src/Package/Dependencies.hs | 18 ++++++------ 4 files changed, 99 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 128c5acbbf6bff7ba4ac5b0e03e533e0666f8ae4 From git at git.haskell.org Thu Oct 26 23:49:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GhcCabal: Simplify imports (0be2c4b) Message-ID: <20171026234919.DAC8F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0be2c4bb4b02cb74322191e72b042688603af5b4/ghc >--------------------------------------------------------------- commit 0be2c4bb4b02cb74322191e72b042688603af5b4 Author: Ben Gamari Date: Thu Dec 24 14:44:16 2015 +0100 GhcCabal: Simplify imports >--------------------------------------------------------------- 0be2c4bb4b02cb74322191e72b042688603af5b4 src/Settings/Builders/GhcCabal.hs | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 7905a2c..bd95cfc 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -3,13 +3,7 @@ module Settings.Builders.GhcCabal ( customPackageArgs, ccArgs, cppArgs, ccWarnings, argStagedSettingList, needDll0 ) where -import Data.Monoid -import Control.Monad.Trans.Class -import Control.Monad.Extra - -import Development.Shake -import Development.Shake.FilePath -import Base ((-/-), bootPackageConstraints) +import Base import Oracles.Config.Setting import Oracles.Config.Flag import GHC From git at git.haskell.org Thu Oct 26 23:49:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #150 from snowleopard/angerman-patch-1 (754ed41) Message-ID: <20171026234920.6A74F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/754ed41f02f404dc0b735df8f48e855a12f2248f/ghc >--------------------------------------------------------------- commit 754ed41f02f404dc0b735df8f48e855a12f2248f Merge: 24e6c28 55b0d41 Author: Andrey Mokhov Date: Mon Jan 11 03:31:50 2016 +0000 Merge pull request #150 from snowleopard/angerman-patch-1 Update Setting.hs >--------------------------------------------------------------- 754ed41f02f404dc0b735df8f48e855a12f2248f src/Oracles/Config/Setting.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) From git at git.haskell.org Thu Oct 26 23:49:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify: Package -> TodoItem -> Rules () is a monoid! (56689f0) Message-ID: <20171026234923.AD02A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56689f0356383efb1cb285138cdd6b2a57d0fc11/ghc >--------------------------------------------------------------- commit 56689f0356383efb1cb285138cdd6b2a57d0fc11 Author: Andrey Mokhov Date: Sun Jan 11 19:25:46 2015 +0000 Simplify: Package -> TodoItem -> Rules () is a monoid! >--------------------------------------------------------------- 56689f0356383efb1cb285138cdd6b2a57d0fc11 src/Package.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 8f2850d..2fd10f1 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -11,12 +11,11 @@ import Package.Dependencies packages :: [Package] packages = [libraryPackage "deepseq" Stage1 defaultSettings] --- Rule buildXY is defined in module X.Y +-- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () -buildPackage pkg todoItem = do - buildPackageData pkg todoItem - buildPackageDependencies pkg todoItem - buildPackageCompile pkg todoItem +buildPackage = buildPackageData + <> buildPackageDependencies + <> buildPackageCompile packageRules :: Rules () packageRules = do From git at git.haskell.org Thu Oct 26 23:49:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #36 from bgamari/reexport (84af166) Message-ID: <20171026234923.E8C753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84af1661707ed82d1b378d02ce712ecc212535f5/ghc >--------------------------------------------------------------- commit 84af1661707ed82d1b378d02ce712ecc212535f5 Merge: 58d7fcc 30484e2 Author: Andrey Mokhov Date: Mon Dec 28 13:09:27 2015 +0000 Merge pull request #36 from bgamari/reexport Begin paring down reexports >--------------------------------------------------------------- 84af1661707ed82d1b378d02ce712ecc212535f5 src/Base.hs | 11 ++--------- src/Builder.hs | 19 +++++++++++-------- src/Expression.hs | 3 ++- src/Oracles/ArgsHash.hs | 1 + src/Oracles/Config.hs | 1 + src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 2 ++ src/Oracles/PackageData.hs | 1 + src/Oracles/WindowsRoot.hs | 1 + src/Predicates.hs | 6 ++---- src/Rules.hs | 1 + src/Rules/Actions.hs | 1 + src/Rules/Cabal.hs | 1 + src/Rules/Compile.hs | 1 + src/Rules/Data.hs | 1 + src/Rules/Dependencies.hs | 2 ++ src/Rules/Documentation.hs | 1 + src/Rules/Generate.hs | 1 + src/Rules/Generators/ConfigHs.hs | 1 + src/Rules/Generators/GhcAutoconfH.hs | 1 + src/Rules/Generators/GhcBootPlatformH.hs | 1 + src/Rules/Generators/GhcPlatformH.hs | 1 + src/Rules/Generators/VersionHs.hs | 1 + src/Rules/Install.hs | 1 + src/Rules/Library.hs | 5 ++++- src/Rules/Program.hs | 3 +++ src/Settings.hs | 7 ++++--- src/Settings/Args.hs | 2 ++ src/Settings/Builders/Ar.hs | 1 + src/Settings/Builders/DeriveConstants.hs | 1 + src/Settings/Builders/Gcc.hs | 2 ++ src/Settings/Builders/Ghc.hs | 1 + src/Settings/Builders/GhcCabal.hs | 8 ++++++++ src/Settings/Builders/GhcPkg.hs | 2 ++ src/Settings/Builders/Haddock.hs | 4 ++++ src/Settings/Builders/Hsc2Hs.hs | 4 ++++ src/Settings/Packages.hs | 3 +++ src/Settings/TargetDirectory.hs | 1 + src/Settings/User.hs | 2 +- src/Settings/Ways.hs | 2 ++ src/Target.hs | 2 ++ 41 files changed, 85 insertions(+), 27 deletions(-) From git at git.haskell.org Thu Oct 26 23:49:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, add a Test module with selftest (28c706d) Message-ID: <20171026234924.886263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28c706da832e79687af29b9d64289d6a57b53adf/ghc >--------------------------------------------------------------- commit 28c706da832e79687af29b9d64289d6a57b53adf Author: Neil Mitchell Date: Mon Jan 11 10:47:41 2016 +0000 #146, add a Test module with selftest >--------------------------------------------------------------- 28c706da832e79687af29b9d64289d6a57b53adf shaking-up-ghc.cabal | 3 +++ src/Main.hs | 4 +++- src/Test.hs | 19 +++++++++++++++++++ src/Way.hs | 2 +- 4 files changed, 26 insertions(+), 2 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index a091020..132e84d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -100,6 +100,7 @@ executable ghc-shake , Settings.Ways , Stage , Target + , Test , Way default-extensions: BangPatterns @@ -111,6 +112,7 @@ executable ghc-shake , FlexibleInstances , OverloadedStrings , RecordWildCards + , ScopedTypeVariables build-depends: base , ansi-terminal >= 0.6 , Cabal >= 1.22 @@ -118,6 +120,7 @@ executable ghc-shake , directory >= 1.2 , extra >= 1.4 , mtl >= 2.2 + , QuickCheck >= 2.6 , shake >= 0.15 , transformers >= 0.4 , unordered-containers >= 0.2 diff --git a/src/Main.hs b/src/Main.hs index 63dbd7c..dea793e 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -11,6 +11,7 @@ import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl +import qualified Test main :: IO () main = shakeArgs options rules @@ -25,7 +26,8 @@ main = shakeArgs options rules , Rules.Gmp.gmpRules , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules - , Rules.packageRules ] + , Rules.packageRules + , Test.testRules ] options = shakeOptions { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple diff --git a/src/Test.hs b/src/Test.hs new file mode 100644 index 0000000..75b1b5d --- /dev/null +++ b/src/Test.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE ScopedTypeVariables #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} + +module Test (testRules) where + +import Way +import Development.Shake +import Test.QuickCheck + +instance Arbitrary Way where + arbitrary = wayFromUnits <$> arbitrary + +instance Arbitrary WayUnit where + arbitrary = arbitraryBoundedEnum + +testRules :: Rules () +testRules = + phony "selftest" $ do + liftIO $ quickCheck $ \(x :: Way) -> read (show x) == x diff --git a/src/Way.hs b/src/Way.hs index 3b1f6c0..ba20bd7 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,5 +1,5 @@ module Way ( - WayUnit (..), Way, wayUnit, + WayUnit (..), Way, wayUnit, wayFromUnits, vanilla, profiling, logging, parallel, granSim, threaded, threadedProfiling, threadedLogging, From git at git.haskell.org Thu Oct 26 23:49:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters. (d264db1) Message-ID: <20171026234927.540A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d264db1967999ff34350037afc0440128c7667d2/ghc >--------------------------------------------------------------- commit d264db1967999ff34350037afc0440128c7667d2 Author: Andrey Mokhov Date: Sun Jan 11 19:55:14 2015 +0000 Fit lines into 80 characters. >--------------------------------------------------------------- d264db1967999ff34350037afc0440128c7667d2 src/Ways.hs | 38 ++++++++++++++++++++++---------------- 1 file changed, 22 insertions(+), 16 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index 368e449..c6d733c 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -21,7 +21,14 @@ module Ways ( import Base import Oracles -data WayUnit = Profiling | Logging | Parallel | GranSim | Threaded | Debug | Dynamic deriving Eq +data WayUnit = Profiling + | Logging + | Parallel + | GranSim + | Threaded + | Debug + | Dynamic + deriving Eq data Way = Way { @@ -36,7 +43,7 @@ logging = Way "l" [Logging] parallel = Way "mp" [Parallel] granSim = Way "gm" [GranSim] --- RTS only ways +-- RTS only ways. TODO: do we need to define these here? threaded = Way "thr" [Threaded] threadedProfiling = Way "thr_p" [Threaded, Profiling] threadedLogging = Way "thr_l" [Threaded, Logging] @@ -60,9 +67,6 @@ allWays = [vanilla, profiling, logging, parallel, granSim, threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic] --- TODO: what are ways 't' and 's'? --- ALL_WAYS=v p t l s mp mg debug dyn thr thr_l p_dyn debug_dyn thr_dyn thr_p_dyn thr_debug_dyn thr_p thr_debug debug_p thr_debug_p l_dyn thr_l_dyn - defaultWays :: Stage -> Action [Way] defaultWays stage = do sharedLibs <- platformSupportsSharedLibs @@ -70,17 +74,19 @@ defaultWays stage = do ++ [profiling | stage /= Stage0] ++ [dynamic | sharedLibs ] +-- TODO: do '-ticky' in all debug ways? wayHcArgs :: Way -> Args wayHcArgs (Way _ units) = - when (Dynamic `notElem` units) (arg "-static") - <> when (Dynamic `elem` units) (arg ["-fPIC", "-dynamic"]) - <> when (Threaded `elem` units) (arg "-optc-DTHREADED_RTS") - <> when (Debug `elem` units) (arg "-optc-DDEBUG") - <> when (Profiling `elem` units) (arg "-prof") - <> when (Logging `elem` units) (arg "-eventlog") - <> when (Parallel `elem` units) (arg "-parallel") - <> when (GranSim `elem` units) (arg "-gransim") - <> when (units == [Debug] || units == [Debug, Dynamic]) (arg ["-ticky", "-DTICKY_TICKY"]) + (Dynamic `notElem` units) arg "-static" + <> (Dynamic `elem` units) arg ["-fPIC", "-dynamic"] + <> (Threaded `elem` units) arg "-optc-DTHREADED_RTS" + <> (Debug `elem` units) arg "-optc-DDEBUG" + <> (Profiling `elem` units) arg "-prof" + <> (Logging `elem` units) arg "-eventlog" + <> (Parallel `elem` units) arg "-parallel" + <> (GranSim `elem` units) arg "-gransim" + <> (units == [Debug] || units == [Debug, Dynamic]) + arg ["-ticky", "-DTICKY_TICKY"] suffix :: Way -> String suffix way | way == vanilla = "" @@ -94,7 +100,7 @@ hcsuf = (++ "hc") . suffix -- Detect way from a given extension. Fail if the result is not unique. detectWay :: FilePath -> Way detectWay extension = case solutions of - [way] -> way - otherwise -> error $ "Cannot detect way from extension '" ++ extension ++ "'." + [way] -> way + _ -> error $ "Cannot detect way from extension '" ++ extension ++ "'." where solutions = [w | f <- [hisuf, osuf, hcsuf], w <- allWays, f w == extension] From git at git.haskell.org Thu Oct 26 23:49:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export Data.Monoid from Expression. (024b562) Message-ID: <20171026234927.A8D9D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/024b5625e53789755a0af096b7a9438e8e33cc8c/ghc >--------------------------------------------------------------- commit 024b5625e53789755a0af096b7a9438e8e33cc8c Author: Andrey Mokhov Date: Mon Dec 28 14:28:36 2015 +0000 Re-export Data.Monoid from Expression. >--------------------------------------------------------------- 024b5625e53789755a0af096b7a9438e8e33cc8c src/Expression.hs | 2 ++ src/Rules/Program.hs | 2 +- 2 files changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Expression.hs b/src/Expression.hs index a83ea15..2b7ef9a 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -18,6 +18,7 @@ module Expression ( getInput, getOutput, -- * Re-exports + module Data.Monoid, module Builder, module Package, module Stage, @@ -25,6 +26,7 @@ module Expression ( ) where import Control.Monad.Trans.Reader +import Data.Monoid import Base import Package diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 781231f..0199071 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -3,7 +3,7 @@ module Rules.Program (buildProgram) where import Data.Char import Base -import Expression hiding (splitPath) +import Expression import GHC hiding (ghci) import Oracles import Rules.Actions From git at git.haskell.org Thu Oct 26 23:49:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, run the tests on Appveyor (70b40d9) Message-ID: <20171026234928.262353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/70b40d9e1ca12be3a3d7de28ee2e5ef8dcf7120c/ghc >--------------------------------------------------------------- commit 70b40d9e1ca12be3a3d7de28ee2e5ef8dcf7120c Author: Neil Mitchell Date: Mon Jan 11 10:47:49 2016 +0000 #146, run the tests on Appveyor >--------------------------------------------------------------- 70b40d9e1ca12be3a3d7de28ee2e5ef8dcf7120c .appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.appveyor.yml b/.appveyor.yml index f4f1d83..f0d0e69 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,4 +30,5 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build + - echo "" | stack --no-terminal exec -- build.bat selftest - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Thu Oct 26 23:49:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor oracle rules. (21e48fc) Message-ID: <20171026234931.839823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21e48fc51345e7294e1dd2a642a1c305230ceb2f/ghc >--------------------------------------------------------------- commit 21e48fc51345e7294e1dd2a642a1c305230ceb2f Author: Andrey Mokhov Date: Sun Jan 11 20:08:00 2015 +0000 Refactor oracle rules. >--------------------------------------------------------------- 21e48fc51345e7294e1dd2a642a1c305230ceb2f src/Oracles.hs | 34 ++++++++++++++++++++++------------ 1 file changed, 22 insertions(+), 12 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 3321610..3a0c430 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -17,31 +17,41 @@ import Oracles.Option import Oracles.Builder import Oracles.PackageData -oracleRules :: Rules () -oracleRules = do +defaultConfig, userConfig :: FilePath +defaultConfig = cfgPath "default.config" +userConfig = cfgPath "user.config" + +-- Oracle for configuration files. +configOracle :: Rules () +configOracle = do cfg <- newCache $ \() -> do - unless (doesFileExist $ cfgPath "default.config.in") $ do + unless (doesFileExist $ defaultConfig <.> "in") $ do error $ "\nDefault configuration file '" - ++ (cfgPath "default.config.in") + ++ (defaultConfig <.> "in") ++ "' is missing; unwilling to proceed." return () - need [cfgPath "default.config"] - cfgDefault <- liftIO $ readConfigFile $ cfgPath "default.config" - existsUser <- doesFileExist $ cfgPath "user.config" + need [defaultConfig] + cfgDefault <- liftIO $ readConfigFile defaultConfig + existsUser <- doesFileExist userConfig cfgUser <- if existsUser - then liftIO $ readConfigFile $ cfgPath "user.config" + then liftIO $ readConfigFile userConfig else do putLoud $ "\nUser defined configuration file '" - ++ (cfgPath "user.config") - ++ "' is missing; proceeding with default configuration.\n" + ++ userConfig ++ "' is missing; " + ++ "proceeding with default configuration.\n" return M.empty return $ cfgUser `M.union` cfgDefault - addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () + return () +-- Oracle for 'package-data.mk' files. +packageDataOracle :: Rules () +packageDataOracle = do pkgData <- newCache $ \file -> do need [file] liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () + +oracleRules :: Rules () +oracleRules = configOracle <> packageDataOracle From git at git.haskell.org Thu Oct 26 23:49:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use orderOnly dependencies for ordering ghc-cabal invocations (avoids unnecessary rebuilds). (804a5e2) Message-ID: <20171026234932.2C9C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/804a5e2ccc8a844f30b897fbe743b424b0cc7efb/ghc >--------------------------------------------------------------- commit 804a5e2ccc8a844f30b897fbe743b424b0cc7efb Author: Andrey Mokhov Date: Mon Dec 28 14:56:44 2015 +0000 Use orderOnly dependencies for ordering ghc-cabal invocations (avoids unnecessary rebuilds). >--------------------------------------------------------------- 804a5e2ccc8a844f30b897fbe743b424b0cc7efb src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index e0a6239..879dc1e 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -26,7 +26,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - need $ map (pkgDataFile stage) depPkgs + orderOnly $ map (pkgDataFile stage) depPkgs need [cabalFile] buildWithResources [(resGhcCabal rs, 1)] $ From git at git.haskell.org Thu Oct 26 23:49:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rewrite chunksOfSize so it doesn't go pear shaped on long inputs (763a518) Message-ID: <20171026234932.494163A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/763a518c64ec88acc29db8cc2f7b17955b02a6df/ghc >--------------------------------------------------------------- commit 763a518c64ec88acc29db8cc2f7b17955b02a6df Author: Neil Mitchell Date: Mon Jan 11 11:06:18 2016 +0000 Rewrite chunksOfSize so it doesn't go pear shaped on long inputs >--------------------------------------------------------------- 763a518c64ec88acc29db8cc2f7b17955b02a6df src/Settings/Builders/Ar.hs | 12 ++---------- 1 file changed, 2 insertions(+), 10 deletions(-) diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 86f4310..fc43d45 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -48,13 +48,5 @@ useSuccessiveInvocations path flagArgs fileArgs = do -- | @chunksOfSize size strings@ splits a given list of strings into chunks not -- exceeding the given @size at . chunksOfSize :: Int -> [String] -> [[String]] -chunksOfSize _ [] = [] -chunksOfSize size strings = reverse chunk : chunksOfSize size rest - where - (chunk, rest) = go [] 0 strings - go res _ [] = (res, []) - go res chunkSize (s:ss) = - if newSize > size then (res, s:ss) else go (s:res) newSize ss - where - newSize = chunkSize + length s - +chunksOfSize n = repeatedly f + where f xs = splitAt (max 1 $ length $ takeWhile (<= n) $ scanl1 (+) $ map length xs) xs From git at git.haskell.org Thu Oct 26 23:49:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, add a test helper (077bf47) Message-ID: <20171026234935.DFF523A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/077bf477e5059ccbff621ea59a439830890b8f1c/ghc >--------------------------------------------------------------- commit 077bf477e5059ccbff621ea59a439830890b8f1c Author: Neil Mitchell Date: Mon Jan 11 11:06:40 2016 +0000 #146, add a test helper >--------------------------------------------------------------- 077bf477e5059ccbff621ea59a439830890b8f1c src/Test.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Test.hs b/src/Test.hs index 75b1b5d..a55e6e6 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -16,4 +16,8 @@ instance Arbitrary WayUnit where testRules :: Rules () testRules = phony "selftest" $ do - liftIO $ quickCheck $ \(x :: Way) -> read (show x) == x + test $ \(x :: Way) -> read (show x) == x + + +test :: Testable a => a -> Action () +test = liftIO . quickCheck From git at git.haskell.org Thu Oct 26 23:49:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove postProcessPackageData from Util. (481caa8) Message-ID: <20171026234935.37FBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/481caa85874e966d8adc82dddde1313187647167/ghc >--------------------------------------------------------------- commit 481caa85874e966d8adc82dddde1313187647167 Author: Andrey Mokhov Date: Sun Jan 11 21:29:13 2015 +0000 Remove postProcessPackageData from Util. >--------------------------------------------------------------- 481caa85874e966d8adc82dddde1313187647167 src/Package/Data.hs | 12 ++++++++++++ src/Util.hs | 14 +------------- 2 files changed, 13 insertions(+), 13 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index e2260fd..eaaa072 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -43,6 +43,18 @@ configureArgs stage settings = <> when CrossCompiling (argConf "--host" TargetPlatformFull) <> argConf "--with-cc" Gcc +-- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: +-- 1) Drop lines containing '$' +-- 2) Replace '/' and '\' with '_' before '=' +postProcessPackageData :: FilePath -> Action () +postProcessPackageData file = do + pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) + length pkgData `seq` writeFileLines file $ map processLine pkgData + where + processLine line = replaceSeparators '_' prefix ++ suffix + where + (prefix, suffix) = break (== '=') line + buildPackageData :: Package -> TodoItem -> Rules () buildPackageData (Package name path _) (stage, dist, settings) = let pathDist = path dist diff --git a/src/Util.hs b/src/Util.hs index d7e98bd..f91ff79 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,7 +1,6 @@ module Util ( module Data.Char, - replaceIf, replaceEq, replaceSeparators, - postProcessPackageData + replaceIf, replaceEq, replaceSeparators ) where import Base @@ -16,14 +15,3 @@ replaceEq from = replaceIf (== from) replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator --- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: --- 1) Drop lines containing '$' --- 2) Replace '/' and '\' with '_' before '=' -postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map processLine pkgData - where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line From git at git.haskell.org Thu Oct 26 23:49:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: First step towards #60. (3e2cdc9) Message-ID: <20171026234935.D9EE93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e2cdc9ff449c85d96de67238835e0159b5b3724/ghc >--------------------------------------------------------------- commit 3e2cdc9ff449c85d96de67238835e0159b5b3724 Author: Andrey Mokhov Date: Mon Dec 28 15:58:06 2015 +0000 First step towards #60. >--------------------------------------------------------------- 3e2cdc9ff449c85d96de67238835e0159b5b3724 src/Settings/Args.hs | 13 ++++++++----- src/Settings/Builders/Alex.hs | 11 +---------- src/Settings/Packages/Compiler.hs | 9 +++++++++ 3 files changed, 18 insertions(+), 15 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 8aa0268..6715680 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -16,21 +16,20 @@ import Settings.Builders.Happy import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld +import Settings.Packages.Compiler import Settings.User getArgs :: Expr [String] -getArgs = fromDiffExpr $ defaultArgs <> userArgs +getArgs = fromDiffExpr $ defaultBuilderArgs <> defaultPackageArgs <> userArgs --- TODO: add all other settings -- TODO: add src-hc-args = -H32m -O -- TODO: GhcStage2HcOpts=-O2 unless GhcUnregisterised -- TODO: compiler/stage1/build/Parser_HC_OPTS += -O0 -fno-ignore-interface-pragmas -- TODO: compiler/main/GhcMake_HC_OPTS += -auto-all --- TODO: compiler_stage2_HADDOCK_OPTS += --optghc=-DSTAGE=2 -- TODO: compiler/prelude/PrimOp_HC_OPTS += -fforce-recomp -- TODO: is GhcHcOpts=-Rghc-timing needed? -defaultArgs :: Args -defaultArgs = mconcat +defaultBuilderArgs :: Args +defaultBuilderArgs = mconcat [ alexArgs , arArgs , cabalArgs @@ -48,3 +47,7 @@ defaultArgs = mconcat , hsc2HsArgs , hsCppArgs , ldArgs ] + +defaultPackageArgs :: Args +defaultPackageArgs = mconcat + [ compilerArgs ] diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs index 239ae85..086bf1b 100644 --- a/src/Settings/Builders/Alex.hs +++ b/src/Settings/Builders/Alex.hs @@ -1,18 +1,9 @@ module Settings.Builders.Alex (alexArgs) where import Expression -import GHC (compiler) -import Predicates (builder, package) +import Predicates (builder) alexArgs :: Args alexArgs = builder Alex ? mconcat [ arg "-g" - , package compiler ? arg "--latin1" , arg =<< getInput , arg "-o", arg =<< getOutput ] - --- TODO: separate arguments into builder-specific and package-specific --- compilierArgs = package compiler ? builder Alex ? arg "awe" - --- args = mconcat --- [ alexArgs --- , compilerArgs ] diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs new file mode 100644 index 0000000..2ade082 --- /dev/null +++ b/src/Settings/Packages/Compiler.hs @@ -0,0 +1,9 @@ +module Settings.Packages.Compiler (compilerArgs) where + +import Expression +import GHC (compiler) +import Predicates (builder, package) + +compilerArgs :: Args +compilerArgs = package compiler ? + mconcat [ builder Alex ? arg "--latin1" ] From git at git.haskell.org Thu Oct 26 23:49:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters. (d956739) Message-ID: <20171026234939.3FA613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d956739dd5d551fa4f0259966f2f0b0cce250bcd/ghc >--------------------------------------------------------------- commit d956739dd5d551fa4f0259966f2f0b0cce250bcd Author: Andrey Mokhov Date: Sun Jan 11 21:42:39 2015 +0000 Fit lines into 80 characters. >--------------------------------------------------------------- d956739dd5d551fa4f0259966f2f0b0cce250bcd src/Oracles/PackageData.hs | 20 ++++++++++++-------- 1 file changed, 12 insertions(+), 8 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index ba63612..6bffafd 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -12,21 +12,25 @@ import Util newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -data PackageData = Modules FilePath | SrcDirs FilePath | PackageKey FilePath - | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath +data PackageData = Modules FilePath + | SrcDirs FilePath + | PackageKey FilePath + | IncludeDirs FilePath + | Deps FilePath + | DepKeys FilePath instance ShowArgs PackageData where - showArgs key = do - let (keyName, file, ifEmpty) = case key of + showArgs packageData = do + let (key, file, defaultValue) = case packageData of Modules file -> ("MODULES" , file, "" ) SrcDirs file -> ("HS_SRC_DIRS" , file, ".") PackageKey file -> ("PACKAGE_KEY" , file, "" ) IncludeDirs file -> ("INCLUDE_DIRS", file, ".") Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) - keyFullName = replaceSeparators '_' $ takeDirectory file ++ "_" ++ keyName - res <- askOracle $ PackageDataKey (file, keyFullName) + fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key + res <- askOracle $ PackageDataKey (file, fullKey) return $ words $ case res of - Nothing -> error $ "\nCannot find key '" ++ keyName ++ "' in " ++ file ++ "." - Just "" -> ifEmpty + Nothing -> error $ "No key '" ++ key ++ "' in " ++ file ++ "." + Just "" -> defaultValue Just value -> value From git at git.haskell.org Thu Oct 26 23:49:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Target fields for printing out relevant build information. (f415ad1) Message-ID: <20171026234940.1CB523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f415ad1d528c29d0a1708e2406c4fabd99484e31/ghc >--------------------------------------------------------------- commit f415ad1d528c29d0a1708e2406c4fabd99484e31 Author: Andrey Mokhov Date: Tue Dec 29 15:39:52 2015 +0000 Use Target fields for printing out relevant build information. >--------------------------------------------------------------- f415ad1d528c29d0a1708e2406c4fabd99484e31 shaking-up-ghc.cabal | 1 + src/Builder.hs | 10 +++++++++- src/Rules/Actions.hs | 44 +++++++++++++++++--------------------------- 3 files changed, 27 insertions(+), 28 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 0e60637..f530894 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -84,6 +84,7 @@ executable ghc-shake , DeriveGeneric , FlexibleInstances , OverloadedStrings + , RecordWildCards build-depends: base , ansi-terminal >= 0.6 , Cabal >= 1.22 diff --git a/src/Builder.hs b/src/Builder.hs index 0174dad..b4b01c3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} module Builder ( - Builder (..), builderPath, getBuilderPath, specified, needBuilder + Builder (..), isStaged, builderPath, getBuilderPath, specified, needBuilder ) where import Control.Monad.Trans.Reader @@ -43,6 +43,14 @@ data Builder = Alex | Unlit deriving (Show, Eq, Generic) +isStaged :: Builder -> Bool +isStaged (Gcc _) = True +isStaged (GccM _) = True +isStaged (Ghc _) = True +isStaged (GhcM _) = True +isStaged (GhcPkg _) = True +isStaged _ = False + -- Configuration files refer to Builders as follows: builderKey :: Builder -> String builderKey builder = case builder of diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 086cb8e..8b243eb 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE RecordWildCards #-} module Rules.Actions (build, buildWithResources) where import Base @@ -22,9 +23,7 @@ buildWithResources rs target = do -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do - unless verbose $ do - putBuild $ renderBox $ [ "Running " ++ show builder ++ " with arguments:" ] - ++ map (" "++) (interestingInfo builder argList) + unless verbose $ putInfo target quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList @@ -46,28 +45,19 @@ buildWithResources rs target = do build :: Target -> Action () build = buildWithResources [] -interestingInfo :: Builder -> [String] -> [String] -interestingInfo builder ss = case builder of - Alex -> prefixAndSuffix 0 3 ss - Ar -> prefixAndSuffix 2 1 ss - DeriveConstants -> prefixAndSuffix 3 0 ss - Gcc _ -> prefixAndSuffix 0 4 ss - GccM _ -> prefixAndSuffix 0 1 ss - Ghc _ -> prefixAndSuffix 0 4 ss - GhcCabal -> prefixAndSuffix 3 0 ss - GhcM _ -> prefixAndSuffix 1 1 ss - GhcPkg _ -> prefixAndSuffix 3 0 ss - Haddock -> prefixAndSuffix 1 0 ss - Happy -> prefixAndSuffix 0 3 ss - Hsc2Hs -> prefixAndSuffix 0 3 ss - HsCpp -> prefixAndSuffix 0 1 ss - Ld -> prefixAndSuffix 4 0 ss - _ -> ss +-- Print out key information about the command being executed +putInfo :: Target.Target -> Action () +putInfo (Target.Target {..}) = putBuild $ renderBox $ + [ "Running " ++ show builder + ++ " (" ++ stageInfo + ++ "package = " ++ pkgNameString package + ++ wayInfo ++ "):" + , " input: " ++ digest inputs + , "=> output: " ++ digest outputs ] where - prefixAndSuffix n m list = - let len = length list in - if len <= n + m + 1 - then list - else take n list - ++ ["... skipping " ++ show (len - n - m) ++ " arguments ..."] - ++ drop (len - m) list + stageInfo = if isStaged builder then "" else "stage = " ++ show stage ++ ", " + wayInfo = if way == vanilla then "" else ", way = " ++ show way + digest list = case list of + [] -> "none" + [x] -> x + xs -> head xs ++ " (and " ++ show (length xs - 1) ++ " more)" From git at git.haskell.org Thu Oct 26 23:49:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, add tests for chunksOfSize (d001140) Message-ID: <20171026234940.364493A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d001140948a06ae50475eb919010d192e37b3829/ghc >--------------------------------------------------------------- commit d001140948a06ae50475eb919010d192e37b3829 Author: Neil Mitchell Date: Mon Jan 11 11:06:54 2016 +0000 #146, add tests for chunksOfSize >--------------------------------------------------------------- d001140948a06ae50475eb919010d192e37b3829 src/Settings/Builders/Ar.hs | 2 +- src/Test.hs | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index fc43d45..8cf175f 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,4 +1,4 @@ -module Settings.Builders.Ar (arBuilderArgs, arCmd) where +module Settings.Builders.Ar (arBuilderArgs, arCmd, chunksOfSize) where import Base import Expression diff --git a/src/Test.hs b/src/Test.hs index a55e6e6..6cbc557 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -6,6 +6,7 @@ module Test (testRules) where import Way import Development.Shake import Test.QuickCheck +import Settings.Builders.Ar(chunksOfSize) instance Arbitrary Way where arbitrary = wayFromUnits <$> arbitrary @@ -17,6 +18,10 @@ testRules :: Rules () testRules = phony "selftest" $ do test $ \(x :: Way) -> read (show x) == x + test $ \n xs -> + let res = chunksOfSize n xs + in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res + test $ chunksOfSize 3 ["a","b","c","defg","hi","jk"] == [["a","b","c"],["defg"],["hi"],["jk"]] test :: Testable a => a -> Action () From git at git.haskell.org Thu Oct 26 23:49:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add instance Show Stage. (d0095df) Message-ID: <20171026234942.E78213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d0095df621aa39dfbe7f827e073c5b1fb7aa7b89/ghc >--------------------------------------------------------------- commit d0095df621aa39dfbe7f827e073c5b1fb7aa7b89 Author: Andrey Mokhov Date: Sun Jan 11 21:45:31 2015 +0000 Add instance Show Stage. >--------------------------------------------------------------- d0095df621aa39dfbe7f827e073c5b1fb7aa7b89 src/Base.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index b84b48c..169f556 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -24,6 +24,9 @@ import Data.List data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) +instance Show Stage where + show = show . fromEnum + type Args = Action [String] type Condition = Action Bool From git at git.haskell.org Thu Oct 26 23:49:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update the docs for chunksOfSize (916d5a9) Message-ID: <20171026234944.1D9473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/916d5a93c7dba53c730e49e00a0c0656e75e602b/ghc >--------------------------------------------------------------- commit 916d5a93c7dba53c730e49e00a0c0656e75e602b Author: Neil Mitchell Date: Mon Jan 11 11:14:12 2016 +0000 Update the docs for chunksOfSize >--------------------------------------------------------------- 916d5a93c7dba53c730e49e00a0c0656e75e602b src/Settings/Builders/Ar.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 8cf175f..59b70b8 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -46,7 +46,7 @@ useSuccessiveInvocations path flagArgs fileArgs = do unit . cmd [path] $ flagArgs ++ argsChunk -- | @chunksOfSize size strings@ splits a given list of strings into chunks not --- exceeding the given @size at . +-- exceeding the given @size at . If that is impossible, it uses singleton chunks. chunksOfSize :: Int -> [String] -> [[String]] chunksOfSize n = repeatedly f where f xs = splitAt (max 1 $ length $ takeWhile (<= n) $ scanl1 (+) $ map length xs) xs From git at git.haskell.org Thu Oct 26 23:49:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Settings/Builders/Common.hs for storing common Args, refactor code. (0c9571a) Message-ID: <20171026234944.276223A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c9571aac4cf2d4f5c84d6d2bcbf9a029e52c2ef/ghc >--------------------------------------------------------------- commit 0c9571aac4cf2d4f5c84d6d2bcbf9a029e52c2ef Author: Andrey Mokhov Date: Tue Dec 29 18:47:48 2015 +0000 Add Settings/Builders/Common.hs for storing common Args, refactor code. >--------------------------------------------------------------- 0c9571aac4cf2d4f5c84d6d2bcbf9a029e52c2ef src/Rules/Data.hs | 6 +++--- src/Settings/Builders/Ar.hs | 6 +++--- src/Settings/Builders/Common.hs | 9 +++++++++ src/Settings/Builders/DeriveConstants.hs | 3 ++- src/Settings/Builders/GhcCabal.hs | 10 +++------- 5 files changed, 20 insertions(+), 14 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 879dc1e..70c8e8a 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -8,7 +8,7 @@ import Predicates (registerPackage) import Rules.Actions import Rules.Resources import Settings -import Settings.Builders.GhcCabal +import Settings.Builders.Common -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: Resources -> PartialTarget -> Rules () @@ -42,9 +42,9 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do postProcessPackageData dataFile -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps - -- TODO: code duplication around ghcIncludeDirs priority 2.0 $ do when (pkg == hp2ps) $ dataFile %> \mk -> do + includes <- interpretPartial target $ fromDiffExpr includesArgs let prefix = "utils_hp2ps_stage" ++ show (fromEnum stage) ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" , "Reorder.c", "TopTwenty.c", "AuxFile.c" @@ -57,7 +57,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do , "INSTALL = YES" , "INSTALL_INPLACE = YES" , "DEP_EXTRA_LIBS = m" - , "CC_OPTS = " ++ unwords (map ("-I"++) ghcIncludeDirs) ] + , "CC_OPTS = " ++ unwords includes ] writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 662d5fe..dae4a82 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -26,15 +26,15 @@ arCmd path argList = do fileArgs = drop arFlagsCount argList if arSupportsAtFile then useAtFile path flagArgs fileArgs - else useSuccessiveInvokations path flagArgs fileArgs + else useSuccessiveInvocations path flagArgs fileArgs useAtFile :: FilePath -> [String] -> [String] -> Action () useAtFile path flagArgs fileArgs = withTempFile $ \tmp -> do writeFile' tmp $ unwords fileArgs cmd [path] flagArgs ('@' : tmp) -useSuccessiveInvokations :: FilePath -> [String] -> [String] -> Action () -useSuccessiveInvokations path flagArgs fileArgs = do +useSuccessiveInvocations :: FilePath -> [String] -> [String] -> Action () +useSuccessiveInvocations path flagArgs fileArgs = do maxChunk <- cmdLineLengthLimit forM_ (chunksOfSize maxChunk fileArgs) $ \argsChunk -> unit . cmd [path] $ flagArgs ++ argsChunk diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs new file mode 100644 index 0000000..fc3ed53 --- /dev/null +++ b/src/Settings/Builders/Common.hs @@ -0,0 +1,9 @@ +module Settings.Builders.Common (includesArgs) where + +import Expression + +includes :: [FilePath] +includes = [ "includes", "includes/dist-derivedconstants/header" ] + +includesArgs :: Args +includesArgs = append $ map ("-I" ++) includes diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 1f42243..ee07d34 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -7,6 +7,7 @@ import Expression import Oracles.Config.Flag import Oracles.Config.Setting import Predicates (builder, file) +import Settings.Builders.Common import Settings.Builders.GhcCabal derivedConstantsPath :: FilePath @@ -39,7 +40,7 @@ includeCcArgs = do , ccWarnings , append confCcArgs , flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER" - , append $ map ("-I" ++) ghcIncludeDirs -- TODO: fix code duplication + , includesArgs , arg "-Irts" , notM ghcWithSMP ? arg "-DNOSMP" , arg "-fcommon" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index bd95cfc..61da725 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,5 +1,5 @@ module Settings.Builders.GhcCabal ( - cabalArgs, ghcCabalHsColourArgs, ghcIncludeDirs, bootPackageDbArgs, + cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, ccArgs, cppArgs, ccWarnings, argStagedSettingList, needDll0 ) where @@ -14,6 +14,7 @@ import Stage import Expression import Predicates hiding (stage) import Settings +import Settings.Builders.Common cabalArgs :: Args cabalArgs = builder GhcCabal ? do @@ -115,13 +116,8 @@ ccWarnings = do ldArgs :: Args ldArgs = mempty -ghcIncludeDirs :: [FilePath] -ghcIncludeDirs = [ "includes", "includes/dist" - , "includes/dist-derivedconstants/header" - , "includes/dist-ghcconstants/header" ] - cppArgs :: Args -cppArgs = append $ map ("-I" ++) ghcIncludeDirs +cppArgs = includesArgs -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" From git at git.haskell.org Thu Oct 26 23:49:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose src/Settings/Builders/Gcc.hs, factor out cIncludeArgs into src/Settings/Builders/Common.hs. (bf70983) Message-ID: <20171026234948.06A2A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf70983e38c76138bf5819a2dff9109181a1f2aa/ghc >--------------------------------------------------------------- commit bf70983e38c76138bf5819a2dff9109181a1f2aa Author: Andrey Mokhov Date: Tue Dec 29 21:46:04 2015 +0000 Decompose src/Settings/Builders/Gcc.hs, factor out cIncludeArgs into src/Settings/Builders/Common.hs. >--------------------------------------------------------------- bf70983e38c76138bf5819a2dff9109181a1f2aa src/Settings/Args.hs | 4 +++- src/Settings/Builders/Common.hs | 17 ++++++++++++++++- src/Settings/Builders/Gcc.hs | 21 ++++----------------- src/Settings/Builders/Ghc.hs | 6 ++---- src/Settings/Builders/Hsc2Hs.hs | 7 ++----- src/Settings/Packages/Directory.hs | 13 +++++++++++++ 6 files changed, 40 insertions(+), 28 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 6715680..f474f8f 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -17,6 +17,7 @@ import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld import Settings.Packages.Compiler +import Settings.Packages.Directory import Settings.User getArgs :: Expr [String] @@ -50,4 +51,5 @@ defaultBuilderArgs = mconcat defaultPackageArgs :: Args defaultPackageArgs = mconcat - [ compilerArgs ] + [ compilerArgs + , directoryArgs ] diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index fc3ed53..9ed6efd 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -1,9 +1,24 @@ -module Settings.Builders.Common (includesArgs) where +module Settings.Builders.Common (includesArgs, cIncludeArgs) where +import Base import Expression +import Oracles.PackageData +import Settings includes :: [FilePath] includes = [ "includes", "includes/dist-derivedconstants/header" ] includesArgs :: Args includesArgs = append $ map ("-I" ++) includes + +cIncludeArgs :: Args +cIncludeArgs = do + stage <- getStage + pkg <- getPackage + incDirs <- getPkgDataList IncludeDirs + depDirs <- getPkgDataList DepIncludeDirs + let buildPath = targetPath stage pkg -/- "build" + mconcat [ arg $ "-I" ++ buildPath + , arg $ "-I" ++ buildPath -/- "autogen" + , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] + , append [ "-I" ++ dir | dir <- depDirs ] ] diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index fab5104..8a6b087 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -2,20 +2,14 @@ module Settings.Builders.Gcc (gccArgs, gccMArgs) where import Development.Shake.FilePath import Expression -import GHC import Oracles -import Base ((-/-)) -import Predicates (package, stagedBuilder) +import Predicates (stagedBuilder) import Settings +import Settings.Builders.Common (cIncludeArgs) --- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is --- effectively empty. I presume it was expected that GHC will be used for --- compiling all C files, but I don't know why. It seems that directory.c is the --- only file which requires special treatment when using GCC. gccArgs :: Args gccArgs = stagedBuilder Gcc ? mconcat [ commonGccArgs - , package directory ? arg "-D__GLASGOW_HASKELL__" , arg "-c", arg =<< getInput , arg "-o", arg =<< getOutput ] @@ -35,12 +29,5 @@ gccMArgs = stagedBuilder GccM ? do , arg =<< getInput ] commonGccArgs :: Args -commonGccArgs = do - pkg <- getPackage - path <- getTargetPath - iDirs <- getPkgDataList IncludeDirs - dDirs <- getPkgDataList DepIncludeDirs - ccArgs <- getPkgDataList CcArgs - mconcat [ append ccArgs - , arg $ "-I" ++ path -/- "build/autogen" - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- iDirs ++ dDirs ]] +commonGccArgs = mconcat [ append =<< getPkgDataList CcArgs + , cIncludeArgs ] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index f354458..593f0e0 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -7,6 +7,7 @@ import GHC import Predicates hiding (way, stage) import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) +import Settings.Builders.Common (cIncludeArgs) -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot @@ -114,16 +115,13 @@ includeGhcArgs = do pkg <- getPackage path <- getTargetPath srcDirs <- getPkgDataList SrcDirs - incDirs <- getPkgDataList IncludeDirs let buildPath = path -/- "build" autogenPath = buildPath -/- "autogen" mconcat [ arg "-i" , arg $ "-i" ++ buildPath , arg $ "-i" ++ autogenPath - , arg $ "-I" ++ buildPath - , arg $ "-I" ++ autogenPath , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] + , cIncludeArgs , (pkg == compiler || pkg == ghc) ? arg ("-I" ++ pkgPath compiler -/- "stage" ++ show (fromEnum stage)) , not (pkg == hp2ps || pkg == ghcCabal && stage == Stage0) ? diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 90abc82..c89caf0 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -9,6 +9,7 @@ import Oracles import Predicates (builder, stage0, notStage0) import Settings import Settings.Builders.GhcCabal hiding (cppArgs) +import Settings.Builders.Common (cIncludeArgs) templateHsc :: FilePath templateHsc = "inplace/lib/template-hsc.h" @@ -48,18 +49,14 @@ hsc2HsArgs = builder Hsc2Hs ? do getCFlags :: Expr [String] getCFlags = fromDiffExpr $ do - pkg <- getPackage path <- getTargetPath - iDirs <- getPkgDataList IncludeDirs - dDirs <- getPkgDataList DepIncludeDirs cppArgs <- getPkgDataList CppArgs depCcArgs <- getPkgDataList DepCcArgs mconcat [ ccArgs , argStagedSettingList ConfCcArgs , remove ["-O"] , argStagedSettingList ConfCppArgs - , arg $ "-I" ++ path -/- "build/autogen" - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- iDirs ++ dDirs ] + , cIncludeArgs , append cppArgs , append depCcArgs , ccWarnings diff --git a/src/Settings/Packages/Directory.hs b/src/Settings/Packages/Directory.hs new file mode 100644 index 0000000..3ff69ce --- /dev/null +++ b/src/Settings/Packages/Directory.hs @@ -0,0 +1,13 @@ +module Settings.Packages.Directory (directoryArgs) where + +import Expression +import GHC (directory) +import Predicates (stagedBuilder, package) + +-- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is +-- effectively empty. I presume it was expected that GHC will be used for +-- compiling all C files, but I don't know why. It seems that directory.c is the +-- only file which requires special treatment when using GCC. +directoryArgs :: Args +directoryArgs = package directory ? + stagedBuilder Gcc ? arg "-D__GLASGOW_HASKELL__" From git at git.haskell.org Thu Oct 26 23:49:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #151, add a call to selftest (c5cb061) Message-ID: <20171026234948.11DEC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5cb0617314c3b6fcb201246a76b6a02cb93350f/ghc >--------------------------------------------------------------- commit c5cb0617314c3b6fcb201246a76b6a02cb93350f Author: Neil Mitchell Date: Mon Jan 11 11:39:47 2016 +0000 #151, add a call to selftest >--------------------------------------------------------------- c5cb0617314c3b6fcb201246a76b6a02cb93350f .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index dd3bd12..0dc23c1 100644 --- a/.travis.yml +++ b/.travis.yml @@ -62,6 +62,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) + - ./ghc/shake-build/build.sh selftest - ./ghc/shake-build/build.sh -j --no-progress $TARGET cache: From git at git.haskell.org Thu Oct 26 23:49:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for SolarisBrokenShld flag. (e77d98b) Message-ID: <20171026234950.1685A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e77d98ba7ad9c4eef57f28784267ba6da339d8fe/ghc >--------------------------------------------------------------- commit e77d98ba7ad9c4eef57f28784267ba6da339d8fe Author: Andrey Mokhov Date: Sun Jan 11 23:43:31 2015 +0000 Add support for SolarisBrokenShld flag. >--------------------------------------------------------------- e77d98ba7ad9c4eef57f28784267ba6da339d8fe cfg/default.config.in | 1 + src/Oracles/Flag.hs | 17 ++++++++++++----- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index 50c3937..b1eadd0 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -31,6 +31,7 @@ gcc-lt-46 = @GccLT46@ lax-dependencies = NO dynamic-ghc-programs = NO supports-package-key = @SUPPORTS_PACKAGE_KEY@ +solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ # Information about host and target systems: #=========================================== diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 946c4fb..7a235a4 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -13,23 +13,30 @@ import Prelude hiding (not, (&&), (||)) import Base import Oracles.Base -data Flag = LaxDeps | DynamicGhcPrograms - | GccIsClang | GccLt46 | CrossCompiling | Validating +data Flag = LaxDeps + | DynamicGhcPrograms + | GccIsClang + | GccLt46 + | CrossCompiling + | Validating | SupportsPackageKey + | SolarisBrokenShld +-- TODO: Give the warning *only once* per key test :: Flag -> Action Bool test flag = do (key, defaultValue) <- return $ case flag of - LaxDeps -> ("lax-dependencies" , False) -- TODO: move flags to a separate file + LaxDeps -> ("lax-dependencies" , False) DynamicGhcPrograms -> ("dynamic-ghc-programs" , False) GccIsClang -> ("gcc-is-clang" , False) GccLt46 -> ("gcc-lt-46" , False) CrossCompiling -> ("cross-compiling" , False) Validating -> ("validating" , False) SupportsPackageKey -> ("supports-package-key" , False) + SolarisBrokenShld -> ("solaris-broken-shld" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ - do putLoud $ "\nFlag '" -- TODO: Give the warning *only once* per key + do putLoud $ "\nFlag '" ++ key ++ "' not set in configuration files. " ++ "Proceeding with default value '" @@ -103,4 +110,4 @@ instance ToCondition a => AndOr Flag a where x && y = toCondition x && y x || y = toCondition x || y - +-- TODO: need one more instance? \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:49:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new source files. (73d198b) Message-ID: <20171026234952.245E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73d198b03cc64d2200e4bcdad4a6da51d419e43a/ghc >--------------------------------------------------------------- commit 73d198b03cc64d2200e4bcdad4a6da51d419e43a Author: Andrey Mokhov Date: Wed Dec 30 01:19:36 2015 +0000 Add new source files. >--------------------------------------------------------------- 73d198b03cc64d2200e4bcdad4a6da51d419e43a shaking-up-ghc.cabal | 3 +++ 1 file changed, 3 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f530894..5ad614e 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -58,6 +58,7 @@ executable ghc-shake , Settings.Args , Settings.Builders.Alex , Settings.Builders.Ar + , Settings.Builders.Common , Settings.Builders.Gcc , Settings.Builders.GenPrimopCode , Settings.Builders.Ghc @@ -69,6 +70,8 @@ executable ghc-shake , Settings.Builders.HsCpp , Settings.Builders.Ld , Settings.Packages + , Settings.Packages.Compiler + , Settings.Packages.Directory , Settings.TargetDirectory , Settings.User , Settings.Ways From git at git.haskell.org Thu Oct 26 23:49:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #151 from ndmitchell/master (5f80d4f) Message-ID: <20171026234952.2F26B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f80d4f2a5269a8546a5040edbd26502fab7bc26/ghc >--------------------------------------------------------------- commit 5f80d4f2a5269a8546a5040edbd26502fab7bc26 Merge: 754ed41 c5cb061 Author: Andrey Mokhov Date: Mon Jan 11 14:29:39 2016 +0000 Merge pull request #151 from ndmitchell/master Add tests >--------------------------------------------------------------- 5f80d4f2a5269a8546a5040edbd26502fab7bc26 .appveyor.yml | 1 + .travis.yml | 1 + shaking-up-ghc.cabal | 3 +++ src/Main.hs | 4 +++- src/Settings/Builders/Ar.hs | 16 ++++------------ src/Test.hs | 28 ++++++++++++++++++++++++++++ src/Way.hs | 2 +- 7 files changed, 41 insertions(+), 14 deletions(-) From git at git.haskell.org Thu Oct 26 23:49:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for SolarisBrokenShld flag. (a5de5a5) Message-ID: <20171026234953.81C223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5de5a592f8b2bdae851e0d0c0a0041414dd1c39/ghc >--------------------------------------------------------------- commit a5de5a592f8b2bdae851e0d0c0a0041414dd1c39 Author: Andrey Mokhov Date: Sun Jan 11 23:44:30 2015 +0000 Add support for SolarisBrokenShld flag. >--------------------------------------------------------------- a5de5a592f8b2bdae851e0d0c0a0041414dd1c39 src/Oracles/Option.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 0a5506d..029b9bd 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,9 +1,11 @@ +{-# LANGUAGE NoImplicitPrelude #-} module Oracles.Option ( Option (..), ghcWithInterpreter, platformSupportsSharedLibs, windowsHost ) where import Base +import Oracles.Flag import Oracles.Base data Option = TargetOS @@ -47,14 +49,15 @@ ghcWithInterpreter = do && arch `elem` ["i386", "x86_64", "powerpc", "sparc", "sparc64", "arm"] --- TODO: i386-unknown-solaris2 should be in the list if --- @SOLARIS_BROKEN_SHLD@ == YES platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do [platform] <- showArgs TargetPlatformFull - return $ platform `notElem` [ "powerpc-unknown-linux" - , "x86_64-unknown-mingw32" - , "i386-unknown-mingw32" ] + solarisBrokenShld <- test SolarisBrokenShld + return $ notElem platform $ + [ "powerpc-unknown-linux" + , "x86_64-unknown-mingw32" + , "i386-unknown-mingw32"] ++ + [ "i386-unknown-solaris2" | solarisBrokenShld ] windowsHost :: Condition windowsHost = do From git at git.haskell.org Thu Oct 26 23:49:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use shallow git clone. (0c3a659) Message-ID: <20171026234955.E7CA83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c3a65984127a8e17cde5cec4257ed8b023487db/ghc >--------------------------------------------------------------- commit 0c3a65984127a8e17cde5cec4257ed8b023487db Author: Andrey Mokhov Date: Mon Jan 11 14:48:30 2016 +0000 Use shallow git clone. See #110. [skip ci] >--------------------------------------------------------------- 0c3a65984127a8e17cde5cec4257ed8b023487db .appveyor.yml | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f0d0e69..68c1fd8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -16,7 +16,14 @@ install: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp + + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ + - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ + - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ + - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ + - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot From git at git.haskell.org Thu Oct 26 23:49:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Stage.stageString, rename runghc -> runGhc. (9e2ddcb) Message-ID: <20171026234955.EF12F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e2ddcb188ecf614edbaeca9404d0adb77f125b3/ghc >--------------------------------------------------------------- commit 9e2ddcb188ecf614edbaeca9404d0adb77f125b3 Author: Andrey Mokhov Date: Wed Dec 30 03:02:27 2015 +0000 Add Stage.stageString, rename runghc -> runGhc. >--------------------------------------------------------------- 9e2ddcb188ecf614edbaeca9404d0adb77f125b3 src/GHC.hs | 14 +++++++------- src/Oracles/Config/Setting.hs | 8 ++++---- src/Rules/Data.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Stage.hs | 5 ++++- 6 files changed, 18 insertions(+), 15 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 859bec4..f93d92a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -5,7 +5,7 @@ module GHC ( genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, - runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, + runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -26,7 +26,7 @@ defaultKnownPackages = , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin , integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty - , primitive , process, runghc, stm, templateHaskell, terminfo, time + , primitive , process, runGhc, stm, templateHaskell, terminfo, time , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) @@ -35,7 +35,7 @@ array, base, binary, bytestring, cabal, compiler, containers, compareSizes, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, - runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package + runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -75,7 +75,7 @@ parallel = library "parallel" pretty = library "pretty" primitive = library "primitive" process = library "process" -runghc = utility "runghc" +runGhc = utility "runGhc" stm = library "stm" templateHaskell = library "template-haskell" terminfo = library "terminfo" @@ -97,17 +97,17 @@ xhtml = library "xhtml" -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal defaultTargetDirectory :: Stage -> Package -> FilePath -defaultTargetDirectory stage _ = "stage" ++ show (fromEnum stage) +defaultTargetDirectory stage _ = stageString stage -- TODO: simplify -- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg - | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) + | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing - | isProgram pkg = case stage of + | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg | otherwise = Nothing diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index b0c6da3..ace9158 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -91,10 +91,10 @@ setting key = askConfig $ case key of settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of - ConfCcArgs stage -> "conf-cc-args-stage" ++ show (fromEnum stage) - ConfCppArgs stage -> "conf-cpp-args-stage" ++ show (fromEnum stage) - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show (fromEnum stage) - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show (fromEnum stage) + ConfCcArgs stage -> "conf-cc-args-" ++ stageString stage + ConfCppArgs stage -> "conf-cpp-args-" ++ stageString stage + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-" ++ stageString stage + ConfLdLinkerArgs stage -> "conf-ld-linker-args-" ++ stageString stage GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" HsCppArgs -> "hs-cpp-args" diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 70c8e8a..a863968 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -45,7 +45,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do priority 2.0 $ do when (pkg == hp2ps) $ dataFile %> \mk -> do includes <- interpretPartial target $ fromDiffExpr includesArgs - let prefix = "utils_hp2ps_stage" ++ show (fromEnum stage) ++ "_" + let prefix = "utils_hp2ps_" ++ stageString stage ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" , "Reorder.c", "TopTwenty.c", "AuxFile.c" , "Deviation.c", "HpFile.c", "Marks.c", "Scale.c" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index ea5ed63..fd101a1 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -127,7 +127,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do file <~ generateVersionHs - when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do + when (pkg == runGhc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putSuccess $ "| Successfully generated '" ++ file ++ "'." diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 61457cb..308fb8c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -32,7 +32,7 @@ packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq , directory, filepath, ghci, ghcPrim, ghcPwd, haskeline, hpcBin - , integerLibrary, mkUserGuidePart, pretty, process, runghc, time ] + , integerLibrary, mkUserGuidePart, pretty, process, runGhc, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , notM windowsHost ? append [iservBin] diff --git a/src/Stage.hs b/src/Stage.hs index d474557..70fe6ba 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DeriveGeneric #-} -module Stage (Stage (..)) where +module Stage (Stage (..), stageString) where import Base import GHC.Generics (Generic) @@ -8,6 +8,9 @@ import GHC.Generics (Generic) data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Show, Eq, Ord, Enum, Generic) +stageString :: Stage -> String +stageString stage = "stage" ++ show (fromEnum stage) + -- Instances for storing in the Shake database instance Binary Stage instance Hashable Stage From git at git.haskell.org Thu Oct 26 23:49:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant GHC extentions. (238efc2) Message-ID: <20171026234957.02FD63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/238efc2b316f5a8ed2f955af6639e4fa543d2359/ghc >--------------------------------------------------------------- commit 238efc2b316f5a8ed2f955af6639e4fa543d2359 Author: Andrey Mokhov Date: Sun Jan 11 23:45:29 2015 +0000 Remove redundant GHC extentions. >--------------------------------------------------------------- 238efc2b316f5a8ed2f955af6639e4fa543d2359 src/Package/Compile.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index b876482..50cf412 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-} +{-# LANGUAGE NoImplicitPrelude #-} module Package.Compile (buildPackageCompile) where import Package.Base From git at git.haskell.org Thu Oct 26 23:50:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Expressions.removePair function to remove pairs of arguments. (9140548) Message-ID: <20171026235000.16FAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9140548b75f96d17e9888a21bf32a2f46d447cbe/ghc >--------------------------------------------------------------- commit 9140548b75f96d17e9888a21bf32a2f46d447cbe Author: Andrey Mokhov Date: Wed Dec 30 03:03:26 2015 +0000 Add Expressions.removePair function to remove pairs of arguments. >--------------------------------------------------------------- 9140548b75f96d17e9888a21bf32a2f46d447cbe src/Expression.hs | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/src/Expression.hs b/src/Expression.hs index 2b7ef9a..a2eaea9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -3,7 +3,8 @@ module Expression ( -- * Expressions Expr, DiffExpr, fromDiffExpr, -- ** Operators - apply, append, arg, remove, appendSub, appendSubD, filterSub, removeSub, + apply, append, arg, remove, removePair, + appendSub, appendSubD, filterSub, removeSub, -- ** Evaluation interpret, interpretPartial, interpretWithStage, interpretDiff, -- ** Predicates @@ -76,6 +77,16 @@ append x = apply (<> x) remove :: Eq a => [a] -> DiffExpr [a] remove xs = apply $ filter (`notElem` xs) +-- | Remove given pair of elements from a list expression +-- Example: removePair "-flag" "b" ["-flag", "a", "-flag", "b"] = ["-flag", "a"] +removePair :: Eq a => a -> a -> DiffExpr [a] +removePair x y = apply filterPair + where + filterPair (z1 : z2 : zs) = if x == z1 && y == z2 + then filterPair zs + else z1 : filterPair (z2 : zs) + filterPair zs = zs + -- | Apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do From git at git.haskell.org Thu Oct 26 23:50:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix parallel invocations of DeriveConstants builder. (9178de2) Message-ID: <20171026235000.1A2223A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9178de2bd2483148777975b5bab48d96ce2884ad/ghc >--------------------------------------------------------------- commit 9178de2bd2483148777975b5bab48d96ce2884ad Author: Andrey Mokhov Date: Mon Jan 11 16:06:21 2016 +0000 Fix parallel invocations of DeriveConstants builder. See #137. >--------------------------------------------------------------- 9178de2bd2483148777975b5bab48d96ce2884ad src/Rules/Generate.hs | 9 ++++++--- src/Settings/Builders/DeriveConstants.hs | 14 +++++--------- 2 files changed, 11 insertions(+), 12 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 4fd7da6..025f1ee 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -19,7 +19,6 @@ import Rules.Gmp import Rules.Libffi import Rules.Resources (Resources) import Settings -import Settings.Builders.DeriveConstants installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" @@ -53,6 +52,9 @@ ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> [ "GHC/PrimopWrappers.hs" , "autogen/GHC/Prim.hs" ] +derivedConstantsPath :: FilePath +derivedConstantsPath = "includes/dist-derivedconstants/header" + derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) [ "DerivedConstants.h" @@ -178,9 +180,10 @@ generateRules = do generate ghcSplit emptyTarget generateGhcSplit makeExecutable ghcSplit - -- TODO: simplify + -- TODO: simplify, get rid of fake rts target derivedConstantsPath ++ "//*" %> \file -> do - build $ fullTarget (PartialTarget Stage1 rts) DeriveConstants [] [file] + withTempDir $ \dir -> build $ + fullTarget (PartialTarget Stage1 rts) DeriveConstants [] [file, dir] where file <~ gen = file %> \out -> generate out emptyTarget gen diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 6f4828a..fb578f5 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -1,6 +1,4 @@ -module Settings.Builders.DeriveConstants ( - derivedConstantsPath, deriveConstantsBuilderArgs - ) where +module Settings.Builders.DeriveConstants (deriveConstantsBuilderArgs) where import Base import Expression @@ -9,21 +7,19 @@ import Oracles.Config.Setting import Predicates (builder, file) import Settings.Builders.Common -derivedConstantsPath :: FilePath -derivedConstantsPath = "includes/dist-derivedconstants/header" - -- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? deriveConstantsBuilderArgs :: Args deriveConstantsBuilderArgs = builder DeriveConstants ? do - cFlags <- fromDiffExpr includeCcArgs + cFlags <- fromDiffExpr includeCcArgs + [output, tempDir] <- getOutputs mconcat [ file "//DerivedConstants.h" ? arg "--gen-header" , file "//GHCConstantsHaskellType.hs" ? arg "--gen-haskell-type" , file "//platformConstants" ? arg "--gen-haskell-value" , file "//GHCConstantsHaskellWrappers.hs" ? arg "--gen-haskell-wrappers" , file "//GHCConstantsHaskellExports.hs" ? arg "--gen-haskell-exports" - , arg "-o", arg =<< getOutput - , arg "--tmpdir", arg derivedConstantsPath + , arg "-o", arg output + , arg "--tmpdir", arg tempDir , arg "--gcc-program", arg =<< getBuilderPath (Gcc Stage1) , append . concat $ map (\a -> ["--gcc-flag", a]) cFlags , arg "--nm-program", arg =<< getBuilderPath Nm From git at git.haskell.org Thu Oct 26 23:50:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (2e29ea9) Message-ID: <20171026235000.832E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2e29ea968bba4737bbdeb914e90cae4933202c75/ghc >--------------------------------------------------------------- commit 2e29ea968bba4737bbdeb914e90cae4933202c75 Author: Andrey Mokhov Date: Mon Jan 12 00:29:28 2015 +0000 Clean up. >--------------------------------------------------------------- 2e29ea968bba4737bbdeb914e90cae4933202c75 src/Oracles/Base.hs | 3 ++- src/Oracles/Flag.hs | 10 +++++----- 2 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index f9e5c73..c9827a9 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -8,7 +8,8 @@ module Oracles.Base ( import Base import Development.Shake.Classes -newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +newtype ConfigKey = ConfigKey String + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) askConfigWithDefault :: String -> Action String -> Action String askConfigWithDefault key defaultAction = do diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 7a235a4..b93e4ab 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -81,11 +81,11 @@ instance Not Bool where instance Not Condition where type NotResult Condition = Condition - not x = not <$> (toCondition x) + not = fmap not instance Not Flag where type NotResult Flag = Condition - not x = not (toCondition x) + not = not . toCondition class AndOr a b where type AndOrResult a b @@ -102,12 +102,12 @@ instance AndOr Bool Bool where instance ToCondition a => AndOr Condition a where type AndOrResult Condition a = Condition - x && y = (Prelude.&&) <$> toCondition x <*> toCondition y - x || y = (Prelude.||) <$> toCondition x <*> toCondition y + x && y = (&&) <$> x <*> toCondition y + x || y = (||) <$> x <*> toCondition y instance ToCondition a => AndOr Flag a where type AndOrResult Flag a = Condition x && y = toCondition x && y x || y = toCondition x || y --- TODO: need one more instance? \ No newline at end of file +-- TODO: need more instances to handle Bool as first argument of (&&), (||) From git at git.haskell.org Thu Oct 26 23:50:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add custom predicate builderGhc for Ghc/GhcM builders. (7ca8be7) Message-ID: <20171026235004.14A773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ca8be77837fed2ebb05d369996edd6ee5d72b8e/ghc >--------------------------------------------------------------- commit 7ca8be77837fed2ebb05d369996edd6ee5d72b8e Author: Andrey Mokhov Date: Wed Dec 30 03:04:12 2015 +0000 Add custom predicate builderGhc for Ghc/GhcM builders. >--------------------------------------------------------------- 7ca8be77837fed2ebb05d369996edd6ee5d72b8e src/Predicates.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 28dd51a..7f590f4 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,6 +1,6 @@ -- | Convenient predicates module Predicates ( - stage, package, builder, stagedBuilder, file, way, + stage, package, builder, stagedBuilder, builderGhc, file, way, stage0, stage1, stage2, notStage0, notPackage, registerPackage, splitObjects ) where @@ -24,6 +24,9 @@ builder b = fmap (b ==) getBuilder stagedBuilder :: (Stage -> Builder) -> Predicate stagedBuilder sb = (builder . sb) =<< getStage +builderGhc :: Predicate +builderGhc = stagedBuilder Ghc ||^ stagedBuilder GhcM + file :: FilePattern -> Predicate file f = fmap (any (f ?==)) getOutputs From git at git.haskell.org Thu Oct 26 23:50:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Report success on IRC only if the build was fixed (462f78f) Message-ID: <20171026235004.71F1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/462f78f8a676120ae0505c083afa93a14ccd7418/ghc >--------------------------------------------------------------- commit 462f78f8a676120ae0505c083afa93a14ccd7418 Author: David Luposchainsky Date: Mon Jan 11 18:35:25 2016 +0100 Report success on IRC only if the build was fixed >--------------------------------------------------------------- 462f78f8a676120ae0505c083afa93a14ccd7418 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0dc23c1..4ff35ec 100644 --- a/.travis.yml +++ b/.travis.yml @@ -72,7 +72,7 @@ cache: notifications: irc: - on_success: always # always/never/change + on_success: change # always/never/change on_failure: always channels: - "chat.freenode.net#shaking-up-ghc" From git at git.haskell.org Thu Oct 26 23:50:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters, add exists Builder function. (f956bdc) Message-ID: <20171026235004.D60D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f956bdcf059fac29eafbfb24e1eb2180e8689009/ghc >--------------------------------------------------------------- commit f956bdcf059fac29eafbfb24e1eb2180e8689009 Author: Andrey Mokhov Date: Mon Jan 12 01:21:37 2015 +0000 Fit lines into 80 characters, add exists Builder function. >--------------------------------------------------------------- f956bdcf059fac29eafbfb24e1eb2180e8689009 src/Oracles/Builder.hs | 76 ++++++++++++++++++++++++++++++-------------------- src/Package/Data.hs | 2 +- 2 files changed, 46 insertions(+), 32 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index d91e5e7..eefa7a2 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,8 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, - hsColourSrcs + with, run, exists ) where import Data.Char @@ -12,10 +11,22 @@ import Oracles.Base import Oracles.Flag import Oracles.Option -data Builder = Ar | Ld | Gcc | Alex | Happy | HsColour | GhcCabal | GhcPkg Stage | Ghc Stage +-- Ghc Stage0 is the bootstrapping compiler +-- Ghc StageN, N > 0, is the one built on stage (N - 1) +-- GhcPkg Stage0 is the bootstrapping GhcPkg +-- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) +data Builder = Ar + | Ld + | Gcc + | Alex + | Happy + | HsColour + | GhcCabal + | Ghc Stage + | GhcPkg Stage instance ShowArgs Builder where - showArgs builder = showArgs $ do + showArgs builder = showArgs $ fmap words $ do let key = case builder of Ar -> "ar" Ld -> "ld" @@ -24,16 +35,15 @@ instance ShowArgs Builder where Happy -> "happy" HsColour -> "hscolour" GhcCabal -> "ghc-cabal" - Ghc Stage0 -> "system-ghc" -- Ghc Stage0 is the bootstrapping compiler - Ghc Stage1 -> "ghc-stage1" -- Ghc StageN, N > 0, is the one built on stage (N - 1) + Ghc Stage0 -> "system-ghc" + Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - GhcPkg Stage0 -> "system-ghc-pkg" -- GhcPkg Stage0 is the bootstrapping GhcPkg - GhcPkg _ -> "ghc-pkg" -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) + GhcPkg Stage0 -> "system-ghc-pkg" + GhcPkg _ -> "ghc-pkg" cfgPath <- askConfigWithDefault key $ - error $ "\nCannot find path to '" - ++ key - ++ "' in configuration files." + error $ "\nCannot find path to '" ++ key + ++ "' in configuration files." let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" windows <- windowsHost if (windows && "/" `isPrefixOf` cfgPathExe) @@ -43,25 +53,26 @@ instance ShowArgs Builder where else return cfgPathExe --- When LaxDeps flag is set (by adding 'lax-dependencies = YES' to user.config), --- dependencies on the GHC executable are turned into order-only dependencies to --- avoid needless recompilation when making changes to GHC's sources. In certain --- situations this can lead to build failures, in which case you should reset --- the flag (at least temporarily). +-- When LaxDeps flag is set ('lax-dependencies = YES' in user.config), +-- dependencies on the GHC executable are turned into order-only dependencies +-- to avoid needless recompilation when making changes to GHC's sources. In +-- certain situations this can lead to build failures, in which case you +-- should reset the flag (at least temporarily). needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - [target] <- showArgs ghc - laxDeps <- test LaxDeps - if laxDeps then orderOnly [target] else need [target] + [exe] <- showArgs ghc -- Raise an error if builder is not unique + laxDeps <- test LaxDeps + if laxDeps then orderOnly [exe] else need [exe] needBuilder builder = do - [target] <- showArgs builder - need [target] + [exe] <- showArgs builder + need [exe] --- Action 'with Gcc' returns an argument '--with-gcc=/path/to/gcc' and needs the builder +-- Action 'with Gcc' returns '--with-gcc=/path/to/gcc' and needs Gcc +-- Raises an error if the builder is not uniquely defined in config files with :: Builder -> Args with builder = do - let prefix = case builder of + let key = case builder of Ar -> "--with-ar=" Ld -> "--with-ld=" Gcc -> "--with-gcc=" @@ -70,18 +81,21 @@ with builder = do Happy -> "--with-happy=" GhcPkg _ -> "--with-ghc-pkg=" HsColour -> "--with-hscolour=" - [suffix] <- showArgs builder + [exe] <- showArgs builder needBuilder builder - return [prefix ++ suffix] + arg $ key ++ normaliseEx exe +-- Raises an error if the builder is not uniquely defined in config files run :: Builder -> Args -> Action () run builder args = do needBuilder builder [exe] <- showArgs builder - args' <- args - cmd [exe] args' + cmd [exe] =<< args -hsColourSrcs :: Condition -hsColourSrcs = do - [hscolour] <- showArgs HsColour - return $ hscolour /= "" +-- Check if the builder is uniquely defined in config files +exists :: Builder -> Condition +exists builder = do + exes <- showArgs builder + return $ case exes of + [_] -> True + _ -> False diff --git a/src/Package/Data.hs b/src/Package/Data.hs index eaaa072..f2805b8 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -68,7 +68,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = <> with (GhcPkg stage) <> customConfArgs settings <> (libraryArgs =<< ways settings) - <> when hsColourSrcs (with HsColour) + <> when (exists HsColour) (with HsColour) <> configureArgs stage settings <> when (stage == Stage0) bootPkgConstraints <> with Gcc From git at git.haskell.org Thu Oct 26 23:50:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Settings/Builders/Ghc.hs (see #60). (8ba5827) Message-ID: <20171026235008.0F2D03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ba5827108393cf6c37fff802db0126500e2bd0a/ghc >--------------------------------------------------------------- commit 8ba5827108393cf6c37fff802db0126500e2bd0a Author: Andrey Mokhov Date: Wed Dec 30 03:07:45 2015 +0000 Decompose Settings/Builders/Ghc.hs (see #60). >--------------------------------------------------------------- 8ba5827108393cf6c37fff802db0126500e2bd0a shaking-up-ghc.cabal | 4 ++++ src/Settings/Args.hs | 12 ++++++++++-- src/Settings/Builders/GenPrimopCode.hs | 1 - src/Settings/Builders/Ghc.hs | 35 ++++------------------------------ src/Settings/Builders/GhcCabal.hs | 3 +-- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Packages/Compiler.hs | 14 +++++++++----- src/Settings/Packages/Directory.hs | 6 +++--- src/Settings/Packages/Ghc.hs | 13 +++++++++++++ src/Settings/Packages/GhcCabal.hs | 34 +++++++++++++++++++++++++++++++++ src/Settings/Packages/Hp2ps.hs | 16 ++++++++++++++++ src/Settings/Packages/RunGhc.hs | 13 +++++++++++++ 12 files changed, 108 insertions(+), 45 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 8ba5827108393cf6c37fff802db0126500e2bd0a From git at git.haskell.org Thu Oct 26 23:50:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #152 from snowleopard/report-on-fix (27f303f) Message-ID: <20171026235008.CC6EB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27f303f3cedbd506c7373318e4f785354dc6ddaf/ghc >--------------------------------------------------------------- commit 27f303f3cedbd506c7373318e4f785354dc6ddaf Merge: 9178de2 462f78f Author: Andrey Mokhov Date: Mon Jan 11 17:51:16 2016 +0000 Merge pull request #152 from snowleopard/report-on-fix Report success on IRC only if the build was fixed [skip ci] >--------------------------------------------------------------- 27f303f3cedbd506c7373318e4f785354dc6ddaf .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:50:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename exists Builder to specified Builder, add comments. (7c9dfba) Message-ID: <20171026235009.10D0D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c9dfba2978d9dba7050e477938d3f99826d55f2/ghc >--------------------------------------------------------------- commit 7c9dfba2978d9dba7050e477938d3f99826d55f2 Author: Andrey Mokhov Date: Mon Jan 12 15:41:02 2015 +0000 Rename exists Builder to specified Builder, add comments. >--------------------------------------------------------------- 7c9dfba2978d9dba7050e477938d3f99826d55f2 src/Oracles/Builder.hs | 19 ++++++++++++------- src/Package/Data.hs | 2 +- 2 files changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index eefa7a2..16b5da5 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, exists + with, run, specified ) where import Data.Char @@ -46,6 +46,7 @@ instance ShowArgs Builder where ++ "' in configuration files." let cfgPathExe = if cfgPath /= "" then cfgPath -<.> exe else "" windows <- windowsHost + -- Note, below is different from FilePath.isAbsolute: if (windows && "/" `isPrefixOf` cfgPathExe) then do Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] @@ -58,9 +59,12 @@ instance ShowArgs Builder where -- to avoid needless recompilation when making changes to GHC's sources. In -- certain situations this can lead to build failures, in which case you -- should reset the flag (at least temporarily). + +-- Make sure the builder exists on the given path and rebuild it if out of date +-- Raise an error if the builder is not uniquely specified in config files needBuilder :: Builder -> Action () needBuilder ghc @ (Ghc stage) = do - [exe] <- showArgs ghc -- Raise an error if builder is not unique + [exe] <- showArgs ghc laxDeps <- test LaxDeps if laxDeps then orderOnly [exe] else need [exe] @@ -69,7 +73,7 @@ needBuilder builder = do need [exe] -- Action 'with Gcc' returns '--with-gcc=/path/to/gcc' and needs Gcc --- Raises an error if the builder is not uniquely defined in config files +-- Raises an error if the builder is not uniquely specified in config files with :: Builder -> Args with builder = do let key = case builder of @@ -85,16 +89,17 @@ with builder = do needBuilder builder arg $ key ++ normaliseEx exe --- Raises an error if the builder is not uniquely defined in config files +-- Run the builder with a given collection of arguments +-- Raises an error if the builder is not uniquely specified in config files run :: Builder -> Args -> Action () run builder args = do needBuilder builder [exe] <- showArgs builder cmd [exe] =<< args --- Check if the builder is uniquely defined in config files -exists :: Builder -> Condition -exists builder = do +-- Check if the builder is uniquely specified in config files +specified :: Builder -> Condition +specified builder = do exes <- showArgs builder return $ case exes of [_] -> True diff --git a/src/Package/Data.hs b/src/Package/Data.hs index f2805b8..7ff0d7d 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -68,7 +68,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = <> with (GhcPkg stage) <> customConfArgs settings <> (libraryArgs =<< ways settings) - <> when (exists HsColour) (with HsColour) + <> when (specified HsColour) (with HsColour) <> configureArgs stage settings <> when (stage == Stage0) bootPkgConstraints <> with Gcc From git at git.haskell.org Thu Oct 26 23:50:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a build rule for inplace/lib/settings. (0ceae64) Message-ID: <20171026235011.8A18C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ceae64327289b2cb79041cb75ec1e7c92af8546/ghc >--------------------------------------------------------------- commit 0ceae64327289b2cb79041cb75ec1e7c92af8546 Author: Andrey Mokhov Date: Wed Dec 30 15:16:18 2015 +0000 Add a build rule for inplace/lib/settings. >--------------------------------------------------------------- 0ceae64327289b2cb79041cb75ec1e7c92af8546 src/Rules/Install.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 13a0e00..2e74bd3 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -7,12 +7,14 @@ import Rules.Generate installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" - , "inplace/lib/platformConstants" ] + , "inplace/lib/platformConstants" + , "inplace/lib/settings" ] installRules :: Rules () installRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." where file <~ dir = file %> \out -> do let source = dir -/- takeFileName out From git at git.haskell.org Thu Oct 26 23:50:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch off -split-objs by default, fix #153. (1b226d9) Message-ID: <20171026235012.7321B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b226d992e53e3dee36fbfe22c0218477bc2bacb/ghc >--------------------------------------------------------------- commit 1b226d992e53e3dee36fbfe22c0218477bc2bacb Author: Andrey Mokhov Date: Tue Jan 12 02:08:58 2016 +0000 Switch off -split-objs by default, fix #153. >--------------------------------------------------------------- 1b226d992e53e3dee36fbfe22c0218477bc2bacb src/Settings/User.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 35eb86e..3cebe13 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -62,9 +62,9 @@ trackBuildSystem = True validating :: Bool validating = False --- To switch off split objects change to 'return False' +-- To switch on split objects use 'splitObjects = defaultSplitObjects', see #153 splitObjects :: Predicate -splitObjects = defaultSplitObjects +splitObjects = return False dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Thu Oct 26 23:50:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add options SplitObjectsBroken, GhcUnregisterised, DynamicExtension, ProjectVersion. (b5beba9) Message-ID: <20171026235012.A44503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b5beba96f0d4c6ba31e0e97d08ca54502acf8ec7/ghc >--------------------------------------------------------------- commit b5beba96f0d4c6ba31e0e97d08ca54502acf8ec7 Author: Andrey Mokhov Date: Tue Jan 13 02:17:53 2015 +0000 Add options SplitObjectsBroken, GhcUnregisterised, DynamicExtension, ProjectVersion. >--------------------------------------------------------------- b5beba96f0d4c6ba31e0e97d08ca54502acf8ec7 cfg/default.config.in | 6 ++++++ src/Oracles/Flag.hs | 4 ++++ src/Oracles/Option.hs | 34 ++++++++++++++++++++++++++-------- 3 files changed, 36 insertions(+), 8 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index b1eadd0..ac42e24 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -32,6 +32,8 @@ lax-dependencies = NO dynamic-ghc-programs = NO supports-package-key = @SUPPORTS_PACKAGE_KEY@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ +split-objects-broken = @SplitObjsBroken@ +ghc-unregisterised = @Unregisterised@ # Information about host and target systems: #=========================================== @@ -44,6 +46,10 @@ host-os-cpp = @HostOS_CPP@ cross-compiling = @CrossCompiling@ +dynamic-extension = @soext_target@ + +project-version = @ProjectVersion@ + # Compilation and linking flags: #=============================== diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index b93e4ab..e9aace5 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -21,6 +21,8 @@ data Flag = LaxDeps | Validating | SupportsPackageKey | SolarisBrokenShld + | SplitObjectsBroken + | GhcUnregisterised -- TODO: Give the warning *only once* per key test :: Flag -> Action Bool @@ -34,6 +36,8 @@ test flag = do Validating -> ("validating" , False) SupportsPackageKey -> ("supports-package-key" , False) SolarisBrokenShld -> ("solaris-broken-shld" , False) + SplitObjectsBroken -> ("split-objects-broken" , False) + GhcUnregisterised -> ("ghc-unregisterised" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ do putLoud $ "\nFlag '" diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 029b9bd..89192a7 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -1,13 +1,14 @@ {-# LANGUAGE NoImplicitPrelude #-} module Oracles.Option ( Option (..), - ghcWithInterpreter, platformSupportsSharedLibs, windowsHost + ghcWithInterpreter, platformSupportsSharedLibs, windowsHost, splitObjects ) where import Base import Oracles.Flag import Oracles.Base +-- TODO: separate single string options from multiple string ones. data Option = TargetOS | TargetArch | TargetPlatformFull @@ -21,6 +22,8 @@ data Option = TargetOS | GmpLibDirs | SrcHcOpts | HostOsCpp + | DynamicExtension + | ProjectVersion instance ShowArgs Option where showArgs opt = showArgs $ fmap words $ askConfig $ case opt of @@ -37,15 +40,17 @@ instance ShowArgs Option where GmpLibDirs -> "gmp-lib-dirs" SrcHcOpts -> "src-hc-opts" HostOsCpp -> "host-os-cpp" + DynamicExtension -> "dynamic-extension" + ProjectVersion -> "project-version" ghcWithInterpreter :: Condition ghcWithInterpreter = do [os] <- showArgs TargetOS [arch] <- showArgs TargetArch return $ - os `elem` [ "mingw32", "cygwin32", "linux", "solaris2" - , "freebsd", "dragonfly", "netbsd", "openbsd" - , "darwin", "kfreebsdgnu"] + os `elem` ["mingw32", "cygwin32", "linux", "solaris2", + "freebsd", "dragonfly", "netbsd", "openbsd", + "darwin", "kfreebsdgnu"] && arch `elem` ["i386", "x86_64", "powerpc", "sparc", "sparc64", "arm"] @@ -54,12 +59,25 @@ platformSupportsSharedLibs = do [platform] <- showArgs TargetPlatformFull solarisBrokenShld <- test SolarisBrokenShld return $ notElem platform $ - [ "powerpc-unknown-linux" - , "x86_64-unknown-mingw32" - , "i386-unknown-mingw32"] ++ - [ "i386-unknown-solaris2" | solarisBrokenShld ] + ["powerpc-unknown-linux", + "x86_64-unknown-mingw32", + "i386-unknown-mingw32"] ++ + ["i386-unknown-solaris2" | solarisBrokenShld] windowsHost :: Condition windowsHost = do [hostOsCpp] <- showArgs HostOsCpp return $ hostOsCpp `elem` ["mingw32", "cygwin32"] + +-- TODO: refactor helper Condition functions into a separate file +splitObjects :: Stage -> Condition +splitObjects stage = do + [os] <- showArgs TargetOS + [arch] <- showArgs TargetArch + splitObjectsBroken <- test SplitObjectsBroken + ghcUnregisterised <- test GhcUnregisterised + return $ not splitObjectsBroken && not ghcUnregisterised + && arch `elem` ["i386", "x86_64", "powerpc", "sparc"] + && os `elem` ["mingw32", "cygwin32", "linux", "darwin", + "solaris2", "freebsd", "dragonfly", "netbsd", + "openbsd"] From git at git.haskell.org Thu Oct 26 23:50:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for wrappers. (a1eab18) Message-ID: <20171026235015.110E13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1eab187eb929d2d82d2f093d4768849978973a4/ghc >--------------------------------------------------------------- commit a1eab187eb929d2d82d2f093d4768849978973a4 Author: Andrey Mokhov Date: Thu Dec 31 00:41:00 2015 +0000 Add support for wrappers. >--------------------------------------------------------------- a1eab187eb929d2d82d2f093d4768849978973a4 src/Rules/Program.hs | 120 ++++++++++++++++++++++++++++++---------------- src/Rules/Wrappers/Ghc.hs | 14 ++++++ src/Target.hs | 2 +- 3 files changed, 94 insertions(+), 42 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a1eab187eb929d2d82d2f093d4768849978973a4 From git at git.haskell.org Thu Oct 26 23:50:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Preliminary working state (5d4e182) Message-ID: <20171026235016.4642F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d4e18236b64fa400a66967cd7dbb8371b0e08b7/ghc >--------------------------------------------------------------- commit 5d4e18236b64fa400a66967cd7dbb8371b0e08b7 Author: Moritz Angermann Date: Tue Jan 12 14:56:53 2016 +0800 Preliminary working state This almost works. Yet we run into: ``` Build system error - cannot currently call askOracle: Reason: Within withResource using Resource ghc-cabal Question type: OracleQ CmdLineFlags Question value: OracleQ (CmdLineFlags ()) Move the askOracle call earlier/later ``` >--------------------------------------------------------------- 5d4e18236b64fa400a66967cd7dbb8371b0e08b7 shaking-up-ghc.cabal | 1 + src/Base.hs | 27 +++++++++++++++-- src/Main.hs | 7 ++++- src/Oracles/Config/CmdLineFlag.hs | 64 +++++++++++++++++++++++++++++++++++++++ src/Rules/Actions.hs | 20 +++++------- src/Rules/Library.hs | 9 +++--- src/Rules/Program.hs | 9 +++--- 7 files changed, 111 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5d4e18236b64fa400a66967cd7dbb8371b0e08b7 From git at git.haskell.org Thu Oct 26 23:50:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Record new progress. (2840dab) Message-ID: <20171026235016.800EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2840dab476a13a6f75463b6c34ec8e756e40cf06/ghc >--------------------------------------------------------------- commit 2840dab476a13a6f75463b6c34ec8e756e40cf06 Author: Andrey Mokhov Date: Tue Jan 13 02:18:57 2015 +0000 Record new progress. >--------------------------------------------------------------- 2840dab476a13a6f75463b6c34ec8e756e40cf06 doc/deepseq-build-progress.txt | 42 ++++++++++++++++++++++++++++-------------- 1 file changed, 28 insertions(+), 14 deletions(-) diff --git a/doc/deepseq-build-progress.txt b/doc/deepseq-build-progress.txt index 07214c6..f951d61 100644 --- a/doc/deepseq-build-progress.txt +++ b/doc/deepseq-build-progress.txt @@ -1,48 +1,62 @@ +# Skipping: "inplace/bin/ghc-cabal.exe" check libraries/deepseq -Skipping. - - +# Done: "inplace/bin/ghc-cabal.exe" configure libraries/deepseq dist-install "" --with-ghc="C:/msys/home/chEEtah/ghc/inplace/bin/ghc-stage1.exe" --with-ghc-pkg="C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe" --disable-library-for-ghci --enable-library-vanilla --enable-library-for-ghci --enable-library-profiling --disable-shared --configure-option=CFLAGS=" -fno-stack-protector " --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc-options=" -fno-stack-protector " --with-gcc="C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe" --with-ld="C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" --configure-option=--with-cc="C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe" --with-ar="/usr/bin/ar" --with-alex="/usr/local/bin/alex" --with-happy="/usr/local/bin/happy" -C:/msys/home/chEEtah/ghc/inplace/bin/ghc-cabal.exe configure libraries\deepseq dist-install --with-ghc= C:/msys/home/chEEtah/ghc/inplace/bin/ghc-stage1.exe --with-ghc-pkg= C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe --disable-library-for-ghci --enable-library-vanilla --enable-library-for-ghci --enable-library-profiling --disable-shared --configure-option=CFLAGS=-fno-stack-protector --configure-option=LDFLAGS= --configure-option=CPPFLAGS= --gcc-options=-fno-stack-protector --with-gcc= C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe --with-ld= C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe --configure-option=--with-cc= C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe --with-ar=C:/msys/usr/bin/ar.exe --with-alex=C:/msys/usr/local/bin/alex.exe --with-happy=C:/msys/usr/local/bin/happy.exe - Configuring deepseq-1.4.0.0... +# Done: "C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe" update --force libraries/deepseq/dist-install/inplace-pkg-config - C:/msys/home/chEEtah/ghc/inplace/bin/ghc-pkg.exe update --force libraries\deepseq\dist-install\inplace-pkg-config - Reading package info from "libraries/deepseq/dist-install/inplace-pkg-config" ... done. - +# Skipping: "rm" -f libraries/deepseq/dist-install/build/.depend-v-p.c_asm.tmp + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/.depend-v-p.c_asm.bit +# Skipping: echo "libraries/deepseq_dist-install_depfile_c_asm_EXISTS = YES" >> libraries/deepseq/dist-install/build/.depend-v-p.c_asm.tmp + +# Skipping: mv libraries/deepseq/dist-install/build/.depend-v-p.c_asm.tmp libraries/deepseq/dist-install/build/.depend-v-p.c_asm + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp +# Done: "inplace/bin/ghc-stage1.exe" -M -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -dep-makefile libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp -dep-suffix "" -dep-suffix "p_" -include-pkg-deps libraries/deepseq/./Control/DeepSeq.hs +# Skipping: echo "libraries/deepseq_dist-install_depfile_haskell_EXISTS = YES" >> libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp + +# Skipping: for dir in libraries/deepseq/dist-install/build/Control/; do if test ! -d $dir; then mkdir -p $dir; fi done -grep -v ' : [a-zA-Z]:/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp > libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 -sed -e '/hs$/ p' -e '/hs$/ s/o /hi /g' -e '/hs$/ s/:/ : %hi: %o /' -e '/hs$/ s/^/$(eval $(call hi-rule,/' -e '/hs$/ s/$/))/' -e '/hs-boot$/ p' -e '/hs-boot$/ s/o-boot /hi-boot /g' -e '/hs-boot$/ s/:/ : %hi-boot: %o-boot /' -e '/hs-boot$/ s/^/$(eval $(call hi-rule,/' -e '/hs-boot$/ s/$/))/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 > libraries/deepseq/dist-install/build/.depend-v-p.haskell +# Skipping: +grep -v ' : [a-zA-Z]:/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp > libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 +# Skipping: +sed -e '/hs$/ p' -e '/hs$/ s/o /hi /g' -e '/hs$/ s/:/ : %hi: %o /' -e '/hs$/ s/^/$(eval $(call hi-rule,/' -e '/hs$/ s/$/))/' -e '/hs-boot$/ p' -e '/hs-boot$/ s/o-boot /hi-boot /g' -e '/hs-boot$/ s/:/ : %hi-boot: %o-boot /' -e '/hs-boot$/ s/^/$(eval $(call hi-rule,/' -e '/hs-boot$/ s/$/))/' libraries/deepseq/dist-install/build/.depend-v-p.haskell.tmp2 > libraries/deepseq/dist-install/build/.depend-v-p.haskell +# Done: "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.o - - +# Skipping: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + +# Skipping: /usr/bin/find libraries/deepseq/dist-install/build/Control/DeepSeq_o_split -name '*.o' -print >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + +# Skipping: echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + +# Done: "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents /usr/bin/ar: creating libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents - - +# Done: "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.p_o From git at git.haskell.org Thu Oct 26 23:50:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing sources. (109a6f8) Message-ID: <20171026235018.81EF03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/109a6f843864def992865b81b0fea462e0fad7b4/ghc >--------------------------------------------------------------- commit 109a6f843864def992865b81b0fea462e0fad7b4 Author: Andrey Mokhov Date: Thu Dec 31 01:08:26 2015 +0000 Add missing sources. >--------------------------------------------------------------- 109a6f843864def992865b81b0fea462e0fad7b4 shaking-up-ghc.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index b60bf46..e7c3e28 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -54,6 +54,7 @@ executable ghc-shake , Rules.Package , Rules.Program , Rules.Resources + , Rules.Wrappers.Ghc , Settings , Settings.Args , Settings.Builders.Alex From git at git.haskell.org Thu Oct 26 23:50:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' into angerman/feature/build-info-flags (8dfe2b9) Message-ID: <20171026235020.466113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8dfe2b928d8e2d8eef9f45fb148764799e844257/ghc >--------------------------------------------------------------- commit 8dfe2b928d8e2d8eef9f45fb148764799e844257 Merge: 5d4e182 27f303f Author: Moritz Angermann Date: Tue Jan 12 14:57:35 2016 +0800 Merge branch 'master' into angerman/feature/build-info-flags # Conflicts: # src/Main.hs >--------------------------------------------------------------- 8dfe2b928d8e2d8eef9f45fb148764799e844257 .appveyor.yml | 10 +++++++++- .travis.yml | 3 ++- shaking-up-ghc.cabal | 3 +++ src/Main.hs | 7 ++++++- src/Rules/Generate.hs | 9 ++++++--- src/Settings/Builders/Ar.hs | 16 ++++------------ src/Settings/Builders/DeriveConstants.hs | 14 +++++--------- src/Test.hs | 28 ++++++++++++++++++++++++++++ src/Way.hs | 2 +- 9 files changed, 64 insertions(+), 28 deletions(-) diff --cc src/Main.hs index f65483d,dea793e..6d79cb8 --- a/src/Main.hs +++ b/src/Main.hs @@@ -11,15 -11,11 +11,19 @@@ import qualified Rules.Gm import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl ++<<<<<<< HEAD +import Oracles.Config.CmdLineFlag (cmdLineOracle, flags) ++======= + import qualified Test ++>>>>>>> master main :: IO () -main = shakeArgs options rules +main = shakeArgsWith options flags $ \cmdLineFlags targets -> + return . Just $ cmdLineOracle cmdLineFlags + >> if null targets then rules else want targets + >> withoutActions rules where + rules :: Rules () rules = mconcat [ Rules.Cabal.cabalRules , Rules.Config.configRules From git at git.haskell.org Thu Oct 26 23:50:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Work on way suffixes. (91ecc02) Message-ID: <20171026235020.7ABB33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91ecc023c94c9a694749024d1973e72ccc8c5336/ghc >--------------------------------------------------------------- commit 91ecc023c94c9a694749024d1973e72ccc8c5336 Author: Andrey Mokhov Date: Tue Jan 13 02:20:39 2015 +0000 Work on way suffixes. >--------------------------------------------------------------- 91ecc023c94c9a694749024d1973e72ccc8c5336 src/Ways.hs | 62 +++++++++++++++++++++++++++++++++++++++++++++++-------------- 1 file changed, 48 insertions(+), 14 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index c6d733c..b478a04 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -13,7 +13,7 @@ module Ways ( loggingDynamic, threadedLoggingDynamic, wayHcArgs, - suffix, + wayPrefix, hisuf, osuf, hcsuf, detectWay ) where @@ -43,7 +43,8 @@ logging = Way "l" [Logging] parallel = Way "mp" [Parallel] granSim = Way "gm" [GranSim] --- RTS only ways. TODO: do we need to define these here? +-- RTS only ways +-- TODO: do we need to define *only* these? Shall we generalise/simplify? threaded = Way "thr" [Threaded] threadedProfiling = Way "thr_p" [Threaded, Profiling] threadedLogging = Way "thr_l" [Threaded, Logging] @@ -88,19 +89,52 @@ wayHcArgs (Way _ units) = <> (units == [Debug] || units == [Debug, Dynamic]) arg ["-ticky", "-DTICKY_TICKY"] -suffix :: Way -> String -suffix way | way == vanilla = "" - | otherwise = tag way ++ "_" +wayPrefix :: Way -> String +wayPrefix way | way == vanilla = "" + | otherwise = tag way ++ "_" -hisuf, osuf, hcsuf :: Way -> String -hisuf = (++ "hi") . suffix -osuf = (++ "o" ) . suffix -hcsuf = (++ "hc") . suffix +hisuf, osuf, hcsuf, obootsuf, ssuf :: Way -> String +osuf = (++ "o" ) . wayPrefix +ssuf = (++ "s" ) . wayPrefix +hisuf = (++ "hi" ) . wayPrefix +hcsuf = (++ "hc" ) . wayPrefix +obootsuf = (++ "o-boot") . wayPrefix + +-- Note: in the previous build system libsuf was mysteriously different +-- from other suffixes. For example, in the profiling way it used to be +-- "_p.a" instead of ".p_a" which is how other suffixes work. I decided +-- to make all suffixes consistent: ".way_extension". +libsuf :: Way -> Action String +libsuf way = do + let staticSuffix = wayPrefix $ dropDynamic way + if Dynamic `notElem` units way + then return $ staticSuffix ++ "a" + else do + [extension] <- showArgs DynamicExtension + [version] <- showArgs ProjectVersion + return $ staticSuffix ++ "-ghc" ++ version ++ extension + +-- TODO: This may be slow -- optimise if overhead is significant. +dropDynamic :: Way -> Way +dropDynamic way + | way == dynamic = vanilla + | way == profilingDynamic = profiling + | way == threadedProfilingDynamic = threadedProfiling + | way == threadedDynamic = threaded + | way == threadedDebugDynamic = threadedDebug + | way == debugDynamic = debug + | way == loggingDynamic = logging + | way == threadedLoggingDynamic = threadedLogging + | otherwise = error $ "Cannot drop Dynamic from way " ++ tag way ++ "." -- Detect way from a given extension. Fail if the result is not unique. +-- TODO: This may be slow -- optimise if overhead is significant. detectWay :: FilePath -> Way -detectWay extension = case solutions of - [way] -> way - _ -> error $ "Cannot detect way from extension '" ++ extension ++ "'." - where - solutions = [w | f <- [hisuf, osuf, hcsuf], w <- allWays, f w == extension] +detectWay extension = + let prefix = reverse $ dropWhile (/= '_') $ reverse extension + result = filter ((== prefix) . wayPrefix) allWays + in + case result of + [way] -> way + _ -> error $ "Cannot detect way from extension '" + ++ extension ++ "'." From git at git.haskell.org Thu Oct 26 23:50:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Settings/Builders/GhcCabal.hs (see #60). (7cf7210) Message-ID: <20171026235021.E76D33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7cf7210ecee07729579f630ee93fa694e8e16635/ghc >--------------------------------------------------------------- commit 7cf7210ecee07729579f630ee93fa694e8e16635 Author: Andrey Mokhov Date: Thu Dec 31 02:20:32 2015 +0000 Decompose Settings/Builders/GhcCabal.hs (see #60). >--------------------------------------------------------------- 7cf7210ecee07729579f630ee93fa694e8e16635 shaking-up-ghc.cabal | 5 ++ src/Settings/Args.hs | 13 +++- src/Settings/Builders/Common.hs | 36 ++++++++++- src/Settings/Builders/DeriveConstants.hs | 7 +-- src/Settings/Builders/GhcCabal.hs | 102 ++----------------------------- src/Settings/Builders/Hsc2Hs.hs | 7 +-- src/Settings/Packages/Base.hs | 11 ++++ src/Settings/Packages/Compiler.hs | 32 +++++++++- src/Settings/Packages/Ghc.hs | 12 ++-- src/Settings/Packages/GhcPrim.hs | 9 +++ src/Settings/Packages/Haddock.hs | 9 +++ src/Settings/Packages/IntegerGmp.hs | 19 ++++++ 12 files changed, 145 insertions(+), 117 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 7cf7210ecee07729579f630ee93fa694e8e16635 From git at git.haskell.org Thu Oct 26 23:50:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Merge. (e519681) Message-ID: <20171026235023.B80673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e5196817511ddd50939d1f11b8ff2d6d856aa203/ghc >--------------------------------------------------------------- commit e5196817511ddd50939d1f11b8ff2d6d856aa203 Author: Moritz Angermann Date: Tue Jan 12 15:41:55 2016 +0800 Fix Merge. >--------------------------------------------------------------- e5196817511ddd50939d1f11b8ff2d6d856aa203 src/Main.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 6d79cb8..b372fa1 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -11,11 +11,8 @@ import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl -<<<<<<< HEAD -import Oracles.Config.CmdLineFlag (cmdLineOracle, flags) -======= import qualified Test ->>>>>>> master +import Oracles.Config.CmdLineFlag (cmdLineOracle, flags) main :: IO () main = shakeArgsWith options flags $ \cmdLineFlags targets -> From git at git.haskell.org Thu Oct 26 23:50:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageLibrary. (a325521) Message-ID: <20171026235023.D4C5F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a325521e7db63f1bda2b38f3e7988c364708ce43/ghc >--------------------------------------------------------------- commit a325521e7db63f1bda2b38f3e7988c364708ce43 Author: Andrey Mokhov Date: Tue Jan 13 02:21:14 2015 +0000 Add buildPackageLibrary. >--------------------------------------------------------------- a325521e7db63f1bda2b38f3e7988c364708ce43 src/Package.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 2fd10f1..a3fcf89 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -3,6 +3,7 @@ module Package (packageRules) where import Package.Base import Package.Data import Package.Compile +import Package.Library import Package.Dependencies -- See Package.Base for definitions of basic types @@ -16,12 +17,13 @@ buildPackage :: Package -> TodoItem -> Rules () buildPackage = buildPackageData <> buildPackageDependencies <> buildPackageCompile + <> buildPackageLibrary packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments - want [ "libraries/deepseq/dist-install/build/Control/DeepSeq.o" - , "libraries/deepseq/dist-install/build/Control/DeepSeq.p_o" ] + want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" + , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:50:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track wrapped binary. (49521c0) Message-ID: <20171026235025.5A9BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49521c02bdd181b57713c8f3e2bf111416b0df37/ghc >--------------------------------------------------------------- commit 49521c02bdd181b57713c8f3e2bf111416b0df37 Author: Andrey Mokhov Date: Thu Dec 31 02:28:23 2015 +0000 Track wrapped binary. >--------------------------------------------------------------- 49521c02bdd181b57713c8f3e2bf111416b0df37 src/Rules/Program.hs | 18 ++++++++++++------ 1 file changed, 12 insertions(+), 6 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 93c6a97..a1aaa2f 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -29,6 +29,11 @@ buildProgram _ target @ (PartialTarget stage pkg) = do let match file = case programPath stage pkg of Nothing -> False Just program -> program == file + matchWrapped file = case programPath stage pkg of + Nothing -> False + Just program -> case computeWrappedPath program of + Nothing -> False + Just wrappedProgram -> wrappedProgram == file match ?> \bin -> do windows <- windowsHost @@ -37,15 +42,16 @@ buildProgram _ target @ (PartialTarget stage pkg) = do else case find ((== target) . fst) wrappers of Nothing -> buildBinary target bin -- No wrapper found Just (_, wrapper) -> do - wrappedBin <- moveToLib bin - buildBinary target wrappedBin + let Just wrappedBin = computeWrappedPath bin + need [wrappedBin] buildWrapper target wrapper bin wrappedBin + matchWrapped ?> \bin -> buildBinary target bin + -- Replace programInplacePath with programInplaceLibPath in a given path -moveToLib :: FilePath -> Action FilePath -moveToLib path = case stripPrefix programInplacePath path of - Just suffix -> return $ programInplaceLibPath ++ suffix - Nothing -> putError $ "moveToLib: cannot move " ++ path +computeWrappedPath :: FilePath -> Maybe FilePath +computeWrappedPath = + fmap (programInplaceLibPath ++) . stripPrefix programInplacePath buildWrapper :: PartialTarget -> Wrapper -> FilePath -> FilePath -> Action () buildWrapper target @ (PartialTarget stage pkg) wrapper wrapperPath binPath = do From git at git.haskell.org Thu Oct 26 23:50:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Pony (5dd8bbb) Message-ID: <20171026235027.866AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5dd8bbb0090ebef875650ca7de8bc87aa37f54c9/ghc >--------------------------------------------------------------- commit 5dd8bbb0090ebef875650ca7de8bc87aa37f54c9 Author: Moritz Angermann Date: Tue Jan 12 15:42:56 2016 +0800 Adds Pony This fixes #92 for good. Together this fixes #134 almost entirely. >--------------------------------------------------------------- 5dd8bbb0090ebef875650ca7de8bc87aa37f54c9 src/Base.hs | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index c733226..ffe06d8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -142,26 +142,52 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg +-- | Render an action. renderAction :: String -> String -> String -> Action String renderAction what input output = buildInfo >>= return . \case Normal -> renderBox [ what , " input:" ++ input , " => output:" ++ output ] Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output - Pony -> " *** PONY NOT YET SUPPORTED ***" + Pony -> renderPony [ what + , " input:" ++ input + , " => output:" ++ output ] Dot -> "." None -> "" +-- | Render the successful build of a program renderProgram :: String -> String -> String -> Action String renderProgram name bin synopsis = return $ renderBox [ "Successfully built program " ++ name , "Executable: " ++ bin , "Program synopsis: " ++ synopsis ++ "."] +-- | Render the successful built of a library renderLibrary :: String -> String -> String -> Action String renderLibrary name lib synopsis = return $ renderBox [ "Successfully built library " ++ name , "Library: " ++ lib , "Library synopsis: " ++ synopsis ++ "."] +-- | Render the given set of lines next to our favorit unicorn Robert. +renderPony :: [String] -> String +renderPony ls = + unlines $ take (max (length ponyLines) (length boxLines)) $ + zipWith (++) (ponyLines ++ repeat ponyPadding) (boxLines ++ repeat "") + where + ponyLines :: [String] + ponyLines = [ " ,;,,;'" + , " ,;;'( Robert the spitting unicorn" + , " __ ,;;' ' \\ wants you to know" + , " /' '\\'~~'~' \\ /'\\.) that a task " + , " ,;( ) / |. / just finished! " + , " ,;' \\ /-.,,( ) \\ " + , " ^ ) / ) / )| Almost there! " + , " || || \\) " + , " (_\\ (_\\ " ] + ponyPadding :: String + ponyPadding = " " + boxLines :: [String] + boxLines = ["", "", ""] ++ (lines . renderBox $ ls) + -- | Render the given set of lines in a nice box of ASCII. -- -- The minimum width and whether to use Unicode symbols are hardcoded in the From git at git.haskell.org Thu Oct 26 23:50:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement search for *.hs and *.o files for a given package. (750a43f) Message-ID: <20171026235027.9875F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/750a43fcef635a38485a1a2ecc30412e557e44f0/ghc >--------------------------------------------------------------- commit 750a43fcef635a38485a1a2ecc30412e557e44f0 Author: Andrey Mokhov Date: Tue Jan 13 02:23:01 2015 +0000 Implement search for *.hs and *.o files for a given package. >--------------------------------------------------------------- 750a43fcef635a38485a1a2ecc30412e557e44f0 src/Package/Base.hs | 50 +++++++++++++++++++++++++++++++++++++++----------- 1 file changed, 39 insertions(+), 11 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index d9302b7..a8de80d 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -8,7 +8,8 @@ module Package.Base ( defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, bootPkgConstraints, - pathArgs, packageArgs, includeArgs, srcArgs + pathArgs, packageArgs, includeArgs, pkgHsSources, + pkgDepObjects, pkgLibObjects ) where import Base @@ -108,13 +109,40 @@ includeArgs path dist = <> arg "-optP-include" -- TODO: Shall we also add -cpp? <> concatArgs "-optP" (buildDir "autogen/cabal_macros.h") -srcArgs :: FilePath -> FilePath -> Args -srcArgs path pkgData = do - mods <- arg (Modules pkgData) - dirs <- arg (SrcDirs pkgData) - srcs <- getDirectoryFiles "" $ do - dir <- dirs - modPath <- map (replaceEq '.' pathSeparator) mods - extension <- ["hs", "lhs"] - return $ path dir modPath <.> extension - arg (map normaliseEx srcs) +pkgHsSources :: FilePath -> FilePath -> Action [FilePath] +pkgHsSources path dist = do + let pkgData = path dist "package-data.mk" + dirs <- map (path ) <$> arg (SrcDirs pkgData) + findModuleFiles pkgData dirs [".hs", ".lhs"] + +-- Find objects we depend on (we don't want to depend on split objects) +-- TODO: look for non-hs objects too +pkgDepObjects :: FilePath -> FilePath -> Way -> Action [FilePath] +pkgDepObjects path dist way = do + let pkgData = path dist "package-data.mk" + buildDir = path dist "build" + hs2obj = (buildDir ++) . drop (length path) . (-<.> osuf way) + srcs <- pkgHsSources path dist + return $ map hs2obj srcs + +-- Find objects that go to library +pkgLibObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] +pkgLibObjects path dist stage way = do + let pkgData = path dist "package-data.mk" + buildDir = path dist "build" + split <- splitObjects stage + if split + then do + let suffixes = ["_" ++ osuf way ++ "_split//*"] + findModuleFiles pkgData [buildDir] suffixes + else pkgDepObjects path dist way + +findModuleFiles :: FilePath -> [FilePath] -> [String] -> Action [FilePath] +findModuleFiles pkgData directories suffixes = do + mods <- arg (Modules pkgData) + files <- getDirectoryFiles "" $ do + dir <- directories + modPath <- map (replaceEq '.' pathSeparator) mods + suffix <- suffixes + return $ dir modPath ++ suffix + return $ map normaliseEx files From git at git.haskell.org Thu Oct 26 23:50:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fixes the -B path for the ghcWrapper. (d9d00b8) Message-ID: <20171026235028.BF7E73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9d00b86b79d998a288c5a2ffd2520d01b9c72e5/ghc >--------------------------------------------------------------- commit d9d00b86b79d998a288c5a2ffd2520d01b9c72e5 Author: Moritz Angermann Date: Thu Dec 31 10:40:37 2015 +0800 Fixes the -B path for the ghcWrapper. >--------------------------------------------------------------- d9d00b86b79d998a288c5a2ffd2520d01b9c72e5 src/Rules/Wrappers/Ghc.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Wrappers/Ghc.hs b/src/Rules/Wrappers/Ghc.hs index 93ceba0..c24bb70 100644 --- a/src/Rules/Wrappers/Ghc.hs +++ b/src/Rules/Wrappers/Ghc.hs @@ -11,4 +11,4 @@ ghcWrapper program = do return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) - ++ " -B" ++ (top -/- takeDirectory program) ++ " ${1+\"$@\"}" ] + ++ " -B" ++ (top -/- "inplace" -/- "lib") ++ " ${1+\"$@\"}" ] From git at git.haskell.org Thu Oct 26 23:50:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace Oracle with IO Ref (f794e73) Message-ID: <20171026235031.CFB983A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f794e7369f2b2b6e86f27d9587e5baf74cfc73e3/ghc >--------------------------------------------------------------- commit f794e7369f2b2b6e86f27d9587e5baf74cfc73e3 Author: Moritz Angermann Date: Tue Jan 12 18:03:59 2016 +0800 Replace Oracle with IO Ref >--------------------------------------------------------------- f794e7369f2b2b6e86f27d9587e5baf74cfc73e3 src/Base.hs | 21 ++++++++--------- src/Main.hs | 8 +++---- src/Oracles/Config/CmdLineFlag.hs | 48 ++++++++++++++++----------------------- src/Rules/Actions.hs | 6 ++--- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 4 ++-- 6 files changed, 40 insertions(+), 49 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 f794e7369f2b2b6e86f27d9587e5baf74cfc73e3 From git at git.haskell.org Thu Oct 26 23:50:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement terseRun and arArgs functions. (30138cb) Message-ID: <20171026235031.CE1683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30138cb17e6a67a6036b8c0077d393134c57edd2/ghc >--------------------------------------------------------------- commit 30138cb17e6a67a6036b8c0077d393134c57edd2 Author: Andrey Mokhov Date: Tue Jan 13 02:27:29 2015 +0000 Implement terseRun and arArgs functions. >--------------------------------------------------------------- 30138cb17e6a67a6036b8c0077d393134c57edd2 src/Oracles/Builder.hs | 35 ++++++++++++++++++++++++++++++++++- 1 file changed, 34 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 16b5da5..e4cd7da 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,8 @@ module Oracles.Builder ( Builder (..), - with, run, specified + with, run, terseRun, specified, + arArgs ) where import Data.Char @@ -24,6 +25,7 @@ data Builder = Ar | GhcCabal | Ghc Stage | GhcPkg Stage + deriving Show instance ShowArgs Builder where showArgs builder = showArgs $ fmap words $ do @@ -97,6 +99,33 @@ run builder args = do [exe] <- showArgs builder cmd [exe] =<< args +-- Run the builder with a given collection of arguments printing out a +-- terse commentary with only 'interesting' info for the builder. +-- Raises an error if the builder is not uniquely specified in config files +terseRun :: Builder -> Args -> Action () +terseRun builder args = do + needBuilder builder + [exe] <- showArgs builder + args' <- args + putNormal $ "--------\nRunning " ++ show builder ++ " with arguments:" + mapM_ (putNormal . (" " ++)) $ interestingInfo builder args' + putNormal "--------" + quietly $ cmd [exe] args' + +interestingInfo :: Builder -> [String] -> [String] +interestingInfo builder ss = case builder of + Ar -> prefixAndSuffix 3 1 ss + Ghc _ -> if head ss == "-M" + then prefixAndSuffix 1 1 ss + else prefixAndSuffix 0 4 ss + GhcPkg _ -> prefixAndSuffix 2 0 ss + GhcCabal -> prefixAndSuffix 3 0 ss + where + prefixAndSuffix n m ss = + if length ss <= n + m + then ss + else take n ss ++ ["..."] ++ drop (length ss - m) ss + -- Check if the builder is uniquely specified in config files specified :: Builder -> Condition specified builder = do @@ -104,3 +133,7 @@ specified builder = do return $ case exes of [_] -> True _ -> False + +-- TODO: generalise for other builders +arArgs :: Args +arArgs = arg "q" From git at git.haskell.org Thu Oct 26 23:50:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Settings/Builders/Haddock.hs (see #60). (4ade862) Message-ID: <20171026235032.2D68C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ade862d347dd04e9e61abcd0aa96a6864cb5962/ghc >--------------------------------------------------------------- commit 4ade862d347dd04e9e61abcd0aa96a6864cb5962 Author: Andrey Mokhov Date: Thu Dec 31 02:53:36 2015 +0000 Decompose Settings/Builders/Haddock.hs (see #60). >--------------------------------------------------------------- 4ade862d347dd04e9e61abcd0aa96a6864cb5962 src/Settings/Builders/Haddock.hs | 12 ++---------- src/Settings/Packages/Compiler.hs | 6 ++++-- 2 files changed, 6 insertions(+), 12 deletions(-) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index c8226fc..d626f26 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -43,19 +43,11 @@ haddockArgs = builder Haddock ? do arg "--source-module=src/%{MODULE/./-}.html" , specified HsColour ? arg "--source-entity=src/%{MODULE/./-}.html\\#%{NAME}" - , customPackageArgs , append =<< getInputs , arg "+RTS" , arg $ "-t" ++ path -/- "haddock.t" - , arg "--machine-readable" ] - -customPackageArgs :: Args -customPackageArgs = mconcat - [ package compiler ? stage1 ? - arg "--optghc=-DSTAGE=2" ] - -- TODO: move to getPackageSources - -- , package ghcPrim ? stage1 ? - -- arg "libraries/ghc-prim/dist-install/build/autogen/GHC/Prim.hs" ] + , arg "--machine-readable" + , arg "-RTS" ] -- From ghc.mk: -- # ----------------------------------------------- diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 88ccf2a..0dd7551 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -5,7 +5,7 @@ import Expression import GHC (compiler) import Oracles.Config.Setting import Oracles.Config.Flag -import Predicates (builder, builderGhc, package, notStage0) +import Predicates (builder, builderGhc, package, notStage0, stage1) import Settings compilerPackageArgs :: Args @@ -36,4 +36,6 @@ compilerPackageArgs = package compiler ? do ghciWithDebugger ? notStage0 ? arg "--ghc-option=-DDEBUGGER" , ghcProfiled ? - notStage0 ? arg "--ghc-pkg-option=--force" ] ] + notStage0 ? arg "--ghc-pkg-option=--force" ] + + , builder Haddock ? stage1 ? arg "--optghc=-DSTAGE=2" ] From git at git.haskell.org Thu Oct 26 23:50:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use terseRun and new configuration options. (efb5972) Message-ID: <20171026235035.9E5B23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efb59728189c8a5bd9270d1c3f00787ed4b27913/ghc >--------------------------------------------------------------- commit efb59728189c8a5bd9270d1c3f00787ed4b27913 Author: Andrey Mokhov Date: Tue Jan 13 02:29:17 2015 +0000 Use terseRun and new configuration options. >--------------------------------------------------------------- efb59728189c8a5bd9270d1c3f00787ed4b27913 src/Package/Compile.hs | 4 ++-- src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 6 +++--- 3 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 50cf412..6badbb7 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -43,7 +43,7 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = let deps = concat $ snd $ unzip $ filter ((== out) . fst) depContents srcs = filter ("//*hs" ?==) deps -- TODO: handle *.c sources need deps - run (Ghc stage) $ suffixArgs way + terseRun (Ghc stage) $ suffixArgs way <> wayHcArgs way <> arg SrcHcOpts <> packageArgs stage pkgData @@ -51,6 +51,6 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = -- TODO: now we have both -O and -O2 <> arg ["-Wall", "-XHaskell2010", "-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir - <> arg "-split-objs" + <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) <> arg ["-o", out] diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 7ff0d7d..a73a521 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -93,6 +93,6 @@ buildPackageData (Package name path _) (stage, dist, settings) = need ["shake/src/Package/Data.hs"] need [path name <.> "cabal"] when (doesFileExist $ configure <.> "ac") $ need [configure] - run GhcCabal cabalArgs - when (registerPackage settings) $ run (GhcPkg stage) ghcPkgArgs + terseRun GhcCabal cabalArgs + when (registerPackage settings) $ terseRun (GhcPkg stage) ghcPkgArgs postProcessPackageData $ pathDist "package-data.mk" diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 1cb512d..f3a494b 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -10,13 +10,13 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = in (buildDir name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] - run (Ghc stage) $ arg "-M" + terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData <> includeArgs path dist <> productArgs ["-odir", "-stubdir"] buildDir <> arg ["-dep-makefile", out] - <> productArgs "-dep-suffix" (map suffix <$> ways settings) - <> srcArgs path pkgData + <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) + <> arg (pkgHsSources path dist) -- TODO: Check that skipping all _HC_OPTS is safe. -- <> arg SrcHcOpts -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? From git at git.haskell.org Thu Oct 26 23:50:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add dependencies, fix #155. (85799a5) Message-ID: <20171026235035.DD5043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/85799a569efbace0d6fdc168c6ddff0a015d1df8/ghc >--------------------------------------------------------------- commit 85799a569efbace0d6fdc168c6ddff0a015d1df8 Author: Andrey Mokhov Date: Tue Jan 12 17:25:00 2016 +0000 Add dependencies, fix #155. [skip ci] >--------------------------------------------------------------- 85799a569efbace0d6fdc168c6ddff0a015d1df8 README.md | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index fe6a909..823e472 100644 --- a/README.md +++ b/README.md @@ -12,7 +12,7 @@ on the [wiki page][ghc-shake-wiki] and in this [blog post][shake-blog-post]. This is supposed to go into the `shake-build` directory of the GHC source tree. -[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc) +[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc). Trying it --------- @@ -23,6 +23,9 @@ identical to those for the `make` build system. This means that you don't need to adjust anything if you are already familiar with building ghc using the `make` build system. +Furthermore, we depend on the following packages which need to be installed: +`ansi-terminal`, `mtl`, `shake`, `quickcheck`. + ### Getting the source and configuring GHC ```bash @@ -51,7 +54,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). +To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (#131). How to contribute From git at git.haskell.org Thu Oct 26 23:50:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #65 from angerman/fix-B (75ebcfb) Message-ID: <20171026235036.2B4DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/75ebcfb2b778e71b4ec920a63804fe09597e8f17/ghc >--------------------------------------------------------------- commit 75ebcfb2b778e71b4ec920a63804fe09597e8f17 Merge: 4ade862 d9d00b8 Author: Andrey Mokhov Date: Thu Dec 31 02:54:19 2015 +0000 Merge pull request #65 from angerman/fix-B Fixes the -B path for the ghcWrapper. >--------------------------------------------------------------- 75ebcfb2b778e71b4ec920a63804fe09597e8f17 src/Rules/Wrappers/Ghc.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:50:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement new build rule: buildPackageLibrary. (2143dce) Message-ID: <20171026235039.A5F3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2143dce721122b3e9e0b08fb4691160305f0ba99/ghc >--------------------------------------------------------------- commit 2143dce721122b3e9e0b08fb4691160305f0ba99 Author: Andrey Mokhov Date: Tue Jan 13 02:30:01 2015 +0000 Implement new build rule: buildPackageLibrary. >--------------------------------------------------------------- 2143dce721122b3e9e0b08fb4691160305f0ba99 src/Package/Library.hs | 25 +++++++++++++++++++++++++ 1 file changed, 25 insertions(+) diff --git a/src/Package/Library.hs b/src/Package/Library.hs new file mode 100644 index 0000000..9598b1a --- /dev/null +++ b/src/Package/Library.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module Package.Library (buildPackageLibrary) where + +import Package.Base + +{- "/usr/bin/ar" q +libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a + at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents +-} + +-- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents +-- AR_OPTS = $(SRC_AR_OPTS) $(WAY$(_way)_AR_OPTS) $(EXTRA_AR_OPTS) + +buildPackageLibrary :: Package -> TodoItem -> Rules () +buildPackageLibrary (Package _ path _) (stage, dist, _) = + let buildDir = path dist "build" + pkgData = path dist "package-data.mk" + in + (buildDir "*a") %> \out -> do + let way = detectWay $ tail $ takeExtension out + need ["shake/src/Package/Library.hs"] + depObjs <- pkgDepObjects path dist way + need depObjs + libObjs <- pkgLibObjects path dist stage way + terseRun Ar $ arArgs <+> out <+> libObjs From git at git.haskell.org Thu Oct 26 23:50:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix compilerPackageArgs (Haddock builder). (02b0d75) Message-ID: <20171026235039.AD74B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02b0d758636e8b9cf79845d7cf786c3154bfad28/ghc >--------------------------------------------------------------- commit 02b0d758636e8b9cf79845d7cf786c3154bfad28 Author: Andrey Mokhov Date: Thu Dec 31 12:15:02 2015 +0000 Fix compilerPackageArgs (Haddock builder). >--------------------------------------------------------------- 02b0d758636e8b9cf79845d7cf786c3154bfad28 src/Settings/Packages/Compiler.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 0dd7551..c2f31e6 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -5,16 +5,17 @@ import Expression import GHC (compiler) import Oracles.Config.Setting import Oracles.Config.Flag -import Predicates (builder, builderGhc, package, notStage0, stage1) +import Predicates (builder, builderGhc, package, notStage0) import Settings compilerPackageArgs :: Args compilerPackageArgs = package compiler ? do stage <- getStage rtsWays <- getRtsWays + path <- getTargetPath mconcat [ builder Alex ? arg "--latin1" - , builderGhc ? arg ("-I" ++ pkgPath compiler -/- stageString stage) + , builderGhc ? arg ("-I" ++ path) , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) @@ -38,4 +39,4 @@ compilerPackageArgs = package compiler ? do , ghcProfiled ? notStage0 ? arg "--ghc-pkg-option=--force" ] - , builder Haddock ? stage1 ? arg "--optghc=-DSTAGE=2" ] + , builder Haddock ? arg ("--optghc=-I" ++ path) ] From git at git.haskell.org Thu Oct 26 23:50:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (a482625) Message-ID: <20171026235039.C947F3A5EC@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a482625b00358fd14646bac23a7911113c394157/ghc >--------------------------------------------------------------- commit a482625b00358fd14646bac23a7911113c394157 Author: Andrey Mokhov Date: Tue Jan 12 17:37:02 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- a482625b00358fd14646bac23a7911113c394157 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 823e472..4226415 100644 --- a/README.md +++ b/README.md @@ -17,7 +17,7 @@ This is supposed to go into the `shake-build` directory of the GHC source tree. Trying it --------- -Please see the [Preparation][ghc-preparation] on the haskell wiki +Please see the [Preparation][ghc-preparation] on the GHC wiki for general preparation. The preparation steps for the `shake` build system are identical to those for the `make` build system. This means that you don't need to adjust anything if you are already familiar with building ghc using the `make` @@ -54,7 +54,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (#131). +To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality ([#131](https://github.com/snowleopard/shaking-up-ghc/issues/131)). How to contribute From git at git.haskell.org Thu Oct 26 23:50:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove old library files before calling Ar. (5aa3add) Message-ID: <20171026235043.3E9553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5aa3addc4ed59f1984e040415d707f4067f82007/ghc >--------------------------------------------------------------- commit 5aa3addc4ed59f1984e040415d707f4067f82007 Author: Andrey Mokhov Date: Tue Jan 13 02:45:49 2015 +0000 Remove old library files before calling Ar. >--------------------------------------------------------------- 5aa3addc4ed59f1984e040415d707f4067f82007 src/Package/Library.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 9598b1a..0c2e1f8 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -22,4 +22,5 @@ buildPackageLibrary (Package _ path _) (stage, dist, _) = depObjs <- pkgDepObjects path dist way need depObjs libObjs <- pkgLibObjects path dist stage way + liftIO $ removeFiles "" [out] terseRun Ar $ arArgs <+> out <+> libObjs From git at git.haskell.org Thu Oct 26 23:50:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow users to choose which 'make' to use. (43d5847) Message-ID: <20171026235043.ADCF83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/43d5847155ff33dd67929164d49358fc82985944/ghc >--------------------------------------------------------------- commit 43d5847155ff33dd67929164d49358fc82985944 Author: Andrey Mokhov Date: Tue Jan 12 18:12:14 2016 +0000 Allow users to choose which 'make' to use. Fix #157. [skip ci] >--------------------------------------------------------------- 43d5847155ff33dd67929164d49358fc82985944 src/Rules/Actions.hs | 2 +- src/Settings/User.hs | 7 ++++++- 2 files changed, 7 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 338bec3..0600d82 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -105,7 +105,7 @@ runMake dir args = do need [dir -/- "Makefile"] let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir] args + quietly $ cmd Shell (EchoStdout False) makeCommand ["-C", dir] args runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 3cebe13..3d08ecd 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors, splitObjects + verboseCommands, turnWarningsIntoErrors, splitObjects, makeCommand ) where import GHC @@ -101,3 +101,8 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False + +-- | Specify which @make@ command to use, for example set to "gmake" for +-- @GNU make at . +makeCommand :: FilePath +makeCommand = "make" From git at git.haskell.org Thu Oct 26 23:50:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: ghcPkg Wrapper (aee3088) Message-ID: <20171026235043.8F2993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aee308892e923e8f2ba24d912fc3197599ef47a8/ghc >--------------------------------------------------------------- commit aee308892e923e8f2ba24d912fc3197599ef47a8 Author: Moritz Angermann Date: Thu Dec 31 20:21:13 2015 +0800 ghcPkg Wrapper >--------------------------------------------------------------- aee308892e923e8f2ba24d912fc3197599ef47a8 shaking-up-ghc.cabal | 1 + src/Rules/Program.hs | 4 +++- src/Rules/Wrappers/GhcPkg.hs | 20 ++++++++++++++++++++ 3 files changed, 24 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index cfa55ff..2c75566 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -55,6 +55,7 @@ executable ghc-shake , Rules.Program , Rules.Resources , Rules.Wrappers.Ghc + , Rules.Wrappers.GhcPkg , Settings , Settings.Args , Settings.Builders.Alex diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index a1aaa2f..75314c3 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -10,6 +10,7 @@ import Rules.Actions import Rules.Library import Rules.Resources import Rules.Wrappers.Ghc +import Rules.Wrappers.GhcPkg import Settings import Settings.Builders.GhcCabal @@ -22,7 +23,8 @@ type Wrapper = FilePath -> Expr String -- List of wrappers we build wrappers :: [(PartialTarget, Wrapper)] -wrappers = [(PartialTarget Stage0 ghc, ghcWrapper)] +wrappers = [ (PartialTarget Stage0 ghc, ghcWrapper) + , (PartialTarget Stage0 ghcPkg, ghcPkgWrapper)] buildProgram :: Resources -> PartialTarget -> Rules () buildProgram _ target @ (PartialTarget stage pkg) = do diff --git a/src/Rules/Wrappers/GhcPkg.hs b/src/Rules/Wrappers/GhcPkg.hs new file mode 100644 index 0000000..7edc43c --- /dev/null +++ b/src/Rules/Wrappers/GhcPkg.hs @@ -0,0 +1,20 @@ +module Rules.Wrappers.GhcPkg (ghcPkgWrapper) where + +import Base +import Expression +import Oracles + +-- Note about wrapper: +-- bindir is usually GhcSourcePath / inplace / bin +-- topdir is usually GhcSourcePath / inplace / lib +-- datadir is usually the same as topdir + +ghcPkgWrapper :: FilePath -> Expr String +ghcPkgWrapper program = do + lift $ need [sourcePath -/- "Rules/Wrappers/GhcPkg.hs"] + top <- getSetting GhcSourcePath + let pkgConf = top -/- "inplace" -/- "lib" -/- "package.conf.d" + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (top -/- program) + ++ " --global-package-db " ++ pkgConf ++ " ${1+\"$@\"}" ] From git at git.haskell.org Thu Oct 26 23:50:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve terseRun. (4fcb471) Message-ID: <20171026235046.D9DE33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fcb471826530ba60abdc40b2ed4304910edf24a/ghc >--------------------------------------------------------------- commit 4fcb471826530ba60abdc40b2ed4304910edf24a Author: Andrey Mokhov Date: Tue Jan 13 03:05:35 2015 +0000 Improve terseRun. >--------------------------------------------------------------- 4fcb471826530ba60abdc40b2ed4304910edf24a src/Oracles/Builder.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index e4cd7da..ffc3cf5 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -122,9 +122,13 @@ interestingInfo builder ss = case builder of GhcCabal -> prefixAndSuffix 3 0 ss where prefixAndSuffix n m ss = - if length ss <= n + m + if length ss <= n + m + 1 then ss - else take n ss ++ ["..."] ++ drop (length ss - m) ss + else take n ss + ++ ["... skipping " + ++ show (length ss - n - m) + ++ " arguments ..."] + ++ drop (length ss - m) ss -- Check if the builder is uniquely specified in config files specified :: Builder -> Condition From git at git.haskell.org Thu Oct 26 23:50:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #68 from angerman/wrapper/ghc-pkg (c720603) Message-ID: <20171026235047.B82673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7206034ba32d2a14e583c03580826ddb28a0aa4/ghc >--------------------------------------------------------------- commit c7206034ba32d2a14e583c03580826ddb28a0aa4 Merge: 02b0d75 aee3088 Author: Andrey Mokhov Date: Thu Dec 31 12:27:30 2015 +0000 Merge pull request #68 from angerman/wrapper/ghc-pkg ghcPkg Wrapper >--------------------------------------------------------------- c7206034ba32d2a14e583c03580826ddb28a0aa4 shaking-up-ghc.cabal | 1 + src/Rules/Program.hs | 4 +++- src/Rules/Wrappers/GhcPkg.hs | 20 ++++++++++++++++++++ 3 files changed, 24 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:50:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create .build/stage0 for libffi to be moved to. (31dbe92) Message-ID: <20171026235047.E78193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31dbe92dcfd55c17c8395945050aad240fdd640c/ghc >--------------------------------------------------------------- commit 31dbe92dcfd55c17c8395945050aad240fdd640c Author: Andrey Mokhov Date: Tue Jan 12 21:54:53 2016 +0000 Create .build/stage0 for libffi to be moved to. Fix #160. [skip ci] >--------------------------------------------------------------- 31dbe92dcfd55c17c8395945050aad240fdd640c src/Rules/Libffi.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 7e811ba..7dd0376 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -75,6 +75,8 @@ libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] + createDirectory $ buildRootPath -/- "stage0" + tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] when (length tarballs /= 1) $ putError $ "libffiRules: exactly one libffi tarball expected" From git at git.haskell.org Thu Oct 26 23:50:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise buildPackageDependencies rule. (7c45e18) Message-ID: <20171026235050.5C4393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c45e18e0d1ef091aac126e9a316ac9cd5f0a2bb/ghc >--------------------------------------------------------------- commit 7c45e18e0d1ef091aac126e9a316ac9cd5f0a2bb Author: Andrey Mokhov Date: Tue Jan 13 03:13:10 2015 +0000 Optimise buildPackageDependencies rule. >--------------------------------------------------------------- 7c45e18e0d1ef091aac126e9a316ac9cd5f0a2bb src/Package/Dependencies.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index f3a494b..7390b2e 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -14,10 +14,13 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = <> packageArgs stage pkgData <> includeArgs path dist <> productArgs ["-odir", "-stubdir"] buildDir - <> arg ["-dep-makefile", out] + <> arg ["-dep-makefile", out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) <> arg (pkgHsSources path dist) -- TODO: Check that skipping all _HC_OPTS is safe. -- <> arg SrcHcOpts -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? -- <> wayHcOpts vanilla + -- Avoid rebuilding dependecies of out if it hasn't changed: + copyFileChanged (out <.> "new") out + removeFilesAfter "." [out <.> "new"] From git at git.haskell.org Thu Oct 26 23:50:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initialise inplace/lib/package.conf.d, fix #66. (84704cf) Message-ID: <20171026235051.EDBD33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84704cf2cf9324a09153b65f667581d03671e6ed/ghc >--------------------------------------------------------------- commit 84704cf2cf9324a09153b65f667581d03671e6ed Author: Andrey Mokhov Date: Thu Dec 31 13:53:29 2015 +0000 Initialise inplace/lib/package.conf.d, fix #66. >--------------------------------------------------------------- 84704cf2cf9324a09153b65f667581d03671e6ed src/Base.hs | 15 ++++++++++----- src/Rules/Cabal.hs | 20 +++++++++++--------- src/Rules/Wrappers/GhcPkg.hs | 5 +++-- src/Settings/Builders/GhcCabal.hs | 12 +++++++----- src/Settings/Builders/GhcPkg.hs | 7 +++++-- src/Stage.hs | 2 +- 6 files changed, 37 insertions(+), 24 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 25a69df..a127299 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,7 +16,7 @@ module Base ( -- * Paths shakeFilesPath, configPath, sourcePath, programInplacePath, bootPackageConstraints, packageDependencies, - bootstrappingConf, bootstrappingConfInitialised, + packageConfiguration, packageConfigurationInitialised, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, @@ -41,6 +41,9 @@ import System.Console.ANSI import qualified System.Directory as IO import System.IO +-- TODO: reexport Stage, etc.? +import Stage + -- Build system files and paths shakePath :: FilePath shakePath = "shake-build" @@ -65,11 +68,13 @@ bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" packageDependencies :: FilePath packageDependencies = shakeFilesPath -/- "package-dependencies" -bootstrappingConf :: FilePath -bootstrappingConf = "libraries/bootstrapping.conf" +packageConfiguration :: Stage -> FilePath +packageConfiguration Stage0 = "libraries/bootstrapping.conf" +packageConfiguration _ = "inplace/lib/package.conf.d" -bootstrappingConfInitialised :: FilePath -bootstrappingConfInitialised = shakeFilesPath -/- "bootstrapping-conf-initialised" +packageConfigurationInitialised :: Stage -> FilePath +packageConfigurationInitialised stage = + shakeFilesPath -/- "package-configuration-initialised-" ++ stageString stage -- Utility functions -- | Find and replace all occurrences of a value in a list diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 9239e67..ab7622c 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -39,17 +39,19 @@ cabalRules = do return . unwords $ pkgNameString pkg : sort depNames writeFileChanged out . unlines $ pkgDeps - -- When the file exists, the bootstrappingConf has been initialised + -- When the file exists, the packageConfiguration has been initialised -- TODO: get rid of an extra file? - bootstrappingConfInitialised %> \out -> do - removeDirectoryIfExists bootstrappingConf - -- TODO: can we get rid of this fake target? - let target = PartialTarget Stage0 cabal - build $ fullTarget target (GhcPkg Stage0) [] [bootstrappingConf] - let message = "Successfully initialised " ++ bootstrappingConf - writeFileChanged out message - putSuccess message + forM_ [Stage0 ..] $ \stage -> + packageConfigurationInitialised stage %> \out -> do + let target = PartialTarget stage cabal + pkgConf = packageConfiguration stage + removeDirectoryIfExists pkgConf + -- TODO: can we get rid of this fake target? + build $ fullTarget target (GhcPkg stage) [] [pkgConf] + let message = "Successfully initialised " ++ pkgConf + writeFileChanged out message + putSuccess message collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] diff --git a/src/Rules/Wrappers/GhcPkg.hs b/src/Rules/Wrappers/GhcPkg.hs index 7edc43c..3f70617 100644 --- a/src/Rules/Wrappers/GhcPkg.hs +++ b/src/Rules/Wrappers/GhcPkg.hs @@ -12,8 +12,9 @@ import Oracles ghcPkgWrapper :: FilePath -> Expr String ghcPkgWrapper program = do lift $ need [sourcePath -/- "Rules/Wrappers/GhcPkg.hs"] - top <- getSetting GhcSourcePath - let pkgConf = top -/- "inplace" -/- "lib" -/- "package.conf.d" + top <- getSetting GhcSourcePath + stage <- getStage + let pkgConf = top -/- packageConfiguration stage return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 597f591..06b2a63 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -85,11 +85,13 @@ configureArgs = do , conf "--with-cc" $ argStagedBuilderPath Gcc ] bootPackageDbArgs :: Args -bootPackageDbArgs = stage0 ? do - path <- getSetting GhcSourcePath - lift $ need [bootstrappingConfInitialised] - prefix <- ifM builderGhc (return "-package-db ") (return "--package-db=") - arg $ prefix ++ path -/- bootstrappingConf +bootPackageDbArgs = do + stage <- getStage + lift $ need [packageConfigurationInitialised stage] + stage0 ? do + path <- getSetting GhcSourcePath + prefix <- ifM builderGhc (return "-package-db ") (return "--package-db=") + arg $ prefix ++ path -/- packageConfiguration Stage0 packageConstraints :: Args packageConstraints = stage0 ? do diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index e79a360..c8e25ff 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -10,13 +10,16 @@ import Settings.Builders.GhcCabal ghcPkgArgs :: Args ghcPkgArgs = stagedBuilder GhcPkg ? (initArgs <> updateArgs) +initPredicate :: Predicate +initPredicate = orM $ map (file . packageConfiguration) [Stage0 ..] + initArgs :: Args -initArgs = file bootstrappingConf ? do +initArgs = initPredicate ? do mconcat [ arg "init" , arg =<< getOutput ] updateArgs :: Args -updateArgs = notM (file bootstrappingConf) ? do +updateArgs = notM initPredicate ? do path <- getTargetPath mconcat [ arg "update" , arg "--force" diff --git a/src/Stage.hs b/src/Stage.hs index 70fe6ba..144aa29 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} module Stage (Stage (..), stageString) where -import Base +import Development.Shake.Classes import GHC.Generics (Generic) -- TODO: explain stages From git at git.haskell.org Thu Oct 26 23:50:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't move from a temporary directory. (86f3052) Message-ID: <20171026235052.2F54A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86f3052c2cd738427136899bfe3a47210c4d98a5/ghc >--------------------------------------------------------------- commit 86f3052c2cd738427136899bfe3a47210c4d98a5 Author: Andrey Mokhov Date: Tue Jan 12 22:22:34 2016 +0000 Don't move from a temporary directory. Fix #156. >--------------------------------------------------------------- 86f3052c2cd738427136899bfe3a47210c4d98a5 src/Rules/Libffi.hs | 14 +++++--------- 1 file changed, 5 insertions(+), 9 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 7dd0376..0c38cd2 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -27,9 +27,6 @@ libffiBuild = buildRootPath -/- "stage0/libffi" libffiLibrary :: FilePath libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" -libffiMakefile :: FilePath -libffiMakefile = libffiBuild -/- "Makefile.in" - fixLibffiMakefile :: String -> String fixLibffiMakefile = unlines . map ( replace "-MD" "-MMD" @@ -75,7 +72,7 @@ libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] - createDirectory $ buildRootPath -/- "stage0" + createDirectory $ buildRootPath -/- stageString Stage0 tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] when (length tarballs /= 1) $ @@ -85,12 +82,11 @@ libffiRules = do need tarballs let libname = dropExtension . dropExtension . takeFileName $ head tarballs - withTempDir $ \tmpDir -> do - let unifiedTmpDir = unifyPath tmpDir - build $ fullTarget libffiTarget Tar tarballs [unifiedTmpDir] - moveDirectory (unifiedTmpDir -/- libname) libffiBuild + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + actionFinally (moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] - fixFile libffiMakefile fixLibffiMakefile + fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile forM_ ["config.guess", "config.sub"] $ \file -> copyFile file (libffiBuild -/- file) From git at git.haskell.org Thu Oct 26 23:50:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise buildPackageDependencies rule. (1e5c095) Message-ID: <20171026235053.E1A733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1e5c0952d044d8c1c16988e221d014443b04fb19/ghc >--------------------------------------------------------------- commit 1e5c0952d044d8c1c16988e221d014443b04fb19 Author: Andrey Mokhov Date: Tue Jan 13 03:30:54 2015 +0000 Optimise buildPackageDependencies rule. >--------------------------------------------------------------- 1e5c0952d044d8c1c16988e221d014443b04fb19 src/Package/Dependencies.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 7390b2e..6339adb 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -22,5 +22,7 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? -- <> wayHcOpts vanilla -- Avoid rebuilding dependecies of out if it hasn't changed: - copyFileChanged (out <.> "new") out + -- Note: cannot use copyFileChanged as it depends on the source file + deps <- liftIO $ readFile $ out <.> "new" + writeFileChanged out deps removeFilesAfter "." [out <.> "new"] From git at git.haskell.org Thu Oct 26 23:50:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't re-initialise packageConfiguration in Stage2, see #66. (e2fb954) Message-ID: <20171026235055.579E83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2fb95438402a6a76eff23be687020255a5cc218/ghc >--------------------------------------------------------------- commit e2fb95438402a6a76eff23be687020255a5cc218 Author: Andrey Mokhov Date: Thu Dec 31 14:06:07 2015 +0000 Don't re-initialise packageConfiguration in Stage2, see #66. >--------------------------------------------------------------- e2fb95438402a6a76eff23be687020255a5cc218 src/Base.hs | 4 +++- src/Rules/Cabal.hs | 2 +- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a127299..6f3b6d6 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -72,9 +72,11 @@ packageConfiguration :: Stage -> FilePath packageConfiguration Stage0 = "libraries/bootstrapping.conf" packageConfiguration _ = "inplace/lib/package.conf.d" +-- StageN, N > 0, share the same packageConfiguration (see above) packageConfigurationInitialised :: Stage -> FilePath packageConfigurationInitialised stage = - shakeFilesPath -/- "package-configuration-initialised-" ++ stageString stage + shakeFilesPath -/- "package-configuration-initialised-" + ++ stageString (min stage Stage1) -- Utility functions -- | Find and replace all occurrences of a value in a list diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index ab7622c..bf4c8f6 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -42,7 +42,7 @@ cabalRules = do -- When the file exists, the packageConfiguration has been initialised -- TODO: get rid of an extra file? - forM_ [Stage0 ..] $ \stage -> + forM_ [Stage0, Stage1] $ \stage -> packageConfigurationInitialised stage %> \out -> do let target = PartialTarget stage cabal pkgConf = packageConfiguration stage From git at git.haskell.org Thu Oct 26 23:50:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add removeDirectory to Rules/Actions, seems to fit (db11fb0) Message-ID: <20171026235055.A13A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db11fb04e50c4cc46a2e3286adf0b67acbc82b47/ghc >--------------------------------------------------------------- commit db11fb04e50c4cc46a2e3286adf0b67acbc82b47 Author: Neil Mitchell Date: Tue Jan 12 22:33:21 2016 +0000 Add removeDirectory to Rules/Actions, seems to fit >--------------------------------------------------------------- db11fb04e50c4cc46a2e3286adf0b67acbc82b47 src/Rules/Actions.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 0600d82..a968160 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,6 +1,6 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( - build, buildWithResources, copyFile, createDirectory, moveDirectory, + build, buildWithResources, copyFile, createDirectory, removeDirectory, moveDirectory, fixFile, runConfigure, runMake, runBuilder, makeExecutable ) where @@ -74,6 +74,11 @@ createDirectory dir = do putBuild $ "| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir +removeDirectory :: FilePath -> Action () +removeDirectory dir = do + putBuild $ "| Remove directory " ++ dir + liftIO $ IO.removeDirectoryRecursive dir + -- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do From git at git.haskell.org Thu Oct 26 23:50:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Print more diagnostic info. (0ad3af2) Message-ID: <20171026235057.4C6BD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ad3af27554bdaa8ba765353ca53256d4f342f32/ghc >--------------------------------------------------------------- commit 0ad3af27554bdaa8ba765353ca53256d4f342f32 Author: Andrey Mokhov Date: Tue Jan 13 04:05:59 2015 +0000 Print more diagnostic info. >--------------------------------------------------------------- 0ad3af27554bdaa8ba765353ca53256d4f342f32 src/Oracles.hs | 1 + src/Oracles/PackageData.hs | 2 ++ src/Package/Library.hs | 16 ++++++++++++---- 3 files changed, 15 insertions(+), 4 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 3a0c430..5b2ff11 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -49,6 +49,7 @@ packageDataOracle :: Rules () packageDataOracle = do pkgData <- newCache $ \file -> do need [file] + putNormal $ "Parsing " ++ file ++ "..." liftIO $ readConfigFile file addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 6bffafd..66a3f55 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -18,6 +18,7 @@ data PackageData = Modules FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath + | Synopsis FilePath instance ShowArgs PackageData where showArgs packageData = do @@ -28,6 +29,7 @@ instance ShowArgs PackageData where IncludeDirs file -> ("INCLUDE_DIRS", file, ".") Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) + Synopsis file -> ("SYNOPSIS" , file, "" ) fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key res <- askOracle $ PackageDataKey (file, fullKey) return $ words $ case res of diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 0c2e1f8..6660a2f 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -5,14 +5,16 @@ import Package.Base {- "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a - at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents + at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a +.contents -} --- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents +-- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) +-- $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents -- AR_OPTS = $(SRC_AR_OPTS) $(WAY$(_way)_AR_OPTS) $(EXTRA_AR_OPTS) buildPackageLibrary :: Package -> TodoItem -> Rules () -buildPackageLibrary (Package _ path _) (stage, dist, _) = +buildPackageLibrary (Package name path _) (stage, dist, _) = let buildDir = path dist "build" pkgData = path dist "package-data.mk" in @@ -22,5 +24,11 @@ buildPackageLibrary (Package _ path _) (stage, dist, _) = depObjs <- pkgDepObjects path dist way need depObjs libObjs <- pkgLibObjects path dist stage way - liftIO $ removeFiles "" [out] + liftIO $ removeFiles "." [out] terseRun Ar $ arArgs <+> out <+> libObjs + when (way == vanilla) $ do + synopsis <- unwords <$> arg (Synopsis pkgData) + putNormal $ "Successfully built library for package " + ++ name ++ "." + putNormal $ "Synopsis: " ++ synopsis ++ "." + From git at git.haskell.org Thu Oct 26 23:50:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (79ceb45) Message-ID: <20171026235059.5A0893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79ceb456ffb5511e630ace24ed409782119ddf5d/ghc >--------------------------------------------------------------- commit 79ceb456ffb5511e630ace24ed409782119ddf5d Author: Moritz Angermann Date: Fri Jan 1 01:20:06 2016 +0800 Update README.md Roll Linux / OS X into one section. This should fix #37. >--------------------------------------------------------------- 79ceb456ffb5511e630ace24ed409782119ddf5d README.md | 29 +++++++++++------------------ 1 file changed, 11 insertions(+), 18 deletions(-) diff --git a/README.md b/README.md index 93674a1..f26cc49 100644 --- a/README.md +++ b/README.md @@ -14,7 +14,13 @@ This is supposed to go into the `shake-build` directory of the GHC source tree. Trying it --------- -### Linux +Please see the [Preparation][ghc-preparation] on the haskell wiki +for general preparation. The preparation steps for the `shake` build system are +identical to those for the `make` build system. This means that you don't need +to adjust anything if you are already familiar with building ghc using the `make` +build system. + +### Linux / Mac OS X ```bash git clone git://git.haskell.org/ghc @@ -23,6 +29,9 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure +# or if you want to use clang (e.g. building on OS X) +./configure --with-gcc=$(which clang) # See #26 + ``` Now you have a couple of options: @@ -46,20 +55,6 @@ shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. -### Mac OS X - -```bash -git clone git://git.haskell.org/ghc -cd ghc -git submodule update --init -git clone git://github.com/snowleopard/shaking-up-ghc shake-build -./boot -./configure --with-gcc=$(which clang) # See #26 -./shake-build/build.sh -``` - -See the Linux section for running in a Cabal sandbox. - ### Resetting the build To reset the new build system run the build script with `-B` flag. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). @@ -76,10 +71,8 @@ documentation is currently non-existent, but we will start addressing this once the codebase stabilises. - - - [ghc-shake-wiki]: https://ghc.haskell.org/trac/ghc/wiki/Building/Shake +[ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-building-guide]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows [ghc]: https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler [shake-blog-post]: https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc From git at git.haskell.org Thu Oct 26 23:50:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:50:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify fixLibffiMakefile, no need to chop into lines first (07d94c9) Message-ID: <20171026235059.A26E13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/07d94c918a4fa0f7f5ea43496f4a3e6e95662c08/ghc >--------------------------------------------------------------- commit 07d94c918a4fa0f7f5ea43496f4a3e6e95662c08 Author: Neil Mitchell Date: Tue Jan 12 22:33:42 2016 +0000 Simplify fixLibffiMakefile, no need to chop into lines first >--------------------------------------------------------------- 07d94c918a4fa0f7f5ea43496f4a3e6e95662c08 src/Rules/Libffi.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0c38cd2..63bc1e8 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -28,11 +28,11 @@ libffiLibrary :: FilePath libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" fixLibffiMakefile :: String -> String -fixLibffiMakefile = unlines . map - ( replace "-MD" "-MMD" +fixLibffiMakefile = + replace "-MD" "-MMD" . replace "@toolexeclibdir@" "$(libdir)" . replace "@INSTALL@" "$(subst ../install-sh,C:/msys/home/chEEtah/ghc/install-sh, at INSTALL@)" - ) . lines + -- TODO: remove code duplication (see Settings/Builders/GhcCabal.hs) configureEnvironment :: Action [CmdOption] From git at git.haskell.org Thu Oct 26 23:51:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add link rule. (7b1964e) Message-ID: <20171026235100.B9F543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b1964efccba7ca2072e41f0e782a4ccfd843244/ghc >--------------------------------------------------------------- commit 7b1964efccba7ca2072e41f0e782a4ccfd843244 Author: Andrey Mokhov Date: Tue Jan 13 04:57:33 2015 +0000 Add link rule. >--------------------------------------------------------------- 7b1964efccba7ca2072e41f0e782a4ccfd843244 doc/deepseq-build-progress.txt | 8 +++++++- src/Oracles/Builder.hs | 8 +++----- src/Package.hs | 3 ++- src/Package/Library.hs | 44 +++++++++++++++++++++++++----------------- 4 files changed, 38 insertions(+), 25 deletions(-) diff --git a/doc/deepseq-build-progress.txt b/doc/deepseq-build-progress.txt index f951d61..0df6c05 100644 --- a/doc/deepseq-build-progress.txt +++ b/doc/deepseq-build-progress.txt @@ -54,14 +54,20 @@ echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0 # Done: "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents /usr/bin/ar: creating libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a.contents # Done: "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -H32m -O -this-package-key deeps_FT5iVCELxOr62eHY0nbvnU -hide-all-packages -i -ilibraries/deepseq/. -ilibraries/deepseq/dist-install/build -ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/dist-install/build -Ilibraries/deepseq/dist-install/build/autogen -Ilibraries/deepseq/. -optP-include -optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h -package-key array_3w0nMK0JfaFJPpLFn2yWAJ -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key ghcpr_FgrV6cgh2JHBlbcx1OSlwt -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/deepseq/dist-install/build -hidir libraries/deepseq/dist-install/build -stubdir libraries/deepseq/dist-install/build -split-objs -c libraries/deepseq/./Control/DeepSeq.hs -o libraries/deepseq/dist-install/build/Control/DeepSeq.p_o - +# Done: "C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" -r -o libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o libraries/deepseq/dist-install/build/Control/DeepSeq.o + +# Done: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents + +# Skipping: /usr/bin/find libraries/deepseq/dist-install/build/Control/DeepSeq_p_o_split -name '*.p_o' -print >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index ffc3cf5..71f8575 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,8 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, terseRun, specified, - arArgs + with, run, terseRun, specified ) where import Data.Char @@ -115,11 +114,13 @@ terseRun builder args = do interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of Ar -> prefixAndSuffix 3 1 ss + Ld -> prefixAndSuffix 4 0 ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss else prefixAndSuffix 0 4 ss GhcPkg _ -> prefixAndSuffix 2 0 ss GhcCabal -> prefixAndSuffix 3 0 ss + _ -> ss where prefixAndSuffix n m ss = if length ss <= n + m + 1 @@ -138,6 +139,3 @@ specified builder = do [_] -> True _ -> False --- TODO: generalise for other builders -arArgs :: Args -arArgs = arg "q" diff --git a/src/Package.hs b/src/Package.hs index a3fcf89..8b41809 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -23,7 +23,8 @@ packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" - , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" ] + , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" + , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 6660a2f..529d777 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -3,18 +3,8 @@ module Package.Library (buildPackageLibrary) where import Package.Base -{- "/usr/bin/ar" q -libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a - at libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a -.contents --} - --- "$$(XARGS)" $$(XARGS_OPTS) "$$($1_$2_AR)" $$($1_$2_AR_OPTS) --- $$($1_$2_EXTRA_AR_ARGS) $$@ < $$@.contents --- AR_OPTS = $(SRC_AR_OPTS) $(WAY$(_way)_AR_OPTS) $(EXTRA_AR_OPTS) - -buildPackageLibrary :: Package -> TodoItem -> Rules () -buildPackageLibrary (Package name path _) (stage, dist, _) = +arRule :: Package -> TodoItem -> Rules () +arRule (Package _ path _) (stage, dist, _) = let buildDir = path dist "build" pkgData = path dist "package-data.mk" in @@ -25,10 +15,28 @@ buildPackageLibrary (Package name path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] - terseRun Ar $ arArgs <+> out <+> libObjs - when (way == vanilla) $ do - synopsis <- unwords <$> arg (Synopsis pkgData) - putNormal $ "Successfully built library for package " - ++ name ++ "." - putNormal $ "Synopsis: " ++ synopsis ++ "." + terseRun Ar $ "q" <+> out <+> libObjs +{- "C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" -r -o +libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o +libraries/deepseq/dist-install/build/Control/DeepSeq.o +-} + +ldRule :: Package -> TodoItem -> Rules () +ldRule (Package name path _) (stage, dist, _) = + let buildDir = path dist "build" + pkgData = path dist "package-data.mk" + in + priority 2 $ (buildDir "*.o") %> \out -> do + need ["shake/src/Package/Library.hs"] + depObjs <- pkgDepObjects path dist vanilla + need depObjs + terseRun Ld $ arg (ConfLdLinkerArgs stage) + <> arg ["-r", "-o", out] + <> arg depObjs + synopsis <- unwords <$> arg (Synopsis pkgData) + putNormal $ "Successfully built package " ++ name ++ "." + putNormal $ "Package synopsis: " ++ synopsis ++ "." + +buildPackageLibrary :: Package -> TodoItem -> Rules () +buildPackageLibrary = arRule <> ldRule \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:51:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #72 from snowleopard/angerman-patch-4 (e97d689) Message-ID: <20171026235103.99B813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e97d6892c70c570c2425d7e49f8b5158f0e584cf/ghc >--------------------------------------------------------------- commit e97d6892c70c570c2425d7e49f8b5158f0e584cf Merge: e2fb954 79ceb45 Author: Andrey Mokhov Date: Thu Dec 31 18:42:46 2015 +0000 Merge pull request #72 from snowleopard/angerman-patch-4 Update README.md >--------------------------------------------------------------- e97d6892c70c570c2425d7e49f8b5158f0e584cf README.md | 29 +++++++++++------------------ 1 file changed, 11 insertions(+), 18 deletions(-) From git at git.haskell.org Thu Oct 26 23:51:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use removeDirectory where appropriate (ccc16b2) Message-ID: <20171026235103.EFF463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccc16b21b7d255b692ffbc9b0c96167bec2ed77e/ghc >--------------------------------------------------------------- commit ccc16b21b7d255b692ffbc9b0c96167bec2ed77e Author: Neil Mitchell Date: Tue Jan 12 22:33:55 2016 +0000 Use removeDirectory where appropriate >--------------------------------------------------------------- ccc16b21b7d255b692ffbc9b0c96167bec2ed77e src/Rules/Libffi.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 63bc1e8..1d761ff 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -71,7 +71,7 @@ libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - liftIO $ removeFiles libffiBuild ["//*"] + removeDirectory libffiBuild createDirectory $ buildRootPath -/- stageString Stage0 tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] From git at git.haskell.org Thu Oct 26 23:51:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (4863449) Message-ID: <20171026235104.8E4A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4863449633ec90de6607df0d80f4b2a8f40ecdc7/ghc >--------------------------------------------------------------- commit 4863449633ec90de6607df0d80f4b2a8f40ecdc7 Author: Andrey Mokhov Date: Tue Jan 13 05:12:38 2015 +0000 Clean up. >--------------------------------------------------------------- 4863449633ec90de6607df0d80f4b2a8f40ecdc7 doc/deepseq-build-progress.txt | 6 ++++++ src/Oracles.hs | 2 +- src/Oracles/Builder.hs | 2 +- src/Package/Base.hs | 6 +++--- src/Package/Compile.hs | 2 +- src/Package/Data.hs | 2 +- src/Package/Library.hs | 9 ++------- 7 files changed, 15 insertions(+), 14 deletions(-) diff --git a/doc/deepseq-build-progress.txt b/doc/deepseq-build-progress.txt index 0df6c05..84845fe 100644 --- a/doc/deepseq-build-progress.txt +++ b/doc/deepseq-build-progress.txt @@ -70,9 +70,15 @@ echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0 # Skipping: /usr/bin/find libraries/deepseq/dist-install/build/Control/DeepSeq_p_o_split -name '*.p_o' -print >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents echo >> libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents + +# Done: "/usr/bin/ar" q libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a @libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents /usr/bin/ar: creating libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a + +# Skipping: "rm" -f libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU_p.a.contents + + "inplace/bin/mkdirhier" libraries/deepseq/dist-install/doc/html/deepseq//. "C:/msys/home/chEEtah/ghc/inplace/bin/haddock" --odir="libraries/deepseq/dist-install/doc/html/deepseq" --no-tmp-comp-dir --dump-interface=libraries/deepseq/dist-install/doc/html/deepseq/deepseq.haddock --html --hoogle --title="deepseq-1.4.0.0: Deep evaluation of data structures" --prologue="libraries/deepseq/dist-install/haddock-prologue.txt" --read-interface=../array-0.5.0.1,../array-0.5.0.1/src/%{MODULE/./-}.html\#%{NAME},libraries/array/dist-install/doc/html/array/array.haddock --read-interface=../base-4.8.0.0,../base-4.8.0.0/src/%{MODULE/./-}.html\#%{NAME},libraries/base/dist-install/doc/html/base/base.haddock --read-interface=../ghc-prim-0.3.1.0,../ghc-prim-0.3.1.0/src/%{MODULE/./-}.html\#%{NAME},libraries/ghc-prim/dist-install/doc/html/ghc-prim/ghc-prim.haddock --optghc=-hisuf --optghc=hi --optghc=-osuf --optghc=o --optghc=-hcsuf --optghc=hc --optghc=-static --optghc=-H32m --optghc=-O --optghc=-this-package-key --optghc=deeps_FT5iVCELxOr62eHY0nbvnU --optghc=-hide-all-package s --optghc=-i --optghc=-ilibraries/deepseq/. --optghc=-ilibraries/deepseq/dist-install/build --optghc=-ilibraries/deepseq/dist-install/build/autogen --optghc=-Ilibraries/deepseq/dist-install/build --optghc=-Ilibraries/deepseq/dist-install/build/autogen --optghc=-Ilibraries/deepseq/. --optghc=-optP-include --optghc=-optPlibraries/deepseq/dist-install/build/autogen/cabal_macros.h --optghc=-package-key --optghc=array_3w0nMK0JfaFJPpLFn2yWAJ --optghc=-package-key --optghc=base_469rOtLAqwTGFEOGWxSUiQ --optghc=-package-key --optghc=ghcpr_FgrV6cgh2JHBlbcx1OSlwt --optghc=-Wall --optghc=-XHaskell2010 --optghc=-O2 --optghc=-no-user-package-db --optghc=-rtsopts --optghc=-odir --optghc=libraries/deepseq/dist-install/build --optghc=-hidir --optghc=libraries/deepseq/dist-install/build --optghc=-stubdir --optghc=libraries/deepseq/dist-install/build --optghc=-split-objs libraries/deepseq/./Control/DeepSeq.hs +RTS -tlibraries/deepseq/dist-install/doc/html/deepseq/deepseq.haddock.t --machine-reada ble Haddock coverage: diff --git a/src/Oracles.hs b/src/Oracles.hs index 5b2ff11..2fe8430 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -49,7 +49,7 @@ packageDataOracle :: Rules () packageDataOracle = do pkgData <- newCache $ \file -> do need [file] - putNormal $ "Parsing " ++ file ++ "..." + putNormal $ "Parsing " ++ toStandard file ++ "..." liftIO $ readConfigFile file addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 71f8575..8a2c5b2 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -27,7 +27,7 @@ data Builder = Ar deriving Show instance ShowArgs Builder where - showArgs builder = showArgs $ fmap words $ do + showArgs builder = showArgs $ fmap (map toStandard . words) $ do let key = case builder of Ar -> "ar" Ld -> "ld" diff --git a/src/Package/Base.hs b/src/Package/Base.hs index a8de80d..9882900 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -49,7 +49,7 @@ libraryPackage :: String -> Stage -> (Stage -> Settings) -> Package libraryPackage name stage settings = Package name - ("libraries" name) + (toStandard $ "libraries" name) [( stage, if stage == Stage0 then "dist-boot" else "dist-install", @@ -123,7 +123,7 @@ pkgDepObjects path dist way = do buildDir = path dist "build" hs2obj = (buildDir ++) . drop (length path) . (-<.> osuf way) srcs <- pkgHsSources path dist - return $ map hs2obj srcs + return $ map (toStandard . hs2obj) srcs -- Find objects that go to library pkgLibObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] @@ -145,4 +145,4 @@ findModuleFiles pkgData directories suffixes = do modPath <- map (replaceEq '.' pathSeparator) mods suffix <- suffixes return $ dir modPath ++ suffix - return $ map normaliseEx files + return $ map (toStandard . normaliseEx) files diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 6badbb7..760c96f 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -53,4 +53,4 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) - <> arg ["-o", out] + <> arg ["-o", toStandard out] diff --git a/src/Package/Data.hs b/src/Package/Data.hs index a73a521..ef89ed0 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -79,7 +79,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = ghcPkgArgs = arg ["update", "--force"] <> (stage == Stage0) arg "--package-db=libraries/bootstrapping.conf" - <> arg (pathDist "inplace-pkg-config") + <> arg (toStandard $ pathDist "inplace-pkg-config") in (pathDist ) <$> [ "package-data.mk" diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 529d777..9f200e4 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -15,12 +15,7 @@ arRule (Package _ path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] - terseRun Ar $ "q" <+> out <+> libObjs - -{- "C:/msys/home/chEEtah/ghc/inplace/mingw/bin/ld.exe" -r -o -libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o -libraries/deepseq/dist-install/build/Control/DeepSeq.o --} + terseRun Ar $ "q" <+> toStandard out <+> libObjs ldRule :: Package -> TodoItem -> Rules () ldRule (Package name path _) (stage, dist, _) = @@ -32,7 +27,7 @@ ldRule (Package name path _) (stage, dist, _) = depObjs <- pkgDepObjects path dist vanilla need depObjs terseRun Ld $ arg (ConfLdLinkerArgs stage) - <> arg ["-r", "-o", out] + <> arg ["-r", "-o", toStandard out] <> arg depObjs synopsis <- unwords <$> arg (Synopsis pkgData) putNormal $ "Successfully built package " ++ name ++ "." From git at git.haskell.org Thu Oct 26 23:51:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Match generator sources exactly, see #69 and #70. (6c80bd8) Message-ID: <20171026235107.951213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6c80bd874eb2d4ca9607009dcf33eedbe011d5cd/ghc >--------------------------------------------------------------- commit 6c80bd874eb2d4ca9607009dcf33eedbe011d5cd Author: Andrey Mokhov Date: Thu Dec 31 19:01:38 2015 +0000 Match generator sources exactly, see #69 and #70. >--------------------------------------------------------------- 6c80bd874eb2d4ca9607009dcf33eedbe011d5cd src/Rules/Generate.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index fd101a1..b53b2b8 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -83,11 +83,13 @@ generate file target expr = do generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let buildPath = targetPath stage pkg -/- "build" + dropBuild = drop (length buildPath + 1) generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) file <~ gen = generate file target gen in do generated ?> \file -> do - let pattern = "//" ++ takeBaseName file <.> "*" + let srcFile = dropBuild file + pattern = "//" ++ srcFile <.> "*" files <- fmap (filter (pattern ?==)) $ moduleFiles stage pkg let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ From git at git.haskell.org Thu Oct 26 23:51:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #156, ensure the entire piece is under a removeFiles so we always clean up the garbage (3a88dc5) Message-ID: <20171026235107.D59D23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3a88dc56215804ab95d9c5eb3127de6f4c7a5f0b/ghc >--------------------------------------------------------------- commit 3a88dc56215804ab95d9c5eb3127de6f4c7a5f0b Author: Neil Mitchell Date: Tue Jan 12 22:34:39 2016 +0000 #156, ensure the entire piece is under a removeFiles so we always clean up the garbage >--------------------------------------------------------------- 3a88dc56215804ab95d9c5eb3127de6f4c7a5f0b src/Rules/Libffi.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 1d761ff..8bcfdae 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -82,9 +82,10 @@ libffiRules = do need tarballs let libname = dropExtension . dropExtension . takeFileName $ head tarballs - build $ fullTarget libffiTarget Tar tarballs [buildRootPath] - actionFinally (moveDirectory (buildRootPath -/- libname) libffiBuild) $ - removeFiles buildRootPath [libname "*"] + actionFinally (do + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile From git at git.haskell.org Thu Oct 26 23:51:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add array package. (d4aabcd) Message-ID: <20171026235108.1986C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4aabcd7e1e1d3de6302f0b8d436a5bcf4794f5b/ghc >--------------------------------------------------------------- commit d4aabcd7e1e1d3de6302f0b8d436a5bcf4794f5b Author: Andrey Mokhov Date: Tue Jan 13 06:31:37 2015 +0000 Add array package. >--------------------------------------------------------------- d4aabcd7e1e1d3de6302f0b8d436a5bcf4794f5b src/Package.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 8b41809..e29551f 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -10,7 +10,8 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] -packages = [libraryPackage "deepseq" Stage1 defaultSettings] +packages = [libraryPackage "array" Stage1 defaultSettings, + libraryPackage "deepseq" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -24,7 +25,10 @@ packageRules = do -- TODO: control targets from commang line arguments want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" - , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" ] + , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" + , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.a" + , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.p_a" + , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:49:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:49:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fit lines into 80 characters. (817ed05) Message-ID: <20171026234946.A051E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/817ed0570d9b58d3a3220fadcc704cfa7913d90f/ghc >--------------------------------------------------------------- commit 817ed0570d9b58d3a3220fadcc704cfa7913d90f Author: Andrey Mokhov Date: Sun Jan 11 21:50:41 2015 +0000 Fit lines into 80 characters. >--------------------------------------------------------------- 817ed0570d9b58d3a3220fadcc704cfa7913d90f src/Oracles/Option.hs | 32 +++++++++++++++++++++++--------- 1 file changed, 23 insertions(+), 9 deletions(-) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index d08b394..0a5506d 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -6,9 +6,17 @@ module Oracles.Option ( import Base import Oracles.Base -data Option = TargetOS | TargetArch | TargetPlatformFull - | ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage - | IconvIncludeDirs | IconvLibDirs | GmpIncludeDirs | GmpLibDirs +data Option = TargetOS + | TargetArch + | TargetPlatformFull + | ConfCcArgs Stage + | ConfGccLinkerArgs Stage + | ConfLdLinkerArgs Stage + | ConfCppArgs Stage + | IconvIncludeDirs + | IconvLibDirs + | GmpIncludeDirs + | GmpLibDirs | SrcHcOpts | HostOsCpp @@ -17,10 +25,10 @@ instance ShowArgs Option where TargetOS -> "target-os" TargetArch -> "target-arch" TargetPlatformFull -> "target-platform-full" - ConfCcArgs stage -> "conf-cc-args-stage-" ++ (show . fromEnum) stage - ConfCppArgs stage -> "conf-cpp-args-stage-" ++ (show . fromEnum) stage - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ (show . fromEnum) stage - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ (show . fromEnum) stage + ConfCcArgs stage -> "conf-cc-args-stage-" ++ show stage + ConfCppArgs stage -> "conf-cpp-args-stage-" ++ show stage + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage-" ++ show stage + ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage-" ++ show stage IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" GmpIncludeDirs -> "gmp-include-dirs" @@ -33,14 +41,20 @@ ghcWithInterpreter = do [os] <- showArgs TargetOS [arch] <- showArgs TargetArch return $ - os `elem` ["mingw32", "cygwin32", "linux", "solaris2", "freebsd", "dragonfly", "netbsd", "openbsd", "darwin", "kfreebsdgnu"] + os `elem` [ "mingw32", "cygwin32", "linux", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" + , "darwin", "kfreebsdgnu"] && arch `elem` ["i386", "x86_64", "powerpc", "sparc", "sparc64", "arm"] +-- TODO: i386-unknown-solaris2 should be in the list if +-- @SOLARIS_BROKEN_SHLD@ == YES platformSupportsSharedLibs :: Condition platformSupportsSharedLibs = do [platform] <- showArgs TargetPlatformFull - return $ platform `notElem` [ "powerpc-unknown-linux", "x86_64-unknown-mingw32", "i386-unknown-mingw32" ] -- TODO: i386-unknown-solaris2? + return $ platform `notElem` [ "powerpc-unknown-linux" + , "x86_64-unknown-mingw32" + , "i386-unknown-mingw32" ] windowsHost :: Condition windowsHost = do From git at git.haskell.org Thu Oct 26 23:51:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix extention, see #69 and #70. (26cd11f) Message-ID: <20171026235111.532843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/26cd11fb2e334f7a09e53bcd0d0e1dbc4cb646fe/ghc >--------------------------------------------------------------- commit 26cd11fb2e334f7a09e53bcd0d0e1dbc4cb646fe Author: Andrey Mokhov Date: Thu Dec 31 19:12:39 2015 +0000 Fix extention, see #69 and #70. >--------------------------------------------------------------- 26cd11fb2e334f7a09e53bcd0d0e1dbc4cb646fe src/Rules/Generate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index b53b2b8..d8f7129 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -89,7 +89,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = in do generated ?> \file -> do let srcFile = dropBuild file - pattern = "//" ++ srcFile <.> "*" + pattern = "//" ++ srcFile -<.> "*" files <- fmap (filter (pattern ?==)) $ moduleFiles stage pkg let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ From git at git.haskell.org Thu Oct 26 23:51:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #154 from snowleopard/angerman/feature/build-info-flags (57c6497) Message-ID: <20171026235112.18F183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57c6497776b08bd0548a094fa96b21977ae54254/ghc >--------------------------------------------------------------- commit 57c6497776b08bd0548a094fa96b21977ae54254 Merge: 86f3052 f794e73 Author: Andrey Mokhov Date: Tue Jan 12 22:41:37 2016 +0000 Merge pull request #154 from snowleopard/angerman/feature/build-info-flags Add Advanced render box styles [skip ci] >--------------------------------------------------------------- 57c6497776b08bd0548a094fa96b21977ae54254 shaking-up-ghc.cabal | 1 + src/Base.hs | 52 ++++++++++++++++++++++++++++++++++-- src/Main.hs | 7 ++++- src/Oracles/Config/CmdLineFlag.hs | 56 +++++++++++++++++++++++++++++++++++++++ src/Rules/Actions.hs | 20 +++++--------- src/Rules/Library.hs | 9 +++---- src/Rules/Program.hs | 11 ++++---- 7 files changed, 129 insertions(+), 27 deletions(-) From git at git.haskell.org Thu Oct 26 23:51:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add hiRule. (fae8451) Message-ID: <20171026235112.1A4133A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fae8451a106cc2c298154d586201ce8924b9d701/ghc >--------------------------------------------------------------- commit fae8451a106cc2c298154d586201ce8924b9d701 Author: Andrey Mokhov Date: Tue Jan 13 06:32:36 2015 +0000 Add hiRule. >--------------------------------------------------------------- fae8451a106cc2c298154d586201ce8924b9d701 src/Package/Compile.hs | 17 +++++++++++++++-- 1 file changed, 15 insertions(+), 2 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 760c96f..80835f8 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -29,8 +29,8 @@ suffixArgs way = arg ["-hisuf", hisuf way] <> arg [ "-osuf", osuf way] <> arg ["-hcsuf", hcsuf way] -buildPackageCompile :: Package -> TodoItem -> Rules () -buildPackageCompile (Package name path _) (stage, dist, settings) = +oRule :: Package -> TodoItem -> Rules () +oRule (Package name path _) (stage, dist, settings) = let buildDir = path dist "build" pkgData = path dist "package-data.mk" depFile = buildDir name <.> "m" @@ -54,3 +54,16 @@ buildPackageCompile (Package name path _) (stage, dist, settings) = <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) <> arg ["-o", toStandard out] + +-- TODO: This rule looks a bit of a hack... combine it with the above? +hiRule :: Package -> TodoItem -> Rules () +hiRule (Package name path _) (stage, dist, settings) = + let buildDir = path dist "build" + in + (buildDir "*hi") %> \out -> do + let way = detectWay $ tail $ takeExtension out + oFile = out -<.> osuf way + need [oFile] + +buildPackageCompile :: Package -> TodoItem -> Rules () +buildPackageCompile = oRule <> hiRule From git at git.haskell.org Thu Oct 26 23:51:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename builder arguments, fix #60. (56705eb) Message-ID: <20171026235115.0B71B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56705eb7ed074516a370054db7e3b81bae1afca4/ghc >--------------------------------------------------------------- commit 56705eb7ed074516a370054db7e3b81bae1afca4 Author: Andrey Mokhov Date: Fri Jan 1 01:23:21 2016 +0000 Rename builder arguments, fix #60. >--------------------------------------------------------------- 56705eb7ed074516a370054db7e3b81bae1afca4 src/Settings/Args.hs | 32 ++++++++++++++++---------------- src/Settings/Builders/Alex.hs | 10 +++++----- src/Settings/Builders/Ar.hs | 14 +++++++------- src/Settings/Builders/DeriveConstants.hs | 6 +++--- src/Settings/Builders/Gcc.hs | 10 +++++----- src/Settings/Builders/GenPrimopCode.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 12 ++++++------ src/Settings/Builders/GhcCabal.hs | 11 ++++++----- src/Settings/Builders/GhcPkg.hs | 6 +++--- src/Settings/Builders/Haddock.hs | 6 +++--- src/Settings/Builders/Happy.hs | 12 ++++++------ src/Settings/Builders/HsCpp.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 6 +++--- src/Settings/Builders/Ld.hs | 6 +++--- 14 files changed, 72 insertions(+), 71 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 56705eb7ed074516a370054db7e3b81bae1afca4 From git at git.haskell.org Thu Oct 26 23:51:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: In the removeDirectory operation, use removeIfExists (2dd57cc) Message-ID: <20171026235115.B93683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2dd57cc06f172145f668a89d29756de6dccceb0f/ghc >--------------------------------------------------------------- commit 2dd57cc06f172145f668a89d29756de6dccceb0f Author: Neil Mitchell Date: Tue Jan 12 22:43:01 2016 +0000 In the removeDirectory operation, use removeIfExists >--------------------------------------------------------------- 2dd57cc06f172145f668a89d29756de6dccceb0f src/Rules/Actions.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index a968160..55f81dd 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -77,7 +77,7 @@ createDirectory dir = do removeDirectory :: FilePath -> Action () removeDirectory dir = do putBuild $ "| Remove directory " ++ dir - liftIO $ IO.removeDirectoryRecursive dir + removeDirectoryIfExists dir -- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Thu Oct 26 23:51:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split Ar arguments into chunks of length 100 at most. (821776b) Message-ID: <20171026235115.BB7E03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/821776b91341b4651f30f56ec08069a17c0d0a2b/ghc >--------------------------------------------------------------- commit 821776b91341b4651f30f56ec08069a17c0d0a2b Author: Andrey Mokhov Date: Tue Jan 13 06:33:44 2015 +0000 Split Ar arguments into chunks of length 100 at most. >--------------------------------------------------------------- 821776b91341b4651f30f56ec08069a17c0d0a2b src/Package/Library.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 9f200e4..ec2b845 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -2,6 +2,7 @@ module Package.Library (buildPackageLibrary) where import Package.Base +import Data.List.Split arRule :: Package -> TodoItem -> Rules () arRule (Package _ path _) (stage, dist, _) = @@ -15,7 +16,8 @@ arRule (Package _ path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] - terseRun Ar $ "q" <+> toStandard out <+> libObjs + forM_ (chunksOf 100 libObjs) $ \os -> do + terseRun Ar $ "q" <+> toStandard out <+> os ldRule :: Package -> TodoItem -> Rules () ldRule (Package name path _) (stage, dist, _) = From git at git.haskell.org Thu Oct 26 23:51:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update GhcPkg.hs (6dbe055) Message-ID: <20171026235118.97A6B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6dbe055462a3d943ade75da94f3e1d8f42d23d0d/ghc >--------------------------------------------------------------- commit 6dbe055462a3d943ade75da94f3e1d8f42d23d0d Author: Moritz Angermann Date: Fri Jan 1 14:31:07 2016 +0800 Update GhcPkg.hs - Fix package conf path. - Adds comment - Drops the left over comments from previous. >--------------------------------------------------------------- 6dbe055462a3d943ade75da94f3e1d8f42d23d0d src/Rules/Wrappers/GhcPkg.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Rules/Wrappers/GhcPkg.hs b/src/Rules/Wrappers/GhcPkg.hs index 3f70617..3e077ac 100644 --- a/src/Rules/Wrappers/GhcPkg.hs +++ b/src/Rules/Wrappers/GhcPkg.hs @@ -4,17 +4,14 @@ import Base import Expression import Oracles --- Note about wrapper: --- bindir is usually GhcSourcePath / inplace / bin --- topdir is usually GhcSourcePath / inplace / lib --- datadir is usually the same as topdir - ghcPkgWrapper :: FilePath -> Expr String ghcPkgWrapper program = do lift $ need [sourcePath -/- "Rules/Wrappers/GhcPkg.hs"] top <- getSetting GhcSourcePath stage <- getStage - let pkgConf = top -/- packageConfiguration stage + -- Use the package configuration for the next stage in the wrapper. + -- The wrapper is generated in StageN, but used in StageN+1. + let pkgConf = top -/- packageConfiguration (succ stage) return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) From git at git.haskell.org Thu Oct 26 23:51:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #156, remove the directory if it already exists (8f995f6) Message-ID: <20171026235119.6CB3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f995f6b65c27d18f2f9606ba95ac25c2974ae23/ghc >--------------------------------------------------------------- commit 8f995f6b65c27d18f2f9606ba95ac25c2974ae23 Author: Neil Mitchell Date: Tue Jan 12 22:43:24 2016 +0000 #156, remove the directory if it already exists >--------------------------------------------------------------- 8f995f6b65c27d18f2f9606ba95ac25c2974ae23 src/Rules/Libffi.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 8bcfdae..dbf50dc 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -82,6 +82,7 @@ libffiRules = do need tarballs let libname = dropExtension . dropExtension . takeFileName $ head tarballs + removeDirectory (buildRootPath -/- libname) actionFinally (do build $ fullTarget libffiTarget Tar tarballs [buildRootPath] moveDirectory (buildRootPath -/- libname) libffiBuild) $ From git at git.haskell.org Thu Oct 26 23:51:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add toStandard to varios places. (5d2cf2c) Message-ID: <20171026235119.6E13F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d2cf2c3163f37cb53d0217eae93582980e211de/ghc >--------------------------------------------------------------- commit 5d2cf2c3163f37cb53d0217eae93582980e211de Author: Andrey Mokhov Date: Tue Jan 13 06:34:24 2015 +0000 Add toStandard to varios places. >--------------------------------------------------------------- 5d2cf2c3163f37cb53d0217eae93582980e211de src/Package/Base.hs | 11 ++++++----- src/Package/Dependencies.hs | 8 ++++---- 2 files changed, 10 insertions(+), 9 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 9882900..f6c70ea 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -84,7 +84,8 @@ bootPkgConstraints = mempty -- sed "s/[^0-9.]//g")")) pathArgs :: ShowArgs a => String -> FilePath -> a -> Args -pathArgs key path as = map (\a -> key ++ normaliseEx (path a)) <$> arg as +pathArgs key path as = + map (\a -> key ++ toStandard (normaliseEx $ path a)) <$> arg as packageArgs :: Stage -> FilePath -> Args packageArgs stage pkgData = do @@ -100,14 +101,14 @@ packageArgs stage pkgData = do includeArgs :: FilePath -> FilePath -> Args includeArgs path dist = - let pkgData = path dist "package-data.mk" - buildDir = path dist "build" + let pkgData = toStandard $ path dist "package-data.mk" + buildDir = toStandard $ path dist "build" in arg "-i" <> pathArgs "-i" path (SrcDirs pkgData) - <> concatArgs ["-i", "-I"] [buildDir, buildDir "autogen"] + <> concatArgs ["-i", "-I"] [buildDir, toStandard $ buildDir "autogen"] <> pathArgs "-I" path (IncludeDirs pkgData) <> arg "-optP-include" -- TODO: Shall we also add -cpp? - <> concatArgs "-optP" (buildDir "autogen/cabal_macros.h") + <> concatArgs "-optP" (toStandard $ buildDir "autogen/cabal_macros.h") pkgHsSources :: FilePath -> FilePath -> Action [FilePath] pkgHsSources path dist = do diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 6339adb..63ed508 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -5,16 +5,16 @@ import Package.Base buildPackageDependencies :: Package -> TodoItem -> Rules () buildPackageDependencies (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" - pkgData = path dist "package-data.mk" + let buildDir = toStandard $ path dist "build" + pkgData = toStandard $ path dist "package-data.mk" in (buildDir name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData <> includeArgs path dist - <> productArgs ["-odir", "-stubdir"] buildDir - <> arg ["-dep-makefile", out <.> "new"] + <> productArgs ["-odir", "-stubdir", "-hidir"] buildDir + <> arg ["-dep-makefile", toStandard $ out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) <> arg (pkgHsSources path dist) -- TODO: Check that skipping all _HC_OPTS is safe. From git at git.haskell.org Thu Oct 26 23:51:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #74 from snowleopard/angerman-patch-5 (77655b7) Message-ID: <20171026235122.55B0B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/77655b7c31c2e37c83bbe36937d4ca65dee74701/ghc >--------------------------------------------------------------- commit 77655b7c31c2e37c83bbe36937d4ca65dee74701 Merge: 56705eb 6dbe055 Author: Andrey Mokhov Date: Fri Jan 1 09:55:54 2016 +0000 Merge pull request #74 from snowleopard/angerman-patch-5 Update GhcPkg.hs >--------------------------------------------------------------- 77655b7c31c2e37c83bbe36937d4ca65dee74701 src/Rules/Wrappers/GhcPkg.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) From git at git.haskell.org Thu Oct 26 23:51:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #161 from ndmitchell/master (f5f6c41) Message-ID: <20171026235122.EA8323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5f6c41b98c7f4682f0bd73f573fc170e233235a/ghc >--------------------------------------------------------------- commit f5f6c41b98c7f4682f0bd73f573fc170e233235a Merge: 57c6497 8f995f6 Author: Andrey Mokhov Date: Tue Jan 12 22:46:47 2016 +0000 Merge pull request #161 from ndmitchell/master Cleanups in libffi >--------------------------------------------------------------- f5f6c41b98c7f4682f0bd73f573fc170e233235a src/Rules/Actions.hs | 7 ++++++- src/Rules/Libffi.hs | 16 +++++++++------- 2 files changed, 15 insertions(+), 8 deletions(-) From git at git.haskell.org Thu Oct 26 23:51:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a cool screenshot. (9f89177) Message-ID: <20171026235123.084123A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9f8917750b4d83c15934a2e9dfbf51edf76d406d/ghc >--------------------------------------------------------------- commit 9f8917750b4d83c15934a2e9dfbf51edf76d406d Author: Andrey Mokhov Date: Tue Jan 13 06:34:54 2015 +0000 Add a cool screenshot. >--------------------------------------------------------------- 9f8917750b4d83c15934a2e9dfbf51edf76d406d doc/boom.png | Bin 0 -> 91102 bytes 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/doc/boom.png b/doc/boom.png new file mode 100644 index 0000000..834e1bb Binary files /dev/null and b/doc/boom.png differ From git at git.haskell.org Thu Oct 26 23:51:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove a (useless?) output from the buildPackageData rule. (90c4840) Message-ID: <20171026235126.C54B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90c48400bd72d55c030707b62eb3b4eb42eac6b1/ghc >--------------------------------------------------------------- commit 90c48400bd72d55c030707b62eb3b4eb42eac6b1 Author: Andrey Mokhov Date: Tue Jan 13 06:42:45 2015 +0000 Remove a (useless?) output from the buildPackageData rule. >--------------------------------------------------------------- 90c48400bd72d55c030707b62eb3b4eb42eac6b1 src/Package/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index ef89ed0..d3b13a5 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -88,7 +88,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = , "setup-config" , "build" "autogen" "cabal_macros.h" -- TODO: Is this needed? Also check out Paths_cpsa.hs. - , "build" "autogen" ("Paths_" ++ name) <.> "hs" + -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do need ["shake/src/Package/Data.hs"] need [path name <.> "cabal"] From git at git.haskell.org Thu Oct 26 23:51:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GenApply builder, #22. (4b70d6e) Message-ID: <20171026235126.388A43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b70d6e8c474ba0a7789be0b3009e625c1a27820/ghc >--------------------------------------------------------------- commit 4b70d6e8c474ba0a7789be0b3009e625c1a27820 Author: Andrey Mokhov Date: Sat Jan 2 02:09:27 2016 +0000 Add GenApply builder, #22. >--------------------------------------------------------------- 4b70d6e8c474ba0a7789be0b3009e625c1a27820 cfg/system.config.in | 1 + shaking-up-ghc.cabal | 4 +++- src/Builder.hs | 2 ++ src/Rules/Actions.hs | 16 ++++++++++------ src/Settings/Args.hs | 4 ++++ src/Settings/Builders/GenApply.hs | 8 ++++++++ 6 files changed, 28 insertions(+), 7 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index a2cfef3..c5808c7 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -22,6 +22,7 @@ haddock = inplace/bin/haddock hsc2hs = inplace/bin/hsc2hs genprimopcode = inplace/bin/genprimopcode +genapply = inplace/bin/genapply derive-constants = inplace/bin/deriveConstants hs-cpp = @HaskellCPPCmd@ diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 2c75566..48dd0b8 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -38,6 +38,7 @@ executable ghc-shake , Rules.Cabal , Rules.Compile , Rules.Config + , Rules.Copy , Rules.Data , Rules.Dependencies , Rules.Documentation @@ -48,7 +49,6 @@ executable ghc-shake , Rules.Generators.GhcPlatformH , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs - , Rules.Install , Rules.Library , Rules.Oracles , Rules.Package @@ -63,6 +63,7 @@ executable ghc-shake , Settings.Builders.Common , Settings.Builders.DeriveConstants , Settings.Builders.Gcc + , Settings.Builders.GenApply , Settings.Builders.GenPrimopCode , Settings.Builders.Ghc , Settings.Builders.GhcCabal @@ -82,6 +83,7 @@ executable ghc-shake , Settings.Packages.Haddock , Settings.Packages.Hp2ps , Settings.Packages.IntegerGmp + , Settings.Packages.Rts , Settings.Packages.RunGhc , Settings.TargetDirectory , Settings.User diff --git a/src/Builder.hs b/src/Builder.hs index b4b01c3..c8e3f6e 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -25,6 +25,7 @@ data Builder = Alex | DeriveConstants | Gcc Stage | GccM Stage + | GenApply | GenPrimopCode | Ghc Stage | GhcCabal @@ -60,6 +61,7 @@ builderKey builder = case builder of Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' + GenApply -> "genapply" GenPrimopCode -> "genprimopcode" Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 8b243eb..e930b52 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -27,14 +27,12 @@ buildWithResources rs target = do quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList - HsCpp -> do - let file = head $ Target.outputs target -- TODO: ugly - Stdout output <- cmd [path] argList - writeFileChanged file output + HsCpp -> captureStdout target path argList + GenApply -> captureStdout target path argList GenPrimopCode -> do - let src = head $ Target.inputs target -- TODO: ugly - file = head $ Target.outputs target + src <- interpret target getInput + file <- interpret target getOutput input <- readFile' src Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output @@ -45,6 +43,12 @@ buildWithResources rs target = do build :: Target -> Action () build = buildWithResources [] +captureStdout :: Target -> FilePath -> [String] -> Action () +captureStdout target path argList = do + file <- interpret target getOutput + Stdout output <- cmd [path] argList + writeFileChanged file output + -- Print out key information about the command being executed putInfo :: Target.Target -> Action () putInfo (Target.Target {..}) = putBuild $ renderBox $ diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 8066e81..c4c919c 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -7,6 +7,7 @@ import Settings.Builders.Alex import Settings.Builders.Ar import Settings.Builders.DeriveConstants import Settings.Builders.Gcc +import Settings.Builders.GenApply import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc import Settings.Builders.GhcCabal @@ -25,6 +26,7 @@ import Settings.Packages.GhcPrim import Settings.Packages.Haddock import Settings.Packages.Hp2ps import Settings.Packages.IntegerGmp +import Settings.Packages.Rts import Settings.Packages.RunGhc import Settings.User @@ -44,6 +46,7 @@ defaultBuilderArgs = mconcat , deriveConstantsBuilderArgs , gccBuilderArgs , gccMBuilderArgs + , genApplyBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs , ghcCabalBuilderArgs @@ -67,4 +70,5 @@ defaultPackageArgs = mconcat , haddockPackageArgs , hp2psPackageArgs , integerGmpPackageArgs + , rtsPackageArgs , runGhcPackageArgs ] diff --git a/src/Settings/Builders/GenApply.hs b/src/Settings/Builders/GenApply.hs new file mode 100644 index 0000000..2d8140a --- /dev/null +++ b/src/Settings/Builders/GenApply.hs @@ -0,0 +1,8 @@ +module Settings.Builders.GenApply (genApplyBuilderArgs) where + +import Expression + +-- Stdin/stdout are handled in a special way. See Rules/Actions.hs. +-- TODO: Dead code? ifeq "$(GhcUnregisterised)" "YES" GENAPPLY_OPTS = -u +genApplyBuilderArgs :: Args +genApplyBuilderArgs = mempty From git at git.haskell.org Thu Oct 26 23:51:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #155, fix the name of the QuickCheck package (it doesn't follow the convention all the others do) (a60cdcd) Message-ID: <20171026235126.DCA423A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a60cdcd7cb6ce45d1b8f6794d4aa9e5f9415c810/ghc >--------------------------------------------------------------- commit a60cdcd7cb6ce45d1b8f6794d4aa9e5f9415c810 Author: Neil Mitchell Date: Wed Jan 13 08:47:25 2016 +0000 #155, fix the name of the QuickCheck package (it doesn't follow the convention all the others do) >--------------------------------------------------------------- a60cdcd7cb6ce45d1b8f6794d4aa9e5f9415c810 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 4226415..f5b8117 100644 --- a/README.md +++ b/README.md @@ -24,7 +24,7 @@ to adjust anything if you are already familiar with building ghc using the `make build system. Furthermore, we depend on the following packages which need to be installed: -`ansi-terminal`, `mtl`, `shake`, `quickcheck`. +`ansi-terminal`, `mtl`, `shake`, `QuickCheck`. ### Getting the source and configuring GHC From git at git.haskell.org Thu Oct 26 23:51:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename installRules into copyRules and add copy rules for ffi*.h files, #22. (3872f96) Message-ID: <20171026235130.76B333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3872f96896f53e4967674a7e4839dfd0fe1700b7/ghc >--------------------------------------------------------------- commit 3872f96896f53e4967674a7e4839dfd0fe1700b7 Author: Andrey Mokhov Date: Sat Jan 2 02:12:02 2016 +0000 Rename installRules into copyRules and add copy rules for ffi*.h files, #22. >--------------------------------------------------------------- 3872f96896f53e4967674a7e4839dfd0fe1700b7 src/Main.hs | 4 ++-- src/Rules/Copy.hs | 32 ++++++++++++++++++++++++++++++++ src/Rules/Install.hs | 22 ---------------------- 3 files changed, 34 insertions(+), 24 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index fdc43cd..b2c5340 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,14 +3,14 @@ import Rules import Rules.Cabal import Rules.Config import Rules.Generate -import Rules.Install +import Rules.Copy import Rules.Oracles main :: IO () main = shakeArgs options $ do cabalRules -- see Rules.Cabal configRules -- see Rules.Config - installRules -- see Rules.Install + copyRules -- see Rules.Copy generateTargets -- see Rules generateRules -- see Rules.Generate oracleRules -- see Rules.Oracles diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs new file mode 100644 index 0000000..47d6f02 --- /dev/null +++ b/src/Rules/Copy.hs @@ -0,0 +1,32 @@ +module Rules.Copy (installTargets, copyRules) where + +import Base +import Expression +import GHC +import Rules.Generate +import Settings.TargetDirectory + +installTargets :: [FilePath] +installTargets = [ "inplace/lib/template-hsc.h" + , "inplace/lib/platformConstants" + , "inplace/lib/settings" ] + +copyRules :: Rules () +copyRules = do + targetPath Stage1 rts -/- "build/ffi*.h" %> \ffih -> do + ffiHPaths <- getDirectoryFiles "" ["libffi/build/inst/lib/*/include/ffi.h"] + when (length ffiHPaths /= 1) $ + putError "copyRules: cannot determine location of ffi.h" + let ffiHPath = takeDirectory $ head ffiHPaths + copy ffih ffiHPath + + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs + "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." + where + file <~ dir = file %> \_ -> copy file dir + + copy file dir = do + let source = dir -/- takeFileName file + copyFileChanged source file + putBuild $ "| Copy " ++ source ++ " -> " ++ file diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs deleted file mode 100644 index 2e74bd3..0000000 --- a/src/Rules/Install.hs +++ /dev/null @@ -1,22 +0,0 @@ -module Rules.Install (installTargets, installRules) where - -import Base -import Expression -import GHC -import Rules.Generate - -installTargets :: [FilePath] -installTargets = [ "inplace/lib/template-hsc.h" - , "inplace/lib/platformConstants" - , "inplace/lib/settings" ] - -installRules :: Rules () -installRules = do - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs - "inplace/lib/platformConstants" <~ derivedConstantsPath - "inplace/lib/settings" <~ "." - where - file <~ dir = file %> \out -> do - let source = dir -/- takeFileName out - copyFileChanged source out - putSuccess $ "| Installed " ++ source ++ " -> " ++ out From git at git.haskell.org Thu Oct 26 23:51:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add bin-package-db package. (cd02d00) Message-ID: <20171026235131.189363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cd02d00639738e151e77288de9d116e286cb83c1/ghc >--------------------------------------------------------------- commit cd02d00639738e151e77288de9d116e286cb83c1 Author: Andrey Mokhov Date: Tue Jan 13 06:43:02 2015 +0000 Add bin-package-db package. >--------------------------------------------------------------- cd02d00639738e151e77288de9d116e286cb83c1 src/Package.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index e29551f..d2fd4db 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -10,8 +10,9 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] -packages = [libraryPackage "array" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings] +packages = [libraryPackage "array" Stage1 defaultSettings, + libraryPackage "deepseq" Stage1 defaultSettings, + libraryPackage "bin-package-db" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -28,7 +29,10 @@ packageRules = do , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.a" , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.p_a" - , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" ] + , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" + , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.a" + , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.p_a" + , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:51:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #162 from ndmitchell/master (6934485) Message-ID: <20171026235131.26B8C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6934485f0e98b62630ce0d867ebc6b8f3da5f04a/ghc >--------------------------------------------------------------- commit 6934485f0e98b62630ce0d867ebc6b8f3da5f04a Merge: f5f6c41 a60cdcd Author: Andrey Mokhov Date: Wed Jan 13 09:15:24 2016 +0000 Merge pull request #162 from ndmitchell/master #155, fix the name of the QuickCheck package [skip ci] >--------------------------------------------------------------- 6934485f0e98b62630ce0d867ebc6b8f3da5f04a README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:51:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add basic support for rts package, #22. (34488df) Message-ID: <20171026235134.456F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34488dfe235c8793012a53a407359dcf0dff80b4/ghc >--------------------------------------------------------------- commit 34488dfe235c8793012a53a407359dcf0dff80b4 Author: Andrey Mokhov Date: Sat Jan 2 02:12:49 2016 +0000 Add basic support for rts package, #22. >--------------------------------------------------------------- 34488dfe235c8793012a53a407359dcf0dff80b4 src/GHC.hs | 17 ++-- src/Predicates.hs | 12 ++- src/Rules.hs | 8 +- src/Rules/Cabal.hs | 2 +- src/Rules/Data.hs | 18 +++++ src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 4 +- src/Rules/Generate.hs | 18 +++-- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Builders/Haddock.hs | 3 +- src/Settings/Packages.hs | 3 +- src/Settings/Packages/Rts.hs | 165 +++++++++++++++++++++++++++++++++++++++ 12 files changed, 228 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 34488dfe235c8793012a53a407359dcf0dff80b4 From git at git.haskell.org Thu Oct 26 23:51:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CppOpts. (316ff4c) Message-ID: <20171026235135.1F55B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/316ff4cb2e421831281e42b09fb90ba5dae2b239/ghc >--------------------------------------------------------------- commit 316ff4cb2e421831281e42b09fb90ba5dae2b239 Author: Andrey Mokhov Date: Tue Jan 13 07:28:48 2015 +0000 Add CppOpts. >--------------------------------------------------------------- 316ff4cb2e421831281e42b09fb90ba5dae2b239 src/Oracles/PackageData.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 66a3f55..bf94713 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -19,6 +19,7 @@ data PackageData = Modules FilePath | Deps FilePath | DepKeys FilePath | Synopsis FilePath + | CppOpts FilePath instance ShowArgs PackageData where showArgs packageData = do @@ -30,6 +31,7 @@ instance ShowArgs PackageData where Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) Synopsis file -> ("SYNOPSIS" , file, "" ) + CppOpts file -> ("CPP_OPTS" , file, "" ) fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key res <- askOracle $ PackageDataKey (file, fullKey) return $ words $ case res of From git at git.haskell.org Thu Oct 26 23:51:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix handling of --with-gmp-* configure arguments (80eac86) Message-ID: <20171026235135.2EC853A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/80eac86c555a8e0d48a694ffc23f0ac2c75236d0/ghc >--------------------------------------------------------------- commit 80eac86c555a8e0d48a694ffc23f0ac2c75236d0 Author: Karel Gardas Date: Wed Jan 13 22:24:38 2016 +0100 fix handling of --with-gmp-* configure arguments >--------------------------------------------------------------- 80eac86c555a8e0d48a694ffc23f0ac2c75236d0 src/Rules/Gmp.hs | 46 ++++++++++++++++++++++++++++++++-------------- 1 file changed, 32 insertions(+), 14 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index b02fe36..94086e1 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -57,6 +57,19 @@ configureArguments = do , "--host=" ++ hostPlatform , "--build=" ++ buildPlatform] +configureIntGmpArguments :: Action [String] +configureIntGmpArguments = do + includes <- settingList GmpIncludeDirs + libs <- settingList GmpLibDirs + return ([] + ++ (if (not (null includes)) + then map ((++) "--with-gmp-includes=") includes + else []) + ++ (if (not (null libs)) + then map ((++) "--with-gmp-libraries=") libs + else []) + ) + -- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do @@ -105,7 +118,8 @@ gmpRules = do runConfigure libPath envs args -- TODO: currently we configure integerGmp package twice -- optimise - runConfigure (pkgPath integerGmp) [] [] + intGmpArgs <- configureIntGmpArguments + runConfigure (pkgPath integerGmp) envs intGmpArgs createDirectory $ takeDirectory gmpLibraryH -- check whether we need to build in tree gmp @@ -115,19 +129,23 @@ gmpRules = do then do putBuild "| GMP framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - else do - putBuild "| No GMP framework detected; in tree GMP will be built" - runMake libPath ["MAKEFLAGS="] - - copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH - copyFile (libPath -/- "gmp.h") gmpLibraryH - -- TODO: why copy library, can we move it instead? - copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary - - createDirectory gmpObjects - build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] - - runBuilder Ranlib [gmpLibrary] + else if "HaveLibGmp = YES" `isInfixOf` configMk + then do + putBuild "| GMP detected and will be used" + copyFile gmpLibraryFakeH gmpLibraryH + else do + putBuild "| No GMP framework detected; in tree GMP will be built" + runMake libPath ["MAKEFLAGS="] + + copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH + copyFile (libPath -/- "gmp.h") gmpLibraryH + -- TODO: why copy library, can we move it instead? + copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary + + createDirectory gmpObjects + build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] + + runBuilder Ranlib [gmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" From git at git.haskell.org Thu Oct 26 23:51:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Ranlib and Tar builders. (d06dabc) Message-ID: <20171026235137.EF60C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d06dabcb601c169ad1f8742e318d899891b380e3/ghc >--------------------------------------------------------------- commit d06dabcb601c169ad1f8742e318d899891b380e3 Author: Andrey Mokhov Date: Sun Jan 3 01:09:34 2016 +0000 Add Ranlib and Tar builders. >--------------------------------------------------------------- d06dabcb601c169ad1f8742e318d899891b380e3 cfg/system.config.in | 2 ++ src/Builder.hs | 4 ++++ src/Settings/Args.hs | 4 +++- src/Settings/Builders/Tar.hs | 10 ++++++++++ 4 files changed, 19 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index c5808c7..7f9b8de 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -38,6 +38,8 @@ hscolour = @HSCOLOUR@ ld = @LdCmd@ nm = @NmCmd@ objdump = @ObjdumpCmd@ +ranlib = @REAL_RANLIB_CMD@ +tar = @TarCmd@ # Information about builders: #============================ diff --git a/src/Builder.hs b/src/Builder.hs index c8e3f6e..ad7c9f0 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -41,6 +41,8 @@ data Builder = Alex | Ld | Nm | Objdump + | Ranlib + | Tar | Unlit deriving (Show, Eq, Generic) @@ -81,6 +83,8 @@ builderKey builder = case builder of Ld -> "ld" Nm -> "nm" Objdump -> "objdump" + Ranlib -> "ranlib" + Tar -> "tar" Unlit -> "unlit" -- | Determine the location of a 'Builder' diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index c4c919c..a677c80 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -17,6 +17,7 @@ import Settings.Builders.Happy import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld +import Settings.Builders.Tar import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Directory @@ -57,7 +58,8 @@ defaultBuilderArgs = mconcat , happyBuilderArgs , hsc2hsBuilderArgs , hsCppBuilderArgs - , ldBuilderArgs ] + , ldBuilderArgs + , tarBuilderArgs ] defaultPackageArgs :: Args defaultPackageArgs = mconcat diff --git a/src/Settings/Builders/Tar.hs b/src/Settings/Builders/Tar.hs new file mode 100644 index 0000000..1f9f0ba --- /dev/null +++ b/src/Settings/Builders/Tar.hs @@ -0,0 +1,10 @@ +module Settings.Builders.Tar (tarBuilderArgs) where + +import Expression +import Predicates (builder) + +tarBuilderArgs :: Args +tarBuilderArgs = builder Tar ? do + mconcat [ arg "-xzf" + , arg =<< getInput + , arg "-C", arg =<< getOutput ] From git at git.haskell.org Thu Oct 26 23:51:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add binary package. (02297c2) Message-ID: <20171026235139.416BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02297c23579d7a11d9d99efacda7a328801cbfaa/ghc >--------------------------------------------------------------- commit 02297c23579d7a11d9d99efacda7a328801cbfaa Author: Andrey Mokhov Date: Tue Jan 13 07:29:15 2015 +0000 Add binary package. >--------------------------------------------------------------- 02297c23579d7a11d9d99efacda7a328801cbfaa src/Package.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index d2fd4db..899e48a 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -12,7 +12,8 @@ import Package.Dependencies packages :: [Package] packages = [libraryPackage "array" Stage1 defaultSettings, libraryPackage "deepseq" Stage1 defaultSettings, - libraryPackage "bin-package-db" Stage1 defaultSettings] + libraryPackage "bin-package-db" Stage1 defaultSettings, + libraryPackage "binary" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -32,7 +33,10 @@ packageRules = do , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.a" , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.p_a" - , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" ] + , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" + , "libraries/binary/dist-install/build/HSbinar_8WpSY1EWq5j1AwY619xVVw.o" + , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.a" + , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.p_a" ] forM_ packages $ \pkg -> do forM_ (pkgTodo pkg) $ \todoItem -> do buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:51:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: merge GMP library and framework GMP checks together (b784a22) Message-ID: <20171026235139.5F4253A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b784a2233bc75245bfddef304fa690dbcf382311/ghc >--------------------------------------------------------------- commit b784a2233bc75245bfddef304fa690dbcf382311 Author: Karel Gardas Date: Wed Jan 13 23:03:08 2016 +0100 merge GMP library and framework GMP checks together >--------------------------------------------------------------- b784a2233bc75245bfddef304fa690dbcf382311 src/Rules/Gmp.hs | 33 +++++++++++++++------------------ 1 file changed, 15 insertions(+), 18 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 94086e1..f34f3f0 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -126,26 +126,23 @@ gmpRules = do -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` configMk <- liftIO . readFile $ gmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk + || "HaveLibGmp = YES" `isInfixOf` configMk then do - putBuild "| GMP framework detected and will be used" + putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - else if "HaveLibGmp = YES" `isInfixOf` configMk - then do - putBuild "| GMP detected and will be used" - copyFile gmpLibraryFakeH gmpLibraryH - else do - putBuild "| No GMP framework detected; in tree GMP will be built" - runMake libPath ["MAKEFLAGS="] - - copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH - copyFile (libPath -/- "gmp.h") gmpLibraryH - -- TODO: why copy library, can we move it instead? - copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary - - createDirectory gmpObjects - build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] - - runBuilder Ranlib [gmpLibrary] + else do + putBuild "| No GMP library/framework detected; in tree GMP will be built" + runMake libPath ["MAKEFLAGS="] + + copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH + copyFile (libPath -/- "gmp.h") gmpLibraryH + -- TODO: why copy library, can we move it instead? + copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary + + createDirectory gmpObjects + build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] + + runBuilder Ranlib [gmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" From git at git.haskell.org Thu Oct 26 23:51:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add COMPONENT_ID field to rts package-data.mk (#22). (d3eef6d) Message-ID: <20171026235141.582393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3eef6dc2e2c2ae8b6727f17b610bb058f45282d/ghc >--------------------------------------------------------------- commit d3eef6dc2e2c2ae8b6727f17b610bb058f45282d Author: Andrey Mokhov Date: Sun Jan 3 01:11:16 2016 +0000 Add COMPONENT_ID field to rts package-data.mk (#22). >--------------------------------------------------------------- d3eef6dc2e2c2ae8b6727f17b610bb058f45282d src/Rules/Data.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index c2a186f..b24bb85 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -87,7 +87,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do includes <- interpretPartial target $ fromDiffExpr includesArgs let contents = unlines $ map (prefix++) [ "C_SRCS = " ++ unwords (cSrcs ++ cmmSrcs ++ extraSrcs) - , "CC_OPTS = " ++ unwords includes ] + , "CC_OPTS = " ++ unwords includes + , "COMPONENT_ID = " ++ "rts" ] writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." From git at git.haskell.org Thu Oct 26 23:51:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing options and pkgDepObjects. (92352f7) Message-ID: <20171026235143.4616B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92352f7763115e6a78452b48d9872681a4dca3eb/ghc >--------------------------------------------------------------- commit 92352f7763115e6a78452b48d9872681a4dca3eb Author: Andrey Mokhov Date: Tue Jan 13 07:29:56 2015 +0000 Fix missing options and pkgDepObjects. >--------------------------------------------------------------- 92352f7763115e6a78452b48d9872681a4dca3eb src/Package/Base.hs | 7 ++++--- src/Package/Compile.hs | 3 ++- src/Package/Dependencies.hs | 1 + 3 files changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index f6c70ea..bac6801 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -122,9 +122,10 @@ pkgDepObjects :: FilePath -> FilePath -> Way -> Action [FilePath] pkgDepObjects path dist way = do let pkgData = path dist "package-data.mk" buildDir = path dist "build" - hs2obj = (buildDir ++) . drop (length path) . (-<.> osuf way) - srcs <- pkgHsSources path dist - return $ map (toStandard . hs2obj) srcs + dirs <- map (normaliseEx . (path )) <$> arg (SrcDirs pkgData) + fmap concat $ forM dirs $ \d -> + map (toStandard . (buildDir ++) . (-<.> osuf way) . drop (length d)) + <$> (findModuleFiles pkgData [d] [".hs", ".lhs"]) -- Find objects that go to library pkgLibObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 80835f8..c42d592 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -48,6 +48,7 @@ oRule (Package name path _) (stage, dist, settings) = <> arg SrcHcOpts <> packageArgs stage pkgData <> includeArgs path dist + <> concatArgs ["-optP"] (CppOpts pkgData) -- TODO: now we have both -O and -O2 <> arg ["-Wall", "-XHaskell2010", "-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir @@ -55,7 +56,7 @@ oRule (Package name path _) (stage, dist, settings) = <> arg ("-c":srcs) <> arg ["-o", toStandard out] --- TODO: This rule looks a bit of a hack... combine it with the above? +-- TODO: This rule looks hacky... combine it with the above? hiRule :: Package -> TodoItem -> Rules () hiRule (Package name path _) (stage, dist, settings) = let buildDir = path dist "build" diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 63ed508..fc9f4af 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -13,6 +13,7 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData <> includeArgs path dist + <> concatArgs ["-optP"] (CppOpts pkgData) <> productArgs ["-odir", "-stubdir", "-hidir"] buildDir <> arg ["-dep-makefile", toStandard $ out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) From git at git.haskell.org Thu Oct 26 23:51:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: simplify configureIntGmpArguments based on idea provided by Gabor Greif (86a3fe5) Message-ID: <20171026235143.6BBA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86a3fe5f1e16ef919cf0145c0830f2ad7cd8586e/ghc >--------------------------------------------------------------- commit 86a3fe5f1e16ef919cf0145c0830f2ad7cd8586e Author: Karel Gardas Date: Wed Jan 13 23:31:29 2016 +0100 simplify configureIntGmpArguments based on idea provided by Gabor Greif >--------------------------------------------------------------- 86a3fe5f1e16ef919cf0145c0830f2ad7cd8586e src/Rules/Gmp.hs | 11 +++-------- 1 file changed, 3 insertions(+), 8 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index f34f3f0..f6d6fe8 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -61,14 +61,9 @@ configureIntGmpArguments :: Action [String] configureIntGmpArguments = do includes <- settingList GmpIncludeDirs libs <- settingList GmpLibDirs - return ([] - ++ (if (not (null includes)) - then map ((++) "--with-gmp-includes=") includes - else []) - ++ (if (not (null libs)) - then map ((++) "--with-gmp-libraries=") libs - else []) - ) + return $ map ("--with-gmp-includes=" ++) includes + ++ map ("--with-gmp-libraries=" ++) libs + -- TODO: we rebuild gmp every time. gmpRules :: Rules () From git at git.haskell.org Thu Oct 26 23:51:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build libffi library, fix #75. (3b8aa92) Message-ID: <20171026235144.D5E603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b8aa92730ff232c16a6fa0da54b6e9c4fe47381/ghc >--------------------------------------------------------------- commit 3b8aa92730ff232c16a6fa0da54b6e9c4fe47381 Author: Andrey Mokhov Date: Sun Jan 3 01:12:26 2016 +0000 Build libffi library, fix #75. >--------------------------------------------------------------- 3b8aa92730ff232c16a6fa0da54b6e9c4fe47381 shaking-up-ghc.cabal | 2 + src/GHC.hs | 19 +++--- src/Main.hs | 2 + src/Rules.hs | 2 +- src/Rules/Cabal.hs | 19 +++--- src/Rules/Copy.hs | 5 +- src/Rules/Libffi.hs | 119 ++++++++++++++++++++++++++++++++++++++ src/Rules/Library.hs | 4 +- src/Rules/Program.hs | 2 +- src/Settings/Builders/Common.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 3 - src/Settings/Builders/Hsc2Hs.hs | 6 +- 12 files changed, 159 insertions(+), 29 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3b8aa92730ff232c16a6fa0da54b6e9c4fe47381 From git at git.haskell.org Thu Oct 26 23:51:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix dropDynamic. (d1ade7d) Message-ID: <20171026235146.BC23B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1ade7d5917eeea88c2034dc52bb8bf100bfc05a/ghc >--------------------------------------------------------------- commit d1ade7d5917eeea88c2034dc52bb8bf100bfc05a Author: Andrey Mokhov Date: Tue Jan 13 13:01:30 2015 +0000 Fix dropDynamic. >--------------------------------------------------------------- d1ade7d5917eeea88c2034dc52bb8bf100bfc05a src/Ways.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Ways.hs b/src/Ways.hs index b478a04..24c1a80 100644 --- a/src/Ways.hs +++ b/src/Ways.hs @@ -14,7 +14,7 @@ module Ways ( wayHcArgs, wayPrefix, - hisuf, osuf, hcsuf, + hisuf, osuf, hcsuf, obootsuf, ssuf, libsuf, detectWay ) where @@ -125,7 +125,7 @@ dropDynamic way | way == debugDynamic = debug | way == loggingDynamic = logging | way == threadedLoggingDynamic = threadedLogging - | otherwise = error $ "Cannot drop Dynamic from way " ++ tag way ++ "." + | otherwise = way -- Detect way from a given extension. Fail if the result is not unique. -- TODO: This may be slow -- optimise if overhead is significant. From git at git.haskell.org Thu Oct 26 23:51:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drops 'none' (a24a85f) Message-ID: <20171026235146.EE8A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a24a85f283a387df60e9755398c1e2c563fe1cda/ghc >--------------------------------------------------------------- commit a24a85f283a387df60e9755398c1e2c563fe1cda Author: Moritz Angermann Date: Thu Jan 14 14:02:51 2016 +0800 Drops 'none' shake has `-q` already, which is identical. >--------------------------------------------------------------- a24a85f283a387df60e9755398c1e2c563fe1cda src/Base.hs | 1 - src/Oracles/Config/CmdLineFlag.hs | 3 +-- 2 files changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index be3ff1b..a46031c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -152,7 +152,6 @@ renderAction what input output = case buildInfo of , " input:" ++ input , " => output:" ++ output ] Dot -> "." - None -> "" -- | Render the successful build of a program renderProgram :: String -> String -> String -> String diff --git a/src/Oracles/Config/CmdLineFlag.hs b/src/Oracles/Config/CmdLineFlag.hs index 687c541..47dbbbc 100644 --- a/src/Oracles/Config/CmdLineFlag.hs +++ b/src/Oracles/Config/CmdLineFlag.hs @@ -8,7 +8,7 @@ import Data.IORef -- Flags -data BuildInfoFlag = Normal | Brief | Pony | Dot | None deriving (Eq, Show) +data BuildInfoFlag = Normal | Brief | Pony | Dot deriving (Eq, Show) data CmdLineOptions = CmdLineOptions { flagBuildInfo :: BuildInfoFlag @@ -29,7 +29,6 @@ readBuildInfoFlag ms = go "brief" = Just Brief go "pony" = Just Pony go "dot" = Just Dot - go "none" = Just None go _ = Nothing -- Left "no parse" mkClosure :: BuildInfoFlag -> CmdLineOptions -> CmdLineOptions mkClosure flag opts = opts { flagBuildInfo = flag } From git at git.haskell.org Thu Oct 26 23:51:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Register rts package, see #22 and #67. (9be3f7e) Message-ID: <20171026235148.8B7D03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9be3f7e7f4de05897602959de5ee5025a10d7a8b/ghc >--------------------------------------------------------------- commit 9be3f7e7f4de05897602959de5ee5025a10d7a8b Author: Andrey Mokhov Date: Sun Jan 3 02:45:41 2016 +0000 Register rts package, see #22 and #67. >--------------------------------------------------------------- 9be3f7e7f4de05897602959de5ee5025a10d7a8b src/Base.hs | 13 +++++++++- src/Rules/Data.hs | 52 ++++++++++++++++++++++++-------------- src/Rules/Libffi.hs | 10 -------- src/Settings/Packages/Rts.hs | 59 ++++++++++++++++++++++++++++++++++++++++---- 4 files changed, 99 insertions(+), 35 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 9be3f7e7f4de05897602959de5ee5025a10d7a8b From git at git.haskell.org Thu Oct 26 23:51:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add toStandard. (fd28d9a) Message-ID: <20171026235150.764713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd28d9aa2dc7a212d20685e5541c1e059288c799/ghc >--------------------------------------------------------------- commit fd28d9aa2dc7a212d20685e5541c1e059288c799 Author: Andrey Mokhov Date: Tue Jan 13 13:02:06 2015 +0000 Add toStandard. >--------------------------------------------------------------- fd28d9aa2dc7a212d20685e5541c1e059288c799 src/Package/Compile.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index c42d592..56d168a 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -31,8 +31,8 @@ suffixArgs way = arg ["-hisuf", hisuf way] oRule :: Package -> TodoItem -> Rules () oRule (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" - pkgData = path dist "package-data.mk" + let buildDir = toStandard $ path dist "build" + pkgData = toStandard $ path dist "package-data.mk" depFile = buildDir name <.> "m" in (buildDir "*o") %> \out -> do @@ -59,7 +59,7 @@ oRule (Package name path _) (stage, dist, settings) = -- TODO: This rule looks hacky... combine it with the above? hiRule :: Package -> TodoItem -> Rules () hiRule (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" + let buildDir = toStandard $ path dist "build" in (buildDir "*hi") %> \out -> do let way = detectWay $ tail $ takeExtension out From git at git.haskell.org Thu Oct 26 23:51:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Proper support for `dot` (46bf4bc) Message-ID: <20171026235150.CCCBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46bf4bcb391b6008d39aa2c334ec265141fd6a80/ghc >--------------------------------------------------------------- commit 46bf4bcb391b6008d39aa2c334ec265141fd6a80 Author: Moritz Angermann Date: Thu Jan 14 14:03:05 2016 +0800 Proper support for `dot` Adds support for `dot`, by conditionally switching between `BS.putStr` and `BS.putStrLn` depending on the msg. The additional imports are part of shake anyway. Fixes #134, dot support for good :) >--------------------------------------------------------------- 46bf4bcb391b6008d39aa2c334ec265141fd6a80 shaking-up-ghc.cabal | 2 ++ src/Main.hs | 29 ++++++++++++++++++++++++++++- 2 files changed, 30 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index b38feac..123870d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -116,6 +116,7 @@ executable ghc-shake , ScopedTypeVariables build-depends: base , ansi-terminal >= 0.6 + , bytestring >= 0.10.6 , Cabal >= 1.22 , containers >= 0.5 , directory >= 1.2 @@ -125,5 +126,6 @@ executable ghc-shake , shake >= 0.15 , transformers >= 0.4 , unordered-containers >= 0.2 + , utf8-string >= 1.0.1 default-language: Haskell2010 ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j diff --git a/src/Main.hs b/src/Main.hs index e3f1a34..6ec93429 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -14,6 +14,10 @@ import qualified Rules.Perl import qualified Test import Oracles.Config.CmdLineFlag (putOptions, flags) +import qualified Data.ByteString.Char8 as BS +import qualified Data.ByteString.UTF8 as UTF8 +import Data.Char (chr) + main :: IO () main = shakeArgsWith options flags $ \cmdLineFlags targets -> do putOptions cmdLineFlags @@ -36,4 +40,27 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do options = shakeOptions { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple - , shakeTimings = True } + , shakeTimings = True + , shakeOutput = const showMsg + } + +showMsg :: String -> IO () +showMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg +showMsg msg | dropEscSequence msg == "" = return () +showMsg msg = BS.putStrLn . UTF8.fromString $ msg + +dropEscSequence :: String -> String +dropEscSequence = go + where + esc :: Char + esc = Data.Char.chr 27 + go :: String -> String + go [] = [] + go [x] = [x] + go (x:xs) | x == esc = skip xs + go (x:xs) | otherwise = x:go xs + skip :: String -> String + skip [] = [] + skip ['m'] = [] + skip ('m':xs) = go xs + skip (_ :xs) = skip xs From git at git.haskell.org Thu Oct 26 23:51:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghcautoconf, ghcplatform as rtsConf dependencies (122a01d) Message-ID: <20171026235152.2CB9D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/122a01d4350e0c8888a0bc0007f2edfccaf87f47/ghc >--------------------------------------------------------------- commit 122a01d4350e0c8888a0bc0007f2edfccaf87f47 Author: Moritz Angermann Date: Sun Jan 3 12:41:28 2016 +0800 Add ghcautoconf, ghcplatform as rtsConf dependencies This fixes #76. >--------------------------------------------------------------- 122a01d4350e0c8888a0bc0007f2edfccaf87f47 src/Rules/Data.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 00f6368..84ac619 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -99,7 +99,9 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fullTarget target (GhcPkg stage) [rtsConf] [] rtsConf %> \_ -> do - need [rtsConfIn] + need [rtsConfIn + , "includes/ghcautoconf.h" + , "includes/ghcplatform.h" ] build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] old <- liftIO $ readFile rtsConf let new = unlines . map (replace "\"\"" "") From git at git.haskell.org Thu Oct 26 23:51:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate targets from package list. (5c01b64) Message-ID: <20171026235154.5CA4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5c01b64cff13863a0c3dc34a63352b7214245a72/ghc >--------------------------------------------------------------- commit 5c01b64cff13863a0c3dc34a63352b7214245a72 Author: Andrey Mokhov Date: Tue Jan 13 13:03:48 2015 +0000 Generate targets from package list. >--------------------------------------------------------------- 5c01b64cff13863a0c3dc34a63352b7214245a72 src/Package.hs | 30 ++++++++++++++++-------------- 1 file changed, 16 insertions(+), 14 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 899e48a..217c05a 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -25,18 +25,20 @@ buildPackage = buildPackageData packageRules :: Rules () packageRules = do -- TODO: control targets from commang line arguments - want [ "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.a" - , "libraries/deepseq/dist-install/build/libHSdeeps_FT5iVCELxOr62eHY0nbvnU.p_a" - , "libraries/deepseq/dist-install/build/HSdeeps_FT5iVCELxOr62eHY0nbvnU.o" - , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.a" - , "libraries/array/dist-install/build/libHSarray_3w0nMK0JfaFJPpLFn2yWAJ.p_a" - , "libraries/array/dist-install/build/HSarray_3w0nMK0JfaFJPpLFn2yWAJ.o" - , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.a" - , "libraries/bin-package-db/dist-install/build/libHSbinpa_9qPPbdABQ6HK3eua2jBtib.p_a" - , "libraries/bin-package-db/dist-install/build/HSbinpa_9qPPbdABQ6HK3eua2jBtib.o" - , "libraries/binary/dist-install/build/HSbinar_8WpSY1EWq5j1AwY619xVVw.o" - , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.a" - , "libraries/binary/dist-install/build/libHSbinar_8WpSY1EWq5j1AwY619xVVw.p_a" ] - forM_ packages $ \pkg -> do - forM_ (pkgTodo pkg) $ \todoItem -> do + forM_ packages $ \pkg @ (Package name path todo) -> do + forM_ todo $ \todoItem @ (stage, dist, settings) -> do + + -- Want top .o and .a files for the pkg/todo combo: + action $ do + let buildDir = path dist "build" + pkgData = path dist "package-data.mk" + [key] <- arg (PackageKey pkgData) + let oFile = buildDir "Hs" ++ key <.> "o" + ways' <- ways settings + aFiles <- forM ways' $ \way -> do + extension <- libsuf way + return $ buildDir "libHs" ++ key <.> extension + need $ [oFile] ++ aFiles + + -- Build rules for the package buildPackage pkg todoItem From git at git.haskell.org Thu Oct 26 23:51:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Complete Advanced Render Box (231a5ce) Message-ID: <20171026235154.AB0493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/231a5ce27baa03e0750e991b5d6af3b81d9cde29/ghc >--------------------------------------------------------------- commit 231a5ce27baa03e0750e991b5d6af3b81d9cde29 Author: Moritz Angermann Date: Thu Jan 14 14:16:41 2016 +0800 Complete Advanced Render Box Should fix #134 for good. >--------------------------------------------------------------- 231a5ce27baa03e0750e991b5d6af3b81d9cde29 src/Base.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index a46031c..b9c7f72 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -115,11 +115,16 @@ a -/- b = unifyPath $ a b infixr 6 -/- +-- | A wrapper around shakes @putNormal@ that substitutes +-- any message for a fullstop if @buildInfo@ is @Dot at . +putNormal' :: String -> Action () +putNormal' = if buildInfo == Dot then putNormal . const "." else putNormal + -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do liftIO $ setSGR [SetColor Foreground Vivid colour] - putNormal msg + putNormal' msg liftIO $ setSGR [] liftIO $ hFlush stdout From git at git.haskell.org Thu Oct 26 23:51:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds ghcversion and derivedconstants to rts (25b2408) Message-ID: <20171026235155.98CFE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/25b2408edd914c06d2e25f16bde711e54a548f2c/ghc >--------------------------------------------------------------- commit 25b2408edd914c06d2e25f16bde711e54a548f2c Author: Moritz Angermann Date: Sun Jan 3 12:42:27 2016 +0800 Adds ghcversion and derivedconstants to rts Fixes #77 and fixes #76 (ghcverison). >--------------------------------------------------------------- 25b2408edd914c06d2e25f16bde711e54a548f2c src/Rules/Generate.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index e14b941..299f79a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -62,6 +62,9 @@ generatedDependencies stage pkg , "includes/ghcplatform.h" ] | pkg == rts = let buildPath = targetPath stage rts -/- "build" in + [ "includes/ghcversion.h" -- missing only in stage1. See #76 + , derivedConstantsPath -/- "DerivedConstants.h" ] + ++ fmap (buildPath -/-) ["ffi.h", "ffitarget.h"] | otherwise = [] From git at git.haskell.org Thu Oct 26 23:51:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (7ad0b09) Message-ID: <20171026235157.C3CB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ad0b09ddbfd98ec8e026ef146add00e12c35e2f/ghc >--------------------------------------------------------------- commit 7ad0b09ddbfd98ec8e026ef146add00e12c35e2f Author: Andrey Mokhov Date: Tue Jan 13 15:22:31 2015 +0000 Clean up. >--------------------------------------------------------------- 7ad0b09ddbfd98ec8e026ef146add00e12c35e2f src/Base.hs | 2 ++ src/Oracles/Builder.hs | 12 ++++++++---- src/Oracles/Option.hs | 4 ++++ src/Package.hs | 6 +++--- src/Package/Compile.hs | 7 ++++--- src/Package/Dependencies.hs | 2 +- src/Package/Library.hs | 3 ++- 7 files changed, 24 insertions(+), 12 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 169f556..e3f2256 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -27,6 +27,8 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) instance Show Stage where show = show . fromEnum +-- The returned list of strings is a list of arguments +-- to be passed to a Builder type Args = Action [String] type Condition = Action Bool diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 8a2c5b2..5c9d64b 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -11,6 +11,9 @@ import Oracles.Base import Oracles.Flag import Oracles.Option +-- A Builder is an external command invoked in separate process +-- by calling Shake.cmd +-- -- Ghc Stage0 is the bootstrapping compiler -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg @@ -96,7 +99,8 @@ run :: Builder -> Args -> Action () run builder args = do needBuilder builder [exe] <- showArgs builder - cmd [exe] =<< args + args' <- args + cmd [exe] args' -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. @@ -106,9 +110,9 @@ terseRun builder args = do needBuilder builder [exe] <- showArgs builder args' <- args - putNormal $ "--------\nRunning " ++ show builder ++ " with arguments:" - mapM_ (putNormal . (" " ++)) $ interestingInfo builder args' - putNormal "--------" + putNormal $ "|--------\n| Running " ++ show builder ++ " with arguments:" + mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args' + putNormal "|--------" quietly $ cmd [exe] args' interestingInfo :: Builder -> [String] -> [String] diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 89192a7..ee8fb66 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -8,6 +8,10 @@ import Base import Oracles.Flag import Oracles.Base +-- For each Option the files {default.config, user.config} contain +-- a line of the form 'target-os = mingw32'. +-- (showArgs TargetOS) is an action that consults the config files +-- and returns ["mingw32"]. -- TODO: separate single string options from multiple string ones. data Option = TargetOS | TargetArch diff --git a/src/Package.hs b/src/Package.hs index 217c05a..e815c4b 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -11,9 +11,9 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] packages = [libraryPackage "array" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings, libraryPackage "bin-package-db" Stage1 defaultSettings, - libraryPackage "binary" Stage1 defaultSettings] + libraryPackage "binary" Stage1 defaultSettings, + libraryPackage "deepseq" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -24,7 +24,7 @@ buildPackage = buildPackageData packageRules :: Rules () packageRules = do - -- TODO: control targets from commang line arguments + -- TODO: control targets from command line arguments forM_ packages $ \pkg @ (Package name path todo) -> do forM_ todo $ \todoItem @ (stage, dist, settings) -> do diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 56d168a..d701af6 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -32,7 +32,7 @@ suffixArgs way = arg ["-hisuf", hisuf way] oRule :: Package -> TodoItem -> Rules () oRule (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" - pkgData = toStandard $ path dist "package-data.mk" + pkgData = path dist "package-data.mk" depFile = buildDir name <.> "m" in (buildDir "*o") %> \out -> do @@ -49,6 +49,7 @@ oRule (Package name path _) (stage, dist, settings) = <> packageArgs stage pkgData <> includeArgs path dist <> concatArgs ["-optP"] (CppOpts pkgData) + -- TODO: use HC_OPTS from pkgData -- TODO: now we have both -O and -O2 <> arg ["-Wall", "-XHaskell2010", "-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir @@ -59,10 +60,10 @@ oRule (Package name path _) (stage, dist, settings) = -- TODO: This rule looks hacky... combine it with the above? hiRule :: Package -> TodoItem -> Rules () hiRule (Package name path _) (stage, dist, settings) = - let buildDir = toStandard $ path dist "build" + let buildDir = path dist "build" in (buildDir "*hi") %> \out -> do - let way = detectWay $ tail $ takeExtension out + let way = detectWay $ tail $ takeExtension out oFile = out -<.> osuf way need [oFile] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index fc9f4af..e428371 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -6,7 +6,7 @@ import Package.Base buildPackageDependencies :: Package -> TodoItem -> Rules () buildPackageDependencies (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" - pkgData = toStandard $ path dist "package-data.mk" + pkgData = path dist "package-data.mk" in (buildDir name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] diff --git a/src/Package/Library.hs b/src/Package/Library.hs index ec2b845..043977a 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -7,7 +7,6 @@ import Data.List.Split arRule :: Package -> TodoItem -> Rules () arRule (Package _ path _) (stage, dist, _) = let buildDir = path dist "build" - pkgData = path dist "package-data.mk" in (buildDir "*a") %> \out -> do let way = detectWay $ tail $ takeExtension out @@ -16,6 +15,8 @@ arRule (Package _ path _) (stage, dist, _) = need depObjs libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] + -- Splitting argument list into chunks as otherwise Ar chokes up + -- TODO: use simpler list notation for passing arguments forM_ (chunksOf 100 libObjs) $ \os -> do terseRun Ar $ "q" <+> toStandard out <+> os From git at git.haskell.org Thu Oct 26 23:51:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refinements. (59a30fe) Message-ID: <20171026235158.327F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59a30fe3270816ca27f514a3432e941538d7dcdc/ghc >--------------------------------------------------------------- commit 59a30fe3270816ca27f514a3432e941538d7dcdc Author: Moritz Angermann Date: Thu Jan 14 14:19:23 2016 +0800 Refinements. >--------------------------------------------------------------- 59a30fe3270816ca27f514a3432e941538d7dcdc src/Main.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 6ec93429..14f3554 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -41,14 +41,15 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True - , shakeOutput = const showMsg + , shakeOutput = const putMsg } -showMsg :: String -> IO () -showMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg -showMsg msg | dropEscSequence msg == "" = return () -showMsg msg = BS.putStrLn . UTF8.fromString $ msg +-- | Dynamic switch for @putStr@ and @putStrLn@ depending on the @msg at . +putMsg :: String -> IO () +putMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg +putMsg msg = BS.putStrLn . UTF8.fromString $ msg +-- | Drops ANSI Escape sequences from a string. dropEscSequence :: String -> String dropEscSequence = go where From git at git.haskell.org Thu Oct 26 23:51:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:51:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Rules for IntegerGmp (94f5e79) Message-ID: <20171026235159.298603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/94f5e79a5947dca7fa4719f79f8892fa18d88f33/ghc >--------------------------------------------------------------- commit 94f5e79a5947dca7fa4719f79f8892fa18d88f33 Author: Moritz Angermann Date: Sun Jan 3 18:48:04 2016 +0800 Adds Rules for IntegerGmp This should fix #71. We build the integer-gmp library similary to libffi now. >--------------------------------------------------------------- 94f5e79a5947dca7fa4719f79f8892fa18d88f33 shaking-up-ghc.cabal | 1 + src/Main.hs | 2 + src/Rules/IntegerGmp.hs | 112 ++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 115 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 3f91f30..334cd59 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -49,6 +49,7 @@ executable ghc-shake , Rules.Generators.GhcPlatformH , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs + , Rules.IntegerGmp , Rules.Libffi , Rules.Library , Rules.Oracles diff --git a/src/Main.hs b/src/Main.hs index 82f0072..043e173 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -5,6 +5,7 @@ import Rules.Config import Rules.Generate import Rules.Copy import Rules.Libffi +import Rules.IntegerGmp import Rules.Oracles main :: IO () @@ -15,6 +16,7 @@ main = shakeArgs options $ do generateTargets -- see Rules generateRules -- see Rules.Generate libffiRules -- see Rules.Libffi + integerGmpRules -- see Rules.IntegerGmp oracleRules -- see Rules.Oracles packageRules -- see Rules where diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs new file mode 100644 index 0000000..443b912 --- /dev/null +++ b/src/Rules/IntegerGmp.hs @@ -0,0 +1,112 @@ +module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where + +import System.Directory + +import Base +import Expression +import GHC +import Oracles.Config.Setting +import Rules.Actions + +integerGmpBase :: FilePath +integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp" + +integerGmpBuild :: FilePath +integerGmpBuild = integerGmpBase -/- "gmpbuild" + +integerGmpLibrary :: FilePath +integerGmpLibrary = integerGmpBase -/- "libgmp.a" + +-- relative to integerGmpBuild +integerGmpPatch :: FilePath +integerGmpPatch = ".." -/- "tarball" -/- "gmp-5.0.4.patch" + +target :: PartialTarget +target = PartialTarget Stage0 integerGmp + +-- TODO: See Libffi.hs about removing code duplication. +configureEnvironment :: Action [CmdOption] +configureEnvironment = do + sequence [ builderEnv "CC" $ Gcc Stage1 + , builderEnv "CXX" $ Gcc Stage1 + , builderEnv "AR" Ar + , builderEnv "NM" Nm] + where + builderEnv var builder = do + needBuilder False builder + path <- builderPath builder + return $ AddEnv var path + +configureArguments :: Action [String] +configureArguments = do + hostPlatform <- setting HostPlatform + buildPlatform <- setting BuildPlatform + return [ "--enable-shared=no" + , "--host=" ++ hostPlatform + , "--build=" ++ buildPlatform] + +-- TODO: we rebuild integer-gmp every time. +integerGmpRules :: Rules () +integerGmpRules = do + integerGmpLibrary %> \_ -> do + need [sourcePath -/- "Rules" -/- "integerGmp.hs"] + + -- remove the old build folder, if it exists. + liftIO $ removeFiles integerGmpBuild ["//*"] + + -- unpack the gmp tarball. + -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is + -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. + -- That's because the doc/ directory contents are under the GFDL, + -- which causes problems for Debian. + tarballs <- getDirectoryFiles "" [integerGmpBase -/- "tarball/gmp*.tar.bz2"] + when (length tarballs /= 1) $ + putError $ "integerGmpRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + let filename = dropExtension . dropExtension . takeFileName $ head tarballs + let suffix = "-nodoc-patched" + unless (suffix `isSuffixOf` filename) $ + putError $ "integerGmpRules: expected suffix " ++ suffix + ++ " (found: " ++ filename ++ ")." + let libname = take (length filename - length suffix) filename + + need tarballs + build $ fullTarget target Tar tarballs [integerGmpBase] + + -- move gmp- to gmpbuild + let integerGmpExtracted = integerGmpBase -/- libname + liftIO $ renameDirectory integerGmpExtracted integerGmpBuild + putBuild $ "| Move " ++ integerGmpExtracted ++ " -> " ++ integerGmpBuild + + -- apply patches + -- TODO: replace "patch" with PATCH_CMD + unit $ cmd Shell [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch" + unit $ cmd Shell [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch] + putBuild $ "| Applied gmpsrc.patch and " ++ takeFileName integerGmpPatch + + -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? + + -- ./configure + putBuild "| Running libffi configure..." + envs <- configureEnvironment + args <- configureArguments + unit $ cmd Shell [Cwd integerGmpBuild] "bash configure" envs args + + -- make + putBuild "| Running make..." + unit $ cmd Shell "make" ["-C", integerGmpBuild, "MAKEFLAGS="] + + -- copy library and header + forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> do + let file' = integerGmpBase -/- takeFileName file + copyFileChanged (integerGmpBuild -/- file) file' + putBuild $ "| Copy " ++ file ++ " -> " ++ file' + + -- TODO: do we need these as well? + -- mkdir integerGmpBase -/- objs + -- unit $ cmd Shell [Cwd integerGmpBase -/- "objs"] "$AR_STAGE1 x ../libgmp.a" + -- $RANLIB_CMD integerGmpBase -/- "libgmp.a" + + putSuccess "| Successfully build custom library 'integer-gmp'" + + "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary] From git at git.haskell.org Thu Oct 26 23:52:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use multiple output rules for *.o and *.hi files. (6ce7cd3) Message-ID: <20171026235201.C3E0B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6ce7cd3ac8b3ba4ef0228dec9c8d4741f746a873/ghc >--------------------------------------------------------------- commit 6ce7cd3ac8b3ba4ef0228dec9c8d4741f746a873 Author: Andrey Mokhov Date: Wed Jan 14 03:58:59 2015 +0000 Use multiple output rules for *.o and *.hi files. >--------------------------------------------------------------- 6ce7cd3ac8b3ba4ef0228dec9c8d4741f746a873 src/Package/Compile.hs | 24 ++++++------------------ 1 file changed, 6 insertions(+), 18 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index d701af6..cd91c8e 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -29,13 +29,13 @@ suffixArgs way = arg ["-hisuf", hisuf way] <> arg [ "-osuf", osuf way] <> arg ["-hcsuf", hcsuf way] -oRule :: Package -> TodoItem -> Rules () -oRule (Package name path _) (stage, dist, settings) = +buildPackageCompile :: Package -> TodoItem -> Rules () +buildPackageCompile (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" pkgData = path dist "package-data.mk" - depFile = buildDir name <.> "m" + depFile = buildDir takeBaseName name <.> "m" in - (buildDir "*o") %> \out -> do + [buildDir "*o", buildDir "*hi"] &%> \[out, _] -> do let way = detectWay $ tail $ takeExtension out need ["shake/src/Package/Compile.hs"] need [depFile] @@ -49,23 +49,11 @@ oRule (Package name path _) (stage, dist, settings) = <> packageArgs stage pkgData <> includeArgs path dist <> concatArgs ["-optP"] (CppOpts pkgData) - -- TODO: use HC_OPTS from pkgData + <> arg (HsOpts pkgData) -- TODO: now we have both -O and -O2 - <> arg ["-Wall", "-XHaskell2010", "-O2"] + -- <> arg ["-O2"] <> productArgs ["-odir", "-hidir", "-stubdir"] buildDir <> when (splitObjects stage) (arg "-split-objs") <> arg ("-c":srcs) <> arg ["-o", toStandard out] --- TODO: This rule looks hacky... combine it with the above? -hiRule :: Package -> TodoItem -> Rules () -hiRule (Package name path _) (stage, dist, settings) = - let buildDir = path dist "build" - in - (buildDir "*hi") %> \out -> do - let way = detectWay $ tail $ takeExtension out - oFile = out -<.> osuf way - need [oFile] - -buildPackageCompile :: Package -> TodoItem -> Rules () -buildPackageCompile = oRule <> hiRule From git at git.haskell.org Thu Oct 26 23:52:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #168 from kgardas/fix_gmp_args (dc90c3c) Message-ID: <20171026235202.736B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dc90c3ce5301a08b3d149d551580cf88e7221e5c/ghc >--------------------------------------------------------------- commit dc90c3ce5301a08b3d149d551580cf88e7221e5c Merge: 6934485 86a3fe5 Author: Andrey Mokhov Date: Thu Jan 14 12:32:46 2016 +0000 Merge pull request #168 from kgardas/fix_gmp_args fix handling of --with-gmp-* configure arguments [skip ci] >--------------------------------------------------------------- dc90c3ce5301a08b3d149d551580cf88e7221e5c src/Rules/Gmp.hs | 32 +++++++++++++++++++++----------- 1 file changed, 21 insertions(+), 11 deletions(-) From git at git.haskell.org Thu Oct 26 23:52:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #78 from angerman/feature/dependencies (a4893ad) Message-ID: <20171026235203.196B73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4893ad7be1b199ba407fa74b53c49f15eb152cf/ghc >--------------------------------------------------------------- commit a4893ad7be1b199ba407fa74b53c49f15eb152cf Merge: 9be3f7e 25b2408 Author: Andrey Mokhov Date: Sun Jan 3 12:11:40 2016 +0000 Merge pull request #78 from angerman/feature/dependencies Feature/dependencies >--------------------------------------------------------------- a4893ad7be1b199ba407fa74b53c49f15eb152cf src/Rules/Data.hs | 4 +++- src/Rules/Generate.hs | 3 +++ 2 files changed, 6 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:52:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add package data key HsOpts. (1a3f43b) Message-ID: <20171026235205.451E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a3f43b55d543e784762cf8f0e9bf40e15820703/ghc >--------------------------------------------------------------- commit 1a3f43b55d543e784762cf8f0e9bf40e15820703 Author: Andrey Mokhov Date: Wed Jan 14 04:00:39 2015 +0000 Add package data key HsOpts. >--------------------------------------------------------------- 1a3f43b55d543e784762cf8f0e9bf40e15820703 src/Oracles/PackageData.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index bf94713..854fb8c 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -20,6 +20,7 @@ data PackageData = Modules FilePath | DepKeys FilePath | Synopsis FilePath | CppOpts FilePath + | HsOpts FilePath instance ShowArgs PackageData where showArgs packageData = do @@ -32,8 +33,10 @@ instance ShowArgs PackageData where DepKeys file -> ("DEP_KEYS" , file, "" ) Synopsis file -> ("SYNOPSIS" , file, "" ) CppOpts file -> ("CPP_OPTS" , file, "" ) + HsOpts file -> ("HC_OPTS" , file, "" ) fullKey = replaceSeparators '_' $ takeDirectory file ++ "_" ++ key - res <- askOracle $ PackageDataKey (file, fullKey) + file' = toStandard $ normaliseEx file + res <- askOracle $ PackageDataKey (file', fullKey) return $ words $ case res of Nothing -> error $ "No key '" ++ key ++ "' in " ++ file ++ "." Just "" -> defaultValue From git at git.haskell.org Thu Oct 26 23:52:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use doesDirectoryExist to workaround a getDirectoryContents bug. (34c999b) Message-ID: <20171026235206.27A703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34c999b8e9d78b848ef75f8b439b408eafdf7166/ghc >--------------------------------------------------------------- commit 34c999b8e9d78b848ef75f8b439b408eafdf7166 Author: Andrey Mokhov Date: Thu Jan 14 13:01:48 2016 +0000 Use doesDirectoryExist to workaround a getDirectoryContents bug. See #168. >--------------------------------------------------------------- 34c999b8e9d78b848ef75f8b439b408eafdf7166 src/Rules/Gmp.hs | 4 +--- src/Rules/Library.hs | 5 ++++- 2 files changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index f6d6fe8..c788ed2 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -118,10 +118,8 @@ gmpRules = do createDirectory $ takeDirectory gmpLibraryH -- check whether we need to build in tree gmp - -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` configMk <- liftIO . readFile $ gmpBase -/- "config.mk" - if "HaveFrameworkGMP = YES" `isInfixOf` configMk - || "HaveLibGmp = YES" `isInfixOf` configMk + if any (`isInfixOf` configMk) ["HaveFrameworkGMP = YES", "HaveLibGmp = YES"] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 6b2180c..0ffaf3f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -84,5 +84,8 @@ extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? - getDirectoryFiles "" [gmpObjects -/- "*.o"] + exists <- doesDirectoryExist gmpObjects + if exists + then getDirectoryFiles "" [gmpObjects -/- "*.o"] + else return [] | otherwise = return [] From git at git.haskell.org Thu Oct 26 23:52:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #79 from angerman/feature/integer-gmp (ee639c7) Message-ID: <20171026235206.B94003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee639c7de4ae1861255953daa8f7b65d4a374c1f/ghc >--------------------------------------------------------------- commit ee639c7de4ae1861255953daa8f7b65d4a374c1f Merge: a4893ad 94f5e79 Author: Andrey Mokhov Date: Sun Jan 3 12:13:05 2016 +0000 Merge pull request #79 from angerman/feature/integer-gmp Adds Rules for IntegerGmp >--------------------------------------------------------------- ee639c7de4ae1861255953daa8f7b65d4a374c1f shaking-up-ghc.cabal | 1 + src/Main.hs | 2 + src/Rules/IntegerGmp.hs | 112 ++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 115 insertions(+) From git at git.haskell.org Thu Oct 26 23:52:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Cabal/Cabal to list of packages. (8bdefdd) Message-ID: <20171026235208.BC5D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8bdefdd7cbb9cd1c558d7f01f05a79ec4ff25a6e/ghc >--------------------------------------------------------------- commit 8bdefdd7cbb9cd1c558d7f01f05a79ec4ff25a6e Author: Andrey Mokhov Date: Wed Jan 14 04:01:55 2015 +0000 Add Cabal/Cabal to list of packages. >--------------------------------------------------------------- 8bdefdd7cbb9cd1c558d7f01f05a79ec4ff25a6e src/Package.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index e815c4b..5d16d22 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -13,7 +13,8 @@ packages :: [Package] packages = [libraryPackage "array" Stage1 defaultSettings, libraryPackage "bin-package-db" Stage1 defaultSettings, libraryPackage "binary" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings] + libraryPackage "deepseq" Stage1 defaultSettings, + libraryPackage "Cabal/Cabal" Stage1 defaultSettings] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () @@ -28,7 +29,8 @@ packageRules = do forM_ packages $ \pkg @ (Package name path todo) -> do forM_ todo $ \todoItem @ (stage, dist, settings) -> do - -- Want top .o and .a files for the pkg/todo combo: + -- Want top .o and .a files for the pkg/todo combo + -- TODO: Check BUILD_GHCI_LIB flag to decide if .o is needed action $ do let buildDir = path dist "build" pkgData = path dist "package-data.mk" From git at git.haskell.org Thu Oct 26 23:52:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use system GMP on Windows. (ff0194b) Message-ID: <20171026235209.A0ECD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff0194b7a49cd554065fc68e209e1188be133bff/ghc >--------------------------------------------------------------- commit ff0194b7a49cd554065fc68e209e1188be133bff Author: Andrey Mokhov Date: Thu Jan 14 13:22:16 2016 +0000 Don't use system GMP on Windows. See #168. >--------------------------------------------------------------- ff0194b7a49cd554065fc68e209e1188be133bff src/Rules/Gmp.hs | 6 ++++-- src/Rules/Library.hs | 1 + 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index c788ed2..069dd28 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -117,9 +117,11 @@ gmpRules = do runConfigure (pkgPath integerGmp) envs intGmpArgs createDirectory $ takeDirectory gmpLibraryH - -- check whether we need to build in tree gmp + -- We don't use system GMP on Windows. TODO: fix? + windows <- windowsHost configMk <- liftIO . readFile $ gmpBase -/- "config.mk" - if any (`isInfixOf` configMk) ["HaveFrameworkGMP = YES", "HaveLibGmp = YES"] + if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES" + , "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 0ffaf3f..b53c472 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -84,6 +84,7 @@ extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? + -- FIXME: simplify after Shake's getDirectoryFiles bug is fixed, #168 exists <- doesDirectoryExist gmpObjects if exists then getDirectoryFiles "" [gmpObjects -/- "*.o"] From git at git.haskell.org Thu Oct 26 23:52:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds integer gmp path to the Gcc builder. (8cea200) Message-ID: <20171026235210.494433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8cea2007b3449adb88c35cbdbeaf2407b658c4ae/ghc >--------------------------------------------------------------- commit 8cea2007b3449adb88c35cbdbeaf2407b658c4ae Author: Moritz Angermann Date: Sun Jan 3 20:56:24 2016 +0800 Adds integer gmp path to the Gcc builder. This fixes the isse mentioned in #79, where `gmp.h` could not be found. >--------------------------------------------------------------- 8cea2007b3449adb88c35cbdbeaf2407b658c4ae src/Settings/Packages/IntegerGmp.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 1c8ed13..6d1b2b6 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -3,7 +3,7 @@ module Settings.Packages.IntegerGmp (integerGmpPackageArgs) where import Base import Expression import GHC (integerGmp) -import Predicates (builder, package) +import Predicates (builder, builderGcc, package) -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" @@ -11,9 +11,12 @@ import Predicates (builder, package) -- endif integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? - builder GhcCabal ? mconcat - [ arg "--configure-option=--with-intree-gmp" - , appendSub "--configure-option=CFLAGS" includeGmp - , appendSub "--gcc-options" includeGmp ] + mconcat + [ builder GhcCabal ? mconcat + [ arg "--configure-option=--with-intree-gmp" + , appendSub "--configure-option=CFLAGS" includeGmp + , appendSub "--gcc-options" includeGmp ] + , builderGcc ? ( arg $ "-I" ++ pkgPath integerGmp -/- "gmp" ) + ] where includeGmp = ["-I" ++ pkgPath integerGmp -/- "gmp"] From git at git.haskell.org Thu Oct 26 23:52:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix file names for package names with slashes (e.g. Cabal/Cabal). (f124e23) Message-ID: <20171026235212.82D133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f124e23635f6fa05edc945e4b0200acc0e57d8c2/ghc >--------------------------------------------------------------- commit f124e23635f6fa05edc945e4b0200acc0e57d8c2 Author: Andrey Mokhov Date: Wed Jan 14 04:02:44 2015 +0000 Fix file names for package names with slashes (e.g. Cabal/Cabal). >--------------------------------------------------------------- f124e23635f6fa05edc945e4b0200acc0e57d8c2 src/Package/Data.hs | 3 ++- src/Package/Dependencies.hs | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index d3b13a5..c5d3bd2 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -59,6 +59,7 @@ buildPackageData :: Package -> TodoItem -> Rules () buildPackageData (Package name path _) (stage, dist, settings) = let pathDist = path dist configure = path "configure" + cabal = path takeBaseName name <.> "cabal" cabalArgs = arg ["configure", path, dist] -- this is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument @@ -91,7 +92,7 @@ buildPackageData (Package name path _) (stage, dist, settings) = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do need ["shake/src/Package/Data.hs"] - need [path name <.> "cabal"] + need [cabal] when (doesFileExist $ configure <.> "ac") $ need [configure] terseRun GhcCabal cabalArgs when (registerPackage settings) $ terseRun (GhcPkg stage) ghcPkgArgs diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index e428371..1d3a8d2 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -8,7 +8,7 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = let buildDir = toStandard $ path dist "build" pkgData = path dist "package-data.mk" in - (buildDir name <.> "m") %> \out -> do + (buildDir takeBaseName name <.> "m") %> \out -> do need ["shake/src/Package/Dependencies.hs"] terseRun (Ghc stage) $ arg "-M" <> packageArgs stage pkgData From git at git.haskell.org Thu Oct 26 23:52:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting in renderAction. (14e5009) Message-ID: <20171026235213.C08C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14e50095ba46d4ab28cffda306008c41b00167e7/ghc >--------------------------------------------------------------- commit 14e50095ba46d4ab28cffda306008c41b00167e7 Author: Andrey Mokhov Date: Thu Jan 14 14:19:54 2016 +0000 Fix formatting in renderAction. [skip ci] >--------------------------------------------------------------- 14e50095ba46d4ab28cffda306008c41b00167e7 src/Base.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index be3ff1b..27fe5c1 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -145,12 +145,12 @@ putError msg = do renderAction :: String -> String -> String -> String renderAction what input output = case buildInfo of Normal -> renderBox [ what - , " input:" ++ input - , " => output:" ++ output ] + , " input: " ++ input + , " => output: " ++ output ] Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output Pony -> renderPony [ what - , " input:" ++ input - , " => output:" ++ output ] + , " input: " ++ input + , " => output: " ++ output ] Dot -> "." None -> "" From git at git.haskell.org Thu Oct 26 23:52:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #80 from angerman/feature/integerGmpIncludePath (80d3477) Message-ID: <20171026235214.623C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/80d34775cae65bfa0fbd26942a99cd546bcadfa0/ghc >--------------------------------------------------------------- commit 80d34775cae65bfa0fbd26942a99cd546bcadfa0 Merge: ee639c7 8cea200 Author: Andrey Mokhov Date: Sun Jan 3 13:17:44 2016 +0000 Merge pull request #80 from angerman/feature/integerGmpIncludePath Adds integer gmp path to the Gcc builder. >--------------------------------------------------------------- 80d34775cae65bfa0fbd26942a99cd546bcadfa0 src/Settings/Packages/IntegerGmp.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) From git at git.haskell.org Thu Oct 26 23:52:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (f80948c) Message-ID: <20171026235216.531653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f80948c6655e0c6bf2ba6a10e09647b78e5ee1ab/ghc >--------------------------------------------------------------- commit f80948c6655e0c6bf2ba6a10e09647b78e5ee1ab Author: Andrey Mokhov Date: Wed Jan 14 04:02:49 2015 +0000 Clean up. >--------------------------------------------------------------- f80948c6655e0c6bf2ba6a10e09647b78e5ee1ab src/Oracles/Builder.hs | 8 +++----- src/Package/Base.hs | 11 +++++------ 2 files changed, 8 insertions(+), 11 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 5c9d64b..0fce046 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -107,13 +107,11 @@ run builder args = do -- Raises an error if the builder is not uniquely specified in config files terseRun :: Builder -> Args -> Action () terseRun builder args = do - needBuilder builder - [exe] <- showArgs builder args' <- args - putNormal $ "|--------\n| Running " ++ show builder ++ " with arguments:" + putNormal $ "/--------\n| Running " ++ show builder ++ " with arguments:" mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args' - putNormal "|--------" - quietly $ cmd [exe] args' + putNormal "\\--------" + quietly $ run builder args interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of diff --git a/src/Package/Base.hs b/src/Package/Base.hs index bac6801..9cf8fc8 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -65,13 +65,12 @@ commonLdArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? commonCppArgs :: Args commonCppArgs = mempty -- TODO: Why empty? Perhaps drop it altogether? --- TODO: simplify commonCcWarninigArgs :: Args -commonCcWarninigArgs = when Validating $ - GccIsClang arg "-Wno-unknown-pragmas" - <> (not GccIsClang && not GccLt46) arg "-Wno-error=inline" - <> (GccIsClang && not GccLt46 && windowsHost) - arg "-Werror=unused-but-set-variable" +commonCcWarninigArgs = when Validating $ arg + [ when GccIsClang $ arg "-Wno-unknown-pragmas" + , when (not GccIsClang && not GccLt46) $ arg "-Wno-error=inline" + , when (GccIsClang && not GccLt46 && windowsHost) $ + arg "-Werror=unused-but-set-variable" ] bootPkgConstraints :: Args bootPkgConstraints = mempty From git at git.haskell.org Thu Oct 26 23:52:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Print out system.config when running CI. (e094834) Message-ID: <20171026235218.EDD5F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e094834509c6280ea2d049fea51e1a129ccac2ae/ghc >--------------------------------------------------------------- commit e094834509c6280ea2d049fea51e1a129ccac2ae Author: Andrey Mokhov Date: Thu Jan 14 17:53:50 2016 +0000 Print out system.config when running CI. >--------------------------------------------------------------- e094834509c6280ea2d049fea51e1a129ccac2ae .appveyor.yml | 1 + .travis.yml | 1 + 2 files changed, 2 insertions(+) diff --git a/.appveyor.yml b/.appveyor.yml index 68c1fd8..d8854cc 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,6 +30,7 @@ install: - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3d5b11ab21eaee5e7dcdca007acc05131d512be/ghc >--------------------------------------------------------------- commit d3d5b11ab21eaee5e7dcdca007acc05131d512be Author: Moritz Angermann Date: Sun Jan 3 23:01:17 2016 +0800 Split libgmp.a Fixes the issue mentioned in #83 ``` * utils/hpc/stage1/build/tmp/hpc-bin * libraries/integer-gmp/stage1/build/libHSinteger-gmp-1.0.0.0.a * getDirectoryFiles [libraries/integer-gmp/gmp/objs/*.o] libraries/integer-gmp/gmp/objs: getDirectoryContents: does not exist (No such file or directory) ``` >--------------------------------------------------------------- d3d5b11ab21eaee5e7dcdca007acc05131d512be src/Rules/IntegerGmp.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 443b912..1f50dc0 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -53,6 +53,7 @@ integerGmpRules = do -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] + liftIO $ removeFiles (integerGmpBase -/- "objs") ["//*"] -- unpack the gmp tarball. -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is @@ -102,10 +103,13 @@ integerGmpRules = do copyFileChanged (integerGmpBuild -/- file) file' putBuild $ "| Copy " ++ file ++ " -> " ++ file' - -- TODO: do we need these as well? - -- mkdir integerGmpBase -/- objs - -- unit $ cmd Shell [Cwd integerGmpBase -/- "objs"] "$AR_STAGE1 x ../libgmp.a" - -- $RANLIB_CMD integerGmpBase -/- "libgmp.a" + ar <- builderPath Ar + ran <- builderPath Ranlib + -- unpack libgmp.a + putBuild "| Unpacking libgmp.a..." + unit $ cmd Shell [Cwd integerGmpBase] "mkdir -p objs" + unit $ cmd Shell [Cwd (integerGmpBase -/- "objs")] [ar] " x ../libgmp.a" + unit $ cmd Shell [Cwd integerGmpBase] [ran] " libgmp.a" putSuccess "| Successfully build custom library 'integer-gmp'" From git at git.haskell.org Thu Oct 26 23:52:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add chunksOfSize helper function. (797df55) Message-ID: <20171026235220.1B3083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/797df55a99ffbe2fe94bae5dc202444b294ae2d0/ghc >--------------------------------------------------------------- commit 797df55a99ffbe2fe94bae5dc202444b294ae2d0 Author: Andrey Mokhov Date: Thu Jan 15 02:02:28 2015 +0000 Add chunksOfSize helper function. >--------------------------------------------------------------- 797df55a99ffbe2fe94bae5dc202444b294ae2d0 src/Util.hs | 17 ++++++++++++++++- 1 file changed, 16 insertions(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index f91ff79..b1ff9e5 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,7 @@ module Util ( module Data.Char, - replaceIf, replaceEq, replaceSeparators + replaceIf, replaceEq, replaceSeparators, + chunksOfSize ) where import Base @@ -15,3 +16,17 @@ replaceEq from = replaceIf (== from) replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator +-- (chunksOfSize size ss) splits a list of strings 'ss' into chunks not +-- exceeding the given 'size'. +chunksOfSize :: Int -> [String] -> [[String]] +chunksOfSize _ [] = [] +chunksOfSize size ss = reverse chunk : chunksOfSize size rest + where + (chunk, rest) = go [] 0 ss + go chunk _ [] = (chunk, []) + go chunk chunkSize (s:ss) = let newSize = chunkSize + length s + (newChunk, rest) = go (s:chunk) newSize ss + in + if newSize > size + then (chunk , s:ss) + else (newChunk, rest) From git at git.haskell.org Thu Oct 26 23:52:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix comments. (f792789) Message-ID: <20171026235222.A50B33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f79278948b635567c1b0830a9539b97551db8dd5/ghc >--------------------------------------------------------------- commit f79278948b635567c1b0830a9539b97551db8dd5 Author: Andrey Mokhov Date: Thu Jan 14 17:59:21 2016 +0000 Fix comments. [skip ci] >--------------------------------------------------------------- f79278948b635567c1b0830a9539b97551db8dd5 cfg/system.config.in | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 498f78c..8b5b553 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -1,5 +1,6 @@ -# Edit 'user.config' to override these settings. -#=============================================== +# This file is processed by the configure script +# See 'Settings/User.hs' for user-defined settings +#================================================= # Paths to builders: #=================== From git at git.haskell.org Thu Oct 26 23:52:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #85 from angerman/feature/fix-integer-gmp (d271649) Message-ID: <20171026235223.694503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d27164938eff42d2622d416d5f81d7dd0833a32f/ghc >--------------------------------------------------------------- commit d27164938eff42d2622d416d5f81d7dd0833a32f Merge: 80d3477 d3d5b11 Author: Andrey Mokhov Date: Sun Jan 3 15:09:45 2016 +0000 Merge pull request #85 from angerman/feature/fix-integer-gmp Split libgmp.a >--------------------------------------------------------------- d27164938eff42d2622d416d5f81d7dd0833a32f src/Rules/IntegerGmp.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) From git at git.haskell.org Thu Oct 26 23:52:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add packages: containers, filepath, hoopl, hpc, parallel, pretty, stm, template-haskell, transformers. (d52b4c9) Message-ID: <20171026235223.A88F43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d52b4c94f317bfe4e631432b97a6f23d30dbf14a/ghc >--------------------------------------------------------------- commit d52b4c94f317bfe4e631432b97a6f23d30dbf14a Author: Andrey Mokhov Date: Thu Jan 15 02:03:22 2015 +0000 Add packages: containers, filepath, hoopl, hpc, parallel, pretty, stm, template-haskell, transformers. >--------------------------------------------------------------- d52b4c94f317bfe4e631432b97a6f23d30dbf14a src/Package.hs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 5d16d22..b8de413 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -10,11 +10,20 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] -packages = [libraryPackage "array" Stage1 defaultSettings, - libraryPackage "bin-package-db" Stage1 defaultSettings, - libraryPackage "binary" Stage1 defaultSettings, - libraryPackage "deepseq" Stage1 defaultSettings, - libraryPackage "Cabal/Cabal" Stage1 defaultSettings] +packages = [ libraryPackage "array" Stage1 defaultSettings + , libraryPackage "bin-package-db" Stage1 defaultSettings + , libraryPackage "binary" Stage1 defaultSettings + , libraryPackage "deepseq" Stage1 defaultSettings + , libraryPackage "Cabal/Cabal" Stage1 defaultSettings + , libraryPackage "containers" Stage1 defaultSettings + , libraryPackage "filepath" Stage1 defaultSettings + , libraryPackage "hoopl" Stage1 defaultSettings + , libraryPackage "hpc" Stage1 defaultSettings + , libraryPackage "parallel" Stage1 defaultSettings + , libraryPackage "pretty" Stage1 defaultSettings + , libraryPackage "stm" Stage1 defaultSettings + , libraryPackage "template-haskell" Stage1 defaultSettings + , libraryPackage "transformers" Stage1 defaultSettings ] -- Rule buildPackageX is defined in module Package.X buildPackage :: Package -> TodoItem -> Rules () From git at git.haskell.org Thu Oct 26 23:52:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Detect the right patch command and use it when building gmp. (79cf2e3) Message-ID: <20171026235226.3546D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79cf2e3d1f5d48ff731060f4c0f17cd7e8310514/ghc >--------------------------------------------------------------- commit 79cf2e3d1f5d48ff731060f4c0f17cd7e8310514 Author: Andrey Mokhov Date: Thu Jan 14 23:41:31 2016 +0000 Detect the right patch command and use it when building gmp. See #158. >--------------------------------------------------------------- 79cf2e3d1f5d48ff731060f4c0f17cd7e8310514 cfg/system.config.in | 5 +++-- src/Builder.hs | 2 ++ src/Rules/Actions.hs | 11 ++++++++++- src/Rules/Gmp.hs | 6 +----- 4 files changed, 16 insertions(+), 8 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 8b5b553..4539979 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -1,6 +1,6 @@ # This file is processed by the configure script -# See 'Settings/User.hs' for user-defined settings -#================================================= +# See 'src/Settings/User.hs' for user-defined settings +#===================================================== # Paths to builders: #=================== @@ -40,6 +40,7 @@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ tar = @TarCmd@ +patch = @PatchCmd@ perl = @PerlCmd@ # Information about builders: diff --git a/src/Builder.hs b/src/Builder.hs index efc3216..353c00f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -40,6 +40,7 @@ data Builder = Alex | Ld | Nm | Objdump + | Patch | Perl | Ranlib | Tar @@ -82,6 +83,7 @@ builderKey builder = case builder of Ld -> "ld" Nm -> "nm" Objdump -> "objdump" + Patch -> "patch" Perl -> "perl" Ranlib -> "ranlib" Tar -> "tar" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index eb37630..7692c86 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,7 +1,7 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, moveDirectory, - fixFile, runConfigure, runMake, runBuilder, makeExecutable + fixFile, runConfigure, runMake, applyPatch, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -108,6 +108,15 @@ runMake dir args = do putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) makeCommand ["-C", dir] args +applyPatch :: FilePath -> FilePath -> Action () +applyPatch dir patch = do + let file = dir -/- patch + need [file] + needBuilder False Patch + path <- builderPath Patch + putBuild $ "| Apply patch " ++ file + quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] + runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do needBuilder laxDependencies builder diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 069dd28..eb1158e 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -73,7 +73,6 @@ gmpRules = do gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - -- Do we need this step? liftIO $ removeFiles gmpBuildPath ["//*"] -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is @@ -86,17 +85,14 @@ gmpRules = do ++ "(found: " ++ show tarballs ++ ")." need tarballs - createDirectory gmpBuildPath build $ fullTarget gmpTarget Tar tarballs [gmpBuildPath] - -- TODO: replace "patch" with PATCH_CMD forM_ gmpPatches $ \src -> do let patch = takeFileName src patchPath = gmpBuildPath -/- patch copyFile src patchPath - putBuild $ "| Apply " ++ patchPath - unit . quietly $ cmd Shell (EchoStdout False) [Cwd gmpBuildPath] "patch -p0 <" [patch] + applyPatch gmpBuildPath patch -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? From git at git.haskell.org Thu Oct 26 23:52:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for both *.gz and *.bz2 archives, see #79. (fd3a1f8) Message-ID: <20171026235227.5301F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd3a1f89719fb551ed3f6579ef978ab304abe66c/ghc >--------------------------------------------------------------- commit fd3a1f89719fb551ed3f6579ef978ab304abe66c Author: Andrey Mokhov Date: Sun Jan 3 18:16:59 2016 +0000 Add support for both *.gz and *.bz2 archives, see #79. >--------------------------------------------------------------- fd3a1f89719fb551ed3f6579ef978ab304abe66c src/Settings/Builders/Tar.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/Tar.hs b/src/Settings/Builders/Tar.hs index 1f9f0ba..f59b1cf 100644 --- a/src/Settings/Builders/Tar.hs +++ b/src/Settings/Builders/Tar.hs @@ -1,10 +1,14 @@ module Settings.Builders.Tar (tarBuilderArgs) where +import Base import Expression import Predicates (builder) tarBuilderArgs :: Args tarBuilderArgs = builder Tar ? do - mconcat [ arg "-xzf" - , arg =<< getInput + input <- getInput + mconcat [ arg "-xf" + , ("*.gz" ?== input) ? arg "--gzip" + , ("*.bz2" ?== input) ? arg "--bzip2" + , arg input , arg "-C", arg =<< getOutput ] From git at git.haskell.org Thu Oct 26 23:52:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add argSizeLimit function (mainly for Ar builder). (cff887e) Message-ID: <20171026235227.893913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cff887e3d3e30b187542580e8f5c4671bbe126b9/ghc >--------------------------------------------------------------- commit cff887e3d3e30b187542580e8f5c4671bbe126b9 Author: Andrey Mokhov Date: Thu Jan 15 02:05:05 2015 +0000 Add argSizeLimit function (mainly for Ar builder). >--------------------------------------------------------------- cff887e3d3e30b187542580e8f5c4671bbe126b9 src/Package/Base.hs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 9cf8fc8..a1eab2c 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -9,7 +9,8 @@ module Package.Base ( commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, bootPkgConstraints, pathArgs, packageArgs, includeArgs, pkgHsSources, - pkgDepObjects, pkgLibObjects + pkgDepObjects, pkgLibObjects, + argSizeLimit ) where import Base @@ -147,3 +148,14 @@ findModuleFiles pkgData directories suffixes = do suffix <- suffixes return $ dir modPath ++ suffix return $ map (toStandard . normaliseEx) files + +-- The argument list has a limited size on Windows. Since Windows 7 the limit +-- is 32768 (theoretically). In practice we use 31000 to leave some breathing +-- space for the builder's path & name, auxiliary flags, and other overheads. +-- Use this function to set limits for other operating systems if necessary. +argSizeLimit :: Action Int +argSizeLimit = do + windows <- windowsHost + return $ if windows + then 31000 + else 1048576 -- surely, 1MB should be enough? From git at git.haskell.org Thu Oct 26 23:52:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Determine system GMP library name and pass it via -optl. (2024396) Message-ID: <20171026235230.1D1423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20243965783cfb5ba75096ebe375517d63cf37c8/ghc >--------------------------------------------------------------- commit 20243965783cfb5ba75096ebe375517d63cf37c8 Author: Andrey Mokhov Date: Fri Jan 15 01:11:36 2016 +0000 Determine system GMP library name and pass it via -optl. See #173. >--------------------------------------------------------------- 20243965783cfb5ba75096ebe375517d63cf37c8 src/Rules/Gmp.hs | 113 +++++++++++++++++++++++-------------------- src/Settings/Builders/Ghc.hs | 11 ++++- 2 files changed, 69 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 20243965783cfb5ba75096ebe375517d63cf37c8 From git at git.haskell.org Thu Oct 26 23:52:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor our common build actions into src/Rules/Actions.hs (498939a) Message-ID: <20171026235231.314643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/498939a9b2942c4d95cc59b45721579a59a36f97/ghc >--------------------------------------------------------------- commit 498939a9b2942c4d95cc59b45721579a59a36f97 Author: Andrey Mokhov Date: Mon Jan 4 01:32:11 2016 +0000 Factor our common build actions into src/Rules/Actions.hs >--------------------------------------------------------------- 498939a9b2942c4d95cc59b45721579a59a36f97 src/Base.hs | 2 +- src/Rules/Actions.hs | 72 ++++++++++++++++++++++++++++++++++++++++++++++++---- src/Rules/Copy.hs | 11 +++----- src/Rules/Data.hs | 11 ++++---- src/Rules/Program.hs | 2 +- 5 files changed, 77 insertions(+), 21 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index acbd3c3..8733282 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -175,7 +175,7 @@ putError msg = do -- | Render the given set of lines in a ASCII box renderBox :: [String] -> String renderBox ls = - unlines $ [begin] ++ map (bar++) ls ++ [end] + unlines ([begin] ++ map (bar++) ls) ++ end where (begin,bar,end) | useUnicode = ( "╭──────────" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index e930b52..2a4fc80 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,9 +1,15 @@ {-# LANGUAGE RecordWildCards #-} -module Rules.Actions (build, buildWithResources) where +module Rules.Actions ( + build, buildWithResources, copyFile, createDirectory, moveDirectory, + fixFile, runConfigure, runMake, runBuilder + ) where + +import qualified System.Directory as IO import Base import Expression import Oracles.ArgsHash +import Oracles.Config.Setting import Settings import Settings.Args import Settings.Builders.Ar @@ -25,7 +31,14 @@ buildWithResources rs target = do withResources rs $ do unless verbose $ putInfo target quietlyUnlessVerbose $ case builder of - Ar -> arCmd path argList + Ar -> do + output <- interpret target getOutput + if "//*.a" ?== output + then arCmd path argList + else do + input <- interpret target getInput + top <- setting GhcSourcePath + cmd [path] [Cwd output] "x" (top -/- input) HsCpp -> captureStdout target path argList GenApply -> captureStdout target path argList @@ -49,13 +62,62 @@ captureStdout target path argList = do Stdout output <- cmd [path] argList writeFileChanged file output +copyFile :: FilePath -> FilePath -> Action () +copyFile source target = do + putBuild $ renderBox [ "Copy file" + , " input: " ++ source + , "=> output: " ++ target ] + copyFileChanged source target + +createDirectory :: FilePath -> Action () +createDirectory dir = do + putBuild $ "| Create directory " ++ dir + liftIO $ IO.createDirectoryIfMissing True dir + +-- Note, the source directory is untracked +moveDirectory :: FilePath -> FilePath -> Action () +moveDirectory source target = do + putBuild $ renderBox [ "Move directory" + , " input: " ++ source + , "=> output: " ++ target ] + liftIO $ IO.renameDirectory source target + +-- Transform a given file by applying a function to its contents +fixFile :: FilePath -> (String -> String) -> Action () +fixFile file f = do + putBuild $ "| Fix " ++ file + old <- liftIO $ readFile file + let new = f old + length new `seq` liftIO $ writeFile file new + +runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () +runConfigure dir opts args = do + need [dir -/- "configure"] + putBuild $ "| Run configure in " ++ dir ++ "..." + quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args + +runMake :: FilePath -> [String] -> Action () +runMake dir args = do + need [dir -/- "Makefile"] + let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." + quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args + +runBuilder :: Builder -> [String] -> Action () +runBuilder builder args = do + needBuilder laxDependencies builder + path <- builderPath builder + let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + putBuild $ "| Run " ++ show builder ++ note + quietly $ cmd [path] args + -- Print out key information about the command being executed putInfo :: Target.Target -> Action () -putInfo (Target.Target {..}) = putBuild $ renderBox $ - [ "Running " ++ show builder +putInfo (Target.Target {..}) = putBuild $ renderBox + [ "Run " ++ show builder ++ " (" ++ stageInfo ++ "package = " ++ pkgNameString package - ++ wayInfo ++ "):" + ++ wayInfo ++ ")" , " input: " ++ digest inputs , "=> output: " ++ digest outputs ] where diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index 766e865..3a385b8 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -3,6 +3,7 @@ module Rules.Copy (installTargets, copyRules) where import Base import Expression import GHC +import Rules.Actions import Rules.Generate import Rules.Libffi import Settings.TargetDirectory @@ -20,16 +21,10 @@ copyRules = do when (length ffiHPaths /= 1) $ putError $ "copyRules: exactly one ffi.h header expected" ++ "(found: " ++ show ffiHPaths ++ ")." - let ffiHPath = takeDirectory $ head ffiHPaths - copy ffih ffiHPath + copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." where - file <~ dir = file %> \_ -> copy file dir - - copy file dir = do - let source = dir -/- takeFileName file - copyFileChanged source file - putBuild $ "| Copy " ++ source ++ " -> " ++ file + file <~ dir = file %> \_ -> copyFile (dir -/- file) file diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 84ac619..274092b 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -118,10 +118,9 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 -- Reason: Shake's built-in makefile parser doesn't recognise slashes postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - contents <- fmap (filter ('$' `notElem`) . lines) . liftIO $ readFile file - length contents `seq` writeFileLines file $ map processLine contents +postProcessPackageData file = fixFile file fixPackageData + where + fixPackageData = unlines . map processLine . filter ('$' `notElem`) . lines + processLine line = replaceSeparators '_' prefix ++ suffix where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line + (prefix, suffix) = break (== '=') line diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index b2840dd..fe55005 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -59,7 +59,7 @@ buildWrapper :: PartialTarget -> Wrapper -> FilePath -> FilePath -> Action () buildWrapper target @ (PartialTarget stage pkg) wrapper wrapperPath binPath = do contents <- interpretPartial target $ wrapper binPath writeFileChanged wrapperPath contents - () <- cmd "chmod +x " [wrapperPath] + unit $ cmd "chmod +x " [wrapperPath] putSuccess $ "| Successfully created wrapper for '" ++ pkgNameString pkg ++ "' (" ++ show stage ++ ")." From git at git.haskell.org Thu Oct 26 23:52:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generalise run and terseRun. (5596b04) Message-ID: <20171026235231.41EDD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5596b04183c7c55c88c4173d5143803cd93691a4/ghc >--------------------------------------------------------------- commit 5596b04183c7c55c88c4173d5143803cd93691a4 Author: Andrey Mokhov Date: Thu Jan 15 02:05:49 2015 +0000 Generalise run and terseRun. >--------------------------------------------------------------- 5596b04183c7c55c88c4173d5143803cd93691a4 src/Oracles/Builder.hs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 0fce046..b1aca5d 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -95,27 +95,27 @@ with builder = do -- Run the builder with a given collection of arguments -- Raises an error if the builder is not uniquely specified in config files -run :: Builder -> Args -> Action () -run builder args = do +run :: ShowArgs a => Builder -> a -> Action () +run builder as = do needBuilder builder [exe] <- showArgs builder - args' <- args - cmd [exe] args' + args <- showArgs as + cmd [exe] args -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. -- Raises an error if the builder is not uniquely specified in config files -terseRun :: Builder -> Args -> Action () -terseRun builder args = do - args' <- args +terseRun :: ShowArgs a => Builder -> a -> Action () +terseRun builder as = do + args <- showArgs as putNormal $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args' + mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args putNormal "\\--------" - quietly $ run builder args + quietly $ run builder as interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of - Ar -> prefixAndSuffix 3 1 ss + Ar -> prefixAndSuffix 2 1 ss Ld -> prefixAndSuffix 4 0 ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss From git at git.haskell.org Thu Oct 26 23:52:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drops dot, adds none; renames pony to unicorn (da96a23) Message-ID: <20171026235233.9622D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da96a236f4678b2e64535bfe7a57928275d5aca1/ghc >--------------------------------------------------------------- commit da96a236f4678b2e64535bfe7a57928275d5aca1 Author: Moritz Angermann Date: Fri Jan 15 15:22:17 2016 +0800 Drops dot, adds none; renames pony to unicorn >--------------------------------------------------------------- da96a236f4678b2e64535bfe7a57928275d5aca1 shaking-up-ghc.cabal | 2 -- src/Base.hs | 23 ++++++++++------------- src/Main.hs | 27 --------------------------- src/Oracles/Config/CmdLineFlag.hs | 14 +++++++------- 4 files changed, 17 insertions(+), 49 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 123870d..b38feac 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -116,7 +116,6 @@ executable ghc-shake , ScopedTypeVariables build-depends: base , ansi-terminal >= 0.6 - , bytestring >= 0.10.6 , Cabal >= 1.22 , containers >= 0.5 , directory >= 1.2 @@ -126,6 +125,5 @@ executable ghc-shake , shake >= 0.15 , transformers >= 0.4 , unordered-containers >= 0.2 - , utf8-string >= 1.0.1 default-language: Haskell2010 ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j diff --git a/src/Base.hs b/src/Base.hs index b9c7f72..07b21e4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -115,16 +115,11 @@ a -/- b = unifyPath $ a b infixr 6 -/- --- | A wrapper around shakes @putNormal@ that substitutes --- any message for a fullstop if @buildInfo@ is @Dot at . -putNormal' :: String -> Action () -putNormal' = if buildInfo == Dot then putNormal . const "." else putNormal - -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do liftIO $ setSGR [SetColor Foreground Vivid colour] - putNormal' msg + putNormal msg liftIO $ setSGR [] liftIO $ hFlush stdout @@ -134,7 +129,9 @@ putOracle = putColoured Blue -- | Make build output more distinguishable putBuild :: String -> Action () -putBuild = putColoured White +putBuild = if buildInfo /= None + then putColoured White + else const (pure ()) -- | A more colourful version of success message putSuccess :: String -> Action () @@ -149,14 +146,14 @@ putError msg = do -- | Render an action. renderAction :: String -> String -> String -> String renderAction what input output = case buildInfo of - Normal -> renderBox [ what - , " input:" ++ input - , " => output:" ++ output ] - Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output - Pony -> renderPony [ what + Normal -> renderBox [ what , " input:" ++ input , " => output:" ++ output ] - Dot -> "." + Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output + Unicorn -> renderPony [ what + , " input:" ++ input + , " => output:" ++ output ] + None -> "" -- | Render the successful build of a program renderProgram :: String -> String -> String -> String diff --git a/src/Main.hs b/src/Main.hs index 14f3554..e9d1e56 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -14,10 +14,6 @@ import qualified Rules.Perl import qualified Test import Oracles.Config.CmdLineFlag (putOptions, flags) -import qualified Data.ByteString.Char8 as BS -import qualified Data.ByteString.UTF8 as UTF8 -import Data.Char (chr) - main :: IO () main = shakeArgsWith options flags $ \cmdLineFlags targets -> do putOptions cmdLineFlags @@ -41,27 +37,4 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True - , shakeOutput = const putMsg } - --- | Dynamic switch for @putStr@ and @putStrLn@ depending on the @msg at . -putMsg :: String -> IO () -putMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg -putMsg msg = BS.putStrLn . UTF8.fromString $ msg - --- | Drops ANSI Escape sequences from a string. -dropEscSequence :: String -> String -dropEscSequence = go - where - esc :: Char - esc = Data.Char.chr 27 - go :: String -> String - go [] = [] - go [x] = [x] - go (x:xs) | x == esc = skip xs - go (x:xs) | otherwise = x:go xs - skip :: String -> String - skip [] = [] - skip ['m'] = [] - skip ('m':xs) = go xs - skip (_ :xs) = skip xs diff --git a/src/Oracles/Config/CmdLineFlag.hs b/src/Oracles/Config/CmdLineFlag.hs index 47dbbbc..4b97c72 100644 --- a/src/Oracles/Config/CmdLineFlag.hs +++ b/src/Oracles/Config/CmdLineFlag.hs @@ -8,7 +8,7 @@ import Data.IORef -- Flags -data BuildInfoFlag = Normal | Brief | Pony | Dot deriving (Eq, Show) +data BuildInfoFlag = None | Brief | Normal | Unicorn deriving (Eq, Show) data CmdLineOptions = CmdLineOptions { flagBuildInfo :: BuildInfoFlag @@ -25,16 +25,16 @@ readBuildInfoFlag ms = (go =<< fmap (map toLower) ms) where go :: String -> Maybe BuildInfoFlag - go "normal" = Just Normal - go "brief" = Just Brief - go "pony" = Just Pony - go "dot" = Just Dot - go _ = Nothing -- Left "no parse" + go "none" = Just None + go "brief" = Just Brief + go "normal" = Just Normal + go "unicorn" = Just Unicorn + go _ = Nothing -- Left "no parse" mkClosure :: BuildInfoFlag -> CmdLineOptions -> CmdLineOptions mkClosure flag opts = opts { flagBuildInfo = flag } flags :: [OptDescr (Either String (CmdLineOptions -> CmdLineOptions))] -flags = [Option [] ["build-info"] (OptArg readBuildInfoFlag "") "Build Info Style (Normal, Brief, Pony, Dot, or None)"] +flags = [Option [] ["progress-info"] (OptArg readBuildInfoFlag "") "Build Info Style (None, Brief, Normal, or Unicorn)"] -- IO -- We use IO here instead of Oracles, as Oracles form part of shakes cache -- hence, changing command line arguments, would cause a full rebuild. And we From git at git.haskell.org Thu Oct 26 23:52:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Respect trackBuildSystem user setting (4ce3206) Message-ID: <20171026235234.BBD143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ce32069c4b46822dae309002fcbece8b62627ea/ghc >--------------------------------------------------------------- commit 4ce32069c4b46822dae309002fcbece8b62627ea Author: Andrey Mokhov Date: Mon Jan 4 01:33:45 2016 +0000 Respect trackBuildSystem user setting >--------------------------------------------------------------- 4ce32069c4b46822dae309002fcbece8b62627ea src/Rules/Generators/ConfigHs.hs | 3 ++- src/Rules/Generators/GhcAutoconfH.hs | 4 +++- src/Rules/Generators/GhcBootPlatformH.hs | 4 +++- src/Rules/Generators/GhcPlatformH.hs | 4 +++- src/Rules/Generators/GhcVersionH.hs | 4 ++++ src/Rules/Generators/VersionHs.hs | 4 +++- 6 files changed, 18 insertions(+), 5 deletions(-) diff --git a/src/Rules/Generators/ConfigHs.hs b/src/Rules/Generators/ConfigHs.hs index 1ec96e9..547670a 100644 --- a/src/Rules/Generators/ConfigHs.hs +++ b/src/Rules/Generators/ConfigHs.hs @@ -10,7 +10,8 @@ import Settings -- TODO: add tracking by moving these functions to separate tracked files generateConfigHs :: Expr String generateConfigHs = do - lift $ need [sourcePath -/- "Rules/Generators/ConfigHs.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/ConfigHs.hs"] cProjectName <- getSetting ProjectName cProjectGitCommitId <- getSetting ProjectGitCommitId cProjectVersion <- getSetting ProjectVersion diff --git a/src/Rules/Generators/GhcAutoconfH.hs b/src/Rules/Generators/GhcAutoconfH.hs index 67ec731..f5f89c6 100644 --- a/src/Rules/Generators/GhcAutoconfH.hs +++ b/src/Rules/Generators/GhcAutoconfH.hs @@ -3,6 +3,7 @@ module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH) where import Base import Expression import Oracles +import Settings.User -- TODO: change `mk/config.h` to `shake-build/cfg/config.h` configH :: FilePath @@ -16,7 +17,8 @@ undefinePackage s generateGhcAutoconfH :: Expr String generateGhcAutoconfH = do - lift $ need [sourcePath -/- "Rules/Generators/GhcAutoconfH.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcAutoconfH.hs"] configHContents <- lift $ map undefinePackage <$> readFileLines configH tablesNextToCode <- lift $ ghcEnableTablesNextToCode ghcUnreg <- getFlag GhcUnregisterised diff --git a/src/Rules/Generators/GhcBootPlatformH.hs b/src/Rules/Generators/GhcBootPlatformH.hs index 7416d24..6c111c2 100644 --- a/src/Rules/Generators/GhcBootPlatformH.hs +++ b/src/Rules/Generators/GhcBootPlatformH.hs @@ -3,10 +3,12 @@ module Rules.Generators.GhcBootPlatformH (generateGhcBootPlatformH) where import Base import Expression import Oracles +import Settings.User generateGhcBootPlatformH :: Expr String generateGhcBootPlatformH = do - lift $ need [sourcePath -/- "Rules/Generators/GhcBootPlatformH.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcBootPlatformH.hs"] stage <- getStage let cppify = replaceEq '-' '_' . replaceEq '.' '_' chooseSetting x y = getSetting $ if stage == Stage0 then x else y diff --git a/src/Rules/Generators/GhcPlatformH.hs b/src/Rules/Generators/GhcPlatformH.hs index 8652382..1deee3d 100644 --- a/src/Rules/Generators/GhcPlatformH.hs +++ b/src/Rules/Generators/GhcPlatformH.hs @@ -3,10 +3,12 @@ module Rules.Generators.GhcPlatformH (generateGhcPlatformH) where import Base import Expression import Oracles +import Settings.User generateGhcPlatformH :: Expr String generateGhcPlatformH = do - lift $ need [sourcePath -/- "Rules/Generators/GhcPlatformH.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcPlatformH.hs"] let cppify = replaceEq '-' '_' . replaceEq '.' '_' hostPlatform <- getSetting HostPlatform hostArch <- getSetting HostArch diff --git a/src/Rules/Generators/GhcVersionH.hs b/src/Rules/Generators/GhcVersionH.hs index a45df55..278813f 100644 --- a/src/Rules/Generators/GhcVersionH.hs +++ b/src/Rules/Generators/GhcVersionH.hs @@ -1,10 +1,14 @@ module Rules.Generators.GhcVersionH (generateGhcVersionH) where +import Base import Expression import Oracles +import Settings.User generateGhcVersionH :: Expr String generateGhcVersionH = do + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcVersionH.hs"] version <- getSetting ProjectVersionInt patchLevel1 <- getSetting ProjectPatchLevel1 patchLevel2 <- getSetting ProjectPatchLevel2 diff --git a/src/Rules/Generators/VersionHs.hs b/src/Rules/Generators/VersionHs.hs index 3023fc9..33b62193d 100644 --- a/src/Rules/Generators/VersionHs.hs +++ b/src/Rules/Generators/VersionHs.hs @@ -3,10 +3,12 @@ module Rules.Generators.VersionHs (generateVersionHs) where import Base import Expression import Oracles +import Settings.User generateVersionHs :: Expr String generateVersionHs = do - lift $ need [sourcePath -/- "Rules/Generators/VersionHs.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/VersionHs.hs"] projectVersion <- getSetting ProjectVersion targetOs <- getSetting TargetOs targetArch <- getSetting TargetArch From git at git.haskell.org Thu Oct 26 23:52:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Space leak. (c2f1abd) Message-ID: <20171026235237.064E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c2f1abd4d8ef56134168afb6b208c05b29008c34/ghc >--------------------------------------------------------------- commit c2f1abd4d8ef56134168afb6b208c05b29008c34 Author: Moritz Angermann Date: Fri Jan 15 15:23:21 2016 +0800 Space leak. >--------------------------------------------------------------- c2f1abd4d8ef56134168afb6b208c05b29008c34 src/Main.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index e9d1e56..e3f1a34 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -36,5 +36,4 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do options = shakeOptions { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple - , shakeTimings = True - } + , shakeTimings = True } From git at git.haskell.org Thu Oct 26 23:52:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass HsOpts to ghc -M. (b75a548) Message-ID: <20171026235234.CDACD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b75a548ad3e0c117a11db7cfc3d0ed0e00960612/ghc >--------------------------------------------------------------- commit b75a548ad3e0c117a11db7cfc3d0ed0e00960612 Author: Andrey Mokhov Date: Thu Jan 15 02:06:25 2015 +0000 Pass HsOpts to ghc -M. >--------------------------------------------------------------- b75a548ad3e0c117a11db7cfc3d0ed0e00960612 src/Package/Dependencies.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 1d3a8d2..f296419 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -17,11 +17,8 @@ buildPackageDependencies (Package name path _) (stage, dist, settings) = <> productArgs ["-odir", "-stubdir", "-hidir"] buildDir <> arg ["-dep-makefile", toStandard $ out <.> "new"] <> productArgs "-dep-suffix" (map wayPrefix <$> ways settings) + <> arg (HsOpts pkgData) <> arg (pkgHsSources path dist) - -- TODO: Check that skipping all _HC_OPTS is safe. - -- <> arg SrcHcOpts - -- TODO: i) is this needed? ii) shall we run GHC -M multiple times? - -- <> wayHcOpts vanilla -- Avoid rebuilding dependecies of out if it hasn't changed: -- Note: cannot use copyFileChanged as it depends on the source file deps <- liftIO $ readFile $ out <.> "new" From git at git.haskell.org Thu Oct 26 23:52:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass arguments as simple lists. (6269a42) Message-ID: <20171026235238.3B0723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6269a42dc3c1f166f8ab913d5cca4a0ed7000f88/ghc >--------------------------------------------------------------- commit 6269a42dc3c1f166f8ab913d5cca4a0ed7000f88 Author: Andrey Mokhov Date: Thu Jan 15 02:07:53 2015 +0000 Pass arguments as simple lists. >--------------------------------------------------------------- 6269a42dc3c1f166f8ab913d5cca4a0ed7000f88 src/Package/Library.hs | 21 ++++++++++++--------- 1 file changed, 12 insertions(+), 9 deletions(-) diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 043977a..22c9869 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -2,7 +2,6 @@ module Package.Library (buildPackageLibrary) where import Package.Base -import Data.List.Split arRule :: Package -> TodoItem -> Rules () arRule (Package _ path _) (stage, dist, _) = @@ -16,9 +15,11 @@ arRule (Package _ path _) (stage, dist, _) = libObjs <- pkgLibObjects path dist stage way liftIO $ removeFiles "." [out] -- Splitting argument list into chunks as otherwise Ar chokes up - -- TODO: use simpler list notation for passing arguments - forM_ (chunksOf 100 libObjs) $ \os -> do - terseRun Ar $ "q" <+> toStandard out <+> os + maxChunk <- argSizeLimit + forM_ (chunksOfSize maxChunk libObjs) $ \os -> do + terseRun Ar [ arg "q" + , arg $ toStandard out + , arg os ] ldRule :: Package -> TodoItem -> Rules () ldRule (Package name path _) (stage, dist, _) = @@ -29,12 +30,14 @@ ldRule (Package name path _) (stage, dist, _) = need ["shake/src/Package/Library.hs"] depObjs <- pkgDepObjects path dist vanilla need depObjs - terseRun Ld $ arg (ConfLdLinkerArgs stage) - <> arg ["-r", "-o", toStandard out] - <> arg depObjs + terseRun Ld [ arg (ConfLdLinkerArgs stage) + , arg "-r" + , arg "-o" + , arg $ toStandard out + , arg depObjs ] synopsis <- unwords <$> arg (Synopsis pkgData) - putNormal $ "Successfully built package " ++ name ++ "." - putNormal $ "Package synopsis: " ++ synopsis ++ "." + putNormal $ "/--------\nSuccessfully built package " ++ name ++ "." + putNormal $ "Package synopsis: " ++ synopsis ++ ".\n\\--------" buildPackageLibrary :: Package -> TodoItem -> Rules () buildPackageLibrary = arRule <> ldRule From git at git.haskell.org Thu Oct 26 23:52:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up build rules for custom packages. (1c3c9f3) Message-ID: <20171026235238.3C5AD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c3c9f3438f0fbd80ff476f63e253ecf0355920a/ghc >--------------------------------------------------------------- commit 1c3c9f3438f0fbd80ff476f63e253ecf0355920a Author: Andrey Mokhov Date: Mon Jan 4 01:34:17 2016 +0000 Clean up build rules for custom packages. >--------------------------------------------------------------- 1c3c9f3438f0fbd80ff476f63e253ecf0355920a src/Rules/IntegerGmp.hs | 64 +++++++++++++++++++++---------------------------- src/Rules/Libffi.hs | 31 ++++++++---------------- 2 files changed, 37 insertions(+), 58 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 1f50dc0..4e19b9d 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,12 +1,11 @@ module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where -import System.Directory - import Base import Expression import GHC import Oracles.Config.Setting import Rules.Actions +import Settings.User integerGmpBase :: FilePath integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp" @@ -28,9 +27,8 @@ target = PartialTarget Stage0 integerGmp configureEnvironment :: Action [CmdOption] configureEnvironment = do sequence [ builderEnv "CC" $ Gcc Stage1 - , builderEnv "CXX" $ Gcc Stage1 , builderEnv "AR" Ar - , builderEnv "NM" Nm] + , builderEnv "NM" Nm ] where builderEnv var builder = do needBuilder False builder @@ -49,7 +47,7 @@ configureArguments = do integerGmpRules :: Rules () integerGmpRules = do integerGmpLibrary %> \_ -> do - need [sourcePath -/- "Rules" -/- "integerGmp.hs"] + when trackBuildSystem $ need [sourcePath -/- "Rules" -/- "integerGmp.hs"] -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] @@ -64,53 +62,45 @@ integerGmpRules = do when (length tarballs /= 1) $ putError $ "integerGmpRules: exactly one tarball expected" ++ "(found: " ++ show tarballs ++ ")." - let filename = dropExtension . dropExtension . takeFileName $ head tarballs - let suffix = "-nodoc-patched" - unless (suffix `isSuffixOf` filename) $ - putError $ "integerGmpRules: expected suffix " ++ suffix - ++ " (found: " ++ filename ++ ")." - let libname = take (length filename - length suffix) filename need tarballs build $ fullTarget target Tar tarballs [integerGmpBase] -- move gmp- to gmpbuild - let integerGmpExtracted = integerGmpBase -/- libname - liftIO $ renameDirectory integerGmpExtracted integerGmpBuild - putBuild $ "| Move " ++ integerGmpExtracted ++ " -> " ++ integerGmpBuild + let filename = dropExtension . dropExtension . takeFileName $ head tarballs + suffix = "-nodoc-patched" + unless (suffix `isSuffixOf` filename) $ + putError $ "integerGmpRules: expected suffix " ++ suffix + ++ " (found: " ++ filename ++ ")." + let libname = take (length filename - length suffix) filename + moveDirectory (integerGmpBase -/- libname) integerGmpBuild -- apply patches -- TODO: replace "patch" with PATCH_CMD - unit $ cmd Shell [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch" - unit $ cmd Shell [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch] - putBuild $ "| Applied gmpsrc.patch and " ++ takeFileName integerGmpPatch + unit . quietly $ cmd Shell (EchoStdout False) [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch" + putBuild $ "| Apply " ++ (integerGmpBase -/- "gmpsrc.patch") + unit . quietly $ cmd Shell (EchoStdout False) [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch] + putBuild $ "| Apply " ++ (integerGmpBase -/- integerGmpPatch) -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? - -- ./configure - putBuild "| Running libffi configure..." envs <- configureEnvironment args <- configureArguments - unit $ cmd Shell [Cwd integerGmpBuild] "bash configure" envs args + runConfigure integerGmpBuild envs args - -- make - putBuild "| Running make..." - unit $ cmd Shell "make" ["-C", integerGmpBuild, "MAKEFLAGS="] + runMake integerGmpBuild [] -- copy library and header - forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> do - let file' = integerGmpBase -/- takeFileName file - copyFileChanged (integerGmpBuild -/- file) file' - putBuild $ "| Copy " ++ file ++ " -> " ++ file' - - ar <- builderPath Ar - ran <- builderPath Ranlib - -- unpack libgmp.a - putBuild "| Unpacking libgmp.a..." - unit $ cmd Shell [Cwd integerGmpBase] "mkdir -p objs" - unit $ cmd Shell [Cwd (integerGmpBase -/- "objs")] [ar] " x ../libgmp.a" - unit $ cmd Shell [Cwd integerGmpBase] [ran] " libgmp.a" - - putSuccess "| Successfully build custom library 'integer-gmp'" + -- TODO: why copy library, can we move it instead? + forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> + copyFile (integerGmpBuild -/- file) (integerGmpBase -/- takeFileName file) + + let objsDir = integerGmpBase -/- "objs" + createDirectory objsDir + build $ fullTarget target Ar [integerGmpLibrary] [objsDir] + + runBuilder Ranlib [integerGmpLibrary] + + putSuccess "| Successfully built custom library 'integer-gmp'" "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary] diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index f5f2668..93a20ab 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,13 +1,12 @@ module Rules.Libffi (libffiRules, libffiLibrary) where -import System.Directory - import Base import Expression import GHC import Oracles.Config.Setting import Rules.Actions import Settings.Builders.Common +import Settings.User -- We use this file to track the whole libffi library libffiLibrary :: FilePath @@ -63,40 +62,30 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiLibrary %> \_ -> do - need [sourcePath -/- "Rules/Libffi.hs"] + when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] when (length tarballs /= 1) $ putError $ "libffiRules: exactly one libffi tarball expected" ++ "(found: " ++ show tarballs ++ ")." - let libname = dropExtension . dropExtension . takeFileName $ head tarballs need tarballs build $ fullTarget target Tar tarballs ["libffi-tarballs"] - let libffiExtracted = "libffi-tarballs" -/- libname - liftIO $ renameDirectory libffiExtracted libffiBuild - putBuild $ "| Move " ++ libffiExtracted ++ " -> " ++ libffiBuild + let libname = dropExtension . dropExtension . takeFileName $ head tarballs + moveDirectory ("libffi-tarballs" -/- libname) libffiBuild - old <- liftIO $ readFile libffiMakefile - let new = fixLibffiMakefile old - length new `seq` liftIO $ writeFile libffiMakefile new - putBuild $ "| Fix " ++ libffiMakefile + fixFile libffiMakefile fixLibffiMakefile - forM_ ["config.guess", "config.sub"] $ \file -> do - copyFileChanged file $ libffiBuild -/- file - putBuild $ "| Copy " ++ file ++ " -> " ++ (libffiBuild -/- file) + forM_ ["config.guess", "config.sub"] $ \file -> + copyFile file (libffiBuild -/- file) - putBuild $ "| Running libffi configure..." envs <- configureEnvironment args <- configureArguments - unit $ cmd Shell [Cwd libffiBuild] "bash configure" envs args - - putBuild $ "| Running make..." - unit $ cmd Shell "make" ["-C", libffiBuild, "MAKEFLAGS="] + runConfigure libffiBuild envs args - putBuild $ "| Running make install..." - unit $ cmd Shell "make" ["-C", libffiBuild, "MAKEFLAGS= install"] + runMake libffiBuild [] + runMake libffiBuild ["install"] putSuccess $ "| Successfully built custom library 'libffi'" From git at git.haskell.org Thu Oct 26 23:52:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: adds putBuildInfo (ade3088) Message-ID: <20171026235240.75CC23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ade30882bd45c0f4e4747ba9c6d19b2ec08846de/ghc >--------------------------------------------------------------- commit ade30882bd45c0f4e4747ba9c6d19b2ec08846de Author: Moritz Angermann Date: Fri Jan 15 15:31:23 2016 +0800 adds putBuildInfo >--------------------------------------------------------------- ade30882bd45c0f4e4747ba9c6d19b2ec08846de src/Base.hs | 13 ++++++++----- src/Rules/Actions.hs | 6 +++--- 2 files changed, 11 insertions(+), 8 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 07b21e4..68a223b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -20,8 +20,8 @@ module Base ( bootPackageConstraints, packageDependencies, -- * Output - putColoured, putOracle, putBuild, putSuccess, putError, renderAction, - renderLibrary, renderProgram, + putColoured, putOracle, putBuild, putBuildInfo, putSuccess, putError, + renderAction, renderLibrary, renderProgram, -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, @@ -129,9 +129,12 @@ putOracle = putColoured Blue -- | Make build output more distinguishable putBuild :: String -> Action () -putBuild = if buildInfo /= None - then putColoured White - else const (pure ()) +putBuild = putColoured White + +-- | Switch for @putBuild@ filtered through @buildInfo@ +putBuildInfo :: String -> Action () +putBuildInfo s | buildInfo /= None = putBuild s +putBuildInfo _ = pure () -- | A more colourful version of success message putSuccess :: String -> Action () diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index eb37630..77d283b 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -64,7 +64,7 @@ captureStdout target path argList = do copyFile :: FilePath -> FilePath -> Action () copyFile source target = do - putBuild $ renderAction "Copy file" source target + putBuildInfo $ renderAction "Copy file" source target copyFileChanged source target createDirectory :: FilePath -> Action () @@ -80,7 +80,7 @@ removeDirectory dir = do -- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do - putBuild $ renderAction "Move directory" source target + putBuildInfo $ renderAction "Move directory" source target liftIO $ IO.renameDirectory source target -- Transform a given file by applying a function to its contents @@ -123,7 +123,7 @@ makeExecutable file = do -- Print out key information about the command being executed putInfo :: Target.Target -> Action () -putInfo Target.Target {..} = putBuild $ renderAction +putInfo Target.Target {..} = putBuildInfo $ renderAction ("Run " ++ show builder ++ " (" ++ stageInfo ++ "package = " ++ pkgNameString package ++ wayInfo ++ ")") (digest inputs) From git at git.haskell.org Thu Oct 26 23:52:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add bin-package-db (stage 0) to packages. (ad6da32) Message-ID: <20171026235241.F22B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ad6da32754b4c9eea30f344beb36728302e03b8f/ghc >--------------------------------------------------------------- commit ad6da32754b4c9eea30f344beb36728302e03b8f Author: Andrey Mokhov Date: Thu Jan 15 11:46:20 2015 +0000 Add bin-package-db (stage 0) to packages. >--------------------------------------------------------------- ad6da32754b4c9eea30f344beb36728302e03b8f src/Package.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Package.hs b/src/Package.hs index b8de413..881fd21 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -11,6 +11,7 @@ import Package.Dependencies -- These are the packages we build: packages :: [Package] packages = [ libraryPackage "array" Stage1 defaultSettings + , libraryPackage "bin-package-db" Stage0 defaultSettings , libraryPackage "bin-package-db" Stage1 defaultSettings , libraryPackage "binary" Stage1 defaultSettings , libraryPackage "deepseq" Stage1 defaultSettings From git at git.haskell.org Thu Oct 26 23:52:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix #87. (563307b) Message-ID: <20171026235242.0EB093A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/563307bd23206aafe88c74088411ff55fa7bfb5a/ghc >--------------------------------------------------------------- commit 563307bd23206aafe88c74088411ff55fa7bfb5a Author: Andrey Mokhov Date: Mon Jan 4 01:45:12 2016 +0000 Fix #87. >--------------------------------------------------------------- 563307bd23206aafe88c74088411ff55fa7bfb5a src/Rules/Copy.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index 3a385b8..3f33d9c 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -27,4 +27,4 @@ copyRules = do "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." where - file <~ dir = file %> \_ -> copyFile (dir -/- file) file + file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file From git at git.haskell.org Thu Oct 26 23:52:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge remote-tracking branch 'snowleopard/master' into angerman/feature/advanced-render-box (ee95b14) Message-ID: <20171026235244.6072A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee95b14e13491cc42329afed8ae038e9e94527cb/ghc >--------------------------------------------------------------- commit ee95b14e13491cc42329afed8ae038e9e94527cb Merge: ade3088 2024396 Author: Moritz Angermann Date: Fri Jan 15 15:59:02 2016 +0800 Merge remote-tracking branch 'snowleopard/master' into angerman/feature/advanced-render-box # Conflicts: # src/Base.hs >--------------------------------------------------------------- ee95b14e13491cc42329afed8ae038e9e94527cb .appveyor.yml | 1 + .travis.yml | 1 + cfg/system.config.in | 6 ++- src/Builder.hs | 2 + src/Rules/Actions.hs | 11 ++++- src/Rules/Gmp.hs | 101 ++++++++++++++++++++++++------------------- src/Rules/Library.hs | 6 ++- src/Settings/Builders/Ghc.hs | 11 ++++- 8 files changed, 89 insertions(+), 50 deletions(-) From git at git.haskell.org Thu Oct 26 23:52:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add arg folder. (e86a741) Message-ID: <20171026235246.195F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e86a74150fe51816c2f72094e9c0319638e914e1/ghc >--------------------------------------------------------------- commit e86a74150fe51816c2f72094e9c0319638e914e1 Author: Andrey Mokhov Date: Thu Jan 15 11:47:22 2015 +0000 Add arg folder. >--------------------------------------------------------------- e86a74150fe51816c2f72094e9c0319638e914e1 arg/README.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/arg/README.md b/arg/README.md new file mode 100644 index 0000000..0af8834 --- /dev/null +++ b/arg/README.md @@ -0,0 +1,5 @@ +This folder serves two purposes: + +* Tracking argument lists produced by rules + +* Documentation From git at git.haskell.org Thu Oct 26 23:52:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build rts in stage1 instead of dist (c4c7a7f) Message-ID: <20171026235246.384A43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4c7a7f8d710c1a02ff68456f7ee9cb8fd5aa3a3/ghc >--------------------------------------------------------------- commit c4c7a7f8d710c1a02ff68456f7ee9cb8fd5aa3a3 Author: Moritz Angermann Date: Mon Jan 4 20:26:14 2016 +0800 Build rts in stage1 instead of dist `rts/dist` is hardcoded, while the shake build system builds in `rts/stage1`. Fixes #86 >--------------------------------------------------------------- c4c7a7f8d710c1a02ff68456f7ee9cb8fd5aa3a3 src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 274092b..b68f1c7 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -104,7 +104,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do , "includes/ghcplatform.h" ] build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] old <- liftIO $ readFile rtsConf - let new = unlines . map (replace "\"\"" "") + let new = unlines . map (replace "\"\"" "" . replace "rts/dist/build" "rts/stage1/build") . filter (not . null) $ lines old liftIO $ length new `seq` writeFile rtsConf new From git at git.haskell.org Thu Oct 26 23:52:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move rendering to Actions. (c7c45fc) Message-ID: <20171026235247.EEA113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7c45fc3ec57e888fc6560e77a29617f18c3a46c/ghc >--------------------------------------------------------------- commit c7c45fc3ec57e888fc6560e77a29617f18c3a46c Author: Moritz Angermann Date: Fri Jan 15 21:36:36 2016 +0800 Move rendering to Actions. >--------------------------------------------------------------- c7c45fc3ec57e888fc6560e77a29617f18c3a46c src/Base.hs | 98 +--------------------------------------------- src/Rules/Actions.hs | 107 +++++++++++++++++++++++++++++++++++++++++++++++++-- 2 files changed, 104 insertions(+), 101 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 c7c45fc3ec57e888fc6560e77a29617f18c3a46c From git at git.haskell.org Thu Oct 26 23:52:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generated arg/*.txt files to .gitignore. (440aeff) Message-ID: <20171026235249.738D73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/440aeff3e952f2721e4d82b1609f72b90c332901/ghc >--------------------------------------------------------------- commit 440aeff3e952f2721e4d82b1609f72b90c332901 Author: Andrey Mokhov Date: Thu Jan 15 18:40:14 2015 +0000 Add generated arg/*.txt files to .gitignore. >--------------------------------------------------------------- 440aeff3e952f2721e4d82b1609f72b90c332901 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 375b257..82a6588 100644 --- a/.gitignore +++ b/.gitignore @@ -3,3 +3,4 @@ _shake/ _build/ cfg/default.config +arg/*.txt From git at git.haskell.org Thu Oct 26 23:52:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy libffi into place (6d36942) Message-ID: <20171026235249.A48103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d369421eee990adb0f97e087dfc357fd7093262/ghc >--------------------------------------------------------------- commit 6d369421eee990adb0f97e087dfc357fd7093262 Author: Moritz Angermann Date: Mon Jan 4 20:27:15 2016 +0800 Copy libffi into place rts needs libffi as libCff in rts/stage1/build. This fixes #89 >--------------------------------------------------------------- 6d369421eee990adb0f97e087dfc357fd7093262 src/Rules/Copy.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index 3f33d9c..bcd1f1e 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -21,7 +21,9 @@ copyRules = do when (length ffiHPaths /= 1) $ putError $ "copyRules: exactly one ffi.h header expected" ++ "(found: " ++ show ffiHPaths ++ ")." + copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih + copyFile libffiLibrary (targetPath Stage1 rts -/- "build" -/- "libCffi.a") "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath From git at git.haskell.org Thu Oct 26 23:52:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #171 from snowleopard/angerman/feature/advanced-render-box (8a0380a) Message-ID: <20171026235251.8D7493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8a0380a71035774db6a874567e962e37d61089a5/ghc >--------------------------------------------------------------- commit 8a0380a71035774db6a874567e962e37d61089a5 Merge: 2024396 c7c45fc Author: Andrey Mokhov Date: Fri Jan 15 13:41:06 2016 +0000 Merge pull request #171 from snowleopard/angerman/feature/advanced-render-box advanced render box, fix #134 [skip ci] >--------------------------------------------------------------- 8a0380a71035774db6a874567e962e37d61089a5 src/Base.hs | 94 +-------------------------------- src/Oracles/Config/CmdLineFlag.hs | 15 +++--- src/Rules/Actions.hs | 107 ++++++++++++++++++++++++++++++++++++-- 3 files changed, 111 insertions(+), 105 deletions(-) From git at git.haskell.org Thu Oct 26 23:52:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generated arg/*/*.txt files to .gitignore. (11ad707) Message-ID: <20171026235253.2482F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/11ad7076f72a8c879bed4637318aedb5f6df7b63/ghc >--------------------------------------------------------------- commit 11ad7076f72a8c879bed4637318aedb5f6df7b63 Author: Andrey Mokhov Date: Thu Jan 15 18:41:45 2015 +0000 Add generated arg/*/*.txt files to .gitignore. >--------------------------------------------------------------- 11ad7076f72a8c879bed4637318aedb5f6df7b63 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 82a6588..dad3a3c 100644 --- a/.gitignore +++ b/.gitignore @@ -3,4 +3,4 @@ _shake/ _build/ cfg/default.config -arg/*.txt +arg/*/*.txt From git at git.haskell.org Thu Oct 26 23:52:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds integerGmpLibraryH to Rules.IntegerGmp (d40050f) Message-ID: <20171026235253.882463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d40050fb1554db54db683f7d26a55bc3fb0868df/ghc >--------------------------------------------------------------- commit d40050fb1554db54db683f7d26a55bc3fb0868df Author: Moritz Angermann Date: Mon Jan 4 20:50:58 2016 +0800 Adds integerGmpLibraryH to Rules.IntegerGmp This is, so we can use integerGmpLibraryH, without having to use the path outside of the Rules.IntegerGmp module. >--------------------------------------------------------------- d40050fb1554db54db683f7d26a55bc3fb0868df src/Rules/IntegerGmp.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 4e19b9d..f927102 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,4 +1,4 @@ -module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where +module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary, integerGmpLibraryH) where import Base import Expression @@ -16,6 +16,9 @@ integerGmpBuild = integerGmpBase -/- "gmpbuild" integerGmpLibrary :: FilePath integerGmpLibrary = integerGmpBase -/- "libgmp.a" +integerGmpLibraryH :: FilePath +integerGmpLibraryH = integerGmpBase -/- "gmp.h" + -- relative to integerGmpBuild integerGmpPatch :: FilePath integerGmpPatch = ".." -/- "tarball" -/- "gmp-5.0.4.patch" @@ -103,4 +106,4 @@ integerGmpRules = do putSuccess "| Successfully built custom library 'integer-gmp'" - "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary] + integerGmpLibraryH %> \_ -> need [integerGmpLibrary] From git at git.haskell.org Thu Oct 26 23:52:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make error message more helpful. (b4f0b5c) Message-ID: <20171026235255.4C97A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b4f0b5c264583fbd2410fd3d720fa9004f0490b9/ghc >--------------------------------------------------------------- commit b4f0b5c264583fbd2410fd3d720fa9004f0490b9 Author: Andrey Mokhov Date: Fri Jan 15 14:48:29 2016 +0000 Make error message more helpful. [skip ci] >--------------------------------------------------------------- b4f0b5c264583fbd2410fd3d720fa9004f0490b9 src/Builder.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 353c00f..96cb608 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -93,9 +93,9 @@ builderKey builder = case builder of -- TODO: Paths to some builders should be determined using 'defaultProgramPath' builderPath :: Builder -> Action FilePath builderPath builder = do - path <- askConfigWithDefault (builderKey builder) $ - putError $ "\nCannot find path to '" ++ (builderKey builder) - ++ "' in configuration files." + path <- askConfigWithDefault (builderKey builder) . putError $ + "\nCannot find path to '" ++ (builderKey builder) + ++ "' in configuration files. Have you forgot to run configure?" windows <- windowsHost case (path, windows) of ("", _) -> return path From git at git.haskell.org Thu Oct 26 23:52:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add putColoured. (63d4481) Message-ID: <20171026235256.A6CE83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/63d4481898a503c5532e39f3b18a60c3518cad57/ghc >--------------------------------------------------------------- commit 63d4481898a503c5532e39f3b18a60c3518cad57 Author: Andrey Mokhov Date: Thu Jan 15 18:42:54 2015 +0000 Add putColoured. >--------------------------------------------------------------- 63d4481898a503c5532e39f3b18a60c3518cad57 src/Oracles/Builder.hs | 9 ++++++--- src/Util.hs | 13 ++++++++++++- 2 files changed, 18 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index b1aca5d..88f9649 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -7,6 +7,7 @@ module Oracles.Builder ( import Data.Char import Base +import Util import Oracles.Base import Oracles.Flag import Oracles.Option @@ -108,9 +109,11 @@ run builder as = do terseRun :: ShowArgs a => Builder -> a -> Action () terseRun builder as = do args <- showArgs as - putNormal $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args - putNormal "\\--------" + putColoured Vivid White $ "/--------\n" ++ + "| Running " ++ show builder ++ " with arguments:" + mapM_ (putColoured Vivid White . ("| " ++)) $ + interestingInfo builder args + putColoured Vivid White $ "\\--------" quietly $ run builder as interestingInfo :: Builder -> [String] -> [String] diff --git a/src/Util.hs b/src/Util.hs index b1ff9e5..e0524df 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,11 +1,15 @@ module Util ( module Data.Char, + module System.Console.ANSI, replaceIf, replaceEq, replaceSeparators, - chunksOfSize + chunksOfSize, + putColoured ) where import Base import Data.Char +import System.Console.ANSI +import System.IO replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -30,3 +34,10 @@ chunksOfSize size ss = reverse chunk : chunksOfSize size rest if newSize > size then (chunk , s:ss) else (newChunk, rest) + +putColoured :: ColorIntensity -> Color -> String -> Action () +putColoured intensity colour msg = do + liftIO $ setSGR [SetColor Foreground intensity colour] + putNormal msg + liftIO $ setSGR [] + liftIO $ hFlush stdout From git at git.haskell.org Thu Oct 26 23:53:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor package-data oracles. (5a9b0a7) Message-ID: <20171026235322.E38A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a9b0a741769feacc65bf976ca31d05ac3a58647/ghc >--------------------------------------------------------------- commit 5a9b0a741769feacc65bf976ca31d05ac3a58647 Author: Andrey Mokhov Date: Fri Jan 16 13:59:39 2015 +0000 Refactor package-data oracles. >--------------------------------------------------------------- 5a9b0a741769feacc65bf976ca31d05ac3a58647 src/Oracles/PackageData.hs | 9 +++++---- src/Package.hs | 11 +++-------- src/Package/Base.hs | 42 +++++++++++++++++++++--------------------- src/Package/Compile.hs | 10 +++++----- src/Package/Data.hs | 16 +++++++--------- src/Package/Dependencies.hs | 10 +++++----- src/Package/Library.hs | 6 +++--- 7 files changed, 49 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 5a9b0a741769feacc65bf976ca31d05ac3a58647 From git at git.haskell.org Thu Oct 26 23:53:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve handling of generated dependencies, clean up code. (87568c1) Message-ID: <20171026235324.8AD873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/87568c1d948f9c588419b48146bec38a909eb99b/ghc >--------------------------------------------------------------- commit 87568c1d948f9c588419b48146bec38a909eb99b Author: Andrey Mokhov Date: Mon Jan 4 17:26:20 2016 +0000 Improve handling of generated dependencies, clean up code. >--------------------------------------------------------------- 87568c1d948f9c588419b48146bec38a909eb99b src/Rules/Data.hs | 15 ++++++--- src/Rules/Dependencies.hs | 6 +--- src/Rules/Generate.hs | 81 ++++++++++++++++++++++++----------------------- src/Rules/Library.hs | 5 ++- 4 files changed, 56 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 87568c1d948f9c588419b48146bec38a909eb99b From git at git.haskell.org Thu Oct 26 23:53:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch compileInterfaceFilesSeparately off by default. (c9ec473) Message-ID: <20171026235326.C890B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9ec473baba6bde9097a456e82dedfcc3bb1252e/ghc >--------------------------------------------------------------- commit c9ec473baba6bde9097a456e82dedfcc3bb1252e Author: Andrey Mokhov Date: Sat Jan 16 03:12:55 2016 +0000 Switch compileInterfaceFilesSeparately off by default. See #174. >--------------------------------------------------------------- c9ec473baba6bde9097a456e82dedfcc3bb1252e src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 5b82571..2a1471d 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -105,4 +105,4 @@ turnWarningsIntoErrors = return False -- | Decouple the compilation of @*.hi@ and @*.o@ files by setting to True. compileInterfaceFilesSeparately :: Bool -compileInterfaceFilesSeparately = True +compileInterfaceFilesSeparately = False From git at git.haskell.org Thu Oct 26 23:53:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make single and multiple string options type safe. (5c1a7e4) Message-ID: <20171026235327.0FBE13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5c1a7e4ec089b8ce044ca45d03d2305915974ada/ghc >--------------------------------------------------------------- commit 5c1a7e4ec089b8ce044ca45d03d2305915974ada Author: Andrey Mokhov Date: Fri Jan 16 17:05:33 2015 +0000 Make single and multiple string options type safe. >--------------------------------------------------------------- 5c1a7e4ec089b8ce044ca45d03d2305915974ada src/Base.hs | 22 ++++++++++--- src/Oracles/Option.hs | 2 +- src/Oracles/PackageData.hs | 75 +++++++++++++++++++++++++++++---------------- src/Package.hs | 4 +-- src/Package/Base.hs | 59 ++++++++++++++++++----------------- src/Package/Compile.hs | 26 ++++++++-------- src/Package/Data.hs | 65 ++++++++++++++++++++------------------- src/Package/Dependencies.hs | 18 +++++------ src/Package/Library.hs | 16 +++++----- src/Targets.hs | 31 ++++++++++--------- src/Util.hs | 8 ++++- src/Ways.hs | 6 ++-- 12 files changed, 187 insertions(+), 145 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 5c1a7e4ec089b8ce044ca45d03d2305915974ada From git at git.haskell.org Thu Oct 26 23:53:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Travis support (64da998) Message-ID: <20171026235328.0563B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64da99895a240d9af031ac9357b0bedcb215ac02/ghc >--------------------------------------------------------------- commit 64da99895a240d9af031ac9357b0bedcb215ac02 Author: David Luposchainsky Date: Mon Jan 4 18:20:23 2016 +0100 Add Travis support >--------------------------------------------------------------- 64da99895a240d9af031ac9357b0bedcb215ac02 .travis.yml | 32 ++++++++++++++++++++++++++++++++ .travis/install-cabal-happy-alex.sh | 18 ++++++++++++++++++ .travis/install-ghc-shake.sh | 16 ++++++++++++++++ .travis/install-ghc.sh | 15 +++++++++++++++ .travis/print-env.sh | 9 +++++++++ .travis/run-ghc-shake.sh | 9 +++++++++ README.md | 2 ++ 7 files changed, 101 insertions(+) diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..5e169fa --- /dev/null +++ b/.travis.yml @@ -0,0 +1,32 @@ +sudo: false + +matrix: + include: + - env: CABALVER=1.22 GHCVER=7.10.3 + addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.3,zlib1g-dev,terminfo-dev], sources: [hvr-ghc]}} + +before_install: + + - PATH="$HOME/.cabal/bin:$PATH" + - PATH="/opt/ghc/$GHCVER/bin:$PATH" + - PATH="/opt/cabal/$CABALVER/bin:$PATH" + - export PATH + + - .travis/print-env.sh + +install: + - .travis/install-cabal-happy-alex.sh + - .travis/install-ghc.sh + - .travis/install-ghc-shake.sh + +script: + - .travis/run-ghc-shake.sh + +cache: + directories: + - $HOME/.cabal + # - ghc/shake-build/.cabal-sandbox + # - ghc/shake-build/cabal.sandbox.config + +# before_cache: +# - rm -rf ghc/shake-build diff --git a/.travis/install-cabal-happy-alex.sh b/.travis/install-cabal-happy-alex.sh new file mode 100755 index 0000000..93df460 --- /dev/null +++ b/.travis/install-cabal-happy-alex.sh @@ -0,0 +1,18 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[32m" # Green +RESET="\e[m" + +echo -e "${COLOR}GHC version:${RESET}" +ghc --version + +echo -e "${COLOR}Cabal version:${RESET}" +cabal --version + +echo -e "${COLOR}Update Cabal${RESET}" +cabal update + +echo -e "${COLOR}Install Alex+Happy${RESET}" +cabal install alex happy diff --git a/.travis/install-ghc-shake.sh b/.travis/install-ghc-shake.sh new file mode 100755 index 0000000..2dc0392 --- /dev/null +++ b/.travis/install-ghc-shake.sh @@ -0,0 +1,16 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[31m" # Red, because this file is serious business +RESET="\e[m" + +echo -e "${COLOR}Brutally hacking GHC-Shake to its proper location${RESET}" +SHAKEDIR="ghc/shake-build" +mkdir -p "$SHAKEDIR" +mv .git "$SHAKEDIR/" +( cd "$SHAKEDIR" && git reset --hard HEAD ) + +echo -e "${COLOR}Installing deps into sandbox${RESET}" +( cd "$SHAKEDIR" && cabal sandbox init ) +( cd "$SHAKEDIR" && cabal install --only-dependencies . ) diff --git a/.travis/install-ghc.sh b/.travis/install-ghc.sh new file mode 100755 index 0000000..126cbe2 --- /dev/null +++ b/.travis/install-ghc.sh @@ -0,0 +1,15 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[34m" # Blue +RESET="\e[m" + +echo -e "${COLOR}Clone GHC source${RESET}" +git clone git://git.haskell.org/ghc + +echo -e "${COLOR}Initialize GHC submodules${RESET}" +( cd ghc && git submodule update --init ) + +echo -e "${COLOR}GHC boot/configure${RESET}" +( cd ghc && ./boot && ./configure) diff --git a/.travis/print-env.sh b/.travis/print-env.sh new file mode 100755 index 0000000..c09c11f --- /dev/null +++ b/.travis/print-env.sh @@ -0,0 +1,9 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[32m" # Green +RESET="\e[m" + +echo -e "${COLOR}Environment:${RESET}" +env diff --git a/.travis/run-ghc-shake.sh b/.travis/run-ghc-shake.sh new file mode 100755 index 0000000..7b867b7 --- /dev/null +++ b/.travis/run-ghc-shake.sh @@ -0,0 +1,9 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[32m" # Green +RESET="\e[m" + +echo -e "${COLOR}Running Shake build system${RESET}" +( cd ghc && ./shake-build/build.cabal.sh ) diff --git a/README.md b/README.md index f26cc49..43b74be 100644 --- a/README.md +++ b/README.md @@ -1,6 +1,8 @@ Shaking up GHC ============== +[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) + As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC][ghc] build system based on standard `make` into a new and (hopefully) better one based on From git at git.haskell.org Thu Oct 26 23:53:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix lint error on doesFileExist 'config.mk'. (f63e9db) Message-ID: <20171026235330.6D9D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f63e9db131bfd9860db988b01d4a581a6541d796/ghc >--------------------------------------------------------------- commit f63e9db131bfd9860db988b01d4a581a6541d796 Author: Andrey Mokhov Date: Sat Jan 16 12:16:29 2016 +0000 Fix lint error on doesFileExist 'config.mk'. >--------------------------------------------------------------- f63e9db131bfd9860db988b01d4a581a6541d796 src/Rules/Gmp.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 61a0a6f..ec14b36 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -2,6 +2,8 @@ module Rules.Gmp ( gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH, gmpDependencies ) where +import qualified System.Directory as IO + import Base import Expression import GHC @@ -80,7 +82,7 @@ gmpRules = do -- twice -- think how this can be optimised (shall we solve #18 first?) -- TODO: this is a hacky optimisation: we do not rerun configure of -- integerGmp package if we detect the results of the previous run - unlessM (doesFileExist $ gmpBase -/- "config.mk") $ do + unlessM (liftIO . IO.doesFileExist $ gmpBase -/- "config.mk") $ do args <- configureIntGmpArguments runConfigure (pkgPath integerGmp) envs args From git at git.haskell.org Thu Oct 26 23:53:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcSourcePath option. (eac54ff) Message-ID: <20171026235330.9114A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eac54ff6799eeb7824c7a8d1e5bb2bfa662d3189/ghc >--------------------------------------------------------------- commit eac54ff6799eeb7824c7a8d1e5bb2bfa662d3189 Author: Andrey Mokhov Date: Fri Jan 16 18:18:00 2015 +0000 Add GhcSourcePath option. >--------------------------------------------------------------- eac54ff6799eeb7824c7a8d1e5bb2bfa662d3189 cfg/default.config.in | 4 ++++ src/Oracles/Option.hs | 2 ++ 2 files changed, 6 insertions(+) diff --git a/cfg/default.config.in b/cfg/default.config.in index 10ee7ee..7402bd5 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -1,3 +1,6 @@ +# Edit 'user.config' to override these settings. +#=============================================== + # Paths to builders: #=================== @@ -35,6 +38,7 @@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ validating = NO +ghc-source-path = @hardtop@ # Information about host and target systems: #=========================================== diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index 667e50e..7dcb9a8 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -22,6 +22,7 @@ data Option = TargetOs | HostOsCpp | DynamicExtension | ProjectVersion + | GhcSourcePath data MultiOption = SrcHcArgs | ConfCcArgs Stage @@ -41,6 +42,7 @@ instance ShowArg Option where HostOsCpp -> "host-os-cpp" DynamicExtension -> "dynamic-extension" ProjectVersion -> "project-version" + GhcSourcePath -> "ghc-source-path" instance ShowArgs MultiOption where showArgs opt = showArgs $ fmap words $ askConfig $ case opt of From git at git.haskell.org Thu Oct 26 23:53:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #93 from quchen/travis-ci (45c731c) Message-ID: <20171026235331.918033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45c731c4105f0eb7daf2975cb9073f6879587042/ghc >--------------------------------------------------------------- commit 45c731c4105f0eb7daf2975cb9073f6879587042 Merge: 87568c1 64da998 Author: Andrey Mokhov Date: Mon Jan 4 18:51:30 2016 +0000 Merge pull request #93 from quchen/travis-ci Travis CI using dirty tricks >--------------------------------------------------------------- 45c731c4105f0eb7daf2975cb9073f6879587042 .travis.yml | 32 ++++++++++++++++++++++++++++++++ .travis/install-cabal-happy-alex.sh | 18 ++++++++++++++++++ .travis/install-ghc-shake.sh | 16 ++++++++++++++++ .travis/install-ghc.sh | 15 +++++++++++++++ .travis/print-env.sh | 9 +++++++++ .travis/run-ghc-shake.sh | 9 +++++++++ README.md | 2 ++ 7 files changed, 101 insertions(+) From git at git.haskell.org Thu Oct 26 23:53:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make the build badges follow the master branch only (e9013dc) Message-ID: <20171026235334.C49583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e9013dcf7a13d9b55e353bb5e1527c4a75726b4d/ghc >--------------------------------------------------------------- commit e9013dcf7a13d9b55e353bb5e1527c4a75726b4d Author: Andrey Mokhov Date: Sat Jan 16 15:40:59 2016 +0000 Make the build badges follow the master branch only [skip ci] >--------------------------------------------------------------- e9013dcf7a13d9b55e353bb5e1527c4a75726b4d README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index f5b8117..8651b9b 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Shaking up GHC ============== -[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) As part of my 6-month research secondment to Microsoft Research in Cambridge From git at git.haskell.org Thu Oct 26 23:53:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add bootPackageDb function. (2990db6) Message-ID: <20171026235335.19A603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2990db6fa1688f58c252787320a14e800658e6f8/ghc >--------------------------------------------------------------- commit 2990db6fa1688f58c252787320a14e800658e6f8 Author: Andrey Mokhov Date: Fri Jan 16 18:19:12 2015 +0000 Add bootPackageDb function. >--------------------------------------------------------------- 2990db6fa1688f58c252787320a14e800658e6f8 src/Base.hs | 1 + src/Package/Data.hs | 18 ++++++++++++------ src/Targets.hs | 22 ++++++++++++---------- 3 files changed, 25 insertions(+), 16 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index f4edb45..232bca2 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -65,6 +65,7 @@ instance ShowArgs a => ShowArgs [a] where instance ShowArgs a => ShowArgs (Action a) where showArgs = (showArgs =<<) +-- TODO: improve args type safety args :: ShowArgs a => a -> Args args = showArgs diff --git a/src/Package/Data.hs b/src/Package/Data.hs index cfc8b53..b6c28c6 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -73,6 +73,12 @@ bootPkgConstraints = args $ do _ -> redError $ "Cannot determine package version in '" ++ toStandard cabal ++ "'." +bootPackageDb :: Args +bootPackageDb = do + top <- showArg GhcSourcePath + arg $ toStandard + $ "--package-db=" ++ top "libraries/bootstrapping.conf" + cabalArgs :: Package -> TodoItem -> Args cabalArgs pkg @ (Package _ path _) todo @ (stage, dist, settings) = args [ args ["configure", path, dist] @@ -83,6 +89,7 @@ cabalArgs pkg @ (Package _ path _) todo @ (stage, dist, settings) = args , with (Ghc stage) -- TODO: used limited to max stage1 GHC , with (GhcPkg stage) , customConfArgs settings + , when (stage == Stage0) bootPackageDb , libraryArgs =<< ways settings , when (specified HsColour) $ with HsColour , configureArgs stage settings @@ -94,12 +101,11 @@ cabalArgs pkg @ (Package _ path _) todo @ (stage, dist, settings) = args , with Happy ] -- TODO: reorder with's ghcPkgArgs :: Package -> TodoItem -> Args -ghcPkgArgs (Package _ path _) (stage, dist, _) = return $ - [ "update" - , "--force" - , toStandard $ path dist "inplace-pkg-config" ] - ++ - [ "--package-db=libraries/bootstrapping.conf" | stage == Stage0 ] +ghcPkgArgs (Package _ path _) (stage, dist, _) = args $ + [ arg "update" + , arg "--force" + , arg $ toStandard $ path dist "inplace-pkg-config" + , when (stage == Stage0) bootPackageDb ] buildRule :: Package -> TodoItem -> Rules () buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = diff --git a/src/Targets.hs b/src/Targets.hs index 59fdbf1..3895bae 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -12,16 +12,18 @@ libraryPackagesInStage Stage0 = , "hoopl" , "hpc" , "transformers" ] -libraryPackagesInStage Stage1 = [] - --[ "array" - --, "deepseq" - --, "Cabal/Cabal" - --, "containers" - --, "filepath" - --, "parallel" - --, "pretty" - --, "stm" - --, "template-haskell" ] +libraryPackagesInStage Stage1 = + libraryPackagesInStage Stage0 ++ + [ "array" + , "deepseq" + , "Cabal/Cabal" + , "containers" + , "filepath" + , "parallel" + , "pretty" + , "stm" + , "template-haskell" ] + libraryPackagesInStage _ = [] libraryPackages :: [String] From git at git.haskell.org Thu Oct 26 23:53:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Continue refactoring of generated dependencies. (64f9350) Message-ID: <20171026235335.ABD713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64f93509197b23722bf14928ce50c5a3930b4d27/ghc >--------------------------------------------------------------- commit 64f93509197b23722bf14928ce50c5a3930b4d27 Author: Andrey Mokhov Date: Mon Jan 4 19:59:27 2016 +0000 Continue refactoring of generated dependencies. >--------------------------------------------------------------- 64f93509197b23722bf14928ce50c5a3930b4d27 src/Rules/Dependencies.hs | 4 +-- src/Rules/Generate.hs | 87 ++++++++++++++++++++++++++--------------------- 2 files changed, 50 insertions(+), 41 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 5b51c1d..b0dd474 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -18,13 +18,13 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do let srcFile = dropBuild . dropExtension $ out - orderOnly $ generatedDependencies stage pkg + orderOnly $ generatedDependencies stage need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - orderOnly $ generatedDependencies stage pkg + orderOnly $ generatedDependencies stage need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 21c197b..140c978 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -16,6 +16,7 @@ import Oracles.ModuleFiles import Rules.Actions import Rules.Resources (Resources) import Settings +import Settings.Builders.DeriveConstants primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -26,47 +27,55 @@ primopsTxt stage = targetPath stage compiler -/- "build/primops.txt" platformH :: Stage -> FilePath platformH stage = targetPath stage compiler -/- "ghc_boot_platform.h" -derivedConstantsPath :: FilePath -derivedConstantsPath = "includes/dist-derivedconstants/header" - -defaultGeneratedDependencies :: [FilePath] -defaultGeneratedDependencies = - [ "includes/ghcautoconf.h" - , "includes/ghcplatform.h" - , derivedConstantsPath -/- "DerivedConstants.h" - , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" - , targetPath Stage1 rts -/- "build/ffi.h" - , targetPath Stage1 rts -/- "build/ffitarget.h" ] +includesDependencies :: [FilePath] +includesDependencies = ("includes" -/-) <$> + [ "ghcautoconf.h" + , "ghcplatform.h" + , "ghcversion.h" ] + +derivedConstantsDependencies :: [FilePath] +derivedConstantsDependencies = (derivedConstantsPath -/-) <$> [] + -- [ "DerivedConstants.h" + -- , "GHCConstantsHaskellType.hs" + -- , "GHCConstantsHaskellWrappers.hs" + -- , "GHCConstantsHaskellExports.hs" ] + +libffiDependencies :: [FilePath] +libffiDependencies = (targetPath Stage1 rts -/-) <$> + [ "build/ffi.h" + , "build/ffitarget.h" ] + +defaultDependencies :: [FilePath] +defaultDependencies = + includesDependencies ++ derivedConstantsDependencies ++ libffiDependencies + +compilerDependencies :: Stage -> [FilePath] +compilerDependencies stage = + [ platformH stage ] + ++ + fmap ((targetPath stage compiler -/- "build") -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] -- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? -generatedDependencies :: Stage -> Package -> [FilePath] -generatedDependencies stage pkg = - defaultGeneratedDependencies ++ extraGeneratedDependencies - where - extraGeneratedDependencies - | pkg == compiler = let buildPath = targetPath stage compiler -/- "build" - in - [ platformH stage ] - ++ - fmap (buildPath -/-) - [ "primop-vector-uniques.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" - , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] - | otherwise = [] +-- TODO: improve +generatedDependencies :: Stage -> [FilePath] +generatedDependencies stage + | stage == Stage1 = defaultDependencies ++ compilerDependencies stage + | otherwise = [] -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] From git at git.haskell.org Thu Oct 26 23:53:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor paths to auxiliary build files. (4a90b33) Message-ID: <20171026235339.5E7633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a90b33ef70df26624fc064cdd4508677a0b7eec/ghc >--------------------------------------------------------------- commit 4a90b33ef70df26624fc064cdd4508677a0b7eec Author: Andrey Mokhov Date: Sat Jan 16 18:08:51 2016 +0000 Refactor paths to auxiliary build files. See #176. >--------------------------------------------------------------- 4a90b33ef70df26624fc064cdd4508677a0b7eec src/Rules/Actions.hs | 2 -- src/Settings/Builders/Ghc.hs | 4 ---- src/Settings/Packages/IntegerGmp.hs | 6 +----- src/Settings/Paths.hs | 16 ++++++++++++---- 4 files changed, 13 insertions(+), 15 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 21d134f..663f53d 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -157,13 +157,11 @@ putInfo Target.Target {..} = putProgressInfo $ renderAction digest [x] = x digest (x:xs) = x ++ " (and " ++ show (length xs) ++ " more)" - -- | Switch for @putBuild@ filtered through @buildInfo@ putProgressInfo :: String -> Action () putProgressInfo s | buildInfo /= None = putBuild s putProgressInfo _ = pure () - -- | Render an action. renderAction :: String -> String -> String -> String renderAction what input output = case buildInfo of diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 0f1fc32..c97cd56 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -11,10 +11,6 @@ import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) import Settings.Builders.Common (cIncludeArgs) --- GMP library names extracted from integer-gmp.buildinfo -gmpLibNameCache :: FilePath -gmpLibNameCache = shakeFilesPath -/- "gmp-lib-names" - -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 8b100b3..7122457 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -4,11 +4,7 @@ import Base import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) -import Settings.User - --- TODO: move elsewhere -gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage0/gmp" +import Settings.Paths -- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index bec143b..0513d6c 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,6 +1,7 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgGhciLibraryFile, packageConfiguration, packageConfigurationInitialised + pkgGhciLibraryFile, packageConfiguration, packageConfigurationInitialised, + gmpBuildPath, gmpLibNameCache ) where import Base @@ -47,6 +48,13 @@ packageConfiguration _ = "inplace/lib/package.conf.d" -- StageN, N > 0, share the same packageConfiguration (see above) packageConfigurationInitialised :: Stage -> FilePath -packageConfigurationInitialised stage = - shakeFilesPath -/- "package-configuration-initialised-" - ++ stageString (min stage Stage1) +packageConfigurationInitialised stage = packageConfiguration stage -/- + "package-configuration-initialised-" ++ stageString (min stage Stage1) + +-- This is the build directory for in-tree GMP library +gmpBuildPath :: FilePath +gmpBuildPath = buildRootPath -/- "stage0/gmp" + +-- GMP library names extracted from integer-gmp.buildinfo +gmpLibNameCache :: FilePath +gmpLibNameCache = gmpBuildPath -/- "gmp-lib-names" From git at git.haskell.org Thu Oct 26 23:53:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up colourisation code. (a5a2fed) Message-ID: <20171026235339.8779E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a2fed84493a7afa0942ba28a33b1ae9bc2a804/ghc >--------------------------------------------------------------- commit a5a2fed84493a7afa0942ba28a33b1ae9bc2a804 Author: Andrey Mokhov Date: Sat Jan 17 23:12:02 2015 +0000 Clean up colourisation code. >--------------------------------------------------------------- a5a2fed84493a7afa0942ba28a33b1ae9bc2a804 src/Config.hs | 6 ++---- src/Oracles/Builder.hs | 14 +++++++++----- src/Oracles/Flag.hs | 2 +- src/Util.hs | 16 ++++++++++------ 4 files changed, 22 insertions(+), 16 deletions(-) diff --git a/src/Config.hs b/src/Config.hs index dd5db2a..1a4ef9a 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -11,15 +11,13 @@ cfgPath = "shake" "cfg" autoconfRules :: Rules () autoconfRules = do "configure" %> \out -> do - need ["shake/src/Config.hs"] copyFile' (cfgPath "configure.ac") "configure.ac" - putColoured Vivid White $ "Running autoconf..." + putColoured White $ "Running autoconf..." cmd "bash autoconf" -- TODO: get rid of 'bash' configureRules :: Rules () configureRules = do cfgPath "default.config" %> \out -> do - need ["shake/src/Config.hs"] need [cfgPath "default.config.in", "configure"] - putColoured Vivid White "Running configure..." + putColoured White "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 3386b6f..13b8d7c 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -47,8 +47,8 @@ instance ShowArg Builder where GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" cfgPath <- askConfigWithDefault key $ - error $ "\nCannot find path to '" ++ key - ++ "' in configuration files." + redError $ "\nCannot find path to '" ++ key + ++ "' in configuration files." let cfgPathExe = if null cfgPath then "" else cfgPath -<.> exe windows <- windowsHost -- Note, below is different from FilePath.isAbsolute: @@ -104,20 +104,24 @@ run builder as = do -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. -- Raises an error if the builder is not uniquely specified in config files +-- TODO: make this a default 'run', rename current 'run' to verboseRun terseRun :: ShowArgs a => Builder -> a -> Action () terseRun builder as = do args <- showArgs as - putColoured Vivid White $ "/--------\n" ++ + putColoured White $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" - mapM_ (putColoured Vivid White . ("| " ++)) $ + mapM_ (putColoured White . ("| " ++)) $ interestingInfo builder args - putColoured Vivid White $ "\\--------" + putColoured White $ "\\--------" quietly $ run builder as interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of Ar -> prefixAndSuffix 2 1 ss Ld -> prefixAndSuffix 4 0 ss + Gcc -> if head ss == "-MM" + then prefixAndSuffix 1 1 ss + else ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss else prefixAndSuffix 0 4 ss diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 6339696..fa29415 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -41,7 +41,7 @@ test flag = do GhcUnregisterised -> ("ghc-unregisterised" , False) let defaultString = if defaultValue then "YES" else "NO" value <- askConfigWithDefault key $ -- TODO: warn just once - do putColoured Dull Red $ "\nFlag '" + do putColoured Red $ "\nFlag '" ++ key ++ "' not set in configuration files. " ++ "Proceeding with default value '" diff --git a/src/Util.hs b/src/Util.hs index 5bec54d..16728ce 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -3,13 +3,14 @@ module Util ( module System.Console.ANSI, replaceIf, replaceEq, replaceSeparators, chunksOfSize, - putColoured, redError + putColoured, redError, redError_ ) where import Base import Data.Char import System.Console.ANSI import System.IO +import Control.Monad replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -36,9 +37,9 @@ chunksOfSize size ss = reverse chunk : chunksOfSize size rest else (newChunk, rest) -- A more colourful version of Shake's putNormal -putColoured :: ColorIntensity -> Color -> String -> Action () -putColoured intensity colour msg = do - liftIO $ setSGR [SetColor Foreground intensity colour] +putColoured :: Color -> String -> Action () +putColoured colour msg = do + liftIO $ setSGR [SetColor Foreground Vivid colour] putNormal msg liftIO $ setSGR [] liftIO $ hFlush stdout @@ -46,5 +47,8 @@ putColoured intensity colour msg = do -- A more colourful version of error redError :: String -> Action a redError msg = do - putColoured Vivid Red msg - return $ error $ "GHC build system error: " ++ msg + putColoured Red msg + error $ "GHC build system error: " ++ msg + +redError_ :: String -> Action () +redError_ = void . redError From git at git.haskell.org Thu Oct 26 23:53:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix libCffi name on Windows (fix #89). (19310e7) Message-ID: <20171026235339.ED5823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/19310e7fbaf16190f0e206564f45f76cb6e20b61/ghc >--------------------------------------------------------------- commit 19310e7fbaf16190f0e206564f45f76cb6e20b61 Author: Andrey Mokhov Date: Mon Jan 4 20:09:33 2016 +0000 Fix libCffi name on Windows (fix #89). >--------------------------------------------------------------- 19310e7fbaf16190f0e206564f45f76cb6e20b61 src/Rules/Copy.hs | 4 +++- src/Settings/Packages/Rts.hs | 14 ++++++++++---- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index bcd1f1e..b1f9760 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -6,6 +6,7 @@ import GHC import Rules.Actions import Rules.Generate import Rules.Libffi +import Settings.Packages.Rts import Settings.TargetDirectory installTargets :: [FilePath] @@ -23,7 +24,8 @@ copyRules = do ++ "(found: " ++ show ffiHPaths ++ ")." copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih - copyFile libffiLibrary (targetPath Stage1 rts -/- "build" -/- "libCffi.a") + libffiName <- rtsLibffiLibraryName + copyFile libffiLibrary (targetPath Stage1 rts -/- "build/lib" ++ libffiName <.> "a") "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 56b0cf8..421d7f7 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,4 +1,6 @@ -module Settings.Packages.Rts (rtsPackageArgs, rtsConfIn, rtsConf) where +module Settings.Packages.Rts ( + rtsPackageArgs, rtsConfIn, rtsConf, rtsLibffiLibraryName + ) where import Base import Expression @@ -15,6 +17,11 @@ rtsConfIn = pkgPath rts -/- "package.conf.in" rtsConf :: FilePath rtsConf = targetPath Stage1 rts -/- "package.conf.inplace" +rtsLibffiLibraryName :: Action FilePath +rtsLibffiLibraryName = do + windows <- windowsHost + return $ if windows then "Cffi-6" else "Cffi" + rtsPackageArgs :: Args rtsPackageArgs = package rts ? do let yesNo = lift . fmap (\x -> if x then "YES" else "NO") @@ -36,8 +43,7 @@ rtsPackageArgs = package rts ? do way <- getWay path <- getTargetPath top <- getSetting GhcSourcePath - windows <- lift $ windowsHost - let libffiName = if windows then "ffi-6" else "ffi" + libffiName <- lift $ rtsLibffiLibraryName mconcat [ builderGcc ? mconcat [ arg "-Irts" @@ -74,7 +80,7 @@ rtsPackageArgs = package rts ? do [ arg ("-DTOP=" ++ quote top) , arg "-DFFI_INCLUDE_DIR=" , arg "-DFFI_LIB_DIR=" - , arg $ "-DFFI_LIB=" ++ quote ("C" ++ libffiName) ] ] + , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] -- #----------------------------------------------------------------------------- -- # Use system provided libffi From git at git.haskell.org Thu Oct 26 23:53:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (1c877aa) Message-ID: <20171026235343.CBDF03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c877aa89595d8d6e30f2673e8031d23cdeabdfa/ghc >--------------------------------------------------------------- commit 1c877aa89595d8d6e30f2673e8031d23cdeabdfa Merge: 4a90b33 e9013dc Author: Andrey Mokhov Date: Sat Jan 16 18:10:49 2016 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 1c877aa89595d8d6e30f2673e8031d23cdeabdfa README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:53:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add topDirectory function instead of less reliable GhcSourcePath. (5bc7a0a) Message-ID: <20171026235343.F17663A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5bc7a0ae097f038f3b04227b214a985a0c60cfbc/ghc >--------------------------------------------------------------- commit 5bc7a0ae097f038f3b04227b214a985a0c60cfbc Author: Andrey Mokhov Date: Tue Jan 5 00:53:11 2016 +0000 Add topDirectory function instead of less reliable GhcSourcePath. >--------------------------------------------------------------- 5bc7a0ae097f038f3b04227b214a985a0c60cfbc src/Builder.hs | 19 ------------------- src/Oracles/WindowsRoot.hs | 29 ++++++++++++++++++++++++++++- src/Rules/Actions.hs | 4 ++-- src/Rules/Libffi.hs | 4 ++-- src/Rules/Wrappers/Ghc.hs | 4 ++-- src/Rules/Wrappers/GhcPkg.hs | 4 ++-- src/Settings.hs | 5 ++++- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- 10 files changed, 44 insertions(+), 33 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 5bc7a0ae097f038f3b04227b214a985a0c60cfbc From git at git.haskell.org Thu Oct 26 23:52:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Integer Gmp Library to IntegerGmp (a228d2b) Message-ID: <20171026235257.0963E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a228d2b44c75b4899f12a3700b98f181e3b408ec/ghc >--------------------------------------------------------------- commit a228d2b44c75b4899f12a3700b98f181e3b408ec Author: Moritz Angermann Date: Mon Jan 4 21:05:42 2016 +0800 Adds Integer Gmp Library to IntegerGmp This should fix #88 >--------------------------------------------------------------- a228d2b44c75b4899f12a3700b98f181e3b408ec src/Rules/Dependencies.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index d604488..3a3c49a 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -2,9 +2,11 @@ module Rules.Dependencies (buildPackageDependencies) where import Base import Expression +import GHC import Oracles import Rules.Actions import Rules.Generate +import Rules.IntegerGmp import Rules.Resources import Settings import Development.Shake.Util (parseMakefile) @@ -17,6 +19,9 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = hDepFile = buildPath -/- ".hs-dependencies" in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do + -- integerGmp (cbits/wrappers.c) depends on the integerGmp library, + -- which provides gmp.h + when (pkg == integerGmp) $ need [integerGmpLibraryH] let srcFile = dropBuild . dropExtension $ out orderOnly $ generatedDependencies stage pkg need [srcFile] From git at git.haskell.org Thu Oct 26 23:52:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:52:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't track integer-gmp.buildinfo. (d684612) Message-ID: <20171026235258.BCF533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6846121743a4b61cb2cef6d57afa322b3fb6076/ghc >--------------------------------------------------------------- commit d6846121743a4b61cb2cef6d57afa322b3fb6076 Author: Andrey Mokhov Date: Fri Jan 15 16:07:28 2016 +0000 Don't track integer-gmp.buildinfo. See #173. >--------------------------------------------------------------- d6846121743a4b61cb2cef6d57afa322b3fb6076 src/Rules/Gmp.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index cfd8c53..d8cf707 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -82,18 +82,19 @@ gmpRules = do createDirectory $ takeDirectory gmpLibraryH -- We don't use system GMP on Windows. TODO: fix? + -- TODO: we do not track "config.mk" and "integer-gmp.buildinfo", see #173 windows <- windowsHost configMk <- liftIO . readFile $ gmpBase -/- "config.mk" if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - buildInfo <- readFileLines $ pkgPath integerGmp -/- "integer-gmp.buildinfo" + buildInfo <- liftIO . readFile $ pkgPath integerGmp -/- "integer-gmp.buildinfo" let prefix = "extra-libraries: " libs s = case stripPrefix prefix s of Nothing -> [] Just value -> words value - writeFileChanged gmpLibNameCache . unlines $ concatMap libs buildInfo + writeFileChanged gmpLibNameCache . unlines . concatMap libs $ lines buildInfo else do putBuild "| No GMP library/framework detected; in tree GMP will be built" writeFileChanged gmpLibNameCache "" From git at git.haskell.org Thu Oct 26 23:53:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix splitObjects function. (1b0bfa6) Message-ID: <20171026235300.A343C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b0bfa663029117b64bfc84687718dc3579119e8/ghc >--------------------------------------------------------------- commit 1b0bfa663029117b64bfc84687718dc3579119e8 Author: Andrey Mokhov Date: Thu Jan 15 18:43:25 2015 +0000 Fix splitObjects function. >--------------------------------------------------------------- 1b0bfa663029117b64bfc84687718dc3579119e8 src/Oracles/Option.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index ee8fb66..57137ba 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -81,6 +81,7 @@ splitObjects stage = do splitObjectsBroken <- test SplitObjectsBroken ghcUnregisterised <- test GhcUnregisterised return $ not splitObjectsBroken && not ghcUnregisterised + && stage == Stage1 && arch `elem` ["i386", "x86_64", "powerpc", "sparc"] && os `elem` ["mingw32", "cygwin32", "linux", "darwin", "solaris2", "freebsd", "dragonfly", "netbsd", From git at git.haskell.org Thu Oct 26 23:53:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop SUPPORTS_COMPONENT_ID which is no longer provided by configure. (72ed36f) Message-ID: <20171026235301.0DF933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72ed36f9bfb99fc239d84026945e2b47446005ed/ghc >--------------------------------------------------------------- commit 72ed36f9bfb99fc239d84026945e2b47446005ed Author: Andrey Mokhov Date: Mon Jan 4 13:14:51 2016 +0000 Drop SUPPORTS_COMPONENT_ID which is no longer provided by configure. >--------------------------------------------------------------- 72ed36f9bfb99fc239d84026945e2b47446005ed cfg/system.config.in | 1 - src/Oracles/Config/Flag.hs | 2 -- src/Settings/Builders/Ghc.hs | 13 ++++--------- 3 files changed, 4 insertions(+), 12 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 7f9b8de..292d91f 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -53,7 +53,6 @@ cc-clang-backend = @CC_CLANG_BACKEND@ # Build options: #=============== -supports-component-id = @SUPPORTS_COMPONENT_ID@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index d40b762..44e8a17 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -18,7 +18,6 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken - | SupportsComponentId | WithLibdw -- Note, if a flag is set to empty string we treat it as set to NO. This seems @@ -34,7 +33,6 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" - SupportsComponentId -> "supports-component-id" WithLibdw -> "with-libdw" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a0f2678..9a07fc2 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -84,19 +84,14 @@ wayGhcArgs = do -- TODO: Improve handling of "-hide-all-packages" packageGhcArgs :: Args packageGhcArgs = do - stage <- getStage - pkg <- getPackage - supportsComponentId <- getFlag SupportsComponentId - compId <- getPkgData ComponentId - pkgDepIds <- getPkgDataList DepIds + pkg <- getPackage + compId <- getPkgData ComponentId + pkgDepIds <- getPkgDataList DepIds mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" , bootPackageDbArgs - , isLibrary pkg ? - if supportsComponentId || stage /= Stage0 - then arg $ "-this-package-key " ++ compId - else arg $ "-package-name " ++ compId + , isLibrary pkg ? (arg $ "-this-package-key " ++ compId) , append $ map ("-package-id " ++) pkgDepIds ] -- TODO: Improve handling of "cabal_macros.h" From git at git.haskell.org Thu Oct 26 23:53:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Make builder. (ba5f163) Message-ID: <20171026235302.4D4E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba5f16377f357f009e932b1301a0e3fbcc4b8578/ghc >--------------------------------------------------------------- commit ba5f16377f357f009e932b1301a0e3fbcc4b8578 Author: Andrey Mokhov Date: Fri Jan 15 23:13:05 2016 +0000 Add Make builder. See #167. >--------------------------------------------------------------- ba5f16377f357f009e932b1301a0e3fbcc4b8578 cfg/system.config.in | 1 + src/Builder.hs | 2 ++ 2 files changed, 3 insertions(+) diff --git a/cfg/system.config.in b/cfg/system.config.in index 4539979..dfde8e3 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -36,6 +36,7 @@ ar = @ArCmd@ happy = @HappyCmd@ hscolour = @HSCOLOUR@ ld = @LdCmd@ +make = @MakeCmd@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ diff --git a/src/Builder.hs b/src/Builder.hs index 96cb608..560f734 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -38,6 +38,7 @@ data Builder = Alex | HsCpp | Hsc2Hs | Ld + | Make | Nm | Objdump | Patch @@ -81,6 +82,7 @@ builderKey builder = case builder of Hsc2Hs -> "hsc2hs" HsCpp -> "hs-cpp" Ld -> "ld" + Make -> "make" Nm -> "nm" Objdump -> "objdump" Patch -> "patch" From git at git.haskell.org Thu Oct 26 23:53:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add dependencies on argument lists. (50b8c2f) Message-ID: <20171026235304.4522B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b/ghc >--------------------------------------------------------------- commit 50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b Author: Andrey Mokhov Date: Thu Jan 15 18:43:51 2015 +0000 Add dependencies on argument lists. >--------------------------------------------------------------- 50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b src/Package.hs | 29 +++++++++--------- src/Package/Base.hs | 59 +++++++++++++++++++++++++++--------- src/Package/Compile.hs | 72 +++++++++++++++++++++---------------------- src/Package/Data.hs | 74 ++++++++++++++++++++++++++++----------------- src/Package/Dependencies.hs | 43 ++++++++++++++++++-------- src/Package/Library.hs | 62 ++++++++++++++++++++++++++----------- 6 files changed, 217 insertions(+), 122 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 50b8c2ff85d68347b5f5ee992f10e06b0f7b6c9b From git at git.haskell.org Thu Oct 26 23:53:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #91 from angerman/feature/div (bee905c) Message-ID: <20171026235305.C83EF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bee905cfbb2d0fcc048b2c7837ef307e6447acae/ghc >--------------------------------------------------------------- commit bee905cfbb2d0fcc048b2c7837ef307e6447acae Merge: 72ed36f a228d2b Author: Andrey Mokhov Date: Mon Jan 4 13:31:32 2016 +0000 Merge pull request #91 from angerman/feature/div Feature/div >--------------------------------------------------------------- bee905cfbb2d0fcc048b2c7837ef307e6447acae src/Rules/Copy.hs | 2 ++ src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 5 +++++ src/Rules/IntegerGmp.hs | 7 +++++-- 4 files changed, 13 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:53:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop makeCommand, use make detected by configure. (266461a) Message-ID: <20171026235306.5B1613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/266461a38790c86451a441db5b308341df3c6e61/ghc >--------------------------------------------------------------- commit 266461a38790c86451a441db5b308341df3c6e61 Author: Andrey Mokhov Date: Fri Jan 15 23:57:49 2016 +0000 Drop makeCommand, use make detected by configure. Fix #167. >--------------------------------------------------------------- 266461a38790c86451a441db5b308341df3c6e61 src/Rules/Actions.hs | 21 ++++++++++++++++----- src/Rules/Gmp.hs | 1 - src/Settings/User.hs | 7 +------ 3 files changed, 17 insertions(+), 12 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index a0a88ff..429f241 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -6,18 +6,18 @@ module Rules.Actions ( ) where import qualified System.Directory as IO +import System.Console.ANSI import Base import Expression import Oracles import Oracles.ArgsHash +import Oracles.Config.CmdLineFlag (buildInfo, BuildInfoFlag(..)) import Settings import Settings.Args import Settings.Builders.Ar import qualified Target -import Oracles.Config.CmdLineFlag (buildInfo, BuildInfoFlag(..)) - -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last -- built (that is, track changes in the build system). @@ -107,15 +107,26 @@ runConfigure dir opts args = do runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] + path <- builderPath Make + + -- FIXME: temporary safety net for those who are not on GHC HEAD, see #167 + fixPath <- if path == "@MakeCmd@" <.> exe + then do + putColoured Red $ "You are behind GHC HEAD, make autodetection is disabled." + return "make" + else do + needBuilder False Make + return path + let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) makeCommand ["-C", dir] args + putBuild $ "| Run " ++ fixPath ++ " " ++ note ++ " in " ++ dir ++ "..." + quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch need [file] - needBuilder False Patch + needBuilder False Patch -- TODO: add a specialised version ~needBuilderFalse? path <- builderPath Patch putBuild $ "| Apply patch " ++ file quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index d8cf707..8df337b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -109,7 +109,6 @@ gmpRules = do ++ "(found: " ++ show tarballs ++ ")." need tarballs - createDirectory gmpBuildPath build $ fullTarget gmpTarget Tar tarballs [gmpBuildPath] forM_ gmpPatches $ \src -> do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 3d08ecd..3cebe13 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors, splitObjects, makeCommand + verboseCommands, turnWarningsIntoErrors, splitObjects ) where import GHC @@ -101,8 +101,3 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False - --- | Specify which @make@ command to use, for example set to "gmake" for --- @GNU make at . -makeCommand :: FilePath -makeCommand = "make" From git at git.haskell.org Thu Oct 26 23:53:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename opts to args. (3cbaccc) Message-ID: <20171026235307.B47353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3cbacccf34dc3da2811e5a2f3e608bdd2a3cac1a/ghc >--------------------------------------------------------------- commit 3cbacccf34dc3da2811e5a2f3e608bdd2a3cac1a Author: Andrey Mokhov Date: Fri Jan 16 03:11:21 2015 +0000 Rename opts to args. >--------------------------------------------------------------- 3cbacccf34dc3da2811e5a2f3e608bdd2a3cac1a cfg/default.config.in | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index ac42e24..10ee7ee 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -34,6 +34,7 @@ supports-package-key = @SUPPORTS_PACKAGE_KEY@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ +validating = NO # Information about host and target systems: #=========================================== @@ -69,7 +70,7 @@ conf-ld-linker-args-stage-0 = @CONF_LD_LINKER_OPTS_STAGE0@ conf-ld-linker-args-stage-1 = @CONF_LD_LINKER_OPTS_STAGE1@ conf-ld-linker-args-stage-2 = @CONF_LD_LINKER_OPTS_STAGE2@ -src-hc-opts = -H32m -O +src-hc-args = -H32m -O # Include and library directories: #================================= From git at git.haskell.org Thu Oct 26 23:53:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make output boxes prettier by closing them on the right (8235f15) Message-ID: <20171026235309.9894E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8235f157b7dc6debca50cce96905ab3327b6fee1/ghc >--------------------------------------------------------------- commit 8235f157b7dc6debca50cce96905ab3327b6fee1 Author: David Luposchainsky Date: Mon Jan 4 14:38:07 2016 +0100 Make output boxes prettier by closing them on the right >--------------------------------------------------------------- 8235f157b7dc6debca50cce96905ab3327b6fee1 src/Base.hs | 42 ++++++++++++++++++++++++++++++------------ 1 file changed, 30 insertions(+), 12 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 8733282..69904c4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -172,23 +172,41 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg --- | Render the given set of lines in a ASCII box +-- | Render the given set of lines in a nice box of ASCII renderBox :: [String] -> String -renderBox ls = - unlines ([begin] ++ map (bar++) ls) ++ end +renderBox ls = concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) where - (begin,bar,end) - | useUnicode = ( "╭──────────" - , "│ " - , "╰──────────" - ) - | otherwise = ( "/----------" - , "| " - , "\\----------" - ) + -- Minimum total width of the box in characters + minimumBoxWidth = 32 + -- FIXME: See Shake #364. useUnicode = False + -- Characters to draw the box + (dash, pipe, topLeft, topRight, botLeft, botRight, padding) + | useUnicode = ('─', '│', '╭', '╮', '╰', '╯', ' ') + | otherwise = ('-', '|', '/', '\\', '\\', '/', ' ') + + -- Box width, taking minimum desired length and content into account. + -- The -4 is for the beginning and end pipe/padding symbols, as + -- in "| xxx |". + boxContentWidth = (minimumBoxWidth - 4) `max` maxContentLength + where + maxContentLength = maximum (map length ls) + + renderLine l = concat + [ [pipe, padding] + , padToLengthWith boxContentWidth padding l + , [padding, pipe] ] + where + padToLengthWith n filler x = x ++ replicate (n - length x) filler + + (boxTop, boxBot) = ( topLeft : dashes ++ [topRight] + , botLeft : dashes ++ [botRight] ) + where + -- +1 for each non-dash (= corner) char + dashes = replicate (boxContentWidth + 2) dash + -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) From git at git.haskell.org Thu Oct 26 23:53:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need make (fails on Windows). (ba74f58) Message-ID: <20171026235310.6598E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba74f58ab49363b488eef09e2b78c85302b61427/ghc >--------------------------------------------------------------- commit ba74f58ab49363b488eef09e2b78c85302b61427 Author: Andrey Mokhov Date: Sat Jan 16 00:51:33 2016 +0000 Don't need make (fails on Windows). See #167. >--------------------------------------------------------------- ba74f58ab49363b488eef09e2b78c85302b61427 src/Rules/Actions.hs | 7 +++---- src/Settings/Builders/Ghc.hs | 6 ++++-- 2 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 429f241..21d134f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -110,16 +110,15 @@ runMake dir args = do path <- builderPath Make -- FIXME: temporary safety net for those who are not on GHC HEAD, see #167 + -- TODO: add need [path] once lookupInPath is enabled on Windows fixPath <- if path == "@MakeCmd@" <.> exe then do putColoured Red $ "You are behind GHC HEAD, make autodetection is disabled." return "make" - else do - needBuilder False Make - return path + else return path let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run " ++ fixPath ++ " " ++ note ++ " in " ++ dir ++ "..." + putBuild $ "| Run " ++ fixPath ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 40b5a0f..2e40bcb 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -24,7 +24,8 @@ ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output libs <- getPkgDataList DepExtraLibs gmpLibs <- lift $ readFileLines gmpLibNameCache libDirs <- getPkgDataList DepLibDirs @@ -40,7 +41,8 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" , append =<< getInputs - , arg "-o", arg =<< getOutput ] + , buildHi ? append ["-fno-code", "-fwrite-interface"] + , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do From git at git.haskell.org Thu Oct 26 23:53:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ShowArg for single string options, clean up code. (7412fe3) Message-ID: <20171026235311.3E4BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7412fe395e6bf6708c7c58667b3f91852ff5bffa/ghc >--------------------------------------------------------------- commit 7412fe395e6bf6708c7c58667b3f91852ff5bffa Author: Andrey Mokhov Date: Fri Jan 16 03:16:59 2015 +0000 Add ShowArg for single string options, clean up code. >--------------------------------------------------------------- 7412fe395e6bf6708c7c58667b3f91852ff5bffa src/Base.hs | 5 ++- src/Config.hs | 5 +++ src/Oracles.hs | 11 +++++-- src/Oracles/Builder.hs | 31 +++++++----------- src/Oracles/Flag.hs | 11 +++---- src/Oracles/Option.hs | 85 +++++++++++++++++++++++++++----------------------- src/Util.hs | 1 + src/Ways.hs | 27 ++++++++-------- 8 files changed, 95 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 7412fe395e6bf6708c7c58667b3f91852ff5bffa From git at git.haskell.org Thu Oct 26 23:53:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #92 from quchen/closed-box (a2e9fb9) Message-ID: <20171026235313.639193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2e9fb9ef1192b41f732797f444bd9ad33c5eaf3/ghc >--------------------------------------------------------------- commit a2e9fb9ef1192b41f732797f444bd9ad33c5eaf3 Merge: bee905c 8235f15 Author: Andrey Mokhov Date: Mon Jan 4 14:18:51 2016 +0000 Merge pull request #92 from quchen/closed-box Make output boxes prettier by closing them on the right >--------------------------------------------------------------- a2e9fb9ef1192b41f732797f444bd9ad33c5eaf3 src/Base.hs | 42 ++++++++++++++++++++++++++++++------------ 1 file changed, 30 insertions(+), 12 deletions(-) From git at git.haskell.org Thu Oct 26 23:53:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Undo irrelevant changes in previous commit. (f33acd3) Message-ID: <20171026235314.072C53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f33acd3ee4d702751a4ce766efa57e02666f926a/ghc >--------------------------------------------------------------- commit f33acd3ee4d702751a4ce766efa57e02666f926a Author: Andrey Mokhov Date: Sat Jan 16 00:56:11 2016 +0000 Undo irrelevant changes in previous commit. See #167. >--------------------------------------------------------------- f33acd3ee4d702751a4ce766efa57e02666f926a src/Settings/Builders/Ghc.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 2e40bcb..40b5a0f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -24,8 +24,7 @@ ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output - buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output libs <- getPkgDataList DepExtraLibs gmpLibs <- lift $ readFileLines gmpLibNameCache libDirs <- getPkgDataList DepLibDirs @@ -41,8 +40,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" , append =<< getInputs - , buildHi ? append ["-fno-code", "-fwrite-interface"] - , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] + , arg "-o", arg =<< getOutput ] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do From git at git.haskell.org Thu Oct 26 23:53:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Version and DepNames keys to PackageData. (229d5cb) Message-ID: <20171026235314.CACF53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/229d5cbd080a7b581fce325d9cc06a553db93bc9/ghc >--------------------------------------------------------------- commit 229d5cbd080a7b581fce325d9cc06a553db93bc9 Author: Andrey Mokhov Date: Fri Jan 16 03:18:04 2015 +0000 Add Version and DepNames keys to PackageData. >--------------------------------------------------------------- 229d5cbd080a7b581fce325d9cc06a553db93bc9 src/Oracles/PackageData.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 854fb8c..e141120 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -12,12 +12,14 @@ import Util newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -data PackageData = Modules FilePath +data PackageData = Version FilePath + | Modules FilePath | SrcDirs FilePath | PackageKey FilePath | IncludeDirs FilePath | Deps FilePath | DepKeys FilePath + | DepNames FilePath | Synopsis FilePath | CppOpts FilePath | HsOpts FilePath @@ -25,12 +27,14 @@ data PackageData = Modules FilePath instance ShowArgs PackageData where showArgs packageData = do let (key, file, defaultValue) = case packageData of + Version file -> ("VERSION" , file, "" ) Modules file -> ("MODULES" , file, "" ) SrcDirs file -> ("HS_SRC_DIRS" , file, ".") PackageKey file -> ("PACKAGE_KEY" , file, "" ) IncludeDirs file -> ("INCLUDE_DIRS", file, ".") Deps file -> ("DEPS" , file, "" ) DepKeys file -> ("DEP_KEYS" , file, "" ) + DepNames file -> ("DEP_NAMES" , file, "" ) Synopsis file -> ("SYNOPSIS" , file, "" ) CppOpts file -> ("CPP_OPTS" , file, "" ) HsOpts file -> ("HC_OPTS" , file, "" ) From git at git.haskell.org Thu Oct 26 23:53:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename runGhc => runghc (e12516f) Message-ID: <20171026235317.2511B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e12516f4af9047152c7faad88635787b33d6d602/ghc >--------------------------------------------------------------- commit e12516f4af9047152c7faad88635787b33d6d602 Author: Andrey Mokhov Date: Mon Jan 4 14:41:34 2016 +0000 Rename runGhc => runghc >--------------------------------------------------------------- e12516f4af9047152c7faad88635787b33d6d602 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index 1ea0e7f..75f4305 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -79,7 +79,7 @@ pretty = library "pretty" primitive = library "primitive" process = library "process" rts = topLevel "rts" -runGhc = utility "runGhc" +runGhc = utility "runghc" stm = library "stm" templateHaskell = library "template-haskell" terminfo = library "terminfo" From git at git.haskell.org Thu Oct 26 23:53:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't rerun configure for integerGmp package. (16c89e4) Message-ID: <20171026235318.60A713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/16c89e4739ae570e6e8548ac1fe8092df6353911/ghc >--------------------------------------------------------------- commit 16c89e4739ae570e6e8548ac1fe8092df6353911 Author: Andrey Mokhov Date: Sat Jan 16 03:10:54 2016 +0000 Don't rerun configure for integerGmp package. [skip ci] >--------------------------------------------------------------- 16c89e4739ae570e6e8548ac1fe8092df6353911 src/Rules/Gmp.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 8df337b..61a0a6f 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -75,10 +75,14 @@ gmpRules = do liftIO $ removeFiles gmpBuildPath ["//*"] - -- TODO: currently we configure integerGmp package twice -- optimise - args <- configureIntGmpArguments envs <- configureEnvironment - runConfigure (pkgPath integerGmp) envs args + -- TODO: without the optimisation below we configure integerGmp package + -- twice -- think how this can be optimised (shall we solve #18 first?) + -- TODO: this is a hacky optimisation: we do not rerun configure of + -- integerGmp package if we detect the results of the previous run + unlessM (doesFileExist $ gmpBase -/- "config.mk") $ do + args <- configureIntGmpArguments + runConfigure (pkgPath integerGmp) envs args createDirectory $ takeDirectory gmpLibraryH -- We don't use system GMP on Windows. TODO: fix? From git at git.haskell.org Thu Oct 26 23:53:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Targets.hs for specifying targets, clean up code. (7ffb294) Message-ID: <20171026235318.DE09C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ffb2940272c99938582846879e2f297215c3211/ghc >--------------------------------------------------------------- commit 7ffb2940272c99938582846879e2f297215c3211 Author: Andrey Mokhov Date: Fri Jan 16 04:02:01 2015 +0000 Add Targets.hs for specifying targets, clean up code. >--------------------------------------------------------------- 7ffb2940272c99938582846879e2f297215c3211 src/Package.hs | 29 +++++----- src/Package/Base.hs | 67 +++++++++++------------ src/Package/Compile.hs | 36 ++++++------- src/Package/Data.hs | 127 +++++++++++++++++++++++++------------------- src/Package/Dependencies.hs | 20 +++---- src/Package/Library.hs | 24 +++++---- src/Targets.hs | 25 +++++++++ 7 files changed, 183 insertions(+), 145 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 7ffb2940272c99938582846879e2f297215c3211 From git at git.haskell.org Thu Oct 26 23:53:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to src/Rules/IntegerGmp.hs. (c4cbb3a) Message-ID: <20171026235321.00C363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4cbb3a8691851628159ae8f7058efed9f5f8a0a/ghc >--------------------------------------------------------------- commit c4cbb3a8691851628159ae8f7058efed9f5f8a0a Author: Andrey Mokhov Date: Mon Jan 4 16:25:47 2016 +0000 Fix path to src/Rules/IntegerGmp.hs. >--------------------------------------------------------------- c4cbb3a8691851628159ae8f7058efed9f5f8a0a src/Rules/IntegerGmp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index f927102..9bbf482 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -50,7 +50,7 @@ configureArguments = do integerGmpRules :: Rules () integerGmpRules = do integerGmpLibrary %> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules" -/- "integerGmp.hs"] + when trackBuildSystem $ need [sourcePath -/- "Rules/IntegerGmp.hs"] -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] From git at git.haskell.org Thu Oct 26 23:53:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for separate interface file compilation. (6b532ba) Message-ID: <20171026235322.A182D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b532baa0dd71e5c61229c0be832d871bf0bf705/ghc >--------------------------------------------------------------- commit 6b532baa0dd71e5c61229c0be832d871bf0bf705 Author: Andrey Mokhov Date: Sat Jan 16 03:11:31 2016 +0000 Add support for separate interface file compilation. See #174. >--------------------------------------------------------------- 6b532baa0dd71e5c61229c0be832d871bf0bf705 src/Rules/Compile.hs | 16 ++++++++++++++-- src/Settings/Builders/Ghc.hs | 15 +++++++++------ src/Settings/User.hs | 7 ++++++- 3 files changed, 29 insertions(+), 9 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 2fb315c..2065415 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,10 +12,22 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let buildPath = targetPath stage pkg -/- "build" matchBuildResult buildPath "hi" ?> \hi -> - need [ hi -<.> osuf (detectWay hi) ] + if compileInterfaceFilesSeparately + then do + let way = detectWay hi + (src, deps) <- dependencies buildPath $ hi -<.> osuf way + need $ src : deps + build $ fullTargetWithWay target (Ghc stage) way [src] [hi] + else need [ hi -<.> osuf (detectWay hi) ] matchBuildResult buildPath "hi-boot" ?> \hiboot -> - need [ hiboot -<.> obootsuf (detectWay hiboot) ] + if compileInterfaceFilesSeparately + then do + let way = detectWay hiboot + (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf way + need $ src : deps + build $ fullTargetWithWay target (Ghc stage) way [src] [hiboot] + else need [ hiboot -<.> obootsuf (detectWay hiboot) ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) matchBuildResult buildPath "o" ?> \obj -> do diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 40b5a0f..0f1fc32 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -24,7 +24,9 @@ ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output + buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs gmpLibs <- lift $ readFileLines gmpLibNameCache libDirs <- getPkgDataList DepLibDirs @@ -35,12 +37,13 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , not buildObj ? arg "-no-auto-link-packages" - , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] - , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] - , buildObj ? arg "-c" + , buildProg ? arg "-no-auto-link-packages" + , buildProg ? append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] + , buildProg ? append [ "-optl-L" ++ dir | dir <- libDirs ] + , not buildProg ? arg "-c" , append =<< getInputs - , arg "-o", arg =<< getOutput ] + , buildHi ? append ["-fno-code", "-fwrite-interface"] + , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 3cebe13..5b82571 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,8 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors, splitObjects + verboseCommands, turnWarningsIntoErrors, splitObjects, + compileInterfaceFilesSeparately ) where import GHC @@ -101,3 +102,7 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False + +-- | Decouple the compilation of @*.hi@ and @*.o@ files by setting to True. +compileInterfaceFilesSeparately :: Bool +compileInterfaceFilesSeparately = True From git at git.haskell.org Thu Oct 26 23:53:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add DependencyList oracle. (a644c32) Message-ID: <20171026235343.F10063A5EC@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a644c3216b42e6a371f61b2e142df74cf457f51c/ghc >--------------------------------------------------------------- commit a644c3216b42e6a371f61b2e142df74cf457f51c Author: Andrey Mokhov Date: Sat Jan 17 23:13:04 2015 +0000 Add DependencyList oracle. >--------------------------------------------------------------- a644c3216b42e6a371f61b2e142df74cf457f51c src/Oracles.hs | 47 +++++++++++++++++++++++++++++++------------ src/Oracles/DependencyList.hs | 20 ++++++++++++++++++ 2 files changed, 54 insertions(+), 13 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 9ac6191..4c6d9e9 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -4,11 +4,14 @@ module Oracles ( module Oracles.Option, module Oracles.Builder, module Oracles.PackageData, + module Oracles.DependencyList, oracleRules ) where import Development.Shake.Config +import Development.Shake.Util import qualified Data.HashMap.Strict as M +import Data.Bifunctor import Base import Util import Config @@ -17,49 +20,67 @@ import Oracles.Flag import Oracles.Option import Oracles.Builder import Oracles.PackageData +import Oracles.DependencyList defaultConfig, userConfig :: FilePath defaultConfig = cfgPath "default.config" userConfig = cfgPath "user.config" --- Oracle for configuration files. +-- Oracle for configuration files configOracle :: Rules () configOracle = do cfg <- newCache $ \() -> do - unless (doesFileExist $ defaultConfig <.> "in") $ do - error $ "\nDefault configuration file '" - ++ (defaultConfig <.> "in") - ++ "' is missing; unwilling to proceed." - return () + unless (doesFileExist $ defaultConfig <.> "in") $ + redError_ $ "\nDefault configuration file '" + ++ (defaultConfig <.> "in") + ++ "' is missing; unwilling to proceed." need [defaultConfig] - putNormal $ "Parsing " ++ toStandard defaultConfig ++ "..." + putOracle $ "Parsing " ++ toStandard defaultConfig ++ "..." cfgDefault <- liftIO $ readConfigFile defaultConfig existsUser <- doesFileExist userConfig cfgUser <- if existsUser then do - putNormal $ "Parsing " + putOracle $ "Parsing " ++ toStandard userConfig ++ "..." liftIO $ readConfigFile userConfig else do - putColoured Dull Red $ + putColoured Red $ "\nUser defined configuration file '" ++ userConfig ++ "' is missing; " ++ "proceeding with default configuration.\n" return M.empty - putColoured Vivid Green $ "Finished processing configuration files." + putColoured Green $ "Finished processing configuration files." return $ cfgUser `M.union` cfgDefault addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () return () --- Oracle for 'package-data.mk' files. +-- Oracle for 'package-data.mk' files packageDataOracle :: Rules () packageDataOracle = do pkgData <- newCache $ \file -> do need [file] - putNormal $ "Parsing " ++ toStandard file ++ "..." + putOracle $ "Parsing " ++ toStandard file ++ "..." liftIO $ readConfigFile file addOracle $ \(PackageDataKey (file, key)) -> M.lookup key <$> pkgData file return () +-- Oracle for 'path/dist/*.deps' files +dependencyOracle :: Rules () +dependencyOracle = do + deps <- newCache $ \depFile -> do + need [depFile] + putOracle $ "Parsing " ++ toStandard depFile ++ "..." + contents <- parseMakefile <$> (liftIO $ readFile depFile) + return $ M.fromList + $ map (bimap head concat . unzip) + $ groupBy ((==) `on` fst) + $ sortBy (compare `on` fst) contents + addOracle $ \(DependencyListKey (file, obj)) -> M.lookup obj <$> deps file + return () + oracleRules :: Rules () -oracleRules = configOracle <> packageDataOracle +oracleRules = configOracle <> packageDataOracle <> dependencyOracle + +-- Make oracle's output more distinguishable +putOracle :: String -> Action () +putOracle = putColoured Blue diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs new file mode 100644 index 0000000..8f4eda1 --- /dev/null +++ b/src/Oracles/DependencyList.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} + +module Oracles.DependencyList ( + DependencyList (..), + DependencyListKey (..) + ) where + +import Development.Shake.Classes +import Base +import Data.Maybe + +data DependencyList = DependencyList FilePath FilePath + +newtype DependencyListKey = DependencyListKey (FilePath, FilePath) + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +instance ShowArgs DependencyList where + showArgs (DependencyList file obj) = do + res <- askOracle $ DependencyListKey (file, obj) + return $ fromMaybe [] res From git at git.haskell.org Thu Oct 26 23:53:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (f5dff68) Message-ID: <20171026235347.A170B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5dff684386aaec9ed079364423524c91b5be2cd/ghc >--------------------------------------------------------------- commit f5dff684386aaec9ed079364423524c91b5be2cd Author: Andrey Mokhov Date: Sat Jan 16 23:56:57 2016 +0000 Minor revision. [skip ci] >--------------------------------------------------------------- f5dff684386aaec9ed079364423524c91b5be2cd src/Predicates.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 497fca5..1e56993 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -9,15 +9,15 @@ import Expression -- | Is the build currently in the provided stage? stage :: Stage -> Predicate -stage s = fmap (s ==) getStage +stage s = (s ==) <$> getStage -- | Is a particular package being built? package :: Package -> Predicate -package p = fmap (p ==) getPackage +package p = (p ==) <$> getPackage -- | Is an unstaged builder is being used such as /GhcCabal/? builder :: Builder -> Predicate -builder b = fmap (b ==) getBuilder +builder b = (b ==) <$> getBuilder -- | Is a certain builder used in the current stage? stagedBuilder :: (Stage -> Builder) -> Predicate @@ -35,11 +35,11 @@ builderGhc = stagedBuilder Ghc ||^ stagedBuilder GhcM -- | Does any of the output files match a given pattern? file :: FilePattern -> Predicate -file f = fmap (any (f ?==)) getOutputs +file f = any (f ?==) <$> getOutputs -- | Is the current build 'Way' equal to a certain value? way :: Way -> Predicate -way w = fmap (w ==) getWay +way w = (w ==) <$> getWay -- | Is the build currently in stage 0? stage0 :: Predicate From git at git.haskell.org Thu Oct 26 23:53:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CcArgs and CSrcs keys to PackageData. (316d98e) Message-ID: <20171026235348.61E2B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/316d98ef5bf6a5e43c649f5a7269661ff304be96/ghc >--------------------------------------------------------------- commit 316d98ef5bf6a5e43c649f5a7269661ff304be96 Author: Andrey Mokhov Date: Sat Jan 17 23:14:03 2015 +0000 Add CcArgs and CSrcs keys to PackageData. >--------------------------------------------------------------- 316d98ef5bf6a5e43c649f5a7269661ff304be96 src/Oracles/PackageData.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 192896c..0581e82 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -31,6 +31,8 @@ data MultiPackageData = Modules FilePath | DepNames FilePath | CppArgs FilePath | HsArgs FilePath + | CcArgs FilePath + | CSrcs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -59,6 +61,8 @@ instance ShowArgs MultiPackageData where DepNames path -> ("DEP_NAMES" , path, "" ) CppArgs path -> ("CPP_OPTS" , path, "" ) HsArgs path -> ("HC_OPTS" , path, "" ) + CcArgs path -> ("CC_OPTS" , path, "" ) + CSrcs path -> ("C_SRCS" , path, "" ) fullKey = replaceSeparators '_' $ path ++ "_" ++ key pkgData = path "package-data.mk" res <- askOracle $ PackageDataKey (pkgData, fullKey) From git at git.haskell.org Thu Oct 26 23:53:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop ghcPwd package, we no longer build it. (9050f37) Message-ID: <20171026235348.743D03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9050f373671103cd80336e19880a7c14fd7920ab/ghc >--------------------------------------------------------------- commit 9050f373671103cd80336e19880a7c14fd7920ab Author: Andrey Mokhov Date: Tue Jan 5 00:56:31 2016 +0000 Drop ghcPwd package, we no longer build it. >--------------------------------------------------------------- 9050f373671103cd80336e19880a7c14fd7920ab src/GHC.hs | 17 ++++++++--------- src/Settings/Packages.hs | 2 +- 2 files changed, 9 insertions(+), 10 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 75f4305..d4d5511 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -2,8 +2,8 @@ module GHC ( array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, - ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, + haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, @@ -25,16 +25,16 @@ defaultKnownPackages = [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes , deepseq, deriveConstants, directory, dllSplit, filepath, genapply , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim - , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin - , integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel - , pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo - , time, transformers, unix, win32, xhtml ] + , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp + , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty + , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time + , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, - ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, + haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package @@ -60,7 +60,6 @@ ghcCabal = utility "ghc-cabal" ghci = library "ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" -ghcPwd = utility "ghc-pwd" ghcTags = utility "ghctags" haddock = utility "haddock" haskeline = library "haskeline" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 10ed9e1..dba4054 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -31,7 +31,7 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq - , directory, filepath, ghci, ghcPrim, ghcPwd, haskeline, hpcBin + , directory, filepath, ghci, ghcPrim, haskeline, hpcBin , integerLibrary, mkUserGuidePart, pretty, process, rts, runGhc , time ] , windowsHost ? append [win32] From git at git.haskell.org Thu Oct 26 23:53:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor ways, revise comments. (3ff1fc1) Message-ID: <20171026235351.827C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ff1fc1097d98f17ab081be3c9f1379bea69d04a/ghc >--------------------------------------------------------------- commit 3ff1fc1097d98f17ab081be3c9f1379bea69d04a Author: Andrey Mokhov Date: Sat Jan 16 23:58:20 2016 +0000 Refactor ways, revise comments. See #100. >--------------------------------------------------------------- 3ff1fc1097d98f17ab081be3c9f1379bea69d04a src/Rules/Program.hs | 2 +- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/User.hs | 24 +++++++++++++----------- src/Settings/Ways.hs | 33 +++++++++++++++------------------ src/Way.hs | 1 + 6 files changed, 32 insertions(+), 32 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 93a6d6c..d472e88 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -77,7 +77,7 @@ buildBinary target @ (PartialTarget stage pkg) bin = do ++ [ buildPath -/- "Paths_hsc2hs.o" | pkg == hsc2hs ] ++ [ buildPath -/- "Paths_haddock.o" | pkg == haddock ] objs = cObjs ++ hObjs - ways <- interpretPartial target getWays + ways <- interpretPartial target getLibraryWays depNames <- interpretPartial target $ getPkgDataList TransitiveDepNames let libStage = min stage Stage1 -- libraries are built only in Stage0/1 libTarget = PartialTarget libStage pkg diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index c97cd56..3537aed 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -48,7 +48,7 @@ splitObjectsArgs = splitObjects ? do ghcMBuilderArgs :: Args ghcMBuilderArgs = stagedBuilder GhcM ? do - ways <- getWays + ways <- getLibraryWays mconcat [ arg "-M" , commonGhcArgs , arg "-include-pkg-deps" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 8591bd5..afd3def 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -49,7 +49,7 @@ ghcCabalHsColourBuilderArgs = builder GhcCabalHsColour ? do -- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do - ways <- getWays + ways <- getLibraryWays withGhci <- lift ghcWithInterpreter append [ if vanilla `elem` ways then "--enable-library-vanilla" diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 2a1471d..f57a2ac 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,6 +1,6 @@ module Settings.User ( buildRootPath, userTargetDirectory, userProgramPath, trackBuildSystem, - userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, + userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, verboseCommands, turnWarningsIntoErrors, splitObjects, @@ -36,24 +36,26 @@ userPackages = mempty userKnownPackages :: [Package] userKnownPackages = [] --- Control which ways libraries and rts are built --- TODO: skip profiling for speed, skip dynamic since it's currently broken -userLibWays :: Ways -userLibWays = remove [profiling, dynamic] +-- | Control which ways library packages are built +-- FIXME: skip profiling for speed +-- FIXME: skip dynamic since it's currently broken #4 +userLibraryWays :: Ways +userLibraryWays = remove [profiling, dynamic] +-- | Control which ways the 'rts' package is built userRtsWays :: Ways userRtsWays = mempty --- Choose integer library: integerGmp, integerGmp2 or integerSimple +-- | Choose the integer library: integerGmp or integerSimple integerLibrary :: Package integerLibrary = integerGmp --- User-defined flags. Note the following type semantics: +-- | User-defined flags. Note the following type semantics: -- * Bool: a plain Boolean flag whose value is known at compile time -- * Action Bool: a flag whose value can depend on the build environment -- * Predicate: a flag depending on the build environment and the current target --- Set this to True if you are making any changes in the build system and want +-- | Set this to True if you are making any changes in the build system and want -- appropriate rebuilds to be initiated. Switching this to False speeds things -- up a little (particularly zero builds). -- WARNING: a complete rebuild is required when changing this setting. @@ -80,7 +82,7 @@ ghcProfiled = False ghcDebugged :: Bool ghcDebugged = False --- When laxDependencies flag is set to True, dependencies on the GHC executable +-- | When laxDependencies is set to True, dependencies on the GHC executable -- are turned into order-only dependencies to avoid needless recompilation when -- making changes to GHC's sources. In certain situations this can lead to build -- failures, in which case you should reset the flag (at least temporarily). @@ -93,8 +95,8 @@ buildHaddock = return False -- FIXME: should be return True, see #98 buildSystemConfigFile :: Bool buildSystemConfigFile = False --- Set to True to print full command lines during the build process. Note, this --- is a Predicate, hence you can enable verbose output for a chosen package +-- | Set to True to print full command lines during the build process. Note, +-- this is a Predicate, hence you can enable verbose output for a chosen package -- only, e.g.: verboseCommands = package ghcPrim verboseCommands :: Predicate verboseCommands = return False diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 8376213..223bc79 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,34 +1,31 @@ -module Settings.Ways (getWays, getLibWays, getRtsWays) where +module Settings.Ways (getLibraryWays, getRtsWays) where -import Data.Monoid +import Base import Expression import Predicates import Settings.User import Oracles.Config.Flag --- TODO: use a single expression Ways parameterised by package instead of --- expressions libWays and rtsWays - --- Combining default ways with user modifications -getLibWays :: Expr [Way] -getLibWays = fromDiffExpr $ defaultLibWays <> userLibWays - --- In Stage0 we only build vanilla -getWays :: Expr [Way] -getWays = mconcat [ stage0 ? return [vanilla], notStage0 ? getLibWays ] +-- | Combine default ways with user modifications +getLibraryWays :: Expr [Way] +getLibraryWays = fromDiffExpr $ defaultLibraryWays <> userLibraryWays getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays --- These are default ways -defaultLibWays :: Ways -defaultLibWays = mconcat - [ append [vanilla, profiling] - , platformSupportsSharedLibs ? append [dynamic] ] +-- These are default ways for library packages: +-- * We always build 'vanilla' way. +-- * We build 'profiling' way when stage > Stage0. +-- * We build 'dynamic' way when stage > Stage0 and the platform supports it. +defaultLibraryWays :: Ways +defaultLibraryWays = mconcat + [ append [vanilla] + , notStage0 ? append [profiling] + , notStage0 ? platformSupportsSharedLibs ? append [dynamic] ] defaultRtsWays :: Ways defaultRtsWays = do - ways <- getLibWays + ways <- getLibraryWays mconcat [ append [ logging, debug, threaded, threadedDebug, threadedLogging ] , (profiling `elem` ways) ? append [threadedProfiling] diff --git a/src/Way.hs b/src/Way.hs index ba20bd7..8923571 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -101,6 +101,7 @@ granSim = wayFromUnits [GranSim] -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? +-- See compiler/main/DynFlags.hs. threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, threadedDynamic, threadedDebugDynamic, From git at git.haskell.org Thu Oct 26 23:53:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix a loop in generated dependencies. (e651350) Message-ID: <20171026235352.584113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e6513507c7e75050ba93724d8d7e79ecf6adf146/ghc >--------------------------------------------------------------- commit e6513507c7e75050ba93724d8d7e79ecf6adf146 Author: Andrey Mokhov Date: Tue Jan 5 01:26:02 2016 +0000 Fix a loop in generated dependencies. >--------------------------------------------------------------- e6513507c7e75050ba93724d8d7e79ecf6adf146 src/Rules/Dependencies.hs | 4 ++-- src/Rules/Generate.hs | 31 ++++++++++++++++++------------- src/Settings/Builders/DeriveConstants.hs | 2 +- 3 files changed, 21 insertions(+), 16 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index b0dd474..5b51c1d 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -18,13 +18,13 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do let srcFile = dropBuild . dropExtension $ out - orderOnly $ generatedDependencies stage + orderOnly $ generatedDependencies stage pkg need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - orderOnly $ generatedDependencies stage + orderOnly $ generatedDependencies stage pkg need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 140c978..13d5806 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -33,21 +33,20 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -derivedConstantsDependencies :: [FilePath] -derivedConstantsDependencies = (derivedConstantsPath -/-) <$> [] - -- [ "DerivedConstants.h" - -- , "GHCConstantsHaskellType.hs" - -- , "GHCConstantsHaskellWrappers.hs" - -- , "GHCConstantsHaskellExports.hs" ] - libffiDependencies :: [FilePath] libffiDependencies = (targetPath Stage1 rts -/-) <$> [ "build/ffi.h" , "build/ffitarget.h" ] defaultDependencies :: [FilePath] -defaultDependencies = - includesDependencies ++ derivedConstantsDependencies ++ libffiDependencies +defaultDependencies = includesDependencies ++ libffiDependencies + +derivedConstantsDependencies :: [FilePath] +derivedConstantsDependencies = (derivedConstantsPath -/-) <$> + [ "DerivedConstants.h" + , "GHCConstantsHaskellType.hs" + , "GHCConstantsHaskellWrappers.hs" + , "GHCConstantsHaskellExports.hs" ] compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = @@ -69,12 +68,18 @@ compilerDependencies stage = , "primop-vector-tys-exports.hs-incl" , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] + ++ + if stage == Stage0 + then defaultDependencies ++ derivedConstantsDependencies + else [] + -- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? --- TODO: improve -generatedDependencies :: Stage -> [FilePath] -generatedDependencies stage - | stage == Stage1 = defaultDependencies ++ compilerDependencies stage +generatedDependencies :: Stage -> Package -> [FilePath] +generatedDependencies stage pkg + | pkg == compiler = compilerDependencies stage + | stage == Stage0 = defaultDependencies + | stage == Stage1 = derivedConstantsDependencies | otherwise = [] -- The following generators and corresponding source extensions are supported: diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 65c6c53..6f4828a 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -33,7 +33,7 @@ deriveConstantsBuilderArgs = builder DeriveConstants ? do includeCcArgs :: Args includeCcArgs = do - confCcArgs <- lift . settingList $ ConfCcArgs Stage1 + confCcArgs <- getSettingList $ ConfCcArgs Stage1 mconcat [ cArgs , cWarnings From git at git.haskell.org Thu Oct 26 23:53:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for c source files. (debca7a) Message-ID: <20171026235352.71C3D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/debca7ade35a75b7d5947f0abeb3a9a190d2e0f7/ghc >--------------------------------------------------------------- commit debca7ade35a75b7d5947f0abeb3a9a190d2e0f7 Author: Andrey Mokhov Date: Sat Jan 17 23:14:40 2015 +0000 Add support for c source files. >--------------------------------------------------------------- debca7ade35a75b7d5947f0abeb3a9a190d2e0f7 src/Package/Base.hs | 32 +++++++++++++-------- src/Package/Compile.hs | 49 ++++++++++++++++++++++++------- src/Package/Dependencies.hs | 70 +++++++++++++++++++++++++++++++++++++++------ src/Package/Library.hs | 29 ++++++++++--------- src/Targets.hs | 36 +++++++++++------------ src/Ways.hs | 1 + 6 files changed, 154 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc debca7ade35a75b7d5947f0abeb3a9a190d2e0f7 From git at git.haskell.org Thu Oct 26 23:53:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Further work on #174. (1300254) Message-ID: <20171026235355.ADEFA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/130025463ea2a8b50decceae44c2618198466acd/ghc >--------------------------------------------------------------- commit 130025463ea2a8b50decceae44c2618198466acd Author: Andrey Mokhov Date: Sun Jan 17 03:01:26 2016 +0000 Further work on #174. >--------------------------------------------------------------- 130025463ea2a8b50decceae44c2618198466acd src/Rules/Compile.hs | 14 ++++++++++---- src/Settings/Packages/RunGhc.hs | 2 +- 2 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 2065415..b27d36e 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,7 +12,7 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let buildPath = targetPath stage pkg -/- "build" matchBuildResult buildPath "hi" ?> \hi -> - if compileInterfaceFilesSeparately + if compileInterfaceFilesSeparately && not ("//HpcParser.*" ?== hi) then do let way = detectWay hi (src, deps) <- dependencies buildPath $ hi -<.> osuf way @@ -32,16 +32,22 @@ compilePackage _ target @ (PartialTarget stage pkg) = do -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) matchBuildResult buildPath "o" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need $ src : deps if ("//*.c" ?== src) - then build $ fullTarget target (Gcc stage) [src] [obj] + then do + need $ src : deps + build $ fullTarget target (Gcc stage) [src] [obj] else do let way = detectWay obj + if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) + then need $ (obj -<.> hisuf (detectWay obj)) : src : deps + else need $ src : deps build $ fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases matchBuildResult buildPath "o-boot" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need $ src : deps let way = detectWay obj + if compileInterfaceFilesSeparately + then need $ (obj -<.> hibootsuf (detectWay obj)) : src : deps + else need $ src : deps build $ fullTargetWithWay target (Ghc stage) way [src] [obj] diff --git a/src/Settings/Packages/RunGhc.hs b/src/Settings/Packages/RunGhc.hs index 37cdb95..e982fe6 100644 --- a/src/Settings/Packages/RunGhc.hs +++ b/src/Settings/Packages/RunGhc.hs @@ -9,5 +9,5 @@ runGhcPackageArgs :: Args runGhcPackageArgs = package runGhc ? do version <- getSetting ProjectVersion mconcat [ builderGhc ? - file "//Main.o" ? + file "//Main.*" ? append ["-cpp", "-DVERSION=\"" ++ version ++ "\""] ] From git at git.haskell.org Thu Oct 26 23:53:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Another tweak of generated dependencies. (ba41ec6) Message-ID: <20171026235356.464993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba41ec6a9b2db3708b1076fef2c4391d4887875d/ghc >--------------------------------------------------------------- commit ba41ec6a9b2db3708b1076fef2c4391d4887875d Author: Andrey Mokhov Date: Tue Jan 5 01:54:50 2016 +0000 Another tweak of generated dependencies. >--------------------------------------------------------------- ba41ec6a9b2db3708b1076fef2c4391d4887875d src/Rules/Generate.hs | 43 ++++++++++++++++++------------------------- 1 file changed, 18 insertions(+), 25 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 13d5806..6a4270b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -51,35 +51,28 @@ derivedConstantsDependencies = (derivedConstantsPath -/-) <$> compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = [ platformH stage ] - ++ - fmap ((targetPath stage compiler -/- "build") -/-) - [ "primop-vector-uniques.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" - , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] - ++ - if stage == Stage0 - then defaultDependencies ++ derivedConstantsDependencies - else [] - - --- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? + ++ defaultDependencies ++ derivedConstantsDependencies + ++ fmap ((targetPath stage compiler -/- "build") -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] + generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | stage == Stage0 = defaultDependencies - | stage == Stage1 = derivedConstantsDependencies | otherwise = [] -- The following generators and corresponding source extensions are supported: From git at git.haskell.org Thu Oct 26 23:53:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename includeHcArgs to includeGhcArgs. (734994c) Message-ID: <20171026235356.975D03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/734994cf18ee377472128ceab7ad6ef1f8773684/ghc >--------------------------------------------------------------- commit 734994cf18ee377472128ceab7ad6ef1f8773684 Author: Andrey Mokhov Date: Sat Jan 17 23:31:52 2015 +0000 Rename includeHcArgs to includeGhcArgs. >--------------------------------------------------------------- 734994cf18ee377472128ceab7ad6ef1f8773684 src/Package/Base.hs | 6 +++--- src/Package/Compile.hs | 2 +- src/Package/Dependencies.hs | 6 +----- 3 files changed, 5 insertions(+), 9 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 0b053e8..9d75e04 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -7,7 +7,7 @@ module Package.Base ( Package (..), Settings (..), TodoItem (..), defaultSettings, libraryPackage, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - pathArgs, packageArgs, includeHcArgs, pkgHsSources, + pathArgs, packageArgs, includeGhcArgs, pkgHsSources, pkgDepHsObjects, pkgLibHsObjects, pkgCObjects, argSizeLimit, sourceDependecies, @@ -92,8 +92,8 @@ packageArgs stage pathDist = do else productArgs "-package-name" (arg $ PackageKey pathDist) <> productArgs "-package" (args $ Deps pathDist) ] -includeHcArgs :: FilePath -> FilePath -> Args -includeHcArgs path dist = +includeGhcArgs :: FilePath -> FilePath -> Args +includeGhcArgs path dist = let pathDist = path dist buildDir = toStandard $ pathDist "build" in args [ arg "-i" diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 0c25ae8..8052356 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -18,7 +18,7 @@ ghcArgs (Package _ path _) (stage, dist, _) way srcs result = , wayHcArgs way , args SrcHcArgs , packageArgs stage pathDist - , includeHcArgs path dist + , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist , args $ HsArgs pathDist -- TODO: now we have both -O and -O2 diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 7378f20..7301051 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -13,7 +13,7 @@ ghcArgs (Package name path _) (stage, dist, settings) = depFile = buildDir "haskell.deps" in args [ arg "-M" , packageArgs stage pathDist - , includeHcArgs path dist + , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist , productArgs ["-odir", "-stubdir", "-hidir"] buildDir , args ["-dep-makefile", depFile <.> "new"] @@ -21,10 +21,6 @@ ghcArgs (Package name path _) (stage, dist, settings) = , args $ HsArgs pathDist , args $ pkgHsSources path dist ] --- $(CPP) $($1_$2_MKDEPENDC_OPTS) --- $($1_$2_$(firstword $($1_$2_WAYS))_ALL_CC_OPTS) --- $($(basename $4)_CC_OPTS) -MM -x c $4 -MF $3.bit --- -- $1_$2_$3_ALL_CC_OPTS = \ -- $$(WAY_$3_CC_OPTS) \ -- $$($1_$2_DIST_GCC_CC_OPTS) \ From git at git.haskell.org Thu Oct 26 23:53:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix handling of FFI library configure params (6abfdfa) Message-ID: <20171026235359.3ED703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6abfdfaec035057a956ded2dad8695c4c600e24c/ghc >--------------------------------------------------------------- commit 6abfdfaec035057a956ded2dad8695c4c600e24c Author: Karel Gardas Date: Sun Jan 17 22:55:57 2016 +0100 fix handling of FFI library configure params >--------------------------------------------------------------- 6abfdfaec035057a956ded2dad8695c4c600e24c cfg/system.config.in | 3 ++ src/Oracles/Config/Setting.hs | 6 +++ src/Rules/Libffi.hs | 87 ++++++++++++++++++++++++------------------- src/Settings/Packages/Rts.hs | 8 +++- 4 files changed, 65 insertions(+), 39 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index dfde8e3..ecbf18d 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -127,6 +127,9 @@ iconv-lib-dirs = @ICONV_LIB_DIRS@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ +use-system-ffi = @UseSystemLibFFI@ +ffi-include-dirs = @FFIIncludeDir@ +ffi-lib-dirs = @FFILibDir@ # Optional Dependencies: #======================= diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 46d0d33..7b5d71e 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -47,6 +47,7 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor + | UseSystemFfi data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -57,6 +58,8 @@ data SettingList = ConfCcArgs Stage | HsCppArgs | IconvIncludeDirs | IconvLibDirs + | FfiIncludeDirs + | FfiLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of @@ -88,6 +91,7 @@ setting key = askConfig $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" + UseSystemFfi -> "use-system-ffi" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -100,6 +104,8 @@ settingList key = fmap words $ askConfig $ case key of HsCppArgs -> "hs-cpp-args" IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" + FfiIncludeDirs -> "ffi-include-dirs" + FfiLibDirs -> "ffi-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index dbf50dc..5f23cad 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,44 +70,55 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - removeDirectory libffiBuild - createDirectory $ buildRootPath -/- stageString Stage0 - - tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - when (length tarballs /= 1) $ - putError $ "libffiRules: exactly one libffi tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - - need tarballs - let libname = dropExtension . dropExtension . takeFileName $ head tarballs - - removeDirectory (buildRootPath -/- libname) - actionFinally (do - build $ fullTarget libffiTarget Tar tarballs [buildRootPath] - moveDirectory (buildRootPath -/- libname) libffiBuild) $ - removeFiles buildRootPath [libname "*"] - - fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile - - forM_ ["config.guess", "config.sub"] $ \file -> - copyFile file (libffiBuild -/- file) - - envs <- configureEnvironment - args <- configureArguments - runConfigure libffiBuild envs args - - runMake libffiBuild ["MAKEFLAGS="] - runMake libffiBuild ["MAKEFLAGS=", "install"] - - forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file - copyFile src (rtsBuildPath -/- file) - - libffiName <- rtsLibffiLibraryName - copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") - - putSuccess $ "| Successfully built custom library 'libffi'" + use_system_ffi <- setting UseSystemFfi + ffi_header_dirs <- settingList FfiIncludeDirs + if use_system_ffi == "YES" + then do + putBuild "| System supplied FFI library will be used" + let ffi_header_dir = head ffi_header_dirs + forM_ ["ffi.h", "ffitarget.h"] $ \file -> do + let src = ffi_header_dir -/- file + copyFile src (rtsBuildPath -/- file) + putSuccess $ "| Successfully copied system supplied FFI library header files" + else do + when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] + removeDirectory libffiBuild + createDirectory $ buildRootPath -/- stageString Stage0 + + tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] + when (length tarballs /= 1) $ + putError $ "libffiRules: exactly one libffi tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + + need tarballs + let libname = dropExtension . dropExtension . takeFileName $ head tarballs + + removeDirectory (buildRootPath -/- libname) + actionFinally (do + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] + + fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile + + forM_ ["config.guess", "config.sub"] $ \file -> + copyFile file (libffiBuild -/- file) + + envs <- configureEnvironment + args <- configureArguments + runConfigure libffiBuild envs args + + runMake libffiBuild ["MAKEFLAGS="] + runMake libffiBuild ["MAKEFLAGS=", "install"] + + forM_ ["ffi.h", "ffitarget.h"] $ \file -> do + let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file + copyFile src (rtsBuildPath -/- file) + + libffiName <- rtsLibffiLibraryName + copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") + + putSuccess $ "| Successfully built custom library 'libffi'" -- chmod +x libffi/ln -- # wc on OS X has spaces in its output, which libffi's Makefile diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index f1d67d9..26fce73 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,8 +20,14 @@ rtsConf = pkgPath rts -/- targetDirectory Stage1 rts -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do + use_system_ffi <- setting UseSystemFfi windows <- windowsHost - return $ if windows then "Cffi-6" else "Cffi" + case (use_system_ffi, windows) of + ("YES", False) -> return "ffi" + ("NO", False) -> return "Cffi" + (_, True) -> return "Cffi-6" + (_, _) -> error "Unsupported FFI library configuration case" + rtsPackageArgs :: Args rtsPackageArgs = package rts ? do From git at git.haskell.org Thu Oct 26 23:53:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:53:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds derivedConstantsDependencies for rts (2565fc3) Message-ID: <20171026235359.E67053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2565fc354a241ff9f6137c5202949a6f8f46bff9/ghc >--------------------------------------------------------------- commit 2565fc354a241ff9f6137c5202949a6f8f46bff9 Author: Moritz Angermann Date: Tue Jan 5 11:14:20 2016 +0800 Adds derivedConstantsDependencies for rts Building rts depends on derived constants, as we can not rely on the compiler to be build prior to rts, as we build rts with gcc, and hence do not depend on ghc, we need to have rts depend on the derived constants. This fixes #94. However, if we are going to build rts with the stage1 ghc, this should not be an issue anymore (see #90), as derived constants would be build then anyway. Yet I do not see any problem with explicilty noting down the derived constants dependency for rts. >--------------------------------------------------------------- 2565fc354a241ff9f6137c5202949a6f8f46bff9 src/Rules/Generate.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 6a4270b..65c0abf 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -72,6 +72,7 @@ compilerDependencies stage = generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage + | pkg == rts = derivedConstantsDependencies | stage == Stage0 = defaultDependencies | otherwise = [] From git at git.haskell.org Thu Oct 26 23:54:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add stage parameter to Gcc builder. Clean up. (d6744a7) Message-ID: <20171026235400.29E7E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6744a706e0ed263c6f67a3f2a668363ddaa36c5/ghc >--------------------------------------------------------------- commit d6744a706e0ed263c6f67a3f2a668363ddaa36c5 Author: Andrey Mokhov Date: Sun Jan 18 00:09:45 2015 +0000 Add stage parameter to Gcc builder. Clean up. >--------------------------------------------------------------- d6744a706e0ed263c6f67a3f2a668363ddaa36c5 cfg/default.config.in | 33 +++++++++++++++++---------------- src/Oracles/Base.hs | 3 ++- src/Oracles/Builder.hs | 9 +++++---- src/Oracles/Option.hs | 2 +- src/Package/Compile.hs | 10 ++++++++-- src/Package/Data.hs | 8 ++++---- src/Package/Dependencies.hs | 4 ++-- 7 files changed, 39 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 d6744a706e0ed263c6f67a3f2a668363ddaa36c5 From git at git.haskell.org Thu Oct 26 23:54:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: use flag instead of setting for use system ffi value (afc4d05) Message-ID: <20171026235402.D32603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/afc4d05a9f33555887df3217adb6c70ebe806d2f/ghc >--------------------------------------------------------------- commit afc4d05a9f33555887df3217adb6c70ebe806d2f Author: Karel Gardas Date: Sun Jan 17 23:52:48 2016 +0100 use flag instead of setting for use system ffi value >--------------------------------------------------------------- afc4d05a9f33555887df3217adb6c70ebe806d2f src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 2 -- src/Rules/Libffi.hs | 4 ++-- src/Settings/Packages/Rts.hs | 6 +++--- 4 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 44e8a17..9d33445 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -19,6 +19,7 @@ data Flag = ArSupportsAtFile | SolarisBrokenShld | SplitObjectsBroken | WithLibdw + | UseSystemFfi -- Note, if a flag is set to empty string we treat it as set to NO. This seems -- fragile, but some flags do behave like this, e.g. GccIsClang. @@ -34,6 +35,7 @@ flag f = do SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" WithLibdw -> "with-libdw" + UseSystemFfi -> "use-system-ffi" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." unless (value == "YES" || value == "NO" || value == "") . putError diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 7b5d71e..56ef1ca 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -47,7 +47,6 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor - | UseSystemFfi data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -91,7 +90,6 @@ setting key = askConfig $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" - UseSystemFfi -> "use-system-ffi" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 5f23cad..fea58ab 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,9 +70,9 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - use_system_ffi <- setting UseSystemFfi ffi_header_dirs <- settingList FfiIncludeDirs - if use_system_ffi == "YES" + use_system_ffi <- flag UseSystemFfi + if use_system_ffi then do putBuild "| System supplied FFI library will be used" let ffi_header_dir = head ffi_header_dirs diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 26fce73..e684b7a 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,11 +20,11 @@ rtsConf = pkgPath rts -/- targetDirectory Stage1 rts -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do - use_system_ffi <- setting UseSystemFfi + use_system_ffi <- flag UseSystemFfi windows <- windowsHost case (use_system_ffi, windows) of - ("YES", False) -> return "ffi" - ("NO", False) -> return "Cffi" + (True, False) -> return "ffi" + (False, False) -> return "Cffi" (_, True) -> return "Cffi-6" (_, _) -> error "Unsupported FFI library configuration case" From git at git.haskell.org Thu Oct 26 23:54:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds gmp.h to the integerGmp dependencies. (6fd807b) Message-ID: <20171026235403.E00653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6fd807ba05023634fb7f6082ef2369b9f7f90f6b/ghc >--------------------------------------------------------------- commit 6fd807ba05023634fb7f6082ef2369b9f7f90f6b Author: Moritz Angermann Date: Tue Jan 5 13:05:18 2016 +0800 Adds gmp.h to the integerGmp dependencies. Fix #88. is imported by libraries/integer-gmp/cbits/wrappers.c, hence the dependency generation with GccM, requires gmp.h to be available. We therefore add it to the generated dependencies. >--------------------------------------------------------------- 6fd807ba05023634fb7f6082ef2369b9f7f90f6b src/Rules/Generate.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 65c0abf..921c672 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -69,10 +69,15 @@ compilerDependencies stage = , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] +integerGmpDependencies :: [FilePath] +integerGmpDependencies = ((pkgPath integerGmp -/- "gmp") -/-) <$> + [ "gmp.h" ] -- identical to integerGmpLibraryH, but doesn't require the import. + generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == rts = derivedConstantsDependencies + | pkg == integerGmp = integerGmpDependencies | stage == Stage0 = defaultDependencies | otherwise = [] From git at git.haskell.org Thu Oct 26 23:54:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up rules related to dependency lists. (7d42fda) Message-ID: <20171026235404.0F0043A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d42fdac5a5574825124b250e3db0287cab8c417/ghc >--------------------------------------------------------------- commit 7d42fdac5a5574825124b250e3db0287cab8c417 Author: Andrey Mokhov Date: Sun Jan 18 12:45:23 2015 +0000 Clean up rules related to dependency lists. >--------------------------------------------------------------- 7d42fdac5a5574825124b250e3db0287cab8c417 src/Package/Compile.hs | 2 +- src/Package/Dependencies.hs | 14 ++++++-------- 2 files changed, 7 insertions(+), 9 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 0cdb62c..1155117 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -48,7 +48,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = let oPattern = "*." ++ osuf way let hiPattern = "*." ++ hisuf way [buildDir oPattern, buildDir hiPattern] |%> \out -> do - need [argListPath argListDir pkg stage, hDepFile, cDepFile] + need [argListPath argListDir pkg stage] let obj = toStandard $ out -<.> osuf way vanillaObj = toStandard $ out -<.> "o" -- TODO: keep only vanilla dependencies in hDepFile diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 08bb9e5..31c8d92 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -16,7 +16,7 @@ ghcArgs (Package name path _) (stage, dist, settings) = , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist , productArgs ["-odir", "-stubdir", "-hidir"] buildDir - , args ["-dep-makefile", depFile <.> "new"] + , args ["-dep-makefile", depFile ] , productArgs "-dep-suffix" $ map wayPrefix <$> ways settings , args $ HsArgs pathDist , args $ pkgHsSources path dist ] @@ -60,19 +60,17 @@ buildRule :: Package -> TodoItem -> Rules () buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do let pathDist = path dist buildDir = pathDist "build" - hDepFile = buildDir "haskell.deps" - cDepFile = buildDir "c.deps" - hDepFile %> \out -> do + (buildDir "haskell.deps") %> \out -> do need [argListPath argListDir pkg stage] terseRun (Ghc stage) $ ghcArgs pkg todo -- Avoid rebuilding dependecies of out if it hasn't changed: -- Note: cannot use copyFileChanged as it depends on the source file - deps <- liftIO $ readFile $ out <.> "new" - writeFileChanged out deps - liftIO $ removeFiles "." [out <.> "new"] + --deps <- liftIO $ readFile $ out <.> "new" + --writeFileChanged out deps + --liftIO $ removeFiles "." [out <.> "new"] - cDepFile %> \out -> do + (buildDir "c.deps") %> \out -> do need [argListPath argListDir pkg stage] srcs <- args $ CSrcs pathDist deps <- fmap concat $ forM srcs $ \src -> do From git at git.haskell.org Thu Oct 26 23:54:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build unlit. (51c24a8) Message-ID: <20171026235406.8F0733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/51c24a8f1320013d75ac9b06df60f3834b5bc0be/ghc >--------------------------------------------------------------- commit 51c24a8f1320013d75ac9b06df60f3834b5bc0be Author: Andrey Mokhov Date: Sun Jan 17 23:33:28 2016 +0000 Build unlit. See #181. [skip ci] >--------------------------------------------------------------- 51c24a8f1320013d75ac9b06df60f3834b5bc0be src/Settings/Packages.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index b7e2dac..691cd78 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -24,7 +24,8 @@ packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] + , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode + , hp2ps, unlit ] , stage0 ? windowsHost ? append [touchy] , notM windowsHost ? notM iosHost ? append [terminfo] ] From git at git.haskell.org Thu Oct 26 23:54:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compile rts with -O2 (8e3e9bc) Message-ID: <20171026235407.B514A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e3e9bcf2c7fc37423a5b19ac314fe23447610ad/ghc >--------------------------------------------------------------- commit 8e3e9bcf2c7fc37423a5b19ac314fe23447610ad Author: Moritz Angermann Date: Tue Jan 5 13:57:35 2016 +0800 Compile rts with -O2 Fixes #90. We need to force inlining for rts to compile and not end up with missing symbols. >--------------------------------------------------------------- 8e3e9bcf2c7fc37423a5b19ac314fe23447610ad src/Settings/Packages/Rts.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 36476a0..eb74eea 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -49,6 +49,13 @@ rtsPackageArgs = package rts ? do [ arg "-Irts" , arg $ "-I" ++ path -/- "build" , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" + -- rts **must** be compiled with optimizations. The INLINE_HEADER macro, + -- requires that functions are inlined to work as expected. Inlining + -- only happens for optimized builds. Otherwise we can assume that + -- there is a non-inlined variant to use instead. But rts does not + -- provide non-inlined alternatives and hence needs the function to + -- be inlined. See also Issue #90 + , arg $ "-O2" , (file "//RtsMessages.*" ||^ file "//Trace.*") ? arg ("-DProjectVersion=" ++ quote projectVersion) From git at git.haskell.org Thu Oct 26 23:54:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename (run, terseRun) to (verboseRun, run). (9e247b0) Message-ID: <20171026235407.DB8E93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e247b0618357bdca4b0218de19e2eb7f9f23b63/ghc >--------------------------------------------------------------- commit 9e247b0618357bdca4b0218de19e2eb7f9f23b63 Author: Andrey Mokhov Date: Sun Jan 18 12:50:13 2015 +0000 Rename (run, terseRun) to (verboseRun, run). >--------------------------------------------------------------- 9e247b0618357bdca4b0218de19e2eb7f9f23b63 src/Oracles/Builder.hs | 15 ++++++--------- src/Package/Compile.hs | 4 ++-- src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 9 ++------- src/Package/Library.hs | 4 ++-- 5 files changed, 14 insertions(+), 22 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 1dcc797..e52cc58 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -2,7 +2,7 @@ module Oracles.Builder ( Builder (..), - with, run, terseRun, specified + with, run, verboseRun, specified ) where import Data.Char @@ -94,9 +94,8 @@ with builder = do return [key ++ exe] -- Run the builder with a given collection of arguments --- Raises an error if the builder is not uniquely specified in config files -run :: ShowArgs a => Builder -> a -> Action () -run builder as = do +verboseRun :: ShowArgs a => Builder -> a -> Action () +verboseRun builder as = do needBuilder builder exe <- showArg builder args <- showArgs as @@ -104,17 +103,15 @@ run builder as = do -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. --- Raises an error if the builder is not uniquely specified in config files --- TODO: make this a default 'run', rename current 'run' to verboseRun -terseRun :: ShowArgs a => Builder -> a -> Action () -terseRun builder as = do +run :: ShowArgs a => Builder -> a -> Action () +run builder as = do args <- showArgs as putColoured White $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" mapM_ (putColoured White . ("| " ++)) $ interestingInfo builder args putColoured White $ "\\--------" - quietly $ run builder as + quietly $ verboseRun builder as interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 1155117..e0080f9 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -66,9 +66,9 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = -- Build using appropriate compiler need $ hDeps ++ cDeps when (not $ null hSrcs) - $ terseRun (Ghc stage) $ ghcArgs pkg todo way hSrcs obj + $ run (Ghc stage) $ ghcArgs pkg todo way hSrcs obj when (not $ null cSrcs) - $ terseRun (Gcc stage) $ gccArgs pkg todo cSrcs obj + $ run (Gcc stage) $ gccArgs pkg todo cSrcs obj argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, settings) = diff --git a/src/Package/Data.hs b/src/Package/Data.hs index a3f0936..91f0b2d 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -124,9 +124,9 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = ] &%> \_ -> do need [argListPath argListDir pkg stage, cabal] when (doesFileExist $ configure <.> "ac") $ need [configure] - terseRun GhcCabal $ cabalArgs pkg todo + run GhcCabal $ cabalArgs pkg todo when (registerPackage settings) $ - terseRun (GhcPkg stage) $ ghcPkgArgs pkg todo + run (GhcPkg stage) $ ghcPkgArgs pkg todo postProcessPackageData $ pathDist "package-data.mk" argListRule :: Package -> TodoItem -> Rules () diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 31c8d92..d1a8a14 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -63,12 +63,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do (buildDir "haskell.deps") %> \out -> do need [argListPath argListDir pkg stage] - terseRun (Ghc stage) $ ghcArgs pkg todo - -- Avoid rebuilding dependecies of out if it hasn't changed: - -- Note: cannot use copyFileChanged as it depends on the source file - --deps <- liftIO $ readFile $ out <.> "new" - --writeFileChanged out deps - --liftIO $ removeFiles "." [out <.> "new"] + run (Ghc stage) $ ghcArgs pkg todo (buildDir "c.deps") %> \out -> do need [argListPath argListDir pkg stage] @@ -76,7 +71,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do deps <- fmap concat $ forM srcs $ \src -> do let srcPath = path src depFile = buildDir takeFileName src <.> "deps" - terseRun (Gcc stage) $ gccArgs srcPath pkg todo + run (Gcc stage) $ gccArgs srcPath pkg todo liftIO $ readFile depFile writeFileChanged out deps liftIO $ removeFiles buildDir ["*.c.deps"] diff --git a/src/Package/Library.hs b/src/Package/Library.hs index 2b82260..e5fa0b8 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -25,7 +25,7 @@ arRule pkg @ (Package _ path _) todo @ (stage, dist, _) = -- Splitting argument list into chunks as otherwise Ar chokes up maxChunk <- argSizeLimit forM_ (chunksOfSize maxChunk $ libHsObjs ++ cObjs) $ \os -> do - terseRun Ar $ arArgs os $ toStandard out + run Ar $ arArgs os $ toStandard out ldArgs :: Package -> TodoItem -> FilePath -> Args ldArgs (Package _ path _) (stage, dist, _) result = do @@ -45,7 +45,7 @@ ldRule pkg @ (Package name path _) todo @ (stage, dist, _) = in priority 2 $ (buildDir "*.o") %> \out -> do need [argListPath argListDir pkg stage] - terseRun Ld $ ldArgs pkg todo $ toStandard out + run Ld $ ldArgs pkg todo $ toStandard out synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) putColoured Green $ "/--------\n| Successfully built package " ++ name ++ " (stage " ++ show stage ++ ")." From git at git.haskell.org Thu Oct 26 23:54:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy ghc-usage.txt and ghci-usage.txt. (b5d0778) Message-ID: <20171026235410.189203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b5d0778726fd75fd7547b89864ee8e2859ce0ccf/ghc >--------------------------------------------------------------- commit b5d0778726fd75fd7547b89864ee8e2859ce0ccf Author: Andrey Mokhov Date: Sun Jan 17 23:37:01 2016 +0000 Copy ghc-usage.txt and ghci-usage.txt. Fix #181. >--------------------------------------------------------------- b5d0778726fd75fd7547b89864ee8e2859ce0ccf src/Rules/Generate.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 025f1ee..c5386e4 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -23,7 +23,9 @@ import Settings installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" , "inplace/lib/platformConstants" - , "inplace/lib/settings" ] + , "inplace/lib/settings" + , "inplace/lib/ghc-usage.txt" + , "inplace/lib/ghci-usage.txt" ] primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -167,6 +169,8 @@ copyRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." + "inplace/lib/ghc-usage.txt" <~ "driver" + "inplace/lib/ghci-usage.txt" <~ "driver" where file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file From git at git.haskell.org Thu Oct 26 23:54:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Wrap ghc-stage2 (04fc52c) Message-ID: <20171026235411.8B5D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/04fc52cd10d23e480ca4de402eb545b4269bdcb1/ghc >--------------------------------------------------------------- commit 04fc52cd10d23e480ca4de402eb545b4269bdcb1 Author: Moritz Angermann Date: Tue Jan 5 14:06:23 2016 +0800 Wrap ghc-stage2 Fix #96 (c.f. #57 for stage1) >--------------------------------------------------------------- 04fc52cd10d23e480ca4de402eb545b4269bdcb1 src/Rules/Program.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index fe55005..547fb86 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -24,6 +24,7 @@ type Wrapper = FilePath -> Expr String -- List of wrappers we build wrappers :: [(PartialTarget, Wrapper)] wrappers = [ (PartialTarget Stage0 ghc, ghcWrapper) + , (PartialTarget Stage1 ghc, ghcWrapper) , (PartialTarget Stage0 ghcPkg, ghcPkgWrapper)] buildProgram :: Resources -> PartialTarget -> Rules () From git at git.haskell.org Thu Oct 26 23:54:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split compile rules for {hi, o}, clean up code. (3344cea) Message-ID: <20171026235411.C52F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3344ceadaa807de7708c9444b1a71537fa0a7fdd/ghc >--------------------------------------------------------------- commit 3344ceadaa807de7708c9444b1a71537fa0a7fdd Author: Andrey Mokhov Date: Sun Jan 18 13:34:58 2015 +0000 Split compile rules for {hi, o}, clean up code. >--------------------------------------------------------------- 3344ceadaa807de7708c9444b1a71537fa0a7fdd src/Oracles.hs | 12 +++++++----- src/Package/Compile.hs | 15 ++++++++++----- 2 files changed, 17 insertions(+), 10 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 4c6d9e9..215ccb7 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -67,15 +67,17 @@ packageDataOracle = do -- Oracle for 'path/dist/*.deps' files dependencyOracle :: Rules () dependencyOracle = do - deps <- newCache $ \depFile -> do - need [depFile] - putOracle $ "Parsing " ++ toStandard depFile ++ "..." - contents <- parseMakefile <$> (liftIO $ readFile depFile) + deps <- newCache $ \file -> do + need [file] + putOracle $ "Parsing " ++ file ++ "..." + contents <- parseMakefile <$> (liftIO $ readFile file) return $ M.fromList + $ map (bimap toStandard (map toStandard)) $ map (bimap head concat . unzip) $ groupBy ((==) `on` fst) $ sortBy (compare `on` fst) contents - addOracle $ \(DependencyListKey (file, obj)) -> M.lookup obj <$> deps file + addOracle $ \(DependencyListKey (file, obj)) -> + M.lookup (toStandard obj) <$> deps (toStandard file) return () oracleRules :: Rules () diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index e0080f9..762f533 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -47,10 +47,14 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = forM_ allWays $ \way -> do -- TODO: optimise (too many ways in allWays) let oPattern = "*." ++ osuf way let hiPattern = "*." ++ hisuf way - [buildDir oPattern, buildDir hiPattern] |%> \out -> do + + (buildDir hiPattern) %> \out -> do + let obj = out -<.> osuf way + need [obj] + + (buildDir oPattern) %> \obj -> do need [argListPath argListDir pkg stage] - let obj = toStandard $ out -<.> osuf way - vanillaObj = toStandard $ out -<.> "o" + let vanillaObj = obj -<.> "o" -- TODO: keep only vanilla dependencies in hDepFile hDeps <- args $ DependencyList hDepFile obj cDeps <- args $ DependencyList cDepFile $ takeFileName vanillaObj @@ -59,10 +63,10 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = -- Report impossible cases when (null $ hSrcs ++ cSrcs) $ redError_ $ "No source files found for " - ++ toStandard out ++ "." + ++ toStandard obj ++ "." when (not (null hSrcs) && not (null cSrcs)) $ redError_ $ "Both c and Haskell sources found for " - ++ toStandard out ++ "." + ++ toStandard obj ++ "." -- Build using appropriate compiler need $ hDeps ++ cDeps when (not $ null hSrcs) @@ -70,6 +74,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = when (not $ null cSrcs) $ run (Gcc stage) $ gccArgs pkg todo cSrcs obj + argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, settings) = (argListPath argListDir pkg stage) %> \out -> do From git at git.haskell.org Thu Oct 26 23:54:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Builder.hs. (40b7920) Message-ID: <20171026235413.9DF7B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/40b792062cfe1289460323228a0b6c7487300980/ghc >--------------------------------------------------------------- commit 40b792062cfe1289460323228a0b6c7487300980 Author: Andrey Mokhov Date: Mon Jan 18 01:31:06 2016 +0000 Refactor Builder.hs. Fix #124. >--------------------------------------------------------------- 40b792062cfe1289460323228a0b6c7487300980 cfg/system.config.in | 74 ++++++++++------------------ src/Builder.hs | 126 ++++++++++++++++++++++++++---------------------- src/GHC.hs | 35 +++++++++++++- src/Settings.hs | 5 +- src/Settings/Default.hs | 34 +------------ src/Settings/Paths.hs | 5 +- src/Settings/User.hs | 14 +----- 7 files changed, 134 insertions(+), 159 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 40b792062cfe1289460323228a0b6c7487300980 From git at git.haskell.org Thu Oct 26 23:54:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #95 from angerman/feature/fix-rts-deps (ccf4030) Message-ID: <20171026235415.810363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccf4030baa2739d1ce03a273f764a532fb3428c9/ghc >--------------------------------------------------------------- commit ccf4030baa2739d1ce03a273f764a532fb3428c9 Merge: ba41ec6 8e3e9bc Author: Andrey Mokhov Date: Tue Jan 5 09:27:42 2016 +0000 Merge pull request #95 from angerman/feature/fix-rts-deps Adds derivedConstantsDependencies for rts >--------------------------------------------------------------- ccf4030baa2739d1ce03a273f764a532fb3428c9 src/Rules/Generate.hs | 6 ++++++ src/Settings/Packages/Rts.hs | 7 +++++++ 2 files changed, 13 insertions(+) From git at git.haskell.org Thu Oct 26 23:54:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more targets. (4399476) Message-ID: <20171026235415.9E5743A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4399476dfd70a7ce9ad97750873e8b3397deb270/ghc >--------------------------------------------------------------- commit 4399476dfd70a7ce9ad97750873e8b3397deb270 Author: Andrey Mokhov Date: Sun Jan 18 14:27:23 2015 +0000 Add more targets. >--------------------------------------------------------------- 4399476dfd70a7ce9ad97750873e8b3397deb270 src/Targets.hs | 36 +++++++++++++++++++----------------- 1 file changed, 19 insertions(+), 17 deletions(-) diff --git a/src/Targets.hs b/src/Targets.hs index a8c9e68..25a3a0e 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -6,23 +6,25 @@ import Base -- TODO: this should eventually be removed and replaced by the top-level -- target, i.e. GHC (and perhaps, something else) libraryPackagesInStage :: Stage -> [String] -libraryPackagesInStage Stage0 = [] - --[ "bin-package-db" - --, "binary" - --, "hoopl" - --, "hpc" - --, "transformers" ] -libraryPackagesInStage Stage1 = ["directory", "bytestring"] - --libraryPackagesInStage Stage0 ++ - --[ "array" - --, "deepseq" - --, "Cabal/Cabal" - --, "containers" - --, "filepath" - --, "parallel" - --, "pretty" - --, "stm" - --, "template-haskell" ] +libraryPackagesInStage Stage0 = + [ "bin-package-db" + , "binary" + , "hoopl" + , "hpc" + , "transformers" ] +libraryPackagesInStage Stage1 = + libraryPackagesInStage Stage0 ++ + [ "array" + , "bytestring" + , "Cabal/Cabal" + , "containers" + , "deepseq" + , "directory" + , "filepath" + , "parallel" + , "pretty" + , "stm" + , "template-haskell" ] libraryPackagesInStage _ = [] From git at git.haskell.org Thu Oct 26 23:54:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: change from using "dirs" to "dir" for FFI library configuration (a3afd03) Message-ID: <20171026235417.289873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a3afd03cf3b46e3344c3274606a3d42b1b08a254/ghc >--------------------------------------------------------------- commit a3afd03cf3b46e3344c3274606a3d42b1b08a254 Author: Karel Gardas Date: Mon Jan 18 10:24:42 2016 +0100 change from using "dirs" to "dir" for FFI library configuration >--------------------------------------------------------------- a3afd03cf3b46e3344c3274606a3d42b1b08a254 cfg/system.config.in | 4 ++-- src/Oracles/Config/Setting.hs | 8 ++++---- src/Rules/Libffi.hs | 3 +-- 3 files changed, 7 insertions(+), 8 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index ecbf18d..94058df 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -128,8 +128,8 @@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ use-system-ffi = @UseSystemLibFFI@ -ffi-include-dirs = @FFIIncludeDir@ -ffi-lib-dirs = @FFILibDir@ +ffi-include-dir = @FFIIncludeDir@ +ffi-lib-dir = @FFILibDir@ # Optional Dependencies: #======================= diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 56ef1ca..f4540cc 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -47,6 +47,8 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor + | FfiIncludeDir + | FfiLibDir data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -57,8 +59,6 @@ data SettingList = ConfCcArgs Stage | HsCppArgs | IconvIncludeDirs | IconvLibDirs - | FfiIncludeDirs - | FfiLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of @@ -90,6 +90,8 @@ setting key = askConfig $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" + FfiIncludeDir -> "ffi-include-dir" + FfiLibDir -> "ffi-lib-dir" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -102,8 +104,6 @@ settingList key = fmap words $ askConfig $ case key of HsCppArgs -> "hs-cpp-args" IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" - FfiIncludeDirs -> "ffi-include-dirs" - FfiLibDirs -> "ffi-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index fea58ab..518389e 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,12 +70,11 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - ffi_header_dirs <- settingList FfiIncludeDirs + ffi_header_dir <- setting FfiIncludeDir use_system_ffi <- flag UseSystemFfi if use_system_ffi then do putBuild "| System supplied FFI library will be used" - let ffi_header_dir = head ffi_header_dirs forM_ ["ffi.h", "ffitarget.h"] $ \file -> do let src = ffi_header_dir -/- file copyFile src (rtsBuildPath -/- file) From git at git.haskell.org Thu Oct 26 23:54:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Util/unifyPath function and make sure it is used. (a93823b) Message-ID: <20171026235419.CBE1F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1/ghc >--------------------------------------------------------------- commit a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1 Author: Andrey Mokhov Date: Sun Jan 18 14:28:04 2015 +0000 Add Util/unifyPath function and make sure it is used. >--------------------------------------------------------------- a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1 src/Oracles.hs | 13 +++++++------ src/Oracles/PackageData.hs | 4 ++-- src/Package/Base.hs | 21 ++++++++++----------- src/Package/Compile.hs | 8 ++++---- src/Package/Data.hs | 7 +++---- src/Package/Dependencies.hs | 6 +++--- src/Package/Library.hs | 10 +++++----- src/Util.hs | 4 ++++ 8 files changed, 38 insertions(+), 35 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 a93823be7a1b6dd2884fd3c197ff3ddeab99dbc1 From git at git.haskell.org Thu Oct 26 23:54:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #97 from angerman/feature/ghc-stage2-wrapper (9e1ef6a) Message-ID: <20171026235419.DCF5E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e1ef6ab9ce326638528140be935e05793f4ea16/ghc >--------------------------------------------------------------- commit 9e1ef6ab9ce326638528140be935e05793f4ea16 Merge: ccf4030 04fc52c Author: Andrey Mokhov Date: Tue Jan 5 09:28:26 2016 +0000 Merge pull request #97 from angerman/feature/ghc-stage2-wrapper Wrap ghc-stage2 >--------------------------------------------------------------- 9e1ef6ab9ce326638528140be935e05793f4ea16 src/Rules/Program.hs | 1 + 1 file changed, 1 insertion(+) From git at git.haskell.org Thu Oct 26 23:54:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor rules, clean up code. (a1819f6) Message-ID: <20171026235423.D3D4A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e/ghc >--------------------------------------------------------------- commit a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e Author: Andrey Mokhov Date: Sun Jan 18 23:52:09 2015 +0000 Refactor rules, clean up code. >--------------------------------------------------------------- a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e src/Oracles.hs | 8 ++++---- src/Package/Base.hs | 21 ++++++++++++-------- src/Package/Compile.hs | 45 +++++++++++++++++++++---------------------- src/Package/Library.hs | 52 +++++++++++++++++++++++++------------------------- src/Targets.hs | 2 +- src/Ways.hs | 1 - 6 files changed, 66 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a1819f6a8ed0a373bdbbc6ac3aac83066fa88b1e From git at git.haskell.org Thu Oct 26 23:54:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' into fix_ffi_args (680766b) Message-ID: <20171026235421.2E56A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/680766bbf029a391d4c4334648aa4739274cb25f/ghc >--------------------------------------------------------------- commit 680766bbf029a391d4c4334648aa4739274cb25f Merge: a3afd03 40b7920 Author: Karel Gardas Date: Mon Jan 18 12:49:15 2016 +0100 Merge branch 'master' into fix_ffi_args Conflicts: cfg/system.config.in >--------------------------------------------------------------- 680766bbf029a391d4c4334648aa4739274cb25f cfg/system.config.in | 73 ++++++++++----------------- src/Builder.hs | 126 ++++++++++++++++++++++++++--------------------- src/GHC.hs | 35 ++++++++++++- src/Rules/Generate.hs | 6 ++- src/Settings.hs | 5 +- src/Settings/Default.hs | 34 +------------ src/Settings/Packages.hs | 3 +- src/Settings/Paths.hs | 5 +- src/Settings/User.hs | 14 +----- 9 files changed, 141 insertions(+), 160 deletions(-) From git at git.haskell.org Thu Oct 26 23:54:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix travis script: configure after shake-build is in place. (b978e17) Message-ID: <20171026235423.EB33F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b978e17552d87de8973a5bdd0255da5d1baa7d51/ghc >--------------------------------------------------------------- commit b978e17552d87de8973a5bdd0255da5d1baa7d51 Author: Andrey Mokhov Date: Tue Jan 5 10:29:08 2016 +0000 Fix travis script: configure after shake-build is in place. >--------------------------------------------------------------- b978e17552d87de8973a5bdd0255da5d1baa7d51 .travis/install-ghc-shake.sh | 3 +++ .travis/install-ghc.sh | 3 --- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis/install-ghc-shake.sh b/.travis/install-ghc-shake.sh index 2dc0392..c2b8774 100755 --- a/.travis/install-ghc-shake.sh +++ b/.travis/install-ghc-shake.sh @@ -14,3 +14,6 @@ mv .git "$SHAKEDIR/" echo -e "${COLOR}Installing deps into sandbox${RESET}" ( cd "$SHAKEDIR" && cabal sandbox init ) ( cd "$SHAKEDIR" && cabal install --only-dependencies . ) + +echo -e "${COLOR}GHC boot/configure${RESET}" +( cd ghc && ./boot && ./configure) diff --git a/.travis/install-ghc.sh b/.travis/install-ghc.sh index 126cbe2..fc34ea4 100755 --- a/.travis/install-ghc.sh +++ b/.travis/install-ghc.sh @@ -10,6 +10,3 @@ git clone git://git.haskell.org/ghc echo -e "${COLOR}Initialize GHC submodules${RESET}" ( cd ghc && git submodule update --init ) - -echo -e "${COLOR}GHC boot/configure${RESET}" -( cd ghc && ./boot && ./configure) From git at git.haskell.org Thu Oct 26 23:54:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: pass ffi include/library directories to HsCpp (39f0e7a) Message-ID: <20171026235424.B05223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39f0e7a2fe46ea6e6fc1cc86685fd8729a4cf4c7/ghc >--------------------------------------------------------------- commit 39f0e7a2fe46ea6e6fc1cc86685fd8729a4cf4c7 Author: Karel Gardas Date: Mon Jan 18 20:06:55 2016 +0100 pass ffi include/library directories to HsCpp >--------------------------------------------------------------- 39f0e7a2fe46ea6e6fc1cc86685fd8729a4cf4c7 src/Settings/Packages/Rts.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e684b7a..58b76cf 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -51,6 +51,8 @@ rtsPackageArgs = package rts ? do path <- getTargetPath top <- getTopDirectory libffiName <- lift $ rtsLibffiLibraryName + ffiIncludeDir <- getSetting FfiIncludeDir + ffiLibraryDir <- getSetting FfiLibDir mconcat [ builderGcc ? mconcat [ arg "-Irts" @@ -92,8 +94,8 @@ rtsPackageArgs = package rts ? do , builder HsCpp ? mconcat [ arg ("-DTOP=" ++ quote top) - , arg "-DFFI_INCLUDE_DIR=" - , arg "-DFFI_LIB_DIR=" + , arg ("-DFFI_INCLUDE_DIR=" ++ quote ffiIncludeDir) + , arg ("-DFFI_LIB_DIR=" ++ quote ffiLibraryDir) , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] From git at git.haskell.org Thu Oct 26 23:54:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (d4e44fb) Message-ID: <20171026235427.8B57F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4e44fb28e3487c00fb375e4a528f97cab720c53/ghc >--------------------------------------------------------------- commit d4e44fb28e3487c00fb375e4a528f97cab720c53 Author: Andrey Mokhov Date: Tue Jan 5 10:29:30 2016 +0000 Add comments. >--------------------------------------------------------------- d4e44fb28e3487c00fb375e4a528f97cab720c53 src/Settings/Packages/Rts.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index eb74eea..d300e5a 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -89,6 +89,14 @@ rtsPackageArgs = package rts ? do , arg "-DFFI_LIB_DIR=" , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] + +-- # If we're compiling on windows, enforce that we only support XP+ +-- # Adding this here means it doesn't have to be done in individual .c files +-- # and also centralizes the versioning. +-- ifeq "$$(TargetOS_CPP)" "mingw32" +-- rts_dist_$1_CC_OPTS += -DWINVER=$(rts_WINVER) +-- endif + -- #----------------------------------------------------------------------------- -- # Use system provided libffi From git at git.haskell.org Thu Oct 26 23:54:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix recursive rules error. (8290198) Message-ID: <20171026235427.E1F313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82901986216e56d42623299aaec8ca7d1bddcdca/ghc >--------------------------------------------------------------- commit 82901986216e56d42623299aaec8ca7d1bddcdca Author: Andrey Mokhov Date: Mon Jan 19 03:45:10 2015 +0000 Fix recursive rules error. >--------------------------------------------------------------- 82901986216e56d42623299aaec8ca7d1bddcdca src/Package/Base.hs | 8 +++++--- src/Package/Compile.hs | 12 +++++++++--- src/Package/Data.hs | 4 +++- src/Package/Dependencies.hs | 8 +++++--- src/Package/Library.hs | 8 ++++++-- 5 files changed, 28 insertions(+), 12 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 023b001..cf29e59 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -108,8 +108,9 @@ includeGhcArgs path dist = pkgHsSources :: FilePath -> FilePath -> Action [FilePath] pkgHsSources path dist = do let pathDist = path dist + autogen = pathDist "build/autogen" dirs <- map (path ) <$> args (SrcDirs pathDist) - findModuleFiles pathDist dirs [".hs", ".lhs"] + findModuleFiles pathDist (autogen:dirs) [".hs", ".lhs"] -- TODO: look for non-{hs,c} objects too @@ -136,11 +137,13 @@ pkgLibHsObjects path dist stage way = do let pathDist = path dist buildDir = unifyPath $ pathDist "build" split <- splitObjects stage + depObjs <- pkgDepHsObjects path dist way if split then do + need depObjs -- Otherwise, split objects may not yet be available let suffix = "_" ++ osuf way ++ "_split/*." ++ osuf way findModuleFiles pathDist [buildDir] [suffix] - else pkgDepHsObjects path dist way + else do return depObjs findModuleFiles :: FilePath -> [FilePath] -> [String] -> Action [FilePath] findModuleFiles pathDist directories suffixes = do @@ -153,7 +156,6 @@ findModuleFiles pathDist directories suffixes = do let dir = takeDirectory file dirExists <- liftIO $ S.doesDirectoryExist dir when dirExists $ return file - files <- getDirectoryFiles "" fileList return $ map unifyPath files diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 01659b6..94cf16a 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -49,8 +49,10 @@ compileHaskell pkg @ (Package _ path _) todo @ (stage, dist, _) obj way = do let buildDir = unifyPath $ path dist "build" -- TODO: keep only vanilla dependencies in 'haskell.deps' deps <- args $ DependencyList (buildDir "haskell.deps") obj + let (srcs, his) = partition ("//*hs" ?==) deps + objs = map (-<.> osuf way) his + -- Need *.o files instead of *.hi files to avoid recursive rules need deps - let srcs = filter ("//*hs" ?==) deps run (Ghc stage) $ ghcArgs pkg todo way srcs obj buildRule :: Package -> TodoItem -> Rules () @@ -64,15 +66,19 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) = (buildDir hiPattern) %> \hi -> do let obj = hi -<.> osuf way - need [obj] + -- TODO: Understand why 'need [obj]' doesn't work, leading to + -- recursive rules error. Below is a workaround. + -- putColoured Yellow $ "Hi " ++ hi + compileHaskell pkg todo obj way (buildDir oPattern) %> \obj -> do - need [argListPath argListDir pkg stage] let vanillaObjName = takeFileName obj -<.> "o" cDeps <- args $ DependencyList cDepFile vanillaObjName if null cDeps then compileHaskell pkg todo obj way else compileC pkg todo cDeps obj + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, settings) = diff --git a/src/Package/Data.hs b/src/Package/Data.hs index e1afee1..6d01ba5 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -121,12 +121,14 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = -- TODO: Is this needed? Also check out Paths_cpsa.hs. -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do - need [argListPath argListDir pkg stage, cabal] + need [cabal] when (doesFileExist $ configure <.> "ac") $ need [configure] run GhcCabal $ cabalArgs pkg todo when (registerPackage settings) $ run (GhcPkg stage) $ ghcPkgArgs pkg todo postProcessPackageData $ pathDist "package-data.mk" + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, _) = diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 8675c6f..f87580a 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -61,12 +61,12 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do let pathDist = path dist buildDir = pathDist "build" - (buildDir "haskell.deps") %> \out -> do - need [argListPath argListDir pkg stage] + (buildDir "haskell.deps") %> \_ -> do run (Ghc stage) $ ghcArgs pkg todo + -- Finally, record the argument list + need [argListPath argListDir pkg stage] (buildDir "c.deps") %> \out -> do - need [argListPath argListDir pkg stage] srcs <- args $ CSrcs pathDist deps <- fmap concat $ forM srcs $ \src -> do let srcPath = path src @@ -75,6 +75,8 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do liftIO $ readFile depFile writeFileChanged out deps liftIO $ removeFiles buildDir ["*.c.deps"] + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg todo @ (stage, _, _) = diff --git a/src/Package/Library.hs b/src/Package/Library.hs index c377bc8..6ad029d 100644 --- a/src/Package/Library.hs +++ b/src/Package/Library.hs @@ -26,13 +26,15 @@ arRule pkg @ (Package _ path _) todo @ (stage, dist, _) = let way = detectWay $ tail $ takeExtension out cObjs <- pkgCObjects path dist way hsObjs <- pkgDepHsObjects path dist way - need $ [argListPath argListDir pkg stage] ++ cObjs ++ hsObjs + need $ cObjs ++ hsObjs libHsObjs <- pkgLibHsObjects path dist stage way liftIO $ removeFiles "." [out] -- Splitting argument list into chunks as otherwise Ar chokes up maxChunk <- argSizeLimit forM_ (chunksOfSize maxChunk $ cObjs ++ libHsObjs) $ \objs -> do run Ar $ arArgs objs $ unifyPath out + -- Finally, record the argument list + need [argListPath argListDir pkg stage] ldRule :: Package -> TodoItem -> Rules () ldRule pkg @ (Package name path _) todo @ (stage, dist, _) = @@ -42,13 +44,15 @@ ldRule pkg @ (Package name path _) todo @ (stage, dist, _) = priority 2 $ (buildDir "*.o") %> \out -> do cObjs <- pkgCObjects path dist vanilla hObjs <- pkgDepHsObjects path dist vanilla - need $ [argListPath argListDir pkg stage] ++ cObjs ++ hObjs + need $ cObjs ++ hObjs run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) putColoured Green $ "/--------\n| Successfully built package '" ++ name ++ "' (stage " ++ show stage ++ ")." putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." ++ "\n\\--------" + -- Finally, record the argument list + need [argListPath argListDir pkg stage] argListRule :: Package -> TodoItem -> Rules () argListRule pkg @ (Package _ path _) todo @ (stage, dist, settings) = From git at git.haskell.org Thu Oct 26 23:54:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix tracking of changes to Libffi rules file (efc92c5) Message-ID: <20171026235428.9B7533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efc92c529a00d16f18f2708dd5898ce0ae564cd6/ghc >--------------------------------------------------------------- commit efc92c529a00d16f18f2708dd5898ce0ae564cd6 Author: Karel Gardas Date: Mon Jan 18 20:23:40 2016 +0100 fix tracking of changes to Libffi rules file >--------------------------------------------------------------- efc92c529a00d16f18f2708dd5898ce0ae564cd6 src/Rules/Libffi.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 518389e..97ebc2d 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,6 +70,7 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do + when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] ffi_header_dir <- setting FfiIncludeDir use_system_ffi <- flag UseSystemFfi if use_system_ffi @@ -80,7 +81,6 @@ libffiRules = do copyFile src (rtsBuildPath -/- file) putSuccess $ "| Successfully copied system supplied FFI library header files" else do - when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] removeDirectory libffiBuild createDirectory $ buildRootPath -/- stageString Stage0 From git at git.haskell.org Thu Oct 26 23:54:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow splitObjects to be controlled in Settings/User.hs, see #84. (b18f0e3) Message-ID: <20171026235431.F1F793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b18f0e3f79ee051e9d384b508f0ca3eaa902d80b/ghc >--------------------------------------------------------------- commit b18f0e3f79ee051e9d384b508f0ca3eaa902d80b Author: Andrey Mokhov Date: Tue Jan 5 11:08:20 2016 +0000 Allow splitObjects to be controlled in Settings/User.hs, see #84. >--------------------------------------------------------------- b18f0e3f79ee051e9d384b508f0ca3eaa902d80b shaking-up-ghc.cabal | 1 + src/Predicates.hs | 12 +----------- src/Rules/Library.hs | 1 - src/Settings/Default.hs | 15 +++++++++++++++ src/Settings/User.hs | 6 +++++- 5 files changed, 22 insertions(+), 13 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 334cd59..2eb9f72 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -76,6 +76,7 @@ executable ghc-shake , Settings.Builders.HsCpp , Settings.Builders.Ld , Settings.Builders.Tar + , Settings.Default , Settings.Packages , Settings.Packages.Base , Settings.Packages.Compiler diff --git a/src/Predicates.hs b/src/Predicates.hs index 7b788fe..ad63598 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,13 +1,11 @@ -- | Convenient predicates module Predicates ( stage, package, builder, stagedBuilder, builderGcc, builderGhc, file, way, - stage0, stage1, stage2, notStage0, notPackage, registerPackage, splitObjects + stage0, stage1, stage2, notStage0, notPackage, registerPackage ) where import Base import Expression -import GHC -import Oracles.Config.Flag -- Basic predicates stage :: Stage -> Predicate @@ -55,11 +53,3 @@ notPackage = notM . package -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate registerPackage = return True - -splitObjects :: Predicate -splitObjects = do - goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages - pkg <- getPackage - supported <- lift supportsSplitObjects - let goodPackage = isLibrary pkg && pkg /= compiler && pkg /= rts - return $ goodStage && goodPackage && supported diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 8633c69..d9a1a48 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -6,7 +6,6 @@ import Base hiding (splitPath) import Expression import GHC import Oracles -import Predicates (splitObjects) import Rules.Actions import Rules.IntegerGmp import Rules.Resources diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs new file mode 100644 index 0000000..93b647a --- /dev/null +++ b/src/Settings/Default.hs @@ -0,0 +1,15 @@ +module Settings.Default (defaultSplitObjects) where + +import Base +import Expression +import GHC +import Oracles.Config.Flag +import Predicates + +defaultSplitObjects :: Predicate +defaultSplitObjects = do + goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages + pkg <- getPackage + supported <- lift supportsSplitObjects + let goodPackage = isLibrary pkg && pkg /= compiler && pkg /= rts + return $ goodStage && goodPackage && supported diff --git a/src/Settings/User.hs b/src/Settings/User.hs index cad2578..6107f6f 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors + verboseCommands, turnWarningsIntoErrors, splitObjects ) where import GHC @@ -57,6 +57,10 @@ trackBuildSystem = True validating :: Bool validating = False +-- To switch off split objects change to 'return False' +splitObjects :: Predicate +splitObjects = return False -- FIXME: should be defaultSplitObjects, see #84. + dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Thu Oct 26 23:54:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (20ed2d1) Message-ID: <20171026235433.38ECB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20ed2d1d6d1ce6b612eb607cae447c9646f7be6b/ghc >--------------------------------------------------------------- commit 20ed2d1d6d1ce6b612eb607cae447c9646f7be6b Author: Andrey Mokhov Date: Mon Jan 19 04:13:06 2015 +0000 Clean up. >--------------------------------------------------------------- 20ed2d1d6d1ce6b612eb607cae447c9646f7be6b src/Package/Compile.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 94cf16a..d99e2bf 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -49,9 +49,7 @@ compileHaskell pkg @ (Package _ path _) todo @ (stage, dist, _) obj way = do let buildDir = unifyPath $ path dist "build" -- TODO: keep only vanilla dependencies in 'haskell.deps' deps <- args $ DependencyList (buildDir "haskell.deps") obj - let (srcs, his) = partition ("//*hs" ?==) deps - objs = map (-<.> osuf way) his - -- Need *.o files instead of *.hi files to avoid recursive rules + let srcs = filter ("//*hs" ?==) deps need deps run (Ghc stage) $ ghcArgs pkg todo way srcs obj From git at git.haskell.org Thu Oct 26 23:54:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #182 from kgardas/fix_ffi_args (9a4bdc7) Message-ID: <20171026235433.D90653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a4bdc7c11538e6984a93bda483aa72d7e4aae0e/ghc >--------------------------------------------------------------- commit 9a4bdc7c11538e6984a93bda483aa72d7e4aae0e Merge: 40b7920 efc92c5 Author: Andrey Mokhov Date: Mon Jan 18 23:43:30 2016 +0000 Merge pull request #182 from kgardas/fix_ffi_args fix handling of FFI library configure params >--------------------------------------------------------------- 9a4bdc7c11538e6984a93bda483aa72d7e4aae0e cfg/system.config.in | 4 +++ src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 4 +++ src/Rules/Libffi.hs | 84 ++++++++++++++++++++++++------------------- src/Settings/Packages/Rts.hs | 14 ++++++-- 5 files changed, 68 insertions(+), 40 deletions(-) From git at git.haskell.org Thu Oct 26 23:54:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rework Travis CI script (d0ffc1f) Message-ID: <20171026235435.791993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d0ffc1f8d7e109511b08c0a70a4956188718a911/ghc >--------------------------------------------------------------- commit d0ffc1f8d7e109511b08c0a70a4956188718a911 Author: David Luposchainsky Date: Tue Jan 5 09:50:08 2016 +0100 Rework Travis CI script - Move all .travis/*.sh functionality directly into .travis.yml - Install Alex/Happy from PPA instead of compiling them by hand - Skip Shake progress indicators, as they're rather useless on clean-slate Travis builds, and clutter up the log - Don't use a Cabal sandbox for building so Travis can share $HOME/.cabal - boot/configure only after the Shake build system is in place, otherwise some required *.in files are not converted, and Shake fails >--------------------------------------------------------------- d0ffc1f8d7e109511b08c0a70a4956188718a911 .travis.yml | 52 +++++++++++++++++++++++++++---------- .travis/install-cabal-happy-alex.sh | 18 ------------- .travis/install-ghc-shake.sh | 19 -------------- .travis/install-ghc.sh | 12 --------- .travis/print-env.sh | 9 ------- .travis/run-ghc-shake.sh | 9 ------- build.cabal.sh | 3 ++- build.sh | 2 +- 8 files changed, 42 insertions(+), 82 deletions(-) diff --git a/.travis.yml b/.travis.yml index 5e169fa..9079fa9 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,9 +1,23 @@ sudo: false matrix: - include: - - env: CABALVER=1.22 GHCVER=7.10.3 - addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.3,zlib1g-dev,terminfo-dev], sources: [hvr-ghc]}} + include: + - env: + CABALVER=1.22 + GHCVER=7.10.3 + + addons: { + apt: { + packages: [ + ghc-7.10.3, + alex-3.1.4, + happy-1.19.5, + cabal-install-1.22, + zlib1g-dev + ], + sources: [hvr-ghc] + } + } before_install: @@ -12,21 +26,33 @@ before_install: - PATH="/opt/cabal/$CABALVER/bin:$PATH" - export PATH - - .travis/print-env.sh + - env + - ghc --version + - cabal --version + - alex --version + - happy --version + - cabal update install: - - .travis/install-cabal-happy-alex.sh - - .travis/install-ghc.sh - - .travis/install-ghc-shake.sh + + - travis_retry git clone git://git.haskell.org/ghc --recurse-submodules + + # Travis clones the project into ".", but we need it as a child directory + # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake + # ".git" directory into the appropriate location, and perform a hard reset + # in order to regenerate the GHC-Shake files. + - mkdir ghc/shake-build + - mv .git ghc/shake-build + - ( cd ghc/shake-build && git reset --hard HEAD ) + + - ( cd ghc/shake-build && cabal install --only-dependencies ) + + - ( cd ghc && ./boot ) + - ( cd ghc && ./configure ) script: - - .travis/run-ghc-shake.sh + - ./ghc/shake-build/build.sh -j --no-progress cache: directories: - $HOME/.cabal - # - ghc/shake-build/.cabal-sandbox - # - ghc/shake-build/cabal.sandbox.config - -# before_cache: -# - rm -rf ghc/shake-build diff --git a/.travis/install-cabal-happy-alex.sh b/.travis/install-cabal-happy-alex.sh deleted file mode 100755 index 93df460..0000000 --- a/.travis/install-cabal-happy-alex.sh +++ /dev/null @@ -1,18 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[32m" # Green -RESET="\e[m" - -echo -e "${COLOR}GHC version:${RESET}" -ghc --version - -echo -e "${COLOR}Cabal version:${RESET}" -cabal --version - -echo -e "${COLOR}Update Cabal${RESET}" -cabal update - -echo -e "${COLOR}Install Alex+Happy${RESET}" -cabal install alex happy diff --git a/.travis/install-ghc-shake.sh b/.travis/install-ghc-shake.sh deleted file mode 100755 index c2b8774..0000000 --- a/.travis/install-ghc-shake.sh +++ /dev/null @@ -1,19 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[31m" # Red, because this file is serious business -RESET="\e[m" - -echo -e "${COLOR}Brutally hacking GHC-Shake to its proper location${RESET}" -SHAKEDIR="ghc/shake-build" -mkdir -p "$SHAKEDIR" -mv .git "$SHAKEDIR/" -( cd "$SHAKEDIR" && git reset --hard HEAD ) - -echo -e "${COLOR}Installing deps into sandbox${RESET}" -( cd "$SHAKEDIR" && cabal sandbox init ) -( cd "$SHAKEDIR" && cabal install --only-dependencies . ) - -echo -e "${COLOR}GHC boot/configure${RESET}" -( cd ghc && ./boot && ./configure) diff --git a/.travis/install-ghc.sh b/.travis/install-ghc.sh deleted file mode 100755 index fc34ea4..0000000 --- a/.travis/install-ghc.sh +++ /dev/null @@ -1,12 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[34m" # Blue -RESET="\e[m" - -echo -e "${COLOR}Clone GHC source${RESET}" -git clone git://git.haskell.org/ghc - -echo -e "${COLOR}Initialize GHC submodules${RESET}" -( cd ghc && git submodule update --init ) diff --git a/.travis/print-env.sh b/.travis/print-env.sh deleted file mode 100755 index c09c11f..0000000 --- a/.travis/print-env.sh +++ /dev/null @@ -1,9 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[32m" # Green -RESET="\e[m" - -echo -e "${COLOR}Environment:${RESET}" -env diff --git a/.travis/run-ghc-shake.sh b/.travis/run-ghc-shake.sh deleted file mode 100755 index 7b867b7..0000000 --- a/.travis/run-ghc-shake.sh +++ /dev/null @@ -1,9 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[32m" # Green -RESET="\e[m" - -echo -e "${COLOR}Running Shake build system${RESET}" -( cd ghc && ./shake-build/build.cabal.sh ) diff --git a/build.cabal.sh b/build.cabal.sh index 65da82b..cf165b8 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -6,9 +6,10 @@ absoltueRoot="$(dirname "$(readlink -f "$0")")" cd "$absoltueRoot" # Initialize sandbox if necessary -if ! $(cabal sandbox hc-pkg list 2>&1 > /dev/null); then +if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then cabal sandbox init cabal install \ + --dependencies-only \ --disable-library-profiling \ --disable-shared fi diff --git a/build.sh b/build.sh index f09c30c..82cbb93 100755 --- a/build.sh +++ b/build.sh @@ -2,7 +2,7 @@ set -euo pipefail -root="$(dirname "$0")" +root="$(dirname "$(readlink -f "$0")")" mkdir -p "$root/.shake" From git at git.haskell.org Thu Oct 26 23:54:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add DepIncludeDirs package data option. (91a8bab) Message-ID: <20171026235436.8CFCE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91a8babed3f640ecd972c7a20fd574e3853250d1/ghc >--------------------------------------------------------------- commit 91a8babed3f640ecd972c7a20fd574e3853250d1 Author: Andrey Mokhov Date: Mon Jan 19 11:49:40 2015 +0000 Add DepIncludeDirs package data option. >--------------------------------------------------------------- 91a8babed3f640ecd972c7a20fd574e3853250d1 src/Oracles/PackageData.hs | 42 ++++++++++++++++++++++-------------------- src/Package/Base.hs | 2 +- src/Package/Compile.hs | 1 + src/Targets.hs | 1 + 4 files changed, 25 insertions(+), 21 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 38accfe..760f47e 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -23,16 +23,17 @@ data PackageData = Version FilePath | PackageKey FilePath | Synopsis FilePath -data MultiPackageData = Modules FilePath - | SrcDirs FilePath - | IncludeDirs FilePath - | Deps FilePath - | DepKeys FilePath - | DepNames FilePath - | CppArgs FilePath - | HsArgs FilePath - | CcArgs FilePath - | CSrcs FilePath +data MultiPackageData = Modules FilePath + | SrcDirs FilePath + | IncludeDirs FilePath + | Deps FilePath + | DepKeys FilePath + | DepNames FilePath + | CppArgs FilePath + | HsArgs FilePath + | CcArgs FilePath + | CSrcs FilePath + | DepIncludeDirs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -53,16 +54,17 @@ instance ShowArg PackageData where instance ShowArgs MultiPackageData where showArgs packageData = do let (key, path, defaultValue) = case packageData of - Modules path -> ("MODULES" , path, "" ) - SrcDirs path -> ("HS_SRC_DIRS" , path, ".") - IncludeDirs path -> ("INCLUDE_DIRS", path, ".") - Deps path -> ("DEPS" , path, "" ) - DepKeys path -> ("DEP_KEYS" , path, "" ) - DepNames path -> ("DEP_NAMES" , path, "" ) - CppArgs path -> ("CPP_OPTS" , path, "" ) - HsArgs path -> ("HC_OPTS" , path, "" ) - CcArgs path -> ("CC_OPTS" , path, "" ) - CSrcs path -> ("C_SRCS" , path, "" ) + Modules path -> ("MODULES" , path, "" ) + SrcDirs path -> ("HS_SRC_DIRS" , path, ".") + IncludeDirs path -> ("INCLUDE_DIRS" , path, ".") + Deps path -> ("DEPS" , path, "" ) + DepKeys path -> ("DEP_KEYS" , path, "" ) + DepNames path -> ("DEP_NAMES" , path, "" ) + CppArgs path -> ("CPP_OPTS" , path, "" ) + HsArgs path -> ("HC_OPTS" , path, "" ) + CcArgs path -> ("CC_OPTS" , path, "" ) + CSrcs path -> ("C_SRCS" , path, "" ) + DepIncludeDirs path -> ("DEP_LIB_REL_DIRS", path, "" ) fullKey = replaceSeparators '_' $ path ++ "_" ++ key pkgData = path "package-data.mk" res <- askOracle $ PackageDataKey (pkgData, fullKey) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index cf29e59..aafc85b 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -155,7 +155,7 @@ findModuleFiles pathDist directories suffixes = do ] $ \file -> do let dir = takeDirectory file dirExists <- liftIO $ S.doesDirectoryExist dir - when dirExists $ return file + when dirExists $ return $ unifyPath file files <- getDirectoryFiles "" fileList return $ map unifyPath files diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index d99e2bf..e98f1a5 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -35,6 +35,7 @@ gccArgs (Package _ path _) (_, dist, _) srcs result = , commonCcArgs , commonCcWarninigArgs , pathArgs "-I" path $ IncludeDirs pathDist + , pathArgs "-I" path $ DepIncludeDirs pathDist , args ("-c":srcs) , args ["-o", result] ] diff --git a/src/Targets.hs b/src/Targets.hs index cf1ceb2..847c1fa 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -21,6 +21,7 @@ libraryPackagesInStage Stage1 = , "deepseq" , "directory" , "filepath" + , "ghc-prim" , "parallel" , "pretty" , "stm" From git at git.haskell.org Thu Oct 26 23:54:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create package database directories using oracles. (6e00b02) Message-ID: <20171026235437.759CE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e00b0238ebb28460f69ed0aa68c54d52d7e223a/ghc >--------------------------------------------------------------- commit 6e00b0238ebb28460f69ed0aa68c54d52d7e223a Author: Andrey Mokhov Date: Tue Jan 19 03:14:31 2016 +0000 Create package database directories using oracles. Fix #176. >--------------------------------------------------------------- 6e00b0238ebb28460f69ed0aa68c54d52d7e223a shaking-up-ghc.cabal | 1 + src/Oracles/PackageDb.hs | 23 +++++++++++++++++++++++ src/Rules/Actions.hs | 6 +++--- src/Rules/Cabal.hs | 14 -------------- src/Rules/Oracles.hs | 3 +++ src/Rules/Wrappers/GhcPkg.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 15 +++++++++++---- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Paths.hs | 19 +++++++------------ 9 files changed, 51 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 6e00b0238ebb28460f69ed0aa68c54d52d7e223a From git at git.haskell.org Thu Oct 26 23:54:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #101 from quchen/master (0d43a40) Message-ID: <20171026235439.31C333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0d43a40a2b42a3332e41e7e096b2d0834dffeb53/ghc >--------------------------------------------------------------- commit 0d43a40a2b42a3332e41e7e096b2d0834dffeb53 Merge: b18f0e3 d0ffc1f Author: Andrey Mokhov Date: Tue Jan 5 11:31:03 2016 +0000 Merge pull request #101 from quchen/master Rework Travis CI script >--------------------------------------------------------------- 0d43a40a2b42a3332e41e7e096b2d0834dffeb53 .travis.yml | 52 +++++++++++++++++++++++++++---------- .travis/install-cabal-happy-alex.sh | 18 ------------- .travis/install-ghc-shake.sh | 19 -------------- .travis/install-ghc.sh | 12 --------- .travis/print-env.sh | 9 ------- .travis/run-ghc-shake.sh | 9 ------- build.cabal.sh | 3 ++- build.sh | 2 +- 8 files changed, 42 insertions(+), 82 deletions(-) From git at git.haskell.org Thu Oct 26 23:54:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, do minor refactoring. (79bc4c9) Message-ID: <20171026235440.191693A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79bc4c9d2452c1e1621beef3a892c7bdf00199cd/ghc >--------------------------------------------------------------- commit 79bc4c9d2452c1e1621beef3a892c7bdf00199cd Author: Andrey Mokhov Date: Mon Jan 19 16:16:54 2015 +0000 Add comments, do minor refactoring. >--------------------------------------------------------------- 79bc4c9d2452c1e1621beef3a892c7bdf00199cd src/Oracles/PackageData.hs | 6 +++-- src/Package.hs | 23 +++++++------------ src/Package/Base.hs | 11 +++++++-- src/Package/Data.hs | 18 ++++++++++++--- src/Targets.hs | 56 +++++++++++++++++++++++++--------------------- src/Ways.hs | 35 ++++++++++++++++++++--------- 6 files changed, 90 insertions(+), 59 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 79bc4c9d2452c1e1621beef3a892c7bdf00199cd From git at git.haskell.org Thu Oct 26 23:54:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix "dirs" to "dir" for gmp and iconv libraries (36b7f4d) Message-ID: <20171026235440.EBDBB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/36b7f4de03fd661e6439b84a3d03b4ca00ca6bcc/ghc >--------------------------------------------------------------- commit 36b7f4de03fd661e6439b84a3d03b4ca00ca6bcc Author: Karel Gardas Date: Tue Jan 19 07:38:52 2016 +0100 fix "dirs" to "dir" for gmp and iconv libraries >--------------------------------------------------------------- 36b7f4de03fd661e6439b84a3d03b4ca00ca6bcc cfg/system.config.in | 8 ++++---- src/Oracles/Config/Setting.hs | 16 ++++++++-------- src/Rules/Gmp.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 8 ++++---- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- 5 files changed, 22 insertions(+), 22 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 126387f..0eb775a 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -100,11 +100,11 @@ conf-ld-linker-args-stage2 = @CONF_LD_LINKER_OPTS_STAGE2@ # Include and library directories: #================================= -iconv-include-dirs = @ICONV_INCLUDE_DIRS@ -iconv-lib-dirs = @ICONV_LIB_DIRS@ +iconv-include-dir = @ICONV_INCLUDE_DIRS@ +iconv-lib-dir = @ICONV_LIB_DIRS@ -gmp-include-dirs = @GMP_INCLUDE_DIRS@ -gmp-lib-dirs = @GMP_LIB_DIRS@ +gmp-include-dir = @GMP_INCLUDE_DIRS@ +gmp-lib-dir = @GMP_LIB_DIRS@ use-system-ffi = @UseSystemLibFFI@ ffi-include-dir = @FFIIncludeDir@ diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index f4540cc..3502929 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -49,16 +49,16 @@ data Setting = BuildArch | TargetVendor | FfiIncludeDir | FfiLibDir + | GmpIncludeDir + | GmpLibDir + | IconvIncludeDir + | IconvLibDir data SettingList = ConfCcArgs Stage | ConfCppArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage - | GmpIncludeDirs - | GmpLibDirs | HsCppArgs - | IconvIncludeDirs - | IconvLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of @@ -92,6 +92,10 @@ setting key = askConfig $ case key of TargetVendor -> "target-vendor" FfiIncludeDir -> "ffi-include-dir" FfiLibDir -> "ffi-lib-dir" + GmpIncludeDir -> "gmp-include-dir" + GmpLibDir -> "gmp-lib-dir" + IconvIncludeDir -> "iconv-include-dir" + IconvLibDir -> "iconv-lib-dir" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -99,11 +103,7 @@ settingList key = fmap words $ askConfig $ case key of ConfCppArgs stage -> "conf-cpp-args-" ++ stageString stage ConfGccLinkerArgs stage -> "conf-gcc-linker-args-" ++ stageString stage ConfLdLinkerArgs stage -> "conf-ld-linker-args-" ++ stageString stage - GmpIncludeDirs -> "gmp-include-dirs" - GmpLibDirs -> "gmp-lib-dirs" HsCppArgs -> "hs-cpp-args" - IconvIncludeDirs -> "iconv-include-dirs" - IconvLibDirs -> "iconv-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index ec14b36..702e645 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -62,10 +62,10 @@ configureArguments = do configureIntGmpArguments :: Action [String] configureIntGmpArguments = do - includes <- settingList GmpIncludeDirs - libs <- settingList GmpLibDirs - return $ map ("--with-gmp-includes=" ++) includes - ++ map ("--with-gmp-libraries=" ++) libs + includes <- setting GmpIncludeDir + libs <- setting GmpLibDir + return $ map ("--with-gmp-includes=" ++) [includes] + ++ map ("--with-gmp-libraries=" ++) [libs] -- TODO: we rebuild gmp every time. gmpRules :: Rules () diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 06787c5..51d0e6b 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -79,10 +79,10 @@ configureArgs = do , conf "LDFLAGS" ldFlags , conf "CPPFLAGS" cppFlags , appendSubD "--gcc-options" $ cFlags <> ldFlags - , conf "--with-iconv-includes" $ argSettingList IconvIncludeDirs - , conf "--with-iconv-libraries" $ argSettingList IconvLibDirs - , conf "--with-gmp-includes" $ argSettingList GmpIncludeDirs - , conf "--with-gmp-libraries" $ argSettingList GmpLibDirs + , conf "--with-iconv-includes" $ argSetting IconvIncludeDir + , conf "--with-iconv-libraries" $ argSetting IconvLibDir + , conf "--with-gmp-includes" $ argSetting GmpIncludeDir + , conf "--with-gmp-libraries" $ argSetting GmpLibDir , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" $ argStagedBuilderPath Gcc ] diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index c4e518b..4529af8 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -17,7 +17,7 @@ hsc2hsBuilderArgs :: Args hsc2hsBuilderArgs = builder Hsc2Hs ? do stage <- getStage ccPath <- lift . builderPath $ Gcc stage - gmpDirs <- getSettingList GmpIncludeDirs + gmpDir <- getSetting GmpIncludeDir cFlags <- getCFlags lFlags <- getLFlags top <- getTopDirectory @@ -32,7 +32,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" - , append $ map ("-I" ++) gmpDirs + , append $ map ("-I" ++) [gmpDir] , append $ map ("--cflag=" ++) cFlags , append $ map ("--lflag=" ++) lFlags , notStage0 ? crossCompiling ? arg "--cross-compile" From git at git.haskell.org Thu Oct 26 23:54:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Temporarily disable haddock, see #98. (2d1efa2) Message-ID: <20171026235442.B93433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d1efa2110af8b0aa2b5aa641e61f8c906e02d38/ghc >--------------------------------------------------------------- commit 2d1efa2110af8b0aa2b5aa641e61f8c906e02d38 Author: Andrey Mokhov Date: Tue Jan 5 11:39:38 2016 +0000 Temporarily disable haddock, see #98. >--------------------------------------------------------------- 2d1efa2110af8b0aa2b5aa641e61f8c906e02d38 src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 6107f6f..aba4a48 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -82,7 +82,7 @@ laxDependencies :: Bool laxDependencies = False buildHaddock :: Predicate -buildHaddock = return True +buildHaddock = return False -- FIXME: should be return True, see #98 buildSystemConfigFile :: Bool buildSystemConfigFile = False From git at git.haskell.org Thu Oct 26 23:54:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix include paths for Gcc. (2c7003a) Message-ID: <20171026235443.AA8993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c7003a009d1205a73430b21bdc05caab23a8d85/ghc >--------------------------------------------------------------- commit 2c7003a009d1205a73430b21bdc05caab23a8d85 Author: Andrey Mokhov Date: Mon Jan 19 17:03:40 2015 +0000 Fix include paths for Gcc. >--------------------------------------------------------------- 2c7003a009d1205a73430b21bdc05caab23a8d85 src/Oracles/Builder.hs | 2 +- src/Package/Base.hs | 9 ++++++++- src/Package/Compile.hs | 3 +-- src/Package/Dependencies.hs | 2 +- 4 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index e52cc58..dc41507 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -119,7 +119,7 @@ interestingInfo builder ss = case builder of Ld -> prefixAndSuffix 4 0 ss Gcc _ -> if head ss == "-MM" then prefixAndSuffix 1 1 ss - else ss + else prefixAndSuffix 0 4 ss Ghc _ -> if head ss == "-M" then prefixAndSuffix 1 1 ss else prefixAndSuffix 0 4 ss diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 8e12f15..e2031b6 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -7,7 +7,8 @@ module Package.Base ( Package (..), Settings (..), TodoItem (..), defaultSettings, libraryPackage, standardLibrary, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - pathArgs, packageArgs, includeGhcArgs, pkgHsSources, + pathArgs, packageArgs, + includeGccArgs, includeGhcArgs, pkgHsSources, pkgDepHsObjects, pkgLibHsObjects, pkgCObjects, argSizeLimit, sourceDependecies, @@ -99,6 +100,12 @@ packageArgs stage pathDist = do else productArgs "-package-name" (arg $ PackageKey pathDist) <> productArgs "-package" (args $ Deps pathDist) ] +includeGccArgs :: FilePath -> FilePath -> Args +includeGccArgs path dist = + let pathDist = path dist + in args [ pathArgs "-I" path $ IncludeDirs pathDist + , pathArgs "-I" path $ DepIncludeDirs pathDist ] + includeGhcArgs :: FilePath -> FilePath -> Args includeGhcArgs path dist = let pathDist = path dist diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index e98f1a5..eb2417f 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -34,8 +34,7 @@ gccArgs (Package _ path _) (_, dist, _) srcs result = in args [ args $ CcArgs pathDist , commonCcArgs , commonCcWarninigArgs - , pathArgs "-I" path $ IncludeDirs pathDist - , pathArgs "-I" path $ DepIncludeDirs pathDist + , includeGccArgs path dist , args ("-c":srcs) , args ["-o", result] ] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index f87580a..abee3f3 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -51,7 +51,7 @@ gccArgs sourceFile (Package _ path _) (stage, dist, _) = , args $ CcArgs pathDist , commonCcArgs , commonCcWarninigArgs - , pathArgs "-I" path $ IncludeDirs pathDist + , includeGccArgs path dist , args ["-MF", unifyPath depFile] , args ["-x", "c"] , arg $ unifyPath sourceFile ] From git at git.haskell.org Thu Oct 26 23:54:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #183 from kgardas/fix_dirs_to_dir (875d9ca) Message-ID: <20171026235444.760883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/875d9ca47a82c58c2e5e99864f67dc5f3559dffc/ghc >--------------------------------------------------------------- commit 875d9ca47a82c58c2e5e99864f67dc5f3559dffc Merge: 6e00b02 36b7f4d Author: Andrey Mokhov Date: Tue Jan 19 08:54:29 2016 +0000 Merge pull request #183 from kgardas/fix_dirs_to_dir fix "dirs" to "dir" for gmp and iconv libraries >--------------------------------------------------------------- 875d9ca47a82c58c2e5e99864f67dc5f3559dffc cfg/system.config.in | 8 ++++---- src/Oracles/Config/Setting.hs | 16 ++++++++-------- src/Rules/Gmp.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 8 ++++---- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- 5 files changed, 22 insertions(+), 22 deletions(-) From git at git.haskell.org Thu Oct 26 23:54:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix readlink for os x. (0b0e1d6) Message-ID: <20171026235446.486F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b0e1d68b1e58b23c2dff0edd0c4135e0cb3a583/ghc >--------------------------------------------------------------- commit 0b0e1d68b1e58b23c2dff0edd0c4135e0cb3a583 Author: Moritz Angermann Date: Tue Jan 5 20:43:29 2016 +0800 Fix readlink for os x. This should fix #104. >--------------------------------------------------------------- 0b0e1d68b1e58b23c2dff0edd0c4135e0cb3a583 build.sh | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 82cbb93..de9b9d7 100755 --- a/build.sh +++ b/build.sh @@ -1,8 +1,34 @@ #!/usr/bin/env bash +# readlink on os x, doesn't support -f, to prevent the +# need of installing coreutils (e.g. through brew, just +# for readlink, we use the follownig substitute. +# +# source: http://stackoverflow.com/a/1116890 +function rl { + TARGET_FILE=$1 + + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE=$(basename "$TARGET_FILE") + + # Iterate down a (possible) chain of symlinks + while [ -L "$TARGET_FILE" ] + do + TARGET_FILE=$(readlink "$TARGET_FILE") + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE=$(basename "$TARGET_FILE") + done + + # Compute the canonicalized name by finding the physical path + # for the directory we're in and appending the target file. + PHYS_DIR=`pwd -P` + RESULT=$PHYS_DIR/$TARGET_FILE + echo $RESULT +} + set -euo pipefail -root="$(dirname "$(readlink -f "$0")")" +root="$(dirname "$(rl "$0")")" mkdir -p "$root/.shake" From git at git.haskell.org Thu Oct 26 23:54:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add remaining library packages to Targets.hs. (8a860e6) Message-ID: <20171026235447.691EB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8a860e62574675274d1d7158503dfd5b4bb21e15/ghc >--------------------------------------------------------------- commit 8a860e62574675274d1d7158503dfd5b4bb21e15 Author: Andrey Mokhov Date: Tue Jan 20 04:39:40 2015 +0000 Add remaining library packages to Targets.hs. >--------------------------------------------------------------- 8a860e62574675274d1d7158503dfd5b4bb21e15 src/Oracles/Builder.hs | 1 + src/Package.hs | 6 +-- src/Package/Base.hs | 61 ++++++++++++++++-------- src/Package/Compile.hs | 8 ++-- src/Package/Data.hs | 17 +++---- src/Package/Dependencies.hs | 8 ++-- src/Package/Library.hs | 6 +-- src/Targets.hs | 112 +++++++++++++++++++++++++++++++++++--------- src/Ways.hs | 3 +- 9 files changed, 157 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8a860e62574675274d1d7158503dfd5b4bb21e15 From git at git.haskell.org Thu Oct 26 23:54:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CI regression, minor revision. (8f68b8b) Message-ID: <20171026235448.31CCD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f68b8bc8dc40a17eb8c0816437a4b474b9def78/ghc >--------------------------------------------------------------- commit 8f68b8bc8dc40a17eb8c0816437a4b474b9def78 Author: Andrey Mokhov Date: Tue Jan 19 09:34:35 2016 +0000 Fix CI regression, minor revision. See #183. >--------------------------------------------------------------- 8f68b8bc8dc40a17eb8c0816437a4b474b9def78 cfg/system.config.in | 2 +- src/Rules/Gmp.hs | 4 ++-- src/Rules/Libffi.hs | 8 ++++---- src/Settings/Builders/Hsc2Hs.hs | 2 +- 4 files changed, 8 insertions(+), 8 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 0eb775a..43730a2 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -106,7 +106,7 @@ iconv-lib-dir = @ICONV_LIB_DIRS@ gmp-include-dir = @GMP_INCLUDE_DIRS@ gmp-lib-dir = @GMP_LIB_DIRS@ -use-system-ffi = @UseSystemLibFFI@ +use-system-ffi = @UseSystemLibFFI@ ffi-include-dir = @FFIIncludeDir@ ffi-lib-dir = @FFILibDir@ diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 702e645..b6bfdf0 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -64,8 +64,8 @@ configureIntGmpArguments :: Action [String] configureIntGmpArguments = do includes <- setting GmpIncludeDir libs <- setting GmpLibDir - return $ map ("--with-gmp-includes=" ++) [includes] - ++ map ("--with-gmp-libraries=" ++) [libs] + return $ map ("--with-gmp-includes=" ++) (words includes) + ++ map ("--with-gmp-libraries=" ++) (words libs) -- TODO: we rebuild gmp every time. gmpRules :: Rules () diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 97ebc2d..0f4e05a 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -71,13 +71,13 @@ libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - ffi_header_dir <- setting FfiIncludeDir - use_system_ffi <- flag UseSystemFfi - if use_system_ffi + ffiHeaderDir <- setting FfiIncludeDir + useSystemFfi <- flag UseSystemFfi + if useSystemFfi then do putBuild "| System supplied FFI library will be used" forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = ffi_header_dir -/- file + let src = ffiHeaderDir -/- file copyFile src (rtsBuildPath -/- file) putSuccess $ "| Successfully copied system supplied FFI library header files" else do diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 4529af8..ffa3b1a 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -32,7 +32,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" - , append $ map ("-I" ++) [gmpDir] + , append . map ("-I" ++) $ words gmpDir , append $ map ("--cflag=" ++) cFlags , append $ map ("--lflag=" ++) lFlags , notStage0 ? crossCompiling ? arg "--cross-compile" From git at git.haskell.org Thu Oct 26 23:54:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds -no-hs-main to iservBin (8718da8) Message-ID: <20171026235449.C11933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8718da8fe567d0ab9fa3b0f85726d73c9ed04cb3/ghc >--------------------------------------------------------------- commit 8718da8fe567d0ab9fa3b0f85726d73c9ed04cb3 Author: Moritz Angermann Date: Tue Jan 5 20:44:55 2016 +0800 Adds -no-hs-main to iservBin Fixes #102. But does not *yet* include the generation of the wrapper script. >--------------------------------------------------------------- 8718da8fe567d0ab9fa3b0f85726d73c9ed04cb3 shaking-up-ghc.cabal | 1 + src/Settings/Args.hs | 2 ++ src/Settings/Packages/IservBin.hs | 10 ++++++++++ 3 files changed, 13 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 2eb9f72..00fb408 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -87,6 +87,7 @@ executable ghc-shake , Settings.Packages.Haddock , Settings.Packages.Hp2ps , Settings.Packages.IntegerGmp + , Settings.Packages.IservBin , Settings.Packages.Rts , Settings.Packages.RunGhc , Settings.TargetDirectory diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index a677c80..fb121ed 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -27,6 +27,7 @@ import Settings.Packages.GhcPrim import Settings.Packages.Haddock import Settings.Packages.Hp2ps import Settings.Packages.IntegerGmp +import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc import Settings.User @@ -72,5 +73,6 @@ defaultPackageArgs = mconcat , haddockPackageArgs , hp2psPackageArgs , integerGmpPackageArgs + , iservBinPackageArgs , rtsPackageArgs , runGhcPackageArgs ] diff --git a/src/Settings/Packages/IservBin.hs b/src/Settings/Packages/IservBin.hs new file mode 100644 index 0000000..5ad3bd5 --- /dev/null +++ b/src/Settings/Packages/IservBin.hs @@ -0,0 +1,10 @@ +module Settings.Packages.IservBin (iservBinPackageArgs) where + +import Expression +import GHC (iservBin) +import Predicates (builderGhc, package) + +iservBinPackageArgs :: Args +iservBinPackageArgs = package iservBin ? do + mconcat [ builderGhc ? + mconcat [ arg "-no-hs-main" ]] From git at git.haskell.org Thu Oct 26 23:54:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add base and integer-gmp2 to the list of targets. (2d24ed4) Message-ID: <20171026235451.2D2F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d24ed4ae03015db98fb7ca1a86fe490b4540d75/ghc >--------------------------------------------------------------- commit 2d24ed4ae03015db98fb7ca1a86fe490b4540d75 Author: Andrey Mokhov Date: Tue Jan 20 16:23:12 2015 +0000 Add base and integer-gmp2 to the list of targets. >--------------------------------------------------------------- 2d24ed4ae03015db98fb7ca1a86fe490b4540d75 src/Package/Base.hs | 4 ++- src/Package/Compile.hs | 3 ++- src/Package/Data.hs | 4 +-- src/Package/Dependencies.hs | 5 ++-- src/Targets.hs | 65 ++++++++++++++++++++++++--------------------- 5 files changed, 45 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 2d24ed4ae03015db98fb7ca1a86fe490b4540d75 From git at git.haskell.org Thu Oct 26 23:54:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant case. (bbbf03c) Message-ID: <20171026235452.3275E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbbf03c99d8c0264317aa5527baec180caf94388/ghc >--------------------------------------------------------------- commit bbbf03c99d8c0264317aa5527baec180caf94388 Author: Andrey Mokhov Date: Tue Jan 19 11:56:35 2016 +0000 Drop redundant case. [skip ci] >--------------------------------------------------------------- bbbf03c99d8c0264317aa5527baec180caf94388 src/Settings/Packages/Rts.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 58b76cf..e41e2bf 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -23,11 +23,9 @@ rtsLibffiLibraryName = do use_system_ffi <- flag UseSystemFfi windows <- windowsHost case (use_system_ffi, windows) of - (True, False) -> return "ffi" + (True , False) -> return "ffi" (False, False) -> return "Cffi" - (_, True) -> return "Cffi-6" - (_, _) -> error "Unsupported FFI library configuration case" - + (_ , True ) -> return "Cffi-6" rtsPackageArgs :: Args rtsPackageArgs = package rts ? do From git at git.haskell.org Thu Oct 26 23:54:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #107 from angerman/feature/iserv (f4ef847) Message-ID: <20171026235453.4718A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4ef847b4f4ea44ff8ceeefcdbe7fdb5dcaac336/ghc >--------------------------------------------------------------- commit f4ef847b4f4ea44ff8ceeefcdbe7fdb5dcaac336 Merge: 2d1efa2 8718da8 Author: Andrey Mokhov Date: Tue Jan 5 12:52:41 2016 +0000 Merge pull request #107 from angerman/feature/iserv Adds -no-hs-main to iservBin >--------------------------------------------------------------- f4ef847b4f4ea44ff8ceeefcdbe7fdb5dcaac336 shaking-up-ghc.cabal | 1 + src/Settings/Args.hs | 2 ++ src/Settings/Packages/IservBin.hs | 10 ++++++++++ 3 files changed, 13 insertions(+) From git at git.haskell.org Thu Oct 26 23:54:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (e809d1c) Message-ID: <20171026235454.92CFF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e809d1c945a36f87fc1c006e8b4b88296b5ea48e/ghc >--------------------------------------------------------------- commit e809d1c945a36f87fc1c006e8b4b88296b5ea48e Author: Andrey Mokhov Date: Tue Jan 20 16:27:51 2015 +0000 Clean up. >--------------------------------------------------------------- e809d1c945a36f87fc1c006e8b4b88296b5ea48e src/Targets.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Targets.hs b/src/Targets.hs index 595c38f..2ff6eae 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -60,7 +60,7 @@ targetPackages = baseConfArgs :: Settings -> Settings baseConfArgs settings = - settings { customConfArgs = arg $ "--flags=" ++ show integerLibrary } + settings { customConfArgs = arg $ "--flags=" ++ integerLibraryName } -- see Note [Cabal package weirdness] cabalTraits :: (String, Settings -> Settings) From git at git.haskell.org Thu Oct 26 23:54:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (11f78b1) Message-ID: <20171026235455.B08F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/11f78b18b914bb72e1f1cff75cadc9d7c4012ac2/ghc >--------------------------------------------------------------- commit 11f78b18b914bb72e1f1cff75cadc9d7c4012ac2 Author: Andrey Mokhov Date: Tue Jan 19 12:02:52 2016 +0000 Minor revision. [skip ci] >--------------------------------------------------------------- 11f78b18b914bb72e1f1cff75cadc9d7c4012ac2 src/Settings/Packages/Rts.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e41e2bf..f67b709 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,9 +20,9 @@ rtsConf = pkgPath rts -/- targetDirectory Stage1 rts -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do - use_system_ffi <- flag UseSystemFfi - windows <- windowsHost - case (use_system_ffi, windows) of + useSystemFfi <- flag UseSystemFfi + windows <- windowsHost + case (useSystemFfi, windows) of (True , False) -> return "ffi" (False, False) -> return "Cffi" (_ , True ) -> return "Cffi-6" From git at git.haskell.org Thu Oct 26 23:54:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds quotes. (a1f3c8d) Message-ID: <20171026235456.B8C663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1f3c8df8f27422eef777f4b9ff4e6a844c88532/ghc >--------------------------------------------------------------- commit a1f3c8df8f27422eef777f4b9ff4e6a844c88532 Author: Moritz Angermann Date: Tue Jan 5 20:54:18 2016 +0800 Adds quotes. >--------------------------------------------------------------- a1f3c8df8f27422eef777f4b9ff4e6a844c88532 build.sh | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/build.sh b/build.sh index de9b9d7..a3f0bf5 100755 --- a/build.sh +++ b/build.sh @@ -1,33 +1,33 @@ #!/usr/bin/env bash +set -euo pipefail + # readlink on os x, doesn't support -f, to prevent the # need of installing coreutils (e.g. through brew, just # for readlink, we use the follownig substitute. # # source: http://stackoverflow.com/a/1116890 function rl { - TARGET_FILE=$1 + TARGET_FILE="$1" cd "$(dirname "$TARGET_FILE")" - TARGET_FILE=$(basename "$TARGET_FILE") + TARGET_FILE="$(basename "$TARGET_FILE")" # Iterate down a (possible) chain of symlinks while [ -L "$TARGET_FILE" ] do - TARGET_FILE=$(readlink "$TARGET_FILE") + TARGET_FILE="$(readlink "$TARGET_FILE")" cd "$(dirname "$TARGET_FILE")" - TARGET_FILE=$(basename "$TARGET_FILE") + TARGET_FILE="$(basename "$TARGET_FILE")" done # Compute the canonicalized name by finding the physical path # for the directory we're in and appending the target file. - PHYS_DIR=`pwd -P` - RESULT=$PHYS_DIR/$TARGET_FILE - echo $RESULT + PHYS_DIR="$(pwd -P)" + RESULT="$PHYS_DIR/$TARGET_FILE" + echo "$RESULT" } -set -euo pipefail - root="$(dirname "$(rl "$0")")" mkdir -p "$root/.shake" From git at git.haskell.org Thu Oct 26 23:54:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: do not pass --with-intree-gmp to configure when system gmp is used (dc8dbcc) Message-ID: <20171026235459.6E5D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dc8dbcc5a9c621a3eb4fb99b0e7d24b2e1a5a967/ghc >--------------------------------------------------------------- commit dc8dbcc5a9c621a3eb4fb99b0e7d24b2e1a5a967 Author: Karel Gardas Date: Tue Jan 19 21:42:08 2016 +0100 do not pass --with-intree-gmp to configure when system gmp is used >--------------------------------------------------------------- dc8dbcc5a9c621a3eb4fb99b0e7d24b2e1a5a967 src/Settings/Packages/IntegerGmp.hs | 18 +++++++++++++----- 1 file changed, 13 insertions(+), 5 deletions(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 7122457..fbb7101 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -4,7 +4,9 @@ import Base import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) +import Settings.Builders.Common import Settings.Paths +import Oracles.Config.Setting -- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? @@ -14,11 +16,17 @@ import Settings.Paths integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" + gmp_includedir <- getSetting GmpIncludeDir + gmp_libdir <- getSetting GmpLibDir + let gmp_args = if (gmp_includedir == "" && gmp_libdir == "") + then + [ arg "--configure-option=--with-intree-gmp" ] + else + [] + mconcat [ builder GhcCabal ? mconcat - [ arg "--configure-option=--with-intree-gmp" - , appendSub "--configure-option=CFLAGS" [includeGmp] - , appendSub "--gcc-options" [includeGmp] ] + (gmp_args ++ + [ appendSub "--configure-option=CFLAGS" [includeGmp] + , appendSub "--gcc-options" [includeGmp] ] ) , builderGcc ? arg includeGmp ] - where - From git at git.haskell.org Thu Oct 26 23:54:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:54:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (7c2279b) Message-ID: <20171026235458.229033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c2279b523ce8b71dc0e9492380d8798a8b1b4f2/ghc >--------------------------------------------------------------- commit 7c2279b523ce8b71dc0e9492380d8798a8b1b4f2 Author: Andrey Mokhov Date: Wed Jan 21 23:20:52 2015 +0000 Add comments. >--------------------------------------------------------------- 7c2279b523ce8b71dc0e9492380d8798a8b1b4f2 src/Oracles.hs | 1 + src/Package.hs | 2 +- src/Package/Base.hs | 11 ++++++++--- src/Package/Data.hs | 4 ++-- src/Package/Dependencies.hs | 7 ++++--- src/Targets.hs | 19 +++++++++++++++++++ 6 files changed, 35 insertions(+), 9 deletions(-) diff --git a/src/Oracles.hs b/src/Oracles.hs index 80e2e60..4e6fe5b 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -11,6 +11,7 @@ module Oracles ( import Development.Shake.Config import Development.Shake.Util import qualified Data.HashMap.Strict as M +-- TODO: get rid of Bifunctor dependency import Data.Bifunctor import Base import Util diff --git a/src/Package.hs b/src/Package.hs index 4d24e2a..1931ea3 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -26,7 +26,7 @@ packageRules = do -- We build *only one* vanilla .o file (not sure why) -- We build .way_a file for each way (or its dynamic version). -- TODO: Check BUILD_GHCI_LIB flag to decide if .o is needed - -- TODO: move this into buildPackage + -- TODO: move this into a separate file (perhaps, to Targets.hs?) action $ when (buildWhen settings) $ do let pathDist = path dist buildDir = pathDist "build" diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 00b4356..88e357f 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -39,9 +39,9 @@ defaultSettings stage = Settings { customConfArgs = mempty, customCcArgs = mempty, - customLdArgs = mempty, - customCppArgs = mempty, - customDllArgs = mempty, + customLdArgs = mempty, -- currently not used + customCppArgs = mempty, -- currently not used + customDllArgs = mempty, -- only for compiler registerPackage = True, ways = defaultWays stage, buildWhen = return True @@ -54,6 +54,11 @@ defaultSettings stage = Settings -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to package.cabal -- Settings may be different for different combinations of Stage & FilePath +-- TODO: the above may be incorrect, settings seem to *only* depend on the +-- stage. In fact Stage seem to define FilePath and Settings, therefore we +-- can drop the TodoItem and replace it by [Stage] and two functions +-- * distDirectory :: Package -> Stage -> FilePath +-- * settings :: Package -> Stage -> Settings type TodoItem = (Stage, FilePath, Settings) -- pkgPath is the path to the source code relative to the root diff --git a/src/Package/Data.hs b/src/Package/Data.hs index b2de8c5..602993e 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -26,8 +26,8 @@ configureArgs stage settings = unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s cflags = [ commonCcArgs `filterOut` "-Werror" , args $ ConfCcArgs stage - -- , customCcArgs settings -- TODO: fix - , commonCcWarninigArgs ] -- TODO: check if cflags are glued + -- , customCcArgs settings -- TODO: bring this back + , commonCcWarninigArgs ] -- TODO: check why cflags are glued ldflags = [ commonLdArgs , args $ ConfGccLinkerArgs stage , customLdArgs settings ] diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index 604034e..c861707 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -3,6 +3,7 @@ module Package.Dependencies (buildPackageDependencies) where import Package.Base +-- TODO: use oracles instead of arg files. argListDir :: FilePath argListDir = "shake/arg/buildPackageDependencies" @@ -49,9 +50,9 @@ gccArgs sourceFile (Package _ path _ _) (stage, dist, settings) = depFile = buildDir takeFileName sourceFile <.> "deps" in args [ args ["-E", "-MM"] -- TODO: add a Cpp Builder instead , args $ CcArgs pathDist - , commonCcArgs - , customCcArgs settings - , commonCcWarninigArgs + , commonCcArgs -- TODO: remove? + , customCcArgs settings -- TODO: Replace by customCppArgs? + , commonCcWarninigArgs -- TODO: remove? , includeGccArgs path dist , args ["-MF", unifyPath depFile] , args ["-x", "c"] diff --git a/src/Targets.hs b/src/Targets.hs index 2ff6eae..bc4c29d 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -15,12 +15,14 @@ instance Show IntegerLibrary where IntegerGmp2 -> "integer-gmp2" IntegerSimple -> "integer-simple" +-- TODO: keep or move to configuration files? see Note [configuration files] integerLibrary :: IntegerLibrary integerLibrary = IntegerGmp2 integerLibraryName :: String integerLibraryName = show integerLibrary +-- see Note [configuration files] buildHaddock :: Bool buildHaddock = True @@ -107,6 +109,23 @@ targetPackagesInStage stage = filter inStage targetPackages inStage (Package _ _ _ todoItems) = any matchStage todoItems matchStage (todoStage, _, _) = todoStage == stage +-- TODISCUSS -- Note [Cabal package weirdness] -- Find out if we can move the contents to just Cabal/ -- What is Cabal/cabal-install? Do we need it? + +-- TODISCUSS +-- Note [configuration files] +-- In this file we have two configuration options: integerLibrary and +-- buildHaddock. Arguably, their place should be among other configuration +-- options in the config files, however, moving integerLibrary there would +-- actually be quite painful, because it would then be confined to live in +-- the Action monad. +-- In general, shall we keep as many options as possible inside Shake, or +-- leave them in one place -- configuration files? We could try to move +-- everything to Shake which would be great: +-- * type safety and better abstractions +-- * useable outside the Action monad, e.g. for creating rules +-- * recompiling Shake is much faster then re-running configure script +-- * ... no more autoconf/configure and native Windows build?! Sign me up! +-- However, moving everything to Shake seems unfeasible at the moment. From git at git.haskell.org Thu Oct 26 23:55:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add rl function to the cabal build file as well. (2c635d5) Message-ID: <20171026235500.625B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c635d55d07ddeb2f827dd5d3007fc9b362b043a/ghc >--------------------------------------------------------------- commit 2c635d55d07ddeb2f827dd5d3007fc9b362b043a Author: Moritz Angermann Date: Tue Jan 5 20:58:07 2016 +0800 Add rl function to the cabal build file as well. >--------------------------------------------------------------- 2c635d55d07ddeb2f827dd5d3007fc9b362b043a build.cabal.sh | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index cf165b8..8add516 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -2,7 +2,33 @@ set -euo pipefail -absoltueRoot="$(dirname "$(readlink -f "$0")")" +# readlink on os x, doesn't support -f, to prevent the +# need of installing coreutils (e.g. through brew, just +# for readlink, we use the follownig substitute. +# +# source: http://stackoverflow.com/a/1116890 +function rl { + TARGET_FILE="$1" + + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE="$(basename "$TARGET_FILE")" + + # Iterate down a (possible) chain of symlinks + while [ -L "$TARGET_FILE" ] + do + TARGET_FILE="$(readlink "$TARGET_FILE")" + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE="$(basename "$TARGET_FILE")" + done + + # Compute the canonicalized name by finding the physical path + # for the directory we're in and appending the target file. + PHYS_DIR="$(pwd -P)" + RESULT="$PHYS_DIR/$TARGET_FILE" + echo "$RESULT" +} + +absoltueRoot="$(dirname "$(rl "$0")")" cd "$absoltueRoot" # Initialize sandbox if necessary From git at git.haskell.org Thu Oct 26 23:55:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: remove redundant Settings.Builders.Common import (88af41c) Message-ID: <20171026235502.E3E983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88af41cfff4e4c8e349693cdc423661a8f571c02/ghc >--------------------------------------------------------------- commit 88af41cfff4e4c8e349693cdc423661a8f571c02 Author: Karel Gardas Date: Tue Jan 19 22:06:12 2016 +0100 remove redundant Settings.Builders.Common import >--------------------------------------------------------------- 88af41cfff4e4c8e349693cdc423661a8f571c02 src/Settings/Packages/IntegerGmp.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index fbb7101..657eed0 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -4,7 +4,6 @@ import Base import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) -import Settings.Builders.Common import Settings.Paths import Oracles.Config.Setting From git at git.haskell.org Thu Oct 26 23:55:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: -Augenkrebs (e17f0e6) Message-ID: <20171026235503.D00093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e17f0e6575bf53cc23e966e343b32e0fc4705c86/ghc >--------------------------------------------------------------- commit e17f0e6575bf53cc23e966e343b32e0fc4705c86 Author: Moritz Angermann Date: Tue Jan 5 20:58:38 2016 +0800 -Augenkrebs >--------------------------------------------------------------- e17f0e6575bf53cc23e966e343b32e0fc4705c86 build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index a3f0bf5..719e85e 100755 --- a/build.sh +++ b/build.sh @@ -39,7 +39,7 @@ ghc \ -rtsopts \ -with-rtsopts=-I0 \ -outputdir="$root/.shake" \ - -j -O \ + -j -O \ -o "$root/.shake/build" "$root/.shake/build" \ From git at git.haskell.org Thu Oct 26 23:55:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Restrict ShowArgs and args to accept only lists. (9c218ad) Message-ID: <20171026235501.A11563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c218adf6e025572ae550302419f0bcc632d3be6/ghc >--------------------------------------------------------------- commit 9c218adf6e025572ae550302419f0bcc632d3be6 Author: Andrey Mokhov Date: Thu Jan 22 23:38:46 2015 +0000 Restrict ShowArgs and args to accept only lists. >--------------------------------------------------------------- 9c218adf6e025572ae550302419f0bcc632d3be6 src/Base.hs | 31 +++++++++++-------------------- src/Package/Base.hs | 14 ++++++++------ src/Package/Compile.hs | 2 +- src/Package/Data.hs | 9 +++++---- src/Package/Dependencies.hs | 6 +++--- 5 files changed, 28 insertions(+), 34 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 232bca2..fa9104a 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,7 +12,6 @@ module Base ( ShowArg (..), ShowArgs (..), arg, args, Condition (..), - (<+>), filterOut, productArgs, concatArgs ) where @@ -49,34 +48,26 @@ instance ShowArg String where instance ShowArg a => ShowArg (Action a) where showArg = (showArg =<<) --- Using the Creators' trick for overlapping String instances class ShowArgs a where - showArgs :: a -> Args - showListArgs :: [a] -> Args - showListArgs = mconcat . map showArgs + showArgs :: a -> Args -instance ShowArgs Char where - showArgs c = return [[c]] - showListArgs s = return [s] +instance ShowArgs [String] where + showArgs = return -instance ShowArgs a => ShowArgs [a] where - showArgs = showListArgs +instance ShowArgs [Arg] where + showArgs = sequence + +instance ShowArgs [Args] where + showArgs = mconcat instance ShowArgs a => ShowArgs (Action a) where showArgs = (showArgs =<<) --- TODO: improve args type safety args :: ShowArgs a => a -> Args args = showArgs arg :: ShowArg a => a -> Args -arg = args . showArg - --- Combine two heterogeneous ShowArgs values -(<+>) :: (ShowArgs a, ShowArgs b) => a -> b -> Args -a <+> b = (<>) <$> showArgs a <*> showArgs b - -infixr 6 <+> +arg a = args [showArg a] -- Filter out given arg(s) from a collection filterOut :: ShowArgs a => Args -> a -> Args @@ -85,7 +76,7 @@ filterOut as exclude = do filter (`notElem` exclude') <$> as -- Generate a cross product collection of two argument collections --- Example: productArgs ["-a", "-b"] "c" = arg ["-a", "c", "-b", "c"] +-- Example: productArgs ["-a", "-b"] "c" = args ["-a", "c", "-b", "c"] productArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args productArgs as bs = do as' <- showArgs as @@ -93,7 +84,7 @@ productArgs as bs = do return $ concat $ sequence [as', bs'] -- Similar to productArgs but concat resulting arguments pairwise --- Example: concatArgs ["-a", "-b"] "c" = arg ["-ac", "-bc"] +-- Example: concatArgs ["-a", "-b"] "c" = args ["-ac", "-bc"] concatArgs :: (ShowArgs a, ShowArgs b) => a -> b -> Args concatArgs as bs = do as' <- showArgs as diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 88e357f..d54320f 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -122,10 +122,11 @@ packageArgs stage pathDist = do , when (stage == Stage0) $ arg "-package-db libraries/bootstrapping.conf" , if usePackageKey - then productArgs "-this-package-key" (arg $ PackageKey pathDist) - <> productArgs "-package-key" (args $ DepKeys pathDist) - else productArgs "-package-name" (arg $ PackageKey pathDist) - <> productArgs "-package" (args $ Deps pathDist) ] + then productArgs ["-this-package-key"] [arg $ PackageKey pathDist] + <> productArgs ["-package-key" ] [args $ DepKeys pathDist] + else productArgs ["-package-name" ] [arg $ PackageKey pathDist] + <> productArgs ["-package" ] [args $ Deps pathDist] + ] includeGccArgs :: FilePath -> FilePath -> Args includeGccArgs path dist = @@ -145,8 +146,9 @@ includeGhcArgs path dist = [buildDir, unifyPath $ buildDir "autogen"] , pathArgs "-I" path $ IncludeDirs pathDist , arg "-optP-include" -- TODO: Shall we also add -cpp? - , concatArgs "-optP" $ - unifyPath $ buildDir "autogen/cabal_macros.h" ] + , concatArgs ["-optP"] + [unifyPath $ buildDir "autogen/cabal_macros.h"] + ] pkgHsSources :: FilePath -> FilePath -> Action [FilePath] pkgHsSources path dist = do diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs index 99aee33..fe9ba73 100644 --- a/src/Package/Compile.hs +++ b/src/Package/Compile.hs @@ -23,7 +23,7 @@ ghcArgs (Package _ path _ _) (stage, dist, _) way srcs result = , args $ HsArgs pathDist -- TODO: now we have both -O and -O2 -- <> arg ["-O2"] - , productArgs ["-odir", "-hidir", "-stubdir"] buildDir + , productArgs ["-odir", "-hidir", "-stubdir"] [buildDir] , when (splitObjects stage) $ arg "-split-objs" , args ("-c":srcs) , args ["-o", result] ] diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 602993e..5373f6e 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -24,7 +24,7 @@ configureArgs stage settings = let conf key as = do s <- unwords <$> args as unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = [ commonCcArgs `filterOut` "-Werror" + cflags = [ commonCcArgs `filterOut` ["-Werror"] , args $ ConfCcArgs stage -- , customCcArgs settings -- TODO: bring this back , commonCcWarninigArgs ] -- TODO: check why cflags are glued @@ -37,7 +37,8 @@ configureArgs stage settings = in args [ conf "CFLAGS" cflags , conf "LDFLAGS" ldflags , conf "CPPFLAGS" cppflags - , arg $ concat <$> "--gcc-options=" <+> cflags <+> " " <+> ldflags + , arg $ concat <$> + arg "--gcc-options=" <> args cflags <> arg " " <> args ldflags , conf "--with-iconv-includes" IconvIncludeDirs , conf "--with-iconv-libraries" IconvLibDirs , conf "--with-gmp-includes" GmpIncludeDirs @@ -73,8 +74,8 @@ bootPkgConstraints = args $ do content <- lines <$> liftIO (readFile cabal) let versionLines = filter (("ersion:" `isPrefixOf`) . drop 1) content case versionLines of - [versionLine] -> args ["--constraint", depName ++ " == " - ++ dropWhile (not . isDigit) versionLine ] + [versionLine] -> return $ "--constraint " ++ depName ++ " == " + ++ dropWhile (not . isDigit) versionLine _ -> redError $ "Cannot determine package version in '" ++ unifyPath cabal ++ "'." diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs index c861707..8fb27b2 100644 --- a/src/Package/Dependencies.hs +++ b/src/Package/Dependencies.hs @@ -16,9 +16,9 @@ ghcArgs (Package name path _ _) (stage, dist, settings) = , packageArgs stage pathDist , includeGhcArgs path dist , concatArgs ["-optP"] $ CppArgs pathDist - , productArgs ["-odir", "-stubdir", "-hidir"] buildDir - , args ["-dep-makefile", depFile ] - , productArgs "-dep-suffix" $ map wayPrefix <$> ways settings + , productArgs ["-odir", "-stubdir", "-hidir"] [buildDir] + , args ["-dep-makefile", depFile] + , productArgs ["-dep-suffix"] $ map wayPrefix <$> ways settings , args $ HsArgs pathDist , args $ pkgHsSources path dist ] From git at git.haskell.org Thu Oct 26 23:55:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix bootPkgConstraints. (98cfed5) Message-ID: <20171026235505.1FFA03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/98cfed580f1655de01f706761b4c4b56da22e523/ghc >--------------------------------------------------------------- commit 98cfed580f1655de01f706761b4c4b56da22e523 Author: Andrey Mokhov Date: Fri Jan 30 12:47:22 2015 +0000 Fix bootPkgConstraints. >--------------------------------------------------------------- 98cfed580f1655de01f706761b4c4b56da22e523 src/Package/Data.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs index 5373f6e..6d108aa 100644 --- a/src/Package/Data.hs +++ b/src/Package/Data.hs @@ -74,8 +74,8 @@ bootPkgConstraints = args $ do content <- lines <$> liftIO (readFile cabal) let versionLines = filter (("ersion:" `isPrefixOf`) . drop 1) content case versionLines of - [versionLine] -> return $ "--constraint " ++ depName ++ " == " - ++ dropWhile (not . isDigit) versionLine + [versionLine] -> return $ args ["--constraint", depName ++ " == " + ++ dropWhile (not . isDigit) versionLine] _ -> redError $ "Cannot determine package version in '" ++ unifyPath cabal ++ "'." From git at git.haskell.org Thu Oct 26 23:55:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: simplify code and fix naming conventions based on Andrey's comments (06fb099) Message-ID: <20171026235506.844BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/06fb099d3fe8a253d79f7af4aa7d67cc5ef91bcc/ghc >--------------------------------------------------------------- commit 06fb099d3fe8a253d79f7af4aa7d67cc5ef91bcc Author: Karel Gardas Date: Tue Jan 19 22:27:36 2016 +0100 simplify code and fix naming conventions based on Andrey's comments >--------------------------------------------------------------- 06fb099d3fe8a253d79f7af4aa7d67cc5ef91bcc src/Settings/Packages/IntegerGmp.hs | 16 ++++++---------- 1 file changed, 6 insertions(+), 10 deletions(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 657eed0..9ad160f 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -15,17 +15,13 @@ import Oracles.Config.Setting integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" - gmp_includedir <- getSetting GmpIncludeDir - gmp_libdir <- getSetting GmpLibDir - let gmp_args = if (gmp_includedir == "" && gmp_libdir == "") - then - [ arg "--configure-option=--with-intree-gmp" ] - else - [] + gmpIncludeDir <- getSetting GmpIncludeDir + gmpLibDir <- getSetting GmpLibDir mconcat [ builder GhcCabal ? mconcat - (gmp_args ++ - [ appendSub "--configure-option=CFLAGS" [includeGmp] - , appendSub "--gcc-options" [includeGmp] ] ) + [ (null gmpIncludeDir && null gmpLibDir) ? + arg "--configure-option=--with-intree-gmp" + , appendSub "--configure-option=CFLAGS" [includeGmp] + , appendSub "--gcc-options" [includeGmp] ] , builderGcc ? arg includeGmp ] From git at git.haskell.org Thu Oct 26 23:55:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #106 from angerman/feature/broken-osx-readlink (5517cb0) Message-ID: <20171026235507.67D903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5517cb05c724c86d04f526c933e94c6a54ba2e18/ghc >--------------------------------------------------------------- commit 5517cb05c724c86d04f526c933e94c6a54ba2e18 Merge: f4ef847 e17f0e6 Author: Andrey Mokhov Date: Tue Jan 5 13:02:14 2016 +0000 Merge pull request #106 from angerman/feature/broken-osx-readlink Fix readlink for os x [skip ci] >--------------------------------------------------------------- 5517cb05c724c86d04f526c933e94c6a54ba2e18 build.cabal.sh | 28 +++++++++++++++++++++++++++- build.sh | 30 ++++++++++++++++++++++++++++-- 2 files changed, 55 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:55:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement customise :: Package -> Package function. (eafd5e0) Message-ID: <20171026235508.B8DCD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb/ghc >--------------------------------------------------------------- commit eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb Author: Andrey Mokhov Date: Mon Feb 9 14:48:18 2015 +0000 Implement customise :: Package -> Package function. >--------------------------------------------------------------- eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb src/Package/Base.hs | 27 ++++++------ src/Package/Data.hs | 15 +++---- src/Targets.hs | 119 +++++++++++++++++++++++----------------------------- 3 files changed, 74 insertions(+), 87 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 eafd5e054b597fd2c4b57cb7bac159ebeb00d4fb From git at git.haskell.org Thu Oct 26 23:55:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #185 from kgardas/fix_gmp_cabal_args (30883f8) Message-ID: <20171026235510.6ACB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30883f8d1e5289a8b90213ebfee0ee99e1712899/ghc >--------------------------------------------------------------- commit 30883f8d1e5289a8b90213ebfee0ee99e1712899 Merge: 11f78b1 06fb099 Author: Andrey Mokhov Date: Tue Jan 19 22:49:58 2016 +0000 Merge pull request #185 from kgardas/fix_gmp_cabal_args do not pass --with-intree-gmp to configure when system gmp is used >--------------------------------------------------------------- 30883f8d1e5289a8b90213ebfee0ee99e1712899 src/Settings/Packages/IntegerGmp.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Oct 26 23:55:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make ghc-cabal build parallel [skip ci]. (83c73a2) Message-ID: <20171026235511.ADD373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/83c73a2bd507915d2a655e5c6148ec92c8a9e9a5/ghc >--------------------------------------------------------------- commit 83c73a2bd507915d2a655e5c6148ec92c8a9e9a5 Author: Andrey Mokhov Date: Tue Jan 5 14:02:21 2016 +0000 Make ghc-cabal build parallel [skip ci]. >--------------------------------------------------------------- 83c73a2bd507915d2a655e5c6148ec92c8a9e9a5 src/Settings/Packages/GhcCabal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 67fa5b4..f1a7373 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -23,6 +23,7 @@ ghcCabalBootArgs = stage0 ? do [ remove ["-hide-all-packages"] , removePair "-optP-include" $ "-optP" ++ cabalMacros , arg "--make" + , arg "-j" , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" , arg "-DGENERICS" From git at git.haskell.org Thu Oct 26 23:55:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep Haskell-land settings in Settings.hs. (9d35421) Message-ID: <20171026235512.7E1A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d35421d9ba504fb9e412027d574b455b94ff90c/ghc >--------------------------------------------------------------- commit 9d35421d9ba504fb9e412027d574b455b94ff90c Author: Andrey Mokhov Date: Mon Feb 9 14:49:19 2015 +0000 Keep Haskell-land settings in Settings.hs. >--------------------------------------------------------------- 9d35421d9ba504fb9e412027d574b455b94ff90c src/Base.hs | 2 ++ src/Settings.hs | 18 ++++++++++++++++++ 2 files changed, 20 insertions(+) diff --git a/src/Base.hs b/src/Base.hs index fa9104a..923e13d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,6 +7,7 @@ module Base ( module Data.Function, module Data.Monoid, module Data.List, + module Settings, Stage (..), Arg, Args, ShowArg (..), ShowArgs (..), @@ -22,6 +23,7 @@ import Control.Applicative import Data.Function import Data.Monoid import Data.List +import Settings data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) diff --git a/src/Settings.hs b/src/Settings.hs new file mode 100644 index 0000000..6ffc976 --- /dev/null +++ b/src/Settings.hs @@ -0,0 +1,18 @@ +module Settings ( + IntegerLibrary (..), integerLibrary, + buildHaddock + ) where + +data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple + +instance Show IntegerLibrary where + show library = case library of + IntegerGmp -> "integer-gmp" + IntegerGmp2 -> "integer-gmp2" + IntegerSimple -> "integer-simple" + +integerLibrary :: IntegerLibrary +integerLibrary = IntegerGmp2 + +buildHaddock :: Bool +buildHaddock = True From git at git.haskell.org Thu Oct 26 23:55:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor CmdLineFlag.hs. (c50e0dc) Message-ID: <20171026235514.018FD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c50e0dc4eb0200dae1d4b50e824db4764e95b827/ghc >--------------------------------------------------------------- commit c50e0dc4eb0200dae1d4b50e824db4764e95b827 Author: Andrey Mokhov Date: Wed Jan 20 00:11:45 2016 +0000 Refactor CmdLineFlag.hs. >--------------------------------------------------------------- c50e0dc4eb0200dae1d4b50e824db4764e95b827 shaking-up-ghc.cabal | 2 +- src/CmdLineFlag.hs | 56 +++++++++++++++++++++++++++++++++++++++ src/Main.hs | 9 ++++--- src/Oracles/Config/CmdLineFlag.hs | 55 -------------------------------------- src/Rules/Actions.hs | 33 ++++++++++++----------- 5 files changed, 80 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 c50e0dc4eb0200dae1d4b50e824db4764e95b827 From git at git.haskell.org Thu Oct 26 23:55:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Separate build messages with a newline. (ff676fc) Message-ID: <20171026235515.6B2243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff676fcbb1e7f1956d94de28bd3fba9ddce40312/ghc >--------------------------------------------------------------- commit ff676fcbb1e7f1956d94de28bd3fba9ddce40312 Author: Andrey Mokhov Date: Tue Jan 5 16:59:41 2016 +0000 Separate build messages with a newline. >--------------------------------------------------------------- ff676fcbb1e7f1956d94de28bd3fba9ddce40312 src/Rules/Actions.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 6f116b5..d567747 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -71,7 +71,7 @@ copyFile source target = do createDirectory :: FilePath -> Action () createDirectory dir = do - putBuild $ "| Create directory " ++ dir + putBuild $ "\n| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir -- Note, the source directory is untracked @@ -85,7 +85,7 @@ moveDirectory source target = do -- Transform a given file by applying a function to its contents fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do - putBuild $ "| Fix " ++ file + putBuild $ "\n| Fix " ++ file old <- liftIO $ readFile file let new = f old length new `seq` liftIO $ writeFile file new @@ -93,14 +93,14 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] - putBuild $ "| Run configure in " ++ dir ++ "..." + putBuild $ "\n| Run configure in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." + putBuild $ "\n| Run make" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args runBuilder :: Builder -> [String] -> Action () @@ -108,7 +108,7 @@ runBuilder builder args = do needBuilder laxDependencies builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "| Run " ++ show builder ++ note + putBuild $ "\n| Run " ++ show builder ++ note quietly $ cmd [path] args -- Print out key information about the command being executed From git at git.haskell.org Thu Oct 26 23:55:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix cabalName in libraryPackage. (ba209b9) Message-ID: <20171026235516.1235C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba209b90b53ff9b6bfe32f4f890fc2911c274122/ghc >--------------------------------------------------------------- commit ba209b90b53ff9b6bfe32f4f890fc2911c274122 Author: Andrey Mokhov Date: Mon Feb 9 15:14:08 2015 +0000 Fix cabalName in libraryPackage. >--------------------------------------------------------------- ba209b90b53ff9b6bfe32f4f890fc2911c274122 src/Package/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 076bc2a..7f310d1 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -84,7 +84,7 @@ libraryPackage name cabalName stages settings = Package name (unifyPath $ "libraries" name) - (unifyPath $ "libraries" name cabalName <.> "cabal") + cabalName [ (stage , if stage == Stage0 then "dist-boot" else "dist-install" , settings stage) From git at git.haskell.org Thu Oct 26 23:55:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (e7377d1) Message-ID: <20171026235517.6E94A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7377d1113d34ca56881cfc46b25e2ad8a6ba3aa/ghc >--------------------------------------------------------------- commit e7377d1113d34ca56881cfc46b25e2ad8a6ba3aa Author: Andrey Mokhov Date: Wed Jan 20 00:33:27 2016 +0000 Minor revision. [skip ci] >--------------------------------------------------------------- e7377d1113d34ca56881cfc46b25e2ad8a6ba3aa src/Expression.hs | 59 ++++++++++++++++++++++++++++--------------------------- 1 file changed, 30 insertions(+), 29 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 932ed80..1d1dc27 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -36,17 +36,18 @@ import Stage import Target import Way --- | @Expr a@ is a computation that produces a value of type @Action a@ and can read --- parameters of the current build 'Target'. +-- | @Expr a@ is a computation that produces a value of type @Action a@ and can +-- read parameters of the current build 'Target'. type Expr a = ReaderT Target Action a -- | @Diff a@ is a /difference list/ containing values of type @a at . A difference --- list is a list with efficient concatenation, encoded as a value @a -> a at . --- We could use @Dual (Endo a)@ instead of @Diff a@, but the former may look scary. +-- list is a list with efficient concatenation, encoded as a value @a -> a at . We +-- could use @Dual (Endo a)@ instead of @Diff a@, but the former may look scary. newtype Diff a = Diff { fromDiff :: a -> a } --- | @DiffExpr a@ is a computation that builds a difference list (i.e., a function --- of type @'Action' (a -> a)@) and can read parameters of the current build ''Target'. +-- | @DiffExpr a@ is a computation that builds a difference list (i.e., a +-- function of type @'Action' (a -> a)@) and can read parameters of the current +-- build 'Target'. type DiffExpr a = Expr (Diff a) -- Note the reverse order of function composition (y . x), which ensures that @@ -65,19 +66,19 @@ type Packages = DiffExpr [Package] type Ways = DiffExpr [Way] -- Basic operations on expressions: --- | Transform an expression by applying a given function +-- | Transform an expression by applying a given function. apply :: (a -> a) -> DiffExpr a apply = return . Diff --- | Append something to an expression +-- | Append something to an expression. append :: Monoid a => a -> DiffExpr a append x = apply (<> x) --- | Remove given elements from a list expression +-- | Remove given elements from a list expression. remove :: Eq a => [a] -> DiffExpr [a] remove xs = apply $ filter (`notElem` xs) --- | Remove given pair of elements from a list expression +-- | Remove given pair of elements from a list expression. -- Example: removePair "-flag" "b" ["-flag", "a", "-flag", "b"] = ["-flag", "a"] removePair :: Eq a => a -> a -> DiffExpr [a] removePair x y = apply filterPair @@ -87,30 +88,30 @@ removePair x y = apply filterPair else z1 : filterPair (z2 : zs) filterPair zs = zs --- | Apply a predicate to an expression +-- | Apply a predicate to an expression. applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate if bool then expr else return mempty --- | Add a single argument to 'Args' +-- | Add a single argument to 'Args'. arg :: String -> Args arg = append . return --- | A convenient operator for predicate application +-- | A convenient operator for predicate application. class PredicateLike a where - (?) :: Monoid m => a -> Expr m -> Expr m + (?) :: Monoid m => a -> Expr m -> Expr m infixr 8 ? instance PredicateLike Predicate where - (?) = applyPredicate + (?) = applyPredicate instance PredicateLike Bool where - (?) = applyPredicate . return + (?) = applyPredicate . return instance PredicateLike (Action Bool) where - (?) = applyPredicate . lift + (?) = applyPredicate . lift -- | @appendSub@ appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument @@ -141,11 +142,11 @@ filterSub prefix p = apply $ map filterSubstr | otherwise = s -- | Remove given elements from a list of sub-arguments with a given prefix --- Example: removeSub "--configure-option=CFLAGS" ["-Werror"] +-- Example: removeSub "--configure-option=CFLAGS" ["-Werror"]. removeSub :: String -> [String] -> Args removeSub prefix xs = filterSub prefix (`notElem` xs) --- | Interpret a given expression in a given environment +-- | Interpret a given expression in a given environment. interpret :: Target -> Expr a -> Action a interpret = flip runReaderT @@ -156,46 +157,46 @@ interpretWithStage :: Stage -> Expr a -> Action a interpretWithStage s = interpretPartial $ PartialTarget s (error "interpretWithStage: package not set") --- | Extract an expression from a difference expression +-- | Extract an expression from a difference expression. fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) --- | Interpret a given difference expression in a given environment +-- | Interpret a given difference expression in a given environment. interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a interpretDiff target = interpret target . fromDiffExpr --- | Convenient getters for target parameters +-- | Convenient getters for target parameters. getStage :: Expr Stage getStage = asks stage --- | Get the 'Package' of the current 'Target' +-- | Get the 'Package' of the current 'Target'. getPackage :: Expr Package getPackage = asks package --- | Get the 'Builder' for the current 'Target' +-- | Get the 'Builder' for the current 'Target'. getBuilder :: Expr Builder getBuilder = asks builder --- | Get the 'Way' of the current 'Target' +-- | Get the 'Way' of the current 'Target'. getWay :: Expr Way getWay = asks way --- | Get the input files of the current 'Target' +-- | Get the input files of the current 'Target'. getInputs :: Expr [FilePath] getInputs = asks inputs --- | Run 'getInputs' and check that the result contains a single input file only +-- | Run 'getInputs' and check that the result contains one input file only. getInput :: Expr FilePath getInput = do target <- ask getSingleton getInputs $ "getInput: exactly one input file expected in target " ++ show target --- | Get the files produced by the current 'Target' +-- | Get the files produced by the current 'Target'. getOutputs :: Expr [FilePath] getOutputs = asks outputs --- | Run 'getOutputs' and check that the result contains a output file only +-- | Run 'getOutputs' and check that the result contains one output file only. getOutput :: Expr FilePath getOutput = do target <- ask From git at git.haskell.org Thu Oct 26 23:55:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor libffi rules. (709026d) Message-ID: <20171026235518.D8D513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/709026de4920d45ad83a9e6a98153b9328533d1a/ghc >--------------------------------------------------------------- commit 709026de4920d45ad83a9e6a98153b9328533d1a Author: Andrey Mokhov Date: Tue Jan 5 17:00:37 2016 +0000 Refactor libffi rules. >--------------------------------------------------------------- 709026de4920d45ad83a9e6a98153b9328533d1a src/Rules/Copy.hs | 14 -------------- src/Rules/Libffi.hs | 26 +++++++++++++++++++------- 2 files changed, 19 insertions(+), 21 deletions(-) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index b1f9760..7454fd9 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -5,9 +5,6 @@ import Expression import GHC import Rules.Actions import Rules.Generate -import Rules.Libffi -import Settings.Packages.Rts -import Settings.TargetDirectory installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" @@ -16,17 +13,6 @@ installTargets = [ "inplace/lib/template-hsc.h" copyRules :: Rules () copyRules = do - targetPath Stage1 rts -/- "build/ffi*.h" %> \ffih -> do - need [libffiLibrary] - ffiHPaths <- getDirectoryFiles "" ["libffi/build/inst/lib/*/include/ffi.h"] - when (length ffiHPaths /= 1) $ - putError $ "copyRules: exactly one ffi.h header expected" - ++ "(found: " ++ show ffiHPaths ++ ")." - - copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih - libffiName <- rtsLibffiLibraryName - copyFile libffiLibrary (targetPath Stage1 rts -/- "build/lib" ++ libffiName <.> "a") - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 603b35f..041650f 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,4 +1,4 @@ -module Rules.Libffi (libffiRules, libffiLibrary) where +module Rules.Libffi (libffiRules, libffiDependencies) where import Base import Expression @@ -6,15 +6,22 @@ import GHC import Oracles import Rules.Actions import Settings.Builders.Common +import Settings.Packages.Rts +import Settings.TargetDirectory import Settings.User --- We use this file to track the whole libffi library -libffiLibrary :: FilePath -libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" +rtsBuildPath :: FilePath +rtsBuildPath = targetPath Stage1 rts -/- "build" + +libffiDependencies :: [FilePath] +libffiDependencies = (rtsBuildPath -/-) <$> [ "ffi.h", "ffitarget.h" ] libffiBuild :: FilePath libffiBuild = "libffi/build" +libffiLibrary :: FilePath +libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" + libffiMakefile :: FilePath libffiMakefile = libffiBuild -/- "Makefile.in" @@ -61,7 +68,7 @@ configureArguments = do libffiRules :: Rules () libffiRules = do - libffiLibrary %> \_ -> do + libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] @@ -87,9 +94,14 @@ libffiRules = do runMake libffiBuild [] runMake libffiBuild ["install"] - putSuccess $ "| Successfully built custom library 'libffi'" + forM_ ["ffi.h", "ffitarget.h"] $ \file -> do + let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file + copyFile src (rtsBuildPath -/- file) - "libffi/build/inst/lib/*/include/*.h" %> \_ -> need [libffiLibrary] + libffiName <- rtsLibffiLibraryName + copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") + + putSuccess $ "| Successfully built custom library 'libffi'" -- chmod +x libffi/ln -- # wc on OS X has spaces in its output, which libffi's Makefile From git at git.haskell.org Thu Oct 26 23:55:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix comments. (77766e8) Message-ID: <20171026235519.B8DE03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/77766e8e875b069d05c9a536811df20796d023c5/ghc >--------------------------------------------------------------- commit 77766e8e875b069d05c9a536811df20796d023c5 Author: Andrey Mokhov Date: Mon Feb 9 15:40:44 2015 +0000 Fix comments. >--------------------------------------------------------------- 77766e8e875b069d05c9a536811df20796d023c5 src/Package/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 7f310d1..2738b83 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -52,7 +52,7 @@ defaultSettings stage = Settings -- The typical structure of that directory is: -- * build/ : contains compiled object code -- * doc/ : produced by haddock --- * package-data.mk : contains output of ghc-cabal applied to package.cabal +-- * package-data.mk : contains output of ghc-cabal applied to pkgCabal.cabal -- Settings may be different for different combinations of Stage & FilePath -- TODO: the above may be incorrect, settings seem to *only* depend on the -- stage. In fact Stage seem to define FilePath and Settings, therefore we From git at git.haskell.org Thu Oct 26 23:55:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for --split-object command line flag. (87c6fae) Message-ID: <20171026235520.ED8D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/87c6fae6c8073315ca8f5aba0e2e5501500437db/ghc >--------------------------------------------------------------- commit 87c6fae6c8073315ca8f5aba0e2e5501500437db Author: Andrey Mokhov Date: Wed Jan 20 01:00:50 2016 +0000 Add support for --split-object command line flag. See #132. >--------------------------------------------------------------- 87c6fae6c8073315ca8f5aba0e2e5501500437db src/CmdLineFlag.hs | 22 ++++++++++++++++------ src/Settings/User.hs | 8 ++++++-- 2 files changed, 22 insertions(+), 8 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 444940a..05b74e5 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,5 +1,5 @@ module CmdLineFlag ( - putCmdLineFlags, flags, cmdProgressInfo, ProgressInfo (..) + putCmdLineFlags, flags, cmdProgressInfo, ProgressInfo (..), cmdSplitObjects ) where import Base @@ -16,13 +16,15 @@ data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -- command line. These flags are not tracked, that is they do not force any -- build rules to be rurun. data Untracked = Untracked - { progressInfo :: ProgressInfo } + { progressInfo :: ProgressInfo + , splitObjects :: Bool } deriving (Eq, Show) -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked defaultUntracked = Untracked - { progressInfo = Normal } + { progressInfo = Normal + , splitObjects = False } readProgressInfo :: Maybe String -> Either String (Untracked -> Untracked) readProgressInfo ms = @@ -35,11 +37,16 @@ readProgressInfo ms = go "unicorn" = Just Unicorn go _ = Nothing -- Left "no parse" mkClosure :: ProgressInfo -> Untracked -> Untracked - mkClosure flag opts = opts { progressInfo = flag } + mkClosure flag flags = flags { progressInfo = flag } + +readSplitObjects :: Either String (Untracked -> Untracked) +readSplitObjects = Right $ \flags -> flags { splitObjects = True } flags :: [OptDescr (Either String (Untracked -> Untracked))] flags = [ Option [] ["progress-info"] (OptArg readProgressInfo "") - "Progress Info Style (None, Brief, Normal, or Unicorn)" ] + "Progress Info Style (None, Brief, Normal, or Unicorn)" + , Option [] ["split-objects"] (NoArg readSplitObjects) + "Generate split objects (requires a full clean rebuild)." ] -- TODO: Get rid of unsafePerformIO by using shakeExtra. {-# NOINLINE cmdLineFlags #-} @@ -47,10 +54,13 @@ cmdLineFlags :: IORef Untracked cmdLineFlags = unsafePerformIO $ newIORef defaultUntracked putCmdLineFlags :: [Untracked -> Untracked] -> IO () -putCmdLineFlags opts = modifyIORef cmdLineFlags (\o -> foldl (flip id) o opts) +putCmdLineFlags flags = modifyIORef cmdLineFlags (\f -> foldl (flip id) f flags) getCmdLineFlags :: Action Untracked getCmdLineFlags = liftIO $ readIORef cmdLineFlags cmdProgressInfo :: Action ProgressInfo cmdProgressInfo = progressInfo <$> getCmdLineFlags + +cmdSplitObjects :: Action Bool +cmdSplitObjects = splitObjects <$> getCmdLineFlags diff --git a/src/Settings/User.hs b/src/Settings/User.hs index fb6ffb6..096f6ef 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -6,9 +6,12 @@ module Settings.User ( verboseCommands, turnWarningsIntoErrors, splitObjects ) where +import Base +import CmdLineFlag import GHC import Expression import Predicates +import Settings.Default -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath @@ -55,9 +58,10 @@ trackBuildSystem = True validating :: Bool validating = False --- To switch on split objects use 'splitObjects = defaultSplitObjects', see #153 +-- | Control when split objects are generated. Note, due to the GHC bug #11315 +-- it is necessary to do a full clean rebuild when changing this option. splitObjects :: Predicate -splitObjects = return False +splitObjects = (lift $ cmdSplitObjects) &&^ defaultSplitObjects dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Thu Oct 26 23:55:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (14a236b) Message-ID: <20171026235523.213323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14a236b420ac7a03ef68b6a193efe10936dc10b8/ghc >--------------------------------------------------------------- commit 14a236b420ac7a03ef68b6a193efe10936dc10b8 Author: Andrey Mokhov Date: Mon Feb 9 22:25:30 2015 +0000 Clean up. >--------------------------------------------------------------- 14a236b420ac7a03ef68b6a193efe10936dc10b8 src/Base.hs | 2 -- src/Oracles/Flag.hs | 2 +- src/Package/Base.hs | 2 ++ src/Targets.hs | 3 --- 4 files changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 923e13d..fa9104a 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -7,7 +7,6 @@ module Base ( module Data.Function, module Data.Monoid, module Data.List, - module Settings, Stage (..), Arg, Args, ShowArg (..), ShowArgs (..), @@ -23,7 +22,6 @@ import Control.Applicative import Data.Function import Data.Monoid import Data.List -import Settings data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index fa29415..8149619 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -7,9 +7,9 @@ module Oracles.Flag ( test, when, unless, not, (&&), (||) ) where -import Control.Monad hiding (when, unless) import qualified Prelude import Prelude hiding (not, (&&), (||)) +import Control.Monad hiding (when, unless) import Base import Util import Oracles.Base diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 2738b83..40d893e 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -4,6 +4,7 @@ module Package.Base ( module Ways, module Util, module Oracles, + module Settings, Package (..), Settings (..), TodoItem (..), defaultSettings, library, customise, updateSettings, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, @@ -20,6 +21,7 @@ import Base import Ways import Util import Oracles +import Settings import qualified System.Directory as S data Settings = Settings diff --git a/src/Targets.hs b/src/Targets.hs index 19cb664..bdfb2ee 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -5,9 +5,6 @@ module Targets ( import Package.Base -integerLibraryName :: String -integerLibraryName = show integerLibrary - -- These are the packages we build: -- TODO: this should eventually be removed and replaced by the top-level -- target, i.e. GHC (and perhaps, something else) From git at git.haskell.org Thu Oct 26 23:55:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix integer-gmp problem on Travis, see #103. (ae6f58d) Message-ID: <20171026235522.6BECE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8/ghc >--------------------------------------------------------------- commit ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8 Author: Andrey Mokhov Date: Tue Jan 5 17:02:55 2016 +0000 Attempt to fix integer-gmp problem on Travis, see #103. >--------------------------------------------------------------- ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8 src/Rules/Generate.hs | 16 ++++++---------- src/Rules/IntegerGmp.hs | 48 ++++++++++++++++++++++++++++++++---------------- src/Rules/Library.hs | 8 ++++++-- 3 files changed, 44 insertions(+), 28 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 921c672..2b33a53 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -14,6 +14,8 @@ import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles import Rules.Actions +import Rules.IntegerGmp +import Rules.Libffi import Rules.Resources (Resources) import Settings import Settings.Builders.DeriveConstants @@ -33,13 +35,12 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -libffiDependencies :: [FilePath] -libffiDependencies = (targetPath Stage1 rts -/-) <$> - [ "build/ffi.h" - , "build/ffitarget.h" ] +integerGmpDependencies :: [FilePath] +integerGmpDependencies = [integerGmpLibraryH] defaultDependencies :: [FilePath] -defaultDependencies = includesDependencies ++ libffiDependencies +defaultDependencies = + includesDependencies ++ libffiDependencies ++ integerGmpDependencies derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = (derivedConstantsPath -/-) <$> @@ -69,15 +70,10 @@ compilerDependencies stage = , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] -integerGmpDependencies :: [FilePath] -integerGmpDependencies = ((pkgPath integerGmp -/- "gmp") -/-) <$> - [ "gmp.h" ] -- identical to integerGmpLibraryH, but doesn't require the import. - generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == rts = derivedConstantsDependencies - | pkg == integerGmp = integerGmpDependencies | stage == Stage0 = defaultDependencies | otherwise = [] diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 9bbf482..91ca074 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,4 +1,4 @@ -module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary, integerGmpLibraryH) where +module Rules.IntegerGmp (integerGmpRules, integerGmpObjects, integerGmpLibraryH) where import Base import Expression @@ -8,16 +8,25 @@ import Rules.Actions import Settings.User integerGmpBase :: FilePath -integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp" +integerGmpBase = "libraries/integer-gmp/gmp" integerGmpBuild :: FilePath integerGmpBuild = integerGmpBase -/- "gmpbuild" +integerGmpObjects :: FilePath +integerGmpObjects = integerGmpBase -/- "objs" + integerGmpLibrary :: FilePath integerGmpLibrary = integerGmpBase -/- "libgmp.a" +integerGmpLibraryInTreeH :: FilePath +integerGmpLibraryInTreeH = integerGmpBase -/- "gmp.h" + integerGmpLibraryH :: FilePath -integerGmpLibraryH = integerGmpBase -/- "gmp.h" +integerGmpLibraryH = pkgPath integerGmp -/- "include/ghc-gmp.h" + +integerGmpLibraryFakeH :: FilePath +integerGmpLibraryFakeH = integerGmpBase -/- "ghc-gmp.h" -- relative to integerGmpBuild integerGmpPatch :: FilePath @@ -49,12 +58,14 @@ configureArguments = do -- TODO: we rebuild integer-gmp every time. integerGmpRules :: Rules () integerGmpRules = do - integerGmpLibrary %> \_ -> do + + -- TODO: split into multiple rules + integerGmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/IntegerGmp.hs"] -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] - liftIO $ removeFiles (integerGmpBase -/- "objs") ["//*"] + liftIO $ removeFiles (integerGmpObjects) ["//*"] -- unpack the gmp tarball. -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is @@ -91,19 +102,24 @@ integerGmpRules = do args <- configureArguments runConfigure integerGmpBuild envs args - runMake integerGmpBuild [] + -- check whether we need to build in tree gmp + -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` + configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" + if "HaveFrameworkGMP = YES" `isInfixOf` configMk + then do + putBuild "\n| GMP framework detected and will be used" + copyFile integerGmpLibraryFakeH integerGmpLibraryH + else do + putBuild "\n| No GMP framework detected" + runMake integerGmpBuild [] - -- copy library and header - -- TODO: why copy library, can we move it instead? - forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> - copyFile (integerGmpBuild -/- file) (integerGmpBase -/- takeFileName file) + copyFile integerGmpLibraryInTreeH integerGmpLibraryH + -- TODO: why copy library, can we move it instead? + copyFile (integerGmpBuild -/- ".libs/libgmp.a") integerGmpLibrary - let objsDir = integerGmpBase -/- "objs" - createDirectory objsDir - build $ fullTarget target Ar [integerGmpLibrary] [objsDir] + createDirectory integerGmpObjects + build $ fullTarget target Ar [integerGmpLibrary] [integerGmpObjects] - runBuilder Ranlib [integerGmpLibrary] + runBuilder Ranlib [integerGmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" - - integerGmpLibraryH %> \_ -> need [integerGmpLibrary] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index d9a1a48..41e7b3d 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -79,6 +79,10 @@ hSources target = do extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do - need [integerGmpLibrary] - getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] + need [integerGmpLibraryH] + objsExist <- doesDirectoryExist integerGmpObjects + putBuild $ "objsExist = " ++ show objsExist + if objsExist + then getDirectoryFiles "" [integerGmpObjects -/- "*.o"] + else return [] | otherwise = return [] From git at git.haskell.org Thu Oct 26 23:55:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add initial support for --configure command line flag. (e874fed) Message-ID: <20171026235524.784CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e874fed8e68f9941d2cbd0ed4a64680a7f09586f/ghc >--------------------------------------------------------------- commit e874fed8e68f9941d2cbd0ed4a64680a7f09586f Author: Andrey Mokhov Date: Thu Jan 21 11:13:34 2016 +0000 Add initial support for --configure command line flag. >--------------------------------------------------------------- e874fed8e68f9941d2cbd0ed4a64680a7f09586f src/CmdLineFlag.hs | 56 +++++++++++++++++++++++++++++++++++----------------- src/Rules/Actions.hs | 39 ++++++++++++++++++------------------ src/Rules/Cabal.hs | 1 - src/Rules/Config.hs | 21 ++++++++++---------- src/Settings/User.hs | 9 +++------ 5 files changed, 72 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 e874fed8e68f9941d2cbd0ed4a64680a7f09586f From git at git.haskell.org Thu Oct 26 23:55:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Force integerGmp package to be configured before reading config.mk file, see #103. (a33ab01) Message-ID: <20171026235526.1350D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a33ab012f0e9e997035d7bd6c3ce0535cc9cbed2/ghc >--------------------------------------------------------------- commit a33ab012f0e9e997035d7bd6c3ce0535cc9cbed2 Author: Andrey Mokhov Date: Tue Jan 5 19:35:34 2016 +0000 Force integerGmp package to be configured before reading config.mk file, see #103. >--------------------------------------------------------------- a33ab012f0e9e997035d7bd6c3ce0535cc9cbed2 src/Rules/IntegerGmp.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 91ca074..f86371c 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -6,6 +6,7 @@ import GHC import Oracles.Config.Setting import Rules.Actions import Settings.User +import Settings.TargetDirectory integerGmpBase :: FilePath integerGmpBase = "libraries/integer-gmp/gmp" @@ -104,6 +105,7 @@ integerGmpRules = do -- check whether we need to build in tree gmp -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` + need [pkgDataFile Stage1 integerGmp] configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk then do From git at git.haskell.org Thu Oct 26 23:55:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Experiment with parameterised graphs. (8f52904) Message-ID: <20171026235526.B6C6D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f52904d2c05f7503b142fa48eb46eb7945e450c/ghc >--------------------------------------------------------------- commit 8f52904d2c05f7503b142fa48eb46eb7945e450c Author: Andrey Mokhov Date: Mon Feb 9 22:25:52 2015 +0000 Experiment with parameterised graphs. >--------------------------------------------------------------- 8f52904d2c05f7503b142fa48eb46eb7945e450c src/Settings.hs | 94 ++++++++++++++++++++++++++++++++++++++++++++++++++++----- 1 file changed, 87 insertions(+), 7 deletions(-) diff --git a/src/Settings.hs b/src/Settings.hs index 6ffc976..42ceed9 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,18 +1,98 @@ +{-# LANGUAGE FlexibleInstances #-} + module Settings ( - IntegerLibrary (..), integerLibrary, + IntegerLibrary (..), integerLibrary, integerLibraryName, buildHaddock ) where -data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple +import Base +import Ways -instance Show IntegerLibrary where - show library = case library of - IntegerGmp -> "integer-gmp" - IntegerGmp2 -> "integer-gmp2" - IntegerSimple -> "integer-simple" +data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple integerLibrary :: IntegerLibrary integerLibrary = IntegerGmp2 +integerLibraryName :: String +integerLibraryName = case integerLibrary of + IntegerGmp -> "integer-gmp" + IntegerGmp2 -> "integer-gmp2" + IntegerSimple -> "integer-simple" + buildHaddock :: Bool buildHaddock = True + +-- A Parameterised Graph datatype for storing argument lists with conditions +data PG a b = Epsilon + | Vertex a + | Overlay (PG a b) (PG a b) + | Sequence (PG a b) (PG a b) + | Condition b (PG a b) + +instance Monoid (PG a b) where + mempty = Epsilon + mappend = Overlay + +type ArgsExpression = PG String Predicate +type WaysExpression = PG Way Predicate + +data Match = MatchPackage FilePath -- Match a Package name + | MatchFile FilePath -- Match a file + | MatchStage Stage -- Match a Stage + | MatchWay Way -- Match a Way + | MatchKeyValue String String -- Match a key with a value (config) + +-- A Matcher takes a Match description and attempts to evaluate it. +-- Returns Nothing if the attempt fails. +type Matcher = Match -> Maybe Bool + +-- A Monoid instance for matchers (returns first successful match) +instance Monoid Matcher where + mempty = const Nothing + p `mappend` q = \m -> getFirst $ First (p m) <> First (q m) + +data Predicate = Evaluated Bool -- Evaluated predicate + | If Match -- Perform a match to evaluate + | Not Predicate -- Negate predicate + | And Predicate Predicate -- Conjunction of two predicates + | Or Predicate Predicate -- Disjunction of two predicates + +match :: Predicate -> Matcher -> Predicate +match p @ (Evaluated _) _ = p +match p @ (If match ) m = case m match of + Just bool -> Evaluated bool + Nothing -> p +match (Not p ) m = match p m +match (And p q) m = And (match p m) (match q m) +match (Or p q) m = Or (match p m) (match q m) + +-- returns Nothing if the given predicate cannot be uniquely evaluated +evalPredicate :: Predicate -> Maybe Bool +evalPredicate (Evaluated bool) = Just bool +evalPredicate (Not p) = not <$> evalPredicate p +evalPredicate (And p q) + | p' == Just False || q' == Just False = Just False + | p' == Just True && q' == Just True = Just True + | otherwise = Nothing + where + p' = evalPredicate p + q' = evalPredicate q +evalPredicate (Or p q) + | p' == Just True || q' == Just True = Just True + | p' == Just False && q' == Just False = Just False + | otherwise = Nothing + where + p' = evalPredicate p + q' = evalPredicate q +evalPredicate (If _) = Nothing + +-- returns Nothing if the given expression cannot be uniquely evaluated +evalPG :: PG a Predicate -> Maybe [a] +evalPG Epsilon = Just [] +evalPG (Vertex v) = Just [v] +evalPG (Overlay p q) = (++) <$> evalPG p <*> evalPG q +evalPG (Sequence p q) = (++) <$> evalPG p <*> evalPG q +evalPG (Condition x p) = case evalPredicate x of + Just True -> evalPG p + Just False -> Just [] + Nothing -> Nothing From git at git.haskell.org Thu Oct 26 23:55:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do we need tabs? (d705676) Message-ID: <20171026235556.92E493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d705676ac7aee5a5bf153ad0c9d44696ce127d70/ghc >--------------------------------------------------------------- commit d705676ac7aee5a5bf153ad0c9d44696ce127d70 Author: Moritz Angermann Date: Wed Jan 6 11:57:30 2016 +0800 Do we need tabs? >--------------------------------------------------------------- d705676ac7aee5a5bf153ad0c9d44696ce127d70 .travis.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 58e23cd..0a85228 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,8 +1,8 @@ sudo: false os: - - linux - - osx + - linux + - osx matrix: include: From git at git.haskell.org Thu Oct 26 23:55:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on clean target (497f750) Message-ID: <20171026235557.1D08F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/497f75095c1265b19025077a2fec0633604d1abf/ghc >--------------------------------------------------------------- commit 497f75095c1265b19025077a2fec0633604d1abf Author: Andrey Mokhov Date: Fri Jan 22 13:04:34 2016 +0000 Add a note on clean target [skip ci] >--------------------------------------------------------------- 497f75095c1265b19025077a2fec0633604d1abf README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index b80b621..602148b 100644 --- a/README.md +++ b/README.md @@ -71,7 +71,8 @@ experiment following the Haddock comments. To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. -This is a temporary solution; we are working on proper reset functionality ([#131][reset-issue]). +To remove all build artefacts, run the build script with `clean` target. Note, we are +working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. Current limitations ------------------- @@ -114,7 +115,6 @@ helped me endure and enjoy the project. [build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs -[reset-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/131 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 [profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 From git at git.haskell.org Thu Oct 26 23:56:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove old file src/Expression/Args.hs. (21b789e) Message-ID: <20171026235600.0D8163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21b789ea7729715fe7252099808b062271793e40/ghc >--------------------------------------------------------------- commit 21b789ea7729715fe7252099808b062271793e40 Author: Andrey Mokhov Date: Sun Apr 12 02:14:52 2015 +0100 Remove old file src/Expression/Args.hs. >--------------------------------------------------------------- 21b789ea7729715fe7252099808b062271793e40 src/Expression/Args.hs | 289 ------------------------------------------------- 1 file changed, 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 21b789ea7729715fe7252099808b062271793e40 From git at git.haskell.org Thu Oct 26 23:56:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: env for all, apt only for linux (a7610e0) Message-ID: <20171026235600.982E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7610e09f39b37e683848a161121f52ce01555df/ghc >--------------------------------------------------------------- commit a7610e09f39b37e683848a161121f52ce01555df Author: Moritz Angermann Date: Wed Jan 6 12:15:00 2016 +0800 env for all, apt only for linux >--------------------------------------------------------------- a7610e09f39b37e683848a161121f52ce01555df .travis.yml | 32 ++++++++++++++------------------ 1 file changed, 14 insertions(+), 18 deletions(-) diff --git a/.travis.yml b/.travis.yml index 0a85228..0a8f49a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -4,24 +4,20 @@ os: - linux - osx -matrix: - include: - - env: - CABALVER=1.22 - GHCVER=7.10.3 - - addons: { - apt: { - packages: [ - ghc-7.10.3, - alex-3.1.4, - happy-1.19.5, - cabal-install-1.22, - zlib1g-dev - ], - sources: [hvr-ghc] - } - } +env: + - CABALVER=1.22 + - GHCVER=7.10.3 + +addons: + linux: + apt: + packages: + - ghc-7.10.3, + - alex-3.1.4, + - happy-1.19.5, + - cabal-install-1.22, + - zlib1g-dev + sources: hvr-ghc before_install: From git at git.haskell.org Thu Oct 26 23:56:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use removeFiles instead of removeFilesAfter. (a8ea524) Message-ID: <20171026235601.001963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8ea524634d870e75c3dc13bc96d174b064849ae/ghc >--------------------------------------------------------------- commit a8ea524634d870e75c3dc13bc96d174b064849ae Author: Andrey Mokhov Date: Fri Jan 22 13:08:36 2016 +0000 Use removeFiles instead of removeFilesAfter. See #131. >--------------------------------------------------------------- a8ea524634d870e75c3dc13bc96d174b064849ae src/Rules/Clean.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 6ab5309..2b4094a 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -12,13 +12,13 @@ cleanRules :: Rules () cleanRules = do "clean" ~> do putBuild $ "| Remove files in " ++ buildRootPath ++ "..." - removeFilesAfter buildRootPath ["//*"] + liftIO $ removeFiles buildRootPath ["//*"] putBuild $ "| Remove files in " ++ programInplacePath ++ "..." - removeFilesAfter programInplacePath ["//*"] + liftIO $ removeFiles programInplacePath ["//*"] putBuild $ "| Remove files in inplace/lib..." - removeFilesAfter "inplace/lib" ["//*"] + liftIO $ removeFiles "inplace/lib" ["//*"] putBuild $ "| Remove files in " ++ derivedConstantsPath ++ "..." - removeFilesAfter derivedConstantsPath ["//*"] + liftIO $ removeFiles derivedConstantsPath ["//*"] forM_ includesDependencies $ \file -> do putBuild $ "| Remove " ++ file removeFileIfExists file From git at git.haskell.org Thu Oct 26 23:56:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Continue major refactoring for expression-based build system. (cb2003c) Message-ID: <20171026235604.A14353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb2003ce5221cf043f77eeb0690d6d8b6bc19dea/ghc >--------------------------------------------------------------- commit cb2003ce5221cf043f77eeb0690d6d8b6bc19dea Author: Andrey Mokhov Date: Wed Apr 15 03:24:09 2015 +0100 Continue major refactoring for expression-based build system. >--------------------------------------------------------------- cb2003ce5221cf043f77eeb0690d6d8b6bc19dea src/Expression/Base.hs | 146 +++++++++++++++++++++--------------- src/Expression/Build.hs | 34 ++++----- src/Expression/PG.hs | 49 +++++++++++- src/Main.hs | 3 +- src/Package.hs | 58 ++++++--------- src/Package/Base.hs | 170 ++++++++++-------------------------------- src/PackageBuild.hs | 67 +++++++++++++++++ src/Settings.hs | 101 ++++++++++++------------- src/Targets.hs | 193 +++++++++++++++++++++++------------------------- 9 files changed, 420 insertions(+), 401 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 cb2003ce5221cf043f77eeb0690d6d8b6bc19dea From git at git.haskell.org Thu Oct 26 23:56:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (30a3d91) Message-ID: <20171026235604.D5D713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30a3d9199fe606b08b26b387bc9b8b932dc2098d/ghc >--------------------------------------------------------------- commit 30a3d9199fe606b08b26b387bc9b8b932dc2098d Merge: a8ea524 497f750 Author: Andrey Mokhov Date: Fri Jan 22 13:08:56 2016 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 30a3d9199fe606b08b26b387bc9b8b932dc2098d README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Thu Oct 26 23:56:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: collapse env, addons wihout linux (fb5ed14) Message-ID: <20171026235605.5B0043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fb5ed14f7d95b0ea65e925c15e04ed766fad9247/ghc >--------------------------------------------------------------- commit fb5ed14f7d95b0ea65e925c15e04ed766fad9247 Author: Moritz Angermann Date: Wed Jan 6 12:16:48 2016 +0800 collapse env, addons wihout linux >--------------------------------------------------------------- fb5ed14f7d95b0ea65e925c15e04ed766fad9247 .travis.yml | 20 +++++++++----------- 1 file changed, 9 insertions(+), 11 deletions(-) diff --git a/.travis.yml b/.travis.yml index 0a8f49a..09ed050 100644 --- a/.travis.yml +++ b/.travis.yml @@ -5,19 +5,17 @@ os: - osx env: - - CABALVER=1.22 - - GHCVER=7.10.3 + - CABALVER=1.22 GHCVER=7.10.3 addons: - linux: - apt: - packages: - - ghc-7.10.3, - - alex-3.1.4, - - happy-1.19.5, - - cabal-install-1.22, - - zlib1g-dev - sources: hvr-ghc + apt: + packages: + - ghc-7.10.3, + - alex-3.1.4, + - happy-1.19.5, + - cabal-install-1.22, + - zlib1g-dev + sources: hvr-ghc before_install: From git at git.haskell.org Thu Oct 26 23:56:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish Args datatype, propagate changes to related modules. (79ad8ee) Message-ID: <20171026235609.2D7673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79ad8ee4e0830da7125d6975c6f13790d97f2439/ghc >--------------------------------------------------------------- commit 79ad8ee4e0830da7125d6975c6f13790d97f2439 Author: Andrey Mokhov Date: Thu Apr 16 02:08:59 2015 +0100 Finish Args datatype, propagate changes to related modules. >--------------------------------------------------------------- 79ad8ee4e0830da7125d6975c6f13790d97f2439 src/Expression/Base.hs | 52 ++++++++++++++++++++------- src/Expression/Build.hs | 2 +- src/Main.hs | 1 + src/Settings.hs | 94 ++++++++++++++++++++++++++----------------------- src/Targets.hs | 22 ++++++------ 5 files changed, 102 insertions(+), 69 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 79ad8ee4e0830da7125d6975c6f13790d97f2439 From git at git.haskell.org Thu Oct 26 23:56:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove Shake database on clean. (0bde9c1) Message-ID: <20171026235609.89CE43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0bde9c13cd854c1297296a77be53ec7940045f71/ghc >--------------------------------------------------------------- commit 0bde9c13cd854c1297296a77be53ec7940045f71 Author: Andrey Mokhov Date: Fri Jan 22 14:38:21 2016 +0000 Remove Shake database on clean. See #131. [skip ci] >--------------------------------------------------------------- 0bde9c13cd854c1297296a77be53ec7940045f71 src/Rules/Clean.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 2b4094a..eb7f8de 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -27,4 +27,6 @@ cleanRules = do forM_ [Stage0 ..] $ \stage -> do let dir = pkgPath pkg -/- targetDirectory stage pkg removeDirectoryIfExists dir + putBuild $ "| Remove the Shake database " ++ shakeFilesPath ++ "..." + removeFilesAfter shakeFilesPath ["//*"] putSuccess $ "| Done. " From git at git.haskell.org Thu Oct 26 23:56:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop commas (35d0909) Message-ID: <20171026235609.E12753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/35d09097edef38416909648fd04a50836d39e485/ghc >--------------------------------------------------------------- commit 35d09097edef38416909648fd04a50836d39e485 Author: Moritz Angermann Date: Wed Jan 6 12:20:58 2016 +0800 Drop commas >--------------------------------------------------------------- 35d09097edef38416909648fd04a50836d39e485 .travis.yml | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 09ed050..13a70d2 100644 --- a/.travis.yml +++ b/.travis.yml @@ -10,10 +10,10 @@ env: addons: apt: packages: - - ghc-7.10.3, - - alex-3.1.4, - - happy-1.19.5, - - cabal-install-1.22, + - ghc-7.10.3 + - alex-3.1.4 + - happy-1.19.5 + - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc From git at git.haskell.org Thu Oct 26 23:56:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Simplify instances for PG and Predicate. (0fe624f) Message-ID: <20171026235613.612313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0fe624fbec4b1eee99bc2e056f662568da0ffa91/ghc >--------------------------------------------------------------- commit 0fe624fbec4b1eee99bc2e056f662568da0ffa91 Author: Andrey Mokhov Date: Fri Apr 17 01:29:08 2015 +0100 Add Simplify instances for PG and Predicate. >--------------------------------------------------------------- 0fe624fbec4b1eee99bc2e056f662568da0ffa91 src/Expression/Base.hs | 14 +++++++--- src/Expression/Build.hs | 63 ++++++++++++++++++++++++++++++------------- src/Expression/PG.hs | 48 ++++++++++++++++++++++++++++++++- src/Expression/Simplify.hs | 6 +++++ src/Main.hs | 6 +++++ src/Package.hs | 3 +++ src/Settings.hs | 67 ++++++++++++++++++++++------------------------ src/Ways.hs | 3 +++ 8 files changed, 152 insertions(+), 58 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 0fe624fbec4b1eee99bc2e056f662568da0ffa91 From git at git.haskell.org Thu Oct 26 23:56:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Can we install ghc and cabal through homebrew on os x? (3ea7037) Message-ID: <20171026235613.C03AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ea7037adc5e9b0592df20d44d4269097706fe5e/ghc >--------------------------------------------------------------- commit 3ea7037adc5e9b0592df20d44d4269097706fe5e Author: Moritz Angermann Date: Wed Jan 6 12:26:12 2016 +0800 Can we install ghc and cabal through homebrew on os x? >--------------------------------------------------------------- 3ea7037adc5e9b0592df20d44d4269097706fe5e .travis.yml | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.travis.yml b/.travis.yml index 13a70d2..33c4c3e 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,6 +18,10 @@ addons: sources: hvr-ghc before_install: + osx: + - brew update + - brew outdated ghc || brew upgrade ghc + - brew outdated cabal-install || brew upgrade cabal-install - PATH="$HOME/.cabal/bin:$PATH" - PATH="/opt/ghc/$GHCVER/bin:$PATH" From git at git.haskell.org Thu Oct 26 23:56:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build.stack.sh (93605e1) Message-ID: <20171026235613.C1DA63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/93605e1d7e6644f011c7202f2a3431e927f0d87f/ghc >--------------------------------------------------------------- commit 93605e1d7e6644f011c7202f2a3431e927f0d87f Author: Joe Hillenbrand Date: Fri Jan 22 15:41:24 2016 -0800 Add build.stack.sh >--------------------------------------------------------------- 93605e1d7e6644f011c7202f2a3431e927f0d87f .gitignore | 1 + build.cabal.sh => build.stack.sh | 13 +++---------- stack.yaml | 35 +++++++++++++++++++++++++++++++++++ 3 files changed, 39 insertions(+), 10 deletions(-) diff --git a/.gitignore b/.gitignore index 39cd693..6cc5501 100644 --- a/.gitignore +++ b/.gitignore @@ -4,3 +4,4 @@ cfg/system.config cabal.sandbox.config dist/ .cabal-sandbox/ +.stack-work/ diff --git a/build.cabal.sh b/build.stack.sh similarity index 77% copy from build.cabal.sh copy to build.stack.sh index 8add516..1cc968b 100755 --- a/build.cabal.sh +++ b/build.stack.sh @@ -31,16 +31,9 @@ function rl { absoltueRoot="$(dirname "$(rl "$0")")" cd "$absoltueRoot" -# Initialize sandbox if necessary -if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then - cabal sandbox init - cabal install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared -fi - -cabal run ghc-shake -- \ +stack build --no-library-profiling + +stack exec ghc-shake -- \ --lint \ --directory "$absoltueRoot/.." \ --colour \ diff --git a/stack.yaml b/stack.yaml new file mode 100644 index 0000000..2bc3b0e --- /dev/null +++ b/stack.yaml @@ -0,0 +1,35 @@ +# For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html + +# Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) +resolver: lts-4.2 + +# Local packages, usually specified by relative directory name +packages: +- '.' + +# Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) +extra-deps: [] + +# Override default flag values for local packages and extra-deps +flags: {} + +# Extra package databases containing global packages +extra-package-dbs: [] + +# Control whether we use the GHC we find on the path +# system-ghc: false + +# Require a specific version of stack, using version ranges +# require-stack-version: -any # Default +# require-stack-version: >= 1.0.0 + +# Override the architecture used by stack, especially useful on Windows +# arch: i386 +# arch: x86_64 + +# Extra directories used by stack for building +# extra-include-dirs: [/path/to/dir] +# extra-lib-dirs: [/path/to/dir] + +# Allow a newer minor version of GHC than the snapshot specifies +# compiler-check: newer-minor From git at git.haskell.org Thu Oct 26 23:56:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a draft implementation for resolution of Config variables. (489e385) Message-ID: <20171026235617.651233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/489e385ab98b0ce8ec0b9ab8248b9bc9adb1f38b/ghc >--------------------------------------------------------------- commit 489e385ab98b0ce8ec0b9ab8248b9bc9adb1f38b Author: Andrey Mokhov Date: Fri Apr 17 22:49:20 2015 +0100 Add a draft implementation for resolution of Config variables. >--------------------------------------------------------------- 489e385ab98b0ce8ec0b9ab8248b9bc9adb1f38b src/Expression/Base.hs | 24 +++++++++---------- src/Expression/Build.hs | 2 +- src/Expression/Resolve.hs | 60 +++++++++++++++++++++++++++++++++++++++++++++++ src/Main.hs | 40 +++++++++++++++++++++++++++++-- src/Targets.hs | 2 +- 5 files changed, 112 insertions(+), 16 deletions(-) diff --git a/src/Expression/Base.hs b/src/Expression/Base.hs index e9316e8..ef6ad72 100644 --- a/src/Expression/Base.hs +++ b/src/Expression/Base.hs @@ -118,7 +118,6 @@ argWithStagedBuilder :: (Stage -> Builder) -> Settings argWithStagedBuilder f = msum $ map (\s -> stage s ? argWithBuilder (f s)) [Stage0 ..] - -- Accessing key value pairs from package-data.mk files argPackageKey :: Settings argPackageKey = return $ PackageData "PACKAGE_KEY" @@ -165,35 +164,36 @@ argPrefix prefix = fmap (Fold Concat . (arg prefix |>) . return) argPrefixPath :: String -> Settings -> Settings argPrefixPath prefix = fmap (Fold ConcatPath . (arg prefix |>) . return) --- Partially evaluate Settings using a truth-teller (compute a 'projection') -project :: (BuildVariable -> Maybe Bool) -> Settings -> Settings +-- Partially evaluate expression using a truth-teller (compute a 'projection') +project :: (BuildVariable -> Maybe Bool) -> BuildExpression v + -> BuildExpression v project _ Epsilon = Epsilon project t (Vertex v) = Vertex v -- TODO: go deeper project t (Overlay l r) = Overlay (project t l) (project t r) project t (Sequence l r) = Sequence (project t l) (project t r) project t (Condition l r) = Condition (evaluate t l) (project t r) --- Partial evaluation of settings - -setPackage :: Package -> Settings -> Settings +-- Partial evaluation of setting +setPackage :: Package -> BuildExpression v -> BuildExpression v setPackage = project . matchPackage -setBuilder :: Builder -> Settings -> Settings +setBuilder :: Builder -> BuildExpression v -> BuildExpression v setBuilder = project . matchBuilder -setBuilderFamily :: (Stage -> Builder) -> Settings -> Settings +setBuilderFamily :: (Stage -> Builder) -> BuildExpression v + -> BuildExpression v setBuilderFamily = project . matchBuilderFamily -setStage :: Stage -> Settings -> Settings +setStage :: Stage -> BuildExpression v -> BuildExpression v setStage = project . matchStage -setWay :: Way -> Settings -> Settings +setWay :: Way -> BuildExpression v -> BuildExpression v setWay = project . matchWay -setFile :: FilePath -> Settings -> Settings +setFile :: FilePath -> BuildExpression v -> BuildExpression v setFile = project . matchFile -setConfig :: String -> String -> Settings -> Settings +setConfig :: String -> String -> BuildExpression v -> BuildExpression v setConfig key = project . matchConfig key --type ArgsTeller = Args -> Maybe [String] diff --git a/src/Expression/Build.hs b/src/Expression/Build.hs index 19ff60e..8a7372d 100644 --- a/src/Expression/Build.hs +++ b/src/Expression/Build.hs @@ -21,8 +21,8 @@ module Expression.Build ( import Control.Applicative import Base import Ways -import Package (Package) import Oracles.Builder +import Package (Package) import Expression.PG -- Build variables that can be used in build predicates diff --git a/src/Expression/Resolve.hs b/src/Expression/Resolve.hs new file mode 100644 index 0000000..4ce4f7b --- /dev/null +++ b/src/Expression/Resolve.hs @@ -0,0 +1,60 @@ +{-# LANGUAGE FlexibleInstances #-} + +module Expression.Resolve ( + ResolveConfig (..) + ) where + +import Base +import Oracles.Base +import Expression.PG +import Expression.Predicate +import Expression.Base +import Expression.Build + +-- Resolve configuration variables +class ResolveConfig a where + resolveConfig :: a -> Action a + -- resolveConfig = return . id + +instance ResolveConfig BuildPredicate where + resolveConfig p @ (Evaluated _) = return p + + resolveConfig (Unevaluated (ConfigVariable key value)) = do + lookup <- askConfig key + return $ Evaluated $ lookup == value + + resolveConfig p @ (Unevaluated _) = return p + + resolveConfig (Not p) = do + p' <- resolveConfig p + return $ Not p' + + resolveConfig (And p q) = do + p' <- resolveConfig p + q' <- resolveConfig q + return $ And p' q' + + resolveConfig (Or p q) = do + p' <- resolveConfig p + q' <- resolveConfig q + return $ Or p' q' + +instance ResolveConfig (BuildExpression v) where + resolveConfig Epsilon = return Epsilon + + resolveConfig v @ (Vertex _) = return v -- TODO: go deeper + + resolveConfig (Overlay l r) = do + l' <- resolveConfig l + r' <- resolveConfig r + return $ Overlay l' r' + + resolveConfig (Sequence l r) = do + l' <- resolveConfig l + r' <- resolveConfig r + return $ Sequence l' r' + + resolveConfig (Condition l r) = do + l' <- resolveConfig l + r' <- resolveConfig r + return $ Condition l' r' diff --git a/src/Main.hs b/src/Main.hs index 4b6349a..bf0e8f7 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -4,7 +4,9 @@ import Oracles import Package import Targets import Settings +import Expression.Base import Expression.Simplify +import Expression.Resolve main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do oracleRules @@ -13,6 +15,40 @@ main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do --packageRules action $ do - putNormal $ "targetPackages = " ++ show (simplify targetPackages) - putNormal $ "\ntargetWays = " ++ show (simplify targetWays) + putNormal $ "\ntargetPackages = " ++ show (simplify targetPackages) + putNormal $ "\n\ntargetWays = " ++ show (simplify targetWays) + putNormal $ "\n\n=============================\n" + -- Read config file + targetPackages' <- resolveConfig targetPackages + targetWays' <- resolveConfig targetWays + + -- Build stages + forM_ [Stage0 ..] $ \stage -> do + putNormal $ "Stage = " ++ show stage + let packages = setStage stage targetPackages' + ways = setStage stage targetWays' + putNormal $ "\n packages = " ++ show (simplify packages) + putNormal $ "\n ways = " ++ show (simplify ways) + + --forM_ targetPackages $ \pkg @ (Package name path _ todo) -> do + -- forM_ todo $ \todoItem @ (stage, dist, settings) -> do + + -- -- Want top .o and .a files for the pkg/todo combo + -- -- We build *only one* vanilla .o file (not sure why) + -- -- We build .way_a file for each way (or its dynamic version). + -- -- TODO: Check BUILD_GHCI_LIB flag to decide if .o is needed + -- -- TODO: move this into a separate file (perhaps, to Targets.hs?) + -- action $ when (buildWhen settings) $ do + -- let pathDist = path dist + -- buildDir = pathDist "build" + -- key <- showArg (PackageKey pathDist) + -- let oFile = buildDir "Hs" ++ key <.> "o" + -- ways' <- ways settings + -- libFiles <- forM ways' $ \way -> do + -- extension <- libsuf way + -- return $ buildDir "libHs" ++ key <.> extension + -- need $ [oFile] ++ libFiles + + -- -- Build rules for the package + -- buildPackage pkg todoItem diff --git a/src/Targets.hs b/src/Targets.hs index 1b7bba2..bc2756a 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -26,7 +26,7 @@ targetPackages = msum packagesStage0 :: Packages packagesStage0 = msum [ fromList [ binPackageDb, binary, cabal, hoopl, hpc, transformers ] - , windowsHost && not (targetOs "ios") ? return terminfo ] + , not windowsHost && not (targetOs "ios") ? return terminfo ] packagesStage1 :: Packages packagesStage1 = msum From git at git.haskell.org Thu Oct 26 23:56:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: This should work, I guess. (019b513) Message-ID: <20171026235618.0C7E23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/019b51376ee25ec0d73931f3bd946bf2d3c23e71/ghc >--------------------------------------------------------------- commit 019b51376ee25ec0d73931f3bd946bf2d3c23e71 Author: Moritz Angermann Date: Wed Jan 6 12:38:22 2016 +0800 This should work, I guess. >--------------------------------------------------------------- 019b51376ee25ec0d73931f3bd946bf2d3c23e71 .travis.yml | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 33c4c3e..4a2179d 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,10 +18,9 @@ addons: sources: hvr-ghc before_install: - osx: - - brew update - - brew outdated ghc || brew upgrade ghc - - brew outdated cabal-install || brew upgrade cabal-install + - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi + - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated ghc || brew upgrade ghc; fi + - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated cabal-install || brew upgrade cabal-install; fi - PATH="$HOME/.cabal/bin:$PATH" - PATH="/opt/ghc/$GHCVER/bin:$PATH" From git at git.haskell.org Thu Oct 26 23:56:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix typos in build.*.sh (4aa3bb6) Message-ID: <20171026235618.302913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4aa3bb622b08d7f7b2fe0b45c32c4127f5ca972a/ghc >--------------------------------------------------------------- commit 4aa3bb622b08d7f7b2fe0b45c32c4127f5ca972a Author: Joe Hillenbrand Date: Fri Jan 22 16:24:41 2016 -0800 fix typos in build.*.sh >--------------------------------------------------------------- 4aa3bb622b08d7f7b2fe0b45c32c4127f5ca972a build.cabal.sh | 6 +++--- build.stack.sh | 6 +++--- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/build.cabal.sh b/build.cabal.sh index 8add516..5f20c1b 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -28,8 +28,8 @@ function rl { echo "$RESULT" } -absoltueRoot="$(dirname "$(rl "$0")")" -cd "$absoltueRoot" +absoluteRoot="$(dirname "$(rl "$0")")" +cd "$absoluteRoot" # Initialize sandbox if necessary if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then @@ -42,6 +42,6 @@ fi cabal run ghc-shake -- \ --lint \ - --directory "$absoltueRoot/.." \ + --directory "$absoluteRoot/.." \ --colour \ "$@" diff --git a/build.stack.sh b/build.stack.sh index 1cc968b..578e7eb 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -28,13 +28,13 @@ function rl { echo "$RESULT" } -absoltueRoot="$(dirname "$(rl "$0")")" -cd "$absoltueRoot" +absoluteRoot="$(dirname "$(rl "$0")")" +cd "$absoluteRoot" stack build --no-library-profiling stack exec ghc-shake -- \ --lint \ - --directory "$absoltueRoot/.." \ + --directory "$absoluteRoot/.." \ --colour \ "$@" From git at git.haskell.org Thu Oct 26 23:56:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Force AppVeyor CI to succeed and store the cache. (e01bf2f) Message-ID: <20171026235638.0001C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e01bf2f9e665a83e2cd5eae7f5a20df755ae67a9/ghc >--------------------------------------------------------------- commit e01bf2f9e665a83e2cd5eae7f5a20df755ae67a9 Author: Andrey Mokhov Date: Sat Jan 23 20:55:07 2016 +0000 Force AppVeyor CI to succeed and store the cache. [skip ci] >--------------------------------------------------------------- e01bf2f9e665a83e2cd5eae7f5a20df755ae67a9 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index d8854cc..dce914b 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -39,4 +39,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-cabal.exe From git at git.haskell.org Thu Oct 26 23:56:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add topLevel function to construct top-level packages like compiler. (f60980a) Message-ID: <20171026235640.D5CFF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f60980a571dc9da77a6718d889faf0b8a9b4b58b/ghc >--------------------------------------------------------------- commit f60980a571dc9da77a6718d889faf0b8a9b4b58b Author: Andrey Mokhov Date: Sun May 10 01:36:35 2015 +0100 Add topLevel function to construct top-level packages like compiler. >--------------------------------------------------------------- f60980a571dc9da77a6718d889faf0b8a9b4b58b src/Package.hs | 15 ++++++--------- 1 file changed, 6 insertions(+), 9 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index e5dc94e..3b2f0ec 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,4 +1,4 @@ -module Package (Package (..), library, setCabal) where +module Package (Package (..), library, topLevel, setCabal) where import Base import Util @@ -20,15 +20,12 @@ instance Eq Package where instance Ord Package where compare = compare `on` pkgName -libraryPackage :: String -> String -> Package -libraryPackage name cabalName = - Package - name - (unifyPath $ "libraries" name) - cabalName - library :: String -> Package -library name = libraryPackage name (name <.> "cabal") +library name = + Package name (unifyPath $ "libraries" name) (name <.> "cabal") + +topLevel :: String -> Package +topLevel name = Package name name (name <.> "cabal") setCabal :: Package -> FilePath -> Package setCabal pkg cabalName = pkg { pkgCabal = cabalName } From git at git.haskell.org Thu Oct 26 23:56:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: before_install steps don't merge (12c433c) Message-ID: <20171026235641.7BDF23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12c433c197e3e1db24d535aae5c7d07a6dc50e8a/ghc >--------------------------------------------------------------- commit 12c433c197e3e1db24d535aae5c7d07a6dc50e8a Author: Moritz Angermann Date: Wed Jan 6 13:11:19 2016 +0800 before_install steps don't merge Moved the validation of before_install into install. >--------------------------------------------------------------- 12c433c197e3e1db24d535aae5c7d07a6dc50e8a .travis.yml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 5c5708c..1bcd7fd 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,6 +18,8 @@ matrix: - PATH="/opt/cabal/$CABALVER/bin:$PATH" - PATH="$HOME/.cabal/bin:$PATH" - export PATH + - cabal update + - os: osx before_install: - brew update @@ -27,15 +29,14 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH -before_install: + +install: + - env - ghc --version - cabal --version - alex --version - happy --version - - cabal update - -install: - travis_retry git clone git://git.haskell.org/ghc --recurse-submodules From git at git.haskell.org Thu Oct 26 23:56:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Environment module for setting up environment variables. (f6cd23d) Message-ID: <20171026235641.B425A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f6cd23dc4b92bcedc230754f06b4c3f11438f6ae/ghc >--------------------------------------------------------------- commit f6cd23dc4b92bcedc230754f06b4c3f11438f6ae Author: Andrey Mokhov Date: Sun Jan 24 01:35:03 2016 +0000 Add Environment module for setting up environment variables. Fix #191. >--------------------------------------------------------------- f6cd23dc4b92bcedc230754f06b4c3f11438f6ae shaking-up-ghc.cabal | 1 + src/Environment.hs | 22 ++++++++++++++++++++++ src/Main.hs | 14 ++++++++------ src/Rules/Config.hs | 8 +------- 4 files changed, 32 insertions(+), 13 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index bd21d28..cdd512a 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -20,6 +20,7 @@ executable ghc-shake other-modules: Base , Builder , CmdLineFlag + , Environment , Expression , GHC , Oracles diff --git a/src/Environment.hs b/src/Environment.hs new file mode 100644 index 0000000..fd207ed --- /dev/null +++ b/src/Environment.hs @@ -0,0 +1,22 @@ +module Environment (setupEnvironment) where + +import Base +import System.Environment + +-- | The build system invokes many external builders whose behaviour is +-- influenced by the environment variables. We need to modify some of them +-- for better robustness of the build system. +setupEnvironment :: IO () +setupEnvironment = do + -- ghc-cabal refuses to work when GHC_PACKAGE_PATH is set (e.g. by Stack) + unsetEnv "GHC_PACKAGE_PATH" + + -- On Windows, some path variables start a prefix like "C:\\" which may + -- lead to failures of scripts such as autoreconf. One particular variable + -- which causes issues is ACLOCAL_PATH. At the moment we simply reset it + -- if it contains a problematic Windows path. + -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. + aclocal <- lookupEnv "ACLOCAL_PATH" + case aclocal of + Nothing -> return () + Just s -> when (":\\" `isPrefixOf` drop 1 s) $ unsetEnv "ACLOCAL_PATH" diff --git a/src/Main.hs b/src/Main.hs index 7321f88..69f739b 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,7 +3,8 @@ module Main (main) where import Development.Shake import qualified Base -import CmdLineFlag +import qualified CmdLineFlag +import qualified Environment import qualified Rules import qualified Rules.Cabal import qualified Rules.Clean @@ -16,8 +17,9 @@ import qualified Rules.Perl import qualified Test main :: IO () -main = shakeArgsWith options flags $ \cmdLineFlags targets -> do - putCmdLineFlags cmdLineFlags +main = shakeArgsWith options CmdLineFlag.flags $ \cmdLineFlags targets -> do + CmdLineFlag.putCmdLineFlags cmdLineFlags + Environment.setupEnvironment return . Just $ if null targets then rules else want targets >> withoutActions rules @@ -27,13 +29,13 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do [ Rules.Cabal.cabalRules , Rules.Clean.cleanRules , Rules.Config.configRules - , Rules.Generate.copyRules , Rules.Generate.generateRules - , Rules.Perl.perlScriptRules - , Rules.generateTargets + , Rules.Generate.copyRules , Rules.Gmp.gmpRules , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules + , Rules.Perl.perlScriptRules + , Rules.generateTargets , Rules.packageRules , Test.testRules ] options = shakeOptions diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 77ac1ac..1297825 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -21,10 +21,4 @@ configRules = do -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. "configure" %> \_ -> do putBuild "| Running boot..." - aclocal <- getEnv "ACLOCAL_PATH" - let env = case aclocal of - Nothing -> [] - Just s -> if ":\\" `isPrefixOf` (drop 1 s) - then [AddEnv "ACLOCAL_PATH" ""] - else [] - quietly $ cmd (EchoStdout False) env "perl boot" + quietly $ cmd (EchoStdout False) "perl boot" From git at git.haskell.org Thu Oct 26 23:56:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove TargetDir from Base.hs. (f033f1f) Message-ID: <20171026235644.5F70C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f033f1ff0b94df3b12dd32d774043522c96f0cac/ghc >--------------------------------------------------------------- commit f033f1ff0b94df3b12dd32d774043522c96f0cac Author: Andrey Mokhov Date: Sun May 10 01:37:24 2015 +0100 Remove TargetDir from Base.hs. >--------------------------------------------------------------- f033f1ff0b94df3b12dd32d774043522c96f0cac src/Base.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 2bd350f..49b0fb2 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -8,7 +8,6 @@ module Base ( module Data.Monoid, module Data.List, Stage (..), - TargetDir (..), Arg, Args, ShowArg (..), ShowArgs (..), arg, args, @@ -29,9 +28,6 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum) instance Show Stage where show = show . fromEnum --- Need TargetDir and FilePath to be distinct types -newtype TargetDir = TargetDir { fromTargetDir :: FilePath } deriving (Show, Eq) - -- The returned string or list of strings is a part of an argument list -- to be passed to a Builder type Arg = Action String From git at git.haskell.org Thu Oct 26 23:56:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set CONFIG_SHELL, such that libtool obtains the bash header. (cb74ce8) Message-ID: <20171026235644.E7F7C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb74ce8f2ca00bc2cfac8b003c4c7adade5734af/ghc >--------------------------------------------------------------- commit cb74ce8f2ca00bc2cfac8b003c4c7adade5734af Author: Moritz Angermann Date: Wed Jan 6 14:37:10 2016 +0800 Set CONFIG_SHELL, such that libtool obtains the bash header. This improves on #103 and fixes #114, hopefully. >--------------------------------------------------------------- cb74ce8f2ca00bc2cfac8b003c4c7adade5734af src/Rules/Actions.hs | 6 +++++- src/Rules/IntegerGmp.hs | 2 +- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9250357..e32a42f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -94,7 +94,11 @@ runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] putBuild $ "| Run configure in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args + quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args + where + -- Always configure with bash. + -- This also injects /bin/bash into `libtool`, instead of /bin/sh + opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] runMake :: FilePath -> [String] -> Action () runMake dir args = do diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 2b9bbd9..7ef124f 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -114,7 +114,7 @@ integerGmpRules = do copyFile integerGmpLibraryFakeH integerGmpLibraryH else do putBuild "| No GMP framework detected; in tree GMP will be built" - runMake integerGmpBuild ["MAKEFLAGS='LIBTOOL=bash\\ libtool'"] + runMake integerGmpBuild [] copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryInTreeH copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryH From git at git.haskell.org Thu Oct 26 23:56:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, build stage 1 GHC on AppVeyor. (73d8de1) Message-ID: <20171026235645.5333D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73d8de188efbf8c07d750416bfd74ef567ffacec/ghc >--------------------------------------------------------------- commit 73d8de188efbf8c07d750416bfd74ef567ffacec Author: Andrey Mokhov Date: Sun Jan 24 02:15:57 2016 +0000 Clean up, build stage 1 GHC on AppVeyor. >--------------------------------------------------------------- 73d8de188efbf8c07d750416bfd74ef567ffacec .appveyor.yml | 2 +- src/GHC.hs | 4 ++-- src/Package.hs | 14 ++++++++++++-- src/Rules.hs | 3 +-- src/Rules/Config.hs | 2 -- src/Rules/Libffi.hs | 2 +- src/Stage.hs | 23 +++++++++++------------ src/Target.hs | 2 +- src/Test.hs | 7 +++---- 9 files changed, 32 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 73d8de188efbf8c07d750416bfd74ef567ffacec From git at git.haskell.org Thu Oct 26 23:56:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add documentation drafts. (a2de9b0) Message-ID: <20171026235648.245643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2de9b043b90ef7fc68fea6b1f16535e9f7a20c8/ghc >--------------------------------------------------------------- commit a2de9b043b90ef7fc68fea6b1f16535e9f7a20c8 Author: Andrey Mokhov Date: Sun May 10 01:39:20 2015 +0100 Add documentation drafts. >--------------------------------------------------------------- a2de9b043b90ef7fc68fea6b1f16535e9f7a20c8 doc/build-expressions.docx | Bin 0 -> 22575 bytes doc/build-expressions.pdf | Bin 0 -> 644843 bytes 2 files changed, 0 insertions(+), 0 deletions(-) diff --git a/doc/build-expressions.docx b/doc/build-expressions.docx new file mode 100644 index 0000000..e4fef75 Binary files /dev/null and b/doc/build-expressions.docx differ diff --git a/doc/build-expressions.pdf b/doc/build-expressions.pdf new file mode 100644 index 0000000..bf70430 Binary files /dev/null and b/doc/build-expressions.pdf differ From git at git.haskell.org Thu Oct 26 23:56:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove -Wall and -fwarn-tabs, fix #116. (f8d9ddc) Message-ID: <20171026235649.1DD5E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8d9ddc5a43872f248d60e7fcdb1f0c5be580cc1/ghc >--------------------------------------------------------------- commit f8d9ddc5a43872f248d60e7fcdb1f0c5be580cc1 Author: Andrey Mokhov Date: Wed Jan 6 10:41:19 2016 +0000 Remove -Wall and -fwarn-tabs, fix #116. >--------------------------------------------------------------- f8d9ddc5a43872f248d60e7fcdb1f0c5be580cc1 src/Settings/User.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index aba4a48..7a877ce 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -8,11 +8,11 @@ module Settings.User ( import GHC import Expression +import Predicates --- No user-specific settings by default --- TODO: rename to userArgs +-- Control user-specific settings userArgs :: Args -userArgs = mempty +userArgs = builderGhc ? remove ["-Wall", "-fwarn-tabs"] -- Control which packages get to be built userPackages :: Packages From git at git.haskell.org Thu Oct 26 23:56:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make .cabal meta-data more accurate (f9e5109) Message-ID: <20171026235649.4CECC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f9e510913956bc01201ad74bab60767794424034/ghc >--------------------------------------------------------------- commit f9e510913956bc01201ad74bab60767794424034 Author: Herbert Valerio Riedel Date: Sun Jan 24 10:07:01 2016 +0100 Make .cabal meta-data more accurate We need this so cabal (this is even more important with the upcoming nix-style cabal features) can do a proper job so this is a pre-requisite for the new build-system being used by default for GHC anyway, as we need to be as accurate as possible with the build specification to give `git bisect` a chance of remaining usable. >--------------------------------------------------------------- f9e510913956bc01201ad74bab60767794424034 shaking-up-ghc.cabal | 32 +++++++++++++++----------------- 1 file changed, 15 insertions(+), 17 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index cdd512a..674d6f0 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -107,26 +107,24 @@ executable ghc-shake , Test , Way - default-extensions: BangPatterns - , LambdaCase - , MultiWayIf - , TupleSections + default-language: Haskell2010 other-extensions: DeriveDataTypeable , DeriveGeneric , FlexibleInstances + , GeneralizedNewtypeDeriving + , LambdaCase , OverloadedStrings , RecordWildCards , ScopedTypeVariables - build-depends: base - , ansi-terminal >= 0.6 - , Cabal >= 1.22 - , containers >= 0.5 - , directory >= 1.2 - , extra >= 1.4 - , mtl >= 2.2 - , QuickCheck >= 2.6 - , shake >= 0.15 - , transformers >= 0.4 - , unordered-containers >= 0.2 - default-language: Haskell2010 - ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j + build-depends: base >= 4.8 && < 5 + , ansi-terminal == 0.6.* + , Cabal == 1.22.* + , containers == 0.5.* + , directory == 1.2.* + , extra == 1.4.* + , mtl == 2.2.* + , QuickCheck >= 2.6 && < 2.9 + , shake == 0.15.* + , transformers >= 0.4 && < 0.6 + , unordered-containers == 0.2.* + ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 From git at git.haskell.org Thu Oct 26 23:56:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildPackageDependencies rule. (2be9217) Message-ID: <20171026235652.09A4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2be9217deed8466c4aa62ac4120174a354d342c8/ghc >--------------------------------------------------------------- commit 2be9217deed8466c4aa62ac4120174a354d342c8 Author: Andrey Mokhov Date: Sun May 10 01:40:19 2015 +0100 Add buildPackageDependencies rule. >--------------------------------------------------------------- 2be9217deed8466c4aa62ac4120174a354d342c8 src/Rules/Dependencies.hs | 185 ++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 185 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs new file mode 100644 index 0000000..930ba98 --- /dev/null +++ b/src/Rules/Dependencies.hs @@ -0,0 +1,185 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module Rules.Data ( + ghcArgs, gccArgs, buildPackageDependencies + ) where + +import qualified Ways +import Base hiding (arg, args, Args) +import Package +import Expression.Base +import Oracles.Flag (when) +import Oracles.Builder +import Targets +import Switches +import Util + +packageSettings :: Settings +packageSettings = msum + [ args ["-hide-all-packages", "-no-user-package-db", "-include-pkg-deps"] + , stage Stage0 ? + (arg "-package-db" |> argPath "libraries/bootstrapping.conf") + , supportsPackageKey ? notStage Stage0 ?? + ( argPairs "-this-package-key" argPackageKey <|> + argPairs "-package-key" argPackageDepKeys + , argPairs "-package-name" argPackageKey <|> + argPairs "-package" argPackageDeps )] + +ghcArgs :: Settings +ghcArgs = + let pathDist = path dist + buildDir = unifyPath $ pathDist "build" + depFile = buildDir "haskell.deps" + in msum [ arg "-M" + , packageSettings + , includeGhcArgs path dist + , concatArgs ["-optP"] $ CppArgs pathDist + , productArgs ["-odir", "-stubdir", "-hidir"] [buildDir] + , args ["-dep-makefile", depFile] + , productArgs ["-dep-suffix"] $ map wayPrefix <$> ways settings + , args $ HsArgs pathDist + , args $ pkgHsSources path dist ] + +-- $1_$2_$3_ALL_CC_OPTS = \ +-- $$(WAY_$3_CC_OPTS) \ +-- $$($1_$2_DIST_GCC_CC_OPTS) \ +-- $$($1_$2_$3_CC_OPTS) \ +-- $$($$(basename $$<)_CC_OPTS) \ +-- $$($1_$2_EXTRA_CC_OPTS) \ +-- $$(EXTRA_CC_OPTS) +-- +-- $1_$2_DIST_CC_OPTS = \ +-- $$(SRC_CC_OPTS) \ +-- $$($1_CC_OPTS) \ +-- -I$1/$2/build/autogen \ +-- $$(foreach dir,$$(filter-out /%,$$($1_$2_INCLUDE_DIRS)),-I$1/$$(dir)) \ +-- $$(foreach dir,$$(filter /%,$$($1_$2_INCLUDE_DIRS)),-I$$(dir)) \ +-- $$($1_$2_CC_OPTS) \ +-- $$($1_$2_CPP_OPTS) \ +-- $$($1_$2_CC_INC_FLAGS) \ +-- $$($1_$2_DEP_CC_OPTS) \ +-- $$(SRC_CC_WARNING_OPTS) + +-- TODO: handle custom $1_$2_MKDEPENDC_OPTS and +gccArgs :: FilePath -> Package -> TodoItem -> Args +gccArgs sourceFile (Package _ path _ _) (stage, dist, settings) = + let pathDist = path dist + buildDir = pathDist "build" + depFile = buildDir takeFileName sourceFile <.> "deps" + in args [ args ["-E", "-MM"] -- TODO: add a Cpp Builder instead + , args $ CcArgs pathDist + , commonCcArgs -- TODO: remove? + , customCcArgs settings -- TODO: Replace by customCppArgs? + , commonCcWarninigArgs -- TODO: remove? + , includeGccArgs path dist + , args ["-MF", unifyPath depFile] + , args ["-x", "c"] + , arg $ unifyPath sourceFile ] + +buildRule :: Package -> TodoItem -> Rules () +buildRule pkg @ (Package name path _ _) todo @ (stage, dist, settings) = do + let pathDist = path dist + buildDir = pathDist "build" + + (buildDir "haskell.deps") %> \_ -> do + run (Ghc stage) $ ghcArgs pkg todo + -- Finally, record the argument list + need [argListPath argListDir pkg stage] + + (buildDir "c.deps") %> \out -> do + srcs <- args $ CSrcs pathDist + deps <- fmap concat $ forM srcs $ \src -> do + let srcPath = path src + depFile = buildDir takeFileName src <.> "deps" + run (Gcc stage) $ gccArgs srcPath pkg todo + liftIO $ readFile depFile + writeFileChanged out deps + liftIO $ removeFiles buildDir ["*.c.deps"] + -- Finally, record the argument list + need [argListPath argListDir pkg stage] + +argListRule :: Package -> TodoItem -> Rules () +argListRule pkg todo @ (stage, _, _) = + (argListPath argListDir pkg stage) %> \out -> do + need $ ["shake/src/Package/Dependencies.hs"] ++ sourceDependecies + ghcList <- argList (Ghc stage) $ ghcArgs pkg todo + gccList <- argList (Gcc stage) $ gccArgs "source.c" pkg todo + writeFileChanged out $ ghcList ++ "\n" ++ gccList + +buildPackageDependencies :: Package -> TodoItem -> Rules () +buildPackageDependencies = argListRule <> buildRule + + +-- Build package-data.mk by using GhcCabal to process pkgCabal file +buildPackageData :: Stage -> Package -> FilePath -> Ways -> Settings -> Rules () +buildPackageData stage pkg dir ways settings = + (dir ) <$> + [ "package-data.mk" + , "haddock-prologue.txt" + , "inplace-pkg-config" + , "setup-config" + , "build" "autogen" "cabal_macros.h" + -- TODO: Is this needed? Also check out Paths_cpsa.hs. + -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" + ] &%> \_ -> do + let configure = pkgPath pkg "configure" + need [pkgPath pkg pkgCabal pkg] + -- GhcCabal will run the configure script, so we depend on it + -- We still don't know who build the configure script from configure.ac + when (doesFileExist $ configure <.> "ac") $ need [configure] + run' GhcCabal settings + -- TODO: when (registerPackage settings) $ + run' (GhcPkg stage) settings + postProcessPackageData $ dir "package-data.mk" + +run' :: Builder -> Settings -> Action () +run' builder settings = do + settings' <- evaluate (project builder settings) + case fromSettings settings' of + Nothing -> + redError $ "Cannot determine " ++ show builder ++ " settings." + Just args -> do + putColoured Green (show args) + run builder args + +--buildRule :: Package -> TodoItem -> Rules () +--buildRule pkg @ (Package name path cabal _) todo @ (stage, dist, settings) = +-- let pathDist = path dist +-- cabalPath = path cabal +-- configure = path "configure" +-- in +-- -- All these files are produced by a single run of GhcCabal +-- (pathDist ) <$> +-- [ "package-data.mk" +-- , "haddock-prologue.txt" +-- , "inplace-pkg-config" +-- , "setup-config" +-- , "build" "autogen" "cabal_macros.h" +-- -- TODO: Is this needed? Also check out Paths_cpsa.hs. +-- -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" +-- ] &%> \_ -> do +-- need [cabalPath] +-- when (doesFileExist $ configure <.> "ac") $ need [configure] +-- -- GhcCabal will run the configure script, so we depend on it +-- -- We still don't know who build the configure script from configure.ac +-- run GhcCabal $ cabalArgs pkg todo +-- when (registerPackage settings) $ +-- run (GhcPkg stage) $ ghcPkgArgs pkg todo +-- postProcessPackageData $ pathDist "package-data.mk" + +ccSettings :: Settings +ccSettings = msum + [ package integerLibrary ? argPath "-Ilibraries/integer-gmp2/gmp" + , builder GhcCabal ? argStagedConfig "conf-cc-args" + , validating ? msum + [ not (builder GhcCabal) ? arg "-Werror" + , arg "-Wall" + , gccIsClang ?? + ( arg "-Wno-unknown-pragmas" <|> + not gccLt46 ? windowsHost ? arg "-Werror=unused-but-set-variable" + , not gccLt46 ? arg "-Wno-error=inline" )]] + +ldSettings :: Settings +ldSettings = builder GhcCabal ? argStagedConfig "conf-gcc-linker-args" + +cppSettings :: Settings +cppSettings = builder GhcCabal ? argStagedConfig "conf-cpp-args" From git at git.haskell.org Thu Oct 26 23:56:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds "MAKEFLAGS=" back in. (7b5c5bf) Message-ID: <20171026235652.BBAF63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b5c5bf2250f088bac663c2d2773b32d5e1b756b/ghc >--------------------------------------------------------------- commit 7b5c5bf2250f088bac663c2d2773b32d5e1b756b Author: Moritz Angermann Date: Wed Jan 6 18:48:56 2016 +0800 Adds "MAKEFLAGS=" back in. >--------------------------------------------------------------- 7b5c5bf2250f088bac663c2d2773b32d5e1b756b src/Rules/IntegerGmp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 7ef124f..b82dcbb 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -114,7 +114,7 @@ integerGmpRules = do copyFile integerGmpLibraryFakeH integerGmpLibraryH else do putBuild "| No GMP framework detected; in tree GMP will be built" - runMake integerGmpBuild [] + runMake integerGmpBuild ["MAKEFLAGS="] copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryInTreeH copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryH From git at git.haskell.org Thu Oct 26 23:56:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add `cabal new-build` based wrapper script (6432f0c) Message-ID: <20171026235653.058153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6432f0c241ea173bd5d7f7de4833085d6155c47f/ghc >--------------------------------------------------------------- commit 6432f0c241ea173bd5d7f7de4833085d6155c47f Author: Herbert Valerio Riedel Date: Sun Jan 24 10:43:43 2016 +0100 Add `cabal new-build` based wrapper script This makes use of the new nix-store cache for the shake library and other pre-requisities, rather than using the reinstall-breakage-prone old-style global pkg-db >--------------------------------------------------------------- 6432f0c241ea173bd5d7f7de4833085d6155c47f .gitignore | 17 ++++++++++++----- build.sh => build.cabal-new.sh | 28 +++++++++++++++++++--------- 2 files changed, 31 insertions(+), 14 deletions(-) diff --git a/.gitignore b/.gitignore index 6cc5501..967be07 100644 --- a/.gitignore +++ b/.gitignore @@ -1,7 +1,14 @@ -.shake/ -.db/ +/.shake/ +/.db/ cfg/system.config + +# build.cabal.sh specific +/dist/ +/.cabal-sandbox/ cabal.sandbox.config -dist/ -.cabal-sandbox/ -.stack-work/ + +# build.cabal-new.sh specific +/dist-newstyle/ + +# build.stack.sh specific +/.stack-work/ diff --git a/build.sh b/build.cabal-new.sh similarity index 60% copy from build.sh copy to build.cabal-new.sh index 719e85e..96c194e 100755 --- a/build.sh +++ b/build.cabal-new.sh @@ -1,5 +1,8 @@ #!/usr/bin/env bash +# This wrapper scripts makes use of cabal 1.24+'s nix-store; +# In order to clean/reset, remove the `dist-newstyle/` folder + set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -32,15 +35,22 @@ root="$(dirname "$(rl "$0")")" mkdir -p "$root/.shake" -ghc \ - "$root/src/Main.hs" \ - -Wall \ - -i"$root/src" \ - -rtsopts \ - -with-rtsopts=-I0 \ - -outputdir="$root/.shake" \ - -j -O \ - -o "$root/.shake/build" +# Notes/Random thoughts: +# +# - if ghc.git had a top-level `cabal.project` file, we could maybe avoid the +# boilerplate above, as we could simply say `cabal exec ghc-shake` from within +# any GHC folder not shadowed by a nearer shadowing `cabal.project` file. + +pushd "$root/" + +cabal new-build --disable-profiling --disable-documentation -j exe:ghc-shake + +PKGVER="$(awk '/^version:/ { print $2 }' shaking-up-ghc.cabal)" + +cp -v "$root/dist-newstyle/build/shaking-up-ghc-${PKGVER}/build/ghc-shake/ghc-shake" \ + "$root/.shake/build" + +popd "$root/.shake/build" \ --lint \ From git at git.haskell.org Thu Oct 26 23:56:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Continue refactoring. (cf54d1a) Message-ID: <20171026235655.A1C683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf54d1aacd927a06a74918de2db479ac6d5ef2a8/ghc >--------------------------------------------------------------- commit cf54d1aacd927a06a74918de2db479ac6d5ef2a8 Author: Andrey Mokhov Date: Sun May 10 01:41:36 2015 +0100 Continue refactoring. >--------------------------------------------------------------- cf54d1aacd927a06a74918de2db479ac6d5ef2a8 src/Rules.hs | 8 ++-- src/Rules/Data.hs | 23 +++++---- src/Rules/Package.hs | 2 +- src/Settings.hs | 11 ----- src/Switches.hs | 95 ++++++++++++++++++------------------ src/Targets.hs | 132 +++++++++++++++++++++++++++------------------------ 6 files changed, 138 insertions(+), 133 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 cf54d1aacd927a06a74918de2db479ac6d5ef2a8 From git at git.haskell.org Thu Oct 26 23:56:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #115 from angerman/feature/libtool (2f52d19) Message-ID: <20171026235656.5101B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f52d196dbd5cd3f1da25286deef5cb3cd17c142/ghc >--------------------------------------------------------------- commit 2f52d196dbd5cd3f1da25286deef5cb3cd17c142 Merge: f8d9ddc 7b5c5bf Author: Andrey Mokhov Date: Wed Jan 6 10:51:29 2016 +0000 Merge pull request #115 from angerman/feature/libtool Set CONFIG_SHELL, such that libtool obtains the bash header. >--------------------------------------------------------------- 2f52d196dbd5cd3f1da25286deef5cb3cd17c142 src/Rules/Actions.hs | 6 +++++- src/Rules/IntegerGmp.hs | 2 +- 2 files changed, 6 insertions(+), 2 deletions(-) From git at git.haskell.org Thu Oct 26 23:56:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Temporarily disable ChangeModtimeAndDigest (test AppVeyor speed up). (21eef1e) Message-ID: <20171026235656.A6E623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21eef1e36c8592c04724fa59a61f0826fd2b94cd/ghc >--------------------------------------------------------------- commit 21eef1e36c8592c04724fa59a61f0826fd2b94cd Author: Andrey Mokhov Date: Sun Jan 24 13:06:56 2016 +0000 Temporarily disable ChangeModtimeAndDigest (test AppVeyor speed up). [skip ci] >--------------------------------------------------------------- 21eef1e36c8592c04724fa59a61f0826fd2b94cd src/Main.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 69f739b..0f0d450 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -39,7 +39,6 @@ main = shakeArgsWith options CmdLineFlag.flags $ \cmdLineFlags targets -> do , Rules.packageRules , Test.testRules ] options = shakeOptions - { shakeChange = ChangeModtimeAndDigest - , shakeFiles = Base.shakeFilesPath + { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Thu Oct 26 23:56:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop parameterisation by monad in Expression. (fdb6117) Message-ID: <20171026235659.537843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fdb6117f21e3bc39ae97bf0f12c0fc3caf10e093/ghc >--------------------------------------------------------------- commit fdb6117f21e3bc39ae97bf0f12c0fc3caf10e093 Author: Andrey Mokhov Date: Mon Jun 8 02:07:09 2015 +0100 Drop parameterisation by monad in Expression. >--------------------------------------------------------------- fdb6117f21e3bc39ae97bf0f12c0fc3caf10e093 src/Expression.hs | 51 ++++++++++++++++++++++++++++----------------------- 1 file changed, 28 insertions(+), 23 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index fc70be1..de5fae9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -2,13 +2,11 @@ module Expression ( module Control.Monad.Reader, Ways, - Packages, - TargetDir, Predicate, Expression, - Environment (..), + Environment (..), defaultEnvironment, interpret, - whenPredicate, (?), stage, notStage, package, + whenPredicate, (?), (??), stage, notStage, builder, notBuilder, package, configKeyValue, configKeyValues, configKeyYes, configKeyNo, configKeyNonEmpty ) where @@ -34,51 +32,58 @@ defaultEnvironment = Environment getPackage = error "Package not set in the environment" } -type Expression m a = ReaderT Environment m a +type Expression a = ReaderT Environment Action a -type Ways m = Expression m [Way] -type Packages m = Expression m [Package] -type Predicate m = Expression m Bool -type TargetDir m = Expression m FilePath +type Ways = Expression [Way] +type Predicate = Expression Bool -instance (Monad m, Monoid a) => Monoid (Expression m a) where +instance Monoid a => Monoid (Expression a) where mempty = return mempty mappend = liftM2 mappend -interpret :: (Monad m, Monoid a) => Expression m a -> Environment -> m a -interpret = runReaderT +interpret :: Environment -> Expression a -> Action a +interpret = flip runReaderT -whenPredicate :: (Monad m, Monoid a) => Predicate m -> Expression m a -> Expression m a +whenPredicate :: Monoid a => Predicate -> Expression a -> Expression a whenPredicate predicate expr = do bool <- predicate if bool then expr else return mempty -(?) :: (Monad m, Monoid a) => Predicate m -> Expression m a -> Expression m a +(?) :: Monoid a => Predicate -> Expression a -> Expression a (?) = whenPredicate +(??) :: Monoid a => Predicate -> (Expression a, Expression a) -> Expression a +p ?? (t, f) = p ? t <> (liftM not p) ? f + infixr 8 ? -stage :: Monad m => Stage -> Predicate m +stage :: Stage -> Predicate stage s = liftM (s ==) (asks getStage) -notStage :: Monad m => Stage -> Predicate m +notStage :: Stage -> Predicate notStage = liftM not . stage -package :: Monad m => Package -> Predicate m +builder :: Builder -> Predicate +builder b = liftM (b ==) (asks getBuilder) + +notBuilder :: Builder -> Predicate +notBuilder = liftM not . builder + +package :: Package -> Predicate package p = liftM (p ==) (asks getPackage) -configKeyValue :: String -> String -> Predicate Action +configKeyValue :: String -> String -> Predicate configKeyValue key value = liftM (value ==) (lift $ askConfig key) -- checks if there is at least one match -configKeyValues :: String -> [String] -> Predicate Action +configKeyValues :: String -> [String] -> Predicate configKeyValues key values = liftM (flip elem $ values) (lift $ askConfig key) -configKeyYes :: String -> Predicate Action +configKeyYes :: String -> Predicate configKeyYes key = configKeyValue key "YES" -configKeyNo :: String -> Predicate Action +configKeyNo :: String -> Predicate configKeyNo key = configKeyValue key "NO" -configKeyNonEmpty :: String -> Predicate Action -configKeyNonEmpty key = configKeyValue key "" +configKeyNonEmpty :: String -> Predicate +configKeyNonEmpty key = liftM not $ configKeyValue key "" From git at git.haskell.org Thu Oct 26 23:57:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #112 from angerman/feature/osx-ci (6095058) Message-ID: <20171026235700.1D9123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/609505834ca4a9178b8263b00208ec651318c8c1/ghc >--------------------------------------------------------------- commit 609505834ca4a9178b8263b00208ec651318c8c1 Merge: 2f52d19 12c433c Author: Andrey Mokhov Date: Wed Jan 6 10:56:48 2016 +0000 Merge pull request #112 from angerman/feature/osx-ci Adds osx to the list of operatin systems in the travis.yml >--------------------------------------------------------------- 609505834ca4a9178b8263b00208ec651318c8c1 .travis.yml | 55 +++++++++++++++++++++++++++++-------------------------- 1 file changed, 29 insertions(+), 26 deletions(-) From git at git.haskell.org Thu Oct 26 23:57:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #192 from hvr/pr/fix-cabal-metadata (45e208e) Message-ID: <20171026235700.894653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45e208eda37617737650d02ad7a6427e4618e1bf/ghc >--------------------------------------------------------------- commit 45e208eda37617737650d02ad7a6427e4618e1bf Merge: 21eef1e f9e5109 Author: Andrey Mokhov Date: Sun Jan 24 13:48:25 2016 +0000 Merge pull request #192 from hvr/pr/fix-cabal-metadata Make .cabal meta-data more accurate [skip ci] >--------------------------------------------------------------- 45e208eda37617737650d02ad7a6427e4618e1bf shaking-up-ghc.cabal | 32 +++++++++++++++----------------- 1 file changed, 15 insertions(+), 17 deletions(-) From git at git.haskell.org Thu Oct 26 23:57:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish buildPackageData with the Reader approach. (031179a) Message-ID: <20171026235704.998413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/031179a7506ef56897b6316fc83b46fecfb61946/ghc >--------------------------------------------------------------- commit 031179a7506ef56897b6316fc83b46fecfb61946 Author: Andrey Mokhov Date: Mon Jun 8 02:08:57 2015 +0100 Finish buildPackageData with the Reader approach. >--------------------------------------------------------------- 031179a7506ef56897b6316fc83b46fecfb61946 src/Expression/Settings.hs | 15 ++-- src/Rules.hs | 41 ++++----- src/Rules/Data.hs | 202 ++++++++++++++++++++++++++------------------- src/Rules/Package.hs | 1 + src/Settings.hs | 11 +-- src/Switches.hs | 39 +++++---- src/Targets.hs | 70 +++++++++------- 7 files changed, 206 insertions(+), 173 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 031179a7506ef56897b6316fc83b46fecfb61946 From git at git.haskell.org Thu Oct 26 23:57:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify extraObjects in src/Rules/Library.hs, see #117. (ce8ffdb) Message-ID: <20171026235705.184B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ce8ffdbbb7d477d022f5df20e77467413f80349b/ghc >--------------------------------------------------------------- commit ce8ffdbbb7d477d022f5df20e77467413f80349b Author: Andrey Mokhov Date: Wed Jan 6 11:10:49 2016 +0000 Simplify extraObjects in src/Rules/Library.hs, see #117. >--------------------------------------------------------------- ce8ffdbbb7d477d022f5df20e77467413f80349b src/Rules/Library.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 41e7b3d..46f3971 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -80,9 +80,5 @@ extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do need [integerGmpLibraryH] - objsExist <- doesDirectoryExist integerGmpObjects - putBuild $ "objsExist = " ++ show objsExist - if objsExist - then getDirectoryFiles "" [integerGmpObjects -/- "*.o"] - else return [] + getDirectoryFiles "" [integerGmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Thu Oct 26 23:57:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #193 from hvr/pr/cabal-nix (e2271ac) Message-ID: <20171026235705.700223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2271ac0a67bec50c9fd45bef036e98e19e83d21/ghc >--------------------------------------------------------------- commit e2271ac0a67bec50c9fd45bef036e98e19e83d21 Merge: 45e208e 6432f0c Author: Andrey Mokhov Date: Sun Jan 24 13:49:25 2016 +0000 Merge pull request #193 from hvr/pr/cabal-nix Add `cabal new-build`-based wrapper script [skip ci] >--------------------------------------------------------------- e2271ac0a67bec50c9fd45bef036e98e19e83d21 .gitignore | 17 ++++++++++++----- build.sh => build.cabal-new.sh | 28 +++++++++++++++++++--------- 2 files changed, 31 insertions(+), 14 deletions(-) From git at git.haskell.org Thu Oct 26 23:57:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify build rule interfaces. (622d3c1) Message-ID: <20171026235708.6572F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/622d3c164d3c36fba97e780a5d3e3b4049e18417/ghc >--------------------------------------------------------------- commit 622d3c164d3c36fba97e780a5d3e3b4049e18417 Author: Andrey Mokhov Date: Sat Jun 13 14:14:03 2015 +0100 Simplify build rule interfaces. >--------------------------------------------------------------- 622d3c164d3c36fba97e780a5d3e3b4049e18417 src/Rules.hs | 4 ++-- src/Rules/Data.hs | 9 ++++++--- src/Rules/Package.hs | 3 +-- 3 files changed, 9 insertions(+), 7 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 8f2825f..dd9e2e0 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -30,5 +30,5 @@ packageRules :: Rules () packageRules = forM_ [Stage0, Stage1] $ \stage -> do forM_ targetPackages $ \pkg -> do - let dir = pkgPath pkg targetDirectory stage pkg - buildPackage stage pkg dir targetWays buildSettings + let env = defaultEnvironment { getStage = stage, getPackage = pkg } + buildPackage env targetWays buildSettings diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 0a1abf1..7447e5e 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -140,8 +140,12 @@ postProcessPackageData file = do -- * otherwise, we must collapse it into one space-separated string -- Build package-data.mk by using GhcCabal to process pkgCabal file -buildPackageData :: Stage -> Package -> FilePath -> Ways -> Settings -> Rules () -buildPackageData stage pkg dir ways settings = +buildPackageData :: Environment -> Ways -> Settings -> Rules () +buildPackageData env ways settings = + let stage = getStage env + pkg = getPackage env + dir = pkgPath pkg targetDirectory stage pkg + in (dir ) <$> [ "package-data.mk" , "haddock-prologue.txt" @@ -152,7 +156,6 @@ buildPackageData stage pkg dir ways settings = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" - env = defaultEnvironment { getStage = stage, getPackage = pkg } need [pkgPath pkg pkgCabal pkg] -- GhcCabal will run the configure script, so we depend on it -- We still don't know who build the configure script from configure.ac diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 5ce0ed9..d56bb30 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -3,10 +3,9 @@ module Rules.Package ( ) where import Base -import Package import Rules.Data import Expression import Expression.Settings -buildPackage :: Stage -> Package -> FilePath -> Ways -> Settings -> Rules () +buildPackage :: Environment -> Ways -> Settings -> Rules () buildPackage = buildPackageData From git at git.haskell.org Thu Oct 26 23:57:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor generated dependencies (41ecfdc) Message-ID: <20171026235708.D198A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/41ecfdc70602aed5335f7205a092c336c090ec90/ghc >--------------------------------------------------------------- commit 41ecfdc70602aed5335f7205a092c336c090ec90 Author: Andrey Mokhov Date: Wed Jan 6 11:56:22 2016 +0000 Refactor generated dependencies Do not proceed with building a package until all its generated dependencies are in place. List generated files in ghcPrim package, see #117. >--------------------------------------------------------------- 41ecfdc70602aed5335f7205a092c336c090ec90 src/Rules/Data.hs | 5 +++++ src/Rules/Dependencies.hs | 3 --- src/Rules/Generate.hs | 17 ++++++++++------- src/Rules/IntegerGmp.hs | 7 ++++++- 4 files changed, 21 insertions(+), 11 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 42fb2a6..29f8d3d 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -6,6 +6,7 @@ import GHC import Oracles import Predicates (registerPackage) import Rules.Actions +import Rules.Generate import Rules.Resources import Settings import Settings.Builders.Common @@ -19,6 +20,10 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do dataFile = pkgDataFile stage pkg dataFile %> \mk -> do + -- The first thing we do with any package is make sure all generated + -- dependencies are in place before proceeding. + orderOnly $ generatedDependencies stage pkg + -- GhcCabal may run the configure script, so we depend on it -- We don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 5b51c1d..79bcdb2 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -4,7 +4,6 @@ import Base import Expression import Oracles import Rules.Actions -import Rules.Generate import Rules.Resources import Settings import Development.Shake.Util (parseMakefile) @@ -18,13 +17,11 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do let srcFile = dropBuild . dropExtension $ out - orderOnly $ generatedDependencies stage pkg need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - orderOnly $ generatedDependencies stage pkg need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 2b33a53..3eb1231 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -35,13 +35,15 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -integerGmpDependencies :: [FilePath] -integerGmpDependencies = [integerGmpLibraryH] - defaultDependencies :: [FilePath] defaultDependencies = includesDependencies ++ libffiDependencies ++ integerGmpDependencies +ghcPrimDependencies :: Stage -> [FilePath] +ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> + [ "GHC/PrimopWrappers.hs" + , "autogen/GHC/Prim.hs" ] + derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = (derivedConstantsPath -/-) <$> [ "DerivedConstants.h" @@ -72,10 +74,11 @@ compilerDependencies stage = generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage - | pkg == rts = derivedConstantsDependencies - | stage == Stage0 = defaultDependencies - | otherwise = [] + | pkg == compiler = compilerDependencies stage + | pkg == ghcPrim = ghcPrimDependencies stage + | pkg == rts = derivedConstantsDependencies + | stage == Stage0 = defaultDependencies + | otherwise = [] -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index b82dcbb..b796c6c 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,4 +1,6 @@ -module Rules.IntegerGmp (integerGmpRules, integerGmpObjects, integerGmpLibraryH) where +module Rules.IntegerGmp ( + integerGmpRules, integerGmpObjects, integerGmpLibraryH, integerGmpDependencies + ) where import Base import Expression @@ -28,6 +30,9 @@ integerGmpLibraryH = pkgPath integerGmp -/- "include/ghc-gmp.h" integerGmpLibraryFakeH :: FilePath integerGmpLibraryFakeH = integerGmpBase -/- "ghc-gmp.h" +integerGmpDependencies :: [FilePath] +integerGmpDependencies = [integerGmpLibraryH] + -- relative to integerGmpBuild integerGmpPatch :: FilePath integerGmpPatch = ".." -/- "tarball" -/- "gmp-5.0.4.patch" From git at git.haskell.org Thu Oct 26 23:57:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring ChangeModtimeAndDigest back. (dfabde8) Message-ID: <20171026235708.F06A53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfabde88d19471916a86c73a977d6f320f271978/ghc >--------------------------------------------------------------- commit dfabde88d19471916a86c73a977d6f320f271978 Author: Andrey Mokhov Date: Sun Jan 24 17:06:09 2016 +0000 Bring ChangeModtimeAndDigest back. [skip ci] >--------------------------------------------------------------- dfabde88d19471916a86c73a977d6f320f271978 src/Main.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index 0f0d450..69f739b 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -39,6 +39,7 @@ main = shakeArgsWith options CmdLineFlag.flags $ \cmdLineFlags targets -> do , Rules.packageRules , Test.testRules ] options = shakeOptions - { shakeFiles = Base.shakeFilesPath + { shakeChange = ChangeModtimeAndDigest + , shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Thu Oct 26 23:57:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add example UserSettings.hs. (b5bf68d) Message-ID: <20171026235711.CC6763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b5bf68d5ec49bf888321dc7a55e02c772b073de5/ghc >--------------------------------------------------------------- commit b5bf68d5ec49bf888321dc7a55e02c772b073de5 Author: Andrey Mokhov Date: Sun Jun 14 01:18:49 2015 +0100 Add example UserSettings.hs. >--------------------------------------------------------------- b5bf68d5ec49bf888321dc7a55e02c772b073de5 src/UserSettings.hs | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/src/UserSettings.hs b/src/UserSettings.hs new file mode 100644 index 0000000..0a37159 --- /dev/null +++ b/src/UserSettings.hs @@ -0,0 +1,17 @@ +module UserSettings ( + userSettings + ) where + +import Base hiding (arg, args, Args) +import Rules.Data +import Oracles.Builder +import Expression +import Expression.Settings + +userSettings :: Settings +userSettings = mconcat + [ package compiler ? stage Stage0 ? append ["foo", "bar"] + , builder (Ghc Stage0) ? remove ["-O2"] + , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] + ] + From git at git.haskell.org Thu Oct 26 23:57:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Cache $HOME/.ghc as well (9784dfb) Message-ID: <20171026235712.C63F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9784dfb75fdbafb1aa16422eee0bde40ce0ace13/ghc >--------------------------------------------------------------- commit 9784dfb75fdbafb1aa16422eee0bde40ce0ace13 Author: David Luposchainsky Date: Tue Jan 5 16:45:41 2016 +0100 Cache $HOME/.ghc as well >--------------------------------------------------------------- 9784dfb75fdbafb1aa16422eee0bde40ce0ace13 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 68e843c..055edd5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,6 +59,7 @@ script: cache: directories: - $HOME/.cabal + - $HOME/.ghc notifications: irc: From git at git.haskell.org Thu Oct 26 23:57:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build flavours, implement a simple quick flavour. (8738dd2) Message-ID: <20171026235712.C887D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8738dd20c48b8728a353858e771a107a5ca883ad/ghc >--------------------------------------------------------------- commit 8738dd20c48b8728a353858e771a107a5ca883ad Author: Andrey Mokhov Date: Sun Jan 24 22:16:48 2016 +0000 Add build flavours, implement a simple quick flavour. See #188. >--------------------------------------------------------------- 8738dd20c48b8728a353858e771a107a5ca883ad .appveyor.yml | 2 +- src/CmdLineFlag.hs | 80 ++++++++++++++++++++++++++---------------- src/Expression.hs | 2 +- src/Main.hs | 2 +- src/Settings/Args.hs | 13 +++++-- src/Settings/Flavours/Quick.hs | 9 +++++ 6 files changed, 72 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 8738dd20c48b8728a353858e771a107a5ca883ad From git at git.haskell.org Thu Oct 26 23:57:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to difference lists. (5b1c215) Message-ID: <20171026235715.8D2CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8/ghc >--------------------------------------------------------------- commit 5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8 Author: Andrey Mokhov Date: Sun Jun 14 01:19:19 2015 +0100 Switch to difference lists. >--------------------------------------------------------------- 5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8 src/Expression.hs | 73 ++++++++++++++++++++++++++++++++++-------- src/Expression/Settings.hs | 15 +++++---- src/Rules.hs | 15 ++++----- src/Rules/Data.hs | 76 ++++++++++++++++++++----------------------- src/Targets.hs | 80 +++++++++++++++++++--------------------------- 5 files changed, 142 insertions(+), 117 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 5b1c21538cbfa3d1b3a1e4c778072d889f65bbb8 From git at git.haskell.org Thu Oct 26 23:57:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add IRC notifications (2e4f060) Message-ID: <20171026235716.9BCAB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2e4f060ee78c68726cb6434796d208075d4394a7/ghc >--------------------------------------------------------------- commit 2e4f060ee78c68726cb6434796d208075d4394a7 Author: David Luposchainsky Date: Tue Jan 5 16:07:39 2016 +0100 Add IRC notifications >--------------------------------------------------------------- 2e4f060ee78c68726cb6434796d208075d4394a7 .travis.yml | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/.travis.yml b/.travis.yml index 1bcd7fd..68e843c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,3 +59,15 @@ script: cache: directories: - $HOME/.cabal + +notifications: + irc: + on_success: always # always/never/change + on_failure: always + channels: + - "chat.freenode.net#shaking-up-ghc" + template: + - "#%{build_number} finished in %{duration}. %{message}" + - "Repo: %{repository_slug}, branch: %{branch}" + - "%{author}: %{commit_subject}" + - "Build details: %{build_url}" From git at git.haskell.org Thu Oct 26 23:57:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use quick flavour on Travis. (5ed8f3a) Message-ID: <20171026235716.B03683A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ed8f3a48e8e6c401302988547fc10f73c9340c7/ghc >--------------------------------------------------------------- commit 5ed8f3a48e8e6c401302988547fc10f73c9340c7 Author: Andrey Mokhov Date: Sun Jan 24 23:08:16 2016 +0000 Use quick flavour on Travis. See #188. >--------------------------------------------------------------- 5ed8f3a48e8e6c401302988547fc10f73c9340c7 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 1b96c78..84bb380 100644 --- a/.travis.yml +++ b/.travis.yml @@ -64,7 +64,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress $TARGET + - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET cache: directories: From git at git.haskell.org Thu Oct 26 23:57:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add userPackages for overriding default targetPackages. (5d6c2d7) Message-ID: <20171026235719.08CC83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d6c2d7a48d85f2af6f341ee14bc86de400b4779/ghc >--------------------------------------------------------------- commit 5d6c2d7a48d85f2af6f341ee14bc86de400b4779 Author: Andrey Mokhov Date: Sun Jun 14 14:50:48 2015 +0100 Add userPackages for overriding default targetPackages. >--------------------------------------------------------------- 5d6c2d7a48d85f2af6f341ee14bc86de400b4779 src/Expression.hs | 5 ++++- src/Rules.hs | 2 +- src/UserSettings.hs | 9 ++++++--- 3 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index ac72891..77be4e9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -6,7 +6,7 @@ module Expression ( Ways, Packages, Environment (..), defaultEnvironment, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, - interpret, + interpret, interpretDiff, applyPredicate, (?), (??), stage, notStage, builder, notBuilder, package, configKeyValue, configKeyValues, configKeyYes, configKeyNo, configKeyNonEmpty @@ -89,6 +89,9 @@ interpret = flip runReaderT fromDiff :: Monoid a => DiffExpr a -> Expr a fromDiff = fmap (($ mempty) . appEndo) +interpretDiff :: Environment -> Expr a -> Action a +interpretDiff env = interpret env . fromDiff + applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate diff --git a/src/Rules.hs b/src/Rules.hs index 50fa5e1..2873abf 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -18,7 +18,7 @@ generateTargets :: Rules () generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do let env = defaultEnvironment { getStage = stage } - pkgs <- interpret env $ fromDiff targetPackages + pkgs <- interpretDiff env $ targetPackages <> userPackages forM_ pkgs $ \pkg -> do let dir = targetDirectory stage pkg need [pkgPath pkg dir "package-data.mk"] diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 0a37159..1615d60 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -1,5 +1,5 @@ module UserSettings ( - userSettings + userSettings, userPackages ) where import Base hiding (arg, args, Args) @@ -12,6 +12,9 @@ userSettings :: Settings userSettings = mconcat [ package compiler ? stage Stage0 ? append ["foo", "bar"] , builder (Ghc Stage0) ? remove ["-O2"] - , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] - ] + , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] +userPackages :: Settings +userPackages = mconcat + [ stage Stage1 ? remove [cabal] + , remove [compiler] ] From git at git.haskell.org Thu Oct 26 23:57:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #120 from quchen/irc-notifications (31fdc6b) Message-ID: <20171026235720.588D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31fdc6b713e90aa8a2b14ce7157bef811836028d/ghc >--------------------------------------------------------------- commit 31fdc6b713e90aa8a2b14ce7157bef811836028d Merge: 41ecfdc 9784dfb Author: Andrey Mokhov Date: Wed Jan 6 13:10:12 2016 +0000 Merge pull request #120 from quchen/irc-notifications Add IRC notifications >--------------------------------------------------------------- 31fdc6b713e90aa8a2b14ce7157bef811836028d .travis.yml | 13 +++++++++++++ 1 file changed, 13 insertions(+) From git at git.haskell.org Thu Oct 26 23:57:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a new command line flag: build flavour. (5286213) Message-ID: <20171026235720.639AE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/528621354633d9d1af4ae6ed7572c9b727a13460/ghc >--------------------------------------------------------------- commit 528621354633d9d1af4ae6ed7572c9b727a13460 Author: Andrey Mokhov Date: Mon Jan 25 00:19:39 2016 +0000 Add a new command line flag: build flavour. See #188. >--------------------------------------------------------------- 528621354633d9d1af4ae6ed7572c9b727a13460 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index b8fd40f..85b9cbe 100644 --- a/README.md +++ b/README.md @@ -55,6 +55,8 @@ currently supports several others: arguments; also run the `boot` script to create the `configure` script if necessary. You do not have to use this functionality of the new build system; feel free to run `boot` and `configure` scripts manually, as you do when using `make`. +* `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: +`default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). From git at git.haskell.org Thu Oct 26 23:57:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add userPackages for overriding default list of target packages. (f500bd1) Message-ID: <20171026235722.7315C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f500bd171e7d5ca2416876b5477b59fa89e7762e/ghc >--------------------------------------------------------------- commit f500bd171e7d5ca2416876b5477b59fa89e7762e Author: Andrey Mokhov Date: Sun Jun 14 15:02:09 2015 +0100 Add userPackages for overriding default list of target packages. >--------------------------------------------------------------- f500bd171e7d5ca2416876b5477b59fa89e7762e src/Expression.hs | 2 +- src/Rules.hs | 1 + src/Targets.hs | 8 ++++---- src/UserSettings.hs | 4 ++-- 4 files changed, 8 insertions(+), 7 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 77be4e9..ec76244 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -89,7 +89,7 @@ interpret = flip runReaderT fromDiff :: Monoid a => DiffExpr a -> Expr a fromDiff = fmap (($ mempty) . appEndo) -interpretDiff :: Environment -> Expr a -> Action a +interpretDiff :: Monoid a => Environment -> DiffExpr a -> Action a interpretDiff env = interpret env . fromDiff applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a diff --git a/src/Rules.hs b/src/Rules.hs index 2873abf..227eef1 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -10,6 +10,7 @@ import Targets import Settings import Package import Expression +import UserSettings import Rules.Package -- generateTargets needs package-data.mk files of all target packages diff --git a/src/Targets.hs b/src/Targets.hs index 186a321..5929eb8 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -1,10 +1,10 @@ module Targets ( targetWays, targetPackages, targetDirectory, allPackages, customConfigureSettings, - array, base, binPackageDb, binary, bytestring, cabal, containers, deepseq, - directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerLibrary, - parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, - transformers, unix, win32, xhtml + array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, + deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, + integerLibrary, parallel, pretty, primitive, process, stm, templateHaskell, + terminfo, time, transformers, unix, win32, xhtml ) where import Ways hiding (parallel) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 1615d60..b785c7f 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,8 +3,8 @@ module UserSettings ( ) where import Base hiding (arg, args, Args) -import Rules.Data import Oracles.Builder +import Targets import Expression import Expression.Settings @@ -14,7 +14,7 @@ userSettings = mconcat , builder (Ghc Stage0) ? remove ["-O2"] , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] -userPackages :: Settings +userPackages :: Packages userPackages = mconcat [ stage Stage1 ? remove [cabal] , remove [compiler] ] From git at git.haskell.org Thu Oct 26 23:57:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Let's try the stupid --with-gcc fix for os x. (7d55b36) Message-ID: <20171026235724.5F5F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d55b36149cf7f5896d9920c8dbd53ac3a8a787d/ghc >--------------------------------------------------------------- commit 7d55b36149cf7f5896d9920c8dbd53ac3a8a787d Author: Moritz Angermann Date: Wed Jan 6 21:43:38 2016 +0800 Let's try the stupid --with-gcc fix for os x. See #111 >--------------------------------------------------------------- 7d55b36149cf7f5896d9920c8dbd53ac3a8a787d .travis.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 055edd5..e096ddf 100644 --- a/.travis.yml +++ b/.travis.yml @@ -51,7 +51,8 @@ install: - ( cd ghc/shake-build && cabal install --only-dependencies ) - ( cd ghc && ./boot ) - - ( cd ghc && ./configure ) + - if [ $TRAVIS_OS_NAME == osx ]; then ( cd ghc && ./configure --with-gcc="$(which clang)"); fi + - if [ $TRAVIS_OS_NAME == linux ]; then ( cd ghc && ./configure ); fi script: - ./ghc/shake-build/build.sh -j --no-progress From git at git.haskell.org Thu Oct 26 23:57:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't change extension of files found in PATH. (3787444) Message-ID: <20171026235724.74A163A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37874441d3ff2255fea40d60420d4353245ed930/ghc >--------------------------------------------------------------- commit 37874441d3ff2255fea40d60420d4353245ed930 Author: Andrey Mokhov Date: Mon Jan 25 14:04:03 2016 +0000 Don't change extension of files found in PATH. See #194. >--------------------------------------------------------------- 37874441d3ff2255fea40d60420d4353245ed930 src/Builder.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 22723a5..bfb757f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -112,9 +112,9 @@ builderPath builder = case builderProvenance builder of ++ "' in configuration files. Have you forgot to run configure?" windows <- windowsHost case (path, windows) of - ("", _) -> return path - (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) - (p, False) -> lookupInPath (p -<.> exe) + ("", _ ) -> return path + (p , True ) -> fixAbsolutePathOnWindows (p -<.> exe) + (p , False) -> lookupInPath p getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath From git at git.haskell.org Thu Oct 26 23:57:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add userWays and make sure all user-specific settings are used. (a1dd39f) Message-ID: <20171026235725.E04173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1dd39f2b8f32948de4c219a866712dc2eb7884b/ghc >--------------------------------------------------------------- commit a1dd39f2b8f32948de4c219a866712dc2eb7884b Author: Andrey Mokhov Date: Sun Jun 14 15:17:20 2015 +0100 Add userWays and make sure all user-specific settings are used. >--------------------------------------------------------------- a1dd39f2b8f32948de4c219a866712dc2eb7884b src/Rules.hs | 2 +- src/Settings.hs | 6 +++--- src/UserSettings.hs | 23 +++++++++++++++++++---- 3 files changed, 23 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 227eef1..bb68b47 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -31,4 +31,4 @@ packageRules = forM_ [Stage0, Stage1] $ \stage -> do forM_ allPackages $ \pkg -> do let env = defaultEnvironment { getStage = stage, getPackage = pkg } - buildPackage env targetWays buildSettings + buildPackage env (targetWays <> userWays) (settings <> userSettings) diff --git a/src/Settings.hs b/src/Settings.hs index 539ed48..41b31ba 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,7 +1,7 @@ {-# LANGUAGE NoImplicitPrelude, FlexibleInstances #-} module Settings ( - buildSettings + settings ) where import Base hiding (arg, args, Args) @@ -10,8 +10,8 @@ import Oracles.Builder import Expression import Expression.Settings -buildSettings :: Settings -buildSettings = do +settings :: Settings +settings = do stage <- asks getStage mconcat [ builder GhcCabal ? cabalSettings , builder (GhcPkg stage) ? ghcPkgSettings ] diff --git a/src/UserSettings.hs b/src/UserSettings.hs index b785c7f..ccc03f5 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -1,20 +1,35 @@ module UserSettings ( - userSettings, userPackages + userSettings, userPackages, userWays ) where import Base hiding (arg, args, Args) import Oracles.Builder +import Ways import Targets import Expression import Expression.Settings +-- No user-specific settings by default userSettings :: Settings -userSettings = mconcat +userSettings = mempty + +userPackages :: Packages +userPackages = mempty + +userWays :: Ways +userWays = mempty + +-- Examples: +userSettings' :: Settings +userSettings' = mconcat [ package compiler ? stage Stage0 ? append ["foo", "bar"] , builder (Ghc Stage0) ? remove ["-O2"] , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] -userPackages :: Packages -userPackages = mconcat +userPackages' :: Packages +userPackages' = mconcat [ stage Stage1 ? remove [cabal] , remove [compiler] ] + +userWays' :: Ways +userWays' = remove [profiling] From git at git.haskell.org Thu Oct 26 23:57:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #121 from angerman/feature/fix-osx-ci (0fee526) Message-ID: <20171026235728.9271F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0fee526aa68cff1b10d733ba4257fb3435276c66/ghc >--------------------------------------------------------------- commit 0fee526aa68cff1b10d733ba4257fb3435276c66 Merge: 31fdc6b 7d55b36 Author: Andrey Mokhov Date: Wed Jan 6 13:47:24 2016 +0000 Merge pull request #121 from angerman/feature/fix-osx-ci Let's try the stupid --with-gcc fix for os x. >--------------------------------------------------------------- 0fee526aa68cff1b10d733ba4257fb3435276c66 .travis.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:57:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve the clean and rebuild section. (f6355ec) Message-ID: <20171026235728.C8E683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f6355ecd2d3cd047a0b550636dc9cf3f2924f9b2/ghc >--------------------------------------------------------------- commit f6355ecd2d3cd047a0b550636dc9cf3f2924f9b2 Author: Andrey Mokhov Date: Mon Jan 25 15:06:32 2016 +0000 Improve the clean and rebuild section. See #194. [skip ci] >--------------------------------------------------------------- f6355ecd2d3cd047a0b550636dc9cf3f2924f9b2 README.md | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/README.md b/README.md index 85b9cbe..057b864 100644 --- a/README.md +++ b/README.md @@ -69,12 +69,11 @@ The `make`-based build system uses `mk/build.mk` to specify user build settings. use [`src/Settings/User.hs`][user-settings] for the same purpose. Feel free to experiment following the Haddock comments. -#### Resetting the build +#### Clean and full rebuild -To reset the new build system run the build script with `-B` flag. This forces Shake -to rerun all rules, even if results of the previous build are still in the GHC tree. -To remove all build artefacts, run the build script with `clean` target. Note, we are -working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `shake-build/build.sh clean` removes all build artefacts. Note, we are working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. + +* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. Current limitations ------------------- From git at git.haskell.org Thu Oct 26 23:57:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix ordering of appends. (95b6614) Message-ID: <20171026235729.973663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95b6614a659907ec33afce9bca396a7f7d20a498/ghc >--------------------------------------------------------------- commit 95b6614a659907ec33afce9bca396a7f7d20a498 Author: Andrey Mokhov Date: Sun Jun 14 15:39:21 2015 +0100 Fix ordering of appends. >--------------------------------------------------------------- 95b6614a659907ec33afce9bca396a7f7d20a498 src/Expression.hs | 2 +- src/Rules/Data.hs | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index ec76244..8ae285d 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -45,7 +45,7 @@ instance Monoid a => Monoid (Expr a) where mappend = liftM2 mappend append :: Monoid a => a -> DiffExpr a -append x = return $ Endo (<> x) +append = return . Endo . mappend appendM :: Monoid a => Action a -> DiffExpr a appendM mx = lift mx >>= append diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index c8cb354..4c7e5de 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -148,9 +148,9 @@ buildPackageData env ways settings = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" - need [pkgPath pkg pkgCabal pkg] -- GhcCabal will run the configure script, so we depend on it - -- We still don't know who build the configure script from configure.ac + need [pkgPath pkg pkgCabal pkg] + -- We still don't know who built the configure script from configure.ac when (doesFileExist $ configure <.> "ac") $ need [configure] run' env GhcCabal settings -- TODO: when (registerPackage settings) $ From git at git.haskell.org Thu Oct 26 23:57:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Lookup builder in PATH if they are given without path. (4478851) Message-ID: <20171026235732.053CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44788518cb14c59788fdf320b9ca2d11e11509ca/ghc >--------------------------------------------------------------- commit 44788518cb14c59788fdf320b9ca2d11e11509ca Author: Moritz Angermann Date: Wed Jan 6 23:22:43 2016 +0800 Lookup builder in PATH if they are given without path. `system-gcc` may be given without path (e.g. `clang`), this patch adds lookup using `which` for those commands. Also drops calling `fixAbsolutePathOnWindows` on non window hosts. Fixes #26 >--------------------------------------------------------------- 44788518cb14c59788fdf320b9ca2d11e11509ca src/Builder.hs | 4 +++- src/Oracles/WindowsRoot.hs | 11 ++++++++++- 2 files changed, 13 insertions(+), 2 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 5ed9e1d..6e4dba5 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -94,7 +94,9 @@ builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ putError $ "\nCannot find path to '" ++ (builderKey builder) ++ "' in configuration files." - fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe + windows <- windowsHost + let path' = if null path then "" else path -<.> exe in + (if windows then fixAbsolutePathOnWindows else lookupInPath) path' getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 413f289..195f591 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.WindowsRoot ( - windowsRoot, fixAbsolutePathOnWindows, topDirectory, windowsRootOracle + windowsRoot, fixAbsolutePathOnWindows, lookupInPath, topDirectory, windowsRootOracle ) where import Data.Char (isSpace) @@ -38,6 +38,15 @@ fixAbsolutePathOnWindows path = do else return path +-- | Lookup a @command@ in @PATH@ environment. +lookupInPath :: FilePath -> Action FilePath +lookupInPath command + | command /= takeFileName command = return command + | otherwise = do + Stdout out <- quietly $ cmd ["which", command] + let path = dropWhileEnd isSpace out + return path + -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). windowsRootOracle :: Rules () From git at git.haskell.org Thu Oct 26 23:57:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note about interaction of the new and existing build systems. (92a3ffb) Message-ID: <20171026235732.625DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92a3ffba8b0f61ed772f942c16a3ca1a0495f1d8/ghc >--------------------------------------------------------------- commit 92a3ffba8b0f61ed772f942c16a3ca1a0495f1d8 Author: Andrey Mokhov Date: Tue Jan 26 20:02:05 2016 +0000 Add a note about interaction of the new and existing build systems. [skip ci] >--------------------------------------------------------------- 92a3ffba8b0f61ed772f942c16a3ca1a0495f1d8 README.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README.md b/README.md index 057b864..18ba8f6 100644 --- a/README.md +++ b/README.md @@ -9,6 +9,10 @@ on [Shake][shake] and we hope that it will eventually replace the current ideas behind the project you can find more details on the [wiki page][ghc-shake-wiki] and in this [blog post][blog-post-1]. +The new build system can work side-by-side with the existing build system. Note, there is +some interaction between them: they put (some) build results in the same directories, +e.g. `inplace/bin/ghc-stage1`. + [Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc). Your first build From git at git.haskell.org Thu Oct 26 23:57:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove redundant argument to build rules. (3461e46) Message-ID: <20171026235733.3651D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3461e46ca8f34eebe63f32a5dc76a6afdcb6f294/ghc >--------------------------------------------------------------- commit 3461e46ca8f34eebe63f32a5dc76a6afdcb6f294 Author: Andrey Mokhov Date: Sun Jun 14 16:03:07 2015 +0100 Remove redundant argument to build rules. >--------------------------------------------------------------- 3461e46ca8f34eebe63f32a5dc76a6afdcb6f294 src/Rules.hs | 5 +- src/Rules/Data.hs | 132 +++------------------------------------------- src/Rules/Package.hs | 3 +- src/Settings.hs | 144 +++++++++++++++++++++++++++++++++++++++++++++++++-- src/Targets.hs | 3 +- 5 files changed, 151 insertions(+), 136 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3461e46ca8f34eebe63f32a5dc76a6afdcb6f294 From git at git.haskell.org Thu Oct 26 23:57:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Updates travis and README to reflect fixing #26 (f3a1eb7) Message-ID: <20171026235735.6E7683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f3a1eb726e550d458476764d99ad68fe042de81b/ghc >--------------------------------------------------------------- commit f3a1eb726e550d458476764d99ad68fe042de81b Author: Moritz Angermann Date: Wed Jan 6 23:24:22 2016 +0800 Updates travis and README to reflect fixing #26 >--------------------------------------------------------------- f3a1eb726e550d458476764d99ad68fe042de81b .travis.yml | 3 +-- README.md | 3 --- 2 files changed, 1 insertion(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index e096ddf..055edd5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -51,8 +51,7 @@ install: - ( cd ghc/shake-build && cabal install --only-dependencies ) - ( cd ghc && ./boot ) - - if [ $TRAVIS_OS_NAME == osx ]; then ( cd ghc && ./configure --with-gcc="$(which clang)"); fi - - if [ $TRAVIS_OS_NAME == linux ]; then ( cd ghc && ./configure ); fi + - ( cd ghc && ./configure ) script: - ./ghc/shake-build/build.sh -j --no-progress diff --git a/README.md b/README.md index 90f6422..45789e3 100644 --- a/README.md +++ b/README.md @@ -31,9 +31,6 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure -# or if you want to use clang (e.g. building on OS X) -./configure --with-gcc=$(which clang) # See #26 - ``` Now you have a couple of options: From git at git.haskell.org Thu Oct 26 23:57:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Test to Selftest. (b06bae8) Message-ID: <20171026235735.D2B973A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b06bae88a40b7ee645b0aecda8019a601d567dce/ghc >--------------------------------------------------------------- commit b06bae88a40b7ee645b0aecda8019a601d567dce Author: Andrey Mokhov Date: Wed Jan 27 23:29:51 2016 +0000 Rename Test to Selftest. >--------------------------------------------------------------- b06bae88a40b7ee645b0aecda8019a601d567dce shaking-up-ghc.cabal | 2 +- src/Main.hs | 4 ++-- src/{Test.hs => Selftest.hs} | 6 +++--- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 674d6f0..60f3c34 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -65,6 +65,7 @@ executable ghc-shake , Rules.Resources , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg + , Selftest , Settings , Settings.Args , Settings.Builders.Alex @@ -104,7 +105,6 @@ executable ghc-shake , Settings.Ways , Stage , Target - , Test , Way default-language: Haskell2010 diff --git a/src/Main.hs b/src/Main.hs index 12ec014..befb6e7 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -14,7 +14,7 @@ import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl -import qualified Test +import qualified Selftest main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -37,7 +37,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do , Rules.Perl.perlScriptRules , Rules.generateTargets , Rules.packageRules - , Test.testRules ] + , Selftest.selftestRules ] options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Test.hs b/src/Selftest.hs similarity index 89% rename from src/Test.hs rename to src/Selftest.hs index 3c88ed4..4800ca8 100644 --- a/src/Test.hs +++ b/src/Selftest.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -module Test (testRules) where +module Selftest (selftestRules) where import Development.Shake import Settings.Builders.Ar (chunksOfSize) @@ -13,8 +13,8 @@ instance Arbitrary Way where instance Arbitrary WayUnit where arbitrary = arbitraryBoundedEnum -testRules :: Rules () -testRules = +selftestRules :: Rules () +selftestRules = "selftest" ~> do test $ \(x :: Way) -> read (show x) == x test $ \n xs -> From git at git.haskell.org Thu Oct 26 23:57:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor folder structure. (2f70955) Message-ID: <20171026235736.C30D73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f70955b45d2c0e4dad2fd8a606caca094bd7c5c/ghc >--------------------------------------------------------------- commit 2f70955b45d2c0e4dad2fd8a606caca094bd7c5c Author: Andrey Mokhov Date: Sun Jun 14 16:10:48 2015 +0100 Refactor folder structure. >--------------------------------------------------------------- 2f70955b45d2c0e4dad2fd8a606caca094bd7c5c src/Expression.hs | 8 +++++--- src/Settings.hs | 2 +- src/{Expression/Settings.hs => Settings/Util.hs} | 6 +----- src/Targets.hs | 1 - src/UserSettings.hs | 1 - 5 files changed, 7 insertions(+), 11 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 8ae285d..7adbce0 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -3,7 +3,7 @@ module Expression ( module Control.Monad.Reader, Expr, DiffExpr, fromDiff, Predicate, - Ways, Packages, + Settings, Ways, Packages, Environment (..), defaultEnvironment, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, interpret, interpretDiff, @@ -37,8 +37,10 @@ type Expr a = ReaderT Environment Action a type DiffExpr a = Expr (Endo a) type Predicate = Expr Bool -type Ways = DiffExpr [Way] -type Packages = DiffExpr [Package] + +type Settings = DiffExpr [String] +type Ways = DiffExpr [Way] +type Packages = DiffExpr [Package] instance Monoid a => Monoid (Expr a) where mempty = return mempty diff --git a/src/Settings.hs b/src/Settings.hs index ebafbc2..95b88b5 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -14,9 +14,9 @@ import Targets import Package import Switches import Oracles.Base +import Settings.Util import UserSettings import Expression hiding (when, liftIO) -import Expression.Settings settings :: Settings settings = defaultSettings <> userSettings diff --git a/src/Expression/Settings.hs b/src/Settings/Util.hs similarity index 97% rename from src/Expression/Settings.hs rename to src/Settings/Util.hs index 5bc185b..dbd07c0 100644 --- a/src/Expression/Settings.hs +++ b/src/Settings/Util.hs @@ -1,8 +1,6 @@ {-# LANGUAGE NoImplicitPrelude #-} -module Expression.Settings ( - Settings, - +module Settings.Util ( -- Primitive settings elements arg, argM, args, argConfig, argStagedConfig, argConfigList, argStagedConfigList, @@ -18,8 +16,6 @@ import Base hiding (Args, arg, args) import Oracles hiding (not) import Expression -type Settings = DiffExpr [String] - -- A single argument arg :: String -> Settings arg = append . return diff --git a/src/Targets.hs b/src/Targets.hs index b2b52d3..4d3c613 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -13,7 +13,6 @@ import Base hiding (arg, args, Args, TargetDir) import Package import Switches import Expression -import Expression.Settings -- These are the packages we build targetPackages :: Packages diff --git a/src/UserSettings.hs b/src/UserSettings.hs index ccc03f5..4928661 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -7,7 +7,6 @@ import Oracles.Builder import Ways import Targets import Expression -import Expression.Settings -- No user-specific settings by default userSettings :: Settings From git at git.haskell.org Thu Oct 26 23:57:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a test appveyor script, see #110. (290e990) Message-ID: <20171026235739.13E7A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/290e990dd8500de9728d83506a0bacd143619def/ghc >--------------------------------------------------------------- commit 290e990dd8500de9728d83506a0bacd143619def Author: Andrey Mokhov Date: Wed Jan 6 17:48:41 2016 +0000 Add a test appveyor script, see #110. >--------------------------------------------------------------- 290e990dd8500de9728d83506a0bacd143619def .appveyor.yml | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/.appveyor.yml b/.appveyor.yml new file mode 100644 index 0000000..25df24b --- /dev/null +++ b/.appveyor.yml @@ -0,0 +1,8 @@ +install: + - set PATH=C:\msys64\usr\bin;%PATH% + - bash "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" + +build_script: + - echo "test" + +test: off From git at git.haskell.org Thu Oct 26 23:57:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add basic validation support (GHC tests). (e9abc61) Message-ID: <20171026235739.8ADC93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101/ghc >--------------------------------------------------------------- commit e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101 Author: Andrey Mokhov Date: Thu Jan 28 02:51:12 2016 +0000 Add basic validation support (GHC tests). See #187. >--------------------------------------------------------------- e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101 shaking-up-ghc.cabal | 1 + src/Main.hs | 4 +++- src/Test.hs | 63 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 67 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 60f3c34..f00c7c6 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -105,6 +105,7 @@ executable ghc-shake , Settings.Ways , Stage , Target + , Test , Way default-language: Haskell2010 diff --git a/src/Main.hs b/src/Main.hs index befb6e7..2c944d4 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -15,6 +15,7 @@ import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl import qualified Selftest +import qualified Test main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -37,7 +38,8 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do , Rules.Perl.perlScriptRules , Rules.generateTargets , Rules.packageRules - , Selftest.selftestRules ] + , Selftest.selftestRules + , Test.testRules ] options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Test.hs b/src/Test.hs new file mode 100644 index 0000000..547e286 --- /dev/null +++ b/src/Test.hs @@ -0,0 +1,63 @@ +module Test (testRules) where + +import Base +import Builder +import Expression +import GHC (rts, libffi) +import Oracles.Config.Flag +import Oracles.Config.Setting +import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory +import Settings.Packages +import Settings.User + +-- TODO: clean up after testing +testRules :: Rules () +testRules = + "test" ~> do + let quote s = "\"" ++ s ++ "\"" + yesNo x = quote $ if x then "YES" else "NO" + pkgs <- interpretWithStage Stage1 getPackages + tests <- filterM doesDirectoryExist $ concat + [ [ pkgPath pkg -/- "tests", pkgPath pkg -/- "tests-ghc" ] + | pkg <- pkgs, isLibrary pkg, pkg /= rts, pkg /= libffi ] + windows <- windowsHost + top <- topDirectory + compiler <- builderPath $ Ghc Stage2 + ghcPkg <- builderPath $ GhcPkg Stage1 + haddock <- builderPath Haddock + threads <- shakeThreads <$> getShakeOptions + ghcWithNativeCodeGenInt <- fromEnum <$> ghcWithNativeCodeGen + ghcWithInterpreterInt <- fromEnum <$> ghcWithInterpreter + ghcUnregisterisedInt <- fromEnum <$> flag GhcUnregisterised + quietly . cmd "python2" $ + [ "testsuite/driver/runtests.py" ] + ++ map ("--rootdir="++) tests ++ + [ "-e", "windows=" ++ show windows + , "-e", "config.speed=2" + , "-e", "ghc_compiler_always_flags=" ++ quote "-fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts" + , "-e", "ghc_with_native_codegen=" ++ show ghcWithNativeCodeGenInt + , "-e", "ghc_debugged=" ++ yesNo ghcDebugged + , "-e", "ghc_with_vanilla=1" -- TODO: do we always build vanilla? + , "-e", "ghc_with_dynamic=0" -- TODO: support dynamic + , "-e", "ghc_with_profiling=0" -- TODO: support profiling + , "-e", "ghc_with_interpreter=" ++ show ghcWithInterpreterInt + , "-e", "ghc_unregisterised=" ++ show ghcUnregisterisedInt + , "-e", "ghc_with_threaded_rts=0" -- TODO: support threaded + , "-e", "ghc_with_dynamic_rts=0" -- TODO: support dynamic + , "-e", "ghc_dynamic_by_default=False" -- TODO: support dynamic + , "-e", "ghc_dynamic=0" -- TODO: support dynamic + , "-e", "ghc_with_llvm=0" -- TODO: support LLVM + , "-e", "in_tree_compiler=True" -- TODO: when is it equal to False? + , "-e", "clean_only=False" -- TODO: do we need to support True? + , "--configfile=testsuite/config/ghc" + , "--config", "compiler=" ++ quote (top -/- compiler) + , "--config", "ghc_pkg=" ++ quote (top -/- ghcPkg) + , "--config", "haddock=" ++ quote (top -/- haddock) + , "--summary-file", "testsuite_summary.txt" + , "--threads=" ++ show threads + ] + + -- , "--config", "hp2ps=" ++ quote ("hp2ps") + -- , "--config", "hpc=" ++ quote ("hpc") + -- , "--config", "gs=$(call quote_path,$(GS))" + -- , "--config", "timeout_prog=$(call quote_path,$(TIMEOUT_PROGRAM))" From git at git.haskell.org Thu Oct 26 23:57:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split Targets.hs and Settings.hs into multiple logically separate files. (062952c) Message-ID: <20171026235740.7FEBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/062952ca22b4c06d96cc0ad601ae3437ea6883dc/ghc >--------------------------------------------------------------- commit 062952ca22b4c06d96cc0ad601ae3437ea6883dc Author: Andrey Mokhov Date: Sun Jun 14 18:03:20 2015 +0100 Split Targets.hs and Settings.hs into multiple logically separate files. >--------------------------------------------------------------- 062952ca22b4c06d96cc0ad601ae3437ea6883dc src/Expression.hs | 2 + src/Rules.hs | 4 +- src/Rules/Data.hs | 2 + src/Settings.hs | 140 +----------------------------- src/{Settings.hs => Settings/GhcCabal.hs} | 89 +++++++------------ src/Settings/GhcPkg.hs | 20 +++++ src/Settings/Packages.hs | 33 +++++++ src/Settings/Ways.hs | 20 +++++ src/Targets.hs | 45 +++------- 9 files changed, 124 insertions(+), 231 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 062952ca22b4c06d96cc0ad601ae3437ea6883dc From git at git.haskell.org Thu Oct 26 23:57:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix test script, see #110. (8bf936f) Message-ID: <20171026235743.43DAE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8bf936f4942a51bbfbd4c561a1dbfb89300bcdff/ghc >--------------------------------------------------------------- commit 8bf936f4942a51bbfbd4c561a1dbfb89300bcdff Author: Andrey Mokhov Date: Wed Jan 6 18:11:05 2016 +0000 Fix test script, see #110. >--------------------------------------------------------------- 8bf936f4942a51bbfbd4c561a1dbfb89300bcdff .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 25df24b..b5faf11 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,6 +1,7 @@ install: - - set PATH=C:\msys64\usr\bin;%PATH% - - bash "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" + - set MSYSTEM=MINGW64 + - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% + - bash -lc "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" build_script: - echo "test" From git at git.haskell.org Thu Oct 26 23:57:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move derived predicates around. (2bd0715) Message-ID: <20171026235744.5399D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2bd0715aa24e153e43707deaa6ef8ca6386105ab/ghc >--------------------------------------------------------------- commit 2bd0715aa24e153e43707deaa6ef8ca6386105ab Author: Andrey Mokhov Date: Sun Jun 14 19:44:05 2015 +0100 Move derived predicates around. >--------------------------------------------------------------- 2bd0715aa24e153e43707deaa6ef8ca6386105ab src/Expression.hs | 8 +------- src/Settings/GhcCabal.hs | 13 +++++++------ src/Settings/GhcPkg.hs | 7 ++++--- src/Settings/Packages.hs | 4 ++-- src/Switches.hs | 27 +++++++++++++++++++-------- src/Targets.hs | 4 +++- src/UserSettings.hs | 20 +++++++++++++++----- 7 files changed, 51 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2bd0715aa24e153e43707deaa6ef8ca6386105ab From git at git.haskell.org Thu Oct 26 23:57:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add testing section (eee29dc) Message-ID: <20171026235743.906BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eee29dc165adceebda020444214e28d0d7456860/ghc >--------------------------------------------------------------- commit eee29dc165adceebda020444214e28d0d7456860 Author: Andrey Mokhov Date: Thu Jan 28 02:51:52 2016 +0000 Add testing section [skip ci] >--------------------------------------------------------------- eee29dc165adceebda020444214e28d0d7456860 README.md | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 18ba8f6..56e13ad 100644 --- a/README.md +++ b/README.md @@ -75,9 +75,19 @@ experiment following the Haddock comments. #### Clean and full rebuild -* `shake-build/build.sh clean` removes all build artefacts. Note, we are working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `shake-build/build.sh clean` removes all build artefacts. Note, we are working +towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. -* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. +* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of +the previous build are still in the GHC tree. + +#### Testing + +* `shake-build/build.sh test` runs GHC tests. The current implementation is very +limited and cannot replace the `validate` script (see [#187][validation-issue]). + +* `shake-build/build.sh selftest` runs tests of the build system. Current test +coverage is close to zero (see [#197][test-issue]). Current limitations ------------------- @@ -120,6 +130,7 @@ helped me endure and enjoy the project. [build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs +[test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 [profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 From git at git.haskell.org Thu Oct 26 23:57:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install prerequisites for Windows build. (584fd8a) Message-ID: <20171026235746.EE67A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/584fd8a9811592d04c7c1d43c37778410b8d6590/ghc >--------------------------------------------------------------- commit 584fd8a9811592d04c7c1d43c37778410b8d6590 Author: Andrey Mokhov Date: Wed Jan 6 18:19:24 2016 +0000 Install prerequisites for Windows build. See #110. [skip ci] >--------------------------------------------------------------- 584fd8a9811592d04c7c1d43c37778410b8d6590 .appveyor.yml | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index b5faf11..2b710e0 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,7 +1,11 @@ install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - bash -lc "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" + - bash -lc "pacman -S --noconfirm git binutils p7zip gcc mingw-w64-$(uname -m)-python3-sphinx" + - bash -lc "curl -L http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" + - bash -lc "curl -L https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + - bash -lc "cabal update" + - bash -lc "cabal install -j --prefix=/usr/local alex happy" build_script: - echo "test" From git at git.haskell.org Thu Oct 26 23:57:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use libHS*_thr.a instead of libHS*.thr_a naming convention for libraries. (c760627) Message-ID: <20171026235747.05C333A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7606279a186f145d5e7751f65be8c2be8aefb80/ghc >--------------------------------------------------------------- commit c7606279a186f145d5e7751f65be8c2be8aefb80 Author: Andrey Mokhov Date: Fri Jan 29 01:05:48 2016 +0000 Use libHS*_thr.a instead of libHS*.thr_a naming convention for libraries. See #98. >--------------------------------------------------------------- c7606279a186f145d5e7751f65be8c2be8aefb80 src/Rules/Library.hs | 2 +- src/Settings/Paths.hs | 2 +- src/Way.hs | 14 ++++++++------ 3 files changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b53c472..2cde962 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -46,7 +46,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do let objs = cObjs ++ splitObjs ++ eObjs asuf <- libsuf way - let isLib0 = ("//*-0" <.> asuf) ?== a + let isLib0 = ("//*-0" ++ asuf) ?== a if isLib0 then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls else build $ fullTarget target Ar objs [a] diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index ed217a8..a152f9a 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -29,7 +29,7 @@ pkgLibraryFile :: Stage -> Package -> String -> Way -> Action FilePath pkgLibraryFile stage pkg componentId way = do extension <- libsuf way let buildPath = targetPath stage pkg -/- "build" - return $ buildPath -/- "libHS" ++ componentId <.> extension + return $ buildPath -/- "libHS" ++ componentId ++ extension -- Relative path to a package ghci library file, e.g.: -- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" diff --git a/src/Way.hs b/src/Way.hs index 8923571..da986a8 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -127,6 +127,10 @@ wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" +waySuffix :: Way -> String +waySuffix way | way == vanilla = "" + | otherwise = "_" ++ show way + osuf, ssuf, hisuf, hcsuf, obootsuf, hibootsuf :: Way -> String osuf = (++ "o" ) . wayPrefix ssuf = (++ "s" ) . wayPrefix @@ -135,10 +139,6 @@ hcsuf = (++ "hc" ) . wayPrefix obootsuf = (++ "o-boot" ) . wayPrefix hibootsuf = (++ "hi-boot") . wayPrefix --- Note: in the previous build system libsuf was mysteriously different --- from other suffixes. For example, in the profiling way it used to be --- "_p.a" instead of ".p_a" which is how other suffixes work. I decided --- to make all suffixes consistent: ".way_extension". -- TODO: find out why we need version number in the dynamic suffix -- The current theory: dynamic libraries are eventually placed in a single -- giant directory in the load path of the dynamic linker, and hence we must @@ -148,7 +148,7 @@ hibootsuf = (++ "hi-boot") . wayPrefix libsuf :: Way -> Action String libsuf way @ (Way set) = if (not . wayUnit Dynamic $ way) - then return $ wayPrefix way ++ "a" -- e.g., p_a + then return $ waySuffix way ++ ".a" -- e.g., _p.a else do extension <- setting DynamicExtension -- e.g., .dll or .so version <- setting ProjectVersion -- e.g., 7.11.20141222 @@ -172,7 +172,9 @@ safeDetectWay file = case reads prefix of then extension else takeExtension . dropExtension . dropExtension . dropExtension $ file - prefix = drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed + prefix = if extension == "a" + then drop 1 . dropWhile (/= '_') $ takeBaseName file + else drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed -- Unsafe version of safeDetectWay. Useful when matchBuildResult has succeeded. detectWay :: FilePath -> Way From git at git.haskell.org Thu Oct 26 23:57:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix argument ordering issues in DiffExpr. (b67db18) Message-ID: <20171026235747.D11A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b67db18e8f9745bd25045f0e09f64cbb5c5b09b5/ghc >--------------------------------------------------------------- commit b67db18e8f9745bd25045f0e09f64cbb5c5b09b5 Author: Andrey Mokhov Date: Sun Jun 14 20:33:13 2015 +0100 Fix argument ordering issues in DiffExpr. >--------------------------------------------------------------- b67db18e8f9745bd25045f0e09f64cbb5c5b09b5 src/Expression.hs | 29 +++++++++++++++-------------- 1 file changed, 15 insertions(+), 14 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index a37bf7c..d147280 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -36,7 +36,7 @@ defaultEnvironment = Environment } type Expr a = ReaderT Environment Action a -type DiffExpr a = Expr (Endo a) +type DiffExpr a = Expr (Dual (Endo a)) type Predicate = Expr Bool @@ -49,49 +49,50 @@ instance Monoid a => Monoid (Expr a) where mappend = liftM2 mappend append :: Monoid a => a -> DiffExpr a -append = return . Endo . mappend +append x = return . Dual . Endo $ (<> x) appendM :: Monoid a => Action a -> DiffExpr a appendM mx = lift mx >>= append remove :: Eq a => [a] -> DiffExpr [a] -remove xs = return . Endo $ filter (`notElem` xs) +remove xs = return . Dual . Endo $ filter (`notElem` xs) -- appendSub appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument -- of the form 'prefix=listOfSubarguments' is appended to the expression. -- Note: nothing is done if the list of sub-arguments is empty. -appendSub :: String -> [String] -> DiffExpr [String] +appendSub :: String -> [String] -> Settings appendSub prefix xs - | xs == [] = mempty - | otherwise = return $ Endo (go False) + | xs' == [] = mempty + | otherwise = return . Dual . Endo $ go False where + xs' = filter (/= "") xs go True [] = [] - go False [] = [prefix ++ "=" ++ unwords xs] + go False [] = [prefix ++ "=" ++ unwords xs'] go found (y:ys) = if prefix `isPrefixOf` y - then unwords (y : xs) : go True ys - else go found ys + then unwords (y : xs') : go True ys + else y : go found ys -- appendSubD is similar to appendSub but it extracts the list of sub-arguments -- from the given DiffExpr. -appendSubD :: String -> DiffExpr [String] -> DiffExpr [String] +appendSubD :: String -> Settings -> Settings appendSubD prefix diffExpr = fromDiff diffExpr >>= appendSub prefix -filterSub :: String -> (String -> Bool) -> DiffExpr [String] -filterSub prefix p = return . Endo $ map filterSubstr +filterSub :: String -> (String -> Bool) -> Settings +filterSub prefix p = return . Dual . Endo $ map filterSubstr where filterSubstr s | prefix `isPrefixOf` s = unwords . filter p . words $ s | otherwise = s -removeSub :: String -> [String] -> DiffExpr [String] +removeSub :: String -> [String] -> Settings removeSub prefix xs = filterSub prefix (`notElem` xs) interpret :: Environment -> Expr a -> Action a interpret = flip runReaderT fromDiff :: Monoid a => DiffExpr a -> Expr a -fromDiff = fmap (($ mempty) . appEndo) +fromDiff = fmap (($ mempty) . appEndo . getDual) interpretDiff :: Monoid a => Environment -> DiffExpr a -> Action a interpretDiff env = interpret env . fromDiff From git at git.haskell.org Thu Oct 26 23:57:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a rule to build gmpLibraryInTreeH. (3b0fdab) Message-ID: <20171026235751.786EC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b0fdab49988b9f1981e238c903a08fd75419cc3/ghc >--------------------------------------------------------------- commit 3b0fdab49988b9f1981e238c903a08fd75419cc3 Author: Andrey Mokhov Date: Fri Jan 29 01:06:24 2016 +0000 Add a rule to build gmpLibraryInTreeH. >--------------------------------------------------------------- 3b0fdab49988b9f1981e238c903a08fd75419cc3 src/Rules/Gmp.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index b384b68..ab25495 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -144,3 +144,5 @@ gmpRules = do runBuilder Ranlib [gmpLibrary] putSuccess "| Successfully built custom library 'gmp'" + + gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] From git at git.haskell.org Thu Oct 26 23:57:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create /usr/local/bin, silence curl. (1731a15) Message-ID: <20171026235751.965883A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1731a15422f2be3eb09b612426900801ea3b294f/ghc >--------------------------------------------------------------- commit 1731a15422f2be3eb09b612426900801ea3b294f Author: Andrey Mokhov Date: Wed Jan 6 18:33:03 2016 +0000 Create /usr/local/bin, silence curl. See #110. [skip ci] >--------------------------------------------------------------- 1731a15422f2be3eb09b612426900801ea3b294f .appveyor.yml | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 2b710e0..f8ce40a 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -2,8 +2,10 @@ install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc mingw-w64-$(uname -m)-python3-sphinx" - - bash -lc "curl -L http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "curl -L https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" + - bash -lc "mkdir /usr/local" + - bash -lc "mkdir /usr/local/bin" + - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" From git at git.haskell.org Thu Oct 26 23:57:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor settings predicates. (463094d) Message-ID: <20171026235751.C08103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/463094da9933beec44729dd96ea47430a4e9f2a0/ghc >--------------------------------------------------------------- commit 463094da9933beec44729dd96ea47430a4e9f2a0 Author: Andrey Mokhov Date: Mon Jun 15 00:44:08 2015 +0100 Refactor settings predicates. >--------------------------------------------------------------- 463094da9933beec44729dd96ea47430a4e9f2a0 cfg/default.config.in | 1 - src/Settings.hs | 10 +++++----- src/Settings/GhcCabal.hs | 26 ++++++++++++++------------ src/Settings/GhcPkg.hs | 10 ++++++---- src/Targets.hs | 17 ++++++++--------- 5 files changed, 33 insertions(+), 31 deletions(-) diff --git a/cfg/default.config.in b/cfg/default.config.in index 2e65688..f31af13 100644 --- a/cfg/default.config.in +++ b/cfg/default.config.in @@ -38,7 +38,6 @@ supports-package-key = @SUPPORTS_PACKAGE_KEY@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ -validating = NO ghc-source-path = @hardtop@ # Information about host and target systems: diff --git a/src/Settings.hs b/src/Settings.hs index a9f5cce..cde678e 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,8 +2,8 @@ module Settings ( settings ) where +import Targets import Base hiding (arg, args) -import Oracles.Builder import Settings.GhcPkg import Settings.GhcCabal import UserSettings @@ -13,7 +13,7 @@ settings :: Settings settings = defaultSettings <> userSettings defaultSettings :: Settings -defaultSettings = do - stage <- asks getStage - mconcat [ builder GhcCabal ? cabalSettings - , builder (GhcPkg stage) ? ghcPkgSettings ] +defaultSettings = mconcat + [ cabalSettings + , ghcPkgSettings + , customPackageSettings ] diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index d0f6512..db972ac 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -17,7 +17,7 @@ import Settings.Packages import UserSettings cabalSettings :: Settings -cabalSettings = do +cabalSettings = builder GhcCabal ? do stage <- asks getStage pkg <- asks getPackage mconcat [ arg "configure" @@ -26,7 +26,6 @@ cabalSettings = do , dllSettings , with' $ Ghc stage , with' $ GhcPkg stage - , customConfigureSettings , stage0 ? bootPackageDbSettings , librarySettings , configKeyNonEmpty "hscolour" ? with' HsColour -- TODO: generalise? @@ -59,14 +58,18 @@ librarySettings = do configureSettings :: Settings configureSettings = do - let conf key = appendSubD $ "--configure-option=" ++ key - ccSettings' = ccSettings <> remove ["-Werror"] + let conf key = appendSubD $ "--configure-option=" ++ key + cFlags = mconcat [ ccSettings + , remove ["-Werror"] + , argStagedConfig "conf-cc-args" ] + ldFlags = ldSettings <> argStagedConfig "conf-gcc-linker-args" + cppFlags = cppSettings <> argStagedConfig "conf-cpp-args" stage <- asks getStage mconcat - [ conf "CFLAGS" ccSettings' - , conf "LDFLAGS" ldSettings - , conf "CPPFLAGS" cppSettings - , appendSubD "--gcc-options" $ ccSettings' <> ldSettings + [ conf "CFLAGS" cFlags + , conf "LDFLAGS" ldFlags + , conf "CPPFLAGS" cppFlags + , appendSubD "--gcc-options" $ cFlags <> ldFlags , conf "--with-iconv-includes" $ argConfig "iconv-include-dirs" , conf "--with-iconv-libraries" $ argConfig "iconv-lib-dirs" , conf "--with-gmp-includes" $ argConfig "gmp-include-dirs" @@ -106,9 +109,8 @@ ccSettings = do let gccGe46 = liftM not gccLt46 mconcat [ package integerLibrary ? arg "-Ilibraries/integer-gmp2/gmp" - , builder GhcCabal ? argStagedConfig "conf-cc-args" , validating ? mconcat - [ notBuilder GhcCabal ? arg "-Werror" + [ arg "-Werror" , arg "-Wall" , gccIsClang ?? ( arg "-Wno-unknown-pragmas" <> @@ -117,7 +119,7 @@ ccSettings = do ] ldSettings :: Settings -ldSettings = builder GhcCabal ? argStagedConfig "conf-gcc-linker-args" +ldSettings = mempty cppSettings :: Settings -cppSettings = builder GhcCabal ? argStagedConfig "conf-cpp-args" +cppSettings = mempty diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index b3ba6f9..0e17b02 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -8,6 +8,7 @@ import Targets import Switches import Expression hiding (when, liftIO) import Settings.Util +import Oracles.Builder import Settings.GhcCabal ghcPkgSettings :: Settings @@ -15,7 +16,8 @@ ghcPkgSettings = do pkg <- asks getPackage stage <- asks getStage let dir = pkgPath pkg targetDirectory stage pkg - mconcat [ arg "update" - , arg "--force" - , stage0 ? bootPackageDbSettings - , arg $ dir "inplace-pkg-config" ] + builder (GhcPkg stage) ? mconcat + [ arg "update" + , arg "--force" + , stage0 ? bootPackageDbSettings + , arg $ dir "inplace-pkg-config" ] diff --git a/src/Targets.hs b/src/Targets.hs index 5218909..c8aeb22 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -1,7 +1,7 @@ module Targets ( targetDirectory, knownPackages, - customConfigureSettings, + customPackageSettings, array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerLibrary, parallel, pretty, primitive, process, stm, templateHaskell, @@ -12,6 +12,7 @@ import Base hiding (arg, args) import Package import Switches import Expression +import Oracles.Builder -- Build results will be placed into a target directory with the following -- typical structure: @@ -79,15 +80,13 @@ integerLibraryCabal = case integerLibraryImpl of IntegerGmp2 -> "integer-gmp.cabal" -- Indeed, why make life easier? IntegerSimple -> "integer-simple.cabal" --- Custom configure settings for packages --- TODO: check if '--flag' and '--flags' should be collections of --- sub-arguments or not. -customConfigureSettings :: Settings -customConfigureSettings = mconcat +-- Custom package settings for packages +customPackageSettings :: Settings +customPackageSettings = builder GhcCabal ? mconcat [ package integerLibrary ? - windowsHost ? appendSub "--configure-option" ["--with-intree-gmp"] - , package base ? appendSub "--flags" [integerLibraryName] - , package ghcPrim ? appendSub "--flag" ["include-ghc-prim"] ] + windowsHost ? append ["--configure-option=--with-intree-gmp"] + , package base ? append ["--flags=" ++ integerLibraryName] + , package ghcPrim ? append ["--flag=include-ghc-prim"] ] -- Note [Cabal name weirdness] -- Find out if we can move the contents to just Cabal/ From git at git.haskell.org Thu Oct 26 23:57:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop heavy python dependency, change project folder. (907af3f) Message-ID: <20171026235755.A659B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/907af3f12f842ca7598854e5707d6398f48fd93e/ghc >--------------------------------------------------------------- commit 907af3f12f842ca7598854e5707d6398f48fd93e Author: Andrey Mokhov Date: Wed Jan 6 18:51:55 2016 +0000 Drop heavy python dependency, change project folder. See #110. [skip ci] >--------------------------------------------------------------- 907af3f12f842ca7598854e5707d6398f48fd93e .appveyor.yml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f8ce40a..f9f938d 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,7 +1,9 @@ +clone_folder: "C:\msys64\home\ghc\shake-build" + install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - bash -lc "pacman -S --noconfirm git binutils p7zip gcc mingw-w64-$(uname -m)-python3-sphinx" + - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - bash -lc "mkdir /usr/local" - bash -lc "mkdir /usr/local/bin" From git at git.haskell.org Thu Oct 26 23:57:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a target for threaded rts library. (8f9dd7e) Message-ID: <20171026235755.A7C083A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f9dd7ed189b075faecea5224fb147b7743b16f7/ghc >--------------------------------------------------------------- commit 8f9dd7ed189b075faecea5224fb147b7743b16f7 Author: Andrey Mokhov Date: Fri Jan 29 01:07:11 2016 +0000 Add a target for threaded rts library. See #98. >--------------------------------------------------------------- 8f9dd7ed189b075faecea5224fb147b7743b16f7 src/Rules.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 31489f3..5f505b3 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -15,9 +15,10 @@ allStages = [minBound ..] -- | 'need' all top-level build targets generateTargets :: Rules () generateTargets = action $ do - targets <- fmap concat (traverse targetsForStage allStages) - rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla - need $ targets ++ installTargets ++ [ rtsLib ] + targets <- fmap concat (traverse targetsForStage allStages) + rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla + rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded + need $ targets ++ installTargets ++ [ rtsLib, rtsThrLib ] targetsForStage :: Stage -> Action [String] targetsForStage stage = do From git at git.haskell.org Thu Oct 26 23:57:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement appendCcArgs abstraction for passing arguments both to Gcc and GhcCabal. (ac4dab0) Message-ID: <20171026235755.F0D2D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ac4dab040a3eaeae26ed20198fce5fa00b0dda30/ghc >--------------------------------------------------------------- commit ac4dab040a3eaeae26ed20198fce5fa00b0dda30 Author: Andrey Mokhov Date: Mon Jun 15 01:47:05 2015 +0100 Implement appendCcArgs abstraction for passing arguments both to Gcc and GhcCabal. >--------------------------------------------------------------- ac4dab040a3eaeae26ed20198fce5fa00b0dda30 src/Settings/GhcCabal.hs | 12 +++++------- src/Settings/Util.hs | 8 ++++++++ src/Switches.hs | 5 ++++- src/Targets.hs | 16 +++++++++++----- 4 files changed, 28 insertions(+), 13 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index db972ac..21ca0e0 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -58,13 +58,13 @@ librarySettings = do configureSettings :: Settings configureSettings = do + stage <- asks getStage let conf key = appendSubD $ "--configure-option=" ++ key cFlags = mconcat [ ccSettings , remove ["-Werror"] , argStagedConfig "conf-cc-args" ] ldFlags = ldSettings <> argStagedConfig "conf-gcc-linker-args" cppFlags = cppSettings <> argStagedConfig "conf-cpp-args" - stage <- asks getStage mconcat [ conf "CFLAGS" cFlags , conf "LDFLAGS" ldFlags @@ -86,6 +86,7 @@ bootPackageDbSettings = do dllSettings :: Settings dllSettings = arg "" +-- TODO: remove with' :: Builder -> Settings with' builder = appendM $ with builder @@ -104,19 +105,16 @@ packageConstraints = do ++ cabal ++ "'." args $ concatMap (\c -> ["--constraint", c]) $ constraints +-- TODO: remove ccSettings :: Settings -ccSettings = do +ccSettings = validating ? do let gccGe46 = liftM not gccLt46 - mconcat - [ package integerLibrary ? arg "-Ilibraries/integer-gmp2/gmp" - , validating ? mconcat - [ arg "-Werror" + mconcat [ arg "-Werror" , arg "-Wall" , gccIsClang ?? ( arg "-Wno-unknown-pragmas" <> gccGe46 ? windowsHost ? arg "-Werror=unused-but-set-variable" , gccGe46 ? arg "-Wno-error=inline" )] - ] ldSettings :: Settings ldSettings = mempty diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index dbd07c0..f73f0f7 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -4,6 +4,7 @@ module Settings.Util ( -- Primitive settings elements arg, argM, args, argConfig, argStagedConfig, argConfigList, argStagedConfigList, + appendCcArgs, -- argBuilderPath, argStagedBuilderPath, -- argPackageKey, argPackageDeps, argPackageDepKeys, argSrcDirs, -- argIncludeDirs, argDepIncludeDirs, @@ -46,6 +47,13 @@ argStagedConfigList key = do stage <- asks getStage argConfigList (stagedKey stage key) +appendCcArgs :: [String] -> Settings +appendCcArgs args = do + stage <- asks getStage + mconcat [ builder (Gcc stage) ? append args + , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args + , builder GhcCabal ? appendSub "--gcc-options" args ] + -- packageData :: Arity -> String -> Settings -- packageData arity key = -- return $ EnvironmentParameter $ PackageData arity key Nothing Nothing diff --git a/src/Switches.hs b/src/Switches.hs index b67d9fc..0433682 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,6 +1,6 @@ module Switches ( IntegerLibraryImpl (..), integerLibraryImpl, - notStage, stage0, stage1, stage2, notBuilder, + notStage, stage0, stage1, stage2, builders, notBuilder, supportsPackageKey, targetPlatforms, targetPlatform, targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, @@ -31,6 +31,9 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 +builders :: [Builder] -> Predicate +builders = liftM or . sequence . map builder + notBuilder :: Builder -> Predicate notBuilder = liftM not . builder diff --git a/src/Targets.hs b/src/Targets.hs index c8aeb22..1839112 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -12,6 +12,7 @@ import Base hiding (arg, args) import Package import Switches import Expression +import Settings.Util import Oracles.Builder -- Build results will be placed into a target directory with the following @@ -80,13 +81,18 @@ integerLibraryCabal = case integerLibraryImpl of IntegerGmp2 -> "integer-gmp.cabal" -- Indeed, why make life easier? IntegerSimple -> "integer-simple.cabal" --- Custom package settings for packages customPackageSettings :: Settings -customPackageSettings = builder GhcCabal ? mconcat +customPackageSettings = mconcat [ package integerLibrary ? - windowsHost ? append ["--configure-option=--with-intree-gmp"] - , package base ? append ["--flags=" ++ integerLibraryName] - , package ghcPrim ? append ["--flag=include-ghc-prim"] ] + mconcat [ windowsHost ? builder GhcCabal ? + append ["--configure-option=--with-intree-gmp"] + , appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] ] + + , package base ? + builder GhcCabal ? append ["--flags=" ++ integerLibraryName] + + , package ghcPrim ? + builder GhcCabal ? append ["--flag=include-ghc-prim"] ] -- Note [Cabal name weirdness] -- Find out if we can move the contents to just Cabal/ From git at git.haskell.org Thu Oct 26 23:57:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build hpc-bin. (0c06eac) Message-ID: <20171026235759.716793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c06eaca884d2e2606cc7ccb0726fdb520164b5d/ghc >--------------------------------------------------------------- commit 0c06eaca884d2e2606cc7ccb0726fdb520164b5d Author: Andrey Mokhov Date: Fri Jan 29 01:07:51 2016 +0000 Build hpc-bin. See #187. >--------------------------------------------------------------- 0c06eaca884d2e2606cc7ccb0726fdb520164b5d src/Builder.hs | 2 ++ src/GHC.hs | 3 +++ 2 files changed, 5 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index bfb757f..71399a7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -36,6 +36,7 @@ data Builder = Alex | GhcPkg Stage | Haddock | Happy + | Hpc | HsColour | HsCpp | Hsc2Hs @@ -63,6 +64,7 @@ builderProvenance = \case GhcCabalHsColour -> builderProvenance $ GhcCabal GhcPkg stage -> if stage > Stage0 then Just (Stage0, ghcPkg) else Nothing Haddock -> Just (Stage2, haddock) + Hpc -> Just (Stage1, hpcBin) Hsc2Hs -> Just (Stage0, hsc2hs) Unlit -> Just (Stage0, unlit) _ -> Nothing diff --git a/src/GHC.hs b/src/GHC.hs index 7504c27..0262243 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -112,6 +112,9 @@ programPath stage pkg | pkg `elem` [touchy, unlit] = case stage of Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe _ -> Nothing + | pkg == hpcBin = case stage of + Stage1 -> Just $ inplaceProgram "hpc" + _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg From git at git.haskell.org Thu Oct 26 23:57:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused predicates notBuilder and builders. (af8520c) Message-ID: <20171026235759.901153A5EC@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/af8520cecee4facafffe20a85da550cb06f32c58/ghc >--------------------------------------------------------------- commit af8520cecee4facafffe20a85da550cb06f32c58 Author: Andrey Mokhov Date: Mon Jun 15 10:48:54 2015 +0100 Drop unused predicates notBuilder and builders. >--------------------------------------------------------------- af8520cecee4facafffe20a85da550cb06f32c58 src/Settings/Util.hs | 4 ++-- src/Switches.hs | 9 +-------- 2 files changed, 3 insertions(+), 10 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index f73f0f7..dba49d5 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -51,8 +51,8 @@ appendCcArgs :: [String] -> Settings appendCcArgs args = do stage <- asks getStage mconcat [ builder (Gcc stage) ? append args - , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args - , builder GhcCabal ? appendSub "--gcc-options" args ] + , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args + , builder GhcCabal ? appendSub "--gcc-options" args ] -- packageData :: Arity -> String -> Settings -- packageData arity key = diff --git a/src/Switches.hs b/src/Switches.hs index 0433682..eada97c 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,6 +1,6 @@ module Switches ( IntegerLibraryImpl (..), integerLibraryImpl, - notStage, stage0, stage1, stage2, builders, notBuilder, + notStage, stage0, stage1, stage2, supportsPackageKey, targetPlatforms, targetPlatform, targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, @@ -9,7 +9,6 @@ module Switches ( ) where import Base -import Oracles.Builder import Expression -- Support for multiple integer library implementations @@ -31,12 +30,6 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 -builders :: [Builder] -> Predicate -builders = liftM or . sequence . map builder - -notBuilder :: Builder -> Predicate -notBuilder = liftM not . builder - -- Predicates based on configuration files supportsPackageKey :: Predicate supportsPackageKey = configKeyYes "supports-package-key" From git at git.haskell.org Thu Oct 26 23:57:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:57:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to clone folder. (dfc34f1) Message-ID: <20171026235759.8BC283A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfc34f1fb0d7aec2392cd700eaa91d10a6c87835/ghc >--------------------------------------------------------------- commit dfc34f1fb0d7aec2392cd700eaa91d10a6c87835 Author: Andrey Mokhov Date: Wed Jan 6 18:53:37 2016 +0000 Fix path to clone folder. See #110. [skip ci] >--------------------------------------------------------------- dfc34f1fb0d7aec2392cd700eaa91d10a6c87835 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f9f938d..fa03afe 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,4 +1,4 @@ -clone_folder: "C:\msys64\home\ghc\shake-build" +clone_folder: "C:\\msys64\\home\\ghc\\shake-build" install: - set MSYSTEM=MINGW64 From git at git.haskell.org Thu Oct 26 23:58:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, move derived predicates to Switches.hs. (7e62041) Message-ID: <20171026235803.868913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e62041bd01856a4920e51028a2f3bbe161374c6/ghc >--------------------------------------------------------------- commit 7e62041bd01856a4920e51028a2f3bbe161374c6 Author: Andrey Mokhov Date: Tue Jun 16 00:00:19 2015 +0100 Add comments, move derived predicates to Switches.hs. >--------------------------------------------------------------- 7e62041bd01856a4920e51028a2f3bbe161374c6 src/Expression.hs | 54 ++++++++++++++++++++++++++++++------------------------ src/Switches.hs | 10 ++++++++++ 2 files changed, 40 insertions(+), 24 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index d147280..81ed26f 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -9,8 +9,7 @@ module Expression ( append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, interpret, interpretDiff, applyPredicate, (?), (??), stage, builder, package, - configKeyValue, configKeyValues, - configKeyYes, configKeyNo, configKeyNonEmpty + configKeyValue, configKeyValues ) where import Base hiding (arg, args, Args, TargetDir) @@ -25,8 +24,11 @@ data Environment = Environment getStage :: Stage, getBuilder :: Builder, getPackage :: Package + -- getWay :: Way, and maybe something else will be useful later } +-- TODO: all readers are currently partial functions. Can use type classes to +-- guarantee these errors never occur. defaultEnvironment :: Environment defaultEnvironment = Environment { @@ -48,15 +50,31 @@ instance Monoid a => Monoid (Expr a) where mempty = return mempty mappend = liftM2 mappend +-- Basic operations on expressions: +-- 1) append something to an expression append :: Monoid a => a -> DiffExpr a append x = return . Dual . Endo $ (<> x) -appendM :: Monoid a => Action a -> DiffExpr a -appendM mx = lift mx >>= append - +-- 2) remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] remove xs = return . Dual . Endo $ filter (`notElem` xs) +-- 3) apply a predicate to an expression +applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a +applyPredicate predicate expr = do + bool <- predicate + if bool then expr else return mempty + +-- A convenient operator for predicate application +(?) :: Monoid a => Predicate -> Expr a -> Expr a +(?) = applyPredicate + +infixr 8 ? + +-- A monadic version of append +appendM :: Monoid a => Action a -> DiffExpr a +appendM mx = lift mx >>= append + -- appendSub appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument -- of the form 'prefix=listOfSubarguments' is appended to the expression. @@ -85,31 +103,28 @@ filterSub prefix p = return . Dual . Endo $ map filterSubstr | prefix `isPrefixOf` s = unwords . filter p . words $ s | otherwise = s +-- remove given elements from a list of sub-arguments with a given prefix +-- Example: removeSub "--configure-option=CFLAGS" ["-Werror"] removeSub :: String -> [String] -> Settings removeSub prefix xs = filterSub prefix (`notElem` xs) +-- Interpret a given expression in a given environment interpret :: Environment -> Expr a -> Action a interpret = flip runReaderT +-- Extract an expression from a difference expression fromDiff :: Monoid a => DiffExpr a -> Expr a fromDiff = fmap (($ mempty) . appEndo . getDual) +-- Interpret a given difference expression in a given environment interpretDiff :: Monoid a => Environment -> DiffExpr a -> Action a interpretDiff env = interpret env . fromDiff -applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a -applyPredicate predicate expr = do - bool <- predicate - if bool then expr else return mempty - -(?) :: Monoid a => Predicate -> Expr a -> Expr a -(?) = applyPredicate - +-- An equivalent of if-then-else for predicates (??) :: Monoid a => Predicate -> (Expr a, Expr a) -> Expr a p ?? (t, f) = p ? t <> (liftM not p) ? f -infixr 8 ? - +-- Basic predicates stage :: Stage -> Predicate stage s = liftM (s ==) (asks getStage) @@ -125,12 +140,3 @@ configKeyValue key value = liftM (value ==) (lift $ askConfig key) -- checks if there is at least one match configKeyValues :: String -> [String] -> Predicate configKeyValues key values = liftM (`elem` values) (lift $ askConfig key) - -configKeyYes :: String -> Predicate -configKeyYes key = configKeyValue key "YES" - -configKeyNo :: String -> Predicate -configKeyNo key = configKeyValue key "NO" - -configKeyNonEmpty :: String -> Predicate -configKeyNonEmpty key = liftM not $ configKeyValue key "" diff --git a/src/Switches.hs b/src/Switches.hs index eada97c..5436d94 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,6 +1,7 @@ module Switches ( IntegerLibraryImpl (..), integerLibraryImpl, notStage, stage0, stage1, stage2, + configKeyYes, configKeyNo, configKeyNonEmpty, supportsPackageKey, targetPlatforms, targetPlatform, targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, @@ -30,6 +31,15 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 +configKeyYes :: String -> Predicate +configKeyYes key = configKeyValue key "YES" + +configKeyNo :: String -> Predicate +configKeyNo key = configKeyValue key "NO" + +configKeyNonEmpty :: String -> Predicate +configKeyNonEmpty key = liftM not $ configKeyValue key "" + -- Predicates based on configuration files supportsPackageKey :: Predicate supportsPackageKey = configKeyYes "supports-package-key" From git at git.haskell.org Thu Oct 26 23:58:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep experimenting with cabal folder. (d913235) Message-ID: <20171026235826.7ACFD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d913235b1f6e907a63ee8974e1f09c20b711bf0a/ghc >--------------------------------------------------------------- commit d913235b1f6e907a63ee8974e1f09c20b711bf0a Author: Andrey Mokhov Date: Wed Jan 6 22:44:46 2016 +0000 Keep experimenting with cabal folder. See #110. [skip ci] >--------------------------------------------------------------- d913235b1f6e907a63ee8974e1f09c20b711bf0a .appveyor.yml | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index a3dd1ef..751bc1f 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,22 +1,23 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" cache: - - "C:\\msys64\\home\\ghc\\.cabal" + - "C:\\msys64\\home\\cabal" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /home/ghc/.cabal" + - bash -lc "mkdir -p /home/cabal" + - bash -lc "chmod -R 777 /home/cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal --config-file=/home/ghc/.cabal update" - - bash -lc "cabal --config-file=/home/ghc/.cabal install -j --prefix=/usr/local alex happy" + - bash -lc "cabal --config-file=/home/cabal update" + - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/ghc/.cabal install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:58:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add configFile to Base, track building ./settings (acd13b4) Message-ID: <20171026235827.06F9F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acd13b473853eab11eac680a67c3e4ab2f7f82ad/ghc >--------------------------------------------------------------- commit acd13b473853eab11eac680a67c3e4ab2f7f82ad Author: Andrey Mokhov Date: Tue Feb 2 15:11:11 2016 +0000 Add configFile to Base, track building ./settings See #200. >--------------------------------------------------------------- acd13b473853eab11eac680a67c3e4ab2f7f82ad src/Base.hs | 5 ++++- src/Oracles/Config.hs | 3 --- src/Rules/Config.hs | 10 ++++++---- 3 files changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 37f4716..464c1c9 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,7 +16,7 @@ module Base ( module Development.Shake.FilePath, -- * Paths - shakeFilesPath, configPath, sourcePath, programInplacePath, + shakeFilesPath, configPath, configFile, sourcePath, programInplacePath, bootPackageConstraints, packageDependencies, -- * Output @@ -54,6 +54,9 @@ shakeFilesPath = shakePath -/- ".db" configPath :: FilePath configPath = shakePath -/- "cfg" +configFile :: FilePath +configFile = configPath -/- "system.config" + -- | Path to source files of the build system, e.g. this file is located at -- sourcePath -/- "Base.hs". We use this to `need` some of the source files. sourcePath :: FilePath diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index cde2383..7801208 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -8,9 +8,6 @@ import Development.Shake.Config newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -configFile :: FilePath -configFile = configPath -/- "system.config" - askConfig :: String -> Action String askConfig key = askConfigWithDefault key . putError $ "Cannot find key '" ++ key ++ "' in configuration files." diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 7b6e8fa..eea61c6 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -8,12 +8,14 @@ configRules :: Rules () configRules = do -- We always rerun the configure script in this mode, because the flags -- passed to it can affect the contents of system.config file. - configPath -/- "system.config" %> \out -> do + [configFile, "settings"] &%> \[cfg, settings] -> do alwaysRerun case cmdConfigure of - RunConfigure args -> runConfigure "." [] [args] - SkipConfigure -> unlessM (doesFileExist out) $ - putError $ "Configuration file " ++ out ++ " is missing.\n" + RunConfigure args -> do + need [ settings <.> "in" ] + runConfigure "." [] [args] + SkipConfigure -> unlessM (doesFileExist cfg) $ + putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " ++ "build system by passing --configure[=ARGS] flag." From git at git.haskell.org Thu Oct 26 23:58:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (b2b7c5c) Message-ID: <20171026235827.46BEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2b7c5c53ed5369249ebff39aa8735a897ad86a9/ghc >--------------------------------------------------------------- commit b2b7c5c53ed5369249ebff39aa8735a897ad86a9 Author: Andrey Mokhov Date: Tue Jun 16 09:54:10 2015 +0100 Add comments. >--------------------------------------------------------------- b2b7c5c53ed5369249ebff39aa8735a897ad86a9 src/Expression.hs | 2 +- src/Rules/Data.hs | 70 ++++++++++++++---------------------------------- src/Settings/GhcCabal.hs | 3 +++ 3 files changed, 24 insertions(+), 51 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 9232aed..4809324 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -24,7 +24,7 @@ data Environment = Environment getStage :: Stage, getPackage :: Package, getBuilder :: Builder, - getFile :: FilePath, + getFile :: FilePath, -- TODO: handle multple files? getWay :: Way } diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index aa1ebab..3754cdc 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -13,29 +13,6 @@ import Settings.GhcPkg import Settings.GhcCabal import Util --- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: --- 1) Drop lines containing '$' --- For example, get rid of --- libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ... --- Reason: we don't need them and we can't parse them. --- 2) Replace '/' and '\' with '_' before '=' --- For example libraries/deepseq/dist-install_VERSION = 1.4.0.0 --- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 --- Reason: Shake's built-in makefile parser doesn't recognise slashes - -postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map processLine pkgData - where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line - --- this is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument --- * otherwise, we must collapse it into one space-separated string - -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: Environment -> Rules () buildPackageData env = @@ -53,6 +30,8 @@ buildPackageData env = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" + -- TODO: 1) how to automate this? 2) handle multiple files? + newEnv = env { getFile = dir "package-data.mk" } -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac @@ -62,37 +41,28 @@ buildPackageData env = run' env (GhcPkg stage) postProcessPackageData $ dir "package-data.mk" +-- TODO: This should probably go to Oracles.Builder run' :: Environment -> Builder -> Action () run' env builder = do args <- interpret (env {getBuilder = builder}) $ fromDiff settings putColoured Green (show args) run builder args ---buildRule :: Package -> TodoItem -> Rules () ---buildRule pkg @ (Package name path cabal _) todo @ (stage, dist, settings) = --- let pathDist = path dist --- cabalPath = path cabal --- configure = path "configure" --- in --- -- All these files are produced by a single run of GhcCabal --- (pathDist ) <$> --- [ "package-data.mk" --- , "haddock-prologue.txt" --- , "inplace-pkg-config" --- , "setup-config" --- , "build" "autogen" "cabal_macros.h" --- -- TODO: Is this needed? Also check out Paths_cpsa.hs. --- -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" --- ] &%> \_ -> do --- need [cabalPath] --- when (doesFileExist $ configure <.> "ac") $ need [configure] --- -- GhcCabal will run the configure script, so we depend on it --- -- We still don't know who build the configure script from configure.ac --- run GhcCabal $ cabalArgs pkg todo --- when (registerPackage settings) $ --- run (GhcPkg stage) $ ghcPkgArgs pkg todo --- postProcessPackageData $ pathDist "package-data.mk" - --- buildSettings = + builder Gcc ? ccSettings +-- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: +-- 1) Drop lines containing '$' +-- For example, get rid of +-- libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ... +-- Reason: we don't need them and we can't parse them. +-- 2) Replace '/' and '\' with '_' before '=' +-- For example libraries/deepseq/dist-install_VERSION = 1.4.0.0 +-- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 +-- Reason: Shake's built-in makefile parser doesn't recognise slashes --- builder Gcc ? "-tricky-flag" +postProcessPackageData :: FilePath -> Action () +postProcessPackageData file = do + pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) + length pkgData `seq` writeFileLines file $ map processLine pkgData + where + processLine line = replaceSeparators '_' prefix ++ suffix + where + (prefix, suffix) = break (== '=') line diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 4388b17..4cbb0a3 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -83,6 +83,9 @@ bootPackageDbSettings = do sourcePath <- lift $ askConfig "ghc-source-path" arg $ "--package-db=" ++ sourcePath "libraries/bootstrapping.conf" +-- this is a positional argument, hence: +-- * if it is empty, we need to emit one empty string argument +-- * otherwise, we must collapse it into one space-separated string dllSettings :: Settings dllSettings = arg "" From git at git.haskell.org Thu Oct 26 23:58:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run cabal outside bash. (f419f64) Message-ID: <20171026235829.ED7993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f419f6430ff16818513a33fd802b2c09488c5311/ghc >--------------------------------------------------------------- commit f419f6430ff16818513a33fd802b2c09488c5311 Author: Andrey Mokhov Date: Wed Jan 6 23:12:14 2016 +0000 Run cabal outside bash. See #110. [skip ci] >--------------------------------------------------------------- f419f6430ff16818513a33fd802b2c09488c5311 .appveyor.yml | 15 ++++++++------- 1 file changed, 8 insertions(+), 7 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 751bc1f..d8bb09d 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,7 +1,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -cache: - - "C:\\msys64\\home\\cabal" +# cache: +# - "C:\\msys64\\home\\cabal" install: - set MSYSTEM=MINGW64 @@ -9,15 +9,16 @@ install: - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - bash -lc "mkdir -p /home/cabal" - - bash -lc "chmod -R 777 /home/cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal --config-file=/home/cabal update" - - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" + - cabal update -v + - cabal install -j --prefix=/usr/local alex happy + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - cd C:\msys64\mingw64\home\ghc\shake-build + - cabal install --only-dependencies build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:58:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't print progress info too early. (e5e7221) Message-ID: <20171026235831.33E1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e5e722178f227e3b81d27c8f66c152002d375aad/ghc >--------------------------------------------------------------- commit e5e722178f227e3b81d27c8f66c152002d375aad Author: Andrey Mokhov Date: Tue Feb 2 15:11:53 2016 +0000 Don't print progress info too early. See #200. >--------------------------------------------------------------- e5e722178f227e3b81d27c8f66c152002d375aad src/Rules/Actions.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d85e0dc..658ba17 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -67,6 +67,7 @@ captureStdout target path argList = do copyFile :: FilePath -> FilePath -> Action () copyFile source target = do + need [source] -- Guarantee source is built before printing progress info. putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target From git at git.haskell.org Thu Oct 26 23:58:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make targetDirectory and knownPackages configurable, rename Environment to Target. (418a1cd) Message-ID: <20171026235831.64CDE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/418a1cd630e1c2eb6e467e502d615ae4307113b7/ghc >--------------------------------------------------------------- commit 418a1cd630e1c2eb6e467e502d615ae4307113b7 Author: Andrey Mokhov Date: Sun Jul 12 23:12:39 2015 +0100 Make targetDirectory and knownPackages configurable, rename Environment to Target. >--------------------------------------------------------------- 418a1cd630e1c2eb6e467e502d615ae4307113b7 doc/meeting-16-June-2015.txt | 22 ++++++++++++- src/Expression.hs | 72 ++++++++++++++++++++++++----------------- src/Package.hs | 1 + src/Rules.hs | 8 ++--- src/Rules/Data.hs | 22 ++++++------- src/Rules/Package.hs | 2 +- src/Settings.hs | 1 - src/Settings/GhcCabal.hs | 20 ++++++++++-- src/Settings/GhcPkg.hs | 2 +- src/Settings/Packages.hs | 18 ++++++++++- src/Settings/TargetDirectory.hs | 11 +++++++ src/Settings/Util.hs | 9 +++--- src/Switches.hs | 9 ------ src/Targets.hs | 59 +++++---------------------------- src/UserSettings.hs | 54 ++++++++++--------------------- 15 files changed, 155 insertions(+), 155 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 418a1cd630e1c2eb6e467e502d615ae4307113b7 From git at git.haskell.org Thu Oct 26 23:58:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run cabal in -v3 mode to reveal the problem. (accce20) Message-ID: <20171026235833.7EF543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/accce2015d2e61fd949885866f014026a4a69049/ghc >--------------------------------------------------------------- commit accce2015d2e61fd949885866f014026a4a69049 Author: Andrey Mokhov Date: Wed Jan 6 23:36:07 2016 +0000 Run cabal in -v3 mode to reveal the problem. See #110. [skip ci] >--------------------------------------------------------------- accce2015d2e61fd949885866f014026a4a69049 .appveyor.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index d8bb09d..0b90efa 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,12 +8,11 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /home/cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - cabal update -v + - cabal update -v3 - cabal install -j --prefix=/usr/local alex happy - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Thu Oct 26 23:58:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Sort list items. (d1fb3de) Message-ID: <20171026235835.0A43D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1fb3de6d250c1d30ba86612595c3f48c2661c1a/ghc >--------------------------------------------------------------- commit d1fb3de6d250c1d30ba86612595c3f48c2661c1a Author: Andrey Mokhov Date: Tue Feb 2 15:16:21 2016 +0000 Sort list items. See #200. >--------------------------------------------------------------- d1fb3de6d250c1d30ba86612595c3f48c2661c1a src/Rules/Generate.hs | 46 +++++++++++++++++++++++----------------------- 1 file changed, 23 insertions(+), 23 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 7538470..9c67760 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -21,11 +21,11 @@ import Rules.Resources (Resources) import Settings installTargets :: [FilePath] -installTargets = [ "inplace/lib/template-hsc.h" +installTargets = [ "inplace/lib/ghc-usage.txt" + , "inplace/lib/ghci-usage.txt" , "inplace/lib/platformConstants" , "inplace/lib/settings" - , "inplace/lib/ghc-usage.txt" - , "inplace/lib/ghci-usage.txt" ] + , "inplace/lib/template-hsc.h" ] primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -45,8 +45,8 @@ includesDependencies = ("includes" -/-) <$> ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> - [ "GHC/PrimopWrappers.hs" - , "autogen/GHC/Prim.hs" ] + [ "autogen/GHC/Prim.hs" + , "GHC/PrimopWrappers.hs" ] derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" @@ -54,9 +54,9 @@ derivedConstantsPath = "includes/dist-derivedconstants/header" derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) [ "DerivedConstants.h" + , "GHCConstantsHaskellExports.hs" , "GHCConstantsHaskellType.hs" - , "GHCConstantsHaskellWrappers.hs" - , "GHCConstantsHaskellExports.hs" ] + , "GHCConstantsHaskellWrappers.hs" ] compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = @@ -66,21 +66,21 @@ compilerDependencies stage = ++ filter (const $ stage > Stage0) libffiDependencies ++ derivedConstantsDependencies ++ fmap ((targetPath stage compiler -/- "build") -/-) - [ "primop-vector-uniques.hs-incl" + [ "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" + , "primop-list.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-strictness.hs-incl" + , "primop-tag.hs-incl" , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tys.hs-incl" + , "primop-vector-uniques.hs-incl" ] -- TODO: Turn this into a FilePaths expression generatedDependencies :: Stage -> Package -> [FilePath] @@ -139,8 +139,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = -- TODO: why different folders for generated files? fmap (buildPath -/-) - [ "GHC/PrimopWrappers.hs" - , "autogen/GHC/Prim.hs" + [ "autogen/GHC/Prim.hs" + , "GHC/PrimopWrappers.hs" , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] build $ fullTarget target GenPrimopCode [primopsTxt stage] [file] @@ -164,11 +164,11 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = copyRules :: Rules () copyRules = do - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs - "inplace/lib/platformConstants" <~ derivedConstantsPath - "inplace/lib/settings" <~ "." "inplace/lib/ghc-usage.txt" <~ "driver" "inplace/lib/ghci-usage.txt" <~ "driver" + "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs where file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file From git at git.haskell.org Thu Oct 26 23:58:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, rename interpretDiff to interpret. (238398a) Message-ID: <20171026235835.2BD9D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/238398a839967ceb0dfc8f6e013a23f8551d67f5/ghc >--------------------------------------------------------------- commit 238398a839967ceb0dfc8f6e013a23f8551d67f5 Author: Andrey Mokhov Date: Mon Jul 13 16:13:58 2015 +0100 Add comments, rename interpretDiff to interpret. >--------------------------------------------------------------- 238398a839967ceb0dfc8f6e013a23f8551d67f5 src/Expression.hs | 51 +++++++++++++++++++++++++++++++++++---------------- src/Rules.hs | 2 +- src/Rules/Data.hs | 2 +- 3 files changed, 37 insertions(+), 18 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 46b3c40..88561eb 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -7,7 +7,7 @@ module Expression ( Settings, Ways, Packages, Target (..), stageTarget, stagePackageTarget, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, - interpret, interpretDiff, + interpret, interpretExpr, applyPredicate, (?), (??), stage, package, builder, file, way, configKeyValue, configKeyValues ) where @@ -19,6 +19,9 @@ import Package import Data.Monoid import Control.Monad.Reader +-- Target captures parameters relevant to the current build target: Stage and +-- Package being built, Builder that is to be invoked, file(s) that are to +-- be built and the Way they are to be built. data Target = Target { getStage :: Stage, @@ -48,24 +51,40 @@ stagePackageTarget stage package = Target getWay = error "stagePackageTarget: Way not set" } +-- Expr a is a computation that produces a value of type Action a and can read +-- parameters of the current build Target. +type Expr a = ReaderT Target Action a + +-- If values of type a form a Monoid then so do computations of type Expr a: +-- * the empty computation returns the identity element of the underlying type +-- * two computations can be combined by combining their results +instance Monoid a => Monoid (Expr a) where + mempty = return mempty + mappend = liftM2 mappend + +-- Diff a holds functions of type a -> a and is equipped with a Monoid instance. -- We could use Dual (Endo a) instead of Diff a, but the former may look scary. +-- The name comes from "difference lists". newtype Diff a = Diff { fromDiff :: a -> a } +-- DiffExpr a is a computation that builds a difference list (i.e., a function +-- of type Action (a -> a)) and can read parameters of the current build Target. +type DiffExpr a = Expr (Diff a) + +-- Note the reverse order of function composition (y . x), which ensures that +-- when two DiffExpr computations c1 and c2 are combined (c1 <> c2), then c1 is +-- applied first, and c2 is applied second. instance Monoid (Diff a) where mempty = Diff id Diff x `mappend` Diff y = Diff $ y . x -type Expr a = ReaderT Target Action a -type DiffExpr a = Expr (Diff a) - -type Predicate = Expr Bool -type Settings = DiffExpr [String] -- TODO: rename to Args -type Ways = DiffExpr [Way] -type Packages = DiffExpr [Package] - -instance Monoid a => Monoid (Expr a) where - mempty = return mempty - mappend = liftM2 mappend +-- The following expressions are used throughout the build system for +-- specifying conditions (Predicate), lists of arguments (Settings), Ways and +-- Packages. +type Predicate = Expr Bool +type Settings = DiffExpr [String] -- TODO: rename to Args +type Ways = DiffExpr [Way] +type Packages = DiffExpr [Package] -- Basic operations on expressions: -- 1) append something to an expression @@ -126,16 +145,16 @@ removeSub :: String -> [String] -> Settings removeSub prefix xs = filterSub prefix (`notElem` xs) -- Interpret a given expression in a given environment -interpret :: Target -> Expr a -> Action a -interpret = flip runReaderT +interpretExpr :: Target -> Expr a -> Action a +interpretExpr = flip runReaderT -- Extract an expression from a difference expression fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) -- Interpret a given difference expression in a given environment -interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a -interpretDiff target = interpret target . fromDiffExpr +interpret :: Monoid a => Target -> DiffExpr a -> Action a +interpret target = interpretExpr target . fromDiffExpr -- An equivalent of if-then-else for predicates (??) :: Monoid a => Predicate -> (Expr a, Expr a) -> Expr a diff --git a/src/Rules.hs b/src/Rules.hs index 6e1093b..852a6cf 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -17,7 +17,7 @@ import Settings.TargetDirectory generateTargets :: Rules () generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do - pkgs <- interpretDiff (stageTarget stage) packages + pkgs <- interpret (stageTarget stage) packages forM_ pkgs $ \pkg -> do let dir = targetDirectory stage pkg need [pkgPath pkg dir "package-data.mk"] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 20f05f5..d608fea 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -44,7 +44,7 @@ buildPackageData target = -- TODO: This should probably go to Oracles.Builder run' :: Target -> Builder -> Action () run' target builder = do - args <- interpret (target {getBuilder = builder}) $ fromDiffExpr settings + args <- interpret (target {getBuilder = builder}) settings putColoured Green (show args) run builder args From git at git.haskell.org Thu Oct 26 23:58:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run cabal in -v3 mode in bash. (351c39f) Message-ID: <20171026235836.E2EDE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/351c39f38b709a6304e8085cae52fe90d23a2cd9/ghc >--------------------------------------------------------------- commit 351c39f38b709a6304e8085cae52fe90d23a2cd9 Author: Andrey Mokhov Date: Wed Jan 6 23:56:24 2016 +0000 Run cabal in -v3 mode in bash. See #110. [skip ci] >--------------------------------------------------------------- 351c39f38b709a6304e8085cae52fe90d23a2cd9 .appveyor.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 0b90efa..19236d4 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -12,12 +12,12 @@ install: - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - cabal update -v3 - - cabal install -j --prefix=/usr/local alex happy + - bash -lc "cabal update -v3" + - bash -lc "cabal install -j --prefix=/usr/local alex happy" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build - - cabal install --only-dependencies + - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:55:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add full support for --configure command line flag. (4460146) Message-ID: <20171026235528.465953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/446014681874982a340c245d3c279229eeb6f121/ghc >--------------------------------------------------------------- commit 446014681874982a340c245d3c279229eeb6f121 Author: Andrey Mokhov Date: Thu Jan 21 17:36:50 2016 +0000 Add full support for --configure command line flag. >--------------------------------------------------------------- 446014681874982a340c245d3c279229eeb6f121 src/CmdLineFlag.hs | 2 +- src/Rules/Actions.hs | 5 +++-- src/Rules/Config.hs | 31 ++++++++++++++++++++++--------- 3 files changed, 26 insertions(+), 12 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 9e33397..249070a 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -61,7 +61,7 @@ flags = [ Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") , Option [] ["split-objects"] (NoArg readSplitObjects) "Generate split objects (requires a full clean rebuild)." , Option [] ["configure"] (OptArg readConfigure "ARGS") - "Run boot and configure scripts (passing ARGS to the latter)." ] + "Run configure with ARGS (also run boot if necessary)." ] -- TODO: Avoid unsafePerformIO by using shakeExtra (awaiting Shake's release) {-# NOINLINE cmdLineFlags #-} diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 2b05207..0e4961f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -97,12 +97,13 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] + let note = if null args || args == [""] then "" else " (" ++ intercalate ", " args ++ ")" if dir == "." then do - putBuild $ "| Run configure..." + putBuild $ "| Run configure" ++ note ++ "..." quietly $ cmd Shell (EchoStdout False) "bash configure" opts' args else do - putBuild $ "| Run configure in " ++ dir ++ "..." + putBuild $ "| Run configure" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args where -- Always configure with bash. diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 6f0447f..77ac1ac 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -5,13 +5,26 @@ import CmdLineFlag import Rules.Actions configRules :: Rules () -configRules = case cmdConfigure of - SkipConfigure -> mempty - RunConfigure args -> do - configPath -/- "system.config" %> \_ -> do - need [configPath -/- "system.config.in"] - runConfigure "." [] [args] +configRules = do + -- We always rerun the configure script in this mode, because the flags + -- passed to it can affect the contents of system.config file. + configPath -/- "system.config" %> \out -> do + alwaysRerun + case cmdConfigure of + RunConfigure args -> runConfigure "." [] [args] + SkipConfigure -> unlessM (doesFileExist out) $ + putError $ "Configuration file " ++ out ++ " is missing.\n" + ++ "Run the configure script either manually or via the " + ++ "build system by passing --configure[=ARGS] flag." - "configure" %> \_ -> do - putBuild "| Running boot..." - unit $ cmd "perl boot" + -- When we detect Windows paths in ACLOCAL_PATH we reset it. + -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. + "configure" %> \_ -> do + putBuild "| Running boot..." + aclocal <- getEnv "ACLOCAL_PATH" + let env = case aclocal of + Nothing -> [] + Just s -> if ":\\" `isPrefixOf` (drop 1 s) + then [AddEnv "ACLOCAL_PATH" ""] + else [] + quietly $ cmd (EchoStdout False) env "perl boot" From git at git.haskell.org Thu Oct 26 23:55:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid cyclic dependencies, see #103. (50dbdd4) Message-ID: <20171026235530.098A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/50dbdd4040e45284fc4cc53115469fe3a882ac5a/ghc >--------------------------------------------------------------- commit 50dbdd4040e45284fc4cc53115469fe3a882ac5a Author: Andrey Mokhov Date: Tue Jan 5 21:30:58 2016 +0000 Avoid cyclic dependencies, see #103. >--------------------------------------------------------------- 50dbdd4040e45284fc4cc53115469fe3a882ac5a src/Rules/IntegerGmp.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index f86371c..0d5da26 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -105,7 +105,9 @@ integerGmpRules = do -- check whether we need to build in tree gmp -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` - need [pkgDataFile Stage1 integerGmp] + + runConfigure (pkgPath integerGmp) [] [] + configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk then do From git at git.haskell.org Thu Oct 26 23:55:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement basic infrastructure for parameterised expressions. (a5a8d53) Message-ID: <20171026235530.941CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a8d53e5cca5cb6a5609bde961d6f560fbb143f/ghc >--------------------------------------------------------------- commit a5a8d53e5cca5cb6a5609bde961d6f560fbb143f Author: Andrey Mokhov Date: Tue Feb 10 02:44:34 2015 +0000 Implement basic infrastructure for parameterised expressions. >--------------------------------------------------------------- a5a8d53e5cca5cb6a5609bde961d6f560fbb143f src/Base.hs | 2 +- src/Settings.hs | 165 +++++++++++++++++++++++++++++++++++++++++--------------- 2 files changed, 122 insertions(+), 45 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fa9104a..49b0fb2 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,7 +16,7 @@ module Base ( productArgs, concatArgs ) where -import Development.Shake hiding ((*>)) +import Development.Shake hiding ((*>), alternatives) import Development.Shake.FilePath import Control.Applicative import Data.Function diff --git a/src/Settings.hs b/src/Settings.hs index 42ceed9..aaec2ab 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -7,6 +7,7 @@ module Settings ( import Base import Ways +import Oracles.Builder data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple @@ -22,52 +23,45 @@ integerLibraryName = case integerLibrary of buildHaddock :: Bool buildHaddock = True --- A Parameterised Graph datatype for storing argument lists with conditions -data PG a b = Epsilon - | Vertex a - | Overlay (PG a b) (PG a b) - | Sequence (PG a b) (PG a b) - | Condition b (PG a b) +-- A generic Parameterised Graph datatype for parameterised argument lists +data PG p v = Epsilon + | Vertex v + | Overlay (PG p v) (PG p v) + | Sequence (PG p v) (PG p v) + | Condition p (PG p v) -instance Monoid (PG a b) where +instance Monoid (PG p v) where mempty = Epsilon mappend = Overlay -type ArgsExpression = PG String Predicate -type WaysExpression = PG Way Predicate +data Predicate a = Evaluated Bool -- Evaluated predicate + | Parameter a -- To be evaluated later + | Not (Predicate a) -- Negate predicate + | And (Predicate a) (Predicate a) -- Conjunction + | Or (Predicate a) (Predicate a) -- Disjunction -data Match = MatchPackage FilePath -- Match a Package name - | MatchFile FilePath -- Match a file - | MatchStage Stage -- Match a Stage - | MatchWay Way -- Match a Way - | MatchKeyValue String String -- Match a key with a value (config) - --- A Matcher takes a Match description and attempts to evaluate it. +-- Evaluator takes a Parameter and attempts to evaluate it. -- Returns Nothing if the attempt fails. -type Matcher = Match -> Maybe Bool +type Evaluator a = a -> Maybe Bool --- A Monoid instance for matchers (returns first successful match) -instance Monoid Matcher where +-- Monoid instance for evaluators (returns first successful evaluation) +instance Monoid (Evaluator a) where mempty = const Nothing - p `mappend` q = \m -> getFirst $ First (p m) <> First (q m) - -data Predicate = Evaluated Bool -- Evaluated predicate - | If Match -- Perform a match to evaluate - | Not Predicate -- Negate predicate - | And Predicate Predicate -- Conjunction of two predicates - | Or Predicate Predicate -- Disjunction of two predicates + e `mappend` f = \p -> getFirst $ First (e p) <> First (f p) -match :: Predicate -> Matcher -> Predicate -match p @ (Evaluated _) _ = p -match p @ (If match ) m = case m match of +-- Apply an evalulator to a predicate (partial evaluation, or projection) +apply :: Evaluator a -> Predicate a -> Predicate a +apply _ p @ (Evaluated _) = p +apply e p @ (Parameter q) = case e q of Just bool -> Evaluated bool Nothing -> p -match (Not p ) m = match p m -match (And p q) m = And (match p m) (match q m) -match (Or p q) m = Or (match p m) (match q m) +apply e (Not p ) = Not (apply e p) +apply e (And p q) = And (apply e p) (apply e q) +apply e (Or p q) = Or (apply e p) (apply e q) --- returns Nothing if the given predicate cannot be uniquely evaluated -evalPredicate :: Predicate -> Maybe Bool +-- Attempt to evaluate a predicate. Returns Nothing if the predicate +-- cannot be uniquely evaluated due to remaining parameters. +evalPredicate :: Predicate a -> Maybe Bool evalPredicate (Evaluated bool) = Just bool evalPredicate (Not p) = not <$> evalPredicate p evalPredicate (And p q) @@ -84,15 +78,98 @@ evalPredicate (Or p q) where p' = evalPredicate p q' = evalPredicate q -evalPredicate (If _) = Nothing - --- returns Nothing if the given expression cannot be uniquely evaluated -evalPG :: PG a Predicate -> Maybe [a] -evalPG Epsilon = Just [] -evalPG (Vertex v) = Just [v] -evalPG (Overlay p q) = (++) <$> evalPG p <*> evalPG q -evalPG (Sequence p q) = (++) <$> evalPG p <*> evalPG q -evalPG (Condition x p) = case evalPredicate x of - Just True -> evalPG p +evalPredicate (Parameter _) = Nothing -- cannot evaluate Parameter + +-- Flatten a PG into a list. Returns Nothing if the given expression +-- cannot be uniquely evaluated due to remaining parameters. +linearise :: PG (Predicate a) v -> Maybe [v] +linearise Epsilon = Just [] +linearise (Vertex v) = Just [v] +linearise (Overlay p q) = (++) <$> linearise p <*> linearise q +linearise (Sequence p q) = (++) <$> linearise p <*> linearise q +linearise (Condition x p) = case evalPredicate x of + Just True -> linearise p Just False -> Just [] Nothing -> Nothing + +(~>) :: PG p v -> PG p v -> PG p v +a ~> b = Sequence a b + +type PGP p v = PG (Predicate p) v + +disjuction :: [a] -> (a -> Predicate p) -> PGP p v -> PGP p v +disjuction [] _ = id +disjuction (a:as) convert = Condition (foldr Or (convert a) $ map convert as) + +-- GHC build specific + +data BuildParameter = WhenPackage FilePath + | WhenBuilder Builder + | WhenStage Stage + | WhenWay Way + | WhenFile FilePath + | WhenKeyValue String String -- from config files + +type Expression a = PGP BuildParameter a + +type Rewrite a = Expression a -> Expression a + +type ArgsExpression = Expression String + +alternatives :: (b -> BuildParameter) -> [b] -> Rewrite a +alternatives p bs = disjuction bs (Parameter . p) + +whenPackages :: [FilePath] -> Rewrite a +whenPackages = alternatives WhenPackage + +whenBuilders :: [Builder] -> Rewrite a +whenBuilders = alternatives WhenBuilder + +whenStages :: [Stage] -> Rewrite a +whenStages = alternatives WhenStage + +unlessStage :: Stage -> Rewrite a +unlessStage stage = Condition (Not $ Parameter $ WhenStage stage) + +whenWays :: [Way] -> Rewrite a +whenWays = alternatives WhenWay + +whenFiles :: [FilePath] -> Rewrite a +whenFiles = alternatives WhenFile + +whenKeyValues :: String -> [String] -> Rewrite a +whenKeyValues key = alternatives (WhenKeyValue key) + +whenKeyValue :: String -> String -> Rewrite a +whenKeyValue key value = whenKeyValues key [value] + +whenPackageKey :: Rewrite a +whenPackageKey = whenKeyValue "supports-package-key" "YES" . unlessStage Stage0 + +--packageArgs = +-- Vertex "-hide-all-packages" +-- ~> +-- Vertex "-no-user-package-db" +-- ~> +-- Vertex "-include-pkg-deps" +-- ~> If (MatchStage Stage0) +-- (Vertex "-package-db libraries/bootstrapping.conf") +-- ~> If usePackageKey +-- ( + +-- ) + +--packageArgs :: Stage -> FilePath -> Args +--packageArgs stage pathDist = do +-- usePackageKey <- SupportsPackageKey || stage /= Stage0 +-- args [ arg "-hide-all-packages" +-- , arg "-no-user-package-db" +-- , arg "-include-pkg-deps" +-- , when (stage == Stage0) $ +-- arg "-package-db libraries/bootstrapping.conf" +-- , if usePackageKey +-- then productArgs ["-this-package-key"] [arg $ PackageKey pathDist] +-- <> productArgs ["-package-key" ] [args $ DepKeys pathDist] +-- else productArgs ["-package-name" ] [arg $ PackageKey pathDist] +-- <> productArgs ["-package" ] [args $ Deps pathDist] +-- ] From git at git.haskell.org Thu Oct 26 23:55:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch on ChangeModtimeAndDigest by default. (c9b2b76) Message-ID: <20171026235531.C29D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9b2b7633dea28eb1e5e0f6001f9cc12b34c8584/ghc >--------------------------------------------------------------- commit c9b2b7633dea28eb1e5e0f6001f9cc12b34c8584 Author: Andrey Mokhov Date: Thu Jan 21 19:14:08 2016 +0000 Switch on ChangeModtimeAndDigest by default. >--------------------------------------------------------------- c9b2b7633dea28eb1e5e0f6001f9cc12b34c8584 src/Main.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index 5c62479..f83734c 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -35,6 +35,7 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do , Rules.packageRules , Test.testRules ] options = shakeOptions - { shakeFiles = Base.shakeFilesPath + { shakeChange = ChangeModtimeAndDigest + , shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Thu Oct 26 23:55:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't separate build commands with an empty line.\n\nThis allows to fit more commands on screen. (412009d) Message-ID: <20171026235533.877083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/412009d52e693f3f67b86a71de4e7f359cd3b2a8/ghc >--------------------------------------------------------------- commit 412009d52e693f3f67b86a71de4e7f359cd3b2a8 Author: Andrey Mokhov Date: Tue Jan 5 23:21:54 2016 +0000 Don't separate build commands with an empty line.\n\nThis allows to fit more commands on screen. >--------------------------------------------------------------- 412009d52e693f3f67b86a71de4e7f359cd3b2a8 src/Base.hs | 2 +- src/Rules/Actions.hs | 10 +++++----- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 69904c4..36f2eb9 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -174,7 +174,7 @@ putError msg = do -- | Render the given set of lines in a nice box of ASCII renderBox :: [String] -> String -renderBox ls = concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) +renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) where -- Minimum total width of the box in characters minimumBoxWidth = 32 diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d567747..6f116b5 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -71,7 +71,7 @@ copyFile source target = do createDirectory :: FilePath -> Action () createDirectory dir = do - putBuild $ "\n| Create directory " ++ dir + putBuild $ "| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir -- Note, the source directory is untracked @@ -85,7 +85,7 @@ moveDirectory source target = do -- Transform a given file by applying a function to its contents fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do - putBuild $ "\n| Fix " ++ file + putBuild $ "| Fix " ++ file old <- liftIO $ readFile file let new = f old length new `seq` liftIO $ writeFile file new @@ -93,14 +93,14 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] - putBuild $ "\n| Run configure in " ++ dir ++ "..." + putBuild $ "| Run configure in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "\n| Run make" ++ note ++ " in " ++ dir ++ "..." + putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args runBuilder :: Builder -> [String] -> Action () @@ -108,7 +108,7 @@ runBuilder builder args = do needBuilder laxDependencies builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "\n| Run " ++ show builder ++ note + putBuild $ "| Run " ++ show builder ++ note quietly $ cmd [path] args -- Print out key information about the command being executed From git at git.haskell.org Thu Oct 26 23:55:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Eq instances. (27bc02e) Message-ID: <20171026235534.1C55B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27bc02eb27cefd49c0292a6190b269c5dd2bb4b7/ghc >--------------------------------------------------------------- commit 27bc02eb27cefd49c0292a6190b269c5dd2bb4b7 Author: Andrey Mokhov Date: Wed Feb 11 03:22:35 2015 +0000 Add Eq instances. >--------------------------------------------------------------- 27bc02eb27cefd49c0292a6190b269c5dd2bb4b7 src/Oracles/Builder.hs | 2 +- src/Package/Base.hs | 5 +++-- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 07b1bbd..d538611 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -29,7 +29,7 @@ data Builder = Ar | Gcc Stage | Ghc Stage | GhcPkg Stage - deriving Show + deriving (Show, Eq) instance ShowArg Builder where showArg builder = toStandard <$> do diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 40d893e..e3c38e7 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -4,7 +4,6 @@ module Package.Base ( module Ways, module Util, module Oracles, - module Settings, Package (..), Settings (..), TodoItem (..), defaultSettings, library, customise, updateSettings, commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, @@ -21,7 +20,6 @@ import Base import Ways import Util import Oracles -import Settings import qualified System.Directory as S data Settings = Settings @@ -72,6 +70,9 @@ data Package = Package pkgTodo :: [TodoItem] -- [(Stage1, "dist-install", defaultSettings)] } +instance Eq Package where + (==) = (==) `on` pkgName + updateSettings :: (Settings -> Settings) -> Package -> Package updateSettings update (Package name path cabal todo) = Package name path cabal (map updateTodo todo) From git at git.haskell.org Thu Oct 26 23:55:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Major rewrite before the first release (6bdb902) Message-ID: <20171026235535.436CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6bdb90260373d6ab3af2836d2e621d60beb13815/ghc >--------------------------------------------------------------- commit 6bdb90260373d6ab3af2836d2e621d60beb13815 Author: Andrey Mokhov Date: Fri Jan 22 02:07:49 2016 +0000 Major rewrite before the first release >--------------------------------------------------------------- 6bdb90260373d6ab3af2836d2e621d60beb13815 README.md | 146 +++++++++++++++++++++++++++++++++++++++----------------------- 1 file changed, 92 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 6bdb90260373d6ab3af2836d2e621d60beb13815 From git at git.haskell.org Thu Oct 26 23:55:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to invoke libtool via bash. (9e731d6) Message-ID: <20171026235537.5AA263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e731d6d7d730b14e805886ca34df7f0bfbac745/ghc >--------------------------------------------------------------- commit 9e731d6d7d730b14e805886ca34df7f0bfbac745 Author: Andrey Mokhov Date: Tue Jan 5 23:43:25 2016 +0000 Try to invoke libtool via bash. See #103. >--------------------------------------------------------------- 9e731d6d7d730b14e805886ca34df7f0bfbac745 src/Rules/IntegerGmp.hs | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 0d5da26..193b43d 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -6,7 +6,6 @@ import GHC import Oracles.Config.Setting import Rules.Actions import Settings.User -import Settings.TargetDirectory integerGmpBase :: FilePath integerGmpBase = "libraries/integer-gmp/gmp" @@ -103,19 +102,19 @@ integerGmpRules = do args <- configureArguments runConfigure integerGmpBuild envs args - -- check whether we need to build in tree gmp - -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` - + -- TODO: currently we configure integerGmp package twice -- optimise runConfigure (pkgPath integerGmp) [] [] + -- check whether we need to build in tree gmp + -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk then do - putBuild "\n| GMP framework detected and will be used" + putBuild "| GMP framework detected and will be used" copyFile integerGmpLibraryFakeH integerGmpLibraryH else do - putBuild "\n| No GMP framework detected" - runMake integerGmpBuild [] + putBuild "| No GMP framework detected; in tree GMP will be built" + runMake integerGmpBuild ["LIBTOOL=\"bash libtool\""] copyFile integerGmpLibraryInTreeH integerGmpLibraryH -- TODO: why copy library, can we move it instead? From git at git.haskell.org Thu Oct 26 23:55:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement predicates and evaluators. (71be3a8) Message-ID: <20171026235537.D84A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/71be3a823ae81fde9371e93cd9efa9ffbb9a6cea/ghc >--------------------------------------------------------------- commit 71be3a823ae81fde9371e93cd9efa9ffbb9a6cea Author: Andrey Mokhov Date: Wed Feb 11 03:23:27 2015 +0000 Implement predicates and evaluators. >--------------------------------------------------------------- 71be3a823ae81fde9371e93cd9efa9ffbb9a6cea src/Settings.hs | 114 ++++++++++++++++++++++++++++++++++++++++++++------------ src/Targets.hs | 1 + 2 files changed, 92 insertions(+), 23 deletions(-) diff --git a/src/Settings.hs b/src/Settings.hs index aaec2ab..6d25a92 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -7,6 +7,7 @@ module Settings ( import Base import Ways +import Package.Base (Package) import Oracles.Builder data IntegerLibrary = IntegerGmp | IntegerGmp2 | IntegerSimple @@ -34,23 +35,36 @@ instance Monoid (PG p v) where mempty = Epsilon mappend = Overlay +fromList :: [v] -> PG p v +fromList = foldr Sequence Epsilon . map Vertex + +type RewritePG p v = PG p v -> PG p v + data Predicate a = Evaluated Bool -- Evaluated predicate | Parameter a -- To be evaluated later | Not (Predicate a) -- Negate predicate | And (Predicate a) (Predicate a) -- Conjunction | Or (Predicate a) (Predicate a) -- Disjunction --- Evaluator takes a Parameter and attempts to evaluate it. +multiOr :: [Predicate a] -> RewritePG (Predicate a) v +multiOr = Condition . foldr Or (Evaluated False) + +multiAnd :: [Predicate a] -> RewritePG (Predicate a) v +multiAnd = Condition . foldr And (Evaluated True) + +type RewrtePredicate a = Predicate a -> Predicate a + +-- Evaluator takes an argument and attempts to determine its truth. -- Returns Nothing if the attempt fails. type Evaluator a = a -> Maybe Bool -- Monoid instance for evaluators (returns first successful evaluation) instance Monoid (Evaluator a) where mempty = const Nothing - e `mappend` f = \p -> getFirst $ First (e p) <> First (f p) + p `mappend` q = \a -> getFirst $ First (p a) <> First (q a) --- Apply an evalulator to a predicate (partial evaluation, or projection) -apply :: Evaluator a -> Predicate a -> Predicate a +-- Apply an evalulator to a predicate (partial evaluation, or 'projection'). +apply :: Evaluator a -> RewrtePredicate a apply _ p @ (Evaluated _) = p apply e p @ (Parameter q) = case e q of Just bool -> Evaluated bool @@ -59,8 +73,20 @@ apply e (Not p ) = Not (apply e p) apply e (And p q) = And (apply e p) (apply e q) apply e (Or p q) = Or (apply e p) (apply e q) +-- Map over all PG predicates, e.g., apply an evaluator to a given PG. +mapP :: RewrtePredicate a -> RewritePG (Predicate a) v +mapP _ Epsilon = Epsilon +mapP _ v @ (Vertex _) = v +mapP r (Overlay p q) = Overlay (mapP r p) (mapP r q) +mapP r (Sequence p q) = Sequence (mapP r p) (mapP r q) +mapP r (Condition x p) = Condition (r x) (mapP r p) + +project :: Evaluator a -> RewritePG (Predicate a) v +project = mapP . apply + -- Attempt to evaluate a predicate. Returns Nothing if the predicate -- cannot be uniquely evaluated due to remaining parameters. +-- An alternative type: evalPredicate :: Evaluator (Predicate a) evalPredicate :: Predicate a -> Maybe Bool evalPredicate (Evaluated bool) = Just bool evalPredicate (Not p) = not <$> evalPredicate p @@ -80,46 +106,42 @@ evalPredicate (Or p q) q' = evalPredicate q evalPredicate (Parameter _) = Nothing -- cannot evaluate Parameter --- Flatten a PG into a list. Returns Nothing if the given expression +-- Linearise a PG into a list. Returns Nothing if the given expression -- cannot be uniquely evaluated due to remaining parameters. linearise :: PG (Predicate a) v -> Maybe [v] linearise Epsilon = Just [] linearise (Vertex v) = Just [v] -linearise (Overlay p q) = (++) <$> linearise p <*> linearise q +linearise (Overlay p q) = (++) <$> linearise p <*> linearise q -- TODO: union linearise (Sequence p q) = (++) <$> linearise p <*> linearise q linearise (Condition x p) = case evalPredicate x of Just True -> linearise p Just False -> Just [] Nothing -> Nothing -(~>) :: PG p v -> PG p v -> PG p v -a ~> b = Sequence a b +-- GHC build specific -type PGP p v = PG (Predicate p) v +type Expression a = PG (Predicate BuildParameter) a +type Rewrite a = Expression a -> Expression a -disjuction :: [a] -> (a -> Predicate p) -> PGP p v -> PGP p v -disjuction [] _ = id -disjuction (a:as) convert = Condition (foldr Or (convert a) $ map convert as) +--type ArgsExpression = Expression String +--type Args = Expression String --- GHC build specific +--args :: [String] -> Args +--args = fromList -data BuildParameter = WhenPackage FilePath +data BuildParameter = WhenPackage Package | WhenBuilder Builder | WhenStage Stage | WhenWay Way - | WhenFile FilePath + | WhenFile FilePattern | WhenKeyValue String String -- from config files -type Expression a = PGP BuildParameter a - -type Rewrite a = Expression a -> Expression a - -type ArgsExpression = Expression String +-- Predicates alternatives :: (b -> BuildParameter) -> [b] -> Rewrite a -alternatives p bs = disjuction bs (Parameter . p) +alternatives p = multiOr . map (Parameter . p) -whenPackages :: [FilePath] -> Rewrite a +whenPackages :: [Package] -> Rewrite a whenPackages = alternatives WhenPackage whenBuilders :: [Builder] -> Rewrite a @@ -134,7 +156,7 @@ unlessStage stage = Condition (Not $ Parameter $ WhenStage stage) whenWays :: [Way] -> Rewrite a whenWays = alternatives WhenWay -whenFiles :: [FilePath] -> Rewrite a +whenFiles :: [FilePattern] -> Rewrite a whenFiles = alternatives WhenFile whenKeyValues :: String -> [String] -> Rewrite a @@ -143,6 +165,52 @@ whenKeyValues key = alternatives (WhenKeyValue key) whenKeyValue :: String -> String -> Rewrite a whenKeyValue key value = whenKeyValues key [value] +-- Evaluators + +packageEvaluator :: Package -> Evaluator BuildParameter +packageEvaluator p (WhenPackage p') = Just $ p == p' +packageEvaluator _ _ = Nothing + +builderEvaluator :: Builder -> Evaluator BuildParameter +builderEvaluator b (WhenBuilder b') = Just $ b == b' +builderEvaluator _ _ = Nothing + +stageEvaluator :: Stage -> Evaluator BuildParameter +stageEvaluator s (WhenStage s') = Just $ s == s' +stageEvaluator _ _ = Nothing + +wayEvaluator :: Way -> Evaluator BuildParameter +wayEvaluator w (WhenWay w') = Just $ w == w' +wayEvaluator _ _ = Nothing + +fileEvaluator :: FilePath -> Evaluator BuildParameter +fileEvaluator file (WhenFile pattern) = Just $ pattern ?== file +fileEvaluator _ _ = Nothing + +keyValueEvaluator :: String -> String -> Evaluator BuildParameter +keyValueEvaluator key value (WhenKeyValue key' value') + | key == key' = Just $ value == value' + | otherwise = Nothing +keyValueEvaluator _ _ _ = Nothing + +setPackage :: Package -> Rewrite a +setPackage = project . packageEvaluator + +setBuilder :: Builder -> Rewrite a +setBuilder = project . builderEvaluator + +setStage :: Stage -> Rewrite a +setStage = project . stageEvaluator + +setWay :: Way -> Rewrite a +setWay = project . wayEvaluator + +setFile :: FilePath -> Rewrite a +setFile = project . fileEvaluator + +setKeyValue :: String -> String -> Rewrite a +setKeyValue key = project . keyValueEvaluator key + whenPackageKey :: Rewrite a whenPackageKey = whenKeyValue "supports-package-key" "YES" . unlessStage Stage0 diff --git a/src/Targets.hs b/src/Targets.hs index bdfb2ee..bc50ed9 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -4,6 +4,7 @@ module Targets ( ) where import Package.Base +import Settings -- These are the packages we build: -- TODO: this should eventually be removed and replaced by the top-level From git at git.haskell.org Thu Oct 26 23:55:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (82a7fa5) Message-ID: <20171026235538.B70323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82a7fa5557590ec395af8cd506d50cb6d4c5805b/ghc >--------------------------------------------------------------- commit 82a7fa5557590ec395af8cd506d50cb6d4c5805b Author: Andrey Mokhov Date: Fri Jan 22 11:39:44 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- 82a7fa5557590ec395af8cd506d50cb6d4c5805b README.md | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index e51e1e0..1f96505 100644 --- a/README.md +++ b/README.md @@ -30,7 +30,7 @@ packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickChe cd ghc git clone git://github.com/snowleopard/shaking-up-ghc shake-build ``` -* Start your first build: +* Start your first build (you might want to enable parallelism with `-j`): ```bash shake-build/build.sh --configure @@ -44,7 +44,8 @@ If you are interested in building in a Cabal sandbox, have a look at `shake-buil Using the build system ---------------------- Once your first build is successful, simply run `shake-build/build.sh` or `shake-build/build.bat` -to rebuild (you no longer need to use the `--configure` flag). Use `-j` flag to enable parallelism. +to rebuild (you no longer need to use the `--configure` flag). Most build artefacts are placed +into `.build` and `inplace` directories. ### Command line flags From git at git.haskell.org Thu Oct 26 23:55:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Another attempt to invoke libtool via bash, see #103. (375d41e) Message-ID: <20171026235540.BB5143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/375d41e7658d6b4f91c15eaf1ac74ce37b720f1b/ghc >--------------------------------------------------------------- commit 375d41e7658d6b4f91c15eaf1ac74ce37b720f1b Author: Andrey Mokhov Date: Wed Jan 6 00:51:54 2016 +0000 Another attempt to invoke libtool via bash, see #103. >--------------------------------------------------------------- 375d41e7658d6b4f91c15eaf1ac74ce37b720f1b src/Rules/Actions.hs | 6 +++--- src/Rules/IntegerGmp.hs | 2 +- src/Rules/Libffi.hs | 4 ++-- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 6f116b5..9250357 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -99,15 +99,15 @@ runConfigure dir opts args = do runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] - let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args + quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir] args runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do needBuilder laxDependencies builder path <- builderPath builder - let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ show builder ++ note quietly $ cmd [path] args diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 193b43d..142a9c6 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -114,7 +114,7 @@ integerGmpRules = do copyFile integerGmpLibraryFakeH integerGmpLibraryH else do putBuild "| No GMP framework detected; in tree GMP will be built" - runMake integerGmpBuild ["LIBTOOL=\"bash libtool\""] + runMake integerGmpBuild ["MAKEFLAGS='LIBTOOL=bash\\ libtool'"] copyFile integerGmpLibraryInTreeH integerGmpLibraryH -- TODO: why copy library, can we move it instead? diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 041650f..9d77814 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -91,8 +91,8 @@ libffiRules = do args <- configureArguments runConfigure libffiBuild envs args - runMake libffiBuild [] - runMake libffiBuild ["install"] + runMake libffiBuild ["MAKEFLAGS="] + runMake libffiBuild ["MAKEFLAGS=", "install"] forM_ ["ffi.h", "ffitarget.h"] $ \file -> do let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file From git at git.haskell.org Thu Oct 26 23:55:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor argument expressions. (93e218e) Message-ID: <20171026235541.4831C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/93e218e59d6f0e03ffdcfc691c19548a2e697135/ghc >--------------------------------------------------------------- commit 93e218e59d6f0e03ffdcfc691c19548a2e697135 Author: Andrey Mokhov Date: Wed Apr 8 02:34:02 2015 +0100 Refactor argument expressions. >--------------------------------------------------------------- 93e218e59d6f0e03ffdcfc691c19548a2e697135 src/Expression.hs | 159 ++++++++++++++++++++++++++++++ src/Expression/ArgList.hs | 32 ++++++ src/Expression/PG.hs | 56 +++++++++++ src/Expression/Predicate.hs | 55 +++++++++++ src/Expression/TruthTeller.hs | 16 +++ src/Settings.hs | 220 +++--------------------------------------- 6 files changed, 333 insertions(+), 205 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 93e218e59d6f0e03ffdcfc691c19548a2e697135 From git at git.haskell.org Thu Oct 26 23:55:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add and link to important issues. (3d335e1) Message-ID: <20171026235542.4527F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d335e1eca20caaf40bb8227ffbf85e9a675c187/ghc >--------------------------------------------------------------- commit 3d335e1eca20caaf40bb8227ffbf85e9a675c187 Author: Andrey Mokhov Date: Fri Jan 22 12:16:12 2016 +0000 Add and link to important issues. [skip ci] >--------------------------------------------------------------- 3d335e1eca20caaf40bb8227ffbf85e9a675c187 README.md | 29 +++++++++++++++++++---------- 1 file changed, 19 insertions(+), 10 deletions(-) diff --git a/README.md b/README.md index 1f96505..a368c01 100644 --- a/README.md +++ b/README.md @@ -45,9 +45,9 @@ Using the build system ---------------------- Once your first build is successful, simply run `shake-build/build.sh` or `shake-build/build.bat` to rebuild (you no longer need to use the `--configure` flag). Most build artefacts are placed -into `.build` and `inplace` directories. +into `.build` and `inplace` directories ([#113][build-artefacts-issue]). -### Command line flags +#### Command line flags In addition to standard Shake flags (try `--help`), the build system currently supports several others: @@ -61,13 +61,13 @@ build command; this is the default setting), and `unicorn` (when `normal` just w * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. -### User settings +#### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We use [`src/Settings/User.hs`][user-settings] for the same purpose. Feel free to -experiment. +experiment following the Haddock comments. -### Resetting the build +#### Resetting the build To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. @@ -76,11 +76,11 @@ This is a temporary solution; we are working on proper reset functionality ([#13 Current limitations ------------------- The new build system still lacks many important features: -* We only build `vanilla` way. +* We only build `vanilla` way: [#4][dynamic-issue], [#186][profiling-issue]. * Documentation is broken: [#98][haddock-issue]. -* Validation is not implemented. -* Build flavours and conventional command line flags are not implemented. -* Cross-compilation is not implemented. +* Validation is not implemented: [#187][validation-issue]. +* Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. +* Cross-compilation is not implemented: [#177][cross-compilation-issue]. How to contribute ----------------- @@ -88,7 +88,8 @@ How to contribute The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note the codebase is very unstable at present and we expect a lot of further refactoring. The documentation is -currently non-existent, but we are working on it. +currently non-existent, but we are working on it: [#55][comments-issue], +[#56][doc-issue]. Acknowledgements ---------------- @@ -108,8 +109,16 @@ helped me endure and enjoy the project. [issues]: https://github.com/snowleopard/shaking-up-ghc/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild +[build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs [reset-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/131 +[dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 +[profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 +[validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 +[flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 +[cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 +[comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 +[doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 [contributors]: https://github.com/snowleopard/shaking-up-ghc/graphs/contributors From git at git.haskell.org Thu Oct 26 23:55:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (da61b39) Message-ID: <20171026235544.B797F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da61b39228f39feb4d201d9505bd1ef02dc6518e/ghc >--------------------------------------------------------------- commit da61b39228f39feb4d201d9505bd1ef02dc6518e Author: Andrey Mokhov Date: Wed Jan 6 01:20:21 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- da61b39228f39feb4d201d9505bd1ef02dc6518e README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 43b74be..90f6422 100644 --- a/README.md +++ b/README.md @@ -59,7 +59,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system run the build script with `-B` flag. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). +To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). How to contribute From git at git.haskell.org Thu Oct 26 23:55:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename src/Expression.hs -> src/Expression/Base.hs. (35cab30) Message-ID: <20171026235544.DFE7D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/35cab3032cf80af4274dfd6563a821bcc34e4618/ghc >--------------------------------------------------------------- commit 35cab3032cf80af4274dfd6563a821bcc34e4618 Author: Andrey Mokhov Date: Wed Apr 8 23:04:19 2015 +0100 Rename src/Expression.hs -> src/Expression/Base.hs. >--------------------------------------------------------------- 35cab3032cf80af4274dfd6563a821bcc34e4618 src/{Expression.hs => Expression/Base.hs} | 0 src/Settings.hs | 5 ++++- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Expression.hs b/src/Expression/Base.hs similarity index 100% rename from src/Expression.hs rename to src/Expression/Base.hs diff --git a/src/Settings.hs b/src/Settings.hs index 2885282..e70e41c 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -22,8 +22,11 @@ integerLibraryName = case integerLibrary of buildHaddock :: Bool buildHaddock = True +supportsPackageKey :: Guard +supportsPackageKey = keyYes "supports-package-key" + whenPackageKey :: Guard -whenPackageKey = keyYes "supports-package-key" <> notStage Stage0 +whenPackageKey = supportsPackageKey <> notStage Stage0 depSettings :: Settings depSettings = From git at git.haskell.org Thu Oct 26 23:55:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (e2b0201) Message-ID: <20171026235545.D808B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2b0201a4b8694955bd2701deaca22c4be15c155/ghc >--------------------------------------------------------------- commit e2b0201a4b8694955bd2701deaca22c4be15c155 Author: Andrey Mokhov Date: Fri Jan 22 12:18:22 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- e2b0201a4b8694955bd2701deaca22c4be15c155 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index a368c01..9845e17 100644 --- a/README.md +++ b/README.md @@ -95,7 +95,7 @@ Acknowledgements ---------------- I started this project as part of my 6-month research visit to Microsoft -Research in Cambridge. It was funded by Newcastle University, EPSRC, and +Research in Cambridge, which was funded by Newcastle University, EPSRC, and Microsoft Research. I would like to thank Simon Peyton Jones, Neil Mitchell and Simon Marlow for kick-starting the project and for their guidance. Last but not least, big thanks to the project [contributors][contributors], who From git at git.haskell.org Thu Oct 26 23:55:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Begin translating the code using expressions. (d7cd023) Message-ID: <20171026235548.98B453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d7cd023a4cc538bcde70d1872af41e4eafc77248/ghc >--------------------------------------------------------------- commit d7cd023a4cc538bcde70d1872af41e4eafc77248 Author: Andrey Mokhov Date: Thu Apr 9 02:50:25 2015 +0100 Begin translating the code using expressions. >--------------------------------------------------------------- d7cd023a4cc538bcde70d1872af41e4eafc77248 src/Expression/PGPredicate.hs | 62 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 62 insertions(+) diff --git a/src/Expression/PGPredicate.hs b/src/Expression/PGPredicate.hs new file mode 100644 index 0000000..45bb97f --- /dev/null +++ b/src/Expression/PGPredicate.hs @@ -0,0 +1,62 @@ +{-# LANGUAGE FlexibleInstances #-} + +module Expression.PGPredicate ( + module Expression.PG, + module Expression.Predicate, + PGPredicate (..), + fence, (?), ite, + whenExists, + remove, + project, + linearise + ) where + +import Control.Applicative +import Expression.PG +import Expression.Predicate + +type PGPredicate p v = PG (Predicate p) v + +fence :: PGPredicate p v -> PGPredicate p v -> PGPredicate p v +fence = Sequence + +(?) :: Predicate p -> PGPredicate p v -> PGPredicate p v +(?) = Condition + +ite :: Predicate p -> PGPredicate p v -> PGPredicate p v -> PGPredicate p v +ite p t f = Overlay (p ? t) (Not p ? f) + +infixl 7 ? + +whenExists :: Eq v => v -> PGPredicate p v -> Predicate p +whenExists _ Epsilon = Evaluated False +whenExists a (Vertex b) = Evaluated $ a == b +whenExists a (Overlay l r) = Or (whenExists a l) (whenExists a r) +whenExists a (Sequence l r) = Or (whenExists a l) (whenExists a r) +whenExists a (Condition x r) = And x (whenExists a r) + +remove :: Eq v => v -> PGPredicate p v -> PGPredicate p v +remove _ Epsilon = Epsilon +remove a v @ (Vertex b) + | a == b = Epsilon + | otherwise = v +remove a (Overlay l r) = Overlay (remove a l) (remove a r) +remove a (Sequence l r) = Sequence (remove a l) (remove a r) +remove a (Condition x r) = Condition x (remove a r) + +-- Partially evaluate a PG using a truth-teller (compute a 'projection') +project :: TruthTeller p -> PGPredicate p v -> PGPredicate p v +project t = mapP (evaluate t) + +-- Linearise a PG into a list. Returns Nothing if the given expression +-- cannot be uniquely evaluated due to remaining parameters. +-- Overlay subexpressions are evaluated in arbitrary order. +linearise :: PGPredicate p v -> Maybe [v] +linearise Epsilon = Just [] +linearise (Vertex v) = Just [v] +linearise (Overlay l r) = (++) <$> linearise l <*> linearise r -- TODO: union +linearise (Sequence l r) = (++) <$> linearise l <*> linearise r +linearise (Condition x r) = case tellTruth x of + Just True -> linearise r + Just False -> Just [] + Nothing -> Nothing From git at git.haskell.org Thu Oct 26 23:55:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a rule for libraries/integer-gmp/gmp/gmp.h, see #103. (d716ae5) Message-ID: <20171026235548.9E8873A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d716ae544c182207ba70b3becdb11bcc3aca5a73/ghc >--------------------------------------------------------------- commit d716ae544c182207ba70b3becdb11bcc3aca5a73 Author: Andrey Mokhov Date: Wed Jan 6 01:50:10 2016 +0000 Add a rule for libraries/integer-gmp/gmp/gmp.h, see #103. >--------------------------------------------------------------- d716ae544c182207ba70b3becdb11bcc3aca5a73 src/Rules/IntegerGmp.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 142a9c6..2b9bbd9 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -116,7 +116,8 @@ integerGmpRules = do putBuild "| No GMP framework detected; in tree GMP will be built" runMake integerGmpBuild ["MAKEFLAGS='LIBTOOL=bash\\ libtool'"] - copyFile integerGmpLibraryInTreeH integerGmpLibraryH + copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryInTreeH + copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryH -- TODO: why copy library, can we move it instead? copyFile (integerGmpBuild -/- ".libs/libgmp.a") integerGmpLibrary @@ -126,3 +127,5 @@ integerGmpRules = do runBuilder Ranlib [integerGmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" + + integerGmpLibraryInTreeH %> \_ -> need [integerGmpLibraryH] From git at git.haskell.org Thu Oct 26 23:55:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a link to milestones. (1b08589) Message-ID: <20171026235549.8F5043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b08589b98dc1c354042d62c004640d394485c39/ghc >--------------------------------------------------------------- commit 1b08589b98dc1c354042d62c004640d394485c39 Author: Andrey Mokhov Date: Fri Jan 22 12:26:18 2016 +0000 Add a link to milestones. [skip ci] >--------------------------------------------------------------- 1b08589b98dc1c354042d62c004640d394485c39 README.md | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 9845e17..b80b621 100644 --- a/README.md +++ b/README.md @@ -82,6 +82,8 @@ The new build system still lacks many important features: * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. +Check out [milestones] to see when we hope to resolve the above limitations. + How to contribute ----------------- @@ -95,7 +97,7 @@ Acknowledgements ---------------- I started this project as part of my 6-month research visit to Microsoft -Research in Cambridge, which was funded by Newcastle University, EPSRC, and +Research Cambridge, which was funded by Newcastle University, EPSRC, and Microsoft Research. I would like to thank Simon Peyton Jones, Neil Mitchell and Simon Marlow for kick-starting the project and for their guidance. Last but not least, big thanks to the project [contributors][contributors], who @@ -119,6 +121,7 @@ helped me endure and enjoy the project. [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 +[milestones]: https://github.com/snowleopard/shaking-up-ghc/milestones [comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 [doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 [contributors]: https://github.com/snowleopard/shaking-up-ghc/graphs/contributors From git at git.haskell.org Thu Oct 26 23:55:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish translation of Data.hs argument lists. (8cf38ba) Message-ID: <20171026235552.B9CF63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8cf38baf8224a14a2fc167bfc0776123d1bd1167/ghc >--------------------------------------------------------------- commit 8cf38baf8224a14a2fc167bfc0776123d1bd1167 Author: Andrey Mokhov Date: Fri Apr 10 02:05:27 2015 +0100 Finish translation of Data.hs argument lists. >--------------------------------------------------------------- 8cf38baf8224a14a2fc167bfc0776123d1bd1167 src/Expression/ArgList.hs | 7 +- src/Expression/Base.hs | 190 ++++++++++++++++++++++++++++++++++++------ src/Expression/PG.hs | 41 ++------- src/Expression/PGPredicate.hs | 18 +--- src/Oracles/Builder.hs | 1 + src/Settings.hs | 129 ++++++++++++++++++++++------ src/Targets.hs | 148 ++++++++++++++++---------------- 7 files changed, 363 insertions(+), 171 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 8cf38baf8224a14a2fc167bfc0776123d1bd1167 From git at git.haskell.org Thu Oct 26 23:55:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds osx to the list of operatin systems in the travis.yml (f466624) Message-ID: <20171026235553.044C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4666240df45766aa8d8e38af4a0d88d50e9325c/ghc >--------------------------------------------------------------- commit f4666240df45766aa8d8e38af4a0d88d50e9325c Author: Moritz Angermann Date: Wed Jan 6 11:50:02 2016 +0800 Adds osx to the list of operatin systems in the travis.yml This should fix #111. >--------------------------------------------------------------- f4666240df45766aa8d8e38af4a0d88d50e9325c .travis.yml | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.travis.yml b/.travis.yml index 9079fa9..58e23cd 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,5 +1,9 @@ sudo: false +os: + - linux + - osx + matrix: include: - env: From git at git.haskell.org Thu Oct 26 23:55:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement clean target. (a730d9b) Message-ID: <20171026235553.7A4443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a730d9bd25ac701cd9b6bd22b4f4fb14f88902dd/ghc >--------------------------------------------------------------- commit a730d9bd25ac701cd9b6bd22b4f4fb14f88902dd Author: Andrey Mokhov Date: Fri Jan 22 12:57:14 2016 +0000 Implement clean target. Fix #131. >--------------------------------------------------------------- a730d9bd25ac701cd9b6bd22b4f4fb14f88902dd shaking-up-ghc.cabal | 1 + src/Main.hs | 2 ++ src/Rules/Clean.hs | 30 ++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 2 +- 4 files changed, 34 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index b6a42d5..bd21d28 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -39,6 +39,7 @@ executable ghc-shake , Rules , Rules.Actions , Rules.Cabal + , Rules.Clean , Rules.Compile , Rules.Config , Rules.Data diff --git a/src/Main.hs b/src/Main.hs index f83734c..7321f88 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -6,6 +6,7 @@ import qualified Base import CmdLineFlag import qualified Rules import qualified Rules.Cabal +import qualified Rules.Clean import qualified Rules.Config import qualified Rules.Generate import qualified Rules.Gmp @@ -24,6 +25,7 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do rules :: Rules () rules = mconcat [ Rules.Cabal.cabalRules + , Rules.Clean.cleanRules , Rules.Config.configRules , Rules.Generate.copyRules , Rules.Generate.generateRules diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs new file mode 100644 index 0000000..6ab5309 --- /dev/null +++ b/src/Rules/Clean.hs @@ -0,0 +1,30 @@ +module Rules.Clean (cleanRules) where + +import Base +import Package +import Rules.Generate +import Settings.Packages +import Settings.Paths +import Settings.User +import Stage + +cleanRules :: Rules () +cleanRules = do + "clean" ~> do + putBuild $ "| Remove files in " ++ buildRootPath ++ "..." + removeFilesAfter buildRootPath ["//*"] + putBuild $ "| Remove files in " ++ programInplacePath ++ "..." + removeFilesAfter programInplacePath ["//*"] + putBuild $ "| Remove files in inplace/lib..." + removeFilesAfter "inplace/lib" ["//*"] + putBuild $ "| Remove files in " ++ derivedConstantsPath ++ "..." + removeFilesAfter derivedConstantsPath ["//*"] + forM_ includesDependencies $ \file -> do + putBuild $ "| Remove " ++ file + removeFileIfExists file + putBuild $ "| Remove files generated by ghc-cabal..." + forM_ knownPackages $ \pkg -> + forM_ [Stage0 ..] $ \stage -> do + let dir = pkgPath pkg -/- targetDirectory stage pkg + removeDirectoryIfExists dir + putSuccess $ "| Done. " diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index c5386e4..73b160a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( generatePackageCode, generateRules, installTargets, copyRules, - derivedConstantsPath, generatedDependencies + includesDependencies, derivedConstantsPath, generatedDependencies ) where import Base From git at git.haskell.org Thu Oct 26 23:55:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:55:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (08136dd) Message-ID: <20171026235556.4CFAC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/08136ddd1386ec9b7a4b79779d51f388606fce0b/ghc >--------------------------------------------------------------- commit 08136ddd1386ec9b7a4b79779d51f388606fce0b Author: Andrey Mokhov Date: Sun Apr 12 02:13:23 2015 +0100 Clean up. >--------------------------------------------------------------- 08136ddd1386ec9b7a4b79779d51f388606fce0b src/Expression/ArgList.hs | 37 ---- src/Expression/{Base.hs => Args.hs} | 12 -- src/Expression/Base.hs | 345 ++++++++++-------------------------- src/Expression/Build.hs | 238 +++++++++++++++++++++++++ src/Expression/PG.hs | 31 ++-- src/Expression/PGPredicate.hs | 46 ----- src/Expression/Predicate.hs | 68 ++----- src/Expression/TruthTeller.hs | 16 -- src/Settings.hs | 116 ++++++------ src/Targets.hs | 3 +- 10 files changed, 433 insertions(+), 479 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 08136ddd1386ec9b7a4b79779d51f388606fce0b From git at git.haskell.org Thu Oct 26 23:56:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Work on the top-level build structure. (8bdc64c) Message-ID: <20171026235621.8116A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8bdc64ccbf49838c6a90635cb45683bcc609a4b3/ghc >--------------------------------------------------------------- commit 8bdc64ccbf49838c6a90635cb45683bcc609a4b3 Author: Andrey Mokhov Date: Sat Apr 18 01:42:25 2015 +0100 Work on the top-level build structure. >--------------------------------------------------------------- 8bdc64ccbf49838c6a90635cb45683bcc609a4b3 src/Expression/Base.hs | 31 +++++++++---- src/Expression/Resolve.hs | 110 ++++++++++++++++++++++++++++++++-------------- src/Main.hs | 37 ++++++++++------ src/Targets.hs | 2 +- src/Ways.hs | 2 +- 5 files changed, 127 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 8bdc64ccbf49838c6a90635cb45683bcc609a4b3 From git at git.haskell.org Thu Oct 26 23:56:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use install. (59c09b8) Message-ID: <20171026235621.B8AE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59c09b8be58c2f1fd8e75788d9bccf63e9ff1458/ghc >--------------------------------------------------------------- commit 59c09b8be58c2f1fd8e75788d9bccf63e9ff1458 Author: Moritz Angermann Date: Wed Jan 6 12:43:17 2016 +0800 Use install. >--------------------------------------------------------------- 59c09b8be58c2f1fd8e75788d9bccf63e9ff1458 .travis.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4a2179d..6e1bf5b 100644 --- a/.travis.yml +++ b/.travis.yml @@ -19,8 +19,7 @@ addons: before_install: - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated ghc || brew upgrade ghc; fi - - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated cabal-install || brew upgrade cabal-install; fi + - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi - PATH="$HOME/.cabal/bin:$PATH" - PATH="/opt/ghc/$GHCVER/bin:$PATH" From git at git.haskell.org Thu Oct 26 23:56:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #190 from joehillen/stack (ce71b6d) Message-ID: <20171026235622.AFCD13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ce71b6dde7bf070e847b9d04673508b4d42066df/ghc >--------------------------------------------------------------- commit ce71b6dde7bf070e847b9d04673508b4d42066df Merge: 0bde9c1 4aa3bb6 Author: Andrey Mokhov Date: Sat Jan 23 00:36:13 2016 +0000 Merge pull request #190 from joehillen/stack Allow building ghc-shake with stack >--------------------------------------------------------------- ce71b6dde7bf070e847b9d04673508b4d42066df .gitignore | 1 + build.cabal.sh | 6 +++--- build.cabal.sh => build.stack.sh | 21 +++++++-------------- stack.yaml | 35 +++++++++++++++++++++++++++++++++++ 4 files changed, 46 insertions(+), 17 deletions(-) From git at git.haskell.org Thu Oct 26 23:56:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement buildPackageData rule. (4ad4d41) Message-ID: <20171026235625.35E543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f/ghc >--------------------------------------------------------------- commit 4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f Author: Andrey Mokhov Date: Mon Apr 20 01:25:09 2015 +0100 Implement buildPackageData rule. >--------------------------------------------------------------- 4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f src/Base.hs | 4 + src/Expression/Args.hs | 179 +++++++++++++++++++++++++++++++++++ src/Expression/Base.hs | 228 +++------------------------------------------ src/Expression/Build.hs | 174 +++------------------------------- src/Expression/PG.hs | 61 +++++------- src/Expression/Project.hs | 133 ++++++++++++++++++++++++++ src/Expression/Resolve.hs | 75 +++++++++------ src/Expression/Simplify.hs | 119 ++++++++++++++++++++++- src/Main.hs | 65 ++----------- src/Oracles/Builder.hs | 61 ++++++------ src/Oracles/PackageData.hs | 11 ++- src/Package.hs | 7 +- src/PackageBuild.hs | 67 ------------- src/Rules.hs | 41 ++++++++ src/Rules/Data.hs | 184 ++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 11 +++ src/Settings.hs | 116 ++--------------------- src/Switches.hs | 78 ++++++++++++++++ src/Targets.hs | 55 +++++------ 19 files changed, 933 insertions(+), 736 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 4ad4d412b05e8b1ba8830ecfacc08ecd32b15c8f From git at git.haskell.org Thu Oct 26 23:56:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install alex, happy; adjust path only on ghc/cabal path only on linux. (17306dc) Message-ID: <20171026235625.8B5523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/17306dc5a8e5ff70b3a0b973915fc6e6ec5cc3b7/ghc >--------------------------------------------------------------- commit 17306dc5a8e5ff70b3a0b973915fc6e6ec5cc3b7 Author: Moritz Angermann Date: Wed Jan 6 12:50:09 2016 +0800 Install alex, happy; adjust path only on ghc/cabal path only on linux. >--------------------------------------------------------------- 17306dc5a8e5ff70b3a0b973915fc6e6ec5cc3b7 .travis.yml | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 6e1bf5b..64e8597 100644 --- a/.travis.yml +++ b/.travis.yml @@ -5,7 +5,9 @@ os: - osx env: - - CABALVER=1.22 GHCVER=7.10.3 + matrix: + linux: + - CABALVER=1.22 GHCVER=7.10.3 addons: apt: @@ -20,10 +22,10 @@ addons: before_install: - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi - + - if [ $TRAVIS_OS_NAME == osx ]; then cabal install alex happy; fi + - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/ghc/$GHCVER/bin:$PATH"; fi + - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/cabal/$CABALVER/bin:$PATH"; fi - PATH="$HOME/.cabal/bin:$PATH" - - PATH="/opt/ghc/$GHCVER/bin:$PATH" - - PATH="/opt/cabal/$CABALVER/bin:$PATH" - export PATH - env From git at git.haskell.org Thu Oct 26 23:56:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on build.stack.sh. (cf5d338) Message-ID: <20171026235626.6F6323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf5d3387e960ae9ebdec5c08113e84195618dc3f/ghc >--------------------------------------------------------------- commit cf5d3387e960ae9ebdec5c08113e84195618dc3f Author: Andrey Mokhov Date: Sat Jan 23 00:42:04 2016 +0000 Add a note on build.stack.sh. [skip ci] >--------------------------------------------------------------- cf5d3387e960ae9ebdec5c08113e84195618dc3f README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 602148b..b8fd40f 100644 --- a/README.md +++ b/README.md @@ -39,7 +39,7 @@ On Windows, use `build.bat` instead and pass an extra flag to configure (also se ```bash shake-build/build.bat --configure=--enable-tarballs-autodownload ``` -If you are interested in building in a Cabal sandbox, have a look at `shake-build/build.cabal.sh`. +If you are interested in building in a Cabal sandbox or using Stack, have a look at `shake-build/build.cabal.sh` and `shake-build/build.stack.sh` scripts. Using the build system ---------------------- From git at git.haskell.org Thu Oct 26 23:56:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up Expression package. (51028b8) Message-ID: <20171026235629.01CC23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/51028b8d25146dde9cc45d92912acb498388c9d7/ghc >--------------------------------------------------------------- commit 51028b8d25146dde9cc45d92912acb498388c9d7 Author: Andrey Mokhov Date: Sat Apr 25 00:50:55 2015 +0100 Clean up Expression package. >--------------------------------------------------------------- 51028b8d25146dde9cc45d92912acb498388c9d7 src/Expression/Base.hs | 16 ++--- src/Expression/Build.hs | 121 -------------------------------- src/Expression/BuildExpression.hs | 21 ++++++ src/Expression/BuildPredicate.hs | 51 ++++++++++++++ src/Expression/{Args.hs => Derived.hs} | 123 ++++++++++++++++++++------------- src/Expression/Project.hs | 10 +-- src/Expression/Resolve.hs | 6 +- src/Expression/Settings.hs | 55 +++++++++++++++ src/Expression/Simplify.hs | 5 +- src/Targets.hs | 1 - 10 files changed, 222 insertions(+), 187 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 51028b8d25146dde9cc45d92912acb498388c9d7 From git at git.haskell.org Thu Oct 26 23:56:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reorder os and env (9ff8773) Message-ID: <20171026235629.2F9A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ff8773943c628ec660bd59de0e48e1eb9dd2e22/ghc >--------------------------------------------------------------- commit 9ff8773943c628ec660bd59de0e48e1eb9dd2e22 Author: Moritz Angermann Date: Wed Jan 6 12:55:34 2016 +0800 Reorder os and env >--------------------------------------------------------------- 9ff8773943c628ec660bd59de0e48e1eb9dd2e22 .travis.yml | 13 +++++-------- 1 file changed, 5 insertions(+), 8 deletions(-) diff --git a/.travis.yml b/.travis.yml index 64e8597..72e2f80 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,13 +1,10 @@ sudo: false -os: - - linux - - osx - -env: - matrix: - linux: - - CABALVER=1.22 GHCVER=7.10.3 +matrix: + include: + - os: linux + env: CABALVER=1.22 GHCVER=7.10.3 + - os: osx addons: apt: From git at git.haskell.org Thu Oct 26 23:56:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move GMP build to Stage1. (3f74e8b) Message-ID: <20171026235630.0B5253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3f74e8bf2c170740f46279b98659d57b47721afa/ghc >--------------------------------------------------------------- commit 3f74e8bf2c170740f46279b98659d57b47721afa Author: Andrey Mokhov Date: Sat Jan 23 15:36:20 2016 +0000 Move GMP build to Stage1. Should make AppVeyor CI fit in 1 hr. >--------------------------------------------------------------- 3f74e8bf2c170740f46279b98659d57b47721afa src/Rules/Generate.hs | 13 +++++++------ src/Rules/Gmp.hs | 15 ++++----------- src/Settings/Builders/Ghc.hs | 5 ++++- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Paths.hs | 2 +- 5 files changed, 17 insertions(+), 20 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 73b160a..f329228 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -43,11 +43,12 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -defaultDependencies :: [FilePath] -defaultDependencies = concat +defaultDependencies :: Stage -> [FilePath] +defaultDependencies stage = concat [ includesDependencies - , libffiDependencies - , gmpDependencies ] + , libffiDependencies ] + ++ + [ gmpLibraryH | stage > Stage0 ] ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> @@ -67,7 +68,7 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = [ platformH stage ] - ++ defaultDependencies ++ derivedConstantsDependencies + ++ defaultDependencies stage ++ derivedConstantsDependencies ++ fmap ((targetPath stage compiler -/- "build") -/-) [ "primop-vector-uniques.hs-incl" , "primop-data-decl.hs-incl" @@ -91,7 +92,7 @@ generatedDependencies stage pkg | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = libffiDependencies ++ includesDependencies ++ derivedConstantsDependencies - | stage == Stage0 = defaultDependencies + | stage == Stage0 = defaultDependencies Stage0 | otherwise = [] -- The following generators and corresponding source extensions are supported: diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index b6bfdf0..b384b68 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,6 +1,4 @@ -module Rules.Gmp ( - gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH, gmpDependencies - ) where +module Rules.Gmp (gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH) where import qualified System.Directory as IO @@ -17,7 +15,7 @@ gmpBase :: FilePath gmpBase = "libraries/integer-gmp/gmp" gmpTarget :: PartialTarget -gmpTarget = PartialTarget Stage0 integerGmp +gmpTarget = PartialTarget Stage1 integerGmp gmpObjects :: FilePath gmpObjects = gmpBuildPath -/- "objs" @@ -34,9 +32,6 @@ gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" gmpLibraryFakeH :: FilePath gmpLibraryFakeH = gmpBase -/- "ghc-gmp.h" -gmpDependencies :: [FilePath] -gmpDependencies = [gmpLibraryH] - gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] @@ -77,11 +72,11 @@ gmpRules = do liftIO $ removeFiles gmpBuildPath ["//*"] - envs <- configureEnvironment -- TODO: without the optimisation below we configure integerGmp package -- twice -- think how this can be optimised (shall we solve #18 first?) -- TODO: this is a hacky optimisation: we do not rerun configure of -- integerGmp package if we detect the results of the previous run + envs <- configureEnvironment unlessM (liftIO . IO.doesFileExist $ gmpBase -/- "config.mk") $ do args <- configureIntGmpArguments runConfigure (pkgPath integerGmp) envs args @@ -148,6 +143,4 @@ gmpRules = do runBuilder Ranlib [gmpLibrary] - putSuccess "| Successfully built custom library 'integer-gmp'" - - -- gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] + putSuccess "| Successfully built custom library 'gmp'" diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 3537aed..c79fc50 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -19,12 +19,15 @@ import Settings.Builders.Common (cIncludeArgs) ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput + stage <- getStage way <- getWay let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs - gmpLibs <- lift $ readFileLines gmpLibNameCache + gmpLibs <- if stage > Stage0 && buildProg + then lift $ readFileLines gmpLibNameCache -- TODO: use oracles + else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs , arg "-H32m" diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 9ad160f..0640e52 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -16,7 +16,7 @@ integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" gmpIncludeDir <- getSetting GmpIncludeDir - gmpLibDir <- getSetting GmpLibDir + gmpLibDir <- getSetting GmpLibDir mconcat [ builder GhcCabal ? mconcat [ (null gmpIncludeDir && null gmpLibDir) ? diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 3e9fec9..ed217a8 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -39,7 +39,7 @@ pkgGhciLibraryFile stage pkg componentId = -- This is the build directory for in-tree GMP library gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage0/gmp" +gmpBuildPath = buildRootPath -/- "stage1/gmp" -- GMP library names extracted from integer-gmp.buildinfo gmpLibNameCache :: FilePath From git at git.haskell.org Thu Oct 26 23:56:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make PG and BuildPredicate abstract. (353b02b) Message-ID: <20171026235633.621623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/353b02bdb3999067523c30436c8a4c3dcbc2b770/ghc >--------------------------------------------------------------- commit 353b02bdb3999067523c30436c8a4c3dcbc2b770 Author: Andrey Mokhov Date: Mon Apr 27 02:36:01 2015 +0100 Make PG and BuildPredicate abstract. >--------------------------------------------------------------- 353b02bdb3999067523c30436c8a4c3dcbc2b770 src/Expression/BuildExpression.hs | 34 ++++++++++++ src/Expression/BuildPredicate.hs | 64 +++++++++++++++++++++- src/Expression/Derived.hs | 4 +- src/Expression/PG.hs | 110 +++++++++++++++++++++---------------- src/Expression/Predicate.hs | 20 ++++++- src/Expression/Project.hs | 112 +------------------------------------- src/Expression/Resolve.hs | 57 ++++++------------- src/Expression/Settings.hs | 44 ++++++++++++++- src/Expression/Simplify.hs | 109 +++++++++++++++++++------------------ src/Rules/Data.hs | 2 +- src/Settings.hs | 2 +- src/Targets.hs | 4 +- 12 files changed, 300 insertions(+), 262 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 353b02bdb3999067523c30436c8a4c3dcbc2b770 From git at git.haskell.org Thu Oct 26 23:56:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: run cabal update (e18abef) Message-ID: <20171026235633.A20293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e18abefe7f05cda6f758eb3b46f283e431aaa590/ghc >--------------------------------------------------------------- commit e18abefe7f05cda6f758eb3b46f283e431aaa590 Author: Moritz Angermann Date: Wed Jan 6 12:55:41 2016 +0800 run cabal update >--------------------------------------------------------------- e18abefe7f05cda6f758eb3b46f283e431aaa590 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 72e2f80..b21b89e 100644 --- a/.travis.yml +++ b/.travis.yml @@ -19,6 +19,7 @@ addons: before_install: - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi + - if [ $TRAVIS_OS_NAME == osx ]; then cabal update; fi - if [ $TRAVIS_OS_NAME == osx ]; then cabal install alex happy; fi - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/ghc/$GHCVER/bin:$PATH"; fi - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/cabal/$CABALVER/bin:$PATH"; fi From git at git.haskell.org Thu Oct 26 23:56:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move libffi build to Stage1. (48d0ee0) Message-ID: <20171026235633.EFCEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/48d0ee0e397abc8fb447db6e3c858b4d5be2f863/ghc >--------------------------------------------------------------- commit 48d0ee0e397abc8fb447db6e3c858b4d5be2f863 Author: Andrey Mokhov Date: Sat Jan 23 17:04:11 2016 +0000 Move libffi build to Stage1. Should make AppVeyor CI fit in 1 hr. >--------------------------------------------------------------- 48d0ee0e397abc8fb447db6e3c858b4d5be2f863 src/Rules/Generate.hs | 15 ++++++--------- src/Rules/Libffi.hs | 5 ++--- 2 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index f329228..d98527c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -43,13 +43,6 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -defaultDependencies :: Stage -> [FilePath] -defaultDependencies stage = concat - [ includesDependencies - , libffiDependencies ] - ++ - [ gmpLibraryH | stage > Stage0 ] - ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> [ "GHC/PrimopWrappers.hs" @@ -68,7 +61,10 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = [ platformH stage ] - ++ defaultDependencies stage ++ derivedConstantsDependencies + ++ includesDependencies + ++ [ gmpLibraryH | stage > Stage0 ] + ++ filter (const $ stage > Stage0) libffiDependencies + ++ derivedConstantsDependencies ++ fmap ((targetPath stage compiler -/- "build") -/-) [ "primop-vector-uniques.hs-incl" , "primop-data-decl.hs-incl" @@ -86,13 +82,14 @@ compilerDependencies stage = , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] +-- TODO: Turn this into a FilePaths expression generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = libffiDependencies ++ includesDependencies ++ derivedConstantsDependencies - | stage == Stage0 = defaultDependencies Stage0 + | stage == Stage0 = includesDependencies | otherwise = [] -- The following generators and corresponding source extensions are supported: diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0f4e05a..d2742eb 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -19,10 +19,10 @@ libffiDependencies :: [FilePath] libffiDependencies = (rtsBuildPath -/-) <$> [ "ffi.h", "ffitarget.h" ] libffiTarget :: PartialTarget -libffiTarget = PartialTarget Stage0 libffi +libffiTarget = PartialTarget Stage1 libffi libffiBuild :: FilePath -libffiBuild = buildRootPath -/- "stage0/libffi" +libffiBuild = buildRootPath -/- "stage1/libffi" libffiLibrary :: FilePath libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" @@ -33,7 +33,6 @@ fixLibffiMakefile = . replace "@toolexeclibdir@" "$(libdir)" . replace "@INSTALL@" "$(subst ../install-sh,C:/msys/home/chEEtah/ghc/install-sh, at INSTALL@)" - -- TODO: remove code duplication (see Settings/Builders/GhcCabal.hs) configureEnvironment :: Action [CmdOption] configureEnvironment = do From git at git.haskell.org Thu Oct 26 23:56:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: New refactoring started: switching to a shallow embedding. (a827aa5) Message-ID: <20171026235637.433A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a827aa580a188603ec8b0b30f58b254dfef8081e/ghc >--------------------------------------------------------------- commit a827aa580a188603ec8b0b30f58b254dfef8081e Author: Andrey Mokhov Date: Sun May 10 01:32:56 2015 +0100 New refactoring started: switching to a shallow embedding. >--------------------------------------------------------------- a827aa580a188603ec8b0b30f58b254dfef8081e src/Expression.hs | 84 ++++++++++++++++ src/Expression/Base.hs | 21 ---- src/Expression/BuildExpression.hs | 55 ---------- src/Expression/BuildPredicate.hs | 113 --------------------- src/Expression/Derived.hs | 204 -------------------------------------- src/Expression/PG.hs | 132 ------------------------ src/Expression/Predicate.hs | 39 -------- src/Expression/Project.hs | 27 ----- src/Expression/Resolve.hs | 100 ------------------- src/Expression/Settings.hs | 186 +++++++++++++++++----------------- src/Expression/Simplify.hs | 127 ------------------------ 11 files changed, 178 insertions(+), 910 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 a827aa580a188603ec8b0b30f58b254dfef8081e From git at git.haskell.org Thu Oct 26 23:56:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:56:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Can we put addons and before_install into the include? (a5aa58f) Message-ID: <20171026235637.BBD423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5aa58f81ceab822e035cb17f25bc05dec8dc092/ghc >--------------------------------------------------------------- commit a5aa58f81ceab822e035cb17f25bc05dec8dc092 Author: Moritz Angermann Date: Wed Jan 6 13:03:06 2016 +0800 Can we put addons and before_install into the include? >--------------------------------------------------------------- a5aa58f81ceab822e035cb17f25bc05dec8dc092 .travis.yml | 40 +++++++++++++++++++++------------------- 1 file changed, 21 insertions(+), 19 deletions(-) diff --git a/.travis.yml b/.travis.yml index b21b89e..5c5708c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -4,28 +4,30 @@ matrix: include: - os: linux env: CABALVER=1.22 GHCVER=7.10.3 + addons: + apt: + packages: + - ghc-7.10.3 + - alex-3.1.4 + - happy-1.19.5 + - cabal-install-1.22 + - zlib1g-dev + sources: hvr-ghc + before_install: + - PATH="/opt/ghc/$GHCVER/bin:$PATH" + - PATH="/opt/cabal/$CABALVER/bin:$PATH" + - PATH="$HOME/.cabal/bin:$PATH" + - export PATH - os: osx - -addons: - apt: - packages: - - ghc-7.10.3 - - alex-3.1.4 - - happy-1.19.5 - - cabal-install-1.22 - - zlib1g-dev - sources: hvr-ghc + before_install: + - brew update + - brew install ghc cabal-install + - cabal update + - cabal install alex happy + - PATH="$HOME/.cabal/bin:$PATH" + - export PATH before_install: - - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi - - if [ $TRAVIS_OS_NAME == osx ]; then cabal update; fi - - if [ $TRAVIS_OS_NAME == osx ]; then cabal install alex happy; fi - - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/ghc/$GHCVER/bin:$PATH"; fi - - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/cabal/$CABALVER/bin:$PATH"; fi - - PATH="$HOME/.cabal/bin:$PATH" - - export PATH - - env - ghc --version - cabal --version From git at git.haskell.org Thu Oct 26 23:58:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename cabal, add build script. (da29ac9) Message-ID: <20171026235803.931653A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da29ac914723944acd7c65709fa93c0dce198571/ghc >--------------------------------------------------------------- commit da29ac914723944acd7c65709fa93c0dce198571 Author: Andrey Mokhov Date: Wed Jan 6 19:21:43 2016 +0000 Rename cabal, add build script. See #110. [skip ci] >--------------------------------------------------------------- da29ac914723944acd7c65709fa93c0dce198571 .appveyor.yml | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index fa03afe..93375e0 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,10 +8,14 @@ install: - bash -lc "mkdir /usr/local" - bash -lc "mkdir /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + - ren C:\msys64\usr\local\bin\cabal-1.22.0.0-i386-unknown-mingw32.exe C:\msys64\usr\local\bin\cabal.exe - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" + - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" build_script: - - echo "test" + - bash -lc "cd /home/ghc && ./boot" + - bash -lc "cd /home/ghc && ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && ./shake-build/build.bat" test: off From git at git.haskell.org Thu Oct 26 23:58:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add validate target. (a9f9876) Message-ID: <20171026235803.A7AC83A5EC@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9f98769fbd07b93342cd263f6dcf3c6e51e4afd/ghc >--------------------------------------------------------------- commit a9f98769fbd07b93342cd263f6dcf3c6e51e4afd Author: Andrey Mokhov Date: Fri Jan 29 01:18:51 2016 +0000 Add validate target. See #187. >--------------------------------------------------------------- a9f98769fbd07b93342cd263f6dcf3c6e51e4afd src/Rules/Actions.hs | 16 ++++++++++++---- src/Test.hs | 6 +++++- 2 files changed, 17 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 0e4961f..d85e0dc 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,8 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, - moveDirectory, fixFile, runConfigure, runMake, applyPatch, renderLibrary, - renderProgram, runBuilder, makeExecutable + moveDirectory, fixFile, runConfigure, runMake, runMakeVerbose, applyPatch, + renderLibrary, renderProgram, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -111,7 +111,13 @@ runConfigure dir opts args = do opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] runMake :: FilePath -> [String] -> Action () -runMake dir args = do +runMake = runMakeWithVerbosity False + +runMakeVerbose :: FilePath -> [String] -> Action () +runMakeVerbose = runMakeWithVerbosity True + +runMakeWithVerbosity :: Bool -> FilePath -> [String] -> Action () +runMakeWithVerbosity verbose dir args = do need [dir -/- "Makefile"] path <- builderPath Make @@ -125,7 +131,9 @@ runMake dir args = do let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ fixPath ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args + if verbose + then cmd Shell fixPath ["-C", dir] args + else quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do diff --git a/src/Test.hs b/src/Test.hs index 547e286..06c82eb 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -7,12 +7,16 @@ import GHC (rts, libffi) import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory +import Rules.Actions import Settings.Packages import Settings.User -- TODO: clean up after testing testRules :: Rules () -testRules = +testRules = do + "validate" ~> do + runMakeVerbose "testsuite/tests" ["fast"] + "test" ~> do let quote s = "\"" ++ s ++ "\"" yesNo x = quote $ if x then "YES" else "NO" From git at git.haskell.org Thu Oct 26 23:58:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install project dependencies, pass -j --no-progress to build.bat (5afac8a) Message-ID: <20171026235807.32F543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5afac8aceaa4a656231fbd03b61a03a38327ee78/ghc >--------------------------------------------------------------- commit 5afac8aceaa4a656231fbd03b61a03a38327ee78 Author: Andrey Mokhov Date: Wed Jan 6 19:35:18 2016 +0000 Install project dependencies, pass -j --no-progress to build.bat See #110. [skip ci] >--------------------------------------------------------------- 5afac8aceaa4a656231fbd03b61a03a38327ee78 .appveyor.yml | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 93375e0..47210eb 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -12,10 +12,9 @@ install: - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" + - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" - bash -lc "cd /home/ghc && ./configure --enable-tarballs-autodownload" - - bash -lc "cd /home/ghc && ./shake-build/build.bat" - -test: off + - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:58:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an agenda for the meeting on 16 June 2015. (8f6fe55) Message-ID: <20171026235807.7C7AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f6fe558bf383f83f8cc8aa1d1e1858c25c06765/ghc >--------------------------------------------------------------- commit 8f6fe558bf383f83f8cc8aa1d1e1858c25c06765 Author: Andrey Mokhov Date: Tue Jun 16 01:08:05 2015 +0100 Add an agenda for the meeting on 16 June 2015. >--------------------------------------------------------------- 8f6fe558bf383f83f8cc8aa1d1e1858c25c06765 doc/meeting-16-June-2015.txt | 83 ++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 83 insertions(+) diff --git a/doc/meeting-16-June-2015.txt b/doc/meeting-16-June-2015.txt new file mode 100644 index 0000000..a407bb9 --- /dev/null +++ b/doc/meeting-16-June-2015.txt @@ -0,0 +1,83 @@ +Shaking up GHC (3rd shake) meeting, 16 June 2015 + +Things to discuss: +================================================ + +1. Parameters of the build system that are still not user configurable: + +* targetDirectory (Targets.hs) -- is this important? Can be moved to +UserSettings.hs, but will clutter it (what is the good balance of +what we expose to users?). Can be made into a conditional expression +similar to userWays, userPackages and userSettings, but is it worth it? + +* knownPackages (Targets.hs) -- fix by adding knownUserPackages? A nasty +import cycle is then created between Targets.hs and UserSettings.hs + +* integerLibraryImpl (Switches.hs) -- fix by having three integer library +packages in Targets.hs and choosing which one to build in userPackages, e.g.: + +userPackages = remove [integerGmp2] <> append [integerSimple] + +* In general, should Targets.hs be editable by users as well? Ideally, +there should only be one place for user to look: UserSettings.hs. + +* Any other parameters I missed which should be user configurable? + +================================================ + +2. When predicates are moved from configuration files to UserSettings we +no longer track their state in oracles. This may lead to inconsistent +state of the build system. A more general problem: how do we accurately +track changes in the build systems, specifically in UserSettings.hs? + +================================================ + +3. Discuss if the current design makes recording provenance information +possible. (Should probably be implemented only after the first successful +complete build though.) + +============================================== + +4. I'd like interpret/interpretDiff to be total functions. It should be +possible to check at compile which questions a given environment can +answer and raise an error if an expression needs to know more. + +For example, consider an environment envS that can only answer 'getStage' +question, and environment envSP that can answer questions 'getStage' and +'getPackage'. Now consider two expressions + +exprS = stage0 ? foo + +exprSP = stage0 ? package base ? bar + +Now I'd like the following to produce a compile error: + +interpret envS exprSP + +However, all other combinations should be fine: + +interpret envS exprS +interpret envSP exprS +interpret envSP exprSP + +I played with some possible solutions using type classes, but they all +seem clumsy/heavy. + +Hence, for now I have: + +data Environment = Environment + { + getStage :: Stage, + getBuilder :: Builder, + getPackage :: Package + } + +defaultEnvironment :: Environment +defaultEnvironment = Environment + { + getStage = error "Stage not set in the environment", + getBuilder = error "Builder not set in the environment", + getPackage = error "Package not set in the environment" + } + +which leads to a lot of partial functions all over the build system. \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:58:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on Stage2 GHC, ghc-pkg and hpc in validate target. (304840f) Message-ID: <20171026235807.9916C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/304840f8073ef7b3369601a97afb0605326e79e3/ghc >--------------------------------------------------------------- commit 304840f8073ef7b3369601a97afb0605326e79e3 Author: Andrey Mokhov Date: Sat Jan 30 23:58:57 2016 +0000 Depend on Stage2 GHC, ghc-pkg and hpc in validate target. See #187. [skip ci] >--------------------------------------------------------------- 304840f8073ef7b3369601a97afb0605326e79e3 src/Builder.hs | 2 ++ src/Test.hs | 3 +++ 2 files changed, 5 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 71399a7..80fc4ba 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -124,6 +124,8 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath +-- TODO: split into two functions: needBuilder (without laxDependencies) and +-- unsafeNeedBuilder (with the laxDependencies parameter) -- | Make sure a builder exists on the given path and rebuild it if out of date. -- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). diff --git a/src/Test.hs b/src/Test.hs index 06c82eb..a79c9fc 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -15,6 +15,9 @@ import Settings.User testRules :: Rules () testRules = do "validate" ~> do + needBuilder False $ Ghc Stage2 -- TODO: get rid of False parameters + needBuilder False $ GhcPkg Stage1 + needBuilder False $ Hpc runMakeVerbose "testsuite/tests" ["fast"] "test" ~> do From git at git.haskell.org Thu Oct 26 23:58:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #189, clear PWD so we can be sure it has the Unix-style path even on Windows (fce6921) Message-ID: <20171026235815.A0FB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fce6921fca6c3dd14f9a1b0a4c0940db2a8f7841/ghc >--------------------------------------------------------------- commit fce6921fca6c3dd14f9a1b0a4c0940db2a8f7841 Author: Neil Mitchell Date: Mon Feb 1 20:57:56 2016 +0000 #189, clear PWD so we can be sure it has the Unix-style path even on Windows >--------------------------------------------------------------- fce6921fca6c3dd14f9a1b0a4c0940db2a8f7841 src/Environment.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Environment.hs b/src/Environment.hs index fd207ed..e674f83 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -11,6 +11,11 @@ setupEnvironment = do -- ghc-cabal refuses to work when GHC_PACKAGE_PATH is set (e.g. by Stack) unsetEnv "GHC_PACKAGE_PATH" + -- in MinGW if PWD is set to a Windows "C:\\" style path then configure + -- `pwd` will return the Windows path, and then modifying $PATH will fail. + -- See https://github.com/snowleopard/shaking-up-ghc/issues/189 for details. + unsetEnv "PWD" + -- On Windows, some path variables start a prefix like "C:\\" which may -- lead to failures of scripts such as autoreconf. One particular variable -- which causes issues is ACLOCAL_PATH. At the moment we simply reset it From git at git.haskell.org Thu Oct 26 23:58:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix cabal path, create directory for cabal if it does not exist. (3e42d47) Message-ID: <20171026235818.5A6753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e42d47e05153bee9fe430e8e91e58c0bea12ea0/ghc >--------------------------------------------------------------- commit 3e42d47e05153bee9fe430e8e91e58c0bea12ea0 Author: Andrey Mokhov Date: Wed Jan 6 22:11:00 2016 +0000 Fix cabal path, create directory for cabal if it does not exist. See #110. [skip ci] >--------------------------------------------------------------- 3e42d47e05153bee9fe430e8e91e58c0bea12ea0 .appveyor.yml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f70a821..eb57bd8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,21 +1,22 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" cache: - - "C:\\msys64\home\cabal" + - "C:\\msys64\\home\\cabal" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir /usr/local" - - bash -lc "mkdir /usr/local/bin" + - bash -lc "mkdir -p /home/cabal" + - bash -lc "mkdir -p /usr/local" + - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - bash -lc "cabal --config-file=/home/cabal update" - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal \install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:58:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename appendCcArgs to ccArgs. (56cf235) Message-ID: <20171026235818.D1CFA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56cf235d4dd89316597abb5024af57756b1fc47e/ghc >--------------------------------------------------------------- commit 56cf235d4dd89316597abb5024af57756b1fc47e Author: Andrey Mokhov Date: Tue Jun 16 07:52:33 2015 +0100 Rename appendCcArgs to ccArgs. >--------------------------------------------------------------- 56cf235d4dd89316597abb5024af57756b1fc47e src/Settings/Util.hs | 6 +++--- src/Targets.hs | 2 +- src/UserSettings.hs | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 74190ec..e9433a2 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -4,7 +4,7 @@ module Settings.Util ( -- Primitive settings elements arg, argM, args, argConfig, argStagedConfig, argConfigList, argStagedConfigList, - appendCcArgs, + ccArgs, -- argBuilderPath, argStagedBuilderPath, -- argPackageKey, argPackageDeps, argPackageDepKeys, argSrcDirs, -- argIncludeDirs, argDepIncludeDirs, @@ -48,8 +48,8 @@ argStagedConfigList key = do argConfigList (stagedKey stage key) -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal -appendCcArgs :: [String] -> Settings -appendCcArgs args = do +ccArgs :: [String] -> Settings +ccArgs args = do stage <- asks getStage mconcat [ builder (Gcc stage) ? append args , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args diff --git a/src/Targets.hs b/src/Targets.hs index 4bbb963..068e767 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -88,7 +88,7 @@ customPackageSettings = mconcat [ package integerLibrary ? mconcat [ windowsHost ? builder GhcCabal ? arg "--configure-option=--with-intree-gmp" - , appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] ] + , ccArgs ["-Ilibraries/integer-gmp2/gmp"] ] , package base ? builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 3cbf136..52d9678 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -38,7 +38,7 @@ userSettings' = mconcat [ package base ? builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) - , package integerLibrary ? appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] + , package integerLibrary ? ccArgs ["-Ilibraries/integer-gmp2/gmp"] , windowsHost ? package integerLibrary ? From git at git.haskell.org Thu Oct 26 23:58:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #199 from ndmitchell/master (0cf18c9) Message-ID: <20171026235819.116B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0cf18c9864f5524260c6cad87ec390ce06ad20ff/ghc >--------------------------------------------------------------- commit 0cf18c9864f5524260c6cad87ec390ce06ad20ff Merge: 4cc0abb fce6921 Author: Andrey Mokhov Date: Mon Feb 1 21:02:57 2016 +0000 Merge pull request #199 from ndmitchell/master Clear PWD >--------------------------------------------------------------- 0cf18c9864f5524260c6cad87ec390ce06ad20ff src/Environment.hs | 5 +++++ 1 file changed, 5 insertions(+) From git at git.haskell.org Thu Oct 26 23:58:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move cabal folder inside /home/ghc. (3008453) Message-ID: <20171026235822.5619C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3008453094756facfea0d45fcc0b5823c1c54b01/ghc >--------------------------------------------------------------- commit 3008453094756facfea0d45fcc0b5823c1c54b01 Author: Andrey Mokhov Date: Wed Jan 6 22:32:46 2016 +0000 Move cabal folder inside /home/ghc. See #110. [skip ci] >--------------------------------------------------------------- 3008453094756facfea0d45fcc0b5823c1c54b01 .appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index eb57bd8..a3dd1ef 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,22 +1,22 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" cache: - - "C:\\msys64\\home\\cabal" + - "C:\\msys64\\home\\ghc\\.cabal" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /home/cabal" + - bash -lc "mkdir -p /home/ghc/.cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal --config-file=/home/cabal update" - - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" + - bash -lc "cabal --config-file=/home/ghc/.cabal update" + - bash -lc "cabal --config-file=/home/ghc/.cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal \install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/ghc/.cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:58:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finalise meeting agenda. (7d53e6b) Message-ID: <20171026235822.ACAEC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d53e6b43cc5a0280218c12fab1a16bf9fcc2f1c/ghc >--------------------------------------------------------------- commit 7d53e6b43cc5a0280218c12fab1a16bf9fcc2f1c Author: Andrey Mokhov Date: Tue Jun 16 09:53:30 2015 +0100 Finalise meeting agenda. >--------------------------------------------------------------- 7d53e6b43cc5a0280218c12fab1a16bf9fcc2f1c doc/meeting-16-June-2015.txt | 54 ++++++++++++++++++++++++++++++++++++-------- 1 file changed, 44 insertions(+), 10 deletions(-) diff --git a/doc/meeting-16-June-2015.txt b/doc/meeting-16-June-2015.txt index bd2b94f..d58b541 100644 --- a/doc/meeting-16-June-2015.txt +++ b/doc/meeting-16-June-2015.txt @@ -13,45 +13,76 @@ similar to userWays, userPackages and userSettings, but is it worth it? * knownPackages (Targets.hs) -- fix by adding knownUserPackages? A nasty import cycle is then created between Targets.hs and UserSettings.hs. Possible solution: add file Settings/Targets.hs which will actually put two things -together similar to what's done with userWays, userPackages and userSettings. +together similar to how it's done with userWays, userPackages and userSettings. * integerLibraryImpl (Switches.hs) -- fix by having three integer library packages in Targets.hs and choosing which one to build in userPackages, e.g.: userPackages = remove [integerGmp2] <> append [integerSimple] -* In general, should Targets.hs be editable by users as well? Ideally, -there should only be one place for user to look: UserSettings.hs. +(Maybe a useful pattern: replace a b = remove a <> append b.) + +* In general, should Targets.hs (or any other file) be editable by users? +Ideally, there should only be one place for users to look: UserSettings.hs. * Any other parameters I missed which should be user configurable? ================================================ 2. When predicates (e.g. buildHaddock) are moved from configuration files to -UserSettings we no longer track their state in oracles. This may lead to an +UserSettings.hs we no longer track their state in oracles. This may lead to an inconsistent state of the build system. This is a special case of a more general problem: how do we accurately track changes in the build system, specifically in UserSettings.hs? Although in general this is a hard problem, this special -case may be easier to solve: just channel everything exported from +case may be easier to solve: e.g., just channel everything exported from UserSettings.hs through oracles? Another alternative which was discussed previously: pass the final lists of arguments through oracles. Care must -be taken though as final command lines can be as large as 5Mb! +be taken though as final command lines can be as large as 5Mb and may bloat +the Shake database! ================================================ -3. Discuss if the current design makes recording provenance information +3. Discuss if/how the current approach makes recording provenance information possible. (Should probably be implemented only after the first successful complete build though.) ============================================== -4. I'd like interpret/interpretDiff to be total functions. It should be +4. Duplication of information in knownPackages and packages. + +I'd like to enforce the following invariant: whenever a package is used +in userPackages, it must also be placed in knownPackages/knownUserPackages. + +This feels awkward/redundant. The reason for having knownPackages is that I +need a list of packages outside the Action monad for it to be useable in +packageRules (see Rules.hs). The current solution seems to be the cheapest way +to achieve that. An alternative would be to have one additional implementation +of interpret, which would extract the 'support' from a given expression, i.e. +the set of packages that can occur in a given expression, regardless of how +predicates evaluate (without looking up oracles which live in the Action monad). + +For example, + +interpret' (stage0 ? base <> stage1 ? compiler) == [base, compiler] + +This seems to require a lot of extra code though. Hence redundant knownPackages. + +============================================== + +5. (Just realised that the following is trickier than I thought. Maybe not +worth raising at this meeting if not enough time.) + +I'd like interpret/interpretDiff to be total functions. It should be possible to check at compile which questions a given environment can -answer and raise a *compile* error if the expression needs to know more. +answer and raise a *compile* error if the expression needs to know more. Why +is this useful? For example, I'd like to allow only getStage and +platform-specific predicates in userPackages (since nothing else is known at +this point; one can argue that we should even forbid to use such predicates +when constructing expressions of type Packages). For example, consider an environment envS that can only answer 'getStage' question, and environment envSP that can answer questions 'getStage' and -'getPackage'. Now consider two expressions +'getPackage'. Now consider two expressions: exprS = stage0 ? arg "foo" @@ -106,3 +137,6 @@ getPackage, getBuilder, getFile, getWay. Hence, it may be OK to have only 6 combinations of getters in a type constraint, not 2^5, e.g.: empty, GetStage env, (GetStage env, GetPackage env), etc. +============================================== + + From git at git.haskell.org Thu Oct 26 23:58:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add includesDependencies to primops.txt rule. (1329a94) Message-ID: <20171026235822.D41FB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1329a948ad88a8dec33834a4394024bae715df3b/ghc >--------------------------------------------------------------- commit 1329a948ad88a8dec33834a4394024bae715df3b Author: Andrey Mokhov Date: Tue Feb 2 12:26:45 2016 +0000 Add includesDependencies to primops.txt rule. Fix #201. >--------------------------------------------------------------- 1329a948ad88a8dec33834a4394024bae715df3b src/Rules/Generate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index d98527c..7538470 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -134,7 +134,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = -- TODO: needing platformH is ugly and fragile when (pkg == compiler) $ primopsTxt stage %> \file -> do - need [platformH stage, primopsSource] + need $ [platformH stage, primopsSource] ++ includesDependencies build $ fullTarget target HsCpp [primopsSource] [file] -- TODO: why different folders for generated files? From git at git.haskell.org Thu Oct 26 23:58:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build top-level targets in parallel. (1441846) Message-ID: <20171026235838.E06183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1441846ddc4fa070a8fa9351ec6386b8645b176e/ghc >--------------------------------------------------------------- commit 1441846ddc4fa070a8fa9351ec6386b8645b176e Author: Andrey Mokhov Date: Tue Feb 2 15:17:05 2016 +0000 Build top-level targets in parallel. See #200. >--------------------------------------------------------------- 1441846ddc4fa070a8fa9351ec6386b8645b176e src/Main.hs | 2 +- src/Package.hs | 3 ++- src/Rules.hs | 48 +++++++++++++++++++++++++++++------------------- 3 files changed, 32 insertions(+), 21 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 2c944d4..79601d8 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -36,7 +36,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules , Rules.Perl.perlScriptRules - , Rules.generateTargets + , Rules.topLevelTargets , Rules.packageRules , Selftest.selftestRules , Test.testRules ] diff --git a/src/Package.hs b/src/Package.hs index b34dc02..43eb480 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -21,7 +21,8 @@ newtype PackageName = PackageName { getPackageName :: String } instance Show PackageName where show (PackageName name) = name --- TODO: make PackageType more precise, #12 +-- TODO: Make PackageType more precise, #12 +-- TODO: Turn Program to Program FilePath thereby getting rid of programPath -- | We regard packages as either being libraries or programs. This is -- bit of a convenient lie as Cabal packages can be both, but it works -- for now. diff --git a/src/Rules.hs b/src/Rules.hs index 5f505b3..b22e028 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,10 +1,11 @@ -module Rules (generateTargets, packageRules) where +module Rules (topLevelTargets, packageRules) where import Base import Data.Foldable import Expression import GHC -import Rules.Generate +import Oracles.PackageData +import qualified Rules.Generate import Rules.Package import Rules.Resources import Settings @@ -13,23 +14,32 @@ allStages :: [Stage] allStages = [minBound ..] -- | 'need' all top-level build targets -generateTargets :: Rules () -generateTargets = action $ do - targets <- fmap concat (traverse targetsForStage allStages) - rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla - rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded - need $ targets ++ installTargets ++ [ rtsLib, rtsThrLib ] - -targetsForStage :: Stage -> Action [String] -targetsForStage stage = do - pkgs <- interpretWithStage stage getPackages - let libPkgs = filter isLibrary pkgs \\ [rts, libffi] - libTargets <- fmap concat . forM libPkgs $ \pkg -> do - let target = PartialTarget stage pkg - needHaddock <- interpretPartial target buildHaddock - return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] - let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] - return $ libTargets ++ programTargets +topLevelTargets :: Rules () +topLevelTargets = do + + want $ Rules.Generate.installTargets + + -- TODO: do we want libffiLibrary to be a top-level target? + + action $ do -- TODO: Add support for all rtsWays + rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla + rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded + need [ rtsLib, rtsThrLib ] + + for_ allStages $ \stage -> + for_ (knownPackages \\ [rts, libffi]) $ \pkg -> action $ do + let target = PartialTarget stage pkg + activePackages <- interpretPartial target getPackages + when (pkg `elem` activePackages) $ + if isLibrary pkg + then do -- build a library + ways <- interpretPartial target getLibraryWays + compId <- interpretPartial target $ getPkgData ComponentId + libs <- traverse (pkgLibraryFile stage pkg compId) ways + haddock <- interpretPartial target buildHaddock + need $ libs ++ [ pkgHaddockFile pkg | haddock && stage == Stage1 ] + else do -- otherwise build a program + need [ fromJust $ programPath stage pkg ] -- TODO: drop fromJust packageRules :: Rules () packageRules = do From git at git.haskell.org Thu Oct 26 23:58:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add argWith. (cbda822) Message-ID: <20171026235838.E51593A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbda8225449ac1ed80f64843f4fc58390e113994/ghc >--------------------------------------------------------------- commit cbda8225449ac1ed80f64843f4fc58390e113994 Author: Andrey Mokhov Date: Mon Jul 13 16:42:04 2015 +0100 Add argWith. >--------------------------------------------------------------- cbda8225449ac1ed80f64843f4fc58390e113994 src/Oracles/Builder.hs | 7 +++---- src/Settings/GhcCabal.hs | 20 ++++++++------------ src/Settings/Util.hs | 5 ++++- 3 files changed, 15 insertions(+), 17 deletions(-) diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs index 316217f..1f3e45a 100644 --- a/src/Oracles/Builder.hs +++ b/src/Oracles/Builder.hs @@ -12,8 +12,7 @@ import Oracles.Base import Oracles.Flag import Oracles.Option --- A Builder is an external command invoked in separate process --- by calling Shake.cmd +-- A Builder is an external command invoked in separate process using Shake.cmd -- -- Ghc Stage0 is the bootstrapping compiler -- Ghc StageN, N > 0, is the one built on stage (N - 1) @@ -82,11 +81,11 @@ needBuilder builder = do need [exe] -- Action 'with Gcc' returns '--with-gcc=/path/to/gcc' and needs Gcc -with :: Builder -> Args +with :: Builder -> Action String with builder = do exe <- showArg builder needBuilder builder - return [withBuilderKey builder ++ exe] + return $ withBuilderKey builder ++ exe withBuilderKey :: Builder -> String withBuilderKey builder = case builder of diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index d8eda6a..db8fd6e 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -25,18 +25,18 @@ cabalSettings = builder GhcCabal ? do , arg $ pkgPath pkg , arg $ targetDirectory stage pkg , dllSettings - , with' $ Ghc stage - , with' $ GhcPkg stage + , argWith $ Ghc stage + , argWith $ GhcPkg stage , stage0 ? bootPackageDbSettings , librarySettings - , configKeyNonEmpty "hscolour" ? with' HsColour -- TODO: generalise? + , configKeyNonEmpty "hscolour" ? argWith HsColour -- TODO: generalise? , configureSettings , stage0 ? packageConstraints - , with' $ Gcc stage - , notStage Stage0 ? with' Ld - , with' Ar - , with' Alex - , with' Happy ] -- TODO: reorder with's + , argWith $ Gcc stage + , notStage Stage0 ? argWith Ld + , argWith Ar + , argWith Alex + , argWith Happy ] -- TODO: reorder argWiths -- TODO: Isn't vanilla always built? If yes, some conditions are redundant. librarySettings :: Settings @@ -90,10 +90,6 @@ bootPackageDbSettings = do dllSettings :: Settings dllSettings = arg "" --- TODO: remove -with' :: Builder -> Settings -with' builder = appendM $ with builder - packageConstraints :: Settings packageConstraints = do pkgs <- fromDiffExpr packages diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 4b22be4..d7bfa49 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -2,7 +2,7 @@ module Settings.Util ( -- Primitive settings elements - arg, argM, args, + arg, argM, args, argWith, argConfig, argStagedConfig, argConfigList, argStagedConfigList, ccArgs, -- argBuilderPath, argStagedBuilderPath, @@ -28,6 +28,9 @@ argM = appendM . fmap return args :: [String] -> Settings args = append +argWith :: Builder -> Settings +argWith = argM . with + argConfig :: String -> Settings argConfig = appendM . fmap return . askConfig From git at git.haskell.org Thu Oct 26 23:58:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to use an older cabal version. (05b4a6e) Message-ID: <20171026235840.4FDB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/05b4a6e3c481e08317678edf8e5aa21e7f658271/ghc >--------------------------------------------------------------- commit 05b4a6e3c481e08317678edf8e5aa21e7f658271 Author: Andrey Mokhov Date: Thu Jan 7 01:01:32 2016 +0000 Try to use an older cabal version. See #110. [skip ci] >--------------------------------------------------------------- 05b4a6e3c481e08317678edf8e5aa21e7f658271 .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 19236d4..4d54924 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -10,8 +10,9 @@ install: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" + # - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + # - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" + - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.20.0.3/cabal-1.20.0.3-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "cabal update -v3" - bash -lc "cabal install -j --prefix=/usr/local alex happy" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp From git at git.haskell.org Thu Oct 26 23:58:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track mk/config.h (af2d086) Message-ID: <20171026235842.687813A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/af2d08616055124477b86b14f9f602b2c306a768/ghc >--------------------------------------------------------------- commit af2d08616055124477b86b14f9f602b2c306a768 Author: Andrey Mokhov Date: Tue Feb 2 15:41:50 2016 +0000 Track mk/config.h See #200. >--------------------------------------------------------------- af2d08616055124477b86b14f9f602b2c306a768 src/Rules/Config.hs | 5 +++-- src/Rules/Generators/GhcAutoconfH.hs | 2 +- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index eea61c6..f258674 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -3,16 +3,17 @@ module Rules.Config (configRules) where import Base import CmdLineFlag import Rules.Actions +import Rules.Generators.GhcAutoconfH configRules :: Rules () configRules = do -- We always rerun the configure script in this mode, because the flags -- passed to it can affect the contents of system.config file. - [configFile, "settings"] &%> \[cfg, settings] -> do + [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do alwaysRerun case cmdConfigure of RunConfigure args -> do - need [ settings <.> "in" ] + need [ settings <.> "in", cfgH <.> "in" ] runConfigure "." [] [args] SkipConfigure -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" diff --git a/src/Rules/Generators/GhcAutoconfH.hs b/src/Rules/Generators/GhcAutoconfH.hs index d6e783f..9d93744 100644 --- a/src/Rules/Generators/GhcAutoconfH.hs +++ b/src/Rules/Generators/GhcAutoconfH.hs @@ -1,4 +1,4 @@ -module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH) where +module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH, configH) where import Base import Expression From git at git.haskell.org Thu Oct 26 23:58:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (f62f166) Message-ID: <20171026235842.67FDE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f62f166802cf0aa26ce72bb29b073d184897a512/ghc >--------------------------------------------------------------- commit f62f166802cf0aa26ce72bb29b073d184897a512 Author: Andrey Mokhov Date: Mon Jul 13 16:56:48 2015 +0100 Clean up. >--------------------------------------------------------------- f62f166802cf0aa26ce72bb29b073d184897a512 src/Settings/GhcCabal.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index db8fd6e..8e1a8cf 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -10,7 +10,7 @@ import Util import Package import Targets import Switches -import Expression hiding (when, liftIO) +import Expression hiding (liftIO) import Settings.Ways import Settings.Util import Settings.Packages @@ -29,14 +29,14 @@ cabalSettings = builder GhcCabal ? do , argWith $ GhcPkg stage , stage0 ? bootPackageDbSettings , librarySettings - , configKeyNonEmpty "hscolour" ? argWith HsColour -- TODO: generalise? + , configKeyNonEmpty "hscolour" ? argWith HsColour , configureSettings , stage0 ? packageConstraints , argWith $ Gcc stage , notStage Stage0 ? argWith Ld , argWith Ar , argWith Alex - , argWith Happy ] -- TODO: reorder argWiths + , argWith Happy ] -- TODO: Isn't vanilla always built? If yes, some conditions are redundant. librarySettings :: Settings @@ -84,9 +84,9 @@ bootPackageDbSettings = do sourcePath <- lift $ askConfig "ghc-source-path" arg $ "--package-db=" ++ sourcePath "libraries/bootstrapping.conf" --- this is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument --- * otherwise, we must collapse it into one space-separated string +-- This is a positional argument, hence: +-- * if it is empty, we need to emit one empty string argument; +-- * otherwise, we must collapse it into one space-separated string. dllSettings :: Settings dllSettings = arg "" From git at git.haskell.org Thu Oct 26 23:58:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to use stack instead of cabal. (d314d4f) Message-ID: <20171026235843.CD9673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d314d4f902566fe3cd14e6426ba985226f1df49e/ghc >--------------------------------------------------------------- commit d314d4f902566fe3cd14e6426ba985226f1df49e Author: Andrey Mokhov Date: Thu Jan 7 01:34:53 2016 +0000 Try to use stack instead of cabal. See #110. [skip ci] >--------------------------------------------------------------- d314d4f902566fe3cd14e6426ba985226f1df49e .appveyor.yml | 17 +++++------------ 1 file changed, 5 insertions(+), 12 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 4d54924..7410a5e 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,24 +1,17 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -# cache: -# - "C:\\msys64\\home\\cabal" - install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" + - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 + - 7z x stack.zip stack.exe + - stack exec -- pacman -S --noconfirm gcc binutils p7zip git + - stack install -v3 -j --prefix=/usr/local alex happy - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /usr/local" - - bash -lc "mkdir -p /usr/local/bin" - # - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - # - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.20.0.3/cabal-1.20.0.3-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - - bash -lc "cabal update -v3" - - bash -lc "cabal install -j --prefix=/usr/local alex happy" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build - - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" + - stack install --only-dependencies build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:58:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add targetPath. (35d9a07) Message-ID: <20171026235845.CBCEF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/35d9a0726b9751c29c8f0250bd925f84074cc3b2/ghc >--------------------------------------------------------------- commit 35d9a0726b9751c29c8f0250bd925f84074cc3b2 Author: Andrey Mokhov Date: Mon Jul 13 22:24:50 2015 +0100 Add targetPath. >--------------------------------------------------------------- 35d9a0726b9751c29c8f0250bd925f84074cc3b2 src/Rules.hs | 4 +--- src/Rules/Data.hs | 8 ++++---- src/Settings/GhcCabal.hs | 1 + src/Settings/GhcPkg.hs | 4 +--- src/Settings/TargetDirectory.hs | 6 +++++- 5 files changed, 12 insertions(+), 11 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 852a6cf..ce204ea 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -6,7 +6,6 @@ module Rules ( import Base hiding (arg, args, Args) import Control.Monad -import Package import Expression import Rules.Package import Settings.Packages @@ -19,8 +18,7 @@ generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do pkgs <- interpret (stageTarget stage) packages forM_ pkgs $ \pkg -> do - let dir = targetDirectory stage pkg - need [pkgPath pkg dir "package-data.mk"] + need [targetPath stage pkg "package-data.mk"] -- TODO: add Stage2 (compiler only?) packageRules :: Rules () diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index d608fea..a18a097 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -18,9 +18,9 @@ buildPackageData :: Target -> Rules () buildPackageData target = let stage = getStage target pkg = getPackage target - dir = pkgPath pkg targetDirectory stage pkg + path = targetPath stage pkg in - (dir ) <$> + (path ) <$> [ "package-data.mk" , "haddock-prologue.txt" , "inplace-pkg-config" @@ -31,7 +31,7 @@ buildPackageData target = ] &%> \_ -> do let configure = pkgPath pkg "configure" -- TODO: 1) how to automate this? 2) handle multiple files? - newEnv = target { getFile = dir "package-data.mk" } + newEnv = target { getFile = path "package-data.mk" } -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac @@ -39,7 +39,7 @@ buildPackageData target = run' newEnv GhcCabal -- TODO: when (registerPackage settings) $ run' newEnv (GhcPkg stage) - postProcessPackageData $ dir "package-data.mk" + postProcessPackageData $ path "package-data.mk" -- TODO: This should probably go to Oracles.Builder run' :: Target -> Builder -> Action () diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 8e1a8cf..578c264 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -106,6 +106,7 @@ packageConstraints = do args $ concatMap (\c -> ["--constraint", c]) $ constraints -- TODO: should be in a different file +-- TODO: put all validating options together in one file ccSettings :: Settings ccSettings = validating ? do let gccGe46 = liftM not gccLt46 diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index d5fb21e..601d2b8 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -3,7 +3,6 @@ module Settings.GhcPkg ( ) where import Base hiding (arg, args) -import Package import Switches import Expression hiding (when, liftIO) import Settings.Util @@ -15,9 +14,8 @@ ghcPkgSettings :: Settings ghcPkgSettings = do pkg <- asks getPackage stage <- asks getStage - let dir = pkgPath pkg targetDirectory stage pkg builder (GhcPkg stage) ? mconcat [ arg "update" , arg "--force" , stage0 ? bootPackageDbSettings - , arg $ dir "inplace-pkg-config" ] + , arg $ targetPath stage pkg "inplace-pkg-config" ] diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 83e1d0e..d8eb067 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,5 +1,5 @@ module Settings.TargetDirectory ( - targetDirectory + targetDirectory, targetPath ) where import Base @@ -9,3 +9,7 @@ import UserSettings -- User can override the default target directory settings given below targetDirectory :: Stage -> Package -> FilePath targetDirectory = userTargetDirectory + +-- Path to the target directory from GHC source root +targetPath :: Stage -> Package -> FilePath +targetPath stage pkg = pkgPath pkg targetDirectory stage pkg From git at git.haskell.org Thu Oct 26 23:58:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track mk/config.h.in (adfff77) Message-ID: <20171026235845.CE2613A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/adfff77a8843662c4d5034076702101443460deb/ghc >--------------------------------------------------------------- commit adfff77a8843662c4d5034076702101443460deb Author: Andrey Mokhov Date: Tue Feb 2 15:52:51 2016 +0000 Track mk/config.h.in See #200. >--------------------------------------------------------------- adfff77a8843662c4d5034076702101443460deb src/Rules/Config.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index f258674..89434cb 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -20,6 +20,6 @@ configRules = do ++ "Run the configure script either manually or via the " ++ "build system by passing --configure[=ARGS] flag." - "configure" %> \_ -> do + ["configure", configH <.> "in"] &%> \_ -> do putBuild "| Running boot..." quietly $ cmd (EchoStdout False) "perl boot" From git at git.haskell.org Thu Oct 26 23:58:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install ghc-7.10.3 before using stack. (ccf97ae) Message-ID: <20171026235847.4CA1D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccf97ae74f3cbfaaa0484d12af82231832e2620f/ghc >--------------------------------------------------------------- commit ccf97ae74f3cbfaaa0484d12af82231832e2620f Author: Andrey Mokhov Date: Thu Jan 7 01:40:09 2016 +0000 Install ghc-7.10.3 before using stack. See #110. [skip ci] >--------------------------------------------------------------- ccf97ae74f3cbfaaa0484d12af82231832e2620f .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7410a5e..f282d5b 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -5,9 +5,9 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 - 7z x stack.zip stack.exe + - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - stack install -v3 -j --prefix=/usr/local alex happy - - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build From git at git.haskell.org Thu Oct 26 23:58:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do a full build on both Travis instances. (be9a21c) Message-ID: <20171026235849.7F4D93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/be9a21c630f2d8585ba2c349cc97eb8f749abc80/ghc >--------------------------------------------------------------- commit be9a21c630f2d8585ba2c349cc97eb8f749abc80 Author: Andrey Mokhov Date: Tue Feb 2 19:13:55 2016 +0000 Do a full build on both Travis instances. 1000th commit! >--------------------------------------------------------------- be9a21c630f2d8585ba2c349cc97eb8f749abc80 .travis.yml | 7 ++----- 1 file changed, 2 insertions(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 84bb380..cf2f1cb 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: false matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 addons: apt: packages: @@ -21,7 +21,6 @@ matrix: - cabal update - os: osx - env: TARGET=inplace/bin/ghc-stage1 before_install: - brew update - brew install ghc cabal-install @@ -30,9 +29,7 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH - install: - - env - ghc --version - cabal --version @@ -64,7 +61,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET + - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick cache: directories: From git at git.haskell.org Thu Oct 26 23:58:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add argsHashOracle for tracking changes in the build system. (196430d) Message-ID: <20171026235849.7E4773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/196430d4a0647e7258429e59caad0400151bb8ef/ghc >--------------------------------------------------------------- commit 196430d4a0647e7258429e59caad0400151bb8ef Author: Andrey Mokhov Date: Tue Jul 14 11:16:34 2015 +0100 Add argsHashOracle for tracking changes in the build system. >--------------------------------------------------------------- 196430d4a0647e7258429e59caad0400151bb8ef doc/meeting-16-June-2015.txt | 3 ++- src/Base.hs | 8 +++++++- src/Expression.hs | 16 ++++++++++++++++ src/Main.hs | 4 +--- src/Oracles.hs | 5 +---- src/Oracles/ArgsHash.hs | 22 ++++++++++++++++++++++ src/Oracles/Builder.hs | 8 +++++++- src/Package.hs | 10 ++++++++++ src/Rules.hs | 3 ++- src/Rules/Data.hs | 16 ++++++++++++---- src/Rules/Oracles.hs | 11 +++++++++++ src/Ways.hs | 13 +++++++++++-- 12 files changed, 102 insertions(+), 17 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 196430d4a0647e7258429e59caad0400151bb8ef From git at git.haskell.org Thu Oct 26 23:58:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to stack/windows-x86_64. (280b6fa) Message-ID: <20171026235850.DF6493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/280b6fa49b1e3541de7a1bc242a9b953bc00cec1/ghc >--------------------------------------------------------------- commit 280b6fa49b1e3541de7a1bc242a9b953bc00cec1 Author: Andrey Mokhov Date: Thu Jan 7 01:49:02 2016 +0000 Switch to stack/windows-x86_64. See #110. [skip ci] >--------------------------------------------------------------- 280b6fa49b1e3541de7a1bc242a9b953bc00cec1 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f282d5b..a78c02c 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -3,7 +3,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 + - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git From git at git.haskell.org Thu Oct 26 23:58:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out build :: Target -> Action () into Rules/Util.hs. (5db0017) Message-ID: <20171026235853.863C53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5db0017b40d59894d5a6d4d5ba22196f55c47a48/ghc >--------------------------------------------------------------- commit 5db0017b40d59894d5a6d4d5ba22196f55c47a48 Author: Andrey Mokhov Date: Tue Jul 14 11:39:23 2015 +0100 Factor out build :: Target -> Action () into Rules/Util.hs. >--------------------------------------------------------------- 5db0017b40d59894d5a6d4d5ba22196f55c47a48 src/Rules/Data.hs | 21 +++++---------------- src/Rules/Util.hs | 19 +++++++++++++++++++ 2 files changed, 24 insertions(+), 16 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index dabccc1..f3c6064 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -9,11 +9,10 @@ import Package import Expression hiding (when, liftIO) import Oracles.Flag (when) import Oracles.Builder -import Oracles.ArgsHash -import Settings import Settings.GhcPkg import Settings.GhcCabal import Settings.TargetDirectory +import Rules.Util import Util import Ways @@ -35,27 +34,17 @@ buildPackageData target = ] &%> \_ -> do let configure = pkgPath pkg "configure" -- TODO: 1) how to automate this? 2) handle multiple files? - newTarget = target { getFile = path "package-data.mk" } + newTarget = target { getFile = path "package-data.mk" + , getWay = vanilla } -- TODO: think -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac when (doesFileExist $ configure <.> "ac") $ need [configure] - run' newTarget GhcCabal + build $ newTarget { getBuilder = GhcCabal } -- TODO: when (registerPackage settings) $ - run' newTarget (GhcPkg stage) + build $ newTarget { getBuilder = GhcPkg stage } postProcessPackageData $ path "package-data.mk" --- TODO: This should probably go to Oracles.Builder -run' :: Target -> Builder -> Action () -run' target builder = do - let finalTarget = target {getBuilder = builder, getWay = vanilla } - args <- interpret finalTarget settings - putColoured Green (show args) - -- The line below forces the rule to be rerun if the hash has changed - argsHash <- askArgsHash finalTarget - putColoured Yellow (show argsHash) - run builder args - -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- For example, get rid of diff --git a/src/Rules/Util.hs b/src/Rules/Util.hs new file mode 100644 index 0000000..8c9f1c4 --- /dev/null +++ b/src/Rules/Util.hs @@ -0,0 +1,19 @@ +module Rules.Util ( + build + ) where + +import Base +import Util +import Settings +import Expression +import Oracles.Builder +import Oracles.ArgsHash + +build :: Target -> Action () +build target = do + args <- interpret target settings + putColoured Green (show target) + putColoured Green (show args) + -- The line below forces the rule to be rerun if the args hash has changed + argsHash <- askArgsHash target + run (getBuilder target) args From git at git.haskell.org Thu Oct 26 23:58:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Need touchy when calling ghc-stageN, N > 0, on Windows. (fc040db) Message-ID: <20171026235853.CE7F23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fc040dbd72081339e3eff5083dcb13d145f69ded/ghc >--------------------------------------------------------------- commit fc040dbd72081339e3eff5083dcb13d145f69ded Author: Andrey Mokhov Date: Tue Feb 2 22:06:22 2016 +0000 Need touchy when calling ghc-stageN, N > 0, on Windows. >--------------------------------------------------------------- fc040dbd72081339e3eff5083dcb13d145f69ded src/Settings/Builders/Ghc.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index c79fc50..74381eb 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -21,6 +21,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput stage <- getStage way <- getWay + when (stage > Stage0) . lift $ needTouchy let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output buildProg = not (buildObj || buildHi) @@ -44,6 +45,9 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , buildHi ? append ["-fno-code", "-fwrite-interface"] , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] +needTouchy :: Action () +needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy ] + splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do lift $ need [ghcSplit] From git at git.haskell.org Thu Oct 26 23:58:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop extra flags to stack install. (78fee43) Message-ID: <20171026235854.9A0AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/78fee435f395b30199947fd7eefd32bbb25d5804/ghc >--------------------------------------------------------------- commit 78fee435f395b30199947fd7eefd32bbb25d5804 Author: Andrey Mokhov Date: Thu Jan 7 01:59:39 2016 +0000 Drop extra flags to stack install. See #110. [skip ci] >--------------------------------------------------------------- 78fee435f395b30199947fd7eefd32bbb25d5804 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index a78c02c..1b5e3bc 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,7 +7,7 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - stack install -v3 -j --prefix=/usr/local alex happy + - stack install alex happy - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build From git at git.haskell.org Thu Oct 26 23:58:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactoring: Target is now defined in Target.hs, old Targets.hs is dropped. (92ef777) Message-ID: <20171026235857.9A4043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92ef7772b82fe25e48b4f43f752e09cd545d4751/ghc >--------------------------------------------------------------- commit 92ef7772b82fe25e48b4f43f752e09cd545d4751 Author: Andrey Mokhov Date: Tue Jul 14 13:56:52 2015 +0100 Refactoring: Target is now defined in Target.hs, old Targets.hs is dropped. >--------------------------------------------------------------- 92ef7772b82fe25e48b4f43f752e09cd545d4751 src/Expression.hs | 56 +++--------------------------- src/Settings.hs | 2 +- src/{Targets.hs => Settings/Default.hs} | 27 +++++++++++---- src/Settings/GhcCabal.hs | 3 +- src/Settings/Packages.hs | 15 +------- src/Settings/TargetDirectory.hs | 2 +- src/{UserSettings.hs => Settings/User.hs} | 7 ++-- src/Settings/Ways.hs | 2 +- src/Target.hs | 57 +++++++++++++++++++++++++++++++ 9 files changed, 90 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 92ef7772b82fe25e48b4f43f752e09cd545d4751 From git at git.haskell.org Thu Oct 26 23:58:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build GhcPkg Stage1 on OS X Travis. (f8bd699) Message-ID: <20171026235857.D4C1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8bd699693493f3ba8eb10e025c5db72a75b8495/ghc >--------------------------------------------------------------- commit f8bd699693493f3ba8eb10e025c5db72a75b8495 Author: Andrey Mokhov Date: Tue Feb 2 22:07:07 2016 +0000 Build GhcPkg Stage1 on OS X Travis. >--------------------------------------------------------------- f8bd699693493f3ba8eb10e025c5db72a75b8495 .travis.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index cf2f1cb..4642d70 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: false matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 + env: CABALVER=1.22 GHCVER=7.10.3 TARGET= addons: apt: packages: @@ -21,6 +21,7 @@ matrix: - cabal update - os: osx + env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg.exe before_install: - brew update - brew install ghc cabal-install @@ -61,7 +62,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick + - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET cache: directories: From git at git.haskell.org Thu Oct 26 23:58:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create /home/ghc/tmp, add stack install dir to PATH. (3ecd105) Message-ID: <20171026235858.46B233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ecd10554246bfe2d69153807248881f22d50a6d/ghc >--------------------------------------------------------------- commit 3ecd10554246bfe2d69153807248881f22d50a6d Author: Andrey Mokhov Date: Thu Jan 7 02:10:08 2016 +0000 Create /home/ghc/tmp, add stack install dir to PATH. See #110. [skip ci] >--------------------------------------------------------------- 3ecd10554246bfe2d69153807248881f22d50a6d .appveyor.yml | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.appveyor.yml b/.appveyor.yml index 1b5e3bc..011b327 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,6 +8,8 @@ install: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - stack install alex happy + - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ + - bash -lc "mkdir /home/ghc/tmp" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build From git at git.haskell.org Thu Oct 26 23:59:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Settings to Args. Rename old Args defined in Base.hs to ArgList (to be dropped later). (da64dca) Message-ID: <20171026235901.4B0B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da64dcaf2d7d2ced1673ed5f57c8801a166215b1/ghc >--------------------------------------------------------------- commit da64dcaf2d7d2ced1673ed5f57c8801a166215b1 Author: Andrey Mokhov Date: Tue Jul 14 14:19:15 2015 +0100 Rename Settings to Args. Rename old Args defined in Base.hs to ArgList (to be dropped later). >--------------------------------------------------------------- da64dcaf2d7d2ced1673ed5f57c8801a166215b1 src/Base.hs | 24 ++++++++----------- src/Expression.hs | 18 +++++++-------- src/Oracles/ArgsHash.hs | 6 ++--- src/Rules.hs | 2 +- src/Rules/Data.hs | 4 ++-- src/Rules/Util.hs | 6 ++--- src/Settings.hs | 18 +++++++-------- src/Settings/GhcCabal.hs | 60 ++++++++++++++++++++++++------------------------ src/Settings/GhcPkg.hs | 10 ++++---- src/Settings/User.hs | 8 +++---- src/Settings/Util.hs | 56 +++++++++++++++++++++----------------------- src/Ways.hs | 41 ++++++++++++++++----------------- 12 files changed, 121 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 da64dcaf2d7d2ced1673ed5f57c8801a166215b1 From git at git.haskell.org Thu Oct 26 23:59:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop exe extension. (c3fc983) Message-ID: <20171026235901.C5BED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3fc983e3fe68c4e2ae74aec45e9bf2d8fa0dcf1/ghc >--------------------------------------------------------------- commit c3fc983e3fe68c4e2ae74aec45e9bf2d8fa0dcf1 Author: Andrey Mokhov Date: Tue Feb 2 22:31:37 2016 +0000 Drop exe extension. >--------------------------------------------------------------- c3fc983e3fe68c4e2ae74aec45e9bf2d8fa0dcf1 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 4642d70..d7e58c3 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - cabal update - os: osx - env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg.exe + env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Thu Oct 26 23:59:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add appveyor badge (152f4da) Message-ID: <20171026235902.52CC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/152f4dae7932519935f4615f305505027fbd5159/ghc >--------------------------------------------------------------- commit 152f4dae7932519935f4615f305505027fbd5159 Author: Andrey Mokhov Date: Thu Jan 7 02:21:18 2016 +0000 Add appveyor badge See #110. [skip ci] >--------------------------------------------------------------- 152f4dae7932519935f4615f305505027fbd5159 README.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 90f6422..1347ee5 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,8 @@ Shaking up GHC ============== -[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) +[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Build status](https://ci.appveyor.com/api/projects/status/9er74sbnrkco98gb?svg=true&pendingText=Windows&passingText=Windows&failingText=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) + As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC][ghc] build system From git at git.haskell.org Thu Oct 26 23:59:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove unused code from Base and Oracles. (9737176) Message-ID: <20171026235906.73FFA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9737176b107f64282a24c9ffd1a3a09fe1b92ed2/ghc >--------------------------------------------------------------- commit 9737176b107f64282a24c9ffd1a3a09fe1b92ed2 Author: Andrey Mokhov Date: Tue Jul 14 15:21:55 2015 +0100 Remove unused code from Base and Oracles. >--------------------------------------------------------------- 9737176b107f64282a24c9ffd1a3a09fe1b92ed2 src/Base.hs | 8 ++---- src/Expression.hs | 9 +++--- src/Oracles.hs | 11 ++------ src/Oracles/ArgsHash.hs | 2 +- src/Oracles/Builder.hs | 7 +++-- src/Oracles/Flag.hs | 72 +----------------------------------------------- src/Oracles/Option.hs | 40 ++------------------------- src/Rules.hs | 1 - src/Rules/Data.hs | 6 ++-- src/Rules/Oracles.hs | 2 +- src/Settings.hs | 4 +-- src/Settings/GhcCabal.hs | 2 +- src/Settings/GhcPkg.hs | 2 +- src/Settings/Util.hs | 7 ++--- src/Settings/Ways.hs | 2 +- src/Switches.hs | 11 ++++++++ src/Target.hs | 2 +- src/Ways.hs | 3 +- 18 files changed, 42 insertions(+), 149 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 9737176b107f64282a24c9ffd1a3a09fe1b92ed2 From git at git.haskell.org Thu Oct 26 23:59:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop registerPackage predicate. (8424eb5) Message-ID: <20171026235907.4ACAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8424eb5e1b4a462c4a04f499c4f08cee65585fed/ghc >--------------------------------------------------------------- commit 8424eb5e1b4a462c4a04f499c4f08cee65585fed Author: Andrey Mokhov Date: Wed Feb 3 00:36:29 2016 +0000 Drop registerPackage predicate. See #200. >--------------------------------------------------------------- 8424eb5e1b4a462c4a04f499c4f08cee65585fed src/Predicates.hs | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 1e56993..c0f6095 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,7 +1,7 @@ -- | Convenient predicates module Predicates ( stage, package, builder, stagedBuilder, builderGcc, builderGhc, file, way, - stage0, stage1, stage2, notStage0, notPackage, registerPackage + stage0, stage1, stage2, notStage0, notPackage ) where import Base @@ -60,9 +60,3 @@ notStage0 = notM stage0 -- | Is a certain package /not/ built right now? notPackage :: Package -> Predicate notPackage = notM . package - --- TODO: Actually, we don't register compiler in some circumstances -- fix. --- | Do we need to run @ghc-pkg update@ on the currently built package? --- See "Rules.Data". -registerPackage :: Predicate -registerPackage = return True From git at git.haskell.org Thu Oct 26 23:59:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths. (a599895) Message-ID: <20171026235907.53D513A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5998956f9b8cc5b9042379fd298d7b823dbdaf9/ghc >--------------------------------------------------------------- commit a5998956f9b8cc5b9042379fd298d7b823dbdaf9 Author: Andrey Mokhov Date: Thu Jan 7 02:23:41 2016 +0000 Fix paths. See #110. [skip ci] >--------------------------------------------------------------- a5998956f9b8cc5b9042379fd298d7b823dbdaf9 .appveyor.yml | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 011b327..991ef0a 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -9,10 +9,9 @@ install: - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - stack install alex happy - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - - bash -lc "mkdir /home/ghc/tmp" - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - cd C:\msys64\mingw64\home\ghc\shake-build + - cd C:\msys64\home\ghc\shake-build - stack install --only-dependencies build_script: From git at git.haskell.org Thu Oct 26 23:59:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Distringuish partial Targets using type synonyms. (c319fbb) Message-ID: <20171026235910.6E4FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c319fbbf892b9a8a231676b3ecf9550d4b56a01b/ghc >--------------------------------------------------------------- commit c319fbbf892b9a8a231676b3ecf9550d4b56a01b Author: Andrey Mokhov Date: Tue Jul 14 16:07:42 2015 +0100 Distringuish partial Targets using type synonyms. >--------------------------------------------------------------- c319fbbf892b9a8a231676b3ecf9550d4b56a01b src/Oracles/ArgsHash.hs | 4 ++-- src/Rules/Data.hs | 10 ++++----- src/Rules/Package.hs | 2 +- src/Rules/Util.hs | 2 +- src/Settings/Packages.hs | 5 ++++- src/Target.hs | 55 ++++++++++++++++++++++++++++++++---------------- 6 files changed, 49 insertions(+), 29 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 1586b97..acb3e98 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -9,10 +9,10 @@ import Base import Settings import Expression -newtype ArgsHashKey = ArgsHashKey Target +newtype ArgsHashKey = ArgsHashKey FullTarget deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -askArgsHash :: Target -> Action Int +askArgsHash :: FullTarget -> Action Int askArgsHash = askOracle . ArgsHashKey -- Oracle for storing per-target argument list hashes diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 684cde6..2a40519 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -17,7 +17,7 @@ import Util import Ways -- Build package-data.mk by using GhcCabal to process pkgCabal file -buildPackageData :: Target -> Rules () +buildPackageData :: StagePackageTarget -> Rules () buildPackageData target = let stage = getStage target pkg = getPackage target @@ -33,16 +33,14 @@ buildPackageData target = -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" ] &%> \_ -> do let configure = pkgPath pkg "configure" - -- TODO: 1) how to automate this? 2) handle multiple files? - newTarget = target { getFile = path "package-data.mk" - , getWay = vanilla } -- TODO: think -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - build $ newTarget { getBuilder = GhcCabal } + -- TODO: 1) automate? 2) mutliple files 3) vanilla? + build $ fullTarget target (path "package-data.mk") GhcCabal vanilla -- TODO: when (registerPackage settings) $ - build $ newTarget { getBuilder = GhcPkg stage } + build $ fullTarget target (path "package-data.mk") (GhcPkg stage) vanilla postProcessPackageData $ path "package-data.mk" -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index a5a09dd..e316805 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -6,5 +6,5 @@ import Base import Rules.Data import Expression -buildPackage :: Target -> Rules () +buildPackage :: StagePackageTarget -> Rules () buildPackage = buildPackageData diff --git a/src/Rules/Util.hs b/src/Rules/Util.hs index a18e25e..6e1296e 100644 --- a/src/Rules/Util.hs +++ b/src/Rules/Util.hs @@ -9,7 +9,7 @@ import Expression import Oracles.Builder import Oracles.ArgsHash -build :: Target -> Action () +build :: FullTarget -> Action () build target = do argList <- interpret target args putColoured Green (show target) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 7eaa5d5..b1d98de 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -1,4 +1,5 @@ module Settings.Packages ( + module Settings.Default, packages, knownPackages ) where @@ -6,6 +7,7 @@ import Base import Package import Switches import Expression +import Settings.Default import Settings.User -- Combining default list of packages with user modifications @@ -25,7 +27,8 @@ packagesStage0 = mconcat packagesStage1 :: Packages packagesStage1 = mconcat - [ append [ array, base, bytestring, containers, deepseq, directory + [ packagesStage0 + , append [ array, base, bytestring, containers, deepseq, directory , filepath, ghcPrim, haskeline, integerLibrary, parallel , pretty, primitive, process, stm, templateHaskell, time ] , windowsHost ? append [win32] diff --git a/src/Target.hs b/src/Target.hs index 6161db7..0a0ed00 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,6 +1,7 @@ -{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} module Target ( - Target (..), stageTarget, stagePackageTarget + Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), + stageTarget, stagePackageTarget, fullTarget ) where import Base @@ -17,41 +18,59 @@ data Target = Target { getStage :: Stage, getPackage :: Package, - getBuilder :: Builder, getFile :: FilePath, -- TODO: handle multple files? + getBuilder :: Builder, getWay :: Way } deriving (Eq, Generic) --- Shows a target as "package:file at stage (builder, way)" -instance Show Target where - show target = show (getPackage target) - ++ ":" ++ show (getFile target) - ++ "@" ++ show (getStage target) - ++ " (" ++ show (getBuilder target) - ++ ", " ++ show (getWay target) ++ ")" +-- StageTarget is a Target whose field getStage is already assigned +type StageTarget = Target -stageTarget :: Stage -> Target +stageTarget :: Stage -> StageTarget stageTarget stage = Target { getStage = stage, getPackage = error "stageTarget: Package not set", - getBuilder = error "stageTarget: Builder not set", getFile = error "stageTarget: File not set", + getBuilder = error "stageTarget: Builder not set", getWay = error "stageTarget: Way not set" } -stagePackageTarget :: Stage -> Package -> Target +-- StagePackageTarget is a Target whose fields getStage and getPackage are +-- already assigned +type StagePackageTarget = Target + +stagePackageTarget :: Stage -> Package -> StagePackageTarget stagePackageTarget stage package = Target { getStage = stage, getPackage = package, - getBuilder = error "stagePackageTarget: Builder not set", getFile = error "stagePackageTarget: File not set", + getBuilder = error "stagePackageTarget: Builder not set", getWay = error "stagePackageTarget: Way not set" } --- Instances for storing Target in the Shake database -instance Binary Target -instance NFData Target -instance Hashable Target +-- FullTarget is a Target whose fields are all assigned +type FullTarget = Target + +fullTarget :: StagePackageTarget -> FilePath -> Builder -> Way -> FullTarget +fullTarget target file builder way = target + { + getFile = file, + getBuilder = builder, + getWay = way + } + +-- Shows a (full) target as "package:file at stage (builder, way)" +instance Show FullTarget where + show target = show (getPackage target) + ++ ":" ++ getFile target + ++ "@" ++ show (getStage target) + ++ " (" ++ show (getBuilder target) + ++ ", " ++ show (getWay target) ++ ")" + +-- Instances for storing FullTarget in the Shake database +instance Binary FullTarget +instance NFData FullTarget +instance Hashable FullTarget From git at git.haskell.org Thu Oct 26 23:59:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Settings.Paths, add pkgConfFile. (c1364e5) Message-ID: <20171026235911.B776E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1364e54b2178d83410dfa12ff468423e51728fa/ghc >--------------------------------------------------------------- commit c1364e54b2178d83410dfa12ff468423e51728fa Author: Andrey Mokhov Date: Wed Feb 3 00:38:41 2016 +0000 Refactor Settings.Paths, add pkgConfFile. See #200. >--------------------------------------------------------------- c1364e54b2178d83410dfa12ff468423e51728fa src/Rules.hs | 8 +++----- src/Rules/Program.hs | 9 ++++----- src/Settings/Paths.hs | 33 ++++++++++++++++++++++++--------- 3 files changed, 31 insertions(+), 19 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index b22e028..1d92baf 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -4,7 +4,6 @@ import Base import Data.Foldable import Expression import GHC -import Oracles.PackageData import qualified Rules.Generate import Rules.Package import Rules.Resources @@ -22,8 +21,8 @@ topLevelTargets = do -- TODO: do we want libffiLibrary to be a top-level target? action $ do -- TODO: Add support for all rtsWays - rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla - rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded + rtsLib <- pkgLibraryFile Stage1 rts vanilla + rtsThrLib <- pkgLibraryFile Stage1 rts threaded need [ rtsLib, rtsThrLib ] for_ allStages $ \stage -> @@ -34,8 +33,7 @@ topLevelTargets = do if isLibrary pkg then do -- build a library ways <- interpretPartial target getLibraryWays - compId <- interpretPartial target $ getPkgData ComponentId - libs <- traverse (pkgLibraryFile stage pkg compId) ways + libs <- traverse (pkgLibraryFile stage pkg) ways haddock <- interpretPartial target buildHaddock need $ libs ++ [ pkgHaddockFile pkg | haddock && stage == Stage1 ] else do -- otherwise build a program diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index d472e88..9a5b501 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -86,14 +86,13 @@ buildBinary target @ (PartialTarget stage pkg) bin = do let deps = matchPackageNames (sort pkgs) (map PackageName $ sort depNames) ghci = ghciFlag == "YES" && stage == Stage1 libs <- fmap concat . forM deps $ \dep -> do - let depTarget = PartialTarget libStage dep - compId <- interpretPartial depTarget $ getPkgData ComponentId libFiles <- fmap concat . forM ways $ \way -> do - libFile <- pkgLibraryFile libStage dep compId way - lib0File <- pkgLibraryFile libStage dep (compId ++ "-0") way + libFile <- pkgLibraryFile libStage dep way + lib0File <- pkgLibraryFile0 libStage dep way dll0 <- needDll0 libStage dep return $ libFile : [ lib0File | dll0 ] - return $ libFiles ++ [ pkgGhciLibraryFile libStage dep compId | ghci ] + ghciLib <- pkgGhciLibraryFile libStage dep + return $ libFiles ++ [ ghciLib | ghci ] let binDeps = if pkg == ghcCabal && stage == Stage0 then [ pkgPath pkg -/- src <.> "hs" | src <- hSrcs ] else objs diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index a152f9a..20f4721 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,11 +1,13 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgGhciLibraryFile, gmpBuildPath, gmpLibNameCache, packageDbDirectory + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibNameCache, + packageDbDirectory, pkgConfFile ) where import Base import Expression import GHC +import Oracles.PackageData import Settings.User -- Path to the target directory from GHC source root @@ -24,18 +26,26 @@ pkgHaddockFile pkg = -- Relative path to a package library file, e.g.: -- "libraries/array/stage2/build/libHSarray-0.5.1.0.a" --- TODO: remove code duplication for computing buildPath -pkgLibraryFile :: Stage -> Package -> String -> Way -> Action FilePath -pkgLibraryFile stage pkg componentId way = do +pkgLibraryFile :: Stage -> Package -> Way -> Action FilePath +pkgLibraryFile stage pkg way = do extension <- libsuf way - let buildPath = targetPath stage pkg -/- "build" - return $ buildPath -/- "libHS" ++ componentId ++ extension + pkgFile stage pkg "build/libHS" extension + +pkgLibraryFile0 :: Stage -> Package -> Way -> Action FilePath +pkgLibraryFile0 stage pkg way = do + extension <- libsuf way + pkgFile stage pkg "build/libHS" ("-0" ++ extension) -- Relative path to a package ghci library file, e.g.: -- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" -pkgGhciLibraryFile :: Stage -> Package -> String -> FilePath -pkgGhciLibraryFile stage pkg componentId = - targetPath stage pkg -/- "build" -/- "HS" ++ componentId <.> "o" +pkgGhciLibraryFile :: Stage -> Package -> Action FilePath +pkgGhciLibraryFile stage pkg = pkgFile stage pkg "build/HS" ".o" + +pkgFile :: Stage -> Package -> String -> String -> Action FilePath +pkgFile stage pkg prefix suffix = do + let path = targetPath stage pkg + componentId <- pkgData $ ComponentId path + return $ path -/- prefix ++ componentId ++ suffix -- This is the build directory for in-tree GMP library gmpBuildPath :: FilePath @@ -50,3 +60,8 @@ gmpLibNameCache = gmpBuildPath -/- "gmp-lib-names" packageDbDirectory :: Stage -> FilePath packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" + +pkgConfFile :: Stage -> Package -> Action FilePath +pkgConfFile stage pkg = do + componentId <- pkgData . ComponentId $ targetPath stage pkg + return $ packageDbDirectory stage -/- componentId <.> "conf" From git at git.haskell.org Thu Oct 26 23:59:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install shake, mtl and ansi-terminal. (f514cc4) Message-ID: <20171026235911.C090B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f514cc4d9b216c6dae5cb69f406f911fb3959718/ghc >--------------------------------------------------------------- commit f514cc4d9b216c6dae5cb69f406f911fb3959718 Author: Andrey Mokhov Date: Thu Jan 7 02:40:43 2016 +0000 Install shake, mtl and ansi-terminal. See #110. [skip ci] >--------------------------------------------------------------- f514cc4d9b216c6dae5cb69f406f911fb3959718 .appveyor.yml | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 991ef0a..7bcda85 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,12 +7,10 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - stack install alex happy + - stack install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - cd C:\msys64\home\ghc\shake-build - - stack install --only-dependencies build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:59:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Oracles/Builder.hs. (772ea96) Message-ID: <20171026235914.3D40A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/772ea960e295c90f0052edc7ba0c0ec6a26d33c3/ghc >--------------------------------------------------------------- commit 772ea960e295c90f0052edc7ba0c0ec6a26d33c3 Author: Andrey Mokhov Date: Tue Jul 14 23:27:54 2015 +0100 Refactor Oracles/Builder.hs. >--------------------------------------------------------------- 772ea960e295c90f0052edc7ba0c0ec6a26d33c3 src/Builder.hs | 92 ++++++++++++++++++++++++++++ src/Expression.hs | 4 +- src/Oracles/Builder.hs | 154 ----------------------------------------------- src/Rules/Actions.hs | 62 +++++++++++++++++++ src/Rules/Data.hs | 4 +- src/Rules/Util.hs | 19 ------ src/Settings/GhcCabal.hs | 43 +++++++++---- src/Settings/GhcPkg.hs | 2 +- src/Settings/Util.hs | 7 +-- src/Target.hs | 2 +- 10 files changed, 193 insertions(+), 196 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 772ea960e295c90f0052edc7ba0c0ec6a26d33c3 From git at git.haskell.org Thu Oct 26 23:59:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decouple buildPackageData and registerPackage rules. (9129e8b) Message-ID: <20171026235915.B6D4B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9129e8bc158dab081094554abc4dcbef3f8b2a5f/ghc >--------------------------------------------------------------- commit 9129e8bc158dab081094554abc4dcbef3f8b2a5f Author: Andrey Mokhov Date: Wed Feb 3 00:39:32 2016 +0000 Decouple buildPackageData and registerPackage rules. See #200. >--------------------------------------------------------------- 9129e8bc158dab081094554abc4dcbef3f8b2a5f shaking-up-ghc.cabal | 1 + src/Rules/Data.hs | 26 ++++---------------------- src/Rules/Documentation.hs | 3 ++- src/Rules/Package.hs | 30 ++++++++++++++++-------------- src/Rules/Register.hs | 39 +++++++++++++++++++++++++++++++++++++++ 5 files changed, 62 insertions(+), 37 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f00c7c6..0807ff3 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -62,6 +62,7 @@ executable ghc-shake , Rules.Package , Rules.Perl , Rules.Program + , Rules.Register , Rules.Resources , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index fbe22db..f2e3d43 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -6,7 +6,6 @@ import Base import Expression import GHC import Oracles -import Predicates (registerPackage) import Rules.Actions import Rules.Generate import Rules.Libffi @@ -29,14 +28,14 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do orderOnly $ generatedDependencies stage pkg -- GhcCabal may run the configure script, so we depend on it - -- We don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - -- We configure packages in the order of their dependencies + -- Before we configure a package its dependencies need to be registered deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - orderOnly $ map (pkgDataFile stage) depPkgs + depConfs <- traverse (pkgConfFile stage) depPkgs + orderOnly depConfs -- TODO: get rid of this, see #113 let inTreeMk = oldPath -/- takeFileName dataFile @@ -52,23 +51,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do forM_ autogenFiles $ \file -> do copyFile (oldPath -/- file) (targetPath stage pkg -/- file) - -- ghc-pkg produces inplace-pkg-config when run on packages with - -- library components only - when (isLibrary pkg) . - whenM (interpretPartial target registerPackage) $ do - - -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 - let fixPkgConf = unlines - . map (replace oldPath (targetPath stage pkg) - . replace (replaceSeparators '\\' $ oldPath) - (targetPath stage pkg) ) - . lines - - fixFile (oldPath -/- "inplace-pkg-config") fixPkgConf - - buildWithResources [(resGhcPkg rs, 1)] $ - fullTarget target (GhcPkg stage) [cabalFile] [] - postProcessPackageData stage pkg dataFile -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps @@ -141,7 +123,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do [ "C_SRCS = " ++ unwords (cSrcs ++ cmmSrcs ++ sSrcs ++ extraSrcs) , "CC_OPTS = " ++ unwords includes - , "COMPONENT_ID = " ++ "rts" ] + , "COMPONENT_ID = rts" ] writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index cb74952..e235bfc 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -26,7 +26,8 @@ buildPackageDocumentation _ target @ (PartialTarget stage pkg) = -- HsColour sources whenM (specified HsColour) $ do - need [cabalFile, pkgDataFile stage pkg ] + pkgConf <- pkgConfFile stage pkg + need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf build $ fullTarget target GhcCabalHsColour [cabalFile] [] -- Build Haddock documentation diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 7a7d854..28fe635 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -1,22 +1,24 @@ module Rules.Package (buildPackage) where import Base -import Rules.Compile -import Rules.Data -import Rules.Dependencies -import Rules.Documentation -import Rules.Generate -import Rules.Library -import Rules.Program +import qualified Rules.Compile +import qualified Rules.Data +import qualified Rules.Dependencies +import qualified Rules.Documentation +import qualified Rules.Generate +import qualified Rules.Library +import qualified Rules.Program +import qualified Rules.Register import Rules.Resources import Target buildPackage :: Resources -> PartialTarget -> Rules () buildPackage = mconcat - [ buildPackageData - , buildPackageDependencies - , generatePackageCode - , compilePackage - , buildPackageLibrary - , buildPackageDocumentation - , buildProgram ] + [ Rules.Compile.compilePackage + , Rules.Data.buildPackageData + , Rules.Dependencies.buildPackageDependencies + , Rules.Documentation.buildPackageDocumentation + , Rules.Generate.generatePackageCode + , Rules.Library.buildPackageLibrary + , Rules.Program.buildProgram + , Rules.Register.registerPackage ] diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs new file mode 100644 index 0000000..8c3ec73 --- /dev/null +++ b/src/Rules/Register.hs @@ -0,0 +1,39 @@ +module Rules.Register (registerPackage) where + +import Data.Char + +import Base +import Expression +import GHC +import Rules.Actions +import Rules.Resources +import Settings + +-- matchPkgConf :: FilePath -> Bool +-- matchPkgConf file = + +-- Build package-data.mk by using GhcCabal to process pkgCabal file +registerPackage :: Resources -> PartialTarget -> Rules () +registerPackage rs target @ (PartialTarget stage pkg) = do + let oldPath = pkgPath pkg -/- targetDirectory stage pkg -- TODO: remove, #113 + pkgConf = packageDbDirectory stage -/- pkgNameString pkg + match f = case stripPrefix (pkgConf ++ "-") f of + Nothing -> False + Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf" + + when (stage <= Stage1) $ match ?> \_ -> do + -- This produces pkgConfig. TODO: Add explicit tracking + need [pkgDataFile stage pkg] + + -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 + let pkgConfig = oldPath -/- "inplace-pkg-config" + fixPkgConf = unlines + . map (replace oldPath (targetPath stage pkg) + . replace (replaceSeparators '\\' $ oldPath) + (targetPath stage pkg) ) + . lines + + fixFile pkgConfig fixPkgConf + + buildWithResources [(resGhcPkg rs, 1)] $ + fullTarget target (GhcPkg stage) [pkgConfig] [] From git at git.haskell.org Thu Oct 26 23:59:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Take 2 (a7da5e0) Message-ID: <20171026235915.C2EFE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7da5e01637652109a75b05371b5e5864df8e836/ghc >--------------------------------------------------------------- commit a7da5e01637652109a75b05371b5e5864df8e836 Author: Moritz Angermann Date: Thu Jan 7 11:06:37 2016 +0800 Take 2 >--------------------------------------------------------------- a7da5e01637652109a75b05371b5e5864df8e836 shaking-up-ghc.cabal | 1 + src/Oracles/WindowsRoot.hs | 12 +++++++----- 2 files changed, 8 insertions(+), 5 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 00fb408..f9990e9 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -114,6 +114,7 @@ executable ghc-shake , extra >= 1.4 , mtl >= 2.2 , shake >= 0.15 + , split >= 0.2 , transformers >= 0.4 , unordered-containers >= 0.2 default-language: Haskell2010 diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 195f591..473a235 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -4,6 +4,7 @@ module Oracles.WindowsRoot ( ) where import Data.Char (isSpace) +import Data.List.Split (splitOn) import Base import Oracles.Config.Setting @@ -40,12 +41,13 @@ fixAbsolutePathOnWindows path = do -- | Lookup a @command@ in @PATH@ environment. lookupInPath :: FilePath -> Action FilePath -lookupInPath command - | command /= takeFileName command = return command +lookupInPath c + | c /= takeFileName c = return c | otherwise = do - Stdout out <- quietly $ cmd ["which", command] - let path = dropWhileEnd isSpace out - return path + envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" + let candidates = map (-/- c) envPaths in + -- this will crash if we do not find any valid candidate. + head <$> filterM doesFileExist candidates -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). From git at git.haskell.org Thu Oct 26 23:59:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up Base. (9bde7d8) Message-ID: <20171026235917.BBB873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9bde7d8668019ed08561c701e3f2ba61ac173d6e/ghc >--------------------------------------------------------------- commit 9bde7d8668019ed08561c701e3f2ba61ac173d6e Author: Andrey Mokhov Date: Tue Jul 14 23:49:13 2015 +0100 Clean up Base. >--------------------------------------------------------------- 9bde7d8668019ed08561c701e3f2ba61ac173d6e src/Base.hs | 13 ------------- 1 file changed, 13 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 026f211..97a22d5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -10,7 +10,6 @@ module Base ( Stage (..), Arg, ArgList, ShowArg (..), ShowArgs (..), - filterOut, productArgs, concatArgs ) where @@ -56,21 +55,9 @@ class ShowArgs a where instance ShowArgs [String] where showArgs = return -instance ShowArgs [Arg] where - showArgs = sequence - -instance ShowArgs [ArgList] where - showArgs = mconcat - instance ShowArgs a => ShowArgs (Action a) where showArgs = (showArgs =<<) --- Filter out given arg(s) from a collection -filterOut :: ShowArgs a => ArgList -> a -> ArgList -filterOut as exclude = do - exclude' <- showArgs exclude - filter (`notElem` exclude') <$> as - -- Generate a cross product collection of two argument collections -- Example: productArgs ["-a", "-b"] "c" = args ["-a", "c", "-b", "c"] productArgs :: (ShowArgs a, ShowArgs b) => a -> b -> ArgList From git at git.haskell.org Thu Oct 26 23:59:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Show the candidates. (e4ed614) Message-ID: <20171026235919.4013A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4ed614de3a98ec374536032946802a37b96e85d/ghc >--------------------------------------------------------------- commit e4ed614de3a98ec374536032946802a37b96e85d Author: Moritz Angermann Date: Thu Jan 7 11:30:05 2016 +0800 Show the candidates. >--------------------------------------------------------------- e4ed614de3a98ec374536032946802a37b96e85d src/Oracles/WindowsRoot.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 473a235..0c45230 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -46,8 +46,9 @@ lookupInPath c | otherwise = do envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths in - -- this will crash if we do not find any valid candidate. - head <$> filterM doesFileExist candidates + mapM_ putStrLn candidates + -- this will crash if we do not find any valid candidate. + head <$> filterM doesFileExist candidates -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). From git at git.haskell.org Thu Oct 26 23:59:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop ghc-cabal resource. (13d735f) Message-ID: <20171026235919.5CE023A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13d735f298d0a51a83c422a34e9844058ca5e89d/ghc >--------------------------------------------------------------- commit 13d735f298d0a51a83c422a34e9844058ca5e89d Author: Andrey Mokhov Date: Wed Feb 3 01:03:46 2016 +0000 Drop ghc-cabal resource. See #200. >--------------------------------------------------------------- 13d735f298d0a51a83c422a34e9844058ca5e89d src/Rules/Data.hs | 3 +-- src/Rules/Resources.hs | 10 +++------- 2 files changed, 4 insertions(+), 9 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index f2e3d43..ade93fd 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -41,8 +41,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do let inTreeMk = oldPath -/- takeFileName dataFile need [cabalFile] - buildWithResources [(resGhcCabal rs, 1)] $ - fullTarget target GhcCabal [cabalFile] [inTreeMk] + build $ fullTarget target GhcCabal [cabalFile] [inTreeMk] -- TODO: get rid of this, see #113 liftIO $ IO.copyFile inTreeMk dataFile diff --git a/src/Rules/Resources.hs b/src/Rules/Resources.hs index 514a222..d5e58fe 100644 --- a/src/Rules/Resources.hs +++ b/src/Rules/Resources.hs @@ -4,13 +4,9 @@ import Base data Resources = Resources { - resGhcCabal :: Resource, - resGhcPkg :: Resource + resGhcPkg :: Resource } --- Unfortunately parallel invokations of ghc-cabal or ghc-pkg do not work: --- * https://mail.haskell.org/pipermail/ghc-commits/2013-May/001712.html --- * ghc.mk: see comment about parallel ghc-pkg invokations +-- We cannot register multiple packages in parallel: resourceRules :: Rules Resources -resourceRules = liftM2 Resources (newResource "ghc-cabal" 1) - (newResource "ghc-pkg" 1) +resourceRules = Resources <$> newResource "ghc-pkg" 1 From git at git.haskell.org Thu Oct 26 23:59:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Ways.hs => Way.hs and refactor it. (3726211) Message-ID: <20171026235921.9C4713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37262111fee905d4d0312c02f80ae3abd8250566/ghc >--------------------------------------------------------------- commit 37262111fee905d4d0312c02f80ae3abd8250566 Author: Andrey Mokhov Date: Wed Jul 15 20:30:52 2015 +0200 Rename Ways.hs => Way.hs and refactor it. >--------------------------------------------------------------- 37262111fee905d4d0312c02f80ae3abd8250566 src/Base.hs | 8 +-- src/Builder.hs | 2 +- src/Expression.hs | 2 +- src/Package.hs | 10 +-- src/Rules/Data.hs | 2 +- src/Settings/GhcCabal.hs | 2 +- src/Settings/Util.hs | 15 +++++ src/Settings/Ways.hs | 2 +- src/Target.hs | 4 +- src/Way.hs | 138 +++++++++++++++++++++++++++++++++++++++ src/Ways.hs | 165 ----------------------------------------------- 11 files changed, 169 insertions(+), 181 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 37262111fee905d4d0312c02f80ae3abd8250566 From git at git.haskell.org Thu Oct 26 23:59:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: :( (0fa71d1) Message-ID: <20171026235923.11BD53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0fa71d10277a13d26c0f441745993f0a45ad5dc3/ghc >--------------------------------------------------------------- commit 0fa71d10277a13d26c0f441745993f0a45ad5dc3 Author: Moritz Angermann Date: Thu Jan 7 13:02:51 2016 +0800 :( >--------------------------------------------------------------- 0fa71d10277a13d26c0f441745993f0a45ad5dc3 src/Oracles/WindowsRoot.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 0c45230..6def89c 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -45,8 +45,8 @@ lookupInPath c | c /= takeFileName c = return c | otherwise = do envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" - let candidates = map (-/- c) envPaths in - mapM_ putStrLn candidates + let candidates = map (-/- c) envPaths + liftIO $ mapM_ putStrLn candidates -- this will crash if we do not find any valid candidate. head <$> filterM doesFileExist candidates From git at git.haskell.org Thu Oct 26 23:59:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update stack.yaml to lts-5.1 (82b665e) Message-ID: <20171026235923.3B0EE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82b665e184a92fb27bc894e6f0fe2d186ea1fbe0/ghc >--------------------------------------------------------------- commit 82b665e184a92fb27bc894e6f0fe2d186ea1fbe0 Author: Joe Hillenbrand Date: Wed Feb 3 10:35:55 2016 -0800 Update stack.yaml to lts-5.1 I don't plan to change this file every time there is a new stackage lts, but lts-4.x has a bug with aeson. >--------------------------------------------------------------- 82b665e184a92fb27bc894e6f0fe2d186ea1fbe0 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index 2bc3b0e..0772c76 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,7 +1,7 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-4.2 +resolver: lts-5.1 # Local packages, usually specified by relative directory name packages: From git at git.haskell.org Thu Oct 26 23:59:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support to multiple files in Target, implement registerPackage predicate. (c41e156) Message-ID: <20171026235925.325A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c41e156c6bee670112d50825040ccc2ebc56a78e/ghc >--------------------------------------------------------------- commit c41e156c6bee670112d50825040ccc2ebc56a78e Author: Andrey Mokhov Date: Wed Jul 15 23:44:30 2015 +0200 Add support to multiple files in Target, implement registerPackage predicate. >--------------------------------------------------------------- c41e156c6bee670112d50825040ccc2ebc56a78e src/Expression.hs | 2 +- src/Rules/Actions.hs | 7 ++++++- src/Rules/Data.hs | 10 ++++------ src/Switches.hs | 7 ++++++- src/Target.hs | 30 ++++++++++++++++++++---------- 5 files changed, 37 insertions(+), 19 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 2f8ea4b..0ee8034 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -140,7 +140,7 @@ builder :: Builder -> Predicate builder b = liftM (b ==) (asks getBuilder) file :: FilePattern -> Predicate -file f = liftM (f ?==) (asks getFile) +file f = liftM (any (f ?==)) (asks getFiles) way :: Way -> Predicate way w = liftM (w ==) (asks getWay) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9010647..d29d486 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,5 +1,5 @@ module Rules.Actions ( - build, run, verboseRun, + build, buildWhen, run, verboseRun, ) where import Base @@ -21,6 +21,11 @@ build target = do argsHash <- askArgsHash target run (getBuilder target) argList +buildWhen :: Predicate -> FullTarget -> Action () +buildWhen predicate target = do + bool <- interpretExpr target predicate + when bool $ build target + -- Run the builder with a given collection of arguments verboseRun :: Builder -> [String] -> Action () verboseRun builder args = do diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index beadd7e..eb34b65 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -4,10 +4,10 @@ module Rules.Data ( cabalArgs, ghcPkgArgs, buildPackageData ) where -import Way import Base import Package import Builder +import Switches import Expression import Control.Monad.Extra import Settings.GhcPkg @@ -31,16 +31,14 @@ buildPackageData target = , "build" "autogen" "cabal_macros.h" -- TODO: Is this needed? Also check out Paths_cpsa.hs. -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" - ] &%> \_ -> do + ] &%> \files -> do let configure = pkgPath pkg "configure" -- GhcCabal will run the configure script, so we depend on it need [pkgPath pkg pkgCabal pkg] -- We still don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - -- TODO: 1) automate? 2) mutliple files 3) vanilla? - build $ fullTarget target (path "package-data.mk") GhcCabal vanilla - -- TODO: when (registerPackage settings) $ - build $ fullTarget target (path "package-data.mk") (GhcPkg stage) vanilla + build $ fullTarget target files GhcCabal + buildWhen registerPackage $ fullTarget target files (GhcPkg stage) postProcessPackageData $ path "package-data.mk" -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: diff --git a/src/Switches.hs b/src/Switches.hs index ce03ade..8ab2de2 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -5,7 +5,8 @@ module Switches ( targetOss, targetOs, notTargetOs, targetArchs, dynamicGhcPrograms, ghcWithInterpreter, platformSupportsSharedLibs, crossCompiling, - gccIsClang, gccLt46, windowsHost, notWindowsHost + gccIsClang, gccLt46, windowsHost, notWindowsHost, + registerPackage ) where import Base @@ -91,6 +92,10 @@ windowsHost = configKeyValues "host-os-cpp" ["mingw32", "cygwin32"] notWindowsHost :: Predicate notWindowsHost = liftM not windowsHost +-- TODO: Actually, we don't register compiler in some circumstances -- fix. +registerPackage :: Predicate +registerPackage = return True + -- splitObjects :: Stage -> Condition -- splitObjects stage = do -- arch <- showArg TargetArch diff --git a/src/Target.hs b/src/Target.hs index 198cffc..6b02af9 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} module Target ( Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), - stageTarget, stagePackageTarget, fullTarget + stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay ) where import Way @@ -18,7 +18,7 @@ data Target = Target { getStage :: Stage, getPackage :: Package, - getFile :: FilePath, -- TODO: handle multple files? + getFiles :: [FilePath], getBuilder :: Builder, getWay :: Way } @@ -32,9 +32,9 @@ stageTarget stage = Target { getStage = stage, getPackage = error "stageTarget: Package not set", - getFile = error "stageTarget: File not set", + getFiles = error "stageTarget: Files not set", getBuilder = error "stageTarget: Builder not set", - getWay = error "stageTarget: Way not set" + getWay = vanilla -- most targets are built only one way (vanilla) } -- StagePackageTarget is a Target whose fields getStage and getPackage are @@ -46,18 +46,28 @@ stagePackageTarget stage package = Target { getStage = stage, getPackage = package, - getFile = error "stagePackageTarget: File not set", + getFiles = error "stagePackageTarget: Files not set", getBuilder = error "stagePackageTarget: Builder not set", - getWay = error "stagePackageTarget: Way not set" + getWay = vanilla } -- FullTarget is a Target whose fields are all assigned type FullTarget = Target -fullTarget :: StagePackageTarget -> FilePath -> Builder -> Way -> FullTarget -fullTarget target file builder way = target +-- Most targets are built only one way, vanilla, hence we set it by default. +fullTarget :: StagePackageTarget -> [FilePath] -> Builder -> FullTarget +fullTarget target files builder = target { - getFile = file, + getFiles = files, + getBuilder = builder, + getWay = vanilla + } + +-- Use this function to be explicit about build the way. +fullTargetWithWay :: StagePackageTarget -> [FilePath] -> Builder -> Way -> FullTarget +fullTargetWithWay target files builder way = target + { + getFiles = files, getBuilder = builder, getWay = way } @@ -65,7 +75,7 @@ fullTarget target file builder way = target -- Shows a (full) target as "package:file at stage (builder, way)" instance Show FullTarget where show target = show (getPackage target) - ++ ":" ++ getFile target + ++ ":" ++ show (getFiles target) ++ "@" ++ show (getStage target) ++ " (" ++ show (getBuilder target) ++ ", " ++ show (getWay target) ++ ")" From git at git.haskell.org Thu Oct 26 23:59:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: :+1: (b47bd51) Message-ID: <20171026235927.0ED533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b47bd516326d7d9652a1ba6d37352e01766390f2/ghc >--------------------------------------------------------------- commit b47bd516326d7d9652a1ba6d37352e01766390f2 Author: Moritz Angermann Date: Thu Jan 7 13:51:30 2016 +0800 :+1: >--------------------------------------------------------------- b47bd516326d7d9652a1ba6d37352e01766390f2 src/Builder.hs | 6 ++++-- src/Oracles/WindowsRoot.hs | 1 - 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 6e4dba5..0613452 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -95,8 +95,10 @@ builderPath builder = do putError $ "\nCannot find path to '" ++ (builderKey builder) ++ "' in configuration files." windows <- windowsHost - let path' = if null path then "" else path -<.> exe in - (if windows then fixAbsolutePathOnWindows else lookupInPath) path' + case (path, windows) of + ("", _) -> return path + (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) + (p, False) -> lookupInPath (p -<.> exe) getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 6def89c..4186700 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -46,7 +46,6 @@ lookupInPath c | otherwise = do envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths - liftIO $ mapM_ putStrLn candidates -- this will crash if we do not find any valid candidate. head <$> filterM doesFileExist candidates From git at git.haskell.org Thu Oct 26 23:59:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #202 from joehillen/patch-1 (793587b) Message-ID: <20171026235927.274C53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/793587bd5c2a0981221e7d11fe57071f5367e021/ghc >--------------------------------------------------------------- commit 793587bd5c2a0981221e7d11fe57071f5367e021 Merge: 13d735f 82b665e Author: Andrey Mokhov Date: Wed Feb 3 18:50:40 2016 +0000 Merge pull request #202 from joehillen/patch-1 Update stack.yaml to lts-5.1 [skip ci] >--------------------------------------------------------------- 793587bd5c2a0981221e7d11fe57071f5367e021 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Oct 26 23:59:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Settings.hs to Settings/Args.hs. (d9b03d3) Message-ID: <20171026235928.A78203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9b03d37d49ecbd2db59fd242692727488ef92dd/ghc >--------------------------------------------------------------- commit d9b03d37d49ecbd2db59fd242692727488ef92dd Author: Andrey Mokhov Date: Wed Jul 15 23:49:10 2015 +0200 Rename Settings.hs to Settings/Args.hs. >--------------------------------------------------------------- d9b03d37d49ecbd2db59fd242692727488ef92dd src/Oracles/ArgsHash.hs | 4 ++-- src/Rules/Actions.hs | 2 +- src/{Settings.hs => Settings/Args.hs} | 2 +- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index acb3e98..b930ef6 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -4,10 +4,10 @@ module Oracles.ArgsHash ( ArgsHashKey (..), askArgsHash, argsHashOracle ) where -import Development.Shake.Classes import Base -import Settings import Expression +import Settings.Args +import Development.Shake.Classes newtype ArgsHashKey = ArgsHashKey FullTarget deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d29d486..e4688dc 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -5,8 +5,8 @@ module Rules.Actions ( import Base import Util import Builder -import Settings import Expression +import Settings.Args import Oracles.ArgsHash -- Build a given target using an appropriate builder. Force a rebuilt if the diff --git a/src/Settings.hs b/src/Settings/Args.hs similarity index 92% rename from src/Settings.hs rename to src/Settings/Args.hs index 196f4d7..cc7a22c 100644 --- a/src/Settings.hs +++ b/src/Settings/Args.hs @@ -1,4 +1,4 @@ -module Settings ( +module Settings.Args ( args ) where From git at git.haskell.org Thu Oct 26 23:59:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix the old-time issue. (909ed08) Message-ID: <20171026235930.D20423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/909ed08eea7d843c5fb6c022349b3afc10946b60/ghc >--------------------------------------------------------------- commit 909ed08eea7d843c5fb6c022349b3afc10946b60 Author: Andrey Mokhov Date: Thu Jan 7 09:24:05 2016 +0000 Fix the old-time issue. See #110. [skip ci] >--------------------------------------------------------------- 909ed08eea7d843c5fb6c022349b3afc10946b60 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7bcda85..da02948 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,7 +7,7 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - stack install alex happy shake ansi-terminal mtl + - echo "" | stack --no-terminal alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Thu Oct 26 23:59:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't print empty arguments. (2bde60d) Message-ID: <20171026235931.017593A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2bde60d83dd71c50b88f385efefef71bf27220d0/ghc >--------------------------------------------------------------- commit 2bde60d83dd71c50b88f385efefef71bf27220d0 Author: Andrey Mokhov Date: Fri Feb 5 01:07:48 2016 +0000 Don't print empty arguments. See #204. >--------------------------------------------------------------- 2bde60d83dd71c50b88f385efefef71bf27220d0 src/Rules/Actions.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 658ba17..daa4c5e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -98,7 +98,8 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] - let note = if null args || args == [""] then "" else " (" ++ intercalate ", " args ++ ")" + let args' = filter (not . null) args + note = if null args' then "" else " (" ++ intercalate ", " args' ++ ")" if dir == "." then do putBuild $ "| Run configure" ++ note ++ "..." From git at git.haskell.org Thu Oct 26 23:59:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement argPath that unifies the path argument. (5a4a443) Message-ID: <20171026235932.1DAE53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a4a443af1fabc548894ca9d3f75702a4b08cf21/ghc >--------------------------------------------------------------- commit 5a4a443af1fabc548894ca9d3f75702a4b08cf21 Author: Andrey Mokhov Date: Wed Jul 15 23:55:46 2015 +0200 Implement argPath that unifies the path argument. >--------------------------------------------------------------- 5a4a443af1fabc548894ca9d3f75702a4b08cf21 src/Settings/GhcCabal.hs | 4 ++-- src/Settings/GhcPkg.hs | 2 +- src/Settings/Util.hs | 12 +++++++----- 3 files changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 7281b9f..34984b7 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -21,8 +21,8 @@ cabalArgs = builder GhcCabal ? do stage <- asks getStage pkg <- asks getPackage mconcat [ arg "configure" - , arg $ pkgPath pkg - , arg $ targetDirectory stage pkg + , argPath $ pkgPath pkg + , argPath $ targetDirectory stage pkg , dllArgs , with $ Ghc stage , with $ GhcPkg stage diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index 9bf85e7..a75eab7 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -18,4 +18,4 @@ ghcPkgArgs = do [ arg "update" , arg "--force" , stage0 ? bootPackageDbArgs - , arg $ targetPath stage pkg "inplace-pkg-config" ] + , argPath $ targetPath stage pkg "inplace-pkg-config" ] diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index b529376..9ee4986 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -1,6 +1,6 @@ module Settings.Util ( -- Primitive settings elements - arg, argM, + arg, argPath, argM, argConfig, argStagedConfig, argConfigList, argStagedConfigList, appendCcArgs, -- argBuilderPath, argStagedBuilderPath, @@ -12,14 +12,19 @@ module Settings.Util ( ) where import Base +import Util import Builder import Oracles.Base import Expression --- A single argument +-- A single argument. arg :: String -> Args arg = append . return +-- A single path argument. The path gets unified. +argPath :: String -> Args +argPath = append . return . unifyPath + argM :: Action String -> Args argM = appendM . fmap return @@ -50,9 +55,6 @@ appendCcArgs xs = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" xs , builder GhcCabal ? appendSub "--gcc-options" xs ] - - - -- packageData :: Arity -> String -> Args -- packageData arity key = -- return $ EnvironmentParameter $ PackageData arity key Nothing Nothing From git at git.haskell.org Thu Oct 26 23:59:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Restore install argument to stack. (2ad773b) Message-ID: <20171026235934.497083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ad773b62f0558f6a83b585b543e3a0a847c2911/ghc >--------------------------------------------------------------- commit 2ad773b62f0558f6a83b585b543e3a0a847c2911 Author: Andrey Mokhov Date: Thu Jan 7 09:37:20 2016 +0000 Restore install argument to stack. See #110. [skip ci] >--------------------------------------------------------------- 2ad773b62f0558f6a83b585b543e3a0a847c2911 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index da02948..8f2e278 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,7 +7,7 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - echo "" | stack --no-terminal alex happy shake ansi-terminal mtl + - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Thu Oct 26 23:59:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass --enable-tarballs-autodownload to configure by default on Windows. (1562315) Message-ID: <20171026235934.6EEBA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1562315b94894f4e8098da8ac35ce2a007f2dc1f/ghc >--------------------------------------------------------------- commit 1562315b94894f4e8098da8ac35ce2a007f2dc1f Author: Andrey Mokhov Date: Fri Feb 5 01:08:31 2016 +0000 Pass --enable-tarballs-autodownload to configure by default on Windows. See #204. >--------------------------------------------------------------- 1562315b94894f4e8098da8ac35ce2a007f2dc1f src/Rules/Config.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 89434cb..1016be9 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -1,5 +1,7 @@ module Rules.Config (configRules) where +import qualified System.Info + import Base import CmdLineFlag import Rules.Actions @@ -14,7 +16,11 @@ configRules = do case cmdConfigure of RunConfigure args -> do need [ settings <.> "in", cfgH <.> "in" ] - runConfigure "." [] [args] + -- We cannot use windowsHost here due to a cyclic dependency + let defaultArgs = if System.Info.os == "mingw32" + then [ "--enable-tarballs-autodownload" ] + else [] + runConfigure "." [] $ defaultArgs ++ [args] SkipConfigure -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " From git at git.haskell.org Thu Oct 26 23:59:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove user.config file, rename default.config to system.config. (a8cfbde) Message-ID: <20171026235935.8D2D73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8cfbde5e0fc9df532d739815a28ac2e022eff0d/ghc >--------------------------------------------------------------- commit a8cfbde5e0fc9df532d739815a28ac2e022eff0d Author: Andrey Mokhov Date: Sun Jul 19 00:15:45 2015 +0100 Remove user.config file, rename default.config to system.config. >--------------------------------------------------------------- a8cfbde5e0fc9df532d739815a28ac2e022eff0d .gitignore | 2 +- cfg/configure.ac | 2 +- cfg/{default.config.in => system.config.in} | 0 cfg/user.config | 4 ---- src/Config.hs | 4 ++-- src/Oracles.hs | 37 ++++++++--------------------- src/Oracles/Option.hs | 4 ++-- 7 files changed, 16 insertions(+), 37 deletions(-) diff --git a/.gitignore b/.gitignore index dad3a3c..94b9664 100644 --- a/.gitignore +++ b/.gitignore @@ -2,5 +2,5 @@ *.hi _shake/ _build/ -cfg/default.config +cfg/system.config arg/*/*.txt diff --git a/cfg/configure.ac b/cfg/configure.ac index 125fd49..687eac7 100644 --- a/cfg/configure.ac +++ b/cfg/configure.ac @@ -978,7 +978,7 @@ if grep ' ' compiler/ghc.cabal.in 2>&1 >/dev/null; then AC_MSG_ERROR([compiler/ghc.cabal.in contains tab characters; please remove them]) fi -AC_CONFIG_FILES([shake/cfg/default.config mk/config.mk mk/install.mk mk/project.mk compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal settings docs/users_guide/ug-book.xml docs/users_guide/ug-ent.xml docs/index.html libraries/prologue.txt distrib/configure.ac]) +AC_CONFIG_FILES([shake/cfg/system.config mk/config.mk mk/install.mk mk/project.mk compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal settings docs/users_guide/ug-book.xml docs/users_guide/ug-ent.xml docs/index.html libraries/prologue.txt distrib/configure.ac]) AC_OUTPUT # We got caught by diff --git a/cfg/default.config.in b/cfg/system.config.in similarity index 100% rename from cfg/default.config.in rename to cfg/system.config.in diff --git a/cfg/user.config b/cfg/user.config deleted file mode 100644 index b72c5b4..0000000 --- a/cfg/user.config +++ /dev/null @@ -1,4 +0,0 @@ -# Override default settings (stored in default.config file): -#=========================================================== - -lax-dependencies = YES diff --git a/src/Config.hs b/src/Config.hs index 1a4ef9a..0dc67a2 100644 --- a/src/Config.hs +++ b/src/Config.hs @@ -17,7 +17,7 @@ autoconfRules = do configureRules :: Rules () configureRules = do - cfgPath "default.config" %> \out -> do - need [cfgPath "default.config.in", "configure"] + cfgPath "system.config" %> \out -> do + need [cfgPath "system.config.in", "configure"] putColoured White "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' diff --git a/src/Oracles.hs b/src/Oracles.hs index e6e31f9..cd8c879 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -6,45 +6,25 @@ module Oracles ( import Development.Shake.Config import Development.Shake.Util import qualified Data.HashMap.Strict as M --- TODO: get rid of Bifunctor dependency -import Data.Bifunctor import Base import Util import Config +import Control.Monad.Extra import Oracles.Base import Oracles.PackageData -import Control.Monad.Extra import Oracles.DependencyList -defaultConfig, userConfig :: FilePath -defaultConfig = cfgPath "default.config" -userConfig = cfgPath "user.config" - -- Oracle for configuration files configOracle :: Rules () configOracle = do + let configFile = cfgPath "system.config" cfg <- newCache $ \() -> do - unlessM (doesFileExist $ defaultConfig <.> "in") $ - redError_ $ "\nDefault configuration file '" - ++ (defaultConfig <.> "in") + unlessM (doesFileExist $ configFile <.> "in") $ + redError_ $ "\nConfiguration file '" ++ (configFile <.> "in") ++ "' is missing; unwilling to proceed." - need [defaultConfig] - putOracle $ "Reading " ++ unifyPath defaultConfig ++ "..." - cfgDefault <- liftIO $ readConfigFile defaultConfig - existsUser <- doesFileExist userConfig - cfgUser <- if existsUser - then do - putOracle $ "Reading " - ++ unifyPath userConfig ++ "..." - liftIO $ readConfigFile userConfig - else do - putColoured Red $ - "\nUser defined configuration file '" - ++ userConfig ++ "' is missing; " - ++ "proceeding with default configuration.\n" - return M.empty - putColoured Green $ "Finished processing configuration files." - return $ cfgUser `M.union` cfgDefault + need [configFile] + putOracle $ "Reading " ++ unifyPath configFile ++ "..." + liftIO $ readConfigFile configFile addOracle $ \(ConfigKey key) -> M.lookup key <$> cfg () return () @@ -59,6 +39,9 @@ packageDataOracle = do M.lookup key <$> pkgData (unifyPath file) return () +bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) +bimap f g (x, y) = (f x, g y) + -- Oracle for 'path/dist/*.deps' files dependencyOracle :: Rules () dependencyOracle = do diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs index f1a35e2..ff0c5fc 100644 --- a/src/Oracles/Option.hs +++ b/src/Oracles/Option.hs @@ -5,8 +5,8 @@ module Oracles.Option ( import Base import Oracles.Base --- For each Option the files {default.config, user.config} contain --- a line of the form 'target-os = mingw32'. +-- For each Option the file default.config contains a line of the +-- form 'target-os = mingw32'. -- (showArg TargetOs) is an action that consults the config files -- and returns "mingw32". -- From git at git.haskell.org Thu Oct 26 23:59:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use --configure by default, add --enable-tarballs-autodownload flag on Windows. (2825f93) Message-ID: <20171026235937.E14573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2825f9345544b96b4f904c2db64b82d1982a3c0a/ghc >--------------------------------------------------------------- commit 2825f9345544b96b4f904c2db64b82d1982a3c0a Author: Andrey Mokhov Date: Fri Feb 5 01:34:35 2016 +0000 Don't use --configure by default, add --enable-tarballs-autodownload flag on Windows. See #204. [skip ci] >--------------------------------------------------------------- 2825f9345544b96b4f904c2db64b82d1982a3c0a README.md | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/README.md b/README.md index 0a60d11..f048ee4 100644 --- a/README.md +++ b/README.md @@ -27,29 +27,26 @@ follow these steps: * This build system is written in Haskell (obviously) and depends on the following Haskell packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. -* Get the sources. It is important for the build system to be in the `shake-build` directory of the GHC source tree: +* Get the sources and run standard configuration scripts. It is important for the build +system to be in the `shake-build` directory of the GHC source tree: ```bash git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/shaking-up-ghc shake-build + ./boot + ./configure # On Windows run ./configure --enable-tarballs-autodownload ``` -* Start your first build (you might want to enable parallelism with `-j`): - ```bash - shake-build/build.sh --configure - ``` -On Windows, use `build.bat` instead and pass an extra flag to configure (also see [building on Windows][ghc-windows-quick-build]): - ```bash - shake-build/build.bat --configure=--enable-tarballs-autodownload - ``` -If you are interested in building in a Cabal sandbox or using Stack, have a look at `shake-build/build.cabal.sh` and `shake-build/build.stack.sh` scripts. +* Build GHC using `shake-build/build.sh` or `shake-build/build.bat` (on Windows) instead +of `make`. You might want to enable parallelism with `-j`. We will further refer to the +build script simply as `build`. If you are interested in building in a Cabal sandbox +or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Using the build system ---------------------- -Once your first build is successful, simply run `shake-build/build.sh` or `shake-build/build.bat` -to rebuild (you no longer need to use the `--configure` flag). Most build artefacts are placed -into `.build` and `inplace` directories ([#113][build-artefacts-issue]). +Once your first build is successful, simply run `build` to rebuild. Most build artefacts +are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue]). #### Command line flags @@ -58,7 +55,10 @@ currently supports several others: * `--configure[=ARGS]`: run the `configure` script forwarding `ARGS` as command line arguments; also run the `boot` script to create the `configure` script if necessary. You do not have to use this functionality of the new build system; feel free to run -`boot` and `configure` scripts manually, as you do when using `make`. +`boot` and `configure` scripts manually, as you do when using `make`. Note: on Windows +we automatically add flag `--enable-tarballs-autodownload` to `ARGS`, so you +don't have to do it manually. Beware, this uses network I/O which may sometimes be +undesirable. * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). * `--progress-info=STYLE`: choose how build progress info is printed. There are four From git at git.haskell.org Thu Oct 26 23:59:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve needBuilder, see #124. (360a4c3) Message-ID: <20171026235937.F18193A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/360a4c37f4060254157d19443a3b3c95b8c5b1c7/ghc >--------------------------------------------------------------- commit 360a4c37f4060254157d19443a3b3c95b8c5b1c7 Author: Andrey Mokhov Date: Thu Jan 7 09:37:52 2016 +0000 Improve needBuilder, see #124. >--------------------------------------------------------------- 360a4c37f4060254157d19443a3b3c95b8c5b1c7 src/Builder.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Builder.hs b/src/Builder.hs index 5ed9e1d..e4d8221 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -106,7 +106,7 @@ specified = fmap (not . null) . builderPath -- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). needBuilder :: Bool -> Builder -> Action () -needBuilder laxDependencies builder = do +needBuilder laxDependencies builder = whenM (specified builder) $ do path <- builderPath builder if laxDependencies && allowOrderOnlyDependency builder then orderOnly [path] From git at git.haskell.org Thu Oct 26 23:59:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor and rename Oracles/Option.hs. (272f100) Message-ID: <20171026235939.0EFCE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7/ghc >--------------------------------------------------------------- commit 272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7 Author: Andrey Mokhov Date: Sun Jul 19 00:45:35 2015 +0100 Refactor and rename Oracles/Option.hs. >--------------------------------------------------------------- 272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7 src/Base.hs | 3 +-- src/Builder.hs | 3 ++- src/Expression.hs | 1 + src/Oracles.hs | 1 + src/Oracles/Option.hs | 61 ---------------------------------------------- src/Oracles/PackageData.hs | 1 + src/Oracles/Setting.hs | 61 ++++++++++++++++++++++++++++++++++++++++++++++ src/Settings/GhcCabal.hs | 5 ++-- src/Way.hs | 18 +++++++------- 9 files changed, 79 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 272f1005e130fa1dd0142cb3e9ca9078ef5eb1a7 From git at git.haskell.org Thu Oct 26 23:59:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refer to the build script simple as 'build'. (b9af374) Message-ID: <20171026235941.5FDE93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b9af374ec77c17971166f3a37c7409710bd7d8c5/ghc >--------------------------------------------------------------- commit b9af374ec77c17971166f3a37c7409710bd7d8c5 Author: Andrey Mokhov Date: Fri Feb 5 01:37:29 2016 +0000 Refer to the build script simple as 'build'. [skip ci] >--------------------------------------------------------------- b9af374ec77c17971166f3a37c7409710bd7d8c5 README.md | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/README.md b/README.md index f048ee4..37a144e 100644 --- a/README.md +++ b/README.md @@ -75,24 +75,24 @@ experiment following the Haddock comments. #### Clean and full rebuild -* `shake-build/build.sh clean` removes all build artefacts. Note, we are working -towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `build clean` removes all build artefacts. Note, we are working towards a +complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. -* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of -the previous build are still in the GHC tree. +* `build -B` forces Shake to rerun all rules, even if results of the previous build +are still in the GHC tree. #### Testing -* `shake-build/build.sh validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` -directory. This can be used instead of `sh validate --fast --no-clean` in the existing build system. -Note: this will rebuild Stage2 GHC, `ghc-pkg` and `hpc` if they are out of date. +* `build validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` +directory. This can be used instead of `sh validate --fast --no-clean` in the existing +build system. Note: this will rebuild Stage2 GHC, `ghc-pkg` and `hpc` if they are out of date. -* `shake-build/build.sh test` runs GHC tests by calling the `testsuite/driver/runtests.py` python -script with appropriate flags. The current implementation is limited and cannot replace the -`validate` script (see [#187][validation-issue]). +* `build test` runs GHC tests by calling the `testsuite/driver/runtests.py` python +script with appropriate flags. The current implementation is limited and cannot +replace the `validate` script (see [#187][validation-issue]). -* `shake-build/build.sh selftest` runs tests of the build system. Current test -coverage is close to zero (see [#197][test-issue]). +* `build selftest` runs tests of the build system. Current test coverage is close to +zero (see [#197][test-issue]). Current limitations ------------------- From git at git.haskell.org Thu Oct 26 23:59:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Prepend to configure. (39c3486) Message-ID: <20171026235941.7B3333A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39c34860df442efeb8e4c185d92549d828255191/ghc >--------------------------------------------------------------- commit 39c34860df442efeb8e4c185d92549d828255191 Author: Andrey Mokhov Date: Thu Jan 7 10:12:13 2016 +0000 Prepend to configure. See #110. [skip ci] >--------------------------------------------------------------- 39c34860df442efeb8e4c185d92549d828255191 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 8f2e278..a5763cc 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,5 +14,5 @@ install: build_script: - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload" - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:59:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove Base.hs, move Stage definition to Stage.hs. (03f90e7) Message-ID: <20171026235942.AAA623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03f90e74e6d472f26f22baef563c38d088dadb8f/ghc >--------------------------------------------------------------- commit 03f90e74e6d472f26f22baef563c38d088dadb8f Author: Andrey Mokhov Date: Sun Jul 19 01:26:22 2015 +0100 Remove Base.hs, move Stage definition to Stage.hs. >--------------------------------------------------------------- 03f90e74e6d472f26f22baef563c38d088dadb8f src/Base.hs | 74 ---------------------------------- src/Builder.hs | 4 +- src/Config.hs | 3 +- src/Expression.hs | 5 ++- src/Main.hs | 2 +- src/Oracles.hs | 13 +++--- src/Oracles/ArgsHash.hs | 3 +- src/Oracles/Base.hs | 2 +- src/Oracles/DependencyList.hs | 11 ++--- src/Oracles/Flag.hs | 2 +- src/Oracles/PackageData.hs | 89 ++++++++++++++++++++--------------------- src/Oracles/Setting.hs | 17 ++++---- src/Package.hs | 3 +- src/Rules.hs | 5 ++- src/Rules/Actions.hs | 2 +- src/Rules/Data.hs | 8 ++-- src/Rules/Oracles.hs | 3 +- src/Rules/Package.hs | 2 +- src/Settings/Args.hs | 3 +- src/Settings/Default.hs | 2 +- src/Settings/GhcCabal.hs | 7 +++- src/Settings/GhcPkg.hs | 2 +- src/Settings/Packages.hs | 3 +- src/Settings/TargetDirectory.hs | 3 +- src/Settings/User.hs | 4 +- src/Settings/Util.hs | 3 +- src/Settings/Ways.hs | 2 +- src/Stage.hs | 17 ++++++++ src/Switches.hs | 2 +- src/Target.hs | 2 +- src/Util.hs | 7 ++-- src/Way.hs | 3 +- 32 files changed, 135 insertions(+), 173 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 03f90e74e6d472f26f22baef563c38d088dadb8f From git at git.haskell.org Thu Oct 26 23:59:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Oracle (aff54c8) Message-ID: <20171026235945.2FA4A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aff54c850f52d875105564d9ef2ec5662cc6c5b2/ghc >--------------------------------------------------------------- commit aff54c850f52d875105564d9ef2ec5662cc6c5b2 Author: Moritz Angermann Date: Thu Jan 7 18:47:46 2016 +0800 Adds Oracle >--------------------------------------------------------------- aff54c850f52d875105564d9ef2ec5662cc6c5b2 shaking-up-ghc.cabal | 2 +- src/Oracles.hs | 2 ++ src/Oracles/AbsoluteCommand.hs | 40 ++++++++++++++++++++++++++++++++++++++++ src/Oracles/WindowsRoot.hs | 13 +------------ src/Rules/Oracles.hs | 15 ++++++++------- 5 files changed, 52 insertions(+), 20 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f9990e9..96efe57 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -22,6 +22,7 @@ executable ghc-shake , Expression , GHC , Oracles + , Oracles.AbsoluteCommand , Oracles.ArgsHash , Oracles.Config , Oracles.Config.Flag @@ -114,7 +115,6 @@ executable ghc-shake , extra >= 1.4 , mtl >= 2.2 , shake >= 0.15 - , split >= 0.2 , transformers >= 0.4 , unordered-containers >= 0.2 default-language: Haskell2010 diff --git a/src/Oracles.hs b/src/Oracles.hs index b77a786..07e92f2 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,4 +1,5 @@ module Oracles ( + module Oracles.AbsoluteCommand, module Oracles.Config, module Oracles.Config.Flag, module Oracles.Config.Setting, @@ -8,6 +9,7 @@ module Oracles ( module Oracles.WindowsRoot ) where +import Oracles.AbsoluteCommand import Oracles.Config import Oracles.Config.Flag import Oracles.Config.Setting diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/AbsoluteCommand.hs new file mode 100644 index 0000000..23de6ff --- /dev/null +++ b/src/Oracles/AbsoluteCommand.hs @@ -0,0 +1,40 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +module Oracles.AbsoluteCommand ( + lookupInPath, absoluteCommandOracle + ) where + +import Base + +newtype AbsoluteCommand = AbsoluteCommand String + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +absoluteCommand :: String -> Action String +absoluteCommand = askOracle . AbsoluteCommand + +-- | Lookup a @command@ in @PATH@ environment. +lookupInPath :: FilePath -> Action FilePath +lookupInPath c + | c /= takeFileName c = return c + | otherwise = absoluteCommand c + +-- | Split function. Splits a string @s@ into chunks +-- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 +wordsWhen :: (Char -> Bool) -> String -> [String] +wordsWhen p s = + case dropWhile p s of + "" -> [] + s' -> w : wordsWhen p s'' + where (w, s'') = break p s' + + +absoluteCommandOracle :: Rules () +absoluteCommandOracle = do + o <- newCache $ \c -> do + envPaths <- wordsWhen (== ':') <$> getEnvWithDefault "" "PATH" + let candidates = map (-/- c) envPaths + -- this will crash if we do not find any valid candidate. + fullCommand <- head <$> filterM doesFileExist candidates + putOracle $ "Found '" ++ c ++ "' at " ++ "'" ++ fullCommand ++ "'" + return fullCommand + _ <- addOracle $ \(AbsoluteCommand c) -> o c + return () diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 4186700..413f289 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -1,10 +1,9 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.WindowsRoot ( - windowsRoot, fixAbsolutePathOnWindows, lookupInPath, topDirectory, windowsRootOracle + windowsRoot, fixAbsolutePathOnWindows, topDirectory, windowsRootOracle ) where import Data.Char (isSpace) -import Data.List.Split (splitOn) import Base import Oracles.Config.Setting @@ -39,16 +38,6 @@ fixAbsolutePathOnWindows path = do else return path --- | Lookup a @command@ in @PATH@ environment. -lookupInPath :: FilePath -> Action FilePath -lookupInPath c - | c /= takeFileName c = return c - | otherwise = do - envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" - let candidates = map (-/- c) envPaths - -- this will crash if we do not find any valid candidate. - head <$> filterM doesFileExist candidates - -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). windowsRootOracle :: Rules () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 92e8a40..a4d6c70 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -7,10 +7,11 @@ import Oracles.ModuleFiles oracleRules :: Rules () oracleRules = do - argsHashOracle -- see Oracles.ArgsHash - configOracle -- see Oracles.Config - dependenciesOracle -- see Oracles.Dependencies - moduleFilesOracle -- see Oracles.ModuleFiles - packageDataOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - windowsRootOracle -- see Oracles.WindowsRoot + absoluteCommandOracle -- see Oracles.WindowsRoot + argsHashOracle -- see Oracles.ArgsHash + configOracle -- see Oracles.Config + dependenciesOracle -- see Oracles.Dependencies + moduleFilesOracle -- see Oracles.ModuleFiles + packageDataOracle -- see Oracles.PackageData + packageDepsOracle -- see Oracles.PackageDeps + windowsRootOracle -- see Oracles.WindowsRoot From git at git.haskell.org Thu Oct 26 23:59:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on package configuration when compiling package sources with GHC. (83c1e5e) Message-ID: <20171026235945.6A62F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/83c1e5e78010487dbe053c39b921c917ddb7f282/ghc >--------------------------------------------------------------- commit 83c1e5e78010487dbe053c39b921c917ddb7f282 Author: Andrey Mokhov Date: Sat Feb 6 02:39:27 2016 +0000 Depend on package configuration when compiling package sources with GHC. See #205. >--------------------------------------------------------------- 83c1e5e78010487dbe053c39b921c917ddb7f282 src/Settings/Builders/Ghc.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 74381eb..cc2afd5 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -103,9 +103,13 @@ wayGhcArgs = do -- TODO: Improve handling of "-hide-all-packages" packageGhcArgs :: Args packageGhcArgs = do + stage <- getStage pkg <- getPackage compId <- getPkgData ComponentId pkgDepIds <- getPkgDataList DepIds + lift . when (isLibrary pkg) $ do + conf <- pkgConfFile stage pkg + need [conf] mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" From git at git.haskell.org Thu Oct 26 23:59:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor oracles, add comments. (49419bc) Message-ID: <20171026235946.623393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49419bc553873c21efebe87f4e0aa343013d4bad/ghc >--------------------------------------------------------------- commit 49419bc553873c21efebe87f4e0aa343013d4bad Author: Andrey Mokhov Date: Sun Jul 19 16:38:17 2015 +0100 Refactor oracles, add comments. >--------------------------------------------------------------- 49419bc553873c21efebe87f4e0aa343013d4bad src/Builder.hs | 3 -- src/Expression.hs | 1 - src/Main.hs | 1 - src/Oracles.hs | 67 ------------------------------------------- src/Oracles/ArgsHash.hs | 8 ++++-- src/Oracles/Base.hs | 41 +++++++++++++++++++++++--- src/Oracles/DependencyList.hs | 46 +++++++++++++++++++++-------- src/Oracles/Flag.hs | 1 - src/Oracles/PackageData.hs | 55 ++++++++++++++++++++--------------- src/Oracles/Setting.hs | 43 +++++++++++++-------------- src/Rules.hs | 2 ++ src/{ => Rules}/Config.hs | 16 ++++------- src/Rules/Oracles.hs | 7 +++-- src/Settings/GhcCabal.hs | 2 -- src/Settings/Util.hs | 1 - 15 files changed, 141 insertions(+), 153 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 49419bc553873c21efebe87f4e0aa343013d4bad From git at git.haskell.org Thu Oct 26 23:59:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Escape echo quotes. (9024712) Message-ID: <20171026235949.4F6AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/902471256bf5aee2974afb968f0cf5bdbd8cae78/ghc >--------------------------------------------------------------- commit 902471256bf5aee2974afb968f0cf5bdbd8cae78 Author: Andrey Mokhov Date: Thu Jan 7 10:54:09 2016 +0000 Escape echo quotes. See #110. [skip ci] >--------------------------------------------------------------- 902471256bf5aee2974afb968f0cf5bdbd8cae78 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index a5763cc..f74c459 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,5 +14,5 @@ install: build_script: - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Thu Oct 26 23:59:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't run GHC concurrently with ghc-pkg. (116bf85) Message-ID: <20171026235949.684A33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/116bf853352b305eccf1392561d699c551cb07aa/ghc >--------------------------------------------------------------- commit 116bf853352b305eccf1392561d699c551cb07aa Author: Andrey Mokhov Date: Sat Feb 6 02:40:15 2016 +0000 Don't run GHC concurrently with ghc-pkg. Fix #205. >--------------------------------------------------------------- 116bf853352b305eccf1392561d699c551cb07aa src/Rules/Compile.hs | 14 +++++++++----- src/Rules/Data.hs | 24 ++---------------------- src/Rules/Register.hs | 30 ++++++++++++++++++++++++------ src/Rules/Resources.hs | 13 +++++++++---- 4 files changed, 44 insertions(+), 37 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index b27d36e..13af013 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -8,7 +8,7 @@ import Rules.Resources import Settings compilePackage :: Resources -> PartialTarget -> Rules () -compilePackage _ target @ (PartialTarget stage pkg) = do +compilePackage rs target @ (PartialTarget stage pkg) = do let buildPath = targetPath stage pkg -/- "build" matchBuildResult buildPath "hi" ?> \hi -> @@ -17,7 +17,8 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let way = detectWay hi (src, deps) <- dependencies buildPath $ hi -<.> osuf way need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [hi] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [hi] else need [ hi -<.> osuf (detectWay hi) ] matchBuildResult buildPath "hi-boot" ?> \hiboot -> @@ -26,7 +27,8 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let way = detectWay hiboot (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf way need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [hiboot] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [hiboot] else need [ hiboot -<.> obootsuf (detectWay hiboot) ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) @@ -41,7 +43,8 @@ compilePackage _ target @ (PartialTarget stage pkg) = do if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) then need $ (obj -<.> hisuf (detectWay obj)) : src : deps else need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [obj] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases matchBuildResult buildPath "o-boot" ?> \obj -> do @@ -50,4 +53,5 @@ compilePackage _ target @ (PartialTarget stage pkg) = do if compileInterfaceFilesSeparately then need $ (obj -<.> hibootsuf (detectWay obj)) : src : deps else need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [obj] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [obj] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index ade93fd..00ec163 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -12,11 +12,10 @@ import Rules.Libffi import Rules.Resources import Settings import Settings.Builders.Common -import Settings.Packages.Rts -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: Resources -> PartialTarget -> Rules () -buildPackageData rs target @ (PartialTarget stage pkg) = do +buildPackageData _ target @ (PartialTarget stage pkg) = do let cabalFile = pkgCabalFile pkg configure = pkgPath pkg -/- "configure" dataFile = pkgDataFile stage pkg @@ -34,8 +33,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - depConfs <- traverse (pkgConfFile stage) depPkgs - orderOnly depConfs + need =<< traverse (pkgConfFile stage) depPkgs -- TODO: get rid of this, see #113 let inTreeMk = oldPath -/- takeFileName dataFile @@ -126,24 +124,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." - need [rtsConf] - buildWithResources [(resGhcPkg rs, 1)] $ - fullTarget target (GhcPkg stage) [rtsConf] [] - - rtsConf %> \_ -> do - orderOnly $ generatedDependencies stage pkg - need [ rtsConfIn ] - build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] - - let fixRtsConf = unlines - . map - ( replace "\"\"" "" - . replace "rts/dist/build" rtsBuildPath ) - . filter (not . null) - . lines - - fixFile rtsConf fixRtsConf - -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- For example, get rid of diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 8c3ec73..d1b5312 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -6,11 +6,10 @@ import Base import Expression import GHC import Rules.Actions +import Rules.Libffi import Rules.Resources import Settings - --- matchPkgConf :: FilePath -> Bool --- matchPkgConf file = +import Settings.Packages.Rts -- Build package-data.mk by using GhcCabal to process pkgCabal file registerPackage :: Resources -> PartialTarget -> Rules () @@ -21,7 +20,7 @@ registerPackage rs target @ (PartialTarget stage pkg) = do Nothing -> False Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf" - when (stage <= Stage1) $ match ?> \_ -> do + when (stage <= Stage1) $ match ?> \conf -> do -- This produces pkgConfig. TODO: Add explicit tracking need [pkgDataFile stage pkg] @@ -35,5 +34,24 @@ registerPackage rs target @ (PartialTarget stage pkg) = do fixFile pkgConfig fixPkgConf - buildWithResources [(resGhcPkg rs, 1)] $ - fullTarget target (GhcPkg stage) [pkgConfig] [] + buildWithResources [(resPackageDb rs, resPackageDbLimit)] $ + fullTarget target (GhcPkg stage) [pkgConfig] [conf] + + when (pkg == rts && stage == Stage1) $ do + packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do + need [rtsConf] + buildWithResources [(resPackageDb rs, resPackageDbLimit)] $ + fullTarget target (GhcPkg stage) [rtsConf] [conf] + + rtsConf %> \_ -> do + need [ pkgDataFile Stage1 rts, rtsConfIn ] + build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] + + let fixRtsConf = unlines + . map + ( replace "\"\"" "" + . replace "rts/dist/build" rtsBuildPath ) + . filter (not . null) + . lines + + fixFile rtsConf fixRtsConf diff --git a/src/Rules/Resources.hs b/src/Rules/Resources.hs index d5e58fe..40939e0 100644 --- a/src/Rules/Resources.hs +++ b/src/Rules/Resources.hs @@ -1,12 +1,17 @@ -module Rules.Resources (resourceRules, Resources (..)) where +module Rules.Resources (resourceRules, Resources (..), resPackageDbLimit) where import Base data Resources = Resources { - resGhcPkg :: Resource + resPackageDb :: Resource } --- We cannot register multiple packages in parallel: +-- We cannot register multiple packages in parallel. Also we cannot run GHC +-- when the package database is being mutated by "ghc-pkg". This is a classic +-- concurrent read exclusive write (CREW) conflict. resourceRules :: Rules Resources -resourceRules = Resources <$> newResource "ghc-pkg" 1 +resourceRules = Resources <$> newResource "package-db" resPackageDbLimit + +resPackageDbLimit :: Int +resPackageDbLimit = 1000 From git at git.haskell.org Thu Oct 26 23:59:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify Rules.Config. (7dc414c) Message-ID: <20171026235950.276CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7dc414caf7aa55531c2d25f69c785bec30f192c7/ghc >--------------------------------------------------------------- commit 7dc414caf7aa55531c2d25f69c785bec30f192c7 Author: Andrey Mokhov Date: Sun Jul 19 16:55:54 2015 +0100 Simplify Rules.Config. >--------------------------------------------------------------- 7dc414caf7aa55531c2d25f69c785bec30f192c7 src/Main.hs | 3 +-- src/Rules/Config.hs | 18 ++++++++---------- 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 8bd3384..50420af 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -4,6 +4,5 @@ import Development.Shake main = shakeArgs shakeOptions{shakeFiles="_build/"} $ do oracleRules -- see module Rules.Oracles packageRules -- see module Rules - autoconfRules -- see module Config - configureRules -- see module Config + configRules -- see module Rules.Config generateTargets -- see module Rules diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 2aa3988..3fb4c6a 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -1,20 +1,18 @@ module Rules.Config ( - autoconfRules, configureRules + configRules ) where import Util import Oracles.Base -autoconfRules :: Rules () -autoconfRules = do - "configure" %> \out -> do - copyFile' (configPath "configure.ac") "configure.ac" - putColoured White $ "Running autoconf..." - cmd "bash autoconf" -- TODO: get rid of 'bash' - -configureRules :: Rules () -configureRules = do +configRules :: Rules () +configRules = do configPath "system.config" %> \out -> do need [configPath "system.config.in", "configure"] putColoured White "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' + + "configure" %> \out -> do + copyFile' (configPath "configure.ac") "configure.ac" + putColoured White $ "Running autoconf..." + cmd "bash autoconf" -- TODO: get rid of 'bash' From git at git.haskell.org Thu Oct 26 23:59:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Call bash with single quotes. (b54121d) Message-ID: <20171026235953.47BFF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b54121d141b55b7b81d5be6e4a2571ab27756fd3/ghc >--------------------------------------------------------------- commit b54121d141b55b7b81d5be6e4a2571ab27756fd3 Author: Andrey Mokhov Date: Thu Jan 7 11:15:24 2016 +0000 Call bash with single quotes. See #110. [skip ci] >--------------------------------------------------------------- b54121d141b55b7b81d5be6e4a2571ab27756fd3 .appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f74c459..c3c4869 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -5,14 +5,14 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" + - bash -lc 'curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1' - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - bash -lc 'mv /home/ghc/tmp/* /home/ghc' build_script: - - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" - - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" + - bash -lc 'cd /home/ghc && ./boot' + - bash -lc 'cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload' + - bash -lc 'cd /home/ghc && ./shake-build/build.bat -j --no-progress' From git at git.haskell.org Thu Oct 26 23:59:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't run GHC -M concurrently with ghc-pkg. (44fd16d) Message-ID: <20171026235953.79D4E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44fd16dbaabe96205c493952930da708e774febd/ghc >--------------------------------------------------------------- commit 44fd16dbaabe96205c493952930da708e774febd Author: Andrey Mokhov Date: Sat Feb 6 14:53:29 2016 +0000 Don't run GHC -M concurrently with ghc-pkg. See #205. >--------------------------------------------------------------- 44fd16dbaabe96205c493952930da708e774febd src/Rules/Dependencies.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 92ac8db..30a5232 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -10,7 +10,7 @@ import Development.Shake.Util (parseMakefile) -- TODO: simplify handling of AutoApply.cmm buildPackageDependencies :: Resources -> PartialTarget -> Rules () -buildPackageDependencies _ target @ (PartialTarget stage pkg) = +buildPackageDependencies rs target @ (PartialTarget stage pkg) = let path = targetPath stage pkg buildPath = path -/- "build" dropBuild = (pkgPath pkg ++) . drop (length buildPath) @@ -29,7 +29,8 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need srcs if srcs == [] then writeFileChanged out "" - else build $ fullTarget target (GhcM stage) srcs [out] + else buildWithResources [(resPackageDb rs, 1)] $ + fullTarget target (GhcM stage) srcs [out] removeFileIfExists $ out <.> "bak" -- TODO: don't accumulate *.deps into .dependencies From git at git.haskell.org Thu Oct 26 23:59:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix import of IntSet. (6e8416e) Message-ID: <20171026235953.D509F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e8416e2117fd487e89e58ab112c3688093a0055/ghc >--------------------------------------------------------------- commit 6e8416e2117fd487e89e58ab112c3688093a0055 Author: Andrey Mokhov Date: Sun Jul 19 16:59:50 2015 +0100 Fix import of IntSet. >--------------------------------------------------------------- 6e8416e2117fd487e89e58ab112c3688093a0055 src/Way.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index dffd050..c0b49e3 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -18,8 +18,9 @@ import Oracles.Setting import Control.Applicative import Development.Shake import Development.Shake.Classes -import Data.List hiding (delete) -import Data.IntSet (IntSet, elems, member, delete, fromList) +import Data.List +import Data.IntSet (IntSet) +import qualified Data.IntSet as Set data WayUnit = Threaded | Debug @@ -46,13 +47,13 @@ instance Read WayUnit where newtype Way = Way IntSet wayFromUnits :: [WayUnit] -> Way -wayFromUnits = Way . fromList . map fromEnum +wayFromUnits = Way . Set.fromList . map fromEnum wayToUnits :: Way -> [WayUnit] -wayToUnits (Way set) = map toEnum . elems $ set +wayToUnits (Way set) = map toEnum . Set.elems $ set wayUnit :: WayUnit -> Way -> Bool -wayUnit unit (Way set) = fromEnum unit `member` set +wayUnit unit (Way set) = fromEnum unit `Set.member` set instance Show Way where show way = if null tag then "v" else tag @@ -120,7 +121,7 @@ libsuf way @ (Way set) = else do extension <- setting DynamicExtension -- e.g., .dll or .so version <- setting ProjectVersion -- e.g., 7.11.20141222 - let prefix = wayPrefix . Way . delete (fromEnum Dynamic) $ set + let prefix = wayPrefix . Way . Set.delete (fromEnum Dynamic) $ set -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension From git at git.haskell.org Thu Oct 26 23:59:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add copyDirectory to Rules.Actions. (63bbebf) Message-ID: <20171026235957.163263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac/ghc >--------------------------------------------------------------- commit 63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac Author: Andrey Mokhov Date: Sun Feb 7 01:13:05 2016 +0000 Add copyDirectory to Rules.Actions. See #98. >--------------------------------------------------------------- 63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac src/Rules/Actions.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index daa4c5e..9275207 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,8 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, - moveDirectory, fixFile, runConfigure, runMake, runMakeVerbose, applyPatch, - renderLibrary, renderProgram, runBuilder, makeExecutable + copyDirectory, moveDirectory, applyPatch, fixFile, runConfigure, runMake, + runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -82,6 +82,12 @@ removeDirectory dir = do removeDirectoryIfExists dir -- Note, the source directory is untracked +copyDirectory :: FilePath -> FilePath -> Action () +copyDirectory source target = do + putProgressInfo $ renderAction "Copy directory" source target + quietly $ cmd (EchoStdout False) ["cp", "-r", source, target] + +-- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target From git at git.haskell.org Thu Oct 26 23:59:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing generated dependencies for rts, see #123. (f187ca8) Message-ID: <20171026235957.4405B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f187ca8af97a2a45a3a1d09b87dbdc12d4819987/ghc >--------------------------------------------------------------- commit f187ca8af97a2a45a3a1d09b87dbdc12d4819987 Author: Andrey Mokhov Date: Thu Jan 7 11:20:36 2016 +0000 Fix missing generated dependencies for rts, see #123. >--------------------------------------------------------------- f187ca8af97a2a45a3a1d09b87dbdc12d4819987 src/Rules/Data.hs | 5 ++--- src/Rules/Generate.hs | 2 +- 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 29f8d3d..ee15c19 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -104,9 +104,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fullTarget target (GhcPkg stage) [rtsConf] [] rtsConf %> \_ -> do - need [ rtsConfIn - , "includes/ghcautoconf.h" - , "includes/ghcplatform.h" ] + orderOnly $ generatedDependencies stage pkg + need [ rtsConfIn ] build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] let fixRtsConf = unlines diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 3eb1231..8ca7b94 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -76,7 +76,7 @@ generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == ghcPrim = ghcPrimDependencies stage - | pkg == rts = derivedConstantsDependencies + | pkg == rts = includesDependencies ++ derivedConstantsDependencies | stage == Stage0 = defaultDependencies | otherwise = [] From git at git.haskell.org Thu Oct 26 23:59:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:59:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Migrate all user-configurable settings from system.default to Settings/User.hs. (b253397) Message-ID: <20171026235957.AB5AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b253397966a028a13d39b59c1233bef3007eb857/ghc >--------------------------------------------------------------- commit b253397966a028a13d39b59c1233bef3007eb857 Author: Andrey Mokhov Date: Mon Jul 20 00:09:15 2015 +0100 Migrate all user-configurable settings from system.default to Settings/User.hs. >--------------------------------------------------------------- b253397966a028a13d39b59c1233bef3007eb857 cfg/system.config.in | 4 -- src/Builder.hs | 17 ++------- src/Expression.hs | 39 ++++++++++--------- src/Oracles/Flag.hs | 71 ++++++++++++++++++++-------------- src/Oracles/Setting.hs | 38 ++++++++++++++++++- src/Rules/Actions.hs | 5 +-- src/Settings/GhcCabal.hs | 13 ++++--- src/Settings/Packages.hs | 1 + src/Settings/User.hs | 20 +++++++--- src/Settings/Util.hs | 16 ++++++++ src/Settings/Ways.hs | 1 + src/Switches.hs | 99 +++++++----------------------------------------- 12 files changed, 160 insertions(+), 164 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 b253397966a028a13d39b59c1233bef3007eb857 From git at git.haskell.org Fri Oct 27 00:00:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --haddock command line flag. (7f2c6a1) Message-ID: <20171027000001.24B983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7f2c6a1a360d5351fadc3ab9a6cfa322a56b797e/ghc >--------------------------------------------------------------- commit 7f2c6a1a360d5351fadc3ab9a6cfa322a56b797e Author: Andrey Mokhov Date: Sun Feb 7 02:31:37 2016 +0000 Add --haddock command line flag. See #98. >--------------------------------------------------------------- 7f2c6a1a360d5351fadc3ab9a6cfa322a56b797e src/CmdLineFlag.hs | 18 ++++++++++++++---- src/Settings/User.hs | 2 +- 2 files changed, 15 insertions(+), 5 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 0142abb..84d4f11 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,6 +1,6 @@ module CmdLineFlag ( - putCmdLineFlags, cmdFlags, cmdConfigure, Configure (..), cmdFlavour, - Flavour (..), cmdProgressInfo, ProgressInfo (..), cmdSplitObjects + putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdConfigure, Configure (..), + cmdFlavour, Flavour (..), cmdProgressInfo, ProgressInfo (..), cmdSplitObjects ) where import Data.List.Extra @@ -18,7 +18,8 @@ data Flavour = Default | Quick deriving (Eq, Show) -- command line. These flags are not tracked, that is they do not force any -- build rules to be rurun. data Untracked = Untracked - { configure :: Configure + { buildHaddock :: Bool + , configure :: Configure , flavour :: Flavour , progressInfo :: ProgressInfo , splitObjects :: Bool } @@ -27,11 +28,15 @@ data Untracked = Untracked -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked defaultUntracked = Untracked - { configure = SkipConfigure + { buildHaddock = False + , configure = SkipConfigure , flavour = Default , progressInfo = Normal , splitObjects = False } +readBuildHaddock :: Either String (Untracked -> Untracked) +readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } + readConfigure :: Maybe String -> Either String (Untracked -> Untracked) readConfigure ms = maybe (Left "Cannot parse configure") (Right . set) (go $ lower <$> ms) @@ -75,6 +80,8 @@ cmdFlags = "Run configure with ARGS (also run boot if necessary)." , Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") "Build flavour (Default or Quick)." + , Option [] ["haddock"] (NoArg readBuildHaddock) + "Generate Haddock documentation." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") "Progress info style (None, Brief, Normal, or Unicorn)." , Option [] ["split-objects"] (NoArg readSplitObjects) @@ -93,6 +100,9 @@ putCmdLineFlags flags = modifyIORef cmdLineFlags (\f -> foldl (flip id) f flags) getCmdLineFlags :: Untracked getCmdLineFlags = unsafePerformIO $ readIORef cmdLineFlags +cmdBuildHaddock :: Bool +cmdBuildHaddock = buildHaddock getCmdLineFlags + cmdConfigure :: Configure cmdConfigure = configure getCmdLineFlags diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 2cf39aa..dd6150a 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -84,7 +84,7 @@ laxDependencies :: Bool laxDependencies = False buildHaddock :: Predicate -buildHaddock = return False -- FIXME: should be return True, see #98 +buildHaddock = return cmdBuildHaddock -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package From git at git.haskell.org Fri Oct 27 00:00:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring bash quoting back. (2d333d5) Message-ID: <20171027000002.11ACC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d333d5fdf2b85180eb03a59764d73ff3477ea19/ghc >--------------------------------------------------------------- commit 2d333d5fdf2b85180eb03a59764d73ff3477ea19 Author: Andrey Mokhov Date: Thu Jan 7 12:17:15 2016 +0000 Bring bash quoting back. See #110. [skip ci] >--------------------------------------------------------------- 2d333d5fdf2b85180eb03a59764d73ff3477ea19 .appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index c3c4869..f74c459 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -5,14 +5,14 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - - bash -lc 'curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1' + - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - - bash -lc 'mv /home/ghc/tmp/* /home/ghc' + - bash -lc "mv /home/ghc/tmp/* /home/ghc" build_script: - - bash -lc 'cd /home/ghc && ./boot' - - bash -lc 'cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload' - - bash -lc 'cd /home/ghc && ./shake-build/build.bat -j --no-progress' + - bash -lc "cd /home/ghc && ./boot" + - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:00:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve performance by caching windows root lookup. (580d397) Message-ID: <20171027000002.C8A323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/580d39722d627eb95eab63d374441d6c92276f9e/ghc >--------------------------------------------------------------- commit 580d39722d627eb95eab63d374441d6c92276f9e Author: Andrey Mokhov Date: Mon Jul 20 10:06:06 2015 +0100 Improve performance by caching windows root lookup. >--------------------------------------------------------------- 580d39722d627eb95eab63d374441d6c92276f9e src/Builder.hs | 6 +++--- src/Oracles/PackageData.hs | 1 + src/Oracles/Setting.hs | 8 +++----- src/Oracles/WindowsRoot.hs | 28 ++++++++++++++++++++++++++++ src/Rules/Oracles.hs | 10 +++++++--- src/Settings/Args.hs | 1 + 6 files changed, 43 insertions(+), 11 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 0001fc4..91c6fa3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -9,6 +9,7 @@ import Stage import Data.List import Oracles.Base import Oracles.Setting +import Oracles.WindowsRoot import GHC.Generics -- A Builder is an external command invoked in separate process using Shake.cmd @@ -58,7 +59,6 @@ builderPath builder = do specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- TODO: get rid of code duplication (windowsHost) -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". fixAbsolutePathOnWindows :: FilePath -> Action FilePath @@ -67,8 +67,8 @@ fixAbsolutePathOnWindows path = do -- Note, below is different from FilePath.isAbsolute: if (windows && "/" `isPrefixOf` path) then do - Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] - return . unifyPath $ dropWhileEnd isSpace out ++ drop 1 path + root <- windowsRoot + return . unifyPath $ root ++ drop 1 path else return path diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index f12b842..3b00cf8 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -39,6 +39,7 @@ data PackageDataList = Modules FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +-- TODO: is this needed? askPackageData :: FilePath -> String -> Action String askPackageData path key = do let fullKey = replaceSeparators '_' $ path ++ "_" ++ key diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 02073e9..9694c00 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -12,8 +12,8 @@ import Oracles.Base -- setting TargetOs looks up the config file and returns "mingw32". -- -- SettingList is used for multiple string values separated by spaces, such --- as 'src-hc-args = -H32m -O'. --- settingList SrcHcArgs therefore returns a list of strings ["-H32", "-O"]. +-- as 'gmp-include-dirs = a b'. +-- settingList GmpIncludeDirs therefore returns a list of strings ["a", "b"]. data Setting = TargetOs | TargetArch | TargetPlatformFull @@ -22,8 +22,7 @@ data Setting = TargetOs | ProjectVersion | GhcSourcePath -data SettingList = SrcHcArgs - | ConfCcArgs Stage +data SettingList = ConfCcArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage | ConfCppArgs Stage @@ -44,7 +43,6 @@ setting key = askConfig $ case key of settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of - SrcHcArgs -> "src-hc-args" ConfCcArgs stage -> "conf-cc-args-stage" ++ show stage ConfCppArgs stage -> "conf-cpp-args-stage" ++ show stage ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show stage diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs new file mode 100644 index 0000000..261ca93 --- /dev/null +++ b/src/Oracles/WindowsRoot.hs @@ -0,0 +1,28 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} + +module Oracles.WindowsRoot ( + windowsRoot, windowsRootOracle + ) where + +import Util +import Oracles.Base +import Data.List + +newtype WindowsRoot = WindowsRoot () + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +-- Looks up cygwin/msys root on Windows +windowsRoot :: Action String +windowsRoot = askOracle $ WindowsRoot () + +-- Oracle for windowsRoot. This operation requires caching as looking up +-- the root is slow (at least the current implementation). +windowsRootOracle :: Rules () +windowsRootOracle = do + root <- newCache $ \() -> do + Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] + let root = dropWhileEnd isSpace out + putOracle $ "Detected root on Windows: " ++ root + return root + addOracle $ \WindowsRoot{} -> root () + return () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 7c646be..ba15031 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -5,9 +5,13 @@ module Rules.Oracles ( import Oracles.Base import Oracles.ArgsHash import Oracles.PackageData +import Oracles.WindowsRoot import Oracles.DependencyList -import Data.Monoid oracleRules :: Rules () -oracleRules = - configOracle <> packageDataOracle <> dependencyListOracle <> argsHashOracle +oracleRules = do + configOracle -- see Oracles.Base + packageDataOracle -- see Oracles.PackageData + dependencyListOracle -- see Oracles.DependencyList + argsHashOracle -- see Oracles.ArgsHash + windowsRootOracle -- see Oracles.WindowsRoot diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 78b4f3d..3031093 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -11,6 +11,7 @@ args :: Args args = defaultArgs <> userArgs -- TODO: add all other settings +-- TODO: add src-hc-args = -H32m -O defaultArgs :: Args defaultArgs = mconcat [ cabalArgs From git at git.haskell.org Fri Oct 27 00:00:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy generated files to old build directories. (90c59d1) Message-ID: <20171027000004.C3B793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90c59d1382021802b10c385b93b70a6967a25719/ghc >--------------------------------------------------------------- commit 90c59d1382021802b10c385b93b70a6967a25719 Author: Andrey Mokhov Date: Sun Feb 7 02:32:32 2016 +0000 Copy generated files to old build directories. See #98. >--------------------------------------------------------------- 90c59d1382021802b10c385b93b70a6967a25719 src/Rules/Generate.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 9c67760..4ced436 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -3,6 +3,8 @@ module Rules.Generate ( includesDependencies, derivedConstantsPath, generatedDependencies ) where +import qualified System.Directory as IO + import Base import Expression import GHC @@ -144,19 +146,32 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] build $ fullTarget target GenPrimopCode [primopsTxt stage] [file] + -- TODO: this is temporary hack, get rid of this (#113) + let oldPath = pkgPath pkg -/- targetDirectory stage pkg -/- "build" + newFile = oldPath ++ (drop (length buildPath) file) + createDirectory $ takeDirectory newFile + liftIO $ IO.copyFile file newFile + putSuccess $ "| Duplicate file " ++ file ++ " -> " ++ newFile when (pkg == rts) $ buildPath -/- "AutoApply.cmm" %> \file -> do build $ fullTarget target GenApply [] [file] priority 2.0 $ do + -- TODO: this is temporary hack, get rid of this (#113) + let oldPath = pkgPath pkg -/- targetDirectory stage pkg -/- "build" + olden f = oldPath ++ (drop (length buildPath) f) + when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs + olden file <~ generateConfigHs -- TODO: get rid of this (#113) when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH + olden file <~ generateGhcBootPlatformH -- TODO: get rid of this (#113) when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do file <~ generateVersionHs + olden file <~ generateVersionHs -- TODO: get rid of this (#113) when (pkg == runGhc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file From git at git.haskell.org Fri Oct 27 00:00:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Moves wordsWhen into Base, and adjusts names and types to be more descriptive. (1d3de4c) Message-ID: <20171027000005.947A43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1d3de4cf66717bd5c10dda3b10b305aa736abddb/ghc >--------------------------------------------------------------- commit 1d3de4cf66717bd5c10dda3b10b305aa736abddb Author: Moritz Angermann Date: Thu Jan 7 20:17:23 2016 +0800 Moves wordsWhen into Base, and adjusts names and types to be more descriptive. >--------------------------------------------------------------- 1d3de4cf66717bd5c10dda3b10b305aa736abddb src/Base.hs | 11 ++++++++++- src/Builder.hs | 2 +- src/Oracles/AbsoluteCommand.hs | 20 ++++++-------------- 3 files changed, 17 insertions(+), 16 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 36f2eb9..8830a7c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -24,7 +24,7 @@ module Base ( -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, replace, quote, chunksOfSize, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), - versionToInt, removeFileIfExists, removeDirectoryIfExists + versionToInt, removeFileIfExists, removeDirectoryIfExists, wordsWhen ) where import Control.Applicative @@ -238,3 +238,12 @@ removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f removeDirectoryIfExists :: FilePath -> Action () removeDirectoryIfExists d = liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d + +-- | Split function. Splits a string @s@ into chunks +-- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 +wordsWhen :: (Char -> Bool) -> String -> [String] +wordsWhen p s = + case dropWhile p s of + "" -> [] + s' -> w : wordsWhen p s'' + where (w, s'') = break p s' diff --git a/src/Builder.hs b/src/Builder.hs index 0613452..743c956 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -98,7 +98,7 @@ builderPath builder = do case (path, windows) of ("", _) -> return path (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) - (p, False) -> lookupInPath (p -<.> exe) + (p, False) -> lookupInPathOracle (p -<.> exe) getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/AbsoluteCommand.hs index 23de6ff..c60f429 100644 --- a/src/Oracles/AbsoluteCommand.hs +++ b/src/Oracles/AbsoluteCommand.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.AbsoluteCommand ( - lookupInPath, absoluteCommandOracle + lookupInPathOracle, absoluteCommandOracle ) where import Base @@ -8,25 +8,17 @@ import Base newtype AbsoluteCommand = AbsoluteCommand String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -absoluteCommand :: String -> Action String +-- | Fetches the absolute FilePath to a given FilePath from the +-- Oracle. +absoluteCommand :: FilePath -> Action FilePath absoluteCommand = askOracle . AbsoluteCommand -- | Lookup a @command@ in @PATH@ environment. -lookupInPath :: FilePath -> Action FilePath -lookupInPath c +lookupInPathOracle :: FilePath -> Action FilePath +lookupInPathOracle c | c /= takeFileName c = return c | otherwise = absoluteCommand c --- | Split function. Splits a string @s@ into chunks --- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 -wordsWhen :: (Char -> Bool) -> String -> [String] -wordsWhen p s = - case dropWhile p s of - "" -> [] - s' -> w : wordsWhen p s'' - where (w, s'') = break p s' - - absoluteCommandOracle :: Rules () absoluteCommandOracle = do o <- newCache $ \c -> do From git at git.haskell.org Fri Oct 27 00:00:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop stringly-typed configuration keys. (4512f27) Message-ID: <20171027000006.3DA953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4512f2736c3fec57c6e067c760a229915abff307/ghc >--------------------------------------------------------------- commit 4512f2736c3fec57c6e067c760a229915abff307 Author: Andrey Mokhov Date: Fri Jul 24 00:21:19 2015 +0100 Drop stringly-typed configuration keys. >--------------------------------------------------------------- 4512f2736c3fec57c6e067c760a229915abff307 src/Settings/GhcCabal.hs | 21 ++++++++++----------- src/Settings/Util.hs | 29 ++++++++--------------------- src/Switches.hs | 11 +++++++---- 3 files changed, 25 insertions(+), 36 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 0e4db8f..05ec1fc 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -3,7 +3,6 @@ module Settings.GhcCabal ( ) where import Way -import Stage import Builder import Package import Util @@ -36,7 +35,7 @@ cabalArgs = builder GhcCabal ? do , configureArgs , stage0 ? packageConstraints , with $ Gcc stage - , notStage Stage0 ? with Ld + , notStage0 ? with Ld , with Ar , with Alex , with Happy ] @@ -65,25 +64,25 @@ configureArgs = do let conf key = appendSubD $ "--configure-option=" ++ key cFlags = mconcat [ ccArgs , remove ["-Werror"] - , argStagedConfig "conf-cc-args" ] - ldFlags = ldArgs <> argStagedConfig "conf-gcc-linker-args" - cppFlags = cppArgs <> argStagedConfig "conf-cpp-args" + , argSettingList $ ConfCcArgs stage ] + ldFlags = ldArgs <> (argSettingList $ ConfGccLinkerArgs stage) + cppFlags = cppArgs <> (argSettingList $ ConfCppArgs stage) mconcat [ conf "CFLAGS" cFlags , conf "LDFLAGS" ldFlags , conf "CPPFLAGS" cppFlags , appendSubD "--gcc-options" $ cFlags <> ldFlags - , conf "--with-iconv-includes" $ argConfig "iconv-include-dirs" - , conf "--with-iconv-libraries" $ argConfig "iconv-lib-dirs" - , conf "--with-gmp-includes" $ argConfig "gmp-include-dirs" - , conf "--with-gmp-libraries" $ argConfig "gmp-lib-dirs" + , conf "--with-iconv-includes" $ argSettingList IconvIncludeDirs + , conf "--with-iconv-libraries" $ argSettingList IconvLibDirs + , conf "--with-gmp-includes" $ argSettingList GmpIncludeDirs + , conf "--with-gmp-libraries" $ argSettingList GmpLibDirs -- TODO: why TargetPlatformFull and not host? - , crossCompiling ? (conf "--host" $ argConfig "target-platform-full") + , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" . argM . builderPath $ Gcc stage ] bootPackageDbArgs :: Args bootPackageDbArgs = do - sourcePath <- lift $ askConfig "ghc-source-path" + sourcePath <- lift . setting $ GhcSourcePath arg $ "--package-db=" ++ sourcePath "libraries/bootstrapping.conf" -- This is a positional argument, hence: diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 82be349..5f0d035 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -1,7 +1,7 @@ module Settings.Util ( -- Primitive settings elements arg, argPath, argM, - argConfig, argStagedConfig, argConfigList, argStagedConfigList, + argSetting, argSettingList, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -13,11 +13,11 @@ module Settings.Util ( ) where import Util -import Stage import Builder -import Settings.User -import Oracles.Base import Expression +import Oracles.Base +import Oracles.Setting +import Settings.User -- A single argument. arg :: String -> Args @@ -30,24 +30,11 @@ argPath = append . return . unifyPath argM :: Action String -> Args argM = appendM . fmap return -argConfig :: String -> Args -argConfig = appendM . fmap return . askConfig - -argConfigList :: String -> Args -argConfigList = appendM . fmap words . askConfig +argSetting :: Setting -> Args +argSetting = argM . setting -stagedKey :: Stage -> String -> String -stagedKey stage key = key ++ "-stage" ++ show stage - -argStagedConfig :: String -> Args -argStagedConfig key = do - stage <- asks getStage - argConfig (stagedKey stage key) - -argStagedConfigList :: String -> Args -argStagedConfigList key = do - stage <- asks getStage - argConfigList (stagedKey stage key) +argSettingList :: SettingList -> Args +argSettingList = appendM . settingList -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal appendCcArgs :: [String] -> Args diff --git a/src/Switches.hs b/src/Switches.hs index 8d5e124..3a56a5a 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,5 +1,5 @@ module Switches ( - notStage, stage0, stage1, stage2, + stage0, stage1, stage2, notStage, notStage0, registerPackage, splitObjects ) where @@ -9,9 +9,6 @@ import Oracles.Setting import Expression -- Derived predicates -notStage :: Stage -> Predicate -notStage = notP . stage - stage0 :: Predicate stage0 = stage Stage0 @@ -21,6 +18,12 @@ stage1 = stage Stage1 stage2 :: Predicate stage2 = stage Stage2 +notStage :: Stage -> Predicate +notStage = notP . stage + +notStage0 :: Predicate +notStage0 = notP stage0 + -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate registerPackage = return True From git at git.haskell.org Fri Oct 27 00:00:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy haddock-prologue.txt to new build directory. (7122295) Message-ID: <20171027000008.8F9333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7122295adffb0c254bfbd39a394e8915ac0e806a/ghc >--------------------------------------------------------------- commit 7122295adffb0c254bfbd39a394e8915ac0e806a Author: Andrey Mokhov Date: Sun Feb 7 02:33:04 2016 +0000 Copy haddock-prologue.txt to new build directory. See #98. >--------------------------------------------------------------- 7122295adffb0c254bfbd39a394e8915ac0e806a src/Rules/Data.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 00ec163..dc77d21 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -47,6 +47,8 @@ buildPackageData _ target @ (PartialTarget stage pkg) = do createDirectory $ targetPath stage pkg -/- "build/autogen" forM_ autogenFiles $ \file -> do copyFile (oldPath -/- file) (targetPath stage pkg -/- file) + let haddockPrologue = "haddock-prologue.txt" + copyFile (oldPath -/- haddockPrologue) (targetPath stage pkg -/- haddockPrologue) postProcessPackageData stage pkg dataFile From git at git.haskell.org Fri Oct 27 00:00:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Renames absoluteCommand to lookupInPath (6f88557) Message-ID: <20171027000009.515A93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6f88557b1fa263bf22f698ec3384a0ab37ed3447/ghc >--------------------------------------------------------------- commit 6f88557b1fa263bf22f698ec3384a0ab37ed3447 Author: Moritz Angermann Date: Thu Jan 7 20:37:59 2016 +0800 Renames absoluteCommand to lookupInPath >--------------------------------------------------------------- 6f88557b1fa263bf22f698ec3384a0ab37ed3447 shaking-up-ghc.cabal | 2 +- src/Builder.hs | 2 +- src/Oracles.hs | 4 ++-- .../{AbsoluteCommand.hs => LookupInPath.hs} | 22 +++++++++++----------- src/Rules/Oracles.hs | 16 ++++++++-------- 5 files changed, 23 insertions(+), 23 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 96efe57..c680b85 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -22,12 +22,12 @@ executable ghc-shake , Expression , GHC , Oracles - , Oracles.AbsoluteCommand , Oracles.ArgsHash , Oracles.Config , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies + , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData , Oracles.PackageDeps diff --git a/src/Builder.hs b/src/Builder.hs index 743c956..0613452 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -98,7 +98,7 @@ builderPath builder = do case (path, windows) of ("", _) -> return path (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) - (p, False) -> lookupInPathOracle (p -<.> exe) + (p, False) -> lookupInPath (p -<.> exe) getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles.hs b/src/Oracles.hs index 07e92f2..564c7bb 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,19 +1,19 @@ module Oracles ( - module Oracles.AbsoluteCommand, module Oracles.Config, module Oracles.Config.Flag, module Oracles.Config.Setting, module Oracles.Dependencies, + module Oracles.LookupInPath, module Oracles.PackageData, module Oracles.PackageDeps, module Oracles.WindowsRoot ) where -import Oracles.AbsoluteCommand import Oracles.Config import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Dependencies +import Oracles.LookupInPath import Oracles.PackageData import Oracles.PackageDeps import Oracles.WindowsRoot diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/LookupInPath.hs similarity index 61% rename from src/Oracles/AbsoluteCommand.hs rename to src/Oracles/LookupInPath.hs index c60f429..c2a05e2 100644 --- a/src/Oracles/AbsoluteCommand.hs +++ b/src/Oracles/LookupInPath.hs @@ -1,26 +1,26 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} -module Oracles.AbsoluteCommand ( - lookupInPathOracle, absoluteCommandOracle +module Oracles.LookupInPath ( + lookupInPath, lookupInPathOracle ) where import Base -newtype AbsoluteCommand = AbsoluteCommand String +newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- | Fetches the absolute FilePath to a given FilePath from the -- Oracle. -absoluteCommand :: FilePath -> Action FilePath -absoluteCommand = askOracle . AbsoluteCommand +commandPath :: FilePath -> Action FilePath +commandPath = askOracle . LookupInPath -- | Lookup a @command@ in @PATH@ environment. -lookupInPathOracle :: FilePath -> Action FilePath -lookupInPathOracle c +lookupInPath :: FilePath -> Action FilePath +lookupInPath c | c /= takeFileName c = return c - | otherwise = absoluteCommand c + | otherwise = commandPath c -absoluteCommandOracle :: Rules () -absoluteCommandOracle = do +lookupInPathOracle :: Rules () +lookupInPathOracle = do o <- newCache $ \c -> do envPaths <- wordsWhen (== ':') <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths @@ -28,5 +28,5 @@ absoluteCommandOracle = do fullCommand <- head <$> filterM doesFileExist candidates putOracle $ "Found '" ++ c ++ "' at " ++ "'" ++ fullCommand ++ "'" return fullCommand - _ <- addOracle $ \(AbsoluteCommand c) -> o c + _ <- addOracle $ \(LookupInPath c) -> o c return () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index a4d6c70..f44b4ad 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -7,11 +7,11 @@ import Oracles.ModuleFiles oracleRules :: Rules () oracleRules = do - absoluteCommandOracle -- see Oracles.WindowsRoot - argsHashOracle -- see Oracles.ArgsHash - configOracle -- see Oracles.Config - dependenciesOracle -- see Oracles.Dependencies - moduleFilesOracle -- see Oracles.ModuleFiles - packageDataOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - windowsRootOracle -- see Oracles.WindowsRoot + argsHashOracle -- see Oracles.ArgsHash + configOracle -- see Oracles.Config + dependenciesOracle -- see Oracles.Dependencies + lookupInPathOracle -- see Oracles.LookupInPath + moduleFilesOracle -- see Oracles.ModuleFiles + packageDataOracle -- see Oracles.PackageData + packageDepsOracle -- see Oracles.PackageDeps + windowsRootOracle -- see Oracles.WindowsRoot From git at git.haskell.org Fri Oct 27 00:00:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop old src/Package/Data.hs. (9b560ce) Message-ID: <20171027000010.18D183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b560ce0d998e7561d8102a0bfe6a18867f5e621/ghc >--------------------------------------------------------------- commit 9b560ce0d998e7561d8102a0bfe6a18867f5e621 Author: Andrey Mokhov Date: Fri Jul 24 00:25:32 2015 +0100 Drop old src/Package/Data.hs. >--------------------------------------------------------------- 9b560ce0d998e7561d8102a0bfe6a18867f5e621 src/Package/Data.hs | 153 ---------------------------------------------------- 1 file changed, 153 deletions(-) diff --git a/src/Package/Data.hs b/src/Package/Data.hs deleted file mode 100644 index 03195be..0000000 --- a/src/Package/Data.hs +++ /dev/null @@ -1,153 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package.Data (buildPackageData) where - -import Package.Base -import Targets - -argListDir :: FilePath -argListDir = "shake/arg/buildPackageData" - -libraryArgs :: [Way] -> Args -libraryArgs ways = do - let enable x = ((if x then "--enable-" else "--disable-") ++) - libraryForGhci <- ghcWithInterpreter - && not DynamicGhcPrograms - && vanilla `elem` ways - return $ - [ enable (vanilla `elem` ways) "library-vanilla" - , enable libraryForGhci "library-for-ghci" - , enable (profiling `elem` ways) "library-profiling" - , enable (dynamic `elem` ways) "shared" ] - -configureArgs :: Stage -> Settings -> Args -configureArgs stage settings = - let conf key as = do - s <- unwords <$> args as - unless (null s) $ arg $ "--configure-option=" ++ key ++ "=" ++ s - cflags = [ commonCcArgs `filterOut` ["-Werror"] - , args $ ConfCcArgs stage - -- , customCcArgs settings -- TODO: bring this back - , commonCcWarninigArgs ] -- TODO: check why cflags are glued - ldflags = [ commonLdArgs - , args $ ConfGccLinkerArgs stage - , customLdArgs settings ] - cppflags = [ commonCppArgs - , args $ ConfCppArgs stage - , customCppArgs settings ] - in args [ conf "CFLAGS" cflags - , conf "LDFLAGS" ldflags - , conf "CPPFLAGS" cppflags - , arg $ concat <$> - arg "--gcc-options=" <> args cflags <> arg " " <> args ldflags - , conf "--with-iconv-includes" IconvIncludeDirs - , conf "--with-iconv-libraries" IconvLibDirs - , conf "--with-gmp-includes" GmpIncludeDirs - , conf "--with-gmp-libraries" GmpLibDirs - -- TODO: why TargetPlatformFull and not host? - , when CrossCompiling $ conf "--host" $ arg TargetPlatformFull - , conf "--with-cc" $ arg $ Gcc stage ] - --- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: --- 1) Drop lines containing '$' --- For example, get rid of --- libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ... --- Reason: we don't need them and we can't parse them. --- 2) Replace '/' and '\' with '_' before '=' --- For example libraries/deepseq/dist-install_VERSION = 1.4.0.0 --- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 --- Reason: Shake's built-in makefile parser doesn't recognise slashes - -postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - pkgData <- (filter ('$' `notElem`) . lines) <$> liftIO (readFile file) - length pkgData `seq` writeFileLines file $ map processLine pkgData - where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line - -bootPkgConstraints :: Args -bootPkgConstraints = args $ do - forM (targetPackagesInStage Stage0) $ \pkg @ (Package _ path cabal _) -> do - let cabalPath = path cabal <.> "cabal" - need [cabalPath] - content <- lines <$> liftIO (readFile cabalPath) - let versionLines = filter (("ersion:" `isPrefixOf`) . drop 1) content - case versionLines of - [versionLine] -> return $ args ["--constraint", cabal ++ " == " - ++ dropWhile (not . isDigit) versionLine] - _ -> redError $ "Cannot determine package version in '" - ++ unifyPath cabalPath ++ "'." - -bootPackageDb :: Args -bootPackageDb = do - top <- showArg GhcSourcePath - arg $ unifyPath $ "--package-db=" ++ top "libraries/bootstrapping.conf" - -cabalArgs :: Package -> TodoItem -> Args -cabalArgs pkg @ (Package _ path _ _) todo @ (stage, dist, settings) = args - [ args ["configure", path, dist] - -- this is a positional argument, hence: - -- * if it is empty, we need to emit one empty string argument - -- * otherwise, we must collapse it into one space-separated string - , arg (unwords <$> customDllArgs settings) - , with $ Ghc stage -- TODO: used to be limited to max stage1 GHC - , with $ GhcPkg stage - , customConfArgs settings - , when (stage == Stage0) bootPackageDb - , libraryArgs =<< ways settings - , when (specified HsColour) $ with HsColour - , configureArgs stage settings - , when (stage == Stage0) bootPkgConstraints - , with $ Gcc stage - , when (stage /= Stage0) $ with Ld - , with Ar - , with Alex - , with Happy ] -- TODO: reorder with's - -ghcPkgArgs :: Package -> TodoItem -> Args -ghcPkgArgs (Package _ path _ _) (stage, dist, _) = args $ - [ arg "update" - , arg "--force" - , arg $ unifyPath $ path dist "inplace-pkg-config" - , when (stage == Stage0) bootPackageDb ] - -buildRule :: Package -> TodoItem -> Rules () -buildRule pkg @ (Package name path cabal _) todo @ (stage, dist, settings) = - let pathDist = path dist - cabalPath = path cabal <.> "cabal" - configure = path "configure" - in - -- All these files are produced by a single run of GhcCabal - (pathDist ) <$> - [ "package-data.mk" - , "haddock-prologue.txt" - , "inplace-pkg-config" - , "setup-config" - , "build" "autogen" "cabal_macros.h" - -- TODO: Is this needed? Also check out Paths_cpsa.hs. - -- , "build" "autogen" ("Paths_" ++ name) <.> "hs" - ] &%> \_ -> do - need [cabalPath] - when (doesFileExist $ configure <.> "ac") $ need [configure] - -- GhcCabal will run the configure script, so we depend on it - -- We still don't know who build the configure script from configure.ac - run GhcCabal $ cabalArgs pkg todo - when (registerPackage settings) $ - run (GhcPkg stage) $ ghcPkgArgs pkg todo - postProcessPackageData $ pathDist "package-data.mk" - -- Finally, record the argument list - need [argListPath argListDir pkg stage] - -argListRule :: Package -> TodoItem -> Rules () -argListRule pkg todo @ (stage, _, _) = - (argListPath argListDir pkg stage) %> \out -> do - -- TODO: depend on ALL source files - need $ ["shake/src/Package/Data.hs"] ++ sourceDependecies - cabalList <- argList GhcCabal $ cabalArgs pkg todo - ghcPkgList <- argList (GhcPkg stage) $ ghcPkgArgs pkg todo - writeFileChanged out $ cabalList ++ "\n" ++ ghcPkgList - --- How to build package-data.mk using GhcCabal to process package.cabal -buildPackageData :: Package -> TodoItem -> Rules () -buildPackageData = argListRule <> buildRule From git at git.haskell.org Fri Oct 27 00:00:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Haddock documentation. (e1b6c56) Message-ID: <20171027000012.40D0C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1b6c5688198e78d8c1a6261479f69efdc640e1f/ghc >--------------------------------------------------------------- commit e1b6c5688198e78d8c1a6261479f69efdc640e1f Author: Andrey Mokhov Date: Sun Feb 7 02:34:27 2016 +0000 Fix Haddock documentation. Fix #98. >--------------------------------------------------------------- e1b6c5688198e78d8c1a6261479f69efdc640e1f src/Rules/Documentation.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index e235bfc..533ea47 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -8,6 +8,9 @@ import Rules.Actions import Rules.Resources import Settings +haddockHtmlLib :: FilePath +haddockHtmlLib = "inplace/lib/html/haddock-util.js" + -- Note: this build rule creates plenty of files, not just the .haddock one. -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. @@ -22,9 +25,10 @@ buildPackageDocumentation _ target @ (PartialTarget stage pkg) = let haddocks = [ pkgHaddockFile depPkg | Just depPkg <- map findKnownPackage deps , depPkg /= rts ] - need $ srcs ++ haddocks + need $ srcs ++ haddocks ++ [haddockHtmlLib] -- HsColour sources + -- TODO: what is the output of GhcCabalHsColour? whenM (specified HsColour) $ do pkgConf <- pkgConfFile stage pkg need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf @@ -34,6 +38,11 @@ buildPackageDocumentation _ target @ (PartialTarget stage pkg) = let haddockWay = if dynamicGhcPrograms then dynamic else vanilla build $ fullTargetWithWay target Haddock haddockWay srcs [file] + when (pkg == haddock) $ haddockHtmlLib %> \_ -> do + let dir = takeDirectory haddockHtmlLib + liftIO $ removeFiles dir ["//*"] + copyDirectory "utils/haddock/haddock-api/resources/html" dir + -- # Make the haddocking depend on the library .a file, to ensure -- # that we wait until the library is fully built before we haddock it -- $$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) : $$($1_$2_$$(HADDOCK_WAY)_LIB) From git at git.haskell.org Fri Oct 27 00:00:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Makes wordsWhen more generic. (5ccd03c) Message-ID: <20171027000013.0060A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ccd03cac69896ef8ff2df7a8601aa1baa110c98/ghc >--------------------------------------------------------------- commit 5ccd03cac69896ef8ff2df7a8601aa1baa110c98 Author: Moritz Angermann Date: Thu Jan 7 20:38:11 2016 +0800 Makes wordsWhen more generic. >--------------------------------------------------------------- 5ccd03cac69896ef8ff2df7a8601aa1baa110c98 src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 8830a7c..86ddbf5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -241,9 +241,9 @@ removeDirectoryIfExists d = -- | Split function. Splits a string @s@ into chunks -- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 -wordsWhen :: (Char -> Bool) -> String -> [String] +wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] wordsWhen p s = case dropWhile p s of - "" -> [] + [] -> [] s' -> w : wordsWhen p s'' where (w, s'') = break p s' From git at git.haskell.org Fri Oct 27 00:00:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcM builder. (d2dfdfa) Message-ID: <20171027000013.95B623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2dfdfa91578e2e4ce5b5419986ea08c50b39e74/ghc >--------------------------------------------------------------- commit d2dfdfa91578e2e4ce5b5419986ea08c50b39e74 Author: Andrey Mokhov Date: Fri Jul 24 04:09:40 2015 +0100 Add GhcM builder. >--------------------------------------------------------------- d2dfdfa91578e2e4ce5b5419986ea08c50b39e74 src/Builder.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 91c6fa3..33735d3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -28,6 +28,7 @@ data Builder = Ar | GhcCabal | Gcc Stage | Ghc Stage + | GhcM Stage | GhcPkg Stage deriving (Show, Eq, Generic) @@ -48,6 +49,8 @@ builderKey builder = case builder of Gcc _ -> "gcc" GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" + -- GhcM is currently a synonym for Ghc (to be called with -M flag) + GhcM stage -> builderKey $ Ghc stage builderPath :: Builder -> Action String builderPath builder = do From git at git.haskell.org Fri Oct 27 00:00:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --haddock flag. (52b915f) Message-ID: <20171027000015.B405A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/52b915f9193a726c4a93ccea5e22ebfedcafbe3f/ghc >--------------------------------------------------------------- commit 52b915f9193a726c4a93ccea5e22ebfedcafbe3f Author: Andrey Mokhov Date: Sun Feb 7 02:42:27 2016 +0000 Add --haddock flag. See #98. [skip ci] >--------------------------------------------------------------- 52b915f9193a726c4a93ccea5e22ebfedcafbe3f README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 37a144e..35f8ac3 100644 --- a/README.md +++ b/README.md @@ -61,6 +61,7 @@ don't have to do it manually. Beware, this uses network I/O which may sometimes undesirable. * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). +* `--haddock`: build Haddock documentation. * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). @@ -98,8 +99,8 @@ Current limitations ------------------- The new build system still lacks many important features: * We only build `vanilla` way: [#4][dynamic-issue], [#186][profiling-issue]. -* Documentation is broken: [#98][haddock-issue]. * Validation is not implemented: [#187][validation-issue]. +* Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. @@ -138,7 +139,6 @@ helped me endure and enjoy the project. [test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 [profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 -[haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 From git at git.haskell.org Fri Oct 27 00:00:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build touchy, fix #125. (fee02d9) Message-ID: <20171027000016.860543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3/ghc >--------------------------------------------------------------- commit fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3 Author: Andrey Mokhov Date: Thu Jan 7 12:59:47 2016 +0000 Build touchy, fix #125. >--------------------------------------------------------------- fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3 src/GHC.hs | 14 +++++++++----- src/Rules/Data.hs | 8 ++++++++ src/Settings/Args.hs | 4 +++- src/Settings/Packages.hs | 3 ++- src/Settings/Packages/{Hp2ps.hs => Touchy.hs} | 8 ++++---- 5 files changed, 26 insertions(+), 11 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index d4d5511..6e3a477 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -6,7 +6,7 @@ module GHC ( haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - transformers, unix, win32, xhtml, + touchy, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -28,7 +28,7 @@ defaultKnownPackages = , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time - , transformers, unix, win32, xhtml ] + , touchy, transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) array, base, binary, bytestring, cabal, compiler, containers, compareSizes, @@ -37,7 +37,7 @@ array, base, binary, bytestring, cabal, compiler, containers, compareSizes, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - transformers, unix, win32, xhtml :: Package + touchy, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -83,6 +83,7 @@ stm = library "stm" templateHaskell = library "template-haskell" terminfo = library "terminfo" time = library "time" +touchy = utility "touchy" transformers = library "transformers" unix = library "unix" win32 = library "Win32" @@ -92,7 +93,7 @@ xhtml = library "xhtml" -- TODO: The following utils are not included into the build system because -- they seem to be unused or unrelated to the build process: checkUniques, -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, --- lndir, mkdirhier, testremove, touchy, vagrant +-- lndir, mkdirhier, testremove, vagrant -- GHC build results will be placed into target directories with the following -- typical structure: @@ -102,7 +103,7 @@ xhtml = library "xhtml" defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage _ = stageString stage --- TODO: simplify +-- TODO: simplify, add programInplaceLibPath -- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg @@ -110,6 +111,9 @@ defaultProgramPath stage pkg | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing + | pkg == touchy = case stage of + Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe + _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index ee15c19..46072ce 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -67,6 +67,14 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." + when (pkg == touchy) $ dataFile %> \mk -> do + let prefix = "utils_touchy_" ++ stageString stage ++ "_" + contents = unlines $ map (prefix++) + [ "PROGNAME = touchy" + , "C_SRCS = touchy.c" ] + writeFileChanged mk contents + putSuccess $ "| Successfully generated '" ++ mk ++ "'." + -- Bootstrapping `ghcCabal`: although `ghcCabal` is a proper cabal -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index fb121ed..f2b30fa 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -30,6 +30,7 @@ import Settings.Packages.IntegerGmp import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc +import Settings.Packages.Touchy import Settings.User getArgs :: Expr [String] @@ -75,4 +76,5 @@ defaultPackageArgs = mconcat , integerGmpPackageArgs , iservBinPackageArgs , rtsPackageArgs - , runGhcPackageArgs ] + , runGhcPackageArgs + , touchyPackageArgs ] diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index dba4054..f80f0d0 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -24,7 +24,8 @@ packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] + , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode + , hp2ps, touchy ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] packagesStage1 :: Packages diff --git a/src/Settings/Packages/Hp2ps.hs b/src/Settings/Packages/Touchy.hs similarity index 72% copy from src/Settings/Packages/Hp2ps.hs copy to src/Settings/Packages/Touchy.hs index 26518c6..8345449 100644 --- a/src/Settings/Packages/Hp2ps.hs +++ b/src/Settings/Packages/Touchy.hs @@ -1,13 +1,13 @@ -module Settings.Packages.Hp2ps (hp2psPackageArgs) where +module Settings.Packages.Touchy (touchyPackageArgs) where import Base import Expression -import GHC (hp2ps) +import GHC (touchy) import Predicates (builderGhc, package) import Settings -hp2psPackageArgs :: Args -hp2psPackageArgs = package hp2ps ? do +touchyPackageArgs :: Args +touchyPackageArgs = package touchy ? do path <- getTargetPath let cabalMacros = path -/- "build/autogen/cabal_macros.h" mconcat [ builderGhc ? From git at git.haskell.org Fri Oct 27 00:00:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add apply function for transforming expressions. (505302b) Message-ID: <20171027000017.12EC03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/505302b7e32640ed8782bbf6cb45c02d0c58fe0f/ghc >--------------------------------------------------------------- commit 505302b7e32640ed8782bbf6cb45c02d0c58fe0f Author: Andrey Mokhov Date: Fri Jul 24 04:10:50 2015 +0100 Add apply function for transforming expressions. >--------------------------------------------------------------- 505302b7e32640ed8782bbf6cb45c02d0c58fe0f src/Expression.hs | 21 +++++++++++++-------- 1 file changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index f33e236..7ac380d 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -6,7 +6,8 @@ module Expression ( Expr, DiffExpr, fromDiffExpr, Predicate, PredicateLike (..), applyPredicate, (??), Args, Ways, Packages, - append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, + apply, append, appendM, remove, + appendSub, appendSubD, filterSub, removeSub, interpret, interpretExpr, stage, package, builder, file, way ) where @@ -57,15 +58,19 @@ type Packages = DiffExpr [Package] type Ways = DiffExpr [Way] -- Basic operations on expressions: --- 1) append something to an expression +-- 1) transform an expression by applying a given function +apply :: (a -> a) -> DiffExpr a +apply = return . Diff + +-- 2) append something to an expression append :: Monoid a => a -> DiffExpr a -append x = return . Diff $ (<> x) +append x = apply (<> x) --- 2) remove given elements from a list expression +-- 3) remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] -remove xs = return . Diff $ filter (`notElem` xs) +remove xs = apply . filter $ (`notElem` xs) --- 3) apply a predicate to an expression +-- 4) apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate @@ -105,7 +110,7 @@ appendM mx = lift mx >>= append appendSub :: String -> [String] -> Args appendSub prefix xs | xs' == [] = mempty - | otherwise = return . Diff $ go False + | otherwise = apply . go $ False where xs' = filter (/= "") xs go True [] = [] @@ -120,7 +125,7 @@ appendSubD :: String -> Args -> Args appendSubD prefix diffExpr = fromDiffExpr diffExpr >>= appendSub prefix filterSub :: String -> (String -> Bool) -> Args -filterSub prefix p = return . Diff $ map filterSubstr +filterSub prefix p = apply . map $ filterSubstr where filterSubstr s | prefix `isPrefixOf` s = unwords . filter p . words $ s From git at git.haskell.org Fri Oct 27 00:00:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop duplication of ghc_boot_platform.h (8b24f9f) Message-ID: <20171027000019.5CEFF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8b24f9f05a7daf8b158748f4d04b4872085ec254/ghc >--------------------------------------------------------------- commit 8b24f9f05a7daf8b158748f4d04b4872085ec254 Author: Andrey Mokhov Date: Sun Feb 7 12:30:28 2016 +0000 Drop duplication of ghc_boot_platform.h See #98. >--------------------------------------------------------------- 8b24f9f05a7daf8b158748f4d04b4872085ec254 src/Rules/Generate.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 4ced436..1258d3f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -158,8 +158,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = priority 2.0 $ do -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- targetDirectory stage pkg -/- "build" - olden f = oldPath ++ (drop (length buildPath) f) + let oldPath = pkgPath pkg -/- targetDirectory stage pkg + olden f = oldPath ++ (drop (length (targetPath stage pkg)) f) when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs @@ -167,7 +167,6 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH - olden file <~ generateGhcBootPlatformH -- TODO: get rid of this (#113) when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do file <~ generateVersionHs From git at git.haskell.org Fri Oct 27 00:00:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Download ghc-tarballs manually. (79a0bf3) Message-ID: <20171027000020.2176F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79a0bf31e51d12dbc6209b4ea5c0492530667c4e/ghc >--------------------------------------------------------------- commit 79a0bf31e51d12dbc6209b4ea5c0492530667c4e Author: Andrey Mokhov Date: Thu Jan 7 13:11:16 2016 +0000 Download ghc-tarballs manually. See #110. [skip ci] >--------------------------------------------------------------- 79a0bf31e51d12dbc6209b4ea5c0492530667c4e .appveyor.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f74c459..6821abf 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -11,8 +11,9 @@ install: - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - bash -lc "cd /home/ghc && ./mk/get-win32-tarballs.sh download x86_64" build_script: - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && echo \"\" | ./configure" - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:00:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (7be13bf) Message-ID: <20171027000023.56ED93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7be13bfa70a63ff190245cbfc6779e675e5d6816/ghc >--------------------------------------------------------------- commit 7be13bfa70a63ff190245cbfc6779e675e5d6816 Merge: 8b24f9f 52b915f Author: Andrey Mokhov Date: Sun Feb 7 12:30:56 2016 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 7be13bfa70a63ff190245cbfc6779e675e5d6816 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 00:00:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (86b0a17) Message-ID: <20171027000020.9A3F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86b0a17ad6fab8c9dde6f082b291c2d785f957d0/ghc >--------------------------------------------------------------- commit 86b0a17ad6fab8c9dde6f082b291c2d785f957d0 Author: Andrey Mokhov Date: Fri Jul 24 04:12:31 2015 +0100 Clean up. >--------------------------------------------------------------- 86b0a17ad6fab8c9dde6f082b291c2d785f957d0 src/Package.hs | 1 - src/Rules/Data.hs | 1 - src/Settings/GhcPkg.hs | 2 +- src/Util.hs | 1 + 4 files changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 5d2429f..a007b4e 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -6,7 +6,6 @@ import Util import Data.Function import GHC.Generics import Development.Shake.Classes -import Development.Shake.FilePath -- pkgPath is the path to the source code relative to the root data Package = Package diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 3ce7d08..2a2a995 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -16,7 +16,6 @@ import Rules.Actions import Control.Applicative import Control.Monad.Extra import Development.Shake -import Development.Shake.FilePath -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: StagePackageTarget -> Rules () diff --git a/src/Settings/GhcPkg.hs b/src/Settings/GhcPkg.hs index 83bef1d..8e3a287 100644 --- a/src/Settings/GhcPkg.hs +++ b/src/Settings/GhcPkg.hs @@ -12,8 +12,8 @@ import Development.Shake.FilePath ghcPkgArgs :: Args ghcPkgArgs = do - pkg <- asks getPackage stage <- asks getStage + pkg <- asks getPackage builder (GhcPkg stage) ? mconcat [ arg "update" , arg "--force" diff --git a/src/Util.hs b/src/Util.hs index 4b1a2c6..7cc38ee 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,7 @@ module Util ( module Data.Char, module System.Console.ANSI, + module Development.Shake.FilePath, replaceIf, replaceEq, replaceSeparators, unifyPath, chunksOfSize, From git at git.haskell.org Fri Oct 27 00:00:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #123 from angerman/feature/fix-clang (4c75d3f) Message-ID: <20171027000024.559483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4c75d3ff0040645fe7107d244ce64b88dbf7010b/ghc >--------------------------------------------------------------- commit 4c75d3ff0040645fe7107d244ce64b88dbf7010b Merge: 79a0bf3 5ccd03c Author: Andrey Mokhov Date: Thu Jan 7 13:14:07 2016 +0000 Merge pull request #123 from angerman/feature/fix-clang Feature/fix clang >--------------------------------------------------------------- 4c75d3ff0040645fe7107d244ce64b88dbf7010b .travis.yml | 3 +-- README.md | 3 --- shaking-up-ghc.cabal | 1 + src/Base.hs | 11 ++++++++++- src/Builder.hs | 6 +++++- src/Oracles.hs | 2 ++ src/Oracles/LookupInPath.hs | 32 ++++++++++++++++++++++++++++++++ src/Rules/Oracles.hs | 1 + 8 files changed, 52 insertions(+), 7 deletions(-) From git at git.haskell.org Fri Oct 27 00:00:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement expression for GhcM builder. (fcb25e6) Message-ID: <20171027000024.7688B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fcb25e6e86cd2fa82be62cf8541372ef3fb97c34/ghc >--------------------------------------------------------------- commit fcb25e6e86cd2fa82be62cf8541372ef3fb97c34 Author: Andrey Mokhov Date: Fri Jul 24 04:13:30 2015 +0100 Implement expression for GhcM builder. >--------------------------------------------------------------- fcb25e6e86cd2fa82be62cf8541372ef3fb97c34 src/Settings/Args.hs | 2 + src/Settings/GhcM.hs | 158 +++++++++++++++++++++++++++++++++++++++++++++++++++ src/Settings/Util.hs | 17 ++++++ 3 files changed, 177 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 fcb25e6e86cd2fa82be62cf8541372ef3fb97c34 From git at git.haskell.org Fri Oct 27 00:00:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (7e8bfbb) Message-ID: <20171027000026.BFFBD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e8bfbbe5cf6a1ea303bdaebd862ea74b51eb843/ghc >--------------------------------------------------------------- commit 7e8bfbbe5cf6a1ea303bdaebd862ea74b51eb843 Author: Andrey Mokhov Date: Mon Feb 8 03:09:14 2016 +0000 Minor revision. >--------------------------------------------------------------- 7e8bfbbe5cf6a1ea303bdaebd862ea74b51eb843 src/Builder.hs | 2 +- src/Package.hs | 12 +++++------- src/Target.hs | 16 +++++++--------- 3 files changed, 13 insertions(+), 17 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 80fc4ba..d1a2cc3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -58,7 +58,7 @@ builderProvenance = \case DeriveConstants -> Just (Stage0, deriveConstants) GenApply -> Just (Stage0, genapply) GenPrimopCode -> Just (Stage0, genprimopcode) - Ghc stage -> if stage > Stage0 then Just (pred stage, ghc) else Nothing + Ghc stage -> if stage == Stage0 then Nothing else Just (pred stage, ghc) GhcM stage -> builderProvenance $ Ghc stage GhcCabal -> Just (Stage0, ghcCabal) GhcCabalHsColour -> builderProvenance $ GhcCabal diff --git a/src/Package.hs b/src/Package.hs index 43eb480..4b6fbc6 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -29,13 +29,11 @@ instance Show PackageName where data PackageType = Program | Library deriving Generic data Package = Package - { - pkgName :: PackageName, -- ^ Examples: "ghc", "Cabal" - pkgPath :: FilePath, -- ^ pkgPath is the path to the source code relative to the root. - -- e.g. "compiler", "libraries/Cabal/Cabal" - pkgType :: PackageType - } - deriving Generic + { pkgName :: PackageName -- ^ Examples: "ghc", "Cabal" + , pkgPath :: FilePath -- ^ pkgPath is the path to the source code relative to the root. + -- e.g. "compiler", "libraries/Cabal/Cabal" + , pkgType :: PackageType + } deriving Generic -- | Prettyprint Package name. pkgNameString :: Package -> String diff --git a/src/Target.hs b/src/Target.hs index d2cbfce..8c39ac7 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -18,15 +18,13 @@ import Way -- | Parameters relevant to the current build target. data Target = Target - { - stage :: Stage, -- ^ Stage being built - package :: Package, -- ^ Package being built - builder :: Builder, -- ^ Builder to be invoked - way :: Way, -- ^ Way to build (set to vanilla for most targets) - inputs :: [FilePath], -- ^ Source files passed to the builder - outputs :: [FilePath] -- ^ Files to be produced - } - deriving (Show, Eq, Generic) + { stage :: Stage -- ^ Stage being built + , package :: Package -- ^ Package being built + , builder :: Builder -- ^ Builder to be invoked + , way :: Way -- ^ Way to build (set to vanilla for most targets) + , inputs :: [FilePath] -- ^ Source files passed to the builder + , outputs :: [FilePath] -- ^ Files to be produced + } deriving (Show, Eq, Generic) -- | If values of type @a@ form a 'Monoid' then we can also derive a 'Monoid' -- instance for values of type @'ReaderT' 'Target' 'Action' a@: From git at git.haskell.org Fri Oct 27 00:00:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build touchy only on Windows, see #125. (bcb7894) Message-ID: <20171027000028.409753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bcb7894c282280861014f8f6fd0bb6bb3c0f4a02/ghc >--------------------------------------------------------------- commit bcb7894c282280861014f8f6fd0bb6bb3c0f4a02 Author: Andrey Mokhov Date: Thu Jan 7 13:35:09 2016 +0000 Build touchy only on Windows, see #125. >--------------------------------------------------------------- bcb7894c282280861014f8f6fd0bb6bb3c0f4a02 src/Settings/Packages.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index f80f0d0..3f4f661 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -24,8 +24,8 @@ packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode - , hp2ps, touchy ] + , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] + , stage0 ? windowsHost ? append [touchy] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] packagesStage1 :: Packages From git at git.haskell.org Fri Oct 27 00:00:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -/- for combining paths with unification of the result. (179d1cd) Message-ID: <20171027000028.578553A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/179d1cd8a9dbaa304f51bef9cfbba745940ec2db/ghc >--------------------------------------------------------------- commit 179d1cd8a9dbaa304f51bef9cfbba745940ec2db Author: Andrey Mokhov Date: Fri Jul 24 13:10:57 2015 +0100 Add -/- for combining paths with unification of the result. >--------------------------------------------------------------- 179d1cd8a9dbaa304f51bef9cfbba745940ec2db src/Oracles/Base.hs | 8 +++----- src/Oracles/PackageData.hs | 11 +++++------ src/Package.hs | 2 +- src/Rules.hs | 4 ++-- src/Rules/Config.hs | 6 +++--- src/Rules/Data.hs | 12 ++++++------ src/Settings/GhcCabal.hs | 8 ++++---- src/Settings/GhcM.hs | 20 ++++++++++---------- src/Settings/GhcPkg.hs | 4 ++-- src/Settings/TargetDirectory.hs | 4 ++-- src/Settings/Util.hs | 7 +------ src/Util.hs | 9 ++++++++- 12 files changed, 47 insertions(+), 48 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 179d1cd8a9dbaa304f51bef9cfbba745940ec2db From git at git.haskell.org Fri Oct 27 00:00:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -fno-warn-name-shadowing. (7d7802d) Message-ID: <20171027000030.34DB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d7802d73a03dd913d43aad6e36ec6e72c6744ae/ghc >--------------------------------------------------------------- commit 7d7802d73a03dd913d43aad6e36ec6e72c6744ae Author: Andrey Mokhov Date: Mon Feb 8 23:17:49 2016 +0000 Add -fno-warn-name-shadowing. >--------------------------------------------------------------- 7d7802d73a03dd913d43aad6e36ec6e72c6744ae build.sh | 1 + 1 file changed, 1 insertion(+) diff --git a/build.sh b/build.sh index 719e85e..77c9fa4 100755 --- a/build.sh +++ b/build.sh @@ -35,6 +35,7 @@ mkdir -p "$root/.shake" ghc \ "$root/src/Main.hs" \ -Wall \ + -fno-warn-name-shadowing \ -i"$root/src" \ -rtsopts \ -with-rtsopts=-I0 \ From git at git.haskell.org Fri Oct 27 00:00:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (53784f5) Message-ID: <20171027000032.2F4553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/53784f526f5ee88136966f5f9c8328459334436b/ghc >--------------------------------------------------------------- commit 53784f526f5ee88136966f5f9c8328459334436b Author: Moritz Angermann Date: Thu Jan 7 21:37:46 2016 +0800 Update README.md - Trying to unify Linux / OS X / Windows build steps. - Added note about `src/Settings/User.hs`. [skip ci] >--------------------------------------------------------------- 53784f526f5ee88136966f5f9c8328459334436b README.md | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) diff --git a/README.md b/README.md index 9f9de91..6a89dc6 100644 --- a/README.md +++ b/README.md @@ -23,36 +23,30 @@ identical to those for the `make` build system. This means that you don't need to adjust anything if you are already familiar with building ghc using the `make` build system. -### Linux / Mac OS X +### Getting the source and configuring GHC ```bash -git clone git://git.haskell.org/ghc +git clone --recursive git://git.haskell.org/ghc.git cd ghc -git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot -./configure +./configure # on linux / os x +./configure --enable-tarballs-autodownload # on windows ``` -Now you have a couple of options: - -- `./shake-build/build.sh` to run the script directly. You'll need to have - `shake` installed globally. -- `./shake-build/build.cabal.sh` to install the build system in a Cabal sandbox - and then run it. +### Configuring the build process +`ghc` uses `mk/build.mk` to configure the build process. `shaking-up-ghc` +uses `src/Settings/User.hs` for build specification. - -### Windows +### Building GHC using `shaking-up-ghc` ```bash -git clone --recursive git://git.haskell.org/ghc.git -cd ghc -git clone git://github.com/snowleopard/shaking-up-ghc shake-build -./boot -./configure --enable-tarballs-autodownload -shake-build/build.bat +./shake-build/build.sh # linux / os x: to run the script directly. You'll need to have `shake` installed globally. +./shake-build/build.cabal.sh # linux / os x: OR to install the build system in a Cabal sandbox and then run it. +shake-build/build.bat # windows ``` + Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build From git at git.haskell.org Fri Oct 27 00:00:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename ask* to get* to avoid mixing up oracles with expressions. (d9d1dd9e) Message-ID: <20171027000032.3E1343A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9d1dd9ef0d2827579f9c7c647e081156a14c8ab/ghc >--------------------------------------------------------------- commit d9d1dd9ef0d2827579f9c7c647e081156a14c8ab Author: Andrey Mokhov Date: Fri Jul 24 13:15:29 2015 +0100 Rename ask* to get* to avoid mixing up oracles with expressions. >--------------------------------------------------------------- d9d1dd9ef0d2827579f9c7c647e081156a14c8ab src/Settings/GhcM.hs | 30 +++++++++++++++--------------- src/Settings/Util.hs | 10 +++++----- 2 files changed, 20 insertions(+), 20 deletions(-) diff --git a/src/Settings/GhcM.hs b/src/Settings/GhcM.hs index 4f792e0..89c4634 100644 --- a/src/Settings/GhcM.hs +++ b/src/Settings/GhcM.hs @@ -19,9 +19,9 @@ ghcMArgs = do stage <- asks getStage builder (GhcM stage) ? do pkg <- asks getPackage - cppArgs <- askPkgDataList CppArgs - hsArgs <- askPkgDataList HsArgs - hsSrcs <- askHsSources + cppArgs <- getPkgDataList CppArgs + hsArgs <- getPkgDataList HsArgs + hsSrcs <- getHsSources ways <- fromDiffExpr Settings.Ways.ways let buildPath = targetPath stage pkg -/- "build" mconcat @@ -41,9 +41,9 @@ packageGhcArgs :: Args packageGhcArgs = do stage <- asks getStage supportsPackageKey <- lift . flag $ SupportsPackageKey - pkgKey <- askPkgData PackageKey - pkgDepKeys <- askPkgDataList DepKeys - pkgDeps <- askPkgDataList Deps + pkgKey <- getPkgData PackageKey + pkgDepKeys <- getPkgDataList DepKeys + pkgDeps <- getPkgDataList Deps mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" @@ -59,8 +59,8 @@ includeGhcArgs :: Args includeGhcArgs = do stage <- asks getStage pkg <- asks getPackage - srcDirs <- askPkgDataList SrcDirs - includeDirs <- askPkgDataList IncludeDirs + srcDirs <- getPkgDataList SrcDirs + includeDirs <- getPkgDataList IncludeDirs let buildPath = targetPath stage pkg -/- "build" autogenPath = buildPath -/- "autogen" mconcat @@ -74,18 +74,18 @@ includeGhcArgs = do , arg "-optP-include" -- TODO: Shall we also add -cpp? , arg $ "-optP" ++ autogenPath -/- "cabal_macros.h" ] -askHsSources :: Expr [FilePath] -askHsSources = do +getHsSources :: Expr [FilePath] +getHsSources = do stage <- asks getStage pkg <- asks getPackage - srcDirs <- askPkgDataList SrcDirs + srcDirs <- getPkgDataList SrcDirs let autogenPath = targetPath stage pkg -/- "build/autogen" dirs = autogenPath : map (pkgPath pkg -/-) srcDirs - askModuleFiles dirs [".hs", ".lhs"] + getModuleFiles dirs [".hs", ".lhs"] -askModuleFiles :: [FilePath] -> [String] -> Expr [FilePath] -askModuleFiles directories suffixes = do - modules <- askPkgDataList Modules +getModuleFiles :: [FilePath] -> [String] -> Expr [FilePath] +getModuleFiles directories suffixes = do + modules <- getPkgDataList Modules let modPaths = map (replaceEq '.' pathSeparator) modules files <- lift $ forM [ dir -/- modPath ++ suffix | dir <- directories diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 4fadcd7..22ffd29 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -2,7 +2,7 @@ module Settings.Util ( -- Primitive settings elements arg, argM, argSetting, argSettingList, - askPkgData, askPkgDataList, + getPkgData, getPkgDataList, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -34,15 +34,15 @@ argSetting = argM . setting argSettingList :: SettingList -> Args argSettingList = appendM . settingList -askPkgData :: (FilePath -> PackageData) -> Expr String -askPkgData key = do +getPkgData :: (FilePath -> PackageData) -> Expr String +getPkgData key = do stage <- asks getStage pkg <- asks getPackage let path = targetPath stage pkg lift . pkgData . key $ path -askPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] -askPkgDataList key = do +getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] +getPkgDataList key = do stage <- asks getStage pkg <- asks getPackage let path = targetPath stage pkg From git at git.haskell.org Fri Oct 27 00:00:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Rules.Config to Rules.Setup. (d5e2d92) Message-ID: <20171027000033.B23143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d5e2d9278d4590fa370fb73900447a573fc37e2f/ghc >--------------------------------------------------------------- commit d5e2d9278d4590fa370fb73900447a573fc37e2f Author: Andrey Mokhov Date: Mon Feb 8 23:19:35 2016 +0000 Rename Rules.Config to Rules.Setup. See #204. >--------------------------------------------------------------- d5e2d9278d4590fa370fb73900447a573fc37e2f shaking-up-ghc.cabal | 2 +- src/Main.hs | 4 ++-- src/Rules/{Config.hs => Setup.hs} | 6 +++--- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 0807ff3..254617d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -42,7 +42,6 @@ executable ghc-shake , Rules.Cabal , Rules.Clean , Rules.Compile - , Rules.Config , Rules.Data , Rules.Dependencies , Rules.Documentation @@ -64,6 +63,7 @@ executable ghc-shake , Rules.Program , Rules.Register , Rules.Resources + , Rules.Setup , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg , Selftest diff --git a/src/Main.hs b/src/Main.hs index 79601d8..544987d 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -8,12 +8,12 @@ import qualified Environment import qualified Rules import qualified Rules.Cabal import qualified Rules.Clean -import qualified Rules.Config import qualified Rules.Generate import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl +import qualified Rules.Setup import qualified Selftest import qualified Test @@ -29,13 +29,13 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do rules = mconcat [ Rules.Cabal.cabalRules , Rules.Clean.cleanRules - , Rules.Config.configRules , Rules.Generate.generateRules , Rules.Generate.copyRules , Rules.Gmp.gmpRules , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules , Rules.Perl.perlScriptRules + , Rules.Setup.setupRules , Rules.topLevelTargets , Rules.packageRules , Selftest.selftestRules diff --git a/src/Rules/Config.hs b/src/Rules/Setup.hs similarity index 93% rename from src/Rules/Config.hs rename to src/Rules/Setup.hs index 1016be9..a88084c 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Setup.hs @@ -1,4 +1,4 @@ -module Rules.Config (configRules) where +module Rules.Setup (setupRules) where import qualified System.Info @@ -7,8 +7,8 @@ import CmdLineFlag import Rules.Actions import Rules.Generators.GhcAutoconfH -configRules :: Rules () -configRules = do +setupRules :: Rules () +setupRules = do -- We always rerun the configure script in this mode, because the flags -- passed to it can affect the contents of system.config file. [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do From git at git.haskell.org Fri Oct 27 00:00:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (fff8d58) Message-ID: <20171027000035.9799C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fff8d58cbbf23090752b897768bf4eac8af5f819/ghc >--------------------------------------------------------------- commit fff8d58cbbf23090752b897768bf4eac8af5f819 Author: Moritz Angermann Date: Thu Jan 7 21:48:28 2016 +0800 Update README.md Drop `shake` requirement, as it applies to windows as well and is not exhaustive. [skip ci] >--------------------------------------------------------------- fff8d58cbbf23090752b897768bf4eac8af5f819 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 6a89dc6..2259c0b 100644 --- a/README.md +++ b/README.md @@ -42,7 +42,7 @@ uses `src/Settings/User.hs` for build specification. ### Building GHC using `shaking-up-ghc` ```bash -./shake-build/build.sh # linux / os x: to run the script directly. You'll need to have `shake` installed globally. +./shake-build/build.sh # linux / os x: to run the script directly. ./shake-build/build.cabal.sh # linux / os x: OR to install the build system in a Cabal sandbox and then run it. shake-build/build.bat # windows ``` From git at git.haskell.org Fri Oct 27 00:00:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactoring for consistent interface (getters) for expressions. (ff86f40) Message-ID: <20171027000035.E335F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894/ghc >--------------------------------------------------------------- commit ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894 Author: Andrey Mokhov Date: Fri Jul 24 14:07:46 2015 +0100 Refactoring for consistent interface (getters) for expressions. >--------------------------------------------------------------- ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894 src/Expression.hs | 31 ++++++++++++++++---- src/Rules/Actions.hs | 3 +- src/Rules/Data.hs | 5 ++-- src/Settings/GhcCabal.hs | 12 ++++---- src/Settings/GhcM.hs | 20 ++++++------- src/Settings/GhcPkg.hs | 4 +-- src/Settings/Packages.hs | 5 +++- src/Settings/Util.hs | 27 ++++++++++++------ src/Settings/Ways.hs | 5 +++- src/Switches.hs | 19 +++++++------ src/Target.hs | 73 ++++++++++++++++++++++++------------------------ 11 files changed, 121 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ff86f40ecbfd80e9bbe2104a6c3f2bafeec89894 From git at git.haskell.org Fri Oct 27 00:00:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run mk/get-win32-tarballs.sh on Windows. (0678acb) Message-ID: <20171027000037.3AA9D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0678acb67ab59b4af9f2401959e1d71ef27d77bc/ghc >--------------------------------------------------------------- commit 0678acb67ab59b4af9f2401959e1d71ef27d77bc Author: Andrey Mokhov Date: Mon Feb 8 23:37:58 2016 +0000 Run mk/get-win32-tarballs.sh on Windows. See #204. >--------------------------------------------------------------- 0678acb67ab59b4af9f2401959e1d71ef27d77bc src/Rules/Setup.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index a88084c..ac53592 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -17,10 +17,13 @@ setupRules = do RunConfigure args -> do need [ settings <.> "in", cfgH <.> "in" ] -- We cannot use windowsHost here due to a cyclic dependency - let defaultArgs = if System.Info.os == "mingw32" - then [ "--enable-tarballs-autodownload" ] - else [] - runConfigure "." [] $ defaultArgs ++ [args] + when (System.Info.os == "mingw32") $ do + putBuild "| Checking for Windows tarballs..." + quietly $ cmd [ "bash" + , "mk/get-win32-tarballs.sh" + , "download" + , System.Info.arch ] + runConfigure "." [] [args] SkipConfigure -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " From git at git.haskell.org Fri Oct 27 00:00:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #129 from snowleopard/angerman-patch-2 (6df7616) Message-ID: <20171027000039.5CD6E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6df7616bbc76029bafaa2493ea8d75e28ca03a60/ghc >--------------------------------------------------------------- commit 6df7616bbc76029bafaa2493ea8d75e28ca03a60 Merge: bcb7894 fff8d58 Author: Andrey Mokhov Date: Thu Jan 7 13:52:04 2016 +0000 Merge pull request #129 from snowleopard/angerman-patch-2 Update README.md [skip ci] >--------------------------------------------------------------- 6df7616bbc76029bafaa2493ea8d75e28ca03a60 README.md | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) From git at git.haskell.org Fri Oct 27 00:00:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement buildPackageDependencies rule. (65b298b) Message-ID: <20171027000039.7DB333A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65b298b0c7fe85fa106bc7d0558096825eb01e09/ghc >--------------------------------------------------------------- commit 65b298b0c7fe85fa106bc7d0558096825eb01e09 Author: Andrey Mokhov Date: Sat Jul 25 02:05:14 2015 +0100 Implement buildPackageDependencies rule. >--------------------------------------------------------------- 65b298b0c7fe85fa106bc7d0558096825eb01e09 src/Builder.hs | 2 + src/Package/Dependencies.hs | 92 ------------------- src/Rules.hs | 3 +- src/Rules/Actions.hs | 10 +-- src/Rules/Data.hs | 8 +- src/Rules/Dependencies.hs | 210 ++++++-------------------------------------- src/Rules/Package.hs | 5 +- src/Settings/Args.hs | 2 + src/Settings/GccM.hs | 41 +++++++++ src/Settings/GhcM.hs | 104 +++++----------------- src/Settings/GhcPkg.hs | 4 +- src/Settings/User.hs | 2 +- src/Settings/Util.hs | 59 +------------ 13 files changed, 108 insertions(+), 434 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 65b298b0c7fe85fa106bc7d0558096825eb01e09 From git at git.haskell.org Fri Oct 27 00:00:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (507f48d) Message-ID: <20171027000040.F407A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/507f48d12b6715d0943ae1b6bc4d7e8b6c676870/ghc >--------------------------------------------------------------- commit 507f48d12b6715d0943ae1b6bc4d7e8b6c676870 Author: Andrey Mokhov Date: Mon Feb 8 23:52:38 2016 +0000 Minor revision. >--------------------------------------------------------------- 507f48d12b6715d0943ae1b6bc4d7e8b6c676870 src/Rules/Actions.hs | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9275207..1a6fbf8 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -106,17 +106,16 @@ runConfigure dir opts args = do need [dir -/- "configure"] let args' = filter (not . null) args note = if null args' then "" else " (" ++ intercalate ", " args' ++ ")" + -- Always configure with bash. + -- This also injects /bin/bash into `libtool`, instead of /bin/sh + opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] if dir == "." then do putBuild $ "| Run configure" ++ note ++ "..." - quietly $ cmd Shell (EchoStdout False) "bash configure" opts' args + quietly $ cmd Shell (EchoStdout False) "bash configure" opts' args' else do putBuild $ "| Run configure" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args - where - -- Always configure with bash. - -- This also injects /bin/bash into `libtool`, instead of /bin/sh - opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] + quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args' runMake :: FilePath -> [String] -> Action () runMake = runMakeWithVerbosity False From git at git.haskell.org Fri Oct 27 00:00:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build only stage1 base library to fit into Travis 50 min limit for OSX. (b67f727) Message-ID: <20171027000043.0D20A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b67f727b982025b1039994cdb7731fc2a47f2119/ghc >--------------------------------------------------------------- commit b67f727b982025b1039994cdb7731fc2a47f2119 Author: Andrey Mokhov Date: Thu Jan 7 15:43:14 2016 +0000 Build only stage1 base library to fit into Travis 50 min limit for OSX. >--------------------------------------------------------------- b67f727b982025b1039994cdb7731fc2a47f2119 .travis.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 055edd5..4cc0396 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: false matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 + env: CABALVER=1.22 GHCVER=7.10.3 TARGET= addons: apt: packages: @@ -21,6 +21,7 @@ matrix: - cabal update - os: osx + env: TARGET=libraries/base/stage1/build/libHSbase-4.9.0.0.a before_install: - brew update - brew install ghc cabal-install @@ -54,7 +55,7 @@ install: - ( cd ghc && ./configure ) script: - - ./ghc/shake-build/build.sh -j --no-progress + - ./ghc/shake-build/build.sh -j --no-progress $TARGET cache: directories: From git at git.haskell.org Fri Oct 27 00:00:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a draft description of demo. (4bd8812) Message-ID: <20171027000043.0B2103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4bd88123d1eeb16bfb272768b3ec93a4d503003f/ghc >--------------------------------------------------------------- commit 4bd88123d1eeb16bfb272768b3ec93a4d503003f Author: Andrey Mokhov Date: Sat Jul 25 12:33:33 2015 +0100 Add a draft description of demo. >--------------------------------------------------------------- 4bd88123d1eeb16bfb272768b3ec93a4d503003f doc/demo.txt | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/doc/demo.txt b/doc/demo.txt new file mode 100644 index 0000000..4b6b671 --- /dev/null +++ b/doc/demo.txt @@ -0,0 +1,4 @@ +1. Rebuild only when argument list has changed +2. Rebuild only when package-data.mk contents has changed + +* Add to Settings/GhcPkg.hs: package deepseq ? arg "--force" From git at git.haskell.org Fri Oct 27 00:00:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename the --configure flag to --setup. (4cef7ec) Message-ID: <20171027000044.7312E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1/ghc >--------------------------------------------------------------- commit 4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1 Author: Andrey Mokhov Date: Mon Feb 8 23:53:19 2016 +0000 Rename the --configure flag to --setup. See #204. >--------------------------------------------------------------- 4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1 src/CmdLineFlag.hs | 40 ++++++++++++++++++++-------------------- src/Rules/Setup.hs | 10 +++++----- 2 files changed, 25 insertions(+), 25 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 84d4f11..c7d2b35 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,5 +1,5 @@ module CmdLineFlag ( - putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdConfigure, Configure (..), + putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdSetup, Setup (..), cmdFlavour, Flavour (..), cmdProgressInfo, ProgressInfo (..), cmdSplitObjects ) where @@ -11,7 +11,7 @@ import System.IO.Unsafe (unsafePerformIO) -- Command line flags data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -data Configure = SkipConfigure | RunConfigure String deriving (Eq, Show) +data Setup = SkipSetup | RunSetup String deriving (Eq, Show) data Flavour = Default | Quick deriving (Eq, Show) -- | 'CmdLineFlag.Untracked' is a collection of flags that can be passed via the @@ -19,9 +19,9 @@ data Flavour = Default | Quick deriving (Eq, Show) -- build rules to be rurun. data Untracked = Untracked { buildHaddock :: Bool - , configure :: Configure , flavour :: Flavour , progressInfo :: ProgressInfo + , setup :: Setup , splitObjects :: Bool } deriving (Eq, Show) @@ -29,24 +29,14 @@ data Untracked = Untracked defaultUntracked :: Untracked defaultUntracked = Untracked { buildHaddock = False - , configure = SkipConfigure , flavour = Default , progressInfo = Normal + , setup = SkipSetup , splitObjects = False } readBuildHaddock :: Either String (Untracked -> Untracked) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } -readConfigure :: Maybe String -> Either String (Untracked -> Untracked) -readConfigure ms = - maybe (Left "Cannot parse configure") (Right . set) (go $ lower <$> ms) - where - go :: Maybe String -> Maybe Configure - go (Just args) = Just $ RunConfigure args - go Nothing = Just $ RunConfigure "" - set :: Configure -> Untracked -> Untracked - set flag flags = flags { configure = flag } - readFlavour :: Maybe String -> Either String (Untracked -> Untracked) readFlavour ms = maybe (Left "Cannot parse flavour") (Right . set) (go =<< lower <$> ms) @@ -71,19 +61,29 @@ readProgressInfo ms = set :: ProgressInfo -> Untracked -> Untracked set flag flags = flags { progressInfo = flag } +readSetup :: Maybe String -> Either String (Untracked -> Untracked) +readSetup ms = + maybe (Left "Cannot parse setup") (Right . set) (go $ lower <$> ms) + where + go :: Maybe String -> Maybe Setup + go (Just args) = Just $ RunSetup args + go Nothing = Just $ RunSetup "" + set :: Setup -> Untracked -> Untracked + set flag flags = flags { setup = flag } + readSplitObjects :: Either String (Untracked -> Untracked) readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = - [ Option [] ["configure"] (OptArg readConfigure "ARGS") - "Run configure with ARGS (also run boot if necessary)." - , Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") + [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") "Build flavour (Default or Quick)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") "Progress info style (None, Brief, Normal, or Unicorn)." + , Option [] ["setup"] (OptArg readSetup "CONFIGURE_ARGS") + "Setup the build system, pass CONFIGURE_ARGS to ./configure." , Option [] ["split-objects"] (NoArg readSplitObjects) "Generate split objects (requires a full clean rebuild)." ] @@ -103,14 +103,14 @@ getCmdLineFlags = unsafePerformIO $ readIORef cmdLineFlags cmdBuildHaddock :: Bool cmdBuildHaddock = buildHaddock getCmdLineFlags -cmdConfigure :: Configure -cmdConfigure = configure getCmdLineFlags - cmdFlavour :: Flavour cmdFlavour = flavour getCmdLineFlags cmdProgressInfo :: ProgressInfo cmdProgressInfo = progressInfo getCmdLineFlags +cmdSetup :: Setup +cmdSetup = setup getCmdLineFlags + cmdSplitObjects :: Bool cmdSplitObjects = splitObjects getCmdLineFlags diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index ac53592..c99c8be 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -13,8 +13,8 @@ setupRules = do -- passed to it can affect the contents of system.config file. [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do alwaysRerun - case cmdConfigure of - RunConfigure args -> do + case cmdSetup of + RunSetup configureArgs -> do need [ settings <.> "in", cfgH <.> "in" ] -- We cannot use windowsHost here due to a cyclic dependency when (System.Info.os == "mingw32") $ do @@ -23,11 +23,11 @@ setupRules = do , "mk/get-win32-tarballs.sh" , "download" , System.Info.arch ] - runConfigure "." [] [args] - SkipConfigure -> unlessM (doesFileExist cfg) $ + runConfigure "." [] [configureArgs] + SkipSetup -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " - ++ "build system by passing --configure[=ARGS] flag." + ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." ["configure", configH <.> "in"] &%> \_ -> do putBuild "| Running boot..." From git at git.haskell.org Fri Oct 27 00:00:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create ghc-tarballs folder. (45eefc0) Message-ID: <20171027000047.0F2883A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45eefc07e8d5820ca0640a7ecb398dcb717aa35a/ghc >--------------------------------------------------------------- commit 45eefc07e8d5820ca0640a7ecb398dcb717aa35a Author: Andrey Mokhov Date: Thu Jan 7 16:35:01 2016 +0000 Create ghc-tarballs folder. See #110. [skip ci] >--------------------------------------------------------------- 45eefc07e8d5820ca0640a7ecb398dcb717aa35a .appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.appveyor.yml b/.appveyor.yml index 6821abf..7d5a0f8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -11,6 +11,7 @@ install: - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - bash -lc "mkdir -p /home/ghc/ghc-tarballs" - bash -lc "cd /home/ghc && ./mk/get-win32-tarballs.sh download x86_64" build_script: From git at git.haskell.org Fri Oct 27 00:00:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (28a8078) Message-ID: <20171027000047.0EC4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28a807878a86600df0884fc5ee28be02adc52386/ghc >--------------------------------------------------------------- commit 28a807878a86600df0884fc5ee28be02adc52386 Author: Andrey Mokhov Date: Sat Jul 25 12:33:52 2015 +0100 Clean up. >--------------------------------------------------------------- 28a807878a86600df0884fc5ee28be02adc52386 src/Expression.hs | 21 +++++++- src/Package/Base.hs | 138 +++++++++++++++++++++++------------------------ src/Settings/GccM.hs | 48 ++++++++--------- src/Settings/GhcCabal.hs | 35 ++++++------ src/Settings/GhcM.hs | 59 ++++++++++---------- src/Settings/GhcPkg.hs | 15 +++--- src/Settings/Util.hs | 11 ++++ 7 files changed, 173 insertions(+), 154 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 28a807878a86600df0884fc5ee28be02adc52386 From git at git.haskell.org Fri Oct 27 00:00:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename --configure to --setup. (2fe68f0) Message-ID: <20171027000047.DAAC33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2fe68f0a0c1e737ed2ba1f8d4a606a6953497f74/ghc >--------------------------------------------------------------- commit 2fe68f0a0c1e737ed2ba1f8d4a606a6953497f74 Author: Andrey Mokhov Date: Tue Feb 9 00:07:10 2016 +0000 Rename --configure to --setup. Fix #204. [skip ci] >--------------------------------------------------------------- 2fe68f0a0c1e737ed2ba1f8d4a606a6953497f74 README.md | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 35f8ac3..96b3106 100644 --- a/README.md +++ b/README.md @@ -52,19 +52,19 @@ are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue In addition to standard Shake flags (try `--help`), the build system currently supports several others: -* `--configure[=ARGS]`: run the `configure` script forwarding `ARGS` as command line -arguments; also run the `boot` script to create the `configure` script if necessary. -You do not have to use this functionality of the new build system; feel free to run -`boot` and `configure` scripts manually, as you do when using `make`. Note: on Windows -we automatically add flag `--enable-tarballs-autodownload` to `ARGS`, so you -don't have to do it manually. Beware, this uses network I/O which may sometimes be -undesirable. * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). * `--haddock`: build Haddock documentation. * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). +* `--setup[=CONFIGURE_ARGS]`: setup the build system by running the `configure` script +with `CONFIGURE_ARGS` arguments; also run the `boot` script to create the `configure` +script if necessary. On Windows, download the required tarballs by executing +`mk/get-win32-tarballs.sh` with appropriate parameters. You do not have to +use this functionality of the new build system; feel free to run `boot` and `configure` +scripts manually, as you do when using `make`. Beware: `--setup` uses network I/O +which may sometimes be undesirable. * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. From git at git.haskell.org Fri Oct 27 00:00:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add dependencies to Target. (4f2fbbb) Message-ID: <20171027000050.D86463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b/ghc >--------------------------------------------------------------- commit 4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b Author: Andrey Mokhov Date: Sat Jul 25 17:08:35 2015 +0100 Add dependencies to Target. >--------------------------------------------------------------- 4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b src/Expression.hs | 15 +++++++++- src/Rules/Actions.hs | 1 + src/Rules/Data.hs | 17 ++++++----- src/Rules/Dependencies.hs | 18 ++++++----- src/Settings/GccM.hs | 5 ++-- src/Settings/GhcCabal.hs | 1 + src/Settings/GhcM.hs | 19 ------------ src/Settings/Util.hs | 21 +++++++++++++ src/Target.hs | 76 +++++++++++++++++++++++------------------------ 9 files changed, 98 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 4f2fbbbe9cd8ed6aeea59965b95eff254e8f7f7b From git at git.haskell.org Fri Oct 27 00:00:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename replaceIf -> replaceWhen to match wordsWhen, clean up. (f7cd3ae) Message-ID: <20171027000051.350DF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f7cd3aeef421946ef3f1ff1e9916b19ac8ddf9d4/ghc >--------------------------------------------------------------- commit f7cd3aeef421946ef3f1ff1e9916b19ac8ddf9d4 Author: Andrey Mokhov Date: Thu Jan 7 16:52:25 2016 +0000 Rename replaceIf -> replaceWhen to match wordsWhen, clean up. [skip ci] >--------------------------------------------------------------- f7cd3aeef421946ef3f1ff1e9916b19ac8ddf9d4 src/Base.hs | 51 +++++++++++++++++++++++++-------------------------- 1 file changed, 25 insertions(+), 26 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 86ddbf5..a116892 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -81,14 +81,14 @@ packageConfigurationInitialised stage = -- Utility functions -- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] -replaceEq from = replaceIf (== from) +replaceEq from = replaceWhen (== from) -- | Find and replace all occurrences of path separators in a String with a Char replaceSeparators :: Char -> String -> String -replaceSeparators = replaceIf isPathSeparator +replaceSeparators = replaceWhen isPathSeparator -replaceIf :: (a -> Bool) -> a -> [a] -> [a] -replaceIf p to = map (\from -> if p from then to else from) +replaceWhen :: (a -> Bool) -> a -> [a] -> [a] +replaceWhen p to = map (\from -> if p from then to else from) -- | Find all occurrences of substring 'from' and replace them to 'to' in a -- given string. Not very efficient, but simple and fast enough for our purposes @@ -101,6 +101,27 @@ replace from to = go | from `isPrefixOf` s = to ++ go (skipFrom s) | otherwise = x : go xs +-- | Split a list into chunks in places where the predicate @p@ holds. +-- See: http://stackoverflow.com/a/4981265 +wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] +wordsWhen p list = + case dropWhile p list of + [] -> [] + l -> w : wordsWhen p rest where (w, rest) = break p l + +-- | @chunksOfSize size strings@ splits a given list of strings into chunks not +-- exceeding the given @size at . +chunksOfSize :: Int -> [String] -> [[String]] +chunksOfSize _ [] = [] +chunksOfSize size strings = reverse chunk : chunksOfSize size rest + where + (chunk, rest) = go [] 0 strings + go res _ [] = (res, []) + go res chunkSize (s:ss) = + if newSize > size then (res, s:ss) else go (s:res) newSize ss + where + newSize = chunkSize + length s + -- | Add quotes to a String quote :: String -> String quote s = "\"" ++ s ++ "\"" @@ -133,19 +154,6 @@ a -/- b = unifyPath $ a b infixr 6 -/- --- | @chunksOfSize size strings@ splits a given list of strings into chunks not --- exceeding the given @size at . -chunksOfSize :: Int -> [String] -> [[String]] -chunksOfSize _ [] = [] -chunksOfSize size strings = reverse chunk : chunksOfSize size rest - where - (chunk, rest) = go [] 0 strings - go res _ [] = (res, []) - go res chunkSize (s:ss) = - if newSize > size then (res, s:ss) else go (s:res) newSize ss - where - newSize = chunkSize + length s - -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do @@ -238,12 +246,3 @@ removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f removeDirectoryIfExists :: FilePath -> Action () removeDirectoryIfExists d = liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d - --- | Split function. Splits a string @s@ into chunks --- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 -wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] -wordsWhen p s = - case dropWhile p s of - [] -> [] - s' -> w : wordsWhen p s'' - where (w, s'') = break p s' From git at git.haskell.org Fri Oct 27 00:00:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement path lookup on Windows. (f5299c8) Message-ID: <20171027000051.DAEB33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5299c86b5e89909488e1a5997a8c98c595f5d25/ghc >--------------------------------------------------------------- commit f5299c86b5e89909488e1a5997a8c98c595f5d25 Author: Andrey Mokhov Date: Tue Feb 9 15:05:09 2016 +0000 Implement path lookup on Windows. >--------------------------------------------------------------- f5299c86b5e89909488e1a5997a8c98c595f5d25 shaking-up-ghc.cabal | 2 +- src/Oracles.hs | 4 ++-- src/Oracles/WindowsPath.hs | 41 +++++++++++++++++++++++++++++++++++++ src/Oracles/WindowsRoot.hs | 51 ---------------------------------------------- src/Rules/Oracles.hs | 2 +- src/Test.hs | 2 +- 6 files changed, 46 insertions(+), 56 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 254617d..035bb9d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -34,7 +34,7 @@ executable ghc-shake , Oracles.PackageData , Oracles.PackageDb , Oracles.PackageDeps - , Oracles.WindowsRoot + , Oracles.WindowsPath , Package , Predicates , Rules diff --git a/src/Oracles.hs b/src/Oracles.hs index 564c7bb..eb37b47 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -6,7 +6,7 @@ module Oracles ( module Oracles.LookupInPath, module Oracles.PackageData, module Oracles.PackageDeps, - module Oracles.WindowsRoot + module Oracles.WindowsPath ) where import Oracles.Config @@ -16,4 +16,4 @@ import Oracles.Dependencies import Oracles.LookupInPath import Oracles.PackageData import Oracles.PackageDeps -import Oracles.WindowsRoot +import Oracles.WindowsPath diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs new file mode 100644 index 0000000..189c329 --- /dev/null +++ b/src/Oracles/WindowsPath.hs @@ -0,0 +1,41 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +module Oracles.WindowsPath ( + fixAbsolutePathOnWindows, topDirectory, windowsPathOracle + ) where + +import Data.Char (isSpace) +import Base +import Oracles.Config.Setting + +newtype WindowsPath = WindowsPath FilePath + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +topDirectory :: Action FilePath +topDirectory = do + ghcSourcePath <- setting GhcSourcePath + fixAbsolutePathOnWindows ghcSourcePath + +-- Fix an absolute path on Windows: +-- * "/c/" => "C:/" +-- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" +fixAbsolutePathOnWindows :: FilePath -> Action FilePath +fixAbsolutePathOnWindows path = do + windows <- windowsHost + if windows + then do + let (dir, file) = splitFileName path + winDir <- askOracle $ WindowsPath dir + return $ winDir -/- file + else + return path + +-- Detecting path mapping on Windows. This is slow and requires caching. +windowsPathOracle :: Rules () +windowsPathOracle = do + answer <- newCache $ \path -> do + Stdout out <- quietly $ cmd ["cygpath", "-m", path] + let windowsPath = dropWhileEnd isSpace out + putOracle $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath + return windowsPath + _ <- addOracle $ \(WindowsPath query) -> answer query + return () diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs deleted file mode 100644 index 413f289..0000000 --- a/src/Oracles/WindowsRoot.hs +++ /dev/null @@ -1,51 +0,0 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} -module Oracles.WindowsRoot ( - windowsRoot, fixAbsolutePathOnWindows, topDirectory, windowsRootOracle - ) where - -import Data.Char (isSpace) -import Base -import Oracles.Config.Setting - -newtype WindowsRoot = WindowsRoot () - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) - --- Looks up cygwin/msys root on Windows -windowsRoot :: Action String -windowsRoot = askOracle $ WindowsRoot () - -topDirectory :: Action FilePath -topDirectory = do - ghcSourcePath <- setting GhcSourcePath - fixAbsolutePathOnWindows ghcSourcePath - --- TODO: this is fragile, e.g. we currently only handle C: drive --- On Windows: --- * if the path starts with "/c/" change the prefix to "C:/" --- * otherwise, if the path starts with "/", prepend it with the correct path --- to the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe" -fixAbsolutePathOnWindows :: FilePath -> Action FilePath -fixAbsolutePathOnWindows path = do - windows <- windowsHost - -- Note, below is different from FilePath.isAbsolute: - if (windows && "/" `isPrefixOf` path) - then do - if ("/c/" `isPrefixOf` path) - then return $ "C:" ++ drop 2 path - else do - root <- windowsRoot - return . unifyPath $ root ++ drop 1 path - else - return path - --- Oracle for windowsRoot. This operation requires caching as looking up --- the root is slow (at least the current implementation). -windowsRootOracle :: Rules () -windowsRootOracle = do - root <- newCache $ \_ -> do - Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] - let root = dropWhileEnd isSpace out - putOracle $ "Detected root on Windows: " ++ root - return root - _ <- addOracle $ \WindowsRoot{} -> root () - return () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 55f7aee..1bc1606 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -17,4 +17,4 @@ oracleRules = do packageDataOracle -- see Oracles.PackageData packageDbOracle -- see Oracles.PackageData packageDepsOracle -- see Oracles.PackageDeps - windowsRootOracle -- see Oracles.WindowsRoot + windowsPathOracle -- see Oracles.WindowsRoot diff --git a/src/Test.hs b/src/Test.hs index a79c9fc..f8e93e7 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -6,7 +6,7 @@ import Expression import GHC (rts, libffi) import Oracles.Config.Flag import Oracles.Config.Setting -import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory +import Oracles.WindowsPath import Rules.Actions import Settings.Packages import Settings.User From git at git.haskell.org Fri Oct 27 00:00:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add custom settings for compiler and other packages. (096b595) Message-ID: <20171027000055.06E143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/096b595bc7b269be01cca98aa567c540d8bce1fd/ghc >--------------------------------------------------------------- commit 096b595bc7b269be01cca98aa567c540d8bce1fd Author: Andrey Mokhov Date: Sun Jul 26 01:31:40 2015 +0100 Add custom settings for compiler and other packages. >--------------------------------------------------------------- 096b595bc7b269be01cca98aa567c540d8bce1fd src/Oracles/Flag.hs | 15 ++++++++++++- src/Oracles/Setting.hs | 6 +++++- src/Package/Base.hs | 28 ------------------------ src/Settings/Args.hs | 7 ++++++ src/Settings/GhcCabal.hs | 56 +++++++++++++++++++++++++++++++++++++----------- src/Settings/GhcM.hs | 8 +++++-- src/Settings/User.hs | 17 ++++++++++++--- src/Settings/Ways.hs | 19 +++++++++++++++- src/Switches.hs | 5 ++++- src/Util.hs | 2 +- 10 files changed, 113 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 096b595bc7b269be01cca98aa567c540d8bce1fd From git at git.haskell.org Fri Oct 27 00:00:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move copyRules to Rules/Generate.hs, add missing generated dependencies. (03b3379) Message-ID: <20171027000055.D3A3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03b33797d88b27291c6a05f6141fac18be30efc4/ghc >--------------------------------------------------------------- commit 03b33797d88b27291c6a05f6141fac18be30efc4 Author: Andrey Mokhov Date: Thu Jan 7 17:02:35 2016 +0000 Move copyRules to Rules/Generate.hs, add missing generated dependencies. >--------------------------------------------------------------- 03b33797d88b27291c6a05f6141fac18be30efc4 shaking-up-ghc.cabal | 1 - src/Main.hs | 3 +-- src/Rules.hs | 2 +- src/Rules/Copy.hs | 20 -------------------- src/Rules/Generate.hs | 18 ++++++++++++++++-- 5 files changed, 18 insertions(+), 26 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index c680b85..9f2c80c 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -39,7 +39,6 @@ executable ghc-shake , Rules.Cabal , Rules.Compile , Rules.Config - , Rules.Copy , Rules.Data , Rules.Dependencies , Rules.Documentation diff --git a/src/Main.hs b/src/Main.hs index 043e173..07f14ea 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,7 +3,6 @@ import Rules import Rules.Cabal import Rules.Config import Rules.Generate -import Rules.Copy import Rules.Libffi import Rules.IntegerGmp import Rules.Oracles @@ -12,7 +11,7 @@ main :: IO () main = shakeArgs options $ do cabalRules -- see Rules.Cabal configRules -- see Rules.Config - copyRules -- see Rules.Copy + copyRules -- see Rules.Generate generateTargets -- see Rules generateRules -- see Rules.Generate libffiRules -- see Rules.Libffi diff --git a/src/Rules.hs b/src/Rules.hs index 9933225..22c5230 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -3,7 +3,7 @@ module Rules (generateTargets, packageRules) where import Base import Expression import GHC -import Rules.Copy +import Rules.Generate import Rules.Package import Rules.Resources import Settings diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs deleted file mode 100644 index 7454fd9..0000000 --- a/src/Rules/Copy.hs +++ /dev/null @@ -1,20 +0,0 @@ -module Rules.Copy (installTargets, copyRules) where - -import Base -import Expression -import GHC -import Rules.Actions -import Rules.Generate - -installTargets :: [FilePath] -installTargets = [ "inplace/lib/template-hsc.h" - , "inplace/lib/platformConstants" - , "inplace/lib/settings" ] - -copyRules :: Rules () -copyRules = do - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs - "inplace/lib/platformConstants" <~ derivedConstantsPath - "inplace/lib/settings" <~ "." - where - file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8ca7b94..71d88b1 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,7 @@ module Rules.Generate ( generatePackageCode, generateRules, - derivedConstantsPath, generatedDependencies + derivedConstantsPath, generatedDependencies, + installTargets, copyRules ) where import Base @@ -20,6 +21,11 @@ import Rules.Resources (Resources) import Settings import Settings.Builders.DeriveConstants +installTargets :: [FilePath] +installTargets = [ "inplace/lib/template-hsc.h" + , "inplace/lib/platformConstants" + , "inplace/lib/settings" ] + primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -45,7 +51,7 @@ ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> , "autogen/GHC/Prim.hs" ] derivedConstantsDependencies :: [FilePath] -derivedConstantsDependencies = (derivedConstantsPath -/-) <$> +derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) [ "DerivedConstants.h" , "GHCConstantsHaskellType.hs" , "GHCConstantsHaskellWrappers.hs" @@ -150,6 +156,14 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = copyFileChanged (pkgPath pkg -/- "runghc.hs") file putSuccess $ "| Successfully generated '" ++ file ++ "'." +copyRules :: Rules () +copyRules = do + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs + "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." + where + file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file + generateRules :: Rules () generateRules = do "includes/ghcautoconf.h" <~ generateGhcAutoconfH From git at git.haskell.org Fri Oct 27 00:00:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix executable lookup. (68cf604) Message-ID: <20171027000056.501123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68cf6048ac5a08b158282d9284868002ecc28a8e/ghc >--------------------------------------------------------------- commit 68cf6048ac5a08b158282d9284868002ecc28a8e Author: Andrey Mokhov Date: Tue Feb 9 15:59:04 2016 +0000 Fix executable lookup. >--------------------------------------------------------------- 68cf6048ac5a08b158282d9284868002ecc28a8e src/Builder.hs | 10 +++++----- src/Oracles/LookupInPath.hs | 24 ++++++++++-------------- 2 files changed, 15 insertions(+), 19 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index d1a2cc3..1826875 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -112,11 +112,11 @@ builderPath builder = case builderProvenance builder of path <- askConfigWithDefault builderKey . putError $ "\nCannot find path to '" ++ builderKey ++ "' in configuration files. Have you forgot to run configure?" - windows <- windowsHost - case (path, windows) of - ("", _ ) -> return path - (p , True ) -> fixAbsolutePathOnWindows (p -<.> exe) - (p , False) -> lookupInPath p + if path == "" -- TODO: get rid of "" paths + then return "" + else do + path' <- lookupInPath path + fixAbsolutePathOnWindows $ path' -<.> exe getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index a9dc995..6bf2bba 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -1,29 +1,25 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where +import System.Directory + import Base newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) --- | Fetches the absolute FilePath to a given FilePath using the oracle. -commandPath :: FilePath -> Action FilePath -commandPath = askOracle . LookupInPath - --- | Lookup a @command@ in @PATH@ environment. +-- | Lookup an executable in @PATH at . lookupInPath :: FilePath -> Action FilePath -lookupInPath c - | c /= takeFileName c = return c - | otherwise = commandPath c +lookupInPath name + | name == takeFileName name = askOracle $ LookupInPath name + | otherwise = return name lookupInPathOracle :: Rules () lookupInPathOracle = do answer <- newCache $ \query -> do - envPaths <- wordsBy (== ':') <$> getEnvWithDefault "" "PATH" - let candidates = map (-/- query) envPaths - -- this will crash if we do not find any valid candidate. - fullCommand <- head <$> filterM doesFileExist candidates - putOracle $ "Found '" ++ query ++ "' at " ++ "'" ++ fullCommand ++ "'" - return fullCommand + maybePath <- liftIO $ findExecutable query + let path = fromMaybe query maybePath + putOracle $ "Lookup executable '" ++ query ++ "': " ++ path + return path _ <- addOracle $ \(LookupInPath query) -> answer query return () From git at git.haskell.org Fri Oct 27 00:00:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:00:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Parallelise build by collecting targets and then needing them. (9463852) Message-ID: <20171027000058.D000C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/946385207cf7691b7baa05e3003ebfa4fdb29082/ghc >--------------------------------------------------------------- commit 946385207cf7691b7baa05e3003ebfa4fdb29082 Author: Andrey Mokhov Date: Sun Jul 26 17:01:03 2015 +0100 Parallelise build by collecting targets and then needing them. >--------------------------------------------------------------- 946385207cf7691b7baa05e3003ebfa4fdb29082 src/Rules.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index f8fd786..b63687f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,7 +1,7 @@ module Rules ( generateTargets, packageRules, oracleRules, - module Rules.Package, module Rules.Config, + module Rules.Package, ) where import Util @@ -17,12 +17,13 @@ import Development.Shake -- generateTargets needs package-data.mk files of all target packages -- TODO: make interpretDiff total generateTargets :: Rules () -generateTargets = action $ - forM_ [Stage0 ..] $ \stage -> do +generateTargets = action $ do + targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpret (stageTarget stage) packages - forM_ pkgs $ \pkg -> do - need [targetPath stage pkg -/- "build/haskell.deps"] - need [targetPath stage pkg -/- "build/c.deps"] + fmap concat . forM pkgs $ \pkg -> return + [ targetPath stage pkg -/- "build/haskell.deps" + , targetPath stage pkg -/- "build/c.deps" ] + need targets -- TODO: add Stage2 (compiler only?) packageRules :: Rules () From git at git.haskell.org Fri Oct 27 00:01:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddock comments in Predicates.hs (de634da) Message-ID: <20171027000100.30C733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de634dadaf365799b3e0b8945ec812b2bec37c74/ghc >--------------------------------------------------------------- commit de634dadaf365799b3e0b8945ec812b2bec37c74 Author: David Luposchainsky Date: Wed Jan 6 14:31:37 2016 +0100 Add Haddock comments in Predicates.hs >--------------------------------------------------------------- de634dadaf365799b3e0b8945ec812b2bec37c74 src/Predicates.hs | 23 +++++++++++++++++------ 1 file changed, 17 insertions(+), 6 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index ad63598..b5ce0cb 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -7,49 +7,60 @@ module Predicates ( import Base import Expression --- Basic predicates +-- | Is the build currently in the provided stage? stage :: Stage -> Predicate stage s = fmap (s ==) getStage +-- | Is a particular package being built? package :: Package -> Predicate package p = fmap (p ==) getPackage --- For unstaged builders, e.g. GhcCabal +-- | Is an unstaged builder is being used such as /GhcCabal/? builder :: Builder -> Predicate builder b = fmap (b ==) getBuilder --- For staged builders, e.g. Ghc Stage +-- | Is a certain builder used in the current stage? stagedBuilder :: (Stage -> Builder) -> Predicate -stagedBuilder sb = (builder . sb) =<< getStage +stagedBuilder stageBuilder = do + s <- getStage + builder (stageBuilder s) +-- | Are we building with GCC? builderGcc :: Predicate builderGcc = stagedBuilder Gcc ||^ stagedBuilder GccM +-- | Are we building with GHC? builderGhc :: Predicate builderGhc = stagedBuilder Ghc ||^ stagedBuilder GhcM +-- | Does any of the output files match a given pattern? file :: FilePattern -> Predicate file f = fmap (any (f ?==)) getOutputs +-- | Is the current build 'Way' equal to a certain value? way :: Way -> Predicate way w = fmap (w ==) getWay --- Derived predicates +-- | Is the build currently in stage 0? stage0 :: Predicate stage0 = stage Stage0 +-- | Is the build currently in stage 1? stage1 :: Predicate stage1 = stage Stage1 +-- | Is the build currently in stage 2? stage2 :: Predicate stage2 = stage Stage2 +-- | Is the build /not/ in stage 0 right now? notStage0 :: Predicate notStage0 = notM stage0 +-- | Is a certain package /not/ built right now? notPackage :: Package -> Predicate notPackage = notM . package --- TODO: Actually, we don't register compiler in some circumstances -- fix. +-- | TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate registerPackage = return True From git at git.haskell.org Fri Oct 27 00:01:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use qualified imports. (bd405c1) Message-ID: <20171027000100.6FEAB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd405c1006be30c99cb718a30dd779c1462baf61/ghc >--------------------------------------------------------------- commit bd405c1006be30c99cb718a30dd779c1462baf61 Author: Andrey Mokhov Date: Wed Feb 10 01:03:56 2016 +0000 Use qualified imports. >--------------------------------------------------------------- bd405c1006be30c99cb718a30dd779c1462baf61 src/Rules/Oracles.hs | 32 ++++++++++++++++++-------------- 1 file changed, 18 insertions(+), 14 deletions(-) diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 1bc1606..108c5ce 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -1,20 +1,24 @@ module Rules.Oracles (oracleRules) where import Base -import Oracles -import Oracles.ArgsHash -import Oracles.PackageDb -import Oracles.ModuleFiles +import qualified Oracles.Config +import qualified Oracles.Dependencies +import qualified Oracles.LookupInPath +import qualified Oracles.PackageData +import qualified Oracles.PackageDeps +import qualified Oracles.WindowsPath +import qualified Oracles.ArgsHash +import qualified Oracles.ModuleFiles +import qualified Oracles.PackageDb --- TODO: replace comments with qualified imports oracleRules :: Rules () oracleRules = do - argsHashOracle -- see Oracles.ArgsHash - configOracle -- see Oracles.Config - dependenciesOracle -- see Oracles.Dependencies - lookupInPathOracle -- see Oracles.LookupInPath - moduleFilesOracle -- see Oracles.ModuleFiles - packageDataOracle -- see Oracles.PackageData - packageDbOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - windowsPathOracle -- see Oracles.WindowsRoot + Oracles.ArgsHash.argsHashOracle + Oracles.Config.configOracle + Oracles.Dependencies.dependenciesOracle + Oracles.LookupInPath.lookupInPathOracle + Oracles.ModuleFiles.moduleFilesOracle + Oracles.PackageData.packageDataOracle + Oracles.PackageDb.packageDbOracle + Oracles.PackageDeps.packageDepsOracle + Oracles.WindowsPath.windowsPathOracle From git at git.haskell.org Fri Oct 27 00:01:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for resources. Limit parallelism of ghc-pkg. (6547fc7) Message-ID: <20171027000102.55CAC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6547fc76758720a51f4b0d4819b95128892be459/ghc >--------------------------------------------------------------- commit 6547fc76758720a51f4b0d4819b95128892be459 Author: Andrey Mokhov Date: Sun Jul 26 17:03:36 2015 +0100 Add support for resources. Limit parallelism of ghc-pkg. >--------------------------------------------------------------- 6547fc76758720a51f4b0d4819b95128892be459 src/Rules/Actions.hs | 33 ++++++++++++++++----------------- src/Rules/Data.hs | 39 ++++++++++++++++++++++----------------- src/Target.hs | 5 +++-- 3 files changed, 41 insertions(+), 36 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 055931e..2730c55 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,5 +1,5 @@ module Rules.Actions ( - build, buildWhen, run, verboseRun + build, buildWithResources, run, verboseRun ) where import Util @@ -11,38 +11,37 @@ import Settings.Util import Oracles.ArgsHash import Development.Shake --- Build a given target using an appropriate builder. Force a rebuilt if the --- argument list has changed since the last built (that is, track changes in --- the build system). -build :: FullTarget -> Action () -build target = do +-- Build a given target using an appropriate builder and acquiring necessary +-- resources. Force a rebuilt if the argument list has changed since the last +-- built (that is, track changes in the build system). +buildWithResources :: [(Resource, Int)] -> FullTarget -> Action () +buildWithResources rs target = do need $ Target.dependencies target argList <- interpret target args -- The line below forces the rule to be rerun if the args hash has changed argsHash <- askArgsHash target - run (Target.builder target) argList + run rs (Target.builder target) argList -buildWhen :: Predicate -> FullTarget -> Action () -buildWhen predicate target = do - bool <- interpretExpr target predicate - when bool $ build target +-- Most targets are built without explicitly acquiring resources +build :: FullTarget -> Action () +build = buildWithResources [] -- Run the builder with a given collection of arguments -verboseRun :: Builder -> [String] -> Action () -verboseRun builder args = do +verboseRun :: [(Resource, Int)] -> Builder -> [String] -> Action () +verboseRun rs builder args = do needBuilder builder path <- builderPath builder - cmd [path] args + withResources rs $ cmd [path] args -- Run the builder with a given collection of arguments printing out a -- terse commentary with only 'interesting' info for the builder. -run :: Builder -> [String] -> Action () -run builder args = do +run :: [(Resource, Int)] -> Builder -> [String] -> Action () +run rs builder args = do putColoured White $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" mapM_ (putColoured White . ("| " ++)) $ interestingInfo builder args putColoured White $ "\\--------" - quietly $ verboseRun builder args + quietly $ verboseRun rs builder args interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index b48ff48..d60dbfa 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -12,31 +12,36 @@ import Control.Applicative import Control.Monad.Extra import Development.Shake +-- TODO: Add ordering between packages? (see ghc.mk) -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: StagePackageTarget -> Rules () -buildPackageData target = +buildPackageData target = do let stage = Target.stage target pkg = Target.package target path = targetPath stage pkg cabal = pkgPath pkg -/- pkgCabal pkg configure = pkgPath pkg -/- "configure" - in + + -- We do not allow parallel invokations of ghc-pkg (they don't work) + ghcPkg <- newResource "ghc-pkg" 1 + (path -/-) <$> - [ "package-data.mk" - , "haddock-prologue.txt" - , "inplace-pkg-config" - , "setup-config" - , "build" -/- "autogen" -/- "cabal_macros.h" - -- TODO: Is this needed? Also check out Paths_cpsa.hs. - -- , "build" -/- "autogen" -/- ("Paths_" ++ name) <.> "hs" - ] &%> \files -> do - -- GhcCabal may run the configure script, so we depend on it - -- We still don't know who built the configure script from configure.ac - whenM (doesFileExist $ configure <.> "ac") $ need [configure] - build $ fullTarget target [cabal] GhcCabal files - buildWhen registerPackage $ - fullTarget target [cabal] (GhcPkg stage) files - postProcessPackageData $ path -/- "package-data.mk" + [ "package-data.mk" + , "haddock-prologue.txt" + , "inplace-pkg-config" + , "setup-config" + , "build" -/- "autogen" -/- "cabal_macros.h" + -- TODO: Is this needed? Also check out Paths_cpsa.hs. + -- , "build" -/- "autogen" -/- ("Paths_" ++ name) <.> "hs" + ] &%> \files -> do + -- GhcCabal may run the configure script, so we depend on it + -- We don't know who built the configure script from configure.ac + whenM (doesFileExist $ configure <.> "ac") $ need [configure] + build $ fullTarget target [cabal] GhcCabal files + whenM (interpretExpr target registerPackage) . + buildWithResources [(ghcPkg, 1)] $ + fullTarget target [cabal] (GhcPkg stage) files + postProcessPackageData $ path -/- "package-data.mk" -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' diff --git a/src/Target.hs b/src/Target.hs index c3b6b93..dc0bde7 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} module Target ( Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), - stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay + stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay, ) where import Way @@ -72,7 +72,8 @@ fullTarget target deps b fs = target } -- Use this function to be explicit about the build way. -fullTargetWithWay :: StagePackageTarget -> [FilePath] -> Builder -> Way -> [FilePath] -> FullTarget +fullTargetWithWay :: StagePackageTarget -> [FilePath] -> Builder -> Way + -> [FilePath] -> FullTarget fullTargetWithWay target deps b w fs = target { dependencies = deps, From git at git.haskell.org Fri Oct 27 00:01:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make value sources more explicit (921dcce) Message-ID: <20171027000104.087103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/921dcce1ab2e0cc1e6df25df98bb24f134fe0742/ghc >--------------------------------------------------------------- commit 921dcce1ab2e0cc1e6df25df98bb24f134fe0742 Author: David Luposchainsky Date: Tue Jan 5 16:44:06 2016 +0100 Make value sources more explicit [skip ci] Rather than relying on comments, move the documentation into the source, so it's checked by the compiler automatically >--------------------------------------------------------------- 921dcce1ab2e0cc1e6df25df98bb24f134fe0742 src/Main.hs | 40 ++++++++++++++++++++++------------------ 1 file changed, 22 insertions(+), 18 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 07f14ea..bacc8f1 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,24 +1,28 @@ -import Base -import Rules -import Rules.Cabal -import Rules.Config -import Rules.Generate -import Rules.Libffi -import Rules.IntegerGmp -import Rules.Oracles +module Main (main) where + +import qualified Base as B +import qualified Rules as R +import qualified Rules.Cabal as RCabal +import qualified Rules.Config as RConfig +import qualified Rules.Copy as RCopy +import qualified Rules.Generate as RGen +import qualified Rules.IntegerGmp as RInt +import qualified Rules.Libffi as RFfi +import qualified Rules.Oracles as ROracle main :: IO () -main = shakeArgs options $ do - cabalRules -- see Rules.Cabal - configRules -- see Rules.Config - copyRules -- see Rules.Generate - generateTargets -- see Rules - generateRules -- see Rules.Generate - libffiRules -- see Rules.Libffi - integerGmpRules -- see Rules.IntegerGmp - oracleRules -- see Rules.Oracles - packageRules -- see Rules +main = shakeArgs options rules where + rules = mconcat + [ RCabal.cabalRules + , RConfig.configRules + , RCopy.copyRules + , R.generateTargets + , RGen.generateRules + , RFfi.libffiRules + , RInt.integerGmpRules + , ROracle.oracleRules + , R.packageRules ] options = shakeOptions { shakeFiles = shakeFilesPath , shakeProgress = progressSimple From git at git.haskell.org Fri Oct 27 00:01:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop top-level Oracles.hs (3178d82) Message-ID: <20171027000104.480AC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3178d829038e5216c474f5ce6f8f7bd7b09b02f9/ghc >--------------------------------------------------------------- commit 3178d829038e5216c474f5ce6f8f7bd7b09b02f9 Author: Andrey Mokhov Date: Wed Feb 10 01:20:56 2016 +0000 Drop top-level Oracles.hs >--------------------------------------------------------------- 3178d829038e5216c474f5ce6f8f7bd7b09b02f9 shaking-up-ghc.cabal | 1 - src/Builder.hs | 4 +++- src/Oracles.hs | 19 ------------------- src/Rules/Actions.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 3 ++- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generators/ConfigHs.hs | 3 ++- src/Rules/Generators/GhcAutoconfH.hs | 3 ++- src/Rules/Generators/GhcBootPlatformH.hs | 2 +- src/Rules/Generators/GhcPlatformH.hs | 3 ++- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Generators/GhcVersionH.hs | 2 +- src/Rules/Generators/VersionHs.hs | 2 +- src/Rules/Libffi.hs | 4 +++- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 3 ++- src/Settings.hs | 3 ++- src/Settings/Builders/Ar.hs | 3 ++- src/Settings/Builders/Gcc.hs | 2 +- src/Settings/Builders/Ghc.hs | 3 ++- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 4 +++- src/Settings/Builders/Ld.hs | 2 +- src/Way.hs | 2 +- 27 files changed, 39 insertions(+), 45 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 3178d829038e5216c474f5ce6f8f7bd7b09b02f9 From git at git.haskell.org Fri Oct 27 00:01:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix custom settings of the compiler package. (3090409) Message-ID: <20171027000105.C2E323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3090409f9a90cda50892d25f02ea3e3a55f43121/ghc >--------------------------------------------------------------- commit 3090409f9a90cda50892d25f02ea3e3a55f43121 Author: Andrey Mokhov Date: Sun Jul 26 17:04:23 2015 +0100 Fix custom settings of the compiler package. >--------------------------------------------------------------- 3090409f9a90cda50892d25f02ea3e3a55f43121 src/Settings/GhcCabal.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index cba05cc..2c475ab 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -149,6 +149,7 @@ customPackageArgs = do , package compiler ? builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (succ stage) + , arg $ "--flags=stage" ++ show (succ stage) , arg "--disable-library-for-ghci" , targetOs "openbsd" ? arg "--ld-options=-E" , flag GhcUnregisterised ? arg "--ghc-option=-DNO_REGS" @@ -157,7 +158,8 @@ customPackageArgs = do , (threaded `elem` rtsWays) ? notStage0 ? arg "--ghc-option=-optc-DTHREADED_RTS" , ghcWithNativeCodeGen ? arg "--flags=ncg" - , ghcWithInterpreter ? arg "--flags=ghci" + , ghcWithInterpreter ? + notStage0 ? arg "--flags=ghci" , ghcWithInterpreter ? ghcEnableTablesNextToCode ? notP (flag GhcUnregisterised) ? From git at git.haskell.org Fri Oct 27 00:01:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split up definitions in Rules.hs (20381e5) Message-ID: <20171027000107.AF6E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20381e58208ca2693f034566e450f5b0b28674b4/ghc >--------------------------------------------------------------- commit 20381e58208ca2693f034566e450f5b0b28674b4 Author: David Luposchainsky Date: Wed Jan 6 14:49:58 2016 +0100 Split up definitions in Rules.hs >--------------------------------------------------------------- 20381e58208ca2693f034566e450f5b0b28674b4 src/Rules.hs | 33 ++++++++++++++++++++------------- 1 file changed, 20 insertions(+), 13 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 22c5230..f8b2810 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,6 +1,8 @@ module Rules (generateTargets, packageRules) where import Base +import Data.Foldable +import Data.Traversable import Expression import GHC import Rules.Generate @@ -8,26 +10,31 @@ import Rules.Package import Rules.Resources import Settings +allStages :: [Stage] +allStages = [Stage0 ..] + -- TODO: not all program targets should be needed explicitly --- | generateTargets needs top-level build targets +-- | 'need' all top-level build targets generateTargets :: Rules () generateTargets = action $ do - targets <- fmap concat . forM [Stage0 ..] $ \stage -> do - pkgs <- interpretWithStage stage getPackages - let libPkgs = filter isLibrary pkgs \\ [rts, libffi] - libTargets <- fmap concat . forM libPkgs $ \pkg -> do - let target = PartialTarget stage pkg - needHaddock <- interpretPartial target buildHaddock - return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] - let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] - return $ libTargets ++ programTargets - + targets <- fmap concat (traverse targetsForStage allStages) rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla need $ targets ++ installTargets ++ [ rtsLib ] +targetsForStage :: Stage -> Action [String] +targetsForStage stage = do + pkgs <- interpretWithStage stage getPackages + let libPkgs = filter isLibrary pkgs \\ [rts, libffi] + libTargets <- fmap concat . for libPkgs $ \pkg -> do + let target = PartialTarget stage pkg + needHaddock <- interpretPartial target buildHaddock + return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] + let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] + return (libTargets ++ programTargets) + packageRules :: Rules () packageRules = do resources <- resourceRules - forM_ [Stage0 ..] $ \stage -> - forM_ knownPackages $ \pkg -> + for allStages $ \stage -> + for_ knownPackages $ \pkg -> buildPackage resources $ PartialTarget stage pkg From git at git.haskell.org Fri Oct 27 00:01:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Report an error if an executable is not found, unify paths. (05e7242) Message-ID: <20171027000108.088543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/05e7242655e0b8d5657c487e2ed2f392dd520429/ghc >--------------------------------------------------------------- commit 05e7242655e0b8d5657c487e2ed2f392dd520429 Author: Andrey Mokhov Date: Wed Feb 10 11:27:03 2016 +0000 Report an error if an executable is not found, unify paths. >--------------------------------------------------------------- 05e7242655e0b8d5657c487e2ed2f392dd520429 src/Oracles/LookupInPath.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 6bf2bba..2f6e713 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -18,8 +18,10 @@ lookupInPathOracle :: Rules () lookupInPathOracle = do answer <- newCache $ \query -> do maybePath <- liftIO $ findExecutable query - let path = fromMaybe query maybePath - putOracle $ "Lookup executable '" ++ query ++ "': " ++ path + path <- case maybePath of + Just value -> return $ unifyPath value + Nothing -> putError $ "Cannot find executable '" ++ query ++ "'." + putOracle $ "Executable found: " ++ query ++ " => " ++ path return path _ <- addOracle $ \(LookupInPath query) -> answer query return () From git at git.haskell.org Fri Oct 27 00:01:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add to demo.txt. (140376a) Message-ID: <20171027000109.371C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/140376acfd4cedd015f436f83ea30abf3aaed848/ghc >--------------------------------------------------------------- commit 140376acfd4cedd015f436f83ea30abf3aaed848 Author: Andrey Mokhov Date: Mon Jul 27 02:03:46 2015 +0100 Add to demo.txt. >--------------------------------------------------------------- 140376acfd4cedd015f436f83ea30abf3aaed848 doc/demo.txt | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/doc/demo.txt b/doc/demo.txt index 4b6b671..cec474a 100644 --- a/doc/demo.txt +++ b/doc/demo.txt @@ -2,3 +2,8 @@ 2. Rebuild only when package-data.mk contents has changed * Add to Settings/GhcPkg.hs: package deepseq ? arg "--force" + +3. Reduce complexity when searching for source files by 40x: + +* compiler, was: 25 dirs (24 source dirs + autogen) x 406 modules x 2 extensions = 20300 candidates +* compiler, now: 25 dirs x 20 module-dirs = 500 candidates \ No newline at end of file From git at git.haskell.org Thu Oct 26 23:58:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix cabal rename error. (e008f71) Message-ID: <20171026235811.2F32B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e008f71950c8197157e3da6274b12d410bce81f9/ghc >--------------------------------------------------------------- commit e008f71950c8197157e3da6274b12d410bce81f9 Author: Andrey Mokhov Date: Wed Jan 6 20:30:11 2016 +0000 Fix cabal rename error. See #110. [skip ci] >--------------------------------------------------------------- e008f71950c8197157e3da6274b12d410bce81f9 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 47210eb..8bb6c15 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,7 +8,7 @@ install: - bash -lc "mkdir /usr/local" - bash -lc "mkdir /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - - ren C:\msys64\usr\local\bin\cabal-1.22.0.0-i386-unknown-mingw32.exe C:\msys64\usr\local\bin\cabal.exe + - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" From git at git.haskell.org Thu Oct 26 23:58:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. Minor refactoring. (acde0ea) Message-ID: <20171026235811.3CBF93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acde0ea23775e06a4cfd2f60974c075e8babdc86/ghc >--------------------------------------------------------------- commit acde0ea23775e06a4cfd2f60974c075e8babdc86 Author: Andrey Mokhov Date: Tue Jun 16 01:09:37 2015 +0100 Add comments. Minor refactoring. >--------------------------------------------------------------- acde0ea23775e06a4cfd2f60974c075e8babdc86 src/Expression.hs | 5 +++-- src/Rules.hs | 3 +-- src/Settings.hs | 1 + src/Settings/GhcCabal.hs | 2 +- src/Settings/Util.hs | 5 +++++ src/Switches.hs | 2 ++ src/Targets.hs | 7 ++++--- src/UserSettings.hs | 7 ++++++- 8 files changed, 23 insertions(+), 9 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 81ed26f..a0c3bf0 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -124,7 +124,7 @@ interpretDiff env = interpret env . fromDiff (??) :: Monoid a => Predicate -> (Expr a, Expr a) -> Expr a p ?? (t, f) = p ? t <> (liftM not p) ? f --- Basic predicates +-- Basic predicates (see Switches.hs for derived predicates) stage :: Stage -> Predicate stage s = liftM (s ==) (asks getStage) @@ -137,6 +137,7 @@ package p = liftM (p ==) (asks getPackage) configKeyValue :: String -> String -> Predicate configKeyValue key value = liftM (value ==) (lift $ askConfig key) --- checks if there is at least one match +-- Check if there is at least one match +-- Example: configKeyValues "host-os-cpp" ["mingw32", "cygwin32"] configKeyValues :: String -> [String] -> Predicate configKeyValues key values = liftM (`elem` values) (lift $ askConfig key) diff --git a/src/Rules.hs b/src/Rules.hs index 5d59ae6..a84f30e 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -13,7 +13,7 @@ import Rules.Package import Settings.Packages -- generateTargets needs package-data.mk files of all target packages --- TODO: make interpret total +-- TODO: make interpretDiff total generateTargets :: Rules () generateTargets = action $ forM_ [Stage0 ..] $ \stage -> do @@ -23,7 +23,6 @@ generateTargets = action $ let dir = targetDirectory stage pkg need [pkgPath pkg dir "package-data.mk"] --- TODO: make interpret total -- TODO: add Stage2 (compiler only?) packageRules :: Rules () packageRules = diff --git a/src/Settings.hs b/src/Settings.hs index cde678e..fb0938a 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -12,6 +12,7 @@ import Expression hiding (when, liftIO) settings :: Settings settings = defaultSettings <> userSettings +-- TODO: add all other settings defaultSettings :: Settings defaultSettings = mconcat [ cabalSettings diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 21ca0e0..4388b17 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -105,7 +105,7 @@ packageConstraints = do ++ cabal ++ "'." args $ concatMap (\c -> ["--constraint", c]) $ constraints --- TODO: remove +-- TODO: should be in a different file ccSettings :: Settings ccSettings = validating ? do let gccGe46 = liftM not gccLt46 diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index dba49d5..74190ec 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -47,6 +47,7 @@ argStagedConfigList key = do stage <- asks getStage argConfigList (stagedKey stage key) +-- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal appendCcArgs :: [String] -> Settings appendCcArgs args = do stage <- asks getStage @@ -54,6 +55,10 @@ appendCcArgs args = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" args , builder GhcCabal ? appendSub "--gcc-options" args ] + + + + -- packageData :: Arity -> String -> Settings -- packageData arity key = -- return $ EnvironmentParameter $ PackageData arity key Nothing Nothing diff --git a/src/Switches.hs b/src/Switches.hs index 5436d94..3c6abac 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -12,6 +12,8 @@ module Switches ( import Base import Expression +-- TODO: This setting should be moved to UserSettings.hs +-- TODO: Define three packages for integer library instead of one in Targets.hs -- Support for multiple integer library implementations data IntegerLibraryImpl = IntegerGmp | IntegerGmp2 | IntegerSimple diff --git a/src/Targets.hs b/src/Targets.hs index 1839112..2c61152 100644 --- a/src/Targets.hs +++ b/src/Targets.hs @@ -20,6 +20,7 @@ import Oracles.Builder -- * build/ : contains compiled object code -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal +-- TODO: This is currently not user configurable. Is this right? targetDirectory :: Stage -> Package -> FilePath targetDirectory stage package | package == compiler = "stage" ++ show (fromEnum stage + 1) @@ -85,14 +86,14 @@ customPackageSettings :: Settings customPackageSettings = mconcat [ package integerLibrary ? mconcat [ windowsHost ? builder GhcCabal ? - append ["--configure-option=--with-intree-gmp"] + arg "--configure-option=--with-intree-gmp" , appendCcArgs ["-Ilibraries/integer-gmp2/gmp"] ] , package base ? - builder GhcCabal ? append ["--flags=" ++ integerLibraryName] + builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) , package ghcPrim ? - builder GhcCabal ? append ["--flag=include-ghc-prim"] ] + builder GhcCabal ? arg "--flag=include-ghc-prim" ] -- Note [Cabal name weirdness] -- Find out if we can move the contents to just Cabal/ diff --git a/src/UserSettings.hs b/src/UserSettings.hs index f443659..378db1c 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -10,18 +10,23 @@ import Ways import Targets import Switches import Expression +import Settings.Util -- No user-specific settings by default userSettings :: Settings userSettings = mempty +-- Control conditions of which packages get to be built +-- TODO: adding *new* packages is not possible (see knownPackages in Targets.hs) userPackages :: Packages userPackages = mempty +-- Control which ways are built userWays :: Ways userWays = mempty -- User-defined predicates +-- TODO: migrate more predicates here from configuration files buildHaddock :: Predicate buildHaddock = return True @@ -31,7 +36,7 @@ validating = return False -- Examples: userSettings' :: Settings userSettings' = mconcat - [ package compiler ? stage0 ? append ["foo", "bar"] + [ package compiler ? stage0 ? arg "foo" , builder (Ghc Stage0) ? remove ["-O2"] , builder GhcCabal ? removeSub "--configure-option=CFLAGS" ["-Werror"] ] From git at git.haskell.org Thu Oct 26 23:58:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on validate target (4cc0abb) Message-ID: <20171026235811.904D23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4cc0abb94f94db16533a6737de3e892409e389fc/ghc >--------------------------------------------------------------- commit 4cc0abb94f94db16533a6737de3e892409e389fc Author: Andrey Mokhov Date: Sun Jan 31 00:00:48 2016 +0000 Add a note on validate target See #187. [skip ci] >--------------------------------------------------------------- 4cc0abb94f94db16533a6737de3e892409e389fc README.md | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 56e13ad..0a60d11 100644 --- a/README.md +++ b/README.md @@ -83,8 +83,13 @@ the previous build are still in the GHC tree. #### Testing -* `shake-build/build.sh test` runs GHC tests. The current implementation is very -limited and cannot replace the `validate` script (see [#187][validation-issue]). +* `shake-build/build.sh validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` +directory. This can be used instead of `sh validate --fast --no-clean` in the existing build system. +Note: this will rebuild Stage2 GHC, `ghc-pkg` and `hpc` if they are out of date. + +* `shake-build/build.sh test` runs GHC tests by calling the `testsuite/driver/runtests.py` python +script with appropriate flags. The current implementation is limited and cannot replace the +`validate` script (see [#187][validation-issue]). * `shake-build/build.sh selftest` runs tests of the build system. Current test coverage is close to zero (see [#197][test-issue]). From git at git.haskell.org Thu Oct 26 23:58:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change cabal config path and cache it. (a4447be) Message-ID: <20171026235814.AC3263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4447bef24be3eebef8413d27f34aec113d73b4f/ghc >--------------------------------------------------------------- commit a4447bef24be3eebef8413d27f34aec113d73b4f Author: Andrey Mokhov Date: Wed Jan 6 22:07:41 2016 +0000 Change cabal config path and cache it. See #110. [skip ci] >--------------------------------------------------------------- a4447bef24be3eebef8413d27f34aec113d73b4f .appveyor.yml | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 8bb6c15..f70a821 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,5 +1,8 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" +cache: + - "C:\\msys64\home\cabal" + install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% @@ -9,10 +12,10 @@ install: - bash -lc "mkdir /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal update" - - bash -lc "cabal install -j --prefix=/usr/local alex happy" + - bash -lc "cabal --config-file=/home/cabal update" + - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Thu Oct 26 23:58:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Oct 2017 23:58:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add getFile and getWay to Environment. (2f373e4) Message-ID: <20171026235815.39EDE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f373e4ab96d1eab13b9e358c39170684a34fa1e/ghc >--------------------------------------------------------------- commit 2f373e4ab96d1eab13b9e358c39170684a34fa1e Author: Andrey Mokhov Date: Tue Jun 16 07:48:23 2015 +0100 Add getFile and getWay to Environment. >--------------------------------------------------------------- 2f373e4ab96d1eab13b9e358c39170684a34fa1e doc/meeting-16-June-2015.txt | 51 +++++++++++++++++++++++++++++++++----------- src/Expression.hs | 21 ++++++++++++------ src/Targets.hs | 1 + src/UserSettings.hs | 22 +++++++++++++++---- 4 files changed, 72 insertions(+), 23 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 2f373e4ab96d1eab13b9e358c39170684a34fa1e From git at git.haskell.org Fri Oct 27 00:01:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddocks to Target.hs (1b013b0) Message-ID: <20171027000111.1B1D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b013b0886e59cdd0ff2bd7a182e874d21899961/ghc >--------------------------------------------------------------- commit 1b013b0886e59cdd0ff2bd7a182e874d21899961 Author: David Luposchainsky Date: Wed Jan 6 15:14:08 2016 +0100 Add Haddocks to Target.hs >--------------------------------------------------------------- 1b013b0886e59cdd0ff2bd7a182e874d21899961 src/Expression.hs | 4 +-- src/Target.hs | 75 ++++++++++++++++++++++++++++++++----------------------- 2 files changed, 46 insertions(+), 33 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index a2eaea9..6e2a225 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -12,7 +12,7 @@ module Expression ( -- ** Common expressions Args, Ways, Packages, -- ** Targets - Target, PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay, + Target, PartialTarget (..), unsafeFromPartial, fullTarget, fullTargetWithWay, -- * Convenient accessors getStage, getPackage, getBuilder, getOutputs, getInputs, getWay, @@ -150,7 +150,7 @@ interpret :: Target -> Expr a -> Action a interpret = flip runReaderT interpretPartial :: PartialTarget -> Expr a -> Action a -interpretPartial = interpret . fromPartial +interpretPartial = interpret . unsafeFromPartial interpretWithStage :: Stage -> Expr a -> Action a interpretWithStage s = interpretPartial $ diff --git a/src/Target.hs b/src/Target.hs index cd22f48..152de3d 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,7 +1,11 @@ {-# LANGUAGE DeriveGeneric, FlexibleInstances #-} module Target ( - Target (..), PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay - ) where + Target (..) + , PartialTarget (..) + , unsafeFromPartial + , fullTarget + , fullTargetWithWay +) where import Control.Monad.Trans.Reader @@ -12,50 +16,53 @@ import Package import Stage import Way --- Target captures all parameters relevant to the current build target: --- * Stage and Package being built, --- * Builder to be invoked, --- * Way to be built (set to vanilla for most targets), --- * source file(s) to be passed to Builder, --- * file(s) to be produced. +-- | Parameters relevant to the current build target. data Target = Target { - stage :: Stage, - package :: Package, - builder :: Builder, - way :: Way, - inputs :: [FilePath], - outputs :: [FilePath] + stage :: Stage, -- ^ Stage being built + package :: Package, -- ^ Package being built + builder :: Builder, -- ^ Builder to be invoked + way :: Way, -- ^ Way to build (set to vanilla for most targets) + inputs :: [FilePath], -- ^ Source files passed to the builder + outputs :: [FilePath] -- ^ Files to be produced } deriving (Show, Eq, Generic) --- If values of type 'a' form a Monoid then we can also derive a Monoid instance --- for values of type 'ReaderT Target Action a': --- * the empty computation returns the identity element of the underlying type +-- | If values of type @a@ form a 'Monoid' then we can also derive a 'Monoid' +-- instance for values of type @'ReaderT' 'Target' 'Action' a@: +-- +-- * the empty computation is the identity element of the underlying type -- * two computations can be combined by combining their results instance Monoid a => Monoid (ReaderT Target Action a) where mempty = return mempty mappend = liftM2 mappend --- PartialTarget is a partially constructed Target with fields Stage and --- Package only. PartialTarget's are used for generating build rules. +-- A partially constructed Target with fields 'Stage' and 'Package' only. +-- 'PartialTarget's are used for generating build rules. data PartialTarget = PartialTarget Stage Package deriving (Eq, Show) --- Convert PartialTarget to Target assuming that unknown fields won't be used. -fromPartial :: PartialTarget -> Target -fromPartial (PartialTarget s p) = Target +-- | Convert 'PartialTarget' to a 'Target' assuming that unknown fields won't +-- be used. +unsafeFromPartial :: PartialTarget -> Target +unsafeFromPartial (PartialTarget s p) = Target { stage = s, package = p, - builder = error "fromPartial: builder not set", - way = error "fromPartial: way not set", - inputs = error "fromPartial: inputs not set", - outputs = error "fromPartial: outputs not set" + builder = error "unsafeFromPartial: builder not set", + way = error "unsafeFromPartial: way not set", + inputs = error "unsafeFromPartial: inputs not set", + outputs = error "unsafeFromPartial: outputs not set" } --- Construct a full target by augmenting a PartialTarget with missing fields. --- Most targets are built only one way, vanilla, hence we set it by default. -fullTarget :: PartialTarget -> Builder -> [FilePath] -> [FilePath] -> Target +-- | Construct a full 'Target' by augmenting a 'PartialTarget' with missing +-- fields. Most targets are built only one way, 'vanilla', hence it is set by +-- default. Use 'fullTargetWithWay' otherwise. +fullTarget :: + PartialTarget + -> Builder + -> [FilePath] -- ^ Source files + -> [FilePath] -- ^ Produced files + -> Target fullTarget (PartialTarget s p) b srcs fs = Target { stage = s, @@ -66,8 +73,14 @@ fullTarget (PartialTarget s p) b srcs fs = Target outputs = map unifyPath fs } --- Use this function to be explicit about the build way. -fullTargetWithWay :: PartialTarget -> Builder -> Way -> [FilePath] -> [FilePath] -> Target +-- | Like 'fullTarget', but allows an explicit 'Way' parameter. +fullTargetWithWay :: + PartialTarget + -> Builder + -> Way + -> [FilePath] -- ^ Source files + -> [FilePath] -- ^ Produced files + -> Target fullTargetWithWay pt b w srcs fs = (fullTarget pt b srcs fs) { way = w } -- Instances for storing in the Shake database From git at git.haskell.org Fri Oct 27 00:01:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify paths. (56d3256) Message-ID: <20171027000111.89EEC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56d32568e5f290d9c93f11568b63e206caa0b9e1/ghc >--------------------------------------------------------------- commit 56d32568e5f290d9c93f11568b63e206caa0b9e1 Author: Andrey Mokhov Date: Wed Feb 10 11:27:21 2016 +0000 Unify paths. >--------------------------------------------------------------- 56d32568e5f290d9c93f11568b63e206caa0b9e1 src/Oracles/WindowsPath.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index 189c329..3cbf1f1 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -34,7 +34,7 @@ windowsPathOracle :: Rules () windowsPathOracle = do answer <- newCache $ \path -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] - let windowsPath = dropWhileEnd isSpace out + let windowsPath = unifyPath $ dropWhileEnd isSpace out putOracle $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath _ <- addOracle $ \(WindowsPath query) -> answer query From git at git.haskell.org Fri Oct 27 00:01:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve performance of getHsSources. (3122d3a) Message-ID: <20171027000112.9DF713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3122d3a2b9fe8ed79df55edd09b1cb12b1d9cdba/ghc >--------------------------------------------------------------- commit 3122d3a2b9fe8ed79df55edd09b1cb12b1d9cdba Author: Andrey Mokhov Date: Mon Jul 27 02:04:34 2015 +0100 Improve performance of getHsSources. >--------------------------------------------------------------- 3122d3a2b9fe8ed79df55edd09b1cb12b1d9cdba src/Oracles/DependencyList.hs | 3 --- src/Oracles/PackageData.hs | 2 +- src/Package/Base.hs | 60 ------------------------------------------- src/Rules/Actions.hs | 2 +- src/Settings/Util.hs | 32 +++++++++++++++++++++-- src/Util.hs | 7 ++++- 6 files changed, 38 insertions(+), 68 deletions(-) diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs index 76d7eac..0ad9267 100644 --- a/src/Oracles/DependencyList.hs +++ b/src/Oracles/DependencyList.hs @@ -38,6 +38,3 @@ dependencyListOracle = do addOracle $ \(DependencyListKey (file, obj)) -> Map.lookup (unifyPath obj) <$> deps (unifyPath file) return () - -bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) -bimap f g (x, y) = (f x, g y) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index fd30cc3..579312f 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -90,6 +90,6 @@ packageDataOracle = do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> + addOracle $ \(PackageDataKey (file, key)) -> do Map.lookup key <$> pkgData (unifyPath file) return () diff --git a/src/Package/Base.hs b/src/Package/Base.hs index 3e2eb37..1f9d2c8 100644 --- a/src/Package/Base.hs +++ b/src/Package/Base.hs @@ -23,52 +23,6 @@ import Oracles import Settings import qualified System.Directory as S ---pathArgs :: ShowArgs a => String -> FilePath -> a -> Args ---pathArgs key path as = map (\a -> key ++ unifyPath (path a)) <$> args as - --- prefixedPath :: String -> [Settings] -> Settings --- prefixedPath prefix = argPrefix prefix . argConcatPath . sconcat - ---includeGccArgs :: FilePath -> FilePath -> Args ---includeGccArgs path dist = --- let pathDist = path dist --- autogen = pathDist "build/autogen" --- in args [ arg $ "-I" ++ unifyPath autogen --- , pathArgs "-I" path $ IncludeDirs pathDist --- , pathArgs "-I" path $ DepIncludeDirs pathDist ] - - --- includeGccSettings :: Settings --- includeGccSettings = mconcat --- [ prefixedPath "-I" [argBuildPath, argBuildDir, arg "build", arg "autogen"] --- , argPrefix "-I" $ argPaths ... --- , prefixedPath "-I" [argBuildPath, argIncludeDirs ] -- wrong --- , prefixedPath "-I" [argBuildPath, argDepIncludeDirs ]] - --- includeGhcSettings :: Settings --- includeGhcSettings = --- let buildDir = argBuildPath `fence` argSrcDirs --- in arg "-i" `fence` --- mconcat --- [ argPathList "-i" [argBuildPath, argSrcDirs] --- , argPath "-i" buildDir --- , argPath "-I" buildDir --- , argPathList "-i" [buildDir, arg "autogen"] --- , argPathList "-I" [buildDir, arg "autogen"] --- , argPathList "-I" [argBuildPath, argIncludeDirs] --- , arg "-optP-include" -- TODO: Shall we also add -cpp? --- , argPathList "-optP" [buildDir, arg "autogen/cabal_macros.h"] ] - - --- pkgHsSources :: FilePath -> FilePath -> Action [FilePath] --- pkgHsSources path dist = do --- let pathDist = path dist --- autogen = pathDist "build/autogen" --- dirs <- map (path ) <$> args (SrcDirs pathDist) --- findModuleFiles pathDist (autogen:dirs) [".hs", ".lhs"] - --- TODO: look for non-{hs,c} objects too - -- Find Haskell objects we depend on (we don't want to depend on split objects) pkgDepHsObjects :: FilePath -> FilePath -> Way -> Action [FilePath] pkgDepHsObjects path dist way = do @@ -101,20 +55,6 @@ pkgLibHsObjects path dist stage way = do findModuleFiles pathDist [buildDir] [suffix] else do return depObjs --- findModuleFiles :: FilePath -> [FilePath] -> [String] -> Action [FilePath] --- findModuleFiles pathDist directories suffixes = do --- modPaths <- map (replaceEq '.' pathSeparator) <$> args (Modules pathDist) --- fileList <- forM [ dir modPath ++ suffix --- | dir <- directories --- , modPath <- modPaths --- , suffix <- suffixes --- ] $ \file -> do --- let dir = takeDirectory file --- dirExists <- liftIO $ S.doesDirectoryExist dir --- when dirExists $ return $ unifyPath file --- files <- getDirectoryFiles "" fileList --- return $ map unifyPath files - -- The argument list has a limited size on Windows. Since Windows 7 the limit -- is 32768 (theoretically). In practice we use 31000 to leave some breathing -- space for the builder's path & name, auxiliary flags, and other overheads. diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 2730c55..d91cd84 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -50,7 +50,7 @@ interestingInfo builder ss = case builder of Gcc _ -> prefixAndSuffix 0 4 ss GccM _ -> prefixAndSuffix 0 1 ss Ghc _ -> prefixAndSuffix 0 4 ss - GhcM _ -> prefixAndSuffix 1 1 ss + --GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss GhcCabal -> prefixAndSuffix 3 0 ss _ -> ss diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 1e7585e..1901a8c 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -26,6 +26,8 @@ import Oracles.Setting import Oracles.PackageData import Settings.User import Settings.TargetDirectory +import Data.List +import Data.Function -- A single argument. arg :: String -> Args @@ -76,8 +78,34 @@ getHsSources = do path <- getTargetPath pkgPath <- getPackagePath srcDirs <- getPkgDataList SrcDirs - let paths = (path -/- "build/autogen") : map (pkgPath -/-) srcDirs - getSourceFiles paths [".hs", ".lhs"] + modules <- getPkgDataList Modules + let buildPath = path -/- "build" + autogenPath = buildPath -/- "autogen" + dirs = autogenPath : map (pkgPath -/-) srcDirs + decodedMods = sort $ map decodeModule modules + modDirFiles = map (bimap head sort . unzip) + $ groupBy ((==) `on` fst) decodedMods + + result <- lift . fmap concat . forM dirs $ \dir -> do + todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles + forM todo $ \(mDir, mFiles) -> do + let files = [ dir -/- mDir -/- mFile <.> "*hs" | mFile <- mFiles ] + found <- fmap (map unifyPath) $ getDirectoryFiles "" files + return (found, (mDir, map takeBaseName found)) + + let foundSources = concatMap fst result + foundMods = [ (d, f) | (d, fs) <- map snd result, f <- fs ] + leftMods = decodedMods \\ sort foundMods + genSources = map (\(d, f) -> buildPath -/- d -/- f <.> "hs") leftMods + + return $ foundSources ++ genSources + +-- Given a module name extract the directory and file names, e.g.: +-- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +decodeModule :: String -> (FilePath, FilePath) +decodeModule = splitFileName . replaceEq '.' '/' + + -- getSourceFiles paths [".hs", ".lhs"] -- Find all source files in specified paths and with given extensions getSourceFiles :: [FilePath] -> [String] -> Expr [FilePath] diff --git a/src/Util.hs b/src/Util.hs index 7c5f786..fd33e73 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -5,7 +5,8 @@ module Util ( replaceIf, replaceEq, replaceSeparators, unifyPath, (-/-), chunksOfSize, - putColoured, redError, redError_ + putColoured, redError, redError_, + bimap ) where import Data.Char @@ -65,3 +66,7 @@ redError msg = do redError_ :: String -> Action () redError_ = void . redError + +-- Depending on Data.Bifunctor only for this function seems an overkill +bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) +bimap f g (x, y) = (f x, g y) From git at git.haskell.org Fri Oct 27 00:01:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Explain stages (bee9cee) Message-ID: <20171027000114.85FED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bee9ceed2f9e196b1d7adcc02c74246ec8c89f82/ghc >--------------------------------------------------------------- commit bee9ceed2f9e196b1d7adcc02c74246ec8c89f82 Author: David Luposchainsky Date: Wed Jan 6 15:05:37 2016 +0100 Explain stages >--------------------------------------------------------------- bee9ceed2f9e196b1d7adcc02c74246ec8c89f82 src/Stage.hs | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/src/Stage.hs b/src/Stage.hs index 144aa29..2e581c4 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -4,10 +4,27 @@ module Stage (Stage (..), stageString) where import Development.Shake.Classes import GHC.Generics (Generic) --- TODO: explain stages +-- | A stage refers to a certain compiler in GHC's build process. +-- +-- * Stage 0 is the bootstrapping compiler, i.e. the one already installed on +-- the user's system. +-- +-- * Stage 1 is built using the stage 0 compiler, using GHC's source code. +-- The result is a compiler that was built by the bootstrapping compiler, +-- with all the features of the new compiler. +-- +-- * Stage 2 is built using the stage 1 compiler and GHC's source code. The +-- result is a compiler "built by itself", commonly referred to as +-- /bootstrapping/. +-- +-- * Stage 3 uses stage 2 to build from source again. The result should have +-- the same object code as stage 2, which is a good test for the compiler. +-- Since it serves no other purpose than that, the stage 3 build is usually +-- omitted in the build process. data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Show, Eq, Ord, Enum, Generic) +-- | Prettyprint a 'Stage'. stageString :: Stage -> String stageString stage = "stage" ++ show (fromEnum stage) From git at git.haskell.org Fri Oct 27 00:01:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop alwaysRerun from setup rules. (b3e25ee) Message-ID: <20171027000114.EE45D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3e25ee579ad44a35b4cbf243b05728c4f63c5d1/ghc >--------------------------------------------------------------- commit b3e25ee579ad44a35b4cbf243b05728c4f63c5d1 Author: Andrey Mokhov Date: Wed Feb 10 12:42:54 2016 +0000 Drop alwaysRerun from setup rules. >--------------------------------------------------------------- b3e25ee579ad44a35b4cbf243b05728c4f63c5d1 src/Rules/Setup.hs | 27 ++++++++++++++++++--------- 1 file changed, 18 insertions(+), 9 deletions(-) diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index c99c8be..a17fb59 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -9,13 +9,10 @@ import Rules.Generators.GhcAutoconfH setupRules :: Rules () setupRules = do - -- We always rerun the configure script in this mode, because the flags - -- passed to it can affect the contents of system.config file. [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do - alwaysRerun + need [ settings <.> "in", cfgH <.> "in", "configure" ] case cmdSetup of RunSetup configureArgs -> do - need [ settings <.> "in", cfgH <.> "in" ] -- We cannot use windowsHost here due to a cyclic dependency when (System.Info.os == "mingw32") $ do putBuild "| Checking for Windows tarballs..." @@ -24,11 +21,23 @@ setupRules = do , "download" , System.Info.arch ] runConfigure "." [] [configureArgs] - SkipSetup -> unlessM (doesFileExist cfg) $ - putError $ "Configuration file " ++ cfg ++ " is missing.\n" - ++ "Run the configure script either manually or via the " + SkipSetup -> do + cfgExists <- doesFileExist cfg + if cfgExists + then putError $ "Configuration file " ++ cfg ++ " is out-of-date." + ++ "\nRerun the configure script either manually or via the " + ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." + else putError $ "Configuration file " ++ cfg ++ " is missing." + ++ "\nRun the configure script either manually or via the " ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." ["configure", configH <.> "in"] &%> \_ -> do - putBuild "| Running boot..." - quietly $ cmd (EchoStdout False) "perl boot" + need ["configure.ac"] + case cmdSetup of + RunSetup _ -> do + putBuild "| Running boot..." + quietly $ cmd (EchoStdout False) "perl boot" + SkipSetup -> do + putError $ "The configure script is out-of-date." + ++ "\nRun the boot script either manually or via the " + ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." From git at git.haskell.org Fri Oct 27 00:01:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (4364462) Message-ID: <20171027000116.4D2433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/436446265ec493014808d9b19dc1f0883bb3e9a8/ghc >--------------------------------------------------------------- commit 436446265ec493014808d9b19dc1f0883bb3e9a8 Author: Andrey Mokhov Date: Tue Jul 28 02:24:04 2015 +0100 Clean up. >--------------------------------------------------------------- 436446265ec493014808d9b19dc1f0883bb3e9a8 src/Oracles/PackageData.hs | 2 +- src/Rules/Actions.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 579312f..fd30cc3 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -90,6 +90,6 @@ packageDataOracle = do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> do + addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> pkgData (unifyPath file) return () diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d91cd84..2730c55 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -50,7 +50,7 @@ interestingInfo builder ss = case builder of Gcc _ -> prefixAndSuffix 0 4 ss GccM _ -> prefixAndSuffix 0 1 ss Ghc _ -> prefixAndSuffix 0 4 ss - --GhcM _ -> prefixAndSuffix 1 1 ss + GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss GhcCabal -> prefixAndSuffix 3 0 ss _ -> ss From git at git.haskell.org Fri Oct 27 00:01:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add cabal configure to CI (5f4a8f6) Message-ID: <20171027000119.148AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f4a8f61707469c736f79b8da372e5ef4beb081a/ghc >--------------------------------------------------------------- commit 5f4a8f61707469c736f79b8da372e5ef4beb081a Author: David Luposchainsky Date: Wed Jan 6 15:39:33 2016 +0100 Add cabal configure to CI >--------------------------------------------------------------- 5f4a8f61707469c736f79b8da372e5ef4beb081a .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index a28a979..6413818 100644 --- a/.travis.yml +++ b/.travis.yml @@ -50,6 +50,7 @@ install: - ( cd ghc/shake-build && git reset --hard HEAD ) - ( cd ghc/shake-build && cabal install --only-dependencies ) + - ( cd ghc/shake-build && cabal configure ) - ( cd ghc && ./boot ) - ( cd ghc && ./configure ) From git at git.haskell.org Fri Oct 27 00:01:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop support for old configure.ac. (0b0996b) Message-ID: <20171027000119.AFD0B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b0996b12437a70eeeac0739b493ed505b2c8b89/ghc >--------------------------------------------------------------- commit 0b0996b12437a70eeeac0739b493ed505b2c8b89 Author: Andrey Mokhov Date: Wed Feb 10 12:45:40 2016 +0000 Drop support for old configure.ac. >--------------------------------------------------------------- 0b0996b12437a70eeeac0739b493ed505b2c8b89 src/Rules/Actions.hs | 16 +++------------- 1 file changed, 3 insertions(+), 13 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d81b838..f8f4925 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -6,7 +6,6 @@ module Rules.Actions ( ) where import qualified System.Directory as IO -import System.Console.ANSI import Base import CmdLineFlag @@ -127,20 +126,11 @@ runMakeWithVerbosity :: Bool -> FilePath -> [String] -> Action () runMakeWithVerbosity verbose dir args = do need [dir -/- "Makefile"] path <- builderPath Make - - -- FIXME: temporary safety net for those who are not on GHC HEAD, see #167 - -- TODO: add need [path] once lookupInPath is enabled on Windows - fixPath <- if path == "@MakeCmd@" <.> exe - then do - putColoured Red $ "You are behind GHC HEAD, make autodetection is disabled." - return "make" - else return path - let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run " ++ fixPath ++ note ++ " in " ++ dir ++ "..." + putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." if verbose - then cmd Shell fixPath ["-C", dir] args - else quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args + then cmd Shell path ["-C", dir] args + else quietly $ cmd Shell (EchoStdout False) path ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do From git at git.haskell.org Fri Oct 27 00:01:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor findModuleFiles and add comments. (0be1b62) Message-ID: <20171027000120.90E923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0be1b62e3ca05ce9e4c3da40e972aab9e42f991f/ghc >--------------------------------------------------------------- commit 0be1b62e3ca05ce9e4c3da40e972aab9e42f991f Author: Andrey Mokhov Date: Sat Aug 1 00:19:04 2015 +0100 Refactor findModuleFiles and add comments. >--------------------------------------------------------------- 0be1b62e3ca05ce9e4c3da40e972aab9e42f991f src/Settings/Util.hs | 62 ++++++++++++++++++++++++++++------------------------ src/Util.hs | 11 +++++++++- 2 files changed, 44 insertions(+), 29 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 1901a8c..3ea13e3 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -5,7 +5,7 @@ module Settings.Util ( getFlag, getSetting, getSettingList, getPkgData, getPkgDataList, getPackagePath, getTargetPath, getTargetDirectory, - getHsSources, getSourceFiles, + getHsSources, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -78,44 +78,50 @@ getHsSources = do path <- getTargetPath pkgPath <- getPackagePath srcDirs <- getPkgDataList SrcDirs + + let buildPath = path -/- "build" + dirs = (buildPath -/- "autogen") : map (pkgPath -/-) srcDirs + + (foundSources, missingSources) <- findModuleFiles dirs "*hs" + + -- Generated source files will live in buildPath and have extension "hs" + let generatedSources = map (\f -> buildPath -/- f <.> "hs") missingSources + + return $ foundSources ++ generatedSources + +-- Given a module name extract the directory and file names, e.g.: +-- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +decodeModule :: String -> (FilePath, String) +decodeModule = splitFileName . replaceEq '.' '/' + +-- findModuleFiles scans a list of given directories and finds files matching a +-- given extension pattern (e.g., "*hs") that correspond to modules of the +-- currently built package. Missing module files are returned in a separate +-- list. The returned pair contains the following: +-- * a list of found module files, with paths being relative to one of given +-- directories, e.g. "codeGen/CodeGen/Platform.hs" for the compiler package. +-- * a list of module files that have not been found, with paths being relative +-- to the module directory, e.g. "CodeGen/Platform", and with no extension. +findModuleFiles :: [FilePath] -> FilePattern -> Expr ([FilePath], [FilePath]) +findModuleFiles dirs ext = do modules <- getPkgDataList Modules - let buildPath = path -/- "build" - autogenPath = buildPath -/- "autogen" - dirs = autogenPath : map (pkgPath -/-) srcDirs - decodedMods = sort $ map decodeModule modules + let decodedMods = sort . map decodeModule $ modules modDirFiles = map (bimap head sort . unzip) - $ groupBy ((==) `on` fst) decodedMods + . groupBy ((==) `on` fst) $ decodedMods result <- lift . fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do - let files = [ dir -/- mDir -/- mFile <.> "*hs" | mFile <- mFiles ] + let files = [ dir -/- mDir -/- mFile <.> ext | mFile <- mFiles ] found <- fmap (map unifyPath) $ getDirectoryFiles "" files return (found, (mDir, map takeBaseName found)) - let foundSources = concatMap fst result + let foundFiles = concatMap fst result foundMods = [ (d, f) | (d, fs) <- map snd result, f <- fs ] - leftMods = decodedMods \\ sort foundMods - genSources = map (\(d, f) -> buildPath -/- d -/- f <.> "hs") leftMods - - return $ foundSources ++ genSources - --- Given a module name extract the directory and file names, e.g.: --- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") -decodeModule :: String -> (FilePath, FilePath) -decodeModule = splitFileName . replaceEq '.' '/' + missingMods = decodedMods `minusOrd` sort foundMods + missingFiles = map (uncurry (-/-)) missingMods - -- getSourceFiles paths [".hs", ".lhs"] - --- Find all source files in specified paths and with given extensions -getSourceFiles :: [FilePath] -> [String] -> Expr [FilePath] -getSourceFiles paths exts = do - modules <- getPkgDataList Modules - let modPaths = map (replaceEq '.' '/') modules - candidates = [ p -/- m ++ e | p <- paths, m <- modPaths, e <- exts ] - files <- lift $ filterM (doesDirectoryExist . takeDirectory) candidates - result <- lift $ getDirectoryFiles "" files - return $ map unifyPath result + return (foundFiles, missingFiles) -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal appendCcArgs :: [String] -> Args diff --git a/src/Util.hs b/src/Util.hs index fd33e73..31c0e6a 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -6,7 +6,7 @@ module Util ( unifyPath, (-/-), chunksOfSize, putColoured, redError, redError_, - bimap + bimap, minusOrd ) where import Data.Char @@ -70,3 +70,12 @@ redError_ = void . redError -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) + +-- Depending on Data.List.Ordered only for this function seems an overkill +minusOrd :: Ord a => [a] -> [a] -> [a] +minusOrd [] _ = [] +minusOrd xs [] = xs +minusOrd (x:xs) (y:ys) = case compare x y of + LT -> x : minusOrd xs (y:ys) + EQ -> minusOrd xs ys + GT -> minusOrd (x:xs) ys From git at git.haskell.org Fri Oct 27 00:01:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddock build to CI (db5e646) Message-ID: <20171027000123.1C1173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db5e646e6fedd351caeed52ecdb8ce4946eb4613/ghc >--------------------------------------------------------------- commit db5e646e6fedd351caeed52ecdb8ce4946eb4613 Author: David Luposchainsky Date: Wed Jan 6 15:01:20 2016 +0100 Add Haddock build to CI >--------------------------------------------------------------- db5e646e6fedd351caeed52ecdb8ce4946eb4613 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 4cc0396..a28a979 100644 --- a/.travis.yml +++ b/.travis.yml @@ -55,6 +55,7 @@ install: - ( cd ghc && ./configure ) script: + - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh -j --no-progress $TARGET cache: From git at git.haskell.org Fri Oct 27 00:01:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't fail if configuration file is out-of-date. (d17c1f5) Message-ID: <20171027000123.C29323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d17c1f538b14b86405bb0be4f3fc4100a2ec8bec/ghc >--------------------------------------------------------------- commit d17c1f538b14b86405bb0be4f3fc4100a2ec8bec Author: Andrey Mokhov Date: Wed Feb 10 13:39:50 2016 +0000 Don't fail if configuration file is out-of-date. >--------------------------------------------------------------- d17c1f538b14b86405bb0be4f3fc4100a2ec8bec src/Rules/Setup.hs | 13 ++++--------- 1 file changed, 4 insertions(+), 9 deletions(-) diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index a17fb59..e0cd729 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -21,13 +21,8 @@ setupRules = do , "download" , System.Info.arch ] runConfigure "." [] [configureArgs] - SkipSetup -> do - cfgExists <- doesFileExist cfg - if cfgExists - then putError $ "Configuration file " ++ cfg ++ " is out-of-date." - ++ "\nRerun the configure script either manually or via the " - ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." - else putError $ "Configuration file " ++ cfg ++ " is missing." + SkipSetup -> unlessM (doesFileExist cfg) $ + putError $ "Configuration file " ++ cfg ++ " is missing." ++ "\nRun the configure script either manually or via the " ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." @@ -37,7 +32,7 @@ setupRules = do RunSetup _ -> do putBuild "| Running boot..." quietly $ cmd (EchoStdout False) "perl boot" - SkipSetup -> do - putError $ "The configure script is out-of-date." + SkipSetup -> unlessM (doesFileExist "configure") $ + putError $ "The configure script is missing." ++ "\nRun the boot script either manually or via the " ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." From git at git.haskell.org Fri Oct 27 00:01:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up and optimise performance. (7a936b6) Message-ID: <20171027000124.3714D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7a936b6313920818057e807b6898390f7c7df2f8/ghc >--------------------------------------------------------------- commit 7a936b6313920818057e807b6898390f7c7df2f8 Author: Andrey Mokhov Date: Sat Aug 1 12:02:45 2015 +0100 Clean up and optimise performance. >--------------------------------------------------------------- 7a936b6313920818057e807b6898390f7c7df2f8 src/Oracles/DependencyList.hs | 12 ++++++------ src/Settings/Util.hs | 19 +++++++++++-------- src/Util.hs | 14 ++++++++++++-- 3 files changed, 29 insertions(+), 16 deletions(-) diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs index 0ad9267..1ffc46d 100644 --- a/src/Oracles/DependencyList.hs +++ b/src/Oracles/DependencyList.hs @@ -21,7 +21,7 @@ newtype DependencyListKey = DependencyListKey (FilePath, FilePath) dependencyList :: FilePath -> FilePath -> Action [FilePath] dependencyList depFile objFile = do res <- askOracle $ DependencyListKey (depFile, objFile) - return $ fromMaybe [] res + return . fromMaybe [] $ res -- Oracle for 'path/dist/*.deps' files dependencyListOracle :: Rules () @@ -30,11 +30,11 @@ dependencyListOracle = do need [file] putOracle $ "Reading " ++ file ++ "..." contents <- parseMakefile <$> (liftIO $ readFile file) - return $ Map.fromList - $ map (bimap unifyPath (map unifyPath)) - $ map (bimap head concat . unzip) - $ groupBy ((==) `on` fst) - $ sortBy (compare `on` fst) contents + return . Map.fromList + . map (bimap unifyPath (map unifyPath)) + . map (bimap head concat . unzip) + . groupBy ((==) `on` fst) + . sortBy (compare `on` fst) $ contents addOracle $ \(DependencyListKey (file, obj)) -> Map.lookup (unifyPath obj) <$> deps (unifyPath file) return () diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 3ea13e3..a9aabba 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -84,7 +84,7 @@ getHsSources = do (foundSources, missingSources) <- findModuleFiles dirs "*hs" - -- Generated source files will live in buildPath and have extension "hs" + -- Generated source files live in buildPath and have extension "hs" let generatedSources = map (\f -> buildPath -/- f <.> "hs") missingSources return $ foundSources ++ generatedSources @@ -103,18 +103,21 @@ decodeModule = splitFileName . replaceEq '.' '/' -- * a list of module files that have not been found, with paths being relative -- to the module directory, e.g. "CodeGen/Platform", and with no extension. findModuleFiles :: [FilePath] -> FilePattern -> Expr ([FilePath], [FilePath]) -findModuleFiles dirs ext = do +findModuleFiles dirs extension = do modules <- getPkgDataList Modules - let decodedMods = sort . map decodeModule $ modules - modDirFiles = map (bimap head sort . unzip) - . groupBy ((==) `on` fst) $ decodedMods + let decodedMods = sort . map decodeModule $ modules + modDirFiles = map (bimap head sort . unzip) + . groupBy ((==) `on` fst) $ decodedMods + matchExtension = (?==) ("*" <.> extension) result <- lift . fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do - let files = [ dir -/- mDir -/- mFile <.> ext | mFile <- mFiles ] - found <- fmap (map unifyPath) $ getDirectoryFiles "" files - return (found, (mDir, map takeBaseName found)) + let fullDir = dir -/- mDir + files <- fmap (filter matchExtension) $ getDirectoryContents fullDir + let cmp fe f = compare (dropExtension fe) f + found = intersectOrd cmp files mFiles + return (map (fullDir -/-) found, (mDir, map dropExtension found)) let foundFiles = concatMap fst result foundMods = [ (d, f) | (d, fs) <- map snd result, f <- fs ] diff --git a/src/Util.hs b/src/Util.hs index 31c0e6a..1c43801 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -6,7 +6,7 @@ module Util ( unifyPath, (-/-), chunksOfSize, putColoured, redError, redError_, - bimap, minusOrd + bimap, minusOrd, intersectOrd ) where import Data.Char @@ -71,7 +71,7 @@ redError_ = void . redError bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) --- Depending on Data.List.Ordered only for this function seems an overkill +-- Depending on Data.List.Ordered only for these two functions seems an overkill minusOrd :: Ord a => [a] -> [a] -> [a] minusOrd [] _ = [] minusOrd xs [] = xs @@ -79,3 +79,13 @@ minusOrd (x:xs) (y:ys) = case compare x y of LT -> x : minusOrd xs (y:ys) EQ -> minusOrd xs ys GT -> minusOrd (x:xs) ys + +intersectOrd :: (a -> b -> Ordering) -> [a] -> [b] -> [a] +intersectOrd cmp = loop + where + loop [] _ = [] + loop _ [] = [] + loop (x:xs) (y:ys) = case cmp x y of + LT -> loop xs (y:ys) + EQ -> x : loop xs ys + GT -> loop (x:xs) ys From git at git.haskell.org Fri Oct 27 00:01:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Haddocks for Way.hs (997ce25) Message-ID: <20171027000126.C584F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/997ce259b41f6e60b7d4906292b920a00c799bfd/ghc >--------------------------------------------------------------- commit 997ce259b41f6e60b7d4906292b920a00c799bfd Author: David Luposchainsky Date: Wed Jan 6 15:31:55 2016 +0100 Haddocks for Way.hs >--------------------------------------------------------------- 997ce259b41f6e60b7d4906292b920a00c799bfd src/Rules.hs | 2 +- src/Stage.hs | 2 +- src/Way.hs | 37 +++++++++++++++++++++++++++++-------- 3 files changed, 31 insertions(+), 10 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index f8b2810..c24b354 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -11,7 +11,7 @@ import Rules.Resources import Settings allStages :: [Stage] -allStages = [Stage0 ..] +allStages = [minBound ..] -- TODO: not all program targets should be needed explicitly -- | 'need' all top-level build targets diff --git a/src/Stage.hs b/src/Stage.hs index 2e581c4..af6d2df 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -22,7 +22,7 @@ import GHC.Generics (Generic) -- Since it serves no other purpose than that, the stage 3 build is usually -- omitted in the build process. data Stage = Stage0 | Stage1 | Stage2 | Stage3 - deriving (Show, Eq, Ord, Enum, Generic) + deriving (Show, Eq, Ord, Enum, Generic, Bounded) -- | Prettyprint a 'Stage'. stageString :: Stage -> String diff --git a/src/Way.hs b/src/Way.hs index 28d1365..9f7f12a 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -19,6 +19,8 @@ import Oracles -- Note: order of constructors is important for compatibility with the old build -- system, e.g. we want "thr_p", not "p_thr" (see instance Show Way). +-- | A 'WayUnit' is a single way of building source code, for example with +-- profiling enabled, or dynamically linked. data WayUnit = Threaded | Debug | Profiling @@ -26,7 +28,7 @@ data WayUnit = Threaded | Dynamic | Parallel | GranSim - deriving (Eq, Enum) + deriving (Eq, Enum, Bounded) -- TODO: get rid of non-derived Show instances instance Show WayUnit where @@ -40,16 +42,22 @@ instance Show WayUnit where GranSim -> "gm" instance Read WayUnit where - readsPrec _ s = [(unit, "") | unit <- [Threaded ..], show unit == s] + readsPrec _ s = [(unit, "") | unit <- [minBound ..], show unit == s] +-- | Collection of 'WayUnit's that stands for the different ways source code +-- is to be built. newtype Way = Way IntSet +-- | Construct a 'Way' from multiple 'WayUnit's. Inverse of 'wayToUnits'. wayFromUnits :: [WayUnit] -> Way wayFromUnits = Way . Set.fromList . map fromEnum +-- | Split a 'Way' into its 'WayUnit' building blocks. +-- Inverse of 'wayFromUnits'. wayToUnits :: Way -> [WayUnit] wayToUnits (Way set) = map toEnum . Set.elems $ set +-- | Check whether a 'Way' contains a certain 'WayUnit'. wayUnit :: WayUnit -> Way -> Bool wayUnit unit (Way set) = fromEnum unit `Set.member` set @@ -72,11 +80,23 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b -vanilla, profiling, logging, parallel, granSim :: Way +-- | Build with no 'WayUnit's at all. +vanilla :: Way vanilla = wayFromUnits [] + +-- | Build with profiling. +profiling :: Way profiling = wayFromUnits [Profiling] + +-- | Build with logging. +logging :: Way logging = wayFromUnits [Logging] + +-- | Build in parallel. +parallel :: Way parallel = wayFromUnits [Parallel] + +granSim :: Way granSim = wayFromUnits [GranSim] -- RTS only ways @@ -135,11 +155,12 @@ libsuf way @ (Way set) = -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension --- Detect way from a given filename. Returns Nothing if there is no match: --- * safeDetectWay "foo/bar.hi" == Just vanilla --- * safeDetectWay "baz.thr_p_o" == Just threadedProfiling --- * safeDetectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") --- * safeDetectWay "xru.p_ghc7.11.20141222.so" == Just profiling +-- | Detect way from a given 'FilePath'. Returns 'Nothing' if there is no match. +-- +-- * @'safeDetectWay' "foo/bar.hi" '==' 'Just' vanilla@ +-- * @'safeDetectWay' "baz.thr_p_o" '==' 'Just' threadedProfiling@ +-- * @'safeDetectWay' "qwe.ph_i" '==' 'Nothing' (expected "qwe.p_hi")@ +-- * @'safeDetectWay' "xru.p_ghc7.11.123.so" '==' 'Just' profiling@ safeDetectWay :: FilePath -> Maybe Way safeDetectWay file = case reads prefix of [(way, "")] -> Just way From git at git.haskell.org Fri Oct 27 00:01:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting, drop old comments. (0123303) Message-ID: <20171027000127.DDCD33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/01233034d1790dd831b59e0233e48cebaa8a4579/ghc >--------------------------------------------------------------- commit 01233034d1790dd831b59e0233e48cebaa8a4579 Author: Andrey Mokhov Date: Wed Feb 10 16:55:50 2016 +0000 Fix formatting, drop old comments. >--------------------------------------------------------------- 01233034d1790dd831b59e0233e48cebaa8a4579 src/Rules/Libffi.hs | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 99922d0..f1837c4 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -72,15 +72,14 @@ libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - ffiHeaderDir <- setting FfiIncludeDir useSystemFfi <- flag UseSystemFfi if useSystemFfi then do - putBuild "| System supplied FFI library will be used" - forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = ffiHeaderDir -/- file - copyFile src (rtsBuildPath -/- file) - putSuccess $ "| Successfully copied system supplied FFI library header files" + ffiIncludeDir <- setting FfiIncludeDir + putBuild "| System supplied FFI library will be used" + forM_ ["ffi.h", "ffitarget.h"] $ \file -> + copyFile (ffiIncludeDir -/- file) (rtsBuildPath -/- file) + putSuccess $ "| Successfully copied system FFI library header files" else do removeDirectory libffiBuild createDirectory $ buildRootPath -/- stageString Stage0 @@ -94,15 +93,16 @@ libffiRules = do let libname = dropExtension . dropExtension . takeFileName $ head tarballs removeDirectory (buildRootPath -/- libname) + -- TODO: Simplify. actionFinally (do - build $ fullTarget libffiTarget Tar tarballs [buildRootPath] - moveDirectory (buildRootPath -/- libname) libffiBuild) $ - removeFiles buildRootPath [libname "*"] + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile forM_ ["config.guess", "config.sub"] $ \file -> - copyFile file (libffiBuild -/- file) + copyFile file (libffiBuild -/- file) envs <- configureEnvironment args <- configureArguments @@ -111,17 +111,11 @@ libffiRules = do runMake libffiBuild ["MAKEFLAGS="] runMake libffiBuild ["MAKEFLAGS=", "install"] + let ffiHDir = libffiBuild -/- "inst/lib" -/- libname -/- "include" forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file - copyFile src (rtsBuildPath -/- file) + copyFile (ffiHDir -/- file) (rtsBuildPath -/- file) libffiName <- rtsLibffiLibraryName copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") putSuccess $ "| Successfully built custom library 'libffi'" - --- chmod +x libffi/ln --- # wc on OS X has spaces in its output, which libffi's Makefile --- # doesn't expect, so we tweak it to sed them out --- mv libffi/build/Makefile libffi/build/Makefile.orig --- sed "s#wc -w#wc -w | sed 's/ //g'#" < libffi/build/Makefile.orig > libffi/build/Makefile From git at git.haskell.org Fri Oct 27 00:01:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Limit parallelism of ghc-cabal. (4e96a03) Message-ID: <20171027000128.35B133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e96a03842279f4822ca2b50a7eed7993a3e815a/ghc >--------------------------------------------------------------- commit 4e96a03842279f4822ca2b50a7eed7993a3e815a Author: Andrey Mokhov Date: Sat Aug 1 14:14:42 2015 +0100 Limit parallelism of ghc-cabal. >--------------------------------------------------------------- 4e96a03842279f4822ca2b50a7eed7993a3e815a src/Rules/Data.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index d60dbfa..1114c88 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -37,7 +37,8 @@ buildPackageData target = do -- GhcCabal may run the configure script, so we depend on it -- We don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - build $ fullTarget target [cabal] GhcCabal files + buildWithResources [(ghcPkg, 1)] $ -- GhcCabal calls ghc-pkg too + fullTarget target [cabal] GhcCabal files whenM (interpretExpr target registerPackage) . buildWithResources [(ghcPkg, 1)] $ fullTarget target [cabal] (GhcPkg stage) files From git at git.haskell.org Fri Oct 27 00:01:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix type error (ffc151c) Message-ID: <20171027000131.2167F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffc151c004163822f9e5d131b9556b0c42a3be44/ghc >--------------------------------------------------------------- commit ffc151c004163822f9e5d131b9556b0c42a3be44 Author: David Luposchainsky Date: Wed Jan 6 15:35:22 2016 +0100 Fix type error >--------------------------------------------------------------- ffc151c004163822f9e5d131b9556b0c42a3be44 src/Rules.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules.hs b/src/Rules.hs index c24b354..fe8242b 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -35,6 +35,6 @@ targetsForStage stage = do packageRules :: Rules () packageRules = do resources <- resourceRules - for allStages $ \stage -> + for_ allStages $ \stage -> for_ knownPackages $ \pkg -> buildPackage resources $ PartialTarget stage pkg From git at git.haskell.org Fri Oct 27 00:01:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use fine-grain dependencies in buildPackageDependencies. (4aabd6f) Message-ID: <20171027000132.96C4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4aabd6f2c6818c237b569a4d807e1a29ad72f0f0/ghc >--------------------------------------------------------------- commit 4aabd6f2c6818c237b569a4d807e1a29ad72f0f0 Author: Andrey Mokhov Date: Sat Aug 1 14:16:12 2015 +0100 Use fine-grain dependencies in buildPackageDependencies. >--------------------------------------------------------------- 4aabd6f2c6818c237b569a4d807e1a29ad72f0f0 src/Rules/Dependencies.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 251a233..656e853 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -17,17 +17,17 @@ buildPackageDependencies target = pkg = Target.package target path = targetPath stage pkg buildPath = path -/- "build" + dropBuild = (pkgPath pkg ++) . drop (length buildPath) in do - (buildPath -/- "haskell.deps") %> \file -> do - srcs <- interpretExpr target getHsSources - build $ fullTarget target srcs (GhcM stage) [file] + (buildPath "*.c.deps") %> \depFile -> do + let srcFile = dropBuild . dropExtension $ depFile + build $ fullTarget target [srcFile] (GccM stage) [depFile] (buildPath -/- "c.deps") %> \file -> do srcs <- pkgDataList $ CSrcs path - deps <- forM srcs $ \src -> do - let srcFile = pkgPath pkg -/- src - depFile = buildPath -/- takeFileName src <.> "deps" - build $ fullTarget target [srcFile] (GccM stage) [depFile] - liftIO . readFile $ depFile + deps <- forM srcs $ \src -> readFile' $ buildPath -/- src <.> "deps" writeFileChanged file (concat deps) - liftIO $ removeFiles buildPath ["*.c.deps"] + + (buildPath -/- "haskell.deps") %> \file -> do + srcs <- interpretExpr target getHsSources + build $ fullTarget target srcs (GhcM stage) [file] From git at git.haskell.org Fri Oct 27 00:01:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make fixFile more robust. (27317cf) Message-ID: <20171027000132.4A6B43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27317cf1ebcc6e89bd0e42b449cc2059f74673e6/ghc >--------------------------------------------------------------- commit 27317cf1ebcc6e89bd0e42b449cc2059f74673e6 Author: Andrey Mokhov Date: Wed Feb 10 22:51:09 2016 +0000 Make fixFile more robust. See #206. >--------------------------------------------------------------- 27317cf1ebcc6e89bd0e42b449cc2059f74673e6 src/Rules/Actions.hs | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index f8f4925..e815bcf 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -5,7 +5,9 @@ module Rules.Actions ( runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable ) where -import qualified System.Directory as IO +import qualified System.Directory as IO +import qualified System.IO as IO +import qualified Control.Exception.Base as IO import Base import CmdLineFlag @@ -96,9 +98,12 @@ moveDirectory source target = do fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do putBuild $ "| Fix " ++ file - old <- liftIO $ readFile file - let new = f old - length new `seq` liftIO $ writeFile file new + contents <- liftIO $ IO.withFile file IO.ReadMode $ \h -> do + old <- IO.hGetContents h + let new = f old + IO.evaluate $ rnf new + return new + liftIO $ writeFile file contents runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do From git at git.haskell.org Fri Oct 27 00:01:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix bad imports (302c1df) Message-ID: <20171027000134.978E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/302c1dfb07284855bafd93d8a0cfb34bcbb50847/ghc >--------------------------------------------------------------- commit 302c1dfb07284855bafd93d8a0cfb34bcbb50847 Author: David Luposchainsky Date: Wed Jan 6 15:45:34 2016 +0100 Fix bad imports >--------------------------------------------------------------- 302c1dfb07284855bafd93d8a0cfb34bcbb50847 src/Main.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index bacc8f1..b30b38e 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,5 +1,7 @@ module Main (main) where +import Development.Shake + import qualified Base as B import qualified Rules as R import qualified Rules.Cabal as RCabal @@ -24,6 +26,6 @@ main = shakeArgs options rules , ROracle.oracleRules , R.packageRules ] options = shakeOptions - { shakeFiles = shakeFilesPath + { shakeFiles = B.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:01:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of gmpLibNameCache. (d4b6ee5) Message-ID: <20171027000136.414AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd/ghc >--------------------------------------------------------------- commit d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd Author: Andrey Mokhov Date: Wed Feb 10 23:40:49 2016 +0000 Get rid of gmpLibNameCache. Fix #206. >--------------------------------------------------------------- d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd src/Rules/Gmp.hs | 17 +++++------------ src/Settings/Builders/Ghc.hs | 10 +++++----- src/Settings/Paths.hs | 8 ++------ 3 files changed, 12 insertions(+), 23 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index ab25495..3e1acea 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -7,7 +7,6 @@ import Expression import GHC import Oracles.Config.Setting import Rules.Actions -import Settings.Builders.Ghc import Settings.Packages.IntegerGmp import Settings.User @@ -67,7 +66,7 @@ gmpRules :: Rules () gmpRules = do -- TODO: split into multiple rules - [gmpLibraryH, gmpLibNameCache] &%> \_ -> do + gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] liftIO $ removeFiles gmpBuildPath ["//*"] @@ -83,22 +82,16 @@ gmpRules = do createDirectory $ takeDirectory gmpLibraryH -- We don't use system GMP on Windows. TODO: fix? - -- TODO: we do not track "config.mk" and "integer-gmp.buildinfo", see #173 - windows <- windowsHost + -- TODO: we don't track "config.mk" & "integer-gmp.buildinfo", see #173 + windows <- windowsHost configMk <- liftIO . readFile $ gmpBase -/- "config.mk" - if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] + if not windows && any (`isInfixOf` configMk) + [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - buildInfo <- liftIO . readFile $ pkgPath integerGmp -/- "integer-gmp.buildinfo" - let prefix = "extra-libraries: " - libs s = case stripPrefix prefix s of - Nothing -> [] - Just value -> words value - writeFileChanged gmpLibNameCache . unlines . concatMap libs $ lines buildInfo else do putBuild "| No GMP library/framework detected; in tree GMP will be built" - writeFileChanged gmpLibNameCache "" -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index b3bca31..c9f8ddc 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,5 +1,5 @@ module Settings.Builders.Ghc ( - ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs, gmpLibNameCache + ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs ) where import Base @@ -23,12 +23,12 @@ ghcBuilderArgs = stagedBuilder Ghc ? do stage <- getStage way <- getWay when (stage > Stage0) . lift $ needTouchy - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output - buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output + let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] + buildHi = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf] buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs gmpLibs <- if stage > Stage0 && buildProg - then lift $ readFileLines gmpLibNameCache -- TODO: use oracles + then words <$> getSetting GmpLibDir else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs @@ -47,7 +47,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] needTouchy :: Action () -needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy ] +needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 20f4721..99a4962 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,7 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibNameCache, - packageDbDirectory, pkgConfFile + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, packageDbDirectory, + pkgConfFile ) where import Base @@ -51,10 +51,6 @@ pkgFile stage pkg prefix suffix = do gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" --- GMP library names extracted from integer-gmp.buildinfo -gmpLibNameCache :: FilePath -gmpLibNameCache = gmpBuildPath -/- "gmp-lib-names" - -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory packageDbDirectory :: Stage -> FilePath From git at git.haskell.org Fri Oct 27 00:01:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to using Distribution package for parsing cabal files. (f1249da) Message-ID: <20171027000136.8361D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f1249daba280044fc478516d00db75689e128333/ghc >--------------------------------------------------------------- commit f1249daba280044fc478516d00db75689e128333 Author: Andrey Mokhov Date: Sat Aug 1 16:57:13 2015 +0100 Switch to using Distribution package for parsing cabal files. >--------------------------------------------------------------- f1249daba280044fc478516d00db75689e128333 src/Settings/GhcCabal.hs | 28 +++++++++++++++------------- 1 file changed, 15 insertions(+), 13 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 2c475ab..a3d43f7 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -16,8 +16,11 @@ import Settings.User import Settings.Ways import Settings.Util import Settings.Packages -import Data.List -import Control.Applicative +import Data.Version +import qualified Distribution.Package as D +import qualified Distribution.PackageDescription as D +import qualified Distribution.Verbosity as D +import qualified Distribution.PackageDescription.Parse as D cabalArgs :: Args cabalArgs = builder GhcCabal ? do @@ -33,7 +36,7 @@ cabalArgs = builder GhcCabal ? do , libraryArgs , with HsColour , configureArgs - , stage0 ? packageConstraints + , packageConstraints , withStaged Gcc , notStage0 ? with Ld , with Ar @@ -92,20 +95,19 @@ bootPackageDbArgs = do dllArgs :: Args dllArgs = arg "" +-- TODO: speed up by caching the result in Shake database? packageConstraints :: Args -packageConstraints = do +packageConstraints = stage0 ? do pkgs <- getPackages constraints <- lift $ forM pkgs $ \pkg -> do - let cabal = pkgPath pkg -/- pkgCabal pkg - prefix = dropExtension (pkgCabal pkg) ++ " == " + let cabal = pkgPath pkg -/- pkgCabal pkg need [cabal] - content <- lines <$> liftIO (readFile cabal) - let vs = filter (("ersion:" `isPrefixOf`) . drop 1) content - case vs of - [v] -> return $ prefix ++ dropWhile (not . isDigit) v - _ -> redError $ "Cannot determine package version in '" - ++ cabal ++ "'." - append $ concatMap (\c -> ["--constraint", c]) $ constraints + description <- liftIO $ D.readPackageDescription D.silent cabal + let identifier = D.package . D.packageDescription $ description + version = showVersion . D.pkgVersion $ identifier + D.PackageName name = D.pkgName $ identifier + return $ name ++ " == " ++ version + append . concatMap (\c -> ["--constraint", c]) $ constraints -- TODO: should be in a different file -- TODO: put all validating options together in one file From git at git.haskell.org Fri Oct 27 00:01:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddocks to GHC.hs (9dd9ae0) Message-ID: <20171027000138.3DB163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dd9ae02b8bae0ead318594555929727960aee6a/ghc >--------------------------------------------------------------- commit 9dd9ae02b8bae0ead318594555929727960aee6a Author: David Luposchainsky Date: Wed Jan 6 15:45:48 2016 +0100 Add Haddocks to GHC.hs >--------------------------------------------------------------- 9dd9ae02b8bae0ead318594555929727960aee6a src/GHC.hs | 23 ++++++++++++----------- 1 file changed, 12 insertions(+), 11 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 6e3a477..3d99e63 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -15,11 +15,11 @@ import Base import Package import Stage --- These are all GHC packages we know about. Build rules will be generated for +-- | These are all GHC packages we know about. Build rules will be generated for -- all of them. However, not all of these packages will be built. For example, --- package 'win32' is built only on Windows. --- Settings/Packages.hs defines default conditions for building each package, --- which can be overridden in Settings/User.hs. +-- package /win32/ is built only on Windows. +-- "Packages" defines default conditions for building each package, which can +-- be overridden in "User". defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes @@ -30,7 +30,7 @@ defaultKnownPackages = , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time , touchy, transformers, unix, win32, xhtml ] --- Package definitions (see Package.hs) +-- Package definitions (see "Package") array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, @@ -95,16 +95,17 @@ xhtml = library "xhtml" -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, -- lndir, mkdirhier, testremove, vagrant --- GHC build results will be placed into target directories with the following --- typical structure: --- * build/ : contains compiled object code --- * doc/ : produced by haddock --- * package-data.mk : contains output of ghc-cabal applied to pkgCabal +-- | GHC build results will be placed into target directories with the +-- following typical structure: + +-- * @build/@ contains compiled object code +-- * @doc/@ is produced by haddock +-- * @package-data.mk@ contains output of ghc-cabal applied to pkgCabal defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage _ = stageString stage -- TODO: simplify, add programInplaceLibPath --- | Returns a relative path to the program executable +-- | The relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) From git at git.haskell.org Fri Oct 27 00:01:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add TODO. (d07b5b2) Message-ID: <20171027000140.A42F43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d07b5b20b922d45967d22a29db3f00f9fd0e4247/ghc >--------------------------------------------------------------- commit d07b5b20b922d45967d22a29db3f00f9fd0e4247 Author: Andrey Mokhov Date: Thu Feb 11 01:17:31 2016 +0000 Add TODO. >--------------------------------------------------------------- d07b5b20b922d45967d22a29db3f00f9fd0e4247 src/Settings/Builders/GhcCabal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 51d0e6b..4a46b84 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -66,6 +66,7 @@ libraryArgs = do else "--disable-shared" ] -- TODO: LD_OPTS? +-- TODO: WARNING: unrecognized options: --with-compiler, --with-gmp-libraries, --with-cc configureArgs :: Args configureArgs = do let conf key = appendSubD $ "--configure-option=" ++ key From git at git.haskell.org Fri Oct 27 00:01:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Base.hs with Shake imports and build paths. (44ce571) Message-ID: <20171027000140.AE3DC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44ce57199610244416d9c003de42dbca1e1beed0/ghc >--------------------------------------------------------------- commit 44ce57199610244416d9c003de42dbca1e1beed0 Author: Andrey Mokhov Date: Sat Aug 1 17:18:52 2015 +0100 Add Base.hs with Shake imports and build paths. >--------------------------------------------------------------- 44ce57199610244416d9c003de42dbca1e1beed0 src/Base.hs | 20 ++++++++++++++++++++ src/Builder.hs | 1 + src/Expression.hs | 2 +- src/Main.hs | 4 ++-- src/Oracles/ArgsHash.hs | 3 +-- src/Oracles/Base.hs | 13 +------------ src/Oracles/DependencyList.hs | 1 + src/Oracles/Flag.hs | 1 + src/Oracles/PackageData.hs | 1 + src/Oracles/Setting.hs | 1 + src/Oracles/WindowsRoot.hs | 1 + src/Package.hs | 2 +- src/Rules.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Config.hs | 6 ++---- src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Oracles.hs | 1 + src/Rules/Package.hs | 2 +- src/Settings/GhcCabal.hs | 2 +- src/Settings/Util.hs | 2 +- src/Stage.hs | 2 +- src/Target.hs | 2 +- src/Util.hs | 4 +--- src/Way.hs | 5 ++--- 25 files changed, 47 insertions(+), 37 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 44ce57199610244416d9c003de42dbca1e1beed0 From git at git.haskell.org Fri Oct 27 00:01:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddocks to Base.hs (5a82579) Message-ID: <20171027000142.1167F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a8257902248c32409835ab47b89c3e1a38be2b1/ghc >--------------------------------------------------------------- commit 5a8257902248c32409835ab47b89c3e1a38be2b1 Author: David Luposchainsky Date: Wed Jan 6 16:00:06 2016 +0100 Add Haddocks to Base.hs >--------------------------------------------------------------- 5a8257902248c32409835ab47b89c3e1a38be2b1 src/Base.hs | 19 ++++++++++++++++--- 1 file changed, 16 insertions(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a116892..05686e0 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -180,7 +180,16 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg --- | Render the given set of lines in a nice box of ASCII +-- | Render the given set of lines in a nice box of ASCII. +-- +-- The minimum width and whether to use Unicode symbols are hardcoded in the +-- function's body. +-- +-- >>> renderBox (words "lorem ipsum") +-- /----------\ +-- | lorem | +-- | ipsum | +-- \----------/ renderBox :: [String] -> String renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) where @@ -215,11 +224,13 @@ renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot] -- +1 for each non-dash (= corner) char dashes = replicate (boxContentWidth + 2) dash --- Depending on Data.Bifunctor only for this function seems an overkill +-- Explicit definition to avoid dependency on Data.Bifunctor +-- | Bifunctor bimap. bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) --- Depending on Data.List.Ordered only for these two functions seems an overkill +-- Explicit definition to avoid dependency on Data.List.Ordered +-- | Difference of two ordered lists. minusOrd :: Ord a => [a] -> [a] -> [a] minusOrd [] _ = [] minusOrd xs [] = xs @@ -228,6 +239,8 @@ minusOrd (x:xs) (y:ys) = case compare x y of EQ -> minusOrd xs ys GT -> minusOrd (x:xs) ys +-- Explicit definition to avoid dependency on Data.List.Ordered +-- | Intersection of two ordered lists by a predicate. intersectOrd :: (a -> b -> Ordering) -> [a] -> [b] -> [a] intersectOrd cmp = loop where From git at git.haskell.org Fri Oct 27 00:01:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on integerGmp configure in gmpRules. (e9106e8) Message-ID: <20171027000144.C63763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e9106e8ddca0a1bc5677a03c682bc26d345826bd/ghc >--------------------------------------------------------------- commit e9106e8ddca0a1bc5677a03c682bc26d345826bd Author: Andrey Mokhov Date: Thu Feb 11 01:18:48 2016 +0000 Depend on integerGmp configure in gmpRules. See #159. >--------------------------------------------------------------- e9106e8ddca0a1bc5677a03c682bc26d345826bd src/Rules/Gmp.hs | 28 ++++++++-------------------- 1 file changed, 8 insertions(+), 20 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 3e1acea..4c7a480 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,7 +1,5 @@ module Rules.Gmp (gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH) where -import qualified System.Directory as IO - import Base import Expression import GHC @@ -9,6 +7,7 @@ import Oracles.Config.Setting import Rules.Actions import Settings.Packages.IntegerGmp import Settings.User +import Settings.Paths gmpBase :: FilePath gmpBase = "libraries/integer-gmp/gmp" @@ -64,27 +63,15 @@ configureIntGmpArguments = do -- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do - -- TODO: split into multiple rules gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - liftIO $ removeFiles gmpBuildPath ["//*"] - - -- TODO: without the optimisation below we configure integerGmp package - -- twice -- think how this can be optimised (shall we solve #18 first?) - -- TODO: this is a hacky optimisation: we do not rerun configure of - -- integerGmp package if we detect the results of the previous run - envs <- configureEnvironment - unlessM (liftIO . IO.doesFileExist $ gmpBase -/- "config.mk") $ do - args <- configureIntGmpArguments - runConfigure (pkgPath integerGmp) envs args - createDirectory $ takeDirectory gmpLibraryH + -- We don't use system GMP on Windows. TODO: fix? - -- TODO: we don't track "config.mk" & "integer-gmp.buildinfo", see #173 windows <- windowsHost - configMk <- liftIO . readFile $ gmpBase -/- "config.mk" + configMk <- readFile' $ gmpBase -/- "config.mk" if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do @@ -111,8 +98,6 @@ gmpRules = do copyFile src patchPath applyPatch gmpBuildPath patch - -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? - let filename = dropExtension . dropExtension . takeFileName $ head tarballs suffix = "-nodoc-patched" unless (suffix `isSuffixOf` filename) $ @@ -121,8 +106,9 @@ gmpRules = do let libName = take (length filename - length suffix) filename libPath = gmpBuildPath -/- libName - args2 <- configureArguments - runConfigure libPath envs args2 + envs <- configureEnvironment + args <- configureArguments + runConfigure libPath envs args runMake libPath ["MAKEFLAGS="] @@ -139,3 +125,5 @@ gmpRules = do putSuccess "| Successfully built custom library 'gmp'" gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] + + gmpBase -/- "config.mk" %> \_ -> need [pkgDataFile Stage1 integerGmp] From git at git.haskell.org Fri Oct 27 00:01:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Cache computation of boot package constraints in a file. (8e9fe8d) Message-ID: <20171027000145.16B033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e9fe8d6f6ddbe681073baf1414403a14fe7c8f0/ghc >--------------------------------------------------------------- commit 8e9fe8d6f6ddbe681073baf1414403a14fe7c8f0 Author: Andrey Mokhov Date: Sat Aug 1 18:23:49 2015 +0100 Cache computation of boot package constraints in a file. >--------------------------------------------------------------- 8e9fe8d6f6ddbe681073baf1414403a14fe7c8f0 src/Base.hs | 5 ++++- src/Main.hs | 1 + src/Rules.hs | 5 ++--- src/Rules/Cabal.hs | 29 +++++++++++++++++++++++++++++ src/Rules/Package.hs | 4 +--- src/Settings/Args.hs | 2 +- src/Settings/GhcCabal.hs | 17 +---------------- 7 files changed, 39 insertions(+), 24 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7cf3a4e..5b022e8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,5 +1,5 @@ module Base ( - shakeFilesPath, configPath, + shakeFilesPath, configPath, bootPackageConstraints, module Development.Shake, module Development.Shake.Util, module Development.Shake.Config, @@ -18,3 +18,6 @@ shakeFilesPath = "_build/" configPath :: FilePath configPath = "shake/cfg/" + +bootPackageConstraints :: FilePath +bootPackageConstraints = shakeFilesPath ++ "boot-package-constraints" diff --git a/src/Main.hs b/src/Main.hs index c7e076a..ffbd7c0 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,6 +3,7 @@ import Rules main = shakeArgs shakeOptions{shakeFiles = shakeFilesPath} $ do oracleRules -- see module Rules.Oracles + cabalRules -- see module Rules.Cabal packageRules -- see module Rules configRules -- see module Rules.Config generateTargets -- see module Rules diff --git a/src/Rules.hs b/src/Rules.hs index 6d153e1..002eda2 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,13 +1,12 @@ module Rules ( - generateTargets, packageRules, oracleRules, - module Rules.Config, - module Rules.Package, + oracleRules, cabalRules, configRules, packageRules, generateTargets ) where import Base import Util import Stage import Expression +import Rules.Cabal import Rules.Config import Rules.Package import Rules.Oracles diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs new file mode 100644 index 0000000..adcb57e --- /dev/null +++ b/src/Rules/Cabal.hs @@ -0,0 +1,29 @@ +module Rules.Cabal (cabalRules) where + +import Base +import Util +import Stage +import Package +import Expression +import Settings.Packages +import Data.List +import Data.Version +import qualified Distribution.Package as D +import qualified Distribution.PackageDescription as D +import qualified Distribution.Verbosity as D +import qualified Distribution.PackageDescription.Parse as D + +cabalRules :: Rules () +cabalRules = + -- Cache boot package constraints (to be used in cabalArgs) + bootPackageConstraints %> \file -> do + pkgs <- interpret (stageTarget Stage0) packages + constraints <- forM (sort pkgs) $ \pkg -> do + let cabal = pkgPath pkg -/- pkgCabal pkg + need [cabal] + descr <- liftIO $ D.readPackageDescription D.silent cabal + let identifier = D.package . D.packageDescription $ descr + version = showVersion . D.pkgVersion $ identifier + D.PackageName name = D.pkgName $ identifier + return $ name ++ " == " ++ version + writeFileChanged file . unlines $ constraints diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index a6365e8..ff64832 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -1,6 +1,4 @@ -module Rules.Package ( - buildPackage - ) where +module Rules.Package (buildPackage) where import Base import Expression diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index be6ac42..d698017 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -2,12 +2,12 @@ module Settings.Args ( args ) where +import Expression import Settings.User import Settings.GhcM import Settings.GccM import Settings.GhcPkg import Settings.GhcCabal -import Expression args :: Args args = defaultArgs <> userArgs diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index 092f97a..315df12 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -15,12 +15,6 @@ import Oracles.Setting import Settings.User import Settings.Ways import Settings.Util -import Settings.Packages -import Data.Version -import qualified Distribution.Package as D -import qualified Distribution.PackageDescription as D -import qualified Distribution.Verbosity as D -import qualified Distribution.PackageDescription.Parse as D cabalArgs :: Args cabalArgs = builder GhcCabal ? do @@ -95,18 +89,9 @@ bootPackageDbArgs = do dllArgs :: Args dllArgs = arg "" --- TODO: speed up by caching the result in Shake database? packageConstraints :: Args packageConstraints = stage0 ? do - pkgs <- getPackages - constraints <- lift $ forM pkgs $ \pkg -> do - let cabal = pkgPath pkg -/- pkgCabal pkg - need [cabal] - description <- liftIO $ D.readPackageDescription D.silent cabal - let identifier = D.package . D.packageDescription $ description - version = showVersion . D.pkgVersion $ identifier - D.PackageName name = D.pkgName $ identifier - return $ name ++ " == " ++ version + constraints <- lift . readFileLines $ bootPackageConstraints append . concatMap (\c -> ["--constraint", c]) $ constraints -- TODO: should be in a different file From git at git.haskell.org Fri Oct 27 00:01:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing Haddock header (6cf7902) Message-ID: <20171027000146.0801A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6cf79029f6b1f6a1014a3be1d75a7360373c35b3/ghc >--------------------------------------------------------------- commit 6cf79029f6b1f6a1014a3be1d75a7360373c35b3 Author: David Luposchainsky Date: Thu Jan 7 18:19:18 2016 +0100 Add missing Haddock header >--------------------------------------------------------------- 6cf79029f6b1f6a1014a3be1d75a7360373c35b3 src/Target.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Target.hs b/src/Target.hs index 152de3d..3992ce2 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -37,7 +37,7 @@ instance Monoid a => Monoid (ReaderT Target Action a) where mempty = return mempty mappend = liftM2 mappend --- A partially constructed Target with fields 'Stage' and 'Package' only. +-- | A partially constructed Target with fields 'Stage' and 'Package' only. -- 'PartialTarget's are used for generating build rules. data PartialTarget = PartialTarget Stage Package deriving (Eq, Show) @@ -83,7 +83,6 @@ fullTargetWithWay :: -> Target fullTargetWithWay pt b w srcs fs = (fullTarget pt b srcs fs) { way = w } --- Instances for storing in the Shake database instance Binary Target instance NFData Target instance Hashable Target From git at git.haskell.org Fri Oct 27 00:01:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop configureIntGmpArguments. (cc10288) Message-ID: <20171027000148.862FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cc102887b32e84005d553c4adbef1ca5f5c43a1a/ghc >--------------------------------------------------------------- commit cc102887b32e84005d553c4adbef1ca5f5c43a1a Author: Andrey Mokhov Date: Thu Feb 11 01:51:10 2016 +0000 Drop configureIntGmpArguments. See #159. >--------------------------------------------------------------- cc102887b32e84005d553c4adbef1ca5f5c43a1a src/Rules/Gmp.hs | 7 ------- 1 file changed, 7 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 4c7a480..9916ad6 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -53,13 +53,6 @@ configureArguments = do , "--host=" ++ hostPlatform , "--build=" ++ buildPlatform] -configureIntGmpArguments :: Action [String] -configureIntGmpArguments = do - includes <- setting GmpIncludeDir - libs <- setting GmpLibDir - return $ map ("--with-gmp-includes=" ++) (words includes) - ++ map ("--with-gmp-libraries=" ++) (words libs) - -- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do From git at git.haskell.org Fri Oct 27 00:01:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Configure packages in dependency order, refactor resources. (49c3bb1) Message-ID: <20171027000148.BBC5D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49c3bb1f7da2677b7ca95ae6db5abee302f2d408/ghc >--------------------------------------------------------------- commit 49c3bb1f7da2677b7ca95ae6db5abee302f2d408 Author: Andrey Mokhov Date: Sun Aug 2 03:28:14 2015 +0100 Configure packages in dependency order, refactor resources. >--------------------------------------------------------------- 49c3bb1f7da2677b7ca95ae6db5abee302f2d408 doc/demo.txt | 5 +++++ src/Base.hs | 6 +++++- src/Main.hs | 1 + src/Oracles/Base.hs | 4 ---- src/Oracles/DependencyList.hs | 1 - src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 33 +++++++++++++++++++++++++++++++++ src/Oracles/WindowsRoot.hs | 1 - src/Rules.hs | 6 ++++-- src/Rules/Actions.hs | 32 ++++++++++++-------------------- src/Rules/Cabal.hs | 40 +++++++++++++++++++++++++++++----------- src/Rules/Data.hs | 29 ++++++++++++++++++++++------- src/Rules/Dependencies.hs | 5 +++-- src/Rules/Oracles.hs | 2 ++ src/Rules/Package.hs | 3 ++- src/Rules/Resources.hs | 20 ++++++++++++++++++++ src/Util.hs | 11 ++++++++++- 17 files changed, 148 insertions(+), 52 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 49c3bb1f7da2677b7ca95ae6db5abee302f2d408 From git at git.haskell.org Fri Oct 27 00:01:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make imports fully qualified (2ba641b) Message-ID: <20171027000149.DE6643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ba641b3d7d4aa8a84ab96a847208a7e79760496/ghc >--------------------------------------------------------------- commit 2ba641b3d7d4aa8a84ab96a847208a7e79760496 Author: David Luposchainsky Date: Thu Jan 7 19:12:17 2016 +0100 Make imports fully qualified >--------------------------------------------------------------- 2ba641b3d7d4aa8a84ab96a847208a7e79760496 src/Main.hs | 37 ++++++++++++++++++------------------- 1 file changed, 18 insertions(+), 19 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index b30b38e..1710b39 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,30 +2,29 @@ module Main (main) where import Development.Shake -import qualified Base as B -import qualified Rules as R -import qualified Rules.Cabal as RCabal -import qualified Rules.Config as RConfig -import qualified Rules.Copy as RCopy -import qualified Rules.Generate as RGen -import qualified Rules.IntegerGmp as RInt -import qualified Rules.Libffi as RFfi -import qualified Rules.Oracles as ROracle +import qualified Base +import qualified Rules +import qualified Rules.Cabal +import qualified Rules.Config +import qualified Rules.Generate +import qualified Rules.IntegerGmp +import qualified Rules.Libffi +import qualified Rules.Oracles main :: IO () main = shakeArgs options rules where rules = mconcat - [ RCabal.cabalRules - , RConfig.configRules - , RCopy.copyRules - , R.generateTargets - , RGen.generateRules - , RFfi.libffiRules - , RInt.integerGmpRules - , ROracle.oracleRules - , R.packageRules ] + [ Rules.Cabal.cabalRules + , Rules.Config.configRules + , Rules.Generate.copyRules + , Rules.Generate.generateRules + , Rules.generateTargets + , Rules.IntegerGmp.integerGmpRules + , Rules.Libffi.libffiRules + , Rules.Oracles.oracleRules + , Rules.packageRules ] options = shakeOptions - { shakeFiles = B.shakeFilesPath + { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:01:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Extract gmpLibs from integer-gmp.buildinfo directly. (aafa9ad) Message-ID: <20171027000152.83A2F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aafa9add2e1c98059b7ffa6ded7c86195f9967e1/ghc >--------------------------------------------------------------- commit aafa9add2e1c98059b7ffa6ded7c86195f9967e1 Author: Andrey Mokhov Date: Thu Feb 11 01:52:55 2016 +0000 Extract gmpLibs from integer-gmp.buildinfo directly. See #159, #206. >--------------------------------------------------------------- aafa9add2e1c98059b7ffa6ded7c86195f9967e1 src/Settings/Builders/Ghc.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index c9f8ddc..b7aef56 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -12,6 +12,9 @@ import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) import Settings.Builders.Common (cIncludeArgs) +buildInfoPath :: FilePath +buildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" + -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ @@ -28,7 +31,12 @@ ghcBuilderArgs = stagedBuilder Ghc ? do buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs gmpLibs <- if stage > Stage0 && buildProg - then words <$> getSetting GmpLibDir + then do -- TODO: get this data more gracefully + buildInfo <- lift $ readFileLines buildInfoPath + let extract s = case stripPrefix "extra-libraries: " s of + Nothing -> [] + Just value -> words value + return $ concatMap extract buildInfo else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs From git at git.haskell.org Fri Oct 27 00:01:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow more parallelism in buildPackageData. (61a085c) Message-ID: <20171027000152.AAD383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/61a085c0310dbd583855319be36faf017fe2aaf5/ghc >--------------------------------------------------------------- commit 61a085c0310dbd583855319be36faf017fe2aaf5 Author: Andrey Mokhov Date: Sun Aug 2 03:39:17 2015 +0100 Allow more parallelism in buildPackageData. >--------------------------------------------------------------- 61a085c0310dbd583855319be36faf017fe2aaf5 src/Rules/Data.hs | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 752cde7..adc31f1 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -35,15 +35,17 @@ buildPackageData (Resources ghcCabal ghcPkg) target = do -- TODO: Is this needed? Also check out Paths_cpsa.hs. -- , "build" -/- "autogen" -/- ("Paths_" ++ name) <.> "hs" ] &%> \files -> do - -- GhcCabal may run the configure script, so we depend on it - -- We don't know who built the configure script from configure.ac - whenM (doesFileExist $ configure <.> "ac") $ need [configure] - -- We configure packages in the order of their dependencies deps <- packageDeps . dropExtension . pkgCabal $ pkg pkgs <- interpret target packages let depPkgs = concatMap (maybeToList . findPackage pkgs) deps - need $ map (\p -> targetPath stage p -/- "package-data.mk") depPkgs + + -- GhcCabal may run the configure script, so we depend on it + -- We don't know who built the configure script from configure.ac + needConfigure <- doesFileExist $ configure <.> "ac" + + need $ [ configure | needConfigure ] ++ + [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] buildWithResources [(ghcCabal, 1)] $ fullTarget target [cabal] GhcCabal files From git at git.haskell.org Fri Oct 27 00:01:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Document the provenance of the Main functions in the code rather than in comments (c573af0) Message-ID: <20171027000153.A7EE13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c573af06514bb073cb76918343303b9a2c043160/ghc >--------------------------------------------------------------- commit c573af06514bb073cb76918343303b9a2c043160 Author: Neil Mitchell Date: Thu Jan 7 18:30:03 2016 +0000 Document the provenance of the Main functions in the code rather than in comments >--------------------------------------------------------------- c573af06514bb073cb76918343303b9a2c043160 src/Main.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 07f14ea..0fe2ee3 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -9,15 +9,15 @@ import Rules.Oracles main :: IO () main = shakeArgs options $ do - cabalRules -- see Rules.Cabal - configRules -- see Rules.Config - copyRules -- see Rules.Generate - generateTargets -- see Rules - generateRules -- see Rules.Generate - libffiRules -- see Rules.Libffi - integerGmpRules -- see Rules.IntegerGmp - oracleRules -- see Rules.Oracles - packageRules -- see Rules + Rules.Cabal.cabalRules + Rules.Config.configRules + Rules.Generate.copyRules + Rules.generateTargets + Rules.Generate.generateRules + Rules.Libffi.libffiRules + Rules.IntegerGmp.integerGmpRules + Rules.Oracles.oracleRules + Rules.packageRules where options = shakeOptions { shakeFiles = shakeFilesPath From git at git.haskell.org Fri Oct 27 00:01:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track gmpBuildInfoPath explicitly. (2c21908) Message-ID: <20171027000156.7A3F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c219087e3f7ec91e7ab02edbfd3466818402c73/ghc >--------------------------------------------------------------- commit 2c219087e3f7ec91e7ab02edbfd3466818402c73 Author: Andrey Mokhov Date: Thu Feb 11 11:40:42 2016 +0000 Track gmpBuildInfoPath explicitly. See #159. >--------------------------------------------------------------- 2c219087e3f7ec91e7ab02edbfd3466818402c73 src/Rules/Gmp.hs | 4 +++- src/Settings/Builders/Ghc.hs | 5 +---- src/Settings/Paths.hs | 8 ++++++-- 3 files changed, 10 insertions(+), 7 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 9916ad6..b70b840 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -119,4 +119,6 @@ gmpRules = do gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] - gmpBase -/- "config.mk" %> \_ -> need [pkgDataFile Stage1 integerGmp] + -- This causes integerGmp package to be configured, hence creating the files + [gmpBase -/- "config.mk", gmpBuildInfoPath] &%> \_ -> + need [pkgDataFile Stage1 integerGmp] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index b7aef56..51fde7f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -12,9 +12,6 @@ import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) import Settings.Builders.Common (cIncludeArgs) -buildInfoPath :: FilePath -buildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" - -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ @@ -32,7 +29,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do libs <- getPkgDataList DepExtraLibs gmpLibs <- if stage > Stage0 && buildProg then do -- TODO: get this data more gracefully - buildInfo <- lift $ readFileLines buildInfoPath + buildInfo <- lift $ readFileLines gmpBuildInfoPath let extract s = case stripPrefix "extra-libraries: " s of Nothing -> [] Just value -> words value diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 99a4962..96cd3bf 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,7 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, packageDbDirectory, - pkgConfFile + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpBuildInfoPath, + packageDbDirectory, pkgConfFile ) where import Base @@ -51,6 +51,10 @@ pkgFile stage pkg prefix suffix = do gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" +-- We extract system gmp library name from this file +gmpBuildInfoPath :: FilePath +gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" + -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory packageDbDirectory :: Stage -> FilePath From git at git.haskell.org Fri Oct 27 00:01:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify Package. (c677b04) Message-ID: <20171027000156.D44403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c677b049c05d9ebae12c1ae516dc094b622d0d8f/ghc >--------------------------------------------------------------- commit c677b049c05d9ebae12c1ae516dc094b622d0d8f Author: Andrey Mokhov Date: Sun Aug 2 14:17:35 2015 +0100 Simplify Package. >--------------------------------------------------------------- c677b049c05d9ebae12c1ae516dc094b622d0d8f src/Oracles/PackageDeps.hs | 14 ++++++++------ src/Package.hs | 31 +++++++++++++++++++------------ src/Rules/Cabal.hs | 13 ++++++------- src/Rules/Data.hs | 23 ++++++++--------------- src/Settings/Default.hs | 11 +++-------- src/Settings/GhcCabal.hs | 5 +++-- 6 files changed, 47 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c677b049c05d9ebae12c1ae516dc094b622d0d8f From git at git.haskell.org Fri Oct 27 00:01:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:01:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert "Document the provenance of the Main functions in the code rather than in comments" (619f31e) Message-ID: <20171027000157.8EC1B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/619f31ec9fb5d7dac00582129d8722f514a54f3b/ghc >--------------------------------------------------------------- commit 619f31ec9fb5d7dac00582129d8722f514a54f3b Author: Andrey Mokhov Date: Thu Jan 7 20:16:57 2016 +0000 Revert "Document the provenance of the Main functions in the code rather than in comments" This reverts commit c573af06514bb073cb76918343303b9a2c043160. >--------------------------------------------------------------- 619f31ec9fb5d7dac00582129d8722f514a54f3b src/Main.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 0fe2ee3..07f14ea 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -9,15 +9,15 @@ import Rules.Oracles main :: IO () main = shakeArgs options $ do - Rules.Cabal.cabalRules - Rules.Config.configRules - Rules.Generate.copyRules - Rules.generateTargets - Rules.Generate.generateRules - Rules.Libffi.libffiRules - Rules.IntegerGmp.integerGmpRules - Rules.Oracles.oracleRules - Rules.packageRules + cabalRules -- see Rules.Cabal + configRules -- see Rules.Config + copyRules -- see Rules.Generate + generateTargets -- see Rules + generateRules -- see Rules.Generate + libffiRules -- see Rules.Libffi + integerGmpRules -- see Rules.IntegerGmp + oracleRules -- see Rules.Oracles + packageRules -- see Rules where options = shakeOptions { shakeFiles = shakeFilesPath From git at git.haskell.org Fri Oct 27 00:02:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out Context from Target. (e8b62f7) Message-ID: <20171027000200.0DE163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e8b62f7e939cb19194fea1ff0123ae8df1788e61/ghc >--------------------------------------------------------------- commit e8b62f7e939cb19194fea1ff0123ae8df1788e61 Author: Andrey Mokhov Date: Fri Feb 12 01:22:58 2016 +0000 Factor out Context from Target. See #207. >--------------------------------------------------------------- e8b62f7e939cb19194fea1ff0123ae8df1788e61 shaking-up-ghc.cabal | 1 + src/Context.hs | 28 ++++++++++++++++++ src/Expression.hs | 24 +++++++-------- src/Oracles/PackageDb.hs | 4 +-- src/Rules.hs | 12 ++++---- src/Rules/Actions.hs | 22 +++++++------- src/Rules/Cabal.hs | 4 +-- src/Rules/Compile.hs | 32 +++++++++++--------- src/Rules/Data.hs | 67 ++++++++++++++++++++++-------------------- src/Rules/Dependencies.hs | 20 ++++++++----- src/Rules/Documentation.hs | 23 ++++++++------- src/Rules/Generate.hs | 34 +++++++++++---------- src/Rules/Gmp.hs | 15 +++++----- src/Rules/Libffi.hs | 17 ++++++----- src/Rules/Library.hs | 64 +++++++++++++++++++++------------------- src/Rules/Package.hs | 4 +-- src/Rules/Program.hs | 73 ++++++++++++++++++++++++---------------------- src/Rules/Register.hs | 26 ++++++++++------- src/Target.hs | 67 ++++++------------------------------------ src/Test.hs | 13 ++++----- 20 files changed, 278 insertions(+), 272 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 e8b62f7e939cb19194fea1ff0123ae8df1788e61 From git at git.haskell.org Fri Oct 27 00:02:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up rules. (5f8abc4) Message-ID: <20171027000200.B0B163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f8abc4b283d401a7d5b5eb341cab21f799fdf63/ghc >--------------------------------------------------------------- commit 5f8abc4b283d401a7d5b5eb341cab21f799fdf63 Author: Andrey Mokhov Date: Sun Aug 2 14:36:36 2015 +0100 Clean up rules. >--------------------------------------------------------------- 5f8abc4b283d401a7d5b5eb341cab21f799fdf63 src/Rules/Config.hs | 4 ++-- src/Rules/Dependencies.hs | 4 +++- src/Util.hs | 1 - 3 files changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 5946bfb..8d886fa 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -7,10 +7,10 @@ configRules :: Rules () configRules = do configPath -/- "system.config" %> \out -> do need [configPath -/- "system.config.in", "configure"] - putColoured White "Running configure..." + putBuild "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' "configure" %> \out -> do copyFile' (configPath -/- "configure.ac") "configure.ac" - putColoured White $ "Running autoconf..." + putBuild "Running autoconf..." cmd "bash autoconf" -- TODO: get rid of 'bash' diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 92664d2..7fab8cf 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -26,7 +26,9 @@ buildPackageDependencies _ target = (buildPath -/- "c.deps") %> \file -> do srcs <- pkgDataList $ CSrcs path - deps <- forM srcs $ \src -> readFile' $ buildPath -/- src <.> "deps" + let depFiles = [ buildPath -/- src <.> "deps" | src <- srcs ] + need depFiles -- increase parallelism by needing all at once + deps <- mapM readFile' depFiles writeFileChanged file (concat deps) (buildPath -/- "haskell.deps") %> \file -> do diff --git a/src/Util.hs b/src/Util.hs index d8a4db7..70de3ec 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -64,7 +64,6 @@ putOracle = putColoured Blue putBuild :: String -> Action () putBuild = putColoured White - -- A more colourful version of error redError :: String -> Action a redError msg = do From git at git.haskell.org Fri Oct 27 00:02:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #122 from quchen/housekeeping (1690e0f) Message-ID: <20171027000201.9ADDE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1690e0fc7b5168c2a80079dd3c3822a27ded9841/ghc >--------------------------------------------------------------- commit 1690e0fc7b5168c2a80079dd3c3822a27ded9841 Merge: 619f31e 2ba641b Author: Andrey Mokhov Date: Thu Jan 7 20:17:40 2016 +0000 Merge pull request #122 from quchen/housekeeping Add documentation, small refactorings >--------------------------------------------------------------- 1690e0fc7b5168c2a80079dd3c3822a27ded9841 .travis.yml | 2 ++ src/Base.hs | 19 +++++++++++--- src/Expression.hs | 4 +-- src/GHC.hs | 23 +++++++++-------- src/Main.hs | 43 +++++++++++++++++-------------- src/Predicates.hs | 23 ++++++++++++----- src/Rules.hs | 33 ++++++++++++++---------- src/Stage.hs | 21 +++++++++++++-- src/Target.hs | 76 ++++++++++++++++++++++++++++++++----------------------- src/Way.hs | 37 +++++++++++++++++++++------ 10 files changed, 185 insertions(+), 96 deletions(-) From git at git.haskell.org Fri Oct 27 00:02:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (6482e6a) Message-ID: <20171027000203.8D92D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6482e6a90e68c54b7d0202d0ae5d9d600873646d/ghc >--------------------------------------------------------------- commit 6482e6a90e68c54b7d0202d0ae5d9d600873646d Author: Andrey Mokhov Date: Sun Feb 14 21:18:57 2016 +0000 Add comments. >--------------------------------------------------------------- 6482e6a90e68c54b7d0202d0ae5d9d600873646d src/Context.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Context.hs b/src/Context.hs index 9bf8020..b578208 100644 --- a/src/Context.hs +++ b/src/Context.hs @@ -20,6 +20,8 @@ data Context = Context vanillaContext :: Stage -> Package -> Context vanillaContext s p = Context s p vanilla +-- | Partial context with undefined 'Package' field. Useful for 'Packages' +-- expressions that only read the environment and current 'Stage'. stageContext :: Stage -> Context stageContext s = vanillaContext s $ error "stageContext: package not set" From git at git.haskell.org Fri Oct 27 00:02:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename redError(_) to putError(_). (9a6f684) Message-ID: <20171027000208.024FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a6f68428bc2ae6ce0ec2188cb43a48938d8ff87/ghc >--------------------------------------------------------------- commit 9a6f68428bc2ae6ce0ec2188cb43a48938d8ff87 Author: Andrey Mokhov Date: Wed Aug 5 22:29:05 2015 +0100 Rename redError(_) to putError(_). >--------------------------------------------------------------- 9a6f68428bc2ae6ce0ec2188cb43a48938d8ff87 src/Builder.hs | 2 +- src/Oracles/Base.hs | 4 ++-- src/Oracles/Flag.hs | 4 ++-- src/Util.hs | 10 +++++----- 4 files changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index a148fc5..b175fac 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -58,7 +58,7 @@ builderKey builder = case builder of builderPath :: Builder -> Action String builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ - redError $ "\nCannot find path to '" ++ (builderKey builder) + putError $ "\nCannot find path to '" ++ (builderKey builder) ++ "' in configuration files." fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 5c2a252..29ec4e4 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -22,7 +22,7 @@ askConfigWithDefault key defaultAction = do Nothing -> defaultAction askConfig :: String -> Action String -askConfig key = askConfigWithDefault key . redError +askConfig key = askConfigWithDefault key . putError $ "Cannot find key '" ++ key ++ "' in configuration files." -- Oracle for configuration files @@ -31,7 +31,7 @@ configOracle = do let configFile = configPath -/- "system.config" cfg <- newCache $ \() -> do unlessM (doesFileExist $ configFile <.> "in") $ - redError_ $ "\nConfiguration file '" ++ (configFile <.> "in") + putError_ $ "\nConfiguration file '" ++ (configFile <.> "in") ++ "' is missing; unwilling to proceed." need [configFile] putOracle $ "Reading " ++ configFile ++ "..." diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index dfa0920..391ed5e 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -28,9 +28,9 @@ flag f = do SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" GhcUnregisterised -> "ghc-unregisterised" - value <- askConfigWithDefault key . redError + value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." - unless (value == "YES" || value == "NO") . redError + unless (value == "YES" || value == "NO") . putError $ "\nFlag '" ++ key ++ "' is set to '" ++ value ++ "' instead of 'YES' or 'NO'." return $ value == "YES" diff --git a/src/Util.hs b/src/Util.hs index 70de3ec..32b6478 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -4,7 +4,7 @@ module Util ( replaceIf, replaceEq, replaceSeparators, unifyPath, (-/-), chunksOfSize, - putColoured, putOracle, putBuild, redError, redError_, + putColoured, putOracle, putBuild, putError, putError_, bimap, minusOrd, intersectOrd ) where @@ -65,13 +65,13 @@ putBuild :: String -> Action () putBuild = putColoured White -- A more colourful version of error -redError :: String -> Action a -redError msg = do +putError :: String -> Action a +putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg -redError_ :: String -> Action () -redError_ = void . redError +putError_ :: String -> Action () +putError_ = void . putError -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) From git at git.haskell.org Fri Oct 27 00:02:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (comments, whitespace). (cedbb79) Message-ID: <20171027000208.DA8163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cedbb7953afda4348a27cdd0b96af895e84e34e6/ghc >--------------------------------------------------------------- commit cedbb7953afda4348a27cdd0b96af895e84e34e6 Author: Andrey Mokhov Date: Thu Jan 7 22:52:46 2016 +0000 Minor revision (comments, whitespace). [skip ci] >--------------------------------------------------------------- cedbb7953afda4348a27cdd0b96af895e84e34e6 src/Predicates.hs | 4 +++- src/Way.hs | 8 ++++---- 2 files changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index b5ce0cb..497fca5 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -61,6 +61,8 @@ notStage0 = notM stage0 notPackage :: Package -> Predicate notPackage = notM . package --- | TODO: Actually, we don't register compiler in some circumstances -- fix. +-- TODO: Actually, we don't register compiler in some circumstances -- fix. +-- | Do we need to run @ghc-pkg update@ on the currently built package? +-- See "Rules.Data". registerPackage :: Predicate registerPackage = return True diff --git a/src/Way.hs b/src/Way.hs index 9f7f12a..3b1f6c0 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -82,7 +82,7 @@ instance Eq Way where -- | Build with no 'WayUnit's at all. vanilla :: Way -vanilla = wayFromUnits [] +vanilla = wayFromUnits [] -- | Build with profiling. profiling :: Way @@ -90,14 +90,14 @@ profiling = wayFromUnits [Profiling] -- | Build with logging. logging :: Way -logging = wayFromUnits [Logging] +logging = wayFromUnits [Logging] -- | Build in parallel. parallel :: Way -parallel = wayFromUnits [Parallel] +parallel = wayFromUnits [Parallel] granSim :: Way -granSim = wayFromUnits [GranSim] +granSim = wayFromUnits [GranSim] -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? From git at git.haskell.org Fri Oct 27 00:02:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install mkUserGuidePart binary to inplace/bin. (d1ec507) Message-ID: <20171027000211.04C0C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1ec507d7b4d837ee0161f08e9eab0b5630f2797/ghc >--------------------------------------------------------------- commit d1ec507d7b4d837ee0161f08e9eab0b5630f2797 Author: Andrey Mokhov Date: Sun Feb 14 22:55:38 2016 +0000 Install mkUserGuidePart binary to inplace/bin. >--------------------------------------------------------------- d1ec507d7b4d837ee0161f08e9eab0b5630f2797 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0262243..d29cbbf 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -106,7 +106,7 @@ ghcSplit = "inplace/lib/bin/ghc-split" programPath :: Stage -> Package -> Maybe FilePath programPath stage pkg | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) - | pkg == haddock || pkg == ghcTags = case stage of + | pkg `elem` [ghcTags, haddock, mkUserGuidePart] = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing | pkg `elem` [touchy, unlit] = case stage of From git at git.haskell.org Fri Oct 27 00:02:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add knownWays and knownRtsWays to Settings.Ways. (12cecf1) Message-ID: <20171027000211.8D1443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12cecf14f5205327b6520f72f8ddcb94a416fba9/ghc >--------------------------------------------------------------- commit 12cecf14f5205327b6520f72f8ddcb94a416fba9 Author: Andrey Mokhov Date: Wed Aug 5 22:31:19 2015 +0100 Add knownWays and knownRtsWays to Settings.Ways. >--------------------------------------------------------------- 12cecf14f5205327b6520f72f8ddcb94a416fba9 src/Settings/GhcCabal.hs | 1 + src/Settings/User.hs | 1 - src/Settings/Ways.hs | 16 ++++++++++++++-- 3 files changed, 15 insertions(+), 3 deletions(-) diff --git a/src/Settings/GhcCabal.hs b/src/Settings/GhcCabal.hs index dfcb3df..5f264b2 100644 --- a/src/Settings/GhcCabal.hs +++ b/src/Settings/GhcCabal.hs @@ -15,6 +15,7 @@ import Oracles.Setting import Settings.User import Settings.Ways import Settings.Util +import Settings.Packages cabalArgs :: Args cabalArgs = builder GhcCabal ? do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 6426e82..572feb4 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,5 +1,4 @@ module Settings.User ( - module Settings.Default, userArgs, userPackages, userWays, userRtsWays, userTargetDirectory, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index c8377eb..ae4bd38 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,6 +1,7 @@ module Settings.Ways ( ways, getWays, - rtsWays, getRtsWays + rtsWays, getRtsWays, + knownWays, knownRtsWays ) where import Way @@ -8,7 +9,7 @@ import Stage import Switches import Expression import Oracles.Flag -import Settings.User +import Settings.User hiding (parallel) -- Combining default ways with user modifications ways :: Ways @@ -39,3 +40,14 @@ defaultRtsWays = do , (dynamic `elem` ways) ? append [ dynamic, debugDynamic, threadedDynamic, threadedDebugDynamic , loggingDynamic, threadedLoggingDynamic ] ] + +-- These are all ways known to the build system +knownWays :: [Way] +knownWays = [vanilla, profiling, logging, parallel, granSim] + +knownRtsWays :: [Way] +knownRtsWays = [ threaded, threadedProfiling, threadedLogging, debug + , debugProfiling, threadedDebug, threadedDebugProfiling, dynamic + , profilingDynamic, threadedProfilingDynamic, threadedDynamic + , threadedDebugDynamic, debugDynamic, loggingDynamic + , threadedLoggingDynamic ] From git at git.haskell.org Fri Oct 27 00:02:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build badges more informative (bf18da2) Message-ID: <20171027000212.827523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf18da2ffa30040b3a51949f8cf75f2fef09d2cd/ghc >--------------------------------------------------------------- commit bf18da2ffa30040b3a51949f8cf75f2fef09d2cd Author: Andrey Mokhov Date: Thu Jan 7 23:13:16 2016 +0000 Make build badges more informative [skip ci] >--------------------------------------------------------------- bf18da2ffa30040b3a51949f8cf75f2fef09d2cd README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 2259c0b..fe6a909 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Shaking up GHC ============== -[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Build status](https://ci.appveyor.com/api/projects/status/9er74sbnrkco98gb?svg=true&pendingText=Windows&passingText=Windows&failingText=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) As part of my 6-month research secondment to Microsoft Research in Cambridge From git at git.haskell.org Fri Oct 27 00:02:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix incorrect context when reading BuildGhciLib flag. (9207f25) Message-ID: <20171027000214.7F8003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9207f2530763c2bace7708cac77c767e596035da/ghc >--------------------------------------------------------------- commit 9207f2530763c2bace7708cac77c767e596035da Author: Andrey Mokhov Date: Sun Feb 14 22:57:17 2016 +0000 Fix incorrect context when reading BuildGhciLib flag. >--------------------------------------------------------------- 9207f2530763c2bace7708cac77c767e596035da src/Rules/Program.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index f00dd59..00f4c52 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -85,18 +85,18 @@ buildBinary context @ (Context stage package _) bin = do depNames <- interpretInContext context $ getPkgDataList TransitiveDepNames let libStage = min stage Stage1 -- libraries are built only in Stage0/1 libContext = vanillaContext libStage package - pkgs <- interpretInContext libContext getPackages - ghciFlag <- interpretInContext libContext $ getPkgData BuildGhciLib + pkgs <- interpretInContext libContext getPackages let deps = matchPackageNames (sort pkgs) (map PackageName $ sort depNames) - ghci = ghciFlag == "YES" && stage == Stage1 libs <- fmap concat . forM deps $ \dep -> do + let depContext = vanillaContext libStage dep + ghciFlag <- interpretInContext depContext $ getPkgData BuildGhciLib libFiles <- fmap concat . forM ways $ \way -> do libFile <- pkgLibraryFile libStage dep way lib0File <- pkgLibraryFile0 libStage dep way dll0 <- needDll0 libStage dep return $ libFile : [ lib0File | dll0 ] ghciLib <- pkgGhciLibraryFile libStage dep - return $ libFiles ++ [ ghciLib | ghci ] + return $ libFiles ++ [ ghciLib | ghciFlag == "YES" && stage == Stage1 ] let binDeps = if package == ghcCabal && stage == Stage0 then [ pkgPath package -/- src <.> "hs" | src <- hSrcs ] else objs From git at git.haskell.org Fri Oct 27 00:02:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement compilePackage build rule. (098d9c1) Message-ID: <20171027000215.166803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/098d9c1e26a4da698eaea64a3da39bb7b0cd3838/ghc >--------------------------------------------------------------- commit 098d9c1e26a4da698eaea64a3da39bb7b0cd3838 Author: Andrey Mokhov Date: Wed Aug 5 22:31:59 2015 +0100 Implement compilePackage build rule. >--------------------------------------------------------------- 098d9c1e26a4da698eaea64a3da39bb7b0cd3838 src/Package/Compile.hs | 101 --------------------------------------- src/Rules/Compile.hs | 40 ++++++++++++++++ src/Rules/Package.hs | 3 +- src/Settings/{GccM.hs => Gcc.hs} | 26 +++++----- src/Settings/GccM.hs | 13 +---- src/Settings/{GhcM.hs => Ghc.hs} | 46 ++++++++++++------ src/Settings/GhcM.hs | 45 +---------------- src/Settings/Util.hs | 15 ------ 8 files changed, 88 insertions(+), 201 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 098d9c1e26a4da698eaea64a3da39bb7b0cd3838 From git at git.haskell.org Fri Oct 27 00:02:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try fetching ghc-tarballs via stack exec. (ee94a7c) Message-ID: <20171027000216.0A6333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee94a7ce968d9a5fe1674018af8d7a2f52e8bb12/ghc >--------------------------------------------------------------- commit ee94a7ce968d9a5fe1674018af8d7a2f52e8bb12 Author: Andrey Mokhov Date: Thu Jan 7 23:23:10 2016 +0000 Try fetching ghc-tarballs via stack exec. See #110. [skip ci] >--------------------------------------------------------------- ee94a7ce968d9a5fe1674018af8d7a2f52e8bb12 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7d5a0f8..79f3369 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -11,8 +11,8 @@ install: - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - bash -lc "mkdir -p /home/ghc/ghc-tarballs" - - bash -lc "cd /home/ghc && ./mk/get-win32-tarballs.sh download x86_64" + - cd C:\msys64\home\ghc + - stack exec -- mk/get-win32-tarballs.sh download x86_64 build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:02:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out build rules into Rules.buildRules. (e7f8710) Message-ID: <20171027000218.E8A9E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7f8710c591d5329e4a06df538ca0aa789b065a0/ghc >--------------------------------------------------------------- commit e7f8710c591d5329e4a06df538ca0aa789b065a0 Author: Andrey Mokhov Date: Sun Feb 14 22:59:11 2016 +0000 Factor out build rules into Rules.buildRules. >--------------------------------------------------------------- e7f8710c591d5329e4a06df538ca0aa789b065a0 src/Main.hs | 17 ++--------------- src/Rules.hs | 39 ++++++++++++++++++++++++++++----------- 2 files changed, 30 insertions(+), 26 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 544987d..e028597 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -6,14 +6,8 @@ import qualified Base import qualified CmdLineFlag import qualified Environment import qualified Rules -import qualified Rules.Cabal import qualified Rules.Clean -import qualified Rules.Generate -import qualified Rules.Gmp -import qualified Rules.Libffi import qualified Rules.Oracles -import qualified Rules.Perl -import qualified Rules.Setup import qualified Selftest import qualified Test @@ -27,17 +21,10 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do where rules :: Rules () rules = mconcat - [ Rules.Cabal.cabalRules - , Rules.Clean.cleanRules - , Rules.Generate.generateRules - , Rules.Generate.copyRules - , Rules.Gmp.gmpRules - , Rules.Libffi.libffiRules + [ Rules.Clean.cleanRules , Rules.Oracles.oracleRules - , Rules.Perl.perlScriptRules - , Rules.Setup.setupRules + , Rules.buildRules , Rules.topLevelTargets - , Rules.packageRules , Selftest.selftestRules , Test.testRules ] options = shakeOptions diff --git a/src/Rules.hs b/src/Rules.hs index 34cea4c..5cbfa7e 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,12 +1,18 @@ -module Rules (topLevelTargets, packageRules) where +module Rules (topLevelTargets, buildRules) where -import Base import Data.Foldable + +import Base import Expression -import GHC hiding (haddock) +import GHC import qualified Rules.Generate -import Rules.Package -import Rules.Resources +import qualified Rules.Package +import qualified Rules.Resources +import qualified Rules.Cabal +import qualified Rules.Gmp +import qualified Rules.Libffi +import qualified Rules.Perl +import qualified Rules.Setup import Settings allStages :: [Stage] @@ -32,16 +38,27 @@ topLevelTargets = do when (pkg `elem` activePackages) $ if isLibrary pkg then do -- build a library - ways <- interpretInContext context getLibraryWays - libs <- traverse (pkgLibraryFile stage pkg) ways - haddock <- interpretInContext context buildHaddock - need $ libs ++ [ pkgHaddockFile pkg | haddock && stage == Stage1 ] + ways <- interpretInContext context getLibraryWays + libs <- traverse (pkgLibraryFile stage pkg) ways + docs <- interpretInContext context buildHaddock + need $ libs ++ [ pkgHaddockFile pkg | docs && stage == Stage1 ] else do -- otherwise build a program need [ fromJust $ programPath stage pkg ] -- TODO: drop fromJust packageRules :: Rules () packageRules = do - resources <- resourceRules + resources <- Rules.Resources.resourceRules for_ allStages $ \stage -> for_ knownPackages $ \pkg -> - buildPackage resources $ vanillaContext stage pkg + Rules.Package.buildPackage resources $ vanillaContext stage pkg + +buildRules :: Rules () +buildRules = mconcat + [ Rules.Cabal.cabalRules + , Rules.Generate.generateRules + , Rules.Generate.copyRules + , Rules.Gmp.gmpRules + , Rules.Libffi.libffiRules + , Rules.Perl.perlScriptRules + , Rules.Setup.setupRules + , Rules.packageRules ] From git at git.haskell.org Fri Oct 27 00:02:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build rules for *.S sources, add rts/*.S files. (b6bb19c) Message-ID: <20171027000219.D2AF13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6bb19c87edc0e36e1322af12622493a61f48386/ghc >--------------------------------------------------------------- commit b6bb19c87edc0e36e1322af12622493a61f48386 Author: Andrey Mokhov Date: Thu Jan 7 23:53:44 2016 +0000 Add build rules for *.S sources, add rts/*.S files. See #126. >--------------------------------------------------------------- b6bb19c87edc0e36e1322af12622493a61f48386 src/Rules/Data.hs | 11 ++++++++--- src/Rules/Dependencies.hs | 9 +++++---- 2 files changed, 13 insertions(+), 7 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 46072ce..de4f8c0 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -95,13 +95,18 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do ++ [ "posix" | not windows ] ++ [ "win32" | windows ] -- TODO: rts/dist/build/sm/Evac_thr.c, rts/dist/build/sm/Scav_thr.c - -- TODO: adding cmm sources to C_SRCS is a hack; rethink after #18 + -- TODO: adding cmm/S sources to C_SRCS is a hack; rethink after #18 cSrcs <- getDirectoryFiles (pkgPath pkg) (map (-/- "*.c") dirs) cmmSrcs <- getDirectoryFiles (pkgPath pkg) ["*.cmm"] - let extraSrcs = [ targetDirectory Stage1 rts -/- "build/AutoApply.cmm" ] + buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] + buildStgCRunAsm <- anyTargetArch ["powerpc64le"] + let sSrcs = [ "AdjustorAsm.S" | buildAdjustor ] + ++ [ "StgCRunAsm.S" | buildStgCRunAsm ] + extraSrcs = [ targetDirectory Stage1 rts -/- "build/AutoApply.cmm" ] includes <- interpretPartial target $ fromDiffExpr includesArgs let contents = unlines $ map (prefix++) - [ "C_SRCS = " ++ unwords (cSrcs ++ cmmSrcs ++ extraSrcs) + [ "C_SRCS = " + ++ unwords (cSrcs ++ cmmSrcs ++ sSrcs ++ extraSrcs) , "CC_OPTS = " ++ unwords includes , "COMPONENT_ID = " ++ "rts" ] writeFileChanged mk contents diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 79bcdb2..2da9549 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -15,10 +15,11 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = dropBuild = (pkgPath pkg ++) . drop (length buildPath) hDepFile = buildPath -/- ".hs-dependencies" in do - [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do - let srcFile = dropBuild . dropExtension $ out - need [srcFile] - build $ fullTarget target (GccM stage) [srcFile] [out] + fmap (buildPath++) + [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do + let srcFile = dropBuild . dropExtension $ out + need [srcFile] + build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources From git at git.haskell.org Fri Oct 27 00:02:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Selftest and Test rules into Rules directory. (d81e041) Message-ID: <20171027000222.B3DC93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d81e041691644e1f99a84691ac0d0fb94c96b263/ghc >--------------------------------------------------------------- commit d81e041691644e1f99a84691ac0d0fb94c96b263 Author: Andrey Mokhov Date: Sun Feb 14 23:02:46 2016 +0000 Move Selftest and Test rules into Rules directory. >--------------------------------------------------------------- d81e041691644e1f99a84691ac0d0fb94c96b263 shaking-up-ghc.cabal | 4 ++-- src/Main.hs | 10 +++++----- src/{ => Rules}/Selftest.hs | 2 +- src/{ => Rules}/Test.hs | 2 +- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 2ab8ee7..6435d30 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -63,10 +63,11 @@ executable ghc-shake , Rules.Program , Rules.Register , Rules.Resources + , Rules.Selftest , Rules.Setup + , Rules.Test , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg - , Selftest , Settings , Settings.Args , Settings.Builders.Alex @@ -106,7 +107,6 @@ executable ghc-shake , Settings.Ways , Stage , Target - , Test , Way default-language: Haskell2010 diff --git a/src/Main.hs b/src/Main.hs index e028597..5de50ad 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -8,8 +8,8 @@ import qualified Environment import qualified Rules import qualified Rules.Clean import qualified Rules.Oracles -import qualified Selftest -import qualified Test +import qualified Rules.Selftest +import qualified Rules.Test main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -23,10 +23,10 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do rules = mconcat [ Rules.Clean.cleanRules , Rules.Oracles.oracleRules + , Rules.Selftest.selftestRules + , Rules.Test.testRules , Rules.buildRules - , Rules.topLevelTargets - , Selftest.selftestRules - , Test.testRules ] + , Rules.topLevelTargets ] options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Selftest.hs b/src/Rules/Selftest.hs similarity index 94% rename from src/Selftest.hs rename to src/Rules/Selftest.hs index 4800ca8..a3cc089 100644 --- a/src/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -module Selftest (selftestRules) where +module Rules.Selftest (selftestRules) where import Development.Shake import Settings.Builders.Ar (chunksOfSize) diff --git a/src/Test.hs b/src/Rules/Test.hs similarity index 98% rename from src/Test.hs rename to src/Rules/Test.hs index 3ef0d1d..0448b2b 100644 --- a/src/Test.hs +++ b/src/Rules/Test.hs @@ -1,4 +1,4 @@ -module Test (testRules) where +module Rules.Test (testRules) where import Base import Builder From git at git.haskell.org Fri Oct 27 00:02:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of redError_. (4fd1732) Message-ID: <20171027000219.3D07B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fd17325b1c7921c1278a8da85544960ef07a5af/ghc >--------------------------------------------------------------- commit 4fd17325b1c7921c1278a8da85544960ef07a5af Author: Andrey Mokhov Date: Wed Aug 5 23:23:22 2015 +0100 Get rid of redError_. >--------------------------------------------------------------- 4fd17325b1c7921c1278a8da85544960ef07a5af src/Oracles/Base.hs | 4 ++-- src/Util.hs | 6 +----- 2 files changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Oracles/Base.hs b/src/Oracles/Base.hs index 29ec4e4..a6abbfc 100644 --- a/src/Oracles/Base.hs +++ b/src/Oracles/Base.hs @@ -31,8 +31,8 @@ configOracle = do let configFile = configPath -/- "system.config" cfg <- newCache $ \() -> do unlessM (doesFileExist $ configFile <.> "in") $ - putError_ $ "\nConfiguration file '" ++ (configFile <.> "in") - ++ "' is missing; unwilling to proceed." + putError $ "\nConfiguration file '" ++ (configFile <.> "in") + ++ "' is missing; unwilling to proceed." need [configFile] putOracle $ "Reading " ++ configFile ++ "..." liftIO $ readConfigFile configFile diff --git a/src/Util.hs b/src/Util.hs index 32b6478..f00785f 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -4,13 +4,12 @@ module Util ( replaceIf, replaceEq, replaceSeparators, unifyPath, (-/-), chunksOfSize, - putColoured, putOracle, putBuild, putError, putError_, + putColoured, putOracle, putBuild, putError, bimap, minusOrd, intersectOrd ) where import Base import Data.Char -import Control.Monad import System.IO import System.Console.ANSI @@ -70,9 +69,6 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg -putError_ :: String -> Action () -putError_ = void . putError - -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) From git at git.haskell.org Fri Oct 27 00:02:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make detectWay safe, add comments. (7ebd24f) Message-ID: <20171027000223.32F1B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ebd24fe9d9177e65d5823d02a73c6a1776d85b2/ghc >--------------------------------------------------------------- commit 7ebd24fe9d9177e65d5823d02a73c6a1776d85b2 Author: Andrey Mokhov Date: Wed Aug 5 23:24:15 2015 +0100 Make detectWay safe, add comments. >--------------------------------------------------------------- 7ebd24fe9d9177e65d5823d02a73c6a1776d85b2 src/Way.hs | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index b48a29d..912ea63 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -124,11 +124,16 @@ libsuf way @ (Way set) = -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension --- Detect way from a given file extension. Fails if there is no match. -detectWay :: FilePath -> Way -detectWay extension = read prefix +-- Detect way from a given filename. Returns Nothing if there is no match: +-- * detectWay "foo/bar.hi" == Just vanilla +-- * detectWay "baz.thr_p_o" == Just threadedProfiling +-- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +detectWay :: FilePath -> Maybe Way +detectWay file = case reads prefix of + [(way, "")] -> Just way + _ -> Nothing where - prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ extension + prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ takeExtension file -- Instances for storing in the Shake database instance Binary Way where From git at git.haskell.org Fri Oct 27 00:02:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Specify path to stack. (9ad20c9) Message-ID: <20171027000223.9FF293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ad20c9a77dd8655d53bc1e0f512794876df8741/ghc >--------------------------------------------------------------- commit 9ad20c9a77dd8655d53bc1e0f512794876df8741 Author: Andrey Mokhov Date: Thu Jan 7 23:57:57 2016 +0000 Specify path to stack. See #110. [skip ci] >--------------------------------------------------------------- 9ad20c9a77dd8655d53bc1e0f512794876df8741 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 79f3369..9e1ed1e 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -12,7 +12,7 @@ install: - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - - stack exec -- mk/get-win32-tarballs.sh download x86_64 + - C:\stack exec -- mk/get-win32-tarballs.sh download x86_64 build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:02:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Rules/Package.hs into Rules.hs. (a10669a) Message-ID: <20171027000226.879A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a10669a6788da387e9e5a3e6fe35383589f22ac1/ghc >--------------------------------------------------------------- commit a10669a6788da387e9e5a3e6fe35383589f22ac1 Author: Andrey Mokhov Date: Sun Feb 14 23:21:54 2016 +0000 Move Rules/Package.hs into Rules.hs. >--------------------------------------------------------------- a10669a6788da387e9e5a3e6fe35383589f22ac1 shaking-up-ghc.cabal | 1 - src/Rules.hs | 21 +++++++++++++++++++-- src/Rules/Package.hs | 24 ------------------------ 3 files changed, 19 insertions(+), 27 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 6435d30..193b04e 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -58,7 +58,6 @@ executable ghc-shake , Rules.Libffi , Rules.Library , Rules.Oracles - , Rules.Package , Rules.Perl , Rules.Program , Rules.Register diff --git a/src/Rules.hs b/src/Rules.hs index 5cbfa7e..cea2c0d 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,13 +5,19 @@ import Data.Foldable import Base import Expression import GHC +import qualified Rules.Compile +import qualified Rules.Data +import qualified Rules.Dependencies +import qualified Rules.Documentation import qualified Rules.Generate -import qualified Rules.Package import qualified Rules.Resources import qualified Rules.Cabal import qualified Rules.Gmp import qualified Rules.Libffi +import qualified Rules.Library import qualified Rules.Perl +import qualified Rules.Program +import qualified Rules.Register import qualified Rules.Setup import Settings @@ -50,7 +56,18 @@ packageRules = do resources <- Rules.Resources.resourceRules for_ allStages $ \stage -> for_ knownPackages $ \pkg -> - Rules.Package.buildPackage resources $ vanillaContext stage pkg + buildPackage resources $ vanillaContext stage pkg + +buildPackage :: Rules.Resources.Resources -> Context -> Rules () +buildPackage = mconcat + [ Rules.Compile.compilePackage + , Rules.Data.buildPackageData + , Rules.Dependencies.buildPackageDependencies + , Rules.Documentation.buildPackageDocumentation + , Rules.Generate.generatePackageCode + , Rules.Library.buildPackageLibrary + , Rules.Program.buildProgram + , Rules.Register.registerPackage ] buildRules :: Rules () buildRules = mconcat diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs deleted file mode 100644 index 26de923..0000000 --- a/src/Rules/Package.hs +++ /dev/null @@ -1,24 +0,0 @@ -module Rules.Package (buildPackage) where - -import Base -import Context -import qualified Rules.Compile -import qualified Rules.Data -import qualified Rules.Dependencies -import qualified Rules.Documentation -import qualified Rules.Generate -import qualified Rules.Library -import qualified Rules.Program -import qualified Rules.Register -import Rules.Resources - -buildPackage :: Resources -> Context -> Rules () -buildPackage = mconcat - [ Rules.Compile.compilePackage - , Rules.Data.buildPackageData - , Rules.Dependencies.buildPackageDependencies - , Rules.Documentation.buildPackageDocumentation - , Rules.Generate.generatePackageCode - , Rules.Library.buildPackageLibrary - , Rules.Program.buildProgram - , Rules.Register.registerPackage ] From git at git.haskell.org Fri Oct 27 00:02:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop knownWays and knownRtsWays. (be568c0) Message-ID: <20171027000226.DFC393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/be568c02f7ea7af3b916257cbf7656c8f9ad4979/ghc >--------------------------------------------------------------- commit be568c02f7ea7af3b916257cbf7656c8f9ad4979 Author: Andrey Mokhov Date: Wed Aug 5 23:24:47 2015 +0100 Drop knownWays and knownRtsWays. >--------------------------------------------------------------- be568c02f7ea7af3b916257cbf7656c8f9ad4979 src/Settings/Ways.hs | 14 +------------- 1 file changed, 1 insertion(+), 13 deletions(-) diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index ae4bd38..0ea3432 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,7 +1,6 @@ module Settings.Ways ( ways, getWays, - rtsWays, getRtsWays, - knownWays, knownRtsWays + rtsWays, getRtsWays ) where import Way @@ -40,14 +39,3 @@ defaultRtsWays = do , (dynamic `elem` ways) ? append [ dynamic, debugDynamic, threadedDynamic, threadedDebugDynamic , loggingDynamic, threadedLoggingDynamic ] ] - --- These are all ways known to the build system -knownWays :: [Way] -knownWays = [vanilla, profiling, logging, parallel, granSim] - -knownRtsWays :: [Way] -knownRtsWays = [ threaded, threadedProfiling, threadedLogging, debug - , debugProfiling, threadedDebug, threadedDebugProfiling, dynamic - , profilingDynamic, threadedProfilingDynamic, threadedDynamic - , threadedDebugDynamic, debugDynamic, loggingDynamic - , threadedLoggingDynamic ] From git at git.haskell.org Fri Oct 27 00:02:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add init script, fix path to stak. (23ef499) Message-ID: <20171027000227.2573A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23ef49931f9e0970746cd603c46e4a996438d27e/ghc >--------------------------------------------------------------- commit 23ef49931f9e0970746cd603c46e4a996438d27e Author: Andrey Mokhov Date: Fri Jan 8 01:18:48 2016 +0000 Add init script, fix path to stak. See #110. [skip ci] >--------------------------------------------------------------- 23ef49931f9e0970746cd603c46e4a996438d27e .appveyor.yml | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 9e1ed1e..5ad5f0b 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,6 +1,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -install: +init: + - cd - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 @@ -9,12 +10,13 @@ install: - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc + +install: - cd C:\msys64\home\ghc - - C:\stack exec -- mk/get-win32-tarballs.sh download x86_64 + - shake-build\stack.exe exec -- mk/get-win32-tarballs.sh download x86_64 build_script: - - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo \"\" | ./configure" - - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" + - bash -lc "./boot" + - bash -lc "echo \"\" | ./configure" + - bash -lc "./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:02:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add APPVEYOR_BUILD_FOLDER to PATH, show versions of key binaries. (782e998) Message-ID: <20171027000231.1D2C13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/782e99878b0a669aaa585b84531a089e68502f26/ghc >--------------------------------------------------------------- commit 782e99878b0a669aaa585b84531a089e68502f26 Author: Andrey Mokhov Date: Fri Jan 8 01:31:18 2016 +0000 Add APPVEYOR_BUILD_FOLDER to PATH, show versions of key binaries. See #110. [skip ci] >--------------------------------------------------------------- 782e99878b0a669aaa585b84531a089e68502f26 .appveyor.yml | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 5ad5f0b..136bee6 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -9,12 +9,16 @@ init: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ + - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc install: - cd C:\msys64\home\ghc - - shake-build\stack.exe exec -- mk/get-win32-tarballs.sh download x86_64 + - stack exec -- mk/get-win32-tarballs.sh download x86_64 + - ghc --version + - stack --version + - alex --version + - happy --version build_script: - bash -lc "./boot" From git at git.haskell.org Fri Oct 27 00:02:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise rules by removing a loop over all possible ways. (c204ca9) Message-ID: <20171027000231.4E42C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c204ca9764ac5ffdb141247151e040bd1bffa5d6/ghc >--------------------------------------------------------------- commit c204ca9764ac5ffdb141247151e040bd1bffa5d6 Author: Andrey Mokhov Date: Wed Aug 5 23:26:36 2015 +0100 Optimise rules by removing a loop over all possible ways. >--------------------------------------------------------------- c204ca9764ac5ffdb141247151e040bd1bffa5d6 src/Rules/Compile.hs | 34 +++++++++++++++++++--------------- 1 file changed, 19 insertions(+), 15 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 4b2fe4b..89b60c2 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -7,10 +7,14 @@ import Builder import Expression import qualified Target import Oracles.DependencyList -import Settings.Ways import Settings.TargetDirectory import Rules.Actions import Rules.Resources +import Data.Maybe + +matchBuildResult :: FilePath -> String -> FilePath -> Bool +matchBuildResult buildPath extension file = + (buildPath "*" ++ extension) ?== file && (isJust . detectWay $ file) compilePackage :: Resources -> StagePackageTarget -> Rules () compilePackage _ target = do @@ -21,20 +25,20 @@ compilePackage _ target = do cDepsFile = buildPath -/- "c.deps" hDepsFile = buildPath -/- "haskell.deps" - forM_ knownWays $ \way -> do - (buildPath "*." ++ hisuf way) %> \hi -> do - let obj = hi -<.> osuf way - need [obj] + matchBuildResult buildPath "hi" ?> \hi -> do + let way = fromJust . detectWay $ hi -- fromJust is safe + need [hi -<.> osuf way] - (buildPath "*." ++ osuf way) %> \obj -> do - let vanillaObjName = takeFileName obj -<.> "o" - cDeps <- dependencyList cDepsFile vanillaObjName - hDeps <- dependencyList hDepsFile obj - let hSrcDeps = filter ("//*hs" ?==) hDeps + matchBuildResult buildPath "o" ?> \obj -> do + let way = fromJust . detectWay $ obj -- fromJust is safe + vanillaObj = takeFileName obj -<.> "o" + cDeps <- dependencyList cDepsFile vanillaObj + hDeps <- dependencyList hDepsFile obj + let hSrcDeps = filter ("//*hs" ?==) hDeps - when (null cDeps && null hDeps) $ - putError_ $ "Cannot determine sources for '" ++ obj ++ "'." + when (null cDeps && null hDeps) $ + putError $ "Cannot determine sources for '" ++ obj ++ "'." - if null cDeps - then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] - else build $ fullTarget target cDeps (Gcc stage) [obj] + if null cDeps + then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] + else build $ fullTarget target cDeps (Gcc stage) [obj] From git at git.haskell.org Fri Oct 27 00:02:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused Resources parameter. (010fb8c) Message-ID: <20171027000231.1854B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/010fb8c148ae0d0c08236c19e74e214968d45410/ghc >--------------------------------------------------------------- commit 010fb8c148ae0d0c08236c19e74e214968d45410 Author: Andrey Mokhov Date: Sun Feb 14 23:30:15 2016 +0000 Drop unused Resources parameter. >--------------------------------------------------------------- 010fb8c148ae0d0c08236c19e74e214968d45410 src/Rules.hs | 23 ++++++++++------------- src/Rules/Data.hs | 5 ++--- src/Rules/Documentation.hs | 5 ++--- src/Rules/Generate.hs | 5 ++--- src/Rules/Library.hs | 5 ++--- src/Rules/Program.hs | 5 ++--- 6 files changed, 20 insertions(+), 28 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index cea2c0d..be71d2f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -55,19 +55,16 @@ packageRules :: Rules () packageRules = do resources <- Rules.Resources.resourceRules for_ allStages $ \stage -> - for_ knownPackages $ \pkg -> - buildPackage resources $ vanillaContext stage pkg - -buildPackage :: Rules.Resources.Resources -> Context -> Rules () -buildPackage = mconcat - [ Rules.Compile.compilePackage - , Rules.Data.buildPackageData - , Rules.Dependencies.buildPackageDependencies - , Rules.Documentation.buildPackageDocumentation - , Rules.Generate.generatePackageCode - , Rules.Library.buildPackageLibrary - , Rules.Program.buildProgram - , Rules.Register.registerPackage ] + for_ knownPackages $ \package -> do + let context = vanillaContext stage package + Rules.Compile.compilePackage resources context + Rules.Data.buildPackageData context + Rules.Dependencies.buildPackageDependencies resources context + Rules.Documentation.buildPackageDocumentation context + Rules.Generate.generatePackageCode context + Rules.Library.buildPackageLibrary context + Rules.Program.buildProgram context + Rules.Register.registerPackage resources context buildRules :: Rules () buildRules = mconcat diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 7386003..f47e8d0 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -12,14 +12,13 @@ import Oracles.PackageDeps import Rules.Actions import Rules.Generate import Rules.Libffi -import Rules.Resources import Settings import Settings.Builders.Common import Target -- Build package-data.mk by using GhcCabal to process pkgCabal file -buildPackageData :: Resources -> Context -> Rules () -buildPackageData _ context @ (Context {..}) = do +buildPackageData :: Context -> Rules () +buildPackageData context @ (Context {..}) = do let cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile stage package diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 95a5667..848a3fa 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -7,7 +7,6 @@ import Expression import GHC import Oracles.PackageData import Rules.Actions -import Rules.Resources import Settings import Target @@ -17,8 +16,8 @@ haddockHtmlLib = "inplace/lib/html/haddock-util.js" -- Note: this build rule creates plenty of files, not just the .haddock one. -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. -buildPackageDocumentation :: Resources -> Context -> Rules () -buildPackageDocumentation _ context @ (Context {..}) = +buildPackageDocumentation :: Context -> Rules () +buildPackageDocumentation context @ (Context {..}) = let cabalFile = pkgCabalFile package haddockFile = pkgHaddockFile package in when (stage == Stage1) $ do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 1a8a239..050f83c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -20,7 +20,6 @@ import Oracles.ModuleFiles import Rules.Actions import Rules.Gmp import Rules.Libffi -import Rules.Resources (Resources) import Settings import Target hiding (builder, context) @@ -114,8 +113,8 @@ generate file context expr = do writeFileChanged file contents putSuccess $ "| Successfully generated '" ++ file ++ "'." -generatePackageCode :: Resources -> Context -> Rules () -generatePackageCode _ context @ (Context stage pkg _) = +generatePackageCode :: Context -> Rules () +generatePackageCode context @ (Context stage pkg _) = let buildPath = targetPath stage pkg -/- "build" dropBuild = drop (length buildPath + 1) generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index be8f158..79b4952 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -11,13 +11,12 @@ import GHC import Oracles.PackageData import Rules.Actions import Rules.Gmp -import Rules.Resources import Settings import Target -- TODO: Use way from Context, #207 -buildPackageLibrary :: Resources -> Context -> Rules () -buildPackageLibrary _ context @ (Context {..}) = do +buildPackageLibrary :: Context -> Rules () +buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" -- TODO: handle dynamic libraries diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 00f4c52..d7fdaad 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -11,7 +11,6 @@ import Oracles.Config.Setting import Oracles.PackageData import Rules.Actions import Rules.Library -import Rules.Resources import Rules.Wrappers.Ghc import Rules.Wrappers.GhcPkg import Settings @@ -32,8 +31,8 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper)] -buildProgram :: Resources -> Context -> Rules () -buildProgram _ context @ (Context {..}) = do +buildProgram :: Context -> Rules () +buildProgram context @ (Context {..}) = do let match file = case programPath stage package of Nothing -> False Just program -> program == file From git at git.haskell.org Fri Oct 27 00:02:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clone ghc into ghc/tmp. (2fd5c6e) Message-ID: <20171027000235.6DCF43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2fd5c6e03952155a73d39fbfe925606d8d99fbfe/ghc >--------------------------------------------------------------- commit 2fd5c6e03952155a73d39fbfe925606d8d99fbfe Author: Andrey Mokhov Date: Fri Jan 8 01:58:26 2016 +0000 Clone ghc into ghc/tmp. See #110. [skip ci] >--------------------------------------------------------------- 2fd5c6e03952155a73d39fbfe925606d8d99fbfe .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 136bee6..ef66eb7 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -4,13 +4,14 @@ init: - cd - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% + - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" install: - cd C:\msys64\home\ghc From git at git.haskell.org Fri Oct 27 00:02:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use do notation to combine Rules. (b820539) Message-ID: <20171027000235.944323A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b82053913f31548325da535ba769bb21aa4338ec/ghc >--------------------------------------------------------------- commit b82053913f31548325da535ba769bb21aa4338ec Author: Andrey Mokhov Date: Sun Feb 14 23:34:37 2016 +0000 Use do notation to combine Rules. >--------------------------------------------------------------- b82053913f31548325da535ba769bb21aa4338ec src/Main.hs | 14 +++++++------- src/Rules.hs | 18 +++++++++--------- 2 files changed, 16 insertions(+), 16 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 5de50ad..96639d2 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -20,13 +20,13 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do else want targets >> withoutActions rules where rules :: Rules () - rules = mconcat - [ Rules.Clean.cleanRules - , Rules.Oracles.oracleRules - , Rules.Selftest.selftestRules - , Rules.Test.testRules - , Rules.buildRules - , Rules.topLevelTargets ] + rules = do + Rules.Clean.cleanRules + Rules.Oracles.oracleRules + Rules.Selftest.selftestRules + Rules.Test.testRules + Rules.buildRules + Rules.topLevelTargets options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Rules.hs b/src/Rules.hs index be71d2f..e817fc1 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -67,12 +67,12 @@ packageRules = do Rules.Register.registerPackage resources context buildRules :: Rules () -buildRules = mconcat - [ Rules.Cabal.cabalRules - , Rules.Generate.generateRules - , Rules.Generate.copyRules - , Rules.Gmp.gmpRules - , Rules.Libffi.libffiRules - , Rules.Perl.perlScriptRules - , Rules.Setup.setupRules - , Rules.packageRules ] +buildRules = do + Rules.Cabal.cabalRules + Rules.Generate.generateRules + Rules.Generate.copyRules + Rules.Gmp.gmpRules + Rules.Libffi.libffiRules + Rules.Perl.perlScriptRules + Rules.Setup.setupRules + Rules.packageRules From git at git.haskell.org Fri Oct 27 00:02:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move matchBuildResult to Way.hs. (1711977) Message-ID: <20171027000235.B1EF93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1711977649e14d87093d0f4ff0de132d1c044e42/ghc >--------------------------------------------------------------- commit 1711977649e14d87093d0f4ff0de132d1c044e42 Author: Andrey Mokhov Date: Thu Aug 6 01:34:24 2015 +0100 Move matchBuildResult to Way.hs. >--------------------------------------------------------------- 1711977649e14d87093d0f4ff0de132d1c044e42 src/Way.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/src/Way.hs b/src/Way.hs index 912ea63..365a949 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -10,7 +10,7 @@ module Way ( -- TODO: rename to "Way"? loggingDynamic, threadedLoggingDynamic, wayPrefix, hisuf, osuf, hcsuf, obootsuf, ssuf, libsuf, - detectWay + detectWay, matchBuildResult ) where import Base @@ -20,6 +20,7 @@ import Data.List import Data.IntSet (IntSet) import Control.Applicative import qualified Data.IntSet as Set +import Data.Maybe data WayUnit = Threaded | Debug @@ -135,6 +136,13 @@ detectWay file = case reads prefix of where prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ takeExtension file +-- Given a path, an extension suffix, and a file name check if the latter: +-- 1) conforms to pattern 'path//*suffix' +-- 2) has extension prefixed with a known way tag, i.e. detectWay does not fail +matchBuildResult :: FilePath -> String -> FilePath -> Bool +matchBuildResult path suffix file = + (path "*" ++ suffix) ?== file && (isJust . detectWay $ file) + -- Instances for storing in the Shake database instance Binary Way where put = put . show From git at git.haskell.org Fri Oct 27 00:02:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop init script. (cd567f7) Message-ID: <20171027000239.A6B303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cd567f71ec9ba2b0eb0b3232b4b375df23557354/ghc >--------------------------------------------------------------- commit cd567f71ec9ba2b0eb0b3232b4b375df23557354 Author: Andrey Mokhov Date: Fri Jan 8 02:22:05 2016 +0000 Drop init script. See #110. [skip ci] >--------------------------------------------------------------- cd567f71ec9ba2b0eb0b3232b4b375df23557354 .appveyor.yml | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index ef66eb7..f663d96 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,6 +1,6 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -init: +install: - cd - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% @@ -12,9 +12,6 @@ init: - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - -install: - - cd C:\msys64\home\ghc - stack exec -- mk/get-win32-tarballs.sh download x86_64 - ghc --version - stack --version From git at git.haskell.org Fri Oct 27 00:02:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add cmdLineLengthLimit for detecting command line size limits. (ef14064) Message-ID: <20171027000239.D1A783A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef1406494d3dc15ab0b311fcaf7e3c853c2a3a81/ghc >--------------------------------------------------------------- commit ef1406494d3dc15ab0b311fcaf7e3c853c2a3a81 Author: Andrey Mokhov Date: Thu Aug 6 01:35:31 2015 +0100 Add cmdLineLengthLimit for detecting command line size limits. >--------------------------------------------------------------- ef1406494d3dc15ab0b311fcaf7e3c853c2a3a81 src/Oracles/Setting.hs | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 33067b1..20e4376 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -3,7 +3,7 @@ module Oracles.Setting ( setting, settingList, targetPlatform, targetPlatforms, targetOs, targetOss, notTargetOs, targetArchs, windowsHost, notWindowsHost, ghcWithInterpreter, - ghcEnableTablesNextToCode + ghcEnableTablesNextToCode, cmdLineLengthLimit ) where import Base @@ -96,3 +96,14 @@ ghcWithInterpreter = do ghcEnableTablesNextToCode :: Action Bool ghcEnableTablesNextToCode = targetArchs ["ia64", "powerpc64"] + +-- Command lines have limited size on Windows. Since Windows 7 the limit is +-- 32768 characters (theoretically). In practice we use 31000 to leave some +-- breathing space for the builder's path & name, auxiliary flags, and other +-- overheads. Use this function to set limits for other OSs if necessary. +cmdLineLengthLimit :: Action Int +cmdLineLengthLimit = do + windows <- windowsHost + return $ if windows + then 31000 + else 4194304 -- Cabal needs a bit more than 2MB! From git at git.haskell.org Fri Oct 27 00:02:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (6a9772a) Message-ID: <20171027000240.0777C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a9772a11c4bb3284cf6f3993c4ba25896301a74/ghc >--------------------------------------------------------------- commit 6a9772a11c4bb3284cf6f3993c4ba25896301a74 Author: Andrey Mokhov Date: Sun Feb 14 23:42:17 2016 +0000 Minor revision. >--------------------------------------------------------------- 6a9772a11c4bb3284cf6f3993c4ba25896301a74 src/Main.hs | 1 + src/Rules.hs | 62 ++++++++++++++++++++++++++++++------------------------------ 2 files changed, 32 insertions(+), 31 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 96639d2..cf45cc3 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -27,6 +27,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do Rules.Test.testRules Rules.buildRules Rules.topLevelTargets + options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Rules.hs b/src/Rules.hs index e817fc1..f3db558 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,20 +5,20 @@ import Data.Foldable import Base import Expression import GHC -import qualified Rules.Compile -import qualified Rules.Data -import qualified Rules.Dependencies -import qualified Rules.Documentation -import qualified Rules.Generate -import qualified Rules.Resources -import qualified Rules.Cabal -import qualified Rules.Gmp -import qualified Rules.Libffi -import qualified Rules.Library -import qualified Rules.Perl -import qualified Rules.Program -import qualified Rules.Register -import qualified Rules.Setup +import Rules.Compile +import Rules.Data +import Rules.Dependencies +import Rules.Documentation +import Rules.Generate +import Rules.Resources +import Rules.Cabal +import Rules.Gmp +import Rules.Libffi +import Rules.Library +import Rules.Perl +import Rules.Program +import Rules.Register +import Rules.Setup import Settings allStages :: [Stage] @@ -53,26 +53,26 @@ topLevelTargets = do packageRules :: Rules () packageRules = do - resources <- Rules.Resources.resourceRules + resources <- resourceRules for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package - Rules.Compile.compilePackage resources context - Rules.Data.buildPackageData context - Rules.Dependencies.buildPackageDependencies resources context - Rules.Documentation.buildPackageDocumentation context - Rules.Generate.generatePackageCode context - Rules.Library.buildPackageLibrary context - Rules.Program.buildProgram context - Rules.Register.registerPackage resources context + compilePackage resources context + buildPackageData context + buildPackageDependencies resources context + buildPackageDocumentation context + generatePackageCode context + buildPackageLibrary context + buildProgram context + registerPackage resources context buildRules :: Rules () buildRules = do - Rules.Cabal.cabalRules - Rules.Generate.generateRules - Rules.Generate.copyRules - Rules.Gmp.gmpRules - Rules.Libffi.libffiRules - Rules.Perl.perlScriptRules - Rules.Setup.setupRules - Rules.packageRules + cabalRules + generateRules + copyRules + gmpRules + libffiRules + perlScriptRules + setupRules + packageRules From git at git.haskell.org Fri Oct 27 00:02:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot & configure via stack exec. (8c9544a) Message-ID: <20171027000244.18DE53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c9544add5c72545c98e7b5cb43aa7d0db35590d/ghc >--------------------------------------------------------------- commit 8c9544add5c72545c98e7b5cb43aa7d0db35590d Author: Andrey Mokhov Date: Fri Jan 8 02:51:51 2016 +0000 Run boot & configure via stack exec. See #110. [skip ci] >--------------------------------------------------------------- 8c9544add5c72545c98e7b5cb43aa7d0db35590d .appveyor.yml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f663d96..8333761 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,17 +8,18 @@ install: - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - stack exec -- pacman -S --noconfirm gcc binutils p7zip git + - stack exec -- pacman -S --noconfirm perl gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - stack exec -- mk/get-win32-tarballs.sh download x86_64 + - cd C:\msys64\home\ghc + - stack exec -- perl boot + - stack exec -- configure --enable-tarballs-autodownload - ghc --version - stack --version - alex --version - happy --version build_script: - - bash -lc "./boot" - - bash -lc "echo \"\" | ./configure" + - cd - bash -lc "./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:02:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove unused code. (6c89bd0) Message-ID: <20171027000244.D669B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6c89bd01c53fe3ffa0c26499effff7687530711e/ghc >--------------------------------------------------------------- commit 6c89bd01c53fe3ffa0c26499effff7687530711e Author: Andrey Mokhov Date: Thu Aug 6 01:36:39 2015 +0100 Remove unused code. >--------------------------------------------------------------- 6c89bd01c53fe3ffa0c26499effff7687530711e src/Package/Base.hs | 68 -------------------------------------------- src/Package/Library.hs | 76 -------------------------------------------------- 2 files changed, 144 deletions(-) diff --git a/src/Package/Base.hs b/src/Package/Base.hs deleted file mode 100644 index 1f9d2c8..0000000 --- a/src/Package/Base.hs +++ /dev/null @@ -1,68 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package.Base ( - module Base, - module Ways, - module Util, - module Oracles, - -- Package (..), Settings (..), TodoItem (..), - -- defaultSettings, library, customise, updateSettings, - -- commonCcArgs, commonLdArgs, commonCppArgs, commonCcWarninigArgs, - pathArgs, packageArgs, - includeGccArgs, includeGhcArgs, pkgHsSources, - pkgDepHsObjects, pkgLibHsObjects, pkgCObjects, - argSizeLimit, - sourceDependecies, - argList, argListWithComment, - argListPath - ) where - -import Base -import Ways -import Util -import Oracles -import Settings -import qualified System.Directory as S - --- Find Haskell objects we depend on (we don't want to depend on split objects) -pkgDepHsObjects :: FilePath -> FilePath -> Way -> Action [FilePath] -pkgDepHsObjects path dist way = do - let pathDist = path dist - buildDir = pathDist "build" - dirs <- map (dropWhileEnd isPathSeparator . unifyPath . (path )) - <$> args (SrcDirs pathDist) - fmap concat $ forM dirs $ \d -> - map (unifyPath . (buildDir ++) . (-<.> osuf way) . drop (length d)) - <$> (findModuleFiles pathDist [d] [".hs", ".lhs"]) - -pkgCObjects :: FilePath -> FilePath -> Way -> Action [FilePath] -pkgCObjects path dist way = do - let pathDist = path dist - buildDir = pathDist "build" - srcs <- args $ CSrcs pathDist - return $ map (unifyPath . (buildDir ) . (-<.> osuf way)) srcs - --- Find Haskell objects that go to library -pkgLibHsObjects :: FilePath -> FilePath -> Stage -> Way -> Action [FilePath] -pkgLibHsObjects path dist stage way = do - let pathDist = path dist - buildDir = unifyPath $ pathDist "build" - split <- splitObjects stage - depObjs <- pkgDepHsObjects path dist way - if split - then do - need depObjs -- Otherwise, split objects may not yet be available - let suffix = "_" ++ osuf way ++ "_split/*." ++ osuf way - findModuleFiles pathDist [buildDir] [suffix] - else do return depObjs - --- The argument list has a limited size on Windows. Since Windows 7 the limit --- is 32768 (theoretically). In practice we use 31000 to leave some breathing --- space for the builder's path & name, auxiliary flags, and other overheads. --- Use this function to set limits for other operating systems if necessary. -argSizeLimit :: Action Int -argSizeLimit = do - windows <- windowsHost - return $ if windows - then 31000 - else 4194304 -- Cabal needs a bit more than 2MB! - diff --git a/src/Package/Library.hs b/src/Package/Library.hs deleted file mode 100644 index 82b1ab8..0000000 --- a/src/Package/Library.hs +++ /dev/null @@ -1,76 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -module Package.Library (buildPackageLibrary) where - -import Package.Base - -argListDir :: FilePath -argListDir = "shake/arg/buildPackageLibrary" - -arArgs :: [FilePath] -> FilePath -> Args -arArgs objs result = args [ arg "q" - , arg result - , args objs ] - -ldArgs :: Stage -> [FilePath] -> FilePath -> Args -ldArgs stage objs result = args [ args $ ConfLdLinkerArgs stage - , arg "-r" - , arg "-o" - , arg result - , args objs ] - -arRule :: Package -> TodoItem -> Rules () -arRule pkg @ (Package _ path _ _) todo @ (stage, dist, _) = - let buildDir = path dist "build" - in - (buildDir "*a") %> \out -> do - let way = detectWay $ tail $ takeExtension out - cObjs <- pkgCObjects path dist way - hsObjs <- pkgDepHsObjects path dist way - need $ cObjs ++ hsObjs - libHsObjs <- pkgLibHsObjects path dist stage way - liftIO $ removeFiles "." [out] - -- Splitting argument list into chunks as otherwise Ar chokes up - maxChunk <- argSizeLimit - forM_ (chunksOfSize maxChunk $ cObjs ++ libHsObjs) $ \objs -> do - run Ar $ arArgs objs $ unifyPath out - -- Finally, record the argument list - need [argListPath argListDir pkg stage] - -ldRule :: Package -> TodoItem -> Rules () -ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) = - let pathDist = path dist - buildDir = pathDist "build" - in - priority 2 $ (buildDir "*.o") %> \out -> do - cObjs <- pkgCObjects path dist vanilla - hObjs <- pkgDepHsObjects path dist vanilla - need $ cObjs ++ hObjs - run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out - synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) - putColoured Green $ "/--------\n| Successfully built package '" - ++ name ++ "' (stage " ++ show stage ++ ")." - putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." - ++ "\n\\--------" - -- Finally, record the argument list - need [argListPath argListDir pkg stage] - -argListRule :: Package -> TodoItem -> Rules () -argListRule pkg @ (Package _ path _ _) todo @ (stage, dist, settings) = - (argListPath argListDir pkg stage) %> \out -> do - need $ ["shake/src/Package/Library.hs"] ++ sourceDependecies - cObjsV <- pkgCObjects path dist vanilla - hsObjsV <- pkgDepHsObjects path dist vanilla - ldList <- argList Ld $ ldArgs stage (cObjsV ++ hsObjsV) "output.o" - ways' <- ways settings - arList <- forM ways' $ \way -> do - cObjs <- pkgCObjects path dist way - hsObjs <- pkgLibHsObjects path dist stage way - suffix <- libsuf way - argListWithComment - ("way '" ++ tag way ++ "'") - Ar - (arArgs (cObjs ++ hsObjs) $ "output" <.> suffix) - writeFileChanged out $ unlines $ [ldList] ++ arList - -buildPackageLibrary :: Package -> TodoItem -> Rules () -buildPackageLibrary = argListRule <> arRule <> ldRule From git at git.haskell.org Fri Oct 27 00:02:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Rules.Resources, move packageDb resource to buildRules. (2fc7bd3) Message-ID: <20171027000245.136C63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2fc7bd3ee96d07862b240e8ddcfb584de56a040c/ghc >--------------------------------------------------------------- commit 2fc7bd3ee96d07862b240e8ddcfb584de56a040c Author: Andrey Mokhov Date: Mon Feb 15 23:20:41 2016 +0000 Drop Rules.Resources, move packageDb resource to buildRules. >--------------------------------------------------------------- 2fc7bd3ee96d07862b240e8ddcfb584de56a040c shaking-up-ghc.cabal | 1 - src/Rules.hs | 26 ++++++++++++++++---------- src/Rules/Compile.hs | 11 +++++------ src/Rules/Dependencies.hs | 5 ++--- src/Rules/Register.hs | 7 +++---- src/Rules/Resources.hs | 17 ----------------- 6 files changed, 26 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2fc7bd3ee96d07862b240e8ddcfb584de56a040c From git at git.haskell.org Fri Oct 27 00:02:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't reinstall perl. (efeb163) Message-ID: <20171027000247.AF6733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efeb163633b8e2f9c2e551da13fff7b7c750578c/ghc >--------------------------------------------------------------- commit efeb163633b8e2f9c2e551da13fff7b7c750578c Author: Andrey Mokhov Date: Fri Jan 8 02:55:38 2016 +0000 Don't reinstall perl. See #110. [skip ci] >--------------------------------------------------------------- efeb163633b8e2f9c2e551da13fff7b7c750578c .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 8333761..2a4a628 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,7 +8,7 @@ install: - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - stack exec -- pacman -S --noconfirm perl gcc binutils p7zip git + - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Fri Oct 27 00:02:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for multiple invokations of Ar when argument list is too long. (c02e070) Message-ID: <20171027000248.835003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c02e070cb0b05a443a823ef1134415b14d7043df/ghc >--------------------------------------------------------------- commit c02e070cb0b05a443a823ef1134415b14d7043df Author: Andrey Mokhov Date: Thu Aug 6 01:37:32 2015 +0100 Add support for multiple invokations of Ar when argument list is too long. >--------------------------------------------------------------- c02e070cb0b05a443a823ef1134415b14d7043df src/Rules/Actions.hs | 13 +++++++++++-- 1 file changed, 11 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d96157c..50eb87f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -7,9 +7,11 @@ import Util import Builder import Expression import qualified Target +import Oracles.Setting +import Oracles.ArgsHash import Settings.Args import Settings.Util -import Oracles.ArgsHash +import Settings.Builders.Ar -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last @@ -29,7 +31,14 @@ buildWithResources rs target = do ++ show builder ++ " with arguments:" mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList putBuild $ "\\--------" - quietly $ cmd [path] argList + quietly $ if builder /= Ar + then cmd [path] argList + else do -- Split argument list into chunks as otherwise Ar chokes up + maxChunk <- cmdLineLengthLimit + let persistentArgs = take arPersistentArgsCount argList + remainingArgs = drop arPersistentArgsCount argList + forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> + unit . cmd [path] $ persistentArgs ++ argsChunk -- Most targets are built without explicitly acquiring resources build :: FullTarget -> Action () From git at git.haskell.org Fri Oct 27 00:02:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop GranSim way unit. (de8ca62) Message-ID: <20171027000248.8C0C53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de8ca62e36c5202e8e430c6649313228f529d226/ghc >--------------------------------------------------------------- commit de8ca62e36c5202e8e430c6649313228f529d226 Author: Andrey Mokhov Date: Tue Feb 16 00:01:47 2016 +0000 Drop GranSim way unit. >--------------------------------------------------------------- de8ca62e36c5202e8e430c6649313228f529d226 src/Settings/Builders/Ghc.hs | 1 - src/Way.hs | 7 +------ 2 files changed, 1 insertion(+), 7 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 51fde7f..96737f4 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -102,7 +102,6 @@ wayGhcArgs = do , (Profiling `wayUnit` way) ? arg "-prof" , (Logging `wayUnit` way) ? arg "-eventlog" , (Parallel `wayUnit` way) ? arg "-parallel" - , (GranSim `wayUnit` way) ? arg "-gransim" , (way == debug || way == debugDynamic) ? append ["-ticky", "-DTICKY_TICKY"] ] diff --git a/src/Way.hs b/src/Way.hs index a301afe..59bbbc9 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, wayFromUnits, - vanilla, profiling, logging, parallel, granSim, + vanilla, profiling, logging, parallel, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, @@ -27,7 +27,6 @@ data WayUnit = Threaded | Logging | Dynamic | Parallel - | GranSim deriving (Eq, Enum, Bounded) -- TODO: get rid of non-derived Show instances @@ -39,7 +38,6 @@ instance Show WayUnit where Logging -> "l" Dynamic -> "dyn" Parallel -> "mp" - GranSim -> "gm" instance Read WayUnit where readsPrec _ s = [(unit, "") | unit <- [minBound ..], show unit == s] @@ -96,9 +94,6 @@ logging = wayFromUnits [Logging] parallel :: Way parallel = wayFromUnits [Parallel] -granSim :: Way -granSim = wayFromUnits [GranSim] - -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? -- See compiler/main/DynFlags.hs. From git at git.haskell.org Fri Oct 27 00:02:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to configure. (c6d3c5e) Message-ID: <20171027000251.CC7FD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6d3c5eedbd3257c75b5fbd31fe8cea3dcfa0c05/ghc >--------------------------------------------------------------- commit c6d3c5eedbd3257c75b5fbd31fe8cea3dcfa0c05 Author: Andrey Mokhov Date: Fri Jan 8 03:23:31 2016 +0000 Fix path to configure. See #110. [skip ci] >--------------------------------------------------------------- c6d3c5eedbd3257c75b5fbd31fe8cea3dcfa0c05 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 2a4a628..82cdce4 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,7 +14,7 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - stack exec -- configure --enable-tarballs-autodownload + - stack exec -- ./configure --enable-tarballs-autodownload - ghc --version - stack --version - alex --version From git at git.haskell.org Fri Oct 27 00:02:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move decodeModule to Util.hs. (c1b296a) Message-ID: <20171027000252.D1CFF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1b296ab5dd0d4795ad2c4e86f5a00b2ffa947b7/ghc >--------------------------------------------------------------- commit c1b296ab5dd0d4795ad2c4e86f5a00b2ffa947b7 Author: Andrey Mokhov Date: Thu Aug 6 01:38:54 2015 +0100 Move decodeModule to Util.hs. >--------------------------------------------------------------- c1b296ab5dd0d4795ad2c4e86f5a00b2ffa947b7 src/Settings/Util.hs | 5 ----- src/Util.hs | 7 ++++++- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index c688b5d..13e5be0 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -89,11 +89,6 @@ getHsSources = do return $ foundSources ++ generatedSources --- Given a module name extract the directory and file names, e.g.: --- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") -decodeModule :: String -> (FilePath, String) -decodeModule = splitFileName . replaceEq '.' '/' - -- findModuleFiles scans a list of given directories and finds files matching a -- given extension pattern (e.g., "*hs") that correspond to modules of the -- currently built package. Missing module files are returned in a separate diff --git a/src/Util.hs b/src/Util.hs index f00785f..1c34a87 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,7 +1,7 @@ module Util ( module Data.Char, module System.Console.ANSI, - replaceIf, replaceEq, replaceSeparators, + replaceIf, replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, putColoured, putOracle, putBuild, putError, @@ -22,6 +22,11 @@ replaceEq from = replaceIf (== from) replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator +-- Given a module name extract the directory and file names, e.g.: +-- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +decodeModule :: String -> (FilePath, String) +decodeModule = splitFileName . replaceEq '.' '/' + -- Normalise a path and convert all path separators to /, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx From git at git.haskell.org Fri Oct 27 00:02:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Parallel way unit. (49a7cb2) Message-ID: <20171027000253.34ACD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49a7cb2fb676a1b0a7a9b4235aaa198b9ce0d8db/ghc >--------------------------------------------------------------- commit 49a7cb2fb676a1b0a7a9b4235aaa198b9ce0d8db Author: Andrey Mokhov Date: Tue Feb 16 00:04:46 2016 +0000 Drop Parallel way unit. >--------------------------------------------------------------- 49a7cb2fb676a1b0a7a9b4235aaa198b9ce0d8db src/Settings/Builders/Ghc.hs | 1 - src/Way.hs | 8 +------- 2 files changed, 1 insertion(+), 8 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 96737f4..ef3130f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -101,7 +101,6 @@ wayGhcArgs = do , (Debug `wayUnit` way) ? arg "-optc-DDEBUG" , (Profiling `wayUnit` way) ? arg "-prof" , (Logging `wayUnit` way) ? arg "-eventlog" - , (Parallel `wayUnit` way) ? arg "-parallel" , (way == debug || way == debugDynamic) ? append ["-ticky", "-DTICKY_TICKY"] ] diff --git a/src/Way.hs b/src/Way.hs index 59bbbc9..6d034e9 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, wayFromUnits, - vanilla, profiling, logging, parallel, + vanilla, profiling, logging, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, @@ -26,7 +26,6 @@ data WayUnit = Threaded | Profiling | Logging | Dynamic - | Parallel deriving (Eq, Enum, Bounded) -- TODO: get rid of non-derived Show instances @@ -37,7 +36,6 @@ instance Show WayUnit where Profiling -> "p" Logging -> "l" Dynamic -> "dyn" - Parallel -> "mp" instance Read WayUnit where readsPrec _ s = [(unit, "") | unit <- [minBound ..], show unit == s] @@ -90,10 +88,6 @@ profiling = wayFromUnits [Profiling] logging :: Way logging = wayFromUnits [Logging] --- | Build in parallel. -parallel :: Way -parallel = wayFromUnits [Parallel] - -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? -- See compiler/main/DynFlags.hs. From git at git.haskell.org Fri Oct 27 00:02:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try bash within stack to run configure. (01b7eed) Message-ID: <20171027000255.5DA0A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/01b7eed7be12304e71952ce3345b8244f1c6bd8e/ghc >--------------------------------------------------------------- commit 01b7eed7be12304e71952ce3345b8244f1c6bd8e Author: Andrey Mokhov Date: Fri Jan 8 03:49:14 2016 +0000 Try bash within stack to run configure. See #110. [skip ci] >--------------------------------------------------------------- 01b7eed7be12304e71952ce3345b8244f1c6bd8e .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 82cdce4..c9ec4fd 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,7 +14,7 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - stack exec -- ./configure --enable-tarballs-autodownload + - stack exec -- bash -lc "./configure --enable-tarballs-autodownload" - ghc --version - stack --version - alex --version From git at git.haskell.org Fri Oct 27 00:02:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create Settings/Builders/ directory for keeping builder-related settings. (1ac1688) Message-ID: <20171027000257.15CE13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ac1688ff9c472e99125c1583a7a202946a036b4/ghc >--------------------------------------------------------------- commit 1ac1688ff9c472e99125c1583a7a202946a036b4 Author: Andrey Mokhov Date: Thu Aug 6 01:40:41 2015 +0100 Create Settings/Builders/ directory for keeping builder-related settings. >--------------------------------------------------------------- 1ac1688ff9c472e99125c1583a7a202946a036b4 src/Settings/Args.hs | 14 ++++++++++---- src/Settings/Builders/Ar.hs | 18 ++++++++++++++++++ src/Settings/{ => Builders}/Gcc.hs | 21 ++++++++++++++++++++- src/Settings/{ => Builders}/Ghc.hs | 27 ++++++++++++++++++++++++++- src/Settings/{ => Builders}/GhcCabal.hs | 2 +- src/Settings/{ => Builders}/GhcPkg.hs | 4 ++-- src/Settings/Builders/Ld.hs | 18 ++++++++++++++++++ src/Settings/GccM.hs | 25 ------------------------- src/Settings/GhcM.hs | 33 --------------------------------- 9 files changed, 95 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 1ac1688ff9c472e99125c1583a7a202946a036b4 From git at git.haskell.org Fri Oct 27 00:02:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do not hide Shake.parallel (we no longer have conflicting Way.parallel). (cfb1331) Message-ID: <20171027000257.396753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cfb1331d6c0f338fb3998c6fd3a25759fbd9f4c9/ghc >--------------------------------------------------------------- commit cfb1331d6c0f338fb3998c6fd3a25759fbd9f4c9 Author: Andrey Mokhov Date: Tue Feb 16 00:08:25 2016 +0000 Do not hide Shake.parallel (we no longer have conflicting Way.parallel). >--------------------------------------------------------------- cfb1331d6c0f338fb3998c6fd3a25759fbd9f4c9 src/Base.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 464c1c9..1a06120 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel - module Base ( -- * General utilities module Control.Applicative, @@ -35,7 +33,7 @@ import Data.Function import Data.List.Extra import Data.Maybe import Data.Monoid -import Development.Shake hiding (parallel, unit, (*>), Normal) +import Development.Shake hiding (unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Fri Oct 27 00:02:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring bash configure back. (29ce56c) Message-ID: <20171027000258.E45A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/29ce56c97cc414b2a3e66e4b44dff829a8660a47/ghc >--------------------------------------------------------------- commit 29ce56c97cc414b2a3e66e4b44dff829a8660a47 Author: Andrey Mokhov Date: Fri Jan 8 04:13:50 2016 +0000 Bring bash configure back. See #110. [skip ci] >--------------------------------------------------------------- 29ce56c97cc414b2a3e66e4b44dff829a8660a47 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index c9ec4fd..bb01556 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,7 +14,7 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - stack exec -- bash -lc "./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3f3134cc10b412afc71b7beb80a77ee779ecc3c1/ghc >--------------------------------------------------------------- commit 3f3134cc10b412afc71b7beb80a77ee779ecc3c1 Author: Andrey Mokhov Date: Thu Aug 6 01:41:25 2015 +0100 Add buildPackageLibrary build rule. >--------------------------------------------------------------- 3f3134cc10b412afc71b7beb80a77ee779ecc3c1 src/Rules/Compile.hs | 4 ---- src/Rules/Library.hs | 63 ++++++++++++++++++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 7 +++++- 3 files changed, 69 insertions(+), 5 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 89b60c2..6f57a81 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,10 +12,6 @@ import Rules.Actions import Rules.Resources import Data.Maybe -matchBuildResult :: FilePath -> String -> FilePath -> Bool -matchBuildResult buildPath extension file = - (buildPath "*" ++ extension) ?== file && (isJust . detectWay $ file) - compilePackage :: Resources -> StagePackageTarget -> Rules () compilePackage _ target = do let stage = Target.stage target diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs new file mode 100644 index 0000000..5bd6551 --- /dev/null +++ b/src/Rules/Library.hs @@ -0,0 +1,63 @@ +module Rules.Library (buildPackageLibrary) where + +import Way +import Base +import Util +import Builder +import Switches +import Expression +import qualified Target +import Oracles.PackageData +import Settings.Util +import Settings.TargetDirectory +import Rules.Actions +import Rules.Resources +import Data.Maybe + +buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () +buildPackageLibrary _ target = do + let stage = Target.stage target + pkg = Target.package target + path = targetPath stage pkg + buildPath = path -/- "build" + + matchBuildResult buildPath "a" ?> \a -> do + liftIO $ removeFiles "." [a] + cSrcs <- interpret target $ getPkgDataList CSrcs + modules <- interpret target $ getPkgDataList Modules + + let way = fromJust . detectWay $ a -- fromJust is safe + hsSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] + hsObjs = [ buildPath -/- src <.> osuf way | src <- hsSrcs ] + + need $ cObjs ++ hsObjs -- this will create split objects if required + + splitObjs <- fmap concat $ forM hsSrcs $ \src -> do + let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" + getDirectoryFiles "" [files] + + split <- interpret target splitObjects + let allObjs = if split + then cObjs ++ hsObjs ++ splitObjs + else cObjs ++ hsObjs + + build $ fullTarget target allObjs Ar [a] + +-- ldRule :: Resources -> StagePackageTarget -> Rules () +-- ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) = +-- let pathDist = path dist +-- buildDir = pathDist "build" +-- in +-- priority 2 $ (buildDir "*.o") %> \out -> do +-- cObjs <- pkgCObjects path dist vanilla +-- hObjs <- pkgDepHsObjects path dist vanilla +-- need $ cObjs ++ hObjs +-- run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out +-- synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) +-- putColoured Green $ "/--------\n| Successfully built package '" +-- ++ name ++ "' (stage " ++ show stage ++ ")." +-- putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." +-- ++ "\n\\--------" +-- -- Finally, record the argument list +-- need [argListPath argListDir pkg stage] diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 572fff6..dbbe5cc 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -4,8 +4,13 @@ import Base import Expression import Rules.Data import Rules.Compile +import Rules.Library import Rules.Resources import Rules.Dependencies buildPackage :: Resources -> StagePackageTarget -> Rules () -buildPackage = buildPackageData <> buildPackageDependencies <> compilePackage +buildPackage = mconcat + [ buildPackageData + , buildPackageDependencies + , compilePackage + , buildPackageLibrary ] From git at git.haskell.org Fri Oct 27 00:03:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix separation into full and RTS-only ways, add comments. (799b809) Message-ID: <20171027000301.5AA573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/799b8090941e4c0e9c601890a480511052e36f8f/ghc >--------------------------------------------------------------- commit 799b8090941e4c0e9c601890a480511052e36f8f Author: Andrey Mokhov Date: Tue Feb 16 00:31:32 2016 +0000 Fix separation into full and RTS-only ways, add comments. >--------------------------------------------------------------- 799b8090941e4c0e9c601890a480511052e36f8f src/Way.hs | 42 ++++++++++++++++++++++++------------------ 1 file changed, 24 insertions(+), 18 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 6d034e9..01b18d2 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -76,7 +76,7 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b --- | Build with no 'WayUnit's at all. +-- | Build default _vanilla_ way. vanilla :: Way vanilla = wayFromUnits [] @@ -84,33 +84,39 @@ vanilla = wayFromUnits [] profiling :: Way profiling = wayFromUnits [Profiling] --- | Build with logging. +-- | Build with dynamic linking. +dynamic :: Way +dynamic = wayFromUnits [Dynamic] + +-- RTS only ways. See compiler/main/DynFlags.hs. +-- | Build RTS with event logging. logging :: Way logging = wayFromUnits [Logging] --- RTS only ways --- TODO: do we need to define *only* these? Shall we generalise/simplify? --- See compiler/main/DynFlags.hs. -threaded, threadedProfiling, threadedLogging, debug, debugProfiling, - threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, - threadedProfilingDynamic, threadedDynamic, threadedDebugDynamic, - debugDynamic, loggingDynamic, threadedLoggingDynamic :: Way +-- | Build multithreaded RTS. +threaded :: Way +threaded = wayFromUnits [Threaded] + +-- | Build RTS with debug information. +debug :: Way +debug = wayFromUnits [Debug] -threaded = wayFromUnits [Threaded] +threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, + threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, + threadedLoggingDynamic, debugProfiling, debugDynamic, profilingDynamic, + loggingDynamic :: Way +threadedDebug = wayFromUnits [Threaded, Debug] threadedProfiling = wayFromUnits [Threaded, Profiling] threadedLogging = wayFromUnits [Threaded, Logging] -debug = wayFromUnits [Debug] -debugProfiling = wayFromUnits [Debug, Profiling] -threadedDebug = wayFromUnits [Threaded, Debug] -threadedDebugProfiling = wayFromUnits [Threaded, Debug, Profiling] -dynamic = wayFromUnits [Dynamic] -profilingDynamic = wayFromUnits [Profiling, Dynamic] -threadedProfilingDynamic = wayFromUnits [Threaded, Profiling, Dynamic] threadedDynamic = wayFromUnits [Threaded, Dynamic] +threadedDebugProfiling = wayFromUnits [Threaded, Debug, Profiling] threadedDebugDynamic = wayFromUnits [Threaded, Debug, Dynamic] +threadedProfilingDynamic = wayFromUnits [Threaded, Profiling, Dynamic] +threadedLoggingDynamic = wayFromUnits [Threaded, Logging, Dynamic] +debugProfiling = wayFromUnits [Debug, Profiling] debugDynamic = wayFromUnits [Debug, Dynamic] +profilingDynamic = wayFromUnits [Profiling, Dynamic] loggingDynamic = wayFromUnits [Logging, Dynamic] -threadedLoggingDynamic = wayFromUnits [Threaded, Logging, Dynamic] wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" From git at git.haskell.org Fri Oct 27 00:03:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use mingw64_shell.bat for running scripts. (75063f0) Message-ID: <20171027000302.A1FBC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/75063f04ab2d93494366e80cbc17d02094ac1703/ghc >--------------------------------------------------------------- commit 75063f04ab2d93494366e80cbc17d02094ac1703 Author: Andrey Mokhov Date: Fri Jan 8 16:47:17 2016 +0000 Use mingw64_shell.bat for running scripts. See #110. [skip ci] >--------------------------------------------------------------- 75063f04ab2d93494366e80cbc17d02094ac1703 .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index bb01556..1d4bb53 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -3,7 +3,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" install: - cd - set MSYSTEM=MINGW64 - - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% + - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\bin;C:\msys64;%PATH% - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe @@ -14,7 +14,8 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/83cd6c55ba8eeebe877cc643308435afe3c3d785/ghc >--------------------------------------------------------------- commit 83cd6c55ba8eeebe877cc643308435afe3c3d785 Author: Andrey Mokhov Date: Fri Aug 7 01:07:24 2015 +0100 Handle dyamic libraries in detectWay. >--------------------------------------------------------------- 83cd6c55ba8eeebe877cc643308435afe3c3d785 src/Way.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 365a949..3046867 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -126,15 +126,21 @@ libsuf way @ (Way set) = return $ prefix ++ "ghc" ++ version ++ extension -- Detect way from a given filename. Returns Nothing if there is no match: --- * detectWay "foo/bar.hi" == Just vanilla --- * detectWay "baz.thr_p_o" == Just threadedProfiling --- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +-- * detectWay "foo/bar.hi" == Just vanilla +-- * detectWay "baz.thr_p_o" == Just threadedProfiling +-- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +-- * detectWay "xru.p_ghc7.11.20141222.dll" == Just profiling detectWay :: FilePath -> Maybe Way detectWay file = case reads prefix of [(way, "")] -> Just way _ -> Nothing where - prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ takeExtension file + extension = takeExtension file + prefixed = if extension `notElem` ["so", "dll", "dynlib"] + then extension + else takeExtension . dropExtension . + dropExtension . dropExtension $ file + prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed -- Given a path, an extension suffix, and a file name check if the latter: -- 1) conforms to pattern 'path//*suffix' From git at git.haskell.org Fri Oct 27 00:03:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move profilingDynamic to full ways. (3c88f16) Message-ID: <20171027000305.8C47A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c88f16cf2ff282481a06abcf0ad839abe1c5fab/ghc >--------------------------------------------------------------- commit 3c88f16cf2ff282481a06abcf0ad839abe1c5fab Author: Andrey Mokhov Date: Tue Feb 16 00:44:44 2016 +0000 Move profilingDynamic to full ways. >--------------------------------------------------------------- 3c88f16cf2ff282481a06abcf0ad839abe1c5fab src/Settings/Ways.hs | 1 + src/Way.hs | 11 +++++++---- 2 files changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 223bc79..0fee897 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -13,6 +13,7 @@ getLibraryWays = fromDiffExpr $ defaultLibraryWays <> userLibraryWays getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays +-- TODO: what about profilingDynamic way? Do we need platformSupportsSharedLibs? -- These are default ways for library packages: -- * We always build 'vanilla' way. -- * We build 'profiling' way when stage > Stage0. diff --git a/src/Way.hs b/src/Way.hs index 01b18d2..b297e79 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -88,7 +88,11 @@ profiling = wayFromUnits [Profiling] dynamic :: Way dynamic = wayFromUnits [Dynamic] --- RTS only ways. See compiler/main/DynFlags.hs. +-- | Build with profiling and dynamic linking. +profilingDynamic :: Way +profilingDynamic = wayFromUnits [Profiling, Dynamic] + +-- RTS only ways below. See compiler/main/DynFlags.hs. -- | Build RTS with event logging. logging :: Way logging = wayFromUnits [Logging] @@ -101,10 +105,10 @@ threaded = wayFromUnits [Threaded] debug :: Way debug = wayFromUnits [Debug] +-- | Various combinations of RTS only ways. threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, - threadedLoggingDynamic, debugProfiling, debugDynamic, profilingDynamic, - loggingDynamic :: Way + threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic :: Way threadedDebug = wayFromUnits [Threaded, Debug] threadedProfiling = wayFromUnits [Threaded, Profiling] threadedLogging = wayFromUnits [Threaded, Logging] @@ -115,7 +119,6 @@ threadedProfilingDynamic = wayFromUnits [Threaded, Profiling, Dynamic] threadedLoggingDynamic = wayFromUnits [Threaded, Logging, Dynamic] debugProfiling = wayFromUnits [Debug, Profiling] debugDynamic = wayFromUnits [Debug, Dynamic] -profilingDynamic = wayFromUnits [Profiling, Dynamic] loggingDynamic = wayFromUnits [Logging, Dynamic] wayPrefix :: Way -> String From git at git.haskell.org Fri Oct 27 00:03:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to use get-win32-tarballs.sh. (4a625f8) Message-ID: <20171027000306.765DB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a625f8aa2358597281a6b2633fdb40f9f8c2707/ghc >--------------------------------------------------------------- commit 4a625f8aa2358597281a6b2633fdb40f9f8c2707 Author: Andrey Mokhov Date: Fri Jan 8 17:03:55 2016 +0000 Try to use get-win32-tarballs.sh. See #110. [skip ci] >--------------------------------------------------------------- 4a625f8aa2358597281a6b2633fdb40f9f8c2707 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 1d4bb53..f0014e3 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,8 +14,8 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - mingw64_shell.bat "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fafec426576d246a2deedb6875258eefcc55a4ee/ghc >--------------------------------------------------------------- commit fafec426576d246a2deedb6875258eefcc55a4ee Author: Andrey Mokhov Date: Fri Aug 7 02:56:02 2015 +0100 Fix detectWay and way parsing. >--------------------------------------------------------------- fafec426576d246a2deedb6875258eefcc55a4ee src/Way.hs | 21 +++++++++++++-------- 1 file changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 3046867..4d14025 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -29,7 +29,7 @@ data WayUnit = Threaded | Dynamic | Parallel | GranSim - deriving Enum + deriving (Eq, Enum) instance Show WayUnit where show unit = case unit of @@ -61,10 +61,15 @@ instance Show Way where tag = intercalate "_" . map show . wayToUnits $ way instance Read Way where - readsPrec _ s = - if s == "v" - then [(vanilla, "")] - else [(wayFromUnits . map read . words . replaceEq '_' ' ' $ s, "")] + readsPrec _ s = if s == "v" then [(vanilla, "")] else result + where + uniqueReads token = case reads token of + [(unit, "")] -> Just unit + _ -> Nothing + units = map uniqueReads . words . replaceEq '_' ' ' $ s + result = if Nothing `elem` units + then [] + else [(wayFromUnits . map fromJust $ units, "")] instance Eq Way where Way a == Way b = a == b @@ -128,7 +133,7 @@ libsuf way @ (Way set) = -- Detect way from a given filename. Returns Nothing if there is no match: -- * detectWay "foo/bar.hi" == Just vanilla -- * detectWay "baz.thr_p_o" == Just threadedProfiling --- * detectWay "qwe.phi" == Nothing (expected "qwe.p_hi") +-- * detectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") -- * detectWay "xru.p_ghc7.11.20141222.dll" == Just profiling detectWay :: FilePath -> Maybe Way detectWay file = case reads prefix of @@ -136,11 +141,11 @@ detectWay file = case reads prefix of _ -> Nothing where extension = takeExtension file - prefixed = if extension `notElem` ["so", "dll", "dynlib"] + prefixed = if extension `notElem` [".so", ".dll", ".dynlib"] then extension else takeExtension . dropExtension . dropExtension . dropExtension $ file - prefix = dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed + prefix = drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed -- Given a path, an extension suffix, and a file name check if the latter: -- 1) conforms to pattern 'path//*suffix' From git at git.haskell.org Fri Oct 27 00:03:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add allWays. (575d82f) Message-ID: <20171027000309.9C8713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/575d82fe621956b8a6c293eb381a19896aed2366/ghc >--------------------------------------------------------------- commit 575d82fe621956b8a6c293eb381a19896aed2366 Author: Andrey Mokhov Date: Tue Feb 16 00:53:44 2016 +0000 Add allWays. >--------------------------------------------------------------- 575d82fe621956b8a6c293eb381a19896aed2366 src/Way.hs | 22 ++++++++++++++-------- 1 file changed, 14 insertions(+), 8 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index b297e79..668ed63 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,14 +1,12 @@ module Way ( WayUnit (..), Way, wayUnit, wayFromUnits, - vanilla, profiling, logging, - threaded, threadedProfiling, threadedLogging, - debug, debugProfiling, threadedDebug, threadedDebugProfiling, - dynamic, profilingDynamic, threadedProfilingDynamic, - threadedDynamic, threadedDebugDynamic, debugDynamic, - loggingDynamic, threadedLoggingDynamic, - - wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, + vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging, + threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, + threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, + threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic, + + allWays, wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, safeDetectWay, detectWay, matchBuildResult ) where @@ -121,6 +119,14 @@ debugProfiling = wayFromUnits [Debug, Profiling] debugDynamic = wayFromUnits [Debug, Dynamic] loggingDynamic = wayFromUnits [Logging, Dynamic] +-- | All ways supported by the build system. +allWays :: [Way] +allWays = + [ vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging + , threadedDebug, threadedProfiling, threadedLogging, threadedDynamic + , threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic + , threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic ] + wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" From git at git.haskell.org Fri Oct 27 00:03:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create ghc-tarballs/mingw-w64/x86_64/ directory. (b3382b9) Message-ID: <20171027000310.442C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3382b95c0fc6385df7c33a6e84fa62b207b75ab/ghc >--------------------------------------------------------------- commit b3382b95c0fc6385df7c33a6e84fa62b207b75ab Author: Andrey Mokhov Date: Fri Jan 8 17:12:33 2016 +0000 Create ghc-tarballs/mingw-w64/x86_64/ directory. See #110. [skip ci] >--------------------------------------------------------------- b3382b95c0fc6385df7c33a6e84fa62b207b75ab .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f0014e3..1d3b7c5 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,8 +14,8 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - bash -lc "cd /home/ghc; ./mk/get-win32-tarballs.sh download x86_64" - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a6623ab5988c2705b22e8a5157db013595f634ce/ghc >--------------------------------------------------------------- commit a6623ab5988c2705b22e8a5157db013595f634ce Author: Andrey Mokhov Date: Fri Aug 7 02:56:33 2015 +0100 Add putSuccess helper function. >--------------------------------------------------------------- a6623ab5988c2705b22e8a5157db013595f634ce src/Util.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 1c34a87..7a68b2a 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -4,7 +4,7 @@ module Util ( replaceIf, replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, - putColoured, putOracle, putBuild, putError, + putColoured, putOracle, putBuild, putSuccess, putError, bimap, minusOrd, intersectOrd ) where @@ -69,6 +69,12 @@ putBuild :: String -> Action () putBuild = putColoured White -- A more colourful version of error +putSuccess :: String -> Action a +putSuccess msg = do + putColoured Green msg + error $ "GHC build system error: " ++ msg + +-- A more colourful version of error putError :: String -> Action a putError msg = do putColoured Red msg From git at git.haskell.org Fri Oct 27 00:03:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass way to compilePackage via Context. (23d501a) Message-ID: <20171027000313.573A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23d501a474266920e395e60d4d6c69369785608f/ghc >--------------------------------------------------------------- commit 23d501a474266920e395e60d4d6c69369785608f Author: Andrey Mokhov Date: Tue Feb 16 02:24:35 2016 +0000 Pass way to compilePackage via Context. See #207. >--------------------------------------------------------------- 23d501a474266920e395e60d4d6c69369785608f src/Rules.hs | 10 +++++++--- src/Rules/Compile.hs | 37 ++++++++++++++----------------------- 2 files changed, 21 insertions(+), 26 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index e12fc1c..f765b5e 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -3,6 +3,7 @@ module Rules (topLevelTargets, buildRules) where import Data.Foldable import Base +import Context hiding (stage, package, way) import Expression import GHC import Rules.Compile @@ -52,18 +53,21 @@ topLevelTargets = do packageRules :: Rules () packageRules = do - -- We cannot register multiple packages in parallel. Also we cannot run GHC - -- when the package database is being mutated by "ghc-pkg". This is a + -- We cannot register multiple GHC packages in parallel. Also we cannot run + -- GHC when the package database is being mutated by "ghc-pkg". This is a -- classic concurrent read exclusive write (CREW) conflict. let maxConcurrentReaders = 1000 packageDb <- newResource "package-db" maxConcurrentReaders let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] + let contexts = liftM3 Context allStages knownPackages allWays + + traverse_ (compilePackage readPackageDb) contexts + for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package - compilePackage readPackageDb context buildPackageData context buildPackageDependencies readPackageDb context buildPackageDocumentation context diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index b583f5a..14e71ee 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -9,52 +9,43 @@ import Rules.Actions import Settings import Target hiding (context) --- TODO: Use way from Context, #207 compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" - matchBuildResult buildPath "hi" ?> \hi -> + buildPath "*" <.> hisuf way %> \hi -> if compileInterfaceFilesSeparately && not ("//HpcParser.*" ?== hi) then do - let w = detectWay hi - (src, deps) <- dependencies buildPath $ hi -<.> osuf w + (src, deps) <- dependencies buildPath $ hi -<.> osuf way need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [hi] - else need [ hi -<.> osuf (detectWay hi) ] + buildWithResources rs $ Target context (Ghc stage) [src] [hi] + else need [ hi -<.> osuf way ] - matchBuildResult buildPath "hi-boot" ?> \hiboot -> + buildPath "*" <.> hibootsuf way %> \hiboot -> if compileInterfaceFilesSeparately then do - let w = detectWay hiboot - (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf w + (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf way need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [hiboot] - else need [ hiboot -<.> obootsuf (detectWay hiboot) ] + buildWithResources rs $ Target context (Ghc stage) [src] [hiboot] + else need [ hiboot -<.> obootsuf way ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) - matchBuildResult buildPath "o" ?> \obj -> do + buildPath "*" <.> osuf way %> \obj -> do (src, deps) <- dependencies buildPath obj if ("//*.c" ?== src) then do need $ src : deps build $ Target context (Gcc stage) [src] [obj] else do - let w = detectWay obj if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) - then need $ (obj -<.> hisuf (detectWay obj)) : src : deps + then need $ (obj -<.> hisuf way) : src : deps else need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [obj] + buildWithResources rs $ Target context (Ghc stage) [src] [obj] -- TODO: get rid of these special cases - matchBuildResult buildPath "o-boot" ?> \obj -> do + buildPath "*" <.> obootsuf way %> \obj -> do (src, deps) <- dependencies buildPath obj - let w = detectWay obj if compileInterfaceFilesSeparately - then need $ (obj -<.> hibootsuf (detectWay obj)) : src : deps + then need $ (obj -<.> hibootsuf way) : src : deps else need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [obj] + buildWithResources rs $ Target context (Ghc stage) [src] [obj] From git at git.haskell.org Fri Oct 27 00:03:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix unnecessary import hiding (988dabb) Message-ID: <20171027000314.346D23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/988dabb35a239fa8dd799de5951acf55786bc0ee/ghc >--------------------------------------------------------------- commit 988dabb35a239fa8dd799de5951acf55786bc0ee Author: David Luposchainsky Date: Fri Jan 8 18:23:46 2016 +0100 Fix unnecessary import hiding >--------------------------------------------------------------- 988dabb35a239fa8dd799de5951acf55786bc0ee src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 05686e0..925c427 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -34,7 +34,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>), parallel) +import Development.Shake hiding (unit, (*>)) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Fri Oct 27 00:03:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add library targets. (e3e3c1d) Message-ID: <20171027000316.94B693A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3e3c1d6e03c1fd46af44afd5e29e7b1a4000093/ghc >--------------------------------------------------------------- commit e3e3c1d6e03c1fd46af44afd5e29e7b1a4000093 Author: Andrey Mokhov Date: Fri Aug 7 02:57:05 2015 +0100 Add library targets. >--------------------------------------------------------------- e3e3c1d6e03c1fd46af44afd5e29e7b1a4000093 src/Rules.hs | 22 +++++++++++++++++++--- 1 file changed, 19 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index be109f8..2509cf7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -2,15 +2,19 @@ module Rules ( oracleRules, cabalRules, configRules, packageRules, generateTargets ) where +import Way import Base import Util import Stage import Expression +import Oracles.PackageData import Rules.Cabal import Rules.Config import Rules.Package import Rules.Oracles import Rules.Resources +import Settings.Ways +import Settings.Util import Settings.Packages import Settings.TargetDirectory @@ -19,9 +23,21 @@ generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpret (stageTarget stage) getPackages - fmap concat . forM pkgs $ \pkg -> return - [ targetPath stage pkg -/- "build/haskell.deps" - , targetPath stage pkg -/- "build/c.deps" ] + fmap concat . forM pkgs $ \pkg -> do + let target = stagePackageTarget stage pkg + buildPath = targetPath stage pkg -/- "build" + buildGhciLib <- interpret target $ getPkgData BuildGhciLib + pkgKey <- interpret target $ getPkgData PackageKey + let ghciLib = [ buildPath -/- "HS" ++ pkgKey <.> "o" + | buildGhciLib == "YES" && stage /= Stage0 ] + + ways <- interpret target getWays + libs <- forM ways $ \way -> do + extension <- libsuf way + return $ buildPath -/- "libHS" ++ pkgKey <.> extension + + return $ ghciLib ++ libs + need targets -- TODO: add Stage2 (compiler only?) From git at git.haskell.org Fri Oct 27 00:03:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop workaround for GHC bug #11331. (8478284) Message-ID: <20171027000317.0FACA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84782844c149c729e5277f79ee80c8001f05c095/ghc >--------------------------------------------------------------- commit 84782844c149c729e5277f79ee80c8001f05c095 Author: Andrey Mokhov Date: Tue Feb 16 02:26:08 2016 +0000 Drop workaround for GHC bug #11331. See #174. >--------------------------------------------------------------- 84782844c149c729e5277f79ee80c8001f05c095 src/Rules/Compile.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 14e71ee..a52edef 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -14,7 +14,7 @@ compilePackage rs context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" buildPath "*" <.> hisuf way %> \hi -> - if compileInterfaceFilesSeparately && not ("//HpcParser.*" ?== hi) + if compileInterfaceFilesSeparately then do (src, deps) <- dependencies buildPath $ hi -<.> osuf way need $ src : deps @@ -37,7 +37,7 @@ compilePackage rs context @ (Context {..}) = do need $ src : deps build $ Target context (Gcc stage) [src] [obj] else do - if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) + if compileInterfaceFilesSeparately && "//*.hs" ?== src then need $ (obj -<.> hisuf way) : src : deps else need $ src : deps buildWithResources rs $ Target context (Ghc stage) [src] [obj] From git at git.haskell.org Fri Oct 27 00:03:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #136 from quchen/redundant-hiding (4116dbd) Message-ID: <20171027000317.D2D0A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4116dbdd0c3407fac56a101e2592240411108c86/ghc >--------------------------------------------------------------- commit 4116dbdd0c3407fac56a101e2592240411108c86 Merge: b3382b9 988dabb Author: Andrey Mokhov Date: Fri Jan 8 17:29:30 2016 +0000 Merge pull request #136 from quchen/redundant-hiding Fix unnecessary import hiding of "parallel" [skip ci] >--------------------------------------------------------------- 4116dbdd0c3407fac56a101e2592240411108c86 src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:03:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for BUILD_GHCI_LIB field of package-data.mk. (85808dd) Message-ID: <20171027000320.9D0EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/85808dd149afdb17d34f9e877029bc8c50020b63/ghc >--------------------------------------------------------------- commit 85808dd149afdb17d34f9e877029bc8c50020b63 Author: Andrey Mokhov Date: Fri Aug 7 02:57:44 2015 +0100 Add support for BUILD_GHCI_LIB field of package-data.mk. >--------------------------------------------------------------- 85808dd149afdb17d34f9e877029bc8c50020b63 src/Oracles/PackageData.hs | 14 ++++++++------ 1 file changed, 8 insertions(+), 6 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index c01c87f..de9db7c 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -20,9 +20,10 @@ import qualified Data.HashMap.Strict as Map -- PackageDataList is used for multiple string options separated by spaces, -- such as 'path_MODULES = Data.Array Data.Array.Base ...'. -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] -data PackageData = Version FilePath - | PackageKey FilePath - | Synopsis FilePath +data PackageData = Version FilePath + | PackageKey FilePath + | Synopsis FilePath + | BuildGhciLib FilePath data PackageDataList = Modules FilePath | SrcDirs FilePath @@ -51,9 +52,10 @@ askPackageData path key = do pkgData :: PackageData -> Action String pkgData packageData = do let (key, path) = case packageData of - Version path -> ("VERSION" , path) - PackageKey path -> ("PACKAGE_KEY" , path) - Synopsis path -> ("SYNOPSIS" , path) + Version path -> ("VERSION" , path) + PackageKey path -> ("PACKAGE_KEY" , path) + Synopsis path -> ("SYNOPSIS" , path) + BuildGhciLib path -> ("BUILD_GHCI_LIB", path) fullKey = replaceSeparators '_' $ path ++ "_" ++ key pkgData = path -/- "package-data.mk" res <- askOracle $ PackageDataKey (pkgData, fullKey) From git at git.haskell.org Fri Oct 27 00:03:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (0ddf3b4) Message-ID: <20171027000320.C98C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ddf3b4d341a31ce66d78b5c840b2e55929ab5e3/ghc >--------------------------------------------------------------- commit 0ddf3b4d341a31ce66d78b5c840b2e55929ab5e3 Author: Andrey Mokhov Date: Tue Feb 16 02:40:38 2016 +0000 Minor revision. See #207. >--------------------------------------------------------------- 0ddf3b4d341a31ce66d78b5c840b2e55929ab5e3 src/Rules.hs | 7 ++++--- src/Rules/Compile.hs | 2 +- src/Rules/Dependencies.hs | 9 ++++----- 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index f765b5e..a3d67cb 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -61,15 +61,16 @@ packageRules = do let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] - let contexts = liftM3 Context allStages knownPackages allWays + let contexts = liftM3 Context allStages knownPackages allWays + vanillaContexts = liftM2 vanillaContext allStages knownPackages - traverse_ (compilePackage readPackageDb) contexts + traverse_ (compilePackage readPackageDb) contexts + traverse_ (buildPackageDependencies readPackageDb) vanillaContexts for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package buildPackageData context - buildPackageDependencies readPackageDb context buildPackageDocumentation context generatePackageCode context buildPackageLibrary context diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index a52edef..f62c644 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -7,7 +7,7 @@ import Expression import Oracles.Dependencies import Rules.Actions import Settings -import Target hiding (context) +import Target compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context @ (Context {..}) = do diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 45a8f8c..330c821 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -19,7 +19,7 @@ buildPackageDependencies rs context @ (Context {..}) = dropBuild = (pkgPath package ++) . drop (length buildPath) hDepFile = buildPath -/- ".hs-dependencies" in do - fmap (buildPath++) + fmap (buildPath ++) [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do let srcFile = if "//AutoApply.*" ?== out then dropExtension out @@ -32,19 +32,18 @@ buildPackageDependencies rs context @ (Context {..}) = need srcs if srcs == [] then writeFileChanged out "" - else buildWithResources rs $ - Target context (GhcM stage) srcs [out] + else buildWithResources rs $ Target context (GhcM stage) srcs [out] removeFileIfExists $ out <.> "bak" -- TODO: don't accumulate *.deps into .dependencies - (buildPath -/- ".dependencies") %> \out -> do + buildPath -/- ".dependencies" %> \out -> do cSrcs <- pkgDataList $ CSrcs path let cDepFiles = [ buildPath -/- src <.> "deps" | src <- cSrcs , not ("//AutoApply.cmm" ?== src) ] ++ [ src <.> "deps" | src <- cSrcs, "//AutoApply.cmm" ?== src ] need $ hDepFile : cDepFiles -- need all for more parallelism - cDeps <- fmap concat $ mapM readFile' cDepFiles + cDeps <- fmap concat $ traverse readFile' cDepFiles hDeps <- readFile' hDepFile let result = unlines . map (\(src, deps) -> unwords $ src : deps) From git at git.haskell.org Fri Oct 27 00:03:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create ghc-tarballs/perl folder. (eab9a54) Message-ID: <20171027000321.E4D6A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eab9a54f888dba48e8975bca1140c5f6dbdef3e2/ghc >--------------------------------------------------------------- commit eab9a54f888dba48e8975bca1140c5f6dbdef3e2 Author: Andrey Mokhov Date: Fri Jan 8 18:32:47 2016 +0000 Create ghc-tarballs/perl folder. See #110. [skip ci] >--------------------------------------------------------------- eab9a54f888dba48e8975bca1140c5f6dbdef3e2 .appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.appveyor.yml b/.appveyor.yml index 1d3b7c5..7c724b8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -15,6 +15,7 @@ install: - cd C:\msys64\home\ghc - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" + - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/020d528e4a296e264bee478f3d89b63d6bb1f0b9/ghc >--------------------------------------------------------------- commit 020d528e4a296e264bee478f3d89b63d6bb1f0b9 Author: Andrey Mokhov Date: Fri Aug 7 02:58:15 2015 +0100 Implement build rule for GHCI libraries. >--------------------------------------------------------------- 020d528e4a296e264bee478f3d89b63d6bb1f0b9 src/Rules/Library.hs | 53 +++++++++++++++++++-------------------- src/Settings/Builders/GhcCabal.hs | 1 + 2 files changed, 27 insertions(+), 27 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 5bd6551..c788edb 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -4,6 +4,7 @@ import Way import Base import Util import Builder +import Package import Switches import Expression import qualified Target @@ -12,6 +13,7 @@ import Settings.Util import Settings.TargetDirectory import Rules.Actions import Rules.Resources +import Data.List import Data.Maybe buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () @@ -21,6 +23,7 @@ buildPackageLibrary _ target = do path = targetPath stage pkg buildPath = path -/- "build" + -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do liftIO $ removeFiles "." [a] cSrcs <- interpret target $ getPkgDataList CSrcs @@ -33,31 +36,27 @@ buildPackageLibrary _ target = do need $ cObjs ++ hsObjs -- this will create split objects if required - splitObjs <- fmap concat $ forM hsSrcs $ \src -> do - let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" - getDirectoryFiles "" [files] - split <- interpret target splitObjects - let allObjs = if split - then cObjs ++ hsObjs ++ splitObjs - else cObjs ++ hsObjs - - build $ fullTarget target allObjs Ar [a] - --- ldRule :: Resources -> StagePackageTarget -> Rules () --- ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) = --- let pathDist = path dist --- buildDir = pathDist "build" --- in --- priority 2 $ (buildDir "*.o") %> \out -> do --- cObjs <- pkgCObjects path dist vanilla --- hObjs <- pkgDepHsObjects path dist vanilla --- need $ cObjs ++ hObjs --- run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out --- synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist) --- putColoured Green $ "/--------\n| Successfully built package '" --- ++ name ++ "' (stage " ++ show stage ++ ")." --- putColoured Green $ "| Package synopsis: " ++ synopsis ++ "." --- ++ "\n\\--------" --- -- Finally, record the argument list --- need [argListPath argListDir pkg stage] + splitObjs <- if split + then fmap concat $ forM hsSrcs $ \src -> do + let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" + getDirectoryFiles "" [files] + else return [] + + build $ fullTarget target (cObjs ++ hsObjs ++ splitObjs) Ar [a] + + synopsis <- interpret target $ getPkgData Synopsis + putSuccess $ "/--------\n| Successfully built package '" + ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + putSuccess $ "| Package synopsis: " + ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" + + -- TODO: this looks fragile as haskell objects can match this rule if their + -- names start with "HS" and they are on top of the module hierarchy. + (buildPath -/- "HS*.o") %> \o -> do + cSrcs <- interpret target $ getPkgDataList CSrcs + modules <- interpret target $ getPkgDataList Modules + let hsSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] + hsObjs = [ buildPath -/- src <.> "o" | src <- hsSrcs ] + build $ fullTarget target (cObjs ++ hsObjs) Ld [o] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 301791d..6969aec 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -39,6 +39,7 @@ cabalArgs = builder GhcCabal ? do , with Happy ] -- TODO: Isn't vanilla always built? If yes, some conditions are redundant. +-- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do ways <- getWays From git at git.haskell.org Fri Oct 27 00:05:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Export Data.List.Extra from Base, rather than importing Extra in each module (seems to fit with the general style) (b9c6d43) Message-ID: <20171027000542.94F4B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b9c6d43718f66950024abb1212bb7fb0de1e8090/ghc >--------------------------------------------------------------- commit b9c6d43718f66950024abb1212bb7fb0de1e8090 Author: Neil Mitchell Date: Sat Jan 9 21:47:34 2016 +0000 Export Data.List.Extra from Base, rather than importing Extra in each module (seems to fit with the general style) >--------------------------------------------------------------- b9c6d43718f66950024abb1212bb7fb0de1e8090 src/Base.hs | 4 ++-- src/Oracles/LookupInPath.hs | 1 - src/Rules/Data.hs | 1 - src/Rules/Libffi.hs | 1 - src/Rules/Library.hs | 2 +- 5 files changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 65a2d1d..a428c2c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -3,7 +3,7 @@ module Base ( module Control.Applicative, module Control.Monad.Extra, module Data.Function, - module Data.List, + module Data.List.Extra, module Data.Maybe, module Data.Monoid, MonadTrans(lift), @@ -31,7 +31,7 @@ import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader import Data.Function -import Data.List +import Data.List.Extra import Data.Maybe import Data.Monoid import Development.Shake hiding (unit, (*>)) diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 2532cb9..d573fd7 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -4,7 +4,6 @@ module Oracles.LookupInPath ( ) where import Base -import Extra (wordsBy) newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index d6f46a6..8b21fc7 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -2,7 +2,6 @@ module Rules.Data (buildPackageData) where import Base import Expression -import Extra (replace) import GHC import Oracles import Predicates (registerPackage) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 31f249b..9d77814 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -2,7 +2,6 @@ module Rules.Libffi (libffiRules, libffiDependencies) where import Base import Expression -import Extra (replace) import GHC import Oracles import Rules.Actions diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 46f3971..ba20034 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -2,7 +2,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Data.Char -import Base hiding (splitPath) +import Base hiding (splitPath, split) import Expression import GHC import Oracles From git at git.haskell.org Fri Oct 27 00:05:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (e2fbf4c) Message-ID: <20171027000544.39ADC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2fbf4c8b06e6e9692473dca31b390fe30953256/ghc >--------------------------------------------------------------- commit e2fbf4c8b06e6e9692473dca31b390fe30953256 Author: Andrey Mokhov Date: Fri Feb 26 12:09:40 2016 +0000 Add comments. See #210. >--------------------------------------------------------------- e2fbf4c8b06e6e9692473dca31b390fe30953256 src/Oracles/ModuleFiles.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 508b554..5cb7a5b 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -101,6 +101,8 @@ moduleFilesOracle = void $ do ++ f1 ++ " and " ++ f2 ++ "." return $ lookupAll modules pairs + -- Optimisation: we discard .(l)hs files here, because they are never used + -- as generators, and hence would be discarded in 'findGenerator' anyway. gens <- newCache $ \context -> do files <- contextFiles context return $ Map.fromList [ (generatedFile context modName, src) From git at git.haskell.org Fri Oct 27 00:05:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add PartialTarget, handle GHC.Prim module in a special way. (aabc5a6) Message-ID: <20171027000546.5E3683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aabc5a6ef5968dd14eb67c5cce6d50257c1288ae/ghc >--------------------------------------------------------------- commit aabc5a6ef5968dd14eb67c5cce6d50257c1288ae Author: Andrey Mokhov Date: Fri Aug 21 22:14:48 2015 +0100 Add PartialTarget, handle GHC.Prim module in a special way. >--------------------------------------------------------------- aabc5a6ef5968dd14eb67c5cce6d50257c1288ae src/Expression.hs | 47 ++++++++++++++++++++-------------- src/Oracles/ArgsHash.hs | 2 +- src/Rules.hs | 19 +++++++------- src/Rules/Actions.hs | 11 ++++---- src/Rules/Cabal.hs | 4 +-- src/Rules/Compile.hs | 11 +++----- src/Rules/Data.hs | 14 +++++------ src/Rules/Dependencies.hs | 12 ++++----- src/Rules/Documentation.hs | 14 +++++------ src/Rules/Library.hs | 39 +++++++++++++++------------- src/Rules/Package.hs | 3 ++- src/Target.hs | 63 ++++++++++++++++------------------------------ 12 files changed, 112 insertions(+), 127 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 aabc5a6ef5968dd14eb67c5cce6d50257c1288ae From git at git.haskell.org Fri Oct 27 00:05:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use splitOn to parse the Way (9ae96f4) Message-ID: <20171027000546.CA0B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ae96f4017f3d11da5684a15b0a6b4e10c182dd9/ghc >--------------------------------------------------------------- commit 9ae96f4017f3d11da5684a15b0a6b4e10c182dd9 Author: Neil Mitchell Date: Sat Jan 9 21:47:47 2016 +0000 Use splitOn to parse the Way >--------------------------------------------------------------- 9ae96f4017f3d11da5684a15b0a6b4e10c182dd9 src/Way.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Way.hs b/src/Way.hs index 94a3bcc..5b24662 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -72,7 +72,7 @@ instance Read Way where uniqueReads token = case reads token of [(unit, "")] -> Just unit _ -> Nothing - units = map uniqueReads . words . replaceEq '_' ' ' $ s + units = map uniqueReads . splitOn "_" $ s result = if Nothing `elem` units then [] else [(wayFromUnits . map fromJust $ units, "")] From git at git.haskell.org Fri Oct 27 00:05:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use (Stage, Package) as the key for moduleFilesOracle. (39f61a4) Message-ID: <20171027000547.ADD923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39f61a41680e0abcf2cfe185f6115213b1dbc649/ghc >--------------------------------------------------------------- commit 39f61a41680e0abcf2cfe185f6115213b1dbc649 Author: Andrey Mokhov Date: Fri Feb 26 13:35:33 2016 +0000 Use (Stage, Package) as the key for moduleFilesOracle. See #210. >--------------------------------------------------------------- 39f61a41680e0abcf2cfe185f6115213b1dbc649 src/Oracles/ModuleFiles.hs | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 5cb7a5b..96e66ac 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -11,10 +11,10 @@ import Expression import Oracles.PackageData import Settings.Paths -newtype ModuleFilesKey = ModuleFilesKey Context +newtype ModuleFilesKey = ModuleFilesKey (Stage, Package) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -newtype Generator = Generator (Context, FilePath) +newtype Generator = Generator (Stage, Package, FilePath) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- The following generators and corresponding source extensions are supported: @@ -34,8 +34,8 @@ determineBuilder file = case takeExtension file of -- ".build/stage1/base/build/Prelude.hs" -- == Nothing findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder)) -findGenerator context file = do - maybeSource <- askOracle $ Generator (context, file) +findGenerator Context {..} file = do + maybeSource <- askOracle $ Generator (stage, package, file) return $ do source <- maybeSource builder <- determineBuilder source @@ -62,7 +62,7 @@ contextFiles :: Context -> Action [(String, Maybe FilePath)] contextFiles context at Context {..} = do let path = contextPath context modules <- fmap sort . pkgDataList $ Modules path - zip modules <$> askOracle (ModuleFilesKey context) + zip modules <$> askOracle (ModuleFilesKey (stage, package)) -- | This is an important oracle whose role is to find and cache module source -- files. It takes a 'Context', looks up corresponding source directories @dirs@ @@ -77,12 +77,12 @@ contextFiles context at Context {..} = do -- Just "compiler/parser/Lexer.x"]. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do - void $ addOracle $ \(ModuleFilesKey context) -> do - let path = contextPath context + void $ addOracle $ \(ModuleFilesKey (stage, package)) -> do + let path = contextPath $ vanillaContext stage package autogen = path -/- "build/autogen" srcDirs <- pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - let dirs = autogen : map (pkgPath (package context) -/-) srcDirs + let dirs = autogen : map (pkgPath package -/-) srcDirs modDirFiles = groupSort $ map decodeModule modules result <- fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles @@ -103,10 +103,12 @@ moduleFilesOracle = void $ do -- Optimisation: we discard .(l)hs files here, because they are never used -- as generators, and hence would be discarded in 'findGenerator' anyway. - gens <- newCache $ \context -> do + generators <- newCache $ \(stage, package) -> do + let context = vanillaContext stage package files <- contextFiles context return $ Map.fromList [ (generatedFile context modName, src) | (modName, Just src) <- files , takeExtension src `notElem` [".hs", ".lhs"] ] - addOracle $ \(Generator (context, file)) -> Map.lookup file <$> gens context + addOracle $ \(Generator (stage, package, file)) -> + Map.lookup file <$> generators (stage, package) From git at git.haskell.org Fri Oct 27 00:05:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Switches.hs to Predicates.hs. (47764c0) Message-ID: <20171027000550.397603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47764c0eaedab75e54c0209ef117ddb0280d05b2/ghc >--------------------------------------------------------------- commit 47764c0eaedab75e54c0209ef117ddb0280d05b2 Author: Andrey Mokhov Date: Fri Aug 21 22:23:05 2015 +0100 Rename Switches.hs to Predicates.hs. >--------------------------------------------------------------- 47764c0eaedab75e54c0209ef117ddb0280d05b2 src/{Switches.hs => Predicates.hs} | 2 +- src/Rules/Data.hs | 2 +- src/Rules/Library.hs | 2 +- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Gcc.hs | 2 +- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Builders/Ld.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/User.hs | 2 +- src/Settings/Util.hs | 2 +- src/Settings/Ways.hs | 2 +- 14 files changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Switches.hs b/src/Predicates.hs similarity index 98% rename from src/Switches.hs rename to src/Predicates.hs index c30a33f..0dfa8db 100644 --- a/src/Switches.hs +++ b/src/Predicates.hs @@ -1,4 +1,4 @@ -module Switches ( +module Predicates ( stage, package, builder, stagedBuilder, file, way, stage0, stage1, stage2, notStage, notStage0, registerPackage, splitObjects diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index e64938f..d481a67 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -5,8 +5,8 @@ import Util import Target (PartialTarget (..), fullTarget) import Package import Builder -import Switches (registerPackage) import Expression +import Predicates (registerPackage) import Oracles.PackageDeps import Settings.Packages import Settings.TargetDirectory diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 4f5e787..4ff15c3 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -6,8 +6,8 @@ import Util import Target (PartialTarget (..), fullTarget) import Builder import Package -import Switches (splitObjects) import Expression +import Predicates (splitObjects) import Oracles.PackageData import Settings.Util import Settings.TargetDirectory diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index ec8b6ac..4bde3f8 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,8 +1,8 @@ module Settings.Builders.Ar (arArgs, arPersistentArgsCount) where import Builder -import Switches (builder) import Expression +import Predicates (builder) import Settings.Util arArgs :: Args diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index 748e544..20867f7 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -3,8 +3,8 @@ module Settings.Builders.Gcc (gccArgs, gccMArgs) where import Base import Util import Builder -import Switches (stagedBuilder) import Expression +import Predicates (stagedBuilder) import Oracles.PackageData import Settings.Util diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index af20c7a..e48be86 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -4,8 +4,8 @@ import Way import Util import Stage import Builder -import Switches (stagedBuilder, splitObjects, stage0) import Expression +import Predicates (stagedBuilder, splitObjects, stage0) import Oracles.Flag import Oracles.PackageData import Settings.Util diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 623110b..4862e9f 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -9,8 +9,8 @@ import Util import Stage import Builder import Package -import Switches import Expression +import Predicates import Oracles.Flag import Oracles.Setting import Settings.User diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index b2bab83..64981c6 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -2,8 +2,8 @@ module Settings.Builders.GhcPkg (ghcPkgArgs) where import Util import Builder -import Switches import Expression +import Predicates import Settings.Util import Settings.Builders.GhcCabal diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 94a1669..19c1979 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -4,8 +4,8 @@ import Base import Util import Builder import Package -import Switches (builder, package, stage1) import Expression +import Predicates (builder, package, stage1) import Oracles.PackageData import Settings.Util import Settings.Packages diff --git a/src/Settings/Builders/Ld.hs b/src/Settings/Builders/Ld.hs index e21a262..6a17ca7 100644 --- a/src/Settings/Builders/Ld.hs +++ b/src/Settings/Builders/Ld.hs @@ -1,8 +1,8 @@ module Settings.Builders.Ld (ldArgs) where import Builder -import Switches (builder) import Expression +import Predicates (builder) import Oracles.Setting import Settings.Util diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 5820e0c..b84bb5b 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -4,8 +4,8 @@ module Settings.Packages ( ) where import Package -import Switches import Expression +import Predicates import Oracles.Setting import Settings.User import Settings.Default diff --git a/src/Settings/User.hs b/src/Settings/User.hs index e67afc3..cdf2840 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -7,8 +7,8 @@ module Settings.User ( import Stage import Package -import Switches import Expression +import Predicates import Settings.Default -- No user-specific settings by default diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 81b7b69..1ab4308 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -13,8 +13,8 @@ import Util import Stage import Builder import Package -import Switches import Expression +import Predicates import Oracles.Flag import Oracles.Setting import Oracles.PackageData diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index d6e541e..183068a 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -2,8 +2,8 @@ module Settings.Ways (getWays, getRtsWays) where import Way import Stage -import Switches import Expression +import Predicates import Oracles.Flag import Settings.User From git at git.haskell.org Fri Oct 27 00:05:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghc-cabal only, add cache. (9dbd805) Message-ID: <20171027000551.04FA83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dbd805af4dcc0f90f80b33a74cb1f0c1c49f861/ghc >--------------------------------------------------------------- commit 9dbd805af4dcc0f90f80b33a74cb1f0c1c49f861 Author: Andrey Mokhov Date: Sat Jan 9 23:35:04 2016 +0000 Build ghc-cabal only, add cache. See #110. [skip ci] >--------------------------------------------------------------- 9dbd805af4dcc0f90f80b33a74cb1f0c1c49f861 .appveyor.yml | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 99196db..e7cf731 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,4 +1,10 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" +environment: + global: + STACK_ROOT: "c:\\sr" + +cache: + - c:\\sr install: - cd @@ -24,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-cabal.exe From git at git.haskell.org Fri Oct 27 00:05:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix outdated comments. (0273e3e) Message-ID: <20171027000551.E87D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0273e3ea2449f646c46059d2be4a7261571511c0/ghc >--------------------------------------------------------------- commit 0273e3ea2449f646c46059d2be4a7261571511c0 Author: Andrey Mokhov Date: Fri Feb 26 15:47:56 2016 +0000 Fix outdated comments. See #210. >--------------------------------------------------------------- 0273e3ea2449f646c46059d2be4a7261571511c0 src/Oracles/ModuleFiles.hs | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 96e66ac..b38929c 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -65,16 +65,16 @@ contextFiles context at Context {..} = do zip modules <$> askOracle (ModuleFilesKey (stage, package)) -- | This is an important oracle whose role is to find and cache module source --- files. It takes a 'Context', looks up corresponding source directories @dirs@ --- and sorted list of module names @modules@, and for each module, e.g. --- @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, such that --- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or 'Nothing' --- if there is no such file. If more than one matching file is found an error is --- raised. For example, for @Context Stage1 compiler vanilla@, @dirs@ will +-- files. It takes a 'Stage' and a 'Package', looks up corresponding source +-- directories @dirs@ and a sorted list of module names @modules@, and for each +-- module, e.g. @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, +-- such that @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or +-- 'Nothing' if there is no such file. If more than one matching file is found +-- an error is raised. For example, for 'Stage1' and 'compiler', @dirs@ will -- contain ["compiler/codeGen", "compiler/parser"], and @modules@ will contain -- ["CodeGen.Platform.ARM", "Config", "Lexer"]; the oracle will produce a list -- containing [Just "compiler/codeGen/CodeGen/Platform/ARM.hs", Nothing, --- Just "compiler/parser/Lexer.x"]. +-- Just "compiler/parser/Lexer.x"]. The oracle ignores @.(l)hs-boot@ files. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do void $ addOracle $ \(ModuleFilesKey (stage, package)) -> do From git at git.haskell.org Fri Oct 27 00:05:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix infinite loop bug in chunksOfSize. (1d27a44) Message-ID: <20171027000553.C42883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1d27a444cc91ce912bbff440507170cc14729961/ghc >--------------------------------------------------------------- commit 1d27a444cc91ce912bbff440507170cc14729961 Author: Andrey Mokhov Date: Fri Aug 21 23:39:06 2015 +0100 Fix infinite loop bug in chunksOfSize. >--------------------------------------------------------------- 1d27a444cc91ce912bbff440507170cc14729961 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index b39fc6c..51b5ccb 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -49,7 +49,7 @@ chunksOfSize size strings = reverse chunk : chunksOfSize size rest (chunk, rest) = go [] 0 strings go res _ [] = (res, []) go res chunkSize (s:ss) = - if newSize > size then (chunk, s:ss) else go (s:res) newSize ss + if newSize > size then (res, s:ss) else go (s:res) newSize ss where newSize = chunkSize + length s From git at git.haskell.org Fri Oct 27 00:02:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid using interpretDiff, use simpler interpret instead. (327b06e) Message-ID: <20171027000204.5A3583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/327b06e578a4194368020152bd90b8eb4193dd7a/ghc >--------------------------------------------------------------- commit 327b06e578a4194368020152bd90b8eb4193dd7a Author: Andrey Mokhov Date: Sun Aug 2 15:02:23 2015 +0100 Avoid using interpretDiff, use simpler interpret instead. >--------------------------------------------------------------- 327b06e578a4194368020152bd90b8eb4193dd7a src/Expression.hs | 10 +++++----- src/Oracles/ArgsHash.hs | 2 +- src/Rules.hs | 3 +-- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 4 ++-- src/Rules/Data.hs | 8 ++++---- src/Rules/Dependencies.hs | 2 +- src/Settings/Args.hs | 7 ++++--- src/Settings/Util.hs | 2 +- 9 files changed, 20 insertions(+), 20 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 6ec6ef4..ee8e8f3 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -8,7 +8,7 @@ module Expression ( Args, Ways, Packages, apply, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, - interpret, interpretExpr, + interpret, interpretDiff, getStage, getPackage, getBuilder, getFiles, getFile, getDependencies, getDependency, getWay, stage, package, builder, stagedBuilder, file, way @@ -141,16 +141,16 @@ removeSub :: String -> [String] -> Args removeSub prefix xs = filterSub prefix (`notElem` xs) -- Interpret a given expression in a given environment -interpretExpr :: Target -> Expr a -> Action a -interpretExpr = flip runReaderT +interpret :: Target -> Expr a -> Action a +interpret = flip runReaderT -- Extract an expression from a difference expression fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) -- Interpret a given difference expression in a given environment -interpret :: Monoid a => Target -> DiffExpr a -> Action a -interpret target = interpretExpr target . fromDiffExpr +interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a +interpretDiff target = interpret target . fromDiffExpr -- Convenient getters for target parameters getStage :: Expr Stage diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 1972638..ca0aa6c 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -22,5 +22,5 @@ askArgsHash = askOracle . ArgsHashKey -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () argsHashOracle = do - addOracle $ \(ArgsHashKey target) -> hash <$> interpret target args + addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs return () diff --git a/src/Rules.hs b/src/Rules.hs index e651325..be109f8 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -15,11 +15,10 @@ import Settings.Packages import Settings.TargetDirectory -- generateTargets needs package-data.mk files of all target packages --- TODO: make interpretDiff total generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do - pkgs <- interpret (stageTarget stage) packages + pkgs <- interpret (stageTarget stage) getPackages fmap concat . forM pkgs $ \pkg -> return [ targetPath stage pkg -/- "build/haskell.deps" , targetPath stage pkg -/- "build/c.deps" ] diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 1940a4a..d96157c 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -21,7 +21,7 @@ buildWithResources rs target = do needBuilder builder need deps path <- builderPath builder - argList <- interpret target args + argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed argsHash <- askArgsHash target withResources rs $ do diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 48db356..55d909d 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -16,7 +16,7 @@ cabalRules :: Rules () cabalRules = do -- Cache boot package constraints (to be used in cabalArgs) bootPackageConstraints %> \file -> do - pkgs <- interpret (stageTarget Stage0) packages + pkgs <- interpret (stageTarget Stage0) getPackages constraints <- forM (sort pkgs) $ \pkg -> do let cabal = pkgCabalPath pkg need [cabal] @@ -29,7 +29,7 @@ cabalRules = do -- Cache package dependencies packageDependencies %> \file -> do - pkgs <- interpret (stageTarget Stage1) packages + pkgs <- interpret (stageTarget Stage1) getPackages pkgDeps <- forM (sort pkgs) $ \pkg -> do let cabal = pkgCabalPath pkg need [cabal] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 762115c..8f365e8 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -40,16 +40,16 @@ buildPackageData (Resources ghcCabal ghcPkg) target = do -- We configure packages in the order of their dependencies deps <- packageDeps pkg - pkgs <- interpret target packages - let cmp pkg = compare (pkgName pkg) - depPkgs = intersectOrd cmp (sort pkgs) deps + pkgs <- interpret target getPackages + let cmp pkg name = compare (pkgName pkg) name + depPkgs = intersectOrd cmp (sort pkgs) deps need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] buildWithResources [(ghcCabal, 1)] $ fullTarget target [cabal] GhcCabal files -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg - whenM (interpretExpr target registerPackage) . + whenM (interpret target registerPackage) . buildWithResources [(ghcPkg, 1)] $ fullTarget target [cabal] (GhcPkg stage) files diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 7fab8cf..bee85c6 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -32,5 +32,5 @@ buildPackageDependencies _ target = writeFileChanged file (concat deps) (buildPath -/- "haskell.deps") %> \file -> do - srcs <- interpretExpr target getHsSources + srcs <- interpret target getHsSources build $ fullTarget target srcs (GhcM stage) [file] diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index d698017..4d4dd17 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -1,6 +1,4 @@ -module Settings.Args ( - args - ) where +module Settings.Args (args, getArgs) where import Expression import Settings.User @@ -12,6 +10,9 @@ import Settings.GhcCabal args :: Args args = defaultArgs <> userArgs +getArgs :: Expr [String] +getArgs = fromDiffExpr args + -- TODO: add all other settings -- TODO: add src-hc-args = -H32m -O -- TODO: GhcStage2HcOpts=-O2 unless GhcUnregisterised diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index d2daa0b..d04a12a 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -85,7 +85,7 @@ getHsSources = do (foundSources, missingSources) <- findModuleFiles dirs "*hs" -- Generated source files live in buildPath and have extension "hs" - let generatedSources = map (\f -> buildPath -/- f <.> "hs") missingSources + let generatedSources = [ buildPath -/- s <.> "hs" | s <- missingSources ] return $ foundSources ++ generatedSources From git at git.haskell.org Fri Oct 27 00:02:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing package Settings.Packages.Touchy. (39e1756) Message-ID: <20171027000205.63D9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39e17562d9f76f92cd63242a8c960ce1a9143f3f/ghc >--------------------------------------------------------------- commit 39e17562d9f76f92cd63242a8c960ce1a9143f3f Author: Andrey Mokhov Date: Thu Jan 7 22:31:45 2016 +0000 Add missing package Settings.Packages.Touchy. See #125. [skip ci] >--------------------------------------------------------------- 39e17562d9f76f92cd63242a8c960ce1a9143f3f shaking-up-ghc.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 9f2c80c..ab9f7bc 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -90,6 +90,7 @@ executable ghc-shake , Settings.Packages.IservBin , Settings.Packages.Rts , Settings.Packages.RunGhc + , Settings.Packages.Touchy , Settings.TargetDirectory , Settings.User , Settings.Ways From git at git.haskell.org Fri Oct 27 00:02:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:02:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move mkUserGuidePart to Stage2. (9497fbe) Message-ID: <20171027000207.519A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9497fbee97634610c2d9af6115f139f794c5fb0f/ghc >--------------------------------------------------------------- commit 9497fbee97634610c2d9af6115f139f794c5fb0f Author: Andrey Mokhov Date: Sun Feb 14 21:54:25 2016 +0000 Move mkUserGuidePart to Stage2. >--------------------------------------------------------------- 9497fbee97634610c2d9af6115f139f794c5fb0f src/Settings/Packages.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 691cd78..ef8fc26 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -34,8 +34,7 @@ packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq , directory, filepath, ghci, ghcPrim, haskeline, hpcBin - , integerLibrary, mkUserGuidePart, pretty, process, rts, runGhc - , time ] + , integerLibrary, pretty, process, rts, runGhc, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , notM windowsHost ? append [iservBin] @@ -45,7 +44,7 @@ packagesStage1 = mconcat -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages packagesStage2 = mconcat - [ append [ghcTags] + [ append [ghcTags, mkUserGuidePart] , buildHaddock ? append [haddock] ] -- TODO: switch to Set Package as the order of packages should not matter? From git at git.haskell.org Fri Oct 27 00:03:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass way to buildPackageLibrary via Context, minor revision. (98b1f8c) Message-ID: <20171027000325.52CDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/98b1f8c2e233d4b9504dfe359b0f538f7af9095e/ghc >--------------------------------------------------------------- commit 98b1f8c2e233d4b9504dfe359b0f538f7af9095e Author: Andrey Mokhov Date: Tue Feb 16 03:01:56 2016 +0000 Pass way to buildPackageLibrary via Context, minor revision. See #207. >--------------------------------------------------------------- 98b1f8c2e233d4b9504dfe359b0f538f7af9095e src/Rules.hs | 15 +++++++++------ src/Rules/Documentation.hs | 1 + src/Rules/Library.hs | 13 +++++-------- src/Way.hs | 4 ++-- 4 files changed, 17 insertions(+), 16 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index a3d67cb..4592b4a 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -64,16 +64,19 @@ packageRules = do let contexts = liftM3 Context allStages knownPackages allWays vanillaContexts = liftM2 vanillaContext allStages knownPackages - traverse_ (compilePackage readPackageDb) contexts - traverse_ (buildPackageDependencies readPackageDb) vanillaContexts + for_ contexts $ mconcat + [ compilePackage readPackageDb + , buildPackageLibrary ] + + for_ vanillaContexts $ mconcat + [ buildPackageData + , buildPackageDependencies readPackageDb + , buildPackageDocumentation + , generatePackageCode ] for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package - buildPackageData context - buildPackageDocumentation context - generatePackageCode context - buildPackageLibrary context buildProgram context registerPackage writePackageDb context diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 848a3fa..e3b0e7d 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -37,6 +37,7 @@ buildPackageDocumentation context @ (Context {..}) = build $ Target context GhcCabalHsColour [cabalFile] [] -- Build Haddock documentation + -- TODO: pass the correct way from Rules via Context let haddockWay = if dynamicGhcPrograms then dynamic else vanilla build $ Target (context {way = haddockWay}) Haddock srcs [file] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 79b4952..d77d58e 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -14,24 +14,21 @@ import Rules.Gmp import Settings import Target --- TODO: Use way from Context, #207 buildPackageLibrary :: Context -> Rules () buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" -- TODO: handle dynamic libraries - matchBuildResult buildPath "a" ?> \a -> do - + buildPath "*" ++ waySuffix way ++ ".a" %> \a -> do removeFileIfExists a cSrcs <- cSources context hSrcs <- hSources context - -- TODO: simplify handling of AutoApply.cmm - let w = detectWay a -- TODO: eliminate differences below - cObjs = [ buildPath -/- src -<.> osuf w | src <- cSrcs + -- TODO: simplify handling of AutoApply.cmm, eliminate differences below + let cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs , not ("//AutoApply.cmm" ?== src) ] - ++ [ src -<.> osuf w | src <- cSrcs, "//AutoApply.cmm" ?== src ] - hObjs = [ buildPath -/- src <.> osuf w | src <- hSrcs ] + ++ [ src -<.> osuf way | src <- cSrcs, "//AutoApply.cmm" ?== src ] + hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] -- This will create split objects if required (we don't track them -- explicitly as this would needlessly bloat the Shake database). diff --git a/src/Way.hs b/src/Way.hs index 668ed63..c393437 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -6,8 +6,8 @@ module Way ( threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic, - allWays, wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, - safeDetectWay, detectWay, matchBuildResult + allWays, wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, + libsuf, safeDetectWay, detectWay, matchBuildResult ) where import Base hiding (unit) From git at git.haskell.org Fri Oct 27 00:03:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix shake script path. (192fd13) Message-ID: <20171027000326.146303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/192fd13c7e9a8e71940513a78816f701b89ea87a/ghc >--------------------------------------------------------------- commit 192fd13c7e9a8e71940513a78816f701b89ea87a Author: Andrey Mokhov Date: Fri Jan 8 19:21:00 2016 +0000 Fix shake script path. See #110. [skip ci] >--------------------------------------------------------------- 192fd13c7e9a8e71940513a78816f701b89ea87a .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7c724b8..ef571b3 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd - - bash -lc "./shake-build/build.bat -j --no-progress" + - bash -lc "cd /home/ghc; ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:03:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove error from putSuccess :-) (9afd164) Message-ID: <20171027000328.A6E613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9afd164fa76821409208e8a425ccaee625a8ee94/ghc >--------------------------------------------------------------- commit 9afd164fa76821409208e8a425ccaee625a8ee94 Author: Andrey Mokhov Date: Fri Aug 7 12:24:17 2015 +0100 Remove error from putSuccess :-) >--------------------------------------------------------------- 9afd164fa76821409208e8a425ccaee625a8ee94 src/Util.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index 7a68b2a..dd0f2d8 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -69,10 +69,8 @@ putBuild :: String -> Action () putBuild = putColoured White -- A more colourful version of error -putSuccess :: String -> Action a -putSuccess msg = do - putColoured Green msg - error $ "GHC build system error: " ++ msg +putSuccess :: String -> Action () +putSuccess = putColoured Green -- A more colourful version of error putError :: String -> Action a From git at git.haskell.org Fri Oct 27 00:03:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finalise generation of build rules from contexts. (f6a9d2f) Message-ID: <20171027000329.121D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f6a9d2f4e67a163ba8255d8e66def0668dd492a1/ghc >--------------------------------------------------------------- commit f6a9d2f4e67a163ba8255d8e66def0668dd492a1 Author: Andrey Mokhov Date: Tue Feb 16 03:08:24 2016 +0000 Finalise generation of build rules from contexts. See #207. >--------------------------------------------------------------- f6a9d2f4e67a163ba8255d8e66def0668dd492a1 src/Rules.hs | 10 +++------- src/Rules/Register.hs | 1 - 2 files changed, 3 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 4592b4a..74ffe30 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -72,13 +72,9 @@ packageRules = do [ buildPackageData , buildPackageDependencies readPackageDb , buildPackageDocumentation - , generatePackageCode ] - - for_ allStages $ \stage -> - for_ knownPackages $ \package -> do - let context = vanillaContext stage package - buildProgram context - registerPackage writePackageDb context + , generatePackageCode + , buildProgram + , registerPackage writePackageDb ] buildRules :: Rules () buildRules = do diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 2bbfcfc..01d8ab9 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -13,7 +13,6 @@ import Settings import Settings.Packages.Rts import Target --- TODO: Use way from Context, #207 -- Build package-data.mk by using GhcCabal to process pkgCabal file registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context @ (Context {..}) = do From git at git.haskell.org Fri Oct 27 00:03:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script from shake-build. (8d1c201) Message-ID: <20171027000329.B752D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8d1c201b7fcea98907fa54419f91f3fdfc3007fd/ghc >--------------------------------------------------------------- commit 8d1c201b7fcea98907fa54419f91f3fdfc3007fd Author: Andrey Mokhov Date: Fri Jan 8 20:11:52 2016 +0000 Run shake script from shake-build. See #110. [skip ci] >--------------------------------------------------------------- 8d1c201b7fcea98907fa54419f91f3fdfc3007fd .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index ef571b3..0e62796 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd - - bash -lc "cd /home/ghc; ./shake-build/build.bat -j --no-progress" + - bash -lc "cd /home/ghc/shake-build; ./build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:03:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reverse the target list passed to need (otherwise the targets are build in reverse order). (b397bb3) Message-ID: <20171027000332.5527A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b397bb360a980c60290df89a6b358b614edce5a9/ghc >--------------------------------------------------------------- commit b397bb360a980c60290df89a6b358b614edce5a9 Author: Andrey Mokhov Date: Fri Aug 7 12:25:28 2015 +0100 Reverse the target list passed to need (otherwise the targets are build in reverse order). >--------------------------------------------------------------- b397bb360a980c60290df89a6b358b614edce5a9 src/Rules.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules.hs b/src/Rules.hs index 2509cf7..43f5922 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -38,7 +38,7 @@ generateTargets = action $ do return $ ghciLib ++ libs - need targets + need $ reverse targets -- TODO: add Stage2 (compiler only?) packageRules :: Rules () From git at git.haskell.org Fri Oct 27 00:03:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script outside bash. (a5763fa) Message-ID: <20171027000333.814803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5763fa0dca8a35fb15e5ef6c991c24e2bc04c28/ghc >--------------------------------------------------------------- commit a5763fa0dca8a35fb15e5ef6c991c24e2bc04c28 Author: Andrey Mokhov Date: Fri Jan 8 20:52:02 2016 +0000 Run shake script outside bash. See #110. [skip ci] >--------------------------------------------------------------- a5763fa0dca8a35fb15e5ef6c991c24e2bc04c28 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 0e62796..b6b5ecb 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,5 +23,5 @@ install: - happy --version build_script: - - cd - - bash -lc "cd /home/ghc/shake-build; ./build.bat -j --no-progress" + - cd C:\msys64\home\ghc\shake-build + - ./build.bat -j --no-progress From git at git.haskell.org Fri Oct 27 00:03:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop matchBuildResult and associated functions. (1aec72e) Message-ID: <20171027000332.BEAE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1aec72e34e0e3da138c6e0105c509f20592f6bc6/ghc >--------------------------------------------------------------- commit 1aec72e34e0e3da138c6e0105c509f20592f6bc6 Author: Andrey Mokhov Date: Tue Feb 16 03:12:11 2016 +0000 Drop matchBuildResult and associated functions. See #207. >--------------------------------------------------------------- 1aec72e34e0e3da138c6e0105c509f20592f6bc6 src/Way.hs | 36 ++---------------------------------- 1 file changed, 2 insertions(+), 34 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index c393437..340321c 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,13 +1,12 @@ module Way ( - WayUnit (..), Way, wayUnit, wayFromUnits, + WayUnit (..), Way, wayUnit, wayFromUnits, allWays, vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging, threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic, - allWays, wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, - libsuf, safeDetectWay, detectWay, matchBuildResult + wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf ) where import Base hiding (unit) @@ -160,37 +159,6 @@ libsuf way @ (Way set) = -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension --- | Detect way from a given 'FilePath'. Returns 'Nothing' if there is no match. --- --- * @'safeDetectWay' "foo/bar.hi" '==' 'Just' vanilla@ --- * @'safeDetectWay' "baz.thr_p_o" '==' 'Just' threadedProfiling@ --- * @'safeDetectWay' "qwe.ph_i" '==' 'Nothing' (expected "qwe.p_hi")@ --- * @'safeDetectWay' "xru.p_ghc7.11.123.so" '==' 'Just' profiling@ -safeDetectWay :: FilePath -> Maybe Way -safeDetectWay file = case reads prefix of - [(way, "")] -> Just way - _ -> Nothing - where - extension = takeExtension file - prefixed = if extension `notElem` [".so", ".dll", ".dynlib"] - then extension - else takeExtension . dropExtension . - dropExtension . dropExtension $ file - prefix = if extension == "a" - then drop 1 . dropWhile (/= '_') $ takeBaseName file - else drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed - --- Unsafe version of safeDetectWay. Useful when matchBuildResult has succeeded. -detectWay :: FilePath -> Way -detectWay = fromJust . safeDetectWay - --- Given a path, an extension suffix, and a file name check: --- 1) the file conforms to pattern 'path//*suffix' --- 2) file's extension has a valid way tag (i.e., safeDetectWay does not fail) -matchBuildResult :: FilePath -> String -> FilePath -> Bool -matchBuildResult path suffix file = - (path "*" ++ suffix) ?== file && isJust (safeDetectWay file) - -- Instances for storing in the Shake database instance Binary Way where put = put . show From git at git.haskell.org Fri Oct 27 00:03:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop need from build. Add appropriate needs to build rules. (5bb1d7e) Message-ID: <20171027000336.320513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5bb1d7e24f6f51f2d2e570de47b5f554bb990753/ghc >--------------------------------------------------------------- commit 5bb1d7e24f6f51f2d2e570de47b5f554bb990753 Author: Andrey Mokhov Date: Fri Aug 7 12:26:57 2015 +0100 Drop need from build. Add appropriate needs to build rules. >--------------------------------------------------------------- 5bb1d7e24f6f51f2d2e570de47b5f554bb990753 src/Rules/Actions.hs | 2 +- src/Rules/Compile.hs | 5 +++++ src/Rules/Data.hs | 1 + src/Rules/Dependencies.hs | 4 +++- 4 files changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 50eb87f..062a5d5 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -21,7 +21,7 @@ buildWithResources rs target = do let builder = Target.builder target deps = Target.dependencies target needBuilder builder - need deps + -- need deps -- TODO: think if needs could be done here path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 6f57a81..223f9b2 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -35,6 +35,11 @@ compilePackage _ target = do when (null cDeps && null hDeps) $ putError $ "Cannot determine sources for '" ++ obj ++ "'." + when (not (null cDeps) && not (null hDeps)) $ + putError $ "Both .c and .hs sources found for '" ++ obj ++ "'." + + need $ hDeps ++ cDeps + if null cDeps then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] else build $ fullTarget target cDeps (Gcc stage) [obj] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 8f365e8..8b3eb05 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -45,6 +45,7 @@ buildPackageData (Resources ghcCabal ghcPkg) target = do depPkgs = intersectOrd cmp (sort pkgs) deps need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] + need [cabal] buildWithResources [(ghcCabal, 1)] $ fullTarget target [cabal] GhcCabal files diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index bee85c6..ea47241 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -22,15 +22,17 @@ buildPackageDependencies _ target = in do (buildPath "*.c.deps") %> \depFile -> do let srcFile = dropBuild . dropExtension $ depFile + need [srcFile] build $ fullTarget target [srcFile] (GccM stage) [depFile] (buildPath -/- "c.deps") %> \file -> do srcs <- pkgDataList $ CSrcs path let depFiles = [ buildPath -/- src <.> "deps" | src <- srcs ] - need depFiles -- increase parallelism by needing all at once + need depFiles deps <- mapM readFile' depFiles writeFileChanged file (concat deps) (buildPath -/- "haskell.deps") %> \file -> do srcs <- interpret target getHsSources + need srcs build $ fullTarget target srcs (GhcM stage) [file] From git at git.haskell.org Fri Oct 27 00:03:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add matchVersionedFilePath and use for matching library targets. (5fcb480) Message-ID: <20171027000336.F32133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5fcb480b9e5efc1aea8c4b32965d65cdae5da766/ghc >--------------------------------------------------------------- commit 5fcb480b9e5efc1aea8c4b32965d65cdae5da766 Author: Andrey Mokhov Date: Tue Feb 16 17:30:13 2016 +0000 Add matchVersionedFilePath and use for matching library targets. >--------------------------------------------------------------- 5fcb480b9e5efc1aea8c4b32965d65cdae5da766 src/Base.hs | 19 ++++++++++++++++++- src/Rules/Library.hs | 22 ++++++++++++---------- 2 files changed, 30 insertions(+), 11 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 1a06120..feec868 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,12 +23,13 @@ module Base ( -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - removeFileIfExists, removeDirectoryIfExists + removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath ) where import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader +import Data.Char import Data.Function import Data.List.Extra import Data.Maybe @@ -175,3 +176,19 @@ removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f removeDirectoryIfExists :: FilePath -> Action () removeDirectoryIfExists d = liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d + +-- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the +-- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string +-- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: +-- +--- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ +--- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar-" "a" "foo/bar-0.1.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False'@ +matchVersionedFilePath :: String -> String -> FilePath -> Bool +matchVersionedFilePath prefix suffix filePath = + case stripPrefix prefix (unifyPath filePath) >>= stripSuffix suffix of + Nothing -> False + Just version -> all (\c -> isDigit c || c == '-' || c == '.') version diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index d77d58e..e53355f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -17,9 +17,10 @@ import Target buildPackageLibrary :: Context -> Rules () buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" + libHs = buildPath -/- "libHS" ++ pkgNameString package -- TODO: handle dynamic libraries - buildPath "*" ++ waySuffix way ++ ".a" %> \a -> do + matchVersionedFilePath libHs (waySuffix way <.> "a") ?> \a -> do removeFileIfExists a cSrcs <- cSources context hSrcs <- hSources context @@ -61,15 +62,16 @@ buildPackageLibrary context @ (Context {..}) = do -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. -- This happens with hsc2hs, which has top-level file HSCParser.hs. - when (package /= hsc2hs) $ priority 2 $ (buildPath -/- "HS*.o") %> \obj -> do - cSrcs <- cSources context - hSrcs <- hSources context - let cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs - , not ("//AutoApply.cmm" ?== src) ] - ++ [ src -<.> "o" | src <- cSrcs, "//AutoApply.cmm" ?== src ] - hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] - need $ cObjs ++ hObjs - build $ Target context Ld (cObjs ++ hObjs) [obj] + priority 2 $ when (package /= hsc2hs && way == vanilla) $ + (buildPath -/- "HS*.o") %> \obj -> do + cSrcs <- cSources context + hSrcs <- hSources context + let cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs + , not ("//AutoApply.cmm" ?== src) ] + ++ [ src -<.> "o" | src <- cSrcs, "//AutoApply.cmm" ?== src ] + hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] + need $ cObjs ++ hObjs + build $ Target context Ld (cObjs ++ hObjs) [obj] cSources :: Context -> Action [FilePath] cSources context = interpretInContext context $ getPkgDataList CSrcs From git at git.haskell.org Fri Oct 27 00:03:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script via stack. (f4ece5b) Message-ID: <20171027000337.5B5443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4ece5be780b194845548d9e1ab46a916b22b4f5/ghc >--------------------------------------------------------------- commit f4ece5be780b194845548d9e1ab46a916b22b4f5 Author: Andrey Mokhov Date: Fri Jan 8 21:34:15 2016 +0000 Run shake script via stack. See #110. [skip ci] >--------------------------------------------------------------- f4ece5be780b194845548d9e1ab46a916b22b4f5 .appveyor.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index b6b5ecb..14c6521 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,5 +23,4 @@ install: - happy --version build_script: - - cd C:\msys64\home\ghc\shake-build - - ./build.bat -j --no-progress + - stack exec -- C:\msys64\home\ghc\shake-build\build.bat -j --no-progress From git at git.haskell.org Fri Oct 27 00:03:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (036328f) Message-ID: <20171027000339.A35D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/036328f08a067c6d8817c1d56d43e4f5b68d9e0f/ghc >--------------------------------------------------------------- commit 036328f08a067c6d8817c1d56d43e4f5b68d9e0f Author: Andrey Mokhov Date: Fri Aug 7 12:28:07 2015 +0100 Clean up. >--------------------------------------------------------------- 036328f08a067c6d8817c1d56d43e4f5b68d9e0f src/Rules/Library.hs | 32 +++++++++++++++++--------------- 1 file changed, 17 insertions(+), 15 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index c788edb..fe0c72d 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -29,34 +29,36 @@ buildPackageLibrary _ target = do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules - let way = fromJust . detectWay $ a -- fromJust is safe - hsSrcs = map (replaceEq '.' '/') modules - cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] - hsObjs = [ buildPath -/- src <.> osuf way | src <- hsSrcs ] + let way = fromJust . detectWay $ a -- fromJust is safe + hSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] + hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] - need $ cObjs ++ hsObjs -- this will create split objects if required + need $ cObjs ++ hObjs -- this will create split objects if required split <- interpret target splitObjects splitObjs <- if split - then fmap concat $ forM hsSrcs $ \src -> do + then fmap concat $ forM hSrcs $ \src -> do let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" - getDirectoryFiles "" [files] + fmap (map unifyPath) $ getDirectoryFiles "" [files] else return [] - build $ fullTarget target (cObjs ++ hsObjs ++ splitObjs) Ar [a] + build $ fullTarget target (cObjs ++ hObjs ++ splitObjs) Ar [a] synopsis <- interpret target $ getPkgData Synopsis - putSuccess $ "/--------\n| Successfully built package '" - ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + putSuccess $ "/--------\n| Successfully built package library '" + ++ pkgName pkg + ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." putSuccess $ "| Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. - (buildPath -/- "HS*.o") %> \o -> do + priority 2 $ (buildPath -/- "HS*.o") %> \o -> do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules - let hsSrcs = map (replaceEq '.' '/') modules - cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] - hsObjs = [ buildPath -/- src <.> "o" | src <- hsSrcs ] - build $ fullTarget target (cObjs ++ hsObjs) Ld [o] + let hSrcs = map (replaceEq '.' '/') modules + cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] + hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] + need $ cObjs ++ hObjs + build $ fullTarget target (cObjs ++ hObjs) Ld [o] From git at git.haskell.org Fri Oct 27 00:03:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hide Shake.parallel. Again. (89c79cd) Message-ID: <20171027000340.B50343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/89c79cdb52a9feeb949148348afffdd8cc150450/ghc >--------------------------------------------------------------- commit 89c79cdb52a9feeb949148348afffdd8cc150450 Author: Andrey Mokhov Date: Tue Feb 16 18:00:52 2016 +0000 Hide Shake.parallel. Again. >--------------------------------------------------------------- 89c79cdb52a9feeb949148348afffdd8cc150450 src/Base.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index feec868..a794ea8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel module Base ( -- * General utilities module Control.Applicative, @@ -34,7 +35,7 @@ import Data.Function import Data.List.Extra import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>), Normal) +import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Fri Oct 27 00:03:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script via stack from shake-build folder. (ffc5d73) Message-ID: <20171027000341.1E91A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffc5d73536fc68b3abcc1eb8b2dc375fcea33f1d/ghc >--------------------------------------------------------------- commit ffc5d73536fc68b3abcc1eb8b2dc375fcea33f1d Author: Andrey Mokhov Date: Sat Jan 9 02:19:18 2016 +0000 Run shake script via stack from shake-build folder. See #110. [skip ci] >--------------------------------------------------------------- ffc5d73536fc68b3abcc1eb8b2dc375fcea33f1d .appveyor.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 14c6521..1ecaaef 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,4 +23,5 @@ install: - happy --version build_script: - - stack exec -- C:\msys64\home\ghc\shake-build\build.bat -j --no-progress + - cd C:\msys64\home\ghc\shake-build + - stack exec -- build.bat -j --no-progress From git at git.haskell.org Fri Oct 27 00:03:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add hibootsuf and an unsafe version of safeDetectWay. (c48554d) Message-ID: <20171027000343.3F4203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c48554d96ebfb9b55c4b6be9fcbc52b23b24ef2d/ghc >--------------------------------------------------------------- commit c48554d96ebfb9b55c4b6be9fcbc52b23b24ef2d Author: Andrey Mokhov Date: Fri Aug 7 22:32:59 2015 +0100 Add hibootsuf and an unsafe version of safeDetectWay. >--------------------------------------------------------------- c48554d96ebfb9b55c4b6be9fcbc52b23b24ef2d src/Way.hs | 39 ++++++++++++++++++++++----------------- 1 file changed, 22 insertions(+), 17 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 4d14025..74d1f26 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -9,8 +9,8 @@ module Way ( -- TODO: rename to "Way"? threadedDynamic, threadedDebugDynamic, debugDynamic, loggingDynamic, threadedLoggingDynamic, - wayPrefix, hisuf, osuf, hcsuf, obootsuf, ssuf, libsuf, - detectWay, matchBuildResult + wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, + safeDetectWay, detectWay, matchBuildResult ) where import Base @@ -103,11 +103,12 @@ wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" hisuf, osuf, hcsuf, obootsuf, ssuf :: Way -> String -osuf = (++ "o" ) . wayPrefix -ssuf = (++ "s" ) . wayPrefix -hisuf = (++ "hi" ) . wayPrefix -hcsuf = (++ "hc" ) . wayPrefix -obootsuf = (++ "o-boot") . wayPrefix +osuf = (++ "o" ) . wayPrefix +ssuf = (++ "s" ) . wayPrefix +hisuf = (++ "hi" ) . wayPrefix +hcsuf = (++ "hc" ) . wayPrefix +obootsuf = (++ "o-boot" ) . wayPrefix +hibootsuf = (++ "hi-boot") . wayPrefix -- Note: in the previous build system libsuf was mysteriously different -- from other suffixes. For example, in the profiling way it used to be @@ -131,12 +132,12 @@ libsuf way @ (Way set) = return $ prefix ++ "ghc" ++ version ++ extension -- Detect way from a given filename. Returns Nothing if there is no match: --- * detectWay "foo/bar.hi" == Just vanilla --- * detectWay "baz.thr_p_o" == Just threadedProfiling --- * detectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") --- * detectWay "xru.p_ghc7.11.20141222.dll" == Just profiling -detectWay :: FilePath -> Maybe Way -detectWay file = case reads prefix of +-- * safeDetectWay "foo/bar.hi" == Just vanilla +-- * safeDetectWay "baz.thr_p_o" == Just threadedProfiling +-- * safeDetectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") +-- * safeDetectWay "xru.p_ghc7.11.20141222.so" == Just profiling +safeDetectWay :: FilePath -> Maybe Way +safeDetectWay file = case reads prefix of [(way, "")] -> Just way _ -> Nothing where @@ -147,12 +148,16 @@ detectWay file = case reads prefix of dropExtension . dropExtension $ file prefix = drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed --- Given a path, an extension suffix, and a file name check if the latter: --- 1) conforms to pattern 'path//*suffix' --- 2) has extension prefixed with a known way tag, i.e. detectWay does not fail +-- Unsafe version of safeDetectWay. Useful when matchBuildResult has succeeded. +detectWay :: FilePath -> Way +detectWay = fromJust . safeDetectWay + +-- Given a path, an extension suffix, and a file name check: +-- 1) the file conforms to pattern 'path//*suffix' +-- 2) file's extension has a valid way tag (i.e., safeDetectWay does not fail) matchBuildResult :: FilePath -> String -> FilePath -> Bool matchBuildResult path suffix file = - (path "*" ++ suffix) ?== file && (isJust . detectWay $ file) + (path "*" ++ suffix) ?== file && isJust (safeDetectWay file) -- Instances for storing in the Shake database instance Binary Way where From git at git.haskell.org Fri Oct 27 00:03:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out buildPackageGhciLibrary from buildPackageLibrary and make it more robust. (c0b1a37) Message-ID: <20171027000344.45F553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c0b1a37c9681fb98ed85bbccb4004fad993c58f2/ghc >--------------------------------------------------------------- commit c0b1a37c9681fb98ed85bbccb4004fad993c58f2 Author: Andrey Mokhov Date: Tue Feb 16 19:15:47 2016 +0000 Factor out buildPackageGhciLibrary from buildPackageLibrary and make it more robust. See #207. >--------------------------------------------------------------- c0b1a37c9681fb98ed85bbccb4004fad993c58f2 src/Rules.hs | 2 ++ src/Rules/Library.hs | 19 +++++++++++-------- 2 files changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 74ffe30..444a2cb 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -61,6 +61,7 @@ packageRules = do let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] + -- TODO: not all build rules make sense for all stage/package combinations let contexts = liftM3 Context allStages knownPackages allWays vanillaContexts = liftM2 vanillaContext allStages knownPackages @@ -72,6 +73,7 @@ packageRules = do [ buildPackageData , buildPackageDependencies readPackageDb , buildPackageDocumentation + , buildPackageGhciLibrary , generatePackageCode , buildProgram , registerPackage writePackageDb ] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index e53355f..c6d92a5 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,5 +1,7 @@ {-# LANGUAGE RecordWildCards #-} -module Rules.Library (buildPackageLibrary, cSources, hSources) where +module Rules.Library ( + buildPackageLibrary, buildPackageGhciLibrary, cSources, hSources + ) where import Data.Char import qualified System.Directory as IO @@ -17,10 +19,10 @@ import Target buildPackageLibrary :: Context -> Rules () buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" - libHs = buildPath -/- "libHS" ++ pkgNameString package + libPrefix = buildPath -/- "libHS" ++ pkgNameString package -- TODO: handle dynamic libraries - matchVersionedFilePath libHs (waySuffix way <.> "a") ?> \a -> do + matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do removeFileIfExists a cSrcs <- cSources context hSrcs <- hSources context @@ -58,12 +60,13 @@ buildPackageLibrary context @ (Context {..}) = do a (dropWhileEnd isPunctuation synopsis) +buildPackageGhciLibrary :: Context -> Rules () +buildPackageGhciLibrary context @ (Context {..}) = priority 2 $ do + let buildPath = targetPath stage package -/- "build" + libPrefix = buildPath -/- "HS" ++ pkgNameString package + -- TODO: simplify handling of AutoApply.cmm - -- TODO: this looks fragile as haskell objects can match this rule if their - -- names start with "HS" and they are on top of the module hierarchy. - -- This happens with hsc2hs, which has top-level file HSCParser.hs. - priority 2 $ when (package /= hsc2hs && way == vanilla) $ - (buildPath -/- "HS*.o") %> \obj -> do + matchVersionedFilePath libPrefix (waySuffix way <.> "o") ?> \obj -> do cSrcs <- cSources context hSrcs <- hSources context let cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs From git at git.haskell.org Fri Oct 27 00:03:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix terminal issue, build stage1 ghc only. (a64efa9) Message-ID: <20171027000344.B283A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a64efa96c9b19edcf801b675685619292a1f878f/ghc >--------------------------------------------------------------- commit a64efa96c9b19edcf801b675685619292a1f878f Author: Andrey Mokhov Date: Sat Jan 9 02:53:36 2016 +0000 Fix terminal issue, build stage1 ghc only. See #110. [skip ci] >--------------------------------------------------------------- a64efa96c9b19edcf801b675685619292a1f878f .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 1ecaaef..99196db 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - stack exec -- build.bat -j --no-progress + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:03:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for hs-boot files. (6344510) Message-ID: <20171027000346.C9C873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6344510f3cda3097bf77d62a021e70049407c9ac/ghc >--------------------------------------------------------------- commit 6344510f3cda3097bf77d62a021e70049407c9ac Author: Andrey Mokhov Date: Fri Aug 7 22:33:20 2015 +0100 Add support for hs-boot files. >--------------------------------------------------------------- 6344510f3cda3097bf77d62a021e70049407c9ac src/Rules/Compile.hs | 32 +++++++++++++++++++++++++------- src/Rules/Library.hs | 7 +++---- 2 files changed, 28 insertions(+), 11 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 223f9b2..35c9755 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -10,7 +10,6 @@ import Oracles.DependencyList import Settings.TargetDirectory import Rules.Actions import Rules.Resources -import Data.Maybe compilePackage :: Resources -> StagePackageTarget -> Rules () compilePackage _ target = do @@ -21,14 +20,16 @@ compilePackage _ target = do cDepsFile = buildPath -/- "c.deps" hDepsFile = buildPath -/- "haskell.deps" - matchBuildResult buildPath "hi" ?> \hi -> do - let way = fromJust . detectWay $ hi -- fromJust is safe - need [hi -<.> osuf way] + matchBuildResult buildPath "hi" ?> \hi -> + need [ hi -<.> osuf (detectWay hi) ] + + matchBuildResult buildPath "hi-boot" ?> \hiboot -> + need [ hiboot -<.> obootsuf (detectWay hiboot) ] matchBuildResult buildPath "o" ?> \obj -> do - let way = fromJust . detectWay $ obj -- fromJust is safe - vanillaObj = takeFileName obj -<.> "o" - cDeps <- dependencyList cDepsFile vanillaObj + let way = detectWay obj + cObj = takeFileName obj -<.> "o" + cDeps <- dependencyList cDepsFile cObj hDeps <- dependencyList hDepsFile obj let hSrcDeps = filter ("//*hs" ?==) hDeps @@ -43,3 +44,20 @@ compilePackage _ target = do if null cDeps then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] else build $ fullTarget target cDeps (Gcc stage) [obj] + + matchBuildResult buildPath "o-boot" ?> \obj -> do + let way = detectWay obj + hDeps <- dependencyList hDepsFile obj + let hSrcDeps = filter ("//*hs-boot" ?==) hDeps + + when (null hDeps) $ + putError $ "Cannot determine sources for '" ++ obj ++ "'." + + need hDeps + build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] + +-- TODO: add support for -dyno +-- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot +-- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ +-- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno +-- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index fe0c72d..8fd9b0b 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -14,7 +14,6 @@ import Settings.TargetDirectory import Rules.Actions import Rules.Resources import Data.List -import Data.Maybe buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () buildPackageLibrary _ target = do @@ -29,7 +28,7 @@ buildPackageLibrary _ target = do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules - let way = fromJust . detectWay $ a -- fromJust is safe + let way = detectWay a hSrcs = map (replaceEq '.' '/') modules cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] @@ -54,11 +53,11 @@ buildPackageLibrary _ target = do -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. - priority 2 $ (buildPath -/- "HS*.o") %> \o -> do + priority 2 $ (buildPath -/- "HS*.o") %> \obj -> do cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules let hSrcs = map (replaceEq '.' '/') modules cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs ] hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] need $ cObjs ++ hObjs - build $ fullTarget target (cObjs ++ hObjs) Ld [o] + build $ fullTarget target (cObjs ++ hObjs) Ld [obj] From git at git.haskell.org Fri Oct 27 00:03:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use matchVersionedFilePath in registerPackage build rule. (f0f4193) Message-ID: <20171027000347.CD01A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f0f4193049fabd48cd1c0b5e37849319849b9bf5/ghc >--------------------------------------------------------------- commit f0f4193049fabd48cd1c0b5e37849319849b9bf5 Author: Andrey Mokhov Date: Tue Feb 16 19:16:33 2016 +0000 Use matchVersionedFilePath in registerPackage build rule. See #207. >--------------------------------------------------------------- f0f4193049fabd48cd1c0b5e37849319849b9bf5 src/Rules/Register.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 01d8ab9..85fac80 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -1,8 +1,6 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Register (registerPackage) where -import Data.Char - import Base import Context import Expression @@ -18,12 +16,9 @@ registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context @ (Context {..}) = do let oldPath = pkgPath package -/- targetDirectory stage package -- TODO: remove, #113 pkgConf = packageDbDirectory stage -/- pkgNameString package - match f = case stripPrefix (pkgConf ++ "-") f of - Nothing -> False - Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf" - when (stage <= Stage1) $ match ?> \conf -> do - -- This produces pkgConfig. TODO: Add explicit tracking + when (stage <= Stage1) $ matchVersionedFilePath pkgConf "conf" ?> \conf -> do + -- This produces inplace-pkg-config. TODO: Add explicit tracking need [pkgDataFile stage package] -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 From git at git.haskell.org Fri Oct 27 00:03:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Unlit utility (cce8759) Message-ID: <20171027000348.2E1233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cce8759fdf3eed5988013cea4d2810457e8272a0/ghc >--------------------------------------------------------------- commit cce8759fdf3eed5988013cea4d2810457e8272a0 Author: Moritz Angermann Date: Fri Jan 8 18:21:31 2016 +0800 Adds Unlit utility Adds the unlit utility to turn literate files into unliterate files. Fixes #83 >--------------------------------------------------------------- cce8759fdf3eed5988013cea4d2810457e8272a0 shaking-up-ghc.cabal | 1 + src/GHC.hs | 14 +++++++++----- src/Rules/Data.hs | 11 +++++++++++ src/Settings/Args.hs | 4 +++- src/Settings/Packages/{Hp2ps.hs => Unlit.hs} | 10 +++++----- 5 files changed, 29 insertions(+), 11 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index ab9f7bc..066b9e7 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -91,6 +91,7 @@ executable ghc-shake , Settings.Packages.Rts , Settings.Packages.RunGhc , Settings.Packages.Touchy + , Settings.Packages.Unlit , Settings.TargetDirectory , Settings.User , Settings.Ways diff --git a/src/GHC.hs b/src/GHC.hs index 3d99e63..c26f552 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -6,7 +6,7 @@ module GHC ( haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unix, win32, xhtml, + touchy, transformers, unlit, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -28,7 +28,7 @@ defaultKnownPackages = , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time - , touchy, transformers, unix, win32, xhtml ] + , touchy, transformers, unlit, unix, win32, xhtml ] -- Package definitions (see "Package") array, base, binary, bytestring, cabal, compiler, containers, compareSizes, @@ -37,7 +37,7 @@ array, base, binary, bytestring, cabal, compiler, containers, compareSizes, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unix, win32, xhtml :: Package + touchy, transformers, unlit, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -85,11 +85,12 @@ terminfo = library "terminfo" time = library "time" touchy = utility "touchy" transformers = library "transformers" +unlit = utility "unlit" unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" --- TODO: The following utils are not implemented yet: unlit, driver/ghc-split +-- TODO: The following utils are not implemented yet: driver/ghc-split -- TODO: The following utils are not included into the build system because -- they seem to be unused or unrelated to the build process: checkUniques, -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, @@ -112,9 +113,12 @@ defaultProgramPath stage pkg | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing - | pkg == touchy = case stage of + | pkg == touchy = case stage of Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe _ -> Nothing + | pkg == unlit = case stage of + Stage0 -> Just $ "inplace/lib" -/- pkgNameString pkg <.> exe + _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index de4f8c0..8b21fc7 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -67,6 +67,17 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." + when (pkg == unlit) $ dataFile %> \mk -> do + let prefix = "utils_unlit_" ++ stageString stage ++ "_" + contents = unlines $ map (prefix++) + [ "PROGNAME = unlit" + , "C_SRCS = unlit.c" + , "INSTALL = YES" + , "INSTALL_INPLACE = YES" + , "SYNOPSIS = Literate script filter." ] + writeFileChanged mk contents + putSuccess $ "| Successfully generated '" ++ mk ++ "'." + when (pkg == touchy) $ dataFile %> \mk -> do let prefix = "utils_touchy_" ++ stageString stage ++ "_" contents = unlines $ map (prefix++) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index f2b30fa..3bd32d7 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -31,6 +31,7 @@ import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc import Settings.Packages.Touchy +import Settings.Packages.Unlit import Settings.User getArgs :: Expr [String] @@ -77,4 +78,5 @@ defaultPackageArgs = mconcat , iservBinPackageArgs , rtsPackageArgs , runGhcPackageArgs - , touchyPackageArgs ] + , touchyPackageArgs + , unlitPackageArgs ] diff --git a/src/Settings/Packages/Hp2ps.hs b/src/Settings/Packages/Unlit.hs similarity index 68% copy from src/Settings/Packages/Hp2ps.hs copy to src/Settings/Packages/Unlit.hs index 26518c6..e654a66 100644 --- a/src/Settings/Packages/Hp2ps.hs +++ b/src/Settings/Packages/Unlit.hs @@ -1,13 +1,13 @@ -module Settings.Packages.Hp2ps (hp2psPackageArgs) where +module Settings.Packages.Unlit (unlitPackageArgs) where import Base import Expression -import GHC (hp2ps) +import GHC (unlit) import Predicates (builderGhc, package) -import Settings +import Settings (getTargetPath) -hp2psPackageArgs :: Args -hp2psPackageArgs = package hp2ps ? do +unlitPackageArgs :: Args +unlitPackageArgs = package unlit ? do path <- getTargetPath let cabalMacros = path -/- "build/autogen/cabal_macros.h" mconcat [ builderGhc ? From git at git.haskell.org Fri Oct 27 00:03:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve zero build performance. (d2910ba) Message-ID: <20171027000350.73EF53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2910ba1570a2b8a21d83b7ace7d3437c8311b22/ghc >--------------------------------------------------------------- commit d2910ba1570a2b8a21d83b7ace7d3437c8311b22 Author: Andrey Mokhov Date: Sat Aug 8 01:03:26 2015 +0100 Improve zero build performance. >--------------------------------------------------------------- d2910ba1570a2b8a21d83b7ace7d3437c8311b22 src/Oracles/DependencyList.hs | 2 +- src/Rules/Compile.hs | 52 ++++++++++++++++++------------------------- src/Rules/Library.hs | 10 ++++++--- src/Settings/Builders/Ghc.hs | 5 +++++ 4 files changed, 35 insertions(+), 34 deletions(-) diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs index 900b48e..e571f7b 100644 --- a/src/Oracles/DependencyList.hs +++ b/src/Oracles/DependencyList.hs @@ -28,7 +28,7 @@ dependencyListOracle :: Rules () dependencyListOracle = do deps <- newCache $ \file -> do need [file] - putOracle $ "Reading " ++ file ++ "..." + putOracle $ "Reading dependencies from " ++ file ++ "..." contents <- parseMakefile <$> (liftIO $ readFile file) return . Map.fromList . map (bimap unifyPath (map unifyPath)) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 35c9755..66ab73b 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -27,37 +27,29 @@ compilePackage _ target = do need [ hiboot -<.> obootsuf (detectWay hiboot) ] matchBuildResult buildPath "o" ?> \obj -> do - let way = detectWay obj - cObj = takeFileName obj -<.> "o" - cDeps <- dependencyList cDepsFile cObj - hDeps <- dependencyList hDepsFile obj - let hSrcDeps = filter ("//*hs" ?==) hDeps - - when (null cDeps && null hDeps) $ - putError $ "Cannot determine sources for '" ++ obj ++ "'." - - when (not (null cDeps) && not (null hDeps)) $ - putError $ "Both .c and .hs sources found for '" ++ obj ++ "'." - - need $ hDeps ++ cDeps - - if null cDeps - then build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] - else build $ fullTarget target cDeps (Gcc stage) [obj] + cDeps <- dependencyList cDepsFile (takeFileName obj -<.> "o") + if not (null cDeps) + then do -- obj is produced from a C source file + need cDeps + build $ fullTarget target cDeps (Gcc stage) [obj] + else do -- obj is produced from a Haskell source file + hDeps <- dependencyList hDepsFile obj + when (null hDeps) . putError $ + "No dependencies found for '" ++ obj ++ "'." + let way = detectWay obj + hSrc = head hDeps + unless ("//*hs" ?== hSrc) . putError $ + "No Haskell source file found for '" ++ obj ++ "'." + need hDeps + build $ fullTargetWithWay target [hSrc] (Ghc stage) way [obj] matchBuildResult buildPath "o-boot" ?> \obj -> do - let way = detectWay obj hDeps <- dependencyList hDepsFile obj - let hSrcDeps = filter ("//*hs-boot" ?==) hDeps - - when (null hDeps) $ - putError $ "Cannot determine sources for '" ++ obj ++ "'." - + when (null hDeps) . putError $ + "No dependencies found for '" ++ obj ++ "'." + let way = detectWay obj + hSrc = head hDeps + unless ("//*.hs-boot" ?== hSrc) . putError $ + "No Haskell source file found for '" ++ obj ++ "'." need hDeps - build $ fullTargetWithWay target hSrcDeps (Ghc stage) way [obj] - --- TODO: add support for -dyno --- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot --- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ --- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno --- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) + build $ fullTargetWithWay target [hSrc] (Ghc stage) way [obj] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 8fd9b0b..d9ce835 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -14,6 +14,7 @@ import Settings.TargetDirectory import Rules.Actions import Rules.Resources import Data.List +import qualified System.Directory as IO buildPackageLibrary :: Resources -> StagePackageTarget -> Rules () buildPackageLibrary _ target = do @@ -33,13 +34,16 @@ buildPackageLibrary _ target = do cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] - need $ cObjs ++ hObjs -- this will create split objects if required + -- This will create split objects if required (we don't track them) + need $ cObjs ++ hObjs split <- interpret target splitObjects splitObjs <- if split then fmap concat $ forM hSrcs $ \src -> do - let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*" - fmap (map unifyPath) $ getDirectoryFiles "" [files] + let splitPath = buildPath -/- src ++ "_" ++ osuf way ++ "_split" + contents <- liftIO $ IO.getDirectoryContents splitPath + return . map (splitPath -/-) + . filter (not . all (== '.')) $ contents else return [] build $ fullTarget target (cObjs ++ hObjs ++ splitObjs) Ar [a] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 9c120bc..8ece818 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -11,6 +11,11 @@ import Oracles.PackageData import Settings.Util import Settings.Ways +-- TODO: add support for -dyno +-- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot +-- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ +-- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno +-- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) -- TODO: check code duplication ghcArgs :: Args ghcArgs = stagedBuilder Ghc ? do From git at git.haskell.org Fri Oct 27 00:03:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add tests for matchVersionedFilePath. (0b68ae8) Message-ID: <20171027000351.C1A9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b68ae8b754a400577dbd05e646764742251ec27/ghc >--------------------------------------------------------------- commit 0b68ae8b754a400577dbd05e646764742251ec27 Author: Andrey Mokhov Date: Tue Feb 16 19:26:37 2016 +0000 Add tests for matchVersionedFilePath. >--------------------------------------------------------------- 0b68ae8b754a400577dbd05e646764742251ec27 src/Base.hs | 1 + src/Rules/Selftest.hs | 13 ++++++++++++- 2 files changed, 13 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index a794ea8..372ec78 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -183,6 +183,7 @@ removeDirectoryIfExists d = -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: -- --- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'True'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ --- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index a3cc089..5fafda5 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -3,8 +3,10 @@ module Rules.Selftest (selftestRules) where import Development.Shake -import Settings.Builders.Ar (chunksOfSize) import Test.QuickCheck + +import Base +import Settings.Builders.Ar (chunksOfSize) import Way instance Arbitrary Way where @@ -22,6 +24,15 @@ selftestRules = in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res test $ chunksOfSize 3 ["a","b","c","defg","hi","jk"] == [["a","b","c"],["defg"],["hi"],["jk"]] + test $ matchVersionedFilePath "foo/bar" ".a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" ".a" "foo\\bar.a" == True + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" "" "foo/bar.a" == False + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar-" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar/" "a" "foo/bar-0.1.a" == False + + -- TODO: add automated tests for matchVersionedFilePath too test :: Testable a => a -> Action () test = liftIO . quickCheck From git at git.haskell.org Fri Oct 27 00:03:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds knowledge about Perl (bd5bc65) Message-ID: <20171027000352.205D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd5bc6544a5594bc69027d96b7e30da720812922/ghc >--------------------------------------------------------------- commit bd5bc6544a5594bc69027d96b7e30da720812922 Author: Moritz Angermann Date: Sat Jan 9 14:38:18 2016 +0800 Adds knowledge about Perl Fixes #82. Let's hope this is only a stop gap measure until we get rid of ghc-split as a perl script. >--------------------------------------------------------------- bd5bc6544a5594bc69027d96b7e30da720812922 cfg/system.config.in | 1 + src/Builder.hs | 2 ++ 2 files changed, 3 insertions(+) diff --git a/cfg/system.config.in b/cfg/system.config.in index 292d91f..6338e33 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -40,6 +40,7 @@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ tar = @TarCmd@ +perl = @PerlCmd@ # Information about builders: #============================ diff --git a/src/Builder.hs b/src/Builder.hs index fedcb8a..5450815 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -41,6 +41,7 @@ data Builder = Alex | Ld | Nm | Objdump + | Perl | Ranlib | Tar | Unlit @@ -83,6 +84,7 @@ builderKey builder = case builder of Ld -> "ld" Nm -> "nm" Objdump -> "objdump" + Perl -> "perl" Ranlib -> "ranlib" Tar -> "tar" Unlit -> "unlit" From git at git.haskell.org Fri Oct 27 00:03:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to using one dependency file for all objects. (4914709) Message-ID: <20171027000354.5C1623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4914709cd864e4f28be22ea9e12d60b8f5945ffc/ghc >--------------------------------------------------------------- commit 4914709cd864e4f28be22ea9e12d60b8f5945ffc Author: Andrey Mokhov Date: Mon Aug 10 01:35:55 2015 +0100 Switch to using one dependency file for all objects. >--------------------------------------------------------------- 4914709cd864e4f28be22ea9e12d60b8f5945ffc src/Oracles/Dependencies.hs | 49 +++++++++++++++++++++++++++++++++++++++++++ src/Oracles/DependencyList.hs | 40 ----------------------------------- src/Rules/Dependencies.hs | 30 ++++++++++++++------------ 3 files changed, 66 insertions(+), 53 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs new file mode 100644 index 0000000..c301547 --- /dev/null +++ b/src/Oracles/Dependencies.hs @@ -0,0 +1,49 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} + +module Oracles.Dependencies ( + dependencies, + dependenciesOracle + ) where + +import Base +import Util +import Data.List +import Data.Function +import qualified Data.HashMap.Strict as Map +import Control.Applicative + +newtype DependenciesKey = DependenciesKey (FilePath, FilePath) + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +-- dependencies path obj is an action that looks up dependencies of an object +-- file in a generated dependecy file 'path/.dependencies'. +-- If the dependencies cannot be determined, an appropriate error is raised. +-- Otherwise, a pair (source, depFiles) is returned, such that obj can be +-- produced by compiling 'source'; the latter can also depend on a number of +-- other dependencies listed in depFiles. +dependencies :: FilePath -> FilePath -> Action (FilePath, [FilePath]) +dependencies path obj = do + let depFile = path -/- ".dependencies" + res1 <- askOracle $ DependenciesKey (depFile, obj) + -- if no dependencies found attempt to drop the way prefix (for *.c sources) + res2 <- case res1 of + Nothing -> askOracle $ DependenciesKey (depFile, obj -<.> "o") + _ -> return res1 + case res2 of + Nothing -> putError $ "No dependencies found for '" ++ obj ++ "'." + Just [] -> putError $ "Empty dependency list for '" ++ obj ++ "'." + Just (src:depFiles) -> return (src, depFiles) + +-- Oracle for 'path/dist/.dependencies' files +dependenciesOracle :: Rules () +dependenciesOracle = do + deps <- newCache $ \file -> do + putOracle $ "Reading dependencies from " ++ file ++ "..." + contents <- parseMakefile <$> readFile' file + return . Map.fromList . map (bimap unifyPath (map unifyPath)) + . map (bimap head concat . unzip) + . groupBy ((==) `on` fst) + . sortBy (compare `on` fst) $ contents + + addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file + return () diff --git a/src/Oracles/DependencyList.hs b/src/Oracles/DependencyList.hs deleted file mode 100644 index e571f7b..0000000 --- a/src/Oracles/DependencyList.hs +++ /dev/null @@ -1,40 +0,0 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} - -module Oracles.DependencyList ( - dependencyList, - dependencyListOracle - ) where - -import Base -import Util -import Data.List -import Data.Maybe -import Data.Function -import qualified Data.HashMap.Strict as Map -import Control.Applicative - -newtype DependencyListKey = DependencyListKey (FilePath, FilePath) - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) - --- dependencyList depFile objFile is an action that looks up dependencies of an --- object file (objFile) in a generated dependecy file (depFile). -dependencyList :: FilePath -> FilePath -> Action [FilePath] -dependencyList depFile objFile = do - res <- askOracle $ DependencyListKey (depFile, objFile) - return . fromMaybe [] $ res - --- Oracle for 'path/dist/*.deps' files -dependencyListOracle :: Rules () -dependencyListOracle = do - deps <- newCache $ \file -> do - need [file] - putOracle $ "Reading dependencies from " ++ file ++ "..." - contents <- parseMakefile <$> (liftIO $ readFile file) - return . Map.fromList - . map (bimap unifyPath (map unifyPath)) - . map (bimap head concat . unzip) - . groupBy ((==) `on` fst) - . sortBy (compare `on` fst) $ contents - addOracle $ \(DependencyListKey (file, obj)) -> - Map.lookup (unifyPath obj) <$> deps (unifyPath file) - return () diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index ea47241..90c764f 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -19,20 +19,24 @@ buildPackageDependencies _ target = path = targetPath stage pkg buildPath = path -/- "build" dropBuild = (pkgPath pkg ++) . drop (length buildPath) + hDepFile = buildPath -/- ".hs-dependencies" in do - (buildPath "*.c.deps") %> \depFile -> do - let srcFile = dropBuild . dropExtension $ depFile + (buildPath "*.c.deps") %> \file -> do + let srcFile = dropBuild . dropExtension $ file need [srcFile] - build $ fullTarget target [srcFile] (GccM stage) [depFile] + build $ fullTarget target (GccM stage) [srcFile] [file] - (buildPath -/- "c.deps") %> \file -> do - srcs <- pkgDataList $ CSrcs path - let depFiles = [ buildPath -/- src <.> "deps" | src <- srcs ] - need depFiles - deps <- mapM readFile' depFiles - writeFileChanged file (concat deps) - - (buildPath -/- "haskell.deps") %> \file -> do - srcs <- interpret target getHsSources + hDepFile %> \file -> do + srcs <- interpret target getPackageSources need srcs - build $ fullTarget target srcs (GhcM stage) [file] + build $ fullTarget target (GhcM stage) srcs [file] + liftIO $ removeFiles "." [hDepFile <.> "bak"] + + (buildPath -/- ".dependencies") %> \file -> do + cSrcs <- pkgDataList $ CSrcs path + let cDepFiles = [ buildPath -/- src <.> "deps" | src <- cSrcs ] + need $ hDepFile : cDepFiles -- need all for more parallelism + cDeps <- fmap concat $ mapM readFile' cDepFiles + hDeps <- readFile' hDepFile + writeFileChanged file $ cDeps ++ hDeps + From git at git.haskell.org Fri Oct 27 00:03:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't unify paths as it seems prone to surprises. (a849c93) Message-ID: <20171027000355.AA16C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a849c93a1f092e6c611d1bd4fae68b91612bfadb/ghc >--------------------------------------------------------------- commit a849c93a1f092e6c611d1bd4fae68b91612bfadb Author: Andrey Mokhov Date: Tue Feb 16 23:09:34 2016 +0000 Don't unify paths as it seems prone to surprises. >--------------------------------------------------------------- a849c93a1f092e6c611d1bd4fae68b91612bfadb src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 372ec78..769fdc4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -183,7 +183,7 @@ removeDirectoryIfExists d = -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: -- --- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'False'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ --- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ @@ -191,6 +191,6 @@ removeDirectoryIfExists d = --- * @'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False'@ matchVersionedFilePath :: String -> String -> FilePath -> Bool matchVersionedFilePath prefix suffix filePath = - case stripPrefix prefix (unifyPath filePath) >>= stripSuffix suffix of + case stripPrefix prefix filePath >>= stripSuffix suffix of Nothing -> False Just version -> all (\c -> isDigit c || c == '-' || c == '.') version From git at git.haskell.org Fri Oct 27 00:05:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to a more ambitious build target. (f168dc4) Message-ID: <20171027000554.E221E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f168dc4eaef267ce321821088dba79d961617a88/ghc >--------------------------------------------------------------- commit f168dc4eaef267ce321821088dba79d961617a88 Author: Andrey Mokhov Date: Sun Jan 10 00:30:03 2016 +0000 Switch to a more ambitious build target. See #110. [skip ci] >--------------------------------------------------------------- f168dc4eaef267ce321821088dba79d961617a88 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index e7cf731..b2f27af 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-cabal.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/libHSghc-boot-8.1.a From git at git.haskell.org Fri Oct 27 00:05:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (d8a249b) Message-ID: <20171027000555.DD9453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d8a249b43b494428675b85fab7e53dff4ce859d9/ghc >--------------------------------------------------------------- commit d8a249b43b494428675b85fab7e53dff4ce859d9 Author: Andrey Mokhov Date: Fri Feb 26 19:00:31 2016 +0000 Add comments. See #55. >--------------------------------------------------------------- d8a249b43b494428675b85fab7e53dff4ce859d9 src/Settings/Paths.hs | 31 ++++++++++++++++++------------- 1 file changed, 18 insertions(+), 13 deletions(-) diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 6ad6b9d..629d6d0 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -11,58 +11,63 @@ import GHC import Oracles.PackageData import Settings.User --- Path to the target directory from GHC source root +-- | Path to the directory containing build artefacts of a given 'Context'. contextPath :: Context -> FilePath contextPath context at Context {..} = buildRootPath -/- contextDirectory context -/- pkgPath package +-- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath pkgDataFile context = contextPath context -/- "package-data.mk" --- Relative path to a package haddock file, e.g.: --- "libraries/array/dist-install/doc/html/array/array.haddock" +-- | Path to the haddock file of a given 'Context', e.g.: +-- ".build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = contextPath context -/- "doc/html" -/- name -/- name <.> "haddock" where name = pkgNameString package --- Relative path to a package library file, e.g.: --- "libraries/array/stage2/build/libHSarray-0.5.1.0.a" +-- | Path to the library file of a given 'Context', e.g.: +-- ".build/stage1/libraries/array/build/libHSarray-0.5.1.0.a". pkgLibraryFile :: Context -> Action FilePath pkgLibraryFile context at Context {..} = do extension <- libsuf way - pkgFile context "build/libHS" extension + pkgFile context "libHS" extension +-- | Path to the auxiliary library file of a given 'Context', e.g.: +-- ".build/stage1/compiler/build/libHSghc-8.1-0.a". pkgLibraryFile0 :: Context -> Action FilePath pkgLibraryFile0 context at Context {..} = do extension <- libsuf way - pkgFile context "build/libHS" ("-0" ++ extension) + pkgFile context "libHS" ("-0" ++ extension) --- Relative path to a package ghci library file, e.g.: --- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" +-- | Path to the GHCi library file of a given 'Context', e.g.: +-- ".build/stage1/libraries/array/build/HSarray-0.5.1.0.o". pkgGhciLibraryFile :: Context -> Action FilePath -pkgGhciLibraryFile context = pkgFile context "build/HS" ".o" +pkgGhciLibraryFile context = pkgFile context "HS" ".o" pkgFile :: Context -> String -> String -> Action FilePath pkgFile context prefix suffix = do let path = contextPath context componentId <- pkgData $ ComponentId path - return $ path -/- prefix ++ componentId ++ suffix + return $ path -/- "build" -/- prefix ++ componentId ++ suffix --- This is the build directory for in-tree GMP library +-- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" --- We extract system gmp library name from this file +-- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory +-- | Path to package database directory of a given 'Stage'. packageDbDirectory :: Stage -> FilePath packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" +-- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do componentId <- pkgData . ComponentId $ contextPath context From git at git.haskell.org Fri Oct 27 00:05:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement interestingInfo for Haddock. (c6b59ef) Message-ID: <20171027000557.40BAC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6b59ef5c98617955b4c4c98742cc99b68371fd6/ghc >--------------------------------------------------------------- commit c6b59ef5c98617955b4c4c98742cc99b68371fd6 Author: Andrey Mokhov Date: Fri Aug 21 23:39:40 2015 +0100 Implement interestingInfo for Haddock. >--------------------------------------------------------------- c6b59ef5c98617955b4c4c98742cc99b68371fd6 src/Rules/Actions.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d73c6a7..e58669a 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -50,6 +50,7 @@ interestingInfo builder ss = case builder of Ghc _ -> prefixAndSuffix 0 4 ss GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss + Haddock -> prefixAndSuffix 1 0 ss GhcCabal -> prefixAndSuffix 3 0 ss _ -> ss where From git at git.haskell.org Fri Oct 27 00:05:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Quote cache path. (1b36ea9) Message-ID: <20171027000558.8230C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b36ea956be80db55406fffc868cb676de5ce100/ghc >--------------------------------------------------------------- commit 1b36ea956be80db55406fffc868cb676de5ce100 Author: Andrey Mokhov Date: Sun Jan 10 00:42:55 2016 +0000 Quote cache path. See #110. [skip ci] >--------------------------------------------------------------- 1b36ea956be80db55406fffc868cb676de5ce100 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index b2f27af..176fb2a 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -4,7 +4,7 @@ environment: STACK_ROOT: "c:\\sr" cache: - - c:\\sr + - "c:\\sr" install: - cd @@ -30,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/libHSghc-boot-8.1.a + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/build/libHSghc-boot-8.1.a From git at git.haskell.org Fri Oct 27 00:05:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant 'build' component in build paths, rename contextPath to buildPath. (0d7891b) Message-ID: <20171027000559.7D98A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0d7891b43ae5f3bd4dd6b271749187cfd4a24f77/ghc >--------------------------------------------------------------- commit 0d7891b43ae5f3bd4dd6b271749187cfd4a24f77 Author: Andrey Mokhov Date: Fri Feb 26 22:36:38 2016 +0000 Drop redundant 'build' component in build paths, rename contextPath to buildPath. >--------------------------------------------------------------- 0d7891b43ae5f3bd4dd6b271749187cfd4a24f77 src/Oracles/ModuleFiles.hs | 16 +++++++--------- src/Rules/Compile.hs | 18 +++++++++--------- src/Rules/Data.hs | 18 +++++++++--------- src/Rules/Dependencies.hs | 15 +++++++-------- src/Rules/Generate.hs | 29 +++++++++++++---------------- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 18 +++++++++--------- src/Rules/Program.hs | 10 +++++----- src/Rules/Register.hs | 13 +++++++------ src/Settings.hs | 10 +++++----- src/Settings/Builders/Common.hs | 7 +++---- src/Settings/Builders/Ghc.hs | 19 ++++++++----------- src/Settings/Builders/Haddock.hs | 4 ++-- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 4 ++-- src/Settings/Packages/Hp2ps.hs | 2 +- src/Settings/Packages/Rts.hs | 4 ++-- src/Settings/Packages/Touchy.hs | 4 ++-- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/Paths.hs | 16 ++++++++-------- 23 files changed, 107 insertions(+), 116 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 0d7891b43ae5f3bd4dd6b271749187cfd4a24f77 From git at git.haskell.org Fri Oct 27 00:06:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Haddock arguments. (bf86f0e) Message-ID: <20171027000600.B7D053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf86f0ec66186df924ba0e173ba606fe39ddbf1b/ghc >--------------------------------------------------------------- commit bf86f0ec66186df924ba0e173ba606fe39ddbf1b Author: Andrey Mokhov Date: Sat Aug 22 00:26:44 2015 +0100 Fix Haddock arguments. >--------------------------------------------------------------- bf86f0ec66186df924ba0e173ba606fe39ddbf1b src/Settings/Builders/Haddock.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 19c1979..0e839ce 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -26,6 +26,7 @@ haddockArgs = builder Haddock ? do ghcOpts <- fromDiffExpr commonGhcArgs mconcat [ arg $ "--odir=" ++ takeDirectory file + , arg "--verbosity=0" , arg "--no-tmp-comp-dir" , arg $ "--dump-interface=" ++ file , arg "--html" @@ -39,12 +40,14 @@ haddockArgs = builder Haddock ? do | (dep, depName) <- zip deps depNames , Just depPkg <- [findKnownPackage depName] ] , append [ "--optghc=" ++ opt | opt <- ghcOpts ] - , arg "--source-module=src/%{MODULE/./-}.html" - , arg "--source-entity=src/%{MODULE/./-}.html\\#%{NAME}" + , specified HsColour ? + arg "--source-module=src/%{MODULE/./-}.html" + , specified HsColour ? + arg "--source-entity=src/%{MODULE/./-}.html\\#%{NAME}" , customPackageArgs , append srcs , arg "+RTS" - , arg $ "-t" ++ file <.> "t" + , arg $ "-t" ++ path "haddock.t" , arg "--machine-readable" ] customPackageArgs :: Args From git at git.haskell.org Fri Oct 27 00:06:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to build stage1 GHC. (c217881) Message-ID: <20171027000602.2A3383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c217881e59c759dc519e56f246ccb9ab56a6e7d4/ghc >--------------------------------------------------------------- commit c217881e59c759dc519e56f246ccb9ab56a6e7d4 Author: Andrey Mokhov Date: Sun Jan 10 02:20:00 2016 +0000 Attempt to build stage1 GHC. See #110. [skip ci] >--------------------------------------------------------------- c217881e59c759dc519e56f246ccb9ab56a6e7d4 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 176fb2a..f4f1d83 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/build/libHSghc-boot-8.1.a + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:06:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use default project name on AppVeyor. (2e3ec0c) Message-ID: <20171027000603.1E7793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2e3ec0cce02a1f125b5672b2f7a5fb85afee0605/ghc >--------------------------------------------------------------- commit 2e3ec0cce02a1f125b5672b2f7a5fb85afee0605 Author: Andrey Mokhov Date: Fri Feb 26 22:55:25 2016 +0000 Use default project name on AppVeyor. >--------------------------------------------------------------- 2e3ec0cce02a1f125b5672b2f7a5fb85afee0605 .appveyor.yml => appveyor.yml | 0 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/.appveyor.yml b/appveyor.yml similarity index 100% rename from .appveyor.yml rename to appveyor.yml From git at git.haskell.org Fri Oct 27 00:06:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add runghcid.bat. (14c35b5) Message-ID: <20171027000604.449663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14c35b529b90f9b5578c086a603c4c496c7b5c07/ghc >--------------------------------------------------------------- commit 14c35b529b90f9b5578c086a603c4c496c7b5c07 Author: Andrey Mokhov Date: Sat Aug 22 17:59:18 2015 +0100 Add runghcid.bat. >--------------------------------------------------------------- 14c35b529b90f9b5578c086a603c4c496c7b5c07 runghcid.bat | 1 + 1 file changed, 1 insertion(+) diff --git a/runghcid.bat b/runghcid.bat new file mode 100644 index 0000000..f2f8ddc --- /dev/null +++ b/runghcid.bat @@ -0,0 +1 @@ +ghcid --height=8 --topmost "--command=ghci -isrc -Wall src/Main.hs" From git at git.haskell.org Fri Oct 27 00:06:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move build artefacts to .build/ directory. (eda85ff) Message-ID: <20171027000606.0E8863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eda85ffd9bca4b43667b9a172fc5a4b888f018cd/ghc >--------------------------------------------------------------- commit eda85ffd9bca4b43667b9a172fc5a4b888f018cd Author: Andrey Mokhov Date: Sun Jan 10 05:02:18 2016 +0000 Move build artefacts to .build/ directory. See #113. >--------------------------------------------------------------- eda85ffd9bca4b43667b9a172fc5a4b888f018cd src/Base.hs | 2 ++ src/GHC.hs | 33 +--------------------- src/Oracles/LookupInPath.hs | 15 ++++------ src/Oracles/PackageDeps.hs | 4 +-- src/Rules/Compile.hs | 3 +- src/Rules/Config.hs | 1 + src/Rules/Data.hs | 62 ++++++++++++++++++++++++++--------------- src/Rules/Dependencies.hs | 10 +++++-- src/Rules/Generate.hs | 6 ++-- src/Rules/IntegerGmp.hs | 1 + src/Rules/Libffi.hs | 10 ++++--- src/Rules/Library.hs | 13 ++++++--- src/Rules/Program.hs | 4 +-- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Builders/GhcPkg.hs | 6 ++-- src/Settings/Default.hs | 36 ++++++++++++++++++++++-- src/Settings/Packages/Rts.hs | 5 ++-- src/Settings/TargetDirectory.hs | 4 +-- src/Settings/User.hs | 26 +++++++++-------- 19 files changed, 143 insertions(+), 101 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 eda85ffd9bca4b43667b9a172fc5a4b888f018cd From git at git.haskell.org Fri Oct 27 00:06:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing arguments for rts package. (13b1491) Message-ID: <20171027000606.A86DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13b1491faf02d9e03385ad61a26bf90cbc951fda/ghc >--------------------------------------------------------------- commit 13b1491faf02d9e03385ad61a26bf90cbc951fda Author: Andrey Mokhov Date: Sun Feb 28 23:47:46 2016 +0000 Add missing arguments for rts package. >--------------------------------------------------------------- 13b1491faf02d9e03385ad61a26bf90cbc951fda src/Settings/Packages/Rts.hs | 16 +++++++--------- 1 file changed, 7 insertions(+), 9 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 334a712..ba79289 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -62,7 +62,9 @@ rtsPackageArgs = package rts ? do -- there is a non-inlined variant to use instead. But rts does not -- provide non-inlined alternatives and hence needs the function to -- be inlined. See also Issue #90 - , arg $ "-O2" + , arg "-O2" + + , way == threaded ? arg "-DTHREADED_RTS" , (file "//RtsMessages.*" ||^ file "//Trace.*") ? arg ("-DProjectVersion=" ++ quote projectVersion) @@ -82,7 +84,10 @@ rtsPackageArgs = package rts ? do , "-DTargetOS=" ++ quote targetOs , "-DTargetVendor=" ++ quote targetVendor , "-DGhcUnregisterised=" ++ quote ghcUnreg - , "-DGhcEnableTablesNextToCode=" ++ quote ghcEnableTNC ] ] + , "-DGhcEnableTablesNextToCode=" ++ quote ghcEnableTNC ] + + , (file "//Evac_thr.*" ||^ file "//Scav_thr.*") ? + append [ "-DPARALLEL_GC", "-Irts/sm" ] ] , builderGhc ? (arg "-Irts" <> includesArgs) @@ -233,10 +238,3 @@ rtsPackageArgs = package rts ? do -- # -O3 helps unroll some loops (especially in copy() with a constant argument). -- rts/sm/Evac_CC_OPTS += -funroll-loops -- rts/dist/build/sm/Evac_thr_HC_OPTS += -optc-funroll-loops - --- # These files are just copies of sm/Evac.c and sm/Scav.c respectively, --- # but compiled with -DPARALLEL_GC. --- rts/dist/build/sm/Evac_thr_CC_OPTS += -DPARALLEL_GC -Irts/sm --- rts/dist/build/sm/Scav_thr_CC_OPTS += -DPARALLEL_GC -Irts/sm - --- #----------------------------------------------------------------------------- From git at git.haskell.org Fri Oct 27 00:06:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use -Wall when compiling the build system. (134cac9) Message-ID: <20171027000607.9FF7C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/134cac9ab3a450be48cadce39a0faac00be227fb/ghc >--------------------------------------------------------------- commit 134cac9ab3a450be48cadce39a0faac00be227fb Author: Andrey Mokhov Date: Sat Aug 22 17:59:54 2015 +0100 Use -Wall when compiling the build system. >--------------------------------------------------------------- 134cac9ab3a450be48cadce39a0faac00be227fb build.bat | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.bat b/build.bat index b6b9a82..b45bdde 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,2 @@ @mkdir _shake 2> nul - at ghc --make -fwarn-tabs -fwarn-unused-imports src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* From git at git.haskell.org Fri Oct 27 00:06:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix include paths. (1d18a74) Message-ID: <20171027000609.76F0C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1d18a749606d4c093b00e8f4823b89597dae4c9a/ghc >--------------------------------------------------------------- commit 1d18a749606d4c093b00e8f4823b89597dae4c9a Author: Andrey Mokhov Date: Sun Jan 10 12:11:11 2016 +0000 Fix include paths. See #145. >--------------------------------------------------------------- 1d18a749606d4c093b00e8f4823b89597dae4c9a src/Settings/Builders/HsCpp.hs | 4 +++- src/Settings/Packages/Ghc.hs | 4 ++-- src/Settings/Packages/IntegerGmp.hs | 1 + src/Settings/Packages/IservBin.hs | 3 +-- 4 files changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs index 89980ee..43b9455 100644 --- a/src/Settings/Builders/HsCpp.hs +++ b/src/Settings/Builders/HsCpp.hs @@ -1,9 +1,11 @@ module Settings.Builders.HsCpp (hsCppBuilderArgs) where import Expression +import GHC import Oracles import Predicates (builder) import Settings.Builders.GhcCabal +import Settings.TargetDirectory hsCppBuilderArgs :: Args hsCppBuilderArgs = builder HsCpp ? do @@ -11,7 +13,7 @@ hsCppBuilderArgs = builder HsCpp ? do mconcat [ append =<< getSettingList HsCppArgs , arg "-P" , cppArgs - , arg $ "-Icompiler/" ++ stageString stage + , arg $ "-I" ++ targetPath stage compiler , arg "-x" , arg "c" , arg =<< getInput ] diff --git a/src/Settings/Packages/Ghc.hs b/src/Settings/Packages/Ghc.hs index efc059d..0830cb6 100644 --- a/src/Settings/Packages/Ghc.hs +++ b/src/Settings/Packages/Ghc.hs @@ -1,16 +1,16 @@ module Settings.Packages.Ghc (ghcPackageArgs) where -import Base import Expression import GHC (ghc, compiler) import Oracles.Config.Setting import Predicates (builder, builderGhc, package, notStage0) +import Settings.TargetDirectory ghcPackageArgs :: Args ghcPackageArgs = package ghc ? do stage <- getStage mconcat [ builderGhc ? mconcat - [ arg ("-I" ++ pkgPath compiler -/- stageString stage) + [ arg $ "-I" ++ targetPath stage compiler , arg "-no-hs-main" ] , builder GhcCabal ? diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 6d1b2b6..c679bf3 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -5,6 +5,7 @@ import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) +-- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" -- libraries/integer-gmp_CONFIGURE_OPTS += --with-gmp-framework-preferred diff --git a/src/Settings/Packages/IservBin.hs b/src/Settings/Packages/IservBin.hs index 5ad3bd5..a662d1c 100644 --- a/src/Settings/Packages/IservBin.hs +++ b/src/Settings/Packages/IservBin.hs @@ -6,5 +6,4 @@ import Predicates (builderGhc, package) iservBinPackageArgs :: Args iservBinPackageArgs = package iservBin ? do - mconcat [ builderGhc ? - mconcat [ arg "-no-hs-main" ]] + mconcat [ builderGhc ? arg "-no-hs-main" ] From git at git.haskell.org Fri Oct 27 00:06:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix haddock. (7e7497a) Message-ID: <20171027000610.26ACB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1/ghc >--------------------------------------------------------------- commit 7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1 Author: Andrey Mokhov Date: Mon Feb 29 02:02:53 2016 +0000 Fix haddock. >--------------------------------------------------------------- 7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1 src/Rules/Data.hs | 18 +++++++++--------- src/Rules/Dependencies.hs | 35 ++++++++++++++++++++++++----------- src/Rules/Generate.hs | 16 +++++++++------- src/Rules/Library.hs | 33 +++++++++++++++++++++------------ src/Settings/Packages/Rts.hs | 19 +++++++++---------- 5 files changed, 72 insertions(+), 49 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 7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1 From git at git.haskell.org Fri Oct 27 00:06:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports. (c125896) Message-ID: <20171027000611.250393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1258966f7b34115402c8d4f2243cc2e75cb1deb/ghc >--------------------------------------------------------------- commit c1258966f7b34115402c8d4f2243cc2e75cb1deb Author: Andrey Mokhov Date: Sat Aug 22 18:00:14 2015 +0100 Refactor imports. >--------------------------------------------------------------- c1258966f7b34115402c8d4f2243cc2e75cb1deb src/Base.hs | 15 +++++++-------- src/Builder.hs | 11 +++-------- src/Expression.hs | 20 +++++++++++--------- src/Main.hs | 10 ++++++---- src/Oracles/Base.hs | 17 +++++++++-------- src/Oracles/Dependencies.hs | 2 -- src/Oracles/Flag.hs | 3 --- src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 3 --- src/Oracles/Setting.hs | 1 - src/Oracles/WindowsRoot.hs | 1 - src/Package.hs | 8 +++----- src/Predicates.hs | 6 +----- src/Rules.hs | 19 +++++-------------- src/Rules/Cabal.hs | 1 - src/Rules/Config.hs | 2 -- src/Rules/Data.hs | 7 ++----- src/Rules/Dependencies.hs | 3 +-- src/Rules/Documentation.hs | 1 - src/Rules/Library.hs | 20 +++++++------------- src/Rules/Oracles.hs | 11 ++++------- src/Rules/Package.hs | 8 ++++---- src/Rules/Resources.hs | 6 ++---- src/Settings/Builders/Gcc.hs | 11 +++++------ src/Settings/Builders/Ghc.hs | 9 +++------ src/Settings/Builders/Haddock.hs | 1 - src/Settings/Packages.hs | 1 - src/Settings/Util.hs | 4 +--- src/Stage.hs | 10 ++++------ src/Target.hs | 12 ++++++------ src/Util.hs | 37 +++++++++++++++++++++---------------- src/Way.hs | 14 +++++--------- 32 files changed, 110 insertions(+), 165 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c1258966f7b34115402c8d4f2243cc2e75cb1deb From git at git.haskell.org Fri Oct 27 00:06:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Postprocess inplace-pkg-config files. (f84ee22) Message-ID: <20171027000613.35C533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f84ee22ff9c333ccd1625f06931e339b23e6e7cf/ghc >--------------------------------------------------------------- commit f84ee22ff9c333ccd1625f06931e339b23e6e7cf Author: Andrey Mokhov Date: Sun Jan 10 14:24:58 2016 +0000 Postprocess inplace-pkg-config files. See #113 and #148. >--------------------------------------------------------------- f84ee22ff9c333ccd1625f06931e339b23e6e7cf src/Rules/Data.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 9aeb7b3..4428b35 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -54,7 +54,17 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- ghc-pkg produces inplace-pkg-config when run on packages with -- library components only when (isLibrary pkg) . - whenM (interpretPartial target registerPackage) . + whenM (interpretPartial target registerPackage) $ do + + -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 + let fixPkgConf = unlines + . map (replace oldPath (targetPath stage pkg) + . replace (replaceSeparators '\\' $ oldPath) + (targetPath stage pkg) ) + . lines + + fixFile (oldPath -/- "inplace-pkg-config") fixPkgConf + buildWithResources [(resGhcPkg rs, 1)] $ fullTarget target (GhcPkg stage) [cabalFile] [] From git at git.haskell.org Fri Oct 27 00:06:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add docs for how to compile on Windows, with a list of complete instructions (3dcbe7a) Message-ID: <20171027000613.CF8B73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3dcbe7a62e7ad62016456000c925d6493e509a2e/ghc >--------------------------------------------------------------- commit 3dcbe7a62e7ad62016456000c925d6493e509a2e Author: Neil Mitchell Date: Thu Mar 3 20:52:50 2016 +0000 Add docs for how to compile on Windows, with a list of complete instructions >--------------------------------------------------------------- 3dcbe7a62e7ad62016456000c925d6493e509a2e doc/windows.md | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) diff --git a/doc/windows.md b/doc/windows.md new file mode 100644 index 0000000..2d823e7 --- /dev/null +++ b/doc/windows.md @@ -0,0 +1,26 @@ +# Compiling on Windows + +Here are a list of instructions to compile GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. + +The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_64-installer) (I just accepted all the defaults), then open a command prompt and run: + + stack setup + stack install happy alex + stack exec -- pacman -S gcc binutils git automake-wrapper tar make patch autoconf --noconfirm + stack exec -- git clone --recursive git://git.haskell.org/ghc.git + cd ghc + stack exec -- git clone git://github.com/snowleopard/shaking-up-ghc shake-build + stack build --stack-yaml=shake-build/stack.yaml --only-dependencies + stack exec -- perl boot + stack exec -- bash configure --enable-tarballs-autodownload + stack exec --stack-yaml=shake-build/stack.yaml -- shake-build/build.bat -j + +The entire process should take about an hour. + +#### Future ideas + +Here are some alternatives that have been considered, but not yet tested. Use the instructions above. + +* Use `shake-build/build.bat --setup` to replace `boot` and `configure`. +* The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. +* Can Happy/Alex be installed by adding them as tool dependencies to the Stack file? From git at git.haskell.org Fri Oct 27 00:06:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Oracles. (d4a438f) Message-ID: <20171027000614.CEE813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf/ghc >--------------------------------------------------------------- commit d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf Author: Andrey Mokhov Date: Sat Aug 22 18:47:04 2015 +0100 Refactor Oracles. >--------------------------------------------------------------- d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf src/Builder.hs | 7 +++---- src/Oracles.hs | 17 +++++++++++++++++ src/Oracles/ArgsHash.hs | 4 ++-- src/Oracles/{Base.hs => Config.hs} | 9 +-------- src/Oracles/{ => Config}/Flag.hs | 8 +++++--- src/Oracles/{ => Config}/Setting.hs | 5 +++-- src/Oracles/Dependencies.hs | 1 - src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 3 ++- src/Predicates.hs | 3 +-- src/Rules/Actions.hs | 2 +- src/Rules/Oracles.hs | 19 +++++++------------ src/Settings/Builders/Ghc.hs | 3 +-- src/Settings/Builders/GhcCabal.hs | 3 +-- src/Settings/Builders/Ld.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/Util.hs | 4 +--- src/Settings/Ways.hs | 2 +- src/Util.hs | 2 ++ src/Way.hs | 2 +- 20 files changed, 51 insertions(+), 48 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 d4a438fbb9b163e3c5c2fef1bc4c1bffe41310bf From git at git.haskell.org Fri Oct 27 00:06:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/snowleopard/shaking-up-ghc (c96b1e9) Message-ID: <20171027000617.54CCD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c96b1e9f8ffdd430787ee8cd2f016d3474ffba9a/ghc >--------------------------------------------------------------- commit c96b1e9f8ffdd430787ee8cd2f016d3474ffba9a Merge: 9ae96f4 f84ee22 Author: Neil Mitchell Date: Sun Jan 10 20:28:45 2016 +0000 Merge branch 'master' of https://github.com/snowleopard/shaking-up-ghc >--------------------------------------------------------------- c96b1e9f8ffdd430787ee8cd2f016d3474ffba9a .appveyor.yml | 6 +++ src/Base.hs | 2 + src/GHC.hs | 33 +---------------- src/Oracles/LookupInPath.hs | 15 +++----- src/Oracles/PackageDeps.hs | 4 +- src/Rules/Compile.hs | 3 +- src/Rules/Config.hs | 1 + src/Rules/Data.hs | 74 +++++++++++++++++++++++++------------ src/Rules/Dependencies.hs | 10 ++++- src/Rules/Generate.hs | 6 ++- src/Rules/IntegerGmp.hs | 1 + src/Rules/Libffi.hs | 10 +++-- src/Rules/Library.hs | 13 +++++-- src/Rules/Program.hs | 4 +- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Builders/GhcPkg.hs | 6 ++- src/Settings/Builders/HsCpp.hs | 4 +- src/Settings/Default.hs | 36 +++++++++++++++++- src/Settings/Packages/Ghc.hs | 4 +- src/Settings/Packages/IntegerGmp.hs | 1 + src/Settings/Packages/IservBin.hs | 3 +- src/Settings/Packages/Rts.hs | 5 ++- src/Settings/TargetDirectory.hs | 4 +- src/Settings/User.hs | 26 +++++++------ 24 files changed, 167 insertions(+), 107 deletions(-) diff --cc src/Oracles/LookupInPath.hs index d573fd7,e75a80d..a9dc995 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@@ -1,9 -1,8 +1,7 @@@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} - module Oracles.LookupInPath ( - lookupInPath, lookupInPathOracle - ) where + module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where import Base -import Extra (wordsBy) newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) From git at git.haskell.org Fri Oct 27 00:06:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on how to install Happy/Alex better (2d02668) Message-ID: <20171027000618.2D58E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d0266864b16b273b7e6d296a42fa60bf75d9bd0/ghc >--------------------------------------------------------------- commit 2d0266864b16b273b7e6d296a42fa60bf75d9bd0 Author: Neil Mitchell Date: Thu Mar 3 23:18:44 2016 +0000 Add a note on how to install Happy/Alex better >--------------------------------------------------------------- 2d0266864b16b273b7e6d296a42fa60bf75d9bd0 doc/windows.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/windows.md b/doc/windows.md index 2d823e7..aa7a560 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -23,4 +23,4 @@ Here are some alternatives that have been considered, but not yet tested. Use th * Use `shake-build/build.bat --setup` to replace `boot` and `configure`. * The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. -* Can Happy/Alex be installed by adding them as tool dependencies to the Stack file? +* Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:06:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Settings/Default.hs to GHC.hs, add Settings.hs. (f68d70f) Message-ID: <20171027000618.BA3203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f68d70f07527618af262cf45d84c5ca898b166b7/ghc >--------------------------------------------------------------- commit f68d70f07527618af262cf45d84c5ca898b166b7 Author: Andrey Mokhov Date: Sat Aug 22 19:20:11 2015 +0100 Move Settings/Default.hs to GHC.hs, add Settings.hs. >--------------------------------------------------------------- f68d70f07527618af262cf45d84c5ca898b166b7 src/{Settings/Default.hs => GHC.hs} | 32 ++++++++++++++++---------------- src/Oracles/ArgsHash.hs | 2 +- src/Predicates.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 9 ++++----- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 5 +---- src/Rules/Library.hs | 2 +- src/Settings.hs | 13 +++++++++++++ src/Settings/Args.hs | 3 +-- src/Settings/Builders/Ghc.hs | 3 +-- src/Settings/Builders/GhcCabal.hs | 5 +---- src/Settings/Packages.hs | 14 +++++--------- src/Settings/User.hs | 4 +--- 16 files changed, 50 insertions(+), 52 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 f68d70f07527618af262cf45d84c5ca898b166b7 From git at git.haskell.org Fri Oct 27 00:06:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hide parallel when importing from Development.Shake (6c81e9a) Message-ID: <20171027000621.3B10A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6c81e9aef6f0eaa626f27ceb6ed4a3d2af269a43/ghc >--------------------------------------------------------------- commit 6c81e9aef6f0eaa626f27ceb6ed4a3d2af269a43 Author: Neil Mitchell Date: Sun Jan 10 20:31:24 2016 +0000 Hide parallel when importing from Development.Shake >--------------------------------------------------------------- 6c81e9aef6f0eaa626f27ceb6ed4a3d2af269a43 src/Base.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 6d80a72..54f2f99 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,3 +1,5 @@ +{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} + module Base ( -- * General utilities module Control.Applicative, @@ -34,7 +36,7 @@ import Data.Function import Data.List.Extra import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>)) +import Development.Shake hiding (parallel, unit, (*>)) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Fri Oct 27 00:06:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #212 from ndmitchell/master (a5a37b9) Message-ID: <20171027000621.E3EAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a37b93f8d6e4a521a3770bc0a4b8b6c8bc5fe4/ghc >--------------------------------------------------------------- commit a5a37b93f8d6e4a521a3770bc0a4b8b6c8bc5fe4 Merge: 7e7497a 2d02668 Author: Andrey Mokhov Date: Thu Mar 3 23:40:30 2016 +0000 Merge pull request #212 from ndmitchell/master Add docs for how to compile on Windows [skip ci] >--------------------------------------------------------------- a5a37b93f8d6e4a521a3770bc0a4b8b6c8bc5fe4 doc/windows.md | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) From git at git.haskell.org Fri Oct 27 00:06:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge Base.hs and Util.hs. (190f3fd) Message-ID: <20171027000622.56BD73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/190f3fde35a3230bbdfe50afce81dd5e10590c24/ghc >--------------------------------------------------------------- commit 190f3fde35a3230bbdfe50afce81dd5e10590c24 Author: Andrey Mokhov Date: Sat Aug 22 21:03:38 2015 +0100 Merge Base.hs and Util.hs. >--------------------------------------------------------------- 190f3fde35a3230bbdfe50afce81dd5e10590c24 src/Base.hs | 119 +++++++++++++++++++++++++++++++++++++- src/Builder.hs | 1 - src/Expression.hs | 3 +- src/Oracles/ArgsHash.hs | 2 - src/Oracles/Config.hs | 1 - src/Oracles/Config/Flag.hs | 1 - src/Oracles/Dependencies.hs | 1 - src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 1 - src/Oracles/WindowsRoot.hs | 1 - src/Package.hs | 1 - src/Predicates.hs | 1 - src/Rules.hs | 6 +- src/Rules/Actions.hs | 3 - src/Rules/Cabal.hs | 1 - src/Rules/Compile.hs | 1 - src/Rules/Config.hs | 1 - src/Rules/Data.hs | 2 - src/Rules/Dependencies.hs | 2 - src/Rules/Documentation.hs | 1 - src/Rules/Library.hs | 7 +-- src/Rules/Package.hs | 1 - src/Rules/Resources.hs | 1 - src/Settings/Args.hs | 2 +- src/Settings/Builders/Gcc.hs | 2 - src/Settings/Builders/Ghc.hs | 1 - src/Settings/Builders/GhcCabal.hs | 2 - src/Settings/Builders/GhcPkg.hs | 1 - src/Settings/Builders/Haddock.hs | 2 - src/Settings/TargetDirectory.hs | 1 - src/Settings/Util.hs | 1 - src/Settings/Ways.hs | 1 - src/Target.hs | 1 - src/Util.hs | 117 ------------------------------------- src/Way.hs | 3 +- 35 files changed, 124 insertions(+), 169 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 190f3fde35a3230bbdfe50afce81dd5e10590c24 From git at git.haskell.org Fri Oct 27 00:06:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove qualification on parallel identifiers (aaf934d) Message-ID: <20171027000624.BABB33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aaf934d0677ddd675918e2bd075c0a1015a4d7bf/ghc >--------------------------------------------------------------- commit aaf934d0677ddd675918e2bd075c0a1015a4d7bf Author: Neil Mitchell Date: Sun Jan 10 20:31:37 2016 +0000 Remove qualification on parallel identifiers >--------------------------------------------------------------- aaf934d0677ddd675918e2bd075c0a1015a4d7bf src/GHC.hs | 4 ++-- src/Way.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 54f94d9..c0013ad 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,7 +4,7 @@ module GHC ( deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty, + integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, @@ -24,7 +24,7 @@ defaultKnownPackages = , deepseq, deriveConstants, directory, dllSplit, filepath, genapply , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp - , integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty + , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time , touchy, transformers, unlit, unix, win32, xhtml ] diff --git a/src/Way.hs b/src/Way.hs index 5b24662..974314c 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, - vanilla, profiling, logging, Way.parallel, granSim, + vanilla, profiling, logging, parallel, granSim, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, From git at git.haskell.org Fri Oct 27 00:06:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to Stack-based build instructions for Windows. (42bce9a) Message-ID: <20171027000625.86A2E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/42bce9aa45d72ad571223b3c23996177ca22cef1/ghc >--------------------------------------------------------------- commit 42bce9aa45d72ad571223b3c23996177ca22cef1 Author: Andrey Mokhov Date: Fri Mar 4 00:18:18 2016 +0000 Link to Stack-based build instructions for Windows. >--------------------------------------------------------------- 42bce9aa45d72ad571223b3c23996177ca22cef1 README.md | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 96b3106..aca17ea 100644 --- a/README.md +++ b/README.md @@ -41,7 +41,8 @@ system to be in the `shake-build` directory of the GHC source tree: * Build GHC using `shake-build/build.sh` or `shake-build/build.bat` (on Windows) instead of `make`. You might want to enable parallelism with `-j`. We will further refer to the build script simply as `build`. If you are interested in building in a Cabal sandbox -or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. +or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Also +see [instructions for building GHC on Windows using Stack][windows-build]. Using the build system ---------------------- @@ -133,6 +134,7 @@ helped me endure and enjoy the project. [issues]: https://github.com/snowleopard/shaking-up-ghc/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild +[windows-build]: https://github.com/snowleopard/shaking-up-ghc/blob/master/doc/windows.md [build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs From git at git.haskell.org Fri Oct 27 00:06:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (c928f2c) Message-ID: <20171027000626.1BED43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c928f2ce774091b7a6345c5c3cbdf05782bb2d23/ghc >--------------------------------------------------------------- commit c928f2ce774091b7a6345c5c3cbdf05782bb2d23 Author: Andrey Mokhov Date: Sat Aug 22 21:08:19 2015 +0100 Add comments. >--------------------------------------------------------------- c928f2ce774091b7a6345c5c3cbdf05782bb2d23 src/Base.hs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 862c46b..13483ce 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -50,15 +50,17 @@ packageDependencies :: FilePath packageDependencies = shakeFilesPath ++ "package-dependencies" -- Utility functions -replaceIf :: (a -> Bool) -> a -> [a] -> [a] -replaceIf p to = map (\from -> if p from then to else from) - +-- Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) +-- Find and replace all occurrences of path separators in a String with a Char replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator +replaceIf :: (a -> Bool) -> a -> [a] -> [a] +replaceIf p to = map (\from -> if p from then to else from) + -- Given a module name extract the directory and file names, e.g.: -- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") decodeModule :: String -> (FilePath, String) From git at git.haskell.org Fri Oct 27 00:06:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comment as to why we disable a warning (02c75e7) Message-ID: <20171027000628.4A87B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02c75e7600d4208151f8ff1949f05fc0c339f1ff/ghc >--------------------------------------------------------------- commit 02c75e7600d4208151f8ff1949f05fc0c339f1ff Author: Neil Mitchell Date: Sun Jan 10 20:32:04 2016 +0000 Comment as to why we disable a warning >--------------------------------------------------------------- 02c75e7600d4208151f8ff1949f05fc0c339f1ff src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 54f2f99..4b6ad10 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,4 @@ -{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} +{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel module Base ( -- * General utilities From git at git.haskell.org Fri Oct 27 00:06:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (f1157df) Message-ID: <20171027000629.210C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f1157df657dbb3f09dd6520331f4699108507bb6/ghc >--------------------------------------------------------------- commit f1157df657dbb3f09dd6520331f4699108507bb6 Author: Andrey Mokhov Date: Fri Mar 4 00:20:39 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- f1157df657dbb3f09dd6520331f4699108507bb6 doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index aa7a560..7fc8dcf 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -1,6 +1,6 @@ -# Compiling on Windows +# Building on Windows -Here are a list of instructions to compile GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. +Here are a list of instructions to build GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_64-installer) (I just accepted all the defaults), then open a command prompt and run: From git at git.haskell.org Fri Oct 27 00:06:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments, order Builder alphabetically. (a4c1eba) Message-ID: <20171027000629.A083E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4c1ebabfc62d83ec7d717210db4ae56ca900205/ghc >--------------------------------------------------------------- commit a4c1ebabfc62d83ec7d717210db4ae56ca900205 Author: Andrey Mokhov Date: Sat Aug 22 21:18:28 2015 +0100 Add comments, order Builder alphabetically. >--------------------------------------------------------------- a4c1ebabfc62d83ec7d717210db4ae56ca900205 src/Builder.hs | 47 ++++++++++++++++++++++------------------------- 1 file changed, 22 insertions(+), 25 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 5d60035..dde37c1 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -11,48 +11,45 @@ import Stage -- Ghc Stage0 is the bootstrapping compiler -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg --- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) +-- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) -- TODO: add Cpp builders -- TODO: rename Gcc to Cc? -data Builder = Ar - | Ld - | Alex - | Happy - | Haddock - | HsColour - | GhcCabal +data Builder = Alex + | Ar | Gcc Stage + | GccM Stage | Ghc Stage + | GhcCabal + | GhcCabalHsColour | GhcM Stage - | GccM Stage | GhcPkg Stage - | GhcCabalHsColour + | Haddock + | Happy + | HsColour + | Ld deriving (Show, Eq, Generic) -- Configuration files refer to Builders as follows: --- TODO: determine paths to utils without looking up configuration files builderKey :: Builder -> String builderKey builder = case builder of - Ar -> "ar" - Ld -> "ld" Alex -> "alex" - Happy -> "happy" - Haddock -> "haddock" - HsColour -> "hscolour" - GhcCabal -> "ghc-cabal" + Ar -> "ar" + Gcc Stage0 -> "system-gcc" + Gcc _ -> "gcc" + GccM stage -> builderKey $ Gcc stage -- Synonym for 'Gcc -MM' Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - Gcc Stage0 -> "system-gcc" - Gcc _ -> "gcc" + GhcM stage -> builderKey $ Ghc stage -- Synonym for 'Ghc -M' + GhcCabal -> "ghc-cabal" + GhcCabalHsColour -> builderKey $ GhcCabal -- Synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" - -- GhcM/GccM are synonyms for Ghc/Gcc (called with -M and -MM flags) - GhcM stage -> builderKey $ Ghc stage - GccM stage -> builderKey $ Gcc stage - -- GhcCabalHsColour is a synonym for GhcCabal (called in hscolour mode) - GhcCabalHsColour -> builderKey $ GhcCabal + Happy -> "happy" + Haddock -> "haddock" + HsColour -> "hscolour" + Ld -> "ld" builderPath :: Builder -> Action FilePath builderPath builder = do @@ -77,7 +74,7 @@ needBuilder laxDependencies builder = do allowOrderOnlyDependency :: Builder -> Bool allowOrderOnlyDependency (Ghc _) = True allowOrderOnlyDependency (GhcM _) = True - allowOrderOnlyDependency _ = False + allowOrderOnlyDependency _ = False -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". From git at git.haskell.org Fri Oct 27 00:06:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #143, turn of name shadowing warning (f89a75f) Message-ID: <20171027000632.00C863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f89a75f6730f643acc7002ee940803d01f1bda56/ghc >--------------------------------------------------------------- commit f89a75f6730f643acc7002ee940803d01f1bda56 Author: Neil Mitchell Date: Sun Jan 10 20:34:15 2016 +0000 #143, turn of name shadowing warning >--------------------------------------------------------------- f89a75f6730f643acc7002ee940803d01f1bda56 .ghci | 2 +- build.bat | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 1fe85b3..2f24ebe 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,2 @@ -:set -Wall -isrc +:set -Wall -fno-warn-name-shadowing -isrc :load Main diff --git a/build.bat b/build.bat index 07e355a..41b7877 100644 --- a/build.bat +++ b/build.bat @@ -2,6 +2,7 @@ @set ghcArgs=--make ^ -Wall ^ + -fno-warn-name-shadowing ^ src/Main.hs ^ -isrc ^ -rtsopts ^ From git at git.haskell.org Fri Oct 27 00:06:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Error when a non-optional builder is not specified. (8ba5cff) Message-ID: <20171027000633.5591E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ba5cfffa37a1992567104a90566d506b4d83f56/ghc >--------------------------------------------------------------- commit 8ba5cfffa37a1992567104a90566d506b4d83f56 Author: Andrey Mokhov Date: Fri Mar 4 01:43:30 2016 +0000 Error when a non-optional builder is not specified. See #211. >--------------------------------------------------------------- 8ba5cfffa37a1992567104a90566d506b4d83f56 src/Builder.hs | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 75d3d4e..eee24cb 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -86,6 +86,11 @@ isStaged = \case (GhcPkg _) -> True _ -> False +isOptional :: Builder -> Bool +isOptional = \case + HsColour -> True + _ -> False + -- TODO: get rid of fromJust -- | Determine the location of a 'Builder' builderPath :: Builder -> Action FilePath @@ -116,9 +121,13 @@ builderPath builder = case builderProvenance builder of _ -> error $ "Cannot determine builderKey for " ++ show builder path <- askConfigWithDefault builderKey . putError $ "\nCannot find path to '" ++ builderKey - ++ "' in configuration files. Have you forgot to run configure?" - if path == "" -- TODO: get rid of "" paths - then return "" + ++ "' in system.config file. Have you forgot to run configure?" + if null path + then do + if isOptional builder + then return "" + else putError $ "Builder '" ++ builderKey ++ "' is not specified in" + ++ " system.config file. Cannot proceed without it." else do path' <- lookupInPath path fixAbsolutePathOnWindows $ path' -<.> exe From git at git.haskell.org Fri Oct 27 00:06:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove notP and (??) Predicate functions. (88fa774) Message-ID: <20171027000633.BF2573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88fa774add49f09b3ccac966c85c49458275a5c6/ghc >--------------------------------------------------------------- commit 88fa774add49f09b3ccac966c85c49458275a5c6 Author: Andrey Mokhov Date: Sat Aug 22 21:40:24 2015 +0100 Remove notP and (??) Predicate functions. >--------------------------------------------------------------- 88fa774add49f09b3ccac966c85c49458275a5c6 src/Expression.hs | 12 ++++-------- src/Predicates.hs | 6 +++--- src/Settings/Builders/GhcCabal.hs | 15 +++++++-------- 3 files changed, 14 insertions(+), 19 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index e62acf0..d84fb2c 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -7,7 +7,7 @@ module Expression ( module Stage, module Way, Expr, DiffExpr, fromDiffExpr, - Predicate, (?), (??), notP, applyPredicate, + Predicate, (?), applyPredicate, Args, Ways, Packages, apply, append, appendM, remove, appendSub, appendSubD, filterSub, removeSub, @@ -63,7 +63,7 @@ append x = apply (<> x) -- 3) remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] -remove xs = apply . filter $ (`notElem` xs) +remove xs = apply $ filter (`notElem` xs) -- 4) apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a @@ -74,25 +74,21 @@ applyPredicate predicate expr = do -- A convenient operator for predicate application class PredicateLike a where (?) :: Monoid m => a -> Expr m -> Expr m - notP :: a -> Predicate infixr 8 ? instance PredicateLike Predicate where (?) = applyPredicate - notP = liftM not instance PredicateLike Bool where (?) = applyPredicate . return - notP = return . not instance PredicateLike (Action Bool) where (?) = applyPredicate . lift - notP = lift . fmap not -- An equivalent of if-then-else for predicates -(??) :: (PredicateLike a, Monoid m) => a -> (Expr m, Expr m) -> Expr m -p ?? (t, f) = p ? t <> notP p ? f +-- (??) :: (PredicateLike a, Monoid m) => a -> (Expr m, Expr m) -> Expr m +-- p ?? (t, f) = p ? t <> notP p ? f -- A monadic version of append appendM :: Monoid a => Action a -> DiffExpr a diff --git a/src/Predicates.hs b/src/Predicates.hs index 8743881..5bc0aed 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -40,10 +40,10 @@ stage2 :: Predicate stage2 = stage Stage2 notStage :: Stage -> Predicate -notStage = notP . stage +notStage = liftM not . stage notStage0 :: Predicate -notStage0 = notP stage0 +notStage0 = liftM not stage0 -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate @@ -52,7 +52,7 @@ registerPackage = return True splitObjects :: Predicate splitObjects = do goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages - goodPkg <- notP $ package compiler -- We don't split compiler + goodPkg <- liftM not $ package compiler -- We don't split compiler broken <- lift $ flag SplitObjectsBroken ghcUnreg <- lift $ flag GhcUnregisterised goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 11529bf..1925daf 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -102,13 +102,12 @@ packageConstraints = stage0 ? do -- TODO: put all validating options together in one file ccArgs :: Args ccArgs = validating ? do - let gccGe46 = notP gccLt46 + let notClang = fmap not gccIsClang mconcat [ arg "-Werror" , arg "-Wall" - , gccIsClang ?? - ( arg "-Wno-unknown-pragmas" <> - gccGe46 ? windowsHost ? arg "-Werror=unused-but-set-variable" - , gccGe46 ? arg "-Wno-error=inline" )] + , gccIsClang ? arg "-Wno-unknown-pragmas" + , notClang ? gccGe46 ? notWindowsHost ? arg "-Werror=unused-but-set-variable" + , notClang ? gccGe46 ? arg "-Wno-error=inline" ] ldArgs :: Args ldArgs = mempty @@ -151,8 +150,8 @@ customPackageArgs = do , arg "--disable-library-for-ghci" , targetOs "openbsd" ? arg "--ld-options=-E" , flag GhcUnregisterised ? arg "--ghc-option=-DNO_REGS" - , notP ghcWithSMP ? arg "--ghc-option=-DNOSMP" - , notP ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" + , fmap not ghcWithSMP ? arg "--ghc-option=-DNOSMP" + , fmap not ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" , (threaded `elem` rtsWays) ? notStage0 ? arg "--ghc-option=-optc-DTHREADED_RTS" , ghcWithNativeCodeGen ? arg "--flags=ncg" @@ -160,7 +159,7 @@ customPackageArgs = do notStage0 ? arg "--flags=ghci" , ghcWithInterpreter ? ghcEnableTablesNextToCode ? - notP (flag GhcUnregisterised) ? + fmap not (flag GhcUnregisterised) ? notStage0 ? arg "--ghc-option=-DGHCI_TABLES_NEXT_TO_CODE" , ghcWithInterpreter ? ghciWithDebugger ? From git at git.haskell.org Fri Oct 27 00:06:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove an unnecessary hiding after disabling name shadow warning (6e1511f) Message-ID: <20171027000635.849C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e1511f9d48bb5198ab6feb4f9a2e6039df5b67f/ghc >--------------------------------------------------------------- commit 6e1511f9d48bb5198ab6feb4f9a2e6039df5b67f Author: Neil Mitchell Date: Sun Jan 10 20:34:32 2016 +0000 Remove an unnecessary hiding after disabling name shadow warning >--------------------------------------------------------------- 6e1511f9d48bb5198ab6feb4f9a2e6039df5b67f src/Rules/Library.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 03f91aa..788deb6 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -2,7 +2,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Data.Char -import Base hiding (splitPath, split) +import Base hiding (splitPath) import Expression import GHC import Oracles From git at git.haskell.org Fri Oct 27 00:06:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make Objdump builder optional. (d89358f) Message-ID: <20171027000637.246B33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d89358f615755e5482e526c38d52cef76cfb3b7e/ghc >--------------------------------------------------------------- commit d89358f615755e5482e526c38d52cef76cfb3b7e Author: Andrey Mokhov Date: Sat Mar 5 13:17:23 2016 +0000 Make Objdump builder optional. See #211. >--------------------------------------------------------------- d89358f615755e5482e526c38d52cef76cfb3b7e src/Builder.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index eee24cb..e8011e7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -86,9 +86,14 @@ isStaged = \case (GhcPkg _) -> True _ -> False +-- TODO: Some builders are required only on certain platforms. For example, +-- Objdump is only required on OpenBSD and AIX, as mentioned in #211. Add +-- support for platform-specific optional builders as soon as we can reliably +-- test this feature. isOptional :: Builder -> Bool isOptional = \case HsColour -> True + Objdump -> True _ -> False -- TODO: get rid of fromJust From git at git.haskell.org Fri Oct 27 00:06:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace GccLt46 with gccGe46 as the former was always used negated. (aff7b3c) Message-ID: <20171027000637.4B79D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aff7b3c9ee5a06b7c7070f14cecf941ba1c2820d/ghc >--------------------------------------------------------------- commit aff7b3c9ee5a06b7c7070f14cecf941ba1c2820d Author: Andrey Mokhov Date: Sat Aug 22 21:41:21 2015 +0100 Replace GccLt46 with gccGe46 as the former was always used negated. >--------------------------------------------------------------- aff7b3c9ee5a06b7c7070f14cecf941ba1c2820d src/Oracles/Config/Flag.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 737af97..80d8c6a 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -1,6 +1,6 @@ module Oracles.Config.Flag ( Flag (..), flag, - crossCompiling, gccIsClang, gccLt46, + crossCompiling, gccIsClang, gccGe46, platformSupportsSharedLibs, ghcWithSMP, ghcWithNativeCodeGen ) where @@ -39,8 +39,8 @@ crossCompiling = flag CrossCompiling gccIsClang :: Action Bool gccIsClang = flag GccIsClang -gccLt46 :: Action Bool -gccLt46 = flag GccLt46 +gccGe46 :: Action Bool +gccGe46 = fmap not $ flag GccLt46 platformSupportsSharedLibs :: Action Bool platformSupportsSharedLibs = do From git at git.haskell.org Fri Oct 27 00:06:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build.bat work regardless of your current directory, so you can invoke it from the root directory (4be2130) Message-ID: <20171027000638.EF7BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4be213017f9d2a64ae1413c1e73678ead571d7e9/ghc >--------------------------------------------------------------- commit 4be213017f9d2a64ae1413c1e73678ead571d7e9 Author: Neil Mitchell Date: Sun Jan 10 22:31:38 2016 +0000 Make build.bat work regardless of your current directory, so you can invoke it from the root directory >--------------------------------------------------------------- 4be213017f9d2a64ae1413c1e73678ead571d7e9 build.bat | 1 + 1 file changed, 1 insertion(+) diff --git a/build.bat b/build.bat index 41b7877..0cf778a 100644 --- a/build.bat +++ b/build.bat @@ -1,3 +1,4 @@ + at cd %~dp0 @mkdir .shake 2> nul @set ghcArgs=--make ^ From git at git.haskell.org Fri Oct 27 00:06:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split buildPackageData rule. (c1adff7) Message-ID: <20171027000641.54CF03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1adff7f36f088712b52c310eb0fb925e72d2549/ghc >--------------------------------------------------------------- commit c1adff7f36f088712b52c310eb0fb925e72d2549 Author: Andrey Mokhov Date: Sat Mar 5 14:07:47 2016 +0000 Split buildPackageData rule. See #206. >--------------------------------------------------------------- c1adff7f36f088712b52c310eb0fb925e72d2549 src/Rules/Data.hs | 18 +++++++----------- 1 file changed, 7 insertions(+), 11 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index fee310f..719352f 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,5 @@ module Rules.Data (buildPackageData) where -import qualified System.Directory as IO - import Base import Context import Expression @@ -22,8 +20,9 @@ buildPackageData context at Context {..} = do configure = pkgPath package -/- "configure" dataFile = pkgDataFile context oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 + inTreeMk = oldPath -/- takeFileName dataFile -- TODO: remove, #113 - [dataFile, oldPath -/- "package-data.mk"] &%> \_ -> do + inTreeMk %> \mk -> do -- The first thing we do with any package is make sure all generated -- dependencies are in place before proceeding. orderOnly $ generatedDependencies stage package @@ -37,22 +36,19 @@ buildPackageData context at Context {..} = do let depPkgs = matchPackageNames (sort pkgs) deps need =<< traverse (pkgConfFile . vanillaContext stage) depPkgs - -- TODO: get rid of this, see #113 - let inTreeMk = oldPath -/- takeFileName dataFile - need [cabalFile] - build $ Target context GhcCabal [cabalFile] [inTreeMk] + build $ Target context GhcCabal [cabalFile] [mk] - -- TODO: get rid of this, see #113 - liftIO $ IO.copyFile inTreeMk dataFile + -- TODO: get rid of this, see #113 + dataFile %> \mk -> do + copyFile inTreeMk mk autogenFiles <- getDirectoryFiles (oldPath -/- "build") ["autogen/*"] createDirectory $ buildPath context -/- "autogen" forM_ autogenFiles $ \file -> do copyFile (oldPath -/- "build" -/- file) (buildPath context -/- file) let haddockPrologue = "haddock-prologue.txt" copyFile (oldPath -/- haddockPrologue) (buildPath context -/- haddockPrologue) - - postProcessPackageData context dataFile + postProcessPackageData context mk -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps priority 2.0 $ do From git at git.haskell.org Fri Oct 27 00:06:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports, add comments. (5603275) Message-ID: <20171027000641.7763C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5603275f1aeeb2b3469307859daabcd6f957d8c9/ghc >--------------------------------------------------------------- commit 5603275f1aeeb2b3469307859daabcd6f957d8c9 Author: Andrey Mokhov Date: Sat Aug 22 22:18:14 2015 +0100 Refactor imports, add comments. >--------------------------------------------------------------- 5603275f1aeeb2b3469307859daabcd6f957d8c9 src/Expression.hs | 7 ++----- src/GHC.hs | 13 +++++++------ src/Main.hs | 12 ++++++------ src/Package.hs | 21 ++++++++++----------- src/Rules.hs | 3 +-- src/Rules/Actions.hs | 4 +--- src/Rules/Cabal.hs | 7 +++---- src/Rules/Compile.hs | 9 +++------ src/Rules/Data.hs | 7 ++----- src/Rules/Dependencies.hs | 7 ++----- src/Rules/Documentation.hs | 7 +------ src/Rules/Library.hs | 3 +-- src/Target.hs | 3 +-- src/Way.hs | 2 ++ 14 files changed, 42 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5603275f1aeeb2b3469307859daabcd6f957d8c9 From git at git.haskell.org Fri Oct 27 00:06:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move gmp build results to buildRootPath. (a850455) Message-ID: <20171027000642.6B1AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a850455e1402e79b01bd65cbb0a7e0571969170a/ghc >--------------------------------------------------------------- commit a850455e1402e79b01bd65cbb0a7e0571969170a Author: Andrey Mokhov Date: Sun Jan 10 22:52:19 2016 +0000 Move gmp build results to buildRootPath. See #113. >--------------------------------------------------------------- a850455e1402e79b01bd65cbb0a7e0571969170a shaking-up-ghc.cabal | 2 +- src/Main.hs | 4 +- src/Rules/Data.hs | 10 +-- src/Rules/Generate.hs | 4 +- src/Rules/Gmp.hs | 134 +++++++++++++++++++++++++++++++++++ src/Rules/IntegerGmp.hs | 137 ------------------------------------ src/Rules/Libffi.hs | 24 ++++--- src/Rules/Library.hs | 6 +- src/Settings/Packages/IntegerGmp.hs | 25 ++++--- src/Settings/TargetDirectory.hs | 2 +- 10 files changed, 178 insertions(+), 170 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 a850455e1402e79b01bd65cbb0a7e0571969170a From git at git.haskell.org Fri Oct 27 00:06:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hash Target inputs in ArgsHashOracle. (ad44a95) Message-ID: <20171027000644.E5B253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ad44a95b78bc2ed712c44f55b691203787b3df93/ghc >--------------------------------------------------------------- commit ad44a95b78bc2ed712c44f55b691203787b3df93 Author: Andrey Mokhov Date: Tue Mar 8 01:35:17 2016 +0000 Hash Target inputs in ArgsHashOracle. See #217. >--------------------------------------------------------------- ad44a95b78bc2ed712c44f55b691203787b3df93 src/Oracles/ArgsHash.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index aec0dc9..d3bfd61 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -23,8 +23,8 @@ newtype ArgsHashKey = ArgsHashKey Target -- TODO: Hash Target to improve accuracy and performance. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do - let firstInput = take 1 $ inputs target - _ <- askOracle . ArgsHashKey $ target { inputs = firstInput } :: Action Int + let hashed = [ show . hash $ inputs target ] + _ <- askOracle . ArgsHashKey $ target { inputs = hashed } :: Action Int return () -- Oracle for storing per-target argument list hashes From git at git.haskell.org Fri Oct 27 00:06:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code, add comments. (b04c769) Message-ID: <20171027000645.1C5C73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b04c76947514b996239afde8b7b460c7bbadfea1/ghc >--------------------------------------------------------------- commit b04c76947514b996239afde8b7b460c7bbadfea1 Author: Andrey Mokhov Date: Sun Aug 23 00:04:55 2015 +0100 Clean up code, add comments. >--------------------------------------------------------------- b04c76947514b996239afde8b7b460c7bbadfea1 src/Base.hs | 2 + src/Expression.hs | 20 +++--- src/Oracles/ArgsHash.hs | 6 +- src/Oracles/Config/Flag.hs | 19 +++--- src/Oracles/Config/Setting.hs | 8 ++- src/Oracles/Dependencies.hs | 6 +- src/Oracles/PackageData.hs | 1 - src/Oracles/PackageDeps.hs | 6 +- src/Oracles/WindowsRoot.hs | 5 +- src/Predicates.hs | 32 +++++----- src/Rules.hs | 12 ++-- src/Rules/Actions.hs | 1 + src/Rules/Dependencies.hs | 1 - src/Rules/Documentation.hs | 12 +--- src/Settings.hs | 72 +++++++++++++++++++++- src/Settings/Args.hs | 9 +-- src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Gcc.hs | 40 ++++++------ src/Settings/Builders/Ghc.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 41 +++++++++---- src/Settings/Builders/GhcPkg.hs | 3 +- src/Settings/Builders/Haddock.hs | 9 +-- src/Settings/Builders/Ld.hs | 5 +- src/Settings/Packages.hs | 5 +- src/Settings/TargetDirectory.hs | 4 +- src/Settings/User.hs | 3 +- src/Settings/Util.hs | 125 -------------------------------------- src/Settings/Ways.hs | 4 +- src/Target.hs | 2 +- 29 files changed, 190 insertions(+), 268 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b04c76947514b996239afde8b7b460c7bbadfea1 From git at git.haskell.org Fri Oct 27 00:06:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #144 from ndmitchell/master (ef27c7c) Message-ID: <20171027000645.D9E943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef27c7c14f589fdd585c8c9bb2d6264db92a73d0/ghc >--------------------------------------------------------------- commit ef27c7c14f589fdd585c8c9bb2d6264db92a73d0 Merge: a850455 4be2130 Author: Andrey Mokhov Date: Sun Jan 10 22:54:19 2016 +0000 Merge pull request #144 from ndmitchell/master General refactorings >--------------------------------------------------------------- ef27c7c14f589fdd585c8c9bb2d6264db92a73d0 .ghci | 2 ++ build.bat | 2 ++ src/Base.hs | 8 +++++--- src/Expression.hs | 4 ++-- src/Oracles/LookupInPath.hs | 1 - src/Rules.hs | 3 +-- src/Rules/Actions.hs | 7 +++---- src/Rules/Data.hs | 1 - src/Rules/Libffi.hs | 1 - src/Way.hs | 2 +- 10 files changed, 16 insertions(+), 15 deletions(-) diff --cc src/Rules/Data.hs index 5cd2e50,99334f4..fbe22db --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@@ -1,10 -1,7 +1,9 @@@ module Rules.Data (buildPackageData) where +import qualified System.Directory as IO + import Base import Expression - import Extra (replace) import GHC import Oracles import Predicates (registerPackage) From git at git.haskell.org Fri Oct 27 00:06:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable library profiling in quick build flavour. (c7a4165) Message-ID: <20171027000648.B1D523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7a41657a0393aa1a1d5d5b7219c0f8c7c2e31dc/ghc >--------------------------------------------------------------- commit c7a41657a0393aa1a1d5d5b7219c0f8c7c2e31dc Author: Andrey Mokhov Date: Wed Mar 9 23:47:34 2016 +0000 Disable library profiling in quick build flavour. See #188. >--------------------------------------------------------------- c7a41657a0393aa1a1d5d5b7219c0f8c7c2e31dc src/Settings/Flavours/Quick.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 1f2def1..97af880 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -1,9 +1,10 @@ -module Settings.Flavours.Quick (quickFlavourArgs) where +module Settings.Flavours.Quick (quickFlavourArgs, quickFlavourWays) where import Expression import Predicates (builderGhc) --- TODO: consider putting all flavours in a single file --- TODO: handle other, non Args, settings affected by flavours quickFlavourArgs :: Args quickFlavourArgs = builderGhc ? arg "-O0" + +quickFlavourWays :: Ways +quickFlavourWays = remove [profiling] From git at git.haskell.org Fri Oct 27 00:06:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Ghc/GhcM arguments. (3039df4) Message-ID: <20171027000649.4F7543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3039df428add9752791ecba96a9bef8fc41980f3/ghc >--------------------------------------------------------------- commit 3039df428add9752791ecba96a9bef8fc41980f3 Author: Andrey Mokhov Date: Sun Aug 23 00:33:01 2015 +0100 Fix Ghc/GhcM arguments. >--------------------------------------------------------------- 3039df428add9752791ecba96a9bef8fc41980f3 src/Settings/Builders/Ghc.hs | 35 +++++++++++++++++++---------------- 1 file changed, 19 insertions(+), 16 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 6ecc26d..5ab520e 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,7 +2,7 @@ module Settings.Builders.Ghc (ghcArgs, ghcMArgs, commonGhcArgs) where import Expression import Oracles -import Predicates (stagedBuilder, splitObjects, stage0) +import Predicates (stagedBuilder, splitObjects, stage0, notStage0) import Settings -- TODO: add support for -dyno @@ -15,6 +15,12 @@ ghcArgs = stagedBuilder Ghc ? do file <- getFile srcs <- getSources mconcat [ commonGhcArgs + , arg "-H32m" + , stage0 ? arg "-O" + , notStage0 ? arg "-O2" + , arg "-Wall" + , arg "-fwarn-tabs" + , splitObjects ? arg "-split-objs" , arg "-c", append srcs , arg "-o", arg file ] @@ -25,6 +31,7 @@ ghcMArgs = stagedBuilder GhcM ? do srcs <- getSources mconcat [ arg "-M" , commonGhcArgs + , arg "-include-pkg-deps" , arg "-dep-makefile", arg file , append $ concat [ ["-dep-suffix", wayPrefix w] | w <- ways ] , append srcs ] @@ -46,10 +53,9 @@ commonGhcArgs = do , append hsArgs , append $ map ("-optP" ++) cppArgs , arg "-odir" , arg buildPath - , arg "-stubdir" , arg buildPath , arg "-hidir" , arg buildPath - , splitObjects ? arg "-split-objs" - , arg "-rtsopts" ] -- TODO: is this needed? + , arg "-stubdir" , arg buildPath + , arg "-rtsopts" ] -- TODO: ifeq "$(HC_VERSION_GE_6_13)" "YES" -- TODO: do '-ticky' in all debug ways? wayGhcArgs :: Args @@ -76,7 +82,6 @@ packageGhcArgs = do mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" - , arg "-include-pkg-deps" , stage0 ? arg "-package-db libraries/bootstrapping.conf" , if supportsPackageKey || stage /= Stage0 then arg $ "-this-package-key " ++ pkgKey @@ -89,19 +94,17 @@ includeGhcArgs = do path <- getTargetPath srcDirs <- getPkgDataList SrcDirs incDirs <- getPkgDataList IncludeDirs - cppArgs <- getPkgDataList CppArgs let buildPath = path -/- "build" autogenPath = buildPath -/- "autogen" - mconcat - [ arg "-i" - , arg $ "-i" ++ buildPath - , arg $ "-i" ++ autogenPath - , arg $ "-I" ++ buildPath - , arg $ "-I" ++ autogenPath - , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] - , arg "-optP-include", arg $ "-optP" ++ autogenPath -/- "cabal_macros.h" - , append $ map ("-optP" ++) cppArgs ] + mconcat [ arg "-i" + , arg $ "-i" ++ buildPath + , arg $ "-i" ++ autogenPath + , arg $ "-I" ++ buildPath + , arg $ "-I" ++ autogenPath + , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] + , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] + , arg "-optP-include" + , arg $ "-optP" ++ autogenPath -/- "cabal_macros.h" ] -- TODO: see ghc.mk -- # And then we strip it out again before building the package: From git at git.haskell.org Fri Oct 27 00:06:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert changes in Way.hs from #144. (697cba53) Message-ID: <20171027000649.AA1363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/697cba53396690ff295c15b09e03520d2fc07cd5/ghc >--------------------------------------------------------------- commit 697cba53396690ff295c15b09e03520d2fc07cd5 Author: Andrey Mokhov Date: Sun Jan 10 23:34:10 2016 +0000 Revert changes in Way.hs from #144. >--------------------------------------------------------------- 697cba53396690ff295c15b09e03520d2fc07cd5 src/Way.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Way.hs b/src/Way.hs index 974314c..3b1f6c0 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -72,7 +72,7 @@ instance Read Way where uniqueReads token = case reads token of [(unit, "")] -> Just unit _ -> Nothing - units = map uniqueReads . splitOn "_" $ s + units = map uniqueReads . words . replaceEq '_' ' ' $ s result = if Nothing `elem` units then [] else [(wayFromUnits . map fromJust $ units, "")] From git at git.haskell.org Fri Oct 27 00:06:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow build flavours to control Ways. (0b327b5) Message-ID: <20171027000652.AA5A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b327b564fbab286b6999040565046b5d6bf60c8/ghc >--------------------------------------------------------------- commit 0b327b564fbab286b6999040565046b5d6bf60c8 Author: Andrey Mokhov Date: Wed Mar 9 23:48:54 2016 +0000 Allow build flavours to control Ways. See #188, #218. >--------------------------------------------------------------- 0b327b564fbab286b6999040565046b5d6bf60c8 src/Settings/Ways.hs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 0fee897..7e46406 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,14 +1,18 @@ module Settings.Ways (getLibraryWays, getRtsWays) where +import CmdLineFlag import Base import Expression +import Oracles.Config.Flag import Predicates +import Settings.Flavours.Quick import Settings.User -import Oracles.Config.Flag -- | Combine default ways with user modifications getLibraryWays :: Expr [Way] -getLibraryWays = fromDiffExpr $ defaultLibraryWays <> userLibraryWays +getLibraryWays = fromDiffExpr $ mconcat [ defaultLibraryWays + , userLibraryWays + , flavourLibraryWays ] getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays @@ -24,6 +28,10 @@ defaultLibraryWays = mconcat , notStage0 ? append [profiling] , notStage0 ? platformSupportsSharedLibs ? append [dynamic] ] +flavourLibraryWays :: Ways +flavourLibraryWays = mconcat + [ cmdFlavour == Quick ? quickFlavourWays ] + defaultRtsWays :: Ways defaultRtsWays = do ways <- getLibraryWays From git at git.haskell.org Fri Oct 27 00:06:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate only one rule for Haddock (Stage1). (cdf208c) Message-ID: <20171027000653.1DFEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cdf208c342c346b48f848e06b9ffc8a089326254/ghc >--------------------------------------------------------------- commit cdf208c342c346b48f848e06b9ffc8a089326254 Author: Andrey Mokhov Date: Sun Aug 23 01:04:55 2015 +0100 Generate only one rule for Haddock (Stage1). >--------------------------------------------------------------- cdf208c342c346b48f848e06b9ffc8a089326254 src/Rules/Documentation.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 81e3140..5978cfd 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -10,10 +10,10 @@ import Settings -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. buildPackageDocumentation :: Resources -> PartialTarget -> Rules () -buildPackageDocumentation _ target @ (PartialTarget _ pkg) = +buildPackageDocumentation _ target @ (PartialTarget stage pkg) = let cabalFile = pkgCabalFile pkg haddockFile = pkgHaddockFile pkg - in do + in when (stage == Stage1) $ do haddockFile %> \file -> do whenM (specified HsColour) $ do need [cabalFile] From git at git.haskell.org Fri Oct 27 00:06:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting. (016a71f) Message-ID: <20171027000653.23B073A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/016a71fbb371e2e726ec13e665510bf680dce5cb/ghc >--------------------------------------------------------------- commit 016a71fbb371e2e726ec13e665510bf680dce5cb Author: Andrey Mokhov Date: Sun Jan 10 23:37:20 2016 +0000 Fix formatting. >--------------------------------------------------------------- 016a71fbb371e2e726ec13e665510bf680dce5cb build.bat | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/build.bat b/build.bat index 0cf778a..348537d 100644 --- a/build.bat +++ b/build.bat @@ -1,16 +1,16 @@ @cd %~dp0 @mkdir .shake 2> nul - at set ghcArgs=--make ^ - -Wall ^ + at set ghcArgs=--make ^ + -Wall ^ -fno-warn-name-shadowing ^ - src/Main.hs ^ - -isrc ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=.shake ^ - -j ^ - -O ^ + src/Main.hs ^ + -isrc ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=.shake ^ + -j ^ + -O ^ -o .shake/build @set shakeArgs=--lint ^ From git at git.haskell.org Fri Oct 27 00:06:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build profiled libraries by default. (56526ff) Message-ID: <20171027000656.961873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56526ffc8dde7873fc35db912d9793eba1e63734/ghc >--------------------------------------------------------------- commit 56526ffc8dde7873fc35db912d9793eba1e63734 Author: Andrey Mokhov Date: Wed Mar 9 23:49:48 2016 +0000 Build profiled libraries by default. See #186, #218. >--------------------------------------------------------------- 56526ffc8dde7873fc35db912d9793eba1e63734 src/Settings/User.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index dd6150a..6fc5536 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -30,10 +30,9 @@ userKnownPackages :: [Package] userKnownPackages = [] -- | Control which ways library packages are built --- FIXME: skip profiling for speed -- FIXME: skip dynamic since it's currently broken #4 userLibraryWays :: Ways -userLibraryWays = remove [profiling, dynamic] +userLibraryWays = remove [dynamic] -- | Control which ways the 'rts' package is built userRtsWays :: Ways From git at git.haskell.org Fri Oct 27 00:06:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (a9adcf3) Message-ID: <20171027000656.EE7A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9adcf31d5daf441cfa4efc5ac4012a3836c9b19/ghc >--------------------------------------------------------------- commit a9adcf31d5daf441cfa4efc5ac4012a3836c9b19 Author: Andrey Mokhov Date: Sat Sep 19 00:04:02 2015 +0100 Clean up. >--------------------------------------------------------------- a9adcf31d5daf441cfa4efc5ac4012a3836c9b19 arg/README.md | 5 ----- src/Builder.hs | 13 +++++++------ src/Oracles/Config/Setting.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Rules/Cabal.hs | 4 ++-- src/Settings/Args.hs | 8 ++++---- src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Packages.hs | 4 +--- src/Stage.hs | 2 +- 10 files changed, 18 insertions(+), 25 deletions(-) diff --git a/arg/README.md b/arg/README.md deleted file mode 100644 index 0af8834..0000000 --- a/arg/README.md +++ /dev/null @@ -1,5 +0,0 @@ -This folder serves two purposes: - -* Tracking argument lists produced by rules - -* Documentation diff --git a/src/Builder.hs b/src/Builder.hs index dde37c1..8e5f639 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -36,14 +36,14 @@ builderKey builder = case builder of Ar -> "ar" Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" - GccM stage -> builderKey $ Gcc stage -- Synonym for 'Gcc -MM' + GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - GhcM stage -> builderKey $ Ghc stage -- Synonym for 'Ghc -M' + GhcM stage -> builderKey $ Ghc stage -- synonym for 'Ghc -M' GhcCabal -> "ghc-cabal" - GhcCabalHsColour -> builderKey $ GhcCabal -- Synonym for 'GhcCabal hscolour' + GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" Happy -> "happy" @@ -72,9 +72,10 @@ needBuilder laxDependencies builder = do else need [path] where allowOrderOnlyDependency :: Builder -> Bool - allowOrderOnlyDependency (Ghc _) = True - allowOrderOnlyDependency (GhcM _) = True - allowOrderOnlyDependency _ = False + allowOrderOnlyDependency b = case b of + Ghc _ -> True + GhcM _ -> True + _ -> False -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 27b2d89..f0f7fb7 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -7,8 +7,8 @@ module Oracles.Config.Setting ( ) where import Base -import Stage import Oracles.Config +import Stage -- Each Setting comes from the system.config file, e.g. 'target-os = mingw32'. -- setting TargetOs looks up the config file and returns "mingw32". diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 1898d21..0d1a0b4 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -2,8 +2,8 @@ module Oracles.PackageDeps (packageDeps, packageDepsOracle) where import Base -import Package import qualified Data.HashMap.Strict as Map +import Package newtype PackageDepsKey = PackageDepsKey PackageName deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index b958db4..aac8ab2 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,11 +1,11 @@ module Rules.Cabal (cabalRules) where +import Expression import Data.Version import Distribution.Package -import Distribution.Verbosity import Distribution.PackageDescription import Distribution.PackageDescription.Parse -import Expression +import Distribution.Verbosity import Package hiding (library) import Settings diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 4e55a3d..5a8c63a 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -1,14 +1,14 @@ module Settings.Args (getArgs) where import Expression -import Settings.User import Settings.Builders.Ar -import Settings.Builders.Ld -import Settings.Builders.Ghc import Settings.Builders.Gcc +import Settings.Builders.Ghc +import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg import Settings.Builders.Haddock -import Settings.Builders.GhcCabal +import Settings.Builders.Ld +import Settings.User getArgs :: Expr [String] getArgs = fromDiffExpr $ defaultArgs <> userArgs diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 617d4e1..082cbaf 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,6 +1,5 @@ module Settings.Builders.Ar (arArgs, arPersistentArgsCount) where -import Builder import Expression import Predicates (builder) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index bc6622c..2cd26d0 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -1,8 +1,8 @@ module Settings.Builders.Haddock (haddockArgs) where import Expression -import Predicates hiding (file) import Oracles +import Predicates hiding (file) import Settings import Settings.Builders.Ghc diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 7f2a64b..87f293d 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -1,6 +1,4 @@ -module Settings.Packages ( - getPackages, knownPackages, findKnownPackage - ) where +module Settings.Packages (getPackages, knownPackages, findKnownPackage) where import Expression import Predicates diff --git a/src/Stage.hs b/src/Stage.hs index 50a273b..edddb6f 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -4,7 +4,7 @@ module Stage (Stage (..)) where import Base import GHC.Generics (Generic) --- TODO: rename to something more meaningful, e.g. Stage0 -> Boot. +-- TODO: rename to something more meaningful, e.g. 'Stage0' -> 'Boot'. data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum, Generic) instance Show Stage where From git at git.haskell.org Fri Oct 27 00:06:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:06:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -fno-warn-name-shadowing to cabal file. (91622d3) Message-ID: <20171027000657.08CD63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91622d38572cd63c4c94e11f81cff321f01a83d3/ghc >--------------------------------------------------------------- commit 91622d38572cd63c4c94e11f81cff321f01a83d3 Author: Andrey Mokhov Date: Mon Jan 11 00:49:50 2016 +0000 Add -fno-warn-name-shadowing to cabal file. See #143. [skip ci] >--------------------------------------------------------------- 91622d38572cd63c4c94e11f81cff321f01a83d3 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 1f7cfc1..a7b3352 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -122,4 +122,4 @@ executable ghc-shake , transformers >= 0.4 , unordered-containers >= 0.2 default-language: Haskell2010 - ghc-options: -Wall -rtsopts -with-rtsopts=-I0 -j + ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j From git at git.haskell.org Fri Oct 27 00:07:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Quick flavour now disables library profiling (9b68950) Message-ID: <20171027000700.E40C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b68950fd0a53a33dbe902ed6e55b627f6ecb516/ghc >--------------------------------------------------------------- commit 9b68950fd0a53a33dbe902ed6e55b627f6ecb516 Author: Andrey Mokhov Date: Thu Mar 10 00:01:55 2016 +0000 Quick flavour now disables library profiling See #188. [skip ci] >--------------------------------------------------------------- 9b68950fd0a53a33dbe902ed6e55b627f6ecb516 README.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index aca17ea..b6d762b 100644 --- a/README.md +++ b/README.md @@ -54,7 +54,8 @@ are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue In addition to standard Shake flags (try `--help`), the build system currently supports several others: * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: -`default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). +`default` and `quick` (adds `-O0` flag to all GHC invocations and disables library +profiling, which speeds up builds by 3-4x). * `--haddock`: build Haddock documentation. * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per From git at git.haskell.org Fri Oct 27 00:05:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move basic predicates to src/Switches.hs. (4d70a1e) Message-ID: <20171027000518.B0F413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4d70a1e6a5f3ed5353fa9d6af2daf013d1dde318/ghc >--------------------------------------------------------------- commit 4d70a1e6a5f3ed5353fa9d6af2daf013d1dde318 Author: Andrey Mokhov Date: Fri Aug 21 16:09:43 2015 +0100 Move basic predicates to src/Switches.hs. >--------------------------------------------------------------- 4d70a1e6a5f3ed5353fa9d6af2daf013d1dde318 src/Expression.hs | 40 ++++------------------------------------ src/Switches.hs | 46 +++++++++++++++++++++++++++++++++++----------- 2 files changed, 39 insertions(+), 47 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 44be38f..d51f434c 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -10,8 +10,7 @@ module Expression ( appendSub, appendSubD, filterSub, removeSub, interpret, interpretDiff, getStage, getPackage, getBuilder, getFiles, getFile, - getSources, getSource, getWay, - stage, package, builder, stagedBuilder, file, way + getSources, getSource, getWay ) where import Way @@ -30,13 +29,6 @@ import Control.Monad.Reader hiding (liftIO) -- parameters of the current build Target. type Expr a = ReaderT Target Action a --- If values of type a form a Monoid then so do computations of type Expr a: --- * the empty computation returns the identity element of the underlying type --- * two computations can be combined by combining their results -instance Monoid a => Monoid (Expr a) where - mempty = return mempty - mappend = liftM2 mappend - -- Diff a holds functions of type a -> a and is equipped with a Monoid instance. -- We could use Dual (Endo a) instead of Diff a, but the former may look scary. -- The name comes from "difference lists". @@ -105,7 +97,7 @@ p ?? (t, f) = p ? t <> notP p ? f -- A monadic version of append appendM :: Monoid a => Action a -> DiffExpr a -appendM mx = lift mx >>= append +appendM = (append =<<) . lift -- appendSub appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument @@ -185,29 +177,5 @@ getFile = do target <- ask files <- getFiles case files of - [file] -> return file - _ -> error $ "Exactly one file expected in target " ++ show target - --- Basic predicates (see Switches.hs for derived predicates) -stage :: Stage -> Predicate -stage s = liftM (s ==) getStage - -package :: Package -> Predicate -package p = liftM (p ==) getPackage - --- For unstaged builders, e.g. GhcCabal -builder :: Builder -> Predicate -builder b = liftM (b ==) getBuilder - --- For staged builders, e.g. Ghc Stage -stagedBuilder :: (Stage -> Builder) -> Predicate -stagedBuilder sb = do - stage <- getStage - builder <- getBuilder - return $ builder == sb stage - -file :: FilePattern -> Predicate -file f = liftM (any (f ?==)) getFiles - -way :: Way -> Predicate -way w = liftM (w ==) getWay + [res] -> return res + _ -> error $ "Exactly one file expected in target " ++ show target diff --git a/src/Switches.hs b/src/Switches.hs index 244c87f..c30a33f 100644 --- a/src/Switches.hs +++ b/src/Switches.hs @@ -1,15 +1,40 @@ module Switches ( + stage, package, builder, stagedBuilder, file, way, stage0, stage1, stage2, notStage, notStage0, registerPackage, splitObjects ) where +import Way +import Base import Stage +import Package +import Builder import Expression -import Settings.Util import Settings.Default import Oracles.Flag import Oracles.Setting +-- Basic predicates (see Switches.hs for derived predicates) +stage :: Stage -> Predicate +stage s = liftM (s ==) getStage + +package :: Package -> Predicate +package p = liftM (p ==) getPackage + +-- For unstaged builders, e.g. GhcCabal +builder :: Builder -> Predicate +builder b = liftM (b ==) getBuilder + +-- For staged builders, e.g. Ghc Stage +stagedBuilder :: (Stage -> Builder) -> Predicate +stagedBuilder sb = (builder . sb) =<< getStage + +file :: FilePattern -> Predicate +file f = liftM (any (f ?==)) getFiles + +way :: Way -> Predicate +way w = liftM (w ==) getWay + -- Derived predicates stage0 :: Predicate stage0 = stage Stage0 @@ -32,13 +57,12 @@ registerPackage = return True splitObjects :: Predicate splitObjects = do - stage <- getStage -- We don't split bootstrap (stage 0) packages - package <- getPackage -- We don't split compiler - broken <- getFlag SplitObjectsBroken - ghcUnreg <- getFlag GhcUnregisterised - goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] - goodOs <- lift $ targetOss [ "mingw32", "cygwin32", "linux" - , "darwin", "solaris2", "freebsd" - , "dragonfly", "netbsd", "openbsd"] - return $ stage == Stage1 && package /= compiler && not broken - && not ghcUnreg && goodArch && goodOs + goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages + goodPkg <- notP $ package compiler -- We don't split compiler + broken <- lift $ flag SplitObjectsBroken + ghcUnreg <- lift $ flag GhcUnregisterised + goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] + goodOs <- lift $ targetOss [ "mingw32", "cygwin32", "linux", "darwin" + , "solaris2", "freebsd", "dragonfly" + , "netbsd", "openbsd" ] + return $ goodStage && goodPkg && not broken && not ghcUnreg && goodArch && goodOs From git at git.haskell.org Fri Oct 27 00:05:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop exe extension. (ef6ddf9) Message-ID: <20171027000519.0B2ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef6ddf94b8cd9d3ca0f3054dc163d04996838839/ghc >--------------------------------------------------------------- commit ef6ddf94b8cd9d3ca0f3054dc163d04996838839 Author: Andrey Mokhov Date: Sat Jan 9 20:38:42 2016 +0000 Drop exe extension. >--------------------------------------------------------------- ef6ddf94b8cd9d3ca0f3054dc163d04996838839 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 3c5f522..dd3bd12 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - cabal update - os: osx - env: TARGET=inplace/bin/ghc-stage1.exe + env: TARGET=inplace/bin/ghc-stage1 before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Fri Oct 27 00:05:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (d396ba3) Message-ID: <20171027000522.95EDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d396ba3d8f4d2ce6e15d3149404fbb94118bddc3/ghc >--------------------------------------------------------------- commit d396ba3d8f4d2ce6e15d3149404fbb94118bddc3 Author: Andrey Mokhov Date: Fri Feb 26 01:54:51 2016 +0000 Minor revision. >--------------------------------------------------------------- d396ba3d8f4d2ce6e15d3149404fbb94118bddc3 src/Oracles/Dependencies.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index b34535b..aa54d86 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,10 +1,11 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.Dependencies (dependencies, dependenciesOracle) where -import Base import Control.Monad.Trans.Maybe import qualified Data.HashMap.Strict as Map +import Base + newtype DependenciesKey = DependenciesKey (FilePath, FilePath) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -28,10 +29,9 @@ dependencies path obj = do -- Oracle for 'path/dist/.dependencies' files dependenciesOracle :: Rules () -dependenciesOracle = do +dependenciesOracle = void $ do deps <- newCache $ \file -> do putOracle $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return . Map.fromList $ map (\(x:xs) -> (x, xs)) contents - _ <- addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file - return () + addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file From git at git.haskell.org Fri Oct 27 00:05:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependencies. (41778b0) Message-ID: <20171027000518.20DAD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/41778b07cc7fbbb8fa0006343213a65d2c12afaf/ghc >--------------------------------------------------------------- commit 41778b07cc7fbbb8fa0006343213a65d2c12afaf Author: Andrey Mokhov Date: Fri Feb 26 00:46:11 2016 +0000 Add missing dependencies. >--------------------------------------------------------------- 41778b07cc7fbbb8fa0006343213a65d2c12afaf src/Rules/Data.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 360eb5a..1eca7d9 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -57,6 +57,7 @@ buildPackageData context @ Context {..} = do -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps priority 2.0 $ do when (package == hp2ps) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package includes <- interpretInContext context $ fromDiffExpr includesArgs let prefix = fixKey (contextPath context) ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" @@ -73,6 +74,7 @@ buildPackageData context @ Context {..} = do putSuccess $ "| Successfully generated '" ++ mk ++ "'." when (package == unlit) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package let prefix = fixKey (contextPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = unlit" @@ -82,6 +84,7 @@ buildPackageData context @ Context {..} = do putSuccess $ "| Successfully generated '" ++ mk ++ "'." when (package == touchy) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package let prefix = fixKey (contextPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = touchy" @@ -93,6 +96,7 @@ buildPackageData context @ Context {..} = do -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. when (package == ghcCabal && stage == Stage0) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package let prefix = fixKey (contextPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = ghc-cabal" From git at git.haskell.org Fri Oct 27 00:05:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Monoid (ReaderT Target Action a) instance to src/Target.hs. (95d2949) Message-ID: <20171027000523.910D73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95d2949e9c255d525adfcc6af61f6a7711ae5dab/ghc >--------------------------------------------------------------- commit 95d2949e9c255d525adfcc6af61f6a7711ae5dab Author: Andrey Mokhov Date: Fri Aug 21 16:10:44 2015 +0100 Move Monoid (ReaderT Target Action a) instance to src/Target.hs. >--------------------------------------------------------------- 95d2949e9c255d525adfcc6af61f6a7711ae5dab src/Target.hs | 14 ++++++++++++-- 1 file changed, 12 insertions(+), 2 deletions(-) diff --git a/src/Target.hs b/src/Target.hs index 2ce94bc..1717a87 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,6 +1,6 @@ -{-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-} +{-# LANGUAGE DeriveGeneric, FlexibleInstances #-} module Target ( - Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..), + Target (..), StageTarget, StagePackageTarget, FullTarget, stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay, ) where @@ -10,6 +10,8 @@ import Stage import Package import Builder import GHC.Generics +import Data.Monoid +import Control.Monad.Reader -- Target captures all parameters relevant to the current build target: -- * Stage and Package being built, @@ -28,6 +30,14 @@ data Target = Target } deriving (Show, Eq, Generic) +-- If values of type 'a' form a Monoid then we can also derive a Monoid instance +-- for values of type 'ReaderT Target Action a': +-- * the empty computation returns the identity element of the underlying type +-- * two computations can be combined by combining their results +instance Monoid a => Monoid (ReaderT Target Action a) where + mempty = return mempty + mappend = liftM2 mappend + -- StageTarget is a partially constructed Target. Only stage is guaranteed to -- be assigned. type StageTarget = Target From git at git.haskell.org Fri Oct 27 00:05:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't conflict with parallel in the latest Shake, provides a warning free way to be forward and backward compatible with Shake (albeit not pretty) (8efb43d) Message-ID: <20171027000523.B7B873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8efb43dd384111a0f724924507aac59a655b382d/ghc >--------------------------------------------------------------- commit 8efb43dd384111a0f724924507aac59a655b382d Author: Neil Mitchell Date: Sat Jan 9 21:33:02 2016 +0000 Don't conflict with parallel in the latest Shake, provides a warning free way to be forward and backward compatible with Shake (albeit not pretty) >--------------------------------------------------------------- 8efb43dd384111a0f724924507aac59a655b382d src/GHC.hs | 4 ++-- src/Way.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index f967263..1574ec3 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,7 +4,7 @@ module GHC ( deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, + integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, @@ -26,7 +26,7 @@ defaultKnownPackages = , deepseq, deriveConstants, directory, dllSplit, filepath, genapply , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp - , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty + , integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time , touchy, transformers, unlit, unix, win32, xhtml ] diff --git a/src/Way.hs b/src/Way.hs index 3b1f6c0..94a3bcc 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, - vanilla, profiling, logging, parallel, granSim, + vanilla, profiling, logging, Way.parallel, granSim, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, From git at git.haskell.org Fri Oct 27 00:05:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add findGenerator, refactor Oracles.ModuleFiles. (79858ef) Message-ID: <20171027000526.767673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79858ef2f73d7444b74cac12680dfc234fbacda9/ghc >--------------------------------------------------------------- commit 79858ef2f73d7444b74cac12680dfc234fbacda9 Author: Andrey Mokhov Date: Fri Feb 26 02:25:44 2016 +0000 Add findGenerator, refactor Oracles.ModuleFiles. See #210. >--------------------------------------------------------------- 79858ef2f73d7444b74cac12680dfc234fbacda9 src/Oracles/ModuleFiles.hs | 94 +++++++++++++++++++++++++++------------------- src/Rules/Generate.hs | 25 ++---------- 2 files changed, 60 insertions(+), 59 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 79858ef2f73d7444b74cac12680dfc234fbacda9 From git at git.haskell.org Fri Oct 27 00:05:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (bc4a11c) Message-ID: <20171027000527.7D9713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc4a11c9eba6c98e82c2ed8e0f0452c101179660/ghc >--------------------------------------------------------------- commit bc4a11c9eba6c98e82c2ed8e0f0452c101179660 Author: Andrey Mokhov Date: Fri Aug 21 16:11:53 2015 +0100 Clean up. >--------------------------------------------------------------- bc4a11c9eba6c98e82c2ed8e0f0452c101179660 src/Way.hs | 12 +++++++++--- 1 file changed, 9 insertions(+), 3 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 74d1f26..a1df1ce 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,4 +1,4 @@ -module Way ( -- TODO: rename to "Way"? +module Way ( WayUnit (..), Way, wayFromUnits, wayUnit, @@ -13,7 +13,7 @@ module Way ( -- TODO: rename to "Way"? safeDetectWay, detectWay, matchBuildResult ) where -import Base +import Base hiding (unit) import Util import Oracles.Setting import Data.List @@ -74,6 +74,7 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b +vanilla, profiling, logging, parallel, granSim :: Way vanilla = wayFromUnits [] profiling = wayFromUnits [Profiling] logging = wayFromUnits [Logging] @@ -82,6 +83,11 @@ granSim = wayFromUnits [GranSim] -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? +threaded, threadedProfiling, threadedLogging, debug, debugProfiling, + threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, + threadedProfilingDynamic, threadedDynamic, threadedDebugDynamic, + debugDynamic, loggingDynamic, threadedLoggingDynamic :: Way + threaded = wayFromUnits [Threaded] threadedProfiling = wayFromUnits [Threaded, Profiling] threadedLogging = wayFromUnits [Threaded, Logging] @@ -102,7 +108,7 @@ wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" -hisuf, osuf, hcsuf, obootsuf, ssuf :: Way -> String +osuf, ssuf, hisuf, hcsuf, obootsuf, hibootsuf :: Way -> String osuf = (++ "o" ) . wayPrefix ssuf = (++ "s" ) . wayPrefix hisuf = (++ "hi" ) . wayPrefix From git at git.haskell.org Fri Oct 27 00:05:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a .ghci file, useful for experimenting and using ghcid (4444fa4) Message-ID: <20171027000527.E5F163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4444fa437e6a36908414924a707ff538841f17a1/ghc >--------------------------------------------------------------- commit 4444fa437e6a36908414924a707ff538841f17a1 Author: Neil Mitchell Date: Sat Jan 9 21:33:21 2016 +0000 Add a .ghci file, useful for experimenting and using ghcid >--------------------------------------------------------------- 4444fa437e6a36908414924a707ff538841f17a1 .ghci | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.ghci b/.ghci new file mode 100644 index 0000000..1fe85b3 --- /dev/null +++ b/.ghci @@ -0,0 +1,2 @@ +:set -Wall -isrc +:load Main From git at git.haskell.org Fri Oct 27 00:05:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop integerGmp2 and clean up. (efe9d6f) Message-ID: <20171027000531.267173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efe9d6fa2c26d2befc6dcd97eadef5474f94c6e7/ghc >--------------------------------------------------------------- commit efe9d6fa2c26d2befc6dcd97eadef5474f94c6e7 Author: Andrey Mokhov Date: Fri Aug 21 16:12:27 2015 +0100 Drop integerGmp2 and clean up. >--------------------------------------------------------------- efe9d6fa2c26d2befc6dcd97eadef5474f94c6e7 src/Settings/Default.hs | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 5a021e7..71698da 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -3,8 +3,8 @@ module Settings.Default ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, - integerGmp2, integerSimple, parallel, pretty, primitive, process, stm, - templateHaskell, terminfo, time, transformers, unix, win32, xhtml + integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, + terminfo, time, transformers, unix, win32, xhtml ) where import Stage @@ -29,12 +29,16 @@ defaultTargetDirectory stage package defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghcPrim, haskeline - , hoopl, hpc, integerGmp, integerGmp2, integerSimple, parallel - , pretty, primitive, process, stm, templateHaskell, terminfo, time - , transformers, unix, win32, xhtml ] + , containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc + , integerGmp, integerSimple, parallel, pretty, primitive, process, stm + , templateHaskell, terminfo, time, transformers, unix, win32, xhtml ] -- Package definitions +array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, + deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, + integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, + terminfo, time, transformers, unix, win32, xhtml :: Package + array = library "array" base = library "base" binPackageDb = library "bin-package-db" @@ -51,7 +55,6 @@ haskeline = library "haskeline" hoopl = library "hoopl" hpc = library "hpc" integerGmp = library "integer-gmp" -integerGmp2 = library "integer-gmp" `setPath` "libraries/integer-gmp2" integerSimple = library "integer-simple" parallel = library "parallel" pretty = library "pretty" From git at git.haskell.org Fri Oct 27 00:05:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor getSingleton to avoid using list, otherwise an import of Data.Extra.List causes shadowing issues (dbe8c1e) Message-ID: <20171027000531.9F7313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dbe8c1e0f387f98c7edaaaf2f5dfda1ed25a9b2a/ghc >--------------------------------------------------------------- commit dbe8c1e0f387f98c7edaaaf2f5dfda1ed25a9b2a Author: Neil Mitchell Date: Sat Jan 9 21:45:53 2016 +0000 Refactor getSingleton to avoid using list, otherwise an import of Data.Extra.List causes shadowing issues >--------------------------------------------------------------- dbe8c1e0f387f98c7edaaaf2f5dfda1ed25a9b2a src/Expression.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 6e2a225..932ed80 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -204,7 +204,7 @@ getOutput = do getSingleton :: Expr [a] -> String -> Expr a getSingleton expr msg = do - list <- expr - case list of + xs <- expr + case xs of [res] -> return res _ -> lift $ putError msg From git at git.haskell.org Fri Oct 27 00:05:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Context as key to moduleFilesOracle. (1fd2368) Message-ID: <20171027000533.A13DE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fd23681fe3f63fcdff82ab7b1d65eeedf5227aa/ghc >--------------------------------------------------------------- commit 1fd23681fe3f63fcdff82ab7b1d65eeedf5227aa Author: Andrey Mokhov Date: Fri Feb 26 03:37:22 2016 +0000 Use Context as key to moduleFilesOracle. See #210. >--------------------------------------------------------------- 1fd23681fe3f63fcdff82ab7b1d65eeedf5227aa src/Oracles/ModuleFiles.hs | 42 ++++++++++++++++++------------------------ 1 file changed, 18 insertions(+), 24 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 73ec6eb..630a05f 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,6 +1,6 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, LambdaCase #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.ModuleFiles ( - findGenerator, haskellSources, moduleFilesOracle, findModuleFiles + findGenerator, haskellSources, moduleFilesOracle ) where import qualified Data.HashMap.Strict as Map @@ -11,7 +11,7 @@ import Expression import Oracles.PackageData import Settings.Paths -newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) +newtype ModuleFilesKey = ModuleFilesKey Context deriving (Show, Typeable, Eq, Hashable, Binary, NFData) newtype Generator = Generator (Context, FilePath) @@ -55,32 +55,29 @@ generatedFile context moduleName = contextFiles :: Context -> Action [(String, Maybe FilePath)] contextFiles context @ Context {..} = do let path = contextPath context - srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - zip modules <$> findModuleFiles (path -/- "build/autogen" : dirs) modules + zip modules <$> askOracle (ModuleFilesKey context) -- | This is an important oracle whose role is to find and cache module source --- files. More specifically, it takes a list of directories @dirs@ and a sorted --- list of module names @modules@ as arguments, and for each module, e.g. +-- files. It takes a 'Context', looks up corresponding source directories @dirs@ +-- and sorted list of module names @modules@, and for each module, e.g. -- @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, such that -- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or 'Nothing' -- if there is no such file. If more than one matching file is found an error is --- raised. For example, for the 'compiler' package given --- @dirs = ["compiler/codeGen", "compiler/parser"]@, and --- @modules = ["CodeGen.Platform.ARM", "Lexer", "Missing.Module"]@, it produces --- @[Just "compiler/codeGen/CodeGen/Platform/ARM.hs", --- Just "compiler/parser/Lexer.x", Nothing]@. -findModuleFiles :: [FilePath] -> [String] -> Action [Maybe FilePath] -findModuleFiles dirs modules = askOracle $ ModuleFilesKey (dirs, modules) - +-- raised. For example, for @Context Stage1 compiler vanilla@, @dirs@ will +-- contain ["compiler/codeGen", "compiler/parser"], and @modules@ will contain +-- ["CodeGen.Platform.ARM", "Config", "Lexer"]; the oracle will produce a list +-- containing [Just "compiler/codeGen/CodeGen/Platform/ARM.hs", Nothing, +-- Just "compiler/parser/Lexer.x"]. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do - void $ addOracle $ \(ModuleFilesKey (dirs, modules)) -> do - let decodedPairs = map decodeModule modules - modDirFiles = map (bimap head id . unzip) - . groupBy ((==) `on` fst) $ decodedPairs - + void $ addOracle $ \(ModuleFilesKey context) -> do + let path = contextPath context + autogen = path -/- "build/autogen" + srcDirs <- pkgDataList $ SrcDirs path + modules <- fmap sort . pkgDataList $ Modules path + let dirs = autogen : map (pkgPath (package context) -/-) srcDirs + modDirFiles = groupSort $ map decodeModule modules result <- fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do @@ -90,15 +87,12 @@ moduleFilesOracle = void $ do cmp fe f = compare (dropExtension fe) f found = intersectOrd cmp noBoot mFiles return (map (fullDir -/-) found, mDir) - let pairs = sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ] - unless (null multi) $ do let (m, f1, f2) = head multi putError $ "Module " ++ m ++ " has more than one source file: " ++ f1 ++ " and " ++ f2 ++ "." - return $ lookupAll modules pairs gens <- newCache $ \context -> do From git at git.haskell.org Fri Oct 27 00:05:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, fix -Wall warnings. (4238fb7) Message-ID: <20171027000534.D9D613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4238fb77e4db131ddb1cb938a76f0dbe2b03a798/ghc >--------------------------------------------------------------- commit 4238fb77e4db131ddb1cb938a76f0dbe2b03a798 Author: Andrey Mokhov Date: Fri Aug 21 16:28:03 2015 +0100 Clean up, fix -Wall warnings. >--------------------------------------------------------------- 4238fb77e4db131ddb1cb938a76f0dbe2b03a798 src/Main.hs | 1 + src/Oracles/ArgsHash.hs | 4 +-- src/Oracles/Base.hs | 2 +- src/Oracles/Dependencies.hs | 2 +- src/Oracles/Flag.hs | 5 +-- src/Oracles/PackageDeps.hs | 2 +- src/Oracles/WindowsRoot.hs | 2 +- src/Package.hs | 6 ++-- src/Rules.hs | 14 ++++---- src/Rules/Actions.hs | 15 ++++---- src/Rules/Cabal.hs | 24 ++++++------- src/Rules/Config.hs | 5 +-- src/Rules/Data.hs | 22 ++++++------ src/Rules/Dependencies.hs | 6 ++-- src/Rules/Documentation.hs | 17 +++++---- src/Rules/Resources.hs | 7 ++-- src/Settings/Builders/Ar.hs | 1 + src/Settings/Builders/Gcc.hs | 27 +++++++------- src/Settings/Builders/Ghc.hs | 14 ++++---- src/Settings/Builders/GhcCabal.hs | 40 +++++++++++---------- src/Settings/Builders/Haddock.hs | 5 +-- src/Settings/Builders/Ld.hs | 12 +++---- src/Settings/TargetDirectory.hs | 6 ++-- src/Settings/User.hs | 7 +++- src/Settings/Util.hs | 74 +++++++++++++++------------------------ src/Settings/Ways.hs | 17 +++------ src/Util.hs | 18 +++++----- 27 files changed, 162 insertions(+), 193 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4238fb77e4db131ddb1cb938a76f0dbe2b03a798 From git at git.haskell.org Fri Oct 27 00:05:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rewrite digest, avoid using list (to avoid a shadow warning), and avoid using head (partial function) (02ec50d) Message-ID: <20171027000535.0AF9B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02ec50d957a3ebd736ccb631795489eec971d528/ghc >--------------------------------------------------------------- commit 02ec50d957a3ebd736ccb631795489eec971d528 Author: Neil Mitchell Date: Sat Jan 9 21:46:36 2016 +0000 Rewrite digest, avoid using list (to avoid a shadow warning), and avoid using head (partial function) >--------------------------------------------------------------- 02ec50d957a3ebd736ccb631795489eec971d528 src/Rules/Actions.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 51f7625..338bec3 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -132,7 +132,6 @@ putInfo (Target.Target {..}) = putBuild $ renderBox where stageInfo = if isStaged builder then "" else "stage = " ++ show stage ++ ", " wayInfo = if way == vanilla then "" else ", way = " ++ show way - digest list = case list of - [] -> "none" - [x] -> x - xs -> head xs ++ " (and " ++ show (length xs - 1) ++ " more)" + digest [] = "none" + digest [x] = x + digest (x:xs) = x ++ " (and " ++ show (length xs) ++ " more)" From git at git.haskell.org Fri Oct 27 00:05:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (9171856) Message-ID: <20171027000537.241803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9171856f647213aea42005a8dfec9bff0ff7223c/ghc >--------------------------------------------------------------- commit 9171856f647213aea42005a8dfec9bff0ff7223c Author: Andrey Mokhov Date: Fri Feb 26 11:37:00 2016 +0000 Minor revision. See #210. >--------------------------------------------------------------- 9171856f647213aea42005a8dfec9bff0ff7223c src/Oracles/ModuleFiles.hs | 18 ++++++++++++------ 1 file changed, 12 insertions(+), 6 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 630a05f..508b554 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -34,7 +34,12 @@ determineBuilder file = case takeExtension file of -- ".build/stage1/base/build/Prelude.hs" -- == Nothing findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder)) -findGenerator context file = askOracle $ Generator (context, file) +findGenerator context file = do + maybeSource <- askOracle $ Generator (context, file) + return $ do + source <- maybeSource + builder <- determineBuilder source + return (source, builder) -- | Find all Haskell source files for a given 'Context'. haskellSources :: Context -> Action [FilePath] @@ -44,8 +49,9 @@ haskellSources context = do -- that GHC/Prim.hs lives in build/autogen/. TODO: fix the inconsistency? let modFile ("GHC.Prim", _) = autogen -/- "GHC/Prim.hs" modFile (m, Nothing ) = generatedFile context m - modFile (m, Just file ) | "//*hs" ?== file = file - | otherwise = modFile (m, Nothing) + modFile (m, Just file ) + | takeExtension file `elem` [".hs", ".lhs"] = file + | otherwise = generatedFile context m map modFile <$> contextFiles context generatedFile :: Context -> String -> FilePath @@ -53,7 +59,7 @@ generatedFile context moduleName = contextPath context -/- "build" -/- replaceEq '.' '/' moduleName <.> "hs" contextFiles :: Context -> Action [(String, Maybe FilePath)] -contextFiles context @ Context {..} = do +contextFiles context at Context {..} = do let path = contextPath context modules <- fmap sort . pkgDataList $ Modules path zip modules <$> askOracle (ModuleFilesKey context) @@ -97,8 +103,8 @@ moduleFilesOracle = void $ do gens <- newCache $ \context -> do files <- contextFiles context - return $ Map.fromList [ (generatedFile context modName, (src, builder)) + return $ Map.fromList [ (generatedFile context modName, src) | (modName, Just src) <- files - , let Just builder = determineBuilder src ] + , takeExtension src `notElem` [".hs", ".lhs"] ] addOracle $ \(Generator (context, file)) -> Map.lookup file <$> gens context From git at git.haskell.org Fri Oct 27 00:05:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop DepKeys, add DepId, clean up code. (49574e6) Message-ID: <20171027000538.7FDC23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49574e62cd65023a3d4c6c145bbac86c16c73d69/ghc >--------------------------------------------------------------- commit 49574e62cd65023a3d4c6c145bbac86c16c73d69 Author: Andrey Mokhov Date: Fri Aug 21 16:29:01 2015 +0100 Drop DepKeys, add DepId, clean up code. >--------------------------------------------------------------- 49574e62cd65023a3d4c6c145bbac86c16c73d69 src/Oracles/PackageData.hs | 74 +++++++++++++++++++--------------------------- 1 file changed, 31 insertions(+), 43 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 4097ac1..c873601 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -8,7 +8,6 @@ module Oracles.PackageData ( import Base import Util import Data.List -import Data.Maybe import Control.Applicative import qualified Data.HashMap.Strict as Map @@ -22,6 +21,7 @@ import qualified Data.HashMap.Strict as Map -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] data PackageData = Version FilePath | PackageKey FilePath + | LibName FilePath | Synopsis FilePath | BuildGhciLib FilePath @@ -30,7 +30,7 @@ data PackageDataList = Modules FilePath | SrcDirs FilePath | IncludeDirs FilePath | Deps FilePath - | DepKeys FilePath + | DepIds FilePath | DepNames FilePath | CppArgs FilePath | HsArgs FilePath @@ -41,59 +41,47 @@ data PackageDataList = Modules FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) --- TODO: is this needed? askPackageData :: FilePath -> String -> Action String askPackageData path key = do let fullKey = replaceSeparators '_' $ path ++ "_" ++ key - pkgData = path -/- "package-data.mk" - value <- askOracle $ PackageDataKey (pkgData, fullKey) - return $ fromMaybe - (error $ "No key '" ++ key ++ "' in " ++ pkgData ++ ".") value + file = path -/- "package-data.mk" + maybeValue <- askOracle $ PackageDataKey (file, fullKey) + case maybeValue of + Nothing -> putError $ "No key '" ++ key ++ "' in " ++ file ++ "." + Just value -> return value pkgData :: PackageData -> Action String -pkgData packageData = do - let (key, path) = case packageData of - Version path -> ("VERSION" , path) - PackageKey path -> ("PACKAGE_KEY" , path) - Synopsis path -> ("SYNOPSIS" , path) - BuildGhciLib path -> ("BUILD_GHCI_LIB", path) - fullKey = replaceSeparators '_' $ path ++ "_" ++ key - pkgData = path -/- "package-data.mk" - res <- askOracle $ PackageDataKey (pkgData, fullKey) - return $ fromMaybe - (error $ "No key '" ++ key ++ "' in " ++ pkgData ++ ".") res +pkgData packageData = case packageData of + Version path -> askPackageData path "VERSION" + PackageKey path -> askPackageData path "PACKAGE_KEY" + LibName path -> askPackageData path "LIB_NAME" + Synopsis path -> askPackageData path "SYNOPSIS" + BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" pkgDataList :: PackageDataList -> Action [String] -pkgDataList packageData = do - let (key, path, defaultValue) = case packageData of - Modules path -> ("MODULES" , path, "" ) - HiddenModules path -> ("HIDDEN_MODULES" , path, "" ) - SrcDirs path -> ("HS_SRC_DIRS" , path, ".") - IncludeDirs path -> ("INCLUDE_DIRS" , path, ".") - Deps path -> ("DEPS" , path, "" ) - DepKeys path -> ("DEP_KEYS" , path, "" ) - DepNames path -> ("DEP_NAMES" , path, "" ) - CppArgs path -> ("CPP_OPTS" , path, "" ) - HsArgs path -> ("HC_OPTS" , path, "" ) - CcArgs path -> ("CC_OPTS" , path, "" ) - CSrcs path -> ("C_SRCS" , path, "" ) - DepIncludeDirs path -> ("DEP_INCLUDE_DIRS_SINGLE_QUOTED", path, "" ) - fullKey = replaceSeparators '_' $ path ++ "_" ++ key - pkgData = path -/- "package-data.mk" - unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') - res <- askOracle $ PackageDataKey (pkgData, fullKey) - return $ map unquote $ words $ case res of - Nothing -> error $ "No key '" ++ key ++ "' in " ++ pkgData ++ "." - Just "" -> defaultValue - Just value -> value +pkgDataList packageData = fmap (map unquote . words) $ case packageData of + Modules path -> askPackageData path "MODULES" + HiddenModules path -> askPackageData path "HIDDEN_MODULES" + SrcDirs path -> askPackageData path "HS_SRC_DIRS" + IncludeDirs path -> askPackageData path "INCLUDE_DIRS" + Deps path -> askPackageData path "DEPS" + DepIds path -> askPackageData path "DEP_IPIDS" + DepNames path -> askPackageData path "DEP_NAMES" + CppArgs path -> askPackageData path "CPP_OPTS" + HsArgs path -> askPackageData path "HC_OPTS" + CcArgs path -> askPackageData path "CC_OPTS" + CSrcs path -> askPackageData path "C_SRCS" + DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" + where + unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') -- Oracle for 'package-data.mk' files packageDataOracle :: Rules () packageDataOracle = do - pkgData <- newCache $ \file -> do + pkgDataContents <- newCache $ \file -> do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(PackageDataKey (file, key)) -> - Map.lookup key <$> pkgData (unifyPath file) + _ <- addOracle $ \(PackageDataKey (file, key)) -> + Map.lookup key <$> pkgDataContents file return () From git at git.haskell.org Fri Oct 27 00:05:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid using Traversable to get at forM (eda5882) Message-ID: <20171027000538.E49183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eda5882a83ad353eb636b4249439095d237e331f/ghc >--------------------------------------------------------------- commit eda5882a83ad353eb636b4249439095d237e331f Author: Neil Mitchell Date: Sat Jan 9 21:46:52 2016 +0000 Avoid using Traversable to get at forM >--------------------------------------------------------------- eda5882a83ad353eb636b4249439095d237e331f src/Rules.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index fe8242b..7af1556 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -2,7 +2,6 @@ module Rules (generateTargets, packageRules) where import Base import Data.Foldable -import Data.Traversable import Expression import GHC import Rules.Generate @@ -25,7 +24,7 @@ targetsForStage :: Stage -> Action [String] targetsForStage stage = do pkgs <- interpretWithStage stage getPackages let libPkgs = filter isLibrary pkgs \\ [rts, libffi] - libTargets <- fmap concat . for libPkgs $ \pkg -> do + libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg needHaddock <- interpretPartial target buildHaddock return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] From git at git.haskell.org Fri Oct 27 00:05:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use conventional whitespacing for @. (31515fa) Message-ID: <20171027000540.A4F1F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31515fad107d28f83b47d6249dd7b8c1eeb3bc70/ghc >--------------------------------------------------------------- commit 31515fad107d28f83b47d6249dd7b8c1eeb3bc70 Author: Andrey Mokhov Date: Fri Feb 26 11:37:47 2016 +0000 Use conventional whitespacing for @. See #210. >--------------------------------------------------------------- 31515fad107d28f83b47d6249dd7b8c1eeb3bc70 src/GHC.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 4 ++-- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Rules/Program.hs | 6 +++--- src/Rules/Register.hs | 2 +- src/Settings/Paths.hs | 10 +++++----- src/Way.hs | 2 +- 12 files changed, 20 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 31515fad107d28f83b47d6249dd7b8c1eeb3bc70 From git at git.haskell.org Fri Oct 27 00:05:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove parallel, stm, random, primitive, vector and dph from Stage1 packages, drop integerGmp2 support. (228da6f) Message-ID: <20171027000542.1BAA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/228da6fe168616b0aeca8d462eab345cef5b7e48/ghc >--------------------------------------------------------------- commit 228da6fe168616b0aeca8d462eab345cef5b7e48 Author: Andrey Mokhov Date: Fri Aug 21 16:30:17 2015 +0100 Remove parallel, stm, random, primitive, vector and dph from Stage1 packages, drop integerGmp2 support. >--------------------------------------------------------------- 228da6fe168616b0aeca8d462eab345cef5b7e48 src/Settings/Packages.hs | 11 ++++------- 1 file changed, 4 insertions(+), 7 deletions(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 369879c..5820e0c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -29,12 +29,13 @@ packagesStage0 = mconcat [ append [binPackageDb, binary, cabal, compiler, hoopl, hpc, transformers] , notWindowsHost ? notTargetOs "ios" ? append [terminfo] ] +-- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory - , filepath, ghcPrim, haskeline, integerLibrary, parallel - , pretty, primitive, process, stm, templateHaskell, time ] + , filepath, ghcPrim, haskeline, integerLibrary, pretty, process + , templateHaskell, time ] , windowsHost ? append [win32] , notWindowsHost ? append [unix] , buildHaddock ? append [xhtml] ] @@ -43,9 +44,5 @@ knownPackages :: [Package] knownPackages = defaultKnownPackages ++ userKnownPackages -- Note: this is slow but we keep it simple as there not too many packages (30) --- We handle integerLibrary in a special way, because packages integerGmp and --- integerGmp2 have the same package name -- we return the user-selected one. findKnownPackage :: PackageName -> Maybe Package -findKnownPackage name - | name == pkgName integerLibrary = Just integerLibrary - | otherwise = find (\pkg -> pkgName pkg == name) knownPackages +findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Fri Oct 27 00:07:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generatePackageCode rule, alexArgs, happyArgs and Hsc2Hs builder. (fdbc3fb) Message-ID: <20171027000701.8B5483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fdbc3fba223a2d437954bd0908fdb839fe836ac8/ghc >--------------------------------------------------------------- commit fdbc3fba223a2d437954bd0908fdb839fe836ac8 Author: Andrey Mokhov Date: Sun Sep 20 02:22:46 2015 +0100 Add generatePackageCode rule, alexArgs, happyArgs and Hsc2Hs builder. >--------------------------------------------------------------- fdbc3fba223a2d437954bd0908fdb839fe836ac8 cfg/system.config.in | 2 ++ doc/demo.txt | 5 ++++ src/Builder.hs | 2 ++ src/Rules/Documentation.hs | 6 ++--- src/Rules/Generate.hs | 55 ++++++++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 2 ++ src/Settings/Args.hs | 20 +++++++++------ src/Settings/Builders/Alex.hs | 14 +++++++++++ src/Settings/Builders/Happy.hs | 13 ++++++++++ 9 files changed, 108 insertions(+), 11 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index a274e84..b92b6ba 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -19,6 +19,8 @@ ghc-cabal = @hardtop@/inplace/bin/ghc-cabal haddock = @hardtop@/inplace/bin/haddock +hsc2hs = @hardtop@/inplace/bin/hsc2hs + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ diff --git a/doc/demo.txt b/doc/demo.txt index 7acd27d..28b3689 100644 --- a/doc/demo.txt +++ b/doc/demo.txt @@ -12,3 +12,8 @@ * https://mail.haskell.org/pipermail/ghc-commits/2013-May/001712.html * see ghc.mk, comment about parallel ghc-pkg invokations + +5. Discovered dead code in the old build system, e.g: + +* Alex3 variable not needed as Alex 3.1 is required. +* There are no generated *.y/*.ly files, hence they can never be in the build directory. \ No newline at end of file diff --git a/src/Builder.hs b/src/Builder.hs index 8e5f639..3a24df3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -26,6 +26,7 @@ data Builder = Alex | Haddock | Happy | HsColour + | Hsc2Hs | Ld deriving (Show, Eq, Generic) @@ -49,6 +50,7 @@ builderKey builder = case builder of Happy -> "happy" Haddock -> "haddock" HsColour -> "hscolour" + Hsc2Hs -> "hsc2hs" Ld -> "ld" builderPath :: Builder -> Action FilePath diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 5978cfd..2ebaa59 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -10,9 +10,9 @@ import Settings -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. buildPackageDocumentation :: Resources -> PartialTarget -> Rules () -buildPackageDocumentation _ target @ (PartialTarget stage pkg) = - let cabalFile = pkgCabalFile pkg - haddockFile = pkgHaddockFile pkg +buildPackageDocumentation _ target @ (PartialTarget stage package) = + let cabalFile = pkgCabalFile package + haddockFile = pkgHaddockFile package in when (stage == Stage1) $ do haddockFile %> \file -> do whenM (specified HsColour) $ do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs new file mode 100644 index 0000000..055dccb --- /dev/null +++ b/src/Rules/Generate.hs @@ -0,0 +1,55 @@ +module Rules.Generate (generatePackageCode) where + +import Expression +import Oracles +import Rules.Actions +import Rules.Resources +import Settings + +-- The following generators and corresponding source extensions are supported: +knownGenerators :: [ (Builder, String) ] +knownGenerators = [ (Alex , ".x" ) + , (Happy , ".y" ) + , (Happy , ".ly" ) + , (Hsc2Hs , ".hsc") ] + +determineBuilder :: FilePath -> Maybe Builder +determineBuilder file = fmap fst $ find (\(_, e) -> e == ext) knownGenerators + where + ext = takeExtension file + +generatePackageCode :: Resources -> PartialTarget -> Rules () +generatePackageCode _ target @ (PartialTarget stage package) = + let path = targetPath stage package + packagePath = pkgPath package + buildPath = path -/- "build" + in do + buildPath "*.hs" %> \file -> do + dirs <- interpretPartial target $ getPkgDataList SrcDirs + files <- getDirectoryFiles "" $ + [ packagePath d takeBaseName file <.> "*" | d <- dirs ] + let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] + (src, builder) = head gens + when (length gens /= 1) . putError $ + "Exactly one generator expected for " ++ file + ++ "(found: " ++ show gens ++ ")." + need [src] + build $ fullTarget target builder [src] [file] + +-- $1/$2/build/%.hs : $1/$3/%.ly | $$$$(dir $$$$@)/. +-- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ + +-- $1/$2/build/%.hs : $1/$3/%.y | $$$$(dir $$$$@)/. +-- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ + +-- $1/$2/build/%_hsc.c $1/$2/build/%_hsc.h $1/$2/build/%.hs : $1/$3/%.hsc $$$$(hsc2hs_INPLACE) | $$$$(dir $$$$@)/. +-- $$(call cmd,hsc2hs_INPLACE) $$($1_$2_ALL_HSC2HS_OPTS) $$< -o $$@ + +-- # Now the rules for hs-boot files. + +-- $1/$2/build/%.hs-boot : $1/$3/%.hs-boot +-- "$$(CP)" $$< $$@ + +-- $1/$2/build/%.lhs-boot : $1/$3/%.lhs-boot +-- "$$(CP)" $$< $$@ + diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index dfc15e8..9da4f8b 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -5,6 +5,7 @@ import Rules.Compile import Rules.Data import Rules.Dependencies import Rules.Documentation +import Rules.Generate import Rules.Library import Rules.Resources import Target @@ -13,6 +14,7 @@ buildPackage :: Resources -> PartialTarget -> Rules () buildPackage = mconcat [ buildPackageData , buildPackageDependencies + , generatePackageCode , compilePackage , buildPackageLibrary , buildPackageDocumentation ] diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 5a8c63a..2e2f379 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -1,12 +1,14 @@ module Settings.Args (getArgs) where import Expression +import Settings.Builders.Alex import Settings.Builders.Ar import Settings.Builders.Gcc import Settings.Builders.Ghc import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg import Settings.Builders.Haddock +import Settings.Builders.Happy import Settings.Builders.Ld import Settings.User @@ -23,14 +25,16 @@ getArgs = fromDiffExpr $ defaultArgs <> userArgs -- TODO: is GhcHcOpts=-Rghc-timing needed? defaultArgs :: Args defaultArgs = mconcat - [ cabalArgs - , ghcPkgArgs - , ghcMArgs - , gccMArgs - , ghcArgs - , gccArgs + [ alexArgs , arArgs - , ldArgs + , cabalArgs + , customPackageArgs + , ghcArgs , ghcCabalHsColourArgs + , ghcMArgs + , ghcPkgArgs + , gccArgs + , gccMArgs , haddockArgs - , customPackageArgs ] + , happyArgs + , ldArgs ] diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs new file mode 100644 index 0000000..6aedcdb --- /dev/null +++ b/src/Settings/Builders/Alex.hs @@ -0,0 +1,14 @@ +module Settings.Builders.Alex (alexArgs) where + +import Expression +import GHC (compiler) +import Predicates (builder, package) + +alexArgs :: Args +alexArgs = builder Alex ? do + file <- getFile + src <- getSource + mconcat [ arg "-g" + , package compiler ? arg "--latin1" + , arg src + , arg "-o", arg file ] diff --git a/src/Settings/Builders/Happy.hs b/src/Settings/Builders/Happy.hs new file mode 100644 index 0000000..fcd962a --- /dev/null +++ b/src/Settings/Builders/Happy.hs @@ -0,0 +1,13 @@ +module Settings.Builders.Happy (happyArgs) where + +import Expression +import Predicates (builder) + +happyArgs :: Args +happyArgs = builder Happy ? do + file <- getFile + src <- getSource + mconcat [ arg "-agc" + , arg "--strict" + , arg src + , arg "-o", arg file ] From git at git.haskell.org Fri Oct 27 00:07:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: We can now build profiling way (b052ae7) Message-ID: <20171027000704.A51893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b052ae700aa9a6831dc824824617bbebc4494351/ghc >--------------------------------------------------------------- commit b052ae700aa9a6831dc824824617bbebc4494351 Author: Andrey Mokhov Date: Thu Mar 10 00:26:04 2016 +0000 We can now build profiling way See #186. [skip ci] >--------------------------------------------------------------- b052ae700aa9a6831dc824824617bbebc4494351 README.md | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/README.md b/README.md index b6d762b..7317384 100644 --- a/README.md +++ b/README.md @@ -100,7 +100,7 @@ zero (see [#197][test-issue]). Current limitations ------------------- The new build system still lacks many important features: -* We only build `vanilla` way: [#4][dynamic-issue], [#186][profiling-issue]. +* We only build `vanilla` and `profiling` way: [#4][dynamic-issue]. * Validation is not implemented: [#187][validation-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. @@ -141,7 +141,6 @@ helped me endure and enjoy the project. [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs [test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 -[profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 From git at git.haskell.org Fri Oct 27 00:07:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move bootstrapping.conf to .build. (24e6c28) Message-ID: <20171027000701.A03763A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/24e6c28e5884d49fbd408fe81fad9ca48c1f7f94/ghc >--------------------------------------------------------------- commit 24e6c28e5884d49fbd408fe81fad9ca48c1f7f94 Author: Andrey Mokhov Date: Mon Jan 11 01:29:35 2016 +0000 Move bootstrapping.conf to .build. See #113. >--------------------------------------------------------------- 24e6c28e5884d49fbd408fe81fad9ca48c1f7f94 shaking-up-ghc.cabal | 2 +- src/Base.hs | 13 ------------- src/Oracles/ModuleFiles.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Settings.hs | 4 ++-- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/{TargetDirectory.hs => Paths.hs} | 17 +++++++++++++---- 8 files changed, 20 insertions(+), 24 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index a7b3352..a091020 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -95,7 +95,7 @@ executable ghc-shake , Settings.Packages.RunGhc , Settings.Packages.Touchy , Settings.Packages.Unlit - , Settings.TargetDirectory + , Settings.Paths , Settings.User , Settings.Ways , Stage diff --git a/src/Base.hs b/src/Base.hs index 4b6ad10..8786c26 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -18,7 +18,6 @@ module Base ( -- * Paths shakeFilesPath, configPath, sourcePath, programInplacePath, bootPackageConstraints, packageDependencies, - packageConfiguration, packageConfigurationInitialised, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, @@ -44,7 +43,6 @@ import qualified System.Directory as IO import System.IO -- TODO: reexport Stage, etc.? -import Stage -- Build system files and paths shakePath :: FilePath @@ -71,17 +69,6 @@ bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" packageDependencies :: FilePath packageDependencies = shakeFilesPath -/- "package-dependencies" --- TODO: move to buildRootPath, see #113 -packageConfiguration :: Stage -> FilePath -packageConfiguration Stage0 = "libraries/bootstrapping.conf" -packageConfiguration _ = "inplace/lib/package.conf.d" - --- StageN, N > 0, share the same packageConfiguration (see above) -packageConfigurationInitialised :: Stage -> FilePath -packageConfigurationInitialised stage = - shakeFilesPath -/- "package-configuration-initialised-" - ++ stageString (min stage Stage1) - -- Utility functions -- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 33f6138..391990e 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -5,7 +5,7 @@ import Base import Oracles.PackageData import Package import Stage -import Settings.TargetDirectory +import Settings.Paths newtype ModuleFilesKey = ModuleFilesKey ([String], [FilePath]) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 93a121b..7e811ba 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -7,7 +7,7 @@ import Oracles import Rules.Actions import Settings.Builders.Common import Settings.Packages.Rts -import Settings.TargetDirectory +import Settings.Paths import Settings.User -- TODO: this should be moved elsewhere diff --git a/src/Settings.hs b/src/Settings.hs index 229a2f9..12830ca 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,6 +1,6 @@ module Settings ( module Settings.Packages, - module Settings.TargetDirectory, + module Settings.Paths, module Settings.User, module Settings.Ways, getPkgData, getPkgDataList, getTopDirectory, programPath, isLibrary, @@ -12,7 +12,7 @@ import Expression import Oracles import Oracles.ModuleFiles import Settings.Packages -import Settings.TargetDirectory +import Settings.Paths import Settings.User import Settings.Ways diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs index 43b9455..c1f1435 100644 --- a/src/Settings/Builders/HsCpp.hs +++ b/src/Settings/Builders/HsCpp.hs @@ -5,7 +5,7 @@ import GHC import Oracles import Predicates (builder) import Settings.Builders.GhcCabal -import Settings.TargetDirectory +import Settings.Paths hsCppBuilderArgs :: Args hsCppBuilderArgs = builder HsCpp ? do diff --git a/src/Settings/Packages/Ghc.hs b/src/Settings/Packages/Ghc.hs index 0830cb6..a7936e9 100644 --- a/src/Settings/Packages/Ghc.hs +++ b/src/Settings/Packages/Ghc.hs @@ -4,7 +4,7 @@ import Expression import GHC (ghc, compiler) import Oracles.Config.Setting import Predicates (builder, builderGhc, package, notStage0) -import Settings.TargetDirectory +import Settings.Paths ghcPackageArgs :: Args ghcPackageArgs = package ghc ? do diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/Paths.hs similarity index 73% rename from src/Settings/TargetDirectory.hs rename to src/Settings/Paths.hs index 6bbef72..bec143b 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/Paths.hs @@ -1,14 +1,12 @@ -module Settings.TargetDirectory ( +module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgGhciLibraryFile + pkgGhciLibraryFile, packageConfiguration, packageConfigurationInitialised ) where import Base import Expression import Settings.User --- TODO: rename to Settings.Paths as part of #113 - -- User can override the default target directory settings given below targetDirectory :: Stage -> Package -> FilePath targetDirectory = userTargetDirectory @@ -41,3 +39,14 @@ pkgLibraryFile stage pkg componentId way = do pkgGhciLibraryFile :: Stage -> Package -> String -> FilePath pkgGhciLibraryFile stage pkg componentId = targetPath stage pkg -/- "build" -/- "HS" ++ componentId <.> "o" + +-- TODO: move to buildRootPath, see #113 +packageConfiguration :: Stage -> FilePath +packageConfiguration Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" +packageConfiguration _ = "inplace/lib/package.conf.d" + +-- StageN, N > 0, share the same packageConfiguration (see above) +packageConfigurationInitialised :: Stage -> FilePath +packageConfigurationInitialised stage = + shakeFilesPath -/- "package-configuration-initialised-" + ++ stageString (min stage Stage1) From git at git.haskell.org Fri Oct 27 00:07:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update Setting.hs (55b0d41) Message-ID: <20171027000705.440AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/55b0d414555297fc845a3ed0196accd5ab454890/ghc >--------------------------------------------------------------- commit 55b0d414555297fc845a3ed0196accd5ab454890 Author: Moritz Angermann Date: Mon Jan 11 11:19:18 2016 +0800 Update Setting.hs Set a sensible default `cmdLineLengthLimit` for os x. >--------------------------------------------------------------- 55b0d414555297fc845a3ed0196accd5ab454890 src/Oracles/Config/Setting.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 0047f03..46d0d33 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -166,6 +166,9 @@ cmdLineLengthLimit = do return $ case (windows, osx) of -- windows (True, False) -> 31000 - -- osx 262144 is ARG_MAX, 33166 experimentally determined - (False, True) -> 262144 - 33166 + -- osx 262144 is ARG_MAX + -- yet when using `xargs` on osx this is reduced by over 20 000. + -- 200 000 seems like a sensible limit. + (False, True) -> 200000 + -- On all other systems, we try this: _ -> 4194304 -- Cabal needs a bit more than 2MB! From git at git.haskell.org Fri Oct 27 00:07:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Collect arguments for Hsc2Hs builder. (f225aed) Message-ID: <20171027000705.541293A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f225aedc18efa02b48f99ee84d0794eb4aa94368/ghc >--------------------------------------------------------------- commit f225aedc18efa02b48f99ee84d0794eb4aa94368 Author: Andrey Mokhov Date: Mon Sep 21 00:54:29 2015 +0100 Collect arguments for Hsc2Hs builder. >--------------------------------------------------------------- f225aedc18efa02b48f99ee84d0794eb4aa94368 src/Settings/Builders/Hsc2Hs.hs | 70 +++++++++++++++++++++++++++++++++++++++++ 1 file changed, 70 insertions(+) diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs new file mode 100644 index 0000000..fae7c1f --- /dev/null +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -0,0 +1,70 @@ +module Settings.Builders.Hsc2Hs (hsc2HsArgs) where + +import Expression +import Oracles +import Predicates (builder, stage0, notStage0) +import Settings +import Settings.Builders.GhcCabal + +hsc2HsArgs :: Args +hsc2HsArgs = builder Hsc2Hs ? do + stage <- getStage + src <- getSource + file <- getFile + ccPath <- lift . builderPath $ Gcc stage + gmpDirs <- getSettingList GmpIncludeDirs + cFlags <- getCFlags + lFlags <- getLFlags + hArch <- getSetting HostArch + hOs <- getSetting HostOs + tArch <- getSetting TargetArch + tOs <- getSetting TargetOs + version <- if stage == Stage0 + then lift $ ghcCanonVersion + else getSetting ProjectVersionInt + mconcat [ arg $ "--cc=" ++ ccPath + , arg $ "--ld=" ++ ccPath + , notWindowsHost ? arg "--cross-safe" + , append $ map ("-I" ++) gmpDirs + , append $ map ("--cflag=" ++) cFlags + , append $ map ("--lflag=" ++) lFlags + , notStage0 ? crossCompiling ? arg "--cross-compile" + , stage0 ? arg ("--cflag=-D" ++ hArch ++ "_HOST_ARCH=1") + , stage0 ? arg ("--cflag=-D" ++ hOs ++ "_HOST_OS=1" ) + , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") + , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) + , arg ("--cflag=-D__GLASGOW_HASKELL__=" ++ version) + , arg src + , arg "-o", arg file ] + +getCFlags :: Expr [String] +getCFlags = fromDiffExpr $ do + pkg <- getPackage + path <- getTargetPath + iDirs <- getPkgDataList IncludeDirs + dDirs <- getPkgDataList DepIncludeDirs + cppArgs <- getPkgDataList CppArgs + depCcArgs <- getPkgDataList DepCcArgs + mconcat [ ccArgs + , argStagedSettingList ConfCcArgs + , remove ["-O"] + , argStagedSettingList ConfCppArgs + , arg $ "-I" ++ path -/- "build/autogen" + , append [ "-I" ++ pkgPath pkg -/- dir | dir <- iDirs ++ dDirs ] + , append cppArgs + , append depCcArgs + , ccWarnings + , arg "-include", arg $ path -/- "build/autogen/cabal_macros.h" ] + +getLFlags :: Expr [String] +getLFlags = fromDiffExpr $ do + ldArgs <- getPkgDataList LdArgs + libDirs <- getPkgDataList DepLibDirs + extraLibs <- getPkgDataList DepExtraLibs + depLdArgs <- getPkgDataList DepLdArgs + mconcat [ argStagedSettingList ConfGccLinkerArgs + --, ldArgs -- TODO: resolve name conflict (ldArgs is currently empty) + , append ldArgs + , append $ [ "-L" ++ unifyPath dir | dir <- libDirs ] + , append $ [ "-l" ++ unifyPath dir | dir <- extraLibs ] + , append depLdArgs ] From git at git.haskell.org Fri Oct 27 00:07:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update limitations (acf3623) Message-ID: <20171027000708.B87643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acf362369999eacdd9d3c73abc83e0e607c315b5/ghc >--------------------------------------------------------------- commit acf362369999eacdd9d3c73abc83e0e607c315b5 Author: Andrey Mokhov Date: Thu Mar 10 11:57:53 2016 +0000 Update limitations See #219. [skip ci] >--------------------------------------------------------------- acf362369999eacdd9d3c73abc83e0e607c315b5 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 7317384..c61f5c6 100644 --- a/README.md +++ b/README.md @@ -105,6 +105,7 @@ The new build system still lacks many important features: * Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. +* There is no support for installation or binary/source distribution: [#219][install-issue]. Check out [milestones] to see when we hope to resolve the above limitations. @@ -144,6 +145,7 @@ helped me endure and enjoy the project. [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 +[install-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/219 [milestones]: https://github.com/snowleopard/shaking-up-ghc/milestones [comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 [doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 From git at git.haskell.org Fri Oct 27 00:07:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #150 from snowleopard/angerman-patch-1 (754ed41) Message-ID: <20171027000709.803513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/754ed41f02f404dc0b735df8f48e855a12f2248f/ghc >--------------------------------------------------------------- commit 754ed41f02f404dc0b735df8f48e855a12f2248f Merge: 24e6c28 55b0d41 Author: Andrey Mokhov Date: Mon Jan 11 03:31:50 2016 +0000 Merge pull request #150 from snowleopard/angerman-patch-1 Update Setting.hs >--------------------------------------------------------------- 754ed41f02f404dc0b735df8f48e855a12f2248f src/Oracles/Config/Setting.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 00:07:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more configuration flags. (b2928a3) Message-ID: <20171027000709.89B5B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2928a32abf293f02f4ebe8efe6349e6fb73bc4a/ghc >--------------------------------------------------------------- commit b2928a32abf293f02f4ebe8efe6349e6fb73bc4a Author: Andrey Mokhov Date: Mon Sep 21 00:55:17 2015 +0100 Add more configuration flags. >--------------------------------------------------------------- b2928a32abf293f02f4ebe8efe6349e6fb73bc4a cfg/system.config.in | 16 +++++++++++----- 1 file changed, 11 insertions(+), 5 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index b92b6ba..6bfb20d 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -5,14 +5,14 @@ #=================== system-ghc = @WithGhc@ -system-gcc = @CC_STAGE0@ -system-ghc-pkg = @GhcPkgCmd@ -gcc = @WhatGccIsCalled@ - ghc-stage1 = @hardtop@/inplace/bin/ghc-stage1 ghc-stage2 = @hardtop@/inplace/bin/ghc-stage2 ghc-stage3 = @hardtop@/inplace/bin/ghc-stage3 +system-gcc = @CC_STAGE0@ +gcc = @WhatGccIsCalled@ + +system-ghc-pkg = @GhcPkgCmd@ ghc-pkg = @hardtop@/inplace/bin/ghc-pkg ghc-cabal = @hardtop@/inplace/bin/ghc-cabal @@ -49,13 +49,19 @@ target-os = @TargetOS_CPP@ target-arch = @TargetArch_CPP@ target-platform-full = @TargetPlatformFull@ -host-os-cpp = @HostOS_CPP@ +host-os = @HostOS_CPP@ +host-arch = @HostArch_CPP@ cross-compiling = @CrossCompiling@ dynamic-extension = @soext_target@ +ghc-major-version = @GhcMajVersion@ +ghc-minor-version = @GhcMinVersion@ +ghc-patch-level = @GhcPatchLevel@ + project-version = @ProjectVersion@ +project-version-int = @ProjectVersionInt@ # Compilation and linking flags: #=============================== From git at git.haskell.org Fri Oct 27 00:07:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Experiment with a more efficient version of -/- in Settings.Paths (c50799d) Message-ID: <20171027000712.5BD2E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c50799d46b53afbde517be8ca1626ef37a626d8f/ghc >--------------------------------------------------------------- commit c50799d46b53afbde517be8ca1626ef37a626d8f Author: Andrey Mokhov Date: Thu Mar 10 12:34:51 2016 +0000 Experiment with a more efficient version of -/- in Settings.Paths See #218. >--------------------------------------------------------------- c50799d46b53afbde517be8ca1626ef37a626d8f src/Settings/Paths.hs | 21 +++++++++++++-------- 1 file changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 62a5c57..678ed92 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -11,20 +11,25 @@ import GHC import Oracles.PackageData import Settings.User +-- A more efficient version of '-/-' which assumes that given FilePaths have +-- already been unified. See #218. TODO: Switch to 'newtype FilePath'. +(~/~) :: FilePath -> FilePath -> FilePath +x ~/~ y = x ++ '/' : y + -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath buildPath context at Context {..} = - buildRootPath -/- contextDirectory context -/- pkgPath package + buildRootPath ~/~ contextDirectory context ~/~ pkgPath package -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath -pkgDataFile context = buildPath context -/- "package-data.mk" +pkgDataFile context = buildPath context ~/~ "package-data.mk" -- | Path to the haddock file of a given 'Context', e.g.: -- ".build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = - buildPath context -/- "doc/html" -/- name -/- name <.> "haddock" + buildPath context ~/~ "doc/html" ~/~ name ~/~ name <.> "haddock" where name = pkgNameString package -- | Path to the library file of a given 'Context', e.g.: @@ -50,25 +55,25 @@ pkgFile :: Context -> String -> String -> Action FilePath pkgFile context prefix suffix = do let path = buildPath context componentId <- pkgData $ ComponentId path - return $ path -/- prefix ++ componentId ++ suffix + return $ path ~/~ prefix ++ componentId ++ suffix -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage1/gmp" +gmpBuildPath = buildRootPath ~/~ "stage1/gmp" -- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath -gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" +gmpBuildInfoPath = pkgPath integerGmp ~/~ "integer-gmp.buildinfo" -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory -- | Path to package database directory of a given 'Stage'. packageDbDirectory :: Stage -> FilePath -packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" +packageDbDirectory Stage0 = buildRootPath ~/~ "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" -- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do componentId <- pkgData . ComponentId $ buildPath context - return $ packageDbDirectory stage -/- componentId <.> "conf" + return $ packageDbDirectory stage ~/~ componentId <.> "conf" From git at git.haskell.org Fri Oct 27 00:07:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on dead/duplicated code. (e68f4ed) Message-ID: <20171027000713.5B2763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e68f4ed4d3fbba7228a5eb9c9419ec00ca93c8f5/ghc >--------------------------------------------------------------- commit e68f4ed4d3fbba7228a5eb9c9419ec00ca93c8f5 Author: Andrey Mokhov Date: Mon Sep 21 00:56:55 2015 +0100 Add a note on dead/duplicated code. >--------------------------------------------------------------- e68f4ed4d3fbba7228a5eb9c9419ec00ca93c8f5 doc/demo.txt | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/doc/demo.txt b/doc/demo.txt index 28b3689..2c8bf75 100644 --- a/doc/demo.txt +++ b/doc/demo.txt @@ -13,7 +13,9 @@ * https://mail.haskell.org/pipermail/ghc-commits/2013-May/001712.html * see ghc.mk, comment about parallel ghc-pkg invokations -5. Discovered dead code in the old build system, e.g: +5. Discovered dead & duplicated code in the old build system, e.g: -* Alex3 variable not needed as Alex 3.1 is required. -* There are no generated *.y/*.ly files, hence they can never be in the build directory. \ No newline at end of file +* Alex3 variable not needed as Alex 3.1 is required +* There are no generated *.y/*.ly files, hence they can never be in the build directory +* hsc2hs gets multuple "--cflag=-I$1/$2/build/autogen" flags in one invokation +* No generated Haskell files actually require copying of *.(l)hs-boot files \ No newline at end of file From git at git.haskell.org Fri Oct 27 00:07:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, add a Test module with selftest (28c706d) Message-ID: <20171027000713.6FED13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28c706da832e79687af29b9d64289d6a57b53adf/ghc >--------------------------------------------------------------- commit 28c706da832e79687af29b9d64289d6a57b53adf Author: Neil Mitchell Date: Mon Jan 11 10:47:41 2016 +0000 #146, add a Test module with selftest >--------------------------------------------------------------- 28c706da832e79687af29b9d64289d6a57b53adf shaking-up-ghc.cabal | 3 +++ src/Main.hs | 4 +++- src/Test.hs | 19 +++++++++++++++++++ src/Way.hs | 2 +- 4 files changed, 26 insertions(+), 2 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index a091020..132e84d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -100,6 +100,7 @@ executable ghc-shake , Settings.Ways , Stage , Target + , Test , Way default-extensions: BangPatterns @@ -111,6 +112,7 @@ executable ghc-shake , FlexibleInstances , OverloadedStrings , RecordWildCards + , ScopedTypeVariables build-depends: base , ansi-terminal >= 0.6 , Cabal >= 1.22 @@ -118,6 +120,7 @@ executable ghc-shake , directory >= 1.2 , extra >= 1.4 , mtl >= 2.2 + , QuickCheck >= 2.6 , shake >= 0.15 , transformers >= 0.4 , unordered-containers >= 0.2 diff --git a/src/Main.hs b/src/Main.hs index 63dbd7c..dea793e 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -11,6 +11,7 @@ import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl +import qualified Test main :: IO () main = shakeArgs options rules @@ -25,7 +26,8 @@ main = shakeArgs options rules , Rules.Gmp.gmpRules , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules - , Rules.packageRules ] + , Rules.packageRules + , Test.testRules ] options = shakeOptions { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple diff --git a/src/Test.hs b/src/Test.hs new file mode 100644 index 0000000..75b1b5d --- /dev/null +++ b/src/Test.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE ScopedTypeVariables #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} + +module Test (testRules) where + +import Way +import Development.Shake +import Test.QuickCheck + +instance Arbitrary Way where + arbitrary = wayFromUnits <$> arbitrary + +instance Arbitrary WayUnit where + arbitrary = arbitraryBoundedEnum + +testRules :: Rules () +testRules = + phony "selftest" $ do + liftIO $ quickCheck $ \(x :: Way) -> read (show x) == x diff --git a/src/Way.hs b/src/Way.hs index 3b1f6c0..ba20bd7 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,5 +1,5 @@ module Way ( - WayUnit (..), Way, wayUnit, + WayUnit (..), Way, wayUnit, wayFromUnits, vanilla, profiling, logging, parallel, granSim, threaded, threadedProfiling, threadedLogging, From git at git.haskell.org Fri Oct 27 00:07:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of git://github.com/snowleopard/shaking-up-ghc (950ac6b) Message-ID: <20171027000715.C29EF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/950ac6b7dc479aebfc367db3c459130cb71668e0/ghc >--------------------------------------------------------------- commit 950ac6b7dc479aebfc367db3c459130cb71668e0 Merge: c50799d acf3623 Author: Andrey Mokhov Date: Thu Mar 10 12:37:03 2016 +0000 Merge branch 'master' of git://github.com/snowleopard/shaking-up-ghc >--------------------------------------------------------------- 950ac6b7dc479aebfc367db3c459130cb71668e0 README.md | 2 ++ 1 file changed, 2 insertions(+) From git at git.haskell.org Fri Oct 27 00:07:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for empty YES/NO flags (treat empty as NO). (8b1feb5) Message-ID: <20171027000716.D16173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8b1feb5b13fc1c9848f2f0e39f271e5c1fb39c27/ghc >--------------------------------------------------------------- commit 8b1feb5b13fc1c9848f2f0e39f271e5c1fb39c27 Author: Andrey Mokhov Date: Mon Sep 21 00:57:40 2015 +0100 Add support for empty YES/NO flags (treat empty as NO). >--------------------------------------------------------------- 8b1feb5b13fc1c9848f2f0e39f271e5c1fb39c27 src/Oracles/Config/Flag.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index b73a687..d520a85 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -16,6 +16,8 @@ data Flag = CrossCompiling | SplitObjectsBroken | SupportsPackageKey +-- Note, if a flag is set to empty string we treat it as set to NO. This seems +-- fragile, but some flags do behave like this, e.g. GccIsClang. flag :: Flag -> Action Bool flag f = do key <- return $ case f of @@ -28,7 +30,7 @@ flag f = do SupportsPackageKey -> "supports-package-key" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." - unless (value == "YES" || value == "NO") . putError + unless (value == "YES" || value == "NO" || value == "") . putError $ "\nFlag '" ++ key ++ "' is set to '" ++ value ++ "' instead of 'YES' or 'NO'." return $ value == "YES" From git at git.haskell.org Fri Oct 27 00:07:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, run the tests on Appveyor (70b40d9) Message-ID: <20171027000716.EC89D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/70b40d9e1ca12be3a3d7de28ee2e5ef8dcf7120c/ghc >--------------------------------------------------------------- commit 70b40d9e1ca12be3a3d7de28ee2e5ef8dcf7120c Author: Neil Mitchell Date: Mon Jan 11 10:47:49 2016 +0000 #146, run the tests on Appveyor >--------------------------------------------------------------- 70b40d9e1ca12be3a3d7de28ee2e5ef8dcf7120c .appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.appveyor.yml b/.appveyor.yml index f4f1d83..f0d0e69 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,4 +30,5 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build + - echo "" | stack --no-terminal exec -- build.bat selftest - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:07:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -threaded to ghc options. (bf60359) Message-ID: <20171027000719.6226A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf60359360e91bf41773efbd7facdfda3b399c7c/ghc >--------------------------------------------------------------- commit bf60359360e91bf41773efbd7facdfda3b399c7c Author: Andrey Mokhov Date: Mon Apr 11 00:27:21 2016 +0100 Add -threaded to ghc options. >--------------------------------------------------------------- bf60359360e91bf41773efbd7facdfda3b399c7c build.bat | 1 + build.sh | 1 + shaking-up-ghc.cabal | 5 ++++- 3 files changed, 6 insertions(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 465d957..2f6d4cd 100644 --- a/build.bat +++ b/build.bat @@ -6,6 +6,7 @@ -fno-warn-name-shadowing ^ -XRecordWildCards ^ src/Main.hs ^ + -threaded ^ -isrc ^ -rtsopts ^ -with-rtsopts=-I0 ^ diff --git a/build.sh b/build.sh index 7c070e9..95de2e6 100755 --- a/build.sh +++ b/build.sh @@ -40,6 +40,7 @@ ghc \ -i"$root/src" \ -rtsopts \ -with-rtsopts=-I0 \ + -threaded \ -outputdir="$root/.shake" \ -j -O \ -o "$root/.shake/build" diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index fc0744d..8ef820f 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -127,4 +127,7 @@ executable ghc-shake , shake == 0.15.* , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* - ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 + ghc-options: -Wall + -fno-warn-name-shadowing + -rtsopts -with-rtsopts=-I0 + -threaded From git at git.haskell.org Fri Oct 27 00:07:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for Alex, Happy and Hsc2Hs builders. (1e13a6e) Message-ID: <20171027000720.D4F193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1e13a6e1021c8354a86af9ea4cba7e3c2ce1bc65/ghc >--------------------------------------------------------------- commit 1e13a6e1021c8354a86af9ea4cba7e3c2ce1bc65 Author: Andrey Mokhov Date: Mon Sep 21 00:58:19 2015 +0100 Add support for Alex, Happy and Hsc2Hs builders. >--------------------------------------------------------------- 1e13a6e1021c8354a86af9ea4cba7e3c2ce1bc65 src/Rules/Actions.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 4285831..f261b4f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -39,15 +39,18 @@ build = buildWithResources [] interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of + Alex -> prefixAndSuffix 0 3 ss Ar -> prefixAndSuffix 2 1 ss - Ld -> prefixAndSuffix 4 0 ss Gcc _ -> prefixAndSuffix 0 4 ss GccM _ -> prefixAndSuffix 0 1 ss Ghc _ -> prefixAndSuffix 0 4 ss + GhcCabal -> prefixAndSuffix 3 0 ss GhcM _ -> prefixAndSuffix 1 1 ss GhcPkg _ -> prefixAndSuffix 3 0 ss Haddock -> prefixAndSuffix 1 0 ss - GhcCabal -> prefixAndSuffix 3 0 ss + Happy -> prefixAndSuffix 0 3 ss + Hsc2Hs -> prefixAndSuffix 0 3 ss + Ld -> prefixAndSuffix 4 0 ss _ -> ss where prefixAndSuffix n m list = From git at git.haskell.org Fri Oct 27 00:07:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rewrite chunksOfSize so it doesn't go pear shaped on long inputs (763a518) Message-ID: <20171027000721.01FBB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/763a518c64ec88acc29db8cc2f7b17955b02a6df/ghc >--------------------------------------------------------------- commit 763a518c64ec88acc29db8cc2f7b17955b02a6df Author: Neil Mitchell Date: Mon Jan 11 11:06:18 2016 +0000 Rewrite chunksOfSize so it doesn't go pear shaped on long inputs >--------------------------------------------------------------- 763a518c64ec88acc29db8cc2f7b17955b02a6df src/Settings/Builders/Ar.hs | 12 ++---------- 1 file changed, 2 insertions(+), 10 deletions(-) diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 86f4310..fc43d45 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -48,13 +48,5 @@ useSuccessiveInvocations path flagArgs fileArgs = do -- | @chunksOfSize size strings@ splits a given list of strings into chunks not -- exceeding the given @size at . chunksOfSize :: Int -> [String] -> [[String]] -chunksOfSize _ [] = [] -chunksOfSize size strings = reverse chunk : chunksOfSize size rest - where - (chunk, rest) = go [] 0 strings - go res _ [] = (res, []) - go res chunkSize (s:ss) = - if newSize > size then (res, s:ss) else go (s:res) newSize ss - where - newSize = chunkSize + length s - +chunksOfSize n = repeatedly f + where f xs = splitAt (max 1 $ length $ takeWhile (<= n) $ scanl1 (+) $ map length xs) xs From git at git.haskell.org Fri Oct 27 00:07:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install alex and happy using cabal to fix Travis failure (67e3104) Message-ID: <20171027000722.E313D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/67e31045fb749fdcb4cb67248931e5ce403e012b/ghc >--------------------------------------------------------------- commit 67e31045fb749fdcb4cb67248931e5ce403e012b Author: Andrey Mokhov Date: Mon Apr 11 00:43:59 2016 +0100 Install alex and happy using cabal to fix Travis failure >--------------------------------------------------------------- 67e31045fb749fdcb4cb67248931e5ce403e012b .travis.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 9547914..21bf769 100644 --- a/.travis.yml +++ b/.travis.yml @@ -8,8 +8,6 @@ matrix: apt: packages: - ghc-7.10.3 - - alex-3.1.4 - - happy-1.19.5 - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc @@ -19,6 +17,7 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH - cabal update + - cabal install alex happy - os: osx env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg From git at git.haskell.org Fri Oct 27 00:07:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add hsc2HsArgs to global settings. (330dcdb) Message-ID: <20171027000724.ECD3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/330dcdbf2b5f84e658fbbe4c540492c7b03c6951/ghc >--------------------------------------------------------------- commit 330dcdbf2b5f84e658fbbe4c540492c7b03c6951 Author: Andrey Mokhov Date: Mon Sep 21 00:58:57 2015 +0100 Add hsc2HsArgs to global settings. >--------------------------------------------------------------- 330dcdbf2b5f84e658fbbe4c540492c7b03c6951 src/Settings/Args.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 2e2f379..97933fa 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -9,6 +9,7 @@ import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg import Settings.Builders.Haddock import Settings.Builders.Happy +import Settings.Builders.Hsc2Hs import Settings.Builders.Ld import Settings.User @@ -37,4 +38,5 @@ defaultArgs = mconcat , gccMArgs , haddockArgs , happyArgs + , hsc2HsArgs , ldArgs ] From git at git.haskell.org Fri Oct 27 00:07:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, add a test helper (077bf47) Message-ID: <20171027000725.138353A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/077bf477e5059ccbff621ea59a439830890b8f1c/ghc >--------------------------------------------------------------- commit 077bf477e5059ccbff621ea59a439830890b8f1c Author: Neil Mitchell Date: Mon Jan 11 11:06:40 2016 +0000 #146, add a test helper >--------------------------------------------------------------- 077bf477e5059ccbff621ea59a439830890b8f1c src/Test.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Test.hs b/src/Test.hs index 75b1b5d..a55e6e6 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -16,4 +16,8 @@ instance Arbitrary WayUnit where testRules :: Rules () testRules = phony "selftest" $ do - liftIO $ quickCheck $ \(x :: Way) -> read (show x) == x + test $ \(x :: Way) -> read (show x) == x + + +test :: Testable a => a -> Action () +test = liftIO . quickCheck From git at git.haskell.org Fri Oct 27 00:07:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass conf-cc-args-stageN to Gcc builder. (0e27bf4) Message-ID: <20171027000726.6E35F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0e27bf4172aa629796af44dfe3642967eace1dba/ghc >--------------------------------------------------------------- commit 0e27bf4172aa629796af44dfe3642967eace1dba Author: Andrey Mokhov Date: Mon Apr 11 23:18:19 2016 +0100 Pass conf-cc-args-stageN to Gcc builder. See #221. >--------------------------------------------------------------- 0e27bf4172aa629796af44dfe3642967eace1dba src/Settings/Builders/Gcc.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index 4902ea3..7c237da 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -2,6 +2,7 @@ module Settings.Builders.Gcc (gccBuilderArgs, gccMBuilderArgs) where import Development.Shake.FilePath import Expression +import Oracles.Config.Setting import Oracles.PackageData import Predicates (stagedBuilder) import Settings @@ -30,4 +31,5 @@ gccMBuilderArgs = stagedBuilder GccM ? do commonGccArgs :: Args commonGccArgs = mconcat [ append =<< getPkgDataList CcArgs + , append =<< getSettingList . ConfCcArgs =<< getStage , cIncludeArgs ] From git at git.haskell.org Fri Oct 27 00:07:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify paths of sources and files in a target. (00de798) Message-ID: <20171027000728.B9ED23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/00de798905ba76aaa6f034b0b7110fe1c4be3acb/ghc >--------------------------------------------------------------- commit 00de798905ba76aaa6f034b0b7110fe1c4be3acb Author: Andrey Mokhov Date: Mon Sep 21 00:59:34 2015 +0100 Unify paths of sources and files in a target. >--------------------------------------------------------------- 00de798905ba76aaa6f034b0b7110fe1c4be3acb src/Target.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Target.hs b/src/Target.hs index 2901ffe..8e2a44e 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -60,8 +60,8 @@ fullTarget (PartialTarget s p) b srcs fs = Target package = p, builder = b, way = vanilla, - sources = srcs, - files = fs + sources = map unifyPath srcs, + files = map unifyPath fs } -- Use this function to be explicit about the build way. From git at git.haskell.org Fri Oct 27 00:07:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, add tests for chunksOfSize (d001140) Message-ID: <20171027000728.CC02F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d001140948a06ae50475eb919010d192e37b3829/ghc >--------------------------------------------------------------- commit d001140948a06ae50475eb919010d192e37b3829 Author: Neil Mitchell Date: Mon Jan 11 11:06:54 2016 +0000 #146, add tests for chunksOfSize >--------------------------------------------------------------- d001140948a06ae50475eb919010d192e37b3829 src/Settings/Builders/Ar.hs | 2 +- src/Test.hs | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index fc43d45..8cf175f 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,4 +1,4 @@ -module Settings.Builders.Ar (arBuilderArgs, arCmd) where +module Settings.Builders.Ar (arBuilderArgs, arCmd, chunksOfSize) where import Base import Expression diff --git a/src/Test.hs b/src/Test.hs index a55e6e6..6cbc557 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -6,6 +6,7 @@ module Test (testRules) where import Way import Development.Shake import Test.QuickCheck +import Settings.Builders.Ar(chunksOfSize) instance Arbitrary Way where arbitrary = wayFromUnits <$> arbitrary @@ -17,6 +18,10 @@ testRules :: Rules () testRules = phony "selftest" $ do test $ \(x :: Way) -> read (show x) == x + test $ \n xs -> + let res = chunksOfSize n xs + in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res + test $ chunksOfSize 3 ["a","b","c","defg","hi","jk"] == [["a","b","c"],["defg"],["hi"],["jk"]] test :: Testable a => a -> Action () From git at git.haskell.org Fri Oct 27 00:07:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor tweaks (5b49f64) Message-ID: <20171027000729.E93023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b49f649a2f4b9a4fcb0ea6a46f5a40480ee0375/ghc >--------------------------------------------------------------- commit 5b49f649a2f4b9a4fcb0ea6a46f5a40480ee0375 Author: Andrey Mokhov Date: Tue Apr 12 01:04:31 2016 +0100 Minor tweaks >--------------------------------------------------------------- 5b49f649a2f4b9a4fcb0ea6a46f5a40480ee0375 src/Predicates.hs | 4 +--- src/Settings/Builders/Common.hs | 6 +++--- src/Settings/Builders/GhcCabal.hs | 2 +- 3 files changed, 5 insertions(+), 7 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index c0f6095..1c5ce38 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -21,9 +21,7 @@ builder b = (b ==) <$> getBuilder -- | Is a certain builder used in the current stage? stagedBuilder :: (Stage -> Builder) -> Predicate -stagedBuilder stageBuilder = do - s <- getStage - builder (stageBuilder s) +stagedBuilder stageBuilder = builder . stageBuilder =<< getStage -- | Are we building with GCC? builderGcc :: Predicate diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 4ecf1d4..1f1d33b 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -51,10 +51,10 @@ argSetting :: Setting -> Args argSetting = argM . setting argSettingList :: SettingList -> Args -argSettingList = (append =<<) . lift . settingList +argSettingList = (append =<<) . getSettingList argStagedSettingList :: (Stage -> SettingList) -> Args -argStagedSettingList ss = (argSettingList . ss) =<< getStage +argStagedSettingList ss = argSettingList . ss =<< getStage argStagedBuilderPath :: (Stage -> Builder) -> Args -argStagedBuilderPath sb = (argM . builderPath . sb) =<< getStage +argStagedBuilderPath sb = argM . builderPath . sb =<< getStage diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index be89546..24b7d7d 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -131,7 +131,7 @@ with b = specified b ? do append [withBuilderKey b ++ top -/- path] withStaged :: (Stage -> Builder) -> Args -withStaged sb = (with . sb) =<< getStage +withStaged sb = with . sb =<< getStage needDll0 :: Stage -> Package -> Action Bool needDll0 stage pkg = do From git at git.haskell.org Fri Oct 27 00:07:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update the docs for chunksOfSize (916d5a9) Message-ID: <20171027000732.D3B663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/916d5a93c7dba53c730e49e00a0c0656e75e602b/ghc >--------------------------------------------------------------- commit 916d5a93c7dba53c730e49e00a0c0656e75e602b Author: Neil Mitchell Date: Mon Jan 11 11:14:12 2016 +0000 Update the docs for chunksOfSize >--------------------------------------------------------------- 916d5a93c7dba53c730e49e00a0c0656e75e602b src/Settings/Builders/Ar.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 8cf175f..59b70b8 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -46,7 +46,7 @@ useSuccessiveInvocations path flagArgs fileArgs = do unit . cmd [path] $ flagArgs ++ argsChunk -- | @chunksOfSize size strings@ splits a given list of strings into chunks not --- exceeding the given @size at . +-- exceeding the given @size at . If that is impossible, it uses singleton chunks. chunksOfSize :: Int -> [String] -> [[String]] chunksOfSize n = repeatedly f where f xs = splitAt (max 1 $ length $ takeWhile (<= n) $ scanl1 (+) $ map length xs) xs From git at git.haskell.org Fri Oct 27 00:07:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (738bac8) Message-ID: <20171027000732.DE3B83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/738bac8ccaa266a76a1a21ccb1ff1f8cbe785a70/ghc >--------------------------------------------------------------- commit 738bac8ccaa266a76a1a21ccb1ff1f8cbe785a70 Author: Andrey Mokhov Date: Mon Sep 21 01:00:48 2015 +0100 Clean up. >--------------------------------------------------------------- 738bac8ccaa266a76a1a21ccb1ff1f8cbe785a70 src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 10 ++++++++-- src/Settings/Builders/Happy.hs | 2 +- 3 files changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs index 6aedcdb..1e0f87b 100644 --- a/src/Settings/Builders/Alex.hs +++ b/src/Settings/Builders/Alex.hs @@ -6,8 +6,8 @@ import Predicates (builder, package) alexArgs :: Args alexArgs = builder Alex ? do - file <- getFile src <- getSource + file <- getFile mconcat [ arg "-g" , package compiler ? arg "--latin1" , arg src diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index dd54097..ab65a51 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,5 +1,6 @@ module Settings.Builders.GhcCabal ( - cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs + cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, + ccArgs, ccWarnings, argStagedSettingList ) where import Expression @@ -54,6 +55,7 @@ libraryArgs = do then "--enable-shared" else "--disable-shared" ] +-- TODO: LD_OPTS? configureArgs :: Args configureArgs = do let conf key = appendSubD $ "--configure-option=" ++ key @@ -94,7 +96,11 @@ packageConstraints = stage0 ? do -- TODO: should be in a different file -- TODO: put all validating options together in one file ccArgs :: Args -ccArgs = validating ? do +ccArgs = validating ? ccWarnings + +-- TODO: should be in a different file +ccWarnings :: Args +ccWarnings = do let notClang = fmap not gccIsClang mconcat [ arg "-Werror" , arg "-Wall" diff --git a/src/Settings/Builders/Happy.hs b/src/Settings/Builders/Happy.hs index fcd962a..685c30d 100644 --- a/src/Settings/Builders/Happy.hs +++ b/src/Settings/Builders/Happy.hs @@ -5,8 +5,8 @@ import Predicates (builder) happyArgs :: Args happyArgs = builder Happy ? do - file <- getFile src <- getSource + file <- getFile mconcat [ arg "-agc" , arg "--strict" , arg src From git at git.haskell.org Fri Oct 27 00:07:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't add exe extension to builder paths on Windows. (e23dab7) Message-ID: <20171027000733.9349A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e23dab7cab22ecd9ba7f69ba735c43878a7b6c3a/ghc >--------------------------------------------------------------- commit e23dab7cab22ecd9ba7f69ba735c43878a7b6c3a Author: Andrey Mokhov Date: Tue Apr 12 18:45:50 2016 +0100 Don't add exe extension to builder paths on Windows. See #221, #222. >--------------------------------------------------------------- e23dab7cab22ecd9ba7f69ba735c43878a7b6c3a src/Builder.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index e8011e7..a0cc093 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -133,9 +133,7 @@ builderPath builder = case builderProvenance builder of then return "" else putError $ "Builder '" ++ builderKey ++ "' is not specified in" ++ " system.config file. Cannot proceed without it." - else do - path' <- lookupInPath path - fixAbsolutePathOnWindows $ path' -<.> exe + else fixAbsolutePathOnWindows =<< lookupInPath path getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath From git at git.haskell.org Fri Oct 27 00:07:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #151, add a call to selftest (c5cb061) Message-ID: <20171027000736.B68623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5cb0617314c3b6fcb201246a76b6a02cb93350f/ghc >--------------------------------------------------------------- commit c5cb0617314c3b6fcb201246a76b6a02cb93350f Author: Neil Mitchell Date: Mon Jan 11 11:39:47 2016 +0000 #151, add a call to selftest >--------------------------------------------------------------- c5cb0617314c3b6fcb201246a76b6a02cb93350f .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index dd3bd12..0dc23c1 100644 --- a/.travis.yml +++ b/.travis.yml @@ -62,6 +62,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) + - ./ghc/shake-build/build.sh selftest - ./ghc/shake-build/build.sh -j --no-progress $TARGET cache: From git at git.haskell.org Fri Oct 27 00:07:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track generated sources. (44f7b51) Message-ID: <20171027000736.C96FE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44f7b51095e7d4c151eef50c6f6180b27efa4aa1/ghc >--------------------------------------------------------------- commit 44f7b51095e7d4c151eef50c6f6180b27efa4aa1 Author: Andrey Mokhov Date: Mon Sep 21 01:01:13 2015 +0100 Track generated sources. >--------------------------------------------------------------- 44f7b51095e7d4c151eef50c6f6180b27efa4aa1 src/Rules/Compile.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 3940d64..90712ce 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -19,7 +19,7 @@ compilePackage _ target @ (PartialTarget stage package) = do matchBuildResult buildPath "o" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need deps + need $ src : deps if ("//*.c" ?== src) then build $ fullTarget target (Gcc stage) [src] [obj] else do @@ -28,6 +28,6 @@ compilePackage _ target @ (PartialTarget stage package) = do matchBuildResult buildPath "o-boot" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need deps + need $ src : deps let way = detectWay obj build $ fullTargetWithWay target (Ghc stage) way [src] [obj] From git at git.haskell.org Fri Oct 27 00:07:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Gcc(M) to Cc(M). (96dec14) Message-ID: <20171027000737.68CB43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/96dec1490c1a95e7e5a4c58f736e617773ff9d32/ghc >--------------------------------------------------------------- commit 96dec1490c1a95e7e5a4c58f736e617773ff9d32 Author: Andrey Mokhov Date: Thu Apr 14 01:41:02 2016 +0100 Rename Gcc(M) to Cc(M). See #222, #223. >--------------------------------------------------------------- 96dec1490c1a95e7e5a4c58f736e617773ff9d32 cfg/system.config.in | 4 +-- shaking-up-ghc.cabal | 2 +- src/Builder.hs | 62 ++++++++++++++++---------------- src/Predicates.hs | 6 ++-- src/Rules/Compile.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 +-- src/Settings/Args.hs | 6 ++-- src/Settings/Builders/{Gcc.hs => Cc.hs} | 22 ++++++------ src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 8 ++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Directory.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 4 +-- src/Settings/Packages/Rts.hs | 4 +-- 16 files changed, 67 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 96dec1490c1a95e7e5a4c58f736e617773ff9d32 From git at git.haskell.org Fri Oct 27 00:07:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #151 from ndmitchell/master (5f80d4f) Message-ID: <20171027000740.8611F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f80d4f2a5269a8546a5040edbd26502fab7bc26/ghc >--------------------------------------------------------------- commit 5f80d4f2a5269a8546a5040edbd26502fab7bc26 Merge: 754ed41 c5cb061 Author: Andrey Mokhov Date: Mon Jan 11 14:29:39 2016 +0000 Merge pull request #151 from ndmitchell/master Add tests >--------------------------------------------------------------- 5f80d4f2a5269a8546a5040edbd26502fab7bc26 .appveyor.yml | 1 + .travis.yml | 1 + shaking-up-ghc.cabal | 3 +++ src/Main.hs | 4 +++- src/Settings/Builders/Ar.hs | 16 ++++------------ src/Test.hs | 28 ++++++++++++++++++++++++++++ src/Way.hs | 2 +- 7 files changed, 41 insertions(+), 14 deletions(-) From git at git.haskell.org Fri Oct 27 00:07:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for new keys in package-data files. (13708d7) Message-ID: <20171027000740.8001F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13708d7313bb91ea60e4129d2e6b0f2bcec4ad8e/ghc >--------------------------------------------------------------- commit 13708d7313bb91ea60e4129d2e6b0f2bcec4ad8e Author: Andrey Mokhov Date: Mon Sep 21 01:01:59 2015 +0100 Add support for new keys in package-data files. >--------------------------------------------------------------- 13708d7313bb91ea60e4129d2e6b0f2bcec4ad8e src/Oracles/PackageData.hs | 58 +++++++++++++++++++++++++++------------------- 1 file changed, 34 insertions(+), 24 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index e3c1eb5..22031b1 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -15,24 +15,29 @@ import qualified Data.HashMap.Strict as Map -- PackageDataList is used for multiple string options separated by spaces, -- such as 'path_MODULES = Data.Array Data.Array.Base ...'. -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] -data PackageData = Version FilePath - | PackageKey FilePath +data PackageData = BuildGhciLib FilePath | LibName FilePath + | PackageKey FilePath | Synopsis FilePath - | BuildGhciLib FilePath + | Version FilePath -data PackageDataList = Modules FilePath - | HiddenModules FilePath - | SrcDirs FilePath - | IncludeDirs FilePath - | Deps FilePath +data PackageDataList = CcArgs FilePath + | CSrcs FilePath + | CppArgs FilePath + | DepCcArgs FilePath + | DepExtraLibs FilePath | DepIds FilePath + | DepIncludeDirs FilePath + | DepLdArgs FilePath + | DepLibDirs FilePath | DepNames FilePath - | CppArgs FilePath + | Deps FilePath + | HiddenModules FilePath | HsArgs FilePath - | CcArgs FilePath - | CSrcs FilePath - | DepIncludeDirs FilePath + | IncludeDirs FilePath + | LdArgs FilePath + | Modules FilePath + | SrcDirs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -48,26 +53,31 @@ askPackageData path key = do pkgData :: PackageData -> Action String pkgData packageData = case packageData of - Version path -> askPackageData path "VERSION" - PackageKey path -> askPackageData path "PACKAGE_KEY" + BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" LibName path -> askPackageData path "LIB_NAME" + PackageKey path -> askPackageData path "PACKAGE_KEY" Synopsis path -> askPackageData path "SYNOPSIS" - BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" + Version path -> askPackageData path "VERSION" pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = fmap (map unquote . words) $ case packageData of - Modules path -> askPackageData path "MODULES" - HiddenModules path -> askPackageData path "HIDDEN_MODULES" - SrcDirs path -> askPackageData path "HS_SRC_DIRS" - IncludeDirs path -> askPackageData path "INCLUDE_DIRS" - Deps path -> askPackageData path "DEPS" - DepIds path -> askPackageData path "DEP_IPIDS" - DepNames path -> askPackageData path "DEP_NAMES" - CppArgs path -> askPackageData path "CPP_OPTS" - HsArgs path -> askPackageData path "HC_OPTS" CcArgs path -> askPackageData path "CC_OPTS" CSrcs path -> askPackageData path "C_SRCS" + CppArgs path -> askPackageData path "CPP_OPTS" + DepCcArgs path -> askPackageData path "DEP_CC_OPTS" + DepExtraLibs path -> askPackageData path "DEP_EXTRA_LIBS" + DepIds path -> askPackageData path "DEP_IPIDS" DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" + DepLibDirs path -> askPackageData path "DEP_LIB_DIRS_SINGLE_QUOTED" + DepLdArgs path -> askPackageData path "DEP_LD_OPTS" + DepNames path -> askPackageData path "DEP_NAMES" + Deps path -> askPackageData path "DEPS" + HiddenModules path -> askPackageData path "HIDDEN_MODULES" + HsArgs path -> askPackageData path "HC_OPTS" + IncludeDirs path -> askPackageData path "INCLUDE_DIRS" + LdArgs path -> askPackageData path "LD_OPTS" + Modules path -> askPackageData path "MODULES" + SrcDirs path -> askPackageData path "HS_SRC_DIRS" where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') From git at git.haskell.org Fri Oct 27 00:07:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CompilerMode to Cc and Ghc builders. (897ba61) Message-ID: <20171027000741.4EE183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/897ba61daec64836092aa46fe097743013cd7bc5/ghc >--------------------------------------------------------------- commit 897ba61daec64836092aa46fe097743013cd7bc5 Author: Andrey Mokhov Date: Fri Apr 15 02:23:37 2016 +0100 Add CompilerMode to Cc and Ghc builders. See #223. >--------------------------------------------------------------- 897ba61daec64836092aa46fe097743013cd7bc5 src/Builder.hs | 80 ++++++++++++++++---------------- src/Predicates.hs | 13 ++++-- src/Rules/Compile.hs | 10 ++-- src/Rules/Dependencies.hs | 5 +- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 +- src/Rules/Program.hs | 3 +- src/Rules/Test.hs | 4 +- src/Settings/Args.hs | 1 - src/Settings/Builders/Cc.hs | 38 +++++++-------- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/Ghc.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 10 ++-- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Directory.hs | 4 +- 15 files changed, 95 insertions(+), 87 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 897ba61daec64836092aa46fe097743013cd7bc5 From git at git.haskell.org Fri Oct 27 00:07:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use shallow git clone. (0c3a659) Message-ID: <20171027000744.2AA673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c3a65984127a8e17cde5cec4257ed8b023487db/ghc >--------------------------------------------------------------- commit 0c3a65984127a8e17cde5cec4257ed8b023487db Author: Andrey Mokhov Date: Mon Jan 11 14:48:30 2016 +0000 Use shallow git clone. See #110. [skip ci] >--------------------------------------------------------------- 0c3a65984127a8e17cde5cec4257ed8b023487db .appveyor.yml | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f0d0e69..68c1fd8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -16,7 +16,14 @@ install: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp + + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ + - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ + - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ + - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ + - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot From git at git.haskell.org Fri Oct 27 00:07:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for new configuration flags. (8e74ca7) Message-ID: <20171027000744.7515A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e74ca7b158cb0a3fd7413b1b6646fa2cdbcb1a7/ghc >--------------------------------------------------------------- commit 8e74ca7b158cb0a3fd7413b1b6646fa2cdbcb1a7 Author: Andrey Mokhov Date: Mon Sep 21 01:02:39 2015 +0100 Add support for new configuration flags. >--------------------------------------------------------------- 8e74ca7b158cb0a3fd7413b1b6646fa2cdbcb1a7 src/Oracles/Config/Setting.hs | 55 ++++++++++++++++++++++++++++--------------- 1 file changed, 36 insertions(+), 19 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index f0f7fb7..a01a7fa 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -3,7 +3,7 @@ module Oracles.Config.Setting ( setting, settingList, getSetting, getSettingList, targetPlatform, targetPlatforms, targetOs, targetOss, notTargetOs, targetArchs, windowsHost, notWindowsHost, ghcWithInterpreter, - ghcEnableTablesNextToCode, cmdLineLengthLimit + ghcEnableTablesNextToCode, ghcCanonVersion, cmdLineLengthLimit ) where import Base @@ -16,32 +16,42 @@ import Stage -- SettingList is used for multiple string values separated by spaces, such -- as 'gmp-include-dirs = a b'. -- settingList GmpIncludeDirs therefore returns a list of strings ["a", "b"]. -data Setting = TargetOs +data Setting = DynamicExtension + | GhcMajorVersion + | GhcMinorVersion + | GhcPatchLevel + | GhcSourcePath + | HostArch + | HostOs + | ProjectVersion + | ProjectVersionInt | TargetArch + | TargetOs | TargetPlatformFull - | HostOsCpp - | DynamicExtension - | ProjectVersion - | GhcSourcePath data SettingList = ConfCcArgs Stage + | ConfCppArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage - | ConfCppArgs Stage - | IconvIncludeDirs - | IconvLibDirs | GmpIncludeDirs | GmpLibDirs + | IconvIncludeDirs + | IconvLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of - TargetOs -> "target-os" - TargetArch -> "target-arch" - TargetPlatformFull -> "target-platform-full" - HostOsCpp -> "host-os-cpp" DynamicExtension -> "dynamic-extension" - ProjectVersion -> "project-version" + GhcMajorVersion -> "ghc-major-version" + GhcMinorVersion -> "ghc-minor-version" + GhcPatchLevel -> "ghc-patch-level" GhcSourcePath -> "ghc-source-path" + HostArch -> "host-arch" + HostOs -> "host-os" + ProjectVersion -> "project-version" + ProjectVersionInt -> "project-version-int" + TargetArch -> "target-arch" + TargetOs -> "target-os" + TargetPlatformFull -> "target-platform-full" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -49,10 +59,10 @@ settingList key = fmap words $ askConfig $ case key of ConfCppArgs stage -> "conf-cpp-args-stage" ++ show stage ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show stage ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show stage - IconvIncludeDirs -> "iconv-include-dirs" - IconvLibDirs -> "iconv-lib-dirs" GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" + IconvIncludeDirs -> "iconv-include-dirs" + IconvLibDirs -> "iconv-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting @@ -84,9 +94,7 @@ targetArchs :: [String] -> Action Bool targetArchs = matchSetting TargetArch windowsHost :: Action Bool -windowsHost = do - hostOsCpp <- setting HostOsCpp - return $ hostOsCpp `elem` ["mingw32", "cygwin32"] +windowsHost = matchSetting HostOs ["mingw32", "cygwin32"] notWindowsHost :: Action Bool notWindowsHost = fmap not windowsHost @@ -103,6 +111,15 @@ ghcWithInterpreter = do ghcEnableTablesNextToCode :: Action Bool ghcEnableTablesNextToCode = targetArchs ["ia64", "powerpc64"] +-- Canonicalised GHC version number, used for integer version comparisons. We +-- expand GhcMinorVersion to two digits by adding a leading zero if necessary. +ghcCanonVersion :: Action String +ghcCanonVersion = do + ghcMajorVersion <- setting GhcMajorVersion + ghcMinorVersion <- setting GhcMinorVersion + let leadingZero = [ '0' | length ghcMinorVersion == 1 ] + return $ ghcMajorVersion ++ leadingZero ++ ghcMinorVersion + -- Command lines have limited size on Windows. Since Windows 7 the limit is -- 32768 characters (theoretically). In practice we use 31000 to leave some -- breathing space for the builder's path & name, auxiliary flags, and other From git at git.haskell.org Fri Oct 27 00:07:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to @WhatIsGcc@ being renamed to @CC@ in GHC HEAD (1c137b3) Message-ID: <20171027000745.181653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c137b3d58a85d01eb9018eca927616077d87098/ghc >--------------------------------------------------------------- commit 1c137b3d58a85d01eb9018eca927616077d87098 Author: Herbert Valerio Riedel Date: Sun Apr 17 15:46:06 2016 +0200 Adapt to @WhatIsGcc@ being renamed to @CC@ in GHC HEAD >--------------------------------------------------------------- 1c137b3d58a85d01eb9018eca927616077d87098 cfg/system.config.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 0b2e1f1..3c74076 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -7,7 +7,7 @@ alex = @AlexCmd@ ar = @ArCmd@ -cc = @WhatGccIsCalled@ +cc = @CC@ happy = @HappyCmd@ hs-cpp = @HaskellCPPCmd@ hscolour = @HSCOLOUR@ From git at git.haskell.org Fri Oct 27 00:07:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix parallel invocations of DeriveConstants builder. (9178de2) Message-ID: <20171027000747.F16113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9178de2bd2483148777975b5bab48d96ce2884ad/ghc >--------------------------------------------------------------- commit 9178de2bd2483148777975b5bab48d96ce2884ad Author: Andrey Mokhov Date: Mon Jan 11 16:06:21 2016 +0000 Fix parallel invocations of DeriveConstants builder. See #137. >--------------------------------------------------------------- 9178de2bd2483148777975b5bab48d96ce2884ad src/Rules/Generate.hs | 9 ++++++--- src/Settings/Builders/DeriveConstants.hs | 14 +++++--------- 2 files changed, 11 insertions(+), 12 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 4fd7da6..025f1ee 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -19,7 +19,6 @@ import Rules.Gmp import Rules.Libffi import Rules.Resources (Resources) import Settings -import Settings.Builders.DeriveConstants installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" @@ -53,6 +52,9 @@ ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> [ "GHC/PrimopWrappers.hs" , "autogen/GHC/Prim.hs" ] +derivedConstantsPath :: FilePath +derivedConstantsPath = "includes/dist-derivedconstants/header" + derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) [ "DerivedConstants.h" @@ -178,9 +180,10 @@ generateRules = do generate ghcSplit emptyTarget generateGhcSplit makeExecutable ghcSplit - -- TODO: simplify + -- TODO: simplify, get rid of fake rts target derivedConstantsPath ++ "//*" %> \file -> do - build $ fullTarget (PartialTarget Stage1 rts) DeriveConstants [] [file] + withTempDir $ \dir -> build $ + fullTarget (PartialTarget Stage1 rts) DeriveConstants [] [file, dir] where file <~ gen = file %> \out -> generate out emptyTarget gen diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 6f4828a..fb578f5 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -1,6 +1,4 @@ -module Settings.Builders.DeriveConstants ( - derivedConstantsPath, deriveConstantsBuilderArgs - ) where +module Settings.Builders.DeriveConstants (deriveConstantsBuilderArgs) where import Base import Expression @@ -9,21 +7,19 @@ import Oracles.Config.Setting import Predicates (builder, file) import Settings.Builders.Common -derivedConstantsPath :: FilePath -derivedConstantsPath = "includes/dist-derivedconstants/header" - -- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? deriveConstantsBuilderArgs :: Args deriveConstantsBuilderArgs = builder DeriveConstants ? do - cFlags <- fromDiffExpr includeCcArgs + cFlags <- fromDiffExpr includeCcArgs + [output, tempDir] <- getOutputs mconcat [ file "//DerivedConstants.h" ? arg "--gen-header" , file "//GHCConstantsHaskellType.hs" ? arg "--gen-haskell-type" , file "//platformConstants" ? arg "--gen-haskell-value" , file "//GHCConstantsHaskellWrappers.hs" ? arg "--gen-haskell-wrappers" , file "//GHCConstantsHaskellExports.hs" ? arg "--gen-haskell-exports" - , arg "-o", arg =<< getOutput - , arg "--tmpdir", arg derivedConstantsPath + , arg "-o", arg output + , arg "--tmpdir", arg tempDir , arg "--gcc-program", arg =<< getBuilderPath (Gcc Stage1) , append . concat $ map (\a -> ["--gcc-flag", a]) cFlags , arg "--nm-program", arg =<< getBuilderPath Nm From git at git.haskell.org Fri Oct 27 00:07:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finish Generate rule. (f7ee775) Message-ID: <20171027000748.31E073A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f7ee77565aa3b16f2911f99b7ef14059c16f9534/ghc >--------------------------------------------------------------- commit f7ee77565aa3b16f2911f99b7ef14059c16f9534 Author: Andrey Mokhov Date: Mon Sep 21 01:03:02 2015 +0100 Finish Generate rule. >--------------------------------------------------------------- f7ee77565aa3b16f2911f99b7ef14059c16f9534 src/Rules/Generate.hs | 22 ++-------------------- 1 file changed, 2 insertions(+), 20 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 055dccb..535f99b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -23,33 +23,15 @@ generatePackageCode _ target @ (PartialTarget stage package) = let path = targetPath stage package packagePath = pkgPath package buildPath = path -/- "build" - in do + in do -- TODO: do we need to copy *.(l)hs-boot files here? Never happens? buildPath "*.hs" %> \file -> do dirs <- interpretPartial target $ getPkgDataList SrcDirs files <- getDirectoryFiles "" $ [ packagePath d takeBaseName file <.> "*" | d <- dirs ] let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] - (src, builder) = head gens when (length gens /= 1) . putError $ "Exactly one generator expected for " ++ file ++ "(found: " ++ show gens ++ ")." + let (src, builder) = head gens need [src] build $ fullTarget target builder [src] [file] - --- $1/$2/build/%.hs : $1/$3/%.ly | $$$$(dir $$$$@)/. --- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ - --- $1/$2/build/%.hs : $1/$3/%.y | $$$$(dir $$$$@)/. --- $$(call cmd,HAPPY) $$($1_$2_ALL_HAPPY_OPTS) $$< -o $$@ - --- $1/$2/build/%_hsc.c $1/$2/build/%_hsc.h $1/$2/build/%.hs : $1/$3/%.hsc $$$$(hsc2hs_INPLACE) | $$$$(dir $$$$@)/. --- $$(call cmd,hsc2hs_INPLACE) $$($1_$2_ALL_HSC2HS_OPTS) $$< -o $$@ - --- # Now the rules for hs-boot files. - --- $1/$2/build/%.hs-boot : $1/$3/%.hs-boot --- "$$(CP)" $$< $$@ - --- $1/$2/build/%.lhs-boot : $1/$3/%.lhs-boot --- "$$(CP)" $$< $$@ - From git at git.haskell.org Fri Oct 27 00:07:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Convert cfg/system.config.in to use unix line-endings (3bab113) Message-ID: <20171027000749.025BD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3bab11333ae35906dc030f1d8652d765e92db879/ghc >--------------------------------------------------------------- commit 3bab11333ae35906dc030f1d8652d765e92db879 Author: Herbert Valerio Riedel Date: Sun Apr 17 15:46:57 2016 +0200 Convert cfg/system.config.in to use unix line-endings >--------------------------------------------------------------- 3bab11333ae35906dc030f1d8652d765e92db879 cfg/system.config.in | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Fri Oct 27 00:07:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Report success on IRC only if the build was fixed (462f78f) Message-ID: <20171027000752.112C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/462f78f8a676120ae0505c083afa93a14ccd7418/ghc >--------------------------------------------------------------- commit 462f78f8a676120ae0505c083afa93a14ccd7418 Author: David Luposchainsky Date: Mon Jan 11 18:35:25 2016 +0100 Report success on IRC only if the build was fixed >--------------------------------------------------------------- 462f78f8a676120ae0505c083afa93a14ccd7418 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0dc23c1..4ff35ec 100644 --- a/.travis.yml +++ b/.travis.yml @@ -72,7 +72,7 @@ cache: notifications: irc: - on_success: always # always/never/change + on_success: change # always/never/change on_failure: always channels: - "chat.freenode.net#shaking-up-ghc" From git at git.haskell.org Fri Oct 27 00:07:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new configuration flags for generating Config.hs. (7ae3a52) Message-ID: <20171027000752.555E83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ae3a52e7f4ea090e99ad98988951067b45e1397/ghc >--------------------------------------------------------------- commit 7ae3a52e7f4ea090e99ad98988951067b45e1397 Author: Andrey Mokhov Date: Wed Sep 23 02:06:28 2015 +0100 Add new configuration flags for generating Config.hs. >--------------------------------------------------------------- 7ae3a52e7f4ea090e99ad98988951067b45e1397 cfg/system.config.in | 33 +++++++++++++++++++++------------ 1 file changed, 21 insertions(+), 12 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 6bfb20d..2bfe449 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -21,6 +21,8 @@ haddock = @hardtop@/inplace/bin/haddock hsc2hs = @hardtop@/inplace/bin/hsc2hs +genprimopcode = @hardtop@/inplace/bin/genprimopcode + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ @@ -45,23 +47,30 @@ ghc-source-path = @hardtop@ # Information about host and target systems: #=========================================== -target-os = @TargetOS_CPP@ -target-arch = @TargetArch_CPP@ -target-platform-full = @TargetPlatformFull@ +target-os = @TargetOS_CPP@ +target-arch = @TargetArch_CPP@ +target-platform-full = @TargetPlatformFull@ + +host-os = @HostOS_CPP@ +host-arch = @HostArch_CPP@ -host-os = @HostOS_CPP@ -host-arch = @HostArch_CPP@ +cross-compiling = @CrossCompiling@ -cross-compiling = @CrossCompiling@ +dynamic-extension = @soext_target@ -dynamic-extension = @soext_target@ +ghc-version = @GhcVersion@ +ghc-major-version = @GhcMajVersion@ +ghc-minor-version = @GhcMinVersion@ +ghc-patch-level = @GhcPatchLevel@ -ghc-major-version = @GhcMajVersion@ -ghc-minor-version = @GhcMinVersion@ -ghc-patch-level = @GhcPatchLevel@ +project-name = @ProjectName@ +project-version = @ProjectVersion@ +project-version-int = @ProjectVersionInt@ +project-patch-level = @ProjectPatchLevel@ +project-patch-level1 = @ProjectPatchLevel1@ +project-patch-level2 = @ProjectPatchLevel2@ +project-git-commit-id = @ProjectGitCommitId@ -project-version = @ProjectVersion@ -project-version-int = @ProjectVersionInt@ # Compilation and linking flags: #=============================== From git at git.haskell.org Fri Oct 27 00:07:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #225 from hvr/pr/systemcfg-fixes (1099f62) Message-ID: <20171027000752.CC3C03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1099f6232570c8124afb27a13097272f436dd596/ghc >--------------------------------------------------------------- commit 1099f6232570c8124afb27a13097272f436dd596 Merge: 897ba61 3bab113 Author: Andrey Mokhov Date: Sun Apr 17 17:00:15 2016 +0100 Merge pull request #225 from hvr/pr/systemcfg-fixes Misc `system.config.in` fixes >--------------------------------------------------------------- 1099f6232570c8124afb27a13097272f436dd596 cfg/system.config.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:07:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #152 from snowleopard/report-on-fix (27f303f) Message-ID: <20171027000755.B50343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27f303f3cedbd506c7373318e4f785354dc6ddaf/ghc >--------------------------------------------------------------- commit 27f303f3cedbd506c7373318e4f785354dc6ddaf Merge: 9178de2 462f78f Author: Andrey Mokhov Date: Mon Jan 11 17:51:16 2016 +0000 Merge pull request #152 from snowleopard/report-on-fix Report success on IRC only if the build was fixed [skip ci] >--------------------------------------------------------------- 27f303f3cedbd506c7373318e4f785354dc6ddaf .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:07:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GenPrimopCode builder. (702ce42) Message-ID: <20171027000756.3E4063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/702ce42a9324375c294d8a3e0a49ce0c8a44bc62/ghc >--------------------------------------------------------------- commit 702ce42a9324375c294d8a3e0a49ce0c8a44bc62 Author: Andrey Mokhov Date: Wed Sep 23 02:06:48 2015 +0100 Add GenPrimopCode builder. >--------------------------------------------------------------- 702ce42a9324375c294d8a3e0a49ce0c8a44bc62 src/Builder.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 3a24df3..9448ed2 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -18,6 +18,7 @@ data Builder = Alex | Ar | Gcc Stage | GccM Stage + | GenPrimopCode | Ghc Stage | GhcCabal | GhcCabalHsColour @@ -38,6 +39,7 @@ builderKey builder = case builder of Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' + GenPrimopCode -> "genprimopcode" Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" From git at git.haskell.org Fri Oct 27 00:07:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep up with recent GHC changes, see #215. (e34e7e2) Message-ID: <20171027000756.AB6D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e34e7e287864bd8028e1b1d2e4b526135106787a/ghc >--------------------------------------------------------------- commit e34e7e287864bd8028e1b1d2e4b526135106787a Author: Andrey Mokhov Date: Mon Apr 18 01:19:21 2016 +0100 Keep up with recent GHC changes, see #215. >--------------------------------------------------------------- e34e7e287864bd8028e1b1d2e4b526135106787a cfg/system.config.in | 2 ++ shaking-up-ghc.cabal | 2 +- src/Oracles/Config/Flag.hs | 2 ++ src/Settings/Builders/Ghc.hs | 8 +++++++- src/Settings/Packages/GhcCabal.hs | 10 ++++++++-- 5 files changed, 20 insertions(+), 4 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index d053e65..f235f19 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -70,6 +70,8 @@ ghc-major-version = @GhcMajVersion@ ghc-minor-version = @GhcMinVersion@ ghc-patch-level = @GhcPatchLevel@ +supports-this-unit-id = @SUPPORTS_THIS_UNIT_ID@ + project-name = @ProjectName@ project-version = @ProjectVersion@ project-version-int = @ProjectVersionInt@ diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 17b48f0..92be3c7 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -118,7 +118,7 @@ executable ghc-shake , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* + , Cabal == 1.22.* || == 1.24.* , containers == 0.5.* , directory == 1.2.* , extra == 1.4.* diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 9d33445..449e2b2 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -18,6 +18,7 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken + | SupportsThisUnitId | WithLibdw | UseSystemFfi @@ -34,6 +35,7 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" + SupportsThisUnitId -> "supports-this-unit-id" WithLibdw -> "with-libdw" UseSystemFfi -> "use-system-ffi" value <- askConfigWithDefault key . putError diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 067c76e..a07c512 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -5,6 +5,7 @@ module Settings.Builders.Ghc ( import Base import Expression import GHC +import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.PackageData import Predicates hiding (way, stage) @@ -114,11 +115,16 @@ packageGhcArgs = do lift . when (isLibrary pkg) $ do conf <- pkgConfFile context need [conf] + -- FIXME: Get rid of to-be-deprecated -this-package-key. + thisArg <- do + not0 <- notStage0 + unit <- getFlag SupportsThisUnitId + return $ if not0 || unit then "-this-unit-id " else "-this-package-key " mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" , bootPackageDbArgs - , isLibrary pkg ? (arg $ "-this-package-key " ++ compId) + , isLibrary pkg ? (arg $ thisArg ++ compId) , append $ map ("-package-id " ++) pkgDepIds ] -- TODO: Improve handling of "cabal_macros.h" diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 762720f..80bda57 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -2,7 +2,8 @@ module Settings.Packages.GhcCabal (ghcCabalPackageArgs) where import Base import Expression -import GHC (ghcCabal) +import GHC +import Oracles.Config.Setting import Predicates (builderGhc, package, stage0) import Settings @@ -19,8 +20,13 @@ ghcCabalBootArgs = stage0 ? do path <- getBuildPath let cabalMacros = path -/- "autogen/cabal_macros.h" cabalMacrosBoot = pkgPath ghcCabal -/- "cabal_macros_boot.h" + cabalDeps <- fromDiffExpr $ mconcat + [ append [ array, base, bytestring, containers, deepseq, directory + , pretty, process, time ] + , notM windowsHost ? append [unix] + , windowsHost ? append [win32] ] mconcat - [ remove ["-hide-all-packages"] + [ append [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , removePair "-optP-include" $ "-optP" ++ cabalMacros , arg "--make" , arg "-j" From git at git.haskell.org Fri Oct 27 00:07:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:07:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch off -split-objs by default, fix #153. (1b226d9) Message-ID: <20171027000759.C01833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b226d992e53e3dee36fbfe22c0218477bc2bacb/ghc >--------------------------------------------------------------- commit 1b226d992e53e3dee36fbfe22c0218477bc2bacb Author: Andrey Mokhov Date: Tue Jan 12 02:08:58 2016 +0000 Switch off -split-objs by default, fix #153. >--------------------------------------------------------------- 1b226d992e53e3dee36fbfe22c0218477bc2bacb src/Settings/User.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 35eb86e..3cebe13 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -62,9 +62,9 @@ trackBuildSystem = True validating :: Bool validating = False --- To switch off split objects change to 'return False' +-- To switch on split objects use 'splitObjects = defaultSplitObjects', see #153 splitObjects :: Predicate -splitObjects = defaultSplitObjects +splitObjects = return False dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Fri Oct 27 00:08:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle GenPrimopCode builder in a special way. (17087d7) Message-ID: <20171027000800.0777F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/17087d74a371ab996b81e8436f07839294a21cf8/ghc >--------------------------------------------------------------- commit 17087d74a371ab996b81e8436f07839294a21cf8 Author: Andrey Mokhov Date: Wed Sep 23 02:07:17 2015 +0100 Handle GenPrimopCode builder in a special way. >--------------------------------------------------------------- 17087d74a371ab996b81e8436f07839294a21cf8 src/Rules/Actions.hs | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index f261b4f..1e0472a 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -24,15 +24,23 @@ buildWithResources rs target = do ++ show builder ++ " with arguments:" mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList putBuild $ "\\--------" - quietly $ if builder /= Ar - then cmd [path] argList - else do -- Split argument list into chunks as otherwise Ar chokes up + quietly $ case builder of + Ar -> do -- Split argument list into chunks as otherwise Ar chokes up maxChunk <- cmdLineLengthLimit let persistentArgs = take arPersistentArgsCount argList remainingArgs = drop arPersistentArgsCount argList forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> unit . cmd [path] $ persistentArgs ++ argsChunk + GenPrimopCode -> do + let src = head $ Target.sources target -- TODO: ugly + file = head $ Target.files target + input <- readFile' src + Stdout output <- cmd (Stdin input) [path] argList + writeFileChanged file output + + _ -> cmd [path] argList + -- Most targets are built without explicitly acquiring resources build :: Target -> Action () build = buildWithResources [] From git at git.haskell.org Fri Oct 27 00:08:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on cabalDeps list. (d1c8ba4) Message-ID: <20171027000800.58A1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1c8ba4b5787d0995538cc0b69a4aa93969f6488/ghc >--------------------------------------------------------------- commit d1c8ba4b5787d0995538cc0b69a4aa93969f6488 Author: Andrey Mokhov Date: Mon Apr 18 10:16:13 2016 +0100 Add a note on cabalDeps list. See #215. [skip ci] >--------------------------------------------------------------- d1c8ba4b5787d0995538cc0b69a4aa93969f6488 src/Settings/Packages/GhcCabal.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 80bda57..1dac541 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -20,6 +20,9 @@ ghcCabalBootArgs = stage0 ? do path <- getBuildPath let cabalMacros = path -/- "autogen/cabal_macros.h" cabalMacrosBoot = pkgPath ghcCabal -/- "cabal_macros_boot.h" + -- Note: We could have computed 'cabalDeps' instead of hard-coding it + -- but this doesn't worth the effort, since we plan to drop ghc-cabal + -- altogether at some point. See #18. cabalDeps <- fromDiffExpr $ mconcat [ append [ array, base, bytestring, containers, deepseq, directory , pretty, process, time ] From git at git.haskell.org Fri Oct 27 00:08:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Preliminary working state (5d4e182) Message-ID: <20171027000804.3F2C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d4e18236b64fa400a66967cd7dbb8371b0e08b7/ghc >--------------------------------------------------------------- commit 5d4e18236b64fa400a66967cd7dbb8371b0e08b7 Author: Moritz Angermann Date: Tue Jan 12 14:56:53 2016 +0800 Preliminary working state This almost works. Yet we run into: ``` Build system error - cannot currently call askOracle: Reason: Within withResource using Resource ghc-cabal Question type: OracleQ CmdLineFlags Question value: OracleQ (CmdLineFlags ()) Move the askOracle call earlier/later ``` >--------------------------------------------------------------- 5d4e18236b64fa400a66967cd7dbb8371b0e08b7 shaking-up-ghc.cabal | 1 + src/Base.hs | 27 +++++++++++++++-- src/Main.hs | 7 ++++- src/Oracles/Config/CmdLineFlag.hs | 64 +++++++++++++++++++++++++++++++++++++++ src/Rules/Actions.hs | 20 +++++------- src/Rules/Library.hs | 9 +++--- src/Rules/Program.hs | 9 +++--- 7 files changed, 111 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5d4e18236b64fa400a66967cd7dbb8371b0e08b7 From git at git.haskell.org Fri Oct 27 00:08:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new configuration flags for generating Config.hs. (b8d04a6) Message-ID: <20171027000804.62ED53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b8d04a663c092320d5b0fe2556349557d72ae373/ghc >--------------------------------------------------------------- commit b8d04a663c092320d5b0fe2556349557d72ae373 Author: Andrey Mokhov Date: Wed Sep 23 02:07:52 2015 +0100 Add new configuration flags for generating Config.hs. >--------------------------------------------------------------- b8d04a663c092320d5b0fe2556349557d72ae373 src/Oracles/Config/Setting.hs | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index a01a7fa..8ee4752 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -20,11 +20,17 @@ data Setting = DynamicExtension | GhcMajorVersion | GhcMinorVersion | GhcPatchLevel + | GhcVersion | GhcSourcePath | HostArch | HostOs + | ProjectGitCommitId + | ProjectName | ProjectVersion | ProjectVersionInt + | ProjectPatchLevel + | ProjectPatchLevel1 + | ProjectPatchLevel2 | TargetArch | TargetOs | TargetPlatformFull @@ -44,11 +50,17 @@ setting key = askConfig $ case key of GhcMajorVersion -> "ghc-major-version" GhcMinorVersion -> "ghc-minor-version" GhcPatchLevel -> "ghc-patch-level" + GhcVersion -> "ghc-version" GhcSourcePath -> "ghc-source-path" HostArch -> "host-arch" HostOs -> "host-os" + ProjectGitCommitId -> "project-git-commit-id" + ProjectName -> "project-name" ProjectVersion -> "project-version" ProjectVersionInt -> "project-version-int" + ProjectPatchLevel -> "project-patch-level" + ProjectPatchLevel1 -> "project-patch-level1" + ProjectPatchLevel2 -> "project-patch-level2" TargetArch -> "target-arch" TargetOs -> "target-os" TargetPlatformFull -> "target-platform-full" From git at git.haskell.org Fri Oct 27 00:08:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: List installed packages in CI (61032aa) Message-ID: <20171027000804.981803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/61032aa99bc8f1afab5e0f3487202c30488243fb/ghc >--------------------------------------------------------------- commit 61032aa99bc8f1afab5e0f3487202c30488243fb Author: Andrey Mokhov Date: Fri Apr 22 12:21:26 2016 +0100 List installed packages in CI >--------------------------------------------------------------- 61032aa99bc8f1afab5e0f3487202c30488243fb .travis.yml | 1 + appveyor.yml | 1 + 2 files changed, 2 insertions(+) diff --git a/.travis.yml b/.travis.yml index 21bf769..0e59864 100644 --- a/.travis.yml +++ b/.travis.yml @@ -57,6 +57,7 @@ install: - ( cd ghc && ./boot ) - ( cd ghc && ./configure ) - cat ghc/shake-build/cfg/system.config + - ghc-pkg list script: - ( cd ghc/shake-build && cabal haddock --internal ) diff --git a/appveyor.yml b/appveyor.yml index 537983c..88ca776 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -35,6 +35,7 @@ install: - stack --version - alex --version - happy --version + - ghc-pkg list build_script: - cd C:\msys64\home\ghc\shake-build From git at git.haskell.org Fri Oct 27 00:08:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' into angerman/feature/build-info-flags (8dfe2b9) Message-ID: <20171027000808.4200E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8dfe2b928d8e2d8eef9f45fb148764799e844257/ghc >--------------------------------------------------------------- commit 8dfe2b928d8e2d8eef9f45fb148764799e844257 Merge: 5d4e182 27f303f Author: Moritz Angermann Date: Tue Jan 12 14:57:35 2016 +0800 Merge branch 'master' into angerman/feature/build-info-flags # Conflicts: # src/Main.hs >--------------------------------------------------------------- 8dfe2b928d8e2d8eef9f45fb148764799e844257 .appveyor.yml | 10 +++++++++- .travis.yml | 3 ++- shaking-up-ghc.cabal | 3 +++ src/Main.hs | 7 ++++++- src/Rules/Generate.hs | 9 ++++++--- src/Settings/Builders/Ar.hs | 16 ++++------------ src/Settings/Builders/DeriveConstants.hs | 14 +++++--------- src/Test.hs | 28 ++++++++++++++++++++++++++++ src/Way.hs | 2 +- 9 files changed, 64 insertions(+), 28 deletions(-) diff --cc src/Main.hs index f65483d,dea793e..6d79cb8 --- a/src/Main.hs +++ b/src/Main.hs @@@ -11,15 -11,11 +11,19 @@@ import qualified Rules.Gm import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl ++<<<<<<< HEAD +import Oracles.Config.CmdLineFlag (cmdLineOracle, flags) ++======= + import qualified Test ++>>>>>>> master main :: IO () -main = shakeArgs options rules +main = shakeArgsWith options flags $ \cmdLineFlags targets -> + return . Just $ cmdLineOracle cmdLineFlags + >> if null targets then rules else want targets + >> withoutActions rules where + rules :: Rules () rules = mconcat [ Rules.Cabal.cabalRules , Rules.Config.configRules From git at git.haskell.org Fri Oct 27 00:08:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add genPrimopCodeArgs to defaultArgs. (f406d36) Message-ID: <20171027000808.514643A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f406d36fead05bbfd323aafc85d836c2fdb6ae89/ghc >--------------------------------------------------------------- commit f406d36fead05bbfd323aafc85d836c2fdb6ae89 Author: Andrey Mokhov Date: Wed Sep 23 02:08:22 2015 +0100 Add genPrimopCodeArgs to defaultArgs. >--------------------------------------------------------------- f406d36fead05bbfd323aafc85d836c2fdb6ae89 src/Settings/Args.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 97933fa..349668a 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -4,6 +4,7 @@ import Expression import Settings.Builders.Alex import Settings.Builders.Ar import Settings.Builders.Gcc +import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc import Settings.Builders.GhcCabal import Settings.Builders.GhcPkg @@ -30,12 +31,13 @@ defaultArgs = mconcat , arArgs , cabalArgs , customPackageArgs + , gccArgs + , gccMArgs + , genPrimopCodeArgs , ghcArgs , ghcCabalHsColourArgs , ghcMArgs , ghcPkgArgs - , gccArgs - , gccMArgs , haddockArgs , happyArgs , hsc2HsArgs From git at git.haskell.org Fri Oct 27 00:08:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run ghc-pkg list through stack (e29218a) Message-ID: <20171027000808.752783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e29218a5f8df4e9c03e30b2f0579d5f8ea8ac647/ghc >--------------------------------------------------------------- commit e29218a5f8df4e9c03e30b2f0579d5f8ea8ac647 Author: Andrey Mokhov Date: Fri Apr 22 13:04:44 2016 +0100 Run ghc-pkg list through stack >--------------------------------------------------------------- e29218a5f8df4e9c03e30b2f0579d5f8ea8ac647 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 88ca776..6cc17b6 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -35,7 +35,7 @@ install: - stack --version - alex --version - happy --version - - ghc-pkg list + - stack exec -- ghc-pkg list build_script: - cd C:\msys64\home\ghc\shake-build From git at git.haskell.org Fri Oct 27 00:08:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add next meeting discusion agenda. (395f3ce) Message-ID: <20171027000812.04A103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/395f3ce523108018dc1ffaefc2daa3318fbcf4bd/ghc >--------------------------------------------------------------- commit 395f3ce523108018dc1ffaefc2daa3318fbcf4bd Author: Andrey Mokhov Date: Wed Sep 23 02:08:56 2015 +0100 Add next meeting discusion agenda. >--------------------------------------------------------------- 395f3ce523108018dc1ffaefc2daa3318fbcf4bd doc/meeting-25-September-2015.txt | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt new file mode 100644 index 0000000..6ee4297 --- /dev/null +++ b/doc/meeting-25-September-2015.txt @@ -0,0 +1,35 @@ +Shaking up GHC meeting, 25 September 2015 + +Things to discuss: +================================================ + +1. Better names for build stages + +* Currently we have Stage0, Stage1, etc. It is not particularly clear +from the names what they stand for. We no longer need to stick to +numbers and can pick more helpful names, for example: + +Stage0 -> Boot +Stage1 -> Interim +Stage2 -> Install +Stage3 -> Selftest + + + + +i. Unclear abstractions Builder/BuildRule... + +ii. Limits to build parallelism: GHC crashes during parallel builds. Also ghc-pkg and ghc-cabal are apparently not thread-safe, so I had to use Shake resources to limit the parallelism... + + +2. Do we need a name for the new build system? + +* At least we need a name for the folder in the GHC tree + +* If we call it 'shake' there may be a confusion with the Shake library. + +* In future discussions/announcements/etc. calling it 'the new shake-based + build system' is overly verbose. Calling it 'shake' is confusing. + +* I haven't thought about any names yet, just checking whether we want to. + From git at git.haskell.org Fri Oct 27 00:08:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use Docker on Travis. (ee592f4) Message-ID: <20171027000812.AA6623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee592f4254da5b9f2db59ea465fd55adf66b771f/ghc >--------------------------------------------------------------- commit ee592f4254da5b9f2db59ea465fd55adf66b771f Author: Andrey Mokhov Date: Fri Apr 22 13:08:07 2016 +0100 Don't use Docker on Travis. See #229. >--------------------------------------------------------------- ee592f4254da5b9f2db59ea465fd55adf66b771f .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0e59864..2f0739a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,4 +1,4 @@ -sudo: false +sudo: true matrix: include: From git at git.haskell.org Fri Oct 27 00:08:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Merge. (e519681) Message-ID: <20171027000812.BBBFE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e5196817511ddd50939d1f11b8ff2d6d856aa203/ghc >--------------------------------------------------------------- commit e5196817511ddd50939d1f11b8ff2d6d856aa203 Author: Moritz Angermann Date: Tue Jan 12 15:41:55 2016 +0800 Fix Merge. >--------------------------------------------------------------- e5196817511ddd50939d1f11b8ff2d6d856aa203 src/Main.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 6d79cb8..b372fa1 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -11,11 +11,8 @@ import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl -<<<<<<< HEAD -import Oracles.Config.CmdLineFlag (cmdLineOracle, flags) -======= import qualified Test ->>>>>>> master +import Oracles.Config.CmdLineFlag (cmdLineOracle, flags) main :: IO () main = shakeArgsWith options flags $ \cmdLineFlags targets -> From git at git.haskell.org Fri Oct 27 00:08:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Draft GenPrimopCode argument list. (ed20ac4) Message-ID: <20171027000815.E6C983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ed20ac498137f4c2e3f297e6312da93dab64be6d/ghc >--------------------------------------------------------------- commit ed20ac498137f4c2e3f297e6312da93dab64be6d Author: Andrey Mokhov Date: Wed Sep 23 02:09:29 2015 +0100 Draft GenPrimopCode argument list. >--------------------------------------------------------------- ed20ac498137f4c2e3f297e6312da93dab64be6d src/Settings/Builders/GenPrimopCode.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/src/Settings/Builders/GenPrimopCode.hs b/src/Settings/Builders/GenPrimopCode.hs new file mode 100644 index 0000000..711aa80 --- /dev/null +++ b/src/Settings/Builders/GenPrimopCode.hs @@ -0,0 +1,8 @@ +module Settings.Builders.GenPrimopCode (genPrimopCodeArgs) where + +import Expression +import Predicates (builder) + +-- Stdin/stdout are handled in a special way. See Rules/Actions.hs. +genPrimopCodeArgs :: Args +genPrimopCodeArgs = builder GenPrimopCode ? arg "--make-haskell-wrappers" From git at git.haskell.org Fri Oct 27 00:08:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try full build on Mac OS X. (219da37) Message-ID: <20171027000816.7D03A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/219da3757e6f5ee6761c672099a005987156849e/ghc >--------------------------------------------------------------- commit 219da3757e6f5ee6761c672099a005987156849e Author: Andrey Mokhov Date: Fri Apr 22 13:47:29 2016 +0100 Try full build on Mac OS X. >--------------------------------------------------------------- 219da3757e6f5ee6761c672099a005987156849e .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 2f0739a..d6092fb 100644 --- a/.travis.yml +++ b/.travis.yml @@ -20,7 +20,7 @@ matrix: - cabal install alex happy - os: osx - env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg + env: TARGET= before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Fri Oct 27 00:08:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Pony (5dd8bbb) Message-ID: <20171027000816.BBBD43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5dd8bbb0090ebef875650ca7de8bc87aa37f54c9/ghc >--------------------------------------------------------------- commit 5dd8bbb0090ebef875650ca7de8bc87aa37f54c9 Author: Moritz Angermann Date: Tue Jan 12 15:42:56 2016 +0800 Adds Pony This fixes #92 for good. Together this fixes #134 almost entirely. >--------------------------------------------------------------- 5dd8bbb0090ebef875650ca7de8bc87aa37f54c9 src/Base.hs | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index c733226..ffe06d8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -142,26 +142,52 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg +-- | Render an action. renderAction :: String -> String -> String -> Action String renderAction what input output = buildInfo >>= return . \case Normal -> renderBox [ what , " input:" ++ input , " => output:" ++ output ] Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output - Pony -> " *** PONY NOT YET SUPPORTED ***" + Pony -> renderPony [ what + , " input:" ++ input + , " => output:" ++ output ] Dot -> "." None -> "" +-- | Render the successful build of a program renderProgram :: String -> String -> String -> Action String renderProgram name bin synopsis = return $ renderBox [ "Successfully built program " ++ name , "Executable: " ++ bin , "Program synopsis: " ++ synopsis ++ "."] +-- | Render the successful built of a library renderLibrary :: String -> String -> String -> Action String renderLibrary name lib synopsis = return $ renderBox [ "Successfully built library " ++ name , "Library: " ++ lib , "Library synopsis: " ++ synopsis ++ "."] +-- | Render the given set of lines next to our favorit unicorn Robert. +renderPony :: [String] -> String +renderPony ls = + unlines $ take (max (length ponyLines) (length boxLines)) $ + zipWith (++) (ponyLines ++ repeat ponyPadding) (boxLines ++ repeat "") + where + ponyLines :: [String] + ponyLines = [ " ,;,,;'" + , " ,;;'( Robert the spitting unicorn" + , " __ ,;;' ' \\ wants you to know" + , " /' '\\'~~'~' \\ /'\\.) that a task " + , " ,;( ) / |. / just finished! " + , " ,;' \\ /-.,,( ) \\ " + , " ^ ) / ) / )| Almost there! " + , " || || \\) " + , " (_\\ (_\\ " ] + ponyPadding :: String + ponyPadding = " " + boxLines :: [String] + boxLines = ["", "", ""] ++ (lines . renderBox $ ls) + -- | Render the given set of lines in a nice box of ASCII. -- -- The minimum width and whether to use Unicode symbols are hardcoded in the From git at git.haskell.org Fri Oct 27 00:08:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement generation of PrimopWrappers.hs. Work on generating Config.hs. (7e4f903) Message-ID: <20171027000819.845043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e4f9033115b8f0591b3a1e4541b8dd6a4c9d633/ghc >--------------------------------------------------------------- commit 7e4f9033115b8f0591b3a1e4541b8dd6a4c9d633 Author: Andrey Mokhov Date: Wed Sep 23 02:10:25 2015 +0100 Implement generation of PrimopWrappers.hs. Work on generating Config.hs. >--------------------------------------------------------------- 7e4f9033115b8f0591b3a1e4541b8dd6a4c9d633 src/Rules/Generate.hs | 93 ++++++++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 92 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 535f99b..a12f6a8 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -6,6 +6,9 @@ import Rules.Actions import Rules.Resources import Settings +primops :: FilePath +primops = "compiler/stage1/build/primops.txt" + -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] knownGenerators = [ (Alex , ".x" ) @@ -31,7 +34,95 @@ generatePackageCode _ target @ (PartialTarget stage package) = let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ "Exactly one generator expected for " ++ file - ++ "(found: " ++ show gens ++ ")." + ++ " (found: " ++ show gens ++ ")." let (src, builder) = head gens need [src] build $ fullTarget target builder [src] [file] + + path -/- "build/GHC/PrimopWrappers.hs" %> \file -> do + need [primops] + build $ fullTarget target GenPrimopCode [primops] [file] + + priority 2.0 $ path -/- "build/Config.hs" %> \file -> do + config <- generateConfig + writeFileChanged file config + +generateConfig :: Action String +generateConfig = do + cProjectName <- setting ProjectName + cProjectGitCommitId <- setting ProjectGitCommitId + cProjectVersion <- setting ProjectVersion + cProjectVersionInt <- setting ProjectVersionInt + cProjectPatchLevel <- setting ProjectPatchLevel + cProjectPatchLevel1 <- setting ProjectPatchLevel1 + cProjectPatchLevel2 <- setting ProjectPatchLevel2 + cBooterVersion <- setting GhcVersion + cIntegerLibraryType <- case integerLibrary of + integerGmp -> return "IntegerGMP" + integerSimple -> return "IntegerSimple" + _ -> putError $ "Unknown integer library: " ++ integerLibrary ++ "." + cSupportsSplitObjs <- yesNo splitObjects + return "{-# LANGUAGE CPP #-}\n" + ++ "module Config where\n" + ++ "\n" + ++ "#include \"ghc_boot_platform.h\"\n" + ++ "\n" + ++ "data IntegerLibrary = IntegerGMP\n" + ++ " | IntegerSimple\n" + ++ " deriving Eq\n" + ++ "\n" + ++ "cBuildPlatformString :: String\n" + ++ "cBuildPlatformString = BuildPlatform_NAME\n" + ++ "cHostPlatformString :: String\n" + ++ "cHostPlatformString = HostPlatform_NAME\n" + ++ "cTargetPlatformString :: String\n" + ++ "cTargetPlatformString = TargetPlatform_NAME\n" + ++ "\n" + ++ "cProjectName :: String\n" + ++ "cProjectName = " ++ cProjectName ++ "\n" + ++ "cProjectGitCommitId :: String\n" + ++ "cProjectGitCommitId = " ++ cProjectGitCommitId ++ "\n" + ++ "cProjectVersion :: String\n" + ++ "cProjectVersion = " ++ cProjectVersion ++ "\n" + ++ "cProjectVersionInt :: String\n" + ++ "cProjectVersionInt = " ++ cProjectVersionInt ++ "\n" + ++ "cProjectPatchLevel :: String\n" + ++ "cProjectPatchLevel = " ++ cProjectPatchLevel ++ "\n" + ++ "cProjectPatchLevel1 :: String\n" + ++ "cProjectPatchLevel1 = " ++ cProjectPatchLevel1 ++ "\n" + ++ "cProjectPatchLevel2 :: String\n" + ++ "cProjectPatchLevel2 = " ++ cProjectPatchLevel2 ++ "\n" + ++ "cBooterVersion :: String\n" + ++ "cBooterVersion = " ++ cBooterVersion ++ "\n" + ++ "cStage :: String\n" + ++ "cStage = show (STAGE :: Int)\n" + ++ "cIntegerLibrary :: String\n" + ++ "cIntegerLibrary = " ++ pkgName integerLibrary ++ "\n" + ++ "cIntegerLibraryType :: IntegerLibrary\n" + ++ "cIntegerLibraryType = " ++ cIntegerLibraryType ++ "\n" + ++ "cSupportsSplitObjs :: String\n" + ++ "cSupportsSplitObjs = " ++ cSupportsSplitObjs ++ "\n" + ++ "cGhcWithInterpreter :: String\n" + ++ "cGhcWithInterpreter = "YES"\n" + ++ "cGhcWithNativeCodeGen :: String\n" + ++ "cGhcWithNativeCodeGen = "YES"\n" + ++ "cGhcWithSMP :: String\n" + ++ "cGhcWithSMP = "YES"\n" + ++ "cGhcRTSWays :: String\n" + ++ "cGhcRTSWays = "l debug thr thr_debug thr_l thr_p "\n" + ++ "cGhcEnableTablesNextToCode :: String\n" + ++ "cGhcEnableTablesNextToCode = "YES"\n" + ++ "cLeadingUnderscore :: String\n" + ++ "cLeadingUnderscore = "NO"\n" + ++ "cGHC_UNLIT_PGM :: String\n" + ++ "cGHC_UNLIT_PGM = "unlit.exe"\n" + ++ "cGHC_SPLIT_PGM :: String\n" + ++ "cGHC_SPLIT_PGM = "ghc-split"\n" + ++ "cLibFFI :: Bool\n" + ++ "cLibFFI = False\n" + ++ "cGhcThreaded :: Bool\n" + ++ "cGhcThreaded = True\n" + ++ "cGhcDebugged :: Bool\n" + ++ "cGhcDebugged = False\n" + + From git at git.haskell.org Fri Oct 27 00:08:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to shake-0.15.6. (cf5ab9a) Message-ID: <20171027000820.C761D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf5ab9ad72cf29153cc0cbfdd510465fc6abcbc9/ghc >--------------------------------------------------------------- commit cf5ab9ad72cf29153cc0cbfdd510465fc6abcbc9 Author: Andrey Mokhov Date: Fri Apr 22 17:05:28 2016 +0100 Switch to shake-0.15.6. >--------------------------------------------------------------- cf5ab9ad72cf29153cc0cbfdd510465fc6abcbc9 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 92be3c7..da19de1 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -124,7 +124,7 @@ executable ghc-shake , extra == 1.4.* , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.9 - , shake == 0.15.* + , shake == 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* ghc-options: -Wall From git at git.haskell.org Fri Oct 27 00:08:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace Oracle with IO Ref (f794e73) Message-ID: <20171027000820.D30FB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f794e7369f2b2b6e86f27d9587e5baf74cfc73e3/ghc >--------------------------------------------------------------- commit f794e7369f2b2b6e86f27d9587e5baf74cfc73e3 Author: Moritz Angermann Date: Tue Jan 12 18:03:59 2016 +0800 Replace Oracle with IO Ref >--------------------------------------------------------------- f794e7369f2b2b6e86f27d9587e5baf74cfc73e3 src/Base.hs | 21 ++++++++--------- src/Main.hs | 8 +++---- src/Oracles/Config/CmdLineFlag.hs | 48 ++++++++++++++++----------------------- src/Rules/Actions.hs | 6 ++--- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 4 ++-- 6 files changed, 40 insertions(+), 49 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 f794e7369f2b2b6e86f27d9587e5baf74cfc73e3 From git at git.haskell.org Fri Oct 27 00:08:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcSplit and Unlit builders. (47c7ab1) Message-ID: <20171027000823.066173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47c7ab173f636eb0c636765b412c523bdb3e7fb3/ghc >--------------------------------------------------------------- commit 47c7ab173f636eb0c636765b412c523bdb3e7fb3 Author: Andrey Mokhov Date: Thu Sep 24 05:43:05 2015 +0100 Add GhcSplit and Unlit builders. >--------------------------------------------------------------- 47c7ab173f636eb0c636765b412c523bdb3e7fb3 cfg/system.config.in | 4 ++++ src/Builder.hs | 11 ++++++++++- 2 files changed, 14 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 2bfe449..87d2b93 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -23,6 +23,9 @@ hsc2hs = @hardtop@/inplace/bin/hsc2hs genprimopcode = @hardtop@/inplace/bin/genprimopcode +unlit = @hardtop@/inplace/lib/unlit +ghc-split = @hardtop@/inplace/lib/ghc-split + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ @@ -43,6 +46,7 @@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ ghc-source-path = @hardtop@ +leading-underscore = @LeadingUnderscore@ # Information about host and target systems: #=========================================== diff --git a/src/Builder.hs b/src/Builder.hs index 9448ed2..a6521a1 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,5 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} -module Builder (Builder (..), builderPath, specified, needBuilder) where +module Builder ( + Builder (..), builderPath, getBuilderPath, specified, needBuilder + ) where import Base import GHC.Generics (Generic) @@ -24,11 +26,13 @@ data Builder = Alex | GhcCabalHsColour | GhcM Stage | GhcPkg Stage + | GhcSplit | Haddock | Happy | HsColour | Hsc2Hs | Ld + | Unlit deriving (Show, Eq, Generic) -- Configuration files refer to Builders as follows: @@ -49,11 +53,13 @@ builderKey builder = case builder of GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" + GhcSplit -> "ghc-split" Happy -> "happy" Haddock -> "haddock" HsColour -> "hscolour" Hsc2Hs -> "hsc2hs" Ld -> "ld" + Unlit -> "unlit" builderPath :: Builder -> Action FilePath builderPath builder = do @@ -62,6 +68,9 @@ builderPath builder = do ++ "' in configuration files." fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe +getBuilderPath :: Builder -> ReaderT a Action FilePath +getBuilderPath = lift . builderPath + specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath From git at git.haskell.org Fri Oct 27 00:08:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add shake-0.15.6 to stack extra-deps (028ef28) Message-ID: <20171027000825.0E46C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/028ef285adb1b4c4ada79c1ec2ee891e240b0c59/ghc >--------------------------------------------------------------- commit 028ef285adb1b4c4ada79c1ec2ee891e240b0c59 Author: Moritz Kiefer Date: Fri Apr 22 18:24:35 2016 +0200 Add shake-0.15.6 to stack extra-deps >--------------------------------------------------------------- 028ef285adb1b4c4ada79c1ec2ee891e240b0c59 stack.yaml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index 0772c76..0d8809b 100644 --- a/stack.yaml +++ b/stack.yaml @@ -8,7 +8,8 @@ packages: - '.' # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) -extra-deps: [] +extra-deps: +- shake-0.15.6 # Override default flag values for local packages and extra-deps flags: {} From git at git.haskell.org Fri Oct 27 00:08:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add dependencies, fix #155. (85799a5) Message-ID: <20171027000825.158C53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/85799a569efbace0d6fdc168c6ddff0a015d1df8/ghc >--------------------------------------------------------------- commit 85799a569efbace0d6fdc168c6ddff0a015d1df8 Author: Andrey Mokhov Date: Tue Jan 12 17:25:00 2016 +0000 Add dependencies, fix #155. [skip ci] >--------------------------------------------------------------- 85799a569efbace0d6fdc168c6ddff0a015d1df8 README.md | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index fe6a909..823e472 100644 --- a/README.md +++ b/README.md @@ -12,7 +12,7 @@ on the [wiki page][ghc-shake-wiki] and in this [blog post][shake-blog-post]. This is supposed to go into the `shake-build` directory of the GHC source tree. -[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc) +[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc). Trying it --------- @@ -23,6 +23,9 @@ identical to those for the `make` build system. This means that you don't need to adjust anything if you are already familiar with building ghc using the `make` build system. +Furthermore, we depend on the following packages which need to be installed: +`ansi-terminal`, `mtl`, `shake`, `quickcheck`. + ### Getting the source and configuring GHC ```bash @@ -51,7 +54,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). +To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (#131). How to contribute From git at git.haskell.org Fri Oct 27 00:08:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix ghcEnableTablesNextToCode, refactor code. (aecfdda) Message-ID: <20171027000826.6D1323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aecfddac1536bf6f565df227acff0ab37ce534a8/ghc >--------------------------------------------------------------- commit aecfddac1536bf6f565df227acff0ab37ce534a8 Author: Andrey Mokhov Date: Thu Sep 24 05:45:34 2015 +0100 Fix ghcEnableTablesNextToCode, refactor code. >--------------------------------------------------------------- aecfddac1536bf6f565df227acff0ab37ce534a8 src/Oracles/Config/Flag.hs | 35 ++++++++++++++++------------- src/Oracles/Config/Setting.hs | 52 ++++++++++++++++++------------------------- 2 files changed, 42 insertions(+), 45 deletions(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index d520a85..69d4884 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -1,7 +1,7 @@ module Oracles.Config.Flag ( Flag (..), flag, getFlag, - crossCompiling, gccIsClang, gccGe46, - platformSupportsSharedLibs, ghcWithSMP, ghcWithNativeCodeGen + crossCompiling, platformSupportsSharedLibs, ghcWithSMP, + ghcWithNativeCodeGen, supportsSplitObjects ) where import Base @@ -12,6 +12,7 @@ data Flag = CrossCompiling | GccIsClang | GccLt46 | GhcUnregisterised + | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken | SupportsPackageKey @@ -25,6 +26,7 @@ flag f = do GccIsClang -> "gcc-is-clang" GccLt46 -> "gcc-lt-46" GhcUnregisterised -> "ghc-unregisterised" + LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" SupportsPackageKey -> "supports-package-key" @@ -41,30 +43,33 @@ getFlag = lift . flag crossCompiling :: Action Bool crossCompiling = flag CrossCompiling -gccIsClang :: Action Bool -gccIsClang = flag GccIsClang - -gccGe46 :: Action Bool -gccGe46 = fmap not $ flag GccLt46 - platformSupportsSharedLibs :: Action Bool platformSupportsSharedLibs = do - badPlatform <- targetPlatforms [ "powerpc-unknown-linux" - , "x86_64-unknown-mingw32" - , "i386-unknown-mingw32" ] - solaris <- targetPlatform "i386-unknown-solaris2" + badPlatform <- anyTargetPlatform [ "powerpc-unknown-linux" + , "x86_64-unknown-mingw32" + , "i386-unknown-mingw32" ] + solaris <- anyTargetPlatform [ "i386-unknown-solaris2" ] solarisBroken <- flag SolarisBrokenShld return $ not (badPlatform || solaris && solarisBroken) ghcWithSMP :: Action Bool ghcWithSMP = do - goodArch <- targetArchs ["i386", "x86_64", "sparc", "powerpc", "arm"] + goodArch <- anyTargetArch ["i386", "x86_64", "sparc", "powerpc", "arm"] ghcUnreg <- flag GhcUnregisterised return $ goodArch && not ghcUnreg ghcWithNativeCodeGen :: Action Bool ghcWithNativeCodeGen = do - goodArch <- targetArchs ["i386", "x86_64", "sparc", "powerpc"] - badOs <- targetOss ["ios", "aix"] + goodArch <- anyTargetArch ["i386", "x86_64", "sparc", "powerpc"] + badOs <- anyTargetOs ["ios", "aix"] ghcUnreg <- flag GhcUnregisterised return $ goodArch && not badOs && not ghcUnreg + +supportsSplitObjects :: Action Bool +supportsSplitObjects = do + broken <- flag SplitObjectsBroken + ghcUnreg <- flag GhcUnregisterised + goodArch <- anyTargetArch [ "i386", "x86_64", "powerpc", "sparc" ] + goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "darwin", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" ] + return $ not broken && not ghcUnreg && goodArch && goodOs diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 8ee4752..e1dfefa 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -1,9 +1,9 @@ module Oracles.Config.Setting ( Setting (..), SettingList (..), setting, settingList, getSetting, getSettingList, - targetPlatform, targetPlatforms, targetOs, targetOss, notTargetOs, - targetArchs, windowsHost, notWindowsHost, ghcWithInterpreter, - ghcEnableTablesNextToCode, ghcCanonVersion, cmdLineLengthLimit + anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, windowsHost, + ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, + ghcCanonVersion, cmdLineLengthLimit ) where import Base @@ -83,45 +83,37 @@ getSettingList :: SettingList -> ReaderT a Action [String] getSettingList = lift . settingList matchSetting :: Setting -> [String] -> Action Bool -matchSetting key values = do - value <- setting key - return $ value `elem` values +matchSetting key values = fmap (`elem` values) $ setting key -targetPlatforms :: [String] -> Action Bool -targetPlatforms = matchSetting TargetPlatformFull +anyTargetPlatform :: [String] -> Action Bool +anyTargetPlatform = matchSetting TargetPlatformFull -targetPlatform :: String -> Action Bool -targetPlatform s = targetPlatforms [s] +anyTargetOs :: [String] -> Action Bool +anyTargetOs = matchSetting TargetOs -targetOss :: [String] -> Action Bool -targetOss = matchSetting TargetOs +anyTargetArch :: [String] -> Action Bool +anyTargetArch = matchSetting TargetArch -targetOs :: String -> Action Bool -targetOs s = targetOss [s] - -notTargetOs :: String -> Action Bool -notTargetOs = fmap not . targetOs - -targetArchs :: [String] -> Action Bool -targetArchs = matchSetting TargetArch +anyHostOs :: [String] -> Action Bool +anyHostOs = matchSetting HostOs windowsHost :: Action Bool -windowsHost = matchSetting HostOs ["mingw32", "cygwin32"] - -notWindowsHost :: Action Bool -notWindowsHost = fmap not windowsHost +windowsHost = anyHostOs ["mingw32", "cygwin32"] ghcWithInterpreter :: Action Bool ghcWithInterpreter = do - goodOs <- targetOss [ "mingw32", "cygwin32", "linux", "solaris2" - , "freebsd", "dragonfly", "netbsd", "openbsd" - , "darwin", "kfreebsdgnu" ] - goodArch <- targetArchs [ "i386", "x86_64", "powerpc", "sparc" - , "sparc64", "arm" ] + goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" + , "darwin", "kfreebsdgnu" ] + goodArch <- anyTargetArch [ "i386", "x86_64", "powerpc", "sparc" + , "sparc64", "arm" ] return $ goodOs && goodArch ghcEnableTablesNextToCode :: Action Bool -ghcEnableTablesNextToCode = targetArchs ["ia64", "powerpc64"] +ghcEnableTablesNextToCode = notM $ anyTargetArch ["ia64", "powerpc64", "powerpc64le"] + +useLibFFIForAdjustors :: Action Bool +useLibFFIForAdjustors = notM $ anyTargetArch ["i386", "x86_64"] -- Canonicalised GHC version number, used for integer version comparisons. We -- expand GhcMinorVersion to two digits by adding a leading zero if necessary. From git at git.haskell.org Fri Oct 27 00:08:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (a482625) Message-ID: <20171027000828.D4F1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a482625b00358fd14646bac23a7911113c394157/ghc >--------------------------------------------------------------- commit a482625b00358fd14646bac23a7911113c394157 Author: Andrey Mokhov Date: Tue Jan 12 17:37:02 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- a482625b00358fd14646bac23a7911113c394157 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 823e472..4226415 100644 --- a/README.md +++ b/README.md @@ -17,7 +17,7 @@ This is supposed to go into the `shake-build` directory of the GHC source tree. Trying it --------- -Please see the [Preparation][ghc-preparation] on the haskell wiki +Please see the [Preparation][ghc-preparation] on the GHC wiki for general preparation. The preparation steps for the `shake` build system are identical to those for the `make` build system. This means that you don't need to adjust anything if you are already familiar with building ghc using the `make` @@ -54,7 +54,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (#131). +To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality ([#131](https://github.com/snowleopard/shaking-up-ghc/issues/131)). How to contribute From git at git.haskell.org Fri Oct 27 00:08:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #230 from cocreature/stack-shake-0.15.6 (6826d14) Message-ID: <20171027000828.F3D8C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6826d14069396002e5a1fbee6b8c9c1a54cda815/ghc >--------------------------------------------------------------- commit 6826d14069396002e5a1fbee6b8c9c1a54cda815 Merge: cf5ab9a 028ef28 Author: Andrey Mokhov Date: Fri Apr 22 19:44:30 2016 +0100 Merge pull request #230 from cocreature/stack-shake-0.15.6 Add shake-0.15.6 to stack extra-deps >--------------------------------------------------------------- 6826d14069396002e5a1fbee6b8c9c1a54cda815 stack.yaml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:08:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix GhcPrim path in getPackageSources. (c7f9f7c) Message-ID: <20171027000830.077C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7f9f7c349b0498f9a42b4a2c2dbc02082d03645/ghc >--------------------------------------------------------------- commit c7f9f7c349b0498f9a42b4a2c2dbc02082d03645 Author: Andrey Mokhov Date: Thu Sep 24 05:46:13 2015 +0100 Fix GhcPrim path in getPackageSources. >--------------------------------------------------------------- c7f9f7c349b0498f9a42b4a2c2dbc02082d03645 src/Settings.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/src/Settings.hs b/src/Settings.hs index 1a35a94..dab73ed 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -37,14 +37,17 @@ getPackageSources = do srcDirs <- getPkgDataList SrcDirs let buildPath = path -/- "build" - dirs = (buildPath -/- "autogen") : map (packagePath -/-) srcDirs + autogen = buildPath -/- "autogen" + dirs = autogen : map (packagePath -/-) srcDirs (foundSources, missingSources) <- findModuleFiles dirs "*hs" - -- Generated source files live in buildPath and have extension "hs" + -- Generated source files live in buildPath and have extension "hs"... let generatedSources = [ buildPath -/- s <.> "hs" | s <- missingSources ] + -- ...except that GHC/Prim.hs lives in autogen. TODO: fix? + fixGhcPrim = replaceEq (buildPath -/- "GHC/Prim.hs") (autogen -/- "GHC/Prim.hs") - return $ foundSources ++ generatedSources + return $ foundSources ++ fixGhcPrim generatedSources -- findModuleFiles scans a list of given directories and finds files matching a -- given extension pattern (e.g., "*hs") that correspond to modules of the From git at git.haskell.org Fri Oct 27 00:08:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow users to choose which 'make' to use. (43d5847) Message-ID: <20171027000833.287B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/43d5847155ff33dd67929164d49358fc82985944/ghc >--------------------------------------------------------------- commit 43d5847155ff33dd67929164d49358fc82985944 Author: Andrey Mokhov Date: Tue Jan 12 18:12:14 2016 +0000 Allow users to choose which 'make' to use. Fix #157. [skip ci] >--------------------------------------------------------------- 43d5847155ff33dd67929164d49358fc82985944 src/Rules/Actions.hs | 2 +- src/Settings/User.hs | 7 ++++++- 2 files changed, 7 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 338bec3..0600d82 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -105,7 +105,7 @@ runMake dir args = do need [dir -/- "Makefile"] let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir] args + quietly $ cmd Shell (EchoStdout False) makeCommand ["-C", dir] args runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 3cebe13..3d08ecd 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors, splitObjects + verboseCommands, turnWarningsIntoErrors, splitObjects, makeCommand ) where import GHC @@ -101,3 +101,8 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False + +-- | Specify which @make@ command to use, for example set to "gmake" for +-- @GNU make at . +makeCommand :: FilePath +makeCommand = "make" From git at git.haskell.org Fri Oct 27 00:08:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Tweak shake constraint. (98041b2) Message-ID: <20171027000833.385D33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/98041b2607cbe3fab8208bb41c0381bce021fbf2/ghc >--------------------------------------------------------------- commit 98041b2607cbe3fab8208bb41c0381bce021fbf2 Author: Andrey Mokhov Date: Fri Apr 22 19:47:18 2016 +0100 Tweak shake constraint. See #230. >--------------------------------------------------------------- 98041b2607cbe3fab8208bb41c0381bce021fbf2 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index da19de1..a5e6d22 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -124,7 +124,7 @@ executable ghc-shake , extra == 1.4.* , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.9 - , shake == 0.15.6 + , shake >= 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* ghc-options: -Wall From git at git.haskell.org Fri Oct 27 00:08:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code. (28e3a26) Message-ID: <20171027000833.8815A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28e3a26cbaa18b6efc353d543843efd1efb311f0/ghc >--------------------------------------------------------------- commit 28e3a26cbaa18b6efc353d543843efd1efb311f0 Author: Andrey Mokhov Date: Thu Sep 24 05:47:46 2015 +0100 Clean up code. >--------------------------------------------------------------- 28e3a26cbaa18b6efc353d543843efd1efb311f0 src/Predicates.hs | 15 +++++---------- src/Settings/Builders/GhcCabal.hs | 18 +++++++++--------- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages.hs | 8 ++++---- 4 files changed, 19 insertions(+), 24 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 00c12ca..13482b7 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -43,7 +43,7 @@ stage2 :: Predicate stage2 = stage Stage2 notStage0 :: Predicate -notStage0 = fmap not stage0 +notStage0 = notM stage0 -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate @@ -51,12 +51,7 @@ registerPackage = return True splitObjects :: Predicate splitObjects = do - goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages - goodPkg <- fmap not $ package compiler -- We don't split compiler - broken <- getFlag SplitObjectsBroken - ghcUnreg <- getFlag GhcUnregisterised - goodArch <- lift $ targetArchs [ "i386", "x86_64", "powerpc", "sparc" ] - goodOs <- lift $ targetOss [ "mingw32", "cygwin32", "linux", "darwin" - , "solaris2", "freebsd", "dragonfly" - , "netbsd", "openbsd" ] - return $ goodStage && goodPkg && not broken && not ghcUnreg && goodArch && goodOs + goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages + goodPackage <- notM $ package compiler -- We don't split compiler + supported <- lift supportsSplitObjects + return $ goodStage && goodPackage && supported diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index ab65a51..54452d8 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -101,12 +101,12 @@ ccArgs = validating ? ccWarnings -- TODO: should be in a different file ccWarnings :: Args ccWarnings = do - let notClang = fmap not gccIsClang + let gccGe46 = notM $ (flag GccIsClang ||^ flag GccLt46) mconcat [ arg "-Werror" , arg "-Wall" - , gccIsClang ? arg "-Wno-unknown-pragmas" - , notClang ? gccGe46 ? notWindowsHost ? arg "-Werror=unused-but-set-variable" - , notClang ? gccGe46 ? arg "-Wno-error=inline" ] + , flag GccIsClang ? arg "-Wno-unknown-pragmas" + , gccGe46 ? notM windowsHost ? arg "-Werror=unused-but-set-variable" + , gccGe46 ? arg "-Wno-error=inline" ] ldArgs :: Args ldArgs = mempty @@ -147,10 +147,10 @@ customPackageArgs = do mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show nextStage , arg $ "--flags=stage" ++ show nextStage , arg "--disable-library-for-ghci" - , targetOs "openbsd" ? arg "--ld-options=-E" + , anyTargetOs ["openbsd"] ? arg "--ld-options=-E" , flag GhcUnregisterised ? arg "--ghc-option=-DNO_REGS" - , fmap not ghcWithSMP ? arg "--ghc-option=-DNOSMP" - , fmap not ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" + , notM ghcWithSMP ? arg "--ghc-option=-DNOSMP" + , notM ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP" , (threaded `elem` rtsWays) ? notStage0 ? arg "--ghc-option=-optc-DTHREADED_RTS" , ghcWithNativeCodeGen ? arg "--flags=ncg" @@ -158,7 +158,7 @@ customPackageArgs = do notStage0 ? arg "--flags=ghci" , ghcWithInterpreter ? ghcEnableTablesNextToCode ? - fmap not (flag GhcUnregisterised) ? + notM (flag GhcUnregisterised) ? notStage0 ? arg "--ghc-option=-DGHCI_TABLES_NEXT_TO_CODE" , ghcWithInterpreter ? ghciWithDebugger ? @@ -183,7 +183,7 @@ withBuilderKey b = case b of -- Expression 'with Gcc' appends "--with-gcc=/path/to/gcc" and needs Gcc. with :: Builder -> Args with b = specified b ? do - path <- lift $ builderPath b + path <- getBuilderPath b lift $ needBuilder laxDependencies b append [withBuilderKey b ++ path] diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index fae7c1f..7dfe286 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -24,7 +24,7 @@ hsc2HsArgs = builder Hsc2Hs ? do else getSetting ProjectVersionInt mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath - , notWindowsHost ? arg "--cross-safe" + , notM windowsHost ? arg "--cross-safe" , append $ map ("-I" ++) gmpDirs , append $ map ("--cflag=" ++) cFlags , append $ map ("--lflag=" ++) lFlags diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 87f293d..dee0c95 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -17,7 +17,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binPackageDb, binary, cabal, compiler, hoopl, hpc, transformers ] - , notWindowsHost ? notTargetOs "ios" ? append [terminfo] ] + , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages @@ -26,9 +26,9 @@ packagesStage1 = mconcat , append [ array, base, bytestring, containers, deepseq, directory , filepath, ghcPrim, haskeline, integerLibrary, pretty, process , templateHaskell, time ] - , windowsHost ? append [win32] - , notWindowsHost ? append [unix] - , buildHaddock ? append [xhtml] ] + , windowsHost ? append [win32] + , notM windowsHost ? append [unix] + , buildHaddock ? append [xhtml] ] knownPackages :: [Package] knownPackages = defaultKnownPackages ++ userKnownPackages From git at git.haskell.org Fri Oct 27 00:08:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create .build/stage0 for libffi to be moved to. (31dbe92) Message-ID: <20171027000837.4BD463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31dbe92dcfd55c17c8395945050aad240fdd640c/ghc >--------------------------------------------------------------- commit 31dbe92dcfd55c17c8395945050aad240fdd640c Author: Andrey Mokhov Date: Tue Jan 12 21:54:53 2016 +0000 Create .build/stage0 for libffi to be moved to. Fix #160. [skip ci] >--------------------------------------------------------------- 31dbe92dcfd55c17c8395945050aad240fdd640c src/Rules/Libffi.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 7e811ba..7dd0376 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -75,6 +75,8 @@ libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] + createDirectory $ buildRootPath -/- "stage0" + tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] when (length tarballs /= 1) $ putError $ "libffiRules: exactly one libffi tarball expected" From git at git.haskell.org Fri Oct 27 00:08:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CompilerMode Link. (7bc4867) Message-ID: <20171027000837.A05CB3A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7bc48677710d37d905a1e1b005e8113b28abb473/ghc >--------------------------------------------------------------- commit 7bc48677710d37d905a1e1b005e8113b28abb473 Author: Andrey Mokhov Date: Mon Apr 25 23:51:58 2016 +0100 Add CompilerMode Link. See #223. >--------------------------------------------------------------- 7bc48677710d37d905a1e1b005e8113b28abb473 src/Builder.hs | 16 +++++++++------- src/Rules/Program.hs | 3 +-- src/Settings/Builders/Ghc.hs | 34 ++++++++++++++++++++-------------- 3 files changed, 30 insertions(+), 23 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 348e7e9..09e4ab9 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -15,11 +15,14 @@ import Oracles.LookupInPath import Oracles.WindowsPath import Stage --- TODO: Add Link mode? --- | A C or Haskell compiler can be used in two modes: for compiling sources --- into object files, or for extracting source dependencies, e.g. by passing -M --- command line option. -data CompilerMode = Compile | FindDependencies deriving (Show, Eq, Generic) +-- | A compiler can typically be used in one of three modes: +-- 1) Compiling sources into object files. +-- 2) Extracting source dependencies, e.g. by passing -M command line argument. +-- 3) Linking object files & static libraries into an executable. +data CompilerMode = Compile + | FindDependencies + | Link + deriving (Show, Eq, Generic) -- TODO: Do we really need HsCpp builder? Can't we use Cc instead? -- | A 'Builder' is an external command invoked in separate process using 'Shake.cmd' @@ -138,8 +141,7 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- TODO: split into two functions: needBuilder (without laxDependencies) and --- unsafeNeedBuilder (with the laxDependencies parameter) +-- TODO: Get rid of laxDependencies -- we no longer need it (use Shake's skip). -- | Make sure a builder exists on the given path and rebuild it if out of date. -- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 975be85..2cee06c 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -99,8 +99,7 @@ buildBinary rs context@(Context stage package _) bin = do then [ pkgPath package -/- src <.> "hs" | src <- hSrcs ] else objs need $ binDeps ++ libs - -- TODO: Use Link mode instead of Compile. - buildWithResources rs $ Target context (Ghc Compile stage) binDeps [bin] + buildWithResources rs $ Target context (Ghc Link stage) binDeps [bin] synopsis <- interpretInContext context $ getPkgData Synopsis putSuccess $ renderProgram ("'" ++ pkgNameString package ++ "' (" ++ show stage ++ ").") diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a07c512..7152526 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -18,8 +18,9 @@ import Settings.Builders.Common (cIncludeArgs) -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ -- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) +-- TODO: Simplify ghcBuilderArgs :: Args -ghcBuilderArgs = stagedBuilder (Ghc Compile) ? do +ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do output <- getOutput stage <- getStage way <- getWay @@ -27,16 +28,6 @@ ghcBuilderArgs = stagedBuilder (Ghc Compile) ? do let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] buildHi = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf] buildProg = not (buildObj || buildHi) - libs <- getPkgDataList DepExtraLibs - gmpLibs <- if stage > Stage0 && buildProg - then do -- TODO: get this data more gracefully - buildInfo <- lift $ readFileLines gmpBuildInfoPath - let extract s = case stripPrefix "extra-libraries: " s of - Nothing -> [] - Just value -> words value - return $ concatMap extract buildInfo - else return [] - libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -44,14 +35,29 @@ ghcBuilderArgs = stagedBuilder (Ghc Compile) ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , buildProg ? arg "-no-auto-link-packages" - , buildProg ? append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] - , buildProg ? append [ "-optl-L" ++ dir | dir <- libDirs ] + , buildProg ? ghcLinkArgs , not buildProg ? arg "-c" , append =<< getInputs , buildHi ? append ["-fno-code", "-fwrite-interface"] , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] +ghcLinkArgs :: Args +ghcLinkArgs = stagedBuilder (Ghc Link) ? do + stage <- getStage + libs <- getPkgDataList DepExtraLibs + gmpLibs <- if stage > Stage0 + then do -- TODO: get this data more gracefully + buildInfo <- lift $ readFileLines gmpBuildInfoPath + let extract s = case stripPrefix "extra-libraries: " s of + Nothing -> [] + Just value -> words value + return $ concatMap extract buildInfo + else return [] + libDirs <- getPkgDataList DepLibDirs + mconcat [ arg "-no-auto-link-packages" + , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] + , append [ "-optl-L" ++ dir | dir <- libDirs ] ] + needTouchy :: Action () needTouchy = whenM windowsHost $ need [fromJust $ programPath (vanillaContext Stage0 touchy)] From git at git.haskell.org Fri Oct 27 00:08:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add getLibWays to capture context-less ways. (cc3113d) Message-ID: <20171027000837.9FEF03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cc3113db2263c179a4e91440a9369f44a2825980/ghc >--------------------------------------------------------------- commit cc3113db2263c179a4e91440a9369f44a2825980 Author: Andrey Mokhov Date: Thu Sep 24 05:49:11 2015 +0100 Add getLibWays to capture context-less ways. >--------------------------------------------------------------- cc3113db2263c179a4e91440a9369f44a2825980 src/Settings/User.hs | 14 +++++++++----- src/Settings/Ways.hs | 17 ++++++++++------- 2 files changed, 19 insertions(+), 12 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index f9a430c..5b62e39 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,8 +1,8 @@ module Settings.User ( - userArgs, userPackages, userWays, userRtsWays, userTargetDirectory, + userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - dynamicGhcPrograms, laxDependencies + ghcDebugged, dynamicGhcPrograms, laxDependencies ) where import Expression @@ -21,9 +21,9 @@ userPackages = mempty userKnownPackages :: [Package] userKnownPackages = [] --- Control which ways are built -userWays :: Ways -userWays = mempty +-- Control which ways libraries and rts are built +userLibWays :: Ways +userLibWays = mempty userRtsWays :: Ways userRtsWays = mempty @@ -60,6 +60,10 @@ ghciWithDebugger = False ghcProfiled :: Bool ghcProfiled = False +-- TODO: do we need to be able to set this from command line? +ghcDebugged :: Bool +ghcDebugged = False + -- When laxDependencies flag is set to True, dependencies on the GHC executable -- are turned into order-only dependencies to avoid needless recompilation when -- making changes to GHC's sources. In certain situations this can lead to build diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index cafed64..ad42cea 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,26 +1,29 @@ -module Settings.Ways (getWays, getRtsWays) where +module Settings.Ways (getWays, getLibWays, getRtsWays) where import Expression import Predicates import Settings.User -- Combining default ways with user modifications +getLibWays :: Expr [Way] +getLibWays = fromDiffExpr $ defaultLibWays <> userLibWays + +-- In Stage0 we only build vanilla getWays :: Expr [Way] -getWays = fromDiffExpr $ defaultWays <> userWays +getWays = mconcat [ stage0 ? return [vanilla], notStage0 ? getLibWays ] getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays -- These are default ways -defaultWays :: Ways -defaultWays = mconcat - [ append [vanilla] -- always build vanilla - , notStage0 ? append [profiling] +defaultLibWays :: Ways +defaultLibWays = mconcat + [ append [vanilla, profiling] , platformSupportsSharedLibs ? append [dynamic] ] defaultRtsWays :: Ways defaultRtsWays = do - ways <- getWays + ways <- getLibWays mconcat [ append [ logging, debug, threaded, threadedDebug, threadedLogging ] , (profiling `elem` ways) ? append [threadedProfiling] From git at git.haskell.org Fri Oct 27 00:08:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't move from a temporary directory. (86f3052) Message-ID: <20171027000841.469323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86f3052c2cd738427136899bfe3a47210c4d98a5/ghc >--------------------------------------------------------------- commit 86f3052c2cd738427136899bfe3a47210c4d98a5 Author: Andrey Mokhov Date: Tue Jan 12 22:22:34 2016 +0000 Don't move from a temporary directory. Fix #156. >--------------------------------------------------------------- 86f3052c2cd738427136899bfe3a47210c4d98a5 src/Rules/Libffi.hs | 14 +++++--------- 1 file changed, 5 insertions(+), 9 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 7dd0376..0c38cd2 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -27,9 +27,6 @@ libffiBuild = buildRootPath -/- "stage0/libffi" libffiLibrary :: FilePath libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" -libffiMakefile :: FilePath -libffiMakefile = libffiBuild -/- "Makefile.in" - fixLibffiMakefile :: String -> String fixLibffiMakefile = unlines . map ( replace "-MD" "-MMD" @@ -75,7 +72,7 @@ libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] - createDirectory $ buildRootPath -/- "stage0" + createDirectory $ buildRootPath -/- stageString Stage0 tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] when (length tarballs /= 1) $ @@ -85,12 +82,11 @@ libffiRules = do need tarballs let libname = dropExtension . dropExtension . takeFileName $ head tarballs - withTempDir $ \tmpDir -> do - let unifiedTmpDir = unifyPath tmpDir - build $ fullTarget libffiTarget Tar tarballs [unifiedTmpDir] - moveDirectory (unifiedTmpDir -/- libname) libffiBuild + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + actionFinally (moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] - fixFile libffiMakefile fixLibffiMakefile + fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile forM_ ["config.guess", "config.sub"] $ \file -> copyFile file (libffiBuild -/- file) From git at git.haskell.org Fri Oct 27 00:08:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop experimental code for #174. (64ae7fe) Message-ID: <20171027000841.9361D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64ae7fe8fd907dffd6b6221b95111d24f1bf6372/ghc >--------------------------------------------------------------- commit 64ae7fe8fd907dffd6b6221b95111d24f1bf6372 Author: Andrey Mokhov Date: Tue Apr 26 00:25:12 2016 +0100 Drop experimental code for #174. >--------------------------------------------------------------- 64ae7fe8fd907dffd6b6221b95111d24f1bf6372 src/Rules/Compile.hs | 24 ++++-------------------- src/Settings/Builders/Ghc.hs | 12 ++++-------- src/Settings/User.hs | 13 ++++--------- 3 files changed, 12 insertions(+), 37 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index a3c970d..93503bd 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,21 +12,9 @@ compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context - path "*" <.> hisuf way %> \hi -> - if compileInterfaceFilesSeparately - then do - (src, deps) <- dependencies path $ hi -<.> osuf way - need $ src : deps - buildWithResources rs $ Target context (Ghc Compile stage) [src] [hi] - else need [ hi -<.> osuf way ] + path "*" <.> hisuf way %> \hi -> need [ hi -<.> osuf way ] - path "*" <.> hibootsuf way %> \hiboot -> - if compileInterfaceFilesSeparately - then do - (src, deps) <- dependencies path $ hiboot -<.> obootsuf way - need $ src : deps - buildWithResources rs $ Target context (Ghc Compile stage) [src] [hiboot] - else need [ hiboot -<.> obootsuf way ] + path "*" <.> hibootsuf way %> \hiboot -> need [ hiboot -<.> obootsuf way ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) path "*" <.> osuf way %> \obj -> do @@ -36,15 +24,11 @@ compilePackage rs context at Context {..} = do need $ src : deps build $ Target context (Cc Compile stage) [src] [obj] else do - if compileInterfaceFilesSeparately && "//*.hs" ?== src - then need $ (obj -<.> hisuf way) : src : deps - else need $ src : deps + need $ src : deps buildWithResources rs $ Target context (Ghc Compile stage) [src] [obj] -- TODO: get rid of these special cases path "*" <.> obootsuf way %> \obj -> do (src, deps) <- dependencies path obj - if compileInterfaceFilesSeparately - then need $ (obj -<.> hibootsuf way) : src : deps - else need $ src : deps + need $ src : deps buildWithResources rs $ Target context (Ghc Compile stage) [src] [obj] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 7152526..8dabda6 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -18,16 +18,13 @@ import Settings.Builders.Common (cIncludeArgs) -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ -- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) --- TODO: Simplify ghcBuilderArgs :: Args ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do output <- getOutput stage <- getStage way <- getWay when (stage > Stage0) . lift $ needTouchy - let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] - buildHi = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf] - buildProg = not (buildObj || buildHi) + let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -35,11 +32,10 @@ ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , buildProg ? ghcLinkArgs - , not buildProg ? arg "-c" + , not buildObj ? ghcLinkArgs + , buildObj ? arg "-c" , append =<< getInputs - , buildHi ? append ["-fno-code", "-fwrite-interface"] - , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] + , arg "-o", arg =<< getOutput ] ghcLinkArgs :: Args ghcLinkArgs = stagedBuilder (Ghc Link) ? do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 6fc5536..9f2302b 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,9 +1,8 @@ module Settings.User ( - buildRootPath, trackBuildSystem, compileInterfaceFilesSeparately, - userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, - integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - ghcDebugged, dynamicGhcPrograms, laxDependencies, verboseCommands, - turnWarningsIntoErrors, splitObjects + buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays, + userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, + ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, + laxDependencies, verboseCommands, turnWarningsIntoErrors, splitObjects ) where import Base @@ -94,7 +93,3 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False - --- | Decouple the compilation of @*.hi@ and @*.o@ files by setting to True. -compileInterfaceFilesSeparately :: Bool -compileInterfaceFilesSeparately = False From git at git.haskell.org Fri Oct 27 00:08:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement all modes of GenPrimopCode builder. (1a17fee) Message-ID: <20171027000841.B6DFB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a17fee2b8dc82a4b4778cf1f3219fdad584db8d/ghc >--------------------------------------------------------------- commit 1a17fee2b8dc82a4b4778cf1f3219fdad584db8d Author: Andrey Mokhov Date: Thu Sep 24 05:49:39 2015 +0100 Implement all modes of GenPrimopCode builder. >--------------------------------------------------------------- 1a17fee2b8dc82a4b4778cf1f3219fdad584db8d src/Settings/Builders/GenPrimopCode.hs | 23 +++++++++++++++++++++-- 1 file changed, 21 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/GenPrimopCode.hs b/src/Settings/Builders/GenPrimopCode.hs index 711aa80..6de1f47 100644 --- a/src/Settings/Builders/GenPrimopCode.hs +++ b/src/Settings/Builders/GenPrimopCode.hs @@ -1,8 +1,27 @@ module Settings.Builders.GenPrimopCode (genPrimopCodeArgs) where import Expression -import Predicates (builder) +import Predicates (builder, file) -- Stdin/stdout are handled in a special way. See Rules/Actions.hs. +-- TODO: Do we want to keep "--usage"? It seems to be unused. genPrimopCodeArgs :: Args -genPrimopCodeArgs = builder GenPrimopCode ? arg "--make-haskell-wrappers" +genPrimopCodeArgs = builder GenPrimopCode ? mconcat + [ file "//PrimopWrappers.hs" ? arg "--make-haskell-wrappers" + , file "//Prim.hs" ? arg "--make-haskell-source" + , file "//primop-data-decl.hs-incl" ? arg "--data-decl" + , file "//primop-tag.hs-incl" ? arg "--primop-tag" + , file "//primop-list.hs-incl" ? arg "--primop-list" + , file "//primop-has-side-effects.hs-incl" ? arg "--has-side-effects" + , file "//primop-out-of-line.hs-incl" ? arg "--out-of-line" + , file "//primop-commutable.hs-incl" ? arg "--commutable" + , file "//primop-code-size.hs-incl" ? arg "--code-size" + , file "//primop-can-fail.hs-incl" ? arg "--can-fail" + , file "//primop-strictness.hs-incl" ? arg "--strictness" + , file "//primop-fixity.hs-incl" ? arg "--fixity" + , file "//primop-primop-info.hs-incl" ? arg "--primop-primop-info" + , file "//primop-vector-uniques.hs-incl" ? arg "--primop-vector-uniques" + , file "//primop-vector-tys.hs-incl" ? arg "--primop-vector-tys" + , file "//primop-vector-tys-exports.hs-incl" ? arg "--primop-vector-tys-exports" + , file "//primop-vector-tycons.hs-incl" ? arg "--primop-vector-tycons" + , file "//primop-usage.hs-incl" ? arg "--usage" ] From git at git.haskell.org Fri Oct 27 00:08:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add removeDirectory to Rules/Actions, seems to fit (db11fb0) Message-ID: <20171027000845.9E4933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db11fb04e50c4cc46a2e3286adf0b67acbc82b47/ghc >--------------------------------------------------------------- commit db11fb04e50c4cc46a2e3286adf0b67acbc82b47 Author: Neil Mitchell Date: Tue Jan 12 22:33:21 2016 +0000 Add removeDirectory to Rules/Actions, seems to fit >--------------------------------------------------------------- db11fb04e50c4cc46a2e3286adf0b67acbc82b47 src/Rules/Actions.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 0600d82..a968160 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,6 +1,6 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( - build, buildWithResources, copyFile, createDirectory, moveDirectory, + build, buildWithResources, copyFile, createDirectory, removeDirectory, moveDirectory, fixFile, runConfigure, runMake, runBuilder, makeExecutable ) where @@ -74,6 +74,11 @@ createDirectory dir = do putBuild $ "| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir +removeDirectory :: FilePath -> Action () +removeDirectory dir = do + putBuild $ "| Remove directory " ++ dir + liftIO $ IO.removeDirectoryRecursive dir + -- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do From git at git.haskell.org Fri Oct 27 00:08:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (366b35b) Message-ID: <20171027000846.0A4773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/366b35b27d1a33cb2a752fb0b6c927658496047e/ghc >--------------------------------------------------------------- commit 366b35b27d1a33cb2a752fb0b6c927658496047e Author: Andrey Mokhov Date: Tue Apr 26 00:46:58 2016 +0100 Minor revision. >--------------------------------------------------------------- 366b35b27d1a33cb2a752fb0b6c927658496047e src/Settings/Builders/Ghc.hs | 23 +++++++++++++---------- 1 file changed, 13 insertions(+), 10 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 8dabda6..37fbc34 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,6 +2,8 @@ module Settings.Builders.Ghc ( ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs ) where +import Control.Monad.Trans.Reader + import Base import Expression import GHC @@ -20,11 +22,7 @@ import Settings.Builders.Common (cIncludeArgs) -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) ghcBuilderArgs :: Args ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do - output <- getOutput - stage <- getStage - way <- getWay - when (stage > Stage0) . lift $ needTouchy - let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] + needTouchy mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -32,8 +30,8 @@ ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , not buildObj ? ghcLinkArgs - , buildObj ? arg "-c" + , ghcLinkArgs + , stagedBuilder (Ghc Compile) ? arg "-c" , append =<< getInputs , arg "-o", arg =<< getOutput ] @@ -54,10 +52,15 @@ ghcLinkArgs = stagedBuilder (Ghc Link) ? do , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ dir | dir <- libDirs ] ] -needTouchy :: Action () -needTouchy = - whenM windowsHost $ need [fromJust $ programPath (vanillaContext Stage0 touchy)] +-- TODO: Add Touchy builder and use needBuilder. +needTouchy :: ReaderT Target Action () +needTouchy = do + stage <- getStage + windows <- lift $ windowsHost + lift . when (stage > Stage0 && windows) $ + need [fromJust $ programPath (vanillaContext Stage0 touchy)] +-- TODO: Add GhcSplit builder and use needBuilder. splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do lift $ need [ghcSplit] From git at git.haskell.org Fri Oct 27 00:08:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix untracked .hs-incl dependencies. (9b9f7d2) Message-ID: <20171027000846.1D2063A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b9f7d2fd05b4bb146d794bd9fd1e67ba8311cb2/ghc >--------------------------------------------------------------- commit 9b9f7d2fd05b4bb146d794bd9fd1e67ba8311cb2 Author: Andrey Mokhov Date: Thu Sep 24 05:50:17 2015 +0100 Fix untracked .hs-incl dependencies. >--------------------------------------------------------------- 9b9f7d2fd05b4bb146d794bd9fd1e67ba8311cb2 src/Rules/Dependencies.hs | 22 +++++++++++++++++++++- 1 file changed, 21 insertions(+), 1 deletion(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index c9b5b89..8fd9ca8 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -1,6 +1,7 @@ module Rules.Dependencies (buildPackageDependencies) where import Expression +import GHC import Oracles import Rules.Actions import Rules.Resources @@ -30,4 +31,23 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need $ hDepFile : cDepFiles -- need all for more parallelism cDeps <- fmap concat $ mapM readFile' cDepFiles hDeps <- readFile' hDepFile - writeFileChanged file $ cDeps ++ hDeps + -- TODO: very ugly and fragile + let hsIncl hs incl = buildPath -/- hs <.> "o" ++ " : " + ++ buildPath -/- incl ++ "\n" + extraDeps = if pkg /= compiler then [] else + hsIncl "PrelNames" "primop-vector-uniques.hs-incl" + ++ hsIncl "PrimOp" "primop-data-decl.hs-incl" + ++ hsIncl "PrimOp" "primop-tag.hs-incl" + ++ hsIncl "PrimOp" "primop-list.hs-incl" + ++ hsIncl "PrimOp" "primop-strictness.hs-incl" + ++ hsIncl "PrimOp" "primop-fixity.hs-incl" + ++ hsIncl "PrimOp" "primop-primop-info.hs-incl" + ++ hsIncl "PrimOp" "primop-out-of-line.hs-incl" + ++ hsIncl "PrimOp" "primop-has-side-effects.hs-incl" + ++ hsIncl "PrimOp" "primop-can-fail.hs-incl" + ++ hsIncl "PrimOp" "primop-code-size.hs-incl" + ++ hsIncl "PrimOp" "primop-commutable.hs-incl" + ++ hsIncl "TysPrim" "primop-vector-tys-exports.hs-incl" + ++ hsIncl "TysPrim" "primop-vector-tycons.hs-incl" + ++ hsIncl "TysPrim" "primop-vector-tys.hs-incl" + writeFileChanged file $ cDeps ++ hDeps ++ extraDeps From git at git.haskell.org Fri Oct 27 00:08:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify fixLibffiMakefile, no need to chop into lines first (07d94c9) Message-ID: <20171027000849.C961B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/07d94c918a4fa0f7f5ea43496f4a3e6e95662c08/ghc >--------------------------------------------------------------- commit 07d94c918a4fa0f7f5ea43496f4a3e6e95662c08 Author: Neil Mitchell Date: Tue Jan 12 22:33:42 2016 +0000 Simplify fixLibffiMakefile, no need to chop into lines first >--------------------------------------------------------------- 07d94c918a4fa0f7f5ea43496f4a3e6e95662c08 src/Rules/Libffi.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0c38cd2..63bc1e8 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -28,11 +28,11 @@ libffiLibrary :: FilePath libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" fixLibffiMakefile :: String -> String -fixLibffiMakefile = unlines . map - ( replace "-MD" "-MMD" +fixLibffiMakefile = + replace "-MD" "-MMD" . replace "@toolexeclibdir@" "$(libdir)" . replace "@INSTALL@" "$(subst ../install-sh,C:/msys/home/chEEtah/ghc/install-sh, at INSTALL@)" - ) . lines + -- TODO: remove code duplication (see Settings/Builders/GhcCabal.hs) configureEnvironment :: Action [CmdOption] From git at git.haskell.org Fri Oct 27 00:08:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement new generate rules. (90301e1) Message-ID: <20171027000850.4CC4E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90301e1bd2143ed9f04a1385024de60ff4a68009/ghc >--------------------------------------------------------------- commit 90301e1bd2143ed9f04a1385024de60ff4a68009 Author: Andrey Mokhov Date: Thu Sep 24 05:50:46 2015 +0100 Implement new generate rules. >--------------------------------------------------------------- 90301e1bd2143ed9f04a1385024de60ff4a68009 src/Rules/Generate.hs | 104 +++++++++++++++++++++++++++++--------------------- 1 file changed, 60 insertions(+), 44 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 90301e1bd2143ed9f04a1385024de60ff4a68009 From git at git.haskell.org Fri Oct 27 00:08:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge builder, stagedBuilder, builderGhc/Cc into builder. (e532385) Message-ID: <20171027000850.7FD5C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e53238583d64f7218e57d055651087f594e3a98c/ghc >--------------------------------------------------------------- commit e53238583d64f7218e57d055651087f594e3a98c Author: Andrey Mokhov Date: Tue Apr 26 01:04:04 2016 +0100 Merge builder, stagedBuilder, builderGhc/Cc into builder. See #223. >--------------------------------------------------------------- e53238583d64f7218e57d055651087f594e3a98c src/Predicates.hs | 33 ++++++++++++--------------------- src/Settings/Builders/Cc.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Flavours/Quick.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 4 ++-- src/Settings/Packages/Directory.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 4 ++-- src/Settings/Packages/GhcCabal.hs | 4 ++-- src/Settings/Packages/Hp2ps.hs | 4 ++-- src/Settings/Packages/IntegerGmp.hs | 4 ++-- src/Settings/Packages/IservBin.hs | 4 ++-- src/Settings/Packages/Rts.hs | 6 +++--- src/Settings/Packages/RunGhc.hs | 4 ++-- src/Settings/Packages/Touchy.hs | 4 ++-- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/User.hs | 2 +- 18 files changed, 47 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e53238583d64f7218e57d055651087f594e3a98c From git at git.haskell.org Fri Oct 27 00:08:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use removeDirectory where appropriate (ccc16b2) Message-ID: <20171027000853.62F523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccc16b21b7d255b692ffbc9b0c96167bec2ed77e/ghc >--------------------------------------------------------------- commit ccc16b21b7d255b692ffbc9b0c96167bec2ed77e Author: Neil Mitchell Date: Tue Jan 12 22:33:55 2016 +0000 Use removeDirectory where appropriate >--------------------------------------------------------------- ccc16b21b7d255b692ffbc9b0c96167bec2ed77e src/Rules/Libffi.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 63bc1e8..1d761ff 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -71,7 +71,7 @@ libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - liftIO $ removeFiles libffiBuild ["//*"] + removeDirectory libffiBuild createDirectory $ buildRootPath -/- stageString Stage0 tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] From git at git.haskell.org Fri Oct 27 00:08:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new builder HsCpp. (45d41a5) Message-ID: <20171027000854.5DCC83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45d41a568b324f37d992fdcd616726959d4c439d/ghc >--------------------------------------------------------------- commit 45d41a568b324f37d992fdcd616726959d4c439d Author: Andrey Mokhov Date: Thu Sep 24 12:44:38 2015 +0100 Add new builder HsCpp. >--------------------------------------------------------------- 45d41a568b324f37d992fdcd616726959d4c439d cfg/system.config.in | 2 ++ src/Builder.hs | 2 ++ src/Rules/Actions.hs | 5 +++++ src/Settings/Args.hs | 2 ++ src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/HsCpp.hs | 17 +++++++++++++++++ src/Settings/Builders/Hsc2Hs.hs | 2 +- 7 files changed, 30 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 87d2b93..e85788b 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -23,6 +23,8 @@ hsc2hs = @hardtop@/inplace/bin/hsc2hs genprimopcode = @hardtop@/inplace/bin/genprimopcode +hs-cpp = @HaskellCPPCmd@ @HaskellCPPArgs@ + unlit = @hardtop@/inplace/lib/unlit ghc-split = @hardtop@/inplace/lib/ghc-split diff --git a/src/Builder.hs b/src/Builder.hs index a6521a1..e1c69be 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -30,6 +30,7 @@ data Builder = Alex | Haddock | Happy | HsColour + | HsCpp | Hsc2Hs | Ld | Unlit @@ -58,6 +59,7 @@ builderKey builder = case builder of Haddock -> "haddock" HsColour -> "hscolour" Hsc2Hs -> "hsc2hs" + HsCpp -> "hs-cpp" Ld -> "ld" Unlit -> "unlit" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 1e0472a..8214112 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -32,6 +32,11 @@ buildWithResources rs target = do forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> unit . cmd [path] $ persistentArgs ++ argsChunk + HsCpp -> do + let file = head $ Target.files target -- TODO: ugly + Stdout output <- cmd [path] argList + writeFileChanged file output + GenPrimopCode -> do let src = head $ Target.sources target -- TODO: ugly file = head $ Target.files target diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 349668a..231f5ed 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -11,6 +11,7 @@ import Settings.Builders.GhcPkg import Settings.Builders.Haddock import Settings.Builders.Happy import Settings.Builders.Hsc2Hs +import Settings.Builders.HsCpp import Settings.Builders.Ld import Settings.User @@ -41,4 +42,5 @@ defaultArgs = mconcat , haddockArgs , happyArgs , hsc2HsArgs + , hsCppArgs , ldArgs ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 54452d8..b68da27 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,6 +1,6 @@ module Settings.Builders.GhcCabal ( cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, - ccArgs, ccWarnings, argStagedSettingList + ccArgs, cppArgs, ccWarnings, argStagedSettingList ) where import Expression diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs new file mode 100644 index 0000000..da104cc --- /dev/null +++ b/src/Settings/Builders/HsCpp.hs @@ -0,0 +1,17 @@ +module Settings.Builders.HsCpp (hsCppArgs) where + +import Expression +import Predicates (builder) +import Settings.Builders.GhcCabal + +-- TODO: why process the result with grep -v '^#pragma GCC'? No such lines! +hsCppArgs :: Args +hsCppArgs = builder HsCpp ? do + stage <- getStage + src <- getSource + mconcat [ arg "-P" + , cppArgs + , arg $ "-Icompiler/stage" ++ show stage + , arg "-x" + , arg "c" + , arg src ] diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 7dfe286..dcf44fc 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -4,7 +4,7 @@ import Expression import Oracles import Predicates (builder, stage0, notStage0) import Settings -import Settings.Builders.GhcCabal +import Settings.Builders.GhcCabal hiding (cppArgs) hsc2HsArgs :: Args hsc2HsArgs = builder Hsc2Hs ? do From git at git.haskell.org Fri Oct 27 00:08:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop workaround a Shake getDirectoryFiles bug. (ab5a70f) Message-ID: <20171027000854.808E63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ab5a70fd6fe2e175749b6c55b6395871fe069c77/ghc >--------------------------------------------------------------- commit ab5a70fd6fe2e175749b6c55b6395871fe069c77 Author: Andrey Mokhov Date: Tue Apr 26 01:28:55 2016 +0100 Drop workaround a Shake getDirectoryFiles bug. >--------------------------------------------------------------- ab5a70fd6fe2e175749b6c55b6395871fe069c77 src/Rules/Library.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b74baf8..8e09162 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -97,9 +97,5 @@ extraObjects :: Context -> Action [FilePath] extraObjects (Context _ package _) | package == integerGmp = do orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? - -- FIXME: simplify after Shake's getDirectoryFiles bug is fixed, #168 - exists <- doesDirectoryExist gmpObjects - if exists - then map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] - else return [] + map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:08:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #156, ensure the entire piece is under a removeFiles so we always clean up the garbage (3a88dc5) Message-ID: <20171027000856.E18423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3a88dc56215804ab95d9c5eb3127de6f4c7a5f0b/ghc >--------------------------------------------------------------- commit 3a88dc56215804ab95d9c5eb3127de6f4c7a5f0b Author: Neil Mitchell Date: Tue Jan 12 22:34:39 2016 +0000 #156, ensure the entire piece is under a removeFiles so we always clean up the garbage >--------------------------------------------------------------- 3a88dc56215804ab95d9c5eb3127de6f4c7a5f0b src/Rules/Libffi.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 1d761ff..8bcfdae 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -82,9 +82,10 @@ libffiRules = do need tarballs let libname = dropExtension . dropExtension . takeFileName $ head tarballs - build $ fullTarget libffiTarget Tar tarballs [buildRootPath] - actionFinally (moveDirectory (buildRootPath -/- libname) libffiBuild) $ - removeFiles buildRootPath [libname "*"] + actionFinally (do + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile From git at git.haskell.org Fri Oct 27 00:08:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more thoughts. (14e4942) Message-ID: <20171027000858.61AFC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14e49425f1760d8425ab518c0a49644e415c8173/ghc >--------------------------------------------------------------- commit 14e49425f1760d8425ab518c0a49644e415c8173 Author: Andrey Mokhov Date: Thu Sep 24 12:44:59 2015 +0100 Add more thoughts. >--------------------------------------------------------------- 14e49425f1760d8425ab518c0a49644e415c8173 doc/meeting-25-September-2015.txt | 19 +++++++++++++++++-- 1 file changed, 17 insertions(+), 2 deletions(-) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt index 6ee4297..caf0e8e 100644 --- a/doc/meeting-25-September-2015.txt +++ b/doc/meeting-25-September-2015.txt @@ -3,7 +3,20 @@ Shaking up GHC meeting, 25 September 2015 Things to discuss: ================================================ -1. Better names for build stages +1. Progress report + + +++ Dealing with seemingly dead-code artefacts of the old build systems. I used to carefully migrate all code to the new build system, but it is getting more in the way of readability. New proposal: drop all such suspicious instances and bring them back only if things break. Example: + +C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe -E -undef -traditional -P -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -Icompiler/stage2 -x c compiler/prelude/primops.txt.pp | grep -v '^#pragma GCC' > compiler/stage2/build/primops.txt + +But primops.txt.pp has no lines containing #pragma GCC! Dead code? + +++ Zero build is 7 seconds + +++ .hs-incl includes are currently not tracked properly (e.g. ghc -MM does not list them). See Dependencies.hs + +++ Better names for build stages * Currently we have Stage0, Stage1, etc. It is not particularly clear from the names what they stand for. We no longer need to stick to @@ -21,8 +34,10 @@ i. Unclear abstractions Builder/BuildRule... ii. Limits to build parallelism: GHC crashes during parallel builds. Also ghc-pkg and ghc-cabal are apparently not thread-safe, so I had to use Shake resources to limit the parallelism... +iii. Discuss the need for command line options, e.g. make GhcDebugged=YES. This is a bit annoying to implement since Settings.User seems fairly readable, but recompiling the build systems for changing a flag may be annoying too. + -2. Do we need a name for the new build system? +iv. Do we need a name for the new build system? * At least we need a name for the folder in the GHC tree From git at git.haskell.org Fri Oct 27 00:08:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:08:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comment on unicode build info. (ed4cdd8) Message-ID: <20171027000858.964DA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ed4cdd8c37bcb13e7bf5dda89b1945a29e2ee1bf/ghc >--------------------------------------------------------------- commit ed4cdd8c37bcb13e7bf5dda89b1945a29e2ee1bf Author: Andrey Mokhov Date: Tue Apr 26 01:42:15 2016 +0100 Add comment on unicode build info. [skip ci] >--------------------------------------------------------------- ed4cdd8c37bcb13e7bf5dda89b1945a29e2ee1bf src/Rules/Actions.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5f0fac0..3b12249 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -237,7 +237,8 @@ renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot] -- Minimum total width of the box in characters minimumBoxWidth = 32 - -- FIXME: See Shake #364. + -- TODO: Make this setting configurable? Setting to True by default seems + -- to work poorly with many fonts. useUnicode = False -- Characters to draw the box From git at git.haskell.org Fri Oct 27 00:09:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #154 from snowleopard/angerman/feature/build-info-flags (57c6497) Message-ID: <20171027000900.748F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57c6497776b08bd0548a094fa96b21977ae54254/ghc >--------------------------------------------------------------- commit 57c6497776b08bd0548a094fa96b21977ae54254 Merge: 86f3052 f794e73 Author: Andrey Mokhov Date: Tue Jan 12 22:41:37 2016 +0000 Merge pull request #154 from snowleopard/angerman/feature/build-info-flags Add Advanced render box styles [skip ci] >--------------------------------------------------------------- 57c6497776b08bd0548a094fa96b21977ae54254 shaking-up-ghc.cabal | 1 + src/Base.hs | 52 ++++++++++++++++++++++++++++++++++-- src/Main.hs | 7 ++++- src/Oracles/Config/CmdLineFlag.hs | 56 +++++++++++++++++++++++++++++++++++++++ src/Rules/Actions.hs | 20 +++++--------- src/Rules/Library.hs | 9 +++---- src/Rules/Program.hs | 11 ++++---- 7 files changed, 129 insertions(+), 27 deletions(-) From git at git.haskell.org Fri Oct 27 00:09:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ArSupportsAtFile, BuildPlatform, HostPlatform, TargetPlatform flags. (f164cdc) Message-ID: <20171027000901.E53EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f164cdc5a83432f5f4c156be4a1d518650cb1045/ghc >--------------------------------------------------------------- commit f164cdc5a83432f5f4c156be4a1d518650cb1045 Author: Andrey Mokhov Date: Thu Sep 24 23:41:37 2015 +0100 Add ArSupportsAtFile, BuildPlatform, HostPlatform, TargetPlatform flags. >--------------------------------------------------------------- f164cdc5a83432f5f4c156be4a1d518650cb1045 cfg/system.config.in | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index e85788b..09ea1fa 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -23,7 +23,8 @@ hsc2hs = @hardtop@/inplace/bin/hsc2hs genprimopcode = @hardtop@/inplace/bin/genprimopcode -hs-cpp = @HaskellCPPCmd@ @HaskellCPPArgs@ +hs-cpp = @HaskellCPPCmd@ +hs-cpp-args = @HaskellCPPArgs@ unlit = @hardtop@/inplace/lib/unlit ghc-split = @hardtop@/inplace/lib/ghc-split @@ -37,8 +38,9 @@ hscolour = @HSCOLOUR@ # Information about builders: #============================ -gcc-is-clang = @GccIsClang@ -gcc-lt-46 = @GccLT46@ +gcc-is-clang = @GccIsClang@ +gcc-lt-46 = @GccLT46@ +ar-supports-at-file = @ArSupportsAtFile@ # Build options: #=============== @@ -50,15 +52,24 @@ ghc-unregisterised = @Unregisterised@ ghc-source-path = @hardtop@ leading-underscore = @LeadingUnderscore@ -# Information about host and target systems: -#=========================================== +# Information about build, host and target systems: +#================================================== -target-os = @TargetOS_CPP@ -target-arch = @TargetArch_CPP@ -target-platform-full = @TargetPlatformFull@ +build-platform = @BuildPlatform@ +build-arch = @BuildArch_CPP@ +build-os = @BuildOS_CPP@ +build-vendor = @BuildVendor_CPP@ -host-os = @HostOS_CPP@ +host-platform = @HostPlatform@ host-arch = @HostArch_CPP@ +host-os = @HostOS_CPP@ +host-vendor = @HostVendor_CPP@ + +target-platform = @TargetPlatform@ +target-platform-full = @TargetPlatformFull@ +target-arch = @TargetArch_CPP@ +target-os = @TargetOS_CPP@ +target-vendor = @TargetVendor_CPP@ cross-compiling = @CrossCompiling@ From git at git.haskell.org Fri Oct 27 00:09:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop laxDependencies. To be replaced by Shake's skip feature. (8d0581e) Message-ID: <20171027000902.349E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8d0581ed811c1b180981d4a767e3862e5dd490de/ghc >--------------------------------------------------------------- commit 8d0581ed811c1b180981d4a767e3862e5dd490de Author: Andrey Mokhov Date: Tue Apr 26 09:44:41 2016 +0100 Drop laxDependencies. To be replaced by Shake's skip feature. >--------------------------------------------------------------- 8d0581ed811c1b180981d4a767e3862e5dd490de src/Builder.hs | 18 ++++-------------- src/Predicates.hs | 1 - src/Rules/Actions.hs | 6 +++--- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Test.hs | 6 +++--- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/User.hs | 9 +-------- 8 files changed, 14 insertions(+), 32 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 09e4ab9..8f711e0 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -141,21 +141,11 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- TODO: Get rid of laxDependencies -- we no longer need it (use Shake's skip). --- | Make sure a builder exists on the given path and rebuild it if out of date. --- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of --- date (can save a lot of build time when changing GHC). -needBuilder :: Bool -> Builder -> Action () -needBuilder laxDependencies builder = when (isInternal builder) $ do +-- | Make sure a Builder exists on the given path and rebuild it if out of date. +needBuilder :: Builder -> Action () +needBuilder builder = when (isInternal builder) $ do path <- builderPath builder - if laxDependencies && allowOrderOnlyDependency builder - then orderOnly [path] - else need [path] - where - allowOrderOnlyDependency :: Builder -> Bool - allowOrderOnlyDependency = \case - Ghc _ _ -> True - _ -> False + need [path] -- Instances for storing in the Shake database instance Binary CompilerMode diff --git a/src/Predicates.hs b/src/Predicates.hs index 1f87386..0ae18e9 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -15,7 +15,6 @@ stage s = (s ==) <$> getStage package :: Package -> Predicate package p = (p ==) <$> getPackage --- TODO: Also add needBuilder, builderPath, etc. -- | Is a particular builder being used? class BuilderLike a where builder :: a -> Predicate diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 3b12249..10bcbd2 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -24,7 +24,7 @@ import Target -- built (that is, track changes in the build system). buildWithResources :: [(Resource, Int)] -> Target -> Action () buildWithResources rs target at Target {..} = do - needBuilder laxDependencies builder + needBuilder builder path <- builderPath builder argList <- interpret target getArgs verbose <- interpret target verboseCommands @@ -140,14 +140,14 @@ applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch need [file] - needBuilder False Patch -- TODO: add a specialised version ~needBuilderFalse? + needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do - needBuilder laxDependencies builder + needBuilder builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ show builder ++ note diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index ae73104..99dda79 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -42,7 +42,7 @@ configureEnvironment = do , builderEnv "NM" Nm ] where builderEnv var bld = do - needBuilder False bld + needBuilder bld path <- builderPath bld return $ AddEnv var path diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 18c328b..8dce6d1 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -53,7 +53,7 @@ configureEnvironment = do , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ] where builderEnv var bld = do - needBuilder False bld + needBuilder bld path <- builderPath bld return $ AddEnv var path diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 0604236..7faf62d 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -15,9 +15,9 @@ import Settings.User testRules :: Rules () testRules = do "validate" ~> do - needBuilder False $ Ghc Compile Stage2 -- TODO: get rid of False - needBuilder False $ GhcPkg Stage1 - needBuilder False $ Hpc + needBuilder $ Ghc Compile Stage2 + needBuilder $ GhcPkg Stage1 + needBuilder Hpc runMakeVerbose "testsuite/tests" ["fast"] "test" ~> do diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 1750604..9f6c6e2 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -127,7 +127,7 @@ with :: Builder -> Args with b = specified b ? do top <- getTopDirectory path <- getBuilderPath b - lift $ needBuilder laxDependencies b + lift $ needBuilder b append [withBuilderKey b ++ top -/- path] withStaged :: (Stage -> Builder) -> Args diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 49a3a1d..b147665 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -2,7 +2,7 @@ module Settings.User ( buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, - laxDependencies, verboseCommands, turnWarningsIntoErrors, splitObjects + verboseCommands, turnWarningsIntoErrors, splitObjects ) where import Base @@ -74,13 +74,6 @@ ghcProfiled = False ghcDebugged :: Bool ghcDebugged = False --- | When laxDependencies is set to True, dependencies on the GHC executable --- are turned into order-only dependencies to avoid needless recompilation when --- making changes to GHC's sources. In certain situations this can lead to build --- failures, in which case you should reset the flag (at least temporarily). -laxDependencies :: Bool -laxDependencies = False - buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock From git at git.haskell.org Fri Oct 27 00:09:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: In the removeDirectory operation, use removeIfExists (2dd57cc) Message-ID: <20171027000904.0B68F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2dd57cc06f172145f668a89d29756de6dccceb0f/ghc >--------------------------------------------------------------- commit 2dd57cc06f172145f668a89d29756de6dccceb0f Author: Neil Mitchell Date: Tue Jan 12 22:43:01 2016 +0000 In the removeDirectory operation, use removeIfExists >--------------------------------------------------------------- 2dd57cc06f172145f668a89d29756de6dccceb0f src/Rules/Actions.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index a968160..55f81dd 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -77,7 +77,7 @@ createDirectory dir = do removeDirectory :: FilePath -> Action () removeDirectory dir = do putBuild $ "| Remove directory " ++ dir - liftIO $ IO.removeDirectoryRecursive dir + removeDirectoryIfExists dir -- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:09:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ArSupportsAtFile flag. (093c1a9) Message-ID: <20171027000905.D60513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/093c1a95e1e29df19985840d22138b798744da3c/ghc >--------------------------------------------------------------- commit 093c1a95e1e29df19985840d22138b798744da3c Author: Andrey Mokhov Date: Thu Sep 24 23:42:10 2015 +0100 Add ArSupportsAtFile flag. >--------------------------------------------------------------- 093c1a95e1e29df19985840d22138b798744da3c src/Oracles/Config/Flag.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 69d4884..f352ae3 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -8,7 +8,8 @@ import Base import Oracles.Config import Oracles.Config.Setting -data Flag = CrossCompiling +data Flag = ArSupportsAtFile + | CrossCompiling | GccIsClang | GccLt46 | GhcUnregisterised @@ -22,6 +23,7 @@ data Flag = CrossCompiling flag :: Flag -> Action Bool flag f = do key <- return $ case f of + ArSupportsAtFile -> "ar-supports-at-file" CrossCompiling -> "cross-compiling" GccIsClang -> "gcc-is-clang" GccLt46 -> "gcc-lt-46" From git at git.haskell.org Fri Oct 27 00:09:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #156, remove the directory if it already exists (8f995f6) Message-ID: <20171027000907.874333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f995f6b65c27d18f2f9606ba95ac25c2974ae23/ghc >--------------------------------------------------------------- commit 8f995f6b65c27d18f2f9606ba95ac25c2974ae23 Author: Neil Mitchell Date: Tue Jan 12 22:43:24 2016 +0000 #156, remove the directory if it already exists >--------------------------------------------------------------- 8f995f6b65c27d18f2f9606ba95ac25c2974ae23 src/Rules/Libffi.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 8bcfdae..dbf50dc 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -82,6 +82,7 @@ libffiRules = do need tarballs let libname = dropExtension . dropExtension . takeFileName $ head tarballs + removeDirectory (buildRootPath -/- libname) actionFinally (do build $ fullTarget libffiTarget Tar tarballs [buildRootPath] moveDirectory (buildRootPath -/- libname) libffiBuild) $ From git at git.haskell.org Fri Oct 27 00:09:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian (b08a8f6) Message-ID: <20171027000906.0CFBF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b08a8f64c8d6d7137aa470f83e4fe28f9d39aa07/ghc >--------------------------------------------------------------- commit b08a8f64c8d6d7137aa470f83e4fe28f9d39aa07 Author: Andrey Mokhov Date: Wed Apr 27 00:10:35 2016 +0100 Rename to Hadrian [skip ci] >--------------------------------------------------------------- b08a8f64c8d6d7137aa470f83e4fe28f9d39aa07 README.md | 44 +++++++++++++++++++++----------------------- 1 file changed, 21 insertions(+), 23 deletions(-) diff --git a/README.md b/README.md index c61f5c6..375e4f8 100644 --- a/README.md +++ b/README.md @@ -1,20 +1,18 @@ -Shaking up GHC -============== +Hadrian +======= [![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) -This is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based +Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current [`make`-based build system][make]. If you are curious about the rationale and initial ideas behind the project you can find more details on the [wiki page][ghc-shake-wiki] -and in this [blog post][blog-post-1]. +and in this [blog post][blog-post-1]. This project was formerly known as *Shaking-up-GHC*. The new build system can work side-by-side with the existing build system. Note, there is some interaction between them: they put (some) build results in the same directories, e.g. `inplace/bin/ghc-stage1`. -[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc). - Your first build ---------------- @@ -28,17 +26,17 @@ follow these steps: packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. * Get the sources and run standard configuration scripts. It is important for the build -system to be in the `shake-build` directory of the GHC source tree: +system to be in the `hadrian` directory of the GHC source tree: ```bash git clone --recursive git://git.haskell.org/ghc.git cd ghc - git clone git://github.com/snowleopard/shaking-up-ghc shake-build + git clone git://github.com/snowleopard/hadrian ./boot ./configure # On Windows run ./configure --enable-tarballs-autodownload ``` -* Build GHC using `shake-build/build.sh` or `shake-build/build.bat` (on Windows) instead +* Build GHC using `hadrian/build.sh` or `hadrian/build.bat` (on Windows) instead of `make`. You might want to enable parallelism with `-j`. We will further refer to the build script simply as `build`. If you are interested in building in a Cabal sandbox or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Also @@ -133,20 +131,20 @@ helped me endure and enjoy the project. [make]: https://ghc.haskell.org/trac/ghc/wiki/Building/Architecture [ghc-shake-wiki]: https://ghc.haskell.org/trac/ghc/wiki/Building/Shake [blog-post-1]: https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc -[issues]: https://github.com/snowleopard/shaking-up-ghc/issues +[issues]: https://github.com/snowleopard/hadrian/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild -[windows-build]: https://github.com/snowleopard/shaking-up-ghc/blob/master/doc/windows.md -[build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 +[windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md +[build-artefacts-issue]: https://github.com/snowleopard/hadrian/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 -[user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs -[test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 -[dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 -[validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 -[flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 -[cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 -[install-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/219 -[milestones]: https://github.com/snowleopard/shaking-up-ghc/milestones -[comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 -[doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 -[contributors]: https://github.com/snowleopard/shaking-up-ghc/graphs/contributors +[user-settings]: https://github.com/snowleopard/hadrian/blob/master/src/Settings/User.hs +[test-issue]: https://github.com/snowleopard/hadrian/issues/197 +[dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 +[validation-issue]: https://github.com/snowleopard/hadrian/issues/187 +[flavours-issue]: https://github.com/snowleopard/hadrian/issues/188 +[cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 +[install-issue]: https://github.com/snowleopard/hadrian/issues/219 +[milestones]: https://github.com/snowleopard/hadrian/milestones +[comments-issue]: https://github.com/snowleopard/hadrian/issues/55 +[doc-issue]: https://github.com/snowleopard/hadrian/issues/56 +[contributors]: https://github.com/snowleopard/hadrian/graphs/contributors From git at git.haskell.org Fri Oct 27 00:09:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new setting keys. (2ed0b04) Message-ID: <20171027000910.21FA43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ed0b0414b2cd247808ea3c5e94b27e0556bc9ab/ghc >--------------------------------------------------------------- commit 2ed0b0414b2cd247808ea3c5e94b27e0556bc9ab Author: Andrey Mokhov Date: Thu Sep 24 23:42:47 2015 +0100 Add new setting keys. >--------------------------------------------------------------- 2ed0b0414b2cd247808ea3c5e94b27e0556bc9ab src/Oracles/Config/Setting.hs | 21 ++++++++++++++++++++- 1 file changed, 20 insertions(+), 1 deletion(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index e1dfefa..fa62f97 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -10,13 +10,18 @@ import Base import Oracles.Config import Stage +-- TODO: reduce the variety of similar flags (e.g. CPP and non-CPP versions). -- Each Setting comes from the system.config file, e.g. 'target-os = mingw32'. -- setting TargetOs looks up the config file and returns "mingw32". -- -- SettingList is used for multiple string values separated by spaces, such -- as 'gmp-include-dirs = a b'. -- settingList GmpIncludeDirs therefore returns a list of strings ["a", "b"]. -data Setting = DynamicExtension +data Setting = BuildArch + | BuildOs + | BuildPlatform + | BuildVendor + | DynamicExtension | GhcMajorVersion | GhcMinorVersion | GhcPatchLevel @@ -24,6 +29,8 @@ data Setting = DynamicExtension | GhcSourcePath | HostArch | HostOs + | HostPlatform + | HostVendor | ProjectGitCommitId | ProjectName | ProjectVersion @@ -33,7 +40,9 @@ data Setting = DynamicExtension | ProjectPatchLevel2 | TargetArch | TargetOs + | TargetPlatform | TargetPlatformFull + | TargetVendor data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -41,11 +50,16 @@ data SettingList = ConfCcArgs Stage | ConfLdLinkerArgs Stage | GmpIncludeDirs | GmpLibDirs + | HsCppArgs | IconvIncludeDirs | IconvLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of + BuildArch -> "build-arch" + BuildOs -> "build-os" + BuildPlatform -> "build-platform" + BuildVendor -> "build-vendor" DynamicExtension -> "dynamic-extension" GhcMajorVersion -> "ghc-major-version" GhcMinorVersion -> "ghc-minor-version" @@ -54,6 +68,8 @@ setting key = askConfig $ case key of GhcSourcePath -> "ghc-source-path" HostArch -> "host-arch" HostOs -> "host-os" + HostPlatform -> "host-platform" + HostVendor -> "host-vendor" ProjectGitCommitId -> "project-git-commit-id" ProjectName -> "project-name" ProjectVersion -> "project-version" @@ -63,7 +79,9 @@ setting key = askConfig $ case key of ProjectPatchLevel2 -> "project-patch-level2" TargetArch -> "target-arch" TargetOs -> "target-os" + TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" + TargetVendor -> "target-vendor" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -73,6 +91,7 @@ settingList key = fmap words $ askConfig $ case key of ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show stage GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" + HsCppArgs -> "hs-cpp-args" IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" From git at git.haskell.org Fri Oct 27 00:09:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian. (cf2b1da) Message-ID: <20171027000910.6FEA33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf2b1da44222a8abc3f1d8cbc66c800631348114/ghc >--------------------------------------------------------------- commit cf2b1da44222a8abc3f1d8cbc66c800631348114 Author: Andrey Mokhov Date: Wed Apr 27 00:34:46 2016 +0100 Rename to Hadrian. [skip ci] >--------------------------------------------------------------- cf2b1da44222a8abc3f1d8cbc66c800631348114 shaking-up-ghc.cabal => hadrian.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/shaking-up-ghc.cabal b/hadrian.cabal similarity index 97% rename from shaking-up-ghc.cabal rename to hadrian.cabal index a5e6d22..a2df30a 100644 --- a/shaking-up-ghc.cabal +++ b/hadrian.cabal @@ -1,18 +1,18 @@ -name: shaking-up-ghc +name: hadrian version: 0.1.0.0 synopsis: GHC build system license: BSD3 license-file: LICENSE author: Andrey Mokhov , github: @snowleopard maintainer: Andrey Mokhov , github: @snowleopard -copyright: Andrey Mokhov 2014-2015 +copyright: Andrey Mokhov 2014-2016 category: Development build-type: Simple cabal-version: >=1.10 source-repository head type: git - location: https://github.com/snowleopard/shaking-up-ghc + location: https://github.com/snowleopard/hadrian executable ghc-shake main-is: Main.hs From git at git.haskell.org Fri Oct 27 00:09:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #161 from ndmitchell/master (f5f6c41) Message-ID: <20171027000911.3BFCD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5f6c41b98c7f4682f0bd73f573fc170e233235a/ghc >--------------------------------------------------------------- commit f5f6c41b98c7f4682f0bd73f573fc170e233235a Merge: 57c6497 8f995f6 Author: Andrey Mokhov Date: Tue Jan 12 22:46:47 2016 +0000 Merge pull request #161 from ndmitchell/master Cleanups in libffi >--------------------------------------------------------------- f5f6c41b98c7f4682f0bd73f573fc170e233235a src/Rules/Actions.hs | 7 ++++++- src/Rules/Libffi.hs | 16 +++++++++------- 2 files changed, 15 insertions(+), 8 deletions(-) From git at git.haskell.org Fri Oct 27 00:09:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian (2736806) Message-ID: <20171027000914.A1EB43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27368067f3c22a5313ab507f5f5beede19bcf9bf/ghc >--------------------------------------------------------------- commit 27368067f3c22a5313ab507f5f5beede19bcf9bf Author: Andrey Mokhov Date: Wed Apr 27 00:37:25 2016 +0100 Rename to Hadrian [skip ci] >--------------------------------------------------------------- 27368067f3c22a5313ab507f5f5beede19bcf9bf LICENSE | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/LICENSE b/LICENSE index 9ee6e34..fbedb41 100644 --- a/LICENSE +++ b/LICENSE @@ -1,6 +1,6 @@ BSD License -Copyright (c) 2015, Andrey Mokhov +Copyright (c) 2014, Andrey Mokhov All rights reserved. Redistribution and use in source and binary forms, with or without @@ -13,7 +13,7 @@ modification, are permitted provided that the following conditions are met: this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. -* Neither the name of Shaking up GHC nor the names of its +* Neither the name of the Hadrian project nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. From git at git.haskell.org Fri Oct 27 00:09:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #155, fix the name of the QuickCheck package (it doesn't follow the convention all the others do) (a60cdcd) Message-ID: <20171027000915.114F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a60cdcd7cb6ce45d1b8f6794d4aa9e5f9415c810/ghc >--------------------------------------------------------------- commit a60cdcd7cb6ce45d1b8f6794d4aa9e5f9415c810 Author: Neil Mitchell Date: Wed Jan 13 08:47:25 2016 +0000 #155, fix the name of the QuickCheck package (it doesn't follow the convention all the others do) >--------------------------------------------------------------- a60cdcd7cb6ce45d1b8f6794d4aa9e5f9415c810 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 4226415..f5b8117 100644 --- a/README.md +++ b/README.md @@ -24,7 +24,7 @@ to adjust anything if you are already familiar with building ghc using the `make build system. Furthermore, we depend on the following packages which need to be installed: -`ansi-terminal`, `mtl`, `shake`, `quickcheck`. +`ansi-terminal`, `mtl`, `shake`, `QuickCheck`. ### Getting the source and configuring GHC From git at git.haskell.org Fri Oct 27 00:09:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix HsCpp argument list. (555265c) Message-ID: <20171027000917.99E1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/555265ce0686be733a2a3f66abbab1bc8771d237/ghc >--------------------------------------------------------------- commit 555265ce0686be733a2a3f66abbab1bc8771d237 Author: Andrey Mokhov Date: Thu Sep 24 23:45:01 2015 +0100 Fix HsCpp argument list. >--------------------------------------------------------------- 555265ce0686be733a2a3f66abbab1bc8771d237 src/Settings/Builders/HsCpp.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs index da104cc..cad2897 100644 --- a/src/Settings/Builders/HsCpp.hs +++ b/src/Settings/Builders/HsCpp.hs @@ -1,6 +1,7 @@ module Settings.Builders.HsCpp (hsCppArgs) where import Expression +import Oracles import Predicates (builder) import Settings.Builders.GhcCabal @@ -9,9 +10,11 @@ hsCppArgs :: Args hsCppArgs = builder HsCpp ? do stage <- getStage src <- getSource - mconcat [ arg "-P" + args <- getSettingList HsCppArgs + mconcat [ append args + , arg "-P" , cppArgs - , arg $ "-Icompiler/stage" ++ show stage + , arg $ "-Icompiler/stage" ++ show (succ stage) , arg "-x" , arg "c" , arg src ] From git at git.haskell.org Fri Oct 27 00:09:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new mode for Ar builder: useAtFile (big performance increase). (6cde985) Message-ID: <20171027000914.0AA703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6cde9851e61a88b0773e07346752279129c87d41/ghc >--------------------------------------------------------------- commit 6cde9851e61a88b0773e07346752279129c87d41 Author: Andrey Mokhov Date: Thu Sep 24 23:44:34 2015 +0100 Add new mode for Ar builder: useAtFile (big performance increase). >--------------------------------------------------------------- 6cde9851e61a88b0773e07346752279129c87d41 src/Rules/Actions.hs | 23 ++++++++--------------- src/Settings/Builders/Ar.hs | 31 ++++++++++++++++++++++++++++--- 2 files changed, 36 insertions(+), 18 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 8214112..5f15f3d 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,7 +1,6 @@ module Rules.Actions (build, buildWithResources) where import Expression -import Oracles import Oracles.ArgsHash import Settings import Settings.Args @@ -18,19 +17,13 @@ buildWithResources rs target = do path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed - when trackBuildSystem $ checkArgsHash target + checkArgsHash target withResources rs $ do - putBuild $ "/--------\n" ++ "| Running " - ++ show builder ++ " with arguments:" + putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList putBuild $ "\\--------" quietly $ case builder of - Ar -> do -- Split argument list into chunks as otherwise Ar chokes up - maxChunk <- cmdLineLengthLimit - let persistentArgs = take arPersistentArgsCount argList - remainingArgs = drop arPersistentArgsCount argList - forM_ (chunksOfSize maxChunk remainingArgs) $ \argsChunk -> - unit . cmd [path] $ persistentArgs ++ argsChunk + Ar -> arCmd path argList HsCpp -> do let file = head $ Target.files target -- TODO: ugly @@ -63,14 +56,14 @@ interestingInfo builder ss = case builder of Haddock -> prefixAndSuffix 1 0 ss Happy -> prefixAndSuffix 0 3 ss Hsc2Hs -> prefixAndSuffix 0 3 ss + HsCpp -> prefixAndSuffix 0 1 ss Ld -> prefixAndSuffix 4 0 ss _ -> ss where prefixAndSuffix n m list = - if length list <= n + m + 1 + let len = length list in + if len <= n + m + 1 then list else take n list - ++ ["... skipping " - ++ show (length list - n - m) - ++ " arguments ..."] - ++ drop (length list - m) list + ++ ["... skipping " ++ show (len - n - m) ++ " arguments ..."] + ++ drop (len - m) list diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 082cbaf..7b6eb59 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,6 +1,7 @@ -module Settings.Builders.Ar (arArgs, arPersistentArgsCount) where +module Settings.Builders.Ar (arArgs, arCmd) where import Expression +import Oracles import Predicates (builder) arArgs :: Args @@ -13,5 +14,29 @@ arArgs = builder Ar ? do -- This count includes arg "q" and arg file parameters in arArgs (see above). -- Update this value appropriately when changing arArgs. -arPersistentArgsCount :: Int -arPersistentArgsCount = 2 +arFlagsCount :: Int +arFlagsCount = 2 + +-- Ar needs to be invoked in a special way: we pass the list of files to be +-- archived via a temporary file as otherwise Ar (or rather Windows command +-- line) chokes up. Alternatively, we split argument list into chunks and call +-- ar multiple times (when passing files via a separate file is not supported). +arCmd :: FilePath -> [String] -> Action () +arCmd path argList = do + arSupportsAtFile <- flag ArSupportsAtFile + let flagArgs = take arFlagsCount argList + fileArgs = drop arFlagsCount argList + if arSupportsAtFile + then useAtFile path flagArgs fileArgs + else useSuccessiveInvokations path flagArgs fileArgs + +useAtFile :: FilePath -> [String] -> [String] -> Action () +useAtFile path flagArgs fileArgs = withTempFile $ \tmp -> do + writeFile' tmp $ unwords fileArgs + cmd [path] flagArgs ('@' : tmp) + +useSuccessiveInvokations :: FilePath -> [String] -> [String] -> Action () +useSuccessiveInvokations path flagArgs fileArgs = do + maxChunk <- cmdLineLengthLimit + forM_ (chunksOfSize maxChunk fileArgs) $ \argsChunk -> + unit . cmd [path] $ flagArgs ++ argsChunk From git at git.haskell.org Fri Oct 27 00:09:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian (0c5fe5b) Message-ID: <20171027000918.365663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c5fe5b08bc591073351b60a5e76c9a0a09ad686/ghc >--------------------------------------------------------------- commit 0c5fe5b08bc591073351b60a5e76c9a0a09ad686 Author: Andrey Mokhov Date: Wed Apr 27 00:39:10 2016 +0100 Rename to Hadrian [skip ci] >--------------------------------------------------------------- 0c5fe5b08bc591073351b60a5e76c9a0a09ad686 doc/windows.md | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 7fc8dcf..7afd97c 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -9,11 +9,11 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ stack exec -- pacman -S gcc binutils git automake-wrapper tar make patch autoconf --noconfirm stack exec -- git clone --recursive git://git.haskell.org/ghc.git cd ghc - stack exec -- git clone git://github.com/snowleopard/shaking-up-ghc shake-build - stack build --stack-yaml=shake-build/stack.yaml --only-dependencies + stack exec -- git clone git://github.com/snowleopard/hadrian + stack build --stack-yaml=hadrian/stack.yaml --only-dependencies stack exec -- perl boot stack exec -- bash configure --enable-tarballs-autodownload - stack exec --stack-yaml=shake-build/stack.yaml -- shake-build/build.bat -j + stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j The entire process should take about an hour. @@ -21,6 +21,6 @@ The entire process should take about an hour. Here are some alternatives that have been considered, but not yet tested. Use the instructions above. -* Use `shake-build/build.bat --setup` to replace `boot` and `configure`. +* Use `hadrian/build.bat --setup` to replace `boot` and `configure`. * The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. * Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:09:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #162 from ndmitchell/master (6934485) Message-ID: <20171027000918.8DD233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6934485f0e98b62630ce0d867ebc6b8f3da5f04a/ghc >--------------------------------------------------------------- commit 6934485f0e98b62630ce0d867ebc6b8f3da5f04a Merge: f5f6c41 a60cdcd Author: Andrey Mokhov Date: Wed Jan 13 09:15:24 2016 +0000 Merge pull request #162 from ndmitchell/master #155, fix the name of the QuickCheck package [skip ci] >--------------------------------------------------------------- 6934485f0e98b62630ce0d867ebc6b8f3da5f04a README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:09:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve Generate rule: clean up code, more accurate dependencies. (9253049) Message-ID: <20171027000922.06F613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/925304968b4da8050e618b004cfdccfe0cb895e6/ghc >--------------------------------------------------------------- commit 925304968b4da8050e618b004cfdccfe0cb895e6 Author: Andrey Mokhov Date: Thu Sep 24 23:46:24 2015 +0100 Improve Generate rule: clean up code, more accurate dependencies. >--------------------------------------------------------------- 925304968b4da8050e618b004cfdccfe0cb895e6 src/Rules/Dependencies.hs | 3 + src/Rules/Generate.hs | 217 ++++++++++++++++++++++++++++++---------------- 2 files changed, 146 insertions(+), 74 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 925304968b4da8050e618b004cfdccfe0cb895e6 From git at git.haskell.org Fri Oct 27 00:09:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian. (11759a8) Message-ID: <20171027000922.2955C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/11759a8ee0d735e2331d4d617031dd3dcc3069f6/ghc >--------------------------------------------------------------- commit 11759a8ee0d735e2331d4d617031dd3dcc3069f6 Author: Andrey Mokhov Date: Wed Apr 27 00:45:38 2016 +0100 Rename to Hadrian. [skip ci] >--------------------------------------------------------------- 11759a8ee0d735e2331d4d617031dd3dcc3069f6 .travis.yml | 18 +++++++++--------- appveyor.yml | 6 +++--- 2 files changed, 12 insertions(+), 12 deletions(-) diff --git a/.travis.yml b/.travis.yml index d6092fb..6832cd8 100644 --- a/.travis.yml +++ b/.travis.yml @@ -47,22 +47,22 @@ install: # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake # ".git" directory into the appropriate location, and perform a hard reset # in order to regenerate the GHC-Shake files. - - mkdir ghc/shake-build - - mv .git ghc/shake-build - - ( cd ghc/shake-build && git reset --hard HEAD ) + - mkdir ghc/hadrian + - mv .git ghc/hadrian + - ( cd ghc/hadrian && git reset --hard HEAD ) - - ( cd ghc/shake-build && cabal install --only-dependencies ) - - ( cd ghc/shake-build && cabal configure ) + - ( cd ghc/hadrian && cabal install --only-dependencies ) + - ( cd ghc/hadrian && cabal configure ) - ( cd ghc && ./boot ) - ( cd ghc && ./configure ) - - cat ghc/shake-build/cfg/system.config + - cat ghc/hadrian/cfg/system.config - ghc-pkg list script: - - ( cd ghc/shake-build && cabal haddock --internal ) - - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --profile=- --flavour=quick $TARGET + - ( cd ghc/hadrian && cabal haddock --internal ) + - ./ghc/hadrian/build.sh selftest + - ./ghc/hadrian/build.sh -j --no-progress --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index 6cc17b6..3918779 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -1,4 +1,4 @@ -clone_folder: "C:\\msys64\\home\\ghc\\shake-build" +clone_folder: "C:\\msys64\\home\\ghc\\hadrian" environment: global: STACK_ROOT: "c:\\sr" @@ -30,7 +30,7 @@ install: - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/80eac86c555a8e0d48a694ffc23f0ac2c75236d0/ghc >--------------------------------------------------------------- commit 80eac86c555a8e0d48a694ffc23f0ac2c75236d0 Author: Karel Gardas Date: Wed Jan 13 22:24:38 2016 +0100 fix handling of --with-gmp-* configure arguments >--------------------------------------------------------------- 80eac86c555a8e0d48a694ffc23f0ac2c75236d0 src/Rules/Gmp.hs | 46 ++++++++++++++++++++++++++++++++-------------- 1 file changed, 32 insertions(+), 14 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index b02fe36..94086e1 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -57,6 +57,19 @@ configureArguments = do , "--host=" ++ hostPlatform , "--build=" ++ buildPlatform] +configureIntGmpArguments :: Action [String] +configureIntGmpArguments = do + includes <- settingList GmpIncludeDirs + libs <- settingList GmpLibDirs + return ([] + ++ (if (not (null includes)) + then map ((++) "--with-gmp-includes=") includes + else []) + ++ (if (not (null libs)) + then map ((++) "--with-gmp-libraries=") libs + else []) + ) + -- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do @@ -105,7 +118,8 @@ gmpRules = do runConfigure libPath envs args -- TODO: currently we configure integerGmp package twice -- optimise - runConfigure (pkgPath integerGmp) [] [] + intGmpArgs <- configureIntGmpArguments + runConfigure (pkgPath integerGmp) envs intGmpArgs createDirectory $ takeDirectory gmpLibraryH -- check whether we need to build in tree gmp @@ -115,19 +129,23 @@ gmpRules = do then do putBuild "| GMP framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - else do - putBuild "| No GMP framework detected; in tree GMP will be built" - runMake libPath ["MAKEFLAGS="] - - copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH - copyFile (libPath -/- "gmp.h") gmpLibraryH - -- TODO: why copy library, can we move it instead? - copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary - - createDirectory gmpObjects - build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] - - runBuilder Ranlib [gmpLibrary] + else if "HaveLibGmp = YES" `isInfixOf` configMk + then do + putBuild "| GMP detected and will be used" + copyFile gmpLibraryFakeH gmpLibraryH + else do + putBuild "| No GMP framework detected; in tree GMP will be built" + runMake libPath ["MAKEFLAGS="] + + copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH + copyFile (libPath -/- "gmp.h") gmpLibraryH + -- TODO: why copy library, can we move it instead? + copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary + + createDirectory gmpObjects + build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] + + runBuilder Ranlib [gmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" From git at git.haskell.org Fri Oct 27 00:09:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: merge GMP library and framework GMP checks together (b784a22) Message-ID: <20171027000926.27D683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b784a2233bc75245bfddef304fa690dbcf382311/ghc >--------------------------------------------------------------- commit b784a2233bc75245bfddef304fa690dbcf382311 Author: Karel Gardas Date: Wed Jan 13 23:03:08 2016 +0100 merge GMP library and framework GMP checks together >--------------------------------------------------------------- b784a2233bc75245bfddef304fa690dbcf382311 src/Rules/Gmp.hs | 33 +++++++++++++++------------------ 1 file changed, 15 insertions(+), 18 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 94086e1..f34f3f0 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -126,26 +126,23 @@ gmpRules = do -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` configMk <- liftIO . readFile $ gmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk + || "HaveLibGmp = YES" `isInfixOf` configMk then do - putBuild "| GMP framework detected and will be used" + putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - else if "HaveLibGmp = YES" `isInfixOf` configMk - then do - putBuild "| GMP detected and will be used" - copyFile gmpLibraryFakeH gmpLibraryH - else do - putBuild "| No GMP framework detected; in tree GMP will be built" - runMake libPath ["MAKEFLAGS="] - - copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH - copyFile (libPath -/- "gmp.h") gmpLibraryH - -- TODO: why copy library, can we move it instead? - copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary - - createDirectory gmpObjects - build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] - - runBuilder Ranlib [gmpLibrary] + else do + putBuild "| No GMP library/framework detected; in tree GMP will be built" + runMake libPath ["MAKEFLAGS="] + + copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH + copyFile (libPath -/- "gmp.h") gmpLibraryH + -- TODO: why copy library, can we move it instead? + copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary + + createDirectory gmpObjects + build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] + + runBuilder Ranlib [gmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" From git at git.haskell.org Fri Oct 27 00:09:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghc-bin package. (6a0c30f) Message-ID: <20171027000926.43CFB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a0c30ff7dad21754967ab9178e7ad3b88c1598d/ghc >--------------------------------------------------------------- commit 6a0c30ff7dad21754967ab9178e7ad3b88c1598d Author: Andrey Mokhov Date: Thu Sep 24 23:47:18 2015 +0100 Add ghc-bin package. >--------------------------------------------------------------- 6a0c30ff7dad21754967ab9178e7ad3b88c1598d src/GHC.hs | 18 ++++++++++-------- src/Settings/Builders/GhcCabal.hs | 6 ++++++ src/Settings/Packages.hs | 6 +++--- src/Settings/User.hs | 2 +- 4 files changed, 20 insertions(+), 12 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 8f25c7c..c277c6a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,8 +1,8 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, - integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, - terminfo, time, transformers, unix, win32, xhtml, + deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + integerGmp, integerSimple, parallel, pretty, primitive, process, stm, + templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory ) where @@ -18,15 +18,15 @@ import Stage defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc - , integerGmp, integerSimple, parallel, pretty, primitive, process, stm + , containers, deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl + , hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm , templateHaskell, terminfo, time, transformers, unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghcPrim, haskeline, hoopl, hpc, integerGmp, - integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, - terminfo, time, transformers, unix, win32, xhtml :: Package + deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + integerGmp, integerSimple, parallel, pretty, primitive, process, stm, + templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -39,6 +39,7 @@ containers = library "containers" deepseq = library "deepseq" directory = library "directory" filepath = library "filepath" +ghc = topLevel "ghc-bin" `setPath` "ghc" ghcPrim = library "ghc-prim" haskeline = library "haskeline" hoopl = library "hoopl" @@ -67,5 +68,6 @@ xhtml = library "xhtml" defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage package | package == compiler = "stage" ++ show (fromEnum stage + 1) + | package == ghc = "stage" ++ show (fromEnum stage + 1) | stage == Stage0 = "dist-boot" | otherwise = "dist-install" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index b68da27..582a56c 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -166,6 +166,12 @@ customPackageArgs = do , ghcProfiled ? notStage0 ? arg "--ghc-pkg-option=--force" ] + , package ghc ? + builder GhcCabal ? + mconcat [ arg $ "--flags=stage" ++ show nextStage + , ghcWithInterpreter ? + notStage0 ? arg "--flags=ghci" + ] ] withBuilderKey :: Builder -> String diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index dee0c95..8b913f5 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -16,7 +16,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, hoopl, hpc, transformers ] + [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? @@ -24,8 +24,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory - , filepath, ghcPrim, haskeline, integerLibrary, pretty, process - , templateHaskell, time ] + , filepath, ghc, ghcPrim, haskeline, integerLibrary, pretty + , process, templateHaskell, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 5b62e39..9a71ac2 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -15,7 +15,7 @@ userArgs = mempty -- Control which packages get to be built userPackages :: Packages -userPackages = mempty +userPackages = remove [ghc] -- Add new user-defined packages userKnownPackages :: [Package] From git at git.haskell.org Fri Oct 27 00:09:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename project executable to hadrian. (affe0bd) Message-ID: <20171027000926.56BD03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/affe0bd9add35be2a801a68a0cc1309f2bdb176a/ghc >--------------------------------------------------------------- commit affe0bd9add35be2a801a68a0cc1309f2bdb176a Author: Andrey Mokhov Date: Wed Apr 27 00:50:27 2016 +0100 Rename project executable to hadrian. >--------------------------------------------------------------- affe0bd9add35be2a801a68a0cc1309f2bdb176a build.cabal-new.sh | 8 ++++---- build.cabal.sh | 2 +- build.stack.sh | 2 +- hadrian.cabal | 2 +- src/Environment.hs | 2 +- 5 files changed, 8 insertions(+), 8 deletions(-) diff --git a/build.cabal-new.sh b/build.cabal-new.sh index 96c194e..bca8c7c 100755 --- a/build.cabal-new.sh +++ b/build.cabal-new.sh @@ -38,16 +38,16 @@ mkdir -p "$root/.shake" # Notes/Random thoughts: # # - if ghc.git had a top-level `cabal.project` file, we could maybe avoid the -# boilerplate above, as we could simply say `cabal exec ghc-shake` from within +# boilerplate above, as we could simply say `cabal exec hadrian` from within # any GHC folder not shadowed by a nearer shadowing `cabal.project` file. pushd "$root/" -cabal new-build --disable-profiling --disable-documentation -j exe:ghc-shake +cabal new-build --disable-profiling --disable-documentation -j exe:hadrian -PKGVER="$(awk '/^version:/ { print $2 }' shaking-up-ghc.cabal)" +PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" -cp -v "$root/dist-newstyle/build/shaking-up-ghc-${PKGVER}/build/ghc-shake/ghc-shake" \ +cp -v "$root/dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ "$root/.shake/build" popd diff --git a/build.cabal.sh b/build.cabal.sh index 5f20c1b..f2e320e 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -40,7 +40,7 @@ if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then --disable-shared fi -cabal run ghc-shake -- \ +cabal run hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ --colour \ diff --git a/build.stack.sh b/build.stack.sh index 578e7eb..b5607b1 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -33,7 +33,7 @@ cd "$absoluteRoot" stack build --no-library-profiling -stack exec ghc-shake -- \ +stack exec hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ --colour \ diff --git a/hadrian.cabal b/hadrian.cabal index a2df30a..4bf5a4c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -14,7 +14,7 @@ source-repository head type: git location: https://github.com/snowleopard/hadrian -executable ghc-shake +executable hadrian main-is: Main.hs hs-source-dirs: src other-modules: Base diff --git a/src/Environment.hs b/src/Environment.hs index e674f83..d4d9853 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -13,7 +13,7 @@ setupEnvironment = do -- in MinGW if PWD is set to a Windows "C:\\" style path then configure -- `pwd` will return the Windows path, and then modifying $PATH will fail. - -- See https://github.com/snowleopard/shaking-up-ghc/issues/189 for details. + -- See https://github.com/snowleopard/hadrian/issues/189 for details. unsetEnv "PWD" -- On Windows, some path variables start a prefix like "C:\\" which may From git at git.haskell.org Fri Oct 27 00:09:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: simplify configureIntGmpArguments based on idea provided by Gabor Greif (86a3fe5) Message-ID: <20171027000930.7B18F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86a3fe5f1e16ef919cf0145c0830f2ad7cd8586e/ghc >--------------------------------------------------------------- commit 86a3fe5f1e16ef919cf0145c0830f2ad7cd8586e Author: Karel Gardas Date: Wed Jan 13 23:31:29 2016 +0100 simplify configureIntGmpArguments based on idea provided by Gabor Greif >--------------------------------------------------------------- 86a3fe5f1e16ef919cf0145c0830f2ad7cd8586e src/Rules/Gmp.hs | 11 +++-------- 1 file changed, 3 insertions(+), 8 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index f34f3f0..f6d6fe8 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -61,14 +61,9 @@ configureIntGmpArguments :: Action [String] configureIntGmpArguments = do includes <- settingList GmpIncludeDirs libs <- settingList GmpLibDirs - return ([] - ++ (if (not (null includes)) - then map ((++) "--with-gmp-includes=") includes - else []) - ++ (if (not (null libs)) - then map ((++) "--with-gmp-libraries=") libs - else []) - ) + return $ map ("--with-gmp-includes=" ++) includes + ++ map ("--with-gmp-libraries=" ++) libs + -- TODO: we rebuild gmp every time. gmpRules :: Rules () From git at git.haskell.org Fri Oct 27 00:09:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Put when trackBuildSystem conditional more precisely. (9f99e24) Message-ID: <20171027000931.1499F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9f99e240df6f3c5ad8597e2dafd9a73220dd87d3/ghc >--------------------------------------------------------------- commit 9f99e240df6f3c5ad8597e2dafd9a73220dd87d3 Author: Andrey Mokhov Date: Thu Sep 24 23:48:02 2015 +0100 Put when trackBuildSystem conditional more precisely. >--------------------------------------------------------------- 9f99e240df6f3c5ad8597e2dafd9a73220dd87d3 src/Oracles/ArgsHash.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index bc29031..402923b 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -20,12 +20,12 @@ newtype ArgsHashKey = ArgsHashKey Target -- to argument lists where appropriate. -- TODO: enforce the above assumption via type trickery? checkArgsHash :: Target -> Action () -checkArgsHash target = do +checkArgsHash target = when trackBuildSystem $ do _ <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int return () -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () -argsHashOracle = when trackBuildSystem $ do +argsHashOracle = do _ <- addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs return () From git at git.haskell.org Fri Oct 27 00:09:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add TODOs. (c32b33d) Message-ID: <20171027000931.2A2E53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c32b33d53a3952658d714c975832bb84984b5fe5/ghc >--------------------------------------------------------------- commit c32b33d53a3952658d714c975832bb84984b5fe5 Author: Andrey Mokhov Date: Wed Apr 27 00:58:40 2016 +0100 Add TODOs. [skip ci] >--------------------------------------------------------------- c32b33d53a3952658d714c975832bb84984b5fe5 src/Settings/User.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index b147665..ef08df0 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -12,6 +12,7 @@ import Expression import Predicates import Settings.Default +-- TODO: Rename to _build. -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath buildRootPath = ".build" @@ -83,6 +84,7 @@ buildHaddock = return cmdBuildHaddock verboseCommands :: Predicate verboseCommands = return False +-- TODO: Replace with stage2 ? arg "-Werror"? -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False From git at git.haskell.org Fri Oct 27 00:09:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drops 'none' (a24a85f) Message-ID: <20171027000934.94DA33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a24a85f283a387df60e9755398c1e2c563fe1cda/ghc >--------------------------------------------------------------- commit a24a85f283a387df60e9755398c1e2c563fe1cda Author: Moritz Angermann Date: Thu Jan 14 14:02:51 2016 +0800 Drops 'none' shake has `-q` already, which is identical. >--------------------------------------------------------------- a24a85f283a387df60e9755398c1e2c563fe1cda src/Base.hs | 1 - src/Oracles/Config/CmdLineFlag.hs | 3 +-- 2 files changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index be3ff1b..a46031c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -152,7 +152,6 @@ renderAction what input output = case buildInfo of , " input:" ++ input , " => output:" ++ output ] Dot -> "." - None -> "" -- | Render the successful build of a program renderProgram :: String -> String -> String -> String diff --git a/src/Oracles/Config/CmdLineFlag.hs b/src/Oracles/Config/CmdLineFlag.hs index 687c541..47dbbbc 100644 --- a/src/Oracles/Config/CmdLineFlag.hs +++ b/src/Oracles/Config/CmdLineFlag.hs @@ -8,7 +8,7 @@ import Data.IORef -- Flags -data BuildInfoFlag = Normal | Brief | Pony | Dot | None deriving (Eq, Show) +data BuildInfoFlag = Normal | Brief | Pony | Dot deriving (Eq, Show) data CmdLineOptions = CmdLineOptions { flagBuildInfo :: BuildInfoFlag @@ -29,7 +29,6 @@ readBuildInfoFlag ms = go "brief" = Just Brief go "pony" = Just Pony go "dot" = Just Dot - go "none" = Just None go _ = Nothing -- Left "no parse" mkClosure :: BuildInfoFlag -> CmdLineOptions -> CmdLineOptions mkClosure flag opts = opts { flagBuildInfo = flag } From git at git.haskell.org Fri Oct 27 00:09:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, add comments. (55fd868) Message-ID: <20171027000934.9AB583A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/55fd868e521ea500e3b5e8a6f55890e632e07174/ghc >--------------------------------------------------------------- commit 55fd868e521ea500e3b5e8a6f55890e632e07174 Author: Andrey Mokhov Date: Fri Sep 25 02:52:16 2015 +0100 Clean up, add comments. >--------------------------------------------------------------- 55fd868e521ea500e3b5e8a6f55890e632e07174 src/Builder.hs | 1 + src/Oracles/ArgsHash.hs | 1 + src/Rules/Cabal.hs | 6 ++++-- 3 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index e1c69be..c0ffee0 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -16,6 +16,7 @@ import Stage -- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) -- TODO: add Cpp builders -- TODO: rename Gcc to Cc? +-- TODO: do we really need staged builders? data Builder = Alex | Ar | Gcc Stage diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 402923b..ab4993b 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -19,6 +19,7 @@ newtype ArgsHashKey = ArgsHashKey Target -- constructors are assumed not to examine target sources, but only append them -- to argument lists where appropriate. -- TODO: enforce the above assumption via type trickery? +-- TODO: Hash Target to improve accuracy and performance. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do _ <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index aac8ab2..7ccb1b8 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -2,7 +2,7 @@ module Rules.Cabal (cabalRules) where import Expression import Data.Version -import Distribution.Package +import Distribution.Package hiding (Package) import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Verbosity @@ -29,7 +29,9 @@ cabalRules = do pkgDeps <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - let deps = collectDeps . condLibrary $ pd + let depsLib = collectDeps $ condLibrary pd + depsExes = map (collectDeps . Just . snd) $ condExecutables pd + deps = concat $ depsLib : depsExes depNames = [ name | Dependency (PackageName name) _ <- deps ] return . unwords $ Package.pkgName pkg : sort depNames writeFileChanged out . unlines $ pkgDeps From git at git.haskell.org Fri Oct 27 00:09:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename shakePath to hadrian. (d2051cd) Message-ID: <20171027000935.6AC953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2051cdb91e00d19b02e7cab47e75411c1a29e33/ghc >--------------------------------------------------------------- commit d2051cdb91e00d19b02e7cab47e75411c1a29e33 Author: Andrey Mokhov Date: Wed Apr 27 00:59:24 2016 +0100 Rename shakePath to hadrian. [skip ci] >--------------------------------------------------------------- d2051cdb91e00d19b02e7cab47e75411c1a29e33 src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 871cd3c..b94648e 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -48,7 +48,7 @@ import System.IO -- Build system files and paths shakePath :: FilePath -shakePath = "shake-build" +shakePath = "hadrian" shakeFilesPath :: FilePath shakeFilesPath = shakePath -/- ".db" From git at git.haskell.org Fri Oct 27 00:09:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finalise meeting agenda. (07dbd29) Message-ID: <20171027000939.428CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/07dbd2918f9099fb98986f9cc91b51b52a94d5f8/ghc >--------------------------------------------------------------- commit 07dbd2918f9099fb98986f9cc91b51b52a94d5f8 Author: Andrey Mokhov Date: Fri Sep 25 02:52:32 2015 +0100 Finalise meeting agenda. >--------------------------------------------------------------- 07dbd2918f9099fb98986f9cc91b51b52a94d5f8 doc/meeting-25-September-2015.txt | 67 ++++++++++++++++++++++++++++----------- 1 file changed, 49 insertions(+), 18 deletions(-) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt index caf0e8e..dde2e45 100644 --- a/doc/meeting-25-September-2015.txt +++ b/doc/meeting-25-September-2015.txt @@ -4,42 +4,74 @@ Things to discuss: ================================================ 1. Progress report +------------------ +Done: +* Build all libraries and compiler +* Generate code (alex, happy, hsc2hs, genprimopcode, Config.hs, ghc_boot_platform.h) +* Track changes in the build system +* Extract accurate package dependencies from .cabal files +* Improve complexity when searching for module files (40x) -++ Dealing with seemingly dead-code artefacts of the old build systems. I used to carefully migrate all code to the new build system, but it is getting more in the way of readability. New proposal: drop all such suspicious instances and bring them back only if things break. Example: +Todo: Target: +* Build utils, rts October +* Better dependencies (.hs-incl etc.) November +* Support command line options December +* Validate November-December (GHC 8.0?) +* Documentation December-January + +Notes: +* Zero build: under 7 seconds +* Full build (when compilation not required): under 12 minutes on 4 cores +* Limited parallelism: ghc-cabal/ghc-pkg not thread-safe, ghc fails on > 4 cores +* Codebase growing: 50 files + + +2. Seemingly dead-code +---------------------- + +I used to carefully migrate all code to the new build system even when it seemed dead, but this is often getting in the way of readability. New proposal: drop all such suspicious instances and bring them back only if/when things break. + +Example (generating primops.txt): C:/msys/home/chEEtah/ghc/inplace/mingw/bin/gcc.exe -E -undef -traditional -P -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -Icompiler/stage2 -x c compiler/prelude/primops.txt.pp | grep -v '^#pragma GCC' > compiler/stage2/build/primops.txt -But primops.txt.pp has no lines containing #pragma GCC! Dead code? +But primops.txt.pp has no lines containing #pragma GCC. Dead code? -++ Zero build is 7 seconds +Another example (generating ghc_boot_platform.h): -++ .hs-incl includes are currently not tracked properly (e.g. ghc -MM does not list them). See Dependencies.hs +ifeq "$(TargetOS_CPP)" "irix" + @echo "#ifndef $(IRIX_MAJOR)_TARGET_OS" >> $@ + @echo "#define $(IRIX_MAJOR)_TARGET_OS 1" >> $@ + @echo "#endif" >> $@ +endif -++ Better names for build stages +But IRIX_MAJOR is never set anywhere in the build system. Dead code? -* Currently we have Stage0, Stage1, etc. It is not particularly clear -from the names what they stand for. We no longer need to stick to -numbers and can pick more helpful names, for example: -Stage0 -> Boot -Stage1 -> Interim -Stage2 -> Install -Stage3 -> Selftest +3. Command line options +----------------------- +Discuss the need for command line options, e.g. 'make GhcDebugged=YES'. Do we need to support all options as in the old build system? +Settings.User is fairly readable, so perhaps some options may be changeable only by editing this file and recompiling the build system (typically takes negligible time compared to building). This will simplify things. Can we come up with a must-have list for command line options? -i. Unclear abstractions Builder/BuildRule... +4. Better names for build stages +-------------------------------- -ii. Limits to build parallelism: GHC crashes during parallel builds. Also ghc-pkg and ghc-cabal are apparently not thread-safe, so I had to use Shake resources to limit the parallelism... +Currently we have Stage0, Stage1, etc. It is not particularly clear from the names what they stand for (as a newcomer to the build system I used to look up what these numbers stand for all the time). Shall we use this opportunity to pick more helpful names, for example: -iii. Discuss the need for command line options, e.g. make GhcDebugged=YES. This is a bit annoying to implement since Settings.User seems fairly readable, but recompiling the build systems for changing a flag may be annoying too. +Stage0 -> Boot +Stage1 -> Interim +Stage2 -> Install +Stage3 -> Selftest -iv. Do we need a name for the new build system? +5. Do we need a name for the new build system? +---------------------------------------------- -* At least we need a name for the folder in the GHC tree +* At least we need a name for the folder in the GHC tree. * If we call it 'shake' there may be a confusion with the Shake library. @@ -47,4 +79,3 @@ iv. Do we need a name for the new build system? build system' is overly verbose. Calling it 'shake' is confusing. * I haven't thought about any names yet, just checking whether we want to. - From git at git.haskell.org Fri Oct 27 00:09:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Proper support for `dot` (46bf4bc) Message-ID: <20171027000939.50B343A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46bf4bcb391b6008d39aa2c334ec265141fd6a80/ghc >--------------------------------------------------------------- commit 46bf4bcb391b6008d39aa2c334ec265141fd6a80 Author: Moritz Angermann Date: Thu Jan 14 14:03:05 2016 +0800 Proper support for `dot` Adds support for `dot`, by conditionally switching between `BS.putStr` and `BS.putStrLn` depending on the msg. The additional imports are part of shake anyway. Fixes #134, dot support for good :) >--------------------------------------------------------------- 46bf4bcb391b6008d39aa2c334ec265141fd6a80 shaking-up-ghc.cabal | 2 ++ src/Main.hs | 29 ++++++++++++++++++++++++++++- 2 files changed, 30 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index b38feac..123870d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -116,6 +116,7 @@ executable ghc-shake , ScopedTypeVariables build-depends: base , ansi-terminal >= 0.6 + , bytestring >= 0.10.6 , Cabal >= 1.22 , containers >= 0.5 , directory >= 1.2 @@ -125,5 +126,6 @@ executable ghc-shake , shake >= 0.15 , transformers >= 0.4 , unordered-containers >= 0.2 + , utf8-string >= 1.0.1 default-language: Haskell2010 ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j diff --git a/src/Main.hs b/src/Main.hs index e3f1a34..6ec93429 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -14,6 +14,10 @@ import qualified Rules.Perl import qualified Test import Oracles.Config.CmdLineFlag (putOptions, flags) +import qualified Data.ByteString.Char8 as BS +import qualified Data.ByteString.UTF8 as UTF8 +import Data.Char (chr) + main :: IO () main = shakeArgsWith options flags $ \cmdLineFlags targets -> do putOptions cmdLineFlags @@ -36,4 +40,27 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do options = shakeOptions { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple - , shakeTimings = True } + , shakeTimings = True + , shakeOutput = const showMsg + } + +showMsg :: String -> IO () +showMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg +showMsg msg | dropEscSequence msg == "" = return () +showMsg msg = BS.putStrLn . UTF8.fromString $ msg + +dropEscSequence :: String -> String +dropEscSequence = go + where + esc :: Char + esc = Data.Char.chr 27 + go :: String -> String + go [] = [] + go [x] = [x] + go (x:xs) | x == esc = skip xs + go (x:xs) | otherwise = x:go xs + skip :: String -> String + skip [] = [] + skip ['m'] = [] + skip ('m':xs) = go xs + skip (_ :xs) = skip xs From git at git.haskell.org Fri Oct 27 00:09:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename build directory (5f40553) Message-ID: <20171027000939.B16AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f405539ffaa3f453d244a53f86e9ee4ee0e8e6e/ghc >--------------------------------------------------------------- commit 5f405539ffaa3f453d244a53f86e9ee4ee0e8e6e Author: Andrey Mokhov Date: Thu Apr 28 23:43:28 2016 +0100 Rename build directory >--------------------------------------------------------------- 5f405539ffaa3f453d244a53f86e9ee4ee0e8e6e src/Settings/User.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index ef08df0..0893579 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -12,10 +12,9 @@ import Expression import Predicates import Settings.Default --- TODO: Rename to _build. -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath -buildRootPath = ".build" +buildRootPath = "_build" -- Control user-specific settings userArgs :: Args From git at git.haskell.org Fri Oct 27 00:09:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Complete Advanced Render Box (231a5ce) Message-ID: <20171027000943.0D9B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/231a5ce27baa03e0750e991b5d6af3b81d9cde29/ghc >--------------------------------------------------------------- commit 231a5ce27baa03e0750e991b5d6af3b81d9cde29 Author: Moritz Angermann Date: Thu Jan 14 14:16:41 2016 +0800 Complete Advanced Render Box Should fix #134 for good. >--------------------------------------------------------------- 231a5ce27baa03e0750e991b5d6af3b81d9cde29 src/Base.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index a46031c..b9c7f72 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -115,11 +115,16 @@ a -/- b = unifyPath $ a b infixr 6 -/- +-- | A wrapper around shakes @putNormal@ that substitutes +-- any message for a fullstop if @buildInfo@ is @Dot at . +putNormal' :: String -> Action () +putNormal' = if buildInfo == Dot then putNormal . const "." else putNormal + -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do liftIO $ setSGR [SetColor Foreground Vivid colour] - putNormal msg + putNormal' msg liftIO $ setSGR [] liftIO $ hFlush stdout From git at git.haskell.org Fri Oct 27 00:09:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for non-library packages. (c488f65) Message-ID: <20171027000943.928103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c488f65dd9a894af75e633c5bd78220d7b60cc84/ghc >--------------------------------------------------------------- commit c488f65dd9a894af75e633c5bd78220d7b60cc84 Author: Andrey Mokhov Date: Fri Sep 25 02:53:37 2015 +0100 Add support for non-library packages. >--------------------------------------------------------------- c488f65dd9a894af75e633c5bd78220d7b60cc84 src/GHC.hs | 21 +++++++++++++++------ src/Rules.hs | 7 ++++++- src/Rules/Data.hs | 4 ++-- src/Settings.hs | 8 +++++++- src/Settings/Packages.hs | 8 ++++---- src/Settings/TargetDirectory.hs | 2 ++ src/Settings/User.hs | 10 +++++++--- 7 files changed, 43 insertions(+), 17 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index c277c6a..668cf48 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,9 +4,10 @@ module GHC ( integerGmp, integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, - defaultKnownPackages, defaultTargetDirectory + defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where +import Base import Package import Stage @@ -66,8 +67,16 @@ xhtml = library "xhtml" -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal -- TODO: simplify to just 'show stage'? defaultTargetDirectory :: Stage -> Package -> FilePath -defaultTargetDirectory stage package - | package == compiler = "stage" ++ show (fromEnum stage + 1) - | package == ghc = "stage" ++ show (fromEnum stage + 1) - | stage == Stage0 = "dist-boot" - | otherwise = "dist-install" +defaultTargetDirectory stage pkg + | pkg == compiler = "stage" ++ show (fromEnum stage + 1) + | pkg == ghc = "stage" ++ show (fromEnum stage + 1) + | stage == Stage0 = "dist-boot" + | otherwise = "dist-install" + +defaultProgramPath :: Stage -> Package -> Maybe FilePath +defaultProgramPath stage pkg + | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) + | otherwise = Nothing + where + program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg + -/- "build/tmp" -/- name <.> exe diff --git a/src/Rules.hs b/src/Rules.hs index 26e57bd..e615c64 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -11,7 +11,8 @@ generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpretWithStage stage getPackages - fmap concat . forM pkgs $ \pkg -> do + let (libPkgs, programPkgs) = partition isLibrary pkgs + libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg buildPath = targetPath stage pkg -/- "build" libName <- interpretPartial target $ getPkgData LibName @@ -28,6 +29,10 @@ generateTargets = action $ do ++ [ haddock | needHaddock && stage == Stage1 ] ++ libs + let programTargets = map (fromJust . programPath stage) programPkgs + + return $ libTargets ++ programTargets + need $ reverse targets -- TODO: add Stage2 (compiler only?) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 3622918..1085f8f 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -17,7 +17,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fmap (path -/-) [ "package-data.mk" , "haddock-prologue.txt" - , "inplace-pkg-config" , "setup-config" , "build" -/- "autogen" -/- "cabal_macros.h" -- TODO: Is this needed? Also check out Paths_cpsa.hs. @@ -39,7 +38,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fullTarget target GhcCabal [cabalFile] outs -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg - whenM (interpretPartial target registerPackage) . + when (isLibrary pkg) . + whenM (interpretPartial target registerPackage) . buildWithResources [(ghcPkg rs, 1)] $ fullTarget target (GhcPkg stage) [cabalFile] outs diff --git a/src/Settings.hs b/src/Settings.hs index dab73ed..d16c5cd 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -3,7 +3,7 @@ module Settings ( module Settings.TargetDirectory, module Settings.User, module Settings.Ways, - getPkgData, getPkgDataList, + getPkgData, getPkgDataList, programPath, isLibrary, getPackagePath, getTargetDirectory, getTargetPath, getPackageSources, ) where @@ -29,6 +29,12 @@ getPkgData key = lift . pkgData . key =<< getTargetPath getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getTargetPath +programPath :: Stage -> Package -> Maybe FilePath +programPath = userProgramPath + +isLibrary :: Package -> Bool +isLibrary pkg = programPath Stage0 pkg == Nothing + -- Find all Haskell source files for the current target. TODO: simplify. getPackageSources :: Expr [FilePath] getPackageSources = do diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 8b913f5..1fe70dc 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -16,16 +16,16 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc, transformers ] + [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc + , templateHaskell, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 - , append [ array, base, bytestring, containers, deepseq, directory - , filepath, ghc, ghcPrim, haskeline, integerLibrary, pretty - , process, templateHaskell, time ] + , append [ array, base, bytestring, containers, deepseq, directory, filepath + , ghcPrim, haskeline, integerLibrary, pretty, process, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 58f2d51..b84d03d 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -5,6 +5,8 @@ module Settings.TargetDirectory ( import Expression import Settings.User +-- TODO: move to Settings.hs? + -- User can override the default target directory settings given below targetDirectory :: Stage -> Package -> FilePath targetDirectory = userTargetDirectory diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 9a71ac2..d841028 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,6 +1,6 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, - userKnownPackages, integerLibrary, + userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies ) where @@ -15,7 +15,7 @@ userArgs = mempty -- Control which packages get to be built userPackages :: Packages -userPackages = remove [ghc] +userPackages = mempty -- Add new user-defined packages userKnownPackages :: [Package] @@ -28,10 +28,14 @@ userLibWays = mempty userRtsWays :: Ways userRtsWays = mempty --- Control where build results go (see Settings.Default for an example) +-- Control where build results go (see GHC.hs for defaults) userTargetDirectory :: Stage -> Package -> FilePath userTargetDirectory = defaultTargetDirectory +-- Control how built programs are called (see GHC.hs for defaults) +userProgramPath :: Stage -> Package -> Maybe FilePath +userProgramPath = defaultProgramPath + -- Choose integer library: integerGmp, integerGmp2 or integerSimple integerLibrary :: Package integerLibrary = integerGmp From git at git.haskell.org Fri Oct 27 00:09:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update CI links (5779105) Message-ID: <20171027000944.33A193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/577910572ec2a02cef51889666d9c40d4e961bf1/ghc >--------------------------------------------------------------- commit 577910572ec2a02cef51889666d9c40d4e961bf1 Author: Andrey Mokhov Date: Fri Apr 29 00:01:49 2016 +0100 Update CI links >--------------------------------------------------------------- 577910572ec2a02cef51889666d9c40d4e961bf1 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 375e4f8..d4adfb1 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Hadrian ======= -[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/hadrian/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/hadrian) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current From git at git.haskell.org Fri Oct 27 00:09:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refinements. (59a30fe) Message-ID: <20171027000946.7B6DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59a30fe3270816ca27f514a3432e941538d7dcdc/ghc >--------------------------------------------------------------- commit 59a30fe3270816ca27f514a3432e941538d7dcdc Author: Moritz Angermann Date: Thu Jan 14 14:19:23 2016 +0800 Refinements. >--------------------------------------------------------------- 59a30fe3270816ca27f514a3432e941538d7dcdc src/Main.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 6ec93429..14f3554 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -41,14 +41,15 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True - , shakeOutput = const showMsg + , shakeOutput = const putMsg } -showMsg :: String -> IO () -showMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg -showMsg msg | dropEscSequence msg == "" = return () -showMsg msg = BS.putStrLn . UTF8.fromString $ msg +-- | Dynamic switch for @putStr@ and @putStrLn@ depending on the @msg at . +putMsg :: String -> IO () +putMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg +putMsg msg = BS.putStrLn . UTF8.fromString $ msg +-- | Drops ANSI Escape sequences from a string. dropEscSequence :: String -> String dropEscSequence = go where From git at git.haskell.org Fri Oct 27 00:09:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments/todos. (5e0734b) Message-ID: <20171027000947.1CD283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e0734bc2bfafc15e6b2de692a5b1f22a73217ec/ghc >--------------------------------------------------------------- commit 5e0734bc2bfafc15e6b2de692a5b1f22a73217ec Author: Andrey Mokhov Date: Sat Sep 26 22:56:01 2015 +0100 Add comments/todos. >--------------------------------------------------------------- 5e0734bc2bfafc15e6b2de692a5b1f22a73217ec doc/meeting-25-September-2015.txt | 23 ++++++++++++++++++++--- src/Settings/Builders/Alex.hs | 7 +++++++ src/Stage.hs | 1 + src/Target.hs | 4 ++-- 4 files changed, 30 insertions(+), 5 deletions(-) diff --git a/doc/meeting-25-September-2015.txt b/doc/meeting-25-September-2015.txt index dde2e45..166c3d8 100644 --- a/doc/meeting-25-September-2015.txt +++ b/doc/meeting-25-September-2015.txt @@ -14,11 +14,12 @@ Done: * Improve complexity when searching for module files (40x) Todo: Target: -* Build utils, rts October +* Build utils, rts & put in GHC tree October * Better dependencies (.hs-incl etc.) November * Support command line options December -* Validate November-December (GHC 8.0?) +* Validate November-December * Documentation December-January +* Journal paper + provenance December-February Notes: * Zero build: under 7 seconds @@ -26,6 +27,14 @@ Notes: * Limited parallelism: ghc-cabal/ghc-pkg not thread-safe, ghc fails on > 4 cores * Codebase growing: 50 files +Things to do: +-- Use OrderOnly for ordering ghc-cabal's +-- Fix parallel invokations of ghc-cabal +-- Fix GHC -M to handle .hs-incl (--make already knows how to do that) instead of writing a new parser. Maybe already done -- find a flag! +-- Rename files -> outputs, sources -> inputs +-- Start separating general bits from GHC bits. A separate package for Args maybe +-- Look up Bazel and Buck +-- Decompose args into builder-specific and package-specific 2. Seemingly dead-code ---------------------- @@ -46,7 +55,7 @@ ifeq "$(TargetOS_CPP)" "irix" @echo "#endif" >> $@ endif -But IRIX_MAJOR is never set anywhere in the build system. Dead code? +But IRIX_MAJOR is never set anywhere in the build system. Dead code? YES 3. Command line options @@ -56,6 +65,12 @@ Discuss the need for command line options, e.g. 'make GhcDebugged=YES'. Do we ne Settings.User is fairly readable, so perhaps some options may be changeable only by editing this file and recompiling the build system (typically takes negligible time compared to building). This will simplify things. Can we come up with a must-have list for command line options? +-- Try to support these first: +* EXTRA_HC_OPTS = file "asd" ? arg ".." +* EXTRA_CC_OPTS +* GhcDebugged = True +* make 2 + 4. Better names for build stages -------------------------------- @@ -79,3 +94,5 @@ Stage3 -> Selftest build system' is overly verbose. Calling it 'shake' is confusing. * I haven't thought about any names yet, just checking whether we want to. + +-- Use mk2 \ No newline at end of file diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs index 1e0f87b..257fd58 100644 --- a/src/Settings/Builders/Alex.hs +++ b/src/Settings/Builders/Alex.hs @@ -12,3 +12,10 @@ alexArgs = builder Alex ? do , package compiler ? arg "--latin1" , arg src , arg "-o", arg file ] + +-- TODO: +-- compilierArgs = package compiler ? builder Alex ? arg "awe" + +-- args = mconcat +-- [ alexArgs +-- , compilerArgs ] diff --git a/src/Stage.hs b/src/Stage.hs index edddb6f..e0a6124 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -5,6 +5,7 @@ import Base import GHC.Generics (Generic) -- TODO: rename to something more meaningful, e.g. 'Stage0' -> 'Boot'. +-- TODO: explain stages data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum, Generic) instance Show Stage where diff --git a/src/Target.hs b/src/Target.hs index 8e2a44e..257a896 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -22,8 +22,8 @@ data Target = Target package :: Package, builder :: Builder, way :: Way, - sources :: [FilePath], - files :: [FilePath] + sources :: [FilePath], -- input + files :: [FilePath] -- output } deriving (Show, Eq, Generic) From git at git.haskell.org Fri Oct 27 00:09:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build Hadrian in _build. (1317c88) Message-ID: <20171027000947.A05AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1317c886fe1293c3d21389e85ee154790a710cbd/ghc >--------------------------------------------------------------- commit 1317c886fe1293c3d21389e85ee154790a710cbd Author: Andrey Mokhov Date: Sat Apr 30 02:40:55 2016 +0100 Build Hadrian in _build. >--------------------------------------------------------------- 1317c886fe1293c3d21389e85ee154790a710cbd build.bat | 38 +++++++++++++++++++------------------- build.sh | 32 ++++++++++++++++---------------- src/Base.hs | 1 + src/Rules/Clean.hs | 18 ++++++++++-------- 4 files changed, 46 insertions(+), 43 deletions(-) diff --git a/build.bat b/build.bat index 2f6d4cd..19a2a05 100644 --- a/build.bat +++ b/build.bat @@ -1,24 +1,24 @@ @cd %~dp0 - at mkdir .shake 2> nul + at mkdir ../_build 2> nul - at set ghcArgs=--make ^ - -Wall ^ - -fno-warn-name-shadowing ^ - -XRecordWildCards ^ - src/Main.hs ^ - -threaded ^ - -isrc ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=.shake ^ - -j ^ - -O ^ - -o .shake/build + at set ghcArgs=--make ^ + -Wall ^ + -fno-warn-name-shadowing ^ + -XRecordWildCards ^ + src/Main.hs ^ + -threaded ^ + -isrc ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=../_build/hadrian ^ + -j ^ + -O ^ + -o ../_build/hadrian - at set shakeArgs=--lint ^ - --directory ^ - ".." ^ - %* + at set hadrianArgs=--lint ^ + --directory ^ + ".." ^ + %* @ghc %ghcArgs% @@ -27,4 +27,4 @@ @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains @set GHC_PACKAGE_PATH= - at .shake\build %shakeArgs% + at ..\_build\hadrian %hadrianArgs% diff --git a/build.sh b/build.sh index 95de2e6..8b53f81 100755 --- a/build.sh +++ b/build.sh @@ -30,22 +30,22 @@ function rl { root="$(dirname "$(rl "$0")")" -mkdir -p "$root/.shake" - -ghc \ - "$root/src/Main.hs" \ - -Wall \ - -fno-warn-name-shadowing \ - -XRecordWildCards \ - -i"$root/src" \ - -rtsopts \ - -with-rtsopts=-I0 \ - -threaded \ - -outputdir="$root/.shake" \ - -j -O \ - -o "$root/.shake/build" - -"$root/.shake/build" \ +mkdir -p "$root/../_build" + +ghc \ + "$root/src/Main.hs" \ + -Wall \ + -fno-warn-name-shadowing \ + -XRecordWildCards \ + -i"$root/src" \ + -rtsopts \ + -with-rtsopts=-I0 \ + -threaded \ + -outputdir="$root/../_build/hadrian" \ + -j -O \ + -o "$root/../_build/hadrian" + +"$root/../_build/hadrian" \ --lint \ --directory "$root/.." \ --colour \ diff --git a/src/Base.hs b/src/Base.hs index b94648e..53bb197 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -50,6 +50,7 @@ import System.IO shakePath :: FilePath shakePath = "hadrian" +-- TODO: Move to buildRootPath. shakeFilesPath :: FilePath shakeFilesPath = shakePath -/- ".db" diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index ea1cc37..357ac34 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -9,17 +9,19 @@ import Settings.Paths import Settings.User import Stage +clean :: FilePath -> Action () +clean dir = do + putBuild $ "| Remove files in " ++ dir ++ "..." + removeDirectoryIfExists dir + cleanRules :: Rules () cleanRules = do "clean" ~> do - putBuild $ "| Remove files in " ++ buildRootPath ++ "..." - liftIO $ removeFiles buildRootPath ["//*"] - putBuild $ "| Remove files in " ++ programInplacePath ++ "..." - liftIO $ removeFiles programInplacePath ["//*"] - putBuild $ "| Remove files in inplace/lib..." - liftIO $ removeFiles "inplace/lib" ["//*"] - putBuild $ "| Remove files in " ++ derivedConstantsPath ++ "..." - liftIO $ removeFiles derivedConstantsPath ["//*"] + forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) + clean (buildRootPath -/- "hadrian") + clean programInplacePath + clean "inplace/lib" + clean derivedConstantsPath forM_ includesDependencies $ \file -> do putBuild $ "| Remove " ++ file removeFileIfExists file From git at git.haskell.org Fri Oct 27 00:09:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #168 from kgardas/fix_gmp_args (dc90c3c) Message-ID: <20171027000950.1D91F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dc90c3ce5301a08b3d149d551580cf88e7221e5c/ghc >--------------------------------------------------------------- commit dc90c3ce5301a08b3d149d551580cf88e7221e5c Merge: 6934485 86a3fe5 Author: Andrey Mokhov Date: Thu Jan 14 12:32:46 2016 +0000 Merge pull request #168 from kgardas/fix_gmp_args fix handling of --with-gmp-* configure arguments [skip ci] >--------------------------------------------------------------- dc90c3ce5301a08b3d149d551580cf88e7221e5c src/Rules/Gmp.hs | 32 +++++++++++++++++++++----------- 1 file changed, 21 insertions(+), 11 deletions(-) From git at git.haskell.org Fri Oct 27 00:09:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Target fields: sources -> inputs, files -> outputs. (5a162b2) Message-ID: <20171027000951.0BBE53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a162b2a13746eb5ab90108323bbc6d416bd435a/ghc >--------------------------------------------------------------- commit 5a162b2a13746eb5ab90108323bbc6d416bd435a Author: Andrey Mokhov Date: Sat Sep 26 23:35:57 2015 +0100 Rename Target fields: sources -> inputs, files -> outputs. >--------------------------------------------------------------- 5a162b2a13746eb5ab90108323bbc6d416bd435a doc/demo.txt | 2 ++ src/Expression.hs | 32 ++++++++++++++++---------------- src/Oracles/ArgsHash.hs | 2 +- src/Predicates.hs | 2 +- src/Rules/Actions.hs | 6 +++--- src/Settings/Builders/Alex.hs | 13 +++++-------- src/Settings/Builders/Ar.hs | 9 +++------ src/Settings/Builders/Gcc.hs | 20 +++++++------------- src/Settings/Builders/Ghc.hs | 27 +++++++++++---------------- src/Settings/Builders/Haddock.hs | 9 ++++----- src/Settings/Builders/Happy.hs | 11 ++++------- src/Settings/Builders/HsCpp.hs | 7 ++----- src/Settings/Builders/Hsc2Hs.hs | 6 ++---- src/Settings/Builders/Ld.hs | 6 ++---- src/Stage.hs | 1 - src/Target.hs | 12 ++++++------ 16 files changed, 69 insertions(+), 96 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5a162b2a13746eb5ab90108323bbc6d416bd435a From git at git.haskell.org Fri Oct 27 00:09:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Appveyor CI. (f76a8be) Message-ID: <20171027000951.CE6BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f76a8bea7b7b5d797880621af089f9ee22cc1035/ghc >--------------------------------------------------------------- commit f76a8bea7b7b5d797880621af089f9ee22cc1035 Author: Andrey Mokhov Date: Sat Apr 30 13:01:49 2016 +0100 Fix Appveyor CI. >--------------------------------------------------------------- f76a8bea7b7b5d797880621af089f9ee22cc1035 appveyor.yml | 3 +++ 1 file changed, 3 insertions(+) diff --git a/appveyor.yml b/appveyor.yml index 3918779..8850273 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -36,6 +36,9 @@ install: - alex --version - happy --version - stack exec -- ghc-pkg list + - mkdir _build + - cd _build + - mkdir hadrian build_script: - cd C:\msys64\home\ghc\hadrian From git at git.haskell.org Fri Oct 27 00:09:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use doesDirectoryExist to workaround a getDirectoryContents bug. (34c999b) Message-ID: <20171027000953.B76CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34c999b8e9d78b848ef75f8b439b408eafdf7166/ghc >--------------------------------------------------------------- commit 34c999b8e9d78b848ef75f8b439b408eafdf7166 Author: Andrey Mokhov Date: Thu Jan 14 13:01:48 2016 +0000 Use doesDirectoryExist to workaround a getDirectoryContents bug. See #168. >--------------------------------------------------------------- 34c999b8e9d78b848ef75f8b439b408eafdf7166 src/Rules/Gmp.hs | 4 +--- src/Rules/Library.hs | 5 ++++- 2 files changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index f6d6fe8..c788ed2 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -118,10 +118,8 @@ gmpRules = do createDirectory $ takeDirectory gmpLibraryH -- check whether we need to build in tree gmp - -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` configMk <- liftIO . readFile $ gmpBase -/- "config.mk" - if "HaveFrameworkGMP = YES" `isInfixOf` configMk - || "HaveLibGmp = YES" `isInfixOf` configMk + if any (`isInfixOf` configMk) ["HaveFrameworkGMP = YES", "HaveLibGmp = YES"] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 6b2180c..0ffaf3f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -84,5 +84,8 @@ extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? - getDirectoryFiles "" [gmpObjects -/- "*.o"] + exists <- doesDirectoryExist gmpObjects + if exists + then getDirectoryFiles "" [gmpObjects -/- "*.o"] + else return [] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:09:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for compiling programs with Ghc builder. (d7b3d34) Message-ID: <20171027000955.1539F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d7b3d34b16e2519f2fa2d1eae96dd469d29e5824/ghc >--------------------------------------------------------------- commit d7b3d34b16e2519f2fa2d1eae96dd469d29e5824 Author: Andrey Mokhov Date: Mon Dec 7 01:42:30 2015 +0000 Add support for compiling programs with Ghc builder. >--------------------------------------------------------------- d7b3d34b16e2519f2fa2d1eae96dd469d29e5824 src/Settings/Builders/Ghc.hs | 32 +++++++++++++++++++++----------- 1 file changed, 21 insertions(+), 11 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index ad34e19..8ab4357 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,24 +2,32 @@ module Settings.Builders.Ghc (ghcArgs, ghcMArgs, commonGhcArgs) where import Expression import Oracles -import Predicates (stagedBuilder, splitObjects, stage0, notStage0) +import GHC +import Predicates (package, stagedBuilder, splitObjects, stage0, notStage0) import Settings -- TODO: add support for -dyno +-- TODO: consider adding a new builder for programs (e.g. GhcLink?) -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ -- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) ghcArgs :: Args -ghcArgs = stagedBuilder Ghc ? mconcat [ commonGhcArgs - , arg "-H32m" - , stage0 ? arg "-O" - , notStage0 ? arg "-O2" - , arg "-Wall" - , arg "-fwarn-tabs" - , splitObjects ? arg "-split-objs" - , arg "-c", append =<< getInputs - , arg "-o", arg =<< getOutput ] +ghcArgs = stagedBuilder Ghc ? do + output <- getOutput + way <- getWay + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + mconcat [ commonGhcArgs + , arg "-H32m" + , stage0 ? arg "-O" + , notStage0 ? arg "-O2" + , arg "-Wall" + , arg "-fwarn-tabs" + , buildObj ? splitObjects ? arg "-split-objs" + , package ghc ? arg "-no-hs-main" + , buildObj ? arg "-c" + , append =<< getInputs + , arg "-o", arg =<< getOutput ] ghcMArgs :: Args ghcMArgs = stagedBuilder GhcM ? do @@ -71,6 +79,7 @@ wayGhcArgs = do packageGhcArgs :: Args packageGhcArgs = do stage <- getStage + pkg <- getPackage supportsPackageKey <- getFlag SupportsPackageKey pkgKey <- getPkgData PackageKey pkgDepIds <- getPkgDataList DepIds @@ -78,7 +87,8 @@ packageGhcArgs = do [ arg "-hide-all-packages" , arg "-no-user-package-db" , stage0 ? arg "-package-db libraries/bootstrapping.conf" - , if supportsPackageKey || stage /= Stage0 + , isLibrary pkg ? + if supportsPackageKey || stage /= Stage0 then arg $ "-this-package-key " ++ pkgKey else arg $ "-package-name " ++ pkgKey , append $ map ("-package-id " ++) pkgDepIds ] From git at git.haskell.org Fri Oct 27 00:09:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Travis CI. (a37ad75) Message-ID: <20171027000955.AC9633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a37ad7507e8fef44d94e7e339c521e272bcdaa7e/ghc >--------------------------------------------------------------- commit a37ad7507e8fef44d94e7e339c521e272bcdaa7e Author: Andrey Mokhov Date: Sat Apr 30 13:03:56 2016 +0100 Fix Travis CI. >--------------------------------------------------------------- a37ad7507e8fef44d94e7e339c521e272bcdaa7e .travis.yml | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.travis.yml b/.travis.yml index 6832cd8..251f6ba 100644 --- a/.travis.yml +++ b/.travis.yml @@ -48,6 +48,8 @@ install: # ".git" directory into the appropriate location, and perform a hard reset # in order to regenerate the GHC-Shake files. - mkdir ghc/hadrian + - mkdir ghc/_build + - mkdir ghc/_build/hadrian - mv .git ghc/hadrian - ( cd ghc/hadrian && git reset --hard HEAD ) From git at git.haskell.org Fri Oct 27 00:09:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use system GMP on Windows. (ff0194b) Message-ID: <20171027000957.568CE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff0194b7a49cd554065fc68e209e1188be133bff/ghc >--------------------------------------------------------------- commit ff0194b7a49cd554065fc68e209e1188be133bff Author: Andrey Mokhov Date: Thu Jan 14 13:22:16 2016 +0000 Don't use system GMP on Windows. See #168. >--------------------------------------------------------------- ff0194b7a49cd554065fc68e209e1188be133bff src/Rules/Gmp.hs | 6 ++++-- src/Rules/Library.hs | 1 + 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index c788ed2..069dd28 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -117,9 +117,11 @@ gmpRules = do runConfigure (pkgPath integerGmp) envs intGmpArgs createDirectory $ takeDirectory gmpLibraryH - -- check whether we need to build in tree gmp + -- We don't use system GMP on Windows. TODO: fix? + windows <- windowsHost configMk <- liftIO . readFile $ gmpBase -/- "config.mk" - if any (`isInfixOf` configMk) ["HaveFrameworkGMP = YES", "HaveLibGmp = YES"] + if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES" + , "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 0ffaf3f..b53c472 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -84,6 +84,7 @@ extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? + -- FIXME: simplify after Shake's getDirectoryFiles bug is fixed, #168 exists <- doesDirectoryExist gmpObjects if exists then getDirectoryFiles "" [gmpObjects -/- "*.o"] From git at git.haskell.org Fri Oct 27 00:09:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove duplicates from library archives. (3cd6a3b) Message-ID: <20171027000959.4E9B43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3cd6a3b7e70f658db663251037a6f034e3ab89f0/ghc >--------------------------------------------------------------- commit 3cd6a3b7e70f658db663251037a6f034e3ab89f0 Author: Andrey Mokhov Date: Mon Dec 7 01:43:51 2015 +0000 Remove duplicates from library archives. >--------------------------------------------------------------- 3cd6a3b7e70f658db663251037a6f034e3ab89f0 src/Rules/Library.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b1c3f3c..d51e2ad 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,4 +1,4 @@ -module Rules.Library (buildPackageLibrary) where +module Rules.Library (buildPackageLibrary, cSources, hSources) where import Expression hiding (splitPath) import Oracles @@ -19,7 +19,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do cSrcs <- cSources target hSrcs <- hSources target - let way = detectWay a + let way = detectWay a -- TODO: eliminate differences below cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] @@ -28,14 +28,14 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do need $ cObjs ++ hObjs split <- interpretPartial target splitObjects - splitObjs <- if not split then return [] else + splitObjs <- if not split then return hObjs else -- TODO: make clearer! fmap concat $ forM hSrcs $ \src -> do let splitPath = buildPath -/- src ++ "_" ++ osuf way ++ "_split" contents <- liftIO $ IO.getDirectoryContents splitPath return . map (splitPath -/-) . filter (not . all (== '.')) $ contents - build $ fullTarget target Ar (cObjs ++ hObjs ++ splitObjs) [a] + build $ fullTarget target Ar (cObjs ++ splitObjs) [a] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built package library '" From git at git.haskell.org Fri Oct 27 00:09:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:09:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Hadrian executable to /hadrian. (666f5c2) Message-ID: <20171027000959.CA5103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/666f5c246d0465fd7c11bce4dadeacd46152edf5/ghc >--------------------------------------------------------------- commit 666f5c246d0465fd7c11bce4dadeacd46152edf5 Author: Andrey Mokhov Date: Sat Apr 30 14:35:22 2016 +0100 Move Hadrian executable to /hadrian. >--------------------------------------------------------------- 666f5c246d0465fd7c11bce4dadeacd46152edf5 .gitignore | 5 ++++- .travis.yml | 2 -- appveyor.yml | 3 --- build.bat | 6 +++--- build.sh | 6 +++--- src/Rules/Clean.hs | 3 +-- 6 files changed, 11 insertions(+), 14 deletions(-) diff --git a/.gitignore b/.gitignore index 967be07..b7bfddb 100644 --- a/.gitignore +++ b/.gitignore @@ -1,7 +1,10 @@ -/.shake/ /.db/ cfg/system.config +# build.bat and build.sh specific +/hadrian +/hadrian.exe + # build.cabal.sh specific /dist/ /.cabal-sandbox/ diff --git a/.travis.yml b/.travis.yml index 251f6ba..6832cd8 100644 --- a/.travis.yml +++ b/.travis.yml @@ -48,8 +48,6 @@ install: # ".git" directory into the appropriate location, and perform a hard reset # in order to regenerate the GHC-Shake files. - mkdir ghc/hadrian - - mkdir ghc/_build - - mkdir ghc/_build/hadrian - mv .git ghc/hadrian - ( cd ghc/hadrian && git reset --hard HEAD ) diff --git a/appveyor.yml b/appveyor.yml index 8850273..3918779 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -36,9 +36,6 @@ install: - alex --version - happy --version - stack exec -- ghc-pkg list - - mkdir _build - - cd _build - - mkdir hadrian build_script: - cd C:\msys64\home\ghc\hadrian diff --git a/build.bat b/build.bat index 19a2a05..f9f0b9a 100644 --- a/build.bat +++ b/build.bat @@ -1,5 +1,5 @@ @cd %~dp0 - at mkdir ../_build 2> nul + at mkdir ../_build/hadrian 2> nul @set ghcArgs=--make ^ -Wall ^ @@ -13,7 +13,7 @@ -outputdir=../_build/hadrian ^ -j ^ -O ^ - -o ../_build/hadrian + -o hadrian @set hadrianArgs=--lint ^ --directory ^ @@ -27,4 +27,4 @@ @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains @set GHC_PACKAGE_PATH= - at ..\_build\hadrian %hadrianArgs% + at hadrian %hadrianArgs% diff --git a/build.sh b/build.sh index 8b53f81..f7d06c2 100755 --- a/build.sh +++ b/build.sh @@ -30,7 +30,7 @@ function rl { root="$(dirname "$(rl "$0")")" -mkdir -p "$root/../_build" +mkdir -p "$root/../_build/hadrian" ghc \ "$root/src/Main.hs" \ @@ -43,9 +43,9 @@ ghc \ -threaded \ -outputdir="$root/../_build/hadrian" \ -j -O \ - -o "$root/../_build/hadrian" + -o "$root/hadrian" -"$root/../_build/hadrian" \ +"$root/hadrian" \ --lint \ --directory "$root/.." \ --colour \ diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 357ac34..0bff316 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -17,8 +17,7 @@ clean dir = do cleanRules :: Rules () cleanRules = do "clean" ~> do - forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) - clean (buildRootPath -/- "hadrian") + clean buildRootPath clean programInplacePath clean "inplace/lib" clean derivedConstantsPath From git at git.haskell.org Fri Oct 27 00:10:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting in renderAction. (14e5009) Message-ID: <20171027001000.CAE4A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14e50095ba46d4ab28cffda306008c41b00167e7/ghc >--------------------------------------------------------------- commit 14e50095ba46d4ab28cffda306008c41b00167e7 Author: Andrey Mokhov Date: Thu Jan 14 14:19:54 2016 +0000 Fix formatting in renderAction. [skip ci] >--------------------------------------------------------------- 14e50095ba46d4ab28cffda306008c41b00167e7 src/Base.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index be3ff1b..27fe5c1 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -145,12 +145,12 @@ putError msg = do renderAction :: String -> String -> String -> String renderAction what input output = case buildInfo of Normal -> renderBox [ what - , " input:" ++ input - , " => output:" ++ output ] + , " input: " ++ input + , " => output: " ++ output ] Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output Pony -> renderPony [ what - , " input:" ++ input - , " => output:" ++ output ] + , " input: " ++ input + , " => output: " ++ output ] Dot -> "." None -> "" From git at git.haskell.org Fri Oct 27 00:10:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add buildProgram rule. (3ceca89) Message-ID: <20171027001003.59F6D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ceca89902487a91a337e5a75f7f1de8b5bd4add/ghc >--------------------------------------------------------------- commit 3ceca89902487a91a337e5a75f7f1de8b5bd4add Author: Andrey Mokhov Date: Mon Dec 7 01:44:10 2015 +0000 Add buildProgram rule. >--------------------------------------------------------------- 3ceca89902487a91a337e5a75f7f1de8b5bd4add src/Rules/Package.hs | 4 +++- src/Rules/Program.hs | 29 +++++++++++++++++++++++++++++ 2 files changed, 32 insertions(+), 1 deletion(-) diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 9da4f8b..7a7d854 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -7,6 +7,7 @@ import Rules.Dependencies import Rules.Documentation import Rules.Generate import Rules.Library +import Rules.Program import Rules.Resources import Target @@ -17,4 +18,5 @@ buildPackage = mconcat , generatePackageCode , compilePackage , buildPackageLibrary - , buildPackageDocumentation ] + , buildPackageDocumentation + , buildProgram ] diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs new file mode 100644 index 0000000..14cbea0 --- /dev/null +++ b/src/Rules/Program.hs @@ -0,0 +1,29 @@ +module Rules.Program (buildProgram) where + +import Expression hiding (splitPath) +import Oracles +import Rules.Actions +import Rules.Library +import Rules.Resources +import Settings + +buildProgram :: Resources -> PartialTarget -> Rules () +buildProgram _ target @ (PartialTarget stage pkg) = do + let path = targetPath stage pkg + buildPath = path -/- "build" + program = programPath stage pkg + + (\f -> program == Just f) ?> \bin -> do + cSrcs <- cSources target -- TODO: remove code duplication (Library.hs) + hSrcs <- hSources target + let cObjs = [ buildPath -/- src -<.> osuf vanilla | src <- cSrcs ] + hObjs = [ buildPath -/- src <.> osuf vanilla | src <- hSrcs ] + objs = cObjs ++ hObjs + need objs + build $ fullTargetWithWay target (Ghc stage) vanilla objs [bin] + synopsis <- interpretPartial target $ getPkgData Synopsis + putSuccess $ "/--------\n| Successfully built program '" + ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + putSuccess $ "| Executable: " ++ bin + putSuccess $ "| Package synopsis: " + ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" From git at git.haskell.org Fri Oct 27 00:10:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Print out system.config when running CI. (e094834) Message-ID: <20171027001004.A70243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e094834509c6280ea2d049fea51e1a129ccac2ae/ghc >--------------------------------------------------------------- commit e094834509c6280ea2d049fea51e1a129ccac2ae Author: Andrey Mokhov Date: Thu Jan 14 17:53:50 2016 +0000 Print out system.config when running CI. >--------------------------------------------------------------- e094834509c6280ea2d049fea51e1a129ccac2ae .appveyor.yml | 1 + .travis.yml | 1 + 2 files changed, 2 insertions(+) diff --git a/.appveyor.yml b/.appveyor.yml index 68c1fd8..d8854cc 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,6 +30,7 @@ install: - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/185af600e91c5294fe8f49158ca8d73aec6ec646/ghc >--------------------------------------------------------------- commit 185af600e91c5294fe8f49158ca8d73aec6ec646 Author: Andrey Mokhov Date: Sat Apr 30 23:04:41 2016 +0100 Move Shake files into _build/hadrian >--------------------------------------------------------------- 185af600e91c5294fe8f49158ca8d73aec6ec646 src/Base.hs | 13 +------------ src/Main.hs | 4 ++-- src/Oracles/PackageDeps.hs | 4 +++- src/Rules/Clean.hs | 6 +++--- src/Settings/Paths.hs | 12 +++++++++++- 5 files changed, 20 insertions(+), 19 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 53bb197..a38ea51 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,8 +16,7 @@ module Base ( module Development.Shake.FilePath, -- * Paths - shakeFilesPath, configPath, configFile, sourcePath, programInplacePath, - bootPackageConstraints, packageDependencies, + configPath, configFile, sourcePath, programInplacePath, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, @@ -50,10 +49,6 @@ import System.IO shakePath :: FilePath shakePath = "hadrian" --- TODO: Move to buildRootPath. -shakeFilesPath :: FilePath -shakeFilesPath = shakePath -/- ".db" - configPath :: FilePath configPath = shakePath -/- "cfg" @@ -69,12 +64,6 @@ sourcePath = shakePath -/- "src" programInplacePath :: FilePath programInplacePath = "inplace/bin" -bootPackageConstraints :: FilePath -bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" - -packageDependencies :: FilePath -packageDependencies = shakeFilesPath -/- "package-dependencies" - -- Utility functions -- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] diff --git a/src/Main.hs b/src/Main.hs index cf45cc3..66f897f 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,7 +2,6 @@ module Main (main) where import Development.Shake -import qualified Base import qualified CmdLineFlag import qualified Environment import qualified Rules @@ -10,6 +9,7 @@ import qualified Rules.Clean import qualified Rules.Oracles import qualified Rules.Selftest import qualified Rules.Test +import qualified Settings.Paths main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -30,6 +30,6 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest - , shakeFiles = Base.shakeFilesPath + , shakeFiles = Settings.Paths.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 6a5f7dd..a2a9234 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -1,9 +1,11 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.PackageDeps (packageDeps, packageDepsOracle) where -import Base import qualified Data.HashMap.Strict as Map + +import Base import Package +import Settings.Paths newtype PackageDepsKey = PackageDepsKey PackageName deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 0bff316..ca5c062 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -17,7 +17,7 @@ clean dir = do cleanRules :: Rules () cleanRules = do "clean" ~> do - clean buildRootPath + forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) clean programInplacePath clean "inplace/lib" clean derivedConstantsPath @@ -29,6 +29,6 @@ cleanRules = do forM_ [Stage0 ..] $ \stage -> do let dir = pkgPath pkg -/- contextDirectory (vanillaContext stage pkg) removeDirectoryIfExists dir - putBuild $ "| Remove the Shake database " ++ shakeFilesPath ++ "..." - removeFilesAfter shakeFilesPath ["//*"] + putBuild $ "| Remove Hadrian files..." + removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 678ed92..77fb5a5 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,8 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpBuildInfoPath, - packageDbDirectory, pkgConfFile + packageDbDirectory, pkgConfFile, shakeFilesPath, bootPackageConstraints, + packageDependencies ) where import Base @@ -16,6 +17,15 @@ import Settings.User (~/~) :: FilePath -> FilePath -> FilePath x ~/~ y = x ++ '/' : y +shakeFilesPath :: FilePath +shakeFilesPath = buildRootPath -/- "hadrian/shake-files" + +bootPackageConstraints :: FilePath +bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" + +packageDependencies :: FilePath +packageDependencies = shakeFilesPath -/- "package-dependencies" + -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath buildPath context at Context {..} = From git at git.haskell.org Fri Oct 27 00:10:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass dll0 modules to ghc-cabal for the compiler package. (1c09363) Message-ID: <20171027001006.CE8433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c09363fd8631cd43a885bb8399455b02fc026d1/ghc >--------------------------------------------------------------- commit 1c09363fd8631cd43a885bb8399455b02fc026d1 Author: Andrey Mokhov Date: Mon Dec 7 02:27:38 2015 +0000 Pass dll0 modules to ghc-cabal for the compiler package. >--------------------------------------------------------------- 1c09363fd8631cd43a885bb8399455b02fc026d1 src/Settings/Builders/GhcCabal.hs | 193 +++++++++++++++++++++++++++++++++++--- 1 file changed, 181 insertions(+), 12 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 582a56c..df4af2b 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -4,7 +4,7 @@ module Settings.Builders.GhcCabal ( ) where import Expression -import Predicates +import Predicates hiding (stage) import Settings cabalArgs :: Args @@ -14,7 +14,7 @@ cabalArgs = builder GhcCabal ? do mconcat [ arg "configure" , arg path , arg dir - , dllArgs + , dll0Args , withStaged Ghc , withStaged GhcPkg , stage0 ? bootPackageDbArgs @@ -40,12 +40,12 @@ ghcCabalHsColourArgs = builder GhcCabalHsColour ? do -- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do - ways <- getWays - ghcInt <- lift $ ghcWithInterpreter + ways <- getWays + ghci <- lift ghcWithInterpreter append [ if vanilla `elem` ways then "--enable-library-vanilla" else "--disable-library-vanilla" - , if vanilla `elem` ways && ghcInt && not dynamicGhcPrograms + , if vanilla `elem` ways && ghci && not dynamicGhcPrograms then "--enable-library-for-ghci" else "--disable-library-for-ghci" , if profiling `elem` ways @@ -81,13 +81,6 @@ bootPackageDbArgs = do path <- getSetting GhcSourcePath arg $ "--package-db=" ++ path -/- "libraries/bootstrapping.conf" --- This is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument; --- * otherwise, we must collapse it into one space-separated string. --- TODO: should be non-empty for compiler -dllArgs :: Args -dllArgs = arg "" - packageConstraints :: Args packageConstraints = stage0 ? do constraints <- lift . readFileLines $ bootPackageConstraints @@ -219,3 +212,179 @@ appendCcArgs xs = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" xs , builder GhcCabal ? appendSub "--gcc-options" xs ] +-- This is a positional argument, hence: +-- * if it is empty, we need to emit one empty string argument; +-- * otherwise, we must collapse it into one space-separated string. +dll0Args :: Args +dll0Args = do + windows <- lift windowsHost + pkg <- getPackage + stage <- getStage + let needDll0Args = windows && pkg == compiler && stage == Stage1 + ghci <- lift ghcWithInterpreter + arg . unwords . concat $ [ modules | needDll0Args ] + ++ [ ghciModules | needDll0Args && ghci ] -- see #9552 + where + modules = [ "Annotations" + , "ApiAnnotation" + , "Avail" + , "Bag" + , "BasicTypes" + , "Binary" + , "BooleanFormula" + , "BreakArray" + , "BufWrite" + , "Class" + , "CmdLineParser" + , "CmmType" + , "CoAxiom" + , "ConLike" + , "Coercion" + , "Config" + , "Constants" + , "CoreArity" + , "CoreFVs" + , "CoreSubst" + , "CoreSyn" + , "CoreTidy" + , "CoreUnfold" + , "CoreUtils" + , "CoreSeq" + , "CoreStats" + , "CostCentre" + , "Ctype" + , "DataCon" + , "Demand" + , "Digraph" + , "DriverPhases" + , "DynFlags" + , "Encoding" + , "ErrUtils" + , "Exception" + , "ExtsCompat46" + , "FamInstEnv" + , "FastFunctions" + , "FastMutInt" + , "FastString" + , "FastTypes" + , "Fingerprint" + , "FiniteMap" + , "ForeignCall" + , "Hooks" + , "HsBinds" + , "HsDecls" + , "HsDoc" + , "HsExpr" + , "HsImpExp" + , "HsLit" + , "PlaceHolder" + , "HsPat" + , "HsSyn" + , "HsTypes" + , "HsUtils" + , "HscTypes" + , "IOEnv" + , "Id" + , "IdInfo" + , "IfaceSyn" + , "IfaceType" + , "InstEnv" + , "Kind" + , "Lexeme" + , "Lexer" + , "ListSetOps" + , "Literal" + , "Maybes" + , "MkCore" + , "MkId" + , "Module" + , "MonadUtils" + , "Name" + , "NameEnv" + , "NameSet" + , "OccName" + , "OccurAnal" + , "OptCoercion" + , "OrdList" + , "Outputable" + , "PackageConfig" + , "Packages" + , "Pair" + , "Panic" + , "PatSyn" + , "PipelineMonad" + , "Platform" + , "PlatformConstants" + , "PprCore" + , "PrelNames" + , "PrelRules" + , "Pretty" + , "PrimOp" + , "RdrName" + , "Rules" + , "Serialized" + , "SrcLoc" + , "StaticFlags" + , "StringBuffer" + , "TcEvidence" + , "TcRnTypes" + , "TcType" + , "TrieMap" + , "TyCon" + , "Type" + , "TypeRep" + , "TysPrim" + , "TysWiredIn" + , "Unify" + , "UniqFM" + , "UniqSet" + , "UniqSupply" + , "Unique" + , "Util" + , "Var" + , "VarEnv" + , "VarSet" ] + ghciModules = [ "Bitmap" + , "BlockId" + , "ByteCodeAsm" + , "ByteCodeInstr" + , "ByteCodeItbls" + , "CLabel" + , "Cmm" + , "CmmCallConv" + , "CmmExpr" + , "CmmInfo" + , "CmmMachOp" + , "CmmNode" + , "CmmSwitch" + , "CmmUtils" + , "CodeGen.Platform" + , "CodeGen.Platform.ARM" + , "CodeGen.Platform.ARM64" + , "CodeGen.Platform.NoRegs" + , "CodeGen.Platform.PPC" + , "CodeGen.Platform.PPC_Darwin" + , "CodeGen.Platform.SPARC" + , "CodeGen.Platform.X86" + , "CodeGen.Platform.X86_64" + , "FastBool" + , "Hoopl" + , "Hoopl.Dataflow" + , "InteractiveEvalTypes" + , "MkGraph" + , "PprCmm" + , "PprCmmDecl" + , "PprCmmExpr" + , "Reg" + , "RegClass" + , "SMRep" + , "StgCmmArgRep" + , "StgCmmClosure" + , "StgCmmEnv" + , "StgCmmLayout" + , "StgCmmMonad" + , "StgCmmProf" + , "StgCmmTicky" + , "StgCmmUtils" + , "StgSyn" + , "Stream" ] From git at git.haskell.org Fri Oct 27 00:10:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use in-tree Cabal library. (e6373a0) Message-ID: <20171027001007.97B7D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e6373a064cac830b4ee1a1651d888c5b64b9ca80/ghc >--------------------------------------------------------------- commit e6373a064cac830b4ee1a1651d888c5b64b9ca80 Author: Andrey Mokhov Date: Sun May 1 00:40:08 2016 +0100 Use in-tree Cabal library. See #228. >--------------------------------------------------------------- e6373a064cac830b4ee1a1651d888c5b64b9ca80 build.bat | 1 + build.sh | 1 + 2 files changed, 2 insertions(+) diff --git a/build.bat b/build.bat index f9f0b9a..6e86d42 100644 --- a/build.bat +++ b/build.bat @@ -11,6 +11,7 @@ -rtsopts ^ -with-rtsopts=-I0 ^ -outputdir=../_build/hadrian ^ + -i../libraries/Cabal/Cabal ^ -j ^ -O ^ -o hadrian diff --git a/build.sh b/build.sh index f7d06c2..fff8df4 100755 --- a/build.sh +++ b/build.sh @@ -38,6 +38,7 @@ ghc \ -fno-warn-name-shadowing \ -XRecordWildCards \ -i"$root/src" \ + -i"$root/../libraries/Cabal/Cabal" \ -rtsopts \ -with-rtsopts=-I0 \ -threaded \ From git at git.haskell.org Fri Oct 27 00:10:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix comments. (f792789) Message-ID: <20171027001008.1CF3A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f79278948b635567c1b0830a9539b97551db8dd5/ghc >--------------------------------------------------------------- commit f79278948b635567c1b0830a9539b97551db8dd5 Author: Andrey Mokhov Date: Thu Jan 14 17:59:21 2016 +0000 Fix comments. [skip ci] >--------------------------------------------------------------- f79278948b635567c1b0830a9539b97551db8dd5 cfg/system.config.in | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 498f78c..8b5b553 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -1,5 +1,6 @@ -# Edit 'user.config' to override these settings. -#=============================================== +# This file is processed by the configure script +# See 'Settings/User.hs' for user-defined settings +#================================================= # Paths to builders: #=================== From git at git.haskell.org Fri Oct 27 00:10:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcLink builder. (49dfde7) Message-ID: <20171027001010.502533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49dfde799495f1d8bfdc2a891bc6e930879a855e/ghc >--------------------------------------------------------------- commit 49dfde799495f1d8bfdc2a891bc6e930879a855e Author: Andrey Mokhov Date: Wed Dec 9 01:57:52 2015 +0000 Add GhcLink builder. >--------------------------------------------------------------- 49dfde799495f1d8bfdc2a891bc6e930879a855e src/Builder.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index c0ffee0..67be69f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -25,6 +25,7 @@ data Builder = Alex | Ghc Stage | GhcCabal | GhcCabalHsColour + | GhcLink Stage | GhcM Stage | GhcPkg Stage | GhcSplit @@ -50,6 +51,7 @@ builderKey builder = case builder of Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" + GhcLink stage -> builderKey $ Ghc stage -- using Ghc as linker GhcM stage -> builderKey $ Ghc stage -- synonym for 'Ghc -M' GhcCabal -> "ghc-cabal" GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' From git at git.haskell.org Fri Oct 27 00:10:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Turn Configure into a Builder. (72f6ec6) Message-ID: <20171027001011.4BAF93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72f6ec653e2f8801fc275ffa5d294a85e6e34ee8/ghc >--------------------------------------------------------------- commit 72f6ec653e2f8801fc275ffa5d294a85e6e34ee8 Author: Andrey Mokhov Date: Mon May 2 02:49:30 2016 +0100 Turn Configure into a Builder. >--------------------------------------------------------------- 72f6ec653e2f8801fc275ffa5d294a85e6e34ee8 hadrian.cabal | 1 + src/Builder.hs | 70 ++++++++++++++++++-------------------- src/Predicates.hs | 17 +++++++-- src/Rules/Actions.hs | 53 ++++++++++++++--------------- src/Rules/Gmp.hs | 19 ++++------- src/Rules/Libffi.hs | 51 ++++++++++++--------------- src/Rules/Setup.hs | 19 +++++++---- src/Settings/Args.hs | 2 ++ src/Settings/Builders/Configure.hs | 30 ++++++++++++++++ src/Settings/Paths.hs | 6 +++- src/Settings/User.hs | 2 +- 11 files changed, 155 insertions(+), 115 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 72f6ec653e2f8801fc275ffa5d294a85e6e34ee8 From git at git.haskell.org Fri Oct 27 00:10:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Detect the right patch command and use it when building gmp. (79cf2e3) Message-ID: <20171027001011.C6C4E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79cf2e3d1f5d48ff731060f4c0f17cd7e8310514/ghc >--------------------------------------------------------------- commit 79cf2e3d1f5d48ff731060f4c0f17cd7e8310514 Author: Andrey Mokhov Date: Thu Jan 14 23:41:31 2016 +0000 Detect the right patch command and use it when building gmp. See #158. >--------------------------------------------------------------- 79cf2e3d1f5d48ff731060f4c0f17cd7e8310514 cfg/system.config.in | 5 +++-- src/Builder.hs | 2 ++ src/Rules/Actions.hs | 11 ++++++++++- src/Rules/Gmp.hs | 6 +----- 4 files changed, 16 insertions(+), 8 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 8b5b553..4539979 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -1,6 +1,6 @@ # This file is processed by the configure script -# See 'Settings/User.hs' for user-defined settings -#================================================= +# See 'src/Settings/User.hs' for user-defined settings +#===================================================== # Paths to builders: #=================== @@ -40,6 +40,7 @@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ tar = @TarCmd@ +patch = @PatchCmd@ perl = @PerlCmd@ # Information about builders: diff --git a/src/Builder.hs b/src/Builder.hs index efc3216..353c00f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -40,6 +40,7 @@ data Builder = Alex | Ld | Nm | Objdump + | Patch | Perl | Ranlib | Tar @@ -82,6 +83,7 @@ builderKey builder = case builder of Ld -> "ld" Nm -> "nm" Objdump -> "objdump" + Patch -> "patch" Perl -> "perl" Ranlib -> "ranlib" Tar -> "tar" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index eb37630..7692c86 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,7 +1,7 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, moveDirectory, - fixFile, runConfigure, runMake, runBuilder, makeExecutable + fixFile, runConfigure, runMake, applyPatch, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -108,6 +108,15 @@ runMake dir args = do putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) makeCommand ["-C", dir] args +applyPatch :: FilePath -> FilePath -> Action () +applyPatch dir patch = do + let file = dir -/- patch + need [file] + needBuilder False Patch + path <- builderPath Patch + putBuild $ "| Apply patch " ++ file + quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] + runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do needBuilder laxDependencies builder diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 069dd28..eb1158e 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -73,7 +73,6 @@ gmpRules = do gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - -- Do we need this step? liftIO $ removeFiles gmpBuildPath ["//*"] -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is @@ -86,17 +85,14 @@ gmpRules = do ++ "(found: " ++ show tarballs ++ ")." need tarballs - createDirectory gmpBuildPath build $ fullTarget gmpTarget Tar tarballs [gmpBuildPath] - -- TODO: replace "patch" with PATCH_CMD forM_ gmpPatches $ \src -> do let patch = takeFileName src patchPath = gmpBuildPath -/- patch copyFile src patchPath - putBuild $ "| Apply " ++ patchPath - unit . quietly $ cmd Shell (EchoStdout False) [Cwd gmpBuildPath] "patch -p0 <" [patch] + applyPatch gmpBuildPath patch -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? From git at git.haskell.org Fri Oct 27 00:10:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add basic support for -0 libraries. (3e82d46) Message-ID: <20171027001013.D722A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e82d460ba762334e7d52be121a1fa698dda42e4/ghc >--------------------------------------------------------------- commit 3e82d460ba762334e7d52be121a1fa698dda42e4 Author: Andrey Mokhov Date: Wed Dec 9 01:58:53 2015 +0000 Add basic support for -0 libraries. >--------------------------------------------------------------- 3e82d460ba762334e7d52be121a1fa698dda42e4 src/Rules.hs | 8 ++++++-- src/Rules/Library.hs | 5 ++++- 2 files changed, 10 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index e615c64..2e2963f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,6 +5,7 @@ import Oracles import Rules.Package import Rules.Resources import Settings +import Settings.Builders.GhcCabal -- generateTargets needs top-level build targets generateTargets :: Rules () @@ -21,9 +22,12 @@ generateTargets = action $ do ways <- interpretPartial target getWays let ghciLib = buildPath -/- "HS" ++ libName <.> "o" haddock = pkgHaddockFile pkg - libs <- forM ways $ \way -> do + libs <- fmap concat . forM ways $ \way -> do extension <- libsuf way - return $ buildPath -/- "libHS" ++ libName <.> extension + let name = buildPath -/- "libHS" ++ libName + dll0 <- needDll0 stage pkg + return $ [ name <.> extension ] + ++ [ name ++ "-0" <.> extension | dll0 ] return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] ++ [ haddock | needHaddock && stage == Stage1 ] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index d51e2ad..9e4f7d5 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -15,6 +15,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do + removeFileIfExists a cSrcs <- cSources target hSrcs <- hSources target @@ -35,7 +36,9 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do return . map (splitPath -/-) . filter (not . all (== '.')) $ contents - build $ fullTarget target Ar (cObjs ++ splitObjs) [a] + if "//*-0.*" ?== a + then build $ fullTarget target Ar [] [a] + else build $ fullTarget target Ar (cObjs ++ splitObjs) [a] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built package library '" From git at git.haskell.org Fri Oct 27 00:10:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do putInfo even in verbose mode, minor revision. (0b6c0aa) Message-ID: <20171027001015.533653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b6c0aa0b4dcbbc3eb65a101edf7db64c72043b4/ghc >--------------------------------------------------------------- commit 0b6c0aa0b4dcbbc3eb65a101edf7db64c72043b4 Author: Andrey Mokhov Date: Mon May 2 03:08:10 2016 +0100 Do putInfo even in verbose mode, minor revision. >--------------------------------------------------------------- 0b6c0aa0b4dcbbc3eb65a101edf7db64c72043b4 src/Rules/Actions.hs | 3 ++- src/Settings/User.hs | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5af1ce4..f006947 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -46,7 +46,7 @@ customBuild rs opts target at Target {..} = do -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do - unless verbose $ putInfo target + putInfo target quietlyUnlessVerbose $ case builder of Ar -> do output <- interpret target getOutput @@ -59,6 +59,7 @@ customBuild rs opts target at Target {..} = do Configure dir -> do need [dir -/- "configure"] + -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" cmd Shell (EchoStdout False) [Cwd dir] [path] (env:opts) argList diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 215a05b..0893579 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -81,7 +81,7 @@ buildHaddock = return cmdBuildHaddock -- this is a Predicate, hence you can enable verbose output for a chosen package -- only, e.g.: verboseCommands = package ghcPrim verboseCommands :: Predicate -verboseCommands = builder Configure +verboseCommands = return False -- TODO: Replace with stage2 ? arg "-Werror"? -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. From git at git.haskell.org Fri Oct 27 00:10:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Work on command lines for compiling stage 2 GHC. (159903e) Message-ID: <20171027001017.51B943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/159903e948cb8d3497235e4dd2c0f2c1ddde3227/ghc >--------------------------------------------------------------- commit 159903e948cb8d3497235e4dd2c0f2c1ddde3227 Author: Andrey Mokhov Date: Wed Dec 9 02:00:09 2015 +0000 Work on command lines for compiling stage 2 GHC. >--------------------------------------------------------------- 159903e948cb8d3497235e4dd2c0f2c1ddde3227 src/Settings/Builders/Ghc.hs | 108 +++++++++++++++++++++++++++++++++++++- src/Settings/Builders/GhcCabal.hs | 20 ++++--- 2 files changed, 119 insertions(+), 9 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 8ab4357..8d1a30f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,10 +1,13 @@ -module Settings.Builders.Ghc (ghcArgs, ghcMArgs, commonGhcArgs) where +module Settings.Builders.Ghc ( + ghcArgs, ghcMArgs, ghcLinkArgs, commonGhcArgs + ) where import Expression import Oracles import GHC import Predicates (package, stagedBuilder, splitObjects, stage0, notStage0) import Settings +import Settings.Builders.GhcCabal -- TODO: add support for -dyno -- TODO: consider adding a new builder for programs (e.g. GhcLink?) @@ -17,6 +20,8 @@ ghcArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + libs <- getPkgDataList DepExtraLibs + libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -25,6 +30,9 @@ ghcArgs = stagedBuilder Ghc ? do , arg "-fwarn-tabs" , buildObj ? splitObjects ? arg "-split-objs" , package ghc ? arg "-no-hs-main" + , not buildObj ? arg "-no-auto-link-packages" + , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ] + , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" , append =<< getInputs , arg "-o", arg =<< getOutput ] @@ -116,3 +124,101 @@ includeGhcArgs = do -- define libraries/ghc-prim_PACKAGE_MAGIC -- libraries/ghc-prim_dist-install_MODULES := $$(filter-out GHC.Prim,$$(libraries/ghc-prim_dist-install_MODULES)) -- endef + + +-- # Options for passing to plain ld +-- $1_$2_$3_ALL_LD_OPTS = \ +-- $$(WAY_$3_LD_OPTS) \ +-- $$($1_$2_DIST_LD_OPTS) \ +-- $$($1_$2_$3_LD_OPTS) \ +-- $$($1_$2_EXTRA_LD_OPTS) \ +-- $$(EXTRA_LD_OPTS) + +-- # Options for passing to GHC when we use it for linking +-- $1_$2_$3_GHC_LD_OPTS = \ +-- $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ +-- $$($1_$2_$3_MOST_HC_OPTS) + +-- TODO: add support for TargetElf and darwin +-- ifeq "$3" "dyn" +-- ifneq "$4" "0" +-- ifeq "$$(TargetElf)" "YES" +-- $1_$2_$3_GHC_LD_OPTS += \ +-- -fno-use-rpaths \ +-- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'$$$$ORIGIN/../$$d') -optl-Wl,-zorigin +-- else ifeq "$$(TargetOS_CPP)" "darwin" +-- $1_$2_$3_GHC_LD_OPTS += \ +-- -fno-use-rpaths \ +-- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') + +-- ifeq "$$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS)" "" +-- # We don't want to link the GHC RTS into C-only programs. There's no +-- # point, and it confuses the test that all GHC-compiled programs +-- # were compiled with the right GHC. +-- $1_$2_$$($1_$2_PROGRAM_WAY)_GHC_LD_OPTS += -no-auto-link-packages -no-hs-main +-- endif + +ghcLinkArgs :: Args +ghcLinkArgs = mempty + -- way <- getRtsWays + -- path <- getTargetPath + -- mconcat [ commonGhcArgs + -- , (way == dynamic) ? needDll0Args ? + -- arg $ "-dll-split " ++ path -/- "dll-split" + -- , appendSubD "-optl" (getSettingList . ConfLdLinkerArgs =<< getStage) + -- , appendSubD "-optl-L" (lift $ pkgDataList DepLibDirs) + -- , appendSubD "-optl-l" (lift $ pkgDataList DepExtraLibs) + -- , splitObjects ? arg "-split-objs" + -- , package ghc ? arg "-no-hs-main" + -- , append =<< getInputs + -- , arg "-o", arg =<< getOutput ] + + +-- # Link a dynamic library +-- # On windows we have to supply the extra libs this one links to when building it. +-- ifeq "$$(HostOS_CPP)" "mingw32" +-- $$($1_$2_$3_LIB) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) +-- ifneq "$$($1_$2_$3_LIB0)" "" +-- $$(call build-dll,$1,$2,$3, +-- -L$1/$2/build -l$$($1_$2_$3_LIB0_ROOT), +-- $$(filter-out $$($1_$2_dll0_HS_OBJS),$$($1_$2_$3_HS_OBJS)) +-- $$($1_$2_$3_NON_HS_OBJS),$$@) +-- else +-- $$(call build-dll,$1,$2,$3,,$$($1_$2_$3_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$@) +-- endif + +-- ifneq "$$($1_$2_$3_LIB0)" "" +-- $$($1_$2_$3_LIB) : $$($1_$2_$3_LIB0) +-- $$($1_$2_$3_LIB0) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) +-- $$(call build-dll,$1,$2,$3,,$$($1_$2_dll0_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$($1_$2_$3_LIB0)) +-- endif + + + +-- # $1 = dir +-- # $2 = distdir +-- # $3 = way +-- # $4 = extra flags +-- # $5 = object files to link +-- # $6 = output filename +-- define build-dll +-- $(call cmd,$1_$2_HC) $($1_$2_$3_ALL_HC_OPTS) $($1_$2_$3_GHC_LD_OPTS) $4 $5 \ +-- -shared -dynamic -dynload deploy \ +-- $(addprefix -l,$($1_$2_EXTRA_LIBRARIES)) \ +-- -no-auto-link-packages \ +-- -o $6 +-- # Now check that the DLL doesn't have too many symbols. See trac #5987. +-- SYMBOLS=`$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail -n +2 | wc -l`; echo "Number of symbols in $6: $$SYMBOLS" +-- case `$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | grep "\[ *0\]" | wc -l` in 1) echo DLL $6 OK;; 0) echo No symbols in DLL $6; exit 1;; [0-9]*) echo Too many symbols in DLL $6; $(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail; exit 1;; *) echo bad DLL $6; exit 1;; esac +-- endef + + + +-- TODO: add -dynamic-too? +-- # $1_$2_$3_ALL_HC_OPTS: this is all the options we will pass to GHC +-- # for a given ($1,$2,$3). +-- $1_$2_$3_ALL_HC_OPTS = \ +-- -hisuf $$($3_hisuf) -osuf $$($3_osuf) -hcsuf $$($3_hcsuf) \ +-- $$($1_$2_$3_MOST_DIR_HC_OPTS) \ +-- $$(if $$(findstring YES,$$($1_$2_SplitObjs)),$$(if $$(findstring dyn,$3),,-split-objs),) \ +-- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),$$(if $$(findstring v,$3),-dynamic-too)) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index df4af2b..793a7f7 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,6 +1,6 @@ module Settings.Builders.GhcCabal ( cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, - ccArgs, cppArgs, ccWarnings, argStagedSettingList + ccArgs, cppArgs, ccWarnings, argStagedSettingList, needDll0 ) where import Expression @@ -212,18 +212,22 @@ appendCcArgs xs = do , builder GhcCabal ? appendSub "--configure-option=CFLAGS" xs , builder GhcCabal ? appendSub "--gcc-options" xs ] +needDll0 :: Stage -> Package -> Action Bool +needDll0 stage pkg = do + windows <- windowsHost + return $ windows && pkg == compiler && stage == Stage1 + -- This is a positional argument, hence: -- * if it is empty, we need to emit one empty string argument; -- * otherwise, we must collapse it into one space-separated string. dll0Args :: Args dll0Args = do - windows <- lift windowsHost - pkg <- getPackage - stage <- getStage - let needDll0Args = windows && pkg == compiler && stage == Stage1 - ghci <- lift ghcWithInterpreter - arg . unwords . concat $ [ modules | needDll0Args ] - ++ [ ghciModules | needDll0Args && ghci ] -- see #9552 + stage <- getStage + pkg <- getPackage + dll0 <- lift $ needDll0 stage pkg + ghci <- lift ghcWithInterpreter + arg . unwords . concat $ [ modules | dll0 ] + ++ [ ghciModules | dll0 && ghci ] -- see #9552 where modules = [ "Annotations" , "ApiAnnotation" From git at git.haskell.org Fri Oct 27 00:10:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drops dot, adds none; renames pony to unicorn (da96a23) Message-ID: <20171027001019.4E75B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da96a236f4678b2e64535bfe7a57928275d5aca1/ghc >--------------------------------------------------------------- commit da96a236f4678b2e64535bfe7a57928275d5aca1 Author: Moritz Angermann Date: Fri Jan 15 15:22:17 2016 +0800 Drops dot, adds none; renames pony to unicorn >--------------------------------------------------------------- da96a236f4678b2e64535bfe7a57928275d5aca1 shaking-up-ghc.cabal | 2 -- src/Base.hs | 23 ++++++++++------------- src/Main.hs | 27 --------------------------- src/Oracles/Config/CmdLineFlag.hs | 14 +++++++------- 4 files changed, 17 insertions(+), 49 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 123870d..b38feac 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -116,7 +116,6 @@ executable ghc-shake , ScopedTypeVariables build-depends: base , ansi-terminal >= 0.6 - , bytestring >= 0.10.6 , Cabal >= 1.22 , containers >= 0.5 , directory >= 1.2 @@ -126,6 +125,5 @@ executable ghc-shake , shake >= 0.15 , transformers >= 0.4 , unordered-containers >= 0.2 - , utf8-string >= 1.0.1 default-language: Haskell2010 ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j diff --git a/src/Base.hs b/src/Base.hs index b9c7f72..07b21e4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -115,16 +115,11 @@ a -/- b = unifyPath $ a b infixr 6 -/- --- | A wrapper around shakes @putNormal@ that substitutes --- any message for a fullstop if @buildInfo@ is @Dot at . -putNormal' :: String -> Action () -putNormal' = if buildInfo == Dot then putNormal . const "." else putNormal - -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do liftIO $ setSGR [SetColor Foreground Vivid colour] - putNormal' msg + putNormal msg liftIO $ setSGR [] liftIO $ hFlush stdout @@ -134,7 +129,9 @@ putOracle = putColoured Blue -- | Make build output more distinguishable putBuild :: String -> Action () -putBuild = putColoured White +putBuild = if buildInfo /= None + then putColoured White + else const (pure ()) -- | A more colourful version of success message putSuccess :: String -> Action () @@ -149,14 +146,14 @@ putError msg = do -- | Render an action. renderAction :: String -> String -> String -> String renderAction what input output = case buildInfo of - Normal -> renderBox [ what - , " input:" ++ input - , " => output:" ++ output ] - Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output - Pony -> renderPony [ what + Normal -> renderBox [ what , " input:" ++ input , " => output:" ++ output ] - Dot -> "." + Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output + Unicorn -> renderPony [ what + , " input:" ++ input + , " => output:" ++ output ] + None -> "" -- | Render the successful build of a program renderProgram :: String -> String -> String -> String diff --git a/src/Main.hs b/src/Main.hs index 14f3554..e9d1e56 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -14,10 +14,6 @@ import qualified Rules.Perl import qualified Test import Oracles.Config.CmdLineFlag (putOptions, flags) -import qualified Data.ByteString.Char8 as BS -import qualified Data.ByteString.UTF8 as UTF8 -import Data.Char (chr) - main :: IO () main = shakeArgsWith options flags $ \cmdLineFlags targets -> do putOptions cmdLineFlags @@ -41,27 +37,4 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True - , shakeOutput = const putMsg } - --- | Dynamic switch for @putStr@ and @putStrLn@ depending on the @msg at . -putMsg :: String -> IO () -putMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg -putMsg msg = BS.putStrLn . UTF8.fromString $ msg - --- | Drops ANSI Escape sequences from a string. -dropEscSequence :: String -> String -dropEscSequence = go - where - esc :: Char - esc = Data.Char.chr 27 - go :: String -> String - go [] = [] - go [x] = [x] - go (x:xs) | x == esc = skip xs - go (x:xs) | otherwise = x:go xs - skip :: String -> String - skip [] = [] - skip ['m'] = [] - skip ('m':xs) = go xs - skip (_ :xs) = skip xs diff --git a/src/Oracles/Config/CmdLineFlag.hs b/src/Oracles/Config/CmdLineFlag.hs index 47dbbbc..4b97c72 100644 --- a/src/Oracles/Config/CmdLineFlag.hs +++ b/src/Oracles/Config/CmdLineFlag.hs @@ -8,7 +8,7 @@ import Data.IORef -- Flags -data BuildInfoFlag = Normal | Brief | Pony | Dot deriving (Eq, Show) +data BuildInfoFlag = None | Brief | Normal | Unicorn deriving (Eq, Show) data CmdLineOptions = CmdLineOptions { flagBuildInfo :: BuildInfoFlag @@ -25,16 +25,16 @@ readBuildInfoFlag ms = (go =<< fmap (map toLower) ms) where go :: String -> Maybe BuildInfoFlag - go "normal" = Just Normal - go "brief" = Just Brief - go "pony" = Just Pony - go "dot" = Just Dot - go _ = Nothing -- Left "no parse" + go "none" = Just None + go "brief" = Just Brief + go "normal" = Just Normal + go "unicorn" = Just Unicorn + go _ = Nothing -- Left "no parse" mkClosure :: BuildInfoFlag -> CmdLineOptions -> CmdLineOptions mkClosure flag opts = opts { flagBuildInfo = flag } flags :: [OptDescr (Either String (CmdLineOptions -> CmdLineOptions))] -flags = [Option [] ["build-info"] (OptArg readBuildInfoFlag "") "Build Info Style (Normal, Brief, Pony, Dot, or None)"] +flags = [Option [] ["progress-info"] (OptArg readBuildInfoFlag "") "Build Info Style (None, Brief, Normal, or Unicorn)"] -- IO -- We use IO here instead of Oracles, as Oracles form part of shakes cache -- hence, changing command line arguments, would cause a full rebuild. And we From git at git.haskell.org Fri Oct 27 00:10:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add extra objects into integerGmp library. (9439336) Message-ID: <20171027001020.D88A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9439336c258c9e1d93b1da57cde1d89e8800fbf0/ghc >--------------------------------------------------------------- commit 9439336c258c9e1d93b1da57cde1d89e8800fbf0 Author: Andrey Mokhov Date: Thu Dec 10 00:28:42 2015 +0000 Add extra objects into integerGmp library. >--------------------------------------------------------------- 9439336c258c9e1d93b1da57cde1d89e8800fbf0 src/Rules/Library.hs | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 9e4f7d5..b0afdc6 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,6 +1,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Expression hiding (splitPath) +import GHC import Oracles import Predicates (splitObjects) import Rules.Actions @@ -36,9 +37,12 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do return . map (splitPath -/-) . filter (not . all (== '.')) $ contents + eObjs <- extraObjects target + let objs = cObjs ++ splitObjs ++ eObjs + if "//*-0.*" ?== a - then build $ fullTarget target Ar [] [a] - else build $ fullTarget target Ar (cObjs ++ splitObjs) [a] + then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls + else build $ fullTarget target Ar objs [a] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built package library '" @@ -65,3 +69,10 @@ hSources target = do modules <- interpretPartial target $ getPkgDataList Modules -- GHC.Prim is special: we do not build it return . map (replaceEq '.' '/') . filter (/= "GHC.Prim") $ modules + +extraObjects :: PartialTarget -> Action [FilePath] +extraObjects (PartialTarget _ pkg) = do + gmpObjs <- getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] + if pkg == integerGmp + then return gmpObjs + else return [] From git at git.haskell.org Fri Oct 27 00:10:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move gmp library instead of copying it. Add moveFile. (de4f7bc) Message-ID: <20171027001022.9352C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de4f7bcc27596946d26f708782f74a6266706842/ghc >--------------------------------------------------------------- commit de4f7bcc27596946d26f708782f74a6266706842 Author: Andrey Mokhov Date: Mon May 2 03:59:52 2016 +0100 Move gmp library instead of copying it. Add moveFile. See #163. >--------------------------------------------------------------- de4f7bcc27596946d26f708782f74a6266706842 src/Rules/Actions.hs | 13 ++++++++++--- src/Rules/Gmp.hs | 3 +-- 2 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index f006947..edf98eb 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,7 +1,8 @@ module Rules.Actions ( - build, buildWithResources, buildWithCmdOptions, copyFile, createDirectory, - removeDirectory, copyDirectory, moveDirectory, applyPatch, fixFile, runMake, - runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable + build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, + createDirectory, removeDirectory, copyDirectory, moveDirectory, + applyPatch, fixFile, runMake, runMakeVerbose, renderLibrary, renderProgram, + runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -87,6 +88,12 @@ copyFile source target = do putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target +-- Note, moveFile cannot track the source, because it is moved. +moveFile :: FilePath -> FilePath -> Action () +moveFile source target = do + putProgressInfo $ renderAction "Move file" source target + liftIO $ IO.renameFile source target + createDirectory :: FilePath -> Action () createDirectory dir = do putBuild $ "| Create directory " ++ dir diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index e2502dd..1e962ec 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -103,8 +103,7 @@ gmpRules = do copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH copyFile (libPath -/- "gmp.h") gmpLibraryH - -- TODO: why copy library, can we move it instead? - copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary + moveFile (libPath -/- ".libs/libgmp.a") gmpLibrary createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] From git at git.haskell.org Fri Oct 27 00:10:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Space leak. (c2f1abd) Message-ID: <20171027001022.DF8113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c2f1abd4d8ef56134168afb6b208c05b29008c34/ghc >--------------------------------------------------------------- commit c2f1abd4d8ef56134168afb6b208c05b29008c34 Author: Moritz Angermann Date: Fri Jan 15 15:23:21 2016 +0800 Space leak. >--------------------------------------------------------------- c2f1abd4d8ef56134168afb6b208c05b29008c34 src/Main.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index e9d1e56..e3f1a34 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -36,5 +36,4 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do options = shakeOptions { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple - , shakeTimings = True - } + , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:10:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for utility packages. (2f1eda7) Message-ID: <20171027001024.494313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f1eda773f2d11e11e9f46591078e50be94e458b/ghc >--------------------------------------------------------------- commit 2f1eda773f2d11e11e9f46591078e50be94e458b Author: Andrey Mokhov Date: Thu Dec 10 01:42:07 2015 +0000 Add support for utility packages. >--------------------------------------------------------------- 2f1eda773f2d11e11e9f46591078e50be94e458b src/GHC.hs | 18 +++++++++++------- src/Package.hs | 9 ++++++--- src/Rules/Library.hs | 8 +++----- src/Settings/Builders/Ghc.hs | 3 +-- src/Settings/Packages.hs | 3 ++- 5 files changed, 23 insertions(+), 18 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 668cf48..de482f4 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,6 +1,6 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, @@ -19,13 +19,14 @@ import Stage defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl - , hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm - , templateHaskell, terminfo, time, transformers, unix, win32, xhtml ] + , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPrim + , haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty + , primitive, process, stm, templateHaskell, terminfo, time, transformers + , unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcPrim, haskeline, hoopl, hpc, + deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package @@ -41,6 +42,7 @@ deepseq = library "deepseq" directory = library "directory" filepath = library "filepath" ghc = topLevel "ghc-bin" `setPath` "ghc" +ghcCabal = utility "ghc-cabal" ghcPrim = library "ghc-prim" haskeline = library "haskeline" hoopl = library "hoopl" @@ -60,6 +62,7 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" + -- GHC build results will be placed into target directories with the following -- typical structure: -- * build/ : contains compiled object code @@ -75,8 +78,9 @@ defaultTargetDirectory stage pkg defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg - | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) - | otherwise = Nothing + | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) + | pkg == ghcCabal = program $ pkgName pkg + | otherwise = Nothing where program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg -/- "build/tmp" -/- name <.> exe diff --git a/src/Package.hs b/src/Package.hs index fba192c..85fbd13 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} module Package ( - Package (..), PackageName, pkgCabalFile, setPath, library, topLevel + Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility ) where import Base @@ -21,11 +21,14 @@ data Package = Package pkgCabalFile :: Package -> FilePath pkgCabalFile pkg = pkgPath pkg -/- pkgName pkg <.> "cabal" +topLevel :: PackageName -> Package +topLevel name = Package name name + library :: PackageName -> Package library name = Package name ("libraries" -/- name) -topLevel :: PackageName -> Package -topLevel name = Package name name +utility :: PackageName -> Package +utility name = Package name ("utils" -/- name) setPath :: Package -> FilePath -> Package setPath pkg path = pkg { pkgPath = path } diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b0afdc6..1bf668d 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -71,8 +71,6 @@ hSources target = do return . map (replaceEq '.' '/') . filter (/= "GHC.Prim") $ modules extraObjects :: PartialTarget -> Action [FilePath] -extraObjects (PartialTarget _ pkg) = do - gmpObjs <- getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] - if pkg == integerGmp - then return gmpObjs - else return [] +extraObjects (PartialTarget _ pkg) + | pkg == integerGmp = getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] + | otherwise = return [] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 8d1a30f..15944f3 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -7,7 +7,6 @@ import Oracles import GHC import Predicates (package, stagedBuilder, splitObjects, stage0, notStage0) import Settings -import Settings.Builders.GhcCabal -- TODO: add support for -dyno -- TODO: consider adding a new builder for programs (e.g. GhcLink?) @@ -30,7 +29,7 @@ ghcArgs = stagedBuilder Ghc ? do , arg "-fwarn-tabs" , buildObj ? splitObjects ? arg "-split-objs" , package ghc ? arg "-no-hs-main" - , not buildObj ? arg "-no-auto-link-packages" + -- , not buildObj ? arg "-no-auto-link-packages" , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ] , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 1fe70dc..5ac9c6e 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -25,7 +25,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory, filepath - , ghcPrim, haskeline, integerLibrary, pretty, process, time ] + , ghcCabal, ghcPrim, haskeline, integerLibrary, pretty, process + , time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] From git at git.haskell.org Fri Oct 27 00:10:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of git://github.com/snowleopard/hadrian (2674950) Message-ID: <20171027001026.0827C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2674950daed5ab709cd3e5bab576b6343805d2e0/ghc >--------------------------------------------------------------- commit 2674950daed5ab709cd3e5bab576b6343805d2e0 Merge: de4f7bc 759dff3 Author: Andrey Mokhov Date: Mon May 2 04:00:12 2016 +0100 Merge branch 'master' of git://github.com/snowleopard/hadrian >--------------------------------------------------------------- 2674950daed5ab709cd3e5bab576b6343805d2e0 appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Oct 27 00:10:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: adds putBuildInfo (ade3088) Message-ID: <20171027001026.5B03F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ade30882bd45c0f4e4747ba9c6d19b2ec08846de/ghc >--------------------------------------------------------------- commit ade30882bd45c0f4e4747ba9c6d19b2ec08846de Author: Moritz Angermann Date: Fri Jan 15 15:31:23 2016 +0800 adds putBuildInfo >--------------------------------------------------------------- ade30882bd45c0f4e4747ba9c6d19b2ec08846de src/Base.hs | 13 ++++++++----- src/Rules/Actions.hs | 6 +++--- 2 files changed, 11 insertions(+), 8 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 07b21e4..68a223b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -20,8 +20,8 @@ module Base ( bootPackageConstraints, packageDependencies, -- * Output - putColoured, putOracle, putBuild, putSuccess, putError, renderAction, - renderLibrary, renderProgram, + putColoured, putOracle, putBuild, putBuildInfo, putSuccess, putError, + renderAction, renderLibrary, renderProgram, -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, @@ -129,9 +129,12 @@ putOracle = putColoured Blue -- | Make build output more distinguishable putBuild :: String -> Action () -putBuild = if buildInfo /= None - then putColoured White - else const (pure ()) +putBuild = putColoured White + +-- | Switch for @putBuild@ filtered through @buildInfo@ +putBuildInfo :: String -> Action () +putBuildInfo s | buildInfo /= None = putBuild s +putBuildInfo _ = pure () -- | A more colourful version of success message putSuccess :: String -> Action () diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index eb37630..77d283b 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -64,7 +64,7 @@ captureStdout target path argList = do copyFile :: FilePath -> FilePath -> Action () copyFile source target = do - putBuild $ renderAction "Copy file" source target + putBuildInfo $ renderAction "Copy file" source target copyFileChanged source target createDirectory :: FilePath -> Action () @@ -80,7 +80,7 @@ removeDirectory dir = do -- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do - putBuild $ renderAction "Move directory" source target + putBuildInfo $ renderAction "Move directory" source target liftIO $ IO.renameDirectory source target -- Transform a given file by applying a function to its contents @@ -123,7 +123,7 @@ makeExecutable file = do -- Print out key information about the command being executed putInfo :: Target.Target -> Action () -putInfo Target.Target {..} = putBuild $ renderAction +putInfo Target.Target {..} = putBuildInfo $ renderAction ("Run " ++ show builder ++ " (" ++ stageInfo ++ "package = " ++ pkgNameString package ++ wayInfo ++ ")") (digest inputs) From git at git.haskell.org Fri Oct 27 00:10:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix a poor pattern for detecting -0 library files. (b0424dc) Message-ID: <20171027001027.A8DAE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b0424dc9bb4c9035c1239d9d14bc720d4b6db9ad/ghc >--------------------------------------------------------------- commit b0424dc9bb4c9035c1239d9d14bc720d4b6db9ad Author: Andrey Mokhov Date: Fri Dec 11 00:23:25 2015 +0000 Fix a poor pattern for detecting -0 library files. >--------------------------------------------------------------- b0424dc9bb4c9035c1239d9d14bc720d4b6db9ad src/Rules/Library.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 1bf668d..a2cf010 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -40,7 +40,8 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do eObjs <- extraObjects target let objs = cObjs ++ splitObjs ++ eObjs - if "//*-0.*" ?== a + asuf <- libsuf way + if ("//*-0" <.> asuf) ?== a then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls else build $ fullTarget target Ar objs [a] From git at git.haskell.org Fri Oct 27 00:10:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run configure via stack exec. (d842e0f) Message-ID: <20171027001029.A93F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d842e0f8e336d17a017c94c1d70d9d66a58a3a22/ghc >--------------------------------------------------------------- commit d842e0f8e336d17a017c94c1d70d9d66a58a3a22 Author: Andrey Mokhov Date: Mon May 2 04:10:18 2016 +0100 Run configure via stack exec. >--------------------------------------------------------------- d842e0f8e336d17a017c94c1d70d9d66a58a3a22 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 76ccbe1..7b2e53b 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -34,7 +34,7 @@ install: - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee95b14e13491cc42329afed8ae038e9e94527cb/ghc >--------------------------------------------------------------- commit ee95b14e13491cc42329afed8ae038e9e94527cb Merge: ade3088 2024396 Author: Moritz Angermann Date: Fri Jan 15 15:59:02 2016 +0800 Merge remote-tracking branch 'snowleopard/master' into angerman/feature/advanced-render-box # Conflicts: # src/Base.hs >--------------------------------------------------------------- ee95b14e13491cc42329afed8ae038e9e94527cb .appveyor.yml | 1 + .travis.yml | 1 + cfg/system.config.in | 6 ++- src/Builder.hs | 2 + src/Rules/Actions.hs | 11 ++++- src/Rules/Gmp.hs | 101 ++++++++++++++++++++++++------------------- src/Rules/Library.hs | 6 ++- src/Settings/Builders/Ghc.hs | 11 ++++- 8 files changed, 89 insertions(+), 50 deletions(-) From git at git.haskell.org Fri Oct 27 00:10:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass __GLASGOW_HASKELL__ to gcc when compiling directory.c (098c9ec) Message-ID: <20171027001031.2B6BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/098c9ece49564542cc180a6cba06577695243c7e/ghc >--------------------------------------------------------------- commit 098c9ece49564542cc180a6cba06577695243c7e Author: Andrey Mokhov Date: Fri Dec 11 00:24:01 2015 +0000 Pass __GLASGOW_HASKELL__ to gcc when compiling directory.c >--------------------------------------------------------------- 098c9ece49564542cc180a6cba06577695243c7e src/Settings/Builders/Gcc.hs | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index 6a45740..3437a6c 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -1,14 +1,21 @@ module Settings.Builders.Gcc (gccArgs, gccMArgs) where import Expression +import GHC import Oracles -import Predicates (stagedBuilder) +import Predicates (package, stagedBuilder) import Settings +-- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is +-- effectively empty. I presume it was expected that GHC will be used for +-- compiling all C files, but I don't know why. It seems that directory.c is the +-- only file which requires special treatment when using GCC. gccArgs :: Args -gccArgs = stagedBuilder Gcc ? mconcat [ commonGccArgs - , arg "-c", arg =<< getInput - , arg "-o", arg =<< getOutput ] +gccArgs = stagedBuilder Gcc ? + mconcat [ commonGccArgs + , package directory ? arg "-D__GLASGOW_HASKELL__" + , arg "-c", arg =<< getInput + , arg "-o", arg =<< getOutput ] -- TODO: handle custom $1_$2_MKDEPENDC_OPTS and gccMArgs :: Args From git at git.haskell.org Fri Oct 27 00:10:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move rendering to Actions. (c7c45fc) Message-ID: <20171027001033.995193A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7c45fc3ec57e888fc6560e77a29617f18c3a46c/ghc >--------------------------------------------------------------- commit c7c45fc3ec57e888fc6560e77a29617f18c3a46c Author: Moritz Angermann Date: Fri Jan 15 21:36:36 2016 +0800 Move rendering to Actions. >--------------------------------------------------------------- c7c45fc3ec57e888fc6560e77a29617f18c3a46c src/Base.hs | 98 +--------------------------------------------- src/Rules/Actions.hs | 107 +++++++++++++++++++++++++++++++++++++++++++++++++-- 2 files changed, 104 insertions(+), 101 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 c7c45fc3ec57e888fc6560e77a29617f18c3a46c From git at git.haskell.org Fri Oct 27 00:10:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix Appveyor failure (b8dda5c) Message-ID: <20171027001033.794263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b8dda5c646545ea11c18c70a3f657871b870d1ec/ghc >--------------------------------------------------------------- commit b8dda5c646545ea11c18c70a3f657871b870d1ec Author: Andrey Mokhov Date: Mon May 2 12:28:32 2016 +0100 Attempt to fix Appveyor failure >--------------------------------------------------------------- b8dda5c646545ea11c18c70a3f657871b870d1ec appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 7b2e53b..459cecd 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -34,7 +34,7 @@ install: - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - echo "" | stack --no-terminal exec -- bash "configure --enable-tarballs-autodownload" + - echo "" | stack --no-terminal exec -- bash -lc "cd /home/ghc; configure --enable-tarballs-autodownload" - bash -lc "cat /home/ghc/hadrian/cfg/system.config" build_script: From git at git.haskell.org Fri Oct 27 00:10:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add generator for ghc-pkg//Version.hs. (3021dbe) Message-ID: <20171027001034.AE4203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3021dbebbbc22acc67880f62a067417dcc9b486b/ghc >--------------------------------------------------------------- commit 3021dbebbbc22acc67880f62a067417dcc9b486b Author: Andrey Mokhov Date: Sat Dec 12 00:41:26 2015 +0000 Add generator for ghc-pkg//Version.hs. >--------------------------------------------------------------- 3021dbebbbc22acc67880f62a067417dcc9b486b src/Rules/Generate.hs | 20 +++++++++++++++++++- 1 file changed, 19 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 6f45dbd..97fb81f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -4,7 +4,7 @@ import Expression import GHC import Oracles import Rules.Actions -import Rules.Resources +import Rules.Resources (Resources) import Settings primopsSource :: FilePath @@ -65,6 +65,12 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = writeFileChanged file contents putBuild $ "| Successfully generated '" ++ file ++ "'." + priority 2.0 $ + when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do + contents <- interpretPartial target generateGhcPkgVersionHs + writeFileChanged file contents + putBuild $ "| Successfully generated '" ++ file ++ "'." + quote :: String -> String quote s = "\"" ++ s ++ "\"" @@ -211,3 +217,15 @@ generatePlatformH = do , "#define TARGET_VENDOR " ++ quote targetVendor , "" , "#endif /* __PLATFORM_H__ */" ] + +generateGhcPkgVersionHs :: Expr String +generateGhcPkgVersionHs = do + projectVersion <- getSetting ProjectVersion + targetOs <- getSetting TargetOs + targetArch <- getSetting TargetArch + return $ unlines + [ "module Version where" + , "version, targetOS, targetARCH :: String" + , "version = " ++ quote projectVersion + , "targetOS = " ++ quote targetOs + , "targetARCH = " ++ quote targetArch ] From git at git.haskell.org Fri Oct 27 00:10:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add PATH to happy. (70fd668) Message-ID: <20171027001037.A2BD73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/70fd668dc76660a348e732f370f8cf816a08f0fa/ghc >--------------------------------------------------------------- commit 70fd668dc76660a348e732f370f8cf816a08f0fa Author: Andrey Mokhov Date: Mon May 2 13:33:45 2016 +0100 Add PATH to happy. >--------------------------------------------------------------- 70fd668dc76660a348e732f370f8cf816a08f0fa appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 459cecd..16a1277 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -34,7 +34,7 @@ install: - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - echo "" | stack --no-terminal exec -- bash -lc "cd /home/ghc; configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8a0380a71035774db6a874567e962e37d61089a5/ghc >--------------------------------------------------------------- commit 8a0380a71035774db6a874567e962e37d61089a5 Merge: 2024396 c7c45fc Author: Andrey Mokhov Date: Fri Jan 15 13:41:06 2016 +0000 Merge pull request #171 from snowleopard/angerman/feature/advanced-render-box advanced render box, fix #134 [skip ci] >--------------------------------------------------------------- 8a0380a71035774db6a874567e962e37d61089a5 src/Base.hs | 94 +-------------------------------- src/Oracles/Config/CmdLineFlag.hs | 15 +++--- src/Rules/Actions.hs | 107 ++++++++++++++++++++++++++++++++++++-- 3 files changed, 111 insertions(+), 105 deletions(-) From git at git.haskell.org Fri Oct 27 00:10:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for building ghc-pkg. (bbc6e4a) Message-ID: <20171027001038.8AB393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbc6e4a216c7853c6275757fe1a84bf0e5721281/ghc >--------------------------------------------------------------- commit bbc6e4a216c7853c6275757fe1a84bf0e5721281 Author: Andrey Mokhov Date: Sat Dec 12 00:41:49 2015 +0000 Add support for building ghc-pkg. >--------------------------------------------------------------- bbc6e4a216c7853c6275757fe1a84bf0e5721281 src/GHC.hs | 16 +++++++++------- src/Settings/Packages.hs | 4 ++-- 2 files changed, 11 insertions(+), 9 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index de482f4..eff2334 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,8 +1,8 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, - integerGmp, integerSimple, parallel, pretty, primitive, process, stm, - templateHaskell, terminfo, time, transformers, unix, win32, xhtml, + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, + hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, + stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -19,16 +19,16 @@ import Stage defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler - , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPrim + , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim , haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty , primitive, process, stm, templateHaskell, terminfo, time, transformers , unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPrim, haskeline, hoopl, hpc, - integerGmp, integerSimple, parallel, pretty, primitive, process, stm, - templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, + hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, + stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -43,6 +43,7 @@ directory = library "directory" filepath = library "filepath" ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" +ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" haskeline = library "haskeline" hoopl = library "hoopl" @@ -80,6 +81,7 @@ defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == ghcCabal = program $ pkgName pkg + | pkg == ghcPkg = program $ pkgName pkg | otherwise = Nothing where program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 5ac9c6e..9fbe936 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -25,8 +25,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory, filepath - , ghcCabal, ghcPrim, haskeline, integerLibrary, pretty, process - , time ] + , ghcCabal, ghcPkg, ghcPrim, haskeline, integerLibrary, pretty + , process, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] From git at git.haskell.org Fri Oct 27 00:10:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop support for shake-0.15.5 (0015942) Message-ID: <20171027001042.471573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/00159421655dd8c82a983a8249aa4bc373613893/ghc >--------------------------------------------------------------- commit 00159421655dd8c82a983a8249aa4bc373613893 Author: Andrey Mokhov Date: Mon May 2 14:42:10 2016 +0100 Drop support for shake-0.15.5 >--------------------------------------------------------------- 00159421655dd8c82a983a8249aa4bc373613893 src/Base.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index a38ea51..5e66a27 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel module Base ( -- * General utilities module Control.Applicative, From git at git.haskell.org Fri Oct 27 00:10:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make error message more helpful. (b4f0b5c) Message-ID: <20171027001041.C07E93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b4f0b5c264583fbd2410fd3d720fa9004f0490b9/ghc >--------------------------------------------------------------- commit b4f0b5c264583fbd2410fd3d720fa9004f0490b9 Author: Andrey Mokhov Date: Fri Jan 15 14:48:29 2016 +0000 Make error message more helpful. [skip ci] >--------------------------------------------------------------- b4f0b5c264583fbd2410fd3d720fa9004f0490b9 src/Builder.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 353c00f..96cb608 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -93,9 +93,9 @@ builderKey builder = case builder of -- TODO: Paths to some builders should be determined using 'defaultProgramPath' builderPath :: Builder -> Action FilePath builderPath builder = do - path <- askConfigWithDefault (builderKey builder) $ - putError $ "\nCannot find path to '" ++ (builderKey builder) - ++ "' in configuration files." + path <- askConfigWithDefault (builderKey builder) . putError $ + "\nCannot find path to '" ++ (builderKey builder) + ++ "' in configuration files. Have you forgot to run configure?" windows <- windowsHost case (path, windows) of ("", _) -> return path From git at git.haskell.org Fri Oct 27 00:10:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghc-pkg and ghc-cabal in stage 0. (a0e932a) Message-ID: <20171027001042.BCCDF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a0e932ab5e73ccf062cacea3f6e8b15ca3d15463/ghc >--------------------------------------------------------------- commit a0e932ab5e73ccf062cacea3f6e8b15ca3d15463 Author: Andrey Mokhov Date: Sat Dec 12 00:50:27 2015 +0000 Build ghc-pkg and ghc-cabal in stage 0. >--------------------------------------------------------------- a0e932ab5e73ccf062cacea3f6e8b15ca3d15463 src/GHC.hs | 2 ++ src/Settings/Packages.hs | 4 ++-- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index eff2334..2482854 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -70,6 +70,8 @@ xhtml = library "xhtml" -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal -- TODO: simplify to just 'show stage'? +-- TODO: we divert from the previous convention for ghc-cabal and ghc-pkg, +-- which used to store stage0 build results in 'dist' folder defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage pkg | pkg == compiler = "stage" ++ show (fromEnum stage + 1) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 9fbe936..23ee7e4 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -16,8 +16,8 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc - , templateHaskell, transformers ] + [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg + , hoopl, hpc, templateHaskell, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? From git at git.haskell.org Fri Oct 27 00:10:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't track integer-gmp.buildinfo. (d684612) Message-ID: <20171027001045.B34423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6846121743a4b61cb2cef6d57afa322b3fb6076/ghc >--------------------------------------------------------------- commit d6846121743a4b61cb2cef6d57afa322b3fb6076 Author: Andrey Mokhov Date: Fri Jan 15 16:07:28 2016 +0000 Don't track integer-gmp.buildinfo. See #173. >--------------------------------------------------------------- d6846121743a4b61cb2cef6d57afa322b3fb6076 src/Rules/Gmp.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index cfd8c53..d8cf707 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -82,18 +82,19 @@ gmpRules = do createDirectory $ takeDirectory gmpLibraryH -- We don't use system GMP on Windows. TODO: fix? + -- TODO: we do not track "config.mk" and "integer-gmp.buildinfo", see #173 windows <- windowsHost configMk <- liftIO . readFile $ gmpBase -/- "config.mk" if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - buildInfo <- readFileLines $ pkgPath integerGmp -/- "integer-gmp.buildinfo" + buildInfo <- liftIO . readFile $ pkgPath integerGmp -/- "integer-gmp.buildinfo" let prefix = "extra-libraries: " libs s = case stripPrefix prefix s of Nothing -> [] Just value -> words value - writeFileChanged gmpLibNameCache . unlines $ concatMap libs buildInfo + writeFileChanged gmpLibNameCache . unlines . concatMap libs $ lines buildInfo else do putBuild "| No GMP library/framework detected; in tree GMP will be built" writeFileChanged gmpLibNameCache "" From git at git.haskell.org Fri Oct 27 00:10:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot and configure by default. (7166d12) Message-ID: <20171027001046.98C243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7166d12eaa68317d97c8b5663d6b342042432081/ghc >--------------------------------------------------------------- commit 7166d12eaa68317d97c8b5663d6b342042432081 Author: Andrey Mokhov Date: Wed May 4 23:48:15 2016 +0100 Run boot and configure by default. See #234. >--------------------------------------------------------------- 7166d12eaa68317d97c8b5663d6b342042432081 .travis.yml | 2 +- appveyor.yml | 2 +- hadrian.cabal | 2 +- src/CmdLineFlag.hs | 46 ++++++++++++++++---------------------- src/Rules.hs | 4 ++-- src/Rules/Configure.hs | 44 ++++++++++++++++++++++++++++++++++++ src/Rules/Setup.hs | 45 ------------------------------------- src/Settings/Builders/Configure.hs | 7 +----- 8 files changed, 69 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7166d12eaa68317d97c8b5663d6b342042432081 From git at git.haskell.org Fri Oct 27 00:10:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Make builder. (ba5f163) Message-ID: <20171027001049.408463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba5f16377f357f009e932b1301a0e3fbcc4b8578/ghc >--------------------------------------------------------------- commit ba5f16377f357f009e932b1301a0e3fbcc4b8578 Author: Andrey Mokhov Date: Fri Jan 15 23:13:05 2016 +0000 Add Make builder. See #167. >--------------------------------------------------------------- ba5f16377f357f009e932b1301a0e3fbcc4b8578 cfg/system.config.in | 1 + src/Builder.hs | 2 ++ 2 files changed, 3 insertions(+) diff --git a/cfg/system.config.in b/cfg/system.config.in index 4539979..dfde8e3 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -36,6 +36,7 @@ ar = @ArCmd@ happy = @HappyCmd@ hscolour = @HSCOLOUR@ ld = @LdCmd@ +make = @MakeCmd@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ diff --git a/src/Builder.hs b/src/Builder.hs index 96cb608..560f734 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -38,6 +38,7 @@ data Builder = Alex | HsCpp | Hsc2Hs | Ld + | Make | Nm | Objdump | Patch @@ -81,6 +82,7 @@ builderKey builder = case builder of Hsc2Hs -> "hsc2hs" HsCpp -> "hs-cpp" Ld -> "ld" + Make -> "make" Nm -> "nm" Objdump -> "objdump" Patch -> "patch" From git at git.haskell.org Fri Oct 27 00:10:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghc-pwd. (f659a18) Message-ID: <20171027001046.D7C463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f659a18291a9e4f1a8b8d7f2e22744923effcac0/ghc >--------------------------------------------------------------- commit f659a18291a9e4f1a8b8d7f2e22744923effcac0 Author: Andrey Mokhov Date: Sat Dec 12 00:53:49 2015 +0000 Build ghc-pwd. >--------------------------------------------------------------- f659a18291a9e4f1a8b8d7f2e22744923effcac0 src/GHC.hs | 18 +++++++++++------- src/Settings/Packages.hs | 6 +++--- 2 files changed, 14 insertions(+), 10 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 2482854..d1fb30a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,8 +1,9 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, - hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, - stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, + haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, + primitive, process, stm, templateHaskell, terminfo, time, transformers, + unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -20,15 +21,16 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler , containers, deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim - , haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty + , ghcPwd, haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty , primitive, process, stm, templateHaskell, terminfo, time, transformers , unix, win32, xhtml ] -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, - deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, haskeline, - hoopl, hpc, integerGmp, integerSimple, parallel, pretty, primitive, process, - stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package + deepseq, directory, filepath, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, + haskeline, hoopl, hpc, integerGmp, integerSimple, parallel, pretty, + primitive, process, stm, templateHaskell, terminfo, time, transformers, + unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -45,6 +47,7 @@ ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" +ghcPwd = utility "ghc-pwd" haskeline = library "haskeline" hoopl = library "hoopl" hpc = library "hpc" @@ -84,6 +87,7 @@ defaultProgramPath stage pkg | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == ghcCabal = program $ pkgName pkg | pkg == ghcPkg = program $ pkgName pkg + | pkg == ghcPwd = program $ pkgName pkg | otherwise = Nothing where program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 23ee7e4..b2636d5 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -17,7 +17,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg - , hoopl, hpc, templateHaskell, transformers ] + , ghcPwd, hoopl, hpc, templateHaskell, transformers ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? @@ -25,8 +25,8 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, deepseq, directory, filepath - , ghcCabal, ghcPkg, ghcPrim, haskeline, integerLibrary, pretty - , process, time ] + , ghcCabal, ghcPkg, ghcPrim, ghcPwd, haskeline, integerLibrary + , pretty, process, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , buildHaddock ? append [xhtml] ] From git at git.haskell.org Fri Oct 27 00:10:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use qualified imports in Rules.hs for better readability. (56be38d) Message-ID: <20171027001050.A97633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56be38d48f28022d370edb1f7d3663630dde9c45/ghc >--------------------------------------------------------------- commit 56be38d48f28022d370edb1f7d3663630dde9c45 Author: Andrey Mokhov Date: Thu May 5 00:16:54 2016 +0100 Use qualified imports in Rules.hs for better readability. >--------------------------------------------------------------- 56be38d48f28022d370edb1f7d3663630dde9c45 src/Rules.hs | 58 +++++++++++++++++++++++++++++----------------------------- 1 file changed, 29 insertions(+), 29 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 2f84917..e3caf6c 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -6,19 +6,19 @@ import Base import Context import Expression import GHC -import Rules.Compile -import Rules.Data -import Rules.Dependencies -import Rules.Documentation -import Rules.Generate -import Rules.Cabal -import Rules.Configure -import Rules.Gmp -import Rules.Libffi -import Rules.Library -import Rules.Perl -import Rules.Program -import Rules.Register +import qualified Rules.Compile +import qualified Rules.Data +import qualified Rules.Dependencies +import qualified Rules.Documentation +import qualified Rules.Generate +import qualified Rules.Cabal +import qualified Rules.Configure +import qualified Rules.Gmp +import qualified Rules.Libffi +import qualified Rules.Library +import qualified Rules.Perl +import qualified Rules.Program +import qualified Rules.Register import Settings allStages :: [Stage] @@ -66,25 +66,25 @@ packageRules = do vanillaContexts = liftM2 vanillaContext allStages knownPackages for_ contexts $ mconcat - [ compilePackage readPackageDb - , buildPackageLibrary ] + [ Rules.Compile.compilePackage readPackageDb + , Rules.Library.buildPackageLibrary ] for_ vanillaContexts $ mconcat - [ buildPackageData - , buildPackageDependencies readPackageDb - , buildPackageDocumentation - , buildPackageGhciLibrary - , generatePackageCode - , buildProgram readPackageDb - , registerPackage writePackageDb ] + [ Rules.Data.buildPackageData + , Rules.Dependencies.buildPackageDependencies readPackageDb + , Rules.Documentation.buildPackageDocumentation + , Rules.Library.buildPackageGhciLibrary + , Rules.Generate.generatePackageCode + , Rules.Program.buildProgram readPackageDb + , Rules.Register.registerPackage writePackageDb ] buildRules :: Rules () buildRules = do - cabalRules - configureRules - generateRules - copyRules - gmpRules - libffiRules - perlScriptRules + Rules.Cabal.cabalRules + Rules.Configure.configureRules + Rules.Generate.copyRules + Rules.Generate.generateRules + Rules.Gmp.gmpRules + Rules.Libffi.libffiRules packageRules + Rules.Perl.perlScriptRules From git at git.haskell.org Fri Oct 27 00:10:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build all utils that use cabal files. (f3199c1) Message-ID: <20171027001050.F085B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f3199c17a1f010017eabd4845df7533c62abfde5/ghc >--------------------------------------------------------------- commit f3199c17a1f010017eabd4845df7533c62abfde5 Author: Andrey Mokhov Date: Sat Dec 12 02:13:35 2015 +0000 Build all utils that use cabal files. >--------------------------------------------------------------- f3199c17a1f010017eabd4845df7533c62abfde5 src/GHC.hs | 52 +++++++++++++++++++++++++++++--------------- src/Rules/Generate.hs | 5 +++++ src/Rules/Library.hs | 3 ++- src/Rules/Program.hs | 7 ++++-- src/Settings/Builders/Ghc.hs | 5 ++++- src/Settings/Packages.hs | 9 ++++---- 6 files changed, 56 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f3199c17a1f010017eabd4845df7533c62abfde5 From git at git.haskell.org Fri Oct 27 00:10:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop makeCommand, use make detected by configure. (266461a) Message-ID: <20171027001052.ACFD53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/266461a38790c86451a441db5b308341df3c6e61/ghc >--------------------------------------------------------------- commit 266461a38790c86451a441db5b308341df3c6e61 Author: Andrey Mokhov Date: Fri Jan 15 23:57:49 2016 +0000 Drop makeCommand, use make detected by configure. Fix #167. >--------------------------------------------------------------- 266461a38790c86451a441db5b308341df3c6e61 src/Rules/Actions.hs | 21 ++++++++++++++++----- src/Rules/Gmp.hs | 1 - src/Settings/User.hs | 7 +------ 3 files changed, 17 insertions(+), 12 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index a0a88ff..429f241 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -6,18 +6,18 @@ module Rules.Actions ( ) where import qualified System.Directory as IO +import System.Console.ANSI import Base import Expression import Oracles import Oracles.ArgsHash +import Oracles.Config.CmdLineFlag (buildInfo, BuildInfoFlag(..)) import Settings import Settings.Args import Settings.Builders.Ar import qualified Target -import Oracles.Config.CmdLineFlag (buildInfo, BuildInfoFlag(..)) - -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last -- built (that is, track changes in the build system). @@ -107,15 +107,26 @@ runConfigure dir opts args = do runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] + path <- builderPath Make + + -- FIXME: temporary safety net for those who are not on GHC HEAD, see #167 + fixPath <- if path == "@MakeCmd@" <.> exe + then do + putColoured Red $ "You are behind GHC HEAD, make autodetection is disabled." + return "make" + else do + needBuilder False Make + return path + let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) makeCommand ["-C", dir] args + putBuild $ "| Run " ++ fixPath ++ " " ++ note ++ " in " ++ dir ++ "..." + quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch need [file] - needBuilder False Patch + needBuilder False Patch -- TODO: add a specialised version ~needBuilderFalse? path <- builderPath Patch putBuild $ "| Apply patch " ++ file quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index d8cf707..8df337b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -109,7 +109,6 @@ gmpRules = do ++ "(found: " ++ show tarballs ++ ")." need tarballs - createDirectory gmpBuildPath build $ fullTarget gmpTarget Tar tarballs [gmpBuildPath] forM_ gmpPatches $ \src -> do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 3d08ecd..3cebe13 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors, splitObjects, makeCommand + verboseCommands, turnWarningsIntoErrors, splitObjects ) where import GHC @@ -101,8 +101,3 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False - --- | Specify which @make@ command to use, for example set to "gmake" for --- @GNU make at . -makeCommand :: FilePath -makeCommand = "make" From git at git.haskell.org Fri Oct 27 00:10:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot and configure from Hadrian. (dd4f887) Message-ID: <20171027001054.5CA8B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dd4f8871b08a1063dcd40770ca7a14caaca09c7a/ghc >--------------------------------------------------------------- commit dd4f8871b08a1063dcd40770ca7a14caaca09c7a Author: Andrey Mokhov Date: Thu May 5 00:43:42 2016 +0100 Run boot and configure from Hadrian. See #234. >--------------------------------------------------------------- dd4f8871b08a1063dcd40770ca7a14caaca09c7a .travis.yml | 5 +---- appveyor.yml | 5 +---- 2 files changed, 2 insertions(+), 8 deletions(-) diff --git a/.travis.yml b/.travis.yml index 2b2e7f5..7d5b699 100644 --- a/.travis.yml +++ b/.travis.yml @@ -54,15 +54,12 @@ install: - ( cd ghc/hadrian && cabal install --only-dependencies ) - ( cd ghc/hadrian && cabal configure ) - - ( cd ghc && ./boot ) - - ( cd ghc && ./configure ) - - cat ghc/hadrian/cfg/system.config - ghc-pkg list script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --skip-configure --no-progress --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --no-progress --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index 0bcf7d7..bb78b80 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -31,13 +31,10 @@ install: - stack exec -- ghc-pkg list - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5/ghc >--------------------------------------------------------------- commit 6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5 Author: Andrey Mokhov Date: Sun Dec 13 02:30:44 2015 +0000 Build haddock. >--------------------------------------------------------------- 6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5 src/GHC.hs | 15 ++++++++++++--- src/Rules.hs | 2 +- src/Rules/Compile.hs | 1 + src/Rules/Program.hs | 7 ++++--- src/Settings/Builders/Ghc.hs | 5 +++-- src/Settings/Builders/GhcCabal.hs | 2 ++ src/Settings/Packages.hs | 12 +++++++++--- 7 files changed, 32 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6b143638d5be7e4f1c7e7b5dc01b0fcd53bc33e5 From git at git.haskell.org Fri Oct 27 00:10:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need make (fails on Windows). (ba74f58) Message-ID: <20171027001056.1C90E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba74f58ab49363b488eef09e2b78c85302b61427/ghc >--------------------------------------------------------------- commit ba74f58ab49363b488eef09e2b78c85302b61427 Author: Andrey Mokhov Date: Sat Jan 16 00:51:33 2016 +0000 Don't need make (fails on Windows). See #167. >--------------------------------------------------------------- ba74f58ab49363b488eef09e2b78c85302b61427 src/Rules/Actions.hs | 7 +++---- src/Settings/Builders/Ghc.hs | 6 ++++-- 2 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 429f241..21d134f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -110,16 +110,15 @@ runMake dir args = do path <- builderPath Make -- FIXME: temporary safety net for those who are not on GHC HEAD, see #167 + -- TODO: add need [path] once lookupInPath is enabled on Windows fixPath <- if path == "@MakeCmd@" <.> exe then do putColoured Red $ "You are behind GHC HEAD, make autodetection is disabled." return "make" - else do - needBuilder False Make - return path + else return path let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run " ++ fixPath ++ " " ++ note ++ " in " ++ dir ++ "..." + putBuild $ "| Run " ++ fixPath ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 40b5a0f..2e40bcb 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -24,7 +24,8 @@ ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output libs <- getPkgDataList DepExtraLibs gmpLibs <- lift $ readFileLines gmpLibNameCache libDirs <- getPkgDataList DepLibDirs @@ -40,7 +41,8 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" , append =<< getInputs - , arg "-o", arg =<< getOutput ] + , buildHi ? append ["-fno-code", "-fwrite-interface"] + , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do From git at git.haskell.org Fri Oct 27 00:10:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop --setup, add --skip-configure. (7cb590a) Message-ID: <20171027001057.E4D123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7cb590a6ede9ccfe521e31a116767f46503945c8/ghc >--------------------------------------------------------------- commit 7cb590a6ede9ccfe521e31a116767f46503945c8 Author: Andrey Mokhov Date: Thu May 5 01:37:48 2016 +0100 Drop --setup, add --skip-configure. See #234. [skip ci] >--------------------------------------------------------------- 7cb590a6ede9ccfe521e31a116767f46503945c8 README.md | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/README.md b/README.md index d4adfb1..e0053b0 100644 --- a/README.md +++ b/README.md @@ -32,8 +32,6 @@ system to be in the `hadrian` directory of the GHC source tree: git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/hadrian - ./boot - ./configure # On Windows run ./configure --enable-tarballs-autodownload ``` * Build GHC using `hadrian/build.sh` or `hadrian/build.bat` (on Windows) instead @@ -45,7 +43,7 @@ see [instructions for building GHC on Windows using Stack][windows-build]. Using the build system ---------------------- Once your first build is successful, simply run `build` to rebuild. Most build artefacts -are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue]). +are placed into `_build` and `inplace` directories ([#113][build-artefacts-issue]). #### Command line flags @@ -58,13 +56,17 @@ profiling, which speeds up builds by 3-4x). * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). -* `--setup[=CONFIGURE_ARGS]`: setup the build system by running the `configure` script -with `CONFIGURE_ARGS` arguments; also run the `boot` script to create the `configure` -script if necessary. On Windows, download the required tarballs by executing -`mk/get-win32-tarballs.sh` with appropriate parameters. You do not have to -use this functionality of the new build system; feel free to run `boot` and `configure` -scripts manually, as you do when using `make`. Beware: `--setup` uses network I/O -which may sometimes be undesirable. +* `--skip-configure`: use this flag to suppress the default behaviour of Hadrian that +runs the `boot` and `configure` scripts automatically if need be, so that you don't have +to remember to run them manually. With `--skip-configure` you will need to manually run: + + ```bash + ./boot + ./configure # On Windows run ./configure --enable-tarballs-autodownload + ``` +as you normally do when using `make`. Beware, by default Hadrian may do network I/O on +Windows to download necessary tarballs, which may sometimes be undesirable; `--skip-configure` +is your friend in such cases. * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. From git at git.haskell.org Fri Oct 27 00:10:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build deriveConstants utility. (bbdaa7e) Message-ID: <20171027001058.2D6A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbdaa7eab8d8ebe4c5e21646cd172d53d741872e/ghc >--------------------------------------------------------------- commit bbdaa7eab8d8ebe4c5e21646cd172d53d741872e Author: Andrey Mokhov Date: Sun Dec 13 03:54:05 2015 +0000 Build deriveConstants utility. >--------------------------------------------------------------- bbdaa7eab8d8ebe4c5e21646cd172d53d741872e src/GHC.hs | 10 ++++++---- src/Oracles/PackageData.hs | 3 ++- src/Predicates.hs | 5 ++++- src/Rules/Compile.hs | 10 ++++++++-- src/Rules/Data.hs | 11 +++++++++++ src/Settings/Builders/Ghc.hs | 7 ++++--- src/Settings/Packages.hs | 1 + 7 files changed, 36 insertions(+), 11 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 bbdaa7eab8d8ebe4c5e21646cd172d53d741872e From git at git.haskell.org Fri Oct 27 00:10:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Undo irrelevant changes in previous commit. (f33acd3) Message-ID: <20171027001059.87F863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f33acd3ee4d702751a4ce766efa57e02666f926a/ghc >--------------------------------------------------------------- commit f33acd3ee4d702751a4ce766efa57e02666f926a Author: Andrey Mokhov Date: Sat Jan 16 00:56:11 2016 +0000 Undo irrelevant changes in previous commit. See #167. >--------------------------------------------------------------- f33acd3ee4d702751a4ce766efa57e02666f926a src/Settings/Builders/Ghc.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 2e40bcb..40b5a0f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -24,8 +24,7 @@ ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output - buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output libs <- getPkgDataList DepExtraLibs gmpLibs <- lift $ readFileLines gmpLibNameCache libDirs <- getPkgDataList DepLibDirs @@ -41,8 +40,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" , append =<< getInputs - , buildHi ? append ["-fno-code", "-fwrite-interface"] - , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] + , arg "-o", arg =<< getOutput ] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do From git at git.haskell.org Fri Oct 27 00:11:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Call GMP's configure in gmpBuildPath. (a228b96) Message-ID: <20171027001101.D79A93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a228b96c3ab519968384ff1a5f88353225ff3544/ghc >--------------------------------------------------------------- commit a228b96c3ab519968384ff1a5f88353225ff3544 Author: Andrey Mokhov Date: Thu May 5 03:01:40 2016 +0100 Call GMP's configure in gmpBuildPath. >--------------------------------------------------------------- a228b96c3ab519968384ff1a5f88353225ff3544 src/Rules/Gmp.hs | 54 ++++++++++++++++++++------------------ src/Settings/Builders/Configure.hs | 2 +- 2 files changed, 30 insertions(+), 26 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1e962ec..cceda8e 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -52,8 +52,7 @@ gmpRules = do -- TODO: split into multiple rules gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - liftIO $ removeFiles gmpBuildPath ["//*"] - createDirectory $ takeDirectory gmpLibraryH + removeDirectoryIfExists gmpBuildPath -- We don't use system GMP on Windows. TODO: fix? windows <- windowsHost @@ -62,6 +61,7 @@ gmpRules = do [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" + createDirectory $ takeDirectory gmpLibraryH copyFile gmpLibraryFakeH gmpLibraryH else do putBuild "| No GMP library/framework detected; in tree GMP will be built" @@ -76,34 +76,38 @@ gmpRules = do ++ "(found: " ++ show tarballs ++ ")." need tarballs - build $ Target gmpContext Tar tarballs [gmpBuildPath] - - forM_ gmpPatches $ \src -> do - let patch = takeFileName src - patchPath = gmpBuildPath -/- patch - copyFile src patchPath - applyPatch gmpBuildPath patch - - let filename = dropExtension . dropExtension . takeFileName $ head tarballs - suffix = "-nodoc-patched" - unless (suffix `isSuffixOf` filename) $ - putError $ "gmpRules: expected suffix " ++ suffix - ++ " (found: " ++ filename ++ ")." - let libName = take (length filename - length suffix) filename - libPath = gmpBuildPath -/- "lib" - - moveDirectory (gmpBuildPath -/- libName) libPath + withTempDir $ \dir -> do + let tmp = unifyPath dir + build $ Target gmpContext Tar tarballs [tmp] + + forM_ gmpPatches $ \src -> do + let patch = takeFileName src + patchPath = tmp -/- patch + copyFile src patchPath + applyPatch tmp patch + + let filename = dropExtension . dropExtension . takeFileName + $ head tarballs + suffix = "-nodoc-patched" + unless (suffix `isSuffixOf` filename) $ + putError $ "gmpRules: expected suffix " ++ suffix + ++ " (found: " ++ filename ++ ")." + let libName = take (length filename - length suffix) filename + + moveDirectory (tmp -/- libName) gmpBuildPath env <- configureEnvironment buildWithCmdOptions env $ - Target gmpContext (Configure libPath) - [libPath -/- "Makefile.in"] [libPath -/- "Makefile"] + Target gmpContext (Configure gmpBuildPath) + [gmpBuildPath -/- "Makefile.in"] + [gmpBuildPath -/- "Makefile"] - runMake libPath ["MAKEFLAGS="] + runMake gmpBuildPath ["MAKEFLAGS="] - copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH - copyFile (libPath -/- "gmp.h") gmpLibraryH - moveFile (libPath -/- ".libs/libgmp.a") gmpLibrary + createDirectory $ takeDirectory gmpLibraryH + copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH + copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH + moveFile (gmpBuildPath -/- ".libs/libgmp.a") gmpLibrary createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 45bca37..813b79d 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -17,7 +17,7 @@ configureArgs = mconcat , arg $ "--enable-shared=no" -- TODO: add support for yes , arg $ "--host=" ++ targetPlatform ] - , builder (Configure $ gmpBuildPath -/- "lib") ? do + , builder (Configure gmpBuildPath) ? do hostPlatform <- getSetting HostPlatform buildPlatform <- getSetting BuildPlatform mconcat [ arg $ "--enable-shared=no" From git at git.haskell.org Fri Oct 27 00:11:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build genapply utility. (e99bd28) Message-ID: <20171027001102.13C7B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e99bd28a549c2c362bf8bef7dde9f13ca05a2510/ghc >--------------------------------------------------------------- commit e99bd28a549c2c362bf8bef7dde9f13ca05a2510 Author: Andrey Mokhov Date: Sun Dec 13 19:19:18 2015 +0000 Build genapply utility. >--------------------------------------------------------------- e99bd28a549c2c362bf8bef7dde9f13ca05a2510 src/GHC.hs | 15 +++++++++------ src/Rules/Compile.hs | 7 ++++++- src/Rules/Data.hs | 16 +++++++++++++++- src/Settings/Builders/Ghc.hs | 9 ++++++--- src/Settings/Packages.hs | 2 +- 5 files changed, 37 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e99bd28a549c2c362bf8bef7dde9f13ca05a2510 From git at git.haskell.org Fri Oct 27 00:11:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't rerun configure for integerGmp package. (16c89e4) Message-ID: <20171027001103.254913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/16c89e4739ae570e6e8548ac1fe8092df6353911/ghc >--------------------------------------------------------------- commit 16c89e4739ae570e6e8548ac1fe8092df6353911 Author: Andrey Mokhov Date: Sat Jan 16 03:10:54 2016 +0000 Don't rerun configure for integerGmp package. [skip ci] >--------------------------------------------------------------- 16c89e4739ae570e6e8548ac1fe8092df6353911 src/Rules/Gmp.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 8df337b..61a0a6f 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -75,10 +75,14 @@ gmpRules = do liftIO $ removeFiles gmpBuildPath ["//*"] - -- TODO: currently we configure integerGmp package twice -- optimise - args <- configureIntGmpArguments envs <- configureEnvironment - runConfigure (pkgPath integerGmp) envs args + -- TODO: without the optimisation below we configure integerGmp package + -- twice -- think how this can be optimised (shall we solve #18 first?) + -- TODO: this is a hacky optimisation: we do not rerun configure of + -- integerGmp package if we detect the results of the previous run + unlessM (doesFileExist $ gmpBase -/- "config.mk") $ do + args <- configureIntGmpArguments + runConfigure (pkgPath integerGmp) envs args createDirectory $ takeDirectory gmpLibraryH -- We don't use system GMP on Windows. TODO: fix? From git at git.haskell.org Fri Oct 27 00:11:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of partial functions. (a7adf8c) Message-ID: <20171027001105.B092C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7adf8c5b2719aed8c17b029a74ebc190360df28/ghc >--------------------------------------------------------------- commit a7adf8c5b2719aed8c17b029a74ebc190360df28 Author: Andrey Mokhov Date: Thu May 5 03:13:49 2016 +0100 Get rid of partial functions. >--------------------------------------------------------------- a7adf8c5b2719aed8c17b029a74ebc190360df28 src/Rules/Gmp.hs | 23 +++++++++++------------ 1 file changed, 11 insertions(+), 12 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index cceda8e..d98bc3b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -71,14 +71,15 @@ gmpRules = do -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] - when (length tarballs /= 1) $ - putError $ "gmpRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." + tarball <- case tarballs of + [file] -> return $ unifyPath file + _ -> putError $ "gmpRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." - need tarballs withTempDir $ \dir -> do let tmp = unifyPath dir - build $ Target gmpContext Tar tarballs [tmp] + need [tarball] + build $ Target gmpContext Tar [tarball] [tmp] forM_ gmpPatches $ \src -> do let patch = takeFileName src @@ -86,13 +87,11 @@ gmpRules = do copyFile src patchPath applyPatch tmp patch - let filename = dropExtension . dropExtension . takeFileName - $ head tarballs - suffix = "-nodoc-patched" - unless (suffix `isSuffixOf` filename) $ - putError $ "gmpRules: expected suffix " ++ suffix - ++ " (found: " ++ filename ++ ")." - let libName = take (length filename - length suffix) filename + let name = dropExtension . dropExtension $ takeFileName tarball + libName <- case stripSuffix "-nodoc-patched" name of + Just rest -> return rest + Nothing -> putError $ "gmpRules: expected suffix " + ++ "-nodoc-patched (found: " ++ name ++ ")." moveDirectory (tmp -/- libName) gmpBuildPath From git at git.haskell.org Fri Oct 27 00:11:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build genprimopcode utility. (6f2b78b) Message-ID: <20171027001105.DCE563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6f2b78bb0f063be5ff5a8abc346f765c6729621e/ghc >--------------------------------------------------------------- commit 6f2b78bb0f063be5ff5a8abc346f765c6729621e Author: Andrey Mokhov Date: Sun Dec 13 19:25:30 2015 +0000 Build genprimopcode utility. >--------------------------------------------------------------- 6f2b78bb0f063be5ff5a8abc346f765c6729621e src/GHC.hs | 10 ++++++---- src/Rules/Data.hs | 12 +++++++++++- src/Settings/Builders/Ghc.hs | 4 ++-- src/Settings/Packages.hs | 3 ++- 4 files changed, 21 insertions(+), 8 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 3821518..ff5a106 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,7 +1,7 @@ module GHC ( array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, ghc, ghcCabal, ghcPkg, ghcPrim, + genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hpc, hpcBin, integerGmp, integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, @@ -23,7 +23,7 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binPackageDb, binary, bytestring, cabal, compiler , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, ghc, ghcCabal, ghcPkg, ghcPrim + , filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hpc, hpcBin, integerGmp, integerSimple , mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo , time, transformers, unix, win32, xhtml ] @@ -31,7 +31,7 @@ defaultKnownPackages = -- Package definitions array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, + genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hpc, hpcBin, integerGmp, integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, @@ -52,6 +52,7 @@ directory = library "directory" dllSplit = utility "dll-split" filepath = library "filepath" genapply = utility "genapply" +genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" ghcPkg = utility "ghc-pkg" @@ -81,7 +82,7 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" --- TODO: genprimocode, hp2ps +-- TODO: hp2ps -- TODO: The following utils are not included into the build system because -- they seem to be unused or unrelated to the build process: chechUniques, @@ -110,6 +111,7 @@ defaultProgramPath stage pkg | pkg == deriveConstants = program $ pkgName pkg | pkg == dllSplit = program $ pkgName pkg | pkg == genapply = program $ pkgName pkg + | pkg == genprimopcode = program $ pkgName pkg | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == ghcCabal = program $ pkgName pkg | pkg == ghcPkg = program $ pkgName pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 9fbc6ec..c47c6a3 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (deriveConstants, genapply) +import GHC (deriveConstants, genapply, genprimopcode) import Oracles import Predicates (registerPackage) import Rules.Actions @@ -70,6 +70,16 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do , "utils_genapply_dist-boot_HC_OPTS = " ++ hcOpts ] writeFileChanged mk contents + priority 2.0 $ + when (pkg == genprimopcode) $ path -/- "package-data.mk" %> \mk -> do + let contents = unlines + [ "utils_genprimopcode_dist-boot_MODULES = Lexer Main ParserM Parser Syntax" + , "utils_genprimopcode_dist-boot_PROGNAME = genprimopcode" + , "utils_genprimopcode_dist-boot_HS_SRC_DIRS = ." + , "utils_genprimopcode_dist-boot_INSTALL_INPLACE = YES" + , "utils_genprimopcode_dist-boot_HC_OPTS = -package array" ] + writeFileChanged mk contents + -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- For example, get rid of diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a22bee5..3d3e224 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -96,7 +96,7 @@ packageGhcArgs = do pkgKey <- getPkgData PackageKey pkgDepIds <- getPkgDataList DepIds mconcat - [ not (pkg == deriveConstants || pkg == genapply) ? + [ not (pkg == deriveConstants || pkg == genapply || pkg == genprimopcode) ? arg "-hide-all-packages" , arg "-no-user-package-db" , stage0 ? arg "-package-db libraries/bootstrapping.conf" @@ -122,7 +122,7 @@ includeGhcArgs = do , arg $ "-I" ++ autogenPath , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] - , not (pkg == deriveConstants || pkg == genapply) ? + , not (pkg == deriveConstants || pkg == genapply || pkg == genprimopcode) ? append [ "-optP-include" , "-optP" ++ autogenPath -/- "cabal_macros.h" ] ] diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 1475e40..5f1e55e 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -9,6 +9,7 @@ getPackages :: Expr [Package] getPackages = fromDiffExpr $ defaultPackages <> userPackages -- These are the packages we build by default +-- TODO: simplify defaultPackages :: Packages defaultPackages = mconcat [ stage0 ? packagesStage0 @@ -19,7 +20,7 @@ packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] - , stage0 ? append [deriveConstants, genapply] -- TODO: simplify + , stage0 ? append [deriveConstants, genapply, genprimopcode] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] -- TODO: what do we do with parallel, stm, random, primitive, vector and dph? From git at git.haskell.org Fri Oct 27 00:11:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for separate interface file compilation. (6b532ba) Message-ID: <20171027001106.B2A903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b532baa0dd71e5c61229c0be832d871bf0bf705/ghc >--------------------------------------------------------------- commit 6b532baa0dd71e5c61229c0be832d871bf0bf705 Author: Andrey Mokhov Date: Sat Jan 16 03:11:31 2016 +0000 Add support for separate interface file compilation. See #174. >--------------------------------------------------------------- 6b532baa0dd71e5c61229c0be832d871bf0bf705 src/Rules/Compile.hs | 16 ++++++++++++++-- src/Settings/Builders/Ghc.hs | 15 +++++++++------ src/Settings/User.hs | 7 ++++++- 3 files changed, 29 insertions(+), 9 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 2fb315c..2065415 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,10 +12,22 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let buildPath = targetPath stage pkg -/- "build" matchBuildResult buildPath "hi" ?> \hi -> - need [ hi -<.> osuf (detectWay hi) ] + if compileInterfaceFilesSeparately + then do + let way = detectWay hi + (src, deps) <- dependencies buildPath $ hi -<.> osuf way + need $ src : deps + build $ fullTargetWithWay target (Ghc stage) way [src] [hi] + else need [ hi -<.> osuf (detectWay hi) ] matchBuildResult buildPath "hi-boot" ?> \hiboot -> - need [ hiboot -<.> obootsuf (detectWay hiboot) ] + if compileInterfaceFilesSeparately + then do + let way = detectWay hiboot + (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf way + need $ src : deps + build $ fullTargetWithWay target (Ghc stage) way [src] [hiboot] + else need [ hiboot -<.> obootsuf (detectWay hiboot) ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) matchBuildResult buildPath "o" ?> \obj -> do diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 40b5a0f..0f1fc32 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -24,7 +24,9 @@ ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output + buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs gmpLibs <- lift $ readFileLines gmpLibNameCache libDirs <- getPkgDataList DepLibDirs @@ -35,12 +37,13 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , not buildObj ? arg "-no-auto-link-packages" - , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] - , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] - , buildObj ? arg "-c" + , buildProg ? arg "-no-auto-link-packages" + , buildProg ? append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] + , buildProg ? append [ "-optl-L" ++ dir | dir <- libDirs ] + , not buildProg ? arg "-c" , append =<< getInputs - , arg "-o", arg =<< getOutput ] + , buildHi ? append ["-fno-code", "-fwrite-interface"] + , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 3cebe13..5b82571 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,8 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors, splitObjects + verboseCommands, turnWarningsIntoErrors, splitObjects, + compileInterfaceFilesSeparately ) where import GHC @@ -101,3 +102,7 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False + +-- | Decouple the compilation of @*.hi@ and @*.o@ files by setting to True. +compileInterfaceFilesSeparately :: Bool +compileInterfaceFilesSeparately = True From git at git.haskell.org Fri Oct 27 00:11:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build hp2ps utility. (1057ef3) Message-ID: <20171027001110.741853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1057ef38cea541d0b31b075bd9936a619f23f4fa/ghc >--------------------------------------------------------------- commit 1057ef38cea541d0b31b075bd9936a619f23f4fa Author: Andrey Mokhov Date: Sun Dec 13 22:18:45 2015 +0000 Build hp2ps utility. >--------------------------------------------------------------- 1057ef38cea541d0b31b075bd9936a619f23f4fa src/GHC.hs | 27 +++++++++++++-------------- src/Rules/Data.hs | 22 +++++++++++++++++++++- src/Rules/Dependencies.hs | 7 +++++-- src/Rules/Program.hs | 1 + src/Settings/Builders/Ghc.hs | 9 ++++++--- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Packages.hs | 2 +- 7 files changed, 49 insertions(+), 23 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 1057ef38cea541d0b31b075bd9936a619f23f4fa From git at git.haskell.org Fri Oct 27 00:11:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian. (3be1a41) Message-ID: <20171027001110.192F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3be1a417e326d35b5756a056e93ce2b828bf8790/ghc >--------------------------------------------------------------- commit 3be1a417e326d35b5756a056e93ce2b828bf8790 Author: Andrey Mokhov Date: Thu May 5 03:16:20 2016 +0100 Rename to Hadrian. >--------------------------------------------------------------- 3be1a417e326d35b5756a056e93ce2b828bf8790 src/Base.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 5e66a27..625dfd8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -45,11 +45,11 @@ import System.IO -- TODO: reexport Stage, etc.? -- Build system files and paths -shakePath :: FilePath -shakePath = "hadrian" +hadrianPath :: FilePath +hadrianPath = "hadrian" configPath :: FilePath -configPath = shakePath -/- "cfg" +configPath = hadrianPath -/- "cfg" configFile :: FilePath configFile = configPath -/- "system.config" @@ -57,7 +57,7 @@ configFile = configPath -/- "system.config" -- | Path to source files of the build system, e.g. this file is located at -- sourcePath -/- "Base.hs". We use this to `need` some of the source files. sourcePath :: FilePath -sourcePath = shakePath -/- "src" +sourcePath = hadrianPath -/- "src" -- TODO: move to buildRootPath, see #113 programInplacePath :: FilePath From git at git.haskell.org Fri Oct 27 00:11:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need patch file by default. (6a09a6b) Message-ID: <20171027001113.A9E6F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a09a6b9720f8782224eddd39db9f4ec9cd3164b/ghc >--------------------------------------------------------------- commit 6a09a6b9720f8782224eddd39db9f4ec9cd3164b Author: Andrey Mokhov Date: Thu May 5 03:19:02 2016 +0100 Don't need patch file by default. >--------------------------------------------------------------- 6a09a6b9720f8782224eddd39db9f4ec9cd3164b src/Rules/Actions.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index edf98eb..32d2544 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -146,7 +146,6 @@ runMakeWithVerbosity verbose dir args = do applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch - need [file] needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file From git at git.haskell.org Fri Oct 27 00:11:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch compileInterfaceFilesSeparately off by default. (c9ec473) Message-ID: <20171027001110.CF5013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9ec473baba6bde9097a456e82dedfcc3bb1252e/ghc >--------------------------------------------------------------- commit c9ec473baba6bde9097a456e82dedfcc3bb1252e Author: Andrey Mokhov Date: Sat Jan 16 03:12:55 2016 +0000 Switch compileInterfaceFilesSeparately off by default. See #174. >--------------------------------------------------------------- c9ec473baba6bde9097a456e82dedfcc3bb1252e src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 5b82571..2a1471d 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -105,4 +105,4 @@ turnWarningsIntoErrors = return False -- | Decouple the compilation of @*.hi@ and @*.o@ files by setting to True. compileInterfaceFilesSeparately :: Bool -compileInterfaceFilesSeparately = True +compileInterfaceFilesSeparately = False From git at git.haskell.org Fri Oct 27 00:11:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (0678e10) Message-ID: <20171027001114.8750A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0678e1030e5f90b55dedcf2d72adc431f0995de5/ghc >--------------------------------------------------------------- commit 0678e1030e5f90b55dedcf2d72adc431f0995de5 Author: Andrey Mokhov Date: Mon Dec 14 02:43:00 2015 +0000 Clean up. >--------------------------------------------------------------- 0678e1030e5f90b55dedcf2d72adc431f0995de5 src/GHC.hs | 2 +- src/Package.hs | 3 +++ 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index 355ed71..ea48014 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -28,7 +28,7 @@ defaultKnownPackages = , process, runghc, stm, templateHaskell, terminfo, time, transformers, unix , win32, xhtml ] --- Package definitions +-- Package definitions (see Package.hs) array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, diff --git a/src/Package.hs b/src/Package.hs index 85fbd13..a490cb9 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -9,11 +9,14 @@ import GHC.Generics (Generic) -- It is helpful to distinguish package names from strings. type PackageName = String +-- type PackageType = Program | Library + -- pkgPath is the path to the source code relative to the root data Package = Package { pkgName :: PackageName, -- Examples: "ghc", "Cabal" pkgPath :: FilePath -- "compiler", "libraries/Cabal/Cabal" + -- pkgType :: PackageType -- TopLevel, Library } deriving Generic From git at git.haskell.org Fri Oct 27 00:11:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix lint error on doesFileExist 'config.mk'. (f63e9db) Message-ID: <20171027001114.DAF003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f63e9db131bfd9860db988b01d4a581a6541d796/ghc >--------------------------------------------------------------- commit f63e9db131bfd9860db988b01d4a581a6541d796 Author: Andrey Mokhov Date: Sat Jan 16 12:16:29 2016 +0000 Fix lint error on doesFileExist 'config.mk'. >--------------------------------------------------------------- f63e9db131bfd9860db988b01d4a581a6541d796 src/Rules/Gmp.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 61a0a6f..ec14b36 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -2,6 +2,8 @@ module Rules.Gmp ( gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH, gmpDependencies ) where +import qualified System.Directory as IO + import Base import Expression import GHC @@ -80,7 +82,7 @@ gmpRules = do -- twice -- think how this can be optimised (shall we solve #18 first?) -- TODO: this is a hacky optimisation: we do not rerun configure of -- integerGmp package if we detect the results of the previous run - unlessM (doesFileExist $ gmpBase -/- "config.mk") $ do + unlessM (liftIO . IO.doesFileExist $ gmpBase -/- "config.mk") $ do args <- configureIntGmpArguments runConfigure (pkgPath integerGmp) envs args From git at git.haskell.org Fri Oct 27 00:11:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of partial functions. (fa57784) Message-ID: <20171027001117.7C4D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fa57784081e696d90b305601b9cfd960841f082c/ghc >--------------------------------------------------------------- commit fa57784081e696d90b305601b9cfd960841f082c Author: Andrey Mokhov Date: Thu May 5 03:24:45 2016 +0100 Get rid of partial functions. >--------------------------------------------------------------- fa57784081e696d90b305601b9cfd960841f082c src/Rules/Libffi.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 17067ad..424b552 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -76,17 +76,18 @@ libffiRules = do createDirectory $ buildRootPath -/- stageString Stage0 tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - when (length tarballs /= 1) $ - putError $ "libffiRules: exactly one libffi tarball expected" - ++ "(found: " ++ show tarballs ++ ")." + tarball <- case tarballs of + [file] -> return $ unifyPath file + _ -> putError $ "libffiRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." - need tarballs - let libname = dropExtension . dropExtension . takeFileName $ head tarballs + need [tarball] + let libname = dropExtension . dropExtension $ takeFileName tarball removeDirectory (buildRootPath -/- libname) -- TODO: Simplify. actionFinally (do - build $ Target libffiContext Tar tarballs [buildRootPath] + build $ Target libffiContext Tar [tarball] [buildRootPath] moveDirectory (buildRootPath -/- libname) libffiBuildPath) $ removeFiles buildRootPath [libname "*"] From git at git.haskell.org Fri Oct 27 00:11:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make the build badges follow the master branch only (e9013dc) Message-ID: <20171027001119.588DE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e9013dcf7a13d9b55e353bb5e1527c4a75726b4d/ghc >--------------------------------------------------------------- commit e9013dcf7a13d9b55e353bb5e1527c4a75726b4d Author: Andrey Mokhov Date: Sat Jan 16 15:40:59 2016 +0000 Make the build badges follow the master branch only [skip ci] >--------------------------------------------------------------- e9013dcf7a13d9b55e353bb5e1527c4a75726b4d README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index f5b8117..8651b9b 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Shaking up GHC ============== -[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) As part of my 6-month research secondment to Microsoft Research in Cambridge From git at git.haskell.org Fri Oct 27 00:11:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: No need to modify configure.ac any more. See https://phabricator.haskell.org/D1638 (5e7de75) Message-ID: <20171027001118.CAA293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e7de75760b6b44eb7d9caaae3dc805c44bb6604/ghc >--------------------------------------------------------------- commit 5e7de75760b6b44eb7d9caaae3dc805c44bb6604 Author: Andrey Mokhov Date: Wed Dec 16 22:49:27 2015 +0000 No need to modify configure.ac any more. See https://phabricator.haskell.org/D1638 >--------------------------------------------------------------- 5e7de75760b6b44eb7d9caaae3dc805c44bb6604 src/Rules/Config.hs | 15 --------------- 1 file changed, 15 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 4987fcc..bb4866d 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -2,11 +2,6 @@ module Rules.Config (configRules) where import Base --- We add the following line to 'configure.ac' in order to produce configuration --- file "system.config" from "system.config.in" by running 'configure' script. -configCommand :: String -configCommand = "AC_CONFIG_FILES([" ++ configPath ++ "system.config])" - configRules :: Rules () configRules = do configPath -/- "system.config" %> \_ -> do @@ -14,16 +9,6 @@ configRules = do putBuild "Running configure..." cmd "bash configure" -- TODO: get rid of 'bash' - -- TODO: this rule won't rebuild if configure.ac is changed. Worth fixing? "configure" %> \_ -> do - -- Make sure 'configure.ac' script contains a line with configCommand - script <- fmap lines . liftIO $ readFile "configure.ac" - when (configCommand `notElem` script) $ do - putBuild $ "Adding '" ++ configCommand ++ "' to configure.ac..." - let (before, rest) = break ("AC_CONFIG_FILES" `isPrefixOf`) script - when (null rest) $ do - putError "No AC_CONFIG_FILES command in configure.ac!" - let newScript = unlines $ before ++ [configCommand] ++ rest - length newScript `seq` liftIO (writeFile "configure.ac" newScript) putBuild "Running autoconf..." cmd "bash autoconf" -- TODO: get rid of 'bash' From git at git.haskell.org Fri Oct 27 00:11:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop removeDirectoryIfExists. (ad53022) Message-ID: <20171027001121.37DE93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ad53022e5f3da17d8b744b922c32756dba6408d2/ghc >--------------------------------------------------------------- commit ad53022e5f3da17d8b744b922c32756dba6408d2 Author: Andrey Mokhov Date: Thu May 5 03:52:19 2016 +0100 Drop removeDirectoryIfExists. See #163. >--------------------------------------------------------------- ad53022e5f3da17d8b744b922c32756dba6408d2 src/Base.hs | 7 +------ src/Oracles/PackageDb.hs | 2 +- src/Rules/Actions.hs | 3 ++- src/Rules/Clean.hs | 16 ++++++---------- src/Rules/Gmp.hs | 2 +- 5 files changed, 11 insertions(+), 19 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 625dfd8..ccadd22 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,7 +23,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath + removeFileIfExists, matchVersionedFilePath ) where import Control.Applicative @@ -176,11 +176,6 @@ lookupAll (x:xs) (y:ys) = case compare x (fst y) of removeFileIfExists :: FilePath -> Action () removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f --- | Remove a directory that doesn't necessarily exist -removeDirectoryIfExists :: FilePath -> Action () -removeDirectoryIfExists d = - liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d - -- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the -- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: diff --git a/src/Oracles/PackageDb.hs b/src/Oracles/PackageDb.hs index b644989..760f2a7 100644 --- a/src/Oracles/PackageDb.hs +++ b/src/Oracles/PackageDb.hs @@ -17,6 +17,6 @@ packageDbOracle = void $ let dir = packageDbDirectory stage file = dir -/- "package.cache" unlessM (liftIO $ IO.doesFileExist file) $ do - removeDirectoryIfExists dir + removeDirectory dir build $ Target (vanillaContext stage ghcPkg) (GhcPkg stage) [] [dir] putSuccess $ "| Successfully initialised " ++ dir diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 32d2544..25bf72e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -99,10 +99,11 @@ createDirectory dir = do putBuild $ "| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir +-- | Remove a directory that doesn't necessarily exist. removeDirectory :: FilePath -> Action () removeDirectory dir = do putBuild $ "| Remove directory " ++ dir - removeDirectoryIfExists dir + liftIO . whenM (IO.doesDirectoryExist dir) $ IO.removeDirectoryRecursive dir -- Note, the source directory is untracked copyDirectory :: FilePath -> FilePath -> Action () diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index ca5c062..f615e54 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -3,24 +3,20 @@ module Rules.Clean (cleanRules) where import Base import Context import Package +import Rules.Actions import Rules.Generate import Settings.Packages import Settings.Paths import Settings.User import Stage -clean :: FilePath -> Action () -clean dir = do - putBuild $ "| Remove files in " ++ dir ++ "..." - removeDirectoryIfExists dir - cleanRules :: Rules () cleanRules = do "clean" ~> do - forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) - clean programInplacePath - clean "inplace/lib" - clean derivedConstantsPath + forM_ [Stage0 ..] $ removeDirectory . (buildRootPath -/-) . stageString + removeDirectory programInplacePath + removeDirectory "inplace/lib" + removeDirectory derivedConstantsPath forM_ includesDependencies $ \file -> do putBuild $ "| Remove " ++ file removeFileIfExists file @@ -28,7 +24,7 @@ cleanRules = do forM_ knownPackages $ \pkg -> forM_ [Stage0 ..] $ \stage -> do let dir = pkgPath pkg -/- contextDirectory (vanillaContext stage pkg) - removeDirectoryIfExists dir + quietly $ removeDirectory dir putBuild $ "| Remove Hadrian files..." removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index d98bc3b..9cec3a3 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -52,7 +52,7 @@ gmpRules = do -- TODO: split into multiple rules gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - removeDirectoryIfExists gmpBuildPath + removeDirectory gmpBuildPath -- We don't use system GMP on Windows. TODO: fix? windows <- windowsHost From git at git.haskell.org Fri Oct 27 00:11:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't build system.config by default. (8ef67ed) Message-ID: <20171027001122.953CA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ef67edb699b18ca41ed535069f7183a15a98cf3/ghc >--------------------------------------------------------------- commit 8ef67edb699b18ca41ed535069f7183a15a98cf3 Author: Andrey Mokhov Date: Wed Dec 16 23:07:44 2015 +0000 Don't build system.config by default. >--------------------------------------------------------------- 8ef67edb699b18ca41ed535069f7183a15a98cf3 src/Rules/Config.hs | 3 ++- src/Settings/User.hs | 5 ++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index bb4866d..50471d5 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -1,9 +1,10 @@ module Rules.Config (configRules) where import Base +import Settings.User configRules :: Rules () -configRules = do +configRules = when buildSystemConfigFile $ do configPath -/- "system.config" %> \_ -> do need [configPath -/- "system.config.in", "configure"] putBuild "Running configure..." diff --git a/src/Settings/User.hs b/src/Settings/User.hs index d841028..5159bce 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -2,7 +2,7 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - ghcDebugged, dynamicGhcPrograms, laxDependencies + ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile ) where import Expression @@ -77,3 +77,6 @@ laxDependencies = False buildHaddock :: Predicate buildHaddock = return True + +buildSystemConfigFile :: Bool +buildSystemConfigFile = False From git at git.haskell.org Fri Oct 27 00:11:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor paths to auxiliary build files. (4a90b33) Message-ID: <20171027001123.3418E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a90b33ef70df26624fc064cdd4508677a0b7eec/ghc >--------------------------------------------------------------- commit 4a90b33ef70df26624fc064cdd4508677a0b7eec Author: Andrey Mokhov Date: Sat Jan 16 18:08:51 2016 +0000 Refactor paths to auxiliary build files. See #176. >--------------------------------------------------------------- 4a90b33ef70df26624fc064cdd4508677a0b7eec src/Rules/Actions.hs | 2 -- src/Settings/Builders/Ghc.hs | 4 ---- src/Settings/Packages/IntegerGmp.hs | 6 +----- src/Settings/Paths.hs | 16 ++++++++++++---- 4 files changed, 13 insertions(+), 15 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 21d134f..663f53d 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -157,13 +157,11 @@ putInfo Target.Target {..} = putProgressInfo $ renderAction digest [x] = x digest (x:xs) = x ++ " (and " ++ show (length xs) ++ " more)" - -- | Switch for @putBuild@ filtered through @buildInfo@ putProgressInfo :: String -> Action () putProgressInfo s | buildInfo /= None = putBuild s putProgressInfo _ = pure () - -- | Render an action. renderAction :: String -> String -> String -> String renderAction what input output = case buildInfo of diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 0f1fc32..c97cd56 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -11,10 +11,6 @@ import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) import Settings.Builders.Common (cIncludeArgs) --- GMP library names extracted from integer-gmp.buildinfo -gmpLibNameCache :: FilePath -gmpLibNameCache = shakeFilesPath -/- "gmp-lib-names" - -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 8b100b3..7122457 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -4,11 +4,7 @@ import Base import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) -import Settings.User - --- TODO: move elsewhere -gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage0/gmp" +import Settings.Paths -- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index bec143b..0513d6c 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,6 +1,7 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgGhciLibraryFile, packageConfiguration, packageConfigurationInitialised + pkgGhciLibraryFile, packageConfiguration, packageConfigurationInitialised, + gmpBuildPath, gmpLibNameCache ) where import Base @@ -47,6 +48,13 @@ packageConfiguration _ = "inplace/lib/package.conf.d" -- StageN, N > 0, share the same packageConfiguration (see above) packageConfigurationInitialised :: Stage -> FilePath -packageConfigurationInitialised stage = - shakeFilesPath -/- "package-configuration-initialised-" - ++ stageString (min stage Stage1) +packageConfigurationInitialised stage = packageConfiguration stage -/- + "package-configuration-initialised-" ++ stageString (min stage Stage1) + +-- This is the build directory for in-tree GMP library +gmpBuildPath :: FilePath +gmpBuildPath = buildRootPath -/- "stage0/gmp" + +-- GMP library names extracted from integer-gmp.buildinfo +gmpLibNameCache :: FilePath +gmpLibNameCache = gmpBuildPath -/- "gmp-lib-names" From git at git.haskell.org Fri Oct 27 00:11:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (850863e) Message-ID: <20171027001126.0887E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/850863e56cf2c4d798cac7701e271c85d6bac2de/ghc >--------------------------------------------------------------- commit 850863e56cf2c4d798cac7701e271c85d6bac2de Author: Andrey Mokhov Date: Thu Dec 17 19:42:44 2015 +0000 Update README.md >--------------------------------------------------------------- 850863e56cf2c4d798cac7701e271c85d6bac2de README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 54742ee..faf3155 100644 --- a/README.md +++ b/README.md @@ -3,4 +3,4 @@ Shaking up GHC As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). -This is supposed to go into the `shake` directory of the GHC source tree (as a submodule). +This is supposed to go into the `build` directory of the GHC source tree. From git at git.haskell.org Fri Oct 27 00:11:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Base.removeFileIfExists to Rules.Actions.removeFile. (658d373) Message-ID: <20171027001124.E830B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/658d373c5b823792758e7d3ccb0577b6ecb24c82/ghc >--------------------------------------------------------------- commit 658d373c5b823792758e7d3ccb0577b6ecb24c82 Author: Andrey Mokhov Date: Thu May 5 03:59:50 2016 +0100 Move Base.removeFileIfExists to Rules.Actions.removeFile. See #163. >--------------------------------------------------------------- 658d373c5b823792758e7d3ccb0577b6ecb24c82 src/Base.hs | 7 +------ src/Rules/Actions.hs | 8 +++++++- src/Rules/Clean.hs | 4 +--- src/Rules/Dependencies.hs | 2 +- src/Rules/Library.hs | 2 +- 5 files changed, 11 insertions(+), 12 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index ccadd22..a26fea1 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,7 +23,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - removeFileIfExists, matchVersionedFilePath + matchVersionedFilePath ) where import Control.Applicative @@ -39,7 +39,6 @@ import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI -import qualified System.Directory as IO import System.IO -- TODO: reexport Stage, etc.? @@ -172,10 +171,6 @@ lookupAll (x:xs) (y:ys) = case compare x (fst y) of EQ -> Just (snd y) : lookupAll xs (y:ys) GT -> lookupAll (x:xs) ys --- | Remove a file that doesn't necessarily exist -removeFileIfExists :: FilePath -> Action () -removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f - -- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the -- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 25bf72e..9910ce5 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,6 +1,6 @@ module Rules.Actions ( build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, - createDirectory, removeDirectory, copyDirectory, moveDirectory, + removeFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, applyPatch, fixFile, runMake, runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable ) where @@ -94,6 +94,12 @@ moveFile source target = do putProgressInfo $ renderAction "Move file" source target liftIO $ IO.renameFile source target +-- | Remove a file that doesn't necessarily exist. +removeFile :: FilePath -> Action () +removeFile file = do + putBuild $ "| Remove file " ++ file + liftIO . whenM (IO.doesFileExist file) $ IO.removeFile file + createDirectory :: FilePath -> Action () createDirectory dir = do putBuild $ "| Create directory " ++ dir diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index f615e54..613073a 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -17,9 +17,7 @@ cleanRules = do removeDirectory programInplacePath removeDirectory "inplace/lib" removeDirectory derivedConstantsPath - forM_ includesDependencies $ \file -> do - putBuild $ "| Remove " ++ file - removeFileIfExists file + forM_ includesDependencies removeFile putBuild $ "| Remove files generated by ghc-cabal..." forM_ knownPackages $ \pkg -> forM_ [Stage0 ..] $ \stage -> do diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 9059b3d..f5d781a 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -29,7 +29,7 @@ buildPackageDependencies rs context at Context {..} = then writeFileChanged out "" else buildWithResources rs $ Target context (Ghc FindDependencies stage) srcs [out] - removeFileIfExists $ out <.> "bak" + removeFile $ out <.> "bak" -- TODO: don't accumulate *.deps into .dependencies path -/- ".dependencies" %> \out -> do diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 8e09162..2b90d1f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -22,7 +22,7 @@ buildPackageLibrary context at Context {..} = do -- TODO: handle dynamic libraries matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do - removeFileIfExists a + removeFile a cSrcs <- cSources context hSrcs <- hSources context From git at git.haskell.org Fri Oct 27 00:11:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (1c877aa) Message-ID: <20171027001126.C31803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c877aa89595d8d6e30f2673e8031d23cdeabdfa/ghc >--------------------------------------------------------------- commit 1c877aa89595d8d6e30f2673e8031d23cdeabdfa Merge: 4a90b33 e9013dc Author: Andrey Mokhov Date: Sat Jan 16 18:10:49 2016 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 1c877aa89595d8d6e30f2673e8031d23cdeabdfa README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:11:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Show output of boot and configure. (72cbd44) Message-ID: <20171027001128.92D3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72cbd44066d9a9e30c5c9613884d4f778afe42e5/ghc >--------------------------------------------------------------- commit 72cbd44066d9a9e30c5c9613884d4f778afe42e5 Author: Andrey Mokhov Date: Thu May 5 04:22:57 2016 +0100 Show output of boot and configure. See #234. >--------------------------------------------------------------- 72cbd44066d9a9e30c5c9613884d4f778afe42e5 src/Rules/Actions.hs | 2 +- src/Rules/Configure.hs | 11 ++++------- 2 files changed, 5 insertions(+), 8 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9910ce5..a312ce9 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -62,7 +62,7 @@ customBuild rs opts target at Target {..} = do need [dir -/- "configure"] -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" - cmd Shell (EchoStdout False) [Cwd dir] [path] (env:opts) argList + cmd Shell [Cwd dir] [path] (env:opts) argList HsCpp -> captureStdout target path argList GenApply -> captureStdout target path argList diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index d1c7cf2..44ed75c 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -1,6 +1,6 @@ module Rules.Configure (configureRules) where -import qualified System.Info +import qualified System.Info as System import Base import Builder @@ -22,12 +22,9 @@ configureRules = do ++ "--skip-configure flag." else do -- We cannot use windowsHost here due to a cyclic dependency. - when (System.Info.os == "mingw32") $ do + when (System.os == "mingw32") $ do putBuild "| Checking for Windows tarballs..." - quietly $ cmd [ "bash" - , "mk/get-win32-tarballs.sh" - , "download" - , System.Info.arch ] + quietly $ cmd ["bash mk/get-win32-tarballs.sh download", System.arch] let srcs = map (<.> "in") outs context = vanillaContext Stage0 compiler need srcs @@ -41,4 +38,4 @@ configureRules = do else do need ["configure.ac"] putBuild "| Running boot..." - quietly $ cmd (EchoStdout False) "perl boot" + quietly $ cmd "perl boot" From git at git.haskell.org Fri Oct 27 00:11:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (f5dff68) Message-ID: <20171027001130.A2C8E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5dff684386aaec9ed079364423524c91b5be2cd/ghc >--------------------------------------------------------------- commit f5dff684386aaec9ed079364423524c91b5be2cd Author: Andrey Mokhov Date: Sat Jan 16 23:56:57 2016 +0000 Minor revision. [skip ci] >--------------------------------------------------------------- f5dff684386aaec9ed079364423524c91b5be2cd src/Predicates.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 497fca5..1e56993 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -9,15 +9,15 @@ import Expression -- | Is the build currently in the provided stage? stage :: Stage -> Predicate -stage s = fmap (s ==) getStage +stage s = (s ==) <$> getStage -- | Is a particular package being built? package :: Package -> Predicate -package p = fmap (p ==) getPackage +package p = (p ==) <$> getPackage -- | Is an unstaged builder is being used such as /GhcCabal/? builder :: Builder -> Predicate -builder b = fmap (b ==) getBuilder +builder b = (b ==) <$> getBuilder -- | Is a certain builder used in the current stage? stagedBuilder :: (Stage -> Builder) -> Predicate @@ -35,11 +35,11 @@ builderGhc = stagedBuilder Ghc ||^ stagedBuilder GhcM -- | Does any of the output files match a given pattern? file :: FilePattern -> Predicate -file f = fmap (any (f ?==)) getOutputs +file f = any (f ?==) <$> getOutputs -- | Is the current build 'Way' equal to a certain value? way :: Way -> Predicate -way w = fmap (w ==) getWay +way w = (w ==) <$> getWay -- | Is the build currently in stage 0? stage0 :: Predicate From git at git.haskell.org Fri Oct 27 00:11:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add NFData instances (bf75f42) Message-ID: <20171027001129.D5B153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf75f422b738ae95fb7d3b814d9335c77ef6d6cd/ghc >--------------------------------------------------------------- commit bf75f422b738ae95fb7d3b814d9335c77ef6d6cd Author: Ben Gamari Date: Wed Dec 16 01:27:04 2015 +0100 Add NFData instances >--------------------------------------------------------------- bf75f422b738ae95fb7d3b814d9335c77ef6d6cd src/Builder.hs | 1 + src/Package.hs | 1 + src/Stage.hs | 1 + src/Way.hs | 3 +++ 4 files changed, 6 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 67be69f..007dae3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -111,3 +111,4 @@ fixAbsolutePathOnWindows path = do -- Instances for storing in the Shake database instance Binary Builder instance Hashable Builder +instance NFData Builder diff --git a/src/Package.hs b/src/Package.hs index a490cb9..f64daee 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -49,3 +49,4 @@ instance Ord Package where instance Binary Package instance Hashable Package where hashWithSalt salt = hashWithSalt salt . show +instance NFData Package diff --git a/src/Stage.hs b/src/Stage.hs index f4e39b0..3aca206 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -13,3 +13,4 @@ instance Show Stage where -- Instances for storing in the Shake database instance Binary Stage instance Hashable Stage +instance NFData Stage diff --git a/src/Way.hs b/src/Way.hs index 7f1ca31..095bd52 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -169,3 +169,6 @@ instance Binary Way where instance Hashable Way where hashWithSalt salt = hashWithSalt salt . show + +instance NFData Way where + rnf (Way s) = s `seq` () From git at git.haskell.org Fri Oct 27 00:11:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix get-win32-tarballs command line. (32a2526) Message-ID: <20171027001132.721CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/32a25268694276e609343dfc28361444a5fa7287/ghc >--------------------------------------------------------------- commit 32a25268694276e609343dfc28361444a5fa7287 Author: Andrey Mokhov Date: Thu May 5 04:25:47 2016 +0100 Fix get-win32-tarballs command line. >--------------------------------------------------------------- 32a25268694276e609343dfc28361444a5fa7287 src/Rules/Configure.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index 44ed75c..d36542a 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -24,7 +24,7 @@ configureRules = do -- We cannot use windowsHost here due to a cyclic dependency. when (System.os == "mingw32") $ do putBuild "| Checking for Windows tarballs..." - quietly $ cmd ["bash mk/get-win32-tarballs.sh download", System.arch] + quietly $ cmd ["bash", "mk/get-win32-tarballs.sh", "download", System.arch] let srcs = map (<.> "in") outs context = vanillaContext Stage0 compiler need srcs From git at git.haskell.org Fri Oct 27 00:11:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build.sh for building on Posix platforms (525f966) Message-ID: <20171027001133.54B9A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/525f9668125f368584aa62a0d47e6bc8df23d8b4/ghc >--------------------------------------------------------------- commit 525f9668125f368584aa62a0d47e6bc8df23d8b4 Author: Ben Gamari Date: Wed Dec 16 01:28:13 2015 +0100 Add build.sh for building on Posix platforms >--------------------------------------------------------------- 525f9668125f368584aa62a0d47e6bc8df23d8b4 build.sh | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/build.sh b/build.sh new file mode 100755 index 0000000..cf217bd --- /dev/null +++ b/build.sh @@ -0,0 +1,6 @@ +#!/bin/bash -e + +root=`dirname $0` +mkdir -p $root/_shake +ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/_shake -o $root/_shake/build +$root/_shake/build --lint --directory $root/.. $@ From git at git.haskell.org Fri Oct 27 00:11:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor ways, revise comments. (3ff1fc1) Message-ID: <20171027001134.46E483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ff1fc1097d98f17ab081be3c9f1379bea69d04a/ghc >--------------------------------------------------------------- commit 3ff1fc1097d98f17ab081be3c9f1379bea69d04a Author: Andrey Mokhov Date: Sat Jan 16 23:58:20 2016 +0000 Refactor ways, revise comments. See #100. >--------------------------------------------------------------- 3ff1fc1097d98f17ab081be3c9f1379bea69d04a src/Rules/Program.hs | 2 +- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/User.hs | 24 +++++++++++++----------- src/Settings/Ways.hs | 33 +++++++++++++++------------------ src/Way.hs | 1 + 6 files changed, 32 insertions(+), 32 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 93a6d6c..d472e88 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -77,7 +77,7 @@ buildBinary target @ (PartialTarget stage pkg) bin = do ++ [ buildPath -/- "Paths_hsc2hs.o" | pkg == hsc2hs ] ++ [ buildPath -/- "Paths_haddock.o" | pkg == haddock ] objs = cObjs ++ hObjs - ways <- interpretPartial target getWays + ways <- interpretPartial target getLibraryWays depNames <- interpretPartial target $ getPkgDataList TransitiveDepNames let libStage = min stage Stage1 -- libraries are built only in Stage0/1 libTarget = PartialTarget libStage pkg diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index c97cd56..3537aed 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -48,7 +48,7 @@ splitObjectsArgs = splitObjects ? do ghcMBuilderArgs :: Args ghcMBuilderArgs = stagedBuilder GhcM ? do - ways <- getWays + ways <- getLibraryWays mconcat [ arg "-M" , commonGhcArgs , arg "-include-pkg-deps" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 8591bd5..afd3def 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -49,7 +49,7 @@ ghcCabalHsColourBuilderArgs = builder GhcCabalHsColour ? do -- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do - ways <- getWays + ways <- getLibraryWays withGhci <- lift ghcWithInterpreter append [ if vanilla `elem` ways then "--enable-library-vanilla" diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 2a1471d..f57a2ac 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,6 +1,6 @@ module Settings.User ( buildRootPath, userTargetDirectory, userProgramPath, trackBuildSystem, - userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, + userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, verboseCommands, turnWarningsIntoErrors, splitObjects, @@ -36,24 +36,26 @@ userPackages = mempty userKnownPackages :: [Package] userKnownPackages = [] --- Control which ways libraries and rts are built --- TODO: skip profiling for speed, skip dynamic since it's currently broken -userLibWays :: Ways -userLibWays = remove [profiling, dynamic] +-- | Control which ways library packages are built +-- FIXME: skip profiling for speed +-- FIXME: skip dynamic since it's currently broken #4 +userLibraryWays :: Ways +userLibraryWays = remove [profiling, dynamic] +-- | Control which ways the 'rts' package is built userRtsWays :: Ways userRtsWays = mempty --- Choose integer library: integerGmp, integerGmp2 or integerSimple +-- | Choose the integer library: integerGmp or integerSimple integerLibrary :: Package integerLibrary = integerGmp --- User-defined flags. Note the following type semantics: +-- | User-defined flags. Note the following type semantics: -- * Bool: a plain Boolean flag whose value is known at compile time -- * Action Bool: a flag whose value can depend on the build environment -- * Predicate: a flag depending on the build environment and the current target --- Set this to True if you are making any changes in the build system and want +-- | Set this to True if you are making any changes in the build system and want -- appropriate rebuilds to be initiated. Switching this to False speeds things -- up a little (particularly zero builds). -- WARNING: a complete rebuild is required when changing this setting. @@ -80,7 +82,7 @@ ghcProfiled = False ghcDebugged :: Bool ghcDebugged = False --- When laxDependencies flag is set to True, dependencies on the GHC executable +-- | When laxDependencies is set to True, dependencies on the GHC executable -- are turned into order-only dependencies to avoid needless recompilation when -- making changes to GHC's sources. In certain situations this can lead to build -- failures, in which case you should reset the flag (at least temporarily). @@ -93,8 +95,8 @@ buildHaddock = return False -- FIXME: should be return True, see #98 buildSystemConfigFile :: Bool buildSystemConfigFile = False --- Set to True to print full command lines during the build process. Note, this --- is a Predicate, hence you can enable verbose output for a chosen package +-- | Set to True to print full command lines during the build process. Note, +-- this is a Predicate, hence you can enable verbose output for a chosen package -- only, e.g.: verboseCommands = package ghcPrim verboseCommands :: Predicate verboseCommands = return False diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 8376213..223bc79 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,34 +1,31 @@ -module Settings.Ways (getWays, getLibWays, getRtsWays) where +module Settings.Ways (getLibraryWays, getRtsWays) where -import Data.Monoid +import Base import Expression import Predicates import Settings.User import Oracles.Config.Flag --- TODO: use a single expression Ways parameterised by package instead of --- expressions libWays and rtsWays - --- Combining default ways with user modifications -getLibWays :: Expr [Way] -getLibWays = fromDiffExpr $ defaultLibWays <> userLibWays - --- In Stage0 we only build vanilla -getWays :: Expr [Way] -getWays = mconcat [ stage0 ? return [vanilla], notStage0 ? getLibWays ] +-- | Combine default ways with user modifications +getLibraryWays :: Expr [Way] +getLibraryWays = fromDiffExpr $ defaultLibraryWays <> userLibraryWays getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays --- These are default ways -defaultLibWays :: Ways -defaultLibWays = mconcat - [ append [vanilla, profiling] - , platformSupportsSharedLibs ? append [dynamic] ] +-- These are default ways for library packages: +-- * We always build 'vanilla' way. +-- * We build 'profiling' way when stage > Stage0. +-- * We build 'dynamic' way when stage > Stage0 and the platform supports it. +defaultLibraryWays :: Ways +defaultLibraryWays = mconcat + [ append [vanilla] + , notStage0 ? append [profiling] + , notStage0 ? platformSupportsSharedLibs ? append [dynamic] ] defaultRtsWays :: Ways defaultRtsWays = do - ways <- getLibWays + ways <- getLibraryWays mconcat [ append [ logging, debug, threaded, threadedDebug, threadedLogging ] , (profiling `elem` ways) ? append [threadedProfiling] diff --git a/src/Way.hs b/src/Way.hs index ba20bd7..8923571 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -101,6 +101,7 @@ granSim = wayFromUnits [GranSim] -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? +-- See compiler/main/DynFlags.hs. threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, threadedDynamic, threadedDebugDynamic, From git at git.haskell.org Fri Oct 27 00:11:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move decode/encodeModule to Oracles.ModuleFiles. (9c45e4d) Message-ID: <20171027001136.1EB4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c45e4df1b88c2f726c84a651cb45b8e40f5b7c2/ghc >--------------------------------------------------------------- commit 9c45e4df1b88c2f726c84a651cb45b8e40f5b7c2 Author: Andrey Mokhov Date: Thu May 5 04:56:09 2016 +0100 Move decode/encodeModule to Oracles.ModuleFiles. >--------------------------------------------------------------- 9c45e4df1b88c2f726c84a651cb45b8e40f5b7c2 src/Base.hs | 18 +----------------- src/Oracles/ModuleFiles.hs | 17 ++++++++++++++++- src/Rules/Selftest.hs | 1 + 3 files changed, 18 insertions(+), 18 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a26fea1..1fcbae7 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,8 +22,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, - decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - matchVersionedFilePath + unifyPath, (-/-), versionToInt, matchVersionedFilePath ) where import Control.Applicative @@ -84,21 +83,6 @@ versionToInt s = major * 1000 + minor * 10 + patch where [major, minor, patch] = map read . words $ replaceEq '.' ' ' s --- | Given a module name extract the directory and file name, e.g.: --- --- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") --- > decodeModule "Prelude" == ("./", "Prelude") -decodeModule :: String -> (FilePath, String) -decodeModule = splitFileName . replaceEq '.' '/' - --- | Given the directory and file name find the corresponding module name, e.g.: --- --- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" --- > encodeModule "./" "Prelude" == "Prelude" --- > uncurry encodeModule (decodeModule name) == name -encodeModule :: FilePath -> String -> String -encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file - -- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 70cf983..652eb9a 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.ModuleFiles ( - findGenerator, haskellSources, moduleFilesOracle + decodeModule, encodeModule, findGenerator, haskellSources, moduleFilesOracle ) where import qualified Data.HashMap.Strict as Map @@ -26,6 +26,21 @@ determineBuilder file = case takeExtension file of ".hsc" -> Just Hsc2Hs _ -> Nothing +-- | Given a module name extract the directory and file name, e.g.: +-- +-- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") +-- > decodeModule "Prelude" == ("./", "Prelude") +decodeModule :: String -> (FilePath, String) +decodeModule = splitFileName . replaceEq '.' '/' + +-- | Given the directory and file name find the corresponding module name, e.g.: +-- +-- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" +-- > encodeModule "./" "Prelude" == "Prelude" +-- > uncurry encodeModule (decodeModule name) == name +encodeModule :: FilePath -> String -> String +encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file + -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) -- ".build/stage1/compiler/build/Lexer.hs" diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f549b0f..8037682 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,6 +6,7 @@ import Development.Shake import Test.QuickCheck import Base +import Oracles.ModuleFiles (decodeModule, encodeModule) import Settings.Builders.Ar (chunksOfSize) import Way From git at git.haskell.org Fri Oct 27 00:11:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: deriveConstants now has a Cabal file (c0f3b67) Message-ID: <20171027001137.24E973A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c0f3b6709468744f8192171b94ab08d2c1010959/ghc >--------------------------------------------------------------- commit c0f3b6709468744f8192171b94ab08d2c1010959 Author: Ben Gamari Date: Wed Dec 16 02:19:26 2015 +0100 deriveConstants now has a Cabal file Since 314395e00be10e6343840c215a4779aeec2542df >--------------------------------------------------------------- c0f3b6709468744f8192171b94ab08d2c1010959 src/Rules/Compile.hs | 5 ----- src/Rules/Data.hs | 12 +----------- 2 files changed, 1 insertion(+), 16 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 60123ef..9f718eb 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -28,11 +28,6 @@ compilePackage _ target @ (PartialTarget stage pkg) = do build $ fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases - priority 2.0 $ buildPath -/- "DeriveConstants.o" %> \obj -> do - let src = pkgPath pkg -/- "DeriveConstants.hs" - need [src] - build $ fullTargetWithWay target (Ghc stage) vanilla [src] [obj] - priority 2.0 $ buildPath -/- "GenApply.o" %> \obj -> do let src = pkgPath pkg -/- "GenApply.hs" need [src] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index cba8b69..2898257 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (deriveConstants, genapply, genprimopcode, hp2ps) +import GHC (genapply, genprimopcode, hp2ps) import Oracles import Predicates (registerPackage) import Rules.Actions @@ -50,16 +50,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- TODO: Track dependency on this generated file -- TODO: Use a cabal file instead of manual hacks? priority 2.0 $ - when (pkg == deriveConstants) $ path -/- "package-data.mk" %> \mk -> do - let contents = unlines - [ "utils_deriveConstants_dist-boot_MODULES = DeriveConstants" - , "utils_deriveConstants_dist-boot_PROGNAME = deriveConstants" - , "utils_deriveConstants_dist-boot_HS_SRC_DIRS = ." - , "utils_deriveConstants_dist-boot_INSTALL_INPLACE = YES" - , "utils_deriveConstants_dist-boot_HC_OPTS = -package process -package containers" ] - writeFileChanged mk contents - - priority 2.0 $ when (pkg == genapply) $ path -/- "package-data.mk" %> \mk -> do ghcUnreg <- flag GhcUnregisterised let hcOpts = "-package pretty" ++ if ghcUnreg then " -DNO_REGS" else "" From git at git.haskell.org Fri Oct 27 00:11:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Further work on #174. (1300254) Message-ID: <20171027001137.BA3433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/130025463ea2a8b50decceae44c2618198466acd/ghc >--------------------------------------------------------------- commit 130025463ea2a8b50decceae44c2618198466acd Author: Andrey Mokhov Date: Sun Jan 17 03:01:26 2016 +0000 Further work on #174. >--------------------------------------------------------------- 130025463ea2a8b50decceae44c2618198466acd src/Rules/Compile.hs | 14 ++++++++++---- src/Settings/Packages/RunGhc.hs | 2 +- 2 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 2065415..b27d36e 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,7 +12,7 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let buildPath = targetPath stage pkg -/- "build" matchBuildResult buildPath "hi" ?> \hi -> - if compileInterfaceFilesSeparately + if compileInterfaceFilesSeparately && not ("//HpcParser.*" ?== hi) then do let way = detectWay hi (src, deps) <- dependencies buildPath $ hi -<.> osuf way @@ -32,16 +32,22 @@ compilePackage _ target @ (PartialTarget stage pkg) = do -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) matchBuildResult buildPath "o" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need $ src : deps if ("//*.c" ?== src) - then build $ fullTarget target (Gcc stage) [src] [obj] + then do + need $ src : deps + build $ fullTarget target (Gcc stage) [src] [obj] else do let way = detectWay obj + if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) + then need $ (obj -<.> hisuf (detectWay obj)) : src : deps + else need $ src : deps build $ fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases matchBuildResult buildPath "o-boot" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need $ src : deps let way = detectWay obj + if compileInterfaceFilesSeparately + then need $ (obj -<.> hibootsuf (detectWay obj)) : src : deps + else need $ src : deps build $ fullTargetWithWay target (Ghc stage) way [src] [obj] diff --git a/src/Settings/Packages/RunGhc.hs b/src/Settings/Packages/RunGhc.hs index 37cdb95..e982fe6 100644 --- a/src/Settings/Packages/RunGhc.hs +++ b/src/Settings/Packages/RunGhc.hs @@ -9,5 +9,5 @@ runGhcPackageArgs :: Args runGhcPackageArgs = package runGhc ? do version <- getSetting ProjectVersion mconcat [ builderGhc ? - file "//Main.o" ? + file "//Main.*" ? append ["-cpp", "-DVERSION=\"" ++ version ++ "\""] ] From git at git.haskell.org Fri Oct 27 00:11:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move GMP paths to Settings.Paths. (a88253a) Message-ID: <20171027001139.ADC623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a88253a92b436358af15ab6ff5c99b5270ed6024/ghc >--------------------------------------------------------------- commit a88253a92b436358af15ab6ff5c99b5270ed6024 Author: Andrey Mokhov Date: Thu May 5 05:15:22 2016 +0100 Move GMP paths to Settings.Paths. >--------------------------------------------------------------- a88253a92b436358af15ab6ff5c99b5270ed6024 src/Rules/Generate.hs | 1 - src/Rules/Gmp.hs | 11 +---------- src/Rules/Library.hs | 1 - src/Settings/Paths.hs | 26 +++++++++++++++++++------- 4 files changed, 20 insertions(+), 19 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8d04e8d..78326dd 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -18,7 +18,6 @@ import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles import Rules.Actions -import Rules.Gmp import Rules.Libffi import Settings import Target hiding (builder, context) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 9cec3a3..2de1878 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,4 +1,4 @@ -module Rules.Gmp (gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH) where +module Rules.Gmp (gmpRules) where import Base import Expression @@ -16,18 +16,9 @@ gmpBase = "libraries/integer-gmp/gmp" gmpContext :: Context gmpContext = vanillaContext Stage1 integerGmp -gmpObjects :: FilePath -gmpObjects = gmpBuildPath -/- "objs" - -gmpLibrary :: FilePath -gmpLibrary = gmpBuildPath -/- "libgmp.a" - gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" -gmpLibraryH :: FilePath -gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" - gmpLibraryFakeH :: FilePath gmpLibraryFakeH = gmpBase -/- "ghc-gmp.h" diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 2b90d1f..0538e4e 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -11,7 +11,6 @@ import Expression import GHC import Oracles.PackageData import Rules.Actions -import Rules.Gmp import Settings import Target diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 01b3b16..7174a94 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,8 +1,8 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpBuildInfoPath, - packageDbDirectory, pkgConfFile, shakeFilesPath, bootPackageConstraints, - packageDependencies, libffiBuildPath + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibrary, gmpObjects, + gmpLibraryH, gmpBuildInfoPath, libffiBuildPath, shakeFilesPath, pkgConfFile, + packageDbDirectory, bootPackageConstraints, packageDependencies ) where import Base @@ -67,18 +67,30 @@ pkgFile context prefix suffix = do componentId <- pkgData $ ComponentId path return $ path ~/~ prefix ++ componentId ++ suffix --- | Build directory for in-tree libffi library. -libffiBuildPath :: FilePath -libffiBuildPath = buildRootPath -/- "stage1/libffi" - -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath gmpBuildPath = buildRootPath ~/~ "stage1/gmp" +-- | Path to the GMP library. +gmpLibrary :: FilePath +gmpLibrary = gmpBuildPath -/- "libgmp.a" + +-- | Path to the GMP library header. +gmpLibraryH :: FilePath +gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" + +-- | Path to the GMP library object files. +gmpObjects :: FilePath +gmpObjects = gmpBuildPath -/- "objs" + -- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath gmpBuildInfoPath = pkgPath integerGmp ~/~ "integer-gmp.buildinfo" +-- | Build directory for in-tree libffi library. +libffiBuildPath :: FilePath +libffiBuildPath = buildRootPath -/- "stage1/libffi" + -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory -- | Path to package database directory of a given 'Stage'. From git at git.haskell.org Fri Oct 27 00:11:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: LIB_NAME, PACKAGE_KEY are now COMPONENT_ID (4758a21) Message-ID: <20171027001140.A93F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4758a21d2a9441d5dadf9b40b578c2c8e55773e8/ghc >--------------------------------------------------------------- commit 4758a21d2a9441d5dadf9b40b578c2c8e55773e8 Author: Ben Gamari Date: Wed Dec 16 01:56:05 2015 +0100 LIB_NAME, PACKAGE_KEY are now COMPONENT_ID Since GHC commit 6338a1cc6df2c7fd8a62eeb4c5240dd90ee74a6c. >--------------------------------------------------------------- 4758a21d2a9441d5dadf9b40b578c2c8e55773e8 cfg/system.config.in | 12 ++++++------ src/Oracles/Config/Flag.hs | 4 ++-- src/Oracles/PackageData.hs | 6 ++---- src/Rules.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 16 ++++++++-------- 5 files changed, 21 insertions(+), 23 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 09ea1fa..60dae28 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -45,12 +45,12 @@ ar-supports-at-file = @ArSupportsAtFile@ # Build options: #=============== -supports-package-key = @SUPPORTS_PACKAGE_KEY@ -solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ -split-objects-broken = @SplitObjsBroken@ -ghc-unregisterised = @Unregisterised@ -ghc-source-path = @hardtop@ -leading-underscore = @LeadingUnderscore@ +supports-component-id = @SUPPORTS_COMPONENT_ID@ +solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ +split-objects-broken = @SplitObjsBroken@ +ghc-unregisterised = @Unregisterised@ +ghc-source-path = @hardtop@ +leading-underscore = @LeadingUnderscore@ # Information about build, host and target systems: #================================================== diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index f352ae3..631a6fc 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -16,7 +16,7 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken - | SupportsPackageKey + | SupportsComponentId -- Note, if a flag is set to empty string we treat it as set to NO. This seems -- fragile, but some flags do behave like this, e.g. GccIsClang. @@ -31,7 +31,7 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" - SupportsPackageKey -> "supports-package-key" + SupportsComponentId -> "supports-component-id" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." unless (value == "YES" || value == "NO" || value == "") . putError diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index e4aae0a..8a067b9 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -16,8 +16,7 @@ import qualified Data.HashMap.Strict as Map -- such as 'path_MODULES = Data.Array Data.Array.Base ...'. -- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] data PackageData = BuildGhciLib FilePath - | LibName FilePath - | PackageKey FilePath + | ComponentId FilePath | Synopsis FilePath | Version FilePath @@ -55,8 +54,7 @@ askPackageData path key = do pkgData :: PackageData -> Action String pkgData packageData = case packageData of BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" - LibName path -> askPackageData path "LIB_NAME" - PackageKey path -> askPackageData path "PACKAGE_KEY" + ComponentId path -> askPackageData path "COMPONENT_ID" Synopsis path -> askPackageData path "SYNOPSIS" Version path -> askPackageData path "VERSION" diff --git a/src/Rules.hs b/src/Rules.hs index 2a6bd59..90769c1 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -16,15 +16,15 @@ generateTargets = action $ do libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg buildPath = targetPath stage pkg -/- "build" - libName <- interpretPartial target $ getPkgData LibName + compId <- interpretPartial target $ getPkgData ComponentId needGhciLib <- interpretPartial target $ getPkgData BuildGhciLib needHaddock <- interpretPartial target buildHaddock ways <- interpretPartial target getWays - let ghciLib = buildPath -/- "HS" ++ libName <.> "o" + let ghciLib = buildPath -/- "HS" ++ compId <.> "o" haddock = pkgHaddockFile pkg libs <- fmap concat . forM ways $ \way -> do extension <- libsuf way - let name = buildPath -/- "libHS" ++ libName + let name = buildPath -/- "libHS" ++ compId dll0 <- needDll0 stage pkg return $ [ name <.> extension ] ++ [ name ++ "-0" <.> extension | dll0 ] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 247a114..50973c0 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -91,11 +91,11 @@ wayGhcArgs = do -- TODO: Improve handling of "-hide-all-packages" packageGhcArgs :: Args packageGhcArgs = do - stage <- getStage - pkg <- getPackage - supportsPackageKey <- getFlag SupportsPackageKey - pkgKey <- getPkgData PackageKey - pkgDepIds <- getPkgDataList DepIds + stage <- getStage + pkg <- getPackage + supportsComponentId <- getFlag SupportsComponentId + compId <- getPkgData ComponentId + pkgDepIds <- getPkgDataList DepIds mconcat [ not (pkg == deriveConstants || pkg == genapply || pkg == genprimopcode || pkg == hp2ps) ? @@ -103,9 +103,9 @@ packageGhcArgs = do , arg "-no-user-package-db" , stage0 ? arg "-package-db libraries/bootstrapping.conf" , isLibrary pkg ? - if supportsPackageKey || stage /= Stage0 - then arg $ "-this-package-key " ++ pkgKey - else arg $ "-package-name " ++ pkgKey + if supportsComponentId || stage /= Stage0 + then arg $ "-this-package-key " ++ compId + else arg $ "-package-name " ++ compId , append $ map ("-package-id " ++) pkgDepIds ] -- TODO: Improve handling of "cabal_macros.h" From git at git.haskell.org Fri Oct 27 00:11:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix handling of FFI library configure params (6abfdfa) Message-ID: <20171027001141.305BD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6abfdfaec035057a956ded2dad8695c4c600e24c/ghc >--------------------------------------------------------------- commit 6abfdfaec035057a956ded2dad8695c4c600e24c Author: Karel Gardas Date: Sun Jan 17 22:55:57 2016 +0100 fix handling of FFI library configure params >--------------------------------------------------------------- 6abfdfaec035057a956ded2dad8695c4c600e24c cfg/system.config.in | 3 ++ src/Oracles/Config/Setting.hs | 6 +++ src/Rules/Libffi.hs | 87 ++++++++++++++++++++++++------------------- src/Settings/Packages/Rts.hs | 8 +++- 4 files changed, 65 insertions(+), 39 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index dfde8e3..ecbf18d 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -127,6 +127,9 @@ iconv-lib-dirs = @ICONV_LIB_DIRS@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ +use-system-ffi = @UseSystemLibFFI@ +ffi-include-dirs = @FFIIncludeDir@ +ffi-lib-dirs = @FFILibDir@ # Optional Dependencies: #======================= diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 46d0d33..7b5d71e 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -47,6 +47,7 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor + | UseSystemFfi data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -57,6 +58,8 @@ data SettingList = ConfCcArgs Stage | HsCppArgs | IconvIncludeDirs | IconvLibDirs + | FfiIncludeDirs + | FfiLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of @@ -88,6 +91,7 @@ setting key = askConfig $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" + UseSystemFfi -> "use-system-ffi" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -100,6 +104,8 @@ settingList key = fmap words $ askConfig $ case key of HsCppArgs -> "hs-cpp-args" IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" + FfiIncludeDirs -> "ffi-include-dirs" + FfiLibDirs -> "ffi-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index dbf50dc..5f23cad 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,44 +70,55 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - removeDirectory libffiBuild - createDirectory $ buildRootPath -/- stageString Stage0 - - tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - when (length tarballs /= 1) $ - putError $ "libffiRules: exactly one libffi tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - - need tarballs - let libname = dropExtension . dropExtension . takeFileName $ head tarballs - - removeDirectory (buildRootPath -/- libname) - actionFinally (do - build $ fullTarget libffiTarget Tar tarballs [buildRootPath] - moveDirectory (buildRootPath -/- libname) libffiBuild) $ - removeFiles buildRootPath [libname "*"] - - fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile - - forM_ ["config.guess", "config.sub"] $ \file -> - copyFile file (libffiBuild -/- file) - - envs <- configureEnvironment - args <- configureArguments - runConfigure libffiBuild envs args - - runMake libffiBuild ["MAKEFLAGS="] - runMake libffiBuild ["MAKEFLAGS=", "install"] - - forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file - copyFile src (rtsBuildPath -/- file) - - libffiName <- rtsLibffiLibraryName - copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") - - putSuccess $ "| Successfully built custom library 'libffi'" + use_system_ffi <- setting UseSystemFfi + ffi_header_dirs <- settingList FfiIncludeDirs + if use_system_ffi == "YES" + then do + putBuild "| System supplied FFI library will be used" + let ffi_header_dir = head ffi_header_dirs + forM_ ["ffi.h", "ffitarget.h"] $ \file -> do + let src = ffi_header_dir -/- file + copyFile src (rtsBuildPath -/- file) + putSuccess $ "| Successfully copied system supplied FFI library header files" + else do + when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] + removeDirectory libffiBuild + createDirectory $ buildRootPath -/- stageString Stage0 + + tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] + when (length tarballs /= 1) $ + putError $ "libffiRules: exactly one libffi tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + + need tarballs + let libname = dropExtension . dropExtension . takeFileName $ head tarballs + + removeDirectory (buildRootPath -/- libname) + actionFinally (do + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] + + fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile + + forM_ ["config.guess", "config.sub"] $ \file -> + copyFile file (libffiBuild -/- file) + + envs <- configureEnvironment + args <- configureArguments + runConfigure libffiBuild envs args + + runMake libffiBuild ["MAKEFLAGS="] + runMake libffiBuild ["MAKEFLAGS=", "install"] + + forM_ ["ffi.h", "ffitarget.h"] $ \file -> do + let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file + copyFile src (rtsBuildPath -/- file) + + libffiName <- rtsLibffiLibraryName + copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") + + putSuccess $ "| Successfully built custom library 'libffi'" -- chmod +x libffi/ln -- # wc on OS X has spaces in its output, which libffi's Makefile diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index f1d67d9..26fce73 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,8 +20,14 @@ rtsConf = pkgPath rts -/- targetDirectory Stage1 rts -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do + use_system_ffi <- setting UseSystemFfi windows <- windowsHost - return $ if windows then "Cffi-6" else "Cffi" + case (use_system_ffi, windows) of + ("YES", False) -> return "ffi" + ("NO", False) -> return "Cffi" + (_, True) -> return "Cffi-6" + (_, _) -> error "Unsupported FFI library configuration case" + rtsPackageArgs :: Args rtsPackageArgs = package rts ? do From git at git.haskell.org Fri Oct 27 00:11:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Gmp and Libffi rules. (f0781a7) Message-ID: <20171027001143.30E023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f0781a7c0c1124d7e0150298ca39b08a849ac338/ghc >--------------------------------------------------------------- commit f0781a7c0c1124d7e0150298ca39b08a849ac338 Author: Andrey Mokhov Date: Thu May 5 05:30:22 2016 +0100 Refactor Gmp and Libffi rules. >--------------------------------------------------------------- f0781a7c0c1124d7e0150298ca39b08a849ac338 src/Builder.hs | 9 ++++++++- src/Rules/Gmp.hs | 22 +++++++--------------- src/Rules/Libffi.hs | 18 +++++++----------- 3 files changed, 22 insertions(+), 27 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index fa76097..a205067 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric, LambdaCase #-} module Builder ( CompilerMode (..), Builder (..), - builderPath, getBuilderPath, specified, needBuilder + builderPath, getBuilderPath, builderEnvironment, specified, needBuilder ) where import Control.Monad.Trans.Reader @@ -134,6 +134,13 @@ builderPath builder = case builderProvenance builder of getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath +-- | Write a Builder's path into a given environment variable. +builderEnvironment :: String -> Builder -> Action CmdOption +builderEnvironment variable builder = do + needBuilder builder + path <- builderPath builder + return $ AddEnv variable path + specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 2de1878..1121d5d 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,6 +1,7 @@ module Rules.Gmp (gmpRules) where import Base +import Builder import Expression import GHC import Oracles.Config.Setting @@ -11,31 +12,22 @@ import Settings.Paths import Target gmpBase :: FilePath -gmpBase = "libraries/integer-gmp/gmp" +gmpBase = pkgPath integerGmp -/- "gmp" gmpContext :: Context gmpContext = vanillaContext Stage1 integerGmp +-- TODO: Noone needs this file, but we build it. Why? gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" -gmpLibraryFakeH :: FilePath -gmpLibraryFakeH = gmpBase -/- "ghc-gmp.h" - gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] --- TODO: See Libffi.hs about removing code duplication. configureEnvironment :: Action [CmdOption] -configureEnvironment = do - sequence [ builderEnv "CC" $ Cc Compile Stage1 - , builderEnv "AR" Ar - , builderEnv "NM" Nm ] - where - builderEnv var bld = do - needBuilder bld - path <- builderPath bld - return $ AddEnv var path +configureEnvironment = sequence [ builderEnvironment "CC" $ Cc Compile Stage1 + , builderEnvironment "AR" Ar + , builderEnvironment "NM" Nm ] -- TODO: we rebuild gmp every time. gmpRules :: Rules () @@ -53,7 +45,7 @@ gmpRules = do then do putBuild "| GMP library/framework detected and will be used" createDirectory $ takeDirectory gmpLibraryH - copyFile gmpLibraryFakeH gmpLibraryH + copyFile (gmpBase -/- "ghc-gmp.h") gmpLibraryH else do putBuild "| No GMP library/framework detected; in tree GMP will be built" diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 424b552..0a000aa 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,6 +1,7 @@ module Rules.Libffi (rtsBuildPath, libffiRules, libffiDependencies) where import Base +import Builder import Expression import GHC import Oracles.Config.Flag @@ -43,19 +44,14 @@ configureEnvironment = do [ cArgs , argStagedSettingList ConfCcArgs ] ldFlags <- interpretInContext libffiContext $ fromDiffExpr ldArgs - sequence [ builderEnv "CC" $ Cc Compile Stage1 - , builderEnv "CXX" $ Cc Compile Stage1 - , builderEnv "LD" Ld - , builderEnv "AR" Ar - , builderEnv "NM" Nm - , builderEnv "RANLIB" Ranlib + sequence [ builderEnvironment "CC" $ Cc Compile Stage1 + , builderEnvironment "CXX" $ Cc Compile Stage1 + , builderEnvironment "LD" Ld + , builderEnvironment "AR" Ar + , builderEnvironment "NM" Nm + , builderEnvironment "RANLIB" Ranlib , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w" , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ] - where - builderEnv var b = do - needBuilder b - path <- builderPath b - return $ AddEnv var path -- TODO: remove code duplication (need sourcePath) -- TODO: split into multiple rules From git at git.haskell.org Fri Oct 27 00:11:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add configuration for libdw (96d66f0) Message-ID: <20171027001144.773083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/96d66f0c27df839072ee01555fa98529e3be6ef9/ghc >--------------------------------------------------------------- commit 96d66f0c27df839072ee01555fa98529e3be6ef9 Author: Ben Gamari Date: Wed Dec 16 02:42:11 2015 +0100 Add configuration for libdw >--------------------------------------------------------------- 96d66f0c27df839072ee01555fa98529e3be6ef9 cfg/system.config.in | 6 ++++++ src/Oracles/Config/Flag.hs | 2 ++ src/Rules/Generate.hs | 5 ++++- 3 files changed, 12 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 60dae28..9de3166 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -116,3 +116,9 @@ iconv-lib-dirs = @ICONV_LIB_DIRS@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ + + +# Optional Dependencies: +#======================= + +with-libdw = @HaveLibdw@ diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 631a6fc..47ea75d 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -17,6 +17,7 @@ data Flag = ArSupportsAtFile | SolarisBrokenShld | SplitObjectsBroken | SupportsComponentId + | WithLibdw -- Note, if a flag is set to empty string we treat it as set to NO. This seems -- fragile, but some flags do behave like this, e.g. GccIsClang. @@ -32,6 +33,7 @@ flag f = do SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" SupportsComponentId -> "supports-component-id" + WithLibdw -> "with-libdw" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." unless (value == "YES" || value == "NO" || value == "") . putError diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 069d88f..53b7dd6 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -106,6 +106,7 @@ generateConfigHs = do cGHC_SPLIT_PGM <- fmap takeBaseName $ getBuilderPath GhcSplit cLibFFI <- lift useLibFFIForAdjustors rtsWays <- getRtsWays + cGhcRtsWithLibdw <- getFlag WithLibdw let cGhcRTSWays = unwords $ map show rtsWays return $ unlines [ "{-# LANGUAGE CPP #-}" @@ -169,7 +170,9 @@ generateConfigHs = do , "cGhcThreaded :: Bool" , "cGhcThreaded = " ++ show (threaded `elem` rtsWays) , "cGhcDebugged :: Bool" - , "cGhcDebugged = " ++ show ghcDebugged ] + , "cGhcDebugged = " ++ show ghcDebugged + , "cGhcRtsWithLibdw :: Bool" + , "cGhcRtsWithLibdw = " ++ show cGhcRtsWithLibdw ] generatePlatformH :: Expr String generatePlatformH = do From git at git.haskell.org Fri Oct 27 00:11:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: use flag instead of setting for use system ffi value (afc4d05) Message-ID: <20171027001144.F323F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/afc4d05a9f33555887df3217adb6c70ebe806d2f/ghc >--------------------------------------------------------------- commit afc4d05a9f33555887df3217adb6c70ebe806d2f Author: Karel Gardas Date: Sun Jan 17 23:52:48 2016 +0100 use flag instead of setting for use system ffi value >--------------------------------------------------------------- afc4d05a9f33555887df3217adb6c70ebe806d2f src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 2 -- src/Rules/Libffi.hs | 4 ++-- src/Settings/Packages/Rts.hs | 6 +++--- 4 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 44e8a17..9d33445 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -19,6 +19,7 @@ data Flag = ArSupportsAtFile | SolarisBrokenShld | SplitObjectsBroken | WithLibdw + | UseSystemFfi -- Note, if a flag is set to empty string we treat it as set to NO. This seems -- fragile, but some flags do behave like this, e.g. GccIsClang. @@ -34,6 +35,7 @@ flag f = do SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" WithLibdw -> "with-libdw" + UseSystemFfi -> "use-system-ffi" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." unless (value == "YES" || value == "NO" || value == "") . putError diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 7b5d71e..56ef1ca 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -47,7 +47,6 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor - | UseSystemFfi data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -91,7 +90,6 @@ setting key = askConfig $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" - UseSystemFfi -> "use-system-ffi" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 5f23cad..fea58ab 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,9 +70,9 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - use_system_ffi <- setting UseSystemFfi ffi_header_dirs <- settingList FfiIncludeDirs - if use_system_ffi == "YES" + use_system_ffi <- flag UseSystemFfi + if use_system_ffi then do putBuild "| System supplied FFI library will be used" let ffi_header_dir = head ffi_header_dirs diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 26fce73..e684b7a 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,11 +20,11 @@ rtsConf = pkgPath rts -/- targetDirectory Stage1 rts -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do - use_system_ffi <- setting UseSystemFfi + use_system_ffi <- flag UseSystemFfi windows <- windowsHost case (use_system_ffi, windows) of - ("YES", False) -> return "ffi" - ("NO", False) -> return "Cffi" + (True, False) -> return "ffi" + (False, False) -> return "Cffi" (_, True) -> return "Cffi-6" (_, _) -> error "Unsupported FFI library configuration case" From git at git.haskell.org Fri Oct 27 00:11:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (acf2160) Message-ID: <20171027001146.C85123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acf2160ea8c2ac705e32e4774c02ea7d806261f6/ghc >--------------------------------------------------------------- commit acf2160ea8c2ac705e32e4774c02ea7d806261f6 Author: Andrey Mokhov Date: Thu May 5 05:42:48 2016 +0100 Add comments. See #55. [skip ci] >--------------------------------------------------------------- acf2160ea8c2ac705e32e4774c02ea7d806261f6 src/Rules/Actions.hs | 15 +++++++++------ 1 file changed, 9 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index a312ce9..9a9e51e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -44,7 +44,7 @@ customBuild rs opts target at Target {..} = do argList <- interpret target getArgs verbose <- interpret target verboseCommands let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly - -- The line below forces the rule to be rerun if the args hash has changed + -- The line below forces the rule to be rerun if the args hash has changed. checkArgsHash target withResources rs $ do putInfo target @@ -76,19 +76,21 @@ customBuild rs opts target at Target {..} = do _ -> cmd [path] argList +-- | Run a builder, capture the standard output, and write it to a given file. captureStdout :: Target -> FilePath -> [String] -> Action () captureStdout target path argList = do file <- interpret target getOutput Stdout output <- cmd [path] argList writeFileChanged file output +-- | Copy a file tracking the source. copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target --- Note, moveFile cannot track the source, because it is moved. +-- | Move a file; we cannot track the source, because it is moved. moveFile :: FilePath -> FilePath -> Action () moveFile source target = do putProgressInfo $ renderAction "Move file" source target @@ -100,6 +102,7 @@ removeFile file = do putBuild $ "| Remove file " ++ file liftIO . whenM (IO.doesFileExist file) $ IO.removeFile file +-- | Create a directory if it does not already exist. createDirectory :: FilePath -> Action () createDirectory dir = do putBuild $ "| Create directory " ++ dir @@ -111,19 +114,19 @@ removeDirectory dir = do putBuild $ "| Remove directory " ++ dir liftIO . whenM (IO.doesDirectoryExist dir) $ IO.removeDirectoryRecursive dir --- Note, the source directory is untracked +-- | Copy a directory. The contents of the source directory is untracked. copyDirectory :: FilePath -> FilePath -> Action () copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd (EchoStdout False) ["cp", "-r", source, target] --- Note, the source directory is untracked +-- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target liftIO $ IO.renameDirectory source target --- Transform a given file by applying a function to its contents +-- | Transform a given file by applying a function to its contents. fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do putBuild $ "| Fix " ++ file @@ -171,7 +174,7 @@ makeExecutable file = do putBuild $ "| Make '" ++ file ++ "' executable." quietly $ cmd "chmod +x " [file] --- Print out key information about the command being executed +-- | Print out information about the command being executed. putInfo :: Target -> Action () putInfo Target {..} = putProgressInfo $ renderAction ("Run " ++ show builder ++ contextInfo) (digest inputs) (digest outputs) From git at git.haskell.org Fri Oct 27 00:11:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GHC: bin-package-db is now ghc-boot (73b4605) Message-ID: <20171027001147.F012D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73b460528b96ce7c6c056d25dee9c7e50924f59c/ghc >--------------------------------------------------------------- commit 73b460528b96ce7c6c056d25dee9c7e50924f59c Author: Ben Gamari Date: Wed Dec 16 01:32:59 2015 +0100 GHC: bin-package-db is now ghc-boot >--------------------------------------------------------------- 73b460528b96ce7c6c056d25dee9c7e50924f59c src/GHC.hs | 8 ++++---- src/Settings/Packages.hs | 2 +- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index ea48014..30414db 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,5 +1,5 @@ module GHC ( - array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, + array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, @@ -20,7 +20,7 @@ import Stage -- which can be overridden in Settings/User.hs. defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, binPackageDb, binary, bytestring, cabal, compiler + [ array, base, ghcBoot, binary, bytestring, cabal, compiler , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit , filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin @@ -29,7 +29,7 @@ defaultKnownPackages = , win32, xhtml ] -- Package definitions (see Package.hs) -array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, +array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, @@ -38,7 +38,7 @@ array, base, binPackageDb, binary, bytestring, cabal, compiler, containers, array = library "array" base = library "base" -binPackageDb = library "bin-package-db" +ghcBoot = library "ghc-boot" binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 80fc202..febb254 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -18,7 +18,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binPackageDb, binary, cabal, compiler, ghc, ghcCabal, ghcPkg + [ append [ ghcBoot, binary, cabal, compiler, ghc, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] , stage0 ? append [deriveConstants, genapply, genprimopcode, hp2ps] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] From git at git.haskell.org Fri Oct 27 00:11:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build unlit. (51c24a8) Message-ID: <20171027001148.8CC713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/51c24a8f1320013d75ac9b06df60f3834b5bc0be/ghc >--------------------------------------------------------------- commit 51c24a8f1320013d75ac9b06df60f3834b5bc0be Author: Andrey Mokhov Date: Sun Jan 17 23:33:28 2016 +0000 Build unlit. See #181. [skip ci] >--------------------------------------------------------------- 51c24a8f1320013d75ac9b06df60f3834b5bc0be src/Settings/Packages.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index b7e2dac..691cd78 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -24,7 +24,8 @@ packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] + , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode + , hp2ps, unlit ] , stage0 ? windowsHost ? append [touchy] , notM windowsHost ? notM iosHost ? append [terminfo] ] From git at git.haskell.org Fri Oct 27 00:11:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make only install target in libffi. (2249b40) Message-ID: <20171027001150.3C3923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2249b4037ad429640404e79056efa4043888c9e3/ghc >--------------------------------------------------------------- commit 2249b4037ad429640404e79056efa4043888c9e3 Author: Andrey Mokhov Date: Thu May 5 05:57:20 2016 +0100 Make only install target in libffi. >--------------------------------------------------------------- 2249b4037ad429640404e79056efa4043888c9e3 src/Rules/Libffi.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0a000aa..8ca0bfc9 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -97,7 +97,7 @@ libffiRules = do Target libffiContext (Configure libffiBuildPath) [libffiMakefile <.> "in"] [libffiMakefile] - runMake libffiBuildPath ["MAKEFLAGS="] + --runMake libffiBuildPath ["MAKEFLAGS="] runMake libffiBuildPath ["MAKEFLAGS=", "install"] let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" From git at git.haskell.org Fri Oct 27 00:11:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Dependencies: Use msum instead of explicit pattern matching (1c8539d) Message-ID: <20171027001152.148C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c8539dfd3761a3a69d9514d58e3e196127661a3/ghc >--------------------------------------------------------------- commit 1c8539dfd3761a3a69d9514d58e3e196127661a3 Author: Ben Gamari Date: Wed Dec 16 16:35:24 2015 +0100 Dependencies: Use msum instead of explicit pattern matching >--------------------------------------------------------------- 1c8539dfd3761a3a69d9514d58e3e196127661a3 src/Oracles/Dependencies.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index d0f926d..c27c2cc 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -2,6 +2,7 @@ module Oracles.Dependencies (dependencies, dependenciesOracle) where import Base +import Control.Monad.Trans.Maybe import qualified Data.HashMap.Strict as Map newtype DependenciesKey = DependenciesKey (FilePath, FilePath) @@ -16,12 +17,11 @@ newtype DependenciesKey = DependenciesKey (FilePath, FilePath) dependencies :: FilePath -> FilePath -> Action (FilePath, [FilePath]) dependencies path obj = do let depFile = path -/- ".dependencies" - res1 <- askOracle $ DependenciesKey (depFile, obj) - -- if no dependencies found attempt to drop the way prefix (for *.c sources) - res2 <- case res1 of - Nothing -> askOracle $ DependenciesKey (depFile, obj -<.> "o") - _ -> return res1 - case res2 of + -- if no dependencies found then attempt to drop the way prefix (for *.c sources) + res <- runMaybeT $ msum + $ map (\obj' -> MaybeT $ askOracle $ DependenciesKey (depFile, obj')) + [obj, obj -<.> "o"] + case res of Nothing -> putError $ "No dependencies found for '" ++ obj ++ "'." Just [] -> putError $ "Empty dependency list for '" ++ obj ++ "'." Just (src:depFiles) -> return (src, depFiles) From git at git.haskell.org Fri Oct 27 00:11:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy ghc-usage.txt and ghci-usage.txt. (b5d0778) Message-ID: <20171027001152.7973F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b5d0778726fd75fd7547b89864ee8e2859ce0ccf/ghc >--------------------------------------------------------------- commit b5d0778726fd75fd7547b89864ee8e2859ce0ccf Author: Andrey Mokhov Date: Sun Jan 17 23:37:01 2016 +0000 Copy ghc-usage.txt and ghci-usage.txt. Fix #181. >--------------------------------------------------------------- b5d0778726fd75fd7547b89864ee8e2859ce0ccf src/Rules/Generate.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 025f1ee..c5386e4 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -23,7 +23,9 @@ import Settings installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" , "inplace/lib/platformConstants" - , "inplace/lib/settings" ] + , "inplace/lib/settings" + , "inplace/lib/ghc-usage.txt" + , "inplace/lib/ghci-usage.txt" ] primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -167,6 +169,8 @@ copyRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." + "inplace/lib/ghc-usage.txt" <~ "driver" + "inplace/lib/ghci-usage.txt" <~ "driver" where file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file From git at git.haskell.org Fri Oct 27 00:11:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (6828f4a) Message-ID: <20171027001153.9F2733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6828f4af2d959e352415f7c6c89dd408e8409dcf/ghc >--------------------------------------------------------------- commit 6828f4af2d959e352415f7c6c89dd408e8409dcf Author: Andrey Mokhov Date: Thu May 5 13:07:07 2016 +0100 Add comments. >--------------------------------------------------------------- 6828f4af2d959e352415f7c6c89dd408e8409dcf src/Rules/Libffi.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 8ca0bfc9..20d5acf 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -97,7 +97,8 @@ libffiRules = do Target libffiContext (Configure libffiBuildPath) [libffiMakefile <.> "in"] [libffiMakefile] - --runMake libffiBuildPath ["MAKEFLAGS="] + -- The old build system did runMake libffiBuildPath ["MAKEFLAGS="] + -- TODO: Find out why. It seems redundant, so I removed it. runMake libffiBuildPath ["MAKEFLAGS=", "install"] let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" From git at git.haskell.org Fri Oct 27 00:11:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: genprimopcode also has a Cabal file (5ff0907) Message-ID: <20171027001155.7CD383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ff090768598e587c5ab617e25844911944e79ad/ghc >--------------------------------------------------------------- commit 5ff090768598e587c5ab617e25844911944e79ad Author: Ben Gamari Date: Wed Dec 16 03:17:23 2015 +0100 genprimopcode also has a Cabal file As of GHC commit 314395e00be10e6343840c215a4779aeec2542df. >--------------------------------------------------------------- 5ff090768598e587c5ab617e25844911944e79ad src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 363d804..95ac426 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (genprimopcode, hp2ps) +import GHC (hp2ps) import Oracles import Predicates (registerPackage) import Rules.Actions From git at git.haskell.org Fri Oct 27 00:11:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Actions: use `mv` instead of renameDirectory (fixes #236) (d04a83f) Message-ID: <20171027001157.3579E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d04a83ffa5a94de6215997229c6e4dc0afe21640/ghc >--------------------------------------------------------------- commit d04a83ffa5a94de6215997229c6e4dc0afe21640 Author: Michal Terepeta Date: Thu May 5 17:05:24 2016 +0200 Actions: use `mv` instead of renameDirectory (fixes #236) Implementing `moveDirectory` by calling into `renameDirectory` is problematic because it doesn't work across file-systems (e.g., a tmpfs based `/tmp`). This fixes the problem by calling into `mv` instead (similarly to what we do for `copyDirectory`). >--------------------------------------------------------------- d04a83ffa5a94de6215997229c6e4dc0afe21640 src/Rules/Actions.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9a9e51e..fd117ae 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -124,7 +124,7 @@ copyDirectory source target = do moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target - liftIO $ IO.renameDirectory source target + quietly $ cmd (EchoStdout False) ["mv", source, target] -- | Transform a given file by applying a function to its contents. fixFile :: FilePath -> (String -> String) -> Action () From git at git.haskell.org Fri Oct 27 00:11:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Builder.hs. (40b7920) Message-ID: <20171027001155.D7D2C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/40b792062cfe1289460323228a0b6c7487300980/ghc >--------------------------------------------------------------- commit 40b792062cfe1289460323228a0b6c7487300980 Author: Andrey Mokhov Date: Mon Jan 18 01:31:06 2016 +0000 Refactor Builder.hs. Fix #124. >--------------------------------------------------------------- 40b792062cfe1289460323228a0b6c7487300980 cfg/system.config.in | 74 ++++++++++------------------ src/Builder.hs | 126 ++++++++++++++++++++++++++---------------------- src/GHC.hs | 35 +++++++++++++- src/Settings.hs | 5 +- src/Settings/Default.hs | 34 +------------ src/Settings/Paths.hs | 5 +- src/Settings/User.hs | 14 +----- 7 files changed, 134 insertions(+), 159 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 40b792062cfe1289460323228a0b6c7487300980 From git at git.haskell.org Fri Oct 27 00:11:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: genapply now has a Cabal build (c525470) Message-ID: <20171027001159.53DF93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5254701040d51590fd9f26cbff566be49ee3d58/ghc >--------------------------------------------------------------- commit c5254701040d51590fd9f26cbff566be49ee3d58 Author: Ben Gamari Date: Wed Dec 16 03:13:51 2015 +0100 genapply now has a Cabal build >--------------------------------------------------------------- c5254701040d51590fd9f26cbff566be49ee3d58 src/Rules/Compile.hs | 5 ----- src/Rules/Data.hs | 26 +------------------------- 2 files changed, 1 insertion(+), 30 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 9f718eb..6b81a47 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -28,11 +28,6 @@ compilePackage _ target @ (PartialTarget stage pkg) = do build $ fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases - priority 2.0 $ buildPath -/- "GenApply.o" %> \obj -> do - let src = pkgPath pkg -/- "GenApply.hs" - need [src] - build $ fullTargetWithWay target (Ghc stage) vanilla [src] [obj] - matchBuildResult buildPath "o-boot" ?> \obj -> do (src, deps) <- dependencies buildPath obj need $ src : deps diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 2898257..363d804 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,7 @@ module Rules.Data (buildPackageData) where import Expression -import GHC (genapply, genprimopcode, hp2ps) +import GHC (genprimopcode, hp2ps) import Oracles import Predicates (registerPackage) import Rules.Actions @@ -47,30 +47,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do postProcessPackageData $ path -/- "package-data.mk" - -- TODO: Track dependency on this generated file - -- TODO: Use a cabal file instead of manual hacks? - priority 2.0 $ - when (pkg == genapply) $ path -/- "package-data.mk" %> \mk -> do - ghcUnreg <- flag GhcUnregisterised - let hcOpts = "-package pretty" ++ if ghcUnreg then " -DNO_REGS" else "" - contents = unlines - [ "utils_genapply_dist-boot_MODULES = GenApply" - , "utils_genapply_dist-boot_PROGNAME = genapply" - , "utils_genapply_dist-boot_HS_SRC_DIRS = ." - , "utils_genapply_dist-boot_INSTALL_INPLACE = YES" - , "utils_genapply_dist-boot_HC_OPTS = " ++ hcOpts ] - writeFileChanged mk contents - - priority 2.0 $ - when (pkg == genprimopcode) $ path -/- "package-data.mk" %> \mk -> do - let contents = unlines - [ "utils_genprimopcode_dist-boot_MODULES = Lexer Main ParserM Parser Syntax" - , "utils_genprimopcode_dist-boot_PROGNAME = genprimopcode" - , "utils_genprimopcode_dist-boot_HS_SRC_DIRS = ." - , "utils_genprimopcode_dist-boot_INSTALL_INPLACE = YES" - , "utils_genprimopcode_dist-boot_HC_OPTS = -package array" ] - writeFileChanged mk contents - -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps -- TODO: code duplication around ghcIncludeDirs -- TODO: now using DEP_EXTRA_LIBS instead of EXTRA_LIBRARIES From git at git.haskell.org Fri Oct 27 00:11:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:11:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: change from using "dirs" to "dir" for FFI library configuration (a3afd03) Message-ID: <20171027001159.B509D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a3afd03cf3b46e3344c3274606a3d42b1b08a254/ghc >--------------------------------------------------------------- commit a3afd03cf3b46e3344c3274606a3d42b1b08a254 Author: Karel Gardas Date: Mon Jan 18 10:24:42 2016 +0100 change from using "dirs" to "dir" for FFI library configuration >--------------------------------------------------------------- a3afd03cf3b46e3344c3274606a3d42b1b08a254 cfg/system.config.in | 4 ++-- src/Oracles/Config/Setting.hs | 8 ++++---- src/Rules/Libffi.hs | 3 +-- 3 files changed, 7 insertions(+), 8 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index ecbf18d..94058df 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -128,8 +128,8 @@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ use-system-ffi = @UseSystemLibFFI@ -ffi-include-dirs = @FFIIncludeDir@ -ffi-lib-dirs = @FFILibDir@ +ffi-include-dir = @FFIIncludeDir@ +ffi-lib-dir = @FFILibDir@ # Optional Dependencies: #======================= diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 56ef1ca..f4540cc 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -47,6 +47,8 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor + | FfiIncludeDir + | FfiLibDir data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -57,8 +59,6 @@ data SettingList = ConfCcArgs Stage | HsCppArgs | IconvIncludeDirs | IconvLibDirs - | FfiIncludeDirs - | FfiLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of @@ -90,6 +90,8 @@ setting key = askConfig $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" + FfiIncludeDir -> "ffi-include-dir" + FfiLibDir -> "ffi-lib-dir" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -102,8 +104,6 @@ settingList key = fmap words $ askConfig $ case key of HsCppArgs -> "hs-cpp-args" IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" - FfiIncludeDirs -> "ffi-include-dirs" - FfiLibDirs -> "ffi-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index fea58ab..518389e 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,12 +70,11 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - ffi_header_dirs <- settingList FfiIncludeDirs + ffi_header_dir <- setting FfiIncludeDir use_system_ffi <- flag UseSystemFfi if use_system_ffi then do putBuild "| System supplied FFI library will be used" - let ffi_header_dir = head ffi_header_dirs forM_ ["ffi.h", "ffitarget.h"] $ \file -> do let src = ffi_header_dir -/- file copyFile src (rtsBuildPath -/- file) From git at git.haskell.org Fri Oct 27 00:12:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #237 from michalt/movedirectory-fix/1 (e61bd40) Message-ID: <20171027001200.BCBDC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e61bd4021b696a17c72c8d259adf55621f9c3959/ghc >--------------------------------------------------------------- commit e61bd4021b696a17c72c8d259adf55621f9c3959 Merge: 6828f4a d04a83f Author: Andrey Mokhov Date: Thu May 5 17:59:09 2016 +0100 Merge pull request #237 from michalt/movedirectory-fix/1 Actions: use `mv` instead of renameDirectory (fixes #236) >--------------------------------------------------------------- e61bd4021b696a17c72c8d259adf55621f9c3959 src/Rules/Actions.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:12:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add remote GHCi libraries (0afdf64) Message-ID: <20171027001203.1D9793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0afdf642a4a9209c578ddd8dd84cd2886bcd6e77/ghc >--------------------------------------------------------------- commit 0afdf642a4a9209c578ddd8dd84cd2886bcd6e77 Author: Ben Gamari Date: Fri Dec 18 12:27:16 2015 +0100 Add remote GHCi libraries See GHC commit 4905b83a2d448c65ccced385343d4e8124548a3b. >--------------------------------------------------------------- 0afdf642a4a9209c578ddd8dd84cd2886bcd6e77 src/GHC.hs | 14 ++++++++------ src/Settings/Packages.hs | 3 ++- 2 files changed, 10 insertions(+), 7 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 30414db..06140b1 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,9 +1,9 @@ module GHC ( array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, ghcTags, + genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, + integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath @@ -22,11 +22,11 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, ghcBoot, binary, bytestring, cabal, compiler , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim + , filepath, genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin - , integerGmp, integerSimple, mkUserGuidePart, parallel, pretty, primitive - , process, runghc, stm, templateHaskell, terminfo, time, transformers, unix - , win32, xhtml ] + , integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty + , primitive , process, runghc, stm, templateHaskell, terminfo, time + , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, @@ -54,6 +54,7 @@ genapply = utility "genapply" genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" ghcCabal = utility "ghc-cabal" +ghci = library "ghci" `setPath` "libraries/ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" ghcPwd = utility "ghc-pwd" @@ -67,6 +68,7 @@ hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" integerGmp = library "integer-gmp" integerSimple = library "integer-simple" +iservBin = topLevel "iserv-bin" `setPath` "iserv" mkUserGuidePart = utility "mkUserGuidePart" parallel = library "parallel" pretty = library "pretty" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index febb254..718b8de 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -29,10 +29,11 @@ packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq , directory, dllSplit, filepath - , ghcPrim, ghcPwd, haskeline, hpcBin, integerLibrary + , ghci, ghcPrim, ghcPwd, haskeline, hpcBin, integerLibrary , mkUserGuidePart, pretty, process, runghc, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] + , notM windowsHost ? append [iservBin] , buildHaddock ? append [xhtml] ] packagesStage2 :: Packages From git at git.haskell.org Fri Oct 27 00:12:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' into fix_ffi_args (680766b) Message-ID: <20171027001203.A8E2C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/680766bbf029a391d4c4334648aa4739274cb25f/ghc >--------------------------------------------------------------- commit 680766bbf029a391d4c4334648aa4739274cb25f Merge: a3afd03 40b7920 Author: Karel Gardas Date: Mon Jan 18 12:49:15 2016 +0100 Merge branch 'master' into fix_ffi_args Conflicts: cfg/system.config.in >--------------------------------------------------------------- 680766bbf029a391d4c4334648aa4739274cb25f cfg/system.config.in | 73 ++++++++++----------------- src/Builder.hs | 126 ++++++++++++++++++++++++++--------------------- src/GHC.hs | 35 ++++++++++++- src/Rules/Generate.hs | 6 ++- src/Settings.hs | 5 +- src/Settings/Default.hs | 34 +------------ src/Settings/Packages.hs | 3 +- src/Settings/Paths.hs | 5 +- src/Settings/User.hs | 14 +----- 9 files changed, 141 insertions(+), 160 deletions(-) From git at git.haskell.org Fri Oct 27 00:12:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot and configure via Hadrian (13f3e0c) Message-ID: <20171027001204.8E55F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13f3e0c5cb075eb22785886be439f8235009b766/ghc >--------------------------------------------------------------- commit 13f3e0c5cb075eb22785886be439f8235009b766 Author: Andrey Mokhov Date: Thu May 5 20:20:38 2016 +0100 Run boot and configure via Hadrian [skip ci] >--------------------------------------------------------------- 13f3e0c5cb075eb22785886be439f8235009b766 doc/windows.md | 3 --- 1 file changed, 3 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 7afd97c..79dfcc2 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -11,8 +11,6 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ cd ghc stack exec -- git clone git://github.com/snowleopard/hadrian stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec -- perl boot - stack exec -- bash configure --enable-tarballs-autodownload stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j The entire process should take about an hour. @@ -21,6 +19,5 @@ The entire process should take about an hour. Here are some alternatives that have been considered, but not yet tested. Use the instructions above. -* Use `hadrian/build.bat --setup` to replace `boot` and `configure`. * The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. * Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:12:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: The new build system will live in `shake-build`. (bd2a394) Message-ID: <20171027001206.CBAA43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd2a394ec33a93d17d74db243dc8182d2f13de31/ghc >--------------------------------------------------------------- commit bd2a394ec33a93d17d74db243dc8182d2f13de31 Author: Andrey Mokhov Date: Fri Dec 18 21:18:10 2015 +0000 The new build system will live in `shake-build`. >--------------------------------------------------------------- bd2a394ec33a93d17d74db243dc8182d2f13de31 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index faf3155..05f3352 100644 --- a/README.md +++ b/README.md @@ -3,4 +3,4 @@ Shaking up GHC As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). -This is supposed to go into the `build` directory of the GHC source tree. +This is supposed to go into the `shake-build` directory of the GHC source tree. From git at git.haskell.org Fri Oct 27 00:12:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: pass ffi include/library directories to HsCpp (39f0e7a) Message-ID: <20171027001207.CD7EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39f0e7a2fe46ea6e6fc1cc86685fd8729a4cf4c7/ghc >--------------------------------------------------------------- commit 39f0e7a2fe46ea6e6fc1cc86685fd8729a4cf4c7 Author: Karel Gardas Date: Mon Jan 18 20:06:55 2016 +0100 pass ffi include/library directories to HsCpp >--------------------------------------------------------------- 39f0e7a2fe46ea6e6fc1cc86685fd8729a4cf4c7 src/Settings/Packages/Rts.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e684b7a..58b76cf 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -51,6 +51,8 @@ rtsPackageArgs = package rts ? do path <- getTargetPath top <- getTopDirectory libffiName <- lift $ rtsLibffiLibraryName + ffiIncludeDir <- getSetting FfiIncludeDir + ffiLibraryDir <- getSetting FfiLibDir mconcat [ builderGcc ? mconcat [ arg "-Irts" @@ -92,8 +94,8 @@ rtsPackageArgs = package rts ? do , builder HsCpp ? mconcat [ arg ("-DTOP=" ++ quote top) - , arg "-DFFI_INCLUDE_DIR=" - , arg "-DFFI_LIB_DIR=" + , arg ("-DFFI_INCLUDE_DIR=" ++ quote ffiIncludeDir) + , arg ("-DFFI_LIB_DIR=" ++ quote ffiLibraryDir) , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] From git at git.haskell.org Fri Oct 27 00:12:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use --flavour=quick (da2ce2e) Message-ID: <20171027001208.602503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da2ce2e21529a6e9a4c2dcc8a033996bdca33be5/ghc >--------------------------------------------------------------- commit da2ce2e21529a6e9a4c2dcc8a033996bdca33be5 Author: Andrey Mokhov Date: Fri May 6 00:18:12 2016 +0100 Use --flavour=quick See #234. [skip ci] >--------------------------------------------------------------- da2ce2e21529a6e9a4c2dcc8a033996bdca33be5 doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 79dfcc2..4674ff4 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -11,9 +11,9 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ cd ghc stack exec -- git clone git://github.com/snowleopard/hadrian stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j + stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quick -The entire process should take about an hour. +The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quick` flag from the last command line (this will slow down the build to about an hour). #### Future ideas From git at git.haskell.org Fri Oct 27 00:03:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds ghc-split generator, generateScripts and re-enables SplitObjects (7470e5d) Message-ID: <20171027000356.6EA813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7470e5d6f71ef5a662e8b0b1791683a03cbbebb8/ghc >--------------------------------------------------------------- commit 7470e5d6f71ef5a662e8b0b1791683a03cbbebb8 Author: Moritz Angermann Date: Sat Jan 9 14:39:14 2016 +0800 Adds ghc-split generator, generateScripts and re-enables SplitObjects Fixes #84. >--------------------------------------------------------------- 7470e5d6f71ef5a662e8b0b1791683a03cbbebb8 shaking-up-ghc.cabal | 1 + src/Main.hs | 1 + src/Rules/Generate.hs | 37 +++++++++++++++++++++++++++++++++++-- src/Rules/Generators/GhcSplit.hs | 25 +++++++++++++++++++++++++ src/Settings/User.hs | 3 ++- 5 files changed, 64 insertions(+), 3 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 066b9e7..bd6e31f 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -47,6 +47,7 @@ executable ghc-shake , Rules.Generators.GhcAutoconfH , Rules.Generators.GhcBootPlatformH , Rules.Generators.GhcPlatformH + , Rules.Generators.GhcSplit , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs , Rules.IntegerGmp diff --git a/src/Main.hs b/src/Main.hs index 1710b39..a56f9ed 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -19,6 +19,7 @@ main = shakeArgs options rules , Rules.Config.configRules , Rules.Generate.copyRules , Rules.Generate.generateRules + , Rules.Generate.generateScripts , Rules.generateTargets , Rules.IntegerGmp.integerGmpRules , Rules.Libffi.libffiRules diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 71d88b1..3b6dfdc 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,5 +1,5 @@ module Rules.Generate ( - generatePackageCode, generateRules, + generatePackageCode, generateRules, generateScripts, derivedConstantsPath, generatedDependencies, installTargets, copyRules ) where @@ -11,6 +11,7 @@ import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH import Rules.Generators.GhcBootPlatformH import Rules.Generators.GhcPlatformH +import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles @@ -80,7 +81,7 @@ compilerDependencies stage = generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage + | pkg == compiler = compilerDependencies stage ++ ["inplace/lib/bin/ghc-split"] | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = includesDependencies ++ derivedConstantsDependencies | stage == Stage0 = defaultDependencies @@ -104,6 +105,13 @@ generate file target expr = do writeFileChanged file contents putSuccess $ "| Successfully generated '" ++ file ++ "'." +-- | Generates @file@ for @target@ and marks it as executable. +generateExec :: FilePath -> PartialTarget -> Expr String -> Action () +generateExec file target expr = do + generate file target expr + unit $ cmd "chmod +x " [file] + putSuccess $ "| Made '" ++ file ++ "' executable." + generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let buildPath = targetPath stage pkg -/- "build" @@ -177,6 +185,31 @@ generateRules = do where file <~ gen = file %> \out -> generate out emptyTarget gen +-- | Generate scripts the build system requires. For now we generate the +-- @ghc-split@ script from it's literate perl source. +generateScripts :: Rules () +generateScripts = do + -- how to translate literate perl to perl. + -- this is a hack :-/ + "//*.prl" %> \out -> do + let src = out -<.> "lprl" + path <- builderPath Unlit + need [path] + unit $ cmd [path] [src] [out] + + -- ghc-split is only a perl script. + let ghcSplit = "inplace/lib/ghc-split" -- See system.config + let ghcSplitBin = "inplace/lib/bin/ghc-split" -- See ConfigHs.hs + + ghcSplit <~ generateGhcSplit + + ghcSplitBin %> \out -> do + need [ghcSplit] + copyFileChanged ghcSplit out + + where + file <~ gen = file %> \out -> generateExec out emptyTarget gen + -- TODO: Use the Types, Luke! (drop partial function) -- We sometimes need to evaluate expressions that do not require knowing all -- information about the target. In this case, we don't want to know anything. diff --git a/src/Rules/Generators/GhcSplit.hs b/src/Rules/Generators/GhcSplit.hs new file mode 100644 index 0000000..77cd49f --- /dev/null +++ b/src/Rules/Generators/GhcSplit.hs @@ -0,0 +1,25 @@ +module Rules.Generators.GhcSplit (generateGhcSplit) where + +import Base +import Expression +import Oracles +import Settings.User + +generateGhcSplit :: Expr String +generateGhcSplit = do + let yesNo = lift . fmap (\x -> if x then "YES" else "NO") + perl <- getBuilderPath Perl + let script = "driver" -/- "split" -/- "ghc-split.prl" + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules" -/- "Generators" -/- "GhcSplit.hs"] + lift $ need [script] + targetPlatform <- getSetting TargetPlatform + ghcEnableTNC <- yesNo ghcEnableTablesNextToCode + contents <- lift $ readFileLines script + return . unlines $ + [ "#!" ++ perl + , "$TARGETPLATFORM = \"" ++ targetPlatform ++ "\";" + -- I don't see where the ghc-split tool uses TNC, but + -- it's in the build-perl macro. + , "$TABLES_NEXT_TO_CODE = \"" ++ ghcEnableTNC ++ "\";" + ] ++ contents diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 7a877ce..6ba7155 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -9,6 +9,7 @@ module Settings.User ( import GHC import Expression import Predicates +import Settings.Default -- Control user-specific settings userArgs :: Args @@ -59,7 +60,7 @@ validating = False -- To switch off split objects change to 'return False' splitObjects :: Predicate -splitObjects = return False -- FIXME: should be defaultSplitObjects, see #84. +splitObjects = defaultSplitObjects dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Fri Oct 27 00:03:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up code, do renaming. (d41d5a7) Message-ID: <20171027000357.C8C413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d41d5a7e0efcad961a2ed77e1aecc10102834b89/ghc >--------------------------------------------------------------- commit d41d5a7e0efcad961a2ed77e1aecc10102834b89 Author: Andrey Mokhov Date: Mon Aug 10 01:38:57 2015 +0100 Clean up code, do renaming. >--------------------------------------------------------------- d41d5a7e0efcad961a2ed77e1aecc10102834b89 src/Expression.hs | 31 +++++++++++----------- src/Rules/Compile.hs | 37 +++++++++----------------- src/Rules/Data.hs | 4 +-- src/Rules/Library.hs | 4 +-- src/Rules/Oracles.hs | 14 +++++----- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Gcc.hs | 8 +++--- src/Settings/Builders/Ghc.hs | 9 ++++--- src/Settings/Builders/Ld.hs | 2 +- src/Target.hs | 63 ++++++++++++++++++++++---------------------- 10 files changed, 81 insertions(+), 93 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d41d5a7e0efcad961a2ed77e1aecc10102834b89 From git at git.haskell.org Fri Oct 27 00:03:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:03:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Selftest, add more tests for matchVersionedFilePath. (8ae1c56) Message-ID: <20171027000359.420A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ae1c564d861871d9b587d3525c704e3625a4864/ghc >--------------------------------------------------------------- commit 8ae1c564d861871d9b587d3525c704e3625a4864 Author: Andrey Mokhov Date: Tue Feb 16 23:10:12 2016 +0000 Refactor Selftest, add more tests for matchVersionedFilePath. >--------------------------------------------------------------- 8ae1c564d861871d9b587d3525c704e3625a4864 src/Rules/Selftest.hs | 54 ++++++++++++++++++++++++++++++++++----------------- 1 file changed, 36 insertions(+), 18 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 5fafda5..70a4023 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -15,24 +15,42 @@ instance Arbitrary Way where instance Arbitrary WayUnit where arbitrary = arbitraryBoundedEnum +test :: Testable a => a -> Action () +test = liftIO . quickCheck + selftestRules :: Rules () selftestRules = "selftest" ~> do - test $ \(x :: Way) -> read (show x) == x - test $ \n xs -> - let res = chunksOfSize n xs - in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res - test $ chunksOfSize 3 ["a","b","c","defg","hi","jk"] == [["a","b","c"],["defg"],["hi"],["jk"]] - - test $ matchVersionedFilePath "foo/bar" ".a" "foo/bar.a" == True - test $ matchVersionedFilePath "foo/bar" ".a" "foo\\bar.a" == True - test $ matchVersionedFilePath "foo/bar" "a" "foo/bar.a" == True - test $ matchVersionedFilePath "foo/bar" "" "foo/bar.a" == False - test $ matchVersionedFilePath "foo/bar" "a" "foo/bar-0.1.a" == True - test $ matchVersionedFilePath "foo/bar-" "a" "foo/bar-0.1.a" == True - test $ matchVersionedFilePath "foo/bar/" "a" "foo/bar-0.1.a" == False - - -- TODO: add automated tests for matchVersionedFilePath too - -test :: Testable a => a -> Action () -test = liftIO . quickCheck + testWays + testChunksOfSize + testMatchVersionedFilePath + +testWays :: Action () +testWays = do + putBuild $ "==== Read Way, Show Way" + test $ \(x :: Way) -> read (show x) == x + +testChunksOfSize :: Action () +testChunksOfSize = do + putBuild $ "==== chunksOfSize" + test $ chunksOfSize 3 [ "a", "b", "c" , "defg" , "hi" , "jk" ] + == [ ["a", "b", "c"], ["defg"], ["hi"], ["jk"] ] + test $ \n xs -> + let res = chunksOfSize n xs + in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res + +testMatchVersionedFilePath :: Action () +testMatchVersionedFilePath = do + putBuild $ "==== matchVersionedFilePath" + test $ matchVersionedFilePath "foo/bar" ".a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" ".a" "foo\\bar.a" == False + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" "" "foo/bar.a" == False + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar-" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar/" "a" "foo/bar-0.1.a" == False + + test $ \prefix suffix -> forAll versions $ \version -> + matchVersionedFilePath prefix suffix (prefix ++ version ++ suffix) + where + versions = listOf . elements $ '-' : '.' : ['0'..'9'] From git at git.haskell.org Fri Oct 27 00:04:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Extra library (693a66c) Message-ID: <20171027000400.16DED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/693a66cafe77e0ea2449e9f7b4bc51145c97ab38/ghc >--------------------------------------------------------------- commit 693a66cafe77e0ea2449e9f7b4bc51145c97ab38 Author: Moritz Angermann Date: Sat Jan 9 17:04:58 2016 +0800 Use Extra library - replaces `wordsWhen` with `wordsBy` - replaces `replace` with `replace` Fixes #130 >--------------------------------------------------------------- 693a66cafe77e0ea2449e9f7b4bc51145c97ab38 src/Base.hs | 23 ++--------------------- src/Oracles/LookupInPath.hs | 3 ++- src/Rules/Data.hs | 1 + src/Rules/Libffi.hs | 1 + 4 files changed, 6 insertions(+), 22 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 925c427..fb33907 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,9 +22,9 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, renderBox, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, replaceEq, replace, quote, chunksOfSize, + bimap, minusOrd, intersectOrd, replaceEq, quote, chunksOfSize, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), - versionToInt, removeFileIfExists, removeDirectoryIfExists, wordsWhen + versionToInt, removeFileIfExists, removeDirectoryIfExists ) where import Control.Applicative @@ -90,25 +90,6 @@ replaceSeparators = replaceWhen isPathSeparator replaceWhen :: (a -> Bool) -> a -> [a] -> [a] replaceWhen p to = map (\from -> if p from then to else from) --- | Find all occurrences of substring 'from' and replace them to 'to' in a --- given string. Not very efficient, but simple and fast enough for our purposes -replace :: Eq a => [a] -> [a] -> [a] -> [a] -replace from to = go - where - skipFrom = drop $ length from - go [] = [] - go s @ (x : xs) - | from `isPrefixOf` s = to ++ go (skipFrom s) - | otherwise = x : go xs - --- | Split a list into chunks in places where the predicate @p@ holds. --- See: http://stackoverflow.com/a/4981265 -wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] -wordsWhen p list = - case dropWhile p list of - [] -> [] - l -> w : wordsWhen p rest where (w, rest) = break p l - -- | @chunksOfSize size strings@ splits a given list of strings into chunks not -- exceeding the given @size at . chunksOfSize :: Int -> [String] -> [[String]] diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index c2a05e2..2532cb9 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -4,6 +4,7 @@ module Oracles.LookupInPath ( ) where import Base +import Extra (wordsBy) newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -22,7 +23,7 @@ lookupInPath c lookupInPathOracle :: Rules () lookupInPathOracle = do o <- newCache $ \c -> do - envPaths <- wordsWhen (== ':') <$> getEnvWithDefault "" "PATH" + envPaths <- wordsBy (== ':') <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths -- this will crash if we do not find any valid candidate. fullCommand <- head <$> filterM doesFileExist candidates diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index de4f8c0..b2c5878 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -2,6 +2,7 @@ module Rules.Data (buildPackageData) where import Base import Expression +import Extra (replace) import GHC import Oracles import Predicates (registerPackage) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 9d77814..31f249b 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -2,6 +2,7 @@ module Rules.Libffi (libffiRules, libffiDependencies) where import Base import Expression +import Extra (replace) import GHC import Oracles import Rules.Actions From git at git.haskell.org Fri Oct 27 00:04:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename getHsSources to getPackageSources. (810b1e2) Message-ID: <20171027000401.435E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/810b1e224cc0609b74ffae8d3772eb207e256879/ghc >--------------------------------------------------------------- commit 810b1e224cc0609b74ffae8d3772eb207e256879 Author: Andrey Mokhov Date: Mon Aug 10 01:39:47 2015 +0100 Rename getHsSources to getPackageSources. >--------------------------------------------------------------- 810b1e224cc0609b74ffae8d3772eb207e256879 src/Settings/Util.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Util.hs b/src/Settings/Util.hs index 13e5be0..675ba1b 100644 --- a/src/Settings/Util.hs +++ b/src/Settings/Util.hs @@ -5,7 +5,7 @@ module Settings.Util ( getFlag, getSetting, getSettingList, getPkgData, getPkgDataList, getPackagePath, getTargetPath, getTargetDirectory, - getHsSources, + getPackageSources, appendCcArgs, needBuilder -- argBuilderPath, argStagedBuilderPath, @@ -73,8 +73,8 @@ getTargetDirectory :: Expr FilePath getTargetDirectory = liftM2 targetDirectory getStage getPackage -- Find all Haskell source files for the current target -getHsSources :: Expr [FilePath] -getHsSources = do +getPackageSources :: Expr [FilePath] +getPackageSources = do path <- getTargetPath pkgPath <- getPackagePath srcDirs <- getPkgDataList SrcDirs From git at git.haskell.org Fri Oct 27 00:04:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Data.Bifunctor.bimap as it is now available on bootstrapping GHC. (cbbbc63) Message-ID: <20171027000403.07EB03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbbbc63883b41b794d154efbb7a166ea659980db/ghc >--------------------------------------------------------------- commit cbbbc63883b41b794d154efbb7a166ea659980db Author: Andrey Mokhov Date: Wed Feb 17 01:59:11 2016 +0000 Use Data.Bifunctor.bimap as it is now available on bootstrapping GHC. >--------------------------------------------------------------- cbbbc63883b41b794d154efbb7a166ea659980db src/Base.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 769fdc4..7d63fa0 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -3,6 +3,7 @@ module Base ( -- * General utilities module Control.Applicative, module Control.Monad.Extra, + module Data.Bifunctor, module Data.Function, module Data.List.Extra, module Data.Maybe, @@ -22,7 +23,7 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, + minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath ) where @@ -30,6 +31,7 @@ module Base ( import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader +import Data.Bifunctor import Data.Char import Data.Function import Data.List.Extra @@ -142,11 +144,6 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg --- Explicit definition to avoid dependency on Data.Bifunctor --- | Bifunctor bimap. -bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) -bimap f g (x, y) = (f x, g y) - -- Explicit definition to avoid dependency on Data.List.Ordered -- | Difference of two ordered lists. minusOrd :: Ord a => [a] -> [a] -> [a] From git at git.haskell.org Fri Oct 27 00:04:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #140 from snowleopard/feature/use-extra (8c2a30d) Message-ID: <20171027000403.D7F363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c2a30db05a56cd1e1c33c34acbe3a794a7b00d7/ghc >--------------------------------------------------------------- commit 8c2a30db05a56cd1e1c33c34acbe3a794a7b00d7 Merge: a64efa9 693a66c Author: Andrey Mokhov Date: Sat Jan 9 12:15:46 2016 +0000 Merge pull request #140 from snowleopard/feature/use-extra Use Extra library >--------------------------------------------------------------- 8c2a30db05a56cd1e1c33c34acbe3a794a7b00d7 src/Base.hs | 23 ++--------------------- src/Oracles/LookupInPath.hs | 3 ++- src/Rules/Data.hs | 1 + src/Rules/Libffi.hs | 1 + 4 files changed, 6 insertions(+), 22 deletions(-) From git at git.haskell.org Fri Oct 27 00:04:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise ArgsHash oracle improving zero build time. (486a3e5) Message-ID: <20171027000404.DC23C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/486a3e58a9c323f651f733508492efe9a3e768d0/ghc >--------------------------------------------------------------- commit 486a3e58a9c323f651f733508492efe9a3e768d0 Author: Andrey Mokhov Date: Mon Aug 10 01:40:17 2015 +0100 Optimise ArgsHash oracle improving zero build time. >--------------------------------------------------------------- 486a3e58a9c323f651f733508492efe9a3e768d0 src/Oracles/ArgsHash.hs | 13 ++++++++----- src/Rules/Actions.hs | 4 +--- 2 files changed, 9 insertions(+), 8 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index ca0aa6c..f67f8c4 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -1,23 +1,26 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.ArgsHash ( - askArgsHash, argsHashOracle + checkArgsHash, argsHashOracle ) where import Base +import Target import Expression import Settings.Args import Control.Applicative -newtype ArgsHashKey = ArgsHashKey FullTarget - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +newtype ArgsHashKey = ArgsHashKey Target + deriving (Show, Eq, Typeable, Binary, Hashable, NFData) -- This is an action that given a full target determines the corresponding -- argument list and computes its hash. The resulting value is tracked in a -- Shake oracle, hence initiating rebuilts when the hash is changed (a hash -- change indicates changes in the build system). -askArgsHash :: FullTarget -> Action Int -askArgsHash = askOracle . ArgsHashKey +checkArgsHash :: FullTarget -> Action () +checkArgsHash target = do + tmp <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int + return () -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 062a5d5..2f9ebc6 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -19,13 +19,11 @@ import Settings.Builders.Ar buildWithResources :: [(Resource, Int)] -> FullTarget -> Action () buildWithResources rs target = do let builder = Target.builder target - deps = Target.dependencies target needBuilder builder - -- need deps -- TODO: think if needs could be done here path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed - argsHash <- askArgsHash target + checkArgsHash target withResources rs $ do putBuild $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" From git at git.haskell.org Fri Oct 27 00:04:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Ensure that if ghc compilation fails then we return a non-zero error code from build.bat (e40e2e0) Message-ID: <20171027000406.7019E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e40e2e0e80d81f88d374a6e917b660befdde46b4/ghc >--------------------------------------------------------------- commit e40e2e0e80d81f88d374a6e917b660befdde46b4 Author: Neil Mitchell Date: Wed Feb 17 16:24:19 2016 +0000 Ensure that if ghc compilation fails then we return a non-zero error code from build.bat >--------------------------------------------------------------- e40e2e0e80d81f88d374a6e917b660befdde46b4 build.bat | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/build.bat b/build.bat index 348537d..10a6969 100644 --- a/build.bat +++ b/build.bat @@ -21,8 +21,8 @@ @ghc %ghcArgs% - at if %ERRORLEVEL% EQU 0 ( - @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains - @set GHC_PACKAGE_PATH= - @.shake\build %shakeArgs% -) + at if %ERRORLEVEL% NEQ 0 EXIT /B %ERRORLEVEL% + + at rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains + at set GHC_PACKAGE_PATH= + at .shake\build %shakeArgs% From git at git.haskell.org Fri Oct 27 00:04:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Shallow clone GHC from Github instead of Haskell.org (c43d07d) Message-ID: <20171027000407.A1F4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c43d07d967b7a7876e6a7733a343934d35d0d616/ghc >--------------------------------------------------------------- commit c43d07d967b7a7876e6a7733a343934d35d0d616 Author: David Luposchainsky Date: Sat Jan 9 14:01:33 2016 +0100 Shallow clone GHC from Github instead of Haskell.org >--------------------------------------------------------------- c43d07d967b7a7876e6a7733a343934d35d0d616 .travis.yml | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 6413818..ca51b6f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -39,7 +39,12 @@ install: - alex --version - happy --version - - travis_retry git clone git://git.haskell.org/ghc --recurse-submodules + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ + - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ + - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ + - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ + - travis_retry git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 # Travis clones the project into ".", but we need it as a child directory # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake From git at git.haskell.org Fri Oct 27 00:04:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix performance drop due to improper use of removeFiles. (18a779b) Message-ID: <20171027000408.7E0553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/18a779b20d3084cc681ce28ff88ca6b97d45903f/ghc >--------------------------------------------------------------- commit 18a779b20d3084cc681ce28ff88ca6b97d45903f Author: Andrey Mokhov Date: Tue Aug 11 00:16:38 2015 +0100 Fix performance drop due to improper use of removeFiles. >--------------------------------------------------------------- 18a779b20d3084cc681ce28ff88ca6b97d45903f src/Rules/Dependencies.hs | 3 ++- src/Rules/Library.hs | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 90c764f..8fb890e 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -11,6 +11,7 @@ import Settings.Util import Settings.TargetDirectory import Rules.Actions import Rules.Resources +import qualified System.Directory as IO buildPackageDependencies :: Resources -> StagePackageTarget -> Rules () buildPackageDependencies _ target = @@ -30,7 +31,7 @@ buildPackageDependencies _ target = srcs <- interpret target getPackageSources need srcs build $ fullTarget target (GhcM stage) srcs [file] - liftIO $ removeFiles "." [hDepFile <.> "bak"] + liftIO . IO.removeFile $ file <.> "bak" (buildPath -/- ".dependencies") %> \file -> do cSrcs <- pkgDataList $ CSrcs path diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 87a37ca..4619651 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -25,7 +25,7 @@ buildPackageLibrary _ target = do -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do - liftIO $ removeFiles "." [a] + liftIO $ IO.removeFile a cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules From git at git.haskell.org Fri Oct 27 00:04:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/ndmitchell/shaking-up-ghc (f98836e) Message-ID: <20171027000410.197203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f98836ec1bae9809c167277232e0629647af1145/ghc >--------------------------------------------------------------- commit f98836ec1bae9809c167277232e0629647af1145 Merge: e40e2e0 cbbbc63 Author: Neil Mitchell Date: Wed Feb 17 16:25:50 2016 +0000 Merge branch 'master' of https://github.com/ndmitchell/shaking-up-ghc >--------------------------------------------------------------- f98836ec1bae9809c167277232e0629647af1145 src/Base.hs | 12 +++++------- src/Rules.hs | 2 ++ src/Rules/Library.hs | 19 +++++++++++-------- src/Rules/Register.hs | 9 ++------- src/Rules/Selftest.hs | 45 +++++++++++++++++++++++++++++++++++++-------- 5 files changed, 57 insertions(+), 30 deletions(-) From git at git.haskell.org Fri Oct 27 00:04:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop "ghs-split" builder (b214918) Message-ID: <20171027000411.80FF13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b214918b34ab1ab5131457391dbdb4d023ea46e0/ghc >--------------------------------------------------------------- commit b214918b34ab1ab5131457391dbdb4d023ea46e0 Author: Moritz Angermann Date: Sat Jan 9 21:16:20 2016 +0800 Drop "ghs-split" builder >--------------------------------------------------------------- b214918b34ab1ab5131457391dbdb4d023ea46e0 cfg/system.config.in | 3 +-- src/Builder.hs | 2 -- src/Rules/Generators/ConfigHs.hs | 2 +- 3 files changed, 2 insertions(+), 5 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 6338e33..498f78c 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -28,8 +28,7 @@ derive-constants = inplace/bin/deriveConstants hs-cpp = @HaskellCPPCmd@ hs-cpp-args = @HaskellCPPArgs@ -unlit = inplace/lib/unlit -ghc-split = inplace/lib/ghc-split +unlit = inplace/lib/bin/unlit alex = @AlexCmd@ ar = @ArCmd@ diff --git a/src/Builder.hs b/src/Builder.hs index 5450815..efc3216 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -32,7 +32,6 @@ data Builder = Alex | GhcCabalHsColour | GhcM Stage | GhcPkg Stage - | GhcSplit | Haddock | Happy | HsColour @@ -75,7 +74,6 @@ builderKey builder = case builder of GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" - GhcSplit -> "ghc-split" Happy -> "happy" Haddock -> "haddock" HsColour -> "hscolour" diff --git a/src/Rules/Generators/ConfigHs.hs b/src/Rules/Generators/ConfigHs.hs index 547670a..5cdfc3f 100644 --- a/src/Rules/Generators/ConfigHs.hs +++ b/src/Rules/Generators/ConfigHs.hs @@ -32,7 +32,7 @@ generateConfigHs = do cGhcEnableTablesNextToCode <- yesNo ghcEnableTablesNextToCode cLeadingUnderscore <- yesNo $ flag LeadingUnderscore cGHC_UNLIT_PGM <- fmap takeFileName $ getBuilderPath Unlit - cGHC_SPLIT_PGM <- fmap takeBaseName $ getBuilderPath GhcSplit + let cGHC_SPLIT_PGM = "ghc-split" cLibFFI <- lift useLibFFIForAdjustors rtsWays <- getRtsWays cGhcRtsWithLibdw <- getFlag WithLibdw From git at git.haskell.org Fri Oct 27 00:04:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (096f602) Message-ID: <20171027000412.7F3893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/096f6029109bf36ab29f2178942b62fdce884e26/ghc >--------------------------------------------------------------- commit 096f6029109bf36ab29f2178942b62fdce884e26 Author: Andrey Mokhov Date: Tue Aug 11 00:24:24 2015 +0100 Add comments. >--------------------------------------------------------------- 096f6029109bf36ab29f2178942b62fdce884e26 src/Oracles/ArgsHash.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index f67f8c4..422cacd 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -17,6 +17,12 @@ newtype ArgsHashKey = ArgsHashKey Target -- argument list and computes its hash. The resulting value is tracked in a -- Shake oracle, hence initiating rebuilts when the hash is changed (a hash -- change indicates changes in the build system). +-- Note: we replace target sources with ["src"] for performance reasons -- to +-- avoid storing long lists of source files passed to some builders (e.g. Ar) +-- in the Shake database. This optimisation is harmless, because argument list +-- constructors are assumed not to examine target sources, but only append them +-- to argument lists where appropriate. +-- TODO: enforce the above assumption via type trickery? checkArgsHash :: FullTarget -> Action () checkArgsHash target = do tmp <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int From git at git.haskell.org Fri Oct 27 00:04:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #208 from ndmitchell/master (d1dacae) Message-ID: <20171027000413.EEF133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1dacaea037b9d63b3747c1d1b30e5b3b9fe5dcd/ghc >--------------------------------------------------------------- commit d1dacaea037b9d63b3747c1d1b30e5b3b9fe5dcd Merge: cbbbc63 f98836e Author: Andrey Mokhov Date: Wed Feb 17 17:09:24 2016 +0000 Merge pull request #208 from ndmitchell/master Ensure that if ghc compilation fails then we return a non-zero error code from build.bat >--------------------------------------------------------------- d1dacaea037b9d63b3747c1d1b30e5b3b9fe5dcd build.bat | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Oct 27 00:04:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Include PR Comments (423c5dd) Message-ID: <20171027000414.F3FDF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/423c5dd10b51f3251d59fec64c68b7bc07019dbf/ghc >--------------------------------------------------------------- commit 423c5dd10b51f3251d59fec64c68b7bc07019dbf Author: Moritz Angermann Date: Sat Jan 9 21:44:23 2016 +0800 Include PR Comments >--------------------------------------------------------------- 423c5dd10b51f3251d59fec64c68b7bc07019dbf shaking-up-ghc.cabal | 1 + src/GHC.hs | 5 +---- src/Main.hs | 3 ++- src/Rules/Generate.hs | 33 ++++----------------------------- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Perl.hs | 25 +++++++++++++++++++++++++ 6 files changed, 34 insertions(+), 35 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index bd6e31f..a5b4c57 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -55,6 +55,7 @@ executable ghc-shake , Rules.Library , Rules.Oracles , Rules.Package + , Rules.Perl , Rules.Program , Rules.Resources , Rules.Wrappers.Ghc diff --git a/src/GHC.hs b/src/GHC.hs index c26f552..3b58bbe 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -113,12 +113,9 @@ defaultProgramPath stage pkg | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing - | pkg == touchy = case stage of + | pkg `elem` [touchy, unlit] = case stage of Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe _ -> Nothing - | pkg == unlit = case stage of - Stage0 -> Just $ "inplace/lib" -/- pkgNameString pkg <.> exe - _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg diff --git a/src/Main.hs b/src/Main.hs index a56f9ed..9f223a8 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -10,6 +10,7 @@ import qualified Rules.Generate import qualified Rules.IntegerGmp import qualified Rules.Libffi import qualified Rules.Oracles +import qualified Rules.Perl main :: IO () main = shakeArgs options rules @@ -19,7 +20,7 @@ main = shakeArgs options rules , Rules.Config.configRules , Rules.Generate.copyRules , Rules.Generate.generateRules - , Rules.Generate.generateScripts + , Rules.Perl.perlScriptRules , Rules.generateTargets , Rules.IntegerGmp.integerGmpRules , Rules.Libffi.libffiRules diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 3b6dfdc..2b2962b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( - generatePackageCode, generateRules, generateScripts, - derivedConstantsPath, generatedDependencies, + generate, generateExec, generatePackageCode, generateRules, + derivedConstantsPath, emptyTarget, generatedDependencies, installTargets, copyRules ) where @@ -11,7 +11,6 @@ import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH import Rules.Generators.GhcBootPlatformH import Rules.Generators.GhcPlatformH -import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles @@ -78,10 +77,11 @@ compilerDependencies stage = , "primop-vector-tys-exports.hs-incl" , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] + ++ ["inplace/lib/bin/ghc-split"] generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage ++ ["inplace/lib/bin/ghc-split"] + | pkg == compiler = compilerDependencies stage | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = includesDependencies ++ derivedConstantsDependencies | stage == Stage0 = defaultDependencies @@ -185,31 +185,6 @@ generateRules = do where file <~ gen = file %> \out -> generate out emptyTarget gen --- | Generate scripts the build system requires. For now we generate the --- @ghc-split@ script from it's literate perl source. -generateScripts :: Rules () -generateScripts = do - -- how to translate literate perl to perl. - -- this is a hack :-/ - "//*.prl" %> \out -> do - let src = out -<.> "lprl" - path <- builderPath Unlit - need [path] - unit $ cmd [path] [src] [out] - - -- ghc-split is only a perl script. - let ghcSplit = "inplace/lib/ghc-split" -- See system.config - let ghcSplitBin = "inplace/lib/bin/ghc-split" -- See ConfigHs.hs - - ghcSplit <~ generateGhcSplit - - ghcSplitBin %> \out -> do - need [ghcSplit] - copyFileChanged ghcSplit out - - where - file <~ gen = file %> \out -> generateExec out emptyTarget gen - -- TODO: Use the Types, Luke! (drop partial function) -- We sometimes need to evaluate expressions that do not require knowing all -- information about the target. In this case, we don't want to know anything. diff --git a/src/Rules/Generators/GhcSplit.hs b/src/Rules/Generators/GhcSplit.hs index 77cd49f..a2bd8b2 100644 --- a/src/Rules/Generators/GhcSplit.hs +++ b/src/Rules/Generators/GhcSplit.hs @@ -9,7 +9,7 @@ generateGhcSplit :: Expr String generateGhcSplit = do let yesNo = lift . fmap (\x -> if x then "YES" else "NO") perl <- getBuilderPath Perl - let script = "driver" -/- "split" -/- "ghc-split.prl" + let script = "driver/split/ghc-split.prl" when trackBuildSystem . lift $ need [sourcePath -/- "Rules" -/- "Generators" -/- "GhcSplit.hs"] lift $ need [script] diff --git a/src/Rules/Perl.hs b/src/Rules/Perl.hs new file mode 100644 index 0000000..c1e5ba8 --- /dev/null +++ b/src/Rules/Perl.hs @@ -0,0 +1,25 @@ +module Rules.Perl (perlScriptRules) where + +import Base +import Expression +import Rules.Actions (runBuilder) +import Rules.Generate (generateExec, emptyTarget) +import Rules.Generators.GhcSplit (generateGhcSplit) + +-- | Generate scripts the build system requires. For now we generate the +-- @ghc-split@ script from it's literate perl source. +perlScriptRules :: Rules () +perlScriptRules = do + -- how to translate literate perl to perl. + -- this is a hack :-/ + "//*.prl" %> \out -> do + let src = out -<.> "lprl" + runBuilder Unlit [src, out] + + -- ghc-split is only a perl script. + let ghcSplit = "inplace/lib/bin/ghc-split" + + ghcSplit <~ generateGhcSplit + + where + file <~ gen = file %> \out -> generateExec out emptyTarget gen From git at git.haskell.org Fri Oct 27 00:04:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --profile=- to CI build scripts. (6dc581c) Message-ID: <20171027000417.8C1F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6dc581c2a9b8c1c68980fd59fd3ceee4569d05d3/ghc >--------------------------------------------------------------- commit 6dc581c2a9b8c1c68980fd59fd3ceee4569d05d3 Author: Andrey Mokhov Date: Thu Feb 18 00:25:54 2016 +0000 Add --profile=- to CI build scripts. Fix #209. >--------------------------------------------------------------- 6dc581c2a9b8c1c68980fd59fd3ceee4569d05d3 .appveyor.yml | 2 +- .travis.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7ffabc3..537983c 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -39,4 +39,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --profile=- --flavour=quick inplace/bin/ghc-stage1.exe diff --git a/.travis.yml b/.travis.yml index d7e58c3..9547914 100644 --- a/.travis.yml +++ b/.travis.yml @@ -62,7 +62,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET + - ./ghc/shake-build/build.sh -j --no-progress --profile=- --flavour=quick $TARGET cache: directories: From git at git.haskell.org Fri Oct 27 00:04:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adjust cmdLineLengthLimit for OS X (e3d96ff) Message-ID: <20171027000418.A0CDA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3d96ff27fb0967053043b0d30c0fb4112889613/ghc >--------------------------------------------------------------- commit e3d96ff27fb0967053043b0d30c0fb4112889613 Author: Moritz Angermann Date: Sat Jan 9 21:45:08 2016 +0800 Adjust cmdLineLengthLimit for OS X This should fix #141. >--------------------------------------------------------------- e3d96ff27fb0967053043b0d30c0fb4112889613 src/Oracles/Config/Setting.hs | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index ace9158..58f508b 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -3,7 +3,7 @@ module Oracles.Config.Setting ( setting, settingList, getSetting, getSettingList, anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, windowsHost, ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, - ghcCanonVersion, cmdLineLengthLimit + ghcCanonVersion, cmdLineLengthLimit, osxHost ) where import Control.Monad.Trans.Reader @@ -125,6 +125,9 @@ anyHostOs = matchSetting HostOs windowsHost :: Action Bool windowsHost = anyHostOs ["mingw32", "cygwin32"] +osxHost :: Action Bool +osxHost = anyHostOs ["darwin"] + ghcWithInterpreter :: Action Bool ghcWithInterpreter = do goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "solaris2" @@ -156,6 +159,10 @@ ghcCanonVersion = do cmdLineLengthLimit :: Action Int cmdLineLengthLimit = do windows <- windowsHost - return $ if windows - then 31000 - else 4194304 -- Cabal needs a bit more than 2MB! + osx <- osxHost + return $ case (windows, osx) of + -- windows + (True, False) -> 31000 + -- osx 262144 is ARG_MAX, 33166 experimentally determined + (False, True) -> 262144 - 33166 + _ -> 4194304 -- Cabal needs a bit more than 2MB! From git at git.haskell.org Fri Oct 27 00:04:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add removeFile to Util.hs. (6b0b4ab) Message-ID: <20171027000416.075593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b0b4ab1c3d88df4e67d9ade22f45fcd8369708b/ghc >--------------------------------------------------------------- commit 6b0b4ab1c3d88df4e67d9ade22f45fcd8369708b Author: Andrey Mokhov Date: Tue Aug 11 02:48:11 2015 +0100 Add removeFile to Util.hs. >--------------------------------------------------------------- 6b0b4ab1c3d88df4e67d9ade22f45fcd8369708b src/Rules/Compile.hs | 2 -- src/Rules/Dependencies.hs | 3 +-- src/Rules/Library.hs | 10 +++++----- src/Util.hs | 12 +++++++++++- 4 files changed, 17 insertions(+), 10 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 43659b9..30a77cb 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -17,8 +17,6 @@ compilePackage _ target = do pkg = Target.package target path = targetPath stage pkg buildPath = path -/- "build" - cDepsFile = buildPath -/- "c.deps" - hDepsFile = buildPath -/- "haskell.deps" matchBuildResult buildPath "hi" ?> \hi -> need [ hi -<.> osuf (detectWay hi) ] diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 8fb890e..e63d27d 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -11,7 +11,6 @@ import Settings.Util import Settings.TargetDirectory import Rules.Actions import Rules.Resources -import qualified System.Directory as IO buildPackageDependencies :: Resources -> StagePackageTarget -> Rules () buildPackageDependencies _ target = @@ -31,7 +30,7 @@ buildPackageDependencies _ target = srcs <- interpret target getPackageSources need srcs build $ fullTarget target (GhcM stage) srcs [file] - liftIO . IO.removeFile $ file <.> "bak" + removeFile $ file <.> "bak" (buildPath -/- ".dependencies") %> \file -> do cSrcs <- pkgDataList $ CSrcs path diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 4619651..5956030 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -25,7 +25,7 @@ buildPackageLibrary _ target = do -- TODO: handle dynamic libraries matchBuildResult buildPath "a" ?> \a -> do - liftIO $ IO.removeFile a + removeFile a cSrcs <- interpret target $ getPkgDataList CSrcs modules <- interpret target $ getPkgDataList Modules @@ -34,17 +34,17 @@ buildPackageLibrary _ target = do cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ] hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] - -- This will create split objects if required (we don't track them) + -- This will create split objects if required (we don't track them + -- explicitly as this would needlessly bloat the Shake database). need $ cObjs ++ hObjs split <- interpret target splitObjects - splitObjs <- if split - then fmap concat $ forM hSrcs $ \src -> do + splitObjs <- if not split then return [] else + fmap concat $ forM hSrcs $ \src -> do let splitPath = buildPath -/- src ++ "_" ++ osuf way ++ "_split" contents <- liftIO $ IO.getDirectoryContents splitPath return . map (splitPath -/-) . filter (not . all (== '.')) $ contents - else return [] build $ fullTarget target Ar (cObjs ++ hObjs ++ splitObjs) [a] diff --git a/src/Util.hs b/src/Util.hs index dd0f2d8..b78592a 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -5,13 +5,16 @@ module Util ( unifyPath, (-/-), chunksOfSize, putColoured, putOracle, putBuild, putSuccess, putError, - bimap, minusOrd, intersectOrd + bimap, minusOrd, intersectOrd, + removeFile ) where import Base import Data.Char +import Control.Monad import System.IO import System.Console.ANSI +import qualified System.Directory as IO replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) @@ -100,3 +103,10 @@ intersectOrd cmp = loop LT -> loop xs (y:ys) EQ -> x : loop xs ys GT -> loop (x:xs) ys + +-- Convenient helper function for removing a single file that doesn't +-- necessarily exist. +removeFile :: FilePath -> Action () +removeFile file = do + exists <- liftIO $ IO.doesFileExist file + when exists . liftIO $ IO.removeFile file From git at git.haskell.org Fri Oct 27 00:04:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add trackBuildSystem switch (perhaps, temporarily). (2b2008d) Message-ID: <20171027000419.805ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2b2008d6048aa691d8ea4f86e89c9ee5c4e2f300/ghc >--------------------------------------------------------------- commit 2b2008d6048aa691d8ea4f86e89c9ee5c4e2f300 Author: Andrey Mokhov Date: Wed Aug 12 01:27:28 2015 +0100 Add trackBuildSystem switch (perhaps, temporarily). >--------------------------------------------------------------- 2b2008d6048aa691d8ea4f86e89c9ee5c4e2f300 src/Rules/Actions.hs | 3 ++- src/Rules/Oracles.hs | 14 ++++++++------ src/Settings/User.hs | 11 +++++++++-- 3 files changed, 19 insertions(+), 9 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 2f9ebc6..9726e2f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -11,6 +11,7 @@ import Oracles.Setting import Oracles.ArgsHash import Settings.Args import Settings.Util +import Settings.User import Settings.Builders.Ar -- Build a given target using an appropriate builder and acquiring necessary @@ -23,7 +24,7 @@ buildWithResources rs target = do path <- builderPath builder argList <- interpret target getArgs -- The line below forces the rule to be rerun if the args hash has changed - checkArgsHash target + when trackBuildSystem $ checkArgsHash target withResources rs $ do putBuild $ "/--------\n" ++ "| Running " ++ show builder ++ " with arguments:" diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 32938ff..9b6d597 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -9,12 +9,14 @@ import Oracles.PackageData import Oracles.WindowsRoot import Oracles.PackageDeps import Oracles.Dependencies +import Settings.User +import Control.Monad oracleRules :: Rules () oracleRules = do - configOracle -- see Oracles.Base - packageDataOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - dependenciesOracle -- see Oracles.Dependencies - argsHashOracle -- see Oracles.ArgsHash - windowsRootOracle -- see Oracles.WindowsRoot + configOracle -- see Oracles.Base + packageDataOracle -- see Oracles.PackageData + packageDepsOracle -- see Oracles.PackageDeps + dependenciesOracle -- see Oracles.Dependencies + when trackBuildSystem argsHashOracle -- see Oracles.ArgsHash + windowsRootOracle -- see Oracles.WindowsRoot diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 572feb4..8831d65 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,7 +1,7 @@ module Settings.User ( userArgs, userPackages, userWays, userRtsWays, userTargetDirectory, userKnownPackages, integerLibrary, - buildHaddock, validating, ghciWithDebugger, ghcProfiled, + trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, dynamicGhcPrograms, laxDependencies ) where @@ -42,6 +42,14 @@ integerLibrary = integerGmp2 -- * Bool: a plain Boolean flag whose value is known at compile time -- * Action Bool: a flag whose value can depend on the build environment -- * Predicate: a flag depending on the build environment and the current target + +-- Set this to True if you are making any changes in the build system and want +-- appropriate rebuilds to be initiated. Switching this to False speeds things +-- up a little (particularly zero builds). +-- WARNING: changing this setting leads to a complete rebuild. +trackBuildSystem :: Bool +trackBuildSystem = False + validating :: Bool validating = False @@ -59,4 +67,3 @@ laxDependencies = False buildHaddock :: Predicate buildHaddock = return True - From git at git.haskell.org Fri Oct 27 00:04:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing resource dependency to buildBinary. (dfce0db) Message-ID: <20171027000421.27A933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfce0db830f71511065a5475934a9791c0eb9524/ghc >--------------------------------------------------------------- commit dfce0db830f71511065a5475934a9791c0eb9524 Author: Andrey Mokhov Date: Thu Feb 18 08:36:38 2016 +0000 Add missing resource dependency to buildBinary. See #206. >--------------------------------------------------------------- dfce0db830f71511065a5475934a9791c0eb9524 src/Rules.hs | 2 +- src/Rules/Program.hs | 16 ++++++++-------- 2 files changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 444a2cb..0136c27 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -75,7 +75,7 @@ packageRules = do , buildPackageDocumentation , buildPackageGhciLibrary , generatePackageCode - , buildProgram + , buildProgram readPackageDb , registerPackage writePackageDb ] buildRules :: Rules () diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index d7fdaad..6eaa821 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -31,8 +31,8 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper)] -buildProgram :: Context -> Rules () -buildProgram context @ (Context {..}) = do +buildProgram :: [(Resource, Int)] -> Context -> Rules () +buildProgram rs context @ (Context {..}) = do let match file = case programPath stage package of Nothing -> False Just program -> program == file @@ -45,15 +45,15 @@ buildProgram context @ (Context {..}) = do match ?> \bin -> do windows <- windowsHost if windows - then buildBinary context bin -- We don't build wrappers on Windows + then buildBinary rs context bin -- We don't build wrappers on Windows else case find ((== context) . fst) wrappers of - Nothing -> buildBinary context bin -- No wrapper found + Nothing -> buildBinary rs context bin -- No wrapper found Just (_, wrapper) -> do let Just wrappedBin = computeWrappedPath bin need [wrappedBin] buildWrapper context wrapper bin wrappedBin - matchWrapped ?> \bin -> buildBinary context bin + matchWrapped ?> \bin -> buildBinary rs context bin -- Replace programInplacePath with programInplaceLibPath in a given path computeWrappedPath :: FilePath -> Maybe FilePath @@ -70,8 +70,8 @@ buildWrapper context @ (Context stage package _) wrapper wrapperPath binPath = d -- TODO: Get rid of the Paths_hsc2hs.o hack. -- TODO: Do we need to consider other ways when building programs? -buildBinary :: Context -> FilePath -> Action () -buildBinary context @ (Context stage package _) bin = do +buildBinary :: [(Resource, Int)] -> Context -> FilePath -> Action () +buildBinary rs context @ (Context stage package _) bin = do let buildPath = targetPath stage package -/- "build" cSrcs <- cSources context -- TODO: remove code duplication (Library.hs) hSrcs <- hSources context @@ -100,7 +100,7 @@ buildBinary context @ (Context stage package _) bin = do then [ pkgPath package -/- src <.> "hs" | src <- hSrcs ] else objs need $ binDeps ++ libs - build $ Target context (Ghc stage) binDeps [bin] + buildWithResources rs $ Target context (Ghc stage) binDeps [bin] synopsis <- interpretInContext context $ getPkgData Synopsis putSuccess $ renderProgram ("'" ++ pkgNameString package ++ "' (" ++ show stage ++ ").") From git at git.haskell.org Fri Oct 27 00:04:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #138 from snowleopard/feature/UtilUnlit (883d929) Message-ID: <20171027000422.2B0A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/883d92982c8de5abb8ee22f42f82eba94ed05566/ghc >--------------------------------------------------------------- commit 883d92982c8de5abb8ee22f42f82eba94ed05566 Merge: 8c2a30d e3d96ff Author: Andrey Mokhov Date: Sat Jan 9 14:08:26 2016 +0000 Merge pull request #138 from snowleopard/feature/UtilUnlit Add support for ghc-split, unlit and perl script rules. >--------------------------------------------------------------- 883d92982c8de5abb8ee22f42f82eba94ed05566 cfg/system.config.in | 4 ++-- shaking-up-ghc.cabal | 3 +++ src/Builder.hs | 4 ++-- src/GHC.hs | 11 ++++++----- src/Main.hs | 2 ++ src/Oracles/Config/Setting.hs | 15 +++++++++++---- src/Rules/Data.hs | 11 +++++++++++ src/Rules/Generate.hs | 12 ++++++++++-- src/Rules/Generators/ConfigHs.hs | 2 +- src/Rules/Generators/GhcSplit.hs | 25 +++++++++++++++++++++++++ src/Rules/Perl.hs | 25 +++++++++++++++++++++++++ src/Settings/Args.hs | 4 +++- src/Settings/Packages/{Hp2ps.hs => Unlit.hs} | 10 +++++----- src/Settings/User.hs | 3 ++- 14 files changed, 108 insertions(+), 23 deletions(-) From git at git.haskell.org Fri Oct 27 00:04:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clarify comment. (f72d396) Message-ID: <20171027000423.19B7B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f72d3961e47c80754c60921b72c52e9e71a2410d/ghc >--------------------------------------------------------------- commit f72d3961e47c80754c60921b72c52e9e71a2410d Author: Andrey Mokhov Date: Wed Aug 12 01:30:38 2015 +0100 Clarify comment. >--------------------------------------------------------------- f72d3961e47c80754c60921b72c52e9e71a2410d src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 8831d65..1ca003b 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -46,7 +46,7 @@ integerLibrary = integerGmp2 -- Set this to True if you are making any changes in the build system and want -- appropriate rebuilds to be initiated. Switching this to False speeds things -- up a little (particularly zero builds). --- WARNING: changing this setting leads to a complete rebuild. +-- WARNING: a complete rebuild is required when changing this setting. trackBuildSystem :: Bool trackBuildSystem = False From git at git.haskell.org Fri Oct 27 00:04:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make RecordWildCards a default extension. (548a30b) Message-ID: <20171027000424.926063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/548a30b993efcdad064a6d9b14deb5b7a40b681d/ghc >--------------------------------------------------------------- commit 548a30b993efcdad064a6d9b14deb5b7a40b681d Author: Andrey Mokhov Date: Fri Feb 19 00:00:14 2016 +0000 Make RecordWildCards a default extension. See #207. >--------------------------------------------------------------- 548a30b993efcdad064a6d9b14deb5b7a40b681d build.bat | 1 + build.sh | 1 + shaking-up-ghc.cabal | 2 +- src/Rules/Actions.hs | 1 - src/Rules/Compile.hs | 1 - src/Rules/Data.hs | 1 - src/Rules/Dependencies.hs | 1 - src/Rules/Documentation.hs | 1 - src/Rules/Library.hs | 1 - src/Rules/Program.hs | 1 - src/Rules/Register.hs | 1 - 11 files changed, 3 insertions(+), 9 deletions(-) diff --git a/build.bat b/build.bat index 10a6969..465d957 100644 --- a/build.bat +++ b/build.bat @@ -4,6 +4,7 @@ @set ghcArgs=--make ^ -Wall ^ -fno-warn-name-shadowing ^ + -XRecordWildCards ^ src/Main.hs ^ -isrc ^ -rtsopts ^ diff --git a/build.sh b/build.sh index 77c9fa4..7c070e9 100755 --- a/build.sh +++ b/build.sh @@ -36,6 +36,7 @@ ghc \ "$root/src/Main.hs" \ -Wall \ -fno-warn-name-shadowing \ + -XRecordWildCards \ -i"$root/src" \ -rtsopts \ -with-rtsopts=-I0 \ diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 684e89e..fc0744d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -108,13 +108,13 @@ executable ghc-shake , Way default-language: Haskell2010 + default-extensions: RecordWildCards other-extensions: DeriveDataTypeable , DeriveGeneric , FlexibleInstances , GeneralizedNewtypeDeriving , LambdaCase , OverloadedStrings - , RecordWildCards , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5f8f583..c69298e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, applyPatch, fixFile, runConfigure, runMake, diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index f62c644..c9a1bba 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Compile (compilePackage) where import Base diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index f47e8d0..0e27699 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Data (buildPackageData) where import qualified System.Directory as IO diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 330c821..f2a2141 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Dependencies (buildPackageDependencies) where import Development.Shake.Util (parseMakefile) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index e3b0e7d..7e98e27 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Documentation (buildPackageDocumentation) where import Base diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index c6d92a5..980139f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Library ( buildPackageLibrary, buildPackageGhciLibrary, cSources, hSources ) where diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 6eaa821..af6023d 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Program (buildProgram) where import Data.Char diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 85fac80..bddce8a 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Register (registerPackage) where import Base From git at git.haskell.org Fri Oct 27 00:04:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add iosHost function. (e7fc568) Message-ID: <20171027000425.BA6703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7fc5681234fb897f2014194c81b64450811c543/ghc >--------------------------------------------------------------- commit e7fc5681234fb897f2014194c81b64450811c543 Author: Andrey Mokhov Date: Sat Jan 9 14:33:51 2016 +0000 Add iosHost function. See #138. [skip ci] >--------------------------------------------------------------- e7fc5681234fb897f2014194c81b64450811c543 src/Oracles/Config/Setting.hs | 11 +++++++---- src/Settings/Packages.hs | 2 +- 2 files changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 58f508b..0047f03 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -1,9 +1,9 @@ module Oracles.Config.Setting ( Setting (..), SettingList (..), setting, settingList, getSetting, getSettingList, - anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, windowsHost, + anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, - ghcCanonVersion, cmdLineLengthLimit, osxHost + ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost ) where import Control.Monad.Trans.Reader @@ -122,12 +122,15 @@ anyTargetArch = matchSetting TargetArch anyHostOs :: [String] -> Action Bool anyHostOs = matchSetting HostOs -windowsHost :: Action Bool -windowsHost = anyHostOs ["mingw32", "cygwin32"] +iosHost :: Action Bool +iosHost = anyHostOs ["ios"] osxHost :: Action Bool osxHost = anyHostOs ["darwin"] +windowsHost :: Action Bool +windowsHost = anyHostOs ["mingw32", "cygwin32"] + ghcWithInterpreter :: Action Bool ghcWithInterpreter = do goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "solaris2" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 3f4f661..4d2f76c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -26,7 +26,7 @@ packagesStage0 = mconcat -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] , stage0 ? windowsHost ? append [touchy] - , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] + , notM windowsHost ? iosHost ? append [terminfo] ] packagesStage1 :: Packages packagesStage1 = mconcat From git at git.haskell.org Fri Oct 27 00:04:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add haddock path to cfg/system.config.in. (4e5ab6b) Message-ID: <20171027000426.839633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e5ab6b936082f0c9718447b6dd143ec3785d67b/ghc >--------------------------------------------------------------- commit 4e5ab6b936082f0c9718447b6dd143ec3785d67b Author: Andrey Mokhov Date: Wed Aug 19 02:35:04 2015 +0100 Add haddock path to cfg/system.config.in. >--------------------------------------------------------------- 4e5ab6b936082f0c9718447b6dd143ec3785d67b cfg/system.config.in | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 029a81a..a274e84 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -5,18 +5,20 @@ #=================== system-ghc = @WithGhc@ +system-gcc = @CC_STAGE0@ +system-ghc-pkg = @GhcPkgCmd@ +gcc = @WhatGccIsCalled@ + ghc-stage1 = @hardtop@/inplace/bin/ghc-stage1 ghc-stage2 = @hardtop@/inplace/bin/ghc-stage2 ghc-stage3 = @hardtop@/inplace/bin/ghc-stage3 -system-ghc-pkg = @GhcPkgCmd@ ghc-pkg = @hardtop@/inplace/bin/ghc-pkg -system-gcc = @CC_STAGE0@ -gcc = @WhatGccIsCalled@ - ghc-cabal = @hardtop@/inplace/bin/ghc-cabal +haddock = @hardtop@/inplace/bin/haddock + ld = @LdCmd@ ar = @ArCmd@ alex = @AlexCmd@ From git at git.haskell.org Fri Oct 27 00:04:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant newCache. (57c623d) Message-ID: <20171027000427.F05A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57c623dbc3e8eed480ed5b0812aa8282bea22064/ghc >--------------------------------------------------------------- commit 57c623dbc3e8eed480ed5b0812aa8282bea22064 Author: Andrey Mokhov Date: Fri Feb 19 00:30:00 2016 +0000 Drop redundant newCache. See #210. >--------------------------------------------------------------- 57c623dbc3e8eed480ed5b0812aa8282bea22064 src/Oracles/ModuleFiles.hs | 7 ++----- 1 file changed, 2 insertions(+), 5 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 391990e..d8b1ae7 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -38,8 +38,8 @@ haskellModuleFiles stage pkg = do return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) moduleFilesOracle :: Rules () -moduleFilesOracle = do - answer <- newCache $ \(modules, dirs) -> do +moduleFilesOracle = void $ + addOracle $ \(ModuleFilesKey (modules, dirs)) -> do let decodedPairs = map decodeModule modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedPairs @@ -55,6 +55,3 @@ moduleFilesOracle = do return (map (fullDir -/-) found, mDir) return $ sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] - - _ <- addOracle $ \(ModuleFilesKey query) -> answer query - return () From git at git.haskell.org Fri Oct 27 00:04:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix iosHost condition. (f8660c8) Message-ID: <20171027000429.306A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8660c804c827eb8c0f9f29af2de57e5eca908f1/ghc >--------------------------------------------------------------- commit f8660c804c827eb8c0f9f29af2de57e5eca908f1 Author: Andrey Mokhov Date: Sat Jan 9 14:35:43 2016 +0000 Fix iosHost condition. See #138. [skip ci] >--------------------------------------------------------------- f8660c804c827eb8c0f9f29af2de57e5eca908f1 src/Settings/Packages.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 4d2f76c..b7e2dac 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -26,7 +26,7 @@ packagesStage0 = mconcat -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] , stage0 ? windowsHost ? append [touchy] - , notM windowsHost ? iosHost ? append [terminfo] ] + , notM windowsHost ? notM iosHost ? append [terminfo] ] packagesStage1 :: Packages packagesStage1 = mconcat From git at git.haskell.org Fri Oct 27 00:04:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddock builder. (30687f3) Message-ID: <20171027000429.E53FD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30687f35a0f3ec3cdd488f2f55c0eaf626211ea2/ghc >--------------------------------------------------------------- commit 30687f35a0f3ec3cdd488f2f55c0eaf626211ea2 Author: Andrey Mokhov Date: Wed Aug 19 02:35:56 2015 +0100 Add Haddock builder. >--------------------------------------------------------------- 30687f35a0f3ec3cdd488f2f55c0eaf626211ea2 src/Builder.hs | 42 ++++++++++++++++++++++++------------------ 1 file changed, 24 insertions(+), 18 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index b175fac..ac184d3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -19,12 +19,13 @@ import GHC.Generics -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg -- GhcPkg StageN, N > 0, is the one built on stage 0 (TODO: need only Stage1?) --- TODO: add Cpp and Haddock builders +-- TODO: add Cpp builders -- TODO: rename Gcc to Cc? data Builder = Ar | Ld | Alex | Happy + | Haddock | HsColour | GhcCabal | Gcc Stage @@ -32,28 +33,33 @@ data Builder = Ar | GhcM Stage | GccM Stage | GhcPkg Stage + | GhcCabalHsColour deriving (Show, Eq, Generic) -- Configuration files refer to Builders as follows: +-- TODO: determine paths to utils without looking up configuration files builderKey :: Builder -> String builderKey builder = case builder of - Ar -> "ar" - Ld -> "ld" - Alex -> "alex" - Happy -> "happy" - HsColour -> "hscolour" - GhcCabal -> "ghc-cabal" - Ghc Stage0 -> "system-ghc" - Ghc Stage1 -> "ghc-stage1" - Ghc Stage2 -> "ghc-stage2" - Ghc Stage3 -> "ghc-stage3" - Gcc Stage0 -> "system-gcc" - Gcc _ -> "gcc" - GhcPkg Stage0 -> "system-ghc-pkg" - GhcPkg _ -> "ghc-pkg" - -- GhcM is currently a synonym for Ghc (to be called with -M flag) - GhcM stage -> builderKey $ Ghc stage - GccM stage -> builderKey $ Gcc stage + Ar -> "ar" + Ld -> "ld" + Alex -> "alex" + Happy -> "happy" + Haddock -> "haddock" + HsColour -> "hscolour" + GhcCabal -> "ghc-cabal" + Ghc Stage0 -> "system-ghc" + Ghc Stage1 -> "ghc-stage1" + Ghc Stage2 -> "ghc-stage2" + Ghc Stage3 -> "ghc-stage3" + Gcc Stage0 -> "system-gcc" + Gcc _ -> "gcc" + GhcPkg Stage0 -> "system-ghc-pkg" + GhcPkg _ -> "ghc-pkg" + -- GhcM/GccM are synonyms for Ghc/Gcc (called with -M and -MM flags) + GhcM stage -> builderKey $ Ghc stage + GccM stage -> builderKey $ Gcc stage + -- GhcCabalHsColour is a synonym for GhcCabal (called in hscolour mode) + GhcCabalHsColour -> builderKey $ GhcCabal builderPath :: Builder -> Action String builderPath builder = do From git at git.haskell.org Fri Oct 27 00:04:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (e1d05c5) Message-ID: <20171027000431.A3DB53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1d05c561f1ab7d939dc4decf5ca143a3bd07a5e/ghc >--------------------------------------------------------------- commit e1d05c561f1ab7d939dc4decf5ca143a3bd07a5e Author: Andrey Mokhov Date: Fri Feb 19 00:35:44 2016 +0000 Add comments. See #210. >--------------------------------------------------------------- e1d05c561f1ab7d939dc4decf5ca143a3bd07a5e src/Oracles/ModuleFiles.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index d8b1ae7..b831f76 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -37,6 +37,16 @@ haskellModuleFiles stage pkg = do return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) +-- | This is an important oracle whose role is to find and cache module source +-- files. More specifically, it takes a list of module names @modules@ and a +-- list of directories @dirs@ as arguments, and computes a sorted list of pairs +-- of the form @(A.B.C, dir/A/B/C.extension)@, such that @A.B.C@ belongs to +-- @modules@, @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists. +-- For example, for 'compiler' package given +-- @modules = ["CodeGen.Platform.ARM", "Lexer"]@, and +-- @dirs = ["codeGen", "parser"]@, it produces +-- @[("CodeGen.Platform.ARM", "codeGen/CodeGen/Platform/ARM.hs"), +-- ("Lexer", "parser/Lexer.x")]@. moduleFilesOracle :: Rules () moduleFilesOracle = void $ addOracle $ \(ModuleFilesKey (modules, dirs)) -> do From git at git.haskell.org Fri Oct 27 00:04:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #142 from quchen/clone-from-github (a012ac6) Message-ID: <20171027000432.B6AFF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a012ac65bc12d0ec8afb6bc746eac1246e8da9ea/ghc >--------------------------------------------------------------- commit a012ac65bc12d0ec8afb6bc746eac1246e8da9ea Merge: f8660c8 c43d07d Author: Andrey Mokhov Date: Sat Jan 9 14:40:58 2016 +0000 Merge pull request #142 from quchen/clone-from-github CI: Shallow clone GHC from Github instead of Haskell.org >--------------------------------------------------------------- a012ac65bc12d0ec8afb6bc746eac1246e8da9ea .travis.yml | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:04:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add HiddenModules key to PackageData.hs. (3d65807) Message-ID: <20171027000433.6A9033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d6580728cc485bb8e16d4ee27ed04a8ec8c743e/ghc >--------------------------------------------------------------- commit 3d6580728cc485bb8e16d4ee27ed04a8ec8c743e Author: Andrey Mokhov Date: Wed Aug 19 02:36:33 2015 +0100 Add HiddenModules key to PackageData.hs. >--------------------------------------------------------------- 3d6580728cc485bb8e16d4ee27ed04a8ec8c743e src/Oracles/PackageData.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index de9db7c..4097ac1 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -26,6 +26,7 @@ data PackageData = Version FilePath | BuildGhciLib FilePath data PackageDataList = Modules FilePath + | HiddenModules FilePath | SrcDirs FilePath | IncludeDirs FilePath | Deps FilePath @@ -66,6 +67,7 @@ pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = do let (key, path, defaultValue) = case packageData of Modules path -> ("MODULES" , path, "" ) + HiddenModules path -> ("HIDDEN_MODULES" , path, "" ) SrcDirs path -> ("HS_SRC_DIRS" , path, ".") IncludeDirs path -> ("INCLUDE_DIRS" , path, ".") Deps path -> ("DEPS" , path, "" ) From git at git.haskell.org Fri Oct 27 00:04:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor oracles, drop redundant newCache. (13ad050) Message-ID: <20171027000435.19DA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13ad050070d32c5c6267af8fba60125af878147c/ghc >--------------------------------------------------------------- commit 13ad050070d32c5c6267af8fba60125af878147c Author: Andrey Mokhov Date: Fri Feb 19 01:15:10 2016 +0000 Refactor oracles, drop redundant newCache. >--------------------------------------------------------------- 13ad050070d32c5c6267af8fba60125af878147c src/Oracles/ArgsHash.hs | 5 ++--- src/Oracles/Dependencies.hs | 1 - src/Oracles/LookupInPath.hs | 12 +++++------- src/Oracles/PackageData.hs | 5 ++--- src/Oracles/PackageDb.hs | 5 ++--- src/Oracles/PackageDeps.hs | 8 ++++---- src/Oracles/WindowsPath.hs | 10 ++++------ 7 files changed, 19 insertions(+), 27 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 796e753..aec0dc9 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -29,6 +29,5 @@ checkArgsHash target = when trackBuildSystem $ do -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () -argsHashOracle = do - _ <- addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs - return () +argsHashOracle = void $ + addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 8895758..b34535b 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -33,6 +33,5 @@ dependenciesOracle = do putOracle $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return . Map.fromList $ map (\(x:xs) -> (x, xs)) contents - _ <- addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file return () diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 2f6e713..0ea03fd 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -15,13 +15,11 @@ lookupInPath name | otherwise = return name lookupInPathOracle :: Rules () -lookupInPathOracle = do - answer <- newCache $ \query -> do - maybePath <- liftIO $ findExecutable query +lookupInPathOracle = void $ + addOracle $ \(LookupInPath name) -> do + maybePath <- liftIO $ findExecutable name path <- case maybePath of Just value -> return $ unifyPath value - Nothing -> putError $ "Cannot find executable '" ++ query ++ "'." - putOracle $ "Executable found: " ++ query ++ " => " ++ path + Nothing -> putError $ "Cannot find executable '" ++ name ++ "'." + putOracle $ "Executable found: " ++ name ++ " => " ++ path return path - _ <- addOracle $ \(LookupInPath query) -> answer query - return () diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index d176839..ba3e205 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -86,10 +86,9 @@ pkgDataList packageData = fmap (map unquote . words) $ case packageData of -- Oracle for 'package-data.mk' files packageDataOracle :: Rules () packageDataOracle = do - pkgDataContents <- newCache $ \file -> do + keys <- newCache $ \file -> do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - _ <- addOracle $ \(PackageDataKey (file, key)) -> - Map.lookup key <$> pkgDataContents file + _ <- addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file return () diff --git a/src/Oracles/PackageDb.hs b/src/Oracles/PackageDb.hs index 97a2a5c..b644989 100644 --- a/src/Oracles/PackageDb.hs +++ b/src/Oracles/PackageDb.hs @@ -12,12 +12,11 @@ import Settings.Paths import Target packageDbOracle :: Rules () -packageDbOracle = do - _ <- addOracle $ \(PackageDbKey stage) -> do +packageDbOracle = void $ + addOracle $ \(PackageDbKey stage) -> do let dir = packageDbDirectory stage file = dir -/- "package.cache" unlessM (liftIO $ IO.doesFileExist file) $ do removeDirectoryIfExists dir build $ Target (vanillaContext stage ghcPkg) (GhcPkg stage) [] [dir] putSuccess $ "| Successfully initialised " ++ dir - return () diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 94cdd91..6a5f7dd 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -8,9 +8,9 @@ import Package newtype PackageDepsKey = PackageDepsKey PackageName deriving (Show, Typeable, Eq, Hashable, Binary, NFData) --- packageDeps name is an action that given a package looks up its dependencies --- in Base.packageDependencies file. The dependencies need to be computed by --- scanning package cabal files (see Rules.Cabal). +-- @packageDeps name@ is an action that given a 'Package' looks up its +-- dependencies in 'Base.packageDependencies' file. The dependencies need to be +-- computed by scanning package cabal files (see Rules.Cabal). packageDeps :: Package -> Action [PackageName] packageDeps pkg = do res <- askOracle . PackageDepsKey . pkgName $ pkg @@ -23,6 +23,6 @@ packageDepsOracle = do putOracle $ "Reading package dependencies..." contents <- readFileLines packageDependencies return . Map.fromList $ - [ (head ps, tail ps) | line <- contents, let ps = map PackageName $ words line ] + [ (p, ps) | line <- contents, let p:ps = map PackageName $ words line ] _ <- addOracle $ \(PackageDepsKey pkg) -> Map.lookup pkg <$> deps () return () diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index 3cbf1f1..a0343fb 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -15,7 +15,7 @@ topDirectory = do ghcSourcePath <- setting GhcSourcePath fixAbsolutePathOnWindows ghcSourcePath --- Fix an absolute path on Windows: +-- | Fix an absolute path on Windows: -- * "/c/" => "C:/" -- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" fixAbsolutePathOnWindows :: FilePath -> Action FilePath @@ -29,13 +29,11 @@ fixAbsolutePathOnWindows path = do else return path --- Detecting path mapping on Windows. This is slow and requires caching. +-- | Compute path mapping on Windows. This is slow and requires caching. windowsPathOracle :: Rules () -windowsPathOracle = do - answer <- newCache $ \path -> do +windowsPathOracle = void $ + addOracle $ \(WindowsPath path) -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] let windowsPath = unifyPath $ dropWhileEnd isSpace out putOracle $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath - _ <- addOracle $ \(WindowsPath query) -> answer query - return () From git at git.haskell.org Fri Oct 27 00:04:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unset GHC_PACKAGE_PATH before building. (6200ac8) Message-ID: <20171027000436.341E23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6200ac8589190682a03b32258686a9b452908a9f/ghc >--------------------------------------------------------------- commit 6200ac8589190682a03b32258686a9b452908a9f Author: Andrey Mokhov Date: Sat Jan 9 16:33:13 2016 +0000 Unset GHC_PACKAGE_PATH before building. See #110. [skip ci] >--------------------------------------------------------------- 6200ac8589190682a03b32258686a9b452908a9f .appveyor.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 99196db..9cb8bcb 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,5 +23,6 @@ install: - happy --version build_script: + - unset GHC_PACKAGE_PATH - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress From git at git.haskell.org Fri Oct 27 00:04:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add haddock build targets. (d811225) Message-ID: <20171027000436.DBC913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d811225729618537302bde9cba2d591a2dd54ef4/ghc >--------------------------------------------------------------- commit d811225729618537302bde9cba2d591a2dd54ef4 Author: Andrey Mokhov Date: Wed Aug 19 02:37:30 2015 +0100 Add haddock build targets. >--------------------------------------------------------------- d811225729618537302bde9cba2d591a2dd54ef4 src/Rules.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Rules.hs b/src/Rules.hs index 43f5922..65ae2e4 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -14,6 +14,7 @@ import Rules.Package import Rules.Oracles import Rules.Resources import Settings.Ways +import Settings.User import Settings.Util import Settings.Packages import Settings.TargetDirectory @@ -28,15 +29,17 @@ generateTargets = action $ do buildPath = targetPath stage pkg -/- "build" buildGhciLib <- interpret target $ getPkgData BuildGhciLib pkgKey <- interpret target $ getPkgData PackageKey + buildHaddock <- interpret target $ Settings.User.buildHaddock let ghciLib = [ buildPath -/- "HS" ++ pkgKey <.> "o" | buildGhciLib == "YES" && stage /= Stage0 ] + haddock = [ pkgHaddockPath pkg | buildHaddock ] ways <- interpret target getWays libs <- forM ways $ \way -> do extension <- libsuf way return $ buildPath -/- "libHS" ++ pkgKey <.> extension - return $ ghciLib ++ libs + return $ ghciLib ++ libs ++ haddock need $ reverse targets From git at git.haskell.org Fri Oct 27 00:04:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor paths using Context. (badd551) Message-ID: <20171027000438.A16F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/badd551338ac11ef851d8882b2496de6c31d004f/ghc >--------------------------------------------------------------- commit badd551338ac11ef851d8882b2496de6c31d004f Author: Andrey Mokhov Date: Fri Feb 19 02:49:11 2016 +0000 Refactor paths using Context. See #207. >--------------------------------------------------------------- badd551338ac11ef851d8882b2496de6c31d004f src/Builder.hs | 31 +++++++++++++------------ src/Expression.hs | 18 +++++++++------ src/GHC.hs | 36 ++++++++++++++++------------- src/Oracles/ModuleFiles.hs | 20 ++++++++-------- src/Rules.hs | 12 +++++----- src/Rules/Clean.hs | 3 ++- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 30 ++++++++++++------------ src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 6 ++--- src/Rules/Generate.hs | 23 +++++++++++-------- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Rules/Program.hs | 12 +++++----- src/Rules/Register.hs | 10 ++++---- src/Settings.hs | 22 ++++++++---------- src/Settings/Builders/Common.hs | 4 ++-- src/Settings/Builders/Ghc.hs | 11 +++++---- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Builders/GhcPkg.hs | 6 ++--- src/Settings/Builders/Haddock.hs | 6 ++--- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/Hp2ps.hs | 2 +- src/Settings/Packages/Rts.hs | 6 ++--- src/Settings/Packages/Touchy.hs | 2 +- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/Paths.hs | 48 ++++++++++++++++++++------------------- 32 files changed, 177 insertions(+), 161 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 badd551338ac11ef851d8882b2496de6c31d004f From git at git.haskell.org Fri Oct 27 00:04:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move chunksOfSize to Settings/Builders/Ar.hs, add comments. (5e3f91f) Message-ID: <20171027000440.09CDD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e3f91f9d050c91f8fd842b9548093c0d8d8e532/ghc >--------------------------------------------------------------- commit 5e3f91f9d050c91f8fd842b9548093c0d8d8e532 Author: Andrey Mokhov Date: Sat Jan 9 16:57:49 2016 +0000 Move chunksOfSize to Settings/Builders/Ar.hs, add comments. See #130. [skip ci] >--------------------------------------------------------------- 5e3f91f9d050c91f8fd842b9548093c0d8d8e532 src/Base.hs | 19 +++---------------- src/Settings/Builders/Ar.hs | 28 ++++++++++++++++++++++++---- 2 files changed, 27 insertions(+), 20 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fb33907..65a2d1d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,9 +22,9 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, renderBox, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, replaceEq, quote, chunksOfSize, - replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), - versionToInt, removeFileIfExists, removeDirectoryIfExists + bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, + decodeModule, encodeModule, unifyPath, (-/-), versionToInt, + removeFileIfExists, removeDirectoryIfExists ) where import Control.Applicative @@ -90,19 +90,6 @@ replaceSeparators = replaceWhen isPathSeparator replaceWhen :: (a -> Bool) -> a -> [a] -> [a] replaceWhen p to = map (\from -> if p from then to else from) --- | @chunksOfSize size strings@ splits a given list of strings into chunks not --- exceeding the given @size at . -chunksOfSize :: Int -> [String] -> [[String]] -chunksOfSize _ [] = [] -chunksOfSize size strings = reverse chunk : chunksOfSize size rest - where - (chunk, rest) = go [] 0 strings - go res _ [] = (res, []) - go res chunkSize (s:ss) = - if newSize > size then (res, s:ss) else go (s:res) newSize ss - where - newSize = chunkSize + length s - -- | Add quotes to a String quote :: String -> String quote s = "\"" ++ s ++ "\"" diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 18ce802..86f4310 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -5,6 +5,7 @@ import Expression import Oracles import Predicates (builder) +-- | Default arguments for 'Ar' builder arBuilderArgs :: Args arBuilderArgs = builder Ar ? mconcat [ arg "q" , arg =<< getOutput @@ -15,10 +16,15 @@ arBuilderArgs = builder Ar ? mconcat [ arg "q" arFlagsCount :: Int arFlagsCount = 2 --- Ar needs to be invoked in a special way: we pass the list of files to be --- archived via a temporary file as otherwise Ar (or rather Windows command --- line) chokes up. Alternatively, we split argument list into chunks and call --- ar multiple times (when passing files via a separate file is not supported). +-- | Invoke 'Ar' builder given a path to it and a list of arguments. Take care +-- not to exceed the limit on command line length, which differs across +-- supported operating systems (see 'cmdLineLengthLimit'). 'Ar' needs to be +-- handled in a special way because we sometimes need to archive __a lot__ of +-- files (in Cabal package, for example, command line length can reach 2MB!). +-- To work around the limit on the command line length we pass the list of files +-- to be archived via a temporary file, or alternatively, we split argument list +-- into chunks and call 'Ar' multiple times (when passing arguments via a +-- temporary file is not supported). arCmd :: FilePath -> [String] -> Action () arCmd path argList = do arSupportsAtFile <- flag ArSupportsAtFile @@ -38,3 +44,17 @@ useSuccessiveInvocations path flagArgs fileArgs = do maxChunk <- cmdLineLengthLimit forM_ (chunksOfSize maxChunk fileArgs) $ \argsChunk -> unit . cmd [path] $ flagArgs ++ argsChunk + +-- | @chunksOfSize size strings@ splits a given list of strings into chunks not +-- exceeding the given @size at . +chunksOfSize :: Int -> [String] -> [[String]] +chunksOfSize _ [] = [] +chunksOfSize size strings = reverse chunk : chunksOfSize size rest + where + (chunk, rest) = go [] 0 strings + go res _ [] = (res, []) + go res chunkSize (s:ss) = + if newSize > size then (res, s:ss) else go (s:res) newSize ss + where + newSize = chunkSize + length s + From git at git.haskell.org Fri Oct 27 00:04:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add pkgHaddockPath for finding haddock files. (0aedb12) Message-ID: <20171027000440.E7B9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0aedb12d7790c167f3550b59c3303f8874c8af3c/ghc >--------------------------------------------------------------- commit 0aedb12d7790c167f3550b59c3303f8874c8af3c Author: Andrey Mokhov Date: Wed Aug 19 02:38:31 2015 +0100 Add pkgHaddockPath for finding haddock files. >--------------------------------------------------------------- 0aedb12d7790c167f3550b59c3303f8874c8af3c src/Settings/TargetDirectory.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 0844d14..10f0f67 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,7 +1,8 @@ module Settings.TargetDirectory ( - targetDirectory, targetPath + targetDirectory, targetPath, pkgHaddockPath ) where +import Base import Util import Stage import Package @@ -14,3 +15,9 @@ targetDirectory = userTargetDirectory -- Path to the target directory from GHC source root targetPath :: Stage -> Package -> FilePath targetPath stage pkg = pkgPath pkg -/- targetDirectory stage pkg + +-- Relative path to a package haddock file, e.g.: +-- "libraries/array/dist-install/doc/html/array/array.haddock" +pkgHaddockPath :: Package -> FilePath +pkgHaddockPath pkg @ (Package name _) = + targetPath Stage1 pkg -/- "doc/html" -/- name -/- name <.> "haddock" From git at git.haskell.org Fri Oct 27 00:04:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor moduleFilesOracle, work in progress. (903ab6c) Message-ID: <20171027000442.966F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/903ab6c7579627c52c07af7f9f8965a864af0187/ghc >--------------------------------------------------------------- commit 903ab6c7579627c52c07af7f9f8965a864af0187 Author: Andrey Mokhov Date: Fri Feb 19 18:31:30 2016 +0000 Refactor moduleFilesOracle, work in progress. See #210. >--------------------------------------------------------------- 903ab6c7579627c52c07af7f9f8965a864af0187 src/Oracles/ModuleFiles.hs | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 67d68f3..a5e40ed 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -7,7 +7,7 @@ import Oracles.PackageData import Package import Settings.Paths -newtype ModuleFilesKey = ModuleFilesKey ([String], [FilePath]) +newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) moduleFiles :: Context -> Action [FilePath] @@ -16,7 +16,7 @@ moduleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (modules, dirs) + found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (dirs, modules) return $ map snd found haskellModuleFiles :: Context -> Action ([FilePath], [String]) @@ -27,8 +27,8 @@ haskellModuleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - foundSrcDirs <- askOracle $ ModuleFilesKey (modules, dirs ) - foundAutogen <- askOracle $ ModuleFilesKey (modules, [autogen]) + foundSrcDirs <- askOracle $ ModuleFilesKey (dirs , modules) + foundAutogen <- askOracle $ ModuleFilesKey ([autogen], modules) let found = foundSrcDirs ++ foundAutogen missingMods = modules `minusOrd` (sort $ map fst found) @@ -38,18 +38,18 @@ haskellModuleFiles context @ (Context {..}) = do return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) -- | This is an important oracle whose role is to find and cache module source --- files. More specifically, it takes a list of module names @modules@ and a --- list of directories @dirs@ as arguments, and computes a sorted list of pairs --- of the form @(A.B.C, dir/A/B/C.extension)@, such that @A.B.C@ belongs to --- @modules@, @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists. --- For example, for 'compiler' package given --- @modules = ["CodeGen.Platform.ARM", "Lexer"]@, and --- @dirs = ["codeGen", "parser"]@, it produces --- @[("CodeGen.Platform.ARM", "codeGen/CodeGen/Platform/ARM.hs"), --- ("Lexer", "parser/Lexer.x")]@. +-- files. More specifically, it takes a list of directories @dirs@ and a sorted +-- list of module names @modules@ as arguments, and for each module, e.g. +-- @A.B.C@, returns a FilePath of the form @dir/A/B/C.extension@, such that +-- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or Nothing +-- if there is no such file. If more than one matching file is found an error is +-- raised. For example, for the 'compiler' package given +-- @dirs = ["codeGen", "parser"]@, and +-- @modules = ["CodeGen.Platform.ARM", "Lexer", "Missing.Module"]@, it produces +-- @[Just "codeGen/CodeGen/Platform/ARM.hs", Just "parser/Lexer.x", Nothing]@. moduleFilesOracle :: Rules () moduleFilesOracle = void $ - addOracle $ \(ModuleFilesKey (modules, dirs)) -> do + addOracle $ \(ModuleFilesKey (dirs, modules)) -> do let decodedPairs = map decodeModule modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedPairs From git at git.haskell.org Fri Oct 27 00:04:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (2nd try). (901105e) Message-ID: <20171027000444.1C1A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/901105e56574df051615b59db337bb7ec856ef9a/ghc >--------------------------------------------------------------- commit 901105e56574df051615b59db337bb7ec856ef9a Author: Andrey Mokhov Date: Sat Jan 9 17:06:20 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (2nd try). See #110. [skip ci] >--------------------------------------------------------------- 901105e56574df051615b59db337bb7ec856ef9a .appveyor.yml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 9cb8bcb..e382140 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,6 +23,8 @@ install: - happy --version build_script: - - unset GHC_PACKAGE_PATH + - set GHC_PACKAGE_PATH + - set GHC_PACKAGE_PATH= + - set GHC_PACKAGE_PATH - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat -j --no-progress From git at git.haskell.org Fri Oct 27 00:04:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build haddock only in Stage1. (2520d7f) Message-ID: <20171027000444.B041F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2520d7fdb98c537591653f0f753398dd5e58cdb5/ghc >--------------------------------------------------------------- commit 2520d7fdb98c537591653f0f753398dd5e58cdb5 Author: Andrey Mokhov Date: Wed Aug 19 02:39:23 2015 +0100 Build haddock only in Stage1. >--------------------------------------------------------------- 2520d7fdb98c537591653f0f753398dd5e58cdb5 src/Settings/User.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 1ca003b..3646994 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -48,7 +48,7 @@ integerLibrary = integerGmp2 -- up a little (particularly zero builds). -- WARNING: a complete rebuild is required when changing this setting. trackBuildSystem :: Bool -trackBuildSystem = False +trackBuildSystem = True validating :: Bool validating = False @@ -66,4 +66,4 @@ laxDependencies :: Bool laxDependencies = False buildHaddock :: Predicate -buildHaddock = return True +buildHaddock = stage Stage1 From git at git.haskell.org Fri Oct 27 00:04:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Document and test encode/decodeModule. (5e32c91) Message-ID: <20171027000446.281AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e32c9147ba23b886ae6154200fc7961481f4bd9/ghc >--------------------------------------------------------------- commit 5e32c9147ba23b886ae6154200fc7961481f4bd9 Author: Andrey Mokhov Date: Sat Feb 20 22:40:41 2016 +0000 Document and test encode/decodeModule. See #197, #210. >--------------------------------------------------------------- 5e32c9147ba23b886ae6154200fc7961481f4bd9 src/Base.hs | 7 +++++-- src/Rules/Selftest.hs | 14 ++++++++++++++ 2 files changed, 19 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7d63fa0..7217834 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -98,13 +98,16 @@ versionToInt s = major * 1000 + minor * 10 + patch -- | Given a module name extract the directory and file name, e.g.: -- --- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +-- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") +-- > decodeModule "Prelude" == ("./", "Prelude") decodeModule :: String -> (FilePath, String) decodeModule = splitFileName . replaceEq '.' '/' -- | Given the directory and file name find the corresponding module name, e.g.: -- --- > encodeModule "Data/Functor/" "Identity.hs" = "Data.Functor.Identity" +-- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" +-- > encodeModule "./" "Prelude" == "Prelude" +-- > uncurry encodeModule (decodeModule name) == name encodeModule :: FilePath -> String -> String encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 70a4023..c156b44 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -24,6 +24,7 @@ selftestRules = testWays testChunksOfSize testMatchVersionedFilePath + testModuleNames testWays :: Action () testWays = do @@ -54,3 +55,16 @@ testMatchVersionedFilePath = do matchVersionedFilePath prefix suffix (prefix ++ version ++ suffix) where versions = listOf . elements $ '-' : '.' : ['0'..'9'] + +testModuleNames :: Action () +testModuleNames = do + putBuild $ "==== Encode/decode module name" + test $ encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" + test $ encodeModule "./" "Prelude" == "Prelude" + + test $ decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") + test $ decodeModule "Prelude" == ("./", "Prelude") + + test $ forAll names $ \n -> uncurry encodeModule (decodeModule n) == n + where + names = intercalate "." <$> listOf1 (listOf1 $ elements "abcABC123_'") From git at git.haskell.org Fri Oct 27 00:04:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on ghc-split only when building with split objects. (9580d01) Message-ID: <20171027000447.DD8DF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9580d01895bb231dd38f8000eb7ad1929ee75962/ghc >--------------------------------------------------------------- commit 9580d01895bb231dd38f8000eb7ad1929ee75962 Author: Andrey Mokhov Date: Sat Jan 9 17:09:03 2016 +0000 Depend on ghc-split only when building with split objects. See #81. [skip ci] >--------------------------------------------------------------- 9580d01895bb231dd38f8000eb7ad1929ee75962 src/Rules/Generate.hs | 7 ++++--- src/Settings/Builders/Ghc.hs | 7 ++++++- 2 files changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 2b2962b..b7a360a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -42,8 +42,10 @@ includesDependencies = ("includes" -/-) <$> , "ghcversion.h" ] defaultDependencies :: [FilePath] -defaultDependencies = - includesDependencies ++ libffiDependencies ++ integerGmpDependencies +defaultDependencies = concat + [ includesDependencies + , libffiDependencies + , integerGmpDependencies ] ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> @@ -77,7 +79,6 @@ compilerDependencies stage = , "primop-vector-tys-exports.hs-incl" , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] - ++ ["inplace/lib/bin/ghc-split"] generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 9a07fc2..bc37a04 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -26,7 +26,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , notStage0 ? arg "-O2" , arg "-Wall" , arg "-fwarn-tabs" - , splitObjects ? arg "-split-objs" + , splitObjectsArgs , not buildObj ? arg "-no-auto-link-packages" , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ] , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] @@ -34,6 +34,11 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , append =<< getInputs , arg "-o", arg =<< getOutput ] +splitObjectsArgs :: Args +splitObjectsArgs = splitObjects ? do + lift $ need ["inplace/lib/bin/ghc-split"] + arg "-split-objs" + ghcMBuilderArgs :: Args ghcMBuilderArgs = stagedBuilder GhcM ? do ways <- getWays From git at git.haskell.org Fri Oct 27 00:04:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Collect all arguments for haddock. (b16ec20) Message-ID: <20171027000448.6A3E23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b16ec20251a2f1cee03156062be31fbad0b775dd/ghc >--------------------------------------------------------------- commit b16ec20251a2f1cee03156062be31fbad0b775dd Author: Andrey Mokhov Date: Wed Aug 19 02:41:39 2015 +0100 Collect all arguments for haddock. >--------------------------------------------------------------- b16ec20251a2f1cee03156062be31fbad0b775dd src/Settings/Args.hs | 3 ++ src/Settings/Builders/Ghc.hs | 97 +++++++++++++++++++-------------------- src/Settings/Builders/GhcCabal.hs | 16 +++++-- src/Settings/Builders/Haddock.hs | 69 ++++++++++++++++++++++++++++ src/Settings/Util.hs | 9 ++-- 5 files changed, 137 insertions(+), 57 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b16ec20251a2f1cee03156062be31fbad0b775dd From git at git.haskell.org Fri Oct 27 00:04:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add lookupAll and test it. (e054479) Message-ID: <20171027000449.A4D143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e0544796443fa3f220ac77f68891b6c4fc0f09bb/ghc >--------------------------------------------------------------- commit e0544796443fa3f220ac77f68891b6c4fc0f09bb Author: Andrey Mokhov Date: Sun Feb 21 00:01:08 2016 +0000 Add lookupAll and test it. See #210. >--------------------------------------------------------------- e0544796443fa3f220ac77f68891b6c4fc0f09bb src/Base.hs | 22 ++++++++++++++++++---- src/Rules/Selftest.hs | 15 +++++++++++++++ 2 files changed, 33 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7217834..324feb8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,7 +23,7 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, -- * Miscellaneous utilities - minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, + minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath ) where @@ -165,9 +165,23 @@ intersectOrd cmp = loop loop [] _ = [] loop _ [] = [] loop (x:xs) (y:ys) = case cmp x y of - LT -> loop xs (y:ys) - EQ -> x : loop xs ys - GT -> loop (x:xs) ys + LT -> loop xs (y:ys) + EQ -> x : loop xs ys + GT -> loop (x:xs) ys + +-- | Lookup all elements of a given sorted list in a given sorted dictionary. +-- @lookupAll list dict@ is equivalent to @map (flip lookup dict) list@ but has +-- linear complexity O(|list| + |dist|) instead of quadratic O(|list| * |dict|). +-- +-- > lookupAll ["b", "c"] [("a", 1), ("c", 3), ("d", 4)] == [Nothing, Just 3] +-- > list & dict are sorted: lookupAll list dict == map (flip lookup dict) list +lookupAll :: Ord a => [a] -> [(a, b)] -> [Maybe b] +lookupAll [] _ = [] +lookupAll (_:xs) [] = Nothing : lookupAll xs [] +lookupAll (x:xs) (y:ys) = case compare x (fst y) of + LT -> Nothing : lookupAll xs (y:ys) + EQ -> Just (snd y) : lookupAll xs (y:ys) + GT -> lookupAll (x:xs) ys -- | Remove a file that doesn't necessarily exist removeFileIfExists :: FilePath -> Action () diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index c156b44..f549b0f 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -25,6 +25,7 @@ selftestRules = testChunksOfSize testMatchVersionedFilePath testModuleNames + testLookupAll testWays :: Action () testWays = do @@ -68,3 +69,17 @@ testModuleNames = do test $ forAll names $ \n -> uncurry encodeModule (decodeModule n) == n where names = intercalate "." <$> listOf1 (listOf1 $ elements "abcABC123_'") + +testLookupAll :: Action () +testLookupAll = do + putBuild $ "==== lookupAll" + test $ lookupAll ["b" , "c" ] [("a", 1), ("c", 3), ("d", 4)] + == [Nothing, Just (3 :: Int)] + test $ forAll dicts $ \dict -> forAll extras $ \extra -> + let items = sort $ map fst dict ++ extra + in lookupAll items (sort dict) == map (flip lookup dict) items + where + dicts :: Gen [(Int, Int)] + dicts = nubBy ((==) `on` fst) <$> vector 20 + extras :: Gen [Int] + extras = vector 20 From git at git.haskell.org Fri Oct 27 00:04:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (3rd try). (de13770) Message-ID: <20171027000451.C01653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de13770f7941733a8af2fbd6daeef6fb916b6a11/ghc >--------------------------------------------------------------- commit de13770f7941733a8af2fbd6daeef6fb916b6a11 Author: Andrey Mokhov Date: Sat Jan 9 18:07:22 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (3rd try). See #110. [skip ci] >--------------------------------------------------------------- de13770f7941733a8af2fbd6daeef6fb916b6a11 .appveyor.yml | 3 --- build.bat | 3 +++ 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index e382140..16de309 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,8 +23,5 @@ install: - happy --version build_script: - - set GHC_PACKAGE_PATH - - set GHC_PACKAGE_PATH= - - set GHC_PACKAGE_PATH - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat -j --no-progress diff --git a/build.bat b/build.bat index a4e2548..4cbbc42 100644 --- a/build.bat +++ b/build.bat @@ -16,4 +16,7 @@ ".." ^ %* + at rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains + at if defined GHC_PACKAGE_PATH ( set GHC_PACKAGE_PATH ) + @ghc %ghcArgs% && .shake\build %shakeArgs% From git at git.haskell.org Fri Oct 27 00:04:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add findKnownPackage for finding packages by name. (b51e6d9) Message-ID: <20171027000452.31ED53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b51e6d97b5f930963687dca5eb64983324baa8b1/ghc >--------------------------------------------------------------- commit b51e6d97b5f930963687dca5eb64983324baa8b1 Author: Andrey Mokhov Date: Wed Aug 19 02:42:15 2015 +0100 Add findKnownPackage for finding packages by name. >--------------------------------------------------------------- b51e6d97b5f930963687dca5eb64983324baa8b1 src/Settings/Packages.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 6e236c9..369879c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -1,6 +1,6 @@ module Settings.Packages ( module Settings.Default, - packages, getPackages, knownPackages + packages, getPackages, knownPackages, findKnownPackage ) where import Package @@ -9,6 +9,7 @@ import Expression import Oracles.Setting import Settings.User import Settings.Default +import Data.List -- Combining default list of packages with user modifications packages :: Packages @@ -40,3 +41,11 @@ packagesStage1 = mconcat knownPackages :: [Package] knownPackages = defaultKnownPackages ++ userKnownPackages + +-- Note: this is slow but we keep it simple as there not too many packages (30) +-- We handle integerLibrary in a special way, because packages integerGmp and +-- integerGmp2 have the same package name -- we return the user-selected one. +findKnownPackage :: PackageName -> Maybe Package +findKnownPackage name + | name == pkgName integerLibrary = Just integerLibrary + | otherwise = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Fri Oct 27 00:04:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep duplicates in the intersection. (2ec9f84) Message-ID: <20171027000453.34F523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ec9f84bce2ad28a16802b7ac901685495a6b4ff/ghc >--------------------------------------------------------------- commit 2ec9f84bce2ad28a16802b7ac901685495a6b4ff Author: Andrey Mokhov Date: Sun Feb 21 01:27:24 2016 +0000 Keep duplicates in the intersection. >--------------------------------------------------------------- 2ec9f84bce2ad28a16802b7ac901685495a6b4ff src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 324feb8..871cd3c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -157,7 +157,7 @@ minusOrd (x:xs) (y:ys) = case compare x y of EQ -> minusOrd xs ys GT -> minusOrd (x:xs) ys --- Explicit definition to avoid dependency on Data.List.Ordered +-- Explicit definition to avoid dependency on Data.List.Ordered. TODO: add tests -- | Intersection of two ordered lists by a predicate. intersectOrd :: (a -> b -> Ordering) -> [a] -> [b] -> [a] intersectOrd cmp = loop @@ -166,7 +166,7 @@ intersectOrd cmp = loop loop _ [] = [] loop (x:xs) (y:ys) = case cmp x y of LT -> loop xs (y:ys) - EQ -> x : loop xs ys + EQ -> x : loop xs (y:ys) GT -> loop (x:xs) ys -- | Lookup all elements of a given sorted list in a given sorted dictionary. From git at git.haskell.org Fri Oct 27 00:04:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (4th try). (b183504) Message-ID: <20171027000456.0196F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b1835045bfffcbc23d170b7675bf4156bc02e215/ghc >--------------------------------------------------------------- commit b1835045bfffcbc23d170b7675bf4156bc02e215 Author: Andrey Mokhov Date: Sat Jan 9 18:15:23 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (4th try). See #110. [skip ci] >--------------------------------------------------------------- b1835045bfffcbc23d170b7675bf4156bc02e215 build.bat | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 4cbbc42..2901686 100644 --- a/build.bat +++ b/build.bat @@ -17,6 +17,6 @@ %* @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains - at if defined GHC_PACKAGE_PATH ( set GHC_PACKAGE_PATH ) + at set GHC_PACKAGE_PATH= @ghc %ghcArgs% && .shake\build %shakeArgs% From git at git.haskell.org Fri Oct 27 00:04:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement buildPackageDocumentation build rule. (b38d769) Message-ID: <20171027000457.AA97C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b38d769b73fa7576c2450c7d6057e5e0dd83b8f0/ghc >--------------------------------------------------------------- commit b38d769b73fa7576c2450c7d6057e5e0dd83b8f0 Author: Andrey Mokhov Date: Wed Aug 19 02:42:50 2015 +0100 Implement buildPackageDocumentation build rule. >--------------------------------------------------------------- b38d769b73fa7576c2450c7d6057e5e0dd83b8f0 src/Rules/Documentation.hs | 53 ++++++++++++++++++++++++++++++++++++++++++++++ src/Rules/Package.hs | 4 +++- 2 files changed, 56 insertions(+), 1 deletion(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs new file mode 100644 index 0000000..9cde8d1 --- /dev/null +++ b/src/Rules/Documentation.hs @@ -0,0 +1,53 @@ +module Rules.Documentation (buildPackageDocumentation) where + +import Way +import Base +import Stage +import Builder +import Package +import Expression +import Oracles.PackageData +import qualified Target +import Settings.TargetDirectory +import Rules.Actions +import Rules.Resources +import Settings.Util +import Settings.User +import Settings.Packages +import Control.Monad.Extra + +-- Note: this build rule creates plenty of files, not just the .haddock one. +-- All of them go into the 'doc' subdirectory. Pedantically tracking all built +-- files in the Shake databases seems fragile and unnecesarry. +buildPackageDocumentation :: Resources -> StagePackageTarget -> Rules () +buildPackageDocumentation _ target = + let stage = Target.stage target + pkg = Target.package target + name = pkgName pkg + cabal = pkgCabalPath pkg + haddock = pkgHaddockPath pkg + in when (stage == Stage1) $ do + + haddock %> \file -> do + whenM (specified HsColour) $ do + need [cabal] + build $ fullTarget target GhcCabalHsColour [cabal] [] + srcs <- interpret target getPackageSources + deps <- interpret target $ getPkgDataList DepNames + let haddocks = [ pkgHaddockPath depPkg + | Just depPkg <- map findKnownPackage deps ] + need $ srcs ++ haddocks + let haddockWay = if dynamicGhcPrograms then dynamic else vanilla + build $ fullTargetWithWay target Haddock haddockWay srcs [file] + +-- $$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_DEPS = +-- $$(foreach n,$$($1_$2_DEPS) +-- ,$$($$n_HADDOCK_FILE) $$($$n_dist-install_$$(HADDOCK_WAY)_LIB)) + +-- $$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) : +-- $$$$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_DEPS) | $$$$(dir $$$$@)/. + +-- # Make the haddocking depend on the library .a file, to ensure +-- # that we wait until the library is fully built before we haddock it +-- $$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) : $$($1_$2_$$(HADDOCK_WAY)_LIB) +-- endif diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index dbbe5cc..6e5448b 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -7,10 +7,12 @@ import Rules.Compile import Rules.Library import Rules.Resources import Rules.Dependencies +import Rules.Documentation buildPackage :: Resources -> StagePackageTarget -> Rules () buildPackage = mconcat [ buildPackageData , buildPackageDependencies , compilePackage - , buildPackageLibrary ] + , buildPackageLibrary + , buildPackageDocumentation ] From git at git.haskell.org Fri Oct 27 00:04:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop duplication of module names in moduleFilesOracle. (59d7bf1) Message-ID: <20171027000457.BCA983A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59d7bf155a356bd662a3e74f11b4c2532464b10b/ghc >--------------------------------------------------------------- commit 59d7bf155a356bd662a3e74f11b4c2532464b10b Author: Andrey Mokhov Date: Sun Feb 21 01:28:12 2016 +0000 Drop duplication of module names in moduleFilesOracle. See #210. >--------------------------------------------------------------- 59d7bf155a356bd662a3e74f11b4c2532464b10b src/Oracles/ModuleFiles.hs | 28 +++++++++++++++++++++------- 1 file changed, 21 insertions(+), 7 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index a5e40ed..bced848 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -16,8 +16,7 @@ moduleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (dirs, modules) - return $ map snd found + fmap catMaybes . askOracle $ ModuleFilesKey (dirs, modules) haskellModuleFiles :: Context -> Action ([FilePath], [String]) haskellModuleFiles context @ (Context {..}) = do @@ -29,13 +28,17 @@ haskellModuleFiles context @ (Context {..}) = do let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] foundSrcDirs <- askOracle $ ModuleFilesKey (dirs , modules) foundAutogen <- askOracle $ ModuleFilesKey ([autogen], modules) + found <- sequence $ zipWith3 addSources modules foundSrcDirs foundAutogen - let found = foundSrcDirs ++ foundAutogen - missingMods = modules `minusOrd` (sort $ map fst found) + let missingMods = map fst . filter (isNothing . snd) $ zip modules found otherFileToMod = replaceEq '/' '.' . dropExtension . dropPkgPath - (haskellFiles, otherFiles) = partition ("//*hs" ?==) (map snd found) + (haskellFiles, otherFiles) = partition ("//*hs" ?==) $ catMaybes found return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) + where + addSources _ Nothing r = return r + addSources _ l Nothing = return l + addSources m (Just f1) (Just f2) = errorMultipleSources m f1 f2 -- | This is an important oracle whose role is to find and cache module source -- files. More specifically, it takes a list of directories @dirs@ and a sorted @@ -51,7 +54,7 @@ moduleFilesOracle :: Rules () moduleFilesOracle = void $ addOracle $ \(ModuleFilesKey (dirs, modules)) -> do let decodedPairs = map decodeModule modules - modDirFiles = map (bimap head sort . unzip) + modDirFiles = map (bimap head id . unzip) . groupBy ((==) `on` fst) $ decodedPairs result <- fmap concat . forM dirs $ \dir -> do @@ -64,4 +67,15 @@ moduleFilesOracle = void $ found = intersectOrd cmp noBoot mFiles return (map (fullDir -/-) found, mDir) - return $ sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] + let pairs = sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] + multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ] + + unless (null multi) $ do + let (m, f1, f2) = head multi + errorMultipleSources m f1 f2 + + return $ lookupAll modules pairs + +errorMultipleSources :: String -> FilePath -> FilePath -> Action a +errorMultipleSources m f1 f2 = putError $ "Module " ++ m ++ + " has more than one source file: " ++ f1 ++ " and " ++ f2 ++ "." From git at git.haskell.org Fri Oct 27 00:04:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:04:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (5th try). (9ba5daa) Message-ID: <20171027000459.872623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ba5daa863d59d5b2a7bd8fabdd9caa0b8fe4521/ghc >--------------------------------------------------------------- commit 9ba5daa863d59d5b2a7bd8fabdd9caa0b8fe4521 Author: Andrey Mokhov Date: Sat Jan 9 19:10:44 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (5th try). See #110. >--------------------------------------------------------------- 9ba5daa863d59d5b2a7bd8fabdd9caa0b8fe4521 build.bat | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/build.bat b/build.bat index 2901686..07e355a 100644 --- a/build.bat +++ b/build.bat @@ -16,7 +16,11 @@ ".." ^ %* - at rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains - at set GHC_PACKAGE_PATH= - at ghc %ghcArgs% && .shake\build %shakeArgs% + at ghc %ghcArgs% + + at if %ERRORLEVEL% EQU 0 ( + @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains + @set GHC_PACKAGE_PATH= + @.shake\build %shakeArgs% +) From git at git.haskell.org Fri Oct 27 00:05:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add findModuleFiles and export it. (9039a4f) Message-ID: <20171027000501.948033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9039a4f1dfedbc9606d2ccef35d81d7736993f11/ghc >--------------------------------------------------------------- commit 9039a4f1dfedbc9606d2ccef35d81d7736993f11 Author: Andrey Mokhov Date: Sun Feb 21 02:21:00 2016 +0000 Add findModuleFiles and export it. See #210. >--------------------------------------------------------------- 9039a4f1dfedbc9606d2ccef35d81d7736993f11 src/Oracles/ModuleFiles.hs | 22 ++++++++++++++-------- 1 file changed, 14 insertions(+), 8 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index bced848..501bc89 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,5 +1,7 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} -module Oracles.ModuleFiles (moduleFiles, haskellModuleFiles, moduleFilesOracle) where +module Oracles.ModuleFiles ( + moduleFiles, haskellModuleFiles, moduleFilesOracle, findModuleFiles + ) where import Base import Context @@ -16,7 +18,7 @@ moduleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - fmap catMaybes . askOracle $ ModuleFilesKey (dirs, modules) + fmap catMaybes $ findModuleFiles dirs modules haskellModuleFiles :: Context -> Action ([FilePath], [String]) haskellModuleFiles context @ (Context {..}) = do @@ -26,8 +28,8 @@ haskellModuleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - foundSrcDirs <- askOracle $ ModuleFilesKey (dirs , modules) - foundAutogen <- askOracle $ ModuleFilesKey ([autogen], modules) + foundSrcDirs <- findModuleFiles dirs modules + foundAutogen <- findModuleFiles [autogen] modules found <- sequence $ zipWith3 addSources modules foundSrcDirs foundAutogen let missingMods = map fst . filter (isNothing . snd) $ zip modules found @@ -43,13 +45,17 @@ haskellModuleFiles context @ (Context {..}) = do -- | This is an important oracle whose role is to find and cache module source -- files. More specifically, it takes a list of directories @dirs@ and a sorted -- list of module names @modules@ as arguments, and for each module, e.g. --- @A.B.C@, returns a FilePath of the form @dir/A/B/C.extension@, such that --- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or Nothing +-- @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, such that +-- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or 'Nothing' -- if there is no such file. If more than one matching file is found an error is -- raised. For example, for the 'compiler' package given --- @dirs = ["codeGen", "parser"]@, and +-- @dirs = ["compiler/codeGen", "compiler/parser"]@, and -- @modules = ["CodeGen.Platform.ARM", "Lexer", "Missing.Module"]@, it produces --- @[Just "codeGen/CodeGen/Platform/ARM.hs", Just "parser/Lexer.x", Nothing]@. +-- @[Just "compiler/codeGen/CodeGen/Platform/ARM.hs", +-- Just "compiler/parser/Lexer.x", Nothing]@. +findModuleFiles :: [FilePath] -> [String] -> Action [Maybe FilePath] +findModuleFiles dirs modules = askOracle $ ModuleFilesKey (dirs, modules) + moduleFilesOracle :: Rules () moduleFilesOracle = void $ addOracle $ \(ModuleFilesKey (dirs, modules)) -> do From git at git.haskell.org Fri Oct 27 00:05:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop mk-miner submodule. (885369f) Message-ID: <20171027000501.E1D2C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/885369f3c4ae9664bafc328ee191ec5efb090858/ghc >--------------------------------------------------------------- commit 885369f3c4ae9664bafc328ee191ec5efb090858 Author: Andrey Mokhov Date: Wed Aug 19 15:02:19 2015 +0100 Drop mk-miner submodule. >--------------------------------------------------------------- 885369f3c4ae9664bafc328ee191ec5efb090858 .gitmodules | 3 --- 1 file changed, 3 deletions(-) diff --git a/.gitmodules b/.gitmodules deleted file mode 100644 index 8f798aa..0000000 --- a/.gitmodules +++ /dev/null @@ -1,3 +0,0 @@ -[submodule "mk-miner"] - path = mk-miner - url = https://github.com/snowleopard/mk-miner.git From git at git.haskell.org Fri Oct 27 00:05:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor generators, add makeExecutable action. (3dff957) Message-ID: <20171027000503.5CAC03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3dff95749258bfaa8a21ad0e2588a391ade36649/ghc >--------------------------------------------------------------- commit 3dff95749258bfaa8a21ad0e2588a391ade36649 Author: Andrey Mokhov Date: Sat Jan 9 20:09:51 2016 +0000 Refactor generators, add makeExecutable action. >--------------------------------------------------------------- 3dff95749258bfaa8a21ad0e2588a391ade36649 src/GHC.hs | 8 ++++++-- src/Rules/Actions.hs | 7 ++++++- src/Rules/Generate.hs | 17 +++++++---------- src/Rules/Generators/Common.hs | 20 ++++++++++++++++++++ src/Rules/Generators/ConfigHs.hs | 10 +++------- src/Rules/Generators/GhcAutoconfH.hs | 5 ++--- src/Rules/Generators/GhcBootPlatformH.hs | 8 +++----- src/Rules/Generators/GhcPlatformH.hs | 6 ++---- src/Rules/Generators/GhcSplit.hs | 21 ++++++++++----------- src/Rules/Generators/GhcVersionH.hs | 6 ++---- src/Rules/Generators/VersionHs.hs | 5 ++--- src/Rules/Perl.hs | 17 +++-------------- src/Rules/Program.hs | 2 +- 13 files changed, 67 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3dff95749258bfaa8a21ad0e2588a391ade36649 From git at git.haskell.org Fri Oct 27 00:05:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test findModuleFiles. (1136a62) Message-ID: <20171027000505.ADC963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1136a62c35dfe9df3774667b1e501494e2a496b1/ghc >--------------------------------------------------------------- commit 1136a62c35dfe9df3774667b1e501494e2a496b1 Author: Andrey Mokhov Date: Sun Feb 21 02:22:26 2016 +0000 Test findModuleFiles. See #197, #210. >--------------------------------------------------------------- 1136a62c35dfe9df3774667b1e501494e2a496b1 src/Rules/Selftest.hs | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f549b0f..f4890b0 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,6 +6,7 @@ import Development.Shake import Test.QuickCheck import Base +import Oracles.ModuleFiles import Settings.Builders.Ar (chunksOfSize) import Way @@ -26,6 +27,7 @@ selftestRules = testMatchVersionedFilePath testModuleNames testLookupAll + testModuleFilesOracle testWays :: Action () testWays = do @@ -83,3 +85,14 @@ testLookupAll = do dicts = nubBy ((==) `on` fst) <$> vector 20 extras :: Gen [Int] extras = vector 20 + +testModuleFilesOracle :: Action () +testModuleFilesOracle = do + putBuild $ "==== moduleFilesOracle" + result <- findModuleFiles ["compiler/codeGen", "compiler/parser"] + [ "CodeGen.Platform.ARM" + , "Lexer" + , "Missing.Module"] + test $ result == [ Just "compiler/codeGen/CodeGen/Platform/ARM.hs" + , Just "compiler/parser/Lexer.x" + , Nothing] From git at git.haskell.org Fri Oct 27 00:05:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove traces of mk-miner submodule. (d56995a) Message-ID: <20171027000506.27DBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d56995a00e2dbf7053bb3fdea357ef6e456b9639/ghc >--------------------------------------------------------------- commit d56995a00e2dbf7053bb3fdea357ef6e456b9639 Author: Andrey Mokhov Date: Wed Aug 19 15:14:52 2015 +0100 Remove traces of mk-miner submodule. >--------------------------------------------------------------- d56995a00e2dbf7053bb3fdea357ef6e456b9639 mk-miner | 1 - 1 file changed, 1 deletion(-) diff --git a/mk-miner b/mk-miner deleted file mode 160000 index 276425e..0000000 --- a/mk-miner +++ /dev/null @@ -1 +0,0 @@ -Subproject commit 276425ea44420f49ac34fd942c0dad84b0c0d332 From git at git.haskell.org Fri Oct 27 00:05:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build stage1 GHC only on appveyor to fit into the time limit. (4745578) Message-ID: <20171027000507.3DB193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4745578604163225043051c6963284c0a52affef/ghc >--------------------------------------------------------------- commit 4745578604163225043051c6963284c0a52affef Author: Andrey Mokhov Date: Sat Jan 9 20:14:31 2016 +0000 Build stage1 GHC only on appveyor to fit into the time limit. See #110. [skip ci] >--------------------------------------------------------------- 4745578604163225043051c6963284c0a52affef .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 16de309..99196db 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:05:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant brackets. (a09185a) Message-ID: <20171027000509.959D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a09185a4d6a5aa90930ecab25724830bcddb9fa2/ghc >--------------------------------------------------------------- commit a09185a4d6a5aa90930ecab25724830bcddb9fa2 Author: Andrey Mokhov Date: Tue Feb 23 02:46:06 2016 +0000 Drop redundant brackets. >--------------------------------------------------------------- a09185a4d6a5aa90930ecab25724830bcddb9fa2 src/GHC.hs | 4 ++-- src/Oracles/ModuleFiles.hs | 4 ++-- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 4 ++-- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 2 +- src/Settings/Paths.hs | 10 +++++----- 10 files changed, 18 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a09185a4d6a5aa90930ecab25724830bcddb9fa2 From git at git.haskell.org Fri Oct 27 00:05:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop custom cfg/configure.ac and instead add an appropriate AC_CONFIG_FILES command directly to the existing configure.ac. (d4f6e48) Message-ID: <20171027000510.6C7483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50/ghc >--------------------------------------------------------------- commit d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50 Author: Andrey Mokhov Date: Thu Aug 20 23:56:01 2015 +0100 Drop custom cfg/configure.ac and instead add an appropriate AC_CONFIG_FILES command directly to the existing configure.ac. >--------------------------------------------------------------- d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50 cfg/configure.ac | 1073 --------------------------------------------------- src/Rules/Config.hs | 17 +- 2 files changed, 16 insertions(+), 1074 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 d4f6e48b1cc1fc20e6e2cf48bb556a476cf59a50 From git at git.haskell.org Fri Oct 27 00:05:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing source Settings.Builders.Common (1ad387d) Message-ID: <20171027000511.47FDC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ad387d0ac1af354fff93b384251fab482eee49d/ghc >--------------------------------------------------------------- commit 1ad387d0ac1af354fff93b384251fab482eee49d Author: Andrey Mokhov Date: Sat Jan 9 20:21:27 2016 +0000 Add missing source Settings.Builders.Common [skip ci] >--------------------------------------------------------------- 1ad387d0ac1af354fff93b384251fab482eee49d shaking-up-ghc.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index a5b4c57..9c40f46 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -43,6 +43,7 @@ executable ghc-shake , Rules.Dependencies , Rules.Documentation , Rules.Generate + , Rules.Generators.Common , Rules.Generators.ConfigHs , Rules.Generators.GhcAutoconfH , Rules.Generators.GhcBootPlatformH From git at git.haskell.org Fri Oct 27 00:05:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify and refactor moduleFiles oracle. (3d9c2fd) Message-ID: <20171027000513.E58C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d9c2fdaf006a7aada8454295469cc5d8aa23938/ghc >--------------------------------------------------------------- commit 3d9c2fdaf006a7aada8454295469cc5d8aa23938 Author: Andrey Mokhov Date: Thu Feb 25 23:15:18 2016 +0000 Simplify and refactor moduleFiles oracle. See #210. >--------------------------------------------------------------- 3d9c2fdaf006a7aada8454295469cc5d8aa23938 src/Oracles/ModuleFiles.hs | 31 ++++++++++++++++++------------- src/Rules/Dependencies.hs | 3 ++- src/Rules/Documentation.hs | 3 ++- src/Settings.hs | 16 +--------------- 4 files changed, 23 insertions(+), 30 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index cf33e20..4c74265 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,12 +1,12 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} module Oracles.ModuleFiles ( - moduleFiles, haskellModuleFiles, moduleFilesOracle, findModuleFiles + moduleFiles, haskellSources, moduleFilesOracle, findModuleFiles ) where import Base import Context +import Expression import Oracles.PackageData -import Package import Settings.Paths newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) @@ -14,11 +14,12 @@ newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) moduleFiles :: Context -> Action [FilePath] moduleFiles context @ Context {..} = do - let path = contextPath context + let path = contextPath context + autogen = path -/- "build/autogen" srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - fmap catMaybes $ findModuleFiles dirs modules + catMaybes <$> findModuleFiles (autogen : dirs) modules haskellModuleFiles :: Context -> Action ([FilePath], [String]) haskellModuleFiles context @ Context {..} = do @@ -28,19 +29,23 @@ haskellModuleFiles context @ Context {..} = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - foundSrcDirs <- findModuleFiles dirs modules - foundAutogen <- findModuleFiles [autogen] modules - found <- sequence $ zipWith3 addSources modules foundSrcDirs foundAutogen - + found <- findModuleFiles (autogen : dirs) modules let missingMods = map fst . filter (isNothing . snd) $ zip modules found otherFileToMod = replaceEq '/' '.' . dropExtension . dropPkgPath (haskellFiles, otherFiles) = partition ("//*hs" ?==) $ catMaybes found - return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) - where - addSources _ Nothing r = return r - addSources _ l Nothing = return l - addSources m (Just f1) (Just f2) = errorMultipleSources m f1 f2 + +-- | Find all Haskell source files for the current context +haskellSources :: Context -> Action [FilePath] +haskellSources context = do + let buildPath = contextPath context -/- "build" + autogen = buildPath -/- "autogen" + (found, missingMods) <- haskellModuleFiles context + -- Generated source files live in buildPath and have extension "hs"... + let generated = [ buildPath -/- (replaceEq '.' '/' m) <.> "hs" | m <- missingMods ] + -- ...except that GHC/Prim.hs lives in autogen. TODO: fix the inconsistency? + fixGhcPrim = replaceEq (buildPath -/- "GHC/Prim.hs") (autogen -/- "GHC/Prim.hs") + return $ found ++ fixGhcPrim generated -- | This is an important oracle whose role is to find and cache module source -- files. More specifically, it takes a list of directories @dirs@ and a sorted diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 16d2c0e..04cffc2 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -5,6 +5,7 @@ import Development.Shake.Util (parseMakefile) import Base import Context import Expression +import Oracles.ModuleFiles import Oracles.PackageData import Rules.Actions import Settings @@ -27,7 +28,7 @@ buildPackageDependencies rs context @ Context {..} = build $ Target context (GccM stage) [srcFile] [out] hDepFile %> \out -> do - srcs <- interpretInContext context getPackageSources + srcs <- haskellSources context need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 4e96571..b9407bc 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -4,6 +4,7 @@ import Base import Context import Expression import GHC +import Oracles.ModuleFiles import Oracles.PackageData import Rules.Actions import Settings @@ -21,7 +22,7 @@ buildPackageDocumentation context @ Context {..} = haddockFile = pkgHaddockFile context in when (stage == Stage1) $ do haddockFile %> \file -> do - srcs <- interpretInContext context getPackageSources + srcs <- haskellSources context deps <- map PackageName <$> interpretInContext context (getPkgDataList DepNames) let haddocks = [ pkgHaddockFile $ vanillaContext Stage1 depPkg | Just depPkg <- map findKnownPackage deps diff --git a/src/Settings.hs b/src/Settings.hs index e134fbc..9f52026 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -4,12 +4,11 @@ module Settings ( module Settings.User, module Settings.Ways, getPkgData, getPkgDataList, getTopDirectory, isLibrary, - getPackagePath, getContextDirectory, getContextPath, getPackageSources + getPackagePath, getContextDirectory, getContextPath ) where import Base import Expression -import Oracles.ModuleFiles import Oracles.PackageData import Oracles.WindowsPath import Settings.Packages @@ -34,16 +33,3 @@ getPkgDataList key = lift . pkgDataList . key =<< getContextPath getTopDirectory :: Expr FilePath getTopDirectory = lift topDirectory - --- | Find all Haskell source files for the current target -getPackageSources :: Expr [FilePath] -getPackageSources = do - context <- getContext - let buildPath = contextPath context -/- "build" - autogen = buildPath -/- "autogen" - (found, missingMods) <- lift $ haskellModuleFiles context - -- Generated source files live in buildPath and have extension "hs"... - let generated = [ buildPath -/- (replaceEq '.' '/' m) <.> "hs" | m <- missingMods ] - -- ...except that GHC/Prim.hs lives in autogen. TODO: fix the inconsistency? - fixGhcPrim = replaceEq (buildPath -/- "GHC/Prim.hs") (autogen -/- "GHC/Prim.hs") - return $ found ++ fixGhcPrim generated From git at git.haskell.org Fri Oct 27 00:05:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move needBuilder to src/Builder.hs. (7baa070) Message-ID: <20171027000514.63C353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7baa070bd5bb2b40235bdb362d1f0ec6063f260d/ghc >--------------------------------------------------------------- commit 7baa070bd5bb2b40235bdb362d1f0ec6063f260d Author: Andrey Mokhov Date: Fri Aug 21 16:07:01 2015 +0100 Move needBuilder to src/Builder.hs. >--------------------------------------------------------------- 7baa070bd5bb2b40235bdb362d1f0ec6063f260d src/Builder.hs | 25 +++++++++++++++++-------- 1 file changed, 17 insertions(+), 8 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index ac184d3..bd0ef49 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} module Builder ( - Builder (..), builderKey, builderPath, specified + Builder (..), builderKey, builderPath, specified, needBuilder ) where import Base @@ -61,7 +61,7 @@ builderKey builder = case builder of -- GhcCabalHsColour is a synonym for GhcCabal (called in hscolour mode) GhcCabalHsColour -> builderKey $ GhcCabal -builderPath :: Builder -> Action String +builderPath :: Builder -> Action FilePath builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ putError $ "\nCannot find path to '" ++ (builderKey builder) @@ -71,6 +71,21 @@ builderPath builder = do specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath +-- Make sure a builder exists on the given path and rebuild it if out of date. +-- If laxDependencies is True then we do not rebuild GHC even if it is out of +-- date (can save a lot of build time when changing GHC). +needBuilder :: Bool -> Builder -> Action () +needBuilder laxDependencies builder = do + path <- builderPath builder + if laxDependencies && allowOrderOnlyDependency builder + then orderOnly [path] + else need [path] + where + allowOrderOnlyDependency :: Builder -> Bool + allowOrderOnlyDependency (Ghc _) = True + allowOrderOnlyDependency (GhcM _) = True + allowOrderOnlyDependency _ = False + -- On Windows: if the path starts with "/", prepend it with the correct path to -- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". fixAbsolutePathOnWindows :: FilePath -> Action FilePath @@ -84,12 +99,6 @@ fixAbsolutePathOnWindows path = do else return path --- When LaxDeps flag is set ('lax-dependencies = YES' in user.config), --- dependencies on the GHC executable are turned into order-only dependencies --- to avoid needless recompilation when making changes to GHC's sources. In --- certain situations this can lead to build failures, in which case you --- should reset the flag (at least temporarily). - -- Instances for storing in the Shake database instance Binary Builder instance Hashable Builder From git at git.haskell.org Fri Oct 27 00:05:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build stage1 GHC only to fit into OS X time limit on Travis. (db5dce0) Message-ID: <20171027000514.F141C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db5dce0cb5d252e1a0576ec9731a758b98385fdc/ghc >--------------------------------------------------------------- commit db5dce0cb5d252e1a0576ec9731a758b98385fdc Author: Andrey Mokhov Date: Sat Jan 9 20:23:41 2016 +0000 Build stage1 GHC only to fit into OS X time limit on Travis. >--------------------------------------------------------------- db5dce0cb5d252e1a0576ec9731a758b98385fdc .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index ca51b6f..3c5f522 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - cabal update - os: osx - env: TARGET=libraries/base/stage1/build/libHSbase-4.9.0.0.a + env: TARGET=inplace/bin/ghc-stage1.exe before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Fri Oct 27 00:05:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:05:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop testModuleFilesOracle. (50663a4) Message-ID: <20171027000530.360EF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/50663a4d4e5a04653e4a30034e688bf1dbd549ec/ghc >--------------------------------------------------------------- commit 50663a4d4e5a04653e4a30034e688bf1dbd549ec Author: Andrey Mokhov Date: Fri Feb 26 03:36:31 2016 +0000 Drop testModuleFilesOracle. See #210. >--------------------------------------------------------------- 50663a4d4e5a04653e4a30034e688bf1dbd549ec src/Rules/Selftest.hs | 13 ------------- 1 file changed, 13 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f4890b0..f549b0f 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,7 +6,6 @@ import Development.Shake import Test.QuickCheck import Base -import Oracles.ModuleFiles import Settings.Builders.Ar (chunksOfSize) import Way @@ -27,7 +26,6 @@ selftestRules = testMatchVersionedFilePath testModuleNames testLookupAll - testModuleFilesOracle testWays :: Action () testWays = do @@ -85,14 +83,3 @@ testLookupAll = do dicts = nubBy ((==) `on` fst) <$> vector 20 extras :: Gen [Int] extras = vector 20 - -testModuleFilesOracle :: Action () -testModuleFilesOracle = do - putBuild $ "==== moduleFilesOracle" - result <- findModuleFiles ["compiler/codeGen", "compiler/parser"] - [ "CodeGen.Platform.ARM" - , "Lexer" - , "Missing.Module"] - test $ result == [ Just "compiler/codeGen/CodeGen/Platform/ARM.hs" - , Just "compiler/parser/Lexer.x" - , Nothing] From git at git.haskell.org Fri Oct 27 00:10:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Determine system GMP library name and pass it via -optl. (2024396) Message-ID: <20171027001015.D92213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20243965783cfb5ba75096ebe375517d63cf37c8/ghc >--------------------------------------------------------------- commit 20243965783cfb5ba75096ebe375517d63cf37c8 Author: Andrey Mokhov Date: Fri Jan 15 01:11:36 2016 +0000 Determine system GMP library name and pass it via -optl. See #173. >--------------------------------------------------------------- 20243965783cfb5ba75096ebe375517d63cf37c8 src/Rules/Gmp.hs | 113 +++++++++++++++++++++++-------------------- src/Settings/Builders/Ghc.hs | 11 ++++- 2 files changed, 69 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 20243965783cfb5ba75096ebe375517d63cf37c8 From git at git.haskell.org Fri Oct 27 00:10:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:10:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Print version info before running configure (759dff3) Message-ID: <20171027001018.CBAF23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/759dff36f7d30aba45bd3b6f9947328b4c0a8c77/ghc >--------------------------------------------------------------- commit 759dff36f7d30aba45bd3b6f9947328b4c0a8c77 Author: Andrey Mokhov Date: Mon May 2 03:45:49 2016 +0100 Print version info before running configure >--------------------------------------------------------------- 759dff36f7d30aba45bd3b6f9947328b4c0a8c77 appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 3918779..76ccbe1 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -24,6 +24,11 @@ install: - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - ghc --version + - stack --version + - alex --version + - happy --version + - stack exec -- ghc-pkg list - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot @@ -31,11 +36,6 @@ install: - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c937606629a97188500bac159d2c8882ccbac3e9/ghc >--------------------------------------------------------------- commit c937606629a97188500bac159d2c8882ccbac3e9 Merge: bd2a394 0afdf64 Author: Andrey Mokhov Date: Fri Dec 18 23:16:30 2015 +0000 Merge pull request #2 from bgamari/master Various fixes >--------------------------------------------------------------- c937606629a97188500bac159d2c8882ccbac3e9 build.sh | 6 ++++++ cfg/system.config.in | 18 ++++++++++++------ src/Builder.hs | 1 + src/GHC.hs | 22 ++++++++++++---------- src/Oracles/Config/Flag.hs | 6 ++++-- src/Oracles/Dependencies.hs | 12 ++++++------ src/Oracles/PackageData.hs | 6 ++---- src/Package.hs | 1 + src/Rules.hs | 6 +++--- src/Rules/Compile.hs | 10 ---------- src/Rules/Data.hs | 36 +----------------------------------- src/Rules/Generate.hs | 5 ++++- src/Settings/Builders/Ghc.hs | 16 ++++++++-------- src/Settings/Packages.hs | 5 +++-- src/Stage.hs | 1 + src/Way.hs | 3 +++ 16 files changed, 67 insertions(+), 87 deletions(-) From git at git.haskell.org Fri Oct 27 00:12:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix tracking of changes to Libffi rules file (efc92c5) Message-ID: <20171027001211.C70B33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efc92c529a00d16f18f2708dd5898ce0ae564cd6/ghc >--------------------------------------------------------------- commit efc92c529a00d16f18f2708dd5898ce0ae564cd6 Author: Karel Gardas Date: Mon Jan 18 20:23:40 2016 +0100 fix tracking of changes to Libffi rules file >--------------------------------------------------------------- efc92c529a00d16f18f2708dd5898ce0ae564cd6 src/Rules/Libffi.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 518389e..97ebc2d 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,6 +70,7 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do + when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] ffi_header_dir <- setting FfiIncludeDir use_system_ffi <- flag UseSystemFfi if use_system_ffi @@ -80,7 +81,6 @@ libffiRules = do copyFile src (rtsBuildPath -/- file) putSuccess $ "| Successfully copied system supplied FFI library header files" else do - when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] removeDirectory libffiBuild createDirectory $ buildRootPath -/- stageString Stage0 From git at git.haskell.org Fri Oct 27 00:12:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #182 from kgardas/fix_ffi_args (9a4bdc7) Message-ID: <20171027001215.835B23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a4bdc7c11538e6984a93bda483aa72d7e4aae0e/ghc >--------------------------------------------------------------- commit 9a4bdc7c11538e6984a93bda483aa72d7e4aae0e Merge: 40b7920 efc92c5 Author: Andrey Mokhov Date: Mon Jan 18 23:43:30 2016 +0000 Merge pull request #182 from kgardas/fix_ffi_args fix handling of FFI library configure params >--------------------------------------------------------------- 9a4bdc7c11538e6984a93bda483aa72d7e4aae0e cfg/system.config.in | 4 +++ src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 4 +++ src/Rules/Libffi.hs | 84 ++++++++++++++++++++++++------------------- src/Settings/Packages/Rts.hs | 14 ++++++-- 5 files changed, 68 insertions(+), 40 deletions(-) From git at git.haskell.org Fri Oct 27 00:12:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on automated run of boot and configure (6864e8b) Message-ID: <20171027001212.41B413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6864e8b3d1d1e89b7f37f816caf6851d6052d930/ghc >--------------------------------------------------------------- commit 6864e8b3d1d1e89b7f37f816caf6851d6052d930 Author: Andrey Mokhov Date: Sat May 7 11:46:35 2016 +0100 Add a note on automated run of boot and configure See #234. [skip ci] >--------------------------------------------------------------- 6864e8b3d1d1e89b7f37f816caf6851d6052d930 README.md | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index e0053b0..a8ca935 100644 --- a/README.md +++ b/README.md @@ -25,8 +25,8 @@ follow these steps: * This build system is written in Haskell (obviously) and depends on the following Haskell packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. -* Get the sources and run standard configuration scripts. It is important for the build -system to be in the `hadrian` directory of the GHC source tree: +* Get the sources. It is important for the build system to be in the `hadrian` directory +of the GHC source tree: ```bash git clone --recursive git://git.haskell.org/ghc.git @@ -38,7 +38,10 @@ system to be in the `hadrian` directory of the GHC source tree: of `make`. You might want to enable parallelism with `-j`. We will further refer to the build script simply as `build`. If you are interested in building in a Cabal sandbox or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Also -see [instructions for building GHC on Windows using Stack][windows-build]. +see [instructions for building GHC on Windows using Stack][windows-build]. Note, Hadrian +runs the `boot` and `configure` scripts automatically on the first build, so that you don't +need to. Use `--skip-configure` to suppress this behaviour (see overview of command line +flags below). Using the build system ---------------------- @@ -52,10 +55,13 @@ currently supports several others: * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations and disables library profiling, which speeds up builds by 3-4x). + * `--haddock`: build Haddock documentation. + * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). + * `--skip-configure`: use this flag to suppress the default behaviour of Hadrian that runs the `boot` and `configure` scripts automatically if need be, so that you don't have to remember to run them manually. With `--skip-configure` you will need to manually run: @@ -67,6 +73,7 @@ to remember to run them manually. With `--skip-configure` you will need to manua as you normally do when using `make`. Beware, by default Hadrian may do network I/O on Windows to download necessary tarballs, which may sometimes be undesirable; `--skip-configure` is your friend in such cases. + * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. From git at git.haskell.org Fri Oct 27 00:12:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move to shake-build subdirectory. (6961517) Message-ID: <20171027001213.CC14A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/69615175a302d90a4e8b76d419124282d0b861e6/ghc >--------------------------------------------------------------- commit 69615175a302d90a4e8b76d419124282d0b861e6 Author: Andrey Mokhov Date: Sat Dec 19 01:04:20 2015 +0000 Move to shake-build subdirectory. >--------------------------------------------------------------- 69615175a302d90a4e8b76d419124282d0b861e6 src/Base.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 896ddc9..bfa7730 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -39,11 +39,14 @@ import qualified System.Directory as IO import System.IO -- Build system files and paths +shakePath :: FilePath +shakePath = "shake-build" + shakeFilesPath :: FilePath -shakeFilesPath = "_build/" +shakeFilesPath = shakeFilesPath -/- ".db" configPath :: FilePath -configPath = "shake/cfg/" +configPath = shakePath -/- "cfg" bootPackageConstraints :: FilePath bootPackageConstraints = shakeFilesPath ++ "boot-package-constraints" From git at git.haskell.org Fri Oct 27 00:12:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Echo stdout only if --progress-info={normal, unicorn}. (6ef09f4) Message-ID: <20171027001215.EE9CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6ef09f44f4c6128971ecaafda61b22cb0befa35c/ghc >--------------------------------------------------------------- commit 6ef09f44f4c6128971ecaafda61b22cb0befa35c Author: Andrey Mokhov Date: Mon May 9 23:31:47 2016 +0100 Echo stdout only if --progress-info={normal, unicorn}. See #235. >--------------------------------------------------------------- 6ef09f44f4c6128971ecaafda61b22cb0befa35c src/Rules/Actions.hs | 27 +++++++++++---------------- src/Rules/Test.hs | 2 +- 2 files changed, 12 insertions(+), 17 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index fd117ae..4928e00 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,8 @@ module Rules.Actions ( build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, removeFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, - applyPatch, fixFile, runMake, runMakeVerbose, renderLibrary, renderProgram, - runBuilder, makeExecutable + applyPatch, fixFile, runMake, renderLibrary, renderProgram, runBuilder, + makeExecutable ) where import qualified System.Directory as IO @@ -62,7 +62,7 @@ customBuild rs opts target at Target {..} = do need [dir -/- "configure"] -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" - cmd Shell [Cwd dir] [path] (env:opts) argList + cmd Shell cmdEcho env [Cwd dir] [path] opts argList HsCpp -> captureStdout target path argList GenApply -> captureStdout target path argList @@ -76,6 +76,9 @@ customBuild rs opts target at Target {..} = do _ -> cmd [path] argList +cmdEcho :: CmdOption +cmdEcho = EchoStdout $ cmdProgressInfo `elem` [Normal, Unicorn] + -- | Run a builder, capture the standard output, and write it to a given file. captureStdout :: Target -> FilePath -> [String] -> Action () captureStdout target path argList = do @@ -118,13 +121,13 @@ removeDirectory dir = do copyDirectory :: FilePath -> FilePath -> Action () copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target - quietly $ cmd (EchoStdout False) ["cp", "-r", source, target] + quietly $ cmd cmdEcho ["cp", "-r", source, target] -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target - quietly $ cmd (EchoStdout False) ["mv", source, target] + quietly $ cmd cmdEcho ["mv", source, target] -- | Transform a given file by applying a function to its contents. fixFile :: FilePath -> (String -> String) -> Action () @@ -138,20 +141,12 @@ fixFile file f = do liftIO $ writeFile file contents runMake :: FilePath -> [String] -> Action () -runMake = runMakeWithVerbosity False - -runMakeVerbose :: FilePath -> [String] -> Action () -runMakeVerbose = runMakeWithVerbosity True - -runMakeWithVerbosity :: Bool -> FilePath -> [String] -> Action () -runMakeWithVerbosity verbose dir args = do +runMake dir args = do need [dir -/- "Makefile"] path <- builderPath Make let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - if verbose - then cmd Shell path ["-C", dir] args - else quietly $ cmd Shell (EchoStdout False) path ["-C", dir] args + quietly $ cmd Shell cmdEcho path ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do @@ -159,7 +154,7 @@ applyPatch dir patch = do needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file - quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] + quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 7faf62d..544b5d9 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -18,7 +18,7 @@ testRules = do needBuilder $ Ghc Compile Stage2 needBuilder $ GhcPkg Stage1 needBuilder Hpc - runMakeVerbose "testsuite/tests" ["fast"] + runMake "testsuite/tests" ["fast"] "test" ~> do let yesNo x = show $ if x then "YES" else "NO" From git at git.haskell.org Fri Oct 27 00:12:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set shakeFilesPath to shake-build/.db (1203444) Message-ID: <20171027001217.4F6C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12034445640aadd319ee7639c303b524c1d6df80/ghc >--------------------------------------------------------------- commit 12034445640aadd319ee7639c303b524c1d6df80 Author: Andrey Mokhov Date: Sat Dec 19 01:06:14 2015 +0000 Set shakeFilesPath to shake-build/.db >--------------------------------------------------------------- 12034445640aadd319ee7639c303b524c1d6df80 src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index bfa7730..e95aa94 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -43,7 +43,7 @@ shakePath :: FilePath shakePath = "shake-build" shakeFilesPath :: FilePath -shakeFilesPath = shakeFilesPath -/- ".db" +shakeFilesPath = shakePath -/- ".db" configPath :: FilePath configPath = shakePath -/- "cfg" From git at git.haskell.org Fri Oct 27 00:12:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create package database directories using oracles. (6e00b02) Message-ID: <20171027001219.674A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e00b0238ebb28460f69ed0aa68c54d52d7e223a/ghc >--------------------------------------------------------------- commit 6e00b0238ebb28460f69ed0aa68c54d52d7e223a Author: Andrey Mokhov Date: Tue Jan 19 03:14:31 2016 +0000 Create package database directories using oracles. Fix #176. >--------------------------------------------------------------- 6e00b0238ebb28460f69ed0aa68c54d52d7e223a shaking-up-ghc.cabal | 1 + src/Oracles/PackageDb.hs | 23 +++++++++++++++++++++++ src/Rules/Actions.hs | 6 +++--- src/Rules/Cabal.hs | 14 -------------- src/Rules/Oracles.hs | 3 +++ src/Rules/Wrappers/GhcPkg.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 15 +++++++++++---- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Paths.hs | 19 +++++++------------ 9 files changed, 51 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 6e00b0238ebb28460f69ed0aa68c54d52d7e223a From git at git.haskell.org Fri Oct 27 00:12:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Make builder. (f31a7de) Message-ID: <20171027001219.94D7A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f31a7de2d4a6886edc64ff5bfb3301bbdee7cc2c/ghc >--------------------------------------------------------------- commit f31a7de2d4a6886edc64ff5bfb3301bbdee7cc2c Author: Andrey Mokhov Date: Tue May 10 00:32:04 2016 +0100 Add Make builder. >--------------------------------------------------------------- f31a7de2d4a6886edc64ff5bfb3301bbdee7cc2c hadrian.cabal | 1 + src/Builder.hs | 4 ++-- src/Rules/Actions.hs | 19 +++++++------------ src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Test.hs | 5 +++-- src/Settings/Args.hs | 2 ++ 7 files changed, 17 insertions(+), 18 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 160a5d0..2dfd9e9 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -84,6 +84,7 @@ executable hadrian , Settings.Builders.Hsc2Hs , Settings.Builders.HsCpp , Settings.Builders.Ld + , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default , Settings.Packages diff --git a/src/Builder.hs b/src/Builder.hs index a205067..76f0988 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -49,7 +49,7 @@ data Builder = Alex | HsCpp | Hsc2Hs | Ld - | Make + | Make FilePath | Nm | Objdump | Patch @@ -111,7 +111,7 @@ builderPath builder = case builderProvenance builder of HsColour -> fromKey "hscolour" HsCpp -> fromKey "hs-cpp" Ld -> fromKey "ld" - Make -> fromKey "make" + Make _ -> fromKey "make" Nm -> fromKey "nm" Objdump -> fromKey "objdump" Patch -> fromKey "patch" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 4928e00..4a0844b 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,7 @@ module Rules.Actions ( - build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, - removeFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, - applyPatch, fixFile, runMake, renderLibrary, renderProgram, runBuilder, - makeExecutable + build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, + removeFile, copyDirectory, createDirectory, moveDirectory, removeDirectory, + applyPatch, renderLibrary, renderProgram, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -74,6 +73,10 @@ customBuild rs opts target at Target {..} = do Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output + Make dir -> do + need [dir -/- "Makefile"] + cmd Shell cmdEcho path ["-C", dir] argList + _ -> cmd [path] argList cmdEcho :: CmdOption @@ -140,14 +143,6 @@ fixFile file f = do return new liftIO $ writeFile file contents -runMake :: FilePath -> [String] -> Action () -runMake dir args = do - need [dir -/- "Makefile"] - path <- builderPath Make - let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell cmdEcho path ["-C", dir] args - applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1121d5d..fe5b684 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -84,7 +84,7 @@ gmpRules = do [gmpBuildPath -/- "Makefile.in"] [gmpBuildPath -/- "Makefile"] - runMake gmpBuildPath ["MAKEFLAGS="] + build $ Target gmpContext (Make gmpBuildPath) [] [] createDirectory $ takeDirectory gmpLibraryH copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 20d5acf..3269a31 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -99,7 +99,7 @@ libffiRules = do -- The old build system did runMake libffiBuildPath ["MAKEFLAGS="] -- TODO: Find out why. It seems redundant, so I removed it. - runMake libffiBuildPath ["MAKEFLAGS=", "install"] + build $ Target libffiContext (Make libffiBuildPath) [] [] let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" forM_ ["ffi.h", "ffitarget.h"] $ \file -> do diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 544b5d9..7ec5e04 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -3,13 +3,14 @@ module Rules.Test (testRules) where import Base import Builder import Expression -import GHC (rts, libffi) +import GHC (compiler, rts, libffi) import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.WindowsPath import Rules.Actions import Settings.Packages import Settings.User +import Target -- TODO: clean up after testing testRules :: Rules () @@ -18,7 +19,7 @@ testRules = do needBuilder $ Ghc Compile Stage2 needBuilder $ GhcPkg Stage1 needBuilder Hpc - runMake "testsuite/tests" ["fast"] + build $ Target (vanillaContext Stage2 compiler) (Make "testsuite/tests") [] [] "test" ~> do let yesNo x = show $ if x then "YES" else "NO" diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index b7c369f..d8c3649 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -17,6 +17,7 @@ import Settings.Builders.Happy import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld +import Settings.Builders.Make import Settings.Builders.Tar import Settings.Flavours.Quick import Settings.Packages.Base @@ -66,6 +67,7 @@ defaultBuilderArgs = mconcat , hsc2hsBuilderArgs , hsCppBuilderArgs , ldBuilderArgs + , makeBuilderArgs , tarBuilderArgs ] defaultPackageArgs :: Args From git at git.haskell.org Fri Oct 27 00:12:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Shake database to shake-build/.db, rename _shake to .shake for consistency. (ddfe5bc) Message-ID: <20171027001220.C7AA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ddfe5bcdfaf7147bee73d790e42584c78485127c/ghc >--------------------------------------------------------------- commit ddfe5bcdfaf7147bee73d790e42584c78485127c Author: Andrey Mokhov Date: Sun Dec 20 04:04:07 2015 +0000 Move Shake database to shake-build/.db, rename _shake to .shake for consistency. >--------------------------------------------------------------- ddfe5bcdfaf7147bee73d790e42584c78485127c .gitignore | 7 ++----- build.bat | 4 ++-- build.sh | 6 +++--- src/Base.hs | 4 ++-- 4 files changed, 9 insertions(+), 12 deletions(-) diff --git a/.gitignore b/.gitignore index 94b9664..74a0c27 100644 --- a/.gitignore +++ b/.gitignore @@ -1,6 +1,3 @@ -*.o -*.hi -_shake/ -_build/ +.shake/ +.db/ cfg/system.config -arg/*/*.txt diff --git a/build.bat b/build.bat index b45bdde..ab26e07 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,2 @@ - at mkdir _shake 2> nul - at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake\build --lint --directory ".." %* + at mkdir .shake 2> nul + at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=.shake -o .shake/build && .shake\build --lint --directory ".." %* diff --git a/build.sh b/build.sh index cf217bd..d350779 100755 --- a/build.sh +++ b/build.sh @@ -1,6 +1,6 @@ #!/bin/bash -e root=`dirname $0` -mkdir -p $root/_shake -ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/_shake -o $root/_shake/build -$root/_shake/build --lint --directory $root/.. $@ +mkdir -p $root/.shake +ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/.shake -o $root/.shake/build +$root/.shake/build --lint --directory $root/.. $@ diff --git a/src/Base.hs b/src/Base.hs index e95aa94..33b01bd 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -49,10 +49,10 @@ configPath :: FilePath configPath = shakePath -/- "cfg" bootPackageConstraints :: FilePath -bootPackageConstraints = shakeFilesPath ++ "boot-package-constraints" +bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" packageDependencies :: FilePath -packageDependencies = shakeFilesPath ++ "package-dependencies" +packageDependencies = shakeFilesPath -/- "package-dependencies" -- Utility functions -- Find and replace all occurrences of a value in a list From git at git.haskell.org Fri Oct 27 00:12:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix "dirs" to "dir" for gmp and iconv libraries (36b7f4d) Message-ID: <20171027001223.356A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/36b7f4de03fd661e6439b84a3d03b4ca00ca6bcc/ghc >--------------------------------------------------------------- commit 36b7f4de03fd661e6439b84a3d03b4ca00ca6bcc Author: Karel Gardas Date: Tue Jan 19 07:38:52 2016 +0100 fix "dirs" to "dir" for gmp and iconv libraries >--------------------------------------------------------------- 36b7f4de03fd661e6439b84a3d03b4ca00ca6bcc cfg/system.config.in | 8 ++++---- src/Oracles/Config/Setting.hs | 16 ++++++++-------- src/Rules/Gmp.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 8 ++++---- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- 5 files changed, 22 insertions(+), 22 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 126387f..0eb775a 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -100,11 +100,11 @@ conf-ld-linker-args-stage2 = @CONF_LD_LINKER_OPTS_STAGE2@ # Include and library directories: #================================= -iconv-include-dirs = @ICONV_INCLUDE_DIRS@ -iconv-lib-dirs = @ICONV_LIB_DIRS@ +iconv-include-dir = @ICONV_INCLUDE_DIRS@ +iconv-lib-dir = @ICONV_LIB_DIRS@ -gmp-include-dirs = @GMP_INCLUDE_DIRS@ -gmp-lib-dirs = @GMP_LIB_DIRS@ +gmp-include-dir = @GMP_INCLUDE_DIRS@ +gmp-lib-dir = @GMP_LIB_DIRS@ use-system-ffi = @UseSystemLibFFI@ ffi-include-dir = @FFIIncludeDir@ diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index f4540cc..3502929 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -49,16 +49,16 @@ data Setting = BuildArch | TargetVendor | FfiIncludeDir | FfiLibDir + | GmpIncludeDir + | GmpLibDir + | IconvIncludeDir + | IconvLibDir data SettingList = ConfCcArgs Stage | ConfCppArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage - | GmpIncludeDirs - | GmpLibDirs | HsCppArgs - | IconvIncludeDirs - | IconvLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of @@ -92,6 +92,10 @@ setting key = askConfig $ case key of TargetVendor -> "target-vendor" FfiIncludeDir -> "ffi-include-dir" FfiLibDir -> "ffi-lib-dir" + GmpIncludeDir -> "gmp-include-dir" + GmpLibDir -> "gmp-lib-dir" + IconvIncludeDir -> "iconv-include-dir" + IconvLibDir -> "iconv-lib-dir" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -99,11 +103,7 @@ settingList key = fmap words $ askConfig $ case key of ConfCppArgs stage -> "conf-cpp-args-" ++ stageString stage ConfGccLinkerArgs stage -> "conf-gcc-linker-args-" ++ stageString stage ConfLdLinkerArgs stage -> "conf-ld-linker-args-" ++ stageString stage - GmpIncludeDirs -> "gmp-include-dirs" - GmpLibDirs -> "gmp-lib-dirs" HsCppArgs -> "hs-cpp-args" - IconvIncludeDirs -> "iconv-include-dirs" - IconvLibDirs -> "iconv-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index ec14b36..702e645 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -62,10 +62,10 @@ configureArguments = do configureIntGmpArguments :: Action [String] configureIntGmpArguments = do - includes <- settingList GmpIncludeDirs - libs <- settingList GmpLibDirs - return $ map ("--with-gmp-includes=" ++) includes - ++ map ("--with-gmp-libraries=" ++) libs + includes <- setting GmpIncludeDir + libs <- setting GmpLibDir + return $ map ("--with-gmp-includes=" ++) [includes] + ++ map ("--with-gmp-libraries=" ++) [libs] -- TODO: we rebuild gmp every time. gmpRules :: Rules () diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 06787c5..51d0e6b 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -79,10 +79,10 @@ configureArgs = do , conf "LDFLAGS" ldFlags , conf "CPPFLAGS" cppFlags , appendSubD "--gcc-options" $ cFlags <> ldFlags - , conf "--with-iconv-includes" $ argSettingList IconvIncludeDirs - , conf "--with-iconv-libraries" $ argSettingList IconvLibDirs - , conf "--with-gmp-includes" $ argSettingList GmpIncludeDirs - , conf "--with-gmp-libraries" $ argSettingList GmpLibDirs + , conf "--with-iconv-includes" $ argSetting IconvIncludeDir + , conf "--with-iconv-libraries" $ argSetting IconvLibDir + , conf "--with-gmp-includes" $ argSetting GmpIncludeDir + , conf "--with-gmp-libraries" $ argSetting GmpLibDir , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" $ argStagedBuilderPath Gcc ] diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index c4e518b..4529af8 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -17,7 +17,7 @@ hsc2hsBuilderArgs :: Args hsc2hsBuilderArgs = builder Hsc2Hs ? do stage <- getStage ccPath <- lift . builderPath $ Gcc stage - gmpDirs <- getSettingList GmpIncludeDirs + gmpDir <- getSetting GmpIncludeDir cFlags <- getCFlags lFlags <- getLFlags top <- getTopDirectory @@ -32,7 +32,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" - , append $ map ("-I" ++) gmpDirs + , append $ map ("-I" ++) [gmpDir] , append $ map ("--cflag=" ++) cFlags , append $ map ("--lflag=" ++) lFlags , notStage0 ? crossCompiling ? arg "--cross-compile" From git at git.haskell.org Fri Oct 27 00:12:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (5975b50) Message-ID: <20171027001224.3ECA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5975b50e948df0c680b56c077494f55599131fa1/ghc >--------------------------------------------------------------- commit 5975b50e948df0c680b56c077494f55599131fa1 Author: Andrey Mokhov Date: Sun Dec 20 04:04:28 2015 +0000 Clean up. >--------------------------------------------------------------- 5975b50e948df0c680b56c077494f55599131fa1 src/GHC.hs | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 06140b1..0279197 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,7 +1,7 @@ module GHC ( - array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, - compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, + array, base, binary, bytestring, cabal, compiler, containers, compareSizes, + deepseq, deriveConstants, directory, dllSplit, filepath, genapply, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, @@ -20,25 +20,24 @@ import Stage -- which can be overridden in Settings/User.hs. defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, ghcBoot, binary, bytestring, cabal, compiler - , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcCabal, ghci, ghcPkg, ghcPrim + [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes + , deepseq, deriveConstants, directory, dllSplit, filepath, genapply + , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin , integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty , primitive , process, runghc, stm, templateHaskell, terminfo, time , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) -array, base, ghcBoot, binary, bytestring, cabal, compiler, containers, - compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, - genapply, genprimopcode, ghc, ghcCabal, ghcPkg, ghcPrim, ghcPwd, +array, base, binary, bytestring, cabal, compiler, containers, compareSizes, + deepseq, deriveConstants, directory, dllSplit, filepath, genapply, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, mkUserGuidePart, parallel, pretty, primitive, process, + integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" -ghcBoot = library "ghc-boot" binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" @@ -53,8 +52,9 @@ filepath = library "filepath" genapply = utility "genapply" genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" +ghcBoot = library "ghc-boot" ghcCabal = utility "ghc-cabal" -ghci = library "ghci" `setPath` "libraries/ghci" +ghci = library "ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" ghcPwd = utility "ghc-pwd" From git at git.haskell.org Fri Oct 27 00:12:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing Settings.Flavours.Quick module. (6da6b45) Message-ID: <20171027001223.56F153A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6da6b454c1a8ff2df7e54a165b28e103d5e6a0f2/ghc >--------------------------------------------------------------- commit 6da6b454c1a8ff2df7e54a165b28e103d5e6a0f2 Author: Andrey Mokhov Date: Tue May 10 01:05:59 2016 +0100 Add missing Settings.Flavours.Quick module. >--------------------------------------------------------------- 6da6b454c1a8ff2df7e54a165b28e103d5e6a0f2 hadrian.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/hadrian.cabal b/hadrian.cabal index 2dfd9e9..5c13f7a 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -87,6 +87,7 @@ executable hadrian , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default + , Settings.Flavours.Quick , Settings.Packages , Settings.Packages.Base , Settings.Packages.Compiler From git at git.haskell.org Fri Oct 27 00:12:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix configureBuilderArgs name. (e19cd9f) Message-ID: <20171027001226.C6A0C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e19cd9ffd1cf551529d8f00a4715d2a53048154a/ghc >--------------------------------------------------------------- commit e19cd9ffd1cf551529d8f00a4715d2a53048154a Author: Andrey Mokhov Date: Tue May 10 01:06:35 2016 +0100 Fix configureBuilderArgs name. >--------------------------------------------------------------- e19cd9ffd1cf551529d8f00a4715d2a53048154a src/Settings/Args.hs | 2 +- src/Settings/Builders/Configure.hs | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index d8c3649..1e239a4 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -53,7 +53,7 @@ defaultBuilderArgs = mconcat [ alexBuilderArgs , arBuilderArgs , ccBuilderArgs - , configureArgs + , configureBuilderArgs , deriveConstantsBuilderArgs , genApplyBuilderArgs , genPrimopCodeBuilderArgs diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 813b79d..b0cb4bd 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -1,4 +1,4 @@ -module Settings.Builders.Configure (configureArgs) where +module Settings.Builders.Configure (configureBuilderArgs) where import Base import Expression @@ -6,8 +6,8 @@ import Oracles.Config.Setting import Predicates (builder) import Settings -configureArgs :: Args -configureArgs = mconcat +configureBuilderArgs :: Args +configureBuilderArgs = mconcat [ builder (Configure libffiBuildPath) ? do top <- getTopDirectory targetPlatform <- getSetting TargetPlatform From git at git.haskell.org Fri Oct 27 00:12:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #183 from kgardas/fix_dirs_to_dir (875d9ca) Message-ID: <20171027001226.C013D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/875d9ca47a82c58c2e5e99864f67dc5f3559dffc/ghc >--------------------------------------------------------------- commit 875d9ca47a82c58c2e5e99864f67dc5f3559dffc Merge: 6e00b02 36b7f4d Author: Andrey Mokhov Date: Tue Jan 19 08:54:29 2016 +0000 Merge pull request #183 from kgardas/fix_dirs_to_dir fix "dirs" to "dir" for gmp and iconv libraries >--------------------------------------------------------------- 875d9ca47a82c58c2e5e99864f67dc5f3559dffc cfg/system.config.in | 8 ++++---- src/Oracles/Config/Setting.hs | 16 ++++++++-------- src/Rules/Gmp.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 8 ++++---- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- 5 files changed, 22 insertions(+), 22 deletions(-) From git at git.haskell.org Fri Oct 27 00:12:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable profiling and dynamic ways temporarily. (f4fb52d) Message-ID: <20171027001227.C2B6D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4fb52d17a91d97b37ac5352beb32153a8345f45/ghc >--------------------------------------------------------------- commit f4fb52d17a91d97b37ac5352beb32153a8345f45 Author: Andrey Mokhov Date: Sun Dec 20 04:06:07 2015 +0000 Disable profiling and dynamic ways temporarily. >--------------------------------------------------------------- f4fb52d17a91d97b37ac5352beb32153a8345f45 src/Settings/User.hs | 3 ++- src/Settings/Ways.hs | 3 +++ 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 5159bce..0dffbfd 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -22,8 +22,9 @@ userKnownPackages :: [Package] userKnownPackages = [] -- Control which ways libraries and rts are built +-- TODO: skip profiling for speed, skip dynamic since it's currently broken userLibWays :: Ways -userLibWays = mempty +userLibWays = remove [profiling, dynamic] userRtsWays :: Ways userRtsWays = mempty diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index ad42cea..7788242 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -4,6 +4,9 @@ import Expression import Predicates import Settings.User +-- TODO: use a single expression Ways parameterised by package instead of +-- expressions libWays and rtsWays + -- Combining default ways with user modifications getLibWays :: Expr [Way] getLibWays = fromDiffExpr $ defaultLibWays <> userLibWays From git at git.haskell.org Fri Oct 27 00:12:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add makeBuilderArgs. (d27501d) Message-ID: <20171027001230.4ACC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d27501d1f279c145fd4c76809c6fab272f53cc4c/ghc >--------------------------------------------------------------- commit d27501d1f279c145fd4c76809c6fab272f53cc4c Author: Andrey Mokhov Date: Tue May 10 01:07:25 2016 +0100 Add makeBuilderArgs. >--------------------------------------------------------------- d27501d1f279c145fd4c76809c6fab272f53cc4c src/Settings/Builders/Make.hs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs new file mode 100644 index 0000000..85f16ac --- /dev/null +++ b/src/Settings/Builders/Make.hs @@ -0,0 +1,11 @@ +module Settings.Builders.Make (makeBuilderArgs) where + +import Expression +import Predicates (builder) +import Settings + +makeBuilderArgs :: Args +makeBuilderArgs = mconcat + [ builder (Make "testsuite/tests") ? arg "fast" + , builder (Make gmpBuildPath ) ? arg "MAKEFLAGS=" + , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=", "install"] ] From git at git.haskell.org Fri Oct 27 00:12:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CI regression, minor revision. (8f68b8b) Message-ID: <20171027001230.73C693A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f68b8bc8dc40a17eb8c0816437a4b474b9def78/ghc >--------------------------------------------------------------- commit 8f68b8bc8dc40a17eb8c0816437a4b474b9def78 Author: Andrey Mokhov Date: Tue Jan 19 09:34:35 2016 +0000 Fix CI regression, minor revision. See #183. >--------------------------------------------------------------- 8f68b8bc8dc40a17eb8c0816437a4b474b9def78 cfg/system.config.in | 2 +- src/Rules/Gmp.hs | 4 ++-- src/Rules/Libffi.hs | 8 ++++---- src/Settings/Builders/Hsc2Hs.hs | 2 +- 4 files changed, 8 insertions(+), 8 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 0eb775a..43730a2 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -106,7 +106,7 @@ iconv-lib-dir = @ICONV_LIB_DIRS@ gmp-include-dir = @GMP_INCLUDE_DIRS@ gmp-lib-dir = @GMP_LIB_DIRS@ -use-system-ffi = @UseSystemLibFFI@ +use-system-ffi = @UseSystemLibFFI@ ffi-include-dir = @FFIIncludeDir@ ffi-lib-dir = @FFILibDir@ diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 702e645..b6bfdf0 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -64,8 +64,8 @@ configureIntGmpArguments :: Action [String] configureIntGmpArguments = do includes <- setting GmpIncludeDir libs <- setting GmpLibDir - return $ map ("--with-gmp-includes=" ++) [includes] - ++ map ("--with-gmp-libraries=" ++) [libs] + return $ map ("--with-gmp-includes=" ++) (words includes) + ++ map ("--with-gmp-libraries=" ++) (words libs) -- TODO: we rebuild gmp every time. gmpRules :: Rules () diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 97ebc2d..0f4e05a 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -71,13 +71,13 @@ libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - ffi_header_dir <- setting FfiIncludeDir - use_system_ffi <- flag UseSystemFfi - if use_system_ffi + ffiHeaderDir <- setting FfiIncludeDir + useSystemFfi <- flag UseSystemFfi + if useSystemFfi then do putBuild "| System supplied FFI library will be used" forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = ffi_header_dir -/- file + let src = ffiHeaderDir -/- file copyFile src (rtsBuildPath -/- file) putSuccess $ "| Successfully copied system supplied FFI library header files" else do diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 4529af8..ffa3b1a 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -32,7 +32,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" - , append $ map ("-I" ++) [gmpDir] + , append . map ("-I" ++) $ words gmpDir , append $ map ("--cflag=" ++) cFlags , append $ map ("--lflag=" ++) lFlags , notStage0 ? crossCompiling ? arg "--cross-compile" From git at git.haskell.org Fri Oct 27 00:12:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (a66be35) Message-ID: <20171027001231.7E62D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a66be35210083bbc2646b38df3a224a77f37dbf1/ghc >--------------------------------------------------------------- commit a66be35210083bbc2646b38df3a224a77f37dbf1 Author: Andrey Mokhov Date: Sun Dec 20 04:09:14 2015 +0000 Clean up. >--------------------------------------------------------------- a66be35210083bbc2646b38df3a224a77f37dbf1 src/Rules/Dependencies.hs | 1 - src/Settings/Builders/GhcCabal.hs | 18 +++++++++--------- 2 files changed, 9 insertions(+), 10 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 1def1ac..996d927 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -24,7 +24,6 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = hDepFile %> \file -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) $ need [platformH] - putBuild $ "srcs = " ++ show srcs need srcs if srcs == [] then writeFileChanged file "" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 01b061e..151cd5f 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -40,12 +40,12 @@ ghcCabalHsColourArgs = builder GhcCabalHsColour ? do -- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do - ways <- getWays - ghci <- lift ghcWithInterpreter + ways <- getWays + withGhci <- lift ghcWithInterpreter append [ if vanilla `elem` ways then "--enable-library-vanilla" else "--disable-library-vanilla" - , if vanilla `elem` ways && ghci && not dynamicGhcPrograms + , if vanilla `elem` ways && withGhci && not dynamicGhcPrograms then "--enable-library-for-ghci" else "--disable-library-for-ghci" , if profiling `elem` ways @@ -224,12 +224,12 @@ needDll0 stage pkg = do -- * otherwise, we must collapse it into one space-separated string. dll0Args :: Args dll0Args = do - stage <- getStage - pkg <- getPackage - dll0 <- lift $ needDll0 stage pkg - ghci <- lift ghcWithInterpreter - arg . unwords . concat $ [ modules | dll0 ] - ++ [ ghciModules | dll0 && ghci ] -- see #9552 + stage <- getStage + pkg <- getPackage + dll0 <- lift $ needDll0 stage pkg + withGhci <- lift ghcWithInterpreter + arg . unwords . concat $ [ modules | dll0 ] + ++ [ ghciModules | dll0 && withGhci ] -- see #9552 where modules = [ "Annotations" , "ApiAnnotation" From git at git.haskell.org Fri Oct 27 00:12:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do not unify paths on each -/- invocation. (6e953f1) Message-ID: <20171027001233.CF27F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e953f10e2c445addda3ade10191c60d90546ef4/ghc >--------------------------------------------------------------- commit 6e953f10e2c445addda3ade10191c60d90546ef4 Author: Andrey Mokhov Date: Tue May 10 02:26:26 2016 +0100 Do not unify paths on each -/- invocation. See #220. >--------------------------------------------------------------- 6e953f10e2c445addda3ade10191c60d90546ef4 src/Base.hs | 4 ++-- src/Oracles/ModuleFiles.hs | 4 +++- src/Oracles/WindowsPath.hs | 2 +- src/Rules/Wrappers/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Paths.hs | 21 ++++++++------------- 6 files changed, 16 insertions(+), 19 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 1fcbae7..bd80f47 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -87,9 +87,9 @@ versionToInt s = major * 1000 + minor * 10 + patch unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx --- | Combine paths using '' and apply 'unifyPath' to the result +-- | Combine paths with a forward slash regardless of platform. (-/-) :: FilePath -> FilePath -> FilePath -a -/- b = unifyPath $ a b +a -/- b = a ++ '/' : b infixr 6 -/- diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 652eb9a..897b2e0 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -39,7 +39,9 @@ decodeModule = splitFileName . replaceEq '.' '/' -- > encodeModule "./" "Prelude" == "Prelude" -- > uncurry encodeModule (decodeModule name) == name encodeModule :: FilePath -> String -> String -encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file +encodeModule dir file + | dir == "./" = replaceEq '/' '.' $ takeBaseName file + | otherwise = replaceEq '/' '.' $ dir ++ takeBaseName file -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index a0343fb..e252bba 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -25,7 +25,7 @@ fixAbsolutePathOnWindows path = do then do let (dir, file) = splitFileName path winDir <- askOracle $ WindowsPath dir - return $ winDir -/- file + return $ winDir ++ file else return path diff --git a/src/Rules/Wrappers/Ghc.hs b/src/Rules/Wrappers/Ghc.hs index 343f780..7338450 100644 --- a/src/Rules/Wrappers/Ghc.hs +++ b/src/Rules/Wrappers/Ghc.hs @@ -11,4 +11,4 @@ ghcWrapper program = do return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) - ++ " -B" ++ (top -/- "inplace" -/- "lib") ++ " ${1+\"$@\"}" ] + ++ " -B" ++ (top -/- "inplace/lib") ++ " ${1+\"$@\"}" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 9f6c6e2..faeb99d 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -128,7 +128,7 @@ with b = specified b ? do top <- getTopDirectory path <- getBuilderPath b lift $ needBuilder b - append [withBuilderKey b ++ top -/- path] + arg $ withBuilderKey b ++ unifyPath (top path) withStaged :: (Stage -> Builder) -> Args withStaged sb = with . sb =<< getStage diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 7174a94..288544b 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -12,11 +12,6 @@ import GHC import Oracles.PackageData import Settings.User --- A more efficient version of '-/-' which assumes that given FilePaths have --- already been unified. See #218. TODO: Switch to 'newtype FilePath'. -(~/~) :: FilePath -> FilePath -> FilePath -x ~/~ y = x ++ '/' : y - shakeFilesPath :: FilePath shakeFilesPath = buildRootPath -/- "hadrian/shake-files" @@ -29,17 +24,17 @@ packageDependencies = shakeFilesPath -/- "package-dependencies" -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath buildPath context at Context {..} = - buildRootPath ~/~ contextDirectory context ~/~ pkgPath package + buildRootPath -/- contextDirectory context -/- pkgPath package -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath -pkgDataFile context = buildPath context ~/~ "package-data.mk" +pkgDataFile context = buildPath context -/- "package-data.mk" -- | Path to the haddock file of a given 'Context', e.g.: -- ".build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = - buildPath context ~/~ "doc/html" ~/~ name ~/~ name <.> "haddock" + buildPath context -/- "doc/html" -/- name -/- name <.> "haddock" where name = pkgNameString package -- | Path to the library file of a given 'Context', e.g.: @@ -65,11 +60,11 @@ pkgFile :: Context -> String -> String -> Action FilePath pkgFile context prefix suffix = do let path = buildPath context componentId <- pkgData $ ComponentId path - return $ path ~/~ prefix ++ componentId ++ suffix + return $ path -/- prefix ++ componentId ++ suffix -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath ~/~ "stage1/gmp" +gmpBuildPath = buildRootPath -/- "stage1/gmp" -- | Path to the GMP library. gmpLibrary :: FilePath @@ -85,7 +80,7 @@ gmpObjects = gmpBuildPath -/- "objs" -- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath -gmpBuildInfoPath = pkgPath integerGmp ~/~ "integer-gmp.buildinfo" +gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" -- | Build directory for in-tree libffi library. libffiBuildPath :: FilePath @@ -95,11 +90,11 @@ libffiBuildPath = buildRootPath -/- "stage1/libffi" -- StageN, N > 0, share the same packageDbDirectory -- | Path to package database directory of a given 'Stage'. packageDbDirectory :: Stage -> FilePath -packageDbDirectory Stage0 = buildRootPath ~/~ "stage0/bootstrapping.conf" +packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" -- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do componentId <- pkgData . ComponentId $ buildPath context - return $ packageDbDirectory stage ~/~ componentId <.> "conf" + return $ packageDbDirectory stage -/- componentId <.> "conf" From git at git.haskell.org Fri Oct 27 00:12:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant case. (bbbf03c) Message-ID: <20171027001234.280223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbbf03c99d8c0264317aa5527baec180caf94388/ghc >--------------------------------------------------------------- commit bbbf03c99d8c0264317aa5527baec180caf94388 Author: Andrey Mokhov Date: Tue Jan 19 11:56:35 2016 +0000 Drop redundant case. [skip ci] >--------------------------------------------------------------- bbbf03c99d8c0264317aa5527baec180caf94388 src/Settings/Packages/Rts.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 58b76cf..e41e2bf 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -23,11 +23,9 @@ rtsLibffiLibraryName = do use_system_ffi <- flag UseSystemFfi windows <- windowsHost case (use_system_ffi, windows) of - (True, False) -> return "ffi" + (True , False) -> return "ffi" (False, False) -> return "Cffi" - (_, True) -> return "Cffi-6" - (_, _) -> error "Unsupported FFI library configuration case" - + (_ , True ) -> return "Cffi-6" rtsPackageArgs :: Args rtsPackageArgs = package rts ? do From git at git.haskell.org Fri Oct 27 00:12:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add matchPackageNames to match packages and package names. (341f711) Message-ID: <20171027001235.31CCB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/341f711761e2ec9680613e81ad65335e61713f08/ghc >--------------------------------------------------------------- commit 341f711761e2ec9680613e81ad65335e61713f08 Author: Andrey Mokhov Date: Sun Dec 20 04:11:35 2015 +0000 Add matchPackageNames to match packages and package names. >--------------------------------------------------------------- 341f711761e2ec9680613e81ad65335e61713f08 src/Package.hs | 8 +++++++- src/Rules/Data.hs | 3 +-- src/Settings/Packages.hs | 7 ++++--- 3 files changed, 12 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index f64daee..8415bf1 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,6 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} module Package ( - Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility + Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility, + matchPackageNames ) where import Base @@ -45,6 +46,11 @@ instance Eq Package where instance Ord Package where compare = compare `on` pkgName +-- Given a sorted list of packages and a sorted list of package names, returns +-- packages whose names appear in the list of names +matchPackageNames :: [Package] -> [PackageName] -> [Package] +matchPackageNames = intersectOrd (\pkg name -> compare (pkgName pkg) name) + -- Instances for storing in the Shake database instance Binary Package instance Hashable Package where diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 95ac426..b6925d0 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -31,8 +31,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- We configure packages in the order of their dependencies deps <- packageDeps pkg pkgs <- interpretPartial target getPackages - let cmp p name = compare (pkgName p) name - depPkgs = intersectOrd cmp (sort pkgs) deps + let depPkgs = matchPackageNames (sort pkgs) deps need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] need [cabalFile] diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 718b8de..df52715 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -18,7 +18,7 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ ghcBoot, binary, cabal, compiler, ghc, ghcCabal, ghcPkg + [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] , stage0 ? append [deriveConstants, genapply, genprimopcode, hp2ps] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] @@ -41,9 +41,10 @@ packagesStage2 = mconcat [ append [ghcTags] , buildHaddock ? append [haddock] ] +-- TODO: switch to Set Package as the order of packages should not matter? knownPackages :: [Package] -knownPackages = defaultKnownPackages ++ userKnownPackages +knownPackages = sort $ defaultKnownPackages ++ userKnownPackages --- Note: this is slow but we keep it simple as there not too many packages (30) +-- Note: this is slow but we keep it simple as there are just ~50 packages findKnownPackage :: PackageName -> Maybe Package findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Fri Oct 27 00:12:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update comments. (7239000) Message-ID: <20171027001237.EBC7B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7239000ffaeada9c33343aeddc28e121c3366af4/ghc >--------------------------------------------------------------- commit 7239000ffaeada9c33343aeddc28e121c3366af4 Author: Andrey Mokhov Date: Tue May 10 02:31:16 2016 +0100 Update comments. [skip ci] >--------------------------------------------------------------- 7239000ffaeada9c33343aeddc28e121c3366af4 src/Oracles/ModuleFiles.hs | 4 ++-- src/Rules/Dependencies.hs | 8 ++++---- src/Rules/Library.hs | 4 ++-- src/Settings/Paths.hs | 8 ++++---- 4 files changed, 12 insertions(+), 12 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 897b2e0..e77d2ba 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -45,10 +45,10 @@ encodeModule dir file -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) --- ".build/stage1/compiler/build/Lexer.hs" +-- "_build/stage1/compiler/build/Lexer.hs" -- == Just ("compiler/parser/Lexer.x", Alex) -- findGenerator (Context Stage1 base vanilla) --- ".build/stage1/base/build/Prelude.hs" +-- "_build/stage1/base/build/Prelude.hs" -- == Nothing findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder)) findGenerator Context {..} file = do diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index f5d781a..78f4d40 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -49,8 +49,8 @@ buildPackageDependencies rs context at Context {..} = -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' -- to its dependencies. For example, in vanillaContext Stage1 rts: --- * "Task.c" -> ".build/stage1/rts/Task.c.deps" --- * ".build/stage1/rts/AutoApply.cmm" -> ".build/stage1/rts/AutoApply.cmm.deps" +-- * "Task.c" -> "_build/stage1/rts/Task.c.deps" +-- * "_build/stage1/rts/AutoApply.cmm" -> "_build/stage1/rts/AutoApply.cmm.deps" src2dep :: Context -> FilePath -> FilePath src2dep context src | buildRootPath `isPrefixOf` src = src <.> "deps" @@ -58,8 +58,8 @@ src2dep context src -- Given a 'Context' and a 'FilePath' to a file with dependencies, compute the -- 'FilePath' to the source file. For example, in vanillaContext Stage1 rts: --- * ".build/stage1/rts/Task.c.deps" -> "Task.c" --- * ".build/stage1/rts/AutoApply.cmm.deps" -> ".build/stage1/rts/AutoApply.cmm" +-- * "_build/stage1/rts/Task.c.deps" -> "Task.c" +-- * "_build/stage1/rts/AutoApply.cmm.deps" -> "_build/stage1/rts/AutoApply.cmm" dep2src :: Context -> FilePath -> FilePath dep2src context at Context {..} dep | takeBaseName dep `elem` [ "AutoApply.cmm", "Evac_thr.c", "Scav_thr.c" ] = src diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 0538e4e..a45b591 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -76,8 +76,8 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do -- TODO: Get rid of code duplication and simplify. See also src2dep. -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' -- to its object file. For example, in Context Stage1 rts threaded: --- * "Task.c" -> ".build/stage1/rts/Task.thr_o" --- * ".build/stage1/rts/sm/Evac_thr.c" -> ".build/stage1/rts/sm/Evac_thr.thr_o" +-- * "Task.c" -> "_build/stage1/rts/Task.thr_o" +-- * "_build/stage1/rts/sm/Evac_thr.c" -> "_build/stage1/rts/sm/Evac_thr.thr_o" objFile :: Context -> FilePath -> FilePath objFile context at Context {..} src | buildRootPath `isPrefixOf` src = src -<.> osuf way diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 288544b..c39b12b 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -31,28 +31,28 @@ pkgDataFile :: Context -> FilePath pkgDataFile context = buildPath context -/- "package-data.mk" -- | Path to the haddock file of a given 'Context', e.g.: --- ".build/stage1/libraries/array/doc/html/array/array.haddock". +-- "_build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = buildPath context -/- "doc/html" -/- name -/- name <.> "haddock" where name = pkgNameString package -- | Path to the library file of a given 'Context', e.g.: --- ".build/stage1/libraries/array/build/libHSarray-0.5.1.0.a". +-- "_build/stage1/libraries/array/build/libHSarray-0.5.1.0.a". pkgLibraryFile :: Context -> Action FilePath pkgLibraryFile context at Context {..} = do extension <- libsuf way pkgFile context "libHS" extension -- | Path to the auxiliary library file of a given 'Context', e.g.: --- ".build/stage1/compiler/build/libHSghc-8.1-0.a". +-- "_build/stage1/compiler/build/libHSghc-8.1-0.a". pkgLibraryFile0 :: Context -> Action FilePath pkgLibraryFile0 context at Context {..} = do extension <- libsuf way pkgFile context "libHS" ("-0" ++ extension) -- | Path to the GHCi library file of a given 'Context', e.g.: --- ".build/stage1/libraries/array/build/HSarray-0.5.1.0.o". +-- "_build/stage1/libraries/array/build/HSarray-0.5.1.0.o". pkgGhciLibraryFile :: Context -> Action FilePath pkgGhciLibraryFile context = pkgFile context "HS" ".o" From git at git.haskell.org Fri Oct 27 00:12:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (11f78b1) Message-ID: <20171027001238.96A5B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/11f78b18b914bb72e1f1cff75cadc9d7c4012ac2/ghc >--------------------------------------------------------------- commit 11f78b18b914bb72e1f1cff75cadc9d7c4012ac2 Author: Andrey Mokhov Date: Tue Jan 19 12:02:52 2016 +0000 Minor revision. [skip ci] >--------------------------------------------------------------- 11f78b18b914bb72e1f1cff75cadc9d7c4012ac2 src/Settings/Packages/Rts.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e41e2bf..f67b709 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,9 +20,9 @@ rtsConf = pkgPath rts -/- targetDirectory Stage1 rts -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do - use_system_ffi <- flag UseSystemFfi - windows <- windowsHost - case (use_system_ffi, windows) of + useSystemFfi <- flag UseSystemFfi + windows <- windowsHost + case (useSystemFfi, windows) of (True , False) -> return "ffi" (False, False) -> return "Cffi" (_ , True ) -> return "Cffi-6" From git at git.haskell.org Fri Oct 27 00:12:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix boot package constraints. (3ee9ae2) Message-ID: <20171027001239.3E8723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ee9ae25495416fa212741f062e56016c7c573c4/ghc >--------------------------------------------------------------- commit 3ee9ae25495416fa212741f062e56016c7c573c4 Author: Andrey Mokhov Date: Sun Dec 20 04:12:21 2015 +0000 Fix boot package constraints. >--------------------------------------------------------------- 3ee9ae25495416fa212741f062e56016c7c573c4 src/Rules/Cabal.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 7ccb1b8..d8e557b 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,11 +1,12 @@ module Rules.Cabal (cabalRules) where -import Expression import Data.Version import Distribution.Package hiding (Package) import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Verbosity +import Expression +import GHC import Package hiding (library) import Settings @@ -13,7 +14,8 @@ cabalRules :: Rules () cabalRules = do -- Cache boot package constraints (to be used in cabalArgs) bootPackageConstraints %> \out -> do - pkgs <- interpretWithStage Stage0 getPackages + bootPkgs <- interpretWithStage Stage0 getPackages + let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg From git at git.haskell.org Fri Oct 27 00:12:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add predicate input, rename predicate file to output. (caf0d6a) Message-ID: <20171027001241.9F66F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8/ghc >--------------------------------------------------------------- commit caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8 Author: Andrey Mokhov Date: Wed May 11 23:29:15 2016 +0100 Add predicate input, rename predicate file to output. See #245. >--------------------------------------------------------------- caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8 src/Predicates.hs | 11 ++++++--- src/Settings/Builders/DeriveConstants.hs | 16 +++++++------- src/Settings/Builders/GenPrimopCode.hs | 38 ++++++++++++++++---------------- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Packages/Rts.hs | 14 ++++++------ src/Settings/Packages/RunGhc.hs | 4 ++-- 7 files changed, 46 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8 From git at git.haskell.org Fri Oct 27 00:12:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: do not pass --with-intree-gmp to configure when system gmp is used (dc8dbcc) Message-ID: <20171027001242.433613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dc8dbcc5a9c621a3eb4fb99b0e7d24b2e1a5a967/ghc >--------------------------------------------------------------- commit dc8dbcc5a9c621a3eb4fb99b0e7d24b2e1a5a967 Author: Karel Gardas Date: Tue Jan 19 21:42:08 2016 +0100 do not pass --with-intree-gmp to configure when system gmp is used >--------------------------------------------------------------- dc8dbcc5a9c621a3eb4fb99b0e7d24b2e1a5a967 src/Settings/Packages/IntegerGmp.hs | 18 +++++++++++++----- 1 file changed, 13 insertions(+), 5 deletions(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 7122457..fbb7101 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -4,7 +4,9 @@ import Base import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) +import Settings.Builders.Common import Settings.Paths +import Oracles.Config.Setting -- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? @@ -14,11 +16,17 @@ import Settings.Paths integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" + gmp_includedir <- getSetting GmpIncludeDir + gmp_libdir <- getSetting GmpLibDir + let gmp_args = if (gmp_includedir == "" && gmp_libdir == "") + then + [ arg "--configure-option=--with-intree-gmp" ] + else + [] + mconcat [ builder GhcCabal ? mconcat - [ arg "--configure-option=--with-intree-gmp" - , appendSub "--configure-option=CFLAGS" [includeGmp] - , appendSub "--gcc-options" [includeGmp] ] + (gmp_args ++ + [ appendSub "--configure-option=CFLAGS" [includeGmp] + , appendSub "--gcc-options" [includeGmp] ] ) , builderGcc ? arg includeGmp ] - where - From git at git.haskell.org Fri Oct 27 00:12:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix broken parallel build: track dependencies due to -package-id flags. (361c3c2) Message-ID: <20171027001242.BB1A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/361c3c2b250bd016ec16494b6f89b4971241e41e/ghc >--------------------------------------------------------------- commit 361c3c2b250bd016ec16494b6f89b4971241e41e Author: Andrey Mokhov Date: Sun Dec 20 04:13:38 2015 +0000 Fix broken parallel build: track dependencies due to -package-id flags. >--------------------------------------------------------------- 361c3c2b250bd016ec16494b6f89b4971241e41e src/Rules.hs | 24 ++---------------------- src/Rules/Program.hs | 26 +++++++++++++++++++++++--- src/Settings/TargetDirectory.hs | 17 ++++++++++++++++- 3 files changed, 41 insertions(+), 26 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 90769c1..505b8a5 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,11 +1,9 @@ module Rules (generateTargets, packageRules) where import Expression -import Oracles import Rules.Package import Rules.Resources import Settings -import Settings.Builders.GhcCabal -- generateTargets needs top-level build targets generateTargets :: Rules () @@ -14,29 +12,11 @@ generateTargets = action $ do pkgs <- interpretWithStage stage getPackages let (libPkgs, programPkgs) = partition isLibrary pkgs libTargets <- fmap concat . forM libPkgs $ \pkg -> do - let target = PartialTarget stage pkg - buildPath = targetPath stage pkg -/- "build" - compId <- interpretPartial target $ getPkgData ComponentId - needGhciLib <- interpretPartial target $ getPkgData BuildGhciLib + let target = PartialTarget stage pkg needHaddock <- interpretPartial target buildHaddock - ways <- interpretPartial target getWays - let ghciLib = buildPath -/- "HS" ++ compId <.> "o" - haddock = pkgHaddockFile pkg - libs <- fmap concat . forM ways $ \way -> do - extension <- libsuf way - let name = buildPath -/- "libHS" ++ compId - dll0 <- needDll0 stage pkg - return $ [ name <.> extension ] - ++ [ name ++ "-0" <.> extension | dll0 ] - - return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] - ++ [ haddock | needHaddock && stage == Stage1 ] - ++ libs - + return $ [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] let programTargets = map (fromJust . programPath stage) programPkgs - return $ libTargets ++ programTargets - need $ reverse targets -- TODO: use stage 2 compiler for building stage 2 packages (instead of stage 1) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index afe2738..8e3ec77 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -1,20 +1,26 @@ module Rules.Program (buildProgram) where import Expression hiding (splitPath) -import GHC +import GHC (hsc2hs, haddock) import Oracles import Rules.Actions import Rules.Library import Rules.Resources import Settings +import Settings.Builders.GhcCabal -- TODO: Get rid of the Paths_hsc2hs.o hack. +-- TODO: Do we need to consider other ways when building programs? buildProgram :: Resources -> PartialTarget -> Rules () buildProgram _ target @ (PartialTarget stage pkg) = do let path = targetPath stage pkg buildPath = path -/- "build" program = programPath stage pkg + -- return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] + -- ++ [ haddock | needHaddock && stage == Stage1 ] + -- ++ libs + (\f -> program == Just f) ?> \bin -> do cSrcs <- cSources target -- TODO: remove code duplication (Library.hs) hSrcs <- hSources target @@ -23,8 +29,22 @@ buildProgram _ target @ (PartialTarget stage pkg) = do ++ [ buildPath -/- "Paths_hsc2hs.o" | pkg == hsc2hs ] ++ [ buildPath -/- "Paths_haddock.o" | pkg == haddock ] objs = cObjs ++ hObjs - putBuild $ "objs = " ++ show objs - need objs + pkgs <- interpretPartial target getPackages + ways <- interpretPartial target getWays + depNames <- interpretPartial target $ getPkgDataList DepNames + ghciFlag <- interpretPartial target $ getPkgData BuildGhciLib + let deps = matchPackageNames (sort pkgs) (sort depNames) + ghci = ghciFlag == "YES" && stage == Stage1 + libs <- fmap concat . forM deps $ \dep -> do + let depTarget = PartialTarget stage dep + compId <- interpretPartial depTarget $ getPkgData ComponentId + libFiles <- fmap concat . forM ways $ \way -> do + libFile <- pkgLibraryFile stage dep compId way + lib0File <- pkgLibraryFile stage dep (compId ++ "-0") way + dll0 <- needDll0 stage dep + return $ [ libFile ] ++ [ lib0File | dll0 ] + return $ libFiles ++ [ pkgGhciLibraryFile stage dep compId | ghci ] + need $ objs ++ libs build $ fullTargetWithWay target (Ghc stage) vanilla objs [bin] synopsis <- interpretPartial target $ getPkgData Synopsis putSuccess $ "/--------\n| Successfully built program '" diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index b84d03d..6bcec88 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,5 +1,5 @@ module Settings.TargetDirectory ( - targetDirectory, targetPath, pkgHaddockFile + targetDirectory, targetPath, pkgHaddockFile, pkgLibraryFile, pkgGhciLibraryFile ) where import Expression @@ -20,3 +20,18 @@ targetPath stage pkg = pkgPath pkg -/- targetDirectory stage pkg pkgHaddockFile :: Package -> FilePath pkgHaddockFile pkg @ (Package name _) = targetPath Stage1 pkg -/- "doc/html" -/- name -/- name <.> "haddock" + +-- Relative path to a package library file, e.g.: +-- "libraries/array/dist-install/build/libHSarray-0.5.1.0.a" +-- TODO: remove code duplication for computing buildPath +pkgLibraryFile :: Stage -> Package -> String -> Way -> Action FilePath +pkgLibraryFile stage pkg componentId way = do + extension <- libsuf way + let buildPath = targetPath stage pkg -/- "build" + return $ buildPath -/- "libHS" ++ componentId <.> extension + +-- Relative path to a package ghci library file, e.g.: +-- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" +pkgGhciLibraryFile :: Stage -> Package -> String -> FilePath +pkgGhciLibraryFile stage pkg componentId = + targetPath stage pkg -/- "build" -/- "HS" ++ componentId <.> "o" From git at git.haskell.org Fri Oct 27 00:12:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing path unifications. (bc5b5e1) Message-ID: <20171027001245.6BB6D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc5b5e167368ecbf4e53cbbf9833cdfca9604211/ghc >--------------------------------------------------------------- commit bc5b5e167368ecbf4e53cbbf9833cdfca9604211 Author: Andrey Mokhov Date: Thu May 12 01:05:08 2016 +0100 Add missing path unifications. >--------------------------------------------------------------- bc5b5e167368ecbf4e53cbbf9833cdfca9604211 src/Oracles/ModuleFiles.hs | 20 +++++++++++--------- src/Rules/Data.hs | 6 ++++-- src/Rules/Selftest.hs | 8 ++++---- 3 files changed, 19 insertions(+), 15 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index e77d2ba..233cdc0 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -28,20 +28,22 @@ determineBuilder file = case takeExtension file of -- | Given a module name extract the directory and file name, e.g.: -- --- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") --- > decodeModule "Prelude" == ("./", "Prelude") +-- > decodeModule "Data.Functor.Identity" == ("Data/Functor", "Identity") +-- > decodeModule "Prelude" == ("", "Prelude") decodeModule :: String -> (FilePath, String) -decodeModule = splitFileName . replaceEq '.' '/' +decodeModule modName = (intercalate "/" (init xs), last xs) + where + xs = words $ replaceEq '.' ' ' modName -- | Given the directory and file name find the corresponding module name, e.g.: -- --- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" --- > encodeModule "./" "Prelude" == "Prelude" --- > uncurry encodeModule (decodeModule name) == name +-- > encodeModule "Data/Functor" "Identity.hs" == "Data.Functor.Identity" +-- > encodeModule "" "Prelude" == "Prelude" +-- > uncurry encodeModule (decodeModule name) == name encodeModule :: FilePath -> String -> String encodeModule dir file - | dir == "./" = replaceEq '/' '.' $ takeBaseName file - | otherwise = replaceEq '/' '.' $ dir ++ takeBaseName file + | dir == "" = takeBaseName file + | otherwise = replaceEq '/' '.' dir ++ '.' : takeBaseName file -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) @@ -102,7 +104,7 @@ moduleFilesOracle = void $ do result <- fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do - let fullDir = dir -/- mDir + let fullDir = unifyPath $ dir -/- mDir files <- getDirectoryFiles fullDir ["*"] let noBoot = filter (not . (isSuffixOf "-boot")) files cmp fe f = compare (dropExtension fe) f diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 719352f..f901069 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -44,7 +44,8 @@ buildPackageData context at Context {..} = do copyFile inTreeMk mk autogenFiles <- getDirectoryFiles (oldPath -/- "build") ["autogen/*"] createDirectory $ buildPath context -/- "autogen" - forM_ autogenFiles $ \file -> do + forM_ autogenFiles $ \file' -> do + let file = unifyPath file' copyFile (oldPath -/- "build" -/- file) (buildPath context -/- file) let haddockPrologue = "haddock-prologue.txt" copyFile (oldPath -/- haddockPrologue) (buildPath context -/- haddockPrologue) @@ -111,7 +112,8 @@ buildPackageData context at Context {..} = do ++ [ "posix" | not windows ] ++ [ "win32" | windows ] -- TODO: adding cmm/S sources to C_SRCS is a hack; rethink after #18 - cSrcs <- getDirectoryFiles (pkgPath package) (map (-/- "*.c") dirs) + cSrcs <- map unifyPath <$> + getDirectoryFiles (pkgPath package) (map (-/- "*.c") dirs) cmmSrcs <- getDirectoryFiles (pkgPath package) ["*.cmm"] buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] buildStgCRunAsm <- anyTargetArch ["powerpc64le"] diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 8037682..9ba4524 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -61,11 +61,11 @@ testMatchVersionedFilePath = do testModuleNames :: Action () testModuleNames = do putBuild $ "==== Encode/decode module name" - test $ encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" - test $ encodeModule "./" "Prelude" == "Prelude" + test $ encodeModule "Data/Functor" "Identity.hs" == "Data.Functor.Identity" + test $ encodeModule "" "Prelude" == "Prelude" - test $ decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") - test $ decodeModule "Prelude" == ("./", "Prelude") + test $ decodeModule "Data.Functor.Identity" == ("Data/Functor", "Identity") + test $ decodeModule "Prelude" == ("", "Prelude") test $ forAll names $ \n -> uncurry encodeModule (decodeModule n) == n where From git at git.haskell.org Fri Oct 27 00:12:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: remove redundant Settings.Builders.Common import (88af41c) Message-ID: <20171027001246.148763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88af41cfff4e4c8e349693cdc423661a8f571c02/ghc >--------------------------------------------------------------- commit 88af41cfff4e4c8e349693cdc423661a8f571c02 Author: Karel Gardas Date: Tue Jan 19 22:06:12 2016 +0100 remove redundant Settings.Builders.Common import >--------------------------------------------------------------- 88af41cfff4e4c8e349693cdc423661a8f571c02 src/Settings/Packages/IntegerGmp.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index fbb7101..657eed0 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -4,7 +4,6 @@ import Base import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) -import Settings.Builders.Common import Settings.Paths import Oracles.Config.Setting From git at git.haskell.org Fri Oct 27 00:12:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix absolute paths starting with /c/ on Windows. (30d3d63) Message-ID: <20171027001246.62ECA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30d3d63bf7423e7da637981810dd62261868d7d2/ghc >--------------------------------------------------------------- commit 30d3d63bf7423e7da637981810dd62261868d7d2 Author: Andrey Mokhov Date: Sun Dec 20 15:18:44 2015 +0000 Fix absolute paths starting with /c/ on Windows. >--------------------------------------------------------------- 30d3d63bf7423e7da637981810dd62261868d7d2 src/Builder.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 007dae3..f15054d 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -95,16 +95,22 @@ needBuilder laxDependencies builder = do GhcM _ -> True _ -> False --- On Windows: if the path starts with "/", prepend it with the correct path to --- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe". +-- TODO: this is fragile, e.g. we currently only handle C: drive +-- On Windows: +-- * if the path starts with "/c/" change the prefix to "C:/" +-- * otherwise, if the path starts with "/", prepend it with the correct path +-- to the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe" fixAbsolutePathOnWindows :: FilePath -> Action FilePath fixAbsolutePathOnWindows path = do windows <- windowsHost -- Note, below is different from FilePath.isAbsolute: if (windows && "/" `isPrefixOf` path) then do - root <- windowsRoot - return . unifyPath $ root ++ drop 1 path + if ("/c/" `isPrefixOf` path) + then return $ "C:" ++ drop 2 path + else do + root <- windowsRoot + return . unifyPath $ root ++ drop 1 path else return path From git at git.haskell.org Fri Oct 27 00:12:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add link to MVP issue (82ead73) Message-ID: <20171027001249.5B2BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82ead7329fffd487907579625213da513ca4094f/ghc >--------------------------------------------------------------- commit 82ead7329fffd487907579625213da513ca4094f Author: Andrey Mokhov Date: Fri May 13 20:11:02 2016 +0100 Add link to MVP issue See #239. >--------------------------------------------------------------- 82ead7329fffd487907579625213da513ca4094f README.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index a8ca935..5c950dd 100644 --- a/README.md +++ b/README.md @@ -123,7 +123,8 @@ The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note the codebase is very unstable at present and we expect a lot of further refactoring. The documentation is currently non-existent, but we are working on it: [#55][comments-issue], -[#56][doc-issue]. +[#56][doc-issue]. See also [#239](https://github.com/snowleopard/hadrian/issues/239) +for a list of issues on the critical path. Acknowledgements ---------------- From git at git.haskell.org Fri Oct 27 00:12:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: simplify code and fix naming conventions based on Andrey's comments (06fb099) Message-ID: <20171027001250.779783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/06fb099d3fe8a253d79f7af4aa7d67cc5ef91bcc/ghc >--------------------------------------------------------------- commit 06fb099d3fe8a253d79f7af4aa7d67cc5ef91bcc Author: Karel Gardas Date: Tue Jan 19 22:27:36 2016 +0100 simplify code and fix naming conventions based on Andrey's comments >--------------------------------------------------------------- 06fb099d3fe8a253d79f7af4aa7d67cc5ef91bcc src/Settings/Packages/IntegerGmp.hs | 16 ++++++---------- 1 file changed, 6 insertions(+), 10 deletions(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 657eed0..9ad160f 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -15,17 +15,13 @@ import Oracles.Config.Setting integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" - gmp_includedir <- getSetting GmpIncludeDir - gmp_libdir <- getSetting GmpLibDir - let gmp_args = if (gmp_includedir == "" && gmp_libdir == "") - then - [ arg "--configure-option=--with-intree-gmp" ] - else - [] + gmpIncludeDir <- getSetting GmpIncludeDir + gmpLibDir <- getSetting GmpLibDir mconcat [ builder GhcCabal ? mconcat - (gmp_args ++ - [ appendSub "--configure-option=CFLAGS" [includeGmp] - , appendSub "--gcc-options" [includeGmp] ] ) + [ (null gmpIncludeDir && null gmpLibDir) ? + arg "--configure-option=--with-intree-gmp" + , appendSub "--configure-option=CFLAGS" [includeGmp] + , appendSub "--gcc-options" [includeGmp] ] , builderGcc ? arg includeGmp ] From git at git.haskell.org Fri Oct 27 00:12:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add pkgDataFile to look up the path to package-data.mk of a particular stage/package combination. (304b099) Message-ID: <20171027001250.A809B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/304b0999ea6282dc3a86e2923bb361a889c5acff/ghc >--------------------------------------------------------------- commit 304b0999ea6282dc3a86e2923bb361a889c5acff Author: Andrey Mokhov Date: Sun Dec 20 18:30:24 2015 +0000 Add pkgDataFile to look up the path to package-data.mk of a particular stage/package combination. >--------------------------------------------------------------- 304b0999ea6282dc3a86e2923bb361a889c5acff src/Rules/Data.hs | 2 +- src/Settings/TargetDirectory.hs | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index b6925d0..b68a1f6 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -32,7 +32,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ] + need $ map (pkgDataFile stage) depPkgs need [cabalFile] buildWithResources [(ghcCabal rs, 1)] $ diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 6bcec88..286670b 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -1,5 +1,6 @@ module Settings.TargetDirectory ( - targetDirectory, targetPath, pkgHaddockFile, pkgLibraryFile, pkgGhciLibraryFile + targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, + pkgGhciLibraryFile ) where import Expression @@ -15,6 +16,9 @@ targetDirectory = userTargetDirectory targetPath :: Stage -> Package -> FilePath targetPath stage pkg = pkgPath pkg -/- targetDirectory stage pkg +pkgDataFile :: Stage -> Package -> FilePath +pkgDataFile stage pkg = targetPath stage pkg -/- "package-data.mk" + -- Relative path to a package haddock file, e.g.: -- "libraries/array/dist-install/doc/html/array/array.haddock" pkgHaddockFile :: Package -> FilePath From git at git.haskell.org Fri Oct 27 00:12:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add user settings documentation (b56f4eb) Message-ID: <20171027001252.D48423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b56f4eb4034f51dbb5364ff57752900c8d9f417b/ghc >--------------------------------------------------------------- commit b56f4eb4034f51dbb5364ff57752900c8d9f417b Author: Andrey Mokhov Date: Sat May 14 13:58:21 2016 +0100 Add user settings documentation See #56, #245. >--------------------------------------------------------------- b56f4eb4034f51dbb5364ff57752900c8d9f417b doc/user-settings.md | 124 +++++++++++++++++++++++++++++++++++++++++++++++++++ src/Settings/User.hs | 20 ++++----- 2 files changed, 134 insertions(+), 10 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md new file mode 100644 index 0000000..a7f1469 --- /dev/null +++ b/doc/user-settings.md @@ -0,0 +1,124 @@ +# User settings + +Users can customise Hadrian by specifying user build settings in file +`src/Settings/User.hs`. Here we document currently supported settings. + +## Build directory + +Hadrian puts build results into `_build` directory by default, which is +controlled by `buildRootPath`: +```haskell +-- | All build artefacts are stored in 'buildRootPath' directory. +buildRootPath :: FilePath +buildRootPath = "_build" +``` + +## Command line arguments + +One of the key features of Hadrian is that users can modify any build command by +changing `userArgs`. The build system will detect the change and will rerun all +affected build rules during the next build, without requiring a full rebuild. + +As an example, here is how to pass an extra argument `-O0` to all invocations of +GHC when compiling package `cabal`: +```haskell +-- | Control user-specific command line arguments. +userArgs :: Args +userArgs = builder Ghc ? package cabal ? arg "-O0" +``` +Builders such as `Ghc` are defined in `src/Builder.hs`, and all packages that +are currently built as part of the GHC are defined in `src/GHC.hs` (also see +`src/Package.hs`). + +It is possible to specify several custom command line arguments combining the +list with `mconcat`: +```haskell +userArgs :: Args +userArgs = mconcat + [ builder Ghc ? package cabal ? arg "-O0" + , package rts ? input "//Evac\_thr.c" ? append [ "-DPARALLEL\_GC", "-Irts/sm" ] + , builder Ghc ? output "//Prelude.\*" ? remove ["-Wall", "-fwarn-tabs"] ] +``` +The above example also demostrates the use of `append` for adding more than one +argument and `remove` for removing arguments that Hadrian uses by default. It is +possible to match any combination of the current `builder`, `stage`, `package`, +`way`, `input` and `output` using predicates. File patterns such as +`"//Prelude.\*"` can be used when matching input and output files where `//` +matches an arbitrary number of path components and `\*` matches an entire path component, excluding any separators. + +## Packages + +To add or remove a package from a particular build stage, use `userPackages`. As +an example, below we add package `base` to Stage0 and remove package `haskeline` +from Stage1: +```haskell +-- | Control which packages get to be built. +userPackages :: Packages +userPackages = mconcat + [ stage0 ? append [base] + , stage1 ? remove [haskeline] ] +``` +If you are working on a new GHC package you need to let Hadrian know about it +by setting `userKnownPackages`: +```haskell +-- | Add new user-defined packages. +userKnownPackages :: [Package] +userKnownPackages = [] +``` +To control which integer library to use when builing GHC, set `integerLibrary`: +```haskell +-- | Choose the integer library: integerGmp or integerSimple. +integerLibrary :: Package +integerLibrary = integerGmp +``` + +## Build ways + +Libraries can be built in a number of ways, such as `vanilla`, `profiling` (with +profiling information enabled), and many others as defined in `src/Way.hs`. To +control which ways particular packages are built, set `userLibraryWays` and +`userRtsWays`. As an example, below we remove `dynamic` from the list of library +ways and keep `rts` package ways unchanged: +```haskell +-- | Control which ways library packages are built. +userLibraryWays :: Ways +userLibraryWays = remove [dynamic] + +-- | Control which ways the 'rts' package is built. +userRtsWays :: Ways +userRtsWays = mempty +``` + +## Verbose command lines + +By default Hadrian does not print full command lines during the build process +and instead prints short human readable digests for each executed command. It is +possible to suppress this behaviour completely or partially using +`verboseCommands` setting: +```haskell +-- | Set to True to print full command lines during the build process. Note, +-- this is a Predicate, hence you can enable verbose output for a chosen package +-- only, e.g.: verboseCommands = package ghcPrim +verboseCommands :: Predicate +verboseCommands = return False +``` +For example, to print the full command lines used to compile GHC executables, +set `verboseCommands` to: +```haskell +verboseCommands :: Predicate +verboseCommands = input "ghc/Main.hs" +``` +Below are a few other examples: +```haskell +-- Print command lines for all Ghc Link invocations: +verboseCommands = builder (Ghc Link) + +-- Print command lines when compiling files in package compiler using Gcc: +verboseCommands = builder (Gcc Compile) &&^ package compiler + +-- Use patterns when matching files: +verboseCommands = file "//rts/sm/*" &&^ way threaded + +-- Show all commands: +verboseCommands = return True +``` \ No newline at end of file diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 0893579..cc48684 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -16,31 +16,31 @@ import Settings.Default buildRootPath :: FilePath buildRootPath = "_build" --- Control user-specific settings +-- | Control user-specific command line arguments. userArgs :: Args userArgs = builder Ghc ? remove ["-Wall", "-fwarn-tabs"] --- Control which packages get to be built +-- | Control which packages get to be built. userPackages :: Packages userPackages = mempty --- Add new user-defined packages +-- | Add new user-defined packages. userKnownPackages :: [Package] userKnownPackages = [] --- | Control which ways library packages are built +-- | Choose the integer library: integerGmp or integerSimple. +integerLibrary :: Package +integerLibrary = integerGmp + +-- | Control which ways library packages are built. -- FIXME: skip dynamic since it's currently broken #4 userLibraryWays :: Ways userLibraryWays = remove [dynamic] --- | Control which ways the 'rts' package is built +-- | Control which ways the 'rts' package is built. userRtsWays :: Ways userRtsWays = mempty --- | Choose the integer library: integerGmp or integerSimple -integerLibrary :: Package -integerLibrary = integerGmp - -- | User-defined flags. Note the following type semantics: -- * Bool: a plain Boolean flag whose value is known at compile time -- * Action Bool: a flag whose value can depend on the build environment @@ -79,7 +79,7 @@ buildHaddock = return cmdBuildHaddock -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package --- only, e.g.: verboseCommands = package ghcPrim +-- only, e.g.: verboseCommands = package ghcPrim. verboseCommands :: Predicate verboseCommands = return False From git at git.haskell.org Fri Oct 27 00:12:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #185 from kgardas/fix_gmp_cabal_args (30883f8) Message-ID: <20171027001254.79A6F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30883f8d1e5289a8b90213ebfee0ee99e1712899/ghc >--------------------------------------------------------------- commit 30883f8d1e5289a8b90213ebfee0ee99e1712899 Merge: 11f78b1 06fb099 Author: Andrey Mokhov Date: Tue Jan 19 22:49:58 2016 +0000 Merge pull request #185 from kgardas/fix_gmp_cabal_args do not pass --with-intree-gmp to configure when system gmp is used >--------------------------------------------------------------- 30883f8d1e5289a8b90213ebfee0ee99e1712899 src/Settings/Packages/IntegerGmp.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:12:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add verboseCommands predicate to show executed commands in full when needed. (f48da18) Message-ID: <20171027001254.A76E93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f48da1844187e9dab91be2038d0675b6d1eb90b8/ghc >--------------------------------------------------------------- commit f48da1844187e9dab91be2038d0675b6d1eb90b8 Author: Andrey Mokhov Date: Sun Dec 20 18:41:44 2015 +0000 Add verboseCommands predicate to show executed commands in full when needed. >--------------------------------------------------------------- f48da1844187e9dab91be2038d0675b6d1eb90b8 src/Rules/Actions.hs | 11 +++++++---- src/Settings/User.hs | 9 ++++++++- 2 files changed, 15 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index cdc2e17..805c771 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -16,13 +16,16 @@ buildWithResources rs target = do needBuilder laxDependencies builder path <- builderPath builder argList <- interpret target getArgs + verbose <- interpret target verboseCommands + let quitelyUnlessVerbose = if verbose then withVerbosity Loud else quietly -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do - putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList - putBuild $ "\\--------" - quietly $ case builder of + unless verbose $ do + putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" + mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList + putBuild $ "\\--------" + quitelyUnlessVerbose $ case builder of Ar -> arCmd path argList HsCpp -> do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 0dffbfd..4c7a5f4 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -2,7 +2,8 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory, userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile + ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, + verboseCommands ) where import Expression @@ -81,3 +82,9 @@ buildHaddock = return True buildSystemConfigFile :: Bool buildSystemConfigFile = False + +-- Set to True to print full command lines during the build process. Note, this +-- is a Predicate, hence you can enable verbose output for a chosen package +-- only, e.g.: verboseCommands = package ghcPrim +verboseCommands :: Predicate +verboseCommands = return False From git at git.haskell.org Fri Oct 27 00:12:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a link to the user settings doc (f715a27) Message-ID: <20171027001256.57C9A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f715a274f7ef2e07625f22401f755a30dfbce001/ghc >--------------------------------------------------------------- commit f715a274f7ef2e07625f22401f755a30dfbce001 Author: Andrey Mokhov Date: Sat May 14 14:05:05 2016 +0100 Add a link to the user settings doc See #245. [skip ci] >--------------------------------------------------------------- f715a274f7ef2e07625f22401f755a30dfbce001 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 5c950dd..fdbdbc5 100644 --- a/README.md +++ b/README.md @@ -80,8 +80,8 @@ a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this f #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We -use [`src/Settings/User.hs`][user-settings] for the same purpose. Feel free to -experiment following the Haddock comments. +use [`src/Settings/User.hs`][user-settings] for the same purpose, see +[documentation](doc/user-settings.md). #### Clean and full rebuild From git at git.haskell.org Fri Oct 27 00:12:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: README: Add basic instructions for Linux (5211197) Message-ID: <20171027001258.26E1A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/52111971658afeafdcd3e3f13fecd29e672549e8/ghc >--------------------------------------------------------------- commit 52111971658afeafdcd3e3f13fecd29e672549e8 Author: Ben Gamari Date: Sun Dec 20 14:04:05 2015 +0100 README: Add basic instructions for Linux >--------------------------------------------------------------- 52111971658afeafdcd3e3f13fecd29e672549e8 README.md | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/README.md b/README.md index 05f3352..63673e3 100644 --- a/README.md +++ b/README.md @@ -4,3 +4,18 @@ Shaking up GHC As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC](https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler) build system based on standard `make` into a new and (hopefully) better one based on [Shake](https://github.com/ndmitchell/shake/blob/master/README.md). If you are curious about the project you can find more details on the [wiki page](https://ghc.haskell.org/trac/ghc/wiki/Building/Shake) and in this [blog post](https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc/). This is supposed to go into the `shake-build` directory of the GHC source tree. + +Trying it +--------- + +On Linux, +``` +$ git clone git://git.haskell.org/ghc +$ cd ghc +$ git submodule update --init +$ git clone git://github.com/snowleopard/shaking-up-ghc shake-build +$ ./boot +$ ./configure +$ make inplace/bin/ghc-cabal # This needs to be fixed +$ shake-build/build.sh +``` From git at git.haskell.org Fri Oct 27 00:12:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor CmdLineFlag.hs. (c50e0dc) Message-ID: <20171027001258.1E6163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c50e0dc4eb0200dae1d4b50e824db4764e95b827/ghc >--------------------------------------------------------------- commit c50e0dc4eb0200dae1d4b50e824db4764e95b827 Author: Andrey Mokhov Date: Wed Jan 20 00:11:45 2016 +0000 Refactor CmdLineFlag.hs. >--------------------------------------------------------------- c50e0dc4eb0200dae1d4b50e824db4764e95b827 shaking-up-ghc.cabal | 2 +- src/CmdLineFlag.hs | 56 +++++++++++++++++++++++++++++++++++++++ src/Main.hs | 9 ++++--- src/Oracles/Config/CmdLineFlag.hs | 55 -------------------------------------- src/Rules/Actions.hs | 33 ++++++++++++----------- 5 files changed, 80 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 c50e0dc4eb0200dae1d4b50e824db4764e95b827 From git at git.haskell.org Fri Oct 27 00:12:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:12:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (4b0dc2f) Message-ID: <20171027001259.BB3523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b0dc2fe52989ff18dc5e0202a1bd48f00689772/ghc >--------------------------------------------------------------- commit 4b0dc2fe52989ff18dc5e0202a1bd48f00689772 Author: Andrey Mokhov Date: Sat May 14 18:10:51 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- 4b0dc2fe52989ff18dc5e0202a1bd48f00689772 doc/user-settings.md | 45 ++++++++++++++++++++++++++------------------- 1 file changed, 26 insertions(+), 19 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index a7f1469..e9bea77 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,12 +1,12 @@ # User settings -Users can customise Hadrian by specifying user build settings in file +You can customise Hadrian by specifying user build settings in file `src/Settings/User.hs`. Here we document currently supported settings. ## Build directory Hadrian puts build results into `_build` directory by default, which is -controlled by `buildRootPath`: +specified by `buildRootPath`: ```haskell -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath @@ -19,7 +19,7 @@ One of the key features of Hadrian is that users can modify any build command by changing `userArgs`. The build system will detect the change and will rerun all affected build rules during the next build, without requiring a full rebuild. -As an example, here is how to pass an extra argument `-O0` to all invocations of +For example, here is how to pass an extra argument `-O0` to all invocations of GHC when compiling package `cabal`: ```haskell -- | Control user-specific command line arguments. @@ -27,24 +27,24 @@ userArgs :: Args userArgs = builder Ghc ? package cabal ? arg "-O0" ``` Builders such as `Ghc` are defined in `src/Builder.hs`, and all packages that -are currently built as part of the GHC are defined in `src/GHC.hs` (also see -`src/Package.hs`). +are currently built as part of the GHC are defined in `src/GHC.hs`. See also +`src/Package.hs`. -It is possible to specify several custom command line arguments combining the -list with `mconcat`: +You can combine several custom command line settings using `mconcat`: ```haskell userArgs :: Args userArgs = mconcat [ builder Ghc ? package cabal ? arg "-O0" - , package rts ? input "//Evac\_thr.c" ? append [ "-DPARALLEL\_GC", "-Irts/sm" ] - , builder Ghc ? output "//Prelude.\*" ? remove ["-Wall", "-fwarn-tabs"] ] + , package rts ? input "//Evac_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] + , builder Ghc ? output "//Prelude.*" ? remove ["-Wall", "-fwarn-tabs"] ] ``` The above example also demostrates the use of `append` for adding more than one -argument and `remove` for removing arguments that Hadrian uses by default. It is -possible to match any combination of the current `builder`, `stage`, `package`, -`way`, `input` and `output` using predicates. File patterns such as -`"//Prelude.\*"` can be used when matching input and output files where `//` -matches an arbitrary number of path components and `\*` matches an entire path component, excluding any separators. +argument and `remove` for removing arguments that Hadrian uses by default. You +can match any combination of the `builder`, `stage`, `package`, `way`, `input` +and `output` when specifying custom command line arguments. File patterns such as +`"//Prelude.*"` can be used when matching input and output files where `//` +matches an arbitrary number of path components and `*` matches an entire path +component, excluding any separators. ## Packages @@ -63,20 +63,27 @@ by setting `userKnownPackages`: ```haskell -- | Add new user-defined packages. userKnownPackages :: [Package] -userKnownPackages = [] +userKnownPackages = [myPackage] + +-- An example package that lives in "libraries/my-package" directory. +myPackage :: Package +myPackage = library "my-package" ``` -To control which integer library to use when builing GHC, set `integerLibrary`: +Note, you will also need to add it to a specific build stage by modifying +`userPackages` as otherwise it will not be built. + +You can choose which integer library to use when builing GHC by setting +`integerLibrary`: ```haskell -- | Choose the integer library: integerGmp or integerSimple. integerLibrary :: Package integerLibrary = integerGmp ``` - ## Build ways Libraries can be built in a number of ways, such as `vanilla`, `profiling` (with profiling information enabled), and many others as defined in `src/Way.hs`. To -control which ways particular packages are built, set `userLibraryWays` and +control which ways particular ways are built, set `userLibraryWays` and `userRtsWays`. As an example, below we remove `dynamic` from the list of library ways and keep `rts` package ways unchanged: ```haskell @@ -119,6 +126,6 @@ verboseCommands = builder (Gcc Compile) &&^ package compiler -- Use patterns when matching files: verboseCommands = file "//rts/sm/*" &&^ way threaded --- Show all commands: +-- Print all commands: verboseCommands = return True ``` From git at git.haskell.org Fri Oct 27 00:13:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (e7377d1) Message-ID: <20171027001302.4F7233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7377d1113d34ca56881cfc46b25e2ad8a6ba3aa/ghc >--------------------------------------------------------------- commit e7377d1113d34ca56881cfc46b25e2ad8a6ba3aa Author: Andrey Mokhov Date: Wed Jan 20 00:33:27 2016 +0000 Minor revision. [skip ci] >--------------------------------------------------------------- e7377d1113d34ca56881cfc46b25e2ad8a6ba3aa src/Expression.hs | 59 ++++++++++++++++++++++++++++--------------------------- 1 file changed, 30 insertions(+), 29 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 932ed80..1d1dc27 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -36,17 +36,18 @@ import Stage import Target import Way --- | @Expr a@ is a computation that produces a value of type @Action a@ and can read --- parameters of the current build 'Target'. +-- | @Expr a@ is a computation that produces a value of type @Action a@ and can +-- read parameters of the current build 'Target'. type Expr a = ReaderT Target Action a -- | @Diff a@ is a /difference list/ containing values of type @a at . A difference --- list is a list with efficient concatenation, encoded as a value @a -> a at . --- We could use @Dual (Endo a)@ instead of @Diff a@, but the former may look scary. +-- list is a list with efficient concatenation, encoded as a value @a -> a at . We +-- could use @Dual (Endo a)@ instead of @Diff a@, but the former may look scary. newtype Diff a = Diff { fromDiff :: a -> a } --- | @DiffExpr a@ is a computation that builds a difference list (i.e., a function --- of type @'Action' (a -> a)@) and can read parameters of the current build ''Target'. +-- | @DiffExpr a@ is a computation that builds a difference list (i.e., a +-- function of type @'Action' (a -> a)@) and can read parameters of the current +-- build 'Target'. type DiffExpr a = Expr (Diff a) -- Note the reverse order of function composition (y . x), which ensures that @@ -65,19 +66,19 @@ type Packages = DiffExpr [Package] type Ways = DiffExpr [Way] -- Basic operations on expressions: --- | Transform an expression by applying a given function +-- | Transform an expression by applying a given function. apply :: (a -> a) -> DiffExpr a apply = return . Diff --- | Append something to an expression +-- | Append something to an expression. append :: Monoid a => a -> DiffExpr a append x = apply (<> x) --- | Remove given elements from a list expression +-- | Remove given elements from a list expression. remove :: Eq a => [a] -> DiffExpr [a] remove xs = apply $ filter (`notElem` xs) --- | Remove given pair of elements from a list expression +-- | Remove given pair of elements from a list expression. -- Example: removePair "-flag" "b" ["-flag", "a", "-flag", "b"] = ["-flag", "a"] removePair :: Eq a => a -> a -> DiffExpr [a] removePair x y = apply filterPair @@ -87,30 +88,30 @@ removePair x y = apply filterPair else z1 : filterPair (z2 : zs) filterPair zs = zs --- | Apply a predicate to an expression +-- | Apply a predicate to an expression. applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate if bool then expr else return mempty --- | Add a single argument to 'Args' +-- | Add a single argument to 'Args'. arg :: String -> Args arg = append . return --- | A convenient operator for predicate application +-- | A convenient operator for predicate application. class PredicateLike a where - (?) :: Monoid m => a -> Expr m -> Expr m + (?) :: Monoid m => a -> Expr m -> Expr m infixr 8 ? instance PredicateLike Predicate where - (?) = applyPredicate + (?) = applyPredicate instance PredicateLike Bool where - (?) = applyPredicate . return + (?) = applyPredicate . return instance PredicateLike (Action Bool) where - (?) = applyPredicate . lift + (?) = applyPredicate . lift -- | @appendSub@ appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument @@ -141,11 +142,11 @@ filterSub prefix p = apply $ map filterSubstr | otherwise = s -- | Remove given elements from a list of sub-arguments with a given prefix --- Example: removeSub "--configure-option=CFLAGS" ["-Werror"] +-- Example: removeSub "--configure-option=CFLAGS" ["-Werror"]. removeSub :: String -> [String] -> Args removeSub prefix xs = filterSub prefix (`notElem` xs) --- | Interpret a given expression in a given environment +-- | Interpret a given expression in a given environment. interpret :: Target -> Expr a -> Action a interpret = flip runReaderT @@ -156,46 +157,46 @@ interpretWithStage :: Stage -> Expr a -> Action a interpretWithStage s = interpretPartial $ PartialTarget s (error "interpretWithStage: package not set") --- | Extract an expression from a difference expression +-- | Extract an expression from a difference expression. fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) --- | Interpret a given difference expression in a given environment +-- | Interpret a given difference expression in a given environment. interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a interpretDiff target = interpret target . fromDiffExpr --- | Convenient getters for target parameters +-- | Convenient getters for target parameters. getStage :: Expr Stage getStage = asks stage --- | Get the 'Package' of the current 'Target' +-- | Get the 'Package' of the current 'Target'. getPackage :: Expr Package getPackage = asks package --- | Get the 'Builder' for the current 'Target' +-- | Get the 'Builder' for the current 'Target'. getBuilder :: Expr Builder getBuilder = asks builder --- | Get the 'Way' of the current 'Target' +-- | Get the 'Way' of the current 'Target'. getWay :: Expr Way getWay = asks way --- | Get the input files of the current 'Target' +-- | Get the input files of the current 'Target'. getInputs :: Expr [FilePath] getInputs = asks inputs --- | Run 'getInputs' and check that the result contains a single input file only +-- | Run 'getInputs' and check that the result contains one input file only. getInput :: Expr FilePath getInput = do target <- ask getSingleton getInputs $ "getInput: exactly one input file expected in target " ++ show target --- | Get the files produced by the current 'Target' +-- | Get the files produced by the current 'Target'. getOutputs :: Expr [FilePath] getOutputs = asks outputs --- | Run 'getOutputs' and check that the result contains a output file only +-- | Run 'getOutputs' and check that the result contains one output file only. getOutput :: Expr FilePath getOutput = do target <- ask From git at git.haskell.org Fri Oct 27 00:13:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Documentation: Move HsColour invocation to after `need` (8e8cc53) Message-ID: <20171027001302.561B03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e8cc532db9c18fb9b3867b3ceb0e730a93493ff/ghc >--------------------------------------------------------------- commit 8e8cc532db9c18fb9b3867b3ceb0e730a93493ff Author: Ben Gamari Date: Sun Dec 20 16:43:12 2015 +0100 Documentation: Move HsColour invocation to after `need` HsColour also depends upon the sources existing. Fixes #6. >--------------------------------------------------------------- 8e8cc532db9c18fb9b3867b3ceb0e730a93493ff src/Rules/Documentation.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 2ebaa59..495a16c 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -15,14 +15,18 @@ buildPackageDocumentation _ target @ (PartialTarget stage package) = haddockFile = pkgHaddockFile package in when (stage == Stage1) $ do haddockFile %> \file -> do - whenM (specified HsColour) $ do - need [cabalFile] - build $ fullTarget target GhcCabalHsColour [cabalFile] [] srcs <- interpretPartial target getPackageSources deps <- interpretPartial target $ getPkgDataList DepNames let haddocks = [ pkgHaddockFile depPkg | Just depPkg <- map findKnownPackage deps ] need $ srcs ++ haddocks + + -- HsColour sources + whenM (specified HsColour) $ do + need [cabalFile] + build $ fullTarget target GhcCabalHsColour [cabalFile] [] + + -- Build Haddock documentation let haddockWay = if dynamicGhcPrograms then dynamic else vanilla build $ fullTargetWithWay target Haddock haddockWay srcs [file] From git at git.haskell.org Fri Oct 27 00:13:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (be59fae) Message-ID: <20171027001303.53D463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/be59faec5e11a7338888227ffdc36a2513c1fd00/ghc >--------------------------------------------------------------- commit be59faec5e11a7338888227ffdc36a2513c1fd00 Author: Andrey Mokhov Date: Sat May 14 18:15:10 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- be59faec5e11a7338888227ffdc36a2513c1fd00 doc/user-settings.md | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index e9bea77..e395ea2 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -41,10 +41,10 @@ userArgs = mconcat The above example also demostrates the use of `append` for adding more than one argument and `remove` for removing arguments that Hadrian uses by default. You can match any combination of the `builder`, `stage`, `package`, `way`, `input` -and `output` when specifying custom command line arguments. File patterns such as -`"//Prelude.*"` can be used when matching input and output files where `//` -matches an arbitrary number of path components and `*` matches an entire path -component, excluding any separators. +and `output` predicates when specifying custom command line arguments. File +patterns such as `"//Prelude.*"` can be used when matching input and output files, +where `//` matches an arbitrary number of path components and `*` matches an entire +path component, excluding any separators. ## Packages @@ -69,7 +69,7 @@ userKnownPackages = [myPackage] myPackage :: Package myPackage = library "my-package" ``` -Note, you will also need to add it to a specific build stage by modifying +Note, you will also need to add `myPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting From git at git.haskell.org Fri Oct 27 00:13:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Actions: Factor out box drawing (9d2868b) Message-ID: <20171027001305.E1A253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d2868b107cce0af8445ec6ce8471ba1d45e3042/ghc >--------------------------------------------------------------- commit 9d2868b107cce0af8445ec6ce8471ba1d45e3042 Author: Ben Gamari Date: Sun Dec 20 17:21:47 2015 +0100 Actions: Factor out box drawing Also add (currently broken) Unicode support although this is broken by Shake, the console output interface of which is badly broken (see Shake #364) >--------------------------------------------------------------- 9d2868b107cce0af8445ec6ce8471ba1d45e3042 src/Rules/Actions.hs | 25 ++++++++++++++++++++----- 1 file changed, 20 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 805c771..775524a 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -7,6 +7,22 @@ import Settings.Args import Settings.Builders.Ar import qualified Target +insideBox :: [String] -> String +insideBox ls = + unlines $ [begin] ++ map (bar++) ls ++ [end] + where + (begin,bar,end) + | useUnicode = ( "╭──────────" + , "│ " + , "╰──────────" + ) + | otherwise = ( "/----------" + , "| " + , "\\----------" + ) + -- FIXME: See Shake #364. + useUnicode = False + -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last -- built (that is, track changes in the build system). @@ -17,15 +33,14 @@ buildWithResources rs target = do path <- builderPath builder argList <- interpret target getArgs verbose <- interpret target verboseCommands - let quitelyUnlessVerbose = if verbose then withVerbosity Loud else quietly + let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do unless verbose $ do - putBuild $ "/--------\n| Running " ++ show builder ++ " with arguments:" - mapM_ (putBuild . ("| " ++)) $ interestingInfo builder argList - putBuild $ "\\--------" - quitelyUnlessVerbose $ case builder of + putBuild $ insideBox $ [ "Running " ++ show builder ++ " with arguments:" ] + ++ map (" "++) (interestingInfo builder argList) + quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList HsCpp -> do From git at git.haskell.org Fri Oct 27 00:13:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for --split-object command line flag. (87c6fae) Message-ID: <20171027001306.42E8E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/87c6fae6c8073315ca8f5aba0e2e5501500437db/ghc >--------------------------------------------------------------- commit 87c6fae6c8073315ca8f5aba0e2e5501500437db Author: Andrey Mokhov Date: Wed Jan 20 01:00:50 2016 +0000 Add support for --split-object command line flag. See #132. >--------------------------------------------------------------- 87c6fae6c8073315ca8f5aba0e2e5501500437db src/CmdLineFlag.hs | 22 ++++++++++++++++------ src/Settings/User.hs | 8 ++++++-- 2 files changed, 22 insertions(+), 8 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 444940a..05b74e5 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,5 +1,5 @@ module CmdLineFlag ( - putCmdLineFlags, flags, cmdProgressInfo, ProgressInfo (..) + putCmdLineFlags, flags, cmdProgressInfo, ProgressInfo (..), cmdSplitObjects ) where import Base @@ -16,13 +16,15 @@ data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -- command line. These flags are not tracked, that is they do not force any -- build rules to be rurun. data Untracked = Untracked - { progressInfo :: ProgressInfo } + { progressInfo :: ProgressInfo + , splitObjects :: Bool } deriving (Eq, Show) -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked defaultUntracked = Untracked - { progressInfo = Normal } + { progressInfo = Normal + , splitObjects = False } readProgressInfo :: Maybe String -> Either String (Untracked -> Untracked) readProgressInfo ms = @@ -35,11 +37,16 @@ readProgressInfo ms = go "unicorn" = Just Unicorn go _ = Nothing -- Left "no parse" mkClosure :: ProgressInfo -> Untracked -> Untracked - mkClosure flag opts = opts { progressInfo = flag } + mkClosure flag flags = flags { progressInfo = flag } + +readSplitObjects :: Either String (Untracked -> Untracked) +readSplitObjects = Right $ \flags -> flags { splitObjects = True } flags :: [OptDescr (Either String (Untracked -> Untracked))] flags = [ Option [] ["progress-info"] (OptArg readProgressInfo "") - "Progress Info Style (None, Brief, Normal, or Unicorn)" ] + "Progress Info Style (None, Brief, Normal, or Unicorn)" + , Option [] ["split-objects"] (NoArg readSplitObjects) + "Generate split objects (requires a full clean rebuild)." ] -- TODO: Get rid of unsafePerformIO by using shakeExtra. {-# NOINLINE cmdLineFlags #-} @@ -47,10 +54,13 @@ cmdLineFlags :: IORef Untracked cmdLineFlags = unsafePerformIO $ newIORef defaultUntracked putCmdLineFlags :: [Untracked -> Untracked] -> IO () -putCmdLineFlags opts = modifyIORef cmdLineFlags (\o -> foldl (flip id) o opts) +putCmdLineFlags flags = modifyIORef cmdLineFlags (\f -> foldl (flip id) f flags) getCmdLineFlags :: Action Untracked getCmdLineFlags = liftIO $ readIORef cmdLineFlags cmdProgressInfo :: Action ProgressInfo cmdProgressInfo = progressInfo <$> getCmdLineFlags + +cmdSplitObjects :: Action Bool +cmdSplitObjects = splitObjects <$> getCmdLineFlags diff --git a/src/Settings/User.hs b/src/Settings/User.hs index fb6ffb6..096f6ef 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -6,9 +6,12 @@ module Settings.User ( verboseCommands, turnWarningsIntoErrors, splitObjects ) where +import Base +import CmdLineFlag import GHC import Expression import Predicates +import Settings.Default -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath @@ -55,9 +58,10 @@ trackBuildSystem = True validating :: Bool validating = False --- To switch on split objects use 'splitObjects = defaultSplitObjects', see #153 +-- | Control when split objects are generated. Note, due to the GHC bug #11315 +-- it is necessary to do a full clean rebuild when changing this option. splitObjects :: Predicate -splitObjects = return False +splitObjects = (lift $ cmdSplitObjects) &&^ defaultSplitObjects dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Fri Oct 27 00:13:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add TODOs. (86ae5c7) Message-ID: <20171027001307.1B2093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86ae5c73a514bea9a5035128f673833b071e5dc9/ghc >--------------------------------------------------------------- commit 86ae5c73a514bea9a5035128f673833b071e5dc9 Author: Andrey Mokhov Date: Sat May 14 18:29:43 2016 +0100 Add TODOs. >--------------------------------------------------------------- 86ae5c73a514bea9a5035128f673833b071e5dc9 src/Settings/User.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index cc48684..2294fc7 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -53,6 +53,7 @@ userRtsWays = mempty trackBuildSystem :: Bool trackBuildSystem = True +-- TODO: This should be set automatically when validating. validating :: Bool validating = False @@ -61,6 +62,12 @@ validating = False splitObjects :: Predicate splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects +-- | Control when to build documentation. +buildHaddock :: Predicate +buildHaddock = return cmdBuildHaddock + +-- TODO: Do we need to be able to set these from command line? +-- TODO: Turn below into ghcWays? dynamicGhcPrograms :: Bool dynamicGhcPrograms = False @@ -70,13 +77,9 @@ ghciWithDebugger = False ghcProfiled :: Bool ghcProfiled = False --- TODO: do we need to be able to set this from command line? ghcDebugged :: Bool ghcDebugged = False -buildHaddock :: Predicate -buildHaddock = return cmdBuildHaddock - -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package -- only, e.g.: verboseCommands = package ghcPrim. From git at git.haskell.org Fri Oct 27 00:13:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix detection of libraries (86ed4e3) Message-ID: <20171027001309.AAEE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86ed4e32b39b0ab57e64fbd93cccfb8113d162b7/ghc >--------------------------------------------------------------- commit 86ed4e32b39b0ab57e64fbd93cccfb8113d162b7 Author: Ben Gamari Date: Sun Dec 20 20:23:34 2015 +0100 Fix detection of libraries Previously a very fragile heuristic was used. Now we explicitly declare this. Perhaps a better option in the future would be to instead emit this information from `ghc-cabal` and pick it up from `package-data.mk`. Fixes #9. >--------------------------------------------------------------- 86ed4e32b39b0ab57e64fbd93cccfb8113d162b7 src/GHC.hs | 2 +- src/Package.hs | 37 ++++++++++++++++++++++++++----------- src/Rules/Data.hs | 3 ++- src/Settings.hs | 3 ++- src/Settings/TargetDirectory.hs | 2 +- 5 files changed, 32 insertions(+), 15 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0279197..c38af04 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -51,7 +51,7 @@ dllSplit = utility "dll-split" filepath = library "filepath" genapply = utility "genapply" genprimopcode = utility "genprimopcode" -ghc = topLevel "ghc-bin" `setPath` "ghc" +ghc = topLevel "ghc-bin" `setPath` "ghc" `setPkgType` Program ghcBoot = library "ghc-boot" ghcCabal = utility "ghc-cabal" ghci = library "ghci" diff --git a/src/Package.hs b/src/Package.hs index 8415bf1..6273a62 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,23 +1,31 @@ {-# LANGUAGE DeriveGeneric #-} module Package ( - Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility, - matchPackageNames + Package (..), PackageName, PackageType (..), + -- * Queries + pkgCabalFile, + matchPackageNames, + -- * Helpers for constructing 'Package's + setPath, topLevel, library, utility, setPkgType ) where import Base import GHC.Generics (Generic) --- It is helpful to distinguish package names from strings. +-- | It is helpful to distinguish package names from strings. type PackageName = String --- type PackageType = Program | Library +-- | We regard packages as either being libraries or programs. This is +-- bit of a convenient lie as Cabal packages can be both, but it works +-- for now. +data PackageType = Program | Library + deriving Generic --- pkgPath is the path to the source code relative to the root data Package = Package { - pkgName :: PackageName, -- Examples: "ghc", "Cabal" - pkgPath :: FilePath -- "compiler", "libraries/Cabal/Cabal" - -- pkgType :: PackageType -- TopLevel, Library + pkgName :: PackageName, -- ^ Examples: "ghc", "Cabal" + pkgPath :: FilePath, -- ^ pkgPath is the path to the source code relative to the root. + -- e.g. "compiler", "libraries/Cabal/Cabal" + pkgType :: PackageType } deriving Generic @@ -26,17 +34,20 @@ pkgCabalFile :: Package -> FilePath pkgCabalFile pkg = pkgPath pkg -/- pkgName pkg <.> "cabal" topLevel :: PackageName -> Package -topLevel name = Package name name +topLevel name = Package name name Library library :: PackageName -> Package -library name = Package name ("libraries" -/- name) +library name = Package name ("libraries" -/- name) Library utility :: PackageName -> Package -utility name = Package name ("utils" -/- name) +utility name = Package name ("utils" -/- name) Program setPath :: Package -> FilePath -> Package setPath pkg path = pkg { pkgPath = path } +setPkgType :: Package -> PackageType -> Package +setPkgType pkg ty = pkg { pkgType = ty } + instance Show Package where show = pkgName @@ -56,3 +67,7 @@ instance Binary Package instance Hashable Package where hashWithSalt salt = hashWithSalt salt . show instance NFData Package + +instance Binary PackageType +instance Hashable PackageType +instance NFData PackageType diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index b68a1f6..fdbe21d 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -38,7 +38,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do buildWithResources [(ghcCabal rs, 1)] $ fullTarget target GhcCabal [cabalFile] outs - -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg + -- ghc-pkg produces inplace-pkg-config when run on packages with + -- library components only when (isLibrary pkg) . whenM (interpretPartial target registerPackage) . buildWithResources [(ghcPkg rs, 1)] $ diff --git a/src/Settings.hs b/src/Settings.hs index d16c5cd..7a1ab72 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -33,7 +33,8 @@ programPath :: Stage -> Package -> Maybe FilePath programPath = userProgramPath isLibrary :: Package -> Bool -isLibrary pkg = programPath Stage0 pkg == Nothing +isLibrary (Package {pkgType=Library}) = True +isLibrary _ = False -- Find all Haskell source files for the current target. TODO: simplify. getPackageSources :: Expr [FilePath] diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs index 286670b..a4301f4 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/TargetDirectory.hs @@ -22,7 +22,7 @@ pkgDataFile stage pkg = targetPath stage pkg -/- "package-data.mk" -- Relative path to a package haddock file, e.g.: -- "libraries/array/dist-install/doc/html/array/array.haddock" pkgHaddockFile :: Package -> FilePath -pkgHaddockFile pkg @ (Package name _) = +pkgHaddockFile pkg @ (Package name _ _) = targetPath Stage1 pkg -/- "doc/html" -/- name -/- name <.> "haddock" -- Relative path to a package library file, e.g.: From git at git.haskell.org Fri Oct 27 00:13:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add initial support for --configure command line flag. (e874fed) Message-ID: <20171027001309.D45413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e874fed8e68f9941d2cbd0ed4a64680a7f09586f/ghc >--------------------------------------------------------------- commit e874fed8e68f9941d2cbd0ed4a64680a7f09586f Author: Andrey Mokhov Date: Thu Jan 21 11:13:34 2016 +0000 Add initial support for --configure command line flag. >--------------------------------------------------------------- e874fed8e68f9941d2cbd0ed4a64680a7f09586f src/CmdLineFlag.hs | 56 +++++++++++++++++++++++++++++++++++----------------- src/Rules/Actions.hs | 39 ++++++++++++++++++------------------ src/Rules/Cabal.hs | 1 - src/Rules/Config.hs | 21 ++++++++++---------- src/Settings/User.hs | 9 +++------ 5 files changed, 72 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 e874fed8e68f9941d2cbd0ed4a64680a7f09586f From git at git.haskell.org Fri Oct 27 00:13:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add miscellaneous, minor revision (8c6a188) Message-ID: <20171027001310.D48773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c6a188fc3ecea807a6536ce0442dda6244b7b92/ghc >--------------------------------------------------------------- commit 8c6a188fc3ecea807a6536ce0442dda6244b7b92 Author: Andrey Mokhov Date: Sat May 14 18:33:55 2016 +0100 Add miscellaneous, minor revision [skip ci] >--------------------------------------------------------------- 8c6a188fc3ecea807a6536ce0442dda6244b7b92 doc/user-settings.md | 31 +++++++++++++++++++++++-------- 1 file changed, 23 insertions(+), 8 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index e395ea2..dc718ed 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -81,11 +81,11 @@ integerLibrary = integerGmp ``` ## Build ways -Libraries can be built in a number of ways, such as `vanilla`, `profiling` (with -profiling information enabled), and many others as defined in `src/Way.hs`. To -control which ways particular ways are built, set `userLibraryWays` and -`userRtsWays`. As an example, below we remove `dynamic` from the list of library -ways and keep `rts` package ways unchanged: +Packages can be built in a number of ways, such as `vanilla`, `profiling` (with +profiling information enabled), and many others as defined in `src/Way.hs`. You +can change the default build ways using `userLibraryWays` and `userRtsWays` settings. +As an example, below we remove `dynamic` from the list of library ways but keep +`rts` package ways unchanged: ```haskell -- | Control which ways library packages are built. userLibraryWays :: Ways @@ -99,9 +99,8 @@ userRtsWays = mempty ## Verbose command lines By default Hadrian does not print full command lines during the build process -and instead prints short human readable digests for each executed command. It is -possible to suppress this behaviour completely or partially using -`verboseCommands` setting: +and instead prints short human readable digests for each executed command. You +can suppress this behaviour completely or partially using `verboseCommands` setting: ```haskell -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package @@ -129,3 +128,19 @@ verboseCommands = file "//rts/sm/*" &&^ way threaded -- Print all commands: verboseCommands = return True ``` + +## Miscellaneous + +Use the following settings to change the default behaviour of Hadrian with respect +to building split objects and Haddock documentation. + +```haskell +-- | Control when split objects are generated. Note, due to the GHC bug #11315 +-- it is necessary to do a full clean rebuild when changing this option. +splitObjects :: Predicate +splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects + +-- | Control when to build documentation. +buildHaddock :: Predicate +buildHaddock = return cmdBuildHaddock +``` From git at git.haskell.org Fri Oct 27 00:13:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #8 from bgamari/master (821d9e9) Message-ID: <20171027001313.C2D7E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/821d9e9c6b81381c1dff2c78755a525f4d3543a1/ghc >--------------------------------------------------------------- commit 821d9e9c6b81381c1dff2c78755a525f4d3543a1 Merge: f48da18 86ed4e3 Author: Andrey Mokhov Date: Sun Dec 20 19:34:47 2015 +0000 Merge pull request #8 from bgamari/master Miscellany >--------------------------------------------------------------- 821d9e9c6b81381c1dff2c78755a525f4d3543a1 README.md | 15 +++++++++++++++ src/GHC.hs | 2 +- src/Package.hs | 37 ++++++++++++++++++++++++++----------- src/Rules/Actions.hs | 25 ++++++++++++++++++++----- src/Rules/Data.hs | 3 ++- src/Rules/Documentation.hs | 10 +++++++--- src/Settings.hs | 3 ++- src/Settings/TargetDirectory.hs | 2 +- 8 files changed, 74 insertions(+), 23 deletions(-) From git at git.haskell.org Fri Oct 27 00:13:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add full support for --configure command line flag. (4460146) Message-ID: <20171027001314.3E71F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/446014681874982a340c245d3c279229eeb6f121/ghc >--------------------------------------------------------------- commit 446014681874982a340c245d3c279229eeb6f121 Author: Andrey Mokhov Date: Thu Jan 21 17:36:50 2016 +0000 Add full support for --configure command line flag. >--------------------------------------------------------------- 446014681874982a340c245d3c279229eeb6f121 src/CmdLineFlag.hs | 2 +- src/Rules/Actions.hs | 5 +++-- src/Rules/Config.hs | 31 ++++++++++++++++++++++--------- 3 files changed, 26 insertions(+), 12 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 9e33397..249070a 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -61,7 +61,7 @@ flags = [ Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") , Option [] ["split-objects"] (NoArg readSplitObjects) "Generate split objects (requires a full clean rebuild)." , Option [] ["configure"] (OptArg readConfigure "ARGS") - "Run boot and configure scripts (passing ARGS to the latter)." ] + "Run configure with ARGS (also run boot if necessary)." ] -- TODO: Avoid unsafePerformIO by using shakeExtra (awaiting Shake's release) {-# NOINLINE cmdLineFlags #-} diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 2b05207..0e4961f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -97,12 +97,13 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] + let note = if null args || args == [""] then "" else " (" ++ intercalate ", " args ++ ")" if dir == "." then do - putBuild $ "| Run configure..." + putBuild $ "| Run configure" ++ note ++ "..." quietly $ cmd Shell (EchoStdout False) "bash configure" opts' args else do - putBuild $ "| Run configure in " ++ dir ++ "..." + putBuild $ "| Run configure" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args where -- Always configure with bash. diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 6f0447f..77ac1ac 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -5,13 +5,26 @@ import CmdLineFlag import Rules.Actions configRules :: Rules () -configRules = case cmdConfigure of - SkipConfigure -> mempty - RunConfigure args -> do - configPath -/- "system.config" %> \_ -> do - need [configPath -/- "system.config.in"] - runConfigure "." [] [args] +configRules = do + -- We always rerun the configure script in this mode, because the flags + -- passed to it can affect the contents of system.config file. + configPath -/- "system.config" %> \out -> do + alwaysRerun + case cmdConfigure of + RunConfigure args -> runConfigure "." [] [args] + SkipConfigure -> unlessM (doesFileExist out) $ + putError $ "Configuration file " ++ out ++ " is missing.\n" + ++ "Run the configure script either manually or via the " + ++ "build system by passing --configure[=ARGS] flag." - "configure" %> \_ -> do - putBuild "| Running boot..." - unit $ cmd "perl boot" + -- When we detect Windows paths in ACLOCAL_PATH we reset it. + -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. + "configure" %> \_ -> do + putBuild "| Running boot..." + aclocal <- getEnv "ACLOCAL_PATH" + let env = case aclocal of + Nothing -> [] + Just s -> if ":\\" `isPrefixOf` (drop 1 s) + then [AddEnv "ACLOCAL_PATH" ""] + else [] + quietly $ cmd (EchoStdout False) env "perl boot" From git at git.haskell.org Fri Oct 27 00:13:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comments (b91d515) Message-ID: <20171027001314.C667F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b91d5152c1979d7c36cb2ab16821abec8da7ec1c/ghc >--------------------------------------------------------------- commit b91d5152c1979d7c36cb2ab16821abec8da7ec1c Author: Andrey Mokhov Date: Sun May 15 00:03:12 2016 +0100 Comments [skip ci] >--------------------------------------------------------------- b91d5152c1979d7c36cb2ab16821abec8da7ec1c src/Settings/User.hs | 38 +++++++++++++++++++++----------------- 1 file changed, 21 insertions(+), 17 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 2294fc7..7cf9997 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -12,40 +12,44 @@ import Expression import Predicates import Settings.Default --- | All build artefacts are stored in 'buildRootPath' directory. +-- See doc/user-settings.md for instructions. + +-- | All build results are put into 'buildRootPath' directory. buildRootPath :: FilePath buildRootPath = "_build" --- | Control user-specific command line arguments. +-- | Modify default build command line arguments. userArgs :: Args userArgs = builder Ghc ? remove ["-Wall", "-fwarn-tabs"] --- | Control which packages get to be built. +-- | Modify the set of packages that are built by default in each stage. userPackages :: Packages userPackages = mempty --- | Add new user-defined packages. +-- | Add user defined packages. Don't forget to add them to 'userPackages' too. userKnownPackages :: [Package] userKnownPackages = [] --- | Choose the integer library: integerGmp or integerSimple. +-- | Choose the integer library: 'integerGmp' or 'integerSimple'. integerLibrary :: Package integerLibrary = integerGmp --- | Control which ways library packages are built. --- FIXME: skip dynamic since it's currently broken #4 +-- FIXME: We skip 'dynamic' since it's currently broken #4. +-- | Modify the set of ways in which library packages are built. userLibraryWays :: Ways userLibraryWays = remove [dynamic] --- | Control which ways the 'rts' package is built. +-- | Modify the set of ways in which the 'rts' package is built. userRtsWays :: Ways userRtsWays = mempty --- | User-defined flags. Note the following type semantics: --- * Bool: a plain Boolean flag whose value is known at compile time --- * Action Bool: a flag whose value can depend on the build environment --- * Predicate: a flag depending on the build environment and the current target +-- | User defined flags. Note the following type semantics: +-- * @Bool@: a plain Boolean flag whose value is known at compile time. +-- * @Action Bool@: a flag whose value can depend on the build environment. +-- * @Predicate@: a flag whose value can depend on the build environment and +-- on the current build target. +-- TODO: Drop 'trackBuildSystem' as it brings negligible gains. -- | Set this to True if you are making any changes in the build system and want -- appropriate rebuilds to be initiated. Switching this to False speeds things -- up a little (particularly zero builds). @@ -62,12 +66,12 @@ validating = False splitObjects :: Predicate splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects --- | Control when to build documentation. +-- | Control when to build Haddock documentation. buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock -- TODO: Do we need to be able to set these from command line? --- TODO: Turn below into ghcWays? +-- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? dynamicGhcPrograms :: Bool dynamicGhcPrograms = False @@ -81,12 +85,12 @@ ghcDebugged :: Bool ghcDebugged = False -- | Set to True to print full command lines during the build process. Note, --- this is a Predicate, hence you can enable verbose output for a chosen package --- only, e.g.: verboseCommands = package ghcPrim. +-- this is a Predicate, hence you can enable verbose output only for certain +-- targets, e.g.: @verboseCommands = package ghcPrim at . verboseCommands :: Predicate verboseCommands = return False --- TODO: Replace with stage2 ? arg "-Werror"? +-- TODO: Replace with stage2 ? arg "-Werror"? Also see #251. -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False From git at git.haskell.org Fri Oct 27 00:13:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rules: Refactor generateTargets (c84445f) Message-ID: <20171027001318.223C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c84445f81aafbe4089d860ae4a3e0c020a38b118/ghc >--------------------------------------------------------------- commit c84445f81aafbe4089d860ae4a3e0c020a38b118 Author: Ben Gamari Date: Sun Dec 20 20:49:29 2015 +0100 Rules: Refactor generateTargets This previously used `fromJust`, which bottomed due to the recent `isLibrary` change. >--------------------------------------------------------------- c84445f81aafbe4089d860ae4a3e0c020a38b118 src/Rules.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 505b8a5..55ff066 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -10,12 +10,12 @@ generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do pkgs <- interpretWithStage stage getPackages - let (libPkgs, programPkgs) = partition isLibrary pkgs + let libPkgs = filter isLibrary pkgs libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg needHaddock <- interpretPartial target buildHaddock - return $ [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] - let programTargets = map (fromJust . programPath stage) programPkgs + return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] + let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] return $ libTargets ++ programTargets need $ reverse targets From git at git.haskell.org Fri Oct 27 00:13:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch on ChangeModtimeAndDigest by default. (c9b2b76) Message-ID: <20171027001318.CBF473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9b2b7633dea28eb1e5e0f6001f9cc12b34c8584/ghc >--------------------------------------------------------------- commit c9b2b7633dea28eb1e5e0f6001f9cc12b34c8584 Author: Andrey Mokhov Date: Thu Jan 21 19:14:08 2016 +0000 Switch on ChangeModtimeAndDigest by default. >--------------------------------------------------------------- c9b2b7633dea28eb1e5e0f6001f9cc12b34c8584 src/Main.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index 5c62479..f83734c 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -35,6 +35,7 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do , Rules.packageRules , Test.testRules ] options = shakeOptions - { shakeFiles = Base.shakeFilesPath + { shakeChange = ChangeModtimeAndDigest + , shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:13:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unix line endings, match Haddock comments in Settings/User.hs (3ff4183) Message-ID: <20171027001319.309A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ff4183c5741ca780fb4e4b7274b7d951430fdde/ghc >--------------------------------------------------------------- commit 3ff4183c5741ca780fb4e4b7274b7d951430fdde Author: Andrey Mokhov Date: Sun May 15 00:11:25 2016 +0100 Unix line endings, match Haddock comments in Settings/User.hs [skip ci] >--------------------------------------------------------------- 3ff4183c5741ca780fb4e4b7274b7d951430fdde doc/user-settings.md | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index dc718ed..e6b81f8 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -8,7 +8,7 @@ You can customise Hadrian by specifying user build settings in file Hadrian puts build results into `_build` directory by default, which is specified by `buildRootPath`: ```haskell --- | All build artefacts are stored in 'buildRootPath' directory. +-- | All build results are put into 'buildRootPath' directory. buildRootPath :: FilePath buildRootPath = "_build" ``` @@ -22,7 +22,7 @@ affected build rules during the next build, without requiring a full rebuild. For example, here is how to pass an extra argument `-O0` to all invocations of GHC when compiling package `cabal`: ```haskell --- | Control user-specific command line arguments. +-- | Modify default build command line arguments. userArgs :: Args userArgs = builder Ghc ? package cabal ? arg "-O0" ``` @@ -52,7 +52,7 @@ To add or remove a package from a particular build stage, use `userPackages`. As an example, below we add package `base` to Stage0 and remove package `haskeline` from Stage1: ```haskell --- | Control which packages get to be built. +-- | Modify the set of packages that are built by default in each stage. userPackages :: Packages userPackages = mconcat [ stage0 ? append [base] @@ -61,7 +61,7 @@ userPackages = mconcat If you are working on a new GHC package you need to let Hadrian know about it by setting `userKnownPackages`: ```haskell --- | Add new user-defined packages. +-- | Add user defined packages. Don't forget to add them to 'userPackages' too. userKnownPackages :: [Package] userKnownPackages = [myPackage] @@ -73,9 +73,9 @@ Note, you will also need to add `myPackage` to a specific build stage by modifyi `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting -`integerLibrary`: +`integerLibrary`. Possible values are: `integerGmp` (default) and `integerSimple`. ```haskell --- | Choose the integer library: integerGmp or integerSimple. +-- | Choose the integer library: 'integerGmp' or 'integerSimple'. integerLibrary :: Package integerLibrary = integerGmp ``` @@ -87,11 +87,11 @@ can change the default build ways using `userLibraryWays` and `userRtsWays` sett As an example, below we remove `dynamic` from the list of library ways but keep `rts` package ways unchanged: ```haskell --- | Control which ways library packages are built. +-- | Modify the set of ways in which library packages are built. userLibraryWays :: Ways userLibraryWays = remove [dynamic] --- | Control which ways the 'rts' package is built. +-- | Modify the set of ways in which the 'rts' package is built. userRtsWays :: Ways userRtsWays = mempty ``` @@ -103,8 +103,8 @@ and instead prints short human readable digests for each executed command. You can suppress this behaviour completely or partially using `verboseCommands` setting: ```haskell -- | Set to True to print full command lines during the build process. Note, --- this is a Predicate, hence you can enable verbose output for a chosen package --- only, e.g.: verboseCommands = package ghcPrim +-- this is a Predicate, hence you can enable verbose output only for certain +-- targets, e.g.: @verboseCommands = package ghcPrim at . verboseCommands :: Predicate verboseCommands = return False ``` @@ -140,7 +140,7 @@ to building split objects and Haddock documentation. splitObjects :: Predicate splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects --- | Control when to build documentation. +-- | Control when to build Haddock documentation. buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock ``` From git at git.haskell.org Fri Oct 27 00:13:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GHC: Set PackageType of iservBin (139d90d) Message-ID: <20171027001322.65C5C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/139d90d43b6a8fb125ea05136531848cebb96096/ghc >--------------------------------------------------------------- commit 139d90d43b6a8fb125ea05136531848cebb96096 Author: Ben Gamari Date: Sun Dec 20 20:45:05 2015 +0100 GHC: Set PackageType of iservBin >--------------------------------------------------------------- 139d90d43b6a8fb125ea05136531848cebb96096 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index c38af04..29db671 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -68,7 +68,7 @@ hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" integerGmp = library "integer-gmp" integerSimple = library "integer-simple" -iservBin = topLevel "iserv-bin" `setPath` "iserv" +iservBin = topLevel "iserv-bin" `setPath` "iserv" `setPkgType` Program mkUserGuidePart = utility "mkUserGuidePart" parallel = library "parallel" pretty = library "pretty" From git at git.haskell.org Fri Oct 27 00:13:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Major rewrite before the first release (6bdb902) Message-ID: <20171027001323.23BA83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6bdb90260373d6ab3af2836d2e621d60beb13815/ghc >--------------------------------------------------------------- commit 6bdb90260373d6ab3af2836d2e621d60beb13815 Author: Andrey Mokhov Date: Fri Jan 22 02:07:49 2016 +0000 Major rewrite before the first release >--------------------------------------------------------------- 6bdb90260373d6ab3af2836d2e621d60beb13815 README.md | 146 +++++++++++++++++++++++++++++++++++++++----------------------- 1 file changed, 92 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 6bdb90260373d6ab3af2836d2e621d60beb13815 From git at git.haskell.org Fri Oct 27 00:13:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix predicate (c8725b2) Message-ID: <20171027001323.3EFA83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8725b225655b0d7f320cff4ebff1fb1918311f4/ghc >--------------------------------------------------------------- commit c8725b225655b0d7f320cff4ebff1fb1918311f4 Author: Andrey Mokhov Date: Sun May 15 00:14:34 2016 +0100 Fix predicate [skip ci] >--------------------------------------------------------------- c8725b225655b0d7f320cff4ebff1fb1918311f4 doc/user-settings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index e6b81f8..4624e2d 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -123,7 +123,7 @@ verboseCommands = builder (Ghc Link) verboseCommands = builder (Gcc Compile) &&^ package compiler -- Use patterns when matching files: -verboseCommands = file "//rts/sm/*" &&^ way threaded +verboseCommands = output "//rts/sm/*" &&^ way threaded -- Print all commands: verboseCommands = return True From git at git.haskell.org Fri Oct 27 00:13:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #11 from bgamari/master (5c42b58) Message-ID: <20171027001326.193513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5c42b582cb8c05741cc5be87dd3ec2f935997f56/ghc >--------------------------------------------------------------- commit 5c42b582cb8c05741cc5be87dd3ec2f935997f56 Merge: 821d9e9 c84445f Author: Andrey Mokhov Date: Sun Dec 20 20:15:12 2015 +0000 Merge pull request #11 from bgamari/master Fix fallout from previous refactoring >--------------------------------------------------------------- 5c42b582cb8c05741cc5be87dd3ec2f935997f56 src/GHC.hs | 2 +- src/Rules.hs | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) From git at git.haskell.org Fri Oct 27 00:13:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify (2ac9e71) Message-ID: <20171027001327.0196B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ac9e71747347801d70e80e9d603a5c79c8f5d5a/ghc >--------------------------------------------------------------- commit 2ac9e71747347801d70e80e9d603a5c79c8f5d5a Author: Andrey Mokhov Date: Sun May 15 00:20:54 2016 +0100 Simplify >--------------------------------------------------------------- 2ac9e71747347801d70e80e9d603a5c79c8f5d5a src/Settings/Packages/Rts.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 60fdf7a..35a1f95 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -96,13 +96,13 @@ rtsPackageArgs = package rts ? do , builder (GhcPkg Stage1) ? mconcat [ remove ["rts/stage1/inplace-pkg-config"] -- TODO: fix, see #113 - , arg $ rtsConf ] + , arg rtsConf ] - , builder HsCpp ? mconcat - [ arg ("-DTOP=" ++ quote top) - , arg ("-DFFI_INCLUDE_DIR=" ++ quote ffiIncludeDir) - , arg ("-DFFI_LIB_DIR=" ++ quote ffiLibraryDir) - , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] + , builder HsCpp ? append + [ "-DTOP=" ++ quote top + , "-DFFI_INCLUDE_DIR=" ++ quote ffiIncludeDir + , "-DFFI_LIB_DIR=" ++ quote ffiLibraryDir + , "-DFFI_LIB=" ++ quote libffiName ] ] -- # If we're compiling on windows, enforce that we only support XP+ From git at git.haskell.org Fri Oct 27 00:13:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hide `parallel` from shake (aad2247) Message-ID: <20171027001329.D58923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aad2247ecc85160af1d27f7c4e3bb227a754630f/ghc >--------------------------------------------------------------- commit aad2247ecc85160af1d27f7c4e3bb227a754630f Author: Ben Gamari Date: Sun Dec 20 21:41:07 2015 +0100 Hide `parallel` from shake Shake `master` branch exports a symbol called `parallel` which overlaps with ours. >--------------------------------------------------------------- aad2247ecc85160af1d27f7c4e3bb227a754630f src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 1c72fd8..7edae37 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -38,7 +38,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>)) +import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes import Development.Shake.Config import Development.Shake.FilePath From git at git.haskell.org Fri Oct 27 00:13:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add and link to important issues. (3d335e1) Message-ID: <20171027001331.2827D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d335e1eca20caaf40bb8227ffbf85e9a675c187/ghc >--------------------------------------------------------------- commit 3d335e1eca20caaf40bb8227ffbf85e9a675c187 Author: Andrey Mokhov Date: Fri Jan 22 12:16:12 2016 +0000 Add and link to important issues. [skip ci] >--------------------------------------------------------------- 3d335e1eca20caaf40bb8227ffbf85e9a675c187 README.md | 29 +++++++++++++++++++---------- 1 file changed, 19 insertions(+), 10 deletions(-) diff --git a/README.md b/README.md index 1f96505..a368c01 100644 --- a/README.md +++ b/README.md @@ -45,9 +45,9 @@ Using the build system ---------------------- Once your first build is successful, simply run `shake-build/build.sh` or `shake-build/build.bat` to rebuild (you no longer need to use the `--configure` flag). Most build artefacts are placed -into `.build` and `inplace` directories. +into `.build` and `inplace` directories ([#113][build-artefacts-issue]). -### Command line flags +#### Command line flags In addition to standard Shake flags (try `--help`), the build system currently supports several others: @@ -61,13 +61,13 @@ build command; this is the default setting), and `unicorn` (when `normal` just w * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. -### User settings +#### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We use [`src/Settings/User.hs`][user-settings] for the same purpose. Feel free to -experiment. +experiment following the Haddock comments. -### Resetting the build +#### Resetting the build To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. @@ -76,11 +76,11 @@ This is a temporary solution; we are working on proper reset functionality ([#13 Current limitations ------------------- The new build system still lacks many important features: -* We only build `vanilla` way. +* We only build `vanilla` way: [#4][dynamic-issue], [#186][profiling-issue]. * Documentation is broken: [#98][haddock-issue]. -* Validation is not implemented. -* Build flavours and conventional command line flags are not implemented. -* Cross-compilation is not implemented. +* Validation is not implemented: [#187][validation-issue]. +* Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. +* Cross-compilation is not implemented: [#177][cross-compilation-issue]. How to contribute ----------------- @@ -88,7 +88,8 @@ How to contribute The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note the codebase is very unstable at present and we expect a lot of further refactoring. The documentation is -currently non-existent, but we are working on it. +currently non-existent, but we are working on it: [#55][comments-issue], +[#56][doc-issue]. Acknowledgements ---------------- @@ -108,8 +109,16 @@ helped me endure and enjoy the project. [issues]: https://github.com/snowleopard/shaking-up-ghc/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild +[build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs [reset-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/131 +[dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 +[profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 +[validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 +[flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 +[cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 +[comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 +[doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 [contributors]: https://github.com/snowleopard/shaking-up-ghc/graphs/contributors From git at git.haskell.org Fri Oct 27 00:13:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop non-derived Show instance for PackageName (dc0bae1) Message-ID: <20171027001331.3B0AC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dc0bae1e5aeb05e5704e38a8aa5c64887165fcc6/ghc >--------------------------------------------------------------- commit dc0bae1e5aeb05e5704e38a8aa5c64887165fcc6 Author: Andrey Mokhov Date: Sun May 15 00:47:13 2016 +0100 Drop non-derived Show instance for PackageName >--------------------------------------------------------------- dc0bae1e5aeb05e5704e38a8aa5c64887165fcc6 src/Oracles/PackageDeps.hs | 8 ++++---- src/Package.hs | 21 +++++++++------------ 2 files changed, 13 insertions(+), 16 deletions(-) diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index a2a9234..7983c7f 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -7,7 +7,7 @@ import Base import Package import Settings.Paths -newtype PackageDepsKey = PackageDepsKey PackageName +newtype PackageDepsKey = PackageDepsKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- @packageDeps name@ is an action that given a 'Package' looks up its @@ -15,8 +15,8 @@ newtype PackageDepsKey = PackageDepsKey PackageName -- computed by scanning package cabal files (see Rules.Cabal). packageDeps :: Package -> Action [PackageName] packageDeps pkg = do - res <- askOracle . PackageDepsKey . pkgName $ pkg - return . fromMaybe [] $ res + res <- askOracle . PackageDepsKey $ pkgNameString pkg + return . map PackageName $ fromMaybe [] res -- Oracle for the package dependencies file packageDepsOracle :: Rules () @@ -25,6 +25,6 @@ packageDepsOracle = do putOracle $ "Reading package dependencies..." contents <- readFileLines packageDependencies return . Map.fromList $ - [ (p, ps) | line <- contents, let p:ps = map PackageName $ words line ] + [ (p, ps) | line <- contents, let p:ps = words line ] _ <- addOracle $ \(PackageDepsKey pkg) -> Map.lookup pkg <$> deps () return () diff --git a/src/Package.hs b/src/Package.hs index 4b6fbc6..1fc1ac9 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -15,12 +15,9 @@ import GHC.Generics (Generic) import Data.String -- | The name of a Cabal package -newtype PackageName = PackageName { getPackageName :: String } +newtype PackageName = PackageName { fromPackageName :: String } deriving (Eq, Ord, IsString, Generic, Binary, Hashable, Typeable, NFData) -instance Show PackageName where - show (PackageName name) = name - -- TODO: Make PackageType more precise, #12 -- TODO: Turn Program to Program FilePath thereby getting rid of programPath -- | We regard packages as either being libraries or programs. This is @@ -37,23 +34,23 @@ data Package = Package -- | Prettyprint Package name. pkgNameString :: Package -> String -pkgNameString = getPackageName . pkgName +pkgNameString = fromPackageName . pkgName -- | Relative path to cabal file, e.g.: "libraries/Cabal/Cabal/Cabal.cabal" pkgCabalFile :: Package -> FilePath -pkgCabalFile pkg = pkgPath pkg -/- getPackageName (pkgName pkg) <.> "cabal" +pkgCabalFile pkg = pkgPath pkg -/- pkgNameString pkg <.> "cabal" -- | Smart constructor for a top-level package, e.g. 'compiler'. topLevel :: PackageName -> Package -topLevel name = Package name (getPackageName name) Library +topLevel name = Package name (fromPackageName name) Library -- | Smart constructor for a library package, e.g. 'array'. library :: PackageName -> Package -library name = Package name ("libraries" -/- getPackageName name) Library +library name = Package name ("libraries" -/- fromPackageName name) Library -- | Smart constructor for a utility package, e.g. 'haddock'. utility :: PackageName -> Package -utility name = Package name ("utils" -/- getPackageName name) Program +utility name = Package name ("utils" -/- fromPackageName name) Program -- | Amend package path. Useful when a package name doesn't match its path. setPath :: Package -> FilePath -> Package @@ -65,17 +62,17 @@ setType pkg ty = pkg { pkgType = ty } -- | Check whether a package is a library. isLibrary :: Package -> Bool -isLibrary (Package {pkgType=Library}) = True +isLibrary (Package _ _ Library) = True isLibrary _ = False -- | Check whether a package is a program. isProgram :: Package -> Bool -isProgram (Package {pkgType=Program}) = True +isProgram (Package _ _ Program) = True isProgram _ = False -- TODO: Get rid of non-derived Show instances. instance Show Package where - show = show . pkgName + show = pkgNameString instance Eq Package where (==) = (==) `on` pkgName From git at git.haskell.org Fri Oct 27 00:13:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Use proper Haddock syntax (ecd1e7d) Message-ID: <20171027001333.685D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ecd1e7db540b6cf31cc884b5dccba1bf9e01de70/ghc >--------------------------------------------------------------- commit ecd1e7db540b6cf31cc884b5dccba1bf9e01de70 Author: Ben Gamari Date: Sun Dec 20 21:40:53 2015 +0100 Base: Use proper Haddock syntax >--------------------------------------------------------------- ecd1e7db540b6cf31cc884b5dccba1bf9e01de70 src/Base.hs | 44 +++++++++++++++++++++++++++----------------- 1 file changed, 27 insertions(+), 17 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 33b01bd..1c72fd8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,5 @@ module Base ( + -- * General utilities module Control.Applicative, module Control.Monad.Extra, module Control.Monad.Reader, @@ -7,18 +8,26 @@ module Base ( module Data.List, module Data.Maybe, module Data.Monoid, + + -- * Shake module Development.Shake, module Development.Shake.Classes, module Development.Shake.Config, module Development.Shake.FilePath, module Development.Shake.Util, - module System.Console.ANSI, + + -- * Paths shakeFilesPath, configPath, bootPackageConstraints, packageDependencies, - replaceEq, replaceSeparators, decodeModule, - unifyPath, (-/-), chunksOfSize, + + -- * Output putColoured, putOracle, putBuild, putSuccess, putError, + module System.Console.ANSI, + + -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, - removeFileIfExists + removeFileIfExists, + replaceEq, replaceSeparators, decodeModule, + unifyPath, (-/-), chunksOfSize, ) where import Control.Applicative @@ -55,34 +64,35 @@ packageDependencies :: FilePath packageDependencies = shakeFilesPath -/- "package-dependencies" -- Utility functions --- Find and replace all occurrences of a value in a list +-- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceIf (== from) --- Find and replace all occurrences of path separators in a String with a Char +-- | Find and replace all occurrences of path separators in a String with a Char replaceSeparators :: Char -> String -> String replaceSeparators = replaceIf isPathSeparator replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) --- Given a module name extract the directory and file names, e.g.: --- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +-- | Given a module name extract the directory and file names, e.g.: +-- +-- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") decodeModule :: String -> (FilePath, String) decodeModule = splitFileName . replaceEq '.' '/' --- Normalise a path and convert all path separators to /, even on Windows. +-- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx --- Combine paths using and apply unifyPath to the result +-- | Combine paths using '' and apply 'unifyPath' to the result (-/-) :: FilePath -> FilePath -> FilePath a -/- b = unifyPath $ a b infixr 6 -/- --- (chunksOfSize size strings) splits a given list of strings into chunks not --- exceeding the given 'size'. +-- | @chunksOfSize size strings@ splits a given list of strings into chunks not +-- exceeding the given @size at . chunksOfSize :: Int -> [String] -> [[String]] chunksOfSize _ [] = [] chunksOfSize size strings = reverse chunk : chunksOfSize size rest @@ -94,7 +104,7 @@ chunksOfSize size strings = reverse chunk : chunksOfSize size rest where newSize = chunkSize + length s --- A more colourful version of Shake's putNormal +-- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do liftIO $ setSGR [SetColor Foreground Vivid colour] @@ -102,19 +112,19 @@ putColoured colour msg = do liftIO $ setSGR [] liftIO $ hFlush stdout --- Make oracle output more distinguishable +-- | Make oracle output more distinguishable putOracle :: String -> Action () putOracle = putColoured Blue --- Make build output more distinguishable +-- | Make build output more distinguishable putBuild :: String -> Action () putBuild = putColoured White --- A more colourful version of success message +-- | A more colourful version of success message putSuccess :: String -> Action () putSuccess = putColoured Green --- A more colourful version of error message +-- | A more colourful version of error message putError :: String -> Action a putError msg = do putColoured Red msg From git at git.haskell.org Fri Oct 27 00:13:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (e2b0201) Message-ID: <20171027001334.CB08C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2b0201a4b8694955bd2701deaca22c4be15c155/ghc >--------------------------------------------------------------- commit e2b0201a4b8694955bd2701deaca22c4be15c155 Author: Andrey Mokhov Date: Fri Jan 22 12:18:22 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- e2b0201a4b8694955bd2701deaca22c4be15c155 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index a368c01..9845e17 100644 --- a/README.md +++ b/README.md @@ -95,7 +95,7 @@ Acknowledgements ---------------- I started this project as part of my 6-month research visit to Microsoft -Research in Cambridge. It was funded by Newcastle University, EPSRC, and +Research in Cambridge, which was funded by Newcastle University, EPSRC, and Microsoft Research. I would like to thank Simon Peyton Jones, Neil Mitchell and Simon Marlow for kick-starting the project and for their guidance. Last but not least, big thanks to the project [contributors][contributors], who From git at git.haskell.org Fri Oct 27 00:13:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (3c5998c) Message-ID: <20171027001334.BDE623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c5998cddf477e84ee2e0b98de7a7d26bb0da710/ghc >--------------------------------------------------------------- commit 3c5998cddf477e84ee2e0b98de7a7d26bb0da710 Author: Andrey Mokhov Date: Sun May 15 01:02:51 2016 +0100 Minor revision >--------------------------------------------------------------- 3c5998cddf477e84ee2e0b98de7a7d26bb0da710 src/Oracles/PackageData.hs | 20 +++++++++----------- 1 file changed, 9 insertions(+), 11 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index ba3e205..dba1192 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -5,17 +5,10 @@ module Oracles.PackageData ( ) where import Development.Shake.Config -import Base import qualified Data.HashMap.Strict as Map --- For each (PackageData path) the file 'path/package-data.mk' contains --- a line of the form 'path_VERSION = 1.2.3.4'. --- pkgData $ PackageData path is an action that consults the file and --- returns "1.2.3.4". --- --- PackageDataList is used for multiple string options separated by spaces, --- such as 'path_MODULES = Data.Array Data.Array.Base ...'. --- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] +import Base + data PackageData = BuildGhciLib FilePath | ComponentId FilePath | Synopsis FilePath @@ -51,8 +44,10 @@ askPackageData path key = do case maybeValue of Nothing -> return "" Just value -> return value - -- Nothing -> putError $ "No key '" ++ key ++ "' in " ++ file ++ "." +-- | For each @PackageData path@ the file 'path/package-data.mk' contains a line +-- of the form 'path_VERSION = 1.2.3.4'. @pkgData (PackageData path)@ is an +-- Action that consults the file and returns "1.2.3.4". pkgData :: PackageData -> Action String pkgData packageData = case packageData of BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" @@ -60,6 +55,9 @@ pkgData packageData = case packageData of Synopsis path -> askPackageData path "SYNOPSIS" Version path -> askPackageData path "VERSION" +-- | @PackageDataList path@ is used for multiple string options separated by +-- spaces, such as @path_MODULES = Data.Array Data.Array.Base ... at . +-- @pkgListData Modules@ therefore returns ["Data.Array", "Data.Array.Base", ...] pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = fmap (map unquote . words) $ case packageData of CcArgs path -> askPackageData path "CC_OPTS" @@ -83,7 +81,7 @@ pkgDataList packageData = fmap (map unquote . words) $ case packageData of where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') --- Oracle for 'package-data.mk' files +-- | Oracle for 'package-data.mk' files. packageDataOracle :: Rules () packageDataOracle = do keys <- newCache $ \file -> do From git at git.haskell.org Fri Oct 27 00:13:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Library: Use renderBox (c7a0c19) Message-ID: <20171027001336.CD06B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7a0c197ec98a64089af06a9efd0a8f41bfddead/ghc >--------------------------------------------------------------- commit c7a0c197ec98a64089af06a9efd0a8f41bfddead Author: Ben Gamari Date: Sun Dec 20 21:46:19 2015 +0100 Library: Use renderBox >--------------------------------------------------------------- c7a0c197ec98a64089af06a9efd0a8f41bfddead src/Rules/Library.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 088ac8d..134e2be 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -46,11 +46,12 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do else build $ fullTarget target Ar objs [a] synopsis <- interpretPartial target $ getPkgData Synopsis - putSuccess $ "/--------\n| Successfully built package library '" - ++ pkgName pkg - ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." - putSuccess $ "| Package synopsis: " - ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" + putSuccess $ renderBox + [ "Successfully built package library '" + ++ pkgName pkg + ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." + , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." + ] -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. From git at git.haskell.org Fri Oct 27 00:13:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a link to milestones. (1b08589) Message-ID: <20171027001338.7DB4B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b08589b98dc1c354042d62c004640d394485c39/ghc >--------------------------------------------------------------- commit 1b08589b98dc1c354042d62c004640d394485c39 Author: Andrey Mokhov Date: Fri Jan 22 12:26:18 2016 +0000 Add a link to milestones. [skip ci] >--------------------------------------------------------------- 1b08589b98dc1c354042d62c004640d394485c39 README.md | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 9845e17..b80b621 100644 --- a/README.md +++ b/README.md @@ -82,6 +82,8 @@ The new build system still lacks many important features: * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. +Check out [milestones] to see when we hope to resolve the above limitations. + How to contribute ----------------- @@ -95,7 +97,7 @@ Acknowledgements ---------------- I started this project as part of my 6-month research visit to Microsoft -Research in Cambridge, which was funded by Newcastle University, EPSRC, and +Research Cambridge, which was funded by Newcastle University, EPSRC, and Microsoft Research. I would like to thank Simon Peyton Jones, Neil Mitchell and Simon Marlow for kick-starting the project and for their guidance. Last but not least, big thanks to the project [contributors][contributors], who @@ -119,6 +121,7 @@ helped me endure and enjoy the project. [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 +[milestones]: https://github.com/snowleopard/shaking-up-ghc/milestones [comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 [doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 [contributors]: https://github.com/snowleopard/shaking-up-ghc/graphs/contributors From git at git.haskell.org Fri Oct 27 00:13:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop DeriveDataTypeable extension (fda4673) Message-ID: <20171027001338.8EA793A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fda46732212cd1f052734ac796dafb3b3f7526a8/ghc >--------------------------------------------------------------- commit fda46732212cd1f052734ac796dafb3b3f7526a8 Author: Andrey Mokhov Date: Sun May 15 01:03:32 2016 +0100 Drop DeriveDataTypeable extension >--------------------------------------------------------------- fda46732212cd1f052734ac796dafb3b3f7526a8 hadrian.cabal | 3 +-- src/Oracles/ArgsHash.hs | 2 +- src/Oracles/Config.hs | 2 +- src/Oracles/Dependencies.hs | 2 +- src/Oracles/LookupInPath.hs | 2 +- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Oracles/WindowsPath.hs | 2 +- src/Package.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- 11 files changed, 11 insertions(+), 12 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 5c13f7a..7f03057 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -112,8 +112,7 @@ executable hadrian default-language: Haskell2010 default-extensions: RecordWildCards - other-extensions: DeriveDataTypeable - , DeriveGeneric + other-extensions: DeriveGeneric , FlexibleInstances , GeneralizedNewtypeDeriving , LambdaCase diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index d3bfd61..c26efd4 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.ArgsHash (checkArgsHash, argsHashOracle) where import Base diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index 7801208..95facc8 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Config (askConfig, askConfigWithDefault, configOracle) where import Base diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index aa54d86..08b3afa 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Dependencies (dependencies, dependenciesOracle) where import Control.Monad.Trans.Maybe diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 0ea03fd..18c990b 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where import System.Directory diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 233cdc0..f2b03f3 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.ModuleFiles ( decodeModule, encodeModule, findGenerator, haskellSources, moduleFilesOracle ) where diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index dba1192..6a01692 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( PackageData (..), PackageDataList (..), pkgData, pkgDataList, packageDataOracle diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 7983c7f..c70b959 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.PackageDeps (packageDeps, packageDepsOracle) where import qualified Data.HashMap.Strict as Map diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index e252bba..2a3336d 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.WindowsPath ( fixAbsolutePathOnWindows, topDirectory, windowsPathOracle ) where diff --git a/src/Package.hs b/src/Package.hs index 1fc1ac9..7517d87 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving, DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving #-} module Package ( Package (..), PackageName (..), PackageType (..), diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index faeb99d..9df0fdb 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDbArgs, PackageDbKey (..), cppArgs, needDll0 From git at git.haskell.org Fri Oct 27 00:13:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Program: Use renderBox (cbd6aef) Message-ID: <20171027001340.557953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbd6aef9b8d6697da710d119deb05277822c5e31/ghc >--------------------------------------------------------------- commit cbd6aef9b8d6697da710d119deb05277822c5e31 Author: Ben Gamari Date: Sun Dec 20 21:43:28 2015 +0100 Program: Use renderBox >--------------------------------------------------------------- cbd6aef9b8d6697da710d119deb05277822c5e31 src/Rules/Program.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 8e3ec77..2ff5ef0 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -47,8 +47,9 @@ buildProgram _ target @ (PartialTarget stage pkg) = do need $ objs ++ libs build $ fullTargetWithWay target (Ghc stage) vanilla objs [bin] synopsis <- interpretPartial target $ getPkgData Synopsis - putSuccess $ "/--------\n| Successfully built program '" - ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." - putSuccess $ "| Executable: " ++ bin - putSuccess $ "| Package synopsis: " - ++ dropWhileEnd isPunctuation synopsis ++ "." ++ "\n\\--------" + putSuccess $ renderBox + [ "Successfully built program '" + ++ pkgName pkg ++ "' (stage " ++ show stage ++ ")." + , "Executable: " ++ bin + , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." + ] From git at git.haskell.org Fri Oct 27 00:13:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement clean target. (a730d9b) Message-ID: <20171027001342.706B53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a730d9bd25ac701cd9b6bd22b4f4fb14f88902dd/ghc >--------------------------------------------------------------- commit a730d9bd25ac701cd9b6bd22b4f4fb14f88902dd Author: Andrey Mokhov Date: Fri Jan 22 12:57:14 2016 +0000 Implement clean target. Fix #131. >--------------------------------------------------------------- a730d9bd25ac701cd9b6bd22b4f4fb14f88902dd shaking-up-ghc.cabal | 1 + src/Main.hs | 2 ++ src/Rules/Clean.hs | 30 ++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 2 +- 4 files changed, 34 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index b6a42d5..bd21d28 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -39,6 +39,7 @@ executable ghc-shake , Rules , Rules.Actions , Rules.Cabal + , Rules.Clean , Rules.Compile , Rules.Config , Rules.Data diff --git a/src/Main.hs b/src/Main.hs index f83734c..7321f88 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -6,6 +6,7 @@ import qualified Base import CmdLineFlag import qualified Rules import qualified Rules.Cabal +import qualified Rules.Clean import qualified Rules.Config import qualified Rules.Generate import qualified Rules.Gmp @@ -24,6 +25,7 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do rules :: Rules () rules = mconcat [ Rules.Cabal.cabalRules + , Rules.Clean.cleanRules , Rules.Config.configRules , Rules.Generate.copyRules , Rules.Generate.generateRules diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs new file mode 100644 index 0000000..6ab5309 --- /dev/null +++ b/src/Rules/Clean.hs @@ -0,0 +1,30 @@ +module Rules.Clean (cleanRules) where + +import Base +import Package +import Rules.Generate +import Settings.Packages +import Settings.Paths +import Settings.User +import Stage + +cleanRules :: Rules () +cleanRules = do + "clean" ~> do + putBuild $ "| Remove files in " ++ buildRootPath ++ "..." + removeFilesAfter buildRootPath ["//*"] + putBuild $ "| Remove files in " ++ programInplacePath ++ "..." + removeFilesAfter programInplacePath ["//*"] + putBuild $ "| Remove files in inplace/lib..." + removeFilesAfter "inplace/lib" ["//*"] + putBuild $ "| Remove files in " ++ derivedConstantsPath ++ "..." + removeFilesAfter derivedConstantsPath ["//*"] + forM_ includesDependencies $ \file -> do + putBuild $ "| Remove " ++ file + removeFileIfExists file + putBuild $ "| Remove files generated by ghc-cabal..." + forM_ knownPackages $ \pkg -> + forM_ [Stage0 ..] $ \stage -> do + let dir = pkgPath pkg -/- targetDirectory stage pkg + removeDirectoryIfExists dir + putSuccess $ "| Done. " diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index c5386e4..73b160a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( generatePackageCode, generateRules, installTargets, copyRules, - derivedConstantsPath, generatedDependencies + includesDependencies, derivedConstantsPath, generatedDependencies ) where import Base From git at git.haskell.org Fri Oct 27 00:13:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (f50439d) Message-ID: <20171027001342.736133A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f50439d081f137ee3e7abfbdc2f19e4b37620bbd/ghc >--------------------------------------------------------------- commit f50439d081f137ee3e7abfbdc2f19e4b37620bbd Author: Andrey Mokhov Date: Mon May 16 00:26:02 2016 +0100 Minor revision >--------------------------------------------------------------- f50439d081f137ee3e7abfbdc2f19e4b37620bbd src/Rules/Register.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index cd3649b..f35413a 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -10,38 +10,37 @@ import Settings import Settings.Packages.Rts import Target --- Build package-data.mk by using GhcCabal to process pkgCabal file +-- | Build package-data.mk by processing the .cabal file with ghc-cabal utility. registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context at Context {..} = do - let oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 + let path = buildPath context + oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 pkgConf = packageDbDirectory stage -/- pkgNameString package when (stage <= Stage1) $ matchVersionedFilePath pkgConf "conf" ?> \conf -> do - -- This produces inplace-pkg-config. TODO: Add explicit tracking + -- This produces inplace-pkg-config. TODO: Add explicit tracking. need [pkgDataFile context] -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 let pkgConfig = oldPath -/- "inplace-pkg-config" oldBuildPath = oldPath -/- "build" fixPkgConf = unlines - . map (replace oldBuildPath (buildPath context) - . replace (replaceSeparators '\\' $ oldBuildPath) - (buildPath context) ) + . map + ( replace oldBuildPath path + . replace (replaceSeparators '\\' oldBuildPath) path ) . lines fixFile pkgConfig fixPkgConf - buildWithResources rs $ - Target context (GhcPkg stage) [pkgConfig] [conf] + buildWithResources rs $ Target context (GhcPkg stage) [pkgConfig] [conf] when (package == rts && stage == Stage1) $ do packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do need [rtsConf] - buildWithResources rs $ - Target context (GhcPkg stage) [rtsConf] [conf] + buildWithResources rs $ Target context (GhcPkg stage) [rtsConf] [conf] rtsConf %> \_ -> do - need [ pkgDataFile rtsContext, rtsConfIn ] + need [pkgDataFile rtsContext, rtsConfIn] build $ Target context HsCpp [rtsConfIn] [rtsConf] let fixRtsConf = unlines From git at git.haskell.org Fri Oct 27 00:13:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move `renderBox` to `Base` (26e64ed) Message-ID: <20171027001343.E23D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/26e64ed57d5b0d85e740baedd529e845002103e9/ghc >--------------------------------------------------------------- commit 26e64ed57d5b0d85e740baedd529e845002103e9 Author: Ben Gamari Date: Sun Dec 20 21:41:36 2015 +0100 Move `renderBox` to `Base` >--------------------------------------------------------------- 26e64ed57d5b0d85e740baedd529e845002103e9 src/Base.hs | 18 ++++++++++++++++++ src/Rules/Actions.hs | 20 ++------------------ 2 files changed, 20 insertions(+), 18 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7edae37..fb3b5e1 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -21,6 +21,7 @@ module Base ( -- * Output putColoured, putOracle, putBuild, putSuccess, putError, + renderBox, module System.Console.ANSI, -- * Miscellaneous utilities @@ -130,6 +131,23 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg +-- | Render the given set of lines in a ASCII box +renderBox :: [String] -> String +renderBox ls = + unlines $ [begin] ++ map (bar++) ls ++ [end] + where + (begin,bar,end) + | useUnicode = ( "╭──────────" + , "│ " + , "╰──────────" + ) + | otherwise = ( "/----------" + , "| " + , "\\----------" + ) + -- FIXME: See Shake #364. + useUnicode = False + -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 775524a..5a3d113 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -7,22 +7,6 @@ import Settings.Args import Settings.Builders.Ar import qualified Target -insideBox :: [String] -> String -insideBox ls = - unlines $ [begin] ++ map (bar++) ls ++ [end] - where - (begin,bar,end) - | useUnicode = ( "╭──────────" - , "│ " - , "╰──────────" - ) - | otherwise = ( "/----------" - , "| " - , "\\----------" - ) - -- FIXME: See Shake #364. - useUnicode = False - -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last -- built (that is, track changes in the build system). @@ -38,8 +22,8 @@ buildWithResources rs target = do checkArgsHash target withResources rs $ do unless verbose $ do - putBuild $ insideBox $ [ "Running " ++ show builder ++ " with arguments:" ] - ++ map (" "++) (interestingInfo builder argList) + putBuild $ renderBox $ [ "Running " ++ show builder ++ " with arguments:" ] + ++ map (" "++) (interestingInfo builder argList) quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList From git at git.haskell.org Fri Oct 27 00:13:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on clean target (497f750) Message-ID: <20171027001346.17ACA3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/497f75095c1265b19025077a2fec0633604d1abf/ghc >--------------------------------------------------------------- commit 497f75095c1265b19025077a2fec0633604d1abf Author: Andrey Mokhov Date: Fri Jan 22 13:04:34 2016 +0000 Add a note on clean target [skip ci] >--------------------------------------------------------------- 497f75095c1265b19025077a2fec0633604d1abf README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index b80b621..602148b 100644 --- a/README.md +++ b/README.md @@ -71,7 +71,8 @@ experiment following the Haddock comments. To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. -This is a temporary solution; we are working on proper reset functionality ([#131][reset-issue]). +To remove all build artefacts, run the build script with `clean` target. Note, we are +working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. Current limitations ------------------- @@ -114,7 +115,6 @@ helped me endure and enjoy the project. [build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs -[reset-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/131 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 [profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 From git at git.haskell.org Fri Oct 27 00:13:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't add redundant path separator in -/- (d1780e4) Message-ID: <20171027001346.12E4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1780e499e3e5a3f4adb21f6be366b26ae3ec6a4/ghc >--------------------------------------------------------------- commit d1780e499e3e5a3f4adb21f6be366b26ae3ec6a4 Author: Andrey Mokhov Date: Mon May 16 01:31:02 2016 +0100 Don't add redundant path separator in -/- >--------------------------------------------------------------- d1780e499e3e5a3f4adb21f6be366b26ae3ec6a4 src/Base.hs | 5 ++++- src/Oracles/WindowsPath.hs | 5 +++-- 2 files changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index bd80f47..339a61d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -89,7 +89,10 @@ unifyPath = toStandard . normaliseEx -- | Combine paths with a forward slash regardless of platform. (-/-) :: FilePath -> FilePath -> FilePath -a -/- b = a ++ '/' : b +"" -/- b = b +a -/- b + | last a == '/' = a ++ b + | otherwise = a ++ '/' : b infixr 6 -/- diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index 2a3336d..3cbf73b 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -3,7 +3,8 @@ module Oracles.WindowsPath ( fixAbsolutePathOnWindows, topDirectory, windowsPathOracle ) where -import Data.Char (isSpace) +import Data.Char + import Base import Oracles.Config.Setting @@ -25,7 +26,7 @@ fixAbsolutePathOnWindows path = do then do let (dir, file) = splitFileName path winDir <- askOracle $ WindowsPath dir - return $ winDir ++ file + return $ winDir -/- file else return path From git at git.haskell.org Fri Oct 27 00:13:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an explicit dependency on pkgDataFile to make sure GhcCabal hscolour is run after GhcCabal configure. (0c9d7d8) Message-ID: <20171027001347.8457D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c9d7d887552956816e5acee725dbc79f591b18d/ghc >--------------------------------------------------------------- commit 0c9d7d887552956816e5acee725dbc79f591b18d Author: Andrey Mokhov Date: Sun Dec 20 20:58:10 2015 +0000 Add an explicit dependency on pkgDataFile to make sure GhcCabal hscolour is run after GhcCabal configure. >--------------------------------------------------------------- 0c9d7d887552956816e5acee725dbc79f591b18d src/Rules/Documentation.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 495a16c..463552f 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -10,9 +10,9 @@ import Settings -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. buildPackageDocumentation :: Resources -> PartialTarget -> Rules () -buildPackageDocumentation _ target @ (PartialTarget stage package) = - let cabalFile = pkgCabalFile package - haddockFile = pkgHaddockFile package +buildPackageDocumentation _ target @ (PartialTarget stage pkg) = + let cabalFile = pkgCabalFile pkg + haddockFile = pkgHaddockFile pkg in when (stage == Stage1) $ do haddockFile %> \file -> do srcs <- interpretPartial target getPackageSources @@ -23,7 +23,7 @@ buildPackageDocumentation _ target @ (PartialTarget stage package) = -- HsColour sources whenM (specified HsColour) $ do - need [cabalFile] + need [cabalFile, pkgDataFile stage pkg ] build $ fullTarget target GhcCabalHsColour [cabalFile] [] -- Build Haddock documentation From git at git.haskell.org Fri Oct 27 00:13:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use removeFiles instead of removeFilesAfter. (a8ea524) Message-ID: <20171027001350.282083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8ea524634d870e75c3dc13bc96d174b064849ae/ghc >--------------------------------------------------------------- commit a8ea524634d870e75c3dc13bc96d174b064849ae Author: Andrey Mokhov Date: Fri Jan 22 13:08:36 2016 +0000 Use removeFiles instead of removeFilesAfter. See #131. >--------------------------------------------------------------- a8ea524634d870e75c3dc13bc96d174b064849ae src/Rules/Clean.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 6ab5309..2b4094a 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -12,13 +12,13 @@ cleanRules :: Rules () cleanRules = do "clean" ~> do putBuild $ "| Remove files in " ++ buildRootPath ++ "..." - removeFilesAfter buildRootPath ["//*"] + liftIO $ removeFiles buildRootPath ["//*"] putBuild $ "| Remove files in " ++ programInplacePath ++ "..." - removeFilesAfter programInplacePath ["//*"] + liftIO $ removeFiles programInplacePath ["//*"] putBuild $ "| Remove files in inplace/lib..." - removeFilesAfter "inplace/lib" ["//*"] + liftIO $ removeFiles "inplace/lib" ["//*"] putBuild $ "| Remove files in " ++ derivedConstantsPath ++ "..." - removeFilesAfter derivedConstantsPath ["//*"] + liftIO $ removeFiles derivedConstantsPath ["//*"] forM_ includesDependencies $ \file -> do putBuild $ "| Remove " ++ file removeFileIfExists file From git at git.haskell.org Fri Oct 27 00:13:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up imports (improve consistency) (e982476) Message-ID: <20171027001350.2EF5B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e982476cf7b80add369365d78718e9954a3944d0/ghc >--------------------------------------------------------------- commit e982476cf7b80add369365d78718e9954a3944d0 Author: Andrey Mokhov Date: Mon May 16 01:33:39 2016 +0100 Clean up imports (improve consistency) >--------------------------------------------------------------- e982476cf7b80add369365d78718e9954a3944d0 src/Builder.hs | 2 +- src/CmdLineFlag.hs | 14 ++++++-------- src/Environment.hs | 3 ++- src/Expression.hs | 2 +- src/Oracles/Config.hs | 3 ++- src/Package.hs | 5 +++-- src/Rules/Cabal.hs | 3 ++- src/Rules/Configure.hs | 4 ++-- src/Rules/Generate.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Perl.hs | 2 +- src/Rules/Selftest.hs | 4 ++-- src/Rules/Test.hs | 2 +- src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/Ar.hs | 4 ++-- src/Settings/Builders/Cc.hs | 6 +++--- src/Settings/Builders/Common.hs | 2 +- src/Settings/Builders/Configure.hs | 2 +- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 +++----- src/Settings/Builders/GhcCabal.hs | 9 +++------ src/Settings/Builders/Haddock.hs | 1 - src/Settings/Builders/Happy.hs | 2 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- src/Settings/Builders/Make.hs | 2 +- src/Settings/Builders/Tar.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Packages/Base.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 6 +++--- src/Settings/Packages/Directory.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 4 ++-- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/GhcPrim.hs | 4 ++-- src/Settings/Packages/Haddock.hs | 4 ++-- src/Settings/Packages/Hp2ps.hs | 4 ++-- src/Settings/Packages/IntegerGmp.hs | 6 +++--- src/Settings/Packages/IservBin.hs | 7 +++---- src/Settings/Packages/Rts.hs | 4 ++-- src/Settings/Packages/RunGhc.hs | 4 ++-- src/Settings/Packages/Touchy.hs | 4 ++-- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/Ways.hs | 5 +++-- src/Way.hs | 3 ++- 45 files changed, 84 insertions(+), 87 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 e982476cf7b80add369365d78718e9954a3944d0 From git at git.haskell.org Fri Oct 27 00:13:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #13 from bgamari/master (e801ee0) Message-ID: <20171027001351.2BCBB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e801ee01698baa20d7a56e57768104f74ac35ffa/ghc >--------------------------------------------------------------- commit e801ee01698baa20d7a56e57768104f74ac35ffa Merge: 0c9d7d8 c7a0c19 Author: Andrey Mokhov Date: Sun Dec 20 21:04:59 2015 +0000 Merge pull request #13 from bgamari/master Consolidate box pretty-printing >--------------------------------------------------------------- e801ee01698baa20d7a56e57768104f74ac35ffa src/Base.hs | 64 +++++++++++++++++++++++++++++++++++++--------------- src/Rules/Actions.hs | 20 ++-------------- src/Rules/Library.hs | 11 +++++---- src/Rules/Program.hs | 11 +++++---- 4 files changed, 60 insertions(+), 46 deletions(-) From git at git.haskell.org Fri Oct 27 00:14:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build haddock and ghcTags in stage1 temporarily until stage2 is fixed. (c720083) Message-ID: <20171027001417.2C67B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c720083bc93c9b22719f2b94a3861598c594572c/ghc >--------------------------------------------------------------- commit c720083bc93c9b22719f2b94a3861598c594572c Author: Andrey Mokhov Date: Mon Dec 21 12:00:32 2015 +0000 Build haddock and ghcTags in stage1 temporarily until stage2 is fixed. >--------------------------------------------------------------- c720083bc93c9b22719f2b94a3861598c594572c src/GHC.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/GHC.hs b/src/GHC.hs index f47242a..f528052 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -106,11 +106,17 @@ defaultTargetDirectory stage pkg | otherwise = "dist-install" -- TODO: simplify +-- TODO: haddock and ghtTags should be built in stage2 only -- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == haddock = case stage of + Stage1 -> Just . inplaceProgram $ pkgName pkg + Stage2 -> Just . inplaceProgram $ pkgName pkg + _ -> Nothing + | pkg == ghcTags = case stage of + Stage1 -> Just . inplaceProgram $ pkgName pkg Stage2 -> Just . inplaceProgram $ pkgName pkg _ -> Nothing | isProgram pkg = case stage of From git at git.haskell.org Fri Oct 27 00:14:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on build.stack.sh. (cf5d338) Message-ID: <20171027001416.584993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf5d3387e960ae9ebdec5c08113e84195618dc3f/ghc >--------------------------------------------------------------- commit cf5d3387e960ae9ebdec5c08113e84195618dc3f Author: Andrey Mokhov Date: Sat Jan 23 00:42:04 2016 +0000 Add a note on build.stack.sh. [skip ci] >--------------------------------------------------------------- cf5d3387e960ae9ebdec5c08113e84195618dc3f README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 602148b..b8fd40f 100644 --- a/README.md +++ b/README.md @@ -39,7 +39,7 @@ On Windows, use `build.bat` instead and pass an extra flag to configure (also se ```bash shake-build/build.bat --configure=--enable-tarballs-autodownload ``` -If you are interested in building in a Cabal sandbox, have a look at `shake-build/build.cabal.sh`. +If you are interested in building in a Cabal sandbox or using Stack, have a look at `shake-build/build.cabal.sh` and `shake-build/build.stack.sh` scripts. Using the build system ---------------------- From git at git.haskell.org Fri Oct 27 00:14:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghc-boot-th package (e91daa3) Message-ID: <20171027001417.1F3F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e91daa3eb50b46441619d5ba43852c8dc1f9a164/ghc >--------------------------------------------------------------- commit e91daa3eb50b46441619d5ba43852c8dc1f9a164 Author: Andrey Mokhov Date: Mon May 16 23:10:48 2016 +0100 Add ghc-boot-th package >--------------------------------------------------------------- e91daa3eb50b46441619d5ba43852c8dc1f9a164 src/GHC.hs | 17 +++++++++-------- src/Settings/Packages.hs | 4 ++-- 2 files changed, 11 insertions(+), 10 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 02c76f9..303beca 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -2,11 +2,11 @@ module GHC ( array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, - ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, - primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unlit, unix, win32, xhtml, + genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim, + ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, + integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, + pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, + time, touchy, transformers, unlit, unix, win32, xhtml, defaultKnownPackages, programPath, contextDirectory, rtsContext ) where @@ -25,7 +25,7 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes , deepseq, deriveConstants, directory, dllSplit, filepath, genapply - , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim + , genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time @@ -34,8 +34,8 @@ defaultKnownPackages = -- | Package definitions, see 'Package'. array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, - haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, + genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim, + ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml :: Package @@ -57,6 +57,7 @@ genapply = utility "genapply" genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" `setType` Program ghcBoot = library "ghc-boot" +ghcBootTh = library "ghc-boot-th" ghcCabal = utility "ghc-cabal" ghci = library "ghci" ghcPkg = utility "ghc-pkg" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 6888d0a..40d9ebf 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -20,8 +20,8 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg - , hsc2hs, hoopl, hpc, templateHaskell, transformers ] + [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcBootTh, ghcCabal + , ghcPkg, hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode , hp2ps, unlit ] From git at git.haskell.org Fri Oct 27 00:14:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move GMP build to Stage1. (3f74e8b) Message-ID: <20171027001419.F3BE23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3f74e8bf2c170740f46279b98659d57b47721afa/ghc >--------------------------------------------------------------- commit 3f74e8bf2c170740f46279b98659d57b47721afa Author: Andrey Mokhov Date: Sat Jan 23 15:36:20 2016 +0000 Move GMP build to Stage1. Should make AppVeyor CI fit in 1 hr. >--------------------------------------------------------------- 3f74e8bf2c170740f46279b98659d57b47721afa src/Rules/Generate.hs | 13 +++++++------ src/Rules/Gmp.hs | 15 ++++----------- src/Settings/Builders/Ghc.hs | 5 ++++- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Paths.hs | 2 +- 5 files changed, 17 insertions(+), 20 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 73b160a..f329228 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -43,11 +43,12 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -defaultDependencies :: [FilePath] -defaultDependencies = concat +defaultDependencies :: Stage -> [FilePath] +defaultDependencies stage = concat [ includesDependencies - , libffiDependencies - , gmpDependencies ] + , libffiDependencies ] + ++ + [ gmpLibraryH | stage > Stage0 ] ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> @@ -67,7 +68,7 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = [ platformH stage ] - ++ defaultDependencies ++ derivedConstantsDependencies + ++ defaultDependencies stage ++ derivedConstantsDependencies ++ fmap ((targetPath stage compiler -/- "build") -/-) [ "primop-vector-uniques.hs-incl" , "primop-data-decl.hs-incl" @@ -91,7 +92,7 @@ generatedDependencies stage pkg | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = libffiDependencies ++ includesDependencies ++ derivedConstantsDependencies - | stage == Stage0 = defaultDependencies + | stage == Stage0 = defaultDependencies Stage0 | otherwise = [] -- The following generators and corresponding source extensions are supported: diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index b6bfdf0..b384b68 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,6 +1,4 @@ -module Rules.Gmp ( - gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH, gmpDependencies - ) where +module Rules.Gmp (gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH) where import qualified System.Directory as IO @@ -17,7 +15,7 @@ gmpBase :: FilePath gmpBase = "libraries/integer-gmp/gmp" gmpTarget :: PartialTarget -gmpTarget = PartialTarget Stage0 integerGmp +gmpTarget = PartialTarget Stage1 integerGmp gmpObjects :: FilePath gmpObjects = gmpBuildPath -/- "objs" @@ -34,9 +32,6 @@ gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" gmpLibraryFakeH :: FilePath gmpLibraryFakeH = gmpBase -/- "ghc-gmp.h" -gmpDependencies :: [FilePath] -gmpDependencies = [gmpLibraryH] - gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] @@ -77,11 +72,11 @@ gmpRules = do liftIO $ removeFiles gmpBuildPath ["//*"] - envs <- configureEnvironment -- TODO: without the optimisation below we configure integerGmp package -- twice -- think how this can be optimised (shall we solve #18 first?) -- TODO: this is a hacky optimisation: we do not rerun configure of -- integerGmp package if we detect the results of the previous run + envs <- configureEnvironment unlessM (liftIO . IO.doesFileExist $ gmpBase -/- "config.mk") $ do args <- configureIntGmpArguments runConfigure (pkgPath integerGmp) envs args @@ -148,6 +143,4 @@ gmpRules = do runBuilder Ranlib [gmpLibrary] - putSuccess "| Successfully built custom library 'integer-gmp'" - - -- gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] + putSuccess "| Successfully built custom library 'gmp'" diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 3537aed..c79fc50 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -19,12 +19,15 @@ import Settings.Builders.Common (cIncludeArgs) ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput + stage <- getStage way <- getWay let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs - gmpLibs <- lift $ readFileLines gmpLibNameCache + gmpLibs <- if stage > Stage0 && buildProg + then lift $ readFileLines gmpLibNameCache -- TODO: use oracles + else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs , arg "-H32m" diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 9ad160f..0640e52 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -16,7 +16,7 @@ integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" gmpIncludeDir <- getSetting GmpIncludeDir - gmpLibDir <- getSetting GmpLibDir + gmpLibDir <- getSetting GmpLibDir mconcat [ builder GhcCabal ? mconcat [ (null gmpIncludeDir && null gmpLibDir) ? diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 3e9fec9..ed217a8 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -39,7 +39,7 @@ pkgGhciLibraryFile stage pkg componentId = -- This is the build directory for in-tree GMP library gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage0/gmp" +gmpBuildPath = buildRootPath -/- "stage1/gmp" -- GMP library names extracted from integer-gmp.buildinfo gmpLibNameCache :: FilePath From git at git.haskell.org Fri Oct 27 00:14:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dreary package signagures (34545e3) Message-ID: <20171027001420.CF06E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34545e3d0d54223512f0c05909a23bdb61ad3755/ghc >--------------------------------------------------------------- commit 34545e3d0d54223512f0c05909a23bdb61ad3755 Author: Andrey Mokhov Date: Mon May 16 23:16:59 2016 +0100 Drop dreary package signagures >--------------------------------------------------------------- 34545e3d0d54223512f0c05909a23bdb61ad3755 src/GHC.hs | 12 +++--------- 1 file changed, 3 insertions(+), 9 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 303beca..d75a046 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,4 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, @@ -18,7 +19,7 @@ import Stage -- | These are all GHC packages we know about. Build rules will be generated for -- all of them. However, not all of these packages will be built. For example, --- package /win32/ is built only on Windows. +-- package 'win32' is built only on Windows. -- "Packages" defines default conditions for building each package, which can -- be overridden in "Settings.User". defaultKnownPackages :: [Package] @@ -32,14 +33,6 @@ defaultKnownPackages = , touchy, transformers, unlit, unix, win32, xhtml ] -- | Package definitions, see 'Package'. -array, base, binary, bytestring, cabal, compiler, containers, compareSizes, - deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim, - ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, - primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unlit, unix, win32, xhtml :: Package - array = library "array" base = library "base" binary = library "binary" @@ -126,6 +119,7 @@ programPath context at Context {..} installProgram name = pkgPath package -/- contextDirectory context -/- "build/tmp" -/- name <.> exe +-- TODO: Move this elsewhere. rtsContext :: Context rtsContext = vanillaContext Stage1 rts From git at git.haskell.org Fri Oct 27 00:14:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Windows instructions (f2d3eb5) Message-ID: <20171027001420.D6E253A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f2d3eb55eb6b2c1aaf6ccc995c03de0c3a330917/ghc >--------------------------------------------------------------- commit f2d3eb55eb6b2c1aaf6ccc995c03de0c3a330917 Author: Andrey Mokhov Date: Mon Dec 21 12:11:45 2015 +0000 Add Windows instructions >--------------------------------------------------------------- f2d3eb55eb6b2c1aaf6ccc995c03de0c3a330917 README.md | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/README.md b/README.md index 63673e3..8c81c13 100644 --- a/README.md +++ b/README.md @@ -19,3 +19,15 @@ $ ./configure $ make inplace/bin/ghc-cabal # This needs to be fixed $ shake-build/build.sh ``` + +On Windows, +``` +$ git clone --recursive git://git.haskell.org/ghc.git +$ cd ghc +$ git clone git://github.com/snowleopard/shaking-up-ghc shake-build +$ ./boot +$ ./configure --enable-tarballs-autodownload +$ make inplace/bin/ghc-cabal # This needs to be fixed +$ shake-build/build.bat +``` +Also see the Building GHC on Windows guide: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows. From git at git.haskell.org Fri Oct 27 00:14:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move libffi build to Stage1. (48d0ee0) Message-ID: <20171027001423.724A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/48d0ee0e397abc8fb447db6e3c858b4d5be2f863/ghc >--------------------------------------------------------------- commit 48d0ee0e397abc8fb447db6e3c858b4d5be2f863 Author: Andrey Mokhov Date: Sat Jan 23 17:04:11 2016 +0000 Move libffi build to Stage1. Should make AppVeyor CI fit in 1 hr. >--------------------------------------------------------------- 48d0ee0e397abc8fb447db6e3c858b4d5be2f863 src/Rules/Generate.hs | 15 ++++++--------- src/Rules/Libffi.hs | 5 ++--- 2 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index f329228..d98527c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -43,13 +43,6 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -defaultDependencies :: Stage -> [FilePath] -defaultDependencies stage = concat - [ includesDependencies - , libffiDependencies ] - ++ - [ gmpLibraryH | stage > Stage0 ] - ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> [ "GHC/PrimopWrappers.hs" @@ -68,7 +61,10 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = [ platformH stage ] - ++ defaultDependencies stage ++ derivedConstantsDependencies + ++ includesDependencies + ++ [ gmpLibraryH | stage > Stage0 ] + ++ filter (const $ stage > Stage0) libffiDependencies + ++ derivedConstantsDependencies ++ fmap ((targetPath stage compiler -/- "build") -/-) [ "primop-vector-uniques.hs-incl" , "primop-data-decl.hs-incl" @@ -86,13 +82,14 @@ compilerDependencies stage = , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] +-- TODO: Turn this into a FilePaths expression generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = libffiDependencies ++ includesDependencies ++ derivedConstantsDependencies - | stage == Stage0 = defaultDependencies Stage0 + | stage == Stage0 = includesDependencies | otherwise = [] -- The following generators and corresponding source extensions are supported: diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0f4e05a..d2742eb 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -19,10 +19,10 @@ libffiDependencies :: [FilePath] libffiDependencies = (rtsBuildPath -/-) <$> [ "ffi.h", "ffitarget.h" ] libffiTarget :: PartialTarget -libffiTarget = PartialTarget Stage0 libffi +libffiTarget = PartialTarget Stage1 libffi libffiBuild :: FilePath -libffiBuild = buildRootPath -/- "stage0/libffi" +libffiBuild = buildRootPath -/- "stage1/libffi" libffiLibrary :: FilePath libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" @@ -33,7 +33,6 @@ fixLibffiMakefile = . replace "@toolexeclibdir@" "$(libdir)" . replace "@INSTALL@" "$(subst ../install-sh,C:/msys/home/chEEtah/ghc/install-sh, at INSTALL@)" - -- TODO: remove code duplication (see Settings/Builders/GhcCabal.hs) configureEnvironment :: Action [CmdOption] configureEnvironment = do From git at git.haskell.org Fri Oct 27 00:14:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build progress info colours customisable, drop putError and putOracle. (fa77d93) Message-ID: <20171027001424.89A043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fa77d934a2f15509e33c3ee1aafb88cb20abc1d1/ghc >--------------------------------------------------------------- commit fa77d934a2f15509e33c3ee1aafb88cb20abc1d1 Author: Andrey Mokhov Date: Tue May 17 23:36:41 2016 +0100 Make build progress info colours customisable, drop putError and putOracle. See #244. >--------------------------------------------------------------- fa77d934a2f15509e33c3ee1aafb88cb20abc1d1 src/Base.hs | 64 +++++++++++++++------------------------------ src/Builder.hs | 4 +-- src/Expression.hs | 2 +- src/Oracles/Config.hs | 4 +-- src/Oracles/Config/Flag.hs | 4 +-- src/Oracles/Dependencies.hs | 6 ++--- src/Oracles/LookupInPath.hs | 4 +-- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/PackageDb.hs | 3 ++- src/Oracles/PackageDeps.hs | 2 +- src/Oracles/WindowsPath.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Configure.hs | 5 ++-- src/Rules/Generate.hs | 6 ++--- src/Rules/Gmp.hs | 4 +-- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Rules/Selftest.hs | 1 + src/Settings/User.hs | 20 ++++++++++---- 21 files changed, 67 insertions(+), 76 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 fa77d934a2f15509e33c3ee1aafb88cb20abc1d1 From git at git.haskell.org Fri Oct 27 00:14:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a section on how to contribute (552f617) Message-ID: <20171027001424.911A43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/552f6170baba7c06c500ed913d36a89dfec12262/ghc >--------------------------------------------------------------- commit 552f6170baba7c06c500ed913d36a89dfec12262 Author: Andrey Mokhov Date: Mon Dec 21 12:25:40 2015 +0000 Add a section on how to contribute >--------------------------------------------------------------- 552f6170baba7c06c500ed913d36a89dfec12262 README.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README.md b/README.md index 8c81c13..5d87bc4 100644 --- a/README.md +++ b/README.md @@ -31,3 +31,7 @@ $ make inplace/bin/ghc-cabal # This needs to be fixed $ shake-build/build.bat ``` Also see the Building GHC on Windows guide: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows. + +How to contribute +----------------- +The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note the codebase is very unstable at present and we expect a lot of further refactoring. Before attempting to fix any issue do make sure no one else is already working on it. The documentation is currently non-existent, but we will start addressing this once the codebase stabilises. From git at git.haskell.org Fri Oct 27 00:14:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Force AppVeyor CI to succeed and store the cache. (e01bf2f) Message-ID: <20171027001427.02FC83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e01bf2f9e665a83e2cd5eae7f5a20df755ae67a9/ghc >--------------------------------------------------------------- commit e01bf2f9e665a83e2cd5eae7f5a20df755ae67a9 Author: Andrey Mokhov Date: Sat Jan 23 20:55:07 2016 +0000 Force AppVeyor CI to succeed and store the cache. [skip ci] >--------------------------------------------------------------- e01bf2f9e665a83e2cd5eae7f5a20df755ae67a9 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index d8854cc..dce914b 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -39,4 +39,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-cabal.exe From git at git.haskell.org Fri Oct 27 00:14:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move versionToInt to Settings/Builders/Haddock (acc2c7e) Message-ID: <20171027001428.025393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acc2c7eef93e5372ce355de6c49cc24f9c507dab/ghc >--------------------------------------------------------------- commit acc2c7eef93e5372ce355de6c49cc24f9c507dab Author: Andrey Mokhov Date: Tue May 17 23:41:55 2016 +0100 Move versionToInt to Settings/Builders/Haddock >--------------------------------------------------------------- acc2c7eef93e5372ce355de6c49cc24f9c507dab src/Base.hs | 8 +------- src/Settings/Builders/Haddock.hs | 6 ++++++ 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 328eb98..8f02865 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -19,7 +19,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, - unifyPath, (-/-), versionToInt, matchVersionedFilePath, putColoured + unifyPath, (-/-), matchVersionedFilePath, putColoured ) where import Control.Applicative @@ -74,12 +74,6 @@ replaceWhen p to = map (\from -> if p from then to else from) quote :: String -> String quote s = "\"" ++ s ++ "\"" --- | Given a version string such as "2.16.2" produce an integer equivalent. -versionToInt :: String -> Int -versionToInt s = major * 1000 + minor * 10 + patch - where - [major, minor, patch] = map read . words $ replaceEq '.' ' ' s - -- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 37964b4..4c0b6f7 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -8,6 +8,12 @@ import Predicate import Settings import Settings.Builders.Ghc +-- | Given a version string such as "2.16.2" produce an integer equivalent. +versionToInt :: String -> Int +versionToInt s = major * 1000 + minor * 10 + patch + where + [major, minor, patch] = map read . words $ replaceEq '.' ' ' s + haddockBuilderArgs :: Args haddockBuilderArgs = builder Haddock ? do output <- getOutput From git at git.haskell.org Fri Oct 27 00:14:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Show instances. (31d8890) Message-ID: <20171027001428.09D443A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31d88906c1b734a5d2d0dd39b79415547a6affea/ghc >--------------------------------------------------------------- commit 31d88906c1b734a5d2d0dd39b79415547a6affea Author: Andrey Mokhov Date: Tue Dec 22 04:59:02 2015 +0000 Fix Show instances. >--------------------------------------------------------------- 31d88906c1b734a5d2d0dd39b79415547a6affea src/Oracles/Config/Setting.hs | 8 ++++---- src/Stage.hs | 6 ++---- src/Target.hs | 2 +- src/Way.hs | 1 + 4 files changed, 8 insertions(+), 9 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index fa62f97..8f0b1df 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -85,10 +85,10 @@ setting key = askConfig $ case key of settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of - ConfCcArgs stage -> "conf-cc-args-stage" ++ show stage - ConfCppArgs stage -> "conf-cpp-args-stage" ++ show stage - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show stage - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show stage + ConfCcArgs stage -> "conf-cc-args-stage" ++ show (fromEnum stage) + ConfCppArgs stage -> "conf-cpp-args-stage" ++ show (fromEnum stage) + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show (fromEnum stage) + ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show (fromEnum stage) GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" HsCppArgs -> "hs-cpp-args" diff --git a/src/Stage.hs b/src/Stage.hs index 3aca206..d474557 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -5,10 +5,8 @@ import Base import GHC.Generics (Generic) -- TODO: explain stages -data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum, Generic) - -instance Show Stage where - show = show . fromEnum +data Stage = Stage0 | Stage1 | Stage2 | Stage3 + deriving (Show, Eq, Ord, Enum, Generic) -- Instances for storing in the Shake database instance Binary Stage diff --git a/src/Target.hs b/src/Target.hs index c70790d..2060d04 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -37,7 +37,7 @@ instance Monoid a => Monoid (ReaderT Target Action a) where -- PartialTarget is a partially constructed Target with fields Stage and -- Package only. PartialTarget's are used for generating build rules. -data PartialTarget = PartialTarget Stage Package +data PartialTarget = PartialTarget Stage Package deriving Show -- Convert PartialTarget to Target assuming that unknown fields won't be used. fromPartial :: PartialTarget -> Target diff --git a/src/Way.hs b/src/Way.hs index 095bd52..28d1365 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -28,6 +28,7 @@ data WayUnit = Threaded | GranSim deriving (Eq, Enum) +-- TODO: get rid of non-derived Show instances instance Show WayUnit where show unit = case unit of Threaded -> "thr" From git at git.haskell.org Fri Oct 27 00:14:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Environment module for setting up environment variables. (f6cd23d) Message-ID: <20171027001430.759C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f6cd23dc4b92bcedc230754f06b4c3f11438f6ae/ghc >--------------------------------------------------------------- commit f6cd23dc4b92bcedc230754f06b4c3f11438f6ae Author: Andrey Mokhov Date: Sun Jan 24 01:35:03 2016 +0000 Add Environment module for setting up environment variables. Fix #191. >--------------------------------------------------------------- f6cd23dc4b92bcedc230754f06b4c3f11438f6ae shaking-up-ghc.cabal | 1 + src/Environment.hs | 22 ++++++++++++++++++++++ src/Main.hs | 14 ++++++++------ src/Rules/Config.hs | 8 +------- 4 files changed, 32 insertions(+), 13 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index bd21d28..cdd512a 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -20,6 +20,7 @@ executable ghc-shake other-modules: Base , Builder , CmdLineFlag + , Environment , Expression , GHC , Oracles diff --git a/src/Environment.hs b/src/Environment.hs new file mode 100644 index 0000000..fd207ed --- /dev/null +++ b/src/Environment.hs @@ -0,0 +1,22 @@ +module Environment (setupEnvironment) where + +import Base +import System.Environment + +-- | The build system invokes many external builders whose behaviour is +-- influenced by the environment variables. We need to modify some of them +-- for better robustness of the build system. +setupEnvironment :: IO () +setupEnvironment = do + -- ghc-cabal refuses to work when GHC_PACKAGE_PATH is set (e.g. by Stack) + unsetEnv "GHC_PACKAGE_PATH" + + -- On Windows, some path variables start a prefix like "C:\\" which may + -- lead to failures of scripts such as autoreconf. One particular variable + -- which causes issues is ACLOCAL_PATH. At the moment we simply reset it + -- if it contains a problematic Windows path. + -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. + aclocal <- lookupEnv "ACLOCAL_PATH" + case aclocal of + Nothing -> return () + Just s -> when (":\\" `isPrefixOf` drop 1 s) $ unsetEnv "ACLOCAL_PATH" diff --git a/src/Main.hs b/src/Main.hs index 7321f88..69f739b 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,7 +3,8 @@ module Main (main) where import Development.Shake import qualified Base -import CmdLineFlag +import qualified CmdLineFlag +import qualified Environment import qualified Rules import qualified Rules.Cabal import qualified Rules.Clean @@ -16,8 +17,9 @@ import qualified Rules.Perl import qualified Test main :: IO () -main = shakeArgsWith options flags $ \cmdLineFlags targets -> do - putCmdLineFlags cmdLineFlags +main = shakeArgsWith options CmdLineFlag.flags $ \cmdLineFlags targets -> do + CmdLineFlag.putCmdLineFlags cmdLineFlags + Environment.setupEnvironment return . Just $ if null targets then rules else want targets >> withoutActions rules @@ -27,13 +29,13 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do [ Rules.Cabal.cabalRules , Rules.Clean.cleanRules , Rules.Config.configRules - , Rules.Generate.copyRules , Rules.Generate.generateRules - , Rules.Perl.perlScriptRules - , Rules.generateTargets + , Rules.Generate.copyRules , Rules.Gmp.gmpRules , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules + , Rules.Perl.perlScriptRules + , Rules.generateTargets , Rules.packageRules , Test.testRules ] options = shakeOptions diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 77ac1ac..1297825 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -21,10 +21,4 @@ configRules = do -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. "configure" %> \_ -> do putBuild "| Running boot..." - aclocal <- getEnv "ACLOCAL_PATH" - let env = case aclocal of - Nothing -> [] - Just s -> if ":\\" `isPrefixOf` (drop 1 s) - then [AddEnv "ACLOCAL_PATH" ""] - else [] - quietly $ cmd (EchoStdout False) env "perl boot" + quietly $ cmd (EchoStdout False) "perl boot" From git at git.haskell.org Fri Oct 27 00:14:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't celebrate duplication (a2b39be) Message-ID: <20171027001431.DBB983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2b39be6d48c9844f7d4519406c72857d38dd233/ghc >--------------------------------------------------------------- commit a2b39be6d48c9844f7d4519406c72857d38dd233 Author: Andrey Mokhov Date: Tue May 17 23:45:39 2016 +0100 Don't celebrate duplication >--------------------------------------------------------------- a2b39be6d48c9844f7d4519406c72857d38dd233 src/Rules/Generate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index daebe5d..d19ceac 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -134,7 +134,7 @@ generatePackageCode context@(Context stage pkg _) = newFile = oldPath ++ (drop (length path) file) createDirectory $ takeDirectory newFile liftIO $ IO.copyFile file newFile - putSuccess $ "| Duplicate file " ++ file ++ " -> " ++ newFile + putBuild $ "| Duplicate file " ++ file ++ " -> " ++ newFile when (pkg == rts) $ path -/- "AutoApply.cmm" %> \file -> do build $ Target context GenApply [] [file] From git at git.haskell.org Fri Oct 27 00:14:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for turnWarningsIntoErrors in Settings/User.hs. (3d90d06) Message-ID: <20171027001431.EA8583A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d90d06aa59af43da7edb79dbd930d6fa34c5b9f/ghc >--------------------------------------------------------------- commit 3d90d06aa59af43da7edb79dbd930d6fa34c5b9f Author: Andrey Mokhov Date: Tue Dec 22 05:00:31 2015 +0000 Add support for turnWarningsIntoErrors in Settings/User.hs. >--------------------------------------------------------------- 3d90d06aa59af43da7edb79dbd930d6fa34c5b9f src/Settings/User.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 4c7a5f4..e16fb27 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands + verboseCommands, turnWarningsIntoErrors ) where import Expression @@ -88,3 +88,7 @@ buildSystemConfigFile = False -- only, e.g.: verboseCommands = package ghcPrim verboseCommands :: Predicate verboseCommands = return False + +-- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. +turnWarningsIntoErrors :: Predicate +turnWarningsIntoErrors = return False From git at git.haskell.org Fri Oct 27 00:14:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, build stage 1 GHC on AppVeyor. (73d8de1) Message-ID: <20171027001434.00D193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73d8de188efbf8c07d750416bfd74ef567ffacec/ghc >--------------------------------------------------------------- commit 73d8de188efbf8c07d750416bfd74ef567ffacec Author: Andrey Mokhov Date: Sun Jan 24 02:15:57 2016 +0000 Clean up, build stage 1 GHC on AppVeyor. >--------------------------------------------------------------- 73d8de188efbf8c07d750416bfd74ef567ffacec .appveyor.yml | 2 +- src/GHC.hs | 4 ++-- src/Package.hs | 14 ++++++++++++-- src/Rules.hs | 3 +-- src/Rules/Config.hs | 2 -- src/Rules/Libffi.hs | 2 +- src/Stage.hs | 23 +++++++++++------------ src/Target.hs | 2 +- src/Test.hs | 7 +++---- 9 files changed, 32 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 73d8de188efbf8c07d750416bfd74ef567ffacec From git at git.haskell.org Fri Oct 27 00:14:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a paragraph on customising progress messages (2c77b71) Message-ID: <20171027001435.762933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c77b7107ccf663598b9b64a22f3a4c5bc39b568/ghc >--------------------------------------------------------------- commit 2c77b7107ccf663598b9b64a22f3a4c5bc39b568 Author: Andrey Mokhov Date: Tue May 17 23:55:16 2016 +0100 Add a paragraph on customising progress messages See #244. [skip ci] >--------------------------------------------------------------- 2c77b7107ccf663598b9b64a22f3a4c5bc39b568 doc/user-settings.md | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/doc/user-settings.md b/doc/user-settings.md index 4624e2d..1433ae9 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -144,3 +144,20 @@ splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock ``` + +Hadrian prints various progress info during the build. You can customise how this +info is printed by overriding `putBuild` and `putSuccess` commands: + +```haskell +-- | Customise build progress messages (e.g. executing a build command). +putBuild :: String -> Action () +putBuild = putColoured Vivid White + +-- | Customise build success messages (e.g. a package is built successfully). +putSuccess :: String -> Action () +putSuccess = putColoured Vivid Green +``` + +You can tune colours for your favourite terminal and also change the verbosity +level, e.g. by setting `putSuccess = putLoud`, which will hide success messages +unless Hadrian is called with `--verbose` flag. From git at git.haskell.org Fri Oct 27 00:14:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve naming convention for build directories: always use stageN. (52ecf6c) Message-ID: <20171027001435.A66353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/52ecf6cb909644928ed754f5b111034ecb9dafc3/ghc >--------------------------------------------------------------- commit 52ecf6cb909644928ed754f5b111034ecb9dafc3 Author: Andrey Mokhov Date: Tue Dec 22 05:05:11 2015 +0000 Improve naming convention for build directories: always use stageN. >--------------------------------------------------------------- 52ecf6cb909644928ed754f5b111034ecb9dafc3 src/GHC.hs | 18 ++---------------- src/Rules.hs | 3 +-- src/Rules/Data.hs | 20 ++++++++++---------- src/Rules/Program.hs | 18 ++++++++++-------- src/Settings/Builders/Ghc.hs | 2 ++ src/Settings/Builders/GhcCabal.hs | 23 ++++++++++------------- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Packages.hs | 2 ++ 8 files changed, 38 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 52ecf6cb909644928ed754f5b111034ecb9dafc3 From git at git.haskell.org Fri Oct 27 00:14:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make .cabal meta-data more accurate (f9e5109) Message-ID: <20171027001437.733323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f9e510913956bc01201ad74bab60767794424034/ghc >--------------------------------------------------------------- commit f9e510913956bc01201ad74bab60767794424034 Author: Herbert Valerio Riedel Date: Sun Jan 24 10:07:01 2016 +0100 Make .cabal meta-data more accurate We need this so cabal (this is even more important with the upcoming nix-style cabal features) can do a proper job so this is a pre-requisite for the new build-system being used by default for GHC anyway, as we need to be as accurate as possible with the build specification to give `git bisect` a chance of remaining usable. >--------------------------------------------------------------- f9e510913956bc01201ad74bab60767794424034 shaking-up-ghc.cabal | 32 +++++++++++++++----------------- 1 file changed, 15 insertions(+), 17 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index cdd512a..674d6f0 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -107,26 +107,24 @@ executable ghc-shake , Test , Way - default-extensions: BangPatterns - , LambdaCase - , MultiWayIf - , TupleSections + default-language: Haskell2010 other-extensions: DeriveDataTypeable , DeriveGeneric , FlexibleInstances + , GeneralizedNewtypeDeriving + , LambdaCase , OverloadedStrings , RecordWildCards , ScopedTypeVariables - build-depends: base - , ansi-terminal >= 0.6 - , Cabal >= 1.22 - , containers >= 0.5 - , directory >= 1.2 - , extra >= 1.4 - , mtl >= 2.2 - , QuickCheck >= 2.6 - , shake >= 0.15 - , transformers >= 0.4 - , unordered-containers >= 0.2 - default-language: Haskell2010 - ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j + build-depends: base >= 4.8 && < 5 + , ansi-terminal == 0.6.* + , Cabal == 1.22.* + , containers == 0.5.* + , directory == 1.2.* + , extra == 1.4.* + , mtl == 2.2.* + , QuickCheck >= 2.6 && < 2.9 + , shake == 0.15.* + , transformers >= 0.4 && < 0.6 + , unordered-containers == 0.2.* + ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 From git at git.haskell.org Fri Oct 27 00:14:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace quote by show (d6a0d7a) Message-ID: <20171027001439.4B7213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6a0d7af44a6365e784cfa3e1d0da114b958e3f1/ghc >--------------------------------------------------------------- commit d6a0d7af44a6365e784cfa3e1d0da114b958e3f1 Author: Andrey Mokhov Date: Wed May 18 00:11:12 2016 +0100 Replace quote by show >--------------------------------------------------------------- d6a0d7af44a6365e784cfa3e1d0da114b958e3f1 src/Base.hs | 11 ++++----- src/Rules/Generators/ConfigHs.hs | 36 ++++++++++++++-------------- src/Rules/Generators/GhcBootPlatformH.hs | 24 +++++++++---------- src/Rules/Generators/GhcPlatformH.hs | 16 ++++++------- src/Rules/Generators/GhcSplit.hs | 4 ++-- src/Rules/Generators/VersionHs.hs | 6 ++--- src/Settings/Packages/Rts.hs | 40 ++++++++++++++++---------------- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/User.hs | 2 +- 9 files changed, 69 insertions(+), 72 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 d6a0d7af44a6365e784cfa3e1d0da114b958e3f1 From git at git.haskell.org Fri Oct 27 00:14:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (eda28da) Message-ID: <20171027001439.6B2C73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eda28da9f239b66ea1791d0ac9850cfae1232248/ghc >--------------------------------------------------------------- commit eda28da9f239b66ea1791d0ac9850cfae1232248 Author: Andrey Mokhov Date: Tue Dec 22 05:07:32 2015 +0000 Clean up. >--------------------------------------------------------------- eda28da9f239b66ea1791d0ac9850cfae1232248 src/Rules/Library.hs | 2 +- src/Settings.hs | 11 +++++------ 2 files changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 134e2be..ff5ce63 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -49,7 +49,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do putSuccess $ renderBox [ "Successfully built package library '" ++ pkgName pkg - ++ "' (stage " ++ show stage ++ ", way "++ show way ++ ")." + ++ "' (" ++ show stage ++ ", way "++ show way ++ ")." , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." ] diff --git a/src/Settings.hs b/src/Settings.hs index fd7c14c..9a0e07d 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -53,26 +53,25 @@ getPackageSources = do return $ foundSources ++ fixGhcPrim generatedSources -- findModuleFiles scans a list of given directories and finds files matching a --- given extension pattern (e.g., "*hs") that correspond to modules of the --- currently built package. Missing module files are returned in a separate --- list. The returned pair contains the following: +-- given pattern (e.g., "*hs") that correspond to modules of the currently built +-- package. Missing module files are returned in a separate list. The returned +-- pair contains the following: -- * a list of found module files, with paths being relative to one of given -- directories, e.g. "codeGen/CodeGen/Platform.hs" for the compiler package. -- * a list of module files that have not been found, with paths being relative -- to the module directory, e.g. "CodeGen/Platform", and with no extension. findModuleFiles :: [FilePath] -> FilePattern -> Expr ([FilePath], [FilePath]) -findModuleFiles dirs extension = do +findModuleFiles dirs pattern = do modules <- getPkgDataList Modules let decodedMods = sort . map decodeModule $ modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedMods - matchExtension = (?==) ("*" <.> extension) result <- lift . fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do let fullDir = dir -/- mDir - files <- fmap (filter matchExtension) $ getDirectoryContents fullDir + files <- getDirectoryFiles fullDir [pattern] let cmp fe f = compare (dropExtension fe) f found = intersectOrd cmp files mFiles return (map (fullDir -/-) found, (mDir, map dropExtension found)) From git at git.haskell.org Fri Oct 27 00:14:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add `cabal new-build` based wrapper script (6432f0c) Message-ID: <20171027001440.E1D653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6432f0c241ea173bd5d7f7de4833085d6155c47f/ghc >--------------------------------------------------------------- commit 6432f0c241ea173bd5d7f7de4833085d6155c47f Author: Herbert Valerio Riedel Date: Sun Jan 24 10:43:43 2016 +0100 Add `cabal new-build` based wrapper script This makes use of the new nix-store cache for the shake library and other pre-requisities, rather than using the reinstall-breakage-prone old-style global pkg-db >--------------------------------------------------------------- 6432f0c241ea173bd5d7f7de4833085d6155c47f .gitignore | 17 ++++++++++++----- build.sh => build.cabal-new.sh | 28 +++++++++++++++++++--------- 2 files changed, 31 insertions(+), 14 deletions(-) diff --git a/.gitignore b/.gitignore index 6cc5501..967be07 100644 --- a/.gitignore +++ b/.gitignore @@ -1,7 +1,14 @@ -.shake/ -.db/ +/.shake/ +/.db/ cfg/system.config + +# build.cabal.sh specific +/dist/ +/.cabal-sandbox/ cabal.sandbox.config -dist/ -.cabal-sandbox/ -.stack-work/ + +# build.cabal-new.sh specific +/dist-newstyle/ + +# build.stack.sh specific +/.stack-work/ diff --git a/build.sh b/build.cabal-new.sh similarity index 60% copy from build.sh copy to build.cabal-new.sh index 719e85e..96c194e 100755 --- a/build.sh +++ b/build.cabal-new.sh @@ -1,5 +1,8 @@ #!/usr/bin/env bash +# This wrapper scripts makes use of cabal 1.24+'s nix-store; +# In order to clean/reset, remove the `dist-newstyle/` folder + set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -32,15 +35,22 @@ root="$(dirname "$(rl "$0")")" mkdir -p "$root/.shake" -ghc \ - "$root/src/Main.hs" \ - -Wall \ - -i"$root/src" \ - -rtsopts \ - -with-rtsopts=-I0 \ - -outputdir="$root/.shake" \ - -j -O \ - -o "$root/.shake/build" +# Notes/Random thoughts: +# +# - if ghc.git had a top-level `cabal.project` file, we could maybe avoid the +# boilerplate above, as we could simply say `cabal exec ghc-shake` from within +# any GHC folder not shadowed by a nearer shadowing `cabal.project` file. + +pushd "$root/" + +cabal new-build --disable-profiling --disable-documentation -j exe:ghc-shake + +PKGVER="$(awk '/^version:/ { print $2 }' shaking-up-ghc.cabal)" + +cp -v "$root/dist-newstyle/build/shaking-up-ghc-${PKGVER}/build/ghc-shake/ghc-shake" \ + "$root/.shake/build" + +popd "$root/.shake/build" \ --lint \ From git at git.haskell.org Fri Oct 27 00:14:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add quote function (c81dc684f7) Message-ID: <20171027001443.60CB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c81dc684f7206ebabf877d54c8a740398e5e425a/ghc >--------------------------------------------------------------- commit c81dc684f7206ebabf877d54c8a740398e5e425a Author: Andrey Mokhov Date: Wed May 18 00:28:08 2016 +0100 Add quote function >--------------------------------------------------------------- c81dc684f7206ebabf877d54c8a740398e5e425a src/Base.hs | 6 +++++- src/Builder.hs | 6 +++--- src/Oracles/Config.hs | 2 +- src/Oracles/Config/Flag.hs | 6 +++--- src/Oracles/Dependencies.hs | 4 ++-- src/Rules/Actions.hs | 2 +- src/Rules/Data.hs | 10 +++++----- src/Rules/Generate.hs | 4 ++-- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 6 +++--- 10 files changed, 26 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c81dc684f7206ebabf877d54c8a740398e5e425a From git at git.haskell.org Fri Oct 27 00:14:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix tracking of *.hs-incl files. (363b227) Message-ID: <20171027001443.9016F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/363b227e1e310561018c1991249cbf21bf28be57/ghc >--------------------------------------------------------------- commit 363b227e1e310561018c1991249cbf21bf28be57 Author: Andrey Mokhov Date: Tue Dec 22 05:09:27 2015 +0000 Fix tracking of *.hs-incl files. >--------------------------------------------------------------- 363b227e1e310561018c1991249cbf21bf28be57 src/Rules/Dependencies.hs | 40 +++++++++++++++++++--------------------- 1 file changed, 19 insertions(+), 21 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 996d927..47e6c6d 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -24,7 +24,24 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = hDepFile %> \file -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) $ need [platformH] - need srcs + -- TODO: very ugly and fragile; use gcc -MM instead? + let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] + need $ srcs ++ extraDeps if srcs == [] then writeFileChanged file "" else build $ fullTarget target (GhcM stage) srcs [file] @@ -36,23 +53,4 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need $ hDepFile : cDepFiles -- need all for more parallelism cDeps <- fmap concat $ mapM readFile' cDepFiles hDeps <- readFile' hDepFile - -- TODO: very ugly and fragile; use gcc -MM instead? - let hsIncl hs incl = buildPath -/- hs <.> "o" ++ " : " - ++ buildPath -/- incl ++ "\n" - extraDeps = if pkg /= compiler then [] else - hsIncl "PrelNames" "primop-vector-uniques.hs-incl" - ++ hsIncl "PrimOp" "primop-data-decl.hs-incl" - ++ hsIncl "PrimOp" "primop-tag.hs-incl" - ++ hsIncl "PrimOp" "primop-list.hs-incl" - ++ hsIncl "PrimOp" "primop-strictness.hs-incl" - ++ hsIncl "PrimOp" "primop-fixity.hs-incl" - ++ hsIncl "PrimOp" "primop-primop-info.hs-incl" - ++ hsIncl "PrimOp" "primop-out-of-line.hs-incl" - ++ hsIncl "PrimOp" "primop-has-side-effects.hs-incl" - ++ hsIncl "PrimOp" "primop-can-fail.hs-incl" - ++ hsIncl "PrimOp" "primop-code-size.hs-incl" - ++ hsIncl "PrimOp" "primop-commutable.hs-incl" - ++ hsIncl "TysPrim" "primop-vector-tys-exports.hs-incl" - ++ hsIncl "TysPrim" "primop-vector-tycons.hs-incl" - ++ hsIncl "TysPrim" "primop-vector-tys.hs-incl" - writeFileChanged file $ cDeps ++ hDeps ++ extraDeps + writeFileChanged file $ cDeps ++ hDeps From git at git.haskell.org Fri Oct 27 00:14:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Temporarily disable ChangeModtimeAndDigest (test AppVeyor speed up). (21eef1e) Message-ID: <20171027001444.9940A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21eef1e36c8592c04724fa59a61f0826fd2b94cd/ghc >--------------------------------------------------------------- commit 21eef1e36c8592c04724fa59a61f0826fd2b94cd Author: Andrey Mokhov Date: Sun Jan 24 13:06:56 2016 +0000 Temporarily disable ChangeModtimeAndDigest (test AppVeyor speed up). [skip ci] >--------------------------------------------------------------- 21eef1e36c8592c04724fa59a61f0826fd2b94cd src/Main.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 69f739b..0f0d450 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -39,7 +39,6 @@ main = shakeArgsWith options CmdLineFlag.flags $ \cmdLineFlags targets -> do , Rules.packageRules , Test.testRules ] options = shakeOptions - { shakeChange = ChangeModtimeAndDigest - , shakeFiles = Base.shakeFilesPath + { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:14:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy *.hs-boot files of generated sources. (4e2f6c5) Message-ID: <20171027001447.27A503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e2f6c504a541f7a6eab6eb072bae265d67e5bff/ghc >--------------------------------------------------------------- commit 4e2f6c504a541f7a6eab6eb072bae265d67e5bff Author: Andrey Mokhov Date: Tue Dec 22 05:10:46 2015 +0000 Copy *.hs-boot files of generated sources. >--------------------------------------------------------------- 4e2f6c504a541f7a6eab6eb072bae265d67e5bff src/Rules/Generate.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 53b7dd6..10a4e6b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -29,11 +29,12 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = buildPath = path -/- "build" primopsTxt = targetPath stage compiler -/- "build/primops.txt" platformH = targetPath stage compiler -/- "ghc_boot_platform.h" - in do -- TODO: do we need to copy *.(l)hs-boot files here? Never happens? - buildPath -/- "*.hs" %> \file -> do + generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) + in do + generated ?> \file -> do dirs <- interpretPartial target $ getPkgDataList SrcDirs files <- getDirectoryFiles "" $ - [ packagePath -/- d -/- takeBaseName file <.> "*" | d <- dirs ] + [ packagePath -/- d ++ "//" ++ takeBaseName file <.> "*" | d <- dirs ] let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ "Exactly one generator expected for " ++ file @@ -41,6 +42,9 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = let (src, builder) = head gens need [src] build $ fullTarget target builder [src] [file] + let srcBoot = src -<.> "hs-boot" + whenM (doesFileExist srcBoot) $ + copyFileChanged srcBoot $ file -<.> "hs-boot" when (pkg == compiler) $ primopsTxt %> \file -> do need [platformH, primopsSource] @@ -80,7 +84,7 @@ quote :: String -> String quote s = "\"" ++ s ++ "\"" -- TODO: do we need ghc-split? Always or is it platform specific? --- TODO: add tracking +-- TODO: add tracking by moving these functions to separate tracked files generateConfigHs :: Expr String generateConfigHs = do cProjectName <- getSetting ProjectName From git at git.haskell.org Fri Oct 27 00:14:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix putSuccess (1080ebf) Message-ID: <20171027001447.3DB043A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1080ebfc611e8cdae0b4efb166f166a9cebfa6e8/ghc >--------------------------------------------------------------- commit 1080ebfc611e8cdae0b4efb166f166a9cebfa6e8 Author: Andrey Mokhov Date: Wed May 18 00:53:54 2016 +0100 Fix putSuccess >--------------------------------------------------------------- 1080ebfc611e8cdae0b4efb166f166a9cebfa6e8 src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 60aeb89..16c7c25 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -102,4 +102,4 @@ putBuild = putColoured Vivid White -- | Customise build success messages (e.g. a package is built successfully). putSuccess :: String -> Action () -putSuccess = withVerbosity Loud . putColoured Vivid Green +putSuccess = putColoured Vivid Green From git at git.haskell.org Fri Oct 27 00:14:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #192 from hvr/pr/fix-cabal-metadata (45e208e) Message-ID: <20171027001448.413943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45e208eda37617737650d02ad7a6427e4618e1bf/ghc >--------------------------------------------------------------- commit 45e208eda37617737650d02ad7a6427e4618e1bf Merge: 21eef1e f9e5109 Author: Andrey Mokhov Date: Sun Jan 24 13:48:25 2016 +0000 Merge pull request #192 from hvr/pr/fix-cabal-metadata Make .cabal meta-data more accurate [skip ci] >--------------------------------------------------------------- 45e208eda37617737650d02ad7a6427e4618e1bf shaking-up-ghc.cabal | 32 +++++++++++++++----------------- 1 file changed, 15 insertions(+), 17 deletions(-) From git at git.haskell.org Fri Oct 27 00:14:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove a duplicate success message when building Lib0. (bfe72a5) Message-ID: <20171027001451.335B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bfe72a5f9fa4aa31bf9e83ad690aef6b8741f8e6/ghc >--------------------------------------------------------------- commit bfe72a5f9fa4aa31bf9e83ad690aef6b8741f8e6 Author: Andrey Mokhov Date: Tue Dec 22 05:25:01 2015 +0000 Remove a duplicate success message when building Lib0. >--------------------------------------------------------------- bfe72a5f9fa4aa31bf9e83ad690aef6b8741f8e6 src/Rules/Library.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index ff5ce63..12102c0 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -41,17 +41,17 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do let objs = cObjs ++ splitObjs ++ eObjs asuf <- libsuf way - if ("//*-0" <.> asuf) ?== a + let isLib0 = ("//*-0" <.> asuf) ?== a + if isLib0 then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls else build $ fullTarget target Ar objs [a] synopsis <- interpretPartial target $ getPkgData Synopsis - putSuccess $ renderBox + unless isLib0 . putSuccess $ renderBox [ "Successfully built package library '" ++ pkgName pkg ++ "' (" ++ show stage ++ ", way "++ show way ++ ")." - , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." - ] + , "Package synopsis: " ++ dropWhileEnd isPunctuation synopsis ++ "." ] -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. From git at git.haskell.org Fri Oct 27 00:14:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #193 from hvr/pr/cabal-nix (e2271ac) Message-ID: <20171027001452.222943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2271ac0a67bec50c9fd45bef036e98e19e83d21/ghc >--------------------------------------------------------------- commit e2271ac0a67bec50c9fd45bef036e98e19e83d21 Merge: 45e208e 6432f0c Author: Andrey Mokhov Date: Sun Jan 24 13:49:25 2016 +0000 Merge pull request #193 from hvr/pr/cabal-nix Add `cabal new-build`-based wrapper script [skip ci] >--------------------------------------------------------------- e2271ac0a67bec50c9fd45bef036e98e19e83d21 .gitignore | 17 ++++++++++++----- build.sh => build.cabal-new.sh | 28 +++++++++++++++++++--------- 2 files changed, 31 insertions(+), 14 deletions(-) From git at git.haskell.org Fri Oct 27 00:14:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --progress-colour command line flag (aa9c65b) Message-ID: <20171027001450.B58873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aa9c65b3adb91b56c1974a0db39ef3c5082e816c/ghc >--------------------------------------------------------------- commit aa9c65b3adb91b56c1974a0db39ef3c5082e816c Author: Andrey Mokhov Date: Wed May 18 02:54:23 2016 +0100 Add --progress-colour command line flag Fix #244. >--------------------------------------------------------------- aa9c65b3adb91b56c1974a0db39ef3c5082e816c src/Base.hs | 27 +++++++++++++++++---------- src/CmdLineFlag.hs | 51 ++++++++++++++++++++++++++++++++++++--------------- 2 files changed, 53 insertions(+), 25 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 6fe8ac1..cb040d4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -38,6 +38,8 @@ import System.Console.ANSI import System.IO import System.Info +import CmdLineFlag + -- TODO: reexport Stage, etc.? -- | Hadrian lives in 'hadrianPath' directory of the GHC tree. @@ -144,14 +146,19 @@ matchVersionedFilePath prefix suffix filePath = -- | A more colourful version of Shake's putNormal. putColoured :: ColorIntensity -> Color -> String -> Action () putColoured intensity colour msg = do - liftIO $ set [SetColor Foreground intensity colour] + c <- useColour + when c . liftIO $ setSGR [SetColor Foreground intensity colour] putNormal msg - liftIO $ set [] - liftIO $ hFlush stdout - where - set a = do - supported <- hSupportsANSI stdout - when (win || supported) $ setSGR a - -- An ugly hack to always try to print colours when on mingw and cygwin. - -- See: https://github.com/snowleopard/hadrian/pull/253 - win = "mingw" `isPrefixOf` os || "cygwin" `isPrefixOf` os + when c . liftIO $ do + setSGR [] + hFlush stdout + +useColour :: Action Bool +useColour = case cmdProgressColour of + Never -> return False + Always -> return True + Auto -> do + supported <- liftIO $ hSupportsANSI stdout + -- An ugly hack to always try to print colours when on mingw and cygwin. + let windows = any (`isPrefixOf` os) ["mingw", "cygwin"] + return $ windows || supported diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 8fc1487..10c39f2 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,35 +1,39 @@ module CmdLineFlag ( putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, Flavour (..), - cmdProgressInfo, ProgressInfo (..), cmdSkipConfigure, cmdSplitObjects + cmdProgressColour, ProgressColour (..), cmdProgressInfo, ProgressInfo (..), + cmdSkipConfigure, cmdSplitObjects ) where import Data.IORef import Data.List.Extra import System.Console.GetOpt -import System.IO.Unsafe (unsafePerformIO) +import System.IO.Unsafe -- | 'CmdLineFlag.Untracked' is a collection of flags that can be passed via the -- command line. These flags are not tracked, that is they do not force any -- build rules to be rurun. data Untracked = Untracked - { buildHaddock :: Bool - , flavour :: Flavour - , progressInfo :: ProgressInfo - , skipConfigure :: Bool - , splitObjects :: Bool } + { buildHaddock :: Bool + , flavour :: Flavour + , progressColour :: ProgressColour + , progressInfo :: ProgressInfo + , skipConfigure :: Bool + , splitObjects :: Bool } deriving (Eq, Show) -data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -data Flavour = Default | Quick deriving (Eq, Show) +data Flavour = Default | Quick deriving (Eq, Show) +data ProgressColour = Never | Auto | Always deriving (Eq, Show) +data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked defaultUntracked = Untracked - { buildHaddock = False - , flavour = Default - , progressInfo = Normal - , skipConfigure = False - , splitObjects = False } + { buildHaddock = False + , flavour = Default + , progressColour = Auto + , progressInfo = Normal + , skipConfigure = False + , splitObjects = False } readBuildHaddock :: Either String (Untracked -> Untracked) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } @@ -45,6 +49,18 @@ readFlavour ms = set :: Flavour -> Untracked -> Untracked set flag flags = flags { flavour = flag } +readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) +readProgressColour ms = + maybe (Left "Cannot parse progress-colour") (Right . set) (go =<< lower <$> ms) + where + go :: String -> Maybe ProgressColour + go "never" = Just Never + go "auto" = Just Auto + go "always" = Just Always + go _ = Nothing + set :: ProgressColour -> Untracked -> Untracked + set flag flags = flags { progressColour = flag } + readProgressInfo :: Maybe String -> Either String (Untracked -> Untracked) readProgressInfo ms = maybe (Left "Cannot parse progress-info") (Right . set) (go =<< lower <$> ms) @@ -70,8 +86,10 @@ cmdFlags = "Build flavour (Default or Quick)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." + , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") + "Use colours in progress info (Never, Auto or Always)." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") - "Progress info style (None, Brief, Normal, or Unicorn)." + "Progress info style (None, Brief, Normal or Unicorn)." , Option [] ["skip-configure"] (NoArg readSkipConfigure) "Skip the boot and configure scripts (if you want to run them manually)." , Option [] ["split-objects"] (NoArg readSplitObjects) @@ -96,6 +114,9 @@ cmdBuildHaddock = buildHaddock getCmdLineFlags cmdFlavour :: Flavour cmdFlavour = flavour getCmdLineFlags +cmdProgressColour :: ProgressColour +cmdProgressColour = progressColour getCmdLineFlags + cmdProgressInfo :: ProgressInfo cmdProgressInfo = progressInfo getCmdLineFlags From git at git.haskell.org Fri Oct 27 00:14:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use colours on CI (5ca3853) Message-ID: <20171027001454.563BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ca3853fd62d8dd8566b610a2e1534cf573e9e0d/ghc >--------------------------------------------------------------- commit 5ca3853fd62d8dd8566b610a2e1534cf573e9e0d Author: Andrey Mokhov Date: Wed May 18 02:57:50 2016 +0100 Don't use colours on CI See #244 >--------------------------------------------------------------- 5ca3853fd62d8dd8566b610a2e1534cf573e9e0d .travis.yml | 2 +- appveyor.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 7d5b699..4ec6721 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,7 +59,7 @@ install: script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --no-progress --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index bb78b80..09baa2e 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --profile=- --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:14:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement encodeModule -- the inverse for decodeModule. (ba41ded) Message-ID: <20171027001454.E9F713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba41dedc0c632836dff3c3ce55f7210d344e44e7/ghc >--------------------------------------------------------------- commit ba41dedc0c632836dff3c3ce55f7210d344e44e7 Author: Andrey Mokhov Date: Wed Dec 23 06:12:19 2015 +0000 Implement encodeModule -- the inverse for decodeModule. >--------------------------------------------------------------- ba41dedc0c632836dff3c3ce55f7210d344e44e7 src/Base.hs | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index ac457ad..79ce119 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -25,9 +25,8 @@ module Base ( module System.Console.ANSI, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, - removeFileIfExists, - replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, + bimap, minusOrd, intersectOrd, removeFileIfExists, replaceEq, chunksOfSize, + replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-) ) where import Control.Applicative @@ -78,12 +77,18 @@ replaceSeparators = replaceIf isPathSeparator replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) --- | Given a module name extract the directory and file names, e.g.: +-- | Given a module name extract the directory and file name, e.g.: -- -- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") decodeModule :: String -> (FilePath, String) decodeModule = splitFileName . replaceEq '.' '/' +-- | Given the directory and file name find the corresponding module name, e.g.: +-- +-- > encodeModule "Data/Functor/" "Identity.hs" = "Data.Functor.Identity" +encodeModule :: FilePath -> String -> String +encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file + -- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx From git at git.haskell.org Fri Oct 27 00:14:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring ChangeModtimeAndDigest back. (dfabde8) Message-ID: <20171027001455.AB8863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfabde88d19471916a86c73a977d6f320f271978/ghc >--------------------------------------------------------------- commit dfabde88d19471916a86c73a977d6f320f271978 Author: Andrey Mokhov Date: Sun Jan 24 17:06:09 2016 +0000 Bring ChangeModtimeAndDigest back. [skip ci] >--------------------------------------------------------------- dfabde88d19471916a86c73a977d6f320f271978 src/Main.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index 0f0d450..69f739b 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -39,6 +39,7 @@ main = shakeArgsWith options CmdLineFlag.flags $ \cmdLineFlags targets -> do , Rules.packageRules , Test.testRules ] options = shakeOptions - { shakeFiles = Base.shakeFilesPath + { shakeChange = ChangeModtimeAndDigest + , shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:14:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run CI in verbose mode (dd3d592) Message-ID: <20171027001458.40AB43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dd3d592331fb12f33b117f098e0fb19b388e4eae/ghc >--------------------------------------------------------------- commit dd3d592331fb12f33b117f098e0fb19b388e4eae Author: Andrey Mokhov Date: Wed May 18 09:34:51 2016 +0100 Run CI in verbose mode >--------------------------------------------------------------- dd3d592331fb12f33b117f098e0fb19b388e4eae .travis.yml | 2 +- appveyor.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4ec6721..3b61256 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,7 +59,7 @@ install: script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index 09baa2e..bb5620e 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:14:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (ecdeae7) Message-ID: <20171027001459.132373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ecdeae76f0a89eec2f95a5285f174ef6ef107329/ghc >--------------------------------------------------------------- commit ecdeae76f0a89eec2f95a5285f174ef6ef107329 Author: Andrey Mokhov Date: Wed Dec 23 06:13:11 2015 +0000 Clean up. >--------------------------------------------------------------- ecdeae76f0a89eec2f95a5285f174ef6ef107329 src/Oracles/WindowsRoot.hs | 2 +- src/Rules/Data.hs | 26 +++++++++++++------------- 2 files changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 51cb516..2ec13c7 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -14,7 +14,7 @@ windowsRoot = askOracle $ WindowsRoot () -- the root is slow (at least the current implementation). windowsRootOracle :: Rules () windowsRootOracle = do - root <- newCache $ \() -> do + root <- newCache $ \_ -> do Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] let root = dropWhileEnd isSpace out putOracle $ "Detected root on Windows: " ++ root diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 96deed9..26755ca 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -44,19 +44,19 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- TODO: code duplication around ghcIncludeDirs priority 2.0 $ do when (pkg == hp2ps) $ dataFile %> \mk -> do - let cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" - , "Reorder.c", "TopTwenty.c", "AuxFile.c", "Deviation.c" - , "HpFile.c", "Marks.c", "Scale.c", "TraceElement.c" - , "Axes.c", "Dimensions.c", "Key.c", "PsFile.c" - , "Shade.c", "Utilities.c" ] - contents = unlines - [ "utils_hp2ps_stage0_PROGNAME = hp2ps" - , "utils_hp2ps_stage0_C_SRCS = " ++ unwords cSrcs - , "utils_hp2ps_stage0_INSTALL = YES" - , "utils_hp2ps_stage0_INSTALL_INPLACE = YES" - , "utils_hp2ps_stage0_DEP_EXTRA_LIBS = m" - , "utils_hp2ps_stage0_CC_OPTS = " - ++ unwords (map ("-I"++) ghcIncludeDirs) ] + let prefix = "utils_hp2ps_stage" ++ show (fromEnum stage) ++ "_" + cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" + , "Reorder.c", "TopTwenty.c", "AuxFile.c" + , "Deviation.c", "HpFile.c", "Marks.c", "Scale.c" + , "TraceElement.c", "Axes.c", "Dimensions.c", "Key.c" + , "PsFile.c", "Shade.c", "Utilities.c" ] + contents = unlines $ map (prefix++) + [ "PROGNAME = hp2ps" + , "C_SRCS = " ++ unwords cSrcs + , "INSTALL = YES" + , "INSTALL_INPLACE = YES" + , "DEP_EXTRA_LIBS = m" + , "CC_OPTS = " ++ unwords (map ("-I"++) ghcIncludeDirs) ] writeFileChanged mk contents putBuild $ "| Successfully generated '" ++ mk ++ "'." From git at git.haskell.org Fri Oct 27 00:14:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build flavours, implement a simple quick flavour. (8738dd2) Message-ID: <20171027001459.6F3813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8738dd20c48b8728a353858e771a107a5ca883ad/ghc >--------------------------------------------------------------- commit 8738dd20c48b8728a353858e771a107a5ca883ad Author: Andrey Mokhov Date: Sun Jan 24 22:16:48 2016 +0000 Add build flavours, implement a simple quick flavour. See #188. >--------------------------------------------------------------- 8738dd20c48b8728a353858e771a107a5ca883ad .appveyor.yml | 2 +- src/CmdLineFlag.hs | 80 ++++++++++++++++++++++++++---------------- src/Expression.hs | 2 +- src/Main.hs | 2 +- src/Settings/Args.hs | 13 +++++-- src/Settings/Flavours/Quick.hs | 9 +++++ 6 files changed, 72 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 8738dd20c48b8728a353858e771a107a5ca883ad From git at git.haskell.org Fri Oct 27 00:15:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify include and link paths (13b80f7) Message-ID: <20171027001501.DA85E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13b80f771aac9e9d4a5363632c474261914d5e18/ghc >--------------------------------------------------------------- commit 13b80f771aac9e9d4a5363632c474261914d5e18 Author: Andrey Mokhov Date: Thu May 19 00:45:14 2016 +0100 Unify include and link paths >--------------------------------------------------------------- 13b80f771aac9e9d4a5363632c474261914d5e18 src/Settings/Builders/Common.hs | 2 +- src/Settings/Builders/Ghc.hs | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 3f53dec..252667f 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -25,7 +25,7 @@ cIncludeArgs = do mconcat [ arg $ "-I" ++ path , arg $ "-I" ++ path -/- "autogen" , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] - , append [ "-I" ++ dir | dir <- depDirs ] ] + , append [ "-I" ++ unifyPath dir | dir <- depDirs ] ] ldArgs :: Args ldArgs = mempty diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 66c009b..2199874 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -44,8 +44,8 @@ ghcLinkArgs = builder (Ghc Link) ? do else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ arg "-no-auto-link-packages" - , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] - , append [ "-optl-L" ++ dir | dir <- libDirs ] ] + , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] + , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] -- TODO: Add Touchy builder and use needBuilder. needTouchy :: ReaderT Target Action () From git at git.haskell.org Fri Oct 27 00:15:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement ModuleFiles oracle for caching the search of module files of a package. (cf825fe) Message-ID: <20171027001502.DC9A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf825feba28b287a8e3eee00eee543d4c5b5e8fe/ghc >--------------------------------------------------------------- commit cf825feba28b287a8e3eee00eee543d4c5b5e8fe Author: Andrey Mokhov Date: Wed Dec 23 06:14:11 2015 +0000 Implement ModuleFiles oracle for caching the search of module files of a package. >--------------------------------------------------------------- cf825feba28b287a8e3eee00eee543d4c5b5e8fe src/Oracles/ModuleFiles.hs | 96 ++++++++++++++++++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 7 ++-- src/Rules/Oracles.hs | 6 ++- src/Settings.hs | 55 +++++--------------------- 4 files changed, 113 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 cf825feba28b287a8e3eee00eee543d4c5b5e8fe From git at git.haskell.org Fri Oct 27 00:15:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use quick flavour on Travis. (5ed8f3a) Message-ID: <20171027001503.47BF23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ed8f3a48e8e6c401302988547fc10f73c9340c7/ghc >--------------------------------------------------------------- commit 5ed8f3a48e8e6c401302988547fc10f73c9340c7 Author: Andrey Mokhov Date: Sun Jan 24 23:08:16 2016 +0000 Use quick flavour on Travis. See #188. >--------------------------------------------------------------- 5ed8f3a48e8e6c401302988547fc10f73c9340c7 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 1b96c78..84bb380 100644 --- a/.travis.yml +++ b/.travis.yml @@ -64,7 +64,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress $TARGET + - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET cache: directories: From git at git.haskell.org Fri Oct 27 00:15:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (7053d0c) Message-ID: <20171027001505.BA4F73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7053d0caad3fd13f471a62c681d4d7a91ad843ba/ghc >--------------------------------------------------------------- commit 7053d0caad3fd13f471a62c681d4d7a91ad843ba Author: Andrey Mokhov Date: Thu May 19 22:32:41 2016 +0100 Minor revision >--------------------------------------------------------------- 7053d0caad3fd13f471a62c681d4d7a91ad843ba src/Settings/Builders/Configure.hs | 27 ++++++++++++++------------- src/Settings/Builders/DeriveConstants.hs | 19 +++++++++---------- src/Settings/Builders/Ghc.hs | 13 ++++++------- src/Settings/Builders/GhcCabal.hs | 7 ++----- src/Settings/Builders/GhcPkg.hs | 5 +---- src/Settings/Builders/Haddock.hs | 1 - src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Builders/Make.hs | 6 +++--- src/Settings/Builders/Tar.hs | 8 +++----- src/Settings/Packages/Compiler.hs | 6 ++++-- src/Settings/Packages/Ghc.hs | 3 ++- src/Settings/Packages/GhcCabal.hs | 15 ++++++--------- src/Settings/Packages/Hp2ps.hs | 7 +++---- src/Settings/Packages/IntegerGmp.hs | 10 ++++++---- src/Settings/Packages/Rts.hs | 6 ++++-- src/Settings/Packages/RunGhc.hs | 5 ++--- src/Settings/Packages/Touchy.hs | 7 +++---- src/Settings/Packages/Unlit.hs | 7 +++---- 18 files changed, 72 insertions(+), 82 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 7053d0caad3fd13f471a62c681d4d7a91ad843ba From git at git.haskell.org Fri Oct 27 00:15:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a new command line flag: build flavour. (5286213) Message-ID: <20171027001506.E4E213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/528621354633d9d1af4ae6ed7572c9b727a13460/ghc >--------------------------------------------------------------- commit 528621354633d9d1af4ae6ed7572c9b727a13460 Author: Andrey Mokhov Date: Mon Jan 25 00:19:39 2016 +0000 Add a new command line flag: build flavour. See #188. >--------------------------------------------------------------- 528621354633d9d1af4ae6ed7572c9b727a13460 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index b8fd40f..85b9cbe 100644 --- a/README.md +++ b/README.md @@ -55,6 +55,8 @@ currently supports several others: arguments; also run the `boot` script to create the `configure` script if necessary. You do not have to use this functionality of the new build system; feel free to run `boot` and `configure` scripts manually, as you do when using `make`. +* `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: +`default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). From git at git.haskell.org Fri Oct 27 00:15:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (a5a12ec) Message-ID: <20171027001506.8B8173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a12ec621ad8461cf80cf91fcbf583919358d70/ghc >--------------------------------------------------------------- commit a5a12ec621ad8461cf80cf91fcbf583919358d70 Author: Moritz Angermann Date: Wed Dec 23 14:59:44 2015 +0800 Update README.md Adding missing prerequisites. These are probably installed if you build ghc often or use shake, but if not, these are missing. >--------------------------------------------------------------- a5a12ec621ad8461cf80cf91fcbf583919358d70 README.md | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/README.md b/README.md index 5d87bc4..05e247e 100644 --- a/README.md +++ b/README.md @@ -8,6 +8,12 @@ This is supposed to go into the `shake-build` directory of the GHC source tree. Trying it --------- +Prerequisits +``` +$ cabal install alex +$ cabal install shake +``` + On Linux, ``` $ git clone git://git.haskell.org/ghc From git at git.haskell.org Fri Oct 27 00:15:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link gmp objects to integerGmp library (5b75d12) Message-ID: <20171027001509.4E41E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b75d126eb0716e44be9be27dc4895a915d78a52/ghc >--------------------------------------------------------------- commit 5b75d126eb0716e44be9be27dc4895a915d78a52 Author: Andrey Mokhov Date: Thu May 19 22:55:32 2016 +0100 Link gmp objects to integerGmp library Fix #241 >--------------------------------------------------------------- 5b75d126eb0716e44be9be27dc4895a915d78a52 src/Rules/Library.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 637dbaa..3fff65f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -69,9 +69,10 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do let cObjs = map (objFile context) cSrcs hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] + gObjs = [ gmpObjects -/- "*.o" | package == integerGmp ] objs = cObjs ++ hObjs need objs - build $ Target context Ld objs [obj] + build $ Target context Ld (objs ++ gObjs) [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' From git at git.haskell.org Fri Oct 27 00:15:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #25 from angerman/patch-1 (0153864) Message-ID: <20171027001510.32B9A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0153864864ac88a314b3fbfb4e681e0ea6ab1451/ghc >--------------------------------------------------------------- commit 0153864864ac88a314b3fbfb4e681e0ea6ab1451 Merge: cf825fe a5a12ec Author: Andrey Mokhov Date: Wed Dec 23 11:26:34 2015 +0000 Merge pull request #25 from angerman/patch-1 Update README.md >--------------------------------------------------------------- 0153864864ac88a314b3fbfb4e681e0ea6ab1451 README.md | 6 ++++++ 1 file changed, 6 insertions(+) From git at git.haskell.org Fri Oct 27 00:15:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't change extension of files found in PATH. (3787444) Message-ID: <20171027001510.8E9163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37874441d3ff2255fea40d60420d4353245ed930/ghc >--------------------------------------------------------------- commit 37874441d3ff2255fea40d60420d4353245ed930 Author: Andrey Mokhov Date: Mon Jan 25 14:04:03 2016 +0000 Don't change extension of files found in PATH. See #194. >--------------------------------------------------------------- 37874441d3ff2255fea40d60420d4353245ed930 src/Builder.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 22723a5..bfb757f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -112,9 +112,9 @@ builderPath builder = case builderProvenance builder of ++ "' in configuration files. Have you forgot to run configure?" windows <- windowsHost case (path, windows) of - ("", _) -> return path - (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) - (p, False) -> lookupInPath (p -<.> exe) + ("", _ ) -> return path + (p , True ) -> fixAbsolutePathOnWindows (p -<.> exe) + (p , False) -> lookupInPath p getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath From git at git.haskell.org Fri Oct 27 00:15:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revise comments (816b0ac) Message-ID: <20171027001512.D875A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/816b0acda7a57cdb3c7a88831b445bb17405975b/ghc >--------------------------------------------------------------- commit 816b0acda7a57cdb3c7a88831b445bb17405975b Author: Andrey Mokhov Date: Thu May 19 23:39:15 2016 +0100 Revise comments >--------------------------------------------------------------- 816b0acda7a57cdb3c7a88831b445bb17405975b src/Oracles/ArgsHash.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index c26efd4..bb597c4 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -8,26 +8,25 @@ import Settings.Args import Target newtype ArgsHashKey = ArgsHashKey Target - deriving (Show, Eq, Typeable, Binary, Hashable, NFData) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- This is an action that given a full target determines the corresponding --- argument list and computes its hash. The resulting value is tracked in a --- Shake oracle, hence initiating rebuilts when the hash is changed (a hash --- change indicates changes in the build system). +-- TODO: Hash Target to improve accuracy and performance. +-- | Given a full target this Action determines the corresponding argument list +-- and computes its hash. The resulting value is tracked in a Shake oracle, +-- hence initiating rebuilds when the hash changes (a hash change indicates +-- changes in the build command for the given target). -- Note: we keep only the first target input for performance reasons -- to -- avoid storing long lists of source files passed to some builders (e.g. Ar) --- in the Shake database. This optimisation is harmless, because argument list --- constructors are assumed not to examine target sources, but only append them --- to argument lists where appropriate. --- TODO: enforce the above assumption via type trickery? --- TODO: Hash Target to improve accuracy and performance. +-- in the Shake database. This optimisation is normally harmless, because +-- argument list constructors are assumed not to examine target sources, but +-- only append them to argument lists where appropriate. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do let hashed = [ show . hash $ inputs target ] _ <- askOracle . ArgsHashKey $ target { inputs = hashed } :: Action Int return () --- Oracle for storing per-target argument list hashes +-- | Oracle for storing per-target argument list hashes. argsHashOracle :: Rules () argsHashOracle = void $ addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs From git at git.haskell.org Fri Oct 27 00:15:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create LICENSE (d12e733) Message-ID: <20171027001514.1774C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d12e733ba6fd831157ee436dbfac6e9f2aa8579a/ghc >--------------------------------------------------------------- commit d12e733ba6fd831157ee436dbfac6e9f2aa8579a Author: Andrey Mokhov Date: Wed Dec 23 12:42:57 2015 +0000 Create LICENSE >--------------------------------------------------------------- d12e733ba6fd831157ee436dbfac6e9f2aa8579a LICENSE | 27 +++++++++++++++++++++++++++ 1 file changed, 27 insertions(+) diff --git a/LICENSE b/LICENSE new file mode 100644 index 0000000..20d201e --- /dev/null +++ b/LICENSE @@ -0,0 +1,27 @@ +Copyright (c) 2015, Andrey Mokhov +All rights reserved. + +Redistribution and use in source and binary forms, with or without +modification, are permitted provided that the following conditions are met: + +* Redistributions of source code must retain the above copyright notice, this + list of conditions and the following disclaimer. + +* Redistributions in binary form must reproduce the above copyright notice, + this list of conditions and the following disclaimer in the documentation + and/or other materials provided with the distribution. + +* Neither the name of shaking-up-ghc nor the names of its + contributors may be used to endorse or promote products derived from + this software without specific prior written permission. + +THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" +AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE +DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE +FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. From git at git.haskell.org Fri Oct 27 00:15:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve the clean and rebuild section. (f6355ec) Message-ID: <20171027001514.7E9D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f6355ecd2d3cd047a0b550636dc9cf3f2924f9b2/ghc >--------------------------------------------------------------- commit f6355ecd2d3cd047a0b550636dc9cf3f2924f9b2 Author: Andrey Mokhov Date: Mon Jan 25 15:06:32 2016 +0000 Improve the clean and rebuild section. See #194. [skip ci] >--------------------------------------------------------------- f6355ecd2d3cd047a0b550636dc9cf3f2924f9b2 README.md | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/README.md b/README.md index 85b9cbe..057b864 100644 --- a/README.md +++ b/README.md @@ -69,12 +69,11 @@ The `make`-based build system uses `mk/build.mk` to specify user build settings. use [`src/Settings/User.hs`][user-settings] for the same purpose. Feel free to experiment following the Haddock comments. -#### Resetting the build +#### Clean and full rebuild -To reset the new build system run the build script with `-B` flag. This forces Shake -to rerun all rules, even if results of the previous build are still in the GHC tree. -To remove all build artefacts, run the build script with `clean` target. Note, we are -working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `shake-build/build.sh clean` removes all build artefacts. Note, we are working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. + +* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. Current limitations ------------------- From git at git.haskell.org Fri Oct 27 00:15:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependency (ba108c0) Message-ID: <20171027001516.5ED1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba108c0198cc3ee6cd758273f9bd8fea14ba93a5/ghc >--------------------------------------------------------------- commit ba108c0198cc3ee6cd758273f9bd8fea14ba93a5 Author: Andrey Mokhov Date: Thu May 19 23:50:46 2016 +0100 Add missing dependency See #241. >--------------------------------------------------------------- ba108c0198cc3ee6cd758273f9bd8fea14ba93a5 src/Rules/Library.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 3fff65f..a198c64 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -71,6 +71,7 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] gObjs = [ gmpObjects -/- "*.o" | package == integerGmp ] objs = cObjs ++ hObjs + when (package == integerGmp) $ orderOnly [gmpLibraryH] need objs build $ Target context Ld (objs ++ gObjs) [obj] From git at git.haskell.org Fri Oct 27 00:15:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename "shaking-up-ghc" to "Shaking up GHC" (02dfa6d) Message-ID: <20171027001518.052C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02dfa6dc8e89cf450baf01b4541ab33bbaffebda/ghc >--------------------------------------------------------------- commit 02dfa6dc8e89cf450baf01b4541ab33bbaffebda Author: Andrey Mokhov Date: Wed Dec 23 13:11:40 2015 +0000 Rename "shaking-up-ghc" to "Shaking up GHC" >--------------------------------------------------------------- 02dfa6dc8e89cf450baf01b4541ab33bbaffebda LICENSE | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/LICENSE b/LICENSE index 20d201e..a78df02 100644 --- a/LICENSE +++ b/LICENSE @@ -11,7 +11,7 @@ modification, are permitted provided that the following conditions are met: this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. -* Neither the name of shaking-up-ghc nor the names of its +* Neither the name of Shaking up GHC nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. From git at git.haskell.org Fri Oct 27 00:15:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note about interaction of the new and existing build systems. (92a3ffb) Message-ID: <20171027001518.6F5123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92a3ffba8b0f61ed772f942c16a3ca1a0495f1d8/ghc >--------------------------------------------------------------- commit 92a3ffba8b0f61ed772f942c16a3ca1a0495f1d8 Author: Andrey Mokhov Date: Tue Jan 26 20:02:05 2016 +0000 Add a note about interaction of the new and existing build systems. [skip ci] >--------------------------------------------------------------- 92a3ffba8b0f61ed772f942c16a3ca1a0495f1d8 README.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README.md b/README.md index 057b864..18ba8f6 100644 --- a/README.md +++ b/README.md @@ -9,6 +9,10 @@ on [Shake][shake] and we hope that it will eventually replace the current ideas behind the project you can find more details on the [wiki page][ghc-shake-wiki] and in this [blog post][blog-post-1]. +The new build system can work side-by-side with the existing build system. Note, there is +some interaction between them: they put (some) build results in the same directories, +e.g. `inplace/bin/ghc-stage1`. + [Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc). Your first build From git at git.haskell.org Fri Oct 27 00:15:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass GMP objects to Ld explicitly (aaead2a) Message-ID: <20171027001519.F411E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aaead2a5caa9fa96cc8a9f8a2762582bec70126f/ghc >--------------------------------------------------------------- commit aaead2a5caa9fa96cc8a9f8a2762582bec70126f Author: Andrey Mokhov Date: Fri May 20 00:23:50 2016 +0100 Pass GMP objects to Ld explicitly See #241. >--------------------------------------------------------------- aaead2a5caa9fa96cc8a9f8a2762582bec70126f src/Rules/Library.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index a198c64..2e59755 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -67,13 +67,12 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do cSrcs <- cSources context hSrcs <- hSources context + eObjs <- extraObjects context let cObjs = map (objFile context) cSrcs hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] - gObjs = [ gmpObjects -/- "*.o" | package == integerGmp ] - objs = cObjs ++ hObjs - when (package == integerGmp) $ orderOnly [gmpLibraryH] + objs = cObjs ++ hObjs ++ eObjs need objs - build $ Target context Ld (objs ++ gObjs) [obj] + build $ Target context Ld objs [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' From git at git.haskell.org Fri Oct 27 00:15:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make PackageName into a proper newtype (7e65227) Message-ID: <20171027001522.3AA7E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e6522794e13767080c1add1e304fce960f0e1cd/ghc >--------------------------------------------------------------- commit 7e6522794e13767080c1add1e304fce960f0e1cd Author: Ben Gamari Date: Fri Dec 18 18:05:20 2015 +0100 Make PackageName into a proper newtype >--------------------------------------------------------------- 7e6522794e13767080c1add1e304fce960f0e1cd src/GHC.hs | 7 ++++--- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Package.hs | 30 +++++++++++++++++++++--------- src/Rules/Cabal.hs | 12 ++++++------ src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 4 ++-- src/Settings/TargetDirectory.hs | 3 ++- 11 files changed, 42 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 7e6522794e13767080c1add1e304fce960f0e1cd From git at git.haskell.org Fri Oct 27 00:15:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Test to Selftest. (b06bae8) Message-ID: <20171027001522.602EB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b06bae88a40b7ee645b0aecda8019a601d567dce/ghc >--------------------------------------------------------------- commit b06bae88a40b7ee645b0aecda8019a601d567dce Author: Andrey Mokhov Date: Wed Jan 27 23:29:51 2016 +0000 Rename Test to Selftest. >--------------------------------------------------------------- b06bae88a40b7ee645b0aecda8019a601d567dce shaking-up-ghc.cabal | 2 +- src/Main.hs | 4 ++-- src/{Test.hs => Selftest.hs} | 6 +++--- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 674d6f0..60f3c34 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -65,6 +65,7 @@ executable ghc-shake , Rules.Resources , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg + , Selftest , Settings , Settings.Args , Settings.Builders.Alex @@ -104,7 +105,6 @@ executable ghc-shake , Settings.Ways , Stage , Target - , Test , Way default-language: Haskell2010 diff --git a/src/Main.hs b/src/Main.hs index 12ec014..befb6e7 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -14,7 +14,7 @@ import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl -import qualified Test +import qualified Selftest main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -37,7 +37,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do , Rules.Perl.perlScriptRules , Rules.generateTargets , Rules.packageRules - , Test.testRules ] + , Selftest.selftestRules ] options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Test.hs b/src/Selftest.hs similarity index 89% rename from src/Test.hs rename to src/Selftest.hs index 3c88ed4..4800ca8 100644 --- a/src/Test.hs +++ b/src/Selftest.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -module Test (testRules) where +module Selftest (selftestRules) where import Development.Shake import Settings.Builders.Ar (chunksOfSize) @@ -13,8 +13,8 @@ instance Arbitrary Way where instance Arbitrary WayUnit where arbitrary = arbitraryBoundedEnum -testRules :: Rules () -testRules = +selftestRules :: Rules () +selftestRules = "selftest" ~> do test $ \(x :: Way) -> read (show x) == x test $ \n xs -> From git at git.haskell.org Fri Oct 27 00:15:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on --progress-colour (ffcc3d9) Message-ID: <20171027001523.871303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffcc3d939e3854b8f7041814cb6d64761cf59822/ghc >--------------------------------------------------------------- commit ffcc3d939e3854b8f7041814cb6d64761cf59822 Author: Andrey Mokhov Date: Sat May 21 00:41:58 2016 +0100 Add a note on --progress-colour [skip ci] >--------------------------------------------------------------- ffcc3d939e3854b8f7041814cb6d64761cf59822 README.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/README.md b/README.md index fdbdbc5..9e7c6ca 100644 --- a/README.md +++ b/README.md @@ -58,6 +58,11 @@ profiling, which speeds up builds by 3-4x). * `--haddock`: build Haddock documentation. +* `--progress-colour=MODE`: choose whether to use colours when printing build progress +info. There are three settings: `never` (do not use colours), `auto` (attempt to detect +whether the console supports colours; this is the default setting), and `always` (use +colours). + * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). From git at git.haskell.org Fri Oct 27 00:15:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Parallelize+optimize compilation of build system (-j -O) (bfd3d32) Message-ID: <20171027001525.CD6983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bfd3d3240107fe70cc0ca806aafab1398c9e25ee/ghc >--------------------------------------------------------------- commit bfd3d3240107fe70cc0ca806aafab1398c9e25ee Author: David Luposchainsky Date: Tue Dec 22 08:54:35 2015 +0100 Parallelize+optimize compilation of build system (-j -O) >--------------------------------------------------------------- bfd3d3240107fe70cc0ca806aafab1398c9e25ee build.sh | 1 + 1 file changed, 1 insertion(+) diff --git a/build.sh b/build.sh index 1918cdd..f09c30c 100755 --- a/build.sh +++ b/build.sh @@ -13,6 +13,7 @@ ghc \ -rtsopts \ -with-rtsopts=-I0 \ -outputdir="$root/.shake" \ + -j -O \ -o "$root/.shake/build" "$root/.shake/build" \ From git at git.haskell.org Fri Oct 27 00:15:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add basic validation support (GHC tests). (e9abc61) Message-ID: <20171027001525.DED753A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101/ghc >--------------------------------------------------------------- commit e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101 Author: Andrey Mokhov Date: Thu Jan 28 02:51:12 2016 +0000 Add basic validation support (GHC tests). See #187. >--------------------------------------------------------------- e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101 shaking-up-ghc.cabal | 1 + src/Main.hs | 4 +++- src/Test.hs | 63 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 67 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 60f3c34..f00c7c6 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -105,6 +105,7 @@ executable ghc-shake , Settings.Ways , Stage , Target + , Test , Way default-language: Haskell2010 diff --git a/src/Main.hs b/src/Main.hs index befb6e7..2c944d4 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -15,6 +15,7 @@ import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl import qualified Selftest +import qualified Test main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -37,7 +38,8 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do , Rules.Perl.perlScriptRules , Rules.generateTargets , Rules.packageRules - , Selftest.selftestRules ] + , Selftest.selftestRules + , Test.testRules ] options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Test.hs b/src/Test.hs new file mode 100644 index 0000000..547e286 --- /dev/null +++ b/src/Test.hs @@ -0,0 +1,63 @@ +module Test (testRules) where + +import Base +import Builder +import Expression +import GHC (rts, libffi) +import Oracles.Config.Flag +import Oracles.Config.Setting +import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory +import Settings.Packages +import Settings.User + +-- TODO: clean up after testing +testRules :: Rules () +testRules = + "test" ~> do + let quote s = "\"" ++ s ++ "\"" + yesNo x = quote $ if x then "YES" else "NO" + pkgs <- interpretWithStage Stage1 getPackages + tests <- filterM doesDirectoryExist $ concat + [ [ pkgPath pkg -/- "tests", pkgPath pkg -/- "tests-ghc" ] + | pkg <- pkgs, isLibrary pkg, pkg /= rts, pkg /= libffi ] + windows <- windowsHost + top <- topDirectory + compiler <- builderPath $ Ghc Stage2 + ghcPkg <- builderPath $ GhcPkg Stage1 + haddock <- builderPath Haddock + threads <- shakeThreads <$> getShakeOptions + ghcWithNativeCodeGenInt <- fromEnum <$> ghcWithNativeCodeGen + ghcWithInterpreterInt <- fromEnum <$> ghcWithInterpreter + ghcUnregisterisedInt <- fromEnum <$> flag GhcUnregisterised + quietly . cmd "python2" $ + [ "testsuite/driver/runtests.py" ] + ++ map ("--rootdir="++) tests ++ + [ "-e", "windows=" ++ show windows + , "-e", "config.speed=2" + , "-e", "ghc_compiler_always_flags=" ++ quote "-fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts" + , "-e", "ghc_with_native_codegen=" ++ show ghcWithNativeCodeGenInt + , "-e", "ghc_debugged=" ++ yesNo ghcDebugged + , "-e", "ghc_with_vanilla=1" -- TODO: do we always build vanilla? + , "-e", "ghc_with_dynamic=0" -- TODO: support dynamic + , "-e", "ghc_with_profiling=0" -- TODO: support profiling + , "-e", "ghc_with_interpreter=" ++ show ghcWithInterpreterInt + , "-e", "ghc_unregisterised=" ++ show ghcUnregisterisedInt + , "-e", "ghc_with_threaded_rts=0" -- TODO: support threaded + , "-e", "ghc_with_dynamic_rts=0" -- TODO: support dynamic + , "-e", "ghc_dynamic_by_default=False" -- TODO: support dynamic + , "-e", "ghc_dynamic=0" -- TODO: support dynamic + , "-e", "ghc_with_llvm=0" -- TODO: support LLVM + , "-e", "in_tree_compiler=True" -- TODO: when is it equal to False? + , "-e", "clean_only=False" -- TODO: do we need to support True? + , "--configfile=testsuite/config/ghc" + , "--config", "compiler=" ++ quote (top -/- compiler) + , "--config", "ghc_pkg=" ++ quote (top -/- ghcPkg) + , "--config", "haddock=" ++ quote (top -/- haddock) + , "--summary-file", "testsuite_summary.txt" + , "--threads=" ++ show threads + ] + + -- , "--config", "hp2ps=" ++ quote ("hp2ps") + -- , "--config", "hpc=" ++ quote ("hpc") + -- , "--config", "gs=$(call quote_path,$(GS))" + -- , "--config", "timeout_prog=$(call quote_path,$(TIMEOUT_PROGRAM))" From git at git.haskell.org Fri Oct 27 00:15:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on --verbose (1054490) Message-ID: <20171027001527.0DB0E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/10544904eab3383c145c6904ad6d4bb19cc55329/ghc >--------------------------------------------------------------- commit 10544904eab3383c145c6904ad6d4bb19cc55329 Author: Andrey Mokhov Date: Sat May 21 00:48:01 2016 +0100 Add a note on --verbose [skip ci] >--------------------------------------------------------------- 10544904eab3383c145c6904ad6d4bb19cc55329 README.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/README.md b/README.md index 9e7c6ca..e4fb7dc 100644 --- a/README.md +++ b/README.md @@ -82,6 +82,9 @@ is your friend in such cases. * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. +* `--verbose`: run Hadrian in verbose mode. In particular this prints diagnostic messages +by Shake oracles. + #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We From git at git.haskell.org Fri Oct 27 00:15:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid common shell scripting pitfalls (828bc3a) Message-ID: <20171027001529.78A6C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/828bc3a27a26a02e1bad68ef0c25d7d3a1ce64fd/ghc >--------------------------------------------------------------- commit 828bc3a27a26a02e1bad68ef0c25d7d3a1ce64fd Author: David Luposchainsky Date: Mon Dec 21 13:46:03 2015 +0100 Avoid common shell scripting pitfalls - Get bash from $PATH instead of reading it from /bin/bash (useful for e.g. NixOS) - set -euo pipefail: "strict bash mode" - Quote all paths to be whitespace compatible - GHC uses --make mode automatically >--------------------------------------------------------------- 828bc3a27a26a02e1bad68ef0c25d7d3a1ce64fd build.sh | 26 +++++++++++++++++++++----- 1 file changed, 21 insertions(+), 5 deletions(-) diff --git a/build.sh b/build.sh index d350779..1918cdd 100755 --- a/build.sh +++ b/build.sh @@ -1,6 +1,22 @@ -#!/bin/bash -e +#!/usr/bin/env bash -root=`dirname $0` -mkdir -p $root/.shake -ghc --make -Wall $root/src/Main.hs -i$root/src -rtsopts -with-rtsopts=-I0 -outputdir=$root/.shake -o $root/.shake/build -$root/.shake/build --lint --directory $root/.. $@ +set -euo pipefail + +root="$(dirname "$0")" + +mkdir -p "$root/.shake" + +ghc \ + "$root/src/Main.hs" \ + -Wall \ + -i"$root/src" \ + -rtsopts \ + -with-rtsopts=-I0 \ + -outputdir="$root/.shake" \ + -o "$root/.shake/build" + +"$root/.shake/build" \ + --lint \ + --directory "$root/.." \ + --colour \ + "$@" From git at git.haskell.org Fri Oct 27 00:15:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add testing section (eee29dc) Message-ID: <20171027001529.ABC4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eee29dc165adceebda020444214e28d0d7456860/ghc >--------------------------------------------------------------- commit eee29dc165adceebda020444214e28d0d7456860 Author: Andrey Mokhov Date: Thu Jan 28 02:51:52 2016 +0000 Add testing section [skip ci] >--------------------------------------------------------------- eee29dc165adceebda020444214e28d0d7456860 README.md | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 18ba8f6..56e13ad 100644 --- a/README.md +++ b/README.md @@ -75,9 +75,19 @@ experiment following the Haddock comments. #### Clean and full rebuild -* `shake-build/build.sh clean` removes all build artefacts. Note, we are working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `shake-build/build.sh clean` removes all build artefacts. Note, we are working +towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. -* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. +* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of +the previous build are still in the GHC tree. + +#### Testing + +* `shake-build/build.sh test` runs GHC tests. The current implementation is very +limited and cannot replace the `validate` script (see [#187][validation-issue]). + +* `shake-build/build.sh selftest` runs tests of the build system. Current test +coverage is close to zero (see [#197][test-issue]). Current limitations ------------------- @@ -120,6 +130,7 @@ helped me endure and enjoy the project. [build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs +[test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 [profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 From git at git.haskell.org Fri Oct 27 00:15:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build check-api-annotations (5d2c1ee) Message-ID: <20171027001530.7E9433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d2c1eed519b6d90bcab8f993c428b265d4cb8fd/ghc >--------------------------------------------------------------- commit 5d2c1eed519b6d90bcab8f993c428b265d4cb8fd Author: Andrey Mokhov Date: Sat May 21 00:59:42 2016 +0100 Build check-api-annotations Fix #242. >--------------------------------------------------------------- 5d2c1eed519b6d90bcab8f993c428b265d4cb8fd src/GHC.hs | 137 ++++++++++++++++++++++++----------------------- src/Settings/Packages.hs | 2 +- 2 files changed, 70 insertions(+), 69 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 5d2c1eed519b6d90bcab8f993c428b265d4cb8fd From git at git.haskell.org Fri Oct 27 00:15:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Show simple shake progress and timings (0e19611) Message-ID: <20171027001533.4B40A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0e196114ceb61cfb03e24216203f868a10d294b9/ghc >--------------------------------------------------------------- commit 0e196114ceb61cfb03e24216203f868a10d294b9 Author: David Luposchainsky Date: Mon Dec 21 14:15:16 2015 +0100 Show simple shake progress and timings >--------------------------------------------------------------- 0e196114ceb61cfb03e24216203f868a10d294b9 src/Main.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index aae1d5e..7a0205d 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -5,9 +5,14 @@ import Rules.Config import Rules.Oracles main :: IO () -main = shakeArgs shakeOptions { shakeFiles = shakeFilesPath } $ do +main = shakeArgs options $ do generateTargets -- see Rules packageRules -- see Rules cabalRules -- see Rules.Cabal configRules -- see Rules.Config oracleRules -- see Rules.Oracles + where + options = shakeOptions + { shakeFiles = shakeFilesPath + , shakeProgress = progressSimple + , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:15:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use libHS*_thr.a instead of libHS*.thr_a naming convention for libraries. (c760627) Message-ID: <20171027001533.78D563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7606279a186f145d5e7751f65be8c2be8aefb80/ghc >--------------------------------------------------------------- commit c7606279a186f145d5e7751f65be8c2be8aefb80 Author: Andrey Mokhov Date: Fri Jan 29 01:05:48 2016 +0000 Use libHS*_thr.a instead of libHS*.thr_a naming convention for libraries. See #98. >--------------------------------------------------------------- c7606279a186f145d5e7751f65be8c2be8aefb80 src/Rules/Library.hs | 2 +- src/Settings/Paths.hs | 2 +- src/Way.hs | 14 ++++++++------ 3 files changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b53c472..2cde962 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -46,7 +46,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do let objs = cObjs ++ splitObjs ++ eObjs asuf <- libsuf way - let isLib0 = ("//*-0" <.> asuf) ?== a + let isLib0 = ("//*-0" ++ asuf) ?== a if isLib0 then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls else build $ fullTarget target Ar objs [a] diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index ed217a8..a152f9a 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -29,7 +29,7 @@ pkgLibraryFile :: Stage -> Package -> String -> Way -> Action FilePath pkgLibraryFile stage pkg componentId way = do extension <- libsuf way let buildPath = targetPath stage pkg -/- "build" - return $ buildPath -/- "libHS" ++ componentId <.> extension + return $ buildPath -/- "libHS" ++ componentId ++ extension -- Relative path to a package ghci library file, e.g.: -- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" diff --git a/src/Way.hs b/src/Way.hs index 8923571..da986a8 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -127,6 +127,10 @@ wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" +waySuffix :: Way -> String +waySuffix way | way == vanilla = "" + | otherwise = "_" ++ show way + osuf, ssuf, hisuf, hcsuf, obootsuf, hibootsuf :: Way -> String osuf = (++ "o" ) . wayPrefix ssuf = (++ "s" ) . wayPrefix @@ -135,10 +139,6 @@ hcsuf = (++ "hc" ) . wayPrefix obootsuf = (++ "o-boot" ) . wayPrefix hibootsuf = (++ "hi-boot") . wayPrefix --- Note: in the previous build system libsuf was mysteriously different --- from other suffixes. For example, in the profiling way it used to be --- "_p.a" instead of ".p_a" which is how other suffixes work. I decided --- to make all suffixes consistent: ".way_extension". -- TODO: find out why we need version number in the dynamic suffix -- The current theory: dynamic libraries are eventually placed in a single -- giant directory in the load path of the dynamic linker, and hence we must @@ -148,7 +148,7 @@ hibootsuf = (++ "hi-boot") . wayPrefix libsuf :: Way -> Action String libsuf way @ (Way set) = if (not . wayUnit Dynamic $ way) - then return $ wayPrefix way ++ "a" -- e.g., p_a + then return $ waySuffix way ++ ".a" -- e.g., _p.a else do extension <- setting DynamicExtension -- e.g., .dll or .so version <- setting ProjectVersion -- e.g., 7.11.20141222 @@ -172,7 +172,9 @@ safeDetectWay file = case reads prefix of then extension else takeExtension . dropExtension . dropExtension . dropExtension $ file - prefix = drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed + prefix = if extension == "a" + then drop 1 . dropWhile (/= '_') $ takeBaseName file + else drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed -- Unsafe version of safeDetectWay. Useful when matchBuildResult has succeeded. detectWay :: FilePath -> Way From git at git.haskell.org Fri Oct 27 00:15:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing dependencies for Stage2 packages (2c74f92) Message-ID: <20171027001534.347DF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c74f92cc3db93f71f294e4f0797a1866950467c/ghc >--------------------------------------------------------------- commit 2c74f92cc3db93f71f294e4f0797a1866950467c Author: Andrey Mokhov Date: Sat May 21 02:23:31 2016 +0100 Fix missing dependencies for Stage2 packages Fix #240. >--------------------------------------------------------------- 2c74f92cc3db93f71f294e4f0797a1866950467c src/Rules/Cabal.hs | 2 +- src/Rules/Data.hs | 6 ++++-- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 05078fc..82edb3a 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -28,7 +28,7 @@ cabalRules = do -- Cache package dependencies packageDependencies %> \out -> do - pkgs <- interpretInContext (stageContext Stage1) getPackages + let pkgs = knownPackages \\ [hp2ps, libffi, touchy, unlit] pkgDeps <- forM (sort pkgs) $ \pkg -> if pkg == rts then return $ pkgNameString pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 8512c3a..2ecfb37 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -31,10 +31,12 @@ buildPackageData context at Context {..} = do whenM (doesFileExist $ configure <.> "ac") $ need [configure] -- Before we configure a package its dependencies need to be registered + let depStage = min stage Stage1 -- dependencies come from Stage0/1 + depContext = vanillaContext depStage deps <- packageDeps package - pkgs <- interpretInContext context getPackages + pkgs <- interpretInContext (depContext package) getPackages let depPkgs = matchPackageNames (sort pkgs) deps - need =<< traverse (pkgConfFile . vanillaContext stage) depPkgs + need =<< traverse (pkgConfFile . depContext) depPkgs need [cabalFile] build $ Target context GhcCabal [cabalFile] [mk] From git at git.haskell.org Fri Oct 27 00:15:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #17 from bgamari/types (3783b0d) Message-ID: <20171027001537.3D69F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3783b0d0eab89fdbc0b6ec4dd2ba78423fc79dc1/ghc >--------------------------------------------------------------- commit 3783b0d0eab89fdbc0b6ec4dd2ba78423fc79dc1 Merge: 02dfa6d 7e65227 Author: Andrey Mokhov Date: Wed Dec 23 20:06:00 2015 +0000 Merge pull request #17 from bgamari/types [WIP] Make better use of types >--------------------------------------------------------------- 3783b0d0eab89fdbc0b6ec4dd2ba78423fc79dc1 src/GHC.hs | 7 ++++--- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Package.hs | 30 +++++++++++++++++++++--------- src/Rules/Cabal.hs | 12 ++++++------ src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 4 ++-- src/Settings/TargetDirectory.hs | 3 ++- 11 files changed, 42 insertions(+), 28 deletions(-) From git at git.haskell.org Fri Oct 27 00:15:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a rule to build gmpLibraryInTreeH. (3b0fdab) Message-ID: <20171027001537.7AFED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b0fdab49988b9f1981e238c903a08fd75419cc3/ghc >--------------------------------------------------------------- commit 3b0fdab49988b9f1981e238c903a08fd75419cc3 Author: Andrey Mokhov Date: Fri Jan 29 01:06:24 2016 +0000 Add a rule to build gmpLibraryInTreeH. >--------------------------------------------------------------- 3b0fdab49988b9f1981e238c903a08fd75419cc3 src/Rules/Gmp.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index b384b68..ab25495 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -144,3 +144,5 @@ gmpRules = do runBuilder Ranlib [gmpLibrary] putSuccess "| Successfully built custom library 'gmp'" + + gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] From git at git.haskell.org Fri Oct 27 00:15:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor dependency oracles (b6f224c) Message-ID: <20171027001537.EA0D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6f224c4535039fb77fd31e8229917ee4267f16f/ghc >--------------------------------------------------------------- commit b6f224c4535039fb77fd31e8229917ee4267f16f Author: Andrey Mokhov Date: Sun May 22 00:02:50 2016 +0100 Refactor dependency oracles >--------------------------------------------------------------- b6f224c4535039fb77fd31e8229917ee4267f16f hadrian.cabal | 1 - src/Oracles/Config.hs | 2 +- src/Oracles/Config/Flag.hs | 5 +- src/Oracles/Config/Setting.hs | 31 +++++----- src/Oracles/Dependencies.hs | 102 +++++++++++++++++++++++-------- src/Oracles/LookupInPath.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/PackageDeps.hs | 30 --------- src/Oracles/WindowsPath.hs | 7 +-- src/Package.hs | 35 ++++------- src/Rules/Cabal.hs | 9 ++- src/Rules/Compile.hs | 15 +++-- src/Rules/Data.hs | 29 ++++----- src/Rules/Generators/GhcBootPlatformH.hs | 1 - src/Rules/Generators/GhcPlatformH.hs | 1 - src/Rules/Generators/VersionHs.hs | 1 - src/Rules/Oracles.hs | 4 +- src/Rules/Program.hs | 56 +++++++---------- src/Rules/Register.hs | 2 +- src/Settings/Builders/Ghc.hs | 16 ++--- src/Settings/Builders/GhcCabal.hs | 14 ++--- src/Settings/Paths.hs | 6 +- 22 files changed, 175 insertions(+), 196 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b6f224c4535039fb77fd31e8229917ee4267f16f From git at git.haskell.org Fri Oct 27 00:15:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #29 from quchen/script-refactoring (f354291) Message-ID: <20171027001540.EB9313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f354291e941d1653bb8d3ae6825f588e82372b0a/ghc >--------------------------------------------------------------- commit f354291e941d1653bb8d3ae6825f588e82372b0a Merge: 3783b0d bfd3d32 Author: Andrey Mokhov Date: Wed Dec 23 20:14:46 2015 +0000 Merge pull request #29 from quchen/script-refactoring Show Shake statistics, refactor direct Linux build script >--------------------------------------------------------------- f354291e941d1653bb8d3ae6825f588e82372b0a build.sh | 27 ++++++++++++++++++++++----- src/Main.hs | 7 ++++++- 2 files changed, 28 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 00:15:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a target for threaded rts library. (8f9dd7e) Message-ID: <20171027001541.5FBB93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f9dd7ed189b075faecea5224fb147b7743b16f7/ghc >--------------------------------------------------------------- commit 8f9dd7ed189b075faecea5224fb147b7743b16f7 Author: Andrey Mokhov Date: Fri Jan 29 01:07:11 2016 +0000 Add a target for threaded rts library. See #98. >--------------------------------------------------------------- 8f9dd7ed189b075faecea5224fb147b7743b16f7 src/Rules.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 31489f3..5f505b3 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -15,9 +15,10 @@ allStages = [minBound ..] -- | 'need' all top-level build targets generateTargets :: Rules () generateTargets = action $ do - targets <- fmap concat (traverse targetsForStage allStages) - rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla - need $ targets ++ installTargets ++ [ rtsLib ] + targets <- fmap concat (traverse targetsForStage allStages) + rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla + rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded + need $ targets ++ installTargets ++ [ rtsLib, rtsThrLib ] targetsForStage :: Stage -> Action [String] targetsForStage stage = do From git at git.haskell.org Fri Oct 27 00:15:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop orderOnly dependency on GMP objects (19293d9) Message-ID: <20171027001541.C78E93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/19293d92469d2c80e125f62d527407ea0ac5fe4e/ghc >--------------------------------------------------------------- commit 19293d92469d2c80e125f62d527407ea0ac5fe4e Author: Andrey Mokhov Date: Sun May 22 01:19:16 2016 +0100 Drop orderOnly dependency on GMP objects >--------------------------------------------------------------- 19293d92469d2c80e125f62d527407ea0ac5fe4e src/Rules/Gmp.hs | 2 +- src/Rules/Library.hs | 12 ++++++------ 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 845ba6e..f761639 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,4 +1,4 @@ -module Rules.Gmp (gmpRules) where +module Rules.Gmp (gmpRules, gmpContext) where import Base import Builder diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 2e59755..edbdb52 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -8,9 +8,9 @@ import qualified System.Directory as IO import Base import Context import Expression -import GHC import Oracles.PackageData import Rules.Actions +import Rules.Gmp import Settings import Target @@ -75,7 +75,7 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do build $ Target context Ld objs [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. --- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' +-- | Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' -- to its object file. For example, in Context Stage1 rts threaded: -- * "Task.c" -> "_build/stage1/rts/Task.thr_o" -- * "_build/stage1/rts/sm/Evac_thr.c" -> "_build/stage1/rts/sm/Evac_thr.thr_o" @@ -90,12 +90,12 @@ cSources context = interpretInContext context $ getPkgDataList CSrcs hSources :: Context -> Action [FilePath] hSources context = do modules <- interpretInContext context $ getPkgDataList Modules - -- GHC.Prim is special: we do not build it + -- GHC.Prim is special: we do not build it. return . map (replaceEq '.' '/') . filter (/= "GHC.Prim") $ modules extraObjects :: Context -> Action [FilePath] -extraObjects (Context _ package _) - | package == integerGmp = do - orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? +extraObjects context + | context == gmpContext = do + need [gmpLibraryH] -- TODO: Move this dependency elsewhere, #113? map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:15:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix haddockArgs, clean up code. (1c8a0e7) Message-ID: <20171027001544.B1D8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c8a0e7aa5f3a11561bdb3b45426f319c83291a8/ghc >--------------------------------------------------------------- commit 1c8a0e7aa5f3a11561bdb3b45426f319c83291a8 Author: Andrey Mokhov Date: Thu Dec 24 01:28:50 2015 +0000 Fix haddockArgs, clean up code. >--------------------------------------------------------------- 1c8a0e7aa5f3a11561bdb3b45426f319c83291a8 src/Base.hs | 10 ++++++++-- src/Package.hs | 7 +++---- src/Rules/Cabal.hs | 3 +-- src/Settings/Builders/Haddock.hs | 4 +++- 4 files changed, 15 insertions(+), 9 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 79ce119..7730bf5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -26,7 +26,7 @@ module Base ( -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, removeFileIfExists, replaceEq, chunksOfSize, - replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-) + replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt ) where import Control.Applicative @@ -37,7 +37,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>), parallel) +import Development.Shake hiding (unit, (*>)) import Development.Shake.Classes import Development.Shake.Config import Development.Shake.FilePath @@ -77,6 +77,12 @@ replaceSeparators = replaceIf isPathSeparator replaceIf :: (a -> Bool) -> a -> [a] -> [a] replaceIf p to = map (\from -> if p from then to else from) +-- | Given a version string such as "2.16.2" produce an integer equivalent +versionToInt :: String -> Int +versionToInt s = major * 1000 + minor * 10 + patch + where + [major, minor, patch] = map read . words $ replaceEq '.' ' ' s + -- | Given a module name extract the directory and file name, e.g.: -- -- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") diff --git a/src/Package.hs b/src/Package.hs index a956c6a..536a16f39 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,8 +1,7 @@ -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving, DeriveDataTypeable #-} module Package ( - Package (..), PackageName(..), PackageType (..), + Package (..), PackageName (..), PackageType (..), -- * Queries pkgNameString, pkgCabalFile, @@ -18,7 +17,7 @@ import Data.String -- | The name of a Cabal package newtype PackageName = PackageName { getPackageName :: String } deriving ( Eq, Ord, IsString, Generic, Binary, Hashable - , NFData) + , Typeable, NFData) instance Show PackageName where show (PackageName name) = name diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 74a2468..ce52388 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,13 +1,12 @@ module Rules.Cabal (cabalRules) where import Data.Version -import Distribution.Package as DP hiding (Package) +import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Verbosity import Expression import GHC -import Package hiding (library) import Settings cabalRules :: Rules () diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 4cc8683..0663d04 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -16,6 +16,7 @@ haddockArgs = builder Haddock ? do hidden <- getPkgDataList HiddenModules deps <- getPkgDataList Deps depNames <- getPkgDataList DepNames + hVersion <- lift . pkgData . Version $ targetPath Stage2 haddock ghcOpts <- fromDiffExpr commonGhcArgs mconcat [ arg $ "--odir=" ++ takeDirectory output @@ -26,6 +27,7 @@ haddockArgs = builder Haddock ? do , arg "--hoogle" , arg $ "--title=" ++ pkgNameString pkg ++ "-" ++ version ++ ": " ++ synopsis , arg $ "--prologue=" ++ path -/- "haddock-prologue.txt" + , arg $ "--optghc=-D__HADDOCK_VERSION__=" ++ show (versionToInt hVersion) , append $ map ("--hide=" ++) hidden , append $ [ "--read-interface=../" ++ dep ++ ",../" ++ dep ++ "/src/%{MODULE/./-}.html\\#%{NAME}," @@ -40,7 +42,7 @@ haddockArgs = builder Haddock ? do , customPackageArgs , append =<< getInputs , arg "+RTS" - , arg $ "-t" ++ path "haddock.t" + , arg $ "-t" ++ path -/- "haddock.t" , arg "--machine-readable" ] customPackageArgs :: Args From git at git.haskell.org Fri Oct 27 00:15:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build hpc-bin. (0c06eac) Message-ID: <20171027001545.566233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c06eaca884d2e2606cc7ccb0726fdb520164b5d/ghc >--------------------------------------------------------------- commit 0c06eaca884d2e2606cc7ccb0726fdb520164b5d Author: Andrey Mokhov Date: Fri Jan 29 01:07:51 2016 +0000 Build hpc-bin. See #187. >--------------------------------------------------------------- 0c06eaca884d2e2606cc7ccb0726fdb520164b5d src/Builder.hs | 2 ++ src/GHC.hs | 3 +++ 2 files changed, 5 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index bfb757f..71399a7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -36,6 +36,7 @@ data Builder = Alex | GhcPkg Stage | Haddock | Happy + | Hpc | HsColour | HsCpp | Hsc2Hs @@ -63,6 +64,7 @@ builderProvenance = \case GhcCabalHsColour -> builderProvenance $ GhcCabal GhcPkg stage -> if stage > Stage0 then Just (Stage0, ghcPkg) else Nothing Haddock -> Just (Stage2, haddock) + Hpc -> Just (Stage1, hpcBin) Hsc2Hs -> Just (Stage0, hsc2hs) Unlit -> Just (Stage0, unlit) _ -> Nothing diff --git a/src/GHC.hs b/src/GHC.hs index 7504c27..0262243 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -112,6 +112,9 @@ programPath stage pkg | pkg `elem` [touchy, unlit] = case stage of Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe _ -> Nothing + | pkg == hpcBin = case stage of + Stage1 -> Just $ inplaceProgram "hpc" + _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg From git at git.haskell.org Fri Oct 27 00:15:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run Make builder with -jN using N = shakeThreads (3de1a5a) Message-ID: <20171027001545.D6C343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3de1a5a65b7d97635ccd9a14601113b0802cd8f7/ghc >--------------------------------------------------------------- commit 3de1a5a65b7d97635ccd9a14601113b0802cd8f7 Author: Andrey Mokhov Date: Sun May 22 01:22:19 2016 +0100 Run Make builder with -jN using N = shakeThreads >--------------------------------------------------------------- 3de1a5a65b7d97635ccd9a14601113b0802cd8f7 src/Settings/Builders/Make.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index 6968cd0..3d06775 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -1,10 +1,14 @@ module Settings.Builders.Make (makeBuilderArgs) where +import Base import Predicate import Settings makeBuilderArgs :: Args -makeBuilderArgs = mconcat - [ builder (Make gmpBuildPath ) ? arg "MAKEFLAGS=" - , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=", "install"] - , builder (Make "testsuite/tests") ? arg "fast" ] +makeBuilderArgs = do + threads <- shakeThreads <$> lift getShakeOptions + let j = "-j" ++ show threads + mconcat + [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=" ++ j] + , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=" ++ j, "install"] + , builder (Make "testsuite/tests") ? arg "fast" ] From git at git.haskell.org Fri Oct 27 00:15:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (95d594c) Message-ID: <20171027001548.1E7A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95d594c1836993c98fea985f475df4bbc959fa38/ghc >--------------------------------------------------------------- commit 95d594c1836993c98fea985f475df4bbc959fa38 Author: Andrey Mokhov Date: Thu Dec 24 02:51:44 2015 +0000 Clean up. >--------------------------------------------------------------- 95d594c1836993c98fea985f475df4bbc959fa38 src/Package.hs | 6 ++---- src/Settings/Packages.hs | 6 ++++-- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 536a16f39..9a64fa8 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -16,8 +16,7 @@ import Data.String -- | The name of a Cabal package newtype PackageName = PackageName { getPackageName :: String } - deriving ( Eq, Ord, IsString, Generic, Binary, Hashable - , Typeable, NFData) + deriving (Eq, Ord, IsString, Generic, Binary, Hashable, Typeable, NFData) instance Show PackageName where show (PackageName name) = name @@ -25,8 +24,7 @@ instance Show PackageName where -- | We regard packages as either being libraries or programs. This is -- bit of a convenient lie as Cabal packages can be both, but it works -- for now. -data PackageType = Program | Library - deriving Generic +data PackageType = Program | Library deriving Generic data Package = Package { diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index ee37b07..32d12a5 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -20,10 +20,10 @@ packagesStage0 :: Packages packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] + -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] --- TODO: what do we do with parallel, stm, random, primitive, vector and dph? packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 @@ -35,7 +35,7 @@ packagesStage1 = mconcat , notM windowsHost ? append [iservBin] , buildHaddock ? append [xhtml] ] --- TODO: currently there is an unchecked assumption that we only build programs +-- TODO: currently there is an unchecked assumption that we build only programs -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages packagesStage2 = mconcat @@ -43,9 +43,11 @@ packagesStage2 = mconcat , buildHaddock ? append [haddock] ] -- TODO: switch to Set Package as the order of packages should not matter? +-- Otherwise we have to keep remembering to sort packages from time to time. knownPackages :: [Package] knownPackages = sort $ defaultKnownPackages ++ userKnownPackages -- Note: this is slow but we keep it simple as there are just ~50 packages +-- TODO: speed up? findKnownPackage :: PackageName -> Maybe Package findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages From git at git.haskell.org Fri Oct 27 00:15:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add validate target. (a9f9876) Message-ID: <20171027001548.C3F193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9f98769fbd07b93342cd263f6dcf3c6e51e4afd/ghc >--------------------------------------------------------------- commit a9f98769fbd07b93342cd263f6dcf3c6e51e4afd Author: Andrey Mokhov Date: Fri Jan 29 01:18:51 2016 +0000 Add validate target. See #187. >--------------------------------------------------------------- a9f98769fbd07b93342cd263f6dcf3c6e51e4afd src/Rules/Actions.hs | 16 ++++++++++++---- src/Test.hs | 6 +++++- 2 files changed, 17 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 0e4961f..d85e0dc 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,8 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, - moveDirectory, fixFile, runConfigure, runMake, applyPatch, renderLibrary, - renderProgram, runBuilder, makeExecutable + moveDirectory, fixFile, runConfigure, runMake, runMakeVerbose, applyPatch, + renderLibrary, renderProgram, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -111,7 +111,13 @@ runConfigure dir opts args = do opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] runMake :: FilePath -> [String] -> Action () -runMake dir args = do +runMake = runMakeWithVerbosity False + +runMakeVerbose :: FilePath -> [String] -> Action () +runMakeVerbose = runMakeWithVerbosity True + +runMakeWithVerbosity :: Bool -> FilePath -> [String] -> Action () +runMakeWithVerbosity verbose dir args = do need [dir -/- "Makefile"] path <- builderPath Make @@ -125,7 +131,9 @@ runMake dir args = do let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ fixPath ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args + if verbose + then cmd Shell fixPath ["-C", dir] args + else quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do diff --git a/src/Test.hs b/src/Test.hs index 547e286..06c82eb 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -7,12 +7,16 @@ import GHC (rts, libffi) import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory +import Rules.Actions import Settings.Packages import Settings.User -- TODO: clean up after testing testRules :: Rules () -testRules = +testRules = do + "validate" ~> do + runMakeVerbose "testsuite/tests" ["fast"] + "test" ~> do let quote s = "\"" ++ s ++ "\"" yesNo x = quote $ if x then "YES" else "NO" From git at git.haskell.org Fri Oct 27 00:15:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove runghcid.bat. (920b393) Message-ID: <20171027001552.5405F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/920b3938e452548bdf1d9e24ef7e1971acb1c76e/ghc >--------------------------------------------------------------- commit 920b3938e452548bdf1d9e24ef7e1971acb1c76e Author: Andrey Mokhov Date: Thu Dec 24 03:28:07 2015 +0000 Remove runghcid.bat. >--------------------------------------------------------------- 920b3938e452548bdf1d9e24ef7e1971acb1c76e runghcid.bat | 1 - 1 file changed, 1 deletion(-) diff --git a/runghcid.bat b/runghcid.bat deleted file mode 100644 index f2f8ddc..0000000 --- a/runghcid.bat +++ /dev/null @@ -1 +0,0 @@ -ghcid --height=8 --topmost "--command=ghci -isrc -Wall src/Main.hs" From git at git.haskell.org Fri Oct 27 00:15:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on Stage2 GHC, ghc-pkg and hpc in validate target. (304840f) Message-ID: <20171027001553.123703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/304840f8073ef7b3369601a97afb0605326e79e3/ghc >--------------------------------------------------------------- commit 304840f8073ef7b3369601a97afb0605326e79e3 Author: Andrey Mokhov Date: Sat Jan 30 23:58:57 2016 +0000 Depend on Stage2 GHC, ghc-pkg and hpc in validate target. See #187. [skip ci] >--------------------------------------------------------------- 304840f8073ef7b3369601a97afb0605326e79e3 src/Builder.hs | 2 ++ src/Test.hs | 3 +++ 2 files changed, 5 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 71399a7..80fc4ba 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -124,6 +124,8 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath +-- TODO: split into two functions: needBuilder (without laxDependencies) and +-- unsafeNeedBuilder (with the laxDependencies parameter) -- | Make sure a builder exists on the given path and rebuild it if out of date. -- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). diff --git a/src/Test.hs b/src/Test.hs index 06c82eb..a79c9fc 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -15,6 +15,9 @@ import Settings.User testRules :: Rules () testRules = do "validate" ~> do + needBuilder False $ Ghc Stage2 -- TODO: get rid of False parameters + needBuilder False $ GhcPkg Stage1 + needBuilder False $ Hpc runMakeVerbose "testsuite/tests" ["fast"] "test" ~> do From git at git.haskell.org Fri Oct 27 00:15:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop TransitiveDepNames (97d37ea) Message-ID: <20171027001549.56CB33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9/ghc >--------------------------------------------------------------- commit 97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9 Author: Andrey Mokhov Date: Sun May 22 01:46:39 2016 +0100 Drop TransitiveDepNames >--------------------------------------------------------------- 97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9 src/Oracles/PackageData.hs | 10 +++------- 1 file changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index af9e255..92c2e99 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,7 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( - PackageData (..), PackageDataList (..), - pkgData, pkgDataList, packageDataOracle + PackageData (..), PackageDataList (..), pkgData, pkgDataList, packageDataOracle ) where import Development.Shake.Config @@ -31,7 +30,6 @@ data PackageDataList = CcArgs FilePath | LdArgs FilePath | Modules FilePath | SrcDirs FilePath - | TransitiveDepNames FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -77,16 +75,14 @@ pkgDataList packageData = fmap (map unquote . words) $ case packageData of LdArgs path -> askPackageData path "LD_OPTS" Modules path -> askPackageData path "MODULES" SrcDirs path -> askPackageData path "HS_SRC_DIRS" - TransitiveDepNames path -> askPackageData path "TRANSITIVE_DEP_NAMES" where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') -- | Oracle for 'package-data.mk' files. packageDataOracle :: Rules () -packageDataOracle = do +packageDataOracle = void $ do keys <- newCache $ \file -> do need [file] putLoud $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - _ <- addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file - return () + addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file From git at git.haskell.org Fri Oct 27 00:15:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename PackageDb to PackageDatabase (026466a) Message-ID: <20171027001553.6A76E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/026466ad55688891c0e82b5de98f555dc6932223/ghc >--------------------------------------------------------------- commit 026466ad55688891c0e82b5de98f555dc6932223 Author: Andrey Mokhov Date: Sun May 22 01:48:07 2016 +0100 Rename PackageDb to PackageDatabase >--------------------------------------------------------------- 026466ad55688891c0e82b5de98f555dc6932223 hadrian.cabal | 2 +- src/Oracles/{PackageDb.hs => PackageDatabase.hs} | 8 ++++---- src/Rules/Oracles.hs | 8 ++++---- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 20 ++++++++++---------- src/Settings/Builders/GhcPkg.hs | 4 ++-- 6 files changed, 22 insertions(+), 22 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index a65bbf8..95ae3a0 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -32,7 +32,7 @@ executable hadrian , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData - , Oracles.PackageDb + , Oracles.PackageDatabase , Oracles.WindowsPath , Package , Predicate diff --git a/src/Oracles/PackageDb.hs b/src/Oracles/PackageDatabase.hs similarity index 74% rename from src/Oracles/PackageDb.hs rename to src/Oracles/PackageDatabase.hs index 61b134a..f89a2cc 100644 --- a/src/Oracles/PackageDb.hs +++ b/src/Oracles/PackageDatabase.hs @@ -1,4 +1,4 @@ -module Oracles.PackageDb (packageDbOracle) where +module Oracles.PackageDatabase (packageDatabaseOracle) where import qualified System.Directory as IO @@ -12,9 +12,9 @@ import Settings.Paths import Settings.User import Target -packageDbOracle :: Rules () -packageDbOracle = void $ - addOracle $ \(PackageDbKey stage) -> do +packageDatabaseOracle :: Rules () +packageDatabaseOracle = void $ + addOracle $ \(PackageDatabaseKey stage) -> do let dir = packageDbDirectory stage file = dir -/- "package.cache" unlessM (liftIO $ IO.doesFileExist file) $ do diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 93bccfc..7beb67f 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -1,14 +1,14 @@ module Rules.Oracles (oracleRules) where import Base +import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies import qualified Oracles.LookupInPath +import qualified Oracles.ModuleFiles import qualified Oracles.PackageData +import qualified Oracles.PackageDatabase import qualified Oracles.WindowsPath -import qualified Oracles.ArgsHash -import qualified Oracles.ModuleFiles -import qualified Oracles.PackageDb oracleRules :: Rules () oracleRules = do @@ -18,5 +18,5 @@ oracleRules = do Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle - Oracles.PackageDb.packageDbOracle + Oracles.PackageDatabase.packageDatabaseOracle Oracles.WindowsPath.windowsPathOracle diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 02ffe4d..9b1430d 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -118,7 +118,7 @@ packageGhcArgs = do return $ if not0 || unit then "-this-unit-id " else "-this-package-key " mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" - , bootPackageDbArgs + , bootPackageDatabaseArgs , isLibrary pkg ? arg (thisArg ++ compId) , append $ map ("-package-id " ++) pkgDepIds ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index beaa8c7..396e69b 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,7 +1,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( - ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDbArgs, - PackageDbKey (..), cppArgs, buildDll0 + ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, + PackageDatabaseKey (..), cppArgs, buildDll0 ) where import Base @@ -23,7 +23,7 @@ ghcCabalBuilderArgs = builder GhcCabal ? do , dll0Args , withStaged $ Ghc Compile , withStaged GhcPkg - , bootPackageDbArgs + , bootPackageDatabaseArgs , libraryArgs , with HsColour , configureArgs @@ -81,16 +81,16 @@ configureArgs = do , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" $ argStagedBuilderPath (Cc Compile) ] -newtype PackageDbKey = PackageDbKey Stage - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +newtype PackageDatabaseKey = PackageDatabaseKey Stage + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -initialisePackageDb :: Stage -> Action () -initialisePackageDb stage = askOracle $ PackageDbKey stage +initialisePackageDatabase :: Stage -> Action () +initialisePackageDatabase = askOracle . PackageDatabaseKey -bootPackageDbArgs :: Args -bootPackageDbArgs = do +bootPackageDatabaseArgs :: Args +bootPackageDatabaseArgs = do stage <- getStage - lift $ initialisePackageDb stage + lift $ initialisePackageDatabase stage stage0 ? do path <- getTopDirectory prefix <- ifM (builder Ghc) (return "-package-db ") (return "--package-db=") diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index ba176ac..d6efd0b 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -14,12 +14,12 @@ initPredicate = orM $ map (output . packageDbDirectory) [Stage0 ..] initArgs :: Args initArgs = initPredicate ? mconcat [ arg "init", arg =<< getOutput ] --- TODO: move inplace-pkg-config to buildRootPath, see #113. +-- TODO: Move inplace-pkg-config to buildRootPath, see #113. updateArgs :: Args updateArgs = notM initPredicate ? do pkg <- getPackage dir <- getContextDirectory mconcat [ arg "update" , arg "--force" - , bootPackageDbArgs + , bootPackageDatabaseArgs , arg $ pkgPath pkg -/- dir -/- "inplace-pkg-config" ] From git at git.haskell.org Fri Oct 27 00:15:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split the batch file into multiple lines, add missing flags (-j -O). (5bb30bc) Message-ID: <20171027001555.C49723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5bb30bc25f693652432ff72150a40ceb558f36e3/ghc >--------------------------------------------------------------- commit 5bb30bc25f693652432ff72150a40ceb558f36e3 Author: Andrey Mokhov Date: Thu Dec 24 03:29:32 2015 +0000 Split the batch file into multiple lines, add missing flags (-j -O). >--------------------------------------------------------------- 5bb30bc25f693652432ff72150a40ceb558f36e3 build.bat | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/build.bat b/build.bat index ab26e07..a4e2548 100644 --- a/build.bat +++ b/build.bat @@ -1,2 +1,19 @@ @mkdir .shake 2> nul - at ghc --make -Wall src/Main.hs -isrc -rtsopts -with-rtsopts=-I0 -outputdir=.shake -o .shake/build && .shake\build --lint --directory ".." %* + + at set ghcArgs=--make ^ + -Wall ^ + src/Main.hs ^ + -isrc ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=.shake ^ + -j ^ + -O ^ + -o .shake/build + + at set shakeArgs=--lint ^ + --directory ^ + ".." ^ + %* + + at ghc %ghcArgs% && .shake\build %shakeArgs% From git at git.haskell.org Fri Oct 27 00:15:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on validate target (4cc0abb) Message-ID: <20171027001556.8D30F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4cc0abb94f94db16533a6737de3e892409e389fc/ghc >--------------------------------------------------------------- commit 4cc0abb94f94db16533a6737de3e892409e389fc Author: Andrey Mokhov Date: Sun Jan 31 00:00:48 2016 +0000 Add a note on validate target See #187. [skip ci] >--------------------------------------------------------------- 4cc0abb94f94db16533a6737de3e892409e389fc README.md | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 56e13ad..0a60d11 100644 --- a/README.md +++ b/README.md @@ -83,8 +83,13 @@ the previous build are still in the GHC tree. #### Testing -* `shake-build/build.sh test` runs GHC tests. The current implementation is very -limited and cannot replace the `validate` script (see [#187][validation-issue]). +* `shake-build/build.sh validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` +directory. This can be used instead of `sh validate --fast --no-clean` in the existing build system. +Note: this will rebuild Stage2 GHC, `ghc-pkg` and `hpc` if they are out of date. + +* `shake-build/build.sh test` runs GHC tests by calling the `testsuite/driver/runtests.py` python +script with appropriate flags. The current implementation is limited and cannot replace the +`validate` script (see [#187][validation-issue]). * `shake-build/build.sh selftest` runs tests of the build system. Current test coverage is close to zero (see [#197][test-issue]). From git at git.haskell.org Fri Oct 27 00:15:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use simpler mapM instead of traverse (73ad993) Message-ID: <20171027001556.EA9CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73ad99359cbac01618824c65fa116a46d27a4575/ghc >--------------------------------------------------------------- commit 73ad99359cbac01618824c65fa116a46d27a4575 Author: Andrey Mokhov Date: Sun May 22 01:57:26 2016 +0100 Use simpler mapM instead of traverse >--------------------------------------------------------------- 73ad99359cbac01618824c65fa116a46d27a4575 src/Rules.hs | 2 +- src/Rules/Dependencies.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index e3caf6c..bea672d 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -45,7 +45,7 @@ topLevelTargets = do if isLibrary pkg then do -- build a library ways <- interpretInContext context getLibraryWays - libs <- traverse (pkgLibraryFile . Context stage pkg) ways + libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context buildHaddock need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else do -- otherwise build a program diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 78f4d40..c5f60bb 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -36,7 +36,7 @@ buildPackageDependencies rs context at Context {..} = cSrcs <- pkgDataList $ CSrcs path let cDepFiles = map (src2dep context) cSrcs need $ hDepFile : cDepFiles -- need all for more parallelism - cDeps <- fmap concat $ traverse readFile' cDepFiles + cDeps <- concatMapM readFile' cDepFiles hDeps <- readFile' hDepFile let result = unlines . map (\(src, deps) -> unwords $ src : deps) From git at git.haskell.org Fri Oct 27 00:15:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:15:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify src/Oracles/ModuleFiles.hs, improve performance. (013fa90) Message-ID: <20171027001559.314723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/013fa902ee243621eff3778d94b0f1af37f3de51/ghc >--------------------------------------------------------------- commit 013fa902ee243621eff3778d94b0f1af37f3de51 Author: Andrey Mokhov Date: Thu Dec 24 04:36:07 2015 +0000 Simplify src/Oracles/ModuleFiles.hs, improve performance. >--------------------------------------------------------------- 013fa902ee243621eff3778d94b0f1af37f3de51 src/Oracles/ModuleFiles.hs | 78 ++++++++++++---------------------------------- 1 file changed, 20 insertions(+), 58 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 535d2be..832deef 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,76 +1,44 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} module Oracles.ModuleFiles (moduleFiles, haskellModuleFiles, moduleFilesOracle) where -import Base hiding (exe) -import Distribution.ModuleName -import Distribution.PackageDescription -import Distribution.PackageDescription.Parse -import Distribution.Verbosity -import GHC +import Base import Oracles.PackageData -import Package hiding (library) +import Package import Stage import Settings.TargetDirectory -newtype ModuleFilesKey = ModuleFilesKey (Package, [FilePath]) +newtype ModuleFilesKey = ModuleFilesKey ([String], [FilePath]) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) moduleFiles :: Stage -> Package -> Action [FilePath] moduleFiles stage pkg = do let path = targetPath stage pkg + srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - (found, _ :: [FilePath]) <- askOracle $ ModuleFilesKey (pkg, []) - let cmp (m1, _) m2 = compare m1 m2 - foundFiles = map snd $ intersectOrd cmp found modules - return foundFiles + let dirs = [ pkgPath pkg -/- dir | dir <- srcDirs ] + found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (modules, dirs) + return $ map snd found haskellModuleFiles :: Stage -> Package -> Action ([FilePath], [String]) haskellModuleFiles stage pkg = do let path = targetPath stage pkg autogen = path -/- "build/autogen" + srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - (found, missingMods) <- askOracle $ ModuleFilesKey (pkg, [autogen]) - let cmp (m1, _) m2 = compare m1 m2 - foundFiles = map snd $ intersectOrd cmp found modules + let dirs = [ pkgPath pkg -/- dir | dir <- srcDirs ] + foundSrcDirs <- askOracle $ ModuleFilesKey (modules, dirs ) + foundAutogen <- askOracle $ ModuleFilesKey (modules, [autogen]) + + let found = foundSrcDirs ++ foundAutogen + missingMods = modules `minusOrd` (sort $ map fst found) otherMods = map (replaceEq '/' '.' . dropExtension) otherFiles - (haskellFiles, otherFiles) = partition ("//*hs" ?==) foundFiles + (haskellFiles, otherFiles) = partition ("//*hs" ?==) (map snd found) return (haskellFiles, missingMods ++ otherMods) -extract :: Monoid a => Maybe (CondTree v c a) -> a -extract Nothing = mempty -extract (Just (CondNode leaf _ ifs)) = leaf <> mconcat (map f ifs) - where - f (_, t, mt) = extract (Just t) <> extract mt - --- Look up Haskell source directories and module names of a package -packageInfo :: Package -> Action ([FilePath], [ModuleName]) -packageInfo pkg - | pkg == hp2ps = return (["."], []) - | otherwise = do - need [pkgCabalFile pkg] - pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - - let lib = extract $ condLibrary pd - exe = extract . Just . snd . head $ condExecutables pd - - let (srcDirs, modules) = if lib /= mempty - then ( hsSourceDirs $ libBuildInfo lib, libModules lib) - else ( hsSourceDirs $ buildInfo exe - , [fromString . dropExtension $ modulePath exe] - ++ exeModules exe) - - return (if null srcDirs then ["."] else srcDirs, modules) - moduleFilesOracle :: Rules () moduleFilesOracle = do - answer <- newCache $ \(pkg, extraDirs) -> do - putOracle $ "Searching module files of package " ++ pkgNameString pkg ++ "..." - unless (null extraDirs) $ putOracle $ "Extra directory = " ++ show extraDirs - - (srcDirs, modules) <- packageInfo pkg - - let dirs = extraDirs ++ [ pkgPath pkg -/- dir | dir <- srcDirs ] - decodedPairs = sort $ map (splitFileName . toFilePath) modules + answer <- newCache $ \(modules, dirs) -> do + let decodedPairs = map decodeModule modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedPairs @@ -79,18 +47,12 @@ moduleFilesOracle = do forM todo $ \(mDir, mFiles) -> do let fullDir = dir -/- mDir files <- getDirectoryFiles fullDir ["*"] - let noBoot = filter (not . (isSuffixOf "-boot")) files + let noBoot = filter (not . (isSuffixOf "-boot")) files cmp fe f = compare (dropExtension fe) f found = intersectOrd cmp noBoot mFiles - return (map (fullDir -/-) found, (mDir, map dropExtension found)) - - let foundFiles = sort [ (encodeModule d f, f) - | (fs, (d, _)) <- result, f <- fs ] - foundPairs = [ (d, f) | (d, fs) <- map snd result, f <- fs ] - missingPairs = decodedPairs `minusOrd` sort foundPairs - missingMods = map (uncurry encodeModule) missingPairs + return (map (fullDir -/-) found, mDir) - return (foundFiles, missingMods) + return $ sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] _ <- addOracle $ \(ModuleFilesKey query) -> answer query return () From git at git.haskell.org Fri Oct 27 00:16:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #189, clear PWD so we can be sure it has the Unix-style path even on Windows (fce6921) Message-ID: <20171027001600.72BD83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fce6921fca6c3dd14f9a1b0a4c0940db2a8f7841/ghc >--------------------------------------------------------------- commit fce6921fca6c3dd14f9a1b0a4c0940db2a8f7841 Author: Neil Mitchell Date: Mon Feb 1 20:57:56 2016 +0000 #189, clear PWD so we can be sure it has the Unix-style path even on Windows >--------------------------------------------------------------- fce6921fca6c3dd14f9a1b0a4c0940db2a8f7841 src/Environment.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Environment.hs b/src/Environment.hs index fd207ed..e674f83 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -11,6 +11,11 @@ setupEnvironment = do -- ghc-cabal refuses to work when GHC_PACKAGE_PATH is set (e.g. by Stack) unsetEnv "GHC_PACKAGE_PATH" + -- in MinGW if PWD is set to a Windows "C:\\" style path then configure + -- `pwd` will return the Windows path, and then modifying $PATH will fail. + -- See https://github.com/snowleopard/shaking-up-ghc/issues/189 for details. + unsetEnv "PWD" + -- On Windows, some path variables start a prefix like "C:\\" which may -- lead to failures of scripts such as autoreconf. One particular variable -- which causes issues is ACLOCAL_PATH. At the moment we simply reset it From git at git.haskell.org Fri Oct 27 00:16:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify using firstJustM (8933a3a) Message-ID: <20171027001600.D41723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8933a3a8235a642638ef8e7e5e7c91777829535b/ghc >--------------------------------------------------------------- commit 8933a3a8235a642638ef8e7e5e7c91777829535b Author: Andrey Mokhov Date: Sun May 22 02:10:55 2016 +0100 Simplify using firstJustM >--------------------------------------------------------------- 8933a3a8235a642638ef8e7e5e7c91777829535b src/Oracles/Dependencies.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index d6cdbd3..a458b6d 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -24,8 +24,7 @@ fileDependencies :: Context -> FilePath -> Action (FilePath, [FilePath]) fileDependencies context obj = do let path = buildPath context -/- ".dependencies" -- If no dependencies found, try to drop the way suffix (for *.c sources). - deps <- listToMaybe . catMaybes <$> - mapM (askOracle . ObjDepsKey . (,) path) [obj, obj -<.> "o"] + deps <- firstJustM (askOracle . ObjDepsKey . (,) path) [obj, obj -<.> "o"] case deps of Nothing -> error $ "No dependencies found for file " ++ obj Just [] -> error $ "No source file found for file " ++ obj From git at git.haskell.org Fri Oct 27 00:16:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Cabal support for sandboxed build system building (5da933f) Message-ID: <20171027001602.B84823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5da933f768926b7be7e591d22b47a86809c21398/ghc >--------------------------------------------------------------- commit 5da933f768926b7be7e591d22b47a86809c21398 Author: David Luposchainsky Date: Tue Dec 22 20:54:26 2015 +0100 Add Cabal support for sandboxed build system building >--------------------------------------------------------------- 5da933f768926b7be7e591d22b47a86809c21398 .gitignore | 3 ++ README.md | 70 +++++++++++++++++++++++++++++----------- build.cabal.sh | 20 ++++++++++++ shaking-up-ghc.cabal | 91 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 165 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5da933f768926b7be7e591d22b47a86809c21398 From git at git.haskell.org Fri Oct 27 00:16:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #199 from ndmitchell/master (0cf18c9) Message-ID: <20171027001604.6858D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0cf18c9864f5524260c6cad87ec390ce06ad20ff/ghc >--------------------------------------------------------------- commit 0cf18c9864f5524260c6cad87ec390ce06ad20ff Merge: 4cc0abb fce6921 Author: Andrey Mokhov Date: Mon Feb 1 21:02:57 2016 +0000 Merge pull request #199 from ndmitchell/master Clear PWD >--------------------------------------------------------------- 0cf18c9864f5524260c6cad87ec390ce06ad20ff src/Environment.hs | 5 +++++ 1 file changed, 5 insertions(+) From git at git.haskell.org Fri Oct 27 00:16:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (15acc2c) Message-ID: <20171027001604.C15AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/15acc2cd1cc217335d37b55beeb421bd5c4ac48d/ghc >--------------------------------------------------------------- commit 15acc2cd1cc217335d37b55beeb421bd5c4ac48d Author: Andrey Mokhov Date: Sun May 22 20:04:30 2016 +0100 Minor revision >--------------------------------------------------------------- 15acc2cd1cc217335d37b55beeb421bd5c4ac48d src/Builder.hs | 21 +++++++++++---------- src/Expression.hs | 10 ++++------ src/Oracles/Config.hs | 22 +++++++++------------- src/Oracles/Config/Flag.hs | 32 +++++++++++++++----------------- src/Oracles/Config/Setting.hs | 4 ++-- src/Oracles/Dependencies.hs | 30 +++++++++++------------------- src/Oracles/LookupInPath.hs | 6 ++---- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageData.hs | 5 +---- src/Predicate.hs | 7 +++---- src/Rules/Generate.hs | 6 ++---- src/Rules/Gmp.hs | 9 ++++----- src/Rules/Libffi.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- 14 files changed, 67 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 15acc2cd1cc217335d37b55beeb421bd5c4ac48d From git at git.haskell.org Fri Oct 27 00:16:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Expression: Add Haddocks (263fc63) Message-ID: <20171027001606.266763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/263fc63fb084de713ef67608581d93ff52d2b04b/ghc >--------------------------------------------------------------- commit 263fc63fb084de713ef67608581d93ff52d2b04b Author: Ben Gamari Date: Thu Dec 24 12:34:07 2015 +0100 Expression: Add Haddocks >--------------------------------------------------------------- 263fc63fb084de713ef67608581d93ff52d2b04b src/Expression.hs | 88 ++++++++++++++++++++++++++++++++----------------------- 1 file changed, 52 insertions(+), 36 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 208566c..fa3959d 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -1,37 +1,48 @@ {-# LANGUAGE FlexibleInstances #-} module Expression ( - module Base, - module Builder, - module Package, - module Stage, - module Way, + -- * Expressions Expr, DiffExpr, fromDiffExpr, - Predicate, (?), applyPredicate, Args, Ways, Packages, - Target, PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay, + -- ** Operators apply, append, arg, remove, appendSub, appendSubD, filterSub, removeSub, + -- ** Evaluation interpret, interpretPartial, interpretWithStage, interpretDiff, + -- ** Predicates + Predicate, (?), applyPredicate, + -- ** Common expressions + Args, Ways, Packages, + -- ** Targets + Target, PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay, + + -- * Convenient accessors getStage, getPackage, getBuilder, getOutputs, getInputs, getWay, - getInput, getOutput + getInput, getOutput, + + -- * Re-exports + module Base, + module Builder, + module Package, + module Stage, + module Way ) where import Base -import Builder import Package +import Builder import Stage import Target import Way --- Expr a is a computation that produces a value of type Action a and can read --- parameters of the current build Target. +-- | @Expr a@ is a computation that produces a value of type @Action a@ and can read +-- parameters of the current build 'Target'. type Expr a = ReaderT Target Action a --- Diff a holds functions of type a -> a and is equipped with a Monoid instance. --- We could use Dual (Endo a) instead of Diff a, but the former may look scary. --- The name comes from "difference lists". +-- | @Diff a@ is a /difference list/ containing values of type @a at . A difference +-- list is a list with efficient concatenation, encoded as a value @a -> a at . +-- We could use @Dual (Endo a)@ instead of @Diff a@, but the former may look scary. newtype Diff a = Diff { fromDiff :: a -> a } --- DiffExpr a is a computation that builds a difference list (i.e., a function --- of type Action (a -> a)) and can read parameters of the current build Target. +-- | @DiffExpr a@ is a computation that builds a difference list (i.e., a function +-- of type @'Action' (a -> a)@) and can read parameters of the current build ''Target'. type DiffExpr a = Expr (Diff a) -- Note the reverse order of function composition (y . x), which ensures that @@ -41,38 +52,38 @@ instance Monoid (Diff a) where mempty = Diff id Diff x `mappend` Diff y = Diff $ y . x --- The following expressions are used throughout the build system for --- specifying conditions (Predicate), lists of arguments (Args), Ways and --- Packages. +-- | The following expressions are used throughout the build system for +-- specifying conditions ('Predicate'), lists of arguments ('Args'), 'Ways' +-- and 'Packages'. type Predicate = Expr Bool type Args = DiffExpr [String] type Packages = DiffExpr [Package] type Ways = DiffExpr [Way] -- Basic operations on expressions: --- 1) transform an expression by applying a given function +-- | Transform an expression by applying a given function apply :: (a -> a) -> DiffExpr a apply = return . Diff --- 2) append something to an expression +-- | Append something to an expression append :: Monoid a => a -> DiffExpr a append x = apply (<> x) --- 3) remove given elements from a list expression +-- | Remove given elements from a list expression remove :: Eq a => [a] -> DiffExpr [a] remove xs = apply $ filter (`notElem` xs) --- 4) apply a predicate to an expression +-- | Apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate if bool then expr else return mempty --- Add a single String argument to Args +-- | Add a single argument to 'Args' arg :: String -> Args arg = append . return --- A convenient operator for predicate application +-- | A convenient operator for predicate application class PredicateLike a where (?) :: Monoid m => a -> Expr m -> Expr m @@ -87,9 +98,9 @@ instance PredicateLike Bool where instance PredicateLike (Action Bool) where (?) = applyPredicate . lift --- appendSub appends a list of sub-arguments to all arguments starting with a +-- | @appendSub@ appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument --- of the form 'prefix=listOfSubarguments' is appended to the expression. +-- of the form @prefix=listOfSubarguments@ is appended to the expression. -- Note: nothing is done if the list of sub-arguments is empty. appendSub :: String -> [String] -> Args appendSub prefix xs @@ -103,8 +114,8 @@ appendSub prefix xs then unwords (y : xs') : go True ys else y : go found ys --- appendSubD is similar to appendSub but it extracts the list of sub-arguments --- from the given DiffExpr. +-- | @appendSubD@ is similar to 'appendSub' but it extracts the list of sub-arguments +-- from the given 'DiffExpr'. appendSubD :: String -> Args -> Args appendSubD prefix diffExpr = fromDiffExpr diffExpr >>= appendSub prefix @@ -115,12 +126,12 @@ filterSub prefix p = apply $ map filterSubstr | prefix `isPrefixOf` s = unwords . filter p . words $ s | otherwise = s --- Remove given elements from a list of sub-arguments with a given prefix +-- | Remove given elements from a list of sub-arguments with a given prefix -- Example: removeSub "--configure-option=CFLAGS" ["-Werror"] removeSub :: String -> [String] -> Args removeSub prefix xs = filterSub prefix (`notElem` xs) --- Interpret a given expression in a given environment +-- | Interpret a given expression in a given environment interpret :: Target -> Expr a -> Action a interpret = flip runReaderT @@ -131,41 +142,46 @@ interpretWithStage :: Stage -> Expr a -> Action a interpretWithStage s = interpretPartial $ PartialTarget s (error "interpretWithStage: package not set") --- Extract an expression from a difference expression +-- | Extract an expression from a difference expression fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) --- Interpret a given difference expression in a given environment +-- | Interpret a given difference expression in a given environment interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a interpretDiff target = interpret target . fromDiffExpr --- Convenient getters for target parameters +-- | Convenient getters for target parameters getStage :: Expr Stage getStage = asks stage +-- | Get the 'Package' of the current 'Target' getPackage :: Expr Package getPackage = asks package +-- | Get the 'Builder' for the current 'Target' getBuilder :: Expr Builder getBuilder = asks builder +-- | Get the 'Way' of the current 'Target' getWay :: Expr Way getWay = asks way +-- | Get the input files of the current 'Target' getInputs :: Expr [FilePath] getInputs = asks inputs --- Run getInputs and check that the result contains a single input file only +-- | Run 'getInputs' and check that the result contains a single input file only getInput :: Expr FilePath getInput = do target <- ask getSingleton getInputs $ "getInput: exactly one input file expected in target " ++ show target +-- | Get the files produced by the current 'Target' getOutputs :: Expr [FilePath] getOutputs = asks outputs --- Run getOutputs and check that the result contains a output file only +-- | Run 'getOutputs' and check that the result contains a output file only getOutput :: Expr FilePath getOutput = do target <- ask From git at git.haskell.org Fri Oct 27 00:16:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add includesDependencies to primops.txt rule. (1329a94) Message-ID: <20171027001608.5F6FC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1329a948ad88a8dec33834a4394024bae715df3b/ghc >--------------------------------------------------------------- commit 1329a948ad88a8dec33834a4394024bae715df3b Author: Andrey Mokhov Date: Tue Feb 2 12:26:45 2016 +0000 Add includesDependencies to primops.txt rule. Fix #201. >--------------------------------------------------------------- 1329a948ad88a8dec33834a4394024bae715df3b src/Rules/Generate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index d98527c..7538470 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -134,7 +134,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = -- TODO: needing platformH is ugly and fragile when (pkg == compiler) $ primopsTxt stage %> \file -> do - need [platformH stage, primopsSource] + need $ [platformH stage, primopsSource] ++ includesDependencies build $ fullTarget target HsCpp [primopsSource] [file] -- TODO: why different folders for generated files? From git at git.haskell.org Fri Oct 27 00:16:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set `THREADS` when running validate (e7e58aa) Message-ID: <20171027001608.B3EB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7e58aaff96f2f74097ea8f605b216b8fdd15443/ghc >--------------------------------------------------------------- commit e7e58aaff96f2f74097ea8f605b216b8fdd15443 Author: Michal Terepeta Date: Sun May 22 21:26:53 2016 +0200 Set `THREADS` when running validate GHC testsuite uses the `THREADS` env variable (and not the make's `-j` setting) to control the parallelism. This commit sets THREADS to the value of `shakeThreads`. >--------------------------------------------------------------- e7e58aaff96f2f74097ea8f605b216b8fdd15443 src/Settings/Builders/Make.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index 3d06775..afb46d7 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -11,4 +11,4 @@ makeBuilderArgs = do mconcat [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=" ++ j] , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=" ++ j, "install"] - , builder (Make "testsuite/tests") ? arg "fast" ] + , builder (Make "testsuite/tests") ? append ["THREADS=" ++ show threads, "fast"] ] From git at git.haskell.org Fri Oct 27 00:16:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #34 from bgamari/master (20b4c08) Message-ID: <20171027001609.905E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20b4c080dedd0fd6c1ce6a7d9b8543b8c97cf82e/ghc >--------------------------------------------------------------- commit 20b4c080dedd0fd6c1ce6a7d9b8543b8c97cf82e Merge: 013fa90 263fc63 Author: Andrey Mokhov Date: Thu Dec 24 12:33:42 2015 +0000 Merge pull request #34 from bgamari/master Expression: Add Haddocks >--------------------------------------------------------------- 20b4c080dedd0fd6c1ce6a7d9b8543b8c97cf82e src/Expression.hs | 88 ++++++++++++++++++++++++++++++++----------------------- 1 file changed, 52 insertions(+), 36 deletions(-) From git at git.haskell.org Fri Oct 27 00:16:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add configFile to Base, track building ./settings (acd13b4) Message-ID: <20171027001611.C934D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acd13b473853eab11eac680a67c3e4ab2f7f82ad/ghc >--------------------------------------------------------------- commit acd13b473853eab11eac680a67c3e4ab2f7f82ad Author: Andrey Mokhov Date: Tue Feb 2 15:11:11 2016 +0000 Add configFile to Base, track building ./settings See #200. >--------------------------------------------------------------- acd13b473853eab11eac680a67c3e4ab2f7f82ad src/Base.hs | 5 ++++- src/Oracles/Config.hs | 3 --- src/Rules/Config.hs | 10 ++++++---- 3 files changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 37f4716..464c1c9 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,7 +16,7 @@ module Base ( module Development.Shake.FilePath, -- * Paths - shakeFilesPath, configPath, sourcePath, programInplacePath, + shakeFilesPath, configPath, configFile, sourcePath, programInplacePath, bootPackageConstraints, packageDependencies, -- * Output @@ -54,6 +54,9 @@ shakeFilesPath = shakePath -/- ".db" configPath :: FilePath configPath = shakePath -/- "cfg" +configFile :: FilePath +configFile = configPath -/- "system.config" + -- | Path to source files of the build system, e.g. this file is located at -- sourcePath -/- "Base.hs". We use this to `need` some of the source files. sourcePath :: FilePath diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index cde2383..7801208 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -8,9 +8,6 @@ import Development.Shake.Config newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -configFile :: FilePath -configFile = configPath -/- "system.config" - askConfig :: String -> Action String askConfig key = askConfigWithDefault key . putError $ "Cannot find key '" ++ key ++ "' in configuration files." diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 7b6e8fa..eea61c6 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -8,12 +8,14 @@ configRules :: Rules () configRules = do -- We always rerun the configure script in this mode, because the flags -- passed to it can affect the contents of system.config file. - configPath -/- "system.config" %> \out -> do + [configFile, "settings"] &%> \[cfg, settings] -> do alwaysRerun case cmdConfigure of - RunConfigure args -> runConfigure "." [] [args] - SkipConfigure -> unlessM (doesFileExist out) $ - putError $ "Configuration file " ++ out ++ " is missing.\n" + RunConfigure args -> do + need [ settings <.> "in" ] + runConfigure "." [] [args] + SkipConfigure -> unlessM (doesFileExist cfg) $ + putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " ++ "build system by passing --configure[=ARGS] flag." From git at git.haskell.org Fri Oct 27 00:16:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #256 from michalt/validate-threads (f24d880) Message-ID: <20171027001612.7A1603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f24d88059e6f331dfbe789999d0ec6aca58fe64b/ghc >--------------------------------------------------------------- commit f24d88059e6f331dfbe789999d0ec6aca58fe64b Merge: 15acc2c e7e58aa Author: Andrey Mokhov Date: Sun May 22 21:53:26 2016 +0100 Merge pull request #256 from michalt/validate-threads Set `THREADS` when running validate >--------------------------------------------------------------- f24d88059e6f331dfbe789999d0ec6aca58fe64b src/Settings/Builders/Make.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:16:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #28 from quchen/cabalify (b053270) Message-ID: <20171027001613.5C8853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b053270c04df9aa94b97ced51704cdc676793745/ghc >--------------------------------------------------------------- commit b053270c04df9aa94b97ced51704cdc676793745 Merge: 20b4c08 5da933f Author: Andrey Mokhov Date: Thu Dec 24 12:35:37 2015 +0000 Merge pull request #28 from quchen/cabalify Add Cabal sandboxed build script >--------------------------------------------------------------- b053270c04df9aa94b97ced51704cdc676793745 .gitignore | 3 ++ README.md | 70 +++++++++++++++++++++++++++++----------- build.cabal.sh | 20 ++++++++++++ shaking-up-ghc.cabal | 91 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 165 insertions(+), 19 deletions(-) From git at git.haskell.org Fri Oct 27 00:16:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't print progress info too early. (e5e7221) Message-ID: <20171027001615.7B01C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e5e722178f227e3b81d27c8f66c152002d375aad/ghc >--------------------------------------------------------------- commit e5e722178f227e3b81d27c8f66c152002d375aad Author: Andrey Mokhov Date: Tue Feb 2 15:11:53 2016 +0000 Don't print progress info too early. See #200. >--------------------------------------------------------------- e5e722178f227e3b81d27c8f66c152002d375aad src/Rules/Actions.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d85e0dc..658ba17 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -67,6 +67,7 @@ captureStdout target path argList = do copyFile :: FilePath -> FilePath -> Action () copyFile source target = do + need [source] -- Guarantee source is built before printing progress info. putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target From git at git.haskell.org Fri Oct 27 00:16:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Upgrade to extra-1.4.7 (00b88a1) Message-ID: <20171027001616.2ADC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/00b88a16a67cf107eaf716b55ff5016fc5732c2a/ghc >--------------------------------------------------------------- commit 00b88a16a67cf107eaf716b55ff5016fc5732c2a Author: Andrey Mokhov Date: Mon May 23 00:16:14 2016 +0100 Upgrade to extra-1.4.7 >--------------------------------------------------------------- 00b88a16a67cf107eaf716b55ff5016fc5732c2a hadrian.cabal | 2 +- src/Oracles/Dependencies.hs | 2 +- src/Oracles/ModuleFiles.hs | 2 +- src/Rules/Library.hs | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 95ae3a0..c9d5551 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -122,7 +122,7 @@ executable hadrian , Cabal == 1.22.* || == 1.24.* , containers == 0.5.* , directory == 1.2.* - , extra == 1.4.* + , extra >= 1.4.7 , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.9 , shake >= 0.15.6 diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index ce94805..1a8b587 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -50,7 +50,7 @@ contextDependencies context at Context {..} = do -- | Coarse-grain 'need': make sure given contexts are fully built. needContext :: [Context] -> Action () needContext cs = do - libs <- fmap concat . forM cs $ \context -> do + libs <- concatForM cs $ \context -> do libFile <- pkgLibraryFile context lib0File <- pkgLibraryFile0 context lib0 <- buildDll0 context diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index ece6d0b..b11ef3b 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -115,7 +115,7 @@ moduleFilesOracle = void $ do modules <- fmap sort . pkgDataList $ Modules path let dirs = (path -/- "autogen") : map (pkgPath package -/-) srcDirs modDirFiles = groupSort $ map decodeModule modules - result <- fmap concat . forM dirs $ \dir -> do + result <- concatForM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do let fullDir = unifyPath $ dir -/- mDir diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index edbdb52..dd144d1 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -36,7 +36,7 @@ buildPackageLibrary context at Context {..} = do split <- interpretInContext context splitObjects splitObjs <- if not split then return hObjs else -- TODO: make clearer! - fmap concat $ forM hSrcs $ \src -> do + concatForM hSrcs $ \src -> do let splitPath = path -/- src ++ "_" ++ osuf way ++ "_split" contents <- liftIO $ IO.getDirectoryContents splitPath return . map (splitPath -/-) From git at git.haskell.org Fri Oct 27 00:16:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove `make inplace/bin/ghc-cabal` (see #23) (c1802dc) Message-ID: <20171027001616.CFA2A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1802dc7290cf3b694fefa3e338b49a3b39956d4/ghc >--------------------------------------------------------------- commit c1802dc7290cf3b694fefa3e338b49a3b39956d4 Author: Andrey Mokhov Date: Thu Dec 24 13:00:08 2015 +0000 Remove `make inplace/bin/ghc-cabal` (see #23) >--------------------------------------------------------------- c1802dc7290cf3b694fefa3e338b49a3b39956d4 README.md | 2 -- 1 file changed, 2 deletions(-) diff --git a/README.md b/README.md index 3c42074..4fab178 100644 --- a/README.md +++ b/README.md @@ -25,7 +25,6 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure -make inplace/bin/ghc-cabal # This needs to be fixed ``` Now you have a couple of options: @@ -45,7 +44,6 @@ $ cd ghc $ git clone git://github.com/snowleopard/shaking-up-ghc shake-build $ ./boot $ ./configure --enable-tarballs-autodownload -$ make inplace/bin/ghc-cabal # This needs to be fixed $ shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. From git at git.haskell.org Fri Oct 27 00:16:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Sort list items. (d1fb3de) Message-ID: <20171027001619.45F1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1fb3de6d250c1d30ba86612595c3f48c2661c1a/ghc >--------------------------------------------------------------- commit d1fb3de6d250c1d30ba86612595c3f48c2661c1a Author: Andrey Mokhov Date: Tue Feb 2 15:16:21 2016 +0000 Sort list items. See #200. >--------------------------------------------------------------- d1fb3de6d250c1d30ba86612595c3f48c2661c1a src/Rules/Generate.hs | 46 +++++++++++++++++++++++----------------------- 1 file changed, 23 insertions(+), 23 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 7538470..9c67760 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -21,11 +21,11 @@ import Rules.Resources (Resources) import Settings installTargets :: [FilePath] -installTargets = [ "inplace/lib/template-hsc.h" +installTargets = [ "inplace/lib/ghc-usage.txt" + , "inplace/lib/ghci-usage.txt" , "inplace/lib/platformConstants" , "inplace/lib/settings" - , "inplace/lib/ghc-usage.txt" - , "inplace/lib/ghci-usage.txt" ] + , "inplace/lib/template-hsc.h" ] primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -45,8 +45,8 @@ includesDependencies = ("includes" -/-) <$> ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> - [ "GHC/PrimopWrappers.hs" - , "autogen/GHC/Prim.hs" ] + [ "autogen/GHC/Prim.hs" + , "GHC/PrimopWrappers.hs" ] derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" @@ -54,9 +54,9 @@ derivedConstantsPath = "includes/dist-derivedconstants/header" derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) [ "DerivedConstants.h" + , "GHCConstantsHaskellExports.hs" , "GHCConstantsHaskellType.hs" - , "GHCConstantsHaskellWrappers.hs" - , "GHCConstantsHaskellExports.hs" ] + , "GHCConstantsHaskellWrappers.hs" ] compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = @@ -66,21 +66,21 @@ compilerDependencies stage = ++ filter (const $ stage > Stage0) libffiDependencies ++ derivedConstantsDependencies ++ fmap ((targetPath stage compiler -/- "build") -/-) - [ "primop-vector-uniques.hs-incl" + [ "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" + , "primop-list.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-strictness.hs-incl" + , "primop-tag.hs-incl" , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tys.hs-incl" + , "primop-vector-uniques.hs-incl" ] -- TODO: Turn this into a FilePaths expression generatedDependencies :: Stage -> Package -> [FilePath] @@ -139,8 +139,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = -- TODO: why different folders for generated files? fmap (buildPath -/-) - [ "GHC/PrimopWrappers.hs" - , "autogen/GHC/Prim.hs" + [ "autogen/GHC/Prim.hs" + , "GHC/PrimopWrappers.hs" , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] build $ fullTarget target GenPrimopCode [primopsTxt stage] [file] @@ -164,11 +164,11 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = copyRules :: Rules () copyRules = do - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs - "inplace/lib/platformConstants" <~ derivedConstantsPath - "inplace/lib/settings" <~ "." "inplace/lib/ghc-usage.txt" <~ "driver" "inplace/lib/ghci-usage.txt" <~ "driver" + "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs where file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file From git at git.haskell.org Fri Oct 27 00:16:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop shake-0.15.6 from extra-deps, and add extra-1.4.7 (ec031af) Message-ID: <20171027001619.CF9583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ec031af8526a0187cbf6701c18ccd4687bff0160/ghc >--------------------------------------------------------------- commit ec031af8526a0187cbf6701c18ccd4687bff0160 Author: Andrey Mokhov Date: Mon May 23 00:38:19 2016 +0100 Drop shake-0.15.6 from extra-deps, and add extra-1.4.7 >--------------------------------------------------------------- ec031af8526a0187cbf6701c18ccd4687bff0160 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index 0d8809b..b20331f 100644 --- a/stack.yaml +++ b/stack.yaml @@ -9,7 +9,7 @@ packages: # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: -- shake-0.15.6 +- extra-1.4.7 # Override default flag values for local packages and extra-deps flags: {} From git at git.haskell.org Fri Oct 27 00:16:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add the author's email. (3f55a9e) Message-ID: <20171027001620.3A34F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3f55a9ed5d25f9f6310b76db5a0befe1b66aa19d/ghc >--------------------------------------------------------------- commit 3f55a9ed5d25f9f6310b76db5a0befe1b66aa19d Author: Andrey Mokhov Date: Thu Dec 24 19:50:10 2015 +0000 Add the author's email. >--------------------------------------------------------------- 3f55a9ed5d25f9f6310b76db5a0befe1b66aa19d shaking-up-ghc.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 4cfb30d..f1a3f10 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -3,9 +3,9 @@ version: 0.1.0.0 synopsis: GHC build system license: BSD3 license-file: LICENSE -author: Andrey Mokhov, Github: @snowleopard -maintainer: Andrey Mokhov, Github: @snowleopard -copyright: Andrey Mokhov, Github: @snowleopard +author: Andrey Mokhov , github: @snowleopard +maintainer: Andrey Mokhov , github: @snowleopard +copyright: Andrey Mokhov 2014-2015 category: Development build-type: Simple cabal-version: >=1.10 From git at git.haskell.org Fri Oct 27 00:16:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build top-level targets in parallel. (1441846) Message-ID: <20171027001623.06E4C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1441846ddc4fa070a8fa9351ec6386b8645b176e/ghc >--------------------------------------------------------------- commit 1441846ddc4fa070a8fa9351ec6386b8645b176e Author: Andrey Mokhov Date: Tue Feb 2 15:17:05 2016 +0000 Build top-level targets in parallel. See #200. >--------------------------------------------------------------- 1441846ddc4fa070a8fa9351ec6386b8645b176e src/Main.hs | 2 +- src/Package.hs | 3 ++- src/Rules.hs | 48 +++++++++++++++++++++++++++++------------------- 3 files changed, 32 insertions(+), 21 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 2c944d4..79601d8 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -36,7 +36,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules , Rules.Perl.perlScriptRules - , Rules.generateTargets + , Rules.topLevelTargets , Rules.packageRules , Selftest.selftestRules , Test.testRules ] diff --git a/src/Package.hs b/src/Package.hs index b34dc02..43eb480 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -21,7 +21,8 @@ newtype PackageName = PackageName { getPackageName :: String } instance Show PackageName where show (PackageName name) = name --- TODO: make PackageType more precise, #12 +-- TODO: Make PackageType more precise, #12 +-- TODO: Turn Program to Program FilePath thereby getting rid of programPath -- | We regard packages as either being libraries or programs. This is -- bit of a convenient lie as Cabal packages can be both, but it works -- for now. diff --git a/src/Rules.hs b/src/Rules.hs index 5f505b3..b22e028 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,10 +1,11 @@ -module Rules (generateTargets, packageRules) where +module Rules (topLevelTargets, packageRules) where import Base import Data.Foldable import Expression import GHC -import Rules.Generate +import Oracles.PackageData +import qualified Rules.Generate import Rules.Package import Rules.Resources import Settings @@ -13,23 +14,32 @@ allStages :: [Stage] allStages = [minBound ..] -- | 'need' all top-level build targets -generateTargets :: Rules () -generateTargets = action $ do - targets <- fmap concat (traverse targetsForStage allStages) - rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla - rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded - need $ targets ++ installTargets ++ [ rtsLib, rtsThrLib ] - -targetsForStage :: Stage -> Action [String] -targetsForStage stage = do - pkgs <- interpretWithStage stage getPackages - let libPkgs = filter isLibrary pkgs \\ [rts, libffi] - libTargets <- fmap concat . forM libPkgs $ \pkg -> do - let target = PartialTarget stage pkg - needHaddock <- interpretPartial target buildHaddock - return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] - let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] - return $ libTargets ++ programTargets +topLevelTargets :: Rules () +topLevelTargets = do + + want $ Rules.Generate.installTargets + + -- TODO: do we want libffiLibrary to be a top-level target? + + action $ do -- TODO: Add support for all rtsWays + rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla + rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded + need [ rtsLib, rtsThrLib ] + + for_ allStages $ \stage -> + for_ (knownPackages \\ [rts, libffi]) $ \pkg -> action $ do + let target = PartialTarget stage pkg + activePackages <- interpretPartial target getPackages + when (pkg `elem` activePackages) $ + if isLibrary pkg + then do -- build a library + ways <- interpretPartial target getLibraryWays + compId <- interpretPartial target $ getPkgData ComponentId + libs <- traverse (pkgLibraryFile stage pkg compId) ways + haddock <- interpretPartial target buildHaddock + need $ libs ++ [ pkgHaddockFile pkg | haddock && stage == Stage1 ] + else do -- otherwise build a program + need [ fromJust $ programPath stage pkg ] -- TODO: drop fromJust packageRules :: Rules () packageRules = do From git at git.haskell.org Fri Oct 27 00:16:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use LTS-5.17 (68f8eaf) Message-ID: <20171027001624.0FD263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68f8eafed955a6b1ed895960c21144c50c0c61d1/ghc >--------------------------------------------------------------- commit 68f8eafed955a6b1ed895960c21144c50c0c61d1 Author: Andrey Mokhov Date: Mon May 23 01:31:47 2016 +0100 Use LTS-5.17 >--------------------------------------------------------------- 68f8eafed955a6b1ed895960c21144c50c0c61d1 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index b20331f..f6deca8 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,7 +1,7 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-5.1 +resolver: lts-5.17 # Local packages, usually specified by relative directory name packages: From git at git.haskell.org Fri Oct 27 00:16:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move OverloadedStrings to other-extensions. (b56b886) Message-ID: <20171027001624.177863A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b56b88616e82fb652c49ea9f6c087dd76e950a42/ghc >--------------------------------------------------------------- commit b56b88616e82fb652c49ea9f6c087dd76e950a42 Author: Andrey Mokhov Date: Thu Dec 24 20:24:14 2015 +0000 Move OverloadedStrings to other-extensions. >--------------------------------------------------------------- b56b88616e82fb652c49ea9f6c087dd76e950a42 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f1a3f10..098d8b2 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -72,11 +72,11 @@ executable ghc-shake default-extensions: BangPatterns , LambdaCase , MultiWayIf - , OverloadedStrings , TupleSections other-extensions: DeriveDataTypeable , DeriveGeneric , FlexibleInstances + , OverloadedStrings build-depends: base , ansi-terminal >= 0.6 , Cabal >= 1.22 From git at git.haskell.org Fri Oct 27 00:16:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track mk/config.h (af2d086) Message-ID: <20171027001626.7BB1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/af2d08616055124477b86b14f9f602b2c306a768/ghc >--------------------------------------------------------------- commit af2d08616055124477b86b14f9f602b2c306a768 Author: Andrey Mokhov Date: Tue Feb 2 15:41:50 2016 +0000 Track mk/config.h See #200. >--------------------------------------------------------------- af2d08616055124477b86b14f9f602b2c306a768 src/Rules/Config.hs | 5 +++-- src/Rules/Generators/GhcAutoconfH.hs | 2 +- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index eea61c6..f258674 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -3,16 +3,17 @@ module Rules.Config (configRules) where import Base import CmdLineFlag import Rules.Actions +import Rules.Generators.GhcAutoconfH configRules :: Rules () configRules = do -- We always rerun the configure script in this mode, because the flags -- passed to it can affect the contents of system.config file. - [configFile, "settings"] &%> \[cfg, settings] -> do + [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do alwaysRerun case cmdConfigure of RunConfigure args -> do - need [ settings <.> "in" ] + need [ settings <.> "in", cfgH <.> "in" ] runConfigure "." [] [args] SkipConfigure -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" diff --git a/src/Rules/Generators/GhcAutoconfH.hs b/src/Rules/Generators/GhcAutoconfH.hs index d6e783f..9d93744 100644 --- a/src/Rules/Generators/GhcAutoconfH.hs +++ b/src/Rules/Generators/GhcAutoconfH.hs @@ -1,4 +1,4 @@ -module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH) where +module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH, configH) where import Base import Expression From git at git.haskell.org Fri Oct 27 00:16:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Packages/Rts: add `linker` to RTS directories (166e3fb) Message-ID: <20171027001628.5058D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/166e3fb4aa2e8c4040287c1d87bf022b81a07790/ghc >--------------------------------------------------------------- commit 166e3fb4aa2e8c4040287c1d87bf022b81a07790 Author: Michal Terepeta Date: Wed May 25 20:14:33 2016 +0200 Packages/Rts: add `linker` to RTS directories Recent commit split off the m32 allocator to `rts/linker/`, which broke the build using Hadrian (since it didn't know about the new directory). This fixes it. Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 166e3fb4aa2e8c4040287c1d87bf022b81a07790 src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 52aac32..6c99113 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -104,7 +104,7 @@ buildPackageData context at Context {..} = do orderOnly $ generatedDependencies stage package windows <- windowsHost let prefix = fixKey (buildPath context) ++ "_" - dirs = [ ".", "hooks", "sm", "eventlog" ] + dirs = [ ".", "hooks", "sm", "eventlog", "linker" ] ++ [ if windows then "win32" else "posix" ] -- TODO: Adding cmm/S sources to C_SRCS is a hack -- refactor. cSrcs <- map unifyPath <$> From git at git.haskell.org Fri Oct 27 00:16:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move parseMakefile from dependenciesOracle to Rules.Dependencies (for better performance) (8fe9fa6) Message-ID: <20171027001628.4C1E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1/ghc >--------------------------------------------------------------- commit 8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1 Author: Andrey Mokhov Date: Fri Dec 25 01:19:50 2015 +0000 Move parseMakefile from dependenciesOracle to Rules.Dependencies (for better performance) >--------------------------------------------------------------- 8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1 src/Oracles/Dependencies.hs | 7 ++----- src/Rules/Dependencies.hs | 19 +++++++++++++------ 2 files changed, 15 insertions(+), 11 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index c27c2cc..8895758 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -31,11 +31,8 @@ dependenciesOracle :: Rules () dependenciesOracle = do deps <- newCache $ \file -> do putOracle $ "Reading dependencies from " ++ file ++ "..." - contents <- parseMakefile <$> readFile' file - return . Map.fromList . map (bimap unifyPath (map unifyPath)) - . map (bimap head concat . unzip) - . groupBy ((==) `on` fst) - . sortBy (compare `on` fst) $ contents + contents <- map words <$> readFileLines file + return . Map.fromList $ map (\(x:xs) -> (x, xs)) contents _ <- addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file return () diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 47e6c6d..907c4d3 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -21,7 +21,7 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] - hDepFile %> \file -> do + hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) $ need [platformH] -- TODO: very ugly and fragile; use gcc -MM instead? @@ -43,14 +43,21 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = , "primop-vector-tys.hs-incl" ] need $ srcs ++ extraDeps if srcs == [] - then writeFileChanged file "" - else build $ fullTarget target (GhcM stage) srcs [file] - removeFileIfExists $ file <.> "bak" + then writeFileChanged out "" + else build $ fullTarget target (GhcM stage) srcs [out] + removeFileIfExists $ out <.> "bak" - (buildPath -/- ".dependencies") %> \file -> do + (buildPath -/- ".dependencies") %> \out -> do cSrcs <- pkgDataList $ CSrcs path let cDepFiles = [ buildPath -/- src <.> "deps" | src <- cSrcs ] need $ hDepFile : cDepFiles -- need all for more parallelism cDeps <- fmap concat $ mapM readFile' cDepFiles hDeps <- readFile' hDepFile - writeFileChanged file $ cDeps ++ hDeps + let result = unlines + . map (\(src, deps) -> unwords $ src : deps) + . map (bimap unifyPath (map unifyPath)) + . map (bimap head concat . unzip) + . groupBy ((==) `on` fst) + . sortBy (compare `on` fst) + . parseMakefile $ cDeps ++ hDeps + writeFileChanged out result From git at git.haskell.org Fri Oct 27 00:16:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track mk/config.h.in (adfff77) Message-ID: <20171027001629.F159B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/adfff77a8843662c4d5034076702101443460deb/ghc >--------------------------------------------------------------- commit adfff77a8843662c4d5034076702101443460deb Author: Andrey Mokhov Date: Tue Feb 2 15:52:51 2016 +0000 Track mk/config.h.in See #200. >--------------------------------------------------------------- adfff77a8843662c4d5034076702101443460deb src/Rules/Config.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index f258674..89434cb 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -20,6 +20,6 @@ configRules = do ++ "Run the configure script either manually or via the " ++ "build system by passing --configure[=ARGS] flag." - "configure" %> \_ -> do + ["configure", configH <.> "in"] &%> \_ -> do putBuild "| Running boot..." quietly $ cmd (EchoStdout False) "perl boot" From git at git.haskell.org Fri Oct 27 00:16:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a section on resetting the build (#32) (86ee9f6) Message-ID: <20171027001632.2F67C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86ee9f68057e7ab1a9f09a6d006cddb488c16c02/ghc >--------------------------------------------------------------- commit 86ee9f68057e7ab1a9f09a6d006cddb488c16c02 Author: Andrey Mokhov Date: Fri Dec 25 14:12:35 2015 +0000 Add a section on resetting the build (#32) >--------------------------------------------------------------- 86ee9f68057e7ab1a9f09a6d006cddb488c16c02 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 4fab178..c415ee4 100644 --- a/README.md +++ b/README.md @@ -49,7 +49,9 @@ $ shake-build/build.bat Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. +### Resetting the build +To reset the new build system delete the `shake-build/.db` directory which stores the Shake database. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). How to contribute From git at git.haskell.org Fri Oct 27 00:16:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #257 from michalt/rts-linker/1 (45b5f13) Message-ID: <20171027001632.434AD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45b5f1341e3b400efeaa675ddc9d43d69268ff09/ghc >--------------------------------------------------------------- commit 45b5f1341e3b400efeaa675ddc9d43d69268ff09 Merge: 68f8eaf 166e3fb Author: Andrey Mokhov Date: Wed May 25 21:47:24 2016 +0100 Merge pull request #257 from michalt/rts-linker/1 Packages/Rts: add `linker` to RTS directories >--------------------------------------------------------------- 45b5f1341e3b400efeaa675ddc9d43d69268ff09 src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:16:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do a full build on both Travis instances. (be9a21c) Message-ID: <20171027001633.679593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/be9a21c630f2d8585ba2c349cc97eb8f749abc80/ghc >--------------------------------------------------------------- commit be9a21c630f2d8585ba2c349cc97eb8f749abc80 Author: Andrey Mokhov Date: Tue Feb 2 19:13:55 2016 +0000 Do a full build on both Travis instances. 1000th commit! >--------------------------------------------------------------- be9a21c630f2d8585ba2c349cc97eb8f749abc80 .travis.yml | 7 ++----- 1 file changed, 2 insertions(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 84bb380..cf2f1cb 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: false matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 addons: apt: packages: @@ -21,7 +21,6 @@ matrix: - cabal update - os: osx - env: TARGET=inplace/bin/ghc-stage1 before_install: - brew update - brew install ghc cabal-install @@ -30,9 +29,7 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH - install: - - env - ghc --version - cabal --version @@ -64,7 +61,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET + - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick cache: directories: From git at git.haskell.org Fri Oct 27 00:16:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Need touchy when calling ghc-stageN, N > 0, on Windows. (fc040db) Message-ID: <20171027001636.D07303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fc040dbd72081339e3eff5083dcb13d145f69ded/ghc >--------------------------------------------------------------- commit fc040dbd72081339e3eff5083dcb13d145f69ded Author: Andrey Mokhov Date: Tue Feb 2 22:06:22 2016 +0000 Need touchy when calling ghc-stageN, N > 0, on Windows. >--------------------------------------------------------------- fc040dbd72081339e3eff5083dcb13d145f69ded src/Settings/Builders/Ghc.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index c79fc50..74381eb 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -21,6 +21,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput stage <- getStage way <- getWay + when (stage > Stage0) . lift $ needTouchy let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output buildProg = not (buildObj || buildHi) @@ -44,6 +45,9 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , buildHi ? append ["-fno-code", "-fwrite-interface"] , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] +needTouchy :: Action () +needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy ] + splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do lift $ need [ghcSplit] From git at git.haskell.org Fri Oct 27 00:16:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use `-B` flag to reset the build (bdb88c6) Message-ID: <20171027001635.93FC93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bdb88c61e4e0761a2ad80904f26d2443fecf7fd4/ghc >--------------------------------------------------------------- commit bdb88c61e4e0761a2ad80904f26d2443fecf7fd4 Author: Andrey Mokhov Date: Fri Dec 25 22:49:45 2015 +0000 Use `-B` flag to reset the build >--------------------------------------------------------------- bdb88c61e4e0761a2ad80904f26d2443fecf7fd4 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index c415ee4..6d27b25 100644 --- a/README.md +++ b/README.md @@ -51,7 +51,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system delete the `shake-build/.db` directory which stores the Shake database. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). +To reset the new build system run the build script with `-B` flag. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). How to contribute From git at git.haskell.org Fri Oct 27 00:16:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Enable optional UserSettings.hs file (123bdb3) Message-ID: <20171027001635.BBC383A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/123bdb37674bfe60509886ec92c99e80b0588966/ghc >--------------------------------------------------------------- commit 123bdb37674bfe60509886ec92c99e80b0588966 Author: Kai Harries Date: Sat May 28 17:53:07 2016 +0200 Enable optional UserSettings.hs file Fix #247 The defaul user settings are stored in ./src/UserSettings.hs. If the user want to override these settings, he can copy this file into ./ and make the desired changes to ./UserSettings.hs. >--------------------------------------------------------------- 123bdb37674bfe60509886ec92c99e80b0588966 .gitignore | 3 + README.md | 3 +- doc/user-settings.md | 5 +- hadrian.cabal | 3 +- src/Settings/User.hs | 103 ++---------------------------- src/{Settings/User.hs => UserSettings.hs} | 8 ++- 6 files changed, 20 insertions(+), 105 deletions(-) diff --git a/.gitignore b/.gitignore index b7bfddb..5307cdd 100644 --- a/.gitignore +++ b/.gitignore @@ -15,3 +15,6 @@ cabal.sandbox.config # build.stack.sh specific /.stack-work/ + +# the user settings +/UserSettings.hs diff --git a/README.md b/README.md index e4fb7dc..b1da6f7 100644 --- a/README.md +++ b/README.md @@ -88,7 +88,7 @@ by Shake oracles. #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We -use [`src/Settings/User.hs`][user-settings] for the same purpose, see +use `./UserSettings.hs` for the same purpose, see [documentation](doc/user-settings.md). #### Clean and full rebuild @@ -155,7 +155,6 @@ helped me endure and enjoy the project. [windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md [build-artefacts-issue]: https://github.com/snowleopard/hadrian/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 -[user-settings]: https://github.com/snowleopard/hadrian/blob/master/src/Settings/User.hs [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 diff --git a/doc/user-settings.md b/doc/user-settings.md index 1433ae9..a5185ad 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,7 +1,8 @@ # User settings -You can customise Hadrian by specifying user build settings in file -`src/Settings/User.hs`. Here we document currently supported settings. +You can customise Hadrian by copying the file ./src/UserSettings.hs to +./UserSettings.hs and specifying user build settings in +`./UserSettings.hs`. Here we document currently supported settings. ## Build directory diff --git a/hadrian.cabal b/hadrian.cabal index c9d5551..3bbc2dd 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -16,7 +16,8 @@ source-repository head executable hadrian main-is: Main.hs - hs-source-dirs: src + hs-source-dirs: . + , src other-modules: Base , Builder , CmdLineFlag diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 16c7c25..9588297 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -5,101 +5,8 @@ module Settings.User ( turnWarningsIntoErrors, splitObjects, verboseCommands, putBuild, putSuccess ) where -import System.Console.ANSI - -import Base -import CmdLineFlag -import GHC -import Predicate -import Settings.Default - --- See doc/user-settings.md for instructions. - --- | All build results are put into 'buildRootPath' directory. -buildRootPath :: FilePath -buildRootPath = "_build" - --- | Modify default build command line arguments. -userArgs :: Args -userArgs = builder Ghc ? remove ["-Wall", "-fwarn-tabs"] - --- | Modify the set of packages that are built by default in each stage. -userPackages :: Packages -userPackages = mempty - --- | Add user defined packages. Don't forget to add them to 'userPackages' too. -userKnownPackages :: [Package] -userKnownPackages = [] - --- | Choose the integer library: 'integerGmp' or 'integerSimple'. -integerLibrary :: Package -integerLibrary = integerGmp - --- FIXME: We skip 'dynamic' since it's currently broken #4. --- | Modify the set of ways in which library packages are built. -userLibraryWays :: Ways -userLibraryWays = remove [dynamic] - --- | Modify the set of ways in which the 'rts' package is built. -userRtsWays :: Ways -userRtsWays = mempty - --- | User defined flags. Note the following type semantics: --- * @Bool@: a plain Boolean flag whose value is known at compile time. --- * @Action Bool@: a flag whose value can depend on the build environment. --- * @Predicate@: a flag whose value can depend on the build environment and --- on the current build target. - --- TODO: Drop 'trackBuildSystem' as it brings negligible gains. --- | Set this to True if you are making any changes in the build system and want --- appropriate rebuilds to be initiated. Switching this to False speeds things --- up a little (particularly zero builds). --- WARNING: a complete rebuild is required when changing this setting. -trackBuildSystem :: Bool -trackBuildSystem = True - --- TODO: This should be set automatically when validating. -validating :: Bool -validating = False - --- | Control when split objects are generated. Note, due to the GHC bug #11315 --- it is necessary to do a full clean rebuild when changing this option. -splitObjects :: Predicate -splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects - --- | Control when to build Haddock documentation. -buildHaddock :: Predicate -buildHaddock = return cmdBuildHaddock - --- TODO: Do we need to be able to set these from command line? --- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? -dynamicGhcPrograms :: Bool -dynamicGhcPrograms = False - -ghciWithDebugger :: Bool -ghciWithDebugger = False - -ghcProfiled :: Bool -ghcProfiled = False - -ghcDebugged :: Bool -ghcDebugged = False - --- TODO: Replace with stage2 ? arg "-Werror"? Also see #251. --- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. -turnWarningsIntoErrors :: Predicate -turnWarningsIntoErrors = return False - --- | Set to True to print full command lines during the build process. Note, --- this is a Predicate, hence you can enable verbose output only for certain --- targets, e.g.: @verboseCommands = package ghcPrim at . -verboseCommands :: Predicate -verboseCommands = return False - --- | Customise build progress messages (e.g. executing a build command). -putBuild :: String -> Action () -putBuild = putColoured Vivid White - --- | Customise build success messages (e.g. a package is built successfully). -putSuccess :: String -> Action () -putSuccess = putColoured Vivid Green +-- Import the actual user settings from the module UserSettings. +-- The user can put an UserSettings.hs file into the hadrian root +-- folder that takes precedence over the default UserSettings.hs +-- file located in src/. +import UserSettings diff --git a/src/Settings/User.hs b/src/UserSettings.hs similarity index 94% copy from src/Settings/User.hs copy to src/UserSettings.hs index 16c7c25..7560aa1 100644 --- a/src/Settings/User.hs +++ b/src/UserSettings.hs @@ -1,4 +1,8 @@ -module Settings.User ( +-- +-- If you want to customize your build you should copy this file from +-- ./src/UserSettings.hs to ./UserSettings.hs and only edit your copy. +-- +module UserSettings ( buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, @@ -74,7 +78,7 @@ buildHaddock = return cmdBuildHaddock -- TODO: Do we need to be able to set these from command line? -- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? dynamicGhcPrograms :: Bool -dynamicGhcPrograms = False +dynamicGhcPrograms = True ghciWithDebugger :: Bool ghciWithDebugger = False From git at git.haskell.org Fri Oct 27 00:16:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move generators to a dedicated directory, and track their changes. (8c3022d) Message-ID: <20171027001639.03F4B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c3022df66c07b7c1f78a59d60bb154868b591da/ghc >--------------------------------------------------------------- commit 8c3022df66c07b7c1f78a59d60bb154868b591da Author: Andrey Mokhov Date: Sat Dec 26 00:24:07 2015 +0000 Move generators to a dedicated directory, and track their changes. >--------------------------------------------------------------- 8c3022df66c07b7c1f78a59d60bb154868b591da shaking-up-ghc.cabal | 3 + src/Base.hs | 16 ++- src/Rules/Generate.hs | 166 +------------------------------- src/Rules/Generators/ConfigHs.hs | 102 ++++++++++++++++++++ src/Rules/Generators/GhcPkgVersionHs.hs | 17 ++++ src/Rules/Generators/PlatformH.hs | 57 +++++++++++ 6 files changed, 195 insertions(+), 166 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 8c3022df66c07b7c1f78a59d60bb154868b591da From git at git.haskell.org Fri Oct 27 00:16:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #258 from KaiHa/ticket/247 (20d7082) Message-ID: <20171027001639.3FE6C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20d70820a2c2fc7bfecacf79906db129d157846d/ghc >--------------------------------------------------------------- commit 20d70820a2c2fc7bfecacf79906db129d157846d Merge: 45b5f13 123bdb3 Author: Andrey Mokhov Date: Tue May 31 07:10:48 2016 +0100 Merge pull request #258 from KaiHa/ticket/247 Enable optional UserSettings.hs file >--------------------------------------------------------------- 20d70820a2c2fc7bfecacf79906db129d157846d .gitignore | 3 + README.md | 3 +- doc/user-settings.md | 5 +- hadrian.cabal | 3 +- src/Settings/User.hs | 103 ++---------------------------- src/{Settings/User.hs => UserSettings.hs} | 8 ++- 6 files changed, 20 insertions(+), 105 deletions(-) From git at git.haskell.org Fri Oct 27 00:16:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build GhcPkg Stage1 on OS X Travis. (f8bd699) Message-ID: <20171027001640.4D1B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8bd699693493f3ba8eb10e025c5db72a75b8495/ghc >--------------------------------------------------------------- commit f8bd699693493f3ba8eb10e025c5db72a75b8495 Author: Andrey Mokhov Date: Tue Feb 2 22:07:07 2016 +0000 Build GhcPkg Stage1 on OS X Travis. >--------------------------------------------------------------- f8bd699693493f3ba8eb10e025c5db72a75b8495 .travis.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index cf2f1cb..4642d70 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: false matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 + env: CABALVER=1.22 GHCVER=7.10.3 TARGET= addons: apt: packages: @@ -21,6 +21,7 @@ matrix: - cabal update - os: osx + env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg.exe before_install: - brew update - brew install ghc cabal-install @@ -61,7 +62,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick + - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET cache: directories: From git at git.haskell.org Fri Oct 27 00:16:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename GhcPkgVersionHs.hs to VersionHs.hs, refactor src/Rules/Generate.hs. (641eb2d) Message-ID: <20171027001642.7B2533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/641eb2d33053d8011be52b68ef28e4c44ddf34e5/ghc >--------------------------------------------------------------- commit 641eb2d33053d8011be52b68ef28e4c44ddf34e5 Author: Andrey Mokhov Date: Sat Dec 26 02:03:09 2015 +0000 Rename GhcPkgVersionHs.hs to VersionHs.hs, refactor src/Rules/Generate.hs. >--------------------------------------------------------------- 641eb2d33053d8011be52b68ef28e4c44ddf34e5 shaking-up-ghc.cabal | 2 +- src/Rules/Generate.hs | 27 ++++++++++------------ .../{GhcPkgVersionHs.hs => VersionHs.hs} | 8 +++---- 3 files changed, 17 insertions(+), 20 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 3f09043..d233327 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -43,7 +43,7 @@ executable ghc-shake , Rules.Documentation , Rules.Generate , Rules.Generators.ConfigHs - , Rules.Generators.GhcPkgVersionHs + , Rules.Generators.VersionHs , Rules.Generators.PlatformH , Rules.Library , Rules.Oracles diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index fd22926..13d149e1 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -3,7 +3,7 @@ module Rules.Generate (generatePackageCode) where import Expression import GHC import Rules.Generators.ConfigHs -import Rules.Generators.GhcPkgVersionHs +import Rules.Generators.VersionHs import Rules.Generators.PlatformH import Oracles.ModuleFiles import Rules.Actions @@ -32,6 +32,10 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = primopsTxt = targetPath stage compiler -/- "build/primops.txt" platformH = targetPath stage compiler -/- "ghc_boot_platform.h" generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) + generate file expr = do + contents <- interpretPartial target expr + writeFileChanged file contents + putBuild $ "| Successfully generated '" ++ file ++ "'." in do generated ?> \file -> do let pattern = "//" ++ takeBaseName file <.> "*" @@ -60,23 +64,16 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = need [primopsTxt] build $ fullTarget target GenPrimopCode [primopsTxt] [file] - priority 2.0 $ buildPath -/- "Config.hs" %> \file -> do - contents <- interpretPartial target generateConfigHs - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." + priority 2.0 $ do + when (pkg == ghcPkg) $ buildPath -/- "Config.hs" %> \file -> do + generate file generateConfigHs - when (pkg == compiler) $ platformH %> \file -> do - contents <- interpretPartial target generatePlatformH - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." - - priority 2.0 $ when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do - contents <- interpretPartial target generateGhcPkgVersionHs - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." + generate file generateVersionHs + + when (pkg == compiler) $ platformH %> \file -> do + generate file generatePlatformH - priority 2.0 $ when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putBuild $ "| Successfully generated '" ++ file ++ "'." diff --git a/src/Rules/Generators/GhcPkgVersionHs.hs b/src/Rules/Generators/VersionHs.hs similarity index 66% rename from src/Rules/Generators/GhcPkgVersionHs.hs rename to src/Rules/Generators/VersionHs.hs index f29ee97..ea6501a 100644 --- a/src/Rules/Generators/GhcPkgVersionHs.hs +++ b/src/Rules/Generators/VersionHs.hs @@ -1,11 +1,11 @@ -module Rules.Generators.GhcPkgVersionHs (generateGhcPkgVersionHs) where +module Rules.Generators.VersionHs (generateVersionHs) where import Expression import Oracles -generateGhcPkgVersionHs :: Expr String -generateGhcPkgVersionHs = do - lift $ need [sourcePath -/- "Rules/Generators/GhcPkgVersionHs.hs"] +generateVersionHs :: Expr String +generateVersionHs = do + lift $ need [sourcePath -/- "Rules/Generators/VersionHs.hs"] projectVersion <- getSetting ProjectVersion targetOs <- getSetting TargetOs targetArch <- getSetting TargetArch From git at git.haskell.org Fri Oct 27 00:16:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test the resulting GHC binary (5ad9fad) Message-ID: <20171027001642.BD8073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ad9fad8be600b7042f60cf81d61a2f3ac151dbb/ghc >--------------------------------------------------------------- commit 5ad9fad8be600b7042f60cf81d61a2f3ac151dbb Author: Andrey Mokhov Date: Wed Jun 1 09:15:00 2016 +0100 Test the resulting GHC binary See #259. >--------------------------------------------------------------- 5ad9fad8be600b7042f60cf81d61a2f3ac151dbb .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 3b61256..18ede46 100644 --- a/.travis.yml +++ b/.travis.yml @@ -60,6 +60,7 @@ script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET + - ./ghc/inplace/bin/ghc-stage2 -e 1+2 cache: directories: From git at git.haskell.org Fri Oct 27 00:16:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop exe extension. (c3fc983) Message-ID: <20171027001643.B014A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3fc983e3fe68c4e2ae74aec45e9bf2d8fa0dcf1/ghc >--------------------------------------------------------------- commit c3fc983e3fe68c4e2ae74aec45e9bf2d8fa0dcf1 Author: Andrey Mokhov Date: Tue Feb 2 22:31:37 2016 +0000 Drop exe extension. >--------------------------------------------------------------- c3fc983e3fe68c4e2ae74aec45e9bf2d8fa0dcf1 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 4642d70..d7e58c3 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - cabal update - os: osx - env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg.exe + env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Fri Oct 27 00:16:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CcClangBackend and CcLlvmBackend settings. (27d45f1) Message-ID: <20171027001645.E9C603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27d45f1b334d4af9e8ff18c159c2effa7b45d0c0/ghc >--------------------------------------------------------------- commit 27d45f1b334d4af9e8ff18c159c2effa7b45d0c0 Author: Andrey Mokhov Date: Sat Dec 26 02:58:50 2015 +0000 Add CcClangBackend and CcLlvmBackend settings. >--------------------------------------------------------------- 27d45f1b334d4af9e8ff18c159c2effa7b45d0c0 cfg/system.config.in | 2 ++ src/Oracles/Config/Setting.hs | 4 ++++ 2 files changed, 6 insertions(+) diff --git a/cfg/system.config.in b/cfg/system.config.in index 6c21f6e..12ddeed 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -41,6 +41,8 @@ hscolour = @HSCOLOUR@ gcc-is-clang = @GccIsClang@ gcc-lt-46 = @GccLT46@ ar-supports-at-file = @ArSupportsAtFile@ +cc-llvm-backend = @CC_LLVM_BACKEND@ +cc-clang-backend = @CC_CLANG_BACKEND@ # Build options: #=============== diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 8f0b1df..81e2924 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -21,6 +21,8 @@ data Setting = BuildArch | BuildOs | BuildPlatform | BuildVendor + | CcClangBackend + | CcLlvmBackend | DynamicExtension | GhcMajorVersion | GhcMinorVersion @@ -60,6 +62,8 @@ setting key = askConfig $ case key of BuildOs -> "build-os" BuildPlatform -> "build-platform" BuildVendor -> "build-vendor" + CcClangBackend -> "cc-clang-backend" + CcLlvmBackend -> "cc-llvm-backend" DynamicExtension -> "dynamic-extension" GhcMajorVersion -> "ghc-major-version" GhcMinorVersion -> "ghc-minor-version" From git at git.haskell.org Fri Oct 27 00:16:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to UseLibdw (119bda5) Message-ID: <20171027001646.3877D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/119bda593291be9748b21dc45b3a3777a980a532/ghc >--------------------------------------------------------------- commit 119bda593291be9748b21dc45b3a3777a980a532 Author: Andrey Mokhov Date: Wed Jun 1 09:48:32 2016 +0100 Switch to UseLibdw See #259. >--------------------------------------------------------------- 119bda593291be9748b21dc45b3a3777a980a532 cfg/system.config.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index f235f19..b580f86 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -115,4 +115,4 @@ ffi-lib-dir = @FFILibDir@ # Optional Dependencies: #======================= -with-libdw = @HaveLibdw@ +with-libdw = @UseLibdw@ From git at git.haskell.org Fri Oct 27 00:16:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop registerPackage predicate. (8424eb5) Message-ID: <20171027001647.369EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8424eb5e1b4a462c4a04f499c4f08cee65585fed/ghc >--------------------------------------------------------------- commit 8424eb5e1b4a462c4a04f499c4f08cee65585fed Author: Andrey Mokhov Date: Wed Feb 3 00:36:29 2016 +0000 Drop registerPackage predicate. See #200. >--------------------------------------------------------------- 8424eb5e1b4a462c4a04f499c4f08cee65585fed src/Predicates.hs | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 1e56993..c0f6095 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,7 +1,7 @@ -- | Convenient predicates module Predicates ( stage, package, builder, stagedBuilder, builderGcc, builderGhc, file, way, - stage0, stage1, stage2, notStage0, notPackage, registerPackage + stage0, stage1, stage2, notStage0, notPackage ) where import Base @@ -60,9 +60,3 @@ notStage0 = notM stage0 -- | Is a certain package /not/ built right now? notPackage :: Package -> Predicate notPackage = notM . package - --- TODO: Actually, we don't register compiler in some circumstances -- fix. --- | Do we need to run @ghc-pkg update@ on the currently built package? --- See "Rules.Data". -registerPackage :: Predicate -registerPackage = return True From git at git.haskell.org Fri Oct 27 00:16:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate includes/ghcautoconf.h, refactor Rules/Generate.hs. (6b7b9cc) Message-ID: <20171027001649.5A45C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b7b9cc86e963a4bc200ff45fe16e26b72f372dd/ghc >--------------------------------------------------------------- commit 6b7b9cc86e963a4bc200ff45fe16e26b72f372dd Author: Andrey Mokhov Date: Sat Dec 26 03:00:03 2015 +0000 Generate includes/ghcautoconf.h, refactor Rules/Generate.hs. >--------------------------------------------------------------- 6b7b9cc86e963a4bc200ff45fe16e26b72f372dd src/Main.hs | 6 ++++-- src/Rules/Generate.hs | 33 +++++++++++++++++++++++++-------- src/Rules/Generators/GhcAutoconfH.hs | 34 ++++++++++++++++++++++++++++++++++ 3 files changed, 63 insertions(+), 10 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 7a0205d..0dc8d96 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,15 +2,17 @@ import Base import Rules import Rules.Cabal import Rules.Config +import Rules.Generate import Rules.Oracles main :: IO () main = shakeArgs options $ do - generateTargets -- see Rules - packageRules -- see Rules cabalRules -- see Rules.Cabal configRules -- see Rules.Config + generateTargets -- see Rules + generateRules -- see Rules.Generate oracleRules -- see Rules.Oracles + packageRules -- see Rules where options = shakeOptions { shakeFiles = shakeFilesPath diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 13d149e1..8f60dd0 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,8 +1,9 @@ -module Rules.Generate (generatePackageCode) where +module Rules.Generate (generatePackageCode, generateRules) where import Expression import GHC import Rules.Generators.ConfigHs +import Rules.Generators.GhcAutoconfH import Rules.Generators.VersionHs import Rules.Generators.PlatformH import Oracles.ModuleFiles @@ -25,6 +26,13 @@ determineBuilder file = fmap fst $ find (\(_, e) -> e == ext) knownGenerators where ext = takeExtension file +generate :: FilePath -> PartialTarget -> Expr String -> Action () +generate file target expr = do + contents <- interpretPartial target expr + writeFileChanged file contents + putBuild $ "| Successfully generated '" ++ file ++ "'." + + generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let path = targetPath stage pkg @@ -32,10 +40,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = primopsTxt = targetPath stage compiler -/- "build/primops.txt" platformH = targetPath stage compiler -/- "ghc_boot_platform.h" generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) - generate file expr = do - contents <- interpretPartial target expr - writeFileChanged file contents - putBuild $ "| Successfully generated '" ++ file ++ "'." + file <~ gen = generate file target gen in do generated ?> \file -> do let pattern = "//" ++ takeBaseName file <.> "*" @@ -66,14 +71,26 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = priority 2.0 $ do when (pkg == ghcPkg) $ buildPath -/- "Config.hs" %> \file -> do - generate file generateConfigHs + file <~ generateConfigHs when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do - generate file generateVersionHs + file <~ generateVersionHs when (pkg == compiler) $ platformH %> \file -> do - generate file generatePlatformH + file <~ generatePlatformH when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putBuild $ "| Successfully generated '" ++ file ++ "'." + +generateRules :: Rules () +generateRules = do + "includes/ghcautoconf.h" <~ generateGhcAutoconfH + where + file <~ gen = file %> \out -> generate out fakeTarget gen + +-- TODO: Use the Types, Luke! (drop partial function) +fakeTarget :: PartialTarget +fakeTarget = PartialTarget (error "fakeTarget: unknown stage") + (error "fakeTarget: unknown package") + diff --git a/src/Rules/Generators/GhcAutoconfH.hs b/src/Rules/Generators/GhcAutoconfH.hs new file mode 100644 index 0000000..6d49603 --- /dev/null +++ b/src/Rules/Generators/GhcAutoconfH.hs @@ -0,0 +1,34 @@ +module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH) where + +import Expression +import Oracles + +-- TODO: change `mk/config.h` to `shake-build/cfg/config.h` +configH :: FilePath +configH = "mk/config.h" + +undefinePackage :: String -> String +undefinePackage s + | "#define PACKAGE_" `isPrefixOf` s + = "/* #undef " ++ takeWhile (/=' ') (drop 8 s) ++ " */" + | otherwise = s + +generateGhcAutoconfH :: Expr String +generateGhcAutoconfH = do + lift $ need [sourcePath -/- "Rules/Generators/GhcAutoconfH.hs"] + configHContents <- lift $ map undefinePackage <$> readFileLines configH + tablesNextToCode <- lift $ ghcEnableTablesNextToCode + ghcUnreg <- getFlag GhcUnregisterised + ccLlvmBackend <- getSetting CcLlvmBackend + ccClangBackend <- getSetting CcClangBackend + return . unlines $ + [ "#ifndef __GHCAUTOCONF_H__" + , "#define __GHCAUTOCONF_H__" ] + ++ configHContents ++ + [ "\n#define TABLES_NEXT_TO_CODE 1" | tablesNextToCode && not ghcUnreg ] + ++ + [ "\n#define llvm_CC_FLAVOR 1" | ccLlvmBackend == "1" ] + ++ + [ "\n#define clang_CC_FLAVOR 1" | ccClangBackend == "1" ] + ++ + [ "#endif /* __GHCAUTOCONF_H__ */" ] From git at git.haskell.org Fri Oct 27 00:16:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to user settings (d58dabf) Message-ID: <20171027001649.987473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d58dabfd7ca07e50374b7c859f81b8ed55dc600c/ghc >--------------------------------------------------------------- commit d58dabfd7ca07e50374b7c859f81b8ed55dc600c Author: Andrey Mokhov Date: Thu Jun 2 23:19:21 2016 +0100 Fix path to user settings [skip ci] >--------------------------------------------------------------- d58dabfd7ca07e50374b7c859f81b8ed55dc600c README.md | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/README.md b/README.md index b1da6f7..d99d2b7 100644 --- a/README.md +++ b/README.md @@ -88,8 +88,7 @@ by Shake oracles. #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We -use `./UserSettings.hs` for the same purpose, see -[documentation](doc/user-settings.md). +use `hadrian/UserSettings.hs` for the same purpose, see [documentation](doc/user-settings.md). #### Clean and full rebuild From git at git.haskell.org Fri Oct 27 00:16:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Settings.Paths, add pkgConfFile. (c1364e5) Message-ID: <20171027001650.9D77D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1364e54b2178d83410dfa12ff468423e51728fa/ghc >--------------------------------------------------------------- commit c1364e54b2178d83410dfa12ff468423e51728fa Author: Andrey Mokhov Date: Wed Feb 3 00:38:41 2016 +0000 Refactor Settings.Paths, add pkgConfFile. See #200. >--------------------------------------------------------------- c1364e54b2178d83410dfa12ff468423e51728fa src/Rules.hs | 8 +++----- src/Rules/Program.hs | 9 ++++----- src/Settings/Paths.hs | 33 ++++++++++++++++++++++++--------- 3 files changed, 31 insertions(+), 19 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index b22e028..1d92baf 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -4,7 +4,6 @@ import Base import Data.Foldable import Expression import GHC -import Oracles.PackageData import qualified Rules.Generate import Rules.Package import Rules.Resources @@ -22,8 +21,8 @@ topLevelTargets = do -- TODO: do we want libffiLibrary to be a top-level target? action $ do -- TODO: Add support for all rtsWays - rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla - rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded + rtsLib <- pkgLibraryFile Stage1 rts vanilla + rtsThrLib <- pkgLibraryFile Stage1 rts threaded need [ rtsLib, rtsThrLib ] for_ allStages $ \stage -> @@ -34,8 +33,7 @@ topLevelTargets = do if isLibrary pkg then do -- build a library ways <- interpretPartial target getLibraryWays - compId <- interpretPartial target $ getPkgData ComponentId - libs <- traverse (pkgLibraryFile stage pkg compId) ways + libs <- traverse (pkgLibraryFile stage pkg) ways haddock <- interpretPartial target buildHaddock need $ libs ++ [ pkgHaddockFile pkg | haddock && stage == Stage1 ] else do -- otherwise build a program diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index d472e88..9a5b501 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -86,14 +86,13 @@ buildBinary target @ (PartialTarget stage pkg) bin = do let deps = matchPackageNames (sort pkgs) (map PackageName $ sort depNames) ghci = ghciFlag == "YES" && stage == Stage1 libs <- fmap concat . forM deps $ \dep -> do - let depTarget = PartialTarget libStage dep - compId <- interpretPartial depTarget $ getPkgData ComponentId libFiles <- fmap concat . forM ways $ \way -> do - libFile <- pkgLibraryFile libStage dep compId way - lib0File <- pkgLibraryFile libStage dep (compId ++ "-0") way + libFile <- pkgLibraryFile libStage dep way + lib0File <- pkgLibraryFile0 libStage dep way dll0 <- needDll0 libStage dep return $ libFile : [ lib0File | dll0 ] - return $ libFiles ++ [ pkgGhciLibraryFile libStage dep compId | ghci ] + ghciLib <- pkgGhciLibraryFile libStage dep + return $ libFiles ++ [ ghciLib | ghci ] let binDeps = if pkg == ghcCabal && stage == Stage0 then [ pkgPath pkg -/- src <.> "hs" | src <- hSrcs ] else objs diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index a152f9a..20f4721 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,11 +1,13 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgGhciLibraryFile, gmpBuildPath, gmpLibNameCache, packageDbDirectory + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibNameCache, + packageDbDirectory, pkgConfFile ) where import Base import Expression import GHC +import Oracles.PackageData import Settings.User -- Path to the target directory from GHC source root @@ -24,18 +26,26 @@ pkgHaddockFile pkg = -- Relative path to a package library file, e.g.: -- "libraries/array/stage2/build/libHSarray-0.5.1.0.a" --- TODO: remove code duplication for computing buildPath -pkgLibraryFile :: Stage -> Package -> String -> Way -> Action FilePath -pkgLibraryFile stage pkg componentId way = do +pkgLibraryFile :: Stage -> Package -> Way -> Action FilePath +pkgLibraryFile stage pkg way = do extension <- libsuf way - let buildPath = targetPath stage pkg -/- "build" - return $ buildPath -/- "libHS" ++ componentId ++ extension + pkgFile stage pkg "build/libHS" extension + +pkgLibraryFile0 :: Stage -> Package -> Way -> Action FilePath +pkgLibraryFile0 stage pkg way = do + extension <- libsuf way + pkgFile stage pkg "build/libHS" ("-0" ++ extension) -- Relative path to a package ghci library file, e.g.: -- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" -pkgGhciLibraryFile :: Stage -> Package -> String -> FilePath -pkgGhciLibraryFile stage pkg componentId = - targetPath stage pkg -/- "build" -/- "HS" ++ componentId <.> "o" +pkgGhciLibraryFile :: Stage -> Package -> Action FilePath +pkgGhciLibraryFile stage pkg = pkgFile stage pkg "build/HS" ".o" + +pkgFile :: Stage -> Package -> String -> String -> Action FilePath +pkgFile stage pkg prefix suffix = do + let path = targetPath stage pkg + componentId <- pkgData $ ComponentId path + return $ path -/- prefix ++ componentId ++ suffix -- This is the build directory for in-tree GMP library gmpBuildPath :: FilePath @@ -50,3 +60,8 @@ gmpLibNameCache = gmpBuildPath -/- "gmp-lib-names" packageDbDirectory :: Stage -> FilePath packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" + +pkgConfFile :: Stage -> Package -> Action FilePath +pkgConfFile stage pkg = do + componentId <- pkgData . ComponentId $ targetPath stage pkg + return $ packageDbDirectory stage -/- componentId <.> "conf" From git at git.haskell.org Fri Oct 27 00:16:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add config.h.in to shake-build/cfg. This file is needed for Rules.Generators.GhcAutoconfH. (47529e5) Message-ID: <20171027001653.051183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47529e5ee25f3caa958f566f6eb85e62d86235ee/ghc >--------------------------------------------------------------- commit 47529e5ee25f3caa958f566f6eb85e62d86235ee Author: Andrey Mokhov Date: Sat Dec 26 03:01:26 2015 +0000 Add config.h.in to shake-build/cfg. This file is needed for Rules.Generators.GhcAutoconfH. >--------------------------------------------------------------- 47529e5ee25f3caa958f566f6eb85e62d86235ee cfg/config.h.in | 463 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 463 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 47529e5ee25f3caa958f566f6eb85e62d86235ee From git at git.haskell.org Fri Oct 27 00:16:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to user settings (157b855) Message-ID: <20171027001653.609A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/157b855a026ca48b69ba0dba6a473c34f23cfaa4/ghc >--------------------------------------------------------------- commit 157b855a026ca48b69ba0dba6a473c34f23cfaa4 Author: Andrey Mokhov Date: Thu Jun 2 23:27:10 2016 +0100 Fix paths to user settings [skip ci] >--------------------------------------------------------------- 157b855a026ca48b69ba0dba6a473c34f23cfaa4 doc/user-settings.md | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index a5185ad..1dbfd6f 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,8 +1,9 @@ # User settings -You can customise Hadrian by copying the file ./src/UserSettings.hs to -./UserSettings.hs and specifying user build settings in -`./UserSettings.hs`. Here we document currently supported settings. +You can customise Hadrian by copying the file `hadrian/src/UserSettings.hs` to +`hadrian/UserSettings.hs` and overriding the default build settings (if you don't +copy the file your changes will be tracked by `git` and you can accidentally commit +them). Here we document currently supported settings. ## Build directory From git at git.haskell.org Fri Oct 27 00:16:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decouple buildPackageData and registerPackage rules. (9129e8b) Message-ID: <20171027001654.569143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9129e8bc158dab081094554abc4dcbef3f8b2a5f/ghc >--------------------------------------------------------------- commit 9129e8bc158dab081094554abc4dcbef3f8b2a5f Author: Andrey Mokhov Date: Wed Feb 3 00:39:32 2016 +0000 Decouple buildPackageData and registerPackage rules. See #200. >--------------------------------------------------------------- 9129e8bc158dab081094554abc4dcbef3f8b2a5f shaking-up-ghc.cabal | 1 + src/Rules/Data.hs | 26 ++++---------------------- src/Rules/Documentation.hs | 3 ++- src/Rules/Package.hs | 30 ++++++++++++++++-------------- src/Rules/Register.hs | 39 +++++++++++++++++++++++++++++++++++++++ 5 files changed, 62 insertions(+), 37 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f00c7c6..0807ff3 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -62,6 +62,7 @@ executable ghc-shake , Rules.Package , Rules.Perl , Rules.Program + , Rules.Register , Rules.Resources , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index fbe22db..f2e3d43 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -6,7 +6,6 @@ import Base import Expression import GHC import Oracles -import Predicates (registerPackage) import Rules.Actions import Rules.Generate import Rules.Libffi @@ -29,14 +28,14 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do orderOnly $ generatedDependencies stage pkg -- GhcCabal may run the configure script, so we depend on it - -- We don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - -- We configure packages in the order of their dependencies + -- Before we configure a package its dependencies need to be registered deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - orderOnly $ map (pkgDataFile stage) depPkgs + depConfs <- traverse (pkgConfFile stage) depPkgs + orderOnly depConfs -- TODO: get rid of this, see #113 let inTreeMk = oldPath -/- takeFileName dataFile @@ -52,23 +51,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do forM_ autogenFiles $ \file -> do copyFile (oldPath -/- file) (targetPath stage pkg -/- file) - -- ghc-pkg produces inplace-pkg-config when run on packages with - -- library components only - when (isLibrary pkg) . - whenM (interpretPartial target registerPackage) $ do - - -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 - let fixPkgConf = unlines - . map (replace oldPath (targetPath stage pkg) - . replace (replaceSeparators '\\' $ oldPath) - (targetPath stage pkg) ) - . lines - - fixFile (oldPath -/- "inplace-pkg-config") fixPkgConf - - buildWithResources [(resGhcPkg rs, 1)] $ - fullTarget target (GhcPkg stage) [cabalFile] [] - postProcessPackageData stage pkg dataFile -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps @@ -141,7 +123,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do [ "C_SRCS = " ++ unwords (cSrcs ++ cmmSrcs ++ sSrcs ++ extraSrcs) , "CC_OPTS = " ++ unwords includes - , "COMPONENT_ID = " ++ "rts" ] + , "COMPONENT_ID = rts" ] writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index cb74952..e235bfc 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -26,7 +26,8 @@ buildPackageDocumentation _ target @ (PartialTarget stage pkg) = -- HsColour sources whenM (specified HsColour) $ do - need [cabalFile, pkgDataFile stage pkg ] + pkgConf <- pkgConfFile stage pkg + need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf build $ fullTarget target GhcCabalHsColour [cabalFile] [] -- Build Haddock documentation diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 7a7d854..28fe635 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -1,22 +1,24 @@ module Rules.Package (buildPackage) where import Base -import Rules.Compile -import Rules.Data -import Rules.Dependencies -import Rules.Documentation -import Rules.Generate -import Rules.Library -import Rules.Program +import qualified Rules.Compile +import qualified Rules.Data +import qualified Rules.Dependencies +import qualified Rules.Documentation +import qualified Rules.Generate +import qualified Rules.Library +import qualified Rules.Program +import qualified Rules.Register import Rules.Resources import Target buildPackage :: Resources -> PartialTarget -> Rules () buildPackage = mconcat - [ buildPackageData - , buildPackageDependencies - , generatePackageCode - , compilePackage - , buildPackageLibrary - , buildPackageDocumentation - , buildProgram ] + [ Rules.Compile.compilePackage + , Rules.Data.buildPackageData + , Rules.Dependencies.buildPackageDependencies + , Rules.Documentation.buildPackageDocumentation + , Rules.Generate.generatePackageCode + , Rules.Library.buildPackageLibrary + , Rules.Program.buildProgram + , Rules.Register.registerPackage ] diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs new file mode 100644 index 0000000..8c3ec73 --- /dev/null +++ b/src/Rules/Register.hs @@ -0,0 +1,39 @@ +module Rules.Register (registerPackage) where + +import Data.Char + +import Base +import Expression +import GHC +import Rules.Actions +import Rules.Resources +import Settings + +-- matchPkgConf :: FilePath -> Bool +-- matchPkgConf file = + +-- Build package-data.mk by using GhcCabal to process pkgCabal file +registerPackage :: Resources -> PartialTarget -> Rules () +registerPackage rs target @ (PartialTarget stage pkg) = do + let oldPath = pkgPath pkg -/- targetDirectory stage pkg -- TODO: remove, #113 + pkgConf = packageDbDirectory stage -/- pkgNameString pkg + match f = case stripPrefix (pkgConf ++ "-") f of + Nothing -> False + Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf" + + when (stage <= Stage1) $ match ?> \_ -> do + -- This produces pkgConfig. TODO: Add explicit tracking + need [pkgDataFile stage pkg] + + -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 + let pkgConfig = oldPath -/- "inplace-pkg-config" + fixPkgConf = unlines + . map (replace oldPath (targetPath stage pkg) + . replace (replaceSeparators '\\' $ oldPath) + (targetPath stage pkg) ) + . lines + + fixFile pkgConfig fixPkgConf + + buildWithResources [(resGhcPkg rs, 1)] $ + fullTarget target (GhcPkg stage) [pkgConfig] [] From git at git.haskell.org Fri Oct 27 00:16:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate includes/ghcplatform.h (8c32f2c) Message-ID: <20171027001656.D12913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c32f2c931d68e1f847cfefb8f4d514886217873/ghc >--------------------------------------------------------------- commit 8c32f2c931d68e1f847cfefb8f4d514886217873 Author: Andrey Mokhov Date: Sat Dec 26 03:39:41 2015 +0000 Generate includes/ghcplatform.h >--------------------------------------------------------------- 8c32f2c931d68e1f847cfefb8f4d514886217873 shaking-up-ghc.cabal | 4 +- src/Rules/Generate.hs | 8 ++-- .../{PlatformH.hs => GhcBootPlatformH.hs} | 8 ++-- src/Rules/Generators/GhcPlatformH.hs | 55 ++++++++++++++++++++++ 4 files changed, 67 insertions(+), 8 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index d233327..1e0fbbf 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -43,8 +43,10 @@ executable ghc-shake , Rules.Documentation , Rules.Generate , Rules.Generators.ConfigHs + , Rules.Generators.GhcAutoconfH + , Rules.Generators.GhcBootPlatformH + , Rules.Generators.GhcPlatformH , Rules.Generators.VersionHs - , Rules.Generators.PlatformH , Rules.Library , Rules.Oracles , Rules.Package diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8f60dd0..f9c1e0b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -4,8 +4,9 @@ import Expression import GHC import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH +import Rules.Generators.GhcBootPlatformH +import Rules.Generators.GhcPlatformH import Rules.Generators.VersionHs -import Rules.Generators.PlatformH import Oracles.ModuleFiles import Rules.Actions import Rules.Resources (Resources) @@ -56,12 +57,12 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = whenM (doesFileExist srcBoot) $ copyFileChanged srcBoot $ file -<.> "hs-boot" + -- TODO: needing platformH is ugly and fragile when (pkg == compiler) $ primopsTxt %> \file -> do need [platformH, primopsSource] build $ fullTarget target HsCpp [primopsSource] [file] -- TODO: why different folders for generated files? - -- TODO: needing platformH is ugly and fragile fmap (buildPath -/-) [ "GHC/PrimopWrappers.hs" , "autogen/GHC/Prim.hs" @@ -77,7 +78,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = file <~ generateVersionHs when (pkg == compiler) $ platformH %> \file -> do - file <~ generatePlatformH + file <~ generateGhcBootPlatformH when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file @@ -86,6 +87,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = generateRules :: Rules () generateRules = do "includes/ghcautoconf.h" <~ generateGhcAutoconfH + "includes/ghcplatform.h" <~ generateGhcPlatformH where file <~ gen = file %> \out -> generate out fakeTarget gen diff --git a/src/Rules/Generators/PlatformH.hs b/src/Rules/Generators/GhcBootPlatformH.hs similarity index 91% rename from src/Rules/Generators/PlatformH.hs rename to src/Rules/Generators/GhcBootPlatformH.hs index cc29a1b..93b953b 100644 --- a/src/Rules/Generators/PlatformH.hs +++ b/src/Rules/Generators/GhcBootPlatformH.hs @@ -1,11 +1,11 @@ -module Rules.Generators.PlatformH (generatePlatformH) where +module Rules.Generators.GhcBootPlatformH (generateGhcBootPlatformH) where import Expression import Oracles -generatePlatformH :: Expr String -generatePlatformH = do - lift $ need [sourcePath -/- "Rules/Generators/PlatformH.hs"] +generateGhcBootPlatformH :: Expr String +generateGhcBootPlatformH = do + lift $ need [sourcePath -/- "Rules/Generators/GhcBootPlatformH.hs"] stage <- getStage let cppify = replaceEq '-' '_' . replaceEq '.' '_' chooseSetting x y = getSetting $ if stage == Stage0 then x else y diff --git a/src/Rules/Generators/GhcPlatformH.hs b/src/Rules/Generators/GhcPlatformH.hs new file mode 100644 index 0000000..2bdf5d4 --- /dev/null +++ b/src/Rules/Generators/GhcPlatformH.hs @@ -0,0 +1,55 @@ +module Rules.Generators.GhcPlatformH (generateGhcPlatformH) where + +import Expression +import Oracles + +generateGhcPlatformH :: Expr String +generateGhcPlatformH = do + lift $ need [sourcePath -/- "Rules/Generators/GhcPlatformH.hs"] + let cppify = replaceEq '-' '_' . replaceEq '.' '_' + hostPlatform <- getSetting HostPlatform + hostArch <- getSetting HostArch + hostOs <- getSetting HostOs + hostVendor <- getSetting HostVendor + targetPlatform <- getSetting TargetPlatform + targetArch <- getSetting TargetArch + targetOs <- getSetting TargetOs + targetVendor <- getSetting TargetVendor + ghcUnreg <- getFlag GhcUnregisterised + return . unlines $ + [ "#ifndef __GHCPLATFORM_H__" + , "#define __GHCPLATFORM_H__" + , "" + , "#define BuildPlatform_TYPE " ++ cppify hostPlatform + , "#define HostPlatform_TYPE " ++ cppify targetPlatform + , "" + , "#define " ++ cppify hostPlatform ++ "_BUILD 1" + , "#define " ++ cppify targetPlatform ++ "_HOST 1" + , "" + , "#define " ++ hostArch ++ "_BUILD_ARCH 1" + , "#define " ++ targetArch ++ "_HOST_ARCH 1" + , "#define BUILD_ARCH " ++ quote hostArch + , "#define HOST_ARCH " ++ quote targetArch + , "" + , "#define " ++ hostOs ++ "_BUILD_OS 1" + , "#define " ++ targetOs ++ "_HOST_OS 1" + , "#define BUILD_OS " ++ quote hostOs + , "#define HOST_OS " ++ quote targetOs + , "" + , "#define " ++ hostVendor ++ "_BUILD_VENDOR 1" + , "#define " ++ targetVendor ++ "_HOST_VENDOR 1" + , "#define BUILD_VENDOR " ++ quote hostVendor + , "#define HOST_VENDOR " ++ quote targetVendor + , "" + , "/* These TARGET macros are for backwards compatibility... DO NOT USE! */" + , "#define TargetPlatform_TYPE " ++ cppify targetPlatform + , "#define " ++ cppify targetPlatform ++ "_TARGET 1" + , "#define " ++ targetArch ++ "_TARGET_ARCH 1" + , "#define TARGET_ARCH " ++ quote targetArch + , "#define " ++ targetOs ++ "_TARGET_OS 1" + , "#define TARGET_OS " ++ quote targetOs + , "#define " ++ targetVendor ++ "_TARGET_VENDOR 1" ] + ++ + [ "#define UnregisterisedCompiler 1" | ghcUnreg ] + ++ + [ "\n#endif /* __GHCPLATFORM_H__ */" ] From git at git.haskell.org Fri Oct 27 00:16:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge build.cabal-new.sh into build.cabal.sh (af6a040) Message-ID: <20171027001657.125C23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/af6a040742b654d018bfd2fe4dc839a94aa083db/ghc >--------------------------------------------------------------- commit af6a040742b654d018bfd2fe4dc839a94aa083db Author: Herbert Valerio Riedel Date: Fri Jun 3 22:19:36 2016 +0200 Merge build.cabal-new.sh into build.cabal.sh The script now detect the cabal version and uses either the robust and fast 'new-build'-logic (for version 1.24 or later), or falls back to the fragile sandbox-based legacy logic. >--------------------------------------------------------------- af6a040742b654d018bfd2fe4dc839a94aa083db build.cabal-new.sh | 58 ------------------------------------------------------ build.cabal.sh | 50 +++++++++++++++++++++++++++++++++++----------- build.sh | 9 +++++++++ 3 files changed, 48 insertions(+), 69 deletions(-) diff --git a/build.cabal-new.sh b/build.cabal-new.sh deleted file mode 100755 index 65e222a..0000000 --- a/build.cabal-new.sh +++ /dev/null @@ -1,58 +0,0 @@ -#!/usr/bin/env bash - -# This wrapper scripts makes use of cabal 1.24+'s nix-store; -# In order to clean/reset, remove the `dist-newstyle/` folder - -set -euo pipefail - -# readlink on os x, doesn't support -f, to prevent the -# need of installing coreutils (e.g. through brew, just -# for readlink, we use the follownig substitute. -# -# source: http://stackoverflow.com/a/1116890 -function rl { - TARGET_FILE="$1" - - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - - # Iterate down a (possible) chain of symlinks - while [ -L "$TARGET_FILE" ] - do - TARGET_FILE="$(readlink "$TARGET_FILE")" - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - done - - # Compute the canonicalized name by finding the physical path - # for the directory we're in and appending the target file. - PHYS_DIR="$(pwd -P)" - RESULT="$PHYS_DIR/$TARGET_FILE" - echo "$RESULT" -} - -root="$(dirname "$(rl "$0")")" - -mkdir -p "$root/.shake" - -# Notes/Random thoughts: -# -# - if ghc.git had a top-level `cabal.project` file, we could maybe avoid the -# boilerplate above, as we could simply say `cabal exec hadrian` from within -# any GHC folder not shadowed by a nearer shadowing `cabal.project` file. - -pushd "$root/" - -cabal new-build --disable-profiling --disable-documentation -j exe:hadrian - -PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" - -cp -v "$root/dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ - "$root/.shake/build" - -popd - -"$root/.shake/build" \ - --lint \ - --directory "$root/.." \ - "$@" diff --git a/build.cabal.sh b/build.cabal.sh index 08ff972..4a24dac 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -1,5 +1,7 @@ #!/usr/bin/env bash +CABAL=cabal + set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -31,16 +33,42 @@ function rl { absoluteRoot="$(dirname "$(rl "$0")")" cd "$absoluteRoot" -# Initialize sandbox if necessary -if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then - cabal sandbox init - cabal install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared +if ! type "$CABAL" > /dev/null; then + echo "Please make sure 'cabal' is in your PATH" + exit 2 fi -cabal run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" +CABVERSTR=$("$CABAL" --numeric-version) + +CABVER=( ${CABVERSTR//./ } ) + +if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then + # New enough cabal version detected, so + # let's use the superior 'cabal new-build' mode + + # there's no 'cabal new-run' yet, but it's easy to emulate + "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian + PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" + "./dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" + +else + # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals + echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." + + # Initialize sandbox if necessary + if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then + "$CABAL" sandbox init + "$CABAL" install \ + --dependencies-only \ + --disable-library-profiling \ + --disable-shared + fi + + "$CABAL" run hadrian -- \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" +fi diff --git a/build.sh b/build.sh index 24fdc2f..d627c58 100755 --- a/build.sh +++ b/build.sh @@ -30,6 +30,15 @@ function rl { root="$(dirname "$(rl "$0")")" +if type cabal > /dev/null 2>&1; then + CABVERSTR=$(cabal --numeric-version) + CABVER=( ${CABVERSTR//./ } ) + if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then + echo "** Cabal 1.24 or later detected. Please consider using the 'build.cabal.sh' script **" + echo "" + fi +fi + mkdir -p "$root/../_build/hadrian" ghc \ From git at git.haskell.org Fri Oct 27 00:16:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:16:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop ghc-cabal resource. (13d735f) Message-ID: <20171027001657.E52C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13d735f298d0a51a83c422a34e9844058ca5e89d/ghc >--------------------------------------------------------------- commit 13d735f298d0a51a83c422a34e9844058ca5e89d Author: Andrey Mokhov Date: Wed Feb 3 01:03:46 2016 +0000 Drop ghc-cabal resource. See #200. >--------------------------------------------------------------- 13d735f298d0a51a83c422a34e9844058ca5e89d src/Rules/Data.hs | 3 +-- src/Rules/Resources.hs | 10 +++------- 2 files changed, 4 insertions(+), 9 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index f2e3d43..ade93fd 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -41,8 +41,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do let inTreeMk = oldPath -/- takeFileName dataFile need [cabalFile] - buildWithResources [(resGhcCabal rs, 1)] $ - fullTarget target GhcCabal [cabalFile] [inTreeMk] + build $ fullTarget target GhcCabal [cabalFile] [inTreeMk] -- TODO: get rid of this, see #113 liftIO $ IO.copyFile inTreeMk dataFile diff --git a/src/Rules/Resources.hs b/src/Rules/Resources.hs index 514a222..d5e58fe 100644 --- a/src/Rules/Resources.hs +++ b/src/Rules/Resources.hs @@ -4,13 +4,9 @@ import Base data Resources = Resources { - resGhcCabal :: Resource, - resGhcPkg :: Resource + resGhcPkg :: Resource } --- Unfortunately parallel invokations of ghc-cabal or ghc-pkg do not work: --- * https://mail.haskell.org/pipermail/ghc-commits/2013-May/001712.html --- * ghc.mk: see comment about parallel ghc-pkg invokations +-- We cannot register multiple packages in parallel: resourceRules :: Rules Resources -resourceRules = liftM2 Resources (newResource "ghc-cabal" 1) - (newResource "ghc-pkg" 1) +resourceRules = Resources <$> newResource "ghc-pkg" 1 From git at git.haskell.org Fri Oct 27 00:17:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add "--template" and "-I" arguments to hsc2HsArgs (efbe44f) Message-ID: <20171027001700.A7C023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efbe44f845b88e3885e1c63adcf66c57c5af1f77/ghc >--------------------------------------------------------------- commit efbe44f845b88e3885e1c63adcf66c57c5af1f77 Author: Moritz Angermann Date: Sat Dec 26 17:38:05 2015 +0800 Add "--template" and "-I" arguments to hsc2HsArgs This should fix #35. To have this fully working, #44 needs to be solved as well. >--------------------------------------------------------------- efbe44f845b88e3885e1c63adcf66c57c5af1f77 src/Settings/Builders/Hsc2Hs.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 0e31b4f..0c6172d 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -13,6 +13,7 @@ hsc2HsArgs = builder Hsc2Hs ? do gmpDirs <- getSettingList GmpIncludeDirs cFlags <- getCFlags lFlags <- getLFlags + top <- getSetting GhcSourcePath hArch <- getSetting HostArch hOs <- getSetting HostOs tArch <- getSetting TargetArch @@ -32,6 +33,8 @@ hsc2HsArgs = builder Hsc2Hs ? do , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) , arg ("--cflag=-D__GLASGOW_HASKELL__=" ++ version) + , arg $ "--template=" ++ top -/- "inplace/lib/template-hsc.h" + , arg $ "-I" ++ top -/- "inplace/lib/include/" , arg =<< getInput , arg "-o", arg =<< getOutput ] From git at git.haskell.org Fri Oct 27 00:17:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (c9e7570) Message-ID: <20171027001701.8F9323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9e7570bea7562ca05b6c1469759dfdf9e675e06/ghc >--------------------------------------------------------------- commit c9e7570bea7562ca05b6c1469759dfdf9e675e06 Author: Andrey Mokhov Date: Sat Jun 4 21:56:12 2016 +0100 Minor revision >--------------------------------------------------------------- c9e7570bea7562ca05b6c1469759dfdf9e675e06 src/Settings/Builders/Make.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index afb46d7..7283b4b 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -7,8 +7,8 @@ import Settings makeBuilderArgs :: Args makeBuilderArgs = do threads <- shakeThreads <$> lift getShakeOptions - let j = "-j" ++ show threads + let t = show threads mconcat - [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=" ++ j] - , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=" ++ j, "install"] - , builder (Make "testsuite/tests") ? append ["THREADS=" ++ show threads, "fast"] ] + [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=-j" ++ t] + , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=-j" ++ t, "install"] + , builder (Make "testsuite/tests") ? append ["THREADS=" ++ t, "fast"] ] From git at git.haskell.org Fri Oct 27 00:17:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update stack.yaml to lts-5.1 (82b665e) Message-ID: <20171027001702.1E0B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82b665e184a92fb27bc894e6f0fe2d186ea1fbe0/ghc >--------------------------------------------------------------- commit 82b665e184a92fb27bc894e6f0fe2d186ea1fbe0 Author: Joe Hillenbrand Date: Wed Feb 3 10:35:55 2016 -0800 Update stack.yaml to lts-5.1 I don't plan to change this file every time there is a new stackage lts, but lts-4.x has a bug with aeson. >--------------------------------------------------------------- 82b665e184a92fb27bc894e6f0fe2d186ea1fbe0 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index 2bc3b0e..0772c76 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,7 +1,7 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-4.2 +resolver: lts-5.1 # Local packages, usually specified by relative directory name packages: From git at git.haskell.org Fri Oct 27 00:17:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up switching from Settings.User to UserSettings (39f0509) Message-ID: <20171027001705.938AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39f05090304de772238002ed16ff6a2b8023201d/ghc >--------------------------------------------------------------- commit 39f05090304de772238002ed16ff6a2b8023201d Author: Andrey Mokhov Date: Sat Jun 4 23:40:52 2016 +0100 Clean up switching from Settings.User to UserSettings >--------------------------------------------------------------- 39f05090304de772238002ed16ff6a2b8023201d cfg/system.config.in | 6 +++--- hadrian.cabal | 2 +- src/GHC.hs | 2 +- src/Oracles/PackageDatabase.hs | 2 +- src/Rules/Clean.hs | 2 +- src/Rules/Configure.hs | 2 +- src/Rules/Generators/Common.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Selftest.hs | 2 +- src/Rules/Test.hs | 2 +- src/Settings.hs | 4 ++-- src/Settings/Args.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/Paths.hs | 2 +- src/Settings/User.hs | 12 ------------ src/Settings/Ways.hs | 2 +- src/UserSettings.hs | 10 +++++----- 18 files changed, 25 insertions(+), 37 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 39f05090304de772238002ed16ff6a2b8023201d From git at git.haskell.org Fri Oct 27 00:17:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds OS X Section to Readme (1046838) Message-ID: <20171027001704.41EDA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1046838060dfdacbdf7cdf8e2994edf71e5c0a5f/ghc >--------------------------------------------------------------- commit 1046838060dfdacbdf7cdf8e2994edf71e5c0a5f Author: Moritz Angermann Date: Sat Dec 26 18:06:27 2015 +0800 Adds OS X Section to Readme Still fails at #47 >--------------------------------------------------------------- 1046838060dfdacbdf7cdf8e2994edf71e5c0a5f README.md | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/README.md b/README.md index 6d27b25..9844bf6 100644 --- a/README.md +++ b/README.md @@ -48,6 +48,22 @@ $ shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. +### Mac OS X + +```bash +git clone git://git.haskell.org/ghc +cd ghc +git submodule update --init +git clone git://github.com/snowleopard/shaking-up-ghc shake-build +./boot +./configure --with-gcc=$(which clang) # See #26 +./shake-build/build.sh includes/ghcautoconf.h # See #48 +./shake-build/build.sh includes/ghcplatform.h # See #48 +cp utils/hsc2hs/template-hsc.h inplace/lib/template-hsc.h # See #44 +./shake-build/build.sh +``` + +See the Linux section for running in a Cabal sandbox. ### Resetting the build From git at git.haskell.org Fri Oct 27 00:17:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #202 from joehillen/patch-1 (793587b) Message-ID: <20171027001706.17ABC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/793587bd5c2a0981221e7d11fe57071f5367e021/ghc >--------------------------------------------------------------- commit 793587bd5c2a0981221e7d11fe57071f5367e021 Merge: 13d735f 82b665e Author: Andrey Mokhov Date: Wed Feb 3 18:50:40 2016 +0000 Merge pull request #202 from joehillen/patch-1 Update stack.yaml to lts-5.1 [skip ci] >--------------------------------------------------------------- 793587bd5c2a0981221e7d11fe57071f5367e021 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:17:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #46 from angerman/feature/fix-hsc2hs (9d1952f) Message-ID: <20171027001707.B2BDD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d1952faa145acb44725465cf738dd9448e0892e/ghc >--------------------------------------------------------------- commit 9d1952faa145acb44725465cf738dd9448e0892e Merge: 8c32f2c efbe44f Author: Andrey Mokhov Date: Sat Dec 26 11:50:27 2015 +0000 Merge pull request #46 from angerman/feature/fix-hsc2hs Add "--template" and "-I" arguments to hsc2HsArgs >--------------------------------------------------------------- 9d1952faa145acb44725465cf738dd9448e0892e src/Settings/Builders/Hsc2Hs.hs | 3 +++ 1 file changed, 3 insertions(+) From git at git.haskell.org Fri Oct 27 00:17:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #260 from hvr/pr/unify-cabal-script (24d6d50) Message-ID: <20171027001709.26F433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/24d6d50c5d605aa32cfc5efcd2328480597cfda4/ghc >--------------------------------------------------------------- commit 24d6d50c5d605aa32cfc5efcd2328480597cfda4 Merge: 39f0509 af6a040 Author: Andrey Mokhov Date: Sat Jun 4 23:41:34 2016 +0100 Merge pull request #260 from hvr/pr/unify-cabal-script Merge build.cabal-new.sh into build.cabal.sh >--------------------------------------------------------------- 24d6d50c5d605aa32cfc5efcd2328480597cfda4 build.cabal-new.sh | 58 ------------------------------------------------------ build.cabal.sh | 50 +++++++++++++++++++++++++++++++++++----------- build.sh | 9 +++++++++ 3 files changed, 48 insertions(+), 69 deletions(-) From git at git.haskell.org Fri Oct 27 00:17:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't print empty arguments. (2bde60d) Message-ID: <20171027001709.B9C5E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2bde60d83dd71c50b88f385efefef71bf27220d0/ghc >--------------------------------------------------------------- commit 2bde60d83dd71c50b88f385efefef71bf27220d0 Author: Andrey Mokhov Date: Fri Feb 5 01:07:48 2016 +0000 Don't print empty arguments. See #204. >--------------------------------------------------------------- 2bde60d83dd71c50b88f385efefef71bf27220d0 src/Rules/Actions.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 658ba17..daa4c5e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -98,7 +98,8 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] - let note = if null args || args == [""] then "" else " (" ++ intercalate ", " args ++ ")" + let args' = filter (not . null) args + note = if null args' then "" else " (" ++ intercalate ", " args' ++ ")" if dir == "." then do putBuild $ "| Run configure" ++ note ++ "..." From git at git.haskell.org Fri Oct 27 00:17:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #49 from angerman/feature/readme-osx (eb02aa4) Message-ID: <20171027001711.1DD4A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eb02aa4ae236230b9aa83e18017be779371bdbc7/ghc >--------------------------------------------------------------- commit eb02aa4ae236230b9aa83e18017be779371bdbc7 Merge: 9d1952f 1046838 Author: Andrey Mokhov Date: Sat Dec 26 11:53:40 2015 +0000 Merge pull request #49 from angerman/feature/readme-osx Feature/readme osx >--------------------------------------------------------------- eb02aa4ae236230b9aa83e18017be779371bdbc7 README.md | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) From git at git.haskell.org Fri Oct 27 00:17:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting (49c2df8) Message-ID: <20171027001712.952EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49c2df80afe3754b2c24fae8337d1e1f13e923c3/ghc >--------------------------------------------------------------- commit 49c2df80afe3754b2c24fae8337d1e1f13e923c3 Author: Andrey Mokhov Date: Wed Jun 8 01:20:03 2016 +0100 Fix formatting >--------------------------------------------------------------- 49c2df80afe3754b2c24fae8337d1e1f13e923c3 src/Rules/Library.hs | 18 ++++++++---------- 1 file changed, 8 insertions(+), 10 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index dd144d1..a45ef51 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -62,17 +62,15 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do let path = buildPath context libPrefix = path -/- "HS" ++ pkgNameString package - -- TODO: simplify handling of AutoApply.cmm matchVersionedFilePath libPrefix (waySuffix way <.> "o") ?> \obj -> do - cSrcs <- cSources context - hSrcs <- hSources context - - eObjs <- extraObjects context - let cObjs = map (objFile context) cSrcs - hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] - objs = cObjs ++ hObjs ++ eObjs - need objs - build $ Target context Ld objs [obj] + cSrcs <- cSources context + hSrcs <- hSources context + eObjs <- extraObjects context + let cObjs = map (objFile context) cSrcs + hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] + objs = cObjs ++ hObjs ++ eObjs + need objs + build $ Target context Ld objs [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. -- | Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' From git at git.haskell.org Fri Oct 27 00:17:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass --enable-tarballs-autodownload to configure by default on Windows. (1562315) Message-ID: <20171027001713.2F5943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1562315b94894f4e8098da8ac35ce2a007f2dc1f/ghc >--------------------------------------------------------------- commit 1562315b94894f4e8098da8ac35ce2a007f2dc1f Author: Andrey Mokhov Date: Fri Feb 5 01:08:31 2016 +0000 Pass --enable-tarballs-autodownload to configure by default on Windows. See #204. >--------------------------------------------------------------- 1562315b94894f4e8098da8ac35ce2a007f2dc1f src/Rules/Config.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 89434cb..1016be9 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -1,5 +1,7 @@ module Rules.Config (configRules) where +import qualified System.Info + import Base import CmdLineFlag import Rules.Actions @@ -14,7 +16,11 @@ configRules = do case cmdConfigure of RunConfigure args -> do need [ settings <.> "in", cfgH <.> "in" ] - runConfigure "." [] [args] + -- We cannot use windowsHost here due to a cyclic dependency + let defaultArgs = if System.Info.os == "mingw32" + then [ "--enable-tarballs-autodownload" ] + else [] + runConfigure "." [] $ defaultArgs ++ [args] SkipConfigure -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " From git at git.haskell.org Fri Oct 27 00:17:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up Windows script (8ed92e9) Message-ID: <20171027001714.8ABCC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ed92e90674c9078ebe08fdd5f1edd758f48f7f7/ghc >--------------------------------------------------------------- commit 8ed92e90674c9078ebe08fdd5f1edd758f48f7f7 Author: Andrey Mokhov Date: Sat Dec 26 12:33:59 2015 +0000 Clean up Windows script >--------------------------------------------------------------- 8ed92e90674c9078ebe08fdd5f1edd758f48f7f7 README.md | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 9844bf6..a93ed9a 100644 --- a/README.md +++ b/README.md @@ -38,13 +38,13 @@ Now you have a couple of options: ### Windows -``` -$ git clone --recursive git://git.haskell.org/ghc.git -$ cd ghc -$ git clone git://github.com/snowleopard/shaking-up-ghc shake-build -$ ./boot -$ ./configure --enable-tarballs-autodownload -$ shake-build/build.bat +```bash +git clone --recursive git://git.haskell.org/ghc.git +cd ghc +git clone git://github.com/snowleopard/shaking-up-ghc shake-build +./boot +./configure --enable-tarballs-autodownload +shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. From git at git.haskell.org Fri Oct 27 00:17:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set dynamicGhcPrograms = False (85b4b52) Message-ID: <20171027001716.698833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/85b4b524df1734d0a96c7a5ac66724c0c61cce28/ghc >--------------------------------------------------------------- commit 85b4b524df1734d0a96c7a5ac66724c0c61cce28 Author: Andrey Mokhov Date: Wed Jun 8 01:20:47 2016 +0100 Set dynamicGhcPrograms = False See #259. >--------------------------------------------------------------- 85b4b524df1734d0a96c7a5ac66724c0c61cce28 src/UserSettings.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 908d96d..588f196 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -78,7 +78,7 @@ buildHaddock = return cmdBuildHaddock -- TODO: Do we need to be able to set these from command line? -- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? dynamicGhcPrograms :: Bool -dynamicGhcPrograms = True +dynamicGhcPrograms = False ghciWithDebugger :: Bool ghciWithDebugger = False From git at git.haskell.org Fri Oct 27 00:17:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use --configure by default, add --enable-tarballs-autodownload flag on Windows. (2825f93) Message-ID: <20171027001717.1DF393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2825f9345544b96b4f904c2db64b82d1982a3c0a/ghc >--------------------------------------------------------------- commit 2825f9345544b96b4f904c2db64b82d1982a3c0a Author: Andrey Mokhov Date: Fri Feb 5 01:34:35 2016 +0000 Don't use --configure by default, add --enable-tarballs-autodownload flag on Windows. See #204. [skip ci] >--------------------------------------------------------------- 2825f9345544b96b4f904c2db64b82d1982a3c0a README.md | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/README.md b/README.md index 0a60d11..f048ee4 100644 --- a/README.md +++ b/README.md @@ -27,29 +27,26 @@ follow these steps: * This build system is written in Haskell (obviously) and depends on the following Haskell packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. -* Get the sources. It is important for the build system to be in the `shake-build` directory of the GHC source tree: +* Get the sources and run standard configuration scripts. It is important for the build +system to be in the `shake-build` directory of the GHC source tree: ```bash git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/shaking-up-ghc shake-build + ./boot + ./configure # On Windows run ./configure --enable-tarballs-autodownload ``` -* Start your first build (you might want to enable parallelism with `-j`): - ```bash - shake-build/build.sh --configure - ``` -On Windows, use `build.bat` instead and pass an extra flag to configure (also see [building on Windows][ghc-windows-quick-build]): - ```bash - shake-build/build.bat --configure=--enable-tarballs-autodownload - ``` -If you are interested in building in a Cabal sandbox or using Stack, have a look at `shake-build/build.cabal.sh` and `shake-build/build.stack.sh` scripts. +* Build GHC using `shake-build/build.sh` or `shake-build/build.bat` (on Windows) instead +of `make`. You might want to enable parallelism with `-j`. We will further refer to the +build script simply as `build`. If you are interested in building in a Cabal sandbox +or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Using the build system ---------------------- -Once your first build is successful, simply run `shake-build/build.sh` or `shake-build/build.bat` -to rebuild (you no longer need to use the `--configure` flag). Most build artefacts are placed -into `.build` and `inplace` directories ([#113][build-artefacts-issue]). +Once your first build is successful, simply run `build` to rebuild. Most build artefacts +are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue]). #### Command line flags @@ -58,7 +55,10 @@ currently supports several others: * `--configure[=ARGS]`: run the `configure` script forwarding `ARGS` as command line arguments; also run the `boot` script to create the `configure` script if necessary. You do not have to use this functionality of the new build system; feel free to run -`boot` and `configure` scripts manually, as you do when using `make`. +`boot` and `configure` scripts manually, as you do when using `make`. Note: on Windows +we automatically add flag `--enable-tarballs-autodownload` to `ARGS`, so you +don't have to do it manually. Beware, this uses network I/O which may sometimes be +undesirable. * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). * `--progress-info=STYLE`: choose how build progress info is printed. There are four From git at git.haskell.org Fri Oct 27 00:17:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add IRC to README.md (bf060f8) Message-ID: <20171027001718.016853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf060f88c69ebdfb2c9a673a101b2b18c4f3c3e5/ghc >--------------------------------------------------------------- commit bf060f88c69ebdfb2c9a673a101b2b18c4f3c3e5 Author: Moritz Angermann Date: Sat Dec 26 22:17:12 2015 +0800 Add IRC to README.md add's a link (to what ever systems support `irc://`), everyone else, will hopefully know what to do :) >--------------------------------------------------------------- bf060f88c69ebdfb2c9a673a101b2b18c4f3c3e5 README.md | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/README.md b/README.md index a93ed9a..ca1e5fb 100644 --- a/README.md +++ b/README.md @@ -9,9 +9,7 @@ on the [wiki page][ghc-shake-wiki] and in this [blog post][shake-blog-post]. This is supposed to go into the `shake-build` directory of the GHC source tree. - - - +[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc) Trying it --------- From git at git.haskell.org Fri Oct 27 00:17:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Note on nm on OS X (5422e92) Message-ID: <20171027001719.F02B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5422e921b215ccb4a9041689a9b6cab4aa4af646/ghc >--------------------------------------------------------------- commit 5422e921b215ccb4a9041689a9b6cab4aa4af646 Author: Alex Biehl Date: Wed Jun 8 12:47:49 2016 +0200 Note on nm on OS X >--------------------------------------------------------------- 5422e921b215ccb4a9041689a9b6cab4aa4af646 README.md | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/README.md b/README.md index d99d2b7..6b5b234 100644 --- a/README.md +++ b/README.md @@ -43,6 +43,13 @@ runs the `boot` and `configure` scripts automatically on the first build, so tha need to. Use `--skip-configure` to suppress this behaviour (see overview of command line flags below). +* Also note on OS X newer versions of XCode ship with a broken `nm` tool ([#1174](https://ghc.haskell.org/trac/ghc/ticket/11744)). To mitigate the problem place something like + ````haskell + userArgs :: Args + userArgs = builder (Configure ".") ? arg "--with-nm=$(xcrun --find nm-classic)" + ```` + in your `UserSettings.hs`. + Using the build system ---------------------- Once your first build is successful, simply run `build` to rebuild. Most build artefacts From git at git.haskell.org Fri Oct 27 00:17:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refer to the build script simple as 'build'. (b9af374) Message-ID: <20171027001720.9C4483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b9af374ec77c17971166f3a37c7409710bd7d8c5/ghc >--------------------------------------------------------------- commit b9af374ec77c17971166f3a37c7409710bd7d8c5 Author: Andrey Mokhov Date: Fri Feb 5 01:37:29 2016 +0000 Refer to the build script simple as 'build'. [skip ci] >--------------------------------------------------------------- b9af374ec77c17971166f3a37c7409710bd7d8c5 README.md | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/README.md b/README.md index f048ee4..37a144e 100644 --- a/README.md +++ b/README.md @@ -75,24 +75,24 @@ experiment following the Haddock comments. #### Clean and full rebuild -* `shake-build/build.sh clean` removes all build artefacts. Note, we are working -towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `build clean` removes all build artefacts. Note, we are working towards a +complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. -* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of -the previous build are still in the GHC tree. +* `build -B` forces Shake to rerun all rules, even if results of the previous build +are still in the GHC tree. #### Testing -* `shake-build/build.sh validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` -directory. This can be used instead of `sh validate --fast --no-clean` in the existing build system. -Note: this will rebuild Stage2 GHC, `ghc-pkg` and `hpc` if they are out of date. +* `build validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` +directory. This can be used instead of `sh validate --fast --no-clean` in the existing +build system. Note: this will rebuild Stage2 GHC, `ghc-pkg` and `hpc` if they are out of date. -* `shake-build/build.sh test` runs GHC tests by calling the `testsuite/driver/runtests.py` python -script with appropriate flags. The current implementation is limited and cannot replace the -`validate` script (see [#187][validation-issue]). +* `build test` runs GHC tests by calling the `testsuite/driver/runtests.py` python +script with appropriate flags. The current implementation is limited and cannot +replace the `validate` script (see [#187][validation-issue]). -* `shake-build/build.sh selftest` runs tests of the build system. Current test -coverage is close to zero (see [#197][test-issue]). +* `build selftest` runs tests of the build system. Current test coverage is close to +zero (see [#197][test-issue]). Current limitations ------------------- From git at git.haskell.org Fri Oct 27 00:17:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #51 from snowleopard/angerman-patch-1 (ec44701) Message-ID: <20171027001721.6CFD93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ec447012e50b62b6f96dde134514505ed9795156/ghc >--------------------------------------------------------------- commit ec447012e50b62b6f96dde134514505ed9795156 Merge: 8ed92e9 bf060f8 Author: Andrey Mokhov Date: Sat Dec 26 14:23:16 2015 +0000 Merge pull request #51 from snowleopard/angerman-patch-1 Add IRC to README.md >--------------------------------------------------------------- ec447012e50b62b6f96dde134514505ed9795156 README.md | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:17:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #262 from alexbiehl/patch-1 (920e7bb) Message-ID: <20171027001724.031463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/920e7bba89b3d398c162e7d90d5a3581551e1edb/ghc >--------------------------------------------------------------- commit 920e7bba89b3d398c162e7d90d5a3581551e1edb Merge: 85b4b52 5422e92 Author: Andrey Mokhov Date: Thu Jun 9 10:46:52 2016 +0100 Merge pull request #262 from alexbiehl/patch-1 Note on nm on OS X >--------------------------------------------------------------- 920e7bba89b3d398c162e7d90d5a3581551e1edb README.md | 7 +++++++ 1 file changed, 7 insertions(+) From git at git.haskell.org Fri Oct 27 00:17:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on package configuration when compiling package sources with GHC. (83c1e5e) Message-ID: <20171027001724.86E493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/83c1e5e78010487dbe053c39b921c917ddb7f282/ghc >--------------------------------------------------------------- commit 83c1e5e78010487dbe053c39b921c917ddb7f282 Author: Andrey Mokhov Date: Sat Feb 6 02:39:27 2016 +0000 Depend on package configuration when compiling package sources with GHC. See #205. >--------------------------------------------------------------- 83c1e5e78010487dbe053c39b921c917ddb7f282 src/Settings/Builders/Ghc.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 74381eb..cc2afd5 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -103,9 +103,13 @@ wayGhcArgs = do -- TODO: Improve handling of "-hide-all-packages" packageGhcArgs :: Args packageGhcArgs = do + stage <- getStage pkg <- getPackage compId <- getPkgData ComponentId pkgDepIds <- getPkgDataList DepIds + lift . when (isLibrary pkg) $ do + conf <- pkgConfFile stage pkg + need [conf] mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" From git at git.haskell.org Fri Oct 27 00:17:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update LICENSE (e4e72d8) Message-ID: <20171027001725.326B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4e72d888288f7fb40c94fc13bc6e3a7d9d3bd52/ghc >--------------------------------------------------------------- commit e4e72d888288f7fb40c94fc13bc6e3a7d9d3bd52 Author: Moritz Angermann Date: Sat Dec 26 22:23:31 2015 +0800 Update LICENSE Be explicit about the license. Prevent others from having to lookup the license that matches this text. >--------------------------------------------------------------- e4e72d888288f7fb40c94fc13bc6e3a7d9d3bd52 LICENSE | 2 ++ 1 file changed, 2 insertions(+) diff --git a/LICENSE b/LICENSE index a78df02..9ee6e34 100644 --- a/LICENSE +++ b/LICENSE @@ -1,3 +1,5 @@ +BSD License + Copyright (c) 2015, Andrey Mokhov All rights reserved. From git at git.haskell.org Fri Oct 27 00:17:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change default colours to fit both B-on-W and W-on-B terminals (1ff9ead) Message-ID: <20171027001727.EAC6B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ff9eadbf2daee253e62994dd0717c7f016f1548/ghc >--------------------------------------------------------------- commit 1ff9eadbf2daee253e62994dd0717c7f016f1548 Author: Andrey Mokhov Date: Sun Jun 12 19:58:12 2016 +0100 Change default colours to fit both B-on-W and W-on-B terminals See #263. >--------------------------------------------------------------- 1ff9eadbf2daee253e62994dd0717c7f016f1548 src/UserSettings.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 588f196..23380ce 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -102,8 +102,8 @@ verboseCommands = return False -- | Customise build progress messages (e.g. executing a build command). putBuild :: String -> Action () -putBuild = putColoured Vivid White +putBuild = putColoured Dull Magenta -- | Customise build success messages (e.g. a package is built successfully). putSuccess :: String -> Action () -putSuccess = putColoured Vivid Green +putSuccess = putColoured Dull Green From git at git.haskell.org Fri Oct 27 00:17:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't run GHC concurrently with ghc-pkg. (116bf85) Message-ID: <20171027001728.E97AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/116bf853352b305eccf1392561d699c551cb07aa/ghc >--------------------------------------------------------------- commit 116bf853352b305eccf1392561d699c551cb07aa Author: Andrey Mokhov Date: Sat Feb 6 02:40:15 2016 +0000 Don't run GHC concurrently with ghc-pkg. Fix #205. >--------------------------------------------------------------- 116bf853352b305eccf1392561d699c551cb07aa src/Rules/Compile.hs | 14 +++++++++----- src/Rules/Data.hs | 24 ++---------------------- src/Rules/Register.hs | 30 ++++++++++++++++++++++++------ src/Rules/Resources.hs | 13 +++++++++---- 4 files changed, 44 insertions(+), 37 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index b27d36e..13af013 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -8,7 +8,7 @@ import Rules.Resources import Settings compilePackage :: Resources -> PartialTarget -> Rules () -compilePackage _ target @ (PartialTarget stage pkg) = do +compilePackage rs target @ (PartialTarget stage pkg) = do let buildPath = targetPath stage pkg -/- "build" matchBuildResult buildPath "hi" ?> \hi -> @@ -17,7 +17,8 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let way = detectWay hi (src, deps) <- dependencies buildPath $ hi -<.> osuf way need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [hi] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [hi] else need [ hi -<.> osuf (detectWay hi) ] matchBuildResult buildPath "hi-boot" ?> \hiboot -> @@ -26,7 +27,8 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let way = detectWay hiboot (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf way need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [hiboot] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [hiboot] else need [ hiboot -<.> obootsuf (detectWay hiboot) ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) @@ -41,7 +43,8 @@ compilePackage _ target @ (PartialTarget stage pkg) = do if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) then need $ (obj -<.> hisuf (detectWay obj)) : src : deps else need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [obj] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases matchBuildResult buildPath "o-boot" ?> \obj -> do @@ -50,4 +53,5 @@ compilePackage _ target @ (PartialTarget stage pkg) = do if compileInterfaceFilesSeparately then need $ (obj -<.> hibootsuf (detectWay obj)) : src : deps else need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [obj] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [obj] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index ade93fd..00ec163 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -12,11 +12,10 @@ import Rules.Libffi import Rules.Resources import Settings import Settings.Builders.Common -import Settings.Packages.Rts -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: Resources -> PartialTarget -> Rules () -buildPackageData rs target @ (PartialTarget stage pkg) = do +buildPackageData _ target @ (PartialTarget stage pkg) = do let cabalFile = pkgCabalFile pkg configure = pkgPath pkg -/- "configure" dataFile = pkgDataFile stage pkg @@ -34,8 +33,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - depConfs <- traverse (pkgConfFile stage) depPkgs - orderOnly depConfs + need =<< traverse (pkgConfFile stage) depPkgs -- TODO: get rid of this, see #113 let inTreeMk = oldPath -/- takeFileName dataFile @@ -126,24 +124,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." - need [rtsConf] - buildWithResources [(resGhcPkg rs, 1)] $ - fullTarget target (GhcPkg stage) [rtsConf] [] - - rtsConf %> \_ -> do - orderOnly $ generatedDependencies stage pkg - need [ rtsConfIn ] - build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] - - let fixRtsConf = unlines - . map - ( replace "\"\"" "" - . replace "rts/dist/build" rtsBuildPath ) - . filter (not . null) - . lines - - fixFile rtsConf fixRtsConf - -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- For example, get rid of diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 8c3ec73..d1b5312 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -6,11 +6,10 @@ import Base import Expression import GHC import Rules.Actions +import Rules.Libffi import Rules.Resources import Settings - --- matchPkgConf :: FilePath -> Bool --- matchPkgConf file = +import Settings.Packages.Rts -- Build package-data.mk by using GhcCabal to process pkgCabal file registerPackage :: Resources -> PartialTarget -> Rules () @@ -21,7 +20,7 @@ registerPackage rs target @ (PartialTarget stage pkg) = do Nothing -> False Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf" - when (stage <= Stage1) $ match ?> \_ -> do + when (stage <= Stage1) $ match ?> \conf -> do -- This produces pkgConfig. TODO: Add explicit tracking need [pkgDataFile stage pkg] @@ -35,5 +34,24 @@ registerPackage rs target @ (PartialTarget stage pkg) = do fixFile pkgConfig fixPkgConf - buildWithResources [(resGhcPkg rs, 1)] $ - fullTarget target (GhcPkg stage) [pkgConfig] [] + buildWithResources [(resPackageDb rs, resPackageDbLimit)] $ + fullTarget target (GhcPkg stage) [pkgConfig] [conf] + + when (pkg == rts && stage == Stage1) $ do + packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do + need [rtsConf] + buildWithResources [(resPackageDb rs, resPackageDbLimit)] $ + fullTarget target (GhcPkg stage) [rtsConf] [conf] + + rtsConf %> \_ -> do + need [ pkgDataFile Stage1 rts, rtsConfIn ] + build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] + + let fixRtsConf = unlines + . map + ( replace "\"\"" "" + . replace "rts/dist/build" rtsBuildPath ) + . filter (not . null) + . lines + + fixFile rtsConf fixRtsConf diff --git a/src/Rules/Resources.hs b/src/Rules/Resources.hs index d5e58fe..40939e0 100644 --- a/src/Rules/Resources.hs +++ b/src/Rules/Resources.hs @@ -1,12 +1,17 @@ -module Rules.Resources (resourceRules, Resources (..)) where +module Rules.Resources (resourceRules, Resources (..), resPackageDbLimit) where import Base data Resources = Resources { - resGhcPkg :: Resource + resPackageDb :: Resource } --- We cannot register multiple packages in parallel: +-- We cannot register multiple packages in parallel. Also we cannot run GHC +-- when the package database is being mutated by "ghc-pkg". This is a classic +-- concurrent read exclusive write (CREW) conflict. resourceRules :: Rules Resources -resourceRules = Resources <$> newResource "ghc-pkg" 1 +resourceRules = Resources <$> newResource "package-db" resPackageDbLimit + +resPackageDbLimit :: Int +resPackageDbLimit = 1000 From git at git.haskell.org Fri Oct 27 00:17:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #52 from snowleopard/angerman-patch-2 (b6f3045) Message-ID: <20171027001729.4C3413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6f30456f0c67d0e9393ad4a42f1b99126899e70/ghc >--------------------------------------------------------------- commit b6f30456f0c67d0e9393ad4a42f1b99126899e70 Merge: ec44701 e4e72d8 Author: Andrey Mokhov Date: Sat Dec 26 14:25:47 2015 +0000 Merge pull request #52 from snowleopard/angerman-patch-2 Update LICENSE >--------------------------------------------------------------- b6f30456f0c67d0e9393ad4a42f1b99126899e70 LICENSE | 2 ++ 1 file changed, 2 insertions(+) From git at git.haskell.org Fri Oct 27 00:17:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't run GHC -M concurrently with ghc-pkg. (44fd16d) Message-ID: <20171027001732.C1A763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44fd16dbaabe96205c493952930da708e774febd/ghc >--------------------------------------------------------------- commit 44fd16dbaabe96205c493952930da708e774febd Author: Andrey Mokhov Date: Sat Feb 6 14:53:29 2016 +0000 Don't run GHC -M concurrently with ghc-pkg. See #205. >--------------------------------------------------------------- 44fd16dbaabe96205c493952930da708e774febd src/Rules/Dependencies.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 92ac8db..30a5232 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -10,7 +10,7 @@ import Development.Shake.Util (parseMakefile) -- TODO: simplify handling of AutoApply.cmm buildPackageDependencies :: Resources -> PartialTarget -> Rules () -buildPackageDependencies _ target @ (PartialTarget stage pkg) = +buildPackageDependencies rs target @ (PartialTarget stage pkg) = let path = targetPath stage pkg buildPath = path -/- "build" dropBuild = (pkgPath pkg ++) . drop (length buildPath) @@ -29,7 +29,8 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need srcs if srcs == [] then writeFileChanged out "" - else build $ fullTarget target (GhcM stage) srcs [out] + else buildWithResources [(resPackageDb rs, 1)] $ + fullTarget target (GhcM stage) srcs [out] removeFileIfExists $ out <.> "bak" -- TODO: don't accumulate *.deps into .dependencies From git at git.haskell.org Fri Oct 27 00:17:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to Config.hs (#47). (44d81b0) Message-ID: <20171027001733.0D8043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44d81b0961073c172630fd52b76985fa9a6601b3/ghc >--------------------------------------------------------------- commit 44d81b0961073c172630fd52b76985fa9a6601b3 Author: Andrey Mokhov Date: Sat Dec 26 14:42:49 2015 +0000 Fix path to Config.hs (#47). >--------------------------------------------------------------- 44d81b0961073c172630fd52b76985fa9a6601b3 src/Rules/Generate.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index f9c1e0b..bf0afa0 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -71,15 +71,15 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = build $ fullTarget target GenPrimopCode [primopsTxt] [file] priority 2.0 $ do - when (pkg == ghcPkg) $ buildPath -/- "Config.hs" %> \file -> do + when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs - when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do - file <~ generateVersionHs - when (pkg == compiler) $ platformH %> \file -> do file <~ generateGhcBootPlatformH + when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do + file <~ generateVersionHs + when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putBuild $ "| Successfully generated '" ++ file ++ "'." From git at git.haskell.org Fri Oct 27 00:17:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add actions copyDirectoryContent and runBuilderWith (e592fb1) Message-ID: <20171027001731.5EFC93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e592fb1f438317d4be4893bf9b07b098ffb28085/ghc >--------------------------------------------------------------- commit e592fb1f438317d4be4893bf9b07b098ffb28085 Author: Kai Harries Date: Fri Jun 17 17:23:54 2016 +0200 Add actions copyDirectoryContent and runBuilderWith These new functions will be helpful when implementing the 'sdist' and 'install' rules. >--------------------------------------------------------------- e592fb1f438317d4be4893bf9b07b098ffb28085 src/Rules/Actions.hs | 26 ++++++++++++++++++++++---- 1 file changed, 22 insertions(+), 4 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 6b6c352..8fbe6c0 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,12 +1,14 @@ module Rules.Actions ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, - removeFile, copyDirectory, createDirectory, moveDirectory, removeDirectory, - applyPatch, runBuilder, makeExecutable, renderProgram, renderLibrary + removeFile, copyDirectory, copyDirectoryContent, createDirectory, + moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, + makeExecutable, renderProgram, renderLibrary ) where import qualified System.Directory as IO import qualified System.IO as IO import qualified Control.Exception.Base as IO +import qualified System.Directory.Extra as X import Base import CmdLineFlag @@ -126,6 +128,18 @@ copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd cmdEcho ["cp", "-r", source, target] +-- | Copy the content of the source directory into the target directory. Only +-- the files and directories for which the predicate returns True are copied. +copyDirectoryContent :: (FilePath -> IO Bool) -> FilePath -> FilePath -> Action () +copyDirectoryContent test source target = do + putProgressInfo $ renderAction "Copy directory" source target + liftIO $ X.listFilesInside test' source >>= mapM_ cp + where + target' a = target -/- fromJust (stripPrefix source a) + test' a = ifM (test a) (mkdir a >> return True) (return False) + mkdir a = IO.createDirectoryIfMissing True $ target' a + cp a = whenM (test a) $ IO.copyFile a $ target' a + -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do @@ -152,12 +166,16 @@ applyPatch dir patch = do quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () -runBuilder builder args = do +runBuilder = + runBuilderWith [] + +runBuilderWith :: [CmdOption] -> Builder -> [String] -> Action () +runBuilderWith options builder args = do needBuilder builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ show builder ++ note - quietly $ cmd [path] args + quietly $ cmd options [path] args makeExecutable :: FilePath -> Action () makeExecutable file = do From git at git.haskell.org Fri Oct 27 00:17:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add copyDirectory to Rules.Actions. (63bbebf) Message-ID: <20171027001737.2EFAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac/ghc >--------------------------------------------------------------- commit 63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac Author: Andrey Mokhov Date: Sun Feb 7 01:13:05 2016 +0000 Add copyDirectory to Rules.Actions. See #98. >--------------------------------------------------------------- 63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac src/Rules/Actions.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index daa4c5e..9275207 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,8 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, - moveDirectory, fixFile, runConfigure, runMake, runMakeVerbose, applyPatch, - renderLibrary, renderProgram, runBuilder, makeExecutable + copyDirectory, moveDirectory, applyPatch, fixFile, runConfigure, runMake, + runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -82,6 +82,12 @@ removeDirectory dir = do removeDirectoryIfExists dir -- Note, the source directory is untracked +copyDirectory :: FilePath -> FilePath -> Action () +copyDirectory source target = do + putProgressInfo $ renderAction "Copy directory" source target + quietly $ cmd (EchoStdout False) ["cp", "-r", source, target] + +-- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target From git at git.haskell.org Fri Oct 27 00:17:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (382ecb4) Message-ID: <20171027001737.4CDFD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/382ecb4b36b9e06dc5f3875a7cc8aeb287623696/ghc >--------------------------------------------------------------- commit 382ecb4b36b9e06dc5f3875a7cc8aeb287623696 Merge: 44d81b0 b6f3045 Author: Andrey Mokhov Date: Sat Dec 26 14:43:49 2015 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 382ecb4b36b9e06dc5f3875a7cc8aeb287623696 LICENSE | 2 ++ README.md | 4 +--- 2 files changed, 3 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:17:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove explicit import of 'System.Directory' (73970d5) Message-ID: <20171027001735.21EE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73970d51a9d40c79ec8ed2aea4d36b5c3ff723b0/ghc >--------------------------------------------------------------- commit 73970d51a9d40c79ec8ed2aea4d36b5c3ff723b0 Author: Kai Harries Date: Sun Jun 19 09:34:15 2016 +0200 Remove explicit import of 'System.Directory' >--------------------------------------------------------------- 73970d51a9d40c79ec8ed2aea4d36b5c3ff723b0 src/Rules/Actions.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 8fbe6c0..7221441 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -5,10 +5,9 @@ module Rules.Actions ( makeExecutable, renderProgram, renderLibrary ) where -import qualified System.Directory as IO +import qualified System.Directory.Extra as IO import qualified System.IO as IO import qualified Control.Exception.Base as IO -import qualified System.Directory.Extra as X import Base import CmdLineFlag @@ -133,7 +132,7 @@ copyDirectory source target = do copyDirectoryContent :: (FilePath -> IO Bool) -> FilePath -> FilePath -> Action () copyDirectoryContent test source target = do putProgressInfo $ renderAction "Copy directory" source target - liftIO $ X.listFilesInside test' source >>= mapM_ cp + liftIO $ IO.listFilesInside test' source >>= mapM_ cp where target' a = target -/- fromJust (stripPrefix source a) test' a = ifM (test a) (mkdir a >> return True) (return False) From git at git.haskell.org Fri Oct 27 00:17:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove excessive whitespace (787cb4f) Message-ID: <20171027001738.96EBB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/787cb4f1f82c4928d6a4d0259da6694f3fd0fe64/ghc >--------------------------------------------------------------- commit 787cb4f1f82c4928d6a4d0259da6694f3fd0fe64 Author: Kai Harries Date: Sun Jun 19 09:36:04 2016 +0200 Remove excessive whitespace >--------------------------------------------------------------- 787cb4f1f82c4928d6a4d0259da6694f3fd0fe64 src/Rules/Actions.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 7221441..734cb91 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -165,8 +165,7 @@ applyPatch dir patch = do quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () -runBuilder = - runBuilderWith [] +runBuilder = runBuilderWith [] runBuilderWith :: [CmdOption] -> Builder -> [String] -> Action () runBuilderWith options builder args = do From git at git.haskell.org Fri Oct 27 00:17:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --haddock command line flag. (7f2c6a1) Message-ID: <20171027001740.95A263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7f2c6a1a360d5351fadc3ab9a6cfa322a56b797e/ghc >--------------------------------------------------------------- commit 7f2c6a1a360d5351fadc3ab9a6cfa322a56b797e Author: Andrey Mokhov Date: Sun Feb 7 02:31:37 2016 +0000 Add --haddock command line flag. See #98. >--------------------------------------------------------------- 7f2c6a1a360d5351fadc3ab9a6cfa322a56b797e src/CmdLineFlag.hs | 18 ++++++++++++++---- src/Settings/User.hs | 2 +- 2 files changed, 15 insertions(+), 5 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 0142abb..84d4f11 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,6 +1,6 @@ module CmdLineFlag ( - putCmdLineFlags, cmdFlags, cmdConfigure, Configure (..), cmdFlavour, - Flavour (..), cmdProgressInfo, ProgressInfo (..), cmdSplitObjects + putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdConfigure, Configure (..), + cmdFlavour, Flavour (..), cmdProgressInfo, ProgressInfo (..), cmdSplitObjects ) where import Data.List.Extra @@ -18,7 +18,8 @@ data Flavour = Default | Quick deriving (Eq, Show) -- command line. These flags are not tracked, that is they do not force any -- build rules to be rurun. data Untracked = Untracked - { configure :: Configure + { buildHaddock :: Bool + , configure :: Configure , flavour :: Flavour , progressInfo :: ProgressInfo , splitObjects :: Bool } @@ -27,11 +28,15 @@ data Untracked = Untracked -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked defaultUntracked = Untracked - { configure = SkipConfigure + { buildHaddock = False + , configure = SkipConfigure , flavour = Default , progressInfo = Normal , splitObjects = False } +readBuildHaddock :: Either String (Untracked -> Untracked) +readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } + readConfigure :: Maybe String -> Either String (Untracked -> Untracked) readConfigure ms = maybe (Left "Cannot parse configure") (Right . set) (go $ lower <$> ms) @@ -75,6 +80,8 @@ cmdFlags = "Run configure with ARGS (also run boot if necessary)." , Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") "Build flavour (Default or Quick)." + , Option [] ["haddock"] (NoArg readBuildHaddock) + "Generate Haddock documentation." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") "Progress info style (None, Brief, Normal, or Unicorn)." , Option [] ["split-objects"] (NoArg readSplitObjects) @@ -93,6 +100,9 @@ putCmdLineFlags flags = modifyIORef cmdLineFlags (\f -> foldl (flip id) f flags) getCmdLineFlags :: Untracked getCmdLineFlags = unsafePerformIO $ readIORef cmdLineFlags +cmdBuildHaddock :: Bool +cmdBuildHaddock = buildHaddock getCmdLineFlags + cmdConfigure :: Configure cmdConfigure = configure getCmdLineFlags diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 2cf39aa..dd6150a 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -84,7 +84,7 @@ laxDependencies :: Bool laxDependencies = False buildHaddock :: Predicate -buildHaddock = return False -- FIXME: should be return True, see #98 +buildHaddock = return cmdBuildHaddock -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package From git at git.haskell.org Fri Oct 27 00:17:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop doc directory (no useful docs there anyway), fix #54. (7f8db60) Message-ID: <20171027001740.EA44C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7f8db6059059fbeffe0519bcb60cfac235fa10b2/ghc >--------------------------------------------------------------- commit 7f8db6059059fbeffe0519bcb60cfac235fa10b2 Author: Andrey Mokhov Date: Sat Dec 26 15:23:08 2015 +0000 Drop doc directory (no useful docs there anyway), fix #54. >--------------------------------------------------------------- 7f8db6059059fbeffe0519bcb60cfac235fa10b2 doc/boom.png | Bin 91102 -> 0 bytes doc/build-expressions.docx | Bin 22575 -> 0 bytes doc/build-expressions.pdf | Bin 644843 -> 0 bytes doc/build-package-data.docx | Bin 16519 -> 0 bytes doc/comment-hi-rule.txt | 39 --------- doc/deepseq-build-progress.txt | 86 -------------------- doc/demo.txt | 23 ------ doc/meeting-16-June-2015.txt | 163 -------------------------------------- doc/meeting-25-September-2015.txt | 98 ----------------------- 9 files changed, 409 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 7f8db6059059fbeffe0519bcb60cfac235fa10b2 From git at git.haskell.org Fri Oct 27 00:17:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Quickest build flavour (d7c80c8) Message-ID: <20171027001742.1629B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d7c80c8303b7bc4596c9d04b569c365128cfd958/ghc >--------------------------------------------------------------- commit d7c80c8303b7bc4596c9d04b569c365128cfd958 Author: Andrey Mokhov Date: Mon Jun 20 03:07:24 2016 +0100 Add Quickest build flavour See #259, #268. >--------------------------------------------------------------- d7c80c8303b7bc4596c9d04b569c365128cfd958 hadrian.cabal | 1 + src/CmdLineFlag.hs | 11 ++++++----- src/Settings/Args.hs | 7 +++++-- src/Settings/Flavours/Quickest.hs | 16 ++++++++++++++++ src/Settings/Ways.hs | 7 +++++-- 5 files changed, 33 insertions(+), 9 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 5ffcb65..2b773ee 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -88,6 +88,7 @@ executable hadrian , Settings.Builders.Tar , Settings.Default , Settings.Flavours.Quick + , Settings.Flavours.Quickest , Settings.Packages , Settings.Packages.Base , Settings.Packages.Compiler diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 10c39f2..df3af5b 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -21,7 +21,7 @@ data Untracked = Untracked , splitObjects :: Bool } deriving (Eq, Show) -data Flavour = Default | Quick deriving (Eq, Show) +data Flavour = Default | Quick | Quickest deriving (Eq, Show) data ProgressColour = Never | Auto | Always deriving (Eq, Show) data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) @@ -43,9 +43,10 @@ readFlavour ms = maybe (Left "Cannot parse flavour") (Right . set) (go =<< lower <$> ms) where go :: String -> Maybe Flavour - go "default" = Just Default - go "quick" = Just Quick - go _ = Nothing + go "default" = Just Default + go "quick" = Just Quick + go "quickest" = Just Quickest + go _ = Nothing set :: Flavour -> Untracked -> Untracked set flag flags = flags { flavour = flag } @@ -83,7 +84,7 @@ readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") - "Build flavour (Default or Quick)." + "Build flavour (Default, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 18079a2..2ff071a 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -20,6 +20,7 @@ import Settings.Builders.Ld import Settings.Builders.Make import Settings.Builders.Tar import Settings.Flavours.Quick +import Settings.Flavours.Quickest import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Directory @@ -88,5 +89,7 @@ defaultPackageArgs = mconcat , unlitPackageArgs ] flavourArgs :: Args -flavourArgs = mconcat - [ cmdFlavour == Quick ? quickFlavourArgs ] +flavourArgs = case cmdFlavour of + Default -> mempty + Quick -> quickFlavourArgs + Quickest -> quickestFlavourArgs diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs new file mode 100644 index 0000000..cc1de6b --- /dev/null +++ b/src/Settings/Flavours/Quickest.hs @@ -0,0 +1,16 @@ +module Settings.Flavours.Quickest (quickestFlavourArgs, quickestFlavourWays) where + +import Context +import GHC +import Predicate + +optimise :: Context -> Bool +optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] + +quickestFlavourArgs :: Args +quickestFlavourArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O" else arg "-O0" + +quickestFlavourWays :: Ways +quickestFlavourWays = remove [profiling] diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 79dd164..95301e1 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -5,6 +5,7 @@ import CmdLineFlag import Oracles.Config.Flag import Predicate import Settings.Flavours.Quick +import Settings.Flavours.Quickest import UserSettings -- | Combine default library ways with user modifications. @@ -29,8 +30,10 @@ defaultLibraryWays = mconcat , notStage0 ? platformSupportsSharedLibs ? append [dynamic] ] flavourLibraryWays :: Ways -flavourLibraryWays = mconcat - [ cmdFlavour == Quick ? quickFlavourWays ] +flavourLibraryWays = case cmdFlavour of + Default -> mempty + Quick -> quickFlavourWays + Quickest -> quickestFlavourWays defaultRtsWays :: Ways defaultRtsWays = do From git at git.haskell.org Fri Oct 27 00:17:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy generated files to old build directories. (90c59d1) Message-ID: <20171027001744.91BCA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90c59d1382021802b10c385b93b70a6967a25719/ghc >--------------------------------------------------------------- commit 90c59d1382021802b10c385b93b70a6967a25719 Author: Andrey Mokhov Date: Sun Feb 7 02:32:32 2016 +0000 Copy generated files to old build directories. See #98. >--------------------------------------------------------------- 90c59d1382021802b10c385b93b70a6967a25719 src/Rules/Generate.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 9c67760..4ced436 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -3,6 +3,8 @@ module Rules.Generate ( includesDependencies, derivedConstantsPath, generatedDependencies ) where +import qualified System.Directory as IO + import Base import Expression import GHC @@ -144,19 +146,32 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] build $ fullTarget target GenPrimopCode [primopsTxt stage] [file] + -- TODO: this is temporary hack, get rid of this (#113) + let oldPath = pkgPath pkg -/- targetDirectory stage pkg -/- "build" + newFile = oldPath ++ (drop (length buildPath) file) + createDirectory $ takeDirectory newFile + liftIO $ IO.copyFile file newFile + putSuccess $ "| Duplicate file " ++ file ++ " -> " ++ newFile when (pkg == rts) $ buildPath -/- "AutoApply.cmm" %> \file -> do build $ fullTarget target GenApply [] [file] priority 2.0 $ do + -- TODO: this is temporary hack, get rid of this (#113) + let oldPath = pkgPath pkg -/- targetDirectory stage pkg -/- "build" + olden f = oldPath ++ (drop (length buildPath) f) + when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs + olden file <~ generateConfigHs -- TODO: get rid of this (#113) when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH + olden file <~ generateGhcBootPlatformH -- TODO: get rid of this (#113) when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do file <~ generateVersionHs + olden file <~ generateVersionHs -- TODO: get rid of this (#113) when (pkg == runGhc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file From git at git.haskell.org Fri Oct 27 00:17:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need . (6d4720c) Message-ID: <20171027001744.E44DE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d4720c1e65d2b4a6cc88152f4547915aebcce42/ghc >--------------------------------------------------------------- commit 6d4720c1e65d2b4a6cc88152f4547915aebcce42 Author: Andrey Mokhov Date: Sat Dec 26 16:25:14 2015 +0000 Don't need . >--------------------------------------------------------------- 6d4720c1e65d2b4a6cc88152f4547915aebcce42 src/Oracles/Config.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index 5a163a6..e8333b6 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -7,6 +7,9 @@ import qualified Data.HashMap.Strict as Map newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +configFile :: FilePath +configFile = configPath -/- "system.config" + askConfig :: String -> Action String askConfig key = askConfigWithDefault key . putError $ "Cannot find key '" ++ key ++ "' in configuration files." @@ -21,11 +24,7 @@ askConfigWithDefault key defaultAction = do -- Oracle for configuration files configOracle :: Rules () configOracle = do - let configFile = configPath -/- "system.config" cfg <- newCache $ \() -> do - unlessM (doesFileExist $ configFile <.> "in") $ - putError $ "\nConfiguration file '" ++ (configFile <.> "in") - ++ "' is missing; unwilling to proceed." need [configFile] putOracle $ "Reading " ++ configFile ++ "..." liftIO $ readConfigFile configFile From git at git.haskell.org Fri Oct 27 00:17:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Quickest flavour on Appveyor (3a04d34) Message-ID: <20171027001745.8D6703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3a04d3425a06ff9ad62eb71d20ddd7cce26ae0a0/ghc >--------------------------------------------------------------- commit 3a04d3425a06ff9ad62eb71d20ddd7cce26ae0a0 Author: Andrey Mokhov Date: Mon Jun 20 03:08:10 2016 +0100 Use Quickest flavour on Appveyor See #259, #268. >--------------------------------------------------------------- 3a04d3425a06ff9ad62eb71d20ddd7cce26ae0a0 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index bb5620e..e4d7d52 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:17:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy haddock-prologue.txt to new build directory. (7122295) Message-ID: <20171027001748.779CE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7122295adffb0c254bfbd39a394e8915ac0e806a/ghc >--------------------------------------------------------------- commit 7122295adffb0c254bfbd39a394e8915ac0e806a Author: Andrey Mokhov Date: Sun Feb 7 02:33:04 2016 +0000 Copy haddock-prologue.txt to new build directory. See #98. >--------------------------------------------------------------- 7122295adffb0c254bfbd39a394e8915ac0e806a src/Rules/Data.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 00ec163..dc77d21 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -47,6 +47,8 @@ buildPackageData _ target @ (PartialTarget stage pkg) = do createDirectory $ targetPath stage pkg -/- "build/autogen" forM_ autogenFiles $ \file -> do copyFile (oldPath -/- file) (targetPath stage pkg -/- file) + let haddockPrologue = "haddock-prologue.txt" + copyFile (oldPath -/- haddockPrologue) (targetPath stage pkg -/- haddockPrologue) postProcessPackageData stage pkg dataFile From git at git.haskell.org Fri Oct 27 00:17:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Quick flavour (6d6834a) Message-ID: <20171027001749.740A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d6834a6abebaff0d4aa60e615a027d68ed964d9/ghc >--------------------------------------------------------------- commit 6d6834a6abebaff0d4aa60e615a027d68ed964d9 Author: Andrey Mokhov Date: Mon Jun 20 03:08:45 2016 +0100 Fix Quick flavour See #259, #268. >--------------------------------------------------------------- 6d6834a6abebaff0d4aa60e615a027d68ed964d9 src/Settings/Flavours/Quick.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index e3f0a5d..81fe178 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -1,9 +1,17 @@ module Settings.Flavours.Quick (quickFlavourArgs, quickFlavourWays) where +import Context +import GHC import Predicate +optimise :: Context -> Bool +optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] + || stage == Stage1 && isLibrary package + quickFlavourArgs :: Args -quickFlavourArgs = builder Ghc ? arg "-O0" +quickFlavourArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O" else arg "-O0" quickFlavourWays :: Ways quickFlavourWays = remove [profiling] From git at git.haskell.org Fri Oct 27 00:17:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement build rule for template-hsc.h, fix #44. (6863e5e) Message-ID: <20171027001748.EB6C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6863e5e13c4182976f330a14696109504d1e59b2/ghc >--------------------------------------------------------------- commit 6863e5e13c4182976f330a14696109504d1e59b2 Author: Andrey Mokhov Date: Sat Dec 26 18:31:46 2015 +0000 Implement build rule for template-hsc.h, fix #44. >--------------------------------------------------------------- 6863e5e13c4182976f330a14696109504d1e59b2 shaking-up-ghc.cabal | 1 + src/Main.hs | 2 ++ src/Rules/Install.hs | 11 +++++++++++ src/Settings/Builders/Hsc2Hs.hs | 6 +++++- 4 files changed, 19 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 1e0fbbf..941651b 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -47,6 +47,7 @@ executable ghc-shake , Rules.Generators.GhcBootPlatformH , Rules.Generators.GhcPlatformH , Rules.Generators.VersionHs + , Rules.Install , Rules.Library , Rules.Oracles , Rules.Package diff --git a/src/Main.hs b/src/Main.hs index 0dc8d96..fdc43cd 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,12 +3,14 @@ import Rules import Rules.Cabal import Rules.Config import Rules.Generate +import Rules.Install import Rules.Oracles main :: IO () main = shakeArgs options $ do cabalRules -- see Rules.Cabal configRules -- see Rules.Config + installRules -- see Rules.Install generateTargets -- see Rules generateRules -- see Rules.Generate oracleRules -- see Rules.Oracles diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs new file mode 100644 index 0000000..b592728 --- /dev/null +++ b/src/Rules/Install.hs @@ -0,0 +1,11 @@ +module Rules.Install (installRules) where + +import Expression +import GHC + +installRules :: Rules () +installRules = do + "inplace/lib/template-hsc.h" %> \out -> do + let source = pkgPath hsc2hs -/- "template-hsc.h" + putBuild $ "| Copying " ++ source ++ " -> " ++ out + copyFileChanged source out diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 0c6172d..6721aaf 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -6,6 +6,9 @@ import Predicates (builder, stage0, notStage0) import Settings import Settings.Builders.GhcCabal hiding (cppArgs) +templateHsc :: FilePath +templateHsc = "inplace/lib/template-hsc.h" + hsc2HsArgs :: Args hsc2HsArgs = builder Hsc2Hs ? do stage <- getStage @@ -21,6 +24,7 @@ hsc2HsArgs = builder Hsc2Hs ? do version <- if stage == Stage0 then lift $ ghcCanonVersion else getSetting ProjectVersionInt + lift $ need [templateHsc] mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" @@ -33,7 +37,7 @@ hsc2HsArgs = builder Hsc2Hs ? do , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) , arg ("--cflag=-D__GLASGOW_HASKELL__=" ++ version) - , arg $ "--template=" ++ top -/- "inplace/lib/template-hsc.h" + , arg $ "--template=" ++ top -/- templateHsc , arg $ "-I" ++ top -/- "inplace/lib/include/" , arg =<< getInput , arg "-o", arg =<< getOutput ] From git at git.haskell.org Fri Oct 27 00:17:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Haddock documentation. (e1b6c56) Message-ID: <20171027001752.707843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1b6c5688198e78d8c1a6261479f69efdc640e1f/ghc >--------------------------------------------------------------- commit e1b6c5688198e78d8c1a6261479f69efdc640e1f Author: Andrey Mokhov Date: Sun Feb 7 02:34:27 2016 +0000 Fix Haddock documentation. Fix #98. >--------------------------------------------------------------- e1b6c5688198e78d8c1a6261479f69efdc640e1f src/Rules/Documentation.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index e235bfc..533ea47 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -8,6 +8,9 @@ import Rules.Actions import Rules.Resources import Settings +haddockHtmlLib :: FilePath +haddockHtmlLib = "inplace/lib/html/haddock-util.js" + -- Note: this build rule creates plenty of files, not just the .haddock one. -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. @@ -22,9 +25,10 @@ buildPackageDocumentation _ target @ (PartialTarget stage pkg) = let haddocks = [ pkgHaddockFile depPkg | Just depPkg <- map findKnownPackage deps , depPkg /= rts ] - need $ srcs ++ haddocks + need $ srcs ++ haddocks ++ [haddockHtmlLib] -- HsColour sources + -- TODO: what is the output of GhcCabalHsColour? whenM (specified HsColour) $ do pkgConf <- pkgConfFile stage pkg need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf @@ -34,6 +38,11 @@ buildPackageDocumentation _ target @ (PartialTarget stage pkg) = let haddockWay = if dynamicGhcPrograms then dynamic else vanilla build $ fullTargetWithWay target Haddock haddockWay srcs [file] + when (pkg == haddock) $ haddockHtmlLib %> \_ -> do + let dir = takeDirectory haddockHtmlLib + liftIO $ removeFiles dir ["//*"] + copyDirectory "utils/haddock/haddock-api/resources/html" dir + -- # Make the haddocking depend on the library .a file, to ensure -- # that we wait until the library is fully built before we haddock it -- $$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) : $$($1_$2_$$(HADDOCK_WAY)_LIB) From git at git.haskell.org Fri Oct 27 00:17:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use existing target input instead of made up 'src' (f80dd4c) Message-ID: <20171027001752.CB1E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f80dd4cc253afd4178f794e20aac9b0379b8d036/ghc >--------------------------------------------------------------- commit f80dd4cc253afd4178f794e20aac9b0379b8d036 Author: Andrey Mokhov Date: Sat Dec 26 21:53:37 2015 +0000 Use existing target input instead of made up 'src' >--------------------------------------------------------------- f80dd4cc253afd4178f794e20aac9b0379b8d036 src/Oracles/ArgsHash.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 1f4c584..65bfc8a 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -13,7 +13,7 @@ newtype ArgsHashKey = ArgsHashKey Target -- argument list and computes its hash. The resulting value is tracked in a -- Shake oracle, hence initiating rebuilts when the hash is changed (a hash -- change indicates changes in the build system). --- Note: we replace target sources with ["src"] for performance reasons -- to +-- Note: we keep only the first target input for performance reasons -- to -- avoid storing long lists of source files passed to some builders (e.g. Ar) -- in the Shake database. This optimisation is harmless, because argument list -- constructors are assumed not to examine target sources, but only append them @@ -22,7 +22,8 @@ newtype ArgsHashKey = ArgsHashKey Target -- TODO: Hash Target to improve accuracy and performance. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do - _ <- askOracle . ArgsHashKey $ target { inputs = ["src"] } :: Action Int + let firstInput = take 1 $ inputs target + _ <- askOracle . ArgsHashKey $ target { inputs = firstInput } :: Action Int return () -- Oracle for storing per-target argument list hashes From git at git.haskell.org Fri Oct 27 00:17:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Quickest flavour on Mac OSX (1f1a7b3) Message-ID: <20171027001753.2C4AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1f1a7b3297c7a4747b5e7a89ae47335ea8d79a56/ghc >--------------------------------------------------------------- commit 1f1a7b3297c7a4747b5e7a89ae47335ea8d79a56 Author: Andrey Mokhov Date: Tue Jun 21 01:22:18 2016 +0100 Use Quickest flavour on Mac OSX See #259 >--------------------------------------------------------------- 1f1a7b3297c7a4747b5e7a89ae47335ea8d79a56 .travis.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index 18ede46..b066e89 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quick TARGET= addons: apt: packages: @@ -20,7 +20,7 @@ matrix: - cabal install alex happy - os: osx - env: TARGET= + env: FLAVOUR=quickest TARGET= before_install: - brew update - brew install ghc cabal-install @@ -59,7 +59,7 @@ install: script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=$FLAVOUR $TARGET - ./ghc/inplace/bin/ghc-stage2 -e 1+2 cache: From git at git.haskell.org Fri Oct 27 00:17:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --haddock flag. (52b915f) Message-ID: <20171027001756.D30C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/52b915f9193a726c4a93ccea5e22ebfedcafbe3f/ghc >--------------------------------------------------------------- commit 52b915f9193a726c4a93ccea5e22ebfedcafbe3f Author: Andrey Mokhov Date: Sun Feb 7 02:42:27 2016 +0000 Add --haddock flag. See #98. [skip ci] >--------------------------------------------------------------- 52b915f9193a726c4a93ccea5e22ebfedcafbe3f README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 37a144e..35f8ac3 100644 --- a/README.md +++ b/README.md @@ -61,6 +61,7 @@ don't have to do it manually. Beware, this uses network I/O which may sometimes undesirable. * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). +* `--haddock`: build Haddock documentation. * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). @@ -98,8 +99,8 @@ Current limitations ------------------- The new build system still lacks many important features: * We only build `vanilla` way: [#4][dynamic-issue], [#186][profiling-issue]. -* Documentation is broken: [#98][haddock-issue]. * Validation is not implemented: [#187][validation-issue]. +* Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. @@ -138,7 +139,6 @@ helped me endure and enjoy the project. [test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 [profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 -[haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 From git at git.haskell.org Fri Oct 27 00:17:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to optimise ghc-stage2 in Quick flavour (b299acb) Message-ID: <20171027001757.6F3DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b299acb4ec05bbf8a3b08a67175f8b2eb2f2aded/ghc >--------------------------------------------------------------- commit b299acb4ec05bbf8a3b08a67175f8b2eb2f2aded Author: Andrey Mokhov Date: Tue Jun 21 01:56:20 2016 +0100 Attempt to optimise ghc-stage2 in Quick flavour See #259 >--------------------------------------------------------------- b299acb4ec05bbf8a3b08a67175f8b2eb2f2aded src/Settings/Flavours/Quick.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 81fe178..834a72b 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -5,7 +5,7 @@ import GHC import Predicate optimise :: Context -> Bool -optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] +optimise Context {..} = package `elem` [compiler, ghc] || stage == Stage1 && isLibrary package quickFlavourArgs :: Args From git at git.haskell.org Fri Oct 27 00:17:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:17:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initialise bootstrapping.conf (fix #42). (20037b1) Message-ID: <20171027001757.2CFCB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20037b1e711c2e90ed09bd1c6543cc3f05ac7407/ghc >--------------------------------------------------------------- commit 20037b1e711c2e90ed09bd1c6543cc3f05ac7407 Author: Andrey Mokhov Date: Sat Dec 26 21:58:17 2015 +0000 Initialise bootstrapping.conf (fix #42). >--------------------------------------------------------------- 20037b1e711c2e90ed09bd1c6543cc3f05ac7407 src/Base.hs | 20 ++++++++++++++++---- src/Rules/Cabal.hs | 13 +++++++++++++ src/Rules/Data.hs | 8 ++++---- src/Rules/Generate.hs | 15 ++++++++------- src/Settings/Builders/Ghc.hs | 3 ++- src/Settings/Builders/GhcCabal.hs | 9 ++++++--- src/Settings/Builders/GhcPkg.hs | 12 ++++++++++-- 7 files changed, 59 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 20037b1e711c2e90ed09bd1c6543cc3f05ac7407 From git at git.haskell.org Fri Oct 27 00:18:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use ||^ for OR-ing Predicates. (2d221a4) Message-ID: <20171027001801.0C1743A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d221a4c3d8b79d3a88f8faa90b884aef5d160ea/ghc >--------------------------------------------------------------- commit 2d221a4c3d8b79d3a88f8faa90b884aef5d160ea Author: Andrey Mokhov Date: Sat Dec 26 22:00:44 2015 +0000 Use ||^ for OR-ing Predicates. >--------------------------------------------------------------- 2d221a4c3d8b79d3a88f8faa90b884aef5d160ea src/Settings/Builders/GhcCabal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 17b1725..80c4f4c 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -80,7 +80,7 @@ bootPackageDbArgs :: Args bootPackageDbArgs = stage0 ? do path <- getSetting GhcSourcePath lift $ need [bootstrappingConfInitialised] - isGhc <- (||) <$> stagedBuilder Ghc <*> stagedBuilder GhcM + isGhc <- stagedBuilder Ghc ||^ stagedBuilder GhcM let prefix = if isGhc then "-package-db " else "--package-db=" arg $ prefix ++ path -/- bootstrappingConf From git at git.haskell.org Fri Oct 27 00:18:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop duplication of ghc_boot_platform.h (8b24f9f) Message-ID: <20171027001801.01C223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8b24f9f05a7daf8b158748f4d04b4872085ec254/ghc >--------------------------------------------------------------- commit 8b24f9f05a7daf8b158748f4d04b4872085ec254 Author: Andrey Mokhov Date: Sun Feb 7 12:30:28 2016 +0000 Drop duplication of ghc_boot_platform.h See #98. >--------------------------------------------------------------- 8b24f9f05a7daf8b158748f4d04b4872085ec254 src/Rules/Generate.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 4ced436..1258d3f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -158,8 +158,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = priority 2.0 $ do -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- targetDirectory stage pkg -/- "build" - olden f = oldPath ++ (drop (length buildPath) f) + let oldPath = pkgPath pkg -/- targetDirectory stage pkg + olden f = oldPath ++ (drop (length (targetPath stage pkg)) f) when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs @@ -167,7 +167,6 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH - olden file <~ generateGhcBootPlatformH -- TODO: get rid of this (#113) when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do file <~ generateVersionHs From git at git.haskell.org Fri Oct 27 00:18:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't optimise GHC in Quickest flavour (0955d43) Message-ID: <20171027001801.6FBFD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0955d43bbbde1ee3ab71d3a01bf3d2f6e53afbe9/ghc >--------------------------------------------------------------- commit 0955d43bbbde1ee3ab71d3a01bf3d2f6e53afbe9 Author: Andrey Mokhov Date: Tue Jun 21 20:10:31 2016 +0100 Don't optimise GHC in Quickest flavour See #259, #268. >--------------------------------------------------------------- 0955d43bbbde1ee3ab71d3a01bf3d2f6e53afbe9 src/Settings/Flavours/Quickest.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index cc1de6b..3696237 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -1,16 +1,9 @@ module Settings.Flavours.Quickest (quickestFlavourArgs, quickestFlavourWays) where -import Context -import GHC import Predicate -optimise :: Context -> Bool -optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] - quickestFlavourArgs :: Args -quickestFlavourArgs = builder Ghc ? do - context <- getContext - if optimise context then arg "-O" else arg "-O0" +quickestFlavourArgs = builder Ghc ? arg "-O0" quickestFlavourWays :: Ways quickestFlavourWays = remove [profiling] From git at git.haskell.org Fri Oct 27 00:18:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add builders: DeriveConstants, Nm, Objdump. (6001acb) Message-ID: <20171027001804.819C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6001acb394a70a14e333dd17a8f65b89115dfa52/ghc >--------------------------------------------------------------- commit 6001acb394a70a14e333dd17a8f65b89115dfa52 Author: Andrey Mokhov Date: Sun Dec 27 01:51:33 2015 +0000 Add builders: DeriveConstants, Nm, Objdump. >--------------------------------------------------------------- 6001acb394a70a14e333dd17a8f65b89115dfa52 cfg/system.config.in | 45 ++++++++++++++++++++++++--------------------- src/Builder.hs | 6 ++++++ 2 files changed, 30 insertions(+), 21 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 12ddeed..a2cfef3 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -4,36 +4,39 @@ # Paths to builders: #=================== -system-ghc = @WithGhc@ -ghc-stage1 = inplace/bin/ghc-stage1 -ghc-stage2 = inplace/bin/ghc-stage2 -ghc-stage3 = inplace/bin/ghc-stage3 +system-ghc = @WithGhc@ +ghc-stage1 = inplace/bin/ghc-stage1 +ghc-stage2 = inplace/bin/ghc-stage2 +ghc-stage3 = inplace/bin/ghc-stage3 -system-gcc = @CC_STAGE0@ -gcc = @WhatGccIsCalled@ +system-gcc = @CC_STAGE0@ +gcc = @WhatGccIsCalled@ -system-ghc-pkg = @GhcPkgCmd@ -ghc-pkg = inplace/bin/ghc-pkg +system-ghc-pkg = @GhcPkgCmd@ +ghc-pkg = inplace/bin/ghc-pkg -ghc-cabal = inplace/bin/ghc-cabal +ghc-cabal = inplace/bin/ghc-cabal -haddock = inplace/bin/haddock +haddock = inplace/bin/haddock -hsc2hs = inplace/bin/hsc2hs +hsc2hs = inplace/bin/hsc2hs -genprimopcode = inplace/bin/genprimopcode +genprimopcode = inplace/bin/genprimopcode +derive-constants = inplace/bin/deriveConstants -hs-cpp = @HaskellCPPCmd@ -hs-cpp-args = @HaskellCPPArgs@ +hs-cpp = @HaskellCPPCmd@ +hs-cpp-args = @HaskellCPPArgs@ -unlit = inplace/lib/unlit -ghc-split = inplace/lib/ghc-split +unlit = inplace/lib/unlit +ghc-split = inplace/lib/ghc-split -ld = @LdCmd@ -ar = @ArCmd@ -alex = @AlexCmd@ -happy = @HappyCmd@ -hscolour = @HSCOLOUR@ +alex = @AlexCmd@ +ar = @ArCmd@ +happy = @HappyCmd@ +hscolour = @HSCOLOUR@ +ld = @LdCmd@ +nm = @NmCmd@ +objdump = @ObjdumpCmd@ # Information about builders: #============================ diff --git a/src/Builder.hs b/src/Builder.hs index 4d41d0a..b58d701 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -19,6 +19,7 @@ import Stage -- TODO: do we really need staged builders? data Builder = Alex | Ar + | DeriveConstants | Gcc Stage | GccM Stage | GenPrimopCode @@ -35,6 +36,8 @@ data Builder = Alex | HsCpp | Hsc2Hs | Ld + | Nm + | Objdump | Unlit deriving (Show, Eq, Generic) @@ -43,6 +46,7 @@ builderKey :: Builder -> String builderKey builder = case builder of Alex -> "alex" Ar -> "ar" + DeriveConstants -> "derive-constants" Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' @@ -64,6 +68,8 @@ builderKey builder = case builder of Hsc2Hs -> "hsc2hs" HsCpp -> "hs-cpp" Ld -> "ld" + Nm -> "nm" + Objdump -> "objdump" Unlit -> "unlit" -- TODO: Paths to some builders should be determined using defaultProgramPath From git at git.haskell.org Fri Oct 27 00:18:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (7be13bf) Message-ID: <20171027001804.D956D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7be13bfa70a63ff190245cbfc6779e675e5d6816/ghc >--------------------------------------------------------------- commit 7be13bfa70a63ff190245cbfc6779e675e5d6816 Merge: 8b24f9f 52b915f Author: Andrey Mokhov Date: Sun Feb 7 12:30:56 2016 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 7be13bfa70a63ff190245cbfc6779e675e5d6816 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 00:18:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (0579308) Message-ID: <20171027001805.559B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0579308f9cb7444e28a230867c8ba462238747dd/ghc >--------------------------------------------------------------- commit 0579308f9cb7444e28a230867c8ba462238747dd Author: Andrey Mokhov Date: Fri Jun 24 00:54:42 2016 +0100 Minor revision >--------------------------------------------------------------- 0579308f9cb7444e28a230867c8ba462238747dd README.md | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 6b5b234..4ce3b3a 100644 --- a/README.md +++ b/README.md @@ -43,12 +43,13 @@ runs the `boot` and `configure` scripts automatically on the first build, so tha need to. Use `--skip-configure` to suppress this behaviour (see overview of command line flags below). -* Also note on OS X newer versions of XCode ship with a broken `nm` tool ([#1174](https://ghc.haskell.org/trac/ghc/ticket/11744)). To mitigate the problem place something like +* Also note on OS X newer versions of XCode ship with a broken `nm` tool +([#11744](https://ghc.haskell.org/trac/ghc/ticket/11744)). One way to mitigate the +problem is to add the following into your `UserSettings.hs`: ````haskell userArgs :: Args userArgs = builder (Configure ".") ? arg "--with-nm=$(xcrun --find nm-classic)" ```` - in your `UserSettings.hs`. Using the build system ---------------------- From git at git.haskell.org Fri Oct 27 00:18:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate files with DeriveConstants (#39). (c6cfb36) Message-ID: <20171027001808.203053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6cfb36c2d7ca4f76d3da54d06b40fb86890e7ef/ghc >--------------------------------------------------------------- commit c6cfb36c2d7ca4f76d3da54d06b40fb86890e7ef Author: Andrey Mokhov Date: Sun Dec 27 01:53:52 2015 +0000 Generate files with DeriveConstants (#39). >--------------------------------------------------------------- c6cfb36c2d7ca4f76d3da54d06b40fb86890e7ef src/Rules/Actions.hs | 29 +++++++++++---------- src/Rules/Generate.hs | 22 ++++++++++++++-- src/Settings/Args.hs | 2 ++ src/Settings/Builders/DeriveConstants.hs | 44 ++++++++++++++++++++++++++++++++ src/Settings/Builders/GhcCabal.hs | 1 + 5 files changed, 82 insertions(+), 16 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5a3d113..30ae742 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -47,20 +47,21 @@ build = buildWithResources [] interestingInfo :: Builder -> [String] -> [String] interestingInfo builder ss = case builder of - Alex -> prefixAndSuffix 0 3 ss - Ar -> prefixAndSuffix 2 1 ss - Gcc _ -> prefixAndSuffix 0 4 ss - GccM _ -> prefixAndSuffix 0 1 ss - Ghc _ -> prefixAndSuffix 0 4 ss - GhcCabal -> prefixAndSuffix 3 0 ss - GhcM _ -> prefixAndSuffix 1 1 ss - GhcPkg _ -> prefixAndSuffix 3 0 ss - Haddock -> prefixAndSuffix 1 0 ss - Happy -> prefixAndSuffix 0 3 ss - Hsc2Hs -> prefixAndSuffix 0 3 ss - HsCpp -> prefixAndSuffix 0 1 ss - Ld -> prefixAndSuffix 4 0 ss - _ -> ss + Alex -> prefixAndSuffix 0 3 ss + Ar -> prefixAndSuffix 2 1 ss + DeriveConstants -> prefixAndSuffix 3 0 ss + Gcc _ -> prefixAndSuffix 0 4 ss + GccM _ -> prefixAndSuffix 0 1 ss + Ghc _ -> prefixAndSuffix 0 4 ss + GhcCabal -> prefixAndSuffix 3 0 ss + GhcM _ -> prefixAndSuffix 1 1 ss + GhcPkg _ -> prefixAndSuffix 3 0 ss + Haddock -> prefixAndSuffix 1 0 ss + Happy -> prefixAndSuffix 0 3 ss + Hsc2Hs -> prefixAndSuffix 0 3 ss + HsCpp -> prefixAndSuffix 0 1 ss + Ld -> prefixAndSuffix 4 0 ss + _ -> ss where prefixAndSuffix n m list = let len = length list in diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index e427dfd..2121a9c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,4 +1,6 @@ -module Rules.Generate (generatePackageCode, generateRules) where +module Rules.Generate ( + generatePackageCode, generateRules, includesDependencies + ) where import Expression import GHC @@ -15,6 +17,19 @@ import Settings primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" +derivedConstantsPath :: FilePath +derivedConstantsPath = "includes/dist-derivedconstants/header" + +-- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? +includesDependencies :: [FilePath] +includesDependencies = + [ "includes/ghcautoconf.h" + , "includes/ghcplatform.h" + , derivedConstantsPath -/- "DerivedConstants.h" + , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" ] + -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] knownGenerators = [ (Alex , ".x" ) @@ -33,7 +48,6 @@ generate file target expr = do writeFileChanged file contents putSuccess $ "| Successfully generated '" ++ file ++ "'." - generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let path = targetPath stage pkg @@ -71,6 +85,10 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = build $ fullTarget target GenPrimopCode [primopsTxt] [file] priority 2.0 $ do + when (pkg == compiler && stage == Stage1) $ + derivedConstantsPath ++ "//*" %> \file -> do + build $ fullTarget target DeriveConstants [] [file] + when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 231f5ed..5419f51 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -3,6 +3,7 @@ module Settings.Args (getArgs) where import Expression import Settings.Builders.Alex import Settings.Builders.Ar +import Settings.Builders.DeriveConstants import Settings.Builders.Gcc import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc @@ -32,6 +33,7 @@ defaultArgs = mconcat , arArgs , cabalArgs , customPackageArgs + , deriveConstantsArgs , gccArgs , gccMArgs , genPrimopCodeArgs diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs new file mode 100644 index 0000000..4353875 --- /dev/null +++ b/src/Settings/Builders/DeriveConstants.hs @@ -0,0 +1,44 @@ +module Settings.Builders.DeriveConstants ( + derivedConstantsPath, deriveConstantsArgs + ) where + +import Expression +import Oracles.Config.Flag +import Oracles.Config.Setting +import Predicates (builder, file) +import Settings.Builders.GhcCabal + +derivedConstantsPath :: FilePath +derivedConstantsPath = "includes/dist-derivedconstants/header" + +-- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? +deriveConstantsArgs :: Args +deriveConstantsArgs = builder DeriveConstants ? do + cFlags <- fromDiffExpr includeCcArgs + mconcat + [ file "//DerivedConstants.h" ? arg "--gen-header" + , file "//GHCConstantsHaskellType.hs" ? arg "--gen-haskell-type" + , file "//platformConstants" ? arg "--gen-haskell-value" + , file "//GHCConstantsHaskellWrappers.hs" ? arg "--gen-haskell-wrappers" + , file "//GHCConstantsHaskellExports.hs" ? arg "--gen-haskell-exports" + , arg "-o", arg =<< getOutput + , arg "--tmpdir", arg derivedConstantsPath + , arg "--gcc-program", arg =<< getBuilderPath (Gcc Stage1) + , append . concat $ map (\a -> ["--gcc-flag", a]) cFlags + , arg "--nm-program", arg =<< getBuilderPath Nm + , specified Objdump ? mconcat [ arg "--objdump-program" + , arg =<< getBuilderPath Objdump ] + , arg "--target-os", arg =<< getSetting TargetOs ] + +includeCcArgs :: Args +includeCcArgs = do + confCcArgs <- lift . settingList $ ConfCcArgs Stage1 + mconcat + [ ccArgs + , ccWarnings + , append confCcArgs + , flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER" + , append $ map ("-I" ++) ghcIncludeDirs -- TODO: fix code duplication + , arg "-Irts" + , notM ghcWithSMP ? arg "-DNOSMP" + , arg "-fcommon" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 80c4f4c..cec876a 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -208,6 +208,7 @@ argStagedBuilderPath :: (Stage -> Builder) -> Args argStagedBuilderPath sb = (argM . builderPath . sb) =<< getStage -- Pass arguments to Gcc and corresponding lists of sub-arguments of GhcCabal +-- TODO: simplify appendCcArgs :: [String] -> Args appendCcArgs xs = do mconcat [ stagedBuilder Gcc ? append xs From git at git.haskell.org Fri Oct 27 00:18:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (7e8bfbb) Message-ID: <20171027001808.A035B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e8bfbbe5cf6a1ea303bdaebd862ea74b51eb843/ghc >--------------------------------------------------------------- commit 7e8bfbbe5cf6a1ea303bdaebd862ea74b51eb843 Author: Andrey Mokhov Date: Mon Feb 8 03:09:14 2016 +0000 Minor revision. >--------------------------------------------------------------- 7e8bfbbe5cf6a1ea303bdaebd862ea74b51eb843 src/Builder.hs | 2 +- src/Package.hs | 12 +++++------- src/Target.hs | 16 +++++++--------- 3 files changed, 13 insertions(+), 17 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 80fc4ba..d1a2cc3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -58,7 +58,7 @@ builderProvenance = \case DeriveConstants -> Just (Stage0, deriveConstants) GenApply -> Just (Stage0, genapply) GenPrimopCode -> Just (Stage0, genprimopcode) - Ghc stage -> if stage > Stage0 then Just (pred stage, ghc) else Nothing + Ghc stage -> if stage == Stage0 then Nothing else Just (pred stage, ghc) GhcM stage -> builderProvenance $ Ghc stage GhcCabal -> Just (Stage0, ghcCabal) GhcCabalHsColour -> builderProvenance $ GhcCabal diff --git a/src/Package.hs b/src/Package.hs index 43eb480..4b6fbc6 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -29,13 +29,11 @@ instance Show PackageName where data PackageType = Program | Library deriving Generic data Package = Package - { - pkgName :: PackageName, -- ^ Examples: "ghc", "Cabal" - pkgPath :: FilePath, -- ^ pkgPath is the path to the source code relative to the root. - -- e.g. "compiler", "libraries/Cabal/Cabal" - pkgType :: PackageType - } - deriving Generic + { pkgName :: PackageName -- ^ Examples: "ghc", "Cabal" + , pkgPath :: FilePath -- ^ pkgPath is the path to the source code relative to the root. + -- e.g. "compiler", "libraries/Cabal/Cabal" + , pkgType :: PackageType + } deriving Generic -- | Prettyprint Package name. pkgNameString :: Package -> String diff --git a/src/Target.hs b/src/Target.hs index d2cbfce..8c39ac7 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -18,15 +18,13 @@ import Way -- | Parameters relevant to the current build target. data Target = Target - { - stage :: Stage, -- ^ Stage being built - package :: Package, -- ^ Package being built - builder :: Builder, -- ^ Builder to be invoked - way :: Way, -- ^ Way to build (set to vanilla for most targets) - inputs :: [FilePath], -- ^ Source files passed to the builder - outputs :: [FilePath] -- ^ Files to be produced - } - deriving (Show, Eq, Generic) + { stage :: Stage -- ^ Stage being built + , package :: Package -- ^ Package being built + , builder :: Builder -- ^ Builder to be invoked + , way :: Way -- ^ Way to build (set to vanilla for most targets) + , inputs :: [FilePath] -- ^ Source files passed to the builder + , outputs :: [FilePath] -- ^ Files to be produced + } deriving (Show, Eq, Generic) -- | If values of type @a@ form a 'Monoid' then we can also derive a 'Monoid' -- instance for values of type @'ReaderT' 'Target' 'Action' a@: From git at git.haskell.org Fri Oct 27 00:18:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Oracle 'DirectoryContent' (21f3e05) Message-ID: <20171027001809.405393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21f3e0562f3d4685e384f2ba374898dc6868ce0e/ghc >--------------------------------------------------------------- commit 21f3e0562f3d4685e384f2ba374898dc6868ce0e Author: Kai Harries Date: Tue Jun 28 09:39:55 2016 +0200 Add Oracle 'DirectoryContent' >--------------------------------------------------------------- 21f3e0562f3d4685e384f2ba374898dc6868ce0e hadrian.cabal | 1 + src/Oracles/DirectoryContent.hs | 31 +++++++++++++++++++++++++++++++ src/Rules/Oracles.hs | 2 ++ 3 files changed, 34 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 5ffcb65..df2a4a5 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -30,6 +30,7 @@ executable hadrian , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies + , Oracles.DirectoryContent , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContent.hs new file mode 100644 index 0000000..6211222 --- /dev/null +++ b/src/Oracles/DirectoryContent.hs @@ -0,0 +1,31 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module Oracles.DirectoryContent ( + getDirectoryContent, directoryContentOracle, Exclude(..), ExcludeNot(..) + ) where + +import Base +import System.Directory.Extra + +newtype DirectoryContent = DirectoryContent (Exclude, ExcludeNot, FilePath) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) +newtype Exclude = Exclude [FilePattern] + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) +newtype ExcludeNot = ExcludeNot [FilePattern] + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Get the directory content. 'Exclude' and 'ExcludeNot' are a list of file +-- patterns matched with '?=='. +getDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> Action [FilePath] +getDirectoryContent exclude excludeNot dir = + askOracle $ DirectoryContent (exclude, excludeNot, dir) + +directoryContentOracle :: Rules () +directoryContentOracle = void $ addOracle oracle + where + oracle :: DirectoryContent -> Action [FilePath] + oracle (DirectoryContent (Exclude exclude, ExcludeNot excludeNot, dir)) = + liftIO $ filter test <$> listFilesInside (return . test) dir + where + test a = include' a || not (exclude' a) + exclude' a = any (?== a) exclude + include' a = any (?== a) excludeNot diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 7beb67f..10767b5 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -4,6 +4,7 @@ import Base import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies +import qualified Oracles.DirectoryContent import qualified Oracles.LookupInPath import qualified Oracles.ModuleFiles import qualified Oracles.PackageData @@ -15,6 +16,7 @@ oracleRules = do Oracles.ArgsHash.argsHashOracle Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles + Oracles.DirectoryContent.directoryContentOracle Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle From git at git.haskell.org Fri Oct 27 00:18:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add explicit dependencies on includes/ generated files (fix #48). (1fcb025) Message-ID: <20171027001811.A78B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fcb025a9405f6b2970d1efdaf47558b300de1a9/ghc >--------------------------------------------------------------- commit 1fcb025a9405f6b2970d1efdaf47558b300de1a9 Author: Andrey Mokhov Date: Sun Dec 27 01:55:29 2015 +0000 Add explicit dependencies on includes/ generated files (fix #48). >--------------------------------------------------------------- 1fcb025a9405f6b2970d1efdaf47558b300de1a9 src/Rules/Dependencies.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 907c4d3..5d08df1 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -4,6 +4,7 @@ import Expression import GHC import Oracles import Rules.Actions +import Rules.Generate import Rules.Resources import Settings @@ -17,13 +18,13 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do (buildPath "*.c.deps") %> \out -> do let srcFile = dropBuild . dropExtension $ out - when (pkg == compiler) $ need [platformH] + when (pkg == compiler) . need $ platformH : includesDependencies need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - when (pkg == compiler) $ need [platformH] + when (pkg == compiler) . need $ platformH : includesDependencies -- TODO: very ugly and fragile; use gcc -MM instead? let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) [ "primop-vector-uniques.hs-incl" From git at git.haskell.org Fri Oct 27 00:18:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -fno-warn-name-shadowing. (7d7802d) Message-ID: <20171027001812.334293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d7802d73a03dd913d43aad6e36ec6e72c6744ae/ghc >--------------------------------------------------------------- commit 7d7802d73a03dd913d43aad6e36ec6e72c6744ae Author: Andrey Mokhov Date: Mon Feb 8 23:17:49 2016 +0000 Add -fno-warn-name-shadowing. >--------------------------------------------------------------- 7d7802d73a03dd913d43aad6e36ec6e72c6744ae build.sh | 1 + 1 file changed, 1 insertion(+) diff --git a/build.sh b/build.sh index 719e85e..77c9fa4 100755 --- a/build.sh +++ b/build.sh @@ -35,6 +35,7 @@ mkdir -p "$root/.shake" ghc \ "$root/src/Main.hs" \ -Wall \ + -fno-warn-name-shadowing \ -i"$root/src" \ -rtsopts \ -with-rtsopts=-I0 \ From git at git.haskell.org Fri Oct 27 00:18:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rework copyDirectoryContent (5439f0e) Message-ID: <20171027001812.AF0303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5439f0ee49094ad46574a38b217f741ba4f6ea35/ghc >--------------------------------------------------------------- commit 5439f0ee49094ad46574a38b217f741ba4f6ea35 Author: Kai Harries Date: Tue Jun 28 09:43:52 2016 +0200 Rework copyDirectoryContent >--------------------------------------------------------------- 5439f0ee49094ad46574a38b217f741ba4f6ea35 src/Rules/Actions.hs | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 734cb91..c3680f9 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -2,7 +2,7 @@ module Rules.Actions ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, removeFile, copyDirectory, copyDirectoryContent, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, - makeExecutable, renderProgram, renderLibrary + makeExecutable, renderProgram, renderLibrary, Exclude(..), ExcludeNot(..) ) where import qualified System.Directory.Extra as IO @@ -14,6 +14,7 @@ import CmdLineFlag import Context import Expression import Oracles.ArgsHash +import Oracles.DirectoryContent import Oracles.WindowsPath import Settings import Settings.Args @@ -127,17 +128,18 @@ copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd cmdEcho ["cp", "-r", source, target] --- | Copy the content of the source directory into the target directory. Only --- the files and directories for which the predicate returns True are copied. -copyDirectoryContent :: (FilePath -> IO Bool) -> FilePath -> FilePath -> Action () -copyDirectoryContent test source target = do - putProgressInfo $ renderAction "Copy directory" source target - liftIO $ IO.listFilesInside test' source >>= mapM_ cp +-- | Copy the content of the source directory into the target directory. +-- 'Exclude' and 'ExcludeNot' are a list of file patterns matched with '?=='. +-- The copied content is tracked. +copyDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> FilePath -> Action () +copyDirectoryContent exclude excludeNot source target = do + putProgressInfo $ renderAction "Copy directory content" source target + getDirectoryContent exclude excludeNot source >>= mapM_ cp where + cp a = do + createDirectory $ dropFileName $ target' a + copyFile a $ target' a target' a = target -/- fromJust (stripPrefix source a) - test' a = ifM (test a) (mkdir a >> return True) (return False) - mkdir a = IO.createDirectoryIfMissing True $ target' a - cp a = whenM (test a) $ IO.copyFile a $ target' a -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:18:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add install targets, install inplace/lib/platformConstants. (43b6cc3) Message-ID: <20171027001815.3A6B73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/43b6cc390adbf439e8b98c19eb8b9196f0a58bfb/ghc >--------------------------------------------------------------- commit 43b6cc390adbf439e8b98c19eb8b9196f0a58bfb Author: Andrey Mokhov Date: Sun Dec 27 02:13:55 2015 +0000 Add install targets, install inplace/lib/platformConstants. >--------------------------------------------------------------- 43b6cc390adbf439e8b98c19eb8b9196f0a58bfb src/Rules.hs | 4 +++- src/Rules/Generate.hs | 3 ++- src/Rules/Install.hs | 16 ++++++++++++---- 3 files changed, 17 insertions(+), 6 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 5516c33..a9ac3e4 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,6 +1,7 @@ module Rules (generateTargets, packageRules) where import Expression +import Rules.Install import Rules.Package import Rules.Resources import Settings @@ -18,7 +19,8 @@ generateTargets = action $ do return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] return $ libTargets ++ programTargets - need targets + + need $ targets ++ installTargets packageRules :: Rules () packageRules = do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 2121a9c..ccd059f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,5 +1,6 @@ module Rules.Generate ( - generatePackageCode, generateRules, includesDependencies + generatePackageCode, generateRules, + derivedConstantsPath, includesDependencies ) where import Expression diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index b592728..fca88fe 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -1,11 +1,19 @@ -module Rules.Install (installRules) where +module Rules.Install (installTargets, installRules) where import Expression import GHC +import Rules.Generate + +installTargets :: [FilePath] +installTargets = [ "inplace/lib/template-hsc.h" + , "inplace/lib/platformConstants" ] installRules :: Rules () installRules = do - "inplace/lib/template-hsc.h" %> \out -> do - let source = pkgPath hsc2hs -/- "template-hsc.h" - putBuild $ "| Copying " ++ source ++ " -> " ++ out + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs + "inplace/lib/platformConstants" <~ derivedConstantsPath + where + file <~ dir = file %> \out -> do + let source = dir -/- takeFileName out copyFileChanged source out + putSuccess $ "| Installed " ++ source ++ " -> " ++ out From git at git.haskell.org Fri Oct 27 00:18:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Rules.Config to Rules.Setup. (d5e2d92) Message-ID: <20171027001816.2F8B73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d5e2d9278d4590fa370fb73900447a573fc37e2f/ghc >--------------------------------------------------------------- commit d5e2d9278d4590fa370fb73900447a573fc37e2f Author: Andrey Mokhov Date: Mon Feb 8 23:19:35 2016 +0000 Rename Rules.Config to Rules.Setup. See #204. >--------------------------------------------------------------- d5e2d9278d4590fa370fb73900447a573fc37e2f shaking-up-ghc.cabal | 2 +- src/Main.hs | 4 ++-- src/Rules/{Config.hs => Setup.hs} | 6 +++--- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 0807ff3..254617d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -42,7 +42,6 @@ executable ghc-shake , Rules.Cabal , Rules.Clean , Rules.Compile - , Rules.Config , Rules.Data , Rules.Dependencies , Rules.Documentation @@ -64,6 +63,7 @@ executable ghc-shake , Rules.Program , Rules.Register , Rules.Resources + , Rules.Setup , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg , Selftest diff --git a/src/Main.hs b/src/Main.hs index 79601d8..544987d 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -8,12 +8,12 @@ import qualified Environment import qualified Rules import qualified Rules.Cabal import qualified Rules.Clean -import qualified Rules.Config import qualified Rules.Generate import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl +import qualified Rules.Setup import qualified Selftest import qualified Test @@ -29,13 +29,13 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do rules = mconcat [ Rules.Cabal.cabalRules , Rules.Clean.cleanRules - , Rules.Config.configRules , Rules.Generate.generateRules , Rules.Generate.copyRules , Rules.Gmp.gmpRules , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules , Rules.Perl.perlScriptRules + , Rules.Setup.setupRules , Rules.topLevelTargets , Rules.packageRules , Selftest.selftestRules diff --git a/src/Rules/Config.hs b/src/Rules/Setup.hs similarity index 93% rename from src/Rules/Config.hs rename to src/Rules/Setup.hs index 1016be9..a88084c 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Setup.hs @@ -1,4 +1,4 @@ -module Rules.Config (configRules) where +module Rules.Setup (setupRules) where import qualified System.Info @@ -7,8 +7,8 @@ import CmdLineFlag import Rules.Actions import Rules.Generators.GhcAutoconfH -configRules :: Rules () -configRules = do +setupRules :: Rules () +setupRules = do -- We always rerun the configure script in this mode, because the flags -- passed to it can affect the contents of system.config file. [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do From git at git.haskell.org Fri Oct 27 00:18:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: getDirectoryContent: Implement an AST for matching (5999957) Message-ID: <20171027001816.9813D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59999579eb089d578b0bed928bfe338b8705cace/ghc >--------------------------------------------------------------- commit 59999579eb089d578b0bed928bfe338b8705cace Author: Kai Harries Date: Fri Jul 1 15:30:56 2016 +0200 getDirectoryContent: Implement an AST for matching >--------------------------------------------------------------- 59999579eb089d578b0bed928bfe338b8705cace src/Oracles/DirectoryContent.hs | 44 ++++++++++++++++++++++++----------------- src/Rules/Actions.hs | 9 ++++----- 2 files changed, 30 insertions(+), 23 deletions(-) diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContent.hs index 6211222..45afa92 100644 --- a/src/Oracles/DirectoryContent.hs +++ b/src/Oracles/DirectoryContent.hs @@ -1,31 +1,39 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} module Oracles.DirectoryContent ( - getDirectoryContent, directoryContentOracle, Exclude(..), ExcludeNot(..) + getDirectoryContent, directoryContentOracle, Match(..) ) where import Base +import GHC.Generics import System.Directory.Extra -newtype DirectoryContent = DirectoryContent (Exclude, ExcludeNot, FilePath) - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -newtype Exclude = Exclude [FilePattern] - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -newtype ExcludeNot = ExcludeNot [FilePattern] +newtype DirectoryContent = DirectoryContent (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- | Get the directory content. 'Exclude' and 'ExcludeNot' are a list of file --- patterns matched with '?=='. -getDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> Action [FilePath] -getDirectoryContent exclude excludeNot dir = - askOracle $ DirectoryContent (exclude, excludeNot, dir) +data Match = Test FilePattern | Not (Match) | And [Match] | Or [Match] + deriving (Generic, Eq, Show, Typeable) +instance Binary Match +instance Hashable Match +instance NFData Match + +matches :: Match -> FilePath -> Bool +matches (Test m) f = m ?== f +matches (Not m) f = not $ matches m f +matches (And []) _ = True +matches (And (m:ms)) f | matches m f = matches (And ms) f + | otherwise = False +matches (Or []) _ = False +matches (Or (m:ms)) f | matches m f = True + | otherwise = matches (Or ms) f + +-- | Get the directory content recursively. +getDirectoryContent :: Match -> FilePath -> Action [FilePath] +getDirectoryContent expr dir = + askOracle $ DirectoryContent (expr, dir) directoryContentOracle :: Rules () directoryContentOracle = void $ addOracle oracle where oracle :: DirectoryContent -> Action [FilePath] - oracle (DirectoryContent (Exclude exclude, ExcludeNot excludeNot, dir)) = - liftIO $ filter test <$> listFilesInside (return . test) dir - where - test a = include' a || not (exclude' a) - exclude' a = any (?== a) exclude - include' a = any (?== a) excludeNot + oracle (DirectoryContent (expr, dir)) = + liftIO $ filter (matches expr) <$> listFilesInside (return . matches expr) dir diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index c3680f9..7b4c46c 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -2,7 +2,7 @@ module Rules.Actions ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, removeFile, copyDirectory, copyDirectoryContent, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, - makeExecutable, renderProgram, renderLibrary, Exclude(..), ExcludeNot(..) + makeExecutable, renderProgram, renderLibrary, Match(..) ) where import qualified System.Directory.Extra as IO @@ -129,12 +129,11 @@ copyDirectory source target = do quietly $ cmd cmdEcho ["cp", "-r", source, target] -- | Copy the content of the source directory into the target directory. --- 'Exclude' and 'ExcludeNot' are a list of file patterns matched with '?=='. -- The copied content is tracked. -copyDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> FilePath -> Action () -copyDirectoryContent exclude excludeNot source target = do +copyDirectoryContent :: Match -> FilePath -> FilePath -> Action () +copyDirectoryContent expr source target = do putProgressInfo $ renderAction "Copy directory content" source target - getDirectoryContent exclude excludeNot source >>= mapM_ cp + getDirectoryContent expr source >>= mapM_ cp where cp a = do createDirectory $ dropFileName $ target' a From git at git.haskell.org Fri Oct 27 00:18:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #266 from KaiHa/copyDirectoryContent (df3ad6d) Message-ID: <20171027001820.63AC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/df3ad6da2a9e7865bd535499412fd453d29f8a94/ghc >--------------------------------------------------------------- commit df3ad6da2a9e7865bd535499412fd453d29f8a94 Merge: 0579308 5999957 Author: Andrey Mokhov Date: Fri Jul 1 15:44:33 2016 +0100 Merge pull request #266 from KaiHa/copyDirectoryContent Add actions copyDirectoryContent and runBuilderWith >--------------------------------------------------------------- df3ad6da2a9e7865bd535499412fd453d29f8a94 hadrian.cabal | 1 + src/Oracles/DirectoryContent.hs | 39 +++++++++++++++++++++++++++++++++++++++ src/Rules/Actions.hs | 27 ++++++++++++++++++++++----- src/Rules/Oracles.hs | 2 ++ 4 files changed, 64 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Oct 27 00:18:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Generate includes/ghcversion.h (66f18be) Message-ID: <20171027001819.1B7663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/66f18bec2737a73fc1b2387726e22a35ef6edd8a/ghc >--------------------------------------------------------------- commit 66f18bec2737a73fc1b2387726e22a35ef6edd8a Author: Moritz Angermann Date: Sun Dec 27 14:27:55 2015 +0800 Generate includes/ghcversion.h This should be the final commit to fix #39. >--------------------------------------------------------------- 66f18bec2737a73fc1b2387726e22a35ef6edd8a shaking-up-ghc.cabal | 1 + src/Rules/Generate.hs | 2 ++ src/Rules/Generators/GhcVersionH.hs | 33 +++++++++++++++++++++++++++++++++ 3 files changed, 36 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 941651b..0e60637 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -46,6 +46,7 @@ executable ghc-shake , Rules.Generators.GhcAutoconfH , Rules.Generators.GhcBootPlatformH , Rules.Generators.GhcPlatformH + , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs , Rules.Install , Rules.Library diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index ccd059f..bc0089c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -9,6 +9,7 @@ import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH import Rules.Generators.GhcBootPlatformH import Rules.Generators.GhcPlatformH +import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles import Rules.Actions @@ -107,6 +108,7 @@ generateRules :: Rules () generateRules = do "includes/ghcautoconf.h" <~ generateGhcAutoconfH "includes/ghcplatform.h" <~ generateGhcPlatformH + "includes/ghcversion.h" <~ generateGhcVersionH where file <~ gen = file %> \out -> generate out emptyTarget gen diff --git a/src/Rules/Generators/GhcVersionH.hs b/src/Rules/Generators/GhcVersionH.hs new file mode 100644 index 0000000..a45df55 --- /dev/null +++ b/src/Rules/Generators/GhcVersionH.hs @@ -0,0 +1,33 @@ +module Rules.Generators.GhcVersionH (generateGhcVersionH) where + +import Expression +import Oracles + +generateGhcVersionH :: Expr String +generateGhcVersionH = do + version <- getSetting ProjectVersionInt + patchLevel1 <- getSetting ProjectPatchLevel1 + patchLevel2 <- getSetting ProjectPatchLevel2 + return . unlines $ + [ "#ifndef __GHCVERSION_H__" + , "#define __GHCVERSION_H__" + , "" + , "#ifndef __GLASGOW_HASKELL__" + , "# define __GLASGOW_HASKELL__ " ++ version + , "#endif" + , ""] + ++ + [ "#define __GLASGOW_HASKELL_PATCHLEVEL1__ " ++ patchLevel1 | patchLevel1 /= "" ] + ++ + [ "#define __GLASGOW_HASKELL_PATCHLEVEL2__ " ++ patchLevel2 | patchLevel2 /= "" ] + ++ + [ "" + , "#define MIN_VERSION_GLASGOW_HASKELL(ma,mi,pl1,pl2) (\\" + , " ((ma)*100+(mi)) < __GLASGOW_HASKELL__ || \\" + , " ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \\" + , " && (pl1) < __GLASGOW_HASKELL_PATCHLEVEL1__ || \\" + , " ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \\" + , " && (pl1) == __GLASGOW_HASKELL_PATCHLEVEL1__ \\" + , " && (pl2) <= __GLASGOW_HASKELL_PATCHLEVEL2__ )" + , "" + , "#endif /* __GHCVERSION_H__ */" ] From git at git.haskell.org Fri Oct 27 00:18:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run mk/get-win32-tarballs.sh on Windows. (0678acb) Message-ID: <20171027001820.3D25B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0678acb67ab59b4af9f2401959e1d71ef27d77bc/ghc >--------------------------------------------------------------- commit 0678acb67ab59b4af9f2401959e1d71ef27d77bc Author: Andrey Mokhov Date: Mon Feb 8 23:37:58 2016 +0000 Run mk/get-win32-tarballs.sh on Windows. See #204. >--------------------------------------------------------------- 0678acb67ab59b4af9f2401959e1d71ef27d77bc src/Rules/Setup.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index a88084c..ac53592 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -17,10 +17,13 @@ setupRules = do RunConfigure args -> do need [ settings <.> "in", cfgH <.> "in" ] -- We cannot use windowsHost here due to a cyclic dependency - let defaultArgs = if System.Info.os == "mingw32" - then [ "--enable-tarballs-autodownload" ] - else [] - runConfigure "." [] $ defaultArgs ++ [args] + when (System.Info.os == "mingw32") $ do + putBuild "| Checking for Windows tarballs..." + quietly $ cmd [ "bash" + , "mk/get-win32-tarballs.sh" + , "download" + , System.Info.arch ] + runConfigure "." [] [args] SkipConfigure -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " From git at git.haskell.org Fri Oct 27 00:18:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds ghcautoconf and ghcplatform as dependencies to hp2ps. (456d2bd) Message-ID: <20171027001822.9863E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/456d2bdadab272bc40d63f166e0eeaaf0a13ca02/ghc >--------------------------------------------------------------- commit 456d2bdadab272bc40d63f166e0eeaaf0a13ca02 Author: Moritz Angermann Date: Sun Dec 27 14:41:23 2015 +0800 Adds ghcautoconf and ghcplatform as dependencies to hp2ps. 1fcb025 added includes to the dependencies for the `compiler` package, but `hp2ps` already requires them and is built prior to the `compiler` package. This should fix #48 for good. Also updates the README.md to reflect the closure of #44. >--------------------------------------------------------------- 456d2bdadab272bc40d63f166e0eeaaf0a13ca02 README.md | 3 --- src/Rules/Dependencies.hs | 2 ++ 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index ca1e5fb..93674a1 100644 --- a/README.md +++ b/README.md @@ -55,9 +55,6 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure --with-gcc=$(which clang) # See #26 -./shake-build/build.sh includes/ghcautoconf.h # See #48 -./shake-build/build.sh includes/ghcplatform.h # See #48 -cp utils/hsc2hs/template-hsc.h inplace/lib/template-hsc.h # See #44 ./shake-build/build.sh ``` diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 5d08df1..197fa64 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -19,12 +19,14 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = (buildPath "*.c.deps") %> \out -> do let srcFile = dropBuild . dropExtension $ out when (pkg == compiler) . need $ platformH : includesDependencies + when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources when (pkg == compiler) . need $ platformH : includesDependencies + when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] -- TODO: very ugly and fragile; use gcc -MM instead? let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) [ "primop-vector-uniques.hs-incl" From git at git.haskell.org Fri Oct 27 00:18:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (507f48d) Message-ID: <20171027001824.182663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/507f48d12b6715d0943ae1b6bc4d7e8b6c676870/ghc >--------------------------------------------------------------- commit 507f48d12b6715d0943ae1b6bc4d7e8b6c676870 Author: Andrey Mokhov Date: Mon Feb 8 23:52:38 2016 +0000 Minor revision. >--------------------------------------------------------------- 507f48d12b6715d0943ae1b6bc4d7e8b6c676870 src/Rules/Actions.hs | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9275207..1a6fbf8 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -106,17 +106,16 @@ runConfigure dir opts args = do need [dir -/- "configure"] let args' = filter (not . null) args note = if null args' then "" else " (" ++ intercalate ", " args' ++ ")" + -- Always configure with bash. + -- This also injects /bin/bash into `libtool`, instead of /bin/sh + opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] if dir == "." then do putBuild $ "| Run configure" ++ note ++ "..." - quietly $ cmd Shell (EchoStdout False) "bash configure" opts' args + quietly $ cmd Shell (EchoStdout False) "bash configure" opts' args' else do putBuild $ "| Run configure" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args - where - -- Always configure with bash. - -- This also injects /bin/bash into `libtool`, instead of /bin/sh - opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] + quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args' runMake :: FilePath -> [String] -> Action () runMake = runMakeWithVerbosity False From git at git.haskell.org Fri Oct 27 00:18:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused folder (88b495c) Message-ID: <20171027001824.41BDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88b495c3dec700e76501319a995e2902a159d838/ghc >--------------------------------------------------------------- commit 88b495c3dec700e76501319a995e2902a159d838 Author: Andrey Mokhov Date: Wed Jul 13 00:44:16 2016 +0100 Drop unused folder >--------------------------------------------------------------- 88b495c3dec700e76501319a995e2902a159d838 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 5307cdd..6fbc3b2 100644 --- a/.gitignore +++ b/.gitignore @@ -1,4 +1,4 @@ -/.db/ +# generated by the configure script cfg/system.config # build.bat and build.sh specific From git at git.haskell.org Fri Oct 27 00:18:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #58 from angerman/feature/ghcversion (b45902d) Message-ID: <20171027001826.111B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b45902dd36889637607dd1611272c93d4fcab4fd/ghc >--------------------------------------------------------------- commit b45902dd36889637607dd1611272c93d4fcab4fd Merge: 43b6cc3 66f18be Author: Andrey Mokhov Date: Sun Dec 27 09:35:33 2015 +0000 Merge pull request #58 from angerman/feature/ghcversion Generate includes/ghcversion.h >--------------------------------------------------------------- b45902dd36889637607dd1611272c93d4fcab4fd shaking-up-ghc.cabal | 1 + src/Rules/Generate.hs | 2 ++ src/Rules/Generators/GhcVersionH.hs | 33 +++++++++++++++++++++++++++++++++ 3 files changed, 36 insertions(+) From git at git.haskell.org Fri Oct 27 00:18:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename the --configure flag to --setup. (4cef7ec) Message-ID: <20171027001827.B955D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1/ghc >--------------------------------------------------------------- commit 4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1 Author: Andrey Mokhov Date: Mon Feb 8 23:53:19 2016 +0000 Rename the --configure flag to --setup. See #204. >--------------------------------------------------------------- 4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1 src/CmdLineFlag.hs | 40 ++++++++++++++++++++-------------------- src/Rules/Setup.hs | 10 +++++----- 2 files changed, 25 insertions(+), 25 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 84d4f11..c7d2b35 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,5 +1,5 @@ module CmdLineFlag ( - putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdConfigure, Configure (..), + putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdSetup, Setup (..), cmdFlavour, Flavour (..), cmdProgressInfo, ProgressInfo (..), cmdSplitObjects ) where @@ -11,7 +11,7 @@ import System.IO.Unsafe (unsafePerformIO) -- Command line flags data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -data Configure = SkipConfigure | RunConfigure String deriving (Eq, Show) +data Setup = SkipSetup | RunSetup String deriving (Eq, Show) data Flavour = Default | Quick deriving (Eq, Show) -- | 'CmdLineFlag.Untracked' is a collection of flags that can be passed via the @@ -19,9 +19,9 @@ data Flavour = Default | Quick deriving (Eq, Show) -- build rules to be rurun. data Untracked = Untracked { buildHaddock :: Bool - , configure :: Configure , flavour :: Flavour , progressInfo :: ProgressInfo + , setup :: Setup , splitObjects :: Bool } deriving (Eq, Show) @@ -29,24 +29,14 @@ data Untracked = Untracked defaultUntracked :: Untracked defaultUntracked = Untracked { buildHaddock = False - , configure = SkipConfigure , flavour = Default , progressInfo = Normal + , setup = SkipSetup , splitObjects = False } readBuildHaddock :: Either String (Untracked -> Untracked) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } -readConfigure :: Maybe String -> Either String (Untracked -> Untracked) -readConfigure ms = - maybe (Left "Cannot parse configure") (Right . set) (go $ lower <$> ms) - where - go :: Maybe String -> Maybe Configure - go (Just args) = Just $ RunConfigure args - go Nothing = Just $ RunConfigure "" - set :: Configure -> Untracked -> Untracked - set flag flags = flags { configure = flag } - readFlavour :: Maybe String -> Either String (Untracked -> Untracked) readFlavour ms = maybe (Left "Cannot parse flavour") (Right . set) (go =<< lower <$> ms) @@ -71,19 +61,29 @@ readProgressInfo ms = set :: ProgressInfo -> Untracked -> Untracked set flag flags = flags { progressInfo = flag } +readSetup :: Maybe String -> Either String (Untracked -> Untracked) +readSetup ms = + maybe (Left "Cannot parse setup") (Right . set) (go $ lower <$> ms) + where + go :: Maybe String -> Maybe Setup + go (Just args) = Just $ RunSetup args + go Nothing = Just $ RunSetup "" + set :: Setup -> Untracked -> Untracked + set flag flags = flags { setup = flag } + readSplitObjects :: Either String (Untracked -> Untracked) readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = - [ Option [] ["configure"] (OptArg readConfigure "ARGS") - "Run configure with ARGS (also run boot if necessary)." - , Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") + [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") "Build flavour (Default or Quick)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") "Progress info style (None, Brief, Normal, or Unicorn)." + , Option [] ["setup"] (OptArg readSetup "CONFIGURE_ARGS") + "Setup the build system, pass CONFIGURE_ARGS to ./configure." , Option [] ["split-objects"] (NoArg readSplitObjects) "Generate split objects (requires a full clean rebuild)." ] @@ -103,14 +103,14 @@ getCmdLineFlags = unsafePerformIO $ readIORef cmdLineFlags cmdBuildHaddock :: Bool cmdBuildHaddock = buildHaddock getCmdLineFlags -cmdConfigure :: Configure -cmdConfigure = configure getCmdLineFlags - cmdFlavour :: Flavour cmdFlavour = flavour getCmdLineFlags cmdProgressInfo :: ProgressInfo cmdProgressInfo = progressInfo getCmdLineFlags +cmdSetup :: Setup +cmdSetup = setup getCmdLineFlags + cmdSplitObjects :: Bool cmdSplitObjects = splitObjects getCmdLineFlags diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index ac53592..c99c8be 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -13,8 +13,8 @@ setupRules = do -- passed to it can affect the contents of system.config file. [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do alwaysRerun - case cmdConfigure of - RunConfigure args -> do + case cmdSetup of + RunSetup configureArgs -> do need [ settings <.> "in", cfgH <.> "in" ] -- We cannot use windowsHost here due to a cyclic dependency when (System.Info.os == "mingw32") $ do @@ -23,11 +23,11 @@ setupRules = do , "mk/get-win32-tarballs.sh" , "download" , System.Info.arch ] - runConfigure "." [] [args] - SkipConfigure -> unlessM (doesFileExist cfg) $ + runConfigure "." [] [configureArgs] + SkipSetup -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " - ++ "build system by passing --configure[=ARGS] flag." + ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." ["configure", configH <.> "in"] &%> \_ -> do putBuild "| Running boot..." From git at git.haskell.org Fri Oct 27 00:18:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Enable RecordWildCards (fa4ca65) Message-ID: <20171027001827.E88A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fa4ca65a88bd883758888df5665d78844138c69f/ghc >--------------------------------------------------------------- commit fa4ca65a88bd883758888df5665d78844138c69f Author: Andrey Mokhov Date: Wed Jul 13 00:37:22 2016 +0100 Enable RecordWildCards >--------------------------------------------------------------- fa4ca65a88bd883758888df5665d78844138c69f .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 2f24ebe..85dfc94 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,2 @@ -:set -Wall -fno-warn-name-shadowing -isrc +:set -Wall -fno-warn-name-shadowing -isrc -XRecordWildCards :load Main From git at git.haskell.org Fri Oct 27 00:18:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #59 from angerman/feature/hp2ps-deps (3b1b4df) Message-ID: <20171027001829.76B6F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b1b4df56ef0ec92bd88f53eceb13cff11e4130d/ghc >--------------------------------------------------------------- commit 3b1b4df56ef0ec92bd88f53eceb13cff11e4130d Merge: b45902d 456d2bd Author: Andrey Mokhov Date: Sun Dec 27 09:36:49 2015 +0000 Merge pull request #59 from angerman/feature/hp2ps-deps Adds ghcautoconf and ghcplatform as dependencies to hp2ps. >--------------------------------------------------------------- 3b1b4df56ef0ec92bd88f53eceb13cff11e4130d README.md | 3 --- src/Rules/Dependencies.hs | 2 ++ 2 files changed, 2 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:18:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor build flavours (3be52c5) Message-ID: <20171027001831.99AFE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46/ghc >--------------------------------------------------------------- commit 3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46 Author: Andrey Mokhov Date: Wed Jul 13 00:43:38 2016 +0100 Refactor build flavours See #268. >--------------------------------------------------------------- 3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46 hadrian.cabal | 4 +- src/CmdLineFlag.hs | 24 ++---- src/Flavour.hs | 18 ++++ src/Oracles/ArgsHash.hs | 2 +- src/Oracles/Dependencies.hs | 1 + src/Oracles/WindowsPath.hs | 8 +- src/Rules.hs | 18 ++-- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 1 + src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 3 +- src/Rules/Dependencies.hs | 3 +- src/Rules/Documentation.hs | 4 +- src/Rules/Generate.hs | 3 +- src/Rules/Generators/ConfigHs.hs | 6 +- src/Rules/Library.hs | 5 +- src/Rules/Program.hs | 2 + src/Rules/Register.hs | 2 +- src/Rules/Test.hs | 6 +- src/Rules/Wrappers/Ghc.hs | 2 +- src/Rules/Wrappers/GhcPkg.hs | 3 +- src/Settings.hs | 58 ++++++++++--- src/Settings/Args.hs | 95 --------------------- src/Settings/Builders/Cc.hs | 2 +- src/Settings/Builders/Common.hs | 1 + src/Settings/Builders/Configure.hs | 3 +- src/Settings/Builders/Ghc.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 5 +- src/Settings/Builders/GhcPkg.hs | 1 + src/Settings/Builders/Haddock.hs | 1 + src/Settings/Builders/Hsc2Hs.hs | 1 + src/Settings/Builders/Make.hs | 2 +- src/Settings/Default.hs | 169 ++++++++++++++++++++++++++++++++++++- src/Settings/Default.hs-boot | 13 +++ src/Settings/Flavours/Quick.hs | 22 +++-- src/Settings/Flavours/Quickest.hs | 18 ++-- src/Settings/Packages.hs | 57 ------------- src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Compiler.hs | 5 +- src/Settings/Packages/Rts.hs | 1 + src/Settings/Ways.hs | 46 ---------- src/UserSettings.hs | 57 +++---------- 43 files changed, 360 insertions(+), 324 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 3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46 From git at git.haskell.org Fri Oct 27 00:18:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up. (b27b177) Message-ID: <20171027001832.D9EC23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b27b177a5657e7c8a9088ace440f73074ab4f2d7/ghc >--------------------------------------------------------------- commit b27b177a5657e7c8a9088ace440f73074ab4f2d7 Author: Andrey Mokhov Date: Mon Dec 28 03:01:15 2015 +0000 Clean up. >--------------------------------------------------------------- b27b177a5657e7c8a9088ace440f73074ab4f2d7 src/Builder.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index b58d701..b6fd228 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -14,9 +14,10 @@ import Stage -- Ghc StageN, N > 0, is the one built on stage (N - 1) -- GhcPkg Stage0 is the bootstrapping GhcPkg -- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) --- TODO: add Cpp builders --- TODO: rename Gcc to Cc? --- TODO: do we really need staged builders? +-- TODO: Do we really need HsCpp builder? Can't we use a generic Cpp +-- builder instead? It would also be used instead of GccM. +-- TODO: rename Gcc to CCompiler? We sometimes use gcc and sometimes clang. +-- TODO: why are Gcc/GccM staged? data Builder = Alex | Ar | DeriveConstants @@ -26,7 +27,6 @@ data Builder = Alex | Ghc Stage | GhcCabal | GhcCabalHsColour - | GhcLink Stage | GhcM Stage | GhcPkg Stage | GhcSplit @@ -55,7 +55,6 @@ builderKey builder = case builder of Ghc Stage1 -> "ghc-stage1" Ghc Stage2 -> "ghc-stage2" Ghc Stage3 -> "ghc-stage3" - GhcLink stage -> builderKey $ Ghc stage -- using Ghc as linker GhcM stage -> builderKey $ Ghc stage -- synonym for 'Ghc -M' GhcCabal -> "ghc-cabal" GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' From git at git.haskell.org Fri Oct 27 00:18:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename --configure to --setup. (2fe68f0) Message-ID: <20171027001831.606DE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2fe68f0a0c1e737ed2ba1f8d4a606a6953497f74/ghc >--------------------------------------------------------------- commit 2fe68f0a0c1e737ed2ba1f8d4a606a6953497f74 Author: Andrey Mokhov Date: Tue Feb 9 00:07:10 2016 +0000 Rename --configure to --setup. Fix #204. [skip ci] >--------------------------------------------------------------- 2fe68f0a0c1e737ed2ba1f8d4a606a6953497f74 README.md | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 35f8ac3..96b3106 100644 --- a/README.md +++ b/README.md @@ -52,19 +52,19 @@ are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue In addition to standard Shake flags (try `--help`), the build system currently supports several others: -* `--configure[=ARGS]`: run the `configure` script forwarding `ARGS` as command line -arguments; also run the `boot` script to create the `configure` script if necessary. -You do not have to use this functionality of the new build system; feel free to run -`boot` and `configure` scripts manually, as you do when using `make`. Note: on Windows -we automatically add flag `--enable-tarballs-autodownload` to `ARGS`, so you -don't have to do it manually. Beware, this uses network I/O which may sometimes be -undesirable. * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). * `--haddock`: build Haddock documentation. * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). +* `--setup[=CONFIGURE_ARGS]`: setup the build system by running the `configure` script +with `CONFIGURE_ARGS` arguments; also run the `boot` script to create the `configure` +script if necessary. On Windows, download the required tarballs by executing +`mk/get-win32-tarballs.sh` with appropriate parameters. You do not have to +use this functionality of the new build system; feel free to run `boot` and `configure` +scripts manually, as you do when using `make`. Beware: `--setup` uses network I/O +which may sometimes be undesirable. * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. From git at git.haskell.org Fri Oct 27 00:18:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement path lookup on Windows. (f5299c8) Message-ID: <20171027001834.CDC243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5299c86b5e89909488e1a5997a8c98c595f5d25/ghc >--------------------------------------------------------------- commit f5299c86b5e89909488e1a5997a8c98c595f5d25 Author: Andrey Mokhov Date: Tue Feb 9 15:05:09 2016 +0000 Implement path lookup on Windows. >--------------------------------------------------------------- f5299c86b5e89909488e1a5997a8c98c595f5d25 shaking-up-ghc.cabal | 2 +- src/Oracles.hs | 4 ++-- src/Oracles/WindowsPath.hs | 41 +++++++++++++++++++++++++++++++++++++ src/Oracles/WindowsRoot.hs | 51 ---------------------------------------------- src/Rules/Oracles.hs | 2 +- src/Test.hs | 2 +- 6 files changed, 46 insertions(+), 56 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 254617d..035bb9d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -34,7 +34,7 @@ executable ghc-shake , Oracles.PackageData , Oracles.PackageDb , Oracles.PackageDeps - , Oracles.WindowsRoot + , Oracles.WindowsPath , Package , Predicates , Rules diff --git a/src/Oracles.hs b/src/Oracles.hs index 564c7bb..eb37b47 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -6,7 +6,7 @@ module Oracles ( module Oracles.LookupInPath, module Oracles.PackageData, module Oracles.PackageDeps, - module Oracles.WindowsRoot + module Oracles.WindowsPath ) where import Oracles.Config @@ -16,4 +16,4 @@ import Oracles.Dependencies import Oracles.LookupInPath import Oracles.PackageData import Oracles.PackageDeps -import Oracles.WindowsRoot +import Oracles.WindowsPath diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs new file mode 100644 index 0000000..189c329 --- /dev/null +++ b/src/Oracles/WindowsPath.hs @@ -0,0 +1,41 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +module Oracles.WindowsPath ( + fixAbsolutePathOnWindows, topDirectory, windowsPathOracle + ) where + +import Data.Char (isSpace) +import Base +import Oracles.Config.Setting + +newtype WindowsPath = WindowsPath FilePath + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +topDirectory :: Action FilePath +topDirectory = do + ghcSourcePath <- setting GhcSourcePath + fixAbsolutePathOnWindows ghcSourcePath + +-- Fix an absolute path on Windows: +-- * "/c/" => "C:/" +-- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" +fixAbsolutePathOnWindows :: FilePath -> Action FilePath +fixAbsolutePathOnWindows path = do + windows <- windowsHost + if windows + then do + let (dir, file) = splitFileName path + winDir <- askOracle $ WindowsPath dir + return $ winDir -/- file + else + return path + +-- Detecting path mapping on Windows. This is slow and requires caching. +windowsPathOracle :: Rules () +windowsPathOracle = do + answer <- newCache $ \path -> do + Stdout out <- quietly $ cmd ["cygpath", "-m", path] + let windowsPath = dropWhileEnd isSpace out + putOracle $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath + return windowsPath + _ <- addOracle $ \(WindowsPath query) -> answer query + return () diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs deleted file mode 100644 index 413f289..0000000 --- a/src/Oracles/WindowsRoot.hs +++ /dev/null @@ -1,51 +0,0 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} -module Oracles.WindowsRoot ( - windowsRoot, fixAbsolutePathOnWindows, topDirectory, windowsRootOracle - ) where - -import Data.Char (isSpace) -import Base -import Oracles.Config.Setting - -newtype WindowsRoot = WindowsRoot () - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) - --- Looks up cygwin/msys root on Windows -windowsRoot :: Action String -windowsRoot = askOracle $ WindowsRoot () - -topDirectory :: Action FilePath -topDirectory = do - ghcSourcePath <- setting GhcSourcePath - fixAbsolutePathOnWindows ghcSourcePath - --- TODO: this is fragile, e.g. we currently only handle C: drive --- On Windows: --- * if the path starts with "/c/" change the prefix to "C:/" --- * otherwise, if the path starts with "/", prepend it with the correct path --- to the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe" -fixAbsolutePathOnWindows :: FilePath -> Action FilePath -fixAbsolutePathOnWindows path = do - windows <- windowsHost - -- Note, below is different from FilePath.isAbsolute: - if (windows && "/" `isPrefixOf` path) - then do - if ("/c/" `isPrefixOf` path) - then return $ "C:" ++ drop 2 path - else do - root <- windowsRoot - return . unifyPath $ root ++ drop 1 path - else - return path - --- Oracle for windowsRoot. This operation requires caching as looking up --- the root is slow (at least the current implementation). -windowsRootOracle :: Rules () -windowsRootOracle = do - root <- newCache $ \_ -> do - Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] - let root = dropWhileEnd isSpace out - putOracle $ "Detected root on Windows: " ++ root - return root - _ <- addOracle $ \WindowsRoot{} -> root () - return () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 55f7aee..1bc1606 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -17,4 +17,4 @@ oracleRules = do packageDataOracle -- see Oracles.PackageData packageDbOracle -- see Oracles.PackageData packageDepsOracle -- see Oracles.PackageDeps - windowsRootOracle -- see Oracles.WindowsRoot + windowsPathOracle -- see Oracles.WindowsRoot diff --git a/src/Test.hs b/src/Test.hs index a79c9fc..f8e93e7 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -6,7 +6,7 @@ import Expression import GHC (rts, libffi) import Oracles.Config.Flag import Oracles.Config.Setting -import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory +import Oracles.WindowsPath import Rules.Actions import Settings.Packages import Settings.User From git at git.haskell.org Fri Oct 27 00:18:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch from condLibrary to condLibraries in Cabal (54a8e15) Message-ID: <20171027001835.131B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/54a8e1579314b79890635323ff0e317834b720c9/ghc >--------------------------------------------------------------- commit 54a8e1579314b79890635323ff0e317834b720c9 Author: Andrey Mokhov Date: Thu Jul 14 00:26:35 2016 +0100 Switch from condLibrary to condLibraries in Cabal See #269. >--------------------------------------------------------------- 54a8e1579314b79890635323ff0e317834b720c9 src/Rules/Cabal.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index ed72f93..e2cdb0f 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -35,7 +35,8 @@ cabalRules = do else do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - let depsLib = collectDeps $ condLibrary pd + -- TODO: Support more than one Cabal library per package. + let depsLib = collectDeps . fmap snd . listToMaybe $ condLibraries pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes depNames = [ name | Dependency (DP.PackageName name) _ <- deps ] From git at git.haskell.org Fri Oct 27 00:18:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to generated Haskell files. (7274771) Message-ID: <20171027001836.470193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7274771087702c22c23b94c27560de1199cb005f/ghc >--------------------------------------------------------------- commit 7274771087702c22c23b94c27560de1199cb005f Author: Andrey Mokhov Date: Mon Dec 28 03:02:08 2015 +0000 Fix paths to generated Haskell files. >--------------------------------------------------------------- 7274771087702c22c23b94c27560de1199cb005f src/Oracles/ModuleFiles.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 832deef..33f6138 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -21,8 +21,9 @@ moduleFiles stage pkg = do haskellModuleFiles :: Stage -> Package -> Action ([FilePath], [String]) haskellModuleFiles stage pkg = do - let path = targetPath stage pkg - autogen = path -/- "build/autogen" + let path = targetPath stage pkg + autogen = path -/- "build/autogen" + dropPkgPath = drop $ length (pkgPath pkg) + 1 srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath pkg -/- dir | dir <- srcDirs ] @@ -31,9 +32,10 @@ haskellModuleFiles stage pkg = do let found = foundSrcDirs ++ foundAutogen missingMods = modules `minusOrd` (sort $ map fst found) - otherMods = map (replaceEq '/' '.' . dropExtension) otherFiles + otherFileToMod = replaceEq '/' '.' . dropExtension . dropPkgPath (haskellFiles, otherFiles) = partition ("//*hs" ?==) (map snd found) - return (haskellFiles, missingMods ++ otherMods) + + return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) moduleFilesOracle :: Rules () moduleFilesOracle = do From git at git.haskell.org Fri Oct 27 00:18:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix executable lookup. (68cf604) Message-ID: <20171027001838.A8D093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68cf6048ac5a08b158282d9284868002ecc28a8e/ghc >--------------------------------------------------------------- commit 68cf6048ac5a08b158282d9284868002ecc28a8e Author: Andrey Mokhov Date: Tue Feb 9 15:59:04 2016 +0000 Fix executable lookup. >--------------------------------------------------------------- 68cf6048ac5a08b158282d9284868002ecc28a8e src/Builder.hs | 10 +++++----- src/Oracles/LookupInPath.hs | 24 ++++++++++-------------- 2 files changed, 15 insertions(+), 19 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index d1a2cc3..1826875 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -112,11 +112,11 @@ builderPath builder = case builderProvenance builder of path <- askConfigWithDefault builderKey . putError $ "\nCannot find path to '" ++ builderKey ++ "' in configuration files. Have you forgot to run configure?" - windows <- windowsHost - case (path, windows) of - ("", _ ) -> return path - (p , True ) -> fixAbsolutePathOnWindows (p -<.> exe) - (p , False) -> lookupInPath p + if path == "" -- TODO: get rid of "" paths + then return "" + else do + path' <- lookupInPath path + fixAbsolutePathOnWindows $ path' -<.> exe getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index a9dc995..6bf2bba 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -1,29 +1,25 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where +import System.Directory + import Base newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) --- | Fetches the absolute FilePath to a given FilePath using the oracle. -commandPath :: FilePath -> Action FilePath -commandPath = askOracle . LookupInPath - --- | Lookup a @command@ in @PATH@ environment. +-- | Lookup an executable in @PATH at . lookupInPath :: FilePath -> Action FilePath -lookupInPath c - | c /= takeFileName c = return c - | otherwise = commandPath c +lookupInPath name + | name == takeFileName name = askOracle $ LookupInPath name + | otherwise = return name lookupInPathOracle :: Rules () lookupInPathOracle = do answer <- newCache $ \query -> do - envPaths <- wordsBy (== ':') <$> getEnvWithDefault "" "PATH" - let candidates = map (-/- query) envPaths - -- this will crash if we do not find any valid candidate. - fullCommand <- head <$> filterM doesFileExist candidates - putOracle $ "Found '" ++ query ++ "' at " ++ "'" ++ fullCommand ++ "'" - return fullCommand + maybePath <- liftIO $ findExecutable query + let path = fromMaybe query maybePath + putOracle $ "Lookup executable '" ++ query ++ "': " ++ path + return path _ <- addOracle $ \(LookupInPath query) -> answer query return () From git at git.haskell.org Fri Oct 27 00:18:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Support autogen paths of new Cabal (5fe4668) Message-ID: <20171027001839.075613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5fe46687bbbde9a82577e9b117378d3f9c027ee1/ghc >--------------------------------------------------------------- commit 5fe46687bbbde9a82577e9b117378d3f9c027ee1 Author: Andrey Mokhov Date: Thu Jul 14 01:28:02 2016 +0100 Support autogen paths of new Cabal See #269. >--------------------------------------------------------------- 5fe46687bbbde9a82577e9b117378d3f9c027ee1 src/Rules/Data.hs | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 2da6f86..034b2f4 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -38,12 +38,19 @@ buildPackageData context at Context {..} = do -- TODO: Get rid of this, see #113. dataFile %> \mk -> do + -- TODO: This is a hack. Add a proper support for autogen directory + -- structure of the new Cabal (probably only after #113). + let oldBuild + | isLibrary package = oldPath -/- "build" + | package == ghc = oldPath -/- "build/ghc" + | package == hpcBin = oldPath -/- "build/hpc" + | otherwise = oldPath -/- "build" -/- pkgNameString package copyFile inTreeMk mk - autogenFiles <- getDirectoryFiles (oldPath -/- "build") ["autogen/*"] + autogenFiles <- getDirectoryFiles oldBuild ["autogen/*"] createDirectory $ buildPath context -/- "autogen" forM_ autogenFiles $ \file' -> do let file = unifyPath file' - copyFile (oldPath -/- "build" -/- file) (buildPath context -/- file) + copyFile (oldBuild -/- file) (buildPath context -/- file) let haddockPrologue = "haddock-prologue.txt" copyFile (oldPath -/- haddockPrologue) (buildPath context -/- haddockPrologue) postProcessPackageData context mk From git at git.haskell.org Fri Oct 27 00:18:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use orderOnly dependencies for generated headers, see #48 (e7f3ae8) Message-ID: <20171027001839.EF6613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7f3ae8418552a145dc192ff5127d2e84bf1fa76/ghc >--------------------------------------------------------------- commit e7f3ae8418552a145dc192ff5127d2e84bf1fa76 Author: Andrey Mokhov Date: Mon Dec 28 03:03:26 2015 +0000 Use orderOnly dependencies for generated headers, see #48 >--------------------------------------------------------------- e7f3ae8418552a145dc192ff5127d2e84bf1fa76 src/Rules/Dependencies.hs | 27 +++------------------ src/Rules/Generate.hs | 62 +++++++++++++++++++++++++++++++++-------------- 2 files changed, 47 insertions(+), 42 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 197fa64..dc43071 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -1,7 +1,6 @@ module Rules.Dependencies (buildPackageDependencies) where import Expression -import GHC import Oracles import Rules.Actions import Rules.Generate @@ -14,37 +13,17 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = buildPath = path -/- "build" dropBuild = (pkgPath pkg ++) . drop (length buildPath) hDepFile = buildPath -/- ".hs-dependencies" - platformH = targetPath stage compiler -/- "ghc_boot_platform.h" in do (buildPath "*.c.deps") %> \out -> do let srcFile = dropBuild . dropExtension $ out - when (pkg == compiler) . need $ platformH : includesDependencies - when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] + orderOnly $ generatedDependencies stage pkg need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - when (pkg == compiler) . need $ platformH : includesDependencies - when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"] - -- TODO: very ugly and fragile; use gcc -MM instead? - let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-) - [ "primop-vector-uniques.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" - , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] - need $ srcs ++ extraDeps + orderOnly $ generatedDependencies stage pkg + need srcs if srcs == [] then writeFileChanged out "" else build $ fullTarget target (GhcM stage) srcs [out] diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index bc0089c..c7d13d6 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( generatePackageCode, generateRules, - derivedConstantsPath, includesDependencies + derivedConstantsPath, generatedDependencies ) where import Expression @@ -19,18 +19,47 @@ import Settings primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" +primopsTxt :: Stage -> FilePath +primopsTxt stage = targetPath stage compiler -/- "build/primops.txt" + +platformH :: Stage -> FilePath +platformH stage = targetPath stage compiler -/- "ghc_boot_platform.h" + derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" -- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? -includesDependencies :: [FilePath] -includesDependencies = - [ "includes/ghcautoconf.h" - , "includes/ghcplatform.h" - , derivedConstantsPath -/- "DerivedConstants.h" - , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" ] +generatedDependencies :: Stage -> Package -> [FilePath] +generatedDependencies stage pkg + | pkg == hp2ps = [ "includes/ghcautoconf.h" + , "includes/ghcplatform.h" ] + | pkg == compiler = let buildPath = targetPath stage compiler -/- "build" + in + [ "includes/ghcautoconf.h" + , "includes/ghcplatform.h" + , derivedConstantsPath -/- "DerivedConstants.h" + , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" + , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" + , platformH stage ] + ++ + fmap (buildPath -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] + | otherwise = [] -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] @@ -52,10 +81,7 @@ generate file target expr = do generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = - let path = targetPath stage pkg - buildPath = path -/- "build" - primopsTxt = targetPath stage compiler -/- "build/primops.txt" - platformH = targetPath stage compiler -/- "ghc_boot_platform.h" + let buildPath = targetPath stage pkg -/- "build" generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) file <~ gen = generate file target gen in do @@ -74,8 +100,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = copyFileChanged srcBoot $ file -<.> "hs-boot" -- TODO: needing platformH is ugly and fragile - when (pkg == compiler) $ primopsTxt %> \file -> do - need [platformH, primopsSource] + when (pkg == compiler) $ primopsTxt stage %> \file -> do + need [platformH stage, primopsSource] build $ fullTarget target HsCpp [primopsSource] [file] -- TODO: why different folders for generated files? @@ -83,8 +109,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = [ "GHC/PrimopWrappers.hs" , "autogen/GHC/Prim.hs" , "*.hs-incl" ] |%> \file -> do - need [primopsTxt] - build $ fullTarget target GenPrimopCode [primopsTxt] [file] + need [primopsTxt stage] + build $ fullTarget target GenPrimopCode [primopsTxt stage] [file] priority 2.0 $ do when (pkg == compiler && stage == Stage1) $ @@ -94,7 +120,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs - when (pkg == compiler) $ platformH %> \file -> do + when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do From git at git.haskell.org Fri Oct 27 00:18:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use qualified imports. (bd405c1) Message-ID: <20171027001842.CD7CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd405c1006be30c99cb718a30dd779c1462baf61/ghc >--------------------------------------------------------------- commit bd405c1006be30c99cb718a30dd779c1462baf61 Author: Andrey Mokhov Date: Wed Feb 10 01:03:56 2016 +0000 Use qualified imports. >--------------------------------------------------------------- bd405c1006be30c99cb718a30dd779c1462baf61 src/Rules/Oracles.hs | 32 ++++++++++++++++++-------------- 1 file changed, 18 insertions(+), 14 deletions(-) diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 1bc1606..108c5ce 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -1,20 +1,24 @@ module Rules.Oracles (oracleRules) where import Base -import Oracles -import Oracles.ArgsHash -import Oracles.PackageDb -import Oracles.ModuleFiles +import qualified Oracles.Config +import qualified Oracles.Dependencies +import qualified Oracles.LookupInPath +import qualified Oracles.PackageData +import qualified Oracles.PackageDeps +import qualified Oracles.WindowsPath +import qualified Oracles.ArgsHash +import qualified Oracles.ModuleFiles +import qualified Oracles.PackageDb --- TODO: replace comments with qualified imports oracleRules :: Rules () oracleRules = do - argsHashOracle -- see Oracles.ArgsHash - configOracle -- see Oracles.Config - dependenciesOracle -- see Oracles.Dependencies - lookupInPathOracle -- see Oracles.LookupInPath - moduleFilesOracle -- see Oracles.ModuleFiles - packageDataOracle -- see Oracles.PackageData - packageDbOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - windowsPathOracle -- see Oracles.WindowsRoot + Oracles.ArgsHash.argsHashOracle + Oracles.Config.configOracle + Oracles.Dependencies.dependenciesOracle + Oracles.LookupInPath.lookupInPathOracle + Oracles.ModuleFiles.moduleFilesOracle + Oracles.PackageData.packageDataOracle + Oracles.PackageDb.packageDbOracle + Oracles.PackageDeps.packageDepsOracle + Oracles.WindowsPath.windowsPathOracle From git at git.haskell.org Fri Oct 27 00:18:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Point to in-tree Cabal sources (6369ef0) Message-ID: <20171027001843.188C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6369ef04c8ba978c7670c4b79fe85c16e7a11139/ghc >--------------------------------------------------------------- commit 6369ef04c8ba978c7670c4b79fe85c16e7a11139 Author: Andrey Mokhov Date: Thu Jul 14 02:04:08 2016 +0100 Point to in-tree Cabal sources >--------------------------------------------------------------- 6369ef04c8ba978c7670c4b79fe85c16e7a11139 .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 85dfc94..9c0fe7a 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,2 @@ -:set -Wall -fno-warn-name-shadowing -isrc -XRecordWildCards +:set -Wall -fno-warn-name-shadowing -isrc -i../libraries/Cabal/Cabal -XRecordWildCards :load Main From git at git.haskell.org Fri Oct 27 00:18:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a TODO note for unlit and driver/ghc-split utils. (58d7fcc) Message-ID: <20171027001843.66DC03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/58d7fccf59da038f038446c41901fa086ae4a40c/ghc >--------------------------------------------------------------- commit 58d7fccf59da038f038446c41901fa086ae4a40c Author: Andrey Mokhov Date: Mon Dec 28 12:44:13 2015 +0000 Add a TODO note for unlit and driver/ghc-split utils. >--------------------------------------------------------------- 58d7fccf59da038f038446c41901fa086ae4a40c src/GHC.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 281f15e..859bec4 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -85,10 +85,11 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" +-- TODO: The following utils are not implemented yet: unlit, driver/ghc-split -- TODO: The following utils are not included into the build system because --- they seem to be unused or unrelated to the build process: chechUniques, +-- they seem to be unused or unrelated to the build process: checkUniques, -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, --- lndir, mkdirhier, testremove, touchy, unlit, vagrant +-- lndir, mkdirhier, testremove, touchy, vagrant -- GHC build results will be placed into target directories with the following -- typical structure: From git at git.haskell.org Fri Oct 27 00:18:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop top-level Oracles.hs (3178d82) Message-ID: <20171027001846.C082B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3178d829038e5216c474f5ce6f8f7bd7b09b02f9/ghc >--------------------------------------------------------------- commit 3178d829038e5216c474f5ce6f8f7bd7b09b02f9 Author: Andrey Mokhov Date: Wed Feb 10 01:20:56 2016 +0000 Drop top-level Oracles.hs >--------------------------------------------------------------- 3178d829038e5216c474f5ce6f8f7bd7b09b02f9 shaking-up-ghc.cabal | 1 - src/Builder.hs | 4 +++- src/Oracles.hs | 19 ------------------- src/Rules/Actions.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 3 ++- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generators/ConfigHs.hs | 3 ++- src/Rules/Generators/GhcAutoconfH.hs | 3 ++- src/Rules/Generators/GhcBootPlatformH.hs | 2 +- src/Rules/Generators/GhcPlatformH.hs | 3 ++- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Generators/GhcVersionH.hs | 2 +- src/Rules/Generators/VersionHs.hs | 2 +- src/Rules/Libffi.hs | 4 +++- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 3 ++- src/Settings.hs | 3 ++- src/Settings/Builders/Ar.hs | 3 ++- src/Settings/Builders/Gcc.hs | 2 +- src/Settings/Builders/Ghc.hs | 3 ++- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 4 +++- src/Settings/Builders/Ld.hs | 2 +- src/Way.hs | 2 +- 27 files changed, 39 insertions(+), 45 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 3178d829038e5216c474f5ce6f8f7bd7b09b02f9 From git at git.haskell.org Fri Oct 27 00:18:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop trackBuildSystem setting (4ad8082) Message-ID: <20171027001846.DCDA23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ad80828794f13c3e9139a68f06f3f2b6db1428f/ghc >--------------------------------------------------------------- commit 4ad80828794f13c3e9139a68f06f3f2b6db1428f Author: Andrey Mokhov Date: Thu Jul 14 02:04:32 2016 +0100 Drop trackBuildSystem setting >--------------------------------------------------------------- 4ad80828794f13c3e9139a68f06f3f2b6db1428f src/Oracles/ArgsHash.hs | 3 +-- src/Rules/Generators/Common.hs | 6 ++---- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/UserSettings.hs | 13 ++----------- 5 files changed, 7 insertions(+), 19 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index d1ebc68..660edd9 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -5,7 +5,6 @@ import Base import Expression import Settings import Target -import UserSettings newtype ArgsHashKey = ArgsHashKey Target deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -21,7 +20,7 @@ newtype ArgsHashKey = ArgsHashKey Target -- argument list constructors are assumed not to examine target sources, but -- only append them to argument lists where appropriate. checkArgsHash :: Target -> Action () -checkArgsHash target = when trackBuildSystem $ do +checkArgsHash target = do let hashed = [ show . hash $ inputs target ] _ <- askOracle . ArgsHashKey $ target { inputs = hashed } :: Action Int return () diff --git a/src/Rules/Generators/Common.hs b/src/Rules/Generators/Common.hs index e97d536..b01ad2f 100644 --- a/src/Rules/Generators/Common.hs +++ b/src/Rules/Generators/Common.hs @@ -2,12 +2,10 @@ module Rules.Generators.Common (trackSource, yesNo, cppify) where import Base import Expression -import UserSettings --- | Track a given source file when constructing an expression if the user --- enabled 'trackBuildSystem' in @hadrian/src/UserSettings.hs at . +-- | Track a given source file when constructing an expression. trackSource :: FilePath -> Expr () -trackSource file = lift $ when trackBuildSystem $ need [ sourcePath -/- file ] +trackSource file = lift $ need [ sourcePath -/- file ] -- | Turn a 'Bool' computed by an 'Action' into a 'String' expression returning -- "YES" (when the Boolean is 'True') or "NO" (when the Boolean is 'False'). diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index efe9144..0cf5b91 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -34,7 +34,7 @@ gmpRules :: Rules () gmpRules = do -- TODO: split into multiple rules gmpLibraryH %> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] + need [sourcePath -/- "Rules/Gmp.hs"] removeDirectory gmpBuildPath -- We don't use system GMP on Windows. TODO: fix? diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 3ee3307..99b97df 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -58,7 +58,7 @@ configureEnvironment = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] + need [sourcePath -/- "Rules/Libffi.hs"] useSystemFfi <- flag UseSystemFfi if useSystemFfi then do diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 1f73efa..a0a5d49 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,9 +3,8 @@ -- If you don't copy the file your changes will be tracked by git and you can -- accidentally commit them. module UserSettings ( - buildRootPath, userFlavours, userKnownPackages, integerLibrary, - trackBuildSystem, validating, turnWarningsIntoErrors, verboseCommands, - putBuild, putSuccess + buildRootPath, userFlavours, userKnownPackages, integerLibrary, validating, + turnWarningsIntoErrors, verboseCommands, putBuild, putSuccess ) where import System.Console.ANSI @@ -42,14 +41,6 @@ integerLibrary = integerGmp -- * @Predicate@: a flag whose value can depend on the build environment and -- on the current build target. --- TODO: Drop 'trackBuildSystem' as it brings negligible gains. --- | Set this to True if you are making any changes in the build system and want --- appropriate rebuilds to be initiated. Switching this to False speeds things --- up a little (particularly zero builds). --- WARNING: a complete rebuild is required when changing this setting. -trackBuildSystem :: Bool -trackBuildSystem = True - -- TODO: This should be set automatically when validating. validating :: Bool validating = False From git at git.haskell.org Fri Oct 27 00:18:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport Data.Char (a9aa2ac) Message-ID: <20171027001847.4B17C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9aa2ac5825514967ea60f28473ec1a6d435c1a4/ghc >--------------------------------------------------------------- commit a9aa2ac5825514967ea60f28473ec1a6d435c1a4 Author: Ben Gamari Date: Thu Dec 24 14:02:38 2015 +0100 Base: Don't reexport Data.Char It's really not used often enough to warrant special treatment >--------------------------------------------------------------- a9aa2ac5825514967ea60f28473ec1a6d435c1a4 src/Base.hs | 2 -- src/Oracles/WindowsRoot.hs | 1 + src/Rules/Library.hs | 2 ++ src/Rules/Program.hs | 2 ++ 4 files changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 47a4285..3c62ed5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -3,7 +3,6 @@ module Base ( module Control.Applicative, module Control.Monad.Extra, module Control.Monad.Reader, - module Data.Char, module Data.Function, module Data.List, module Data.Maybe, @@ -34,7 +33,6 @@ module Base ( import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader -import Data.Char import Data.Function import Data.List import Data.Maybe diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 2ec13c7..89dd011 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -1,6 +1,7 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.WindowsRoot (windowsRoot, windowsRootOracle) where +import Data.Char (isSpace) import Base newtype WindowsRoot = WindowsRoot () diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 1df83a8..db1624b 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,5 +1,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where +import Data.Char + import Expression hiding (splitPath) import GHC import Oracles diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index a24fcdc..962ce1d 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -1,5 +1,7 @@ module Rules.Program (buildProgram) where +import Data.Char + import Expression hiding (splitPath) import GHC hiding (ghci) import Oracles From git at git.haskell.org Fri Oct 27 00:18:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Report an error if an executable is not found, unify paths. (05e7242) Message-ID: <20171027001850.433C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/05e7242655e0b8d5657c487e2ed2f392dd520429/ghc >--------------------------------------------------------------- commit 05e7242655e0b8d5657c487e2ed2f392dd520429 Author: Andrey Mokhov Date: Wed Feb 10 11:27:03 2016 +0000 Report an error if an executable is not found, unify paths. >--------------------------------------------------------------- 05e7242655e0b8d5657c487e2ed2f392dd520429 src/Oracles/LookupInPath.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 6bf2bba..2f6e713 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -18,8 +18,10 @@ lookupInPathOracle :: Rules () lookupInPathOracle = do answer <- newCache $ \query -> do maybePath <- liftIO $ findExecutable query - let path = fromMaybe query maybePath - putOracle $ "Lookup executable '" ++ query ++ "': " ++ path + path <- case maybePath of + Just value -> return $ unifyPath value + Nothing -> putError $ "Cannot find executable '" ++ query ++ "'." + putOracle $ "Executable found: " ++ query ++ " => " ++ path return path _ <- addOracle $ \(LookupInPath query) -> answer query return () From git at git.haskell.org Fri Oct 27 00:18:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix autogen path for iserv (38d1f55) Message-ID: <20171027001850.D6B713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/38d1f551cbd1dd94d33da9290e98bacca394f285/ghc >--------------------------------------------------------------- commit 38d1f551cbd1dd94d33da9290e98bacca394f285 Author: Andrey Mokhov Date: Thu Jul 14 02:07:25 2016 +0100 Fix autogen path for iserv See #269. >--------------------------------------------------------------- 38d1f551cbd1dd94d33da9290e98bacca394f285 src/Rules/Data.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 034b2f4..959a7ec 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -41,10 +41,11 @@ buildPackageData context at Context {..} = do -- TODO: This is a hack. Add a proper support for autogen directory -- structure of the new Cabal (probably only after #113). let oldBuild - | isLibrary package = oldPath -/- "build" - | package == ghc = oldPath -/- "build/ghc" - | package == hpcBin = oldPath -/- "build/hpc" - | otherwise = oldPath -/- "build" -/- pkgNameString package + | isLibrary package = oldPath -/- "build" + | package == ghc = oldPath -/- "build/ghc" + | package == hpcBin = oldPath -/- "build/hpc" + | package == iservBin = oldPath -/- "build/iserv" + | otherwise = oldPath -/- "build" -/- pkgNameString package copyFile inTreeMk mk autogenFiles <- getDirectoryFiles oldBuild ["autogen/*"] createDirectory $ buildPath context -/- "autogen" From git at git.haskell.org Fri Oct 27 00:18:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Hide `parallel` (ef0386c) Message-ID: <20171027001851.7240A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef0386c76790b582cb180d5db224d0b4681ae4ba/ghc >--------------------------------------------------------------- commit ef0386c76790b582cb180d5db224d0b4681ae4ba Author: Ben Gamari Date: Thu Dec 24 14:17:54 2015 +0100 Base: Hide `parallel` Otherwise it is shadowed by `GHC.parallel` >--------------------------------------------------------------- ef0386c76790b582cb180d5db224d0b4681ae4ba src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 55c1a9e..47a4285 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -39,7 +39,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>)) +import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes import Development.Shake.Config import Development.Shake.FilePath From git at git.haskell.org Fri Oct 27 00:18:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify paths. (56d3256) Message-ID: <20171027001854.259D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56d32568e5f290d9c93f11568b63e206caa0b9e1/ghc >--------------------------------------------------------------- commit 56d32568e5f290d9c93f11568b63e206caa0b9e1 Author: Andrey Mokhov Date: Wed Feb 10 11:27:21 2016 +0000 Unify paths. >--------------------------------------------------------------- 56d32568e5f290d9c93f11568b63e206caa0b9e1 src/Oracles/WindowsPath.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index 189c329..3cbf1f1 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -34,7 +34,7 @@ windowsPathOracle :: Rules () windowsPathOracle = do answer <- newCache $ \path -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] - let windowsPath = dropWhileEnd isSpace out + let windowsPath = unifyPath $ dropWhileEnd isSpace out putOracle $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath _ <- addOracle $ \(WindowsPath query) -> answer query From git at git.haskell.org Fri Oct 27 00:18:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport Development.Shake.Config (1405953) Message-ID: <20171027001855.870183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14059539b1fa2b5e79e38c34266636c60dfb40f4/ghc >--------------------------------------------------------------- commit 14059539b1fa2b5e79e38c34266636c60dfb40f4 Author: Ben Gamari Date: Thu Dec 24 14:37:49 2015 +0100 Base: Don't reexport Development.Shake.Config >--------------------------------------------------------------- 14059539b1fa2b5e79e38c34266636c60dfb40f4 src/Base.hs | 2 -- src/Oracles/Config.hs | 1 + src/Oracles/PackageData.hs | 1 + 3 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fb0eed7..1012d4e 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -11,7 +11,6 @@ module Base ( -- * Shake module Development.Shake, module Development.Shake.Classes, - module Development.Shake.Config, module Development.Shake.FilePath, module Development.Shake.Util, @@ -38,7 +37,6 @@ import Data.Maybe import Data.Monoid import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes -import Development.Shake.Config import Development.Shake.FilePath import Development.Shake.Util import System.Console.ANSI diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index e8333b6..cde2383 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -3,6 +3,7 @@ module Oracles.Config (askConfig, askConfigWithDefault, configOracle) where import Base import qualified Data.HashMap.Strict as Map +import Development.Shake.Config newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 4e3d306..d176839 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -4,6 +4,7 @@ module Oracles.PackageData ( pkgData, pkgDataList, packageDataOracle ) where +import Development.Shake.Config import Base import qualified Data.HashMap.Strict as Map From git at git.haskell.org Fri Oct 27 00:18:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try full build on AppVeyor (b05a328) Message-ID: <20171027001855.46C563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b05a3287007421b0390a1f19f44874899d0c33f9/ghc >--------------------------------------------------------------- commit b05a3287007421b0390a1f19f44874899d0c33f9 Author: Andrey Mokhov Date: Thu Jul 14 22:32:54 2016 +0100 Try full build on AppVeyor >--------------------------------------------------------------- b05a3287007421b0390a1f19f44874899d0c33f9 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index e4d7d52..a3de01a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest From git at git.haskell.org Fri Oct 27 00:18:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test Stage2 GHC after the build (29c2402) Message-ID: <20171027001859.2D2FC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/29c2402924e4d7af440771b6eff4a019c37b24c3/ghc >--------------------------------------------------------------- commit 29c2402924e4d7af440771b6eff4a019c37b24c3 Author: Andrey Mokhov Date: Thu Jul 14 23:21:43 2016 +0100 Test Stage2 GHC after the build >--------------------------------------------------------------- 29c2402924e4d7af440771b6eff4a019c37b24c3 appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/appveyor.yml b/appveyor.yml index a3de01a..4f55e5a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -38,3 +38,4 @@ build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + - stack exec -- C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 From git at git.haskell.org Fri Oct 27 00:19:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop support for old configure.ac. (0b0996b) Message-ID: <20171027001901.110AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b0996b12437a70eeeac0739b493ed505b2c8b89/ghc >--------------------------------------------------------------- commit 0b0996b12437a70eeeac0739b493ed505b2c8b89 Author: Andrey Mokhov Date: Wed Feb 10 12:45:40 2016 +0000 Drop support for old configure.ac. >--------------------------------------------------------------- 0b0996b12437a70eeeac0739b493ed505b2c8b89 src/Rules/Actions.hs | 16 +++------------- 1 file changed, 3 insertions(+), 13 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d81b838..f8f4925 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -6,7 +6,6 @@ module Rules.Actions ( ) where import qualified System.Directory as IO -import System.Console.ANSI import Base import CmdLineFlag @@ -127,20 +126,11 @@ runMakeWithVerbosity :: Bool -> FilePath -> [String] -> Action () runMakeWithVerbosity verbose dir args = do need [dir -/- "Makefile"] path <- builderPath Make - - -- FIXME: temporary safety net for those who are not on GHC HEAD, see #167 - -- TODO: add need [path] once lookupInPath is enabled on Windows - fixPath <- if path == "@MakeCmd@" <.> exe - then do - putColoured Red $ "You are behind GHC HEAD, make autodetection is disabled." - return "make" - else return path - let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run " ++ fixPath ++ note ++ " in " ++ dir ++ "..." + putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." if verbose - then cmd Shell fixPath ["-C", dir] args - else quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args + then cmd Shell path ["-C", dir] args + else quietly $ cmd Shell (EchoStdout False) path ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do From git at git.haskell.org Fri Oct 27 00:19:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to run Stage2 GHC without Stack (868ffae) Message-ID: <20171027001902.D66F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/868ffae9e2af3e603dc6675b6e6c5a58e4396430/ghc >--------------------------------------------------------------- commit 868ffae9e2af3e603dc6675b6e6c5a58e4396430 Author: Andrey Mokhov Date: Fri Jul 15 00:03:27 2016 +0100 Attempt to run Stage2 GHC without Stack >--------------------------------------------------------------- 868ffae9e2af3e603dc6675b6e6c5a58e4396430 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4f55e5a..4392abe 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -38,4 +38,4 @@ build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest - - stack exec -- C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 + - C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 From git at git.haskell.org Fri Oct 27 00:19:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't fail if configuration file is out-of-date. (d17c1f5) Message-ID: <20171027001904.81BD73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d17c1f538b14b86405bb0be4f3fc4100a2ec8bec/ghc >--------------------------------------------------------------- commit d17c1f538b14b86405bb0be4f3fc4100a2ec8bec Author: Andrey Mokhov Date: Wed Feb 10 13:39:50 2016 +0000 Don't fail if configuration file is out-of-date. >--------------------------------------------------------------- d17c1f538b14b86405bb0be4f3fc4100a2ec8bec src/Rules/Setup.hs | 13 ++++--------- 1 file changed, 4 insertions(+), 9 deletions(-) diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index a17fb59..e0cd729 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -21,13 +21,8 @@ setupRules = do , "download" , System.Info.arch ] runConfigure "." [] [configureArgs] - SkipSetup -> do - cfgExists <- doesFileExist cfg - if cfgExists - then putError $ "Configuration file " ++ cfg ++ " is out-of-date." - ++ "\nRerun the configure script either manually or via the " - ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." - else putError $ "Configuration file " ++ cfg ++ " is missing." + SkipSetup -> unlessM (doesFileExist cfg) $ + putError $ "Configuration file " ++ cfg ++ " is missing." ++ "\nRun the configure script either manually or via the " ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." @@ -37,7 +32,7 @@ setupRules = do RunSetup _ -> do putBuild "| Running boot..." quietly $ cmd (EchoStdout False) "perl boot" - SkipSetup -> do - putError $ "The configure script is out-of-date." + SkipSetup -> unlessM (doesFileExist "configure") $ + putError $ "The configure script is missing." ++ "\nRun the boot script either manually or via the " ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." From git at git.haskell.org Fri Oct 27 00:19:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Reexport `MonadTrans` instead of `Reader` (6472042) Message-ID: <20171027001903.2FDB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6472042ba8fddbc721b1bc6ae322a58212b5fe32/ghc >--------------------------------------------------------------- commit 6472042ba8fddbc721b1bc6ae322a58212b5fe32 Author: Ben Gamari Date: Thu Dec 24 14:35:31 2015 +0100 Base: Reexport `MonadTrans` instead of `Reader` The former is much more common than the latter. >--------------------------------------------------------------- 6472042ba8fddbc721b1bc6ae322a58212b5fe32 src/Base.hs | 2 +- src/Builder.hs | 2 ++ src/Expression.hs | 2 ++ src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 2 ++ src/Target.hs | 2 ++ 6 files changed, 11 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index aa9861b..fb0eed7 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -2,11 +2,11 @@ module Base ( -- * General utilities module Control.Applicative, module Control.Monad.Extra, - module Control.Monad.Reader, module Data.Function, module Data.List, module Data.Maybe, module Data.Monoid, + MonadTrans(lift), -- * Shake module Development.Shake, diff --git a/src/Builder.hs b/src/Builder.hs index b6fd228..78f8376 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -3,6 +3,8 @@ module Builder ( Builder (..), builderPath, getBuilderPath, specified, needBuilder ) where +import Control.Monad.Trans.Reader + import Base import GHC.Generics (Generic) import Oracles diff --git a/src/Expression.hs b/src/Expression.hs index 0d47314..a83ea15 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -24,6 +24,8 @@ module Expression ( module Way ) where +import Control.Monad.Trans.Reader + import Base import Package import Builder diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 47ea75d..d40b762 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -4,6 +4,8 @@ module Oracles.Config.Flag ( ghcWithNativeCodeGen, supportsSplitObjects ) where +import Control.Monad.Trans.Reader + import Base import Oracles.Config import Oracles.Config.Setting diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 81e2924..b0c6da3 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -6,6 +6,8 @@ module Oracles.Config.Setting ( ghcCanonVersion, cmdLineLengthLimit ) where +import Control.Monad.Trans.Reader + import Base import Oracles.Config import Stage diff --git a/src/Target.hs b/src/Target.hs index 2060d04..25967b4 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -3,6 +3,8 @@ module Target ( Target (..), PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay ) where +import Control.Monad.Trans.Reader + import Base import Builder import GHC.Generics (Generic) From git at git.haskell.org Fri Oct 27 00:18:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop alwaysRerun from setup rules. (b3e25ee) Message-ID: <20171027001857.A2DBC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3e25ee579ad44a35b4cbf243b05728c4f63c5d1/ghc >--------------------------------------------------------------- commit b3e25ee579ad44a35b4cbf243b05728c4f63c5d1 Author: Andrey Mokhov Date: Wed Feb 10 12:42:54 2016 +0000 Drop alwaysRerun from setup rules. >--------------------------------------------------------------- b3e25ee579ad44a35b4cbf243b05728c4f63c5d1 src/Rules/Setup.hs | 27 ++++++++++++++++++--------- 1 file changed, 18 insertions(+), 9 deletions(-) diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index c99c8be..a17fb59 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -9,13 +9,10 @@ import Rules.Generators.GhcAutoconfH setupRules :: Rules () setupRules = do - -- We always rerun the configure script in this mode, because the flags - -- passed to it can affect the contents of system.config file. [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do - alwaysRerun + need [ settings <.> "in", cfgH <.> "in", "configure" ] case cmdSetup of RunSetup configureArgs -> do - need [ settings <.> "in", cfgH <.> "in" ] -- We cannot use windowsHost here due to a cyclic dependency when (System.Info.os == "mingw32") $ do putBuild "| Checking for Windows tarballs..." @@ -24,11 +21,23 @@ setupRules = do , "download" , System.Info.arch ] runConfigure "." [] [configureArgs] - SkipSetup -> unlessM (doesFileExist cfg) $ - putError $ "Configuration file " ++ cfg ++ " is missing.\n" - ++ "Run the configure script either manually or via the " + SkipSetup -> do + cfgExists <- doesFileExist cfg + if cfgExists + then putError $ "Configuration file " ++ cfg ++ " is out-of-date." + ++ "\nRerun the configure script either manually or via the " + ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." + else putError $ "Configuration file " ++ cfg ++ " is missing." + ++ "\nRun the configure script either manually or via the " ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." ["configure", configH <.> "in"] &%> \_ -> do - putBuild "| Running boot..." - quietly $ cmd (EchoStdout False) "perl boot" + need ["configure.ac"] + case cmdSetup of + RunSetup _ -> do + putBuild "| Running boot..." + quietly $ cmd (EchoStdout False) "perl boot" + SkipSetup -> do + putError $ "The configure script is out-of-date." + ++ "\nRun the boot script either manually or via the " + ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." From git at git.haskell.org Fri Oct 27 00:18:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:18:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport Development.Shake.Util (062e6b2) Message-ID: <20171027001859.6E76F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/062e6b2ad5dc4be679f14f9b5a8ecbd99febc54b/ghc >--------------------------------------------------------------- commit 062e6b2ad5dc4be679f14f9b5a8ecbd99febc54b Author: Ben Gamari Date: Thu Dec 24 14:38:53 2015 +0100 Base: Don't reexport Development.Shake.Util >--------------------------------------------------------------- 062e6b2ad5dc4be679f14f9b5a8ecbd99febc54b src/Base.hs | 2 -- src/Rules/Dependencies.hs | 1 + 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 1012d4e..25a69df 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -12,7 +12,6 @@ module Base ( module Development.Shake, module Development.Shake.Classes, module Development.Shake.FilePath, - module Development.Shake.Util, -- * Paths shakeFilesPath, configPath, sourcePath, programInplacePath, @@ -38,7 +37,6 @@ import Data.Monoid import Development.Shake hiding (unit, (*>), parallel) import Development.Shake.Classes import Development.Shake.FilePath -import Development.Shake.Util import System.Console.ANSI import qualified System.Directory as IO import System.IO diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index a2f5aa2..88e97b2 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -7,6 +7,7 @@ import Rules.Actions import Rules.Generate import Rules.Resources import Settings +import Development.Shake.Util (parseMakefile) buildPackageDependencies :: Resources -> PartialTarget -> Rules () buildPackageDependencies _ target @ (PartialTarget stage pkg) = From git at git.haskell.org Fri Oct 27 00:19:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try default build flavour on Travis Linux (abfd4e7) Message-ID: <20171027001906.5A0F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/abfd4e73326d967c15ac2254f303cf622ae2af40/ghc >--------------------------------------------------------------- commit abfd4e73326d967c15ac2254f303cf622ae2af40 Author: Andrey Mokhov Date: Fri Jul 15 17:24:29 2016 +0100 Try default build flavour on Travis Linux >--------------------------------------------------------------- abfd4e73326d967c15ac2254f303cf622ae2af40 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index b066e89..2b2379f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quick TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=default TARGET= addons: apt: packages: From git at git.haskell.org Fri Oct 27 00:19:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Base: Don't reexport `System.Console.ANSI` (f05d78d) Message-ID: <20171027001906.A934F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f05d78d92e3fde319e2963806406074868a0a4f0/ghc >--------------------------------------------------------------- commit f05d78d92e3fde319e2963806406074868a0a4f0 Author: Ben Gamari Date: Thu Dec 24 14:32:38 2015 +0100 Base: Don't reexport `System.Console.ANSI` This wasn't even used it seems >--------------------------------------------------------------- f05d78d92e3fde319e2963806406074868a0a4f0 src/Base.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 3c62ed5..aa9861b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,7 +22,6 @@ module Base ( -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, - module System.Console.ANSI, -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, quote, chunksOfSize, From git at git.haskell.org Fri Oct 27 00:19:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting, drop old comments. (0123303) Message-ID: <20171027001907.F01343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/01233034d1790dd831b59e0233e48cebaa8a4579/ghc >--------------------------------------------------------------- commit 01233034d1790dd831b59e0233e48cebaa8a4579 Author: Andrey Mokhov Date: Wed Feb 10 16:55:50 2016 +0000 Fix formatting, drop old comments. >--------------------------------------------------------------- 01233034d1790dd831b59e0233e48cebaa8a4579 src/Rules/Libffi.hs | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 99922d0..f1837c4 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -72,15 +72,14 @@ libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - ffiHeaderDir <- setting FfiIncludeDir useSystemFfi <- flag UseSystemFfi if useSystemFfi then do - putBuild "| System supplied FFI library will be used" - forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = ffiHeaderDir -/- file - copyFile src (rtsBuildPath -/- file) - putSuccess $ "| Successfully copied system supplied FFI library header files" + ffiIncludeDir <- setting FfiIncludeDir + putBuild "| System supplied FFI library will be used" + forM_ ["ffi.h", "ffitarget.h"] $ \file -> + copyFile (ffiIncludeDir -/- file) (rtsBuildPath -/- file) + putSuccess $ "| Successfully copied system FFI library header files" else do removeDirectory libffiBuild createDirectory $ buildRootPath -/- stageString Stage0 @@ -94,15 +93,16 @@ libffiRules = do let libname = dropExtension . dropExtension . takeFileName $ head tarballs removeDirectory (buildRootPath -/- libname) + -- TODO: Simplify. actionFinally (do - build $ fullTarget libffiTarget Tar tarballs [buildRootPath] - moveDirectory (buildRootPath -/- libname) libffiBuild) $ - removeFiles buildRootPath [libname "*"] + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile forM_ ["config.guess", "config.sub"] $ \file -> - copyFile file (libffiBuild -/- file) + copyFile file (libffiBuild -/- file) envs <- configureEnvironment args <- configureArguments @@ -111,17 +111,11 @@ libffiRules = do runMake libffiBuild ["MAKEFLAGS="] runMake libffiBuild ["MAKEFLAGS=", "install"] + let ffiHDir = libffiBuild -/- "inst/lib" -/- libname -/- "include" forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file - copyFile src (rtsBuildPath -/- file) + copyFile (ffiHDir -/- file) (rtsBuildPath -/- file) libffiName <- rtsLibffiLibraryName copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") putSuccess $ "| Successfully built custom library 'libffi'" - --- chmod +x libffi/ln --- # wc on OS X has spaces in its output, which libffi's Makefile --- # doesn't expect, so we tweak it to sed them out --- mv libffi/build/Makefile libffi/build/Makefile.orig --- sed "s#wc -w#wc -w | sed 's/ //g'#" < libffi/build/Makefile.orig > libffi/build/Makefile From git at git.haskell.org Fri Oct 27 00:19:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Eliminate re-exports from `Predicates` (74fb3f9) Message-ID: <20171027001910.96B393A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/74fb3f9e869300335ba2b8ed831b792a64696877/ghc >--------------------------------------------------------------- commit 74fb3f9e869300335ba2b8ed831b792a64696877 Author: Ben Gamari Date: Thu Dec 24 14:31:07 2015 +0100 Eliminate re-exports from `Predicates` >--------------------------------------------------------------- 74fb3f9e869300335ba2b8ed831b792a64696877 src/Predicates.hs | 5 +---- src/Rules/Library.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 1 + src/Settings/Packages.hs | 2 ++ src/Settings/User.hs | 2 +- src/Settings/Ways.hs | 1 + 6 files changed, 8 insertions(+), 7 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index abaa4be..28dd51a 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,7 +1,5 @@ +-- | Convenient predicates module Predicates ( - module GHC, - module Oracles.Config.Flag, - module Oracles.Config.Setting, stage, package, builder, stagedBuilder, file, way, stage0, stage1, stage2, notStage0, notPackage, registerPackage, splitObjects ) where @@ -10,7 +8,6 @@ import Base import Expression import GHC import Oracles.Config.Flag -import Oracles.Config.Setting -- Basic predicates stage :: Stage -> Predicate diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index eeef3ab..76fe872 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -2,8 +2,8 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Data.Char -import Base -import Expression hiding (splitPath) +import Base hiding (splitPath) +import Expression import GHC import Oracles import Predicates (splitObjects) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index ead473e..c8226fc 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -2,6 +2,7 @@ module Settings.Builders.Haddock (haddockArgs) where import Development.Shake.FilePath import Base +import GHC import Package import Expression import Oracles diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index cd856b8..61457cb 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -2,7 +2,9 @@ module Settings.Packages (getPackages, knownPackages, findKnownPackage) where import Base import Expression +import GHC import Predicates +import Oracles.Config.Setting import Settings.User -- Combining default list of packages with user modifications diff --git a/src/Settings/User.hs b/src/Settings/User.hs index e16fb27..cad2578 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -6,8 +6,8 @@ module Settings.User ( verboseCommands, turnWarningsIntoErrors ) where +import GHC import Expression -import Predicates -- No user-specific settings by default -- TODO: rename to userArgs diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 8484575..8376213 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -4,6 +4,7 @@ import Data.Monoid import Expression import Predicates import Settings.User +import Oracles.Config.Flag -- TODO: use a single expression Ways parameterised by package instead of -- expressions libWays and rtsWays From git at git.haskell.org Fri Oct 27 00:19:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update build flavour related text (59b07fd) Message-ID: <20171027001910.593EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59b07fddd177b3813a4dcc5704efbde4dca7857d/ghc >--------------------------------------------------------------- commit 59b07fddd177b3813a4dcc5704efbde4dca7857d Author: Andrey Mokhov Date: Sat Jul 16 17:57:07 2016 +0100 Update build flavour related text See #268. [skip ci] >--------------------------------------------------------------- 59b07fddd177b3813a4dcc5704efbde4dca7857d doc/user-settings.md | 90 +++++++++++++++++++++++++++++++++------------------- 1 file changed, 57 insertions(+), 33 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 1dbfd6f..01c3831 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -15,6 +15,39 @@ buildRootPath :: FilePath buildRootPath = "_build" ``` +## Build flavour + +Build _flavour_ is a collection of build settings that fully define a GHC build: +```haskell +data Flavour = Flavour + { name :: String -- ^ Flavour name, to set from command line. + , args :: Args -- ^ Use these command line arguments. + , packages :: Packages -- ^ Build these packages. + , libraryWays :: Ways -- ^ Build libraries these ways. + , rtsWays :: Ways -- ^ Build RTS these ways. + , splitObjects :: Predicate -- ^ Build split objects. + , buildHaddock :: Predicate -- ^ Build Haddock and documentation. + , dynamicGhcPrograms :: Bool -- ^ Build dynamic GHC programs. + , ghciWithDebugger :: Bool -- ^ Enable GHCi debugger. + , ghcProfiled :: Bool -- ^ Build profiled GHC. + , ghcDebugged :: Bool } -- ^ Build GHC with debug information. +``` +Hadrian provides several built-in flavours (`defaultFlavour`, `quickFlavour`, and +a few others), which can be activated from the command line, e.g. `--flavour=quick`. +Users can define new build flavours by adding them to `userFlavours` list: +```haskell +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default flavour + +userFlavours :: [Flavour] +userFlavours = [userFlavour] +``` +Now `--flavour=user` will run Hadrian with `userFlavour` settings. Note: +`defaultFlavour` is defined in module `Settings.Default`, which must be +imported as `import {-# SOURCE #-} Settings.Default` to handle cyclic +module dependencies. In the following sections we look at specific fields of +the `Flavour` record in more detail. + ## Command line arguments One of the key features of Hadrian is that users can modify any build command by @@ -24,7 +57,9 @@ affected build rules during the next build, without requiring a full rebuild. For example, here is how to pass an extra argument `-O0` to all invocations of GHC when compiling package `cabal`: ```haskell --- | Modify default build command line arguments. +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", args = defaultArgs <> userArgs } + userArgs :: Args userArgs = builder Ghc ? package cabal ? arg "-O0" ``` @@ -50,28 +85,28 @@ path component, excluding any separators. ## Packages -To add or remove a package from a particular build stage, use `userPackages`. As -an example, below we add package `base` to Stage0 and remove package `haskeline` -from Stage1: +Users can add and remove packages from particular build stages. As an example, +below we add package `base` to Stage0 and remove package `haskeline` from Stage1: ```haskell --- | Modify the set of packages that are built by default in each stage. +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", packages = defaultPackages <> userPackages } + userPackages :: Packages userPackages = mconcat [ stage0 ? append [base] , stage1 ? remove [haskeline] ] ``` If you are working on a new GHC package you need to let Hadrian know about it -by setting `userKnownPackages`: +by adding it to `userKnownPackages`: ```haskell --- | Add user defined packages. Don't forget to add them to 'userPackages' too. userKnownPackages :: [Package] -userKnownPackages = [myPackage] +userKnownPackages = [userPackage] --- An example package that lives in "libraries/my-package" directory. -myPackage :: Package -myPackage = library "my-package" +-- An example package that lives in "libraries/user-package" directory. +userPackage :: Package +userPackage = library "user-package" ``` -Note, you will also need to add `myPackage` to a specific build stage by modifying +Note, you will also need to add `userPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting @@ -85,17 +120,12 @@ integerLibrary = integerGmp Packages can be built in a number of ways, such as `vanilla`, `profiling` (with profiling information enabled), and many others as defined in `src/Way.hs`. You -can change the default build ways using `userLibraryWays` and `userRtsWays` settings. -As an example, below we remove `dynamic` from the list of library ways but keep -`rts` package ways unchanged: +can change the default build ways by modifying `libraryWays` and `rtsWays` fields +of the `Flavour` record as required. As an example, below we remove `dynamic` +from the list of library ways but keep `rts` package ways unchanged: ```haskell --- | Modify the set of ways in which library packages are built. -userLibraryWays :: Ways -userLibraryWays = remove [dynamic] - --- | Modify the set of ways in which the 'rts' package is built. -userRtsWays :: Ways -userRtsWays = mempty +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", libraryWays = defaultLibraryWays <> remove [dynamic] } ``` ## Verbose command lines @@ -133,18 +163,12 @@ verboseCommands = return True ## Miscellaneous -Use the following settings to change the default behaviour of Hadrian with respect -to building split objects and Haddock documentation. - +To change the default behaviour of Hadrian with respect to building split +objects and Haddock documentation, override `splitObjects` and `buildHaddock` +fields of the `Flavour` record, for example: ```haskell --- | Control when split objects are generated. Note, due to the GHC bug #11315 --- it is necessary to do a full clean rebuild when changing this option. -splitObjects :: Predicate -splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects - --- | Control when to build Haddock documentation. -buildHaddock :: Predicate -buildHaddock = return cmdBuildHaddock +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", splitObjects = return False, buildHaddock = return True } ``` Hadrian prints various progress info during the build. You can customise how this From git at git.haskell.org Fri Oct 27 00:19:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (0053526) Message-ID: <20171027001914.4D5793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0053526eac7df90feba32fe90541c5e4a413da07/ghc >--------------------------------------------------------------- commit 0053526eac7df90feba32fe90541c5e4a413da07 Author: Andrey Mokhov Date: Sat Jul 16 18:09:07 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- 0053526eac7df90feba32fe90541c5e4a413da07 doc/user-settings.md | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 01c3831..1b0a05e 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -17,7 +17,8 @@ buildRootPath = "_build" ## Build flavour -Build _flavour_ is a collection of build settings that fully define a GHC build: +Build _flavour_ is a collection of build settings that fully define a GHC build +(see `src/Flavour.hs`): ```haskell data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. @@ -37,21 +38,22 @@ a few others), which can be activated from the command line, e.g. `--flavour=qui Users can define new build flavours by adding them to `userFlavours` list: ```haskell userFlavour :: Flavour -userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default flavour +userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default build flavour userFlavours :: [Flavour] userFlavours = [userFlavour] ``` -Now `--flavour=user` will run Hadrian with `userFlavour` settings. Note: -`defaultFlavour` is defined in module `Settings.Default`, which must be -imported as `import {-# SOURCE #-} Settings.Default` to handle cyclic -module dependencies. In the following sections we look at specific fields of -the `Flavour` record in more detail. +Now `--flavour=user` will run Hadrian with `userFlavour` settings. In the +following sections we look at specific fields of the `Flavour` record in +more detail. Note: `defaultFlavour`, as well as its individual fields such +as `defaultArgs`, `defaultPackages`, etc. that we use below, are defined in module +`Settings.Default`. Import it as +`import {-# SOURCE #-} Settings.Default` to handle cyclic module dependencies. ## Command line arguments -One of the key features of Hadrian is that users can modify any build command by -changing `userArgs`. The build system will detect the change and will rerun all +One of the key features of Hadrian is that users can easily modify any build command. +The build system will detect the change and will rerun all affected build rules during the next build, without requiring a full rebuild. For example, here is how to pass an extra argument `-O0` to all invocations of @@ -106,7 +108,7 @@ userKnownPackages = [userPackage] userPackage :: Package userPackage = library "user-package" ``` -Note, you will also need to add `userPackage` to a specific build stage by modifying +You will also need to add `userPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting From git at git.haskell.org Fri Oct 27 00:19:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make fixFile more robust. (27317cf) Message-ID: <20171027001911.771F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27317cf1ebcc6e89bd0e42b449cc2059f74673e6/ghc >--------------------------------------------------------------- commit 27317cf1ebcc6e89bd0e42b449cc2059f74673e6 Author: Andrey Mokhov Date: Wed Feb 10 22:51:09 2016 +0000 Make fixFile more robust. See #206. >--------------------------------------------------------------- 27317cf1ebcc6e89bd0e42b449cc2059f74673e6 src/Rules/Actions.hs | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index f8f4925..e815bcf 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -5,7 +5,9 @@ module Rules.Actions ( runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable ) where -import qualified System.Directory as IO +import qualified System.Directory as IO +import qualified System.IO as IO +import qualified Control.Exception.Base as IO import Base import CmdLineFlag @@ -96,9 +98,12 @@ moveDirectory source target = do fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do putBuild $ "| Fix " ++ file - old <- liftIO $ readFile file - let new = f old - length new `seq` liftIO $ writeFile file new + contents <- liftIO $ IO.withFile file IO.ReadMode $ \h -> do + old <- IO.hGetContents h + let new = f old + IO.evaluate $ rnf new + return new + liftIO $ writeFile file contents runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do From git at git.haskell.org Fri Oct 27 00:19:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Expression: Don't re-export Base (ac5040d) Message-ID: <20171027001914.BDADA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ac5040d2125aa94ecc25ba04dcda443e74a7d232/ghc >--------------------------------------------------------------- commit ac5040d2125aa94ecc25ba04dcda443e74a7d232 Author: Ben Gamari Date: Thu Dec 24 14:11:57 2015 +0100 Expression: Don't re-export Base The beginning of a long journey towards minimal re-exports >--------------------------------------------------------------- ac5040d2125aa94ecc25ba04dcda443e74a7d232 src/Expression.hs | 1 - src/Oracles/ArgsHash.hs | 1 + src/Predicates.hs | 1 + src/Rules.hs | 1 + src/Rules/Actions.hs | 1 + src/Rules/Cabal.hs | 1 + src/Rules/Compile.hs | 1 + src/Rules/Data.hs | 1 + src/Rules/Dependencies.hs | 1 + src/Rules/Documentation.hs | 1 + src/Rules/Generate.hs | 1 + src/Rules/Generators/ConfigHs.hs | 1 + src/Rules/Generators/GhcAutoconfH.hs | 1 + src/Rules/Generators/GhcBootPlatformH.hs | 1 + src/Rules/Generators/GhcPlatformH.hs | 1 + src/Rules/Generators/VersionHs.hs | 1 + src/Rules/Install.hs | 1 + src/Rules/Library.hs | 1 + src/Rules/Program.hs | 1 + src/Settings.hs | 7 ++++--- src/Settings/Args.hs | 2 ++ src/Settings/Builders/Ar.hs | 1 + src/Settings/Builders/DeriveConstants.hs | 1 + src/Settings/Builders/Gcc.hs | 2 ++ src/Settings/Builders/Ghc.hs | 1 + src/Settings/Builders/GhcCabal.hs | 14 ++++++++++++++ src/Settings/Builders/GhcPkg.hs | 2 ++ src/Settings/Builders/Haddock.hs | 3 +++ src/Settings/Builders/Hsc2Hs.hs | 4 ++++ src/Settings/Packages.hs | 1 + src/Settings/TargetDirectory.hs | 1 + src/Settings/Ways.hs | 1 + 32 files changed, 55 insertions(+), 4 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ac5040d2125aa94ecc25ba04dcda443e74a7d232 From git at git.haskell.org Fri Oct 27 00:19:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add TODO. (d07b5b2) Message-ID: <20171027001918.E18C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d07b5b20b922d45967d22a29db3f00f9fd0e4247/ghc >--------------------------------------------------------------- commit d07b5b20b922d45967d22a29db3f00f9fd0e4247 Author: Andrey Mokhov Date: Thu Feb 11 01:17:31 2016 +0000 Add TODO. >--------------------------------------------------------------- d07b5b20b922d45967d22a29db3f00f9fd0e4247 src/Settings/Builders/GhcCabal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 51d0e6b..4a46b84 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -66,6 +66,7 @@ libraryArgs = do else "--disable-shared" ] -- TODO: LD_OPTS? +-- TODO: WARNING: unrecognized options: --with-compiler, --with-gmp-libraries, --with-cc configureArgs :: Args configureArgs = do let conf key = appendSubD $ "--configure-option=" ++ key From git at git.haskell.org Fri Oct 27 00:19:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of gmpLibNameCache. (d4b6ee5) Message-ID: <20171027001915.2912C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd/ghc >--------------------------------------------------------------- commit d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd Author: Andrey Mokhov Date: Wed Feb 10 23:40:49 2016 +0000 Get rid of gmpLibNameCache. Fix #206. >--------------------------------------------------------------- d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd src/Rules/Gmp.hs | 17 +++++------------ src/Settings/Builders/Ghc.hs | 10 +++++----- src/Settings/Paths.hs | 8 ++------ 3 files changed, 12 insertions(+), 23 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index ab25495..3e1acea 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -7,7 +7,6 @@ import Expression import GHC import Oracles.Config.Setting import Rules.Actions -import Settings.Builders.Ghc import Settings.Packages.IntegerGmp import Settings.User @@ -67,7 +66,7 @@ gmpRules :: Rules () gmpRules = do -- TODO: split into multiple rules - [gmpLibraryH, gmpLibNameCache] &%> \_ -> do + gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] liftIO $ removeFiles gmpBuildPath ["//*"] @@ -83,22 +82,16 @@ gmpRules = do createDirectory $ takeDirectory gmpLibraryH -- We don't use system GMP on Windows. TODO: fix? - -- TODO: we do not track "config.mk" and "integer-gmp.buildinfo", see #173 - windows <- windowsHost + -- TODO: we don't track "config.mk" & "integer-gmp.buildinfo", see #173 + windows <- windowsHost configMk <- liftIO . readFile $ gmpBase -/- "config.mk" - if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] + if not windows && any (`isInfixOf` configMk) + [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - buildInfo <- liftIO . readFile $ pkgPath integerGmp -/- "integer-gmp.buildinfo" - let prefix = "extra-libraries: " - libs s = case stripPrefix prefix s of - Nothing -> [] - Just value -> words value - writeFileChanged gmpLibNameCache . unlines . concatMap libs $ lines buildInfo else do putBuild "| No GMP library/framework detected; in tree GMP will be built" - writeFileChanged gmpLibNameCache "" -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index b3bca31..c9f8ddc 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,5 +1,5 @@ module Settings.Builders.Ghc ( - ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs, gmpLibNameCache + ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs ) where import Base @@ -23,12 +23,12 @@ ghcBuilderArgs = stagedBuilder Ghc ? do stage <- getStage way <- getWay when (stage > Stage0) . lift $ needTouchy - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output - buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output + let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] + buildHi = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf] buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs gmpLibs <- if stage > Stage0 && buildProg - then lift $ readFileLines gmpLibNameCache -- TODO: use oracles + then words <$> getSetting GmpLibDir else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs @@ -47,7 +47,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] needTouchy :: Action () -needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy ] +needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 20f4721..99a4962 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,7 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibNameCache, - packageDbDirectory, pkgConfFile + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, packageDbDirectory, + pkgConfFile ) where import Base @@ -51,10 +51,6 @@ pkgFile stage pkg prefix suffix = do gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" --- GMP library names extracted from integer-gmp.buildinfo -gmpLibNameCache :: FilePath -gmpLibNameCache = gmpBuildPath -/- "gmp-lib-names" - -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory packageDbDirectory :: Stage -> FilePath From git at git.haskell.org Fri Oct 27 00:19:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Builder: Add haddocks (30484e2) Message-ID: <20171027001918.6164D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30484e290251d2b765f409fb2498fd770b987bc6/ghc >--------------------------------------------------------------- commit 30484e290251d2b765f409fb2498fd770b987bc6 Author: Ben Gamari Date: Thu Dec 24 14:47:19 2015 +0100 Builder: Add haddocks >--------------------------------------------------------------- 30484e290251d2b765f409fb2498fd770b987bc6 src/Builder.hs | 17 +++++++++-------- 1 file changed, 9 insertions(+), 8 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 78f8376..0174dad 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -10,12 +10,12 @@ import GHC.Generics (Generic) import Oracles import Stage --- A Builder is an external command invoked in separate process using Shake.cmd +-- | A 'Builder' is an external command invoked in separate process using 'Shake.cmd' -- --- Ghc Stage0 is the bootstrapping compiler --- Ghc StageN, N > 0, is the one built on stage (N - 1) --- GhcPkg Stage0 is the bootstrapping GhcPkg --- GhcPkg StageN, N > 0, is the one built in Stage0 (TODO: need only Stage1?) +-- @Ghc Stage0@ is the bootstrapping compiler +-- @Ghc StageN@, N > 0, is the one built on stage (N - 1) +-- @GhcPkg Stage0@ is the bootstrapping @GhcPkg@ +-- @GhcPkg StageN@, N > 0, is the one built in Stage0 (TODO: need only Stage1?) -- TODO: Do we really need HsCpp builder? Can't we use a generic Cpp -- builder instead? It would also be used instead of GccM. -- TODO: rename Gcc to CCompiler? We sometimes use gcc and sometimes clang. @@ -73,7 +73,8 @@ builderKey builder = case builder of Objdump -> "objdump" Unlit -> "unlit" --- TODO: Paths to some builders should be determined using defaultProgramPath +-- | Determine the location of a 'Builder' +-- TODO: Paths to some builders should be determined using 'defaultProgramPath' builderPath :: Builder -> Action FilePath builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ @@ -87,8 +88,8 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- Make sure a builder exists on the given path and rebuild it if out of date. --- If laxDependencies is True then we do not rebuild GHC even if it is out of +-- | Make sure a builder exists on the given path and rebuild it if out of date. +-- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). needBuilder :: Bool -> Builder -> Action () needBuilder laxDependencies builder = do From git at git.haskell.org Fri Oct 27 00:19:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GhcCabal: Simplify imports (0be2c4b) Message-ID: <20171027001922.08E7D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0be2c4bb4b02cb74322191e72b042688603af5b4/ghc >--------------------------------------------------------------- commit 0be2c4bb4b02cb74322191e72b042688603af5b4 Author: Ben Gamari Date: Thu Dec 24 14:44:16 2015 +0100 GhcCabal: Simplify imports >--------------------------------------------------------------- 0be2c4bb4b02cb74322191e72b042688603af5b4 src/Settings/Builders/GhcCabal.hs | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 7905a2c..bd95cfc 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -3,13 +3,7 @@ module Settings.Builders.GhcCabal ( customPackageArgs, ccArgs, cppArgs, ccWarnings, argStagedSettingList, needDll0 ) where -import Data.Monoid -import Control.Monad.Trans.Class -import Control.Monad.Extra - -import Development.Shake -import Development.Shake.FilePath -import Base ((-/-), bootPackageConstraints) +import Base import Oracles.Config.Setting import Oracles.Config.Flag import GHC From git at git.haskell.org Fri Oct 27 00:19:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #270 from ggreif/patch-1 (03ffd8e) Message-ID: <20171027001921.CCBF73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03ffd8e37ba2b55bbba5b97b5a8aa4dfed2afa84/ghc >--------------------------------------------------------------- commit 03ffd8e37ba2b55bbba5b97b5a8aa4dfed2afa84 Merge: 0053526 e1b6e52 Author: Andrey Mokhov Date: Sat Jul 16 18:22:33 2016 +0100 Merge pull request #270 from ggreif/patch-1 Typo [skip ci] >--------------------------------------------------------------- 03ffd8e37ba2b55bbba5b97b5a8aa4dfed2afa84 doc/user-settings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:19:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Typo (e1b6e52) Message-ID: <20171027001918.168DE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1b6e522c1ca78cede5a3a4e45d2a7e05ef1aa0c/ghc >--------------------------------------------------------------- commit e1b6e522c1ca78cede5a3a4e45d2a7e05ef1aa0c Author: Gabor Greif Date: Sat Jul 16 19:18:30 2016 +0200 Typo >--------------------------------------------------------------- e1b6e522c1ca78cede5a3a4e45d2a7e05ef1aa0c doc/user-settings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 1b0a05e..d4f0f95 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -38,7 +38,7 @@ a few others), which can be activated from the command line, e.g. `--flavour=qui Users can define new build flavours by adding them to `userFlavours` list: ```haskell userFlavour :: Flavour -userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default build flavour +userFlavour = defaultFlavour { name = "user", ... } -- modify the default build flavour userFlavours :: [Flavour] userFlavours = [userFlavour] From git at git.haskell.org Fri Oct 27 00:19:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on integerGmp configure in gmpRules. (e9106e8) Message-ID: <20171027001922.DFA123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e9106e8ddca0a1bc5677a03c682bc26d345826bd/ghc >--------------------------------------------------------------- commit e9106e8ddca0a1bc5677a03c682bc26d345826bd Author: Andrey Mokhov Date: Thu Feb 11 01:18:48 2016 +0000 Depend on integerGmp configure in gmpRules. See #159. >--------------------------------------------------------------- e9106e8ddca0a1bc5677a03c682bc26d345826bd src/Rules/Gmp.hs | 28 ++++++++-------------------- 1 file changed, 8 insertions(+), 20 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 3e1acea..4c7a480 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,7 +1,5 @@ module Rules.Gmp (gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH) where -import qualified System.Directory as IO - import Base import Expression import GHC @@ -9,6 +7,7 @@ import Oracles.Config.Setting import Rules.Actions import Settings.Packages.IntegerGmp import Settings.User +import Settings.Paths gmpBase :: FilePath gmpBase = "libraries/integer-gmp/gmp" @@ -64,27 +63,15 @@ configureIntGmpArguments = do -- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do - -- TODO: split into multiple rules gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - liftIO $ removeFiles gmpBuildPath ["//*"] - - -- TODO: without the optimisation below we configure integerGmp package - -- twice -- think how this can be optimised (shall we solve #18 first?) - -- TODO: this is a hacky optimisation: we do not rerun configure of - -- integerGmp package if we detect the results of the previous run - envs <- configureEnvironment - unlessM (liftIO . IO.doesFileExist $ gmpBase -/- "config.mk") $ do - args <- configureIntGmpArguments - runConfigure (pkgPath integerGmp) envs args - createDirectory $ takeDirectory gmpLibraryH + -- We don't use system GMP on Windows. TODO: fix? - -- TODO: we don't track "config.mk" & "integer-gmp.buildinfo", see #173 windows <- windowsHost - configMk <- liftIO . readFile $ gmpBase -/- "config.mk" + configMk <- readFile' $ gmpBase -/- "config.mk" if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do @@ -111,8 +98,6 @@ gmpRules = do copyFile src patchPath applyPatch gmpBuildPath patch - -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? - let filename = dropExtension . dropExtension . takeFileName $ head tarballs suffix = "-nodoc-patched" unless (suffix `isSuffixOf` filename) $ @@ -121,8 +106,9 @@ gmpRules = do let libName = take (length filename - length suffix) filename libPath = gmpBuildPath -/- libName - args2 <- configureArguments - runConfigure libPath envs args2 + envs <- configureEnvironment + args <- configureArguments + runConfigure libPath envs args runMake libPath ["MAKEFLAGS="] @@ -139,3 +125,5 @@ gmpRules = do putSuccess "| Successfully built custom library 'gmp'" gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] + + gmpBase -/- "config.mk" %> \_ -> need [pkgDataFile Stage1 integerGmp] From git at git.haskell.org Fri Oct 27 00:19:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop TODO (3b0fab4) Message-ID: <20171027001925.7F5883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b0fab4ddaf709c17757d97416a84a9e3547ce6b/ghc >--------------------------------------------------------------- commit 3b0fab4ddaf709c17757d97416a84a9e3547ce6b Author: Andrey Mokhov Date: Sat Jul 16 23:52:17 2016 +0100 Drop TODO >--------------------------------------------------------------- 3b0fab4ddaf709c17757d97416a84a9e3547ce6b src/UserSettings.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index a0a5d49..b952363 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -14,7 +14,6 @@ import Flavour import GHC import Predicate --- TODO: Update the docs. -- See doc/user-settings.md for instructions. -- | All build results are put into 'buildRootPath' directory. From git at git.haskell.org Fri Oct 27 00:19:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #36 from bgamari/reexport (84af166) Message-ID: <20171027001925.B46273A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84af1661707ed82d1b378d02ce712ecc212535f5/ghc >--------------------------------------------------------------- commit 84af1661707ed82d1b378d02ce712ecc212535f5 Merge: 58d7fcc 30484e2 Author: Andrey Mokhov Date: Mon Dec 28 13:09:27 2015 +0000 Merge pull request #36 from bgamari/reexport Begin paring down reexports >--------------------------------------------------------------- 84af1661707ed82d1b378d02ce712ecc212535f5 src/Base.hs | 11 ++--------- src/Builder.hs | 19 +++++++++++-------- src/Expression.hs | 3 ++- src/Oracles/ArgsHash.hs | 1 + src/Oracles/Config.hs | 1 + src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 2 ++ src/Oracles/PackageData.hs | 1 + src/Oracles/WindowsRoot.hs | 1 + src/Predicates.hs | 6 ++---- src/Rules.hs | 1 + src/Rules/Actions.hs | 1 + src/Rules/Cabal.hs | 1 + src/Rules/Compile.hs | 1 + src/Rules/Data.hs | 1 + src/Rules/Dependencies.hs | 2 ++ src/Rules/Documentation.hs | 1 + src/Rules/Generate.hs | 1 + src/Rules/Generators/ConfigHs.hs | 1 + src/Rules/Generators/GhcAutoconfH.hs | 1 + src/Rules/Generators/GhcBootPlatformH.hs | 1 + src/Rules/Generators/GhcPlatformH.hs | 1 + src/Rules/Generators/VersionHs.hs | 1 + src/Rules/Install.hs | 1 + src/Rules/Library.hs | 5 ++++- src/Rules/Program.hs | 3 +++ src/Settings.hs | 7 ++++--- src/Settings/Args.hs | 2 ++ src/Settings/Builders/Ar.hs | 1 + src/Settings/Builders/DeriveConstants.hs | 1 + src/Settings/Builders/Gcc.hs | 2 ++ src/Settings/Builders/Ghc.hs | 1 + src/Settings/Builders/GhcCabal.hs | 8 ++++++++ src/Settings/Builders/GhcPkg.hs | 2 ++ src/Settings/Builders/Haddock.hs | 4 ++++ src/Settings/Builders/Hsc2Hs.hs | 4 ++++ src/Settings/Packages.hs | 3 +++ src/Settings/TargetDirectory.hs | 1 + src/Settings/User.hs | 2 +- src/Settings/Ways.hs | 2 ++ src/Target.hs | 2 ++ 41 files changed, 85 insertions(+), 27 deletions(-) From git at git.haskell.org Fri Oct 27 00:19:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop configureIntGmpArguments. (cc10288) Message-ID: <20171027001926.6A4A93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cc102887b32e84005d553c4adbef1ca5f5c43a1a/ghc >--------------------------------------------------------------- commit cc102887b32e84005d553c4adbef1ca5f5c43a1a Author: Andrey Mokhov Date: Thu Feb 11 01:51:10 2016 +0000 Drop configureIntGmpArguments. See #159. >--------------------------------------------------------------- cc102887b32e84005d553c4adbef1ca5f5c43a1a src/Rules/Gmp.hs | 7 ------- 1 file changed, 7 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 4c7a480..9916ad6 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -53,13 +53,6 @@ configureArguments = do , "--host=" ++ hostPlatform , "--build=" ++ buildPlatform] -configureIntGmpArguments :: Action [String] -configureIntGmpArguments = do - includes <- setting GmpIncludeDir - libs <- setting GmpLibDir - return $ map ("--with-gmp-includes=" ++) (words includes) - ++ map ("--with-gmp-libraries=" ++) (words libs) - -- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do From git at git.haskell.org Fri Oct 27 00:19:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert to quickest build flavour on Travis Linux (118adf2) Message-ID: <20171027001929.44D493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/118adf2fa6476460270c3d06d9e935ffcb28ab7d/ghc >--------------------------------------------------------------- commit 118adf2fa6476460270c3d06d9e935ffcb28ab7d Author: Andrey Mokhov Date: Sun Jul 17 00:09:07 2016 +0100 Revert to quickest build flavour on Travis Linux >--------------------------------------------------------------- 118adf2fa6476460270c3d06d9e935ffcb28ab7d .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 2b2379f..dd74f25 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=default TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quickest TARGET= addons: apt: packages: From git at git.haskell.org Fri Oct 27 00:19:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export Data.Monoid from Expression. (024b562) Message-ID: <20171027001929.82BE63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/024b5625e53789755a0af096b7a9438e8e33cc8c/ghc >--------------------------------------------------------------- commit 024b5625e53789755a0af096b7a9438e8e33cc8c Author: Andrey Mokhov Date: Mon Dec 28 14:28:36 2015 +0000 Re-export Data.Monoid from Expression. >--------------------------------------------------------------- 024b5625e53789755a0af096b7a9438e8e33cc8c src/Expression.hs | 2 ++ src/Rules/Program.hs | 2 +- 2 files changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Expression.hs b/src/Expression.hs index a83ea15..2b7ef9a 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -18,6 +18,7 @@ module Expression ( getInput, getOutput, -- * Re-exports + module Data.Monoid, module Builder, module Package, module Stage, @@ -25,6 +26,7 @@ module Expression ( ) where import Control.Monad.Trans.Reader +import Data.Monoid import Base import Package diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 781231f..0199071 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -3,7 +3,7 @@ module Rules.Program (buildProgram) where import Data.Char import Base -import Expression hiding (splitPath) +import Expression import GHC hiding (ghci) import Oracles import Rules.Actions From git at git.haskell.org Fri Oct 27 00:19:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Extract gmpLibs from integer-gmp.buildinfo directly. (aafa9ad) Message-ID: <20171027001930.305393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aafa9add2e1c98059b7ffa6ded7c86195f9967e1/ghc >--------------------------------------------------------------- commit aafa9add2e1c98059b7ffa6ded7c86195f9967e1 Author: Andrey Mokhov Date: Thu Feb 11 01:52:55 2016 +0000 Extract gmpLibs from integer-gmp.buildinfo directly. See #159, #206. >--------------------------------------------------------------- aafa9add2e1c98059b7ffa6ded7c86195f9967e1 src/Settings/Builders/Ghc.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index c9f8ddc..b7aef56 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -12,6 +12,9 @@ import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) import Settings.Builders.Common (cIncludeArgs) +buildInfoPath :: FilePath +buildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" + -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ @@ -28,7 +31,12 @@ ghcBuilderArgs = stagedBuilder Ghc ? do buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs gmpLibs <- if stage > Stage0 && buildProg - then words <$> getSetting GmpLibDir + then do -- TODO: get this data more gracefully + buildInfo <- lift $ readFileLines buildInfoPath + let extract s = case stripPrefix "extra-libraries: " s of + Nothing -> [] + Just value -> words value + return $ concatMap extract buildInfo else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs From git at git.haskell.org Fri Oct 27 00:19:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix the 'unknown symbol stat' issue on Travis Linux (116e64d) Message-ID: <20171027001932.E57973A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/116e64d5596233dcacff48ce7e5e0531f730e6bd/ghc >--------------------------------------------------------------- commit 116e64d5596233dcacff48ce7e5e0531f730e6bd Author: Andrey Mokhov Date: Sun Jul 17 00:52:00 2016 +0100 Attempt to fix the 'unknown symbol stat' issue on Travis Linux See #259. >--------------------------------------------------------------- 116e64d5596233dcacff48ce7e5e0531f730e6bd src/Settings/Packages/Base.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages/Base.hs b/src/Settings/Packages/Base.hs index 261c2bb..dce49e7 100644 --- a/src/Settings/Packages/Base.hs +++ b/src/Settings/Packages/Base.hs @@ -6,5 +6,6 @@ import Predicate import UserSettings basePackageArgs :: Args -basePackageArgs = package base ? - builder GhcCabal ? arg ("--flags=" ++ takeFileName (pkgPath integerLibrary)) +basePackageArgs = package base ? mconcat + [ builder GhcCabal ? arg ("--flags=" ++ takeFileName (pkgPath integerLibrary)) + , builder Cc ? arg "-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. From git at git.haskell.org Fri Oct 27 00:19:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use orderOnly dependencies for ordering ghc-cabal invocations (avoids unnecessary rebuilds). (804a5e2) Message-ID: <20171027001933.A38DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/804a5e2ccc8a844f30b897fbe743b424b0cc7efb/ghc >--------------------------------------------------------------- commit 804a5e2ccc8a844f30b897fbe743b424b0cc7efb Author: Andrey Mokhov Date: Mon Dec 28 14:56:44 2015 +0000 Use orderOnly dependencies for ordering ghc-cabal invocations (avoids unnecessary rebuilds). >--------------------------------------------------------------- 804a5e2ccc8a844f30b897fbe743b424b0cc7efb src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index e0a6239..879dc1e 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -26,7 +26,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - need $ map (pkgDataFile stage) depPkgs + orderOnly $ map (pkgDataFile stage) depPkgs need [cabalFile] buildWithResources [(resGhcCabal rs, 1)] $ From git at git.haskell.org Fri Oct 27 00:19:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track gmpBuildInfoPath explicitly. (2c21908) Message-ID: <20171027001934.302163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c219087e3f7ec91e7ab02edbfd3466818402c73/ghc >--------------------------------------------------------------- commit 2c219087e3f7ec91e7ab02edbfd3466818402c73 Author: Andrey Mokhov Date: Thu Feb 11 11:40:42 2016 +0000 Track gmpBuildInfoPath explicitly. See #159. >--------------------------------------------------------------- 2c219087e3f7ec91e7ab02edbfd3466818402c73 src/Rules/Gmp.hs | 4 +++- src/Settings/Builders/Ghc.hs | 5 +---- src/Settings/Paths.hs | 8 ++++++-- 3 files changed, 10 insertions(+), 7 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 9916ad6..b70b840 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -119,4 +119,6 @@ gmpRules = do gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] - gmpBase -/- "config.mk" %> \_ -> need [pkgDataFile Stage1 integerGmp] + -- This causes integerGmp package to be configured, hence creating the files + [gmpBase -/- "config.mk", gmpBuildInfoPath] &%> \_ -> + need [pkgDataFile Stage1 integerGmp] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index b7aef56..51fde7f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -12,9 +12,6 @@ import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) import Settings.Builders.Common (cIncludeArgs) -buildInfoPath :: FilePath -buildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" - -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ @@ -32,7 +29,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do libs <- getPkgDataList DepExtraLibs gmpLibs <- if stage > Stage0 && buildProg then do -- TODO: get this data more gracefully - buildInfo <- lift $ readFileLines buildInfoPath + buildInfo <- lift $ readFileLines gmpBuildInfoPath let extract s = case stripPrefix "extra-libraries: " s of Nothing -> [] Just value -> words value diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 99a4962..96cd3bf 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,7 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, packageDbDirectory, - pkgConfFile + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpBuildInfoPath, + packageDbDirectory, pkgConfFile ) where import Base @@ -51,6 +51,10 @@ pkgFile stage pkg prefix suffix = do gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" +-- We extract system gmp library name from this file +gmpBuildInfoPath :: FilePath +gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" + -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory packageDbDirectory :: Stage -> FilePath From git at git.haskell.org Fri Oct 27 00:19:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out Context from Target. (e8b62f7) Message-ID: <20171027001937.BB4083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e8b62f7e939cb19194fea1ff0123ae8df1788e61/ghc >--------------------------------------------------------------- commit e8b62f7e939cb19194fea1ff0123ae8df1788e61 Author: Andrey Mokhov Date: Fri Feb 12 01:22:58 2016 +0000 Factor out Context from Target. See #207. >--------------------------------------------------------------- e8b62f7e939cb19194fea1ff0123ae8df1788e61 shaking-up-ghc.cabal | 1 + src/Context.hs | 28 ++++++++++++++++++ src/Expression.hs | 24 +++++++-------- src/Oracles/PackageDb.hs | 4 +-- src/Rules.hs | 12 ++++---- src/Rules/Actions.hs | 22 +++++++------- src/Rules/Cabal.hs | 4 +-- src/Rules/Compile.hs | 32 +++++++++++--------- src/Rules/Data.hs | 67 ++++++++++++++++++++++-------------------- src/Rules/Dependencies.hs | 20 ++++++++----- src/Rules/Documentation.hs | 23 ++++++++------- src/Rules/Generate.hs | 34 +++++++++++---------- src/Rules/Gmp.hs | 15 +++++----- src/Rules/Libffi.hs | 17 ++++++----- src/Rules/Library.hs | 64 +++++++++++++++++++++------------------- src/Rules/Package.hs | 4 +-- src/Rules/Program.hs | 73 ++++++++++++++++++++++++---------------------- src/Rules/Register.hs | 26 ++++++++++------- src/Target.hs | 67 ++++++------------------------------------ src/Test.hs | 13 ++++----- 20 files changed, 278 insertions(+), 272 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 e8b62f7e939cb19194fea1ff0123ae8df1788e61 From git at git.haskell.org Fri Oct 27 00:19:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change the stack configuration to use the local Cabal lib (1281be4) Message-ID: <20171027001936.6BD453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1281be42949bb986c62e0464032145b060649fe4/ghc >--------------------------------------------------------------- commit 1281be42949bb986c62e0464032145b060649fe4 Author: Michal Terepeta Date: Fri Jul 22 11:30:50 2016 +0200 Change the stack configuration to use the local Cabal lib Hadrian should be built with a local Cabal from within the GHC codebase. This makes the stack pick it up, instead of using the released version of Cabal. Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 1281be42949bb986c62e0464032145b060649fe4 hadrian.cabal | 2 +- stack.yaml | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 3429424..63bd164 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* || == 1.24.* + , Cabal == 1.22.* || == 1.24.* || == 1.25.* , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 diff --git a/stack.yaml b/stack.yaml index f6deca8..9eb4cfb 100644 --- a/stack.yaml +++ b/stack.yaml @@ -6,6 +6,7 @@ resolver: lts-5.17 # Local packages, usually specified by relative directory name packages: - '.' +- '../libraries/Cabal/Cabal' # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: From git at git.haskell.org Fri Oct 27 00:19:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: First step towards #60. (3e2cdc9) Message-ID: <20171027001937.389B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e2cdc9ff449c85d96de67238835e0159b5b3724/ghc >--------------------------------------------------------------- commit 3e2cdc9ff449c85d96de67238835e0159b5b3724 Author: Andrey Mokhov Date: Mon Dec 28 15:58:06 2015 +0000 First step towards #60. >--------------------------------------------------------------- 3e2cdc9ff449c85d96de67238835e0159b5b3724 src/Settings/Args.hs | 13 ++++++++----- src/Settings/Builders/Alex.hs | 11 +---------- src/Settings/Packages/Compiler.hs | 9 +++++++++ 3 files changed, 18 insertions(+), 15 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 8aa0268..6715680 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -16,21 +16,20 @@ import Settings.Builders.Happy import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld +import Settings.Packages.Compiler import Settings.User getArgs :: Expr [String] -getArgs = fromDiffExpr $ defaultArgs <> userArgs +getArgs = fromDiffExpr $ defaultBuilderArgs <> defaultPackageArgs <> userArgs --- TODO: add all other settings -- TODO: add src-hc-args = -H32m -O -- TODO: GhcStage2HcOpts=-O2 unless GhcUnregisterised -- TODO: compiler/stage1/build/Parser_HC_OPTS += -O0 -fno-ignore-interface-pragmas -- TODO: compiler/main/GhcMake_HC_OPTS += -auto-all --- TODO: compiler_stage2_HADDOCK_OPTS += --optghc=-DSTAGE=2 -- TODO: compiler/prelude/PrimOp_HC_OPTS += -fforce-recomp -- TODO: is GhcHcOpts=-Rghc-timing needed? -defaultArgs :: Args -defaultArgs = mconcat +defaultBuilderArgs :: Args +defaultBuilderArgs = mconcat [ alexArgs , arArgs , cabalArgs @@ -48,3 +47,7 @@ defaultArgs = mconcat , hsc2HsArgs , hsCppArgs , ldArgs ] + +defaultPackageArgs :: Args +defaultPackageArgs = mconcat + [ compilerArgs ] diff --git a/src/Settings/Builders/Alex.hs b/src/Settings/Builders/Alex.hs index 239ae85..086bf1b 100644 --- a/src/Settings/Builders/Alex.hs +++ b/src/Settings/Builders/Alex.hs @@ -1,18 +1,9 @@ module Settings.Builders.Alex (alexArgs) where import Expression -import GHC (compiler) -import Predicates (builder, package) +import Predicates (builder) alexArgs :: Args alexArgs = builder Alex ? mconcat [ arg "-g" - , package compiler ? arg "--latin1" , arg =<< getInput , arg "-o", arg =<< getOutput ] - --- TODO: separate arguments into builder-specific and package-specific --- compilierArgs = package compiler ? builder Alex ? arg "awe" - --- args = mconcat --- [ alexArgs --- , compilerArgs ] diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs new file mode 100644 index 0000000..2ade082 --- /dev/null +++ b/src/Settings/Packages/Compiler.hs @@ -0,0 +1,9 @@ +module Settings.Packages.Compiler (compilerArgs) where + +import Expression +import GHC (compiler) +import Predicates (builder, package) + +compilerArgs :: Args +compilerArgs = package compiler ? + mconcat [ builder Alex ? arg "--latin1" ] From git at git.haskell.org Fri Oct 27 00:19:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Target fields for printing out relevant build information. (f415ad1) Message-ID: <20171027001941.77ACD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f415ad1d528c29d0a1708e2406c4fabd99484e31/ghc >--------------------------------------------------------------- commit f415ad1d528c29d0a1708e2406c4fabd99484e31 Author: Andrey Mokhov Date: Tue Dec 29 15:39:52 2015 +0000 Use Target fields for printing out relevant build information. >--------------------------------------------------------------- f415ad1d528c29d0a1708e2406c4fabd99484e31 shaking-up-ghc.cabal | 1 + src/Builder.hs | 10 +++++++++- src/Rules/Actions.hs | 44 +++++++++++++++++--------------------------- 3 files changed, 27 insertions(+), 28 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 0e60637..f530894 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -84,6 +84,7 @@ executable ghc-shake , DeriveGeneric , FlexibleInstances , OverloadedStrings + , RecordWildCards build-depends: base , ansi-terminal >= 0.6 , Cabal >= 1.22 diff --git a/src/Builder.hs b/src/Builder.hs index 0174dad..b4b01c3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} module Builder ( - Builder (..), builderPath, getBuilderPath, specified, needBuilder + Builder (..), isStaged, builderPath, getBuilderPath, specified, needBuilder ) where import Control.Monad.Trans.Reader @@ -43,6 +43,14 @@ data Builder = Alex | Unlit deriving (Show, Eq, Generic) +isStaged :: Builder -> Bool +isStaged (Gcc _) = True +isStaged (GccM _) = True +isStaged (Ghc _) = True +isStaged (GhcM _) = True +isStaged (GhcPkg _) = True +isStaged _ = False + -- Configuration files refer to Builders as follows: builderKey :: Builder -> String builderKey builder = case builder of diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 086cb8e..8b243eb 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE RecordWildCards #-} module Rules.Actions (build, buildWithResources) where import Base @@ -22,9 +23,7 @@ buildWithResources rs target = do -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do - unless verbose $ do - putBuild $ renderBox $ [ "Running " ++ show builder ++ " with arguments:" ] - ++ map (" "++) (interestingInfo builder argList) + unless verbose $ putInfo target quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList @@ -46,28 +45,19 @@ buildWithResources rs target = do build :: Target -> Action () build = buildWithResources [] -interestingInfo :: Builder -> [String] -> [String] -interestingInfo builder ss = case builder of - Alex -> prefixAndSuffix 0 3 ss - Ar -> prefixAndSuffix 2 1 ss - DeriveConstants -> prefixAndSuffix 3 0 ss - Gcc _ -> prefixAndSuffix 0 4 ss - GccM _ -> prefixAndSuffix 0 1 ss - Ghc _ -> prefixAndSuffix 0 4 ss - GhcCabal -> prefixAndSuffix 3 0 ss - GhcM _ -> prefixAndSuffix 1 1 ss - GhcPkg _ -> prefixAndSuffix 3 0 ss - Haddock -> prefixAndSuffix 1 0 ss - Happy -> prefixAndSuffix 0 3 ss - Hsc2Hs -> prefixAndSuffix 0 3 ss - HsCpp -> prefixAndSuffix 0 1 ss - Ld -> prefixAndSuffix 4 0 ss - _ -> ss +-- Print out key information about the command being executed +putInfo :: Target.Target -> Action () +putInfo (Target.Target {..}) = putBuild $ renderBox $ + [ "Running " ++ show builder + ++ " (" ++ stageInfo + ++ "package = " ++ pkgNameString package + ++ wayInfo ++ "):" + , " input: " ++ digest inputs + , "=> output: " ++ digest outputs ] where - prefixAndSuffix n m list = - let len = length list in - if len <= n + m + 1 - then list - else take n list - ++ ["... skipping " ++ show (len - n - m) ++ " arguments ..."] - ++ drop (len - m) list + stageInfo = if isStaged builder then "" else "stage = " ++ show stage ++ ", " + wayInfo = if way == vanilla then "" else ", way = " ++ show way + digest list = case list of + [] -> "none" + [x] -> x + xs -> head xs ++ " (and " ++ show (length xs - 1) ++ " more)" From git at git.haskell.org Fri Oct 27 00:19:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install only after GHC sources are fetched (9e22012) Message-ID: <20171027001943.BE6CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e2201243a40e63e010d923005a87dbb26f1b305/ghc >--------------------------------------------------------------- commit 9e2201243a40e63e010d923005a87dbb26f1b305 Author: Andrey Mokhov Date: Fri Jul 22 11:55:50 2016 +0200 Install only after GHC sources are fetched >--------------------------------------------------------------- 9e2201243a40e63e010d923005a87dbb26f1b305 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4392abe..4c3e714 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -15,7 +15,6 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ @@ -24,6 +23,7 @@ install: - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - ghc --version - stack --version - alex --version From git at git.haskell.org Fri Oct 27 00:19:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #271 from michalt/stack-localcabal/1 (3380e0d) Message-ID: <20171027001940.30CEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3380e0d6c1f90a502229390a19298a82d84c14b8/ghc >--------------------------------------------------------------- commit 3380e0d6c1f90a502229390a19298a82d84c14b8 Merge: 116e64d 1281be4 Author: Andrey Mokhov Date: Fri Jul 22 11:45:34 2016 +0200 Merge pull request #271 from michalt/stack-localcabal/1 Change the stack configuration to use the local Cabal lib >--------------------------------------------------------------- 3380e0d6c1f90a502229390a19298a82d84c14b8 hadrian.cabal | 2 +- stack.yaml | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:19:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (6482e6a) Message-ID: <20171027001941.CB10B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6482e6a90e68c54b7d0202d0ae5d9d600873646d/ghc >--------------------------------------------------------------- commit 6482e6a90e68c54b7d0202d0ae5d9d600873646d Author: Andrey Mokhov Date: Sun Feb 14 21:18:57 2016 +0000 Add comments. >--------------------------------------------------------------- 6482e6a90e68c54b7d0202d0ae5d9d600873646d src/Context.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Context.hs b/src/Context.hs index 9bf8020..b578208 100644 --- a/src/Context.hs +++ b/src/Context.hs @@ -20,6 +20,8 @@ data Context = Context vanillaContext :: Stage -> Package -> Context vanillaContext s p = Context s p vanilla +-- | Partial context with undefined 'Package' field. Useful for 'Packages' +-- expressions that only read the environment and current 'Stage'. stageContext :: Stage -> Context stageContext s = vanillaContext s $ error "stageContext: package not set" From git at git.haskell.org Fri Oct 27 00:19:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Settings/Builders/Common.hs for storing common Args, refactor code. (0c9571a) Message-ID: <20171027001945.9E0003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c9571aac4cf2d4f5c84d6d2bcbf9a029e52c2ef/ghc >--------------------------------------------------------------- commit 0c9571aac4cf2d4f5c84d6d2bcbf9a029e52c2ef Author: Andrey Mokhov Date: Tue Dec 29 18:47:48 2015 +0000 Add Settings/Builders/Common.hs for storing common Args, refactor code. >--------------------------------------------------------------- 0c9571aac4cf2d4f5c84d6d2bcbf9a029e52c2ef src/Rules/Data.hs | 6 +++--- src/Settings/Builders/Ar.hs | 6 +++--- src/Settings/Builders/Common.hs | 9 +++++++++ src/Settings/Builders/DeriveConstants.hs | 3 ++- src/Settings/Builders/GhcCabal.hs | 10 +++------- 5 files changed, 20 insertions(+), 14 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 879dc1e..70c8e8a 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -8,7 +8,7 @@ import Predicates (registerPackage) import Rules.Actions import Rules.Resources import Settings -import Settings.Builders.GhcCabal +import Settings.Builders.Common -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: Resources -> PartialTarget -> Rules () @@ -42,9 +42,9 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do postProcessPackageData dataFile -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps - -- TODO: code duplication around ghcIncludeDirs priority 2.0 $ do when (pkg == hp2ps) $ dataFile %> \mk -> do + includes <- interpretPartial target $ fromDiffExpr includesArgs let prefix = "utils_hp2ps_stage" ++ show (fromEnum stage) ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" , "Reorder.c", "TopTwenty.c", "AuxFile.c" @@ -57,7 +57,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do , "INSTALL = YES" , "INSTALL_INPLACE = YES" , "DEP_EXTRA_LIBS = m" - , "CC_OPTS = " ++ unwords (map ("-I"++) ghcIncludeDirs) ] + , "CC_OPTS = " ++ unwords includes ] writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 662d5fe..dae4a82 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -26,15 +26,15 @@ arCmd path argList = do fileArgs = drop arFlagsCount argList if arSupportsAtFile then useAtFile path flagArgs fileArgs - else useSuccessiveInvokations path flagArgs fileArgs + else useSuccessiveInvocations path flagArgs fileArgs useAtFile :: FilePath -> [String] -> [String] -> Action () useAtFile path flagArgs fileArgs = withTempFile $ \tmp -> do writeFile' tmp $ unwords fileArgs cmd [path] flagArgs ('@' : tmp) -useSuccessiveInvokations :: FilePath -> [String] -> [String] -> Action () -useSuccessiveInvokations path flagArgs fileArgs = do +useSuccessiveInvocations :: FilePath -> [String] -> [String] -> Action () +useSuccessiveInvocations path flagArgs fileArgs = do maxChunk <- cmdLineLengthLimit forM_ (chunksOfSize maxChunk fileArgs) $ \argsChunk -> unit . cmd [path] $ flagArgs ++ argsChunk diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs new file mode 100644 index 0000000..fc3ed53 --- /dev/null +++ b/src/Settings/Builders/Common.hs @@ -0,0 +1,9 @@ +module Settings.Builders.Common (includesArgs) where + +import Expression + +includes :: [FilePath] +includes = [ "includes", "includes/dist-derivedconstants/header" ] + +includesArgs :: Args +includesArgs = append $ map ("-I" ++) includes diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 1f42243..ee07d34 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -7,6 +7,7 @@ import Expression import Oracles.Config.Flag import Oracles.Config.Setting import Predicates (builder, file) +import Settings.Builders.Common import Settings.Builders.GhcCabal derivedConstantsPath :: FilePath @@ -39,7 +40,7 @@ includeCcArgs = do , ccWarnings , append confCcArgs , flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER" - , append $ map ("-I" ++) ghcIncludeDirs -- TODO: fix code duplication + , includesArgs , arg "-Irts" , notM ghcWithSMP ? arg "-DNOSMP" , arg "-fcommon" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index bd95cfc..61da725 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,5 +1,5 @@ module Settings.Builders.GhcCabal ( - cabalArgs, ghcCabalHsColourArgs, ghcIncludeDirs, bootPackageDbArgs, + cabalArgs, ghcCabalHsColourArgs, bootPackageDbArgs, customPackageArgs, ccArgs, cppArgs, ccWarnings, argStagedSettingList, needDll0 ) where @@ -14,6 +14,7 @@ import Stage import Expression import Predicates hiding (stage) import Settings +import Settings.Builders.Common cabalArgs :: Args cabalArgs = builder GhcCabal ? do @@ -115,13 +116,8 @@ ccWarnings = do ldArgs :: Args ldArgs = mempty -ghcIncludeDirs :: [FilePath] -ghcIncludeDirs = [ "includes", "includes/dist" - , "includes/dist-derivedconstants/header" - , "includes/dist-ghcconstants/header" ] - cppArgs :: Args -cppArgs = append $ map ("-I" ++) ghcIncludeDirs +cppArgs = includesArgs -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" From git at git.haskell.org Fri Oct 27 00:19:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move mkUserGuidePart to Stage2. (9497fbe) Message-ID: <20171027001945.E24033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9497fbee97634610c2d9af6115f139f794c5fb0f/ghc >--------------------------------------------------------------- commit 9497fbee97634610c2d9af6115f139f794c5fb0f Author: Andrey Mokhov Date: Sun Feb 14 21:54:25 2016 +0000 Move mkUserGuidePart to Stage2. >--------------------------------------------------------------- 9497fbee97634610c2d9af6115f139f794c5fb0f src/Settings/Packages.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 691cd78..ef8fc26 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -34,8 +34,7 @@ packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq , directory, filepath, ghci, ghcPrim, haskeline, hpcBin - , integerLibrary, mkUserGuidePart, pretty, process, rts, runGhc - , time ] + , integerLibrary, pretty, process, rts, runGhc, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , notM windowsHost ? append [iservBin] @@ -45,7 +44,7 @@ packagesStage1 = mconcat -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages packagesStage2 = mconcat - [ append [ghcTags] + [ append [ghcTags, mkUserGuidePart] , buildHaddock ? append [haddock] ] -- TODO: switch to Set Package as the order of packages should not matter? From git at git.haskell.org Fri Oct 27 00:19:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix GHC location before Stack install (b2fc154) Message-ID: <20171027001947.4F1603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2fc1542ca069e5efb3abaa8dcb2213bd1ed8308/ghc >--------------------------------------------------------------- commit b2fc1542ca069e5efb3abaa8dcb2213bd1ed8308 Author: Andrey Mokhov Date: Fri Jul 22 12:17:52 2016 +0200 Fix GHC location before Stack install >--------------------------------------------------------------- b2fc1542ca069e5efb3abaa8dcb2213bd1ed8308 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4c3e714..30e3bcf 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -23,13 +23,13 @@ install: - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - ghc --version - stack --version - alex --version - happy --version - stack exec -- ghc-pkg list - - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" From git at git.haskell.org Fri Oct 27 00:19:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose src/Settings/Builders/Gcc.hs, factor out cIncludeArgs into src/Settings/Builders/Common.hs. (bf70983) Message-ID: <20171027001949.A920C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf70983e38c76138bf5819a2dff9109181a1f2aa/ghc >--------------------------------------------------------------- commit bf70983e38c76138bf5819a2dff9109181a1f2aa Author: Andrey Mokhov Date: Tue Dec 29 21:46:04 2015 +0000 Decompose src/Settings/Builders/Gcc.hs, factor out cIncludeArgs into src/Settings/Builders/Common.hs. >--------------------------------------------------------------- bf70983e38c76138bf5819a2dff9109181a1f2aa src/Settings/Args.hs | 4 +++- src/Settings/Builders/Common.hs | 17 ++++++++++++++++- src/Settings/Builders/Gcc.hs | 21 ++++----------------- src/Settings/Builders/Ghc.hs | 6 ++---- src/Settings/Builders/Hsc2Hs.hs | 7 ++----- src/Settings/Packages/Directory.hs | 13 +++++++++++++ 6 files changed, 40 insertions(+), 28 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 6715680..f474f8f 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -17,6 +17,7 @@ import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld import Settings.Packages.Compiler +import Settings.Packages.Directory import Settings.User getArgs :: Expr [String] @@ -50,4 +51,5 @@ defaultBuilderArgs = mconcat defaultPackageArgs :: Args defaultPackageArgs = mconcat - [ compilerArgs ] + [ compilerArgs + , directoryArgs ] diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index fc3ed53..9ed6efd 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -1,9 +1,24 @@ -module Settings.Builders.Common (includesArgs) where +module Settings.Builders.Common (includesArgs, cIncludeArgs) where +import Base import Expression +import Oracles.PackageData +import Settings includes :: [FilePath] includes = [ "includes", "includes/dist-derivedconstants/header" ] includesArgs :: Args includesArgs = append $ map ("-I" ++) includes + +cIncludeArgs :: Args +cIncludeArgs = do + stage <- getStage + pkg <- getPackage + incDirs <- getPkgDataList IncludeDirs + depDirs <- getPkgDataList DepIncludeDirs + let buildPath = targetPath stage pkg -/- "build" + mconcat [ arg $ "-I" ++ buildPath + , arg $ "-I" ++ buildPath -/- "autogen" + , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] + , append [ "-I" ++ dir | dir <- depDirs ] ] diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index fab5104..8a6b087 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -2,20 +2,14 @@ module Settings.Builders.Gcc (gccArgs, gccMArgs) where import Development.Shake.FilePath import Expression -import GHC import Oracles -import Base ((-/-)) -import Predicates (package, stagedBuilder) +import Predicates (stagedBuilder) import Settings +import Settings.Builders.Common (cIncludeArgs) --- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is --- effectively empty. I presume it was expected that GHC will be used for --- compiling all C files, but I don't know why. It seems that directory.c is the --- only file which requires special treatment when using GCC. gccArgs :: Args gccArgs = stagedBuilder Gcc ? mconcat [ commonGccArgs - , package directory ? arg "-D__GLASGOW_HASKELL__" , arg "-c", arg =<< getInput , arg "-o", arg =<< getOutput ] @@ -35,12 +29,5 @@ gccMArgs = stagedBuilder GccM ? do , arg =<< getInput ] commonGccArgs :: Args -commonGccArgs = do - pkg <- getPackage - path <- getTargetPath - iDirs <- getPkgDataList IncludeDirs - dDirs <- getPkgDataList DepIncludeDirs - ccArgs <- getPkgDataList CcArgs - mconcat [ append ccArgs - , arg $ "-I" ++ path -/- "build/autogen" - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- iDirs ++ dDirs ]] +commonGccArgs = mconcat [ append =<< getPkgDataList CcArgs + , cIncludeArgs ] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index f354458..593f0e0 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -7,6 +7,7 @@ import GHC import Predicates hiding (way, stage) import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) +import Settings.Builders.Common (cIncludeArgs) -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot @@ -114,16 +115,13 @@ includeGhcArgs = do pkg <- getPackage path <- getTargetPath srcDirs <- getPkgDataList SrcDirs - incDirs <- getPkgDataList IncludeDirs let buildPath = path -/- "build" autogenPath = buildPath -/- "autogen" mconcat [ arg "-i" , arg $ "-i" ++ buildPath , arg $ "-i" ++ autogenPath - , arg $ "-I" ++ buildPath - , arg $ "-I" ++ autogenPath , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] + , cIncludeArgs , (pkg == compiler || pkg == ghc) ? arg ("-I" ++ pkgPath compiler -/- "stage" ++ show (fromEnum stage)) , not (pkg == hp2ps || pkg == ghcCabal && stage == Stage0) ? diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 90abc82..c89caf0 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -9,6 +9,7 @@ import Oracles import Predicates (builder, stage0, notStage0) import Settings import Settings.Builders.GhcCabal hiding (cppArgs) +import Settings.Builders.Common (cIncludeArgs) templateHsc :: FilePath templateHsc = "inplace/lib/template-hsc.h" @@ -48,18 +49,14 @@ hsc2HsArgs = builder Hsc2Hs ? do getCFlags :: Expr [String] getCFlags = fromDiffExpr $ do - pkg <- getPackage path <- getTargetPath - iDirs <- getPkgDataList IncludeDirs - dDirs <- getPkgDataList DepIncludeDirs cppArgs <- getPkgDataList CppArgs depCcArgs <- getPkgDataList DepCcArgs mconcat [ ccArgs , argStagedSettingList ConfCcArgs , remove ["-O"] , argStagedSettingList ConfCppArgs - , arg $ "-I" ++ path -/- "build/autogen" - , append [ "-I" ++ pkgPath pkg -/- dir | dir <- iDirs ++ dDirs ] + , cIncludeArgs , append cppArgs , append depCcArgs , ccWarnings diff --git a/src/Settings/Packages/Directory.hs b/src/Settings/Packages/Directory.hs new file mode 100644 index 0000000..3ff69ce --- /dev/null +++ b/src/Settings/Packages/Directory.hs @@ -0,0 +1,13 @@ +module Settings.Packages.Directory (directoryArgs) where + +import Expression +import GHC (directory) +import Predicates (stagedBuilder, package) + +-- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is +-- effectively empty. I presume it was expected that GHC will be used for +-- compiling all C files, but I don't know why. It seems that directory.c is the +-- only file which requires special treatment when using GCC. +directoryArgs :: Args +directoryArgs = package directory ? + stagedBuilder Gcc ? arg "-D__GLASGOW_HASKELL__" From git at git.haskell.org Fri Oct 27 00:19:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install mkUserGuidePart binary to inplace/bin. (d1ec507) Message-ID: <20171027001950.079C03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1ec507d7b4d837ee0161f08e9eab0b5630f2797/ghc >--------------------------------------------------------------- commit d1ec507d7b4d837ee0161f08e9eab0b5630f2797 Author: Andrey Mokhov Date: Sun Feb 14 22:55:38 2016 +0000 Install mkUserGuidePart binary to inplace/bin. >--------------------------------------------------------------- d1ec507d7b4d837ee0161f08e9eab0b5630f2797 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0262243..d29cbbf 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -106,7 +106,7 @@ ghcSplit = "inplace/lib/bin/ghc-split" programPath :: Stage -> Package -> Maybe FilePath programPath stage pkg | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) - | pkg == haddock || pkg == ghcTags = case stage of + | pkg `elem` [ghcTags, haddock, mkUserGuidePart] = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing | pkg `elem` [touchy, unlit] = case stage of From git at git.haskell.org Fri Oct 27 00:19:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix inability to find gmp.h when building concurrently (b3bcd0f) Message-ID: <20171027001951.228963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3bcd0ffe22fa51b78aa28caf406b7cb74b04ae8/ghc >--------------------------------------------------------------- commit b3bcd0ffe22fa51b78aa28caf406b7cb74b04ae8 Author: Matthew Pickering Date: Fri Jul 22 14:03:07 2016 +0200 Fix inability to find gmp.h when building concurrently There were situations when building concurrently when we would request `gmp.h` before it had been built (or copied). This was occuring when we generated the list of dependents for the c files in the `integer-gmp` folder. Thus, when generating the dependents for this library we now require `gmp.h`. >--------------------------------------------------------------- b3bcd0ffe22fa51b78aa28caf406b7cb74b04ae8 src/Rules/Dependencies.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index f78c488..c64a4e6 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -11,6 +11,8 @@ import Rules.Actions import Settings.Paths import Target import UserSettings +import GHC + buildPackageDependencies :: [(Resource, Int)] -> Context -> Rules () buildPackageDependencies rs context at Context {..} = @@ -20,6 +22,7 @@ buildPackageDependencies rs context at Context {..} = fmap (path ++) [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do let src = dep2src context out + when (package == integerGmp) (need [gmpLibraryH]) need [src] build $ Target context (Cc FindDependencies stage) [src] [out] From git at git.haskell.org Fri Oct 27 00:19:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add new source files. (73d198b) Message-ID: <20171027001953.366A43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73d198b03cc64d2200e4bcdad4a6da51d419e43a/ghc >--------------------------------------------------------------- commit 73d198b03cc64d2200e4bcdad4a6da51d419e43a Author: Andrey Mokhov Date: Wed Dec 30 01:19:36 2015 +0000 Add new source files. >--------------------------------------------------------------- 73d198b03cc64d2200e4bcdad4a6da51d419e43a shaking-up-ghc.cabal | 3 +++ 1 file changed, 3 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f530894..5ad614e 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -58,6 +58,7 @@ executable ghc-shake , Settings.Args , Settings.Builders.Alex , Settings.Builders.Ar + , Settings.Builders.Common , Settings.Builders.Gcc , Settings.Builders.GenPrimopCode , Settings.Builders.Ghc @@ -69,6 +70,8 @@ executable ghc-shake , Settings.Builders.HsCpp , Settings.Builders.Ld , Settings.Packages + , Settings.Packages.Compiler + , Settings.Packages.Directory , Settings.TargetDirectory , Settings.User , Settings.Ways From git at git.haskell.org Fri Oct 27 00:19:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix incorrect context when reading BuildGhciLib flag. (9207f25) Message-ID: <20171027001953.84FD43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9207f2530763c2bace7708cac77c767e596035da/ghc >--------------------------------------------------------------- commit 9207f2530763c2bace7708cac77c767e596035da Author: Andrey Mokhov Date: Sun Feb 14 22:57:17 2016 +0000 Fix incorrect context when reading BuildGhciLib flag. >--------------------------------------------------------------- 9207f2530763c2bace7708cac77c767e596035da src/Rules/Program.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index f00dd59..00f4c52 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -85,18 +85,18 @@ buildBinary context @ (Context stage package _) bin = do depNames <- interpretInContext context $ getPkgDataList TransitiveDepNames let libStage = min stage Stage1 -- libraries are built only in Stage0/1 libContext = vanillaContext libStage package - pkgs <- interpretInContext libContext getPackages - ghciFlag <- interpretInContext libContext $ getPkgData BuildGhciLib + pkgs <- interpretInContext libContext getPackages let deps = matchPackageNames (sort pkgs) (map PackageName $ sort depNames) - ghci = ghciFlag == "YES" && stage == Stage1 libs <- fmap concat . forM deps $ \dep -> do + let depContext = vanillaContext libStage dep + ghciFlag <- interpretInContext depContext $ getPkgData BuildGhciLib libFiles <- fmap concat . forM ways $ \way -> do libFile <- pkgLibraryFile libStage dep way lib0File <- pkgLibraryFile0 libStage dep way dll0 <- needDll0 libStage dep return $ libFile : [ lib0File | dll0 ] ghciLib <- pkgGhciLibraryFile libStage dep - return $ libFiles ++ [ ghciLib | ghci ] + return $ libFiles ++ [ ghciLib | ghciFlag == "YES" && stage == Stage1 ] let binDeps = if package == ghcCabal && stage == Stage0 then [ pkgPath package -/- src <.> "hs" | src <- hSrcs ] else objs From git at git.haskell.org Fri Oct 27 00:19:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #273 from mpickering/master (4a7016b) Message-ID: <20171027001954.B73783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a7016b71f1a393cfbd9f2360802b07f0a7e9b06/ghc >--------------------------------------------------------------- commit 4a7016b71f1a393cfbd9f2360802b07f0a7e9b06 Merge: b2fc154 b3bcd0f Author: Andrey Mokhov Date: Fri Jul 22 15:09:40 2016 +0200 Merge pull request #273 from mpickering/master Fix inability to find gmp.h when building concurrently >--------------------------------------------------------------- 4a7016b71f1a393cfbd9f2360802b07f0a7e9b06 src/Rules/Dependencies.hs | 3 +++ 1 file changed, 3 insertions(+) From git at git.haskell.org Fri Oct 27 00:19:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Stage.stageString, rename runghc -> runGhc. (9e2ddcb) Message-ID: <20171027001956.ED08A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e2ddcb188ecf614edbaeca9404d0adb77f125b3/ghc >--------------------------------------------------------------- commit 9e2ddcb188ecf614edbaeca9404d0adb77f125b3 Author: Andrey Mokhov Date: Wed Dec 30 03:02:27 2015 +0000 Add Stage.stageString, rename runghc -> runGhc. >--------------------------------------------------------------- 9e2ddcb188ecf614edbaeca9404d0adb77f125b3 src/GHC.hs | 14 +++++++------- src/Oracles/Config/Setting.hs | 8 ++++---- src/Rules/Data.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Stage.hs | 5 ++++- 6 files changed, 18 insertions(+), 15 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 859bec4..f93d92a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -5,7 +5,7 @@ module GHC ( genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, - runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, + runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -26,7 +26,7 @@ defaultKnownPackages = , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin , integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty - , primitive , process, runghc, stm, templateHaskell, terminfo, time + , primitive , process, runGhc, stm, templateHaskell, terminfo, time , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) @@ -35,7 +35,7 @@ array, base, binary, bytestring, cabal, compiler, containers, compareSizes, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, mkUserGuidePart, parallel, pretty, primitive, process, - runghc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package + runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -75,7 +75,7 @@ parallel = library "parallel" pretty = library "pretty" primitive = library "primitive" process = library "process" -runghc = utility "runghc" +runGhc = utility "runGhc" stm = library "stm" templateHaskell = library "template-haskell" terminfo = library "terminfo" @@ -97,17 +97,17 @@ xhtml = library "xhtml" -- * doc/ : produced by haddock -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal defaultTargetDirectory :: Stage -> Package -> FilePath -defaultTargetDirectory stage _ = "stage" ++ show (fromEnum stage) +defaultTargetDirectory stage _ = stageString stage -- TODO: simplify -- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg - | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) + | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing - | isProgram pkg = case stage of + | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg | otherwise = Nothing diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index b0c6da3..ace9158 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -91,10 +91,10 @@ setting key = askConfig $ case key of settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of - ConfCcArgs stage -> "conf-cc-args-stage" ++ show (fromEnum stage) - ConfCppArgs stage -> "conf-cpp-args-stage" ++ show (fromEnum stage) - ConfGccLinkerArgs stage -> "conf-gcc-linker-args-stage" ++ show (fromEnum stage) - ConfLdLinkerArgs stage -> "conf-ld-linker-args-stage" ++ show (fromEnum stage) + ConfCcArgs stage -> "conf-cc-args-" ++ stageString stage + ConfCppArgs stage -> "conf-cpp-args-" ++ stageString stage + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-" ++ stageString stage + ConfLdLinkerArgs stage -> "conf-ld-linker-args-" ++ stageString stage GmpIncludeDirs -> "gmp-include-dirs" GmpLibDirs -> "gmp-lib-dirs" HsCppArgs -> "hs-cpp-args" diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 70c8e8a..a863968 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -45,7 +45,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do priority 2.0 $ do when (pkg == hp2ps) $ dataFile %> \mk -> do includes <- interpretPartial target $ fromDiffExpr includesArgs - let prefix = "utils_hp2ps_stage" ++ show (fromEnum stage) ++ "_" + let prefix = "utils_hp2ps_" ++ stageString stage ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" , "Reorder.c", "TopTwenty.c", "AuxFile.c" , "Deviation.c", "HpFile.c", "Marks.c", "Scale.c" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index ea5ed63..fd101a1 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -127,7 +127,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do file <~ generateVersionHs - when (pkg == runghc) $ buildPath -/- "Main.hs" %> \file -> do + when (pkg == runGhc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file putSuccess $ "| Successfully generated '" ++ file ++ "'." diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 61457cb..308fb8c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -32,7 +32,7 @@ packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq , directory, filepath, ghci, ghcPrim, ghcPwd, haskeline, hpcBin - , integerLibrary, mkUserGuidePart, pretty, process, runghc, time ] + , integerLibrary, mkUserGuidePart, pretty, process, runGhc, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , notM windowsHost ? append [iservBin] diff --git a/src/Stage.hs b/src/Stage.hs index d474557..70fe6ba 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DeriveGeneric #-} -module Stage (Stage (..)) where +module Stage (Stage (..), stageString) where import Base import GHC.Generics (Generic) @@ -8,6 +8,9 @@ import GHC.Generics (Generic) data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Show, Eq, Ord, Enum, Generic) +stageString :: Stage -> String +stageString stage = "stage" ++ show (fromEnum stage) + -- Instances for storing in the Shake database instance Binary Stage instance Hashable Stage From git at git.haskell.org Fri Oct 27 00:19:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out build rules into Rules.buildRules. (e7f8710) Message-ID: <20171027001957.5B7B23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7f8710c591d5329e4a06df538ca0aa789b065a0/ghc >--------------------------------------------------------------- commit e7f8710c591d5329e4a06df538ca0aa789b065a0 Author: Andrey Mokhov Date: Sun Feb 14 22:59:11 2016 +0000 Factor out build rules into Rules.buildRules. >--------------------------------------------------------------- e7f8710c591d5329e4a06df538ca0aa789b065a0 src/Main.hs | 17 ++--------------- src/Rules.hs | 39 ++++++++++++++++++++++++++++----------- 2 files changed, 30 insertions(+), 26 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 544987d..e028597 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -6,14 +6,8 @@ import qualified Base import qualified CmdLineFlag import qualified Environment import qualified Rules -import qualified Rules.Cabal import qualified Rules.Clean -import qualified Rules.Generate -import qualified Rules.Gmp -import qualified Rules.Libffi import qualified Rules.Oracles -import qualified Rules.Perl -import qualified Rules.Setup import qualified Selftest import qualified Test @@ -27,17 +21,10 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do where rules :: Rules () rules = mconcat - [ Rules.Cabal.cabalRules - , Rules.Clean.cleanRules - , Rules.Generate.generateRules - , Rules.Generate.copyRules - , Rules.Gmp.gmpRules - , Rules.Libffi.libffiRules + [ Rules.Clean.cleanRules , Rules.Oracles.oracleRules - , Rules.Perl.perlScriptRules - , Rules.Setup.setupRules + , Rules.buildRules , Rules.topLevelTargets - , Rules.packageRules , Selftest.selftestRules , Test.testRules ] options = shakeOptions diff --git a/src/Rules.hs b/src/Rules.hs index 34cea4c..5cbfa7e 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,12 +1,18 @@ -module Rules (topLevelTargets, packageRules) where +module Rules (topLevelTargets, buildRules) where -import Base import Data.Foldable + +import Base import Expression -import GHC hiding (haddock) +import GHC import qualified Rules.Generate -import Rules.Package -import Rules.Resources +import qualified Rules.Package +import qualified Rules.Resources +import qualified Rules.Cabal +import qualified Rules.Gmp +import qualified Rules.Libffi +import qualified Rules.Perl +import qualified Rules.Setup import Settings allStages :: [Stage] @@ -32,16 +38,27 @@ topLevelTargets = do when (pkg `elem` activePackages) $ if isLibrary pkg then do -- build a library - ways <- interpretInContext context getLibraryWays - libs <- traverse (pkgLibraryFile stage pkg) ways - haddock <- interpretInContext context buildHaddock - need $ libs ++ [ pkgHaddockFile pkg | haddock && stage == Stage1 ] + ways <- interpretInContext context getLibraryWays + libs <- traverse (pkgLibraryFile stage pkg) ways + docs <- interpretInContext context buildHaddock + need $ libs ++ [ pkgHaddockFile pkg | docs && stage == Stage1 ] else do -- otherwise build a program need [ fromJust $ programPath stage pkg ] -- TODO: drop fromJust packageRules :: Rules () packageRules = do - resources <- resourceRules + resources <- Rules.Resources.resourceRules for_ allStages $ \stage -> for_ knownPackages $ \pkg -> - buildPackage resources $ vanillaContext stage pkg + Rules.Package.buildPackage resources $ vanillaContext stage pkg + +buildRules :: Rules () +buildRules = mconcat + [ Rules.Cabal.cabalRules + , Rules.Generate.generateRules + , Rules.Generate.copyRules + , Rules.Gmp.gmpRules + , Rules.Libffi.libffiRules + , Rules.Perl.perlScriptRules + , Rules.Setup.setupRules + , Rules.packageRules ] From git at git.haskell.org Fri Oct 27 00:19:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:19:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split CompilerMode for GHC and CC (a8abbc9) Message-ID: <20171027001958.4132D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8abbc961fcfcd360e9a731fc42c28b93332bc8b/ghc >--------------------------------------------------------------- commit a8abbc961fcfcd360e9a731fc42c28b93332bc8b Author: Michal Terepeta Date: Sat Jul 23 16:57:19 2016 +0200 Split CompilerMode for GHC and CC Signed-off-by: Michal Terepeta >--------------------------------------------------------------- a8abbc961fcfcd360e9a731fc42c28b93332bc8b src/Builder.hs | 27 +++++++++++++++++---------- src/Predicate.hs | 8 +++++++- src/Rules/Compile.hs | 6 +++--- src/Rules/Dependencies.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Test.hs | 4 ++-- src/Settings/Builders/Cc.hs | 4 ++-- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- 13 files changed, 46 insertions(+), 33 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 a8abbc961fcfcd360e9a731fc42c28b93332bc8b From git at git.haskell.org Fri Oct 27 00:20:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Expressions.removePair function to remove pairs of arguments. (9140548) Message-ID: <20171027002000.A17E23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9140548b75f96d17e9888a21bf32a2f46d447cbe/ghc >--------------------------------------------------------------- commit 9140548b75f96d17e9888a21bf32a2f46d447cbe Author: Andrey Mokhov Date: Wed Dec 30 03:03:26 2015 +0000 Add Expressions.removePair function to remove pairs of arguments. >--------------------------------------------------------------- 9140548b75f96d17e9888a21bf32a2f46d447cbe src/Expression.hs | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/src/Expression.hs b/src/Expression.hs index 2b7ef9a..a2eaea9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -3,7 +3,8 @@ module Expression ( -- * Expressions Expr, DiffExpr, fromDiffExpr, -- ** Operators - apply, append, arg, remove, appendSub, appendSubD, filterSub, removeSub, + apply, append, arg, remove, removePair, + appendSub, appendSubD, filterSub, removeSub, -- ** Evaluation interpret, interpretPartial, interpretWithStage, interpretDiff, -- ** Predicates @@ -76,6 +77,16 @@ append x = apply (<> x) remove :: Eq a => [a] -> DiffExpr [a] remove xs = apply $ filter (`notElem` xs) +-- | Remove given pair of elements from a list expression +-- Example: removePair "-flag" "b" ["-flag", "a", "-flag", "b"] = ["-flag", "a"] +removePair :: Eq a => a -> a -> DiffExpr [a] +removePair x y = apply filterPair + where + filterPair (z1 : z2 : zs) = if x == z1 && y == z2 + then filterPair zs + else z1 : filterPair (z2 : zs) + filterPair zs = zs + -- | Apply a predicate to an expression applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do From git at git.haskell.org Fri Oct 27 00:20:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Selftest and Test rules into Rules directory. (d81e041) Message-ID: <20171027002001.243563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d81e041691644e1f99a84691ac0d0fb94c96b263/ghc >--------------------------------------------------------------- commit d81e041691644e1f99a84691ac0d0fb94c96b263 Author: Andrey Mokhov Date: Sun Feb 14 23:02:46 2016 +0000 Move Selftest and Test rules into Rules directory. >--------------------------------------------------------------- d81e041691644e1f99a84691ac0d0fb94c96b263 shaking-up-ghc.cabal | 4 ++-- src/Main.hs | 10 +++++----- src/{ => Rules}/Selftest.hs | 2 +- src/{ => Rules}/Test.hs | 2 +- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 2ab8ee7..6435d30 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -63,10 +63,11 @@ executable ghc-shake , Rules.Program , Rules.Register , Rules.Resources + , Rules.Selftest , Rules.Setup + , Rules.Test , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg - , Selftest , Settings , Settings.Args , Settings.Builders.Alex @@ -106,7 +107,6 @@ executable ghc-shake , Settings.Ways , Stage , Target - , Test , Way default-language: Haskell2010 diff --git a/src/Main.hs b/src/Main.hs index e028597..5de50ad 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -8,8 +8,8 @@ import qualified Environment import qualified Rules import qualified Rules.Clean import qualified Rules.Oracles -import qualified Selftest -import qualified Test +import qualified Rules.Selftest +import qualified Rules.Test main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -23,10 +23,10 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do rules = mconcat [ Rules.Clean.cleanRules , Rules.Oracles.oracleRules + , Rules.Selftest.selftestRules + , Rules.Test.testRules , Rules.buildRules - , Rules.topLevelTargets - , Selftest.selftestRules - , Test.testRules ] + , Rules.topLevelTargets ] options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Selftest.hs b/src/Rules/Selftest.hs similarity index 94% rename from src/Selftest.hs rename to src/Rules/Selftest.hs index 4800ca8..a3cc089 100644 --- a/src/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -module Selftest (selftestRules) where +module Rules.Selftest (selftestRules) where import Development.Shake import Settings.Builders.Ar (chunksOfSize) diff --git a/src/Test.hs b/src/Rules/Test.hs similarity index 98% rename from src/Test.hs rename to src/Rules/Test.hs index 3ef0d1d..0448b2b 100644 --- a/src/Test.hs +++ b/src/Rules/Test.hs @@ -1,4 +1,4 @@ -module Test (testRules) where +module Rules.Test (testRules) where import Base import Builder From git at git.haskell.org Fri Oct 27 00:20:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #275 from michalt/compilermode/1 (e89ab5c) Message-ID: <20171027002002.21FB83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e89ab5c63394d13793b32b391923945154c4c87d/ghc >--------------------------------------------------------------- commit e89ab5c63394d13793b32b391923945154c4c87d Merge: 4a7016b a8abbc9 Author: Andrey Mokhov Date: Sat Jul 23 20:03:13 2016 +0200 Merge pull request #275 from michalt/compilermode/1 Split CompilerMode for GHC and CC >--------------------------------------------------------------- e89ab5c63394d13793b32b391923945154c4c87d src/Builder.hs | 27 +++++++++++++++++---------- src/Predicate.hs | 8 +++++++- src/Rules/Compile.hs | 6 +++--- src/Rules/Dependencies.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Test.hs | 4 ++-- src/Settings/Builders/Cc.hs | 4 ++-- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- 13 files changed, 46 insertions(+), 33 deletions(-) diff --cc src/Rules/Dependencies.hs index c64a4e6,94a9542..8aeecf5 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@@ -22,9 -20,8 +22,9 @@@ buildPackageDependencies rs context at Con fmap (path ++) [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do let src = dep2src context out + when (package == integerGmp) (need [gmpLibraryH]) need [src] - build $ Target context (Cc FindDependencies stage) [src] [out] + build $ Target context (Cc FindCDependencies stage) [src] [out] hDepFile %> \out -> do srcs <- haskellSources context From git at git.haskell.org Fri Oct 27 00:20:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add custom predicate builderGhc for Ghc/GhcM builders. (7ca8be7) Message-ID: <20171027002005.09DEF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ca8be77837fed2ebb05d369996edd6ee5d72b8e/ghc >--------------------------------------------------------------- commit 7ca8be77837fed2ebb05d369996edd6ee5d72b8e Author: Andrey Mokhov Date: Wed Dec 30 03:04:12 2015 +0000 Add custom predicate builderGhc for Ghc/GhcM builders. >--------------------------------------------------------------- 7ca8be77837fed2ebb05d369996edd6ee5d72b8e src/Predicates.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 28dd51a..7f590f4 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,6 +1,6 @@ -- | Convenient predicates module Predicates ( - stage, package, builder, stagedBuilder, file, way, + stage, package, builder, stagedBuilder, builderGhc, file, way, stage0, stage1, stage2, notStage0, notPackage, registerPackage, splitObjects ) where @@ -24,6 +24,9 @@ builder b = fmap (b ==) getBuilder stagedBuilder :: (Stage -> Builder) -> Predicate stagedBuilder sb = (builder . sb) =<< getStage +builderGhc :: Predicate +builderGhc = stagedBuilder Ghc ||^ stagedBuilder GhcM + file :: FilePattern -> Predicate file f = fmap (any (f ?==)) getOutputs From git at git.haskell.org Fri Oct 27 00:20:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Rules/Package.hs into Rules.hs. (a10669a) Message-ID: <20171027002005.1BE393A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a10669a6788da387e9e5a3e6fe35383589f22ac1/ghc >--------------------------------------------------------------- commit a10669a6788da387e9e5a3e6fe35383589f22ac1 Author: Andrey Mokhov Date: Sun Feb 14 23:21:54 2016 +0000 Move Rules/Package.hs into Rules.hs. >--------------------------------------------------------------- a10669a6788da387e9e5a3e6fe35383589f22ac1 shaking-up-ghc.cabal | 1 - src/Rules.hs | 21 +++++++++++++++++++-- src/Rules/Package.hs | 24 ------------------------ 3 files changed, 19 insertions(+), 27 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 6435d30..193b04e 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -58,7 +58,6 @@ executable ghc-shake , Rules.Libffi , Rules.Library , Rules.Oracles - , Rules.Package , Rules.Perl , Rules.Program , Rules.Register diff --git a/src/Rules.hs b/src/Rules.hs index 5cbfa7e..cea2c0d 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,13 +5,19 @@ import Data.Foldable import Base import Expression import GHC +import qualified Rules.Compile +import qualified Rules.Data +import qualified Rules.Dependencies +import qualified Rules.Documentation import qualified Rules.Generate -import qualified Rules.Package import qualified Rules.Resources import qualified Rules.Cabal import qualified Rules.Gmp import qualified Rules.Libffi +import qualified Rules.Library import qualified Rules.Perl +import qualified Rules.Program +import qualified Rules.Register import qualified Rules.Setup import Settings @@ -50,7 +56,18 @@ packageRules = do resources <- Rules.Resources.resourceRules for_ allStages $ \stage -> for_ knownPackages $ \pkg -> - Rules.Package.buildPackage resources $ vanillaContext stage pkg + buildPackage resources $ vanillaContext stage pkg + +buildPackage :: Rules.Resources.Resources -> Context -> Rules () +buildPackage = mconcat + [ Rules.Compile.compilePackage + , Rules.Data.buildPackageData + , Rules.Dependencies.buildPackageDependencies + , Rules.Documentation.buildPackageDocumentation + , Rules.Generate.generatePackageCode + , Rules.Library.buildPackageLibrary + , Rules.Program.buildProgram + , Rules.Register.registerPackage ] buildRules :: Rules () buildRules = mconcat diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs deleted file mode 100644 index 26de923..0000000 --- a/src/Rules/Package.hs +++ /dev/null @@ -1,24 +0,0 @@ -module Rules.Package (buildPackage) where - -import Base -import Context -import qualified Rules.Compile -import qualified Rules.Data -import qualified Rules.Dependencies -import qualified Rules.Documentation -import qualified Rules.Generate -import qualified Rules.Library -import qualified Rules.Program -import qualified Rules.Register -import Rules.Resources - -buildPackage :: Resources -> Context -> Rules () -buildPackage = mconcat - [ Rules.Compile.compilePackage - , Rules.Data.buildPackageData - , Rules.Dependencies.buildPackageDependencies - , Rules.Documentation.buildPackageDocumentation - , Rules.Generate.generatePackageCode - , Rules.Library.buildPackageLibrary - , Rules.Program.buildProgram - , Rules.Register.registerPackage ] From git at git.haskell.org Fri Oct 27 00:20:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use nm-classic instead of nm when host is Darwin (3c31edc) Message-ID: <20171027002006.086143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c31edcca75f477bfeb54cd844c9d2f575037c3c/ghc >--------------------------------------------------------------- commit 3c31edcca75f477bfeb54cd844c9d2f575037c3c Author: Tomas Carnecky Date: Sun Jul 24 00:03:59 2016 +0200 Use nm-classic instead of nm when host is Darwin >--------------------------------------------------------------- 3c31edcca75f477bfeb54cd844c9d2f575037c3c README.md | 8 -------- src/Settings/Builders/Configure.hs | 7 +++++++ 2 files changed, 7 insertions(+), 8 deletions(-) diff --git a/README.md b/README.md index 4ce3b3a..d99d2b7 100644 --- a/README.md +++ b/README.md @@ -43,14 +43,6 @@ runs the `boot` and `configure` scripts automatically on the first build, so tha need to. Use `--skip-configure` to suppress this behaviour (see overview of command line flags below). -* Also note on OS X newer versions of XCode ship with a broken `nm` tool -([#11744](https://ghc.haskell.org/trac/ghc/ticket/11744)). One way to mitigate the -problem is to add the following into your `UserSettings.hs`: - ````haskell - userArgs :: Args - userArgs = builder (Configure ".") ? arg "--with-nm=$(xcrun --find nm-classic)" - ```` - Using the build system ---------------------- Once your first build is successful, simply run `build` to rebuild. Most build artefacts diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index c95a5da..6482df1 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -1,5 +1,7 @@ module Settings.Builders.Configure (configureBuilderArgs) where +import qualified System.Info as System + import Base import Oracles.Config.Setting import Oracles.WindowsPath @@ -23,4 +25,9 @@ configureBuilderArgs = mconcat , "--enable-static=yes" , "--enable-shared=no" -- TODO: add support for yes , "--host=" ++ targetPlatform ] + + -- On OS X, use "nm-classic" instead of "nm" due to a bug in the later. + -- See https://ghc.haskell.org/trac/ghc/ticket/11744 + , builder (Configure ".") ? System.os == "darwin" ? + arg "--with-nm=$(xcrun --find nm-classic)" ] From git at git.haskell.org Fri Oct 27 00:20:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Settings/Builders/Ghc.hs (see #60). (8ba5827) Message-ID: <20171027002009.0BB1D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ba5827108393cf6c37fff802db0126500e2bd0a/ghc >--------------------------------------------------------------- commit 8ba5827108393cf6c37fff802db0126500e2bd0a Author: Andrey Mokhov Date: Wed Dec 30 03:07:45 2015 +0000 Decompose Settings/Builders/Ghc.hs (see #60). >--------------------------------------------------------------- 8ba5827108393cf6c37fff802db0126500e2bd0a shaking-up-ghc.cabal | 4 ++++ src/Settings/Args.hs | 12 ++++++++++-- src/Settings/Builders/GenPrimopCode.hs | 1 - src/Settings/Builders/Ghc.hs | 35 ++++------------------------------ src/Settings/Builders/GhcCabal.hs | 3 +-- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Packages/Compiler.hs | 14 +++++++++----- src/Settings/Packages/Directory.hs | 6 +++--- src/Settings/Packages/Ghc.hs | 13 +++++++++++++ src/Settings/Packages/GhcCabal.hs | 34 +++++++++++++++++++++++++++++++++ src/Settings/Packages/Hp2ps.hs | 16 ++++++++++++++++ src/Settings/Packages/RunGhc.hs | 13 +++++++++++++ 12 files changed, 108 insertions(+), 45 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 8ba5827108393cf6c37fff802db0126500e2bd0a From git at git.haskell.org Fri Oct 27 00:20:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused Resources parameter. (010fb8c) Message-ID: <20171027002009.770E93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/010fb8c148ae0d0c08236c19e74e214968d45410/ghc >--------------------------------------------------------------- commit 010fb8c148ae0d0c08236c19e74e214968d45410 Author: Andrey Mokhov Date: Sun Feb 14 23:30:15 2016 +0000 Drop unused Resources parameter. >--------------------------------------------------------------- 010fb8c148ae0d0c08236c19e74e214968d45410 src/Rules.hs | 23 ++++++++++------------- src/Rules/Data.hs | 5 ++--- src/Rules/Documentation.hs | 5 ++--- src/Rules/Generate.hs | 5 ++--- src/Rules/Library.hs | 5 ++--- src/Rules/Program.hs | 5 ++--- 6 files changed, 20 insertions(+), 28 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index cea2c0d..be71d2f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -55,19 +55,16 @@ packageRules :: Rules () packageRules = do resources <- Rules.Resources.resourceRules for_ allStages $ \stage -> - for_ knownPackages $ \pkg -> - buildPackage resources $ vanillaContext stage pkg - -buildPackage :: Rules.Resources.Resources -> Context -> Rules () -buildPackage = mconcat - [ Rules.Compile.compilePackage - , Rules.Data.buildPackageData - , Rules.Dependencies.buildPackageDependencies - , Rules.Documentation.buildPackageDocumentation - , Rules.Generate.generatePackageCode - , Rules.Library.buildPackageLibrary - , Rules.Program.buildProgram - , Rules.Register.registerPackage ] + for_ knownPackages $ \package -> do + let context = vanillaContext stage package + Rules.Compile.compilePackage resources context + Rules.Data.buildPackageData context + Rules.Dependencies.buildPackageDependencies resources context + Rules.Documentation.buildPackageDocumentation context + Rules.Generate.generatePackageCode context + Rules.Library.buildPackageLibrary context + Rules.Program.buildProgram context + Rules.Register.registerPackage resources context buildRules :: Rules () buildRules = mconcat diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 7386003..f47e8d0 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -12,14 +12,13 @@ import Oracles.PackageDeps import Rules.Actions import Rules.Generate import Rules.Libffi -import Rules.Resources import Settings import Settings.Builders.Common import Target -- Build package-data.mk by using GhcCabal to process pkgCabal file -buildPackageData :: Resources -> Context -> Rules () -buildPackageData _ context @ (Context {..}) = do +buildPackageData :: Context -> Rules () +buildPackageData context @ (Context {..}) = do let cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile stage package diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 95a5667..848a3fa 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -7,7 +7,6 @@ import Expression import GHC import Oracles.PackageData import Rules.Actions -import Rules.Resources import Settings import Target @@ -17,8 +16,8 @@ haddockHtmlLib = "inplace/lib/html/haddock-util.js" -- Note: this build rule creates plenty of files, not just the .haddock one. -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. -buildPackageDocumentation :: Resources -> Context -> Rules () -buildPackageDocumentation _ context @ (Context {..}) = +buildPackageDocumentation :: Context -> Rules () +buildPackageDocumentation context @ (Context {..}) = let cabalFile = pkgCabalFile package haddockFile = pkgHaddockFile package in when (stage == Stage1) $ do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 1a8a239..050f83c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -20,7 +20,6 @@ import Oracles.ModuleFiles import Rules.Actions import Rules.Gmp import Rules.Libffi -import Rules.Resources (Resources) import Settings import Target hiding (builder, context) @@ -114,8 +113,8 @@ generate file context expr = do writeFileChanged file contents putSuccess $ "| Successfully generated '" ++ file ++ "'." -generatePackageCode :: Resources -> Context -> Rules () -generatePackageCode _ context @ (Context stage pkg _) = +generatePackageCode :: Context -> Rules () +generatePackageCode context @ (Context stage pkg _) = let buildPath = targetPath stage pkg -/- "build" dropBuild = drop (length buildPath + 1) generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index be8f158..79b4952 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -11,13 +11,12 @@ import GHC import Oracles.PackageData import Rules.Actions import Rules.Gmp -import Rules.Resources import Settings import Target -- TODO: Use way from Context, #207 -buildPackageLibrary :: Resources -> Context -> Rules () -buildPackageLibrary _ context @ (Context {..}) = do +buildPackageLibrary :: Context -> Rules () +buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" -- TODO: handle dynamic libraries diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 00f4c52..d7fdaad 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -11,7 +11,6 @@ import Oracles.Config.Setting import Oracles.PackageData import Rules.Actions import Rules.Library -import Rules.Resources import Rules.Wrappers.Ghc import Rules.Wrappers.GhcPkg import Settings @@ -32,8 +31,8 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper)] -buildProgram :: Resources -> Context -> Rules () -buildProgram _ context @ (Context {..}) = do +buildProgram :: Context -> Rules () +buildProgram context @ (Context {..}) = do let match file = case programPath stage package of Nothing -> False Just program -> program == file From git at git.haskell.org Fri Oct 27 00:20:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use in-tree cabal in build.cabal.sh (works for cabal < 1.24) (fc4c968) Message-ID: <20171027002009.EB8F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fc4c968378c1d4467cf59e8bbaefa66f473526f7/ghc >--------------------------------------------------------------- commit fc4c968378c1d4467cf59e8bbaefa66f473526f7 Author: Kai Harries Date: Sun Jul 24 11:37:08 2016 +0200 Use in-tree cabal in build.cabal.sh (works for cabal < 1.24) Partial fix of #274 This installs the in-tree Cabal into the cabal-sandbox before building hadrian itself. This only works if the installed cabal version is < 1.24, because I have not yet figured out how it can be done with the newly introduced `new-build` command. >--------------------------------------------------------------- fc4c968378c1d4467cf59e8bbaefa66f473526f7 build.cabal.sh | 5 +++++ hadrian.cabal | 2 +- 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index 4a24dac..be2a117 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -61,6 +61,11 @@ else # Initialize sandbox if necessary if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then "$CABAL" sandbox init + ( cd ../libraries/Cabal/Cabal + ln -s "$absoluteRoot/cabal.sandbox.config" cabal.sandbox.config + cabal install + rm cabal.sandbox.config + ) "$CABAL" install \ --dependencies-only \ --disable-library-profiling \ diff --git a/hadrian.cabal b/hadrian.cabal index 63bd164..c07cef1 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* || == 1.24.* || == 1.25.* + , Cabal >= 1.25 , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 00:20:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a build rule for inplace/lib/settings. (0ceae64) Message-ID: <20171027002012.D576A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ceae64327289b2cb79041cb75ec1e7c92af8546/ghc >--------------------------------------------------------------- commit 0ceae64327289b2cb79041cb75ec1e7c92af8546 Author: Andrey Mokhov Date: Wed Dec 30 15:16:18 2015 +0000 Add a build rule for inplace/lib/settings. >--------------------------------------------------------------- 0ceae64327289b2cb79041cb75ec1e7c92af8546 src/Rules/Install.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 13a0e00..2e74bd3 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -7,12 +7,14 @@ import Rules.Generate installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" - , "inplace/lib/platformConstants" ] + , "inplace/lib/platformConstants" + , "inplace/lib/settings" ] installRules :: Rules () installRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." where file <~ dir = file %> \out -> do let source = dir -/- takeFileName out From git at git.haskell.org Fri Oct 27 00:20:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use do notation to combine Rules. (b820539) Message-ID: <20171027002013.68BA33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b82053913f31548325da535ba769bb21aa4338ec/ghc >--------------------------------------------------------------- commit b82053913f31548325da535ba769bb21aa4338ec Author: Andrey Mokhov Date: Sun Feb 14 23:34:37 2016 +0000 Use do notation to combine Rules. >--------------------------------------------------------------- b82053913f31548325da535ba769bb21aa4338ec src/Main.hs | 14 +++++++------- src/Rules.hs | 18 +++++++++--------- 2 files changed, 16 insertions(+), 16 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 5de50ad..96639d2 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -20,13 +20,13 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do else want targets >> withoutActions rules where rules :: Rules () - rules = mconcat - [ Rules.Clean.cleanRules - , Rules.Oracles.oracleRules - , Rules.Selftest.selftestRules - , Rules.Test.testRules - , Rules.buildRules - , Rules.topLevelTargets ] + rules = do + Rules.Clean.cleanRules + Rules.Oracles.oracleRules + Rules.Selftest.selftestRules + Rules.Test.testRules + Rules.buildRules + Rules.topLevelTargets options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Rules.hs b/src/Rules.hs index be71d2f..e817fc1 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -67,12 +67,12 @@ packageRules = do Rules.Register.registerPackage resources context buildRules :: Rules () -buildRules = mconcat - [ Rules.Cabal.cabalRules - , Rules.Generate.generateRules - , Rules.Generate.copyRules - , Rules.Gmp.gmpRules - , Rules.Libffi.libffiRules - , Rules.Perl.perlScriptRules - , Rules.Setup.setupRules - , Rules.packageRules ] +buildRules = do + Rules.Cabal.cabalRules + Rules.Generate.generateRules + Rules.Generate.copyRules + Rules.Gmp.gmpRules + Rules.Libffi.libffiRules + Rules.Perl.perlScriptRules + Rules.Setup.setupRules + Rules.packageRules From git at git.haskell.org Fri Oct 27 00:20:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert raising of the cabal version in the build-dependency (564b125) Message-ID: <20171027002017.BDA9B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/564b125e3d6df089ca849392be4d97c682e4ae64/ghc >--------------------------------------------------------------- commit 564b125e3d6df089ca849392be4d97c682e4ae64 Author: Kai Harries Date: Sun Jul 24 12:24:16 2016 +0200 Revert raising of the cabal version in the build-dependency Travis was failing because it uses `cabal install --only-dependencies` in the .travis.yml >--------------------------------------------------------------- 564b125e3d6df089ca849392be4d97c682e4ae64 hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index c07cef1..63bd164 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal >= 1.25 + , Cabal == 1.22.* || == 1.24.* || == 1.25.* , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 00:20:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: build.cabal.sh: Use CABAL variable (fd48c37) Message-ID: <20171027002013.9540A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd48c372feb33e9c58c19c04929f9c63492c3b4d/ghc >--------------------------------------------------------------- commit fd48c372feb33e9c58c19c04929f9c63492c3b4d Author: Kai Harries Date: Sun Jul 24 12:15:55 2016 +0200 build.cabal.sh: Use CABAL variable >--------------------------------------------------------------- fd48c372feb33e9c58c19c04929f9c63492c3b4d build.cabal.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index be2a117..3b6bef5 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -63,7 +63,7 @@ else "$CABAL" sandbox init ( cd ../libraries/Cabal/Cabal ln -s "$absoluteRoot/cabal.sandbox.config" cabal.sandbox.config - cabal install + "$CABAL" install rm cabal.sandbox.config ) "$CABAL" install \ From git at git.haskell.org Fri Oct 27 00:20:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for wrappers. (a1eab18) Message-ID: <20171027002017.306303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1eab187eb929d2d82d2f093d4768849978973a4/ghc >--------------------------------------------------------------- commit a1eab187eb929d2d82d2f093d4768849978973a4 Author: Andrey Mokhov Date: Thu Dec 31 00:41:00 2015 +0000 Add support for wrappers. >--------------------------------------------------------------- a1eab187eb929d2d82d2f093d4768849978973a4 src/Rules/Program.hs | 120 ++++++++++++++++++++++++++++++---------------- src/Rules/Wrappers/Ghc.hs | 14 ++++++ src/Target.hs | 2 +- 3 files changed, 94 insertions(+), 42 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a1eab187eb929d2d82d2f093d4768849978973a4 From git at git.haskell.org Fri Oct 27 00:20:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (6a9772a) Message-ID: <20171027002017.653823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a9772a11c4bb3284cf6f3993c4ba25896301a74/ghc >--------------------------------------------------------------- commit 6a9772a11c4bb3284cf6f3993c4ba25896301a74 Author: Andrey Mokhov Date: Sun Feb 14 23:42:17 2016 +0000 Minor revision. >--------------------------------------------------------------- 6a9772a11c4bb3284cf6f3993c4ba25896301a74 src/Main.hs | 1 + src/Rules.hs | 62 ++++++++++++++++++++++++++++++------------------------------ 2 files changed, 32 insertions(+), 31 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 96639d2..cf45cc3 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -27,6 +27,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do Rules.Test.testRules Rules.buildRules Rules.topLevelTargets + options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Rules.hs b/src/Rules.hs index e817fc1..f3db558 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,20 +5,20 @@ import Data.Foldable import Base import Expression import GHC -import qualified Rules.Compile -import qualified Rules.Data -import qualified Rules.Dependencies -import qualified Rules.Documentation -import qualified Rules.Generate -import qualified Rules.Resources -import qualified Rules.Cabal -import qualified Rules.Gmp -import qualified Rules.Libffi -import qualified Rules.Library -import qualified Rules.Perl -import qualified Rules.Program -import qualified Rules.Register -import qualified Rules.Setup +import Rules.Compile +import Rules.Data +import Rules.Dependencies +import Rules.Documentation +import Rules.Generate +import Rules.Resources +import Rules.Cabal +import Rules.Gmp +import Rules.Libffi +import Rules.Library +import Rules.Perl +import Rules.Program +import Rules.Register +import Rules.Setup import Settings allStages :: [Stage] @@ -53,26 +53,26 @@ topLevelTargets = do packageRules :: Rules () packageRules = do - resources <- Rules.Resources.resourceRules + resources <- resourceRules for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package - Rules.Compile.compilePackage resources context - Rules.Data.buildPackageData context - Rules.Dependencies.buildPackageDependencies resources context - Rules.Documentation.buildPackageDocumentation context - Rules.Generate.generatePackageCode context - Rules.Library.buildPackageLibrary context - Rules.Program.buildProgram context - Rules.Register.registerPackage resources context + compilePackage resources context + buildPackageData context + buildPackageDependencies resources context + buildPackageDocumentation context + generatePackageCode context + buildPackageLibrary context + buildProgram context + registerPackage resources context buildRules :: Rules () buildRules = do - Rules.Cabal.cabalRules - Rules.Generate.generateRules - Rules.Generate.copyRules - Rules.Gmp.gmpRules - Rules.Libffi.libffiRules - Rules.Perl.perlScriptRules - Rules.Setup.setupRules - Rules.packageRules + cabalRules + generateRules + copyRules + gmpRules + libffiRules + perlScriptRules + setupRules + packageRules From git at git.haskell.org Fri Oct 27 00:20:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing sources. (109a6f8) Message-ID: <20171027002021.A9D443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/109a6f843864def992865b81b0fea462e0fad7b4/ghc >--------------------------------------------------------------- commit 109a6f843864def992865b81b0fea462e0fad7b4 Author: Andrey Mokhov Date: Thu Dec 31 01:08:26 2015 +0000 Add missing sources. >--------------------------------------------------------------- 109a6f843864def992865b81b0fea462e0fad7b4 shaking-up-ghc.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index b60bf46..e7c3e28 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -54,6 +54,7 @@ executable ghc-shake , Rules.Package , Rules.Program , Rules.Resources + , Rules.Wrappers.Ghc , Settings , Settings.Args , Settings.Builders.Alex From git at git.haskell.org Fri Oct 27 00:20:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Rules.Resources, move packageDb resource to buildRules. (2fc7bd3) Message-ID: <20171027002022.0AB593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2fc7bd3ee96d07862b240e8ddcfb584de56a040c/ghc >--------------------------------------------------------------- commit 2fc7bd3ee96d07862b240e8ddcfb584de56a040c Author: Andrey Mokhov Date: Mon Feb 15 23:20:41 2016 +0000 Drop Rules.Resources, move packageDb resource to buildRules. >--------------------------------------------------------------- 2fc7bd3ee96d07862b240e8ddcfb584de56a040c shaking-up-ghc.cabal | 1 - src/Rules.hs | 26 ++++++++++++++++---------- src/Rules/Compile.hs | 11 +++++------ src/Rules/Dependencies.hs | 5 ++--- src/Rules/Register.hs | 7 +++---- src/Rules/Resources.hs | 17 ----------------- 6 files changed, 26 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2fc7bd3ee96d07862b240e8ddcfb584de56a040c From git at git.haskell.org Fri Oct 27 00:20:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use in-tree cabal in build.cabal.sh (for cabal >= 1.24) (3724023) Message-ID: <20171027002022.4864E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37240234b116c9aa90a5a0e893a94813373ad158/ghc >--------------------------------------------------------------- commit 37240234b116c9aa90a5a0e893a94813373ad158 Author: Kai Harries Date: Sun Jul 24 13:48:10 2016 +0200 Use in-tree cabal in build.cabal.sh (for cabal >= 1.24) >--------------------------------------------------------------- 37240234b116c9aa90a5a0e893a94813373ad158 cabal.project | 2 ++ 1 file changed, 2 insertions(+) diff --git a/cabal.project b/cabal.project new file mode 100644 index 0000000..1ef81ca --- /dev/null +++ b/cabal.project @@ -0,0 +1,2 @@ +packages: ../libraries/Cabal/Cabal/ + ./ From git at git.haskell.org Fri Oct 27 00:20:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Settings/Builders/GhcCabal.hs (see #60). (7cf7210) Message-ID: <20171027002025.925AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7cf7210ecee07729579f630ee93fa694e8e16635/ghc >--------------------------------------------------------------- commit 7cf7210ecee07729579f630ee93fa694e8e16635 Author: Andrey Mokhov Date: Thu Dec 31 02:20:32 2015 +0000 Decompose Settings/Builders/GhcCabal.hs (see #60). >--------------------------------------------------------------- 7cf7210ecee07729579f630ee93fa694e8e16635 shaking-up-ghc.cabal | 5 ++ src/Settings/Args.hs | 13 +++- src/Settings/Builders/Common.hs | 36 ++++++++++- src/Settings/Builders/DeriveConstants.hs | 7 +-- src/Settings/Builders/GhcCabal.hs | 102 ++----------------------------- src/Settings/Builders/Hsc2Hs.hs | 7 +-- src/Settings/Packages/Base.hs | 11 ++++ src/Settings/Packages/Compiler.hs | 32 +++++++++- src/Settings/Packages/Ghc.hs | 12 ++-- src/Settings/Packages/GhcPrim.hs | 9 +++ src/Settings/Packages/Haddock.hs | 9 +++ src/Settings/Packages/IntegerGmp.hs | 19 ++++++ 12 files changed, 145 insertions(+), 117 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 7cf7210ecee07729579f630ee93fa694e8e16635 From git at git.haskell.org Fri Oct 27 00:20:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop GranSim way unit. (de8ca62) Message-ID: <20171027002026.427C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de8ca62e36c5202e8e430c6649313228f529d226/ghc >--------------------------------------------------------------- commit de8ca62e36c5202e8e430c6649313228f529d226 Author: Andrey Mokhov Date: Tue Feb 16 00:01:47 2016 +0000 Drop GranSim way unit. >--------------------------------------------------------------- de8ca62e36c5202e8e430c6649313228f529d226 src/Settings/Builders/Ghc.hs | 1 - src/Way.hs | 7 +------ 2 files changed, 1 insertion(+), 7 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 51fde7f..96737f4 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -102,7 +102,6 @@ wayGhcArgs = do , (Profiling `wayUnit` way) ? arg "-prof" , (Logging `wayUnit` way) ? arg "-eventlog" , (Parallel `wayUnit` way) ? arg "-parallel" - , (GranSim `wayUnit` way) ? arg "-gransim" , (way == debug || way == debugDynamic) ? append ["-ticky", "-DTICKY_TICKY"] ] diff --git a/src/Way.hs b/src/Way.hs index a301afe..59bbbc9 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, wayFromUnits, - vanilla, profiling, logging, parallel, granSim, + vanilla, profiling, logging, parallel, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, @@ -27,7 +27,6 @@ data WayUnit = Threaded | Logging | Dynamic | Parallel - | GranSim deriving (Eq, Enum, Bounded) -- TODO: get rid of non-derived Show instances @@ -39,7 +38,6 @@ instance Show WayUnit where Logging -> "l" Dynamic -> "dyn" Parallel -> "mp" - GranSim -> "gm" instance Read WayUnit where readsPrec _ s = [(unit, "") | unit <- [minBound ..], show unit == s] @@ -96,9 +94,6 @@ logging = wayFromUnits [Logging] parallel :: Way parallel = wayFromUnits [Parallel] -granSim :: Way -granSim = wayFromUnits [GranSim] - -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? -- See compiler/main/DynFlags.hs. From git at git.haskell.org Fri Oct 27 00:20:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use `add-source` instead of linking cabal.sandbox.config (ea51eaa) Message-ID: <20171027002026.81CCE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ea51eaad8e5b8eb64183fa169224ab2df61a63b9/ghc >--------------------------------------------------------------- commit ea51eaad8e5b8eb64183fa169224ab2df61a63b9 Author: Kai Harries Date: Sun Jul 24 15:17:56 2016 +0200 Use `add-source` instead of linking cabal.sandbox.config As suggested by mpickering >--------------------------------------------------------------- ea51eaad8e5b8eb64183fa169224ab2df61a63b9 build.cabal.sh | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/build.cabal.sh b/build.cabal.sh index 3b6bef5..973cd3e 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -61,11 +61,7 @@ else # Initialize sandbox if necessary if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then "$CABAL" sandbox init - ( cd ../libraries/Cabal/Cabal - ln -s "$absoluteRoot/cabal.sandbox.config" cabal.sandbox.config - "$CABAL" install - rm cabal.sandbox.config - ) + "$CABAL" sandbox add-source ../libraries/Cabal/Cabal "$CABAL" install \ --dependencies-only \ --disable-library-profiling \ From git at git.haskell.org Fri Oct 27 00:20:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track wrapped binary. (49521c0) Message-ID: <20171027002029.5E9593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49521c02bdd181b57713c8f3e2bf111416b0df37/ghc >--------------------------------------------------------------- commit 49521c02bdd181b57713c8f3e2bf111416b0df37 Author: Andrey Mokhov Date: Thu Dec 31 02:28:23 2015 +0000 Track wrapped binary. >--------------------------------------------------------------- 49521c02bdd181b57713c8f3e2bf111416b0df37 src/Rules/Program.hs | 18 ++++++++++++------ 1 file changed, 12 insertions(+), 6 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 93c6a97..a1aaa2f 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -29,6 +29,11 @@ buildProgram _ target @ (PartialTarget stage pkg) = do let match file = case programPath stage pkg of Nothing -> False Just program -> program == file + matchWrapped file = case programPath stage pkg of + Nothing -> False + Just program -> case computeWrappedPath program of + Nothing -> False + Just wrappedProgram -> wrappedProgram == file match ?> \bin -> do windows <- windowsHost @@ -37,15 +42,16 @@ buildProgram _ target @ (PartialTarget stage pkg) = do else case find ((== target) . fst) wrappers of Nothing -> buildBinary target bin -- No wrapper found Just (_, wrapper) -> do - wrappedBin <- moveToLib bin - buildBinary target wrappedBin + let Just wrappedBin = computeWrappedPath bin + need [wrappedBin] buildWrapper target wrapper bin wrappedBin + matchWrapped ?> \bin -> buildBinary target bin + -- Replace programInplacePath with programInplaceLibPath in a given path -moveToLib :: FilePath -> Action FilePath -moveToLib path = case stripPrefix programInplacePath path of - Just suffix -> return $ programInplaceLibPath ++ suffix - Nothing -> putError $ "moveToLib: cannot move " ++ path +computeWrappedPath :: FilePath -> Maybe FilePath +computeWrappedPath = + fmap (programInplaceLibPath ++) . stripPrefix programInplacePath buildWrapper :: PartialTarget -> Wrapper -> FilePath -> FilePath -> Action () buildWrapper target @ (PartialTarget stage pkg) wrapper wrapperPath binPath = do From git at git.haskell.org Fri Oct 27 00:20:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Parallel way unit. (49a7cb2) Message-ID: <20171027002030.B4C0C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49a7cb2fb676a1b0a7a9b4235aaa198b9ce0d8db/ghc >--------------------------------------------------------------- commit 49a7cb2fb676a1b0a7a9b4235aaa198b9ce0d8db Author: Andrey Mokhov Date: Tue Feb 16 00:04:46 2016 +0000 Drop Parallel way unit. >--------------------------------------------------------------- 49a7cb2fb676a1b0a7a9b4235aaa198b9ce0d8db src/Settings/Builders/Ghc.hs | 1 - src/Way.hs | 8 +------- 2 files changed, 1 insertion(+), 8 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 96737f4..ef3130f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -101,7 +101,6 @@ wayGhcArgs = do , (Debug `wayUnit` way) ? arg "-optc-DDEBUG" , (Profiling `wayUnit` way) ? arg "-prof" , (Logging `wayUnit` way) ? arg "-eventlog" - , (Parallel `wayUnit` way) ? arg "-parallel" , (way == debug || way == debugDynamic) ? append ["-ticky", "-DTICKY_TICKY"] ] diff --git a/src/Way.hs b/src/Way.hs index 59bbbc9..6d034e9 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, wayFromUnits, - vanilla, profiling, logging, parallel, + vanilla, profiling, logging, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, @@ -26,7 +26,6 @@ data WayUnit = Threaded | Profiling | Logging | Dynamic - | Parallel deriving (Eq, Enum, Bounded) -- TODO: get rid of non-derived Show instances @@ -37,7 +36,6 @@ instance Show WayUnit where Profiling -> "p" Logging -> "l" Dynamic -> "dyn" - Parallel -> "mp" instance Read WayUnit where readsPrec _ s = [(unit, "") | unit <- [minBound ..], show unit == s] @@ -90,10 +88,6 @@ profiling = wayFromUnits [Profiling] logging :: Way logging = wayFromUnits [Logging] --- | Build in parallel. -parallel :: Way -parallel = wayFromUnits [Parallel] - -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? -- See compiler/main/DynFlags.hs. From git at git.haskell.org Fri Oct 27 00:20:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #277 from KaiHa/ticket274 (eff3e36) Message-ID: <20171027002030.D86733A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eff3e36640d0c72e34411acdcbaef71646d884ae/ghc >--------------------------------------------------------------- commit eff3e36640d0c72e34411acdcbaef71646d884ae Merge: e89ab5c ea51eaa Author: Andrey Mokhov Date: Sun Jul 24 17:51:26 2016 +0200 Merge pull request #277 from KaiHa/ticket274 Use in-tree cabal in build.cabal.sh >--------------------------------------------------------------- eff3e36640d0c72e34411acdcbaef71646d884ae build.cabal.sh | 1 + cabal.project | 2 ++ 2 files changed, 3 insertions(+) From git at git.haskell.org Fri Oct 27 00:20:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fixes the -B path for the ghcWrapper. (d9d00b8) Message-ID: <20171027002032.BC8443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9d00b86b79d998a288c5a2ffd2520d01b9c72e5/ghc >--------------------------------------------------------------- commit d9d00b86b79d998a288c5a2ffd2520d01b9c72e5 Author: Moritz Angermann Date: Thu Dec 31 10:40:37 2015 +0800 Fixes the -B path for the ghcWrapper. >--------------------------------------------------------------- d9d00b86b79d998a288c5a2ffd2520d01b9c72e5 src/Rules/Wrappers/Ghc.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Wrappers/Ghc.hs b/src/Rules/Wrappers/Ghc.hs index 93ceba0..c24bb70 100644 --- a/src/Rules/Wrappers/Ghc.hs +++ b/src/Rules/Wrappers/Ghc.hs @@ -11,4 +11,4 @@ ghcWrapper program = do return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) - ++ " -B" ++ (top -/- takeDirectory program) ++ " ${1+\"$@\"}" ] + ++ " -B" ++ (top -/- "inplace" -/- "lib") ++ " ${1+\"$@\"}" ] From git at git.haskell.org Fri Oct 27 00:20:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do not hide Shake.parallel (we no longer have conflicting Way.parallel). (cfb1331) Message-ID: <20171027002034.80D433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cfb1331d6c0f338fb3998c6fd3a25759fbd9f4c9/ghc >--------------------------------------------------------------- commit cfb1331d6c0f338fb3998c6fd3a25759fbd9f4c9 Author: Andrey Mokhov Date: Tue Feb 16 00:08:25 2016 +0000 Do not hide Shake.parallel (we no longer have conflicting Way.parallel). >--------------------------------------------------------------- cfb1331d6c0f338fb3998c6fd3a25759fbd9f4c9 src/Base.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 464c1c9..1a06120 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel - module Base ( -- * General utilities module Control.Applicative, @@ -35,7 +33,7 @@ import Data.Function import Data.List.Extra import Data.Maybe import Data.Monoid -import Development.Shake hiding (parallel, unit, (*>), Normal) +import Development.Shake hiding (unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Fri Oct 27 00:20:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make generatedDependencies an Expr [FilePath] (234b41b) Message-ID: <20171027002034.BD9C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/234b41b171ad31ecbfec476f8f47202cac6f10cc/ghc >--------------------------------------------------------------- commit 234b41b171ad31ecbfec476f8f47202cac6f10cc Author: Michal Terepeta Date: Sun Jul 24 16:37:11 2016 +0200 Make generatedDependencies an Expr [FilePath] This fixes a TODO to change the `generatedDependencies` to use `Expr`. Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 234b41b171ad31ecbfec476f8f47202cac6f10cc src/Rules/Data.hs | 12 ++++---- src/Rules/Generate.hs | 79 ++++++++++++++++++++++++++++----------------------- 2 files changed, 49 insertions(+), 42 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 959a7ec..4208570 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -25,7 +25,7 @@ buildPackageData context at Context {..} = do inTreeMk %> \mk -> do -- Make sure all generated dependencies are in place before proceeding. - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies -- GhcCabal may run the configure script, so we depend on it. whenM (doesFileExist $ configure <.> "ac") $ need [configure] @@ -59,7 +59,7 @@ buildPackageData context at Context {..} = do -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps. priority 2.0 $ do when (package == hp2ps) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies includes <- interpretInContext context $ fromDiffExpr includesArgs let prefix = fixKey (buildPath context) ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" @@ -76,7 +76,7 @@ buildPackageData context at Context {..} = do putSuccess $ "| Successfully generated " ++ mk when (package == unlit) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies let prefix = fixKey (buildPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = unlit" @@ -86,7 +86,7 @@ buildPackageData context at Context {..} = do putSuccess $ "| Successfully generated " ++ mk when (package == touchy) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies let prefix = fixKey (buildPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = touchy" @@ -98,7 +98,7 @@ buildPackageData context at Context {..} = do -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. when (package == ghcCabal && stage == Stage0) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies let prefix = fixKey (buildPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = ghc-cabal" @@ -110,7 +110,7 @@ buildPackageData context at Context {..} = do when (package == rts && stage == Stage1) $ do dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies windows <- windowsHost let prefix = fixKey (buildPath context) ++ "_" dirs = [ ".", "hooks", "sm", "eventlog", "linker" ] diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 17f51a5..415692b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -10,6 +10,8 @@ import Context import Expression import GHC import Oracles.ModuleFiles +import Predicate ( (?) ) +import qualified Predicate as Predicate import Rules.Actions import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH @@ -46,10 +48,11 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -ghcPrimDependencies :: Stage -> [FilePath] -ghcPrimDependencies stage = (buildPath (vanillaContext stage ghcPrim) -/-) <$> - [ "autogen/GHC/Prim.hs" - , "GHC/PrimopWrappers.hs" ] +ghcPrimDependencies :: Expr [FilePath] +ghcPrimDependencies = getStage >>= \stage -> + let prependPath x = buildPath (vanillaContext stage ghcPrim) -/- x + in return $ + fmap prependPath [ "autogen/GHC/Prim.hs" , "GHC/PrimopWrappers.hs" ] derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" @@ -61,39 +64,43 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) , "GHCConstantsHaskellType.hs" , "GHCConstantsHaskellWrappers.hs" ] -compilerDependencies :: Stage -> [FilePath] -compilerDependencies stage = - [ platformH stage ] - ++ includesDependencies - ++ [ gmpLibraryH | stage > Stage0 ] - ++ filter (const $ stage > Stage0) libffiDependencies - ++ derivedConstantsDependencies - ++ fmap (buildPath (vanillaContext stage compiler) -/-) - [ "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-fixity.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-list.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-strictness.hs-incl" - , "primop-tag.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tys.hs-incl" - , "primop-vector-uniques.hs-incl" ] - --- TODO: Turn this into a FilePaths expression -generatedDependencies :: Stage -> Package -> [FilePath] -generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage - | pkg == ghcPrim = ghcPrimDependencies stage - | pkg == rts = libffiDependencies ++ includesDependencies +compilerDependencies :: Expr [FilePath] +compilerDependencies = getStage >>= \stage -> + let prependBuildPath x = buildPath (vanillaContext stage compiler) -/- x + in mconcat $ + [ return $ (platformH stage) + : includesDependencies ++ derivedConstantsDependencies - | stage == Stage0 = includesDependencies - | otherwise = [] + , Predicate.notStage0 ? return (gmpLibraryH : libffiDependencies) + , return $ fmap prependBuildPath + [ "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-fixity.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-list.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-strictness.hs-incl" + , "primop-tag.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tys.hs-incl" + , "primop-vector-uniques.hs-incl" + ] + ] + +generatedDependencies :: Expr [FilePath] +generatedDependencies = mconcat + [ Predicate.package compiler ? compilerDependencies + , Predicate.package ghcPrim ? ghcPrimDependencies + , Predicate.package rts ? return ( + libffiDependencies + ++ includesDependencies + ++ derivedConstantsDependencies) + , Predicate.stage0 ? return includesDependencies + ] generate :: FilePath -> Context -> Expr String -> Action () generate file context expr = do From git at git.haskell.org Fri Oct 27 00:20:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decompose Settings/Builders/Haddock.hs (see #60). (4ade862) Message-ID: <20171027002036.49CB53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ade862d347dd04e9e61abcd0aa96a6864cb5962/ghc >--------------------------------------------------------------- commit 4ade862d347dd04e9e61abcd0aa96a6864cb5962 Author: Andrey Mokhov Date: Thu Dec 31 02:53:36 2015 +0000 Decompose Settings/Builders/Haddock.hs (see #60). >--------------------------------------------------------------- 4ade862d347dd04e9e61abcd0aa96a6864cb5962 src/Settings/Builders/Haddock.hs | 12 ++---------- src/Settings/Packages/Compiler.hs | 6 ++++-- 2 files changed, 6 insertions(+), 12 deletions(-) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index c8226fc..d626f26 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -43,19 +43,11 @@ haddockArgs = builder Haddock ? do arg "--source-module=src/%{MODULE/./-}.html" , specified HsColour ? arg "--source-entity=src/%{MODULE/./-}.html\\#%{NAME}" - , customPackageArgs , append =<< getInputs , arg "+RTS" , arg $ "-t" ++ path -/- "haddock.t" - , arg "--machine-readable" ] - -customPackageArgs :: Args -customPackageArgs = mconcat - [ package compiler ? stage1 ? - arg "--optghc=-DSTAGE=2" ] - -- TODO: move to getPackageSources - -- , package ghcPrim ? stage1 ? - -- arg "libraries/ghc-prim/dist-install/build/autogen/GHC/Prim.hs" ] + , arg "--machine-readable" + , arg "-RTS" ] -- From ghc.mk: -- # ----------------------------------------------- diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 88ccf2a..0dd7551 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -5,7 +5,7 @@ import Expression import GHC (compiler) import Oracles.Config.Setting import Oracles.Config.Flag -import Predicates (builder, builderGhc, package, notStage0) +import Predicates (builder, builderGhc, package, notStage0, stage1) import Settings compilerPackageArgs :: Args @@ -36,4 +36,6 @@ compilerPackageArgs = package compiler ? do ghciWithDebugger ? notStage0 ? arg "--ghc-option=-DDEBUGGER" , ghcProfiled ? - notStage0 ? arg "--ghc-pkg-option=--force" ] ] + notStage0 ? arg "--ghc-pkg-option=--force" ] + + , builder Haddock ? stage1 ? arg "--optghc=-DSTAGE=2" ] From git at git.haskell.org Fri Oct 27 00:20:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix separation into full and RTS-only ways, add comments. (799b809) Message-ID: <20171027002038.1ABE63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/799b8090941e4c0e9c601890a480511052e36f8f/ghc >--------------------------------------------------------------- commit 799b8090941e4c0e9c601890a480511052e36f8f Author: Andrey Mokhov Date: Tue Feb 16 00:31:32 2016 +0000 Fix separation into full and RTS-only ways, add comments. >--------------------------------------------------------------- 799b8090941e4c0e9c601890a480511052e36f8f src/Way.hs | 42 ++++++++++++++++++++++++------------------ 1 file changed, 24 insertions(+), 18 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 6d034e9..01b18d2 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -76,7 +76,7 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b --- | Build with no 'WayUnit's at all. +-- | Build default _vanilla_ way. vanilla :: Way vanilla = wayFromUnits [] @@ -84,33 +84,39 @@ vanilla = wayFromUnits [] profiling :: Way profiling = wayFromUnits [Profiling] --- | Build with logging. +-- | Build with dynamic linking. +dynamic :: Way +dynamic = wayFromUnits [Dynamic] + +-- RTS only ways. See compiler/main/DynFlags.hs. +-- | Build RTS with event logging. logging :: Way logging = wayFromUnits [Logging] --- RTS only ways --- TODO: do we need to define *only* these? Shall we generalise/simplify? --- See compiler/main/DynFlags.hs. -threaded, threadedProfiling, threadedLogging, debug, debugProfiling, - threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, - threadedProfilingDynamic, threadedDynamic, threadedDebugDynamic, - debugDynamic, loggingDynamic, threadedLoggingDynamic :: Way +-- | Build multithreaded RTS. +threaded :: Way +threaded = wayFromUnits [Threaded] + +-- | Build RTS with debug information. +debug :: Way +debug = wayFromUnits [Debug] -threaded = wayFromUnits [Threaded] +threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, + threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, + threadedLoggingDynamic, debugProfiling, debugDynamic, profilingDynamic, + loggingDynamic :: Way +threadedDebug = wayFromUnits [Threaded, Debug] threadedProfiling = wayFromUnits [Threaded, Profiling] threadedLogging = wayFromUnits [Threaded, Logging] -debug = wayFromUnits [Debug] -debugProfiling = wayFromUnits [Debug, Profiling] -threadedDebug = wayFromUnits [Threaded, Debug] -threadedDebugProfiling = wayFromUnits [Threaded, Debug, Profiling] -dynamic = wayFromUnits [Dynamic] -profilingDynamic = wayFromUnits [Profiling, Dynamic] -threadedProfilingDynamic = wayFromUnits [Threaded, Profiling, Dynamic] threadedDynamic = wayFromUnits [Threaded, Dynamic] +threadedDebugProfiling = wayFromUnits [Threaded, Debug, Profiling] threadedDebugDynamic = wayFromUnits [Threaded, Debug, Dynamic] +threadedProfilingDynamic = wayFromUnits [Threaded, Profiling, Dynamic] +threadedLoggingDynamic = wayFromUnits [Threaded, Logging, Dynamic] +debugProfiling = wayFromUnits [Debug, Profiling] debugDynamic = wayFromUnits [Debug, Dynamic] +profilingDynamic = wayFromUnits [Profiling, Dynamic] loggingDynamic = wayFromUnits [Logging, Dynamic] -threadedLoggingDynamic = wayFromUnits [Threaded, Logging, Dynamic] wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" From git at git.haskell.org Fri Oct 27 00:20:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #278 from michalt/generated-dependencies/1 (14a596a) Message-ID: <20171027002038.6A2343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14a596a8086249053dc291e8cb6b306b6e196cf5/ghc >--------------------------------------------------------------- commit 14a596a8086249053dc291e8cb6b306b6e196cf5 Merge: eff3e36 234b41b Author: Andrey Mokhov Date: Tue Aug 2 00:00:07 2016 +0200 Merge pull request #278 from michalt/generated-dependencies/1 Make generatedDependencies an Expr [FilePath] >--------------------------------------------------------------- 14a596a8086249053dc291e8cb6b306b6e196cf5 src/Rules/Data.hs | 12 ++++---- src/Rules/Generate.hs | 79 ++++++++++++++++++++++++++++----------------------- 2 files changed, 49 insertions(+), 42 deletions(-) From git at git.haskell.org Fri Oct 27 00:20:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #65 from angerman/fix-B (75ebcfb) Message-ID: <20171027002039.AECF73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/75ebcfb2b778e71b4ec920a63804fe09597e8f17/ghc >--------------------------------------------------------------- commit 75ebcfb2b778e71b4ec920a63804fe09597e8f17 Merge: 4ade862 d9d00b8 Author: Andrey Mokhov Date: Thu Dec 31 02:54:19 2015 +0000 Merge pull request #65 from angerman/fix-B Fixes the -B path for the ghcWrapper. >--------------------------------------------------------------- 75ebcfb2b778e71b4ec920a63804fe09597e8f17 src/Rules/Wrappers/Ghc.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:20:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move profilingDynamic to full ways. (3c88f16) Message-ID: <20171027002042.0A8C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c88f16cf2ff282481a06abcf0ad839abe1c5fab/ghc >--------------------------------------------------------------- commit 3c88f16cf2ff282481a06abcf0ad839abe1c5fab Author: Andrey Mokhov Date: Tue Feb 16 00:44:44 2016 +0000 Move profilingDynamic to full ways. >--------------------------------------------------------------- 3c88f16cf2ff282481a06abcf0ad839abe1c5fab src/Settings/Ways.hs | 1 + src/Way.hs | 11 +++++++---- 2 files changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 223bc79..0fee897 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -13,6 +13,7 @@ getLibraryWays = fromDiffExpr $ defaultLibraryWays <> userLibraryWays getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays +-- TODO: what about profilingDynamic way? Do we need platformSupportsSharedLibs? -- These are default ways for library packages: -- * We always build 'vanilla' way. -- * We build 'profiling' way when stage > Stage0. diff --git a/src/Way.hs b/src/Way.hs index 01b18d2..b297e79 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -88,7 +88,11 @@ profiling = wayFromUnits [Profiling] dynamic :: Way dynamic = wayFromUnits [Dynamic] --- RTS only ways. See compiler/main/DynFlags.hs. +-- | Build with profiling and dynamic linking. +profilingDynamic :: Way +profilingDynamic = wayFromUnits [Profiling, Dynamic] + +-- RTS only ways below. See compiler/main/DynFlags.hs. -- | Build RTS with event logging. logging :: Way logging = wayFromUnits [Logging] @@ -101,10 +105,10 @@ threaded = wayFromUnits [Threaded] debug :: Way debug = wayFromUnits [Debug] +-- | Various combinations of RTS only ways. threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, - threadedLoggingDynamic, debugProfiling, debugDynamic, profilingDynamic, - loggingDynamic :: Way + threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic :: Way threadedDebug = wayFromUnits [Threaded, Debug] threadedProfiling = wayFromUnits [Threaded, Profiling] threadedLogging = wayFromUnits [Threaded, Logging] @@ -115,7 +119,6 @@ threadedProfilingDynamic = wayFromUnits [Threaded, Profiling, Dynamic] threadedLoggingDynamic = wayFromUnits [Threaded, Logging, Dynamic] debugProfiling = wayFromUnits [Debug, Profiling] debugDynamic = wayFromUnits [Debug, Dynamic] -profilingDynamic = wayFromUnits [Profiling, Dynamic] loggingDynamic = wayFromUnits [Logging, Dynamic] wayPrefix :: Way -> String From git at git.haskell.org Fri Oct 27 00:20:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (c547d12) Message-ID: <20171027002042.1B49D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c547d12d30964f07671974d5f43c5d5e3cf56b7d/ghc >--------------------------------------------------------------- commit c547d12d30964f07671974d5f43c5d5e3cf56b7d Author: Andrey Mokhov Date: Tue Aug 2 02:27:30 2016 +0200 Minor revision See #278 >--------------------------------------------------------------- c547d12d30964f07671974d5f43c5d5e3cf56b7d src/Rules/Generate.hs | 77 ++++++++++++++++++++++++--------------------------- 1 file changed, 36 insertions(+), 41 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 415692b..988b3d7 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -6,12 +6,11 @@ module Rules.Generate ( import qualified System.Directory as IO import Base -import Context +import Context hiding (package) import Expression import GHC import Oracles.ModuleFiles -import Predicate ( (?) ) -import qualified Predicate as Predicate +import Predicate import Rules.Actions import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH @@ -43,16 +42,16 @@ platformH stage = buildPath (vanillaContext stage compiler) -/- "ghc_boot_platfo -- TODO: move generated files to buildRootPath, see #113 includesDependencies :: [FilePath] -includesDependencies = ("includes" -/-) <$> +includesDependencies = fmap ("includes" -/-) [ "ghcautoconf.h" , "ghcplatform.h" , "ghcversion.h" ] ghcPrimDependencies :: Expr [FilePath] -ghcPrimDependencies = getStage >>= \stage -> - let prependPath x = buildPath (vanillaContext stage ghcPrim) -/- x - in return $ - fmap prependPath [ "autogen/GHC/Prim.hs" , "GHC/PrimopWrappers.hs" ] +ghcPrimDependencies = do + stage <- getStage + let path = buildPath $ vanillaContext stage ghcPrim + return [path -/- "autogen/GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"] derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" @@ -65,42 +64,38 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) , "GHCConstantsHaskellWrappers.hs" ] compilerDependencies :: Expr [FilePath] -compilerDependencies = getStage >>= \stage -> - let prependBuildPath x = buildPath (vanillaContext stage compiler) -/- x - in mconcat $ - [ return $ (platformH stage) - : includesDependencies - ++ derivedConstantsDependencies - , Predicate.notStage0 ? return (gmpLibraryH : libffiDependencies) - , return $ fmap prependBuildPath - [ "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-fixity.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-list.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-strictness.hs-incl" - , "primop-tag.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tys.hs-incl" - , "primop-vector-uniques.hs-incl" - ] - ] +compilerDependencies = do + stage <- getStage + let path = buildPath $ vanillaContext stage compiler + mconcat [ return [platformH stage] + , return includesDependencies + , return derivedConstantsDependencies + , notStage0 ? return (gmpLibraryH : libffiDependencies) + , return $ fmap (path -/-) + [ "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-fixity.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-list.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-strictness.hs-incl" + , "primop-tag.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tys.hs-incl" + , "primop-vector-uniques.hs-incl" ] ] generatedDependencies :: Expr [FilePath] generatedDependencies = mconcat - [ Predicate.package compiler ? compilerDependencies - , Predicate.package ghcPrim ? ghcPrimDependencies - , Predicate.package rts ? return ( - libffiDependencies - ++ includesDependencies - ++ derivedConstantsDependencies) - , Predicate.stage0 ? return includesDependencies - ] + [ package compiler ? compilerDependencies + , package ghcPrim ? ghcPrimDependencies + , package rts ? return (libffiDependencies + ++ includesDependencies + ++ derivedConstantsDependencies) + , stage0 ? return includesDependencies ] generate :: FilePath -> Context -> Expr String -> Action () generate file context expr = do From git at git.haskell.org Fri Oct 27 00:20:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix compilerPackageArgs (Haddock builder). (02b0d75) Message-ID: <20171027002043.3B60D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02b0d758636e8b9cf79845d7cf786c3154bfad28/ghc >--------------------------------------------------------------- commit 02b0d758636e8b9cf79845d7cf786c3154bfad28 Author: Andrey Mokhov Date: Thu Dec 31 12:15:02 2015 +0000 Fix compilerPackageArgs (Haddock builder). >--------------------------------------------------------------- 02b0d758636e8b9cf79845d7cf786c3154bfad28 src/Settings/Packages/Compiler.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 0dd7551..c2f31e6 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -5,16 +5,17 @@ import Expression import GHC (compiler) import Oracles.Config.Setting import Oracles.Config.Flag -import Predicates (builder, builderGhc, package, notStage0, stage1) +import Predicates (builder, builderGhc, package, notStage0) import Settings compilerPackageArgs :: Args compilerPackageArgs = package compiler ? do stage <- getStage rtsWays <- getRtsWays + path <- getTargetPath mconcat [ builder Alex ? arg "--latin1" - , builderGhc ? arg ("-I" ++ pkgPath compiler -/- stageString stage) + , builderGhc ? arg ("-I" ++ path) , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) @@ -38,4 +39,4 @@ compilerPackageArgs = package compiler ? do , ghcProfiled ? notStage0 ? arg "--ghc-pkg-option=--force" ] - , builder Haddock ? stage1 ? arg "--optghc=-DSTAGE=2" ] + , builder Haddock ? arg ("--optghc=-I" ++ path) ] From git at git.haskell.org Fri Oct 27 00:20:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add allWays. (575d82f) Message-ID: <20171027002045.B14D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/575d82fe621956b8a6c293eb381a19896aed2366/ghc >--------------------------------------------------------------- commit 575d82fe621956b8a6c293eb381a19896aed2366 Author: Andrey Mokhov Date: Tue Feb 16 00:53:44 2016 +0000 Add allWays. >--------------------------------------------------------------- 575d82fe621956b8a6c293eb381a19896aed2366 src/Way.hs | 22 ++++++++++++++-------- 1 file changed, 14 insertions(+), 8 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index b297e79..668ed63 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,14 +1,12 @@ module Way ( WayUnit (..), Way, wayUnit, wayFromUnits, - vanilla, profiling, logging, - threaded, threadedProfiling, threadedLogging, - debug, debugProfiling, threadedDebug, threadedDebugProfiling, - dynamic, profilingDynamic, threadedProfilingDynamic, - threadedDynamic, threadedDebugDynamic, debugDynamic, - loggingDynamic, threadedLoggingDynamic, - - wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, + vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging, + threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, + threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, + threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic, + + allWays, wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, safeDetectWay, detectWay, matchBuildResult ) where @@ -121,6 +119,14 @@ debugProfiling = wayFromUnits [Debug, Profiling] debugDynamic = wayFromUnits [Debug, Dynamic] loggingDynamic = wayFromUnits [Logging, Dynamic] +-- | All ways supported by the build system. +allWays :: [Way] +allWays = + [ vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging + , threadedDebug, threadedProfiling, threadedLogging, threadedDynamic + , threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic + , threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic ] + wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" From git at git.haskell.org Fri Oct 27 00:20:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Require Cabal 1.25 (f1f95d5) Message-ID: <20171027002045.F314A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f1f95d5e016b85411487f62d0b9603692bfcd923/ghc >--------------------------------------------------------------- commit f1f95d5e016b85411487f62d0b9603692bfcd923 Author: Andrey Mokhov Date: Fri Aug 5 17:19:36 2016 +0100 Require Cabal 1.25 See #280. >--------------------------------------------------------------- f1f95d5e016b85411487f62d0b9603692bfcd923 hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 63bd164..41cccd8 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* || == 1.24.* || == 1.25.* + , Cabal == 1.25.* , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 00:20:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: ghcPkg Wrapper (aee3088) Message-ID: <20171027002046.BD46D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aee308892e923e8f2ba24d912fc3197599ef47a8/ghc >--------------------------------------------------------------- commit aee308892e923e8f2ba24d912fc3197599ef47a8 Author: Moritz Angermann Date: Thu Dec 31 20:21:13 2015 +0800 ghcPkg Wrapper >--------------------------------------------------------------- aee308892e923e8f2ba24d912fc3197599ef47a8 shaking-up-ghc.cabal | 1 + src/Rules/Program.hs | 4 +++- src/Rules/Wrappers/GhcPkg.hs | 20 ++++++++++++++++++++ 3 files changed, 24 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index cfa55ff..2c75566 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -55,6 +55,7 @@ executable ghc-shake , Rules.Program , Rules.Resources , Rules.Wrappers.Ghc + , Rules.Wrappers.GhcPkg , Settings , Settings.Args , Settings.Builders.Alex diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index a1aaa2f..75314c3 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -10,6 +10,7 @@ import Rules.Actions import Rules.Library import Rules.Resources import Rules.Wrappers.Ghc +import Rules.Wrappers.GhcPkg import Settings import Settings.Builders.GhcCabal @@ -22,7 +23,8 @@ type Wrapper = FilePath -> Expr String -- List of wrappers we build wrappers :: [(PartialTarget, Wrapper)] -wrappers = [(PartialTarget Stage0 ghc, ghcWrapper)] +wrappers = [ (PartialTarget Stage0 ghc, ghcWrapper) + , (PartialTarget Stage0 ghcPkg, ghcPkgWrapper)] buildProgram :: Resources -> PartialTarget -> Rules () buildProgram _ target @ (PartialTarget stage pkg) = do diff --git a/src/Rules/Wrappers/GhcPkg.hs b/src/Rules/Wrappers/GhcPkg.hs new file mode 100644 index 0000000..7edc43c --- /dev/null +++ b/src/Rules/Wrappers/GhcPkg.hs @@ -0,0 +1,20 @@ +module Rules.Wrappers.GhcPkg (ghcPkgWrapper) where + +import Base +import Expression +import Oracles + +-- Note about wrapper: +-- bindir is usually GhcSourcePath / inplace / bin +-- topdir is usually GhcSourcePath / inplace / lib +-- datadir is usually the same as topdir + +ghcPkgWrapper :: FilePath -> Expr String +ghcPkgWrapper program = do + lift $ need [sourcePath -/- "Rules/Wrappers/GhcPkg.hs"] + top <- getSetting GhcSourcePath + let pkgConf = top -/- "inplace" -/- "lib" -/- "package.conf.d" + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (top -/- program) + ++ " --global-package-db " ++ pkgConf ++ " ${1+\"$@\"}" ] From git at git.haskell.org Fri Oct 27 00:20:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass way to compilePackage via Context. (23d501a) Message-ID: <20171027002049.EA43F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23d501a474266920e395e60d4d6c69369785608f/ghc >--------------------------------------------------------------- commit 23d501a474266920e395e60d4d6c69369785608f Author: Andrey Mokhov Date: Tue Feb 16 02:24:35 2016 +0000 Pass way to compilePackage via Context. See #207. >--------------------------------------------------------------- 23d501a474266920e395e60d4d6c69369785608f src/Rules.hs | 10 +++++++--- src/Rules/Compile.hs | 37 ++++++++++++++----------------------- 2 files changed, 21 insertions(+), 26 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index e12fc1c..f765b5e 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -3,6 +3,7 @@ module Rules (topLevelTargets, buildRules) where import Data.Foldable import Base +import Context hiding (stage, package, way) import Expression import GHC import Rules.Compile @@ -52,18 +53,21 @@ topLevelTargets = do packageRules :: Rules () packageRules = do - -- We cannot register multiple packages in parallel. Also we cannot run GHC - -- when the package database is being mutated by "ghc-pkg". This is a + -- We cannot register multiple GHC packages in parallel. Also we cannot run + -- GHC when the package database is being mutated by "ghc-pkg". This is a -- classic concurrent read exclusive write (CREW) conflict. let maxConcurrentReaders = 1000 packageDb <- newResource "package-db" maxConcurrentReaders let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] + let contexts = liftM3 Context allStages knownPackages allWays + + traverse_ (compilePackage readPackageDb) contexts + for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package - compilePackage readPackageDb context buildPackageData context buildPackageDependencies readPackageDb context buildPackageDocumentation context diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index b583f5a..14e71ee 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -9,52 +9,43 @@ import Rules.Actions import Settings import Target hiding (context) --- TODO: Use way from Context, #207 compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" - matchBuildResult buildPath "hi" ?> \hi -> + buildPath "*" <.> hisuf way %> \hi -> if compileInterfaceFilesSeparately && not ("//HpcParser.*" ?== hi) then do - let w = detectWay hi - (src, deps) <- dependencies buildPath $ hi -<.> osuf w + (src, deps) <- dependencies buildPath $ hi -<.> osuf way need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [hi] - else need [ hi -<.> osuf (detectWay hi) ] + buildWithResources rs $ Target context (Ghc stage) [src] [hi] + else need [ hi -<.> osuf way ] - matchBuildResult buildPath "hi-boot" ?> \hiboot -> + buildPath "*" <.> hibootsuf way %> \hiboot -> if compileInterfaceFilesSeparately then do - let w = detectWay hiboot - (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf w + (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf way need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [hiboot] - else need [ hiboot -<.> obootsuf (detectWay hiboot) ] + buildWithResources rs $ Target context (Ghc stage) [src] [hiboot] + else need [ hiboot -<.> obootsuf way ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) - matchBuildResult buildPath "o" ?> \obj -> do + buildPath "*" <.> osuf way %> \obj -> do (src, deps) <- dependencies buildPath obj if ("//*.c" ?== src) then do need $ src : deps build $ Target context (Gcc stage) [src] [obj] else do - let w = detectWay obj if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) - then need $ (obj -<.> hisuf (detectWay obj)) : src : deps + then need $ (obj -<.> hisuf way) : src : deps else need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [obj] + buildWithResources rs $ Target context (Ghc stage) [src] [obj] -- TODO: get rid of these special cases - matchBuildResult buildPath "o-boot" ?> \obj -> do + buildPath "*" <.> obootsuf way %> \obj -> do (src, deps) <- dependencies buildPath obj - let w = detectWay obj if compileInterfaceFilesSeparately - then need $ (obj -<.> hibootsuf (detectWay obj)) : src : deps + then need $ (obj -<.> hibootsuf way) : src : deps else need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [obj] + buildWithResources rs $ Target context (Ghc stage) [src] [obj] From git at git.haskell.org Fri Oct 27 00:20:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make dependencies easier to copy (9467c06) Message-ID: <20171027002050.ABB9E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9467c0611db45c494aba051e2a5e8bd2f3cc86c1/ghc >--------------------------------------------------------------- commit 9467c0611db45c494aba051e2a5e8bd2f3cc86c1 Author: Andrey Mokhov Date: Fri Aug 5 18:53:09 2016 +0100 Make dependencies easier to copy [skip ci] >--------------------------------------------------------------- 9467c0611db45c494aba051e2a5e8bd2f3cc86c1 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 4ce3b3a..be42f82 100644 --- a/README.md +++ b/README.md @@ -23,7 +23,7 @@ follow these steps: * If you have never built GHC before, start with the [preparation guide][ghc-preparation]. * This build system is written in Haskell (obviously) and depends on the following Haskell -packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. +packages, which need to be installed: `ansi-terminal mtl shake QuickCheck`. * Get the sources. It is important for the build system to be in the `hadrian` directory of the GHC source tree: From git at git.haskell.org Fri Oct 27 00:20:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #68 from angerman/wrapper/ghc-pkg (c720603) Message-ID: <20171027002051.44AEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7206034ba32d2a14e583c03580826ddb28a0aa4/ghc >--------------------------------------------------------------- commit c7206034ba32d2a14e583c03580826ddb28a0aa4 Merge: 02b0d75 aee3088 Author: Andrey Mokhov Date: Thu Dec 31 12:27:30 2015 +0000 Merge pull request #68 from angerman/wrapper/ghc-pkg ghcPkg Wrapper >--------------------------------------------------------------- c7206034ba32d2a14e583c03580826ddb28a0aa4 shaking-up-ghc.cabal | 1 + src/Rules/Program.hs | 4 +++- src/Rules/Wrappers/GhcPkg.hs | 20 ++++++++++++++++++++ 3 files changed, 24 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:20:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't capitalise 'quickcheck' (9b474d3) Message-ID: <20171027002054.425143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b474d34ffa182b021956944d669aee0528291ad/ghc >--------------------------------------------------------------- commit 9b474d34ffa182b021956944d669aee0528291ad Author: Andrey Mokhov Date: Fri Aug 5 18:56:33 2016 +0100 Don't capitalise 'quickcheck' [skip ci] >--------------------------------------------------------------- 9b474d34ffa182b021956944d669aee0528291ad README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index be42f82..c39071e 100644 --- a/README.md +++ b/README.md @@ -23,7 +23,7 @@ follow these steps: * If you have never built GHC before, start with the [preparation guide][ghc-preparation]. * This build system is written in Haskell (obviously) and depends on the following Haskell -packages, which need to be installed: `ansi-terminal mtl shake QuickCheck`. +packages, which need to be installed: `ansi-terminal mtl shake quickcheck`. * Get the sources. It is important for the build system to be in the `hadrian` directory of the GHC source tree: From git at git.haskell.org Fri Oct 27 00:20:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop workaround for GHC bug #11331. (8478284) Message-ID: <20171027002053.6788B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84782844c149c729e5277f79ee80c8001f05c095/ghc >--------------------------------------------------------------- commit 84782844c149c729e5277f79ee80c8001f05c095 Author: Andrey Mokhov Date: Tue Feb 16 02:26:08 2016 +0000 Drop workaround for GHC bug #11331. See #174. >--------------------------------------------------------------- 84782844c149c729e5277f79ee80c8001f05c095 src/Rules/Compile.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 14e71ee..a52edef 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -14,7 +14,7 @@ compilePackage rs context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" buildPath "*" <.> hisuf way %> \hi -> - if compileInterfaceFilesSeparately && not ("//HpcParser.*" ?== hi) + if compileInterfaceFilesSeparately then do (src, deps) <- dependencies buildPath $ hi -<.> osuf way need $ src : deps @@ -37,7 +37,7 @@ compilePackage rs context @ (Context {..}) = do need $ src : deps build $ Target context (Gcc stage) [src] [obj] else do - if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) + if compileInterfaceFilesSeparately && "//*.hs" ?== src then need $ (obj -<.> hisuf way) : src : deps else need $ src : deps buildWithResources rs $ Target context (Ghc stage) [src] [obj] From git at git.haskell.org Fri Oct 27 00:20:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initialise inplace/lib/package.conf.d, fix #66. (84704cf) Message-ID: <20171027002054.DDFEC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84704cf2cf9324a09153b65f667581d03671e6ed/ghc >--------------------------------------------------------------- commit 84704cf2cf9324a09153b65f667581d03671e6ed Author: Andrey Mokhov Date: Thu Dec 31 13:53:29 2015 +0000 Initialise inplace/lib/package.conf.d, fix #66. >--------------------------------------------------------------- 84704cf2cf9324a09153b65f667581d03671e6ed src/Base.hs | 15 ++++++++++----- src/Rules/Cabal.hs | 20 +++++++++++--------- src/Rules/Wrappers/GhcPkg.hs | 5 +++-- src/Settings/Builders/GhcCabal.hs | 12 +++++++----- src/Settings/Builders/GhcPkg.hs | 7 +++++-- src/Stage.hs | 2 +- 6 files changed, 37 insertions(+), 24 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 25a69df..a127299 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,7 +16,7 @@ module Base ( -- * Paths shakeFilesPath, configPath, sourcePath, programInplacePath, bootPackageConstraints, packageDependencies, - bootstrappingConf, bootstrappingConfInitialised, + packageConfiguration, packageConfigurationInitialised, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, @@ -41,6 +41,9 @@ import System.Console.ANSI import qualified System.Directory as IO import System.IO +-- TODO: reexport Stage, etc.? +import Stage + -- Build system files and paths shakePath :: FilePath shakePath = "shake-build" @@ -65,11 +68,13 @@ bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" packageDependencies :: FilePath packageDependencies = shakeFilesPath -/- "package-dependencies" -bootstrappingConf :: FilePath -bootstrappingConf = "libraries/bootstrapping.conf" +packageConfiguration :: Stage -> FilePath +packageConfiguration Stage0 = "libraries/bootstrapping.conf" +packageConfiguration _ = "inplace/lib/package.conf.d" -bootstrappingConfInitialised :: FilePath -bootstrappingConfInitialised = shakeFilesPath -/- "bootstrapping-conf-initialised" +packageConfigurationInitialised :: Stage -> FilePath +packageConfigurationInitialised stage = + shakeFilesPath -/- "package-configuration-initialised-" ++ stageString stage -- Utility functions -- | Find and replace all occurrences of a value in a list diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 9239e67..ab7622c 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -39,17 +39,19 @@ cabalRules = do return . unwords $ pkgNameString pkg : sort depNames writeFileChanged out . unlines $ pkgDeps - -- When the file exists, the bootstrappingConf has been initialised + -- When the file exists, the packageConfiguration has been initialised -- TODO: get rid of an extra file? - bootstrappingConfInitialised %> \out -> do - removeDirectoryIfExists bootstrappingConf - -- TODO: can we get rid of this fake target? - let target = PartialTarget Stage0 cabal - build $ fullTarget target (GhcPkg Stage0) [] [bootstrappingConf] - let message = "Successfully initialised " ++ bootstrappingConf - writeFileChanged out message - putSuccess message + forM_ [Stage0 ..] $ \stage -> + packageConfigurationInitialised stage %> \out -> do + let target = PartialTarget stage cabal + pkgConf = packageConfiguration stage + removeDirectoryIfExists pkgConf + -- TODO: can we get rid of this fake target? + build $ fullTarget target (GhcPkg stage) [] [pkgConf] + let message = "Successfully initialised " ++ pkgConf + writeFileChanged out message + putSuccess message collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] diff --git a/src/Rules/Wrappers/GhcPkg.hs b/src/Rules/Wrappers/GhcPkg.hs index 7edc43c..3f70617 100644 --- a/src/Rules/Wrappers/GhcPkg.hs +++ b/src/Rules/Wrappers/GhcPkg.hs @@ -12,8 +12,9 @@ import Oracles ghcPkgWrapper :: FilePath -> Expr String ghcPkgWrapper program = do lift $ need [sourcePath -/- "Rules/Wrappers/GhcPkg.hs"] - top <- getSetting GhcSourcePath - let pkgConf = top -/- "inplace" -/- "lib" -/- "package.conf.d" + top <- getSetting GhcSourcePath + stage <- getStage + let pkgConf = top -/- packageConfiguration stage return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 597f591..06b2a63 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -85,11 +85,13 @@ configureArgs = do , conf "--with-cc" $ argStagedBuilderPath Gcc ] bootPackageDbArgs :: Args -bootPackageDbArgs = stage0 ? do - path <- getSetting GhcSourcePath - lift $ need [bootstrappingConfInitialised] - prefix <- ifM builderGhc (return "-package-db ") (return "--package-db=") - arg $ prefix ++ path -/- bootstrappingConf +bootPackageDbArgs = do + stage <- getStage + lift $ need [packageConfigurationInitialised stage] + stage0 ? do + path <- getSetting GhcSourcePath + prefix <- ifM builderGhc (return "-package-db ") (return "--package-db=") + arg $ prefix ++ path -/- packageConfiguration Stage0 packageConstraints :: Args packageConstraints = stage0 ? do diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index e79a360..c8e25ff 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -10,13 +10,16 @@ import Settings.Builders.GhcCabal ghcPkgArgs :: Args ghcPkgArgs = stagedBuilder GhcPkg ? (initArgs <> updateArgs) +initPredicate :: Predicate +initPredicate = orM $ map (file . packageConfiguration) [Stage0 ..] + initArgs :: Args -initArgs = file bootstrappingConf ? do +initArgs = initPredicate ? do mconcat [ arg "init" , arg =<< getOutput ] updateArgs :: Args -updateArgs = notM (file bootstrappingConf) ? do +updateArgs = notM initPredicate ? do path <- getTargetPath mconcat [ arg "update" , arg "--force" diff --git a/src/Stage.hs b/src/Stage.hs index 70fe6ba..144aa29 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric #-} module Stage (Stage (..), stageString) where -import Base +import Development.Shake.Classes import GHC.Generics (Generic) -- TODO: explain stages From git at git.haskell.org Fri Oct 27 00:20:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (0ddf3b4) Message-ID: <20171027002056.D42853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ddf3b4d341a31ce66d78b5c840b2e55929ab5e3/ghc >--------------------------------------------------------------- commit 0ddf3b4d341a31ce66d78b5c840b2e55929ab5e3 Author: Andrey Mokhov Date: Tue Feb 16 02:40:38 2016 +0000 Minor revision. See #207. >--------------------------------------------------------------- 0ddf3b4d341a31ce66d78b5c840b2e55929ab5e3 src/Rules.hs | 7 ++++--- src/Rules/Compile.hs | 2 +- src/Rules/Dependencies.hs | 9 ++++----- 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index f765b5e..a3d67cb 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -61,15 +61,16 @@ packageRules = do let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] - let contexts = liftM3 Context allStages knownPackages allWays + let contexts = liftM3 Context allStages knownPackages allWays + vanillaContexts = liftM2 vanillaContext allStages knownPackages - traverse_ (compilePackage readPackageDb) contexts + traverse_ (compilePackage readPackageDb) contexts + traverse_ (buildPackageDependencies readPackageDb) vanillaContexts for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package buildPackageData context - buildPackageDependencies readPackageDb context buildPackageDocumentation context generatePackageCode context buildPackageLibrary context diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index a52edef..f62c644 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -7,7 +7,7 @@ import Expression import Oracles.Dependencies import Rules.Actions import Settings -import Target hiding (context) +import Target compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context @ (Context {..}) = do diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 45a8f8c..330c821 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -19,7 +19,7 @@ buildPackageDependencies rs context @ (Context {..}) = dropBuild = (pkgPath package ++) . drop (length buildPath) hDepFile = buildPath -/- ".hs-dependencies" in do - fmap (buildPath++) + fmap (buildPath ++) [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do let srcFile = if "//AutoApply.*" ?== out then dropExtension out @@ -32,19 +32,18 @@ buildPackageDependencies rs context @ (Context {..}) = need srcs if srcs == [] then writeFileChanged out "" - else buildWithResources rs $ - Target context (GhcM stage) srcs [out] + else buildWithResources rs $ Target context (GhcM stage) srcs [out] removeFileIfExists $ out <.> "bak" -- TODO: don't accumulate *.deps into .dependencies - (buildPath -/- ".dependencies") %> \out -> do + buildPath -/- ".dependencies" %> \out -> do cSrcs <- pkgDataList $ CSrcs path let cDepFiles = [ buildPath -/- src <.> "deps" | src <- cSrcs , not ("//AutoApply.cmm" ?== src) ] ++ [ src <.> "deps" | src <- cSrcs, "//AutoApply.cmm" ?== src ] need $ hDepFile : cDepFiles -- need all for more parallelism - cDeps <- fmap concat $ mapM readFile' cDepFiles + cDeps <- fmap concat $ traverse readFile' cDepFiles hDeps <- readFile' hDepFile let result = unlines . map (\(src, deps) -> unwords $ src : deps) From git at git.haskell.org Fri Oct 27 00:20:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't run cabal on Hadrian (ae1fa1a) Message-ID: <20171027002057.A3FE83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae1fa1ac3c153c6110174ada2641607e17bd534c/ghc >--------------------------------------------------------------- commit ae1fa1ac3c153c6110174ada2641607e17bd534c Author: Andrey Mokhov Date: Fri Aug 5 18:58:08 2016 +0100 Don't run cabal on Hadrian >--------------------------------------------------------------- ae1fa1ac3c153c6110174ada2641607e17bd534c .travis.yml | 8 ++------ 1 file changed, 2 insertions(+), 6 deletions(-) diff --git a/.travis.yml b/.travis.yml index dd74f25..33c1738 100644 --- a/.travis.yml +++ b/.travis.yml @@ -17,7 +17,7 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH - cabal update - - cabal install alex happy + - cabal install alex happy ansi-terminal mtl shake quickcheck - os: osx env: FLAVOUR=quickest TARGET= @@ -25,7 +25,7 @@ matrix: - brew update - brew install ghc cabal-install - cabal update - - cabal install alex happy + - cabal install alex happy ansi-terminal mtl shake quickcheck - PATH="$HOME/.cabal/bin:$PATH" - export PATH @@ -51,13 +51,9 @@ install: - mv .git ghc/hadrian - ( cd ghc/hadrian && git reset --hard HEAD ) - - ( cd ghc/hadrian && cabal install --only-dependencies ) - - ( cd ghc/hadrian && cabal configure ) - - ghc-pkg list script: - - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=$FLAVOUR $TARGET - ./ghc/inplace/bin/ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:20:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:20:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't re-initialise packageConfiguration in Stage2, see #66. (e2fb954) Message-ID: <20171027002058.5F04C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2fb95438402a6a76eff23be687020255a5cc218/ghc >--------------------------------------------------------------- commit e2fb95438402a6a76eff23be687020255a5cc218 Author: Andrey Mokhov Date: Thu Dec 31 14:06:07 2015 +0000 Don't re-initialise packageConfiguration in Stage2, see #66. >--------------------------------------------------------------- e2fb95438402a6a76eff23be687020255a5cc218 src/Base.hs | 4 +++- src/Rules/Cabal.hs | 2 +- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a127299..6f3b6d6 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -72,9 +72,11 @@ packageConfiguration :: Stage -> FilePath packageConfiguration Stage0 = "libraries/bootstrapping.conf" packageConfiguration _ = "inplace/lib/package.conf.d" +-- StageN, N > 0, share the same packageConfiguration (see above) packageConfigurationInitialised :: Stage -> FilePath packageConfigurationInitialised stage = - shakeFilesPath -/- "package-configuration-initialised-" ++ stageString stage + shakeFilesPath -/- "package-configuration-initialised-" + ++ stageString (min stage Stage1) -- Utility functions -- | Find and replace all occurrences of a value in a list diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index ab7622c..bf4c8f6 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -42,7 +42,7 @@ cabalRules = do -- When the file exists, the packageConfiguration has been initialised -- TODO: get rid of an extra file? - forM_ [Stage0 ..] $ \stage -> + forM_ [Stage0, Stage1] $ \stage -> packageConfigurationInitialised stage %> \out -> do let target = PartialTarget stage cabal pkgConf = packageConfiguration stage From git at git.haskell.org Fri Oct 27 00:21:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to Cabal library API changes (a931066) Message-ID: <20171027002101.72DAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a931066df88efc745bdd310b3c64aa25834ba243/ghc >--------------------------------------------------------------- commit a931066df88efc745bdd310b3c64aa25834ba243 Author: Andrey Mokhov Date: Thu Aug 11 00:41:02 2016 +0100 Adapt to Cabal library API changes Fix #282. >--------------------------------------------------------------- a931066df88efc745bdd310b3c64aa25834ba243 src/Rules/Cabal.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index e2cdb0f..ed72f93 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -35,8 +35,7 @@ cabalRules = do else do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - -- TODO: Support more than one Cabal library per package. - let depsLib = collectDeps . fmap snd . listToMaybe $ condLibraries pd + let depsLib = collectDeps $ condLibrary pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes depNames = [ name | Dependency (DP.PackageName name) _ <- deps ] From git at git.haskell.org Fri Oct 27 00:21:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass way to buildPackageLibrary via Context, minor revision. (98b1f8c) Message-ID: <20171027002100.5F6123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/98b1f8c2e233d4b9504dfe359b0f538f7af9095e/ghc >--------------------------------------------------------------- commit 98b1f8c2e233d4b9504dfe359b0f538f7af9095e Author: Andrey Mokhov Date: Tue Feb 16 03:01:56 2016 +0000 Pass way to buildPackageLibrary via Context, minor revision. See #207. >--------------------------------------------------------------- 98b1f8c2e233d4b9504dfe359b0f538f7af9095e src/Rules.hs | 15 +++++++++------ src/Rules/Documentation.hs | 1 + src/Rules/Library.hs | 13 +++++-------- src/Way.hs | 4 ++-- 4 files changed, 17 insertions(+), 16 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index a3d67cb..4592b4a 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -64,16 +64,19 @@ packageRules = do let contexts = liftM3 Context allStages knownPackages allWays vanillaContexts = liftM2 vanillaContext allStages knownPackages - traverse_ (compilePackage readPackageDb) contexts - traverse_ (buildPackageDependencies readPackageDb) vanillaContexts + for_ contexts $ mconcat + [ compilePackage readPackageDb + , buildPackageLibrary ] + + for_ vanillaContexts $ mconcat + [ buildPackageData + , buildPackageDependencies readPackageDb + , buildPackageDocumentation + , generatePackageCode ] for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package - buildPackageData context - buildPackageDocumentation context - generatePackageCode context - buildPackageLibrary context buildProgram context registerPackage writePackageDb context diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 848a3fa..e3b0e7d 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -37,6 +37,7 @@ buildPackageDocumentation context @ (Context {..}) = build $ Target context GhcCabalHsColour [cabalFile] [] -- Build Haddock documentation + -- TODO: pass the correct way from Rules via Context let haddockWay = if dynamicGhcPrograms then dynamic else vanilla build $ Target (context {way = haddockWay}) Haddock srcs [file] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 79b4952..d77d58e 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -14,24 +14,21 @@ import Rules.Gmp import Settings import Target --- TODO: Use way from Context, #207 buildPackageLibrary :: Context -> Rules () buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" -- TODO: handle dynamic libraries - matchBuildResult buildPath "a" ?> \a -> do - + buildPath "*" ++ waySuffix way ++ ".a" %> \a -> do removeFileIfExists a cSrcs <- cSources context hSrcs <- hSources context - -- TODO: simplify handling of AutoApply.cmm - let w = detectWay a -- TODO: eliminate differences below - cObjs = [ buildPath -/- src -<.> osuf w | src <- cSrcs + -- TODO: simplify handling of AutoApply.cmm, eliminate differences below + let cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs , not ("//AutoApply.cmm" ?== src) ] - ++ [ src -<.> osuf w | src <- cSrcs, "//AutoApply.cmm" ?== src ] - hObjs = [ buildPath -/- src <.> osuf w | src <- hSrcs ] + ++ [ src -<.> osuf way | src <- cSrcs, "//AutoApply.cmm" ?== src ] + hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] -- This will create split objects if required (we don't track them -- explicitly as this would needlessly bloat the Shake database). diff --git a/src/Way.hs b/src/Way.hs index 668ed63..c393437 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -6,8 +6,8 @@ module Way ( threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic, - allWays, wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, - safeDetectWay, detectWay, matchBuildResult + allWays, wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, + libsuf, safeDetectWay, detectWay, matchBuildResult ) where import Base hiding (unit) From git at git.haskell.org Fri Oct 27 00:21:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (79ceb45) Message-ID: <20171027002102.089833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79ceb456ffb5511e630ace24ed409782119ddf5d/ghc >--------------------------------------------------------------- commit 79ceb456ffb5511e630ace24ed409782119ddf5d Author: Moritz Angermann Date: Fri Jan 1 01:20:06 2016 +0800 Update README.md Roll Linux / OS X into one section. This should fix #37. >--------------------------------------------------------------- 79ceb456ffb5511e630ace24ed409782119ddf5d README.md | 29 +++++++++++------------------ 1 file changed, 11 insertions(+), 18 deletions(-) diff --git a/README.md b/README.md index 93674a1..f26cc49 100644 --- a/README.md +++ b/README.md @@ -14,7 +14,13 @@ This is supposed to go into the `shake-build` directory of the GHC source tree. Trying it --------- -### Linux +Please see the [Preparation][ghc-preparation] on the haskell wiki +for general preparation. The preparation steps for the `shake` build system are +identical to those for the `make` build system. This means that you don't need +to adjust anything if you are already familiar with building ghc using the `make` +build system. + +### Linux / Mac OS X ```bash git clone git://git.haskell.org/ghc @@ -23,6 +29,9 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure +# or if you want to use clang (e.g. building on OS X) +./configure --with-gcc=$(which clang) # See #26 + ``` Now you have a couple of options: @@ -46,20 +55,6 @@ shake-build/build.bat ``` Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. -### Mac OS X - -```bash -git clone git://git.haskell.org/ghc -cd ghc -git submodule update --init -git clone git://github.com/snowleopard/shaking-up-ghc shake-build -./boot -./configure --with-gcc=$(which clang) # See #26 -./shake-build/build.sh -``` - -See the Linux section for running in a Cabal sandbox. - ### Resetting the build To reset the new build system run the build script with `-B` flag. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). @@ -76,10 +71,8 @@ documentation is currently non-existent, but we will start addressing this once the codebase stabilises. - - - [ghc-shake-wiki]: https://ghc.haskell.org/trac/ghc/wiki/Building/Shake +[ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-building-guide]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows [ghc]: https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler [shake-blog-post]: https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc From git at git.haskell.org Fri Oct 27 00:21:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finalise generation of build rules from contexts. (f6a9d2f) Message-ID: <20171027002103.ECE1F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f6a9d2f4e67a163ba8255d8e66def0668dd492a1/ghc >--------------------------------------------------------------- commit f6a9d2f4e67a163ba8255d8e66def0668dd492a1 Author: Andrey Mokhov Date: Tue Feb 16 03:08:24 2016 +0000 Finalise generation of build rules from contexts. See #207. >--------------------------------------------------------------- f6a9d2f4e67a163ba8255d8e66def0668dd492a1 src/Rules.hs | 10 +++------- src/Rules/Register.hs | 1 - 2 files changed, 3 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 4592b4a..74ffe30 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -72,13 +72,9 @@ packageRules = do [ buildPackageData , buildPackageDependencies readPackageDb , buildPackageDocumentation - , generatePackageCode ] - - for_ allStages $ \stage -> - for_ knownPackages $ \package -> do - let context = vanillaContext stage package - buildProgram context - registerPackage writePackageDb context + , generatePackageCode + , buildProgram + , registerPackage writePackageDb ] buildRules :: Rules () buildRules = do diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 2bbfcfc..01d8ab9 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -13,7 +13,6 @@ import Settings import Settings.Packages.Rts import Target --- TODO: Use way from Context, #207 -- Build package-data.mk by using GhcCabal to process pkgCabal file registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context @ (Context {..}) = do From git at git.haskell.org Fri Oct 27 00:21:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initial version of FindMissingInclude (c2d7e2a) Message-ID: <20171027002105.666213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c2d7e2aa683c89d9b1464734ea9ae68ff735655c/ghc >--------------------------------------------------------------- commit c2d7e2aa683c89d9b1464734ea9ae68ff735655c Author: Michal Terepeta Date: Sat Jul 23 16:50:31 2016 +0200 Initial version of FindMissingInclude This allows finding missing includes for `.c` files (this is important for all the cases where we generate the includes during the build process). We're using GCC's `-MM` `-MG` options and iterate as long as we get new includes. Since this would return all includes verbatim from the `#include`, we check which ones are actually generated and what are their final paths. Note: this is currently applied only to `.c` files and does not (yet?) work for `.hs` files (there are issues with things like ifdefs for package versions that cause GCC to error out). Signed-off-by: Michal Terepeta >--------------------------------------------------------------- c2d7e2aa683c89d9b1464734ea9ae68ff735655c src/Builder.hs | 3 ++- src/Rules/Compile.hs | 40 ++++++++++++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 17 ++++++++++++++++- src/Settings/Builders/Cc.hs | 13 ++++++++++++- 4 files changed, 70 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 17198e7..1974eff 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -21,7 +21,8 @@ import Stage -- 3) Linking object files & static libraries into an executable. -- We have CcMode for CC and GhcMode for GHC. -data CcMode = CompileC | FindCDependencies +-- TODO: Consider merging FindCDependencies and FindMissingInclude +data CcMode = CompileC | FindCDependencies | FindMissingInclude deriving (Eq, Generic, Show) data GhcMode = CompileHs | FindHsDependencies | LinkHs diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index fd6cd32..001068a 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -5,9 +5,16 @@ import Context import Expression import Oracles.Dependencies import Rules.Actions +import Rules.Generate import Settings.Paths import Target +import Development.Shake.Util + +import Data.Maybe +import Data.List +import qualified Data.Set as Set + compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context @@ -22,6 +29,9 @@ compilePackage rs context at Context {..} = do if ("//*.c" ?== src) then do need $ src : deps + -- TODO: Improve parallelism by collecting all dependencies and + -- need'ing them all at once + mapM_ (needGenerated context) . filter ("//*.c" ?==) $ src : deps build $ Target context (Cc CompileC stage) [src] [obj] else do need $ src : deps @@ -39,3 +49,33 @@ needCompileDependencies :: Context -> Action () needCompileDependencies context at Context {..} = do when (isLibrary package) $ need =<< return <$> pkgConfFile context needContext =<< contextDependencies context + +needGenerated :: Context -> FilePath -> Action () +needGenerated context origFile = go Set.empty + where + go :: Set.Set String -> Action () + go done = withTempFile $ \outFile -> do + let builder = Cc FindMissingInclude $ stage context + target = Target context builder [origFile] [outFile] + build target + deps <- parseFile outFile + + -- Get the full path if the include refers to a generated file and call + -- `need` on it. + needed <- liftM catMaybes $ + interpretInContext context (mapM getPathIfGenerated deps) + need needed + + let newdone = Set.fromList needed `Set.union` done + -- If we added a new file to the set of needed files, let's try one more + -- time, since the new file might include a genreated header of itself + -- (which we'll `need`). + when (Set.size newdone > Set.size done) (go newdone) + + parseFile :: FilePath -> Action [String] + parseFile file = do + input <- liftIO $ readFile file + case parseMakefile input of + [(_file, deps)] -> return deps + _ -> return [] + diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 988b3d7..34874db 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,7 @@ module Rules.Generate ( generatePackageCode, generateRules, installTargets, copyRules, - includesDependencies, derivedConstantsPath, generatedDependencies + includesDependencies, derivedConstantsPath, generatedDependencies, + getPathIfGenerated ) where import qualified System.Directory as IO @@ -196,3 +197,17 @@ generateRules = do emptyTarget :: Context emptyTarget = vanillaContext (error "Rules.Generate.emptyTarget: unknown stage") (error "Rules.Generate.emptyTarget: unknown package") + +getPathIfGenerated :: FilePath -> Expr (Maybe FilePath) +getPathIfGenerated include = do + generated <- generatedFiles + -- For includes of generated files, we cannot get the full path of the file + -- (since it might be included due to some include dir, i.e., through `-I`). + -- So here we try both the name and the path. + let nameOrPath (name, path) = include == name || include == path + return . fmap snd $ find nameOrPath generated + +generatedFiles :: Expr [(FilePath, FilePath)] +generatedFiles = do + deps <- generatedDependencies + return [ (takeFileName fp, fp) | fp <- deps ] diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index 354d2b4..36a172e 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -26,7 +26,18 @@ ccBuilderArgs = mconcat , arg $ dropExtension output -<.> "o" , arg "-x" , arg "c" - , arg =<< getInput ] ] + , arg =<< getInput ] + + , builder (Cc FindMissingInclude) ? do + mconcat [ arg "-E" + , arg "-MM" + , arg "-MG" + , commonCcArgs + , arg "-MF" + , arg =<< getOutput + , arg =<< getInput + ] + ] commonCcArgs :: Args commonCcArgs = mconcat [ append =<< getPkgDataList CcArgs From git at git.haskell.org Fri Oct 27 00:21:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop matchBuildResult and associated functions. (1aec72e) Message-ID: <20171027002107.7249E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1aec72e34e0e3da138c6e0105c509f20592f6bc6/ghc >--------------------------------------------------------------- commit 1aec72e34e0e3da138c6e0105c509f20592f6bc6 Author: Andrey Mokhov Date: Tue Feb 16 03:12:11 2016 +0000 Drop matchBuildResult and associated functions. See #207. >--------------------------------------------------------------- 1aec72e34e0e3da138c6e0105c509f20592f6bc6 src/Way.hs | 36 ++---------------------------------- 1 file changed, 2 insertions(+), 34 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index c393437..340321c 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,13 +1,12 @@ module Way ( - WayUnit (..), Way, wayUnit, wayFromUnits, + WayUnit (..), Way, wayUnit, wayFromUnits, allWays, vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging, threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic, - allWays, wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, - libsuf, safeDetectWay, detectWay, matchBuildResult + wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf ) where import Base hiding (unit) @@ -160,37 +159,6 @@ libsuf way @ (Way set) = -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension --- | Detect way from a given 'FilePath'. Returns 'Nothing' if there is no match. --- --- * @'safeDetectWay' "foo/bar.hi" '==' 'Just' vanilla@ --- * @'safeDetectWay' "baz.thr_p_o" '==' 'Just' threadedProfiling@ --- * @'safeDetectWay' "qwe.ph_i" '==' 'Nothing' (expected "qwe.p_hi")@ --- * @'safeDetectWay' "xru.p_ghc7.11.123.so" '==' 'Just' profiling@ -safeDetectWay :: FilePath -> Maybe Way -safeDetectWay file = case reads prefix of - [(way, "")] -> Just way - _ -> Nothing - where - extension = takeExtension file - prefixed = if extension `notElem` [".so", ".dll", ".dynlib"] - then extension - else takeExtension . dropExtension . - dropExtension . dropExtension $ file - prefix = if extension == "a" - then drop 1 . dropWhile (/= '_') $ takeBaseName file - else drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed - --- Unsafe version of safeDetectWay. Useful when matchBuildResult has succeeded. -detectWay :: FilePath -> Way -detectWay = fromJust . safeDetectWay - --- Given a path, an extension suffix, and a file name check: --- 1) the file conforms to pattern 'path//*suffix' --- 2) file's extension has a valid way tag (i.e., safeDetectWay does not fail) -matchBuildResult :: FilePath -> String -> FilePath -> Bool -matchBuildResult path suffix file = - (path "*" ++ suffix) ?== file && isJust (safeDetectWay file) - -- Instances for storing in the Shake database instance Binary Way where put = put . show From git at git.haskell.org Fri Oct 27 00:21:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #279 from michalt/gcc-mm-mg/1 (197ca35) Message-ID: <20171027002109.216213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/197ca35ae05c95d3cf710c453630bd2ce399542a/ghc >--------------------------------------------------------------- commit 197ca35ae05c95d3cf710c453630bd2ce399542a Merge: a931066 c2d7e2a Author: Andrey Mokhov Date: Wed Aug 17 19:36:55 2016 +0100 Merge pull request #279 from michalt/gcc-mm-mg/1 Use GCC's `-MM`/`-MG` to find missing dependencies >--------------------------------------------------------------- 197ca35ae05c95d3cf710c453630bd2ce399542a src/Builder.hs | 3 ++- src/Rules/Compile.hs | 40 ++++++++++++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 17 ++++++++++++++++- src/Settings/Builders/Cc.hs | 13 ++++++++++++- 4 files changed, 70 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:21:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #72 from snowleopard/angerman-patch-4 (e97d689) Message-ID: <20171027002105.E63FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e97d6892c70c570c2425d7e49f8b5158f0e584cf/ghc >--------------------------------------------------------------- commit e97d6892c70c570c2425d7e49f8b5158f0e584cf Merge: e2fb954 79ceb45 Author: Andrey Mokhov Date: Thu Dec 31 18:42:46 2015 +0000 Merge pull request #72 from snowleopard/angerman-patch-4 Update README.md >--------------------------------------------------------------- e97d6892c70c570c2425d7e49f8b5158f0e584cf README.md | 29 +++++++++++------------------ 1 file changed, 11 insertions(+), 18 deletions(-) From git at git.haskell.org Fri Oct 27 00:21:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Match generator sources exactly, see #69 and #70. (6c80bd8) Message-ID: <20171027002109.9E5443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6c80bd874eb2d4ca9607009dcf33eedbe011d5cd/ghc >--------------------------------------------------------------- commit 6c80bd874eb2d4ca9607009dcf33eedbe011d5cd Author: Andrey Mokhov Date: Thu Dec 31 19:01:38 2015 +0000 Match generator sources exactly, see #69 and #70. >--------------------------------------------------------------- 6c80bd874eb2d4ca9607009dcf33eedbe011d5cd src/Rules/Generate.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index fd101a1..b53b2b8 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -83,11 +83,13 @@ generate file target expr = do generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let buildPath = targetPath stage pkg -/- "build" + dropBuild = drop (length buildPath + 1) generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) file <~ gen = generate file target gen in do generated ?> \file -> do - let pattern = "//" ++ takeBaseName file <.> "*" + let srcFile = dropBuild file + pattern = "//" ++ srcFile <.> "*" files <- fmap (filter (pattern ?==)) $ moduleFiles stage pkg let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ From git at git.haskell.org Fri Oct 27 00:21:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add matchVersionedFilePath and use for matching library targets. (5fcb480) Message-ID: <20171027002110.E324F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5fcb480b9e5efc1aea8c4b32965d65cdae5da766/ghc >--------------------------------------------------------------- commit 5fcb480b9e5efc1aea8c4b32965d65cdae5da766 Author: Andrey Mokhov Date: Tue Feb 16 17:30:13 2016 +0000 Add matchVersionedFilePath and use for matching library targets. >--------------------------------------------------------------- 5fcb480b9e5efc1aea8c4b32965d65cdae5da766 src/Base.hs | 19 ++++++++++++++++++- src/Rules/Library.hs | 22 ++++++++++++---------- 2 files changed, 30 insertions(+), 11 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 1a06120..feec868 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,12 +23,13 @@ module Base ( -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - removeFileIfExists, removeDirectoryIfExists + removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath ) where import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader +import Data.Char import Data.Function import Data.List.Extra import Data.Maybe @@ -175,3 +176,19 @@ removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f removeDirectoryIfExists :: FilePath -> Action () removeDirectoryIfExists d = liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d + +-- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the +-- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string +-- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: +-- +--- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ +--- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar-" "a" "foo/bar-0.1.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False'@ +matchVersionedFilePath :: String -> String -> FilePath -> Bool +matchVersionedFilePath prefix suffix filePath = + case stripPrefix prefix (unifyPath filePath) >>= stripSuffix suffix of + Nothing -> False + Just version -> all (\c -> isDigit c || c == '-' || c == '.') version diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index d77d58e..e53355f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -17,9 +17,10 @@ import Target buildPackageLibrary :: Context -> Rules () buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" + libHs = buildPath -/- "libHS" ++ pkgNameString package -- TODO: handle dynamic libraries - buildPath "*" ++ waySuffix way ++ ".a" %> \a -> do + matchVersionedFilePath libHs (waySuffix way <.> "a") ?> \a -> do removeFileIfExists a cSrcs <- cSources context hSrcs <- hSources context @@ -61,15 +62,16 @@ buildPackageLibrary context @ (Context {..}) = do -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. -- This happens with hsc2hs, which has top-level file HSCParser.hs. - when (package /= hsc2hs) $ priority 2 $ (buildPath -/- "HS*.o") %> \obj -> do - cSrcs <- cSources context - hSrcs <- hSources context - let cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs - , not ("//AutoApply.cmm" ?== src) ] - ++ [ src -<.> "o" | src <- cSrcs, "//AutoApply.cmm" ?== src ] - hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] - need $ cObjs ++ hObjs - build $ Target context Ld (cObjs ++ hObjs) [obj] + priority 2 $ when (package /= hsc2hs && way == vanilla) $ + (buildPath -/- "HS*.o") %> \obj -> do + cSrcs <- cSources context + hSrcs <- hSources context + let cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs + , not ("//AutoApply.cmm" ?== src) ] + ++ [ src -<.> "o" | src <- cSrcs, "//AutoApply.cmm" ?== src ] + hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] + need $ cObjs ++ hObjs + build $ Target context Ld (cObjs ++ hObjs) [obj] cSources :: Context -> Action [FilePath] cSources context = interpretInContext context $ getPkgDataList CSrcs From git at git.haskell.org Fri Oct 27 00:21:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use --flavour=quickest (0cfd96d) Message-ID: <20171027002112.C2CA53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0cfd96d4dd23ca565f9922357c64c769b78863c1/ghc >--------------------------------------------------------------- commit 0cfd96d4dd23ca565f9922357c64c769b78863c1 Author: Andrey Mokhov Date: Sat Aug 20 17:28:48 2016 +0100 Use --flavour=quickest >--------------------------------------------------------------- 0cfd96d4dd23ca565f9922357c64c769b78863c1 doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 4674ff4..a70f85a 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -11,9 +11,9 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ cd ghc stack exec -- git clone git://github.com/snowleopard/hadrian stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quick + stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quickest -The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quick` flag from the last command line (this will slow down the build to about an hour). +The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quickest` flag from the last command line (this will slow down the build to about an hour). #### Future ideas From git at git.haskell.org Fri Oct 27 00:21:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix extention, see #69 and #70. (26cd11f) Message-ID: <20171027002113.15A8C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/26cd11fb2e334f7a09e53bcd0d0e1dbc4cb646fe/ghc >--------------------------------------------------------------- commit 26cd11fb2e334f7a09e53bcd0d0e1dbc4cb646fe Author: Andrey Mokhov Date: Thu Dec 31 19:12:39 2015 +0000 Fix extention, see #69 and #70. >--------------------------------------------------------------- 26cd11fb2e334f7a09e53bcd0d0e1dbc4cb646fe src/Rules/Generate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index b53b2b8..d8f7129 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -89,7 +89,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = in do generated ?> \file -> do let srcFile = dropBuild file - pattern = "//" ++ srcFile <.> "*" + pattern = "//" ++ srcFile -<.> "*" files <- fmap (filter (pattern ?==)) $ moduleFiles stage pkg let gens = [ (f, b) | f <- files, Just b <- [determineBuilder f] ] when (length gens /= 1) . putError $ From git at git.haskell.org Fri Oct 27 00:21:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hide Shake.parallel. Again. (89c79cd) Message-ID: <20171027002114.62FC83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/89c79cdb52a9feeb949148348afffdd8cc150450/ghc >--------------------------------------------------------------- commit 89c79cdb52a9feeb949148348afffdd8cc150450 Author: Andrey Mokhov Date: Tue Feb 16 18:00:52 2016 +0000 Hide Shake.parallel. Again. >--------------------------------------------------------------- 89c79cdb52a9feeb949148348afffdd8cc150450 src/Base.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index feec868..a794ea8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel module Base ( -- * General utilities module Control.Applicative, @@ -34,7 +35,7 @@ import Data.Function import Data.List.Extra import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>), Normal) +import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Fri Oct 27 00:21:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a Stack build script for Windows (bbd884c) Message-ID: <20171027002117.1A19D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbd884c841d8508abb3dabbbb5cf5abe2e69f4da/ghc >--------------------------------------------------------------- commit bbd884c841d8508abb3dabbbb5cf5abe2e69f4da Author: Andrey Mokhov Date: Sat Aug 20 18:02:33 2016 +0100 Add a Stack build script for Windows See #283 >--------------------------------------------------------------- bbd884c841d8508abb3dabbbb5cf5abe2e69f4da build.stack.bat | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/build.stack.bat b/build.stack.bat new file mode 100644 index 0000000..3586290 --- /dev/null +++ b/build.stack.bat @@ -0,0 +1,8 @@ + at rem Change the current directory to the one containing this script + at cd %~dp0 + + at rem Build Hadrian and dependencies + at stack build + + at rem Run Hadrian in GHC top directory forwarding additional user arguments + at stack exec hadrian -- --lint --directory ".." %* From git at git.haskell.org Fri Oct 27 00:21:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename builder arguments, fix #60. (56705eb) Message-ID: <20171027002117.259523A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56705eb7ed074516a370054db7e3b81bae1afca4/ghc >--------------------------------------------------------------- commit 56705eb7ed074516a370054db7e3b81bae1afca4 Author: Andrey Mokhov Date: Fri Jan 1 01:23:21 2016 +0000 Rename builder arguments, fix #60. >--------------------------------------------------------------- 56705eb7ed074516a370054db7e3b81bae1afca4 src/Settings/Args.hs | 32 ++++++++++++++++---------------- src/Settings/Builders/Alex.hs | 10 +++++----- src/Settings/Builders/Ar.hs | 14 +++++++------- src/Settings/Builders/DeriveConstants.hs | 6 +++--- src/Settings/Builders/Gcc.hs | 10 +++++----- src/Settings/Builders/GenPrimopCode.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 12 ++++++------ src/Settings/Builders/GhcCabal.hs | 11 ++++++----- src/Settings/Builders/GhcPkg.hs | 6 +++--- src/Settings/Builders/Haddock.hs | 6 +++--- src/Settings/Builders/Happy.hs | 12 ++++++------ src/Settings/Builders/HsCpp.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 6 +++--- src/Settings/Builders/Ld.hs | 6 +++--- 14 files changed, 72 insertions(+), 71 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 56705eb7ed074516a370054db7e3b81bae1afca4 From git at git.haskell.org Fri Oct 27 00:21:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out buildPackageGhciLibrary from buildPackageLibrary and make it more robust. (c0b1a37) Message-ID: <20171027002118.504A93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c0b1a37c9681fb98ed85bbccb4004fad993c58f2/ghc >--------------------------------------------------------------- commit c0b1a37c9681fb98ed85bbccb4004fad993c58f2 Author: Andrey Mokhov Date: Tue Feb 16 19:15:47 2016 +0000 Factor out buildPackageGhciLibrary from buildPackageLibrary and make it more robust. See #207. >--------------------------------------------------------------- c0b1a37c9681fb98ed85bbccb4004fad993c58f2 src/Rules.hs | 2 ++ src/Rules/Library.hs | 19 +++++++++++-------- 2 files changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 74ffe30..444a2cb 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -61,6 +61,7 @@ packageRules = do let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] + -- TODO: not all build rules make sense for all stage/package combinations let contexts = liftM3 Context allStages knownPackages allWays vanillaContexts = liftM2 vanillaContext allStages knownPackages @@ -72,6 +73,7 @@ packageRules = do [ buildPackageData , buildPackageDependencies readPackageDb , buildPackageDocumentation + , buildPackageGhciLibrary , generatePackageCode , buildProgram , registerPackage writePackageDb ] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index e53355f..c6d92a5 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,5 +1,7 @@ {-# LANGUAGE RecordWildCards #-} -module Rules.Library (buildPackageLibrary, cSources, hSources) where +module Rules.Library ( + buildPackageLibrary, buildPackageGhciLibrary, cSources, hSources + ) where import Data.Char import qualified System.Directory as IO @@ -17,10 +19,10 @@ import Target buildPackageLibrary :: Context -> Rules () buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" - libHs = buildPath -/- "libHS" ++ pkgNameString package + libPrefix = buildPath -/- "libHS" ++ pkgNameString package -- TODO: handle dynamic libraries - matchVersionedFilePath libHs (waySuffix way <.> "a") ?> \a -> do + matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do removeFileIfExists a cSrcs <- cSources context hSrcs <- hSources context @@ -58,12 +60,13 @@ buildPackageLibrary context @ (Context {..}) = do a (dropWhileEnd isPunctuation synopsis) +buildPackageGhciLibrary :: Context -> Rules () +buildPackageGhciLibrary context @ (Context {..}) = priority 2 $ do + let buildPath = targetPath stage package -/- "build" + libPrefix = buildPath -/- "HS" ++ pkgNameString package + -- TODO: simplify handling of AutoApply.cmm - -- TODO: this looks fragile as haskell objects can match this rule if their - -- names start with "HS" and they are on top of the module hierarchy. - -- This happens with hsc2hs, which has top-level file HSCParser.hs. - priority 2 $ when (package /= hsc2hs && way == vanilla) $ - (buildPath -/- "HS*.o") %> \obj -> do + matchVersionedFilePath libPrefix (waySuffix way <.> "o") ?> \obj -> do cSrcs <- cSources context hSrcs <- hSources context let cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs From git at git.haskell.org Fri Oct 27 00:21:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update GhcPkg.hs (6dbe055) Message-ID: <20171027002121.10AB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6dbe055462a3d943ade75da94f3e1d8f42d23d0d/ghc >--------------------------------------------------------------- commit 6dbe055462a3d943ade75da94f3e1d8f42d23d0d Author: Moritz Angermann Date: Fri Jan 1 14:31:07 2016 +0800 Update GhcPkg.hs - Fix package conf path. - Adds comment - Drops the left over comments from previous. >--------------------------------------------------------------- 6dbe055462a3d943ade75da94f3e1d8f42d23d0d src/Rules/Wrappers/GhcPkg.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Rules/Wrappers/GhcPkg.hs b/src/Rules/Wrappers/GhcPkg.hs index 3f70617..3e077ac 100644 --- a/src/Rules/Wrappers/GhcPkg.hs +++ b/src/Rules/Wrappers/GhcPkg.hs @@ -4,17 +4,14 @@ import Base import Expression import Oracles --- Note about wrapper: --- bindir is usually GhcSourcePath / inplace / bin --- topdir is usually GhcSourcePath / inplace / lib --- datadir is usually the same as topdir - ghcPkgWrapper :: FilePath -> Expr String ghcPkgWrapper program = do lift $ need [sourcePath -/- "Rules/Wrappers/GhcPkg.hs"] top <- getSetting GhcSourcePath stage <- getStage - let pkgConf = top -/- packageConfiguration stage + -- Use the package configuration for the next stage in the wrapper. + -- The wrapper is generated in StageN, but used in StageN+1. + let pkgConf = top -/- packageConfiguration (succ stage) return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) From git at git.haskell.org Fri Oct 27 00:21:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant imports (082f17b) Message-ID: <20171027002121.5410A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/082f17b3c86e559d45e117226094e85923883013/ghc >--------------------------------------------------------------- commit 082f17b3c86e559d45e117226094e85923883013 Author: Andrey Mokhov Date: Sat Aug 20 18:17:37 2016 +0100 Drop redundant imports >--------------------------------------------------------------- 082f17b3c86e559d45e117226094e85923883013 src/Rules/Compile.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 001068a..8f8d92a 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -11,8 +11,6 @@ import Target import Development.Shake.Util -import Data.Maybe -import Data.List import qualified Data.Set as Set compilePackage :: [(Resource, Int)] -> Context -> Rules () From git at git.haskell.org Fri Oct 27 00:21:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use matchVersionedFilePath in registerPackage build rule. (f0f4193) Message-ID: <20171027002122.54A9F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f0f4193049fabd48cd1c0b5e37849319849b9bf5/ghc >--------------------------------------------------------------- commit f0f4193049fabd48cd1c0b5e37849319849b9bf5 Author: Andrey Mokhov Date: Tue Feb 16 19:16:33 2016 +0000 Use matchVersionedFilePath in registerPackage build rule. See #207. >--------------------------------------------------------------- f0f4193049fabd48cd1c0b5e37849319849b9bf5 src/Rules/Register.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 01d8ab9..85fac80 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -1,8 +1,6 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Register (registerPackage) where -import Data.Char - import Base import Context import Expression @@ -18,12 +16,9 @@ registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context @ (Context {..}) = do let oldPath = pkgPath package -/- targetDirectory stage package -- TODO: remove, #113 pkgConf = packageDbDirectory stage -/- pkgNameString package - match f = case stripPrefix (pkgConf ++ "-") f of - Nothing -> False - Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf" - when (stage <= Stage1) $ match ?> \conf -> do - -- This produces pkgConfig. TODO: Add explicit tracking + when (stage <= Stage1) $ matchVersionedFilePath pkgConf "conf" ?> \conf -> do + -- This produces inplace-pkg-config. TODO: Add explicit tracking need [pkgDataFile stage package] -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 From git at git.haskell.org Fri Oct 27 00:21:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #74 from snowleopard/angerman-patch-5 (77655b7) Message-ID: <20171027002124.CE3773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/77655b7c31c2e37c83bbe36937d4ca65dee74701/ghc >--------------------------------------------------------------- commit 77655b7c31c2e37c83bbe36937d4ca65dee74701 Merge: 56705eb 6dbe055 Author: Andrey Mokhov Date: Fri Jan 1 09:55:54 2016 +0000 Merge pull request #74 from snowleopard/angerman-patch-5 Update GhcPkg.hs >--------------------------------------------------------------- 77655b7c31c2e37c83bbe36937d4ca65dee74701 src/Rules/Wrappers/GhcPkg.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 00:21:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix comments (676ec2e) Message-ID: <20171027002125.27B923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/676ec2eabce5fd13ad9deb172d5041d461be01e7/ghc >--------------------------------------------------------------- commit 676ec2eabce5fd13ad9deb172d5041d461be01e7 Author: Andrey Mokhov Date: Sat Aug 20 19:57:26 2016 +0100 Fix comments [skip ci] >--------------------------------------------------------------- 676ec2eabce5fd13ad9deb172d5041d461be01e7 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 6fbc3b2..87bedb8 100644 --- a/.gitignore +++ b/.gitignore @@ -13,7 +13,7 @@ cabal.sandbox.config # build.cabal-new.sh specific /dist-newstyle/ -# build.stack.sh specific +# build.stack.sh and build.stack.bat specific /.stack-work/ # the user settings From git at git.haskell.org Fri Oct 27 00:21:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add tests for matchVersionedFilePath. (0b68ae8) Message-ID: <20171027002125.CCC5E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b68ae8b754a400577dbd05e646764742251ec27/ghc >--------------------------------------------------------------- commit 0b68ae8b754a400577dbd05e646764742251ec27 Author: Andrey Mokhov Date: Tue Feb 16 19:26:37 2016 +0000 Add tests for matchVersionedFilePath. >--------------------------------------------------------------- 0b68ae8b754a400577dbd05e646764742251ec27 src/Base.hs | 1 + src/Rules/Selftest.hs | 13 ++++++++++++- 2 files changed, 13 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index a794ea8..372ec78 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -183,6 +183,7 @@ removeDirectoryIfExists d = -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: -- --- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'True'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ --- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index a3cc089..5fafda5 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -3,8 +3,10 @@ module Rules.Selftest (selftestRules) where import Development.Shake -import Settings.Builders.Ar (chunksOfSize) import Test.QuickCheck + +import Base +import Settings.Builders.Ar (chunksOfSize) import Way instance Arbitrary Way where @@ -22,6 +24,15 @@ selftestRules = in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res test $ chunksOfSize 3 ["a","b","c","defg","hi","jk"] == [["a","b","c"],["defg"],["hi"],["jk"]] + test $ matchVersionedFilePath "foo/bar" ".a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" ".a" "foo\\bar.a" == True + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" "" "foo/bar.a" == False + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar-" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar/" "a" "foo/bar-0.1.a" == False + + -- TODO: add automated tests for matchVersionedFilePath too test :: Testable a => a -> Action () test = liftIO . quickCheck From git at git.haskell.org Fri Oct 27 00:21:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GenApply builder, #22. (4b70d6e) Message-ID: <20171027002129.03DD23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b70d6e8c474ba0a7789be0b3009e625c1a27820/ghc >--------------------------------------------------------------- commit 4b70d6e8c474ba0a7789be0b3009e625c1a27820 Author: Andrey Mokhov Date: Sat Jan 2 02:09:27 2016 +0000 Add GenApply builder, #22. >--------------------------------------------------------------- 4b70d6e8c474ba0a7789be0b3009e625c1a27820 cfg/system.config.in | 1 + shaking-up-ghc.cabal | 4 +++- src/Builder.hs | 2 ++ src/Rules/Actions.hs | 16 ++++++++++------ src/Settings/Args.hs | 4 ++++ src/Settings/Builders/GenApply.hs | 8 ++++++++ 6 files changed, 28 insertions(+), 7 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index a2cfef3..c5808c7 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -22,6 +22,7 @@ haddock = inplace/bin/haddock hsc2hs = inplace/bin/hsc2hs genprimopcode = inplace/bin/genprimopcode +genapply = inplace/bin/genapply derive-constants = inplace/bin/deriveConstants hs-cpp = @HaskellCPPCmd@ diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 2c75566..48dd0b8 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -38,6 +38,7 @@ executable ghc-shake , Rules.Cabal , Rules.Compile , Rules.Config + , Rules.Copy , Rules.Data , Rules.Dependencies , Rules.Documentation @@ -48,7 +49,6 @@ executable ghc-shake , Rules.Generators.GhcPlatformH , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs - , Rules.Install , Rules.Library , Rules.Oracles , Rules.Package @@ -63,6 +63,7 @@ executable ghc-shake , Settings.Builders.Common , Settings.Builders.DeriveConstants , Settings.Builders.Gcc + , Settings.Builders.GenApply , Settings.Builders.GenPrimopCode , Settings.Builders.Ghc , Settings.Builders.GhcCabal @@ -82,6 +83,7 @@ executable ghc-shake , Settings.Packages.Haddock , Settings.Packages.Hp2ps , Settings.Packages.IntegerGmp + , Settings.Packages.Rts , Settings.Packages.RunGhc , Settings.TargetDirectory , Settings.User diff --git a/src/Builder.hs b/src/Builder.hs index b4b01c3..c8e3f6e 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -25,6 +25,7 @@ data Builder = Alex | DeriveConstants | Gcc Stage | GccM Stage + | GenApply | GenPrimopCode | Ghc Stage | GhcCabal @@ -60,6 +61,7 @@ builderKey builder = case builder of Gcc Stage0 -> "system-gcc" Gcc _ -> "gcc" GccM stage -> builderKey $ Gcc stage -- synonym for 'Gcc -MM' + GenApply -> "genapply" GenPrimopCode -> "genprimopcode" Ghc Stage0 -> "system-ghc" Ghc Stage1 -> "ghc-stage1" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 8b243eb..e930b52 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -27,14 +27,12 @@ buildWithResources rs target = do quietlyUnlessVerbose $ case builder of Ar -> arCmd path argList - HsCpp -> do - let file = head $ Target.outputs target -- TODO: ugly - Stdout output <- cmd [path] argList - writeFileChanged file output + HsCpp -> captureStdout target path argList + GenApply -> captureStdout target path argList GenPrimopCode -> do - let src = head $ Target.inputs target -- TODO: ugly - file = head $ Target.outputs target + src <- interpret target getInput + file <- interpret target getOutput input <- readFile' src Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output @@ -45,6 +43,12 @@ buildWithResources rs target = do build :: Target -> Action () build = buildWithResources [] +captureStdout :: Target -> FilePath -> [String] -> Action () +captureStdout target path argList = do + file <- interpret target getOutput + Stdout output <- cmd [path] argList + writeFileChanged file output + -- Print out key information about the command being executed putInfo :: Target.Target -> Action () putInfo (Target.Target {..}) = putBuild $ renderBox $ diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 8066e81..c4c919c 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -7,6 +7,7 @@ import Settings.Builders.Alex import Settings.Builders.Ar import Settings.Builders.DeriveConstants import Settings.Builders.Gcc +import Settings.Builders.GenApply import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc import Settings.Builders.GhcCabal @@ -25,6 +26,7 @@ import Settings.Packages.GhcPrim import Settings.Packages.Haddock import Settings.Packages.Hp2ps import Settings.Packages.IntegerGmp +import Settings.Packages.Rts import Settings.Packages.RunGhc import Settings.User @@ -44,6 +46,7 @@ defaultBuilderArgs = mconcat , deriveConstantsBuilderArgs , gccBuilderArgs , gccMBuilderArgs + , genApplyBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs , ghcCabalBuilderArgs @@ -67,4 +70,5 @@ defaultPackageArgs = mconcat , haddockPackageArgs , hp2psPackageArgs , integerGmpPackageArgs + , rtsPackageArgs , runGhcPackageArgs ] diff --git a/src/Settings/Builders/GenApply.hs b/src/Settings/Builders/GenApply.hs new file mode 100644 index 0000000..2d8140a --- /dev/null +++ b/src/Settings/Builders/GenApply.hs @@ -0,0 +1,8 @@ +module Settings.Builders.GenApply (genApplyBuilderArgs) where + +import Expression + +-- Stdin/stdout are handled in a special way. See Rules/Actions.hs. +-- TODO: Dead code? ifeq "$(GhcUnregisterised)" "YES" GENAPPLY_OPTS = -u +genApplyBuilderArgs :: Args +genApplyBuilderArgs = mempty From git at git.haskell.org Fri Oct 27 00:21:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bump stack to lts-6.12 and remove extra pkg from extra-deps (e789d21) Message-ID: <20171027002129.6335B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e789d211296f7abc031af5e1ab19d2633f7de745/ghc >--------------------------------------------------------------- commit e789d211296f7abc031af5e1ab19d2633f7de745 Author: Michal Terepeta Date: Sun Aug 21 13:46:48 2016 +0200 Bump stack to lts-6.12 and remove extra pkg from extra-deps Signed-off-by: Michal Terepeta >--------------------------------------------------------------- e789d211296f7abc031af5e1ab19d2633f7de745 stack.yaml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/stack.yaml b/stack.yaml index 9eb4cfb..5fa9f94 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,7 +1,7 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-5.17 +resolver: lts-6.12 # Local packages, usually specified by relative directory name packages: @@ -10,7 +10,6 @@ packages: # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: -- extra-1.4.7 # Override default flag values for local packages and extra-deps flags: {} From git at git.haskell.org Fri Oct 27 00:21:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't unify paths as it seems prone to surprises. (a849c93) Message-ID: <20171027002129.6DB963A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a849c93a1f092e6c611d1bd4fae68b91612bfadb/ghc >--------------------------------------------------------------- commit a849c93a1f092e6c611d1bd4fae68b91612bfadb Author: Andrey Mokhov Date: Tue Feb 16 23:09:34 2016 +0000 Don't unify paths as it seems prone to surprises. >--------------------------------------------------------------- a849c93a1f092e6c611d1bd4fae68b91612bfadb src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 372ec78..769fdc4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -183,7 +183,7 @@ removeDirectoryIfExists d = -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: -- --- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'False'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ --- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ @@ -191,6 +191,6 @@ removeDirectoryIfExists d = --- * @'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False'@ matchVersionedFilePath :: String -> String -> FilePath -> Bool matchVersionedFilePath prefix suffix filePath = - case stripPrefix prefix (unifyPath filePath) >>= stripSuffix suffix of + case stripPrefix prefix filePath >>= stripSuffix suffix of Nothing -> False Just version -> all (\c -> isDigit c || c == '-' || c == '.') version From git at git.haskell.org Fri Oct 27 00:21:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename installRules into copyRules and add copy rules for ffi*.h files, #22. (3872f96) Message-ID: <20171027002132.770A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3872f96896f53e4967674a7e4839dfd0fe1700b7/ghc >--------------------------------------------------------------- commit 3872f96896f53e4967674a7e4839dfd0fe1700b7 Author: Andrey Mokhov Date: Sat Jan 2 02:12:02 2016 +0000 Rename installRules into copyRules and add copy rules for ffi*.h files, #22. >--------------------------------------------------------------- 3872f96896f53e4967674a7e4839dfd0fe1700b7 src/Main.hs | 4 ++-- src/Rules/Copy.hs | 32 ++++++++++++++++++++++++++++++++ src/Rules/Install.hs | 22 ---------------------- 3 files changed, 34 insertions(+), 24 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index fdc43cd..b2c5340 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,14 +3,14 @@ import Rules import Rules.Cabal import Rules.Config import Rules.Generate -import Rules.Install +import Rules.Copy import Rules.Oracles main :: IO () main = shakeArgs options $ do cabalRules -- see Rules.Cabal configRules -- see Rules.Config - installRules -- see Rules.Install + copyRules -- see Rules.Copy generateTargets -- see Rules generateRules -- see Rules.Generate oracleRules -- see Rules.Oracles diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs new file mode 100644 index 0000000..47d6f02 --- /dev/null +++ b/src/Rules/Copy.hs @@ -0,0 +1,32 @@ +module Rules.Copy (installTargets, copyRules) where + +import Base +import Expression +import GHC +import Rules.Generate +import Settings.TargetDirectory + +installTargets :: [FilePath] +installTargets = [ "inplace/lib/template-hsc.h" + , "inplace/lib/platformConstants" + , "inplace/lib/settings" ] + +copyRules :: Rules () +copyRules = do + targetPath Stage1 rts -/- "build/ffi*.h" %> \ffih -> do + ffiHPaths <- getDirectoryFiles "" ["libffi/build/inst/lib/*/include/ffi.h"] + when (length ffiHPaths /= 1) $ + putError "copyRules: cannot determine location of ffi.h" + let ffiHPath = takeDirectory $ head ffiHPaths + copy ffih ffiHPath + + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs + "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." + where + file <~ dir = file %> \_ -> copy file dir + + copy file dir = do + let source = dir -/- takeFileName file + copyFileChanged source file + putBuild $ "| Copy " ++ source ++ " -> " ++ file diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs deleted file mode 100644 index 2e74bd3..0000000 --- a/src/Rules/Install.hs +++ /dev/null @@ -1,22 +0,0 @@ -module Rules.Install (installTargets, installRules) where - -import Base -import Expression -import GHC -import Rules.Generate - -installTargets :: [FilePath] -installTargets = [ "inplace/lib/template-hsc.h" - , "inplace/lib/platformConstants" - , "inplace/lib/settings" ] - -installRules :: Rules () -installRules = do - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs - "inplace/lib/platformConstants" <~ derivedConstantsPath - "inplace/lib/settings" <~ "." - where - file <~ dir = file %> \out -> do - let source = dir -/- takeFileName out - copyFileChanged source out - putSuccess $ "| Installed " ++ source ++ " -> " ++ out From git at git.haskell.org Fri Oct 27 00:21:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #284 from michalt/stack/lts612extra (c7f8ae2) Message-ID: <20171027002133.79C4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7f8ae2442955879660752c880405c0c3780f7f4/ghc >--------------------------------------------------------------- commit c7f8ae2442955879660752c880405c0c3780f7f4 Merge: 676ec2e e789d21 Author: Andrey Mokhov Date: Sun Aug 21 17:03:02 2016 +0100 Merge pull request #284 from michalt/stack/lts612extra Bump stack to lts-6.12 and remove extra pkg from extra-deps >--------------------------------------------------------------- c7f8ae2442955879660752c880405c0c3780f7f4 stack.yaml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 00:21:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build-tools Alex and Happy. (4e58441) Message-ID: <20171027002136.DEB453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e584418c121e02029e6dfdd52bbd397e8bb034b/ghc >--------------------------------------------------------------- commit 4e584418c121e02029e6dfdd52bbd397e8bb034b Author: Andrey Mokhov Date: Thu Sep 1 15:42:33 2016 +0100 Add build-tools Alex and Happy. >--------------------------------------------------------------- 4e584418c121e02029e6dfdd52bbd397e8bb034b hadrian.cabal | 2 ++ 1 file changed, 2 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 41cccd8..3e34b16 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -129,6 +129,8 @@ executable hadrian , shake >= 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* + build-tools: alex >= 3.1 + , happy >= 1.19.4 ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 From git at git.haskell.org Fri Oct 27 00:21:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Data.Bifunctor.bimap as it is now available on bootstrapping GHC. (cbbbc63) Message-ID: <20171027002137.01F093A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbbbc63883b41b794d154efbb7a166ea659980db/ghc >--------------------------------------------------------------- commit cbbbc63883b41b794d154efbb7a166ea659980db Author: Andrey Mokhov Date: Wed Feb 17 01:59:11 2016 +0000 Use Data.Bifunctor.bimap as it is now available on bootstrapping GHC. >--------------------------------------------------------------- cbbbc63883b41b794d154efbb7a166ea659980db src/Base.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 769fdc4..7d63fa0 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -3,6 +3,7 @@ module Base ( -- * General utilities module Control.Applicative, module Control.Monad.Extra, + module Data.Bifunctor, module Data.Function, module Data.List.Extra, module Data.Maybe, @@ -22,7 +23,7 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, + minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath ) where @@ -30,6 +31,7 @@ module Base ( import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader +import Data.Bifunctor import Data.Char import Data.Function import Data.List.Extra @@ -142,11 +144,6 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg --- Explicit definition to avoid dependency on Data.Bifunctor --- | Bifunctor bimap. -bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) -bimap f g (x, y) = (f x, g y) - -- Explicit definition to avoid dependency on Data.List.Ordered -- | Difference of two ordered lists. minusOrd :: Ord a => [a] -> [a] -> [a] From git at git.haskell.org Fri Oct 27 00:21:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Selftest, add more tests for matchVersionedFilePath. (8ae1c56) Message-ID: <20171027002133.7CA503A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ae1c564d861871d9b587d3525c704e3625a4864/ghc >--------------------------------------------------------------- commit 8ae1c564d861871d9b587d3525c704e3625a4864 Author: Andrey Mokhov Date: Tue Feb 16 23:10:12 2016 +0000 Refactor Selftest, add more tests for matchVersionedFilePath. >--------------------------------------------------------------- 8ae1c564d861871d9b587d3525c704e3625a4864 src/Rules/Selftest.hs | 54 ++++++++++++++++++++++++++++++++++----------------- 1 file changed, 36 insertions(+), 18 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 5fafda5..70a4023 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -15,24 +15,42 @@ instance Arbitrary Way where instance Arbitrary WayUnit where arbitrary = arbitraryBoundedEnum +test :: Testable a => a -> Action () +test = liftIO . quickCheck + selftestRules :: Rules () selftestRules = "selftest" ~> do - test $ \(x :: Way) -> read (show x) == x - test $ \n xs -> - let res = chunksOfSize n xs - in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res - test $ chunksOfSize 3 ["a","b","c","defg","hi","jk"] == [["a","b","c"],["defg"],["hi"],["jk"]] - - test $ matchVersionedFilePath "foo/bar" ".a" "foo/bar.a" == True - test $ matchVersionedFilePath "foo/bar" ".a" "foo\\bar.a" == True - test $ matchVersionedFilePath "foo/bar" "a" "foo/bar.a" == True - test $ matchVersionedFilePath "foo/bar" "" "foo/bar.a" == False - test $ matchVersionedFilePath "foo/bar" "a" "foo/bar-0.1.a" == True - test $ matchVersionedFilePath "foo/bar-" "a" "foo/bar-0.1.a" == True - test $ matchVersionedFilePath "foo/bar/" "a" "foo/bar-0.1.a" == False - - -- TODO: add automated tests for matchVersionedFilePath too - -test :: Testable a => a -> Action () -test = liftIO . quickCheck + testWays + testChunksOfSize + testMatchVersionedFilePath + +testWays :: Action () +testWays = do + putBuild $ "==== Read Way, Show Way" + test $ \(x :: Way) -> read (show x) == x + +testChunksOfSize :: Action () +testChunksOfSize = do + putBuild $ "==== chunksOfSize" + test $ chunksOfSize 3 [ "a", "b", "c" , "defg" , "hi" , "jk" ] + == [ ["a", "b", "c"], ["defg"], ["hi"], ["jk"] ] + test $ \n xs -> + let res = chunksOfSize n xs + in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res + +testMatchVersionedFilePath :: Action () +testMatchVersionedFilePath = do + putBuild $ "==== matchVersionedFilePath" + test $ matchVersionedFilePath "foo/bar" ".a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" ".a" "foo\\bar.a" == False + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" "" "foo/bar.a" == False + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar-" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar/" "a" "foo/bar-0.1.a" == False + + test $ \prefix suffix -> forAll versions $ \version -> + matchVersionedFilePath prefix suffix (prefix ++ version ++ suffix) + where + versions = listOf . elements $ '-' : '.' : ['0'..'9'] From git at git.haskell.org Fri Oct 27 00:21:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add basic support for rts package, #22. (34488df) Message-ID: <20171027002135.ED7B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34488dfe235c8793012a53a407359dcf0dff80b4/ghc >--------------------------------------------------------------- commit 34488dfe235c8793012a53a407359dcf0dff80b4 Author: Andrey Mokhov Date: Sat Jan 2 02:12:49 2016 +0000 Add basic support for rts package, #22. >--------------------------------------------------------------- 34488dfe235c8793012a53a407359dcf0dff80b4 src/GHC.hs | 17 ++-- src/Predicates.hs | 12 ++- src/Rules.hs | 8 +- src/Rules/Cabal.hs | 2 +- src/Rules/Data.hs | 18 +++++ src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 4 +- src/Rules/Generate.hs | 18 +++-- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Builders/Haddock.hs | 3 +- src/Settings/Packages.hs | 3 +- src/Settings/Packages/Rts.hs | 165 +++++++++++++++++++++++++++++++++++++++ 12 files changed, 228 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 34488dfe235c8793012a53a407359dcf0dff80b4 From git at git.haskell.org Fri Oct 27 00:21:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Ranlib and Tar builders. (d06dabc) Message-ID: <20171027002139.B378C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d06dabcb601c169ad1f8742e318d899891b380e3/ghc >--------------------------------------------------------------- commit d06dabcb601c169ad1f8742e318d899891b380e3 Author: Andrey Mokhov Date: Sun Jan 3 01:09:34 2016 +0000 Add Ranlib and Tar builders. >--------------------------------------------------------------- d06dabcb601c169ad1f8742e318d899891b380e3 cfg/system.config.in | 2 ++ src/Builder.hs | 4 ++++ src/Settings/Args.hs | 4 +++- src/Settings/Builders/Tar.hs | 10 ++++++++++ 4 files changed, 19 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index c5808c7..7f9b8de 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -38,6 +38,8 @@ hscolour = @HSCOLOUR@ ld = @LdCmd@ nm = @NmCmd@ objdump = @ObjdumpCmd@ +ranlib = @REAL_RANLIB_CMD@ +tar = @TarCmd@ # Information about builders: #============================ diff --git a/src/Builder.hs b/src/Builder.hs index c8e3f6e..ad7c9f0 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -41,6 +41,8 @@ data Builder = Alex | Ld | Nm | Objdump + | Ranlib + | Tar | Unlit deriving (Show, Eq, Generic) @@ -81,6 +83,8 @@ builderKey builder = case builder of Ld -> "ld" Nm -> "nm" Objdump -> "objdump" + Ranlib -> "ranlib" + Tar -> "tar" Unlit -> "unlit" -- | Determine the location of a 'Builder' diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index c4c919c..a677c80 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -17,6 +17,7 @@ import Settings.Builders.Happy import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld +import Settings.Builders.Tar import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Directory @@ -57,7 +58,8 @@ defaultBuilderArgs = mconcat , happyBuilderArgs , hsc2hsBuilderArgs , hsCppBuilderArgs - , ldBuilderArgs ] + , ldBuilderArgs + , tarBuilderArgs ] defaultPackageArgs :: Args defaultPackageArgs = mconcat diff --git a/src/Settings/Builders/Tar.hs b/src/Settings/Builders/Tar.hs new file mode 100644 index 0000000..1f9f0ba --- /dev/null +++ b/src/Settings/Builders/Tar.hs @@ -0,0 +1,10 @@ +module Settings.Builders.Tar (tarBuilderArgs) where + +import Expression +import Predicates (builder) + +tarBuilderArgs :: Args +tarBuilderArgs = builder Tar ? do + mconcat [ arg "-xzf" + , arg =<< getInput + , arg "-C", arg =<< getOutput ] From git at git.haskell.org Fri Oct 27 00:21:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Stack to download bootstrapping GHC and install MSYS2. (f644b3f) Message-ID: <20171027002140.66ADC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f644b3fc638631388a343c533f9eb5c49957ffe0/ghc >--------------------------------------------------------------- commit f644b3fc638631388a343c533f9eb5c49957ffe0 Author: Andrey Mokhov Date: Thu Sep 1 17:43:53 2016 +0100 Use Stack to download bootstrapping GHC and install MSYS2. >--------------------------------------------------------------- f644b3fc638631388a343c533f9eb5c49957ffe0 appveyor.yml | 51 +++++++++++++++++++++++---------------------------- 1 file changed, 23 insertions(+), 28 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 30e3bcf..ffca700 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -1,41 +1,36 @@ -clone_folder: "C:\\msys64\\home\\ghc\\hadrian" +clone_folder: "c:\\ghc\\hadrian" environment: global: STACK_ROOT: "c:\\sr" cache: - - "c:\\sr" + - "c:\\sr -> appveyor.yml" install: - - cd - - set MSYSTEM=MINGW64 - - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\bin;C:\msys64;%PATH% - - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% + # Get Stack - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ - - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ - - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + # Fetch GHC sources into c:\ghc + # Note: Appveyor has already cloned Hadrian into c:\ghc\hadrian, so it's tricky + - cd .. + - git init + - git remote add origin git://git.haskell.org/ghc.git + - git pull --recurse-submodules origin master + - git submodule update --init --recursive - - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - ghc --version - - stack --version - - alex --version - - happy --version - - stack exec -- ghc-pkg list - - cd C:\msys64\home\ghc - - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" + # Install all Hadrian and GHC build dependencies + - cd hadrian + - stack setup + - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: - - cd C:\msys64\home\ghc\hadrian - - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest - - C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 + # Build Hadrian + - stack build + # Run internal Hadrian tests + - stack exec hadrian -- selftest + # Build GHC + - echo "" | stack --no-terminal exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + # Test GHC binary + - cd .. + - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:21:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Ensure that if ghc compilation fails then we return a non-zero error code from build.bat (e40e2e0) Message-ID: <20171027002140.9FBFA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e40e2e0e80d81f88d374a6e917b660befdde46b4/ghc >--------------------------------------------------------------- commit e40e2e0e80d81f88d374a6e917b660befdde46b4 Author: Neil Mitchell Date: Wed Feb 17 16:24:19 2016 +0000 Ensure that if ghc compilation fails then we return a non-zero error code from build.bat >--------------------------------------------------------------- e40e2e0e80d81f88d374a6e917b660befdde46b4 build.bat | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/build.bat b/build.bat index 348537d..10a6969 100644 --- a/build.bat +++ b/build.bat @@ -21,8 +21,8 @@ @ghc %ghcArgs% - at if %ERRORLEVEL% EQU 0 ( - @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains - @set GHC_PACKAGE_PATH= - @.shake\build %shakeArgs% -) + at if %ERRORLEVEL% NEQ 0 EXIT /B %ERRORLEVEL% + + at rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains + at set GHC_PACKAGE_PATH= + at .shake\build %shakeArgs% From git at git.haskell.org Fri Oct 27 00:21:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add COMPONENT_ID field to rts package-data.mk (#22). (d3eef6d) Message-ID: <20171027002143.C2EF93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3eef6dc2e2c2ae8b6727f17b610bb058f45282d/ghc >--------------------------------------------------------------- commit d3eef6dc2e2c2ae8b6727f17b610bb058f45282d Author: Andrey Mokhov Date: Sun Jan 3 01:11:16 2016 +0000 Add COMPONENT_ID field to rts package-data.mk (#22). >--------------------------------------------------------------- d3eef6dc2e2c2ae8b6727f17b610bb058f45282d src/Rules/Data.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index c2a186f..b24bb85 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -87,7 +87,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do includes <- interpretPartial target $ fromDiffExpr includesArgs let contents = unlines $ map (prefix++) [ "C_SRCS = " ++ unwords (cSrcs ++ cmmSrcs ++ extraSrcs) - , "CC_OPTS = " ++ unwords includes ] + , "CC_OPTS = " ++ unwords includes + , "COMPONENT_ID = " ++ "rts" ] writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." From git at git.haskell.org Fri Oct 27 00:21:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Exit the build script if Hadrian cannot be built (f937d80) Message-ID: <20171027002144.1BEEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f937d806ea8397132405eeede17f2662d8b0c85f/ghc >--------------------------------------------------------------- commit f937d806ea8397132405eeede17f2662d8b0c85f Author: Andrey Mokhov Date: Thu Sep 1 17:58:44 2016 +0100 Exit the build script if Hadrian cannot be built >--------------------------------------------------------------- f937d806ea8397132405eeede17f2662d8b0c85f build.stack.bat | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/build.stack.bat b/build.stack.bat index 3586290..919854e 100644 --- a/build.stack.bat +++ b/build.stack.bat @@ -1,8 +1,9 @@ @rem Change the current directory to the one containing this script @cd %~dp0 - at rem Build Hadrian and dependencies + at rem Build Hadrian and dependencies and exit the script if the build failed @stack build + at if %errorlevel% neq 0 exit /B %errorlevel% @rem Run Hadrian in GHC top directory forwarding additional user arguments @stack exec hadrian -- --lint --directory ".." %* From git at git.haskell.org Fri Oct 27 00:21:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/ndmitchell/shaking-up-ghc (f98836e) Message-ID: <20171027002144.96C533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f98836ec1bae9809c167277232e0629647af1145/ghc >--------------------------------------------------------------- commit f98836ec1bae9809c167277232e0629647af1145 Merge: e40e2e0 cbbbc63 Author: Neil Mitchell Date: Wed Feb 17 16:25:50 2016 +0000 Merge branch 'master' of https://github.com/ndmitchell/shaking-up-ghc >--------------------------------------------------------------- f98836ec1bae9809c167277232e0629647af1145 src/Base.hs | 12 +++++------- src/Rules.hs | 2 ++ src/Rules/Library.hs | 19 +++++++++++-------- src/Rules/Register.hs | 9 ++------- src/Rules/Selftest.hs | 45 +++++++++++++++++++++++++++++++++++++-------- 5 files changed, 57 insertions(+), 30 deletions(-) From git at git.haskell.org Fri Oct 27 00:21:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build libffi library, fix #75. (3b8aa92) Message-ID: <20171027002147.A7ABE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b8aa92730ff232c16a6fa0da54b6e9c4fe47381/ghc >--------------------------------------------------------------- commit 3b8aa92730ff232c16a6fa0da54b6e9c4fe47381 Author: Andrey Mokhov Date: Sun Jan 3 01:12:26 2016 +0000 Build libffi library, fix #75. >--------------------------------------------------------------- 3b8aa92730ff232c16a6fa0da54b6e9c4fe47381 shaking-up-ghc.cabal | 2 + src/GHC.hs | 19 +++--- src/Main.hs | 2 + src/Rules.hs | 2 +- src/Rules/Cabal.hs | 19 +++--- src/Rules/Copy.hs | 5 +- src/Rules/Libffi.hs | 119 ++++++++++++++++++++++++++++++++++++++ src/Rules/Library.hs | 4 +- src/Rules/Program.hs | 2 +- src/Settings/Builders/Common.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 3 - src/Settings/Builders/Hsc2Hs.hs | 6 +- 12 files changed, 159 insertions(+), 29 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3b8aa92730ff232c16a6fa0da54b6e9c4fe47381 From git at git.haskell.org Fri Oct 27 00:21:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to drop the 'echo' hack. (fe19fc3) Message-ID: <20171027002147.E9AE23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fe19fc382f56b37e7936a0c086e1bddd87c0e168/ghc >--------------------------------------------------------------- commit fe19fc382f56b37e7936a0c086e1bddd87c0e168 Author: Andrey Mokhov Date: Thu Sep 1 19:10:40 2016 +0100 Try to drop the 'echo' hack. >--------------------------------------------------------------- fe19fc382f56b37e7936a0c086e1bddd87c0e168 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index ffca700..07619c8 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -30,7 +30,7 @@ build_script: # Run internal Hadrian tests - stack exec hadrian -- selftest # Build GHC - - echo "" | stack --no-terminal exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + - stack exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest # Test GHC binary - cd .. - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:21:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #208 from ndmitchell/master (d1dacae) Message-ID: <20171027002148.52FE83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1dacaea037b9d63b3747c1d1b30e5b3b9fe5dcd/ghc >--------------------------------------------------------------- commit d1dacaea037b9d63b3747c1d1b30e5b3b9fe5dcd Merge: cbbbc63 f98836e Author: Andrey Mokhov Date: Wed Feb 17 17:09:24 2016 +0000 Merge pull request #208 from ndmitchell/master Ensure that if ghc compilation fails then we return a non-zero error code from build.bat >--------------------------------------------------------------- d1dacaea037b9d63b3747c1d1b30e5b3b9fe5dcd build.bat | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Oct 27 00:21:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Register rts package, see #22 and #67. (9be3f7e) Message-ID: <20171027002152.B113E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9be3f7e7f4de05897602959de5ee5025a10d7a8b/ghc >--------------------------------------------------------------- commit 9be3f7e7f4de05897602959de5ee5025a10d7a8b Author: Andrey Mokhov Date: Sun Jan 3 02:45:41 2016 +0000 Register rts package, see #22 and #67. >--------------------------------------------------------------- 9be3f7e7f4de05897602959de5ee5025a10d7a8b src/Base.hs | 13 +++++++++- src/Rules/Data.hs | 52 ++++++++++++++++++++++++-------------- src/Rules/Libffi.hs | 10 -------- src/Settings/Packages/Rts.hs | 59 ++++++++++++++++++++++++++++++++++++++++---- 4 files changed, 99 insertions(+), 35 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 9be3f7e7f4de05897602959de5ee5025a10d7a8b From git at git.haskell.org Fri Oct 27 00:21:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run stack setup in silent mode (4b682d2) Message-ID: <20171027002152.F33193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b682d2db950154907885acc006a46ea47d9c019/ghc >--------------------------------------------------------------- commit 4b682d2db950154907885acc006a46ea47d9c019 Author: Andrey Mokhov Date: Thu Sep 1 19:59:57 2016 +0100 Run stack setup in silent mode >--------------------------------------------------------------- 4b682d2db950154907885acc006a46ea47d9c019 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 07619c8..ab3ed8c 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -21,7 +21,7 @@ install: # Install all Hadrian and GHC build dependencies - cd hadrian - - stack setup + - stack setup --silent - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: From git at git.haskell.org Fri Oct 27 00:21:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --profile=- to CI build scripts. (6dc581c) Message-ID: <20171027002153.307F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6dc581c2a9b8c1c68980fd59fd3ceee4569d05d3/ghc >--------------------------------------------------------------- commit 6dc581c2a9b8c1c68980fd59fd3ceee4569d05d3 Author: Andrey Mokhov Date: Thu Feb 18 00:25:54 2016 +0000 Add --profile=- to CI build scripts. Fix #209. >--------------------------------------------------------------- 6dc581c2a9b8c1c68980fd59fd3ceee4569d05d3 .appveyor.yml | 2 +- .travis.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7ffabc3..537983c 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -39,4 +39,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --profile=- --flavour=quick inplace/bin/ghc-stage1.exe diff --git a/.travis.yml b/.travis.yml index d7e58c3..9547914 100644 --- a/.travis.yml +++ b/.travis.yml @@ -62,7 +62,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET + - ./ghc/shake-build/build.sh -j --no-progress --profile=- --flavour=quick $TARGET cache: directories: From git at git.haskell.org Fri Oct 27 00:21:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghcautoconf, ghcplatform as rtsConf dependencies (122a01d) Message-ID: <20171027002156.CE8703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/122a01d4350e0c8888a0bc0007f2edfccaf87f47/ghc >--------------------------------------------------------------- commit 122a01d4350e0c8888a0bc0007f2edfccaf87f47 Author: Moritz Angermann Date: Sun Jan 3 12:41:28 2016 +0800 Add ghcautoconf, ghcplatform as rtsConf dependencies This fixes #76. >--------------------------------------------------------------- 122a01d4350e0c8888a0bc0007f2edfccaf87f47 src/Rules/Data.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 00f6368..84ac619 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -99,7 +99,9 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fullTarget target (GhcPkg stage) [rtsConf] [] rtsConf %> \_ -> do - need [rtsConfIn] + need [rtsConfIn + , "includes/ghcautoconf.h" + , "includes/ghcplatform.h" ] build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] old <- liftIO $ readFile rtsConf let new = unlines . map (replace "\"\"" "") From git at git.haskell.org Fri Oct 27 00:21:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing resource dependency to buildBinary. (dfce0db) Message-ID: <20171027002156.D82AE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfce0db830f71511065a5475934a9791c0eb9524/ghc >--------------------------------------------------------------- commit dfce0db830f71511065a5475934a9791c0eb9524 Author: Andrey Mokhov Date: Thu Feb 18 08:36:38 2016 +0000 Add missing resource dependency to buildBinary. See #206. >--------------------------------------------------------------- dfce0db830f71511065a5475934a9791c0eb9524 src/Rules.hs | 2 +- src/Rules/Program.hs | 16 ++++++++-------- 2 files changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 444a2cb..0136c27 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -75,7 +75,7 @@ packageRules = do , buildPackageDocumentation , buildPackageGhciLibrary , generatePackageCode - , buildProgram + , buildProgram readPackageDb , registerPackage writePackageDb ] buildRules :: Rules () diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index d7fdaad..6eaa821 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -31,8 +31,8 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper)] -buildProgram :: Context -> Rules () -buildProgram context @ (Context {..}) = do +buildProgram :: [(Resource, Int)] -> Context -> Rules () +buildProgram rs context @ (Context {..}) = do let match file = case programPath stage package of Nothing -> False Just program -> program == file @@ -45,15 +45,15 @@ buildProgram context @ (Context {..}) = do match ?> \bin -> do windows <- windowsHost if windows - then buildBinary context bin -- We don't build wrappers on Windows + then buildBinary rs context bin -- We don't build wrappers on Windows else case find ((== context) . fst) wrappers of - Nothing -> buildBinary context bin -- No wrapper found + Nothing -> buildBinary rs context bin -- No wrapper found Just (_, wrapper) -> do let Just wrappedBin = computeWrappedPath bin need [wrappedBin] buildWrapper context wrapper bin wrappedBin - matchWrapped ?> \bin -> buildBinary context bin + matchWrapped ?> \bin -> buildBinary rs context bin -- Replace programInplacePath with programInplaceLibPath in a given path computeWrappedPath :: FilePath -> Maybe FilePath @@ -70,8 +70,8 @@ buildWrapper context @ (Context stage package _) wrapper wrapperPath binPath = d -- TODO: Get rid of the Paths_hsc2hs.o hack. -- TODO: Do we need to consider other ways when building programs? -buildBinary :: Context -> FilePath -> Action () -buildBinary context @ (Context stage package _) bin = do +buildBinary :: [(Resource, Int)] -> Context -> FilePath -> Action () +buildBinary rs context @ (Context stage package _) bin = do let buildPath = targetPath stage package -/- "build" cSrcs <- cSources context -- TODO: remove code duplication (Library.hs) hSrcs <- hSources context @@ -100,7 +100,7 @@ buildBinary context @ (Context stage package _) bin = do then [ pkgPath package -/- src <.> "hs" | src <- hSrcs ] else objs need $ binDeps ++ libs - build $ Target context (Ghc stage) binDeps [bin] + buildWithResources rs $ Target context (Ghc stage) binDeps [bin] synopsis <- interpretInContext context $ getPkgData Synopsis putSuccess $ renderProgram ("'" ++ pkgNameString package ++ "' (" ++ show stage ++ ").") From git at git.haskell.org Fri Oct 27 00:21:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:21:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reduce verbosity (80e986b) Message-ID: <20171027002157.12C5F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/80e986ba99c5764f78f6c4b54abc0c24953d836c/ghc >--------------------------------------------------------------- commit 80e986ba99c5764f78f6c4b54abc0c24953d836c Author: Andrey Mokhov Date: Thu Sep 1 20:14:01 2016 +0100 Reduce verbosity >--------------------------------------------------------------- 80e986ba99c5764f78f6c4b54abc0c24953d836c appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index ab3ed8c..def4dd9 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -17,11 +17,11 @@ install: - git init - git remote add origin git://git.haskell.org/ghc.git - git pull --recurse-submodules origin master - - git submodule update --init --recursive + - git submodule update --init --recursive --quiet # Install all Hadrian and GHC build dependencies - cd hadrian - - stack setup --silent + - stack setup > nul - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: From git at git.haskell.org Fri Oct 27 00:22:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds ghcversion and derivedconstants to rts (25b2408) Message-ID: <20171027002201.2F9603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/25b2408edd914c06d2e25f16bde711e54a548f2c/ghc >--------------------------------------------------------------- commit 25b2408edd914c06d2e25f16bde711e54a548f2c Author: Moritz Angermann Date: Sun Jan 3 12:42:27 2016 +0800 Adds ghcversion and derivedconstants to rts Fixes #77 and fixes #76 (ghcverison). >--------------------------------------------------------------- 25b2408edd914c06d2e25f16bde711e54a548f2c src/Rules/Generate.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index e14b941..299f79a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -62,6 +62,9 @@ generatedDependencies stage pkg , "includes/ghcplatform.h" ] | pkg == rts = let buildPath = targetPath stage rts -/- "build" in + [ "includes/ghcversion.h" -- missing only in stage1. See #76 + , derivedConstantsPath -/- "DerivedConstants.h" ] + ++ fmap (buildPath -/-) ["ffi.h", "ffitarget.h"] | otherwise = [] From git at git.haskell.org Fri Oct 27 00:22:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make RecordWildCards a default extension. (548a30b) Message-ID: <20171027002201.3706C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/548a30b993efcdad064a6d9b14deb5b7a40b681d/ghc >--------------------------------------------------------------- commit 548a30b993efcdad064a6d9b14deb5b7a40b681d Author: Andrey Mokhov Date: Fri Feb 19 00:00:14 2016 +0000 Make RecordWildCards a default extension. See #207. >--------------------------------------------------------------- 548a30b993efcdad064a6d9b14deb5b7a40b681d build.bat | 1 + build.sh | 1 + shaking-up-ghc.cabal | 2 +- src/Rules/Actions.hs | 1 - src/Rules/Compile.hs | 1 - src/Rules/Data.hs | 1 - src/Rules/Dependencies.hs | 1 - src/Rules/Documentation.hs | 1 - src/Rules/Library.hs | 1 - src/Rules/Program.hs | 1 - src/Rules/Register.hs | 1 - 11 files changed, 3 insertions(+), 9 deletions(-) diff --git a/build.bat b/build.bat index 10a6969..465d957 100644 --- a/build.bat +++ b/build.bat @@ -4,6 +4,7 @@ @set ghcArgs=--make ^ -Wall ^ -fno-warn-name-shadowing ^ + -XRecordWildCards ^ src/Main.hs ^ -isrc ^ -rtsopts ^ diff --git a/build.sh b/build.sh index 77c9fa4..7c070e9 100755 --- a/build.sh +++ b/build.sh @@ -36,6 +36,7 @@ ghc \ "$root/src/Main.hs" \ -Wall \ -fno-warn-name-shadowing \ + -XRecordWildCards \ -i"$root/src" \ -rtsopts \ -with-rtsopts=-I0 \ diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 684e89e..fc0744d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -108,13 +108,13 @@ executable ghc-shake , Way default-language: Haskell2010 + default-extensions: RecordWildCards other-extensions: DeriveDataTypeable , DeriveGeneric , FlexibleInstances , GeneralizedNewtypeDeriving , LambdaCase , OverloadedStrings - , RecordWildCards , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5f8f583..c69298e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, applyPatch, fixFile, runConfigure, runMake, diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index f62c644..c9a1bba 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Compile (compilePackage) where import Base diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index f47e8d0..0e27699 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Data (buildPackageData) where import qualified System.Directory as IO diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 330c821..f2a2141 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Dependencies (buildPackageDependencies) where import Development.Shake.Util (parseMakefile) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index e3b0e7d..7e98e27 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Documentation (buildPackageDocumentation) where import Base diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index c6d92a5..980139f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Library ( buildPackageLibrary, buildPackageGhciLibrary, cSources, hSources ) where diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 6eaa821..af6023d 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Program (buildProgram) where import Data.Char diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 85fac80..bddce8a 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Register (registerPackage) where import Base From git at git.haskell.org Fri Oct 27 00:22:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Final tweaks (7987366) Message-ID: <20171027002201.5B7863A5EC@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79873665328d089b35b8a75141afe75b0d84dcbf/ghc >--------------------------------------------------------------- commit 79873665328d089b35b8a75141afe75b0d84dcbf Author: Andrey Mokhov Date: Thu Sep 1 21:02:05 2016 +0100 Final tweaks >--------------------------------------------------------------- 79873665328d089b35b8a75141afe75b0d84dcbf appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index def4dd9..5d13d29 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -12,7 +12,7 @@ install: - 7z x stack.zip stack.exe # Fetch GHC sources into c:\ghc - # Note: Appveyor has already cloned Hadrian into c:\ghc\hadrian, so it's tricky + # Note: AppVeyor has already cloned Hadrian into c:\ghc\hadrian, so it's tricky - cd .. - git init - git remote add origin git://git.haskell.org/ghc.git @@ -30,7 +30,7 @@ build_script: # Run internal Hadrian tests - stack exec hadrian -- selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- # Test GHC binary - cd .. - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:22:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Rules for IntegerGmp (94f5e79) Message-ID: <20171027002204.EF24A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/94f5e79a5947dca7fa4719f79f8892fa18d88f33/ghc >--------------------------------------------------------------- commit 94f5e79a5947dca7fa4719f79f8892fa18d88f33 Author: Moritz Angermann Date: Sun Jan 3 18:48:04 2016 +0800 Adds Rules for IntegerGmp This should fix #71. We build the integer-gmp library similary to libffi now. >--------------------------------------------------------------- 94f5e79a5947dca7fa4719f79f8892fa18d88f33 shaking-up-ghc.cabal | 1 + src/Main.hs | 2 + src/Rules/IntegerGmp.hs | 112 ++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 115 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 3f91f30..334cd59 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -49,6 +49,7 @@ executable ghc-shake , Rules.Generators.GhcPlatformH , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs + , Rules.IntegerGmp , Rules.Libffi , Rules.Library , Rules.Oracles diff --git a/src/Main.hs b/src/Main.hs index 82f0072..043e173 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -5,6 +5,7 @@ import Rules.Config import Rules.Generate import Rules.Copy import Rules.Libffi +import Rules.IntegerGmp import Rules.Oracles main :: IO () @@ -15,6 +16,7 @@ main = shakeArgs options $ do generateTargets -- see Rules generateRules -- see Rules.Generate libffiRules -- see Rules.Libffi + integerGmpRules -- see Rules.IntegerGmp oracleRules -- see Rules.Oracles packageRules -- see Rules where diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs new file mode 100644 index 0000000..443b912 --- /dev/null +++ b/src/Rules/IntegerGmp.hs @@ -0,0 +1,112 @@ +module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where + +import System.Directory + +import Base +import Expression +import GHC +import Oracles.Config.Setting +import Rules.Actions + +integerGmpBase :: FilePath +integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp" + +integerGmpBuild :: FilePath +integerGmpBuild = integerGmpBase -/- "gmpbuild" + +integerGmpLibrary :: FilePath +integerGmpLibrary = integerGmpBase -/- "libgmp.a" + +-- relative to integerGmpBuild +integerGmpPatch :: FilePath +integerGmpPatch = ".." -/- "tarball" -/- "gmp-5.0.4.patch" + +target :: PartialTarget +target = PartialTarget Stage0 integerGmp + +-- TODO: See Libffi.hs about removing code duplication. +configureEnvironment :: Action [CmdOption] +configureEnvironment = do + sequence [ builderEnv "CC" $ Gcc Stage1 + , builderEnv "CXX" $ Gcc Stage1 + , builderEnv "AR" Ar + , builderEnv "NM" Nm] + where + builderEnv var builder = do + needBuilder False builder + path <- builderPath builder + return $ AddEnv var path + +configureArguments :: Action [String] +configureArguments = do + hostPlatform <- setting HostPlatform + buildPlatform <- setting BuildPlatform + return [ "--enable-shared=no" + , "--host=" ++ hostPlatform + , "--build=" ++ buildPlatform] + +-- TODO: we rebuild integer-gmp every time. +integerGmpRules :: Rules () +integerGmpRules = do + integerGmpLibrary %> \_ -> do + need [sourcePath -/- "Rules" -/- "integerGmp.hs"] + + -- remove the old build folder, if it exists. + liftIO $ removeFiles integerGmpBuild ["//*"] + + -- unpack the gmp tarball. + -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is + -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. + -- That's because the doc/ directory contents are under the GFDL, + -- which causes problems for Debian. + tarballs <- getDirectoryFiles "" [integerGmpBase -/- "tarball/gmp*.tar.bz2"] + when (length tarballs /= 1) $ + putError $ "integerGmpRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + let filename = dropExtension . dropExtension . takeFileName $ head tarballs + let suffix = "-nodoc-patched" + unless (suffix `isSuffixOf` filename) $ + putError $ "integerGmpRules: expected suffix " ++ suffix + ++ " (found: " ++ filename ++ ")." + let libname = take (length filename - length suffix) filename + + need tarballs + build $ fullTarget target Tar tarballs [integerGmpBase] + + -- move gmp- to gmpbuild + let integerGmpExtracted = integerGmpBase -/- libname + liftIO $ renameDirectory integerGmpExtracted integerGmpBuild + putBuild $ "| Move " ++ integerGmpExtracted ++ " -> " ++ integerGmpBuild + + -- apply patches + -- TODO: replace "patch" with PATCH_CMD + unit $ cmd Shell [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch" + unit $ cmd Shell [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch] + putBuild $ "| Applied gmpsrc.patch and " ++ takeFileName integerGmpPatch + + -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? + + -- ./configure + putBuild "| Running libffi configure..." + envs <- configureEnvironment + args <- configureArguments + unit $ cmd Shell [Cwd integerGmpBuild] "bash configure" envs args + + -- make + putBuild "| Running make..." + unit $ cmd Shell "make" ["-C", integerGmpBuild, "MAKEFLAGS="] + + -- copy library and header + forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> do + let file' = integerGmpBase -/- takeFileName file + copyFileChanged (integerGmpBuild -/- file) file' + putBuild $ "| Copy " ++ file ++ " -> " ++ file' + + -- TODO: do we need these as well? + -- mkdir integerGmpBase -/- objs + -- unit $ cmd Shell [Cwd integerGmpBase -/- "objs"] "$AR_STAGE1 x ../libgmp.a" + -- $RANLIB_CMD integerGmpBase -/- "libgmp.a" + + putSuccess "| Successfully build custom library 'integer-gmp'" + + "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary] From git at git.haskell.org Fri Oct 27 00:22:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant newCache. (57c623d) Message-ID: <20171027002205.675343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57c623dbc3e8eed480ed5b0812aa8282bea22064/ghc >--------------------------------------------------------------- commit 57c623dbc3e8eed480ed5b0812aa8282bea22064 Author: Andrey Mokhov Date: Fri Feb 19 00:30:00 2016 +0000 Drop redundant newCache. See #210. >--------------------------------------------------------------- 57c623dbc3e8eed480ed5b0812aa8282bea22064 src/Oracles/ModuleFiles.hs | 7 ++----- 1 file changed, 2 insertions(+), 5 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 391990e..d8b1ae7 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -38,8 +38,8 @@ haskellModuleFiles stage pkg = do return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) moduleFilesOracle :: Rules () -moduleFilesOracle = do - answer <- newCache $ \(modules, dirs) -> do +moduleFilesOracle = void $ + addOracle $ \(ModuleFilesKey (modules, dirs)) -> do let decodedPairs = map decodeModule modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedPairs @@ -55,6 +55,3 @@ moduleFilesOracle = do return (map (fullDir -/-) found, mDir) return $ sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] - - _ <- addOracle $ \(ModuleFilesKey query) -> answer query - return () From git at git.haskell.org Fri Oct 27 00:22:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Whitespace (5905138) Message-ID: <20171027002205.8C70C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59051380365b8ef66d7c95cb63a038a89b482326/ghc >--------------------------------------------------------------- commit 59051380365b8ef66d7c95cb63a038a89b482326 Author: Andrey Mokhov Date: Thu Sep 1 21:29:15 2016 +0100 Whitespace >--------------------------------------------------------------- 59051380365b8ef66d7c95cb63a038a89b482326 appveyor.yml | 3 +++ 1 file changed, 3 insertions(+) diff --git a/appveyor.yml b/appveyor.yml index 5d13d29..7552a56 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -27,10 +27,13 @@ install: build_script: # Build Hadrian - stack build + # Run internal Hadrian tests - stack exec hadrian -- selftest + # Build GHC - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- + # Test GHC binary - cd .. - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:22:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #78 from angerman/feature/dependencies (a4893ad) Message-ID: <20171027002209.254053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4893ad7be1b199ba407fa74b53c49f15eb152cf/ghc >--------------------------------------------------------------- commit a4893ad7be1b199ba407fa74b53c49f15eb152cf Merge: 9be3f7e 25b2408 Author: Andrey Mokhov Date: Sun Jan 3 12:11:40 2016 +0000 Merge pull request #78 from angerman/feature/dependencies Feature/dependencies >--------------------------------------------------------------- a4893ad7be1b199ba407fa74b53c49f15eb152cf src/Rules/Data.hs | 4 +++- src/Rules/Generate.hs | 3 +++ 2 files changed, 6 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:22:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (e1d05c5) Message-ID: <20171027002209.4E5973A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1d05c561f1ab7d939dc4decf5ca143a3bd07a5e/ghc >--------------------------------------------------------------- commit e1d05c561f1ab7d939dc4decf5ca143a3bd07a5e Author: Andrey Mokhov Date: Fri Feb 19 00:35:44 2016 +0000 Add comments. See #210. >--------------------------------------------------------------- e1d05c561f1ab7d939dc4decf5ca143a3bd07a5e src/Oracles/ModuleFiles.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index d8b1ae7..b831f76 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -37,6 +37,16 @@ haskellModuleFiles stage pkg = do return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) +-- | This is an important oracle whose role is to find and cache module source +-- files. More specifically, it takes a list of module names @modules@ and a +-- list of directories @dirs@ as arguments, and computes a sorted list of pairs +-- of the form @(A.B.C, dir/A/B/C.extension)@, such that @A.B.C@ belongs to +-- @modules@, @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists. +-- For example, for 'compiler' package given +-- @modules = ["CodeGen.Platform.ARM", "Lexer"]@, and +-- @dirs = ["codeGen", "parser"]@, it produces +-- @[("CodeGen.Platform.ARM", "codeGen/CodeGen/Platform/ARM.hs"), +-- ("Lexer", "parser/Lexer.x")]@. moduleFilesOracle :: Rules () moduleFilesOracle = void $ addOracle $ \(ModuleFilesKey (modules, dirs)) -> do From git at git.haskell.org Fri Oct 27 00:22:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor and simplify (3218044) Message-ID: <20171027002209.C34493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/321804478393dbf33c80eaa8ad53e0f859d94171/ghc >--------------------------------------------------------------- commit 321804478393dbf33c80eaa8ad53e0f859d94171 Author: Andrey Mokhov Date: Thu Sep 1 21:29:34 2016 +0100 Refactor and simplify >--------------------------------------------------------------- 321804478393dbf33c80eaa8ad53e0f859d94171 .travis.yml | 69 ++++++++++++++++++++++--------------------------------------- 1 file changed, 25 insertions(+), 44 deletions(-) diff --git a/.travis.yml b/.travis.yml index 33c1738..5b26bbd 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,6 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quickest TARGET= addons: apt: packages: @@ -12,65 +11,47 @@ matrix: - zlib1g-dev sources: hvr-ghc before_install: - - PATH="/opt/ghc/$GHCVER/bin:$PATH" - - PATH="/opt/cabal/$CABALVER/bin:$PATH" - - PATH="$HOME/.cabal/bin:$PATH" - - export PATH - - cabal update - - cabal install alex happy ansi-terminal mtl shake quickcheck + - PATH="/opt/ghc/7.10.3/bin:$PATH" + - PATH="/opt/cabal/1.22/bin:$PATH" - os: osx - env: FLAVOUR=quickest TARGET= before_install: - brew update - brew install ghc cabal-install - - cabal update - - cabal install alex happy ansi-terminal mtl shake quickcheck - - PATH="$HOME/.cabal/bin:$PATH" - - export PATH install: + # Add Cabal to PATH + - PATH="$HOME/.cabal/bin:$PATH" + - export PATH - env - - ghc --version - - cabal --version - - alex --version - - happy --version - - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ - - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ - - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - - travis_retry git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 + # Install all Hadrian and GHC build dependencies + - cabal update + - cabal install alex happy ansi-terminal mtl shake quickcheck - # Travis clones the project into ".", but we need it as a child directory - # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake - # ".git" directory into the appropriate location, and perform a hard reset - # in order to regenerate the GHC-Shake files. + # Fetch GHC sources into ./ghc + - git clone --recursive git://git.haskell.org/ghc.git --quiet + + # Travis has already cloned Hadrian into ./ and we need to move it + # to ./ghc/hadrian -- one way to do it is to move the .git directory + # and perform a hard reset in order to regenerate Hadrian files - mkdir ghc/hadrian - mv .git ghc/hadrian - - ( cd ghc/hadrian && git reset --hard HEAD ) - - - ghc-pkg list + - cd ghc/hadrian + - git reset --hard HEAD script: - - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=$FLAVOUR $TARGET - - ./ghc/inplace/bin/ghc-stage2 -e 1+2 + # Run internal Hadrian tests + - ./build.sh selftest + + # Build GHC + - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + + # Test GHC binary + - cd .. + - ghc/inplace/bin/ghc-stage2 -e 1+2 cache: directories: - $HOME/.cabal - $HOME/.ghc - -notifications: - irc: - on_success: change # always/never/change - on_failure: always - channels: - - "chat.freenode.net#shaking-up-ghc" - template: - - "#%{build_number} finished in %{duration}. %{message}" - - "Repo: %{repository_slug}, branch: %{branch}" - - "%{author}: %{commit_subject}" - - "Build details: %{build_url}" From git at git.haskell.org Fri Oct 27 00:22:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #79 from angerman/feature/integer-gmp (ee639c7) Message-ID: <20171027002213.9B6503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee639c7de4ae1861255953daa8f7b65d4a374c1f/ghc >--------------------------------------------------------------- commit ee639c7de4ae1861255953daa8f7b65d4a374c1f Merge: a4893ad 94f5e79 Author: Andrey Mokhov Date: Sun Jan 3 12:13:05 2016 +0000 Merge pull request #79 from angerman/feature/integer-gmp Adds Rules for IntegerGmp >--------------------------------------------------------------- ee639c7de4ae1861255953daa8f7b65d4a374c1f shaking-up-ghc.cabal | 1 + src/Main.hs | 2 + src/Rules/IntegerGmp.hs | 112 ++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 115 insertions(+) From git at git.haskell.org Fri Oct 27 00:22:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor oracles, drop redundant newCache. (13ad050) Message-ID: <20171027002213.D97243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13ad050070d32c5c6267af8fba60125af878147c/ghc >--------------------------------------------------------------- commit 13ad050070d32c5c6267af8fba60125af878147c Author: Andrey Mokhov Date: Fri Feb 19 01:15:10 2016 +0000 Refactor oracles, drop redundant newCache. >--------------------------------------------------------------- 13ad050070d32c5c6267af8fba60125af878147c src/Oracles/ArgsHash.hs | 5 ++--- src/Oracles/Dependencies.hs | 1 - src/Oracles/LookupInPath.hs | 12 +++++------- src/Oracles/PackageData.hs | 5 ++--- src/Oracles/PackageDb.hs | 5 ++--- src/Oracles/PackageDeps.hs | 8 ++++---- src/Oracles/WindowsPath.hs | 10 ++++------ 7 files changed, 19 insertions(+), 27 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 796e753..aec0dc9 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -29,6 +29,5 @@ checkArgsHash target = when trackBuildSystem $ do -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () -argsHashOracle = do - _ <- addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs - return () +argsHashOracle = void $ + addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 8895758..b34535b 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -33,6 +33,5 @@ dependenciesOracle = do putOracle $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return . Map.fromList $ map (\(x:xs) -> (x, xs)) contents - _ <- addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file return () diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 2f6e713..0ea03fd 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -15,13 +15,11 @@ lookupInPath name | otherwise = return name lookupInPathOracle :: Rules () -lookupInPathOracle = do - answer <- newCache $ \query -> do - maybePath <- liftIO $ findExecutable query +lookupInPathOracle = void $ + addOracle $ \(LookupInPath name) -> do + maybePath <- liftIO $ findExecutable name path <- case maybePath of Just value -> return $ unifyPath value - Nothing -> putError $ "Cannot find executable '" ++ query ++ "'." - putOracle $ "Executable found: " ++ query ++ " => " ++ path + Nothing -> putError $ "Cannot find executable '" ++ name ++ "'." + putOracle $ "Executable found: " ++ name ++ " => " ++ path return path - _ <- addOracle $ \(LookupInPath query) -> answer query - return () diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index d176839..ba3e205 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -86,10 +86,9 @@ pkgDataList packageData = fmap (map unquote . words) $ case packageData of -- Oracle for 'package-data.mk' files packageDataOracle :: Rules () packageDataOracle = do - pkgDataContents <- newCache $ \file -> do + keys <- newCache $ \file -> do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - _ <- addOracle $ \(PackageDataKey (file, key)) -> - Map.lookup key <$> pkgDataContents file + _ <- addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file return () diff --git a/src/Oracles/PackageDb.hs b/src/Oracles/PackageDb.hs index 97a2a5c..b644989 100644 --- a/src/Oracles/PackageDb.hs +++ b/src/Oracles/PackageDb.hs @@ -12,12 +12,11 @@ import Settings.Paths import Target packageDbOracle :: Rules () -packageDbOracle = do - _ <- addOracle $ \(PackageDbKey stage) -> do +packageDbOracle = void $ + addOracle $ \(PackageDbKey stage) -> do let dir = packageDbDirectory stage file = dir -/- "package.cache" unlessM (liftIO $ IO.doesFileExist file) $ do removeDirectoryIfExists dir build $ Target (vanillaContext stage ghcPkg) (GhcPkg stage) [] [dir] putSuccess $ "| Successfully initialised " ++ dir - return () diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 94cdd91..6a5f7dd 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -8,9 +8,9 @@ import Package newtype PackageDepsKey = PackageDepsKey PackageName deriving (Show, Typeable, Eq, Hashable, Binary, NFData) --- packageDeps name is an action that given a package looks up its dependencies --- in Base.packageDependencies file. The dependencies need to be computed by --- scanning package cabal files (see Rules.Cabal). +-- @packageDeps name@ is an action that given a 'Package' looks up its +-- dependencies in 'Base.packageDependencies' file. The dependencies need to be +-- computed by scanning package cabal files (see Rules.Cabal). packageDeps :: Package -> Action [PackageName] packageDeps pkg = do res <- askOracle . PackageDepsKey . pkgName $ pkg @@ -23,6 +23,6 @@ packageDepsOracle = do putOracle $ "Reading package dependencies..." contents <- readFileLines packageDependencies return . Map.fromList $ - [ (head ps, tail ps) | line <- contents, let ps = map PackageName $ words line ] + [ (p, ps) | line <- contents, let p:ps = map PackageName $ words line ] _ <- addOracle $ \(PackageDepsKey pkg) -> Map.lookup pkg <$> deps () return () diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index 3cbf1f1..a0343fb 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -15,7 +15,7 @@ topDirectory = do ghcSourcePath <- setting GhcSourcePath fixAbsolutePathOnWindows ghcSourcePath --- Fix an absolute path on Windows: +-- | Fix an absolute path on Windows: -- * "/c/" => "C:/" -- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" fixAbsolutePathOnWindows :: FilePath -> Action FilePath @@ -29,13 +29,11 @@ fixAbsolutePathOnWindows path = do else return path --- Detecting path mapping on Windows. This is slow and requires caching. +-- | Compute path mapping on Windows. This is slow and requires caching. windowsPathOracle :: Rules () -windowsPathOracle = do - answer <- newCache $ \path -> do +windowsPathOracle = void $ + addOracle $ \(WindowsPath path) -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] let windowsPath = unifyPath $ dropWhileEnd isSpace out putOracle $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath - _ <- addOracle $ \(WindowsPath query) -> answer query - return () From git at git.haskell.org Fri Oct 27 00:22:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to GHC binary (cc72f0c) Message-ID: <20171027002214.3828C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cc72f0caf4547d27774cf6ed551c41ced9f9c9f3/ghc >--------------------------------------------------------------- commit cc72f0caf4547d27774cf6ed551c41ced9f9c9f3 Author: Andrey Mokhov Date: Thu Sep 1 22:15:17 2016 +0100 Fix path to GHC binary >--------------------------------------------------------------- cc72f0caf4547d27774cf6ed551c41ced9f9c9f3 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 5b26bbd..0209cab 100644 --- a/.travis.yml +++ b/.travis.yml @@ -49,7 +49,7 @@ script: # Test GHC binary - cd .. - - ghc/inplace/bin/ghc-stage2 -e 1+2 + - inplace/bin/ghc-stage2 -e 1+2 cache: directories: From git at git.haskell.org Fri Oct 27 00:22:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds integer gmp path to the Gcc builder. (8cea200) Message-ID: <20171027002217.72A263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8cea2007b3449adb88c35cbdbeaf2407b658c4ae/ghc >--------------------------------------------------------------- commit 8cea2007b3449adb88c35cbdbeaf2407b658c4ae Author: Moritz Angermann Date: Sun Jan 3 20:56:24 2016 +0800 Adds integer gmp path to the Gcc builder. This fixes the isse mentioned in #79, where `gmp.h` could not be found. >--------------------------------------------------------------- 8cea2007b3449adb88c35cbdbeaf2407b658c4ae src/Settings/Packages/IntegerGmp.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 1c8ed13..6d1b2b6 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -3,7 +3,7 @@ module Settings.Packages.IntegerGmp (integerGmpPackageArgs) where import Base import Expression import GHC (integerGmp) -import Predicates (builder, package) +import Predicates (builder, builderGcc, package) -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" @@ -11,9 +11,12 @@ import Predicates (builder, package) -- endif integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? - builder GhcCabal ? mconcat - [ arg "--configure-option=--with-intree-gmp" - , appendSub "--configure-option=CFLAGS" includeGmp - , appendSub "--gcc-options" includeGmp ] + mconcat + [ builder GhcCabal ? mconcat + [ arg "--configure-option=--with-intree-gmp" + , appendSub "--configure-option=CFLAGS" includeGmp + , appendSub "--gcc-options" includeGmp ] + , builderGcc ? ( arg $ "-I" ++ pkgPath integerGmp -/- "gmp" ) + ] where includeGmp = ["-I" ++ pkgPath integerGmp -/- "gmp"] From git at git.haskell.org Fri Oct 27 00:22:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor paths using Context. (badd551) Message-ID: <20171027002217.AF8E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/badd551338ac11ef851d8882b2496de6c31d004f/ghc >--------------------------------------------------------------- commit badd551338ac11ef851d8882b2496de6c31d004f Author: Andrey Mokhov Date: Fri Feb 19 02:49:11 2016 +0000 Refactor paths using Context. See #207. >--------------------------------------------------------------- badd551338ac11ef851d8882b2496de6c31d004f src/Builder.hs | 31 +++++++++++++------------ src/Expression.hs | 18 +++++++++------ src/GHC.hs | 36 ++++++++++++++++------------- src/Oracles/ModuleFiles.hs | 20 ++++++++-------- src/Rules.hs | 12 +++++----- src/Rules/Clean.hs | 3 ++- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 30 ++++++++++++------------ src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 6 ++--- src/Rules/Generate.hs | 23 +++++++++++-------- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Rules/Program.hs | 12 +++++----- src/Rules/Register.hs | 10 ++++---- src/Settings.hs | 22 ++++++++---------- src/Settings/Builders/Common.hs | 4 ++-- src/Settings/Builders/Ghc.hs | 11 +++++---- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Builders/GhcPkg.hs | 6 ++--- src/Settings/Builders/Haddock.hs | 6 ++--- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/Hp2ps.hs | 2 +- src/Settings/Packages/Rts.hs | 6 ++--- src/Settings/Packages/Touchy.hs | 2 +- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/Paths.hs | 48 ++++++++++++++++++++------------------- 32 files changed, 177 insertions(+), 161 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 badd551338ac11ef851d8882b2496de6c31d004f From git at git.haskell.org Fri Oct 27 00:22:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify instructions, add CI badge (1fa2cb1) Message-ID: <20171027002218.0DCD73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fa2cb1b470674a5b478a4e4d5e8b931a45b36d6/ghc >--------------------------------------------------------------- commit 1fa2cb1b470674a5b478a4e4d5e8b931a45b36d6 Author: Andrey Mokhov Date: Thu Sep 1 23:20:05 2016 +0100 Simplify instructions, add CI badge [skip ci] >--------------------------------------------------------------- 1fa2cb1b470674a5b478a4e4d5e8b931a45b36d6 doc/windows.md | 69 ++++++++++++++++++++++++++++++++++++++++++++-------------- 1 file changed, 53 insertions(+), 16 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index a70f85a..efbaeb2 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -1,23 +1,60 @@ -# Building on Windows +# Building GHC on Windows -Here are a list of instructions to build GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. +[![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) -The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_64-installer) (I just accepted all the defaults), then open a command prompt and run: +Here is how you can build GHC, from source, on Windows. We assume that you +already have `git` and `stack` installed. - stack setup - stack install happy alex - stack exec -- pacman -S gcc binutils git automake-wrapper tar make patch autoconf --noconfirm - stack exec -- git clone --recursive git://git.haskell.org/ghc.git - cd ghc - stack exec -- git clone git://github.com/snowleopard/hadrian - stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quickest +```sh +# Get GHC and Hadrian sources +git clone --recursive git://git.haskell.org/ghc.git +cd ghc +git clone git://github.com/snowleopard/hadrian +cd hadrian -The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quickest` flag from the last command line (this will slow down the build to about an hour). +# Download and install the bootstrapping GHC and MSYS2 +stack setup -#### Future ideas +# Install utilities required during the GHC build process +stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm -Here are some alternatives that have been considered, but not yet tested. Use the instructions above. +# Build Hadrian and dependencies (including GHC dependencies Alex and Happy) +stack build + +# Build GHC +stack exec hadrian -- --directory ".." -j --flavour=quickest + +# Test GHC +cd .. +inplace\bin\ghc-stage2 -e 1+2 +``` + +The entire process should take about 20 minutes. Note, this will build GHC without +optimisations. If you need an optimised GHC, drop the `--flavour=quickest` flag from +the build command line (this will slow down the build to about an hour). + +These are currently not the +[official GHC building instructions](https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows), +but are much simpler and may also be more robust. + +The `stack build` and `stack exec hadrian` commands can be replaced by an invocation +of Hadrian's Stack-based build script: `build.stack.bat -j --flavour=quickest`. Use this +script if you plan to work on Hadrian and/or rebuild GHC often. + +## Prerequisites + +The above works on a clean machine with `git` and `stack` installed (tested with default +installation settings), which you can get from https://git-scm.com/download/win and +https://www.stackage.org/stack/windows-x86_64-installer. + +## Testing + +These instructions have been tested on a clean Windows 10 machine using the +[free VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/), +and are also routinely tested on +[Hadrian's AppVeyor CI instance](https://ci.appveyor.com/project/snowleopard/hadrian/history). + +## Notes + +Beware of the [current limitations of Hadrian](https://github.com/snowleopard/hadrian#current-limitations). -* The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. -* Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:22:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #80 from angerman/feature/integerGmpIncludePath (80d3477) Message-ID: <20171027002221.3351B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/80d34775cae65bfa0fbd26942a99cd546bcadfa0/ghc >--------------------------------------------------------------- commit 80d34775cae65bfa0fbd26942a99cd546bcadfa0 Merge: ee639c7 8cea200 Author: Andrey Mokhov Date: Sun Jan 3 13:17:44 2016 +0000 Merge pull request #80 from angerman/feature/integerGmpIncludePath Adds integer gmp path to the Gcc builder. >--------------------------------------------------------------- 80d34775cae65bfa0fbd26942a99cd546bcadfa0 src/Settings/Packages/IntegerGmp.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Oct 27 00:22:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor moduleFilesOracle, work in progress. (903ab6c) Message-ID: <20171027002221.D38983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/903ab6c7579627c52c07af7f9f8965a864af0187/ghc >--------------------------------------------------------------- commit 903ab6c7579627c52c07af7f9f8965a864af0187 Author: Andrey Mokhov Date: Fri Feb 19 18:31:30 2016 +0000 Refactor moduleFilesOracle, work in progress. See #210. >--------------------------------------------------------------- 903ab6c7579627c52c07af7f9f8965a864af0187 src/Oracles/ModuleFiles.hs | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 67d68f3..a5e40ed 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -7,7 +7,7 @@ import Oracles.PackageData import Package import Settings.Paths -newtype ModuleFilesKey = ModuleFilesKey ([String], [FilePath]) +newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) moduleFiles :: Context -> Action [FilePath] @@ -16,7 +16,7 @@ moduleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (modules, dirs) + found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (dirs, modules) return $ map snd found haskellModuleFiles :: Context -> Action ([FilePath], [String]) @@ -27,8 +27,8 @@ haskellModuleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - foundSrcDirs <- askOracle $ ModuleFilesKey (modules, dirs ) - foundAutogen <- askOracle $ ModuleFilesKey (modules, [autogen]) + foundSrcDirs <- askOracle $ ModuleFilesKey (dirs , modules) + foundAutogen <- askOracle $ ModuleFilesKey ([autogen], modules) let found = foundSrcDirs ++ foundAutogen missingMods = modules `minusOrd` (sort $ map fst found) @@ -38,18 +38,18 @@ haskellModuleFiles context @ (Context {..}) = do return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) -- | This is an important oracle whose role is to find and cache module source --- files. More specifically, it takes a list of module names @modules@ and a --- list of directories @dirs@ as arguments, and computes a sorted list of pairs --- of the form @(A.B.C, dir/A/B/C.extension)@, such that @A.B.C@ belongs to --- @modules@, @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists. --- For example, for 'compiler' package given --- @modules = ["CodeGen.Platform.ARM", "Lexer"]@, and --- @dirs = ["codeGen", "parser"]@, it produces --- @[("CodeGen.Platform.ARM", "codeGen/CodeGen/Platform/ARM.hs"), --- ("Lexer", "parser/Lexer.x")]@. +-- files. More specifically, it takes a list of directories @dirs@ and a sorted +-- list of module names @modules@ as arguments, and for each module, e.g. +-- @A.B.C@, returns a FilePath of the form @dir/A/B/C.extension@, such that +-- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or Nothing +-- if there is no such file. If more than one matching file is found an error is +-- raised. For example, for the 'compiler' package given +-- @dirs = ["codeGen", "parser"]@, and +-- @modules = ["CodeGen.Platform.ARM", "Lexer", "Missing.Module"]@, it produces +-- @[Just "codeGen/CodeGen/Platform/ARM.hs", Just "parser/Lexer.x", Nothing]@. moduleFilesOracle :: Rules () moduleFilesOracle = void $ - addOracle $ \(ModuleFilesKey (modules, dirs)) -> do + addOracle $ \(ModuleFilesKey (dirs, modules)) -> do let decodedPairs = map decodeModule modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedPairs From git at git.haskell.org Fri Oct 27 00:23:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use conventional whitespacing for @. (31515fa) Message-ID: <20171027002319.DC2A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31515fad107d28f83b47d6249dd7b8c1eeb3bc70/ghc >--------------------------------------------------------------- commit 31515fad107d28f83b47d6249dd7b8c1eeb3bc70 Author: Andrey Mokhov Date: Fri Feb 26 11:37:47 2016 +0000 Use conventional whitespacing for @. See #210. >--------------------------------------------------------------- 31515fad107d28f83b47d6249dd7b8c1eeb3bc70 src/GHC.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 4 ++-- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Rules/Program.hs | 6 +++--- src/Rules/Register.hs | 2 +- src/Settings/Paths.hs | 10 +++++----- src/Way.hs | 2 +- 12 files changed, 20 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 31515fad107d28f83b47d6249dd7b8c1eeb3bc70 From git at git.haskell.org Fri Oct 27 00:23:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop repeated argument (e0de028) Message-ID: <20171027002320.4DA453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e0de0283e09eab974e22c6e37f36479597f3fc78/ghc >--------------------------------------------------------------- commit e0de0283e09eab974e22c6e37f36479597f3fc78 Author: Andrey Mokhov Date: Mon Oct 3 17:23:05 2016 +0100 Drop repeated argument >--------------------------------------------------------------- e0de0283e09eab974e22c6e37f36479597f3fc78 src/Settings/Packages/Compiler.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index df9020d..f33dc18 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -16,8 +16,6 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder Ghc ? arg ("-I" ++ path) - , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) , arg "--disable-library-for-ghci" From git at git.haskell.org Fri Oct 27 00:23:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename runGhc => runghc (e12516f) Message-ID: <20171027002320.9C1593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e12516f4af9047152c7faad88635787b33d6d602/ghc >--------------------------------------------------------------- commit e12516f4af9047152c7faad88635787b33d6d602 Author: Andrey Mokhov Date: Mon Jan 4 14:41:34 2016 +0000 Rename runGhc => runghc >--------------------------------------------------------------- e12516f4af9047152c7faad88635787b33d6d602 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index 1ea0e7f..75f4305 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -79,7 +79,7 @@ pretty = library "pretty" primitive = library "primitive" process = library "process" rts = topLevel "rts" -runGhc = utility "runGhc" +runGhc = utility "runghc" stm = library "stm" templateHaskell = library "template-haskell" terminfo = library "terminfo" From git at git.haskell.org Fri Oct 27 00:23:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (e2fbf4c) Message-ID: <20171027002323.9A34D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2fbf4c8b06e6e9692473dca31b390fe30953256/ghc >--------------------------------------------------------------- commit e2fbf4c8b06e6e9692473dca31b390fe30953256 Author: Andrey Mokhov Date: Fri Feb 26 12:09:40 2016 +0000 Add comments. See #210. >--------------------------------------------------------------- e2fbf4c8b06e6e9692473dca31b390fe30953256 src/Oracles/ModuleFiles.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 508b554..5cb7a5b 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -101,6 +101,8 @@ moduleFilesOracle = void $ do ++ f1 ++ " and " ++ f2 ++ "." return $ lookupAll modules pairs + -- Optimisation: we discard .(l)hs files here, because they are never used + -- as generators, and hence would be discarded in 'findGenerator' anyway. gens <- newCache $ \context -> do files <- contextFiles context return $ Map.fromList [ (generatedFile context modName, src) From git at git.haskell.org Fri Oct 27 00:23:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify paths when printing progress info (6adb600) Message-ID: <20171027002324.812CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6adb60093ae65970bbec17f9b24227b20f5a71f5/ghc >--------------------------------------------------------------- commit 6adb60093ae65970bbec17f9b24227b20f5a71f5 Author: Andrey Mokhov Date: Mon Oct 3 18:22:23 2016 +0100 Unify paths when printing progress info >--------------------------------------------------------------- 6adb60093ae65970bbec17f9b24227b20f5a71f5 src/Rules/Actions.hs | 15 +++++++-------- 1 file changed, 7 insertions(+), 8 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index cbca810..e30bc01 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -200,16 +200,15 @@ putProgressInfo :: String -> Action () putProgressInfo msg = when (cmdProgressInfo /= None) $ putBuild msg -- | Render an action. -renderAction :: String -> String -> String -> String +renderAction :: String -> FilePath -> FilePath -> String renderAction what input output = case cmdProgressInfo of - Normal -> renderBox [ what - , " input: " ++ input - , " => output: " ++ output ] - Brief -> "| " ++ what ++ ": " ++ input ++ " => " ++ output - Unicorn -> renderUnicorn [ what - , " input: " ++ input - , " => output: " ++ output ] + Normal -> renderBox [ what, " input: " ++ i, " => output: " ++ o ] + Brief -> "| " ++ what ++ ": " ++ i ++ " => " ++ o + Unicorn -> renderUnicorn [ what, " input: " ++ i, " => output: " ++ o ] None -> "" + where + i = unifyPath input + o = unifyPath output -- | Render the successful build of a program renderProgram :: String -> String -> String -> String From git at git.haskell.org Fri Oct 27 00:23:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to src/Rules/IntegerGmp.hs. (c4cbb3a) Message-ID: <20171027002324.D40B53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4cbb3a8691851628159ae8f7058efed9f5f8a0a/ghc >--------------------------------------------------------------- commit c4cbb3a8691851628159ae8f7058efed9f5f8a0a Author: Andrey Mokhov Date: Mon Jan 4 16:25:47 2016 +0000 Fix path to src/Rules/IntegerGmp.hs. >--------------------------------------------------------------- c4cbb3a8691851628159ae8f7058efed9f5f8a0a src/Rules/IntegerGmp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index f927102..9bbf482 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -50,7 +50,7 @@ configureArguments = do integerGmpRules :: Rules () integerGmpRules = do integerGmpLibrary %> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules" -/- "integerGmp.hs"] + when trackBuildSystem $ need [sourcePath -/- "Rules/IntegerGmp.hs"] -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] From git at git.haskell.org Fri Oct 27 00:23:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use (Stage, Package) as the key for moduleFilesOracle. (39f61a4) Message-ID: <20171027002327.0AE193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39f61a41680e0abcf2cfe185f6115213b1dbc649/ghc >--------------------------------------------------------------- commit 39f61a41680e0abcf2cfe185f6115213b1dbc649 Author: Andrey Mokhov Date: Fri Feb 26 13:35:33 2016 +0000 Use (Stage, Package) as the key for moduleFilesOracle. See #210. >--------------------------------------------------------------- 39f61a41680e0abcf2cfe185f6115213b1dbc649 src/Oracles/ModuleFiles.hs | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 5cb7a5b..96e66ac 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -11,10 +11,10 @@ import Expression import Oracles.PackageData import Settings.Paths -newtype ModuleFilesKey = ModuleFilesKey Context +newtype ModuleFilesKey = ModuleFilesKey (Stage, Package) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -newtype Generator = Generator (Context, FilePath) +newtype Generator = Generator (Stage, Package, FilePath) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- The following generators and corresponding source extensions are supported: @@ -34,8 +34,8 @@ determineBuilder file = case takeExtension file of -- ".build/stage1/base/build/Prelude.hs" -- == Nothing findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder)) -findGenerator context file = do - maybeSource <- askOracle $ Generator (context, file) +findGenerator Context {..} file = do + maybeSource <- askOracle $ Generator (stage, package, file) return $ do source <- maybeSource builder <- determineBuilder source @@ -62,7 +62,7 @@ contextFiles :: Context -> Action [(String, Maybe FilePath)] contextFiles context at Context {..} = do let path = contextPath context modules <- fmap sort . pkgDataList $ Modules path - zip modules <$> askOracle (ModuleFilesKey context) + zip modules <$> askOracle (ModuleFilesKey (stage, package)) -- | This is an important oracle whose role is to find and cache module source -- files. It takes a 'Context', looks up corresponding source directories @dirs@ @@ -77,12 +77,12 @@ contextFiles context at Context {..} = do -- Just "compiler/parser/Lexer.x"]. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do - void $ addOracle $ \(ModuleFilesKey context) -> do - let path = contextPath context + void $ addOracle $ \(ModuleFilesKey (stage, package)) -> do + let path = contextPath $ vanillaContext stage package autogen = path -/- "build/autogen" srcDirs <- pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - let dirs = autogen : map (pkgPath (package context) -/-) srcDirs + let dirs = autogen : map (pkgPath package -/-) srcDirs modDirFiles = groupSort $ map decodeModule modules result <- fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles @@ -103,10 +103,12 @@ moduleFilesOracle = void $ do -- Optimisation: we discard .(l)hs files here, because they are never used -- as generators, and hence would be discarded in 'findGenerator' anyway. - gens <- newCache $ \context -> do + generators <- newCache $ \(stage, package) -> do + let context = vanillaContext stage package files <- contextFiles context return $ Map.fromList [ (generatedFile context modName, src) | (modName, Just src) <- files , takeExtension src `notElem` [".hs", ".lhs"] ] - addOracle $ \(Generator (context, file)) -> Map.lookup file <$> gens context + addOracle $ \(Generator (stage, package, file)) -> + Map.lookup file <$> generators (stage, package) From git at git.haskell.org Fri Oct 27 00:23:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor libffi build rule (c391842) Message-ID: <20171027002328.8CCF43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3918421098ab7da0d6c62689ccfbe37abe26b24/ghc >--------------------------------------------------------------- commit c3918421098ab7da0d6c62689ccfbe37abe26b24 Author: Andrey Mokhov Date: Mon Oct 3 18:22:48 2016 +0100 Refactor libffi build rule See #289 >--------------------------------------------------------------- c3918421098ab7da0d6c62689ccfbe37abe26b24 src/Rules/Libffi.hs | 79 ++++++++++++++++++++++++++--------------------------- 1 file changed, 39 insertions(+), 40 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 4434f50..5ca17ea 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -6,6 +6,7 @@ import Expression import GHC import Oracles.Config.Flag import Oracles.Config.Setting +import Oracles.WindowsPath import Rules.Actions import Settings.Builders.Common import Settings.Packages.Rts @@ -30,11 +31,11 @@ libffiLibrary = libffiBuildPath -/- "inst/lib/libffi.a" libffiMakefile :: FilePath libffiMakefile = libffiBuildPath -/- "Makefile" -fixLibffiMakefile :: String -> String -fixLibffiMakefile = +fixLibffiMakefile :: FilePath -> String -> String +fixLibffiMakefile top = replace "-MD" "-MMD" . replace "@toolexeclibdir@" "$(libdir)" - . replace "@INSTALL@" "$(subst ../install-sh,C:/msys/home/chEEtah/ghc/install-sh, at INSTALL@)" + . replace "@INSTALL@" ("$(subst ../install-sh," ++ top ++ "/install-sh, at INSTALL@)") -- TODO: remove code duplication (see Settings/Builders/GhcCabal.hs) -- TODO: check code duplication w.r.t. ConfCcArgs @@ -53,12 +54,9 @@ configureEnvironment = do , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w" , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ] --- TODO: remove code duplication (need sourcePath) --- TODO: split into multiple rules libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - need [sourcePath -/- "Rules/Libffi.hs"] useSystemFfi <- flag UseSystemFfi if useSystemFfi then do @@ -68,44 +66,45 @@ libffiRules = do copyFile (ffiIncludeDir -/- file) (rtsBuildPath -/- file) putSuccess $ "| Successfully copied system FFI library header files" else do - removeDirectory libffiBuildPath - createDirectory $ buildRootPath -/- stageString Stage0 - - tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "libffiRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - - need [tarball] - let libname = dropExtension . dropExtension $ takeFileName tarball - - removeDirectory (buildRootPath -/- libname) - -- TODO: Simplify. - actionFinally (do - build $ Target libffiContext Tar [tarball] [buildRootPath] - moveDirectory (buildRootPath -/- libname) libffiBuildPath) $ - removeFiles buildRootPath [libname "*"] - - fixFile (libffiMakefile <.> "in") fixLibffiMakefile - - forM_ ["config.guess", "config.sub"] $ \file -> - copyFile file (libffiBuildPath -/- file) - - env <- configureEnvironment - buildWithCmdOptions env $ - Target libffiContext (Configure libffiBuildPath) - [libffiMakefile <.> "in"] [libffiMakefile] - - -- The old build system did runMake libffiBuildPath ["MAKEFLAGS="] - -- TODO: Find out why. It seems redundant, so I removed it. build $ Target libffiContext (Make libffiBuildPath) [] [] - let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" - forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - copyFile (ffiHDir -/- file) (rtsBuildPath -/- file) + hs <- getDirectoryFiles "" [libffiBuildPath -/- "inst/lib/*/include/*"] + forM_ hs $ \header -> + copyFile header (rtsBuildPath -/- takeFileName header) libffiName <- rtsLibffiLibraryName copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") putSuccess $ "| Successfully built custom library 'libffi'" + + libffiMakefile <.> "in" %> \mkIn -> do + removeDirectory libffiBuildPath + createDirectory $ buildRootPath -/- stageString Stage0 + + tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] + tarball <- case tarballs of -- TODO: Drop code duplication. + [file] -> return $ unifyPath file + _ -> error $ "libffiRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + + need [tarball] + let libname = dropExtension . dropExtension $ takeFileName tarball + + removeDirectory (buildRootPath -/- libname) + -- TODO: Simplify. + actionFinally (do + build $ Target libffiContext Tar [tarball] [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuildPath) $ + removeFiles buildRootPath [libname "*"] + + top <- topDirectory + fixFile mkIn (fixLibffiMakefile top) + + libffiMakefile %> \mk -> do + need [mk <.> "in"] + forM_ ["config.guess", "config.sub"] $ \file -> + copyFile file (libffiBuildPath -/- file) + + env <- configureEnvironment + buildWithCmdOptions env $ + Target libffiContext (Configure libffiBuildPath) [mk <.> "in"] [mk] From git at git.haskell.org Fri Oct 27 00:23:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve handling of generated dependencies, clean up code. (87568c1) Message-ID: <20171027002328.D0D493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/87568c1d948f9c588419b48146bec38a909eb99b/ghc >--------------------------------------------------------------- commit 87568c1d948f9c588419b48146bec38a909eb99b Author: Andrey Mokhov Date: Mon Jan 4 17:26:20 2016 +0000 Improve handling of generated dependencies, clean up code. >--------------------------------------------------------------- 87568c1d948f9c588419b48146bec38a909eb99b src/Rules/Data.hs | 15 ++++++--- src/Rules/Dependencies.hs | 6 +--- src/Rules/Generate.hs | 81 ++++++++++++++++++++++++----------------------- src/Rules/Library.hs | 5 ++- 4 files changed, 56 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 87568c1d948f9c588419b48146bec38a909eb99b From git at git.haskell.org Fri Oct 27 00:23:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix outdated comments. (0273e3e) Message-ID: <20171027002330.6EB9A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0273e3ea2449f646c46059d2be4a7261571511c0/ghc >--------------------------------------------------------------- commit 0273e3ea2449f646c46059d2be4a7261571511c0 Author: Andrey Mokhov Date: Fri Feb 26 15:47:56 2016 +0000 Fix outdated comments. See #210. >--------------------------------------------------------------- 0273e3ea2449f646c46059d2be4a7261571511c0 src/Oracles/ModuleFiles.hs | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 96e66ac..b38929c 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -65,16 +65,16 @@ contextFiles context at Context {..} = do zip modules <$> askOracle (ModuleFilesKey (stage, package)) -- | This is an important oracle whose role is to find and cache module source --- files. It takes a 'Context', looks up corresponding source directories @dirs@ --- and sorted list of module names @modules@, and for each module, e.g. --- @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, such that --- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or 'Nothing' --- if there is no such file. If more than one matching file is found an error is --- raised. For example, for @Context Stage1 compiler vanilla@, @dirs@ will +-- files. It takes a 'Stage' and a 'Package', looks up corresponding source +-- directories @dirs@ and a sorted list of module names @modules@, and for each +-- module, e.g. @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, +-- such that @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or +-- 'Nothing' if there is no such file. If more than one matching file is found +-- an error is raised. For example, for 'Stage1' and 'compiler', @dirs@ will -- contain ["compiler/codeGen", "compiler/parser"], and @modules@ will contain -- ["CodeGen.Platform.ARM", "Config", "Lexer"]; the oracle will produce a list -- containing [Just "compiler/codeGen/CodeGen/Platform/ARM.hs", Nothing, --- Just "compiler/parser/Lexer.x"]. +-- Just "compiler/parser/Lexer.x"]. The oracle ignores @.(l)hs-boot@ files. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do void $ addOracle $ \(ModuleFilesKey (stage, package)) -> do From git at git.haskell.org Fri Oct 27 00:23:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Travis support (64da998) Message-ID: <20171027002332.B3CFA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64da99895a240d9af031ac9357b0bedcb215ac02/ghc >--------------------------------------------------------------- commit 64da99895a240d9af031ac9357b0bedcb215ac02 Author: David Luposchainsky Date: Mon Jan 4 18:20:23 2016 +0100 Add Travis support >--------------------------------------------------------------- 64da99895a240d9af031ac9357b0bedcb215ac02 .travis.yml | 32 ++++++++++++++++++++++++++++++++ .travis/install-cabal-happy-alex.sh | 18 ++++++++++++++++++ .travis/install-ghc-shake.sh | 16 ++++++++++++++++ .travis/install-ghc.sh | 15 +++++++++++++++ .travis/print-env.sh | 9 +++++++++ .travis/run-ghc-shake.sh | 9 +++++++++ README.md | 2 ++ 7 files changed, 101 insertions(+) diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..5e169fa --- /dev/null +++ b/.travis.yml @@ -0,0 +1,32 @@ +sudo: false + +matrix: + include: + - env: CABALVER=1.22 GHCVER=7.10.3 + addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.3,zlib1g-dev,terminfo-dev], sources: [hvr-ghc]}} + +before_install: + + - PATH="$HOME/.cabal/bin:$PATH" + - PATH="/opt/ghc/$GHCVER/bin:$PATH" + - PATH="/opt/cabal/$CABALVER/bin:$PATH" + - export PATH + + - .travis/print-env.sh + +install: + - .travis/install-cabal-happy-alex.sh + - .travis/install-ghc.sh + - .travis/install-ghc-shake.sh + +script: + - .travis/run-ghc-shake.sh + +cache: + directories: + - $HOME/.cabal + # - ghc/shake-build/.cabal-sandbox + # - ghc/shake-build/cabal.sandbox.config + +# before_cache: +# - rm -rf ghc/shake-build diff --git a/.travis/install-cabal-happy-alex.sh b/.travis/install-cabal-happy-alex.sh new file mode 100755 index 0000000..93df460 --- /dev/null +++ b/.travis/install-cabal-happy-alex.sh @@ -0,0 +1,18 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[32m" # Green +RESET="\e[m" + +echo -e "${COLOR}GHC version:${RESET}" +ghc --version + +echo -e "${COLOR}Cabal version:${RESET}" +cabal --version + +echo -e "${COLOR}Update Cabal${RESET}" +cabal update + +echo -e "${COLOR}Install Alex+Happy${RESET}" +cabal install alex happy diff --git a/.travis/install-ghc-shake.sh b/.travis/install-ghc-shake.sh new file mode 100755 index 0000000..2dc0392 --- /dev/null +++ b/.travis/install-ghc-shake.sh @@ -0,0 +1,16 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[31m" # Red, because this file is serious business +RESET="\e[m" + +echo -e "${COLOR}Brutally hacking GHC-Shake to its proper location${RESET}" +SHAKEDIR="ghc/shake-build" +mkdir -p "$SHAKEDIR" +mv .git "$SHAKEDIR/" +( cd "$SHAKEDIR" && git reset --hard HEAD ) + +echo -e "${COLOR}Installing deps into sandbox${RESET}" +( cd "$SHAKEDIR" && cabal sandbox init ) +( cd "$SHAKEDIR" && cabal install --only-dependencies . ) diff --git a/.travis/install-ghc.sh b/.travis/install-ghc.sh new file mode 100755 index 0000000..126cbe2 --- /dev/null +++ b/.travis/install-ghc.sh @@ -0,0 +1,15 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[34m" # Blue +RESET="\e[m" + +echo -e "${COLOR}Clone GHC source${RESET}" +git clone git://git.haskell.org/ghc + +echo -e "${COLOR}Initialize GHC submodules${RESET}" +( cd ghc && git submodule update --init ) + +echo -e "${COLOR}GHC boot/configure${RESET}" +( cd ghc && ./boot && ./configure) diff --git a/.travis/print-env.sh b/.travis/print-env.sh new file mode 100755 index 0000000..c09c11f --- /dev/null +++ b/.travis/print-env.sh @@ -0,0 +1,9 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[32m" # Green +RESET="\e[m" + +echo -e "${COLOR}Environment:${RESET}" +env diff --git a/.travis/run-ghc-shake.sh b/.travis/run-ghc-shake.sh new file mode 100755 index 0000000..7b867b7 --- /dev/null +++ b/.travis/run-ghc-shake.sh @@ -0,0 +1,9 @@ +#!/usr/bin/env bash + +set -euo pipefail + +COLOR="\e[32m" # Green +RESET="\e[m" + +echo -e "${COLOR}Running Shake build system${RESET}" +( cd ghc && ./shake-build/build.cabal.sh ) diff --git a/README.md b/README.md index f26cc49..43b74be 100644 --- a/README.md +++ b/README.md @@ -1,6 +1,8 @@ Shaking up GHC ============== +[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) + As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC][ghc] build system based on standard `make` into a new and (hopefully) better one based on From git at git.haskell.org Fri Oct 27 00:23:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (d8a249b) Message-ID: <20171027002333.F07C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d8a249b43b494428675b85fab7e53dff4ce859d9/ghc >--------------------------------------------------------------- commit d8a249b43b494428675b85fab7e53dff4ce859d9 Author: Andrey Mokhov Date: Fri Feb 26 19:00:31 2016 +0000 Add comments. See #55. >--------------------------------------------------------------- d8a249b43b494428675b85fab7e53dff4ce859d9 src/Settings/Paths.hs | 31 ++++++++++++++++++------------- 1 file changed, 18 insertions(+), 13 deletions(-) diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 6ad6b9d..629d6d0 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -11,58 +11,63 @@ import GHC import Oracles.PackageData import Settings.User --- Path to the target directory from GHC source root +-- | Path to the directory containing build artefacts of a given 'Context'. contextPath :: Context -> FilePath contextPath context at Context {..} = buildRootPath -/- contextDirectory context -/- pkgPath package +-- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath pkgDataFile context = contextPath context -/- "package-data.mk" --- Relative path to a package haddock file, e.g.: --- "libraries/array/dist-install/doc/html/array/array.haddock" +-- | Path to the haddock file of a given 'Context', e.g.: +-- ".build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = contextPath context -/- "doc/html" -/- name -/- name <.> "haddock" where name = pkgNameString package --- Relative path to a package library file, e.g.: --- "libraries/array/stage2/build/libHSarray-0.5.1.0.a" +-- | Path to the library file of a given 'Context', e.g.: +-- ".build/stage1/libraries/array/build/libHSarray-0.5.1.0.a". pkgLibraryFile :: Context -> Action FilePath pkgLibraryFile context at Context {..} = do extension <- libsuf way - pkgFile context "build/libHS" extension + pkgFile context "libHS" extension +-- | Path to the auxiliary library file of a given 'Context', e.g.: +-- ".build/stage1/compiler/build/libHSghc-8.1-0.a". pkgLibraryFile0 :: Context -> Action FilePath pkgLibraryFile0 context at Context {..} = do extension <- libsuf way - pkgFile context "build/libHS" ("-0" ++ extension) + pkgFile context "libHS" ("-0" ++ extension) --- Relative path to a package ghci library file, e.g.: --- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" +-- | Path to the GHCi library file of a given 'Context', e.g.: +-- ".build/stage1/libraries/array/build/HSarray-0.5.1.0.o". pkgGhciLibraryFile :: Context -> Action FilePath -pkgGhciLibraryFile context = pkgFile context "build/HS" ".o" +pkgGhciLibraryFile context = pkgFile context "HS" ".o" pkgFile :: Context -> String -> String -> Action FilePath pkgFile context prefix suffix = do let path = contextPath context componentId <- pkgData $ ComponentId path - return $ path -/- prefix ++ componentId ++ suffix + return $ path -/- "build" -/- prefix ++ componentId ++ suffix --- This is the build directory for in-tree GMP library +-- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" --- We extract system gmp library name from this file +-- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory +-- | Path to package database directory of a given 'Stage'. packageDbDirectory :: Stage -> FilePath packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" +-- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do componentId <- pkgData . ComponentId $ contextPath context From git at git.haskell.org Fri Oct 27 00:23:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't track -jN arguments passed to Make (b096f1e) Message-ID: <20171027002332.7C9943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b096f1e48ba8df3e1636c8671ec867fc6b636c29/ghc >--------------------------------------------------------------- commit b096f1e48ba8df3e1636c8671ec867fc6b636c29 Author: Andrey Mokhov Date: Wed Oct 5 13:28:28 2016 +0100 Don't track -jN arguments passed to Make See #289. >--------------------------------------------------------------- b096f1e48ba8df3e1636c8671ec867fc6b636c29 src/Builder.hs | 13 +++++++++++-- src/Oracles/ArgsHash.hs | 6 +++++- 2 files changed, 16 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 1974eff..704947d 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,10 +1,11 @@ {-# LANGUAGE DeriveGeneric, LambdaCase #-} module Builder ( - CcMode (..), GhcMode (..), Builder (..), - builderPath, getBuilderPath, builderEnvironment, specified, needBuilder + CcMode (..), GhcMode (..), Builder (..), builderPath, getBuilderPath, + builderEnvironment, specified, trackedArgument, needBuilder ) where import Control.Monad.Trans.Reader +import Data.Char import GHC.Generics (Generic) import Base @@ -149,6 +150,14 @@ builderEnvironment variable builder = do specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath +-- | Some arguments do not affect build results and therefore do not need to be +-- tracked by the build system. A notable example is "-jN" that controls Make's +-- parallelism. Given a 'Builder' and an argument, this function should return +-- 'True' only if the argument needs to be tracked. +trackedArgument :: Builder -> String -> Bool +trackedArgument (Make _) ('-' : 'j' : xs) = not $ all isDigit xs +trackedArgument _ _ = True + -- | Make sure a Builder exists on the given path and rebuild it if out of date. needBuilder :: Builder -> Action () needBuilder = \case diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 660edd9..f9cec24 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -2,6 +2,7 @@ module Oracles.ArgsHash (checkArgsHash, argsHashOracle) where import Base +import Builder import Expression import Settings import Target @@ -28,4 +29,7 @@ checkArgsHash target = do -- | Oracle for storing per-target argument list hashes. argsHashOracle :: Rules () argsHashOracle = void $ - addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs + addOracle $ \(ArgsHashKey target) -> do + argList <- interpret target getArgs + let trackedArgList = filter (trackedArgument $ builder target) argList + return $ hash trackedArgList From git at git.haskell.org Fri Oct 27 00:23:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Support several variants of -jN flag, add tests (73b9b7b) Message-ID: <20171027002336.637833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73b9b7b47f9c33506be8238d355eba2363470ce9/ghc >--------------------------------------------------------------- commit 73b9b7b47f9c33506be8238d355eba2363470ce9 Author: Andrey Mokhov Date: Wed Oct 5 15:31:26 2016 +0100 Support several variants of -jN flag, add tests See #289. >--------------------------------------------------------------- 73b9b7b47f9c33506be8238d355eba2363470ce9 src/Builder.hs | 7 +++++-- src/Rules/Selftest.hs | 22 ++++++++++++++++------ 2 files changed, 21 insertions(+), 8 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 704947d..55d561e 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -155,8 +155,11 @@ specified = fmap (not . null) . builderPath -- parallelism. Given a 'Builder' and an argument, this function should return -- 'True' only if the argument needs to be tracked. trackedArgument :: Builder -> String -> Bool -trackedArgument (Make _) ('-' : 'j' : xs) = not $ all isDigit xs -trackedArgument _ _ = True +trackedArgument (Make _) = not . threadArg +trackedArgument _ = const True + +threadArg :: String -> Bool +threadArg s = dropWhileEnd isDigit s `elem` ["-j", "MAKEFLAGS=-j", "THREADS="] -- | Make sure a Builder exists on the given path and rebuild it if out of date. needBuilder :: Builder -> Action () diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f53a5db..3b20f14 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,6 +6,7 @@ import Development.Shake import Test.QuickCheck import Base +import Builder import Oracles.ModuleFiles import Settings.Builders.Ar import UserSettings @@ -23,14 +24,23 @@ test = liftIO . quickCheck selftestRules :: Rules () selftestRules = "selftest" ~> do - testWays + testBuilder + testWay testChunksOfSize testMatchVersionedFilePath - testModuleNames + testModuleName testLookupAll -testWays :: Action () -testWays = do +testBuilder :: Action () +testBuilder = do + putBuild $ "==== trackedArgument" + test $ forAll (elements ["-j", "MAKEFLAGS=-j", "THREADS="]) + $ \prefix -> \(NonNegative n) -> + trackedArgument (Make undefined) prefix == False && + trackedArgument (Make undefined) ("-j" ++ show (n :: Int)) == False + +testWay :: Action () +testWay = do putBuild $ "==== Read Way, Show Way" test $ \(x :: Way) -> read (show x) == x @@ -59,8 +69,8 @@ testMatchVersionedFilePath = do where versions = listOf . elements $ '-' : '.' : ['0'..'9'] -testModuleNames :: Action () -testModuleNames = do +testModuleName :: Action () +testModuleName = do putBuild $ "==== Encode/decode module name" test $ encodeModule "Data/Functor" "Identity.hs" == "Data.Functor.Identity" test $ encodeModule "" "Prelude" == "Prelude" From git at git.haskell.org Fri Oct 27 00:23:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #93 from quchen/travis-ci (45c731c) Message-ID: <20171027002336.861C53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45c731c4105f0eb7daf2975cb9073f6879587042/ghc >--------------------------------------------------------------- commit 45c731c4105f0eb7daf2975cb9073f6879587042 Merge: 87568c1 64da998 Author: Andrey Mokhov Date: Mon Jan 4 18:51:30 2016 +0000 Merge pull request #93 from quchen/travis-ci Travis CI using dirty tricks >--------------------------------------------------------------- 45c731c4105f0eb7daf2975cb9073f6879587042 .travis.yml | 32 ++++++++++++++++++++++++++++++++ .travis/install-cabal-happy-alex.sh | 18 ++++++++++++++++++ .travis/install-ghc-shake.sh | 16 ++++++++++++++++ .travis/install-ghc.sh | 15 +++++++++++++++ .travis/print-env.sh | 9 +++++++++ .travis/run-ghc-shake.sh | 9 +++++++++ README.md | 2 ++ 7 files changed, 101 insertions(+) From git at git.haskell.org Fri Oct 27 00:23:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant 'build' component in build paths, rename contextPath to buildPath. (0d7891b) Message-ID: <20171027002337.6E0F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0d7891b43ae5f3bd4dd6b271749187cfd4a24f77/ghc >--------------------------------------------------------------- commit 0d7891b43ae5f3bd4dd6b271749187cfd4a24f77 Author: Andrey Mokhov Date: Fri Feb 26 22:36:38 2016 +0000 Drop redundant 'build' component in build paths, rename contextPath to buildPath. >--------------------------------------------------------------- 0d7891b43ae5f3bd4dd6b271749187cfd4a24f77 src/Oracles/ModuleFiles.hs | 16 +++++++--------- src/Rules/Compile.hs | 18 +++++++++--------- src/Rules/Data.hs | 18 +++++++++--------- src/Rules/Dependencies.hs | 15 +++++++-------- src/Rules/Generate.hs | 29 +++++++++++++---------------- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 18 +++++++++--------- src/Rules/Program.hs | 10 +++++----- src/Rules/Register.hs | 13 +++++++------ src/Settings.hs | 10 +++++----- src/Settings/Builders/Common.hs | 7 +++---- src/Settings/Builders/Ghc.hs | 19 ++++++++----------- src/Settings/Builders/Haddock.hs | 4 ++-- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 4 ++-- src/Settings/Packages/Hp2ps.hs | 2 +- src/Settings/Packages/Rts.hs | 4 ++-- src/Settings/Packages/Touchy.hs | 4 ++-- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/Paths.hs | 16 ++++++++-------- 23 files changed, 107 insertions(+), 116 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 0d7891b43ae5f3bd4dd6b271749187cfd4a24f77 From git at git.haskell.org Fri Oct 27 00:23:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Continue refactoring of generated dependencies. (64f9350) Message-ID: <20171027002339.EB7D03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64f93509197b23722bf14928ce50c5a3930b4d27/ghc >--------------------------------------------------------------- commit 64f93509197b23722bf14928ce50c5a3930b4d27 Author: Andrey Mokhov Date: Mon Jan 4 19:59:27 2016 +0000 Continue refactoring of generated dependencies. >--------------------------------------------------------------- 64f93509197b23722bf14928ce50c5a3930b4d27 src/Rules/Dependencies.hs | 4 +-- src/Rules/Generate.hs | 87 ++++++++++++++++++++++++++--------------------- 2 files changed, 50 insertions(+), 41 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 5b51c1d..b0dd474 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -18,13 +18,13 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do let srcFile = dropBuild . dropExtension $ out - orderOnly $ generatedDependencies stage pkg + orderOnly $ generatedDependencies stage need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - orderOnly $ generatedDependencies stage pkg + orderOnly $ generatedDependencies stage need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 21c197b..140c978 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -16,6 +16,7 @@ import Oracles.ModuleFiles import Rules.Actions import Rules.Resources (Resources) import Settings +import Settings.Builders.DeriveConstants primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -26,47 +27,55 @@ primopsTxt stage = targetPath stage compiler -/- "build/primops.txt" platformH :: Stage -> FilePath platformH stage = targetPath stage compiler -/- "ghc_boot_platform.h" -derivedConstantsPath :: FilePath -derivedConstantsPath = "includes/dist-derivedconstants/header" - -defaultGeneratedDependencies :: [FilePath] -defaultGeneratedDependencies = - [ "includes/ghcautoconf.h" - , "includes/ghcplatform.h" - , derivedConstantsPath -/- "DerivedConstants.h" - , derivedConstantsPath -/- "GHCConstantsHaskellType.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs" - , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" - , targetPath Stage1 rts -/- "build/ffi.h" - , targetPath Stage1 rts -/- "build/ffitarget.h" ] +includesDependencies :: [FilePath] +includesDependencies = ("includes" -/-) <$> + [ "ghcautoconf.h" + , "ghcplatform.h" + , "ghcversion.h" ] + +derivedConstantsDependencies :: [FilePath] +derivedConstantsDependencies = (derivedConstantsPath -/-) <$> [] + -- [ "DerivedConstants.h" + -- , "GHCConstantsHaskellType.hs" + -- , "GHCConstantsHaskellWrappers.hs" + -- , "GHCConstantsHaskellExports.hs" ] + +libffiDependencies :: [FilePath] +libffiDependencies = (targetPath Stage1 rts -/-) <$> + [ "build/ffi.h" + , "build/ffitarget.h" ] + +defaultDependencies :: [FilePath] +defaultDependencies = + includesDependencies ++ derivedConstantsDependencies ++ libffiDependencies + +compilerDependencies :: Stage -> [FilePath] +compilerDependencies stage = + [ platformH stage ] + ++ + fmap ((targetPath stage compiler -/- "build") -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] -- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? -generatedDependencies :: Stage -> Package -> [FilePath] -generatedDependencies stage pkg = - defaultGeneratedDependencies ++ extraGeneratedDependencies - where - extraGeneratedDependencies - | pkg == compiler = let buildPath = targetPath stage compiler -/- "build" - in - [ platformH stage ] - ++ - fmap (buildPath -/-) - [ "primop-vector-uniques.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" - , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] - | otherwise = [] +-- TODO: improve +generatedDependencies :: Stage -> [FilePath] +generatedDependencies stage + | stage == Stage1 = defaultDependencies ++ compilerDependencies stage + | otherwise = [] -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] From git at git.haskell.org Fri Oct 27 00:23:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix warnings (8cfa6ef) Message-ID: <20171027002340.29DA93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8cfa6efa9fb742b90b2c3019536365f711392b75/ghc >--------------------------------------------------------------- commit 8cfa6efa9fb742b90b2c3019536365f711392b75 Author: Andrey Mokhov Date: Wed Oct 5 15:31:45 2016 +0100 Fix warnings >--------------------------------------------------------------- 8cfa6efa9fb742b90b2c3019536365f711392b75 src/Oracles/ArgsHash.hs | 6 +++--- src/Settings/Packages/Compiler.hs | 1 - 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index f9cec24..36a0cdd 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -30,6 +30,6 @@ checkArgsHash target = do argsHashOracle :: Rules () argsHashOracle = void $ addOracle $ \(ArgsHashKey target) -> do - argList <- interpret target getArgs - let trackedArgList = filter (trackedArgument $ builder target) argList - return $ hash trackedArgList + argList <- interpret target getArgs + let trackedArgList = filter (trackedArgument $ builder target) argList + return $ hash trackedArgList diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index f33dc18..03b8081 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -7,7 +7,6 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Predicate import Settings -import Settings.Paths compilerPackageArgs :: Args compilerPackageArgs = package compiler ? do From git at git.haskell.org Fri Oct 27 00:23:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use default project name on AppVeyor. (2e3ec0c) Message-ID: <20171027002341.1CF023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2e3ec0cce02a1f125b5672b2f7a5fb85afee0605/ghc >--------------------------------------------------------------- commit 2e3ec0cce02a1f125b5672b2f7a5fb85afee0605 Author: Andrey Mokhov Date: Fri Feb 26 22:55:25 2016 +0000 Use default project name on AppVeyor. >--------------------------------------------------------------- 2e3ec0cce02a1f125b5672b2f7a5fb85afee0605 .appveyor.yml => appveyor.yml | 0 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/.appveyor.yml b/appveyor.yml similarity index 100% rename from .appveyor.yml rename to appveyor.yml From git at git.haskell.org Fri Oct 27 00:23:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix libCffi name on Windows (fix #89). (19310e7) Message-ID: <20171027002344.6D6093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/19310e7fbaf16190f0e206564f45f76cb6e20b61/ghc >--------------------------------------------------------------- commit 19310e7fbaf16190f0e206564f45f76cb6e20b61 Author: Andrey Mokhov Date: Mon Jan 4 20:09:33 2016 +0000 Fix libCffi name on Windows (fix #89). >--------------------------------------------------------------- 19310e7fbaf16190f0e206564f45f76cb6e20b61 src/Rules/Copy.hs | 4 +++- src/Settings/Packages/Rts.hs | 14 ++++++++++---- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index bcd1f1e..b1f9760 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -6,6 +6,7 @@ import GHC import Rules.Actions import Rules.Generate import Rules.Libffi +import Settings.Packages.Rts import Settings.TargetDirectory installTargets :: [FilePath] @@ -23,7 +24,8 @@ copyRules = do ++ "(found: " ++ show ffiHPaths ++ ")." copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih - copyFile libffiLibrary (targetPath Stage1 rts -/- "build" -/- "libCffi.a") + libffiName <- rtsLibffiLibraryName + copyFile libffiLibrary (targetPath Stage1 rts -/- "build/lib" ++ libffiName <.> "a") "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 56b0cf8..421d7f7 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,4 +1,6 @@ -module Settings.Packages.Rts (rtsPackageArgs, rtsConfIn, rtsConf) where +module Settings.Packages.Rts ( + rtsPackageArgs, rtsConfIn, rtsConf, rtsLibffiLibraryName + ) where import Base import Expression @@ -15,6 +17,11 @@ rtsConfIn = pkgPath rts -/- "package.conf.in" rtsConf :: FilePath rtsConf = targetPath Stage1 rts -/- "package.conf.inplace" +rtsLibffiLibraryName :: Action FilePath +rtsLibffiLibraryName = do + windows <- windowsHost + return $ if windows then "Cffi-6" else "Cffi" + rtsPackageArgs :: Args rtsPackageArgs = package rts ? do let yesNo = lift . fmap (\x -> if x then "YES" else "NO") @@ -36,8 +43,7 @@ rtsPackageArgs = package rts ? do way <- getWay path <- getTargetPath top <- getSetting GhcSourcePath - windows <- lift $ windowsHost - let libffiName = if windows then "ffi-6" else "ffi" + libffiName <- lift $ rtsLibffiLibraryName mconcat [ builderGcc ? mconcat [ arg "-Irts" @@ -74,7 +80,7 @@ rtsPackageArgs = package rts ? do [ arg ("-DTOP=" ++ quote top) , arg "-DFFI_INCLUDE_DIR=" , arg "-DFFI_LIB_DIR=" - , arg $ "-DFFI_LIB=" ++ quote ("C" ++ libffiName) ] ] + , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] -- #----------------------------------------------------------------------------- -- # Use system provided libffi From git at git.haskell.org Fri Oct 27 00:23:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (9233793) Message-ID: <20171027002344.C05A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9233793b86b2b14efa3ae1adb5f95f378bf15ef8/ghc >--------------------------------------------------------------- commit 9233793b86b2b14efa3ae1adb5f95f378bf15ef8 Author: Andrey Mokhov Date: Wed Oct 5 17:35:44 2016 +0100 Minor revision >--------------------------------------------------------------- 9233793b86b2b14efa3ae1adb5f95f378bf15ef8 src/Rules/Selftest.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 +++----- 2 files changed, 4 insertions(+), 6 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 3b20f14..e7f5dbb 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -35,7 +35,7 @@ testBuilder :: Action () testBuilder = do putBuild $ "==== trackedArgument" test $ forAll (elements ["-j", "MAKEFLAGS=-j", "THREADS="]) - $ \prefix -> \(NonNegative n) -> + $ \prefix (NonNegative n) -> trackedArgument (Make undefined) prefix == False && trackedArgument (Make undefined) ("-j" ++ show (n :: Int)) == False diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 6eaf8ae..7f54af9 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -36,15 +36,13 @@ ghcLinkArgs :: Args ghcLinkArgs = builder (Ghc LinkHs) ? do stage <- getStage libs <- getPkgDataList DepExtraLibs + libDirs <- getPkgDataList DepLibDirs gmpLibs <- if stage > Stage0 then do -- TODO: get this data more gracefully + let strip = fromMaybe "" . stripPrefix "extra-libraries: " buildInfo <- lift $ readFileLines gmpBuildInfoPath - let extract s = case stripPrefix "extra-libraries: " s of - Nothing -> [] - Just value -> words value - return $ concatMap extract buildInfo + return $ concatMap (words . strip) buildInfo else return [] - libDirs <- getPkgDataList DepLibDirs mconcat [ arg "-no-auto-link-packages" , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] From git at git.haskell.org Fri Oct 27 00:23:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing arguments for rts package. (13b1491) Message-ID: <20171027002345.549213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13b1491faf02d9e03385ad61a26bf90cbc951fda/ghc >--------------------------------------------------------------- commit 13b1491faf02d9e03385ad61a26bf90cbc951fda Author: Andrey Mokhov Date: Sun Feb 28 23:47:46 2016 +0000 Add missing arguments for rts package. >--------------------------------------------------------------- 13b1491faf02d9e03385ad61a26bf90cbc951fda src/Settings/Packages/Rts.hs | 16 +++++++--------- 1 file changed, 7 insertions(+), 9 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 334a712..ba79289 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -62,7 +62,9 @@ rtsPackageArgs = package rts ? do -- there is a non-inlined variant to use instead. But rts does not -- provide non-inlined alternatives and hence needs the function to -- be inlined. See also Issue #90 - , arg $ "-O2" + , arg "-O2" + + , way == threaded ? arg "-DTHREADED_RTS" , (file "//RtsMessages.*" ||^ file "//Trace.*") ? arg ("-DProjectVersion=" ++ quote projectVersion) @@ -82,7 +84,10 @@ rtsPackageArgs = package rts ? do , "-DTargetOS=" ++ quote targetOs , "-DTargetVendor=" ++ quote targetVendor , "-DGhcUnregisterised=" ++ quote ghcUnreg - , "-DGhcEnableTablesNextToCode=" ++ quote ghcEnableTNC ] ] + , "-DGhcEnableTablesNextToCode=" ++ quote ghcEnableTNC ] + + , (file "//Evac_thr.*" ||^ file "//Scav_thr.*") ? + append [ "-DPARALLEL_GC", "-Irts/sm" ] ] , builderGhc ? (arg "-Irts" <> includesArgs) @@ -233,10 +238,3 @@ rtsPackageArgs = package rts ? do -- # -O3 helps unroll some loops (especially in copy() with a constant argument). -- rts/sm/Evac_CC_OPTS += -funroll-loops -- rts/dist/build/sm/Evac_thr_HC_OPTS += -optc-funroll-loops - --- # These files are just copies of sm/Evac.c and sm/Scav.c respectively, --- # but compiled with -DPARALLEL_GC. --- rts/dist/build/sm/Evac_thr_CC_OPTS += -DPARALLEL_GC -Irts/sm --- rts/dist/build/sm/Scav_thr_CC_OPTS += -DPARALLEL_GC -Irts/sm - --- #----------------------------------------------------------------------------- From git at git.haskell.org Fri Oct 27 00:23:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add topDirectory function instead of less reliable GhcSourcePath. (5bc7a0a) Message-ID: <20171027002348.B605E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5bc7a0ae097f038f3b04227b214a985a0c60cfbc/ghc >--------------------------------------------------------------- commit 5bc7a0ae097f038f3b04227b214a985a0c60cfbc Author: Andrey Mokhov Date: Tue Jan 5 00:53:11 2016 +0000 Add topDirectory function instead of less reliable GhcSourcePath. >--------------------------------------------------------------- 5bc7a0ae097f038f3b04227b214a985a0c60cfbc src/Builder.hs | 19 ------------------- src/Oracles/WindowsRoot.hs | 29 ++++++++++++++++++++++++++++- src/Rules/Actions.hs | 4 ++-- src/Rules/Libffi.hs | 4 ++-- src/Rules/Wrappers/Ghc.hs | 4 ++-- src/Rules/Wrappers/GhcPkg.hs | 4 ++-- src/Settings.hs | 5 ++++- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- 10 files changed, 44 insertions(+), 33 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 5bc7a0ae097f038f3b04227b214a985a0c60cfbc From git at git.haskell.org Fri Oct 27 00:23:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Limit Make's thread (703429d) Message-ID: <20171027002349.66FF73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/703429d917a4349d0a7ec8809dfb41c8b3433937/ghc >--------------------------------------------------------------- commit 703429d917a4349d0a7ec8809dfb41c8b3433937 Author: Andrey Mokhov Date: Wed Oct 5 17:36:32 2016 +0100 Limit Make's thread See #289. >--------------------------------------------------------------- 703429d917a4349d0a7ec8809dfb41c8b3433937 src/Settings/Builders/Make.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index d6b7dbf..1e55d9a 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -7,7 +7,7 @@ import Settings.Paths makeBuilderArgs :: Args makeBuilderArgs = do threads <- shakeThreads <$> lift getShakeOptions - let t = show threads + let t = show $ max 4 (threads - 2) -- Don't use all Shake's threads mconcat [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=-j" ++ t] , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=-j" ++ t, "install"] From git at git.haskell.org Fri Oct 27 00:23:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix haddock. (7e7497a) Message-ID: <20171027002349.DCFD53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1/ghc >--------------------------------------------------------------- commit 7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1 Author: Andrey Mokhov Date: Mon Feb 29 02:02:53 2016 +0000 Fix haddock. >--------------------------------------------------------------- 7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1 src/Rules/Data.hs | 18 +++++++++--------- src/Rules/Dependencies.hs | 35 ++++++++++++++++++++++++----------- src/Rules/Generate.hs | 16 +++++++++------- src/Rules/Library.hs | 33 +++++++++++++++++++++------------ src/Settings/Packages/Rts.hs | 19 +++++++++---------- 5 files changed, 72 insertions(+), 49 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 7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1 From git at git.haskell.org Fri Oct 27 00:23:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop ghcPwd package, we no longer build it. (9050f37) Message-ID: <20171027002352.8ED373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9050f373671103cd80336e19880a7c14fd7920ab/ghc >--------------------------------------------------------------- commit 9050f373671103cd80336e19880a7c14fd7920ab Author: Andrey Mokhov Date: Tue Jan 5 00:56:31 2016 +0000 Drop ghcPwd package, we no longer build it. >--------------------------------------------------------------- 9050f373671103cd80336e19880a7c14fd7920ab src/GHC.hs | 17 ++++++++--------- src/Settings/Packages.hs | 2 +- 2 files changed, 9 insertions(+), 10 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 75f4305..d4d5511 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -2,8 +2,8 @@ module GHC ( array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, - ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, + haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml, @@ -25,16 +25,16 @@ defaultKnownPackages = [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes , deepseq, deriveConstants, directory, dllSplit, filepath, genapply , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim - , ghcPwd, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin - , integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel - , pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo - , time, transformers, unix, win32, xhtml ] + , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp + , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty + , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time + , transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcPwd, - ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, + genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, + haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, transformers, unix, win32, xhtml :: Package @@ -60,7 +60,6 @@ ghcCabal = utility "ghc-cabal" ghci = library "ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" -ghcPwd = utility "ghc-pwd" ghcTags = utility "ghctags" haddock = utility "haddock" haskeline = library "haskeline" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 10ed9e1..dba4054 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -31,7 +31,7 @@ packagesStage1 :: Packages packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq - , directory, filepath, ghci, ghcPrim, ghcPwd, haskeline, hpcBin + , directory, filepath, ghci, ghcPrim, haskeline, hpcBin , integerLibrary, mkUserGuidePart, pretty, process, rts, runGhc , time ] , windowsHost ? append [win32] From git at git.haskell.org Fri Oct 27 00:23:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reduce verbosity of ghc-cabal and ghc-pkg (d3d00b0) Message-ID: <20171027002353.24E483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3d00b0c412d964891f63fbd6c52bc457d6b3233/ghc >--------------------------------------------------------------- commit d3d00b0c412d964891f63fbd6c52bc457d6b3233 Author: Andrey Mokhov Date: Wed Oct 5 17:36:54 2016 +0100 Reduce verbosity of ghc-cabal and ghc-pkg >--------------------------------------------------------------- d3d00b0c412d964891f63fbd6c52bc457d6b3233 src/Settings/Builders/GhcCabal.hs | 37 ++++++++++++++++++++----------------- src/Settings/Builders/GhcPkg.hs | 2 ++ 2 files changed, 22 insertions(+), 17 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 14c1254..fffb2c0 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -17,23 +17,26 @@ import Settings.Builders.Common import Settings.Paths ghcCabalBuilderArgs :: Args -ghcCabalBuilderArgs = builder GhcCabal ? mconcat - [ arg "configure" - , arg =<< getPackagePath - , arg =<< getContextDirectory - , dll0Args - , withStaged $ Ghc CompileHs - , withStaged GhcPkg - , bootPackageDatabaseArgs - , libraryArgs - , with HsColour - , configureArgs - , packageConstraints - , withStaged $ Cc CompileC - , notStage0 ? with Ld - , with Ar - , with Alex - , with Happy ] +ghcCabalBuilderArgs = builder GhcCabal ? do + verbosity <- lift $ getVerbosity + mconcat [ arg "configure" + , arg =<< getPackagePath + , arg =<< getContextDirectory + , dll0Args + , withStaged $ Ghc CompileHs + , withStaged GhcPkg + , bootPackageDatabaseArgs + , libraryArgs + , with HsColour + , configureArgs + , packageConstraints + , withStaged $ Cc CompileC + , notStage0 ? with Ld + , with Ar + , with Alex + , with Happy + , verbosity < Chatty ? append [ "-v0", "--configure-option=--quiet" + , "--configure-option=--disable-option-checking" ] ] ghcCabalHsColourBuilderArgs :: Args ghcCabalHsColourBuilderArgs = builder GhcCabalHsColour ? do diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index ed6843a..b221b9d 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -20,7 +20,9 @@ updateArgs :: Args updateArgs = notM initPredicate ? do pkg <- getPackage dir <- getContextDirectory + verbosity <- lift $ getVerbosity mconcat [ arg "update" , arg "--force" + , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs , arg $ pkgPath pkg -/- dir -/- "inplace-pkg-config" ] From git at git.haskell.org Fri Oct 27 00:23:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add docs for how to compile on Windows, with a list of complete instructions (3dcbe7a) Message-ID: <20171027002353.88D0B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3dcbe7a62e7ad62016456000c925d6493e509a2e/ghc >--------------------------------------------------------------- commit 3dcbe7a62e7ad62016456000c925d6493e509a2e Author: Neil Mitchell Date: Thu Mar 3 20:52:50 2016 +0000 Add docs for how to compile on Windows, with a list of complete instructions >--------------------------------------------------------------- 3dcbe7a62e7ad62016456000c925d6493e509a2e doc/windows.md | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) diff --git a/doc/windows.md b/doc/windows.md new file mode 100644 index 0000000..2d823e7 --- /dev/null +++ b/doc/windows.md @@ -0,0 +1,26 @@ +# Compiling on Windows + +Here are a list of instructions to compile GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. + +The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_64-installer) (I just accepted all the defaults), then open a command prompt and run: + + stack setup + stack install happy alex + stack exec -- pacman -S gcc binutils git automake-wrapper tar make patch autoconf --noconfirm + stack exec -- git clone --recursive git://git.haskell.org/ghc.git + cd ghc + stack exec -- git clone git://github.com/snowleopard/shaking-up-ghc shake-build + stack build --stack-yaml=shake-build/stack.yaml --only-dependencies + stack exec -- perl boot + stack exec -- bash configure --enable-tarballs-autodownload + stack exec --stack-yaml=shake-build/stack.yaml -- shake-build/build.bat -j + +The entire process should take about an hour. + +#### Future ideas + +Here are some alternatives that have been considered, but not yet tested. Use the instructions above. + +* Use `shake-build/build.bat --setup` to replace `boot` and `configure`. +* The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. +* Can Happy/Alex be installed by adding them as tool dependencies to the Stack file? From git at git.haskell.org Fri Oct 27 00:23:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix a loop in generated dependencies. (e651350) Message-ID: <20171027002356.5D2A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e6513507c7e75050ba93724d8d7e79ecf6adf146/ghc >--------------------------------------------------------------- commit e6513507c7e75050ba93724d8d7e79ecf6adf146 Author: Andrey Mokhov Date: Tue Jan 5 01:26:02 2016 +0000 Fix a loop in generated dependencies. >--------------------------------------------------------------- e6513507c7e75050ba93724d8d7e79ecf6adf146 src/Rules/Dependencies.hs | 4 ++-- src/Rules/Generate.hs | 31 ++++++++++++++++++------------- src/Settings/Builders/DeriveConstants.hs | 2 +- 3 files changed, 21 insertions(+), 16 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index b0dd474..5b51c1d 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -18,13 +18,13 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do let srcFile = dropBuild . dropExtension $ out - orderOnly $ generatedDependencies stage + orderOnly $ generatedDependencies stage pkg need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - orderOnly $ generatedDependencies stage + orderOnly $ generatedDependencies stage pkg need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 140c978..13d5806 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -33,21 +33,20 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -derivedConstantsDependencies :: [FilePath] -derivedConstantsDependencies = (derivedConstantsPath -/-) <$> [] - -- [ "DerivedConstants.h" - -- , "GHCConstantsHaskellType.hs" - -- , "GHCConstantsHaskellWrappers.hs" - -- , "GHCConstantsHaskellExports.hs" ] - libffiDependencies :: [FilePath] libffiDependencies = (targetPath Stage1 rts -/-) <$> [ "build/ffi.h" , "build/ffitarget.h" ] defaultDependencies :: [FilePath] -defaultDependencies = - includesDependencies ++ derivedConstantsDependencies ++ libffiDependencies +defaultDependencies = includesDependencies ++ libffiDependencies + +derivedConstantsDependencies :: [FilePath] +derivedConstantsDependencies = (derivedConstantsPath -/-) <$> + [ "DerivedConstants.h" + , "GHCConstantsHaskellType.hs" + , "GHCConstantsHaskellWrappers.hs" + , "GHCConstantsHaskellExports.hs" ] compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = @@ -69,12 +68,18 @@ compilerDependencies stage = , "primop-vector-tys-exports.hs-incl" , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] + ++ + if stage == Stage0 + then defaultDependencies ++ derivedConstantsDependencies + else [] + -- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? --- TODO: improve -generatedDependencies :: Stage -> [FilePath] -generatedDependencies stage - | stage == Stage1 = defaultDependencies ++ compilerDependencies stage +generatedDependencies :: Stage -> Package -> [FilePath] +generatedDependencies stage pkg + | pkg == compiler = compilerDependencies stage + | stage == Stage0 = defaultDependencies + | stage == Stage1 = derivedConstantsDependencies | otherwise = [] -- The following generators and corresponding source extensions are supported: diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 65c6c53..6f4828a 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -33,7 +33,7 @@ deriveConstantsBuilderArgs = builder DeriveConstants ? do includeCcArgs :: Args includeCcArgs = do - confCcArgs <- lift . settingList $ ConfCcArgs Stage1 + confCcArgs <- getSettingList $ ConfCcArgs Stage1 mconcat [ cArgs , cWarnings From git at git.haskell.org Fri Oct 27 00:23:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Eliminate some uses of fromJust (8657341) Message-ID: <20171027002357.827103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8657341ded43e9671c48929627814e1e64b22ead/ghc >--------------------------------------------------------------- commit 8657341ded43e9671c48929627814e1e64b22ead Author: Ben Gamari Date: Sat Oct 8 15:10:33 2016 -0400 Eliminate some uses of fromJust >--------------------------------------------------------------- 8657341ded43e9671c48929627814e1e64b22ead src/Builder.hs | 7 +++++-- src/Rules.hs | 8 +++++++- 2 files changed, 12 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 55d561e..6f892f2 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -98,11 +98,14 @@ isOptional = \case Objdump -> True _ -> False --- TODO: Get rid of fromJust. -- | Determine the location of a 'Builder'. builderPath :: Builder -> Action FilePath builderPath builder = case builderProvenance builder of - Just context -> return . fromJust $ programPath context + Just context + | Just path <- programPath context -> return path + | otherwise -> + error $ "Cannot determine builderPath for " ++ show builder + ++ " in context " ++ show context Nothing -> case builder of Alex -> fromKey "alex" Ar -> fromKey "ar" diff --git a/src/Rules.hs b/src/Rules.hs index f69cc95..e62ecc7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -49,7 +49,13 @@ topLevelTargets = do docs <- interpretInContext context $ buildHaddock flavour need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else do -- otherwise build a program - need [ fromJust $ programPath context ] -- TODO: drop fromJust + need [ getProgramPath context ] + where + getProgramPath context = + case programPath context of + Nothing -> error $ "topLevelTargets: Can't determine program path for context " + ++ show context + Just path -> path packageRules :: Rules () packageRules = do From git at git.haskell.org Fri Oct 27 00:13:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (82a7fa5) Message-ID: <20171027001326.C7FFF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82a7fa5557590ec395af8cd506d50cb6d4c5805b/ghc >--------------------------------------------------------------- commit 82a7fa5557590ec395af8cd506d50cb6d4c5805b Author: Andrey Mokhov Date: Fri Jan 22 11:39:44 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- 82a7fa5557590ec395af8cd506d50cb6d4c5805b README.md | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index e51e1e0..1f96505 100644 --- a/README.md +++ b/README.md @@ -30,7 +30,7 @@ packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickChe cd ghc git clone git://github.com/snowleopard/shaking-up-ghc shake-build ``` -* Start your first build: +* Start your first build (you might want to enable parallelism with `-j`): ```bash shake-build/build.sh --configure @@ -44,7 +44,8 @@ If you are interested in building in a Cabal sandbox, have a look at `shake-buil Using the build system ---------------------- Once your first build is successful, simply run `shake-build/build.sh` or `shake-build/build.bat` -to rebuild (you no longer need to use the `--configure` flag). Use `-j` flag to enable parallelism. +to rebuild (you no longer need to use the `--configure` flag). Most build artefacts are placed +into `.build` and `inplace` directories. ### Command line flags From git at git.haskell.org Fri Oct 27 00:13:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export Expression from Predicates (12dc4c5) Message-ID: <20171027001354.726BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12dc4c5b7faaf774031fef8539947459cd9b20a5/ghc >--------------------------------------------------------------- commit 12dc4c5b7faaf774031fef8539947459cd9b20a5 Author: Andrey Mokhov Date: Mon May 16 01:47:31 2016 +0100 Re-export Expression from Predicates >--------------------------------------------------------------- 12dc4c5b7faaf774031fef8539947459cd9b20a5 src/Expression.hs | 1 + src/Predicates.hs | 1 + src/Settings/Builders/Alex.hs | 1 - src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Cc.hs | 1 - src/Settings/Builders/Configure.hs | 1 - src/Settings/Builders/DeriveConstants.hs | 1 - src/Settings/Builders/GenApply.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 1 - src/Settings/Builders/Ghc.hs | 3 --- src/Settings/Builders/GhcCabal.hs | 1 - src/Settings/Builders/GhcPkg.hs | 1 - src/Settings/Builders/Haddock.hs | 3 +-- src/Settings/Builders/Happy.hs | 1 - src/Settings/Builders/HsCpp.hs | 1 - src/Settings/Builders/Hsc2Hs.hs | 4 ---- src/Settings/Builders/Ld.hs | 3 +-- src/Settings/Builders/Make.hs | 1 - src/Settings/Builders/Tar.hs | 1 - src/Settings/Default.hs | 3 +-- src/Settings/Flavours/Quick.hs | 1 - src/Settings/Packages.hs | 1 - src/Settings/Packages/Base.hs | 1 - src/Settings/Packages/Compiler.hs | 1 - src/Settings/Packages/Directory.hs | 1 - src/Settings/Packages/Ghc.hs | 1 - src/Settings/Packages/GhcCabal.hs | 1 - src/Settings/Packages/GhcPrim.hs | 1 - src/Settings/Packages/Haddock.hs | 1 - src/Settings/Packages/Hp2ps.hs | 1 - src/Settings/Packages/IntegerGmp.hs | 1 - src/Settings/Packages/IservBin.hs | 1 - src/Settings/Packages/Rts.hs | 1 - src/Settings/Packages/RunGhc.hs | 1 - src/Settings/Packages/Touchy.hs | 1 - src/Settings/Packages/Unlit.hs | 1 - src/Settings/User.hs | 1 - src/Settings/Ways.hs | 1 - 38 files changed, 6 insertions(+), 44 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 12dc4c5b7faaf774031fef8539947459cd9b20a5 From git at git.haskell.org Fri Oct 27 00:13:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (30a3d91) Message-ID: <20171027001354.83A8E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30a3d9199fe606b08b26b387bc9b8b932dc2098d/ghc >--------------------------------------------------------------- commit 30a3d9199fe606b08b26b387bc9b8b932dc2098d Merge: a8ea524 497f750 Author: Andrey Mokhov Date: Fri Jan 22 13:08:56 2016 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 30a3d9199fe606b08b26b387bc9b8b932dc2098d README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 00:13:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, make naming consistent: setPkgType -> setType. (f5d4e7b) Message-ID: <20171027001355.2A8723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5d4e7b91aff5a8a0c1e8368173d6c999a01d4b4/ghc >--------------------------------------------------------------- commit f5d4e7b91aff5a8a0c1e8368173d6c999a01d4b4 Author: Andrey Mokhov Date: Sun Dec 20 21:19:02 2015 +0000 Clean up, make naming consistent: setPkgType -> setType. >--------------------------------------------------------------- f5d4e7b91aff5a8a0c1e8368173d6c999a01d4b4 src/Base.hs | 6 ++---- src/GHC.hs | 4 ++-- src/Package.hs | 6 +++--- src/Rules/Program.hs | 4 ---- 4 files changed, 7 insertions(+), 13 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fb3b5e1..009e197 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -20,15 +20,13 @@ module Base ( shakeFilesPath, configPath, bootPackageConstraints, packageDependencies, -- * Output - putColoured, putOracle, putBuild, putSuccess, putError, - renderBox, + putColoured, putOracle, putBuild, putSuccess, putError, renderBox, module System.Console.ANSI, -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, removeFileIfExists, - replaceEq, replaceSeparators, decodeModule, - unifyPath, (-/-), chunksOfSize, + replaceEq, replaceSeparators, decodeModule, unifyPath, (-/-), chunksOfSize, ) where import Control.Applicative diff --git a/src/GHC.hs b/src/GHC.hs index 29db671..923fdf1 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -51,7 +51,7 @@ dllSplit = utility "dll-split" filepath = library "filepath" genapply = utility "genapply" genprimopcode = utility "genprimopcode" -ghc = topLevel "ghc-bin" `setPath` "ghc" `setPkgType` Program +ghc = topLevel "ghc-bin" `setPath` "ghc" `setType` Program ghcBoot = library "ghc-boot" ghcCabal = utility "ghc-cabal" ghci = library "ghci" @@ -68,7 +68,7 @@ hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" integerGmp = library "integer-gmp" integerSimple = library "integer-simple" -iservBin = topLevel "iserv-bin" `setPath` "iserv" `setPkgType` Program +iservBin = topLevel "iserv-bin" `setPath` "iserv" `setType` Program mkUserGuidePart = utility "mkUserGuidePart" parallel = library "parallel" pretty = library "pretty" diff --git a/src/Package.hs b/src/Package.hs index 6273a62..574f01a 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -5,7 +5,7 @@ module Package ( pkgCabalFile, matchPackageNames, -- * Helpers for constructing 'Package's - setPath, topLevel, library, utility, setPkgType + setPath, topLevel, library, utility, setType ) where import Base @@ -45,8 +45,8 @@ utility name = Package name ("utils" -/- name) Program setPath :: Package -> FilePath -> Package setPath pkg path = pkg { pkgPath = path } -setPkgType :: Package -> PackageType -> Package -setPkgType pkg ty = pkg { pkgType = ty } +setType :: Package -> PackageType -> Package +setType pkg ty = pkg { pkgType = ty } instance Show Package where show = pkgName diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 2ff5ef0..9ca36d6 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -17,10 +17,6 @@ buildProgram _ target @ (PartialTarget stage pkg) = do buildPath = path -/- "build" program = programPath stage pkg - -- return $ [ ghciLib | needGhciLib == "YES" && stage == Stage1 ] - -- ++ [ haddock | needHaddock && stage == Stage1 ] - -- ++ libs - (\f -> program == Just f) ?> \bin -> do cSrcs <- cSources target -- TODO: remove code duplication (Library.hs) hSrcs <- hSources target From git at git.haskell.org Fri Oct 27 00:13:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove Shake database on clean. (0bde9c1) Message-ID: <20171027001359.26B053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0bde9c13cd854c1297296a77be53ec7940045f71/ghc >--------------------------------------------------------------- commit 0bde9c13cd854c1297296a77be53ec7940045f71 Author: Andrey Mokhov Date: Fri Jan 22 14:38:21 2016 +0000 Remove Shake database on clean. See #131. [skip ci] >--------------------------------------------------------------- 0bde9c13cd854c1297296a77be53ec7940045f71 src/Rules/Clean.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 2b4094a..eb7f8de 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -27,4 +27,6 @@ cleanRules = do forM_ [Stage0 ..] $ \stage -> do let dir = pkgPath pkg -/- targetDirectory stage pkg removeDirectoryIfExists dir + putBuild $ "| Remove the Shake database " ++ shakeFilesPath ++ "..." + removeFilesAfter shakeFilesPath ["//*"] putSuccess $ "| Done. " From git at git.haskell.org Fri Oct 27 00:13:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename module Predicates to Predicate (03f89a6) Message-ID: <20171027001359.555AD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7/ghc >--------------------------------------------------------------- commit 03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7 Author: Andrey Mokhov Date: Mon May 16 01:51:17 2016 +0100 Rename module Predicates to Predicate >--------------------------------------------------------------- 03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7 hadrian.cabal | 2 +- src/{Predicates.hs => Predicate.hs} | 2 +- src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Cc.hs | 2 +- src/Settings/Builders/Configure.hs | 2 +- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/GenApply.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 2 +- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Builders/Happy.hs | 2 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Builders/Ld.hs | 2 +- src/Settings/Builders/Make.hs | 2 +- src/Settings/Builders/Tar.hs | 2 +- src/Settings/Default.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Directory.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/GhcPrim.hs | 2 +- src/Settings/Packages/Haddock.hs | 2 +- src/Settings/Packages/Hp2ps.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/IservBin.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/Packages/Touchy.hs | 2 +- src/Settings/Packages/Unlit.hs | 2 +- src/Settings/User.hs | 2 +- src/Settings/Ways.hs | 2 +- 38 files changed, 38 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 03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7 From git at git.haskell.org Fri Oct 27 00:13:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:13:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build program executables directly in inplace/bin. (663ad01) Message-ID: <20171027001359.A19083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/663ad019699389006a2c99e9f17c92bd53ea4e22/ghc >--------------------------------------------------------------- commit 663ad019699389006a2c99e9f17c92bd53ea4e22 Author: Andrey Mokhov Date: Mon Dec 21 02:56:49 2015 +0000 Build program executables directly in inplace/bin. >--------------------------------------------------------------- 663ad019699389006a2c99e9f17c92bd53ea4e22 cfg/system.config.in | 20 ++++++++++---------- src/Base.hs | 7 ++++++- src/Builder.hs | 1 + src/GHC.hs | 30 ++++++++++++------------------ src/Rules.hs | 5 +++-- src/Settings/Builders/GhcCabal.hs | 3 ++- 6 files changed, 34 insertions(+), 32 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 9de3166..6c21f6e 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -5,29 +5,29 @@ #=================== system-ghc = @WithGhc@ -ghc-stage1 = @hardtop@/inplace/bin/ghc-stage1 -ghc-stage2 = @hardtop@/inplace/bin/ghc-stage2 -ghc-stage3 = @hardtop@/inplace/bin/ghc-stage3 +ghc-stage1 = inplace/bin/ghc-stage1 +ghc-stage2 = inplace/bin/ghc-stage2 +ghc-stage3 = inplace/bin/ghc-stage3 system-gcc = @CC_STAGE0@ gcc = @WhatGccIsCalled@ system-ghc-pkg = @GhcPkgCmd@ -ghc-pkg = @hardtop@/inplace/bin/ghc-pkg +ghc-pkg = inplace/bin/ghc-pkg -ghc-cabal = @hardtop@/inplace/bin/ghc-cabal +ghc-cabal = inplace/bin/ghc-cabal -haddock = @hardtop@/inplace/bin/haddock +haddock = inplace/bin/haddock -hsc2hs = @hardtop@/inplace/bin/hsc2hs +hsc2hs = inplace/bin/hsc2hs -genprimopcode = @hardtop@/inplace/bin/genprimopcode +genprimopcode = inplace/bin/genprimopcode hs-cpp = @HaskellCPPCmd@ hs-cpp-args = @HaskellCPPArgs@ -unlit = @hardtop@/inplace/lib/unlit -ghc-split = @hardtop@/inplace/lib/ghc-split +unlit = inplace/lib/unlit +ghc-split = inplace/lib/ghc-split ld = @LdCmd@ ar = @ArCmd@ diff --git a/src/Base.hs b/src/Base.hs index 009e197..834f589 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -17,7 +17,8 @@ module Base ( module Development.Shake.Util, -- * Paths - shakeFilesPath, configPath, bootPackageConstraints, packageDependencies, + shakeFilesPath, configPath, programInplacePath, + bootPackageConstraints, packageDependencies, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, @@ -56,6 +57,10 @@ shakeFilesPath = shakePath -/- ".db" configPath :: FilePath configPath = shakePath -/- "cfg" +-- TODO: shall we read this from system.config instead? +programInplacePath :: FilePath +programInplacePath = "inplace/bin" + bootPackageConstraints :: FilePath bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" diff --git a/src/Builder.hs b/src/Builder.hs index f15054d..4d41d0a 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -66,6 +66,7 @@ builderKey builder = case builder of Ld -> "ld" Unlit -> "unlit" +-- TODO: Paths to some builders should be determined using defaultProgramPath builderPath :: Builder -> Action FilePath builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ diff --git a/src/GHC.hs b/src/GHC.hs index 923fdf1..f47242a 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -105,25 +105,19 @@ defaultTargetDirectory stage pkg | stage == Stage0 = "dist-boot" | otherwise = "dist-install" +-- TODO: simplify +-- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg - | pkg == compareSizes = program $ pkgName pkg - | pkg == deriveConstants = program $ pkgName pkg - | pkg == dllSplit = program $ pkgName pkg - | pkg == genapply = program $ pkgName pkg - | pkg == genprimopcode = program $ pkgName pkg - | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1) - | pkg == ghcCabal = program $ pkgName pkg - | pkg == ghcPkg = program $ pkgName pkg - | pkg == ghcPwd = program $ pkgName pkg - | pkg == ghcTags = program $ pkgName pkg - | pkg == haddock = program $ pkgName pkg - | pkg == hsc2hs = program $ pkgName pkg - | pkg == hp2ps = program $ pkgName pkg - | pkg == hpcBin = program $ pkgName pkg - | pkg == mkUserGuidePart = program $ pkgName pkg - | pkg == runghc = program $ pkgName pkg - | otherwise = Nothing + | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) + | pkg == haddock = case stage of + Stage2 -> Just . inplaceProgram $ pkgName pkg + _ -> Nothing + | isProgram pkg = case stage of + Stage0 -> Just . inplaceProgram $ pkgName pkg + _ -> Just . installProgram $ pkgName pkg + | otherwise = Nothing where - program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg + inplaceProgram name = programInplacePath -/- name <.> exe + installProgram name = pkgPath pkg -/- defaultTargetDirectory stage pkg -/- "build/tmp" -/- name <.> exe diff --git a/src/Rules.hs b/src/Rules.hs index 55ff066..7d88de8 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,7 +5,8 @@ import Rules.Package import Rules.Resources import Settings --- generateTargets needs top-level build targets +-- TODO: not all program targets should be needed explicitly +-- | generateTargets needs top-level build targets generateTargets :: Rules () generateTargets = action $ do targets <- fmap concat . forM [Stage0 ..] $ \stage -> do @@ -17,7 +18,7 @@ generateTargets = action $ do return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] return $ libTargets ++ programTargets - need $ reverse targets + need targets -- TODO: use stage 2 compiler for building stage 2 packages (instead of stage 1) packageRules :: Rules () diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 151cd5f..66f9239 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -184,9 +184,10 @@ withBuilderKey b = case b of -- Expression 'with Gcc' appends "--with-gcc=/path/to/gcc" and needs Gcc. with :: Builder -> Args with b = specified b ? do + top <- getSetting GhcSourcePath path <- getBuilderPath b lift $ needBuilder laxDependencies b - append [withBuilderKey b ++ path] + append [withBuilderKey b ++ top -/- path] withStaged :: (Stage -> Builder) -> Args withStaged sb = (with . sb) =<< getStage From git at git.haskell.org Fri Oct 27 00:14:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bootstrap ghc-cabal. (c98eebc) Message-ID: <20171027001404.B70F23A5EC@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c98eebc43418a33618df317cd92472ac801618b2/ghc >--------------------------------------------------------------- commit c98eebc43418a33618df317cd92472ac801618b2 Author: Andrey Mokhov Date: Mon Dec 21 03:00:14 2015 +0000 Bootstrap ghc-cabal. >--------------------------------------------------------------- c98eebc43418a33618df317cd92472ac801618b2 src/Base.hs | 1 - src/Rules/Data.hs | 93 ++++++++++++++++++++++++-------------------- src/Rules/Program.hs | 22 ++++++----- src/Rules/Resources.hs | 4 +- src/Settings/Builders/Ghc.hs | 51 ++++++++++-------------- 5 files changed, 85 insertions(+), 86 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c98eebc43418a33618df317cd92472ac801618b2 From git at git.haskell.org Fri Oct 27 00:14:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build.stack.sh (93605e1) Message-ID: <20171027001404.B6B9D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/93605e1d7e6644f011c7202f2a3431e927f0d87f/ghc >--------------------------------------------------------------- commit 93605e1d7e6644f011c7202f2a3431e927f0d87f Author: Joe Hillenbrand Date: Fri Jan 22 15:41:24 2016 -0800 Add build.stack.sh >--------------------------------------------------------------- 93605e1d7e6644f011c7202f2a3431e927f0d87f .gitignore | 1 + build.cabal.sh => build.stack.sh | 13 +++---------- stack.yaml | 35 +++++++++++++++++++++++++++++++++++ 3 files changed, 39 insertions(+), 10 deletions(-) diff --git a/.gitignore b/.gitignore index 39cd693..6cc5501 100644 --- a/.gitignore +++ b/.gitignore @@ -4,3 +4,4 @@ cfg/system.config cabal.sandbox.config dist/ .cabal-sandbox/ +.stack-work/ diff --git a/build.cabal.sh b/build.stack.sh similarity index 77% copy from build.cabal.sh copy to build.stack.sh index 8add516..1cc968b 100755 --- a/build.cabal.sh +++ b/build.stack.sh @@ -31,16 +31,9 @@ function rl { absoltueRoot="$(dirname "$(rl "$0")")" cd "$absoltueRoot" -# Initialize sandbox if necessary -if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then - cabal sandbox init - cabal install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared -fi - -cabal run ghc-shake -- \ +stack build --no-library-profiling + +stack exec ghc-shake -- \ --lint \ --directory "$absoltueRoot/.." \ --colour \ diff --git a/stack.yaml b/stack.yaml new file mode 100644 index 0000000..2bc3b0e --- /dev/null +++ b/stack.yaml @@ -0,0 +1,35 @@ +# For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html + +# Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) +resolver: lts-4.2 + +# Local packages, usually specified by relative directory name +packages: +- '.' + +# Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) +extra-deps: [] + +# Override default flag values for local packages and extra-deps +flags: {} + +# Extra package databases containing global packages +extra-package-dbs: [] + +# Control whether we use the GHC we find on the path +# system-ghc: false + +# Require a specific version of stack, using version ranges +# require-stack-version: -any # Default +# require-stack-version: >= 1.0.0 + +# Override the architecture used by stack, especially useful on Windows +# arch: i386 +# arch: x86_64 + +# Extra directories used by stack for building +# extra-include-dirs: [/path/to/dir] +# extra-lib-dirs: [/path/to/dir] + +# Allow a newer minor version of GHC than the snapshot specifies +# compiler-check: newer-minor From git at git.haskell.org Fri Oct 27 00:14:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Check if the output supports colors (fixes #244) (0f7bc96) Message-ID: <20171027001404.E54673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0f7bc96a2c8940181818594ffc71bf928ab8aed2/ghc >--------------------------------------------------------------- commit 0f7bc96a2c8940181818594ffc71bf928ab8aed2 Author: Michal Terepeta Date: Sun May 15 17:31:30 2016 +0200 Check if the output supports colors (fixes #244) This avoids using colors when the output is, e.g., redirected to a file. This requried a change to avoid passing the `--colour` flag to shake (so that hadrian is in charge of colors). Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 0f7bc96a2c8940181818594ffc71bf928ab8aed2 build.cabal-new.sh | 1 - build.cabal.sh | 1 - build.sh | 1 - build.stack.sh | 1 - src/Base.hs | 12 ++++++++++-- 5 files changed, 10 insertions(+), 6 deletions(-) diff --git a/build.cabal-new.sh b/build.cabal-new.sh index bca8c7c..65e222a 100755 --- a/build.cabal-new.sh +++ b/build.cabal-new.sh @@ -55,5 +55,4 @@ popd "$root/.shake/build" \ --lint \ --directory "$root/.." \ - --colour \ "$@" diff --git a/build.cabal.sh b/build.cabal.sh index f2e320e..08ff972 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -43,5 +43,4 @@ fi cabal run hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ - --colour \ "$@" diff --git a/build.sh b/build.sh index fff8df4..24fdc2f 100755 --- a/build.sh +++ b/build.sh @@ -49,5 +49,4 @@ ghc \ "$root/hadrian" \ --lint \ --directory "$root/.." \ - --colour \ "$@" diff --git a/build.stack.sh b/build.stack.sh index b5607b1..23f4833 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -36,5 +36,4 @@ stack build --no-library-profiling stack exec hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ - --colour \ "$@" diff --git a/src/Base.hs b/src/Base.hs index bd80f47..488be04 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -38,6 +38,7 @@ import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI +import qualified System.Info as Info import System.IO -- TODO: reexport Stage, etc.? @@ -96,10 +97,17 @@ infixr 6 -/- -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do - liftIO $ setSGR [SetColor Foreground Vivid colour] + liftIO $ set [SetColor Foreground Vivid colour] putNormal msg - liftIO $ setSGR [] + liftIO $ set [] liftIO $ hFlush stdout + where + set a = do + supported <- hSupportsANSI stdout + when (win || supported) $ setSGR a + -- An ugly hack to always try to print colours when on mingw and cygwin. + -- See: https://github.com/snowleopard/hadrian/pull/253 + win = "mingw" `isPrefixOf` Info.os || "cygwin" `isPrefixOf` Info.os -- | Make oracle output more distinguishable putOracle :: String -> Action () From git at git.haskell.org Fri Oct 27 00:14:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix typos in build.*.sh (4aa3bb6) Message-ID: <20171027001408.610C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4aa3bb622b08d7f7b2fe0b45c32c4127f5ca972a/ghc >--------------------------------------------------------------- commit 4aa3bb622b08d7f7b2fe0b45c32c4127f5ca972a Author: Joe Hillenbrand Date: Fri Jan 22 16:24:41 2016 -0800 fix typos in build.*.sh >--------------------------------------------------------------- 4aa3bb622b08d7f7b2fe0b45c32c4127f5ca972a build.cabal.sh | 6 +++--- build.stack.sh | 6 +++--- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/build.cabal.sh b/build.cabal.sh index 8add516..5f20c1b 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -28,8 +28,8 @@ function rl { echo "$RESULT" } -absoltueRoot="$(dirname "$(rl "$0")")" -cd "$absoltueRoot" +absoluteRoot="$(dirname "$(rl "$0")")" +cd "$absoluteRoot" # Initialize sandbox if necessary if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then @@ -42,6 +42,6 @@ fi cabal run ghc-shake -- \ --lint \ - --directory "$absoltueRoot/.." \ + --directory "$absoluteRoot/.." \ --colour \ "$@" diff --git a/build.stack.sh b/build.stack.sh index 1cc968b..578e7eb 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -28,13 +28,13 @@ function rl { echo "$RESULT" } -absoltueRoot="$(dirname "$(rl "$0")")" -cd "$absoltueRoot" +absoluteRoot="$(dirname "$(rl "$0")")" +cd "$absoluteRoot" stack build --no-library-profiling stack exec ghc-shake -- \ --lint \ - --directory "$absoltueRoot/.." \ + --directory "$absoluteRoot/.." \ --colour \ "$@" From git at git.haskell.org Fri Oct 27 00:14:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move isLibrary to src/Package.hs, add isProgram. (5980218) Message-ID: <20171027001409.0D08E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/598021809c6822f8c30b13ad0f75719a465a1c27/ghc >--------------------------------------------------------------- commit 598021809c6822f8c30b13ad0f75719a465a1c27 Author: Andrey Mokhov Date: Mon Dec 21 03:00:38 2015 +0000 Move isLibrary to src/Package.hs, add isProgram. >--------------------------------------------------------------- 598021809c6822f8c30b13ad0f75719a465a1c27 src/Package.hs | 12 ++++++++++-- src/Settings.hs | 4 ---- 2 files changed, 10 insertions(+), 6 deletions(-) diff --git a/src/Package.hs b/src/Package.hs index 574f01a..5b04b6d 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -4,8 +4,8 @@ module Package ( -- * Queries pkgCabalFile, matchPackageNames, - -- * Helpers for constructing 'Package's - setPath, topLevel, library, utility, setType + -- * Helpers for constructing and using 'Package's + setPath, topLevel, library, utility, setType, isLibrary, isProgram ) where import Base @@ -48,6 +48,14 @@ setPath pkg path = pkg { pkgPath = path } setType :: Package -> PackageType -> Package setType pkg ty = pkg { pkgType = ty } +isLibrary :: Package -> Bool +isLibrary (Package {pkgType=Library}) = True +isLibrary _ = False + +isProgram :: Package -> Bool +isProgram (Package {pkgType=Program}) = True +isProgram _ = False + instance Show Package where show = pkgName diff --git a/src/Settings.hs b/src/Settings.hs index 7a1ab72..fd7c14c 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -32,10 +32,6 @@ getPkgDataList key = lift . pkgDataList . key =<< getTargetPath programPath :: Stage -> Package -> Maybe FilePath programPath = userProgramPath -isLibrary :: Package -> Bool -isLibrary (Package {pkgType=Library}) = True -isLibrary _ = False - -- Find all Haskell source files for the current target. TODO: simplify. getPackageSources :: Expr [FilePath] getPackageSources = do From git at git.haskell.org Fri Oct 27 00:14:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #253 from michalt/colors/1 (a9f43e5) Message-ID: <20171027001409.236E43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9f43e59a1f84108a779b1ce835b5357f47b8e0f/ghc >--------------------------------------------------------------- commit a9f43e59a1f84108a779b1ce835b5357f47b8e0f Merge: 03f89a6 0f7bc96 Author: Andrey Mokhov Date: Mon May 16 13:46:36 2016 +0100 Merge pull request #253 from michalt/colors/1 Check if the output supports colors, see #244 >--------------------------------------------------------------- a9f43e59a1f84108a779b1ce835b5357f47b8e0f build.cabal-new.sh | 1 - build.cabal.sh | 1 - build.sh | 1 - build.stack.sh | 1 - src/Base.hs | 12 ++++++++++-- 5 files changed, 10 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 00:14:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #190 from joehillen/stack (ce71b6d) Message-ID: <20171027001412.55C7B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ce71b6dde7bf070e847b9d04673508b4d42066df/ghc >--------------------------------------------------------------- commit ce71b6dde7bf070e847b9d04673508b4d42066df Merge: 0bde9c1 4aa3bb6 Author: Andrey Mokhov Date: Sat Jan 23 00:36:13 2016 +0000 Merge pull request #190 from joehillen/stack Allow building ghc-shake with stack >--------------------------------------------------------------- ce71b6dde7bf070e847b9d04673508b4d42066df .gitignore | 1 + build.cabal.sh | 6 +++--- build.cabal.sh => build.stack.sh | 21 +++++++-------------- stack.yaml | 35 +++++++++++++++++++++++++++++++++++ 4 files changed, 46 insertions(+), 17 deletions(-) From git at git.haskell.org Fri Oct 27 00:14:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track only files of known extensions when looking for module files (f910a1c) Message-ID: <20171027001412.DA2BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f910a1c96f8e34171e0190931f907becfa40e2e9/ghc >--------------------------------------------------------------- commit f910a1c96f8e34171e0190931f907becfa40e2e9 Author: Andrey Mokhov Date: Mon May 16 21:46:41 2016 +0100 Track only files of known extensions when looking for module files Fix #254 >--------------------------------------------------------------- f910a1c96f8e34171e0190931f907becfa40e2e9 src/Oracles/ModuleFiles.hs | 47 +++++++++++++++++++++++++++++----------------- 1 file changed, 30 insertions(+), 17 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index f2b03f3..43a5f00 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -12,19 +12,31 @@ import Oracles.PackageData import Settings.Paths newtype ModuleFilesKey = ModuleFilesKey (Stage, Package) - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) newtype Generator = Generator (Stage, Package, FilePath) - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- The following generators and corresponding source extensions are supported: +-- | We scan for the following Haskell source extensions when looking for module +-- files. Note, we do not list "*.(l)hs-boot" files here, as they can never +-- appear by themselves and always have accompanying "*.(l)hs" master files. +haskellExtensions :: [String] +haskellExtensions = [".hs", ".lhs"] + +-- | Non-Haskell source extensions and corresponding builders. +otherExtensions :: [(String, Builder)] +otherExtensions = [ (".x" , Alex ) + , (".y" , Happy ) + , (".ly" , Happy ) + , (".hsc", Hsc2Hs) ] + +-- | We match the following file patterns when looking for module files. +moduleFilePatterns :: [FilePattern] +moduleFilePatterns = map ("*" ++) $ haskellExtensions ++ map fst otherExtensions + +-- | Given a FilePath determine the corresponding builder. determineBuilder :: FilePath -> Maybe Builder -determineBuilder file = case takeExtension file of - ".x" -> Just Alex - ".y" -> Just Happy - ".ly" -> Just Happy - ".hsc" -> Just Hsc2Hs - _ -> Nothing +determineBuilder file = lookup (takeExtension file) otherExtensions -- | Given a module name extract the directory and file name, e.g.: -- @@ -69,14 +81,16 @@ haskellSources context = do let modFile ("GHC.Prim", _) = autogen -/- "GHC/Prim.hs" modFile (m, Nothing ) = generatedFile context m modFile (m, Just file ) - | takeExtension file `elem` [".hs", ".lhs"] = file + | takeExtension file `elem` haskellExtensions = file | otherwise = generatedFile context m map modFile <$> contextFiles context +-- | Generated module files live in the 'Context' specific build directory. generatedFile :: Context -> String -> FilePath generatedFile context moduleName = buildPath context -/- replaceEq '.' '/' moduleName <.> "hs" +-- | Module files for a given 'Context'. contextFiles :: Context -> Action [(String, Maybe FilePath)] contextFiles context at Context {..} = do modules <- fmap sort . pkgDataList . Modules $ buildPath context @@ -95,7 +109,7 @@ contextFiles context at Context {..} = do -- Just "compiler/parser/Lexer.x"]. The oracle ignores @.(l)hs-boot@ files. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do - void $ addOracle $ \(ModuleFilesKey (stage, package)) -> do + void . addOracle $ \(ModuleFilesKey (stage, package)) -> do let path = buildPath $ vanillaContext stage package srcDirs <- pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path @@ -105,10 +119,9 @@ moduleFilesOracle = void $ do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do let fullDir = unifyPath $ dir -/- mDir - files <- getDirectoryFiles fullDir ["*"] - let noBoot = filter (not . (isSuffixOf "-boot")) files - cmp fe f = compare (dropExtension fe) f - found = intersectOrd cmp noBoot mFiles + files <- getDirectoryFiles fullDir moduleFilePatterns + let cmp fe f = compare (dropExtension fe) f + found = intersectOrd cmp files mFiles return (map (fullDir -/-) found, mDir) let pairs = sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ] @@ -118,14 +131,14 @@ moduleFilesOracle = void $ do ++ f1 ++ " and " ++ f2 ++ "." return $ lookupAll modules pairs - -- Optimisation: we discard .(l)hs files here, because they are never used + -- Optimisation: we discard Haskell files here, because they are never used -- as generators, and hence would be discarded in 'findGenerator' anyway. generators <- newCache $ \(stage, package) -> do let context = vanillaContext stage package files <- contextFiles context return $ Map.fromList [ (generatedFile context modName, src) | (modName, Just src) <- files - , takeExtension src `notElem` [".hs", ".lhs"] ] + , takeExtension src `notElem` haskellExtensions ] addOracle $ \(Generator (stage, package, file)) -> Map.lookup file <$> generators (stage, package) From git at git.haskell.org Fri Oct 27 00:14:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:14:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix parallel build, clean up code. (6b358c3) Message-ID: <20171027001413.0CEE93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b358c3d68e5643d684e9a645160cb829948de47/ghc >--------------------------------------------------------------- commit 6b358c3d68e5643d684e9a645160cb829948de47 Author: Andrey Mokhov Date: Mon Dec 21 03:57:02 2015 +0000 Fix parallel build, clean up code. >--------------------------------------------------------------- 6b358c3d68e5643d684e9a645160cb829948de47 src/Oracles/PackageData.hs | 70 ++++++++++++++++++++++++---------------------- src/Rules/Data.hs | 3 +- src/Rules/Program.hs | 6 ++-- src/Settings/Packages.hs | 7 ++--- 4 files changed, 43 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 6b358c3d68e5643d684e9a645160cb829948de47 From git at git.haskell.org Fri Oct 27 00:22:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to prerequisites (633fad1) Message-ID: <20171027002222.4949A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/633fad17054268f6c02e360bed5ab4df5e2559ba/ghc >--------------------------------------------------------------- commit 633fad17054268f6c02e360bed5ab4df5e2559ba Author: Andrey Mokhov Date: Thu Sep 1 23:24:34 2016 +0100 Link to prerequisites [skip ci] >--------------------------------------------------------------- 633fad17054268f6c02e360bed5ab4df5e2559ba doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index efbaeb2..1296b76 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -2,8 +2,8 @@ [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) -Here is how you can build GHC, from source, on Windows. We assume that you -already have `git` and `stack` installed. +Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are +installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). ```sh # Get GHC and Hadrian sources From git at git.haskell.org Fri Oct 27 00:22:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split libgmp.a (d3d5b11) Message-ID: <20171027002224.ACEA13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3d5b11ab21eaee5e7dcdca007acc05131d512be/ghc >--------------------------------------------------------------- commit d3d5b11ab21eaee5e7dcdca007acc05131d512be Author: Moritz Angermann Date: Sun Jan 3 23:01:17 2016 +0800 Split libgmp.a Fixes the issue mentioned in #83 ``` * utils/hpc/stage1/build/tmp/hpc-bin * libraries/integer-gmp/stage1/build/libHSinteger-gmp-1.0.0.0.a * getDirectoryFiles [libraries/integer-gmp/gmp/objs/*.o] libraries/integer-gmp/gmp/objs: getDirectoryContents: does not exist (No such file or directory) ``` >--------------------------------------------------------------- d3d5b11ab21eaee5e7dcdca007acc05131d512be src/Rules/IntegerGmp.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 443b912..1f50dc0 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -53,6 +53,7 @@ integerGmpRules = do -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] + liftIO $ removeFiles (integerGmpBase -/- "objs") ["//*"] -- unpack the gmp tarball. -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is @@ -102,10 +103,13 @@ integerGmpRules = do copyFileChanged (integerGmpBuild -/- file) file' putBuild $ "| Copy " ++ file ++ " -> " ++ file' - -- TODO: do we need these as well? - -- mkdir integerGmpBase -/- objs - -- unit $ cmd Shell [Cwd integerGmpBase -/- "objs"] "$AR_STAGE1 x ../libgmp.a" - -- $RANLIB_CMD integerGmpBase -/- "libgmp.a" + ar <- builderPath Ar + ran <- builderPath Ranlib + -- unpack libgmp.a + putBuild "| Unpacking libgmp.a..." + unit $ cmd Shell [Cwd integerGmpBase] "mkdir -p objs" + unit $ cmd Shell [Cwd (integerGmpBase -/- "objs")] [ar] " x ../libgmp.a" + unit $ cmd Shell [Cwd integerGmpBase] [ran] " libgmp.a" putSuccess "| Successfully build custom library 'integer-gmp'" From git at git.haskell.org Fri Oct 27 00:22:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Document and test encode/decodeModule. (5e32c91) Message-ID: <20171027002225.C8BEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e32c9147ba23b886ae6154200fc7961481f4bd9/ghc >--------------------------------------------------------------- commit 5e32c9147ba23b886ae6154200fc7961481f4bd9 Author: Andrey Mokhov Date: Sat Feb 20 22:40:41 2016 +0000 Document and test encode/decodeModule. See #197, #210. >--------------------------------------------------------------- 5e32c9147ba23b886ae6154200fc7961481f4bd9 src/Base.hs | 7 +++++-- src/Rules/Selftest.hs | 14 ++++++++++++++ 2 files changed, 19 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7d63fa0..7217834 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -98,13 +98,16 @@ versionToInt s = major * 1000 + minor * 10 + patch -- | Given a module name extract the directory and file name, e.g.: -- --- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +-- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") +-- > decodeModule "Prelude" == ("./", "Prelude") decodeModule :: String -> (FilePath, String) decodeModule = splitFileName . replaceEq '.' '/' -- | Given the directory and file name find the corresponding module name, e.g.: -- --- > encodeModule "Data/Functor/" "Identity.hs" = "Data.Functor.Identity" +-- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" +-- > encodeModule "./" "Prelude" == "Prelude" +-- > uncurry encodeModule (decodeModule name) == name encodeModule :: FilePath -> String -> String encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 70a4023..c156b44 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -24,6 +24,7 @@ selftestRules = testWays testChunksOfSize testMatchVersionedFilePath + testModuleNames testWays :: Action () testWays = do @@ -54,3 +55,16 @@ testMatchVersionedFilePath = do matchVersionedFilePath prefix suffix (prefix ++ version ++ suffix) where versions = listOf . elements $ '-' : '.' : ['0'..'9'] + +testModuleNames :: Action () +testModuleNames = do + putBuild $ "==== Encode/decode module name" + test $ encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" + test $ encodeModule "./" "Prelude" == "Prelude" + + test $ decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") + test $ decodeModule "Prelude" == ("./", "Prelude") + + test $ forAll names $ \n -> uncurry encodeModule (decodeModule n) == n + where + names = intercalate "." <$> listOf1 (listOf1 $ elements "abcABC123_'") From git at git.haskell.org Fri Oct 27 00:22:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Tweak instructions (fd7dd6f) Message-ID: <20171027002226.436423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd7dd6f7f32eebb7ff1a00ee2b36a0a75fb51e14/ghc >--------------------------------------------------------------- commit fd7dd6f7f32eebb7ff1a00ee2b36a0a75fb51e14 Author: Andrey Mokhov Date: Thu Sep 1 23:27:33 2016 +0100 Tweak instructions [skip ci] >--------------------------------------------------------------- fd7dd6f7f32eebb7ff1a00ee2b36a0a75fb51e14 doc/windows.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/windows.md b/doc/windows.md index 1296b76..73804df 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -10,9 +10,9 @@ installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/maste git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/hadrian -cd hadrian # Download and install the bootstrapping GHC and MSYS2 +cd hadrian stack setup # Install utilities required during the GHC build process From git at git.haskell.org Fri Oct 27 00:22:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #85 from angerman/feature/fix-integer-gmp (d271649) Message-ID: <20171027002228.210143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d27164938eff42d2622d416d5f81d7dd0833a32f/ghc >--------------------------------------------------------------- commit d27164938eff42d2622d416d5f81d7dd0833a32f Merge: 80d3477 d3d5b11 Author: Andrey Mokhov Date: Sun Jan 3 15:09:45 2016 +0000 Merge pull request #85 from angerman/feature/fix-integer-gmp Split libgmp.a >--------------------------------------------------------------- d27164938eff42d2622d416d5f81d7dd0833a32f src/Rules/IntegerGmp.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) From git at git.haskell.org Fri Oct 27 00:22:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add lookupAll and test it. (e054479) Message-ID: <20171027002229.8AE9B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e0544796443fa3f220ac77f68891b6c4fc0f09bb/ghc >--------------------------------------------------------------- commit e0544796443fa3f220ac77f68891b6c4fc0f09bb Author: Andrey Mokhov Date: Sun Feb 21 00:01:08 2016 +0000 Add lookupAll and test it. See #210. >--------------------------------------------------------------- e0544796443fa3f220ac77f68891b6c4fc0f09bb src/Base.hs | 22 ++++++++++++++++++---- src/Rules/Selftest.hs | 15 +++++++++++++++ 2 files changed, 33 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7217834..324feb8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,7 +23,7 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, -- * Miscellaneous utilities - minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, + minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath ) where @@ -165,9 +165,23 @@ intersectOrd cmp = loop loop [] _ = [] loop _ [] = [] loop (x:xs) (y:ys) = case cmp x y of - LT -> loop xs (y:ys) - EQ -> x : loop xs ys - GT -> loop (x:xs) ys + LT -> loop xs (y:ys) + EQ -> x : loop xs ys + GT -> loop (x:xs) ys + +-- | Lookup all elements of a given sorted list in a given sorted dictionary. +-- @lookupAll list dict@ is equivalent to @map (flip lookup dict) list@ but has +-- linear complexity O(|list| + |dist|) instead of quadratic O(|list| * |dict|). +-- +-- > lookupAll ["b", "c"] [("a", 1), ("c", 3), ("d", 4)] == [Nothing, Just 3] +-- > list & dict are sorted: lookupAll list dict == map (flip lookup dict) list +lookupAll :: Ord a => [a] -> [(a, b)] -> [Maybe b] +lookupAll [] _ = [] +lookupAll (_:xs) [] = Nothing : lookupAll xs [] +lookupAll (x:xs) (y:ys) = case compare x (fst y) of + LT -> Nothing : lookupAll xs (y:ys) + EQ -> Just (snd y) : lookupAll xs (y:ys) + GT -> lookupAll (x:xs) ys -- | Remove a file that doesn't necessarily exist removeFileIfExists :: FilePath -> Action () diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index c156b44..f549b0f 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -25,6 +25,7 @@ selftestRules = testChunksOfSize testMatchVersionedFilePath testModuleNames + testLookupAll testWays :: Action () testWays = do @@ -68,3 +69,17 @@ testModuleNames = do test $ forAll names $ \n -> uncurry encodeModule (decodeModule n) == n where names = intercalate "." <$> listOf1 (listOf1 $ elements "abcABC123_'") + +testLookupAll :: Action () +testLookupAll = do + putBuild $ "==== lookupAll" + test $ lookupAll ["b" , "c" ] [("a", 1), ("c", 3), ("d", 4)] + == [Nothing, Just (3 :: Int)] + test $ forAll dicts $ \dict -> forAll extras $ \extra -> + let items = sort $ map fst dict ++ extra + in lookupAll items (sort dict) == map (flip lookup dict) items + where + dicts :: Gen [(Int, Int)] + dicts = nubBy ((==) `on` fst) <$> vector 20 + extras :: Gen [Int] + extras = vector 20 From git at git.haskell.org Fri Oct 27 00:22:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Lowercase flavour names in --help (73c72a6) Message-ID: <20171027002230.09DDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73c72a633398eb0f021fdd4081e2e559a10105f5/ghc >--------------------------------------------------------------- commit 73c72a633398eb0f021fdd4081e2e559a10105f5 Author: Moritz Kiefer Date: Sat Sep 3 12:51:23 2016 +0200 Lowercase flavour names in --help >--------------------------------------------------------------- 73c72a633398eb0f021fdd4081e2e559a10105f5 src/CmdLineFlag.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index cc0eb7f..b58df7b 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -74,7 +74,7 @@ readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") - "Build flavour (Default, Quick or Quickest)." + "Build flavour (default, quick or quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") From git at git.haskell.org Fri Oct 27 00:22:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for both *.gz and *.bz2 archives, see #79. (fd3a1f8) Message-ID: <20171027002231.A535C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd3a1f89719fb551ed3f6579ef978ab304abe66c/ghc >--------------------------------------------------------------- commit fd3a1f89719fb551ed3f6579ef978ab304abe66c Author: Andrey Mokhov Date: Sun Jan 3 18:16:59 2016 +0000 Add support for both *.gz and *.bz2 archives, see #79. >--------------------------------------------------------------- fd3a1f89719fb551ed3f6579ef978ab304abe66c src/Settings/Builders/Tar.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/Tar.hs b/src/Settings/Builders/Tar.hs index 1f9f0ba..f59b1cf 100644 --- a/src/Settings/Builders/Tar.hs +++ b/src/Settings/Builders/Tar.hs @@ -1,10 +1,14 @@ module Settings.Builders.Tar (tarBuilderArgs) where +import Base import Expression import Predicates (builder) tarBuilderArgs :: Args tarBuilderArgs = builder Tar ? do - mconcat [ arg "-xzf" - , arg =<< getInput + input <- getInput + mconcat [ arg "-xf" + , ("*.gz" ?== input) ? arg "--gzip" + , ("*.bz2" ?== input) ? arg "--bzip2" + , arg input , arg "-C", arg =<< getOutput ] From git at git.haskell.org Fri Oct 27 00:22:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #286 from cocreature/lowercase-flavour (e5b4b0c) Message-ID: <20171027002233.E35653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e5b4b0cbef54b3c2c32238cb810a5cebcb9270e7/ghc >--------------------------------------------------------------- commit e5b4b0cbef54b3c2c32238cb810a5cebcb9270e7 Merge: fd7dd6f 73c72a6 Author: Andrey Mokhov Date: Sat Sep 3 12:20:06 2016 +0100 Merge pull request #286 from cocreature/lowercase-flavour Lowercase flavour names in --help >--------------------------------------------------------------- e5b4b0cbef54b3c2c32238cb810a5cebcb9270e7 src/CmdLineFlag.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:22:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep duplicates in the intersection. (2ec9f84) Message-ID: <20171027002233.76E183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ec9f84bce2ad28a16802b7ac901685495a6b4ff/ghc >--------------------------------------------------------------- commit 2ec9f84bce2ad28a16802b7ac901685495a6b4ff Author: Andrey Mokhov Date: Sun Feb 21 01:27:24 2016 +0000 Keep duplicates in the intersection. >--------------------------------------------------------------- 2ec9f84bce2ad28a16802b7ac901685495a6b4ff src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 324feb8..871cd3c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -157,7 +157,7 @@ minusOrd (x:xs) (y:ys) = case compare x y of EQ -> minusOrd xs ys GT -> minusOrd (x:xs) ys --- Explicit definition to avoid dependency on Data.List.Ordered +-- Explicit definition to avoid dependency on Data.List.Ordered. TODO: add tests -- | Intersection of two ordered lists by a predicate. intersectOrd :: (a -> b -> Ordering) -> [a] -> [b] -> [a] intersectOrd cmp = loop @@ -166,7 +166,7 @@ intersectOrd cmp = loop loop _ [] = [] loop (x:xs) (y:ys) = case cmp x y of LT -> loop xs (y:ys) - EQ -> x : loop xs ys + EQ -> x : loop xs (y:ys) GT -> loop (x:xs) ys -- | Lookup all elements of a given sorted list in a given sorted dictionary. From git at git.haskell.org Fri Oct 27 00:22:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add path to generated includes for compiler package (57d6c69) Message-ID: <20171027002237.C986F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57d6c69843a0c2f7fd89a0c9cbc49742c6347414/ghc >--------------------------------------------------------------- commit 57d6c69843a0c2f7fd89a0c9cbc49742c6347414 Author: Andrey Mokhov Date: Sun Sep 25 01:29:46 2016 +0900 Add path to generated includes for compiler package Fix #288. >--------------------------------------------------------------- 57d6c69843a0c2f7fd89a0c9cbc49742c6347414 src/Settings/Builders/Common.hs | 2 +- src/Settings/Packages/Compiler.hs | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index d036f8a..b276102 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -1,5 +1,5 @@ module Settings.Builders.Common ( - includesArgs, cIncludeArgs, ldArgs, cArgs, cWarnings, + includes, includesArgs, cIncludeArgs, ldArgs, cArgs, cWarnings, argSetting, argSettingList, argStagedBuilderPath, argStagedSettingList ) where diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 7dbbaa3..65ced17 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -7,6 +7,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Predicate import Settings +import Settings.Builders.Common compilerPackageArgs :: Args compilerPackageArgs = package compiler ? do @@ -15,7 +16,10 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder Ghc ? arg ("-I" ++ path) + , builder Ghc ? mconcat + [ arg ("-I" ++ path) + , includesArgs + , append [ "-optP-I" ++ dir | dir <- includes ] ] , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) From git at git.haskell.org Fri Oct 27 00:22:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop duplication of module names in moduleFilesOracle. (59d7bf1) Message-ID: <20171027002237.568303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59d7bf155a356bd662a3e74f11b4c2532464b10b/ghc >--------------------------------------------------------------- commit 59d7bf155a356bd662a3e74f11b4c2532464b10b Author: Andrey Mokhov Date: Sun Feb 21 01:28:12 2016 +0000 Drop duplication of module names in moduleFilesOracle. See #210. >--------------------------------------------------------------- 59d7bf155a356bd662a3e74f11b4c2532464b10b src/Oracles/ModuleFiles.hs | 28 +++++++++++++++++++++------- 1 file changed, 21 insertions(+), 7 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index a5e40ed..bced848 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -16,8 +16,7 @@ moduleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (dirs, modules) - return $ map snd found + fmap catMaybes . askOracle $ ModuleFilesKey (dirs, modules) haskellModuleFiles :: Context -> Action ([FilePath], [String]) haskellModuleFiles context @ (Context {..}) = do @@ -29,13 +28,17 @@ haskellModuleFiles context @ (Context {..}) = do let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] foundSrcDirs <- askOracle $ ModuleFilesKey (dirs , modules) foundAutogen <- askOracle $ ModuleFilesKey ([autogen], modules) + found <- sequence $ zipWith3 addSources modules foundSrcDirs foundAutogen - let found = foundSrcDirs ++ foundAutogen - missingMods = modules `minusOrd` (sort $ map fst found) + let missingMods = map fst . filter (isNothing . snd) $ zip modules found otherFileToMod = replaceEq '/' '.' . dropExtension . dropPkgPath - (haskellFiles, otherFiles) = partition ("//*hs" ?==) (map snd found) + (haskellFiles, otherFiles) = partition ("//*hs" ?==) $ catMaybes found return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) + where + addSources _ Nothing r = return r + addSources _ l Nothing = return l + addSources m (Just f1) (Just f2) = errorMultipleSources m f1 f2 -- | This is an important oracle whose role is to find and cache module source -- files. More specifically, it takes a list of directories @dirs@ and a sorted @@ -51,7 +54,7 @@ moduleFilesOracle :: Rules () moduleFilesOracle = void $ addOracle $ \(ModuleFilesKey (dirs, modules)) -> do let decodedPairs = map decodeModule modules - modDirFiles = map (bimap head sort . unzip) + modDirFiles = map (bimap head id . unzip) . groupBy ((==) `on` fst) $ decodedPairs result <- fmap concat . forM dirs $ \dir -> do @@ -64,4 +67,15 @@ moduleFilesOracle = void $ found = intersectOrd cmp noBoot mFiles return (map (fullDir -/-) found, mDir) - return $ sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] + let pairs = sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] + multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ] + + unless (null multi) $ do + let (m, f1, f2) = head multi + errorMultipleSources m f1 f2 + + return $ lookupAll modules pairs + +errorMultipleSources :: String -> FilePath -> FilePath -> Action a +errorMultipleSources m f1 f2 = putError $ "Module " ++ m ++ + " has more than one source file: " ++ f1 ++ " and " ++ f2 ++ "." From git at git.haskell.org Fri Oct 27 00:22:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor our common build actions into src/Rules/Actions.hs (498939a) Message-ID: <20171027002235.44E8A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/498939a9b2942c4d95cc59b45721579a59a36f97/ghc >--------------------------------------------------------------- commit 498939a9b2942c4d95cc59b45721579a59a36f97 Author: Andrey Mokhov Date: Mon Jan 4 01:32:11 2016 +0000 Factor our common build actions into src/Rules/Actions.hs >--------------------------------------------------------------- 498939a9b2942c4d95cc59b45721579a59a36f97 src/Base.hs | 2 +- src/Rules/Actions.hs | 72 ++++++++++++++++++++++++++++++++++++++++++++++++---- src/Rules/Copy.hs | 11 +++----- src/Rules/Data.hs | 11 ++++---- src/Rules/Program.hs | 2 +- 5 files changed, 77 insertions(+), 21 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index acbd3c3..8733282 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -175,7 +175,7 @@ putError msg = do -- | Render the given set of lines in a ASCII box renderBox :: [String] -> String renderBox ls = - unlines $ [begin] ++ map (bar++) ls ++ [end] + unlines ([begin] ++ map (bar++) ls) ++ end where (begin,bar,end) | useUnicode = ( "╭──────────" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index e930b52..2a4fc80 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,9 +1,15 @@ {-# LANGUAGE RecordWildCards #-} -module Rules.Actions (build, buildWithResources) where +module Rules.Actions ( + build, buildWithResources, copyFile, createDirectory, moveDirectory, + fixFile, runConfigure, runMake, runBuilder + ) where + +import qualified System.Directory as IO import Base import Expression import Oracles.ArgsHash +import Oracles.Config.Setting import Settings import Settings.Args import Settings.Builders.Ar @@ -25,7 +31,14 @@ buildWithResources rs target = do withResources rs $ do unless verbose $ putInfo target quietlyUnlessVerbose $ case builder of - Ar -> arCmd path argList + Ar -> do + output <- interpret target getOutput + if "//*.a" ?== output + then arCmd path argList + else do + input <- interpret target getInput + top <- setting GhcSourcePath + cmd [path] [Cwd output] "x" (top -/- input) HsCpp -> captureStdout target path argList GenApply -> captureStdout target path argList @@ -49,13 +62,62 @@ captureStdout target path argList = do Stdout output <- cmd [path] argList writeFileChanged file output +copyFile :: FilePath -> FilePath -> Action () +copyFile source target = do + putBuild $ renderBox [ "Copy file" + , " input: " ++ source + , "=> output: " ++ target ] + copyFileChanged source target + +createDirectory :: FilePath -> Action () +createDirectory dir = do + putBuild $ "| Create directory " ++ dir + liftIO $ IO.createDirectoryIfMissing True dir + +-- Note, the source directory is untracked +moveDirectory :: FilePath -> FilePath -> Action () +moveDirectory source target = do + putBuild $ renderBox [ "Move directory" + , " input: " ++ source + , "=> output: " ++ target ] + liftIO $ IO.renameDirectory source target + +-- Transform a given file by applying a function to its contents +fixFile :: FilePath -> (String -> String) -> Action () +fixFile file f = do + putBuild $ "| Fix " ++ file + old <- liftIO $ readFile file + let new = f old + length new `seq` liftIO $ writeFile file new + +runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () +runConfigure dir opts args = do + need [dir -/- "configure"] + putBuild $ "| Run configure in " ++ dir ++ "..." + quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args + +runMake :: FilePath -> [String] -> Action () +runMake dir args = do + need [dir -/- "Makefile"] + let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." + quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args + +runBuilder :: Builder -> [String] -> Action () +runBuilder builder args = do + needBuilder laxDependencies builder + path <- builderPath builder + let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + putBuild $ "| Run " ++ show builder ++ note + quietly $ cmd [path] args + -- Print out key information about the command being executed putInfo :: Target.Target -> Action () -putInfo (Target.Target {..}) = putBuild $ renderBox $ - [ "Running " ++ show builder +putInfo (Target.Target {..}) = putBuild $ renderBox + [ "Run " ++ show builder ++ " (" ++ stageInfo ++ "package = " ++ pkgNameString package - ++ wayInfo ++ "):" + ++ wayInfo ++ ")" , " input: " ++ digest inputs , "=> output: " ++ digest outputs ] where diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index 766e865..3a385b8 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -3,6 +3,7 @@ module Rules.Copy (installTargets, copyRules) where import Base import Expression import GHC +import Rules.Actions import Rules.Generate import Rules.Libffi import Settings.TargetDirectory @@ -20,16 +21,10 @@ copyRules = do when (length ffiHPaths /= 1) $ putError $ "copyRules: exactly one ffi.h header expected" ++ "(found: " ++ show ffiHPaths ++ ")." - let ffiHPath = takeDirectory $ head ffiHPaths - copy ffih ffiHPath + copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." where - file <~ dir = file %> \_ -> copy file dir - - copy file dir = do - let source = dir -/- takeFileName file - copyFileChanged source file - putBuild $ "| Copy " ++ source ++ " -> " ++ file + file <~ dir = file %> \_ -> copyFile (dir -/- file) file diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 84ac619..274092b 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -118,10 +118,9 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 -- Reason: Shake's built-in makefile parser doesn't recognise slashes postProcessPackageData :: FilePath -> Action () -postProcessPackageData file = do - contents <- fmap (filter ('$' `notElem`) . lines) . liftIO $ readFile file - length contents `seq` writeFileLines file $ map processLine contents +postProcessPackageData file = fixFile file fixPackageData + where + fixPackageData = unlines . map processLine . filter ('$' `notElem`) . lines + processLine line = replaceSeparators '_' prefix ++ suffix where - processLine line = replaceSeparators '_' prefix ++ suffix - where - (prefix, suffix) = break (== '=') line + (prefix, suffix) = break (== '=') line diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index b2840dd..fe55005 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -59,7 +59,7 @@ buildWrapper :: PartialTarget -> Wrapper -> FilePath -> FilePath -> Action () buildWrapper target @ (PartialTarget stage pkg) wrapper wrapperPath binPath = do contents <- interpretPartial target $ wrapper binPath writeFileChanged wrapperPath contents - () <- cmd "chmod +x " [wrapperPath] + unit $ cmd "chmod +x " [wrapperPath] putSuccess $ "| Successfully created wrapper for '" ++ pkgNameString pkg ++ "' (" ++ show stage ++ ")." From git at git.haskell.org Fri Oct 27 00:22:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Respect trackBuildSystem user setting (4ce3206) Message-ID: <20171027002238.BB15C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ce32069c4b46822dae309002fcbece8b62627ea/ghc >--------------------------------------------------------------- commit 4ce32069c4b46822dae309002fcbece8b62627ea Author: Andrey Mokhov Date: Mon Jan 4 01:33:45 2016 +0000 Respect trackBuildSystem user setting >--------------------------------------------------------------- 4ce32069c4b46822dae309002fcbece8b62627ea src/Rules/Generators/ConfigHs.hs | 3 ++- src/Rules/Generators/GhcAutoconfH.hs | 4 +++- src/Rules/Generators/GhcBootPlatformH.hs | 4 +++- src/Rules/Generators/GhcPlatformH.hs | 4 +++- src/Rules/Generators/GhcVersionH.hs | 4 ++++ src/Rules/Generators/VersionHs.hs | 4 +++- 6 files changed, 18 insertions(+), 5 deletions(-) diff --git a/src/Rules/Generators/ConfigHs.hs b/src/Rules/Generators/ConfigHs.hs index 1ec96e9..547670a 100644 --- a/src/Rules/Generators/ConfigHs.hs +++ b/src/Rules/Generators/ConfigHs.hs @@ -10,7 +10,8 @@ import Settings -- TODO: add tracking by moving these functions to separate tracked files generateConfigHs :: Expr String generateConfigHs = do - lift $ need [sourcePath -/- "Rules/Generators/ConfigHs.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/ConfigHs.hs"] cProjectName <- getSetting ProjectName cProjectGitCommitId <- getSetting ProjectGitCommitId cProjectVersion <- getSetting ProjectVersion diff --git a/src/Rules/Generators/GhcAutoconfH.hs b/src/Rules/Generators/GhcAutoconfH.hs index 67ec731..f5f89c6 100644 --- a/src/Rules/Generators/GhcAutoconfH.hs +++ b/src/Rules/Generators/GhcAutoconfH.hs @@ -3,6 +3,7 @@ module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH) where import Base import Expression import Oracles +import Settings.User -- TODO: change `mk/config.h` to `shake-build/cfg/config.h` configH :: FilePath @@ -16,7 +17,8 @@ undefinePackage s generateGhcAutoconfH :: Expr String generateGhcAutoconfH = do - lift $ need [sourcePath -/- "Rules/Generators/GhcAutoconfH.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcAutoconfH.hs"] configHContents <- lift $ map undefinePackage <$> readFileLines configH tablesNextToCode <- lift $ ghcEnableTablesNextToCode ghcUnreg <- getFlag GhcUnregisterised diff --git a/src/Rules/Generators/GhcBootPlatformH.hs b/src/Rules/Generators/GhcBootPlatformH.hs index 7416d24..6c111c2 100644 --- a/src/Rules/Generators/GhcBootPlatformH.hs +++ b/src/Rules/Generators/GhcBootPlatformH.hs @@ -3,10 +3,12 @@ module Rules.Generators.GhcBootPlatformH (generateGhcBootPlatformH) where import Base import Expression import Oracles +import Settings.User generateGhcBootPlatformH :: Expr String generateGhcBootPlatformH = do - lift $ need [sourcePath -/- "Rules/Generators/GhcBootPlatformH.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcBootPlatformH.hs"] stage <- getStage let cppify = replaceEq '-' '_' . replaceEq '.' '_' chooseSetting x y = getSetting $ if stage == Stage0 then x else y diff --git a/src/Rules/Generators/GhcPlatformH.hs b/src/Rules/Generators/GhcPlatformH.hs index 8652382..1deee3d 100644 --- a/src/Rules/Generators/GhcPlatformH.hs +++ b/src/Rules/Generators/GhcPlatformH.hs @@ -3,10 +3,12 @@ module Rules.Generators.GhcPlatformH (generateGhcPlatformH) where import Base import Expression import Oracles +import Settings.User generateGhcPlatformH :: Expr String generateGhcPlatformH = do - lift $ need [sourcePath -/- "Rules/Generators/GhcPlatformH.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcPlatformH.hs"] let cppify = replaceEq '-' '_' . replaceEq '.' '_' hostPlatform <- getSetting HostPlatform hostArch <- getSetting HostArch diff --git a/src/Rules/Generators/GhcVersionH.hs b/src/Rules/Generators/GhcVersionH.hs index a45df55..278813f 100644 --- a/src/Rules/Generators/GhcVersionH.hs +++ b/src/Rules/Generators/GhcVersionH.hs @@ -1,10 +1,14 @@ module Rules.Generators.GhcVersionH (generateGhcVersionH) where +import Base import Expression import Oracles +import Settings.User generateGhcVersionH :: Expr String generateGhcVersionH = do + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/GhcVersionH.hs"] version <- getSetting ProjectVersionInt patchLevel1 <- getSetting ProjectPatchLevel1 patchLevel2 <- getSetting ProjectPatchLevel2 diff --git a/src/Rules/Generators/VersionHs.hs b/src/Rules/Generators/VersionHs.hs index 3023fc9..33b62193d 100644 --- a/src/Rules/Generators/VersionHs.hs +++ b/src/Rules/Generators/VersionHs.hs @@ -3,10 +3,12 @@ module Rules.Generators.VersionHs (generateVersionHs) where import Base import Expression import Oracles +import Settings.User generateVersionHs :: Expr String generateVersionHs = do - lift $ need [sourcePath -/- "Rules/Generators/VersionHs.hs"] + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules/Generators/VersionHs.hs"] projectVersion <- getSetting ProjectVersion targetOs <- getSetting TargetOs targetArch <- getSetting TargetArch From git at git.haskell.org Fri Oct 27 00:22:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up build rules for custom packages. (1c3c9f3) Message-ID: <20171027002242.61B313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c3c9f3438f0fbd80ff476f63e253ecf0355920a/ghc >--------------------------------------------------------------- commit 1c3c9f3438f0fbd80ff476f63e253ecf0355920a Author: Andrey Mokhov Date: Mon Jan 4 01:34:17 2016 +0000 Clean up build rules for custom packages. >--------------------------------------------------------------- 1c3c9f3438f0fbd80ff476f63e253ecf0355920a src/Rules/IntegerGmp.hs | 64 +++++++++++++++++++++---------------------------- src/Rules/Libffi.hs | 31 ++++++++---------------- 2 files changed, 37 insertions(+), 58 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 1f50dc0..4e19b9d 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,12 +1,11 @@ module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where -import System.Directory - import Base import Expression import GHC import Oracles.Config.Setting import Rules.Actions +import Settings.User integerGmpBase :: FilePath integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp" @@ -28,9 +27,8 @@ target = PartialTarget Stage0 integerGmp configureEnvironment :: Action [CmdOption] configureEnvironment = do sequence [ builderEnv "CC" $ Gcc Stage1 - , builderEnv "CXX" $ Gcc Stage1 , builderEnv "AR" Ar - , builderEnv "NM" Nm] + , builderEnv "NM" Nm ] where builderEnv var builder = do needBuilder False builder @@ -49,7 +47,7 @@ configureArguments = do integerGmpRules :: Rules () integerGmpRules = do integerGmpLibrary %> \_ -> do - need [sourcePath -/- "Rules" -/- "integerGmp.hs"] + when trackBuildSystem $ need [sourcePath -/- "Rules" -/- "integerGmp.hs"] -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] @@ -64,53 +62,45 @@ integerGmpRules = do when (length tarballs /= 1) $ putError $ "integerGmpRules: exactly one tarball expected" ++ "(found: " ++ show tarballs ++ ")." - let filename = dropExtension . dropExtension . takeFileName $ head tarballs - let suffix = "-nodoc-patched" - unless (suffix `isSuffixOf` filename) $ - putError $ "integerGmpRules: expected suffix " ++ suffix - ++ " (found: " ++ filename ++ ")." - let libname = take (length filename - length suffix) filename need tarballs build $ fullTarget target Tar tarballs [integerGmpBase] -- move gmp- to gmpbuild - let integerGmpExtracted = integerGmpBase -/- libname - liftIO $ renameDirectory integerGmpExtracted integerGmpBuild - putBuild $ "| Move " ++ integerGmpExtracted ++ " -> " ++ integerGmpBuild + let filename = dropExtension . dropExtension . takeFileName $ head tarballs + suffix = "-nodoc-patched" + unless (suffix `isSuffixOf` filename) $ + putError $ "integerGmpRules: expected suffix " ++ suffix + ++ " (found: " ++ filename ++ ")." + let libname = take (length filename - length suffix) filename + moveDirectory (integerGmpBase -/- libname) integerGmpBuild -- apply patches -- TODO: replace "patch" with PATCH_CMD - unit $ cmd Shell [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch" - unit $ cmd Shell [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch] - putBuild $ "| Applied gmpsrc.patch and " ++ takeFileName integerGmpPatch + unit . quietly $ cmd Shell (EchoStdout False) [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch" + putBuild $ "| Apply " ++ (integerGmpBase -/- "gmpsrc.patch") + unit . quietly $ cmd Shell (EchoStdout False) [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch] + putBuild $ "| Apply " ++ (integerGmpBase -/- integerGmpPatch) -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? - -- ./configure - putBuild "| Running libffi configure..." envs <- configureEnvironment args <- configureArguments - unit $ cmd Shell [Cwd integerGmpBuild] "bash configure" envs args + runConfigure integerGmpBuild envs args - -- make - putBuild "| Running make..." - unit $ cmd Shell "make" ["-C", integerGmpBuild, "MAKEFLAGS="] + runMake integerGmpBuild [] -- copy library and header - forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> do - let file' = integerGmpBase -/- takeFileName file - copyFileChanged (integerGmpBuild -/- file) file' - putBuild $ "| Copy " ++ file ++ " -> " ++ file' - - ar <- builderPath Ar - ran <- builderPath Ranlib - -- unpack libgmp.a - putBuild "| Unpacking libgmp.a..." - unit $ cmd Shell [Cwd integerGmpBase] "mkdir -p objs" - unit $ cmd Shell [Cwd (integerGmpBase -/- "objs")] [ar] " x ../libgmp.a" - unit $ cmd Shell [Cwd integerGmpBase] [ran] " libgmp.a" - - putSuccess "| Successfully build custom library 'integer-gmp'" + -- TODO: why copy library, can we move it instead? + forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> + copyFile (integerGmpBuild -/- file) (integerGmpBase -/- takeFileName file) + + let objsDir = integerGmpBase -/- "objs" + createDirectory objsDir + build $ fullTarget target Ar [integerGmpLibrary] [objsDir] + + runBuilder Ranlib [integerGmpLibrary] + + putSuccess "| Successfully built custom library 'integer-gmp'" "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary] diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index f5f2668..93a20ab 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,13 +1,12 @@ module Rules.Libffi (libffiRules, libffiLibrary) where -import System.Directory - import Base import Expression import GHC import Oracles.Config.Setting import Rules.Actions import Settings.Builders.Common +import Settings.User -- We use this file to track the whole libffi library libffiLibrary :: FilePath @@ -63,40 +62,30 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiLibrary %> \_ -> do - need [sourcePath -/- "Rules/Libffi.hs"] + when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] when (length tarballs /= 1) $ putError $ "libffiRules: exactly one libffi tarball expected" ++ "(found: " ++ show tarballs ++ ")." - let libname = dropExtension . dropExtension . takeFileName $ head tarballs need tarballs build $ fullTarget target Tar tarballs ["libffi-tarballs"] - let libffiExtracted = "libffi-tarballs" -/- libname - liftIO $ renameDirectory libffiExtracted libffiBuild - putBuild $ "| Move " ++ libffiExtracted ++ " -> " ++ libffiBuild + let libname = dropExtension . dropExtension . takeFileName $ head tarballs + moveDirectory ("libffi-tarballs" -/- libname) libffiBuild - old <- liftIO $ readFile libffiMakefile - let new = fixLibffiMakefile old - length new `seq` liftIO $ writeFile libffiMakefile new - putBuild $ "| Fix " ++ libffiMakefile + fixFile libffiMakefile fixLibffiMakefile - forM_ ["config.guess", "config.sub"] $ \file -> do - copyFileChanged file $ libffiBuild -/- file - putBuild $ "| Copy " ++ file ++ " -> " ++ (libffiBuild -/- file) + forM_ ["config.guess", "config.sub"] $ \file -> + copyFile file (libffiBuild -/- file) - putBuild $ "| Running libffi configure..." envs <- configureEnvironment args <- configureArguments - unit $ cmd Shell [Cwd libffiBuild] "bash configure" envs args - - putBuild $ "| Running make..." - unit $ cmd Shell "make" ["-C", libffiBuild, "MAKEFLAGS="] + runConfigure libffiBuild envs args - putBuild $ "| Running make install..." - unit $ cmd Shell "make" ["-C", libffiBuild, "MAKEFLAGS= install"] + runMake libffiBuild [] + runMake libffiBuild ["install"] putSuccess $ "| Successfully built custom library 'libffi'" From git at git.haskell.org Fri Oct 27 00:22:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add findModuleFiles and export it. (9039a4f) Message-ID: <20171027002241.67D1F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9039a4f1dfedbc9606d2ccef35d81d7736993f11/ghc >--------------------------------------------------------------- commit 9039a4f1dfedbc9606d2ccef35d81d7736993f11 Author: Andrey Mokhov Date: Sun Feb 21 02:21:00 2016 +0000 Add findModuleFiles and export it. See #210. >--------------------------------------------------------------- 9039a4f1dfedbc9606d2ccef35d81d7736993f11 src/Oracles/ModuleFiles.hs | 22 ++++++++++++++-------- 1 file changed, 14 insertions(+), 8 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index bced848..501bc89 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,5 +1,7 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} -module Oracles.ModuleFiles (moduleFiles, haskellModuleFiles, moduleFilesOracle) where +module Oracles.ModuleFiles ( + moduleFiles, haskellModuleFiles, moduleFilesOracle, findModuleFiles + ) where import Base import Context @@ -16,7 +18,7 @@ moduleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - fmap catMaybes . askOracle $ ModuleFilesKey (dirs, modules) + fmap catMaybes $ findModuleFiles dirs modules haskellModuleFiles :: Context -> Action ([FilePath], [String]) haskellModuleFiles context @ (Context {..}) = do @@ -26,8 +28,8 @@ haskellModuleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - foundSrcDirs <- askOracle $ ModuleFilesKey (dirs , modules) - foundAutogen <- askOracle $ ModuleFilesKey ([autogen], modules) + foundSrcDirs <- findModuleFiles dirs modules + foundAutogen <- findModuleFiles [autogen] modules found <- sequence $ zipWith3 addSources modules foundSrcDirs foundAutogen let missingMods = map fst . filter (isNothing . snd) $ zip modules found @@ -43,13 +45,17 @@ haskellModuleFiles context @ (Context {..}) = do -- | This is an important oracle whose role is to find and cache module source -- files. More specifically, it takes a list of directories @dirs@ and a sorted -- list of module names @modules@ as arguments, and for each module, e.g. --- @A.B.C@, returns a FilePath of the form @dir/A/B/C.extension@, such that --- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or Nothing +-- @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, such that +-- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or 'Nothing' -- if there is no such file. If more than one matching file is found an error is -- raised. For example, for the 'compiler' package given --- @dirs = ["codeGen", "parser"]@, and +-- @dirs = ["compiler/codeGen", "compiler/parser"]@, and -- @modules = ["CodeGen.Platform.ARM", "Lexer", "Missing.Module"]@, it produces --- @[Just "codeGen/CodeGen/Platform/ARM.hs", Just "parser/Lexer.x", Nothing]@. +-- @[Just "compiler/codeGen/CodeGen/Platform/ARM.hs", +-- Just "compiler/parser/Lexer.x", Nothing]@. +findModuleFiles :: [FilePath] -> [String] -> Action [Maybe FilePath] +findModuleFiles dirs modules = askOracle $ ModuleFilesKey (dirs, modules) + moduleFilesOracle :: Rules () moduleFilesOracle = void $ addOracle $ \(ModuleFilesKey (dirs, modules)) -> do From git at git.haskell.org Fri Oct 27 00:22:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor GMP build rule (6836711) Message-ID: <20171027002241.7FD353A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68367119d7f5d1f01a94a0eab87a53900c54fe3e/ghc >--------------------------------------------------------------- commit 68367119d7f5d1f01a94a0eab87a53900c54fe3e Author: Andrey Mokhov Date: Sun Oct 2 10:40:16 2016 +0900 Refactor GMP build rule See #289. >--------------------------------------------------------------- 68367119d7f5d1f01a94a0eab87a53900c54fe3e src/Rules/Gmp.hs | 92 ++++++++++++++++++++++++--------------------------- src/Settings/Paths.hs | 8 ++--- 2 files changed, 45 insertions(+), 55 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 7fc3e18..66d6c0b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -17,10 +17,12 @@ gmpBase = pkgPath integerGmp -/- "gmp" gmpContext :: Context gmpContext = vanillaContext Stage1 integerGmp --- TODO: Noone needs this file, but we build it. Why? gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" +gmpLibrary :: FilePath +gmpLibrary = gmpBuildPath -/- ".libs/libgmp.a" + gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] @@ -29,76 +31,68 @@ configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 , builderEnvironment "AR" Ar , builderEnvironment "NM" Nm ] --- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do - -- TODO: split into multiple rules gmpLibraryH %> \_ -> do - need [sourcePath -/- "Rules/Gmp.hs"] - removeDirectory gmpBuildPath - - -- We don't use system GMP on Windows. TODO: fix? windows <- windowsHost configMk <- readFile' $ gmpBase -/- "config.mk" - if not windows && any (`isInfixOf` configMk) - [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] + if not windows && -- TODO: We don't use system GMP on Windows. Fix? + any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" createDirectory $ takeDirectory gmpLibraryH copyFile (gmpBase -/- "ghc-gmp.h") gmpLibraryH else do putBuild "| No GMP library/framework detected; in tree GMP will be built" - - -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is - -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. - -- That's because the doc/ directory contents are under the GFDL, - -- which causes problems for Debian. - tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "gmpRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - - withTempDir $ \dir -> do - let tmp = unifyPath dir - need [tarball] - build $ Target gmpContext Tar [tarball] [tmp] - - forM_ gmpPatches $ \src -> do - let patch = takeFileName src - patchPath = tmp -/- patch - copyFile src patchPath - applyPatch tmp patch - - let name = dropExtension . dropExtension $ takeFileName tarball - unpack = fromMaybe . error $ "gmpRules: expected suffix " - ++ "-nodoc-patched (found: " ++ name ++ ")." - libName = unpack $ stripSuffix "-nodoc-patched" name - - moveDirectory (tmp -/- libName) gmpBuildPath - - env <- configureEnvironment - buildWithCmdOptions env $ - Target gmpContext (Configure gmpBuildPath) - [gmpBuildPath -/- "Makefile.in"] - [gmpBuildPath -/- "Makefile"] - build $ Target gmpContext (Make gmpBuildPath) [] [] - createDirectory $ takeDirectory gmpLibraryH copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH - moveFile (gmpBuildPath -/- ".libs/libgmp.a") gmpLibrary - createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] - runBuilder Ranlib [gmpLibrary] - putSuccess "| Successfully built custom library 'gmp'" + -- In-tree GMP header is built in the gmpLibraryH rule gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] -- This causes integerGmp package to be configured, hence creating the files [gmpBase -/- "config.mk", gmpBuildInfoPath] &%> \_ -> need [pkgDataFile gmpContext] + + -- Extract in-tree GMP sources and apply patches + gmpBuildPath -/- "Makefile.in" %> \_ -> do + removeDirectory gmpBuildPath + -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is + -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. + -- That's because the doc/ directory contents are under the GFDL, + -- which causes problems for Debian. + tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] + tarball <- case tarballs of -- TODO: Drop code duplication. + [file] -> return $ unifyPath file + _ -> error $ "gmpRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + + withTempDir $ \dir -> do + let tmp = unifyPath dir + need [tarball] + build $ Target gmpContext Tar [tarball] [tmp] + + forM_ gmpPatches $ \src -> do + let patch = takeFileName src + copyFile src $ tmp -/- patch + applyPatch tmp patch + + let name = dropExtension . dropExtension $ takeFileName tarball + unpack = fromMaybe . error $ "gmpRules: expected suffix " + ++ "-nodoc-patched (found: " ++ name ++ ")." + libName = unpack $ stripSuffix "-nodoc-patched" name + + moveDirectory (tmp -/- libName) gmpBuildPath + + -- Run GMP's configure script + gmpBuildPath -/- "Makefile" %> \mk -> do + env <- configureEnvironment + need [mk <.> "in"] + buildWithCmdOptions env $ + Target gmpContext (Configure gmpBuildPath) [mk <.> "in"] [mk] diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 51e92e2..9c770f3 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,7 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibrary, gmpObjects, - gmpLibraryH, gmpBuildInfoPath, libffiBuildPath, shakeFilesPath, pkgConfFile, + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, + gmpBuildInfoPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, bootPackageConstraints, packageDependencies ) where @@ -66,10 +66,6 @@ pkgFile context prefix suffix = do gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" --- | Path to the GMP library. -gmpLibrary :: FilePath -gmpLibrary = gmpBuildPath -/- "libgmp.a" - -- | Path to the GMP library header. gmpLibraryH :: FilePath gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" From git at git.haskell.org Fri Oct 27 00:22:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test findModuleFiles. (1136a62) Message-ID: <20171027002245.822A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1136a62c35dfe9df3774667b1e501494e2a496b1/ghc >--------------------------------------------------------------- commit 1136a62c35dfe9df3774667b1e501494e2a496b1 Author: Andrey Mokhov Date: Sun Feb 21 02:22:26 2016 +0000 Test findModuleFiles. See #197, #210. >--------------------------------------------------------------- 1136a62c35dfe9df3774667b1e501494e2a496b1 src/Rules/Selftest.hs | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f549b0f..f4890b0 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,6 +6,7 @@ import Development.Shake import Test.QuickCheck import Base +import Oracles.ModuleFiles import Settings.Builders.Ar (chunksOfSize) import Way @@ -26,6 +27,7 @@ selftestRules = testMatchVersionedFilePath testModuleNames testLookupAll + testModuleFilesOracle testWays :: Action () testWays = do @@ -83,3 +85,14 @@ testLookupAll = do dicts = nubBy ((==) `on` fst) <$> vector 20 extras :: Gen [Int] extras = vector 20 + +testModuleFilesOracle :: Action () +testModuleFilesOracle = do + putBuild $ "==== moduleFilesOracle" + result <- findModuleFiles ["compiler/codeGen", "compiler/parser"] + [ "CodeGen.Platform.ARM" + , "Lexer" + , "Missing.Module"] + test $ result == [ Just "compiler/codeGen/CodeGen/Platform/ARM.hs" + , Just "compiler/parser/Lexer.x" + , Nothing] From git at git.haskell.org Fri Oct 27 00:22:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split the GMP build rule even further (d12066d) Message-ID: <20171027002245.D17793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d12066d8d457e2ea7dbc4afa37e8acaac6afa413/ghc >--------------------------------------------------------------- commit d12066d8d457e2ea7dbc4afa37e8acaac6afa413 Author: Andrey Mokhov Date: Sun Oct 2 03:23:42 2016 +0100 Split the GMP build rule even further See #289. >--------------------------------------------------------------- d12066d8d457e2ea7dbc4afa37e8acaac6afa413 src/Rules/Gmp.hs | 36 +++++++++++++++++++++--------------- 1 file changed, 21 insertions(+), 15 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 66d6c0b..0a53102 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -23,6 +23,9 @@ gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" gmpLibrary :: FilePath gmpLibrary = gmpBuildPath -/- ".libs/libgmp.a" +gmpMakefile :: FilePath +gmpMakefile = gmpBuildPath -/- "Makefile" + gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] @@ -33,24 +36,27 @@ configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 gmpRules :: Rules () gmpRules = do - gmpLibraryH %> \_ -> do + -- Copy appropriate GMP header and object files + gmpLibraryH %> \header -> do + createDirectory $ takeDirectory header windows <- windowsHost configMk <- readFile' $ gmpBase -/- "config.mk" if not windows && -- TODO: We don't use system GMP on Windows. Fix? any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" - createDirectory $ takeDirectory gmpLibraryH - copyFile (gmpBase -/- "ghc-gmp.h") gmpLibraryH + copyFile (gmpBase -/- "ghc-gmp.h") header else do putBuild "| No GMP library/framework detected; in tree GMP will be built" - build $ Target gmpContext (Make gmpBuildPath) [] [] - createDirectory $ takeDirectory gmpLibraryH - copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH - copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH + need [gmpLibrary] createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] + copyFile (gmpBuildPath -/- "gmp.h") header + copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH + -- Build in-tree GMP library + gmpLibrary %> \lib -> do + build $ Target gmpContext (Make gmpBuildPath) [gmpMakefile] [lib] putSuccess "| Successfully built custom library 'gmp'" -- In-tree GMP header is built in the gmpLibraryH rule @@ -60,8 +66,15 @@ gmpRules = do [gmpBase -/- "config.mk", gmpBuildInfoPath] &%> \_ -> need [pkgDataFile gmpContext] + -- Run GMP's configure script + gmpMakefile %> \mk -> do + env <- configureEnvironment + need [mk <.> "in"] + buildWithCmdOptions env $ + Target gmpContext (Configure gmpBuildPath) [mk <.> "in"] [mk] + -- Extract in-tree GMP sources and apply patches - gmpBuildPath -/- "Makefile.in" %> \_ -> do + gmpMakefile <.> "in" %> \_ -> do removeDirectory gmpBuildPath -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. @@ -89,10 +102,3 @@ gmpRules = do libName = unpack $ stripSuffix "-nodoc-patched" name moveDirectory (tmp -/- libName) gmpBuildPath - - -- Run GMP's configure script - gmpBuildPath -/- "Makefile" %> \mk -> do - env <- configureEnvironment - need [mk <.> "in"] - buildWithCmdOptions env $ - Target gmpContext (Configure gmpBuildPath) [mk <.> "in"] [mk] From git at git.haskell.org Fri Oct 27 00:22:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix #87. (563307b) Message-ID: <20171027002246.4E08E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/563307bd23206aafe88c74088411ff55fa7bfb5a/ghc >--------------------------------------------------------------- commit 563307bd23206aafe88c74088411ff55fa7bfb5a Author: Andrey Mokhov Date: Mon Jan 4 01:45:12 2016 +0000 Fix #87. >--------------------------------------------------------------- 563307bd23206aafe88c74088411ff55fa7bfb5a src/Rules/Copy.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index 3a385b8..3f33d9c 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -27,4 +27,4 @@ copyRules = do "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." where - file <~ dir = file %> \_ -> copyFile (dir -/- file) file + file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file From git at git.haskell.org Fri Oct 27 00:22:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant brackets. (a09185a) Message-ID: <20171027002249.938113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a09185a4d6a5aa90930ecab25724830bcddb9fa2/ghc >--------------------------------------------------------------- commit a09185a4d6a5aa90930ecab25724830bcddb9fa2 Author: Andrey Mokhov Date: Tue Feb 23 02:46:06 2016 +0000 Drop redundant brackets. >--------------------------------------------------------------- a09185a4d6a5aa90930ecab25724830bcddb9fa2 src/GHC.hs | 4 ++-- src/Oracles/ModuleFiles.hs | 4 ++-- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 4 ++-- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 2 +- src/Settings/Paths.hs | 10 +++++----- 10 files changed, 18 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a09185a4d6a5aa90930ecab25724830bcddb9fa2 From git at git.haskell.org Fri Oct 27 00:22:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing directory (c9ae45b) Message-ID: <20171027002250.11D693A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9ae45b4c7757a54b40f84c6a8532f2d5c2a5418/ghc >--------------------------------------------------------------- commit c9ae45b4c7757a54b40f84c6a8532f2d5c2a5418 Author: Andrey Mokhov Date: Sun Oct 2 18:38:31 2016 +0900 Fix missing directory See #289. >--------------------------------------------------------------- c9ae45b4c7757a54b40f84c6a8532f2d5c2a5418 src/Rules/Gmp.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 0a53102..50c548b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -38,19 +38,20 @@ gmpRules :: Rules () gmpRules = do -- Copy appropriate GMP header and object files gmpLibraryH %> \header -> do - createDirectory $ takeDirectory header windows <- windowsHost configMk <- readFile' $ gmpBase -/- "config.mk" if not windows && -- TODO: We don't use system GMP on Windows. Fix? any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" + createDirectory $ takeDirectory header copyFile (gmpBase -/- "ghc-gmp.h") header else do putBuild "| No GMP library/framework detected; in tree GMP will be built" need [gmpLibrary] createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] + createDirectory $ takeDirectory header copyFile (gmpBuildPath -/- "gmp.h") header copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH From git at git.haskell.org Fri Oct 27 00:22:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build rts in stage1 instead of dist (c4c7a7f) Message-ID: <20171027002250.ADD833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4c7a7f8d710c1a02ff68456f7ee9cb8fd5aa3a3/ghc >--------------------------------------------------------------- commit c4c7a7f8d710c1a02ff68456f7ee9cb8fd5aa3a3 Author: Moritz Angermann Date: Mon Jan 4 20:26:14 2016 +0800 Build rts in stage1 instead of dist `rts/dist` is hardcoded, while the shake build system builds in `rts/stage1`. Fixes #86 >--------------------------------------------------------------- c4c7a7f8d710c1a02ff68456f7ee9cb8fd5aa3a3 src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 274092b..b68f1c7 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -104,7 +104,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do , "includes/ghcplatform.h" ] build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] old <- liftIO $ readFile rtsConf - let new = unlines . map (replace "\"\"" "") + let new = unlines . map (replace "\"\"" "" . replace "rts/dist/build" "rts/stage1/build") . filter (not . null) $ lines old liftIO $ length new `seq` writeFile rtsConf new From git at git.haskell.org Fri Oct 27 00:22:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify and refactor moduleFiles oracle. (3d9c2fd) Message-ID: <20171027002253.3AAD93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d9c2fdaf006a7aada8454295469cc5d8aa23938/ghc >--------------------------------------------------------------- commit 3d9c2fdaf006a7aada8454295469cc5d8aa23938 Author: Andrey Mokhov Date: Thu Feb 25 23:15:18 2016 +0000 Simplify and refactor moduleFiles oracle. See #210. >--------------------------------------------------------------- 3d9c2fdaf006a7aada8454295469cc5d8aa23938 src/Oracles/ModuleFiles.hs | 31 ++++++++++++++++++------------- src/Rules/Dependencies.hs | 3 ++- src/Rules/Documentation.hs | 3 ++- src/Settings.hs | 16 +--------------- 4 files changed, 23 insertions(+), 30 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index cf33e20..4c74265 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,12 +1,12 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} module Oracles.ModuleFiles ( - moduleFiles, haskellModuleFiles, moduleFilesOracle, findModuleFiles + moduleFiles, haskellSources, moduleFilesOracle, findModuleFiles ) where import Base import Context +import Expression import Oracles.PackageData -import Package import Settings.Paths newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) @@ -14,11 +14,12 @@ newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) moduleFiles :: Context -> Action [FilePath] moduleFiles context @ Context {..} = do - let path = contextPath context + let path = contextPath context + autogen = path -/- "build/autogen" srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - fmap catMaybes $ findModuleFiles dirs modules + catMaybes <$> findModuleFiles (autogen : dirs) modules haskellModuleFiles :: Context -> Action ([FilePath], [String]) haskellModuleFiles context @ Context {..} = do @@ -28,19 +29,23 @@ haskellModuleFiles context @ Context {..} = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - foundSrcDirs <- findModuleFiles dirs modules - foundAutogen <- findModuleFiles [autogen] modules - found <- sequence $ zipWith3 addSources modules foundSrcDirs foundAutogen - + found <- findModuleFiles (autogen : dirs) modules let missingMods = map fst . filter (isNothing . snd) $ zip modules found otherFileToMod = replaceEq '/' '.' . dropExtension . dropPkgPath (haskellFiles, otherFiles) = partition ("//*hs" ?==) $ catMaybes found - return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) - where - addSources _ Nothing r = return r - addSources _ l Nothing = return l - addSources m (Just f1) (Just f2) = errorMultipleSources m f1 f2 + +-- | Find all Haskell source files for the current context +haskellSources :: Context -> Action [FilePath] +haskellSources context = do + let buildPath = contextPath context -/- "build" + autogen = buildPath -/- "autogen" + (found, missingMods) <- haskellModuleFiles context + -- Generated source files live in buildPath and have extension "hs"... + let generated = [ buildPath -/- (replaceEq '.' '/' m) <.> "hs" | m <- missingMods ] + -- ...except that GHC/Prim.hs lives in autogen. TODO: fix the inconsistency? + fixGhcPrim = replaceEq (buildPath -/- "GHC/Prim.hs") (autogen -/- "GHC/Prim.hs") + return $ found ++ fixGhcPrim generated -- | This is an important oracle whose role is to find and cache module source -- files. More specifically, it takes a list of directories @dirs@ and a sorted diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 16d2c0e..04cffc2 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -5,6 +5,7 @@ import Development.Shake.Util (parseMakefile) import Base import Context import Expression +import Oracles.ModuleFiles import Oracles.PackageData import Rules.Actions import Settings @@ -27,7 +28,7 @@ buildPackageDependencies rs context @ Context {..} = build $ Target context (GccM stage) [srcFile] [out] hDepFile %> \out -> do - srcs <- interpretInContext context getPackageSources + srcs <- haskellSources context need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 4e96571..b9407bc 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -4,6 +4,7 @@ import Base import Context import Expression import GHC +import Oracles.ModuleFiles import Oracles.PackageData import Rules.Actions import Settings @@ -21,7 +22,7 @@ buildPackageDocumentation context @ Context {..} = haddockFile = pkgHaddockFile context in when (stage == Stage1) $ do haddockFile %> \file -> do - srcs <- interpretInContext context getPackageSources + srcs <- haskellSources context deps <- map PackageName <$> interpretInContext context (getPkgDataList DepNames) let haddocks = [ pkgHaddockFile $ vanillaContext Stage1 depPkg | Just depPkg <- map findKnownPackage deps diff --git a/src/Settings.hs b/src/Settings.hs index e134fbc..9f52026 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -4,12 +4,11 @@ module Settings ( module Settings.User, module Settings.Ways, getPkgData, getPkgDataList, getTopDirectory, isLibrary, - getPackagePath, getContextDirectory, getContextPath, getPackageSources + getPackagePath, getContextDirectory, getContextPath ) where import Base import Expression -import Oracles.ModuleFiles import Oracles.PackageData import Oracles.WindowsPath import Settings.Packages @@ -34,16 +33,3 @@ getPkgDataList key = lift . pkgDataList . key =<< getContextPath getTopDirectory :: Expr FilePath getTopDirectory = lift topDirectory - --- | Find all Haskell source files for the current target -getPackageSources :: Expr [FilePath] -getPackageSources = do - context <- getContext - let buildPath = contextPath context -/- "build" - autogen = buildPath -/- "autogen" - (found, missingMods) <- lift $ haskellModuleFiles context - -- Generated source files live in buildPath and have extension "hs"... - let generated = [ buildPath -/- (replaceEq '.' '/' m) <.> "hs" | m <- missingMods ] - -- ...except that GHC/Prim.hs lives in autogen. TODO: fix the inconsistency? - fixGhcPrim = replaceEq (buildPath -/- "GHC/Prim.hs") (autogen -/- "GHC/Prim.hs") - return $ found ++ fixGhcPrim generated From git at git.haskell.org Fri Oct 27 00:22:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move generated includes to build directory (f2cff6f) Message-ID: <20171027002253.A14A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f2cff6f69f43c83c33f53971c96e770a68030ca5/ghc >--------------------------------------------------------------- commit f2cff6f69f43c83c33f53971c96e770a68030ca5 Author: Andrey Mokhov Date: Mon Oct 3 00:47:32 2016 +0900 Move generated includes to build directory See #113. >--------------------------------------------------------------- f2cff6f69f43c83c33f53971c96e770a68030ca5 src/Rules/Clean.hs | 4 +--- src/Rules/Data.hs | 7 ++---- src/Rules/Generate.hs | 20 +++++++--------- src/Settings/Builders/Cc.hs | 24 +++++++------------ src/Settings/Builders/Common.hs | 13 ++++------- src/Settings/Builders/DeriveConstants.hs | 21 ++++++++--------- src/Settings/Builders/GhcCabal.hs | 40 +++++++++++++++----------------- src/Settings/Builders/HsCpp.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 7 +++--- src/Settings/Packages/IntegerGmp.hs | 3 +-- src/Settings/Packages/Rts.hs | 8 +++---- src/Settings/Paths.hs | 5 +++- 12 files changed, 66 insertions(+), 90 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 f2cff6f69f43c83c33f53971c96e770a68030ca5 From git at git.haskell.org Fri Oct 27 00:22:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy libffi into place (6d36942) Message-ID: <20171027002254.75FBF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d369421eee990adb0f97e087dfc357fd7093262/ghc >--------------------------------------------------------------- commit 6d369421eee990adb0f97e087dfc357fd7093262 Author: Moritz Angermann Date: Mon Jan 4 20:27:15 2016 +0800 Copy libffi into place rts needs libffi as libCff in rts/stage1/build. This fixes #89 >--------------------------------------------------------------- 6d369421eee990adb0f97e087dfc357fd7093262 src/Rules/Copy.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index 3f33d9c..bcd1f1e 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -21,7 +21,9 @@ copyRules = do when (length ffiHPaths /= 1) $ putError $ "copyRules: exactly one ffi.h header expected" ++ "(found: " ++ show ffiHPaths ++ ")." + copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih + copyFile libffiLibrary (targetPath Stage1 rts -/- "build" -/- "libCffi.a") "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath From git at git.haskell.org Fri Oct 27 00:22:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependencies. (41778b0) Message-ID: <20171027002256.D6D613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/41778b07cc7fbbb8fa0006343213a65d2c12afaf/ghc >--------------------------------------------------------------- commit 41778b07cc7fbbb8fa0006343213a65d2c12afaf Author: Andrey Mokhov Date: Fri Feb 26 00:46:11 2016 +0000 Add missing dependencies. >--------------------------------------------------------------- 41778b07cc7fbbb8fa0006343213a65d2c12afaf src/Rules/Data.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 360eb5a..1eca7d9 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -57,6 +57,7 @@ buildPackageData context @ Context {..} = do -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps priority 2.0 $ do when (package == hp2ps) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package includes <- interpretInContext context $ fromDiffExpr includesArgs let prefix = fixKey (contextPath context) ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" @@ -73,6 +74,7 @@ buildPackageData context @ Context {..} = do putSuccess $ "| Successfully generated '" ++ mk ++ "'." when (package == unlit) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package let prefix = fixKey (contextPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = unlit" @@ -82,6 +84,7 @@ buildPackageData context @ Context {..} = do putSuccess $ "| Successfully generated '" ++ mk ++ "'." when (package == touchy) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package let prefix = fixKey (contextPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = touchy" @@ -93,6 +96,7 @@ buildPackageData context @ Context {..} = do -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. when (package == ghcCabal && stage == Stage0) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package let prefix = fixKey (contextPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = ghc-cabal" From git at git.haskell.org Fri Oct 27 00:22:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop TODOs (456a10b) Message-ID: <20171027002257.3F8093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/456a10bc8d12b8b2ac17c28279f35f5b675702d8/ghc >--------------------------------------------------------------- commit 456a10bc8d12b8b2ac17c28279f35f5b675702d8 Author: Andrey Mokhov Date: Mon Oct 3 01:21:11 2016 +0900 Drop TODOs See #113 >--------------------------------------------------------------- 456a10bc8d12b8b2ac17c28279f35f5b675702d8 src/Rules/Generate.hs | 1 - src/Rules/Library.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 1 - 3 files changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index d7068cf..266141f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -40,7 +40,6 @@ primopsTxt stage = buildPath (vanillaContext stage compiler) -/- "primops.txt" platformH :: Stage -> FilePath platformH stage = buildPath (vanillaContext stage compiler) -/- "ghc_boot_platform.h" --- TODO: move generated files to buildRootPath, see #113 includesDependencies :: [FilePath] includesDependencies = fmap (generatedPath -/-) [ "ghcautoconf.h" diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index c2d56b4..00a6be2 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -97,6 +97,6 @@ hSources context = do extraObjects :: Context -> Action [FilePath] extraObjects context | context == gmpContext = do - need [gmpLibraryH] -- TODO: Move this dependency elsewhere, #113? + need [gmpLibraryH] map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 7de3846..93ab4ed 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -6,7 +6,6 @@ import Oracles.Config.Setting import Predicate import Settings.Paths --- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" -- libraries/integer-gmp_CONFIGURE_OPTS += --with-gmp-framework-preferred From git at git.haskell.org Fri Oct 27 00:23:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Integer Gmp Library to IntegerGmp (a228d2b) Message-ID: <20171027002301.BAD733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a228d2b44c75b4899f12a3700b98f181e3b408ec/ghc >--------------------------------------------------------------- commit a228d2b44c75b4899f12a3700b98f181e3b408ec Author: Moritz Angermann Date: Mon Jan 4 21:05:42 2016 +0800 Adds Integer Gmp Library to IntegerGmp This should fix #88 >--------------------------------------------------------------- a228d2b44c75b4899f12a3700b98f181e3b408ec src/Rules/Dependencies.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index d604488..3a3c49a 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -2,9 +2,11 @@ module Rules.Dependencies (buildPackageDependencies) where import Base import Expression +import GHC import Oracles import Rules.Actions import Rules.Generate +import Rules.IntegerGmp import Rules.Resources import Settings import Development.Shake.Util (parseMakefile) @@ -17,6 +19,9 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = hDepFile = buildPath -/- ".hs-dependencies" in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do + -- integerGmp (cbits/wrappers.c) depends on the integerGmp library, + -- which provides gmp.h + when (pkg == integerGmp) $ need [integerGmpLibraryH] let srcFile = dropBuild . dropExtension $ out orderOnly $ generatedDependencies stage pkg need [srcFile] From git at git.haskell.org Fri Oct 27 00:23:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix generated includes (c6cb106) Message-ID: <20171027002300.C571C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6cb106cf0d437ff1352b95b57224d6a2c2a4744/ghc >--------------------------------------------------------------- commit c6cb106cf0d437ff1352b95b57224d6a2c2a4744 Author: Andrey Mokhov Date: Mon Oct 3 04:58:54 2016 +0900 Fix generated includes See #113. >--------------------------------------------------------------- c6cb106cf0d437ff1352b95b57224d6a2c2a4744 src/Rules/Generate.hs | 4 ++++ src/Settings/Builders/Common.hs | 2 ++ src/Settings/Builders/DeriveConstants.hs | 2 ++ src/Settings/Builders/Ghc.hs | 2 ++ src/Settings/Builders/GhcCabal.hs | 4 +++- src/Settings/Packages/Compiler.hs | 4 +--- src/Settings/Packages/Rts.hs | 3 +-- 7 files changed, 15 insertions(+), 6 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 266141f..035318f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -45,6 +45,8 @@ includesDependencies = fmap (generatedPath -/-) [ "ghcautoconf.h" , "ghcplatform.h" , "ghcversion.h" ] + ++ -- TODO: This is a temporary fix, see #113: + [ "includes/ghcversion.h"] ghcPrimDependencies :: Expr [FilePath] ghcPrimDependencies = do @@ -165,6 +167,8 @@ copyRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs rtsBuildPath -/- "sm/Evac_thr.c" %> copyFile (pkgPath rts -/- "sm/Evac.c") rtsBuildPath -/- "sm/Scav_thr.c" %> copyFile (pkgPath rts -/- "sm/Scav.c") + -- TODO: This is a temporary fix, see #113: + "includes/ghcversion.h" <~ generatedPath where file <~ dir = file %> copyFile (dir -/- takeFileName file) diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 49e5f30..698b343 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -9,6 +9,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.PackageData import Settings +import Settings.Paths import UserSettings cIncludeArgs :: Args @@ -18,6 +19,7 @@ cIncludeArgs = do incDirs <- getPkgDataList IncludeDirs depDirs <- getPkgDataList DepIncludeDirs mconcat [ arg "-Iincludes" + , arg $ "-I" ++ generatedPath , arg $ "-I" ++ path , arg $ "-I" ++ path -/- "autogen" , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 9cfd9dd..621a225 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -5,6 +5,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Predicate import Settings.Builders.Common +import Settings.Paths -- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? deriveConstantsBuilderArgs :: Args @@ -34,5 +35,6 @@ includeCcArgs = mconcat , flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER" , arg "-Irts" , arg "-Iincludes" + , arg $ "-I" ++ generatedPath , notM ghcWithSMP ? arg "-DNOSMP" , arg "-fcommon" ] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index d2cd761..475c9b3 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -135,6 +135,8 @@ includeGhcArgs = do , arg $ "-i" ++ path -/- "autogen" , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] , cIncludeArgs + , arg $ "-I" ++ generatedPath + , arg $ "-optc-I" ++ generatedPath , arg "-optP-include" , arg $ "-optP" ++ path -/- "autogen/cabal_macros.h" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 7a3b3a0..14c1254 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -64,10 +64,12 @@ libraryArgs = do -- TODO: WARNING: unrecognized options: --with-compiler, --with-gmp-libraries, --with-cc configureArgs :: Args configureArgs = do + top <- getTopDirectory let conf key = appendSubD $ "--configure-option=" ++ key cFlags = mconcat [ cArgs , remove ["-Werror"] - , argStagedSettingList ConfCcArgs ] + , argStagedSettingList ConfCcArgs + , arg $ "-I" ++ top -/- generatedPath ] ldFlags = ldArgs <> (argStagedSettingList ConfGccLinkerArgs) cppFlags = cppArgs <> (argStagedSettingList ConfCppArgs) mconcat diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 1866a1b..df9020d 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -16,9 +16,7 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder Ghc ? mconcat - [ arg $ "-I" ++ path - , arg $ "-optP-I" ++ generatedPath ] + , builder Ghc ? arg ("-I" ++ path) , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index a4ed2a1..f3f2e43 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -9,7 +9,6 @@ import Oracles.Config.Setting import Oracles.WindowsPath import Predicate import Settings -import Settings.Paths rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" @@ -92,7 +91,7 @@ rtsPackageArgs = package rts ? do , input "//Evac_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] , input "//Scav_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] ] - , builder Ghc ? arg "-Irts" <> arg ("-I" ++ generatedPath) + , builder Ghc ? arg "-Irts" , builder (GhcPkg Stage1) ? mconcat [ remove ["rts/stage1/inplace-pkg-config"] -- TODO: fix, see #113 From git at git.haskell.org Fri Oct 27 00:23:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (d396ba3) Message-ID: <20171027002300.615123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d396ba3d8f4d2ce6e15d3149404fbb94118bddc3/ghc >--------------------------------------------------------------- commit d396ba3d8f4d2ce6e15d3149404fbb94118bddc3 Author: Andrey Mokhov Date: Fri Feb 26 01:54:51 2016 +0000 Minor revision. >--------------------------------------------------------------- d396ba3d8f4d2ce6e15d3149404fbb94118bddc3 src/Oracles/Dependencies.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index b34535b..aa54d86 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,10 +1,11 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.Dependencies (dependencies, dependenciesOracle) where -import Base import Control.Monad.Trans.Maybe import qualified Data.HashMap.Strict as Map +import Base + newtype DependenciesKey = DependenciesKey (FilePath, FilePath) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -28,10 +29,9 @@ dependencies path obj = do -- Oracle for 'path/dist/.dependencies' files dependenciesOracle :: Rules () -dependenciesOracle = do +dependenciesOracle = void $ do deps <- newCache $ \file -> do putOracle $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return . Map.fromList $ map (\(x:xs) -> (x, xs)) contents - _ <- addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file - return () + addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file From git at git.haskell.org Fri Oct 27 00:22:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:22:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds integerGmpLibraryH to Rules.IntegerGmp (d40050f) Message-ID: <20171027002258.304583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d40050fb1554db54db683f7d26a55bc3fb0868df/ghc >--------------------------------------------------------------- commit d40050fb1554db54db683f7d26a55bc3fb0868df Author: Moritz Angermann Date: Mon Jan 4 20:50:58 2016 +0800 Adds integerGmpLibraryH to Rules.IntegerGmp This is, so we can use integerGmpLibraryH, without having to use the path outside of the Rules.IntegerGmp module. >--------------------------------------------------------------- d40050fb1554db54db683f7d26a55bc3fb0868df src/Rules/IntegerGmp.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 4e19b9d..f927102 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,4 +1,4 @@ -module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where +module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary, integerGmpLibraryH) where import Base import Expression @@ -16,6 +16,9 @@ integerGmpBuild = integerGmpBase -/- "gmpbuild" integerGmpLibrary :: FilePath integerGmpLibrary = integerGmpBase -/- "libgmp.a" +integerGmpLibraryH :: FilePath +integerGmpLibraryH = integerGmpBase -/- "gmp.h" + -- relative to integerGmpBuild integerGmpPatch :: FilePath integerGmpPatch = ".." -/- "tarball" -/- "gmp-5.0.4.patch" @@ -103,4 +106,4 @@ integerGmpRules = do putSuccess "| Successfully built custom library 'integer-gmp'" - "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary] + integerGmpLibraryH %> \_ -> need [integerGmpLibrary] From git at git.haskell.org Fri Oct 27 00:23:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add findGenerator, refactor Oracles.ModuleFiles. (79858ef) Message-ID: <20171027002304.599313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79858ef2f73d7444b74cac12680dfc234fbacda9/ghc >--------------------------------------------------------------- commit 79858ef2f73d7444b74cac12680dfc234fbacda9 Author: Andrey Mokhov Date: Fri Feb 26 02:25:44 2016 +0000 Add findGenerator, refactor Oracles.ModuleFiles. See #210. >--------------------------------------------------------------- 79858ef2f73d7444b74cac12680dfc234fbacda9 src/Oracles/ModuleFiles.hs | 94 +++++++++++++++++++++++++++------------------- src/Rules/Generate.hs | 25 ++---------- 2 files changed, 60 insertions(+), 59 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 79858ef2f73d7444b74cac12680dfc234fbacda9 From git at git.haskell.org Fri Oct 27 00:23:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to ghcversion.h header (0ff86b4) Message-ID: <20171027002304.B639C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ff86b4b7071cead9d50310090c86d4a18c068fa/ghc >--------------------------------------------------------------- commit 0ff86b4b7071cead9d50310090c86d4a18c068fa Author: Andrey Mokhov Date: Mon Oct 3 05:52:00 2016 +0900 Fix path to ghcversion.h header See #113. >--------------------------------------------------------------- 0ff86b4b7071cead9d50310090c86d4a18c068fa src/Rules/Generate.hs | 4 ---- src/Rules/Register.hs | 3 ++- 2 files changed, 2 insertions(+), 5 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 035318f..266141f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -45,8 +45,6 @@ includesDependencies = fmap (generatedPath -/-) [ "ghcautoconf.h" , "ghcplatform.h" , "ghcversion.h" ] - ++ -- TODO: This is a temporary fix, see #113: - [ "includes/ghcversion.h"] ghcPrimDependencies :: Expr [FilePath] ghcPrimDependencies = do @@ -167,8 +165,6 @@ copyRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs rtsBuildPath -/- "sm/Evac_thr.c" %> copyFile (pkgPath rts -/- "sm/Evac.c") rtsBuildPath -/- "sm/Scav_thr.c" %> copyFile (pkgPath rts -/- "sm/Scav.c") - -- TODO: This is a temporary fix, see #113: - "includes/ghcversion.h" <~ generatedPath where file <~ dir = file %> copyFile (dir -/- takeFileName file) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index ec33668..272e27b 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -46,7 +46,8 @@ registerPackage rs context at Context {..} = do let fixRtsConf = unlines . map ( replace "\"\"" "" - . replace "rts/dist/build" rtsBuildPath ) + . replace "rts/dist/build" rtsBuildPath + . replace "includes/dist-derivedconstants/header" generatedPath ) . filter (not . null) . lines From git at git.haskell.org Fri Oct 27 00:23:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop SUPPORTS_COMPONENT_ID which is no longer provided by configure. (72ed36f) Message-ID: <20171027002305.877913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72ed36f9bfb99fc239d84026945e2b47446005ed/ghc >--------------------------------------------------------------- commit 72ed36f9bfb99fc239d84026945e2b47446005ed Author: Andrey Mokhov Date: Mon Jan 4 13:14:51 2016 +0000 Drop SUPPORTS_COMPONENT_ID which is no longer provided by configure. >--------------------------------------------------------------- 72ed36f9bfb99fc239d84026945e2b47446005ed cfg/system.config.in | 1 - src/Oracles/Config/Flag.hs | 2 -- src/Settings/Builders/Ghc.hs | 13 ++++--------- 3 files changed, 4 insertions(+), 12 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 7f9b8de..292d91f 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -53,7 +53,6 @@ cc-clang-backend = @CC_CLANG_BACKEND@ # Build options: #=============== -supports-component-id = @SUPPORTS_COMPONENT_ID@ solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index d40b762..44e8a17 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -18,7 +18,6 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken - | SupportsComponentId | WithLibdw -- Note, if a flag is set to empty string we treat it as set to NO. This seems @@ -34,7 +33,6 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" - SupportsComponentId -> "supports-component-id" WithLibdw -> "with-libdw" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a0f2678..9a07fc2 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -84,19 +84,14 @@ wayGhcArgs = do -- TODO: Improve handling of "-hide-all-packages" packageGhcArgs :: Args packageGhcArgs = do - stage <- getStage - pkg <- getPackage - supportsComponentId <- getFlag SupportsComponentId - compId <- getPkgData ComponentId - pkgDepIds <- getPkgDataList DepIds + pkg <- getPackage + compId <- getPkgData ComponentId + pkgDepIds <- getPkgDataList DepIds mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" , bootPackageDbArgs - , isLibrary pkg ? - if supportsComponentId || stage /= Stage0 - then arg $ "-this-package-key " ++ compId - else arg $ "-package-name " ++ compId + , isLibrary pkg ? (arg $ "-this-package-key " ++ compId) , append $ map ("-package-id " ++) pkgDepIds ] -- TODO: Improve handling of "cabal_macros.h" From git at git.haskell.org Fri Oct 27 00:23:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop testModuleFilesOracle. (50663a4) Message-ID: <20171027002308.029B53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/50663a4d4e5a04653e4a30034e688bf1dbd549ec/ghc >--------------------------------------------------------------- commit 50663a4d4e5a04653e4a30034e688bf1dbd549ec Author: Andrey Mokhov Date: Fri Feb 26 03:36:31 2016 +0000 Drop testModuleFilesOracle. See #210. >--------------------------------------------------------------- 50663a4d4e5a04653e4a30034e688bf1dbd549ec src/Rules/Selftest.hs | 13 ------------- 1 file changed, 13 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f4890b0..f549b0f 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,7 +6,6 @@ import Development.Shake import Test.QuickCheck import Base -import Oracles.ModuleFiles import Settings.Builders.Ar (chunksOfSize) import Way @@ -27,7 +26,6 @@ selftestRules = testMatchVersionedFilePath testModuleNames testLookupAll - testModuleFilesOracle testWays :: Action () testWays = do @@ -85,14 +83,3 @@ testLookupAll = do dicts = nubBy ((==) `on` fst) <$> vector 20 extras :: Gen [Int] extras = vector 20 - -testModuleFilesOracle :: Action () -testModuleFilesOracle = do - putBuild $ "==== moduleFilesOracle" - result <- findModuleFiles ["compiler/codeGen", "compiler/parser"] - [ "CodeGen.Platform.ARM" - , "Lexer" - , "Missing.Module"] - test $ result == [ Just "compiler/codeGen/CodeGen/Platform/ARM.hs" - , Just "compiler/parser/Lexer.x" - , Nothing] From git at git.haskell.org Fri Oct 27 00:23:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass configure Cc and Cpp options to GHC (79575b3) Message-ID: <20171027002308.AD5053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79575b395e32de2ad6dec3bf4e11d30767779ee6/ghc >--------------------------------------------------------------- commit 79575b395e32de2ad6dec3bf4e11d30767779ee6 Author: Andrey Mokhov Date: Sun Oct 2 23:30:15 2016 +0100 Pass configure Cc and Cpp options to GHC >--------------------------------------------------------------- 79575b395e32de2ad6dec3bf4e11d30767779ee6 src/Settings/Builders/Ghc.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 475c9b3..6eaf8ae 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -78,7 +78,8 @@ commonGhcArgs :: Args commonGhcArgs = do way <- getWay path <- getBuildPath - hsArgs <- getPkgDataList HsArgs + confCc <- getSettingList . ConfCcArgs =<< getStage + confCpp <- getSettingList . ConfCppArgs =<< getStage cppArgs <- getPkgDataList CppArgs mconcat [ arg "-hisuf", arg $ hisuf way , arg "-osuf" , arg $ osuf way @@ -86,7 +87,9 @@ commonGhcArgs = do , wayGhcArgs , packageGhcArgs , includeGhcArgs - , append hsArgs + , append =<< getPkgDataList HsArgs + , append $ map ("-optc" ++) confCc + , append $ map ("-optP" ++) confCpp , append $ map ("-optP" ++) cppArgs , arg "-odir" , arg path , arg "-hidir" , arg path From git at git.haskell.org Fri Oct 27 00:23:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #91 from angerman/feature/div (bee905c) Message-ID: <20171027002309.27F653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bee905cfbb2d0fcc048b2c7837ef307e6447acae/ghc >--------------------------------------------------------------- commit bee905cfbb2d0fcc048b2c7837ef307e6447acae Merge: 72ed36f a228d2b Author: Andrey Mokhov Date: Mon Jan 4 13:31:32 2016 +0000 Merge pull request #91 from angerman/feature/div Feature/div >--------------------------------------------------------------- bee905cfbb2d0fcc048b2c7837ef307e6447acae src/Rules/Copy.hs | 2 ++ src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 5 +++++ src/Rules/IntegerGmp.hs | 7 +++++-- 4 files changed, 13 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:23:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Context as key to moduleFilesOracle. (1fd2368) Message-ID: <20171027002311.D26D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fd23681fe3f63fcdff82ab7b1d65eeedf5227aa/ghc >--------------------------------------------------------------- commit 1fd23681fe3f63fcdff82ab7b1d65eeedf5227aa Author: Andrey Mokhov Date: Fri Feb 26 03:37:22 2016 +0000 Use Context as key to moduleFilesOracle. See #210. >--------------------------------------------------------------- 1fd23681fe3f63fcdff82ab7b1d65eeedf5227aa src/Oracles/ModuleFiles.hs | 42 ++++++++++++++++++------------------------ 1 file changed, 18 insertions(+), 24 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 73ec6eb..630a05f 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,6 +1,6 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, LambdaCase #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.ModuleFiles ( - findGenerator, haskellSources, moduleFilesOracle, findModuleFiles + findGenerator, haskellSources, moduleFilesOracle ) where import qualified Data.HashMap.Strict as Map @@ -11,7 +11,7 @@ import Expression import Oracles.PackageData import Settings.Paths -newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) +newtype ModuleFilesKey = ModuleFilesKey Context deriving (Show, Typeable, Eq, Hashable, Binary, NFData) newtype Generator = Generator (Context, FilePath) @@ -55,32 +55,29 @@ generatedFile context moduleName = contextFiles :: Context -> Action [(String, Maybe FilePath)] contextFiles context @ Context {..} = do let path = contextPath context - srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - zip modules <$> findModuleFiles (path -/- "build/autogen" : dirs) modules + zip modules <$> askOracle (ModuleFilesKey context) -- | This is an important oracle whose role is to find and cache module source --- files. More specifically, it takes a list of directories @dirs@ and a sorted --- list of module names @modules@ as arguments, and for each module, e.g. +-- files. It takes a 'Context', looks up corresponding source directories @dirs@ +-- and sorted list of module names @modules@, and for each module, e.g. -- @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, such that -- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or 'Nothing' -- if there is no such file. If more than one matching file is found an error is --- raised. For example, for the 'compiler' package given --- @dirs = ["compiler/codeGen", "compiler/parser"]@, and --- @modules = ["CodeGen.Platform.ARM", "Lexer", "Missing.Module"]@, it produces --- @[Just "compiler/codeGen/CodeGen/Platform/ARM.hs", --- Just "compiler/parser/Lexer.x", Nothing]@. -findModuleFiles :: [FilePath] -> [String] -> Action [Maybe FilePath] -findModuleFiles dirs modules = askOracle $ ModuleFilesKey (dirs, modules) - +-- raised. For example, for @Context Stage1 compiler vanilla@, @dirs@ will +-- contain ["compiler/codeGen", "compiler/parser"], and @modules@ will contain +-- ["CodeGen.Platform.ARM", "Config", "Lexer"]; the oracle will produce a list +-- containing [Just "compiler/codeGen/CodeGen/Platform/ARM.hs", Nothing, +-- Just "compiler/parser/Lexer.x"]. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do - void $ addOracle $ \(ModuleFilesKey (dirs, modules)) -> do - let decodedPairs = map decodeModule modules - modDirFiles = map (bimap head id . unzip) - . groupBy ((==) `on` fst) $ decodedPairs - + void $ addOracle $ \(ModuleFilesKey context) -> do + let path = contextPath context + autogen = path -/- "build/autogen" + srcDirs <- pkgDataList $ SrcDirs path + modules <- fmap sort . pkgDataList $ Modules path + let dirs = autogen : map (pkgPath (package context) -/-) srcDirs + modDirFiles = groupSort $ map decodeModule modules result <- fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do @@ -90,15 +87,12 @@ moduleFilesOracle = void $ do cmp fe f = compare (dropExtension fe) f found = intersectOrd cmp noBoot mFiles return (map (fullDir -/-) found, mDir) - let pairs = sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ] - unless (null multi) $ do let (m, f1, f2) = head multi putError $ "Module " ++ m ++ " has more than one source file: " ++ f1 ++ " and " ++ f2 ++ "." - return $ lookupAll modules pairs gens <- newCache $ \context -> do From git at git.haskell.org Fri Oct 27 00:23:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to Cabal library changes (10154e7) Message-ID: <20171027002312.5D9B73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/10154e73137208ba1808c4b19a9e507e0943de8f/ghc >--------------------------------------------------------------- commit 10154e73137208ba1808c4b19a9e507e0943de8f Author: Andrey Mokhov Date: Mon Oct 3 09:30:05 2016 +0100 Adapt to Cabal library changes >--------------------------------------------------------------- 10154e73137208ba1808c4b19a9e507e0943de8f src/Rules/Cabal.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index ed72f93..e12ab33 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,10 +1,11 @@ module Rules.Cabal (cabalRules) where -import Data.Version import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse +import Distribution.Text import Distribution.Verbosity +import Text.PrettyPrint import Base import Expression @@ -22,9 +23,8 @@ cabalRules = do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg let identifier = package . packageDescription $ pd - version = showVersion . pkgVersion $ identifier - DP.PackageName name = DP.pkgName identifier - return $ name ++ " == " ++ version + version = render . disp . pkgVersion $ identifier + return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version writeFileChanged out . unlines $ constraints -- Cache package dependencies. @@ -38,7 +38,7 @@ cabalRules = do let depsLib = collectDeps $ condLibrary pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes - depNames = [ name | Dependency (DP.PackageName name) _ <- deps ] + depNames = [ unPackageName name | Dependency name _ <- deps ] return . unwords $ pkgNameString pkg : sort depNames writeFileChanged out . unlines $ pkgDeps From git at git.haskell.org Fri Oct 27 00:23:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make output boxes prettier by closing them on the right (8235f15) Message-ID: <20171027002312.EC3F73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8235f157b7dc6debca50cce96905ab3327b6fee1/ghc >--------------------------------------------------------------- commit 8235f157b7dc6debca50cce96905ab3327b6fee1 Author: David Luposchainsky Date: Mon Jan 4 14:38:07 2016 +0100 Make output boxes prettier by closing them on the right >--------------------------------------------------------------- 8235f157b7dc6debca50cce96905ab3327b6fee1 src/Base.hs | 42 ++++++++++++++++++++++++++++++------------ 1 file changed, 30 insertions(+), 12 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 8733282..69904c4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -172,23 +172,41 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg --- | Render the given set of lines in a ASCII box +-- | Render the given set of lines in a nice box of ASCII renderBox :: [String] -> String -renderBox ls = - unlines ([begin] ++ map (bar++) ls) ++ end +renderBox ls = concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) where - (begin,bar,end) - | useUnicode = ( "╭──────────" - , "│ " - , "╰──────────" - ) - | otherwise = ( "/----------" - , "| " - , "\\----------" - ) + -- Minimum total width of the box in characters + minimumBoxWidth = 32 + -- FIXME: See Shake #364. useUnicode = False + -- Characters to draw the box + (dash, pipe, topLeft, topRight, botLeft, botRight, padding) + | useUnicode = ('─', '│', '╭', '╮', '╰', '╯', ' ') + | otherwise = ('-', '|', '/', '\\', '\\', '/', ' ') + + -- Box width, taking minimum desired length and content into account. + -- The -4 is for the beginning and end pipe/padding symbols, as + -- in "| xxx |". + boxContentWidth = (minimumBoxWidth - 4) `max` maxContentLength + where + maxContentLength = maximum (map length ls) + + renderLine l = concat + [ [pipe, padding] + , padToLengthWith boxContentWidth padding l + , [padding, pipe] ] + where + padToLengthWith n filler x = x ++ replicate (n - length x) filler + + (boxTop, boxBot) = ( topLeft : dashes ++ [topRight] + , botLeft : dashes ++ [botRight] ) + where + -- +1 for each non-dash (= corner) char + dashes = replicate (boxContentWidth + 2) dash + -- Depending on Data.Bifunctor only for this function seems an overkill bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) From git at git.haskell.org Fri Oct 27 00:23:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (9171856) Message-ID: <20171027002316.2C0C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9171856f647213aea42005a8dfec9bff0ff7223c/ghc >--------------------------------------------------------------- commit 9171856f647213aea42005a8dfec9bff0ff7223c Author: Andrey Mokhov Date: Fri Feb 26 11:37:00 2016 +0000 Minor revision. See #210. >--------------------------------------------------------------- 9171856f647213aea42005a8dfec9bff0ff7223c src/Oracles/ModuleFiles.hs | 18 ++++++++++++------ 1 file changed, 12 insertions(+), 6 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 630a05f..508b554 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -34,7 +34,12 @@ determineBuilder file = case takeExtension file of -- ".build/stage1/base/build/Prelude.hs" -- == Nothing findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder)) -findGenerator context file = askOracle $ Generator (context, file) +findGenerator context file = do + maybeSource <- askOracle $ Generator (context, file) + return $ do + source <- maybeSource + builder <- determineBuilder source + return (source, builder) -- | Find all Haskell source files for a given 'Context'. haskellSources :: Context -> Action [FilePath] @@ -44,8 +49,9 @@ haskellSources context = do -- that GHC/Prim.hs lives in build/autogen/. TODO: fix the inconsistency? let modFile ("GHC.Prim", _) = autogen -/- "GHC/Prim.hs" modFile (m, Nothing ) = generatedFile context m - modFile (m, Just file ) | "//*hs" ?== file = file - | otherwise = modFile (m, Nothing) + modFile (m, Just file ) + | takeExtension file `elem` [".hs", ".lhs"] = file + | otherwise = generatedFile context m map modFile <$> contextFiles context generatedFile :: Context -> String -> FilePath @@ -53,7 +59,7 @@ generatedFile context moduleName = contextPath context -/- "build" -/- replaceEq '.' '/' moduleName <.> "hs" contextFiles :: Context -> Action [(String, Maybe FilePath)] -contextFiles context @ Context {..} = do +contextFiles context at Context {..} = do let path = contextPath context modules <- fmap sort . pkgDataList $ Modules path zip modules <$> askOracle (ModuleFilesKey context) @@ -97,8 +103,8 @@ moduleFilesOracle = void $ do gens <- newCache $ \context -> do files <- contextFiles context - return $ Map.fromList [ (generatedFile context modName, (src, builder)) + return $ Map.fromList [ (generatedFile context modName, src) | (modName, Just src) <- files - , let Just builder = determineBuilder src ] + , takeExtension src `notElem` [".hs", ".lhs"] ] addOracle $ \(Generator (context, file)) -> Map.lookup file <$> gens context From git at git.haskell.org Fri Oct 27 00:23:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #92 from quchen/closed-box (a2e9fb9) Message-ID: <20171027002316.D87593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2e9fb9ef1192b41f732797f444bd9ad33c5eaf3/ghc >--------------------------------------------------------------- commit a2e9fb9ef1192b41f732797f444bd9ad33c5eaf3 Merge: bee905c 8235f15 Author: Andrey Mokhov Date: Mon Jan 4 14:18:51 2016 +0000 Merge pull request #92 from quchen/closed-box Make output boxes prettier by closing them on the right >--------------------------------------------------------------- a2e9fb9ef1192b41f732797f444bd9ad33c5eaf3 src/Base.hs | 42 ++++++++++++++++++++++++++++++------------ 1 file changed, 30 insertions(+), 12 deletions(-) From git at git.haskell.org Fri Oct 27 00:23:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Text.PrettyPrint dependency (4afc5a4) Message-ID: <20171027002316.84F523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4afc5a4ddf3511bfefc3abcaa15144844536d8b6/ghc >--------------------------------------------------------------- commit 4afc5a4ddf3511bfefc3abcaa15144844536d8b6 Author: Andrey Mokhov Date: Mon Oct 3 09:45:34 2016 +0100 Drop Text.PrettyPrint dependency >--------------------------------------------------------------- 4afc5a4ddf3511bfefc3abcaa15144844536d8b6 src/Rules/Cabal.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index e12ab33..69cdd51 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -5,7 +5,6 @@ import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Text import Distribution.Verbosity -import Text.PrettyPrint import Base import Expression @@ -23,7 +22,7 @@ cabalRules = do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg let identifier = package . packageDescription $ pd - version = render . disp . pkgVersion $ identifier + version = display . pkgVersion $ identifier return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version writeFileChanged out . unlines $ constraints From git at git.haskell.org Fri Oct 27 00:23:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on how to install Happy/Alex better (2d02668) Message-ID: <20171027002357.C899B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d0266864b16b273b7e6d296a42fa60bf75d9bd0/ghc >--------------------------------------------------------------- commit 2d0266864b16b273b7e6d296a42fa60bf75d9bd0 Author: Neil Mitchell Date: Thu Mar 3 23:18:44 2016 +0000 Add a note on how to install Happy/Alex better >--------------------------------------------------------------- 2d0266864b16b273b7e6d296a42fa60bf75d9bd0 doc/windows.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/windows.md b/doc/windows.md index 2d823e7..aa7a560 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -23,4 +23,4 @@ Here are some alternatives that have been considered, but not yet tested. Use th * Use `shake-build/build.bat --setup` to replace `boot` and `configure`. * The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. -* Can Happy/Alex be installed by adding them as tool dependencies to the Stack file? +* Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:23:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:23:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Another tweak of generated dependencies. (ba41ec6) Message-ID: <20171027002359.C8EDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba41ec6a9b2db3708b1076fef2c4391d4887875d/ghc >--------------------------------------------------------------- commit ba41ec6a9b2db3708b1076fef2c4391d4887875d Author: Andrey Mokhov Date: Tue Jan 5 01:54:50 2016 +0000 Another tweak of generated dependencies. >--------------------------------------------------------------- ba41ec6a9b2db3708b1076fef2c4391d4887875d src/Rules/Generate.hs | 43 ++++++++++++++++++------------------------- 1 file changed, 18 insertions(+), 25 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 13d5806..6a4270b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -51,35 +51,28 @@ derivedConstantsDependencies = (derivedConstantsPath -/-) <$> compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = [ platformH stage ] - ++ - fmap ((targetPath stage compiler -/- "build") -/-) - [ "primop-vector-uniques.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" - , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] - ++ - if stage == Stage0 - then defaultDependencies ++ derivedConstantsDependencies - else [] - - --- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)? + ++ defaultDependencies ++ derivedConstantsDependencies + ++ fmap ((targetPath stage compiler -/- "build") -/-) + [ "primop-vector-uniques.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-tag.hs-incl" + , "primop-list.hs-incl" + , "primop-strictness.hs-incl" + , "primop-fixity.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys.hs-incl" ] + generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | stage == Stage0 = defaultDependencies - | stage == Stage1 = derivedConstantsDependencies | otherwise = [] -- The following generators and corresponding source extensions are supported: From git at git.haskell.org Fri Oct 27 00:24:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build mkUserGuidePart with stage-0 (a86f2b1) Message-ID: <20171027002401.0D5303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a86f2b1e97fb7fa0ef08327f083049a41b278513/ghc >--------------------------------------------------------------- commit a86f2b1e97fb7fa0ef08327f083049a41b278513 Author: Ben Gamari Date: Sat Oct 8 15:10:43 2016 -0400 Build mkUserGuidePart with stage-0 This addresses GHC #12619, allowing the users guide to be built with only the stage 0 compiler. >--------------------------------------------------------------- a86f2b1e97fb7fa0ef08327f083049a41b278513 src/Builder.hs | 1 + src/GHC.hs | 5 ++++- src/Settings/Default.hs | 4 ++-- 3 files changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 6f892f2..09b87cb 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -104,6 +104,7 @@ builderPath builder = case builderProvenance builder of Just context | Just path <- programPath context -> return path | otherwise -> + -- TODO: Make builderPath total. error $ "Cannot determine builderPath for " ++ show builder ++ " in context " ++ show context Nothing -> case builder of diff --git a/src/GHC.hs b/src/GHC.hs index 0bfd131..3521e54 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -102,7 +102,10 @@ ghcSplit = "inplace/lib/bin/ghc-split" programPath :: Context -> Maybe FilePath programPath context at Context {..} | package == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) - | package `elem` [checkApiAnnotations, ghcTags, haddock, mkUserGuidePart] = + | package `elem` [mkUserGuidePart] = + case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package + _ -> Nothing + | package `elem` [checkApiAnnotations, ghcTags, haddock] = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString package _ -> Nothing | package `elem` [touchy, unlit] = case stage of diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index e35fea0..4588c4b 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -108,7 +108,7 @@ packagesStage0 = mconcat , ghcPkg, hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode - , hp2ps, unlit ] + , hp2ps, unlit, mkUserGuidePart ] , stage0 ? windowsHost ? append [touchy] , notM windowsHost ? notM iosHost ? append [terminfo] ] @@ -127,7 +127,7 @@ packagesStage1 = mconcat -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages packagesStage2 = mconcat - [ append [checkApiAnnotations, ghcTags, mkUserGuidePart] + [ append [checkApiAnnotations, ghcTags ] , buildHaddock flavour ? append [haddock] ] -- TODO: What about profilingDynamic way? Do we need platformSupportsSharedLibs? From git at git.haskell.org Fri Oct 27 00:24:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #212 from ndmitchell/master (a5a37b9) Message-ID: <20171027002401.4535D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a37b93f8d6e4a521a3770bc0a4b8b6c8bc5fe4/ghc >--------------------------------------------------------------- commit a5a37b93f8d6e4a521a3770bc0a4b8b6c8bc5fe4 Merge: 7e7497a 2d02668 Author: Andrey Mokhov Date: Thu Mar 3 23:40:30 2016 +0000 Merge pull request #212 from ndmitchell/master Add docs for how to compile on Windows [skip ci] >--------------------------------------------------------------- a5a37b93f8d6e4a521a3770bc0a4b8b6c8bc5fe4 doc/windows.md | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) From git at git.haskell.org Fri Oct 27 00:24:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds derivedConstantsDependencies for rts (2565fc3) Message-ID: <20171027002403.600AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2565fc354a241ff9f6137c5202949a6f8f46bff9/ghc >--------------------------------------------------------------- commit 2565fc354a241ff9f6137c5202949a6f8f46bff9 Author: Moritz Angermann Date: Tue Jan 5 11:14:20 2016 +0800 Adds derivedConstantsDependencies for rts Building rts depends on derived constants, as we can not rely on the compiler to be build prior to rts, as we build rts with gcc, and hence do not depend on ghc, we need to have rts depend on the derived constants. This fixes #94. However, if we are going to build rts with the stage1 ghc, this should not be an issue anymore (see #90), as derived constants would be build then anyway. Yet I do not see any problem with explicilty noting down the derived constants dependency for rts. >--------------------------------------------------------------- 2565fc354a241ff9f6137c5202949a6f8f46bff9 src/Rules/Generate.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 6a4270b..65c0abf 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -72,6 +72,7 @@ compilerDependencies stage = generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage + | pkg == rts = derivedConstantsDependencies | stage == Stage0 = defaultDependencies | otherwise = [] From git at git.haskell.org Fri Oct 27 00:24:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #290 from bgamari/master (b7948dd) Message-ID: <20171027002404.A6D203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b7948dd53ed2fd905c2f9dda6d30ae5280c9fd6f/ghc >--------------------------------------------------------------- commit b7948dd53ed2fd905c2f9dda6d30ae5280c9fd6f Merge: d3d00b0 a86f2b1 Author: Andrey Mokhov Date: Mon Oct 10 00:27:14 2016 +0100 Merge pull request #290 from bgamari/master Build mkUserGuidePart with stage-0 >--------------------------------------------------------------- b7948dd53ed2fd905c2f9dda6d30ae5280c9fd6f src/Builder.hs | 8 ++++++-- src/GHC.hs | 5 ++++- src/Rules.hs | 8 +++++++- src/Settings/Default.hs | 4 ++-- 4 files changed, 19 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 00:24:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to Stack-based build instructions for Windows. (42bce9a) Message-ID: <20171027002404.D2BB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/42bce9aa45d72ad571223b3c23996177ca22cef1/ghc >--------------------------------------------------------------- commit 42bce9aa45d72ad571223b3c23996177ca22cef1 Author: Andrey Mokhov Date: Fri Mar 4 00:18:18 2016 +0000 Link to Stack-based build instructions for Windows. >--------------------------------------------------------------- 42bce9aa45d72ad571223b3c23996177ca22cef1 README.md | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 96b3106..aca17ea 100644 --- a/README.md +++ b/README.md @@ -41,7 +41,8 @@ system to be in the `shake-build` directory of the GHC source tree: * Build GHC using `shake-build/build.sh` or `shake-build/build.bat` (on Windows) instead of `make`. You might want to enable parallelism with `-j`. We will further refer to the build script simply as `build`. If you are interested in building in a Cabal sandbox -or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. +or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Also +see [instructions for building GHC on Windows using Stack][windows-build]. Using the build system ---------------------- @@ -133,6 +134,7 @@ helped me endure and enjoy the project. [issues]: https://github.com/snowleopard/shaking-up-ghc/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild +[windows-build]: https://github.com/snowleopard/shaking-up-ghc/blob/master/doc/windows.md [build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs From git at git.haskell.org Fri Oct 27 00:24:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds gmp.h to the integerGmp dependencies. (6fd807b) Message-ID: <20171027002406.C44363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6fd807ba05023634fb7f6082ef2369b9f7f90f6b/ghc >--------------------------------------------------------------- commit 6fd807ba05023634fb7f6082ef2369b9f7f90f6b Author: Moritz Angermann Date: Tue Jan 5 13:05:18 2016 +0800 Adds gmp.h to the integerGmp dependencies. Fix #88. is imported by libraries/integer-gmp/cbits/wrappers.c, hence the dependency generation with GccM, requires gmp.h to be available. We therefore add it to the generated dependencies. >--------------------------------------------------------------- 6fd807ba05023634fb7f6082ef2369b9f7f90f6b src/Rules/Generate.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 65c0abf..921c672 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -69,10 +69,15 @@ compilerDependencies stage = , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] +integerGmpDependencies :: [FilePath] +integerGmpDependencies = ((pkgPath integerGmp -/- "gmp") -/-) <$> + [ "gmp.h" ] -- identical to integerGmpLibraryH, but doesn't require the import. + generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == rts = derivedConstantsDependencies + | pkg == integerGmp = integerGmpDependencies | stage == Stage0 = defaultDependencies | otherwise = [] From git at git.haskell.org Fri Oct 27 00:24:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add links to Hadrian paper and talk (2a20ce5) Message-ID: <20171027002408.4BA5A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2a20ce5d54ddf43bebb63cee31e7fea363a931e5/ghc >--------------------------------------------------------------- commit 2a20ce5d54ddf43bebb63cee31e7fea363a931e5 Author: Andrey Mokhov Date: Sun Oct 16 00:37:26 2016 +0100 Add links to Hadrian paper and talk >--------------------------------------------------------------- 2a20ce5d54ddf43bebb63cee31e7fea363a931e5 README.md | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/README.md b/README.md index c39071e..01132cd 100644 --- a/README.md +++ b/README.md @@ -5,9 +5,9 @@ Hadrian Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current -[`make`-based build system][make]. If you are curious about the rationale and initial -ideas behind the project you can find more details on the [wiki page][ghc-shake-wiki] -and in this [blog post][blog-post-1]. This project was formerly known as *Shaking-up-GHC*. +[`make`-based build system][make]. If you are curious about the rationale behind the +project and the architecture of the new build system you can find more details in +this [Haskell Symposium 2016 paper][paper] and this [Haskell eXchange 2016 talk][talk]. The new build system can work side-by-side with the existing build system. Note, there is some interaction between them: they put (some) build results in the same directories, @@ -154,8 +154,8 @@ helped me endure and enjoy the project. [ghc]: https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler [shake]: https://github.com/ndmitchell/shake/blob/master/README.md [make]: https://ghc.haskell.org/trac/ghc/wiki/Building/Architecture -[ghc-shake-wiki]: https://ghc.haskell.org/trac/ghc/wiki/Building/Shake -[blog-post-1]: https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc +[paper]: https://www.staff.ncl.ac.uk/andrey.mokhov/Hadrian.pdf +[talk]: https://skillsmatter.com/skillscasts/8722-meet-hadrian-a-new-build-system-for-ghc [issues]: https://github.com/snowleopard/hadrian/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild From git at git.haskell.org Fri Oct 27 00:24:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (f1157df) Message-ID: <20171027002408.6A2153A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f1157df657dbb3f09dd6520331f4699108507bb6/ghc >--------------------------------------------------------------- commit f1157df657dbb3f09dd6520331f4699108507bb6 Author: Andrey Mokhov Date: Fri Mar 4 00:20:39 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- f1157df657dbb3f09dd6520331f4699108507bb6 doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index aa7a560..7fc8dcf 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -1,6 +1,6 @@ -# Compiling on Windows +# Building on Windows -Here are a list of instructions to compile GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. +Here are a list of instructions to build GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_64-installer) (I just accepted all the defaults), then open a command prompt and run: From git at git.haskell.org Fri Oct 27 00:24:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compile rts with -O2 (8e3e9bc) Message-ID: <20171027002410.312B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e3e9bcf2c7fc37423a5b19ac314fe23447610ad/ghc >--------------------------------------------------------------- commit 8e3e9bcf2c7fc37423a5b19ac314fe23447610ad Author: Moritz Angermann Date: Tue Jan 5 13:57:35 2016 +0800 Compile rts with -O2 Fixes #90. We need to force inlining for rts to compile and not end up with missing symbols. >--------------------------------------------------------------- 8e3e9bcf2c7fc37423a5b19ac314fe23447610ad src/Settings/Packages/Rts.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 36476a0..eb74eea 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -49,6 +49,13 @@ rtsPackageArgs = package rts ? do [ arg "-Irts" , arg $ "-I" ++ path -/- "build" , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" + -- rts **must** be compiled with optimizations. The INLINE_HEADER macro, + -- requires that functions are inlined to work as expected. Inlining + -- only happens for optimized builds. Otherwise we can assume that + -- there is a non-inlined variant to use instead. But rts does not + -- provide non-inlined alternatives and hence needs the function to + -- be inlined. See also Issue #90 + , arg $ "-O2" , (file "//RtsMessages.*" ||^ file "//Trace.*") ? arg ("-DProjectVersion=" ++ quote projectVersion) From git at git.haskell.org Fri Oct 27 00:24:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Whitespace only (325db89) Message-ID: <20171027002411.CFC573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/325db89df96215ee0897187972197372e2ef34b9/ghc >--------------------------------------------------------------- commit 325db89df96215ee0897187972197372e2ef34b9 Author: Andrey Mokhov Date: Sun Oct 16 00:45:17 2016 +0100 Whitespace only >--------------------------------------------------------------- 325db89df96215ee0897187972197372e2ef34b9 src/Oracles/PackageData.hs | 68 +++++++++++++++++++++++----------------------- 1 file changed, 34 insertions(+), 34 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 84d552f..55ea812 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -13,23 +13,23 @@ data PackageData = BuildGhciLib FilePath | Synopsis FilePath | Version FilePath -data PackageDataList = CcArgs FilePath - | CSrcs FilePath - | CppArgs FilePath - | DepCcArgs FilePath - | DepExtraLibs FilePath - | DepIds FilePath - | DepIncludeDirs FilePath - | DepLdArgs FilePath - | DepLibDirs FilePath - | DepNames FilePath - | Deps FilePath - | HiddenModules FilePath - | HsArgs FilePath - | IncludeDirs FilePath - | LdArgs FilePath - | Modules FilePath - | SrcDirs FilePath +data PackageDataList = CcArgs FilePath + | CSrcs FilePath + | CppArgs FilePath + | DepCcArgs FilePath + | DepExtraLibs FilePath + | DepIds FilePath + | DepIncludeDirs FilePath + | DepLdArgs FilePath + | DepLibDirs FilePath + | DepNames FilePath + | Deps FilePath + | HiddenModules FilePath + | HsArgs FilePath + | IncludeDirs FilePath + | LdArgs FilePath + | Modules FilePath + | SrcDirs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -55,23 +55,23 @@ pkgData packageData = case packageData of -- @pkgListData Modules@ therefore returns ["Data.Array", "Data.Array.Base", ...] pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = fmap (map unquote . words) $ case packageData of - CcArgs path -> askPackageData path "CC_OPTS" - CSrcs path -> askPackageData path "C_SRCS" - CppArgs path -> askPackageData path "CPP_OPTS" - DepCcArgs path -> askPackageData path "DEP_CC_OPTS" - DepExtraLibs path -> askPackageData path "DEP_EXTRA_LIBS" - DepIds path -> askPackageData path "DEP_IPIDS" - DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" - DepLibDirs path -> askPackageData path "DEP_LIB_DIRS_SINGLE_QUOTED" - DepLdArgs path -> askPackageData path "DEP_LD_OPTS" - DepNames path -> askPackageData path "DEP_NAMES" - Deps path -> askPackageData path "DEPS" - HiddenModules path -> askPackageData path "HIDDEN_MODULES" - HsArgs path -> askPackageData path "HC_OPTS" - IncludeDirs path -> askPackageData path "INCLUDE_DIRS" - LdArgs path -> askPackageData path "LD_OPTS" - Modules path -> askPackageData path "MODULES" - SrcDirs path -> askPackageData path "HS_SRC_DIRS" + CcArgs path -> askPackageData path "CC_OPTS" + CSrcs path -> askPackageData path "C_SRCS" + CppArgs path -> askPackageData path "CPP_OPTS" + DepCcArgs path -> askPackageData path "DEP_CC_OPTS" + DepExtraLibs path -> askPackageData path "DEP_EXTRA_LIBS" + DepIds path -> askPackageData path "DEP_IPIDS" + DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" + DepLibDirs path -> askPackageData path "DEP_LIB_DIRS_SINGLE_QUOTED" + DepLdArgs path -> askPackageData path "DEP_LD_OPTS" + DepNames path -> askPackageData path "DEP_NAMES" + Deps path -> askPackageData path "DEPS" + HiddenModules path -> askPackageData path "HIDDEN_MODULES" + HsArgs path -> askPackageData path "HC_OPTS" + IncludeDirs path -> askPackageData path "INCLUDE_DIRS" + LdArgs path -> askPackageData path "LD_OPTS" + Modules path -> askPackageData path "MODULES" + SrcDirs path -> askPackageData path "HS_SRC_DIRS" where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') From git at git.haskell.org Fri Oct 27 00:24:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Error when a non-optional builder is not specified. (8ba5cff) Message-ID: <20171027002411.E04333A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ba5cfffa37a1992567104a90566d506b4d83f56/ghc >--------------------------------------------------------------- commit 8ba5cfffa37a1992567104a90566d506b4d83f56 Author: Andrey Mokhov Date: Fri Mar 4 01:43:30 2016 +0000 Error when a non-optional builder is not specified. See #211. >--------------------------------------------------------------- 8ba5cfffa37a1992567104a90566d506b4d83f56 src/Builder.hs | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 75d3d4e..eee24cb 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -86,6 +86,11 @@ isStaged = \case (GhcPkg _) -> True _ -> False +isOptional :: Builder -> Bool +isOptional = \case + HsColour -> True + _ -> False + -- TODO: get rid of fromJust -- | Determine the location of a 'Builder' builderPath :: Builder -> Action FilePath @@ -116,9 +121,13 @@ builderPath builder = case builderProvenance builder of _ -> error $ "Cannot determine builderKey for " ++ show builder path <- askConfigWithDefault builderKey . putError $ "\nCannot find path to '" ++ builderKey - ++ "' in configuration files. Have you forgot to run configure?" - if path == "" -- TODO: get rid of "" paths - then return "" + ++ "' in system.config file. Have you forgot to run configure?" + if null path + then do + if isOptional builder + then return "" + else putError $ "Builder '" ++ builderKey ++ "' is not specified in" + ++ " system.config file. Cannot proceed without it." else do path' <- lookupInPath path fixAbsolutePathOnWindows $ path' -<.> exe From git at git.haskell.org Fri Oct 27 00:24:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Wrap ghc-stage2 (04fc52c) Message-ID: <20171027002413.9B49C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/04fc52cd10d23e480ca4de402eb545b4269bdcb1/ghc >--------------------------------------------------------------- commit 04fc52cd10d23e480ca4de402eb545b4269bdcb1 Author: Moritz Angermann Date: Tue Jan 5 14:06:23 2016 +0800 Wrap ghc-stage2 Fix #96 (c.f. #57 for stage1) >--------------------------------------------------------------- 04fc52cd10d23e480ca4de402eb545b4269bdcb1 src/Rules/Program.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index fe55005..547fb86 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -24,6 +24,7 @@ type Wrapper = FilePath -> Expr String -- List of wrappers we build wrappers :: [(PartialTarget, Wrapper)] wrappers = [ (PartialTarget Stage0 ghc, ghcWrapper) + , (PartialTarget Stage1 ghc, ghcWrapper) , (PartialTarget Stage0 ghcPkg, ghcPkgWrapper)] buildProgram :: Resources -> PartialTarget -> Rules () From git at git.haskell.org Fri Oct 27 00:24:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove old issues (a20d473) Message-ID: <20171027002415.969793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a20d4738dad9c0f45f4f01e7722ee4027cfab398/ghc >--------------------------------------------------------------- commit a20d4738dad9c0f45f4f01e7722ee4027cfab398 Author: Andrey Mokhov Date: Tue Oct 18 16:14:16 2016 +0100 Remove old issues >--------------------------------------------------------------- a20d4738dad9c0f45f4f01e7722ee4027cfab398 README.md | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 01132cd..7aa4b67 100644 --- a/README.md +++ b/README.md @@ -135,11 +135,11 @@ How to contribute ----------------- The best way to contribute is to try the new build system, report the issues -you found, and attempt to fix them. Please note the codebase is very unstable -at present and we expect a lot of further refactoring. The documentation is -currently non-existent, but we are working on it: [#55][comments-issue], -[#56][doc-issue]. See also [#239](https://github.com/snowleopard/hadrian/issues/239) -for a list of issues on the critical path. +you found, and attempt to fix them. Please note: the codebase is very unstable +at present and we expect a lot of further refactoring. If you would like to +work on a particular issue, please let everyone know by adding a comment about +this. The issues that are currently on the critical path are listed in +[#239](https://github.com/snowleopard/hadrian/issues/239). Acknowledgements ---------------- @@ -169,6 +169,4 @@ helped me endure and enjoy the project. [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 [milestones]: https://github.com/snowleopard/hadrian/milestones -[comments-issue]: https://github.com/snowleopard/hadrian/issues/55 -[doc-issue]: https://github.com/snowleopard/hadrian/issues/56 [contributors]: https://github.com/snowleopard/hadrian/graphs/contributors From git at git.haskell.org Fri Oct 27 00:24:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make Objdump builder optional. (d89358f) Message-ID: <20171027002415.AB1F63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d89358f615755e5482e526c38d52cef76cfb3b7e/ghc >--------------------------------------------------------------- commit d89358f615755e5482e526c38d52cef76cfb3b7e Author: Andrey Mokhov Date: Sat Mar 5 13:17:23 2016 +0000 Make Objdump builder optional. See #211. >--------------------------------------------------------------- d89358f615755e5482e526c38d52cef76cfb3b7e src/Builder.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index eee24cb..e8011e7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -86,9 +86,14 @@ isStaged = \case (GhcPkg _) -> True _ -> False +-- TODO: Some builders are required only on certain platforms. For example, +-- Objdump is only required on OpenBSD and AIX, as mentioned in #211. Add +-- support for platform-specific optional builders as soon as we can reliably +-- test this feature. isOptional :: Builder -> Bool isOptional = \case HsColour -> True + Objdump -> True _ -> False -- TODO: get rid of fromJust From git at git.haskell.org Fri Oct 27 00:24:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #95 from angerman/feature/fix-rts-deps (ccf4030) Message-ID: <20171027002417.098B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccf4030baa2739d1ce03a273f764a532fb3428c9/ghc >--------------------------------------------------------------- commit ccf4030baa2739d1ce03a273f764a532fb3428c9 Merge: ba41ec6 8e3e9bc Author: Andrey Mokhov Date: Tue Jan 5 09:27:42 2016 +0000 Merge pull request #95 from angerman/feature/fix-rts-deps Adds derivedConstantsDependencies for rts >--------------------------------------------------------------- ccf4030baa2739d1ce03a273f764a532fb3428c9 src/Rules/Generate.hs | 6 ++++++ src/Settings/Packages/Rts.hs | 7 +++++++ 2 files changed, 13 insertions(+) From git at git.haskell.org Fri Oct 27 00:24:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (2d60196) Message-ID: <20171027002419.2986F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d60196c8661bf75324525b2db37f35ccba76aa4/ghc >--------------------------------------------------------------- commit 2d60196c8661bf75324525b2db37f35ccba76aa4 Author: Andrey Mokhov Date: Tue Oct 18 16:15:58 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- 2d60196c8661bf75324525b2db37f35ccba76aa4 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 7aa4b67..ee3df66 100644 --- a/README.md +++ b/README.md @@ -138,8 +138,8 @@ The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note: the codebase is very unstable at present and we expect a lot of further refactoring. If you would like to work on a particular issue, please let everyone know by adding a comment about -this. The issues that are currently on the critical path are listed in -[#239](https://github.com/snowleopard/hadrian/issues/239). +this. The issues that are currently on the critical path and therefore require +particular attention are listed in [#239](https://github.com/snowleopard/hadrian/issues/239). Acknowledgements ---------------- From git at git.haskell.org Fri Oct 27 00:24:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split buildPackageData rule. (c1adff7) Message-ID: <20171027002419.323673A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1adff7f36f088712b52c310eb0fb925e72d2549/ghc >--------------------------------------------------------------- commit c1adff7f36f088712b52c310eb0fb925e72d2549 Author: Andrey Mokhov Date: Sat Mar 5 14:07:47 2016 +0000 Split buildPackageData rule. See #206. >--------------------------------------------------------------- c1adff7f36f088712b52c310eb0fb925e72d2549 src/Rules/Data.hs | 18 +++++++----------- 1 file changed, 7 insertions(+), 11 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index fee310f..719352f 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,5 @@ module Rules.Data (buildPackageData) where -import qualified System.Directory as IO - import Base import Context import Expression @@ -22,8 +20,9 @@ buildPackageData context at Context {..} = do configure = pkgPath package -/- "configure" dataFile = pkgDataFile context oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 + inTreeMk = oldPath -/- takeFileName dataFile -- TODO: remove, #113 - [dataFile, oldPath -/- "package-data.mk"] &%> \_ -> do + inTreeMk %> \mk -> do -- The first thing we do with any package is make sure all generated -- dependencies are in place before proceeding. orderOnly $ generatedDependencies stage package @@ -37,22 +36,19 @@ buildPackageData context at Context {..} = do let depPkgs = matchPackageNames (sort pkgs) deps need =<< traverse (pkgConfFile . vanillaContext stage) depPkgs - -- TODO: get rid of this, see #113 - let inTreeMk = oldPath -/- takeFileName dataFile - need [cabalFile] - build $ Target context GhcCabal [cabalFile] [inTreeMk] + build $ Target context GhcCabal [cabalFile] [mk] - -- TODO: get rid of this, see #113 - liftIO $ IO.copyFile inTreeMk dataFile + -- TODO: get rid of this, see #113 + dataFile %> \mk -> do + copyFile inTreeMk mk autogenFiles <- getDirectoryFiles (oldPath -/- "build") ["autogen/*"] createDirectory $ buildPath context -/- "autogen" forM_ autogenFiles $ \file -> do copyFile (oldPath -/- "build" -/- file) (buildPath context -/- file) let haddockPrologue = "haddock-prologue.txt" copyFile (oldPath -/- haddockPrologue) (buildPath context -/- haddockPrologue) - - postProcessPackageData context dataFile + postProcessPackageData context mk -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps priority 2.0 $ do From git at git.haskell.org Fri Oct 27 00:24:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #97 from angerman/feature/ghc-stage2-wrapper (9e1ef6a) Message-ID: <20171027002420.7F8E63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e1ef6ab9ce326638528140be935e05793f4ea16/ghc >--------------------------------------------------------------- commit 9e1ef6ab9ce326638528140be935e05793f4ea16 Merge: ccf4030 04fc52c Author: Andrey Mokhov Date: Tue Jan 5 09:28:26 2016 +0000 Merge pull request #97 from angerman/feature/ghc-stage2-wrapper Wrap ghc-stage2 >--------------------------------------------------------------- 9e1ef6ab9ce326638528140be935e05793f4ea16 src/Rules/Program.hs | 1 + 1 file changed, 1 insertion(+) From git at git.haskell.org Fri Oct 27 00:24:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hash Target inputs in ArgsHashOracle. (ad44a95) Message-ID: <20171027002423.098CD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ad44a95b78bc2ed712c44f55b691203787b3df93/ghc >--------------------------------------------------------------- commit ad44a95b78bc2ed712c44f55b691203787b3df93 Author: Andrey Mokhov Date: Tue Mar 8 01:35:17 2016 +0000 Hash Target inputs in ArgsHashOracle. See #217. >--------------------------------------------------------------- ad44a95b78bc2ed712c44f55b691203787b3df93 src/Oracles/ArgsHash.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index aec0dc9..d3bfd61 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -23,8 +23,8 @@ newtype ArgsHashKey = ArgsHashKey Target -- TODO: Hash Target to improve accuracy and performance. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do - let firstInput = take 1 $ inputs target - _ <- askOracle . ArgsHashKey $ target { inputs = firstInput } :: Action Int + let hashed = [ show . hash $ inputs target ] + _ <- askOracle . ArgsHashKey $ target { inputs = hashed } :: Action Int return () -- Oracle for storing per-target argument list hashes From git at git.haskell.org Fri Oct 27 00:24:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify package database directory tracking (3e37d73) Message-ID: <20171027002422.F2D433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e37d7350458218964134a981125a19f095de63a/ghc >--------------------------------------------------------------- commit 3e37d7350458218964134a981125a19f095de63a Author: Andrey Mokhov Date: Tue Oct 18 23:03:50 2016 +0100 Simplify package database directory tracking >--------------------------------------------------------------- 3e37d7350458218964134a981125a19f095de63a hadrian.cabal | 1 - src/Oracles/PackageDatabase.hs | 23 ----------------------- src/Rules/Oracles.hs | 2 -- src/Rules/Register.hs | 22 +++++++++++++++------- src/Settings/Builders/GhcCabal.hs | 11 ++--------- src/Settings/Paths.hs | 6 +++++- 6 files changed, 22 insertions(+), 43 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 3e34b16..6039b01 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -35,7 +35,6 @@ executable hadrian , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData - , Oracles.PackageDatabase , Oracles.WindowsPath , Package , Predicate diff --git a/src/Oracles/PackageDatabase.hs b/src/Oracles/PackageDatabase.hs deleted file mode 100644 index efaf9ca..0000000 --- a/src/Oracles/PackageDatabase.hs +++ /dev/null @@ -1,23 +0,0 @@ -module Oracles.PackageDatabase (packageDatabaseOracle) where - -import qualified System.Directory as IO - -import Base -import Context -import Builder -import GHC -import Rules.Actions -import Settings.Builders.GhcCabal -import Settings.Paths -import Target -import UserSettings - -packageDatabaseOracle :: Rules () -packageDatabaseOracle = void $ - addOracle $ \(PackageDatabaseKey stage) -> do - let dir = packageDbDirectory stage - file = dir -/- "package.cache" - unlessM (liftIO $ IO.doesFileExist file) $ do - removeDirectory dir - build $ Target (vanillaContext stage ghcPkg) (GhcPkg stage) [] [dir] - putSuccess $ "| Successfully initialised " ++ dir diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 10767b5..af03b17 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -8,7 +8,6 @@ import qualified Oracles.DirectoryContent import qualified Oracles.LookupInPath import qualified Oracles.ModuleFiles import qualified Oracles.PackageData -import qualified Oracles.PackageDatabase import qualified Oracles.WindowsPath oracleRules :: Rules () @@ -20,5 +19,4 @@ oracleRules = do Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle - Oracles.PackageDatabase.packageDatabaseOracle Oracles.WindowsPath.windowsPathOracle diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 272e27b..d4799e3 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -9,20 +9,22 @@ import Rules.Libffi import Settings.Packages.Rts import Settings.Paths import Target +import UserSettings --- | Build package-data.mk by processing the .cabal file with ghc-cabal utility. +-- | Build rules for registering packages and initialising package databases +-- by running the @ghc-pkg@ utility. registerPackage :: [(Resource, Int)] -> Context -> Rules () -registerPackage rs context at Context {..} = do - let path = buildPath context - oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 - pkgConf = packageDbDirectory stage -/- pkgNameString package +registerPackage rs context at Context {..} = when (stage <= Stage1) $ do + let dir = packageDbDirectory stage - when (stage <= Stage1) $ matchVersionedFilePath pkgConf "conf" ?> \conf -> do + matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do -- This produces inplace-pkg-config. TODO: Add explicit tracking. need [pkgDataFile context] -- Post-process inplace-pkg-config. TODO: remove, see #113, #148. - let pkgConfig = oldPath -/- "inplace-pkg-config" + let path = buildPath context + oldPath = pkgPath package -/- contextDirectory context + pkgConfig = oldPath -/- "inplace-pkg-config" oldBuildPath = oldPath -/- "build" fixPkgConf = unlines . map @@ -52,3 +54,9 @@ registerPackage rs context at Context {..} = do . lines fixFile rtsConf fixRtsConf + + when (package == ghc) $ packageDbStamp stage %> \stamp -> do + removeDirectory dir + buildWithResources rs $ Target (vanillaContext stage ghc) (GhcPkg stage) [] [dir] + writeFileLines stamp [] + putSuccess $ "| Successfully initialised " ++ dir diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index fffb2c0..5569ba0 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,7 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( - ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, - PackageDatabaseKey (..), buildDll0 + ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, buildDll0 ) where import Base @@ -87,16 +86,10 @@ configureArgs = do , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" $ argStagedBuilderPath (Cc CompileC) ] -newtype PackageDatabaseKey = PackageDatabaseKey Stage - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -initialisePackageDatabase :: Stage -> Action () -initialisePackageDatabase = askOracle . PackageDatabaseKey - bootPackageDatabaseArgs :: Args bootPackageDatabaseArgs = do stage <- getStage - lift $ initialisePackageDatabase stage + lift $ need [packageDbStamp stage] stage0 ? do path <- getTopDirectory prefix <- ifM (builder Ghc) (return "-package-db ") (return "--package-db=") diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index ad200f8..6382fcc 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -2,7 +2,7 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, - packageDbDirectory, bootPackageConstraints, packageDependencies + packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies ) where import Base @@ -92,6 +92,10 @@ packageDbDirectory :: Stage -> FilePath packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" +-- | We use a stamp file to track the existence of a package database. +packageDbStamp :: Stage -> FilePath +packageDbStamp stage = packageDbDirectory stage -/- ".stamp" + -- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do From git at git.haskell.org Fri Oct 27 00:24:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix travis script: configure after shake-build is in place. (b978e17) Message-ID: <20171027002423.EC7D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b978e17552d87de8973a5bdd0255da5d1baa7d51/ghc >--------------------------------------------------------------- commit b978e17552d87de8973a5bdd0255da5d1baa7d51 Author: Andrey Mokhov Date: Tue Jan 5 10:29:08 2016 +0000 Fix travis script: configure after shake-build is in place. >--------------------------------------------------------------- b978e17552d87de8973a5bdd0255da5d1baa7d51 .travis/install-ghc-shake.sh | 3 +++ .travis/install-ghc.sh | 3 --- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis/install-ghc-shake.sh b/.travis/install-ghc-shake.sh index 2dc0392..c2b8774 100755 --- a/.travis/install-ghc-shake.sh +++ b/.travis/install-ghc-shake.sh @@ -14,3 +14,6 @@ mv .git "$SHAKEDIR/" echo -e "${COLOR}Installing deps into sandbox${RESET}" ( cd "$SHAKEDIR" && cabal sandbox init ) ( cd "$SHAKEDIR" && cabal install --only-dependencies . ) + +echo -e "${COLOR}GHC boot/configure${RESET}" +( cd ghc && ./boot && ./configure) diff --git a/.travis/install-ghc.sh b/.travis/install-ghc.sh index 126cbe2..fc34ea4 100755 --- a/.travis/install-ghc.sh +++ b/.travis/install-ghc.sh @@ -10,6 +10,3 @@ git clone git://git.haskell.org/ghc echo -e "${COLOR}Initialize GHC submodules${RESET}" ( cd ghc && git submodule update --init ) - -echo -e "${COLOR}GHC boot/configure${RESET}" -( cd ghc && ./boot && ./configure) From git at git.haskell.org Fri Oct 27 00:24:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused extension (0d8713a) Message-ID: <20171027002426.C43633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0d8713a49c11732343f0a8b3d098ace401778acf/ghc >--------------------------------------------------------------- commit 0d8713a49c11732343f0a8b3d098ace401778acf Author: Andrey Mokhov Date: Tue Oct 18 23:21:24 2016 +0100 Drop unused extension >--------------------------------------------------------------- 0d8713a49c11732343f0a8b3d098ace401778acf src/Settings/Builders/GhcCabal.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 5569ba0..535454e 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, buildDll0 ) where From git at git.haskell.org Fri Oct 27 00:24:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable library profiling in quick build flavour. (c7a4165) Message-ID: <20171027002426.C5FDA3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7a41657a0393aa1a1d5d5b7219c0f8c7c2e31dc/ghc >--------------------------------------------------------------- commit c7a41657a0393aa1a1d5d5b7219c0f8c7c2e31dc Author: Andrey Mokhov Date: Wed Mar 9 23:47:34 2016 +0000 Disable library profiling in quick build flavour. See #188. >--------------------------------------------------------------- c7a41657a0393aa1a1d5d5b7219c0f8c7c2e31dc src/Settings/Flavours/Quick.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 1f2def1..97af880 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -1,9 +1,10 @@ -module Settings.Flavours.Quick (quickFlavourArgs) where +module Settings.Flavours.Quick (quickFlavourArgs, quickFlavourWays) where import Expression import Predicates (builderGhc) --- TODO: consider putting all flavours in a single file --- TODO: handle other, non Args, settings affected by flavours quickFlavourArgs :: Args quickFlavourArgs = builderGhc ? arg "-O0" + +quickFlavourWays :: Ways +quickFlavourWays = remove [profiling] From git at git.haskell.org Fri Oct 27 00:24:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (d4e44fb) Message-ID: <20171027002427.9AB443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4e44fb28e3487c00fb375e4a528f97cab720c53/ghc >--------------------------------------------------------------- commit d4e44fb28e3487c00fb375e4a528f97cab720c53 Author: Andrey Mokhov Date: Tue Jan 5 10:29:30 2016 +0000 Add comments. >--------------------------------------------------------------- d4e44fb28e3487c00fb375e4a528f97cab720c53 src/Settings/Packages/Rts.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index eb74eea..d300e5a 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -89,6 +89,14 @@ rtsPackageArgs = package rts ? do , arg "-DFFI_LIB_DIR=" , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] + +-- # If we're compiling on windows, enforce that we only support XP+ +-- # Adding this here means it doesn't have to be done in individual .c files +-- # and also centralizes the versioning. +-- ifeq "$$(TargetOS_CPP)" "mingw32" +-- rts_dist_$1_CC_OPTS += -DWINVER=$(rts_WINVER) +-- endif + -- #----------------------------------------------------------------------------- -- # Use system provided libffi From git at git.haskell.org Fri Oct 27 00:24:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (a0afb98) Message-ID: <20171027002431.083353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a0afb987569ba2ac617b1bcd035f124c93463da3/ghc >--------------------------------------------------------------- commit a0afb987569ba2ac617b1bcd035f124c93463da3 Author: Andrey Mokhov Date: Wed Oct 19 00:03:58 2016 +0100 Minor revision >--------------------------------------------------------------- a0afb987569ba2ac617b1bcd035f124c93463da3 src/Expression.hs | 4 ++-- src/Rules/Gmp.hs | 11 ++++------- src/Rules/Libffi.hs | 10 +++------- src/Rules/Library.hs | 4 ++-- 4 files changed, 11 insertions(+), 18 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 114bfe4..a572c2c 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -16,7 +16,7 @@ module Expression ( -- * Convenient accessors getContext, getStage, getPackage, getBuilder, getOutputs, getInputs, getWay, - getInput, getOutput, + getInput, getOutput, getSingleton, -- * Re-exports module Control.Monad.Trans.Reader, @@ -206,7 +206,7 @@ getOutput = do getSingleton getOutputs $ "getOutput: exactly one output file expected in target " ++ show target -getSingleton :: Expr [a] -> String -> Expr a +getSingleton :: Monad m => m [a] -> String -> m a getSingleton expr msg = expr >>= \case [res] -> return res _ -> error msg diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 50c548b..3693ad4 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,4 +1,4 @@ -module Rules.Gmp (gmpRules, gmpContext) where +module Rules.Gmp (gmpRules) where import Base import Builder @@ -81,12 +81,9 @@ gmpRules = do -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. - tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "gmpRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - + let tarballs = gmpBase -/- "tarball/gmp*.tar.bz2" + tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) + "Exactly one GMP tarball is expected." withTempDir $ \dir -> do let tmp = unifyPath dir need [tarball] diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 5ca17ea..6dd92bc 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -80,13 +80,9 @@ libffiRules = do libffiMakefile <.> "in" %> \mkIn -> do removeDirectory libffiBuildPath createDirectory $ buildRootPath -/- stageString Stage0 - - tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "libffiRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - + let tarballs = "libffi-tarballs/libffi*.tar.gz" + tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) + "Exactly one LibFFI tarball is expected." need [tarball] let libname = dropExtension . dropExtension $ takeFileName tarball diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 00a6be2..731bb7b 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -9,9 +9,9 @@ import Base import Context import Expression import Flavour +import GHC import Oracles.PackageData import Rules.Actions -import Rules.Gmp import Settings import Settings.Paths import Target @@ -96,7 +96,7 @@ hSources context = do extraObjects :: Context -> Action [FilePath] extraObjects context - | context == gmpContext = do + | package context == integerGmp = do need [gmpLibraryH] map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:24:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow build flavours to control Ways. (0b327b5) Message-ID: <20171027002431.1D01C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b327b564fbab286b6999040565046b5d6bf60c8/ghc >--------------------------------------------------------------- commit 0b327b564fbab286b6999040565046b5d6bf60c8 Author: Andrey Mokhov Date: Wed Mar 9 23:48:54 2016 +0000 Allow build flavours to control Ways. See #188, #218. >--------------------------------------------------------------- 0b327b564fbab286b6999040565046b5d6bf60c8 src/Settings/Ways.hs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 0fee897..7e46406 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,14 +1,18 @@ module Settings.Ways (getLibraryWays, getRtsWays) where +import CmdLineFlag import Base import Expression +import Oracles.Config.Flag import Predicates +import Settings.Flavours.Quick import Settings.User -import Oracles.Config.Flag -- | Combine default ways with user modifications getLibraryWays :: Expr [Way] -getLibraryWays = fromDiffExpr $ defaultLibraryWays <> userLibraryWays +getLibraryWays = fromDiffExpr $ mconcat [ defaultLibraryWays + , userLibraryWays + , flavourLibraryWays ] getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays @@ -24,6 +28,10 @@ defaultLibraryWays = mconcat , notStage0 ? append [profiling] , notStage0 ? platformSupportsSharedLibs ? append [dynamic] ] +flavourLibraryWays :: Ways +flavourLibraryWays = mconcat + [ cmdFlavour == Quick ? quickFlavourWays ] + defaultRtsWays :: Ways defaultRtsWays = do ways <- getLibraryWays From git at git.haskell.org Fri Oct 27 00:24:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow splitObjects to be controlled in Settings/User.hs, see #84. (b18f0e3) Message-ID: <20171027002431.971323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b18f0e3f79ee051e9d384b508f0ca3eaa902d80b/ghc >--------------------------------------------------------------- commit b18f0e3f79ee051e9d384b508f0ca3eaa902d80b Author: Andrey Mokhov Date: Tue Jan 5 11:08:20 2016 +0000 Allow splitObjects to be controlled in Settings/User.hs, see #84. >--------------------------------------------------------------- b18f0e3f79ee051e9d384b508f0ca3eaa902d80b shaking-up-ghc.cabal | 1 + src/Predicates.hs | 12 +----------- src/Rules/Library.hs | 1 - src/Settings/Default.hs | 15 +++++++++++++++ src/Settings/User.hs | 6 +++++- 5 files changed, 22 insertions(+), 13 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 334cd59..2eb9f72 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -76,6 +76,7 @@ executable ghc-shake , Settings.Builders.HsCpp , Settings.Builders.Ld , Settings.Builders.Tar + , Settings.Default , Settings.Packages , Settings.Packages.Base , Settings.Packages.Compiler diff --git a/src/Predicates.hs b/src/Predicates.hs index 7b788fe..ad63598 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,13 +1,11 @@ -- | Convenient predicates module Predicates ( stage, package, builder, stagedBuilder, builderGcc, builderGhc, file, way, - stage0, stage1, stage2, notStage0, notPackage, registerPackage, splitObjects + stage0, stage1, stage2, notStage0, notPackage, registerPackage ) where import Base import Expression -import GHC -import Oracles.Config.Flag -- Basic predicates stage :: Stage -> Predicate @@ -55,11 +53,3 @@ notPackage = notM . package -- TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate registerPackage = return True - -splitObjects :: Predicate -splitObjects = do - goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages - pkg <- getPackage - supported <- lift supportsSplitObjects - let goodPackage = isLibrary pkg && pkg /= compiler && pkg /= rts - return $ goodStage && goodPackage && supported diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 8633c69..d9a1a48 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -6,7 +6,6 @@ import Base hiding (splitPath) import Expression import GHC import Oracles -import Predicates (splitObjects) import Rules.Actions import Rules.IntegerGmp import Rules.Resources diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs new file mode 100644 index 0000000..93b647a --- /dev/null +++ b/src/Settings/Default.hs @@ -0,0 +1,15 @@ +module Settings.Default (defaultSplitObjects) where + +import Base +import Expression +import GHC +import Oracles.Config.Flag +import Predicates + +defaultSplitObjects :: Predicate +defaultSplitObjects = do + goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages + pkg <- getPackage + supported <- lift supportsSplitObjects + let goodPackage = isLibrary pkg && pkg /= compiler && pkg /= rts + return $ goodStage && goodPackage && supported diff --git a/src/Settings/User.hs b/src/Settings/User.hs index cad2578..6107f6f 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userProgramPath, userKnownPackages, integerLibrary, trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors + verboseCommands, turnWarningsIntoErrors, splitObjects ) where import GHC @@ -57,6 +57,10 @@ trackBuildSystem = True validating :: Bool validating = False +-- To switch off split objects change to 'return False' +splitObjects :: Predicate +splitObjects = return False -- FIXME: should be defaultSplitObjects, see #84. + dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Fri Oct 27 00:24:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify getSingleton, add comments (fbe22e6) Message-ID: <20171027002435.4BFB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fbe22e6f83bb5e9f14960b63f1ad40dbbfdd7c86/ghc >--------------------------------------------------------------- commit fbe22e6f83bb5e9f14960b63f1ad40dbbfdd7c86 Author: Andrey Mokhov Date: Wed Oct 19 00:25:01 2016 +0100 Simplify getSingleton, add comments >--------------------------------------------------------------- fbe22e6f83bb5e9f14960b63f1ad40dbbfdd7c86 src/Expression.hs | 19 ++++++++++--------- src/Rules/Gmp.hs | 6 +++--- src/Rules/Libffi.hs | 6 +++--- 3 files changed, 16 insertions(+), 15 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index a572c2c..45967c9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -192,8 +192,8 @@ getInputs = asks inputs getInput :: Expr FilePath getInput = do target <- ask - getSingleton getInputs $ - "getInput: exactly one input file expected in target " ++ show target + getSingleton ("Exactly one input file expected in " ++ show target) + <$> getInputs -- | Get the files produced by the current 'Target'. getOutputs :: Expr [FilePath] @@ -203,10 +203,11 @@ getOutputs = asks outputs getOutput :: Expr FilePath getOutput = do target <- ask - getSingleton getOutputs $ - "getOutput: exactly one output file expected in target " ++ show target - -getSingleton :: Monad m => m [a] -> String -> m a -getSingleton expr msg = expr >>= \case - [res] -> return res - _ -> error msg + getSingleton ("Exactly one output file expected in " ++ show target) + <$> getOutputs + +-- | Extract a value from a singleton list, or raise an error if the list does +-- not contain exactly one value. +getSingleton :: String -> [a] -> a +getSingleton _ [res] = res +getSingleton msg _ = error msg diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 3693ad4..412bea0 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -81,9 +81,9 @@ gmpRules = do -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. - let tarballs = gmpBase -/- "tarball/gmp*.tar.bz2" - tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) - "Exactly one GMP tarball is expected." + tarball <- unifyPath . getSingleton "Exactly one GMP tarball is expected" + <$> getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] + withTempDir $ \dir -> do let tmp = unifyPath dir need [tarball] diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 6dd92bc..9560dbf 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -80,9 +80,9 @@ libffiRules = do libffiMakefile <.> "in" %> \mkIn -> do removeDirectory libffiBuildPath createDirectory $ buildRootPath -/- stageString Stage0 - let tarballs = "libffi-tarballs/libffi*.tar.gz" - tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) - "Exactly one LibFFI tarball is expected." + tarball <- unifyPath . getSingleton "Exactly one LibFFI tarball is expected" + <$> getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] + need [tarball] let libname = dropExtension . dropExtension $ takeFileName tarball From git at git.haskell.org Fri Oct 27 00:24:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build profiled libraries by default. (56526ff) Message-ID: <20171027002435.68FA23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56526ffc8dde7873fc35db912d9793eba1e63734/ghc >--------------------------------------------------------------- commit 56526ffc8dde7873fc35db912d9793eba1e63734 Author: Andrey Mokhov Date: Wed Mar 9 23:49:48 2016 +0000 Build profiled libraries by default. See #186, #218. >--------------------------------------------------------------- 56526ffc8dde7873fc35db912d9793eba1e63734 src/Settings/User.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index dd6150a..6fc5536 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -30,10 +30,9 @@ userKnownPackages :: [Package] userKnownPackages = [] -- | Control which ways library packages are built --- FIXME: skip profiling for speed -- FIXME: skip dynamic since it's currently broken #4 userLibraryWays :: Ways -userLibraryWays = remove [profiling, dynamic] +userLibraryWays = remove [dynamic] -- | Control which ways the 'rts' package is built userRtsWays :: Ways From git at git.haskell.org Fri Oct 27 00:24:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rework Travis CI script (d0ffc1f) Message-ID: <20171027002435.C2FB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d0ffc1f8d7e109511b08c0a70a4956188718a911/ghc >--------------------------------------------------------------- commit d0ffc1f8d7e109511b08c0a70a4956188718a911 Author: David Luposchainsky Date: Tue Jan 5 09:50:08 2016 +0100 Rework Travis CI script - Move all .travis/*.sh functionality directly into .travis.yml - Install Alex/Happy from PPA instead of compiling them by hand - Skip Shake progress indicators, as they're rather useless on clean-slate Travis builds, and clutter up the log - Don't use a Cabal sandbox for building so Travis can share $HOME/.cabal - boot/configure only after the Shake build system is in place, otherwise some required *.in files are not converted, and Shake fails >--------------------------------------------------------------- d0ffc1f8d7e109511b08c0a70a4956188718a911 .travis.yml | 52 +++++++++++++++++++++++++++---------- .travis/install-cabal-happy-alex.sh | 18 ------------- .travis/install-ghc-shake.sh | 19 -------------- .travis/install-ghc.sh | 12 --------- .travis/print-env.sh | 9 ------- .travis/run-ghc-shake.sh | 9 ------- build.cabal.sh | 3 ++- build.sh | 2 +- 8 files changed, 42 insertions(+), 82 deletions(-) diff --git a/.travis.yml b/.travis.yml index 5e169fa..9079fa9 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,9 +1,23 @@ sudo: false matrix: - include: - - env: CABALVER=1.22 GHCVER=7.10.3 - addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.3,zlib1g-dev,terminfo-dev], sources: [hvr-ghc]}} + include: + - env: + CABALVER=1.22 + GHCVER=7.10.3 + + addons: { + apt: { + packages: [ + ghc-7.10.3, + alex-3.1.4, + happy-1.19.5, + cabal-install-1.22, + zlib1g-dev + ], + sources: [hvr-ghc] + } + } before_install: @@ -12,21 +26,33 @@ before_install: - PATH="/opt/cabal/$CABALVER/bin:$PATH" - export PATH - - .travis/print-env.sh + - env + - ghc --version + - cabal --version + - alex --version + - happy --version + - cabal update install: - - .travis/install-cabal-happy-alex.sh - - .travis/install-ghc.sh - - .travis/install-ghc-shake.sh + + - travis_retry git clone git://git.haskell.org/ghc --recurse-submodules + + # Travis clones the project into ".", but we need it as a child directory + # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake + # ".git" directory into the appropriate location, and perform a hard reset + # in order to regenerate the GHC-Shake files. + - mkdir ghc/shake-build + - mv .git ghc/shake-build + - ( cd ghc/shake-build && git reset --hard HEAD ) + + - ( cd ghc/shake-build && cabal install --only-dependencies ) + + - ( cd ghc && ./boot ) + - ( cd ghc && ./configure ) script: - - .travis/run-ghc-shake.sh + - ./ghc/shake-build/build.sh -j --no-progress cache: directories: - $HOME/.cabal - # - ghc/shake-build/.cabal-sandbox - # - ghc/shake-build/cabal.sandbox.config - -# before_cache: -# - rm -rf ghc/shake-build diff --git a/.travis/install-cabal-happy-alex.sh b/.travis/install-cabal-happy-alex.sh deleted file mode 100755 index 93df460..0000000 --- a/.travis/install-cabal-happy-alex.sh +++ /dev/null @@ -1,18 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[32m" # Green -RESET="\e[m" - -echo -e "${COLOR}GHC version:${RESET}" -ghc --version - -echo -e "${COLOR}Cabal version:${RESET}" -cabal --version - -echo -e "${COLOR}Update Cabal${RESET}" -cabal update - -echo -e "${COLOR}Install Alex+Happy${RESET}" -cabal install alex happy diff --git a/.travis/install-ghc-shake.sh b/.travis/install-ghc-shake.sh deleted file mode 100755 index c2b8774..0000000 --- a/.travis/install-ghc-shake.sh +++ /dev/null @@ -1,19 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[31m" # Red, because this file is serious business -RESET="\e[m" - -echo -e "${COLOR}Brutally hacking GHC-Shake to its proper location${RESET}" -SHAKEDIR="ghc/shake-build" -mkdir -p "$SHAKEDIR" -mv .git "$SHAKEDIR/" -( cd "$SHAKEDIR" && git reset --hard HEAD ) - -echo -e "${COLOR}Installing deps into sandbox${RESET}" -( cd "$SHAKEDIR" && cabal sandbox init ) -( cd "$SHAKEDIR" && cabal install --only-dependencies . ) - -echo -e "${COLOR}GHC boot/configure${RESET}" -( cd ghc && ./boot && ./configure) diff --git a/.travis/install-ghc.sh b/.travis/install-ghc.sh deleted file mode 100755 index fc34ea4..0000000 --- a/.travis/install-ghc.sh +++ /dev/null @@ -1,12 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[34m" # Blue -RESET="\e[m" - -echo -e "${COLOR}Clone GHC source${RESET}" -git clone git://git.haskell.org/ghc - -echo -e "${COLOR}Initialize GHC submodules${RESET}" -( cd ghc && git submodule update --init ) diff --git a/.travis/print-env.sh b/.travis/print-env.sh deleted file mode 100755 index c09c11f..0000000 --- a/.travis/print-env.sh +++ /dev/null @@ -1,9 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[32m" # Green -RESET="\e[m" - -echo -e "${COLOR}Environment:${RESET}" -env diff --git a/.travis/run-ghc-shake.sh b/.travis/run-ghc-shake.sh deleted file mode 100755 index 7b867b7..0000000 --- a/.travis/run-ghc-shake.sh +++ /dev/null @@ -1,9 +0,0 @@ -#!/usr/bin/env bash - -set -euo pipefail - -COLOR="\e[32m" # Green -RESET="\e[m" - -echo -e "${COLOR}Running Shake build system${RESET}" -( cd ghc && ./shake-build/build.cabal.sh ) diff --git a/build.cabal.sh b/build.cabal.sh index 65da82b..cf165b8 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -6,9 +6,10 @@ absoltueRoot="$(dirname "$(readlink -f "$0")")" cd "$absoltueRoot" # Initialize sandbox if necessary -if ! $(cabal sandbox hc-pkg list 2>&1 > /dev/null); then +if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then cabal sandbox init cabal install \ + --dependencies-only \ --disable-library-profiling \ --disable-shared fi diff --git a/build.sh b/build.sh index f09c30c..82cbb93 100755 --- a/build.sh +++ b/build.sh @@ -2,7 +2,7 @@ set -euo pipefail -root="$(dirname "$0")" +root="$(dirname "$(readlink -f "$0")")" mkdir -p "$root/.shake" From git at git.haskell.org Fri Oct 27 00:24:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split compilation of Haskell and non-Haskell files (b61423d) Message-ID: <20171027002439.6E6EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b61423dfdb36c96a902f26b14c07e6bc39621a94/ghc >--------------------------------------------------------------- commit b61423dfdb36c96a902f26b14c07e6bc39621a94 Author: Andrey Mokhov Date: Thu Oct 20 02:44:02 2016 +0100 Split compilation of Haskell and non-Haskell files See #216, #264, #267. >--------------------------------------------------------------- b61423dfdb36c96a902f26b14c07e6bc39621a94 src/Oracles/Dependencies.hs | 5 ++- src/Oracles/PackageData.hs | 6 +++- src/Rules/Compile.hs | 58 ++++++++++++++++---------------- src/Rules/Data.hs | 17 +++++----- src/Rules/Dependencies.hs | 77 ++++++++++--------------------------------- src/Rules/Generate.hs | 17 +++++++--- src/Rules/Library.hs | 80 ++++++++++++++++++++++++++++----------------- src/Rules/Program.hs | 12 +++---- 8 files changed, 132 insertions(+), 140 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 b61423dfdb36c96a902f26b14c07e6bc39621a94 From git at git.haskell.org Fri Oct 27 00:24:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Quick flavour now disables library profiling (9b68950) Message-ID: <20171027002439.9B1683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b68950fd0a53a33dbe902ed6e55b627f6ecb516/ghc >--------------------------------------------------------------- commit 9b68950fd0a53a33dbe902ed6e55b627f6ecb516 Author: Andrey Mokhov Date: Thu Mar 10 00:01:55 2016 +0000 Quick flavour now disables library profiling See #188. [skip ci] >--------------------------------------------------------------- 9b68950fd0a53a33dbe902ed6e55b627f6ecb516 README.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index aca17ea..b6d762b 100644 --- a/README.md +++ b/README.md @@ -54,7 +54,8 @@ are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue In addition to standard Shake flags (try `--help`), the build system currently supports several others: * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: -`default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). +`default` and `quick` (adds `-O0` flag to all GHC invocations and disables library +profiling, which speeds up builds by 3-4x). * `--haddock`: build Haddock documentation. * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per From git at git.haskell.org Fri Oct 27 00:24:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #101 from quchen/master (0d43a40) Message-ID: <20171027002439.EC07D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0d43a40a2b42a3332e41e7e096b2d0834dffeb53/ghc >--------------------------------------------------------------- commit 0d43a40a2b42a3332e41e7e096b2d0834dffeb53 Merge: b18f0e3 d0ffc1f Author: Andrey Mokhov Date: Tue Jan 5 11:31:03 2016 +0000 Merge pull request #101 from quchen/master Rework Travis CI script >--------------------------------------------------------------- 0d43a40a2b42a3332e41e7e096b2d0834dffeb53 .travis.yml | 52 +++++++++++++++++++++++++++---------- .travis/install-cabal-happy-alex.sh | 18 ------------- .travis/install-ghc-shake.sh | 19 -------------- .travis/install-ghc.sh | 12 --------- .travis/print-env.sh | 9 ------- .travis/run-ghc-shake.sh | 9 ------- build.cabal.sh | 3 ++- build.sh | 2 +- 8 files changed, 42 insertions(+), 82 deletions(-) From git at git.haskell.org Fri Oct 27 00:24:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor discovery of generated dependencies (bb43f24) Message-ID: <20171027002443.E1E663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bb43f249ba63559f988fedac9b5180bfdc28d1cf/ghc >--------------------------------------------------------------- commit bb43f249ba63559f988fedac9b5180bfdc28d1cf Author: Andrey Mokhov Date: Fri Oct 21 01:30:10 2016 +0100 Refactor discovery of generated dependencies See #285, #267. >--------------------------------------------------------------- bb43f249ba63559f988fedac9b5180bfdc28d1cf src/Builder.hs | 8 ++---- src/Rules/Compile.hs | 59 +++++++++++++++++++++++---------------------- src/Rules/Generate.hs | 17 +------------ src/Settings/Builders/Cc.hs | 12 ++------- 4 files changed, 35 insertions(+), 61 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 09b87cb..860034e 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -20,12 +20,8 @@ import Stage -- 1) Compiling sources into object files. -- 2) Extracting source dependencies, e.g. by passing -M command line argument. -- 3) Linking object files & static libraries into an executable. --- We have CcMode for CC and GhcMode for GHC. - --- TODO: Consider merging FindCDependencies and FindMissingInclude -data CcMode = CompileC | FindCDependencies | FindMissingInclude - deriving (Eq, Generic, Show) - +-- We have CcMode for C compiler and GhcMode for GHC. +data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show) data GhcMode = CompileHs | FindHsDependencies | LinkHs deriving (Eq, Generic, Show) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 535758c..285abe0 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -1,5 +1,7 @@ module Rules.Compile (compilePackage) where +import Development.Shake.Util + import Base import Context import Expression @@ -9,21 +11,14 @@ import Rules.Generate import Settings.Paths import Target -import Development.Shake.Util - -import qualified Data.Set as Set - compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context nonHs extension = path extension "*" <.> osuf way compile compiler obj2src obj = do - let depFile = obj -<.> "d" - src = obj2src context obj + let src = obj2src context obj need [src] - needGenerated context src - build $ Target context (Cc FindCDependencies stage) [src] [depFile] - needMakefileDependencies depFile -- TODO: Is this actually needed? + needDependencies context src $ obj <.> "d" build $ Target context (compiler stage) [src] [obj] compileHs = \[obj, _] -> do (src, deps) <- fileDependencies context obj @@ -41,28 +36,27 @@ compilePackage rs context at Context {..} = do [ path "*" <.> suf way | suf <- [ osuf, hisuf] ] &%> compileHs [ path "*" <.> suf way | suf <- [obootsuf, hibootsuf] ] &%> compileHs --- TODO: Simplify. -needGenerated :: Context -> FilePath -> Action () -needGenerated context origFile = go Set.empty +-- | Discover dependencies of a given source file by iteratively calling @gcc@ +-- in the @-MM -MG@ mode and building generated dependencies if they are missing +-- until reaching a fixed point. +needDependencies :: Context -> FilePath -> FilePath -> Action () +needDependencies context at Context {..} src depFile = discover where - go :: Set.Set String -> Action () - go done = withTempFile $ \outFile -> do - let builder = Cc FindMissingInclude $ stage context - target = Target context builder [origFile] [outFile] - build target - deps <- parseFile outFile - - -- Get the full path if the include refers to a generated file and call - -- `need` on it. - needed <- liftM catMaybes $ - interpretInContext context (mapM getPathIfGenerated deps) - need needed + discover = do + build $ Target context (Cc FindCDependencies stage) [src] [depFile] + deps <- parseFile depFile + -- Generated dependencies, if not yet built, will not be found and hence + -- will be referred to simply by their file names. + let notFound = filter (\file -> file == takeFileName file) deps + -- We find the full paths to generated dependencies, so we can request + -- to build them by calling 'need'. + todo <- catMaybes <$> mapM (fullPathIfGenerated context) notFound - let newdone = Set.fromList needed `Set.union` done - -- If we added a new file to the set of needed files, let's try one more - -- time, since the new file might include a genreated header of itself - -- (which we'll `need`). - when (Set.size newdone > Set.size done) (go newdone) + if null todo + then need deps -- The list of dependencies is final, need all + else do + need todo -- Build newly discovered generated dependencies + discover -- Continue the discovery process parseFile :: FilePath -> Action [String] parseFile file = do @@ -71,6 +65,13 @@ needGenerated context origFile = go Set.empty [(_file, deps)] -> return deps _ -> return [] +-- | Find a given 'FilePath' in the list of generated files in the given +-- 'Context' and return its full path. +fullPathIfGenerated :: Context -> FilePath -> Action (Maybe FilePath) +fullPathIfGenerated context file = interpretInContext context $ do + generated <- generatedDependencies + return $ find ((== file) . takeFileName) generated + obj2src :: String -> (FilePath -> Bool) -> Context -> FilePath -> FilePath obj2src extension isGenerated context at Context {..} obj | isGenerated src = src diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index ceeb182..bfede1a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,7 +1,6 @@ module Rules.Generate ( isGeneratedCFile, isGeneratedCmmFile, generatePackageCode, generateRules, - installTargets, copyRules, includesDependencies, generatedDependencies, - getPathIfGenerated + installTargets, copyRules, includesDependencies, generatedDependencies ) where import qualified System.Directory as IO @@ -199,17 +198,3 @@ generateRules = do emptyTarget :: Context emptyTarget = vanillaContext (error "Rules.Generate.emptyTarget: unknown stage") (error "Rules.Generate.emptyTarget: unknown package") - -getPathIfGenerated :: FilePath -> Expr (Maybe FilePath) -getPathIfGenerated include = do - generated <- generatedFiles - -- For includes of generated files, we cannot get the full path of the file - -- (since it might be included due to some include dir, i.e., through `-I`). - -- So here we try both the name and the path. - let nameOrPath (name, path) = include == name || include == path - return . fmap snd $ find nameOrPath generated - -generatedFiles :: Expr [(FilePath, FilePath)] -generatedFiles = do - deps <- generatedDependencies - return [ (takeFileName fp, fp) | fp <- deps ] diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index 41a8466..595feab 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -21,19 +21,11 @@ ccBuilderArgs = builder Cc ? mconcat output <- getOutput mconcat [ arg "-E" , arg "-MM" + , arg "-MG" , arg "-MF" , arg output , arg "-MT" , arg $ dropExtension output -<.> "o" , arg "-x" , arg "c" - , arg =<< getInput ] - - , builder (Cc FindMissingInclude) ? - mconcat [ arg "-E" - , arg "-MM" - , arg "-MG" - , arg "-MF" - , arg =<< getOutput - , arg =<< getInput ] - ] + , arg =<< getInput ] ] From git at git.haskell.org Fri Oct 27 00:24:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: We can now build profiling way (b052ae7) Message-ID: <20171027002444.2E36C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b052ae700aa9a6831dc824824617bbebc4494351/ghc >--------------------------------------------------------------- commit b052ae700aa9a6831dc824824617bbebc4494351 Author: Andrey Mokhov Date: Thu Mar 10 00:26:04 2016 +0000 We can now build profiling way See #186. [skip ci] >--------------------------------------------------------------- b052ae700aa9a6831dc824824617bbebc4494351 README.md | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/README.md b/README.md index b6d762b..7317384 100644 --- a/README.md +++ b/README.md @@ -100,7 +100,7 @@ zero (see [#197][test-issue]). Current limitations ------------------- The new build system still lacks many important features: -* We only build `vanilla` way: [#4][dynamic-issue], [#186][profiling-issue]. +* We only build `vanilla` and `profiling` way: [#4][dynamic-issue]. * Validation is not implemented: [#187][validation-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. @@ -141,7 +141,6 @@ helped me endure and enjoy the project. [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs [test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 -[profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 From git at git.haskell.org Fri Oct 27 00:24:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Temporarily disable haddock, see #98. (2d1efa2) Message-ID: <20171027002444.83B7E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d1efa2110af8b0aa2b5aa641e61f8c906e02d38/ghc >--------------------------------------------------------------- commit 2d1efa2110af8b0aa2b5aa641e61f8c906e02d38 Author: Andrey Mokhov Date: Tue Jan 5 11:39:38 2016 +0000 Temporarily disable haddock, see #98. >--------------------------------------------------------------- 2d1efa2110af8b0aa2b5aa641e61f8c906e02d38 src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 6107f6f..aba4a48 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -82,7 +82,7 @@ laxDependencies :: Bool laxDependencies = False buildHaddock :: Predicate -buildHaddock = return True +buildHaddock = return False -- FIXME: should be return True, see #98 buildSystemConfigFile :: Bool buildSystemConfigFile = False From git at git.haskell.org Fri Oct 27 00:24:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify, drop code duplication, add comments (ffff1b3) Message-ID: <20171027002448.197293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffff1b38a54fcf55e4a809cc6c403a60016d1492/ghc >--------------------------------------------------------------- commit ffff1b38a54fcf55e4a809cc6c403a60016d1492 Author: Andrey Mokhov Date: Sat Oct 22 00:47:53 2016 +0100 Simplify, drop code duplication, add comments >--------------------------------------------------------------- ffff1b38a54fcf55e4a809cc6c403a60016d1492 src/Oracles/ModuleFiles.hs | 21 +++++++--- src/Rules/Compile.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 4 +- src/Rules/Library.hs | 99 ++++++++++++---------------------------------- src/Rules/Program.hs | 45 +++++++++------------ src/Settings/Paths.hs | 29 +++++++++++++- 7 files changed, 92 insertions(+), 110 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 ffff1b38a54fcf55e4a809cc6c403a60016d1492 From git at git.haskell.org Fri Oct 27 00:24:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update limitations (acf3623) Message-ID: <20171027002448.69F1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acf362369999eacdd9d3c73abc83e0e607c315b5/ghc >--------------------------------------------------------------- commit acf362369999eacdd9d3c73abc83e0e607c315b5 Author: Andrey Mokhov Date: Thu Mar 10 11:57:53 2016 +0000 Update limitations See #219. [skip ci] >--------------------------------------------------------------- acf362369999eacdd9d3c73abc83e0e607c315b5 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 7317384..c61f5c6 100644 --- a/README.md +++ b/README.md @@ -105,6 +105,7 @@ The new build system still lacks many important features: * Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. +* There is no support for installation or binary/source distribution: [#219][install-issue]. Check out [milestones] to see when we hope to resolve the above limitations. @@ -144,6 +145,7 @@ helped me endure and enjoy the project. [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 +[install-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/219 [milestones]: https://github.com/snowleopard/shaking-up-ghc/milestones [comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 [doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 From git at git.haskell.org Fri Oct 27 00:24:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix readlink for os x. (0b0e1d6) Message-ID: <20171027002448.8EB923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b0e1d68b1e58b23c2dff0edd0c4135e0cb3a583/ghc >--------------------------------------------------------------- commit 0b0e1d68b1e58b23c2dff0edd0c4135e0cb3a583 Author: Moritz Angermann Date: Tue Jan 5 20:43:29 2016 +0800 Fix readlink for os x. This should fix #104. >--------------------------------------------------------------- 0b0e1d68b1e58b23c2dff0edd0c4135e0cb3a583 build.sh | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 82cbb93..de9b9d7 100755 --- a/build.sh +++ b/build.sh @@ -1,8 +1,34 @@ #!/usr/bin/env bash +# readlink on os x, doesn't support -f, to prevent the +# need of installing coreutils (e.g. through brew, just +# for readlink, we use the follownig substitute. +# +# source: http://stackoverflow.com/a/1116890 +function rl { + TARGET_FILE=$1 + + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE=$(basename "$TARGET_FILE") + + # Iterate down a (possible) chain of symlinks + while [ -L "$TARGET_FILE" ] + do + TARGET_FILE=$(readlink "$TARGET_FILE") + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE=$(basename "$TARGET_FILE") + done + + # Compute the canonicalized name by finding the physical path + # for the directory we're in and appending the target file. + PHYS_DIR=`pwd -P` + RESULT=$PHYS_DIR/$TARGET_FILE + echo $RESULT +} + set -euo pipefail -root="$(dirname "$(readlink -f "$0")")" +root="$(dirname "$(rl "$0")")" mkdir -p "$root/.shake" From git at git.haskell.org Fri Oct 27 00:24:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix Travis MacOSX instance (c391fea) Message-ID: <20171027002452.897BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c391feaa87a406da4f19e3384b0329fb086d8268/ghc >--------------------------------------------------------------- commit c391feaa87a406da4f19e3384b0329fb086d8268 Author: Andrey Mokhov Date: Sat Oct 22 01:39:25 2016 +0100 Attempt to fix Travis MacOSX instance >--------------------------------------------------------------- c391feaa87a406da4f19e3384b0329fb086d8268 .travis.yml | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0209cab..217a7d5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -39,13 +39,17 @@ install: - mv .git ghc/hadrian - cd ghc/hadrian - git reset --hard HEAD + - cd .. + - ./boot + - ./configure + - cd hadrian script: # Run internal Hadrian tests - ./build.sh selftest # Build GHC - - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.sh -j --skip-configure --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 00:24:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Experiment with a more efficient version of -/- in Settings.Paths (c50799d) Message-ID: <20171027002452.C06383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c50799d46b53afbde517be8ca1626ef37a626d8f/ghc >--------------------------------------------------------------- commit c50799d46b53afbde517be8ca1626ef37a626d8f Author: Andrey Mokhov Date: Thu Mar 10 12:34:51 2016 +0000 Experiment with a more efficient version of -/- in Settings.Paths See #218. >--------------------------------------------------------------- c50799d46b53afbde517be8ca1626ef37a626d8f src/Settings/Paths.hs | 21 +++++++++++++-------- 1 file changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 62a5c57..678ed92 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -11,20 +11,25 @@ import GHC import Oracles.PackageData import Settings.User +-- A more efficient version of '-/-' which assumes that given FilePaths have +-- already been unified. See #218. TODO: Switch to 'newtype FilePath'. +(~/~) :: FilePath -> FilePath -> FilePath +x ~/~ y = x ++ '/' : y + -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath buildPath context at Context {..} = - buildRootPath -/- contextDirectory context -/- pkgPath package + buildRootPath ~/~ contextDirectory context ~/~ pkgPath package -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath -pkgDataFile context = buildPath context -/- "package-data.mk" +pkgDataFile context = buildPath context ~/~ "package-data.mk" -- | Path to the haddock file of a given 'Context', e.g.: -- ".build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = - buildPath context -/- "doc/html" -/- name -/- name <.> "haddock" + buildPath context ~/~ "doc/html" ~/~ name ~/~ name <.> "haddock" where name = pkgNameString package -- | Path to the library file of a given 'Context', e.g.: @@ -50,25 +55,25 @@ pkgFile :: Context -> String -> String -> Action FilePath pkgFile context prefix suffix = do let path = buildPath context componentId <- pkgData $ ComponentId path - return $ path -/- prefix ++ componentId ++ suffix + return $ path ~/~ prefix ++ componentId ++ suffix -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage1/gmp" +gmpBuildPath = buildRootPath ~/~ "stage1/gmp" -- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath -gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" +gmpBuildInfoPath = pkgPath integerGmp ~/~ "integer-gmp.buildinfo" -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory -- | Path to package database directory of a given 'Stage'. packageDbDirectory :: Stage -> FilePath -packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" +packageDbDirectory Stage0 = buildRootPath ~/~ "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" -- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do componentId <- pkgData . ComponentId $ buildPath context - return $ packageDbDirectory stage -/- componentId <.> "conf" + return $ packageDbDirectory stage ~/~ componentId <.> "conf" From git at git.haskell.org Fri Oct 27 00:24:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds -no-hs-main to iservBin (8718da8) Message-ID: <20171027002453.426293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8718da8fe567d0ab9fa3b0f85726d73c9ed04cb3/ghc >--------------------------------------------------------------- commit 8718da8fe567d0ab9fa3b0f85726d73c9ed04cb3 Author: Moritz Angermann Date: Tue Jan 5 20:44:55 2016 +0800 Adds -no-hs-main to iservBin Fixes #102. But does not *yet* include the generation of the wrapper script. >--------------------------------------------------------------- 8718da8fe567d0ab9fa3b0f85726d73c9ed04cb3 shaking-up-ghc.cabal | 1 + src/Settings/Args.hs | 2 ++ src/Settings/Packages/IservBin.hs | 10 ++++++++++ 3 files changed, 13 insertions(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 2eb9f72..00fb408 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -87,6 +87,7 @@ executable ghc-shake , Settings.Packages.Haddock , Settings.Packages.Hp2ps , Settings.Packages.IntegerGmp + , Settings.Packages.IservBin , Settings.Packages.Rts , Settings.Packages.RunGhc , Settings.TargetDirectory diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index a677c80..fb121ed 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -27,6 +27,7 @@ import Settings.Packages.GhcPrim import Settings.Packages.Haddock import Settings.Packages.Hp2ps import Settings.Packages.IntegerGmp +import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc import Settings.User @@ -72,5 +73,6 @@ defaultPackageArgs = mconcat , haddockPackageArgs , hp2psPackageArgs , integerGmpPackageArgs + , iservBinPackageArgs , rtsPackageArgs , runGhcPackageArgs ] diff --git a/src/Settings/Packages/IservBin.hs b/src/Settings/Packages/IservBin.hs new file mode 100644 index 0000000..5ad3bd5 --- /dev/null +++ b/src/Settings/Packages/IservBin.hs @@ -0,0 +1,10 @@ +module Settings.Packages.IservBin (iservBinPackageArgs) where + +import Expression +import GHC (iservBin) +import Predicates (builderGhc, package) + +iservBinPackageArgs :: Args +iservBinPackageArgs = package iservBin ? do + mconcat [ builderGhc ? + mconcat [ arg "-no-hs-main" ]] From git at git.haskell.org Fri Oct 27 00:24:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use nm-classic when running on Travis (90e3e97) Message-ID: <20171027002456.00A743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90e3e973e62788d98d47fc3942ecd8c50e7fe92b/ghc >--------------------------------------------------------------- commit 90e3e973e62788d98d47fc3942ecd8c50e7fe92b Author: Andrey Mokhov Date: Sat Oct 22 01:48:38 2016 +0100 Use nm-classic when running on Travis >--------------------------------------------------------------- 90e3e973e62788d98d47fc3942ecd8c50e7fe92b .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 217a7d5..187c009 100644 --- a/.travis.yml +++ b/.travis.yml @@ -41,7 +41,7 @@ install: - git reset --hard HEAD - cd .. - ./boot - - ./configure + - ./configure --with-nm=$(xcrun --find nm-classic) - cd hadrian script: From git at git.haskell.org Fri Oct 27 00:24:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of git://github.com/snowleopard/shaking-up-ghc (950ac6b) Message-ID: <20171027002456.5B92F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/950ac6b7dc479aebfc367db3c459130cb71668e0/ghc >--------------------------------------------------------------- commit 950ac6b7dc479aebfc367db3c459130cb71668e0 Merge: c50799d acf3623 Author: Andrey Mokhov Date: Thu Mar 10 12:37:03 2016 +0000 Merge branch 'master' of git://github.com/snowleopard/shaking-up-ghc >--------------------------------------------------------------- 950ac6b7dc479aebfc367db3c459130cb71668e0 README.md | 2 ++ 1 file changed, 2 insertions(+) From git at git.haskell.org Fri Oct 27 00:24:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #107 from angerman/feature/iserv (f4ef847) Message-ID: <20171027002457.0315B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4ef847b4f4ea44ff8ceeefcdbe7fdb5dcaac336/ghc >--------------------------------------------------------------- commit f4ef847b4f4ea44ff8ceeefcdbe7fdb5dcaac336 Merge: 2d1efa2 8718da8 Author: Andrey Mokhov Date: Tue Jan 5 12:52:41 2016 +0000 Merge pull request #107 from angerman/feature/iserv Adds -no-hs-main to iservBin >--------------------------------------------------------------- f4ef847b4f4ea44ff8ceeefcdbe7fdb5dcaac336 shaking-up-ghc.cabal | 1 + src/Settings/Args.hs | 2 ++ src/Settings/Packages/IservBin.hs | 10 ++++++++++ 3 files changed, 13 insertions(+) From git at git.haskell.org Fri Oct 27 00:24:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:24:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #276 from wereHamster/osx-use-nm-classic (99404de) Message-ID: <20171027002459.963903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/99404defcfbec85ff25963f480e64c26adcb9f16/ghc >--------------------------------------------------------------- commit 99404defcfbec85ff25963f480e64c26adcb9f16 Merge: 90e3e97 3c31edc Author: Andrey Mokhov Date: Sat Oct 22 02:02:32 2016 +0100 Merge pull request #276 from wereHamster/osx-use-nm-classic Use nm-classic instead of nm when host is Darwin >--------------------------------------------------------------- 99404defcfbec85ff25963f480e64c26adcb9f16 README.md | 8 -------- src/Settings/Builders/Configure.hs | 7 +++++++ 2 files changed, 7 insertions(+), 8 deletions(-) From git at git.haskell.org Fri Oct 27 00:25:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -threaded to ghc options. (bf60359) Message-ID: <20171027002500.366033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf60359360e91bf41773efbd7facdfda3b399c7c/ghc >--------------------------------------------------------------- commit bf60359360e91bf41773efbd7facdfda3b399c7c Author: Andrey Mokhov Date: Mon Apr 11 00:27:21 2016 +0100 Add -threaded to ghc options. >--------------------------------------------------------------- bf60359360e91bf41773efbd7facdfda3b399c7c build.bat | 1 + build.sh | 1 + shaking-up-ghc.cabal | 5 ++++- 3 files changed, 6 insertions(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 465d957..2f6d4cd 100644 --- a/build.bat +++ b/build.bat @@ -6,6 +6,7 @@ -fno-warn-name-shadowing ^ -XRecordWildCards ^ src/Main.hs ^ + -threaded ^ -isrc ^ -rtsopts ^ -with-rtsopts=-I0 ^ diff --git a/build.sh b/build.sh index 7c070e9..95de2e6 100755 --- a/build.sh +++ b/build.sh @@ -40,6 +40,7 @@ ghc \ -i"$root/src" \ -rtsopts \ -with-rtsopts=-I0 \ + -threaded \ -outputdir="$root/.shake" \ -j -O \ -o "$root/.shake/build" diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index fc0744d..8ef820f 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -127,4 +127,7 @@ executable ghc-shake , shake == 0.15.* , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* - ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 + ghc-options: -Wall + -fno-warn-name-shadowing + -rtsopts -with-rtsopts=-I0 + -threaded From git at git.haskell.org Fri Oct 27 00:25:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds quotes. (a1f3c8d) Message-ID: <20171027002500.98AA53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a1f3c8df8f27422eef777f4b9ff4e6a844c88532/ghc >--------------------------------------------------------------- commit a1f3c8df8f27422eef777f4b9ff4e6a844c88532 Author: Moritz Angermann Date: Tue Jan 5 20:54:18 2016 +0800 Adds quotes. >--------------------------------------------------------------- a1f3c8df8f27422eef777f4b9ff4e6a844c88532 build.sh | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/build.sh b/build.sh index de9b9d7..a3f0bf5 100755 --- a/build.sh +++ b/build.sh @@ -1,33 +1,33 @@ #!/usr/bin/env bash +set -euo pipefail + # readlink on os x, doesn't support -f, to prevent the # need of installing coreutils (e.g. through brew, just # for readlink, we use the follownig substitute. # # source: http://stackoverflow.com/a/1116890 function rl { - TARGET_FILE=$1 + TARGET_FILE="$1" cd "$(dirname "$TARGET_FILE")" - TARGET_FILE=$(basename "$TARGET_FILE") + TARGET_FILE="$(basename "$TARGET_FILE")" # Iterate down a (possible) chain of symlinks while [ -L "$TARGET_FILE" ] do - TARGET_FILE=$(readlink "$TARGET_FILE") + TARGET_FILE="$(readlink "$TARGET_FILE")" cd "$(dirname "$TARGET_FILE")" - TARGET_FILE=$(basename "$TARGET_FILE") + TARGET_FILE="$(basename "$TARGET_FILE")" done # Compute the canonicalized name by finding the physical path # for the directory we're in and appending the target file. - PHYS_DIR=`pwd -P` - RESULT=$PHYS_DIR/$TARGET_FILE - echo $RESULT + PHYS_DIR="$(pwd -P)" + RESULT="$PHYS_DIR/$TARGET_FILE" + echo "$RESULT" } -set -euo pipefail - root="$(dirname "$(rl "$0")")" mkdir -p "$root/.shake" From git at git.haskell.org Fri Oct 27 00:25:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert to running the configure script from Hadrian (4378fcf) Message-ID: <20171027002503.D03B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4378fcfe96fc58328bb03378f45529e6d13a7122/ghc >--------------------------------------------------------------- commit 4378fcfe96fc58328bb03378f45529e6d13a7122 Author: Andrey Mokhov Date: Sat Oct 22 02:06:18 2016 +0100 Revert to running the configure script from Hadrian See #276. >--------------------------------------------------------------- 4378fcfe96fc58328bb03378f45529e6d13a7122 .travis.yml | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 187c009..0209cab 100644 --- a/.travis.yml +++ b/.travis.yml @@ -39,17 +39,13 @@ install: - mv .git ghc/hadrian - cd ghc/hadrian - git reset --hard HEAD - - cd .. - - ./boot - - ./configure --with-nm=$(xcrun --find nm-classic) - - cd hadrian script: # Run internal Hadrian tests - ./build.sh selftest # Build GHC - - ./build.sh -j --skip-configure --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 00:25:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install alex and happy using cabal to fix Travis failure (67e3104) Message-ID: <20171027002504.76ED23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/67e31045fb749fdcb4cb67248931e5ce403e012b/ghc >--------------------------------------------------------------- commit 67e31045fb749fdcb4cb67248931e5ce403e012b Author: Andrey Mokhov Date: Mon Apr 11 00:43:59 2016 +0100 Install alex and happy using cabal to fix Travis failure >--------------------------------------------------------------- 67e31045fb749fdcb4cb67248931e5ce403e012b .travis.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 9547914..21bf769 100644 --- a/.travis.yml +++ b/.travis.yml @@ -8,8 +8,6 @@ matrix: apt: packages: - ghc-7.10.3 - - alex-3.1.4 - - happy-1.19.5 - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc @@ -19,6 +17,7 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH - cabal update + - cabal install alex happy - os: osx env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg From git at git.haskell.org Fri Oct 27 00:25:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add rl function to the cabal build file as well. (2c635d5) Message-ID: <20171027002504.AE9323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c635d55d07ddeb2f827dd5d3007fc9b362b043a/ghc >--------------------------------------------------------------- commit 2c635d55d07ddeb2f827dd5d3007fc9b362b043a Author: Moritz Angermann Date: Tue Jan 5 20:58:07 2016 +0800 Add rl function to the cabal build file as well. >--------------------------------------------------------------- 2c635d55d07ddeb2f827dd5d3007fc9b362b043a build.cabal.sh | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index cf165b8..8add516 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -2,7 +2,33 @@ set -euo pipefail -absoltueRoot="$(dirname "$(readlink -f "$0")")" +# readlink on os x, doesn't support -f, to prevent the +# need of installing coreutils (e.g. through brew, just +# for readlink, we use the follownig substitute. +# +# source: http://stackoverflow.com/a/1116890 +function rl { + TARGET_FILE="$1" + + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE="$(basename "$TARGET_FILE")" + + # Iterate down a (possible) chain of symlinks + while [ -L "$TARGET_FILE" ] + do + TARGET_FILE="$(readlink "$TARGET_FILE")" + cd "$(dirname "$TARGET_FILE")" + TARGET_FILE="$(basename "$TARGET_FILE")" + done + + # Compute the canonicalized name by finding the physical path + # for the directory we're in and appending the target file. + PHYS_DIR="$(pwd -P)" + RESULT="$PHYS_DIR/$TARGET_FILE" + echo "$RESULT" +} + +absoltueRoot="$(dirname "$(rl "$0")")" cd "$absoltueRoot" # Initialize sandbox if necessary From git at git.haskell.org Fri Oct 27 00:25:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix typo (2895999) Message-ID: <20171027002507.5837C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2895999d7ac18fe9f90e6f6feb47c4e71a84202f/ghc >--------------------------------------------------------------- commit 2895999d7ac18fe9f90e6f6feb47c4e71a84202f Author: Andrey Mokhov Date: Sat Oct 22 11:27:01 2016 +0100 Fix typo >--------------------------------------------------------------- 2895999d7ac18fe9f90e6f6feb47c4e71a84202f src/Settings/Builders/Configure.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 6482df1..deab649 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -26,8 +26,7 @@ configureBuilderArgs = mconcat , "--enable-shared=no" -- TODO: add support for yes , "--host=" ++ targetPlatform ] - -- On OS X, use "nm-classic" instead of "nm" due to a bug in the later. + -- On OS X, use "nm-classic" instead of "nm" due to a bug in the latter. -- See https://ghc.haskell.org/trac/ghc/ticket/11744 , builder (Configure ".") ? System.os == "darwin" ? - arg "--with-nm=$(xcrun --find nm-classic)" - ] + arg "--with-nm=$(xcrun --find nm-classic)" ] From git at git.haskell.org Fri Oct 27 00:25:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass conf-cc-args-stageN to Gcc builder. (0e27bf4) Message-ID: <20171027002508.A4DF33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0e27bf4172aa629796af44dfe3642967eace1dba/ghc >--------------------------------------------------------------- commit 0e27bf4172aa629796af44dfe3642967eace1dba Author: Andrey Mokhov Date: Mon Apr 11 23:18:19 2016 +0100 Pass conf-cc-args-stageN to Gcc builder. See #221. >--------------------------------------------------------------- 0e27bf4172aa629796af44dfe3642967eace1dba src/Settings/Builders/Gcc.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index 4902ea3..7c237da 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -2,6 +2,7 @@ module Settings.Builders.Gcc (gccBuilderArgs, gccMBuilderArgs) where import Development.Shake.FilePath import Expression +import Oracles.Config.Setting import Oracles.PackageData import Predicates (stagedBuilder) import Settings @@ -30,4 +31,5 @@ gccMBuilderArgs = stagedBuilder GccM ? do commonGccArgs :: Args commonGccArgs = mconcat [ append =<< getPkgDataList CcArgs + , append =<< getSettingList . ConfCcArgs =<< getStage , cIncludeArgs ] From git at git.haskell.org Fri Oct 27 00:25:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: -Augenkrebs (e17f0e6) Message-ID: <20171027002508.D67C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e17f0e6575bf53cc23e966e343b32e0fc4705c86/ghc >--------------------------------------------------------------- commit e17f0e6575bf53cc23e966e343b32e0fc4705c86 Author: Moritz Angermann Date: Tue Jan 5 20:58:38 2016 +0800 -Augenkrebs >--------------------------------------------------------------- e17f0e6575bf53cc23e966e343b32e0fc4705c86 build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index a3f0bf5..719e85e 100755 --- a/build.sh +++ b/build.sh @@ -39,7 +39,7 @@ ghc \ -rtsopts \ -with-rtsopts=-I0 \ -outputdir="$root/.shake" \ - -j -O \ + -j -O \ -o "$root/.shake/build" "$root/.shake/build" \ From git at git.haskell.org Fri Oct 27 00:25:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move package.conf.inplace to build directory (038dfb4) Message-ID: <20171027002510.CA5753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/038dfb43604a5316e0b44f745e9367a09fb6a217/ghc >--------------------------------------------------------------- commit 038dfb43604a5316e0b44f745e9367a09fb6a217 Author: Andrey Mokhov Date: Sat Oct 22 23:47:39 2016 +0100 Move package.conf.inplace to build directory >--------------------------------------------------------------- 038dfb43604a5316e0b44f745e9367a09fb6a217 src/Settings/Packages/Rts.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index f3f2e43..f2b4035 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -9,13 +9,13 @@ import Oracles.Config.Setting import Oracles.WindowsPath import Predicate import Settings +import Settings.Paths rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" --- TODO: move to buildRootPath, see #113 rtsConf :: FilePath -rtsConf = pkgPath rts -/- contextDirectory rtsContext -/- "package.conf.inplace" +rtsConf = buildPath rtsContext -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do From git at git.haskell.org Fri Oct 27 00:25:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor tweaks (5b49f64) Message-ID: <20171027002512.E96F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b49f649a2f4b9a4fcb0ea6a46f5a40480ee0375/ghc >--------------------------------------------------------------- commit 5b49f649a2f4b9a4fcb0ea6a46f5a40480ee0375 Author: Andrey Mokhov Date: Tue Apr 12 01:04:31 2016 +0100 Minor tweaks >--------------------------------------------------------------- 5b49f649a2f4b9a4fcb0ea6a46f5a40480ee0375 src/Predicates.hs | 4 +--- src/Settings/Builders/Common.hs | 6 +++--- src/Settings/Builders/GhcCabal.hs | 2 +- 3 files changed, 5 insertions(+), 7 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index c0f6095..1c5ce38 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -21,9 +21,7 @@ builder b = (b ==) <$> getBuilder -- | Is a certain builder used in the current stage? stagedBuilder :: (Stage -> Builder) -> Predicate -stagedBuilder stageBuilder = do - s <- getStage - builder (stageBuilder s) +stagedBuilder stageBuilder = builder . stageBuilder =<< getStage -- | Are we building with GCC? builderGcc :: Predicate diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 4ecf1d4..1f1d33b 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -51,10 +51,10 @@ argSetting :: Setting -> Args argSetting = argM . setting argSettingList :: SettingList -> Args -argSettingList = (append =<<) . lift . settingList +argSettingList = (append =<<) . getSettingList argStagedSettingList :: (Stage -> SettingList) -> Args -argStagedSettingList ss = (argSettingList . ss) =<< getStage +argStagedSettingList ss = argSettingList . ss =<< getStage argStagedBuilderPath :: (Stage -> Builder) -> Args -argStagedBuilderPath sb = (argM . builderPath . sb) =<< getStage +argStagedBuilderPath sb = argM . builderPath . sb =<< getStage diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index be89546..24b7d7d 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -131,7 +131,7 @@ with b = specified b ? do append [withBuilderKey b ++ top -/- path] withStaged :: (Stage -> Builder) -> Args -withStaged sb = (with . sb) =<< getStage +withStaged sb = with . sb =<< getStage needDll0 :: Stage -> Package -> Action Bool needDll0 stage pkg = do From git at git.haskell.org Fri Oct 27 00:25:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #106 from angerman/feature/broken-osx-readlink (5517cb0) Message-ID: <20171027002513.317693A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5517cb05c724c86d04f526c933e94c6a54ba2e18/ghc >--------------------------------------------------------------- commit 5517cb05c724c86d04f526c933e94c6a54ba2e18 Merge: f4ef847 e17f0e6 Author: Andrey Mokhov Date: Tue Jan 5 13:02:14 2016 +0000 Merge pull request #106 from angerman/feature/broken-osx-readlink Fix readlink for os x [skip ci] >--------------------------------------------------------------- 5517cb05c724c86d04f526c933e94c6a54ba2e18 build.cabal.sh | 28 +++++++++++++++++++++++++++- build.sh | 30 ++++++++++++++++++++++++++++-- 2 files changed, 55 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:25:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify (f52e582) Message-ID: <20171027002514.5C2613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f52e582d9cc21ad369411dc7bc832332e97ff224/ghc >--------------------------------------------------------------- commit f52e582d9cc21ad369411dc7bc832332e97ff224 Author: Andrey Mokhov Date: Sun Oct 23 00:41:23 2016 +0100 Simplify See #265 >--------------------------------------------------------------- f52e582d9cc21ad369411dc7bc832332e97ff224 src/Oracles/DirectoryContent.hs | 41 ++++++++++++++++++----------------------- src/Rules/Actions.hs | 13 ++++++------- 2 files changed, 24 insertions(+), 30 deletions(-) diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContent.hs index 45afa92..3139c6c 100644 --- a/src/Oracles/DirectoryContent.hs +++ b/src/Oracles/DirectoryContent.hs @@ -1,39 +1,34 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} module Oracles.DirectoryContent ( - getDirectoryContent, directoryContentOracle, Match(..) + directoryContent, directoryContentOracle, Match (..) ) where -import Base -import GHC.Generics import System.Directory.Extra +import GHC.Generics + +import Base newtype DirectoryContent = DirectoryContent (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -data Match = Test FilePattern | Not (Match) | And [Match] | Or [Match] +data Match = Test FilePattern | Not Match | And [Match] | Or [Match] deriving (Generic, Eq, Show, Typeable) -instance Binary Match -instance Hashable Match -instance NFData Match matches :: Match -> FilePath -> Bool -matches (Test m) f = m ?== f -matches (Not m) f = not $ matches m f -matches (And []) _ = True -matches (And (m:ms)) f | matches m f = matches (And ms) f - | otherwise = False -matches (Or []) _ = False -matches (Or (m:ms)) f | matches m f = True - | otherwise = matches (Or ms) f +matches (Test p) f = p ?== f +matches (Not m) f = not $ matches m f +matches (And ms) f = all (`matches` f) ms +matches (Or ms) f = any (`matches` f) ms -- | Get the directory content recursively. -getDirectoryContent :: Match -> FilePath -> Action [FilePath] -getDirectoryContent expr dir = - askOracle $ DirectoryContent (expr, dir) +directoryContent :: Match -> FilePath -> Action [FilePath] +directoryContent expr dir = askOracle $ DirectoryContent (expr, dir) directoryContentOracle :: Rules () -directoryContentOracle = void $ addOracle oracle - where - oracle :: DirectoryContent -> Action [FilePath] - oracle (DirectoryContent (expr, dir)) = - liftIO $ filter (matches expr) <$> listFilesInside (return . matches expr) dir +directoryContentOracle = void $ + addOracle $ \(DirectoryContent (expr, dir)) -> liftIO $ + filter (matches expr) <$> listFilesInside (return . matches expr) dir + +instance Binary Match +instance Hashable Match +instance NFData Match diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index e30bc01..cccda24 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -45,8 +45,7 @@ customBuild rs opts target at Target {..} = do argList <- interpret target getArgs verbose <- interpret target verboseCommands let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly - -- The line below forces the rule to be rerun if the args hash has changed. - checkArgsHash target + checkArgsHash target -- Rerun the rule if the hash of argList has changed. withResources rs $ do putInfo target quietlyUnlessVerbose $ case builder of @@ -133,12 +132,12 @@ copyDirectory source target = do copyDirectoryContent :: Match -> FilePath -> FilePath -> Action () copyDirectoryContent expr source target = do putProgressInfo $ renderAction "Copy directory content" source target - getDirectoryContent expr source >>= mapM_ cp + mapM_ cp =<< directoryContent expr source where - cp a = do - createDirectory $ dropFileName $ target' a - copyFile a $ target' a - target' a = target -/- fromJust (stripPrefix source a) + cp file = do + let newFile = target -/- drop (length source) file + createDirectory $ dropFileName newFile -- TODO: Why do it for each file? + copyFile file newFile -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:25:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't add exe extension to builder paths on Windows. (e23dab7) Message-ID: <20171027002516.53C433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e23dab7cab22ecd9ba7f69ba735c43878a7b6c3a/ghc >--------------------------------------------------------------- commit e23dab7cab22ecd9ba7f69ba735c43878a7b6c3a Author: Andrey Mokhov Date: Tue Apr 12 18:45:50 2016 +0100 Don't add exe extension to builder paths on Windows. See #221, #222. >--------------------------------------------------------------- e23dab7cab22ecd9ba7f69ba735c43878a7b6c3a src/Builder.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index e8011e7..a0cc093 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -133,9 +133,7 @@ builderPath builder = case builderProvenance builder of then return "" else putError $ "Builder '" ++ builderKey ++ "' is not specified in" ++ " system.config file. Cannot proceed without it." - else do - path' <- lookupInPath path - fixAbsolutePathOnWindows $ path' -<.> exe + else fixAbsolutePathOnWindows =<< lookupInPath path getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath From git at git.haskell.org Fri Oct 27 00:25:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make ghc-cabal build parallel [skip ci]. (83c73a2) Message-ID: <20171027002516.9D4583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/83c73a2bd507915d2a655e5c6148ec92c8a9e9a5/ghc >--------------------------------------------------------------- commit 83c73a2bd507915d2a655e5c6148ec92c8a9e9a5 Author: Andrey Mokhov Date: Tue Jan 5 14:02:21 2016 +0000 Make ghc-cabal build parallel [skip ci]. >--------------------------------------------------------------- 83c73a2bd507915d2a655e5c6148ec92c8a9e9a5 src/Settings/Packages/GhcCabal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 67fa5b4..f1a7373 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -23,6 +23,7 @@ ghcCabalBootArgs = stage0 ? do [ remove ["-hide-all-packages"] , removePair "-optP-include" $ "-optP" ++ cabalMacros , arg "--make" + , arg "-j" , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" , arg "-DGENERICS" From git at git.haskell.org Fri Oct 27 00:25:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve code consistency, simplify, fix comments (9d13cd8) Message-ID: <20171027002517.D051D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d13cd844b9eabbb5d826a9f518c27bb8756b390/ghc >--------------------------------------------------------------- commit 9d13cd844b9eabbb5d826a9f518c27bb8756b390 Author: Andrey Mokhov Date: Sun Oct 23 01:03:22 2016 +0100 Improve code consistency, simplify, fix comments >--------------------------------------------------------------- 9d13cd844b9eabbb5d826a9f518c27bb8756b390 src/Builder.hs | 31 ++++++++++++++----------------- src/Context.hs | 4 ++-- src/Package.hs | 4 +--- src/Rules/Cabal.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Perl.hs | 5 ++--- src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Cc.hs | 12 ++++-------- src/Settings/Builders/GenApply.hs | 1 - src/Settings/Builders/GenPrimopCode.hs | 1 - src/Settings/Builders/GhcCabal.hs | 1 - src/Settings/Builders/HsCpp.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Builders/Ld.hs | 11 +++++------ src/Settings/Builders/Tar.hs | 11 +++++------ src/Stage.hs | 3 +-- src/Target.hs | 5 ++--- src/Way.hs | 1 - 19 files changed, 43 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 9d13cd844b9eabbb5d826a9f518c27bb8756b390 From git at git.haskell.org Fri Oct 27 00:25:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Gcc(M) to Cc(M). (96dec14) Message-ID: <20171027002520.693B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/96dec1490c1a95e7e5a4c58f736e617773ff9d32/ghc >--------------------------------------------------------------- commit 96dec1490c1a95e7e5a4c58f736e617773ff9d32 Author: Andrey Mokhov Date: Thu Apr 14 01:41:02 2016 +0100 Rename Gcc(M) to Cc(M). See #222, #223. >--------------------------------------------------------------- 96dec1490c1a95e7e5a4c58f736e617773ff9d32 cfg/system.config.in | 4 +-- shaking-up-ghc.cabal | 2 +- src/Builder.hs | 62 ++++++++++++++++---------------- src/Predicates.hs | 6 ++-- src/Rules/Compile.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 +-- src/Settings/Args.hs | 6 ++-- src/Settings/Builders/{Gcc.hs => Cc.hs} | 22 ++++++------ src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 8 ++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Directory.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 4 +-- src/Settings/Packages/Rts.hs | 4 +-- 16 files changed, 67 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 96dec1490c1a95e7e5a4c58f736e617773ff9d32 From git at git.haskell.org Fri Oct 27 00:25:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Separate build messages with a newline. (ff676fc) Message-ID: <20171027002520.8B6BB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff676fcbb1e7f1956d94de28bd3fba9ddce40312/ghc >--------------------------------------------------------------- commit ff676fcbb1e7f1956d94de28bd3fba9ddce40312 Author: Andrey Mokhov Date: Tue Jan 5 16:59:41 2016 +0000 Separate build messages with a newline. >--------------------------------------------------------------- ff676fcbb1e7f1956d94de28bd3fba9ddce40312 src/Rules/Actions.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 6f116b5..d567747 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -71,7 +71,7 @@ copyFile source target = do createDirectory :: FilePath -> Action () createDirectory dir = do - putBuild $ "| Create directory " ++ dir + putBuild $ "\n| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir -- Note, the source directory is untracked @@ -85,7 +85,7 @@ moveDirectory source target = do -- Transform a given file by applying a function to its contents fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do - putBuild $ "| Fix " ++ file + putBuild $ "\n| Fix " ++ file old <- liftIO $ readFile file let new = f old length new `seq` liftIO $ writeFile file new @@ -93,14 +93,14 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] - putBuild $ "| Run configure in " ++ dir ++ "..." + putBuild $ "\n| Run configure in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." + putBuild $ "\n| Run make" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args runBuilder :: Builder -> [String] -> Action () @@ -108,7 +108,7 @@ runBuilder builder args = do needBuilder laxDependencies builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "| Run " ++ show builder ++ note + putBuild $ "\n| Run " ++ show builder ++ note quietly $ cmd [path] args -- Print out key information about the command being executed From git at git.haskell.org Fri Oct 27 00:25:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports in Settings/Builders (2f74254) Message-ID: <20171027002521.95D183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc/ghc >--------------------------------------------------------------- commit 2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc Author: Andrey Mokhov Date: Sun Oct 23 01:25:50 2016 +0100 Refactor imports in Settings/Builders >--------------------------------------------------------------- 2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc src/Rules/Libffi.hs | 9 --------- src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/Ar.hs | 5 +---- src/Settings/Builders/Cc.hs | 5 ----- src/Settings/Builders/Common.hs | 25 ++++++++++++++++++++++++- src/Settings/Builders/Configure.hs | 6 +----- src/Settings/Builders/DeriveConstants.hs | 5 ----- src/Settings/Builders/GenApply.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 2 +- src/Settings/Builders/Ghc.hs | 9 --------- src/Settings/Builders/GhcCabal.hs | 19 +------------------ src/Settings/Builders/GhcPkg.hs | 6 +----- src/Settings/Builders/Haddock.hs | 7 +------ src/Settings/Builders/Happy.hs | 2 +- src/Settings/Builders/HsCpp.hs | 4 ---- src/Settings/Builders/Hsc2Hs.hs | 7 ------- src/Settings/Builders/Ld.hs | 2 -- src/Settings/Builders/Make.hs | 4 +--- src/Settings/Builders/Tar.hs | 2 +- 19 files changed, 35 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 2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc From git at git.haskell.org Fri Oct 27 00:25:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid cyclic dependencies, see #103. (50dbdd4) Message-ID: <20171027002536.040893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/50dbdd4040e45284fc4cc53115469fe3a882ac5a/ghc >--------------------------------------------------------------- commit 50dbdd4040e45284fc4cc53115469fe3a882ac5a Author: Andrey Mokhov Date: Tue Jan 5 21:30:58 2016 +0000 Avoid cyclic dependencies, see #103. >--------------------------------------------------------------- 50dbdd4040e45284fc4cc53115469fe3a882ac5a src/Rules/IntegerGmp.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index f86371c..0d5da26 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -105,7 +105,9 @@ integerGmpRules = do -- check whether we need to build in tree gmp -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` - need [pkgDataFile Stage1 integerGmp] + + runConfigure (pkgPath integerGmp) [] [] + configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk then do From git at git.haskell.org Fri Oct 27 00:25:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #225 from hvr/pr/systemcfg-fixes (1099f62) Message-ID: <20171027002537.538A93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1099f6232570c8124afb27a13097272f436dd596/ghc >--------------------------------------------------------------- commit 1099f6232570c8124afb27a13097272f436dd596 Merge: 897ba61 3bab113 Author: Andrey Mokhov Date: Sun Apr 17 17:00:15 2016 +0100 Merge pull request #225 from hvr/pr/systemcfg-fixes Misc `system.config.in` fixes >--------------------------------------------------------------- 1099f6232570c8124afb27a13097272f436dd596 cfg/system.config.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:25:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop GenApply arguments, as it actually needs none. (0bec73c) Message-ID: <20171027002537.C0C143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0bec73c1eb86a91e15cfa8df53d14264ff854160/ghc >--------------------------------------------------------------- commit 0bec73c1eb86a91e15cfa8df53d14264ff854160 Author: Andrey Mokhov Date: Sun Oct 23 18:15:51 2016 +0100 Drop GenApply arguments, as it actually needs none. >--------------------------------------------------------------- 0bec73c1eb86a91e15cfa8df53d14264ff854160 hadrian.cabal | 1 - src/Settings/Builders/GenApply.hs | 6 ------ src/Settings/Default.hs | 2 -- 3 files changed, 9 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 6039b01..3b19557 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -74,7 +74,6 @@ executable hadrian , Settings.Builders.Cc , Settings.Builders.Configure , Settings.Builders.DeriveConstants - , Settings.Builders.GenApply , Settings.Builders.GenPrimopCode , Settings.Builders.Ghc , Settings.Builders.GhcCabal diff --git a/src/Settings/Builders/GenApply.hs b/src/Settings/Builders/GenApply.hs deleted file mode 100644 index b268c07..0000000 --- a/src/Settings/Builders/GenApply.hs +++ /dev/null @@ -1,6 +0,0 @@ -module Settings.Builders.GenApply (genApplyBuilderArgs) where - -import Settings.Builders.Common - -genApplyBuilderArgs :: Args -genApplyBuilderArgs = builder GenApply ? flag GhcUnregisterised ? arg "-u" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 4588c4b..f529019 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -16,7 +16,6 @@ import Settings.Builders.Ar import Settings.Builders.DeriveConstants import Settings.Builders.Cc import Settings.Builders.Configure -import Settings.Builders.GenApply import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc import Settings.Builders.GhcCabal @@ -52,7 +51,6 @@ defaultBuilderArgs = mconcat , ccBuilderArgs , configureBuilderArgs , deriveConstantsBuilderArgs - , genApplyBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs , ghcCabalBuilderArgs From git at git.haskell.org Fri Oct 27 00:25:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't separate build commands with an empty line.\n\nThis allows to fit more commands on screen. (412009d) Message-ID: <20171027002539.8D1973A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/412009d52e693f3f67b86a71de4e7f359cd3b2a8/ghc >--------------------------------------------------------------- commit 412009d52e693f3f67b86a71de4e7f359cd3b2a8 Author: Andrey Mokhov Date: Tue Jan 5 23:21:54 2016 +0000 Don't separate build commands with an empty line.\n\nThis allows to fit more commands on screen. >--------------------------------------------------------------- 412009d52e693f3f67b86a71de4e7f359cd3b2a8 src/Base.hs | 2 +- src/Rules/Actions.hs | 10 +++++----- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 69904c4..36f2eb9 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -174,7 +174,7 @@ putError msg = do -- | Render the given set of lines in a nice box of ASCII renderBox :: [String] -> String -renderBox ls = concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) +renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) where -- Minimum total width of the box in characters minimumBoxWidth = 32 diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d567747..6f116b5 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -71,7 +71,7 @@ copyFile source target = do createDirectory :: FilePath -> Action () createDirectory dir = do - putBuild $ "\n| Create directory " ++ dir + putBuild $ "| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir -- Note, the source directory is untracked @@ -85,7 +85,7 @@ moveDirectory source target = do -- Transform a given file by applying a function to its contents fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do - putBuild $ "\n| Fix " ++ file + putBuild $ "| Fix " ++ file old <- liftIO $ readFile file let new = f old length new `seq` liftIO $ writeFile file new @@ -93,14 +93,14 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] - putBuild $ "\n| Run configure in " ++ dir ++ "..." + putBuild $ "| Run configure in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "\n| Run make" ++ note ++ " in " ++ dir ++ "..." + putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args runBuilder :: Builder -> [String] -> Action () @@ -108,7 +108,7 @@ runBuilder builder args = do needBuilder laxDependencies builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate "," args ++ ")" - putBuild $ "\n| Run " ++ show builder ++ note + putBuild $ "| Run " ++ show builder ++ note quietly $ cmd [path] args -- Print out key information about the command being executed From git at git.haskell.org Fri Oct 27 00:25:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep up with recent GHC changes, see #215. (e34e7e2) Message-ID: <20171027002541.60F7C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e34e7e287864bd8028e1b1d2e4b526135106787a/ghc >--------------------------------------------------------------- commit e34e7e287864bd8028e1b1d2e4b526135106787a Author: Andrey Mokhov Date: Mon Apr 18 01:19:21 2016 +0100 Keep up with recent GHC changes, see #215. >--------------------------------------------------------------- e34e7e287864bd8028e1b1d2e4b526135106787a cfg/system.config.in | 2 ++ shaking-up-ghc.cabal | 2 +- src/Oracles/Config/Flag.hs | 2 ++ src/Settings/Builders/Ghc.hs | 8 +++++++- src/Settings/Packages/GhcCabal.hs | 10 ++++++++-- 5 files changed, 20 insertions(+), 4 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index d053e65..f235f19 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -70,6 +70,8 @@ ghc-major-version = @GhcMajVersion@ ghc-minor-version = @GhcMinVersion@ ghc-patch-level = @GhcPatchLevel@ +supports-this-unit-id = @SUPPORTS_THIS_UNIT_ID@ + project-name = @ProjectName@ project-version = @ProjectVersion@ project-version-int = @ProjectVersionInt@ diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 17b48f0..92be3c7 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -118,7 +118,7 @@ executable ghc-shake , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* + , Cabal == 1.22.* || == 1.24.* , containers == 0.5.* , directory == 1.2.* , extra == 1.4.* diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 9d33445..449e2b2 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -18,6 +18,7 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken + | SupportsThisUnitId | WithLibdw | UseSystemFfi @@ -34,6 +35,7 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" + SupportsThisUnitId -> "supports-this-unit-id" WithLibdw -> "with-libdw" UseSystemFfi -> "use-system-ffi" value <- askConfigWithDefault key . putError diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 067c76e..a07c512 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -5,6 +5,7 @@ module Settings.Builders.Ghc ( import Base import Expression import GHC +import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.PackageData import Predicates hiding (way, stage) @@ -114,11 +115,16 @@ packageGhcArgs = do lift . when (isLibrary pkg) $ do conf <- pkgConfFile context need [conf] + -- FIXME: Get rid of to-be-deprecated -this-package-key. + thisArg <- do + not0 <- notStage0 + unit <- getFlag SupportsThisUnitId + return $ if not0 || unit then "-this-unit-id " else "-this-package-key " mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" , bootPackageDbArgs - , isLibrary pkg ? (arg $ "-this-package-key " ++ compId) + , isLibrary pkg ? (arg $ thisArg ++ compId) , append $ map ("-package-id " ++) pkgDepIds ] -- TODO: Improve handling of "cabal_macros.h" diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 762720f..80bda57 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -2,7 +2,8 @@ module Settings.Packages.GhcCabal (ghcCabalPackageArgs) where import Base import Expression -import GHC (ghcCabal) +import GHC +import Oracles.Config.Setting import Predicates (builderGhc, package, stage0) import Settings @@ -19,8 +20,13 @@ ghcCabalBootArgs = stage0 ? do path <- getBuildPath let cabalMacros = path -/- "autogen/cabal_macros.h" cabalMacrosBoot = pkgPath ghcCabal -/- "cabal_macros_boot.h" + cabalDeps <- fromDiffExpr $ mconcat + [ append [ array, base, bytestring, containers, deepseq, directory + , pretty, process, time ] + , notM windowsHost ? append [unix] + , windowsHost ? append [win32] ] mconcat - [ remove ["-hide-all-packages"] + [ append [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , removePair "-optP-include" $ "-optP" ++ cabalMacros , arg "--make" , arg "-j" From git at git.haskell.org Fri Oct 27 00:25:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move auxiliary build files to _build/hadrian (aa6bba1) Message-ID: <20171027002541.E645F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aa6bba126fecd412920fa7ca1e90fe9716b328d0/ghc >--------------------------------------------------------------- commit aa6bba126fecd412920fa7ca1e90fe9716b328d0 Author: Andrey Mokhov Date: Sun Oct 23 19:05:51 2016 +0100 Move auxiliary build files to _build/hadrian >--------------------------------------------------------------- aa6bba126fecd412920fa7ca1e90fe9716b328d0 src/Settings/Paths.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 2727696..7147264 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -16,7 +16,7 @@ import UserSettings -- | Path to the directory containing the Shake database and other auxiliary -- files generated by Hadrian. shakeFilesPath :: FilePath -shakeFilesPath = buildRootPath -/- "hadrian/shake-files" +shakeFilesPath = buildRootPath -/- "hadrian" -- | Boot package versions extracted from @.cabal@ files. bootPackageConstraints :: FilePath From git at git.haskell.org Fri Oct 27 00:25:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to invoke libtool via bash. (9e731d6) Message-ID: <20171027002543.159A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e731d6d7d730b14e805886ca34df7f0bfbac745/ghc >--------------------------------------------------------------- commit 9e731d6d7d730b14e805886ca34df7f0bfbac745 Author: Andrey Mokhov Date: Tue Jan 5 23:43:25 2016 +0000 Try to invoke libtool via bash. See #103. >--------------------------------------------------------------- 9e731d6d7d730b14e805886ca34df7f0bfbac745 src/Rules/IntegerGmp.hs | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 0d5da26..193b43d 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -6,7 +6,6 @@ import GHC import Oracles.Config.Setting import Rules.Actions import Settings.User -import Settings.TargetDirectory integerGmpBase :: FilePath integerGmpBase = "libraries/integer-gmp/gmp" @@ -103,19 +102,19 @@ integerGmpRules = do args <- configureArguments runConfigure integerGmpBuild envs args - -- check whether we need to build in tree gmp - -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` - + -- TODO: currently we configure integerGmp package twice -- optimise runConfigure (pkgPath integerGmp) [] [] + -- check whether we need to build in tree gmp + -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk then do - putBuild "\n| GMP framework detected and will be used" + putBuild "| GMP framework detected and will be used" copyFile integerGmpLibraryFakeH integerGmpLibraryH else do - putBuild "\n| No GMP framework detected" - runMake integerGmpBuild [] + putBuild "| No GMP framework detected; in tree GMP will be built" + runMake integerGmpBuild ["LIBTOOL=\"bash libtool\""] copyFile integerGmpLibraryInTreeH integerGmpLibraryH -- TODO: why copy library, can we move it instead? From git at git.haskell.org Fri Oct 27 00:25:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on cabalDeps list. (d1c8ba4) Message-ID: <20171027002544.DE9983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1c8ba4b5787d0995538cc0b69a4aa93969f6488/ghc >--------------------------------------------------------------- commit d1c8ba4b5787d0995538cc0b69a4aa93969f6488 Author: Andrey Mokhov Date: Mon Apr 18 10:16:13 2016 +0100 Add a note on cabalDeps list. See #215. [skip ci] >--------------------------------------------------------------- d1c8ba4b5787d0995538cc0b69a4aa93969f6488 src/Settings/Packages/GhcCabal.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 80bda57..1dac541 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -20,6 +20,9 @@ ghcCabalBootArgs = stage0 ? do path <- getBuildPath let cabalMacros = path -/- "autogen/cabal_macros.h" cabalMacrosBoot = pkgPath ghcCabal -/- "cabal_macros_boot.h" + -- Note: We could have computed 'cabalDeps' instead of hard-coding it + -- but this doesn't worth the effort, since we plan to drop ghc-cabal + -- altogether at some point. See #18. cabalDeps <- fromDiffExpr $ mconcat [ append [ array, base, bytestring, containers, deepseq, directory , pretty, process, time ] From git at git.haskell.org Fri Oct 27 00:25:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build Hadrian in /hadrian/bin (179f5b1) Message-ID: <20171027002545.664B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/179f5b14a138c41cd06423c17a41684157fcdb89/ghc >--------------------------------------------------------------- commit 179f5b14a138c41cd06423c17a41684157fcdb89 Author: Andrey Mokhov Date: Sun Oct 23 19:06:09 2016 +0100 Build Hadrian in /hadrian/bin >--------------------------------------------------------------- 179f5b14a138c41cd06423c17a41684157fcdb89 .gitignore | 3 +-- build.bat | 32 ++++++++++++++++---------------- build.sh | 8 ++++---- 3 files changed, 21 insertions(+), 22 deletions(-) diff --git a/.gitignore b/.gitignore index 87bedb8..6b06fea 100644 --- a/.gitignore +++ b/.gitignore @@ -2,8 +2,7 @@ cfg/system.config # build.bat and build.sh specific -/hadrian -/hadrian.exe +/bin/ # build.cabal.sh specific /dist/ diff --git a/build.bat b/build.bat index 6e86d42..2bc9a95 100644 --- a/build.bat +++ b/build.bat @@ -1,20 +1,20 @@ @cd %~dp0 - at mkdir ../_build/hadrian 2> nul + at mkdir bin 2> nul - at set ghcArgs=--make ^ - -Wall ^ - -fno-warn-name-shadowing ^ - -XRecordWildCards ^ - src/Main.hs ^ - -threaded ^ - -isrc ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=../_build/hadrian ^ - -i../libraries/Cabal/Cabal ^ - -j ^ - -O ^ - -o hadrian + at set ghcArgs=--make ^ + -Wall ^ + -fno-warn-name-shadowing ^ + -XRecordWildCards ^ + src\Main.hs ^ + -threaded ^ + -isrc ^ + -i..\libraries\Cabal\Cabal ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=bin ^ + -j ^ + -O ^ + -o bin\hadrian @set hadrianArgs=--lint ^ --directory ^ @@ -28,4 +28,4 @@ @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains @set GHC_PACKAGE_PATH= - at hadrian %hadrianArgs% + at bin\hadrian %hadrianArgs% diff --git a/build.sh b/build.sh index d627c58..0f957cf 100755 --- a/build.sh +++ b/build.sh @@ -39,7 +39,7 @@ if type cabal > /dev/null 2>&1; then fi fi -mkdir -p "$root/../_build/hadrian" +mkdir -p "$root/bin" ghc \ "$root/src/Main.hs" \ @@ -51,11 +51,11 @@ ghc \ -rtsopts \ -with-rtsopts=-I0 \ -threaded \ - -outputdir="$root/../_build/hadrian" \ + -outputdir="$root/bin" \ -j -O \ - -o "$root/hadrian" + -o "$root/bin/hadrian" -"$root/hadrian" \ +"$root/bin/hadrian" \ --lint \ --directory "$root/.." \ "$@" From git at git.haskell.org Fri Oct 27 00:25:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Another attempt to invoke libtool via bash, see #103. (375d41e) Message-ID: <20171027002546.86EDE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/375d41e7658d6b4f91c15eaf1ac74ce37b720f1b/ghc >--------------------------------------------------------------- commit 375d41e7658d6b4f91c15eaf1ac74ce37b720f1b Author: Andrey Mokhov Date: Wed Jan 6 00:51:54 2016 +0000 Another attempt to invoke libtool via bash, see #103. >--------------------------------------------------------------- 375d41e7658d6b4f91c15eaf1ac74ce37b720f1b src/Rules/Actions.hs | 6 +++--- src/Rules/IntegerGmp.hs | 2 +- src/Rules/Libffi.hs | 4 ++-- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 6f116b5..9250357 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -99,15 +99,15 @@ runConfigure dir opts args = do runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] - let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir, "MAKEFLAGS="] args + quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir] args runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do needBuilder laxDependencies builder path <- builderPath builder - let note = if null args then "" else " (" ++ intercalate "," args ++ ")" + let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ show builder ++ note quietly $ cmd [path] args diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 193b43d..142a9c6 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -114,7 +114,7 @@ integerGmpRules = do copyFile integerGmpLibraryFakeH integerGmpLibraryH else do putBuild "| No GMP framework detected; in tree GMP will be built" - runMake integerGmpBuild ["LIBTOOL=\"bash libtool\""] + runMake integerGmpBuild ["MAKEFLAGS='LIBTOOL=bash\\ libtool'"] copyFile integerGmpLibraryInTreeH integerGmpLibraryH -- TODO: why copy library, can we move it instead? diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 041650f..9d77814 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -91,8 +91,8 @@ libffiRules = do args <- configureArguments runConfigure libffiBuild envs args - runMake libffiBuild [] - runMake libffiBuild ["install"] + runMake libffiBuild ["MAKEFLAGS="] + runMake libffiBuild ["MAKEFLAGS=", "install"] forM_ ["ffi.h", "ffitarget.h"] $ \file -> do let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file From git at git.haskell.org Fri Oct 27 00:25:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: List installed packages in CI (61032aa) Message-ID: <20171027002548.700D23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/61032aa99bc8f1afab5e0f3487202c30488243fb/ghc >--------------------------------------------------------------- commit 61032aa99bc8f1afab5e0f3487202c30488243fb Author: Andrey Mokhov Date: Fri Apr 22 12:21:26 2016 +0100 List installed packages in CI >--------------------------------------------------------------- 61032aa99bc8f1afab5e0f3487202c30488243fb .travis.yml | 1 + appveyor.yml | 1 + 2 files changed, 2 insertions(+) diff --git a/.travis.yml b/.travis.yml index 21bf769..0e59864 100644 --- a/.travis.yml +++ b/.travis.yml @@ -57,6 +57,7 @@ install: - ( cd ghc && ./boot ) - ( cd ghc && ./configure ) - cat ghc/shake-build/cfg/system.config + - ghc-pkg list script: - ( cd ghc/shake-build && cabal haddock --internal ) diff --git a/appveyor.yml b/appveyor.yml index 537983c..88ca776 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -35,6 +35,7 @@ install: - stack --version - alex --version - happy --version + - ghc-pkg list build_script: - cd C:\msys64\home\ghc\shake-build From git at git.haskell.org Fri Oct 27 00:25:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compute package dependencies only for packages we build (67f433b) Message-ID: <20171027002549.02DE93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/67f433bf028ec4c4251b928fa476ff1302e8299c/ghc >--------------------------------------------------------------- commit 67f433bf028ec4c4251b928fa476ff1302e8299c Author: Andrey Mokhov Date: Thu Oct 27 20:00:58 2016 +0100 Compute package dependencies only for packages we build See #265 >--------------------------------------------------------------- 67f433bf028ec4c4251b928fa476ff1302e8299c src/Rules/Cabal.hs | 5 +++-- src/Rules/Test.hs | 2 +- src/Settings.hs | 5 ++++- src/Settings/Default.hs | 1 - 4 files changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 409ca1b..8848268 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -16,7 +16,7 @@ cabalRules :: Rules () cabalRules = do -- Cache boot package constraints (to be used in 'cabalArgs'). bootPackageConstraints %> \out -> do - bootPkgs <- interpretInContext (stageContext Stage0) getPackages + bootPkgs <- stagePackages Stage0 let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] @@ -28,7 +28,8 @@ cabalRules = do -- Cache package dependencies. packageDependencies %> \out -> do - pkgDeps <- forM (sort knownPackages) $ \pkg -> + pkgs <- concatMapM stagePackages [Stage0 .. Stage2] + pkgDeps <- forM (sort pkgs) $ \pkg -> if pkg `elem` [hp2ps, libffi, rts, touchy, unlit] then return $ pkgNameString pkg else do diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 3b2fd1b..18513a7 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -23,7 +23,7 @@ testRules = do "test" ~> do let yesNo x = show $ if x then "YES" else "NO" - pkgs <- interpretInContext (stageContext Stage1) getPackages + pkgs <- stagePackages Stage1 tests <- filterM doesDirectoryExist $ concat [ [ pkgPath pkg -/- "tests", pkgPath pkg -/- "tests-ghc" ] | pkg <- pkgs, isLibrary pkg, pkg /= rts, pkg /= libffi ] diff --git a/src/Settings.hs b/src/Settings.hs index 3fdf14f..0a71c90 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,7 +1,7 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, - getContextDirectory, getBuildPath + getContextDirectory, getBuildPath, stagePackages ) where import Base @@ -28,6 +28,9 @@ getRtsWays = fromDiffExpr $ rtsWays flavour getPackages :: Expr [Package] getPackages = fromDiffExpr $ packages flavour +stagePackages :: Stage -> Action [Package] +stagePackages stage = interpretInContext (stageContext stage) getPackages + getPackagePath :: Expr FilePath getPackagePath = pkgPath <$> getPackage diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index f529019..f7ef62e 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -65,7 +65,6 @@ defaultBuilderArgs = mconcat , makeBuilderArgs , tarBuilderArgs ] - -- | All 'Package'-dependent command line arguments. defaultPackageArgs :: Args defaultPackageArgs = mconcat From git at git.haskell.org Fri Oct 27 00:25:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (da61b39) Message-ID: <20171027002550.096833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da61b39228f39feb4d201d9505bd1ef02dc6518e/ghc >--------------------------------------------------------------- commit da61b39228f39feb4d201d9505bd1ef02dc6518e Author: Andrey Mokhov Date: Wed Jan 6 01:20:21 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- da61b39228f39feb4d201d9505bd1ef02dc6518e README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 43b74be..90f6422 100644 --- a/README.md +++ b/README.md @@ -59,7 +59,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system run the build script with `-B` flag. This will force Shake to rerun all rules, even if the results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). +To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). How to contribute From git at git.haskell.org Fri Oct 27 00:25:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run ghc-pkg list through stack (e29218a) Message-ID: <20171027002552.876F23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e29218a5f8df4e9c03e30b2f0579d5f8ea8ac647/ghc >--------------------------------------------------------------- commit e29218a5f8df4e9c03e30b2f0579d5f8ea8ac647 Author: Andrey Mokhov Date: Fri Apr 22 13:04:44 2016 +0100 Run ghc-pkg list through stack >--------------------------------------------------------------- e29218a5f8df4e9c03e30b2f0579d5f8ea8ac647 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 88ca776..6cc17b6 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -35,7 +35,7 @@ install: - stack --version - alex --version - happy --version - - ghc-pkg list + - stack exec -- ghc-pkg list build_script: - cd C:\msys64\home\ghc\shake-build From git at git.haskell.org Fri Oct 27 00:25:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add rule 'sdist-ghc' (d4d9c03) Message-ID: <20171027002552.E96F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4d9c03de0be0762f973f106d2d4f4b2000d63f1/ghc >--------------------------------------------------------------- commit d4d9c03de0be0762f973f106d2d4f4b2000d63f1 Author: Kai Harries Date: Thu Jun 9 21:50:24 2016 +0200 Add rule 'sdist-ghc' See #219 >--------------------------------------------------------------- d4d9c03de0be0762f973f106d2d4f4b2000d63f1 hadrian.cabal | 1 + src/Main.hs | 2 + src/Rules/Clean.hs | 1 + src/Rules/SourceDist.hs | 105 ++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 109 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 3b19557..4d6fbdf 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -64,6 +64,7 @@ executable hadrian , Rules.Program , Rules.Register , Rules.Selftest + , Rules.SourceDist , Rules.Test , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg diff --git a/src/Main.hs b/src/Main.hs index 66f897f..b4c2d42 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -7,6 +7,7 @@ import qualified Environment import qualified Rules import qualified Rules.Clean import qualified Rules.Oracles +import qualified Rules.SourceDist import qualified Rules.Selftest import qualified Rules.Test import qualified Settings.Paths @@ -23,6 +24,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do rules = do Rules.Clean.cleanRules Rules.Oracles.oracleRules + Rules.SourceDist.sourceDistRules Rules.Selftest.selftestRules Rules.Test.testRules Rules.buildRules diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 4678054..50edd20 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -16,6 +16,7 @@ cleanRules = do removeDirectory generatedPath removeDirectory programInplacePath removeDirectory "inplace/lib" + removeDirectory "sdistprep" putBuild $ "| Remove files generated by ghc-cabal..." forM_ knownPackages $ \pkg -> forM_ [Stage0 ..] $ \stage -> do diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs new file mode 100644 index 0000000..a2cc8f4 --- /dev/null +++ b/src/Rules/SourceDist.hs @@ -0,0 +1,105 @@ +module Rules.SourceDist (sourceDistRules) where + +import Base +import Builder +import Oracles.Config.Setting +import Oracles.DirectoryContent +import Rules.Actions +import UserSettings + +sourceDistRules :: Rules () +sourceDistRules = do + "sdist-ghc" ~> do + version <- setting ProjectVersion + need ["sdistprep/ghc-" ++ version ++ "-src.tar.xz"] + putSuccess "| Done. " + "sdistprep/ghc-*-src.tar.xz" %> \fname -> do + let tarName = takeFileName fname + treePath = "sdistprep/ghc" dropTarXz tarName + prepareTree treePath + runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." tarName, dropTarXz tarName] + "GIT_COMMIT_ID" %> \fname -> + setting ProjectGitCommitId >>= writeFileChanged fname + "VERSION" %> \fname -> + setting ProjectVersion >>= writeFileChanged fname + where + dropTarXz = dropExtension . dropExtension + + +prepareTree :: FilePath -> Action () +prepareTree dest = do + mapM_ cpDir srcDirs + mapM_ cpFile srcFiles + where + cpFile a = copyFile a (dest a) + cpDir a = copyDirectoryContent (Not excluded) a (dest takeFileName a) + excluded = Or + [ Test "//.*" + , Test "//#*" + , Test "//*-SAVE" + , Test "//*.orig" + , Test "//*.rej" + , Test "//*~" + , Test "//autom4te*" + , Test "//dist" + , Test "//log" + , Test "//stage0" + , Test "//stage1" + , Test "//stage2" + , Test "//stage3" + , Test "hadrian/cabal.sandbox.config" + , Test "hadrian/cfg/system.config" + , Test "hadrian/dist" + , Test "hadrian/UserSettings.hs" + , Test "libraries//*.buildinfo" + , Test "libraries//GNUmakefile" + , Test "libraries//config.log" + , Test "libraries//config.status" + , Test "libraries//configure" + , Test "libraries//ghc.mk" + , Test "libraries//include/Hs*Config.h" + , Test "libraries/dph" + , Test "libraries/parallel" + , Test "libraries/primitive" + , Test "libraries/random" + , Test "libraries/stm" + , Test "libraries/vector" + , Test "mk/build.mk" ] + srcDirs = + [ "bindisttest" + , "compiler" + , "distrib" + , "docs" + , "docs" + , "driver" + , "ghc" + , "hadrian" + , "includes" + , "iserv" + , "libffi" + , "libffi-tarballs" + , "libraries" + , "mk" + , "rts" + , "rules" + , "utils" ] + srcFiles = + [ "ANNOUNCE" + , "GIT_COMMIT_ID" + , "HACKING.md" + , "INSTALL.md" + , "LICENSE" + , "MAKEHELP.md" + , "Makefile" + , "README.md" + , "VERSION" + , "aclocal.m4" + , "boot" + , "config.guess" + , "config.sub" + , "configure" + , "configure.ac" + , "ghc.mk" + , "install-sh" + , "packages" + , "settings.in" ] From git at git.haskell.org Fri Oct 27 00:25:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a rule for libraries/integer-gmp/gmp/gmp.h, see #103. (d716ae5) Message-ID: <20171027002553.85B5E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d716ae544c182207ba70b3becdb11bcc3aca5a73/ghc >--------------------------------------------------------------- commit d716ae544c182207ba70b3becdb11bcc3aca5a73 Author: Andrey Mokhov Date: Wed Jan 6 01:50:10 2016 +0000 Add a rule for libraries/integer-gmp/gmp/gmp.h, see #103. >--------------------------------------------------------------- d716ae544c182207ba70b3becdb11bcc3aca5a73 src/Rules/IntegerGmp.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 142a9c6..2b9bbd9 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -116,7 +116,8 @@ integerGmpRules = do putBuild "| No GMP framework detected; in tree GMP will be built" runMake integerGmpBuild ["MAKEFLAGS='LIBTOOL=bash\\ libtool'"] - copyFile integerGmpLibraryInTreeH integerGmpLibraryH + copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryInTreeH + copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryH -- TODO: why copy library, can we move it instead? copyFile (integerGmpBuild -/- ".libs/libgmp.a") integerGmpLibrary @@ -126,3 +127,5 @@ integerGmpRules = do runBuilder Ranlib [integerGmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" + + integerGmpLibraryInTreeH %> \_ -> need [integerGmpLibraryH] From git at git.haskell.org Fri Oct 27 00:25:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use Docker on Travis. (ee592f4) Message-ID: <20171027002556.4FE0F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee592f4254da5b9f2db59ea465fd55adf66b771f/ghc >--------------------------------------------------------------- commit ee592f4254da5b9f2db59ea465fd55adf66b771f Author: Andrey Mokhov Date: Fri Apr 22 13:08:07 2016 +0100 Don't use Docker on Travis. See #229. >--------------------------------------------------------------- ee592f4254da5b9f2db59ea465fd55adf66b771f .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0e59864..2f0739a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,4 +1,4 @@ -sudo: false +sudo: true matrix: include: From git at git.haskell.org Fri Oct 27 00:25:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #265 from KaiHa/wip/ticket219 (0bfadf3) Message-ID: <20171027002556.AA7593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0bfadf34ec199a40c4276c0935ba8c725cf51171/ghc >--------------------------------------------------------------- commit 0bfadf34ec199a40c4276c0935ba8c725cf51171 Merge: 67f433b d4d9c03 Author: Andrey Mokhov Date: Thu Oct 27 23:19:12 2016 +0100 Merge pull request #265 from KaiHa/wip/ticket219 Implement 'sdist-ghc' rule >--------------------------------------------------------------- 0bfadf34ec199a40c4276c0935ba8c725cf51171 hadrian.cabal | 1 + src/Main.hs | 2 + src/Rules/Clean.hs | 1 + src/Rules/SourceDist.hs | 105 ++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 109 insertions(+) From git at git.haskell.org Fri Oct 27 00:25:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds osx to the list of operatin systems in the travis.yml (f466624) Message-ID: <20171027002557.115A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4666240df45766aa8d8e38af4a0d88d50e9325c/ghc >--------------------------------------------------------------- commit f4666240df45766aa8d8e38af4a0d88d50e9325c Author: Moritz Angermann Date: Wed Jan 6 11:50:02 2016 +0800 Adds osx to the list of operatin systems in the travis.yml This should fix #111. >--------------------------------------------------------------- f4666240df45766aa8d8e38af4a0d88d50e9325c .travis.yml | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.travis.yml b/.travis.yml index 9079fa9..58e23cd 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,5 +1,9 @@ sudo: false +os: + - linux + - osx + matrix: include: - env: From git at git.haskell.org Fri Oct 27 00:26:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try full build on Mac OS X. (219da37) Message-ID: <20171027002600.39A9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/219da3757e6f5ee6761c672099a005987156849e/ghc >--------------------------------------------------------------- commit 219da3757e6f5ee6761c672099a005987156849e Author: Andrey Mokhov Date: Fri Apr 22 13:47:29 2016 +0100 Try full build on Mac OS X. >--------------------------------------------------------------- 219da3757e6f5ee6761c672099a005987156849e .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 2f0739a..d6092fb 100644 --- a/.travis.yml +++ b/.travis.yml @@ -20,7 +20,7 @@ matrix: - cabal install alex happy - os: osx - env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg + env: TARGET= before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Fri Oct 27 00:26:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on source distribution (0959e45) Message-ID: <20171027002600.9AC113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0959e45fab08b850fdb5b555ea7250e493386976/ghc >--------------------------------------------------------------- commit 0959e45fab08b850fdb5b555ea7250e493386976 Author: Andrey Mokhov Date: Fri Oct 28 17:33:11 2016 +0100 Add a note on source distribution See #219. >--------------------------------------------------------------- 0959e45fab08b850fdb5b555ea7250e493386976 README.md | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 718421f..d869f4b 100644 --- a/README.md +++ b/README.md @@ -98,6 +98,10 @@ complete separation of GHC sources and build artefacts: [#113][build-artefacts-i * `build -B` forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. +#### Source distribution + +To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` target. + #### Testing * `build validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` @@ -119,7 +123,7 @@ The new build system still lacks many important features: * Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. -* There is no support for installation or binary/source distribution: [#219][install-issue]. +* There is no support for installation or binary distribution: [#219][install-issue]. Check out [milestones] to see when we hope to resolve the above limitations. From git at git.haskell.org Fri Oct 27 00:26:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do we need tabs? (d705676) Message-ID: <20171027002600.A29983A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d705676ac7aee5a5bf153ad0c9d44696ce127d70/ghc >--------------------------------------------------------------- commit d705676ac7aee5a5bf153ad0c9d44696ce127d70 Author: Moritz Angermann Date: Wed Jan 6 11:57:30 2016 +0800 Do we need tabs? >--------------------------------------------------------------- d705676ac7aee5a5bf153ad0c9d44696ce127d70 .travis.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 58e23cd..0a85228 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,8 +1,8 @@ sudo: false os: - - linux - - osx + - linux + - osx matrix: include: From git at git.haskell.org Fri Oct 27 00:26:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to shake-0.15.6. (cf5ab9a) Message-ID: <20171027002604.0FCC83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf5ab9ad72cf29153cc0cbfdd510465fc6abcbc9/ghc >--------------------------------------------------------------- commit cf5ab9ad72cf29153cc0cbfdd510465fc6abcbc9 Author: Andrey Mokhov Date: Fri Apr 22 17:05:28 2016 +0100 Switch to shake-0.15.6. >--------------------------------------------------------------- cf5ab9ad72cf29153cc0cbfdd510465fc6abcbc9 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 92be3c7..da19de1 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -124,7 +124,7 @@ executable ghc-shake , extra == 1.4.* , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.9 - , shake == 0.15.* + , shake == 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* ghc-options: -Wall From git at git.haskell.org Fri Oct 27 00:26:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Retry pacman package downloads on AppVeyor to make CI more robust (6596774) Message-ID: <20171027002604.B02F23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65967740632fed04975ead2f3ea9fe2225e45671/ghc >--------------------------------------------------------------- commit 65967740632fed04975ead2f3ea9fe2225e45671 Author: Andrey Mokhov Date: Fri Oct 28 23:03:05 2016 +0100 Retry pacman package downloads on AppVeyor to make CI more robust >--------------------------------------------------------------- 65967740632fed04975ead2f3ea9fe2225e45671 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 7552a56..7687500 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -22,7 +22,7 @@ install: # Install all Hadrian and GHC build dependencies - cd hadrian - stack setup > nul - - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm + - appveyor-retry stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: # Build Hadrian From git at git.haskell.org Fri Oct 27 00:26:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: env for all, apt only for linux (a7610e0) Message-ID: <20171027002604.BDF4C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7610e09f39b37e683848a161121f52ce01555df/ghc >--------------------------------------------------------------- commit a7610e09f39b37e683848a161121f52ce01555df Author: Moritz Angermann Date: Wed Jan 6 12:15:00 2016 +0800 env for all, apt only for linux >--------------------------------------------------------------- a7610e09f39b37e683848a161121f52ce01555df .travis.yml | 32 ++++++++++++++------------------ 1 file changed, 14 insertions(+), 18 deletions(-) diff --git a/.travis.yml b/.travis.yml index 0a85228..0a8f49a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -4,24 +4,20 @@ os: - linux - osx -matrix: - include: - - env: - CABALVER=1.22 - GHCVER=7.10.3 - - addons: { - apt: { - packages: [ - ghc-7.10.3, - alex-3.1.4, - happy-1.19.5, - cabal-install-1.22, - zlib1g-dev - ], - sources: [hvr-ghc] - } - } +env: + - CABALVER=1.22 + - GHCVER=7.10.3 + +addons: + linux: + apt: + packages: + - ghc-7.10.3, + - alex-3.1.4, + - happy-1.19.5, + - cabal-install-1.22, + - zlib1g-dev + sources: hvr-ghc before_install: From git at git.haskell.org Fri Oct 27 00:26:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add shake-0.15.6 to stack extra-deps (028ef28) Message-ID: <20171027002607.AFF403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/028ef285adb1b4c4ada79c1ec2ee891e240b0c59/ghc >--------------------------------------------------------------- commit 028ef285adb1b4c4ada79c1ec2ee891e240b0c59 Author: Moritz Kiefer Date: Fri Apr 22 18:24:35 2016 +0200 Add shake-0.15.6 to stack extra-deps >--------------------------------------------------------------- 028ef285adb1b4c4ada79c1ec2ee891e240b0c59 stack.yaml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index 0772c76..0d8809b 100644 --- a/stack.yaml +++ b/stack.yaml @@ -8,7 +8,8 @@ packages: - '.' # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) -extra-deps: [] +extra-deps: +- shake-0.15.6 # Override default flag values for local packages and extra-deps flags: {} From git at git.haskell.org Fri Oct 27 00:26:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor package-data generation for custom packages (cfecd73) Message-ID: <20171027002609.007183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cfecd733f3e9df9c5ae6e657588a72153871d549/ghc >--------------------------------------------------------------- commit cfecd733f3e9df9c5ae6e657588a72153871d549 Author: Andrey Mokhov Date: Sat Oct 29 01:19:03 2016 +0100 Refactor package-data generation for custom packages >--------------------------------------------------------------- cfecd733f3e9df9c5ae6e657588a72153871d549 src/Rules/Data.hs | 119 +++++++++++++++++++++++------------------------------- 1 file changed, 50 insertions(+), 69 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 502fc3c..cefd2fa 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -57,80 +57,61 @@ buildPackageData context at Context {..} = do -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps. priority 2.0 $ do - when (package == hp2ps) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" - , "Reorder.c", "TopTwenty.c", "AuxFile.c" - , "Deviation.c", "HpFile.c", "Marks.c", "Scale.c" - , "TraceElement.c", "Axes.c", "Dimensions.c", "Key.c" - , "PsFile.c", "Shade.c", "Utilities.c" ] - contents = unlines $ map (prefix++) - [ "PROGNAME = hp2ps" - , "C_SRCS = " ++ unwords cSrcs - , "DEP_EXTRA_LIBS = m" - , "CC_OPTS = -I" ++ generatedPath ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk - - when (package == unlit) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - contents = unlines $ map (prefix++) - [ "PROGNAME = unlit" - , "C_SRCS = unlit.c" - , "SYNOPSIS = Literate script filter." ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk - - when (package == touchy) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - contents = unlines $ map (prefix++) - [ "PROGNAME = touchy" - , "C_SRCS = touchy.c" ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk + when (package `elem` [hp2ps, rts, touchy, unlit]) $ dataFile %> + generatePackageData context -- Bootstrapping `ghcCabal`: although `ghcCabal` is a proper cabal -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. - when (package == ghcCabal && stage == Stage0) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - contents = unlines $ map (prefix++) - [ "PROGNAME = ghc-cabal" - , "MODULES = Main" - , "SYNOPSIS = Bootstrapped ghc-cabal utility." - , "HS_SRC_DIRS = ." ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk + when (package == ghcCabal && stage == Stage0) $ dataFile %> + generatePackageData context + +generatePackageData :: Context -> FilePath -> Action () +generatePackageData context at Context {..} file = do + orderOnly =<< interpretInContext context generatedDependencies + asmSrcs <- packageAsmSources package + cSrcs <- packageCSources package + cmmSrcs <- packageCmmSources package + let prefix = fixKey (buildPath context) ++ "_" + pkgKey = if isLibrary package then "COMPONENT_ID = " else "PROGNAME = " + writeFileChanged file . unlines . map (prefix ++) $ + [ pkgKey ++ pkgNameString package ] ++ + [ "S_SRCS = " ++ unwords asmSrcs ] ++ + [ "C_SRCS = " ++ unwords cSrcs ] ++ + [ "CMM_SRCS = " ++ unwords cmmSrcs ] ++ + [ "DEP_EXTRA_LIBS = m" | package == hp2ps ] ++ + [ "CC_OPTS = -I" ++ generatedPath | package `elem` [hp2ps, rts]] ++ + [ "MODULES = Main" | package == ghcCabal ] ++ + [ "HS_SRC_DIRS = ." | package == ghcCabal ] ++ + [ "SYNOPSIS = Bootstrapped ghc-cabal." | package == ghcCabal ] + putSuccess $ "| Successfully generated " ++ file + +packageCSources :: Package -> Action [FilePath] +packageCSources pkg + | pkg /= rts = getDirectoryFiles (pkgPath pkg) ["*.c"] + | otherwise = do + windows <- windowsHost + sources <- fmap (map unifyPath) . getDirectoryFiles (pkgPath pkg) . + map (-/- "*.c") $ [ ".", "hooks", "sm", "eventlog", "linker" ] ++ + [ if windows then "win32" else "posix" ] + return $ sources ++ [ rtsBuildPath -/- "c/sm/Evac_thr.c" ] + ++ [ rtsBuildPath -/- "c/sm/Scav_thr.c" ] + +packageAsmSources :: Package -> Action [FilePath] +packageAsmSources pkg + | pkg /= rts = return [] + | otherwise = do + buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] + buildStgCRunAsm <- anyTargetArch ["powerpc64le"] + return $ [ "AdjustorAsm.S" | buildAdjustor ] + ++ [ "StgCRunAsm.S" | buildStgCRunAsm ] - when (package == rts && stage == Stage1) $ do - dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - windows <- windowsHost - let prefix = fixKey (buildPath context) ++ "_" - dirs = [ ".", "hooks", "sm", "eventlog", "linker" ] - ++ [ if windows then "win32" else "posix" ] - cSrcs <- map unifyPath <$> - getDirectoryFiles (pkgPath package) (map (-/- "*.c") dirs) - cmmSrcs <- getDirectoryFiles (pkgPath package) ["*.cmm"] - buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] - buildStgCRunAsm <- anyTargetArch ["powerpc64le"] - let extraCSrcs = [ rtsBuildPath -/- "c/sm/Evac_thr.c" ] - ++ [ rtsBuildPath -/- "c/sm/Scav_thr.c" ] - extraCmmSrcs = [ rtsBuildPath -/- "cmm/AutoApply.cmm" ] - extraAsmSrcs = [ "AdjustorAsm.S" | buildAdjustor ] - ++ [ "StgCRunAsm.S" | buildStgCRunAsm ] - let contents = unlines $ map (prefix ++) - [ "C_SRCS = " ++ unwords (cSrcs ++ extraCSrcs) - , "CMM_SRCS = " ++ unwords (cmmSrcs ++ extraCmmSrcs) - , "S_SRCS = " ++ unwords extraAsmSrcs - , "CC_OPTS = -I" ++ generatedPath - , "COMPONENT_ID = rts" ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk +packageCmmSources :: Package -> Action [FilePath] +packageCmmSources pkg + | pkg /= rts = return [] + | otherwise = do + sources <- getDirectoryFiles (pkgPath pkg) ["*.cmm"] + return $ sources ++ [ rtsBuildPath -/- "cmm/AutoApply.cmm" ] -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' From git at git.haskell.org Fri Oct 27 00:26:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: collapse env, addons wihout linux (fb5ed14) Message-ID: <20171027002609.098E63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fb5ed14f7d95b0ea65e925c15e04ed766fad9247/ghc >--------------------------------------------------------------- commit fb5ed14f7d95b0ea65e925c15e04ed766fad9247 Author: Moritz Angermann Date: Wed Jan 6 12:16:48 2016 +0800 collapse env, addons wihout linux >--------------------------------------------------------------- fb5ed14f7d95b0ea65e925c15e04ed766fad9247 .travis.yml | 20 +++++++++----------- 1 file changed, 9 insertions(+), 11 deletions(-) diff --git a/.travis.yml b/.travis.yml index 0a8f49a..09ed050 100644 --- a/.travis.yml +++ b/.travis.yml @@ -5,19 +5,17 @@ os: - osx env: - - CABALVER=1.22 - - GHCVER=7.10.3 + - CABALVER=1.22 GHCVER=7.10.3 addons: - linux: - apt: - packages: - - ghc-7.10.3, - - alex-3.1.4, - - happy-1.19.5, - - cabal-install-1.22, - - zlib1g-dev - sources: hvr-ghc + apt: + packages: + - ghc-7.10.3, + - alex-3.1.4, + - happy-1.19.5, + - cabal-install-1.22, + - zlib1g-dev + sources: hvr-ghc before_install: From git at git.haskell.org Fri Oct 27 00:26:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #230 from cocreature/stack-shake-0.15.6 (6826d14) Message-ID: <20171027002611.261133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6826d14069396002e5a1fbee6b8c9c1a54cda815/ghc >--------------------------------------------------------------- commit 6826d14069396002e5a1fbee6b8c9c1a54cda815 Merge: cf5ab9a 028ef28 Author: Andrey Mokhov Date: Fri Apr 22 19:44:30 2016 +0100 Merge pull request #230 from cocreature/stack-shake-0.15.6 Add shake-0.15.6 to stack extra-deps >--------------------------------------------------------------- 6826d14069396002e5a1fbee6b8c9c1a54cda815 stack.yaml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:26:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Turn contextDirectory into stageDirectory (241d59a) Message-ID: <20171027002613.68B073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/241d59a5f814d5139ca9d6d9bfa0ea127357f505/ghc >--------------------------------------------------------------- commit 241d59a5f814d5139ca9d6d9bfa0ea127357f505 Author: Andrey Mokhov Date: Sat Oct 29 02:11:59 2016 +0100 Turn contextDirectory into stageDirectory >--------------------------------------------------------------- 241d59a5f814d5139ca9d6d9bfa0ea127357f505 src/GHC.hs | 23 ++++++----------------- src/Rules/Clean.hs | 6 ++---- src/Rules/Data.hs | 6 +++--- src/Rules/Generate.hs | 2 +- src/Rules/Register.hs | 2 +- src/Settings.hs | 2 +- src/Settings/Paths.hs | 5 ++--- 7 files changed, 16 insertions(+), 30 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 7cabff5..0312a3e 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -9,7 +9,7 @@ module GHC ( parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, programPath, contextDirectory, rtsContext + defaultKnownPackages, stageDirectory, rtsContext, programPath ) where import Base @@ -91,16 +91,15 @@ xhtml = library "xhtml" ghcSplit :: FilePath ghcSplit = "inplace/lib/bin/ghc-split" --- TODO: The following utils are not included into the build system because --- they seem to be unused or unrelated to the build process: checkUniques, --- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, --- lndir, mkdirhier, testremove, vagrant +-- | Relative path to the directory containing build artefacts of a given 'Stage'. +stageDirectory :: Stage -> FilePath +stageDirectory = stageString -- TODO: move to buildRootPath, see #113 -- TODO: simplify, add programInplaceLibPath -- | The relative path to the program executable programPath :: Context -> Maybe FilePath -programPath context at Context {..} +programPath Context {..} | package == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) | package `elem` [mkUserGuidePart] = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package @@ -123,19 +122,9 @@ programPath context at Context {..} | otherwise = Nothing where inplaceProgram name = programInplacePath -/- name <.> exe - installProgram name = pkgPath package -/- contextDirectory context + installProgram name = pkgPath package -/- stageDirectory stage -/- "build/tmp" -/- name <.> exe -- TODO: Move this elsewhere. rtsContext :: Context rtsContext = vanillaContext Stage1 rts - --- | GHC build results will be placed into target directories with the --- following typical structure: - --- * @build/@ contains compiled object code --- * @doc/@ is produced by haddock --- * @package-data.mk@ contains output of ghc-cabal applied to pkgCabal -contextDirectory :: Context -> FilePath -contextDirectory Context {..} = stageString stage - diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 50edd20..e212048 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -1,7 +1,6 @@ module Rules.Clean (cleanRules) where import Base -import Context import Package import Rules.Actions import Settings @@ -19,9 +18,8 @@ cleanRules = do removeDirectory "sdistprep" putBuild $ "| Remove files generated by ghc-cabal..." forM_ knownPackages $ \pkg -> - forM_ [Stage0 ..] $ \stage -> do - let dir = pkgPath pkg -/- contextDirectory (vanillaContext stage pkg) - quietly $ removeDirectory dir + forM_ [Stage0 ..] $ \stage -> + quietly . removeDirectory $ pkgPath pkg -/- stageDirectory stage putBuild $ "| Remove Hadrian files..." removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index cefd2fa..5a4d103 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -19,7 +19,7 @@ buildPackageData context at Context {..} = do let cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile context - oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 + oldPath = pkgPath package -/- stageDirectory stage -- TODO: remove, #113 inTreeMk = oldPath -/- takeFileName dataFile -- TODO: remove, #113 inTreeMk %> \mk -> do @@ -123,7 +123,7 @@ packageCmmSources pkg -- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 -- Reason: Shake's built-in makefile parser doesn't recognise slashes postProcessPackageData :: Context -> FilePath -> Action () -postProcessPackageData context at Context {..} file = fixFile file fixPackageData +postProcessPackageData Context {..} file = fixFile file fixPackageData where fixPackageData = unlines . map processLine . filter (not . null) . filter ('$' `notElem`) . lines processLine line = fixKey fixedPrefix ++ suffix @@ -132,7 +132,7 @@ postProcessPackageData context at Context {..} file = fixFile file fixPackageData -- Change package/path/targetDir to takeDirectory file -- This is a temporary hack until we get rid of ghc-cabal fixedPrefix = takeDirectory file ++ drop len prefix - len = length (pkgPath package -/- contextDirectory context) + len = length (pkgPath package -/- stageDirectory stage) -- TODO: Remove, see #113. fixKey :: String -> String diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 698299d..f8cf345 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -133,7 +133,7 @@ generatePackageCode context@(Context stage pkg _) = need [primopsTxt stage] build $ Target context GenPrimopCode [primopsTxt stage] [file] -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- contextDirectory context -/- "build" + let oldPath = pkgPath pkg -/- stageDirectory stage -/- "build" newFile = oldPath ++ (drop (length path) file) createDirectory $ takeDirectory newFile liftIO $ IO.copyFile file newFile diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index d4799e3..6b3e239 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -23,7 +23,7 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do -- Post-process inplace-pkg-config. TODO: remove, see #113, #148. let path = buildPath context - oldPath = pkgPath package -/- contextDirectory context + oldPath = pkgPath package -/- stageDirectory stage pkgConfig = oldPath -/- "inplace-pkg-config" oldBuildPath = oldPath -/- "build" fixPkgConf = unlines diff --git a/src/Settings.hs b/src/Settings.hs index 0a71c90..3aab9ac 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -35,7 +35,7 @@ getPackagePath :: Expr FilePath getPackagePath = pkgPath <$> getPackage getContextDirectory :: Expr FilePath -getContextDirectory = contextDirectory <$> getContext +getContextDirectory = stageDirectory <$> getStage getBuildPath :: Expr FilePath getBuildPath = buildPath <$> getContext diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 7147264..07c762a 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,5 +1,5 @@ module Settings.Paths ( - contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, + stageDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, @@ -33,8 +33,7 @@ generatedPath = buildRootPath -/- "generated" -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath -buildPath context at Context {..} = - buildRootPath -/- contextDirectory context -/- pkgPath package +buildPath Context {..} = buildRootPath -/- stageDirectory stage -/- pkgPath package -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath From git at git.haskell.org Fri Oct 27 00:26:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop commas (35d0909) Message-ID: <20171027002613.81CB73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/35d09097edef38416909648fd04a50836d39e485/ghc >--------------------------------------------------------------- commit 35d09097edef38416909648fd04a50836d39e485 Author: Moritz Angermann Date: Wed Jan 6 12:20:58 2016 +0800 Drop commas >--------------------------------------------------------------- 35d09097edef38416909648fd04a50836d39e485 .travis.yml | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 09ed050..13a70d2 100644 --- a/.travis.yml +++ b/.travis.yml @@ -10,10 +10,10 @@ env: addons: apt: packages: - - ghc-7.10.3, - - alex-3.1.4, - - happy-1.19.5, - - cabal-install-1.22, + - ghc-7.10.3 + - alex-3.1.4 + - happy-1.19.5 + - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc From git at git.haskell.org Fri Oct 27 00:26:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Tweak shake constraint. (98041b2) Message-ID: <20171027002614.9A6BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/98041b2607cbe3fab8208bb41c0381bce021fbf2/ghc >--------------------------------------------------------------- commit 98041b2607cbe3fab8208bb41c0381bce021fbf2 Author: Andrey Mokhov Date: Fri Apr 22 19:47:18 2016 +0100 Tweak shake constraint. See #230. >--------------------------------------------------------------- 98041b2607cbe3fab8208bb41c0381bce021fbf2 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index da19de1..a5e6d22 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -124,7 +124,7 @@ executable ghc-shake , extra == 1.4.* , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.9 - , shake == 0.15.6 + , shake >= 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* ghc-options: -Wall From git at git.haskell.org Fri Oct 27 00:26:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move rtsContext to Settings.Packages.Rts (fd0cb1f) Message-ID: <20171027002616.EA7CA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd0cb1f72339c7ec09962f81d4174e14224a6609/ghc >--------------------------------------------------------------- commit fd0cb1f72339c7ec09962f81d4174e14224a6609 Author: Andrey Mokhov Date: Sat Oct 29 02:15:08 2016 +0100 Move rtsContext to Settings.Packages.Rts >--------------------------------------------------------------- fd0cb1f72339c7ec09962f81d4174e14224a6609 src/GHC.hs | 6 +----- src/Rules.hs | 1 + src/Rules/Generate.hs | 1 + src/Settings/Packages/Rts.hs | 5 ++++- 4 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0312a3e..2af8923 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -9,7 +9,7 @@ module GHC ( parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, stageDirectory, rtsContext, programPath + defaultKnownPackages, stageDirectory, programPath ) where import Base @@ -124,7 +124,3 @@ programPath Context {..} inplaceProgram name = programInplacePath -/- name <.> exe installProgram name = pkgPath package -/- stageDirectory stage -/- "build/tmp" -/- name <.> exe - --- TODO: Move this elsewhere. -rtsContext :: Context -rtsContext = vanillaContext Stage1 rts diff --git a/src/Rules.hs b/src/Rules.hs index e62ecc7..68a06c7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -19,6 +19,7 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings +import Settings.Packages.Rts import Settings.Paths allStages :: [Stage] diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index f8cf345..94bcc40 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -20,6 +20,7 @@ import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Rules.Libffi +import Settings.Packages.Rts import Settings.Paths import Target import UserSettings diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index f2b4035..b3b86a9 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,5 +1,5 @@ module Settings.Packages.Rts ( - rtsPackageArgs, rtsConfIn, rtsConf, rtsLibffiLibraryName + rtsPackageArgs, rtsConfIn, rtsConf, rtsContext, rtsLibffiLibraryName ) where import Base @@ -11,6 +11,9 @@ import Predicate import Settings import Settings.Paths +rtsContext :: Context +rtsContext = vanillaContext Stage1 rts + rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" From git at git.haskell.org Fri Oct 27 00:26:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Can we install ghc and cabal through homebrew on os x? (3ea7037) Message-ID: <20171027002617.51AE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ea7037adc5e9b0592df20d44d4269097706fe5e/ghc >--------------------------------------------------------------- commit 3ea7037adc5e9b0592df20d44d4269097706fe5e Author: Moritz Angermann Date: Wed Jan 6 12:26:12 2016 +0800 Can we install ghc and cabal through homebrew on os x? >--------------------------------------------------------------- 3ea7037adc5e9b0592df20d44d4269097706fe5e .travis.yml | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.travis.yml b/.travis.yml index 13a70d2..33c4c3e 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,6 +18,10 @@ addons: sources: hvr-ghc before_install: + osx: + - brew update + - brew outdated ghc || brew upgrade ghc + - brew outdated cabal-install || brew upgrade cabal-install - PATH="$HOME/.cabal/bin:$PATH" - PATH="/opt/ghc/$GHCVER/bin:$PATH" From git at git.haskell.org Fri Oct 27 00:26:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CompilerMode Link. (7bc4867) Message-ID: <20171027002618.7FAEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7bc48677710d37d905a1e1b005e8113b28abb473/ghc >--------------------------------------------------------------- commit 7bc48677710d37d905a1e1b005e8113b28abb473 Author: Andrey Mokhov Date: Mon Apr 25 23:51:58 2016 +0100 Add CompilerMode Link. See #223. >--------------------------------------------------------------- 7bc48677710d37d905a1e1b005e8113b28abb473 src/Builder.hs | 16 +++++++++------- src/Rules/Program.hs | 3 +-- src/Settings/Builders/Ghc.hs | 34 ++++++++++++++++++++-------------- 3 files changed, 30 insertions(+), 23 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 348e7e9..09e4ab9 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -15,11 +15,14 @@ import Oracles.LookupInPath import Oracles.WindowsPath import Stage --- TODO: Add Link mode? --- | A C or Haskell compiler can be used in two modes: for compiling sources --- into object files, or for extracting source dependencies, e.g. by passing -M --- command line option. -data CompilerMode = Compile | FindDependencies deriving (Show, Eq, Generic) +-- | A compiler can typically be used in one of three modes: +-- 1) Compiling sources into object files. +-- 2) Extracting source dependencies, e.g. by passing -M command line argument. +-- 3) Linking object files & static libraries into an executable. +data CompilerMode = Compile + | FindDependencies + | Link + deriving (Show, Eq, Generic) -- TODO: Do we really need HsCpp builder? Can't we use Cc instead? -- | A 'Builder' is an external command invoked in separate process using 'Shake.cmd' @@ -138,8 +141,7 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- TODO: split into two functions: needBuilder (without laxDependencies) and --- unsafeNeedBuilder (with the laxDependencies parameter) +-- TODO: Get rid of laxDependencies -- we no longer need it (use Shake's skip). -- | Make sure a builder exists on the given path and rebuild it if out of date. -- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 975be85..2cee06c 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -99,8 +99,7 @@ buildBinary rs context@(Context stage package _) bin = do then [ pkgPath package -/- src <.> "hs" | src <- hSrcs ] else objs need $ binDeps ++ libs - -- TODO: Use Link mode instead of Compile. - buildWithResources rs $ Target context (Ghc Compile stage) binDeps [bin] + buildWithResources rs $ Target context (Ghc Link stage) binDeps [bin] synopsis <- interpretInContext context $ getPkgData Synopsis putSuccess $ renderProgram ("'" ++ pkgNameString package ++ "' (" ++ show stage ++ ").") diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a07c512..7152526 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -18,8 +18,9 @@ import Settings.Builders.Common (cIncludeArgs) -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ -- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) +-- TODO: Simplify ghcBuilderArgs :: Args -ghcBuilderArgs = stagedBuilder (Ghc Compile) ? do +ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do output <- getOutput stage <- getStage way <- getWay @@ -27,16 +28,6 @@ ghcBuilderArgs = stagedBuilder (Ghc Compile) ? do let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] buildHi = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf] buildProg = not (buildObj || buildHi) - libs <- getPkgDataList DepExtraLibs - gmpLibs <- if stage > Stage0 && buildProg - then do -- TODO: get this data more gracefully - buildInfo <- lift $ readFileLines gmpBuildInfoPath - let extract s = case stripPrefix "extra-libraries: " s of - Nothing -> [] - Just value -> words value - return $ concatMap extract buildInfo - else return [] - libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -44,14 +35,29 @@ ghcBuilderArgs = stagedBuilder (Ghc Compile) ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , buildProg ? arg "-no-auto-link-packages" - , buildProg ? append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] - , buildProg ? append [ "-optl-L" ++ dir | dir <- libDirs ] + , buildProg ? ghcLinkArgs , not buildProg ? arg "-c" , append =<< getInputs , buildHi ? append ["-fno-code", "-fwrite-interface"] , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] +ghcLinkArgs :: Args +ghcLinkArgs = stagedBuilder (Ghc Link) ? do + stage <- getStage + libs <- getPkgDataList DepExtraLibs + gmpLibs <- if stage > Stage0 + then do -- TODO: get this data more gracefully + buildInfo <- lift $ readFileLines gmpBuildInfoPath + let extract s = case stripPrefix "extra-libraries: " s of + Nothing -> [] + Just value -> words value + return $ concatMap extract buildInfo + else return [] + libDirs <- getPkgDataList DepLibDirs + mconcat [ arg "-no-auto-link-packages" + , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] + , append [ "-optl-L" ++ dir | dir <- libDirs ] ] + needTouchy :: Action () needTouchy = whenM windowsHost $ need [fromJust $ programPath (vanillaContext Stage0 touchy)] From git at git.haskell.org Fri Oct 27 00:26:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify builderPath (058cb92) Message-ID: <20171027002620.B47F73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/058cb92e8f1f21c271073d892d8b504726a345a2/ghc >--------------------------------------------------------------- commit 058cb92e8f1f21c271073d892d8b504726a345a2 Author: Andrey Mokhov Date: Sat Oct 29 02:42:29 2016 +0100 Simplify builderPath >--------------------------------------------------------------- 058cb92e8f1f21c271073d892d8b504726a345a2 src/Builder.hs | 11 +++-------- src/GHC.hs | 2 +- src/Package.hs | 1 - 3 files changed, 4 insertions(+), 10 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index c5dc9fb..61960c7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -94,14 +94,9 @@ isOptional = \case -- | Determine the location of a 'Builder'. builderPath :: Builder -> Action FilePath -builderPath builder = case builderProvenance builder of - Just context - | Just path <- programPath context -> return path - | otherwise -> - -- TODO: Make builderPath total. - error $ "Cannot determine builderPath for " ++ show builder - ++ " in context " ++ show context - Nothing -> case builder of +builderPath builder = case programPath =<< builderProvenance builder of + Just path -> return path + Nothing -> case builder of Alex -> fromKey "alex" Ar -> fromKey "ar" Cc _ Stage0 -> fromKey "system-cc" diff --git a/src/GHC.hs b/src/GHC.hs index 2af8923..91987c6 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -86,7 +86,7 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" --- | ghc-split is a perl script used by GHC with @-split-objs@ flag. It is +-- | @ghc-split@ is a Perl script used by GHC with @-split-objs@ flag. It is -- generated in "Rules.Generators.GhcSplit". ghcSplit :: FilePath ghcSplit = "inplace/lib/bin/ghc-split" diff --git a/src/Package.hs b/src/Package.hs index bee5640..8a1a8d2 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -17,7 +17,6 @@ newtype PackageName = PackageName { fromPackageName :: String } deriving (Binary, Eq, Generic, Hashable, IsString, NFData, Ord, Typeable) -- TODO: Make PackageType more precise, #12. --- TODO: Turn Program to Program FilePath thereby getting rid of programPath -- | We regard packages as either being libraries or programs. This is bit of a -- convenient lie as Cabal packages can be both, but it works for now. data PackageType = Library | Program deriving Generic From git at git.haskell.org Fri Oct 27 00:26:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: This should work, I guess. (019b513) Message-ID: <20171027002621.0D9873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/019b51376ee25ec0d73931f3bd946bf2d3c23e71/ghc >--------------------------------------------------------------- commit 019b51376ee25ec0d73931f3bd946bf2d3c23e71 Author: Moritz Angermann Date: Wed Jan 6 12:38:22 2016 +0800 This should work, I guess. >--------------------------------------------------------------- 019b51376ee25ec0d73931f3bd946bf2d3c23e71 .travis.yml | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 33c4c3e..4a2179d 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,10 +18,9 @@ addons: sources: hvr-ghc before_install: - osx: - - brew update - - brew outdated ghc || brew upgrade ghc - - brew outdated cabal-install || brew upgrade cabal-install + - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi + - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated ghc || brew upgrade ghc; fi + - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated cabal-install || brew upgrade cabal-install; fi - PATH="$HOME/.cabal/bin:$PATH" - PATH="/opt/ghc/$GHCVER/bin:$PATH" From git at git.haskell.org Fri Oct 27 00:26:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop experimental code for #174. (64ae7fe) Message-ID: <20171027002622.142203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64ae7fe8fd907dffd6b6221b95111d24f1bf6372/ghc >--------------------------------------------------------------- commit 64ae7fe8fd907dffd6b6221b95111d24f1bf6372 Author: Andrey Mokhov Date: Tue Apr 26 00:25:12 2016 +0100 Drop experimental code for #174. >--------------------------------------------------------------- 64ae7fe8fd907dffd6b6221b95111d24f1bf6372 src/Rules/Compile.hs | 24 ++++-------------------- src/Settings/Builders/Ghc.hs | 12 ++++-------- src/Settings/User.hs | 13 ++++--------- 3 files changed, 12 insertions(+), 37 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index a3c970d..93503bd 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,21 +12,9 @@ compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context - path "*" <.> hisuf way %> \hi -> - if compileInterfaceFilesSeparately - then do - (src, deps) <- dependencies path $ hi -<.> osuf way - need $ src : deps - buildWithResources rs $ Target context (Ghc Compile stage) [src] [hi] - else need [ hi -<.> osuf way ] + path "*" <.> hisuf way %> \hi -> need [ hi -<.> osuf way ] - path "*" <.> hibootsuf way %> \hiboot -> - if compileInterfaceFilesSeparately - then do - (src, deps) <- dependencies path $ hiboot -<.> obootsuf way - need $ src : deps - buildWithResources rs $ Target context (Ghc Compile stage) [src] [hiboot] - else need [ hiboot -<.> obootsuf way ] + path "*" <.> hibootsuf way %> \hiboot -> need [ hiboot -<.> obootsuf way ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) path "*" <.> osuf way %> \obj -> do @@ -36,15 +24,11 @@ compilePackage rs context at Context {..} = do need $ src : deps build $ Target context (Cc Compile stage) [src] [obj] else do - if compileInterfaceFilesSeparately && "//*.hs" ?== src - then need $ (obj -<.> hisuf way) : src : deps - else need $ src : deps + need $ src : deps buildWithResources rs $ Target context (Ghc Compile stage) [src] [obj] -- TODO: get rid of these special cases path "*" <.> obootsuf way %> \obj -> do (src, deps) <- dependencies path obj - if compileInterfaceFilesSeparately - then need $ (obj -<.> hibootsuf way) : src : deps - else need $ src : deps + need $ src : deps buildWithResources rs $ Target context (Ghc Compile stage) [src] [obj] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 7152526..8dabda6 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -18,16 +18,13 @@ import Settings.Builders.Common (cIncludeArgs) -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ -- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) --- TODO: Simplify ghcBuilderArgs :: Args ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do output <- getOutput stage <- getStage way <- getWay when (stage > Stage0) . lift $ needTouchy - let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] - buildHi = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf] - buildProg = not (buildObj || buildHi) + let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -35,11 +32,10 @@ ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , buildProg ? ghcLinkArgs - , not buildProg ? arg "-c" + , not buildObj ? ghcLinkArgs + , buildObj ? arg "-c" , append =<< getInputs - , buildHi ? append ["-fno-code", "-fwrite-interface"] - , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] + , arg "-o", arg =<< getOutput ] ghcLinkArgs :: Args ghcLinkArgs = stagedBuilder (Ghc Link) ? do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 6fc5536..9f2302b 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,9 +1,8 @@ module Settings.User ( - buildRootPath, trackBuildSystem, compileInterfaceFilesSeparately, - userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, - integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - ghcDebugged, dynamicGhcPrograms, laxDependencies, verboseCommands, - turnWarningsIntoErrors, splitObjects + buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays, + userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, + ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, + laxDependencies, verboseCommands, turnWarningsIntoErrors, splitObjects ) where import Base @@ -94,7 +93,3 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False - --- | Decouple the compilation of @*.hi@ and @*.o@ files by setting to True. -compileInterfaceFilesSeparately :: Bool -compileInterfaceFilesSeparately = False From git at git.haskell.org Fri Oct 27 00:26:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor programPath (44f7374) Message-ID: <20171027002624.5EF4C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44f7374237aa86baf551860bb943b1707fc286a8/ghc >--------------------------------------------------------------- commit 44f7374237aa86baf551860bb943b1707fc286a8 Author: Andrey Mokhov Date: Sat Oct 29 03:53:46 2016 +0100 Refactor programPath >--------------------------------------------------------------- 44f7374237aa86baf551860bb943b1707fc286a8 src/GHC.hs | 67 ++++++++++++++++++++++++++++++++++++++------------------------ 1 file changed, 41 insertions(+), 26 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 91987c6..6c1e147 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -96,31 +96,46 @@ stageDirectory :: Stage -> FilePath stageDirectory = stageString -- TODO: move to buildRootPath, see #113 --- TODO: simplify, add programInplaceLibPath --- | The relative path to the program executable +-- | The 'FilePath' to a program executable in a given 'Context'. programPath :: Context -> Maybe FilePath -programPath Context {..} - | package == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) - | package `elem` [mkUserGuidePart] = - case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package - _ -> Nothing - | package `elem` [checkApiAnnotations, ghcTags, haddock] = - case stage of Stage2 -> Just . inplaceProgram $ pkgNameString package - _ -> Nothing - | package `elem` [touchy, unlit] = case stage of - Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString package <.> exe - _ -> Nothing - | package == hpcBin = case stage of - Stage1 -> Just $ inplaceProgram "hpc" - _ -> Nothing - | package == runGhc = case stage of - Stage1 -> Just $ inplaceProgram "runhaskell" - _ -> Nothing - | isProgram package = case stage of - Stage0 -> Just . inplaceProgram $ pkgNameString package - _ -> Just . installProgram $ pkgNameString package - | otherwise = Nothing +programPath Context {..} = lookup (stage, package) exes where - inplaceProgram name = programInplacePath -/- name <.> exe - installProgram name = pkgPath package -/- stageDirectory stage - -/- "build/tmp" -/- name <.> exe + exes = [ inplace2 checkApiAnnotations + , install1 compareSizes + , inplace0 deriveConstants + , inplace0 dllSplit + , inplace0 genapply + , inplace0 genprimopcode + , inplace0 ghc `setFile` "ghc-stage1" + , inplace1 ghc `setFile` "ghc-stage2" + , install0 ghcCabal + , inplace1 ghcCabal + , inplace0 ghcPkg + , install1 ghcPkg + , inplace2 ghcTags + , inplace2 haddock + , inplace0 hp2ps + , inplace1 hpcBin `setFile` "hpc" + , inplace0 hsc2hs + , install1 hsc2hs + , inplace0 mkUserGuidePart + , inplace1 runGhc `setFile` "runhaskell" + , inplace0 touchy `setDir` "inplace/lib/bin" + , inplace0 unlit `setDir` "inplace/lib/bin" ] + inplace pkg = programInplacePath -/- pkgNameString pkg <.> exe + inplace0 pkg = ((Stage0, pkg), inplace pkg) + inplace1 pkg = ((Stage1, pkg), inplace pkg) + inplace2 pkg = ((Stage2, pkg), inplace pkg) + install stage pkg = pkgPath package -/- stageDirectory stage -/- "build" + -/- pkgNameString pkg <.> exe + install0 pkg = ((Stage0, pkg), install Stage0 pkg) + install1 pkg = ((Stage1, pkg), install Stage1 pkg) + setFile ((stage, pkg), x) y = ((stage, pkg), takeDirectory x -/- y <.> exe) + setDir ((stage, pkg), x) y = ((stage, pkg), y -/- takeFileName x) + + -- | isProgram package = case stage of + -- Stage0 -> Just . inplaceProgram $ pkgNameString package + -- _ -> Just . installProgram $ pkgNameString package + -- | otherwise = Nothing + -- where + -- inplaceProgram name = programInplacePath -/- name <.> exe From git at git.haskell.org Fri Oct 27 00:26:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use install. (59c09b8) Message-ID: <20171027002624.B8C503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59c09b8be58c2f1fd8e75788d9bccf63e9ff1458/ghc >--------------------------------------------------------------- commit 59c09b8be58c2f1fd8e75788d9bccf63e9ff1458 Author: Moritz Angermann Date: Wed Jan 6 12:43:17 2016 +0800 Use install. >--------------------------------------------------------------- 59c09b8be58c2f1fd8e75788d9bccf63e9ff1458 .travis.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4a2179d..6e1bf5b 100644 --- a/.travis.yml +++ b/.travis.yml @@ -19,8 +19,7 @@ addons: before_install: - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated ghc || brew upgrade ghc; fi - - if [ $TRAVIS_OS_NAME == osx ]; then brew outdated cabal-install || brew upgrade cabal-install; fi + - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi - PATH="$HOME/.cabal/bin:$PATH" - PATH="/opt/ghc/$GHCVER/bin:$PATH" From git at git.haskell.org Fri Oct 27 00:26:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (366b35b) Message-ID: <20171027002625.97D933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/366b35b27d1a33cb2a752fb0b6c927658496047e/ghc >--------------------------------------------------------------- commit 366b35b27d1a33cb2a752fb0b6c927658496047e Author: Andrey Mokhov Date: Tue Apr 26 00:46:58 2016 +0100 Minor revision. >--------------------------------------------------------------- 366b35b27d1a33cb2a752fb0b6c927658496047e src/Settings/Builders/Ghc.hs | 23 +++++++++++++---------- 1 file changed, 13 insertions(+), 10 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 8dabda6..37fbc34 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,6 +2,8 @@ module Settings.Builders.Ghc ( ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs ) where +import Control.Monad.Trans.Reader + import Base import Expression import GHC @@ -20,11 +22,7 @@ import Settings.Builders.Common (cIncludeArgs) -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) ghcBuilderArgs :: Args ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do - output <- getOutput - stage <- getStage - way <- getWay - when (stage > Stage0) . lift $ needTouchy - let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] + needTouchy mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -32,8 +30,8 @@ ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , not buildObj ? ghcLinkArgs - , buildObj ? arg "-c" + , ghcLinkArgs + , stagedBuilder (Ghc Compile) ? arg "-c" , append =<< getInputs , arg "-o", arg =<< getOutput ] @@ -54,10 +52,15 @@ ghcLinkArgs = stagedBuilder (Ghc Link) ? do , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ dir | dir <- libDirs ] ] -needTouchy :: Action () -needTouchy = - whenM windowsHost $ need [fromJust $ programPath (vanillaContext Stage0 touchy)] +-- TODO: Add Touchy builder and use needBuilder. +needTouchy :: ReaderT Target Action () +needTouchy = do + stage <- getStage + windows <- lift $ windowsHost + lift . when (stage > Stage0 && windows) $ + need [fromJust $ programPath (vanillaContext Stage0 touchy)] +-- TODO: Add GhcSplit builder and use needBuilder. splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do lift $ need [ghcSplit] From git at git.haskell.org Fri Oct 27 00:26:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build iservBin, fix comments (28f2675) Message-ID: <20171027002628.1352E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28f26751efa6336fac0798eb2e07795eeeb134b2/ghc >--------------------------------------------------------------- commit 28f26751efa6336fac0798eb2e07795eeeb134b2 Author: Andrey Mokhov Date: Sat Oct 29 11:15:33 2016 +0100 Build iservBin, fix comments >--------------------------------------------------------------- 28f26751efa6336fac0798eb2e07795eeeb134b2 src/GHC.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 6c1e147..c3242c6 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -95,6 +95,7 @@ ghcSplit = "inplace/lib/bin/ghc-split" stageDirectory :: Stage -> FilePath stageDirectory = stageString +-- TODO: Create a separate rule for copying executables to inplace/bin -- TODO: move to buildRootPath, see #113 -- | The 'FilePath' to a program executable in a given 'Context'. programPath :: Context -> Maybe FilePath @@ -118,6 +119,7 @@ programPath Context {..} = lookup (stage, package) exes , inplace1 hpcBin `setFile` "hpc" , inplace0 hsc2hs , install1 hsc2hs + , install1 iservBin , inplace0 mkUserGuidePart , inplace1 runGhc `setFile` "runhaskell" , inplace0 touchy `setDir` "inplace/lib/bin" @@ -132,10 +134,3 @@ programPath Context {..} = lookup (stage, package) exes install1 pkg = ((Stage1, pkg), install Stage1 pkg) setFile ((stage, pkg), x) y = ((stage, pkg), takeDirectory x -/- y <.> exe) setDir ((stage, pkg), x) y = ((stage, pkg), y -/- takeFileName x) - - -- | isProgram package = case stage of - -- Stage0 -> Just . inplaceProgram $ pkgNameString package - -- _ -> Just . installProgram $ pkgNameString package - -- | otherwise = Nothing - -- where - -- inplaceProgram name = programInplacePath -/- name <.> exe From git at git.haskell.org Fri Oct 27 00:26:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install alex, happy; adjust path only on ghc/cabal path only on linux. (17306dc) Message-ID: <20171027002628.580213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/17306dc5a8e5ff70b3a0b973915fc6e6ec5cc3b7/ghc >--------------------------------------------------------------- commit 17306dc5a8e5ff70b3a0b973915fc6e6ec5cc3b7 Author: Moritz Angermann Date: Wed Jan 6 12:50:09 2016 +0800 Install alex, happy; adjust path only on ghc/cabal path only on linux. >--------------------------------------------------------------- 17306dc5a8e5ff70b3a0b973915fc6e6ec5cc3b7 .travis.yml | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 6e1bf5b..64e8597 100644 --- a/.travis.yml +++ b/.travis.yml @@ -5,7 +5,9 @@ os: - osx env: - - CABALVER=1.22 GHCVER=7.10.3 + matrix: + linux: + - CABALVER=1.22 GHCVER=7.10.3 addons: apt: @@ -20,10 +22,10 @@ addons: before_install: - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi - + - if [ $TRAVIS_OS_NAME == osx ]; then cabal install alex happy; fi + - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/ghc/$GHCVER/bin:$PATH"; fi + - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/cabal/$CABALVER/bin:$PATH"; fi - PATH="$HOME/.cabal/bin:$PATH" - - PATH="/opt/ghc/$GHCVER/bin:$PATH" - - PATH="/opt/cabal/$CABALVER/bin:$PATH" - export PATH - env From git at git.haskell.org Fri Oct 27 00:26:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge builder, stagedBuilder, builderGhc/Cc into builder. (e532385) Message-ID: <20171027002629.2E8923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e53238583d64f7218e57d055651087f594e3a98c/ghc >--------------------------------------------------------------- commit e53238583d64f7218e57d055651087f594e3a98c Author: Andrey Mokhov Date: Tue Apr 26 01:04:04 2016 +0100 Merge builder, stagedBuilder, builderGhc/Cc into builder. See #223. >--------------------------------------------------------------- e53238583d64f7218e57d055651087f594e3a98c src/Predicates.hs | 33 ++++++++++++--------------------- src/Settings/Builders/Cc.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Flavours/Quick.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 4 ++-- src/Settings/Packages/Directory.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 4 ++-- src/Settings/Packages/GhcCabal.hs | 4 ++-- src/Settings/Packages/Hp2ps.hs | 4 ++-- src/Settings/Packages/IntegerGmp.hs | 4 ++-- src/Settings/Packages/IservBin.hs | 4 ++-- src/Settings/Packages/Rts.hs | 6 +++--- src/Settings/Packages/RunGhc.hs | 4 ++-- src/Settings/Packages/Touchy.hs | 4 ++-- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/User.hs | 2 +- 18 files changed, 47 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e53238583d64f7218e57d055651087f594e3a98c From git at git.haskell.org Fri Oct 27 00:26:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reorder os and env (9ff8773) Message-ID: <20171027002632.701513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ff8773943c628ec660bd59de0e48e1eb9dd2e22/ghc >--------------------------------------------------------------- commit 9ff8773943c628ec660bd59de0e48e1eb9dd2e22 Author: Moritz Angermann Date: Wed Jan 6 12:55:34 2016 +0800 Reorder os and env >--------------------------------------------------------------- 9ff8773943c628ec660bd59de0e48e1eb9dd2e22 .travis.yml | 13 +++++-------- 1 file changed, 5 insertions(+), 8 deletions(-) diff --git a/.travis.yml b/.travis.yml index 64e8597..72e2f80 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,13 +1,10 @@ sudo: false -os: - - linux - - osx - -env: - matrix: - linux: - - CABALVER=1.22 GHCVER=7.10.3 +matrix: + include: + - os: linux + env: CABALVER=1.22 GHCVER=7.10.3 + - os: osx addons: apt: From git at git.haskell.org Fri Oct 27 00:26:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring back tmp directory for in-tree build artefacts (c93cf69) Message-ID: <20171027002632.732793A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c93cf69f4cade6af063fcc26ebe13598f0eb9b56/ghc >--------------------------------------------------------------- commit c93cf69f4cade6af063fcc26ebe13598f0eb9b56 Author: Andrey Mokhov Date: Sat Oct 29 11:50:13 2016 +0100 Bring back tmp directory for in-tree build artefacts >--------------------------------------------------------------- c93cf69f4cade6af063fcc26ebe13598f0eb9b56 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index c3242c6..810c63d 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -128,7 +128,7 @@ programPath Context {..} = lookup (stage, package) exes inplace0 pkg = ((Stage0, pkg), inplace pkg) inplace1 pkg = ((Stage1, pkg), inplace pkg) inplace2 pkg = ((Stage2, pkg), inplace pkg) - install stage pkg = pkgPath package -/- stageDirectory stage -/- "build" + install stage pkg = pkgPath package -/- stageDirectory stage -/- "build/tmp" -/- pkgNameString pkg <.> exe install0 pkg = ((Stage0, pkg), install Stage0 pkg) install1 pkg = ((Stage1, pkg), install Stage1 pkg) From git at git.haskell.org Fri Oct 27 00:26:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop workaround a Shake getDirectoryFiles bug. (ab5a70f) Message-ID: <20171027002632.B74593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ab5a70fd6fe2e175749b6c55b6395871fe069c77/ghc >--------------------------------------------------------------- commit ab5a70fd6fe2e175749b6c55b6395871fe069c77 Author: Andrey Mokhov Date: Tue Apr 26 01:28:55 2016 +0100 Drop workaround a Shake getDirectoryFiles bug. >--------------------------------------------------------------- ab5a70fd6fe2e175749b6c55b6395871fe069c77 src/Rules/Library.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b74baf8..8e09162 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -97,9 +97,5 @@ extraObjects :: Context -> Action [FilePath] extraObjects (Context _ package _) | package == integerGmp = do orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? - -- FIXME: simplify after Shake's getDirectoryFiles bug is fixed, #168 - exists <- doesDirectoryExist gmpObjects - if exists - then map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] - else return [] + map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:26:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: run cabal update (e18abef) Message-ID: <20171027002636.58DFD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e18abefe7f05cda6f758eb3b46f283e431aaa590/ghc >--------------------------------------------------------------- commit e18abefe7f05cda6f758eb3b46f283e431aaa590 Author: Moritz Angermann Date: Wed Jan 6 12:55:41 2016 +0800 run cabal update >--------------------------------------------------------------- e18abefe7f05cda6f758eb3b46f283e431aaa590 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 72e2f80..b21b89e 100644 --- a/.travis.yml +++ b/.travis.yml @@ -19,6 +19,7 @@ addons: before_install: - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi + - if [ $TRAVIS_OS_NAME == osx ]; then cabal update; fi - if [ $TRAVIS_OS_NAME == osx ]; then cabal install alex happy; fi - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/ghc/$GHCVER/bin:$PATH"; fi - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/cabal/$CABALVER/bin:$PATH"; fi From git at git.haskell.org Fri Oct 27 00:26:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor builder path manipulation (8ee46b1) Message-ID: <20171027002636.6C4353A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2/ghc >--------------------------------------------------------------- commit 8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2 Author: Andrey Mokhov Date: Sun Oct 30 01:54:14 2016 +0100 Refactor builder path manipulation >--------------------------------------------------------------- 8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2 hadrian.cabal | 2 +- src/Builder.hs | 92 +------------------------------- src/GHC.hs | 67 ++++++++--------------- src/Oracles/WindowsPath.hs | 45 ---------------- src/Rules/Actions.hs | 24 ++++++++- src/Rules/Documentation.hs | 2 +- src/Rules/Generators/ConfigHs.hs | 1 + src/Rules/Generators/GhcSplit.hs | 1 + src/Rules/Oracles.hs | 4 +- src/Rules/Program.hs | 5 -- src/Rules/Test.hs | 3 +- src/Rules/Wrappers/Ghc.hs | 2 +- src/Rules/Wrappers/GhcPkg.hs | 2 +- src/Settings/Builders/Common.hs | 4 +- src/Settings/Builders/DeriveConstants.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 3 +- src/Settings/Builders/Haddock.hs | 7 ++- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Paths.hs | 64 +++++++++++++++++++++- 19 files changed, 128 insertions(+), 206 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 8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2 From git at git.haskell.org Fri Oct 27 00:26:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comment on unicode build info. (ed4cdd8) Message-ID: <20171027002636.B78AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ed4cdd8c37bcb13e7bf5dda89b1945a29e2ee1bf/ghc >--------------------------------------------------------------- commit ed4cdd8c37bcb13e7bf5dda89b1945a29e2ee1bf Author: Andrey Mokhov Date: Tue Apr 26 01:42:15 2016 +0100 Add comment on unicode build info. [skip ci] >--------------------------------------------------------------- ed4cdd8c37bcb13e7bf5dda89b1945a29e2ee1bf src/Rules/Actions.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5f0fac0..3b12249 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -237,7 +237,8 @@ renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot] -- Minimum total width of the box in characters minimumBoxWidth = 32 - -- FIXME: See Shake #364. + -- TODO: Make this setting configurable? Setting to True by default seems + -- to work poorly with many fonts. useUnicode = False -- Characters to draw the box From git at git.haskell.org Fri Oct 27 00:26:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Can we put addons and before_install into the include? (a5aa58f) Message-ID: <20171027002639.D93053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5aa58f81ceab822e035cb17f25bc05dec8dc092/ghc >--------------------------------------------------------------- commit a5aa58f81ceab822e035cb17f25bc05dec8dc092 Author: Moritz Angermann Date: Wed Jan 6 13:03:06 2016 +0800 Can we put addons and before_install into the include? >--------------------------------------------------------------- a5aa58f81ceab822e035cb17f25bc05dec8dc092 .travis.yml | 40 +++++++++++++++++++++------------------- 1 file changed, 21 insertions(+), 19 deletions(-) diff --git a/.travis.yml b/.travis.yml index b21b89e..5c5708c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -4,28 +4,30 @@ matrix: include: - os: linux env: CABALVER=1.22 GHCVER=7.10.3 + addons: + apt: + packages: + - ghc-7.10.3 + - alex-3.1.4 + - happy-1.19.5 + - cabal-install-1.22 + - zlib1g-dev + sources: hvr-ghc + before_install: + - PATH="/opt/ghc/$GHCVER/bin:$PATH" + - PATH="/opt/cabal/$CABALVER/bin:$PATH" + - PATH="$HOME/.cabal/bin:$PATH" + - export PATH - os: osx - -addons: - apt: - packages: - - ghc-7.10.3 - - alex-3.1.4 - - happy-1.19.5 - - cabal-install-1.22 - - zlib1g-dev - sources: hvr-ghc + before_install: + - brew update + - brew install ghc cabal-install + - cabal update + - cabal install alex happy + - PATH="$HOME/.cabal/bin:$PATH" + - export PATH before_install: - - if [ $TRAVIS_OS_NAME == osx ]; then brew update; fi - - if [ $TRAVIS_OS_NAME == osx ]; then brew install ghc cabal-install; fi - - if [ $TRAVIS_OS_NAME == osx ]; then cabal update; fi - - if [ $TRAVIS_OS_NAME == osx ]; then cabal install alex happy; fi - - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/ghc/$GHCVER/bin:$PATH"; fi - - if [ $TRAVIS_OS_NAME == linux ]; then PATH="/opt/cabal/$CABALVER/bin:$PATH"; fi - - PATH="$HOME/.cabal/bin:$PATH" - - export PATH - - env - ghc --version - cabal --version From git at git.haskell.org Fri Oct 27 00:26:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing src/Oracles/Path.hs (e1e2621) Message-ID: <20171027002640.54B833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1e2621d6bdd5ebe98fb3787733d134fa4d2fd70/ghc >--------------------------------------------------------------- commit e1e2621d6bdd5ebe98fb3787733d134fa4d2fd70 Author: Andrey Mokhov Date: Sun Oct 30 01:01:43 2016 +0000 Add missing src/Oracles/Path.hs >--------------------------------------------------------------- e1e2621d6bdd5ebe98fb3787733d134fa4d2fd70 src/Oracles/Path.hs | 83 +++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 83 insertions(+) diff --git a/src/Oracles/Path.hs b/src/Oracles/Path.hs new file mode 100644 index 0000000..7db1400 --- /dev/null +++ b/src/Oracles/Path.hs @@ -0,0 +1,83 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module Oracles.Path ( + fixAbsolutePathOnWindows, topDirectory, getTopDirectory, windowsPathOracle, + systemBuilderPath + ) where + +import Control.Monad.Trans.Reader +import Data.Char + +import Base +import Builder +import Oracles.Config +import Oracles.Config.Setting +import Oracles.LookupInPath +import Stage + +newtype WindowsPath = WindowsPath FilePath + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Path to the GHC source tree. +topDirectory :: Action FilePath +topDirectory = fixAbsolutePathOnWindows =<< setting GhcSourcePath + +getTopDirectory :: ReaderT a Action FilePath +getTopDirectory = lift topDirectory + +-- | Determine the location of a system 'Builder'. +systemBuilderPath :: Builder -> Action FilePath +systemBuilderPath builder = case builder of + Alex -> fromKey "alex" + Ar -> fromKey "ar" + Cc _ Stage0 -> fromKey "system-cc" + Cc _ _ -> fromKey "cc" + -- We can't ask configure for the path to configure! + Configure _ -> return "bash configure" + Ghc _ Stage0 -> fromKey "system-ghc" + GhcPkg Stage0 -> fromKey "system-ghc-pkg" + Happy -> fromKey "happy" + HsColour -> fromKey "hscolour" + HsCpp -> fromKey "hs-cpp" + Ld -> fromKey "ld" + Make _ -> fromKey "make" + Nm -> fromKey "nm" + Objdump -> fromKey "objdump" + Patch -> fromKey "patch" + Perl -> fromKey "perl" + Ranlib -> fromKey "ranlib" + Tar -> fromKey "tar" + _ -> error $ "No system.config entry for " ++ show builder + where + fromKey key = do + let unpack = fromMaybe . error $ "Cannot find path to builder " + ++ quote key ++ " in system.config file. Did you skip configure?" + path <- unpack <$> askConfig key + if null path + then do + unless (isOptional builder) . error $ "Non optional builder " + ++ quote key ++ " is not specified in system.config file." + return "" -- TODO: Use a safe interface. + else fixAbsolutePathOnWindows =<< lookupInPath path + +-- | Fix an absolute path on Windows: +-- * "/c/" => "C:/" +-- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" +fixAbsolutePathOnWindows :: FilePath -> Action FilePath +fixAbsolutePathOnWindows path = do + windows <- windowsHost + if windows + then do + let (dir, file) = splitFileName path + winDir <- askOracle $ WindowsPath dir + return $ winDir -/- file + else + return path + +-- | Compute path mapping on Windows. This is slow and requires caching. +windowsPathOracle :: Rules () +windowsPathOracle = void $ + addOracle $ \(WindowsPath path) -> do + Stdout out <- quietly $ cmd ["cygpath", "-m", path] + let windowsPath = unifyPath $ dropWhileEnd isSpace out + putLoud $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath + return windowsPath From git at git.haskell.org Fri Oct 27 00:26:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop laxDependencies. To be replaced by Shake's skip feature. (8d0581e) Message-ID: <20171027002640.9265B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8d0581ed811c1b180981d4a767e3862e5dd490de/ghc >--------------------------------------------------------------- commit 8d0581ed811c1b180981d4a767e3862e5dd490de Author: Andrey Mokhov Date: Tue Apr 26 09:44:41 2016 +0100 Drop laxDependencies. To be replaced by Shake's skip feature. >--------------------------------------------------------------- 8d0581ed811c1b180981d4a767e3862e5dd490de src/Builder.hs | 18 ++++-------------- src/Predicates.hs | 1 - src/Rules/Actions.hs | 6 +++--- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Test.hs | 6 +++--- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/User.hs | 9 +-------- 8 files changed, 14 insertions(+), 32 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 09e4ab9..8f711e0 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -141,21 +141,11 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- TODO: Get rid of laxDependencies -- we no longer need it (use Shake's skip). --- | Make sure a builder exists on the given path and rebuild it if out of date. --- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of --- date (can save a lot of build time when changing GHC). -needBuilder :: Bool -> Builder -> Action () -needBuilder laxDependencies builder = when (isInternal builder) $ do +-- | Make sure a Builder exists on the given path and rebuild it if out of date. +needBuilder :: Builder -> Action () +needBuilder builder = when (isInternal builder) $ do path <- builderPath builder - if laxDependencies && allowOrderOnlyDependency builder - then orderOnly [path] - else need [path] - where - allowOrderOnlyDependency :: Builder -> Bool - allowOrderOnlyDependency = \case - Ghc _ _ -> True - _ -> False + need [path] -- Instances for storing in the Shake database instance Binary CompilerMode diff --git a/src/Predicates.hs b/src/Predicates.hs index 1f87386..0ae18e9 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -15,7 +15,6 @@ stage s = (s ==) <$> getStage package :: Package -> Predicate package p = (p ==) <$> getPackage --- TODO: Also add needBuilder, builderPath, etc. -- | Is a particular builder being used? class BuilderLike a where builder :: a -> Predicate diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 3b12249..10bcbd2 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -24,7 +24,7 @@ import Target -- built (that is, track changes in the build system). buildWithResources :: [(Resource, Int)] -> Target -> Action () buildWithResources rs target at Target {..} = do - needBuilder laxDependencies builder + needBuilder builder path <- builderPath builder argList <- interpret target getArgs verbose <- interpret target verboseCommands @@ -140,14 +140,14 @@ applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch need [file] - needBuilder False Patch -- TODO: add a specialised version ~needBuilderFalse? + needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do - needBuilder laxDependencies builder + needBuilder builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ show builder ++ note diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index ae73104..99dda79 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -42,7 +42,7 @@ configureEnvironment = do , builderEnv "NM" Nm ] where builderEnv var bld = do - needBuilder False bld + needBuilder bld path <- builderPath bld return $ AddEnv var path diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 18c328b..8dce6d1 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -53,7 +53,7 @@ configureEnvironment = do , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ] where builderEnv var bld = do - needBuilder False bld + needBuilder bld path <- builderPath bld return $ AddEnv var path diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 0604236..7faf62d 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -15,9 +15,9 @@ import Settings.User testRules :: Rules () testRules = do "validate" ~> do - needBuilder False $ Ghc Compile Stage2 -- TODO: get rid of False - needBuilder False $ GhcPkg Stage1 - needBuilder False $ Hpc + needBuilder $ Ghc Compile Stage2 + needBuilder $ GhcPkg Stage1 + needBuilder Hpc runMakeVerbose "testsuite/tests" ["fast"] "test" ~> do diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 1750604..9f6c6e2 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -127,7 +127,7 @@ with :: Builder -> Args with b = specified b ? do top <- getTopDirectory path <- getBuilderPath b - lift $ needBuilder laxDependencies b + lift $ needBuilder b append [withBuilderKey b ++ top -/- path] withStaged :: (Stage -> Builder) -> Args diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 49a3a1d..b147665 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -2,7 +2,7 @@ module Settings.User ( buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, - laxDependencies, verboseCommands, turnWarningsIntoErrors, splitObjects + verboseCommands, turnWarningsIntoErrors, splitObjects ) where import Base @@ -74,13 +74,6 @@ ghcProfiled = False ghcDebugged :: Bool ghcDebugged = False --- | When laxDependencies is set to True, dependencies on the GHC executable --- are turned into order-only dependencies to avoid needless recompilation when --- making changes to GHC's sources. In certain situations this can lead to build --- failures, in which case you should reset the flag (at least temporarily). -laxDependencies :: Bool -laxDependencies = False - buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock From git at git.haskell.org Fri Oct 27 00:26:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: before_install steps don't merge (12c433c) Message-ID: <20171027002644.5F2833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12c433c197e3e1db24d535aae5c7d07a6dc50e8a/ghc >--------------------------------------------------------------- commit 12c433c197e3e1db24d535aae5c7d07a6dc50e8a Author: Moritz Angermann Date: Wed Jan 6 13:11:19 2016 +0800 before_install steps don't merge Moved the validation of before_install into install. >--------------------------------------------------------------- 12c433c197e3e1db24d535aae5c7d07a6dc50e8a .travis.yml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 5c5708c..1bcd7fd 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,6 +18,8 @@ matrix: - PATH="/opt/cabal/$CABALVER/bin:$PATH" - PATH="$HOME/.cabal/bin:$PATH" - export PATH + - cabal update + - os: osx before_install: - brew update @@ -27,15 +29,14 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH -before_install: + +install: + - env - ghc --version - cabal --version - alex --version - happy --version - - cabal update - -install: - travis_retry git clone git://git.haskell.org/ghc --recurse-submodules From git at git.haskell.org Fri Oct 27 00:26:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge LookupInPath and Path oracles (b42f4fd) Message-ID: <20171027002644.7C3303A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b42f4fdd21227f799c0f3ed52b2f7bfe0225f4d9/ghc >--------------------------------------------------------------- commit b42f4fdd21227f799c0f3ed52b2f7bfe0225f4d9 Author: Andrey Mokhov Date: Sun Oct 30 01:11:22 2016 +0000 Merge LookupInPath and Path oracles >--------------------------------------------------------------- b42f4fdd21227f799c0f3ed52b2f7bfe0225f4d9 hadrian.cabal | 1 - src/Oracles/LookupInPath.hs | 23 ----------------------- src/Oracles/Path.hs | 35 +++++++++++++++++++++++++---------- src/Rules/Oracles.hs | 4 +--- 4 files changed, 26 insertions(+), 37 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 954b1d6..378aff7 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -32,7 +32,6 @@ executable hadrian , Oracles.Config.Setting , Oracles.Dependencies , Oracles.DirectoryContent - , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData , Oracles.Path diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs deleted file mode 100644 index 87e8adf..0000000 --- a/src/Oracles/LookupInPath.hs +++ /dev/null @@ -1,23 +0,0 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where - -import System.Directory - -import Base - -newtype LookupInPath = LookupInPath String - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - --- | Lookup an executable in @PATH at . -lookupInPath :: FilePath -> Action FilePath -lookupInPath name - | name == takeFileName name = askOracle $ LookupInPath name - | otherwise = return name - -lookupInPathOracle :: Rules () -lookupInPathOracle = void $ - addOracle $ \(LookupInPath name) -> do - let unpack = fromMaybe . error $ "Cannot find executable " ++ quote name - path <- unifyPath <$> unpack <$> liftIO (findExecutable name) - putLoud $ "Executable found: " ++ name ++ " => " ++ path - return path diff --git a/src/Oracles/Path.hs b/src/Oracles/Path.hs index 7db1400..1a74915 100644 --- a/src/Oracles/Path.hs +++ b/src/Oracles/Path.hs @@ -1,22 +1,18 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Path ( - fixAbsolutePathOnWindows, topDirectory, getTopDirectory, windowsPathOracle, - systemBuilderPath + topDirectory, getTopDirectory, systemBuilderPath, pathOracle ) where import Control.Monad.Trans.Reader import Data.Char +import System.Directory import Base import Builder import Oracles.Config import Oracles.Config.Setting -import Oracles.LookupInPath import Stage -newtype WindowsPath = WindowsPath FilePath - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -- | Path to the GHC source tree. topDirectory :: Action FilePath topDirectory = fixAbsolutePathOnWindows =<< setting GhcSourcePath @@ -59,6 +55,12 @@ systemBuilderPath builder = case builder of return "" -- TODO: Use a safe interface. else fixAbsolutePathOnWindows =<< lookupInPath path +-- | Lookup an executable in @PATH at . +lookupInPath :: FilePath -> Action FilePath +lookupInPath name + | name == takeFileName name = askOracle $ LookupInPath name + | otherwise = return name + -- | Fix an absolute path on Windows: -- * "/c/" => "C:/" -- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" @@ -73,11 +75,24 @@ fixAbsolutePathOnWindows path = do else return path --- | Compute path mapping on Windows. This is slow and requires caching. -windowsPathOracle :: Rules () -windowsPathOracle = void $ - addOracle $ \(WindowsPath path) -> do +newtype LookupInPath = LookupInPath String + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +newtype WindowsPath = WindowsPath FilePath + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Oracles for looking up paths. These are slow and require caching. +pathOracle :: Rules () +pathOracle = do + void $ addOracle $ \(WindowsPath path) -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] let windowsPath = unifyPath $ dropWhileEnd isSpace out putLoud $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath + + void $ addOracle $ \(LookupInPath name) -> do + let unpack = fromMaybe . error $ "Cannot find executable " ++ quote name + path <- unifyPath <$> unpack <$> liftIO (findExecutable name) + putLoud $ "Executable found: " ++ name ++ " => " ++ path + return path + diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 39fbd00..6c5ace4 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -5,7 +5,6 @@ import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies import qualified Oracles.DirectoryContent -import qualified Oracles.LookupInPath import qualified Oracles.ModuleFiles import qualified Oracles.PackageData import qualified Oracles.Path @@ -16,7 +15,6 @@ oracleRules = do Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles Oracles.DirectoryContent.directoryContentOracle - Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle - Oracles.Path.windowsPathOracle + Oracles.Path.pathOracle From git at git.haskell.org Fri Oct 27 00:26:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian (b08a8f6) Message-ID: <20171027002645.13F743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b08a8f64c8d6d7137aa470f83e4fe28f9d39aa07/ghc >--------------------------------------------------------------- commit b08a8f64c8d6d7137aa470f83e4fe28f9d39aa07 Author: Andrey Mokhov Date: Wed Apr 27 00:10:35 2016 +0100 Rename to Hadrian [skip ci] >--------------------------------------------------------------- b08a8f64c8d6d7137aa470f83e4fe28f9d39aa07 README.md | 44 +++++++++++++++++++++----------------------- 1 file changed, 21 insertions(+), 23 deletions(-) diff --git a/README.md b/README.md index c61f5c6..375e4f8 100644 --- a/README.md +++ b/README.md @@ -1,20 +1,18 @@ -Shaking up GHC -============== +Hadrian +======= [![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) -This is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based +Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current [`make`-based build system][make]. If you are curious about the rationale and initial ideas behind the project you can find more details on the [wiki page][ghc-shake-wiki] -and in this [blog post][blog-post-1]. +and in this [blog post][blog-post-1]. This project was formerly known as *Shaking-up-GHC*. The new build system can work side-by-side with the existing build system. Note, there is some interaction between them: they put (some) build results in the same directories, e.g. `inplace/bin/ghc-stage1`. -[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc). - Your first build ---------------- @@ -28,17 +26,17 @@ follow these steps: packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. * Get the sources and run standard configuration scripts. It is important for the build -system to be in the `shake-build` directory of the GHC source tree: +system to be in the `hadrian` directory of the GHC source tree: ```bash git clone --recursive git://git.haskell.org/ghc.git cd ghc - git clone git://github.com/snowleopard/shaking-up-ghc shake-build + git clone git://github.com/snowleopard/hadrian ./boot ./configure # On Windows run ./configure --enable-tarballs-autodownload ``` -* Build GHC using `shake-build/build.sh` or `shake-build/build.bat` (on Windows) instead +* Build GHC using `hadrian/build.sh` or `hadrian/build.bat` (on Windows) instead of `make`. You might want to enable parallelism with `-j`. We will further refer to the build script simply as `build`. If you are interested in building in a Cabal sandbox or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Also @@ -133,20 +131,20 @@ helped me endure and enjoy the project. [make]: https://ghc.haskell.org/trac/ghc/wiki/Building/Architecture [ghc-shake-wiki]: https://ghc.haskell.org/trac/ghc/wiki/Building/Shake [blog-post-1]: https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc -[issues]: https://github.com/snowleopard/shaking-up-ghc/issues +[issues]: https://github.com/snowleopard/hadrian/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild -[windows-build]: https://github.com/snowleopard/shaking-up-ghc/blob/master/doc/windows.md -[build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 +[windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md +[build-artefacts-issue]: https://github.com/snowleopard/hadrian/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 -[user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs -[test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 -[dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 -[validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 -[flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 -[cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 -[install-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/219 -[milestones]: https://github.com/snowleopard/shaking-up-ghc/milestones -[comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 -[doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 -[contributors]: https://github.com/snowleopard/shaking-up-ghc/graphs/contributors +[user-settings]: https://github.com/snowleopard/hadrian/blob/master/src/Settings/User.hs +[test-issue]: https://github.com/snowleopard/hadrian/issues/197 +[dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 +[validation-issue]: https://github.com/snowleopard/hadrian/issues/187 +[flavours-issue]: https://github.com/snowleopard/hadrian/issues/188 +[cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 +[install-issue]: https://github.com/snowleopard/hadrian/issues/219 +[milestones]: https://github.com/snowleopard/hadrian/milestones +[comments-issue]: https://github.com/snowleopard/hadrian/issues/55 +[doc-issue]: https://github.com/snowleopard/hadrian/issues/56 +[contributors]: https://github.com/snowleopard/hadrian/graphs/contributors From git at git.haskell.org Fri Oct 27 00:26:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set CONFIG_SHELL, such that libtool obtains the bash header. (cb74ce8) Message-ID: <20171027002647.EBC853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb74ce8f2ca00bc2cfac8b003c4c7adade5734af/ghc >--------------------------------------------------------------- commit cb74ce8f2ca00bc2cfac8b003c4c7adade5734af Author: Moritz Angermann Date: Wed Jan 6 14:37:10 2016 +0800 Set CONFIG_SHELL, such that libtool obtains the bash header. This improves on #103 and fixes #114, hopefully. >--------------------------------------------------------------- cb74ce8f2ca00bc2cfac8b003c4c7adade5734af src/Rules/Actions.hs | 6 +++++- src/Rules/IntegerGmp.hs | 2 +- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9250357..e32a42f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -94,7 +94,11 @@ runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] putBuild $ "| Run configure in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts args + quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args + where + -- Always configure with bash. + -- This also injects /bin/bash into `libtool`, instead of /bin/sh + opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] runMake :: FilePath -> [String] -> Action () runMake dir args = do diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 2b9bbd9..7ef124f 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -114,7 +114,7 @@ integerGmpRules = do copyFile integerGmpLibraryFakeH integerGmpLibraryH else do putBuild "| No GMP framework detected; in tree GMP will be built" - runMake integerGmpBuild ["MAKEFLAGS='LIBTOOL=bash\\ libtool'"] + runMake integerGmpBuild [] copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryInTreeH copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryH From git at git.haskell.org Fri Oct 27 00:26:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename src/Settings/Paths.hs -> src/Settings/Path.hs (e31cb51) Message-ID: <20171027002648.6E3963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e31cb5136a66213f8afb744c2b7c81344fc3975a/ghc >--------------------------------------------------------------- commit e31cb5136a66213f8afb744c2b7c81344fc3975a Author: Andrey Mokhov Date: Sun Oct 30 01:20:01 2016 +0000 Rename src/Settings/Paths.hs -> src/Settings/Path.hs >--------------------------------------------------------------- e31cb5136a66213f8afb744c2b7c81344fc3975a hadrian.cabal | 2 +- src/Main.hs | 4 ++-- src/Oracles/Dependencies.hs | 2 +- src/Oracles/ModuleFiles.hs | 2 +- src/Rules.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 2 +- src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Generators/ConfigHs.hs | 2 +- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 2 +- src/Rules/Test.hs | 2 +- src/Rules/Wrappers/GhcPkg.hs | 2 +- src/Settings.hs | 2 +- src/Settings/Builders/Common.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/{Paths.hs => Path.hs} | 2 +- 27 files changed, 29 insertions(+), 29 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e31cb5136a66213f8afb744c2b7c81344fc3975a From git at git.haskell.org Fri Oct 27 00:26:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian. (cf2b1da) Message-ID: <20171027002649.026B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf2b1da44222a8abc3f1d8cbc66c800631348114/ghc >--------------------------------------------------------------- commit cf2b1da44222a8abc3f1d8cbc66c800631348114 Author: Andrey Mokhov Date: Wed Apr 27 00:34:46 2016 +0100 Rename to Hadrian. [skip ci] >--------------------------------------------------------------- cf2b1da44222a8abc3f1d8cbc66c800631348114 shaking-up-ghc.cabal => hadrian.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/shaking-up-ghc.cabal b/hadrian.cabal similarity index 97% rename from shaking-up-ghc.cabal rename to hadrian.cabal index a5e6d22..a2df30a 100644 --- a/shaking-up-ghc.cabal +++ b/hadrian.cabal @@ -1,18 +1,18 @@ -name: shaking-up-ghc +name: hadrian version: 0.1.0.0 synopsis: GHC build system license: BSD3 license-file: LICENSE author: Andrey Mokhov , github: @snowleopard maintainer: Andrey Mokhov , github: @snowleopard -copyright: Andrey Mokhov 2014-2015 +copyright: Andrey Mokhov 2014-2016 category: Development build-type: Simple cabal-version: >=1.10 source-repository head type: git - location: https://github.com/snowleopard/shaking-up-ghc + location: https://github.com/snowleopard/hadrian executable ghc-shake main-is: Main.hs From git at git.haskell.org Fri Oct 27 00:26:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove -Wall and -fwarn-tabs, fix #116. (f8d9ddc) Message-ID: <20171027002651.F123C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8d9ddc5a43872f248d60e7fcdb1f0c5be580cc1/ghc >--------------------------------------------------------------- commit f8d9ddc5a43872f248d60e7fcdb1f0c5be580cc1 Author: Andrey Mokhov Date: Wed Jan 6 10:41:19 2016 +0000 Remove -Wall and -fwarn-tabs, fix #116. >--------------------------------------------------------------- f8d9ddc5a43872f248d60e7fcdb1f0c5be580cc1 src/Settings/User.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index aba4a48..7a877ce 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -8,11 +8,11 @@ module Settings.User ( import GHC import Expression +import Predicates --- No user-specific settings by default --- TODO: rename to userArgs +-- Control user-specific settings userArgs :: Args -userArgs = mempty +userArgs = builderGhc ? remove ["-Wall", "-fwarn-tabs"] -- Control which packages get to be built userPackages :: Packages From git at git.haskell.org Fri Oct 27 00:26:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename src/Rules/Actions.hs -> src/Util.hs (fb30a88) Message-ID: <20171027002652.B2C4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fb30a88d4b90d9bbac63d45fd9d92223a7947947/ghc >--------------------------------------------------------------- commit fb30a88d4b90d9bbac63d45fd9d92223a7947947 Author: Andrey Mokhov Date: Sun Oct 30 01:29:51 2016 +0000 Rename src/Rules/Actions.hs -> src/Util.hs >--------------------------------------------------------------- fb30a88d4b90d9bbac63d45fd9d92223a7947947 hadrian.cabal | 2 +- src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Configure.hs | 2 +- src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Perl.hs | 2 +- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/{Rules/Actions.hs => Util.hs} | 2 +- 18 files changed, 18 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fb30a88d4b90d9bbac63d45fd9d92223a7947947 From git at git.haskell.org Fri Oct 27 00:26:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian (2736806) Message-ID: <20171027002653.1DC0A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27368067f3c22a5313ab507f5f5beede19bcf9bf/ghc >--------------------------------------------------------------- commit 27368067f3c22a5313ab507f5f5beede19bcf9bf Author: Andrey Mokhov Date: Wed Apr 27 00:37:25 2016 +0100 Rename to Hadrian [skip ci] >--------------------------------------------------------------- 27368067f3c22a5313ab507f5f5beede19bcf9bf LICENSE | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/LICENSE b/LICENSE index 9ee6e34..fbedb41 100644 --- a/LICENSE +++ b/LICENSE @@ -1,6 +1,6 @@ BSD License -Copyright (c) 2015, Andrey Mokhov +Copyright (c) 2014, Andrey Mokhov All rights reserved. Redistribution and use in source and binary forms, with or without @@ -13,7 +13,7 @@ modification, are permitted provided that the following conditions are met: this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. -* Neither the name of Shaking up GHC nor the names of its +* Neither the name of the Hadrian project nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. From git at git.haskell.org Fri Oct 27 00:26:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds "MAKEFLAGS=" back in. (7b5c5bf) Message-ID: <20171027002656.222833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b5c5bf2250f088bac663c2d2773b32d5e1b756b/ghc >--------------------------------------------------------------- commit 7b5c5bf2250f088bac663c2d2773b32d5e1b756b Author: Moritz Angermann Date: Wed Jan 6 18:48:56 2016 +0800 Adds "MAKEFLAGS=" back in. >--------------------------------------------------------------- 7b5c5bf2250f088bac663c2d2773b32d5e1b756b src/Rules/IntegerGmp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 7ef124f..b82dcbb 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -114,7 +114,7 @@ integerGmpRules = do copyFile integerGmpLibraryFakeH integerGmpLibraryH else do putBuild "| No GMP framework detected; in tree GMP will be built" - runMake integerGmpBuild [] + runMake integerGmpBuild ["MAKEFLAGS="] copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryInTreeH copyFile (integerGmpBuild -/- "gmp.h") integerGmpLibraryH From git at git.haskell.org Fri Oct 27 00:26:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian (0c5fe5b) Message-ID: <20171027002657.8B7073A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c5fe5b08bc591073351b60a5e76c9a0a09ad686/ghc >--------------------------------------------------------------- commit 0c5fe5b08bc591073351b60a5e76c9a0a09ad686 Author: Andrey Mokhov Date: Wed Apr 27 00:39:10 2016 +0100 Rename to Hadrian [skip ci] >--------------------------------------------------------------- 0c5fe5b08bc591073351b60a5e76c9a0a09ad686 doc/windows.md | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 7fc8dcf..7afd97c 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -9,11 +9,11 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ stack exec -- pacman -S gcc binutils git automake-wrapper tar make patch autoconf --noconfirm stack exec -- git clone --recursive git://git.haskell.org/ghc.git cd ghc - stack exec -- git clone git://github.com/snowleopard/shaking-up-ghc shake-build - stack build --stack-yaml=shake-build/stack.yaml --only-dependencies + stack exec -- git clone git://github.com/snowleopard/hadrian + stack build --stack-yaml=hadrian/stack.yaml --only-dependencies stack exec -- perl boot stack exec -- bash configure --enable-tarballs-autodownload - stack exec --stack-yaml=shake-build/stack.yaml -- shake-build/build.bat -j + stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j The entire process should take about an hour. @@ -21,6 +21,6 @@ The entire process should take about an hour. Here are some alternatives that have been considered, but not yet tested. Use the instructions above. -* Use `shake-build/build.bat --setup` to replace `boot` and `configure`. +* Use `hadrian/build.bat --setup` to replace `boot` and `configure`. * The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. * Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:26:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify defaultPackages definition (75281f2) Message-ID: <20171027002657.88CDE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/75281f2899cc8e3a890dc1af25a06cd81afb6c1e/ghc >--------------------------------------------------------------- commit 75281f2899cc8e3a890dc1af25a06cd81afb6c1e Author: Andrey Mokhov Date: Sun Oct 30 02:18:53 2016 +0000 Simplify defaultPackages definition >--------------------------------------------------------------- 75281f2899cc8e3a890dc1af25a06cd81afb6c1e src/Settings/Default.hs | 96 ++++++++++++++++++++++++++++++++++++------------- 1 file changed, 71 insertions(+), 25 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index f7ef62e..9f61ff7 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -90,42 +90,88 @@ defaultArgs = mconcat , defaultPackageArgs , builder Ghc ? remove ["-Wall", "-fwarn-tabs"] ] -- TODO: Fix warning Args. --- TODO: Simplify. -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". defaultPackages :: Packages -defaultPackages = mconcat - [ stage0 ? packagesStage0 - , stage1 ? packagesStage1 - , stage2 ? packagesStage2 ] +defaultPackages = mconcat [ packagesStage0, packagesStage1, packagesStage2 ] packagesStage0 :: Packages -packagesStage0 = mconcat - [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcBootTh, ghcCabal - , ghcPkg, hsc2hs, hoopl, hpc, templateHaskell, transformers ] - -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode - , hp2ps, unlit, mkUserGuidePart ] - , stage0 ? windowsHost ? append [touchy] - , notM windowsHost ? notM iosHost ? append [terminfo] ] +packagesStage0 = stage0 ? do + win <- lift windowsHost + ios <- lift iosHost + append $ [ binary + , cabal + , compiler + , deriveConstants + , dllSplit + , genapply + , genprimopcode + , ghc + , ghcBoot + , ghcBootTh + , ghcCabal + , ghcPkg + , hsc2hs + , hoopl + , hp2ps + , hpc + , mkUserGuidePart + , templateHaskell + , transformers + , unlit ] ++ + [ terminfo | not win, not ios ] ++ + [ touchy | win ] packagesStage1 :: Packages -packagesStage1 = mconcat - [ packagesStage0 - , append [ array, base, bytestring, containers, compareSizes, deepseq - , directory, filepath, ghci, ghcPrim, haskeline, hpcBin - , integerLibrary, pretty, process, rts, runGhc, time ] - , windowsHost ? append [win32] - , notM windowsHost ? append [unix] - , notM windowsHost ? append [iservBin] - , buildHaddock flavour ? append [xhtml] ] +packagesStage1 = stage1 ? do + win <- lift windowsHost + ios <- lift iosHost + doc <- buildHaddock flavour + append $ [ array + , base + , binary + , bytestring + , cabal + , containers + , compareSizes + , compiler + , deepseq + , directory + , filepath + , ghc + , ghcBoot + , ghcBootTh + , ghcCabal + , ghci + , ghcPkg + , ghcPrim + , haskeline + , hoopl + , hpc + , hpcBin + , hsc2hs + , integerLibrary + , pretty + , process + , rts + , runGhc + , templateHaskell + , time + , transformers ] ++ + [ iservBin | not win ] ++ + [ terminfo | not win, not ios ] ++ + [ unix | not win ] ++ + [ win32 | win ] ++ + [ xhtml | doc ] -- TODO: Currently there is an unchecked assumption that we build only programs -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages -packagesStage2 = mconcat - [ append [checkApiAnnotations, ghcTags ] - , buildHaddock flavour ? append [haddock] ] +packagesStage2 = stage2 ? do + doc <- buildHaddock flavour + append $ [ checkApiAnnotations + , ghcTags ] ++ + [ haddock | doc ] -- TODO: What about profilingDynamic way? Do we need platformSupportsSharedLibs? -- | Default build ways for library packages: From git at git.haskell.org Fri Oct 27 00:26:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:26:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #115 from angerman/feature/libtool (2f52d19) Message-ID: <20171027002659.EC0B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f52d196dbd5cd3f1da25286deef5cb3cd17c142/ghc >--------------------------------------------------------------- commit 2f52d196dbd5cd3f1da25286deef5cb3cd17c142 Merge: f8d9ddc 7b5c5bf Author: Andrey Mokhov Date: Wed Jan 6 10:51:29 2016 +0000 Merge pull request #115 from angerman/feature/libtool Set CONFIG_SHELL, such that libtool obtains the bash header. >--------------------------------------------------------------- 2f52d196dbd5cd3f1da25286deef5cb3cd17c142 src/Rules/Actions.hs | 6 +++++- src/Rules/IntegerGmp.hs | 2 +- 2 files changed, 6 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 00:27:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (223d161) Message-ID: <20171027002701.6E71A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/223d16102070b2d1061197ebb111ca3c9d2ffd45/ghc >--------------------------------------------------------------- commit 223d16102070b2d1061197ebb111ca3c9d2ffd45 Author: Andrey Mokhov Date: Sun Oct 30 13:28:09 2016 +0000 Minor revision >--------------------------------------------------------------- 223d16102070b2d1061197ebb111ca3c9d2ffd45 src/Settings/Default.hs | 163 +++++++++++++++++++++++------------------------- 1 file changed, 77 insertions(+), 86 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 9f61ff7..b59ceeb 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -43,46 +43,6 @@ import Settings.Packages.Touchy import Settings.Packages.Unlit import UserSettings --- | All 'Builder'-dependent command line arguments. -defaultBuilderArgs :: Args -defaultBuilderArgs = mconcat - [ alexBuilderArgs - , arBuilderArgs - , ccBuilderArgs - , configureBuilderArgs - , deriveConstantsBuilderArgs - , genPrimopCodeBuilderArgs - , ghcBuilderArgs - , ghcCabalBuilderArgs - , ghcCabalHsColourBuilderArgs - , ghcMBuilderArgs - , ghcPkgBuilderArgs - , haddockBuilderArgs - , happyBuilderArgs - , hsc2hsBuilderArgs - , hsCppBuilderArgs - , ldBuilderArgs - , makeBuilderArgs - , tarBuilderArgs ] - --- | All 'Package'-dependent command line arguments. -defaultPackageArgs :: Args -defaultPackageArgs = mconcat - [ basePackageArgs - , compilerPackageArgs - , directoryPackageArgs - , ghcPackageArgs - , ghcCabalPackageArgs - , ghcPrimPackageArgs - , haddockPackageArgs - , hp2psPackageArgs - , integerGmpPackageArgs - , iservBinPackageArgs - , rtsPackageArgs - , runGhcPackageArgs - , touchyPackageArgs - , unlitPackageArgs ] - -- | All default command line arguments. defaultArgs :: Args defaultArgs = mconcat @@ -93,10 +53,12 @@ defaultArgs = mconcat -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". defaultPackages :: Packages -defaultPackages = mconcat [ packagesStage0, packagesStage1, packagesStage2 ] +defaultPackages = mconcat [ stage0 ? stage0Packages + , stage1 ? stage1Packages + , stage2 ? stage2Packages ] -packagesStage0 :: Packages -packagesStage0 = stage0 ? do +stage0Packages :: Packages +stage0Packages = do win <- lift windowsHost ios <- lift iosHost append $ [ binary @@ -122,52 +84,41 @@ packagesStage0 = stage0 ? do [ terminfo | not win, not ios ] ++ [ touchy | win ] -packagesStage1 :: Packages -packagesStage1 = stage1 ? do +stage1Packages :: Packages +stage1Packages = do win <- lift windowsHost - ios <- lift iosHost doc <- buildHaddock flavour - append $ [ array - , base - , binary - , bytestring - , cabal - , containers - , compareSizes - , compiler - , deepseq - , directory - , filepath - , ghc - , ghcBoot - , ghcBootTh - , ghcCabal - , ghci - , ghcPkg - , ghcPrim - , haskeline - , hoopl - , hpc - , hpcBin - , hsc2hs - , integerLibrary - , pretty - , process - , rts - , runGhc - , templateHaskell - , time - , transformers ] ++ - [ iservBin | not win ] ++ - [ terminfo | not win, not ios ] ++ - [ unix | not win ] ++ - [ win32 | win ] ++ - [ xhtml | doc ] + mconcat [ stage0Packages + , apply (filter isLibrary) -- Build all Stage0 libraries in Stage1 + , append $ [ array + , base + , bytestring + , containers + , compareSizes + , deepseq + , directory + , filepath + , ghc + , ghcCabal + , ghci + , ghcPkg + , ghcPrim + , haskeline + , hpcBin + , hsc2hs + , integerLibrary + , pretty + , process + , rts + , runGhc + , time ] ++ + [ iservBin | not win ] ++ + [ unix | not win ] ++ + [ win32 | win ] ++ + [ xhtml | doc ] ] --- TODO: Currently there is an unchecked assumption that we build only programs --- in Stage2 and Stage3. Can we check this in compile time? -packagesStage2 :: Packages -packagesStage2 = stage2 ? do +stage2Packages :: Packages +stage2Packages = do doc <- buildHaddock flavour append $ [ checkApiAnnotations , ghcTags ] ++ @@ -220,3 +171,43 @@ defaultSplitObjects = do supported <- lift supportsSplitObjects let goodPackage = isLibrary pkg && pkg /= compiler && pkg /= rts return $ cmdSplitObjects && goodStage && goodPackage && supported + +-- | All 'Builder'-dependent command line arguments. +defaultBuilderArgs :: Args +defaultBuilderArgs = mconcat + [ alexBuilderArgs + , arBuilderArgs + , ccBuilderArgs + , configureBuilderArgs + , deriveConstantsBuilderArgs + , genPrimopCodeBuilderArgs + , ghcBuilderArgs + , ghcCabalBuilderArgs + , ghcCabalHsColourBuilderArgs + , ghcMBuilderArgs + , ghcPkgBuilderArgs + , haddockBuilderArgs + , happyBuilderArgs + , hsc2hsBuilderArgs + , hsCppBuilderArgs + , ldBuilderArgs + , makeBuilderArgs + , tarBuilderArgs ] + +-- | All 'Package'-dependent command line arguments. +defaultPackageArgs :: Args +defaultPackageArgs = mconcat + [ basePackageArgs + , compilerPackageArgs + , directoryPackageArgs + , ghcPackageArgs + , ghcCabalPackageArgs + , ghcPrimPackageArgs + , haddockPackageArgs + , hp2psPackageArgs + , integerGmpPackageArgs + , iservBinPackageArgs + , rtsPackageArgs + , runGhcPackageArgs + , touchyPackageArgs + , unlitPackageArgs ] From git at git.haskell.org Fri Oct 27 00:27:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian. (11759a8) Message-ID: <20171027002701.9404C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/11759a8ee0d735e2331d4d617031dd3dcc3069f6/ghc >--------------------------------------------------------------- commit 11759a8ee0d735e2331d4d617031dd3dcc3069f6 Author: Andrey Mokhov Date: Wed Apr 27 00:45:38 2016 +0100 Rename to Hadrian. [skip ci] >--------------------------------------------------------------- 11759a8ee0d735e2331d4d617031dd3dcc3069f6 .travis.yml | 18 +++++++++--------- appveyor.yml | 6 +++--- 2 files changed, 12 insertions(+), 12 deletions(-) diff --git a/.travis.yml b/.travis.yml index d6092fb..6832cd8 100644 --- a/.travis.yml +++ b/.travis.yml @@ -47,22 +47,22 @@ install: # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake # ".git" directory into the appropriate location, and perform a hard reset # in order to regenerate the GHC-Shake files. - - mkdir ghc/shake-build - - mv .git ghc/shake-build - - ( cd ghc/shake-build && git reset --hard HEAD ) + - mkdir ghc/hadrian + - mv .git ghc/hadrian + - ( cd ghc/hadrian && git reset --hard HEAD ) - - ( cd ghc/shake-build && cabal install --only-dependencies ) - - ( cd ghc/shake-build && cabal configure ) + - ( cd ghc/hadrian && cabal install --only-dependencies ) + - ( cd ghc/hadrian && cabal configure ) - ( cd ghc && ./boot ) - ( cd ghc && ./configure ) - - cat ghc/shake-build/cfg/system.config + - cat ghc/hadrian/cfg/system.config - ghc-pkg list script: - - ( cd ghc/shake-build && cabal haddock --internal ) - - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --profile=- --flavour=quick $TARGET + - ( cd ghc/hadrian && cabal haddock --internal ) + - ./ghc/hadrian/build.sh selftest + - ./ghc/hadrian/build.sh -j --no-progress --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index 6cc17b6..3918779 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -1,4 +1,4 @@ -clone_folder: "C:\\msys64\\home\\ghc\\shake-build" +clone_folder: "C:\\msys64\\home\\ghc\\hadrian" environment: global: STACK_ROOT: "c:\\sr" @@ -30,7 +30,7 @@ install: - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/609505834ca4a9178b8263b00208ec651318c8c1/ghc >--------------------------------------------------------------- commit 609505834ca4a9178b8263b00208ec651318c8c1 Merge: 2f52d19 12c433c Author: Andrey Mokhov Date: Wed Jan 6 10:56:48 2016 +0000 Merge pull request #112 from angerman/feature/osx-ci Adds osx to the list of operatin systems in the travis.yml >--------------------------------------------------------------- 609505834ca4a9178b8263b00208ec651318c8c1 .travis.yml | 55 +++++++++++++++++++++++++++++-------------------------- 1 file changed, 29 insertions(+), 26 deletions(-) From git at git.haskell.org Fri Oct 27 00:27:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a selftest for Packages (e2871fc) Message-ID: <20171027002705.A0C043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2871fc28f9f8de741326bdc9b7ad48aa1936393/ghc >--------------------------------------------------------------- commit e2871fc28f9f8de741326bdc9b7ad48aa1936393 Author: Andrey Mokhov Date: Sun Oct 30 17:26:46 2016 +0000 Add a selftest for Packages >--------------------------------------------------------------- e2871fc28f9f8de741326bdc9b7ad48aa1936393 src/Rules/Selftest.hs | 53 ++++++++++++++++++++++++++++++--------------------- 1 file changed, 31 insertions(+), 22 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index e7f5dbb..58de8fb 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,11 +6,11 @@ import Development.Shake import Test.QuickCheck import Base -import Builder +import Expression import Oracles.ModuleFiles +import Settings import Settings.Builders.Ar import UserSettings -import Way instance Arbitrary Way where arbitrary = wayFromUnits <$> arbitrary @@ -25,11 +25,12 @@ selftestRules :: Rules () selftestRules = "selftest" ~> do testBuilder - testWay testChunksOfSize + testLookupAll testMatchVersionedFilePath testModuleName - testLookupAll + testPackages + testWay testBuilder :: Action () testBuilder = do @@ -39,11 +40,6 @@ testBuilder = do trackedArgument (Make undefined) prefix == False && trackedArgument (Make undefined) ("-j" ++ show (n :: Int)) == False -testWay :: Action () -testWay = do - putBuild $ "==== Read Way, Show Way" - test $ \(x :: Way) -> read (show x) == x - testChunksOfSize :: Action () testChunksOfSize = do putBuild $ "==== chunksOfSize" @@ -53,6 +49,20 @@ testChunksOfSize = do let res = chunksOfSize n xs in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res +testLookupAll :: Action () +testLookupAll = do + putBuild $ "==== lookupAll" + test $ lookupAll ["b" , "c" ] [("a", 1), ("c", 3), ("d", 4)] + == [Nothing, Just (3 :: Int)] + test $ forAll dicts $ \dict -> forAll extras $ \extra -> + let items = sort $ map fst dict ++ extra + in lookupAll items (sort dict) == map (flip lookup dict) items + where + dicts :: Gen [(Int, Int)] + dicts = nubBy ((==) `on` fst) <$> vector 20 + extras :: Gen [Int] + extras = vector 20 + testMatchVersionedFilePath :: Action () testMatchVersionedFilePath = do putBuild $ "==== matchVersionedFilePath" @@ -82,16 +92,15 @@ testModuleName = do where names = intercalate "." <$> listOf1 (listOf1 $ elements "abcABC123_'") -testLookupAll :: Action () -testLookupAll = do - putBuild $ "==== lookupAll" - test $ lookupAll ["b" , "c" ] [("a", 1), ("c", 3), ("d", 4)] - == [Nothing, Just (3 :: Int)] - test $ forAll dicts $ \dict -> forAll extras $ \extra -> - let items = sort $ map fst dict ++ extra - in lookupAll items (sort dict) == map (flip lookup dict) items - where - dicts :: Gen [(Int, Int)] - dicts = nubBy ((==) `on` fst) <$> vector 20 - extras :: Gen [Int] - extras = vector 20 +testPackages :: Action () +testPackages = do + putBuild $ "==== Packages, interpretInContext" + forM_ [Stage0 ..] $ \stage -> do + pkgs <- stagePackages stage + test $ pkgs == nubOrd pkgs + +testWay :: Action () +testWay = do + putBuild $ "==== Read Way, Show Way" + test $ \(x :: Way) -> read (show x) == x + From git at git.haskell.org Fri Oct 27 00:27:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename project executable to hadrian. (affe0bd) Message-ID: <20171027002705.C61523A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/affe0bd9add35be2a801a68a0cc1309f2bdb176a/ghc >--------------------------------------------------------------- commit affe0bd9add35be2a801a68a0cc1309f2bdb176a Author: Andrey Mokhov Date: Wed Apr 27 00:50:27 2016 +0100 Rename project executable to hadrian. >--------------------------------------------------------------- affe0bd9add35be2a801a68a0cc1309f2bdb176a build.cabal-new.sh | 8 ++++---- build.cabal.sh | 2 +- build.stack.sh | 2 +- hadrian.cabal | 2 +- src/Environment.hs | 2 +- 5 files changed, 8 insertions(+), 8 deletions(-) diff --git a/build.cabal-new.sh b/build.cabal-new.sh index 96c194e..bca8c7c 100755 --- a/build.cabal-new.sh +++ b/build.cabal-new.sh @@ -38,16 +38,16 @@ mkdir -p "$root/.shake" # Notes/Random thoughts: # # - if ghc.git had a top-level `cabal.project` file, we could maybe avoid the -# boilerplate above, as we could simply say `cabal exec ghc-shake` from within +# boilerplate above, as we could simply say `cabal exec hadrian` from within # any GHC folder not shadowed by a nearer shadowing `cabal.project` file. pushd "$root/" -cabal new-build --disable-profiling --disable-documentation -j exe:ghc-shake +cabal new-build --disable-profiling --disable-documentation -j exe:hadrian -PKGVER="$(awk '/^version:/ { print $2 }' shaking-up-ghc.cabal)" +PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" -cp -v "$root/dist-newstyle/build/shaking-up-ghc-${PKGVER}/build/ghc-shake/ghc-shake" \ +cp -v "$root/dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ "$root/.shake/build" popd diff --git a/build.cabal.sh b/build.cabal.sh index 5f20c1b..f2e320e 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -40,7 +40,7 @@ if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then --disable-shared fi -cabal run ghc-shake -- \ +cabal run hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ --colour \ diff --git a/build.stack.sh b/build.stack.sh index 578e7eb..b5607b1 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -33,7 +33,7 @@ cd "$absoluteRoot" stack build --no-library-profiling -stack exec ghc-shake -- \ +stack exec hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ --colour \ diff --git a/hadrian.cabal b/hadrian.cabal index a2df30a..4bf5a4c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -14,7 +14,7 @@ source-repository head type: git location: https://github.com/snowleopard/hadrian -executable ghc-shake +executable hadrian main-is: Main.hs hs-source-dirs: src other-modules: Base diff --git a/src/Environment.hs b/src/Environment.hs index e674f83..d4d9853 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -13,7 +13,7 @@ setupEnvironment = do -- in MinGW if PWD is set to a Windows "C:\\" style path then configure -- `pwd` will return the Windows path, and then modifying $PATH will fail. - -- See https://github.com/snowleopard/shaking-up-ghc/issues/189 for details. + -- See https://github.com/snowleopard/hadrian/issues/189 for details. unsetEnv "PWD" -- On Windows, some path variables start a prefix like "C:\\" which may From git at git.haskell.org Fri Oct 27 00:27:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify extraObjects in src/Rules/Library.hs, see #117. (ce8ffdb) Message-ID: <20171027002707.221053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ce8ffdbbb7d477d022f5df20e77467413f80349b/ghc >--------------------------------------------------------------- commit ce8ffdbbb7d477d022f5df20e77467413f80349b Author: Andrey Mokhov Date: Wed Jan 6 11:10:49 2016 +0000 Simplify extraObjects in src/Rules/Library.hs, see #117. >--------------------------------------------------------------- ce8ffdbbb7d477d022f5df20e77467413f80349b src/Rules/Library.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 41e7b3d..46f3971 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -80,9 +80,5 @@ extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do need [integerGmpLibraryH] - objsExist <- doesDirectoryExist integerGmpObjects - putBuild $ "objsExist = " ++ show objsExist - if objsExist - then getDirectoryFiles "" [integerGmpObjects -/- "*.o"] - else return [] + getDirectoryFiles "" [integerGmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:27:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run selftest in GHC tree (f808265) Message-ID: <20171027002709.1FF003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f808265388e8356810b450acf72531475b18d340/ghc >--------------------------------------------------------------- commit f808265388e8356810b450acf72531475b18d340 Author: Andrey Mokhov Date: Sun Oct 30 17:46:37 2016 +0000 Run selftest in GHC tree >--------------------------------------------------------------- f808265388e8356810b450acf72531475b18d340 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 7687500..b80008c 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -29,7 +29,7 @@ build_script: - stack build # Run internal Hadrian tests - - stack exec hadrian -- selftest + - stack exec hadrian -- --directory ".." selftest # Build GHC - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- From git at git.haskell.org Fri Oct 27 00:27:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add TODOs. (c32b33d) Message-ID: <20171027002709.3FA423A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c32b33d53a3952658d714c975832bb84984b5fe5/ghc >--------------------------------------------------------------- commit c32b33d53a3952658d714c975832bb84984b5fe5 Author: Andrey Mokhov Date: Wed Apr 27 00:58:40 2016 +0100 Add TODOs. [skip ci] >--------------------------------------------------------------- c32b33d53a3952658d714c975832bb84984b5fe5 src/Settings/User.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index b147665..ef08df0 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -12,6 +12,7 @@ import Expression import Predicates import Settings.Default +-- TODO: Rename to _build. -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath buildRootPath = ".build" @@ -83,6 +84,7 @@ buildHaddock = return cmdBuildHaddock verboseCommands :: Predicate verboseCommands = return False +-- TODO: Replace with stage2 ? arg "-Werror"? -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False From git at git.haskell.org Fri Oct 27 00:27:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor generated dependencies (41ecfdc) Message-ID: <20171027002710.954213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/41ecfdc70602aed5335f7205a092c336c090ec90/ghc >--------------------------------------------------------------- commit 41ecfdc70602aed5335f7205a092c336c090ec90 Author: Andrey Mokhov Date: Wed Jan 6 11:56:22 2016 +0000 Refactor generated dependencies Do not proceed with building a package until all its generated dependencies are in place. List generated files in ghcPrim package, see #117. >--------------------------------------------------------------- 41ecfdc70602aed5335f7205a092c336c090ec90 src/Rules/Data.hs | 5 +++++ src/Rules/Dependencies.hs | 3 --- src/Rules/Generate.hs | 17 ++++++++++------- src/Rules/IntegerGmp.hs | 7 ++++++- 4 files changed, 21 insertions(+), 11 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 42fb2a6..29f8d3d 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -6,6 +6,7 @@ import GHC import Oracles import Predicates (registerPackage) import Rules.Actions +import Rules.Generate import Rules.Resources import Settings import Settings.Builders.Common @@ -19,6 +20,10 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do dataFile = pkgDataFile stage pkg dataFile %> \mk -> do + -- The first thing we do with any package is make sure all generated + -- dependencies are in place before proceeding. + orderOnly $ generatedDependencies stage pkg + -- GhcCabal may run the configure script, so we depend on it -- We don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 5b51c1d..79bcdb2 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -4,7 +4,6 @@ import Base import Expression import Oracles import Rules.Actions -import Rules.Generate import Rules.Resources import Settings import Development.Shake.Util (parseMakefile) @@ -18,13 +17,11 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = in do [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do let srcFile = dropBuild . dropExtension $ out - orderOnly $ generatedDependencies stage pkg need [srcFile] build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources - orderOnly $ generatedDependencies stage pkg need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 2b33a53..3eb1231 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -35,13 +35,15 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -integerGmpDependencies :: [FilePath] -integerGmpDependencies = [integerGmpLibraryH] - defaultDependencies :: [FilePath] defaultDependencies = includesDependencies ++ libffiDependencies ++ integerGmpDependencies +ghcPrimDependencies :: Stage -> [FilePath] +ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> + [ "GHC/PrimopWrappers.hs" + , "autogen/GHC/Prim.hs" ] + derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = (derivedConstantsPath -/-) <$> [ "DerivedConstants.h" @@ -72,10 +74,11 @@ compilerDependencies stage = generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage - | pkg == rts = derivedConstantsDependencies - | stage == Stage0 = defaultDependencies - | otherwise = [] + | pkg == compiler = compilerDependencies stage + | pkg == ghcPrim = ghcPrimDependencies stage + | pkg == rts = derivedConstantsDependencies + | stage == Stage0 = defaultDependencies + | otherwise = [] -- The following generators and corresponding source extensions are supported: knownGenerators :: [ (Builder, String) ] diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index b82dcbb..b796c6c 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,4 +1,6 @@ -module Rules.IntegerGmp (integerGmpRules, integerGmpObjects, integerGmpLibraryH) where +module Rules.IntegerGmp ( + integerGmpRules, integerGmpObjects, integerGmpLibraryH, integerGmpDependencies + ) where import Base import Expression @@ -28,6 +30,9 @@ integerGmpLibraryH = pkgPath integerGmp -/- "include/ghc-gmp.h" integerGmpLibraryFakeH :: FilePath integerGmpLibraryFakeH = integerGmpBase -/- "ghc-gmp.h" +integerGmpDependencies :: [FilePath] +integerGmpDependencies = [integerGmpLibraryH] + -- relative to integerGmpBuild integerGmpPatch :: FilePath integerGmpPatch = ".." -/- "tarball" -/- "gmp-5.0.4.patch" From git at git.haskell.org Fri Oct 27 00:27:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test conditions for building win32 and unix packages (63ba250) Message-ID: <20171027002712.BA8DA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/63ba25048c8c4ccf62f96704deb2ebfffefb2040/ghc >--------------------------------------------------------------- commit 63ba25048c8c4ccf62f96704deb2ebfffefb2040 Author: Andrey Mokhov Date: Sun Oct 30 17:58:54 2016 +0000 Test conditions for building win32 and unix packages See #197 >--------------------------------------------------------------- 63ba25048c8c4ccf62f96704deb2ebfffefb2040 src/Rules/Selftest.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 58de8fb..0a63641 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -7,6 +7,8 @@ import Test.QuickCheck import Base import Expression +import GHC +import Oracles.Config.Setting import Oracles.ModuleFiles import Settings import Settings.Builders.Ar @@ -94,9 +96,13 @@ testModuleName = do testPackages :: Action () testPackages = do - putBuild $ "==== Packages, interpretInContext" + putBuild $ "==== Check system configuration" + win <- windowsHost -- This depends on the @boot@ and @configure@ scripts. + putBuild $ "==== Packages, interpretInContext, configuration flags" forM_ [Stage0 ..] $ \stage -> do pkgs <- stagePackages stage + when (win32 `elem` pkgs) . test $ win + when (unix `elem` pkgs) . test $ not win test $ pkgs == nubOrd pkgs testWay :: Action () From git at git.haskell.org Fri Oct 27 00:27:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Cache $HOME/.ghc as well (9784dfb) Message-ID: <20171027002714.5E5373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9784dfb75fdbafb1aa16422eee0bde40ce0ace13/ghc >--------------------------------------------------------------- commit 9784dfb75fdbafb1aa16422eee0bde40ce0ace13 Author: David Luposchainsky Date: Tue Jan 5 16:45:41 2016 +0100 Cache $HOME/.ghc as well >--------------------------------------------------------------- 9784dfb75fdbafb1aa16422eee0bde40ce0ace13 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 68e843c..055edd5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,6 +59,7 @@ script: cache: directories: - $HOME/.cabal + - $HOME/.ghc notifications: irc: From git at git.haskell.org Fri Oct 27 00:27:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename shakePath to hadrian. (d2051cd) Message-ID: <20171027002712.DBB5D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2051cdb91e00d19b02e7cab47e75411c1a29e33/ghc >--------------------------------------------------------------- commit d2051cdb91e00d19b02e7cab47e75411c1a29e33 Author: Andrey Mokhov Date: Wed Apr 27 00:59:24 2016 +0100 Rename shakePath to hadrian. [skip ci] >--------------------------------------------------------------- d2051cdb91e00d19b02e7cab47e75411c1a29e33 src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 871cd3c..b94648e 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -48,7 +48,7 @@ import System.IO -- Build system files and paths shakePath :: FilePath -shakePath = "shake-build" +shakePath = "hadrian" shakeFilesPath :: FilePath shakeFilesPath = shakePath -/- ".db" From git at git.haskell.org Fri Oct 27 00:27:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify needTouchy, drop old comments (47a1e7d) Message-ID: <20171027002716.A16CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47a1e7db3a6c815925389f1c7a7a69fd66ab1bea/ghc >--------------------------------------------------------------- commit 47a1e7db3a6c815925389f1c7a7a69fd66ab1bea Author: Andrey Mokhov Date: Sun Oct 30 23:33:07 2016 +0000 Simplify needTouchy, drop old comments >--------------------------------------------------------------- 47a1e7db3a6c815925389f1c7a7a69fd66ab1bea src/Settings/Builders/Ghc.hs | 97 ++------------------------------------------ 1 file changed, 3 insertions(+), 94 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 64fbacb..e12e35c 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -3,11 +3,6 @@ module Settings.Builders.Ghc (ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs) wh import Flavour import Settings.Builders.Common --- TODO: Add support for -dyno. --- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot --- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ --- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno --- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) ghcBuilderArgs :: Args ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do needTouchy @@ -38,15 +33,11 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] --- TODO: Add Touchy builder and use needBuilder. needTouchy :: ReaderT Target Action () -needTouchy = do - stage <- getStage - windows <- lift $ windowsHost - lift . when (stage > Stage0 && windows) $ - need [fromJust $ programPath (vanillaContext Stage0 touchy)] +needTouchy = notStage0 ? do + maybePath <- lift $ programPath (vanillaContext Stage0 touchy) + lift . whenJust maybePath $ \path -> need [path] --- TODO: Add GhcSplit builder and use needBuilder. splitObjectsArgs :: Args splitObjectsArgs = splitObjects flavour ? do lift $ need [ghcSplit] @@ -99,7 +90,6 @@ wayGhcArgs = do , (way == debug || way == debugDynamic) ? append ["-ticky", "-DTICKY_TICKY"] ] --- TODO: Improve handling of "-hide-all-packages". packageGhcArgs :: Args packageGhcArgs = do pkg <- getPackage @@ -131,84 +121,3 @@ includeGhcArgs = do , arg $ "-optc-I" ++ generatedPath , arg "-optP-include" , arg $ "-optP" ++ path -/- "autogen/cabal_macros.h" ] - --- # Options for passing to plain ld --- $1_$2_$3_ALL_LD_OPTS = \ --- $$(WAY_$3_LD_OPTS) \ --- $$($1_$2_DIST_LD_OPTS) \ --- $$($1_$2_$3_LD_OPTS) \ --- $$($1_$2_EXTRA_LD_OPTS) \ --- $$(EXTRA_LD_OPTS) - --- # Options for passing to GHC when we use it for linking --- $1_$2_$3_GHC_LD_OPTS = \ --- $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ --- $$($1_$2_$3_MOST_HC_OPTS) - --- TODO: add support for TargetElf and darwin --- ifeq "$3" "dyn" --- ifneq "$4" "0" --- ifeq "$$(TargetElf)" "YES" --- $1_$2_$3_GHC_LD_OPTS += \ --- -fno-use-rpaths \ --- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'$$$$ORIGIN/../$$d') -optl-Wl,-zorigin --- else ifeq "$$(TargetOS_CPP)" "darwin" --- $1_$2_$3_GHC_LD_OPTS += \ --- -fno-use-rpaths \ --- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') - --- ifeq "$$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS)" "" --- # We don't want to link the GHC RTS into C-only programs. There's no --- # point, and it confuses the test that all GHC-compiled programs --- # were compiled with the right GHC. --- $1_$2_$$($1_$2_PROGRAM_WAY)_GHC_LD_OPTS += -no-auto-link-packages -no-hs-main --- endif - --- # Link a dynamic library --- # On windows we have to supply the extra libs this one links to when building it. --- ifeq "$$(HostOS_CPP)" "mingw32" --- $$($1_$2_$3_LIB) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) --- ifneq "$$($1_$2_$3_LIB0)" "" --- $$(call build-dll,$1,$2,$3, --- -L$1/$2/build -l$$($1_$2_$3_LIB0_ROOT), --- $$(filter-out $$($1_$2_dll0_HS_OBJS),$$($1_$2_$3_HS_OBJS)) --- $$($1_$2_$3_NON_HS_OBJS),$$@) --- else --- $$(call build-dll,$1,$2,$3,,$$($1_$2_$3_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$@) --- endif - --- ifneq "$$($1_$2_$3_LIB0)" "" --- $$($1_$2_$3_LIB) : $$($1_$2_$3_LIB0) --- $$($1_$2_$3_LIB0) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) --- $$(call build-dll,$1,$2,$3,,$$($1_$2_dll0_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$($1_$2_$3_LIB0)) --- endif - - - --- # $1 = dir --- # $2 = distdir --- # $3 = way --- # $4 = extra flags --- # $5 = object files to link --- # $6 = output filename --- define build-dll --- $(call cmd,$1_$2_HC) $($1_$2_$3_ALL_HC_OPTS) $($1_$2_$3_GHC_LD_OPTS) $4 $5 \ --- -shared -dynamic -dynload deploy \ --- $(addprefix -l,$($1_$2_EXTRA_LIBRARIES)) \ --- -no-auto-link-packages \ --- -o $6 --- # Now check that the DLL doesn't have too many symbols. See trac #5987. --- SYMBOLS=`$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail -n +2 | wc -l`; echo "Number of symbols in $6: $$SYMBOLS" --- case `$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | grep "\[ *0\]" | wc -l` in 1) echo DLL $6 OK;; 0) echo No symbols in DLL $6; exit 1;; [0-9]*) echo Too many symbols in DLL $6; $(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail; exit 1;; *) echo bad DLL $6; exit 1;; esac --- endef - - - --- TODO: add -dynamic-too? --- # $1_$2_$3_ALL_HC_OPTS: this is all the options we will pass to GHC --- # for a given ($1,$2,$3). --- $1_$2_$3_ALL_HC_OPTS = \ --- -hisuf $$($3_hisuf) -osuf $$($3_osuf) -hcsuf $$($3_hcsuf) \ --- $$($1_$2_$3_MOST_DIR_HC_OPTS) \ --- $$(if $$(findstring YES,$$($1_$2_SplitObjs)),$$(if $$(findstring dyn,$3),,-split-objs),) \ --- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),$$(if $$(findstring v,$3),-dynamic-too)) From git at git.haskell.org Fri Oct 27 00:27:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename build directory (5f40553) Message-ID: <20171027002716.DBA6E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f405539ffaa3f453d244a53f86e9ee4ee0e8e6e/ghc >--------------------------------------------------------------- commit 5f405539ffaa3f453d244a53f86e9ee4ee0e8e6e Author: Andrey Mokhov Date: Thu Apr 28 23:43:28 2016 +0100 Rename build directory >--------------------------------------------------------------- 5f405539ffaa3f453d244a53f86e9ee4ee0e8e6e src/Settings/User.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index ef08df0..0893579 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -12,10 +12,9 @@ import Expression import Predicates import Settings.Default --- TODO: Rename to _build. -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath -buildRootPath = ".build" +buildRootPath = "_build" -- Control user-specific settings userArgs :: Args From git at git.haskell.org Fri Oct 27 00:27:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add IRC notifications (2e4f060) Message-ID: <20171027002717.D448A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2e4f060ee78c68726cb6434796d208075d4394a7/ghc >--------------------------------------------------------------- commit 2e4f060ee78c68726cb6434796d208075d4394a7 Author: David Luposchainsky Date: Tue Jan 5 16:07:39 2016 +0100 Add IRC notifications >--------------------------------------------------------------- 2e4f060ee78c68726cb6434796d208075d4394a7 .travis.yml | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/.travis.yml b/.travis.yml index 1bcd7fd..68e843c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,3 +59,15 @@ script: cache: directories: - $HOME/.cabal + +notifications: + irc: + on_success: always # always/never/change + on_failure: always + channels: + - "chat.freenode.net#shaking-up-ghc" + template: + - "#%{build_number} finished in %{duration}. %{message}" + - "Repo: %{repository_slug}, branch: %{branch}" + - "%{author}: %{commit_subject}" + - "Build details: %{build_url}" From git at git.haskell.org Fri Oct 27 00:27:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't build ghcPkg in Stage1 (bf83d95) Message-ID: <20171027002720.494523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf83d95c4770330e0b5ec582448ddc70ec9ebc92/ghc >--------------------------------------------------------------- commit bf83d95c4770330e0b5ec582448ddc70ec9ebc92 Author: Andrey Mokhov Date: Sun Oct 30 23:34:46 2016 +0000 Don't build ghcPkg in Stage1 >--------------------------------------------------------------- bf83d95c4770330e0b5ec582448ddc70ec9ebc92 src/Settings/Default.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index b59ceeb..c863a9e 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -101,7 +101,6 @@ stage1Packages = do , ghc , ghcCabal , ghci - , ghcPkg , ghcPrim , haskeline , hpcBin From git at git.haskell.org Fri Oct 27 00:27:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update CI links (5779105) Message-ID: <20171027002720.A50F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/577910572ec2a02cef51889666d9c40d4e961bf1/ghc >--------------------------------------------------------------- commit 577910572ec2a02cef51889666d9c40d4e961bf1 Author: Andrey Mokhov Date: Fri Apr 29 00:01:49 2016 +0100 Update CI links >--------------------------------------------------------------- 577910572ec2a02cef51889666d9c40d4e961bf1 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 375e4f8..d4adfb1 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Hadrian ======= -[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/hadrian/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/hadrian) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current From git at git.haskell.org Fri Oct 27 00:27:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #120 from quchen/irc-notifications (31fdc6b) Message-ID: <20171027002721.5D8783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31fdc6b713e90aa8a2b14ce7157bef811836028d/ghc >--------------------------------------------------------------- commit 31fdc6b713e90aa8a2b14ce7157bef811836028d Merge: 41ecfdc 9784dfb Author: Andrey Mokhov Date: Wed Jan 6 13:10:12 2016 +0000 Merge pull request #120 from quchen/irc-notifications Add IRC notifications >--------------------------------------------------------------- 31fdc6b713e90aa8a2b14ce7157bef811836028d .travis.yml | 13 +++++++++++++ 1 file changed, 13 insertions(+) From git at git.haskell.org Fri Oct 27 00:27:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor programPath (5d12adf) Message-ID: <20171027002723.C626F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d12adf142c16b5214fc01c8a1fab16c81544c89/ghc >--------------------------------------------------------------- commit 5d12adf142c16b5214fc01c8a1fab16c81544c89 Author: Andrey Mokhov Date: Sun Oct 30 23:37:10 2016 +0000 Refactor programPath >--------------------------------------------------------------- 5d12adf142c16b5214fc01c8a1fab16c81544c89 src/GHC.hs | 16 +++++++++-- src/Rules.hs | 8 +----- src/Rules/Generators/ConfigHs.hs | 1 - src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Program.hs | 37 +++++++++++++----------- src/Rules/Test.hs | 1 - src/Settings.hs | 42 ++++++++++++++++++++++----- src/Settings/Path.hs | 61 ++++++---------------------------------- src/Util.hs | 1 - 9 files changed, 79 insertions(+), 90 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 5d12adf142c16b5214fc01c8a1fab16c81544c89 From git at git.haskell.org Fri Oct 27 00:27:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Let's try the stupid --with-gcc fix for os x. (7d55b36) Message-ID: <20171027002724.C99F23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d55b36149cf7f5896d9920c8dbd53ac3a8a787d/ghc >--------------------------------------------------------------- commit 7d55b36149cf7f5896d9920c8dbd53ac3a8a787d Author: Moritz Angermann Date: Wed Jan 6 21:43:38 2016 +0800 Let's try the stupid --with-gcc fix for os x. See #111 >--------------------------------------------------------------- 7d55b36149cf7f5896d9920c8dbd53ac3a8a787d .travis.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 055edd5..e096ddf 100644 --- a/.travis.yml +++ b/.travis.yml @@ -51,7 +51,8 @@ install: - ( cd ghc/shake-build && cabal install --only-dependencies ) - ( cd ghc && ./boot ) - - ( cd ghc && ./configure ) + - if [ $TRAVIS_OS_NAME == osx ]; then ( cd ghc && ./configure --with-gcc="$(which clang)"); fi + - if [ $TRAVIS_OS_NAME == linux ]; then ( cd ghc && ./configure ); fi script: - ./ghc/shake-build/build.sh -j --no-progress From git at git.haskell.org Fri Oct 27 00:27:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build Hadrian in _build. (1317c88) Message-ID: <20171027002724.20DE33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1317c886fe1293c3d21389e85ee154790a710cbd/ghc >--------------------------------------------------------------- commit 1317c886fe1293c3d21389e85ee154790a710cbd Author: Andrey Mokhov Date: Sat Apr 30 02:40:55 2016 +0100 Build Hadrian in _build. >--------------------------------------------------------------- 1317c886fe1293c3d21389e85ee154790a710cbd build.bat | 38 +++++++++++++++++++------------------- build.sh | 32 ++++++++++++++++---------------- src/Base.hs | 1 + src/Rules/Clean.hs | 18 ++++++++++-------- 4 files changed, 46 insertions(+), 43 deletions(-) diff --git a/build.bat b/build.bat index 2f6d4cd..19a2a05 100644 --- a/build.bat +++ b/build.bat @@ -1,24 +1,24 @@ @cd %~dp0 - at mkdir .shake 2> nul + at mkdir ../_build 2> nul - at set ghcArgs=--make ^ - -Wall ^ - -fno-warn-name-shadowing ^ - -XRecordWildCards ^ - src/Main.hs ^ - -threaded ^ - -isrc ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=.shake ^ - -j ^ - -O ^ - -o .shake/build + at set ghcArgs=--make ^ + -Wall ^ + -fno-warn-name-shadowing ^ + -XRecordWildCards ^ + src/Main.hs ^ + -threaded ^ + -isrc ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=../_build/hadrian ^ + -j ^ + -O ^ + -o ../_build/hadrian - at set shakeArgs=--lint ^ - --directory ^ - ".." ^ - %* + at set hadrianArgs=--lint ^ + --directory ^ + ".." ^ + %* @ghc %ghcArgs% @@ -27,4 +27,4 @@ @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains @set GHC_PACKAGE_PATH= - at .shake\build %shakeArgs% + at ..\_build\hadrian %hadrianArgs% diff --git a/build.sh b/build.sh index 95de2e6..8b53f81 100755 --- a/build.sh +++ b/build.sh @@ -30,22 +30,22 @@ function rl { root="$(dirname "$(rl "$0")")" -mkdir -p "$root/.shake" - -ghc \ - "$root/src/Main.hs" \ - -Wall \ - -fno-warn-name-shadowing \ - -XRecordWildCards \ - -i"$root/src" \ - -rtsopts \ - -with-rtsopts=-I0 \ - -threaded \ - -outputdir="$root/.shake" \ - -j -O \ - -o "$root/.shake/build" - -"$root/.shake/build" \ +mkdir -p "$root/../_build" + +ghc \ + "$root/src/Main.hs" \ + -Wall \ + -fno-warn-name-shadowing \ + -XRecordWildCards \ + -i"$root/src" \ + -rtsopts \ + -with-rtsopts=-I0 \ + -threaded \ + -outputdir="$root/../_build/hadrian" \ + -j -O \ + -o "$root/../_build/hadrian" + +"$root/../_build/hadrian" \ --lint \ --directory "$root/.." \ --colour \ diff --git a/src/Base.hs b/src/Base.hs index b94648e..53bb197 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -50,6 +50,7 @@ import System.IO shakePath :: FilePath shakePath = "hadrian" +-- TODO: Move to buildRootPath. shakeFilesPath :: FilePath shakeFilesPath = shakePath -/- ".db" diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index ea1cc37..357ac34 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -9,17 +9,19 @@ import Settings.Paths import Settings.User import Stage +clean :: FilePath -> Action () +clean dir = do + putBuild $ "| Remove files in " ++ dir ++ "..." + removeDirectoryIfExists dir + cleanRules :: Rules () cleanRules = do "clean" ~> do - putBuild $ "| Remove files in " ++ buildRootPath ++ "..." - liftIO $ removeFiles buildRootPath ["//*"] - putBuild $ "| Remove files in " ++ programInplacePath ++ "..." - liftIO $ removeFiles programInplacePath ["//*"] - putBuild $ "| Remove files in inplace/lib..." - liftIO $ removeFiles "inplace/lib" ["//*"] - putBuild $ "| Remove files in " ++ derivedConstantsPath ++ "..." - liftIO $ removeFiles derivedConstantsPath ["//*"] + forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) + clean (buildRootPath -/- "hadrian") + clean programInplacePath + clean "inplace/lib" + clean derivedConstantsPath forM_ includesDependencies $ \file -> do putBuild $ "| Remove " ++ file removeFileIfExists file From git at git.haskell.org Fri Oct 27 00:27:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Appveyor CI. (f76a8be) Message-ID: <20171027002727.93EB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f76a8bea7b7b5d797880621af089f9ee22cc1035/ghc >--------------------------------------------------------------- commit f76a8bea7b7b5d797880621af089f9ee22cc1035 Author: Andrey Mokhov Date: Sat Apr 30 13:01:49 2016 +0100 Fix Appveyor CI. >--------------------------------------------------------------- f76a8bea7b7b5d797880621af089f9ee22cc1035 appveyor.yml | 3 +++ 1 file changed, 3 insertions(+) diff --git a/appveyor.yml b/appveyor.yml index 3918779..8850273 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -36,6 +36,9 @@ install: - alex --version - happy --version - stack exec -- ghc-pkg list + - mkdir _build + - cd _build + - mkdir hadrian build_script: - cd C:\msys64\home\ghc\hadrian From git at git.haskell.org Fri Oct 27 00:27:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move programInplacePath to Settings.Path (c5ba8b9) Message-ID: <20171027002727.99D113A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5ba8b94b6e04cf95392f8520ff649d2538530a2/ghc >--------------------------------------------------------------- commit c5ba8b94b6e04cf95392f8520ff649d2538530a2 Author: Andrey Mokhov Date: Sun Oct 30 23:45:21 2016 +0000 Move programInplacePath to Settings.Path >--------------------------------------------------------------- c5ba8b94b6e04cf95392f8520ff649d2538530a2 src/Base.hs | 6 +----- src/Settings/Path.hs | 8 ++++++-- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index cb040d4..eb8685d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -15,7 +15,7 @@ module Base ( module Development.Shake.FilePath, -- * Paths - configPath, configFile, sourcePath, programInplacePath, + configPath, configFile, sourcePath, -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, replaceSeparators, unifyPath, @@ -58,10 +58,6 @@ configFile = configPath -/- "system.config" sourcePath :: FilePath sourcePath = hadrianPath -/- "src" --- TODO: move to buildRootPath, see #113 -programInplacePath :: FilePath -programInplacePath = "inplace/bin" - -- | Find and replace all occurrences of a value in a list. replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceWhen (== from) diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 9993f9e..6b2e67d 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -3,7 +3,7 @@ module Settings.Path ( pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, - objectPath, programInplaceLibPath, installPath + objectPath, programInplacePath, programInplaceLibPath, installPath ) where import Base @@ -36,7 +36,11 @@ stageDirectory :: Stage -> FilePath stageDirectory = stageString -- TODO: Move to buildRootPath, see #113. --- | Directory for wrapped binaries. +-- | Directory for binaries that are built "in place". +programInplacePath :: FilePath +programInplacePath = "inplace/bin" + +-- | Directory for binary wrappers, and auxiliary binaries such as @touchy at . programInplaceLibPath :: FilePath programInplaceLibPath = "inplace/lib/bin" From git at git.haskell.org Fri Oct 27 00:27:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #121 from angerman/feature/fix-osx-ci (0fee526) Message-ID: <20171027002728.7AA093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0fee526aa68cff1b10d733ba4257fb3435276c66/ghc >--------------------------------------------------------------- commit 0fee526aa68cff1b10d733ba4257fb3435276c66 Merge: 31fdc6b 7d55b36 Author: Andrey Mokhov Date: Wed Jan 6 13:47:24 2016 +0000 Merge pull request #121 from angerman/feature/fix-osx-ci Let's try the stupid --with-gcc fix for os x. >--------------------------------------------------------------- 0fee526aa68cff1b10d733ba4257fb3435276c66 .travis.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:27:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Travis CI. (a37ad75) Message-ID: <20171027002731.807BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a37ad7507e8fef44d94e7e339c521e272bcdaa7e/ghc >--------------------------------------------------------------- commit a37ad7507e8fef44d94e7e339c521e272bcdaa7e Author: Andrey Mokhov Date: Sat Apr 30 13:03:56 2016 +0100 Fix Travis CI. >--------------------------------------------------------------- a37ad7507e8fef44d94e7e339c521e272bcdaa7e .travis.yml | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.travis.yml b/.travis.yml index 6832cd8..251f6ba 100644 --- a/.travis.yml +++ b/.travis.yml @@ -48,6 +48,8 @@ install: # ".git" directory into the appropriate location, and perform a hard reset # in order to regenerate the GHC-Shake files. - mkdir ghc/hadrian + - mkdir ghc/_build + - mkdir ghc/_build/hadrian - mv .git ghc/hadrian - ( cd ghc/hadrian && git reset --hard HEAD ) From git at git.haskell.org Fri Oct 27 00:27:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix buildProgram (7b00fa7) Message-ID: <20171027002731.97C253A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b00fa7081555a5753c90ba8b48d2579cc59be9c/ghc >--------------------------------------------------------------- commit 7b00fa7081555a5753c90ba8b48d2579cc59be9c Author: Andrey Mokhov Date: Sun Oct 30 23:57:13 2016 +0000 Fix buildProgram >--------------------------------------------------------------- 7b00fa7081555a5753c90ba8b48d2579cc59be9c src/Rules/Program.hs | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 98922a5..319ca72 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -29,15 +29,23 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do + let installStage = do + latest <- latestBuildStage package -- isJust below is safe + return $ if package == ghc then stage else fromJust latest + buildPath context -/- programName context <.> exe %> buildBinaryAndWrapper rs context -- Rules for programs built in install directories - when (stage == Stage0 || package == ghc) $ - installPath package -/- programName context <.> exe %> \bin -> do - latest <- latestBuildStage package -- isJust below is safe - let binStage = if package == ghc then stage else fromJust latest + when (stage == Stage0 || package == ghc) $ do + -- Some binaries in programInplacePath are wrapped + programInplacePath -/- programName context <.> exe %> \bin -> do + binStage <- installStage buildBinaryAndWrapper rs (context { stage = binStage }) bin + -- We build only unwrapped binaries in programInplaceLibPath + programInplaceLibPath -/- programName context <.> exe %> \bin -> do + binStage <- installStage + buildBinary rs (context { stage = binStage }) bin buildBinaryAndWrapper :: [(Resource, Int)] -> Context -> FilePath -> Action () buildBinaryAndWrapper rs context bin = do From git at git.haskell.org Fri Oct 27 00:27:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Lookup builder in PATH if they are given without path. (4478851) Message-ID: <20171027002732.540143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44788518cb14c59788fdf320b9ca2d11e11509ca/ghc >--------------------------------------------------------------- commit 44788518cb14c59788fdf320b9ca2d11e11509ca Author: Moritz Angermann Date: Wed Jan 6 23:22:43 2016 +0800 Lookup builder in PATH if they are given without path. `system-gcc` may be given without path (e.g. `clang`), this patch adds lookup using `which` for those commands. Also drops calling `fixAbsolutePathOnWindows` on non window hosts. Fixes #26 >--------------------------------------------------------------- 44788518cb14c59788fdf320b9ca2d11e11509ca src/Builder.hs | 4 +++- src/Oracles/WindowsRoot.hs | 11 ++++++++++- 2 files changed, 13 insertions(+), 2 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 5ed9e1d..6e4dba5 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -94,7 +94,9 @@ builderPath builder = do path <- askConfigWithDefault (builderKey builder) $ putError $ "\nCannot find path to '" ++ (builderKey builder) ++ "' in configuration files." - fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe + windows <- windowsHost + let path' = if null path then "" else path -<.> exe in + (if windows then fixAbsolutePathOnWindows else lookupInPath) path' getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 413f289..195f591 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.WindowsRoot ( - windowsRoot, fixAbsolutePathOnWindows, topDirectory, windowsRootOracle + windowsRoot, fixAbsolutePathOnWindows, lookupInPath, topDirectory, windowsRootOracle ) where import Data.Char (isSpace) @@ -38,6 +38,15 @@ fixAbsolutePathOnWindows path = do else return path +-- | Lookup a @command@ in @PATH@ environment. +lookupInPath :: FilePath -> Action FilePath +lookupInPath command + | command /= takeFileName command = return command + | otherwise = do + Stdout out <- quietly $ cmd ["which", command] + let path = dropWhileEnd isSpace out + return path + -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). windowsRootOracle :: Rules () From git at git.haskell.org Fri Oct 27 00:27:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (d9b059b) Message-ID: <20171027002735.C918E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9b059b3471b2a897b4b0fe8370a6340011310b6/ghc >--------------------------------------------------------------- commit d9b059b3471b2a897b4b0fe8370a6340011310b6 Author: Andrey Mokhov Date: Mon Oct 31 18:25:18 2016 +0000 Minor revision >--------------------------------------------------------------- d9b059b3471b2a897b4b0fe8370a6340011310b6 hadrian.cabal | 2 +- .../{DirectoryContent.hs => DirectoryContents.hs} | 19 +++++++++-------- src/Rules/Oracles.hs | 4 ++-- src/Rules/SourceDist.hs | 4 ++-- src/Util.hs | 24 ++++++++++------------ 5 files changed, 26 insertions(+), 27 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index b20b17d..0663643 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -31,7 +31,7 @@ executable hadrian , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies - , Oracles.DirectoryContent + , Oracles.DirectoryContents , Oracles.ModuleFiles , Oracles.PackageData , Oracles.Path diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContents.hs similarity index 53% rename from src/Oracles/DirectoryContent.hs rename to src/Oracles/DirectoryContents.hs index 3139c6c..6dd3439 100644 --- a/src/Oracles/DirectoryContent.hs +++ b/src/Oracles/DirectoryContents.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} -module Oracles.DirectoryContent ( - directoryContent, directoryContentOracle, Match (..) +module Oracles.DirectoryContents ( + directoryContents, directoryContentsOracle, Match (..) ) where import System.Directory.Extra @@ -8,7 +8,7 @@ import GHC.Generics import Base -newtype DirectoryContent = DirectoryContent (Match, FilePath) +newtype DirectoryContents = DirectoryContents (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) data Match = Test FilePattern | Not Match | And [Match] | Or [Match] @@ -20,13 +20,14 @@ matches (Not m) f = not $ matches m f matches (And ms) f = all (`matches` f) ms matches (Or ms) f = any (`matches` f) ms --- | Get the directory content recursively. -directoryContent :: Match -> FilePath -> Action [FilePath] -directoryContent expr dir = askOracle $ DirectoryContent (expr, dir) +-- | Given a 'Match' expression and a directory, recursively traverse it and all +-- its subdirectories to find and return all matching contents. +directoryContents :: Match -> FilePath -> Action [FilePath] +directoryContents expr dir = askOracle $ DirectoryContents (expr, dir) -directoryContentOracle :: Rules () -directoryContentOracle = void $ - addOracle $ \(DirectoryContent (expr, dir)) -> liftIO $ +directoryContentsOracle :: Rules () +directoryContentsOracle = void $ + addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ filter (matches expr) <$> listFilesInside (return . matches expr) dir instance Binary Match diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 6c5ace4..8f53369 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -4,7 +4,7 @@ import Base import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies -import qualified Oracles.DirectoryContent +import qualified Oracles.DirectoryContents import qualified Oracles.ModuleFiles import qualified Oracles.PackageData import qualified Oracles.Path @@ -14,7 +14,7 @@ oracleRules = do Oracles.ArgsHash.argsHashOracle Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles - Oracles.DirectoryContent.directoryContentOracle + Oracles.DirectoryContents.directoryContentsOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle Oracles.Path.pathOracle diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index 9c49878..d51fe75 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -3,7 +3,7 @@ module Rules.SourceDist (sourceDistRules) where import Base import Builder import Oracles.Config.Setting -import Oracles.DirectoryContent +import Oracles.DirectoryContents import UserSettings import Util @@ -32,7 +32,7 @@ prepareTree dest = do mapM_ cpFile srcFiles where cpFile a = copyFile a (dest a) - cpDir a = copyDirectoryContent (Not excluded) a (dest takeFileName a) + cpDir a = copyDirectoryContents (Not excluded) a (dest takeFileName a) excluded = Or [ Test "//.*" , Test "//#*" diff --git a/src/Util.hs b/src/Util.hs index dbafd85..f2e6516 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,6 @@ module Util ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, - removeFile, copyDirectory, copyDirectoryContent, createDirectory, + removeFile, copyDirectory, copyDirectoryContents, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, makeExecutable, renderProgram, renderLibrary, Match(..), builderEnvironment, needBuilder @@ -16,7 +16,7 @@ import Context import Expression import GHC import Oracles.ArgsHash -import Oracles.DirectoryContent +import Oracles.DirectoryContents import Oracles.Path import Settings import Settings.Builders.Ar @@ -96,6 +96,8 @@ captureStdout target path argList = do copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. + let dir = takeDirectory target + unlessM (liftIO $ IO.doesDirectoryExist dir) $ createDirectory dir putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target @@ -129,17 +131,13 @@ copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd cmdEcho ["cp", "-r", source, target] --- | Copy the content of the source directory into the target directory. --- The copied content is tracked. -copyDirectoryContent :: Match -> FilePath -> FilePath -> Action () -copyDirectoryContent expr source target = do - putProgressInfo $ renderAction "Copy directory content" source target - mapM_ cp =<< directoryContent expr source - where - cp file = do - let newFile = target -/- drop (length source) file - createDirectory $ dropFileName newFile -- TODO: Why do it for each file? - copyFile file newFile +-- | Copy the contents of the source directory that matches a given 'Match' +-- expression into the target directory. The copied contents is tracked. +copyDirectoryContents :: Match -> FilePath -> FilePath -> Action () +copyDirectoryContents expr source target = do + putProgressInfo $ renderAction "Copy directory contents" source target + let cp file = copyFile file $ target -/- makeRelative source file + mapM_ cp =<< directoryContents expr source -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:28:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move gmp library instead of copying it. Add moveFile. (de4f7bc) Message-ID: <20171027002801.CFB153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de4f7bcc27596946d26f708782f74a6266706842/ghc >--------------------------------------------------------------- commit de4f7bcc27596946d26f708782f74a6266706842 Author: Andrey Mokhov Date: Mon May 2 03:59:52 2016 +0100 Move gmp library instead of copying it. Add moveFile. See #163. >--------------------------------------------------------------- de4f7bcc27596946d26f708782f74a6266706842 src/Rules/Actions.hs | 13 ++++++++++--- src/Rules/Gmp.hs | 3 +-- 2 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index f006947..edf98eb 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,7 +1,8 @@ module Rules.Actions ( - build, buildWithResources, buildWithCmdOptions, copyFile, createDirectory, - removeDirectory, copyDirectory, moveDirectory, applyPatch, fixFile, runMake, - runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable + build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, + createDirectory, removeDirectory, copyDirectory, moveDirectory, + applyPatch, fixFile, runMake, runMakeVerbose, renderLibrary, renderProgram, + runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -87,6 +88,12 @@ copyFile source target = do putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target +-- Note, moveFile cannot track the source, because it is moved. +moveFile :: FilePath -> FilePath -> Action () +moveFile source target = do + putProgressInfo $ renderAction "Move file" source target + liftIO $ IO.renameFile source target + createDirectory :: FilePath -> Action () createDirectory dir = do putBuild $ "| Create directory " ++ dir diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index e2502dd..1e962ec 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -103,8 +103,7 @@ gmpRules = do copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH copyFile (libPath -/- "gmp.h") gmpLibraryH - -- TODO: why copy library, can we move it instead? - copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary + moveFile (libPath -/- ".libs/libgmp.a") gmpLibrary createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] From git at git.haskell.org Fri Oct 27 00:28:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build dependencies for all known packages that exist (95ee1ab) Message-ID: <20171027002802.2CE4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95ee1ab41659c3e6f4d64455faed96aebaeb0cbf/ghc >--------------------------------------------------------------- commit 95ee1ab41659c3e6f4d64455faed96aebaeb0cbf Author: Andrey Mokhov Date: Tue Nov 1 21:30:15 2016 +0000 Build dependencies for all known packages that exist >--------------------------------------------------------------- 95ee1ab41659c3e6f4d64455faed96aebaeb0cbf src/Rules/Cabal.hs | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index b2bd630..370bda2 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -11,6 +11,7 @@ import Expression import GHC import Settings import Settings.Path +import UserSettings cabalRules :: Rules () cabalRules = do @@ -25,13 +26,13 @@ cabalRules = do version = display . pkgVersion $ identifier return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version writeFileChanged out . unlines $ constraints + putSuccess $ "| Successfully computed boot package constraints" -- Cache package dependencies. packageDependencies %> \out -> do - pkgs <- concatMapM stagePackages [Stage0 .. Stage2] - pkgDeps <- forM (sort pkgs) $ \pkg -> - if pkg `elem` [hp2ps, libffi, rts, touchy, unlit] - then return $ pkgNameString pkg + pkgDeps <- forM (sort knownPackages) $ \pkg -> do + exists <- doesFileExist $ pkgCabalFile pkg + if not exists then return $ pkgNameString pkg else do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg @@ -40,7 +41,8 @@ cabalRules = do deps = concat $ depsLib : depsExes depNames = [ unPackageName name | Dependency name _ <- deps ] return . unwords $ pkgNameString pkg : sort depNames - writeFileChanged out . unlines $ pkgDeps + writeFileChanged out $ unlines pkgDeps + putSuccess $ "| Successfully computed package dependencies" collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] From git at git.haskell.org Fri Oct 27 00:28:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename cabal, add build script. (da29ac9) Message-ID: <20171027002804.730123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da29ac914723944acd7c65709fa93c0dce198571/ghc >--------------------------------------------------------------- commit da29ac914723944acd7c65709fa93c0dce198571 Author: Andrey Mokhov Date: Wed Jan 6 19:21:43 2016 +0000 Rename cabal, add build script. See #110. [skip ci] >--------------------------------------------------------------- da29ac914723944acd7c65709fa93c0dce198571 .appveyor.yml | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index fa03afe..93375e0 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,10 +8,14 @@ install: - bash -lc "mkdir /usr/local" - bash -lc "mkdir /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + - ren C:\msys64\usr\local\bin\cabal-1.22.0.0-i386-unknown-mingw32.exe C:\msys64\usr\local\bin\cabal.exe - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" + - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" build_script: - - echo "test" + - bash -lc "cd /home/ghc && ./boot" + - bash -lc "cd /home/ghc && ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && ./shake-build/build.bat" test: off From git at git.haskell.org Fri Oct 27 00:28:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of git://github.com/snowleopard/hadrian (2674950) Message-ID: <20171027002806.082ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2674950daed5ab709cd3e5bab576b6343805d2e0/ghc >--------------------------------------------------------------- commit 2674950daed5ab709cd3e5bab576b6343805d2e0 Merge: de4f7bc 759dff3 Author: Andrey Mokhov Date: Mon May 2 04:00:12 2016 +0100 Merge branch 'master' of git://github.com/snowleopard/hadrian >--------------------------------------------------------------- 2674950daed5ab709cd3e5bab576b6343805d2e0 appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Oct 27 00:28:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision, don't copy Hadrian binaries (6d420eb) Message-ID: <20171027002806.4EE0B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d420eb40cf4ebe18c4b556b0449972b6500eeb2/ghc >--------------------------------------------------------------- commit 6d420eb40cf4ebe18c4b556b0449972b6500eeb2 Author: Andrey Mokhov Date: Wed Nov 2 01:55:16 2016 +0000 Minor revision, don't copy Hadrian binaries >--------------------------------------------------------------- 6d420eb40cf4ebe18c4b556b0449972b6500eeb2 src/Rules/SourceDist.hs | 156 +++++++++++++++++++++++++----------------------- 1 file changed, 80 insertions(+), 76 deletions(-) diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index d56eb38..7a60238 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -12,18 +12,18 @@ sourceDistRules = do "sdist-ghc" ~> do version <- setting ProjectVersion need ["sdistprep/ghc-" ++ version ++ "-src.tar.xz"] - putSuccess "| Done. " + putSuccess "| Done" "sdistprep/ghc-*-src.tar.xz" %> \fname -> do - let tarName = takeFileName fname - treePath = "sdistprep/ghc" -/- dropTarXz tarName + let tarName = takeFileName fname + dropTarXz = dropExtension . dropExtension + treePath = "sdistprep/ghc" -/- dropTarXz tarName prepareTree treePath - runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." -/- tarName, dropTarXz tarName] + runBuilderWith [Cwd "sdistprep/ghc"] Tar + ["cJf", ".." -/- tarName, dropTarXz tarName] "GIT_COMMIT_ID" %> \fname -> - setting ProjectGitCommitId >>= writeFileChanged fname + writeFileChanged fname =<< setting ProjectGitCommitId "VERSION" %> \fname -> - setting ProjectVersion >>= writeFileChanged fname - where - dropTarXz = dropExtension . dropExtension + writeFileChanged fname =<< setting ProjectVersion prepareTree :: FilePath -> Action () prepareTree dest = do @@ -31,74 +31,78 @@ prepareTree dest = do mapM_ cpFile srcFiles where cpFile a = copyFile a (dest -/- a) - cpDir a = copyDirectoryContents (Not excluded) a (dest -/- takeFileName a) + cpDir a = copyDirectoryContents (Not excluded) a (dest -/- a) excluded = Or - [ Test "//.*" - , Test "//#*" - , Test "//*-SAVE" - , Test "//*.orig" - , Test "//*.rej" - , Test "//*~" - , Test "//autom4te*" - , Test "//dist" - , Test "//log" - , Test "//stage0" - , Test "//stage1" - , Test "//stage2" - , Test "//stage3" - , Test "hadrian/cabal.sandbox.config" - , Test "hadrian/cfg/system.config" - , Test "hadrian/dist" - , Test "hadrian/UserSettings.hs" - , Test "libraries//*.buildinfo" - , Test "libraries//GNUmakefile" - , Test "libraries//config.log" - , Test "libraries//config.status" - , Test "libraries//configure" - , Test "libraries//ghc.mk" - , Test "libraries//include/Hs*Config.h" - , Test "libraries/dph" - , Test "libraries/parallel" - , Test "libraries/primitive" - , Test "libraries/random" - , Test "libraries/stm" - , Test "libraries/vector" - , Test "mk/build.mk" ] + [ Test "//.*" + , Test "//#*" + , Test "//*-SAVE" + , Test "//*.orig" + , Test "//*.rej" + , Test "//*~" + , Test "//autom4te*" + , Test "//dist" + , Test "//log" + , Test "//stage0" + , Test "//stage1" + , Test "//stage2" + , Test "//stage3" + , Test "hadrian/.cabal-sandbox" + , Test "hadrian/.stack-work" + , Test "hadrian/UserSettings.hs" + , Test "hadrian/cabal.sandbox.config" + , Test "hadrian/cfg/system.config" + , Test "hadrian/bin" + , Test "hadrian/dist" + , Test "hadrian/dist-newstyle" + , Test "libraries//*.buildinfo" + , Test "libraries//GNUmakefile" + , Test "libraries//config.log" + , Test "libraries//config.status" + , Test "libraries//configure" + , Test "libraries//ghc.mk" + , Test "libraries//include/Hs*Config.h" + , Test "libraries/dph" + , Test "libraries/parallel" + , Test "libraries/primitive" + , Test "libraries/random" + , Test "libraries/stm" + , Test "libraries/vector" + , Test "mk/build.mk" ] srcDirs = - [ "bindisttest" - , "compiler" - , "distrib" - , "docs" - , "docs" - , "driver" - , "ghc" - , "hadrian" - , "includes" - , "iserv" - , "libffi" - , "libffi-tarballs" - , "libraries" - , "mk" - , "rts" - , "rules" - , "utils" ] + [ "bindisttest" + , "compiler" + , "distrib" + , "docs" + , "docs" + , "driver" + , "ghc" + , "hadrian" + , "includes" + , "iserv" + , "libffi" + , "libffi-tarballs" + , "libraries" + , "mk" + , "rts" + , "rules" + , "utils" ] srcFiles = - [ "ANNOUNCE" - , "GIT_COMMIT_ID" - , "HACKING.md" - , "INSTALL.md" - , "LICENSE" - , "MAKEHELP.md" - , "Makefile" - , "README.md" - , "VERSION" - , "aclocal.m4" - , "boot" - , "config.guess" - , "config.sub" - , "configure" - , "configure.ac" - , "ghc.mk" - , "install-sh" - , "packages" - , "settings.in" ] + [ "ANNOUNCE" + , "GIT_COMMIT_ID" + , "HACKING.md" + , "INSTALL.md" + , "LICENSE" + , "MAKEHELP.md" + , "Makefile" + , "README.md" + , "VERSION" + , "aclocal.m4" + , "boot" + , "config.guess" + , "config.sub" + , "configure" + , "configure.ac" + , "ghc.mk" + , "install-sh" + , "packages" + , "settings.in" ] From git at git.haskell.org Fri Oct 27 00:28:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install project dependencies, pass -j --no-progress to build.bat (5afac8a) Message-ID: <20171027002808.26D253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5afac8aceaa4a656231fbd03b61a03a38327ee78/ghc >--------------------------------------------------------------- commit 5afac8aceaa4a656231fbd03b61a03a38327ee78 Author: Andrey Mokhov Date: Wed Jan 6 19:35:18 2016 +0000 Install project dependencies, pass -j --no-progress to build.bat See #110. [skip ci] >--------------------------------------------------------------- 5afac8aceaa4a656231fbd03b61a03a38327ee78 .appveyor.yml | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 93375e0..47210eb 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -12,10 +12,9 @@ install: - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" + - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" - bash -lc "cd /home/ghc && ./configure --enable-tarballs-autodownload" - - bash -lc "cd /home/ghc && ./shake-build/build.bat" - -test: off + - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:28:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run configure via stack exec. (d842e0f) Message-ID: <20171027002810.5FCAB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d842e0f8e336d17a017c94c1d70d9d66a58a3a22/ghc >--------------------------------------------------------------- commit d842e0f8e336d17a017c94c1d70d9d66a58a3a22 Author: Andrey Mokhov Date: Mon May 2 04:10:18 2016 +0100 Run configure via stack exec. >--------------------------------------------------------------- d842e0f8e336d17a017c94c1d70d9d66a58a3a22 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 76ccbe1..7b2e53b 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -34,7 +34,7 @@ install: - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/94c88da1c738815f2986439a956d93fdbc707237/ghc >--------------------------------------------------------------- commit 94c88da1c738815f2986439a956d93fdbc707237 Author: Andrey Mokhov Date: Sat Nov 26 23:38:35 2016 +0000 Don't generate in-tree directories by ghc-cabal See #113 >--------------------------------------------------------------- 94c88da1c738815f2986439a956d93fdbc707237 src/Oracles/ModuleFiles.hs | 5 ++-- src/Oracles/PackageData.hs | 6 ++--- src/Rules/Data.hs | 57 +++++++++------------------------------ src/Rules/Register.hs | 18 +++++-------- src/Settings/Builders/Common.hs | 1 - src/Settings/Builders/Ghc.hs | 5 ++-- src/Settings/Builders/GhcCabal.hs | 4 ++- src/Settings/Builders/GhcPkg.hs | 6 ++--- src/Settings/Builders/Hsc2Hs.hs | 4 +-- src/Settings/Packages/GhcCabal.hs | 6 ++--- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Packages/Touchy.hs | 2 +- src/Settings/Packages/Unlit.hs | 2 +- src/Settings/Path.hs | 18 ++++++++++--- 14 files changed, 56 insertions(+), 80 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 94c88da1c738815f2986439a956d93fdbc707237 From git at git.haskell.org Fri Oct 27 00:28:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix cabal rename error. (e008f71) Message-ID: <20171027002811.B51283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e008f71950c8197157e3da6274b12d410bce81f9/ghc >--------------------------------------------------------------- commit e008f71950c8197157e3da6274b12d410bce81f9 Author: Andrey Mokhov Date: Wed Jan 6 20:30:11 2016 +0000 Fix cabal rename error. See #110. [skip ci] >--------------------------------------------------------------- e008f71950c8197157e3da6274b12d410bce81f9 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 47210eb..8bb6c15 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,7 +8,7 @@ install: - bash -lc "mkdir /usr/local" - bash -lc "mkdir /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - - ren C:\msys64\usr\local\bin\cabal-1.22.0.0-i386-unknown-mingw32.exe C:\msys64\usr\local\bin\cabal.exe + - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" From git at git.haskell.org Fri Oct 27 00:28:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix Appveyor failure (b8dda5c) Message-ID: <20171027002814.03D393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b8dda5c646545ea11c18c70a3f657871b870d1ec/ghc >--------------------------------------------------------------- commit b8dda5c646545ea11c18c70a3f657871b870d1ec Author: Andrey Mokhov Date: Mon May 2 12:28:32 2016 +0100 Attempt to fix Appveyor failure >--------------------------------------------------------------- b8dda5c646545ea11c18c70a3f657871b870d1ec appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 7b2e53b..459cecd 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -34,7 +34,7 @@ install: - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - echo "" | stack --no-terminal exec -- bash "configure --enable-tarballs-autodownload" + - echo "" | stack --no-terminal exec -- bash -lc "cd /home/ghc; configure --enable-tarballs-autodownload" - bash -lc "cat /home/ghc/hadrian/cfg/system.config" build_script: From git at git.haskell.org Fri Oct 27 00:28:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant clean up after ghc-cabal (e93f7a4) Message-ID: <20171027002814.6836C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e93f7a4181308147b3d2c9211eb6d63e51cea188/ghc >--------------------------------------------------------------- commit e93f7a4181308147b3d2c9211eb6d63e51cea188 Author: Andrey Mokhov Date: Sun Nov 27 00:32:02 2016 +0000 Drop redundant clean up after ghc-cabal See #113 >--------------------------------------------------------------- e93f7a4181308147b3d2c9211eb6d63e51cea188 src/Rules/Clean.hs | 6 ------ 1 file changed, 6 deletions(-) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index eebb26d..a2cf849 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -1,8 +1,6 @@ module Rules.Clean (cleanRules) where import Base -import Package -import Settings import Settings.Path import Stage import UserSettings @@ -16,10 +14,6 @@ cleanRules = do removeDirectory programInplacePath removeDirectory "inplace/lib" removeDirectory "sdistprep" - putBuild $ "| Remove files generated by ghc-cabal..." - forM_ knownPackages $ \pkg -> - forM_ [Stage0 ..] $ \stage -> - quietly . removeDirectory $ pkgPath pkg -/- stageDirectory stage putBuild $ "| Remove Hadrian files..." removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " From git at git.haskell.org Fri Oct 27 00:28:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change cabal config path and cache it. (a4447be) Message-ID: <20171027002815.3A30F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a4447bef24be3eebef8413d27f34aec113d73b4f/ghc >--------------------------------------------------------------- commit a4447bef24be3eebef8413d27f34aec113d73b4f Author: Andrey Mokhov Date: Wed Jan 6 22:07:41 2016 +0000 Change cabal config path and cache it. See #110. [skip ci] >--------------------------------------------------------------- a4447bef24be3eebef8413d27f34aec113d73b4f .appveyor.yml | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 8bb6c15..f70a821 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,5 +1,8 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" +cache: + - "C:\\msys64\home\cabal" + install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% @@ -9,10 +12,10 @@ install: - bash -lc "mkdir /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal update" - - bash -lc "cabal install -j --prefix=/usr/local alex happy" + - bash -lc "cabal --config-file=/home/cabal update" + - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:28:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add PATH to happy. (70fd668) Message-ID: <20171027002817.AA3313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/70fd668dc76660a348e732f370f8cf816a08f0fa/ghc >--------------------------------------------------------------- commit 70fd668dc76660a348e732f370f8cf816a08f0fa Author: Andrey Mokhov Date: Mon May 2 13:33:45 2016 +0100 Add PATH to happy. >--------------------------------------------------------------- 70fd668dc76660a348e732f370f8cf816a08f0fa appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 459cecd..16a1277 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -34,7 +34,7 @@ install: - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - echo "" | stack --no-terminal exec -- bash -lc "cd /home/ghc; configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3b5f08db5ea710b36a696e38f10263c955b86eb/ghc >--------------------------------------------------------------- commit e3b5f08db5ea710b36a696e38f10263c955b86eb Author: Andrey Mokhov Date: Sun Nov 27 01:01:03 2016 +0000 Put RTS's package configuration into inplace-pkg-config for consistency >--------------------------------------------------------------- e3b5f08db5ea710b36a696e38f10263c955b86eb src/Rules/Register.hs | 4 ++-- src/Settings/Builders/GhcPkg.hs | 3 +-- src/Settings/Packages/Rts.hs | 6 +----- src/Settings/Path.hs | 6 +++++- 4 files changed, 9 insertions(+), 10 deletions(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index f912b20..b7e12d1 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -22,10 +22,10 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do -- This produces inplace-pkg-config. TODO: Add explicit tracking. need [pkgDataFile context] - -- Post-process inplace-pkg-config. TODO: remove, see #113, #148. + -- Post-process inplace-pkg-config. top <- topDirectory let path = buildPath context - pkgConfig = path -/- "inplace-pkg-config" + pkgConfig = inplacePkgConfig context oldPath = top -/- path "build" fixFile pkgConfig $ unlines . map (replace oldPath path) . lines diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index b17f36a..5156d71 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -13,10 +13,9 @@ initArgs = initPredicate ? mconcat [ arg "init", arg =<< getOutput ] updateArgs :: Args updateArgs = notM initPredicate ? do - path <- getBuildPath verbosity <- lift $ getVerbosity mconcat [ arg "update" , arg "--force" , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs - , arg $ path -/- "inplace-pkg-config" ] + , arg . inplacePkgConfig =<< getContext ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 4c3cc99..40b85e4 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -18,7 +18,7 @@ rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" rtsConf :: FilePath -rtsConf = buildPath rtsContext -/- "package.conf.inplace" +rtsConf = inplacePkgConfig rtsContext rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do @@ -96,10 +96,6 @@ rtsPackageArgs = package rts ? do , builder Ghc ? arg "-Irts" - , builder (GhcPkg Stage1) ? mconcat - [ remove [path -/- "inplace-pkg-config"] - , arg rtsConf ] - , builder HsCpp ? append [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 0a22077..cbe1612 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -4,7 +4,7 @@ module Settings.Path ( gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath + installPath, autogenPath, inplacePkgConfig ) where import Base @@ -60,6 +60,10 @@ autogenPath context at Context {..} where autogen dir = buildPath context -/- dir -/- "autogen" +-- | Path to inplace package configuration of a given 'Context'. +inplacePkgConfig :: Context -> FilePath +inplacePkgConfig context = buildPath context -/- "inplace-pkg-config" + -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath pkgDataFile context = buildPath context -/- "package-data.mk" From git at git.haskell.org Fri Oct 27 00:28:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of partial functions. (a7adf8c) Message-ID: <20171027002842.C09F43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7adf8c5b2719aed8c17b029a74ebc190360df28/ghc >--------------------------------------------------------------- commit a7adf8c5b2719aed8c17b029a74ebc190360df28 Author: Andrey Mokhov Date: Thu May 5 03:13:49 2016 +0100 Get rid of partial functions. >--------------------------------------------------------------- a7adf8c5b2719aed8c17b029a74ebc190360df28 src/Rules/Gmp.hs | 23 +++++++++++------------ 1 file changed, 11 insertions(+), 12 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index cceda8e..d98bc3b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -71,14 +71,15 @@ gmpRules = do -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] - when (length tarballs /= 1) $ - putError $ "gmpRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." + tarball <- case tarballs of + [file] -> return $ unifyPath file + _ -> putError $ "gmpRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." - need tarballs withTempDir $ \dir -> do let tmp = unifyPath dir - build $ Target gmpContext Tar tarballs [tmp] + need [tarball] + build $ Target gmpContext Tar [tarball] [tmp] forM_ gmpPatches $ \src -> do let patch = takeFileName src @@ -86,13 +87,11 @@ gmpRules = do copyFile src patchPath applyPatch tmp patch - let filename = dropExtension . dropExtension . takeFileName - $ head tarballs - suffix = "-nodoc-patched" - unless (suffix `isSuffixOf` filename) $ - putError $ "gmpRules: expected suffix " ++ suffix - ++ " (found: " ++ filename ++ ")." - let libName = take (length filename - length suffix) filename + let name = dropExtension . dropExtension $ takeFileName tarball + libName <- case stripSuffix "-nodoc-patched" name of + Just rest -> return rest + Nothing -> putError $ "gmpRules: expected suffix " + ++ "-nodoc-patched (found: " ++ name ++ ")." moveDirectory (tmp -/- libName) gmpBuildPath From git at git.haskell.org Fri Oct 27 00:28:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to use stack instead of cabal. (d314d4f) Message-ID: <20171027002846.07F163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d314d4f902566fe3cd14e6426ba985226f1df49e/ghc >--------------------------------------------------------------- commit d314d4f902566fe3cd14e6426ba985226f1df49e Author: Andrey Mokhov Date: Thu Jan 7 01:34:53 2016 +0000 Try to use stack instead of cabal. See #110. [skip ci] >--------------------------------------------------------------- d314d4f902566fe3cd14e6426ba985226f1df49e .appveyor.yml | 17 +++++------------ 1 file changed, 5 insertions(+), 12 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 4d54924..7410a5e 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,24 +1,17 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -# cache: -# - "C:\\msys64\\home\\cabal" - install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" + - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 + - 7z x stack.zip stack.exe + - stack exec -- pacman -S --noconfirm gcc binutils p7zip git + - stack install -v3 -j --prefix=/usr/local alex happy - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /usr/local" - - bash -lc "mkdir -p /usr/local/bin" - # - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - # - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.20.0.3/cabal-1.20.0.3-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - - bash -lc "cabal update -v3" - - bash -lc "cabal install -j --prefix=/usr/local alex happy" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build - - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" + - stack install --only-dependencies build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:28:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop old TODOs (92b5c35) Message-ID: <20171027002845.5B4003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92b5c3507f296b1676cb7711c09d3e78ec2dfbef/ghc >--------------------------------------------------------------- commit 92b5c3507f296b1676cb7711c09d3e78ec2dfbef Author: Andrey Mokhov Date: Sun Nov 27 17:51:57 2016 +0000 Drop old TODOs See #113 >--------------------------------------------------------------- 92b5c3507f296b1676cb7711c09d3e78ec2dfbef src/Settings/Path.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 9e88ca6..13ef02a 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -37,7 +37,6 @@ generatedPath = buildRootPath -/- "generated" stageDirectory :: Stage -> FilePath stageDirectory = stageString --- TODO: Move to buildRootPath, see #113. -- | Directory for binaries that are built "in place". programInplacePath :: FilePath programInplacePath = "inplace/bin" @@ -141,7 +140,6 @@ libffiContext = vanillaContext Stage1 libffi libffiBuildPath :: FilePath libffiBuildPath = buildPath libffiContext --- TODO: Move to buildRootPath, see #113. -- | Path to package database directory of a given 'Stage'. Note: StageN, N > 0, -- share the same packageDbDirectory. packageDbDirectory :: Stage -> FilePath From git at git.haskell.org Fri Oct 27 00:28:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian. (3be1a41) Message-ID: <20171027002846.8B9D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3be1a417e326d35b5756a056e93ce2b828bf8790/ghc >--------------------------------------------------------------- commit 3be1a417e326d35b5756a056e93ce2b828bf8790 Author: Andrey Mokhov Date: Thu May 5 03:16:20 2016 +0100 Rename to Hadrian. >--------------------------------------------------------------- 3be1a417e326d35b5756a056e93ce2b828bf8790 src/Base.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 5e66a27..625dfd8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -45,11 +45,11 @@ import System.IO -- TODO: reexport Stage, etc.? -- Build system files and paths -shakePath :: FilePath -shakePath = "hadrian" +hadrianPath :: FilePath +hadrianPath = "hadrian" configPath :: FilePath -configPath = shakePath -/- "cfg" +configPath = hadrianPath -/- "cfg" configFile :: FilePath configFile = configPath -/- "system.config" @@ -57,7 +57,7 @@ configFile = configPath -/- "system.config" -- | Path to source files of the build system, e.g. this file is located at -- sourcePath -/- "Base.hs". We use this to `need` some of the source files. sourcePath :: FilePath -sourcePath = shakePath -/- "src" +sourcePath = hadrianPath -/- "src" -- TODO: move to buildRootPath, see #113 programInplacePath :: FilePath From git at git.haskell.org Fri Oct 27 00:28:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcPkgMode (31c6109) Message-ID: <20171027002849.1E0F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31c6109cce4304c1a978fad6b399b91fbb7fe9d0/ghc >--------------------------------------------------------------- commit 31c6109cce4304c1a978fad6b399b91fbb7fe9d0 Author: Andrey Mokhov Date: Sun Nov 27 18:11:58 2016 +0000 Add GhcPkgMode >--------------------------------------------------------------- 31c6109cce4304c1a978fad6b399b91fbb7fe9d0 src/Builder.hs | 12 ++++++++++-- src/GHC.hs | 4 ++-- src/Oracles/Path.hs | 38 +++++++++++++++++++------------------- src/Rules/Register.hs | 6 ++++-- src/Rules/Test.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 20 ++++++++++---------- src/Settings/Builders/GhcPkg.hs | 26 ++++++++++---------------- 7 files changed, 57 insertions(+), 53 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 31c6109cce4304c1a978fad6b399b91fbb7fe9d0 From git at git.haskell.org Fri Oct 27 00:28:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install ghc-7.10.3 before using stack. (ccf97ae) Message-ID: <20171027002849.C7EE93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccf97ae74f3cbfaaa0484d12af82231832e2620f/ghc >--------------------------------------------------------------- commit ccf97ae74f3cbfaaa0484d12af82231832e2620f Author: Andrey Mokhov Date: Thu Jan 7 01:40:09 2016 +0000 Install ghc-7.10.3 before using stack. See #110. [skip ci] >--------------------------------------------------------------- ccf97ae74f3cbfaaa0484d12af82231832e2620f .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7410a5e..f282d5b 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -5,9 +5,9 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 - 7z x stack.zip stack.exe + - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - stack install -v3 -j --prefix=/usr/local alex happy - - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build From git at git.haskell.org Fri Oct 27 00:28:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need patch file by default. (6a09a6b) Message-ID: <20171027002850.3E1863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a09a6b9720f8782224eddd39db9f4ec9cd3164b/ghc >--------------------------------------------------------------- commit 6a09a6b9720f8782224eddd39db9f4ec9cd3164b Author: Andrey Mokhov Date: Thu May 5 03:19:02 2016 +0100 Don't need patch file by default. >--------------------------------------------------------------- 6a09a6b9720f8782224eddd39db9f4ec9cd3164b src/Rules/Actions.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index edf98eb..32d2544 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -146,7 +146,6 @@ runMakeWithVerbosity verbose dir args = do applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch - need [file] needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file From git at git.haskell.org Fri Oct 27 00:28:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop references to #113 (0412d60) Message-ID: <20171027002853.0285B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0412d60aef702d221af1b7c12ed96f1421c8d199/ghc >--------------------------------------------------------------- commit 0412d60aef702d221af1b7c12ed96f1421c8d199 Author: Andrey Mokhov Date: Sun Nov 27 18:23:04 2016 +0000 Drop references to #113 [skip ci] >--------------------------------------------------------------- 0412d60aef702d221af1b7c12ed96f1421c8d199 README.md | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index d869f4b..0d7b3d8 100644 --- a/README.md +++ b/README.md @@ -45,8 +45,8 @@ flags below). Using the build system ---------------------- -Once your first build is successful, simply run `build` to rebuild. Most build artefacts -are placed into `_build` and `inplace` directories ([#113][build-artefacts-issue]). +Once your first build is successful, simply run `build` to rebuild. Build results +are placed into `_build` and `inplace` directories. #### Command line flags @@ -92,11 +92,10 @@ use `hadrian/UserSettings.hs` for the same purpose, see [documentation](doc/user #### Clean and full rebuild -* `build clean` removes all build artefacts. Note, we are working towards a -complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `build clean` removes all build artefacts. -* `build -B` forces Shake to rerun all rules, even if results of the previous build -are still in the GHC tree. +* `build -B` forces Shake to rerun all rules, even if the previous build results are +are still up-to-date. #### Source distribution @@ -156,7 +155,6 @@ helped me endure and enjoy the project. [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild [windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md -[build-artefacts-issue]: https://github.com/snowleopard/hadrian/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 From git at git.haskell.org Fri Oct 27 00:28:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to stack/windows-x86_64. (280b6fa) Message-ID: <20171027002853.D99953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/280b6fa49b1e3541de7a1bc242a9b953bc00cec1/ghc >--------------------------------------------------------------- commit 280b6fa49b1e3541de7a1bc242a9b953bc00cec1 Author: Andrey Mokhov Date: Thu Jan 7 01:49:02 2016 +0000 Switch to stack/windows-x86_64. See #110. [skip ci] >--------------------------------------------------------------- 280b6fa49b1e3541de7a1bc242a9b953bc00cec1 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f282d5b..a78c02c 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -3,7 +3,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 + - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git From git at git.haskell.org Fri Oct 27 00:28:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of partial functions. (fa57784) Message-ID: <20171027002854.225E73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fa57784081e696d90b305601b9cfd960841f082c/ghc >--------------------------------------------------------------- commit fa57784081e696d90b305601b9cfd960841f082c Author: Andrey Mokhov Date: Thu May 5 03:24:45 2016 +0100 Get rid of partial functions. >--------------------------------------------------------------- fa57784081e696d90b305601b9cfd960841f082c src/Rules/Libffi.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 17067ad..424b552 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -76,17 +76,18 @@ libffiRules = do createDirectory $ buildRootPath -/- stageString Stage0 tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - when (length tarballs /= 1) $ - putError $ "libffiRules: exactly one libffi tarball expected" - ++ "(found: " ++ show tarballs ++ ")." + tarball <- case tarballs of + [file] -> return $ unifyPath file + _ -> putError $ "libffiRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." - need tarballs - let libname = dropExtension . dropExtension . takeFileName $ head tarballs + need [tarball] + let libname = dropExtension . dropExtension $ takeFileName tarball removeDirectory (buildRootPath -/- libname) -- TODO: Simplify. actionFinally (do - build $ Target libffiContext Tar tarballs [buildRootPath] + build $ Target libffiContext Tar [tarball] [buildRootPath] moveDirectory (buildRootPath -/- libname) libffiBuildPath) $ removeFiles buildRootPath [libname "*"] From git at git.haskell.org Fri Oct 27 00:28:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Directory package no longer needs special treatment (1eff9b4) Message-ID: <20171027002856.7662B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1eff9b4e3114eb38e935def533b54ce0235a6331/ghc >--------------------------------------------------------------- commit 1eff9b4e3114eb38e935def533b54ce0235a6331 Author: Andrey Mokhov Date: Sun Nov 27 22:18:41 2016 +0000 Directory package no longer needs special treatment >--------------------------------------------------------------- 1eff9b4e3114eb38e935def533b54ce0235a6331 hadrian.cabal | 1 - src/Settings/Default.hs | 2 -- src/Settings/Packages/Directory.hs | 12 ------------ 3 files changed, 15 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 30ed256..374b5a0 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -89,7 +89,6 @@ executable hadrian , Settings.Flavours.Quickest , Settings.Packages.Base , Settings.Packages.Compiler - , Settings.Packages.Directory , Settings.Packages.Ghc , Settings.Packages.GhcCabal , Settings.Packages.GhcPrim diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 6f56c5d..b5df4b5 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -29,7 +29,6 @@ import Settings.Builders.Make import Settings.Builders.Tar import Settings.Packages.Base import Settings.Packages.Compiler -import Settings.Packages.Directory import Settings.Packages.Ghc import Settings.Packages.GhcCabal import Settings.Packages.GhcPrim @@ -194,7 +193,6 @@ defaultPackageArgs :: Args defaultPackageArgs = mconcat [ basePackageArgs , compilerPackageArgs - , directoryPackageArgs , ghcPackageArgs , ghcCabalPackageArgs , ghcPrimPackageArgs diff --git a/src/Settings/Packages/Directory.hs b/src/Settings/Packages/Directory.hs deleted file mode 100644 index 5b5d96b..0000000 --- a/src/Settings/Packages/Directory.hs +++ /dev/null @@ -1,12 +0,0 @@ -module Settings.Packages.Directory (directoryPackageArgs) where - -import GHC -import Predicate - --- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is --- effectively empty. I presume it was expected that GHC will be used for --- compiling all C files, but I don't know why. It seems that directory.c is the --- only file which requires special treatment when using GCC. -directoryPackageArgs :: Args -directoryPackageArgs = package directory ? - builder Cc ? arg "-D__GLASGOW_HASKELL__" From git at git.haskell.org Fri Oct 27 00:28:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop extra flags to stack install. (78fee43) Message-ID: <20171027002858.1E4013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/78fee435f395b30199947fd7eefd32bbb25d5804/ghc >--------------------------------------------------------------- commit 78fee435f395b30199947fd7eefd32bbb25d5804 Author: Andrey Mokhov Date: Thu Jan 7 01:59:39 2016 +0000 Drop extra flags to stack install. See #110. [skip ci] >--------------------------------------------------------------- 78fee435f395b30199947fd7eefd32bbb25d5804 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index a78c02c..1b5e3bc 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,7 +7,7 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - stack install -v3 -j --prefix=/usr/local alex happy + - stack install alex happy - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build From git at git.haskell.org Fri Oct 27 00:28:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop removeDirectoryIfExists. (ad53022) Message-ID: <20171027002858.3BBB73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ad53022e5f3da17d8b744b922c32756dba6408d2/ghc >--------------------------------------------------------------- commit ad53022e5f3da17d8b744b922c32756dba6408d2 Author: Andrey Mokhov Date: Thu May 5 03:52:19 2016 +0100 Drop removeDirectoryIfExists. See #163. >--------------------------------------------------------------- ad53022e5f3da17d8b744b922c32756dba6408d2 src/Base.hs | 7 +------ src/Oracles/PackageDb.hs | 2 +- src/Rules/Actions.hs | 3 ++- src/Rules/Clean.hs | 16 ++++++---------- src/Rules/Gmp.hs | 2 +- 5 files changed, 11 insertions(+), 19 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 625dfd8..ccadd22 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,7 +23,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath + removeFileIfExists, matchVersionedFilePath ) where import Control.Applicative @@ -176,11 +176,6 @@ lookupAll (x:xs) (y:ys) = case compare x (fst y) of removeFileIfExists :: FilePath -> Action () removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f --- | Remove a directory that doesn't necessarily exist -removeDirectoryIfExists :: FilePath -> Action () -removeDirectoryIfExists d = - liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d - -- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the -- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: diff --git a/src/Oracles/PackageDb.hs b/src/Oracles/PackageDb.hs index b644989..760f2a7 100644 --- a/src/Oracles/PackageDb.hs +++ b/src/Oracles/PackageDb.hs @@ -17,6 +17,6 @@ packageDbOracle = void $ let dir = packageDbDirectory stage file = dir -/- "package.cache" unlessM (liftIO $ IO.doesFileExist file) $ do - removeDirectoryIfExists dir + removeDirectory dir build $ Target (vanillaContext stage ghcPkg) (GhcPkg stage) [] [dir] putSuccess $ "| Successfully initialised " ++ dir diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 32d2544..25bf72e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -99,10 +99,11 @@ createDirectory dir = do putBuild $ "| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir +-- | Remove a directory that doesn't necessarily exist. removeDirectory :: FilePath -> Action () removeDirectory dir = do putBuild $ "| Remove directory " ++ dir - removeDirectoryIfExists dir + liftIO . whenM (IO.doesDirectoryExist dir) $ IO.removeDirectoryRecursive dir -- Note, the source directory is untracked copyDirectory :: FilePath -> FilePath -> Action () diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index ca5c062..f615e54 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -3,24 +3,20 @@ module Rules.Clean (cleanRules) where import Base import Context import Package +import Rules.Actions import Rules.Generate import Settings.Packages import Settings.Paths import Settings.User import Stage -clean :: FilePath -> Action () -clean dir = do - putBuild $ "| Remove files in " ++ dir ++ "..." - removeDirectoryIfExists dir - cleanRules :: Rules () cleanRules = do "clean" ~> do - forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) - clean programInplacePath - clean "inplace/lib" - clean derivedConstantsPath + forM_ [Stage0 ..] $ removeDirectory . (buildRootPath -/-) . stageString + removeDirectory programInplacePath + removeDirectory "inplace/lib" + removeDirectory derivedConstantsPath forM_ includesDependencies $ \file -> do putBuild $ "| Remove " ++ file removeFileIfExists file @@ -28,7 +24,7 @@ cleanRules = do forM_ knownPackages $ \pkg -> forM_ [Stage0 ..] $ \stage -> do let dir = pkgPath pkg -/- contextDirectory (vanillaContext stage pkg) - removeDirectoryIfExists dir + quietly $ removeDirectory dir putBuild $ "| Remove Hadrian files..." removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index d98bc3b..9cec3a3 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -52,7 +52,7 @@ gmpRules = do -- TODO: split into multiple rules gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - removeDirectoryIfExists gmpBuildPath + removeDirectory gmpBuildPath -- We don't use system GMP on Windows. TODO: fix? windows <- windowsHost From git at git.haskell.org Fri Oct 27 00:28:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (6552aff) Message-ID: <20171027002859.E0B093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6552aff7cf7fde37106b03b851e6d4cdbe515b74/ghc >--------------------------------------------------------------- commit 6552aff7cf7fde37106b03b851e6d4cdbe515b74 Author: Andrey Mokhov Date: Sun Nov 27 22:39:42 2016 +0000 Minor revision >--------------------------------------------------------------- 6552aff7cf7fde37106b03b851e6d4cdbe515b74 src/Settings/Builders/Cc.hs | 5 ++--- src/Settings/Builders/Haddock.hs | 3 +-- src/Settings/Packages/Compiler.hs | 6 ++---- src/Settings/Packages/IntegerGmp.hs | 4 +--- src/Settings/Packages/Rts.hs | 11 +++++------ src/Settings/Packages/RunGhc.hs | 5 ++--- 6 files changed, 13 insertions(+), 21 deletions(-) diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index b0a5f0e..b5d85df 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -8,9 +8,8 @@ ccBuilderArgs = builder Cc ? mconcat , argSettingList . ConfCcArgs =<< getStage , cIncludeArgs - , builder (Cc CompileC) ? - mconcat [ arg "-c", arg =<< getInput - , arg "-o", arg =<< getOutput ] + , builder (Cc CompileC) ? mconcat [ arg "-c", arg =<< getInput + , arg "-o", arg =<< getOutput ] , builder (Cc FindCDependencies) ? do output <- getOutput diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 312124a..3fff015 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -16,7 +16,6 @@ haddockBuilderArgs = builder Haddock ? do path <- getBuildPath version <- getPkgData Version synopsis <- getPkgData Synopsis - hidden <- getPkgDataList HiddenModules deps <- getPkgDataList Deps depNames <- getPkgDataList DepNames hVersion <- lift . pkgData . Version $ buildPath (vanillaContext Stage2 haddock) @@ -31,7 +30,7 @@ haddockBuilderArgs = builder Haddock ? do , arg $ "--title=" ++ pkgNameString pkg ++ "-" ++ version ++ ": " ++ synopsis , arg $ "--prologue=" ++ path -/- "haddock-prologue.txt" , arg $ "--optghc=-D__HADDOCK_VERSION__=" ++ show (versionToInt hVersion) - , append $ map ("--hide=" ++) hidden + , append . map ("--hide=" ++) =<< getPkgDataList HiddenModules , append $ [ "--read-interface=../" ++ dep ++ ",../" ++ dep ++ "/src/%{MODULE/./-}.html\\#%{NAME}," ++ pkgHaddockFile (vanillaContext Stage1 depPkg) diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 03b8081..308b3c2 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -35,8 +35,6 @@ compilerPackageArgs = package compiler ? do ghciWithDebugger flavour ? notStage0 ? arg "--ghc-option=-DDEBUGGER" , ghcProfiled flavour ? - notStage0 ? arg "--ghc-pkg-option=--force" - ] + notStage0 ? arg "--ghc-pkg-option=--force" ] - , builder Haddock ? arg ("--optghc=-I" ++ path) - ] + , builder Haddock ? arg ("--optghc=-I" ++ path) ] diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index def2021..7dfcb2f 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -15,12 +15,10 @@ integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" gmpIncludeDir <- getSetting GmpIncludeDir gmpLibDir <- getSetting GmpLibDir - mconcat [ builder Cc ? arg includeGmp , builder GhcCabal ? mconcat [ (null gmpIncludeDir && null gmpLibDir) ? arg "--configure-option=--with-intree-gmp" , appendSub "--configure-option=CFLAGS" [includeGmp] - , appendSub "--gcc-options" [includeGmp] ] - ] + , appendSub "--gcc-options" [includeGmp] ] ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index d10c6f0..7d844fa 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -12,10 +12,10 @@ rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do useSystemFfi <- flag UseSystemFfi windows <- windowsHost - case (useSystemFfi, windows) of - (True , False) -> return "ffi" - (False, False) -> return "Cffi" - (_ , True ) -> return "Cffi-6" + return $ case (useSystemFfi, windows) of + (True , False) -> "ffi" + (False, False) -> "Cffi" + (_ , True ) -> "Cffi-6" rtsPackageArgs :: Args rtsPackageArgs = package rts ? do @@ -88,8 +88,7 @@ rtsPackageArgs = package rts ? do [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir , "-DFFI_LIB_DIR=" ++ show ffiLibraryDir - , "-DFFI_LIB=" ++ show libffiName ] - ] + , "-DFFI_LIB=" ++ show libffiName ] ] -- # If we're compiling on windows, enforce that we only support XP+ -- # Adding this here means it doesn't have to be done in individual .c files diff --git a/src/Settings/Packages/RunGhc.hs b/src/Settings/Packages/RunGhc.hs index 6880344..dc8ab1f 100644 --- a/src/Settings/Packages/RunGhc.hs +++ b/src/Settings/Packages/RunGhc.hs @@ -5,7 +5,6 @@ import Oracles.Config.Setting import Predicate runGhcPackageArgs :: Args -runGhcPackageArgs = package runGhc ? do +runGhcPackageArgs = package runGhc ? builder Ghc ? input "//Main.hs" ? do version <- getSetting ProjectVersion - builder Ghc ? input "//Main.hs" ? - append ["-cpp", "-DVERSION=" ++ show version] + append ["-cpp", "-DVERSION=" ++ show version] From git at git.haskell.org Fri Oct 27 00:29:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create /home/ghc/tmp, add stack install dir to PATH. (3ecd105) Message-ID: <20171027002901.DADFE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ecd10554246bfe2d69153807248881f22d50a6d/ghc >--------------------------------------------------------------- commit 3ecd10554246bfe2d69153807248881f22d50a6d Author: Andrey Mokhov Date: Thu Jan 7 02:10:08 2016 +0000 Create /home/ghc/tmp, add stack install dir to PATH. See #110. [skip ci] >--------------------------------------------------------------- 3ecd10554246bfe2d69153807248881f22d50a6d .appveyor.yml | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.appveyor.yml b/.appveyor.yml index 1b5e3bc..011b327 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,6 +8,8 @@ install: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - stack install alex happy + - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ + - bash -lc "mkdir /home/ghc/tmp" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build From git at git.haskell.org Fri Oct 27 00:29:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths in inplace-pkg-config files (e081b08) Message-ID: <20171027002903.5E5573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e081b081214295de8a31631e9d00642965f7fc23/ghc >--------------------------------------------------------------- commit e081b081214295de8a31631e9d00642965f7fc23 Author: Andrey Mokhov Date: Fri Dec 16 01:27:46 2016 +0000 Fix paths in inplace-pkg-config files >--------------------------------------------------------------- e081b081214295de8a31631e9d00642965f7fc23 src/Rules/Data.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index dc53654..cff0896 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -47,10 +47,8 @@ buildPackageData context at Context {..} = do . replace "rts/dist/build" rtsBuildPath . replace "includes/dist-derivedconstants/header" generatedPath ) . lines - else do - top <- topDirectory - let oldPath = top -/- path "build" - fixFile conf $ unlines . map (replace oldPath path) . lines + else + fixFile conf $ unlines . map (replace (path "build") path) . lines priority 2.0 $ when (nonCabalContext context) $ dataFile %> generatePackageData context From git at git.haskell.org Fri Oct 27 00:29:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Base.removeFileIfExists to Rules.Actions.removeFile. (658d373) Message-ID: <20171027002902.10CBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/658d373c5b823792758e7d3ccb0577b6ecb24c82/ghc >--------------------------------------------------------------- commit 658d373c5b823792758e7d3ccb0577b6ecb24c82 Author: Andrey Mokhov Date: Thu May 5 03:59:50 2016 +0100 Move Base.removeFileIfExists to Rules.Actions.removeFile. See #163. >--------------------------------------------------------------- 658d373c5b823792758e7d3ccb0577b6ecb24c82 src/Base.hs | 7 +------ src/Rules/Actions.hs | 8 +++++++- src/Rules/Clean.hs | 4 +--- src/Rules/Dependencies.hs | 2 +- src/Rules/Library.hs | 2 +- 5 files changed, 11 insertions(+), 12 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index ccadd22..a26fea1 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,7 +23,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - removeFileIfExists, matchVersionedFilePath + matchVersionedFilePath ) where import Control.Applicative @@ -39,7 +39,6 @@ import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI -import qualified System.Directory as IO import System.IO -- TODO: reexport Stage, etc.? @@ -172,10 +171,6 @@ lookupAll (x:xs) (y:ys) = case compare x (fst y) of EQ -> Just (snd y) : lookupAll xs (y:ys) GT -> lookupAll (x:xs) ys --- | Remove a file that doesn't necessarily exist -removeFileIfExists :: FilePath -> Action () -removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f - -- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the -- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 25bf72e..9910ce5 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,6 +1,6 @@ module Rules.Actions ( build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, - createDirectory, removeDirectory, copyDirectory, moveDirectory, + removeFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, applyPatch, fixFile, runMake, runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable ) where @@ -94,6 +94,12 @@ moveFile source target = do putProgressInfo $ renderAction "Move file" source target liftIO $ IO.renameFile source target +-- | Remove a file that doesn't necessarily exist. +removeFile :: FilePath -> Action () +removeFile file = do + putBuild $ "| Remove file " ++ file + liftIO . whenM (IO.doesFileExist file) $ IO.removeFile file + createDirectory :: FilePath -> Action () createDirectory dir = do putBuild $ "| Create directory " ++ dir diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index f615e54..613073a 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -17,9 +17,7 @@ cleanRules = do removeDirectory programInplacePath removeDirectory "inplace/lib" removeDirectory derivedConstantsPath - forM_ includesDependencies $ \file -> do - putBuild $ "| Remove " ++ file - removeFileIfExists file + forM_ includesDependencies removeFile putBuild $ "| Remove files generated by ghc-cabal..." forM_ knownPackages $ \pkg -> forM_ [Stage0 ..] $ \stage -> do diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 9059b3d..f5d781a 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -29,7 +29,7 @@ buildPackageDependencies rs context at Context {..} = then writeFileChanged out "" else buildWithResources rs $ Target context (Ghc FindDependencies stage) srcs [out] - removeFileIfExists $ out <.> "bak" + removeFile $ out <.> "bak" -- TODO: don't accumulate *.deps into .dependencies path -/- ".dependencies" %> \out -> do diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 8e09162..2b90d1f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -22,7 +22,7 @@ buildPackageLibrary context at Context {..} = do -- TODO: handle dynamic libraries matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do - removeFileIfExists a + removeFile a cSrcs <- cSources context hSrcs <- hSources context From git at git.haskell.org Fri Oct 27 00:29:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add appveyor badge (152f4da) Message-ID: <20171027002905.67C663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/152f4dae7932519935f4615f305505027fbd5159/ghc >--------------------------------------------------------------- commit 152f4dae7932519935f4615f305505027fbd5159 Author: Andrey Mokhov Date: Thu Jan 7 02:21:18 2016 +0000 Add appveyor badge See #110. [skip ci] >--------------------------------------------------------------- 152f4dae7932519935f4615f305505027fbd5159 README.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 90f6422..1347ee5 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,8 @@ Shaking up GHC ============== -[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) +[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Build status](https://ci.appveyor.com/api/projects/status/9er74sbnrkco98gb?svg=true&pendingText=Windows&passingText=Windows&failingText=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) + As part of my 6-month research secondment to Microsoft Research in Cambridge I am taking up the challenge of migrating the current [GHC][ghc] build system From git at git.haskell.org Fri Oct 27 00:29:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Show output of boot and configure. (72cbd44) Message-ID: <20171027002905.A71E23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72cbd44066d9a9e30c5c9613884d4f778afe42e5/ghc >--------------------------------------------------------------- commit 72cbd44066d9a9e30c5c9613884d4f778afe42e5 Author: Andrey Mokhov Date: Thu May 5 04:22:57 2016 +0100 Show output of boot and configure. See #234. >--------------------------------------------------------------- 72cbd44066d9a9e30c5c9613884d4f778afe42e5 src/Rules/Actions.hs | 2 +- src/Rules/Configure.hs | 11 ++++------- 2 files changed, 5 insertions(+), 8 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9910ce5..a312ce9 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -62,7 +62,7 @@ customBuild rs opts target at Target {..} = do need [dir -/- "configure"] -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" - cmd Shell (EchoStdout False) [Cwd dir] [path] (env:opts) argList + cmd Shell [Cwd dir] [path] (env:opts) argList HsCpp -> captureStdout target path argList GenApply -> captureStdout target path argList diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index d1c7cf2..44ed75c 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -1,6 +1,6 @@ module Rules.Configure (configureRules) where -import qualified System.Info +import qualified System.Info as System import Base import Builder @@ -22,12 +22,9 @@ configureRules = do ++ "--skip-configure flag." else do -- We cannot use windowsHost here due to a cyclic dependency. - when (System.Info.os == "mingw32") $ do + when (System.os == "mingw32") $ do putBuild "| Checking for Windows tarballs..." - quietly $ cmd [ "bash" - , "mk/get-win32-tarballs.sh" - , "download" - , System.Info.arch ] + quietly $ cmd ["bash mk/get-win32-tarballs.sh download", System.arch] let srcs = map (<.> "in") outs context = vanillaContext Stage0 compiler need srcs @@ -41,4 +38,4 @@ configureRules = do else do need ["configure.ac"] putBuild "| Running boot..." - quietly $ cmd (EchoStdout False) "perl boot" + quietly $ cmd "perl boot" From git at git.haskell.org Fri Oct 27 00:29:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle Make correctly in needBuilder, refactor customBuild (7f62b5a) Message-ID: <20171027002906.DED533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7f62b5a774b790a750651a834cc0de6ffaf61943/ghc >--------------------------------------------------------------- commit 7f62b5a774b790a750651a834cc0de6ffaf61943 Author: Andrey Mokhov Date: Fri Dec 16 21:07:13 2016 +0000 Handle Make correctly in needBuilder, refactor customBuild See #295 >--------------------------------------------------------------- 7f62b5a774b790a750651a834cc0de6ffaf61943 src/Util.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index 81f67dd..b6d9536 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -61,7 +61,6 @@ customBuild rs opts target at Target {..} = do cmd [Cwd output] [path] "x" (top -/- input) Configure dir -> do - need [dir -/- "configure"] -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" cmd Shell cmdEcho env [Cwd dir] [path] opts argList @@ -76,9 +75,7 @@ customBuild rs opts target at Target {..} = do Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output - Make dir -> do - need [dir -/- "Makefile"] - cmd Shell cmdEcho path ["-C", dir] argList + Make dir -> cmd Shell cmdEcho path ["-C", dir] argList _ -> cmd [path] argList @@ -170,6 +167,7 @@ isInternal = isJust . builderProvenance -- | Make sure a 'Builder' exists and rebuild it if out of date. needBuilder :: Builder -> Action () needBuilder (Configure dir) = need [dir -/- "configure"] +needBuilder (Make dir) = need [dir -/- "Makefile"] needBuilder builder = when (isInternal builder) $ do path <- builderPath builder need [path] From git at git.haskell.org Fri Oct 27 00:29:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths. (a599895) Message-ID: <20171027002908.D44A93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5998956f9b8cc5b9042379fd298d7b823dbdaf9/ghc >--------------------------------------------------------------- commit a5998956f9b8cc5b9042379fd298d7b823dbdaf9 Author: Andrey Mokhov Date: Thu Jan 7 02:23:41 2016 +0000 Fix paths. See #110. [skip ci] >--------------------------------------------------------------- a5998956f9b8cc5b9042379fd298d7b823dbdaf9 .appveyor.yml | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 011b327..991ef0a 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -9,10 +9,9 @@ install: - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - stack install alex happy - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - - bash -lc "mkdir /home/ghc/tmp" - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - cd C:\msys64\mingw64\home\ghc\shake-build + - cd C:\msys64\home\ghc\shake-build - stack install --only-dependencies build_script: From git at git.haskell.org Fri Oct 27 00:29:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix get-win32-tarballs command line. (32a2526) Message-ID: <20171027002909.1E7F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/32a25268694276e609343dfc28361444a5fa7287/ghc >--------------------------------------------------------------- commit 32a25268694276e609343dfc28361444a5fa7287 Author: Andrey Mokhov Date: Thu May 5 04:25:47 2016 +0100 Fix get-win32-tarballs command line. >--------------------------------------------------------------- 32a25268694276e609343dfc28361444a5fa7287 src/Rules/Configure.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index 44ed75c..d36542a 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -24,7 +24,7 @@ configureRules = do -- We cannot use windowsHost here due to a cyclic dependency. when (System.os == "mingw32") $ do putBuild "| Checking for Windows tarballs..." - quietly $ cmd ["bash mk/get-win32-tarballs.sh download", System.arch] + quietly $ cmd ["bash", "mk/get-win32-tarballs.sh", "download", System.arch] let srcs = map (<.> "in") outs context = vanillaContext Stage0 compiler need srcs From git at git.haskell.org Fri Oct 27 00:29:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to Cabal library changes (6984895) Message-ID: <20171027002910.52D583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/69848955eb325f901ee8a2d387147e5b223e0363/ghc >--------------------------------------------------------------- commit 69848955eb325f901ee8a2d387147e5b223e0363 Author: Andrey Mokhov Date: Fri Dec 30 23:05:50 2016 +0000 Adapt to Cabal library changes >--------------------------------------------------------------- 69848955eb325f901ee8a2d387147e5b223e0363 src/Rules/Cabal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 370bda2..6adaf44 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -4,6 +4,7 @@ import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Text +import Distribution.Types.Dependency import Distribution.Verbosity import Base From git at git.haskell.org Fri Oct 27 00:29:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install shake, mtl and ansi-terminal. (f514cc4) Message-ID: <20171027002912.6C6353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f514cc4d9b216c6dae5cb69f406f911fb3959718/ghc >--------------------------------------------------------------- commit f514cc4d9b216c6dae5cb69f406f911fb3959718 Author: Andrey Mokhov Date: Thu Jan 7 02:40:43 2016 +0000 Install shake, mtl and ansi-terminal. See #110. [skip ci] >--------------------------------------------------------------- f514cc4d9b216c6dae5cb69f406f911fb3959718 .appveyor.yml | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 991ef0a..7bcda85 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,12 +7,10 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - stack install alex happy + - stack install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - cd C:\msys64\home\ghc\shake-build - - stack install --only-dependencies build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:29:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move decode/encodeModule to Oracles.ModuleFiles. (9c45e4d) Message-ID: <20171027002912.B34943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c45e4df1b88c2f726c84a651cb45b8e40f5b7c2/ghc >--------------------------------------------------------------- commit 9c45e4df1b88c2f726c84a651cb45b8e40f5b7c2 Author: Andrey Mokhov Date: Thu May 5 04:56:09 2016 +0100 Move decode/encodeModule to Oracles.ModuleFiles. >--------------------------------------------------------------- 9c45e4df1b88c2f726c84a651cb45b8e40f5b7c2 src/Base.hs | 18 +----------------- src/Oracles/ModuleFiles.hs | 17 ++++++++++++++++- src/Rules/Selftest.hs | 1 + 3 files changed, 18 insertions(+), 18 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a26fea1..1fcbae7 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,8 +22,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, - decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - matchVersionedFilePath + unifyPath, (-/-), versionToInt, matchVersionedFilePath ) where import Control.Applicative @@ -84,21 +83,6 @@ versionToInt s = major * 1000 + minor * 10 + patch where [major, minor, patch] = map read . words $ replaceEq '.' ' ' s --- | Given a module name extract the directory and file name, e.g.: --- --- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") --- > decodeModule "Prelude" == ("./", "Prelude") -decodeModule :: String -> (FilePath, String) -decodeModule = splitFileName . replaceEq '.' '/' - --- | Given the directory and file name find the corresponding module name, e.g.: --- --- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" --- > encodeModule "./" "Prelude" == "Prelude" --- > uncurry encodeModule (decodeModule name) == name -encodeModule :: FilePath -> String -> String -encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file - -- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 70cf983..652eb9a 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.ModuleFiles ( - findGenerator, haskellSources, moduleFilesOracle + decodeModule, encodeModule, findGenerator, haskellSources, moduleFilesOracle ) where import qualified Data.HashMap.Strict as Map @@ -26,6 +26,21 @@ determineBuilder file = case takeExtension file of ".hsc" -> Just Hsc2Hs _ -> Nothing +-- | Given a module name extract the directory and file name, e.g.: +-- +-- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") +-- > decodeModule "Prelude" == ("./", "Prelude") +decodeModule :: String -> (FilePath, String) +decodeModule = splitFileName . replaceEq '.' '/' + +-- | Given the directory and file name find the corresponding module name, e.g.: +-- +-- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" +-- > encodeModule "./" "Prelude" == "Prelude" +-- > uncurry encodeModule (decodeModule name) == name +encodeModule :: FilePath -> String -> String +encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file + -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) -- ".build/stage1/compiler/build/Lexer.hs" diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f549b0f..8037682 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,6 +6,7 @@ import Development.Shake import Test.QuickCheck import Base +import Oracles.ModuleFiles (decodeModule, encodeModule) import Settings.Builders.Ar (chunksOfSize) import Way From git at git.haskell.org Fri Oct 27 00:29:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghci library in Stage0 (8e3cb44) Message-ID: <20171027002913.C68C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e3cb447a9476196099fc7a6b22d0d177795263f/ghc >--------------------------------------------------------------- commit 8e3cb447a9476196099fc7a6b22d0d177795263f Author: Andrey Mokhov Date: Fri Dec 30 23:19:27 2016 +0000 Build ghci library in Stage0 >--------------------------------------------------------------- 8e3cb447a9476196099fc7a6b22d0d177795263f src/Settings/Default.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index b5df4b5..ba4ef79 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -67,6 +67,7 @@ stage0Packages = do , ghcBoot , ghcBootTh , ghcCabal + , ghci , ghcPkg , hsc2hs , hoopl From git at git.haskell.org Fri Oct 27 00:29:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Take 2 (a7da5e0) Message-ID: <20171027002915.CE8003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7da5e01637652109a75b05371b5e5864df8e836/ghc >--------------------------------------------------------------- commit a7da5e01637652109a75b05371b5e5864df8e836 Author: Moritz Angermann Date: Thu Jan 7 11:06:37 2016 +0800 Take 2 >--------------------------------------------------------------- a7da5e01637652109a75b05371b5e5864df8e836 shaking-up-ghc.cabal | 1 + src/Oracles/WindowsRoot.hs | 12 +++++++----- 2 files changed, 8 insertions(+), 5 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 00fb408..f9990e9 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -114,6 +114,7 @@ executable ghc-shake , extra >= 1.4 , mtl >= 2.2 , shake >= 0.15 + , split >= 0.2 , transformers >= 0.4 , unordered-containers >= 0.2 default-language: Haskell2010 diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 195f591..473a235 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -4,6 +4,7 @@ module Oracles.WindowsRoot ( ) where import Data.Char (isSpace) +import Data.List.Split (splitOn) import Base import Oracles.Config.Setting @@ -40,12 +41,13 @@ fixAbsolutePathOnWindows path = do -- | Lookup a @command@ in @PATH@ environment. lookupInPath :: FilePath -> Action FilePath -lookupInPath command - | command /= takeFileName command = return command +lookupInPath c + | c /= takeFileName c = return c | otherwise = do - Stdout out <- quietly $ cmd ["which", command] - let path = dropWhileEnd isSpace out - return path + envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" + let candidates = map (-/- c) envPaths in + -- this will crash if we do not find any valid candidate. + head <$> filterM doesFileExist candidates -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). From git at git.haskell.org Fri Oct 27 00:29:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move GMP paths to Settings.Paths. (a88253a) Message-ID: <20171027002916.2F6EB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a88253a92b436358af15ab6ff5c99b5270ed6024/ghc >--------------------------------------------------------------- commit a88253a92b436358af15ab6ff5c99b5270ed6024 Author: Andrey Mokhov Date: Thu May 5 05:15:22 2016 +0100 Move GMP paths to Settings.Paths. >--------------------------------------------------------------- a88253a92b436358af15ab6ff5c99b5270ed6024 src/Rules/Generate.hs | 1 - src/Rules/Gmp.hs | 11 +---------- src/Rules/Library.hs | 1 - src/Settings/Paths.hs | 26 +++++++++++++++++++------- 4 files changed, 20 insertions(+), 19 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8d04e8d..78326dd 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -18,7 +18,6 @@ import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles import Rules.Actions -import Rules.Gmp import Rules.Libffi import Settings import Target hiding (builder, context) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 9cec3a3..2de1878 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,4 +1,4 @@ -module Rules.Gmp (gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH) where +module Rules.Gmp (gmpRules) where import Base import Expression @@ -16,18 +16,9 @@ gmpBase = "libraries/integer-gmp/gmp" gmpContext :: Context gmpContext = vanillaContext Stage1 integerGmp -gmpObjects :: FilePath -gmpObjects = gmpBuildPath -/- "objs" - -gmpLibrary :: FilePath -gmpLibrary = gmpBuildPath -/- "libgmp.a" - gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" -gmpLibraryH :: FilePath -gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" - gmpLibraryFakeH :: FilePath gmpLibraryFakeH = gmpBase -/- "ghc-gmp.h" diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 2b90d1f..0538e4e 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -11,7 +11,6 @@ import Expression import GHC import Oracles.PackageData import Rules.Actions -import Rules.Gmp import Settings import Target diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 01b3b16..7174a94 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,8 +1,8 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpBuildInfoPath, - packageDbDirectory, pkgConfFile, shakeFilesPath, bootPackageConstraints, - packageDependencies, libffiBuildPath + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibrary, gmpObjects, + gmpLibraryH, gmpBuildInfoPath, libffiBuildPath, shakeFilesPath, pkgConfFile, + packageDbDirectory, bootPackageConstraints, packageDependencies ) where import Base @@ -67,18 +67,30 @@ pkgFile context prefix suffix = do componentId <- pkgData $ ComponentId path return $ path ~/~ prefix ++ componentId ++ suffix --- | Build directory for in-tree libffi library. -libffiBuildPath :: FilePath -libffiBuildPath = buildRootPath -/- "stage1/libffi" - -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath gmpBuildPath = buildRootPath ~/~ "stage1/gmp" +-- | Path to the GMP library. +gmpLibrary :: FilePath +gmpLibrary = gmpBuildPath -/- "libgmp.a" + +-- | Path to the GMP library header. +gmpLibraryH :: FilePath +gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" + +-- | Path to the GMP library object files. +gmpObjects :: FilePath +gmpObjects = gmpBuildPath -/- "objs" + -- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath gmpBuildInfoPath = pkgPath integerGmp ~/~ "integer-gmp.buildinfo" +-- | Build directory for in-tree libffi library. +libffiBuildPath :: FilePath +libffiBuildPath = buildRootPath -/- "stage1/libffi" + -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory -- | Path to package database directory of a given 'Stage'. From git at git.haskell.org Fri Oct 27 00:29:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build internal ghci support in Stage1 (552bb90) Message-ID: <20171027002917.3B29B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/552bb90ed6b3408018c8c9952c5c0f1b28323694/ghc >--------------------------------------------------------------- commit 552bb90ed6b3408018c8c9952c5c0f1b28323694 Author: Andrey Mokhov Date: Sat Dec 31 01:03:52 2016 +0000 Build internal ghci support in Stage1 >--------------------------------------------------------------- 552bb90ed6b3408018c8c9952c5c0f1b28323694 hadrian.cabal | 1 + src/Settings/Default.hs | 2 ++ src/Settings/Packages/Ghci.hs | 7 +++++++ 3 files changed, 10 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 374b5a0..a186d7d 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -91,6 +91,7 @@ executable hadrian , Settings.Packages.Compiler , Settings.Packages.Ghc , Settings.Packages.GhcCabal + , Settings.Packages.Ghci , Settings.Packages.GhcPrim , Settings.Packages.Haddock , Settings.Packages.IntegerGmp diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index ba4ef79..37fcdfa 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -31,6 +31,7 @@ import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Ghc import Settings.Packages.GhcCabal +import Settings.Packages.Ghci import Settings.Packages.GhcPrim import Settings.Packages.Haddock import Settings.Packages.IntegerGmp @@ -196,6 +197,7 @@ defaultPackageArgs = mconcat , compilerPackageArgs , ghcPackageArgs , ghcCabalPackageArgs + , ghciPackageArgs , ghcPrimPackageArgs , haddockPackageArgs , integerGmpPackageArgs diff --git a/src/Settings/Packages/Ghci.hs b/src/Settings/Packages/Ghci.hs new file mode 100644 index 0000000..3d14691 --- /dev/null +++ b/src/Settings/Packages/Ghci.hs @@ -0,0 +1,7 @@ +module Settings.Packages.Ghci (ghciPackageArgs) where + +import GHC +import Predicate + +ghciPackageArgs :: Args +ghciPackageArgs = notStage0 ? package ghci ? builder GhcCabal ? arg "--flags=ghci" From git at git.haskell.org Fri Oct 27 00:29:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Show the candidates. (e4ed614) Message-ID: <20171027002919.4026F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4ed614de3a98ec374536032946802a37b96e85d/ghc >--------------------------------------------------------------- commit e4ed614de3a98ec374536032946802a37b96e85d Author: Moritz Angermann Date: Thu Jan 7 11:30:05 2016 +0800 Show the candidates. >--------------------------------------------------------------- e4ed614de3a98ec374536032946802a37b96e85d src/Oracles/WindowsRoot.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 473a235..0c45230 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -46,8 +46,9 @@ lookupInPath c | otherwise = do envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths in - -- this will crash if we do not find any valid candidate. - head <$> filterM doesFileExist candidates + mapM_ putStrLn candidates + -- this will crash if we do not find any valid candidate. + head <$> filterM doesFileExist candidates -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). From git at git.haskell.org Fri Oct 27 00:29:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Gmp and Libffi rules. (f0781a7) Message-ID: <20171027002919.8F5463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f0781a7c0c1124d7e0150298ca39b08a849ac338/ghc >--------------------------------------------------------------- commit f0781a7c0c1124d7e0150298ca39b08a849ac338 Author: Andrey Mokhov Date: Thu May 5 05:30:22 2016 +0100 Refactor Gmp and Libffi rules. >--------------------------------------------------------------- f0781a7c0c1124d7e0150298ca39b08a849ac338 src/Builder.hs | 9 ++++++++- src/Rules/Gmp.hs | 22 +++++++--------------- src/Rules/Libffi.hs | 18 +++++++----------- 3 files changed, 22 insertions(+), 27 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index fa76097..a205067 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric, LambdaCase #-} module Builder ( CompilerMode (..), Builder (..), - builderPath, getBuilderPath, specified, needBuilder + builderPath, getBuilderPath, builderEnvironment, specified, needBuilder ) where import Control.Monad.Trans.Reader @@ -134,6 +134,13 @@ builderPath builder = case builderProvenance builder of getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath +-- | Write a Builder's path into a given environment variable. +builderEnvironment :: String -> Builder -> Action CmdOption +builderEnvironment variable builder = do + needBuilder builder + path <- builderPath builder + return $ AddEnv variable path + specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 2de1878..1121d5d 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,6 +1,7 @@ module Rules.Gmp (gmpRules) where import Base +import Builder import Expression import GHC import Oracles.Config.Setting @@ -11,31 +12,22 @@ import Settings.Paths import Target gmpBase :: FilePath -gmpBase = "libraries/integer-gmp/gmp" +gmpBase = pkgPath integerGmp -/- "gmp" gmpContext :: Context gmpContext = vanillaContext Stage1 integerGmp +-- TODO: Noone needs this file, but we build it. Why? gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" -gmpLibraryFakeH :: FilePath -gmpLibraryFakeH = gmpBase -/- "ghc-gmp.h" - gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] --- TODO: See Libffi.hs about removing code duplication. configureEnvironment :: Action [CmdOption] -configureEnvironment = do - sequence [ builderEnv "CC" $ Cc Compile Stage1 - , builderEnv "AR" Ar - , builderEnv "NM" Nm ] - where - builderEnv var bld = do - needBuilder bld - path <- builderPath bld - return $ AddEnv var path +configureEnvironment = sequence [ builderEnvironment "CC" $ Cc Compile Stage1 + , builderEnvironment "AR" Ar + , builderEnvironment "NM" Nm ] -- TODO: we rebuild gmp every time. gmpRules :: Rules () @@ -53,7 +45,7 @@ gmpRules = do then do putBuild "| GMP library/framework detected and will be used" createDirectory $ takeDirectory gmpLibraryH - copyFile gmpLibraryFakeH gmpLibraryH + copyFile (gmpBase -/- "ghc-gmp.h") gmpLibraryH else do putBuild "| No GMP library/framework detected; in tree GMP will be built" diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 424b552..0a000aa 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,6 +1,7 @@ module Rules.Libffi (rtsBuildPath, libffiRules, libffiDependencies) where import Base +import Builder import Expression import GHC import Oracles.Config.Flag @@ -43,19 +44,14 @@ configureEnvironment = do [ cArgs , argStagedSettingList ConfCcArgs ] ldFlags <- interpretInContext libffiContext $ fromDiffExpr ldArgs - sequence [ builderEnv "CC" $ Cc Compile Stage1 - , builderEnv "CXX" $ Cc Compile Stage1 - , builderEnv "LD" Ld - , builderEnv "AR" Ar - , builderEnv "NM" Nm - , builderEnv "RANLIB" Ranlib + sequence [ builderEnvironment "CC" $ Cc Compile Stage1 + , builderEnvironment "CXX" $ Cc Compile Stage1 + , builderEnvironment "LD" Ld + , builderEnvironment "AR" Ar + , builderEnvironment "NM" Nm + , builderEnvironment "RANLIB" Ranlib , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w" , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ] - where - builderEnv var b = do - needBuilder b - path <- builderPath b - return $ AddEnv var path -- TODO: remove code duplication (need sourcePath) -- TODO: split into multiple rules From git at git.haskell.org Fri Oct 27 00:29:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build compact library (374b10a) Message-ID: <20171027002920.BB0073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/374b10aa7af36884484e05d7e6ac02295be60957/ghc >--------------------------------------------------------------- commit 374b10aa7af36884484e05d7e6ac02295be60957 Author: Andrey Mokhov Date: Sat Dec 31 01:04:40 2016 +0000 Build compact library >--------------------------------------------------------------- 374b10aa7af36884484e05d7e6ac02295be60957 src/GHC.hs | 33 ++++++++++++++++++--------------- src/Settings/Default.hs | 3 ++- 2 files changed, 20 insertions(+), 16 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 1fff56f..f8abeb8 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,13 +1,14 @@ {-# LANGUAGE OverloadedStrings, LambdaCase #-} {-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( - array, base, binary, bytestring, cabal, checkApiAnnotations, compiler, - containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, - filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, - ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, - hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, - parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, - terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, + array, base, binary, bytestring, cabal, checkApiAnnotations, compact, + compareSizes, compiler, containers, deepseq, deriveConstants, directory, + dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, + ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, + hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, + libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, + stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, + win32, xhtml, defaultKnownPackages, builderProvenance, programName, nonCabalContext, nonHsMainPackage @@ -25,13 +26,14 @@ import Stage -- be overridden in @hadrian/src/UserSettings.hs at . defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, binary, bytestring, cabal, checkApiAnnotations, compiler - , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci - , ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc - , hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart - , parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell - , terminfo, time, touchy, transformers, unlit, unix, win32, xhtml ] + [ array, base, binary, bytestring, cabal, checkApiAnnotations, compact + , compareSizes, compiler, containers, deepseq, deriveConstants, directory + , dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh + , ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs + , hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi + , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm + , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 + , xhtml ] -- | Package definitions, see 'Package'. array = library "array" @@ -40,9 +42,10 @@ binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" checkApiAnnotations = utility "check-api-annotations" +compact = library "compact" +compareSizes = utility "compareSizes" `setPath` "utils/compare_sizes" compiler = topLevel "ghc" `setPath` "compiler" containers = library "containers" -compareSizes = utility "compareSizes" `setPath` "utils/compare_sizes" deepseq = library "deepseq" deriveConstants = utility "deriveConstants" directory = library "directory" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 37fcdfa..67b0d5d 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -90,8 +90,9 @@ stage1Packages = do , append $ [ array , base , bytestring - , containers + , compact , compareSizes + , containers , deepseq , directory , filepath From git at git.haskell.org Fri Oct 27 00:29:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: :( (0fa71d1) Message-ID: <20171027002922.ECAE63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0fa71d10277a13d26c0f441745993f0a45ad5dc3/ghc >--------------------------------------------------------------- commit 0fa71d10277a13d26c0f441745993f0a45ad5dc3 Author: Moritz Angermann Date: Thu Jan 7 13:02:51 2016 +0800 :( >--------------------------------------------------------------- 0fa71d10277a13d26c0f441745993f0a45ad5dc3 src/Oracles/WindowsRoot.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 0c45230..6def89c 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -45,8 +45,8 @@ lookupInPath c | c /= takeFileName c = return c | otherwise = do envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" - let candidates = map (-/- c) envPaths in - mapM_ putStrLn candidates + let candidates = map (-/- c) envPaths + liftIO $ mapM_ putStrLn candidates -- this will crash if we do not find any valid candidate. head <$> filterM doesFileExist candidates From git at git.haskell.org Fri Oct 27 00:29:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (acf2160) Message-ID: <20171027002923.39BAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acf2160ea8c2ac705e32e4774c02ea7d806261f6/ghc >--------------------------------------------------------------- commit acf2160ea8c2ac705e32e4774c02ea7d806261f6 Author: Andrey Mokhov Date: Thu May 5 05:42:48 2016 +0100 Add comments. See #55. [skip ci] >--------------------------------------------------------------- acf2160ea8c2ac705e32e4774c02ea7d806261f6 src/Rules/Actions.hs | 15 +++++++++------ 1 file changed, 9 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index a312ce9..9a9e51e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -44,7 +44,7 @@ customBuild rs opts target at Target {..} = do argList <- interpret target getArgs verbose <- interpret target verboseCommands let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly - -- The line below forces the rule to be rerun if the args hash has changed + -- The line below forces the rule to be rerun if the args hash has changed. checkArgsHash target withResources rs $ do putInfo target @@ -76,19 +76,21 @@ customBuild rs opts target at Target {..} = do _ -> cmd [path] argList +-- | Run a builder, capture the standard output, and write it to a given file. captureStdout :: Target -> FilePath -> [String] -> Action () captureStdout target path argList = do file <- interpret target getOutput Stdout output <- cmd [path] argList writeFileChanged file output +-- | Copy a file tracking the source. copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target --- Note, moveFile cannot track the source, because it is moved. +-- | Move a file; we cannot track the source, because it is moved. moveFile :: FilePath -> FilePath -> Action () moveFile source target = do putProgressInfo $ renderAction "Move file" source target @@ -100,6 +102,7 @@ removeFile file = do putBuild $ "| Remove file " ++ file liftIO . whenM (IO.doesFileExist file) $ IO.removeFile file +-- | Create a directory if it does not already exist. createDirectory :: FilePath -> Action () createDirectory dir = do putBuild $ "| Create directory " ++ dir @@ -111,19 +114,19 @@ removeDirectory dir = do putBuild $ "| Remove directory " ++ dir liftIO . whenM (IO.doesDirectoryExist dir) $ IO.removeDirectoryRecursive dir --- Note, the source directory is untracked +-- | Copy a directory. The contents of the source directory is untracked. copyDirectory :: FilePath -> FilePath -> Action () copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd (EchoStdout False) ["cp", "-r", source, target] --- Note, the source directory is untracked +-- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target liftIO $ IO.renameDirectory source target --- Transform a given file by applying a function to its contents +-- | Transform a given file by applying a function to its contents. fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do putBuild $ "| Fix " ++ file @@ -171,7 +174,7 @@ makeExecutable file = do putBuild $ "| Make '" ++ file ++ "' executable." quietly $ cmd "chmod +x " [file] --- Print out key information about the command being executed +-- | Print out information about the command being executed. putInfo :: Target -> Action () putInfo Target {..} = putProgressInfo $ renderAction ("Run " ++ show builder ++ contextInfo) (digest inputs) (digest outputs) From git at git.haskell.org Fri Oct 27 00:29:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add perf flavour (6508f4b) Message-ID: <20171027002924.38BB93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6508f4b94dd9f0c476269191ce2a083856ef2d60/ghc >--------------------------------------------------------------- commit 6508f4b94dd9f0c476269191ce2a083856ef2d60 Author: Andrey Mokhov Date: Fri Jan 6 00:59:26 2017 +0000 Add perf flavour >--------------------------------------------------------------- 6508f4b94dd9f0c476269191ce2a083856ef2d60 hadrian.cabal | 1 + src/Settings.hs | 3 ++- src/Settings/Flavours/Perf.hs | 21 +++++++++++++++++++++ 3 files changed, 24 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index a186d7d..4f3c2f6 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -85,6 +85,7 @@ executable hadrian , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default + , Settings.Flavours.Perf , Settings.Flavours.Quick , Settings.Flavours.Quickest , Settings.Packages.Base diff --git a/src/Settings.hs b/src/Settings.hs index bef47f1..18dd15b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -14,6 +14,7 @@ import GHC import Oracles.PackageData import Oracles.Path import {-# SOURCE #-} Settings.Default +import Settings.Flavours.Perf import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Path @@ -50,7 +51,7 @@ getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getBuildPath hadrianFlavours :: [Flavour] -hadrianFlavours = [defaultFlavour, quickFlavour, quickestFlavour] +hadrianFlavours = [defaultFlavour, perfFlavour, quickFlavour, quickestFlavour] flavour :: Flavour flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours diff --git a/src/Settings/Flavours/Perf.hs b/src/Settings/Flavours/Perf.hs new file mode 100644 index 0000000..d246b15 --- /dev/null +++ b/src/Settings/Flavours/Perf.hs @@ -0,0 +1,21 @@ +module Settings.Flavours.Perf (perfFlavour) where + +import Context +import Flavour +import GHC +import Predicate +import {-# SOURCE #-} Settings.Default + +perfFlavour :: Flavour +perfFlavour = defaultFlavour + { name = "perf" + , args = defaultArgs <> perfArgs } + +optimise :: Context -> Bool +optimise Context {..} = + package `elem` [compiler, ghc] && stage == Stage2 || isLibrary package + +perfArgs :: Args +perfArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O2" else arg "-O" From git at git.haskell.org Fri Oct 27 00:29:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: :+1: (b47bd51) Message-ID: <20171027002926.C339A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b47bd516326d7d9652a1ba6d37352e01766390f2/ghc >--------------------------------------------------------------- commit b47bd516326d7d9652a1ba6d37352e01766390f2 Author: Moritz Angermann Date: Thu Jan 7 13:51:30 2016 +0800 :+1: >--------------------------------------------------------------- b47bd516326d7d9652a1ba6d37352e01766390f2 src/Builder.hs | 6 ++++-- src/Oracles/WindowsRoot.hs | 1 - 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 6e4dba5..0613452 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -95,8 +95,10 @@ builderPath builder = do putError $ "\nCannot find path to '" ++ (builderKey builder) ++ "' in configuration files." windows <- windowsHost - let path' = if null path then "" else path -<.> exe in - (if windows then fixAbsolutePathOnWindows else lookupInPath) path' + case (path, windows) of + ("", _) -> return path + (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) + (p, False) -> lookupInPath (p -<.> exe) getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 6def89c..4186700 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -46,7 +46,6 @@ lookupInPath c | otherwise = do envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths - liftIO $ mapM_ putStrLn candidates -- this will crash if we do not find any valid candidate. head <$> filterM doesFileExist candidates From git at git.haskell.org Fri Oct 27 00:29:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make only install target in libffi. (2249b40) Message-ID: <20171027002927.182C03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2249b4037ad429640404e79056efa4043888c9e3/ghc >--------------------------------------------------------------- commit 2249b4037ad429640404e79056efa4043888c9e3 Author: Andrey Mokhov Date: Thu May 5 05:57:20 2016 +0100 Make only install target in libffi. >--------------------------------------------------------------- 2249b4037ad429640404e79056efa4043888c9e3 src/Rules/Libffi.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0a000aa..8ca0bfc9 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -97,7 +97,7 @@ libffiRules = do Target libffiContext (Configure libffiBuildPath) [libffiMakefile <.> "in"] [libffiMakefile] - runMake libffiBuildPath ["MAKEFLAGS="] + --runMake libffiBuildPath ["MAKEFLAGS="] runMake libffiBuildPath ["MAKEFLAGS=", "install"] let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" From git at git.haskell.org Fri Oct 27 00:29:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing profiling flags (9c8d9bf) Message-ID: <20171027002927.A65E83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c8d9bf40b129f2faa8f50525c3fac5b322d808f/ghc >--------------------------------------------------------------- commit 9c8d9bf40b129f2faa8f50525c3fac5b322d808f Author: Andrey Mokhov Date: Fri Jan 6 01:59:23 2017 +0000 Add missing profiling flags >--------------------------------------------------------------- 9c8d9bf40b129f2faa8f50525c3fac5b322d808f src/Predicate.hs | 10 +++++++++- src/Settings/Packages/Compiler.hs | 3 +++ 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/src/Predicate.hs b/src/Predicate.hs index d38d9d5..5da5c54 100644 --- a/src/Predicate.hs +++ b/src/Predicate.hs @@ -2,7 +2,7 @@ -- | Convenient predicates module Predicate ( module Expression, stage, stage0, stage1, stage2, notStage0, builder, - package, notPackage, input, output, way + package, notPackage, input, inputs, output, outputs, way ) where import Base @@ -52,10 +52,18 @@ instance BuilderLike a => BuilderLike (FilePath -> a) where input :: FilePattern -> Predicate input f = any (f ?==) <$> getInputs +-- | Does any of the input files match any of the given patterns? +inputs :: [FilePattern] -> Predicate +inputs = anyM input + -- | Does any of the output files match a given pattern? output :: FilePattern -> Predicate output f = any (f ?==) <$> getOutputs +-- | Does any of the output files match any of the given patterns? +outputs :: [FilePattern] -> Predicate +outputs = anyM output + -- | Is the current build 'Way' equal to a certain value? way :: Way -> Predicate way w = (w ==) <$> getWay diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 308b3c2..9280a81 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -15,6 +15,9 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" + , builder (Ghc CompileHs) ? + inputs ["//GHC.hs", "//GhcMake.hs"] ? arg "-fprof-auto" + , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) , arg "--disable-library-for-ghci" From git at git.haskell.org Fri Oct 27 00:29:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix the old-time issue. (909ed08) Message-ID: <20171027002930.3F4BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/909ed08eea7d843c5fb6c022349b3afc10946b60/ghc >--------------------------------------------------------------- commit 909ed08eea7d843c5fb6c022349b3afc10946b60 Author: Andrey Mokhov Date: Thu Jan 7 09:24:05 2016 +0000 Fix the old-time issue. See #110. [skip ci] >--------------------------------------------------------------- 909ed08eea7d843c5fb6c022349b3afc10946b60 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7bcda85..da02948 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,7 +7,7 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - stack install alex happy shake ansi-terminal mtl + - echo "" | stack --no-terminal alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Fri Oct 27 00:29:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (6828f4a) Message-ID: <20171027002930.E97FB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6828f4af2d959e352415f7c6c89dd408e8409dcf/ghc >--------------------------------------------------------------- commit 6828f4af2d959e352415f7c6c89dd408e8409dcf Author: Andrey Mokhov Date: Thu May 5 13:07:07 2016 +0100 Add comments. >--------------------------------------------------------------- 6828f4af2d959e352415f7c6c89dd408e8409dcf src/Rules/Libffi.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 8ca0bfc9..20d5acf 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -97,7 +97,8 @@ libffiRules = do Target libffiContext (Configure libffiBuildPath) [libffiMakefile <.> "in"] [libffiMakefile] - --runMake libffiBuildPath ["MAKEFLAGS="] + -- The old build system did runMake libffiBuildPath ["MAKEFLAGS="] + -- TODO: Find out why. It seems redundant, so I removed it. runMake libffiBuildPath ["MAKEFLAGS=", "install"] let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" From git at git.haskell.org Fri Oct 27 00:29:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add prof flavour (bc44c00) Message-ID: <20171027002931.777943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc44c00792276d7834258db442af9fe687d22a01/ghc >--------------------------------------------------------------- commit bc44c00792276d7834258db442af9fe687d22a01 Author: Andrey Mokhov Date: Fri Jan 6 02:00:02 2017 +0000 Add prof flavour >--------------------------------------------------------------- bc44c00792276d7834258db442af9fe687d22a01 hadrian.cabal | 1 + src/Settings.hs | 4 +++- src/Settings/Flavours/Prof.hs | 21 +++++++++++++++++++++ 3 files changed, 25 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 4f3c2f6..712d4c6 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -86,6 +86,7 @@ executable hadrian , Settings.Builders.Tar , Settings.Default , Settings.Flavours.Perf + , Settings.Flavours.Prof , Settings.Flavours.Quick , Settings.Flavours.Quickest , Settings.Packages.Base diff --git a/src/Settings.hs b/src/Settings.hs index 18dd15b..8f94e5b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -15,6 +15,7 @@ import Oracles.PackageData import Oracles.Path import {-# SOURCE #-} Settings.Default import Settings.Flavours.Perf +import Settings.Flavours.Prof import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Path @@ -51,7 +52,8 @@ getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getBuildPath hadrianFlavours :: [Flavour] -hadrianFlavours = [defaultFlavour, perfFlavour, quickFlavour, quickestFlavour] +hadrianFlavours = [ defaultFlavour, perfFlavour, profFlavour, quickFlavour + , quickestFlavour ] flavour :: Flavour flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours diff --git a/src/Settings/Flavours/Prof.hs b/src/Settings/Flavours/Prof.hs new file mode 100644 index 0000000..4dee8fc --- /dev/null +++ b/src/Settings/Flavours/Prof.hs @@ -0,0 +1,21 @@ +module Settings.Flavours.Prof (profFlavour) where + +import Context +import Flavour +import GHC +import Predicate +import {-# SOURCE #-} Settings.Default + +profFlavour :: Flavour +profFlavour = defaultFlavour + { name = "prof" + , args = defaultArgs <> profArgs + , ghcProfiled = True } + +optimise :: Context -> Bool +optimise Context {..} = package `elem` [compiler, ghc] || isLibrary package + +profArgs :: Args +profArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O" else arg "-O0" From git at git.haskell.org Fri Oct 27 00:29:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Restore install argument to stack. (2ad773b) Message-ID: <20171027002933.BA2203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ad773b62f0558f6a83b585b543e3a0a847c2911/ghc >--------------------------------------------------------------- commit 2ad773b62f0558f6a83b585b543e3a0a847c2911 Author: Andrey Mokhov Date: Thu Jan 7 09:37:20 2016 +0000 Restore install argument to stack. See #110. [skip ci] >--------------------------------------------------------------- 2ad773b62f0558f6a83b585b543e3a0a847c2911 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index da02948..8f2e278 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -7,7 +7,7 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - echo "" | stack --no-terminal alex happy shake ansi-terminal mtl + - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Fri Oct 27 00:29:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Actions: use `mv` instead of renameDirectory (fixes #236) (d04a83f) Message-ID: <20171027002934.649653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d04a83ffa5a94de6215997229c6e4dc0afe21640/ghc >--------------------------------------------------------------- commit d04a83ffa5a94de6215997229c6e4dc0afe21640 Author: Michal Terepeta Date: Thu May 5 17:05:24 2016 +0200 Actions: use `mv` instead of renameDirectory (fixes #236) Implementing `moveDirectory` by calling into `renameDirectory` is problematic because it doesn't work across file-systems (e.g., a tmpfs based `/tmp`). This fixes the problem by calling into `mv` instead (similarly to what we do for `copyDirectory`). >--------------------------------------------------------------- d04a83ffa5a94de6215997229c6e4dc0afe21640 src/Rules/Actions.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9a9e51e..fd117ae 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -124,7 +124,7 @@ copyDirectory source target = do moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target - liftIO $ IO.renameDirectory source target + quietly $ cmd (EchoStdout False) ["mv", source, target] -- | Transform a given file by applying a function to its contents. fixFile :: FilePath -> (String -> String) -> Action () From git at git.haskell.org Fri Oct 27 00:29:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing flags for Parser module (3201312) Message-ID: <20171027002934.EEF4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3201312c71ea91128a11942ff66792f175bed255/ghc >--------------------------------------------------------------- commit 3201312c71ea91128a11942ff66792f175bed255 Author: Andrey Mokhov Date: Fri Jan 6 02:33:02 2017 +0000 Add missing flags for Parser module See #268 >--------------------------------------------------------------- 3201312c71ea91128a11942ff66792f175bed255 src/Settings/Flavours/Perf.hs | 2 +- src/Settings/Flavours/Prof.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/Quickest.hs | 2 +- src/Settings/Packages/Compiler.hs | 6 ++++-- 5 files changed, 8 insertions(+), 6 deletions(-) diff --git a/src/Settings/Flavours/Perf.hs b/src/Settings/Flavours/Perf.hs index d246b15..7641657 100644 --- a/src/Settings/Flavours/Perf.hs +++ b/src/Settings/Flavours/Perf.hs @@ -9,7 +9,7 @@ import {-# SOURCE #-} Settings.Default perfFlavour :: Flavour perfFlavour = defaultFlavour { name = "perf" - , args = defaultArgs <> perfArgs } + , args = defaultBuilderArgs <> perfArgs <> defaultPackageArgs } optimise :: Context -> Bool optimise Context {..} = diff --git a/src/Settings/Flavours/Prof.hs b/src/Settings/Flavours/Prof.hs index 4dee8fc..6d94b90 100644 --- a/src/Settings/Flavours/Prof.hs +++ b/src/Settings/Flavours/Prof.hs @@ -9,7 +9,7 @@ import {-# SOURCE #-} Settings.Default profFlavour :: Flavour profFlavour = defaultFlavour { name = "prof" - , args = defaultArgs <> profArgs + , args = defaultBuilderArgs <> profArgs <> defaultPackageArgs , ghcProfiled = True } optimise :: Context -> Bool diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 448a875..1e4f5c0 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -9,7 +9,7 @@ import {-# SOURCE #-} Settings.Default quickFlavour :: Flavour quickFlavour = defaultFlavour { name = "quick" - , args = defaultArgs <> quickArgs + , args = defaultBuilderArgs <> quickArgs <> defaultPackageArgs , libraryWays = defaultLibraryWays <> quickLibraryWays } optimise :: Context -> Bool diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 9f9b85b..477a245 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -7,7 +7,7 @@ import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour quickestFlavour = defaultFlavour { name = "quickest" - , args = defaultArgs <> quickestArgs + , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs , libraryWays = defaultLibraryWays <> quickestLibraryWays } quickestArgs :: Args diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 9280a81..8cc05cb 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -15,8 +15,10 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder (Ghc CompileHs) ? - inputs ["//GHC.hs", "//GhcMake.hs"] ? arg "-fprof-auto" + , builder (Ghc CompileHs) ? mconcat + [ inputs ["//GHC.hs", "//GhcMake.hs"] ? arg "-fprof-auto" + , input "//Parser.hs" ? + append ["-O0", "-fno-ignore-interface-pragmas", "-fcmm-sink" ] ] , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) From git at git.haskell.org Fri Oct 27 00:29:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve needBuilder, see #124. (360a4c3) Message-ID: <20171027002937.374533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/360a4c37f4060254157d19443a3b3c95b8c5b1c7/ghc >--------------------------------------------------------------- commit 360a4c37f4060254157d19443a3b3c95b8c5b1c7 Author: Andrey Mokhov Date: Thu Jan 7 09:37:52 2016 +0000 Improve needBuilder, see #124. >--------------------------------------------------------------- 360a4c37f4060254157d19443a3b3c95b8c5b1c7 src/Builder.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Builder.hs b/src/Builder.hs index 5ed9e1d..e4d8221 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -106,7 +106,7 @@ specified = fmap (not . null) . builderPath -- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). needBuilder :: Bool -> Builder -> Action () -needBuilder laxDependencies builder = do +needBuilder laxDependencies builder = whenM (specified builder) $ do path <- builderPath builder if laxDependencies && allowOrderOnlyDependency builder then orderOnly [path] From git at git.haskell.org Fri Oct 27 00:29:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #237 from michalt/movedirectory-fix/1 (e61bd40) Message-ID: <20171027002938.251AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e61bd4021b696a17c72c8d259adf55621f9c3959/ghc >--------------------------------------------------------------- commit e61bd4021b696a17c72c8d259adf55621f9c3959 Merge: 6828f4a d04a83f Author: Andrey Mokhov Date: Thu May 5 17:59:09 2016 +0100 Merge pull request #237 from michalt/movedirectory-fix/1 Actions: use `mv` instead of renameDirectory (fixes #236) >--------------------------------------------------------------- e61bd4021b696a17c72c8d259adf55621f9c3959 src/Rules/Actions.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:29:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (25a6441) Message-ID: <20171027002938.A54F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/25a64411df44615296349aec133c180b8f008762/ghc >--------------------------------------------------------------- commit 25a64411df44615296349aec133c180b8f008762 Author: Andrey Mokhov Date: Fri Jan 6 02:59:20 2017 +0000 Minor revision >--------------------------------------------------------------- 25a64411df44615296349aec133c180b8f008762 src/Settings/Packages/Rts.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 7d844fa..8e71c87 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -56,7 +56,7 @@ rtsPackageArgs = package rts ? do , way == threaded ? arg "-DTHREADED_RTS" - , (input "//RtsMessages.c" ||^ input "//Trace.c") ? + , inputs ["//RtsMessages.c", "//Trace.c"] ? arg ("-DProjectVersion=" ++ show projectVersion) , input "//RtsUtils.c" ? append @@ -76,11 +76,10 @@ rtsPackageArgs = package rts ? do , "-DGhcUnregisterised=" ++ show ghcUnreg , "-DGhcEnableTablesNextToCode=" ++ show ghcEnableTNC ] - , input "//Evac.c" ? arg "-funroll-loops" - , input "//Evac_thr.c" ? arg "-funroll-loops" + , inputs ["//Evac.c", "//Evac_thr.c"] ? arg "-funroll-loops" - , input "//Evac_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] - , input "//Scav_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] ] + , inputs ["//Evac_thr.c", "//Scav_thr.c"] ? + append [ "-DPARALLEL_GC", "-Irts/sm" ] ] , builder Ghc ? arg "-Irts" From git at git.haskell.org Fri Oct 27 00:29:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Prepend to configure. (39c3486) Message-ID: <20171027002940.BC29E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39c34860df442efeb8e4c185d92549d828255191/ghc >--------------------------------------------------------------- commit 39c34860df442efeb8e4c185d92549d828255191 Author: Andrey Mokhov Date: Thu Jan 7 10:12:13 2016 +0000 Prepend to configure. See #110. [skip ci] >--------------------------------------------------------------- 39c34860df442efeb8e4c185d92549d828255191 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 8f2e278..a5763cc 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,5 +14,5 @@ install: build_script: - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload" - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:29:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot and configure via Hadrian (13f3e0c) Message-ID: <20171027002941.D51B23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13f3e0c5cb075eb22785886be439f8235009b766/ghc >--------------------------------------------------------------- commit 13f3e0c5cb075eb22785886be439f8235009b766 Author: Andrey Mokhov Date: Thu May 5 20:20:38 2016 +0100 Run boot and configure via Hadrian [skip ci] >--------------------------------------------------------------- 13f3e0c5cb075eb22785886be439f8235009b766 doc/windows.md | 3 --- 1 file changed, 3 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 7afd97c..79dfcc2 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -11,8 +11,6 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ cd ghc stack exec -- git clone git://github.com/snowleopard/hadrian stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec -- perl boot - stack exec -- bash configure --enable-tarballs-autodownload stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j The entire process should take about an hour. @@ -21,6 +19,5 @@ The entire process should take about an hour. Here are some alternatives that have been considered, but not yet tested. Use the instructions above. -* Use `hadrian/build.bat --setup` to replace `boot` and `configure`. * The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. * Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:29:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move -Wall before custom package settings, drop tab warnings (ab1c922) Message-ID: <20171027002942.4B2093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ab1c922d6531519e91ebed34b47070ba6fdc4170/ghc >--------------------------------------------------------------- commit ab1c922d6531519e91ebed34b47070ba6fdc4170 Author: Andrey Mokhov Date: Fri Jan 6 16:34:21 2017 +0000 Move -Wall before custom package settings, drop tab warnings See #296 >--------------------------------------------------------------- ab1c922d6531519e91ebed34b47070ba6fdc4170 src/Settings/Builders/Ghc.hs | 5 ++--- src/Settings/Default.hs | 5 +---- 2 files changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index f5b13e1..98e5e39 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -7,12 +7,11 @@ import Settings.Builders.Common ghcBuilderArgs :: Args ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do needTouchy - mconcat [ commonGhcArgs + mconcat [ arg "-Wall" + , commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" , notStage0 ? arg "-O2" - , arg "-Wall" - , arg "-fwarn-tabs" , splitObjectsArgs , ghcLinkArgs , builder (Ghc CompileHs) ? arg "-c" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 67b0d5d..061d4ae 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -41,10 +41,7 @@ import UserSettings -- | All default command line arguments. defaultArgs :: Args -defaultArgs = mconcat - [ defaultBuilderArgs - , defaultPackageArgs - , builder Ghc ? remove ["-Wall", "-fwarn-tabs"] ] -- TODO: Fix warning Args. +defaultArgs = defaultBuilderArgs <> defaultPackageArgs -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". From git at git.haskell.org Fri Oct 27 00:29:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Oracle (aff54c8) Message-ID: <20171027002944.511A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aff54c850f52d875105564d9ef2ec5662cc6c5b2/ghc >--------------------------------------------------------------- commit aff54c850f52d875105564d9ef2ec5662cc6c5b2 Author: Moritz Angermann Date: Thu Jan 7 18:47:46 2016 +0800 Adds Oracle >--------------------------------------------------------------- aff54c850f52d875105564d9ef2ec5662cc6c5b2 shaking-up-ghc.cabal | 2 +- src/Oracles.hs | 2 ++ src/Oracles/AbsoluteCommand.hs | 40 ++++++++++++++++++++++++++++++++++++++++ src/Oracles/WindowsRoot.hs | 13 +------------ src/Rules/Oracles.hs | 15 ++++++++------- 5 files changed, 52 insertions(+), 20 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f9990e9..96efe57 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -22,6 +22,7 @@ executable ghc-shake , Expression , GHC , Oracles + , Oracles.AbsoluteCommand , Oracles.ArgsHash , Oracles.Config , Oracles.Config.Flag @@ -114,7 +115,6 @@ executable ghc-shake , extra >= 1.4 , mtl >= 2.2 , shake >= 0.15 - , split >= 0.2 , transformers >= 0.4 , unordered-containers >= 0.2 default-language: Haskell2010 diff --git a/src/Oracles.hs b/src/Oracles.hs index b77a786..07e92f2 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,4 +1,5 @@ module Oracles ( + module Oracles.AbsoluteCommand, module Oracles.Config, module Oracles.Config.Flag, module Oracles.Config.Setting, @@ -8,6 +9,7 @@ module Oracles ( module Oracles.WindowsRoot ) where +import Oracles.AbsoluteCommand import Oracles.Config import Oracles.Config.Flag import Oracles.Config.Setting diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/AbsoluteCommand.hs new file mode 100644 index 0000000..23de6ff --- /dev/null +++ b/src/Oracles/AbsoluteCommand.hs @@ -0,0 +1,40 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +module Oracles.AbsoluteCommand ( + lookupInPath, absoluteCommandOracle + ) where + +import Base + +newtype AbsoluteCommand = AbsoluteCommand String + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +absoluteCommand :: String -> Action String +absoluteCommand = askOracle . AbsoluteCommand + +-- | Lookup a @command@ in @PATH@ environment. +lookupInPath :: FilePath -> Action FilePath +lookupInPath c + | c /= takeFileName c = return c + | otherwise = absoluteCommand c + +-- | Split function. Splits a string @s@ into chunks +-- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 +wordsWhen :: (Char -> Bool) -> String -> [String] +wordsWhen p s = + case dropWhile p s of + "" -> [] + s' -> w : wordsWhen p s'' + where (w, s'') = break p s' + + +absoluteCommandOracle :: Rules () +absoluteCommandOracle = do + o <- newCache $ \c -> do + envPaths <- wordsWhen (== ':') <$> getEnvWithDefault "" "PATH" + let candidates = map (-/- c) envPaths + -- this will crash if we do not find any valid candidate. + fullCommand <- head <$> filterM doesFileExist candidates + putOracle $ "Found '" ++ c ++ "' at " ++ "'" ++ fullCommand ++ "'" + return fullCommand + _ <- addOracle $ \(AbsoluteCommand c) -> o c + return () diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs index 4186700..413f289 100644 --- a/src/Oracles/WindowsRoot.hs +++ b/src/Oracles/WindowsRoot.hs @@ -1,10 +1,9 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.WindowsRoot ( - windowsRoot, fixAbsolutePathOnWindows, lookupInPath, topDirectory, windowsRootOracle + windowsRoot, fixAbsolutePathOnWindows, topDirectory, windowsRootOracle ) where import Data.Char (isSpace) -import Data.List.Split (splitOn) import Base import Oracles.Config.Setting @@ -39,16 +38,6 @@ fixAbsolutePathOnWindows path = do else return path --- | Lookup a @command@ in @PATH@ environment. -lookupInPath :: FilePath -> Action FilePath -lookupInPath c - | c /= takeFileName c = return c - | otherwise = do - envPaths <- splitOn ":" <$> getEnvWithDefault "" "PATH" - let candidates = map (-/- c) envPaths - -- this will crash if we do not find any valid candidate. - head <$> filterM doesFileExist candidates - -- Oracle for windowsRoot. This operation requires caching as looking up -- the root is slow (at least the current implementation). windowsRootOracle :: Rules () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 92e8a40..a4d6c70 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -7,10 +7,11 @@ import Oracles.ModuleFiles oracleRules :: Rules () oracleRules = do - argsHashOracle -- see Oracles.ArgsHash - configOracle -- see Oracles.Config - dependenciesOracle -- see Oracles.Dependencies - moduleFilesOracle -- see Oracles.ModuleFiles - packageDataOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - windowsRootOracle -- see Oracles.WindowsRoot + absoluteCommandOracle -- see Oracles.WindowsRoot + argsHashOracle -- see Oracles.ArgsHash + configOracle -- see Oracles.Config + dependenciesOracle -- see Oracles.Dependencies + moduleFilesOracle -- see Oracles.ModuleFiles + packageDataOracle -- see Oracles.PackageData + packageDepsOracle -- see Oracles.PackageDeps + windowsRootOracle -- see Oracles.WindowsRoot From git at git.haskell.org Fri Oct 27 00:29:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use --flavour=quick (da2ce2e) Message-ID: <20171027002945.4C7613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da2ce2e21529a6e9a4c2dcc8a033996bdca33be5/ghc >--------------------------------------------------------------- commit da2ce2e21529a6e9a4c2dcc8a033996bdca33be5 Author: Andrey Mokhov Date: Fri May 6 00:18:12 2016 +0100 Use --flavour=quick See #234. [skip ci] >--------------------------------------------------------------- da2ce2e21529a6e9a4c2dcc8a033996bdca33be5 doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 79dfcc2..4674ff4 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -11,9 +11,9 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ cd ghc stack exec -- git clone git://github.com/snowleopard/hadrian stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j + stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quick -The entire process should take about an hour. +The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quick` flag from the last command line (this will slow down the build to about an hour). #### Future ideas From git at git.haskell.org Fri Oct 27 00:29:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Duplicate libffi library for each build way (c88fc78) Message-ID: <20171027002945.BE28B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c88fc78440eb105ba5fe7d9a8bede47b30de36d6/ghc >--------------------------------------------------------------- commit c88fc78440eb105ba5fe7d9a8bede47b30de36d6 Author: Andrey Mokhov Date: Sat Jan 7 02:50:04 2017 +0000 Duplicate libffi library for each build way >--------------------------------------------------------------- c88fc78440eb105ba5fe7d9a8bede47b30de36d6 src/Rules/Libffi.hs | 4 ++-- src/Settings/Packages/Rts.hs | 11 +++++++++-- 2 files changed, 11 insertions(+), 4 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 65ec1d7..0f703d9 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -55,8 +55,8 @@ libffiRules = do forM_ hs $ \header -> copyFile header (rtsBuildPath -/- takeFileName header) - libffiName <- rtsLibffiLibraryName - copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") + ways <- interpretInContext libffiContext (getLibraryWays <> getRtsWays) + forM_ ways $ \way -> copyFile libffiLibrary =<< rtsLibffiLibrary way putSuccess $ "| Successfully built custom library 'libffi'" diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 8e71c87..e8000c8 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,4 +1,4 @@ -module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibraryName) where +module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibrary) where import Base import GHC @@ -7,6 +7,7 @@ import Oracles.Config.Setting import Oracles.Path import Predicate import Settings +import Settings.Path rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do @@ -17,6 +18,12 @@ rtsLibffiLibraryName = do (False, False) -> "Cffi" (_ , True ) -> "Cffi-6" +rtsLibffiLibrary :: Way -> Action FilePath +rtsLibffiLibrary way = do + name <- rtsLibffiLibraryName + suf <- libsuf way + return $ rtsBuildPath -/- "lib" ++ name ++ suf + rtsPackageArgs :: Args rtsPackageArgs = package rts ? do let yesNo = lift . fmap (\x -> if x then "YES" else "NO") @@ -38,7 +45,7 @@ rtsPackageArgs = package rts ? do way <- getWay path <- getBuildPath top <- getTopDirectory - libffiName <- lift $ rtsLibffiLibraryName + libffiName <- lift rtsLibffiLibraryName ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir mconcat From git at git.haskell.org Fri Oct 27 00:29:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Escape echo quotes. (9024712) Message-ID: <20171027002947.B6F0D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/902471256bf5aee2974afb968f0cf5bdbd8cae78/ghc >--------------------------------------------------------------- commit 902471256bf5aee2974afb968f0cf5bdbd8cae78 Author: Andrey Mokhov Date: Thu Jan 7 10:54:09 2016 +0000 Escape echo quotes. See #110. [skip ci] >--------------------------------------------------------------- 902471256bf5aee2974afb968f0cf5bdbd8cae78 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index a5763cc..f74c459 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,5 +14,5 @@ install: build_script: - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:29:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix way-specific flags (8e7685c) Message-ID: <20171027002949.3B4313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e7685c496e1ef4627d3f3b9d0850e6d5b487e07/ghc >--------------------------------------------------------------- commit 8e7685c496e1ef4627d3f3b9d0850e6d5b487e07 Author: Andrey Mokhov Date: Sat Jan 7 02:50:41 2017 +0000 Fix way-specific flags >--------------------------------------------------------------- 8e7685c496e1ef4627d3f3b9d0850e6d5b487e07 src/Settings/Packages/Rts.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e8000c8..6855402 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -61,7 +61,10 @@ rtsPackageArgs = package rts ? do -- be inlined. See also #90. , arg "-O2" - , way == threaded ? arg "-DTHREADED_RTS" + , Debug `wayUnit` way ? arg "-DDEBUG" + , way `elem` [debug, debugDynamic] ? arg "-DTICKY_TICKY" + , Profiling `wayUnit` way ? arg "-DPROFILING" + , Threaded `wayUnit` way ? arg "-DTHREADED_RTS" , inputs ["//RtsMessages.c", "//Trace.c"] ? arg ("-DProjectVersion=" ++ show projectVersion) From git at git.haskell.org Fri Oct 27 00:29:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on automated run of boot and configure (6864e8b) Message-ID: <20171027002948.BABD53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6864e8b3d1d1e89b7f37f816caf6851d6052d930/ghc >--------------------------------------------------------------- commit 6864e8b3d1d1e89b7f37f816caf6851d6052d930 Author: Andrey Mokhov Date: Sat May 7 11:46:35 2016 +0100 Add a note on automated run of boot and configure See #234. [skip ci] >--------------------------------------------------------------- 6864e8b3d1d1e89b7f37f816caf6851d6052d930 README.md | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index e0053b0..a8ca935 100644 --- a/README.md +++ b/README.md @@ -25,8 +25,8 @@ follow these steps: * This build system is written in Haskell (obviously) and depends on the following Haskell packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. -* Get the sources and run standard configuration scripts. It is important for the build -system to be in the `hadrian` directory of the GHC source tree: +* Get the sources. It is important for the build system to be in the `hadrian` directory +of the GHC source tree: ```bash git clone --recursive git://git.haskell.org/ghc.git @@ -38,7 +38,10 @@ system to be in the `hadrian` directory of the GHC source tree: of `make`. You might want to enable parallelism with `-j`. We will further refer to the build script simply as `build`. If you are interested in building in a Cabal sandbox or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Also -see [instructions for building GHC on Windows using Stack][windows-build]. +see [instructions for building GHC on Windows using Stack][windows-build]. Note, Hadrian +runs the `boot` and `configure` scripts automatically on the first build, so that you don't +need to. Use `--skip-configure` to suppress this behaviour (see overview of command line +flags below). Using the build system ---------------------- @@ -52,10 +55,13 @@ currently supports several others: * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations and disables library profiling, which speeds up builds by 3-4x). + * `--haddock`: build Haddock documentation. + * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). + * `--skip-configure`: use this flag to suppress the default behaviour of Hadrian that runs the `boot` and `configure` scripts automatically if need be, so that you don't have to remember to run them manually. With `--skip-configure` you will need to manually run: @@ -67,6 +73,7 @@ to remember to run them manually. With `--skip-configure` you will need to manua as you normally do when using `make`. Beware, by default Hadrian may do network I/O on Windows to download necessary tarballs, which may sometimes be undesirable; `--skip-configure` is your friend in such cases. + * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. From git at git.haskell.org Fri Oct 27 00:29:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Call bash with single quotes. (b54121d) Message-ID: <20171027002951.81B573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b54121d141b55b7b81d5be6e4a2571ab27756fd3/ghc >--------------------------------------------------------------- commit b54121d141b55b7b81d5be6e4a2571ab27756fd3 Author: Andrey Mokhov Date: Thu Jan 7 11:15:24 2016 +0000 Call bash with single quotes. See #110. [skip ci] >--------------------------------------------------------------- b54121d141b55b7b81d5be6e4a2571ab27756fd3 .appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f74c459..c3c4869 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -5,14 +5,14 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" + - bash -lc 'curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1' - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - bash -lc 'mv /home/ghc/tmp/* /home/ghc' build_script: - - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" - - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" + - bash -lc 'cd /home/ghc && ./boot' + - bash -lc 'cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload' + - bash -lc 'cd /home/ghc && ./shake-build/build.bat -j --no-progress' From git at git.haskell.org Fri Oct 27 00:29:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Echo stdout only if --progress-info={normal, unicorn}. (6ef09f4) Message-ID: <20171027002952.E2A453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6ef09f44f4c6128971ecaafda61b22cb0befa35c/ghc >--------------------------------------------------------------- commit 6ef09f44f4c6128971ecaafda61b22cb0befa35c Author: Andrey Mokhov Date: Mon May 9 23:31:47 2016 +0100 Echo stdout only if --progress-info={normal, unicorn}. See #235. >--------------------------------------------------------------- 6ef09f44f4c6128971ecaafda61b22cb0befa35c src/Rules/Actions.hs | 27 +++++++++++---------------- src/Rules/Test.hs | 2 +- 2 files changed, 12 insertions(+), 17 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index fd117ae..4928e00 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,8 @@ module Rules.Actions ( build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, removeFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, - applyPatch, fixFile, runMake, runMakeVerbose, renderLibrary, renderProgram, - runBuilder, makeExecutable + applyPatch, fixFile, runMake, renderLibrary, renderProgram, runBuilder, + makeExecutable ) where import qualified System.Directory as IO @@ -62,7 +62,7 @@ customBuild rs opts target at Target {..} = do need [dir -/- "configure"] -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" - cmd Shell [Cwd dir] [path] (env:opts) argList + cmd Shell cmdEcho env [Cwd dir] [path] opts argList HsCpp -> captureStdout target path argList GenApply -> captureStdout target path argList @@ -76,6 +76,9 @@ customBuild rs opts target at Target {..} = do _ -> cmd [path] argList +cmdEcho :: CmdOption +cmdEcho = EchoStdout $ cmdProgressInfo `elem` [Normal, Unicorn] + -- | Run a builder, capture the standard output, and write it to a given file. captureStdout :: Target -> FilePath -> [String] -> Action () captureStdout target path argList = do @@ -118,13 +121,13 @@ removeDirectory dir = do copyDirectory :: FilePath -> FilePath -> Action () copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target - quietly $ cmd (EchoStdout False) ["cp", "-r", source, target] + quietly $ cmd cmdEcho ["cp", "-r", source, target] -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target - quietly $ cmd (EchoStdout False) ["mv", source, target] + quietly $ cmd cmdEcho ["mv", source, target] -- | Transform a given file by applying a function to its contents. fixFile :: FilePath -> (String -> String) -> Action () @@ -138,20 +141,12 @@ fixFile file f = do liftIO $ writeFile file contents runMake :: FilePath -> [String] -> Action () -runMake = runMakeWithVerbosity False - -runMakeVerbose :: FilePath -> [String] -> Action () -runMakeVerbose = runMakeWithVerbosity True - -runMakeWithVerbosity :: Bool -> FilePath -> [String] -> Action () -runMakeWithVerbosity verbose dir args = do +runMake dir args = do need [dir -/- "Makefile"] path <- builderPath Make let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - if verbose - then cmd Shell path ["-C", dir] args - else quietly $ cmd Shell (EchoStdout False) path ["-C", dir] args + quietly $ cmd Shell cmdEcho path ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do @@ -159,7 +154,7 @@ applyPatch dir patch = do needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file - quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] + quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 7faf62d..544b5d9 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -18,7 +18,7 @@ testRules = do needBuilder $ Ghc Compile Stage2 needBuilder $ GhcPkg Stage1 needBuilder Hpc - runMakeVerbose "testsuite/tests" ["fast"] + runMake "testsuite/tests" ["fast"] "test" ~> do let yesNo x = show $ if x then "YES" else "NO" From git at git.haskell.org Fri Oct 27 00:29:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix profiled GHC (76de227) Message-ID: <20171027002953.369A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/76de227586804a1bf4b4a98e0307f09966348609/ghc >--------------------------------------------------------------- commit 76de227586804a1bf4b4a98e0307f09966348609 Author: Andrey Mokhov Date: Sat Jan 7 02:55:48 2017 +0000 Fix profiled GHC See #239 >--------------------------------------------------------------- 76de227586804a1bf4b4a98e0307f09966348609 src/Rules.hs | 7 ++++--- src/Rules/Program.hs | 7 +++---- src/Settings.hs | 7 ++++++- 3 files changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 832bf4c..be7c89b 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -49,7 +49,7 @@ topLevelTargets = do docs <- interpretInContext context $ buildHaddock flavour need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else do -- otherwise build a program - need =<< maybeToList <$> programPath context + need =<< maybeToList <$> programPath (programContext stage pkg) packageRules :: Rules () packageRules = do @@ -61,21 +61,22 @@ packageRules = do let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] - -- TODO: not all build rules make sense for all stage/package combinations let contexts = liftM3 Context allStages knownPackages allWays vanillaContexts = liftM2 vanillaContext allStages knownPackages + programContexts = liftM2 programContext allStages knownPackages forM_ contexts $ mconcat [ Rules.Compile.compilePackage readPackageDb , Rules.Library.buildPackageLibrary ] + forM_ programContexts $ Rules.Program.buildProgram readPackageDb + forM_ vanillaContexts $ mconcat [ Rules.Data.buildPackageData , Rules.Dependencies.buildPackageDependencies readPackageDb , Rules.Documentation.buildPackageDocumentation , Rules.Library.buildPackageGhciLibrary , Rules.Generate.generatePackageCode - , Rules.Program.buildProgram readPackageDb , Rules.Register.registerPackage writePackageDb ] buildRules :: Rules () diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 319ca72..92aa4c1 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -30,7 +30,7 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do let installStage = do - latest <- latestBuildStage package -- isJust below is safe + latest <- latestBuildStage package -- fromJust below is safe return $ if package == ghc then stage else fromJust latest buildPath context -/- programName context <.> exe %> @@ -68,15 +68,14 @@ buildWrapper context at Context {..} wrapper wrapperPath binPath = do quote (pkgNameString package) ++ " (" ++ show stage ++ ")." -- TODO: Get rid of the Paths_hsc2hs.o hack. --- TODO: Do we need to consider other ways when building programs? buildBinary :: [(Resource, Int)] -> Context -> FilePath -> Action () buildBinary rs context at Context {..} bin = do binDeps <- if stage == Stage0 && package == ghcCabal then hsSources context else do - ways <- interpretInContext context getLibraryWays deps <- contextDependencies context - needContext [ dep { way = w } | dep <- deps, w <- ways ] + ways <- interpretInContext context (getLibraryWays <> getRtsWays) + needContext $ deps ++ [ rtsContext { way = w } | w <- ways ] let path = buildPath context cObjs <- map (objectPath context) <$> pkgDataList (CSrcs path) hsObjs <- hsObjects context diff --git a/src/Settings.hs b/src/Settings.hs index 8f94e5b..c455e0b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,7 +2,7 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, getContextDirectory, getBuildPath, stagePackages, builderPath, - getBuilderPath, isSpecified, latestBuildStage, programPath + getBuilderPath, isSpecified, latestBuildStage, programPath, programContext ) where import Base @@ -62,6 +62,11 @@ flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours flavours = hadrianFlavours ++ userFlavours flavourName = fromMaybe "default" cmdFlavour +programContext :: Stage -> Package -> Context +programContext stage pkg + | pkg == ghc && ghcProfiled flavour = Context stage pkg profiling + | otherwise = vanillaContext stage pkg + -- TODO: switch to Set Package as the order of packages should not matter? -- Otherwise we have to keep remembering to sort packages from time to time. knownPackages :: [Package] From git at git.haskell.org Fri Oct 27 00:29:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing generated dependencies for rts, see #123. (f187ca8) Message-ID: <20171027002954.EAFFD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f187ca8af97a2a45a3a1d09b87dbdc12d4819987/ghc >--------------------------------------------------------------- commit f187ca8af97a2a45a3a1d09b87dbdc12d4819987 Author: Andrey Mokhov Date: Thu Jan 7 11:20:36 2016 +0000 Fix missing generated dependencies for rts, see #123. >--------------------------------------------------------------- f187ca8af97a2a45a3a1d09b87dbdc12d4819987 src/Rules/Data.hs | 5 ++--- src/Rules/Generate.hs | 2 +- 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 29f8d3d..ee15c19 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -104,9 +104,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do fullTarget target (GhcPkg stage) [rtsConf] [] rtsConf %> \_ -> do - need [ rtsConfIn - , "includes/ghcautoconf.h" - , "includes/ghcplatform.h" ] + orderOnly $ generatedDependencies stage pkg + need [ rtsConfIn ] build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] let fixRtsConf = unlines diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 3eb1231..8ca7b94 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -76,7 +76,7 @@ generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == ghcPrim = ghcPrimDependencies stage - | pkg == rts = derivedConstantsDependencies + | pkg == rts = includesDependencies ++ derivedConstantsDependencies | stage == Stage0 = defaultDependencies | otherwise = [] From git at git.haskell.org Fri Oct 27 00:29:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on RTS only when building GHC program (3ae4e1d) Message-ID: <20171027002956.CE0B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ae4e1d0016ae2c28030da32180e5a5bda18de57/ghc >--------------------------------------------------------------- commit 3ae4e1d0016ae2c28030da32180e5a5bda18de57 Author: Andrey Mokhov Date: Sat Jan 7 03:22:41 2017 +0000 Depend on RTS only when building GHC program >--------------------------------------------------------------- 3ae4e1d0016ae2c28030da32180e5a5bda18de57 src/Rules/Program.hs | 7 ++++--- src/Settings/Flavours/Quickest.hs | 6 ++---- 2 files changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 92aa4c1..b1577e2 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -73,9 +73,10 @@ buildBinary rs context at Context {..} bin = do binDeps <- if stage == Stage0 && package == ghcCabal then hsSources context else do - deps <- contextDependencies context - ways <- interpretInContext context (getLibraryWays <> getRtsWays) - needContext $ deps ++ [ rtsContext { way = w } | w <- ways ] + needContext =<< contextDependencies context + when (package == ghc) $ do + ways <- interpretInContext context (getLibraryWays <> getRtsWays) + needContext [ rtsContext { way = w } | w <- ways ] let path = buildPath context cObjs <- map (objectPath context) <$> pkgDataList (CSrcs path) hsObjs <- hsObjects context diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 477a245..9f95957 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -8,10 +8,8 @@ quickestFlavour :: Flavour quickestFlavour = defaultFlavour { name = "quickest" , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs - , libraryWays = defaultLibraryWays <> quickestLibraryWays } + , libraryWays = append [vanilla] + , rtsWays = append [vanilla] } quickestArgs :: Args quickestArgs = builder Ghc ? arg "-O0" - -quickestLibraryWays :: Ways -quickestLibraryWays = remove [profiling] From git at git.haskell.org Fri Oct 27 00:29:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Make builder. (f31a7de) Message-ID: <20171027002956.7E1263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f31a7de2d4a6886edc64ff5bfb3301bbdee7cc2c/ghc >--------------------------------------------------------------- commit f31a7de2d4a6886edc64ff5bfb3301bbdee7cc2c Author: Andrey Mokhov Date: Tue May 10 00:32:04 2016 +0100 Add Make builder. >--------------------------------------------------------------- f31a7de2d4a6886edc64ff5bfb3301bbdee7cc2c hadrian.cabal | 1 + src/Builder.hs | 4 ++-- src/Rules/Actions.hs | 19 +++++++------------ src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Test.hs | 5 +++-- src/Settings/Args.hs | 2 ++ 7 files changed, 17 insertions(+), 18 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 160a5d0..2dfd9e9 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -84,6 +84,7 @@ executable hadrian , Settings.Builders.Hsc2Hs , Settings.Builders.HsCpp , Settings.Builders.Ld + , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default , Settings.Packages diff --git a/src/Builder.hs b/src/Builder.hs index a205067..76f0988 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -49,7 +49,7 @@ data Builder = Alex | HsCpp | Hsc2Hs | Ld - | Make + | Make FilePath | Nm | Objdump | Patch @@ -111,7 +111,7 @@ builderPath builder = case builderProvenance builder of HsColour -> fromKey "hscolour" HsCpp -> fromKey "hs-cpp" Ld -> fromKey "ld" - Make -> fromKey "make" + Make _ -> fromKey "make" Nm -> fromKey "nm" Objdump -> fromKey "objdump" Patch -> fromKey "patch" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 4928e00..4a0844b 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,7 @@ module Rules.Actions ( - build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, - removeFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, - applyPatch, fixFile, runMake, renderLibrary, renderProgram, runBuilder, - makeExecutable + build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, + removeFile, copyDirectory, createDirectory, moveDirectory, removeDirectory, + applyPatch, renderLibrary, renderProgram, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -74,6 +73,10 @@ customBuild rs opts target at Target {..} = do Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output + Make dir -> do + need [dir -/- "Makefile"] + cmd Shell cmdEcho path ["-C", dir] argList + _ -> cmd [path] argList cmdEcho :: CmdOption @@ -140,14 +143,6 @@ fixFile file f = do return new liftIO $ writeFile file contents -runMake :: FilePath -> [String] -> Action () -runMake dir args = do - need [dir -/- "Makefile"] - path <- builderPath Make - let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell cmdEcho path ["-C", dir] args - applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1121d5d..fe5b684 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -84,7 +84,7 @@ gmpRules = do [gmpBuildPath -/- "Makefile.in"] [gmpBuildPath -/- "Makefile"] - runMake gmpBuildPath ["MAKEFLAGS="] + build $ Target gmpContext (Make gmpBuildPath) [] [] createDirectory $ takeDirectory gmpLibraryH copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 20d5acf..3269a31 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -99,7 +99,7 @@ libffiRules = do -- The old build system did runMake libffiBuildPath ["MAKEFLAGS="] -- TODO: Find out why. It seems redundant, so I removed it. - runMake libffiBuildPath ["MAKEFLAGS=", "install"] + build $ Target libffiContext (Make libffiBuildPath) [] [] let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" forM_ ["ffi.h", "ffitarget.h"] $ \file -> do diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 544b5d9..7ec5e04 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -3,13 +3,14 @@ module Rules.Test (testRules) where import Base import Builder import Expression -import GHC (rts, libffi) +import GHC (compiler, rts, libffi) import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.WindowsPath import Rules.Actions import Settings.Packages import Settings.User +import Target -- TODO: clean up after testing testRules :: Rules () @@ -18,7 +19,7 @@ testRules = do needBuilder $ Ghc Compile Stage2 needBuilder $ GhcPkg Stage1 needBuilder Hpc - runMake "testsuite/tests" ["fast"] + build $ Target (vanillaContext Stage2 compiler) (Make "testsuite/tests") [] [] "test" ~> do let yesNo x = show $ if x then "YES" else "NO" diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index b7c369f..d8c3649 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -17,6 +17,7 @@ import Settings.Builders.Happy import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld +import Settings.Builders.Make import Settings.Builders.Tar import Settings.Flavours.Quick import Settings.Packages.Base @@ -66,6 +67,7 @@ defaultBuilderArgs = mconcat , hsc2hsBuilderArgs , hsCppBuilderArgs , ldBuilderArgs + , makeBuilderArgs , tarBuilderArgs ] defaultPackageArgs :: Args From git at git.haskell.org Fri Oct 27 00:29:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:29:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring bash quoting back. (2d333d5) Message-ID: <20171027002958.5090C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d333d5fdf2b85180eb03a59764d73ff3477ea19/ghc >--------------------------------------------------------------- commit 2d333d5fdf2b85180eb03a59764d73ff3477ea19 Author: Andrey Mokhov Date: Thu Jan 7 12:17:15 2016 +0000 Bring bash quoting back. See #110. [skip ci] >--------------------------------------------------------------- 2d333d5fdf2b85180eb03a59764d73ff3477ea19 .appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index c3c4869..f74c459 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -5,14 +5,14 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - - bash -lc 'curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1' + - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - - bash -lc 'mv /home/ghc/tmp/* /home/ghc' + - bash -lc "mv /home/ghc/tmp/* /home/ghc" build_script: - - bash -lc 'cd /home/ghc && ./boot' - - bash -lc 'cd /home/ghc && echo "" | ./configure --enable-tarballs-autodownload' - - bash -lc 'cd /home/ghc && ./shake-build/build.bat -j --no-progress' + - bash -lc "cd /home/ghc && ./boot" + - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:30:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing Settings.Flavours.Quick module. (6da6b45) Message-ID: <20171027003000.6F30E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6da6b454c1a8ff2df7e54a165b28e103d5e6a0f2/ghc >--------------------------------------------------------------- commit 6da6b454c1a8ff2df7e54a165b28e103d5e6a0f2 Author: Andrey Mokhov Date: Tue May 10 01:05:59 2016 +0100 Add missing Settings.Flavours.Quick module. >--------------------------------------------------------------- 6da6b454c1a8ff2df7e54a165b28e103d5e6a0f2 hadrian.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/hadrian.cabal b/hadrian.cabal index 2dfd9e9..5c13f7a 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -87,6 +87,7 @@ executable hadrian , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default + , Settings.Flavours.Quick , Settings.Packages , Settings.Packages.Base , Settings.Packages.Compiler From git at git.haskell.org Fri Oct 27 00:30:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove dependency on rts for programs built in Stage0 (daa4b7c) Message-ID: <20171027003000.C271C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/daa4b7c1ff6f55a5c8141c33fd36414581828392/ghc >--------------------------------------------------------------- commit daa4b7c1ff6f55a5c8141c33fd36414581828392 Author: Andrey Mokhov Date: Sat Jan 7 14:32:20 2017 +0000 Remove dependency on rts for programs built in Stage0 >--------------------------------------------------------------- daa4b7c1ff6f55a5c8141c33fd36414581828392 src/Rules/Program.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index b1577e2..254284a 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -74,7 +74,7 @@ buildBinary rs context at Context {..} bin = do then hsSources context else do needContext =<< contextDependencies context - when (package == ghc) $ do + when (stage > Stage0) $ do ways <- interpretInContext context (getLibraryWays <> getRtsWays) needContext [ rtsContext { way = w } | w <- ways ] let path = buildPath context From git at git.haskell.org Fri Oct 27 00:30:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Moves wordsWhen into Base, and adjusts names and types to be more descriptive. (1d3de4c) Message-ID: <20171027003001.DFEB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1d3de4cf66717bd5c10dda3b10b305aa736abddb/ghc >--------------------------------------------------------------- commit 1d3de4cf66717bd5c10dda3b10b305aa736abddb Author: Moritz Angermann Date: Thu Jan 7 20:17:23 2016 +0800 Moves wordsWhen into Base, and adjusts names and types to be more descriptive. >--------------------------------------------------------------- 1d3de4cf66717bd5c10dda3b10b305aa736abddb src/Base.hs | 11 ++++++++++- src/Builder.hs | 2 +- src/Oracles/AbsoluteCommand.hs | 20 ++++++-------------- 3 files changed, 17 insertions(+), 16 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 36f2eb9..8830a7c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -24,7 +24,7 @@ module Base ( -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, replace, quote, chunksOfSize, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), - versionToInt, removeFileIfExists, removeDirectoryIfExists + versionToInt, removeFileIfExists, removeDirectoryIfExists, wordsWhen ) where import Control.Applicative @@ -238,3 +238,12 @@ removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f removeDirectoryIfExists :: FilePath -> Action () removeDirectoryIfExists d = liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d + +-- | Split function. Splits a string @s@ into chunks +-- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 +wordsWhen :: (Char -> Bool) -> String -> [String] +wordsWhen p s = + case dropWhile p s of + "" -> [] + s' -> w : wordsWhen p s'' + where (w, s'') = break p s' diff --git a/src/Builder.hs b/src/Builder.hs index 0613452..743c956 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -98,7 +98,7 @@ builderPath builder = do case (path, windows) of ("", _) -> return path (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) - (p, False) -> lookupInPath (p -<.> exe) + (p, False) -> lookupInPathOracle (p -<.> exe) getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/AbsoluteCommand.hs index 23de6ff..c60f429 100644 --- a/src/Oracles/AbsoluteCommand.hs +++ b/src/Oracles/AbsoluteCommand.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.AbsoluteCommand ( - lookupInPath, absoluteCommandOracle + lookupInPathOracle, absoluteCommandOracle ) where import Base @@ -8,25 +8,17 @@ import Base newtype AbsoluteCommand = AbsoluteCommand String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -absoluteCommand :: String -> Action String +-- | Fetches the absolute FilePath to a given FilePath from the +-- Oracle. +absoluteCommand :: FilePath -> Action FilePath absoluteCommand = askOracle . AbsoluteCommand -- | Lookup a @command@ in @PATH@ environment. -lookupInPath :: FilePath -> Action FilePath -lookupInPath c +lookupInPathOracle :: FilePath -> Action FilePath +lookupInPathOracle c | c /= takeFileName c = return c | otherwise = absoluteCommand c --- | Split function. Splits a string @s@ into chunks --- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 -wordsWhen :: (Char -> Bool) -> String -> [String] -wordsWhen p s = - case dropWhile p s of - "" -> [] - s' -> w : wordsWhen p s'' - where (w, s'') = break p s' - - absoluteCommandOracle :: Rules () absoluteCommandOracle = do o <- newCache $ \c -> do From git at git.haskell.org Fri Oct 27 00:30:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant top-level rts target (cf73599) Message-ID: <20171027003004.887F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf7359904f868be93defcdf4a9a65974d8224cb4/ghc >--------------------------------------------------------------- commit cf7359904f868be93defcdf4a9a65974d8224cb4 Author: Andrey Mokhov Date: Sat Jan 7 14:33:25 2017 +0000 Drop redundant top-level rts target >--------------------------------------------------------------- cf7359904f868be93defcdf4a9a65974d8224cb4 src/Rules.hs | 10 +--------- 1 file changed, 1 insertion(+), 9 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index be7c89b..8db01f4 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -27,16 +27,8 @@ allStages = [minBound ..] -- | This rule 'need' all top-level build targets. topLevelTargets :: Rules () topLevelTargets = do - want $ Rules.Generate.installTargets - -- TODO: Do we want libffiLibrary to be a top-level target? - - action $ do -- TODO: Add support for all rtsWays - rtsLib <- pkgLibraryFile $ rtsContext { way = vanilla } - rtsThrLib <- pkgLibraryFile $ rtsContext { way = threaded } - need [ rtsLib, rtsThrLib ] - forM_ allStages $ \stage -> forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> action $ do let context = vanillaContext stage pkg @@ -48,7 +40,7 @@ topLevelTargets = do libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] - else do -- otherwise build a program + else -- otherwise build a program need =<< maybeToList <$> programPath (programContext stage pkg) packageRules :: Rules () From git at git.haskell.org Fri Oct 27 00:30:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix configureBuilderArgs name. (e19cd9f) Message-ID: <20171027003004.17D573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e19cd9ffd1cf551529d8f00a4715d2a53048154a/ghc >--------------------------------------------------------------- commit e19cd9ffd1cf551529d8f00a4715d2a53048154a Author: Andrey Mokhov Date: Tue May 10 01:06:35 2016 +0100 Fix configureBuilderArgs name. >--------------------------------------------------------------- e19cd9ffd1cf551529d8f00a4715d2a53048154a src/Settings/Args.hs | 2 +- src/Settings/Builders/Configure.hs | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index d8c3649..1e239a4 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -53,7 +53,7 @@ defaultBuilderArgs = mconcat [ alexBuilderArgs , arBuilderArgs , ccBuilderArgs - , configureArgs + , configureBuilderArgs , deriveConstantsBuilderArgs , genApplyBuilderArgs , genPrimopCodeBuilderArgs diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 813b79d..b0cb4bd 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -1,4 +1,4 @@ -module Settings.Builders.Configure (configureArgs) where +module Settings.Builders.Configure (configureBuilderArgs) where import Base import Expression @@ -6,8 +6,8 @@ import Oracles.Config.Setting import Predicates (builder) import Settings -configureArgs :: Args -configureArgs = mconcat +configureBuilderArgs :: Args +configureBuilderArgs = mconcat [ builder (Configure libffiBuildPath) ? do top <- getTopDirectory targetPlatform <- getSetting TargetPlatform From git at git.haskell.org Fri Oct 27 00:30:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Renames absoluteCommand to lookupInPath (6f88557) Message-ID: <20171027003005.932ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6f88557b1fa263bf22f698ec3384a0ab37ed3447/ghc >--------------------------------------------------------------- commit 6f88557b1fa263bf22f698ec3384a0ab37ed3447 Author: Moritz Angermann Date: Thu Jan 7 20:37:59 2016 +0800 Renames absoluteCommand to lookupInPath >--------------------------------------------------------------- 6f88557b1fa263bf22f698ec3384a0ab37ed3447 shaking-up-ghc.cabal | 2 +- src/Builder.hs | 2 +- src/Oracles.hs | 4 ++-- .../{AbsoluteCommand.hs => LookupInPath.hs} | 22 +++++++++++----------- src/Rules/Oracles.hs | 16 ++++++++-------- 5 files changed, 23 insertions(+), 23 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 96efe57..c680b85 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -22,12 +22,12 @@ executable ghc-shake , Expression , GHC , Oracles - , Oracles.AbsoluteCommand , Oracles.ArgsHash , Oracles.Config , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies + , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData , Oracles.PackageDeps diff --git a/src/Builder.hs b/src/Builder.hs index 743c956..0613452 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -98,7 +98,7 @@ builderPath builder = do case (path, windows) of ("", _) -> return path (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) - (p, False) -> lookupInPathOracle (p -<.> exe) + (p, False) -> lookupInPath (p -<.> exe) getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles.hs b/src/Oracles.hs index 07e92f2..564c7bb 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -1,19 +1,19 @@ module Oracles ( - module Oracles.AbsoluteCommand, module Oracles.Config, module Oracles.Config.Flag, module Oracles.Config.Setting, module Oracles.Dependencies, + module Oracles.LookupInPath, module Oracles.PackageData, module Oracles.PackageDeps, module Oracles.WindowsRoot ) where -import Oracles.AbsoluteCommand import Oracles.Config import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Dependencies +import Oracles.LookupInPath import Oracles.PackageData import Oracles.PackageDeps import Oracles.WindowsRoot diff --git a/src/Oracles/AbsoluteCommand.hs b/src/Oracles/LookupInPath.hs similarity index 61% rename from src/Oracles/AbsoluteCommand.hs rename to src/Oracles/LookupInPath.hs index c60f429..c2a05e2 100644 --- a/src/Oracles/AbsoluteCommand.hs +++ b/src/Oracles/LookupInPath.hs @@ -1,26 +1,26 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} -module Oracles.AbsoluteCommand ( - lookupInPathOracle, absoluteCommandOracle +module Oracles.LookupInPath ( + lookupInPath, lookupInPathOracle ) where import Base -newtype AbsoluteCommand = AbsoluteCommand String +newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- | Fetches the absolute FilePath to a given FilePath from the -- Oracle. -absoluteCommand :: FilePath -> Action FilePath -absoluteCommand = askOracle . AbsoluteCommand +commandPath :: FilePath -> Action FilePath +commandPath = askOracle . LookupInPath -- | Lookup a @command@ in @PATH@ environment. -lookupInPathOracle :: FilePath -> Action FilePath -lookupInPathOracle c +lookupInPath :: FilePath -> Action FilePath +lookupInPath c | c /= takeFileName c = return c - | otherwise = absoluteCommand c + | otherwise = commandPath c -absoluteCommandOracle :: Rules () -absoluteCommandOracle = do +lookupInPathOracle :: Rules () +lookupInPathOracle = do o <- newCache $ \c -> do envPaths <- wordsWhen (== ':') <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths @@ -28,5 +28,5 @@ absoluteCommandOracle = do fullCommand <- head <$> filterM doesFileExist candidates putOracle $ "Found '" ++ c ++ "' at " ++ "'" ++ fullCommand ++ "'" return fullCommand - _ <- addOracle $ \(AbsoluteCommand c) -> o c + _ <- addOracle $ \(LookupInPath c) -> o c return () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index a4d6c70..f44b4ad 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -7,11 +7,11 @@ import Oracles.ModuleFiles oracleRules :: Rules () oracleRules = do - absoluteCommandOracle -- see Oracles.WindowsRoot - argsHashOracle -- see Oracles.ArgsHash - configOracle -- see Oracles.Config - dependenciesOracle -- see Oracles.Dependencies - moduleFilesOracle -- see Oracles.ModuleFiles - packageDataOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - windowsRootOracle -- see Oracles.WindowsRoot + argsHashOracle -- see Oracles.ArgsHash + configOracle -- see Oracles.Config + dependenciesOracle -- see Oracles.Dependencies + lookupInPathOracle -- see Oracles.LookupInPath + moduleFilesOracle -- see Oracles.ModuleFiles + packageDataOracle -- see Oracles.PackageData + packageDepsOracle -- see Oracles.PackageDeps + windowsRootOracle -- see Oracles.WindowsRoot From git at git.haskell.org Fri Oct 27 00:30:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add makeBuilderArgs. (d27501d) Message-ID: <20171027003007.7933D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d27501d1f279c145fd4c76809c6fab272f53cc4c/ghc >--------------------------------------------------------------- commit d27501d1f279c145fd4c76809c6fab272f53cc4c Author: Andrey Mokhov Date: Tue May 10 01:07:25 2016 +0100 Add makeBuilderArgs. >--------------------------------------------------------------- d27501d1f279c145fd4c76809c6fab272f53cc4c src/Settings/Builders/Make.hs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs new file mode 100644 index 0000000..85f16ac --- /dev/null +++ b/src/Settings/Builders/Make.hs @@ -0,0 +1,11 @@ +module Settings.Builders.Make (makeBuilderArgs) where + +import Expression +import Predicates (builder) +import Settings + +makeBuilderArgs :: Args +makeBuilderArgs = mconcat + [ builder (Make "testsuite/tests") ? arg "fast" + , builder (Make gmpBuildPath ) ? arg "MAKEFLAGS=" + , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=", "install"] ] From git at git.haskell.org Fri Oct 27 00:30:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make quick and quickest flavours more precise (c27e8cb) Message-ID: <20171027003008.162583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c27e8cbe776256e9698957c1c3dda4a62b185bbe/ghc >--------------------------------------------------------------- commit c27e8cbe776256e9698957c1c3dda4a62b185bbe Author: Andrey Mokhov Date: Sat Jan 7 18:43:32 2017 +0000 Make quick and quickest flavours more precise >--------------------------------------------------------------- c27e8cbe776256e9698957c1c3dda4a62b185bbe src/Settings/Flavours/Quick.hs | 6 ++---- src/Settings/Flavours/Quickest.hs | 13 +++++++++---- 2 files changed, 11 insertions(+), 8 deletions(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 1e4f5c0..6935544 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -10,7 +10,8 @@ quickFlavour :: Flavour quickFlavour = defaultFlavour { name = "quick" , args = defaultBuilderArgs <> quickArgs <> defaultPackageArgs - , libraryWays = defaultLibraryWays <> quickLibraryWays } + , libraryWays = append [vanilla] + , rtsWays = append [vanilla, threaded] } optimise :: Context -> Bool optimise Context {..} = @@ -20,6 +21,3 @@ quickArgs :: Args quickArgs = builder Ghc ? do context <- getContext if optimise context then arg "-O" else arg "-O0" - -quickLibraryWays :: Ways -quickLibraryWays = remove [profiling] diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 9f95957..62ad43e 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -6,10 +6,15 @@ import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour quickestFlavour = defaultFlavour - { name = "quickest" - , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs - , libraryWays = append [vanilla] - , rtsWays = append [vanilla] } + { name = "quickest" + , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs + , libraryWays = append [vanilla] + , rtsWays = quickestRtsWays } quickestArgs :: Args quickestArgs = builder Ghc ? arg "-O0" + +quickestRtsWays :: Ways +quickestRtsWays = mconcat + [ append [vanilla] + , buildHaddock defaultFlavour ? append [threaded] ] From git at git.haskell.org Fri Oct 27 00:30:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Makes wordsWhen more generic. (5ccd03c) Message-ID: <20171027003009.0862D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ccd03cac69896ef8ff2df7a8601aa1baa110c98/ghc >--------------------------------------------------------------- commit 5ccd03cac69896ef8ff2df7a8601aa1baa110c98 Author: Moritz Angermann Date: Thu Jan 7 20:38:11 2016 +0800 Makes wordsWhen more generic. >--------------------------------------------------------------- 5ccd03cac69896ef8ff2df7a8601aa1baa110c98 src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 8830a7c..86ddbf5 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -241,9 +241,9 @@ removeDirectoryIfExists d = -- | Split function. Splits a string @s@ into chunks -- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 -wordsWhen :: (Char -> Bool) -> String -> [String] +wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] wordsWhen p s = case dropWhile p s of - "" -> [] + [] -> [] s' -> w : wordsWhen p s'' where (w, s'') = break p s' From git at git.haskell.org Fri Oct 27 00:30:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do not unify paths on each -/- invocation. (6e953f1) Message-ID: <20171027003011.310B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e953f10e2c445addda3ade10191c60d90546ef4/ghc >--------------------------------------------------------------- commit 6e953f10e2c445addda3ade10191c60d90546ef4 Author: Andrey Mokhov Date: Tue May 10 02:26:26 2016 +0100 Do not unify paths on each -/- invocation. See #220. >--------------------------------------------------------------- 6e953f10e2c445addda3ade10191c60d90546ef4 src/Base.hs | 4 ++-- src/Oracles/ModuleFiles.hs | 4 +++- src/Oracles/WindowsPath.hs | 2 +- src/Rules/Wrappers/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Paths.hs | 21 ++++++++------------- 6 files changed, 16 insertions(+), 19 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 1fcbae7..bd80f47 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -87,9 +87,9 @@ versionToInt s = major * 1000 + minor * 10 + patch unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx --- | Combine paths using '' and apply 'unifyPath' to the result +-- | Combine paths with a forward slash regardless of platform. (-/-) :: FilePath -> FilePath -> FilePath -a -/- b = unifyPath $ a b +a -/- b = a ++ '/' : b infixr 6 -/- diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 652eb9a..897b2e0 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -39,7 +39,9 @@ decodeModule = splitFileName . replaceEq '.' '/' -- > encodeModule "./" "Prelude" == "Prelude" -- > uncurry encodeModule (decodeModule name) == name encodeModule :: FilePath -> String -> String -encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file +encodeModule dir file + | dir == "./" = replaceEq '/' '.' $ takeBaseName file + | otherwise = replaceEq '/' '.' $ dir ++ takeBaseName file -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index a0343fb..e252bba 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -25,7 +25,7 @@ fixAbsolutePathOnWindows path = do then do let (dir, file) = splitFileName path winDir <- askOracle $ WindowsPath dir - return $ winDir -/- file + return $ winDir ++ file else return path diff --git a/src/Rules/Wrappers/Ghc.hs b/src/Rules/Wrappers/Ghc.hs index 343f780..7338450 100644 --- a/src/Rules/Wrappers/Ghc.hs +++ b/src/Rules/Wrappers/Ghc.hs @@ -11,4 +11,4 @@ ghcWrapper program = do return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) - ++ " -B" ++ (top -/- "inplace" -/- "lib") ++ " ${1+\"$@\"}" ] + ++ " -B" ++ (top -/- "inplace/lib") ++ " ${1+\"$@\"}" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 9f6c6e2..faeb99d 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -128,7 +128,7 @@ with b = specified b ? do top <- getTopDirectory path <- getBuilderPath b lift $ needBuilder b - append [withBuilderKey b ++ top -/- path] + arg $ withBuilderKey b ++ unifyPath (top path) withStaged :: (Stage -> Builder) -> Args withStaged sb = with . sb =<< getStage diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 7174a94..288544b 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -12,11 +12,6 @@ import GHC import Oracles.PackageData import Settings.User --- A more efficient version of '-/-' which assumes that given FilePaths have --- already been unified. See #218. TODO: Switch to 'newtype FilePath'. -(~/~) :: FilePath -> FilePath -> FilePath -x ~/~ y = x ++ '/' : y - shakeFilesPath :: FilePath shakeFilesPath = buildRootPath -/- "hadrian/shake-files" @@ -29,17 +24,17 @@ packageDependencies = shakeFilesPath -/- "package-dependencies" -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath buildPath context at Context {..} = - buildRootPath ~/~ contextDirectory context ~/~ pkgPath package + buildRootPath -/- contextDirectory context -/- pkgPath package -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath -pkgDataFile context = buildPath context ~/~ "package-data.mk" +pkgDataFile context = buildPath context -/- "package-data.mk" -- | Path to the haddock file of a given 'Context', e.g.: -- ".build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = - buildPath context ~/~ "doc/html" ~/~ name ~/~ name <.> "haddock" + buildPath context -/- "doc/html" -/- name -/- name <.> "haddock" where name = pkgNameString package -- | Path to the library file of a given 'Context', e.g.: @@ -65,11 +60,11 @@ pkgFile :: Context -> String -> String -> Action FilePath pkgFile context prefix suffix = do let path = buildPath context componentId <- pkgData $ ComponentId path - return $ path ~/~ prefix ++ componentId ++ suffix + return $ path -/- prefix ++ componentId ++ suffix -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath ~/~ "stage1/gmp" +gmpBuildPath = buildRootPath -/- "stage1/gmp" -- | Path to the GMP library. gmpLibrary :: FilePath @@ -85,7 +80,7 @@ gmpObjects = gmpBuildPath -/- "objs" -- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath -gmpBuildInfoPath = pkgPath integerGmp ~/~ "integer-gmp.buildinfo" +gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" -- | Build directory for in-tree libffi library. libffiBuildPath :: FilePath @@ -95,11 +90,11 @@ libffiBuildPath = buildRootPath -/- "stage1/libffi" -- StageN, N > 0, share the same packageDbDirectory -- | Path to package database directory of a given 'Stage'. packageDbDirectory :: Stage -> FilePath -packageDbDirectory Stage0 = buildRootPath ~/~ "stage0/bootstrapping.conf" +packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" -- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do componentId <- pkgData . ComponentId $ buildPath context - return $ packageDbDirectory stage ~/~ componentId <.> "conf" + return $ packageDbDirectory stage -/- componentId <.> "conf" From git at git.haskell.org Fri Oct 27 00:30:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (12aa4ef) Message-ID: <20171027003011.E71F73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12aa4ef0c4e6f8e0a89f2aa899d66a42ac2e3eb9/ghc >--------------------------------------------------------------- commit 12aa4ef0c4e6f8e0a89f2aa899d66a42ac2e3eb9 Author: Andrey Mokhov Date: Sat Jan 7 22:40:55 2017 +0000 Minor revision >--------------------------------------------------------------- 12aa4ef0c4e6f8e0a89f2aa899d66a42ac2e3eb9 src/Settings/Default.hs | 1 - src/Settings/Flavours/Quick.hs | 3 +-- src/Settings/Flavours/Quickest.hs | 8 ++++---- 3 files changed, 5 insertions(+), 7 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 061d4ae..92089ab 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -118,7 +118,6 @@ stage2Packages = do , ghcTags ] ++ [ haddock | doc ] --- TODO: What about profilingDynamic way? Do we need platformSupportsSharedLibs? -- | Default build ways for library packages: -- * We always build 'vanilla' way. -- * We build 'profiling' way when stage > Stage0. diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 6935544..324ec85 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -10,8 +10,7 @@ quickFlavour :: Flavour quickFlavour = defaultFlavour { name = "quick" , args = defaultBuilderArgs <> quickArgs <> defaultPackageArgs - , libraryWays = append [vanilla] - , rtsWays = append [vanilla, threaded] } + , libraryWays = append [vanilla] } optimise :: Context -> Bool optimise Context {..} = diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 62ad43e..4d64cd0 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -6,10 +6,10 @@ import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour quickestFlavour = defaultFlavour - { name = "quickest" - , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs - , libraryWays = append [vanilla] - , rtsWays = quickestRtsWays } + { name = "quickest" + , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs + , libraryWays = append [vanilla] + , rtsWays = quickestRtsWays } quickestArgs :: Args quickestArgs = builder Ghc ? arg "-O0" From git at git.haskell.org Fri Oct 27 00:30:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build touchy, fix #125. (fee02d9) Message-ID: <20171027003012.A03953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3/ghc >--------------------------------------------------------------- commit fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3 Author: Andrey Mokhov Date: Thu Jan 7 12:59:47 2016 +0000 Build touchy, fix #125. >--------------------------------------------------------------- fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3 src/GHC.hs | 14 +++++++++----- src/Rules/Data.hs | 8 ++++++++ src/Settings/Args.hs | 4 +++- src/Settings/Packages.hs | 3 ++- src/Settings/Packages/{Hp2ps.hs => Touchy.hs} | 8 ++++---- 5 files changed, 26 insertions(+), 11 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index d4d5511..6e3a477 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -6,7 +6,7 @@ module GHC ( haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - transformers, unix, win32, xhtml, + touchy, transformers, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -28,7 +28,7 @@ defaultKnownPackages = , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time - , transformers, unix, win32, xhtml ] + , touchy, transformers, unix, win32, xhtml ] -- Package definitions (see Package.hs) array, base, binary, bytestring, cabal, compiler, containers, compareSizes, @@ -37,7 +37,7 @@ array, base, binary, bytestring, cabal, compiler, containers, compareSizes, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - transformers, unix, win32, xhtml :: Package + touchy, transformers, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -83,6 +83,7 @@ stm = library "stm" templateHaskell = library "template-haskell" terminfo = library "terminfo" time = library "time" +touchy = utility "touchy" transformers = library "transformers" unix = library "unix" win32 = library "Win32" @@ -92,7 +93,7 @@ xhtml = library "xhtml" -- TODO: The following utils are not included into the build system because -- they seem to be unused or unrelated to the build process: checkUniques, -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, --- lndir, mkdirhier, testremove, touchy, vagrant +-- lndir, mkdirhier, testremove, vagrant -- GHC build results will be placed into target directories with the following -- typical structure: @@ -102,7 +103,7 @@ xhtml = library "xhtml" defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage _ = stageString stage --- TODO: simplify +-- TODO: simplify, add programInplaceLibPath -- | Returns a relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg @@ -110,6 +111,9 @@ defaultProgramPath stage pkg | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing + | pkg == touchy = case stage of + Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe + _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index ee15c19..46072ce 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -67,6 +67,14 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." + when (pkg == touchy) $ dataFile %> \mk -> do + let prefix = "utils_touchy_" ++ stageString stage ++ "_" + contents = unlines $ map (prefix++) + [ "PROGNAME = touchy" + , "C_SRCS = touchy.c" ] + writeFileChanged mk contents + putSuccess $ "| Successfully generated '" ++ mk ++ "'." + -- Bootstrapping `ghcCabal`: although `ghcCabal` is a proper cabal -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index fb121ed..f2b30fa 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -30,6 +30,7 @@ import Settings.Packages.IntegerGmp import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc +import Settings.Packages.Touchy import Settings.User getArgs :: Expr [String] @@ -75,4 +76,5 @@ defaultPackageArgs = mconcat , integerGmpPackageArgs , iservBinPackageArgs , rtsPackageArgs - , runGhcPackageArgs ] + , runGhcPackageArgs + , touchyPackageArgs ] diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index dba4054..f80f0d0 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -24,7 +24,8 @@ packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] + , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode + , hp2ps, touchy ] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] packagesStage1 :: Packages diff --git a/src/Settings/Packages/Hp2ps.hs b/src/Settings/Packages/Touchy.hs similarity index 72% copy from src/Settings/Packages/Hp2ps.hs copy to src/Settings/Packages/Touchy.hs index 26518c6..8345449 100644 --- a/src/Settings/Packages/Hp2ps.hs +++ b/src/Settings/Packages/Touchy.hs @@ -1,13 +1,13 @@ -module Settings.Packages.Hp2ps (hp2psPackageArgs) where +module Settings.Packages.Touchy (touchyPackageArgs) where import Base import Expression -import GHC (hp2ps) +import GHC (touchy) import Predicates (builderGhc, package) import Settings -hp2psPackageArgs :: Args -hp2psPackageArgs = package hp2ps ? do +touchyPackageArgs :: Args +touchyPackageArgs = package touchy ? do path <- getTargetPath let cabalMacros = path -/- "build/autogen/cabal_macros.h" mconcat [ builderGhc ? From git at git.haskell.org Fri Oct 27 00:30:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update comments. (7239000) Message-ID: <20171027003014.E1C4B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7239000ffaeada9c33343aeddc28e121c3366af4/ghc >--------------------------------------------------------------- commit 7239000ffaeada9c33343aeddc28e121c3366af4 Author: Andrey Mokhov Date: Tue May 10 02:31:16 2016 +0100 Update comments. [skip ci] >--------------------------------------------------------------- 7239000ffaeada9c33343aeddc28e121c3366af4 src/Oracles/ModuleFiles.hs | 4 ++-- src/Rules/Dependencies.hs | 8 ++++---- src/Rules/Library.hs | 4 ++-- src/Settings/Paths.hs | 8 ++++---- 4 files changed, 12 insertions(+), 12 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 897b2e0..e77d2ba 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -45,10 +45,10 @@ encodeModule dir file -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) --- ".build/stage1/compiler/build/Lexer.hs" +-- "_build/stage1/compiler/build/Lexer.hs" -- == Just ("compiler/parser/Lexer.x", Alex) -- findGenerator (Context Stage1 base vanilla) --- ".build/stage1/base/build/Prelude.hs" +-- "_build/stage1/base/build/Prelude.hs" -- == Nothing findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder)) findGenerator Context {..} file = do diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index f5d781a..78f4d40 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -49,8 +49,8 @@ buildPackageDependencies rs context at Context {..} = -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' -- to its dependencies. For example, in vanillaContext Stage1 rts: --- * "Task.c" -> ".build/stage1/rts/Task.c.deps" --- * ".build/stage1/rts/AutoApply.cmm" -> ".build/stage1/rts/AutoApply.cmm.deps" +-- * "Task.c" -> "_build/stage1/rts/Task.c.deps" +-- * "_build/stage1/rts/AutoApply.cmm" -> "_build/stage1/rts/AutoApply.cmm.deps" src2dep :: Context -> FilePath -> FilePath src2dep context src | buildRootPath `isPrefixOf` src = src <.> "deps" @@ -58,8 +58,8 @@ src2dep context src -- Given a 'Context' and a 'FilePath' to a file with dependencies, compute the -- 'FilePath' to the source file. For example, in vanillaContext Stage1 rts: --- * ".build/stage1/rts/Task.c.deps" -> "Task.c" --- * ".build/stage1/rts/AutoApply.cmm.deps" -> ".build/stage1/rts/AutoApply.cmm" +-- * "_build/stage1/rts/Task.c.deps" -> "Task.c" +-- * "_build/stage1/rts/AutoApply.cmm.deps" -> "_build/stage1/rts/AutoApply.cmm" dep2src :: Context -> FilePath -> FilePath dep2src context at Context {..} dep | takeBaseName dep `elem` [ "AutoApply.cmm", "Evac_thr.c", "Scav_thr.c" ] = src diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 0538e4e..a45b591 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -76,8 +76,8 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do -- TODO: Get rid of code duplication and simplify. See also src2dep. -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' -- to its object file. For example, in Context Stage1 rts threaded: --- * "Task.c" -> ".build/stage1/rts/Task.thr_o" --- * ".build/stage1/rts/sm/Evac_thr.c" -> ".build/stage1/rts/sm/Evac_thr.thr_o" +-- * "Task.c" -> "_build/stage1/rts/Task.thr_o" +-- * "_build/stage1/rts/sm/Evac_thr.c" -> "_build/stage1/rts/sm/Evac_thr.thr_o" objFile :: Context -> FilePath -> FilePath objFile context at Context {..} src | buildRootPath `isPrefixOf` src = src -<.> osuf way diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 288544b..c39b12b 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -31,28 +31,28 @@ pkgDataFile :: Context -> FilePath pkgDataFile context = buildPath context -/- "package-data.mk" -- | Path to the haddock file of a given 'Context', e.g.: --- ".build/stage1/libraries/array/doc/html/array/array.haddock". +-- "_build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = buildPath context -/- "doc/html" -/- name -/- name <.> "haddock" where name = pkgNameString package -- | Path to the library file of a given 'Context', e.g.: --- ".build/stage1/libraries/array/build/libHSarray-0.5.1.0.a". +-- "_build/stage1/libraries/array/build/libHSarray-0.5.1.0.a". pkgLibraryFile :: Context -> Action FilePath pkgLibraryFile context at Context {..} = do extension <- libsuf way pkgFile context "libHS" extension -- | Path to the auxiliary library file of a given 'Context', e.g.: --- ".build/stage1/compiler/build/libHSghc-8.1-0.a". +-- "_build/stage1/compiler/build/libHSghc-8.1-0.a". pkgLibraryFile0 :: Context -> Action FilePath pkgLibraryFile0 context at Context {..} = do extension <- libsuf way pkgFile context "libHS" ("-0" ++ extension) -- | Path to the GHCi library file of a given 'Context', e.g.: --- ".build/stage1/libraries/array/build/HSarray-0.5.1.0.o". +-- "_build/stage1/libraries/array/build/HSarray-0.5.1.0.o". pkgGhciLibraryFile :: Context -> Action FilePath pkgGhciLibraryFile context = pkgFile context "HS" ".o" From git at git.haskell.org Fri Oct 27 00:30:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move integerLibrary to flavour (6b35c2c) Message-ID: <20171027003016.058743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b35c2c39cc41a548582483476c84e68798687b8/ghc >--------------------------------------------------------------- commit 6b35c2c39cc41a548582483476c84e68798687b8 Author: Andrey Mokhov Date: Sun Jan 8 01:28:06 2017 +0000 Move integerLibrary to flavour See #179 >--------------------------------------------------------------- 6b35c2c39cc41a548582483476c84e68798687b8 src/Flavour.hs | 1 + src/Rules/Generators/ConfigHs.hs | 11 +++++------ src/Settings.hs | 6 +++++- src/Settings/Default.hs | 4 ++-- src/Settings/Packages/Base.hs | 5 ++--- src/UserSettings.hs | 7 +------ 6 files changed, 16 insertions(+), 18 deletions(-) diff --git a/src/Flavour.hs b/src/Flavour.hs index ad658c4..b195767 100644 --- a/src/Flavour.hs +++ b/src/Flavour.hs @@ -8,6 +8,7 @@ data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. , args :: Args -- ^ Use these command line arguments. , packages :: Packages -- ^ Build these packages. + , integerLibrary :: Package -- ^ Either 'integerGmp' or 'integerSimple'. , libraryWays :: Ways -- ^ Build libraries these ways. , rtsWays :: Ways -- ^ Build RTS these ways. , splitObjects :: Predicate -- ^ Build split objects. diff --git a/src/Rules/Generators/ConfigHs.hs b/src/Rules/Generators/ConfigHs.hs index c5ad0cc..ffe0cfc 100644 --- a/src/Rules/Generators/ConfigHs.hs +++ b/src/Rules/Generators/ConfigHs.hs @@ -8,7 +8,6 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Rules.Generators.Common import Settings -import UserSettings generateConfigHs :: Expr String generateConfigHs = do @@ -21,10 +20,10 @@ generateConfigHs = do cProjectPatchLevel1 <- getSetting ProjectPatchLevel1 cProjectPatchLevel2 <- getSetting ProjectPatchLevel2 cBooterVersion <- getSetting GhcVersion - let cIntegerLibraryType | integerLibrary == integerGmp = "IntegerGMP" - | integerLibrary == integerSimple = "IntegerSimple" - | otherwise = error $ "Unknown integer library: " - ++ show integerLibrary ++ "." + let cIntegerLibraryType + | integerLibrary flavour == integerGmp = "IntegerGMP" + | integerLibrary flavour == integerSimple = "IntegerSimple" + | otherwise = error $ "Unknown integer library: " ++ integerLibraryName cSupportsSplitObjs <- yesNo supportsSplitObjects cGhcWithInterpreter <- yesNo ghcWithInterpreter cGhcWithNativeCodeGen <- yesNo ghcWithNativeCodeGen @@ -72,7 +71,7 @@ generateConfigHs = do , "cStage :: String" , "cStage = show (STAGE :: Int)" , "cIntegerLibrary :: String" - , "cIntegerLibrary = " ++ show (pkgNameString integerLibrary) + , "cIntegerLibrary = " ++ show integerLibraryName , "cIntegerLibraryType :: IntegerLibrary" , "cIntegerLibraryType = " ++ cIntegerLibraryType , "cSupportsSplitObjs :: String" diff --git a/src/Settings.hs b/src/Settings.hs index c455e0b..09b58f8 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,7 +2,8 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, getContextDirectory, getBuildPath, stagePackages, builderPath, - getBuilderPath, isSpecified, latestBuildStage, programPath, programContext + getBuilderPath, isSpecified, latestBuildStage, programPath, programContext, + integerLibraryName ) where import Base @@ -62,6 +63,9 @@ flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours flavours = hadrianFlavours ++ userFlavours flavourName = fromMaybe "default" cmdFlavour +integerLibraryName :: String +integerLibraryName = pkgNameString $ integerLibrary flavour + programContext :: Stage -> Package -> Context programContext stage pkg | pkg == ghc && ghcProfiled flavour = Context stage pkg profiling diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 92089ab..103c432 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -37,7 +37,6 @@ import Settings.Packages.Haddock import Settings.Packages.IntegerGmp import Settings.Packages.Rts import Settings.Packages.RunGhc -import UserSettings -- | All default command line arguments. defaultArgs :: Args @@ -100,7 +99,7 @@ stage1Packages = do , haskeline , hpcBin , hsc2hs - , integerLibrary + , integerLibrary flavour , pretty , process , rts @@ -147,6 +146,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages + , integerLibrary = integerGmp , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects diff --git a/src/Settings/Packages/Base.hs b/src/Settings/Packages/Base.hs index dce49e7..219c9d4 100644 --- a/src/Settings/Packages/Base.hs +++ b/src/Settings/Packages/Base.hs @@ -1,11 +1,10 @@ module Settings.Packages.Base (basePackageArgs) where -import Base import GHC import Predicate -import UserSettings +import Settings basePackageArgs :: Args basePackageArgs = package base ? mconcat - [ builder GhcCabal ? arg ("--flags=" ++ takeFileName (pkgPath integerLibrary)) + [ builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) , builder Cc ? arg "-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. diff --git a/src/UserSettings.hs b/src/UserSettings.hs index b952363..e16cf49 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,7 +3,7 @@ -- If you don't copy the file your changes will be tracked by git and you can -- accidentally commit them. module UserSettings ( - buildRootPath, userFlavours, userKnownPackages, integerLibrary, validating, + buildRootPath, userFlavours, userKnownPackages, validating, turnWarningsIntoErrors, verboseCommands, putBuild, putSuccess ) where @@ -11,7 +11,6 @@ import System.Console.ANSI import Base import Flavour -import GHC import Predicate -- See doc/user-settings.md for instructions. @@ -30,10 +29,6 @@ userFlavours = [] userKnownPackages :: [Package] userKnownPackages = [] --- | Choose the integer library: 'integerGmp' or 'integerSimple'. -integerLibrary :: Package -integerLibrary = integerGmp - -- | User defined flags. Note the following type semantics: -- * @Bool@: a plain Boolean flag whose value is known at compile time. -- * @Action Bool@: a flag whose value can depend on the build environment. From git at git.haskell.org Fri Oct 27 00:30:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add predicate input, rename predicate file to output. (caf0d6a) Message-ID: <20171027003018.799F73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8/ghc >--------------------------------------------------------------- commit caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8 Author: Andrey Mokhov Date: Wed May 11 23:29:15 2016 +0100 Add predicate input, rename predicate file to output. See #245. >--------------------------------------------------------------- caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8 src/Predicates.hs | 11 ++++++--- src/Settings/Builders/DeriveConstants.hs | 16 +++++++------- src/Settings/Builders/GenPrimopCode.hs | 38 ++++++++++++++++---------------- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Packages/Rts.hs | 14 ++++++------ src/Settings/Packages/RunGhc.hs | 4 ++-- 7 files changed, 46 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8 From git at git.haskell.org Fri Oct 27 00:30:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Download ghc-tarballs manually. (79a0bf3) Message-ID: <20171027003016.959753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79a0bf31e51d12dbc6209b4ea5c0492530667c4e/ghc >--------------------------------------------------------------- commit 79a0bf31e51d12dbc6209b4ea5c0492530667c4e Author: Andrey Mokhov Date: Thu Jan 7 13:11:16 2016 +0000 Download ghc-tarballs manually. See #110. [skip ci] >--------------------------------------------------------------- 79a0bf31e51d12dbc6209b4ea5c0492530667c4e .appveyor.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f74c459..6821abf 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -11,8 +11,9 @@ install: - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - bash -lc "cd /home/ghc && ./mk/get-win32-tarballs.sh download x86_64" build_script: - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo \"\" | ./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc && echo \"\" | ./configure" - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:30:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on GMP only when using integerGmp (4ac02f6) Message-ID: <20171027003019.A15893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ac02f6d213ff80fdb3659fb246688ada9886bbd/ghc >--------------------------------------------------------------- commit 4ac02f6d213ff80fdb3659fb246688ada9886bbd Author: Andrey Mokhov Date: Sun Jan 8 01:29:35 2017 +0000 Depend on GMP only when using integerGmp See #179 >--------------------------------------------------------------- 4ac02f6d213ff80fdb3659fb246688ada9886bbd src/Rules/Generate.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 5d557b4..51bec60 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -6,6 +6,7 @@ module Rules.Generate ( import Base import Context hiding (package) import Expression +import Flavour import GHC import Oracles.ModuleFiles import Predicate @@ -17,6 +18,7 @@ import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Rules.Libffi +import Settings import Settings.Path import Target import UserSettings @@ -70,7 +72,8 @@ compilerDependencies = do mconcat [ return [platformH stage] , return includesDependencies , return derivedConstantsDependencies - , notStage0 ? return (gmpLibraryH : libffiDependencies) + , notStage0 ? integerLibrary flavour == integerGmp ? return [gmpLibraryH] + , notStage0 ? return libffiDependencies , return $ fmap (path -/-) [ "primop-can-fail.hs-incl" , "primop-code-size.hs-incl" From git at git.haskell.org Fri Oct 27 00:30:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #123 from angerman/feature/fix-clang (4c75d3f) Message-ID: <20171027003020.1B2DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4c75d3ff0040645fe7107d244ce64b88dbf7010b/ghc >--------------------------------------------------------------- commit 4c75d3ff0040645fe7107d244ce64b88dbf7010b Merge: 79a0bf3 5ccd03c Author: Andrey Mokhov Date: Thu Jan 7 13:14:07 2016 +0000 Merge pull request #123 from angerman/feature/fix-clang Feature/fix clang >--------------------------------------------------------------- 4c75d3ff0040645fe7107d244ce64b88dbf7010b .travis.yml | 3 +-- README.md | 3 --- shaking-up-ghc.cabal | 1 + src/Base.hs | 11 ++++++++++- src/Builder.hs | 6 +++++- src/Oracles.hs | 2 ++ src/Oracles/LookupInPath.hs | 32 ++++++++++++++++++++++++++++++++ src/Rules/Oracles.hs | 1 + 8 files changed, 52 insertions(+), 7 deletions(-) From git at git.haskell.org Fri Oct 27 00:30:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing path unifications. (bc5b5e1) Message-ID: <20171027003022.01D853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc5b5e167368ecbf4e53cbbf9833cdfca9604211/ghc >--------------------------------------------------------------- commit bc5b5e167368ecbf4e53cbbf9833cdfca9604211 Author: Andrey Mokhov Date: Thu May 12 01:05:08 2016 +0100 Add missing path unifications. >--------------------------------------------------------------- bc5b5e167368ecbf4e53cbbf9833cdfca9604211 src/Oracles/ModuleFiles.hs | 20 +++++++++++--------- src/Rules/Data.hs | 6 ++++-- src/Rules/Selftest.hs | 8 ++++---- 3 files changed, 19 insertions(+), 15 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index e77d2ba..233cdc0 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -28,20 +28,22 @@ determineBuilder file = case takeExtension file of -- | Given a module name extract the directory and file name, e.g.: -- --- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") --- > decodeModule "Prelude" == ("./", "Prelude") +-- > decodeModule "Data.Functor.Identity" == ("Data/Functor", "Identity") +-- > decodeModule "Prelude" == ("", "Prelude") decodeModule :: String -> (FilePath, String) -decodeModule = splitFileName . replaceEq '.' '/' +decodeModule modName = (intercalate "/" (init xs), last xs) + where + xs = words $ replaceEq '.' ' ' modName -- | Given the directory and file name find the corresponding module name, e.g.: -- --- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" --- > encodeModule "./" "Prelude" == "Prelude" --- > uncurry encodeModule (decodeModule name) == name +-- > encodeModule "Data/Functor" "Identity.hs" == "Data.Functor.Identity" +-- > encodeModule "" "Prelude" == "Prelude" +-- > uncurry encodeModule (decodeModule name) == name encodeModule :: FilePath -> String -> String encodeModule dir file - | dir == "./" = replaceEq '/' '.' $ takeBaseName file - | otherwise = replaceEq '/' '.' $ dir ++ takeBaseName file + | dir == "" = takeBaseName file + | otherwise = replaceEq '/' '.' dir ++ '.' : takeBaseName file -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) @@ -102,7 +104,7 @@ moduleFilesOracle = void $ do result <- fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do - let fullDir = dir -/- mDir + let fullDir = unifyPath $ dir -/- mDir files <- getDirectoryFiles fullDir ["*"] let noBoot = filter (not . (isSuffixOf "-boot")) files cmp fe f = compare (dropExtension fe) f diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 719352f..f901069 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -44,7 +44,8 @@ buildPackageData context at Context {..} = do copyFile inTreeMk mk autogenFiles <- getDirectoryFiles (oldPath -/- "build") ["autogen/*"] createDirectory $ buildPath context -/- "autogen" - forM_ autogenFiles $ \file -> do + forM_ autogenFiles $ \file' -> do + let file = unifyPath file' copyFile (oldPath -/- "build" -/- file) (buildPath context -/- file) let haddockPrologue = "haddock-prologue.txt" copyFile (oldPath -/- haddockPrologue) (buildPath context -/- haddockPrologue) @@ -111,7 +112,8 @@ buildPackageData context at Context {..} = do ++ [ "posix" | not windows ] ++ [ "win32" | windows ] -- TODO: adding cmm/S sources to C_SRCS is a hack; rethink after #18 - cSrcs <- getDirectoryFiles (pkgPath package) (map (-/- "*.c") dirs) + cSrcs <- map unifyPath <$> + getDirectoryFiles (pkgPath package) (map (-/- "*.c") dirs) cmmSrcs <- getDirectoryFiles (pkgPath package) ["*.cmm"] buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] buildStgCRunAsm <- anyTargetArch ["powerpc64le"] diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 8037682..9ba4524 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -61,11 +61,11 @@ testMatchVersionedFilePath = do testModuleNames :: Action () testModuleNames = do putBuild $ "==== Encode/decode module name" - test $ encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" - test $ encodeModule "./" "Prelude" == "Prelude" + test $ encodeModule "Data/Functor" "Identity.hs" == "Data.Functor.Identity" + test $ encodeModule "" "Prelude" == "Prelude" - test $ decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") - test $ decodeModule "Prelude" == ("./", "Prelude") + test $ decodeModule "Data.Functor.Identity" == ("Data/Functor", "Identity") + test $ decodeModule "Prelude" == ("", "Prelude") test $ forAll names $ \n -> uncurry encodeModule (decodeModule n) == n where From git at git.haskell.org Fri Oct 27 00:30:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build touchy only on Windows, see #125. (bcb7894) Message-ID: <20171027003024.0B6123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bcb7894c282280861014f8f6fd0bb6bb3c0f4a02/ghc >--------------------------------------------------------------- commit bcb7894c282280861014f8f6fd0bb6bb3c0f4a02 Author: Andrey Mokhov Date: Thu Jan 7 13:35:09 2016 +0000 Build touchy only on Windows, see #125. >--------------------------------------------------------------- bcb7894c282280861014f8f6fd0bb6bb3c0f4a02 src/Settings/Packages.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index f80f0d0..3f4f661 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -24,8 +24,8 @@ packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode - , hp2ps, touchy ] + , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] + , stage0 ? windowsHost ? append [touchy] , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] packagesStage1 :: Packages From git at git.haskell.org Fri Oct 27 00:30:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test integerSimple on CI (0c08cc6) Message-ID: <20171027003023.96BDD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c08cc6871a95c987d9a559bd805cc91238eea37/ghc >--------------------------------------------------------------- commit 0c08cc6871a95c987d9a559bd805cc91238eea37 Author: Andrey Mokhov Date: Sun Jan 8 01:30:31 2017 +0000 Test integerSimple on CI See #179 >--------------------------------------------------------------- 0c08cc6871a95c987d9a559bd805cc91238eea37 src/Settings/Default.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 103c432..0fb54f6 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -146,7 +146,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages - , integerLibrary = integerGmp + , integerLibrary = integerSimple -- FIXME after testing, #179! , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects From git at git.haskell.org Fri Oct 27 00:30:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add link to MVP issue (82ead73) Message-ID: <20171027003025.6FF863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82ead7329fffd487907579625213da513ca4094f/ghc >--------------------------------------------------------------- commit 82ead7329fffd487907579625213da513ca4094f Author: Andrey Mokhov Date: Fri May 13 20:11:02 2016 +0100 Add link to MVP issue See #239. >--------------------------------------------------------------- 82ead7329fffd487907579625213da513ca4094f README.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index a8ca935..5c950dd 100644 --- a/README.md +++ b/README.md @@ -123,7 +123,8 @@ The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note the codebase is very unstable at present and we expect a lot of further refactoring. The documentation is currently non-existent, but we are working on it: [#55][comments-issue], -[#56][doc-issue]. +[#56][doc-issue]. See also [#239](https://github.com/snowleopard/hadrian/issues/239) +for a list of issues on the critical path. Acknowledgements ---------------- From git at git.haskell.org Fri Oct 27 00:30:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert to integerGmp (de151a9) Message-ID: <20171027003027.0F1CE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de151a9b7b8b5c595aa2084c160663340d7e5c3c/ghc >--------------------------------------------------------------- commit de151a9b7b8b5c595aa2084c160663340d7e5c3c Author: Andrey Mokhov Date: Sun Jan 8 02:11:38 2017 +0000 Revert to integerGmp Fix #179. >--------------------------------------------------------------- de151a9b7b8b5c595aa2084c160663340d7e5c3c src/Settings/Default.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 0fb54f6..103c432 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -146,7 +146,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages - , integerLibrary = integerSimple -- FIXME after testing, #179! + , integerLibrary = integerGmp , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects From git at git.haskell.org Fri Oct 27 00:30:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (53784f5) Message-ID: <20171027003027.78EAB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/53784f526f5ee88136966f5f9c8328459334436b/ghc >--------------------------------------------------------------- commit 53784f526f5ee88136966f5f9c8328459334436b Author: Moritz Angermann Date: Thu Jan 7 21:37:46 2016 +0800 Update README.md - Trying to unify Linux / OS X / Windows build steps. - Added note about `src/Settings/User.hs`. [skip ci] >--------------------------------------------------------------- 53784f526f5ee88136966f5f9c8328459334436b README.md | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) diff --git a/README.md b/README.md index 9f9de91..6a89dc6 100644 --- a/README.md +++ b/README.md @@ -23,36 +23,30 @@ identical to those for the `make` build system. This means that you don't need to adjust anything if you are already familiar with building ghc using the `make` build system. -### Linux / Mac OS X +### Getting the source and configuring GHC ```bash -git clone git://git.haskell.org/ghc +git clone --recursive git://git.haskell.org/ghc.git cd ghc -git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot -./configure +./configure # on linux / os x +./configure --enable-tarballs-autodownload # on windows ``` -Now you have a couple of options: - -- `./shake-build/build.sh` to run the script directly. You'll need to have - `shake` installed globally. -- `./shake-build/build.cabal.sh` to install the build system in a Cabal sandbox - and then run it. +### Configuring the build process +`ghc` uses `mk/build.mk` to configure the build process. `shaking-up-ghc` +uses `src/Settings/User.hs` for build specification. - -### Windows +### Building GHC using `shaking-up-ghc` ```bash -git clone --recursive git://git.haskell.org/ghc.git -cd ghc -git clone git://github.com/snowleopard/shaking-up-ghc shake-build -./boot -./configure --enable-tarballs-autodownload -shake-build/build.bat +./shake-build/build.sh # linux / os x: to run the script directly. You'll need to have `shake` installed globally. +./shake-build/build.cabal.sh # linux / os x: OR to install the build system in a Cabal sandbox and then run it. +shake-build/build.bat # windows ``` + Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build From git at git.haskell.org Fri Oct 27 00:30:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add user settings documentation (b56f4eb) Message-ID: <20171027003028.E09A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b56f4eb4034f51dbb5364ff57752900c8d9f417b/ghc >--------------------------------------------------------------- commit b56f4eb4034f51dbb5364ff57752900c8d9f417b Author: Andrey Mokhov Date: Sat May 14 13:58:21 2016 +0100 Add user settings documentation See #56, #245. >--------------------------------------------------------------- b56f4eb4034f51dbb5364ff57752900c8d9f417b doc/user-settings.md | 124 +++++++++++++++++++++++++++++++++++++++++++++++++++ src/Settings/User.hs | 20 ++++----- 2 files changed, 134 insertions(+), 10 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md new file mode 100644 index 0000000..a7f1469 --- /dev/null +++ b/doc/user-settings.md @@ -0,0 +1,124 @@ +# User settings + +Users can customise Hadrian by specifying user build settings in file +`src/Settings/User.hs`. Here we document currently supported settings. + +## Build directory + +Hadrian puts build results into `_build` directory by default, which is +controlled by `buildRootPath`: +```haskell +-- | All build artefacts are stored in 'buildRootPath' directory. +buildRootPath :: FilePath +buildRootPath = "_build" +``` + +## Command line arguments + +One of the key features of Hadrian is that users can modify any build command by +changing `userArgs`. The build system will detect the change and will rerun all +affected build rules during the next build, without requiring a full rebuild. + +As an example, here is how to pass an extra argument `-O0` to all invocations of +GHC when compiling package `cabal`: +```haskell +-- | Control user-specific command line arguments. +userArgs :: Args +userArgs = builder Ghc ? package cabal ? arg "-O0" +``` +Builders such as `Ghc` are defined in `src/Builder.hs`, and all packages that +are currently built as part of the GHC are defined in `src/GHC.hs` (also see +`src/Package.hs`). + +It is possible to specify several custom command line arguments combining the +list with `mconcat`: +```haskell +userArgs :: Args +userArgs = mconcat + [ builder Ghc ? package cabal ? arg "-O0" + , package rts ? input "//Evac\_thr.c" ? append [ "-DPARALLEL\_GC", "-Irts/sm" ] + , builder Ghc ? output "//Prelude.\*" ? remove ["-Wall", "-fwarn-tabs"] ] +``` +The above example also demostrates the use of `append` for adding more than one +argument and `remove` for removing arguments that Hadrian uses by default. It is +possible to match any combination of the current `builder`, `stage`, `package`, +`way`, `input` and `output` using predicates. File patterns such as +`"//Prelude.\*"` can be used when matching input and output files where `//` +matches an arbitrary number of path components and `\*` matches an entire path component, excluding any separators. + +## Packages + +To add or remove a package from a particular build stage, use `userPackages`. As +an example, below we add package `base` to Stage0 and remove package `haskeline` +from Stage1: +```haskell +-- | Control which packages get to be built. +userPackages :: Packages +userPackages = mconcat + [ stage0 ? append [base] + , stage1 ? remove [haskeline] ] +``` +If you are working on a new GHC package you need to let Hadrian know about it +by setting `userKnownPackages`: +```haskell +-- | Add new user-defined packages. +userKnownPackages :: [Package] +userKnownPackages = [] +``` +To control which integer library to use when builing GHC, set `integerLibrary`: +```haskell +-- | Choose the integer library: integerGmp or integerSimple. +integerLibrary :: Package +integerLibrary = integerGmp +``` + +## Build ways + +Libraries can be built in a number of ways, such as `vanilla`, `profiling` (with +profiling information enabled), and many others as defined in `src/Way.hs`. To +control which ways particular packages are built, set `userLibraryWays` and +`userRtsWays`. As an example, below we remove `dynamic` from the list of library +ways and keep `rts` package ways unchanged: +```haskell +-- | Control which ways library packages are built. +userLibraryWays :: Ways +userLibraryWays = remove [dynamic] + +-- | Control which ways the 'rts' package is built. +userRtsWays :: Ways +userRtsWays = mempty +``` + +## Verbose command lines + +By default Hadrian does not print full command lines during the build process +and instead prints short human readable digests for each executed command. It is +possible to suppress this behaviour completely or partially using +`verboseCommands` setting: +```haskell +-- | Set to True to print full command lines during the build process. Note, +-- this is a Predicate, hence you can enable verbose output for a chosen package +-- only, e.g.: verboseCommands = package ghcPrim +verboseCommands :: Predicate +verboseCommands = return False +``` +For example, to print the full command lines used to compile GHC executables, +set `verboseCommands` to: +```haskell +verboseCommands :: Predicate +verboseCommands = input "ghc/Main.hs" +``` +Below are a few other examples: +```haskell +-- Print command lines for all Ghc Link invocations: +verboseCommands = builder (Ghc Link) + +-- Print command lines when compiling files in package compiler using Gcc: +verboseCommands = builder (Gcc Compile) &&^ package compiler + +-- Use patterns when matching files: +verboseCommands = file "//rts/sm/*" &&^ way threaded + +-- Show all commands: +verboseCommands = return True +``` \ No newline at end of file diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 0893579..cc48684 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -16,31 +16,31 @@ import Settings.Default buildRootPath :: FilePath buildRootPath = "_build" --- Control user-specific settings +-- | Control user-specific command line arguments. userArgs :: Args userArgs = builder Ghc ? remove ["-Wall", "-fwarn-tabs"] --- Control which packages get to be built +-- | Control which packages get to be built. userPackages :: Packages userPackages = mempty --- Add new user-defined packages +-- | Add new user-defined packages. userKnownPackages :: [Package] userKnownPackages = [] --- | Control which ways library packages are built +-- | Choose the integer library: integerGmp or integerSimple. +integerLibrary :: Package +integerLibrary = integerGmp + +-- | Control which ways library packages are built. -- FIXME: skip dynamic since it's currently broken #4 userLibraryWays :: Ways userLibraryWays = remove [dynamic] --- | Control which ways the 'rts' package is built +-- | Control which ways the 'rts' package is built. userRtsWays :: Ways userRtsWays = mempty --- | Choose the integer library: integerGmp or integerSimple -integerLibrary :: Package -integerLibrary = integerGmp - -- | User-defined flags. Note the following type semantics: -- * Bool: a plain Boolean flag whose value is known at compile time -- * Action Bool: a flag whose value can depend on the build environment @@ -79,7 +79,7 @@ buildHaddock = return cmdBuildHaddock -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package --- only, e.g.: verboseCommands = package ghcPrim +-- only, e.g.: verboseCommands = package ghcPrim. verboseCommands :: Predicate verboseCommands = return False From git at git.haskell.org Fri Oct 27 00:30:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update section on integerLibrary, expand build ways example (60c8172) Message-ID: <20171027003031.26F7C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/60c8172861fdc8e4b66b68ae971c91ccc794ebba/ghc >--------------------------------------------------------------- commit 60c8172861fdc8e4b66b68ae971c91ccc794ebba Author: Andrey Mokhov Date: Sun Jan 8 02:39:51 2017 +0000 Update section on integerLibrary, expand build ways example See #179 >--------------------------------------------------------------- 60c8172861fdc8e4b66b68ae971c91ccc794ebba doc/user-settings.md | 25 ++++++++++++++++--------- 1 file changed, 16 insertions(+), 9 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index d4f0f95..9d776ea 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -24,6 +24,7 @@ data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. , args :: Args -- ^ Use these command line arguments. , packages :: Packages -- ^ Build these packages. + , integerLibrary :: Package -- ^ Either 'integerGmp' or 'integerSimple'. , libraryWays :: Ways -- ^ Build libraries these ways. , rtsWays :: Ways -- ^ Build RTS these ways. , splitObjects :: Predicate -- ^ Build split objects. @@ -111,24 +112,30 @@ userPackage = library "user-package" You will also need to add `userPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. -You can choose which integer library to use when builing GHC by setting -`integerLibrary`. Possible values are: `integerGmp` (default) and `integerSimple`. +You can choose which integer library to use when builing GHC using the +`integerLibrary` setting of the build flavour. Possible values are: `integerGmp` +(default) and `integerSimple`. ```haskell --- | Choose the integer library: 'integerGmp' or 'integerSimple'. -integerLibrary :: Package -integerLibrary = integerGmp +simpleFlavour :: Flavour +simpleFlavour = defaultFlavour { name = "simple", integerLibrary = integerSimple } ``` ## Build ways Packages can be built in a number of ways, such as `vanilla`, `profiling` (with profiling information enabled), and many others as defined in `src/Way.hs`. You can change the default build ways by modifying `libraryWays` and `rtsWays` fields -of the `Flavour` record as required. As an example, below we remove `dynamic` -from the list of library ways but keep `rts` package ways unchanged: +of the `Flavour` record as required. As an example, below we remove `profiling` +from the list of library ways: ```haskell -userFlavour :: Flavour -userFlavour = defaultFlavour { name = "user", libraryWays = defaultLibraryWays <> remove [dynamic] } +noProfilingFlavour :: Flavour +noProfilingFlavour = defaultFlavour + { name = "no-profiling" + , libraryWays = defaultLibraryWays <> remove [profiling] + , ghcProfiled = False } -- Can't build profiled GHC without profiled libraries ``` +Note that `rtsWays` is computed from `libraryWays` by default, therefore the above +change will lead to the removal of `threadedProfiling` way from `rtsWays`. To +change this behaviour, you can override the default `rtsWays` setting. ## Verbose command lines From git at git.haskell.org Fri Oct 27 00:30:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (fff8d58) Message-ID: <20171027003031.4E74D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fff8d58cbbf23090752b897768bf4eac8af5f819/ghc >--------------------------------------------------------------- commit fff8d58cbbf23090752b897768bf4eac8af5f819 Author: Moritz Angermann Date: Thu Jan 7 21:48:28 2016 +0800 Update README.md Drop `shake` requirement, as it applies to windows as well and is not exhaustive. [skip ci] >--------------------------------------------------------------- fff8d58cbbf23090752b897768bf4eac8af5f819 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 6a89dc6..2259c0b 100644 --- a/README.md +++ b/README.md @@ -42,7 +42,7 @@ uses `src/Settings/User.hs` for build specification. ### Building GHC using `shaking-up-ghc` ```bash -./shake-build/build.sh # linux / os x: to run the script directly. You'll need to have `shake` installed globally. +./shake-build/build.sh # linux / os x: to run the script directly. ./shake-build/build.cabal.sh # linux / os x: OR to install the build system in a Cabal sandbox and then run it. shake-build/build.bat # windows ``` From git at git.haskell.org Fri Oct 27 00:30:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a link to the user settings doc (f715a27) Message-ID: <20171027003032.9AF813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f715a274f7ef2e07625f22401f755a30dfbce001/ghc >--------------------------------------------------------------- commit f715a274f7ef2e07625f22401f755a30dfbce001 Author: Andrey Mokhov Date: Sat May 14 14:05:05 2016 +0100 Add a link to the user settings doc See #245. [skip ci] >--------------------------------------------------------------- f715a274f7ef2e07625f22401f755a30dfbce001 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 5c950dd..fdbdbc5 100644 --- a/README.md +++ b/README.md @@ -80,8 +80,8 @@ a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this f #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We -use [`src/Settings/User.hs`][user-settings] for the same purpose. Feel free to -experiment following the Haddock comments. +use [`src/Settings/User.hs`][user-settings] for the same purpose, see +[documentation](doc/user-settings.md). #### Clean and full rebuild From git at git.haskell.org Fri Oct 27 00:30:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop no longer relevant bits (1774b40) Message-ID: <20171027003034.CFD483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1774b40d0be398953bc0ad03bc364a951d971a7b/ghc >--------------------------------------------------------------- commit 1774b40d0be398953bc0ad03bc364a951d971a7b Author: Andrey Mokhov Date: Sun Jan 8 02:56:18 2017 +0000 Drop no longer relevant bits >--------------------------------------------------------------- 1774b40d0be398953bc0ad03bc364a951d971a7b src/Flavour.hs | 6 +++++- src/Settings/Builders/Common.hs | 6 ++---- src/UserSettings.hs | 19 ++----------------- 3 files changed, 9 insertions(+), 22 deletions(-) diff --git a/src/Flavour.hs b/src/Flavour.hs index b195767..3283eda 100644 --- a/src/Flavour.hs +++ b/src/Flavour.hs @@ -2,8 +2,12 @@ module Flavour (Flavour (..)) where import Expression --- TODO: Merge {libraryWays, rtsWays}, and {dynamicGhcPrograms, ghcProfiled...}. -- | 'Flavour' is a collection of build settings that fully define a GHC build. +-- Note the following type semantics: +-- * @Bool@: a plain Boolean flag whose value is known at compile time. +-- * @Action Bool@: a flag whose value can depend on the build environment. +-- * @Predicate@: a flag whose value can depend on the build environment and +-- on the current build target. data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. , args :: Args -- ^ Use these command line arguments. diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 271851e..a6b8198 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -41,16 +41,14 @@ cIncludeArgs = do ldArgs :: Args ldArgs = mempty --- TODO: put all validating options together in one file cArgs :: Args -cArgs = validating ? cWarnings +cArgs = mempty -- TODO: should be in a different file cWarnings :: Args cWarnings = do let gccGe46 = notM $ (flag GccIsClang ||^ flag GccLt46) - mconcat [ turnWarningsIntoErrors ? arg "-Werror" - , arg "-Wall" + mconcat [ arg "-Wall" , flag GccIsClang ? arg "-Wno-unknown-pragmas" , gccGe46 ? notM windowsHost ? arg "-Werror=unused-but-set-variable" , gccGe46 ? arg "-Wno-error=inline" ] diff --git a/src/UserSettings.hs b/src/UserSettings.hs index e16cf49..09d70e1 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,8 +3,8 @@ -- If you don't copy the file your changes will be tracked by git and you can -- accidentally commit them. module UserSettings ( - buildRootPath, userFlavours, userKnownPackages, validating, - turnWarningsIntoErrors, verboseCommands, putBuild, putSuccess + buildRootPath, userFlavours, userKnownPackages, verboseCommands, + putBuild, putSuccess ) where import System.Console.ANSI @@ -29,21 +29,6 @@ userFlavours = [] userKnownPackages :: [Package] userKnownPackages = [] --- | User defined flags. Note the following type semantics: --- * @Bool@: a plain Boolean flag whose value is known at compile time. --- * @Action Bool@: a flag whose value can depend on the build environment. --- * @Predicate@: a flag whose value can depend on the build environment and --- on the current build target. - --- TODO: This should be set automatically when validating. -validating :: Bool -validating = False - --- TODO: Replace with stage2 ? arg "-Werror"? Also see #251. --- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. -turnWarningsIntoErrors :: Predicate -turnWarningsIntoErrors = return False - -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output only for certain -- targets, e.g.: @verboseCommands = package ghcPrim at . From git at git.haskell.org Fri Oct 27 00:30:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #129 from snowleopard/angerman-patch-2 (6df7616) Message-ID: <20171027003034.D400C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6df7616bbc76029bafaa2493ea8d75e28ca03a60/ghc >--------------------------------------------------------------- commit 6df7616bbc76029bafaa2493ea8d75e28ca03a60 Merge: bcb7894 fff8d58 Author: Andrey Mokhov Date: Thu Jan 7 13:52:04 2016 +0000 Merge pull request #129 from snowleopard/angerman-patch-2 Update README.md [skip ci] >--------------------------------------------------------------- 6df7616bbc76029bafaa2493ea8d75e28ca03a60 README.md | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) From git at git.haskell.org Fri Oct 27 00:30:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (4b0dc2f) Message-ID: <20171027003036.2E9913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b0dc2fe52989ff18dc5e0202a1bd48f00689772/ghc >--------------------------------------------------------------- commit 4b0dc2fe52989ff18dc5e0202a1bd48f00689772 Author: Andrey Mokhov Date: Sat May 14 18:10:51 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- 4b0dc2fe52989ff18dc5e0202a1bd48f00689772 doc/user-settings.md | 45 ++++++++++++++++++++++++++------------------- 1 file changed, 26 insertions(+), 19 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index a7f1469..e9bea77 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,12 +1,12 @@ # User settings -Users can customise Hadrian by specifying user build settings in file +You can customise Hadrian by specifying user build settings in file `src/Settings/User.hs`. Here we document currently supported settings. ## Build directory Hadrian puts build results into `_build` directory by default, which is -controlled by `buildRootPath`: +specified by `buildRootPath`: ```haskell -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath @@ -19,7 +19,7 @@ One of the key features of Hadrian is that users can modify any build command by changing `userArgs`. The build system will detect the change and will rerun all affected build rules during the next build, without requiring a full rebuild. -As an example, here is how to pass an extra argument `-O0` to all invocations of +For example, here is how to pass an extra argument `-O0` to all invocations of GHC when compiling package `cabal`: ```haskell -- | Control user-specific command line arguments. @@ -27,24 +27,24 @@ userArgs :: Args userArgs = builder Ghc ? package cabal ? arg "-O0" ``` Builders such as `Ghc` are defined in `src/Builder.hs`, and all packages that -are currently built as part of the GHC are defined in `src/GHC.hs` (also see -`src/Package.hs`). +are currently built as part of the GHC are defined in `src/GHC.hs`. See also +`src/Package.hs`. -It is possible to specify several custom command line arguments combining the -list with `mconcat`: +You can combine several custom command line settings using `mconcat`: ```haskell userArgs :: Args userArgs = mconcat [ builder Ghc ? package cabal ? arg "-O0" - , package rts ? input "//Evac\_thr.c" ? append [ "-DPARALLEL\_GC", "-Irts/sm" ] - , builder Ghc ? output "//Prelude.\*" ? remove ["-Wall", "-fwarn-tabs"] ] + , package rts ? input "//Evac_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] + , builder Ghc ? output "//Prelude.*" ? remove ["-Wall", "-fwarn-tabs"] ] ``` The above example also demostrates the use of `append` for adding more than one -argument and `remove` for removing arguments that Hadrian uses by default. It is -possible to match any combination of the current `builder`, `stage`, `package`, -`way`, `input` and `output` using predicates. File patterns such as -`"//Prelude.\*"` can be used when matching input and output files where `//` -matches an arbitrary number of path components and `\*` matches an entire path component, excluding any separators. +argument and `remove` for removing arguments that Hadrian uses by default. You +can match any combination of the `builder`, `stage`, `package`, `way`, `input` +and `output` when specifying custom command line arguments. File patterns such as +`"//Prelude.*"` can be used when matching input and output files where `//` +matches an arbitrary number of path components and `*` matches an entire path +component, excluding any separators. ## Packages @@ -63,20 +63,27 @@ by setting `userKnownPackages`: ```haskell -- | Add new user-defined packages. userKnownPackages :: [Package] -userKnownPackages = [] +userKnownPackages = [myPackage] + +-- An example package that lives in "libraries/my-package" directory. +myPackage :: Package +myPackage = library "my-package" ``` -To control which integer library to use when builing GHC, set `integerLibrary`: +Note, you will also need to add it to a specific build stage by modifying +`userPackages` as otherwise it will not be built. + +You can choose which integer library to use when builing GHC by setting +`integerLibrary`: ```haskell -- | Choose the integer library: integerGmp or integerSimple. integerLibrary :: Package integerLibrary = integerGmp ``` - ## Build ways Libraries can be built in a number of ways, such as `vanilla`, `profiling` (with profiling information enabled), and many others as defined in `src/Way.hs`. To -control which ways particular packages are built, set `userLibraryWays` and +control which ways particular ways are built, set `userLibraryWays` and `userRtsWays`. As an example, below we remove `dynamic` from the list of library ways and keep `rts` package ways unchanged: ```haskell @@ -119,6 +126,6 @@ verboseCommands = builder (Gcc Compile) &&^ package compiler -- Use patterns when matching files: verboseCommands = file "//rts/sm/*" &&^ way threaded --- Show all commands: +-- Print all commands: verboseCommands = return True ``` From git at git.haskell.org Fri Oct 27 00:30:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build only stage1 base library to fit into Travis 50 min limit for OSX. (b67f727) Message-ID: <20171027003038.AAC093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b67f727b982025b1039994cdb7731fc2a47f2119/ghc >--------------------------------------------------------------- commit b67f727b982025b1039994cdb7731fc2a47f2119 Author: Andrey Mokhov Date: Thu Jan 7 15:43:14 2016 +0000 Build only stage1 base library to fit into Travis 50 min limit for OSX. >--------------------------------------------------------------- b67f727b982025b1039994cdb7731fc2a47f2119 .travis.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 055edd5..4cc0396 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: false matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 + env: CABALVER=1.22 GHCVER=7.10.3 TARGET= addons: apt: packages: @@ -21,6 +21,7 @@ matrix: - cabal update - os: osx + env: TARGET=libraries/base/stage1/build/libHSbase-4.9.0.0.a before_install: - brew update - brew install ghc cabal-install @@ -54,7 +55,7 @@ install: - ( cd ghc && ./configure ) script: - - ./ghc/shake-build/build.sh -j --no-progress + - ./ghc/shake-build/build.sh -j --no-progress $TARGET cache: directories: From git at git.haskell.org Fri Oct 27 00:30:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add development flavours (d6e7919) Message-ID: <20171027003038.AD6673A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6e7919a7d67462ee29a3019f46d6e7899bb4c50/ghc >--------------------------------------------------------------- commit d6e7919a7d67462ee29a3019f46d6e7899bb4c50 Author: Andrey Mokhov Date: Mon Jan 9 01:24:57 2017 +0000 Add development flavours See #188, #268 >--------------------------------------------------------------- d6e7919a7d67462ee29a3019f46d6e7899bb4c50 hadrian.cabal | 1 + src/CmdLineFlag.hs | 4 ++-- src/Settings.hs | 6 ++++-- src/Settings/Builders/Ghc.hs | 3 --- src/Settings/Default.hs | 5 ++++- src/Settings/Flavours/Development.hs | 26 ++++++++++++++++++++++++++ 6 files changed, 37 insertions(+), 8 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 712d4c6..598bd27 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -85,6 +85,7 @@ executable hadrian , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default + , Settings.Flavours.Development , Settings.Flavours.Perf , Settings.Flavours.Prof , Settings.Flavours.Quick diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index b58df7b..ebe907a 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -38,7 +38,7 @@ readBuildHaddock :: Either String (Untracked -> Untracked) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } readFlavour :: Maybe String -> Either String (Untracked -> Untracked) -readFlavour ms = Right $ \flags -> flags { flavour = ms } +readFlavour ms = Right $ \flags -> flags { flavour = lower <$> ms } readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) readProgressColour ms = @@ -74,7 +74,7 @@ readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") - "Build flavour (default, quick or quickest)." + "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") diff --git a/src/Settings.hs b/src/Settings.hs index 09b58f8..01ee122 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -15,6 +15,7 @@ import GHC import Oracles.PackageData import Oracles.Path import {-# SOURCE #-} Settings.Default +import Settings.Flavours.Development import Settings.Flavours.Perf import Settings.Flavours.Prof import Settings.Flavours.Quick @@ -53,8 +54,9 @@ getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getBuildPath hadrianFlavours :: [Flavour] -hadrianFlavours = [ defaultFlavour, perfFlavour, profFlavour, quickFlavour - , quickestFlavour ] +hadrianFlavours = + [ defaultFlavour, developmentFlavour Stage1, developmentFlavour Stage2 + , perfFlavour, profFlavour, quickFlavour, quickestFlavour ] flavour :: Flavour flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 98e5e39..669900f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -9,9 +9,6 @@ ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do needTouchy mconcat [ arg "-Wall" , commonGhcArgs - , arg "-H32m" - , stage0 ? arg "-O" - , notStage0 ? arg "-O2" , splitObjectsArgs , ghcLinkArgs , builder (Ghc CompileHs) ? arg "-c" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 103c432..6db669e 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -40,7 +40,10 @@ import Settings.Packages.RunGhc -- | All default command line arguments. defaultArgs :: Args -defaultArgs = defaultBuilderArgs <> defaultPackageArgs +defaultArgs = mconcat + [ defaultBuilderArgs + , builder Ghc ? mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2", arg "-H32m"] + , defaultPackageArgs ] -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs new file mode 100644 index 0000000..afe42d5 --- /dev/null +++ b/src/Settings/Flavours/Development.hs @@ -0,0 +1,26 @@ +module Settings.Flavours.Development (developmentFlavour) where + +import Flavour +import GHC +import Predicate +import {-# SOURCE #-} Settings.Default + +-- TODO: Implement an equivalent of LAX_DEPENDENCIES = YES setting, see #250. +developmentFlavour :: Stage -> Flavour +developmentFlavour ghcStage = defaultFlavour + { name = "devel" ++ show (fromEnum ghcStage) + , args = developmentArgs ghcStage + , libraryWays = append [vanilla] } + +developmentArgs :: Stage -> Args +developmentArgs ghcStage = do + stage <- getStage + pkg <- getPackage + let now = succ stage == ghcStage + mconcat [ defaultBuilderArgs + , builder Ghc ? mconcat + [ append ["-O", "-H64m"] + , now ? pkg == compiler ? append ["-O0", "-DDEBUG", "-dcore-lint"] + , now ? pkg == ghc ? append ["-O0", "-DDEBUG"] + , notStage0 ? isLibrary pkg ? arg "-dcore-lint" ] + , defaultPackageArgs ] From git at git.haskell.org Fri Oct 27 00:30:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor build flavours (b2ca3dd) Message-ID: <20171027003042.D8FB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2ca3dd7366f8f8eaf598597c52e99465124ab2c/ghc >--------------------------------------------------------------- commit b2ca3dd7366f8f8eaf598597c52e99465124ab2c Author: Andrey Mokhov Date: Mon Jan 9 03:30:19 2017 +0000 Refactor build flavours >--------------------------------------------------------------- b2ca3dd7366f8f8eaf598597c52e99465124ab2c hadrian.cabal | 5 +++-- src/Settings.hs | 6 +++--- src/Settings/Default.hs | 11 ++++++++++- src/Settings/Flavours/Development.hs | 20 ++++++++------------ src/Settings/Flavours/Perf.hs | 21 --------------------- src/Settings/Flavours/Performance.hs | 18 ++++++++++++++++++ src/Settings/Flavours/Prof.hs | 21 --------------------- src/Settings/Flavours/Profiled.hs | 19 +++++++++++++++++++ src/Settings/Flavours/Quick.hs | 16 +++++++--------- src/Settings/Flavours/Quickest.hs | 7 ++++++- src/Settings/Optimisation.hs | 21 +++++++++++++++++++++ 11 files changed, 95 insertions(+), 70 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 b2ca3dd7366f8f8eaf598597c52e99465124ab2c From git at git.haskell.org Fri Oct 27 00:30:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (be59fae) Message-ID: <20171027003039.CB26E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/be59faec5e11a7338888227ffdc36a2513c1fd00/ghc >--------------------------------------------------------------- commit be59faec5e11a7338888227ffdc36a2513c1fd00 Author: Andrey Mokhov Date: Sat May 14 18:15:10 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- be59faec5e11a7338888227ffdc36a2513c1fd00 doc/user-settings.md | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index e9bea77..e395ea2 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -41,10 +41,10 @@ userArgs = mconcat The above example also demostrates the use of `append` for adding more than one argument and `remove` for removing arguments that Hadrian uses by default. You can match any combination of the `builder`, `stage`, `package`, `way`, `input` -and `output` when specifying custom command line arguments. File patterns such as -`"//Prelude.*"` can be used when matching input and output files where `//` -matches an arbitrary number of path components and `*` matches an entire path -component, excluding any separators. +and `output` predicates when specifying custom command line arguments. File +patterns such as `"//Prelude.*"` can be used when matching input and output files, +where `//` matches an arbitrary number of path components and `*` matches an entire +path component, excluding any separators. ## Packages @@ -69,7 +69,7 @@ userKnownPackages = [myPackage] myPackage :: Package myPackage = library "my-package" ``` -Note, you will also need to add it to a specific build stage by modifying +Note, you will also need to add `myPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting From git at git.haskell.org Fri Oct 27 00:30:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create ghc-tarballs folder. (45eefc0) Message-ID: <20171027003043.31CA23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45eefc07e8d5820ca0640a7ecb398dcb717aa35a/ghc >--------------------------------------------------------------- commit 45eefc07e8d5820ca0640a7ecb398dcb717aa35a Author: Andrey Mokhov Date: Thu Jan 7 16:35:01 2016 +0000 Create ghc-tarballs folder. See #110. [skip ci] >--------------------------------------------------------------- 45eefc07e8d5820ca0640a7ecb398dcb717aa35a .appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.appveyor.yml b/.appveyor.yml index 6821abf..7d5a0f8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -11,6 +11,7 @@ install: - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - bash -lc "mkdir -p /home/ghc/ghc-tarballs" - bash -lc "cd /home/ghc && ./mk/get-win32-tarballs.sh download x86_64" build_script: From git at git.haskell.org Fri Oct 27 00:30:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add TODOs. (86ae5c7) Message-ID: <20171027003043.AC7673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86ae5c73a514bea9a5035128f673833b071e5dc9/ghc >--------------------------------------------------------------- commit 86ae5c73a514bea9a5035128f673833b071e5dc9 Author: Andrey Mokhov Date: Sat May 14 18:29:43 2016 +0100 Add TODOs. >--------------------------------------------------------------- 86ae5c73a514bea9a5035128f673833b071e5dc9 src/Settings/User.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index cc48684..2294fc7 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -53,6 +53,7 @@ userRtsWays = mempty trackBuildSystem :: Bool trackBuildSystem = True +-- TODO: This should be set automatically when validating. validating :: Bool validating = False @@ -61,6 +62,12 @@ validating = False splitObjects :: Predicate splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects +-- | Control when to build documentation. +buildHaddock :: Predicate +buildHaddock = return cmdBuildHaddock + +-- TODO: Do we need to be able to set these from command line? +-- TODO: Turn below into ghcWays? dynamicGhcPrograms :: Bool dynamicGhcPrograms = False @@ -70,13 +77,9 @@ ghciWithDebugger = False ghcProfiled :: Bool ghcProfiled = False --- TODO: do we need to be able to set this from command line? ghcDebugged :: Bool ghcDebugged = False -buildHaddock :: Predicate -buildHaddock = return cmdBuildHaddock - -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package -- only, e.g.: verboseCommands = package ghcPrim. From git at git.haskell.org Fri Oct 27 00:30:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a doc on build flavours (ff9e5b6) Message-ID: <20171027003046.B55A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff9e5b6362b5112a06f7018a5462639c9ef4d83c/ghc >--------------------------------------------------------------- commit ff9e5b6362b5112a06f7018a5462639c9ef4d83c Author: Andrey Mokhov Date: Thu Jan 12 01:00:53 2017 +0000 Add a doc on build flavours See #239, #268. >--------------------------------------------------------------- ff9e5b6362b5112a06f7018a5462639c9ef4d83c doc/flavours.md | 162 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 162 insertions(+) diff --git a/doc/flavours.md b/doc/flavours.md new file mode 100644 index 0000000..dc672a9 --- /dev/null +++ b/doc/flavours.md @@ -0,0 +1,162 @@ +# Build flavours + +Hadrian supports a few predefined _build flavours_, i.e. collections of build +settings that fully define a GHC build (see `src/Flavour.hs`). Users can add their +own build flavours if need be, as described +[here](https://github.com/snowleopard/hadrian/blob/master/doc/user-settings.md#build-flavour). + +## Arguments + +The following table summarises extra arguments passed to GHC in different build flavours. +There are four groups of arguments: arguments in `hsDefault` are passed to GHC for all Haskell +source files, `hsLibrary` arguments are added when compiling libraries, `hsCompiler` +when compiling the `compiler` library, and `hsGhc` when compiling/linking the GHC program. + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
FlavourExtra arguments
hsDefault + hsLibrary + hsCompiler + hsGhc +
stage0 + stage1+ + stage0 + stage1+ + stage0 + stage1+ + stage0 + stage1+ +
default
+
-O
-H32
-O2
-H32m
quick + -O0
-H64
-O0
-H64
-O-O-O
quickest + -O0
-H64
-O0
-H64
perf + -O
-H64
-O
-H64
-O2-O-O2-O-O2
prof + -O0
-H64
-O0
-H64
-O-O-O-O-O
devel1 + -O
-H64
-O
-H64
-dcore-lint-O0
-DDEBUG
-O0
-DDEBUG
devel2 + -O
-H64
-O
-H64
-dcore-lint-O0
-DDEBUG
-O0
-DDEBUG
+ +## Ways + +Libraries and GHC can be built in different _ways_, e.g. with or without profiling +information. The following table lists ways that are built in different flavours. + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
FlavourLibrary waysRTS waysProfiled GHC
stage0 + stage1+ + stage0 + stage1+ + stage0 + stage1+ +
default
perf
prof
devel1
devel2 +
vanillavanilla
profiling
logging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
threadedProfiling
Only in
prof
flavour
Only in
prof
flavour
quick + vanillavanillalogging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
NoNo
quickest + vanillavanillavanilla
threaded (when --haddock)
vanilla
threaded (when --haddock)
NoNo
From git at git.haskell.org Fri Oct 27 00:30:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename replaceIf -> replaceWhen to match wordsWhen, clean up. (f7cd3ae) Message-ID: <20171027003047.3B5743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f7cd3aeef421946ef3f1ff1e9916b19ac8ddf9d4/ghc >--------------------------------------------------------------- commit f7cd3aeef421946ef3f1ff1e9916b19ac8ddf9d4 Author: Andrey Mokhov Date: Thu Jan 7 16:52:25 2016 +0000 Rename replaceIf -> replaceWhen to match wordsWhen, clean up. [skip ci] >--------------------------------------------------------------- f7cd3aeef421946ef3f1ff1e9916b19ac8ddf9d4 src/Base.hs | 51 +++++++++++++++++++++++++-------------------------- 1 file changed, 25 insertions(+), 26 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 86ddbf5..a116892 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -81,14 +81,14 @@ packageConfigurationInitialised stage = -- Utility functions -- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] -replaceEq from = replaceIf (== from) +replaceEq from = replaceWhen (== from) -- | Find and replace all occurrences of path separators in a String with a Char replaceSeparators :: Char -> String -> String -replaceSeparators = replaceIf isPathSeparator +replaceSeparators = replaceWhen isPathSeparator -replaceIf :: (a -> Bool) -> a -> [a] -> [a] -replaceIf p to = map (\from -> if p from then to else from) +replaceWhen :: (a -> Bool) -> a -> [a] -> [a] +replaceWhen p to = map (\from -> if p from then to else from) -- | Find all occurrences of substring 'from' and replace them to 'to' in a -- given string. Not very efficient, but simple and fast enough for our purposes @@ -101,6 +101,27 @@ replace from to = go | from `isPrefixOf` s = to ++ go (skipFrom s) | otherwise = x : go xs +-- | Split a list into chunks in places where the predicate @p@ holds. +-- See: http://stackoverflow.com/a/4981265 +wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] +wordsWhen p list = + case dropWhile p list of + [] -> [] + l -> w : wordsWhen p rest where (w, rest) = break p l + +-- | @chunksOfSize size strings@ splits a given list of strings into chunks not +-- exceeding the given @size at . +chunksOfSize :: Int -> [String] -> [[String]] +chunksOfSize _ [] = [] +chunksOfSize size strings = reverse chunk : chunksOfSize size rest + where + (chunk, rest) = go [] 0 strings + go res _ [] = (res, []) + go res chunkSize (s:ss) = + if newSize > size then (res, s:ss) else go (s:res) newSize ss + where + newSize = chunkSize + length s + -- | Add quotes to a String quote :: String -> String quote s = "\"" ++ s ++ "\"" @@ -133,19 +154,6 @@ a -/- b = unifyPath $ a b infixr 6 -/- --- | @chunksOfSize size strings@ splits a given list of strings into chunks not --- exceeding the given @size at . -chunksOfSize :: Int -> [String] -> [[String]] -chunksOfSize _ [] = [] -chunksOfSize size strings = reverse chunk : chunksOfSize size rest - where - (chunk, rest) = go [] 0 strings - go res _ [] = (res, []) - go res chunkSize (s:ss) = - if newSize > size then (res, s:ss) else go (s:res) newSize ss - where - newSize = chunkSize + length s - -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do @@ -238,12 +246,3 @@ removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f removeDirectoryIfExists :: FilePath -> Action () removeDirectoryIfExists d = liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d - --- | Split function. Splits a string @s@ into chunks --- when the predicate @p@ holds. See: http://stackoverflow.com/a/4981265 -wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] -wordsWhen p s = - case dropWhile p s of - [] -> [] - s' -> w : wordsWhen p s'' - where (w, s'') = break p s' From git at git.haskell.org Fri Oct 27 00:30:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add miscellaneous, minor revision (8c6a188) Message-ID: <20171027003047.8F75E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c6a188fc3ecea807a6536ce0442dda6244b7b92/ghc >--------------------------------------------------------------- commit 8c6a188fc3ecea807a6536ce0442dda6244b7b92 Author: Andrey Mokhov Date: Sat May 14 18:33:55 2016 +0100 Add miscellaneous, minor revision [skip ci] >--------------------------------------------------------------- 8c6a188fc3ecea807a6536ce0442dda6244b7b92 doc/user-settings.md | 31 +++++++++++++++++++++++-------- 1 file changed, 23 insertions(+), 8 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index e395ea2..dc718ed 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -81,11 +81,11 @@ integerLibrary = integerGmp ``` ## Build ways -Libraries can be built in a number of ways, such as `vanilla`, `profiling` (with -profiling information enabled), and many others as defined in `src/Way.hs`. To -control which ways particular ways are built, set `userLibraryWays` and -`userRtsWays`. As an example, below we remove `dynamic` from the list of library -ways and keep `rts` package ways unchanged: +Packages can be built in a number of ways, such as `vanilla`, `profiling` (with +profiling information enabled), and many others as defined in `src/Way.hs`. You +can change the default build ways using `userLibraryWays` and `userRtsWays` settings. +As an example, below we remove `dynamic` from the list of library ways but keep +`rts` package ways unchanged: ```haskell -- | Control which ways library packages are built. userLibraryWays :: Ways @@ -99,9 +99,8 @@ userRtsWays = mempty ## Verbose command lines By default Hadrian does not print full command lines during the build process -and instead prints short human readable digests for each executed command. It is -possible to suppress this behaviour completely or partially using -`verboseCommands` setting: +and instead prints short human readable digests for each executed command. You +can suppress this behaviour completely or partially using `verboseCommands` setting: ```haskell -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package @@ -129,3 +128,19 @@ verboseCommands = file "//rts/sm/*" &&^ way threaded -- Print all commands: verboseCommands = return True ``` + +## Miscellaneous + +Use the following settings to change the default behaviour of Hadrian with respect +to building split objects and Haddock documentation. + +```haskell +-- | Control when split objects are generated. Note, due to the GHC bug #11315 +-- it is necessary to do a full clean rebuild when changing this option. +splitObjects :: Predicate +splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects + +-- | Control when to build documentation. +buildHaddock :: Predicate +buildHaddock = return cmdBuildHaddock +``` From git at git.haskell.org Fri Oct 27 00:30:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to build flavours doc (e03bcf6) Message-ID: <20171027003050.C35623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e03bcf6b16e3ded4948bd370daab3a05098e32d5/ghc >--------------------------------------------------------------- commit e03bcf6b16e3ded4948bd370daab3a05098e32d5 Author: Andrey Mokhov Date: Thu Jan 12 01:03:13 2017 +0000 Link to build flavours doc [skip ci] >--------------------------------------------------------------- e03bcf6b16e3ded4948bd370daab3a05098e32d5 doc/user-settings.md | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 9d776ea..9207f7f 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -34,7 +34,9 @@ data Flavour = Flavour , ghcProfiled :: Bool -- ^ Build profiled GHC. , ghcDebugged :: Bool } -- ^ Build GHC with debug information. ``` -Hadrian provides several built-in flavours (`defaultFlavour`, `quickFlavour`, and +Hadrian provides several +[built-in flavours](https://github.com/snowleopard/hadrian/blob/master/doc/flavours.md) +(`defaultFlavour`, `quickFlavour`, and a few others), which can be activated from the command line, e.g. `--flavour=quick`. Users can define new build flavours by adding them to `userFlavours` list: ```haskell From git at git.haskell.org Fri Oct 27 00:30:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move copyRules to Rules/Generate.hs, add missing generated dependencies. (03b3379) Message-ID: <20171027003051.4B02D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03b33797d88b27291c6a05f6141fac18be30efc4/ghc >--------------------------------------------------------------- commit 03b33797d88b27291c6a05f6141fac18be30efc4 Author: Andrey Mokhov Date: Thu Jan 7 17:02:35 2016 +0000 Move copyRules to Rules/Generate.hs, add missing generated dependencies. >--------------------------------------------------------------- 03b33797d88b27291c6a05f6141fac18be30efc4 shaking-up-ghc.cabal | 1 - src/Main.hs | 3 +-- src/Rules.hs | 2 +- src/Rules/Copy.hs | 20 -------------------- src/Rules/Generate.hs | 18 ++++++++++++++++-- 5 files changed, 18 insertions(+), 26 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index c680b85..9f2c80c 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -39,7 +39,6 @@ executable ghc-shake , Rules.Cabal , Rules.Compile , Rules.Config - , Rules.Copy , Rules.Data , Rules.Dependencies , Rules.Documentation diff --git a/src/Main.hs b/src/Main.hs index 043e173..07f14ea 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,7 +3,6 @@ import Rules import Rules.Cabal import Rules.Config import Rules.Generate -import Rules.Copy import Rules.Libffi import Rules.IntegerGmp import Rules.Oracles @@ -12,7 +11,7 @@ main :: IO () main = shakeArgs options $ do cabalRules -- see Rules.Cabal configRules -- see Rules.Config - copyRules -- see Rules.Copy + copyRules -- see Rules.Generate generateTargets -- see Rules generateRules -- see Rules.Generate libffiRules -- see Rules.Libffi diff --git a/src/Rules.hs b/src/Rules.hs index 9933225..22c5230 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -3,7 +3,7 @@ module Rules (generateTargets, packageRules) where import Base import Expression import GHC -import Rules.Copy +import Rules.Generate import Rules.Package import Rules.Resources import Settings diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs deleted file mode 100644 index 7454fd9..0000000 --- a/src/Rules/Copy.hs +++ /dev/null @@ -1,20 +0,0 @@ -module Rules.Copy (installTargets, copyRules) where - -import Base -import Expression -import GHC -import Rules.Actions -import Rules.Generate - -installTargets :: [FilePath] -installTargets = [ "inplace/lib/template-hsc.h" - , "inplace/lib/platformConstants" - , "inplace/lib/settings" ] - -copyRules :: Rules () -copyRules = do - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs - "inplace/lib/platformConstants" <~ derivedConstantsPath - "inplace/lib/settings" <~ "." - where - file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8ca7b94..71d88b1 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,7 @@ module Rules.Generate ( generatePackageCode, generateRules, - derivedConstantsPath, generatedDependencies + derivedConstantsPath, generatedDependencies, + installTargets, copyRules ) where import Base @@ -20,6 +21,11 @@ import Rules.Resources (Resources) import Settings import Settings.Builders.DeriveConstants +installTargets :: [FilePath] +installTargets = [ "inplace/lib/template-hsc.h" + , "inplace/lib/platformConstants" + , "inplace/lib/settings" ] + primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -45,7 +51,7 @@ ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> , "autogen/GHC/Prim.hs" ] derivedConstantsDependencies :: [FilePath] -derivedConstantsDependencies = (derivedConstantsPath -/-) <$> +derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) [ "DerivedConstants.h" , "GHCConstantsHaskellType.hs" , "GHCConstantsHaskellWrappers.hs" @@ -150,6 +156,14 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = copyFileChanged (pkgPath pkg -/- "runghc.hs") file putSuccess $ "| Successfully generated '" ++ file ++ "'." +copyRules :: Rules () +copyRules = do + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs + "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." + where + file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file + generateRules :: Rules () generateRules = do "includes/ghcautoconf.h" <~ generateGhcAutoconfH From git at git.haskell.org Fri Oct 27 00:30:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comments (b91d515) Message-ID: <20171027003051.6EEE43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b91d5152c1979d7c36cb2ab16821abec8da7ec1c/ghc >--------------------------------------------------------------- commit b91d5152c1979d7c36cb2ab16821abec8da7ec1c Author: Andrey Mokhov Date: Sun May 15 00:03:12 2016 +0100 Comments [skip ci] >--------------------------------------------------------------- b91d5152c1979d7c36cb2ab16821abec8da7ec1c src/Settings/User.hs | 38 +++++++++++++++++++++----------------- 1 file changed, 21 insertions(+), 17 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 2294fc7..7cf9997 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -12,40 +12,44 @@ import Expression import Predicates import Settings.Default --- | All build artefacts are stored in 'buildRootPath' directory. +-- See doc/user-settings.md for instructions. + +-- | All build results are put into 'buildRootPath' directory. buildRootPath :: FilePath buildRootPath = "_build" --- | Control user-specific command line arguments. +-- | Modify default build command line arguments. userArgs :: Args userArgs = builder Ghc ? remove ["-Wall", "-fwarn-tabs"] --- | Control which packages get to be built. +-- | Modify the set of packages that are built by default in each stage. userPackages :: Packages userPackages = mempty --- | Add new user-defined packages. +-- | Add user defined packages. Don't forget to add them to 'userPackages' too. userKnownPackages :: [Package] userKnownPackages = [] --- | Choose the integer library: integerGmp or integerSimple. +-- | Choose the integer library: 'integerGmp' or 'integerSimple'. integerLibrary :: Package integerLibrary = integerGmp --- | Control which ways library packages are built. --- FIXME: skip dynamic since it's currently broken #4 +-- FIXME: We skip 'dynamic' since it's currently broken #4. +-- | Modify the set of ways in which library packages are built. userLibraryWays :: Ways userLibraryWays = remove [dynamic] --- | Control which ways the 'rts' package is built. +-- | Modify the set of ways in which the 'rts' package is built. userRtsWays :: Ways userRtsWays = mempty --- | User-defined flags. Note the following type semantics: --- * Bool: a plain Boolean flag whose value is known at compile time --- * Action Bool: a flag whose value can depend on the build environment --- * Predicate: a flag depending on the build environment and the current target +-- | User defined flags. Note the following type semantics: +-- * @Bool@: a plain Boolean flag whose value is known at compile time. +-- * @Action Bool@: a flag whose value can depend on the build environment. +-- * @Predicate@: a flag whose value can depend on the build environment and +-- on the current build target. +-- TODO: Drop 'trackBuildSystem' as it brings negligible gains. -- | Set this to True if you are making any changes in the build system and want -- appropriate rebuilds to be initiated. Switching this to False speeds things -- up a little (particularly zero builds). @@ -62,12 +66,12 @@ validating = False splitObjects :: Predicate splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects --- | Control when to build documentation. +-- | Control when to build Haddock documentation. buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock -- TODO: Do we need to be able to set these from command line? --- TODO: Turn below into ghcWays? +-- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? dynamicGhcPrograms :: Bool dynamicGhcPrograms = False @@ -81,12 +85,12 @@ ghcDebugged :: Bool ghcDebugged = False -- | Set to True to print full command lines during the build process. Note, --- this is a Predicate, hence you can enable verbose output for a chosen package --- only, e.g.: verboseCommands = package ghcPrim. +-- this is a Predicate, hence you can enable verbose output only for certain +-- targets, e.g.: @verboseCommands = package ghcPrim at . verboseCommands :: Predicate verboseCommands = return False --- TODO: Replace with stage2 ? arg "-Werror"? +-- TODO: Replace with stage2 ? arg "-Werror"? Also see #251. -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False From git at git.haskell.org Fri Oct 27 00:30:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update notes on build ways and flavours (3d4e548) Message-ID: <20171027003054.BA9893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d4e54873fceedee20c3e0c0fbb56598030252a9/ghc >--------------------------------------------------------------- commit 3d4e54873fceedee20c3e0c0fbb56598030252a9 Author: Andrey Mokhov Date: Thu Jan 12 01:15:19 2017 +0000 Update notes on build ways and flavours [skip ci] >--------------------------------------------------------------- 3d4e54873fceedee20c3e0c0fbb56598030252a9 README.md | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 0d7b3d8..109f7f0 100644 --- a/README.md +++ b/README.md @@ -6,7 +6,7 @@ Hadrian Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current [`make`-based build system][make]. If you are curious about the rationale behind the -project and the architecture of the new build system you can find more details in +project and the architecture of the build system you can find more details in this [Haskell Symposium 2016 paper][paper] and this [Haskell eXchange 2016 talk][talk]. The new build system can work side-by-side with the existing build system. Note, there is @@ -52,9 +52,11 @@ are placed into `_build` and `inplace` directories. In addition to standard Shake flags (try `--help`), the build system currently supports several others: -* `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: -`default` and `quick` (adds `-O0` flag to all GHC invocations and disables library -profiling, which speeds up builds by 3-4x). +* `--flavour=FLAVOUR`: choose a build flavour. The following settings are currently supported: +`default`, `quick`, `quickest`, `perf`, `prof`, `devel1` and `devel2`. As an example, the +`quickest` flavour adds `-O0` flag to all GHC invocations and builds libraries only in the +`vanilla` way, which speeds up builds by 3-4x. Build flavours are documented +[here](https://github.com/snowleopard/hadrian/blob/master/doc/flavours.md). * `--haddock`: build Haddock documentation. @@ -117,10 +119,10 @@ zero (see [#197][test-issue]). Current limitations ------------------- The new build system still lacks many important features: -* We only build `vanilla` and `profiling` way: [#4][dynamic-issue]. +* There is currently no support for the `dynamic` build way: [#4][dynamic-issue]. * Validation is not implemented: [#187][validation-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). -* Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. +* Not all modes of the old build system are supported, e.g. [#250][freeze-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. * There is no support for installation or binary distribution: [#219][install-issue]. @@ -159,7 +161,7 @@ helped me endure and enjoy the project. [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 -[flavours-issue]: https://github.com/snowleopard/hadrian/issues/188 +[freeze-issue]: https://github.com/snowleopard/hadrian/issues/250 [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 [milestones]: https://github.com/snowleopard/hadrian/milestones From git at git.haskell.org Fri Oct 27 00:30:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddock comments in Predicates.hs (de634da) Message-ID: <20171027003055.082B43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de634dadaf365799b3e0b8945ec812b2bec37c74/ghc >--------------------------------------------------------------- commit de634dadaf365799b3e0b8945ec812b2bec37c74 Author: David Luposchainsky Date: Wed Jan 6 14:31:37 2016 +0100 Add Haddock comments in Predicates.hs >--------------------------------------------------------------- de634dadaf365799b3e0b8945ec812b2bec37c74 src/Predicates.hs | 23 +++++++++++++++++------ 1 file changed, 17 insertions(+), 6 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index ad63598..b5ce0cb 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -7,49 +7,60 @@ module Predicates ( import Base import Expression --- Basic predicates +-- | Is the build currently in the provided stage? stage :: Stage -> Predicate stage s = fmap (s ==) getStage +-- | Is a particular package being built? package :: Package -> Predicate package p = fmap (p ==) getPackage --- For unstaged builders, e.g. GhcCabal +-- | Is an unstaged builder is being used such as /GhcCabal/? builder :: Builder -> Predicate builder b = fmap (b ==) getBuilder --- For staged builders, e.g. Ghc Stage +-- | Is a certain builder used in the current stage? stagedBuilder :: (Stage -> Builder) -> Predicate -stagedBuilder sb = (builder . sb) =<< getStage +stagedBuilder stageBuilder = do + s <- getStage + builder (stageBuilder s) +-- | Are we building with GCC? builderGcc :: Predicate builderGcc = stagedBuilder Gcc ||^ stagedBuilder GccM +-- | Are we building with GHC? builderGhc :: Predicate builderGhc = stagedBuilder Ghc ||^ stagedBuilder GhcM +-- | Does any of the output files match a given pattern? file :: FilePattern -> Predicate file f = fmap (any (f ?==)) getOutputs +-- | Is the current build 'Way' equal to a certain value? way :: Way -> Predicate way w = fmap (w ==) getWay --- Derived predicates +-- | Is the build currently in stage 0? stage0 :: Predicate stage0 = stage Stage0 +-- | Is the build currently in stage 1? stage1 :: Predicate stage1 = stage Stage1 +-- | Is the build currently in stage 2? stage2 :: Predicate stage2 = stage Stage2 +-- | Is the build /not/ in stage 0 right now? notStage0 :: Predicate notStage0 = notM stage0 +-- | Is a certain package /not/ built right now? notPackage :: Package -> Predicate notPackage = notM . package --- TODO: Actually, we don't register compiler in some circumstances -- fix. +-- | TODO: Actually, we don't register compiler in some circumstances -- fix. registerPackage :: Predicate registerPackage = return True From git at git.haskell.org Fri Oct 27 00:30:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unix line endings, match Haddock comments in Settings/User.hs (3ff4183) Message-ID: <20171027003055.3E35A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ff4183c5741ca780fb4e4b7274b7d951430fdde/ghc >--------------------------------------------------------------- commit 3ff4183c5741ca780fb4e4b7274b7d951430fdde Author: Andrey Mokhov Date: Sun May 15 00:11:25 2016 +0100 Unix line endings, match Haddock comments in Settings/User.hs [skip ci] >--------------------------------------------------------------- 3ff4183c5741ca780fb4e4b7274b7d951430fdde doc/user-settings.md | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index dc718ed..e6b81f8 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -8,7 +8,7 @@ You can customise Hadrian by specifying user build settings in file Hadrian puts build results into `_build` directory by default, which is specified by `buildRootPath`: ```haskell --- | All build artefacts are stored in 'buildRootPath' directory. +-- | All build results are put into 'buildRootPath' directory. buildRootPath :: FilePath buildRootPath = "_build" ``` @@ -22,7 +22,7 @@ affected build rules during the next build, without requiring a full rebuild. For example, here is how to pass an extra argument `-O0` to all invocations of GHC when compiling package `cabal`: ```haskell --- | Control user-specific command line arguments. +-- | Modify default build command line arguments. userArgs :: Args userArgs = builder Ghc ? package cabal ? arg "-O0" ``` @@ -52,7 +52,7 @@ To add or remove a package from a particular build stage, use `userPackages`. As an example, below we add package `base` to Stage0 and remove package `haskeline` from Stage1: ```haskell --- | Control which packages get to be built. +-- | Modify the set of packages that are built by default in each stage. userPackages :: Packages userPackages = mconcat [ stage0 ? append [base] @@ -61,7 +61,7 @@ userPackages = mconcat If you are working on a new GHC package you need to let Hadrian know about it by setting `userKnownPackages`: ```haskell --- | Add new user-defined packages. +-- | Add user defined packages. Don't forget to add them to 'userPackages' too. userKnownPackages :: [Package] userKnownPackages = [myPackage] @@ -73,9 +73,9 @@ Note, you will also need to add `myPackage` to a specific build stage by modifyi `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting -`integerLibrary`: +`integerLibrary`. Possible values are: `integerGmp` (default) and `integerSimple`. ```haskell --- | Choose the integer library: integerGmp or integerSimple. +-- | Choose the integer library: 'integerGmp' or 'integerSimple'. integerLibrary :: Package integerLibrary = integerGmp ``` @@ -87,11 +87,11 @@ can change the default build ways using `userLibraryWays` and `userRtsWays` sett As an example, below we remove `dynamic` from the list of library ways but keep `rts` package ways unchanged: ```haskell --- | Control which ways library packages are built. +-- | Modify the set of ways in which library packages are built. userLibraryWays :: Ways userLibraryWays = remove [dynamic] --- | Control which ways the 'rts' package is built. +-- | Modify the set of ways in which the 'rts' package is built. userRtsWays :: Ways userRtsWays = mempty ``` @@ -103,8 +103,8 @@ and instead prints short human readable digests for each executed command. You can suppress this behaviour completely or partially using `verboseCommands` setting: ```haskell -- | Set to True to print full command lines during the build process. Note, --- this is a Predicate, hence you can enable verbose output for a chosen package --- only, e.g.: verboseCommands = package ghcPrim +-- this is a Predicate, hence you can enable verbose output only for certain +-- targets, e.g.: @verboseCommands = package ghcPrim at . verboseCommands :: Predicate verboseCommands = return False ``` @@ -140,7 +140,7 @@ to building split objects and Haddock documentation. splitObjects :: Predicate splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects --- | Control when to build documentation. +-- | Control when to build Haddock documentation. buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock ``` From git at git.haskell.org Fri Oct 27 00:30:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't modify ways in development flavours (084ce3b) Message-ID: <20171027003058.786313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/084ce3b4f5fdfbfa83786d96805698a9170b9b0f/ghc >--------------------------------------------------------------- commit 084ce3b4f5fdfbfa83786d96805698a9170b9b0f Author: Andrey Mokhov Date: Thu Jan 12 01:24:26 2017 +0000 Don't modify ways in development flavours >--------------------------------------------------------------- 084ce3b4f5fdfbfa83786d96805698a9170b9b0f src/Settings/Flavours/Development.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index 4314a64..a90c157 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -9,8 +9,7 @@ import Settings.Optimisation developmentFlavour :: Stage -> Flavour developmentFlavour ghcStage = defaultFlavour { name = "devel" ++ show (fromEnum ghcStage) - , args = defaultBuilderArgs <> developmentArgs ghcStage <> defaultPackageArgs - , libraryWays = append [vanilla] } + , args = defaultBuilderArgs <> developmentArgs ghcStage <> defaultPackageArgs } developmentArgs :: Stage -> Args developmentArgs ghcStage = do From git at git.haskell.org Fri Oct 27 00:30:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make value sources more explicit (921dcce) Message-ID: <20171027003058.EAB833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/921dcce1ab2e0cc1e6df25df98bb24f134fe0742/ghc >--------------------------------------------------------------- commit 921dcce1ab2e0cc1e6df25df98bb24f134fe0742 Author: David Luposchainsky Date: Tue Jan 5 16:44:06 2016 +0100 Make value sources more explicit [skip ci] Rather than relying on comments, move the documentation into the source, so it's checked by the compiler automatically >--------------------------------------------------------------- 921dcce1ab2e0cc1e6df25df98bb24f134fe0742 src/Main.hs | 40 ++++++++++++++++++++++------------------ 1 file changed, 22 insertions(+), 18 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 07f14ea..bacc8f1 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,24 +1,28 @@ -import Base -import Rules -import Rules.Cabal -import Rules.Config -import Rules.Generate -import Rules.Libffi -import Rules.IntegerGmp -import Rules.Oracles +module Main (main) where + +import qualified Base as B +import qualified Rules as R +import qualified Rules.Cabal as RCabal +import qualified Rules.Config as RConfig +import qualified Rules.Copy as RCopy +import qualified Rules.Generate as RGen +import qualified Rules.IntegerGmp as RInt +import qualified Rules.Libffi as RFfi +import qualified Rules.Oracles as ROracle main :: IO () -main = shakeArgs options $ do - cabalRules -- see Rules.Cabal - configRules -- see Rules.Config - copyRules -- see Rules.Generate - generateTargets -- see Rules - generateRules -- see Rules.Generate - libffiRules -- see Rules.Libffi - integerGmpRules -- see Rules.IntegerGmp - oracleRules -- see Rules.Oracles - packageRules -- see Rules +main = shakeArgs options rules where + rules = mconcat + [ RCabal.cabalRules + , RConfig.configRules + , RCopy.copyRules + , R.generateTargets + , RGen.generateRules + , RFfi.libffiRules + , RInt.integerGmpRules + , ROracle.oracleRules + , R.packageRules ] options = shakeOptions { shakeFiles = shakeFilesPath , shakeProgress = progressSimple From git at git.haskell.org Fri Oct 27 00:30:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:30:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix predicate (c8725b2) Message-ID: <20171027003059.0B5643A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8725b225655b0d7f320cff4ebff1fb1918311f4/ghc >--------------------------------------------------------------- commit c8725b225655b0d7f320cff4ebff1fb1918311f4 Author: Andrey Mokhov Date: Sun May 15 00:14:34 2016 +0100 Fix predicate [skip ci] >--------------------------------------------------------------- c8725b225655b0d7f320cff4ebff1fb1918311f4 doc/user-settings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index e6b81f8..4624e2d 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -123,7 +123,7 @@ verboseCommands = builder (Ghc Link) verboseCommands = builder (Gcc Compile) &&^ package compiler -- Use patterns when matching files: -verboseCommands = file "//rts/sm/*" &&^ way threaded +verboseCommands = output "//rts/sm/*" &&^ way threaded -- Print all commands: verboseCommands = return True From git at git.haskell.org Fri Oct 27 00:31:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Settings.Optimisation to Settings.SourceArgs (71b2b96) Message-ID: <20171027003102.5EA003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/71b2b96820f4ac6100840c3782d7d9fbabc6dac7/ghc >--------------------------------------------------------------- commit 71b2b96820f4ac6100840c3782d7d9fbabc6dac7 Author: Andrey Mokhov Date: Thu Jan 12 12:21:54 2017 +0000 Rename Settings.Optimisation to Settings.SourceArgs >--------------------------------------------------------------- 71b2b96820f4ac6100840c3782d7d9fbabc6dac7 hadrian.cabal | 2 +- src/Settings/Default.hs | 8 ++++---- src/Settings/Flavours/Development.hs | 4 ++-- src/Settings/Flavours/Performance.hs | 4 ++-- src/Settings/Flavours/Profiled.hs | 4 ++-- src/Settings/Flavours/Quick.hs | 4 ++-- src/Settings/Flavours/Quickest.hs | 4 ++-- src/Settings/{Optimisation.hs => SourceArgs.hs} | 10 +++++----- 8 files changed, 20 insertions(+), 20 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index d3ef74c..c8cb0b7 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -90,7 +90,7 @@ executable hadrian , Settings.Flavours.Profiled , Settings.Flavours.Quick , Settings.Flavours.Quickest - , Settings.Optimisation + , Settings.SourceArgs , Settings.Packages.Base , Settings.Packages.Compiler , Settings.Packages.Ghc diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 2a9fae4..3aa3a65 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -27,7 +27,7 @@ import Settings.Builders.HsCpp import Settings.Builders.Ld import Settings.Builders.Make import Settings.Builders.Tar -import Settings.Optimisation +import Settings.SourceArgs import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Ghc @@ -43,12 +43,12 @@ import Settings.Packages.RunGhc defaultArgs :: Args defaultArgs = mconcat [ defaultBuilderArgs - , optimisationArgs defaultOptimisation + , sourceArgs defaultSourceArgs , defaultPackageArgs ] -- | Default optimisation settings. -defaultOptimisation :: Optimisation -defaultOptimisation = Optimisation +defaultSourceArgs :: SourceArgs +defaultSourceArgs = SourceArgs { hsDefault = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2", arg "-H32m"] , hsLibrary = mempty , hsCompiler = mempty diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index a90c157..f3f9499 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Development (developmentFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs -- TODO: Implement an equivalent of LAX_DEPENDENCIES = YES setting, see #250. developmentFlavour :: Stage -> Flavour @@ -14,7 +14,7 @@ developmentFlavour ghcStage = defaultFlavour developmentArgs :: Stage -> Args developmentArgs ghcStage = do stage <- getStage - optimisationArgs $ Optimisation + sourceArgs $ SourceArgs { hsDefault = append ["-O", "-H64m"] , hsLibrary = notStage0 ? arg "-dcore-lint" , hsCompiler = succ stage == ghcStage ? append ["-O0", "-DDEBUG"] diff --git a/src/Settings/Flavours/Performance.hs b/src/Settings/Flavours/Performance.hs index 69e244a..ae3197e 100644 --- a/src/Settings/Flavours/Performance.hs +++ b/src/Settings/Flavours/Performance.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Performance (performanceFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs performanceFlavour :: Flavour performanceFlavour = defaultFlavour @@ -11,7 +11,7 @@ performanceFlavour = defaultFlavour , args = defaultBuilderArgs <> performanceArgs <> defaultPackageArgs } performanceArgs :: Args -performanceArgs = optimisationArgs $ Optimisation +performanceArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O", "-H64m"] , hsLibrary = notStage0 ? arg "-O2" , hsCompiler = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2"] diff --git a/src/Settings/Flavours/Profiled.hs b/src/Settings/Flavours/Profiled.hs index 0a1a6ed..b3f9117 100644 --- a/src/Settings/Flavours/Profiled.hs +++ b/src/Settings/Flavours/Profiled.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Profiled (profiledFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs profiledFlavour :: Flavour profiledFlavour = defaultFlavour @@ -12,7 +12,7 @@ profiledFlavour = defaultFlavour , ghcProfiled = True } profiledArgs :: Args -profiledArgs = optimisationArgs $ Optimisation +profiledArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O0", "-H64m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = arg "-O" diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index dd9cd58..565e748 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Quick (quickFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs quickFlavour :: Flavour quickFlavour = defaultFlavour @@ -13,7 +13,7 @@ quickFlavour = defaultFlavour -- TODO: the hsLibrary setting seems wrong, but it matches mk/flavours/quick.mk quickArgs :: Args -quickArgs = optimisationArgs $ Optimisation +quickArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O0", "-H64m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = stage0 ? arg "-O" diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 0473dc6..abb2ccf 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Quickest (quickestFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs quickestFlavour :: Flavour quickestFlavour = defaultFlavour @@ -13,7 +13,7 @@ quickestFlavour = defaultFlavour , rtsWays = quickestRtsWays } quickestArgs :: Args -quickestArgs = optimisationArgs $ Optimisation +quickestArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O0", "-H64m"] , hsLibrary = mempty , hsCompiler = mempty diff --git a/src/Settings/Optimisation.hs b/src/Settings/SourceArgs.hs similarity index 66% rename from src/Settings/Optimisation.hs rename to src/Settings/SourceArgs.hs index 6d47941..0c638ca 100644 --- a/src/Settings/Optimisation.hs +++ b/src/Settings/SourceArgs.hs @@ -1,17 +1,17 @@ -module Settings.Optimisation (Optimisation (..), optimisationArgs) where +module Settings.SourceArgs (SourceArgs (..), sourceArgs) where import GHC import Predicate --- TODO: Move C optimisation settings here -data Optimisation = Optimisation +-- TODO: Move C source arguments here +data SourceArgs = SourceArgs { hsDefault :: Args , hsLibrary :: Args , hsCompiler :: Args , hsGhc :: Args } -optimisationArgs :: Optimisation -> Args -optimisationArgs Optimisation {..} = do +sourceArgs :: SourceArgs -> Args +sourceArgs SourceArgs {..} = do hsCompile <- builder $ Ghc CompileHs hsLink <- builder $ Ghc LinkHs pkg <- getPackage From git at git.haskell.org Fri Oct 27 00:31:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split up definitions in Rules.hs (20381e5) Message-ID: <20171027003102.74B053A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20381e58208ca2693f034566e450f5b0b28674b4/ghc >--------------------------------------------------------------- commit 20381e58208ca2693f034566e450f5b0b28674b4 Author: David Luposchainsky Date: Wed Jan 6 14:49:58 2016 +0100 Split up definitions in Rules.hs >--------------------------------------------------------------- 20381e58208ca2693f034566e450f5b0b28674b4 src/Rules.hs | 33 ++++++++++++++++++++------------- 1 file changed, 20 insertions(+), 13 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 22c5230..f8b2810 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,6 +1,8 @@ module Rules (generateTargets, packageRules) where import Base +import Data.Foldable +import Data.Traversable import Expression import GHC import Rules.Generate @@ -8,26 +10,31 @@ import Rules.Package import Rules.Resources import Settings +allStages :: [Stage] +allStages = [Stage0 ..] + -- TODO: not all program targets should be needed explicitly --- | generateTargets needs top-level build targets +-- | 'need' all top-level build targets generateTargets :: Rules () generateTargets = action $ do - targets <- fmap concat . forM [Stage0 ..] $ \stage -> do - pkgs <- interpretWithStage stage getPackages - let libPkgs = filter isLibrary pkgs \\ [rts, libffi] - libTargets <- fmap concat . forM libPkgs $ \pkg -> do - let target = PartialTarget stage pkg - needHaddock <- interpretPartial target buildHaddock - return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] - let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] - return $ libTargets ++ programTargets - + targets <- fmap concat (traverse targetsForStage allStages) rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla need $ targets ++ installTargets ++ [ rtsLib ] +targetsForStage :: Stage -> Action [String] +targetsForStage stage = do + pkgs <- interpretWithStage stage getPackages + let libPkgs = filter isLibrary pkgs \\ [rts, libffi] + libTargets <- fmap concat . for libPkgs $ \pkg -> do + let target = PartialTarget stage pkg + needHaddock <- interpretPartial target buildHaddock + return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] + let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] + return (libTargets ++ programTargets) + packageRules :: Rules () packageRules = do resources <- resourceRules - forM_ [Stage0 ..] $ \stage -> - forM_ knownPackages $ \pkg -> + for allStages $ \stage -> + for_ knownPackages $ \pkg -> buildPackage resources $ PartialTarget stage pkg From git at git.haskell.org Fri Oct 27 00:31:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify (2ac9e71) Message-ID: <20171027003102.D87B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ac9e71747347801d70e80e9d603a5c79c8f5d5a/ghc >--------------------------------------------------------------- commit 2ac9e71747347801d70e80e9d603a5c79c8f5d5a Author: Andrey Mokhov Date: Sun May 15 00:20:54 2016 +0100 Simplify >--------------------------------------------------------------- 2ac9e71747347801d70e80e9d603a5c79c8f5d5a src/Settings/Packages/Rts.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 60fdf7a..35a1f95 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -96,13 +96,13 @@ rtsPackageArgs = package rts ? do , builder (GhcPkg Stage1) ? mconcat [ remove ["rts/stage1/inplace-pkg-config"] -- TODO: fix, see #113 - , arg $ rtsConf ] + , arg rtsConf ] - , builder HsCpp ? mconcat - [ arg ("-DTOP=" ++ quote top) - , arg ("-DFFI_INCLUDE_DIR=" ++ quote ffiIncludeDir) - , arg ("-DFFI_LIB_DIR=" ++ quote ffiLibraryDir) - , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] + , builder HsCpp ? append + [ "-DTOP=" ++ quote top + , "-DFFI_INCLUDE_DIR=" ++ quote ffiIncludeDir + , "-DFFI_LIB_DIR=" ++ quote ffiLibraryDir + , "-DFFI_LIB=" ++ quote libffiName ] ] -- # If we're compiling on windows, enforce that we only support XP+ From git at git.haskell.org Fri Oct 27 00:31:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reorder source arguments (a63d835) Message-ID: <20171027003106.4586E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a63d83530f324bab9b3f0860d53f7198072ffd81/ghc >--------------------------------------------------------------- commit a63d83530f324bab9b3f0860d53f7198072ffd81 Author: Andrey Mokhov Date: Thu Jan 12 20:20:41 2017 +0000 Reorder source arguments >--------------------------------------------------------------- a63d83530f324bab9b3f0860d53f7198072ffd81 hadrian.cabal | 1 - src/Settings/Builders/Ghc.hs | 8 +++++--- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Default.hs | 27 +++++++++++++++++++++++---- src/Settings/Default.hs-boot | 13 +++++++++++-- src/Settings/Flavours/Development.hs | 1 - src/Settings/Flavours/Performance.hs | 1 - src/Settings/Flavours/Profiled.hs | 1 - src/Settings/Flavours/Quick.hs | 2 -- src/Settings/Flavours/Quickest.hs | 1 - src/Settings/SourceArgs.hs | 21 --------------------- 11 files changed, 40 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 a63d83530f324bab9b3f0860d53f7198072ffd81 From git at git.haskell.org Fri Oct 27 00:31:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddocks to Target.hs (1b013b0) Message-ID: <20171027003106.8F9383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b013b0886e59cdd0ff2bd7a182e874d21899961/ghc >--------------------------------------------------------------- commit 1b013b0886e59cdd0ff2bd7a182e874d21899961 Author: David Luposchainsky Date: Wed Jan 6 15:14:08 2016 +0100 Add Haddocks to Target.hs >--------------------------------------------------------------- 1b013b0886e59cdd0ff2bd7a182e874d21899961 src/Expression.hs | 4 +-- src/Target.hs | 75 ++++++++++++++++++++++++++++++++----------------------- 2 files changed, 46 insertions(+), 33 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index a2eaea9..6e2a225 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -12,7 +12,7 @@ module Expression ( -- ** Common expressions Args, Ways, Packages, -- ** Targets - Target, PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay, + Target, PartialTarget (..), unsafeFromPartial, fullTarget, fullTargetWithWay, -- * Convenient accessors getStage, getPackage, getBuilder, getOutputs, getInputs, getWay, @@ -150,7 +150,7 @@ interpret :: Target -> Expr a -> Action a interpret = flip runReaderT interpretPartial :: PartialTarget -> Expr a -> Action a -interpretPartial = interpret . fromPartial +interpretPartial = interpret . unsafeFromPartial interpretWithStage :: Stage -> Expr a -> Action a interpretWithStage s = interpretPartial $ diff --git a/src/Target.hs b/src/Target.hs index cd22f48..152de3d 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -1,7 +1,11 @@ {-# LANGUAGE DeriveGeneric, FlexibleInstances #-} module Target ( - Target (..), PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay - ) where + Target (..) + , PartialTarget (..) + , unsafeFromPartial + , fullTarget + , fullTargetWithWay +) where import Control.Monad.Trans.Reader @@ -12,50 +16,53 @@ import Package import Stage import Way --- Target captures all parameters relevant to the current build target: --- * Stage and Package being built, --- * Builder to be invoked, --- * Way to be built (set to vanilla for most targets), --- * source file(s) to be passed to Builder, --- * file(s) to be produced. +-- | Parameters relevant to the current build target. data Target = Target { - stage :: Stage, - package :: Package, - builder :: Builder, - way :: Way, - inputs :: [FilePath], - outputs :: [FilePath] + stage :: Stage, -- ^ Stage being built + package :: Package, -- ^ Package being built + builder :: Builder, -- ^ Builder to be invoked + way :: Way, -- ^ Way to build (set to vanilla for most targets) + inputs :: [FilePath], -- ^ Source files passed to the builder + outputs :: [FilePath] -- ^ Files to be produced } deriving (Show, Eq, Generic) --- If values of type 'a' form a Monoid then we can also derive a Monoid instance --- for values of type 'ReaderT Target Action a': --- * the empty computation returns the identity element of the underlying type +-- | If values of type @a@ form a 'Monoid' then we can also derive a 'Monoid' +-- instance for values of type @'ReaderT' 'Target' 'Action' a@: +-- +-- * the empty computation is the identity element of the underlying type -- * two computations can be combined by combining their results instance Monoid a => Monoid (ReaderT Target Action a) where mempty = return mempty mappend = liftM2 mappend --- PartialTarget is a partially constructed Target with fields Stage and --- Package only. PartialTarget's are used for generating build rules. +-- A partially constructed Target with fields 'Stage' and 'Package' only. +-- 'PartialTarget's are used for generating build rules. data PartialTarget = PartialTarget Stage Package deriving (Eq, Show) --- Convert PartialTarget to Target assuming that unknown fields won't be used. -fromPartial :: PartialTarget -> Target -fromPartial (PartialTarget s p) = Target +-- | Convert 'PartialTarget' to a 'Target' assuming that unknown fields won't +-- be used. +unsafeFromPartial :: PartialTarget -> Target +unsafeFromPartial (PartialTarget s p) = Target { stage = s, package = p, - builder = error "fromPartial: builder not set", - way = error "fromPartial: way not set", - inputs = error "fromPartial: inputs not set", - outputs = error "fromPartial: outputs not set" + builder = error "unsafeFromPartial: builder not set", + way = error "unsafeFromPartial: way not set", + inputs = error "unsafeFromPartial: inputs not set", + outputs = error "unsafeFromPartial: outputs not set" } --- Construct a full target by augmenting a PartialTarget with missing fields. --- Most targets are built only one way, vanilla, hence we set it by default. -fullTarget :: PartialTarget -> Builder -> [FilePath] -> [FilePath] -> Target +-- | Construct a full 'Target' by augmenting a 'PartialTarget' with missing +-- fields. Most targets are built only one way, 'vanilla', hence it is set by +-- default. Use 'fullTargetWithWay' otherwise. +fullTarget :: + PartialTarget + -> Builder + -> [FilePath] -- ^ Source files + -> [FilePath] -- ^ Produced files + -> Target fullTarget (PartialTarget s p) b srcs fs = Target { stage = s, @@ -66,8 +73,14 @@ fullTarget (PartialTarget s p) b srcs fs = Target outputs = map unifyPath fs } --- Use this function to be explicit about the build way. -fullTargetWithWay :: PartialTarget -> Builder -> Way -> [FilePath] -> [FilePath] -> Target +-- | Like 'fullTarget', but allows an explicit 'Way' parameter. +fullTargetWithWay :: + PartialTarget + -> Builder + -> Way + -> [FilePath] -- ^ Source files + -> [FilePath] -- ^ Produced files + -> Target fullTargetWithWay pt b w srcs fs = (fullTarget pt b srcs fs) { way = w } -- Instances for storing in the Shake database From git at git.haskell.org Fri Oct 27 00:31:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop non-derived Show instance for PackageName (dc0bae1) Message-ID: <20171027003106.D0BAE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dc0bae1e5aeb05e5704e38a8aa5c64887165fcc6/ghc >--------------------------------------------------------------- commit dc0bae1e5aeb05e5704e38a8aa5c64887165fcc6 Author: Andrey Mokhov Date: Sun May 15 00:47:13 2016 +0100 Drop non-derived Show instance for PackageName >--------------------------------------------------------------- dc0bae1e5aeb05e5704e38a8aa5c64887165fcc6 src/Oracles/PackageDeps.hs | 8 ++++---- src/Package.hs | 21 +++++++++------------ 2 files changed, 13 insertions(+), 16 deletions(-) diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index a2a9234..7983c7f 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -7,7 +7,7 @@ import Base import Package import Settings.Paths -newtype PackageDepsKey = PackageDepsKey PackageName +newtype PackageDepsKey = PackageDepsKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- @packageDeps name@ is an action that given a 'Package' looks up its @@ -15,8 +15,8 @@ newtype PackageDepsKey = PackageDepsKey PackageName -- computed by scanning package cabal files (see Rules.Cabal). packageDeps :: Package -> Action [PackageName] packageDeps pkg = do - res <- askOracle . PackageDepsKey . pkgName $ pkg - return . fromMaybe [] $ res + res <- askOracle . PackageDepsKey $ pkgNameString pkg + return . map PackageName $ fromMaybe [] res -- Oracle for the package dependencies file packageDepsOracle :: Rules () @@ -25,6 +25,6 @@ packageDepsOracle = do putOracle $ "Reading package dependencies..." contents <- readFileLines packageDependencies return . Map.fromList $ - [ (p, ps) | line <- contents, let p:ps = map PackageName $ words line ] + [ (p, ps) | line <- contents, let p:ps = words line ] _ <- addOracle $ \(PackageDepsKey pkg) -> Map.lookup pkg <$> deps () return () diff --git a/src/Package.hs b/src/Package.hs index 4b6fbc6..1fc1ac9 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -15,12 +15,9 @@ import GHC.Generics (Generic) import Data.String -- | The name of a Cabal package -newtype PackageName = PackageName { getPackageName :: String } +newtype PackageName = PackageName { fromPackageName :: String } deriving (Eq, Ord, IsString, Generic, Binary, Hashable, Typeable, NFData) -instance Show PackageName where - show (PackageName name) = name - -- TODO: Make PackageType more precise, #12 -- TODO: Turn Program to Program FilePath thereby getting rid of programPath -- | We regard packages as either being libraries or programs. This is @@ -37,23 +34,23 @@ data Package = Package -- | Prettyprint Package name. pkgNameString :: Package -> String -pkgNameString = getPackageName . pkgName +pkgNameString = fromPackageName . pkgName -- | Relative path to cabal file, e.g.: "libraries/Cabal/Cabal/Cabal.cabal" pkgCabalFile :: Package -> FilePath -pkgCabalFile pkg = pkgPath pkg -/- getPackageName (pkgName pkg) <.> "cabal" +pkgCabalFile pkg = pkgPath pkg -/- pkgNameString pkg <.> "cabal" -- | Smart constructor for a top-level package, e.g. 'compiler'. topLevel :: PackageName -> Package -topLevel name = Package name (getPackageName name) Library +topLevel name = Package name (fromPackageName name) Library -- | Smart constructor for a library package, e.g. 'array'. library :: PackageName -> Package -library name = Package name ("libraries" -/- getPackageName name) Library +library name = Package name ("libraries" -/- fromPackageName name) Library -- | Smart constructor for a utility package, e.g. 'haddock'. utility :: PackageName -> Package -utility name = Package name ("utils" -/- getPackageName name) Program +utility name = Package name ("utils" -/- fromPackageName name) Program -- | Amend package path. Useful when a package name doesn't match its path. setPath :: Package -> FilePath -> Package @@ -65,17 +62,17 @@ setType pkg ty = pkg { pkgType = ty } -- | Check whether a package is a library. isLibrary :: Package -> Bool -isLibrary (Package {pkgType=Library}) = True +isLibrary (Package _ _ Library) = True isLibrary _ = False -- | Check whether a package is a program. isProgram :: Package -> Bool -isProgram (Package {pkgType=Program}) = True +isProgram (Package _ _ Program) = True isProgram _ = False -- TODO: Get rid of non-derived Show instances. instance Show Package where - show = show . pkgName + show = pkgNameString instance Eq Package where (==) = (==) `on` pkgName From git at git.haskell.org Fri Oct 27 00:31:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --integer-simple command line argument (b42cac6) Message-ID: <20171027003110.34A073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b42cac65d1a65a101179613dba66d3b711948b84/ghc >--------------------------------------------------------------- commit b42cac65d1a65a101179613dba66d3b711948b84 Author: Andrey Mokhov Date: Thu Jan 12 23:31:50 2017 +0000 Add --integer-simple command line argument See #179 >--------------------------------------------------------------- b42cac65d1a65a101179613dba66d3b711948b84 src/CmdLineFlag.hs | 16 +++++++++++++--- src/Settings/Default.hs | 2 +- 2 files changed, 14 insertions(+), 4 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index ebe907a..961a033 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,7 +1,7 @@ module CmdLineFlag ( - putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, cmdProgressColour, - ProgressColour (..), cmdProgressInfo, ProgressInfo (..), cmdSkipConfigure, - cmdSplitObjects + putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, + cmdProgressColour, ProgressColour (..), cmdProgressInfo, ProgressInfo (..), + cmdSkipConfigure, cmdSplitObjects ) where import Data.IORef @@ -15,6 +15,7 @@ import System.IO.Unsafe data Untracked = Untracked { buildHaddock :: Bool , flavour :: Maybe String + , integerSimple :: Bool , progressColour :: ProgressColour , progressInfo :: ProgressInfo , skipConfigure :: Bool @@ -29,6 +30,7 @@ defaultUntracked :: Untracked defaultUntracked = Untracked { buildHaddock = False , flavour = Nothing + , integerSimple = False , progressColour = Auto , progressInfo = Normal , skipConfigure = False @@ -40,6 +42,9 @@ readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } readFlavour :: Maybe String -> Either String (Untracked -> Untracked) readFlavour ms = Right $ \flags -> flags { flavour = lower <$> ms } +readIntegerSimple :: Either String (Untracked -> Untracked) +readIntegerSimple = Right $ \flags -> flags { integerSimple = True } + readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) readProgressColour ms = maybe (Left "Cannot parse progress-colour") (Right . set) (go =<< lower <$> ms) @@ -77,6 +82,8 @@ cmdFlags = "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." + , Option [] ["integer-simple"] (NoArg readIntegerSimple) + "Build GHC with integer-simple library." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") "Use colours in progress info (Never, Auto or Always)." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") @@ -105,6 +112,9 @@ cmdBuildHaddock = buildHaddock getCmdLineFlags cmdFlavour :: Maybe String cmdFlavour = flavour getCmdLineFlags +cmdIntegerSimple :: Bool +cmdIntegerSimple = integerSimple getCmdLineFlags + cmdProgressColour :: ProgressColour cmdProgressColour = progressColour getCmdLineFlags diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 18f0ae0..351d780 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -177,7 +177,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages - , integerLibrary = integerGmp + , integerLibrary = if cmdIntegerSimple then integerSimple else integerGmp , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects From git at git.haskell.org Fri Oct 27 00:31:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Explain stages (bee9cee) Message-ID: <20171027003110.9124C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bee9ceed2f9e196b1d7adcc02c74246ec8c89f82/ghc >--------------------------------------------------------------- commit bee9ceed2f9e196b1d7adcc02c74246ec8c89f82 Author: David Luposchainsky Date: Wed Jan 6 15:05:37 2016 +0100 Explain stages >--------------------------------------------------------------- bee9ceed2f9e196b1d7adcc02c74246ec8c89f82 src/Stage.hs | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/src/Stage.hs b/src/Stage.hs index 144aa29..2e581c4 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -4,10 +4,27 @@ module Stage (Stage (..), stageString) where import Development.Shake.Classes import GHC.Generics (Generic) --- TODO: explain stages +-- | A stage refers to a certain compiler in GHC's build process. +-- +-- * Stage 0 is the bootstrapping compiler, i.e. the one already installed on +-- the user's system. +-- +-- * Stage 1 is built using the stage 0 compiler, using GHC's source code. +-- The result is a compiler that was built by the bootstrapping compiler, +-- with all the features of the new compiler. +-- +-- * Stage 2 is built using the stage 1 compiler and GHC's source code. The +-- result is a compiler "built by itself", commonly referred to as +-- /bootstrapping/. +-- +-- * Stage 3 uses stage 2 to build from source again. The result should have +-- the same object code as stage 2, which is a good test for the compiler. +-- Since it serves no other purpose than that, the stage 3 build is usually +-- omitted in the build process. data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Show, Eq, Ord, Enum, Generic) +-- | Prettyprint a 'Stage'. stageString :: Stage -> String stageString stage = "stage" ++ show (fromEnum stage) From git at git.haskell.org Fri Oct 27 00:31:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Speed up Travis OSX build by --integer-simple (77840e7) Message-ID: <20171027003114.9ED7D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/77840e7930d55597dc575ec29b2c35afd5516d1f/ghc >--------------------------------------------------------------- commit 77840e7930d55597dc575ec29b2c35afd5516d1f Author: Andrey Mokhov Date: Thu Jan 12 23:32:36 2017 +0000 Speed up Travis OSX build by --integer-simple >--------------------------------------------------------------- 77840e7930d55597dc575ec29b2c35afd5516d1f .travis.yml | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0209cab..35ae3b7 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,6 +3,7 @@ sudo: true matrix: include: - os: linux + env: MODE="--flavour=quickest" addons: apt: packages: @@ -15,9 +16,11 @@ matrix: - PATH="/opt/cabal/1.22/bin:$PATH" - os: osx + env: MODE="--flavour=quickest --integer-simple" before_install: - brew update - brew install ghc cabal-install + - install: # Add Cabal to PATH @@ -45,7 +48,7 @@ script: - ./build.sh selftest # Build GHC - - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 00:31:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add cabal configure to CI (5f4a8f6) Message-ID: <20171027003115.3A3743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f4a8f61707469c736f79b8da372e5ef4beb081a/ghc >--------------------------------------------------------------- commit 5f4a8f61707469c736f79b8da372e5ef4beb081a Author: David Luposchainsky Date: Wed Jan 6 15:39:33 2016 +0100 Add cabal configure to CI >--------------------------------------------------------------- 5f4a8f61707469c736f79b8da372e5ef4beb081a .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index a28a979..6413818 100644 --- a/.travis.yml +++ b/.travis.yml @@ -50,6 +50,7 @@ install: - ( cd ghc/shake-build && git reset --hard HEAD ) - ( cd ghc/shake-build && cabal install --only-dependencies ) + - ( cd ghc/shake-build && cabal configure ) - ( cd ghc && ./boot ) - ( cd ghc && ./configure ) From git at git.haskell.org Fri Oct 27 00:31:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (3c5998c) Message-ID: <20171027003110.BEBFF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c5998cddf477e84ee2e0b98de7a7d26bb0da710/ghc >--------------------------------------------------------------- commit 3c5998cddf477e84ee2e0b98de7a7d26bb0da710 Author: Andrey Mokhov Date: Sun May 15 01:02:51 2016 +0100 Minor revision >--------------------------------------------------------------- 3c5998cddf477e84ee2e0b98de7a7d26bb0da710 src/Oracles/PackageData.hs | 20 +++++++++----------- 1 file changed, 9 insertions(+), 11 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index ba3e205..dba1192 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -5,17 +5,10 @@ module Oracles.PackageData ( ) where import Development.Shake.Config -import Base import qualified Data.HashMap.Strict as Map --- For each (PackageData path) the file 'path/package-data.mk' contains --- a line of the form 'path_VERSION = 1.2.3.4'. --- pkgData $ PackageData path is an action that consults the file and --- returns "1.2.3.4". --- --- PackageDataList is used for multiple string options separated by spaces, --- such as 'path_MODULES = Data.Array Data.Array.Base ...'. --- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] +import Base + data PackageData = BuildGhciLib FilePath | ComponentId FilePath | Synopsis FilePath @@ -51,8 +44,10 @@ askPackageData path key = do case maybeValue of Nothing -> return "" Just value -> return value - -- Nothing -> putError $ "No key '" ++ key ++ "' in " ++ file ++ "." +-- | For each @PackageData path@ the file 'path/package-data.mk' contains a line +-- of the form 'path_VERSION = 1.2.3.4'. @pkgData (PackageData path)@ is an +-- Action that consults the file and returns "1.2.3.4". pkgData :: PackageData -> Action String pkgData packageData = case packageData of BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" @@ -60,6 +55,9 @@ pkgData packageData = case packageData of Synopsis path -> askPackageData path "SYNOPSIS" Version path -> askPackageData path "VERSION" +-- | @PackageDataList path@ is used for multiple string options separated by +-- spaces, such as @path_MODULES = Data.Array Data.Array.Base ... at . +-- @pkgListData Modules@ therefore returns ["Data.Array", "Data.Array.Base", ...] pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = fmap (map unquote . words) $ case packageData of CcArgs path -> askPackageData path "CC_OPTS" @@ -83,7 +81,7 @@ pkgDataList packageData = fmap (map unquote . words) $ case packageData of where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') --- Oracle for 'package-data.mk' files +-- | Oracle for 'package-data.mk' files. packageDataOracle :: Rules () packageDataOracle = do keys <- newCache $ \file -> do From git at git.haskell.org Fri Oct 27 00:31:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop DeriveDataTypeable extension (fda4673) Message-ID: <20171027003115.4D0BA3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fda46732212cd1f052734ac796dafb3b3f7526a8/ghc >--------------------------------------------------------------- commit fda46732212cd1f052734ac796dafb3b3f7526a8 Author: Andrey Mokhov Date: Sun May 15 01:03:32 2016 +0100 Drop DeriveDataTypeable extension >--------------------------------------------------------------- fda46732212cd1f052734ac796dafb3b3f7526a8 hadrian.cabal | 3 +-- src/Oracles/ArgsHash.hs | 2 +- src/Oracles/Config.hs | 2 +- src/Oracles/Dependencies.hs | 2 +- src/Oracles/LookupInPath.hs | 2 +- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Oracles/WindowsPath.hs | 2 +- src/Package.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- 11 files changed, 11 insertions(+), 12 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 5c13f7a..7f03057 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -112,8 +112,7 @@ executable hadrian default-language: Haskell2010 default-extensions: RecordWildCards - other-extensions: DeriveDataTypeable - , DeriveGeneric + other-extensions: DeriveGeneric , FlexibleInstances , GeneralizedNewtypeDeriving , LambdaCase diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index d3bfd61..c26efd4 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.ArgsHash (checkArgsHash, argsHashOracle) where import Base diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index 7801208..95facc8 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Config (askConfig, askConfigWithDefault, configOracle) where import Base diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index aa54d86..08b3afa 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Dependencies (dependencies, dependenciesOracle) where import Control.Monad.Trans.Maybe diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 0ea03fd..18c990b 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where import System.Directory diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 233cdc0..f2b03f3 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.ModuleFiles ( decodeModule, encodeModule, findGenerator, haskellSources, moduleFilesOracle ) where diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index dba1192..6a01692 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( PackageData (..), PackageDataList (..), pkgData, pkgDataList, packageDataOracle diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 7983c7f..c70b959 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.PackageDeps (packageDeps, packageDepsOracle) where import qualified Data.HashMap.Strict as Map diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index e252bba..2a3336d 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.WindowsPath ( fixAbsolutePathOnWindows, topDirectory, windowsPathOracle ) where diff --git a/src/Package.hs b/src/Package.hs index 1fc1ac9..7517d87 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving, DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving #-} module Package ( Package (..), PackageName (..), PackageType (..), diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index faeb99d..9df0fdb 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDbArgs, PackageDbKey (..), cppArgs, needDll0 From git at git.haskell.org Fri Oct 27 00:31:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on --integer-simple command line flag (5ca4af3) Message-ID: <20171027003118.88A9D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ca4af3f65b77af080508655a12c6f48b7d5ce31/ghc >--------------------------------------------------------------- commit 5ca4af3f65b77af080508655a12c6f48b7d5ce31 Author: Andrey Mokhov Date: Fri Jan 13 00:49:58 2017 +0000 Add a note on --integer-simple command line flag See #179. [skip ci] >--------------------------------------------------------------- 5ca4af3f65b77af080508655a12c6f48b7d5ce31 README.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/README.md b/README.md index 109f7f0..038bde5 100644 --- a/README.md +++ b/README.md @@ -60,6 +60,9 @@ currently supports several others: * `--haddock`: build Haddock documentation. +* `--integer-simple`: build GHC using the `integer-simple` integer library (instead +of `integer-gmp`). + * `--progress-colour=MODE`: choose whether to use colours when printing build progress info. There are three settings: `never` (do not use colours), `auto` (attempt to detect whether the console supports colours; this is the default setting), and `always` (use From git at git.haskell.org Fri Oct 27 00:31:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddock build to CI (db5e646) Message-ID: <20171027003119.1CF633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db5e646e6fedd351caeed52ecdb8ce4946eb4613/ghc >--------------------------------------------------------------- commit db5e646e6fedd351caeed52ecdb8ce4946eb4613 Author: David Luposchainsky Date: Wed Jan 6 15:01:20 2016 +0100 Add Haddock build to CI >--------------------------------------------------------------- db5e646e6fedd351caeed52ecdb8ce4946eb4613 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 4cc0396..a28a979 100644 --- a/.travis.yml +++ b/.travis.yml @@ -55,6 +55,7 @@ install: - ( cd ghc && ./configure ) script: + - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh -j --no-progress $TARGET cache: From git at git.haskell.org Fri Oct 27 00:31:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (f50439d) Message-ID: <20171027003119.245A93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f50439d081f137ee3e7abfbdc2f19e4b37620bbd/ghc >--------------------------------------------------------------- commit f50439d081f137ee3e7abfbdc2f19e4b37620bbd Author: Andrey Mokhov Date: Mon May 16 00:26:02 2016 +0100 Minor revision >--------------------------------------------------------------- f50439d081f137ee3e7abfbdc2f19e4b37620bbd src/Rules/Register.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index cd3649b..f35413a 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -10,38 +10,37 @@ import Settings import Settings.Packages.Rts import Target --- Build package-data.mk by using GhcCabal to process pkgCabal file +-- | Build package-data.mk by processing the .cabal file with ghc-cabal utility. registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context at Context {..} = do - let oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 + let path = buildPath context + oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 pkgConf = packageDbDirectory stage -/- pkgNameString package when (stage <= Stage1) $ matchVersionedFilePath pkgConf "conf" ?> \conf -> do - -- This produces inplace-pkg-config. TODO: Add explicit tracking + -- This produces inplace-pkg-config. TODO: Add explicit tracking. need [pkgDataFile context] -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 let pkgConfig = oldPath -/- "inplace-pkg-config" oldBuildPath = oldPath -/- "build" fixPkgConf = unlines - . map (replace oldBuildPath (buildPath context) - . replace (replaceSeparators '\\' $ oldBuildPath) - (buildPath context) ) + . map + ( replace oldBuildPath path + . replace (replaceSeparators '\\' oldBuildPath) path ) . lines fixFile pkgConfig fixPkgConf - buildWithResources rs $ - Target context (GhcPkg stage) [pkgConfig] [conf] + buildWithResources rs $ Target context (GhcPkg stage) [pkgConfig] [conf] when (package == rts && stage == Stage1) $ do packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do need [rtsConf] - buildWithResources rs $ - Target context (GhcPkg stage) [rtsConf] [conf] + buildWithResources rs $ Target context (GhcPkg stage) [rtsConf] [conf] rtsConf %> \_ -> do - need [ pkgDataFile rtsContext, rtsConfIn ] + need [pkgDataFile rtsContext, rtsConfIn] build $ Target context HsCpp [rtsConfIn] [rtsConf] let fixRtsConf = unlines From git at git.haskell.org Fri Oct 27 00:31:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need the GMP library when building with integerSimple (f39305c) Message-ID: <20171027003122.254773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f39305c46467b30b7697ad42c1a817be9ec90670/ghc >--------------------------------------------------------------- commit f39305c46467b30b7697ad42c1a817be9ec90670 Author: Andrey Mokhov Date: Fri Jan 13 02:12:31 2017 +0000 Don't need the GMP library when building with integerSimple >--------------------------------------------------------------- f39305c46467b30b7697ad42c1a817be9ec90670 src/Settings/Builders/Ghc.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index f30b8e6..006d9f8 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -21,7 +21,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do pkg <- getPackage libs <- getPkgDataList DepExtraLibs libDirs <- getPkgDataList DepLibDirs - gmpLibs <- if stage > Stage0 + gmpLibs <- if stage > Stage0 && integerLibrary flavour == integerGmp then do -- TODO: get this data more gracefully let strip = fromMaybe "" . stripPrefix "extra-libraries: " buildInfo <- lift $ readFileLines gmpBuildInfoPath From git at git.haskell.org Fri Oct 27 00:31:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't add redundant path separator in -/- (d1780e4) Message-ID: <20171027003122.DFF6E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1780e499e3e5a3f4adb21f6be366b26ae3ec6a4/ghc >--------------------------------------------------------------- commit d1780e499e3e5a3f4adb21f6be366b26ae3ec6a4 Author: Andrey Mokhov Date: Mon May 16 01:31:02 2016 +0100 Don't add redundant path separator in -/- >--------------------------------------------------------------- d1780e499e3e5a3f4adb21f6be366b26ae3ec6a4 src/Base.hs | 5 ++++- src/Oracles/WindowsPath.hs | 5 +++-- 2 files changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index bd80f47..339a61d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -89,7 +89,10 @@ unifyPath = toStandard . normaliseEx -- | Combine paths with a forward slash regardless of platform. (-/-) :: FilePath -> FilePath -> FilePath -a -/- b = a ++ '/' : b +"" -/- b = b +a -/- b + | last a == '/' = a ++ b + | otherwise = a ++ '/' : b infixr 6 -/- diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index 2a3336d..3cbf73b 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -3,7 +3,8 @@ module Oracles.WindowsPath ( fixAbsolutePathOnWindows, topDirectory, windowsPathOracle ) where -import Data.Char (isSpace) +import Data.Char + import Base import Oracles.Config.Setting @@ -25,7 +26,7 @@ fixAbsolutePathOnWindows path = do then do let (dir, file) = splitFileName path winDir <- askOracle $ WindowsPath dir - return $ winDir ++ file + return $ winDir -/- file else return path From git at git.haskell.org Fri Oct 27 00:31:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Haddocks for Way.hs (997ce25) Message-ID: <20171027003122.DA59F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/997ce259b41f6e60b7d4906292b920a00c799bfd/ghc >--------------------------------------------------------------- commit 997ce259b41f6e60b7d4906292b920a00c799bfd Author: David Luposchainsky Date: Wed Jan 6 15:31:55 2016 +0100 Haddocks for Way.hs >--------------------------------------------------------------- 997ce259b41f6e60b7d4906292b920a00c799bfd src/Rules.hs | 2 +- src/Stage.hs | 2 +- src/Way.hs | 37 +++++++++++++++++++++++++++++-------- 3 files changed, 31 insertions(+), 10 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index f8b2810..c24b354 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -11,7 +11,7 @@ import Rules.Resources import Settings allStages :: [Stage] -allStages = [Stage0 ..] +allStages = [minBound ..] -- TODO: not all program targets should be needed explicitly -- | 'need' all top-level build targets diff --git a/src/Stage.hs b/src/Stage.hs index 2e581c4..af6d2df 100644 --- a/src/Stage.hs +++ b/src/Stage.hs @@ -22,7 +22,7 @@ import GHC.Generics (Generic) -- Since it serves no other purpose than that, the stage 3 build is usually -- omitted in the build process. data Stage = Stage0 | Stage1 | Stage2 | Stage3 - deriving (Show, Eq, Ord, Enum, Generic) + deriving (Show, Eq, Ord, Enum, Generic, Bounded) -- | Prettyprint a 'Stage'. stageString :: Stage -> String diff --git a/src/Way.hs b/src/Way.hs index 28d1365..9f7f12a 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -19,6 +19,8 @@ import Oracles -- Note: order of constructors is important for compatibility with the old build -- system, e.g. we want "thr_p", not "p_thr" (see instance Show Way). +-- | A 'WayUnit' is a single way of building source code, for example with +-- profiling enabled, or dynamically linked. data WayUnit = Threaded | Debug | Profiling @@ -26,7 +28,7 @@ data WayUnit = Threaded | Dynamic | Parallel | GranSim - deriving (Eq, Enum) + deriving (Eq, Enum, Bounded) -- TODO: get rid of non-derived Show instances instance Show WayUnit where @@ -40,16 +42,22 @@ instance Show WayUnit where GranSim -> "gm" instance Read WayUnit where - readsPrec _ s = [(unit, "") | unit <- [Threaded ..], show unit == s] + readsPrec _ s = [(unit, "") | unit <- [minBound ..], show unit == s] +-- | Collection of 'WayUnit's that stands for the different ways source code +-- is to be built. newtype Way = Way IntSet +-- | Construct a 'Way' from multiple 'WayUnit's. Inverse of 'wayToUnits'. wayFromUnits :: [WayUnit] -> Way wayFromUnits = Way . Set.fromList . map fromEnum +-- | Split a 'Way' into its 'WayUnit' building blocks. +-- Inverse of 'wayFromUnits'. wayToUnits :: Way -> [WayUnit] wayToUnits (Way set) = map toEnum . Set.elems $ set +-- | Check whether a 'Way' contains a certain 'WayUnit'. wayUnit :: WayUnit -> Way -> Bool wayUnit unit (Way set) = fromEnum unit `Set.member` set @@ -72,11 +80,23 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b -vanilla, profiling, logging, parallel, granSim :: Way +-- | Build with no 'WayUnit's at all. +vanilla :: Way vanilla = wayFromUnits [] + +-- | Build with profiling. +profiling :: Way profiling = wayFromUnits [Profiling] + +-- | Build with logging. +logging :: Way logging = wayFromUnits [Logging] + +-- | Build in parallel. +parallel :: Way parallel = wayFromUnits [Parallel] + +granSim :: Way granSim = wayFromUnits [GranSim] -- RTS only ways @@ -135,11 +155,12 @@ libsuf way @ (Way set) = -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension --- Detect way from a given filename. Returns Nothing if there is no match: --- * safeDetectWay "foo/bar.hi" == Just vanilla --- * safeDetectWay "baz.thr_p_o" == Just threadedProfiling --- * safeDetectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi") --- * safeDetectWay "xru.p_ghc7.11.20141222.so" == Just profiling +-- | Detect way from a given 'FilePath'. Returns 'Nothing' if there is no match. +-- +-- * @'safeDetectWay' "foo/bar.hi" '==' 'Just' vanilla@ +-- * @'safeDetectWay' "baz.thr_p_o" '==' 'Just' threadedProfiling@ +-- * @'safeDetectWay' "qwe.ph_i" '==' 'Nothing' (expected "qwe.p_hi")@ +-- * @'safeDetectWay' "xru.p_ghc7.11.123.so" '==' 'Just' profiling@ safeDetectWay :: FilePath -> Maybe Way safeDetectWay file = case reads prefix of [(way, "")] -> Just way From git at git.haskell.org Fri Oct 27 00:31:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix type error (ffc151c) Message-ID: <20171027003126.6A6303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffc151c004163822f9e5d131b9556b0c42a3be44/ghc >--------------------------------------------------------------- commit ffc151c004163822f9e5d131b9556b0c42a3be44 Author: David Luposchainsky Date: Wed Jan 6 15:35:22 2016 +0100 Fix type error >--------------------------------------------------------------- ffc151c004163822f9e5d131b9556b0c42a3be44 src/Rules.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules.hs b/src/Rules.hs index c24b354..fe8242b 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -35,6 +35,6 @@ targetsForStage stage = do packageRules :: Rules () packageRules = do resources <- resourceRules - for allStages $ \stage -> + for_ allStages $ \stage -> for_ knownPackages $ \pkg -> buildPackage resources $ PartialTarget stage pkg From git at git.haskell.org Fri Oct 27 00:31:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Filter out repeated ways when copying libffi (b94612d) Message-ID: <20171027003125.B19953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b94612d33b8febed57d26bc696c9454b883f4aed/ghc >--------------------------------------------------------------- commit b94612d33b8febed57d26bc696c9454b883f4aed Author: Andrey Mokhov Date: Fri Jan 13 11:43:58 2017 +0000 Filter out repeated ways when copying libffi >--------------------------------------------------------------- b94612d33b8febed57d26bc696c9454b883f4aed src/Rules/Libffi.hs | 3 ++- src/Way.hs | 5 ++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0f703d9..99b77c8 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -56,7 +56,8 @@ libffiRules = do copyFile header (rtsBuildPath -/- takeFileName header) ways <- interpretInContext libffiContext (getLibraryWays <> getRtsWays) - forM_ ways $ \way -> copyFile libffiLibrary =<< rtsLibffiLibrary way + forM_ (nubOrd ways) $ \way -> + copyFile libffiLibrary =<< rtsLibffiLibrary way putSuccess $ "| Successfully built custom library 'libffi'" diff --git a/src/Way.hs b/src/Way.hs index 22ae6fa8..cb73f04 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -24,7 +24,7 @@ data WayUnit = Threaded | Profiling | Logging | Dynamic - deriving (Eq, Enum, Bounded) + deriving (Bounded, Enum, Eq, Ord) -- TODO: get rid of non-derived Show instances instance Show WayUnit where @@ -74,6 +74,9 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b +instance Ord Way where + compare (Way a) (Way b) = compare a b + -- | Build default _vanilla_ way. vanilla :: Way vanilla = wayFromUnits [] From git at git.haskell.org Fri Oct 27 00:31:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up imports (improve consistency) (e982476) Message-ID: <20171027003126.907BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e982476cf7b80add369365d78718e9954a3944d0/ghc >--------------------------------------------------------------- commit e982476cf7b80add369365d78718e9954a3944d0 Author: Andrey Mokhov Date: Mon May 16 01:33:39 2016 +0100 Clean up imports (improve consistency) >--------------------------------------------------------------- e982476cf7b80add369365d78718e9954a3944d0 src/Builder.hs | 2 +- src/CmdLineFlag.hs | 14 ++++++-------- src/Environment.hs | 3 ++- src/Expression.hs | 2 +- src/Oracles/Config.hs | 3 ++- src/Package.hs | 5 +++-- src/Rules/Cabal.hs | 3 ++- src/Rules/Configure.hs | 4 ++-- src/Rules/Generate.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Perl.hs | 2 +- src/Rules/Selftest.hs | 4 ++-- src/Rules/Test.hs | 2 +- src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/Ar.hs | 4 ++-- src/Settings/Builders/Cc.hs | 6 +++--- src/Settings/Builders/Common.hs | 2 +- src/Settings/Builders/Configure.hs | 2 +- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 +++----- src/Settings/Builders/GhcCabal.hs | 9 +++------ src/Settings/Builders/Haddock.hs | 1 - src/Settings/Builders/Happy.hs | 2 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- src/Settings/Builders/Make.hs | 2 +- src/Settings/Builders/Tar.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Packages/Base.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 6 +++--- src/Settings/Packages/Directory.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 4 ++-- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/GhcPrim.hs | 4 ++-- src/Settings/Packages/Haddock.hs | 4 ++-- src/Settings/Packages/Hp2ps.hs | 4 ++-- src/Settings/Packages/IntegerGmp.hs | 6 +++--- src/Settings/Packages/IservBin.hs | 7 +++---- src/Settings/Packages/Rts.hs | 4 ++-- src/Settings/Packages/RunGhc.hs | 4 ++-- src/Settings/Packages/Touchy.hs | 4 ++-- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/Ways.hs | 5 +++-- src/Way.hs | 3 ++- 45 files changed, 84 insertions(+), 87 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 e982476cf7b80add369365d78718e9954a3944d0 From git at git.haskell.org Fri Oct 27 00:31:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix bad imports (302c1df) Message-ID: <20171027003130.70A4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/302c1dfb07284855bafd93d8a0cfb34bcbb50847/ghc >--------------------------------------------------------------- commit 302c1dfb07284855bafd93d8a0cfb34bcbb50847 Author: David Luposchainsky Date: Wed Jan 6 15:45:34 2016 +0100 Fix bad imports >--------------------------------------------------------------- 302c1dfb07284855bafd93d8a0cfb34bcbb50847 src/Main.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index bacc8f1..b30b38e 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,5 +1,7 @@ module Main (main) where +import Development.Shake + import qualified Base as B import qualified Rules as R import qualified Rules.Cabal as RCabal @@ -24,6 +26,6 @@ main = shakeArgs options rules , ROracle.oracleRules , R.packageRules ] options = shakeOptions - { shakeFiles = shakeFilesPath + { shakeFiles = B.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:31:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use -H32m in all build flavours (a7b1494) Message-ID: <20171027003129.7B89B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7b149453928e5cf7c8051d4c6329ef9db3246f1/ghc >--------------------------------------------------------------- commit a7b149453928e5cf7c8051d4c6329ef9db3246f1 Author: Andrey Mokhov Date: Fri Jan 13 11:47:27 2017 +0000 Use -H32m in all build flavours See #268 >--------------------------------------------------------------- a7b149453928e5cf7c8051d4c6329ef9db3246f1 src/Settings/Flavours/Development.hs | 2 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/Quickest.hs | 2 +- 5 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index 7cfd7da..4e1ee2d 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -14,7 +14,7 @@ developmentArgs :: Stage -> Args developmentArgs ghcStage = do stage <- getStage sourceArgs $ SourceArgs - { hsDefault = append ["-O", "-H64m"] + { hsDefault = append ["-O", "-H32m"] , hsLibrary = notStage0 ? arg "-dcore-lint" , hsCompiler = succ stage == ghcStage ? append ["-O0", "-DDEBUG"] , hsGhc = succ stage == ghcStage ? append ["-O0", "-DDEBUG"] } diff --git a/src/Settings/Flavours/Performance.hs b/src/Settings/Flavours/Performance.hs index 0e07c71..a9cef4d 100644 --- a/src/Settings/Flavours/Performance.hs +++ b/src/Settings/Flavours/Performance.hs @@ -11,7 +11,7 @@ performanceFlavour = defaultFlavour performanceArgs :: Args performanceArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O", "-H64m"] + { hsDefault = append ["-O", "-H32m"] , hsLibrary = notStage0 ? arg "-O2" , hsCompiler = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2"] , hsGhc = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2"] } diff --git a/src/Settings/Flavours/Profiled.hs b/src/Settings/Flavours/Profiled.hs index 2f5dc74..861c66c 100644 --- a/src/Settings/Flavours/Profiled.hs +++ b/src/Settings/Flavours/Profiled.hs @@ -12,7 +12,7 @@ profiledFlavour = defaultFlavour profiledArgs :: Args profiledArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O0", "-H64m"] + { hsDefault = append ["-O0", "-H32m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = arg "-O" , hsGhc = arg "-O" } diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 6fe3353..5cbd1e4 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -12,7 +12,7 @@ quickFlavour = defaultFlavour quickArgs :: Args quickArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O0", "-H64m"] + { hsDefault = append ["-O0", "-H32m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = stage0 ? arg "-O" , hsGhc = stage0 ? arg "-O" } diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 0560b39..d5dff73 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -13,7 +13,7 @@ quickestFlavour = defaultFlavour quickestArgs :: Args quickestArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O0", "-H64m"] + { hsDefault = append ["-O0", "-H32m"] , hsLibrary = mempty , hsCompiler = mempty , hsGhc = mempty } From git at git.haskell.org Fri Oct 27 00:31:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use -H32m in all build flavours (2ef6390) Message-ID: <20171027003133.375413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ef6390e2893eec4d3b7aadd334fa37fd822946b/ghc >--------------------------------------------------------------- commit 2ef6390e2893eec4d3b7aadd334fa37fd822946b Author: Andrey Mokhov Date: Fri Jan 13 12:55:22 2017 +0000 Use -H32m in all build flavours See #268 >--------------------------------------------------------------- 2ef6390e2893eec4d3b7aadd334fa37fd822946b doc/flavours.md | 26 +++++++++++++------------- 1 file changed, 13 insertions(+), 13 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index dc672a9..9fe2239 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -35,7 +35,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH default
- -O
-H32
+ -O
-H32m
-O2
-H32m @@ -46,8 +46,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quick - -O0
-H64 - -O0
-H64 + -O0
-H32m + -O0
-H32m -O -O @@ -57,8 +57,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quickest - -O0
-H64 - -O0
-H64 + -O0
-H32m + -O0
-H32m @@ -68,8 +68,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH perf - -O
-H64 - -O
-H64 + -O
-H32m + -O
-H32m -O2 -O @@ -79,8 +79,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH prof - -O0
-H64 - -O0
-H64 + -O0
-H32m + -O0
-H32m -O -O @@ -90,8 +90,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel1 - -O
-H64 - -O
-H64 + -O
-H32m + -O
-H32m -dcore-lint -O0
-DDEBUG @@ -101,8 +101,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel2 - -O
-H64 - -O
-H64 + -O
-H32m + -O
-H32m -dcore-lint From git at git.haskell.org Fri Oct 27 00:31:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddocks to GHC.hs (9dd9ae0) Message-ID: <20171027003134.CC5743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dd9ae02b8bae0ead318594555929727960aee6a/ghc >--------------------------------------------------------------- commit 9dd9ae02b8bae0ead318594555929727960aee6a Author: David Luposchainsky Date: Wed Jan 6 15:45:48 2016 +0100 Add Haddocks to GHC.hs >--------------------------------------------------------------- 9dd9ae02b8bae0ead318594555929727960aee6a src/GHC.hs | 23 ++++++++++++----------- 1 file changed, 12 insertions(+), 11 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 6e3a477..3d99e63 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -15,11 +15,11 @@ import Base import Package import Stage --- These are all GHC packages we know about. Build rules will be generated for +-- | These are all GHC packages we know about. Build rules will be generated for -- all of them. However, not all of these packages will be built. For example, --- package 'win32' is built only on Windows. --- Settings/Packages.hs defines default conditions for building each package, --- which can be overridden in Settings/User.hs. +-- package /win32/ is built only on Windows. +-- "Packages" defines default conditions for building each package, which can +-- be overridden in "User". defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes @@ -30,7 +30,7 @@ defaultKnownPackages = , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time , touchy, transformers, unix, win32, xhtml ] --- Package definitions (see Package.hs) +-- Package definitions (see "Package") array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, @@ -95,16 +95,17 @@ xhtml = library "xhtml" -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, -- lndir, mkdirhier, testremove, vagrant --- GHC build results will be placed into target directories with the following --- typical structure: --- * build/ : contains compiled object code --- * doc/ : produced by haddock --- * package-data.mk : contains output of ghc-cabal applied to pkgCabal +-- | GHC build results will be placed into target directories with the +-- following typical structure: + +-- * @build/@ contains compiled object code +-- * @doc/@ is produced by haddock +-- * @package-data.mk@ contains output of ghc-cabal applied to pkgCabal defaultTargetDirectory :: Stage -> Package -> FilePath defaultTargetDirectory stage _ = stageString stage -- TODO: simplify, add programInplaceLibPath --- | Returns a relative path to the program executable +-- | The relative path to the program executable defaultProgramPath :: Stage -> Package -> Maybe FilePath defaultProgramPath stage pkg | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) From git at git.haskell.org Fri Oct 27 00:31:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export Expression from Predicates (12dc4c5) Message-ID: <20171027003130.885583A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12dc4c5b7faaf774031fef8539947459cd9b20a5/ghc >--------------------------------------------------------------- commit 12dc4c5b7faaf774031fef8539947459cd9b20a5 Author: Andrey Mokhov Date: Mon May 16 01:47:31 2016 +0100 Re-export Expression from Predicates >--------------------------------------------------------------- 12dc4c5b7faaf774031fef8539947459cd9b20a5 src/Expression.hs | 1 + src/Predicates.hs | 1 + src/Settings/Builders/Alex.hs | 1 - src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Cc.hs | 1 - src/Settings/Builders/Configure.hs | 1 - src/Settings/Builders/DeriveConstants.hs | 1 - src/Settings/Builders/GenApply.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 1 - src/Settings/Builders/Ghc.hs | 3 --- src/Settings/Builders/GhcCabal.hs | 1 - src/Settings/Builders/GhcPkg.hs | 1 - src/Settings/Builders/Haddock.hs | 3 +-- src/Settings/Builders/Happy.hs | 1 - src/Settings/Builders/HsCpp.hs | 1 - src/Settings/Builders/Hsc2Hs.hs | 4 ---- src/Settings/Builders/Ld.hs | 3 +-- src/Settings/Builders/Make.hs | 1 - src/Settings/Builders/Tar.hs | 1 - src/Settings/Default.hs | 3 +-- src/Settings/Flavours/Quick.hs | 1 - src/Settings/Packages.hs | 1 - src/Settings/Packages/Base.hs | 1 - src/Settings/Packages/Compiler.hs | 1 - src/Settings/Packages/Directory.hs | 1 - src/Settings/Packages/Ghc.hs | 1 - src/Settings/Packages/GhcCabal.hs | 1 - src/Settings/Packages/GhcPrim.hs | 1 - src/Settings/Packages/Haddock.hs | 1 - src/Settings/Packages/Hp2ps.hs | 1 - src/Settings/Packages/IntegerGmp.hs | 1 - src/Settings/Packages/IservBin.hs | 1 - src/Settings/Packages/Rts.hs | 1 - src/Settings/Packages/RunGhc.hs | 1 - src/Settings/Packages/Touchy.hs | 1 - src/Settings/Packages/Unlit.hs | 1 - src/Settings/User.hs | 1 - src/Settings/Ways.hs | 1 - 38 files changed, 6 insertions(+), 44 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 12dc4c5b7faaf774031fef8539947459cd9b20a5 From git at git.haskell.org Fri Oct 27 00:31:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename module Predicates to Predicate (03f89a6) Message-ID: <20171027003134.E2F5F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7/ghc >--------------------------------------------------------------- commit 03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7 Author: Andrey Mokhov Date: Mon May 16 01:51:17 2016 +0100 Rename module Predicates to Predicate >--------------------------------------------------------------- 03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7 hadrian.cabal | 2 +- src/{Predicates.hs => Predicate.hs} | 2 +- src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Cc.hs | 2 +- src/Settings/Builders/Configure.hs | 2 +- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/GenApply.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 2 +- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Builders/Happy.hs | 2 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Builders/Ld.hs | 2 +- src/Settings/Builders/Make.hs | 2 +- src/Settings/Builders/Tar.hs | 2 +- src/Settings/Default.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Directory.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/GhcPrim.hs | 2 +- src/Settings/Packages/Haddock.hs | 2 +- src/Settings/Packages/Hp2ps.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/IservBin.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/Packages/Touchy.hs | 2 +- src/Settings/Packages/Unlit.hs | 2 +- src/Settings/User.hs | 2 +- src/Settings/Ways.hs | 2 +- 38 files changed, 38 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 03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7 From git at git.haskell.org Fri Oct 27 00:31:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move checkApiAnnotations, compareSizes and ghcTags to Stage0 (ebee16a) Message-ID: <20171027003136.A06063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ebee16a9e7d37ea14a2e0cd180c0bf6e88c3873c/ghc >--------------------------------------------------------------- commit ebee16a9e7d37ea14a2e0cd180c0bf6e88c3873c Author: Andrey Mokhov Date: Thu Jan 19 02:46:21 2017 +0000 Move checkApiAnnotations, compareSizes and ghcTags to Stage0 See #246 >--------------------------------------------------------------- ebee16a9e7d37ea14a2e0cd180c0bf6e88c3873c src/Settings/Default.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 351d780..318b0a0 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -86,6 +86,8 @@ stage0Packages = do ios <- lift iosHost append $ [ binary , cabal + , checkApiAnnotations + , compareSizes , compiler , deriveConstants , dllSplit @@ -97,6 +99,7 @@ stage0Packages = do , ghcCabal , ghci , ghcPkg + , ghcTags , hsc2hs , hoopl , hp2ps @@ -118,7 +121,6 @@ stage1Packages = do , base , bytestring , compact - , compareSizes , containers , deepseq , directory @@ -142,11 +144,7 @@ stage1Packages = do [ xhtml | doc ] ] stage2Packages :: Packages -stage2Packages = do - doc <- buildHaddock flavour - append $ [ checkApiAnnotations - , ghcTags ] ++ - [ haddock | doc ] +stage2Packages = buildHaddock flavour ? append [ haddock ] -- | Default build ways for library packages: -- * We always build 'vanilla' way. From git at git.haskell.org Fri Oct 27 00:31:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Haddocks to Base.hs (5a82579) Message-ID: <20171027003138.727A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5a8257902248c32409835ab47b89c3e1a38be2b1/ghc >--------------------------------------------------------------- commit 5a8257902248c32409835ab47b89c3e1a38be2b1 Author: David Luposchainsky Date: Wed Jan 6 16:00:06 2016 +0100 Add Haddocks to Base.hs >--------------------------------------------------------------- 5a8257902248c32409835ab47b89c3e1a38be2b1 src/Base.hs | 19 ++++++++++++++++--- 1 file changed, 16 insertions(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a116892..05686e0 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -180,7 +180,16 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg --- | Render the given set of lines in a nice box of ASCII +-- | Render the given set of lines in a nice box of ASCII. +-- +-- The minimum width and whether to use Unicode symbols are hardcoded in the +-- function's body. +-- +-- >>> renderBox (words "lorem ipsum") +-- /----------\ +-- | lorem | +-- | ipsum | +-- \----------/ renderBox :: [String] -> String renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot]) where @@ -215,11 +224,13 @@ renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot] -- +1 for each non-dash (= corner) char dashes = replicate (boxContentWidth + 2) dash --- Depending on Data.Bifunctor only for this function seems an overkill +-- Explicit definition to avoid dependency on Data.Bifunctor +-- | Bifunctor bimap. bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) bimap f g (x, y) = (f x, g y) --- Depending on Data.List.Ordered only for these two functions seems an overkill +-- Explicit definition to avoid dependency on Data.List.Ordered +-- | Difference of two ordered lists. minusOrd :: Ord a => [a] -> [a] -> [a] minusOrd [] _ = [] minusOrd xs [] = xs @@ -228,6 +239,8 @@ minusOrd (x:xs) (y:ys) = case compare x y of EQ -> minusOrd xs ys GT -> minusOrd (x:xs) ys +-- Explicit definition to avoid dependency on Data.List.Ordered +-- | Intersection of two ordered lists by a predicate. intersectOrd :: (a -> b -> Ordering) -> [a] -> [b] -> [a] intersectOrd cmp = loop where From git at git.haskell.org Fri Oct 27 00:31:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix breakage due to changes in Cabal API (e908a4a) Message-ID: <20171027003140.2819F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e908a4a28964908ee30346a04aae23a4d314e8b2/ghc >--------------------------------------------------------------- commit e908a4a28964908ee30346a04aae23a4d314e8b2 Author: Andrey Mokhov Date: Wed Jan 25 17:45:48 2017 +0000 Fix breakage due to changes in Cabal API >--------------------------------------------------------------- e908a4a28964908ee30346a04aae23a4d314e8b2 src/Rules/Cabal.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 6adaf44..0df267f 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -4,6 +4,7 @@ import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Text +import Distribution.Types.CondTree import Distribution.Types.Dependency import Distribution.Verbosity @@ -49,4 +50,4 @@ collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] collectDeps (Just (CondNode _ deps ifs)) = deps ++ concatMap f ifs where - f (_, t, mt) = collectDeps (Just t) ++ collectDeps mt + f (CondBranch _ t mt) = collectDeps (Just t) ++ collectDeps mt From git at git.haskell.org Fri Oct 27 00:31:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing Haddock header (6cf7902) Message-ID: <20171027003142.552F83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6cf79029f6b1f6a1014a3be1d75a7360373c35b3/ghc >--------------------------------------------------------------- commit 6cf79029f6b1f6a1014a3be1d75a7360373c35b3 Author: David Luposchainsky Date: Thu Jan 7 18:19:18 2016 +0100 Add missing Haddock header >--------------------------------------------------------------- 6cf79029f6b1f6a1014a3be1d75a7360373c35b3 src/Target.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Target.hs b/src/Target.hs index 152de3d..3992ce2 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -37,7 +37,7 @@ instance Monoid a => Monoid (ReaderT Target Action a) where mempty = return mempty mappend = liftM2 mappend --- A partially constructed Target with fields 'Stage' and 'Package' only. +-- | A partially constructed Target with fields 'Stage' and 'Package' only. -- 'PartialTarget's are used for generating build rules. data PartialTarget = PartialTarget Stage Package deriving (Eq, Show) @@ -83,7 +83,6 @@ fullTargetWithWay :: -> Target fullTargetWithWay pt b w srcs fs = (fullTarget pt b srcs fs) { way = w } --- Instances for storing in the Shake database instance Binary Target instance NFData Target instance Hashable Target From git at git.haskell.org Fri Oct 27 00:31:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #253 from michalt/colors/1 (a9f43e5) Message-ID: <20171027003142.480D73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9f43e59a1f84108a779b1ce835b5357f47b8e0f/ghc >--------------------------------------------------------------- commit a9f43e59a1f84108a779b1ce835b5357f47b8e0f Merge: 03f89a6 0f7bc96 Author: Andrey Mokhov Date: Mon May 16 13:46:36 2016 +0100 Merge pull request #253 from michalt/colors/1 Check if the output supports colors, see #244 >--------------------------------------------------------------- a9f43e59a1f84108a779b1ce835b5357f47b8e0f build.cabal-new.sh | 1 - build.cabal.sh | 1 - build.sh | 1 - build.stack.sh | 1 - src/Base.hs | 12 ++++++++++-- 5 files changed, 10 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 00:31:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Check if the output supports colors (fixes #244) (0f7bc96) Message-ID: <20171027003138.85BB13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0f7bc96a2c8940181818594ffc71bf928ab8aed2/ghc >--------------------------------------------------------------- commit 0f7bc96a2c8940181818594ffc71bf928ab8aed2 Author: Michal Terepeta Date: Sun May 15 17:31:30 2016 +0200 Check if the output supports colors (fixes #244) This avoids using colors when the output is, e.g., redirected to a file. This requried a change to avoid passing the `--colour` flag to shake (so that hadrian is in charge of colors). Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 0f7bc96a2c8940181818594ffc71bf928ab8aed2 build.cabal-new.sh | 1 - build.cabal.sh | 1 - build.sh | 1 - build.stack.sh | 1 - src/Base.hs | 12 ++++++++++-- 5 files changed, 10 insertions(+), 6 deletions(-) diff --git a/build.cabal-new.sh b/build.cabal-new.sh index bca8c7c..65e222a 100755 --- a/build.cabal-new.sh +++ b/build.cabal-new.sh @@ -55,5 +55,4 @@ popd "$root/.shake/build" \ --lint \ --directory "$root/.." \ - --colour \ "$@" diff --git a/build.cabal.sh b/build.cabal.sh index f2e320e..08ff972 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -43,5 +43,4 @@ fi cabal run hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ - --colour \ "$@" diff --git a/build.sh b/build.sh index fff8df4..24fdc2f 100755 --- a/build.sh +++ b/build.sh @@ -49,5 +49,4 @@ ghc \ "$root/hadrian" \ --lint \ --directory "$root/.." \ - --colour \ "$@" diff --git a/build.stack.sh b/build.stack.sh index b5607b1..23f4833 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -36,5 +36,4 @@ stack build --no-library-profiling stack exec hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ - --colour \ "$@" diff --git a/src/Base.hs b/src/Base.hs index bd80f47..488be04 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -38,6 +38,7 @@ import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI +import qualified System.Info as Info import System.IO -- TODO: reexport Stage, etc.? @@ -96,10 +97,17 @@ infixr 6 -/- -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do - liftIO $ setSGR [SetColor Foreground Vivid colour] + liftIO $ set [SetColor Foreground Vivid colour] putNormal msg - liftIO $ setSGR [] + liftIO $ set [] liftIO $ hFlush stdout + where + set a = do + supported <- hSupportsANSI stdout + when (win || supported) $ setSGR a + -- An ugly hack to always try to print colours when on mingw and cygwin. + -- See: https://github.com/snowleopard/hadrian/pull/253 + win = "mingw" `isPrefixOf` Info.os || "cygwin" `isPrefixOf` Info.os -- | Make oracle output more distinguishable putOracle :: String -> Action () From git at git.haskell.org Fri Oct 27 00:31:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -Wno-sync-nand to ghcPrim's cbits/atomic.c (6e73b4d) Message-ID: <20171027003143.C489A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e73b4d370755518491bdd82f5542b04d2eedf66/ghc >--------------------------------------------------------------- commit 6e73b4d370755518491bdd82f5542b04d2eedf66 Author: Andrey Mokhov Date: Mon Feb 6 02:21:05 2017 +0100 Add -Wno-sync-nand to ghcPrim's cbits/atomic.c See GHC ticket #9678 >--------------------------------------------------------------- 6e73b4d370755518491bdd82f5542b04d2eedf66 cfg/system.config.in | 1 + src/Oracles/Config/Flag.hs | 2 ++ src/Settings/Packages/GhcPrim.hs | 9 +++++++-- 3 files changed, 10 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 9ea0f44..667a22d 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -30,6 +30,7 @@ ar-supports-at-file = @ArSupportsAtFile@ cc-clang-backend = @CC_CLANG_BACKEND@ cc-llvm-backend = @CC_LLVM_BACKEND@ gcc-is-clang = @GccIsClang@ +gcc-lt-44 = @GccLT44@ gcc-lt-46 = @GccLT46@ hs-cpp-args = @HaskellCPPArgs@ diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 6c5879d..8ac753f 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -12,6 +12,7 @@ import Oracles.Config.Setting data Flag = ArSupportsAtFile | CrossCompiling | GccIsClang + | GccLt44 | GccLt46 | GhcUnregisterised | LeadingUnderscore @@ -29,6 +30,7 @@ flag f = do ArSupportsAtFile -> "ar-supports-at-file" CrossCompiling -> "cross-compiling" GccIsClang -> "gcc-is-clang" + GccLt44 -> "gcc-lt-44" GccLt46 -> "gcc-lt-46" GhcUnregisterised -> "ghc-unregisterised" LeadingUnderscore -> "leading-underscore" diff --git a/src/Settings/Packages/GhcPrim.hs b/src/Settings/Packages/GhcPrim.hs index 225ff56..bed8345 100644 --- a/src/Settings/Packages/GhcPrim.hs +++ b/src/Settings/Packages/GhcPrim.hs @@ -1,8 +1,13 @@ module Settings.Packages.GhcPrim (ghcPrimPackageArgs) where import GHC +import Oracles.Config.Flag import Predicate ghcPrimPackageArgs :: Args -ghcPrimPackageArgs = package ghcPrim ? - builder GhcCabal ? arg "--flag=include-ghc-prim" +ghcPrimPackageArgs = package ghcPrim ? mconcat + [ builder GhcCabal ? arg "--flag=include-ghc-prim" + + , builder (Cc CompileC) ? + (not <$> flag GccLt44) ? + input "//cbits/atomic.c" ? arg "-Wno-sync-nand" ] From git at git.haskell.org Fri Oct 27 00:31:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track only files of known extensions when looking for module files (f910a1c) Message-ID: <20171027003145.AED303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f910a1c96f8e34171e0190931f907becfa40e2e9/ghc >--------------------------------------------------------------- commit f910a1c96f8e34171e0190931f907becfa40e2e9 Author: Andrey Mokhov Date: Mon May 16 21:46:41 2016 +0100 Track only files of known extensions when looking for module files Fix #254 >--------------------------------------------------------------- f910a1c96f8e34171e0190931f907becfa40e2e9 src/Oracles/ModuleFiles.hs | 47 +++++++++++++++++++++++++++++----------------- 1 file changed, 30 insertions(+), 17 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index f2b03f3..43a5f00 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -12,19 +12,31 @@ import Oracles.PackageData import Settings.Paths newtype ModuleFilesKey = ModuleFilesKey (Stage, Package) - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) newtype Generator = Generator (Stage, Package, FilePath) - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- The following generators and corresponding source extensions are supported: +-- | We scan for the following Haskell source extensions when looking for module +-- files. Note, we do not list "*.(l)hs-boot" files here, as they can never +-- appear by themselves and always have accompanying "*.(l)hs" master files. +haskellExtensions :: [String] +haskellExtensions = [".hs", ".lhs"] + +-- | Non-Haskell source extensions and corresponding builders. +otherExtensions :: [(String, Builder)] +otherExtensions = [ (".x" , Alex ) + , (".y" , Happy ) + , (".ly" , Happy ) + , (".hsc", Hsc2Hs) ] + +-- | We match the following file patterns when looking for module files. +moduleFilePatterns :: [FilePattern] +moduleFilePatterns = map ("*" ++) $ haskellExtensions ++ map fst otherExtensions + +-- | Given a FilePath determine the corresponding builder. determineBuilder :: FilePath -> Maybe Builder -determineBuilder file = case takeExtension file of - ".x" -> Just Alex - ".y" -> Just Happy - ".ly" -> Just Happy - ".hsc" -> Just Hsc2Hs - _ -> Nothing +determineBuilder file = lookup (takeExtension file) otherExtensions -- | Given a module name extract the directory and file name, e.g.: -- @@ -69,14 +81,16 @@ haskellSources context = do let modFile ("GHC.Prim", _) = autogen -/- "GHC/Prim.hs" modFile (m, Nothing ) = generatedFile context m modFile (m, Just file ) - | takeExtension file `elem` [".hs", ".lhs"] = file + | takeExtension file `elem` haskellExtensions = file | otherwise = generatedFile context m map modFile <$> contextFiles context +-- | Generated module files live in the 'Context' specific build directory. generatedFile :: Context -> String -> FilePath generatedFile context moduleName = buildPath context -/- replaceEq '.' '/' moduleName <.> "hs" +-- | Module files for a given 'Context'. contextFiles :: Context -> Action [(String, Maybe FilePath)] contextFiles context at Context {..} = do modules <- fmap sort . pkgDataList . Modules $ buildPath context @@ -95,7 +109,7 @@ contextFiles context at Context {..} = do -- Just "compiler/parser/Lexer.x"]. The oracle ignores @.(l)hs-boot@ files. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do - void $ addOracle $ \(ModuleFilesKey (stage, package)) -> do + void . addOracle $ \(ModuleFilesKey (stage, package)) -> do let path = buildPath $ vanillaContext stage package srcDirs <- pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path @@ -105,10 +119,9 @@ moduleFilesOracle = void $ do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do let fullDir = unifyPath $ dir -/- mDir - files <- getDirectoryFiles fullDir ["*"] - let noBoot = filter (not . (isSuffixOf "-boot")) files - cmp fe f = compare (dropExtension fe) f - found = intersectOrd cmp noBoot mFiles + files <- getDirectoryFiles fullDir moduleFilePatterns + let cmp fe f = compare (dropExtension fe) f + found = intersectOrd cmp files mFiles return (map (fullDir -/-) found, mDir) let pairs = sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ] @@ -118,14 +131,14 @@ moduleFilesOracle = void $ do ++ f1 ++ " and " ++ f2 ++ "." return $ lookupAll modules pairs - -- Optimisation: we discard .(l)hs files here, because they are never used + -- Optimisation: we discard Haskell files here, because they are never used -- as generators, and hence would be discarded in 'findGenerator' anyway. generators <- newCache $ \(stage, package) -> do let context = vanillaContext stage package files <- contextFiles context return $ Map.fromList [ (generatedFile context modName, src) | (modName, Just src) <- files - , takeExtension src `notElem` [".hs", ".lhs"] ] + , takeExtension src `notElem` haskellExtensions ] addOracle $ \(Generator (stage, package, file)) -> Map.lookup file <$> generators (stage, package) From git at git.haskell.org Fri Oct 27 00:31:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make imports fully qualified (2ba641b) Message-ID: <20171027003145.E008D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ba641b3d7d4aa8a84ab96a847208a7e79760496/ghc >--------------------------------------------------------------- commit 2ba641b3d7d4aa8a84ab96a847208a7e79760496 Author: David Luposchainsky Date: Thu Jan 7 19:12:17 2016 +0100 Make imports fully qualified >--------------------------------------------------------------- 2ba641b3d7d4aa8a84ab96a847208a7e79760496 src/Main.hs | 37 ++++++++++++++++++------------------- 1 file changed, 18 insertions(+), 19 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index b30b38e..1710b39 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,30 +2,29 @@ module Main (main) where import Development.Shake -import qualified Base as B -import qualified Rules as R -import qualified Rules.Cabal as RCabal -import qualified Rules.Config as RConfig -import qualified Rules.Copy as RCopy -import qualified Rules.Generate as RGen -import qualified Rules.IntegerGmp as RInt -import qualified Rules.Libffi as RFfi -import qualified Rules.Oracles as ROracle +import qualified Base +import qualified Rules +import qualified Rules.Cabal +import qualified Rules.Config +import qualified Rules.Generate +import qualified Rules.IntegerGmp +import qualified Rules.Libffi +import qualified Rules.Oracles main :: IO () main = shakeArgs options rules where rules = mconcat - [ RCabal.cabalRules - , RConfig.configRules - , RCopy.copyRules - , R.generateTargets - , RGen.generateRules - , RFfi.libffiRules - , RInt.integerGmpRules - , ROracle.oracleRules - , R.packageRules ] + [ Rules.Cabal.cabalRules + , Rules.Config.configRules + , Rules.Generate.copyRules + , Rules.Generate.generateRules + , Rules.generateTargets + , Rules.IntegerGmp.integerGmpRules + , Rules.Libffi.libffiRules + , Rules.Oracles.oracleRules + , Rules.packageRules ] options = shakeOptions - { shakeFiles = B.shakeFilesPath + { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:31:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to new GMP library (0dc5fdf) Message-ID: <20171027003147.4D1893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0dc5fdf1820c19dc3264d103d325c08c7d93902c/ghc >--------------------------------------------------------------- commit 0dc5fdf1820c19dc3264d103d325c08c7d93902c Author: Andrey Mokhov Date: Mon Feb 6 02:59:37 2017 +0100 Switch to new GMP library See GHC ticket 7655 >--------------------------------------------------------------- 0dc5fdf1820c19dc3264d103d325c08c7d93902c src/Rules/Gmp.hs | 17 +++++++---------- 1 file changed, 7 insertions(+), 10 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1442118..a3e32d3 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -23,9 +23,6 @@ gmpLibrary = gmpBuildPath -/- ".libs/libgmp.a" gmpMakefile :: FilePath gmpMakefile = gmpBuildPath -/- "Makefile" -gmpPatches :: [FilePath] -gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] - configureEnvironment :: Action [CmdOption] configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 , builderEnvironment "AR" Ar @@ -77,21 +74,21 @@ gmpRules = do -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. tarball <- unifyPath . getSingleton "Exactly one GMP tarball is expected" - <$> getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] + <$> getDirectoryFiles "" [gmpBase -/- "gmp-tarballs/gmp*.tar.bz2"] withTempDir $ \dir -> do let tmp = unifyPath dir need [tarball] build $ Target gmpContext Tar [tarball] [tmp] - forM_ gmpPatches $ \src -> do - let patch = takeFileName src - copyFile src $ tmp -/- patch - applyPatch tmp patch + let patch = gmpBase -/- "gmpsrc.patch" + patchName = takeFileName patch + copyFile patch $ tmp -/- patchName + applyPatch tmp patchName let name = dropExtension . dropExtension $ takeFileName tarball unpack = fromMaybe . error $ "gmpRules: expected suffix " - ++ "-nodoc-patched (found: " ++ name ++ ")." - libName = unpack $ stripSuffix "-nodoc-patched" name + ++ "-nodoc (found: " ++ name ++ ")." + libName = unpack $ stripSuffix "-nodoc" name moveDirectory (tmp -/- libName) gmpBuildPath From git at git.haskell.org Fri Oct 27 00:31:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghc-boot-th package (e91daa3) Message-ID: <20171027003149.555E63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e91daa3eb50b46441619d5ba43852c8dc1f9a164/ghc >--------------------------------------------------------------- commit e91daa3eb50b46441619d5ba43852c8dc1f9a164 Author: Andrey Mokhov Date: Mon May 16 23:10:48 2016 +0100 Add ghc-boot-th package >--------------------------------------------------------------- e91daa3eb50b46441619d5ba43852c8dc1f9a164 src/GHC.hs | 17 +++++++++-------- src/Settings/Packages.hs | 4 ++-- 2 files changed, 11 insertions(+), 10 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 02c76f9..303beca 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -2,11 +2,11 @@ module GHC ( array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, - ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, - primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unlit, unix, win32, xhtml, + genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim, + ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, + integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, + pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, + time, touchy, transformers, unlit, unix, win32, xhtml, defaultKnownPackages, programPath, contextDirectory, rtsContext ) where @@ -25,7 +25,7 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes , deepseq, deriveConstants, directory, dllSplit, filepath, genapply - , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim + , genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time @@ -34,8 +34,8 @@ defaultKnownPackages = -- | Package definitions, see 'Package'. array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, - haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, + genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim, + ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml :: Package @@ -57,6 +57,7 @@ genapply = utility "genapply" genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" `setType` Program ghcBoot = library "ghc-boot" +ghcBootTh = library "ghc-boot-th" ghcCabal = utility "ghc-cabal" ghci = library "ghci" ghcPkg = utility "ghc-pkg" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 6888d0a..40d9ebf 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -20,8 +20,8 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg - , hsc2hs, hoopl, hpc, templateHaskell, transformers ] + [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcBootTh, ghcCabal + , ghcPkg, hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode , hp2ps, unlit ] From git at git.haskell.org Fri Oct 27 00:31:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use --depth 1 for git clone (#298) (c3e8242) Message-ID: <20171027003151.1D2D03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3e8242cf0954fb785868019fa73a338cfddfaba/ghc >--------------------------------------------------------------- commit c3e8242cf0954fb785868019fa73a338cfddfaba Author: Gracjan Polak Date: Sat Feb 11 23:32:07 2017 +0100 Use --depth 1 for git clone (#298) * Use --depth 1 for git clone * Update .travis.yml Try separating git commands * Update .travis.yml Try github * Update .travis.yml * Update .travis.yml * Update .travis.yml * Update .travis.yml * Update .travis.yml * Update .travis.yml >--------------------------------------------------------------- c3e8242cf0954fb785868019fa73a338cfddfaba .travis.yml | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 35ae3b7..f6eda04 100644 --- a/.travis.yml +++ b/.travis.yml @@ -28,12 +28,18 @@ install: - export PATH - env + # Fetch GHC sources into ./ghc + - git --version + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git clone --depth 1 --recursive git://github.com/ghc/ghc + # --shallow-submodules is not supported on travis standard git 1.8 (linux), but it is supported + # on Travis Mac OS X machines. But it does not work with github mirrors because it cannot + # find commits. + # Install all Hadrian and GHC build dependencies - cabal update - cabal install alex happy ansi-terminal mtl shake quickcheck - # Fetch GHC sources into ./ghc - - git clone --recursive git://git.haskell.org/ghc.git --quiet # Travis has already cloned Hadrian into ./ and we need to move it # to ./ghc/hadrian -- one way to do it is to move the .git directory From git at git.haskell.org Fri Oct 27 00:31:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Document the provenance of the Main functions in the code rather than in comments (c573af0) Message-ID: <20171027003149.7D2A23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c573af06514bb073cb76918343303b9a2c043160/ghc >--------------------------------------------------------------- commit c573af06514bb073cb76918343303b9a2c043160 Author: Neil Mitchell Date: Thu Jan 7 18:30:03 2016 +0000 Document the provenance of the Main functions in the code rather than in comments >--------------------------------------------------------------- c573af06514bb073cb76918343303b9a2c043160 src/Main.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 07f14ea..0fe2ee3 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -9,15 +9,15 @@ import Rules.Oracles main :: IO () main = shakeArgs options $ do - cabalRules -- see Rules.Cabal - configRules -- see Rules.Config - copyRules -- see Rules.Generate - generateTargets -- see Rules - generateRules -- see Rules.Generate - libffiRules -- see Rules.Libffi - integerGmpRules -- see Rules.IntegerGmp - oracleRules -- see Rules.Oracles - packageRules -- see Rules + Rules.Cabal.cabalRules + Rules.Config.configRules + Rules.Generate.copyRules + Rules.generateTargets + Rules.Generate.generateRules + Rules.Libffi.libffiRules + Rules.IntegerGmp.integerGmpRules + Rules.Oracles.oracleRules + Rules.packageRules where options = shakeOptions { shakeFiles = shakeFilesPath From git at git.haskell.org Fri Oct 27 00:31:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dreary package signagures (34545e3) Message-ID: <20171027003153.22FE13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34545e3d0d54223512f0c05909a23bdb61ad3755/ghc >--------------------------------------------------------------- commit 34545e3d0d54223512f0c05909a23bdb61ad3755 Author: Andrey Mokhov Date: Mon May 16 23:16:59 2016 +0100 Drop dreary package signagures >--------------------------------------------------------------- 34545e3d0d54223512f0c05909a23bdb61ad3755 src/GHC.hs | 12 +++--------- 1 file changed, 3 insertions(+), 9 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 303beca..d75a046 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,4 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, @@ -18,7 +19,7 @@ import Stage -- | These are all GHC packages we know about. Build rules will be generated for -- all of them. However, not all of these packages will be built. For example, --- package /win32/ is built only on Windows. +-- package 'win32' is built only on Windows. -- "Packages" defines default conditions for building each package, which can -- be overridden in "Settings.User". defaultKnownPackages :: [Package] @@ -32,14 +33,6 @@ defaultKnownPackages = , touchy, transformers, unlit, unix, win32, xhtml ] -- | Package definitions, see 'Package'. -array, base, binary, bytestring, cabal, compiler, containers, compareSizes, - deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim, - ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, - primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unlit, unix, win32, xhtml :: Package - array = library "array" base = library "base" binary = library "binary" @@ -126,6 +119,7 @@ programPath context at Context {..} installProgram name = pkgPath package -/- contextDirectory context -/- "build/tmp" -/- name <.> exe +-- TODO: Move this elsewhere. rtsContext :: Context rtsContext = vanillaContext Stage1 rts From git at git.haskell.org Fri Oct 27 00:31:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert "Document the provenance of the Main functions in the code rather than in comments" (619f31e) Message-ID: <20171027003153.37B1E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/619f31ec9fb5d7dac00582129d8722f514a54f3b/ghc >--------------------------------------------------------------- commit 619f31ec9fb5d7dac00582129d8722f514a54f3b Author: Andrey Mokhov Date: Thu Jan 7 20:16:57 2016 +0000 Revert "Document the provenance of the Main functions in the code rather than in comments" This reverts commit c573af06514bb073cb76918343303b9a2c043160. >--------------------------------------------------------------- 619f31ec9fb5d7dac00582129d8722f514a54f3b src/Main.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 0fe2ee3..07f14ea 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -9,15 +9,15 @@ import Rules.Oracles main :: IO () main = shakeArgs options $ do - Rules.Cabal.cabalRules - Rules.Config.configRules - Rules.Generate.copyRules - Rules.generateTargets - Rules.Generate.generateRules - Rules.Libffi.libffiRules - Rules.IntegerGmp.integerGmpRules - Rules.Oracles.oracleRules - Rules.packageRules + cabalRules -- see Rules.Cabal + configRules -- see Rules.Config + copyRules -- see Rules.Generate + generateTargets -- see Rules + generateRules -- see Rules.Generate + libffiRules -- see Rules.Libffi + integerGmpRules -- see Rules.IntegerGmp + oracleRules -- see Rules.Oracles + packageRules -- see Rules where options = shakeOptions { shakeFiles = shakeFilesPath From git at git.haskell.org Fri Oct 27 00:31:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add extra to the list of dependencies (cb5035a) Message-ID: <20171027003154.8D1DF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb5035a49c5eee7706d3634c007520e6b1f4c2a5/ghc >--------------------------------------------------------------- commit cb5035a49c5eee7706d3634c007520e6b1f4c2a5 Author: Andrey Mokhov Date: Tue Feb 14 23:50:42 2017 +0100 Add extra to the list of dependencies >--------------------------------------------------------------- cb5035a49c5eee7706d3634c007520e6b1f4c2a5 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 038bde5..2256fbf 100644 --- a/README.md +++ b/README.md @@ -23,7 +23,7 @@ follow these steps: * If you have never built GHC before, start with the [preparation guide][ghc-preparation]. * This build system is written in Haskell (obviously) and depends on the following Haskell -packages, which need to be installed: `ansi-terminal mtl shake quickcheck`. +packages, which need to be installed: `ansi-terminal extra mtl quickcheck shake`. * Get the sources. It is important for the build system to be in the `hadrian` directory of the GHC source tree: From git at git.haskell.org Fri Oct 27 00:31:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build progress info colours customisable, drop putError and putOracle. (fa77d93) Message-ID: <20171027003157.1C9483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fa77d934a2f15509e33c3ee1aafb88cb20abc1d1/ghc >--------------------------------------------------------------- commit fa77d934a2f15509e33c3ee1aafb88cb20abc1d1 Author: Andrey Mokhov Date: Tue May 17 23:36:41 2016 +0100 Make build progress info colours customisable, drop putError and putOracle. See #244. >--------------------------------------------------------------- fa77d934a2f15509e33c3ee1aafb88cb20abc1d1 src/Base.hs | 64 +++++++++++++++------------------------------ src/Builder.hs | 4 +-- src/Expression.hs | 2 +- src/Oracles/Config.hs | 4 +-- src/Oracles/Config/Flag.hs | 4 +-- src/Oracles/Dependencies.hs | 6 ++--- src/Oracles/LookupInPath.hs | 4 +-- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/PackageDb.hs | 3 ++- src/Oracles/PackageDeps.hs | 2 +- src/Oracles/WindowsPath.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Configure.hs | 5 ++-- src/Rules/Generate.hs | 6 ++--- src/Rules/Gmp.hs | 4 +-- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Rules/Selftest.hs | 1 + src/Settings/User.hs | 20 ++++++++++---- 21 files changed, 67 insertions(+), 76 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 fa77d934a2f15509e33c3ee1aafb88cb20abc1d1 From git at git.haskell.org Fri Oct 27 00:31:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #122 from quchen/housekeeping (1690e0f) Message-ID: <20171027003157.57A2E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1690e0fc7b5168c2a80079dd3c3822a27ded9841/ghc >--------------------------------------------------------------- commit 1690e0fc7b5168c2a80079dd3c3822a27ded9841 Merge: 619f31e 2ba641b Author: Andrey Mokhov Date: Thu Jan 7 20:17:40 2016 +0000 Merge pull request #122 from quchen/housekeeping Add documentation, small refactorings >--------------------------------------------------------------- 1690e0fc7b5168c2a80079dd3c3822a27ded9841 .travis.yml | 2 ++ src/Base.hs | 19 +++++++++++--- src/Expression.hs | 4 +-- src/GHC.hs | 23 +++++++++-------- src/Main.hs | 43 +++++++++++++++++-------------- src/Predicates.hs | 23 ++++++++++++----- src/Rules.hs | 33 ++++++++++++++---------- src/Stage.hs | 21 +++++++++++++-- src/Target.hs | 76 ++++++++++++++++++++++++++++++++----------------------- src/Way.hs | 37 +++++++++++++++++++++------ 10 files changed, 185 insertions(+), 96 deletions(-) From git at git.haskell.org Fri Oct 27 00:31:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:31:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move -rtsopts to linker options (e561f80) Message-ID: <20171027003158.0EDBA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e561f8042ad86c40fda1e4181099c84518e359ad/ghc >--------------------------------------------------------------- commit e561f8042ad86c40fda1e4181099c84518e359ad Author: Andrey Mokhov Date: Thu Mar 16 00:41:56 2017 +0000 Move -rtsopts to linker options >--------------------------------------------------------------- e561f8042ad86c40fda1e4181099c84518e359ad src/Settings/Builders/Ghc.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 006d9f8..8020848 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -28,7 +28,8 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do return $ concatMap (words . strip) buildInfo else return [] mconcat [ arg "-no-auto-link-packages" - , nonHsMainPackage pkg ? arg "-no-hs-main" + , nonHsMainPackage pkg ? arg "-no-hs-main" + , not (nonHsMainPackage pkg) ? arg "-rtsopts" , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] @@ -74,8 +75,7 @@ commonGhcArgs = do , append $ map ("-optP" ++) cppArgs , arg "-odir" , arg path , arg "-hidir" , arg path - , arg "-stubdir" , arg path - , (not . nonHsMainPackage) <$> getPackage ? arg "-rtsopts" ] + , arg "-stubdir" , arg path ] -- TODO: Do '-ticky' in all debug ways? wayGhcArgs :: Args From git at git.haskell.org Fri Oct 27 00:32:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move versionToInt to Settings/Builders/Haddock (acc2c7e) Message-ID: <20171027003200.BDEDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acc2c7eef93e5372ce355de6c49cc24f9c507dab/ghc >--------------------------------------------------------------- commit acc2c7eef93e5372ce355de6c49cc24f9c507dab Author: Andrey Mokhov Date: Tue May 17 23:41:55 2016 +0100 Move versionToInt to Settings/Builders/Haddock >--------------------------------------------------------------- acc2c7eef93e5372ce355de6c49cc24f9c507dab src/Base.hs | 8 +------- src/Settings/Builders/Haddock.hs | 6 ++++++ 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 328eb98..8f02865 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -19,7 +19,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, - unifyPath, (-/-), versionToInt, matchVersionedFilePath, putColoured + unifyPath, (-/-), matchVersionedFilePath, putColoured ) where import Control.Applicative @@ -74,12 +74,6 @@ replaceWhen p to = map (\from -> if p from then to else from) quote :: String -> String quote s = "\"" ++ s ++ "\"" --- | Given a version string such as "2.16.2" produce an integer equivalent. -versionToInt :: String -> Int -versionToInt s = major * 1000 + minor * 10 + patch - where - [major, minor, patch] = map read . words $ replaceEq '.' ' ' s - -- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 37964b4..4c0b6f7 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -8,6 +8,12 @@ import Predicate import Settings import Settings.Builders.Ghc +-- | Given a version string such as "2.16.2" produce an integer equivalent. +versionToInt :: String -> Int +versionToInt s = major * 1000 + minor * 10 + patch + where + [major, minor, patch] = map read . words $ replaceEq '.' ' ' s + haddockBuilderArgs :: Args haddockBuilderArgs = builder Haddock ? do output <- getOutput From git at git.haskell.org Fri Oct 27 00:32:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing package Settings.Packages.Touchy. (39e1756) Message-ID: <20171027003201.5783A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39e17562d9f76f92cd63242a8c960ce1a9143f3f/ghc >--------------------------------------------------------------- commit 39e17562d9f76f92cd63242a8c960ce1a9143f3f Author: Andrey Mokhov Date: Thu Jan 7 22:31:45 2016 +0000 Add missing package Settings.Packages.Touchy. See #125. [skip ci] >--------------------------------------------------------------- 39e17562d9f76f92cd63242a8c960ce1a9143f3f shaking-up-ghc.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 9f2c80c..ab9f7bc 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -90,6 +90,7 @@ executable ghc-shake , Settings.Packages.IservBin , Settings.Packages.Rts , Settings.Packages.RunGhc + , Settings.Packages.Touchy , Settings.TargetDirectory , Settings.User , Settings.Ways From git at git.haskell.org Fri Oct 27 00:32:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/snowleopard/hadrian (f8bd794) Message-ID: <20171027003201.C32A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8bd7949c12c99aae2b6d0388fdf3b6d9143d23e/ghc >--------------------------------------------------------------- commit f8bd7949c12c99aae2b6d0388fdf3b6d9143d23e Merge: e561f80 cb5035a Author: Andrey Mokhov Date: Thu Mar 16 00:42:05 2017 +0000 Merge branch 'master' of https://github.com/snowleopard/hadrian >--------------------------------------------------------------- f8bd7949c12c99aae2b6d0388fdf3b6d9143d23e .travis.yml | 10 ++++++++-- README.md | 2 +- 2 files changed, 9 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:32:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't celebrate duplication (a2b39be) Message-ID: <20171027003204.422DF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2b39be6d48c9844f7d4519406c72857d38dd233/ghc >--------------------------------------------------------------- commit a2b39be6d48c9844f7d4519406c72857d38dd233 Author: Andrey Mokhov Date: Tue May 17 23:45:39 2016 +0100 Don't celebrate duplication >--------------------------------------------------------------- a2b39be6d48c9844f7d4519406c72857d38dd233 src/Rules/Generate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index daebe5d..d19ceac 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -134,7 +134,7 @@ generatePackageCode context@(Context stage pkg _) = newFile = oldPath ++ (drop (length path) file) createDirectory $ takeDirectory newFile liftIO $ IO.copyFile file newFile - putSuccess $ "| Duplicate file " ++ file ++ " -> " ++ newFile + putBuild $ "| Duplicate file " ++ file ++ " -> " ++ newFile when (pkg == rts) $ path -/- "AutoApply.cmm" %> \file -> do build $ Target context GenApply [] [file] From git at git.haskell.org Fri Oct 27 00:32:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (comments, whitespace). (cedbb79) Message-ID: <20171027003205.4A3E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cedbb7953afda4348a27cdd0b96af895e84e34e6/ghc >--------------------------------------------------------------- commit cedbb7953afda4348a27cdd0b96af895e84e34e6 Author: Andrey Mokhov Date: Thu Jan 7 22:52:46 2016 +0000 Minor revision (comments, whitespace). [skip ci] >--------------------------------------------------------------- cedbb7953afda4348a27cdd0b96af895e84e34e6 src/Predicates.hs | 4 +++- src/Way.hs | 8 ++++---- 2 files changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index b5ce0cb..497fca5 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -61,6 +61,8 @@ notStage0 = notM stage0 notPackage :: Package -> Predicate notPackage = notM . package --- | TODO: Actually, we don't register compiler in some circumstances -- fix. +-- TODO: Actually, we don't register compiler in some circumstances -- fix. +-- | Do we need to run @ghc-pkg update@ on the currently built package? +-- See "Rules.Data". registerPackage :: Predicate registerPackage = return True diff --git a/src/Way.hs b/src/Way.hs index 9f7f12a..3b1f6c0 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -82,7 +82,7 @@ instance Eq Way where -- | Build with no 'WayUnit's at all. vanilla :: Way -vanilla = wayFromUnits [] +vanilla = wayFromUnits [] -- | Build with profiling. profiling :: Way @@ -90,14 +90,14 @@ profiling = wayFromUnits [Profiling] -- | Build with logging. logging :: Way -logging = wayFromUnits [Logging] +logging = wayFromUnits [Logging] -- | Build in parallel. parallel :: Way -parallel = wayFromUnits [Parallel] +parallel = wayFromUnits [Parallel] granSim :: Way -granSim = wayFromUnits [GranSim] +granSim = wayFromUnits [GranSim] -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? From git at git.haskell.org Fri Oct 27 00:32:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on the exact version of the in-tree Cabal library (e664431) Message-ID: <20171027003205.A6CDC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e664431fb9a240599f512474cf611c51d5d701cb/ghc >--------------------------------------------------------------- commit e664431fb9a240599f512474cf611c51d5d701cb Author: Andrey Mokhov Date: Thu Mar 16 00:56:50 2017 +0000 Depend on the exact version of the in-tree Cabal library >--------------------------------------------------------------- e664431fb9a240599f512474cf611c51d5d701cb hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 18361f3..fd6c036 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -117,7 +117,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.25.* + , Cabal == 2.0.0.0 , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 00:32:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a paragraph on customising progress messages (2c77b71) Message-ID: <20171027003207.A9D093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c77b7107ccf663598b9b64a22f3a4c5bc39b568/ghc >--------------------------------------------------------------- commit 2c77b7107ccf663598b9b64a22f3a4c5bc39b568 Author: Andrey Mokhov Date: Tue May 17 23:55:16 2016 +0100 Add a paragraph on customising progress messages See #244. [skip ci] >--------------------------------------------------------------- 2c77b7107ccf663598b9b64a22f3a4c5bc39b568 doc/user-settings.md | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/doc/user-settings.md b/doc/user-settings.md index 4624e2d..1433ae9 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -144,3 +144,20 @@ splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock ``` + +Hadrian prints various progress info during the build. You can customise how this +info is printed by overriding `putBuild` and `putSuccess` commands: + +```haskell +-- | Customise build progress messages (e.g. executing a build command). +putBuild :: String -> Action () +putBuild = putColoured Vivid White + +-- | Customise build success messages (e.g. a package is built successfully). +putSuccess :: String -> Action () +putSuccess = putColoured Vivid Green +``` + +You can tune colours for your favourite terminal and also change the verbosity +level, e.g. by setting `putSuccess = putLoud`, which will hide success messages +unless Hadrian is called with `--verbose` flag. From git at git.haskell.org Fri Oct 27 00:32:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build badges more informative (bf18da2) Message-ID: <20171027003208.E43473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf18da2ffa30040b3a51949f8cf75f2fef09d2cd/ghc >--------------------------------------------------------------- commit bf18da2ffa30040b3a51949f8cf75f2fef09d2cd Author: Andrey Mokhov Date: Thu Jan 7 23:13:16 2016 +0000 Make build badges more informative [skip ci] >--------------------------------------------------------------- bf18da2ffa30040b3a51949f8cf75f2fef09d2cd README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 2259c0b..fe6a909 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Shaking up GHC ============== -[![Build Status](https://travis-ci.org/snowleopard/shaking-up-ghc.svg)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Build status](https://ci.appveyor.com/api/projects/status/9er74sbnrkco98gb?svg=true&pendingText=Windows&passingText=Windows&failingText=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) As part of my 6-month research secondment to Microsoft Research in Cambridge From git at git.haskell.org Fri Oct 27 00:32:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename compact to ghc-compact (30708a4) Message-ID: <20171027003209.4C66E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30708a47a3456f68bca6951232c02b26dda86585/ghc >--------------------------------------------------------------- commit 30708a47a3456f68bca6951232c02b26dda86585 Author: Andrey Mokhov Date: Thu Mar 16 01:17:01 2017 +0000 Rename compact to ghc-compact >--------------------------------------------------------------- 30708a47a3456f68bca6951232c02b26dda86585 src/GHC.hs | 25 ++++++++++++------------- src/Settings/Default.hs | 2 +- 2 files changed, 13 insertions(+), 14 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index f8abeb8..33af662 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,14 +1,13 @@ {-# LANGUAGE OverloadedStrings, LambdaCase #-} {-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( - array, base, binary, bytestring, cabal, checkApiAnnotations, compact, - compareSizes, compiler, containers, deepseq, deriveConstants, directory, - dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, - ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, - hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, - libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, - stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, - win32, xhtml, + array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, + compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, + genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, + ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, + hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, + parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, + terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, defaultKnownPackages, builderProvenance, programName, nonCabalContext, nonHsMainPackage @@ -26,10 +25,10 @@ import Stage -- be overridden in @hadrian/src/UserSettings.hs at . defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, binary, bytestring, cabal, checkApiAnnotations, compact - , compareSizes, compiler, containers, deepseq, deriveConstants, directory - , dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh - , ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs + [ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes + , compiler, containers, deepseq, deriveConstants, directory, dllSplit + , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal + , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs , hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 @@ -42,7 +41,6 @@ binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" checkApiAnnotations = utility "check-api-annotations" -compact = library "compact" compareSizes = utility "compareSizes" `setPath` "utils/compare_sizes" compiler = topLevel "ghc" `setPath` "compiler" containers = library "containers" @@ -57,6 +55,7 @@ ghc = topLevel "ghc-bin" `setPath` "ghc" `setType` Progra ghcBoot = library "ghc-boot" ghcBootTh = library "ghc-boot-th" ghcCabal = utility "ghc-cabal" +ghcCompact = library "ghc-compact" ghci = library "ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 318b0a0..89db236 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -120,13 +120,13 @@ stage1Packages = do , append $ [ array , base , bytestring - , compact , containers , deepseq , directory , filepath , ghc , ghcCabal + , ghcCompact , ghci , ghcPrim , haskeline From git at git.haskell.org Fri Oct 27 00:32:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace quote by show (d6a0d7a) Message-ID: <20171027003211.285963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6a0d7af44a6365e784cfa3e1d0da114b958e3f1/ghc >--------------------------------------------------------------- commit d6a0d7af44a6365e784cfa3e1d0da114b958e3f1 Author: Andrey Mokhov Date: Wed May 18 00:11:12 2016 +0100 Replace quote by show >--------------------------------------------------------------- d6a0d7af44a6365e784cfa3e1d0da114b958e3f1 src/Base.hs | 11 ++++----- src/Rules/Generators/ConfigHs.hs | 36 ++++++++++++++-------------- src/Rules/Generators/GhcBootPlatformH.hs | 24 +++++++++---------- src/Rules/Generators/GhcPlatformH.hs | 16 ++++++------- src/Rules/Generators/GhcSplit.hs | 4 ++-- src/Rules/Generators/VersionHs.hs | 6 ++--- src/Settings/Packages/Rts.hs | 40 ++++++++++++++++---------------- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/User.hs | 2 +- 9 files changed, 69 insertions(+), 72 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 d6a0d7af44a6365e784cfa3e1d0da114b958e3f1 From git at git.haskell.org Fri Oct 27 00:32:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try fetching ghc-tarballs via stack exec. (ee94a7c) Message-ID: <20171027003212.6144C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee94a7ce968d9a5fe1674018af8d7a2f52e8bb12/ghc >--------------------------------------------------------------- commit ee94a7ce968d9a5fe1674018af8d7a2f52e8bb12 Author: Andrey Mokhov Date: Thu Jan 7 23:23:10 2016 +0000 Try fetching ghc-tarballs via stack exec. See #110. [skip ci] >--------------------------------------------------------------- ee94a7ce968d9a5fe1674018af8d7a2f52e8bb12 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7d5a0f8..79f3369 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -11,8 +11,8 @@ install: - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - bash -lc "mkdir -p /home/ghc/ghc-tarballs" - - bash -lc "cd /home/ghc && ./mk/get-win32-tarballs.sh download x86_64" + - cd C:\msys64\home\ghc + - stack exec -- mk/get-win32-tarballs.sh download x86_64 build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:32:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename readPackageDescription to readGenericPackageDescription to fix the warning (198abb4) Message-ID: <20171027003212.BFBE13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/198abb4fff538fb67ab9262aa0a7ca5b8bd86c0f/ghc >--------------------------------------------------------------- commit 198abb4fff538fb67ab9262aa0a7ca5b8bd86c0f Author: Andrey Mokhov Date: Thu Mar 16 01:17:36 2017 +0000 Rename readPackageDescription to readGenericPackageDescription to fix the warning >--------------------------------------------------------------- 198abb4fff538fb67ab9262aa0a7ca5b8bd86c0f src/Rules/Cabal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 0df267f..b45af42 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -23,7 +23,7 @@ cabalRules = do let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] - pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg + pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg let identifier = package . packageDescription $ pd version = display . pkgVersion $ identifier return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version @@ -37,7 +37,7 @@ cabalRules = do if not exists then return $ pkgNameString pkg else do need [pkgCabalFile pkg] - pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg + pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg let depsLib = collectDeps $ condLibrary pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes From git at git.haskell.org Fri Oct 27 00:32:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add quote function (c81dc684f7) Message-ID: <20171027003214.983453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c81dc684f7206ebabf877d54c8a740398e5e425a/ghc >--------------------------------------------------------------- commit c81dc684f7206ebabf877d54c8a740398e5e425a Author: Andrey Mokhov Date: Wed May 18 00:28:08 2016 +0100 Add quote function >--------------------------------------------------------------- c81dc684f7206ebabf877d54c8a740398e5e425a src/Base.hs | 6 +++++- src/Builder.hs | 6 +++--- src/Oracles/Config.hs | 2 +- src/Oracles/Config/Flag.hs | 6 +++--- src/Oracles/Dependencies.hs | 4 ++-- src/Rules/Actions.hs | 2 +- src/Rules/Data.hs | 10 +++++----- src/Rules/Generate.hs | 4 ++-- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 6 +++--- 10 files changed, 26 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c81dc684f7206ebabf877d54c8a740398e5e425a From git at git.haskell.org Fri Oct 27 00:32:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build rules for *.S sources, add rts/*.S files. (b6bb19c) Message-ID: <20171027003216.038043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6bb19c87edc0e36e1322af12622493a61f48386/ghc >--------------------------------------------------------------- commit b6bb19c87edc0e36e1322af12622493a61f48386 Author: Andrey Mokhov Date: Thu Jan 7 23:53:44 2016 +0000 Add build rules for *.S sources, add rts/*.S files. See #126. >--------------------------------------------------------------- b6bb19c87edc0e36e1322af12622493a61f48386 src/Rules/Data.hs | 11 ++++++++--- src/Rules/Dependencies.hs | 9 +++++---- 2 files changed, 13 insertions(+), 7 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 46072ce..de4f8c0 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -95,13 +95,18 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do ++ [ "posix" | not windows ] ++ [ "win32" | windows ] -- TODO: rts/dist/build/sm/Evac_thr.c, rts/dist/build/sm/Scav_thr.c - -- TODO: adding cmm sources to C_SRCS is a hack; rethink after #18 + -- TODO: adding cmm/S sources to C_SRCS is a hack; rethink after #18 cSrcs <- getDirectoryFiles (pkgPath pkg) (map (-/- "*.c") dirs) cmmSrcs <- getDirectoryFiles (pkgPath pkg) ["*.cmm"] - let extraSrcs = [ targetDirectory Stage1 rts -/- "build/AutoApply.cmm" ] + buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] + buildStgCRunAsm <- anyTargetArch ["powerpc64le"] + let sSrcs = [ "AdjustorAsm.S" | buildAdjustor ] + ++ [ "StgCRunAsm.S" | buildStgCRunAsm ] + extraSrcs = [ targetDirectory Stage1 rts -/- "build/AutoApply.cmm" ] includes <- interpretPartial target $ fromDiffExpr includesArgs let contents = unlines $ map (prefix++) - [ "C_SRCS = " ++ unwords (cSrcs ++ cmmSrcs ++ extraSrcs) + [ "C_SRCS = " + ++ unwords (cSrcs ++ cmmSrcs ++ sSrcs ++ extraSrcs) , "CC_OPTS = " ++ unwords includes , "COMPONENT_ID = " ++ "rts" ] writeFileChanged mk contents diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 79bcdb2..2da9549 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -15,10 +15,11 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = dropBuild = (pkgPath pkg ++) . drop (length buildPath) hDepFile = buildPath -/- ".hs-dependencies" in do - [ buildPath ++ "//*.c.deps", buildPath ++ "//*.cmm.deps" ] |%> \out -> do - let srcFile = dropBuild . dropExtension $ out - need [srcFile] - build $ fullTarget target (GccM stage) [srcFile] [out] + fmap (buildPath++) + [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do + let srcFile = dropBuild . dropExtension $ out + need [srcFile] + build $ fullTarget target (GccM stage) [srcFile] [out] hDepFile %> \out -> do srcs <- interpretPartial target getPackageSources From git at git.haskell.org Fri Oct 27 00:32:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop repetition in the list of packages, fixing Hadrian's selftest (7b90c76) Message-ID: <20171027003216.5ACD53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b90c7636c20de71b133dba2a1c0bae4ee591dbe/ghc >--------------------------------------------------------------- commit 7b90c7636c20de71b133dba2a1c0bae4ee591dbe Author: Andrey Mokhov Date: Thu Mar 16 11:31:47 2017 +0000 Drop repetition in the list of packages, fixing Hadrian's selftest >--------------------------------------------------------------- 7b90c7636c20de71b133dba2a1c0bae4ee591dbe src/Settings/Default.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 89db236..d242502 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -127,7 +127,6 @@ stage1Packages = do , ghc , ghcCabal , ghcCompact - , ghci , ghcPrim , haskeline , hpcBin From git at git.haskell.org Fri Oct 27 00:32:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix putSuccess (1080ebf) Message-ID: <20171027003218.092923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1080ebfc611e8cdae0b4efb166f166a9cebfa6e8/ghc >--------------------------------------------------------------- commit 1080ebfc611e8cdae0b4efb166f166a9cebfa6e8 Author: Andrey Mokhov Date: Wed May 18 00:53:54 2016 +0100 Fix putSuccess >--------------------------------------------------------------- 1080ebfc611e8cdae0b4efb166f166a9cebfa6e8 src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 60aeb89..16c7c25 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -102,4 +102,4 @@ putBuild = putColoured Vivid White -- | Customise build success messages (e.g. a package is built successfully). putSuccess :: String -> Action () -putSuccess = withVerbosity Loud . putColoured Vivid Green +putSuccess = putColoured Vivid Green From git at git.haskell.org Fri Oct 27 00:32:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Specify path to stack. (9ad20c9) Message-ID: <20171027003219.6842C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ad20c9a77dd8655d53bc1e0f512794876df8741/ghc >--------------------------------------------------------------- commit 9ad20c9a77dd8655d53bc1e0f512794876df8741 Author: Andrey Mokhov Date: Thu Jan 7 23:57:57 2016 +0000 Specify path to stack. See #110. [skip ci] >--------------------------------------------------------------- 9ad20c9a77dd8655d53bc1e0f512794876df8741 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 79f3369..9e1ed1e 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -12,7 +12,7 @@ install: - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - - stack exec -- mk/get-win32-tarballs.sh download x86_64 + - C:\stack exec -- mk/get-win32-tarballs.sh download x86_64 build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:32:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Added a note about git line-ending settings (#303) (295c781) Message-ID: <20171027003219.BD5A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/295c7812ab8fe8e34e6812127e039220a850a344/ghc >--------------------------------------------------------------- commit 295c7812ab8fe8e34e6812127e039220a850a344 Author: Ivan Poliakov Date: Fri Mar 31 23:54:46 2017 +0100 Added a note about git line-ending settings (#303) >--------------------------------------------------------------- 295c7812ab8fe8e34e6812127e039220a850a344 doc/windows.md | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/doc/windows.md b/doc/windows.md index 73804df..510b986 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -5,6 +5,14 @@ Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). +Note that `git` should be configured to check out Unix-style line endings. The default behaviour of `git` on Windows is to check out Windows-style line endings which can cause issues during the build. This can be changed using the following command: + + git config --global core.autocrlf false + +If you would like to restore the default behaviour later run: + + git config --global core.autocrlf true + ```sh # Get GHC and Hadrian sources git clone --recursive git://git.haskell.org/ghc.git From git at git.haskell.org Fri Oct 27 00:32:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add init script, fix path to stak. (23ef499) Message-ID: <20171027003223.311353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23ef49931f9e0970746cd603c46e4a996438d27e/ghc >--------------------------------------------------------------- commit 23ef49931f9e0970746cd603c46e4a996438d27e Author: Andrey Mokhov Date: Fri Jan 8 01:18:48 2016 +0000 Add init script, fix path to stak. See #110. [skip ci] >--------------------------------------------------------------- 23ef49931f9e0970746cd603c46e4a996438d27e .appveyor.yml | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 9e1ed1e..5ad5f0b 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,6 +1,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -install: +init: + - cd - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 @@ -9,12 +10,13 @@ install: - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc + +install: - cd C:\msys64\home\ghc - - C:\stack exec -- mk/get-win32-tarballs.sh download x86_64 + - shake-build\stack.exe exec -- mk/get-win32-tarballs.sh download x86_64 build_script: - - bash -lc "cd /home/ghc && ./boot" - - bash -lc "cd /home/ghc && echo \"\" | ./configure" - - bash -lc "cd /home/ghc && ./shake-build/build.bat -j --no-progress" + - bash -lc "./boot" + - bash -lc "echo \"\" | ./configure" + - bash -lc "./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:32:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add wrapper for Runhaskell, Fix #304 (#305) (c158014) Message-ID: <20171027003223.84A3D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c158014fbb90046a43d1d6d78b888a687ce341c6/ghc >--------------------------------------------------------------- commit c158014fbb90046a43d1d6d78b888a687ce341c6 Author: Zhen Zhang Date: Sun Apr 16 04:08:33 2017 +0800 Add wrapper for Runhaskell, Fix #304 (#305) >--------------------------------------------------------------- c158014fbb90046a43d1d6d78b888a687ce341c6 .gitignore | 3 +++ src/Rules/Program.hs | 2 ++ src/Rules/Wrappers/Runhaskell.hs | 15 +++++++++++++++ 3 files changed, 20 insertions(+) diff --git a/.gitignore b/.gitignore index 6b06fea..2e3581b 100644 --- a/.gitignore +++ b/.gitignore @@ -17,3 +17,6 @@ cabal.sandbox.config # the user settings /UserSettings.hs + +# Mostly temp file by emacs +*~ diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 254284a..71fb8b7 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -12,6 +12,7 @@ import Oracles.ModuleFiles import Oracles.PackageData import Rules.Wrappers.Ghc import Rules.Wrappers.GhcPkg +import Rules.Wrappers.Runhaskell import Settings import Settings.Path import Target @@ -25,6 +26,7 @@ type Wrapper = FilePath -> Expr String wrappers :: [(Context, Wrapper)] wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) + , (vanillaContext Stage1 runGhc, runhaskellWrapper) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper) ] buildProgram :: [(Resource, Int)] -> Context -> Rules () diff --git a/src/Rules/Wrappers/Runhaskell.hs b/src/Rules/Wrappers/Runhaskell.hs new file mode 100644 index 0000000..521b41a --- /dev/null +++ b/src/Rules/Wrappers/Runhaskell.hs @@ -0,0 +1,15 @@ +module Rules.Wrappers.Runhaskell (runhaskellWrapper) where + +import Base +import Expression +import Oracles.Path + +runhaskellWrapper :: FilePath -> Expr String +runhaskellWrapper program = do + lift $ need [sourcePath -/- "Rules/Wrappers/Runhaskell.hs"] + top <- getTopDirectory + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (top -/- program) + ++ " -f" ++ (top -/- "inplace/lib/bin/ghc-stage2") -- HACK + ++ " -B" ++ (top -/- "inplace/lib") ++ " ${1+\"$@\"}" ] From git at git.haskell.org Fri Oct 27 00:32:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --progress-colour command line flag (aa9c65b) Message-ID: <20171027003221.71E753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aa9c65b3adb91b56c1974a0db39ef3c5082e816c/ghc >--------------------------------------------------------------- commit aa9c65b3adb91b56c1974a0db39ef3c5082e816c Author: Andrey Mokhov Date: Wed May 18 02:54:23 2016 +0100 Add --progress-colour command line flag Fix #244. >--------------------------------------------------------------- aa9c65b3adb91b56c1974a0db39ef3c5082e816c src/Base.hs | 27 +++++++++++++++++---------- src/CmdLineFlag.hs | 51 ++++++++++++++++++++++++++++++++++++--------------- 2 files changed, 53 insertions(+), 25 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 6fe8ac1..cb040d4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -38,6 +38,8 @@ import System.Console.ANSI import System.IO import System.Info +import CmdLineFlag + -- TODO: reexport Stage, etc.? -- | Hadrian lives in 'hadrianPath' directory of the GHC tree. @@ -144,14 +146,19 @@ matchVersionedFilePath prefix suffix filePath = -- | A more colourful version of Shake's putNormal. putColoured :: ColorIntensity -> Color -> String -> Action () putColoured intensity colour msg = do - liftIO $ set [SetColor Foreground intensity colour] + c <- useColour + when c . liftIO $ setSGR [SetColor Foreground intensity colour] putNormal msg - liftIO $ set [] - liftIO $ hFlush stdout - where - set a = do - supported <- hSupportsANSI stdout - when (win || supported) $ setSGR a - -- An ugly hack to always try to print colours when on mingw and cygwin. - -- See: https://github.com/snowleopard/hadrian/pull/253 - win = "mingw" `isPrefixOf` os || "cygwin" `isPrefixOf` os + when c . liftIO $ do + setSGR [] + hFlush stdout + +useColour :: Action Bool +useColour = case cmdProgressColour of + Never -> return False + Always -> return True + Auto -> do + supported <- liftIO $ hSupportsANSI stdout + -- An ugly hack to always try to print colours when on mingw and cygwin. + let windows = any (`isPrefixOf` os) ["mingw", "cygwin"] + return $ windows || supported diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 8fc1487..10c39f2 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,35 +1,39 @@ module CmdLineFlag ( putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, Flavour (..), - cmdProgressInfo, ProgressInfo (..), cmdSkipConfigure, cmdSplitObjects + cmdProgressColour, ProgressColour (..), cmdProgressInfo, ProgressInfo (..), + cmdSkipConfigure, cmdSplitObjects ) where import Data.IORef import Data.List.Extra import System.Console.GetOpt -import System.IO.Unsafe (unsafePerformIO) +import System.IO.Unsafe -- | 'CmdLineFlag.Untracked' is a collection of flags that can be passed via the -- command line. These flags are not tracked, that is they do not force any -- build rules to be rurun. data Untracked = Untracked - { buildHaddock :: Bool - , flavour :: Flavour - , progressInfo :: ProgressInfo - , skipConfigure :: Bool - , splitObjects :: Bool } + { buildHaddock :: Bool + , flavour :: Flavour + , progressColour :: ProgressColour + , progressInfo :: ProgressInfo + , skipConfigure :: Bool + , splitObjects :: Bool } deriving (Eq, Show) -data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -data Flavour = Default | Quick deriving (Eq, Show) +data Flavour = Default | Quick deriving (Eq, Show) +data ProgressColour = Never | Auto | Always deriving (Eq, Show) +data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked defaultUntracked = Untracked - { buildHaddock = False - , flavour = Default - , progressInfo = Normal - , skipConfigure = False - , splitObjects = False } + { buildHaddock = False + , flavour = Default + , progressColour = Auto + , progressInfo = Normal + , skipConfigure = False + , splitObjects = False } readBuildHaddock :: Either String (Untracked -> Untracked) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } @@ -45,6 +49,18 @@ readFlavour ms = set :: Flavour -> Untracked -> Untracked set flag flags = flags { flavour = flag } +readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) +readProgressColour ms = + maybe (Left "Cannot parse progress-colour") (Right . set) (go =<< lower <$> ms) + where + go :: String -> Maybe ProgressColour + go "never" = Just Never + go "auto" = Just Auto + go "always" = Just Always + go _ = Nothing + set :: ProgressColour -> Untracked -> Untracked + set flag flags = flags { progressColour = flag } + readProgressInfo :: Maybe String -> Either String (Untracked -> Untracked) readProgressInfo ms = maybe (Left "Cannot parse progress-info") (Right . set) (go =<< lower <$> ms) @@ -70,8 +86,10 @@ cmdFlags = "Build flavour (Default or Quick)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." + , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") + "Use colours in progress info (Never, Auto or Always)." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") - "Progress info style (None, Brief, Normal, or Unicorn)." + "Progress info style (None, Brief, Normal or Unicorn)." , Option [] ["skip-configure"] (NoArg readSkipConfigure) "Skip the boot and configure scripts (if you want to run them manually)." , Option [] ["split-objects"] (NoArg readSplitObjects) @@ -96,6 +114,9 @@ cmdBuildHaddock = buildHaddock getCmdLineFlags cmdFlavour :: Flavour cmdFlavour = flavour getCmdLineFlags +cmdProgressColour :: ProgressColour +cmdProgressColour = progressColour getCmdLineFlags + cmdProgressInfo :: ProgressInfo cmdProgressInfo = progressInfo getCmdLineFlags From git at git.haskell.org Fri Oct 27 00:32:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GHC ticket 13583 has been resolved, so the workaround is no longer needed (4347b0d) Message-ID: <20171027003234.7048C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4347b0dc3265faec235672b1ba889bb56b38798a/ghc >--------------------------------------------------------------- commit 4347b0dc3265faec235672b1ba889bb56b38798a Author: Andrey Mokhov Date: Thu Apr 27 00:43:14 2017 +0100 GHC ticket 13583 has been resolved, so the workaround is no longer needed See #276 >--------------------------------------------------------------- 4347b0dc3265faec235672b1ba889bb56b38798a src/Settings/Builders/Configure.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 3ab3286..b6142d7 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -1,7 +1,5 @@ module Settings.Builders.Configure (configureBuilderArgs) where -import qualified System.Info as System - import Settings.Builders.Common configureBuilderArgs :: Args @@ -20,9 +18,4 @@ configureBuilderArgs = mconcat , "--libdir=" ++ top -/- libffiBuildPath -/- "inst/lib" , "--enable-static=yes" , "--enable-shared=no" -- TODO: add support for yes - , "--host=" ++ targetPlatform ] - - -- On OS X, use "nm-classic" instead of "nm" due to a bug in the latter. - -- See https://ghc.haskell.org/trac/ghc/ticket/11744 - , builder (Configure ".") ? System.os == "darwin" ? - arg "--with-nm=$(xcrun --find nm-classic)" ] + , "--host=" ++ targetPlatform ] ] From git at git.haskell.org Fri Oct 27 00:32:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (7053d0c) Message-ID: <20171027003235.3D0A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7053d0caad3fd13f471a62c681d4d7a91ad843ba/ghc >--------------------------------------------------------------- commit 7053d0caad3fd13f471a62c681d4d7a91ad843ba Author: Andrey Mokhov Date: Thu May 19 22:32:41 2016 +0100 Minor revision >--------------------------------------------------------------- 7053d0caad3fd13f471a62c681d4d7a91ad843ba src/Settings/Builders/Configure.hs | 27 ++++++++++++++------------- src/Settings/Builders/DeriveConstants.hs | 19 +++++++++---------- src/Settings/Builders/Ghc.hs | 13 ++++++------- src/Settings/Builders/GhcCabal.hs | 7 ++----- src/Settings/Builders/GhcPkg.hs | 5 +---- src/Settings/Builders/Haddock.hs | 1 - src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Builders/Make.hs | 6 +++--- src/Settings/Builders/Tar.hs | 8 +++----- src/Settings/Packages/Compiler.hs | 6 ++++-- src/Settings/Packages/Ghc.hs | 3 ++- src/Settings/Packages/GhcCabal.hs | 15 ++++++--------- src/Settings/Packages/Hp2ps.hs | 7 +++---- src/Settings/Packages/IntegerGmp.hs | 10 ++++++---- src/Settings/Packages/Rts.hs | 6 ++++-- src/Settings/Packages/RunGhc.hs | 5 ++--- src/Settings/Packages/Touchy.hs | 7 +++---- src/Settings/Packages/Unlit.hs | 7 +++---- 18 files changed, 72 insertions(+), 82 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 7053d0caad3fd13f471a62c681d4d7a91ad843ba From git at git.haskell.org Fri Oct 27 00:32:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot & configure via stack exec. (8c9544a) Message-ID: <20171027003237.CB50F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c9544add5c72545c98e7b5cb43aa7d0db35590d/ghc >--------------------------------------------------------------- commit 8c9544add5c72545c98e7b5cb43aa7d0db35590d Author: Andrey Mokhov Date: Fri Jan 8 02:51:51 2016 +0000 Run boot & configure via stack exec. See #110. [skip ci] >--------------------------------------------------------------- 8c9544add5c72545c98e7b5cb43aa7d0db35590d .appveyor.yml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f663d96..8333761 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,17 +8,18 @@ install: - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - stack exec -- pacman -S --noconfirm gcc binutils p7zip git + - stack exec -- pacman -S --noconfirm perl gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - stack exec -- mk/get-win32-tarballs.sh download x86_64 + - cd C:\msys64\home\ghc + - stack exec -- perl boot + - stack exec -- configure --enable-tarballs-autodownload - ghc --version - stack --version - alex --version - happy --version build_script: - - bash -lc "./boot" - - bash -lc "echo \"\" | ./configure" + - cd - bash -lc "./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:32:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use xcode8 image (b3339d4) Message-ID: <20171027003238.4272B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3339d475a56c2c1617bb5803e742509eb2b6821/ghc >--------------------------------------------------------------- commit b3339d475a56c2c1617bb5803e742509eb2b6821 Author: Andrey Mokhov Date: Thu Apr 27 01:08:41 2017 +0100 Use xcode8 image >--------------------------------------------------------------- b3339d475a56c2c1617bb5803e742509eb2b6821 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index f6eda04..dd6af26 100644 --- a/.travis.yml +++ b/.travis.yml @@ -16,6 +16,7 @@ matrix: - PATH="/opt/cabal/1.22/bin:$PATH" - os: osx + osx_image: xcode8 env: MODE="--flavour=quickest --integer-simple" before_install: - brew update From git at git.haskell.org Fri Oct 27 00:32:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link gmp objects to integerGmp library (5b75d12) Message-ID: <20171027003238.AC6773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b75d126eb0716e44be9be27dc4895a915d78a52/ghc >--------------------------------------------------------------- commit 5b75d126eb0716e44be9be27dc4895a915d78a52 Author: Andrey Mokhov Date: Thu May 19 22:55:32 2016 +0100 Link gmp objects to integerGmp library Fix #241 >--------------------------------------------------------------- 5b75d126eb0716e44be9be27dc4895a915d78a52 src/Rules/Library.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 637dbaa..3fff65f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -69,9 +69,10 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do let cObjs = map (objFile context) cSrcs hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] + gObjs = [ gmpObjects -/- "*.o" | package == integerGmp ] objs = cObjs ++ hObjs need objs - build $ Target context Ld objs [obj] + build $ Target context Ld (objs ++ gObjs) [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' From git at git.haskell.org Fri Oct 27 00:32:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't reinstall perl. (efeb163) Message-ID: <20171027003241.7356A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efeb163633b8e2f9c2e551da13fff7b7c750578c/ghc >--------------------------------------------------------------- commit efeb163633b8e2f9c2e551da13fff7b7c750578c Author: Andrey Mokhov Date: Fri Jan 8 02:55:38 2016 +0000 Don't reinstall perl. See #110. [skip ci] >--------------------------------------------------------------- efeb163633b8e2f9c2e551da13fff7b7c750578c .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 8333761..2a4a628 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,7 +8,7 @@ install: - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - stack exec -- pacman -S --noconfirm perl gcc binutils p7zip git + - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Fri Oct 27 00:32:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename runHaskell wrapper to runGhc for consistency (c4e2e45) Message-ID: <20171027003241.EA81A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4e2e45be2e11e5785b033ab10511455c2dd00fc/ghc >--------------------------------------------------------------- commit c4e2e45be2e11e5785b033ab10511455c2dd00fc Author: Andrey Mokhov Date: Thu Apr 27 21:39:41 2017 +0100 Rename runHaskell wrapper to runGhc for consistency See #305 >--------------------------------------------------------------- c4e2e45be2e11e5785b033ab10511455c2dd00fc hadrian.cabal | 1 + src/Rules/Program.hs | 4 ++-- src/Rules/Wrappers/{Runhaskell.hs => RunGhc.hs} | 8 ++++---- 3 files changed, 7 insertions(+), 6 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index fd6c036..15c3a2b 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -66,6 +66,7 @@ executable hadrian , Rules.Test , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg + , Rules.Wrappers.RunGhc , Settings , Settings.Builders.Alex , Settings.Builders.Ar diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 71fb8b7..62d4b24 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -12,7 +12,7 @@ import Oracles.ModuleFiles import Oracles.PackageData import Rules.Wrappers.Ghc import Rules.Wrappers.GhcPkg -import Rules.Wrappers.Runhaskell +import Rules.Wrappers.RunGhc import Settings import Settings.Path import Target @@ -26,7 +26,7 @@ type Wrapper = FilePath -> Expr String wrappers :: [(Context, Wrapper)] wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) - , (vanillaContext Stage1 runGhc, runhaskellWrapper) + , (vanillaContext Stage1 runGhc, runGhcWrapper) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper) ] buildProgram :: [(Resource, Int)] -> Context -> Rules () diff --git a/src/Rules/Wrappers/Runhaskell.hs b/src/Rules/Wrappers/RunGhc.hs similarity index 59% rename from src/Rules/Wrappers/Runhaskell.hs rename to src/Rules/Wrappers/RunGhc.hs index 521b41a..95b5700 100644 --- a/src/Rules/Wrappers/Runhaskell.hs +++ b/src/Rules/Wrappers/RunGhc.hs @@ -1,12 +1,12 @@ -module Rules.Wrappers.Runhaskell (runhaskellWrapper) where +module Rules.Wrappers.RunGhc (runGhcWrapper) where import Base import Expression import Oracles.Path -runhaskellWrapper :: FilePath -> Expr String -runhaskellWrapper program = do - lift $ need [sourcePath -/- "Rules/Wrappers/Runhaskell.hs"] +runGhcWrapper :: FilePath -> Expr String +runGhcWrapper program = do + lift $ need [sourcePath -/- "Rules/Wrappers/RunGhc.hs"] top <- getTopDirectory return $ unlines [ "#!/bin/bash" From git at git.haskell.org Fri Oct 27 00:32:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revise comments (816b0ac) Message-ID: <20171027003242.53F843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/816b0acda7a57cdb3c7a88831b445bb17405975b/ghc >--------------------------------------------------------------- commit 816b0acda7a57cdb3c7a88831b445bb17405975b Author: Andrey Mokhov Date: Thu May 19 23:39:15 2016 +0100 Revise comments >--------------------------------------------------------------- 816b0acda7a57cdb3c7a88831b445bb17405975b src/Oracles/ArgsHash.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index c26efd4..bb597c4 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -8,26 +8,25 @@ import Settings.Args import Target newtype ArgsHashKey = ArgsHashKey Target - deriving (Show, Eq, Typeable, Binary, Hashable, NFData) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- This is an action that given a full target determines the corresponding --- argument list and computes its hash. The resulting value is tracked in a --- Shake oracle, hence initiating rebuilts when the hash is changed (a hash --- change indicates changes in the build system). +-- TODO: Hash Target to improve accuracy and performance. +-- | Given a full target this Action determines the corresponding argument list +-- and computes its hash. The resulting value is tracked in a Shake oracle, +-- hence initiating rebuilds when the hash changes (a hash change indicates +-- changes in the build command for the given target). -- Note: we keep only the first target input for performance reasons -- to -- avoid storing long lists of source files passed to some builders (e.g. Ar) --- in the Shake database. This optimisation is harmless, because argument list --- constructors are assumed not to examine target sources, but only append them --- to argument lists where appropriate. --- TODO: enforce the above assumption via type trickery? --- TODO: Hash Target to improve accuracy and performance. +-- in the Shake database. This optimisation is normally harmless, because +-- argument list constructors are assumed not to examine target sources, but +-- only append them to argument lists where appropriate. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do let hashed = [ show . hash $ inputs target ] _ <- askOracle . ArgsHashKey $ target { inputs = hashed } :: Action Int return () --- Oracle for storing per-target argument list hashes +-- | Oracle for storing per-target argument list hashes. argsHashOracle :: Rules () argsHashOracle = void $ addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs From git at git.haskell.org Fri Oct 27 00:32:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to configure. (c6d3c5e) Message-ID: <20171027003244.E41893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6d3c5eedbd3257c75b5fbd31fe8cea3dcfa0c05/ghc >--------------------------------------------------------------- commit c6d3c5eedbd3257c75b5fbd31fe8cea3dcfa0c05 Author: Andrey Mokhov Date: Fri Jan 8 03:23:31 2016 +0000 Fix path to configure. See #110. [skip ci] >--------------------------------------------------------------- c6d3c5eedbd3257c75b5fbd31fe8cea3dcfa0c05 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 2a4a628..82cdce4 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,7 +14,7 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - stack exec -- configure --enable-tarballs-autodownload + - stack exec -- ./configure --enable-tarballs-autodownload - ghc --version - stack --version - alex --version From git at git.haskell.org Fri Oct 27 00:32:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependency (ba108c0) Message-ID: <20171027003245.D739D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba108c0198cc3ee6cd758273f9bd8fea14ba93a5/ghc >--------------------------------------------------------------- commit ba108c0198cc3ee6cd758273f9bd8fea14ba93a5 Author: Andrey Mokhov Date: Thu May 19 23:50:46 2016 +0100 Add missing dependency See #241. >--------------------------------------------------------------- ba108c0198cc3ee6cd758273f9bd8fea14ba93a5 src/Rules/Library.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 3fff65f..a198c64 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -71,6 +71,7 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] gObjs = [ gmpObjects -/- "*.o" | package == integerGmp ] objs = cObjs ++ hObjs + when (package == integerGmp) $ orderOnly [gmpLibraryH] need objs build $ Target context Ld (objs ++ gObjs) [obj] From git at git.haskell.org Fri Oct 27 00:32:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable some warnings (#307) (3ea149a) Message-ID: <20171027003245.683F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ea149adad2311ea711bc58950e288d081fde79a/ghc >--------------------------------------------------------------- commit 3ea149adad2311ea711bc58950e288d081fde79a Author: Zhen Zhang Date: Fri Apr 28 23:28:04 2017 +0800 Disable some warnings (#307) >--------------------------------------------------------------- 3ea149adad2311ea711bc58950e288d081fde79a src/Settings/Default.hs | 42 +++++++++++++++++++++++++++++++++++++++++- 1 file changed, 41 insertions(+), 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index d242502..90e2db0 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -215,6 +215,43 @@ defaultBuilderArgs = mconcat , makeBuilderArgs , tarBuilderArgs ] +-- | Disable some warnings in packages we use +-- | https://github.com/ghc/ghc/blob/master/mk/warnings.mk#L46 +disableWarningArgsStage0 :: Args +disableWarningArgsStage0 = stage Stage0 ? builder Ghc ? mconcat + [ package transformers ? append [ "-fno-warn-unused-matches", "-fno-warn-unused-imports" ] + , package terminfo ? append [ "-fno-warn-unused-imports" ] ] + +disableWarningArgsStage1 :: Args +disableWarningArgsStage1 = notStage0 ? builder Ghc ? mconcat + [ package bytestring ? append [ "-Wno-inline-rule-shadowing" ] + , package haddock ? append [ "-Wno-unused-imports", "-Wno-deprecations" ] + , package directory ? append [ "-Wno-unused-imports" ] + , package binary ? append [ "-Wno-deprecations" ] + , package haskeline ? append [ "-Wno-deprecations", "-Wno-unused-imports", + "-Wno-redundant-constraints", + "-Wno-simplifiable-class-constraints" ] + , package pretty ? append [ "-Wno-unused-imports" ] + , package primitive ? append [ "-Wno-unused-imports", "-Wno-deprecations" ] + , package terminfo ? append [ "-Wno-unused-imports" ] + , package xhtml ? append [ "-Wno-unused-imports", "-Wno-tabs" ] + , package transformers ? append [ "-Wno-unused-matches", "-Wno-unused-imports", + "-Wno-redundant-constraints", "-Wno-orphans" ] + , package base ? append [ "-Wno-trustworthy-safe" ] + , package ghcPrim ? append [ "-Wno-trustworthy-safe" ] + , package win32 ? append [ "-Wno-trustworthy-safe" ] ] + +-- GhcLibExtraHcOpts += -Wno-deprecated-flags +-- GhcBootLibExtraHcOpts += -fno-warn-deprecated-flags +disableWarningArgsLibs :: Args +disableWarningArgsLibs = do + pkg <- getPackage + isLibrary pkg ? builder Ghc ? mconcat + [ notStage0 ? arg "-Wno-deprecated-flags" + , stage Stage0 ? arg "-fno-warn-deprecated-flags"] + +-- TODO: Disable warnings for Windows specifics + -- | All 'Package'-dependent command line arguments. defaultPackageArgs :: Args defaultPackageArgs = mconcat @@ -227,4 +264,7 @@ defaultPackageArgs = mconcat , haddockPackageArgs , integerGmpPackageArgs , rtsPackageArgs - , runGhcPackageArgs ] + , runGhcPackageArgs + , disableWarningArgsStage0 + , disableWarningArgsStage1 + , disableWarningArgsLibs ] From git at git.haskell.org Fri Oct 27 00:32:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try bash within stack to run configure. (01b7eed) Message-ID: <20171027003248.CA6AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/01b7eed7be12304e71952ce3345b8244f1c6bd8e/ghc >--------------------------------------------------------------- commit 01b7eed7be12304e71952ce3345b8244f1c6bd8e Author: Andrey Mokhov Date: Fri Jan 8 03:49:14 2016 +0000 Try bash within stack to run configure. See #110. [skip ci] >--------------------------------------------------------------- 01b7eed7be12304e71952ce3345b8244f1c6bd8e .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 82cdce4..c9ec4fd 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,7 +14,7 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - stack exec -- ./configure --enable-tarballs-autodownload + - stack exec -- bash -lc "./configure --enable-tarballs-autodownload" - ghc --version - stack --version - alex --version From git at git.haskell.org Fri Oct 27 00:32:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Werror to CC and HC (#309) (4952e80) Message-ID: <20171027003249.9D51A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4952e8022f805d31035c3ecfd354518c72d07557/ghc >--------------------------------------------------------------- commit 4952e8022f805d31035c3ecfd354518c72d07557 Author: Zhen Zhang Date: Wed May 3 08:58:34 2017 -0700 Add Werror to CC and HC (#309) >--------------------------------------------------------------- 4952e8022f805d31035c3ecfd354518c72d07557 src/Settings/Builders/Cc.hs | 5 ++++- src/Settings/Default.hs | 16 +++++++++++++++- src/Settings/Packages/GhcPrim.hs | 1 + src/Settings/Packages/Rts.hs | 4 +++- 4 files changed, 23 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index b5d85df..38a1665 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -8,7 +8,10 @@ ccBuilderArgs = builder Cc ? mconcat , argSettingList . ConfCcArgs =<< getStage , cIncludeArgs - , builder (Cc CompileC) ? mconcat [ arg "-c", arg =<< getInput + , builder (Cc CompileC) ? mconcat [ arg "-Werror" + -- mk/warning.mk: + -- SRC_CC_OPTS += -Wall $(WERROR) + , arg "-c", arg =<< getInput , arg "-o", arg =<< getOutput ] , builder (Cc FindCDependencies) ? do diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 90e2db0..619fca1 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -65,10 +65,24 @@ defaultArgs = mconcat , sourceArgs defaultSourceArgs , defaultPackageArgs ] +-- | Default flags about Werror +-- | mk/warnings.mk +defaultErrorGhcFlags :: Args +defaultErrorGhcFlags = + mconcat [ notStage0 ? arg "-Werror" + , (not <$> flag GccIsClang) ? mconcat [ + (not <$> flag GccLt46) ? (not <$> windowsHost) ? + arg "-Werror=unused-but-set-variable" + , (not <$> flag GccLt44) ? arg "-Wno-error=inline" ] + , flag GccIsClang ? arg "-Wno-unknown-pragmas" ] + -- | Default source arguments, e.g. optimisation settings. defaultSourceArgs :: SourceArgs defaultSourceArgs = SourceArgs - { hsDefault = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2", arg "-H32m"] + { hsDefault = mconcat [ stage0 ? arg "-O" + , notStage0 ? arg "-O2" + , arg "-H32m" + , defaultErrorGhcFlags ] , hsLibrary = mempty , hsCompiler = mempty , hsGhc = mempty } diff --git a/src/Settings/Packages/GhcPrim.hs b/src/Settings/Packages/GhcPrim.hs index bed8345..af3c0d5 100644 --- a/src/Settings/Packages/GhcPrim.hs +++ b/src/Settings/Packages/GhcPrim.hs @@ -10,4 +10,5 @@ ghcPrimPackageArgs = package ghcPrim ? mconcat , builder (Cc CompileC) ? (not <$> flag GccLt44) ? + (not <$> flag GccIsClang) ? input "//cbits/atomic.c" ? arg "-Wno-sync-nand" ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 6855402..e278204 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -89,7 +89,9 @@ rtsPackageArgs = package rts ? do , inputs ["//Evac.c", "//Evac_thr.c"] ? arg "-funroll-loops" , inputs ["//Evac_thr.c", "//Scav_thr.c"] ? - append [ "-DPARALLEL_GC", "-Irts/sm" ] ] + append [ "-DPARALLEL_GC", "-Irts/sm" ] + + , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr" ] , builder Ghc ? arg "-Irts" From git at git.haskell.org Fri Oct 27 00:32:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass GMP objects to Ld explicitly (aaead2a) Message-ID: <20171027003249.AC2AE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aaead2a5caa9fa96cc8a9f8a2762582bec70126f/ghc >--------------------------------------------------------------- commit aaead2a5caa9fa96cc8a9f8a2762582bec70126f Author: Andrey Mokhov Date: Fri May 20 00:23:50 2016 +0100 Pass GMP objects to Ld explicitly See #241. >--------------------------------------------------------------- aaead2a5caa9fa96cc8a9f8a2762582bec70126f src/Rules/Library.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index a198c64..2e59755 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -67,13 +67,12 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do cSrcs <- cSources context hSrcs <- hSources context + eObjs <- extraObjects context let cObjs = map (objFile context) cSrcs hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] - gObjs = [ gmpObjects -/- "*.o" | package == integerGmp ] - objs = cObjs ++ hObjs - when (package == integerGmp) $ orderOnly [gmpLibraryH] + objs = cObjs ++ hObjs ++ eObjs need objs - build $ Target context Ld (objs ++ gObjs) [obj] + build $ Target context Ld objs [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' From git at git.haskell.org Fri Oct 27 00:32:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring bash configure back. (29ce56c) Message-ID: <20171027003252.D52C53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/29ce56c97cc414b2a3e66e4b44dff829a8660a47/ghc >--------------------------------------------------------------- commit 29ce56c97cc414b2a3e66e4b44dff829a8660a47 Author: Andrey Mokhov Date: Fri Jan 8 04:13:50 2016 +0000 Bring bash configure back. See #110. [skip ci] >--------------------------------------------------------------- 29ce56c97cc414b2a3e66e4b44dff829a8660a47 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index c9ec4fd..bb01556 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,7 +14,7 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - stack exec -- bash -lc "./configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc32262d3aa0e6586daee0c0d6edef98310ebe98/ghc >--------------------------------------------------------------- commit bc32262d3aa0e6586daee0c0d6edef98310ebe98 Author: Zhen Zhang Date: Tue May 16 13:13:17 2017 -0700 Add copyFileUntracked (#313) >--------------------------------------------------------------- bc32262d3aa0e6586daee0c0d6edef98310ebe98 src/Rules/Libffi.hs | 4 ++-- src/Util.hs | 12 ++++++++++-- 2 files changed, 12 insertions(+), 4 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 99b77c8..57f6263 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -39,7 +39,7 @@ configureEnvironment = do libffiRules :: Rules () libffiRules = do - libffiDependencies &%> \_ -> do + (libffiLibrary : libffiDependencies) &%> \_ -> do useSystemFfi <- flag UseSystemFfi if useSystemFfi then do @@ -57,7 +57,7 @@ libffiRules = do ways <- interpretInContext libffiContext (getLibraryWays <> getRtsWays) forM_ (nubOrd ways) $ \way -> - copyFile libffiLibrary =<< rtsLibffiLibrary way + copyFileUntracked libffiLibrary =<< rtsLibffiLibrary way putSuccess $ "| Successfully built custom library 'libffi'" diff --git a/src/Util.hs b/src/Util.hs index b6d9536..1fd19f8 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -3,7 +3,7 @@ module Util ( removeFile, copyDirectory, copyDirectoryContents, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, makeExecutable, renderProgram, renderLibrary, Match(..), builderEnvironment, - needBuilder + needBuilder, copyFileUntracked ) where import qualified System.Directory.Extra as IO @@ -94,10 +94,18 @@ copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. let dir = takeDirectory target - unlessM (liftIO $ IO.doesDirectoryExist dir) $ createDirectory dir + liftIO $ IO.createDirectoryIfMissing True dir putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target +-- Same as copyFile, but not tracking the source as a build dependency +copyFileUntracked :: FilePath -> FilePath -> Action () +copyFileUntracked source target = do + let dir = takeDirectory target + liftIO $ IO.createDirectoryIfMissing True dir + putProgressInfo $ renderAction "Copy file (Untracked)" source target + liftIO $ IO.copyFile source target + -- | Move a file; we cannot track the source, because it is moved. moveFile :: FilePath -> FilePath -> Action () moveFile source target = do From git at git.haskell.org Fri Oct 27 00:32:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on --progress-colour (ffcc3d9) Message-ID: <20171027003254.2E6533A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffcc3d939e3854b8f7041814cb6d64761cf59822/ghc >--------------------------------------------------------------- commit ffcc3d939e3854b8f7041814cb6d64761cf59822 Author: Andrey Mokhov Date: Sat May 21 00:41:58 2016 +0100 Add a note on --progress-colour [skip ci] >--------------------------------------------------------------- ffcc3d939e3854b8f7041814cb6d64761cf59822 README.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/README.md b/README.md index fdbdbc5..9e7c6ca 100644 --- a/README.md +++ b/README.md @@ -58,6 +58,11 @@ profiling, which speeds up builds by 3-4x). * `--haddock`: build Haddock documentation. +* `--progress-colour=MODE`: choose whether to use colours when printing build progress +info. There are three settings: `never` (do not use colours), `auto` (attempt to detect +whether the console supports colours; this is the default setting), and `always` (use +colours). + * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). From git at git.haskell.org Fri Oct 27 00:32:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use mingw64_shell.bat for running scripts. (75063f0) Message-ID: <20171027003256.5C5253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/75063f04ab2d93494366e80cbc17d02094ac1703/ghc >--------------------------------------------------------------- commit 75063f04ab2d93494366e80cbc17d02094ac1703 Author: Andrey Mokhov Date: Fri Jan 8 16:47:17 2016 +0000 Use mingw64_shell.bat for running scripts. See #110. [skip ci] >--------------------------------------------------------------- 75063f04ab2d93494366e80cbc17d02094ac1703 .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index bb01556..1d4bb53 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -3,7 +3,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" install: - cd - set MSYSTEM=MINGW64 - - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% + - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\bin;C:\msys64;%PATH% - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe @@ -14,7 +14,8 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/10544904eab3383c145c6904ad6d4bb19cc55329/ghc >--------------------------------------------------------------- commit 10544904eab3383c145c6904ad6d4bb19cc55329 Author: Andrey Mokhov Date: Sat May 21 00:48:01 2016 +0100 Add a note on --verbose [skip ci] >--------------------------------------------------------------- 10544904eab3383c145c6904ad6d4bb19cc55329 README.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/README.md b/README.md index 9e7c6ca..e4fb7dc 100644 --- a/README.md +++ b/README.md @@ -82,6 +82,9 @@ is your friend in such cases. * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. +* `--verbose`: run Hadrian in verbose mode. In particular this prints diagnostic messages +by Shake oracles. + #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We From git at git.haskell.org Fri Oct 27 00:32:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CABAL_VERSION argument in building ghc-cabal (#319) (1fd9854) Message-ID: <20171027003258.04BDF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fd9854b798e2a003649baa6cfcc76c9150c0421/ghc >--------------------------------------------------------------- commit 1fd9854b798e2a003649baa6cfcc76c9150c0421 Author: Zhen Zhang Date: Mon Jun 5 18:54:54 2017 +0800 Fix CABAL_VERSION argument in building ghc-cabal (#319) >--------------------------------------------------------------- 1fd9854b798e2a003649baa6cfcc76c9150c0421 src/Settings/Packages/GhcCabal.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 8e5837c..3c830ae 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -1,9 +1,17 @@ module Settings.Packages.GhcCabal (ghcCabalPackageArgs) where +import Distribution.PackageDescription.Parse + import Base import GHC import Oracles.Config.Setting import Predicate +import Package (pkgCabalFile) +import Distribution.Verbosity (silent) +import Distribution.Text (display) +import Distribution.Package (pkgVersion) +import Distribution.PackageDescription (packageDescription) +import qualified Distribution.PackageDescription as DP ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do @@ -12,10 +20,17 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do win <- lift windowsHost let cabalDeps = [ array, base, bytestring, containers, deepseq, directory , pretty, process, time, if win then win32 else unix ] + + lift $ need [pkgCabalFile cabal] + pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile cabal + let identifier = DP.package . packageDescription $ pd + cabalVersion = display . pkgVersion $ identifier + mconcat [ append [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , arg "--make" , arg "-j" + , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" , arg "-DGENERICS" From git at git.haskell.org Fri Oct 27 00:33:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build check-api-annotations (5d2c1ee) Message-ID: <20171027003301.88F553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d2c1eed519b6d90bcab8f993c428b265d4cb8fd/ghc >--------------------------------------------------------------- commit 5d2c1eed519b6d90bcab8f993c428b265d4cb8fd Author: Andrey Mokhov Date: Sat May 21 00:59:42 2016 +0100 Build check-api-annotations Fix #242. >--------------------------------------------------------------- 5d2c1eed519b6d90bcab8f993c428b265d4cb8fd src/GHC.hs | 137 ++++++++++++++++++++++++----------------------- src/Settings/Packages.hs | 2 +- 2 files changed, 70 insertions(+), 69 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 5d2c1eed519b6d90bcab8f993c428b265d4cb8fd From git at git.haskell.org Fri Oct 27 00:32:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to use get-win32-tarballs.sh. (4a625f8) Message-ID: <20171027003259.D08E13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a625f8aa2358597281a6b2633fdb40f9f8c2707/ghc >--------------------------------------------------------------- commit 4a625f8aa2358597281a6b2633fdb40f9f8c2707 Author: Andrey Mokhov Date: Fri Jan 8 17:03:55 2016 +0000 Try to use get-win32-tarballs.sh. See #110. [skip ci] >--------------------------------------------------------------- 4a625f8aa2358597281a6b2633fdb40f9f8c2707 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 1d4bb53..f0014e3 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,8 +14,8 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - mingw64_shell.bat "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3382b95c0fc6385df7c33a6e84fa62b207b75ab/ghc >--------------------------------------------------------------- commit b3382b95c0fc6385df7c33a6e84fa62b207b75ab Author: Andrey Mokhov Date: Fri Jan 8 17:12:33 2016 +0000 Create ghc-tarballs/mingw-w64/x86_64/ directory. See #110. [skip ci] >--------------------------------------------------------------- b3382b95c0fc6385df7c33a6e84fa62b207b75ab .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f0014e3..1d3b7c5 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -14,8 +14,8 @@ install: - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot - - bash -lc "cd /home/ghc; ./mk/get-win32-tarballs.sh download x86_64" - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c74f92cc3db93f71f294e4f0797a1866950467c/ghc >--------------------------------------------------------------- commit 2c74f92cc3db93f71f294e4f0797a1866950467c Author: Andrey Mokhov Date: Sat May 21 02:23:31 2016 +0100 Fix missing dependencies for Stage2 packages Fix #240. >--------------------------------------------------------------- 2c74f92cc3db93f71f294e4f0797a1866950467c src/Rules/Cabal.hs | 2 +- src/Rules/Data.hs | 6 ++++-- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 05078fc..82edb3a 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -28,7 +28,7 @@ cabalRules = do -- Cache package dependencies packageDependencies %> \out -> do - pkgs <- interpretInContext (stageContext Stage1) getPackages + let pkgs = knownPackages \\ [hp2ps, libffi, touchy, unlit] pkgDeps <- forM (sort pkgs) $ \pkg -> if pkg == rts then return $ pkgNameString pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 8512c3a..2ecfb37 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -31,10 +31,12 @@ buildPackageData context at Context {..} = do whenM (doesFileExist $ configure <.> "ac") $ need [configure] -- Before we configure a package its dependencies need to be registered + let depStage = min stage Stage1 -- dependencies come from Stage0/1 + depContext = vanillaContext depStage deps <- packageDeps package - pkgs <- interpretInContext context getPackages + pkgs <- interpretInContext (depContext package) getPackages let depPkgs = matchPackageNames (sort pkgs) deps - need =<< traverse (pkgConfFile . vanillaContext stage) depPkgs + need =<< traverse (pkgConfFile . depContext) depPkgs need [cabalFile] build $ Target context GhcCabal [cabalFile] [mk] From git at git.haskell.org Fri Oct 27 00:33:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix unnecessary import hiding (988dabb) Message-ID: <20171027003306.B7C133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/988dabb35a239fa8dd799de5951acf55786bc0ee/ghc >--------------------------------------------------------------- commit 988dabb35a239fa8dd799de5951acf55786bc0ee Author: David Luposchainsky Date: Fri Jan 8 18:23:46 2016 +0100 Fix unnecessary import hiding >--------------------------------------------------------------- 988dabb35a239fa8dd799de5951acf55786bc0ee src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 05686e0..925c427 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -34,7 +34,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>), parallel) +import Development.Shake hiding (unit, (*>)) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Fri Oct 27 00:33:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compute cabalDeps in GhcCabal build (#320) (0589a9e) Message-ID: <20171027003305.82B903A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c/ghc >--------------------------------------------------------------- commit 0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c Author: Zhen Zhang Date: Tue Jun 6 23:46:11 2017 +0800 Compute cabalDeps in GhcCabal build (#320) >--------------------------------------------------------------- 0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c src/Oracles/Dependencies.hs | 9 ++++++++- src/Settings/Packages/GhcCabal.hs | 7 ++----- 2 files changed, 10 insertions(+), 6 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 2d6a404..167047d 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,6 +1,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Dependencies ( - fileDependencies, contextDependencies, needContext, dependenciesOracles + fileDependencies, contextDependencies, needContext, dependenciesOracles, + pkgDependencies ) where import qualified Data.HashMap.Strict as Map @@ -47,6 +48,12 @@ contextDependencies context at Context {..} = do pkgs <- sort <$> interpretInContext (pkgContext package) getPackages return . map pkgContext $ intersectOrd (compare . pkgNameString) pkgs deps +-- | Given a `Package`, this `Action` looks up its package dependencies +-- 'Settings.Paths.packageDependencies' using 'packageDependenciesOracle' +-- The context will be the vanilla context with stage equal to 1 +pkgDependencies :: Package -> Action [Package] +pkgDependencies = fmap (map Context.package) . contextDependencies . vanillaContext Stage1 + -- | Coarse-grain 'need': make sure given contexts are fully built. needContext :: [Context] -> Action () needContext cs = do diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 3c830ae..57147e4 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -5,6 +5,7 @@ import Distribution.PackageDescription.Parse import Base import GHC import Oracles.Config.Setting +import Oracles.Dependencies (pkgDependencies) import Predicate import Package (pkgCabalFile) import Distribution.Verbosity (silent) @@ -15,12 +16,8 @@ import qualified Distribution.PackageDescription as DP ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do - -- Note: We could compute 'cabalDeps' instead of hard-coding it but this - -- seems unnecessary since we plan to drop @ghc-cabal@ altogether, #18. win <- lift windowsHost - let cabalDeps = [ array, base, bytestring, containers, deepseq, directory - , pretty, process, time, if win then win32 else unix ] - + cabalDeps <- lift $ pkgDependencies cabal lift $ need [pkgCabalFile cabal] pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile cabal let identifier = DP.package . packageDescription $ pd From git at git.haskell.org Fri Oct 27 00:33:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more utilities including install and symbolic link (#316) (8299d14) Message-ID: <20171027003301.A866F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8299d146c112c16c528b3681a6e4404eb47c6375/ghc >--------------------------------------------------------------- commit 8299d146c112c16c528b3681a6e4404eb47c6375 Author: Zhen Zhang Date: Tue Jun 6 08:53:14 2017 +0800 Add more utilities including install and symbolic link (#316) >--------------------------------------------------------------- 8299d146c112c16c528b3681a6e4404eb47c6375 cfg/system.config.in | 15 +++++++++++++ src/Oracles/Config/Setting.hs | 50 ++++++++++++++++++++++++++++++++++++++++++- src/Util.hs | 44 ++++++++++++++++++++++++++++++++++++- 3 files changed, 107 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 667a22d..56a7c7f 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -22,6 +22,7 @@ system-ghc-pkg = @GhcPkgCmd@ tar = @TarCmd@ patch = @PatchCmd@ perl = @PerlCmd@ +ln-s = @LN_S@ # Information about builders: #============================ @@ -117,3 +118,17 @@ ffi-lib-dir = @FFILibDir@ #======================= with-libdw = @UseLibdw@ + +# Installation: +#======================= + +install-prefix = @prefix@ +install-bindir = @prefix@/bin +install-libdir = @prefix@/lib +install-datarootdir = @prefix@/share + +install = @INSTALL@ +install-program = @INSTALL@ -m 755 +install-script = @INSTALL@ -m 755 +install-data = @INSTALL@ -m 644 +install-dir = @INSTALL@ -m 755 -d diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 0b28112..8bdc387 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -2,7 +2,8 @@ module Oracles.Config.Setting ( Setting (..), SettingList (..), setting, settingList, getSetting, getSettingList, anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, - ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost + ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost, + relocatableBuild, installDocDir, installGhcLibDir ) where import Control.Monad.Trans.Reader @@ -51,6 +52,19 @@ data Setting = BuildArch | GmpLibDir | IconvIncludeDir | IconvLibDir + -- Paths to where GHC is installed + | InstallPrefix + | InstallBinDir + | InstallLibDir + | InstallDataRootDir + -- "install" utility + | Install + | InstallData + | InstallProgram + | InstallScript + | InstallDir + -- symbolic link + | LnS data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -94,6 +108,16 @@ setting key = unsafeAskConfig $ case key of GmpLibDir -> "gmp-lib-dir" IconvIncludeDir -> "iconv-include-dir" IconvLibDir -> "iconv-lib-dir" + InstallPrefix -> "install-prefix" + InstallBinDir -> "install-bindir" + InstallLibDir -> "install-libdir" + InstallDataRootDir -> "install-datarootdir" + Install -> "install" + InstallDir -> "install-dir" + InstallProgram -> "install-program" + InstallScript -> "install-script" + InstallData -> "install-data" + LnS -> "ln-s" settingList :: SettingList -> Action [String] settingList key = fmap words $ unsafeAskConfig $ case key of @@ -173,3 +197,27 @@ cmdLineLengthLimit = do (False, True) -> 200000 -- On all other systems, we try this: _ -> 4194304 -- Cabal library needs a bit more than 2MB! + +-- | On Windows we normally want to make a relocatable bindist, +-- to we ignore flags like libdir +-- ref: mk/config.mk.in:232 +relocatableBuild :: Action Bool +relocatableBuild = windowsHost + +installDocDir :: Action String +installDocDir = do + version <- setting ProjectVersion + (-/- ("doc/ghc-" ++ version)) <$> setting InstallDataRootDir + +-- | Unix: override libdir and datadir to put ghc-specific stuff in +-- a subdirectory with the version number included. +-- ref: mk/install.mk:101 +-- TODO: CroosCompilePrefix +installGhcLibDir :: Action String +installGhcLibDir = do + r <- relocatableBuild + libdir <- setting InstallLibDir + if r then return libdir + else do + v <- setting ProjectVersion + return (libdir -/- ("ghc-" ++ v)) diff --git a/src/Util.hs b/src/Util.hs index 1fd19f8..a7310be 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -3,7 +3,8 @@ module Util ( removeFile, copyDirectory, copyDirectoryContents, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, makeExecutable, renderProgram, renderLibrary, Match(..), builderEnvironment, - needBuilder, copyFileUntracked + needBuilder, copyFileUntracked, installDir, installData, installScript, + installProgram, linkSymbolic ) where import qualified System.Directory.Extra as IO @@ -18,6 +19,7 @@ import GHC import Oracles.ArgsHash import Oracles.DirectoryContents import Oracles.Path +import Oracles.Config.Setting import Settings import Settings.Builders.Ar import Target @@ -169,6 +171,46 @@ applyPatch dir patch = do putBuild $ "| Apply patch " ++ file quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] +-- | Install a directory +installDir :: FilePath -> Action () +installDir dir = do + i <- setting InstallDir + putBuild $ "| Install directory" ++ dir + quietly $ cmd i dir + +-- | Install data file to a directory +installData :: [FilePath] -> FilePath -> Action () +installData fs dir = do + i <- setting InstallData + forM_ fs $ \f -> + putBuild $ "| Install data " ++ f ++ " to " ++ dir + quietly $ cmd i fs dir + +-- | Install executable file to a directory +installProgram :: FilePath -> FilePath -> Action () +installProgram f dir = do + i <- setting InstallProgram + putBuild $ "| Install program " ++ f ++ " to " ++ dir + quietly $ cmd i f dir + +-- | Install executable script to a directory +installScript :: FilePath -> FilePath -> Action () +installScript f dir = do + i <- setting InstallScript + putBuild $ "| Install script " ++ f ++ " to " ++ dir + quietly $ cmd i f dir + +-- | Create a symbolic link from source file to target file when supported +linkSymbolic :: FilePath -> FilePath -> Action () +linkSymbolic source target = do + lns <- setting LnS + when (lns /= "") $ do + need [source] -- Guarantee source is built before printing progress info. + let dir = takeDirectory target + liftIO $ IO.createDirectoryIfMissing True dir + putProgressInfo $ renderAction "Create symbolic link" source target + quietly $ cmd lns source target + isInternal :: Builder -> Bool isInternal = isJust . builderProvenance From git at git.haskell.org Fri Oct 27 00:33:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor dependency oracles (b6f224c) Message-ID: <20171027003308.E9F343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6f224c4535039fb77fd31e8229917ee4267f16f/ghc >--------------------------------------------------------------- commit b6f224c4535039fb77fd31e8229917ee4267f16f Author: Andrey Mokhov Date: Sun May 22 00:02:50 2016 +0100 Refactor dependency oracles >--------------------------------------------------------------- b6f224c4535039fb77fd31e8229917ee4267f16f hadrian.cabal | 1 - src/Oracles/Config.hs | 2 +- src/Oracles/Config/Flag.hs | 5 +- src/Oracles/Config/Setting.hs | 31 +++++----- src/Oracles/Dependencies.hs | 102 +++++++++++++++++++++++-------- src/Oracles/LookupInPath.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/PackageDeps.hs | 30 --------- src/Oracles/WindowsPath.hs | 7 +-- src/Package.hs | 35 ++++------- src/Rules/Cabal.hs | 9 ++- src/Rules/Compile.hs | 15 +++-- src/Rules/Data.hs | 29 ++++----- src/Rules/Generators/GhcBootPlatformH.hs | 1 - src/Rules/Generators/GhcPlatformH.hs | 1 - src/Rules/Generators/VersionHs.hs | 1 - src/Rules/Oracles.hs | 4 +- src/Rules/Program.hs | 56 +++++++---------- src/Rules/Register.hs | 2 +- src/Settings/Builders/Ghc.hs | 16 ++--- src/Settings/Builders/GhcCabal.hs | 14 ++--- src/Settings/Paths.hs | 6 +- 22 files changed, 175 insertions(+), 196 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b6f224c4535039fb77fd31e8229917ee4267f16f From git at git.haskell.org Fri Oct 27 00:33:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix implicit assumption about inplace installation etc. (#315) (02351ac) Message-ID: <20171027003309.1AE213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02351ac97f66df4b8c02b0df587e4dde7c4201c8/ghc >--------------------------------------------------------------- commit 02351ac97f66df4b8c02b0df587e4dde7c4201c8 Author: Zhen Zhang Date: Wed Jun 7 09:04:28 2017 +0800 Fix implicit assumption about inplace installation etc. (#315) >--------------------------------------------------------------- 02351ac97f66df4b8c02b0df587e4dde7c4201c8 hadrian.cabal | 5 ++-- src/GHC.hs | 8 +---- src/Rules.hs | 2 +- src/Rules/Cabal.hs | 1 - src/Rules/Clean.hs | 4 +-- src/Rules/Generate.hs | 37 +++++++++++++---------- src/Rules/Generators/GhcSplit.hs | 8 +++-- src/Rules/Program.hs | 34 +++++++++++----------- src/Rules/Register.hs | 2 +- src/Rules/Wrappers.hs | 63 ++++++++++++++++++++++++++++++++++++++++ src/Rules/Wrappers/Ghc.hs | 14 --------- src/Rules/Wrappers/GhcPkg.hs | 19 ------------ src/Rules/Wrappers/RunGhc.hs | 15 ---------- src/Settings/Builders/Common.hs | 2 +- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Install.hs | 14 +++++++++ src/Settings/Path.hs | 39 +++++++++++++++---------- 17 files changed, 154 insertions(+), 116 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 02351ac97f66df4b8c02b0df587e4dde7c4201c8 From git at git.haskell.org Fri Oct 27 00:33:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #136 from quchen/redundant-hiding (4116dbd) Message-ID: <20171027003310.2B6AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4116dbdd0c3407fac56a101e2592240411108c86/ghc >--------------------------------------------------------------- commit 4116dbdd0c3407fac56a101e2592240411108c86 Merge: b3382b9 988dabb Author: Andrey Mokhov Date: Fri Jan 8 17:29:30 2016 +0000 Merge pull request #136 from quchen/redundant-hiding Fix unnecessary import hiding of "parallel" [skip ci] >--------------------------------------------------------------- 4116dbdd0c3407fac56a101e2592240411108c86 src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:33:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop orderOnly dependency on GMP objects (19293d9) Message-ID: <20171027003312.8D79C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/19293d92469d2c80e125f62d527407ea0ac5fe4e/ghc >--------------------------------------------------------------- commit 19293d92469d2c80e125f62d527407ea0ac5fe4e Author: Andrey Mokhov Date: Sun May 22 01:19:16 2016 +0100 Drop orderOnly dependency on GMP objects >--------------------------------------------------------------- 19293d92469d2c80e125f62d527407ea0ac5fe4e src/Rules/Gmp.hs | 2 +- src/Rules/Library.hs | 12 ++++++------ 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 845ba6e..f761639 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,4 +1,4 @@ -module Rules.Gmp (gmpRules) where +module Rules.Gmp (gmpRules, gmpContext) where import Base import Builder diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 2e59755..edbdb52 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -8,9 +8,9 @@ import qualified System.Directory as IO import Base import Context import Expression -import GHC import Oracles.PackageData import Rules.Actions +import Rules.Gmp import Settings import Target @@ -75,7 +75,7 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do build $ Target context Ld objs [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. --- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' +-- | Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' -- to its object file. For example, in Context Stage1 rts threaded: -- * "Task.c" -> "_build/stage1/rts/Task.thr_o" -- * "_build/stage1/rts/sm/Evac_thr.c" -> "_build/stage1/rts/sm/Evac_thr.thr_o" @@ -90,12 +90,12 @@ cSources context = interpretInContext context $ getPkgDataList CSrcs hSources :: Context -> Action [FilePath] hSources context = do modules <- interpretInContext context $ getPkgDataList Modules - -- GHC.Prim is special: we do not build it + -- GHC.Prim is special: we do not build it. return . map (replaceEq '.' '/') . filter (/= "GHC.Prim") $ modules extraObjects :: Context -> Action [FilePath] -extraObjects (Context _ package _) - | package == integerGmp = do - orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? +extraObjects context + | context == gmpContext = do + need [gmpLibraryH] -- TODO: Move this dependency elsewhere, #113? map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:33:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add binary wrappers for hp2ps, hpc, hsc2hs (#321) (49835af) Message-ID: <20171027003312.E0D3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49835aff3bd03dd24d00e9c89aaed0339e4aa3a5/ghc >--------------------------------------------------------------- commit 49835aff3bd03dd24d00e9c89aaed0339e4aa3a5 Author: Zhen Zhang Date: Wed Jun 7 18:15:03 2017 +0800 Add binary wrappers for hp2ps, hpc, hsc2hs (#321) >--------------------------------------------------------------- 49835aff3bd03dd24d00e9c89aaed0339e4aa3a5 src/Rules/Program.hs | 12 ++++++++---- src/Rules/Wrappers.hs | 36 ++++++++++++++++++++++++++++++++++-- 2 files changed, 42 insertions(+), 6 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 79f01f2..5b2e66f 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -12,7 +12,8 @@ import Oracles.ModuleFiles import Oracles.PackageData import Oracles.Path (topDirectory) import Rules.Wrappers (WrappedBinary(..), Wrapper, - ghcWrapper, runGhcWrapper, inplaceGhcPkgWrapper) + ghcWrapper, runGhcWrapper, inplaceGhcPkgWrapper, + hpcWrapper, hp2psWrapper, hsc2hsWrapper) import Settings import Settings.Path (buildPath, inplaceLibBinPath, rtsContext, objectPath, inplaceLibPath, inplaceBinPath) @@ -22,10 +23,13 @@ import Util -- | List of wrappers we build. wrappers :: [(Context, Wrapper)] -wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) - , (vanillaContext Stage1 ghc , ghcWrapper ) +wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper) + , (vanillaContext Stage1 ghc , ghcWrapper) , (vanillaContext Stage1 runGhc, runGhcWrapper) - , (vanillaContext Stage0 ghcPkg, inplaceGhcPkgWrapper) ] + , (vanillaContext Stage0 ghcPkg, inplaceGhcPkgWrapper) + , (vanillaContext Stage1 hp2ps , hp2psWrapper) + , (vanillaContext Stage1 hpc , hpcWrapper) + , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) ] buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs index 93dfee0..246d28a 100644 --- a/src/Rules/Wrappers.hs +++ b/src/Rules/Wrappers.hs @@ -1,13 +1,15 @@ module Rules.Wrappers ( WrappedBinary(..), Wrapper, ghcWrapper, runGhcWrapper, - inplaceGhcPkgWrapper, installGhcPkgWrapper + inplaceGhcPkgWrapper, installGhcPkgWrapper, hp2psWrapper, + hpcWrapper, hsc2hsWrapper ) where import Base -import Expression (Expr, getStage) +import Expression import Settings.Install (installPackageDbDirectory) import Settings.Path (inplacePackageDbDirectory) import Oracles.Path (getTopDirectory) +import Oracles.Config.Setting (SettingList(..), settingList) -- | Wrapper is an expression depending on the 'FilePath' to the -- | library path and name of the wrapped binary. @@ -61,3 +63,33 @@ installGhcPkgWrapper WrappedBinary{..} = do [ "#!/bin/bash" , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " --global-package-db " ++ packageDb ++ " ${1+\"$@\"}" ] + +hp2psWrapper :: WrappedBinary -> Expr String +hp2psWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ] + +hpcWrapper :: WrappedBinary -> Expr String +hpcWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ] + +hsc2hsWrapper :: WrappedBinary -> Expr String +hsc2hsWrapper WrappedBinary{..} = do + top <- getTopDirectory + lift $ need [ sourcePath -/- "Rules/Wrappers.hs" ] + contents <- lift $ readFile' $ top -/- "utils/hsc2hs/hsc2hs.wrapper" + let executableName = binaryLibPath -/- "bin" -/- binaryName + confCcArgs <- lift $ settingList (ConfCcArgs Stage1) + confGccLinkerArgs <- lift $ settingList (ConfGccLinkerArgs Stage1) + let hsc2hsExtra = unwords (map ("-cflags=" ++) confCcArgs) ++ " " ++ + unwords (map ("-lflags=" ++) confGccLinkerArgs) + return $ unlines + [ "#!/bin/bash" + , "executablename=\"" ++ executableName ++ "\"" + , "HSC2HS_EXTRA=\"" ++ hsc2hsExtra ++ "\"" + , contents ] From git at git.haskell.org Fri Oct 27 00:33:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create ghc-tarballs/perl folder. (eab9a54) Message-ID: <20171027003313.E25963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eab9a54f888dba48e8975bca1140c5f6dbdef3e2/ghc >--------------------------------------------------------------- commit eab9a54f888dba48e8975bca1140c5f6dbdef3e2 Author: Andrey Mokhov Date: Fri Jan 8 18:32:47 2016 +0000 Create ghc-tarballs/perl folder. See #110. [skip ci] >--------------------------------------------------------------- eab9a54f888dba48e8975bca1140c5f6dbdef3e2 .appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.appveyor.yml b/.appveyor.yml index 1d3b7c5..7c724b8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -15,6 +15,7 @@ install: - cd C:\msys64\home\ghc - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" + - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3de1a5a65b7d97635ccd9a14601113b0802cd8f7/ghc >--------------------------------------------------------------- commit 3de1a5a65b7d97635ccd9a14601113b0802cd8f7 Author: Andrey Mokhov Date: Sun May 22 01:22:19 2016 +0100 Run Make builder with -jN using N = shakeThreads >--------------------------------------------------------------- 3de1a5a65b7d97635ccd9a14601113b0802cd8f7 src/Settings/Builders/Make.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index 6968cd0..3d06775 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -1,10 +1,14 @@ module Settings.Builders.Make (makeBuilderArgs) where +import Base import Predicate import Settings makeBuilderArgs :: Args -makeBuilderArgs = mconcat - [ builder (Make gmpBuildPath ) ? arg "MAKEFLAGS=" - , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=", "install"] - , builder (Make "testsuite/tests") ? arg "fast" ] +makeBuilderArgs = do + threads <- shakeThreads <$> lift getShakeOptions + let j = "-j" ++ show threads + mconcat + [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=" ++ j] + , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=" ++ j, "install"] + , builder (Make "testsuite/tests") ? arg "fast" ] From git at git.haskell.org Fri Oct 27 00:33:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dependency on hoopl (#328) (ffc905cf) Message-ID: <20171027003317.0DE3F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffc905cf864570cbbc2699ef54570614f9fd6af8/ghc >--------------------------------------------------------------- commit ffc905cf864570cbbc2699ef54570614f9fd6af8 Author: Zhen Zhang Date: Sun Jun 25 17:02:16 2017 +0800 Drop dependency on hoopl (#328) >--------------------------------------------------------------- ffc905cf864570cbbc2699ef54570614f9fd6af8 src/GHC.hs | 5 ++--- src/Settings/Builders/GhcCabal.hs | 2 -- src/Settings/Default.hs | 1 - 3 files changed, 2 insertions(+), 6 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 441f068..78bb356 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,7 +4,7 @@ module GHC ( array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, - ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, + ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, @@ -28,7 +28,7 @@ defaultKnownPackages = , compiler, containers, deepseq, deriveConstants, directory, dllSplit , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs - , hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi + , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 , xhtml ] @@ -62,7 +62,6 @@ ghcTags = utility "ghctags" haddock = utility "haddock" haskeline = library "haskeline" hsc2hs = utility "hsc2hs" -hoopl = library "hoopl" hp2ps = utility "hp2ps" hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 1c50729..428c376 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -269,8 +269,6 @@ dll0Args = do , "CodeGen.Platform.X86" , "CodeGen.Platform.X86_64" , "FastBool" - , "Hoopl" - , "Hoopl.Dataflow" , "InteractiveEvalTypes" , "MkGraph" , "PprCmm" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 619fca1..d7059bf 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -115,7 +115,6 @@ stage0Packages = do , ghcPkg , ghcTags , hsc2hs - , hoopl , hp2ps , hpc , mkUserGuidePart From git at git.haskell.org Fri Oct 27 00:33:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix shake script path. (192fd13) Message-ID: <20171027003317.8517D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/192fd13c7e9a8e71940513a78816f701b89ea87a/ghc >--------------------------------------------------------------- commit 192fd13c7e9a8e71940513a78816f701b89ea87a Author: Andrey Mokhov Date: Fri Jan 8 19:21:00 2016 +0000 Fix shake script path. See #110. [skip ci] >--------------------------------------------------------------- 192fd13c7e9a8e71940513a78816f701b89ea87a .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7c724b8..ef571b3 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd - - bash -lc "./shake-build/build.bat -j --no-progress" + - bash -lc "cd /home/ghc; ./shake-build/build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:33:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Install Rules (#312) (3935e97) Message-ID: <20171027003321.26CDE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3935e97df7496458482dc1b47b6e63c5950dbfc6/ghc >--------------------------------------------------------------- commit 3935e97df7496458482dc1b47b6e63c5950dbfc6 Author: Zhen Zhang Date: Mon Jun 26 01:37:20 2017 +0800 Add Install Rules (#312) >--------------------------------------------------------------- 3935e97df7496458482dc1b47b6e63c5950dbfc6 hadrian.cabal | 1 + src/GHC.hs | 3 +- src/Main.hs | 2 + src/Oracles/Config/Setting.hs | 1 + src/Rules.hs | 29 ++-- src/Rules/Generate.hs | 4 +- src/Rules/Install.hs | 310 ++++++++++++++++++++++++++++++++++++++ src/Rules/Program.hs | 16 +- src/Rules/Wrappers.hs | 39 ++++- src/Settings.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 7 +- src/Settings/Packages/Rts.hs | 18 ++- src/Settings/Path.hs | 17 ++- src/UserSettings.hs | 9 +- 14 files changed, 417 insertions(+), 44 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 3935e97df7496458482dc1b47b6e63c5950dbfc6 From git at git.haskell.org Fri Oct 27 00:33:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script from shake-build. (8d1c201) Message-ID: <20171027003321.BFB293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8d1c201b7fcea98907fa54419f91f3fdfc3007fd/ghc >--------------------------------------------------------------- commit 8d1c201b7fcea98907fa54419f91f3fdfc3007fd Author: Andrey Mokhov Date: Fri Jan 8 20:11:52 2016 +0000 Run shake script from shake-build. See #110. [skip ci] >--------------------------------------------------------------- 8d1c201b7fcea98907fa54419f91f3fdfc3007fd .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index ef571b3..0e62796 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd - - bash -lc "cd /home/ghc; ./shake-build/build.bat -j --no-progress" + - bash -lc "cd /home/ghc/shake-build; ./build.bat -j --no-progress" From git at git.haskell.org Fri Oct 27 00:33:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop TransitiveDepNames (97d37ea) Message-ID: <20171027003320.D61C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9/ghc >--------------------------------------------------------------- commit 97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9 Author: Andrey Mokhov Date: Sun May 22 01:46:39 2016 +0100 Drop TransitiveDepNames >--------------------------------------------------------------- 97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9 src/Oracles/PackageData.hs | 10 +++------- 1 file changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index af9e255..92c2e99 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,7 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( - PackageData (..), PackageDataList (..), - pkgData, pkgDataList, packageDataOracle + PackageData (..), PackageDataList (..), pkgData, pkgDataList, packageDataOracle ) where import Development.Shake.Config @@ -31,7 +30,6 @@ data PackageDataList = CcArgs FilePath | LdArgs FilePath | Modules FilePath | SrcDirs FilePath - | TransitiveDepNames FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -77,16 +75,14 @@ pkgDataList packageData = fmap (map unquote . words) $ case packageData of LdArgs path -> askPackageData path "LD_OPTS" Modules path -> askPackageData path "MODULES" SrcDirs path -> askPackageData path "HS_SRC_DIRS" - TransitiveDepNames path -> askPackageData path "TRANSITIVE_DEP_NAMES" where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') -- | Oracle for 'package-data.mk' files. packageDataOracle :: Rules () -packageDataOracle = do +packageDataOracle = void $ do keys <- newCache $ \file -> do need [file] putLoud $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - _ <- addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file - return () + addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file From git at git.haskell.org Fri Oct 27 00:33:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build dynamic libs (#325) (49b13b8) Message-ID: <20171027003325.E0D283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49b13b8c749a49d53e2e1749d2ee46b18261e3ce/ghc >--------------------------------------------------------------- commit 49b13b8c749a49d53e2e1749d2ee46b18261e3ce Author: Zhen Zhang Date: Mon Jun 26 14:47:18 2017 +0800 Build dynamic libs (#325) >--------------------------------------------------------------- 49b13b8c749a49d53e2e1749d2ee46b18261e3ce src/Base.hs | 8 ++++- src/Rules.hs | 4 +++ src/Rules/Library.hs | 62 +++++++++++++++++++++++++++++---------- src/Settings/Builders/Cc.hs | 6 +++- src/Settings/Builders/Ghc.hs | 5 +++- src/Settings/Default.hs | 5 ++-- src/Settings/Flavours/Quick.hs | 5 +++- src/Settings/Flavours/Quickest.hs | 1 + src/Way.hs | 2 +- 9 files changed, 75 insertions(+), 23 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 49b13b8c749a49d53e2e1749d2ee46b18261e3ce From git at git.haskell.org Fri Oct 27 00:33:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename PackageDb to PackageDatabase (026466a) Message-ID: <20171027003326.0EA213A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/026466ad55688891c0e82b5de98f555dc6932223/ghc >--------------------------------------------------------------- commit 026466ad55688891c0e82b5de98f555dc6932223 Author: Andrey Mokhov Date: Sun May 22 01:48:07 2016 +0100 Rename PackageDb to PackageDatabase >--------------------------------------------------------------- 026466ad55688891c0e82b5de98f555dc6932223 hadrian.cabal | 2 +- src/Oracles/{PackageDb.hs => PackageDatabase.hs} | 8 ++++---- src/Rules/Oracles.hs | 8 ++++---- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 20 ++++++++++---------- src/Settings/Builders/GhcPkg.hs | 4 ++-- 6 files changed, 22 insertions(+), 22 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index a65bbf8..95ae3a0 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -32,7 +32,7 @@ executable hadrian , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData - , Oracles.PackageDb + , Oracles.PackageDatabase , Oracles.WindowsPath , Package , Predicate diff --git a/src/Oracles/PackageDb.hs b/src/Oracles/PackageDatabase.hs similarity index 74% rename from src/Oracles/PackageDb.hs rename to src/Oracles/PackageDatabase.hs index 61b134a..f89a2cc 100644 --- a/src/Oracles/PackageDb.hs +++ b/src/Oracles/PackageDatabase.hs @@ -1,4 +1,4 @@ -module Oracles.PackageDb (packageDbOracle) where +module Oracles.PackageDatabase (packageDatabaseOracle) where import qualified System.Directory as IO @@ -12,9 +12,9 @@ import Settings.Paths import Settings.User import Target -packageDbOracle :: Rules () -packageDbOracle = void $ - addOracle $ \(PackageDbKey stage) -> do +packageDatabaseOracle :: Rules () +packageDatabaseOracle = void $ + addOracle $ \(PackageDatabaseKey stage) -> do let dir = packageDbDirectory stage file = dir -/- "package.cache" unlessM (liftIO $ IO.doesFileExist file) $ do diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 93bccfc..7beb67f 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -1,14 +1,14 @@ module Rules.Oracles (oracleRules) where import Base +import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies import qualified Oracles.LookupInPath +import qualified Oracles.ModuleFiles import qualified Oracles.PackageData +import qualified Oracles.PackageDatabase import qualified Oracles.WindowsPath -import qualified Oracles.ArgsHash -import qualified Oracles.ModuleFiles -import qualified Oracles.PackageDb oracleRules :: Rules () oracleRules = do @@ -18,5 +18,5 @@ oracleRules = do Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle - Oracles.PackageDb.packageDbOracle + Oracles.PackageDatabase.packageDatabaseOracle Oracles.WindowsPath.windowsPathOracle diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 02ffe4d..9b1430d 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -118,7 +118,7 @@ packageGhcArgs = do return $ if not0 || unit then "-this-unit-id " else "-this-package-key " mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" - , bootPackageDbArgs + , bootPackageDatabaseArgs , isLibrary pkg ? arg (thisArg ++ compId) , append $ map ("-package-id " ++) pkgDepIds ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index beaa8c7..396e69b 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,7 +1,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( - ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDbArgs, - PackageDbKey (..), cppArgs, buildDll0 + ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, + PackageDatabaseKey (..), cppArgs, buildDll0 ) where import Base @@ -23,7 +23,7 @@ ghcCabalBuilderArgs = builder GhcCabal ? do , dll0Args , withStaged $ Ghc Compile , withStaged GhcPkg - , bootPackageDbArgs + , bootPackageDatabaseArgs , libraryArgs , with HsColour , configureArgs @@ -81,16 +81,16 @@ configureArgs = do , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" $ argStagedBuilderPath (Cc Compile) ] -newtype PackageDbKey = PackageDbKey Stage - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +newtype PackageDatabaseKey = PackageDatabaseKey Stage + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -initialisePackageDb :: Stage -> Action () -initialisePackageDb stage = askOracle $ PackageDbKey stage +initialisePackageDatabase :: Stage -> Action () +initialisePackageDatabase = askOracle . PackageDatabaseKey -bootPackageDbArgs :: Args -bootPackageDbArgs = do +bootPackageDatabaseArgs :: Args +bootPackageDatabaseArgs = do stage <- getStage - lift $ initialisePackageDb stage + lift $ initialisePackageDatabase stage stage0 ? do path <- getTopDirectory prefix <- ifM (builder Ghc) (return "-package-db ") (return "--package-db=") diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index ba176ac..d6efd0b 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -14,12 +14,12 @@ initPredicate = orM $ map (output . packageDbDirectory) [Stage0 ..] initArgs :: Args initArgs = initPredicate ? mconcat [ arg "init", arg =<< getOutput ] --- TODO: move inplace-pkg-config to buildRootPath, see #113. +-- TODO: Move inplace-pkg-config to buildRootPath, see #113. updateArgs :: Args updateArgs = notM initPredicate ? do pkg <- getPackage dir <- getContextDirectory mconcat [ arg "update" , arg "--force" - , bootPackageDbArgs + , bootPackageDatabaseArgs , arg $ pkgPath pkg -/- dir -/- "inplace-pkg-config" ] From git at git.haskell.org Fri Oct 27 00:33:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script outside bash. (a5763fa) Message-ID: <20171027003326.7E0883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5763fa0dca8a35fb15e5ef6c991c24e2bc04c28/ghc >--------------------------------------------------------------- commit a5763fa0dca8a35fb15e5ef6c991c24e2bc04c28 Author: Andrey Mokhov Date: Fri Jan 8 20:52:02 2016 +0000 Run shake script outside bash. See #110. [skip ci] >--------------------------------------------------------------- a5763fa0dca8a35fb15e5ef6c991c24e2bc04c28 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 0e62796..b6b5ecb 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,5 +23,5 @@ install: - happy --version build_script: - - cd - - bash -lc "cd /home/ghc/shake-build; ./build.bat -j --no-progress" + - cd C:\msys64\home\ghc\shake-build + - ./build.bat -j --no-progress From git at git.haskell.org Fri Oct 27 00:33:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't pass gcc warning options to ghc (#329) (ae7358b) Message-ID: <20171027003329.CD6E93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae7358b596831a2f7683c51e04274099b73c2f20/ghc >--------------------------------------------------------------- commit ae7358b596831a2f7683c51e04274099b73c2f20 Author: Ben Gamari Date: Wed Jun 28 03:48:47 2017 -0400 Don't pass gcc warning options to ghc (#329) We would previously pass -Werror=unused-but-set-variable and -Wno-error=inline to ghc, despite the fact that they are gcc flags. >--------------------------------------------------------------- ae7358b596831a2f7683c51e04274099b73c2f20 src/Settings/Default.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 49ffcb6..3ad1fab 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -72,9 +72,9 @@ defaultErrorGhcFlags = mconcat [ notStage0 ? arg "-Werror" , (not <$> flag GccIsClang) ? mconcat [ (not <$> flag GccLt46) ? (not <$> windowsHost) ? - arg "-Werror=unused-but-set-variable" - , (not <$> flag GccLt44) ? arg "-Wno-error=inline" ] - , flag GccIsClang ? arg "-Wno-unknown-pragmas" ] + arg "-optc-Werror=unused-but-set-variable" + , (not <$> flag GccLt44) ? arg "-optc-Wno-error=inline" ] + , flag GccIsClang ? arg "-optc-Wno-unknown-pragmas" ] -- | Default source arguments, e.g. optimisation settings. defaultSourceArgs :: SourceArgs From git at git.haskell.org Fri Oct 27 00:33:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use simpler mapM instead of traverse (73ad993) Message-ID: <20171027003330.32DBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73ad99359cbac01618824c65fa116a46d27a4575/ghc >--------------------------------------------------------------- commit 73ad99359cbac01618824c65fa116a46d27a4575 Author: Andrey Mokhov Date: Sun May 22 01:57:26 2016 +0100 Use simpler mapM instead of traverse >--------------------------------------------------------------- 73ad99359cbac01618824c65fa116a46d27a4575 src/Rules.hs | 2 +- src/Rules/Dependencies.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index e3caf6c..bea672d 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -45,7 +45,7 @@ topLevelTargets = do if isLibrary pkg then do -- build a library ways <- interpretInContext context getLibraryWays - libs <- traverse (pkgLibraryFile . Context stage pkg) ways + libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context buildHaddock need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else do -- otherwise build a program diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 78f4d40..c5f60bb 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -36,7 +36,7 @@ buildPackageDependencies rs context at Context {..} = cSrcs <- pkgDataList $ CSrcs path let cDepFiles = map (src2dep context) cSrcs need $ hDepFile : cDepFiles -- need all for more parallelism - cDeps <- fmap concat $ traverse readFile' cDepFiles + cDeps <- concatMapM readFile' cDepFiles hDeps <- readFile' hDepFile let result = unlines . map (\(src, deps) -> unwords $ src : deps) From git at git.haskell.org Fri Oct 27 00:33:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script via stack. (f4ece5b) Message-ID: <20171027003330.466453A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f4ece5be780b194845548d9e1ab46a916b22b4f5/ghc >--------------------------------------------------------------- commit f4ece5be780b194845548d9e1ab46a916b22b4f5 Author: Andrey Mokhov Date: Fri Jan 8 21:34:15 2016 +0000 Run shake script via stack. See #110. [skip ci] >--------------------------------------------------------------- f4ece5be780b194845548d9e1ab46a916b22b4f5 .appveyor.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index b6b5ecb..14c6521 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,5 +23,4 @@ install: - happy --version build_script: - - cd C:\msys64\home\ghc\shake-build - - ./build.bat -j --no-progress + - stack exec -- C:\msys64\home\ghc\shake-build\build.bat -j --no-progress From git at git.haskell.org Fri Oct 27 00:33:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run shake script via stack from shake-build folder. (ffc5d73) Message-ID: <20171027003333.F02C53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffc5d73536fc68b3abcc1eb8b2dc375fcea33f1d/ghc >--------------------------------------------------------------- commit ffc5d73536fc68b3abcc1eb8b2dc375fcea33f1d Author: Andrey Mokhov Date: Sat Jan 9 02:19:18 2016 +0000 Run shake script via stack from shake-build folder. See #110. [skip ci] >--------------------------------------------------------------- ffc5d73536fc68b3abcc1eb8b2dc375fcea33f1d .appveyor.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 14c6521..1ecaaef 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,4 +23,5 @@ install: - happy --version build_script: - - stack exec -- C:\msys64\home\ghc\shake-build\build.bat -j --no-progress + - cd C:\msys64\home\ghc\shake-build + - stack exec -- build.bat -j --no-progress From git at git.haskell.org Fri Oct 27 00:33:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Various portability fixes (#331) (edd539f) Message-ID: <20171027003334.217053A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/edd539fc138d3e4b346b9375a63e4e52dafe9020/ghc >--------------------------------------------------------------- commit edd539fc138d3e4b346b9375a63e4e52dafe9020 Author: Ben Gamari Date: Fri Jun 30 13:45:23 2017 -0400 Various portability fixes (#331) * Don't assume location of bash interpreter * Pass curses library directory path to configure >--------------------------------------------------------------- edd539fc138d3e4b346b9375a63e4e52dafe9020 cfg/system.config.in | 2 ++ src/Oracles/Config/Setting.hs | 3 +++ src/Oracles/Path.hs | 9 ++++++--- src/Rules/Wrappers.hs | 26 +++++++++++++++++--------- src/Settings/Builders/GhcCabal.hs | 1 + src/Util.hs | 6 ++++-- 6 files changed, 33 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc edd539fc138d3e4b346b9375a63e4e52dafe9020 From git at git.haskell.org Fri Oct 27 00:33:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify using firstJustM (8933a3a) Message-ID: <20171027003334.64CCC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8933a3a8235a642638ef8e7e5e7c91777829535b/ghc >--------------------------------------------------------------- commit 8933a3a8235a642638ef8e7e5e7c91777829535b Author: Andrey Mokhov Date: Sun May 22 02:10:55 2016 +0100 Simplify using firstJustM >--------------------------------------------------------------- 8933a3a8235a642638ef8e7e5e7c91777829535b src/Oracles/Dependencies.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index d6cdbd3..a458b6d 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -24,8 +24,7 @@ fileDependencies :: Context -> FilePath -> Action (FilePath, [FilePath]) fileDependencies context obj = do let path = buildPath context -/- ".dependencies" -- If no dependencies found, try to drop the way suffix (for *.c sources). - deps <- listToMaybe . catMaybes <$> - mapM (askOracle . ObjDepsKey . (,) path) [obj, obj -<.> "o"] + deps <- firstJustM (askOracle . ObjDepsKey . (,) path) [obj, obj -<.> "o"] case deps of Nothing -> error $ "No dependencies found for file " ++ obj Just [] -> error $ "No source file found for file " ++ obj From git at git.haskell.org Fri Oct 27 00:33:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix terminal issue, build stage1 ghc only. (a64efa9) Message-ID: <20171027003337.CEE673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a64efa96c9b19edcf801b675685619292a1f878f/ghc >--------------------------------------------------------------- commit a64efa96c9b19edcf801b675685619292a1f878f Author: Andrey Mokhov Date: Sat Jan 9 02:53:36 2016 +0000 Fix terminal issue, build stage1 ghc only. See #110. [skip ci] >--------------------------------------------------------------- a64efa96c9b19edcf801b675685619292a1f878f .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 1ecaaef..99196db 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - stack exec -- build.bat -j --no-progress + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:33:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (15acc2c) Message-ID: <20171027003338.47D543A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/15acc2cd1cc217335d37b55beeb421bd5c4ac48d/ghc >--------------------------------------------------------------- commit 15acc2cd1cc217335d37b55beeb421bd5c4ac48d Author: Andrey Mokhov Date: Sun May 22 20:04:30 2016 +0100 Minor revision >--------------------------------------------------------------- 15acc2cd1cc217335d37b55beeb421bd5c4ac48d src/Builder.hs | 21 +++++++++++---------- src/Expression.hs | 10 ++++------ src/Oracles/Config.hs | 22 +++++++++------------- src/Oracles/Config/Flag.hs | 32 +++++++++++++++----------------- src/Oracles/Config/Setting.hs | 4 ++-- src/Oracles/Dependencies.hs | 30 +++++++++++------------------- src/Oracles/LookupInPath.hs | 6 ++---- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageData.hs | 5 +---- src/Predicate.hs | 7 +++---- src/Rules/Generate.hs | 6 ++---- src/Rules/Gmp.hs | 9 ++++----- src/Rules/Libffi.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- 14 files changed, 67 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 15acc2cd1cc217335d37b55beeb421bd5c4ac48d From git at git.haskell.org Fri Oct 27 00:33:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix setup-config dependency (#334) (6d46b39) Message-ID: <20171027003338.46B5C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d46b39a971e8b833b5ffd8f0666c3361fd79bc0/ghc >--------------------------------------------------------------- commit 6d46b39a971e8b833b5ffd8f0666c3361fd79bc0 Author: Zhen Zhang Date: Mon Jul 3 04:05:13 2017 +0800 Fix setup-config dependency (#334) >--------------------------------------------------------------- 6d46b39a971e8b833b5ffd8f0666c3361fd79bc0 src/Rules.hs | 2 ++ src/Rules/Data.hs | 6 ++++-- src/Rules/Install.hs | 3 ++- src/Settings/Path.hs | 8 +++++++- 4 files changed, 15 insertions(+), 4 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 6e9f5d7..e5835c0 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -39,6 +39,8 @@ buildLib stage pkg = do when (pkg `elem` activePackages) $ if isLibrary pkg then do -- build a library + when (nonCabalContext context) $ + need [pkgSetupConfigFile context] ways <- interpretInContext context getLibraryWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 0538f6c..0c19b2a 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -20,8 +20,9 @@ buildPackageData context at Context {..} = do cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile context + setupConfigFile = pkgSetupConfigFile context - dataFile %> \mk -> do + [dataFile, setupConfigFile] &%> \(mk:setupConfig:_) -> do -- Make sure all generated dependencies are in place before proceeding. orderOnly =<< interpretInContext context generatedDependencies @@ -32,7 +33,7 @@ buildPackageData context at Context {..} = do need =<< mapM pkgConfFile =<< contextDependencies context need [cabalFile] - build $ Target context GhcCabal [cabalFile] [mk] + build $ Target context GhcCabal [cabalFile] [mk, setupConfig] postProcessPackageData context mk pkgInplaceConfig context %> \conf -> do @@ -107,6 +108,7 @@ packageCmmSources pkg -- For example, @libraries/deepseq/dist-install_VERSION = 1.4.0.0@ -- is replaced by @VERSION = 1.4.0.0 at . -- Reason: Shake's built-in makefile parser doesn't recognise slashes +-- TODO (izgzhen): should fix DEP_LIB_REL_DIRS_SEARCHPATH postProcessPackageData :: Context -> FilePath -> Action () postProcessPackageData context at Context {..} file = do top <- topDirectory diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 3499b26..e7c6d41 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -18,7 +18,7 @@ import Oracles.Config.Setting import Oracles.PackageData import Oracles.Path -import qualified System.Directory.Extra as IO +import qualified System.Directory as IO {- | Install the built binaries etc. to the @destDir ++ prefix at . @@ -133,6 +133,7 @@ withLatestBuildStage pkg m = do installPackageConf :: Action () installPackageConf = do let context = vanillaContext Stage0 rts + liftIO $ IO.createDirectoryIfMissing True (takeDirectory pkgConfInstallPath) build $ Target context HsCpp [ pkgPath rts -/- "package.conf.in" ] [ pkgConfInstallPath <.> "raw" ] Stdout out <- cmd ("grep" :: String) [ "-v", "^#pragma GCC" diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 240f992..8814620 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -5,7 +5,8 @@ module Settings.Path ( rtsContext, rtsBuildPath, rtsConfIn, shakeFilesPath,inplacePackageDbDirectory, pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, - installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath + installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, + pkgSetupConfigFile ) where import Base @@ -74,6 +75,11 @@ pkgInplaceConfig context = buildPath context -/- "inplace-pkg-config" pkgDataFile :: Context -> FilePath pkgDataFile context = buildPath context -/- "package-data.mk" + +-- | Path to the @setup-config@ of a given 'Context'. +pkgSetupConfigFile :: Context -> FilePath +pkgSetupConfigFile context = buildPath context -/- "setup-config" + -- | Path to the haddock file of a given 'Context', e.g.: -- "_build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath From git at git.haskell.org Fri Oct 27 00:33:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Unlit utility (cce8759) Message-ID: <20171027003341.86B1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cce8759fdf3eed5988013cea4d2810457e8272a0/ghc >--------------------------------------------------------------- commit cce8759fdf3eed5988013cea4d2810457e8272a0 Author: Moritz Angermann Date: Fri Jan 8 18:21:31 2016 +0800 Adds Unlit utility Adds the unlit utility to turn literate files into unliterate files. Fixes #83 >--------------------------------------------------------------- cce8759fdf3eed5988013cea4d2810457e8272a0 shaking-up-ghc.cabal | 1 + src/GHC.hs | 14 +++++++++----- src/Rules/Data.hs | 11 +++++++++++ src/Settings/Args.hs | 4 +++- src/Settings/Packages/{Hp2ps.hs => Unlit.hs} | 10 +++++----- 5 files changed, 29 insertions(+), 11 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index ab9f7bc..066b9e7 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -91,6 +91,7 @@ executable ghc-shake , Settings.Packages.Rts , Settings.Packages.RunGhc , Settings.Packages.Touchy + , Settings.Packages.Unlit , Settings.TargetDirectory , Settings.User , Settings.Ways diff --git a/src/GHC.hs b/src/GHC.hs index 3d99e63..c26f552 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -6,7 +6,7 @@ module GHC ( haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unix, win32, xhtml, + touchy, transformers, unlit, unix, win32, xhtml, defaultKnownPackages, defaultTargetDirectory, defaultProgramPath ) where @@ -28,7 +28,7 @@ defaultKnownPackages = , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time - , touchy, transformers, unix, win32, xhtml ] + , touchy, transformers, unlit, unix, win32, xhtml ] -- Package definitions (see "Package") array, base, binary, bytestring, cabal, compiler, containers, compareSizes, @@ -37,7 +37,7 @@ array, base, binary, bytestring, cabal, compiler, containers, compareSizes, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unix, win32, xhtml :: Package + touchy, transformers, unlit, unix, win32, xhtml :: Package array = library "array" base = library "base" @@ -85,11 +85,12 @@ terminfo = library "terminfo" time = library "time" touchy = utility "touchy" transformers = library "transformers" +unlit = utility "unlit" unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" --- TODO: The following utils are not implemented yet: unlit, driver/ghc-split +-- TODO: The following utils are not implemented yet: driver/ghc-split -- TODO: The following utils are not included into the build system because -- they seem to be unused or unrelated to the build process: checkUniques, -- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, @@ -112,9 +113,12 @@ defaultProgramPath stage pkg | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing - | pkg == touchy = case stage of + | pkg == touchy = case stage of Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe _ -> Nothing + | pkg == unlit = case stage of + Stage0 -> Just $ "inplace/lib" -/- pkgNameString pkg <.> exe + _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index de4f8c0..8b21fc7 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -67,6 +67,17 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." + when (pkg == unlit) $ dataFile %> \mk -> do + let prefix = "utils_unlit_" ++ stageString stage ++ "_" + contents = unlines $ map (prefix++) + [ "PROGNAME = unlit" + , "C_SRCS = unlit.c" + , "INSTALL = YES" + , "INSTALL_INPLACE = YES" + , "SYNOPSIS = Literate script filter." ] + writeFileChanged mk contents + putSuccess $ "| Successfully generated '" ++ mk ++ "'." + when (pkg == touchy) $ dataFile %> \mk -> do let prefix = "utils_touchy_" ++ stageString stage ++ "_" contents = unlines $ map (prefix++) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index f2b30fa..3bd32d7 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -31,6 +31,7 @@ import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc import Settings.Packages.Touchy +import Settings.Packages.Unlit import Settings.User getArgs :: Expr [String] @@ -77,4 +78,5 @@ defaultPackageArgs = mconcat , iservBinPackageArgs , rtsPackageArgs , runGhcPackageArgs - , touchyPackageArgs ] + , touchyPackageArgs + , unlitPackageArgs ] diff --git a/src/Settings/Packages/Hp2ps.hs b/src/Settings/Packages/Unlit.hs similarity index 68% copy from src/Settings/Packages/Hp2ps.hs copy to src/Settings/Packages/Unlit.hs index 26518c6..e654a66 100644 --- a/src/Settings/Packages/Hp2ps.hs +++ b/src/Settings/Packages/Unlit.hs @@ -1,13 +1,13 @@ -module Settings.Packages.Hp2ps (hp2psPackageArgs) where +module Settings.Packages.Unlit (unlitPackageArgs) where import Base import Expression -import GHC (hp2ps) +import GHC (unlit) import Predicates (builderGhc, package) -import Settings +import Settings (getTargetPath) -hp2psPackageArgs :: Args -hp2psPackageArgs = package hp2ps ? do +unlitPackageArgs :: Args +unlitPackageArgs = package unlit ? do path <- getTargetPath let cabalMacros = path -/- "build/autogen/cabal_macros.h" mconcat [ builderGhc ? From git at git.haskell.org Fri Oct 27 00:33:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Stage1Only rule (#340) (b245f0e) Message-ID: <20171027003342.102073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b245f0e8ce176399dd87de283c7ad77125033bf5/ghc >--------------------------------------------------------------- commit b245f0e8ce176399dd87de283c7ad77125033bf5 Author: Zhen Zhang Date: Thu Jul 6 14:11:00 2017 +0800 Add Stage1Only rule (#340) >--------------------------------------------------------------- b245f0e8ce176399dd87de283c7ad77125033bf5 src/Oracles/Dependencies.hs | 2 +- src/Rules.hs | 36 ++++++++++++++++++++++++++++-------- src/Rules/Install.hs | 2 +- src/Settings.hs | 12 +++++++++++- src/UserSettings.hs | 21 ++++++++++++++++++--- 5 files changed, 59 insertions(+), 14 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 167047d..2775b3e 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -63,7 +63,7 @@ needContext cs = do lib0 <- buildDll0 context ghciLib <- pkgGhciLibraryFile context ghciFlag <- interpretInContext context $ getPkgData BuildGhciLib - let ghci = ghciFlag == "YES" && stage context == Stage1 + let ghci = ghciFlag == "YES" && (stage context == Stage1 || stage1Only) return $ [ libFile ] ++ [ lib0File | lib0 ] ++ [ ghciLib | ghci ] confs <- mapM pkgConfFile cs need $ libs ++ confs diff --git a/src/Rules.hs b/src/Rules.hs index e5835c0..3ba6ba7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,4 +1,4 @@ -module Rules (topLevelTargets, buildLib, buildRules) where +module Rules (topLevelTargets, buildPackage, buildRules) where import Base import Context @@ -18,22 +18,35 @@ import qualified Rules.Library import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register +import Oracles.Dependencies (needContext) +import Util (needBuilder) import Settings import Settings.Path allStages :: [Stage] allStages = [minBound ..] --- | This rule 'need' all top-level build targets. +-- | This rule 'need' all top-level build targets +-- or Stage1Only targets topLevelTargets :: Rules () -topLevelTargets = do - want $ Rules.Generate.inplaceLibCopyTargets +topLevelTargets = action $ do + need $ Rules.Generate.inplaceLibCopyTargets - forM_ allStages $ \stage -> - forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> action (buildLib stage pkg) + if stage1Only + then do + forAllPkgs $ \stg pkg -> + when (isLibrary pkg) $ + buildPackage stg pkg + forM_ programsStage1Only $ buildPackage Stage0 + else + forAllPkgs buildPackage + where + forAllPkgs f = + forM_ allStages $ \stage -> + forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> f stage pkg -buildLib :: Stage -> Package -> Action () -buildLib stage pkg = do +buildPackage :: Stage -> Package -> Action () +buildPackage stage pkg = do let context = vanillaContext stage pkg activePackages <- interpretInContext context getPackages when (pkg `elem` activePackages) $ @@ -44,6 +57,7 @@ buildLib stage pkg = do ways <- interpretInContext context getLibraryWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour + needContext [context] need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else -- otherwise build a program need =<< maybeToList <$> programPath (programContext stage pkg) @@ -90,3 +104,9 @@ buildRules = do Rules.Libffi.libffiRules packageRules Rules.Perl.perlScriptRules + +programsStage1Only :: [Package] +programsStage1Only = + [ deriveConstants, genprimopcode, hp2ps, runGhc + , ghcCabal, hpc, dllSplit, ghcPkg, hsc2hs + , genapply, ghc ] diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index e7c6d41..0492a62 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -191,7 +191,7 @@ installPackages = do let context = vanillaContext stg pkg top <- interpretInContext context getTopDirectory let installDistDir = top -/- buildPath context - buildLib stg pkg + buildPackage stg pkg docDir <- installDocDir ghclibDir <- installGhcLibDir version <- interpretInContext context (getPkgData Version) diff --git a/src/Settings.hs b/src/Settings.hs index d09fa31..8152a6e 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -3,7 +3,7 @@ module Settings ( findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, getContextDirectory, getBuildPath, stagePackages, builderPath, getBuilderPath, isSpecified, latestBuildStage, programPath, programContext, - integerLibraryName, destDir, pkgConfInstallPath + integerLibraryName, destDir, pkgConfInstallPath, stage1Only ) where import Base @@ -117,3 +117,13 @@ programPath context at Context {..} = do pkgConfInstallPath :: FilePath pkgConfInstallPath = buildPath (vanillaContext Stage0 rts) -/- "package.conf.install" + +-- | Stage1Only flag +-- TODO: Set this by cmdline flags +stage1Only :: Bool +stage1Only = defaultStage1Only + +-- | Install's DESTDIR flag +-- TODO: Set this by cmdline flags +destDir :: FilePath +destDir = defaultDestDir diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 96e6f4b..4398700 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -4,7 +4,7 @@ -- accidentally commit them. module UserSettings ( buildRootPath, userFlavours, userKnownPackages, verboseCommands, - putBuild, putSuccess, destDir + putBuild, putSuccess, defaultDestDir, defaultStage1Only ) where import System.Console.ANSI @@ -47,5 +47,20 @@ putSuccess = putColoured Dull Green -- It is by default empty, representing the root of file system, -- or it might be a directory. -- It is usually used with @prefix@, like @/usr/local@ -destDir :: FilePath -destDir = "" +defaultDestDir :: FilePath +defaultDestDir = "" + +{- + Stage1Only=YES means: + - don't build ghc-stage2 (the executable) + - don't build utils that rely on ghc-stage2 + See Note [No stage2 packages when CrossCompiling or Stage1Only] in + ./ghc.mk. + - install ghc-stage1 instead of ghc-stage2 + - install the ghc-pkg that was built with the stage0 compiler + - (*do* still build compiler/stage2 (i.e. the ghc library)) + - (*do* still build all other libraries) +-} +-- | Stage1Only flag, default off +defaultStage1Only :: Bool +defaultStage1Only = False From git at git.haskell.org Fri Oct 27 00:33:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set `THREADS` when running validate (e7e58aa) Message-ID: <20171027003342.2EE9F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7e58aaff96f2f74097ea8f605b216b8fdd15443/ghc >--------------------------------------------------------------- commit e7e58aaff96f2f74097ea8f605b216b8fdd15443 Author: Michal Terepeta Date: Sun May 22 21:26:53 2016 +0200 Set `THREADS` when running validate GHC testsuite uses the `THREADS` env variable (and not the make's `-j` setting) to control the parallelism. This commit sets THREADS to the value of `shakeThreads`. >--------------------------------------------------------------- e7e58aaff96f2f74097ea8f605b216b8fdd15443 src/Settings/Builders/Make.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index 3d06775..afb46d7 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -11,4 +11,4 @@ makeBuilderArgs = do mconcat [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=" ++ j] , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=" ++ j, "install"] - , builder (Make "testsuite/tests") ? arg "fast" ] + , builder (Make "testsuite/tests") ? append ["THREADS=" ++ show threads, "fast"] ] From git at git.haskell.org Fri Oct 27 00:33:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds knowledge about Perl (bd5bc65) Message-ID: <20171027003345.0770A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd5bc6544a5594bc69027d96b7e30da720812922/ghc >--------------------------------------------------------------- commit bd5bc6544a5594bc69027d96b7e30da720812922 Author: Moritz Angermann Date: Sat Jan 9 14:38:18 2016 +0800 Adds knowledge about Perl Fixes #82. Let's hope this is only a stop gap measure until we get rid of ghc-split as a perl script. >--------------------------------------------------------------- bd5bc6544a5594bc69027d96b7e30da720812922 cfg/system.config.in | 1 + src/Builder.hs | 2 ++ 2 files changed, 3 insertions(+) diff --git a/cfg/system.config.in b/cfg/system.config.in index 292d91f..6338e33 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -40,6 +40,7 @@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ tar = @TarCmd@ +perl = @PerlCmd@ # Information about builders: #============================ diff --git a/src/Builder.hs b/src/Builder.hs index fedcb8a..5450815 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -41,6 +41,7 @@ data Builder = Alex | Ld | Nm | Objdump + | Perl | Ranlib | Tar | Unlit @@ -83,6 +84,7 @@ builderKey builder = case builder of Ld -> "ld" Nm -> "nm" Objdump -> "objdump" + Perl -> "perl" Ranlib -> "ranlib" Tar -> "tar" Unlit -> "unlit" From git at git.haskell.org Fri Oct 27 00:33:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Automate dependency analysis of installed packages (#342) (5f0e385) Message-ID: <20171027003346.7E92F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f0e385d4377c5d51997ed3f51340d1405095c5d/ghc >--------------------------------------------------------------- commit 5f0e385d4377c5d51997ed3f51340d1405095c5d Author: Zhen Zhang Date: Sat Jul 8 20:35:23 2017 +0800 Automate dependency analysis of installed packages (#342) >--------------------------------------------------------------- 5f0e385d4377c5d51997ed3f51340d1405095c5d src/Oracles/Dependencies.hs | 19 +++++++++++++++++-- src/Rules.hs | 1 - src/Rules/Install.hs | 20 +++++++------------- 3 files changed, 24 insertions(+), 16 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 2775b3e..447df25 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,7 +1,7 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, TupleSections #-} module Oracles.Dependencies ( fileDependencies, contextDependencies, needContext, dependenciesOracles, - pkgDependencies + pkgDependencies, sortPkgsByDep ) where import qualified Data.HashMap.Strict as Map @@ -81,3 +81,18 @@ dependenciesOracles = do putLoud $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return $ Map.fromList [ (key, values) | (key:values) <- contents ] + +-- | Sort packages by their dependency +-- HACK (izgzhen): See https://github.com/snowleopard/hadrian/issues/344 for details +sortPkgsByDep :: [Package] -> Action [Package] +sortPkgsByDep pkgs = do + elems <- mapM (\p -> (p,) <$> pkgDependencies p) pkgs + return $ map fst $ topSort elems + where + annotateInDeg es e = + (foldr (\e' s -> if fst e' `elem` snd e then s + 1 else s) 0 es, e) + topSort [] = [] + topSort es = + let annotated = map (annotateInDeg es) es + inDegZero = map snd $ filter ((== 0). fst) annotated + in inDegZero ++ topSort (es \\ inDegZero) diff --git a/src/Rules.hs b/src/Rules.hs index 3ba6ba7..2081585 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -19,7 +19,6 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Oracles.Dependencies (needContext) -import Util (needBuilder) import Settings import Settings.Path diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 0492a62..8530f50 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -15,7 +15,7 @@ import Rules.Libffi import Rules.Generate import Settings.Packages.Rts import Oracles.Config.Setting -import Oracles.PackageData +import Oracles.Dependencies (sortPkgsByDep) import Oracles.Path import qualified System.Directory as IO @@ -81,7 +81,6 @@ installLibExecs = do (destDir ++ libExecDir -/- "ghc" <.> exe) -- | Binaries to install --- TODO: Consider Stage1Only installBinPkgs :: [Package] installBinPkgs = [ ghc, ghcPkg, ghcSplit, hp2ps @@ -176,14 +175,10 @@ installPackages = do copyFile ghcBootPlatformHeader (pkgPath compiler -/- "ghc_boot_platform.h") - -- TODO: Consider Stage1Only - -- TODO: Use automatic dependency analysis, rather than hardcoding - -- the ordering - let installLibPkgs = [ ghcPrim, integerSimple, base, filepath - , array, deepseq, bytestring, containers, time, unix - , directory, process, hpc, pretty, binary, cabal - , ghcBootTh, ghcBoot, templateHaskell - , transformers, terminfo, haskeline, ghci, compiler ] + activePackages <- filterM ((isJust <$>) . latestBuildStage) + (knownPackages \\ [rts, libffi]) + + installLibPkgs <- sortPkgsByDep (filter isLibrary activePackages) forM_ installLibPkgs $ \pkg at Package{..} -> do when (isLibrary pkg) $ @@ -194,10 +189,9 @@ installPackages = do buildPackage stg pkg docDir <- installDocDir ghclibDir <- installGhcLibDir - version <- interpretInContext context (getPkgData Version) + -- Copy over packages - let targetDest = destDir ++ ghclibDir -/- - pkgNameString pkg ++ "-" ++ version + strip <- stripCmdPath context ways <- interpretInContext context getLibraryWays let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" -- HACK? From git at git.haskell.org Fri Oct 27 00:33:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #256 from michalt/validate-threads (f24d880) Message-ID: <20171027003346.957403A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f24d88059e6f331dfbe789999d0ec6aca58fe64b/ghc >--------------------------------------------------------------- commit f24d88059e6f331dfbe789999d0ec6aca58fe64b Merge: 15acc2c e7e58aa Author: Andrey Mokhov Date: Sun May 22 21:53:26 2016 +0100 Merge pull request #256 from michalt/validate-threads Set `THREADS` when running validate >--------------------------------------------------------------- f24d88059e6f331dfbe789999d0ec6aca58fe64b src/Settings/Builders/Make.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:33:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds ghc-split generator, generateScripts and re-enables SplitObjects (7470e5d) Message-ID: <20171027003348.6F28A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7470e5d6f71ef5a662e8b0b1791683a03cbbebb8/ghc >--------------------------------------------------------------- commit 7470e5d6f71ef5a662e8b0b1791683a03cbbebb8 Author: Moritz Angermann Date: Sat Jan 9 14:39:14 2016 +0800 Adds ghc-split generator, generateScripts and re-enables SplitObjects Fixes #84. >--------------------------------------------------------------- 7470e5d6f71ef5a662e8b0b1791683a03cbbebb8 shaking-up-ghc.cabal | 1 + src/Main.hs | 1 + src/Rules/Generate.hs | 37 +++++++++++++++++++++++++++++++++++-- src/Rules/Generators/GhcSplit.hs | 25 +++++++++++++++++++++++++ src/Settings/User.hs | 3 ++- 5 files changed, 64 insertions(+), 3 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 066b9e7..bd6e31f 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -47,6 +47,7 @@ executable ghc-shake , Rules.Generators.GhcAutoconfH , Rules.Generators.GhcBootPlatformH , Rules.Generators.GhcPlatformH + , Rules.Generators.GhcSplit , Rules.Generators.GhcVersionH , Rules.Generators.VersionHs , Rules.IntegerGmp diff --git a/src/Main.hs b/src/Main.hs index 1710b39..a56f9ed 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -19,6 +19,7 @@ main = shakeArgs options rules , Rules.Config.configRules , Rules.Generate.copyRules , Rules.Generate.generateRules + , Rules.Generate.generateScripts , Rules.generateTargets , Rules.IntegerGmp.integerGmpRules , Rules.Libffi.libffiRules diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 71d88b1..3b6dfdc 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,5 +1,5 @@ module Rules.Generate ( - generatePackageCode, generateRules, + generatePackageCode, generateRules, generateScripts, derivedConstantsPath, generatedDependencies, installTargets, copyRules ) where @@ -11,6 +11,7 @@ import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH import Rules.Generators.GhcBootPlatformH import Rules.Generators.GhcPlatformH +import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles @@ -80,7 +81,7 @@ compilerDependencies stage = generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage + | pkg == compiler = compilerDependencies stage ++ ["inplace/lib/bin/ghc-split"] | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = includesDependencies ++ derivedConstantsDependencies | stage == Stage0 = defaultDependencies @@ -104,6 +105,13 @@ generate file target expr = do writeFileChanged file contents putSuccess $ "| Successfully generated '" ++ file ++ "'." +-- | Generates @file@ for @target@ and marks it as executable. +generateExec :: FilePath -> PartialTarget -> Expr String -> Action () +generateExec file target expr = do + generate file target expr + unit $ cmd "chmod +x " [file] + putSuccess $ "| Made '" ++ file ++ "' executable." + generatePackageCode :: Resources -> PartialTarget -> Rules () generatePackageCode _ target @ (PartialTarget stage pkg) = let buildPath = targetPath stage pkg -/- "build" @@ -177,6 +185,31 @@ generateRules = do where file <~ gen = file %> \out -> generate out emptyTarget gen +-- | Generate scripts the build system requires. For now we generate the +-- @ghc-split@ script from it's literate perl source. +generateScripts :: Rules () +generateScripts = do + -- how to translate literate perl to perl. + -- this is a hack :-/ + "//*.prl" %> \out -> do + let src = out -<.> "lprl" + path <- builderPath Unlit + need [path] + unit $ cmd [path] [src] [out] + + -- ghc-split is only a perl script. + let ghcSplit = "inplace/lib/ghc-split" -- See system.config + let ghcSplitBin = "inplace/lib/bin/ghc-split" -- See ConfigHs.hs + + ghcSplit <~ generateGhcSplit + + ghcSplitBin %> \out -> do + need [ghcSplit] + copyFileChanged ghcSplit out + + where + file <~ gen = file %> \out -> generateExec out emptyTarget gen + -- TODO: Use the Types, Luke! (drop partial function) -- We sometimes need to evaluate expressions that do not require knowing all -- information about the target. In this case, we don't want to know anything. diff --git a/src/Rules/Generators/GhcSplit.hs b/src/Rules/Generators/GhcSplit.hs new file mode 100644 index 0000000..77cd49f --- /dev/null +++ b/src/Rules/Generators/GhcSplit.hs @@ -0,0 +1,25 @@ +module Rules.Generators.GhcSplit (generateGhcSplit) where + +import Base +import Expression +import Oracles +import Settings.User + +generateGhcSplit :: Expr String +generateGhcSplit = do + let yesNo = lift . fmap (\x -> if x then "YES" else "NO") + perl <- getBuilderPath Perl + let script = "driver" -/- "split" -/- "ghc-split.prl" + when trackBuildSystem . lift $ + need [sourcePath -/- "Rules" -/- "Generators" -/- "GhcSplit.hs"] + lift $ need [script] + targetPlatform <- getSetting TargetPlatform + ghcEnableTNC <- yesNo ghcEnableTablesNextToCode + contents <- lift $ readFileLines script + return . unlines $ + [ "#!" ++ perl + , "$TARGETPLATFORM = \"" ++ targetPlatform ++ "\";" + -- I don't see where the ghc-split tool uses TNC, but + -- it's in the build-perl macro. + , "$TABLES_NEXT_TO_CODE = \"" ++ ghcEnableTNC ++ "\";" + ] ++ contents diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 7a877ce..6ba7155 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -9,6 +9,7 @@ module Settings.User ( import GHC import Expression import Predicates +import Settings.Default -- Control user-specific settings userArgs :: Args @@ -59,7 +60,7 @@ validating = False -- To switch off split objects change to 'return False' splitObjects :: Predicate -splitObjects = return False -- FIXME: should be defaultSplitObjects, see #84. +splitObjects = defaultSplitObjects dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Fri Oct 27 00:33:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Better tracking of dependence in installation (#353) (d8e1759) Message-ID: <20171027003350.C88293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d8e17590fc8efcbd87f97bb1d85a1775b85272d3/ghc >--------------------------------------------------------------- commit d8e17590fc8efcbd87f97bb1d85a1775b85272d3 Author: Zhen Zhang Date: Sat Jul 8 21:02:17 2017 +0800 Better tracking of dependence in installation (#353) >--------------------------------------------------------------- d8e17590fc8efcbd87f97bb1d85a1775b85272d3 src/Rules/Install.hs | 27 ++++++++++++--------------- src/Util.hs | 3 +++ 2 files changed, 15 insertions(+), 15 deletions(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 8530f50..4c91316 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedStrings, FlexibleContexts #-} +{-# LANGUAGE FlexibleContexts #-} module Rules.Install (installRules) where import Base @@ -39,8 +39,8 @@ XXX (izgzhen): Do we need @INSTALL_OPTS@ in the make scripts? installRules :: Rules () installRules = do "install" ~> do - installPackageConf installIncludes + installPackageConf installCommonLibs installLibExecs installLibExecScripts @@ -54,7 +54,6 @@ getLibExecDir = (-/- "bin") <$> installGhcLibDir -- ref: ghc.mk installLibExecScripts :: Action () installLibExecScripts = do - need libExecScripts libExecDir <- getLibExecDir installDir (destDir ++ libExecDir) forM_ libExecScripts $ \script -> do @@ -74,7 +73,6 @@ installLibExecs = do withLatestBuildStage pkg $ \stg -> do let context = programContext stg pkg let bin = inplaceLibBinPath -/- programName context <.> exe - need [bin] installProgram bin (destDir ++ libExecDir) when (pkg == ghc) $ do moveFile (destDir ++ libExecDir -/- programName context <.> exe) @@ -111,10 +109,9 @@ installBins = do contents <- interpretInContext context $ wrapper (WrappedBinary (destDir ++ libDir) symName) - withTempDir $ \tmp -> do - let tmpfile = tmp -/- binName - writeFileChanged tmpfile contents - installProgram tmpfile (destDir ++ binDir) + let wrapperPath = destDir ++ binDir -/- binName + writeFileChanged wrapperPath contents + makeExecutable wrapperPath unlessM windowsHost $ linkSymbolic (destDir ++ binDir -/- binName) (destDir ++ binDir -/- symName) @@ -135,13 +132,12 @@ installPackageConf = do liftIO $ IO.createDirectoryIfMissing True (takeDirectory pkgConfInstallPath) build $ Target context HsCpp [ pkgPath rts -/- "package.conf.in" ] [ pkgConfInstallPath <.> "raw" ] - Stdout out <- cmd ("grep" :: String) [ "-v", "^#pragma GCC" - , pkgConfInstallPath <.> "raw" ] + Stdout content <- cmd "grep" [ "-v", "^#pragma GCC" + , pkgConfInstallPath <.> "raw" ] withTempFile $ \tmp -> do - liftIO $ writeFile tmp out - Stdout out' <- cmd ("sed" :: String) - [ "-e", "s/\"\"//g", "-e", "s/:[ ]*,/: /g", tmp ] - liftIO $ writeFile pkgConfInstallPath out' + liftIO $ writeFile tmp content + Stdout content' <- cmd "sed" [ "-e", "s/\"\"//g", "-e", "s/:[ ]*,/: /g", tmp ] + liftIO $ writeFile pkgConfInstallPath content' -- | Install packages to @prefix/lib@ -- ref: ghc.mk @@ -195,6 +191,7 @@ installPackages = do strip <- stripCmdPath context ways <- interpretInContext context getLibraryWays let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" -- HACK? + need [ ghcCabalInplace ] -- HACK (#318): copy stuff back to the place favored by ghc-cabal quietly $ copyDirectoryContents (Not excluded) @@ -250,7 +247,7 @@ installPackages = do [ "--force", "--global-package-db" , installedPackageConf, "recache" ] where - createData f = unit $ cmd ("chmod" :: String) [ "644", f ] + createData f = unit $ cmd "chmod" [ "644", f ] excluded = Or [ Test "//haddock-prologue.txt" , Test "//package-data.mk" diff --git a/src/Util.hs b/src/Util.hs index c2335c2..da12e21 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -184,6 +184,7 @@ installDir dir = do installData :: [FilePath] -> FilePath -> Action () installData fs dir = do i <- setting InstallData + need fs forM_ fs $ \f -> putBuild $ "| Install data " ++ f ++ " to " ++ dir quietly $ cmd i fs dir @@ -192,6 +193,7 @@ installData fs dir = do installProgram :: FilePath -> FilePath -> Action () installProgram f dir = do i <- setting InstallProgram + need [f] putBuild $ "| Install program " ++ f ++ " to " ++ dir quietly $ cmd i f dir @@ -199,6 +201,7 @@ installProgram f dir = do installScript :: FilePath -> FilePath -> Action () installScript f dir = do i <- setting InstallScript + need [f] putBuild $ "| Install script " ++ f ++ " to " ++ dir quietly $ cmd i f dir From git at git.haskell.org Fri Oct 27 00:33:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Upgrade to extra-1.4.7 (00b88a1) Message-ID: <20171027003350.EA77A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/00b88a16a67cf107eaf716b55ff5016fc5732c2a/ghc >--------------------------------------------------------------- commit 00b88a16a67cf107eaf716b55ff5016fc5732c2a Author: Andrey Mokhov Date: Mon May 23 00:16:14 2016 +0100 Upgrade to extra-1.4.7 >--------------------------------------------------------------- 00b88a16a67cf107eaf716b55ff5016fc5732c2a hadrian.cabal | 2 +- src/Oracles/Dependencies.hs | 2 +- src/Oracles/ModuleFiles.hs | 2 +- src/Rules/Library.hs | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 95ae3a0..c9d5551 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -122,7 +122,7 @@ executable hadrian , Cabal == 1.22.* || == 1.24.* , containers == 0.5.* , directory == 1.2.* - , extra == 1.4.* + , extra >= 1.4.7 , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.9 , shake >= 0.15.6 diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index ce94805..1a8b587 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -50,7 +50,7 @@ contextDependencies context at Context {..} = do -- | Coarse-grain 'need': make sure given contexts are fully built. needContext :: [Context] -> Action () needContext cs = do - libs <- fmap concat . forM cs $ \context -> do + libs <- concatForM cs $ \context -> do libFile <- pkgLibraryFile context lib0File <- pkgLibraryFile0 context lib0 <- buildDll0 context diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index ece6d0b..b11ef3b 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -115,7 +115,7 @@ moduleFilesOracle = void $ do modules <- fmap sort . pkgDataList $ Modules path let dirs = (path -/- "autogen") : map (pkgPath package -/-) srcDirs modDirFiles = groupSort $ map decodeModule modules - result <- fmap concat . forM dirs $ \dir -> do + result <- concatForM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do let fullDir = unifyPath $ dir -/- mDir diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index edbdb52..dd144d1 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -36,7 +36,7 @@ buildPackageLibrary context at Context {..} = do split <- interpretInContext context splitObjects splitObjs <- if not split then return hObjs else -- TODO: make clearer! - fmap concat $ forM hSrcs $ \src -> do + concatForM hSrcs $ \src -> do let splitPath = path -/- src ++ "_" ++ osuf way ++ "_split" contents <- liftIO $ IO.getDirectoryContents splitPath return . map (splitPath -/-) From git at git.haskell.org Fri Oct 27 00:33:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Extra library (693a66c) Message-ID: <20171027003352.2409F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/693a66cafe77e0ea2449e9f7b4bc51145c97ab38/ghc >--------------------------------------------------------------- commit 693a66cafe77e0ea2449e9f7b4bc51145c97ab38 Author: Moritz Angermann Date: Sat Jan 9 17:04:58 2016 +0800 Use Extra library - replaces `wordsWhen` with `wordsBy` - replaces `replace` with `replace` Fixes #130 >--------------------------------------------------------------- 693a66cafe77e0ea2449e9f7b4bc51145c97ab38 src/Base.hs | 23 ++--------------------- src/Oracles/LookupInPath.hs | 3 ++- src/Rules/Data.hs | 1 + src/Rules/Libffi.hs | 1 + 4 files changed, 6 insertions(+), 22 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 925c427..fb33907 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,9 +22,9 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, renderBox, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, replaceEq, replace, quote, chunksOfSize, + bimap, minusOrd, intersectOrd, replaceEq, quote, chunksOfSize, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), - versionToInt, removeFileIfExists, removeDirectoryIfExists, wordsWhen + versionToInt, removeFileIfExists, removeDirectoryIfExists ) where import Control.Applicative @@ -90,25 +90,6 @@ replaceSeparators = replaceWhen isPathSeparator replaceWhen :: (a -> Bool) -> a -> [a] -> [a] replaceWhen p to = map (\from -> if p from then to else from) --- | Find all occurrences of substring 'from' and replace them to 'to' in a --- given string. Not very efficient, but simple and fast enough for our purposes -replace :: Eq a => [a] -> [a] -> [a] -> [a] -replace from to = go - where - skipFrom = drop $ length from - go [] = [] - go s @ (x : xs) - | from `isPrefixOf` s = to ++ go (skipFrom s) - | otherwise = x : go xs - --- | Split a list into chunks in places where the predicate @p@ holds. --- See: http://stackoverflow.com/a/4981265 -wordsWhen :: Eq a => (a -> Bool) -> [a] -> [[a]] -wordsWhen p list = - case dropWhile p list of - [] -> [] - l -> w : wordsWhen p rest where (w, rest) = break p l - -- | @chunksOfSize size strings@ splits a given list of strings into chunks not -- exceeding the given @size at . chunksOfSize :: Int -> [String] -> [[String]] diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index c2a05e2..2532cb9 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -4,6 +4,7 @@ module Oracles.LookupInPath ( ) where import Base +import Extra (wordsBy) newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -22,7 +23,7 @@ lookupInPath c lookupInPathOracle :: Rules () lookupInPathOracle = do o <- newCache $ \c -> do - envPaths <- wordsWhen (== ':') <$> getEnvWithDefault "" "PATH" + envPaths <- wordsBy (== ':') <$> getEnvWithDefault "" "PATH" let candidates = map (-/- c) envPaths -- this will crash if we do not find any valid candidate. fullCommand <- head <$> filterM doesFileExist candidates diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index de4f8c0..b2c5878 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -2,6 +2,7 @@ module Rules.Data (buildPackageData) where import Base import Expression +import Extra (replace) import GHC import Oracles import Predicates (registerPackage) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 9d77814..31f249b 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -2,6 +2,7 @@ module Rules.Libffi (libffiRules, libffiDependencies) where import Base import Expression +import Extra (replace) import GHC import Oracles import Rules.Actions From git at git.haskell.org Fri Oct 27 00:33:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (#352) (e93f583d) Message-ID: <20171027003354.992803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e93f583d1d684e9db069c558967dc38d19a180e8/ghc >--------------------------------------------------------------- commit e93f583d1d684e9db069c558967dc38d19a180e8 Author: Zhen Zhang Date: Sat Jul 8 21:25:06 2017 +0800 Update README.md (#352) >--------------------------------------------------------------- e93f583d1d684e9db069c558967dc38d19a180e8 README.md | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index 2256fbf..d65b98c 100644 --- a/README.md +++ b/README.md @@ -106,6 +106,14 @@ are still up-to-date. To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` target. +#### Installation + +To build and install GHC artifacts, run the `install` target. + +By default, the artifacts will be installed to `` on your system. For example, +`ghc` will be installed to `/usr/local/bin`. By modifying `defaultDestDir` in `UserSettings.hs`, +you can install things to non-system path `DESTDIR/` instead. + #### Testing * `build validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` @@ -122,12 +130,12 @@ zero (see [#197][test-issue]). Current limitations ------------------- The new build system still lacks many important features: -* There is currently no support for the `dynamic` build way: [#4][dynamic-issue]. * Validation is not implemented: [#187][validation-issue]. +* Dynamic linking on Windows is not supported [#343][dynamic-windows-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). * Not all modes of the old build system are supported, e.g. [#250][freeze-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. -* There is no support for installation or binary distribution: [#219][install-issue]. +* There is no support for binary distribution: [#219][install-issue]. Check out [milestones] to see when we hope to resolve the above limitations. @@ -162,8 +170,8 @@ helped me endure and enjoy the project. [windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [test-issue]: https://github.com/snowleopard/hadrian/issues/197 -[dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 +[dynamic-windows-issue]: https://github.com/snowleopard/hadrian/issues/343 [freeze-issue]: https://github.com/snowleopard/hadrian/issues/250 [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 From git at git.haskell.org Fri Oct 27 00:33:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop shake-0.15.6 from extra-deps, and add extra-1.4.7 (ec031af) Message-ID: <20171027003354.B22903A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ec031af8526a0187cbf6701c18ccd4687bff0160/ghc >--------------------------------------------------------------- commit ec031af8526a0187cbf6701c18ccd4687bff0160 Author: Andrey Mokhov Date: Mon May 23 00:38:19 2016 +0100 Drop shake-0.15.6 from extra-deps, and add extra-1.4.7 >--------------------------------------------------------------- ec031af8526a0187cbf6701c18ccd4687bff0160 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index 0d8809b..b20331f 100644 --- a/stack.yaml +++ b/stack.yaml @@ -9,7 +9,7 @@ packages: # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: -- shake-0.15.6 +- extra-1.4.7 # Override default flag values for local packages and extra-deps flags: {} From git at git.haskell.org Fri Oct 27 00:33:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #140 from snowleopard/feature/use-extra (8c2a30d) Message-ID: <20171027003355.9380C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c2a30db05a56cd1e1c33c34acbe3a794a7b00d7/ghc >--------------------------------------------------------------- commit 8c2a30db05a56cd1e1c33c34acbe3a794a7b00d7 Merge: a64efa9 693a66c Author: Andrey Mokhov Date: Sat Jan 9 12:15:46 2016 +0000 Merge pull request #140 from snowleopard/feature/use-extra Use Extra library >--------------------------------------------------------------- 8c2a30db05a56cd1e1c33c34acbe3a794a7b00d7 src/Base.hs | 23 ++--------------------- src/Oracles/LookupInPath.hs | 3 ++- src/Rules/Data.hs | 1 + src/Rules/Libffi.hs | 1 + 4 files changed, 6 insertions(+), 22 deletions(-) From git at git.haskell.org Fri Oct 27 00:33:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update flavours doc (#338) (9dde04c) Message-ID: <20171027003358.267AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dde04c09058e7f07e7683fa3d334a096c911b2d/ghc >--------------------------------------------------------------- commit 9dde04c09058e7f07e7683fa3d334a096c911b2d Author: Zhen Zhang Date: Sat Jul 8 23:58:07 2017 +0800 Update flavours doc (#338) >--------------------------------------------------------------- 9dde04c09058e7f07e7683fa3d334a096c911b2d doc/flavours.md | 70 ++++++++++++++++++++++++++++++++++----------------------- 1 file changed, 42 insertions(+), 28 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index 9fe2239..3bf0c30 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -118,45 +118,59 @@ Libraries and GHC can be built in different _ways_, e.g. with or without profili information. The following table lists ways that are built in different flavours. - - - - - - - - - + + + + + + + + + + + + + + + - - - + + + - - - + + + - - + + + - - - + + - +
FlavourLibrary waysRTS waysProfiled GHC
stage0 - stage1+ - stage0 - stage1+ - stage0 - stage1+ -
FlavourLibrary waysRTS waysProfiled GHC
stage0stage1+stage0stage1+stage0stage1+
default
perf
prof
devel1
devel2
vanillavanilla
profiling
logging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
threadedProfiling
vanilla
profiling
dynamic
logging
debug
threaded
threadedDebug
threadedLogging +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
+ logging
debug
threaded
threadedDebug
+ threadedLogging
threadedProfiling +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
Only in
prof
flavour
Only in
prof
flavour
quick - vanilla
quick vanillalogging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
vanilla
dynamic
logging
debug
threaded
threadedDebug
threadedLogging +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
logging
debug
threaded
threadedDebug
threadedLogging +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
No No
quickest +
quickest vanilla vanilla vanilla
threaded (when --haddock)
vanilla
threaded (when --haddock)
No No
From git at git.haskell.org Fri Oct 27 00:33:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use LTS-5.17 (68f8eaf) Message-ID: <20171027003358.56DDD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68f8eafed955a6b1ed895960c21144c50c0c61d1/ghc >--------------------------------------------------------------- commit 68f8eafed955a6b1ed895960c21144c50c0c61d1 Author: Andrey Mokhov Date: Mon May 23 01:31:47 2016 +0100 Use LTS-5.17 >--------------------------------------------------------------- 68f8eafed955a6b1ed895960c21144c50c0c61d1 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index b20331f..f6deca8 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,7 +1,7 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-5.1 +resolver: lts-5.17 # Local packages, usually specified by relative directory name packages: From git at git.haskell.org Fri Oct 27 00:33:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:33:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Shallow clone GHC from Github instead of Haskell.org (c43d07d) Message-ID: <20171027003359.21A043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c43d07d967b7a7876e6a7733a343934d35d0d616/ghc >--------------------------------------------------------------- commit c43d07d967b7a7876e6a7733a343934d35d0d616 Author: David Luposchainsky Date: Sat Jan 9 14:01:33 2016 +0100 Shallow clone GHC from Github instead of Haskell.org >--------------------------------------------------------------- c43d07d967b7a7876e6a7733a343934d35d0d616 .travis.yml | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 6413818..ca51b6f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -39,7 +39,12 @@ install: - alex --version - happy --version - - travis_retry git clone git://git.haskell.org/ghc --recurse-submodules + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ + - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ + - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ + - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ + - travis_retry git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 # Travis clones the project into ".", but we need it as a child directory # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake From git at git.haskell.org Fri Oct 27 00:34:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Packages/Rts: add `linker` to RTS directories (166e3fb) Message-ID: <20171027003402.0157A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/166e3fb4aa2e8c4040287c1d87bf022b81a07790/ghc >--------------------------------------------------------------- commit 166e3fb4aa2e8c4040287c1d87bf022b81a07790 Author: Michal Terepeta Date: Wed May 25 20:14:33 2016 +0200 Packages/Rts: add `linker` to RTS directories Recent commit split off the m32 allocator to `rts/linker/`, which broke the build using Hadrian (since it didn't know about the new directory). This fixes it. Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 166e3fb4aa2e8c4040287c1d87bf022b81a07790 src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 52aac32..6c99113 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -104,7 +104,7 @@ buildPackageData context at Context {..} = do orderOnly $ generatedDependencies stage package windows <- windowsHost let prefix = fixKey (buildPath context) ++ "_" - dirs = [ ".", "hooks", "sm", "eventlog" ] + dirs = [ ".", "hooks", "sm", "eventlog", "linker" ] ++ [ if windows then "win32" else "posix" ] -- TODO: Adding cmm/S sources to C_SRCS is a hack -- refactor. cSrcs <- map unifyPath <$> From git at git.haskell.org Fri Oct 27 00:34:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #257 from michalt/rts-linker/1 (45b5f13) Message-ID: <20171027003405.9B75E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45b5f1341e3b400efeaa675ddc9d43d69268ff09/ghc >--------------------------------------------------------------- commit 45b5f1341e3b400efeaa675ddc9d43d69268ff09 Merge: 68f8eaf 166e3fb Author: Andrey Mokhov Date: Wed May 25 21:47:24 2016 +0100 Merge pull request #257 from michalt/rts-linker/1 Packages/Rts: add `linker` to RTS directories >--------------------------------------------------------------- 45b5f1341e3b400efeaa675ddc9d43d69268ff09 src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:34:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop "ghs-split" builder (b214918) Message-ID: <20171027003402.A053B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b214918b34ab1ab5131457391dbdb4d023ea46e0/ghc >--------------------------------------------------------------- commit b214918b34ab1ab5131457391dbdb4d023ea46e0 Author: Moritz Angermann Date: Sat Jan 9 21:16:20 2016 +0800 Drop "ghs-split" builder >--------------------------------------------------------------- b214918b34ab1ab5131457391dbdb4d023ea46e0 cfg/system.config.in | 3 +-- src/Builder.hs | 2 -- src/Rules/Generators/ConfigHs.hs | 2 +- 3 files changed, 2 insertions(+), 5 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 6338e33..498f78c 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -28,8 +28,7 @@ derive-constants = inplace/bin/deriveConstants hs-cpp = @HaskellCPPCmd@ hs-cpp-args = @HaskellCPPArgs@ -unlit = inplace/lib/unlit -ghc-split = inplace/lib/ghc-split +unlit = inplace/lib/bin/unlit alex = @AlexCmd@ ar = @ArCmd@ diff --git a/src/Builder.hs b/src/Builder.hs index 5450815..efc3216 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -32,7 +32,6 @@ data Builder = Alex | GhcCabalHsColour | GhcM Stage | GhcPkg Stage - | GhcSplit | Haddock | Happy | HsColour @@ -75,7 +74,6 @@ builderKey builder = case builder of GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour' GhcPkg Stage0 -> "system-ghc-pkg" GhcPkg _ -> "ghc-pkg" - GhcSplit -> "ghc-split" Happy -> "happy" Haddock -> "haddock" HsColour -> "hscolour" diff --git a/src/Rules/Generators/ConfigHs.hs b/src/Rules/Generators/ConfigHs.hs index 547670a..5cdfc3f 100644 --- a/src/Rules/Generators/ConfigHs.hs +++ b/src/Rules/Generators/ConfigHs.hs @@ -32,7 +32,7 @@ generateConfigHs = do cGhcEnableTablesNextToCode <- yesNo ghcEnableTablesNextToCode cLeadingUnderscore <- yesNo $ flag LeadingUnderscore cGHC_UNLIT_PGM <- fmap takeFileName $ getBuilderPath Unlit - cGHC_SPLIT_PGM <- fmap takeBaseName $ getBuilderPath GhcSplit + let cGHC_SPLIT_PGM = "ghc-split" cLibFFI <- lift useLibFFIForAdjustors rtsWays <- getRtsWays cGhcRtsWithLibdw <- getFlag WithLibdw From git at git.haskell.org Fri Oct 27 00:34:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use correct ar for host/target (#356) (b7550b2) Message-ID: <20171027003405.A662E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b7550b2bdbd148e80e3d5b06419549bcb7ca92ee/ghc >--------------------------------------------------------------- commit b7550b2bdbd148e80e3d5b06419549bcb7ca92ee Author: Ben Gamari Date: Mon Jul 10 13:40:54 2017 -0400 Use correct ar for host/target (#356) Previously we would always use the ar of the target; this is incorrect. Fixes #350. >--------------------------------------------------------------- b7550b2bdbd148e80e3d5b06419549bcb7ca92ee cfg/system.config.in | 1 + src/Builder.hs | 2 +- src/Oracles/Path.hs | 3 ++- src/Rules/Gmp.hs | 4 ++-- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Util.hs | 2 +- 8 files changed, 12 insertions(+), 10 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 078e1ec..34ef7b9 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -16,6 +16,7 @@ make = @MakeCmd@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ +system-ar = @AR_STAGE0@ system-cc = @CC_STAGE0@ system-ghc = @WithGhc@ system-ghc-pkg = @GhcPkgCmd@ diff --git a/src/Builder.hs b/src/Builder.hs index b2fbca3..7937319 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -28,7 +28,7 @@ data GhcPkgMode = Init | Update deriving (Eq, Generic, Show) -- @GhcPkg Stage0@ is the bootstrapping @GhcPkg at . -- @GhcPkg Stage1@ is the one built in Stage0. data Builder = Alex - | Ar + | Ar Stage | DeriveConstants | Cc CcMode Stage | Configure FilePath diff --git a/src/Oracles/Path.hs b/src/Oracles/Path.hs index a1c56f5..2ec2773 100644 --- a/src/Oracles/Path.hs +++ b/src/Oracles/Path.hs @@ -24,7 +24,8 @@ getTopDirectory = lift topDirectory systemBuilderPath :: Builder -> Action FilePath systemBuilderPath builder = case builder of Alex -> fromKey "alex" - Ar -> fromKey "ar" + Ar Stage0 -> fromKey "system-ar" + Ar _ -> fromKey "ar" Cc _ Stage0 -> fromKey "system-cc" Cc _ _ -> fromKey "cc" -- We can't ask configure for the path to configure! diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index a3e32d3..ee8eb82 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -25,7 +25,7 @@ gmpMakefile = gmpBuildPath -/- "Makefile" configureEnvironment :: Action [CmdOption] configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 - , builderEnvironment "AR" Ar + , builderEnvironment "AR" (Ar Stage1) , builderEnvironment "NM" Nm ] gmpRules :: Rules () @@ -43,7 +43,7 @@ gmpRules = do putBuild "| No GMP library/framework detected; in tree GMP will be built" need [gmpLibrary] createDirectory gmpObjects - build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] + build $ Target gmpContext (Ar Stage1) [gmpLibrary] [gmpObjects] copyFile (gmpBuildPath -/- "gmp.h") header copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 57f6263..bac9970 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -31,7 +31,7 @@ configureEnvironment = do sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 , builderEnvironment "CXX" $ Cc CompileC Stage1 , builderEnvironment "LD" Ld - , builderEnvironment "AR" Ar + , builderEnvironment "AR" (Ar Stage1) , builderEnvironment "NM" Nm , builderEnvironment "RANLIB" Ranlib , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w" diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 455c57c..b746279 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -72,8 +72,8 @@ buildPackageLibrary context at Context {..} = do asuf <- libsuf way let isLib0 = ("//*-0" ++ asuf) ?== a - if isLib0 then build $ Target context Ar [] [a] -- TODO: Scan for dlls - else build $ Target context Ar objs [a] + if isLib0 then build $ Target context (Ar stage) [] [a] -- TODO: Scan for dlls + else build $ Target context (Ar stage) objs [a] synopsis <- interpretInContext context $ getPkgData Synopsis unless isLib0 . putSuccess $ renderLibrary diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 9ddfe15..18816e1 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -25,7 +25,7 @@ ghcCabalBuilderArgs = builder GhcCabal ? do , packageConstraints , withStaged $ Cc CompileC , notStage0 ? with Ld - , with Ar + , withStaged Ar , with Alex , with Happy , verbosity < Chatty ? append [ "-v0", "--configure-option=--quiet" @@ -91,7 +91,7 @@ cppArgs = arg $ "-I" ++ generatedPath withBuilderKey :: Builder -> String withBuilderKey b = case b of - Ar -> "--with-ar=" + Ar _ -> "--with-ar=" Ld -> "--with-ld=" Cc _ _ -> "--with-gcc=" Ghc _ _ -> "--with-ghc=" diff --git a/src/Util.hs b/src/Util.hs index da12e21..944e8e5 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -53,7 +53,7 @@ customBuild rs opts target at Target {..} = do withResources rs $ do putInfo target quietlyUnlessVerbose $ case builder of - Ar -> do + Ar _ -> do output <- interpret target getOutput if "//*.a" ?== output then arCmd path argList From git at git.haskell.org Fri Oct 27 00:34:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix documentation rules (#324) (13023bc) Message-ID: <20171027003401.BF3CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13023bc3e13dcd003efbf00a83a7ab780c2727c3/ghc >--------------------------------------------------------------- commit 13023bc3e13dcd003efbf00a83a7ab780c2727c3 Author: Zhen Zhang Date: Sun Jul 9 18:21:31 2017 +0800 Fix documentation rules (#324) >--------------------------------------------------------------- 13023bc3e13dcd003efbf00a83a7ab780c2727c3 src/Rules/Documentation.hs | 17 ++++++++++------- src/Rules/Install.hs | 14 ++++++++++++++ src/Rules/Wrappers.hs | 12 ++++++++++-- 3 files changed, 34 insertions(+), 9 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index cf54e0a..5ee6818 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -7,11 +7,14 @@ import Flavour import GHC import Oracles.ModuleFiles import Oracles.PackageData +import Oracles.Path (getTopDirectory) import Settings import Settings.Path import Target import Util +import qualified System.Directory as IO + haddockHtmlLib :: FilePath haddockHtmlLib = "inplace/lib/html/haddock-util.js" @@ -31,13 +34,6 @@ buildPackageDocumentation context at Context {..} = , depPkg /= rts ] need $ srcs ++ haddocks ++ [haddockHtmlLib] - -- HsColour sources - -- TODO: what is the output of GhcCabalHsColour? - whenM (isSpecified HsColour) $ do - pkgConf <- pkgConfFile context - need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf - build $ Target context GhcCabalHsColour [cabalFile] [] - -- Build Haddock documentation -- TODO: pass the correct way from Rules via Context let haddockWay = if dynamicGhcPrograms flavour then dynamic else vanilla @@ -47,6 +43,13 @@ buildPackageDocumentation context at Context {..} = let dir = takeDirectory haddockHtmlLib liftIO $ removeFiles dir ["//*"] copyDirectory "utils/haddock/haddock-api/resources/html" dir + where + excluded = Or + [ Test "//haddock-prologue.txt" + , Test "//package-data.mk" + , Test "//setup-config" + , Test "//inplace-pkg-config" + , Test "//build" ] -- # Make the haddocking depend on the library .a file, to ensure -- # that we wait until the library is fully built before we haddock it diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 4c91316..553f8d1 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -193,6 +193,20 @@ installPackages = do let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" -- HACK? need [ ghcCabalInplace ] + let cabalFile = pkgCabalFile pkg + -- HsColour sources + -- QUESTION: what is the output of GhcCabalHsColour? + whenM (isSpecified HsColour) $ do + top <- interpretInContext context getTopDirectory + let installDistDir = top -/- buildPath context + -- HACK: copy stuff back to the place favored by ghc-cabal + quietly $ copyDirectoryContents (Not excluded) + installDistDir (installDistDir -/- "build") + + pkgConf <- pkgConfFile context + need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf + build $ Target context GhcCabalHsColour [cabalFile] [] + -- HACK (#318): copy stuff back to the place favored by ghc-cabal quietly $ copyDirectoryContents (Not excluded) installDistDir (installDistDir -/- "build") diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs index b6f1266..6adf3f7 100644 --- a/src/Rules/Wrappers.hs +++ b/src/Rules/Wrappers.hs @@ -109,12 +109,21 @@ hsc2hsWrapper WrappedBinary{..} = do , "HSC2HS_EXTRA=\"" ++ hsc2hsExtra ++ "\"" , contents ] +haddockWrapper :: WrappedBinary -> Expr String +haddockWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) + ++ " -B" ++ binaryLibPath ++ " -l" ++ binaryLibPath ++ " ${1+\"$@\"}" ] + wrappersCommon :: [(Context, Wrapper)] wrappersCommon = [ (vanillaContext Stage0 ghc , ghcWrapper) , (vanillaContext Stage1 ghc , ghcWrapper) , (vanillaContext Stage1 hp2ps , hp2psWrapper) , (vanillaContext Stage1 hpc , hpcWrapper) - , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) ] + , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) + , (vanillaContext Stage2 haddock, haddockWrapper)] -- | List of wrappers for inplace artefacts inplaceWrappers :: [(Context, Wrapper)] @@ -127,4 +136,3 @@ installWrappers :: [(Context, Wrapper)] installWrappers = wrappersCommon ++ [ (vanillaContext Stage0 ghcPkg, installGhcPkgWrapper) , (vanillaContext Stage1 runGhc, installRunGhcWrapper) ] - From git at git.haskell.org Fri Oct 27 00:34:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Include PR Comments (423c5dd) Message-ID: <20171027003406.5128D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/423c5dd10b51f3251d59fec64c68b7bc07019dbf/ghc >--------------------------------------------------------------- commit 423c5dd10b51f3251d59fec64c68b7bc07019dbf Author: Moritz Angermann Date: Sat Jan 9 21:44:23 2016 +0800 Include PR Comments >--------------------------------------------------------------- 423c5dd10b51f3251d59fec64c68b7bc07019dbf shaking-up-ghc.cabal | 1 + src/GHC.hs | 5 +---- src/Main.hs | 3 ++- src/Rules/Generate.hs | 33 ++++----------------------------- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Perl.hs | 25 +++++++++++++++++++++++++ 6 files changed, 34 insertions(+), 35 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index bd6e31f..a5b4c57 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -55,6 +55,7 @@ executable ghc-shake , Rules.Library , Rules.Oracles , Rules.Package + , Rules.Perl , Rules.Program , Rules.Resources , Rules.Wrappers.Ghc diff --git a/src/GHC.hs b/src/GHC.hs index c26f552..3b58bbe 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -113,12 +113,9 @@ defaultProgramPath stage pkg | pkg == haddock || pkg == ghcTags = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing - | pkg == touchy = case stage of + | pkg `elem` [touchy, unlit] = case stage of Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe _ -> Nothing - | pkg == unlit = case stage of - Stage0 -> Just $ "inplace/lib" -/- pkgNameString pkg <.> exe - _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg diff --git a/src/Main.hs b/src/Main.hs index a56f9ed..9f223a8 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -10,6 +10,7 @@ import qualified Rules.Generate import qualified Rules.IntegerGmp import qualified Rules.Libffi import qualified Rules.Oracles +import qualified Rules.Perl main :: IO () main = shakeArgs options rules @@ -19,7 +20,7 @@ main = shakeArgs options rules , Rules.Config.configRules , Rules.Generate.copyRules , Rules.Generate.generateRules - , Rules.Generate.generateScripts + , Rules.Perl.perlScriptRules , Rules.generateTargets , Rules.IntegerGmp.integerGmpRules , Rules.Libffi.libffiRules diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 3b6dfdc..2b2962b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( - generatePackageCode, generateRules, generateScripts, - derivedConstantsPath, generatedDependencies, + generate, generateExec, generatePackageCode, generateRules, + derivedConstantsPath, emptyTarget, generatedDependencies, installTargets, copyRules ) where @@ -11,7 +11,6 @@ import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH import Rules.Generators.GhcBootPlatformH import Rules.Generators.GhcPlatformH -import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles @@ -78,10 +77,11 @@ compilerDependencies stage = , "primop-vector-tys-exports.hs-incl" , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] + ++ ["inplace/lib/bin/ghc-split"] generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage ++ ["inplace/lib/bin/ghc-split"] + | pkg == compiler = compilerDependencies stage | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = includesDependencies ++ derivedConstantsDependencies | stage == Stage0 = defaultDependencies @@ -185,31 +185,6 @@ generateRules = do where file <~ gen = file %> \out -> generate out emptyTarget gen --- | Generate scripts the build system requires. For now we generate the --- @ghc-split@ script from it's literate perl source. -generateScripts :: Rules () -generateScripts = do - -- how to translate literate perl to perl. - -- this is a hack :-/ - "//*.prl" %> \out -> do - let src = out -<.> "lprl" - path <- builderPath Unlit - need [path] - unit $ cmd [path] [src] [out] - - -- ghc-split is only a perl script. - let ghcSplit = "inplace/lib/ghc-split" -- See system.config - let ghcSplitBin = "inplace/lib/bin/ghc-split" -- See ConfigHs.hs - - ghcSplit <~ generateGhcSplit - - ghcSplitBin %> \out -> do - need [ghcSplit] - copyFileChanged ghcSplit out - - where - file <~ gen = file %> \out -> generateExec out emptyTarget gen - -- TODO: Use the Types, Luke! (drop partial function) -- We sometimes need to evaluate expressions that do not require knowing all -- information about the target. In this case, we don't want to know anything. diff --git a/src/Rules/Generators/GhcSplit.hs b/src/Rules/Generators/GhcSplit.hs index 77cd49f..a2bd8b2 100644 --- a/src/Rules/Generators/GhcSplit.hs +++ b/src/Rules/Generators/GhcSplit.hs @@ -9,7 +9,7 @@ generateGhcSplit :: Expr String generateGhcSplit = do let yesNo = lift . fmap (\x -> if x then "YES" else "NO") perl <- getBuilderPath Perl - let script = "driver" -/- "split" -/- "ghc-split.prl" + let script = "driver/split/ghc-split.prl" when trackBuildSystem . lift $ need [sourcePath -/- "Rules" -/- "Generators" -/- "GhcSplit.hs"] lift $ need [script] diff --git a/src/Rules/Perl.hs b/src/Rules/Perl.hs new file mode 100644 index 0000000..c1e5ba8 --- /dev/null +++ b/src/Rules/Perl.hs @@ -0,0 +1,25 @@ +module Rules.Perl (perlScriptRules) where + +import Base +import Expression +import Rules.Actions (runBuilder) +import Rules.Generate (generateExec, emptyTarget) +import Rules.Generators.GhcSplit (generateGhcSplit) + +-- | Generate scripts the build system requires. For now we generate the +-- @ghc-split@ script from it's literate perl source. +perlScriptRules :: Rules () +perlScriptRules = do + -- how to translate literate perl to perl. + -- this is a hack :-/ + "//*.prl" %> \out -> do + let src = out -<.> "lprl" + runBuilder Unlit [src, out] + + -- ghc-split is only a perl script. + let ghcSplit = "inplace/lib/bin/ghc-split" + + ghcSplit <~ generateGhcSplit + + where + file <~ gen = file %> \out -> generateExec out emptyTarget gen From git at git.haskell.org Fri Oct 27 00:34:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Enable optional UserSettings.hs file (123bdb3) Message-ID: <20171027003409.07C1B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/123bdb37674bfe60509886ec92c99e80b0588966/ghc >--------------------------------------------------------------- commit 123bdb37674bfe60509886ec92c99e80b0588966 Author: Kai Harries Date: Sat May 28 17:53:07 2016 +0200 Enable optional UserSettings.hs file Fix #247 The defaul user settings are stored in ./src/UserSettings.hs. If the user want to override these settings, he can copy this file into ./ and make the desired changes to ./UserSettings.hs. >--------------------------------------------------------------- 123bdb37674bfe60509886ec92c99e80b0588966 .gitignore | 3 + README.md | 3 +- doc/user-settings.md | 5 +- hadrian.cabal | 3 +- src/Settings/User.hs | 103 ++---------------------------- src/{Settings/User.hs => UserSettings.hs} | 8 ++- 6 files changed, 20 insertions(+), 105 deletions(-) diff --git a/.gitignore b/.gitignore index b7bfddb..5307cdd 100644 --- a/.gitignore +++ b/.gitignore @@ -15,3 +15,6 @@ cabal.sandbox.config # build.stack.sh specific /.stack-work/ + +# the user settings +/UserSettings.hs diff --git a/README.md b/README.md index e4fb7dc..b1da6f7 100644 --- a/README.md +++ b/README.md @@ -88,7 +88,7 @@ by Shake oracles. #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We -use [`src/Settings/User.hs`][user-settings] for the same purpose, see +use `./UserSettings.hs` for the same purpose, see [documentation](doc/user-settings.md). #### Clean and full rebuild @@ -155,7 +155,6 @@ helped me endure and enjoy the project. [windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md [build-artefacts-issue]: https://github.com/snowleopard/hadrian/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 -[user-settings]: https://github.com/snowleopard/hadrian/blob/master/src/Settings/User.hs [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 diff --git a/doc/user-settings.md b/doc/user-settings.md index 1433ae9..a5185ad 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,7 +1,8 @@ # User settings -You can customise Hadrian by specifying user build settings in file -`src/Settings/User.hs`. Here we document currently supported settings. +You can customise Hadrian by copying the file ./src/UserSettings.hs to +./UserSettings.hs and specifying user build settings in +`./UserSettings.hs`. Here we document currently supported settings. ## Build directory diff --git a/hadrian.cabal b/hadrian.cabal index c9d5551..3bbc2dd 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -16,7 +16,8 @@ source-repository head executable hadrian main-is: Main.hs - hs-source-dirs: src + hs-source-dirs: . + , src other-modules: Base , Builder , CmdLineFlag diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 16c7c25..9588297 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -5,101 +5,8 @@ module Settings.User ( turnWarningsIntoErrors, splitObjects, verboseCommands, putBuild, putSuccess ) where -import System.Console.ANSI - -import Base -import CmdLineFlag -import GHC -import Predicate -import Settings.Default - --- See doc/user-settings.md for instructions. - --- | All build results are put into 'buildRootPath' directory. -buildRootPath :: FilePath -buildRootPath = "_build" - --- | Modify default build command line arguments. -userArgs :: Args -userArgs = builder Ghc ? remove ["-Wall", "-fwarn-tabs"] - --- | Modify the set of packages that are built by default in each stage. -userPackages :: Packages -userPackages = mempty - --- | Add user defined packages. Don't forget to add them to 'userPackages' too. -userKnownPackages :: [Package] -userKnownPackages = [] - --- | Choose the integer library: 'integerGmp' or 'integerSimple'. -integerLibrary :: Package -integerLibrary = integerGmp - --- FIXME: We skip 'dynamic' since it's currently broken #4. --- | Modify the set of ways in which library packages are built. -userLibraryWays :: Ways -userLibraryWays = remove [dynamic] - --- | Modify the set of ways in which the 'rts' package is built. -userRtsWays :: Ways -userRtsWays = mempty - --- | User defined flags. Note the following type semantics: --- * @Bool@: a plain Boolean flag whose value is known at compile time. --- * @Action Bool@: a flag whose value can depend on the build environment. --- * @Predicate@: a flag whose value can depend on the build environment and --- on the current build target. - --- TODO: Drop 'trackBuildSystem' as it brings negligible gains. --- | Set this to True if you are making any changes in the build system and want --- appropriate rebuilds to be initiated. Switching this to False speeds things --- up a little (particularly zero builds). --- WARNING: a complete rebuild is required when changing this setting. -trackBuildSystem :: Bool -trackBuildSystem = True - --- TODO: This should be set automatically when validating. -validating :: Bool -validating = False - --- | Control when split objects are generated. Note, due to the GHC bug #11315 --- it is necessary to do a full clean rebuild when changing this option. -splitObjects :: Predicate -splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects - --- | Control when to build Haddock documentation. -buildHaddock :: Predicate -buildHaddock = return cmdBuildHaddock - --- TODO: Do we need to be able to set these from command line? --- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? -dynamicGhcPrograms :: Bool -dynamicGhcPrograms = False - -ghciWithDebugger :: Bool -ghciWithDebugger = False - -ghcProfiled :: Bool -ghcProfiled = False - -ghcDebugged :: Bool -ghcDebugged = False - --- TODO: Replace with stage2 ? arg "-Werror"? Also see #251. --- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. -turnWarningsIntoErrors :: Predicate -turnWarningsIntoErrors = return False - --- | Set to True to print full command lines during the build process. Note, --- this is a Predicate, hence you can enable verbose output only for certain --- targets, e.g.: @verboseCommands = package ghcPrim at . -verboseCommands :: Predicate -verboseCommands = return False - --- | Customise build progress messages (e.g. executing a build command). -putBuild :: String -> Action () -putBuild = putColoured Vivid White - --- | Customise build success messages (e.g. a package is built successfully). -putSuccess :: String -> Action () -putSuccess = putColoured Vivid Green +-- Import the actual user settings from the module UserSettings. +-- The user can put an UserSettings.hs file into the hadrian root +-- folder that takes precedence over the default UserSettings.hs +-- file located in src/. +import UserSettings diff --git a/src/Settings/User.hs b/src/UserSettings.hs similarity index 94% copy from src/Settings/User.hs copy to src/UserSettings.hs index 16c7c25..7560aa1 100644 --- a/src/Settings/User.hs +++ b/src/UserSettings.hs @@ -1,4 +1,8 @@ -module Settings.User ( +-- +-- If you want to customize your build you should copy this file from +-- ./src/UserSettings.hs to ./UserSettings.hs and only edit your copy. +-- +module UserSettings ( buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, @@ -74,7 +78,7 @@ buildHaddock = return cmdBuildHaddock -- TODO: Do we need to be able to set these from command line? -- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? dynamicGhcPrograms :: Bool -dynamicGhcPrograms = False +dynamicGhcPrograms = True ghciWithDebugger :: Bool ghciWithDebugger = False From git at git.haskell.org Fri Oct 27 00:34:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix warnings (e8abab2) Message-ID: <20171027003409.5F1213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e8abab220113b10ef22e1080d7771216b2488b0b/ghc >--------------------------------------------------------------- commit e8abab220113b10ef22e1080d7771216b2488b0b Author: Andrey Mokhov Date: Tue Jul 11 18:07:53 2017 +0100 Fix warnings See #358 >--------------------------------------------------------------- e8abab220113b10ef22e1080d7771216b2488b0b src/Oracles/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 13 +------------ src/Settings/Builders/Ghc.hs | 1 - src/Settings/Flavours/Quickest.hs | 1 - src/Settings/Packages/GhcCabal.hs | 3 --- 5 files changed, 2 insertions(+), 18 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 447df25..3aaabfa 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -90,7 +90,7 @@ sortPkgsByDep pkgs = do return $ map fst $ topSort elems where annotateInDeg es e = - (foldr (\e' s -> if fst e' `elem` snd e then s + 1 else s) 0 es, e) + (foldr (\e' s -> if fst e' `elem` snd e then s + 1 else s) (0 :: Int) es, e) topSort [] = [] topSort es = let annotated = map (annotateInDeg es) es diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 5ee6818..a3a7b7c 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -7,14 +7,11 @@ import Flavour import GHC import Oracles.ModuleFiles import Oracles.PackageData -import Oracles.Path (getTopDirectory) import Settings import Settings.Path import Target import Util -import qualified System.Directory as IO - haddockHtmlLib :: FilePath haddockHtmlLib = "inplace/lib/html/haddock-util.js" @@ -23,8 +20,7 @@ haddockHtmlLib = "inplace/lib/html/haddock-util.js" -- files in the Shake database seems fragile and unnecessary. buildPackageDocumentation :: Context -> Rules () buildPackageDocumentation context at Context {..} = - let cabalFile = pkgCabalFile package - haddockFile = pkgHaddockFile context + let haddockFile = pkgHaddockFile context in when (stage == Stage1) $ do haddockFile %> \file -> do srcs <- hsSources context @@ -43,13 +39,6 @@ buildPackageDocumentation context at Context {..} = let dir = takeDirectory haddockHtmlLib liftIO $ removeFiles dir ["//*"] copyDirectory "utils/haddock/haddock-api/resources/html" dir - where - excluded = Or - [ Test "//haddock-prologue.txt" - , Test "//package-data.mk" - , Test "//setup-config" - , Test "//inplace-pkg-config" - , Test "//build" ] -- # Make the haddocking depend on the library .a file, to ensure -- # that we wait until the library is fully built before we haddock it diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index aa6303e..9864946 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,7 +2,6 @@ module Settings.Builders.Ghc (ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs) w import Flavour import GHC -import Settings.Path (ghcSplitPath) import Settings.Builders.Common ghcBuilderArgs :: Args diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index fa7cad5..d5dff73 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -2,7 +2,6 @@ module Settings.Flavours.Quickest (quickestFlavour) where import Flavour import Predicate -import Oracles.Config.Flag (platformSupportsSharedLibs) import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 57147e4..983292f 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -4,10 +4,8 @@ import Distribution.PackageDescription.Parse import Base import GHC -import Oracles.Config.Setting import Oracles.Dependencies (pkgDependencies) import Predicate -import Package (pkgCabalFile) import Distribution.Verbosity (silent) import Distribution.Text (display) import Distribution.Package (pkgVersion) @@ -16,7 +14,6 @@ import qualified Distribution.PackageDescription as DP ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do - win <- lift windowsHost cabalDeps <- lift $ pkgDependencies cabal lift $ need [pkgCabalFile cabal] pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile cabal From git at git.haskell.org Fri Oct 27 00:34:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adjust cmdLineLengthLimit for OS X (e3d96ff) Message-ID: <20171027003410.036203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3d96ff27fb0967053043b0d30c0fb4112889613/ghc >--------------------------------------------------------------- commit e3d96ff27fb0967053043b0d30c0fb4112889613 Author: Moritz Angermann Date: Sat Jan 9 21:45:08 2016 +0800 Adjust cmdLineLengthLimit for OS X This should fix #141. >--------------------------------------------------------------- e3d96ff27fb0967053043b0d30c0fb4112889613 src/Oracles/Config/Setting.hs | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index ace9158..58f508b 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -3,7 +3,7 @@ module Oracles.Config.Setting ( setting, settingList, getSetting, getSettingList, anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, windowsHost, ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, - ghcCanonVersion, cmdLineLengthLimit + ghcCanonVersion, cmdLineLengthLimit, osxHost ) where import Control.Monad.Trans.Reader @@ -125,6 +125,9 @@ anyHostOs = matchSetting HostOs windowsHost :: Action Bool windowsHost = anyHostOs ["mingw32", "cygwin32"] +osxHost :: Action Bool +osxHost = anyHostOs ["darwin"] + ghcWithInterpreter :: Action Bool ghcWithInterpreter = do goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "solaris2" @@ -156,6 +159,10 @@ ghcCanonVersion = do cmdLineLengthLimit :: Action Int cmdLineLengthLimit = do windows <- windowsHost - return $ if windows - then 31000 - else 4194304 -- Cabal needs a bit more than 2MB! + osx <- osxHost + return $ case (windows, osx) of + -- windows + (True, False) -> 31000 + -- osx 262144 is ARG_MAX, 33166 experimentally determined + (False, True) -> 262144 - 33166 + _ -> 4194304 -- Cabal needs a bit more than 2MB! From git at git.haskell.org Fri Oct 27 00:34:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #258 from KaiHa/ticket/247 (20d7082) Message-ID: <20171027003413.185033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20d70820a2c2fc7bfecacf79906db129d157846d/ghc >--------------------------------------------------------------- commit 20d70820a2c2fc7bfecacf79906db129d157846d Merge: 45b5f13 123bdb3 Author: Andrey Mokhov Date: Tue May 31 07:10:48 2016 +0100 Merge pull request #258 from KaiHa/ticket/247 Enable optional UserSettings.hs file >--------------------------------------------------------------- 20d70820a2c2fc7bfecacf79906db129d157846d .gitignore | 3 + README.md | 3 +- doc/user-settings.md | 5 +- hadrian.cabal | 3 +- src/Settings/User.hs | 103 ++---------------------------- src/{Settings/User.hs => UserSettings.hs} | 8 ++- 6 files changed, 20 insertions(+), 105 deletions(-) From git at git.haskell.org Fri Oct 27 00:34:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't optimize cabal stage0 build (#357) (e1aadf3) Message-ID: <20171027003413.390463A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1aadf31f565128c609765f550e5213adbfab35d/ghc >--------------------------------------------------------------- commit e1aadf31f565128c609765f550e5213adbfab35d Author: Ben Gamari Date: Tue Jul 11 17:24:01 2017 -0400 Don't optimize cabal stage0 build (#357) >--------------------------------------------------------------- e1aadf31f565128c609765f550e5213adbfab35d hadrian.cabal | 1 + src/Settings/Default.hs | 5 ++++- src/Settings/Packages/Cabal.hs | 11 +++++++++++ 3 files changed, 16 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index fbda4b0..1178cb4 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -91,6 +91,7 @@ executable hadrian , Settings.Flavours.Quick , Settings.Flavours.Quickest , Settings.Packages.Base + , Settings.Packages.Cabal , Settings.Packages.Compiler , Settings.Packages.Ghc , Settings.Packages.GhcCabal diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 3ad1fab..19c6937 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -30,6 +30,7 @@ import Settings.Builders.Ld import Settings.Builders.Make import Settings.Builders.Tar import Settings.Packages.Base +import Settings.Packages.Cabal import Settings.Packages.Compiler import Settings.Packages.Ghc import Settings.Packages.GhcCabal @@ -268,6 +269,7 @@ disableWarningArgsLibs = do defaultPackageArgs :: Args defaultPackageArgs = mconcat [ basePackageArgs + , cabalPackageArgs , compilerPackageArgs , ghcPackageArgs , ghcCabalPackageArgs @@ -279,4 +281,5 @@ defaultPackageArgs = mconcat , runGhcPackageArgs , disableWarningArgsStage0 , disableWarningArgsStage1 - , disableWarningArgsLibs ] + , disableWarningArgsLibs + ] diff --git a/src/Settings/Packages/Cabal.hs b/src/Settings/Packages/Cabal.hs new file mode 100644 index 0000000..eddee75 --- /dev/null +++ b/src/Settings/Packages/Cabal.hs @@ -0,0 +1,11 @@ +module Settings.Packages.Cabal where + +import GHC +import Predicate + +cabalPackageArgs :: Args +cabalPackageArgs = package cabal ? do + -- Cabal is a rather large library and quite slow to compile. Moreover, we + -- build it for stage0 only so we can link ghc-pkg against it, so there is + -- little reason to spend the effort to optimize it. + stage Stage0 ? builder Ghc ? append [ "-O0" ] From git at git.haskell.org Fri Oct 27 00:34:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #138 from snowleopard/feature/UtilUnlit (883d929) Message-ID: <20171027003413.96B623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/883d92982c8de5abb8ee22f42f82eba94ed05566/ghc >--------------------------------------------------------------- commit 883d92982c8de5abb8ee22f42f82eba94ed05566 Merge: 8c2a30d e3d96ff Author: Andrey Mokhov Date: Sat Jan 9 14:08:26 2016 +0000 Merge pull request #138 from snowleopard/feature/UtilUnlit Add support for ghc-split, unlit and perl script rules. >--------------------------------------------------------------- 883d92982c8de5abb8ee22f42f82eba94ed05566 cfg/system.config.in | 4 ++-- shaking-up-ghc.cabal | 3 +++ src/Builder.hs | 4 ++-- src/GHC.hs | 11 ++++++----- src/Main.hs | 2 ++ src/Oracles/Config/Setting.hs | 15 +++++++++++---- src/Rules/Data.hs | 11 +++++++++++ src/Rules/Generate.hs | 12 ++++++++++-- src/Rules/Generators/ConfigHs.hs | 2 +- src/Rules/Generators/GhcSplit.hs | 25 +++++++++++++++++++++++++ src/Rules/Perl.hs | 25 +++++++++++++++++++++++++ src/Settings/Args.hs | 4 +++- src/Settings/Packages/{Hp2ps.hs => Unlit.hs} | 10 +++++----- src/Settings/User.hs | 3 ++- 14 files changed, 108 insertions(+), 23 deletions(-) From git at git.haskell.org Fri Oct 27 00:34:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add iosHost function. (e7fc568) Message-ID: <20171027003417.2CFC93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7fc5681234fb897f2014194c81b64450811c543/ghc >--------------------------------------------------------------- commit e7fc5681234fb897f2014194c81b64450811c543 Author: Andrey Mokhov Date: Sat Jan 9 14:33:51 2016 +0000 Add iosHost function. See #138. [skip ci] >--------------------------------------------------------------- e7fc5681234fb897f2014194c81b64450811c543 src/Oracles/Config/Setting.hs | 11 +++++++---- src/Settings/Packages.hs | 2 +- 2 files changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 58f508b..0047f03 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -1,9 +1,9 @@ module Oracles.Config.Setting ( Setting (..), SettingList (..), setting, settingList, getSetting, getSettingList, - anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, windowsHost, + anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, - ghcCanonVersion, cmdLineLengthLimit, osxHost + ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost ) where import Control.Monad.Trans.Reader @@ -122,12 +122,15 @@ anyTargetArch = matchSetting TargetArch anyHostOs :: [String] -> Action Bool anyHostOs = matchSetting HostOs -windowsHost :: Action Bool -windowsHost = anyHostOs ["mingw32", "cygwin32"] +iosHost :: Action Bool +iosHost = anyHostOs ["ios"] osxHost :: Action Bool osxHost = anyHostOs ["darwin"] +windowsHost :: Action Bool +windowsHost = anyHostOs ["mingw32", "cygwin32"] + ghcWithInterpreter :: Action Bool ghcWithInterpreter = do goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "solaris2" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 3f4f661..4d2f76c 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -26,7 +26,7 @@ packagesStage0 = mconcat -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] , stage0 ? windowsHost ? append [touchy] - , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ] + , notM windowsHost ? iosHost ? append [terminfo] ] packagesStage1 :: Packages packagesStage1 = mconcat From git at git.haskell.org Fri Oct 27 00:34:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test the resulting GHC binary (5ad9fad) Message-ID: <20171027003417.482793A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ad9fad8be600b7042f60cf81d61a2f3ac151dbb/ghc >--------------------------------------------------------------- commit 5ad9fad8be600b7042f60cf81d61a2f3ac151dbb Author: Andrey Mokhov Date: Wed Jun 1 09:15:00 2016 +0100 Test the resulting GHC binary See #259. >--------------------------------------------------------------- 5ad9fad8be600b7042f60cf81d61a2f3ac151dbb .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 3b61256..18ede46 100644 --- a/.travis.yml +++ b/.travis.yml @@ -60,6 +60,7 @@ script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET + - ./ghc/inplace/bin/ghc-stage2 -e 1+2 cache: directories: From git at git.haskell.org Fri Oct 27 00:34:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix validate's dependency on generated files (#362) (31f9640) Message-ID: <20171027003417.6CFC93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31f9640125cf74dd96b1c210143cb3772656bd35/ghc >--------------------------------------------------------------- commit 31f9640125cf74dd96b1c210143cb3772656bd35 Author: Zhen Zhang Date: Sat Jul 15 21:02:05 2017 +0800 Fix validate's dependency on generated files (#362) >--------------------------------------------------------------- 31f9640125cf74dd96b1c210143cb3772656bd35 src/Rules/Test.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 08eca05..fc059ab 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -5,6 +5,7 @@ import Builder import Expression import Flavour import GHC +import qualified Rules.Generate import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Path @@ -16,6 +17,7 @@ import Util testRules :: Rules () testRules = do "validate" ~> do + need $ Rules.Generate.inplaceLibCopyTargets needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc From git at git.haskell.org Fri Oct 27 00:34:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix iosHost condition. (f8660c8) Message-ID: <20171027003421.0DBDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8660c804c827eb8c0f9f29af2de57e5eca908f1/ghc >--------------------------------------------------------------- commit f8660c804c827eb8c0f9f29af2de57e5eca908f1 Author: Andrey Mokhov Date: Sat Jan 9 14:35:43 2016 +0000 Fix iosHost condition. See #138. [skip ci] >--------------------------------------------------------------- f8660c804c827eb8c0f9f29af2de57e5eca908f1 src/Settings/Packages.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 4d2f76c..b7e2dac 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -26,7 +26,7 @@ packagesStage0 = mconcat -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] , stage0 ? windowsHost ? append [touchy] - , notM windowsHost ? iosHost ? append [terminfo] ] + , notM windowsHost ? notM iosHost ? append [terminfo] ] packagesStage1 :: Packages packagesStage1 = mconcat From git at git.haskell.org Fri Oct 27 00:34:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (9a34338) Message-ID: <20171027003421.955323A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a34338c6dd82ea5df18d0443e63e0a66b1b123e/ghc >--------------------------------------------------------------- commit 9a34338c6dd82ea5df18d0443e63e0a66b1b123e Author: Andrey Mokhov Date: Sun Jul 16 23:55:02 2017 +0100 Minor revision >--------------------------------------------------------------- 9a34338c6dd82ea5df18d0443e63e0a66b1b123e src/Predicate.hs | 6 ++- src/Settings/Builders/Cc.hs | 14 +++--- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Default.hs | 111 +++++++++++++++++++++---------------------- 4 files changed, 66 insertions(+), 68 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 9a34338c6dd82ea5df18d0443e63e0a66b1b123e From git at git.haskell.org Fri Oct 27 00:34:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to UseLibdw (119bda5) Message-ID: <20171027003421.7B2F73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/119bda593291be9748b21dc45b3a3777a980a532/ghc >--------------------------------------------------------------- commit 119bda593291be9748b21dc45b3a3777a980a532 Author: Andrey Mokhov Date: Wed Jun 1 09:48:32 2016 +0100 Switch to UseLibdw See #259. >--------------------------------------------------------------- 119bda593291be9748b21dc45b3a3777a980a532 cfg/system.config.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index f235f19..b580f86 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -115,4 +115,4 @@ ffi-lib-dir = @FFILibDir@ # Optional Dependencies: #======================= -with-libdw = @HaveLibdw@ +with-libdw = @UseLibdw@ From git at git.haskell.org Fri Oct 27 00:34:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #142 from quchen/clone-from-github (a012ac6) Message-ID: <20171027003425.59F1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a012ac65bc12d0ec8afb6bc746eac1246e8da9ea/ghc >--------------------------------------------------------------- commit a012ac65bc12d0ec8afb6bc746eac1246e8da9ea Merge: f8660c8 c43d07d Author: Andrey Mokhov Date: Sat Jan 9 14:40:58 2016 +0000 Merge pull request #142 from quchen/clone-from-github CI: Shallow clone GHC from Github instead of Haskell.org >--------------------------------------------------------------- a012ac65bc12d0ec8afb6bc746eac1246e8da9ea .travis.yml | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:34:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to install-related commands on Windows. Minor revision. (31890f3) Message-ID: <20171027003425.714483A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31890f39222ffffff7a17343925a70c5f13df83b/ghc >--------------------------------------------------------------- commit 31890f39222ffffff7a17343925a70c5f13df83b Author: Andrey Mokhov Date: Mon Jul 17 01:28:24 2017 +0100 Fix paths to install-related commands on Windows. Minor revision. See #345 >--------------------------------------------------------------- 31890f39222ffffff7a17343925a70c5f13df83b src/Oracles/Path.hs | 3 ++- src/Rules/Install.hs | 18 ++++++++-------- src/Util.hs | 60 ++++++++++++++++++++++++++++------------------------ 3 files changed, 43 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 31890f39222ffffff7a17343925a70c5f13df83b From git at git.haskell.org Fri Oct 27 00:34:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to user settings (d58dabf) Message-ID: <20171027003425.C5C4E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d58dabfd7ca07e50374b7c859f81b8ed55dc600c/ghc >--------------------------------------------------------------- commit d58dabfd7ca07e50374b7c859f81b8ed55dc600c Author: Andrey Mokhov Date: Thu Jun 2 23:19:21 2016 +0100 Fix path to user settings [skip ci] >--------------------------------------------------------------- d58dabfd7ca07e50374b7c859f81b8ed55dc600c README.md | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/README.md b/README.md index b1da6f7..d99d2b7 100644 --- a/README.md +++ b/README.md @@ -88,8 +88,7 @@ by Shake oracles. #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We -use `./UserSettings.hs` for the same purpose, see -[documentation](doc/user-settings.md). +use `hadrian/UserSettings.hs` for the same purpose, see [documentation](doc/user-settings.md). #### Clean and full rebuild From git at git.haskell.org Fri Oct 27 00:34:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use mv command to move files (374d7b1) Message-ID: <20171027003429.469C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/374d7b124f474ff8bf6b327fb63cb41860f2aef3/ghc >--------------------------------------------------------------- commit 374d7b124f474ff8bf6b327fb63cb41860f2aef3 Author: Andrey Mokhov Date: Mon Jul 17 01:35:18 2017 +0100 Use mv command to move files See #345 >--------------------------------------------------------------- 374d7b124f474ff8bf6b327fb63cb41860f2aef3 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 5f60fc1..e873ddc 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -115,7 +115,7 @@ copyFileUntracked source target = do moveFile :: FilePath -> FilePath -> Action () moveFile source target = do putProgressInfo $ renderAction "Move file" source target - liftIO $ IO.renameFile source target + quietly $ cmd ["mv", source, target] -- | Remove a file that doesn't necessarily exist. removeFile :: FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:34:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unset GHC_PACKAGE_PATH before building. (6200ac8) Message-ID: <20171027003429.94A1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6200ac8589190682a03b32258686a9b452908a9f/ghc >--------------------------------------------------------------- commit 6200ac8589190682a03b32258686a9b452908a9f Author: Andrey Mokhov Date: Sat Jan 9 16:33:13 2016 +0000 Unset GHC_PACKAGE_PATH before building. See #110. [skip ci] >--------------------------------------------------------------- 6200ac8589190682a03b32258686a9b452908a9f .appveyor.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 99196db..9cb8bcb 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,5 +23,6 @@ install: - happy --version build_script: + - unset GHC_PACKAGE_PATH - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress From git at git.haskell.org Fri Oct 27 00:34:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to user settings (157b855) Message-ID: <20171027003429.B473C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/157b855a026ca48b69ba0dba6a473c34f23cfaa4/ghc >--------------------------------------------------------------- commit 157b855a026ca48b69ba0dba6a473c34f23cfaa4 Author: Andrey Mokhov Date: Thu Jun 2 23:27:10 2016 +0100 Fix paths to user settings [skip ci] >--------------------------------------------------------------- 157b855a026ca48b69ba0dba6a473c34f23cfaa4 doc/user-settings.md | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index a5185ad..1dbfd6f 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,8 +1,9 @@ # User settings -You can customise Hadrian by copying the file ./src/UserSettings.hs to -./UserSettings.hs and specifying user build settings in -`./UserSettings.hs`. Here we document currently supported settings. +You can customise Hadrian by copying the file `hadrian/src/UserSettings.hs` to +`hadrian/UserSettings.hs` and overriding the default build settings (if you don't +copy the file your changes will be tracked by `git` and you can accidentally commit +them). Here we document currently supported settings. ## Build directory From git at git.haskell.org Fri Oct 27 00:34:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge build.cabal-new.sh into build.cabal.sh (af6a040) Message-ID: <20171027003433.30E0C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/af6a040742b654d018bfd2fe4dc839a94aa083db/ghc >--------------------------------------------------------------- commit af6a040742b654d018bfd2fe4dc839a94aa083db Author: Herbert Valerio Riedel Date: Fri Jun 3 22:19:36 2016 +0200 Merge build.cabal-new.sh into build.cabal.sh The script now detect the cabal version and uses either the robust and fast 'new-build'-logic (for version 1.24 or later), or falls back to the fragile sandbox-based legacy logic. >--------------------------------------------------------------- af6a040742b654d018bfd2fe4dc839a94aa083db build.cabal-new.sh | 58 ------------------------------------------------------ build.cabal.sh | 50 +++++++++++++++++++++++++++++++++++----------- build.sh | 9 +++++++++ 3 files changed, 48 insertions(+), 69 deletions(-) diff --git a/build.cabal-new.sh b/build.cabal-new.sh deleted file mode 100755 index 65e222a..0000000 --- a/build.cabal-new.sh +++ /dev/null @@ -1,58 +0,0 @@ -#!/usr/bin/env bash - -# This wrapper scripts makes use of cabal 1.24+'s nix-store; -# In order to clean/reset, remove the `dist-newstyle/` folder - -set -euo pipefail - -# readlink on os x, doesn't support -f, to prevent the -# need of installing coreutils (e.g. through brew, just -# for readlink, we use the follownig substitute. -# -# source: http://stackoverflow.com/a/1116890 -function rl { - TARGET_FILE="$1" - - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - - # Iterate down a (possible) chain of symlinks - while [ -L "$TARGET_FILE" ] - do - TARGET_FILE="$(readlink "$TARGET_FILE")" - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - done - - # Compute the canonicalized name by finding the physical path - # for the directory we're in and appending the target file. - PHYS_DIR="$(pwd -P)" - RESULT="$PHYS_DIR/$TARGET_FILE" - echo "$RESULT" -} - -root="$(dirname "$(rl "$0")")" - -mkdir -p "$root/.shake" - -# Notes/Random thoughts: -# -# - if ghc.git had a top-level `cabal.project` file, we could maybe avoid the -# boilerplate above, as we could simply say `cabal exec hadrian` from within -# any GHC folder not shadowed by a nearer shadowing `cabal.project` file. - -pushd "$root/" - -cabal new-build --disable-profiling --disable-documentation -j exe:hadrian - -PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" - -cp -v "$root/dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ - "$root/.shake/build" - -popd - -"$root/.shake/build" \ - --lint \ - --directory "$root/.." \ - "$@" diff --git a/build.cabal.sh b/build.cabal.sh index 08ff972..4a24dac 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -1,5 +1,7 @@ #!/usr/bin/env bash +CABAL=cabal + set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -31,16 +33,42 @@ function rl { absoluteRoot="$(dirname "$(rl "$0")")" cd "$absoluteRoot" -# Initialize sandbox if necessary -if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then - cabal sandbox init - cabal install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared +if ! type "$CABAL" > /dev/null; then + echo "Please make sure 'cabal' is in your PATH" + exit 2 fi -cabal run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" +CABVERSTR=$("$CABAL" --numeric-version) + +CABVER=( ${CABVERSTR//./ } ) + +if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then + # New enough cabal version detected, so + # let's use the superior 'cabal new-build' mode + + # there's no 'cabal new-run' yet, but it's easy to emulate + "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian + PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" + "./dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" + +else + # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals + echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." + + # Initialize sandbox if necessary + if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then + "$CABAL" sandbox init + "$CABAL" install \ + --dependencies-only \ + --disable-library-profiling \ + --disable-shared + fi + + "$CABAL" run hadrian -- \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" +fi diff --git a/build.sh b/build.sh index 24fdc2f..d627c58 100755 --- a/build.sh +++ b/build.sh @@ -30,6 +30,15 @@ function rl { root="$(dirname "$(rl "$0")")" +if type cabal > /dev/null 2>&1; then + CABVERSTR=$(cabal --numeric-version) + CABVER=( ${CABVERSTR//./ } ) + if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then + echo "** Cabal 1.24 or later detected. Please consider using the 'build.cabal.sh' script **" + echo "" + fi +fi + mkdir -p "$root/../_build/hadrian" ghc \ From git at git.haskell.org Fri Oct 27 00:34:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CircleCI script (#364) (076e53f) Message-ID: <20171027003433.62FA53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/076e53fe9637ed6dbc3d4a926b0d87d597666666/ghc >--------------------------------------------------------------- commit 076e53fe9637ed6dbc3d4a926b0d87d597666666 Author: Zhen Zhang Date: Tue Jul 18 01:05:45 2017 +0800 Add CircleCI script (#364) >--------------------------------------------------------------- 076e53fe9637ed6dbc3d4a926b0d87d597666666 circle.yml | 41 +++++++++++++++++++++++++++++++++++++++++ 1 file changed, 41 insertions(+) diff --git a/circle.yml b/circle.yml new file mode 100644 index 0000000..457add7 --- /dev/null +++ b/circle.yml @@ -0,0 +1,41 @@ +machine: + xcode: + version: 8.0 + environment: + MODE: --flavour=quickest --integer-simple + +dependencies: + override: + - brew update + - brew install ghc cabal-install + - cabal update + - cabal install alex happy ansi-terminal mtl shake quickcheck + cache_directories: + - $HOME/.cabal + - $HOME/.ghc + +compile: + override: + # Fetch GHC sources into ./ghc + - git --version + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git clone --depth 1 --recursive git://github.com/ghc/ghc + + - mkdir ghc/hadrian + # move hadrian's .git into ./ghc/hadrian and perform a hard reset in order to regenerate Hadrian files + - mv .git ghc/hadrian + # NOTE: we must write them in the same line because each line + # in CircleCI is a separate process, thus you can't "cd" for the other lines + - cd ghc/hadrian; git reset --hard HEAD + + # XXX: export PATH doesn't work well either, so we use inline env + # Self test + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh selftest + + # Build GHC + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + +test: + override: + # Test GHC binary + - ghc/inplace/bin/ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:34:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move chunksOfSize to Settings/Builders/Ar.hs, add comments. (5e3f91f) Message-ID: <20171027003433.907413A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e3f91f9d050c91f8fd842b9548093c0d8d8e532/ghc >--------------------------------------------------------------- commit 5e3f91f9d050c91f8fd842b9548093c0d8d8e532 Author: Andrey Mokhov Date: Sat Jan 9 16:57:49 2016 +0000 Move chunksOfSize to Settings/Builders/Ar.hs, add comments. See #130. [skip ci] >--------------------------------------------------------------- 5e3f91f9d050c91f8fd842b9548093c0d8d8e532 src/Base.hs | 19 +++---------------- src/Settings/Builders/Ar.hs | 28 ++++++++++++++++++++++++---- 2 files changed, 27 insertions(+), 20 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index fb33907..65a2d1d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,9 +22,9 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, renderBox, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, replaceEq, quote, chunksOfSize, - replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), - versionToInt, removeFileIfExists, removeDirectoryIfExists + bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, + decodeModule, encodeModule, unifyPath, (-/-), versionToInt, + removeFileIfExists, removeDirectoryIfExists ) where import Control.Applicative @@ -90,19 +90,6 @@ replaceSeparators = replaceWhen isPathSeparator replaceWhen :: (a -> Bool) -> a -> [a] -> [a] replaceWhen p to = map (\from -> if p from then to else from) --- | @chunksOfSize size strings@ splits a given list of strings into chunks not --- exceeding the given @size at . -chunksOfSize :: Int -> [String] -> [[String]] -chunksOfSize _ [] = [] -chunksOfSize size strings = reverse chunk : chunksOfSize size rest - where - (chunk, rest) = go [] 0 strings - go res _ [] = (res, []) - go res chunkSize (s:ss) = - if newSize > size then (res, s:ss) else go (s:res) newSize ss - where - newSize = chunkSize + length s - -- | Add quotes to a String quote :: String -> String quote s = "\"" ++ s ++ "\"" diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 18ce802..86f4310 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -5,6 +5,7 @@ import Expression import Oracles import Predicates (builder) +-- | Default arguments for 'Ar' builder arBuilderArgs :: Args arBuilderArgs = builder Ar ? mconcat [ arg "q" , arg =<< getOutput @@ -15,10 +16,15 @@ arBuilderArgs = builder Ar ? mconcat [ arg "q" arFlagsCount :: Int arFlagsCount = 2 --- Ar needs to be invoked in a special way: we pass the list of files to be --- archived via a temporary file as otherwise Ar (or rather Windows command --- line) chokes up. Alternatively, we split argument list into chunks and call --- ar multiple times (when passing files via a separate file is not supported). +-- | Invoke 'Ar' builder given a path to it and a list of arguments. Take care +-- not to exceed the limit on command line length, which differs across +-- supported operating systems (see 'cmdLineLengthLimit'). 'Ar' needs to be +-- handled in a special way because we sometimes need to archive __a lot__ of +-- files (in Cabal package, for example, command line length can reach 2MB!). +-- To work around the limit on the command line length we pass the list of files +-- to be archived via a temporary file, or alternatively, we split argument list +-- into chunks and call 'Ar' multiple times (when passing arguments via a +-- temporary file is not supported). arCmd :: FilePath -> [String] -> Action () arCmd path argList = do arSupportsAtFile <- flag ArSupportsAtFile @@ -38,3 +44,17 @@ useSuccessiveInvocations path flagArgs fileArgs = do maxChunk <- cmdLineLengthLimit forM_ (chunksOfSize maxChunk fileArgs) $ \argsChunk -> unit . cmd [path] $ flagArgs ++ argsChunk + +-- | @chunksOfSize size strings@ splits a given list of strings into chunks not +-- exceeding the given @size at . +chunksOfSize :: Int -> [String] -> [[String]] +chunksOfSize _ [] = [] +chunksOfSize size strings = reverse chunk : chunksOfSize size rest + where + (chunk, rest) = go [] 0 strings + go res _ [] = (res, []) + go res chunkSize (s:ss) = + if newSize > size then (res, s:ss) else go (s:res) newSize ss + where + newSize = chunkSize + length s + From git at git.haskell.org Fri Oct 27 00:35:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change default colours to fit both B-on-W and W-on-B terminals (1ff9ead) Message-ID: <20171027003503.1A8B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ff9eadbf2daee253e62994dd0717c7f016f1548/ghc >--------------------------------------------------------------- commit 1ff9eadbf2daee253e62994dd0717c7f016f1548 Author: Andrey Mokhov Date: Sun Jun 12 19:58:12 2016 +0100 Change default colours to fit both B-on-W and W-on-B terminals See #263. >--------------------------------------------------------------- 1ff9eadbf2daee253e62994dd0717c7f016f1548 src/UserSettings.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 588f196..23380ce 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -102,8 +102,8 @@ verboseCommands = return False -- | Customise build progress messages (e.g. executing a build command). putBuild :: String -> Action () -putBuild = putColoured Vivid White +putBuild = putColoured Dull Magenta -- | Customise build success messages (e.g. a package is built successfully). putSuccess :: String -> Action () -putSuccess = putColoured Vivid Green +putSuccess = putColoured Dull Green From git at git.haskell.org Fri Oct 27 00:35:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing source Settings.Builders.Common (1ad387d) Message-ID: <20171027003504.3FECE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ad387d0ac1af354fff93b384251fab482eee49d/ghc >--------------------------------------------------------------- commit 1ad387d0ac1af354fff93b384251fab482eee49d Author: Andrey Mokhov Date: Sat Jan 9 20:21:27 2016 +0000 Add missing source Settings.Builders.Common [skip ci] >--------------------------------------------------------------- 1ad387d0ac1af354fff93b384251fab482eee49d shaking-up-ghc.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index a5b4c57..9c40f46 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -43,6 +43,7 @@ executable ghc-shake , Rules.Dependencies , Rules.Documentation , Rules.Generate + , Rules.Generators.Common , Rules.Generators.ConfigHs , Rules.Generators.GhcAutoconfH , Rules.Generators.GhcBootPlatformH From git at git.haskell.org Fri Oct 27 00:35:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make OS X build faster and Add GHC 8.0.2 build on Travis CI (#370) (b7fff3b) Message-ID: <20171027003504.2D6CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b7fff3b6749a01a2ad486bff68e6e0fdeab338e4/ghc >--------------------------------------------------------------- commit b7fff3b6749a01a2ad486bff68e6e0fdeab338e4 Author: Zhen Zhang Date: Wed Jul 19 22:44:42 2017 +0800 Make OS X build faster and Add GHC 8.0.2 build on Travis CI (#370) >--------------------------------------------------------------- b7fff3b6749a01a2ad486bff68e6e0fdeab338e4 .travis.yml | 58 +++++++++++++++++++++++++++++++++++++++++++++------------- 1 file changed, 45 insertions(+), 13 deletions(-) diff --git a/.travis.yml b/.travis.yml index dd6af26..d85291a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,9 +1,36 @@ sudo: true - +language: haskell matrix: include: - os: linux env: MODE="--flavour=quickest" + compiler: "GHC 8.0.2" + addons: + apt: + packages: + - ghc-8.0.2 + - cabal-install-2.0 + - zlib1g-dev + sources: hvr-ghc + + before_install: + - PATH="/opt/ghc/8.0.2/bin:$PATH" + - PATH="/opt/cabal/2.0/bin:$PATH" + + script: + # Run internal Hadrian tests + - ./build.sh selftest + + # Build GHC + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + + # Test GHC binary + - cd .. + - inplace/bin/ghc-stage2 -e 1+2 + + - os: linux + env: MODE="--flavour=quickest" + compiler: "GHC 7.10.3" addons: apt: packages: @@ -11,17 +38,33 @@ matrix: - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc + before_install: - PATH="/opt/ghc/7.10.3/bin:$PATH" - PATH="/opt/cabal/1.22/bin:$PATH" + script: + # Run internal Hadrian tests + - ./build.sh selftest + + # Build GHC + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + + # Test GHC binary + - cd .. + - inplace/bin/ghc-stage2 -e 1+2 + - os: osx osx_image: xcode8 env: MODE="--flavour=quickest --integer-simple" before_install: - brew update - brew install ghc cabal-install - - + + script: + # Due to timeout limit of OS X build on Travis CI, + # we will ignore selftest and build only stage1 + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 install: # Add Cabal to PATH @@ -50,17 +93,6 @@ install: - cd ghc/hadrian - git reset --hard HEAD -script: - # Run internal Hadrian tests - - ./build.sh selftest - - # Build GHC - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- - - # Test GHC binary - - cd .. - - inplace/bin/ghc-stage2 -e 1+2 - cache: directories: - $HOME/.cabal From git at git.haskell.org Fri Oct 27 00:35:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build stage1 GHC only to fit into OS X time limit on Travis. (db5dce0) Message-ID: <20171027003508.21C6C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db5dce0cb5d252e1a0576ec9731a758b98385fdc/ghc >--------------------------------------------------------------- commit db5dce0cb5d252e1a0576ec9731a758b98385fdc Author: Andrey Mokhov Date: Sat Jan 9 20:23:41 2016 +0000 Build stage1 GHC only to fit into OS X time limit on Travis. >--------------------------------------------------------------- db5dce0cb5d252e1a0576ec9731a758b98385fdc .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index ca51b6f..3c5f522 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - cabal update - os: osx - env: TARGET=libraries/base/stage1/build/libHSbase-4.9.0.0.a + env: TARGET=inplace/bin/ghc-stage1.exe before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Fri Oct 27 00:35:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (599381f) Message-ID: <20171027003508.1CA7C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/599381f0fda1ea8fbae64b748b7b09727189f53b/ghc >--------------------------------------------------------------- commit 599381f0fda1ea8fbae64b748b7b09727189f53b Author: Andrey Mokhov Date: Wed Jul 19 16:03:35 2017 +0100 Minor revision >--------------------------------------------------------------- 599381f0fda1ea8fbae64b748b7b09727189f53b src/Oracles/Config/Setting.hs | 20 ++++++++++---------- src/Rules/Install.hs | 9 +++++---- src/Settings/Path.hs | 12 ++++++------ 3 files changed, 21 insertions(+), 20 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index c4ed10e..1bf9186 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -53,19 +53,18 @@ data Setting = BuildArch | IconvIncludeDir | IconvLibDir | CursesLibDir - -- Paths to where GHC is installed - -- ref: mk/install.mk + -- Paths to where GHC is installed (ref: mk/install.mk) | InstallPrefix | InstallBinDir | InstallLibDir | InstallDataRootDir - -- "install" utility + -- Command lines for invoking the @install@ utility | Install | InstallData | InstallProgram | InstallScript | InstallDir - -- symbolic link + -- Command line for creating a symbolic link | LnS data SettingList = ConfCcArgs Stage @@ -202,9 +201,10 @@ cmdLineLengthLimit = do -- On all other systems, we try this: _ -> 4194304 -- Cabal library needs a bit more than 2MB! --- | On Windows we normally want to make a relocatable bindist, --- to we ignore flags like libdir --- ref: mk/config.mk.in:232 +-- ref: https://ghc.haskell.org/trac/ghc/wiki/Building/Installing#HowGHCfindsitsfiles +-- | On Windows we normally build a relocatable installation, which assumes that +-- the library directory @libdir@ is in a fixed location relative to the GHC +-- binary, namely @../lib at . relocatableBuild :: Action Bool relocatableBuild = windowsHost @@ -213,10 +213,10 @@ installDocDir = do version <- setting ProjectVersion (-/- ("doc/ghc-" ++ version)) <$> setting InstallDataRootDir --- | Unix: override libdir and datadir to put ghc-specific stuff in --- a subdirectory with the version number included. -- ref: mk/install.mk:101 -- TODO: CroosCompilePrefix +-- | Unix: override @libdir@ and @datadir@ to put GHC-specific files in a +-- subdirectory with the version number included. installGhcLibDir :: Action String installGhcLibDir = do r <- relocatableBuild @@ -224,4 +224,4 @@ installGhcLibDir = do if r then return libdir else do v <- setting ProjectVersion - return (libdir -/- ("ghc-" ++ v)) + return $ libdir -/- ("ghc-" ++ v) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 525746b..77e340e 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -128,6 +128,7 @@ withLatestBuildStage pkg m = do Nothing -> return () -- ref: rules/manual-package-conf.mk +-- TODO: Should we use a temporary file instead of pkgConfInstallPath? -- | Install @package.conf.install@ for each package. Note that it will be -- recreated each time. installPackageConf :: Action () @@ -161,7 +162,7 @@ installPackages = do -- Install RTS let rtsDir = destDir ++ ghcLibDir -/- "rts" installDirectory rtsDir - ways <- interpretInContext (vanillaContext Stage1 rts) getRtsWays + ways <- interpretInContext (vanillaContext Stage1 rts) getRtsWays rtsLibs <- mapM pkgLibraryFile $ map (Context Stage1 rts) ways ffiLibs <- sequence $ map rtsLibffiLibrary ways @@ -183,14 +184,14 @@ installPackages = do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg - top <- interpretInContext context getTopDirectory + top <- topDirectory let installDistDir = top -/- buildPath context buildPackage stage pkg docDir <- installDocDir ghclibDir <- installGhcLibDir -- Copy over packages - strip <- stripCmdPath context + strip <- stripCmdPath ways <- interpretInContext context getLibraryWays let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" <.> exe -- HACK? need [ghcCabalInplace] @@ -230,7 +231,7 @@ installPackages = do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg - top <- interpretInContext context getTopDirectory + top <- topDirectory let installDistDir = top -/- buildPath context -- TODO: better reference to the built inplace binary path let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 1b0dc13..0be1838 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -14,8 +14,8 @@ import Context import Expression import GHC import Oracles.PackageData -import Oracles.Config.Setting (setting, Setting(..)) -import Oracles.Path (getTopDirectory) +import Oracles.Config.Setting +import Oracles.Path import UserSettings -- | Path to the directory containing the Shake database and other auxiliary @@ -202,12 +202,12 @@ inplaceInstallPath pkg ghcSplitPath :: FilePath ghcSplitPath = inplaceLibBinPath -/- "ghc-split" --- | Command line tool for stripping -- ref: mk/config.mk -stripCmdPath :: Context -> Action FilePath -stripCmdPath ctx = do +-- | Command line tool for stripping. +stripCmdPath :: Action FilePath +stripCmdPath = do targetPlatform <- setting TargetPlatform - top <- interpretInContext ctx getTopDirectory + top <- topDirectory case targetPlatform of "x86_64-unknown-mingw32" -> return (top -/- "inplace/mingw/bin/strip.exe") From git at git.haskell.org Fri Oct 27 00:35:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add actions copyDirectoryContent and runBuilderWith (e592fb1) Message-ID: <20171027003506.98A8E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e592fb1f438317d4be4893bf9b07b098ffb28085/ghc >--------------------------------------------------------------- commit e592fb1f438317d4be4893bf9b07b098ffb28085 Author: Kai Harries Date: Fri Jun 17 17:23:54 2016 +0200 Add actions copyDirectoryContent and runBuilderWith These new functions will be helpful when implementing the 'sdist' and 'install' rules. >--------------------------------------------------------------- e592fb1f438317d4be4893bf9b07b098ffb28085 src/Rules/Actions.hs | 26 ++++++++++++++++++++++---- 1 file changed, 22 insertions(+), 4 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 6b6c352..8fbe6c0 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,12 +1,14 @@ module Rules.Actions ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, - removeFile, copyDirectory, createDirectory, moveDirectory, removeDirectory, - applyPatch, runBuilder, makeExecutable, renderProgram, renderLibrary + removeFile, copyDirectory, copyDirectoryContent, createDirectory, + moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, + makeExecutable, renderProgram, renderLibrary ) where import qualified System.Directory as IO import qualified System.IO as IO import qualified Control.Exception.Base as IO +import qualified System.Directory.Extra as X import Base import CmdLineFlag @@ -126,6 +128,18 @@ copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd cmdEcho ["cp", "-r", source, target] +-- | Copy the content of the source directory into the target directory. Only +-- the files and directories for which the predicate returns True are copied. +copyDirectoryContent :: (FilePath -> IO Bool) -> FilePath -> FilePath -> Action () +copyDirectoryContent test source target = do + putProgressInfo $ renderAction "Copy directory" source target + liftIO $ X.listFilesInside test' source >>= mapM_ cp + where + target' a = target -/- fromJust (stripPrefix source a) + test' a = ifM (test a) (mkdir a >> return True) (return False) + mkdir a = IO.createDirectoryIfMissing True $ target' a + cp a = whenM (test a) $ IO.copyFile a $ target' a + -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do @@ -152,12 +166,16 @@ applyPatch dir patch = do quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () -runBuilder builder args = do +runBuilder = + runBuilderWith [] + +runBuilderWith :: [CmdOption] -> Builder -> [String] -> Action () +runBuilderWith options builder args = do needBuilder builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ show builder ++ note - quietly $ cmd [path] args + quietly $ cmd options [path] args makeExecutable :: FilePath -> Action () makeExecutable file = do From git at git.haskell.org Fri Oct 27 00:35:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop exe extension. (ef6ddf9) Message-ID: <20171027003512.0A1083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef6ddf94b8cd9d3ca0f3054dc163d04996838839/ghc >--------------------------------------------------------------- commit ef6ddf94b8cd9d3ca0f3054dc163d04996838839 Author: Andrey Mokhov Date: Sat Jan 9 20:38:42 2016 +0000 Drop exe extension. >--------------------------------------------------------------- ef6ddf94b8cd9d3ca0f3054dc163d04996838839 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 3c5f522..dd3bd12 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - cabal update - os: osx - env: TARGET=inplace/bin/ghc-stage1.exe + env: TARGET=inplace/bin/ghc-stage1 before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Fri Oct 27 00:35:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an acknowledgement to Zhen Zhang (44b279b) Message-ID: <20171027003512.17C303A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44b279be9b1cc97bcc6cd73d3d0f73de6a7a3149/ghc >--------------------------------------------------------------- commit 44b279be9b1cc97bcc6cd73d3d0f73de6a7a3149 Author: Andrey Mokhov Date: Wed Jul 19 16:17:31 2017 +0100 Add an acknowledgement to Zhen Zhang Fix #371 [skip ci] >--------------------------------------------------------------- 44b279be9b1cc97bcc6cd73d3d0f73de6a7a3149 README.md | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index 8404496..5e49393 100644 --- a/README.md +++ b/README.md @@ -157,9 +157,12 @@ Acknowledgements I started this project as part of my 6-month research visit to Microsoft Research Cambridge, which was funded by Newcastle University, EPSRC, and Microsoft Research. I would like to thank Simon Peyton Jones, Neil Mitchell -and Simon Marlow for kick-starting the project and for their guidance. Last -but not least, big thanks to the project [contributors][contributors], who -helped me endure and enjoy the project. +and Simon Marlow for kick-starting the project and for their guidance. +Zhen Zhang has done fantastic work on Hadrian as part of his Summer of +Haskell 2017 [project](https://summer.haskell.org/ideas.html#hadrian-ghc), +solving a few heavy and long-overdue issues. Last but not least, big thanks +to all other project [contributors][contributors], who helped me endure and +enjoy the project. [ghc]: https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler [shake]: https://github.com/ndmitchell/shake/blob/master/README.md From git at git.haskell.org Fri Oct 27 00:35:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove explicit import of 'System.Directory' (73970d5) Message-ID: <20171027003510.10CD63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73970d51a9d40c79ec8ed2aea4d36b5c3ff723b0/ghc >--------------------------------------------------------------- commit 73970d51a9d40c79ec8ed2aea4d36b5c3ff723b0 Author: Kai Harries Date: Sun Jun 19 09:34:15 2016 +0200 Remove explicit import of 'System.Directory' >--------------------------------------------------------------- 73970d51a9d40c79ec8ed2aea4d36b5c3ff723b0 src/Rules/Actions.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 8fbe6c0..7221441 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -5,10 +5,9 @@ module Rules.Actions ( makeExecutable, renderProgram, renderLibrary ) where -import qualified System.Directory as IO +import qualified System.Directory.Extra as IO import qualified System.IO as IO import qualified Control.Exception.Base as IO -import qualified System.Directory.Extra as X import Base import CmdLineFlag @@ -133,7 +132,7 @@ copyDirectory source target = do copyDirectoryContent :: (FilePath -> IO Bool) -> FilePath -> FilePath -> Action () copyDirectoryContent test source target = do putProgressInfo $ renderAction "Copy directory" source target - liftIO $ X.listFilesInside test' source >>= mapM_ cp + liftIO $ IO.listFilesInside test' source >>= mapM_ cp where target' a = target -/- fromJust (stripPrefix source a) test' a = ifM (test a) (mkdir a >> return True) (return False) From git at git.haskell.org Fri Oct 27 00:35:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove excessive whitespace (787cb4f) Message-ID: <20171027003513.964783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/787cb4f1f82c4928d6a4d0259da6694f3fd0fe64/ghc >--------------------------------------------------------------- commit 787cb4f1f82c4928d6a4d0259da6694f3fd0fe64 Author: Kai Harries Date: Sun Jun 19 09:36:04 2016 +0200 Remove excessive whitespace >--------------------------------------------------------------- 787cb4f1f82c4928d6a4d0259da6694f3fd0fe64 src/Rules/Actions.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 7221441..734cb91 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -165,8 +165,7 @@ applyPatch dir patch = do quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () -runBuilder = - runBuilderWith [] +runBuilder = runBuilderWith [] runBuilderWith :: [CmdOption] -> Builder -> [String] -> Action () runBuilderWith options builder args = do From git at git.haskell.org Fri Oct 27 00:35:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop language in Travis CI config (#372) (2741b3c) Message-ID: <20171027003516.4E0B73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2741b3c419ece51e914bc22e38e18c25476b296b/ghc >--------------------------------------------------------------- commit 2741b3c419ece51e914bc22e38e18c25476b296b Author: Zhen Zhang Date: Thu Jul 20 02:25:36 2017 +0800 Drop language in Travis CI config (#372) >--------------------------------------------------------------- 2741b3c419ece51e914bc22e38e18c25476b296b .travis.yml | 1 - 1 file changed, 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index d85291a..ba67ae3 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,5 +1,4 @@ sudo: true -language: haskell matrix: include: - os: linux From git at git.haskell.org Fri Oct 27 00:35:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't conflict with parallel in the latest Shake, provides a warning free way to be forward and backward compatible with Shake (albeit not pretty) (8efb43d) Message-ID: <20171027003516.62A863A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8efb43dd384111a0f724924507aac59a655b382d/ghc >--------------------------------------------------------------- commit 8efb43dd384111a0f724924507aac59a655b382d Author: Neil Mitchell Date: Sat Jan 9 21:33:02 2016 +0000 Don't conflict with parallel in the latest Shake, provides a warning free way to be forward and backward compatible with Shake (albeit not pretty) >--------------------------------------------------------------- 8efb43dd384111a0f724924507aac59a655b382d src/GHC.hs | 4 ++-- src/Way.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index f967263..1574ec3 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,7 +4,7 @@ module GHC ( deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, + integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, @@ -26,7 +26,7 @@ defaultKnownPackages = , deepseq, deriveConstants, directory, dllSplit, filepath, genapply , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp - , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty + , integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time , touchy, transformers, unlit, unix, win32, xhtml ] diff --git a/src/Way.hs b/src/Way.hs index 3b1f6c0..94a3bcc 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, - vanilla, profiling, logging, parallel, granSim, + vanilla, profiling, logging, Way.parallel, granSim, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, From git at git.haskell.org Fri Oct 27 00:35:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Quickest build flavour (d7c80c8) Message-ID: <20171027003517.5062F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d7c80c8303b7bc4596c9d04b569c365128cfd958/ghc >--------------------------------------------------------------- commit d7c80c8303b7bc4596c9d04b569c365128cfd958 Author: Andrey Mokhov Date: Mon Jun 20 03:07:24 2016 +0100 Add Quickest build flavour See #259, #268. >--------------------------------------------------------------- d7c80c8303b7bc4596c9d04b569c365128cfd958 hadrian.cabal | 1 + src/CmdLineFlag.hs | 11 ++++++----- src/Settings/Args.hs | 7 +++++-- src/Settings/Flavours/Quickest.hs | 16 ++++++++++++++++ src/Settings/Ways.hs | 7 +++++-- 5 files changed, 33 insertions(+), 9 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 5ffcb65..2b773ee 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -88,6 +88,7 @@ executable hadrian , Settings.Builders.Tar , Settings.Default , Settings.Flavours.Quick + , Settings.Flavours.Quickest , Settings.Packages , Settings.Packages.Base , Settings.Packages.Compiler diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 10c39f2..df3af5b 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -21,7 +21,7 @@ data Untracked = Untracked , splitObjects :: Bool } deriving (Eq, Show) -data Flavour = Default | Quick deriving (Eq, Show) +data Flavour = Default | Quick | Quickest deriving (Eq, Show) data ProgressColour = Never | Auto | Always deriving (Eq, Show) data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) @@ -43,9 +43,10 @@ readFlavour ms = maybe (Left "Cannot parse flavour") (Right . set) (go =<< lower <$> ms) where go :: String -> Maybe Flavour - go "default" = Just Default - go "quick" = Just Quick - go _ = Nothing + go "default" = Just Default + go "quick" = Just Quick + go "quickest" = Just Quickest + go _ = Nothing set :: Flavour -> Untracked -> Untracked set flag flags = flags { flavour = flag } @@ -83,7 +84,7 @@ readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") - "Build flavour (Default or Quick)." + "Build flavour (Default, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 18079a2..2ff071a 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -20,6 +20,7 @@ import Settings.Builders.Ld import Settings.Builders.Make import Settings.Builders.Tar import Settings.Flavours.Quick +import Settings.Flavours.Quickest import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Directory @@ -88,5 +89,7 @@ defaultPackageArgs = mconcat , unlitPackageArgs ] flavourArgs :: Args -flavourArgs = mconcat - [ cmdFlavour == Quick ? quickFlavourArgs ] +flavourArgs = case cmdFlavour of + Default -> mempty + Quick -> quickFlavourArgs + Quickest -> quickestFlavourArgs diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs new file mode 100644 index 0000000..cc1de6b --- /dev/null +++ b/src/Settings/Flavours/Quickest.hs @@ -0,0 +1,16 @@ +module Settings.Flavours.Quickest (quickestFlavourArgs, quickestFlavourWays) where + +import Context +import GHC +import Predicate + +optimise :: Context -> Bool +optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] + +quickestFlavourArgs :: Args +quickestFlavourArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O" else arg "-O0" + +quickestFlavourWays :: Ways +quickestFlavourWays = remove [profiling] diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 79dd164..95301e1 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -5,6 +5,7 @@ import CmdLineFlag import Oracles.Config.Flag import Predicate import Settings.Flavours.Quick +import Settings.Flavours.Quickest import UserSettings -- | Combine default library ways with user modifications. @@ -29,8 +30,10 @@ defaultLibraryWays = mconcat , notStage0 ? platformSupportsSharedLibs ? append [dynamic] ] flavourLibraryWays :: Ways -flavourLibraryWays = mconcat - [ cmdFlavour == Quick ? quickFlavourWays ] +flavourLibraryWays = case cmdFlavour of + Default -> mempty + Quick -> quickFlavourWays + Quickest -> quickestFlavourWays defaultRtsWays :: Ways defaultRtsWays = do From git at git.haskell.org Fri Oct 27 00:35:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comments only (58e2120) Message-ID: <20171027003520.55CDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/58e21200a04bc17f5cb7c8fb8dbd36cecc03d36a/ghc >--------------------------------------------------------------- commit 58e21200a04bc17f5cb7c8fb8dbd36cecc03d36a Author: Andrey Mokhov Date: Wed Jul 19 20:17:07 2017 +0100 Comments only See #345 >--------------------------------------------------------------- 58e21200a04bc17f5cb7c8fb8dbd36cecc03d36a src/UserSettings.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 4398700..a3a65ab 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -43,10 +43,11 @@ putBuild = putColoured Dull Magenta putSuccess :: String -> Action () putSuccess = putColoured Dull Green --- | Path to the GHC install destination --- It is by default empty, representing the root of file system, --- or it might be a directory. --- It is usually used with @prefix@, like @/usr/local@ +-- | Path to the GHC install destination. It is empty by default, which +-- corresponds to the root of the file system. You can replace it by a specific +-- directory. Make sure you use correct absolute path on Windows, e.g. "C:/path". +-- The destination directory is used with a @prefix@, commonly @/usr/local@, +-- i.e. GHC is installed into "C:/path/usr/local" for the above example. defaultDestDir :: FilePath defaultDestDir = "" From git at git.haskell.org Fri Oct 27 00:35:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a .ghci file, useful for experimenting and using ghcid (4444fa4) Message-ID: <20171027003520.8795D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4444fa437e6a36908414924a707ff538841f17a1/ghc >--------------------------------------------------------------- commit 4444fa437e6a36908414924a707ff538841f17a1 Author: Neil Mitchell Date: Sat Jan 9 21:33:21 2016 +0000 Add a .ghci file, useful for experimenting and using ghcid >--------------------------------------------------------------- 4444fa437e6a36908414924a707ff538841f17a1 .ghci | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.ghci b/.ghci new file mode 100644 index 0000000..1fe85b3 --- /dev/null +++ b/.ghci @@ -0,0 +1,2 @@ +:set -Wall -isrc +:load Main From git at git.haskell.org Fri Oct 27 00:35:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Quickest flavour on Appveyor (3a04d34) Message-ID: <20171027003521.040773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3a04d3425a06ff9ad62eb71d20ddd7cce26ae0a0/ghc >--------------------------------------------------------------- commit 3a04d3425a06ff9ad62eb71d20ddd7cce26ae0a0 Author: Andrey Mokhov Date: Mon Jun 20 03:08:10 2016 +0100 Use Quickest flavour on Appveyor See #259, #268. >--------------------------------------------------------------- 3a04d3425a06ff9ad62eb71d20ddd7cce26ae0a0 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index bb5620e..e4d7d52 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:35:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor getSingleton to avoid using list, otherwise an import of Data.Extra.List causes shadowing issues (dbe8c1e) Message-ID: <20171027003524.A74C53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dbe8c1e0f387f98c7edaaaf2f5dfda1ed25a9b2a/ghc >--------------------------------------------------------------- commit dbe8c1e0f387f98c7edaaaf2f5dfda1ed25a9b2a Author: Neil Mitchell Date: Sat Jan 9 21:45:53 2016 +0000 Refactor getSingleton to avoid using list, otherwise an import of Data.Extra.List causes shadowing issues >--------------------------------------------------------------- dbe8c1e0f387f98c7edaaaf2f5dfda1ed25a9b2a src/Expression.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 6e2a225..932ed80 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -204,7 +204,7 @@ getOutput = do getSingleton :: Expr [a] -> String -> Expr a getSingleton expr msg = do - list <- expr - case list of + xs <- expr + case xs of [res] -> return res _ -> lift $ putError msg From git at git.haskell.org Fri Oct 27 00:35:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Need all top-level dependencies in one go for better parallelism. Minor revision. (145999c) Message-ID: <20171027003524.B1BFD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/145999cfde98ff857abee0c4abd96ebc637ca04b/ghc >--------------------------------------------------------------- commit 145999cfde98ff857abee0c4abd96ebc637ca04b Author: Andrey Mokhov Date: Thu Jul 20 00:28:33 2017 +0100 Need all top-level dependencies in one go for better parallelism. Minor revision. See #200. >--------------------------------------------------------------- 145999cfde98ff857abee0c4abd96ebc637ca04b src/Oracles/Dependencies.hs | 38 +++++++++++++++++---------------- src/Rules.hs | 51 ++++++++++++++++++++++----------------------- src/Rules/Compile.hs | 2 +- src/Rules/Install.hs | 6 +++--- src/Rules/Program.hs | 4 ++-- 5 files changed, 51 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 145999cfde98ff857abee0c4abd96ebc637ca04b From git at git.haskell.org Fri Oct 27 00:35:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Quick flavour (6d6834a) Message-ID: <20171027003524.E22F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d6834a6abebaff0d4aa60e615a027d68ed964d9/ghc >--------------------------------------------------------------- commit 6d6834a6abebaff0d4aa60e615a027d68ed964d9 Author: Andrey Mokhov Date: Mon Jun 20 03:08:45 2016 +0100 Fix Quick flavour See #259, #268. >--------------------------------------------------------------- 6d6834a6abebaff0d4aa60e615a027d68ed964d9 src/Settings/Flavours/Quick.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index e3f0a5d..81fe178 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -1,9 +1,17 @@ module Settings.Flavours.Quick (quickFlavourArgs, quickFlavourWays) where +import Context +import GHC import Predicate +optimise :: Context -> Bool +optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] + || stage == Stage1 && isLibrary package + quickFlavourArgs :: Args -quickFlavourArgs = builder Ghc ? arg "-O0" +quickFlavourArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O" else arg "-O0" quickFlavourWays :: Ways quickFlavourWays = remove [profiling] From git at git.haskell.org Fri Oct 27 00:35:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rewrite digest, avoid using list (to avoid a shadow warning), and avoid using head (partial function) (02ec50d) Message-ID: <20171027003529.63A8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02ec50d957a3ebd736ccb631795489eec971d528/ghc >--------------------------------------------------------------- commit 02ec50d957a3ebd736ccb631795489eec971d528 Author: Neil Mitchell Date: Sat Jan 9 21:46:36 2016 +0000 Rewrite digest, avoid using list (to avoid a shadow warning), and avoid using head (partial function) >--------------------------------------------------------------- 02ec50d957a3ebd736ccb631795489eec971d528 src/Rules/Actions.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 51f7625..338bec3 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -132,7 +132,6 @@ putInfo (Target.Target {..}) = putBuild $ renderBox where stageInfo = if isStaged builder then "" else "stage = " ++ show stage ++ ", " wayInfo = if way == vanilla then "" else ", way = " ++ show way - digest list = case list of - [] -> "none" - [x] -> x - xs -> head xs ++ " (and " ++ show (length xs - 1) ++ " more)" + digest [] = "none" + digest [x] = x + digest (x:xs) = x ++ " (and " ++ show (length xs) ++ " more)" From git at git.haskell.org Fri Oct 27 00:35:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Quickest flavour on Mac OSX (1f1a7b3) Message-ID: <20171027003529.918ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1f1a7b3297c7a4747b5e7a89ae47335ea8d79a56/ghc >--------------------------------------------------------------- commit 1f1a7b3297c7a4747b5e7a89ae47335ea8d79a56 Author: Andrey Mokhov Date: Tue Jun 21 01:22:18 2016 +0100 Use Quickest flavour on Mac OSX See #259 >--------------------------------------------------------------- 1f1a7b3297c7a4747b5e7a89ae47335ea8d79a56 .travis.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index 18ede46..b066e89 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quick TARGET= addons: apt: packages: @@ -20,7 +20,7 @@ matrix: - cabal install alex happy - os: osx - env: TARGET= + env: FLAVOUR=quickest TARGET= before_install: - brew update - brew install ghc cabal-install @@ -59,7 +59,7 @@ install: script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=$FLAVOUR $TARGET - ./ghc/inplace/bin/ghc-stage2 -e 1+2 cache: From git at git.haskell.org Fri Oct 27 00:35:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix builder dependencies on generated files (#363) (d9c97e8) Message-ID: <20171027003529.798F73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9c97e8f96f482fe7d84e01d61682e82e1edad59/ghc >--------------------------------------------------------------- commit d9c97e8f96f482fe7d84e01d61682e82e1edad59 Author: Zhen Zhang Date: Fri Jul 21 01:14:15 2017 +0800 Fix builder dependencies on generated files (#363) >--------------------------------------------------------------- d9c97e8f96f482fe7d84e01d61682e82e1edad59 src/Rules.hs | 1 - src/Rules/Generate.hs | 14 +------------- src/Rules/Program.hs | 4 +++- src/Rules/Test.hs | 3 ++- src/Settings/Builders/GhcCabal.hs | 4 +++- src/Settings/Builders/Hsc2Hs.hs | 7 ++----- src/Settings/Path.hs | 17 ++++++++++++++++- src/Util.hs | 1 + 8 files changed, 28 insertions(+), 23 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 69fcaee..359d3e9 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -29,7 +29,6 @@ allStages = [minBound ..] -- or Stage1Only targets topLevelTargets :: Rules () topLevelTargets = action $ do - need $ Rules.Generate.inplaceLibCopyTargets let libraryPackages = filter isLibrary (knownPackages \\ [rts, libffi]) need =<< if stage1Only then do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 3507027..80eca91 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( isGeneratedCFile, isGeneratedCmmFile, generatePackageCode, generateRules, - copyRules, includesDependencies, generatedDependencies, inplaceLibCopyTargets + copyRules, includesDependencies, generatedDependencies ) where import Base @@ -24,18 +24,6 @@ import Target import UserSettings import Util --- | Files that need to be copied over to inplace/lib --- ref: ghc/ghc.mk:142 --- ref: driver/ghc.mk --- ref: utils/hsc2hs/ghc.mk:35 -inplaceLibCopyTargets :: [FilePath] -inplaceLibCopyTargets = map (inplaceLibPath -/-) - [ "ghc-usage.txt" - , "ghci-usage.txt" - , "platformConstants" - , "settings" - , "template-hsc.h" ] - primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 846c694..710829b 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -14,7 +14,7 @@ import Oracles.Path (topDirectory) import Rules.Wrappers (WrappedBinary(..), Wrapper, inplaceWrappers) import Settings import Settings.Path (buildPath, inplaceLibBinPath, rtsContext, objectPath, - inplaceLibPath, inplaceBinPath) + inplaceLibPath, inplaceBinPath, inplaceLibCopyTargets) import Target import UserSettings import Util @@ -28,6 +28,8 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do buildPath context -/- programName context <.> exe %> buildBinaryAndWrapper rs context + when (package == ghc) $ want inplaceLibCopyTargets + -- Rules for programs built in install directories when (stage == Stage0 || package == ghc) $ do -- Some binaries in inplace/bin are wrapped diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index fc059ab..93e97c2 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -10,6 +10,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Path import Settings +import Settings.Path (inplaceLibCopyTargets) import Target import Util @@ -17,7 +18,7 @@ import Util testRules :: Rules () testRules = do "validate" ~> do - need $ Rules.Generate.inplaceLibCopyTargets + need inplaceLibCopyTargets needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 18816e1..33a7b99 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -4,7 +4,7 @@ module Settings.Builders.GhcCabal ( import Context import Flavour -import Settings.Builders.Common +import Settings.Builders.Common hiding (package) import Util ghcCabalBuilderArgs :: Args @@ -12,6 +12,8 @@ ghcCabalBuilderArgs = builder GhcCabal ? do verbosity <- lift $ getVerbosity top <- getTopDirectory context <- getContext + when (package context /= deriveConstants) $ + lift (need inplaceLibCopyTargets) mconcat [ arg "configure" , arg =<< getPackagePath , arg $ top -/- buildPath context diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index ba98654..a9ec9c5 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -1,9 +1,7 @@ module Settings.Builders.Hsc2Hs (hsc2hsBuilderArgs) where import Settings.Builders.Common - -templateHsc :: FilePath -templateHsc = "inplace/lib/template-hsc.h" +import Settings.Path (templateHscPath) hsc2hsBuilderArgs :: Args hsc2hsBuilderArgs = builder Hsc2Hs ? do @@ -20,7 +18,6 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do version <- if stage == Stage0 then lift ghcCanonVersion else getSetting ProjectVersionInt - lift $ need [templateHsc] mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" @@ -33,7 +30,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) , arg $ "--cflag=-D__GLASGOW_HASKELL__=" ++ version - , arg $ "--template=" ++ top -/- templateHsc + , arg $ "--template=" ++ top -/- templateHscPath , arg $ "-I" ++ top -/- "inplace/lib/include/" , arg =<< getInput , arg "-o", arg =<< getOutput ] diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 0be1838..c8153bf 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -6,7 +6,7 @@ module Settings.Path ( pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, inplaceInstallPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, - pkgSetupConfigFile + pkgSetupConfigFile, inplaceLibCopyTargets, templateHscPath ) where import Base @@ -214,3 +214,18 @@ stripCmdPath = do "arm-unknown-linux" -> return ":" -- HACK: from the make-based system, see the ref above _ -> return "strip" + +-- | Files that need to be copied over to inplace/lib +-- ref: ghc/ghc.mk:142 +-- ref: driver/ghc.mk +-- ref: utils/hsc2hs/ghc.mk:35 +inplaceLibCopyTargets :: [FilePath] +inplaceLibCopyTargets = map (inplaceLibPath -/-) + [ "ghc-usage.txt" + , "ghci-usage.txt" + , "platformConstants" + , "settings" + , "template-hsc.h" ] + +templateHscPath :: FilePath +templateHscPath = "inplace/lib/template-hsc.h" diff --git a/src/Util.hs b/src/Util.hs index 37743c0..7ea567e 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -22,6 +22,7 @@ import Oracles.Path import Oracles.Config.Setting import Settings import Settings.Builders.Ar +import Settings.Path import Target import UserSettings From git at git.haskell.org Fri Oct 27 00:35:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid using Traversable to get at forM (eda5882) Message-ID: <20171027003533.676633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eda5882a83ad353eb636b4249439095d237e331f/ghc >--------------------------------------------------------------- commit eda5882a83ad353eb636b4249439095d237e331f Author: Neil Mitchell Date: Sat Jan 9 21:46:52 2016 +0000 Avoid using Traversable to get at forM >--------------------------------------------------------------- eda5882a83ad353eb636b4249439095d237e331f src/Rules.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index fe8242b..7af1556 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -2,7 +2,6 @@ module Rules (generateTargets, packageRules) where import Base import Data.Foldable -import Data.Traversable import Expression import GHC import Rules.Generate @@ -25,7 +24,7 @@ targetsForStage :: Stage -> Action [String] targetsForStage stage = do pkgs <- interpretWithStage stage getPackages let libPkgs = filter isLibrary pkgs \\ [rts, libffi] - libTargets <- fmap concat . for libPkgs $ \pkg -> do + libTargets <- fmap concat . forM libPkgs $ \pkg -> do let target = PartialTarget stage pkg needHaddock <- interpretPartial target buildHaddock return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] From git at git.haskell.org Fri Oct 27 00:35:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix validate's executable dependency (#375) (2555a5f) Message-ID: <20171027003533.E30AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2555a5f03040aaf56e44e32c8b133cc5ead87616/ghc >--------------------------------------------------------------- commit 2555a5f03040aaf56e44e32c8b133cc5ead87616 Author: Zhen Zhang Date: Sun Jul 23 20:37:29 2017 +0800 Fix validate's executable dependency (#375) >--------------------------------------------------------------- 2555a5f03040aaf56e44e32c8b133cc5ead87616 src/Rules/Test.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 93e97c2..0f46f6c 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -22,6 +22,8 @@ testRules = do needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc + needBuilder Hsc2Hs + need ["inplace/bin/hp2ps"] -- TODO: Eliminate explicit filepaths in "need" (#376) build $ Target (vanillaContext Stage2 compiler) (Make "testsuite/tests") [] [] "test" ~> do From git at git.haskell.org Fri Oct 27 00:35:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to optimise ghc-stage2 in Quick flavour (b299acb) Message-ID: <20171027003534.189BB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b299acb4ec05bbf8a3b08a67175f8b2eb2f2aded/ghc >--------------------------------------------------------------- commit b299acb4ec05bbf8a3b08a67175f8b2eb2f2aded Author: Andrey Mokhov Date: Tue Jun 21 01:56:20 2016 +0100 Attempt to optimise ghc-stage2 in Quick flavour See #259 >--------------------------------------------------------------- b299acb4ec05bbf8a3b08a67175f8b2eb2f2aded src/Settings/Flavours/Quick.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 81fe178..834a72b 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -5,7 +5,7 @@ import GHC import Predicate optimise :: Context -> Bool -optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] +optimise Context {..} = package `elem` [compiler, ghc] || stage == Stage1 && isLibrary package quickFlavourArgs :: Args From git at git.haskell.org Fri Oct 27 00:35:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Export Data.List.Extra from Base, rather than importing Extra in each module (seems to fit with the general style) (b9c6d43) Message-ID: <20171027003537.BD42E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b9c6d43718f66950024abb1212bb7fb0de1e8090/ghc >--------------------------------------------------------------- commit b9c6d43718f66950024abb1212bb7fb0de1e8090 Author: Neil Mitchell Date: Sat Jan 9 21:47:34 2016 +0000 Export Data.List.Extra from Base, rather than importing Extra in each module (seems to fit with the general style) >--------------------------------------------------------------- b9c6d43718f66950024abb1212bb7fb0de1e8090 src/Base.hs | 4 ++-- src/Oracles/LookupInPath.hs | 1 - src/Rules/Data.hs | 1 - src/Rules/Libffi.hs | 1 - src/Rules/Library.hs | 2 +- 5 files changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 65a2d1d..a428c2c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -3,7 +3,7 @@ module Base ( module Control.Applicative, module Control.Monad.Extra, module Data.Function, - module Data.List, + module Data.List.Extra, module Data.Maybe, module Data.Monoid, MonadTrans(lift), @@ -31,7 +31,7 @@ import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader import Data.Function -import Data.List +import Data.List.Extra import Data.Maybe import Data.Monoid import Development.Shake hiding (unit, (*>)) diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 2532cb9..d573fd7 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -4,7 +4,6 @@ module Oracles.LookupInPath ( ) where import Base -import Extra (wordsBy) newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index d6f46a6..8b21fc7 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -2,7 +2,6 @@ module Rules.Data (buildPackageData) where import Base import Expression -import Extra (replace) import GHC import Oracles import Predicates (registerPackage) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 31f249b..9d77814 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -2,7 +2,6 @@ module Rules.Libffi (libffiRules, libffiDependencies) where import Base import Expression -import Extra (replace) import GHC import Oracles import Rules.Actions diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 46f3971..ba20034 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -2,7 +2,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Data.Char -import Base hiding (splitPath) +import Base hiding (splitPath, split) import Expression import GHC import Oracles From git at git.haskell.org Fri Oct 27 00:35:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix validate's hsc2hs dependency (#375) (#378) (fd5cd07) Message-ID: <20171027003538.26F573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd5cd0756dd1d9a0071c4f3378e6c64cee0e2f63/ghc >--------------------------------------------------------------- commit fd5cd0756dd1d9a0071c4f3378e6c64cee0e2f63 Author: Zhen Zhang Date: Mon Jul 24 02:08:42 2017 +0800 Fix validate's hsc2hs dependency (#375) (#378) >--------------------------------------------------------------- fd5cd0756dd1d9a0071c4f3378e6c64cee0e2f63 src/Rules/Test.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 0f46f6c..5f6d678 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -22,8 +22,9 @@ testRules = do needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc - needBuilder Hsc2Hs - need ["inplace/bin/hp2ps"] -- TODO: Eliminate explicit filepaths in "need" (#376) + need ["inplace/bin/hp2ps", "inplace/bin/hsc2hs"] + -- TODO: Eliminate explicit filepaths in "need" (#376) + -- FIXME: needBuilder Hsc2Hs doesn't work build $ Target (vanillaContext Stage2 compiler) (Make "testsuite/tests") [] [] "test" ~> do From git at git.haskell.org Fri Oct 27 00:35:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't optimise GHC in Quickest flavour (0955d43) Message-ID: <20171027003538.5C5493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0955d43bbbde1ee3ab71d3a01bf3d2f6e53afbe9/ghc >--------------------------------------------------------------- commit 0955d43bbbde1ee3ab71d3a01bf3d2f6e53afbe9 Author: Andrey Mokhov Date: Tue Jun 21 20:10:31 2016 +0100 Don't optimise GHC in Quickest flavour See #259, #268. >--------------------------------------------------------------- 0955d43bbbde1ee3ab71d3a01bf3d2f6e53afbe9 src/Settings/Flavours/Quickest.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index cc1de6b..3696237 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -1,16 +1,9 @@ module Settings.Flavours.Quickest (quickestFlavourArgs, quickestFlavourWays) where -import Context -import GHC import Predicate -optimise :: Context -> Bool -optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] - quickestFlavourArgs :: Args -quickestFlavourArgs = builder Ghc ? do - context <- getContext - if optimise context then arg "-O" else arg "-O0" +quickestFlavourArgs = builder Ghc ? arg "-O0" quickestFlavourWays :: Ways quickestFlavourWays = remove [profiling] From git at git.haskell.org Fri Oct 27 00:35:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use splitOn to parse the Way (9ae96f4) Message-ID: <20171027003541.81EB13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ae96f4017f3d11da5684a15b0a6b4e10c182dd9/ghc >--------------------------------------------------------------- commit 9ae96f4017f3d11da5684a15b0a6b4e10c182dd9 Author: Neil Mitchell Date: Sat Jan 9 21:47:47 2016 +0000 Use splitOn to parse the Way >--------------------------------------------------------------- 9ae96f4017f3d11da5684a15b0a6b4e10c182dd9 src/Way.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Way.hs b/src/Way.hs index 94a3bcc..5b24662 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -72,7 +72,7 @@ instance Read Way where uniqueReads token = case reads token of [(unit, "")] -> Just unit _ -> Nothing - units = map uniqueReads . words . replaceEq '_' ' ' $ s + units = map uniqueReads . splitOn "_" $ s result = if Nothing `elem` units then [] else [(wayFromUnits . map fromJust $ units, "")] From git at git.haskell.org Fri Oct 27 00:35:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (0579308) Message-ID: <20171027003542.10FAC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0579308f9cb7444e28a230867c8ba462238747dd/ghc >--------------------------------------------------------------- commit 0579308f9cb7444e28a230867c8ba462238747dd Author: Andrey Mokhov Date: Fri Jun 24 00:54:42 2016 +0100 Minor revision >--------------------------------------------------------------- 0579308f9cb7444e28a230867c8ba462238747dd README.md | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 6b5b234..4ce3b3a 100644 --- a/README.md +++ b/README.md @@ -43,12 +43,13 @@ runs the `boot` and `configure` scripts automatically on the first build, so tha need to. Use `--skip-configure` to suppress this behaviour (see overview of command line flags below). -* Also note on OS X newer versions of XCode ship with a broken `nm` tool ([#1174](https://ghc.haskell.org/trac/ghc/ticket/11744)). To mitigate the problem place something like +* Also note on OS X newer versions of XCode ship with a broken `nm` tool +([#11744](https://ghc.haskell.org/trac/ghc/ticket/11744)). One way to mitigate the +problem is to add the following into your `UserSettings.hs`: ````haskell userArgs :: Args userArgs = builder (Configure ".") ? arg "--with-nm=$(xcrun --find nm-classic)" ```` - in your `UserSettings.hs`. Using the build system ---------------------- From git at git.haskell.org Fri Oct 27 00:35:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant imports (776cf70) Message-ID: <20171027003542.26BF23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/776cf701a457c0970c7126a840cf8f4afefece2f/ghc >--------------------------------------------------------------- commit 776cf701a457c0970c7126a840cf8f4afefece2f Author: Andrey Mokhov Date: Wed Jul 26 23:07:14 2017 +0100 Drop redundant imports >--------------------------------------------------------------- 776cf701a457c0970c7126a840cf8f4afefece2f src/Rules/Test.hs | 1 - src/Settings/Builders/Hsc2Hs.hs | 1 - src/Util.hs | 1 - 3 files changed, 3 deletions(-) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 5f6d678..335964c 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -5,7 +5,6 @@ import Builder import Expression import Flavour import GHC -import qualified Rules.Generate import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Path diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index a9ec9c5..217636b 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -1,7 +1,6 @@ module Settings.Builders.Hsc2Hs (hsc2hsBuilderArgs) where import Settings.Builders.Common -import Settings.Path (templateHscPath) hsc2hsBuilderArgs :: Args hsc2hsBuilderArgs = builder Hsc2Hs ? do diff --git a/src/Util.hs b/src/Util.hs index 7ea567e..37743c0 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -22,7 +22,6 @@ import Oracles.Path import Oracles.Config.Setting import Settings import Settings.Builders.Ar -import Settings.Path import Target import UserSettings From git at git.haskell.org Fri Oct 27 00:35:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghc-cabal only, add cache. (9dbd805) Message-ID: <20171027003545.5849C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dbd805af4dcc0f90f80b33a74cb1f0c1c49f861/ghc >--------------------------------------------------------------- commit 9dbd805af4dcc0f90f80b33a74cb1f0c1c49f861 Author: Andrey Mokhov Date: Sat Jan 9 23:35:04 2016 +0000 Build ghc-cabal only, add cache. See #110. [skip ci] >--------------------------------------------------------------- 9dbd805af4dcc0f90f80b33a74cb1f0c1c49f861 .appveyor.yml | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 99196db..e7cf731 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,4 +1,10 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" +environment: + global: + STACK_ROOT: "c:\\sr" + +cache: + - c:\\sr install: - cd @@ -24,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-cabal.exe From git at git.haskell.org Fri Oct 27 00:35:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Oracle 'DirectoryContent' (21f3e05) Message-ID: <20171027003546.326BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21f3e0562f3d4685e384f2ba374898dc6868ce0e/ghc >--------------------------------------------------------------- commit 21f3e0562f3d4685e384f2ba374898dc6868ce0e Author: Kai Harries Date: Tue Jun 28 09:39:55 2016 +0200 Add Oracle 'DirectoryContent' >--------------------------------------------------------------- 21f3e0562f3d4685e384f2ba374898dc6868ce0e hadrian.cabal | 1 + src/Oracles/DirectoryContent.hs | 31 +++++++++++++++++++++++++++++++ src/Rules/Oracles.hs | 2 ++ 3 files changed, 34 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 5ffcb65..df2a4a5 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -30,6 +30,7 @@ executable hadrian , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies + , Oracles.DirectoryContent , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContent.hs new file mode 100644 index 0000000..6211222 --- /dev/null +++ b/src/Oracles/DirectoryContent.hs @@ -0,0 +1,31 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module Oracles.DirectoryContent ( + getDirectoryContent, directoryContentOracle, Exclude(..), ExcludeNot(..) + ) where + +import Base +import System.Directory.Extra + +newtype DirectoryContent = DirectoryContent (Exclude, ExcludeNot, FilePath) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) +newtype Exclude = Exclude [FilePattern] + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) +newtype ExcludeNot = ExcludeNot [FilePattern] + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Get the directory content. 'Exclude' and 'ExcludeNot' are a list of file +-- patterns matched with '?=='. +getDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> Action [FilePath] +getDirectoryContent exclude excludeNot dir = + askOracle $ DirectoryContent (exclude, excludeNot, dir) + +directoryContentOracle :: Rules () +directoryContentOracle = void $ addOracle oracle + where + oracle :: DirectoryContent -> Action [FilePath] + oracle (DirectoryContent (Exclude exclude, ExcludeNot excludeNot, dir)) = + liftIO $ filter test <$> listFilesInside (return . test) dir + where + test a = include' a || not (exclude' a) + exclude' a = any (?== a) exclude + include' a = any (?== a) excludeNot diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 7beb67f..10767b5 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -4,6 +4,7 @@ import Base import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies +import qualified Oracles.DirectoryContent import qualified Oracles.LookupInPath import qualified Oracles.ModuleFiles import qualified Oracles.PackageData @@ -15,6 +16,7 @@ oracleRules = do Oracles.ArgsHash.argsHashOracle Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles + Oracles.DirectoryContent.directoryContentOracle Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle From git at git.haskell.org Fri Oct 27 00:35:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bump Cabal library version, fix AppVeyor build (345deee) Message-ID: <20171027003546.60CB13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/345deee0c3850479ab6047920314c3ac30d7dad0/ghc >--------------------------------------------------------------- commit 345deee0c3850479ab6047920314c3ac30d7dad0 Author: Andrey Mokhov Date: Wed Jul 26 23:35:27 2017 +0100 Bump Cabal library version, fix AppVeyor build >--------------------------------------------------------------- 345deee0c3850479ab6047920314c3ac30d7dad0 hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 1178cb4..77fc54c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -119,7 +119,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 2.0.0.0 + , Cabal == 2.0.0.2 , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 00:35:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to a more ambitious build target. (f168dc4) Message-ID: <20171027003548.BF76B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f168dc4eaef267ce321821088dba79d961617a88/ghc >--------------------------------------------------------------- commit f168dc4eaef267ce321821088dba79d961617a88 Author: Andrey Mokhov Date: Sun Jan 10 00:30:03 2016 +0000 Switch to a more ambitious build target. See #110. [skip ci] >--------------------------------------------------------------- f168dc4eaef267ce321821088dba79d961617a88 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index e7cf731..b2f27af 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-cabal.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/libHSghc-boot-8.1.a From git at git.haskell.org Fri Oct 27 00:35:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rework copyDirectoryContent (5439f0e) Message-ID: <20171027003550.69B8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5439f0ee49094ad46574a38b217f741ba4f6ea35/ghc >--------------------------------------------------------------- commit 5439f0ee49094ad46574a38b217f741ba4f6ea35 Author: Kai Harries Date: Tue Jun 28 09:43:52 2016 +0200 Rework copyDirectoryContent >--------------------------------------------------------------- 5439f0ee49094ad46574a38b217f741ba4f6ea35 src/Rules/Actions.hs | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 734cb91..c3680f9 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -2,7 +2,7 @@ module Rules.Actions ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, removeFile, copyDirectory, copyDirectoryContent, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, - makeExecutable, renderProgram, renderLibrary + makeExecutable, renderProgram, renderLibrary, Exclude(..), ExcludeNot(..) ) where import qualified System.Directory.Extra as IO @@ -14,6 +14,7 @@ import CmdLineFlag import Context import Expression import Oracles.ArgsHash +import Oracles.DirectoryContent import Oracles.WindowsPath import Settings import Settings.Args @@ -127,17 +128,18 @@ copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd cmdEcho ["cp", "-r", source, target] --- | Copy the content of the source directory into the target directory. Only --- the files and directories for which the predicate returns True are copied. -copyDirectoryContent :: (FilePath -> IO Bool) -> FilePath -> FilePath -> Action () -copyDirectoryContent test source target = do - putProgressInfo $ renderAction "Copy directory" source target - liftIO $ IO.listFilesInside test' source >>= mapM_ cp +-- | Copy the content of the source directory into the target directory. +-- 'Exclude' and 'ExcludeNot' are a list of file patterns matched with '?=='. +-- The copied content is tracked. +copyDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> FilePath -> Action () +copyDirectoryContent exclude excludeNot source target = do + putProgressInfo $ renderAction "Copy directory content" source target + getDirectoryContent exclude excludeNot source >>= mapM_ cp where + cp a = do + createDirectory $ dropFileName $ target' a + copyFile a $ target' a target' a = target -/- fromJust (stripPrefix source a) - test' a = ifM (test a) (mkdir a >> return True) (return False) - mkdir a = IO.createDirectoryIfMissing True $ target' a - cp a = whenM (test a) $ IO.copyFile a $ target' a -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:35:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Part 1 of the Great Refactoring of the Expression (9c75620) Message-ID: <20171027003550.981313A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c75620168d77d91814d6a3aa562cd58405bfe5a/ghc >--------------------------------------------------------------- commit 9c75620168d77d91814d6a3aa562cd58405bfe5a Author: Andrey Mokhov Date: Thu Jul 27 02:58:55 2017 +0100 Part 1 of the Great Refactoring of the Expression See #347 >--------------------------------------------------------------- 9c75620168d77d91814d6a3aa562cd58405bfe5a hadrian.cabal | 3 +- src/Base.hs | 1 - src/Expression.hs | 154 +++++++++++++------------------ src/Oracles/Config/Flag.hs | 7 +- src/Oracles/Config/Setting.hs | 12 +-- src/Oracles/Path.hs | 6 +- src/Rules/Generators/Common.hs | 4 +- src/Rules/Generators/ConfigHs.hs | 2 +- src/Rules/Generators/GhcAutoconfH.hs | 4 +- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Libffi.hs | 4 +- src/Rules/Wrappers.hs | 46 ++++----- src/Settings.hs | 16 ++-- src/Settings/Builders/Cc.hs | 2 +- src/Settings/Builders/Common.hs | 17 ++-- src/Settings/Builders/DeriveConstants.hs | 6 +- src/Settings/Builders/Ghc.hs | 10 +- src/Settings/Builders/GhcCabal.hs | 38 ++++---- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 4 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 10 +- src/Settings/Builders/Make.hs | 2 +- src/Settings/Default.hs | 12 +-- src/Settings/Packages/GhcCabal.hs | 6 +- src/Settings/Packages/IntegerGmp.hs | 4 +- src/Settings/Packages/Rts.hs | 7 +- 27 files changed, 167 insertions(+), 216 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 9c75620168d77d91814d6a3aa562cd58405bfe5a From git at git.haskell.org Fri Oct 27 00:35:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Quote cache path. (1b36ea9) Message-ID: <20171027003552.5E55D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b36ea956be80db55406fffc868cb676de5ce100/ghc >--------------------------------------------------------------- commit 1b36ea956be80db55406fffc868cb676de5ce100 Author: Andrey Mokhov Date: Sun Jan 10 00:42:55 2016 +0000 Quote cache path. See #110. [skip ci] >--------------------------------------------------------------- 1b36ea956be80db55406fffc868cb676de5ce100 .appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index b2f27af..176fb2a 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -4,7 +4,7 @@ environment: STACK_ROOT: "c:\\sr" cache: - - c:\\sr + - "c:\\sr" install: - cd @@ -30,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/libHSghc-boot-8.1.a + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/build/libHSghc-boot-8.1.a From git at git.haskell.org Fri Oct 27 00:35:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: getDirectoryContent: Implement an AST for matching (5999957) Message-ID: <20171027003554.0566B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59999579eb089d578b0bed928bfe338b8705cace/ghc >--------------------------------------------------------------- commit 59999579eb089d578b0bed928bfe338b8705cace Author: Kai Harries Date: Fri Jul 1 15:30:56 2016 +0200 getDirectoryContent: Implement an AST for matching >--------------------------------------------------------------- 59999579eb089d578b0bed928bfe338b8705cace src/Oracles/DirectoryContent.hs | 44 ++++++++++++++++++++++++----------------- src/Rules/Actions.hs | 9 ++++----- 2 files changed, 30 insertions(+), 23 deletions(-) diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContent.hs index 6211222..45afa92 100644 --- a/src/Oracles/DirectoryContent.hs +++ b/src/Oracles/DirectoryContent.hs @@ -1,31 +1,39 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} module Oracles.DirectoryContent ( - getDirectoryContent, directoryContentOracle, Exclude(..), ExcludeNot(..) + getDirectoryContent, directoryContentOracle, Match(..) ) where import Base +import GHC.Generics import System.Directory.Extra -newtype DirectoryContent = DirectoryContent (Exclude, ExcludeNot, FilePath) - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -newtype Exclude = Exclude [FilePattern] - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -newtype ExcludeNot = ExcludeNot [FilePattern] +newtype DirectoryContent = DirectoryContent (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- | Get the directory content. 'Exclude' and 'ExcludeNot' are a list of file --- patterns matched with '?=='. -getDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> Action [FilePath] -getDirectoryContent exclude excludeNot dir = - askOracle $ DirectoryContent (exclude, excludeNot, dir) +data Match = Test FilePattern | Not (Match) | And [Match] | Or [Match] + deriving (Generic, Eq, Show, Typeable) +instance Binary Match +instance Hashable Match +instance NFData Match + +matches :: Match -> FilePath -> Bool +matches (Test m) f = m ?== f +matches (Not m) f = not $ matches m f +matches (And []) _ = True +matches (And (m:ms)) f | matches m f = matches (And ms) f + | otherwise = False +matches (Or []) _ = False +matches (Or (m:ms)) f | matches m f = True + | otherwise = matches (Or ms) f + +-- | Get the directory content recursively. +getDirectoryContent :: Match -> FilePath -> Action [FilePath] +getDirectoryContent expr dir = + askOracle $ DirectoryContent (expr, dir) directoryContentOracle :: Rules () directoryContentOracle = void $ addOracle oracle where oracle :: DirectoryContent -> Action [FilePath] - oracle (DirectoryContent (Exclude exclude, ExcludeNot excludeNot, dir)) = - liftIO $ filter test <$> listFilesInside (return . test) dir - where - test a = include' a || not (exclude' a) - exclude' a = any (?== a) exclude - include' a = any (?== a) excludeNot + oracle (DirectoryContent (expr, dir)) = + liftIO $ filter (matches expr) <$> listFilesInside (return . matches expr) dir diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index c3680f9..7b4c46c 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -2,7 +2,7 @@ module Rules.Actions ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, removeFile, copyDirectory, copyDirectoryContent, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, - makeExecutable, renderProgram, renderLibrary, Exclude(..), ExcludeNot(..) + makeExecutable, renderProgram, renderLibrary, Match(..) ) where import qualified System.Directory.Extra as IO @@ -129,12 +129,11 @@ copyDirectory source target = do quietly $ cmd cmdEcho ["cp", "-r", source, target] -- | Copy the content of the source directory into the target directory. --- 'Exclude' and 'ExcludeNot' are a list of file patterns matched with '?=='. -- The copied content is tracked. -copyDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> FilePath -> Action () -copyDirectoryContent exclude excludeNot source target = do +copyDirectoryContent :: Match -> FilePath -> FilePath -> Action () +copyDirectoryContent expr source target = do putProgressInfo $ renderAction "Copy directory content" source target - getDirectoryContent exclude excludeNot source >>= mapM_ cp + getDirectoryContent expr source >>= mapM_ cp where cp a = do createDirectory $ dropFileName $ target' a From git at git.haskell.org Fri Oct 27 00:35:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't echo (227d8d7) Message-ID: <20171027003554.323303A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/227d8d7d669f0dc99e7947391521259b0ce28186/ghc >--------------------------------------------------------------- commit 227d8d7d669f0dc99e7947391521259b0ce28186 Author: Andrey Mokhov Date: Fri Jul 28 22:22:18 2017 +0100 Don't echo >--------------------------------------------------------------- 227d8d7d669f0dc99e7947391521259b0ce28186 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 37743c0..e6fd6bf 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -76,7 +76,7 @@ customBuild rs opts target at Target {..} = do src <- interpret target getInput file <- interpret target getOutput input <- readFile' src - Stdout output <- cmd cmdEcho (Stdin input) [path] argList + Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output Make dir -> cmd Shell cmdEcho path ["-C", dir] argList From git at git.haskell.org Fri Oct 27 00:35:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to build stage1 GHC. (c217881) Message-ID: <20171027003555.C33D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c217881e59c759dc519e56f246ccb9ab56a6e7d4/ghc >--------------------------------------------------------------- commit c217881e59c759dc519e56f246ccb9ab56a6e7d4 Author: Andrey Mokhov Date: Sun Jan 10 02:20:00 2016 +0000 Attempt to build stage1 GHC. See #110. [skip ci] >--------------------------------------------------------------- c217881e59c759dc519e56f246ccb9ab56a6e7d4 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 176fb2a..f4f1d83 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,4 +30,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress libraries/ghc-boot/stage0/build/libHSghc-boot-8.1.a + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:35:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #266 from KaiHa/copyDirectoryContent (df3ad6d) Message-ID: <20171027003557.88E1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/df3ad6da2a9e7865bd535499412fd453d29f8a94/ghc >--------------------------------------------------------------- commit df3ad6da2a9e7865bd535499412fd453d29f8a94 Merge: 0579308 5999957 Author: Andrey Mokhov Date: Fri Jul 1 15:44:33 2016 +0100 Merge pull request #266 from KaiHa/copyDirectoryContent Add actions copyDirectoryContent and runBuilderWith >--------------------------------------------------------------- df3ad6da2a9e7865bd535499412fd453d29f8a94 hadrian.cabal | 1 + src/Oracles/DirectoryContent.hs | 39 +++++++++++++++++++++++++++++++++++++++ src/Rules/Actions.hs | 27 ++++++++++++++++++++++----- src/Rules/Oracles.hs | 2 ++ 4 files changed, 64 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Oct 27 00:35:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable parallel garbage collection (#385) (57cfa03) Message-ID: <20171027003557.B18463A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57cfa03c23047bb0c731428e97ca716d9a1cf312/ghc >--------------------------------------------------------------- commit 57cfa03c23047bb0c731428e97ca716d9a1cf312 Author: Ben Gamari Date: Sat Jul 29 06:28:14 2017 -0400 Disable parallel garbage collection (#385) This brings productivity from roughly 40% to 95%. With parallel GC we generally spend much of our time synchronizing between the GC threads and relatively little time doing productive work. >--------------------------------------------------------------- 57cfa03c23047bb0c731428e97ca716d9a1cf312 hadrian.cabal | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 4eb43db..af5fd6c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -133,5 +133,11 @@ executable hadrian , happy >= 1.19.4 ghc-options: -Wall -fno-warn-name-shadowing - -rtsopts -with-rtsopts=-I0 + -rtsopts + -- Disable idle GC to avoid redundant GCs while waiting + -- for external processes + -with-rtsopts=-I0 + -- Don't use parallel GC as the synchronization time tends to eat any + -- benefit. + -with-rtsopts=-qg0 -threaded From git at git.haskell.org Fri Oct 27 00:35:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move build artefacts to .build/ directory. (eda85ff) Message-ID: <20171027003559.37C6A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eda85ffd9bca4b43667b9a172fc5a4b888f018cd/ghc >--------------------------------------------------------------- commit eda85ffd9bca4b43667b9a172fc5a4b888f018cd Author: Andrey Mokhov Date: Sun Jan 10 05:02:18 2016 +0000 Move build artefacts to .build/ directory. See #113. >--------------------------------------------------------------- eda85ffd9bca4b43667b9a172fc5a4b888f018cd src/Base.hs | 2 ++ src/GHC.hs | 33 +--------------------- src/Oracles/LookupInPath.hs | 15 ++++------ src/Oracles/PackageDeps.hs | 4 +-- src/Rules/Compile.hs | 3 +- src/Rules/Config.hs | 1 + src/Rules/Data.hs | 62 ++++++++++++++++++++++++++--------------- src/Rules/Dependencies.hs | 10 +++++-- src/Rules/Generate.hs | 6 ++-- src/Rules/IntegerGmp.hs | 1 + src/Rules/Libffi.hs | 10 ++++--- src/Rules/Library.hs | 13 ++++++--- src/Rules/Program.hs | 4 +-- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Builders/GhcPkg.hs | 6 ++-- src/Settings/Default.hs | 36 ++++++++++++++++++++++-- src/Settings/Packages/Rts.hs | 5 ++-- src/Settings/TargetDirectory.hs | 4 +-- src/Settings/User.hs | 26 +++++++++-------- 19 files changed, 143 insertions(+), 101 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 eda85ffd9bca4b43667b9a172fc5a4b888f018cd From git at git.haskell.org Fri Oct 27 00:36:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix profiled GHC context (7b4fdfb) Message-ID: <20171027003605.C00513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b4fdfba5f8a58c742a23a70b70085830f540e0e/ghc >--------------------------------------------------------------- commit 7b4fdfba5f8a58c742a23a70b70085830f540e0e Author: Andrey Mokhov Date: Tue Aug 1 01:39:38 2017 +0100 Fix profiled GHC context See #387 >--------------------------------------------------------------- 7b4fdfba5f8a58c742a23a70b70085830f540e0e src/Settings.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings.hs b/src/Settings.hs index c1d4fbb..b65a17b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -70,7 +70,7 @@ integerLibraryName = pkgNameString $ integerLibrary flavour programContext :: Stage -> Package -> Context programContext stage pkg - | pkg == ghc && ghcProfiled flavour = Context stage pkg profiling + | pkg == ghc && ghcProfiled flavour && stage > Stage0 = Context stage pkg profiling | otherwise = vanillaContext stage pkg -- TODO: switch to Set Package as the order of packages should not matter? From git at git.haskell.org Fri Oct 27 00:36:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Enable RecordWildCards (fa4ca65) Message-ID: <20171027003605.504103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fa4ca65a88bd883758888df5665d78844138c69f/ghc >--------------------------------------------------------------- commit fa4ca65a88bd883758888df5665d78844138c69f Author: Andrey Mokhov Date: Wed Jul 13 00:37:22 2016 +0100 Enable RecordWildCards >--------------------------------------------------------------- fa4ca65a88bd883758888df5665d78844138c69f .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 2f24ebe..85dfc94 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,2 @@ -:set -Wall -fno-warn-name-shadowing -isrc +:set -Wall -fno-warn-name-shadowing -isrc -XRecordWildCards :load Main From git at git.haskell.org Fri Oct 27 00:36:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused folder (88b495c) Message-ID: <20171027003601.CC71D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88b495c3dec700e76501319a995e2902a159d838/ghc >--------------------------------------------------------------- commit 88b495c3dec700e76501319a995e2902a159d838 Author: Andrey Mokhov Date: Wed Jul 13 00:44:16 2016 +0100 Drop unused folder >--------------------------------------------------------------- 88b495c3dec700e76501319a995e2902a159d838 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 5307cdd..6fbc3b2 100644 --- a/.gitignore +++ b/.gitignore @@ -1,4 +1,4 @@ -/.db/ +# generated by the configure script cfg/system.config # build.bat and build.sh specific From git at git.haskell.org Fri Oct 27 00:36:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use GHC to compile C files (#380) (e6dcd1b) Message-ID: <20171027003602.0DE0F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8/ghc >--------------------------------------------------------------- commit e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8 Author: Zhen Zhang Date: Sat Jul 29 18:37:58 2017 +0800 Use GHC to compile C files (#380) >--------------------------------------------------------------- e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8 src/Builder.hs | 4 ++-- src/Rules/Compile.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 24 +++++++++++++++++++++++- src/Settings/Default.hs | 1 + src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Rts.hs | 7 ++++--- 6 files changed, 34 insertions(+), 10 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 7937319..4112900 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -15,8 +15,8 @@ import Stage -- * Extracting source dependencies, e.g. by passing @-M@ command line argument; -- * Linking object files & static libraries into an executable. -- We have CcMode for C compiler and GhcMode for GHC. -data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show) -data GhcMode = CompileHs | FindHsDependencies | LinkHs +data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show) +data GhcMode = CompileCWithGhc | CompileHs | FindHsDependencies | LinkHs deriving (Eq, Generic, Show) -- | GhcPkg can initialise a package database and register packages in it. diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 87fc39a..d3d2ed5 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -28,9 +28,9 @@ compilePackage rs context at Context {..} = do buildWithResources rs $ Target context (Ghc CompileHs stage) [src] [obj] priority 2.0 $ do - nonHs "c" %> compile (Cc CompileC ) (obj2src "c" isGeneratedCFile ) - nonHs "cmm" %> compile (Ghc CompileHs) (obj2src "cmm" isGeneratedCmmFile) - nonHs "s" %> compile (Ghc CompileHs) (obj2src "S" $ const False ) + nonHs "c" %> compile (Ghc CompileCWithGhc) (obj2src "c" isGeneratedCFile ) + nonHs "cmm" %> compile (Ghc CompileHs) (obj2src "cmm" isGeneratedCmmFile) + nonHs "s" %> compile (Ghc CompileHs) (obj2src "S" $ const False ) -- TODO: Add dependencies for #include of .h and .hs-incl files (gcc -MM?). [ path "*" <.> suf way | suf <- [ osuf, hisuf] ] &%> compileHs diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index bb7c1e0..b7d5d70 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,4 +1,7 @@ -module Settings.Builders.Ghc (ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs) where +module Settings.Builders.Ghc ( + ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs, + ghcCbuilderArgs +) where import Flavour import GHC @@ -15,6 +18,25 @@ ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do , append =<< getInputs , arg "-o", arg =<< getOutput ] +ghcCbuilderArgs :: Args +ghcCbuilderArgs = + builder (Ghc CompileCWithGhc) ? do + way <- getWay + let ccArgs = [ append =<< getPkgDataList CcArgs + , getSettingList . ConfCcArgs =<< getStage + , cIncludeArgs + , arg "-Werror" + , Dynamic `wayUnit` way ? append [ "-fPIC", "-DDYNAMIC" ] ] + + mconcat [ arg "-Wall" + , ghcLinkArgs + , commonGhcArgs + , mconcat (map (map ("-optc" ++) <$>) ccArgs) + , arg "-c" + , append =<< getInputs + , arg "-o" + , arg =<< getOutput ] + ghcLinkArgs :: Args ghcLinkArgs = builder (Ghc LinkHs) ? do stage <- getStage diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index b65e86a..2940406 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -212,6 +212,7 @@ defaultBuilderArgs = mconcat , deriveConstantsBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs + , ghcCbuilderArgs , ghcCabalBuilderArgs , ghcCabalHsColourBuilderArgs , ghcMBuilderArgs diff --git a/src/Settings/Packages/Base.hs b/src/Settings/Packages/Base.hs index 219c9d4..07c19ce 100644 --- a/src/Settings/Packages/Base.hs +++ b/src/Settings/Packages/Base.hs @@ -7,4 +7,4 @@ import Settings basePackageArgs :: Args basePackageArgs = package base ? mconcat [ builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) - , builder Cc ? arg "-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. + , builder (Ghc CompileCWithGhc) ? arg "-optc-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 5a76eae..87e1fe8 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -48,8 +48,7 @@ rtsPackageArgs = package rts ? do ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir ghclibDir <- expr installGhcLibDir - mconcat - [ builder Cc ? mconcat + let cArgs = [ arg "-Irts" , arg $ "-I" ++ path , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" @@ -96,8 +95,10 @@ rtsPackageArgs = package rts ? do append [ "-Wno-incompatible-pointer-types" ] ] + mconcat + [ builder (Cc FindCDependencies) ? mconcat cArgs + , builder (Ghc CompileCWithGhc) ? mconcat (map (map ("-optc" ++) <$>) cArgs) , builder Ghc ? arg "-Irts" - , builder HsCpp ? append [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir From git at git.haskell.org Fri Oct 27 00:36:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix include paths. (1d18a74) Message-ID: <20171027003602.C6B7A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1d18a749606d4c093b00e8f4823b89597dae4c9a/ghc >--------------------------------------------------------------- commit 1d18a749606d4c093b00e8f4823b89597dae4c9a Author: Andrey Mokhov Date: Sun Jan 10 12:11:11 2016 +0000 Fix include paths. See #145. >--------------------------------------------------------------- 1d18a749606d4c093b00e8f4823b89597dae4c9a src/Settings/Builders/HsCpp.hs | 4 +++- src/Settings/Packages/Ghc.hs | 4 ++-- src/Settings/Packages/IntegerGmp.hs | 1 + src/Settings/Packages/IservBin.hs | 3 +-- 4 files changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs index 89980ee..43b9455 100644 --- a/src/Settings/Builders/HsCpp.hs +++ b/src/Settings/Builders/HsCpp.hs @@ -1,9 +1,11 @@ module Settings.Builders.HsCpp (hsCppBuilderArgs) where import Expression +import GHC import Oracles import Predicates (builder) import Settings.Builders.GhcCabal +import Settings.TargetDirectory hsCppBuilderArgs :: Args hsCppBuilderArgs = builder HsCpp ? do @@ -11,7 +13,7 @@ hsCppBuilderArgs = builder HsCpp ? do mconcat [ append =<< getSettingList HsCppArgs , arg "-P" , cppArgs - , arg $ "-Icompiler/" ++ stageString stage + , arg $ "-I" ++ targetPath stage compiler , arg "-x" , arg "c" , arg =<< getInput ] diff --git a/src/Settings/Packages/Ghc.hs b/src/Settings/Packages/Ghc.hs index efc059d..0830cb6 100644 --- a/src/Settings/Packages/Ghc.hs +++ b/src/Settings/Packages/Ghc.hs @@ -1,16 +1,16 @@ module Settings.Packages.Ghc (ghcPackageArgs) where -import Base import Expression import GHC (ghc, compiler) import Oracles.Config.Setting import Predicates (builder, builderGhc, package, notStage0) +import Settings.TargetDirectory ghcPackageArgs :: Args ghcPackageArgs = package ghc ? do stage <- getStage mconcat [ builderGhc ? mconcat - [ arg ("-I" ++ pkgPath compiler -/- stageString stage) + [ arg $ "-I" ++ targetPath stage compiler , arg "-no-hs-main" ] , builder GhcCabal ? diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 6d1b2b6..c679bf3 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -5,6 +5,7 @@ import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) +-- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" -- libraries/integer-gmp_CONFIGURE_OPTS += --with-gmp-framework-preferred diff --git a/src/Settings/Packages/IservBin.hs b/src/Settings/Packages/IservBin.hs index 5ad3bd5..a662d1c 100644 --- a/src/Settings/Packages/IservBin.hs +++ b/src/Settings/Packages/IservBin.hs @@ -6,5 +6,4 @@ import Predicates (builderGhc, package) iservBinPackageArgs :: Args iservBinPackageArgs = package iservBin ? do - mconcat [ builderGhc ? - mconcat [ arg "-no-hs-main" ]] + mconcat [ builderGhc ? arg "-no-hs-main" ] From git at git.haskell.org Fri Oct 27 00:36:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Postprocess inplace-pkg-config files. (f84ee22) Message-ID: <20171027003606.689A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f84ee22ff9c333ccd1625f06931e339b23e6e7cf/ghc >--------------------------------------------------------------- commit f84ee22ff9c333ccd1625f06931e339b23e6e7cf Author: Andrey Mokhov Date: Sun Jan 10 14:24:58 2016 +0000 Postprocess inplace-pkg-config files. See #113 and #148. >--------------------------------------------------------------- f84ee22ff9c333ccd1625f06931e339b23e6e7cf src/Rules/Data.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 9aeb7b3..4428b35 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -54,7 +54,17 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do -- ghc-pkg produces inplace-pkg-config when run on packages with -- library components only when (isLibrary pkg) . - whenM (interpretPartial target registerPackage) . + whenM (interpretPartial target registerPackage) $ do + + -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 + let fixPkgConf = unlines + . map (replace oldPath (targetPath stage pkg) + . replace (replaceSeparators '\\' $ oldPath) + (targetPath stage pkg) ) + . lines + + fixFile (oldPath -/- "inplace-pkg-config") fixPkgConf + buildWithResources [(resGhcPkg rs, 1)] $ fullTarget target (GhcPkg stage) [cabalFile] [] From git at git.haskell.org Fri Oct 27 00:36:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor build flavours (3be52c5) Message-ID: <20171027003608.D89A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46/ghc >--------------------------------------------------------------- commit 3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46 Author: Andrey Mokhov Date: Wed Jul 13 00:43:38 2016 +0100 Refactor build flavours See #268. >--------------------------------------------------------------- 3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46 hadrian.cabal | 4 +- src/CmdLineFlag.hs | 24 ++---- src/Flavour.hs | 18 ++++ src/Oracles/ArgsHash.hs | 2 +- src/Oracles/Dependencies.hs | 1 + src/Oracles/WindowsPath.hs | 8 +- src/Rules.hs | 18 ++-- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 1 + src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 3 +- src/Rules/Dependencies.hs | 3 +- src/Rules/Documentation.hs | 4 +- src/Rules/Generate.hs | 3 +- src/Rules/Generators/ConfigHs.hs | 6 +- src/Rules/Library.hs | 5 +- src/Rules/Program.hs | 2 + src/Rules/Register.hs | 2 +- src/Rules/Test.hs | 6 +- src/Rules/Wrappers/Ghc.hs | 2 +- src/Rules/Wrappers/GhcPkg.hs | 3 +- src/Settings.hs | 58 ++++++++++--- src/Settings/Args.hs | 95 --------------------- src/Settings/Builders/Cc.hs | 2 +- src/Settings/Builders/Common.hs | 1 + src/Settings/Builders/Configure.hs | 3 +- src/Settings/Builders/Ghc.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 5 +- src/Settings/Builders/GhcPkg.hs | 1 + src/Settings/Builders/Haddock.hs | 1 + src/Settings/Builders/Hsc2Hs.hs | 1 + src/Settings/Builders/Make.hs | 2 +- src/Settings/Default.hs | 169 ++++++++++++++++++++++++++++++++++++- src/Settings/Default.hs-boot | 13 +++ src/Settings/Flavours/Quick.hs | 22 +++-- src/Settings/Flavours/Quickest.hs | 18 ++-- src/Settings/Packages.hs | 57 ------------- src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Compiler.hs | 5 +- src/Settings/Packages/Rts.hs | 1 + src/Settings/Ways.hs | 46 ---------- src/UserSettings.hs | 57 +++---------- 43 files changed, 360 insertions(+), 324 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 3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46 From git at git.haskell.org Fri Oct 27 00:36:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bump to lts-9.0 (b6be67c) Message-ID: <20171027003609.A109E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6be67c1c801bda7574a0cd1bb7ca9630deb637f/ghc >--------------------------------------------------------------- commit b6be67c1c801bda7574a0cd1bb7ca9630deb637f Author: Andrey Mokhov Date: Wed Aug 2 00:11:18 2017 +0100 Bump to lts-9.0 See #292, #336 >--------------------------------------------------------------- b6be67c1c801bda7574a0cd1bb7ca9630deb637f hadrian.cabal | 4 ++-- stack.yaml | 36 +++++++++--------------------------- 2 files changed, 11 insertions(+), 29 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index af5fd6c..da905ff 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -122,10 +122,10 @@ executable hadrian , ansi-terminal == 0.6.* , Cabal == 2.0.0.2 , containers == 0.5.* - , directory == 1.2.* + , directory >= 1.2 && < 1.4 , extra >= 1.4.7 , mtl == 2.2.* - , QuickCheck >= 2.6 && < 2.9 + , QuickCheck >= 2.6 && < 2.10 , shake >= 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* diff --git a/stack.yaml b/stack.yaml index 5fa9f94..a05f2cd 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,36 +1,18 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-6.12 +resolver: lts-9.0 # Local packages, usually specified by relative directory name packages: - '.' - '../libraries/Cabal/Cabal' -# Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) -extra-deps: - -# Override default flag values for local packages and extra-deps -flags: {} - -# Extra package databases containing global packages -extra-package-dbs: [] - -# Control whether we use the GHC we find on the path -# system-ghc: false - -# Require a specific version of stack, using version ranges -# require-stack-version: -any # Default -# require-stack-version: >= 1.0.0 - -# Override the architecture used by stack, especially useful on Windows -# arch: i386 -# arch: x86_64 - -# Extra directories used by stack for building -# extra-include-dirs: [/path/to/dir] -# extra-lib-dirs: [/path/to/dir] - -# Allow a newer minor version of GHC than the snapshot specifies -# compiler-check: newer-minor +nix: + packages: + - autoconf + - automake + - gcc + - git + - ncurses + - perl From git at git.haskell.org Fri Oct 27 00:36:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/snowleopard/shaking-up-ghc (c96b1e9) Message-ID: <20171027003609.E67D23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c96b1e9f8ffdd430787ee8cd2f016d3474ffba9a/ghc >--------------------------------------------------------------- commit c96b1e9f8ffdd430787ee8cd2f016d3474ffba9a Merge: 9ae96f4 f84ee22 Author: Neil Mitchell Date: Sun Jan 10 20:28:45 2016 +0000 Merge branch 'master' of https://github.com/snowleopard/shaking-up-ghc >--------------------------------------------------------------- c96b1e9f8ffdd430787ee8cd2f016d3474ffba9a .appveyor.yml | 6 +++ src/Base.hs | 2 + src/GHC.hs | 33 +---------------- src/Oracles/LookupInPath.hs | 15 +++----- src/Oracles/PackageDeps.hs | 4 +- src/Rules/Compile.hs | 3 +- src/Rules/Config.hs | 1 + src/Rules/Data.hs | 74 +++++++++++++++++++++++++------------ src/Rules/Dependencies.hs | 10 ++++- src/Rules/Generate.hs | 6 ++- src/Rules/IntegerGmp.hs | 1 + src/Rules/Libffi.hs | 10 +++-- src/Rules/Library.hs | 13 +++++-- src/Rules/Program.hs | 4 +- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Builders/GhcPkg.hs | 6 ++- src/Settings/Builders/HsCpp.hs | 4 +- src/Settings/Default.hs | 36 +++++++++++++++++- src/Settings/Packages/Ghc.hs | 4 +- src/Settings/Packages/IntegerGmp.hs | 1 + src/Settings/Packages/IservBin.hs | 3 +- src/Settings/Packages/Rts.hs | 5 ++- src/Settings/TargetDirectory.hs | 4 +- src/Settings/User.hs | 26 +++++++------ 24 files changed, 167 insertions(+), 107 deletions(-) diff --cc src/Oracles/LookupInPath.hs index d573fd7,e75a80d..a9dc995 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@@ -1,9 -1,8 +1,7 @@@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} - module Oracles.LookupInPath ( - lookupInPath, lookupInPathOracle - ) where + module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where import Base -import Extra (wordsBy) newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) From git at git.haskell.org Fri Oct 27 00:36:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch from condLibrary to condLibraries in Cabal (54a8e15) Message-ID: <20171027003612.4957B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/54a8e1579314b79890635323ff0e317834b720c9/ghc >--------------------------------------------------------------- commit 54a8e1579314b79890635323ff0e317834b720c9 Author: Andrey Mokhov Date: Thu Jul 14 00:26:35 2016 +0100 Switch from condLibrary to condLibraries in Cabal See #269. >--------------------------------------------------------------- 54a8e1579314b79890635323ff0e317834b720c9 src/Rules/Cabal.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index ed72f93..e2cdb0f 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -35,7 +35,8 @@ cabalRules = do else do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - let depsLib = collectDeps $ condLibrary pd + -- TODO: Support more than one Cabal library per package. + let depsLib = collectDeps . fmap snd . listToMaybe $ condLibraries pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes depNames = [ name | Dependency (DP.PackageName name) _ <- deps ] From git at git.haskell.org Fri Oct 27 00:36:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix AppVeyor (c8b08a2) Message-ID: <20171027003613.1228B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8b08a2231e4b8e34f45bf0a983f39fb0b075b6c/ghc >--------------------------------------------------------------- commit c8b08a2231e4b8e34f45bf0a983f39fb0b075b6c Author: Andrey Mokhov Date: Wed Aug 2 00:56:08 2017 +0100 Fix AppVeyor See #336 >--------------------------------------------------------------- c8b08a2231e4b8e34f45bf0a983f39fb0b075b6c appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/appveyor.yml b/appveyor.yml index b80008c..3b2e43b 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -26,6 +26,7 @@ install: build_script: # Build Hadrian + - stack build alex happy # Otherwise 'stack build' fails on AppVeyor - stack build # Run internal Hadrian tests From git at git.haskell.org Fri Oct 27 00:36:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hide parallel when importing from Development.Shake (6c81e9a) Message-ID: <20171027003613.5C1A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6c81e9aef6f0eaa626f27ceb6ed4a3d2af269a43/ghc >--------------------------------------------------------------- commit 6c81e9aef6f0eaa626f27ceb6ed4a3d2af269a43 Author: Neil Mitchell Date: Sun Jan 10 20:31:24 2016 +0000 Hide parallel when importing from Development.Shake >--------------------------------------------------------------- 6c81e9aef6f0eaa626f27ceb6ed4a3d2af269a43 src/Base.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 6d80a72..54f2f99 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,3 +1,5 @@ +{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} + module Base ( -- * General utilities module Control.Applicative, @@ -34,7 +36,7 @@ import Data.Function import Data.List.Extra import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>)) +import Development.Shake hiding (parallel, unit, (*>)) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Fri Oct 27 00:36:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Support autogen paths of new Cabal (5fe4668) Message-ID: <20171027003615.B47BA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5fe46687bbbde9a82577e9b117378d3f9c027ee1/ghc >--------------------------------------------------------------- commit 5fe46687bbbde9a82577e9b117378d3f9c027ee1 Author: Andrey Mokhov Date: Thu Jul 14 01:28:02 2016 +0100 Support autogen paths of new Cabal See #269. >--------------------------------------------------------------- 5fe46687bbbde9a82577e9b117378d3f9c027ee1 src/Rules/Data.hs | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 2da6f86..034b2f4 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -38,12 +38,19 @@ buildPackageData context at Context {..} = do -- TODO: Get rid of this, see #113. dataFile %> \mk -> do + -- TODO: This is a hack. Add a proper support for autogen directory + -- structure of the new Cabal (probably only after #113). + let oldBuild + | isLibrary package = oldPath -/- "build" + | package == ghc = oldPath -/- "build/ghc" + | package == hpcBin = oldPath -/- "build/hpc" + | otherwise = oldPath -/- "build" -/- pkgNameString package copyFile inTreeMk mk - autogenFiles <- getDirectoryFiles (oldPath -/- "build") ["autogen/*"] + autogenFiles <- getDirectoryFiles oldBuild ["autogen/*"] createDirectory $ buildPath context -/- "autogen" forM_ autogenFiles $ \file' -> do let file = unifyPath file' - copyFile (oldPath -/- "build" -/- file) (buildPath context -/- file) + copyFile (oldBuild -/- file) (buildPath context -/- file) let haddockPrologue = "haddock-prologue.txt" copyFile (oldPath -/- haddockPrologue) (buildPath context -/- haddockPrologue) postProcessPackageData context mk From git at git.haskell.org Fri Oct 27 00:36:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to building using GHC 8.0.2 and GHC 8.2.1 on Travis (3a39f38) Message-ID: <20171027003616.C414A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3a39f383a05863a78b63a2ca445e863e75bede19/ghc >--------------------------------------------------------------- commit 3a39f383a05863a78b63a2ca445e863e75bede19 Author: Andrey Mokhov Date: Wed Aug 2 01:02:58 2017 +0100 Switch to building using GHC 8.0.2 and GHC 8.2.1 on Travis >--------------------------------------------------------------- 3a39f383a05863a78b63a2ca445e863e75bede19 .travis.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index ba67ae3..49fac80 100644 --- a/.travis.yml +++ b/.travis.yml @@ -29,17 +29,17 @@ matrix: - os: linux env: MODE="--flavour=quickest" - compiler: "GHC 7.10.3" + compiler: "GHC 8.2.1" addons: apt: packages: - - ghc-7.10.3 + - ghc-8.2.1 - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc before_install: - - PATH="/opt/ghc/7.10.3/bin:$PATH" + - PATH="/opt/ghc/8.2.1/bin:$PATH" - PATH="/opt/cabal/1.22/bin:$PATH" script: From git at git.haskell.org Fri Oct 27 00:36:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove qualification on parallel identifiers (aaf934d) Message-ID: <20171027003617.0F7293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aaf934d0677ddd675918e2bd075c0a1015a4d7bf/ghc >--------------------------------------------------------------- commit aaf934d0677ddd675918e2bd075c0a1015a4d7bf Author: Neil Mitchell Date: Sun Jan 10 20:31:37 2016 +0000 Remove qualification on parallel identifiers >--------------------------------------------------------------- aaf934d0677ddd675918e2bd075c0a1015a4d7bf src/GHC.hs | 4 ++-- src/Way.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 54f94d9..c0013ad 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,7 +4,7 @@ module GHC ( deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty, + integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, @@ -24,7 +24,7 @@ defaultKnownPackages = , deepseq, deriveConstants, directory, dllSplit, filepath, genapply , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp - , integerSimple, iservBin, libffi, mkUserGuidePart, GHC.parallel, pretty + , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time , touchy, transformers, unlit, unix, win32, xhtml ] diff --git a/src/Way.hs b/src/Way.hs index 5b24662..974314c 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, - vanilla, profiling, logging, Way.parallel, granSim, + vanilla, profiling, logging, parallel, granSim, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, From git at git.haskell.org Fri Oct 27 00:36:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean the source tree before building source distribution (e918ec1) Message-ID: <20171027003620.AB5213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e918ec1d54a5e1b02bc6d466d0487cece77172a4/ghc >--------------------------------------------------------------- commit e918ec1d54a5e1b02bc6d466d0487cece77172a4 Author: Andrey Mokhov Date: Wed Aug 2 02:51:38 2017 +0100 Clean the source tree before building source distribution See #384 >--------------------------------------------------------------- e918ec1d54a5e1b02bc6d466d0487cece77172a4 src/Rules/Clean.hs | 28 +++++++++++++++++----------- src/Rules/SourceDist.hs | 3 +++ 2 files changed, 20 insertions(+), 11 deletions(-) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 33f1e3e..a8528e8 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -1,4 +1,4 @@ -module Rules.Clean (cleanRules) where +module Rules.Clean (clean, cleanSourceTree, cleanRules) where import Base import Settings.Path @@ -6,14 +6,20 @@ import Stage import UserSettings import Util +clean :: Action () +clean = do + cleanSourceTree + putBuild $ "| Remove Hadrian files..." + removeDirectory generatedPath + removeFilesAfter buildRootPath ["//*"] + putSuccess $ "| Done. " + +cleanSourceTree :: Action () +cleanSourceTree = do + forM_ [Stage0 ..] $ removeDirectory . (buildRootPath -/-) . stageString + removeDirectory inplaceBinPath + removeDirectory inplaceLibPath + removeDirectory "sdistprep" + cleanRules :: Rules () -cleanRules = do - "clean" ~> do - forM_ [Stage0 ..] $ removeDirectory . (buildRootPath -/-) . stageString - removeDirectory generatedPath - removeDirectory inplaceBinPath - removeDirectory inplaceLibPath - removeDirectory "sdistprep" - putBuild $ "| Remove Hadrian files..." - removeFilesAfter buildRootPath ["//*"] - putSuccess $ "| Done. " +cleanRules = "clean" ~> clean diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index 7a60238..40a4156 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -4,12 +4,14 @@ import Base import Builder import Oracles.Config.Setting import Oracles.DirectoryContents +import Rules.Clean import UserSettings import Util sourceDistRules :: Rules () sourceDistRules = do "sdist-ghc" ~> do + cleanSourceTree -- We clean the source tree first, see #384 version <- setting ProjectVersion need ["sdistprep/ghc-" ++ version ++ "-src.tar.xz"] putSuccess "| Done" @@ -41,6 +43,7 @@ prepareTree dest = do , Test "//*~" , Test "//autom4te*" , Test "//dist" + , Test "//dist-install" , Test "//log" , Test "//stage0" , Test "//stage1" From git at git.haskell.org Fri Oct 27 00:36:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Point to in-tree Cabal sources (6369ef0) Message-ID: <20171027003619.2BCB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6369ef04c8ba978c7670c4b79fe85c16e7a11139/ghc >--------------------------------------------------------------- commit 6369ef04c8ba978c7670c4b79fe85c16e7a11139 Author: Andrey Mokhov Date: Thu Jul 14 02:04:08 2016 +0100 Point to in-tree Cabal sources >--------------------------------------------------------------- 6369ef04c8ba978c7670c4b79fe85c16e7a11139 .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 85dfc94..9c0fe7a 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,2 @@ -:set -Wall -fno-warn-name-shadowing -isrc -XRecordWildCards +:set -Wall -fno-warn-name-shadowing -isrc -i../libraries/Cabal/Cabal -XRecordWildCards :load Main From git at git.haskell.org Fri Oct 27 00:36:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comment as to why we disable a warning (02c75e7) Message-ID: <20171027003620.E9EFA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02c75e7600d4208151f8ff1949f05fc0c339f1ff/ghc >--------------------------------------------------------------- commit 02c75e7600d4208151f8ff1949f05fc0c339f1ff Author: Neil Mitchell Date: Sun Jan 10 20:32:04 2016 +0000 Comment as to why we disable a warning >--------------------------------------------------------------- 02c75e7600d4208151f8ff1949f05fc0c339f1ff src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 54f2f99..4b6ad10 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,4 @@ -{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} +{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel module Base ( -- * General utilities From git at git.haskell.org Fri Oct 27 00:36:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop trackBuildSystem setting (4ad8082) Message-ID: <20171027003622.A329A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ad80828794f13c3e9139a68f06f3f2b6db1428f/ghc >--------------------------------------------------------------- commit 4ad80828794f13c3e9139a68f06f3f2b6db1428f Author: Andrey Mokhov Date: Thu Jul 14 02:04:32 2016 +0100 Drop trackBuildSystem setting >--------------------------------------------------------------- 4ad80828794f13c3e9139a68f06f3f2b6db1428f src/Oracles/ArgsHash.hs | 3 +-- src/Rules/Generators/Common.hs | 6 ++---- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/UserSettings.hs | 13 ++----------- 5 files changed, 7 insertions(+), 19 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index d1ebc68..660edd9 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -5,7 +5,6 @@ import Base import Expression import Settings import Target -import UserSettings newtype ArgsHashKey = ArgsHashKey Target deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -21,7 +20,7 @@ newtype ArgsHashKey = ArgsHashKey Target -- argument list constructors are assumed not to examine target sources, but -- only append them to argument lists where appropriate. checkArgsHash :: Target -> Action () -checkArgsHash target = when trackBuildSystem $ do +checkArgsHash target = do let hashed = [ show . hash $ inputs target ] _ <- askOracle . ArgsHashKey $ target { inputs = hashed } :: Action Int return () diff --git a/src/Rules/Generators/Common.hs b/src/Rules/Generators/Common.hs index e97d536..b01ad2f 100644 --- a/src/Rules/Generators/Common.hs +++ b/src/Rules/Generators/Common.hs @@ -2,12 +2,10 @@ module Rules.Generators.Common (trackSource, yesNo, cppify) where import Base import Expression -import UserSettings --- | Track a given source file when constructing an expression if the user --- enabled 'trackBuildSystem' in @hadrian/src/UserSettings.hs at . +-- | Track a given source file when constructing an expression. trackSource :: FilePath -> Expr () -trackSource file = lift $ when trackBuildSystem $ need [ sourcePath -/- file ] +trackSource file = lift $ need [ sourcePath -/- file ] -- | Turn a 'Bool' computed by an 'Action' into a 'String' expression returning -- "YES" (when the Boolean is 'True') or "NO" (when the Boolean is 'False'). diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index efe9144..0cf5b91 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -34,7 +34,7 @@ gmpRules :: Rules () gmpRules = do -- TODO: split into multiple rules gmpLibraryH %> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] + need [sourcePath -/- "Rules/Gmp.hs"] removeDirectory gmpBuildPath -- We don't use system GMP on Windows. TODO: fix? diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 3ee3307..99b97df 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -58,7 +58,7 @@ configureEnvironment = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] + need [sourcePath -/- "Rules/Libffi.hs"] useSystemFfi <- flag UseSystemFfi if useSystemFfi then do diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 1f73efa..a0a5d49 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,9 +3,8 @@ -- If you don't copy the file your changes will be tracked by git and you can -- accidentally commit them. module UserSettings ( - buildRootPath, userFlavours, userKnownPackages, integerLibrary, - trackBuildSystem, validating, turnWarningsIntoErrors, verboseCommands, - putBuild, putSuccess + buildRootPath, userFlavours, userKnownPackages, integerLibrary, validating, + turnWarningsIntoErrors, verboseCommands, putBuild, putSuccess ) where import System.Console.ANSI @@ -42,14 +41,6 @@ integerLibrary = integerGmp -- * @Predicate@: a flag whose value can depend on the build environment and -- on the current build target. --- TODO: Drop 'trackBuildSystem' as it brings negligible gains. --- | Set this to True if you are making any changes in the build system and want --- appropriate rebuilds to be initiated. Switching this to False speeds things --- up a little (particularly zero builds). --- WARNING: a complete rebuild is required when changing this setting. -trackBuildSystem :: Bool -trackBuildSystem = True - -- TODO: This should be set automatically when validating. validating :: Bool validating = False From git at git.haskell.org Fri Oct 27 00:36:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: cabal-install-2.x can new-build (#386) (6e8b0af) Message-ID: <20171027003624.D2C2C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e8b0afa1be2fd735784f7e1213a79694b512aa7/ghc >--------------------------------------------------------------- commit 6e8b0afa1be2fd735784f7e1213a79694b512aa7 Author: Oleg Grenrus Date: Wed Aug 2 13:33:09 2017 +0300 cabal-install-2.x can new-build (#386) >--------------------------------------------------------------- 6e8b0afa1be2fd735784f7e1213a79694b512aa7 .gitignore | 1 + build.cabal.sh | 4 ++-- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/.gitignore b/.gitignore index 2e3581b..4b026f2 100644 --- a/.gitignore +++ b/.gitignore @@ -11,6 +11,7 @@ cabal.sandbox.config # build.cabal-new.sh specific /dist-newstyle/ +.ghc.environment.* # build.stack.sh and build.stack.bat specific /.stack-work/ diff --git a/build.cabal.sh b/build.cabal.sh index 973cd3e..0dd9731 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -42,14 +42,14 @@ CABVERSTR=$("$CABAL" --numeric-version) CABVER=( ${CABVERSTR//./ } ) -if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then +if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then # New enough cabal version detected, so # let's use the superior 'cabal new-build' mode # there's no 'cabal new-run' yet, but it's easy to emulate "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" - "./dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ + $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ --lint \ --directory "$absoluteRoot/.." \ "$@" From git at git.haskell.org Fri Oct 27 00:36:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #143, turn of name shadowing warning (f89a75f) Message-ID: <20171027003625.1232A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f89a75f6730f643acc7002ee940803d01f1bda56/ghc >--------------------------------------------------------------- commit f89a75f6730f643acc7002ee940803d01f1bda56 Author: Neil Mitchell Date: Sun Jan 10 20:34:15 2016 +0000 #143, turn of name shadowing warning >--------------------------------------------------------------- f89a75f6730f643acc7002ee940803d01f1bda56 .ghci | 2 +- build.bat | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 1fe85b3..2f24ebe 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,2 @@ -:set -Wall -isrc +:set -Wall -fno-warn-name-shadowing -isrc :load Main diff --git a/build.bat b/build.bat index 07e355a..41b7877 100644 --- a/build.bat +++ b/build.bat @@ -2,6 +2,7 @@ @set ghcArgs=--make ^ -Wall ^ + -fno-warn-name-shadowing ^ src/Main.hs ^ -isrc ^ -rtsopts ^ From git at git.haskell.org Fri Oct 27 00:36:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix autogen path for iserv (38d1f55) Message-ID: <20171027003626.3318C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/38d1f551cbd1dd94d33da9290e98bacca394f285/ghc >--------------------------------------------------------------- commit 38d1f551cbd1dd94d33da9290e98bacca394f285 Author: Andrey Mokhov Date: Thu Jul 14 02:07:25 2016 +0100 Fix autogen path for iserv See #269. >--------------------------------------------------------------- 38d1f551cbd1dd94d33da9290e98bacca394f285 src/Rules/Data.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 034b2f4..959a7ec 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -41,10 +41,11 @@ buildPackageData context at Context {..} = do -- TODO: This is a hack. Add a proper support for autogen directory -- structure of the new Cabal (probably only after #113). let oldBuild - | isLibrary package = oldPath -/- "build" - | package == ghc = oldPath -/- "build/ghc" - | package == hpcBin = oldPath -/- "build/hpc" - | otherwise = oldPath -/- "build" -/- pkgNameString package + | isLibrary package = oldPath -/- "build" + | package == ghc = oldPath -/- "build/ghc" + | package == hpcBin = oldPath -/- "build/hpc" + | package == iservBin = oldPath -/- "build/iserv" + | otherwise = oldPath -/- "build" -/- pkgNameString package copyFile inTreeMk mk autogenFiles <- getDirectoryFiles oldBuild ["autogen/*"] createDirectory $ buildPath context -/- "autogen" From git at git.haskell.org Fri Oct 27 00:36:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant line (dd4270a) Message-ID: <20171027003628.8A7D03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dd4270a359f5e62e6264064b725aaf427001edc1/ghc >--------------------------------------------------------------- commit dd4270a359f5e62e6264064b725aaf427001edc1 Author: Andrey Mokhov Date: Wed Aug 2 11:39:41 2017 +0100 Drop redundant line See #386 >--------------------------------------------------------------- dd4270a359f5e62e6264064b725aaf427001edc1 build.cabal.sh | 1 - 1 file changed, 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index 0dd9731..2a0e8a7 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -48,7 +48,6 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th # there's no 'cabal new-run' yet, but it's easy to emulate "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ --lint \ --directory "$absoluteRoot/.." \ From git at git.haskell.org Fri Oct 27 00:36:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove an unnecessary hiding after disabling name shadow warning (6e1511f) Message-ID: <20171027003628.BD7B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e1511f9d48bb5198ab6feb4f9a2e6039df5b67f/ghc >--------------------------------------------------------------- commit 6e1511f9d48bb5198ab6feb4f9a2e6039df5b67f Author: Neil Mitchell Date: Sun Jan 10 20:34:32 2016 +0000 Remove an unnecessary hiding after disabling name shadow warning >--------------------------------------------------------------- 6e1511f9d48bb5198ab6feb4f9a2e6039df5b67f src/Rules/Library.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 03f91aa..788deb6 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -2,7 +2,7 @@ module Rules.Library (buildPackageLibrary, cSources, hSources) where import Data.Char -import Base hiding (splitPath, split) +import Base hiding (splitPath) import Expression import GHC import Oracles From git at git.haskell.org Fri Oct 27 00:36:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try full build on AppVeyor (b05a328) Message-ID: <20171027003629.A9D033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b05a3287007421b0390a1f19f44874899d0c33f9/ghc >--------------------------------------------------------------- commit b05a3287007421b0390a1f19f44874899d0c33f9 Author: Andrey Mokhov Date: Thu Jul 14 22:32:54 2016 +0100 Try full build on AppVeyor >--------------------------------------------------------------- b05a3287007421b0390a1f19f44874899d0c33f9 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index e4d7d52..a3de01a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest From git at git.haskell.org Fri Oct 27 00:36:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix warnings (81fecb8) Message-ID: <20171027003632.3AFC83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/81fecb8b3f23e6e09441b43ae874f0554cedf50b/ghc >--------------------------------------------------------------- commit 81fecb8b3f23e6e09441b43ae874f0554cedf50b Author: Andrey Mokhov Date: Fri Aug 4 21:15:29 2017 +0100 Fix warnings >--------------------------------------------------------------- 81fecb8b3f23e6e09441b43ae874f0554cedf50b hadrian.cabal | 22 ++++++++++++---------- src/Base.hs | 4 ++-- src/Expression.hs | 22 +++++++++++++--------- src/Settings/Builders/Haddock.hs | 6 +++--- 4 files changed, 30 insertions(+), 24 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index da905ff..6dab6d0 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -131,13 +131,15 @@ executable hadrian , unordered-containers == 0.2.* build-tools: alex >= 3.1 , happy >= 1.19.4 - ghc-options: -Wall - -fno-warn-name-shadowing - -rtsopts - -- Disable idle GC to avoid redundant GCs while waiting - -- for external processes - -with-rtsopts=-I0 - -- Don't use parallel GC as the synchronization time tends to eat any - -- benefit. - -with-rtsopts=-qg0 - -threaded + ghc-options: -Wall + -Wincomplete-record-updates + -Wredundant-constraints + -fno-warn-name-shadowing + -rtsopts + -- Disable idle GC to avoid redundant GCs while waiting + -- for external processes + -with-rtsopts=-I0 + -- Don't use parallel GC as the synchronization time tends to eat any + -- benefit. + -with-rtsopts=-qg0 + -threaded diff --git a/src/Base.hs b/src/Base.hs index d717f2a..9e2922b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -6,7 +6,7 @@ module Base ( module Data.Function, module Data.List.Extra, module Data.Maybe, - module Data.Monoid, + module Data.Semigroup, -- * Shake module Development.Shake, @@ -29,7 +29,7 @@ import Data.Char import Data.Function import Data.List.Extra import Data.Maybe -import Data.Monoid +import Data.Semigroup import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath diff --git a/src/Expression.hs b/src/Expression.hs index a09bb8c..251c04f 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -19,7 +19,7 @@ module Expression ( getTopDirectory, -- * Re-exports - module Data.Monoid, + module Data.Semigroup, module Builder, module Package, module Stage, @@ -28,7 +28,7 @@ module Expression ( import Control.Monad.Trans.Reader import Control.Monad.Trans -import Data.Monoid +import Data.Semigroup import Base import Builder @@ -52,9 +52,13 @@ expr = Expr . lift exprIO :: IO a -> Expr a exprIO = Expr . liftIO -instance Monoid a => Monoid (Expr a) where - mempty = Expr $ return mempty - mappend (Expr x) (Expr y) = Expr $ (<>) <$> x <*> y +instance Semigroup a => Semigroup (Expr a) where + Expr x <> Expr y = Expr $ (<>) <$> x <*> y + +-- TODO: The 'Semigroup a' constraint will at some point become redundant. +instance (Semigroup a, Monoid a) => Monoid (Expr a) where + mempty = pure mempty + mappend = (<>) instance Applicative Expr where pure = Expr . pure @@ -78,15 +82,15 @@ type Ways = Expr [Way] -- Basic operations on expressions: -- | Append something to an expression. -append :: Monoid a => a -> Expr a -append = Expr . return +append :: a -> Expr a +append = pure -- | Remove given elements from a list expression. remove :: Eq a => [a] -> Expr [a] -> Expr [a] remove xs e = filter (`notElem` xs) <$> e -- | Apply a predicate to an expression. -applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a +applyPredicate :: (Monoid a, Semigroup a) => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate if bool then expr else mempty @@ -97,7 +101,7 @@ arg = append . return -- | A convenient operator for predicate application. class PredicateLike a where - (?) :: Monoid m => a -> Expr m -> Expr m + (?) :: (Monoid m, Semigroup m) => a -> Expr m -> Expr m infixr 3 ? diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index bb37d0b..4c6f862 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -5,9 +5,9 @@ import Settings.Builders.Ghc -- | Given a version string such as "2.16.2" produce an integer equivalent. versionToInt :: String -> Int -versionToInt s = major * 1000 + minor * 10 + patch - where - [major, minor, patch] = map read . words $ replaceEq '.' ' ' s +versionToInt s = case map read . words $ replaceEq '.' ' ' s of + [major, minor, patch] -> major * 1000 + minor * 10 + patch + _ -> error "versionToInt: cannot parse version." haddockBuilderArgs :: Args haddockBuilderArgs = builder Haddock ? do From git at git.haskell.org Fri Oct 27 00:36:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build.bat work regardless of your current directory, so you can invoke it from the root directory (4be2130) Message-ID: <20171027003632.666143A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4be213017f9d2a64ae1413c1e73678ead571d7e9/ghc >--------------------------------------------------------------- commit 4be213017f9d2a64ae1413c1e73678ead571d7e9 Author: Neil Mitchell Date: Sun Jan 10 22:31:38 2016 +0000 Make build.bat work regardless of your current directory, so you can invoke it from the root directory >--------------------------------------------------------------- 4be213017f9d2a64ae1413c1e73678ead571d7e9 build.bat | 1 + 1 file changed, 1 insertion(+) diff --git a/build.bat b/build.bat index 41b7877..0cf778a 100644 --- a/build.bat +++ b/build.bat @@ -1,3 +1,4 @@ + at cd %~dp0 @mkdir .shake 2> nul @set ghcArgs=--make ^ From git at git.haskell.org Fri Oct 27 00:36:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test Stage2 GHC after the build (29c2402) Message-ID: <20171027003633.348223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/29c2402924e4d7af440771b6eff4a019c37b24c3/ghc >--------------------------------------------------------------- commit 29c2402924e4d7af440771b6eff4a019c37b24c3 Author: Andrey Mokhov Date: Thu Jul 14 23:21:43 2016 +0100 Test Stage2 GHC after the build >--------------------------------------------------------------- 29c2402924e4d7af440771b6eff4a019c37b24c3 appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/appveyor.yml b/appveyor.yml index a3de01a..4f55e5a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -38,3 +38,4 @@ build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + - stack exec -- C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 From git at git.haskell.org Fri Oct 27 00:36:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out generic build infrastructure (48e8b6f) Message-ID: <20171027003636.138A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/48e8b6f223154b9806081e6018099c66dad5a396/ghc >--------------------------------------------------------------- commit 48e8b6f223154b9806081e6018099c66dad5a396 Author: Andrey Mokhov Date: Sat Aug 5 01:02:57 2017 +0100 Factor out generic build infrastructure See #347 >--------------------------------------------------------------- 48e8b6f223154b9806081e6018099c66dad5a396 hadrian.cabal | 2 + src/Expression.hs | 130 ++++++--------------------------------------- src/Hadrian/Expression.hs | 125 +++++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Target.hs | 31 +++++++++++ src/Oracles/ArgsHash.hs | 8 +-- src/Rules/Compile.hs | 6 +-- src/Rules/Configure.hs | 2 +- src/Rules/Data.hs | 4 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 10 ++-- src/Rules/Gmp.hs | 8 +-- src/Rules/Install.hs | 6 +-- src/Rules/Libffi.hs | 6 +-- src/Rules/Library.hs | 8 +-- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 4 +- src/Rules/Test.hs | 2 +- src/Target.hs | 35 ++---------- src/Util.hs | 21 ++++---- 20 files changed, 225 insertions(+), 189 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 48e8b6f223154b9806081e6018099c66dad5a396 From git at git.haskell.org Fri Oct 27 00:36:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move gmp build results to buildRootPath. (a850455) Message-ID: <20171027003636.4EBFD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a850455e1402e79b01bd65cbb0a7e0571969170a/ghc >--------------------------------------------------------------- commit a850455e1402e79b01bd65cbb0a7e0571969170a Author: Andrey Mokhov Date: Sun Jan 10 22:52:19 2016 +0000 Move gmp build results to buildRootPath. See #113. >--------------------------------------------------------------- a850455e1402e79b01bd65cbb0a7e0571969170a shaking-up-ghc.cabal | 2 +- src/Main.hs | 4 +- src/Rules/Data.hs | 10 +-- src/Rules/Generate.hs | 4 +- src/Rules/Gmp.hs | 134 +++++++++++++++++++++++++++++++++++ src/Rules/IntegerGmp.hs | 137 ------------------------------------ src/Rules/Libffi.hs | 24 ++++--- src/Rules/Library.hs | 6 +- src/Settings/Packages/IntegerGmp.hs | 25 ++++--- src/Settings/TargetDirectory.hs | 2 +- 10 files changed, 178 insertions(+), 170 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 a850455e1402e79b01bd65cbb0a7e0571969170a From git at git.haskell.org Fri Oct 27 00:36:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to run Stage2 GHC without Stack (868ffae) Message-ID: <20171027003636.E02AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/868ffae9e2af3e603dc6675b6e6c5a58e4396430/ghc >--------------------------------------------------------------- commit 868ffae9e2af3e603dc6675b6e6c5a58e4396430 Author: Andrey Mokhov Date: Fri Jul 15 00:03:27 2016 +0100 Attempt to run Stage2 GHC without Stack >--------------------------------------------------------------- 868ffae9e2af3e603dc6675b6e6c5a58e4396430 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4f55e5a..4392abe 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -38,4 +38,4 @@ build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest - - stack exec -- C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 + - C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 From git at git.haskell.org Fri Oct 27 00:36:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #144 from ndmitchell/master (ef27c7c) Message-ID: <20171027003640.6791B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef27c7c14f589fdd585c8c9bb2d6264db92a73d0/ghc >--------------------------------------------------------------- commit ef27c7c14f589fdd585c8c9bb2d6264db92a73d0 Merge: a850455 4be2130 Author: Andrey Mokhov Date: Sun Jan 10 22:54:19 2016 +0000 Merge pull request #144 from ndmitchell/master General refactorings >--------------------------------------------------------------- ef27c7c14f589fdd585c8c9bb2d6264db92a73d0 .ghci | 2 ++ build.bat | 2 ++ src/Base.hs | 8 +++++--- src/Expression.hs | 4 ++-- src/Oracles/LookupInPath.hs | 1 - src/Rules.hs | 3 +-- src/Rules/Actions.hs | 7 +++---- src/Rules/Data.hs | 1 - src/Rules/Libffi.hs | 1 - src/Way.hs | 2 +- 10 files changed, 16 insertions(+), 15 deletions(-) diff --cc src/Rules/Data.hs index 5cd2e50,99334f4..fbe22db --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@@ -1,10 -1,7 +1,9 @@@ module Rules.Data (buildPackageData) where +import qualified System.Directory as IO + import Base import Expression - import Extra (replace) import GHC import Oracles import Predicates (registerPackage) From git at git.haskell.org Fri Oct 27 00:36:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Cabal build scripts on CI (fe857d0) Message-ID: <20171027003640.175C53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fe857d074b30bf657216acdda98067aae3577440/ghc >--------------------------------------------------------------- commit fe857d074b30bf657216acdda98067aae3577440 Author: Andrey Mokhov Date: Sat Aug 5 11:34:34 2017 +0100 Use Cabal build scripts on CI >--------------------------------------------------------------- fe857d074b30bf657216acdda98067aae3577440 .travis.yml | 10 +++++----- circle.yml | 4 ++-- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/.travis.yml b/.travis.yml index 49fac80..c23e92a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,10 +18,10 @@ matrix: script: # Run internal Hadrian tests - - ./build.sh selftest + - ./build.cabal.sh selftest # Build GHC - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. @@ -44,10 +44,10 @@ matrix: script: # Run internal Hadrian tests - - ./build.sh selftest + - ./build.cabal.sh selftest # Build GHC - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. @@ -63,7 +63,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 install: # Add Cabal to PATH diff --git a/circle.yml b/circle.yml index 457add7..606664a 100644 --- a/circle.yml +++ b/circle.yml @@ -30,10 +30,10 @@ compile: # XXX: export PATH doesn't work well either, so we use inline env # Self test - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh selftest + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- test: override: From git at git.haskell.org Fri Oct 27 00:36:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try default build flavour on Travis Linux (abfd4e7) Message-ID: <20171027003640.E87063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/abfd4e73326d967c15ac2254f303cf622ae2af40/ghc >--------------------------------------------------------------- commit abfd4e73326d967c15ac2254f303cf622ae2af40 Author: Andrey Mokhov Date: Fri Jul 15 17:24:29 2016 +0100 Try default build flavour on Travis Linux >--------------------------------------------------------------- abfd4e73326d967c15ac2254f303cf622ae2af40 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index b066e89..2b2379f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quick TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=default TARGET= addons: apt: packages: From git at git.haskell.org Fri Oct 27 00:36:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert changes in Way.hs from #144. (697cba53) Message-ID: <20171027003644.161263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/697cba53396690ff295c15b09e03520d2fc07cd5/ghc >--------------------------------------------------------------- commit 697cba53396690ff295c15b09e03520d2fc07cd5 Author: Andrey Mokhov Date: Sun Jan 10 23:34:10 2016 +0000 Revert changes in Way.hs from #144. >--------------------------------------------------------------- 697cba53396690ff295c15b09e03520d2fc07cd5 src/Way.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Way.hs b/src/Way.hs index 974314c..3b1f6c0 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -72,7 +72,7 @@ instance Read Way where uniqueReads token = case reads token of [(unit, "")] -> Just unit _ -> Nothing - units = map uniqueReads . splitOn "_" $ s + units = map uniqueReads . words . replaceEq '_' ' ' $ s result = if Nothing `elem` units then [] else [(wayFromUnits . map fromJust $ units, "")] From git at git.haskell.org Fri Oct 27 00:36:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (0053526) Message-ID: <20171027003648.5415F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0053526eac7df90feba32fe90541c5e4a413da07/ghc >--------------------------------------------------------------- commit 0053526eac7df90feba32fe90541c5e4a413da07 Author: Andrey Mokhov Date: Sat Jul 16 18:09:07 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- 0053526eac7df90feba32fe90541c5e4a413da07 doc/user-settings.md | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 01c3831..1b0a05e 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -17,7 +17,8 @@ buildRootPath = "_build" ## Build flavour -Build _flavour_ is a collection of build settings that fully define a GHC build: +Build _flavour_ is a collection of build settings that fully define a GHC build +(see `src/Flavour.hs`): ```haskell data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. @@ -37,21 +38,22 @@ a few others), which can be activated from the command line, e.g. `--flavour=qui Users can define new build flavours by adding them to `userFlavours` list: ```haskell userFlavour :: Flavour -userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default flavour +userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default build flavour userFlavours :: [Flavour] userFlavours = [userFlavour] ``` -Now `--flavour=user` will run Hadrian with `userFlavour` settings. Note: -`defaultFlavour` is defined in module `Settings.Default`, which must be -imported as `import {-# SOURCE #-} Settings.Default` to handle cyclic -module dependencies. In the following sections we look at specific fields of -the `Flavour` record in more detail. +Now `--flavour=user` will run Hadrian with `userFlavour` settings. In the +following sections we look at specific fields of the `Flavour` record in +more detail. Note: `defaultFlavour`, as well as its individual fields such +as `defaultArgs`, `defaultPackages`, etc. that we use below, are defined in module +`Settings.Default`. Import it as +`import {-# SOURCE #-} Settings.Default` to handle cyclic module dependencies. ## Command line arguments -One of the key features of Hadrian is that users can modify any build command by -changing `userArgs`. The build system will detect the change and will rerun all +One of the key features of Hadrian is that users can easily modify any build command. +The build system will detect the change and will rerun all affected build rules during the next build, without requiring a full rebuild. For example, here is how to pass an extra argument `-O0` to all invocations of @@ -106,7 +108,7 @@ userKnownPackages = [userPackage] userPackage :: Package userPackage = library "user-package" ``` -Note, you will also need to add `userPackage` to a specific build stage by modifying +You will also need to add `userPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting From git at git.haskell.org Fri Oct 27 00:36:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting. (016a71f) Message-ID: <20171027003647.EAC613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/016a71fbb371e2e726ec13e665510bf680dce5cb/ghc >--------------------------------------------------------------- commit 016a71fbb371e2e726ec13e665510bf680dce5cb Author: Andrey Mokhov Date: Sun Jan 10 23:37:20 2016 +0000 Fix formatting. >--------------------------------------------------------------- 016a71fbb371e2e726ec13e665510bf680dce5cb build.bat | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/build.bat b/build.bat index 0cf778a..348537d 100644 --- a/build.bat +++ b/build.bat @@ -1,16 +1,16 @@ @cd %~dp0 @mkdir .shake 2> nul - at set ghcArgs=--make ^ - -Wall ^ + at set ghcArgs=--make ^ + -Wall ^ -fno-warn-name-shadowing ^ - src/Main.hs ^ - -isrc ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=.shake ^ - -j ^ - -O ^ + src/Main.hs ^ + -isrc ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=.shake ^ + -j ^ + -O ^ -o .shake/build @set shakeArgs=--lint ^ From git at git.haskell.org Fri Oct 27 00:36:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (5e1d004) Message-ID: <20171027003647.4A7513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e1d004c4d92f9847f6d96e38c27815429239fea/ghc >--------------------------------------------------------------- commit 5e1d004c4d92f9847f6d96e38c27815429239fea Author: Andrey Mokhov Date: Sun Aug 6 01:24:06 2017 +0100 Minor revision >--------------------------------------------------------------- 5e1d004c4d92f9847f6d96e38c27815429239fea src/Hadrian/Oracles/ArgsHash.hs | 9 +++++---- src/Util.hs | 2 +- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index 0eba6c2..80a170d 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Hadrian.Oracles.ArgsHash ( - TrackArgument, trackAllArguments, checkArgsHash, argsHashOracle + TrackArgument, trackAllArguments, trackArgsHash, argsHashOracle ) where import Control.Monad @@ -34,13 +34,14 @@ newtype ArgsHashKey c b = ArgsHashKey (Target c b) -- in the Shake database. This optimisation is normally harmless, because -- argument list constructors are assumed not to examine target sources, but -- only append them to argument lists where appropriate. -checkArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action () -checkArgsHash t = do +trackArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action () +trackArgsHash t = do let hashedInputs = [ show $ hash (inputs t) ] hashedTarget = target (context t) (builder t) hashedInputs (outputs t) void (askOracle $ ArgsHashKey hashedTarget :: Action Int) --- | Oracle for storing per-target argument list hashes. +-- | This oracle stores per-target argument list hashes in the Shake database, +-- allowing the user to track them between builds using 'trackArgsHash' queries. argsHashOracle :: (ShakeValue c, ShakeValue b) => TrackArgument c b -> Args c b -> Rules () argsHashOracle trackArgument args = void $ addOracle $ \(ArgsHashKey target) -> do diff --git a/src/Util.hs b/src/Util.hs index ed535fe..c4b888d 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -51,7 +51,7 @@ customBuild rs opts target = do argList <- interpret target getArgs verbose <- interpret target verboseCommands let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly - checkArgsHash target -- Rerun the rule if the hash of argList has changed. + trackArgsHash target -- Rerun the rule if the hash of argList has changed. withResources rs $ do putInfo target quietlyUnlessVerbose $ case targetBuilder of From git at git.haskell.org Fri Oct 27 00:36:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move ArgsHash oracle to the library (a432cff) Message-ID: <20171027003643.8D4653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a432cffccd145a0cb8e7822333fac87e54c02753/ghc >--------------------------------------------------------------- commit a432cffccd145a0cb8e7822333fac87e54c02753 Author: Andrey Mokhov Date: Sun Aug 6 00:55:44 2017 +0100 Move ArgsHash oracle to the library See #347 >--------------------------------------------------------------- a432cffccd145a0cb8e7822333fac87e54c02753 hadrian.cabal | 2 +- src/Builder.hs | 15 +------------ src/Hadrian/Oracles/ArgsHash.hs | 49 +++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Target.hs | 3 +-- src/Oracles/ArgsHash.hs | 35 ----------------------------- src/Rules/Oracles.hs | 7 ++++-- src/Rules/Selftest.hs | 8 ++++--- src/Target.hs | 22 +++++++++++++++--- src/Util.hs | 3 ++- 9 files changed, 83 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 a432cffccd145a0cb8e7822333fac87e54c02753 From git at git.haskell.org Fri Oct 27 00:36:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update build flavour related text (59b07fd) Message-ID: <20171027003644.98ECE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59b07fddd177b3813a4dcc5704efbde4dca7857d/ghc >--------------------------------------------------------------- commit 59b07fddd177b3813a4dcc5704efbde4dca7857d Author: Andrey Mokhov Date: Sat Jul 16 17:57:07 2016 +0100 Update build flavour related text See #268. [skip ci] >--------------------------------------------------------------- 59b07fddd177b3813a4dcc5704efbde4dca7857d doc/user-settings.md | 90 +++++++++++++++++++++++++++++++++------------------- 1 file changed, 57 insertions(+), 33 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 1dbfd6f..01c3831 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -15,6 +15,39 @@ buildRootPath :: FilePath buildRootPath = "_build" ``` +## Build flavour + +Build _flavour_ is a collection of build settings that fully define a GHC build: +```haskell +data Flavour = Flavour + { name :: String -- ^ Flavour name, to set from command line. + , args :: Args -- ^ Use these command line arguments. + , packages :: Packages -- ^ Build these packages. + , libraryWays :: Ways -- ^ Build libraries these ways. + , rtsWays :: Ways -- ^ Build RTS these ways. + , splitObjects :: Predicate -- ^ Build split objects. + , buildHaddock :: Predicate -- ^ Build Haddock and documentation. + , dynamicGhcPrograms :: Bool -- ^ Build dynamic GHC programs. + , ghciWithDebugger :: Bool -- ^ Enable GHCi debugger. + , ghcProfiled :: Bool -- ^ Build profiled GHC. + , ghcDebugged :: Bool } -- ^ Build GHC with debug information. +``` +Hadrian provides several built-in flavours (`defaultFlavour`, `quickFlavour`, and +a few others), which can be activated from the command line, e.g. `--flavour=quick`. +Users can define new build flavours by adding them to `userFlavours` list: +```haskell +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default flavour + +userFlavours :: [Flavour] +userFlavours = [userFlavour] +``` +Now `--flavour=user` will run Hadrian with `userFlavour` settings. Note: +`defaultFlavour` is defined in module `Settings.Default`, which must be +imported as `import {-# SOURCE #-} Settings.Default` to handle cyclic +module dependencies. In the following sections we look at specific fields of +the `Flavour` record in more detail. + ## Command line arguments One of the key features of Hadrian is that users can modify any build command by @@ -24,7 +57,9 @@ affected build rules during the next build, without requiring a full rebuild. For example, here is how to pass an extra argument `-O0` to all invocations of GHC when compiling package `cabal`: ```haskell --- | Modify default build command line arguments. +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", args = defaultArgs <> userArgs } + userArgs :: Args userArgs = builder Ghc ? package cabal ? arg "-O0" ``` @@ -50,28 +85,28 @@ path component, excluding any separators. ## Packages -To add or remove a package from a particular build stage, use `userPackages`. As -an example, below we add package `base` to Stage0 and remove package `haskeline` -from Stage1: +Users can add and remove packages from particular build stages. As an example, +below we add package `base` to Stage0 and remove package `haskeline` from Stage1: ```haskell --- | Modify the set of packages that are built by default in each stage. +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", packages = defaultPackages <> userPackages } + userPackages :: Packages userPackages = mconcat [ stage0 ? append [base] , stage1 ? remove [haskeline] ] ``` If you are working on a new GHC package you need to let Hadrian know about it -by setting `userKnownPackages`: +by adding it to `userKnownPackages`: ```haskell --- | Add user defined packages. Don't forget to add them to 'userPackages' too. userKnownPackages :: [Package] -userKnownPackages = [myPackage] +userKnownPackages = [userPackage] --- An example package that lives in "libraries/my-package" directory. -myPackage :: Package -myPackage = library "my-package" +-- An example package that lives in "libraries/user-package" directory. +userPackage :: Package +userPackage = library "user-package" ``` -Note, you will also need to add `myPackage` to a specific build stage by modifying +Note, you will also need to add `userPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting @@ -85,17 +120,12 @@ integerLibrary = integerGmp Packages can be built in a number of ways, such as `vanilla`, `profiling` (with profiling information enabled), and many others as defined in `src/Way.hs`. You -can change the default build ways using `userLibraryWays` and `userRtsWays` settings. -As an example, below we remove `dynamic` from the list of library ways but keep -`rts` package ways unchanged: +can change the default build ways by modifying `libraryWays` and `rtsWays` fields +of the `Flavour` record as required. As an example, below we remove `dynamic` +from the list of library ways but keep `rts` package ways unchanged: ```haskell --- | Modify the set of ways in which library packages are built. -userLibraryWays :: Ways -userLibraryWays = remove [dynamic] - --- | Modify the set of ways in which the 'rts' package is built. -userRtsWays :: Ways -userRtsWays = mempty +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", libraryWays = defaultLibraryWays <> remove [dynamic] } ``` ## Verbose command lines @@ -133,18 +163,12 @@ verboseCommands = return True ## Miscellaneous -Use the following settings to change the default behaviour of Hadrian with respect -to building split objects and Haddock documentation. - +To change the default behaviour of Hadrian with respect to building split +objects and Haddock documentation, override `splitObjects` and `buildHaddock` +fields of the `Flavour` record, for example: ```haskell --- | Control when split objects are generated. Note, due to the GHC bug #11315 --- it is necessary to do a full clean rebuild when changing this option. -splitObjects :: Predicate -splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects - --- | Control when to build Haddock documentation. -buildHaddock :: Predicate -buildHaddock = return cmdBuildHaddock +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", splitObjects = return False, buildHaddock = return True } ``` Hadrian prints various progress info during the build. You can customise how this From git at git.haskell.org Fri Oct 27 00:36:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -fno-warn-name-shadowing to cabal file. (91622d3) Message-ID: <20171027003651.CB6473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/91622d38572cd63c4c94e11f81cff321f01a83d3/ghc >--------------------------------------------------------------- commit 91622d38572cd63c4c94e11f81cff321f01a83d3 Author: Andrey Mokhov Date: Mon Jan 11 00:49:50 2016 +0000 Add -fno-warn-name-shadowing to cabal file. See #143. [skip ci] >--------------------------------------------------------------- 91622d38572cd63c4c94e11f81cff321f01a83d3 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 1f7cfc1..a7b3352 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -122,4 +122,4 @@ executable ghc-shake , transformers >= 0.4 , unordered-containers >= 0.2 default-language: Haskell2010 - ghc-options: -Wall -rtsopts -with-rtsopts=-I0 -j + ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j From git at git.haskell.org Fri Oct 27 00:36:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move DirectoryContents oracle to the library (7ff841e) Message-ID: <20171027003651.3902F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ff841eb492e16bedfb1d72152e5fc0de4d52c77/ghc >--------------------------------------------------------------- commit 7ff841eb492e16bedfb1d72152e5fc0de4d52c77 Author: Andrey Mokhov Date: Sun Aug 6 01:31:02 2017 +0100 Move DirectoryContents oracle to the library See #347 >--------------------------------------------------------------- 7ff841eb492e16bedfb1d72152e5fc0de4d52c77 hadrian.cabal | 3 ++- src/Base.hs | 14 +------------- src/{ => Hadrian}/Oracles/DirectoryContents.hs | 18 +++++++++++------- src/Hadrian/Utilities.hs | 19 +++++++++++++++++++ src/Rules/Install.hs | 3 ++- src/Rules/Oracles.hs | 4 ++-- src/Rules/SourceDist.hs | 3 ++- src/Util.hs | 2 +- 8 files changed, 40 insertions(+), 26 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 121ba74..b757549 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -28,12 +28,13 @@ executable hadrian , GHC , Hadrian.Expression , Hadrian.Oracles.ArgsHash + , Hadrian.Oracles.DirectoryContents , Hadrian.Target + , Hadrian.Utilities , Oracles.Config , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies - , Oracles.DirectoryContents , Oracles.ModuleFiles , Oracles.PackageData , Oracles.Path diff --git a/src/Base.hs b/src/Base.hs index 9e2922b..7443438 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -33,6 +33,7 @@ import Data.Semigroup import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath +import Hadrian.Utilities import System.Console.ANSI import System.IO import System.Info @@ -72,19 +73,6 @@ replaceWhen p to = map (\from -> if p from then to else from) quote :: String -> String quote s = "'" ++ s ++ "'" --- | Normalise a path and convert all path separators to @/@, even on Windows. -unifyPath :: FilePath -> FilePath -unifyPath = toStandard . normaliseEx - --- | Combine paths with a forward slash regardless of platform. -(-/-) :: FilePath -> FilePath -> FilePath -"" -/- b = b -a -/- b - | last a == '/' = a ++ b - | otherwise = a ++ '/' : b - -infixr 6 -/- - -- Explicit definition to avoid dependency on Data.List.Ordered -- | Difference of two ordered lists. minusOrd :: Ord a => [a] -> [a] -> [a] diff --git a/src/Oracles/DirectoryContents.hs b/src/Hadrian/Oracles/DirectoryContents.hs similarity index 82% rename from src/Oracles/DirectoryContents.hs rename to src/Hadrian/Oracles/DirectoryContents.hs index 1f016ff..e52c5c5 100644 --- a/src/Oracles/DirectoryContents.hs +++ b/src/Hadrian/Oracles/DirectoryContents.hs @@ -1,12 +1,15 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} -module Oracles.DirectoryContents ( +module Hadrian.Oracles.DirectoryContents ( directoryContents, directoryContentsOracle, Match (..), matchAll ) where -import System.Directory.Extra +import Control.Monad +import Development.Shake +import Development.Shake.Classes import GHC.Generics +import System.Directory.Extra -import Base +import Hadrian.Utilities newtype DirectoryContents = DirectoryContents (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -14,6 +17,10 @@ newtype DirectoryContents = DirectoryContents (Match, FilePath) data Match = Test FilePattern | Not Match | And [Match] | Or [Match] deriving (Generic, Eq, Show, Typeable) +instance Binary Match +instance Hashable Match +instance NFData Match + -- | A 'Match' expression that always evaluates to 'True' (i.e. always matches). matchAll :: Match matchAll = And [] @@ -30,11 +37,8 @@ matches (Or ms) f = any (`matches` f) ms directoryContents :: Match -> FilePath -> Action [FilePath] directoryContents expr dir = askOracle $ DirectoryContents (expr, dir) +-- | This oracle answers 'directoryContents' queries and tracks the results. directoryContentsOracle :: Rules () directoryContentsOracle = void $ addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ map unifyPath . filter (matches expr) <$> listFilesInside (return . matches expr) dir - -instance Binary Match -instance Hashable Match -instance NFData Match diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs new file mode 100644 index 0000000..2103452 --- /dev/null +++ b/src/Hadrian/Utilities.hs @@ -0,0 +1,19 @@ +module Hadrian.Utilities ( + -- * FilePath manipulation + unifyPath, (-/-) + ) where + +import Development.Shake.FilePath + +-- | Normalise a path and convert all path separators to @/@, even on Windows. +unifyPath :: FilePath -> FilePath +unifyPath = toStandard . normaliseEx + +-- | Combine paths with a forward slash regardless of platform. +(-/-) :: FilePath -> FilePath -> FilePath +"" -/- b = b +a -/- b + | last a == '/' = a ++ b + | otherwise = a ++ '/' : b + +infixr 6 -/- diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 66e57bf..f90b480 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -1,6 +1,8 @@ {-# LANGUAGE FlexibleContexts #-} module Rules.Install (installRules) where +import Hadrian.Oracles.DirectoryContents + import Base import Target import Context @@ -16,7 +18,6 @@ import Rules.Generate import Settings.Packages.Rts import Oracles.Config.Setting import Oracles.Dependencies -import Oracles.DirectoryContents import Oracles.Path import qualified System.Directory as IO diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index a12bec4..59b55d9 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -1,11 +1,11 @@ module Rules.Oracles (oracleRules) where import qualified Hadrian.Oracles.ArgsHash +import qualified Hadrian.Oracles.DirectoryContents import Base import qualified Oracles.Config import qualified Oracles.Dependencies -import qualified Oracles.DirectoryContents import qualified Oracles.ModuleFiles import qualified Oracles.PackageData import qualified Oracles.Path @@ -15,9 +15,9 @@ import Settings oracleRules :: Rules () oracleRules = do Hadrian.Oracles.ArgsHash.argsHashOracle trackArgument getArgs + Hadrian.Oracles.DirectoryContents.directoryContentsOracle Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles - Oracles.DirectoryContents.directoryContentsOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle Oracles.Path.pathOracle diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index 40a4156..879ae34 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -1,9 +1,10 @@ module Rules.SourceDist (sourceDistRules) where +import Hadrian.Oracles.DirectoryContents + import Base import Builder import Oracles.Config.Setting -import Oracles.DirectoryContents import Rules.Clean import UserSettings import Util diff --git a/src/Util.hs b/src/Util.hs index c4b888d..a616b04 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -12,13 +12,13 @@ import qualified System.IO as IO import qualified Control.Exception.Base as IO import Hadrian.Oracles.ArgsHash +import Hadrian.Oracles.DirectoryContents import Base import CmdLineFlag import Context import Expression import GHC -import Oracles.DirectoryContents import Oracles.Path import Oracles.Config.Setting import Settings From git at git.haskell.org Fri Oct 27 00:36:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Typo (e1b6e52) Message-ID: <20171027003652.35AB23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1b6e522c1ca78cede5a3a4e45d2a7e05ef1aa0c/ghc >--------------------------------------------------------------- commit e1b6e522c1ca78cede5a3a4e45d2a7e05ef1aa0c Author: Gabor Greif Date: Sat Jul 16 19:18:30 2016 +0200 Typo >--------------------------------------------------------------- e1b6e522c1ca78cede5a3a4e45d2a7e05ef1aa0c doc/user-settings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 1b0a05e..d4f0f95 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -38,7 +38,7 @@ a few others), which can be activated from the command line, e.g. `--flavour=qui Users can define new build flavours by adding them to `userFlavours` list: ```haskell userFlavour :: Flavour -userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default build flavour +userFlavour = defaultFlavour { name = "user", ... } -- modify the default build flavour userFlavours :: [Flavour] userFlavours = [userFlavour] From git at git.haskell.org Fri Oct 27 00:36:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out general functionality of path oracles to the library (df8e5aa) Message-ID: <20171027003655.12C383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd/ghc >--------------------------------------------------------------- commit df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd Author: Andrey Mokhov Date: Sun Aug 6 02:17:59 2017 +0100 Factor out general functionality of path oracles to the library See #347 >--------------------------------------------------------------- df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd hadrian.cabal | 2 +- src/Base.hs | 4 -- src/Expression.hs | 5 -- src/Hadrian/Oracles/ArgsHash.hs | 6 +- src/Hadrian/Oracles/DirectoryContents.hs | 6 +- src/Hadrian/Oracles/Path.hs | 57 ++++++++++++++++++ src/Hadrian/Utilities.hs | 8 +++ src/Oracles/Path.hs | 99 -------------------------------- src/Rules/Data.hs | 1 - src/Rules/Install.hs | 5 +- src/Rules/Oracles.hs | 4 +- src/Rules/Program.hs | 6 +- src/Rules/Test.hs | 3 +- src/Rules/Wrappers.hs | 16 +++--- src/Settings.hs | 40 ++++++++++++- src/Settings/Builders/Common.hs | 4 +- src/Settings/Builders/Configure.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 8 +-- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Path.hs | 9 ++- src/Util.hs | 9 ++- 22 files changed, 148 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 df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd From git at git.haskell.org Fri Oct 27 00:36:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move bootstrapping.conf to .build. (24e6c28) Message-ID: <20171027003655.9C12C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/24e6c28e5884d49fbd408fe81fad9ca48c1f7f94/ghc >--------------------------------------------------------------- commit 24e6c28e5884d49fbd408fe81fad9ca48c1f7f94 Author: Andrey Mokhov Date: Mon Jan 11 01:29:35 2016 +0000 Move bootstrapping.conf to .build. See #113. >--------------------------------------------------------------- 24e6c28e5884d49fbd408fe81fad9ca48c1f7f94 shaking-up-ghc.cabal | 2 +- src/Base.hs | 13 ------------- src/Oracles/ModuleFiles.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Settings.hs | 4 ++-- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/{TargetDirectory.hs => Paths.hs} | 17 +++++++++++++---- 8 files changed, 20 insertions(+), 24 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index a7b3352..a091020 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -95,7 +95,7 @@ executable ghc-shake , Settings.Packages.RunGhc , Settings.Packages.Touchy , Settings.Packages.Unlit - , Settings.TargetDirectory + , Settings.Paths , Settings.User , Settings.Ways , Stage diff --git a/src/Base.hs b/src/Base.hs index 4b6ad10..8786c26 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -18,7 +18,6 @@ module Base ( -- * Paths shakeFilesPath, configPath, sourcePath, programInplacePath, bootPackageConstraints, packageDependencies, - packageConfiguration, packageConfigurationInitialised, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, renderBox, @@ -44,7 +43,6 @@ import qualified System.Directory as IO import System.IO -- TODO: reexport Stage, etc.? -import Stage -- Build system files and paths shakePath :: FilePath @@ -71,17 +69,6 @@ bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" packageDependencies :: FilePath packageDependencies = shakeFilesPath -/- "package-dependencies" --- TODO: move to buildRootPath, see #113 -packageConfiguration :: Stage -> FilePath -packageConfiguration Stage0 = "libraries/bootstrapping.conf" -packageConfiguration _ = "inplace/lib/package.conf.d" - --- StageN, N > 0, share the same packageConfiguration (see above) -packageConfigurationInitialised :: Stage -> FilePath -packageConfigurationInitialised stage = - shakeFilesPath -/- "package-configuration-initialised-" - ++ stageString (min stage Stage1) - -- Utility functions -- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 33f6138..391990e 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -5,7 +5,7 @@ import Base import Oracles.PackageData import Package import Stage -import Settings.TargetDirectory +import Settings.Paths newtype ModuleFilesKey = ModuleFilesKey ([String], [FilePath]) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 93a121b..7e811ba 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -7,7 +7,7 @@ import Oracles import Rules.Actions import Settings.Builders.Common import Settings.Packages.Rts -import Settings.TargetDirectory +import Settings.Paths import Settings.User -- TODO: this should be moved elsewhere diff --git a/src/Settings.hs b/src/Settings.hs index 229a2f9..12830ca 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,6 +1,6 @@ module Settings ( module Settings.Packages, - module Settings.TargetDirectory, + module Settings.Paths, module Settings.User, module Settings.Ways, getPkgData, getPkgDataList, getTopDirectory, programPath, isLibrary, @@ -12,7 +12,7 @@ import Expression import Oracles import Oracles.ModuleFiles import Settings.Packages -import Settings.TargetDirectory +import Settings.Paths import Settings.User import Settings.Ways diff --git a/src/Settings/Builders/HsCpp.hs b/src/Settings/Builders/HsCpp.hs index 43b9455..c1f1435 100644 --- a/src/Settings/Builders/HsCpp.hs +++ b/src/Settings/Builders/HsCpp.hs @@ -5,7 +5,7 @@ import GHC import Oracles import Predicates (builder) import Settings.Builders.GhcCabal -import Settings.TargetDirectory +import Settings.Paths hsCppBuilderArgs :: Args hsCppBuilderArgs = builder HsCpp ? do diff --git a/src/Settings/Packages/Ghc.hs b/src/Settings/Packages/Ghc.hs index 0830cb6..a7936e9 100644 --- a/src/Settings/Packages/Ghc.hs +++ b/src/Settings/Packages/Ghc.hs @@ -4,7 +4,7 @@ import Expression import GHC (ghc, compiler) import Oracles.Config.Setting import Predicates (builder, builderGhc, package, notStage0) -import Settings.TargetDirectory +import Settings.Paths ghcPackageArgs :: Args ghcPackageArgs = package ghc ? do diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/Paths.hs similarity index 73% rename from src/Settings/TargetDirectory.hs rename to src/Settings/Paths.hs index 6bbef72..bec143b 100644 --- a/src/Settings/TargetDirectory.hs +++ b/src/Settings/Paths.hs @@ -1,14 +1,12 @@ -module Settings.TargetDirectory ( +module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgGhciLibraryFile + pkgGhciLibraryFile, packageConfiguration, packageConfigurationInitialised ) where import Base import Expression import Settings.User --- TODO: rename to Settings.Paths as part of #113 - -- User can override the default target directory settings given below targetDirectory :: Stage -> Package -> FilePath targetDirectory = userTargetDirectory @@ -41,3 +39,14 @@ pkgLibraryFile stage pkg componentId way = do pkgGhciLibraryFile :: Stage -> Package -> String -> FilePath pkgGhciLibraryFile stage pkg componentId = targetPath stage pkg -/- "build" -/- "HS" ++ componentId <.> "o" + +-- TODO: move to buildRootPath, see #113 +packageConfiguration :: Stage -> FilePath +packageConfiguration Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" +packageConfiguration _ = "inplace/lib/package.conf.d" + +-- StageN, N > 0, share the same packageConfiguration (see above) +packageConfigurationInitialised :: Stage -> FilePath +packageConfigurationInitialised stage = + shakeFilesPath -/- "package-configuration-initialised-" + ++ stageString (min stage Stage1) From git at git.haskell.org Fri Oct 27 00:36:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #270 from ggreif/patch-1 (03ffd8e) Message-ID: <20171027003655.C129C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03ffd8e37ba2b55bbba5b97b5a8aa4dfed2afa84/ghc >--------------------------------------------------------------- commit 03ffd8e37ba2b55bbba5b97b5a8aa4dfed2afa84 Merge: 0053526 e1b6e52 Author: Andrey Mokhov Date: Sat Jul 16 18:22:33 2016 +0100 Merge pull request #270 from ggreif/patch-1 Typo [skip ci] >--------------------------------------------------------------- 03ffd8e37ba2b55bbba5b97b5a8aa4dfed2afa84 doc/user-settings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:36:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge all generators into a single file, factor our common functionality into the library. (8e97252) Message-ID: <20171027003658.AF8513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e97252efa426ec9caff762de839ebeded401692/ghc >--------------------------------------------------------------- commit 8e97252efa426ec9caff762de839ebeded401692 Author: Andrey Mokhov Date: Sun Aug 6 14:17:06 2017 +0100 Merge all generators into a single file, factor our common functionality into the library. See #347 >--------------------------------------------------------------- 8e97252efa426ec9caff762de839ebeded401692 hadrian.cabal | 8 - src/Base.hs | 51 +---- src/Expression.hs | 2 +- src/Hadrian/Expression.hs | 13 +- src/Hadrian/Utilities.hs | 56 +++++- src/Oracles/Dependencies.hs | 1 + src/Oracles/ModuleFiles.hs | 1 + src/Rules/Configure.hs | 2 +- src/Rules/Generate.hs | 310 ++++++++++++++++++++++++++++++- src/Rules/Generators/Common.hs | 18 -- src/Rules/Generators/ConfigHs.hs | 102 ---------- src/Rules/Generators/GhcAutoconfH.hs | 37 ---- src/Rules/Generators/GhcBootPlatformH.hs | 57 ------ src/Rules/Generators/GhcPlatformH.hs | 56 ------ src/Rules/Generators/GhcSplit.hs | 27 --- src/Rules/Generators/GhcVersionH.hs | 35 ---- src/Rules/Generators/VersionHs.hs | 18 -- src/Rules/Gmp.hs | 7 +- src/Rules/Libffi.hs | 4 +- src/Rules/Selftest.hs | 1 + src/Rules/Test.hs | 5 +- src/Settings/Builders/Haddock.hs | 2 + src/Settings/Packages/Rts.hs | 7 +- src/Settings/Path.hs | 7 +- src/Way.hs | 3 +- 25 files changed, 394 insertions(+), 436 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 8e97252efa426ec9caff762de839ebeded401692 From git at git.haskell.org Fri Oct 27 00:36:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update Setting.hs (55b0d41) Message-ID: <20171027003659.595CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/55b0d414555297fc845a3ed0196accd5ab454890/ghc >--------------------------------------------------------------- commit 55b0d414555297fc845a3ed0196accd5ab454890 Author: Moritz Angermann Date: Mon Jan 11 11:19:18 2016 +0800 Update Setting.hs Set a sensible default `cmdLineLengthLimit` for os x. >--------------------------------------------------------------- 55b0d414555297fc845a3ed0196accd5ab454890 src/Oracles/Config/Setting.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 0047f03..46d0d33 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -166,6 +166,9 @@ cmdLineLengthLimit = do return $ case (windows, osx) of -- windows (True, False) -> 31000 - -- osx 262144 is ARG_MAX, 33166 experimentally determined - (False, True) -> 262144 - 33166 + -- osx 262144 is ARG_MAX + -- yet when using `xargs` on osx this is reduced by over 20 000. + -- 200 000 seems like a sensible limit. + (False, True) -> 200000 + -- On all other systems, we try this: _ -> 4194304 -- Cabal needs a bit more than 2MB! From git at git.haskell.org Fri Oct 27 00:36:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:36:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop TODO (3b0fab4) Message-ID: <20171027003659.8F6843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b0fab4ddaf709c17757d97416a84a9e3547ce6b/ghc >--------------------------------------------------------------- commit 3b0fab4ddaf709c17757d97416a84a9e3547ce6b Author: Andrey Mokhov Date: Sat Jul 16 23:52:17 2016 +0100 Drop TODO >--------------------------------------------------------------- 3b0fab4ddaf709c17757d97416a84a9e3547ce6b src/UserSettings.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index a0a5d49..b952363 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -14,7 +14,6 @@ import Flavour import GHC import Predicate --- TODO: Update the docs. -- See doc/user-settings.md for instructions. -- | All build results are put into 'buildRootPath' directory. From git at git.haskell.org Fri Oct 27 00:37:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge Predicate into Expression (2bdb94f) Message-ID: <20171027003702.5D4CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c/ghc >--------------------------------------------------------------- commit 2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c Author: Andrey Mokhov Date: Sun Aug 6 22:27:23 2017 +0100 Merge Predicate into Expression >--------------------------------------------------------------- 2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c hadrian.cabal | 1 - src/Builder.hs | 85 +++++++++++++++++++++++--------- src/Context.hs | 24 ++++++++-- src/Expression.hs | 76 +++++++++++++++++++++++------ src/Oracles/Dependencies.hs | 2 +- src/Predicate.hs | 93 ------------------------------------ src/Rules/Cabal.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 1 - src/Rules/Install.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Settings/Builders/Common.hs | 2 - src/Settings/Default.hs | 2 +- src/Settings/Default.hs-boot | 2 +- src/Settings/Flavours/Development.hs | 2 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/Quickest.hs | 2 +- src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Cabal.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 12 ++--- src/Settings/Packages/GhcPrim.hs | 8 ++-- src/Settings/Packages/Ghci.hs | 4 +- src/Settings/Packages/Haddock.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/Path.hs | 2 +- src/Target.hs | 2 +- src/UserSettings.hs | 2 +- src/Util.hs | 2 +- 35 files changed, 181 insertions(+), 175 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 2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c From git at git.haskell.org Fri Oct 27 00:37:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #150 from snowleopard/angerman-patch-1 (754ed41) Message-ID: <20171027003703.0E3933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/754ed41f02f404dc0b735df8f48e855a12f2248f/ghc >--------------------------------------------------------------- commit 754ed41f02f404dc0b735df8f48e855a12f2248f Merge: 24e6c28 55b0d41 Author: Andrey Mokhov Date: Mon Jan 11 03:31:50 2016 +0000 Merge pull request #150 from snowleopard/angerman-patch-1 Update Setting.hs >--------------------------------------------------------------- 754ed41f02f404dc0b735df8f48e855a12f2248f src/Oracles/Config/Setting.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 00:37:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert to quickest build flavour on Travis Linux (118adf2) Message-ID: <20171027003703.675063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/118adf2fa6476460270c3d06d9e935ffcb28ab7d/ghc >--------------------------------------------------------------- commit 118adf2fa6476460270c3d06d9e935ffcb28ab7d Author: Andrey Mokhov Date: Sun Jul 17 00:09:07 2016 +0100 Revert to quickest build flavour on Travis Linux >--------------------------------------------------------------- 118adf2fa6476460270c3d06d9e935ffcb28ab7d .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 2b2379f..dd74f25 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=default TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quickest TARGET= addons: apt: packages: From git at git.haskell.org Fri Oct 27 00:37:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, add a Test module with selftest (28c706d) Message-ID: <20171027003706.CA1D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28c706da832e79687af29b9d64289d6a57b53adf/ghc >--------------------------------------------------------------- commit 28c706da832e79687af29b9d64289d6a57b53adf Author: Neil Mitchell Date: Mon Jan 11 10:47:41 2016 +0000 #146, add a Test module with selftest >--------------------------------------------------------------- 28c706da832e79687af29b9d64289d6a57b53adf shaking-up-ghc.cabal | 3 +++ src/Main.hs | 4 +++- src/Test.hs | 19 +++++++++++++++++++ src/Way.hs | 2 +- 4 files changed, 26 insertions(+), 2 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index a091020..132e84d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -100,6 +100,7 @@ executable ghc-shake , Settings.Ways , Stage , Target + , Test , Way default-extensions: BangPatterns @@ -111,6 +112,7 @@ executable ghc-shake , FlexibleInstances , OverloadedStrings , RecordWildCards + , ScopedTypeVariables build-depends: base , ansi-terminal >= 0.6 , Cabal >= 1.22 @@ -118,6 +120,7 @@ executable ghc-shake , directory >= 1.2 , extra >= 1.4 , mtl >= 2.2 + , QuickCheck >= 2.6 , shake >= 0.15 , transformers >= 0.4 , unordered-containers >= 0.2 diff --git a/src/Main.hs b/src/Main.hs index 63dbd7c..dea793e 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -11,6 +11,7 @@ import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl +import qualified Test main :: IO () main = shakeArgs options rules @@ -25,7 +26,8 @@ main = shakeArgs options rules , Rules.Gmp.gmpRules , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules - , Rules.packageRules ] + , Rules.packageRules + , Test.testRules ] options = shakeOptions { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple diff --git a/src/Test.hs b/src/Test.hs new file mode 100644 index 0000000..75b1b5d --- /dev/null +++ b/src/Test.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE ScopedTypeVariables #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} + +module Test (testRules) where + +import Way +import Development.Shake +import Test.QuickCheck + +instance Arbitrary Way where + arbitrary = wayFromUnits <$> arbitrary + +instance Arbitrary WayUnit where + arbitrary = arbitraryBoundedEnum + +testRules :: Rules () +testRules = + phony "selftest" $ do + liftIO $ quickCheck $ \(x :: Way) -> read (show x) == x diff --git a/src/Way.hs b/src/Way.hs index 3b1f6c0..ba20bd7 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,5 +1,5 @@ module Way ( - WayUnit (..), Way, wayUnit, + WayUnit (..), Way, wayUnit, wayFromUnits, vanilla, profiling, logging, parallel, granSim, threaded, threadedProfiling, threadedLogging, From git at git.haskell.org Fri Oct 27 00:37:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out generic predicates into the library (65c5d7c) Message-ID: <20171027003706.4374B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65c5d7c6f75a583439b6c52ce4a89e6026cf76dc/ghc >--------------------------------------------------------------- commit 65c5d7c6f75a583439b6c52ce4a89e6026cf76dc Author: Andrey Mokhov Date: Sun Aug 6 23:18:51 2017 +0100 Factor out generic predicates into the library See #347 >--------------------------------------------------------------- 65c5d7c6f75a583439b6c52ce4a89e6026cf76dc hadrian.cabal | 3 ++- src/Expression.hs | 16 --------------- src/Hadrian/Expression.hs | 43 +++++++++++++++++++++++++++++++---------- src/Hadrian/Oracles/ArgsHash.hs | 2 +- 4 files changed, 36 insertions(+), 28 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index e1505aa..93a755c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -102,7 +102,6 @@ executable hadrian , UserSettings , Util , Way - default-language: Haskell2010 default-extensions: RecordWildCards other-extensions: DeriveFunctor @@ -110,8 +109,10 @@ executable hadrian , FlexibleInstances , GeneralizedNewtypeDeriving , LambdaCase + , MultiParamTypeClasses , OverloadedStrings , ScopedTypeVariables + , TypeFamilies build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* , Cabal == 2.0.0.2 diff --git a/src/Expression.hs b/src/Expression.hs index 274613c..0442c23 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -29,7 +29,6 @@ module Expression ( import Control.Monad.Extra import Data.Semigroup -import Development.Shake import qualified Hadrian.Expression as H import Hadrian.Expression hiding (Expr, Predicate, Args) @@ -107,18 +106,3 @@ notPackage = notM . package libraryPackage :: Predicate libraryPackage = isLibrary <$> getPackage --- | Does any of the input files match a given pattern? -input :: FilePattern -> Predicate -input f = any (f ?==) <$> getInputs - --- | Does any of the input files match any of the given patterns? -inputs :: [FilePattern] -> Predicate -inputs = anyM input - --- | Does any of the output files match a given pattern? -output :: FilePattern -> Predicate -output f = any (f ?==) <$> getOutputs - --- | Does any of the output files match any of the given patterns? -outputs :: [FilePattern] -> Predicate -outputs = anyM output diff --git a/src/Hadrian/Expression.hs b/src/Hadrian/Expression.hs index 8010695..4022f02 100644 --- a/src/Hadrian/Expression.hs +++ b/src/Hadrian/Expression.hs @@ -1,11 +1,14 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} module Hadrian.Expression ( -- * Expressions Expr, Predicate, Args, -- ** Construction and modification - expr, exprIO, arg, remove, (?), + expr, exprIO, arg, remove, + + -- ** Predicates + (?), input, inputs, output, outputs, -- ** Evaluation interpret, interpretInContext, @@ -14,12 +17,14 @@ module Hadrian.Expression ( getContext, getBuilder, getOutputs, getInputs, getInput, getOutput ) where +import Control.Monad.Extra import Control.Monad.Trans import Control.Monad.Trans.Reader import Data.Semigroup import Development.Shake -import Hadrian.Target +import qualified Hadrian.Target as Target +import Hadrian.Target (Target, target) import Hadrian.Utilities -- | 'Expr' @c b a@ is a computation that produces a value of type 'Action' @a@ @@ -71,7 +76,7 @@ p ? e = do bool <- toPredicate p if bool then e else mempty -instance ToPredicate (Predicate c b) c b where +instance (c ~ c', b ~ b') => ToPredicate (Predicate c b) c' b' where toPredicate = id instance ToPredicate Bool c b where @@ -93,28 +98,46 @@ interpretInContext c = interpret $ target c -- | Get the current build 'Context'. getContext :: Expr c b c -getContext = Expr $ asks context +getContext = Expr $ asks Target.context -- | Get the 'Builder' for the current 'Target'. getBuilder :: Expr c b b -getBuilder = Expr $ asks builder +getBuilder = Expr $ asks Target.builder -- | Get the input files of the current 'Target'. getInputs :: Expr c b [FilePath] -getInputs = Expr $ asks inputs +getInputs = Expr $ asks Target.inputs -- | Run 'getInputs' and check that the result contains one input file only. getInput :: (Show b, Show c) => Expr c b FilePath getInput = Expr $ do target <- ask - fromSingleton ("Exactly one input file expected in " ++ show target) <$> asks inputs + fromSingleton ("Exactly one input file expected in " ++ show target) <$> + asks Target.inputs -- | Get the files produced by the current 'Target'. getOutputs :: Expr c b [FilePath] -getOutputs = Expr $ asks outputs +getOutputs = Expr $ asks Target.outputs -- | Run 'getOutputs' and check that the result contains one output file only. getOutput :: (Show b, Show c) => Expr c b FilePath getOutput = Expr $ do target <- ask - fromSingleton ("Exactly one output file expected in " ++ show target) <$> asks outputs + fromSingleton ("Exactly one output file expected in " ++ show target) <$> + asks Target.outputs + +-- | Does any of the input files match a given pattern? +input :: FilePattern -> Predicate c b +input f = any (f ?==) <$> getInputs + +-- | Does any of the input files match any of the given patterns? +inputs :: [FilePattern] -> Predicate c b +inputs = anyM input + +-- | Does any of the output files match a given pattern? +output :: FilePattern -> Predicate c b +output f = any (f ?==) <$> getOutputs + +-- | Does any of the output files match any of the given patterns? +outputs :: [FilePattern] -> Predicate c b +outputs = anyM output \ No newline at end of file diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index 68b67e2..e07fc3f 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -7,7 +7,7 @@ import Control.Monad import Development.Shake import Development.Shake.Classes -import Hadrian.Expression +import Hadrian.Expression hiding (inputs, outputs) import Hadrian.Target -- | 'TrackArgument' is used to specify the arguments that should be tracked by From git at git.haskell.org Fri Oct 27 00:37:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, run the tests on Appveyor (70b40d9) Message-ID: <20171027003710.A51343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/70b40d9e1ca12be3a3d7de28ee2e5ef8dcf7120c/ghc >--------------------------------------------------------------- commit 70b40d9e1ca12be3a3d7de28ee2e5ef8dcf7120c Author: Neil Mitchell Date: Mon Jan 11 10:47:49 2016 +0000 #146, run the tests on Appveyor >--------------------------------------------------------------- 70b40d9e1ca12be3a3d7de28ee2e5ef8dcf7120c .appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.appveyor.yml b/.appveyor.yml index f4f1d83..f0d0e69 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,4 +30,5 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build + - echo "" | stack --no-terminal exec -- build.bat selftest - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:37:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix the 'unknown symbol stat' issue on Travis Linux (116e64d) Message-ID: <20171027003707.0D6FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/116e64d5596233dcacff48ce7e5e0531f730e6bd/ghc >--------------------------------------------------------------- commit 116e64d5596233dcacff48ce7e5e0531f730e6bd Author: Andrey Mokhov Date: Sun Jul 17 00:52:00 2016 +0100 Attempt to fix the 'unknown symbol stat' issue on Travis Linux See #259. >--------------------------------------------------------------- 116e64d5596233dcacff48ce7e5e0531f730e6bd src/Settings/Packages/Base.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages/Base.hs b/src/Settings/Packages/Base.hs index 261c2bb..dce49e7 100644 --- a/src/Settings/Packages/Base.hs +++ b/src/Settings/Packages/Base.hs @@ -6,5 +6,6 @@ import Predicate import UserSettings basePackageArgs :: Args -basePackageArgs = package base ? - builder GhcCabal ? arg ("--flags=" ++ takeFileName (pkgPath integerLibrary)) +basePackageArgs = package base ? mconcat + [ builder GhcCabal ? arg ("--flags=" ++ takeFileName (pkgPath integerLibrary)) + , builder Cc ? arg "-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. From git at git.haskell.org Fri Oct 27 00:37:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (5dd20f0) Message-ID: <20171027003713.582E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5dd20f0de9043e46bb2a2bdbed94f86c68e33672/ghc >--------------------------------------------------------------- commit 5dd20f0de9043e46bb2a2bdbed94f86c68e33672 Author: Andrey Mokhov Date: Mon Aug 7 01:19:34 2017 +0100 Minor revision >--------------------------------------------------------------- 5dd20f0de9043e46bb2a2bdbed94f86c68e33672 src/Expression.hs | 17 +++++++---------- src/Rules/Generate.hs | 6 +++--- src/Settings.hs | 28 +++++++++++----------------- src/Settings/Builders/Ghc.hs | 20 +++++++++----------- src/Settings/Builders/GhcCabal.hs | 4 ++-- 5 files changed, 32 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 5dd20f0de9043e46bb2a2bdbed94f86c68e33672 From git at git.haskell.org Fri Oct 27 00:37:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #271 from michalt/stack-localcabal/1 (3380e0d) Message-ID: <20171027003715.041C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3380e0d6c1f90a502229390a19298a82d84c14b8/ghc >--------------------------------------------------------------- commit 3380e0d6c1f90a502229390a19298a82d84c14b8 Merge: 116e64d 1281be4 Author: Andrey Mokhov Date: Fri Jul 22 11:45:34 2016 +0200 Merge pull request #271 from michalt/stack-localcabal/1 Change the stack configuration to use the local Cabal lib >--------------------------------------------------------------- 3380e0d6c1f90a502229390a19298a82d84c14b8 hadrian.cabal | 2 +- stack.yaml | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:37:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rewrite chunksOfSize so it doesn't go pear shaped on long inputs (763a518) Message-ID: <20171027003714.C9EBA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/763a518c64ec88acc29db8cc2f7b17955b02a6df/ghc >--------------------------------------------------------------- commit 763a518c64ec88acc29db8cc2f7b17955b02a6df Author: Neil Mitchell Date: Mon Jan 11 11:06:18 2016 +0000 Rewrite chunksOfSize so it doesn't go pear shaped on long inputs >--------------------------------------------------------------- 763a518c64ec88acc29db8cc2f7b17955b02a6df src/Settings/Builders/Ar.hs | 12 ++---------- 1 file changed, 2 insertions(+), 10 deletions(-) diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 86f4310..fc43d45 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -48,13 +48,5 @@ useSuccessiveInvocations path flagArgs fileArgs = do -- | @chunksOfSize size strings@ splits a given list of strings into chunks not -- exceeding the given @size at . chunksOfSize :: Int -> [String] -> [[String]] -chunksOfSize _ [] = [] -chunksOfSize size strings = reverse chunk : chunksOfSize size rest - where - (chunk, rest) = go [] 0 strings - go res _ [] = (res, []) - go res chunkSize (s:ss) = - if newSize > size then (res, s:ss) else go (s:res) newSize ss - where - newSize = chunkSize + length s - +chunksOfSize n = repeatedly f + where f xs = splitAt (max 1 $ length $ takeWhile (<= n) $ scanl1 (+) $ map length xs) xs From git at git.haskell.org Fri Oct 27 00:37:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop append, simplify (e37a5f7) Message-ID: <20171027003709.BA72E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e37a5f773ae3c5584095d487cd831d5674357670/ghc >--------------------------------------------------------------- commit e37a5f773ae3c5584095d487cd831d5674357670 Author: Andrey Mokhov Date: Mon Aug 7 00:25:42 2017 +0100 Drop append, simplify >--------------------------------------------------------------- e37a5f773ae3c5584095d487cd831d5674357670 src/Expression.hs | 12 +-- src/Hadrian/Expression.hs | 0 src/Rules/Libffi.hs | 2 +- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Cc.hs | 6 +- src/Settings/Builders/Common.hs | 19 +--- src/Settings/Builders/Configure.hs | 16 +-- src/Settings/Builders/DeriveConstants.hs | 4 +- src/Settings/Builders/Ghc.hs | 46 ++++----- src/Settings/Builders/GhcCabal.hs | 50 ++++----- src/Settings/Builders/Haddock.hs | 22 ++-- src/Settings/Builders/Hsc2Hs.hs | 30 +++--- src/Settings/Builders/Ld.hs | 4 +- src/Settings/Builders/Make.hs | 6 +- src/Settings/Default.hs | 168 +++++++++++++++---------------- src/Settings/Flavours/Development.hs | 6 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 6 +- src/Settings/Flavours/Quickest.hs | 8 +- src/Settings/Packages/Cabal.hs | 4 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/Haddock.hs | 2 +- src/Settings/Packages/Rts.hs | 18 ++-- src/Settings/Packages/RunGhc.hs | 2 +- 26 files changed, 206 insertions(+), 235 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 e37a5f773ae3c5584095d487cd831d5674357670 From git at git.haskell.org Fri Oct 27 00:37:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move the Config oracle to the library (d3ef19d) Message-ID: <20171027003716.C599F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3ef19d2fa04f9213bb67409869303d08fa52aee/ghc >--------------------------------------------------------------- commit d3ef19d2fa04f9213bb67409869303d08fa52aee Author: Andrey Mokhov Date: Mon Aug 7 01:58:05 2017 +0100 Move the Config oracle to the library See #347 >--------------------------------------------------------------- d3ef19d2fa04f9213bb67409869303d08fa52aee hadrian.cabal | 6 +++--- src/Expression.hs | 2 +- src/{ => Hadrian}/Oracles/Config.hs | 17 ++++++++++++----- src/Oracles/{Config => }/Flag.hs | 7 ++++--- src/Oracles/{Config => }/Setting.hs | 22 ++++++++++++---------- src/Rules/Data.hs | 2 +- src/Rules/Generate.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Install.hs | 17 ++++++++--------- src/Rules/Oracles.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Selftest.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 4 ++-- src/Rules/Wrappers.hs | 2 +- src/Settings.hs | 2 +- src/Settings/Builders/Common.hs | 8 ++++---- src/Settings/Default.hs | 4 ++-- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Packages/Compiler.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcPrim.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/Rts.hs | 4 ++-- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/Path.hs | 2 +- src/Util.hs | 2 +- src/Way.hs | 2 +- 28 files changed, 71 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 d3ef19d2fa04f9213bb67409869303d08fa52aee From git at git.haskell.org Fri Oct 27 00:37:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, add a test helper (077bf47) Message-ID: <20171027003718.BD5983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/077bf477e5059ccbff621ea59a439830890b8f1c/ghc >--------------------------------------------------------------- commit 077bf477e5059ccbff621ea59a439830890b8f1c Author: Neil Mitchell Date: Mon Jan 11 11:06:40 2016 +0000 #146, add a test helper >--------------------------------------------------------------- 077bf477e5059ccbff621ea59a439830890b8f1c src/Test.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Test.hs b/src/Test.hs index 75b1b5d..a55e6e6 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -16,4 +16,8 @@ instance Arbitrary WayUnit where testRules :: Rules () testRules = phony "selftest" $ do - liftIO $ quickCheck $ \(x :: Way) -> read (show x) == x + test $ \(x :: Way) -> read (show x) == x + + +test :: Testable a => a -> Action () +test = liftIO . quickCheck From git at git.haskell.org Fri Oct 27 00:37:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install only after GHC sources are fetched (9e22012) Message-ID: <20171027003718.E75063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e2201243a40e63e010d923005a87dbb26f1b305/ghc >--------------------------------------------------------------- commit 9e2201243a40e63e010d923005a87dbb26f1b305 Author: Andrey Mokhov Date: Fri Jul 22 11:55:50 2016 +0200 Install only after GHC sources are fetched >--------------------------------------------------------------- 9e2201243a40e63e010d923005a87dbb26f1b305 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4392abe..4c3e714 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -15,7 +15,6 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ @@ -24,6 +23,7 @@ install: - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - ghc --version - stack --version - alex --version From git at git.haskell.org Fri Oct 27 00:37:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #146, add tests for chunksOfSize (d001140) Message-ID: <20171027003722.3FF103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d001140948a06ae50475eb919010d192e37b3829/ghc >--------------------------------------------------------------- commit d001140948a06ae50475eb919010d192e37b3829 Author: Neil Mitchell Date: Mon Jan 11 11:06:54 2016 +0000 #146, add tests for chunksOfSize >--------------------------------------------------------------- d001140948a06ae50475eb919010d192e37b3829 src/Settings/Builders/Ar.hs | 2 +- src/Test.hs | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index fc43d45..8cf175f 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -1,4 +1,4 @@ -module Settings.Builders.Ar (arBuilderArgs, arCmd) where +module Settings.Builders.Ar (arBuilderArgs, arCmd, chunksOfSize) where import Base import Expression diff --git a/src/Test.hs b/src/Test.hs index a55e6e6..6cbc557 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -6,6 +6,7 @@ module Test (testRules) where import Way import Development.Shake import Test.QuickCheck +import Settings.Builders.Ar(chunksOfSize) instance Arbitrary Way where arbitrary = wayFromUnits <$> arbitrary @@ -17,6 +18,10 @@ testRules :: Rules () testRules = phony "selftest" $ do test $ \(x :: Way) -> read (show x) == x + test $ \n xs -> + let res = chunksOfSize n xs + in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res + test $ chunksOfSize 3 ["a","b","c","defg","hi","jk"] == [["a","b","c"],["defg"],["hi"],["jk"]] test :: Testable a => a -> Action () From git at git.haskell.org Fri Oct 27 00:38:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Merge. (e519681) Message-ID: <20171027003803.83EB63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e5196817511ddd50939d1f11b8ff2d6d856aa203/ghc >--------------------------------------------------------------- commit e5196817511ddd50939d1f11b8ff2d6d856aa203 Author: Moritz Angermann Date: Tue Jan 12 15:41:55 2016 +0800 Fix Merge. >--------------------------------------------------------------- e5196817511ddd50939d1f11b8ff2d6d856aa203 src/Main.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 6d79cb8..b372fa1 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -11,11 +11,8 @@ import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl -<<<<<<< HEAD -import Oracles.Config.CmdLineFlag (cmdLineOracle, flags) -======= import qualified Test ->>>>>>> master +import Oracles.Config.CmdLineFlag (cmdLineOracle, flags) main :: IO () main = shakeArgsWith options flags $ \cmdLineFlags targets -> From git at git.haskell.org Fri Oct 27 00:38:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #277 from KaiHa/ticket274 (eff3e36) Message-ID: <20171027003806.1DBC13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eff3e36640d0c72e34411acdcbaef71646d884ae/ghc >--------------------------------------------------------------- commit eff3e36640d0c72e34411acdcbaef71646d884ae Merge: e89ab5c ea51eaa Author: Andrey Mokhov Date: Sun Jul 24 17:51:26 2016 +0200 Merge pull request #277 from KaiHa/ticket274 Use in-tree cabal in build.cabal.sh >--------------------------------------------------------------- eff3e36640d0c72e34411acdcbaef71646d884ae build.cabal.sh | 1 + cabal.project | 2 ++ 2 files changed, 3 insertions(+) From git at git.haskell.org Fri Oct 27 00:38:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Provide more useful ToPredicate instances (db56cf4) Message-ID: <20171027003806.23F633A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db56cf4eaf15378c3023de4e66a1285376eb6599/ghc >--------------------------------------------------------------- commit db56cf4eaf15378c3023de4e66a1285376eb6599 Author: Andrey Mokhov Date: Mon Aug 14 23:07:05 2017 +0100 Provide more useful ToPredicate instances >--------------------------------------------------------------- db56cf4eaf15378c3023de4e66a1285376eb6599 src/Hadrian/Expression.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Hadrian/Expression.hs b/src/Hadrian/Expression.hs index dad9d32..b781cdd 100644 --- a/src/Hadrian/Expression.hs +++ b/src/Hadrian/Expression.hs @@ -75,14 +75,14 @@ p ? e = do bool <- toPredicate p if bool then e else mempty -instance (c ~ c', b ~ b') => ToPredicate (Predicate c b) c' b' where - toPredicate = id - instance ToPredicate Bool c b where toPredicate = pure -instance ToPredicate (Action Bool) c b where - toPredicate = expr +instance ToPredicate p c b => ToPredicate (Action p) c b where + toPredicate = toPredicate . expr + +instance (c ~ c', b ~ b', ToPredicate p c' b') => ToPredicate (Expr c b p) c' b' where + toPredicate p = toPredicate =<< p -- | Interpret a given expression according to the given 'Target'. interpret :: Target c b -> Expr c b a -> Action a From git at git.haskell.org Fri Oct 27 00:38:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adds Pony (5dd8bbb) Message-ID: <20171027003807.14D433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5dd8bbb0090ebef875650ca7de8bc87aa37f54c9/ghc >--------------------------------------------------------------- commit 5dd8bbb0090ebef875650ca7de8bc87aa37f54c9 Author: Moritz Angermann Date: Tue Jan 12 15:42:56 2016 +0800 Adds Pony This fixes #92 for good. Together this fixes #134 almost entirely. >--------------------------------------------------------------- 5dd8bbb0090ebef875650ca7de8bc87aa37f54c9 src/Base.hs | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index c733226..ffe06d8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -142,26 +142,52 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg +-- | Render an action. renderAction :: String -> String -> String -> Action String renderAction what input output = buildInfo >>= return . \case Normal -> renderBox [ what , " input:" ++ input , " => output:" ++ output ] Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output - Pony -> " *** PONY NOT YET SUPPORTED ***" + Pony -> renderPony [ what + , " input:" ++ input + , " => output:" ++ output ] Dot -> "." None -> "" +-- | Render the successful build of a program renderProgram :: String -> String -> String -> Action String renderProgram name bin synopsis = return $ renderBox [ "Successfully built program " ++ name , "Executable: " ++ bin , "Program synopsis: " ++ synopsis ++ "."] +-- | Render the successful built of a library renderLibrary :: String -> String -> String -> Action String renderLibrary name lib synopsis = return $ renderBox [ "Successfully built library " ++ name , "Library: " ++ lib , "Library synopsis: " ++ synopsis ++ "."] +-- | Render the given set of lines next to our favorit unicorn Robert. +renderPony :: [String] -> String +renderPony ls = + unlines $ take (max (length ponyLines) (length boxLines)) $ + zipWith (++) (ponyLines ++ repeat ponyPadding) (boxLines ++ repeat "") + where + ponyLines :: [String] + ponyLines = [ " ,;,,;'" + , " ,;;'( Robert the spitting unicorn" + , " __ ,;;' ' \\ wants you to know" + , " /' '\\'~~'~' \\ /'\\.) that a task " + , " ,;( ) / |. / just finished! " + , " ,;' \\ /-.,,( ) \\ " + , " ^ ) / ) / )| Almost there! " + , " || || \\) " + , " (_\\ (_\\ " ] + ponyPadding :: String + ponyPadding = " " + boxLines :: [String] + boxLines = ["", "", ""] ++ (lines . renderBox $ ls) + -- | Render the given set of lines in a nice box of ASCII. -- -- The minimum width and whether to use Unicode symbols are hardcoded in the From git at git.haskell.org Fri Oct 27 00:38:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make generatedDependencies an Expr [FilePath] (234b41b) Message-ID: <20171027003810.6BF543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/234b41b171ad31ecbfec476f8f47202cac6f10cc/ghc >--------------------------------------------------------------- commit 234b41b171ad31ecbfec476f8f47202cac6f10cc Author: Michal Terepeta Date: Sun Jul 24 16:37:11 2016 +0200 Make generatedDependencies an Expr [FilePath] This fixes a TODO to change the `generatedDependencies` to use `Expr`. Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 234b41b171ad31ecbfec476f8f47202cac6f10cc src/Rules/Data.hs | 12 ++++---- src/Rules/Generate.hs | 79 ++++++++++++++++++++++++++++----------------------- 2 files changed, 49 insertions(+), 42 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 959a7ec..4208570 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -25,7 +25,7 @@ buildPackageData context at Context {..} = do inTreeMk %> \mk -> do -- Make sure all generated dependencies are in place before proceeding. - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies -- GhcCabal may run the configure script, so we depend on it. whenM (doesFileExist $ configure <.> "ac") $ need [configure] @@ -59,7 +59,7 @@ buildPackageData context at Context {..} = do -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps. priority 2.0 $ do when (package == hp2ps) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies includes <- interpretInContext context $ fromDiffExpr includesArgs let prefix = fixKey (buildPath context) ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" @@ -76,7 +76,7 @@ buildPackageData context at Context {..} = do putSuccess $ "| Successfully generated " ++ mk when (package == unlit) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies let prefix = fixKey (buildPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = unlit" @@ -86,7 +86,7 @@ buildPackageData context at Context {..} = do putSuccess $ "| Successfully generated " ++ mk when (package == touchy) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies let prefix = fixKey (buildPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = touchy" @@ -98,7 +98,7 @@ buildPackageData context at Context {..} = do -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. when (package == ghcCabal && stage == Stage0) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies let prefix = fixKey (buildPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = ghc-cabal" @@ -110,7 +110,7 @@ buildPackageData context at Context {..} = do when (package == rts && stage == Stage1) $ do dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies windows <- windowsHost let prefix = fixKey (buildPath context) ++ "_" dirs = [ ".", "hooks", "sm", "eventlog", "linker" ] diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 17f51a5..415692b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -10,6 +10,8 @@ import Context import Expression import GHC import Oracles.ModuleFiles +import Predicate ( (?) ) +import qualified Predicate as Predicate import Rules.Actions import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH @@ -46,10 +48,11 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -ghcPrimDependencies :: Stage -> [FilePath] -ghcPrimDependencies stage = (buildPath (vanillaContext stage ghcPrim) -/-) <$> - [ "autogen/GHC/Prim.hs" - , "GHC/PrimopWrappers.hs" ] +ghcPrimDependencies :: Expr [FilePath] +ghcPrimDependencies = getStage >>= \stage -> + let prependPath x = buildPath (vanillaContext stage ghcPrim) -/- x + in return $ + fmap prependPath [ "autogen/GHC/Prim.hs" , "GHC/PrimopWrappers.hs" ] derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" @@ -61,39 +64,43 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) , "GHCConstantsHaskellType.hs" , "GHCConstantsHaskellWrappers.hs" ] -compilerDependencies :: Stage -> [FilePath] -compilerDependencies stage = - [ platformH stage ] - ++ includesDependencies - ++ [ gmpLibraryH | stage > Stage0 ] - ++ filter (const $ stage > Stage0) libffiDependencies - ++ derivedConstantsDependencies - ++ fmap (buildPath (vanillaContext stage compiler) -/-) - [ "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-fixity.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-list.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-strictness.hs-incl" - , "primop-tag.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tys.hs-incl" - , "primop-vector-uniques.hs-incl" ] - --- TODO: Turn this into a FilePaths expression -generatedDependencies :: Stage -> Package -> [FilePath] -generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage - | pkg == ghcPrim = ghcPrimDependencies stage - | pkg == rts = libffiDependencies ++ includesDependencies +compilerDependencies :: Expr [FilePath] +compilerDependencies = getStage >>= \stage -> + let prependBuildPath x = buildPath (vanillaContext stage compiler) -/- x + in mconcat $ + [ return $ (platformH stage) + : includesDependencies ++ derivedConstantsDependencies - | stage == Stage0 = includesDependencies - | otherwise = [] + , Predicate.notStage0 ? return (gmpLibraryH : libffiDependencies) + , return $ fmap prependBuildPath + [ "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-fixity.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-list.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-strictness.hs-incl" + , "primop-tag.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tys.hs-incl" + , "primop-vector-uniques.hs-incl" + ] + ] + +generatedDependencies :: Expr [FilePath] +generatedDependencies = mconcat + [ Predicate.package compiler ? compilerDependencies + , Predicate.package ghcPrim ? ghcPrimDependencies + , Predicate.package rts ? return ( + libffiDependencies + ++ includesDependencies + ++ derivedConstantsDependencies) + , Predicate.stage0 ? return includesDependencies + ] generate :: FilePath -> Context -> Expr String -> Action () generate file context expr = do From git at git.haskell.org Fri Oct 27 00:38:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor command line arguments and flavours (0530e0d) Message-ID: <20171027003810.88FA73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0530e0df5b9076b1643a2d3b6a4abf4f31041f3c/ghc >--------------------------------------------------------------- commit 0530e0df5b9076b1643a2d3b6a4abf4f31041f3c Author: Andrey Mokhov Date: Mon Aug 14 23:12:52 2017 +0100 Refactor command line arguments and flavours * Get rid of unsafePerformIO using shakeExtra * Move diagnostic info utilities to the library See #347 >--------------------------------------------------------------- 0530e0df5b9076b1643a2d3b6a4abf4f31041f3c hadrian.cabal | 2 +- src/CmdLineFlag.hs | 128 ------------------------------ src/CommandLine.hs | 128 ++++++++++++++++++++++++++++++ src/Flavour.hs | 24 +++--- src/Hadrian/Utilities.hs | 160 ++++++++++++++++++++++++++++++++++++-- src/Main.hs | 58 ++++++++------ src/Rules.hs | 9 +-- src/Rules/Cabal.hs | 1 - src/Rules/Configure.hs | 9 ++- src/Rules/Data.hs | 1 - src/Rules/Documentation.hs | 3 +- src/Rules/Generate.hs | 18 +++-- src/Rules/Gmp.hs | 1 - src/Rules/Install.hs | 6 +- src/Rules/Library.hs | 3 +- src/Rules/Program.hs | 18 +++-- src/Rules/Register.hs | 1 - src/Rules/Selftest.hs | 1 - src/Rules/SourceDist.hs | 1 - src/Rules/Test.hs | 3 +- src/Settings.hs | 40 +++++----- src/Settings/Builders/Ghc.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 7 +- src/Settings/Default.hs | 18 +++-- src/Settings/Packages/Base.hs | 8 +- src/Settings/Packages/Compiler.hs | 4 +- src/UserSettings.hs | 20 +++-- src/Utilities.hs | 131 ++++++------------------------- 28 files changed, 443 insertions(+), 365 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 0530e0df5b9076b1643a2d3b6a4abf4f31041f3c From git at git.haskell.org Fri Oct 27 00:38:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace Oracle with IO Ref (f794e73) Message-ID: <20171027003810.91BAB3A5EC@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f794e7369f2b2b6e86f27d9587e5baf74cfc73e3/ghc >--------------------------------------------------------------- commit f794e7369f2b2b6e86f27d9587e5baf74cfc73e3 Author: Moritz Angermann Date: Tue Jan 12 18:03:59 2016 +0800 Replace Oracle with IO Ref >--------------------------------------------------------------- f794e7369f2b2b6e86f27d9587e5baf74cfc73e3 src/Base.hs | 21 ++++++++--------- src/Main.hs | 8 +++---- src/Oracles/Config/CmdLineFlag.hs | 48 ++++++++++++++++----------------------- src/Rules/Actions.hs | 6 ++--- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 4 ++-- 6 files changed, 40 insertions(+), 49 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 f794e7369f2b2b6e86f27d9587e5baf74cfc73e3 From git at git.haskell.org Fri Oct 27 00:38:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #278 from michalt/generated-dependencies/1 (14a596a) Message-ID: <20171027003814.3AE353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14a596a8086249053dc291e8cb6b306b6e196cf5/ghc >--------------------------------------------------------------- commit 14a596a8086249053dc291e8cb6b306b6e196cf5 Merge: eff3e36 234b41b Author: Andrey Mokhov Date: Tue Aug 2 00:00:07 2016 +0200 Merge pull request #278 from michalt/generated-dependencies/1 Make generatedDependencies an Expr [FilePath] >--------------------------------------------------------------- 14a596a8086249053dc291e8cb6b306b6e196cf5 src/Rules/Data.hs | 12 ++++---- src/Rules/Generate.hs | 79 ++++++++++++++++++++++++++++----------------------- 2 files changed, 49 insertions(+), 42 deletions(-) From git at git.haskell.org Fri Oct 27 00:38:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move file system operations to the library (58e2d05) Message-ID: <20171027003814.D5BF63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/58e2d05064d8102914c7b887df6e2090c1d906db/ghc >--------------------------------------------------------------- commit 58e2d05064d8102914c7b887df6e2090c1d906db Author: Andrey Mokhov Date: Tue Aug 15 00:31:47 2017 +0100 Move file system operations to the library See #347 >--------------------------------------------------------------- 58e2d05064d8102914c7b887df6e2090c1d906db src/Hadrian/Oracles/DirectoryContents.hs | 17 +++++- src/Hadrian/Oracles/Path.hs | 6 +- src/Hadrian/Utilities.hs | 96 ++++++++++++++++++++++++++++--- src/Rules/Clean.hs | 1 - src/Rules/Wrappers.hs | 3 +- src/Utilities.hs | 97 ++------------------------------ 6 files changed, 112 insertions(+), 108 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 58e2d05064d8102914c7b887df6e2090c1d906db From git at git.haskell.org Fri Oct 27 00:38:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add dependencies, fix #155. (85799a5) Message-ID: <20171027003814.E01173A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/85799a569efbace0d6fdc168c6ddff0a015d1df8/ghc >--------------------------------------------------------------- commit 85799a569efbace0d6fdc168c6ddff0a015d1df8 Author: Andrey Mokhov Date: Tue Jan 12 17:25:00 2016 +0000 Add dependencies, fix #155. [skip ci] >--------------------------------------------------------------- 85799a569efbace0d6fdc168c6ddff0a015d1df8 README.md | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index fe6a909..823e472 100644 --- a/README.md +++ b/README.md @@ -12,7 +12,7 @@ on the [wiki page][ghc-shake-wiki] and in this [blog post][shake-blog-post]. This is supposed to go into the `shake-build` directory of the GHC source tree. -[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc) +[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc). Trying it --------- @@ -23,6 +23,9 @@ identical to those for the `make` build system. This means that you don't need to adjust anything if you are already familiar with building ghc using the `make` build system. +Furthermore, we depend on the following packages which need to be installed: +`ansi-terminal`, `mtl`, `shake`, `quickcheck`. + ### Getting the source and configuring GHC ```bash @@ -51,7 +54,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (see [#32](https://github.com/snowleopard/shaking-up-ghc/issues/32)). +To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (#131). How to contribute From git at git.haskell.org Fri Oct 27 00:38:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (c547d12) Message-ID: <20171027003817.F00553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c547d12d30964f07671974d5f43c5d5e3cf56b7d/ghc >--------------------------------------------------------------- commit c547d12d30964f07671974d5f43c5d5e3cf56b7d Author: Andrey Mokhov Date: Tue Aug 2 02:27:30 2016 +0200 Minor revision See #278 >--------------------------------------------------------------- c547d12d30964f07671974d5f43c5d5e3cf56b7d src/Rules/Generate.hs | 77 ++++++++++++++++++++++++--------------------------- 1 file changed, 36 insertions(+), 41 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 415692b..988b3d7 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -6,12 +6,11 @@ module Rules.Generate ( import qualified System.Directory as IO import Base -import Context +import Context hiding (package) import Expression import GHC import Oracles.ModuleFiles -import Predicate ( (?) ) -import qualified Predicate as Predicate +import Predicate import Rules.Actions import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH @@ -43,16 +42,16 @@ platformH stage = buildPath (vanillaContext stage compiler) -/- "ghc_boot_platfo -- TODO: move generated files to buildRootPath, see #113 includesDependencies :: [FilePath] -includesDependencies = ("includes" -/-) <$> +includesDependencies = fmap ("includes" -/-) [ "ghcautoconf.h" , "ghcplatform.h" , "ghcversion.h" ] ghcPrimDependencies :: Expr [FilePath] -ghcPrimDependencies = getStage >>= \stage -> - let prependPath x = buildPath (vanillaContext stage ghcPrim) -/- x - in return $ - fmap prependPath [ "autogen/GHC/Prim.hs" , "GHC/PrimopWrappers.hs" ] +ghcPrimDependencies = do + stage <- getStage + let path = buildPath $ vanillaContext stage ghcPrim + return [path -/- "autogen/GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"] derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" @@ -65,42 +64,38 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) , "GHCConstantsHaskellWrappers.hs" ] compilerDependencies :: Expr [FilePath] -compilerDependencies = getStage >>= \stage -> - let prependBuildPath x = buildPath (vanillaContext stage compiler) -/- x - in mconcat $ - [ return $ (platformH stage) - : includesDependencies - ++ derivedConstantsDependencies - , Predicate.notStage0 ? return (gmpLibraryH : libffiDependencies) - , return $ fmap prependBuildPath - [ "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-fixity.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-list.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-strictness.hs-incl" - , "primop-tag.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tys.hs-incl" - , "primop-vector-uniques.hs-incl" - ] - ] +compilerDependencies = do + stage <- getStage + let path = buildPath $ vanillaContext stage compiler + mconcat [ return [platformH stage] + , return includesDependencies + , return derivedConstantsDependencies + , notStage0 ? return (gmpLibraryH : libffiDependencies) + , return $ fmap (path -/-) + [ "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-fixity.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-list.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-strictness.hs-incl" + , "primop-tag.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tys.hs-incl" + , "primop-vector-uniques.hs-incl" ] ] generatedDependencies :: Expr [FilePath] generatedDependencies = mconcat - [ Predicate.package compiler ? compilerDependencies - , Predicate.package ghcPrim ? ghcPrimDependencies - , Predicate.package rts ? return ( - libffiDependencies - ++ includesDependencies - ++ derivedConstantsDependencies) - , Predicate.stage0 ? return includesDependencies - ] + [ package compiler ? compilerDependencies + , package ghcPrim ? ghcPrimDependencies + , package rts ? return (libffiDependencies + ++ includesDependencies + ++ derivedConstantsDependencies) + , stage0 ? return includesDependencies ] generate :: FilePath -> Context -> Expr String -> Action () generate file context expr = do From git at git.haskell.org Fri Oct 27 00:38:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (a482625) Message-ID: <20171027003818.947F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a482625b00358fd14646bac23a7911113c394157/ghc >--------------------------------------------------------------- commit a482625b00358fd14646bac23a7911113c394157 Author: Andrey Mokhov Date: Tue Jan 12 17:37:02 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- a482625b00358fd14646bac23a7911113c394157 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 823e472..4226415 100644 --- a/README.md +++ b/README.md @@ -17,7 +17,7 @@ This is supposed to go into the `shake-build` directory of the GHC source tree. Trying it --------- -Please see the [Preparation][ghc-preparation] on the haskell wiki +Please see the [Preparation][ghc-preparation] on the GHC wiki for general preparation. The preparation steps for the `shake` build system are identical to those for the `make` build system. This means that you don't need to adjust anything if you are already familiar with building ghc using the `make` @@ -54,7 +54,7 @@ Also see the [Building GHC on Windows guide][ghc-windows-building-guide]. ### Resetting the build -To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality (#131). +To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. This is a temporary solution; we are working on a proper reset functionality ([#131](https://github.com/snowleopard/shaking-up-ghc/issues/131)). How to contribute From git at git.haskell.org Fri Oct 27 00:38:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix compile error on GHC 8.2+ (5026b9c) Message-ID: <20171027003818.46EE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5026b9c6f145f748e0e8b1621e3af482c475b00d/ghc >--------------------------------------------------------------- commit 5026b9c6f145f748e0e8b1621e3af482c475b00d Author: Andrey Mokhov Date: Tue Aug 15 00:44:24 2017 +0100 Fix compile error on GHC 8.2+ >--------------------------------------------------------------- 5026b9c6f145f748e0e8b1621e3af482c475b00d src/CommandLine.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index 18ce2ec..dbcf41f 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -3,10 +3,11 @@ module CommandLine ( cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects ) where -import Data.Dynamic +import Data.Dynamic (Dynamic) import Data.Either import qualified Data.HashMap.Strict as Map import Data.List.Extra +import Data.Typeable (TypeRep) import Development.Shake hiding (Normal) import Hadrian.Utilities import System.Console.GetOpt From git at git.haskell.org Fri Oct 27 00:38:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export Dynamic and Typeable bits (d2ca01b) Message-ID: <20171027003821.DCF513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2ca01bbdf7354c0e88af711696ac333040d2374/ghc >--------------------------------------------------------------- commit d2ca01bbdf7354c0e88af711696ac333040d2374 Author: Andrey Mokhov Date: Tue Aug 15 02:11:02 2017 +0100 Re-export Dynamic and Typeable bits >--------------------------------------------------------------- d2ca01bbdf7354c0e88af711696ac333040d2374 src/CommandLine.hs | 2 -- src/Hadrian/Utilities.hs | 5 ++++- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index dbcf41f..5688d6f 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -3,11 +3,9 @@ module CommandLine ( cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects ) where -import Data.Dynamic (Dynamic) import Data.Either import qualified Data.HashMap.Strict as Map import Data.List.Extra -import Data.Typeable (TypeRep) import Development.Shake hiding (Normal) import Hadrian.Utilities import System.Console.GetOpt diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 0791d44..74c10b4 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -19,7 +19,10 @@ module Hadrian.Utilities ( UseColour (..), putColoured, BuildProgressColour (..), putBuild, SuccessColour (..), putSuccess, ProgressInfo (..), putProgressInfo, renderAction, renderProgram, renderLibrary, renderBox, - renderUnicorn + renderUnicorn, + + -- * Useful re-exports + Dynamic, fromDynamic, toDyn, TypeRep, typeOf ) where import Control.Monad.Extra From git at git.haskell.org Fri Oct 27 00:38:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move need of inplaceLibCopyTargets to top-level (#388) (0c67f7d) Message-ID: <20171027003825.E51273A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c67f7d21536a4ca305758516bce7ccd0f40db7b/ghc >--------------------------------------------------------------- commit 0c67f7d21536a4ca305758516bce7ccd0f40db7b Author: Zhen Zhang Date: Tue Aug 15 20:34:32 2017 +0800 Move need of inplaceLibCopyTargets to top-level (#388) >--------------------------------------------------------------- 0c67f7d21536a4ca305758516bce7ccd0f40db7b src/Rules.hs | 12 +++++++----- src/Rules/Program.hs | 5 ++--- 2 files changed, 9 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index d55a578..4077dc6 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -24,7 +24,8 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings -import Settings.Path +import Settings.Path (inplaceLibCopyTargets, pkgLibraryFile, + pkgSetupConfigFile, pkgHaddockFile) import Target import Utilities @@ -41,10 +42,11 @@ topLevelTargets = action $ do libs <- concatForM [Stage0, Stage1] $ \stage -> concatForM libraryPackages $ packageTargets stage prgs <- concatForM programsStage1Only $ packageTargets Stage0 - return $ libs ++ prgs - else - concatForM allStages $ \stage -> - concatForM (knownPackages \\ [rts, libffi]) $ packageTargets stage + return $ libs ++ prgs ++ inplaceLibCopyTargets + else do + targets <- concatForM allStages $ \stage -> + concatForM (knownPackages \\ [rts, libffi]) $ packageTargets stage + return $ targets ++ inplaceLibCopyTargets -- | Return the list of targets associated with a given 'Stage' and 'Package'. packageTargets :: Stage -> Package -> Action [FilePath] diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 6ca514f..edef17f 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -11,7 +11,8 @@ import Oracles.PackageData import Oracles.Setting import Rules.Wrappers import Settings -import Settings.Path +import Settings.Path (buildPath, inplaceLibBinPath, rtsContext, objectPath, + inplaceLibPath, inplaceBinPath) import Target import Utilities @@ -26,8 +27,6 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do context' <- programContext stage package buildBinaryAndWrapper rs context' bin - when (package == ghc) $ want inplaceLibCopyTargets - -- Rules for programs built in install directories when (stage == Stage0 || package == ghc) $ do -- Some binaries in inplace/bin are wrapped From git at git.haskell.org Fri Oct 27 00:38:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create .build/stage0 for libffi to be moved to. (31dbe92) Message-ID: <20171027003825.E18C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31dbe92dcfd55c17c8395945050aad240fdd640c/ghc >--------------------------------------------------------------- commit 31dbe92dcfd55c17c8395945050aad240fdd640c Author: Andrey Mokhov Date: Tue Jan 12 21:54:53 2016 +0000 Create .build/stage0 for libffi to be moved to. Fix #160. [skip ci] >--------------------------------------------------------------- 31dbe92dcfd55c17c8395945050aad240fdd640c src/Rules/Libffi.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 7e811ba..7dd0376 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -75,6 +75,8 @@ libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] + createDirectory $ buildRootPath -/- "stage0" + tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] when (length tarballs /= 1) $ putError $ "libffiRules: exactly one libffi tarball expected" From git at git.haskell.org Fri Oct 27 00:38:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Major refactoring of path settings (9b70568) Message-ID: <20171027003830.1BB2E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b70568615e2763ff782279be28286373b59d8ff/ghc >--------------------------------------------------------------- commit 9b70568615e2763ff782279be28286373b59d8ff Author: Andrey Mokhov Date: Wed Aug 16 03:45:51 2017 +0100 Major refactoring of path settings * Move buildRoot into the Action monad, so it can be configured from command line in future * Move settings from Setting.Path to Base and Context * Simplify build rule matching and prepare to factoring out common build rules into the library, #347 >--------------------------------------------------------------- 9b70568615e2763ff782279be28286373b59d8ff hadrian.cabal | 2 - src/Base.hs | 76 +++++++++- src/Context.hs | 101 ++++++++++++- src/Expression.hs | 6 +- src/GHC.hs | 70 ++++++++- src/Hadrian/Expression.hs | 6 +- src/Hadrian/Utilities.hs | 64 ++++---- src/Main.hs | 9 +- src/Oracles/ModuleFiles.hs | 32 ++-- src/Rules.hs | 15 +- src/Rules/Cabal.hs | 9 +- src/Rules/Clean.hs | 10 +- src/Rules/Compile.hs | 24 +-- src/Rules/Data.hs | 36 +++-- src/Rules/Dependencies.hs | 3 +- src/Rules/Documentation.hs | 45 +++--- src/Rules/Generate.hs | 100 +++++++------ src/Rules/Gmp.hs | 77 ++++++---- src/Rules/Install.hs | 36 +++-- src/Rules/Libffi.hs | 60 +++++--- src/Rules/Library.hs | 26 ++-- src/Rules/Program.hs | 8 +- src/Rules/Register.hs | 47 ++++-- src/Rules/Selftest.hs | 17 --- src/Rules/Test.hs | 1 - src/Rules/Wrappers.hs | 41 +++--- src/Settings.hs | 19 +-- src/Settings/Builders/Common.hs | 17 ++- src/Settings/Builders/Configure.hs | 34 +++-- src/Settings/Builders/DeriveConstants.hs | 21 +-- src/Settings/Builders/Ghc.hs | 12 +- src/Settings/Builders/GhcCabal.hs | 21 ++- src/Settings/Builders/GhcPkg.hs | 4 +- src/Settings/Builders/Haddock.hs | 11 +- src/Settings/Builders/HsCpp.hs | 8 +- src/Settings/Builders/Hsc2Hs.hs | 5 +- src/Settings/Builders/Make.hs | 10 +- src/Settings/Install.hs | 11 -- src/Settings/Packages/Ghc.hs | 9 +- src/Settings/Packages/IntegerGmp.hs | 7 +- src/Settings/Packages/Rts.hs | 8 +- src/Settings/Path.hs | 245 ------------------------------- src/UserSettings.hs | 8 +- src/Utilities.hs | 14 +- 44 files changed, 733 insertions(+), 652 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 9b70568615e2763ff782279be28286373b59d8ff From git at git.haskell.org Fri Oct 27 00:38:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add removeDirectory to Rules/Actions, seems to fit (db11fb0) Message-ID: <20171027003833.47A903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db11fb04e50c4cc46a2e3286adf0b67acbc82b47/ghc >--------------------------------------------------------------- commit db11fb04e50c4cc46a2e3286adf0b67acbc82b47 Author: Neil Mitchell Date: Tue Jan 12 22:33:21 2016 +0000 Add removeDirectory to Rules/Actions, seems to fit >--------------------------------------------------------------- db11fb04e50c4cc46a2e3286adf0b67acbc82b47 src/Rules/Actions.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 0600d82..a968160 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,6 +1,6 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( - build, buildWithResources, copyFile, createDirectory, moveDirectory, + build, buildWithResources, copyFile, createDirectory, removeDirectory, moveDirectory, fixFile, runConfigure, runMake, runBuilder, makeExecutable ) where @@ -74,6 +74,11 @@ createDirectory dir = do putBuild $ "| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir +removeDirectory :: FilePath -> Action () +removeDirectory dir = do + putBuild $ "| Remove directory " ++ dir + liftIO $ IO.removeDirectoryRecursive dir + -- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do From git at git.haskell.org Fri Oct 27 00:38:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't capitalise 'quickcheck' (9b474d3) Message-ID: <20171027003830.1C1C83A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b474d34ffa182b021956944d669aee0528291ad/ghc >--------------------------------------------------------------- commit 9b474d34ffa182b021956944d669aee0528291ad Author: Andrey Mokhov Date: Fri Aug 5 18:56:33 2016 +0100 Don't capitalise 'quickcheck' [skip ci] >--------------------------------------------------------------- 9b474d34ffa182b021956944d669aee0528291ad README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index be42f82..c39071e 100644 --- a/README.md +++ b/README.md @@ -23,7 +23,7 @@ follow these steps: * If you have never built GHC before, start with the [preparation guide][ghc-preparation]. * This build system is written in Haskell (obviously) and depends on the following Haskell -packages, which need to be installed: `ansi-terminal mtl shake QuickCheck`. +packages, which need to be installed: `ansi-terminal mtl shake quickcheck`. * Get the sources. It is important for the build system to be in the `hadrian` directory of the GHC source tree: From git at git.haskell.org Fri Oct 27 00:38:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make dependencies easier to copy (9467c06) Message-ID: <20171027003826.413C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9467c0611db45c494aba051e2a5e8bd2f3cc86c1/ghc >--------------------------------------------------------------- commit 9467c0611db45c494aba051e2a5e8bd2f3cc86c1 Author: Andrey Mokhov Date: Fri Aug 5 18:53:09 2016 +0100 Make dependencies easier to copy [skip ci] >--------------------------------------------------------------- 9467c0611db45c494aba051e2a5e8bd2f3cc86c1 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 4ce3b3a..be42f82 100644 --- a/README.md +++ b/README.md @@ -23,7 +23,7 @@ follow these steps: * If you have never built GHC before, start with the [preparation guide][ghc-preparation]. * This build system is written in Haskell (obviously) and depends on the following Haskell -packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. +packages, which need to be installed: `ansi-terminal mtl shake QuickCheck`. * Get the sources. It is important for the build system to be in the `hadrian` directory of the GHC source tree: From git at git.haskell.org Fri Oct 27 00:38:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't run cabal on Hadrian (ae1fa1a) Message-ID: <20171027003834.23BAD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae1fa1ac3c153c6110174ada2641607e17bd534c/ghc >--------------------------------------------------------------- commit ae1fa1ac3c153c6110174ada2641607e17bd534c Author: Andrey Mokhov Date: Fri Aug 5 18:58:08 2016 +0100 Don't run cabal on Hadrian >--------------------------------------------------------------- ae1fa1ac3c153c6110174ada2641607e17bd534c .travis.yml | 8 ++------ 1 file changed, 2 insertions(+), 6 deletions(-) diff --git a/.travis.yml b/.travis.yml index dd74f25..33c1738 100644 --- a/.travis.yml +++ b/.travis.yml @@ -17,7 +17,7 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH - cabal update - - cabal install alex happy + - cabal install alex happy ansi-terminal mtl shake quickcheck - os: osx env: FLAVOUR=quickest TARGET= @@ -25,7 +25,7 @@ matrix: - brew update - brew install ghc cabal-install - cabal update - - cabal install alex happy + - cabal install alex happy ansi-terminal mtl shake quickcheck - PATH="$HOME/.cabal/bin:$PATH" - export PATH @@ -51,13 +51,9 @@ install: - mv .git ghc/hadrian - ( cd ghc/hadrian && git reset --hard HEAD ) - - ( cd ghc/hadrian && cabal install --only-dependencies ) - - ( cd ghc/hadrian && cabal configure ) - - ghc-pkg list script: - - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=$FLAVOUR $TARGET - ./ghc/inplace/bin/ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:38:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't move from a temporary directory. (86f3052) Message-ID: <20171027003829.B06703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86f3052c2cd738427136899bfe3a47210c4d98a5/ghc >--------------------------------------------------------------- commit 86f3052c2cd738427136899bfe3a47210c4d98a5 Author: Andrey Mokhov Date: Tue Jan 12 22:22:34 2016 +0000 Don't move from a temporary directory. Fix #156. >--------------------------------------------------------------- 86f3052c2cd738427136899bfe3a47210c4d98a5 src/Rules/Libffi.hs | 14 +++++--------- 1 file changed, 5 insertions(+), 9 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 7dd0376..0c38cd2 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -27,9 +27,6 @@ libffiBuild = buildRootPath -/- "stage0/libffi" libffiLibrary :: FilePath libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" -libffiMakefile :: FilePath -libffiMakefile = libffiBuild -/- "Makefile.in" - fixLibffiMakefile :: String -> String fixLibffiMakefile = unlines . map ( replace "-MD" "-MMD" @@ -75,7 +72,7 @@ libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] - createDirectory $ buildRootPath -/- "stage0" + createDirectory $ buildRootPath -/- stageString Stage0 tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] when (length tarballs /= 1) $ @@ -85,12 +82,11 @@ libffiRules = do need tarballs let libname = dropExtension . dropExtension . takeFileName $ head tarballs - withTempDir $ \tmpDir -> do - let unifiedTmpDir = unifyPath tmpDir - build $ fullTarget libffiTarget Tar tarballs [unifiedTmpDir] - moveDirectory (unifiedTmpDir -/- libname) libffiBuild + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + actionFinally (moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] - fixFile libffiMakefile fixLibffiMakefile + fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile forM_ ["config.guess", "config.sub"] $ \file -> copyFile file (libffiBuild -/- file) From git at git.haskell.org Fri Oct 27 00:38:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix merge conflicts (1ade885) Message-ID: <20171027003834.49DF63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ade88547a2c3256c6b6e6de8c546a04dc1ae1d3/ghc >--------------------------------------------------------------- commit 1ade88547a2c3256c6b6e6de8c546a04dc1ae1d3 Merge: 9b70568 0c67f7d Author: Andrey Mokhov Date: Wed Aug 16 03:47:39 2017 +0100 Fix merge conflicts >--------------------------------------------------------------- 1ade88547a2c3256c6b6e6de8c546a04dc1ae1d3 src/Rules.hs | 9 +++++---- src/Rules/Program.hs | 2 -- 2 files changed, 5 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 00:38:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify fixLibffiMakefile, no need to chop into lines first (07d94c9) Message-ID: <20171027003836.C5ACF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/07d94c918a4fa0f7f5ea43496f4a3e6e95662c08/ghc >--------------------------------------------------------------- commit 07d94c918a4fa0f7f5ea43496f4a3e6e95662c08 Author: Neil Mitchell Date: Tue Jan 12 22:33:42 2016 +0000 Simplify fixLibffiMakefile, no need to chop into lines first >--------------------------------------------------------------- 07d94c918a4fa0f7f5ea43496f4a3e6e95662c08 src/Rules/Libffi.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0c38cd2..63bc1e8 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -28,11 +28,11 @@ libffiLibrary :: FilePath libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" fixLibffiMakefile :: String -> String -fixLibffiMakefile = unlines . map - ( replace "-MD" "-MMD" +fixLibffiMakefile = + replace "-MD" "-MMD" . replace "@toolexeclibdir@" "$(libdir)" . replace "@INSTALL@" "$(subst ../install-sh,C:/msys/home/chEEtah/ghc/install-sh, at INSTALL@)" - ) . lines + -- TODO: remove code duplication (see Settings/Builders/GhcCabal.hs) configureEnvironment :: Action [CmdOption] From git at git.haskell.org Fri Oct 27 00:38:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to Cabal library API changes (a931066) Message-ID: <20171027003837.E4FB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a931066df88efc745bdd310b3c64aa25834ba243/ghc >--------------------------------------------------------------- commit a931066df88efc745bdd310b3c64aa25834ba243 Author: Andrey Mokhov Date: Thu Aug 11 00:41:02 2016 +0100 Adapt to Cabal library API changes Fix #282. >--------------------------------------------------------------- a931066df88efc745bdd310b3c64aa25834ba243 src/Rules/Cabal.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index e2cdb0f..ed72f93 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -35,8 +35,7 @@ cabalRules = do else do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - -- TODO: Support more than one Cabal library per package. - let depsLib = collectDeps . fmap snd . listToMaybe $ condLibraries pd + let depsLib = collectDeps $ condLibrary pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes depNames = [ name | Dependency (DP.PackageName name) _ <- deps ] From git at git.haskell.org Fri Oct 27 00:38:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (7792fbb) Message-ID: <20171027003838.1964D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7792fbbebbb68f8f2b2e95d29a6365f74376b398/ghc >--------------------------------------------------------------- commit 7792fbbebbb68f8f2b2e95d29a6365f74376b398 Author: Andrey Mokhov Date: Wed Aug 16 13:33:16 2017 +0100 Minor revision >--------------------------------------------------------------- 7792fbbebbb68f8f2b2e95d29a6365f74376b398 src/Expression.hs | 13 +++++++++++-- src/GHC.hs | 6 +++++- src/Settings.hs | 13 ------------- 3 files changed, 16 insertions(+), 16 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 8da4a6f..647c057 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -16,8 +16,8 @@ module Expression ( Context, vanillaContext, stageContext, Target, -- * Convenient accessors - getBuildRoot, getBuildPath, getContext, getStage, getPackage, getBuilder, - getOutputs, getInputs, getWay, getInput, getOutput, + getBuildRoot, getBuildPath, getContext, getPkgData, getPkgDataList, getStage, + getPackage, getBuilder, getOutputs, getInputs, getWay, getInput, getOutput, -- * Re-exports module Base @@ -28,6 +28,7 @@ import Hadrian.Expression hiding (Expr, Predicate, Args) import Base import Context (Context, vanillaContext, stageContext, getBuildPath, getStage, getPackage, getWay) +import Oracles.PackageData import Target hiding (builder, inputs, outputs) -- | @Expr a@ is a computation that produces a value of type @Action a@ and can @@ -42,6 +43,14 @@ type Args = H.Args Context Builder type Packages = Expr [Package] type Ways = Expr [Way] +-- | Get a value from the @package-data.mk@ file of the current context. +getPkgData :: (FilePath -> PackageData) -> Expr String +getPkgData key = expr . pkgData . key =<< getBuildPath + +-- | Get a list of values from the @package-data.mk@ file of the current context. +getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] +getPkgDataList key = expr . pkgDataList . key =<< getBuildPath + -- | Is the build currently in the provided stage? stage :: Stage -> Predicate stage s = (s ==) <$> getStage diff --git a/src/GHC.hs b/src/GHC.hs index 6d49630..1141030 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -18,7 +18,7 @@ module GHC ( rtsContext, rtsBuildPath, rtsConfIn, -- * Miscellaneous - ghcSplitPath, stripCmdPath, inplaceInstallPath + ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 ) where import Base @@ -192,3 +192,7 @@ rtsBuildPath = buildPath rtsContext rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" +buildDll0 :: Context -> Action Bool +buildDll0 Context {..} = do + windows <- windowsHost + return $ windows && stage == Stage1 && package == compiler diff --git a/src/Settings.hs b/src/Settings.hs index 2b4b0ef..f25265b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -13,8 +13,6 @@ import CommandLine import Expression import Flavour import GHC -import Oracles.PackageData -import Oracles.Setting import {-# SOURCE #-} Settings.Default import Settings.Flavours.Development import Settings.Flavours.Performance @@ -38,12 +36,6 @@ getPackages = expr flavour >>= packages stagePackages :: Stage -> Action [Package] stagePackages stage = interpretInContext (stageContext stage) getPackages -getPkgData :: (FilePath -> PackageData) -> Expr String -getPkgData key = expr . pkgData . key =<< getBuildPath - -getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] -getPkgDataList key = expr . pkgDataList . key =<< getBuildPath - hadrianFlavours :: [Flavour] hadrianFlavours = [ defaultFlavour, developmentFlavour Stage1, developmentFlavour Stage2 @@ -154,8 +146,3 @@ stage1Only = defaultStage1Only -- | Install's DESTDIR setting. destDir :: FilePath destDir = defaultDestDir - -buildDll0 :: Context -> Action Bool -buildDll0 Context {..} = do - windows <- windowsHost - return $ windows && stage == Stage1 && package == compiler From git at git.haskell.org Fri Oct 27 00:38:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use removeDirectory where appropriate (ccc16b2) Message-ID: <20171027003840.3CE563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ccc16b21b7d255b692ffbc9b0c96167bec2ed77e/ghc >--------------------------------------------------------------- commit ccc16b21b7d255b692ffbc9b0c96167bec2ed77e Author: Neil Mitchell Date: Tue Jan 12 22:33:55 2016 +0000 Use removeDirectory where appropriate >--------------------------------------------------------------- ccc16b21b7d255b692ffbc9b0c96167bec2ed77e src/Rules/Libffi.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 63bc1e8..1d761ff 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -71,7 +71,7 @@ libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - liftIO $ removeFiles libffiBuild ["//*"] + removeDirectory libffiBuild createDirectory $ buildRootPath -/- stageString Stage0 tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] From git at git.haskell.org Fri Oct 27 00:38:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initial version of FindMissingInclude (c2d7e2a) Message-ID: <20171027003841.6A6C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c2d7e2aa683c89d9b1464734ea9ae68ff735655c/ghc >--------------------------------------------------------------- commit c2d7e2aa683c89d9b1464734ea9ae68ff735655c Author: Michal Terepeta Date: Sat Jul 23 16:50:31 2016 +0200 Initial version of FindMissingInclude This allows finding missing includes for `.c` files (this is important for all the cases where we generate the includes during the build process). We're using GCC's `-MM` `-MG` options and iterate as long as we get new includes. Since this would return all includes verbatim from the `#include`, we check which ones are actually generated and what are their final paths. Note: this is currently applied only to `.c` files and does not (yet?) work for `.hs` files (there are issues with things like ifdefs for package versions that cause GCC to error out). Signed-off-by: Michal Terepeta >--------------------------------------------------------------- c2d7e2aa683c89d9b1464734ea9ae68ff735655c src/Builder.hs | 3 ++- src/Rules/Compile.hs | 40 ++++++++++++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 17 ++++++++++++++++- src/Settings/Builders/Cc.hs | 13 ++++++++++++- 4 files changed, 70 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 17198e7..1974eff 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -21,7 +21,8 @@ import Stage -- 3) Linking object files & static libraries into an executable. -- We have CcMode for CC and GhcMode for GHC. -data CcMode = CompileC | FindCDependencies +-- TODO: Consider merging FindCDependencies and FindMissingInclude +data CcMode = CompileC | FindCDependencies | FindMissingInclude deriving (Eq, Generic, Show) data GhcMode = CompileHs | FindHsDependencies | LinkHs diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index fd6cd32..001068a 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -5,9 +5,16 @@ import Context import Expression import Oracles.Dependencies import Rules.Actions +import Rules.Generate import Settings.Paths import Target +import Development.Shake.Util + +import Data.Maybe +import Data.List +import qualified Data.Set as Set + compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context @@ -22,6 +29,9 @@ compilePackage rs context at Context {..} = do if ("//*.c" ?== src) then do need $ src : deps + -- TODO: Improve parallelism by collecting all dependencies and + -- need'ing them all at once + mapM_ (needGenerated context) . filter ("//*.c" ?==) $ src : deps build $ Target context (Cc CompileC stage) [src] [obj] else do need $ src : deps @@ -39,3 +49,33 @@ needCompileDependencies :: Context -> Action () needCompileDependencies context at Context {..} = do when (isLibrary package) $ need =<< return <$> pkgConfFile context needContext =<< contextDependencies context + +needGenerated :: Context -> FilePath -> Action () +needGenerated context origFile = go Set.empty + where + go :: Set.Set String -> Action () + go done = withTempFile $ \outFile -> do + let builder = Cc FindMissingInclude $ stage context + target = Target context builder [origFile] [outFile] + build target + deps <- parseFile outFile + + -- Get the full path if the include refers to a generated file and call + -- `need` on it. + needed <- liftM catMaybes $ + interpretInContext context (mapM getPathIfGenerated deps) + need needed + + let newdone = Set.fromList needed `Set.union` done + -- If we added a new file to the set of needed files, let's try one more + -- time, since the new file might include a genreated header of itself + -- (which we'll `need`). + when (Set.size newdone > Set.size done) (go newdone) + + parseFile :: FilePath -> Action [String] + parseFile file = do + input <- liftIO $ readFile file + case parseMakefile input of + [(_file, deps)] -> return deps + _ -> return [] + diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 988b3d7..34874db 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,7 @@ module Rules.Generate ( generatePackageCode, generateRules, installTargets, copyRules, - includesDependencies, derivedConstantsPath, generatedDependencies + includesDependencies, derivedConstantsPath, generatedDependencies, + getPathIfGenerated ) where import qualified System.Directory as IO @@ -196,3 +197,17 @@ generateRules = do emptyTarget :: Context emptyTarget = vanillaContext (error "Rules.Generate.emptyTarget: unknown stage") (error "Rules.Generate.emptyTarget: unknown package") + +getPathIfGenerated :: FilePath -> Expr (Maybe FilePath) +getPathIfGenerated include = do + generated <- generatedFiles + -- For includes of generated files, we cannot get the full path of the file + -- (since it might be included due to some include dir, i.e., through `-I`). + -- So here we try both the name and the path. + let nameOrPath (name, path) = include == name || include == path + return . fmap snd $ find nameOrPath generated + +generatedFiles :: Expr [(FilePath, FilePath)] +generatedFiles = do + deps <- generatedDependencies + return [ (takeFileName fp, fp) | fp <- deps ] diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index 354d2b4..36a172e 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -26,7 +26,18 @@ ccBuilderArgs = mconcat , arg $ dropExtension output -<.> "o" , arg "-x" , arg "c" - , arg =<< getInput ] ] + , arg =<< getInput ] + + , builder (Cc FindMissingInclude) ? do + mconcat [ arg "-E" + , arg "-MM" + , arg "-MG" + , commonCcArgs + , arg "-MF" + , arg =<< getOutput + , arg =<< getInput + ] + ] commonCcArgs :: Args commonCcArgs = mconcat [ append =<< getPkgDataList CcArgs From git at git.haskell.org Fri Oct 27 00:38:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move systemBuilderPath to GHC (8fc676e) Message-ID: <20171027003841.7FBC83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8fc676e400d02448dea520c0977d64c140b1a560/ghc >--------------------------------------------------------------- commit 8fc676e400d02448dea520c0977d64c140b1a560 Author: Andrey Mokhov Date: Wed Aug 16 15:24:08 2017 +0100 Move systemBuilderPath to GHC >--------------------------------------------------------------- 8fc676e400d02448dea520c0977d64c140b1a560 src/GHC.hs | 42 +++++++++++++++++++++++++++++++++++++++++- src/Settings.hs | 39 --------------------------------------- 2 files changed, 41 insertions(+), 40 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 1141030..2210889 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -18,9 +18,12 @@ module GHC ( rtsContext, rtsBuildPath, rtsConfIn, -- * Miscellaneous - ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 + systemBuilderPath, ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 ) where +import Hadrian.Oracles.KeyValue +import Hadrian.Oracles.Path + import Base import Context import Oracles.Setting @@ -118,6 +121,43 @@ builderProvenance = \case where context s p = Just $ vanillaContext s p +-- | Determine the location of a system 'Builder'. +systemBuilderPath :: Builder -> Action FilePath +systemBuilderPath builder = case builder of + Alex -> fromKey "alex" + Ar Stage0 -> fromKey "system-ar" + Ar _ -> fromKey "ar" + Cc _ Stage0 -> fromKey "system-cc" + Cc _ _ -> fromKey "cc" + -- We can't ask configure for the path to configure! + Configure _ -> return "sh configure" + Ghc _ Stage0 -> fromKey "system-ghc" + GhcPkg _ Stage0 -> fromKey "system-ghc-pkg" + Happy -> fromKey "happy" + HsColour -> fromKey "hscolour" + HsCpp -> fromKey "hs-cpp" + Ld -> fromKey "ld" + Make _ -> fromKey "make" + Nm -> fromKey "nm" + Objdump -> fromKey "objdump" + Patch -> fromKey "patch" + Perl -> fromKey "perl" + Ranlib -> fromKey "ranlib" + Tar -> fromKey "tar" + _ -> error $ "No entry for " ++ show builder ++ inCfg + where + inCfg = " in " ++ quote configFile ++ " file." + fromKey key = do + let unpack = fromMaybe . error $ "Cannot find path to builder " + ++ quote key ++ inCfg ++ " Did you skip configure?" + path <- unpack <$> lookupValue configFile key + if null path + then do + unless (isOptional builder) . error $ "Non optional builder " + ++ quote key ++ " is not specified" ++ inCfg + return "" -- TODO: Use a safe interface. + else fixAbsolutePathOnWindows =<< lookupInPath path + -- | Given a 'Context', compute the name of the program that is built in it -- assuming that the corresponding package's type is 'Program'. For example, GHC -- built in 'Stage0' is called @ghc-stage1 at . If the given package is a diff --git a/src/Settings.hs b/src/Settings.hs index f25265b..fdce8a7 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -5,9 +5,6 @@ module Settings ( programContext, integerLibraryName, destDir, stage1Only, buildDll0 ) where -import Hadrian.Oracles.KeyValue -import Hadrian.Oracles.Path - import Context import CommandLine import Expression @@ -68,42 +65,6 @@ knownPackages = sort $ defaultKnownPackages ++ userKnownPackages findKnownPackage :: PackageName -> Maybe Package findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages --- | Determine the location of a system 'Builder'. -systemBuilderPath :: Builder -> Action FilePath -systemBuilderPath builder = case builder of - Alex -> fromKey "alex" - Ar Stage0 -> fromKey "system-ar" - Ar _ -> fromKey "ar" - Cc _ Stage0 -> fromKey "system-cc" - Cc _ _ -> fromKey "cc" - -- We can't ask configure for the path to configure! - Configure _ -> return "sh configure" - Ghc _ Stage0 -> fromKey "system-ghc" - GhcPkg _ Stage0 -> fromKey "system-ghc-pkg" - Happy -> fromKey "happy" - HsColour -> fromKey "hscolour" - HsCpp -> fromKey "hs-cpp" - Ld -> fromKey "ld" - Make _ -> fromKey "make" - Nm -> fromKey "nm" - Objdump -> fromKey "objdump" - Patch -> fromKey "patch" - Perl -> fromKey "perl" - Ranlib -> fromKey "ranlib" - Tar -> fromKey "tar" - _ -> error $ "No system.config entry for " ++ show builder - where - fromKey key = do - let unpack = fromMaybe . error $ "Cannot find path to builder " - ++ quote key ++ " in system.config file. Did you skip configure?" - path <- unpack <$> lookupValue configFile key - if null path - then do - unless (isOptional builder) . error $ "Non optional builder " - ++ quote key ++ " is not specified in system.config file." - return "" -- TODO: Use a safe interface. - else fixAbsolutePathOnWindows =<< lookupInPath path - -- | Determine the location of a 'Builder'. builderPath :: Builder -> Action FilePath builderPath builder = case builderProvenance builder of From git at git.haskell.org Fri Oct 27 00:38:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #156, ensure the entire piece is under a removeFiles so we always clean up the garbage (3a88dc5) Message-ID: <20171027003843.A67713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3a88dc56215804ab95d9c5eb3127de6f4c7a5f0b/ghc >--------------------------------------------------------------- commit 3a88dc56215804ab95d9c5eb3127de6f4c7a5f0b Author: Neil Mitchell Date: Tue Jan 12 22:34:39 2016 +0000 #156, ensure the entire piece is under a removeFiles so we always clean up the garbage >--------------------------------------------------------------- 3a88dc56215804ab95d9c5eb3127de6f4c7a5f0b src/Rules/Libffi.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 1d761ff..8bcfdae 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -82,9 +82,10 @@ libffiRules = do need tarballs let libname = dropExtension . dropExtension . takeFileName $ head tarballs - build $ fullTarget libffiTarget Tar tarballs [buildRootPath] - actionFinally (moveDirectory (buildRootPath -/- libname) libffiBuild) $ - removeFiles buildRootPath [libname "*"] + actionFinally (do + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile From git at git.haskell.org Fri Oct 27 00:38:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #279 from michalt/gcc-mm-mg/1 (197ca35) Message-ID: <20171027003844.D62993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/197ca35ae05c95d3cf710c453630bd2ce399542a/ghc >--------------------------------------------------------------- commit 197ca35ae05c95d3cf710c453630bd2ce399542a Merge: a931066 c2d7e2a Author: Andrey Mokhov Date: Wed Aug 17 19:36:55 2016 +0100 Merge pull request #279 from michalt/gcc-mm-mg/1 Use GCC's `-MM`/`-MG` to find missing dependencies >--------------------------------------------------------------- 197ca35ae05c95d3cf710c453630bd2ce399542a src/Builder.hs | 3 ++- src/Rules/Compile.hs | 40 ++++++++++++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 17 ++++++++++++++++- src/Settings/Builders/Cc.hs | 13 ++++++++++++- 4 files changed, 70 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:38:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out cabal parsing functionality into the library (4a46d14) Message-ID: <20171027003844.E68E43A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a46d14ec3631672d2a3733c45f0aa61eb861eab/ghc >--------------------------------------------------------------- commit 4a46d14ec3631672d2a3733c45f0aa61eb861eab Author: Andrey Mokhov Date: Wed Aug 16 22:18:45 2017 +0100 Factor out cabal parsing functionality into the library See #347 >--------------------------------------------------------------- 4a46d14ec3631672d2a3733c45f0aa61eb861eab hadrian.cabal | 1 + src/Hadrian/Haskell/Cabal.hs | 38 ++++++++++++++++++++++++++++++++++++++ src/Rules/Cabal.hs | 31 ++++++------------------------- src/Settings/Packages/GhcCabal.hs | 13 ++----------- 4 files changed, 47 insertions(+), 36 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 8ad971f..1520881 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -27,6 +27,7 @@ executable hadrian , Flavour , GHC , Hadrian.Expression + , Hadrian.Haskell.Cabal , Hadrian.Oracles.ArgsHash , Hadrian.Oracles.DirectoryContents , Hadrian.Oracles.KeyValue diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs new file mode 100644 index 0000000..b8f874c --- /dev/null +++ b/src/Hadrian/Haskell/Cabal.hs @@ -0,0 +1,38 @@ +module Hadrian.Haskell.Cabal (readCabal, cabalNameVersion, cabalDependencies) where + +import Development.Shake +import Distribution.Package +import Distribution.PackageDescription +import Distribution.PackageDescription.Parse +import Distribution.Text +import Distribution.Types.CondTree +import Distribution.Verbosity + +-- TODO: Track the values? + +-- | Read a given @.cabal@ file and return the 'GenericPackageDescription'. +readCabal :: FilePath -> Action GenericPackageDescription +readCabal cabal = do + need [cabal] + liftIO $ readGenericPackageDescription silent cabal + +-- | Read a given @.cabal@ file and return the package name and version. +cabalNameVersion :: FilePath -> Action (String, String) +cabalNameVersion cabal = do + identifier <- package . packageDescription <$> readCabal cabal + return (unPackageName $ pkgName identifier, display $ pkgVersion identifier) + +-- | Read a given @.cabal@ file and return the package dependencies. +cabalDependencies :: FilePath -> Action [String] +cabalDependencies cabal = do + gpd <- readCabal cabal + let depsLib = collectDeps $ condLibrary gpd + depsExes = map (collectDeps . Just . snd) $ condExecutables gpd + deps = concat $ depsLib : depsExes + return $ [ unPackageName name | Dependency name _ <- deps ] + +collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] +collectDeps Nothing = [] +collectDeps (Just (CondNode _ deps ifs)) = deps ++ concatMap f ifs + where + f (CondBranch _ t mt) = collectDeps (Just t) ++ collectDeps mt diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index a9a9b51..ab8c6f9 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,11 +1,6 @@ module Rules.Cabal (cabalRules) where -import Distribution.Package as DP -import Distribution.PackageDescription -import Distribution.PackageDescription.Parse -import Distribution.Text -import Distribution.Types.CondTree -import Distribution.Verbosity +import Hadrian.Haskell.Cabal import Base import GHC @@ -18,32 +13,18 @@ cabalRules = do bootPkgs <- stagePackages Stage0 let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do - need [pkgCabalFile pkg] - pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg - let identifier = package . packageDescription $ pd - version = display . pkgVersion $ identifier - return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version + (name, version) <- cabalNameVersion (pkgCabalFile pkg) + return $ name ++ " == " ++ version writeFileChanged out . unlines $ constraints putSuccess $ "| Successfully generated boot package constraints" -- Cache package dependencies. "//" -/- packageDependencies %> \out -> do pkgDeps <- forM (sort knownPackages) $ \pkg -> do - exists <- doesFileExist $ pkgCabalFile pkg + exists <- doesFileExist (pkgCabalFile pkg) if not exists then return $ pkgNameString pkg else do - need [pkgCabalFile pkg] - pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg - let depsLib = collectDeps $ condLibrary pd - depsExes = map (collectDeps . Just . snd) $ condExecutables pd - deps = concat $ depsLib : depsExes - depNames = [ unPackageName name | Dependency name _ <- deps ] - return . unwords $ pkgNameString pkg : (sort depNames \\ [pkgNameString pkg]) + deps <- sort <$> cabalDependencies (pkgCabalFile pkg) + return . unwords $ pkgNameString pkg : (deps \\ [pkgNameString pkg]) writeFileChanged out $ unlines pkgDeps putSuccess $ "| Successfully generated package dependencies" - -collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] -collectDeps Nothing = [] -collectDeps (Just (CondNode _ deps ifs)) = deps ++ concatMap f ifs - where - f (CondBranch _ t mt) = collectDeps (Just t) ++ collectDeps mt diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index c7b82ca..79e92c7 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -1,11 +1,6 @@ module Settings.Packages.GhcCabal (ghcCabalPackageArgs) where -import Distribution.Package (pkgVersion) -import Distribution.PackageDescription (packageDescription) -import Distribution.PackageDescription.Parse -import qualified Distribution.PackageDescription as DP -import Distribution.Text (display) -import Distribution.Verbosity (silent) +import Hadrian.Haskell.Cabal import Base import Expression @@ -15,11 +10,7 @@ import Utilities ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do cabalDeps <- expr $ pkgDependencies cabal - expr $ need [pkgCabalFile cabal] - pd <- exprIO . readGenericPackageDescription silent $ pkgCabalFile cabal - let identifier = DP.package . packageDescription $ pd - cabalVersion = display . pkgVersion $ identifier - + (_, cabalVersion) <- expr $ cabalNameVersion (pkgCabalFile cabal) mconcat [ pure [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , arg "--make" From git at git.haskell.org Fri Oct 27 00:38:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add docs, minor revision (b85602d) Message-ID: <20171027003852.C58DE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b85602dc64ccb927839a2368b9636e2bd91cd232/ghc >--------------------------------------------------------------- commit b85602dc64ccb927839a2368b9636e2bd91cd232 Author: Andrey Mokhov Date: Wed Aug 16 23:15:34 2017 +0100 Add docs, minor revision >--------------------------------------------------------------- b85602dc64ccb927839a2368b9636e2bd91cd232 src/Hadrian/Haskell/Cabal.hs | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs index b8f874c..d579de6 100644 --- a/src/Hadrian/Haskell/Cabal.hs +++ b/src/Hadrian/Haskell/Cabal.hs @@ -1,3 +1,14 @@ +----------------------------------------------------------------------------- +-- | +-- Module : Hadrian.Haskell.Cabal +-- Copyright : (c) Andrey Mokhov 2014-2017 +-- License : MIT (see the file LICENSE) +-- Maintainer : andrey.mokhov at gmail.com +-- Stability : experimental +-- +-- Basic functionality for extracting Haskell package metadata stored in +-- @.cabal@ files. +----------------------------------------------------------------------------- module Hadrian.Haskell.Cabal (readCabal, cabalNameVersion, cabalDependencies) where import Development.Shake @@ -8,28 +19,28 @@ import Distribution.Text import Distribution.Types.CondTree import Distribution.Verbosity --- TODO: Track the values? - --- | Read a given @.cabal@ file and return the 'GenericPackageDescription'. +-- | Read a given @.cabal@ file and return the 'GenericPackageDescription'. The +-- @.cabal@ file is tracked. readCabal :: FilePath -> Action GenericPackageDescription readCabal cabal = do need [cabal] liftIO $ readGenericPackageDescription silent cabal --- | Read a given @.cabal@ file and return the package name and version. +-- | Read a given @.cabal@ file and return the package name and version. The +-- @.cabal@ file is tracked. cabalNameVersion :: FilePath -> Action (String, String) cabalNameVersion cabal = do identifier <- package . packageDescription <$> readCabal cabal return (unPackageName $ pkgName identifier, display $ pkgVersion identifier) --- | Read a given @.cabal@ file and return the package dependencies. +-- | Read a given @.cabal@ file and return the package dependencies. The +-- @.cabal@ file is tracked. cabalDependencies :: FilePath -> Action [String] cabalDependencies cabal = do gpd <- readCabal cabal - let depsLib = collectDeps $ condLibrary gpd - depsExes = map (collectDeps . Just . snd) $ condExecutables gpd - deps = concat $ depsLib : depsExes - return $ [ unPackageName name | Dependency name _ <- deps ] + let libDeps = collectDeps (condLibrary gpd) + exeDeps = map (collectDeps . Just . snd) (condExecutables gpd) + return [ unPackageName p | Dependency p _ <- concat (libDeps : exeDeps) ] collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] From git at git.haskell.org Fri Oct 27 00:38:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #156, remove the directory if it already exists (8f995f6) Message-ID: <20171027003853.F1C773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f995f6b65c27d18f2f9606ba95ac25c2974ae23/ghc >--------------------------------------------------------------- commit 8f995f6b65c27d18f2f9606ba95ac25c2974ae23 Author: Neil Mitchell Date: Tue Jan 12 22:43:24 2016 +0000 #156, remove the directory if it already exists >--------------------------------------------------------------- 8f995f6b65c27d18f2f9606ba95ac25c2974ae23 src/Rules/Libffi.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 8bcfdae..dbf50dc 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -82,6 +82,7 @@ libffiRules = do need tarballs let libname = dropExtension . dropExtension . takeFileName $ head tarballs + removeDirectory (buildRootPath -/- libname) actionFinally (do build $ fullTarget libffiTarget Tar tarballs [buildRootPath] moveDirectory (buildRootPath -/- libname) libffiBuild) $ From git at git.haskell.org Fri Oct 27 00:38:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant imports (082f17b) Message-ID: <20171027003856.73F6E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/082f17b3c86e559d45e117226094e85923883013/ghc >--------------------------------------------------------------- commit 082f17b3c86e559d45e117226094e85923883013 Author: Andrey Mokhov Date: Sat Aug 20 18:17:37 2016 +0100 Drop redundant imports >--------------------------------------------------------------- 082f17b3c86e559d45e117226094e85923883013 src/Rules/Compile.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 001068a..8f8d92a 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -11,8 +11,6 @@ import Target import Development.Shake.Util -import Data.Maybe -import Data.List import qualified Data.Set as Set compilePackage :: [(Resource, Int)] -> Context -> Rules () From git at git.haskell.org Fri Oct 27 00:38:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out file cache functionality into the library (4fca3ae) Message-ID: <20171027003856.7B56A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fca3ae5301a19abc621dc8ec08051c4b2a954ac/ghc >--------------------------------------------------------------- commit 4fca3ae5301a19abc621dc8ec08051c4b2a954ac Author: Andrey Mokhov Date: Thu Aug 17 02:16:45 2017 +0100 Factor out file cache functionality into the library See #347 >--------------------------------------------------------------- 4fca3ae5301a19abc621dc8ec08051c4b2a954ac hadrian.cabal | 2 +- src/Base.hs | 6 ++--- src/Hadrian/Oracles/FileCache.hs | 49 +++++++++++++++++++++++++++++++++++++++ src/Rules.hs | 19 ++++++++------- src/Rules/Cabal.hs | 30 ------------------------ src/Settings/Builders/GhcCabal.hs | 17 ++++++++++++-- src/Utilities.hs | 17 ++++++++++++-- 7 files changed, 93 insertions(+), 47 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 4fca3ae5301a19abc621dc8ec08051c4b2a954ac From git at git.haskell.org Fri Oct 27 00:38:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #161 from ndmitchell/master (f5f6c41) Message-ID: <20171027003857.62EB83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5f6c41b98c7f4682f0bd73f573fc170e233235a/ghc >--------------------------------------------------------------- commit f5f6c41b98c7f4682f0bd73f573fc170e233235a Merge: 57c6497 8f995f6 Author: Andrey Mokhov Date: Tue Jan 12 22:46:47 2016 +0000 Merge pull request #161 from ndmitchell/master Cleanups in libffi >--------------------------------------------------------------- f5f6c41b98c7f4682f0bd73f573fc170e233235a src/Rules/Actions.hs | 7 ++++++- src/Rules/Libffi.hs | 16 +++++++++------- 2 files changed, 15 insertions(+), 8 deletions(-) From git at git.haskell.org Fri Oct 27 00:39:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix comments (676ec2e) Message-ID: <20171027003900.6038E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/676ec2eabce5fd13ad9deb172d5041d461be01e7/ghc >--------------------------------------------------------------- commit 676ec2eabce5fd13ad9deb172d5041d461be01e7 Author: Andrey Mokhov Date: Sat Aug 20 19:57:26 2016 +0100 Fix comments [skip ci] >--------------------------------------------------------------- 676ec2eabce5fd13ad9deb172d5041d461be01e7 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 6fbc3b2..87bedb8 100644 --- a/.gitignore +++ b/.gitignore @@ -13,7 +13,7 @@ cabal.sandbox.config # build.cabal-new.sh specific /dist-newstyle/ -# build.stack.sh specific +# build.stack.sh and build.stack.bat specific /.stack-work/ # the user settings From git at git.haskell.org Fri Oct 27 00:39:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #155, fix the name of the QuickCheck package (it doesn't follow the convention all the others do) (a60cdcd) Message-ID: <20171027003900.DDB583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a60cdcd7cb6ce45d1b8f6794d4aa9e5f9415c810/ghc >--------------------------------------------------------------- commit a60cdcd7cb6ce45d1b8f6794d4aa9e5f9415c810 Author: Neil Mitchell Date: Wed Jan 13 08:47:25 2016 +0000 #155, fix the name of the QuickCheck package (it doesn't follow the convention all the others do) >--------------------------------------------------------------- a60cdcd7cb6ce45d1b8f6794d4aa9e5f9415c810 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 4226415..f5b8117 100644 --- a/README.md +++ b/README.md @@ -24,7 +24,7 @@ to adjust anything if you are already familiar with building ghc using the `make build system. Furthermore, we depend on the following packages which need to be installed: -`ansi-terminal`, `mtl`, `shake`, `quickcheck`. +`ansi-terminal`, `mtl`, `shake`, `QuickCheck`. ### Getting the source and configuring GHC From git at git.haskell.org Fri Oct 27 00:39:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build with '--integer-simple' on Linux GHC 8.0.2 CI (67ae38d) Message-ID: <20171027003904.0E3073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/67ae38d6586cf7f528b7b088a97421f76e029e0e/ghc >--------------------------------------------------------------- commit 67ae38d6586cf7f528b7b088a97421f76e029e0e Author: Andrey Mokhov Date: Thu Aug 17 22:06:32 2017 +0100 Build with '--integer-simple' on Linux GHC 8.0.2 CI >--------------------------------------------------------------- 67ae38d6586cf7f528b7b088a97421f76e029e0e .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index c23e92a..4fecbfc 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,7 +2,7 @@ sudo: true matrix: include: - os: linux - env: MODE="--flavour=quickest" + env: MODE="--flavour=quickest --integer-simple" compiler: "GHC 8.0.2" addons: apt: From git at git.haskell.org Fri Oct 27 00:39:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bump stack to lts-6.12 and remove extra pkg from extra-deps (e789d21) Message-ID: <20171027003904.1C24C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e789d211296f7abc031af5e1ab19d2633f7de745/ghc >--------------------------------------------------------------- commit e789d211296f7abc031af5e1ab19d2633f7de745 Author: Michal Terepeta Date: Sun Aug 21 13:46:48 2016 +0200 Bump stack to lts-6.12 and remove extra pkg from extra-deps Signed-off-by: Michal Terepeta >--------------------------------------------------------------- e789d211296f7abc031af5e1ab19d2633f7de745 stack.yaml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/stack.yaml b/stack.yaml index 9eb4cfb..5fa9f94 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,7 +1,7 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-5.17 +resolver: lts-6.12 # Local packages, usually specified by relative directory name packages: @@ -10,7 +10,6 @@ packages: # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: -- extra-1.4.7 # Override default flag values for local packages and extra-deps flags: {} From git at git.haskell.org Fri Oct 27 00:39:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix overlapping build rules and generalise the pattern (e815c5f) Message-ID: <20171027003900.638E33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e815c5f5100fa218415e19ea9a577c5428f8ec0a/ghc >--------------------------------------------------------------- commit e815c5f5100fa218415e19ea9a577c5428f8ec0a Author: Andrey Mokhov Date: Thu Aug 17 19:59:54 2017 +0100 Fix overlapping build rules and generalise the pattern See #391 >--------------------------------------------------------------- e815c5f5100fa218415e19ea9a577c5428f8ec0a src/Hadrian/Utilities.hs | 11 ++++++++++- src/Rules/Library.hs | 2 +- src/Rules/Register.hs | 10 ++++------ 3 files changed, 15 insertions(+), 8 deletions(-) diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 3fe389d..0765891 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -25,7 +25,7 @@ module Hadrian.Utilities ( renderUnicorn, -- * Miscellaneous - (<&>), + (<&>), (%%>), -- * Useful re-exports Dynamic, fromDynamic, toDyn, TypeRep, typeOf @@ -116,6 +116,15 @@ a -/- b infixr 6 -/- +-- | Like Shake's '%>' but gives higher priority to longer patterns. Useful +-- in situations when a family of build rules, e.g. @"//*.a"@ and @"//*_p.a"@ +-- can be matched by the same file, such as @library_p.a at . We break the tie +-- by preferring longer matches, which correpond to longer patterns. +(%%>) :: FilePattern -> (FilePath -> Action ()) -> Rules () +p %%> a = priority (fromIntegral (length p) + 1) $ p %> a + +infix 1 %%> + -- | Insert a value into Shake's type-indexed map. insertExtra :: Typeable a => a -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic insertExtra value = Map.insert (typeOf value) (toDyn value) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index f4259fb..f3a162e 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -53,7 +53,7 @@ buildDynamicLib context at Context{..} = do buildPackageLibrary :: Context -> Rules () buildPackageLibrary context at Context {..} = do let libPrefix = "//" ++ contextDir context -/- "libHS" ++ pkgNameString package - libPrefix ++ "*" ++ (waySuffix way <.> "a") %> \a -> do + libPrefix ++ "*" ++ (waySuffix way <.> "a") %%> \a -> do objs <- libraryObjects context asuf <- libsuf way let isLib0 = ("//*-0" ++ asuf) ?== a diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 261f142..cd48d91 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -15,17 +15,15 @@ registerPackage rs context at Context {..} = do -- Packages @ghc-boot@ and @ghc-boot-th@ both match the @ghc-boot*@ -- pattern, therefore we need to use priorities to match the right rule. -- TODO: Get rid of this hack. - priority (fromIntegral . length $ pkgNameString package) $ - "//" ++ stage0PackageDbDir -/- pkgNameString package ++ "*.conf" %> - buildConf rs context + "//" ++ stage0PackageDbDir -/- pkgNameString package ++ "*.conf" %%> + buildConf rs context when (package == ghc) $ "//" ++ stage0PackageDbDir -/- packageDbStamp %> buildStamp rs context when (stage == Stage1) $ do - priority (fromIntegral . length $ pkgNameString package) $ - inplacePackageDbPath -/- pkgNameString package ++ "*.conf" %> - buildConf rs context + inplacePackageDbPath -/- pkgNameString package ++ "*.conf" %%> + buildConf rs context when (package == ghc) $ inplacePackageDbPath -/- packageDbStamp %> buildStamp rs context From git at git.haskell.org Fri Oct 27 00:39:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #162 from ndmitchell/master (6934485) Message-ID: <20171027003904.A2A2F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6934485f0e98b62630ce0d867ebc6b8f3da5f04a/ghc >--------------------------------------------------------------- commit 6934485f0e98b62630ce0d867ebc6b8f3da5f04a Merge: f5f6c41 a60cdcd Author: Andrey Mokhov Date: Wed Jan 13 09:15:24 2016 +0000 Merge pull request #162 from ndmitchell/master #155, fix the name of the QuickCheck package [skip ci] >--------------------------------------------------------------- 6934485f0e98b62630ce0d867ebc6b8f3da5f04a README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:39:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #284 from michalt/stack/lts612extra (c7f8ae2) Message-ID: <20171027003908.08B6D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7f8ae2442955879660752c880405c0c3780f7f4/ghc >--------------------------------------------------------------- commit c7f8ae2442955879660752c880405c0c3780f7f4 Merge: 676ec2e e789d21 Author: Andrey Mokhov Date: Sun Aug 21 17:03:02 2016 +0100 Merge pull request #284 from michalt/stack/lts612extra Bump stack to lts-6.12 and remove extra pkg from extra-deps >--------------------------------------------------------------- c7f8ae2442955879660752c880405c0c3780f7f4 stack.yaml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 00:39:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: .bat file tidy up plus shake-0.16 compatibility (#392) (df4848c) Message-ID: <20171027003907.9C17E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/df4848c98c729212840b7de291dcad15fe679451/ghc >--------------------------------------------------------------- commit df4848c98c729212840b7de291dcad15fe679451 Author: Neil Mitchell Date: Fri Aug 18 00:07:13 2017 +0100 .bat file tidy up plus shake-0.16 compatibility (#392) * Switch from @ to @echo off in the batch files * Make sure the .bat files do setlocal - ensures if it fails you don't keep the directory change * Give RuleResult instances to all the oracles, as required by the forthcoming shake-0.16 >--------------------------------------------------------------- df4848c98c729212840b7de291dcad15fe679451 build.bat | 52 +++++++++++++++++--------------- build.stack.bat | 16 +++++----- src/Hadrian/Oracles/ArgsHash.hs | 3 ++ src/Hadrian/Oracles/DirectoryContents.hs | 2 ++ src/Hadrian/Oracles/FileCache.hs | 2 ++ src/Hadrian/Oracles/KeyValue.hs | 3 ++ src/Hadrian/Oracles/Path.hs | 3 ++ src/Hadrian/Utilities.hs | 7 +++++ src/Oracles/ModuleFiles.hs | 3 ++ 9 files changed, 59 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc df4848c98c729212840b7de291dcad15fe679451 From git at git.haskell.org Fri Oct 27 00:39:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build-tools Alex and Happy. (4e58441) Message-ID: <20171027003912.098CB3A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e584418c121e02029e6dfdd52bbd397e8bb034b/ghc >--------------------------------------------------------------- commit 4e584418c121e02029e6dfdd52bbd397e8bb034b Author: Andrey Mokhov Date: Thu Sep 1 15:42:33 2016 +0100 Add build-tools Alex and Happy. >--------------------------------------------------------------- 4e584418c121e02029e6dfdd52bbd397e8bb034b hadrian.cabal | 2 ++ 1 file changed, 2 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 41cccd8..3e34b16 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -129,6 +129,8 @@ executable hadrian , shake >= 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* + build-tools: alex >= 3.1 + , happy >= 1.19.4 ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 From git at git.haskell.org Fri Oct 27 00:39:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: merge GMP library and framework GMP checks together (b784a22) Message-ID: <20171027003912.092B13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b784a2233bc75245bfddef304fa690dbcf382311/ghc >--------------------------------------------------------------- commit b784a2233bc75245bfddef304fa690dbcf382311 Author: Karel Gardas Date: Wed Jan 13 23:03:08 2016 +0100 merge GMP library and framework GMP checks together >--------------------------------------------------------------- b784a2233bc75245bfddef304fa690dbcf382311 src/Rules/Gmp.hs | 33 +++++++++++++++------------------ 1 file changed, 15 insertions(+), 18 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 94086e1..f34f3f0 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -126,26 +126,23 @@ gmpRules = do -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` configMk <- liftIO . readFile $ gmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk + || "HaveLibGmp = YES" `isInfixOf` configMk then do - putBuild "| GMP framework detected and will be used" + putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - else if "HaveLibGmp = YES" `isInfixOf` configMk - then do - putBuild "| GMP detected and will be used" - copyFile gmpLibraryFakeH gmpLibraryH - else do - putBuild "| No GMP framework detected; in tree GMP will be built" - runMake libPath ["MAKEFLAGS="] - - copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH - copyFile (libPath -/- "gmp.h") gmpLibraryH - -- TODO: why copy library, can we move it instead? - copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary - - createDirectory gmpObjects - build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] - - runBuilder Ranlib [gmpLibrary] + else do + putBuild "| No GMP library/framework detected; in tree GMP will be built" + runMake libPath ["MAKEFLAGS="] + + copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH + copyFile (libPath -/- "gmp.h") gmpLibraryH + -- TODO: why copy library, can we move it instead? + copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary + + createDirectory gmpObjects + build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] + + runBuilder Ranlib [gmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" From git at git.haskell.org Fri Oct 27 00:39:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix handling of --with-gmp-* configure arguments (80eac86) Message-ID: <20171027003908.7B6893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/80eac86c555a8e0d48a694ffc23f0ac2c75236d0/ghc >--------------------------------------------------------------- commit 80eac86c555a8e0d48a694ffc23f0ac2c75236d0 Author: Karel Gardas Date: Wed Jan 13 22:24:38 2016 +0100 fix handling of --with-gmp-* configure arguments >--------------------------------------------------------------- 80eac86c555a8e0d48a694ffc23f0ac2c75236d0 src/Rules/Gmp.hs | 46 ++++++++++++++++++++++++++++++++-------------- 1 file changed, 32 insertions(+), 14 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index b02fe36..94086e1 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -57,6 +57,19 @@ configureArguments = do , "--host=" ++ hostPlatform , "--build=" ++ buildPlatform] +configureIntGmpArguments :: Action [String] +configureIntGmpArguments = do + includes <- settingList GmpIncludeDirs + libs <- settingList GmpLibDirs + return ([] + ++ (if (not (null includes)) + then map ((++) "--with-gmp-includes=") includes + else []) + ++ (if (not (null libs)) + then map ((++) "--with-gmp-libraries=") libs + else []) + ) + -- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do @@ -105,7 +118,8 @@ gmpRules = do runConfigure libPath envs args -- TODO: currently we configure integerGmp package twice -- optimise - runConfigure (pkgPath integerGmp) [] [] + intGmpArgs <- configureIntGmpArguments + runConfigure (pkgPath integerGmp) envs intGmpArgs createDirectory $ takeDirectory gmpLibraryH -- check whether we need to build in tree gmp @@ -115,19 +129,23 @@ gmpRules = do then do putBuild "| GMP framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - else do - putBuild "| No GMP framework detected; in tree GMP will be built" - runMake libPath ["MAKEFLAGS="] - - copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH - copyFile (libPath -/- "gmp.h") gmpLibraryH - -- TODO: why copy library, can we move it instead? - copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary - - createDirectory gmpObjects - build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] - - runBuilder Ranlib [gmpLibrary] + else if "HaveLibGmp = YES" `isInfixOf` configMk + then do + putBuild "| GMP detected and will be used" + copyFile gmpLibraryFakeH gmpLibraryH + else do + putBuild "| No GMP framework detected; in tree GMP will be built" + runMake libPath ["MAKEFLAGS="] + + copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH + copyFile (libPath -/- "gmp.h") gmpLibraryH + -- TODO: why copy library, can we move it instead? + copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary + + createDirectory gmpObjects + build $ fullTarget gmpTarget Ar [gmpLibrary] [gmpObjects] + + runBuilder Ranlib [gmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" From git at git.haskell.org Fri Oct 27 00:39:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Package to the library (14aec31) Message-ID: <20171027003911.925753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14aec31f12e398f7cab12e23c95c8eda1d8c9f4a/ghc >--------------------------------------------------------------- commit 14aec31f12e398f7cab12e23c95c8eda1d8c9f4a Author: Andrey Mokhov Date: Fri Aug 18 00:56:33 2017 +0100 Move Package to the library See #347 >--------------------------------------------------------------- 14aec31f12e398f7cab12e23c95c8eda1d8c9f4a hadrian.cabal | 2 +- src/Base.hs | 4 ++-- src/{ => Hadrian/Haskell}/Package.hs | 23 ++++++++++++++--------- 3 files changed, 17 insertions(+), 12 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 7c45af6..93e4707 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -28,6 +28,7 @@ executable hadrian , GHC , Hadrian.Expression , Hadrian.Haskell.Cabal + , Hadrian.Haskell.Package , Hadrian.Oracles.ArgsHash , Hadrian.Oracles.DirectoryContents , Hadrian.Oracles.FileCache @@ -39,7 +40,6 @@ executable hadrian , Oracles.Setting , Oracles.ModuleFiles , Oracles.PackageData - , Package , Rules , Rules.Clean , Rules.Compile diff --git a/src/Base.hs b/src/Base.hs index 8c81706..310d7c4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -15,7 +15,7 @@ module Base ( -- * Basic data types module Builder, - module Package, + module Hadrian.Haskell.Package, module Stage, module Way, @@ -37,9 +37,9 @@ import Development.Shake.Classes import Development.Shake.FilePath import Development.Shake.Util import Hadrian.Utilities +import Hadrian.Haskell.Package import Builder -import Package import Stage import Way diff --git a/src/Package.hs b/src/Hadrian/Haskell/Package.hs similarity index 79% rename from src/Package.hs rename to src/Hadrian/Haskell/Package.hs index 93e8ee0..d7dd3df 100644 --- a/src/Package.hs +++ b/src/Hadrian/Haskell/Package.hs @@ -1,4 +1,4 @@ -module Package ( +module Hadrian.Haskell.Package ( Package (..), PackageName (..), PackageType (..), -- * Queries pkgNameString, pkgCabalFile, @@ -12,20 +12,25 @@ import Development.Shake.FilePath import GHC.Generics import Hadrian.Utilities --- | The name of a Cabal package. +-- | The name of a Haskell package. newtype PackageName = PackageName { fromPackageName :: String } deriving (Binary, Eq, Generic, Hashable, IsString, NFData, Ord, Typeable) -- TODO: Make PackageType more precise, #12. --- | We regard packages as either being libraries or programs. This is bit of a --- convenient lie as Cabal packages can be both, but it works for now. +-- | We regard packages as either being libraries or programs. This is a bit of +-- a convenient lie as Haskell packages can be both, but it works for now. data PackageType = Library | Program deriving Generic -data Package = Package - { pkgName :: PackageName -- ^ Examples: "ghc", "Cabal". - , pkgPath :: FilePath -- ^ pkgPath is the path to the source code relative - -- to the root, e.g. "compiler", "libraries/Cabal/Cabal". - , pkgType :: PackageType -- ^ A library or a program. +-- | A Haskell package. +data Package = Package { + -- | The name of a Haskell package. Examples: @Cabal@, @ghc-bin at . + pkgName :: PackageName, + -- | The path to the package source code relative to the root of the build + -- system. For example, @libraries/Cabal/Cabal@ and @ghc@ are paths to the + -- @Cabal@ and @ghc-bin@ packages in GHC. + pkgPath :: FilePath, + -- | A library (e.g. @Cabal@) or a program (e.g. @ghc-bin@). + pkgType :: PackageType } deriving Generic -- TODO: Get rid of non-derived Show instances. From git at git.haskell.org Fri Oct 27 00:39:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make Package datatype abstract (39a2b89) Message-ID: <20171027003915.D53AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39a2b89543e584f7349800db14ab6d1182f7c2fc/ghc >--------------------------------------------------------------- commit 39a2b89543e584f7349800db14ab6d1182f7c2fc Author: Andrey Mokhov Date: Fri Aug 18 01:03:42 2017 +0100 Make Package datatype abstract >--------------------------------------------------------------- 39a2b89543e584f7349800db14ab6d1182f7c2fc src/Hadrian/Haskell/Package.hs | 4 ++-- src/Rules/Install.hs | 8 ++++---- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Hadrian/Haskell/Package.hs b/src/Hadrian/Haskell/Package.hs index d7dd3df..cd63589 100644 --- a/src/Hadrian/Haskell/Package.hs +++ b/src/Hadrian/Haskell/Package.hs @@ -1,7 +1,7 @@ module Hadrian.Haskell.Package ( - Package (..), PackageName (..), PackageType (..), + Package, PackageName (..), PackageType (..), -- * Queries - pkgNameString, pkgCabalFile, + pkgName, pkgPath, pkgType, pkgNameString, pkgCabalFile, -- * Helpers for constructing and using 'Package's setPath, topLevel, library, utility, setType, isLibrary, isProgram ) where diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 1d0cd9e..a13e8eb 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -181,7 +181,7 @@ installPackages = do installLibPkgs <- topsortPackages (filter isLibrary activePackages) - forM_ installLibPkgs $ \pkg at Package{..} -> do + forM_ installLibPkgs $ \pkg -> do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg @@ -211,7 +211,7 @@ installPackages = do pref <- setting InstallPrefix unit $ cmd ghcCabalInplace [ "copy" - , pkgPath + , pkgPath pkg , installDistDir , strip , destDir @@ -228,7 +228,7 @@ installPackages = do , installedPackageConf, "update" , confPath ] - forM_ installLibPkgs $ \pkg at Package{..} -> do + forM_ installLibPkgs $ \pkg -> do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg @@ -241,7 +241,7 @@ installPackages = do r <- relocatableBuild unit $ cmd ghcCabalInplace [ "register" - , pkgPath + , pkgPath pkg , installDistDir , installedGhcReal , installedGhcPkgReal From git at git.haskell.org Fri Oct 27 00:39:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: simplify configureIntGmpArguments based on idea provided by Gabor Greif (86a3fe5) Message-ID: <20171027003915.E93D93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86a3fe5f1e16ef919cf0145c0830f2ad7cd8586e/ghc >--------------------------------------------------------------- commit 86a3fe5f1e16ef919cf0145c0830f2ad7cd8586e Author: Karel Gardas Date: Wed Jan 13 23:31:29 2016 +0100 simplify configureIntGmpArguments based on idea provided by Gabor Greif >--------------------------------------------------------------- 86a3fe5f1e16ef919cf0145c0830f2ad7cd8586e src/Rules/Gmp.hs | 11 +++-------- 1 file changed, 3 insertions(+), 8 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index f34f3f0..f6d6fe8 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -61,14 +61,9 @@ configureIntGmpArguments :: Action [String] configureIntGmpArguments = do includes <- settingList GmpIncludeDirs libs <- settingList GmpLibDirs - return ([] - ++ (if (not (null includes)) - then map ((++) "--with-gmp-includes=") includes - else []) - ++ (if (not (null libs)) - then map ((++) "--with-gmp-libraries=") libs - else []) - ) + return $ map ("--with-gmp-includes=" ++) includes + ++ map ("--with-gmp-libraries=" ++) libs + -- TODO: we rebuild gmp every time. gmpRules :: Rules () From git at git.haskell.org Fri Oct 27 00:39:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Stack to download bootstrapping GHC and install MSYS2. (f644b3f) Message-ID: <20171027003916.4893E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f644b3fc638631388a343c533f9eb5c49957ffe0/ghc >--------------------------------------------------------------- commit f644b3fc638631388a343c533f9eb5c49957ffe0 Author: Andrey Mokhov Date: Thu Sep 1 17:43:53 2016 +0100 Use Stack to download bootstrapping GHC and install MSYS2. >--------------------------------------------------------------- f644b3fc638631388a343c533f9eb5c49957ffe0 appveyor.yml | 51 +++++++++++++++++++++++---------------------------- 1 file changed, 23 insertions(+), 28 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 30e3bcf..ffca700 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -1,41 +1,36 @@ -clone_folder: "C:\\msys64\\home\\ghc\\hadrian" +clone_folder: "c:\\ghc\\hadrian" environment: global: STACK_ROOT: "c:\\sr" cache: - - "c:\\sr" + - "c:\\sr -> appveyor.yml" install: - - cd - - set MSYSTEM=MINGW64 - - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\bin;C:\msys64;%PATH% - - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% + # Get Stack - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ - - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ - - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + # Fetch GHC sources into c:\ghc + # Note: Appveyor has already cloned Hadrian into c:\ghc\hadrian, so it's tricky + - cd .. + - git init + - git remote add origin git://git.haskell.org/ghc.git + - git pull --recurse-submodules origin master + - git submodule update --init --recursive - - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - ghc --version - - stack --version - - alex --version - - happy --version - - stack exec -- ghc-pkg list - - cd C:\msys64\home\ghc - - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" + # Install all Hadrian and GHC build dependencies + - cd hadrian + - stack setup + - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: - - cd C:\msys64\home\ghc\hadrian - - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest - - C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 + # Build Hadrian + - stack build + # Run internal Hadrian tests + - stack exec hadrian -- selftest + # Build GHC + - echo "" | stack --no-terminal exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + # Test GHC binary + - cd .. + - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:39:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify Package data type (7c65e09) Message-ID: <20171027003919.B02BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c65e0982e8fee2a23438e46de22023fb9d5836d/ghc >--------------------------------------------------------------- commit 7c65e0982e8fee2a23438e46de22023fb9d5836d Author: Andrey Mokhov Date: Fri Aug 18 02:37:00 2017 +0100 Simplify Package data type >--------------------------------------------------------------- 7c65e0982e8fee2a23438e46de22023fb9d5836d hadrian.cabal | 1 - src/Context.hs | 4 +- src/GHC.hs | 138 ++++++++++++++++++++++---------------- src/Hadrian/Haskell/Package.hs | 105 ++++++++++++++--------------- src/Rules/Data.hs | 2 +- src/Rules/Documentation.hs | 3 +- src/Rules/Generate.hs | 4 +- src/Rules/Install.hs | 3 +- src/Rules/Library.hs | 8 +-- src/Rules/Program.hs | 4 +- src/Rules/Register.hs | 4 +- src/Settings.hs | 4 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Utilities.hs | 10 +-- 15 files changed, 153 insertions(+), 141 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 7c65e0982e8fee2a23438e46de22023fb9d5836d From git at git.haskell.org Fri Oct 27 00:39:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drops 'none' (a24a85f) Message-ID: <20171027003920.283803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a24a85f283a387df60e9755398c1e2c563fe1cda/ghc >--------------------------------------------------------------- commit a24a85f283a387df60e9755398c1e2c563fe1cda Author: Moritz Angermann Date: Thu Jan 14 14:02:51 2016 +0800 Drops 'none' shake has `-q` already, which is identical. >--------------------------------------------------------------- a24a85f283a387df60e9755398c1e2c563fe1cda src/Base.hs | 1 - src/Oracles/Config/CmdLineFlag.hs | 3 +-- 2 files changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index be3ff1b..a46031c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -152,7 +152,6 @@ renderAction what input output = case buildInfo of , " input:" ++ input , " => output:" ++ output ] Dot -> "." - None -> "" -- | Render the successful build of a program renderProgram :: String -> String -> String -> String diff --git a/src/Oracles/Config/CmdLineFlag.hs b/src/Oracles/Config/CmdLineFlag.hs index 687c541..47dbbbc 100644 --- a/src/Oracles/Config/CmdLineFlag.hs +++ b/src/Oracles/Config/CmdLineFlag.hs @@ -8,7 +8,7 @@ import Data.IORef -- Flags -data BuildInfoFlag = Normal | Brief | Pony | Dot | None deriving (Eq, Show) +data BuildInfoFlag = Normal | Brief | Pony | Dot deriving (Eq, Show) data CmdLineOptions = CmdLineOptions { flagBuildInfo :: BuildInfoFlag @@ -29,7 +29,6 @@ readBuildInfoFlag ms = go "brief" = Just Brief go "pony" = Just Pony go "dot" = Just Dot - go "none" = Just None go _ = Nothing -- Left "no parse" mkClosure :: BuildInfoFlag -> CmdLineOptions -> CmdLineOptions mkClosure flag opts = opts { flagBuildInfo = flag } From git at git.haskell.org Fri Oct 27 00:39:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Exit the build script if Hadrian cannot be built (f937d80) Message-ID: <20171027003920.5C0EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f937d806ea8397132405eeede17f2662d8b0c85f/ghc >--------------------------------------------------------------- commit f937d806ea8397132405eeede17f2662d8b0c85f Author: Andrey Mokhov Date: Thu Sep 1 17:58:44 2016 +0100 Exit the build script if Hadrian cannot be built >--------------------------------------------------------------- f937d806ea8397132405eeede17f2662d8b0c85f build.stack.bat | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/build.stack.bat b/build.stack.bat index 3586290..919854e 100644 --- a/build.stack.bat +++ b/build.stack.bat @@ -1,8 +1,9 @@ @rem Change the current directory to the one containing this script @cd %~dp0 - at rem Build Hadrian and dependencies + at rem Build Hadrian and dependencies and exit the script if the build failed @stack build + at if %errorlevel% neq 0 exit /B %errorlevel% @rem Run Hadrian in GHC top directory forwarding additional user arguments @stack exec hadrian -- --lint --directory ".." %* From git at git.haskell.org Fri Oct 27 00:39:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move RTS-specific paths to Settings.Packages.Rts (f0fb1be) Message-ID: <20171027003923.6069C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f0fb1be5d3c234d40314f4743d1e45f0d891718e/ghc >--------------------------------------------------------------- commit f0fb1be5d3c234d40314f4743d1e45f0d891718e Author: Andrey Mokhov Date: Fri Aug 18 02:46:30 2017 +0100 Move RTS-specific paths to Settings.Packages.Rts >--------------------------------------------------------------- f0fb1be5d3c234d40314f4743d1e45f0d891718e src/GHC.hs | 16 ---------------- src/Rules/Data.hs | 1 + src/Rules/Generate.hs | 1 + src/Rules/Program.hs | 1 + src/Settings/Packages/Rts.hs | 17 ++++++++++++++++- 5 files changed, 19 insertions(+), 17 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 13142bd..0b3d035 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -13,9 +13,6 @@ module GHC ( -- * Package information builderProvenance, programName, nonCabalContext, nonHsMainPackage, autogenPath, - -- * RTS library - rtsContext, rtsBuildPath, rtsConfIn, - -- * Miscellaneous systemBuilderPath, ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 ) where @@ -239,19 +236,6 @@ stripCmdPath = do return ":" -- HACK: from the make-based system, see the ref above _ -> return "strip" --- TODO: Move to RTS-specific package? --- | RTS is considered a Stage1 package. This determines RTS build directory. -rtsContext :: Context -rtsContext = vanillaContext Stage1 rts - --- | Path to the RTS build directory. -rtsBuildPath :: Action FilePath -rtsBuildPath = buildPath rtsContext - --- | Path to RTS package configuration file, to be processed by HsCpp. -rtsConfIn :: FilePath -rtsConfIn = pkgPath rts -/- "package.conf.in" - buildDll0 :: Context -> Action Bool buildDll0 Context {..} = do windows <- windowsHost diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 975f3fa..ef2f017 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -6,6 +6,7 @@ import Expression import GHC import Oracles.Setting import Rules.Generate +import Settings.Packages.Rts import Target import Utilities diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 0057bf8..e5dffcc 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -14,6 +14,7 @@ import Oracles.Setting import Rules.Gmp import Rules.Libffi import Settings +import Settings.Packages.Rts import Target import Utilities diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index c88ddd8..efdd7f4 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -11,6 +11,7 @@ import Oracles.PackageData import Oracles.Setting import Rules.Wrappers import Settings +import Settings.Packages.Rts import Target import Utilities diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index fe490dd..0ae764f 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,12 +1,27 @@ -module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibrary) where +module Settings.Packages.Rts ( + rtsContext, rtsBuildPath, rtsConfIn, rtsPackageArgs, rtsLibffiLibrary + ) where import Base +import Context (buildPath) import Expression import GHC import Oracles.Flag import Oracles.Setting import Settings +-- | RTS is considered a Stage1 package. This determines RTS build directory. +rtsContext :: Context +rtsContext = vanillaContext Stage1 rts + +-- | Path to the RTS build directory. +rtsBuildPath :: Action FilePath +rtsBuildPath = buildPath rtsContext + +-- | Path to RTS package configuration file, to be processed by HsCpp. +rtsConfIn :: FilePath +rtsConfIn = pkgPath rts -/- "package.conf.in" + rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do useSystemFfi <- flag UseSystemFfi From git at git.haskell.org Fri Oct 27 00:39:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Proper support for `dot` (46bf4bc) Message-ID: <20171027003924.26E4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46bf4bcb391b6008d39aa2c334ec265141fd6a80/ghc >--------------------------------------------------------------- commit 46bf4bcb391b6008d39aa2c334ec265141fd6a80 Author: Moritz Angermann Date: Thu Jan 14 14:03:05 2016 +0800 Proper support for `dot` Adds support for `dot`, by conditionally switching between `BS.putStr` and `BS.putStrLn` depending on the msg. The additional imports are part of shake anyway. Fixes #134, dot support for good :) >--------------------------------------------------------------- 46bf4bcb391b6008d39aa2c334ec265141fd6a80 shaking-up-ghc.cabal | 2 ++ src/Main.hs | 29 ++++++++++++++++++++++++++++- 2 files changed, 30 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index b38feac..123870d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -116,6 +116,7 @@ executable ghc-shake , ScopedTypeVariables build-depends: base , ansi-terminal >= 0.6 + , bytestring >= 0.10.6 , Cabal >= 1.22 , containers >= 0.5 , directory >= 1.2 @@ -125,5 +126,6 @@ executable ghc-shake , shake >= 0.15 , transformers >= 0.4 , unordered-containers >= 0.2 + , utf8-string >= 1.0.1 default-language: Haskell2010 ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j diff --git a/src/Main.hs b/src/Main.hs index e3f1a34..6ec93429 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -14,6 +14,10 @@ import qualified Rules.Perl import qualified Test import Oracles.Config.CmdLineFlag (putOptions, flags) +import qualified Data.ByteString.Char8 as BS +import qualified Data.ByteString.UTF8 as UTF8 +import Data.Char (chr) + main :: IO () main = shakeArgsWith options flags $ \cmdLineFlags targets -> do putOptions cmdLineFlags @@ -36,4 +40,27 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do options = shakeOptions { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple - , shakeTimings = True } + , shakeTimings = True + , shakeOutput = const showMsg + } + +showMsg :: String -> IO () +showMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg +showMsg msg | dropEscSequence msg == "" = return () +showMsg msg = BS.putStrLn . UTF8.fromString $ msg + +dropEscSequence :: String -> String +dropEscSequence = go + where + esc :: Char + esc = Data.Char.chr 27 + go :: String -> String + go [] = [] + go [x] = [x] + go (x:xs) | x == esc = skip xs + go (x:xs) | otherwise = x:go xs + skip :: String -> String + skip [] = [] + skip ['m'] = [] + skip ('m':xs) = go xs + skip (_ :xs) = skip xs From git at git.haskell.org Fri Oct 27 00:39:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to drop the 'echo' hack. (fe19fc3) Message-ID: <20171027003924.3A56B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fe19fc382f56b37e7936a0c086e1bddd87c0e168/ghc >--------------------------------------------------------------- commit fe19fc382f56b37e7936a0c086e1bddd87c0e168 Author: Andrey Mokhov Date: Thu Sep 1 19:10:40 2016 +0100 Try to drop the 'echo' hack. >--------------------------------------------------------------- fe19fc382f56b37e7936a0c086e1bddd87c0e168 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index ffca700..07619c8 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -30,7 +30,7 @@ build_script: # Run internal Hadrian tests - stack exec hadrian -- selftest # Build GHC - - echo "" | stack --no-terminal exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + - stack exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest # Test GHC binary - cd .. - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:39:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Travis timeout (7231dd5) Message-ID: <20171027003926.E15E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7231dd5a3d512bbafbd65aa4ad70ecdf6a924243/ghc >--------------------------------------------------------------- commit 7231dd5a3d512bbafbd65aa4ad70ecdf6a924243 Author: Andrey Mokhov Date: Fri Aug 18 02:50:01 2017 +0100 Fix Travis timeout See #393 >--------------------------------------------------------------- 7231dd5a3d512bbafbd65aa4ad70ecdf6a924243 .travis.yml | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4fecbfc..fdd83d4 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,7 +2,7 @@ sudo: true matrix: include: - os: linux - env: MODE="--flavour=quickest --integer-simple" + env: MODE="--flavour=quickest inplace/bin/ghc-stage1" compiler: "GHC 8.0.2" addons: apt: @@ -28,7 +28,7 @@ matrix: - inplace/bin/ghc-stage2 -e 1+2 - os: linux - env: MODE="--flavour=quickest" + env: MODE="--flavour=quickest --integer-simple" compiler: "GHC 8.2.1" addons: apt: @@ -55,7 +55,7 @@ matrix: - os: osx osx_image: xcode8 - env: MODE="--flavour=quickest --integer-simple" + env: MODE="--flavour=quickest --integer-simple inplace/bin/ghc-stage1" before_install: - brew update - brew install ghc cabal-install @@ -63,7 +63,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- install: # Add Cabal to PATH From git at git.haskell.org Fri Oct 27 00:39:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Complete Advanced Render Box (231a5ce) Message-ID: <20171027003927.DB3413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/231a5ce27baa03e0750e991b5d6af3b81d9cde29/ghc >--------------------------------------------------------------- commit 231a5ce27baa03e0750e991b5d6af3b81d9cde29 Author: Moritz Angermann Date: Thu Jan 14 14:16:41 2016 +0800 Complete Advanced Render Box Should fix #134 for good. >--------------------------------------------------------------- 231a5ce27baa03e0750e991b5d6af3b81d9cde29 src/Base.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index a46031c..b9c7f72 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -115,11 +115,16 @@ a -/- b = unifyPath $ a b infixr 6 -/- +-- | A wrapper around shakes @putNormal@ that substitutes +-- any message for a fullstop if @buildInfo@ is @Dot at . +putNormal' :: String -> Action () +putNormal' = if buildInfo == Dot then putNormal . const "." else putNormal + -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do liftIO $ setSGR [SetColor Foreground Vivid colour] - putNormal msg + putNormal' msg liftIO $ setSGR [] liftIO $ hFlush stdout From git at git.haskell.org Fri Oct 27 00:39:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run stack setup in silent mode (4b682d2) Message-ID: <20171027003928.1B1033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b682d2db950154907885acc006a46ea47d9c019/ghc >--------------------------------------------------------------- commit 4b682d2db950154907885acc006a46ea47d9c019 Author: Andrey Mokhov Date: Thu Sep 1 19:59:57 2016 +0100 Run stack setup in silent mode >--------------------------------------------------------------- 4b682d2db950154907885acc006a46ea47d9c019 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 07619c8..ab3ed8c 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -21,7 +21,7 @@ install: # Install all Hadrian and GHC build dependencies - cd hadrian - - stack setup + - stack setup --silent - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: From git at git.haskell.org Fri Oct 27 00:39:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run ranlib directly (e91b0c2) Message-ID: <20171027003930.7AA723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e91b0c248df89e26d56bd5c34a48fa4e1aebacbb/ghc >--------------------------------------------------------------- commit e91b0c248df89e26d56bd5c34a48fa4e1aebacbb Author: Andrey Mokhov Date: Fri Aug 18 02:59:59 2017 +0100 Run ranlib directly >--------------------------------------------------------------- e91b0c248df89e26d56bd5c34a48fa4e1aebacbb src/Rules/Install.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index e3f7fe6..12135b4 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -281,8 +281,7 @@ installLibsTo libs dir = do ".a" -> do let out = dir -/- takeFileName lib installData [out] dir - -- TODO: Get rid of meaningless context for certain builder like ranlib - build $ target (stageContext Stage0) Ranlib [out] [out] + runBuilder Ranlib [out] _ -> installData [lib] dir -- ref: includes/ghc.mk From git at git.haskell.org Fri Oct 27 00:39:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reduce verbosity (80e986b) Message-ID: <20171027003932.3F28E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/80e986ba99c5764f78f6c4b54abc0c24953d836c/ghc >--------------------------------------------------------------- commit 80e986ba99c5764f78f6c4b54abc0c24953d836c Author: Andrey Mokhov Date: Thu Sep 1 20:14:01 2016 +0100 Reduce verbosity >--------------------------------------------------------------- 80e986ba99c5764f78f6c4b54abc0c24953d836c appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index ab3ed8c..def4dd9 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -17,11 +17,11 @@ install: - git init - git remote add origin git://git.haskell.org/ghc.git - git pull --recurse-submodules origin master - - git submodule update --init --recursive + - git submodule update --init --recursive --quiet # Install all Hadrian and GHC build dependencies - cd hadrian - - stack setup --silent + - stack setup > nul - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: From git at git.haskell.org Fri Oct 27 00:39:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refinements. (59a30fe) Message-ID: <20171027003932.3F9223A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59a30fe3270816ca27f514a3432e941538d7dcdc/ghc >--------------------------------------------------------------- commit 59a30fe3270816ca27f514a3432e941538d7dcdc Author: Moritz Angermann Date: Thu Jan 14 14:19:23 2016 +0800 Refinements. >--------------------------------------------------------------- 59a30fe3270816ca27f514a3432e941538d7dcdc src/Main.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 6ec93429..14f3554 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -41,14 +41,15 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True - , shakeOutput = const showMsg + , shakeOutput = const putMsg } -showMsg :: String -> IO () -showMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg -showMsg msg | dropEscSequence msg == "" = return () -showMsg msg = BS.putStrLn . UTF8.fromString $ msg +-- | Dynamic switch for @putStr@ and @putStrLn@ depending on the @msg at . +putMsg :: String -> IO () +putMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg +putMsg msg = BS.putStrLn . UTF8.fromString $ msg +-- | Drops ANSI Escape sequences from a string. dropEscSequence :: String -> String dropEscSequence = go where From git at git.haskell.org Fri Oct 27 00:39:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Travis (23c8602) Message-ID: <20171027003933.E0D9B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23c860257546f48deb024d2842e2171581f072bb/ghc >--------------------------------------------------------------- commit 23c860257546f48deb024d2842e2171581f072bb Author: Andrey Mokhov Date: Fri Aug 18 11:33:04 2017 +0100 Fix Travis See #393 >--------------------------------------------------------------- 23c860257546f48deb024d2842e2171581f072bb .travis.yml | 7 ------- 1 file changed, 7 deletions(-) diff --git a/.travis.yml b/.travis.yml index fdd83d4..878136c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -23,10 +23,6 @@ matrix: # Build GHC - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- - # Test GHC binary - - cd .. - - inplace/bin/ghc-stage2 -e 1+2 - - os: linux env: MODE="--flavour=quickest --integer-simple" compiler: "GHC 8.2.1" @@ -43,9 +39,6 @@ matrix: - PATH="/opt/cabal/1.22/bin:$PATH" script: - # Run internal Hadrian tests - - ./build.cabal.sh selftest - # Build GHC - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- From git at git.haskell.org Fri Oct 27 00:25:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Convert cfg/system.config.in to use unix line-endings (3bab113) Message-ID: <20171027002532.D9DA13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3bab11333ae35906dc030f1d8652d765e92db879/ghc >--------------------------------------------------------------- commit 3bab11333ae35906dc030f1d8652d765e92db879 Author: Herbert Valerio Riedel Date: Sun Apr 17 15:46:57 2016 +0200 Convert cfg/system.config.in to use unix line-endings >--------------------------------------------------------------- 3bab11333ae35906dc030f1d8652d765e92db879 cfg/system.config.in | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Fri Oct 27 00:25:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build runGhc executable (b2f49f0) Message-ID: <20171027002533.483083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2f49f06bbcda51400711d6370d1a276f01087da/ghc >--------------------------------------------------------------- commit b2f49f06bbcda51400711d6370d1a276f01087da Author: Andrey Mokhov Date: Sun Oct 23 02:35:58 2016 +0100 Build runGhc executable >--------------------------------------------------------------- b2f49f06bbcda51400711d6370d1a276f01087da src/GHC.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/GHC.hs b/src/GHC.hs index 3521e54..7cabff5 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -114,6 +114,9 @@ programPath context at Context {..} | package == hpcBin = case stage of Stage1 -> Just $ inplaceProgram "hpc" _ -> Nothing + | package == runGhc = case stage of + Stage1 -> Just $ inplaceProgram "runhaskell" + _ -> Nothing | isProgram package = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package _ -> Just . installProgram $ pkgNameString package From git at git.haskell.org Fri Oct 27 00:27:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Hadrian executable to /hadrian. (666f5c2) Message-ID: <20171027002735.DE7953A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/666f5c246d0465fd7c11bce4dadeacd46152edf5/ghc >--------------------------------------------------------------- commit 666f5c246d0465fd7c11bce4dadeacd46152edf5 Author: Andrey Mokhov Date: Sat Apr 30 14:35:22 2016 +0100 Move Hadrian executable to /hadrian. >--------------------------------------------------------------- 666f5c246d0465fd7c11bce4dadeacd46152edf5 .gitignore | 5 ++++- .travis.yml | 2 -- appveyor.yml | 3 --- build.bat | 6 +++--- build.sh | 6 +++--- src/Rules/Clean.hs | 3 +-- 6 files changed, 11 insertions(+), 14 deletions(-) diff --git a/.gitignore b/.gitignore index 967be07..b7bfddb 100644 --- a/.gitignore +++ b/.gitignore @@ -1,7 +1,10 @@ -/.shake/ /.db/ cfg/system.config +# build.bat and build.sh specific +/hadrian +/hadrian.exe + # build.cabal.sh specific /dist/ /.cabal-sandbox/ diff --git a/.travis.yml b/.travis.yml index 251f6ba..6832cd8 100644 --- a/.travis.yml +++ b/.travis.yml @@ -48,8 +48,6 @@ install: # ".git" directory into the appropriate location, and perform a hard reset # in order to regenerate the GHC-Shake files. - mkdir ghc/hadrian - - mkdir ghc/_build - - mkdir ghc/_build/hadrian - mv .git ghc/hadrian - ( cd ghc/hadrian && git reset --hard HEAD ) diff --git a/appveyor.yml b/appveyor.yml index 8850273..3918779 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -36,9 +36,6 @@ install: - alex --version - happy --version - stack exec -- ghc-pkg list - - mkdir _build - - cd _build - - mkdir hadrian build_script: - cd C:\msys64\home\ghc\hadrian diff --git a/build.bat b/build.bat index 19a2a05..f9f0b9a 100644 --- a/build.bat +++ b/build.bat @@ -1,5 +1,5 @@ @cd %~dp0 - at mkdir ../_build 2> nul + at mkdir ../_build/hadrian 2> nul @set ghcArgs=--make ^ -Wall ^ @@ -13,7 +13,7 @@ -outputdir=../_build/hadrian ^ -j ^ -O ^ - -o ../_build/hadrian + -o hadrian @set hadrianArgs=--lint ^ --directory ^ @@ -27,4 +27,4 @@ @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains @set GHC_PACKAGE_PATH= - at ..\_build\hadrian %hadrianArgs% + at hadrian %hadrianArgs% diff --git a/build.sh b/build.sh index 8b53f81..f7d06c2 100755 --- a/build.sh +++ b/build.sh @@ -30,7 +30,7 @@ function rl { root="$(dirname "$(rl "$0")")" -mkdir -p "$root/../_build" +mkdir -p "$root/../_build/hadrian" ghc \ "$root/src/Main.hs" \ @@ -43,9 +43,9 @@ ghc \ -threaded \ -outputdir="$root/../_build/hadrian" \ -j -O \ - -o "$root/../_build/hadrian" + -o "$root/hadrian" -"$root/../_build/hadrian" \ +"$root/hadrian" \ --lint \ --directory "$root/.." \ --colour \ diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 357ac34..0bff316 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -17,8 +17,7 @@ clean dir = do cleanRules :: Rules () cleanRules = do "clean" ~> do - forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) - clean (buildRootPath -/- "hadrian") + clean buildRootPath clean programInplacePath clean "inplace/lib" clean derivedConstantsPath From git at git.haskell.org Fri Oct 27 00:27:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Updates travis and README to reflect fixing #26 (f3a1eb7) Message-ID: <20171027002736.80C7C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f3a1eb726e550d458476764d99ad68fe042de81b/ghc >--------------------------------------------------------------- commit f3a1eb726e550d458476764d99ad68fe042de81b Author: Moritz Angermann Date: Wed Jan 6 23:24:22 2016 +0800 Updates travis and README to reflect fixing #26 >--------------------------------------------------------------- f3a1eb726e550d458476764d99ad68fe042de81b .travis.yml | 3 +-- README.md | 3 --- 2 files changed, 1 insertion(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index e096ddf..055edd5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -51,8 +51,7 @@ install: - ( cd ghc/shake-build && cabal install --only-dependencies ) - ( cd ghc && ./boot ) - - if [ $TRAVIS_OS_NAME == osx ]; then ( cd ghc && ./configure --with-gcc="$(which clang)"); fi - - if [ $TRAVIS_OS_NAME == linux ]; then ( cd ghc && ./configure ); fi + - ( cd ghc && ./configure ) script: - ./ghc/shake-build/build.sh -j --no-progress diff --git a/README.md b/README.md index 90f6422..45789e3 100644 --- a/README.md +++ b/README.md @@ -31,9 +31,6 @@ git submodule update --init git clone git://github.com/snowleopard/shaking-up-ghc shake-build ./boot ./configure -# or if you want to use clang (e.g. building on OS X) -./configure --with-gcc=$(which clang) # See #26 - ``` Now you have a couple of options: From git at git.haskell.org Fri Oct 27 00:27:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path separators (8be3f76) Message-ID: <20171027002740.00E3C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8be3f76d78e9806bdbef6a2d2db7bbf341aba0ea/ghc >--------------------------------------------------------------- commit 8be3f76d78e9806bdbef6a2d2db7bbf341aba0ea Author: Andrey Mokhov Date: Mon Oct 31 19:19:19 2016 +0000 Fix path separators >--------------------------------------------------------------- 8be3f76d78e9806bdbef6a2d2db7bbf341aba0ea src/Oracles/DirectoryContents.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/SourceDist.hs | 9 ++++----- 3 files changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Oracles/DirectoryContents.hs b/src/Oracles/DirectoryContents.hs index 6dd3439..d854c7d 100644 --- a/src/Oracles/DirectoryContents.hs +++ b/src/Oracles/DirectoryContents.hs @@ -27,7 +27,7 @@ directoryContents expr dir = askOracle $ DirectoryContents (expr, dir) directoryContentsOracle :: Rules () directoryContentsOracle = void $ - addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ + addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ map unifyPath . filter (matches expr) <$> listFilesInside (return . matches expr) dir instance Binary Match diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 64f8ea9..2d3eb4a 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -14,7 +14,7 @@ import Util compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context - nonHs extension = path extension "*" <.> osuf way + nonHs extension = path -/- extension "*" <.> osuf way compile compiler obj2src obj = do let src = obj2src context obj need [src] diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index d51fe75..d56eb38 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -15,9 +15,9 @@ sourceDistRules = do putSuccess "| Done. " "sdistprep/ghc-*-src.tar.xz" %> \fname -> do let tarName = takeFileName fname - treePath = "sdistprep/ghc" dropTarXz tarName + treePath = "sdistprep/ghc" -/- dropTarXz tarName prepareTree treePath - runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." tarName, dropTarXz tarName] + runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." -/- tarName, dropTarXz tarName] "GIT_COMMIT_ID" %> \fname -> setting ProjectGitCommitId >>= writeFileChanged fname "VERSION" %> \fname -> @@ -25,14 +25,13 @@ sourceDistRules = do where dropTarXz = dropExtension . dropExtension - prepareTree :: FilePath -> Action () prepareTree dest = do mapM_ cpDir srcDirs mapM_ cpFile srcFiles where - cpFile a = copyFile a (dest a) - cpDir a = copyDirectoryContents (Not excluded) a (dest takeFileName a) + cpFile a = copyFile a (dest -/- a) + cpDir a = copyDirectoryContents (Not excluded) a (dest -/- takeFileName a) excluded = Or [ Test "//.*" , Test "//#*" From git at git.haskell.org Fri Oct 27 00:27:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a test appveyor script, see #110. (290e990) Message-ID: <20171027002740.497E73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/290e990dd8500de9728d83506a0bacd143619def/ghc >--------------------------------------------------------------- commit 290e990dd8500de9728d83506a0bacd143619def Author: Andrey Mokhov Date: Wed Jan 6 17:48:41 2016 +0000 Add a test appveyor script, see #110. >--------------------------------------------------------------- 290e990dd8500de9728d83506a0bacd143619def .appveyor.yml | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/.appveyor.yml b/.appveyor.yml new file mode 100644 index 0000000..25df24b --- /dev/null +++ b/.appveyor.yml @@ -0,0 +1,8 @@ +install: + - set PATH=C:\msys64\usr\bin;%PATH% + - bash "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" + +build_script: + - echo "test" + +test: off From git at git.haskell.org Fri Oct 27 00:27:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Shake files into _build/hadrian (185af60) Message-ID: <20171027002740.0734B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/185af600e91c5294fe8f49158ca8d73aec6ec646/ghc >--------------------------------------------------------------- commit 185af600e91c5294fe8f49158ca8d73aec6ec646 Author: Andrey Mokhov Date: Sat Apr 30 23:04:41 2016 +0100 Move Shake files into _build/hadrian >--------------------------------------------------------------- 185af600e91c5294fe8f49158ca8d73aec6ec646 src/Base.hs | 13 +------------ src/Main.hs | 4 ++-- src/Oracles/PackageDeps.hs | 4 +++- src/Rules/Clean.hs | 6 +++--- src/Settings/Paths.hs | 12 +++++++++++- 5 files changed, 20 insertions(+), 19 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 53bb197..a38ea51 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,8 +16,7 @@ module Base ( module Development.Shake.FilePath, -- * Paths - shakeFilesPath, configPath, configFile, sourcePath, programInplacePath, - bootPackageConstraints, packageDependencies, + configPath, configFile, sourcePath, programInplacePath, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, @@ -50,10 +49,6 @@ import System.IO shakePath :: FilePath shakePath = "hadrian" --- TODO: Move to buildRootPath. -shakeFilesPath :: FilePath -shakeFilesPath = shakePath -/- ".db" - configPath :: FilePath configPath = shakePath -/- "cfg" @@ -69,12 +64,6 @@ sourcePath = shakePath -/- "src" programInplacePath :: FilePath programInplacePath = "inplace/bin" -bootPackageConstraints :: FilePath -bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" - -packageDependencies :: FilePath -packageDependencies = shakeFilesPath -/- "package-dependencies" - -- Utility functions -- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] diff --git a/src/Main.hs b/src/Main.hs index cf45cc3..66f897f 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,7 +2,6 @@ module Main (main) where import Development.Shake -import qualified Base import qualified CmdLineFlag import qualified Environment import qualified Rules @@ -10,6 +9,7 @@ import qualified Rules.Clean import qualified Rules.Oracles import qualified Rules.Selftest import qualified Rules.Test +import qualified Settings.Paths main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -30,6 +30,6 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest - , shakeFiles = Base.shakeFilesPath + , shakeFiles = Settings.Paths.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 6a5f7dd..a2a9234 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -1,9 +1,11 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.PackageDeps (packageDeps, packageDepsOracle) where -import Base import qualified Data.HashMap.Strict as Map + +import Base import Package +import Settings.Paths newtype PackageDepsKey = PackageDepsKey PackageName deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 0bff316..ca5c062 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -17,7 +17,7 @@ clean dir = do cleanRules :: Rules () cleanRules = do "clean" ~> do - clean buildRootPath + forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) clean programInplacePath clean "inplace/lib" clean derivedConstantsPath @@ -29,6 +29,6 @@ cleanRules = do forM_ [Stage0 ..] $ \stage -> do let dir = pkgPath pkg -/- contextDirectory (vanillaContext stage pkg) removeDirectoryIfExists dir - putBuild $ "| Remove the Shake database " ++ shakeFilesPath ++ "..." - removeFilesAfter shakeFilesPath ["//*"] + putBuild $ "| Remove Hadrian files..." + removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 678ed92..77fb5a5 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,8 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpBuildInfoPath, - packageDbDirectory, pkgConfFile + packageDbDirectory, pkgConfFile, shakeFilesPath, bootPackageConstraints, + packageDependencies ) where import Base @@ -16,6 +17,15 @@ import Settings.User (~/~) :: FilePath -> FilePath -> FilePath x ~/~ y = x ++ '/' : y +shakeFilesPath :: FilePath +shakeFilesPath = buildRootPath -/- "hadrian/shake-files" + +bootPackageConstraints :: FilePath +bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" + +packageDependencies :: FilePath +packageDependencies = shakeFilesPath -/- "package-dependencies" + -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath buildPath context at Context {..} = From git at git.haskell.org Fri Oct 27 00:27:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant createDirectory calls (7041682) Message-ID: <20171027002744.56A7C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7041682e77204d718def64aee7d0c768ffd685bd/ghc >--------------------------------------------------------------- commit 7041682e77204d718def64aee7d0c768ffd685bd Author: Andrey Mokhov Date: Mon Oct 31 19:50:36 2016 +0000 Drop redundant createDirectory calls >--------------------------------------------------------------- 7041682e77204d718def64aee7d0c768ffd685bd src/Rules/Data.hs | 1 - src/Rules/Gmp.hs | 2 -- src/Rules/Libffi.hs | 1 - src/Util.hs | 2 +- 4 files changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 65c6392..ab8ac97 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -47,7 +47,6 @@ buildPackageData context at Context {..} = do | otherwise = oldPath -/- "build" -/- pkgNameString package copyFile inTreeMk mk autogenFiles <- getDirectoryFiles oldBuild ["autogen/*"] - createDirectory $ buildPath context -/- "autogen" forM_ autogenFiles $ \file' -> do let file = unifyPath file' copyFile (oldBuild -/- file) (buildPath context -/- file) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1024533..2409b6e 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -44,14 +44,12 @@ gmpRules = do any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" - createDirectory $ takeDirectory header copyFile (gmpBase -/- "ghc-gmp.h") header else do putBuild "| No GMP library/framework detected; in tree GMP will be built" need [gmpLibrary] createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] - createDirectory $ takeDirectory header copyFile (gmpBuildPath -/- "gmp.h") header copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index ae1c06f..8d72017 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,7 +70,6 @@ libffiRules = do libffiMakefile <.> "in" %> \mkIn -> do removeDirectory libffiBuildPath - createDirectory $ buildRootPath -/- stageString Stage0 tarball <- unifyPath . getSingleton "Exactly one LibFFI tarball is expected" <$> getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] diff --git a/src/Util.hs b/src/Util.hs index f2e6516..81f67dd 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -92,7 +92,7 @@ captureStdout target path argList = do Stdout output <- cmd [path] argList writeFileChanged file output --- | Copy a file tracking the source. +-- | Copy a file tracking the source, create the target directory if missing. copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. From git at git.haskell.org Fri Oct 27 00:27:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use in-tree Cabal library. (e6373a0) Message-ID: <20171027002744.AA0253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e6373a064cac830b4ee1a1651d888c5b64b9ca80/ghc >--------------------------------------------------------------- commit e6373a064cac830b4ee1a1651d888c5b64b9ca80 Author: Andrey Mokhov Date: Sun May 1 00:40:08 2016 +0100 Use in-tree Cabal library. See #228. >--------------------------------------------------------------- e6373a064cac830b4ee1a1651d888c5b64b9ca80 build.bat | 1 + build.sh | 1 + 2 files changed, 2 insertions(+) diff --git a/build.bat b/build.bat index f9f0b9a..6e86d42 100644 --- a/build.bat +++ b/build.bat @@ -11,6 +11,7 @@ -rtsopts ^ -with-rtsopts=-I0 ^ -outputdir=../_build/hadrian ^ + -i../libraries/Cabal/Cabal ^ -j ^ -O ^ -o hadrian diff --git a/build.sh b/build.sh index f7d06c2..fff8df4 100755 --- a/build.sh +++ b/build.sh @@ -38,6 +38,7 @@ ghc \ -fno-warn-name-shadowing \ -XRecordWildCards \ -i"$root/src" \ + -i"$root/../libraries/Cabal/Cabal" \ -rtsopts \ -with-rtsopts=-I0 \ -threaded \ From git at git.haskell.org Fri Oct 27 00:27:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix test script, see #110. (8bf936f) Message-ID: <20171027002744.CC6543A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8bf936f4942a51bbfbd4c561a1dbfb89300bcdff/ghc >--------------------------------------------------------------- commit 8bf936f4942a51bbfbd4c561a1dbfb89300bcdff Author: Andrey Mokhov Date: Wed Jan 6 18:11:05 2016 +0000 Fix test script, see #110. >--------------------------------------------------------------- 8bf936f4942a51bbfbd4c561a1dbfb89300bcdff .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 25df24b..b5faf11 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,6 +1,7 @@ install: - - set PATH=C:\msys64\usr\bin;%PATH% - - bash "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" + - set MSYSTEM=MINGW64 + - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% + - bash -lc "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" build_script: - echo "test" From git at git.haskell.org Fri Oct 27 00:27:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify, remove old hacks (4fd513a) Message-ID: <20171027002748.8B18E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fd513a325e1689e971f72941975ee20912bd647/ghc >--------------------------------------------------------------- commit 4fd513a325e1689e971f72941975ee20912bd647 Author: Andrey Mokhov Date: Mon Oct 31 23:52:34 2016 +0000 Simplify, remove old hacks >--------------------------------------------------------------- 4fd513a325e1689e971f72941975ee20912bd647 src/Rules/Generate.hs | 39 +++++++++++++-------------------------- 1 file changed, 13 insertions(+), 26 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 0141f29..d13d2bb 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -3,8 +3,6 @@ module Rules.Generate ( installTargets, copyRules, includesDependencies, generatedDependencies ) where -import qualified System.Directory as IO - import Base import Context hiding (package) import Expression @@ -110,21 +108,27 @@ generatePackageCode :: Context -> Rules () generatePackageCode context@(Context stage pkg _) = let path = buildPath context generated f = (path ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) - file <~ gen = generate file context gen + go gen file = generate file context gen in do generated ?> \file -> do let unpack = fromMaybe . error $ "No generator for " ++ file ++ "." (src, builder) <- unpack <$> findGenerator context file need [src] build $ Target context builder [src] [file] - let srcBoot = src -<.> "hs-boot" - whenM (doesFileExist srcBoot) $ - copyFile srcBoot $ file -<.> "hs-boot" + let boot = src -<.> "hs-boot" + whenM (doesFileExist boot) . copyFile boot $ file -<.> "hs-boot" + + priority 2.0 $ do + when (pkg == compiler) $ path -/- "Config.hs" %> go generateConfigHs + when (pkg == ghcPkg) $ path -/- "Version.hs" %> go generateVersionHs -- TODO: needing platformH is ugly and fragile - when (pkg == compiler) $ primopsTxt stage %> \file -> do - need $ [platformH stage, primopsSource] ++ includesDependencies - build $ Target context HsCpp [primopsSource] [file] + when (pkg == compiler) $ do + primopsTxt stage %> \file -> do + need $ [platformH stage, primopsSource] ++ includesDependencies + build $ Target context HsCpp [primopsSource] [file] + + platformH stage %> go generateGhcBootPlatformH -- TODO: why different folders for generated files? fmap (path -/-) @@ -133,26 +137,10 @@ generatePackageCode context@(Context stage pkg _) = , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] build $ Target context GenPrimopCode [primopsTxt stage] [file] - -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- stageDirectory stage -/- "build" - newFile = oldPath ++ (drop (length path) file) - createDirectory $ takeDirectory newFile - liftIO $ IO.copyFile file newFile - putBuild $ "| Duplicate file " ++ file ++ " -> " ++ newFile when (pkg == rts) $ path -/- "cmm/AutoApply.cmm" %> \file -> build $ Target context GenApply [] [file] - priority 2.0 $ do - when (pkg == compiler) $ path -/- "Config.hs" %> \file -> do - file <~ generateConfigHs - - when (pkg == compiler) $ platformH stage %> \file -> do - file <~ generateGhcBootPlatformH - - when (pkg == ghcPkg) $ path -/- "Version.hs" %> \file -> do - file <~ generateVersionHs - copyRules :: Rules () copyRules = do "inplace/lib/ghc-usage.txt" <~ "driver" @@ -179,7 +167,6 @@ generateRules = do generatedPath ++ "//*" %> \file -> do withTempDir $ \dir -> build $ Target rtsContext DeriveConstants [] [file, dir] - where file <~ gen = file %> \out -> generate out emptyTarget gen From git at git.haskell.org Fri Oct 27 00:27:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Turn Configure into a Builder. (72f6ec6) Message-ID: <20171027002748.CC1693A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72f6ec653e2f8801fc275ffa5d294a85e6e34ee8/ghc >--------------------------------------------------------------- commit 72f6ec653e2f8801fc275ffa5d294a85e6e34ee8 Author: Andrey Mokhov Date: Mon May 2 02:49:30 2016 +0100 Turn Configure into a Builder. >--------------------------------------------------------------- 72f6ec653e2f8801fc275ffa5d294a85e6e34ee8 hadrian.cabal | 1 + src/Builder.hs | 70 ++++++++++++++++++-------------------- src/Predicates.hs | 17 +++++++-- src/Rules/Actions.hs | 53 ++++++++++++++--------------- src/Rules/Gmp.hs | 19 ++++------- src/Rules/Libffi.hs | 51 ++++++++++++--------------- src/Rules/Setup.hs | 19 +++++++---- src/Settings/Args.hs | 2 ++ src/Settings/Builders/Configure.hs | 30 ++++++++++++++++ src/Settings/Paths.hs | 6 +++- src/Settings/User.hs | 2 +- 11 files changed, 155 insertions(+), 115 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 72f6ec653e2f8801fc275ffa5d294a85e6e34ee8 From git at git.haskell.org Fri Oct 27 00:27:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install prerequisites for Windows build. (584fd8a) Message-ID: <20171027002749.227D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/584fd8a9811592d04c7c1d43c37778410b8d6590/ghc >--------------------------------------------------------------- commit 584fd8a9811592d04c7c1d43c37778410b8d6590 Author: Andrey Mokhov Date: Wed Jan 6 18:19:24 2016 +0000 Install prerequisites for Windows build. See #110. [skip ci] >--------------------------------------------------------------- 584fd8a9811592d04c7c1d43c37778410b8d6590 .appveyor.yml | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index b5faf11..2b710e0 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,7 +1,11 @@ install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - bash -lc "pacman -S git tar binutils autoconf make libtool automake python2 p7zip patch gcc mingw-w64-$(uname -m)-python3-sphinx" + - bash -lc "pacman -S --noconfirm git binutils p7zip gcc mingw-w64-$(uname -m)-python3-sphinx" + - bash -lc "curl -L http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" + - bash -lc "curl -L https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + - bash -lc "cabal update" + - bash -lc "cabal install -j --prefix=/usr/local alex happy" build_script: - echo "test" From git at git.haskell.org Fri Oct 27 00:27:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependencies on generated files (010dd78) Message-ID: <20171027002753.6DB6A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/010dd78b1e574c648f9a93d2a636ff9ae05422ff/ghc >--------------------------------------------------------------- commit 010dd78b1e574c648f9a93d2a636ff9ae05422ff Author: Andrey Mokhov Date: Mon Oct 31 23:55:27 2016 +0000 Add missing dependencies on generated files See #285. >--------------------------------------------------------------- 010dd78b1e574c648f9a93d2a636ff9ae05422ff src/Rules/Dependencies.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 04c4f1f..192e24c 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -6,6 +6,7 @@ import Base import Context import Expression import Oracles.ModuleFiles +import Rules.Generate import Settings.Path import Target import Util @@ -15,6 +16,7 @@ buildPackageDependencies rs context at Context {..} = buildPath context -/- ".dependencies" %> \deps -> do srcs <- hsSources context need srcs + orderOnly =<< interpretInContext context generatedDependencies let mk = deps <.> "mk" if srcs == [] then writeFileChanged mk "" From git at git.haskell.org Fri Oct 27 00:27:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do putInfo even in verbose mode, minor revision. (0b6c0aa) Message-ID: <20171027002753.7416D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b6c0aa0b4dcbbc3eb65a101edf7db64c72043b4/ghc >--------------------------------------------------------------- commit 0b6c0aa0b4dcbbc3eb65a101edf7db64c72043b4 Author: Andrey Mokhov Date: Mon May 2 03:08:10 2016 +0100 Do putInfo even in verbose mode, minor revision. >--------------------------------------------------------------- 0b6c0aa0b4dcbbc3eb65a101edf7db64c72043b4 src/Rules/Actions.hs | 3 ++- src/Settings/User.hs | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5af1ce4..f006947 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -46,7 +46,7 @@ customBuild rs opts target at Target {..} = do -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do - unless verbose $ putInfo target + putInfo target quietlyUnlessVerbose $ case builder of Ar -> do output <- interpret target getOutput @@ -59,6 +59,7 @@ customBuild rs opts target at Target {..} = do Configure dir -> do need [dir -/- "configure"] + -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" cmd Shell (EchoStdout False) [Cwd dir] [path] (env:opts) argList diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 215a05b..0893579 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -81,7 +81,7 @@ buildHaddock = return cmdBuildHaddock -- this is a Predicate, hence you can enable verbose output for a chosen package -- only, e.g.: verboseCommands = package ghcPrim verboseCommands :: Predicate -verboseCommands = builder Configure +verboseCommands = return False -- TODO: Replace with stage2 ? arg "-Werror"? -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. From git at git.haskell.org Fri Oct 27 00:27:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create /usr/local/bin, silence curl. (1731a15) Message-ID: <20171027002753.C282B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1731a15422f2be3eb09b612426900801ea3b294f/ghc >--------------------------------------------------------------- commit 1731a15422f2be3eb09b612426900801ea3b294f Author: Andrey Mokhov Date: Wed Jan 6 18:33:03 2016 +0000 Create /usr/local/bin, silence curl. See #110. [skip ci] >--------------------------------------------------------------- 1731a15422f2be3eb09b612426900801ea3b294f .appveyor.yml | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 2b710e0..f8ce40a 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -2,8 +2,10 @@ install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc mingw-w64-$(uname -m)-python3-sphinx" - - bash -lc "curl -L http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "curl -L https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" + - bash -lc "mkdir /usr/local" + - bash -lc "mkdir /usr/local/bin" + - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" From git at git.haskell.org Fri Oct 27 00:27:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop heavy python dependency, change project folder. (907af3f) Message-ID: <20171027002757.5A4AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/907af3f12f842ca7598854e5707d6398f48fd93e/ghc >--------------------------------------------------------------- commit 907af3f12f842ca7598854e5707d6398f48fd93e Author: Andrey Mokhov Date: Wed Jan 6 18:51:55 2016 +0000 Drop heavy python dependency, change project folder. See #110. [skip ci] >--------------------------------------------------------------- 907af3f12f842ca7598854e5707d6398f48fd93e .appveyor.yml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f8ce40a..f9f938d 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,7 +1,9 @@ +clone_folder: "C:\msys64\home\ghc\shake-build" + install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - - bash -lc "pacman -S --noconfirm git binutils p7zip gcc mingw-w64-$(uname -m)-python3-sphinx" + - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - bash -lc "mkdir /usr/local" - bash -lc "mkdir /usr/local/bin" From git at git.haskell.org Fri Oct 27 00:27:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:27:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Print version info before running configure (759dff3) Message-ID: <20171027002757.CCF2E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/759dff36f7d30aba45bd3b6f9947328b4c0a8c77/ghc >--------------------------------------------------------------- commit 759dff36f7d30aba45bd3b6f9947328b4c0a8c77 Author: Andrey Mokhov Date: Mon May 2 03:45:49 2016 +0100 Print version info before running configure >--------------------------------------------------------------- 759dff36f7d30aba45bd3b6f9947328b4c0a8c77 appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 3918779..76ccbe1 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -24,6 +24,11 @@ install: - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - ghc --version + - stack --version + - alex --version + - happy --version + - stack exec -- ghc-pkg list - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot @@ -31,11 +36,6 @@ install: - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eca7b6a6d9a17e44854cb8f696cec03140052208/ghc >--------------------------------------------------------------- commit eca7b6a6d9a17e44854cb8f696cec03140052208 Author: Andrey Mokhov Date: Tue Nov 1 19:27:32 2016 +0000 Move GHC/Prim.hs outside of autogen directory >--------------------------------------------------------------- eca7b6a6d9a17e44854cb8f696cec03140052208 src/Oracles/ModuleFiles.hs | 6 +----- src/Rules/Generate.hs | 4 ++-- 2 files changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index a9bae04..70a7a9f 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -75,11 +75,7 @@ findGenerator Context {..} file = do -- | Find all Haskell source files for a given 'Context'. hsSources :: Context -> Action [FilePath] hsSources context = do - let autogen = buildPath context -/- "autogen" - -- Generated source files live in buildPath and have extension "hs", except - -- for GHC/Prim.hs that lives in autogen. TODO: fix the inconsistency? - modFile ("GHC.Prim", _) = autogen -/- "GHC/Prim.hs" - modFile (m, Nothing ) = generatedFile context m + let modFile (m, Nothing ) = generatedFile context m modFile (m, Just file ) | takeExtension file `elem` haskellExtensions = file | otherwise = generatedFile context m diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index d13d2bb..e84313a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -55,7 +55,7 @@ ghcPrimDependencies :: Expr [FilePath] ghcPrimDependencies = do stage <- getStage let path = buildPath $ vanillaContext stage ghcPrim - return [path -/- "autogen/GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"] + return [path -/- "GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"] derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = installTargets ++ fmap (generatedPath -/-) @@ -132,7 +132,7 @@ generatePackageCode context@(Context stage pkg _) = -- TODO: why different folders for generated files? fmap (path -/-) - [ "autogen/GHC/Prim.hs" + [ "GHC/Prim.hs" , "GHC/PrimopWrappers.hs" , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] From git at git.haskell.org Fri Oct 27 00:28:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to clone folder. (dfc34f1) Message-ID: <20171027002800.DC0413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfc34f1fb0d7aec2392cd700eaa91d10a6c87835/ghc >--------------------------------------------------------------- commit dfc34f1fb0d7aec2392cd700eaa91d10a6c87835 Author: Andrey Mokhov Date: Wed Jan 6 18:53:37 2016 +0000 Fix path to clone folder. See #110. [skip ci] >--------------------------------------------------------------- dfc34f1fb0d7aec2392cd700eaa91d10a6c87835 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f9f938d..fa03afe 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,4 +1,4 @@ -clone_folder: "C:\msys64\home\ghc\shake-build" +clone_folder: "C:\\msys64\\home\\ghc\\shake-build" install: - set MSYSTEM=MINGW64 From git at git.haskell.org Fri Oct 27 00:28:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix cabal path, create directory for cabal if it does not exist. (3e42d47) Message-ID: <20171027002818.E37DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e42d47e05153bee9fe430e8e91e58c0bea12ea0/ghc >--------------------------------------------------------------- commit 3e42d47e05153bee9fe430e8e91e58c0bea12ea0 Author: Andrey Mokhov Date: Wed Jan 6 22:11:00 2016 +0000 Fix cabal path, create directory for cabal if it does not exist. See #110. [skip ci] >--------------------------------------------------------------- 3e42d47e05153bee9fe430e8e91e58c0bea12ea0 .appveyor.yml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index f70a821..eb57bd8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,21 +1,22 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" cache: - - "C:\\msys64\home\cabal" + - "C:\\msys64\\home\\cabal" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir /usr/local" - - bash -lc "mkdir /usr/local/bin" + - bash -lc "mkdir -p /home/cabal" + - bash -lc "mkdir -p /usr/local" + - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - bash -lc "cabal --config-file=/home/cabal update" - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal \install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:28:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use qualified imports in Rules.hs for better readability. (56be38d) Message-ID: <20171027002828.92D2D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56be38d48f28022d370edb1f7d3663630dde9c45/ghc >--------------------------------------------------------------- commit 56be38d48f28022d370edb1f7d3663630dde9c45 Author: Andrey Mokhov Date: Thu May 5 00:16:54 2016 +0100 Use qualified imports in Rules.hs for better readability. >--------------------------------------------------------------- 56be38d48f28022d370edb1f7d3663630dde9c45 src/Rules.hs | 58 +++++++++++++++++++++++++++++----------------------------- 1 file changed, 29 insertions(+), 29 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 2f84917..e3caf6c 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -6,19 +6,19 @@ import Base import Context import Expression import GHC -import Rules.Compile -import Rules.Data -import Rules.Dependencies -import Rules.Documentation -import Rules.Generate -import Rules.Cabal -import Rules.Configure -import Rules.Gmp -import Rules.Libffi -import Rules.Library -import Rules.Perl -import Rules.Program -import Rules.Register +import qualified Rules.Compile +import qualified Rules.Data +import qualified Rules.Dependencies +import qualified Rules.Documentation +import qualified Rules.Generate +import qualified Rules.Cabal +import qualified Rules.Configure +import qualified Rules.Gmp +import qualified Rules.Libffi +import qualified Rules.Library +import qualified Rules.Perl +import qualified Rules.Program +import qualified Rules.Register import Settings allStages :: [Stage] @@ -66,25 +66,25 @@ packageRules = do vanillaContexts = liftM2 vanillaContext allStages knownPackages for_ contexts $ mconcat - [ compilePackage readPackageDb - , buildPackageLibrary ] + [ Rules.Compile.compilePackage readPackageDb + , Rules.Library.buildPackageLibrary ] for_ vanillaContexts $ mconcat - [ buildPackageData - , buildPackageDependencies readPackageDb - , buildPackageDocumentation - , buildPackageGhciLibrary - , generatePackageCode - , buildProgram readPackageDb - , registerPackage writePackageDb ] + [ Rules.Data.buildPackageData + , Rules.Dependencies.buildPackageDependencies readPackageDb + , Rules.Documentation.buildPackageDocumentation + , Rules.Library.buildPackageGhciLibrary + , Rules.Generate.generatePackageCode + , Rules.Program.buildProgram readPackageDb + , Rules.Register.registerPackage writePackageDb ] buildRules :: Rules () buildRules = do - cabalRules - configureRules - generateRules - copyRules - gmpRules - libffiRules - perlScriptRules + Rules.Cabal.cabalRules + Rules.Configure.configureRules + Rules.Generate.copyRules + Rules.Generate.generateRules + Rules.Gmp.gmpRules + Rules.Libffi.libffiRules packageRules + Rules.Perl.perlScriptRules From git at git.haskell.org Fri Oct 27 00:28:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move custom contexts to Settings.Path (72a08b0) Message-ID: <20171027002830.060073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72a08b0e226c62396437c29e019a61dba03e48fd/ghc >--------------------------------------------------------------- commit 72a08b0e226c62396437c29e019a61dba03e48fd Author: Andrey Mokhov Date: Sun Nov 27 12:01:41 2016 +0000 Move custom contexts to Settings.Path >--------------------------------------------------------------- 72a08b0e226c62396437c29e019a61dba03e48fd src/Rules/Data.hs | 1 - src/Rules/Gmp.hs | 3 --- src/Rules/Libffi.hs | 9 +-------- src/Settings/Path.hs | 31 ++++++++++++++++++++++--------- 4 files changed, 23 insertions(+), 21 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 5c8a63b..58164d8 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -8,7 +8,6 @@ import Oracles.Config.Setting import Oracles.Dependencies import Oracles.Path import Rules.Generate -import Rules.Libffi import Settings.Path import Target import UserSettings diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 2409b6e..1442118 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -14,9 +14,6 @@ import Util gmpBase :: FilePath gmpBase = pkgPath integerGmp -/- "gmp" -gmpContext :: Context -gmpContext = vanillaContext Stage1 integerGmp - gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 8d72017..989288e 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,21 +1,14 @@ -module Rules.Libffi (rtsBuildPath, libffiRules, libffiDependencies) where +module Rules.Libffi (libffiRules, libffiDependencies) where import Settings.Builders.Common import Settings.Packages.Rts import Target import Util --- TODO: this should be moved elsewhere -rtsBuildPath :: FilePath -rtsBuildPath = buildPath rtsContext - -- TODO: Why copy these include files into rts? Keep in libffi! libffiDependencies :: [FilePath] libffiDependencies = (rtsBuildPath -/-) <$> [ "ffi.h", "ffitarget.h" ] -libffiContext :: Context -libffiContext = vanillaContext Stage1 libffi - libffiLibrary :: FilePath libffiLibrary = libffiBuildPath -/- "inst/lib/libffi.a" diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 8999300..9e88ca6 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -1,10 +1,11 @@ module Settings.Path ( stageDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, - gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, - pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, - packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath, pkgInplaceConfig, rtsContext, rtsConfIn + pkgLibraryFile0, pkgGhciLibraryFile, gmpContext, gmpBuildPath, gmpObjects, + gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiContext, libffiBuildPath, + rtsContext, rtsBuildPath, rtsConfIn, shakeFilesPath,packageDbDirectory, + pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, + objectPath, programInplacePath, programInplaceLibPath, installPath, + autogenPath, pkgInplaceConfig ) where import Base @@ -100,17 +101,25 @@ pkgFile context prefix suffix = do componentId <- pkgData $ ComponentId path return $ path -/- prefix ++ componentId ++ suffix --- | RTS is considered a Stage1 package. This determines RTS build path. +-- | RTS is considered a Stage1 package. This determines RTS build directory. rtsContext :: Context rtsContext = vanillaContext Stage1 rts +-- | Path to the RTS build directory. +rtsBuildPath :: FilePath +rtsBuildPath = buildPath rtsContext + -- | Path to RTS package configuration file, to be processed by HsCpp. rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" +-- | GMP is considered a Stage1 package. This determines GMP build directory. +gmpContext :: Context +gmpContext = vanillaContext Stage1 integerGmp + -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage1/gmp" +gmpBuildPath = buildRootPath -/- stageDirectory (stage gmpContext) -/- "gmp" -- | Path to the GMP library header. gmpLibraryH :: FilePath @@ -124,9 +133,13 @@ gmpObjects = gmpBuildPath -/- "objs" gmpBuildInfoPath :: FilePath gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" --- | Build directory for in-tree libffi library. +-- | Libffi is considered a Stage1 package. This determines its build directory. +libffiContext :: Context +libffiContext = vanillaContext Stage1 libffi + +-- | Build directory for in-tree Libffi library. libffiBuildPath :: FilePath -libffiBuildPath = buildRootPath -/- "stage1/libffi" +libffiBuildPath = buildPath libffiContext -- TODO: Move to buildRootPath, see #113. -- | Path to package database directory of a given 'Stage'. Note: StageN, N > 0, From git at git.haskell.org Fri Oct 27 00:28:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run cabal outside bash. (f419f64) Message-ID: <20171027002830.730BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f419f6430ff16818513a33fd802b2c09488c5311/ghc >--------------------------------------------------------------- commit f419f6430ff16818513a33fd802b2c09488c5311 Author: Andrey Mokhov Date: Wed Jan 6 23:12:14 2016 +0000 Run cabal outside bash. See #110. [skip ci] >--------------------------------------------------------------- f419f6430ff16818513a33fd802b2c09488c5311 .appveyor.yml | 15 ++++++++------- 1 file changed, 8 insertions(+), 7 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 751bc1f..d8bb09d 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,7 +1,7 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -cache: - - "C:\\msys64\\home\\cabal" +# cache: +# - "C:\\msys64\\home\\cabal" install: - set MSYSTEM=MINGW64 @@ -9,15 +9,16 @@ install: - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - bash -lc "mkdir -p /home/cabal" - - bash -lc "chmod -R 777 /home/cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal --config-file=/home/cabal update" - - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" + - cabal update -v + - cabal install -j --prefix=/usr/local alex happy + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" + - cd C:\msys64\mingw64\home\ghc\shake-build + - cabal install --only-dependencies build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:28:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot and configure from Hadrian. (dd4f887) Message-ID: <20171027002832.039FC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dd4f8871b08a1063dcd40770ca7a14caaca09c7a/ghc >--------------------------------------------------------------- commit dd4f8871b08a1063dcd40770ca7a14caaca09c7a Author: Andrey Mokhov Date: Thu May 5 00:43:42 2016 +0100 Run boot and configure from Hadrian. See #234. >--------------------------------------------------------------- dd4f8871b08a1063dcd40770ca7a14caaca09c7a .travis.yml | 5 +---- appveyor.yml | 5 +---- 2 files changed, 2 insertions(+), 8 deletions(-) diff --git a/.travis.yml b/.travis.yml index 2b2e7f5..7d5b699 100644 --- a/.travis.yml +++ b/.travis.yml @@ -54,15 +54,12 @@ install: - ( cd ghc/hadrian && cabal install --only-dependencies ) - ( cd ghc/hadrian && cabal configure ) - - ( cd ghc && ./boot ) - - ( cd ghc && ./configure ) - - cat ghc/hadrian/cfg/system.config - ghc-pkg list script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --skip-configure --no-progress --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --no-progress --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index 0bcf7d7..bb78b80 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -31,13 +31,10 @@ install: - stack exec -- ghc-pkg list - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3be330a3ff24cf3ead50323e104c217e32f4285/ghc >--------------------------------------------------------------- commit e3be330a3ff24cf3ead50323e104c217e32f4285 Author: Andrey Mokhov Date: Sun Nov 27 14:34:52 2016 +0000 Simplify handling of non-Cabal contexts >--------------------------------------------------------------- e3be330a3ff24cf3ead50323e104c217e32f4285 src/Expression.hs | 12 +----------- src/GHC.hs | 9 ++++++++- src/Rules/Data.hs | 12 ++---------- src/Rules/Libffi.hs | 1 - src/Settings/Builders/Ghc.hs | 7 ++++--- src/Settings/Packages/GhcCabal.hs | 4 ---- src/Settings/Packages/Hp2ps.hs | 9 ++------- src/Settings/Packages/Touchy.hs | 9 ++------- src/Settings/Packages/Unlit.hs | 9 ++------- 9 files changed, 21 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 e3be330a3ff24cf3ead50323e104c217e32f4285 From git at git.haskell.org Fri Oct 27 00:28:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run cabal in -v3 mode to reveal the problem. (accce20) Message-ID: <20171027002834.23EB93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/accce2015d2e61fd949885866f014026a4a69049/ghc >--------------------------------------------------------------- commit accce2015d2e61fd949885866f014026a4a69049 Author: Andrey Mokhov Date: Wed Jan 6 23:36:07 2016 +0000 Run cabal in -v3 mode to reveal the problem. See #110. [skip ci] >--------------------------------------------------------------- accce2015d2e61fd949885866f014026a4a69049 .appveyor.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index d8bb09d..0b90efa 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -8,12 +8,11 @@ install: - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /home/cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - cabal update -v + - cabal update -v3 - cabal install -j --prefix=/usr/local alex happy - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" From git at git.haskell.org Fri Oct 27 00:28:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop --setup, add --skip-configure. (7cb590a) Message-ID: <20171027002835.7E1A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7cb590a6ede9ccfe521e31a116767f46503945c8/ghc >--------------------------------------------------------------- commit 7cb590a6ede9ccfe521e31a116767f46503945c8 Author: Andrey Mokhov Date: Thu May 5 01:37:48 2016 +0100 Drop --setup, add --skip-configure. See #234. [skip ci] >--------------------------------------------------------------- 7cb590a6ede9ccfe521e31a116767f46503945c8 README.md | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/README.md b/README.md index d4adfb1..e0053b0 100644 --- a/README.md +++ b/README.md @@ -32,8 +32,6 @@ system to be in the `hadrian` directory of the GHC source tree: git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/hadrian - ./boot - ./configure # On Windows run ./configure --enable-tarballs-autodownload ``` * Build GHC using `hadrian/build.sh` or `hadrian/build.bat` (on Windows) instead @@ -45,7 +43,7 @@ see [instructions for building GHC on Windows using Stack][windows-build]. Using the build system ---------------------- Once your first build is successful, simply run `build` to rebuild. Most build artefacts -are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue]). +are placed into `_build` and `inplace` directories ([#113][build-artefacts-issue]). #### Command line flags @@ -58,13 +56,17 @@ profiling, which speeds up builds by 3-4x). * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). -* `--setup[=CONFIGURE_ARGS]`: setup the build system by running the `configure` script -with `CONFIGURE_ARGS` arguments; also run the `boot` script to create the `configure` -script if necessary. On Windows, download the required tarballs by executing -`mk/get-win32-tarballs.sh` with appropriate parameters. You do not have to -use this functionality of the new build system; feel free to run `boot` and `configure` -scripts manually, as you do when using `make`. Beware: `--setup` uses network I/O -which may sometimes be undesirable. +* `--skip-configure`: use this flag to suppress the default behaviour of Hadrian that +runs the `boot` and `configure` scripts automatically if need be, so that you don't have +to remember to run them manually. With `--skip-configure` you will need to manually run: + + ```bash + ./boot + ./configure # On Windows run ./configure --enable-tarballs-autodownload + ``` +as you normally do when using `make`. Beware, by default Hadrian may do network I/O on +Windows to download necessary tarballs, which may sometimes be undesirable; `--skip-configure` +is your friend in such cases. * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. From git at git.haskell.org Fri Oct 27 00:28:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify handling of programs with no Haskell main (e2761b2) Message-ID: <20171027002837.D03803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2761b27d9c01828650a48e854ce1f3980dc29b4/ghc >--------------------------------------------------------------- commit e2761b27d9c01828650a48e854ce1f3980dc29b4 Author: Andrey Mokhov Date: Sun Nov 27 15:36:50 2016 +0000 Simplify handling of programs with no Haskell main >--------------------------------------------------------------- e2761b27d9c01828650a48e854ce1f3980dc29b4 hadrian.cabal | 4 ---- src/GHC.hs | 7 ++++++- src/Settings/Builders/Ghc.hs | 4 +++- src/Settings/Default.hs | 10 +--------- src/Settings/Packages/Ghc.hs | 7 ++----- src/Settings/Packages/Hp2ps.hs | 9 --------- src/Settings/Packages/IservBin.hs | 7 ------- src/Settings/Packages/Touchy.hs | 9 --------- src/Settings/Packages/Unlit.hs | 9 --------- 9 files changed, 12 insertions(+), 54 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 0663643..30ed256 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -94,13 +94,9 @@ executable hadrian , Settings.Packages.GhcCabal , Settings.Packages.GhcPrim , Settings.Packages.Haddock - , Settings.Packages.Hp2ps , Settings.Packages.IntegerGmp - , Settings.Packages.IservBin , Settings.Packages.Rts , Settings.Packages.RunGhc - , Settings.Packages.Touchy - , Settings.Packages.Unlit , Settings.Path , Stage , Target diff --git a/src/GHC.hs b/src/GHC.hs index 9111d64..4521679 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -9,7 +9,8 @@ module GHC ( parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, builderProvenance, programName, nonCabalContext + defaultKnownPackages, builderProvenance, programName, nonCabalContext, + nonHsMainPackage ) where import Builder @@ -130,3 +131,7 @@ programName Context {..} nonCabalContext :: Context -> Bool nonCabalContext Context {..} = (package `elem` [hp2ps, rts, touchy, unlit]) || package == ghcCabal && stage == Stage0 + +-- | Some program packages should not be linked with Haskell main function. +nonHsMainPackage :: Package -> Bool +nonHsMainPackage = (`elem` [ghc, hp2ps, iservBin, touchy, unlit]) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 0c4c569..f5b13e1 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -22,6 +22,7 @@ ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do ghcLinkArgs :: Args ghcLinkArgs = builder (Ghc LinkHs) ? do stage <- getStage + pkg <- getPackage libs <- getPkgDataList DepExtraLibs libDirs <- getPkgDataList DepLibDirs gmpLibs <- if stage > Stage0 @@ -31,6 +32,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do return $ concatMap (words . strip) buildInfo else return [] mconcat [ arg "-no-auto-link-packages" + , nonHsMainPackage pkg ? arg "-no-hs-main" , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] @@ -75,7 +77,7 @@ commonGhcArgs = do , arg "-odir" , arg path , arg "-hidir" , arg path , arg "-stubdir" , arg path - , arg "-rtsopts" ] -- TODO: ifeq "$(HC_VERSION_GE_6_13)" "YES" + , (not . nonHsMainPackage) <$> getPackage ? arg "-rtsopts" ] -- TODO: Do '-ticky' in all debug ways? wayGhcArgs :: Args diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index c863a9e..6f56c5d 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -34,13 +34,9 @@ import Settings.Packages.Ghc import Settings.Packages.GhcCabal import Settings.Packages.GhcPrim import Settings.Packages.Haddock -import Settings.Packages.Hp2ps import Settings.Packages.IntegerGmp -import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc -import Settings.Packages.Touchy -import Settings.Packages.Unlit import UserSettings -- | All default command line arguments. @@ -203,10 +199,6 @@ defaultPackageArgs = mconcat , ghcCabalPackageArgs , ghcPrimPackageArgs , haddockPackageArgs - , hp2psPackageArgs , integerGmpPackageArgs - , iservBinPackageArgs , rtsPackageArgs - , runGhcPackageArgs - , touchyPackageArgs - , unlitPackageArgs ] + , runGhcPackageArgs ] diff --git a/src/Settings/Packages/Ghc.hs b/src/Settings/Packages/Ghc.hs index b069c23..a95bda6 100644 --- a/src/Settings/Packages/Ghc.hs +++ b/src/Settings/Packages/Ghc.hs @@ -8,10 +8,7 @@ import Settings.Path ghcPackageArgs :: Args ghcPackageArgs = package ghc ? do stage <- getStage - mconcat [ builder Ghc ? mconcat - [ arg $ "-I" ++ buildPath (vanillaContext stage compiler) - , arg "-no-hs-main" ] + mconcat [ builder Ghc ? arg ("-I" ++ buildPath (vanillaContext stage compiler)) , builder GhcCabal ? - ghcWithInterpreter ? notStage0 ? arg "--flags=ghci" - ] + ghcWithInterpreter ? notStage0 ? arg "--flags=ghci" ] diff --git a/src/Settings/Packages/Hp2ps.hs b/src/Settings/Packages/Hp2ps.hs deleted file mode 100644 index a5c62c2..0000000 --- a/src/Settings/Packages/Hp2ps.hs +++ /dev/null @@ -1,9 +0,0 @@ -module Settings.Packages.Hp2ps (hp2psPackageArgs) where - -import GHC -import Predicate - -hp2psPackageArgs :: Args -hp2psPackageArgs = package hp2ps ? - builder Ghc ? mconcat [ arg "-no-hs-main" - , remove ["-hide-all-packages"] ] diff --git a/src/Settings/Packages/IservBin.hs b/src/Settings/Packages/IservBin.hs deleted file mode 100644 index 40b2101..0000000 --- a/src/Settings/Packages/IservBin.hs +++ /dev/null @@ -1,7 +0,0 @@ -module Settings.Packages.IservBin (iservBinPackageArgs) where - -import GHC -import Predicate - -iservBinPackageArgs :: Args -iservBinPackageArgs = package iservBin ? builder Ghc ? arg "-no-hs-main" diff --git a/src/Settings/Packages/Touchy.hs b/src/Settings/Packages/Touchy.hs deleted file mode 100644 index 7c2e04c..0000000 --- a/src/Settings/Packages/Touchy.hs +++ /dev/null @@ -1,9 +0,0 @@ -module Settings.Packages.Touchy (touchyPackageArgs) where - -import GHC -import Predicate - -touchyPackageArgs :: Args -touchyPackageArgs = package touchy ? - builder Ghc ? mconcat [ arg "-no-hs-main" - , remove ["-hide-all-packages"] ] diff --git a/src/Settings/Packages/Unlit.hs b/src/Settings/Packages/Unlit.hs deleted file mode 100644 index a959699..0000000 --- a/src/Settings/Packages/Unlit.hs +++ /dev/null @@ -1,9 +0,0 @@ -module Settings.Packages.Unlit (unlitPackageArgs) where - -import GHC -import Predicate - -unlitPackageArgs :: Args -unlitPackageArgs = package unlit ? - builder Ghc ? mconcat [ arg "-no-hs-main" - , remove ["-hide-all-packages"] ] From git at git.haskell.org Fri Oct 27 00:28:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run cabal in -v3 mode in bash. (351c39f) Message-ID: <20171027002838.4FEB83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/351c39f38b709a6304e8085cae52fe90d23a2cd9/ghc >--------------------------------------------------------------- commit 351c39f38b709a6304e8085cae52fe90d23a2cd9 Author: Andrey Mokhov Date: Wed Jan 6 23:56:24 2016 +0000 Run cabal in -v3 mode in bash. See #110. [skip ci] >--------------------------------------------------------------- 351c39f38b709a6304e8085cae52fe90d23a2cd9 .appveyor.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 0b90efa..19236d4 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -12,12 +12,12 @@ install: - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - cabal update -v3 - - cabal install -j --prefix=/usr/local alex happy + - bash -lc "cabal update -v3" + - bash -lc "cabal install -j --prefix=/usr/local alex happy" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\mingw64\home\ghc\shake-build - - cabal install --only-dependencies + - bash -lc "cd /home/ghc/shake-build && cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:28:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify ghcCabalPackageArgs (4e80495) Message-ID: <20171027002841.7592A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e8049531d734957c1c71fdbe3f18a52db2e2f2d/ghc >--------------------------------------------------------------- commit 4e8049531d734957c1c71fdbe3f18a52db2e2f2d Author: Andrey Mokhov Date: Sun Nov 27 15:56:22 2016 +0000 Simplify ghcCabalPackageArgs >--------------------------------------------------------------- 4e8049531d734957c1c71fdbe3f18a52db2e2f2d src/Settings/Packages/GhcCabal.hs | 21 ++++++--------------- 1 file changed, 6 insertions(+), 15 deletions(-) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index f41053f..8e5837c 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -6,21 +6,12 @@ import Oracles.Config.Setting import Predicate ghcCabalPackageArgs :: Args -ghcCabalPackageArgs = package ghcCabal ? - builder Ghc ? mconcat [ ghcCabalBootArgs - , remove ["-no-auto-link-packages"] ] - --- TODO: do we need -DCABAL_VERSION=$(CABAL_VERSION)? -ghcCabalBootArgs :: Args -ghcCabalBootArgs = stage0 ? do - -- Note: We could have computed 'cabalDeps' instead of hard-coding it - -- but this doesn't worth the effort, since we plan to drop ghc-cabal - -- altogether at some point. See #18. - cabalDeps <- fromDiffExpr $ mconcat - [ append [ array, base, bytestring, containers, deepseq, directory - , pretty, process, time ] - , notM windowsHost ? append [unix] - , windowsHost ? append [win32] ] +ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do + -- Note: We could compute 'cabalDeps' instead of hard-coding it but this + -- seems unnecessary since we plan to drop @ghc-cabal@ altogether, #18. + win <- lift windowsHost + let cabalDeps = [ array, base, bytestring, containers, deepseq, directory + , pretty, process, time, if win then win32 else unix ] mconcat [ append [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , arg "--make" From git at git.haskell.org Fri Oct 27 00:28:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Call GMP's configure in gmpBuildPath. (a228b96) Message-ID: <20171027002839.1940C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a228b96c3ab519968384ff1a5f88353225ff3544/ghc >--------------------------------------------------------------- commit a228b96c3ab519968384ff1a5f88353225ff3544 Author: Andrey Mokhov Date: Thu May 5 03:01:40 2016 +0100 Call GMP's configure in gmpBuildPath. >--------------------------------------------------------------- a228b96c3ab519968384ff1a5f88353225ff3544 src/Rules/Gmp.hs | 54 ++++++++++++++++++++------------------ src/Settings/Builders/Configure.hs | 2 +- 2 files changed, 30 insertions(+), 26 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1e962ec..cceda8e 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -52,8 +52,7 @@ gmpRules = do -- TODO: split into multiple rules gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - liftIO $ removeFiles gmpBuildPath ["//*"] - createDirectory $ takeDirectory gmpLibraryH + removeDirectoryIfExists gmpBuildPath -- We don't use system GMP on Windows. TODO: fix? windows <- windowsHost @@ -62,6 +61,7 @@ gmpRules = do [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" + createDirectory $ takeDirectory gmpLibraryH copyFile gmpLibraryFakeH gmpLibraryH else do putBuild "| No GMP library/framework detected; in tree GMP will be built" @@ -76,34 +76,38 @@ gmpRules = do ++ "(found: " ++ show tarballs ++ ")." need tarballs - build $ Target gmpContext Tar tarballs [gmpBuildPath] - - forM_ gmpPatches $ \src -> do - let patch = takeFileName src - patchPath = gmpBuildPath -/- patch - copyFile src patchPath - applyPatch gmpBuildPath patch - - let filename = dropExtension . dropExtension . takeFileName $ head tarballs - suffix = "-nodoc-patched" - unless (suffix `isSuffixOf` filename) $ - putError $ "gmpRules: expected suffix " ++ suffix - ++ " (found: " ++ filename ++ ")." - let libName = take (length filename - length suffix) filename - libPath = gmpBuildPath -/- "lib" - - moveDirectory (gmpBuildPath -/- libName) libPath + withTempDir $ \dir -> do + let tmp = unifyPath dir + build $ Target gmpContext Tar tarballs [tmp] + + forM_ gmpPatches $ \src -> do + let patch = takeFileName src + patchPath = tmp -/- patch + copyFile src patchPath + applyPatch tmp patch + + let filename = dropExtension . dropExtension . takeFileName + $ head tarballs + suffix = "-nodoc-patched" + unless (suffix `isSuffixOf` filename) $ + putError $ "gmpRules: expected suffix " ++ suffix + ++ " (found: " ++ filename ++ ")." + let libName = take (length filename - length suffix) filename + + moveDirectory (tmp -/- libName) gmpBuildPath env <- configureEnvironment buildWithCmdOptions env $ - Target gmpContext (Configure libPath) - [libPath -/- "Makefile.in"] [libPath -/- "Makefile"] + Target gmpContext (Configure gmpBuildPath) + [gmpBuildPath -/- "Makefile.in"] + [gmpBuildPath -/- "Makefile"] - runMake libPath ["MAKEFLAGS="] + runMake gmpBuildPath ["MAKEFLAGS="] - copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH - copyFile (libPath -/- "gmp.h") gmpLibraryH - moveFile (libPath -/- ".libs/libgmp.a") gmpLibrary + createDirectory $ takeDirectory gmpLibraryH + copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH + copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH + moveFile (gmpBuildPath -/- ".libs/libgmp.a") gmpLibrary createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 45bca37..813b79d 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -17,7 +17,7 @@ configureArgs = mconcat , arg $ "--enable-shared=no" -- TODO: add support for yes , arg $ "--host=" ++ targetPlatform ] - , builder (Configure $ gmpBuildPath -/- "lib") ? do + , builder (Configure gmpBuildPath) ? do hostPlatform <- getSetting HostPlatform buildPlatform <- getSetting BuildPlatform mconcat [ arg $ "--enable-shared=no" From git at git.haskell.org Fri Oct 27 00:28:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to use an older cabal version. (05b4a6e) Message-ID: <20171027002842.1CA413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/05b4a6e3c481e08317678edf8e5aa21e7f658271/ghc >--------------------------------------------------------------- commit 05b4a6e3c481e08317678edf8e5aa21e7f658271 Author: Andrey Mokhov Date: Thu Jan 7 01:01:32 2016 +0000 Try to use an older cabal version. See #110. [skip ci] >--------------------------------------------------------------- 05b4a6e3c481e08317678edf8e5aa21e7f658271 .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 19236d4..4d54924 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -10,8 +10,9 @@ install: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" + # - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" + # - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" + - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.20.0.3/cabal-1.20.0.3-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "cabal update -v3" - bash -lc "cabal install -j --prefix=/usr/local alex happy" - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\mingw64\home\ghc\tmp From git at git.haskell.org Fri Oct 27 00:32:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use colours on CI (5ca3853) Message-ID: <20171027003224.D71163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ca3853fd62d8dd8566b610a2e1534cf573e9e0d/ghc >--------------------------------------------------------------- commit 5ca3853fd62d8dd8566b610a2e1534cf573e9e0d Author: Andrey Mokhov Date: Wed May 18 02:57:50 2016 +0100 Don't use colours on CI See #244 >--------------------------------------------------------------- 5ca3853fd62d8dd8566b610a2e1534cf573e9e0d .travis.yml | 2 +- appveyor.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 7d5b699..4ec6721 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,7 +59,7 @@ install: script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --no-progress --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index bb78b80..09baa2e 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --profile=- --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:32:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add APPVEYOR_BUILD_FOLDER to PATH, show versions of key binaries. (782e998) Message-ID: <20171027003226.E1DC83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/782e99878b0a669aaa585b84531a089e68502f26/ghc >--------------------------------------------------------------- commit 782e99878b0a669aaa585b84531a089e68502f26 Author: Andrey Mokhov Date: Fri Jan 8 01:31:18 2016 +0000 Add APPVEYOR_BUILD_FOLDER to PATH, show versions of key binaries. See #110. [skip ci] >--------------------------------------------------------------- 782e99878b0a669aaa585b84531a089e68502f26 .appveyor.yml | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 5ad5f0b..136bee6 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -9,12 +9,16 @@ init: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\ + - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc install: - cd C:\msys64\home\ghc - - shake-build\stack.exe exec -- mk/get-win32-tarballs.sh download x86_64 + - stack exec -- mk/get-win32-tarballs.sh download x86_64 + - ghc --version + - stack --version + - alex --version + - happy --version build_script: - bash -lc "./boot" From git at git.haskell.org Fri Oct 27 00:32:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow cmm files in non-custom packages (5b9f6e9) Message-ID: <20171027003227.457E93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b9f6e901eb3613544aaf941d33419fb9f8368d0/ghc >--------------------------------------------------------------- commit 5b9f6e901eb3613544aaf941d33419fb9f8368d0 Author: Andrey Mokhov Date: Wed Apr 26 01:53:28 2017 +0100 Allow cmm files in non-custom packages >--------------------------------------------------------------- 5b9f6e901eb3613544aaf941d33419fb9f8368d0 src/Rules/Data.hs | 9 ++++++--- src/Rules/Library.hs | 21 ++++++++++++++------- 2 files changed, 20 insertions(+), 10 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index cff0896..0538f6c 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -102,13 +102,16 @@ packageCmmSources pkg -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$'. For example, get rid of -- @libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ...@ --- Reason: we don't need them and we can't parse them. +-- and replace it with a tracked call to getDirectoryFiles. -- 2) Drop path prefixes to individual settings. -- For example, @libraries/deepseq/dist-install_VERSION = 1.4.0.0@ -- is replaced by @VERSION = 1.4.0.0 at . -- Reason: Shake's built-in makefile parser doesn't recognise slashes postProcessPackageData :: Context -> FilePath -> Action () postProcessPackageData context at Context {..} file = do - top <- topDirectory + top <- topDirectory + cmmSrcs <- getDirectoryFiles (pkgPath package) ["cbits/*.cmm"] let len = length (pkgPath package) + length (top -/- buildPath context) + 2 - fixFile file $ unlines . map (drop len) . filter ('$' `notElem`) . lines + fixFile file $ unlines + . (++ ["CMM_SRCS = " ++ unwords (map unifyPath cmmSrcs) ]) + . map (drop len) . filter ('$' `notElem`) . lines diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 2deb6f9..32db232 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -23,12 +23,8 @@ buildPackageLibrary context at Context {..} = do -- TODO: handle dynamic libraries matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do removeFile a - asmObjs <- map (objectPath context) <$> pkgDataList (AsmSrcs path) - cObjs <- cObjects context - cmmObjs <- map (objectPath context) <$> pkgDataList (CmmSrcs path) - eObjs <- extraObjects context - hsObjs <- hsObjects context - let noHsObjs = asmObjs ++ cObjs ++ cmmObjs ++ eObjs + hsObjs <- hsObjects context + noHsObjs <- nonHsObjects context -- This will create split objects if required (we don't track them -- explicitly as this would needlessly bloat the Shake database). @@ -56,10 +52,21 @@ buildPackageGhciLibrary :: Context -> Rules () buildPackageGhciLibrary context at Context {..} = priority 2 $ do let libPrefix = buildPath context -/- "HS" ++ pkgNameString package matchVersionedFilePath libPrefix (waySuffix way <.> "o") ?> \obj -> do - objs <- concatMapM ($ context) [cObjects, hsObjects, extraObjects] + objs <- allObjects context need objs build $ Target context Ld objs [obj] +allObjects :: Context -> Action [FilePath] +allObjects context = (++) <$> nonHsObjects context <*> hsObjects context + +nonHsObjects :: Context -> Action [FilePath] +nonHsObjects context = do + let path = buildPath context + cObjs <- cObjects context + cmmObjs <- map (objectPath context) <$> pkgDataList (CmmSrcs path) + eObjs <- extraObjects context + return $ cObjs ++ cmmObjs ++ eObjs + cObjects :: Context -> Action [FilePath] cObjects context = do objs <- map (objectPath context) <$> pkgDataList (CSrcs $ buildPath context) From git at git.haskell.org Fri Oct 27 00:32:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run CI in verbose mode (dd3d592) Message-ID: <20171027003228.468283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dd3d592331fb12f33b117f098e0fb19b388e4eae/ghc >--------------------------------------------------------------- commit dd3d592331fb12f33b117f098e0fb19b388e4eae Author: Andrey Mokhov Date: Wed May 18 09:34:51 2016 +0100 Run CI in verbose mode >--------------------------------------------------------------- dd3d592331fb12f33b117f098e0fb19b388e4eae .travis.yml | 2 +- appveyor.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4ec6721..3b61256 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,7 +59,7 @@ install: script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index 09baa2e..bb5620e 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:32:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clone ghc into ghc/tmp. (2fd5c6e) Message-ID: <20171027003230.55A383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2fd5c6e03952155a73d39fbfe925606d8d99fbfe/ghc >--------------------------------------------------------------- commit 2fd5c6e03952155a73d39fbfe925606d8d99fbfe Author: Andrey Mokhov Date: Fri Jan 8 01:58:26 2016 +0000 Clone ghc into ghc/tmp. See #110. [skip ci] >--------------------------------------------------------------- 2fd5c6e03952155a73d39fbfe925606d8d99fbfe .appveyor.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 136bee6..ef66eb7 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -4,13 +4,14 @@ init: - cd - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% + - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc + - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" install: - cd C:\msys64\home\ghc From git at git.haskell.org Fri Oct 27 00:32:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop package self-dependencies (ff322d9) Message-ID: <20171027003230.C64073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff322d9a37a5c9a406e28eab703334737ae20cba/ghc >--------------------------------------------------------------- commit ff322d9a37a5c9a406e28eab703334737ae20cba Author: Andrey Mokhov Date: Thu Apr 27 00:20:42 2017 +0100 Drop package self-dependencies This occurs in iserv-bin package, which contains both a library and an executable. See #12 >--------------------------------------------------------------- ff322d9a37a5c9a406e28eab703334737ae20cba src/Rules/Cabal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index b45af42..ad1312f 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -42,7 +42,7 @@ cabalRules = do depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes depNames = [ unPackageName name | Dependency name _ <- deps ] - return . unwords $ pkgNameString pkg : sort depNames + return . unwords $ pkgNameString pkg : (sort depNames \\ [pkgNameString pkg]) writeFileChanged out $ unlines pkgDeps putSuccess $ "| Successfully computed package dependencies" From git at git.haskell.org Fri Oct 27 00:32:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify include and link paths (13b80f7) Message-ID: <20171027003231.BE1F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13b80f771aac9e9d4a5363632c474261914d5e18/ghc >--------------------------------------------------------------- commit 13b80f771aac9e9d4a5363632c474261914d5e18 Author: Andrey Mokhov Date: Thu May 19 00:45:14 2016 +0100 Unify include and link paths >--------------------------------------------------------------- 13b80f771aac9e9d4a5363632c474261914d5e18 src/Settings/Builders/Common.hs | 2 +- src/Settings/Builders/Ghc.hs | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 3f53dec..252667f 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -25,7 +25,7 @@ cIncludeArgs = do mconcat [ arg $ "-I" ++ path , arg $ "-I" ++ path -/- "autogen" , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] - , append [ "-I" ++ dir | dir <- depDirs ] ] + , append [ "-I" ++ unifyPath dir | dir <- depDirs ] ] ldArgs :: Args ldArgs = mempty diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 66c009b..2199874 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -44,8 +44,8 @@ ghcLinkArgs = builder (Ghc Link) ? do else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ arg "-no-auto-link-packages" - , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] - , append [ "-optl-L" ++ dir | dir <- libDirs ] ] + , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] + , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] -- TODO: Add Touchy builder and use needBuilder. needTouchy :: ReaderT Target Action () From git at git.haskell.org Fri Oct 27 00:32:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:32:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop init script. (cd567f7) Message-ID: <20171027003234.009C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cd567f71ec9ba2b0eb0b3232b4b375df23557354/ghc >--------------------------------------------------------------- commit cd567f71ec9ba2b0eb0b3232b4b375df23557354 Author: Andrey Mokhov Date: Fri Jan 8 02:22:05 2016 +0000 Drop init script. See #110. [skip ci] >--------------------------------------------------------------- cd567f71ec9ba2b0eb0b3232b4b375df23557354 .appveyor.yml | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index ef66eb7..f663d96 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,6 +1,6 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" -init: +install: - cd - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% @@ -12,9 +12,6 @@ init: - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp - bash -lc "mv /home/ghc/tmp/* /home/ghc" - -install: - - cd C:\msys64\home\ghc - stack exec -- mk/get-win32-tarballs.sh download x86_64 - ghc --version - stack --version From git at git.haskell.org Fri Oct 27 00:34:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (c9e7570) Message-ID: <20171027003436.DAFA83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9e7570bea7562ca05b6c1469759dfdf9e675e06/ghc >--------------------------------------------------------------- commit c9e7570bea7562ca05b6c1469759dfdf9e675e06 Author: Andrey Mokhov Date: Sat Jun 4 21:56:12 2016 +0100 Minor revision >--------------------------------------------------------------- c9e7570bea7562ca05b6c1469759dfdf9e675e06 src/Settings/Builders/Make.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index afb46d7..7283b4b 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -7,8 +7,8 @@ import Settings makeBuilderArgs :: Args makeBuilderArgs = do threads <- shakeThreads <$> lift getShakeOptions - let j = "-j" ++ show threads + let t = show threads mconcat - [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=" ++ j] - , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=" ++ j, "install"] - , builder (Make "testsuite/tests") ? append ["THREADS=" ++ show threads, "fast"] ] + [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=-j" ++ t] + , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=-j" ++ t, "install"] + , builder (Make "testsuite/tests") ? append ["THREADS=" ++ t, "fast"] ] From git at git.haskell.org Fri Oct 27 00:34:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CircleCI badge (1400b14) Message-ID: <20171027003437.450213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1400b148157e781c55165bfaf4d706477f3d36be/ghc >--------------------------------------------------------------- commit 1400b148157e781c55165bfaf4d706477f3d36be Author: Andrey Mokhov Date: Mon Jul 17 19:12:04 2017 +0100 Add CircleCI badge [skip ci] >--------------------------------------------------------------- 1400b148157e781c55165bfaf4d706477f3d36be README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index d65b98c..3e5318a 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Hadrian ======= -[![Linux & OS X status](https://img.shields.io/travis/snowleopard/hadrian/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/hadrian) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/hadrian/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/hadrian) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) [![OS X status](https://img.shields.io/circleci/project/github/snowleopard/hadrian.svg?label=OS%20X)](https://circleci.com/gh/snowleopard/hadrian) Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current From git at git.haskell.org Fri Oct 27 00:34:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (2nd try). (901105e) Message-ID: <20171027003437.6660E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/901105e56574df051615b59db337bb7ec856ef9a/ghc >--------------------------------------------------------------- commit 901105e56574df051615b59db337bb7ec856ef9a Author: Andrey Mokhov Date: Sat Jan 9 17:06:20 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (2nd try). See #110. [skip ci] >--------------------------------------------------------------- 901105e56574df051615b59db337bb7ec856ef9a .appveyor.yml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 9cb8bcb..e382140 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,6 +23,8 @@ install: - happy --version build_script: - - unset GHC_PACKAGE_PATH + - set GHC_PACKAGE_PATH + - set GHC_PACKAGE_PATH= + - set GHC_PACKAGE_PATH - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat -j --no-progress From git at git.haskell.org Fri Oct 27 00:34:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up switching from Settings.User to UserSettings (39f0509) Message-ID: <20171027003440.E6D243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39f05090304de772238002ed16ff6a2b8023201d/ghc >--------------------------------------------------------------- commit 39f05090304de772238002ed16ff6a2b8023201d Author: Andrey Mokhov Date: Sat Jun 4 23:40:52 2016 +0100 Clean up switching from Settings.User to UserSettings >--------------------------------------------------------------- 39f05090304de772238002ed16ff6a2b8023201d cfg/system.config.in | 6 +++--- hadrian.cabal | 2 +- src/GHC.hs | 2 +- src/Oracles/PackageDatabase.hs | 2 +- src/Rules/Clean.hs | 2 +- src/Rules/Configure.hs | 2 +- src/Rules/Generators/Common.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Selftest.hs | 2 +- src/Rules/Test.hs | 2 +- src/Settings.hs | 4 ++-- src/Settings/Args.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/Paths.hs | 2 +- src/Settings/User.hs | 12 ------------ src/Settings/Ways.hs | 2 +- src/UserSettings.hs | 10 +++++----- 18 files changed, 25 insertions(+), 37 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 39f05090304de772238002ed16ff6a2b8023201d From git at git.haskell.org Fri Oct 27 00:34:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on ghc-split only when building with split objects. (9580d01) Message-ID: <20171027003441.1BC383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9580d01895bb231dd38f8000eb7ad1929ee75962/ghc >--------------------------------------------------------------- commit 9580d01895bb231dd38f8000eb7ad1929ee75962 Author: Andrey Mokhov Date: Sat Jan 9 17:09:03 2016 +0000 Depend on ghc-split only when building with split objects. See #81. [skip ci] >--------------------------------------------------------------- 9580d01895bb231dd38f8000eb7ad1929ee75962 src/Rules/Generate.hs | 7 ++++--- src/Settings/Builders/Ghc.hs | 7 ++++++- 2 files changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 2b2962b..b7a360a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -42,8 +42,10 @@ includesDependencies = ("includes" -/-) <$> , "ghcversion.h" ] defaultDependencies :: [FilePath] -defaultDependencies = - includesDependencies ++ libffiDependencies ++ integerGmpDependencies +defaultDependencies = concat + [ includesDependencies + , libffiDependencies + , integerGmpDependencies ] ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> @@ -77,7 +79,6 @@ compilerDependencies stage = , "primop-vector-tys-exports.hs-incl" , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] - ++ ["inplace/lib/bin/ghc-split"] generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 9a07fc2..bc37a04 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -26,7 +26,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , notStage0 ? arg "-O2" , arg "-Wall" , arg "-fwarn-tabs" - , splitObjects ? arg "-split-objs" + , splitObjectsArgs , not buildObj ? arg "-no-auto-link-packages" , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ] , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] @@ -34,6 +34,11 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , append =<< getInputs , arg "-o", arg =<< getOutput ] +splitObjectsArgs :: Args +splitObjectsArgs = splitObjects ? do + lift $ need ["inplace/lib/bin/ghc-split"] + arg "-split-objs" + ghcMBuilderArgs :: Args ghcMBuilderArgs = stagedBuilder GhcM ? do ways <- getWays From git at git.haskell.org Fri Oct 27 00:34:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #260 from hvr/pr/unify-cabal-script (24d6d50) Message-ID: <20171027003444.728223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/24d6d50c5d605aa32cfc5efcd2328480597cfda4/ghc >--------------------------------------------------------------- commit 24d6d50c5d605aa32cfc5efcd2328480597cfda4 Merge: 39f0509 af6a040 Author: Andrey Mokhov Date: Sat Jun 4 23:41:34 2016 +0100 Merge pull request #260 from hvr/pr/unify-cabal-script Merge build.cabal-new.sh into build.cabal.sh >--------------------------------------------------------------- 24d6d50c5d605aa32cfc5efcd2328480597cfda4 build.cabal-new.sh | 58 ------------------------------------------------------ build.cabal.sh | 50 +++++++++++++++++++++++++++++++++++----------- build.sh | 9 +++++++++ 3 files changed, 48 insertions(+), 69 deletions(-) From git at git.haskell.org Fri Oct 27 00:34:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Untrack copied artifacts (#365) (6395cf5) Message-ID: <20171027003441.6005E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6395cf549921934602563cfae645e6707b171fac/ghc >--------------------------------------------------------------- commit 6395cf549921934602563cfae645e6707b171fac Author: Zhen Zhang Date: Tue Jul 18 05:26:00 2017 +0800 Untrack copied artifacts (#365) >--------------------------------------------------------------- 6395cf549921934602563cfae645e6707b171fac src/Rules/Install.hs | 13 ++++--------- 1 file changed, 4 insertions(+), 9 deletions(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 57cf008..058e160 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -194,22 +194,17 @@ installPackages = do need [ ghcCabalInplace ] let cabalFile = pkgCabalFile pkg - -- HsColour sources - -- QUESTION: what is the output of GhcCabalHsColour? - whenM (isSpecified HsColour) $ do - top <- interpretInContext context getTopDirectory - let installDistDir = top -/- buildPath context - -- HACK: copy stuff back to the place favored by ghc-cabal - quietly $ copyDirectoryContents (Not excluded) - installDistDir (installDistDir -/- "build") pkgConf <- pkgConfFile context need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf - build $ Target context GhcCabalHsColour [cabalFile] [] -- HACK (#318): copy stuff back to the place favored by ghc-cabal quietly $ copyDirectoryContents (Not excluded) installDistDir (installDistDir -/- "build") + + whenM (isSpecified HsColour) $ + build $ Target context GhcCabalHsColour [cabalFile] [] + pref <- setting InstallPrefix unit $ cmd ghcCabalInplace [ "copy" From git at git.haskell.org Fri Oct 27 00:34:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (3rd try). (de13770) Message-ID: <20171027003444.E08043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de13770f7941733a8af2fbd6daeef6fb916b6a11/ghc >--------------------------------------------------------------- commit de13770f7941733a8af2fbd6daeef6fb916b6a11 Author: Andrey Mokhov Date: Sat Jan 9 18:07:22 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (3rd try). See #110. [skip ci] >--------------------------------------------------------------- de13770f7941733a8af2fbd6daeef6fb916b6a11 .appveyor.yml | 3 --- build.bat | 3 +++ 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index e382140..16de309 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -23,8 +23,5 @@ install: - happy --version build_script: - - set GHC_PACKAGE_PATH - - set GHC_PACKAGE_PATH= - - set GHC_PACKAGE_PATH - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat -j --no-progress diff --git a/build.bat b/build.bat index a4e2548..4cbbc42 100644 --- a/build.bat +++ b/build.bat @@ -16,4 +16,7 @@ ".." ^ %* + at rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains + at if defined GHC_PACKAGE_PATH ( set GHC_PACKAGE_PATH ) + @ghc %ghcArgs% && .shake\build %shakeArgs% From git at git.haskell.org Fri Oct 27 00:34:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix on Windows install (0ca5f3a) Message-ID: <20171027003445.2B2803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ca5f3a8245b92f844e4e68ce511e92ff186bbdc/ghc >--------------------------------------------------------------- commit 0ca5f3a8245b92f844e4e68ce511e92ff186bbdc Author: Andrey Mokhov Date: Tue Jul 18 00:12:29 2017 +0100 Fix on Windows install See #345 >--------------------------------------------------------------- 0ca5f3a8245b92f844e4e68ce511e92ff186bbdc src/Oracles/DirectoryContents.hs | 7 +- src/Rules/Install.hs | 204 +++++++++++++++++++-------------------- src/Util.hs | 4 +- 3 files changed, 109 insertions(+), 106 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 0ca5f3a8245b92f844e4e68ce511e92ff186bbdc From git at git.haskell.org Fri Oct 27 00:34:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting (49c2df8) Message-ID: <20171027003448.7A1EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49c2df80afe3754b2c24fae8337d1e1f13e923c3/ghc >--------------------------------------------------------------- commit 49c2df80afe3754b2c24fae8337d1e1f13e923c3 Author: Andrey Mokhov Date: Wed Jun 8 01:20:03 2016 +0100 Fix formatting >--------------------------------------------------------------- 49c2df80afe3754b2c24fae8337d1e1f13e923c3 src/Rules/Library.hs | 18 ++++++++---------- 1 file changed, 8 insertions(+), 10 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index dd144d1..a45ef51 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -62,17 +62,15 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do let path = buildPath context libPrefix = path -/- "HS" ++ pkgNameString package - -- TODO: simplify handling of AutoApply.cmm matchVersionedFilePath libPrefix (waySuffix way <.> "o") ?> \obj -> do - cSrcs <- cSources context - hSrcs <- hSources context - - eObjs <- extraObjects context - let cObjs = map (objFile context) cSrcs - hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] - objs = cObjs ++ hObjs ++ eObjs - need objs - build $ Target context Ld objs [obj] + cSrcs <- cSources context + hSrcs <- hSources context + eObjs <- extraObjects context + let cObjs = map (objFile context) cSrcs + hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] + objs = cObjs ++ hObjs ++ eObjs + need objs + build $ Target context Ld objs [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. -- | Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' From git at git.haskell.org Fri Oct 27 00:34:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (4th try). (b183504) Message-ID: <20171027003449.4E8EB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b1835045bfffcbc23d170b7675bf4156bc02e215/ghc >--------------------------------------------------------------- commit b1835045bfffcbc23d170b7675bf4156bc02e215 Author: Andrey Mokhov Date: Sat Jan 9 18:15:23 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (4th try). See #110. [skip ci] >--------------------------------------------------------------- b1835045bfffcbc23d170b7675bf4156bc02e215 build.bat | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 4cbbc42..2901686 100644 --- a/build.bat +++ b/build.bat @@ -17,6 +17,6 @@ %* @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains - at if defined GHC_PACKAGE_PATH ( set GHC_PACKAGE_PATH ) + at set GHC_PACKAGE_PATH= @ghc %ghcArgs% && .shake\build %shakeArgs% From git at git.haskell.org Fri Oct 27 00:34:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghc-iserv wrapper (#367) (05b3ebe) Message-ID: <20171027003449.519223A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/05b3ebe6911890145c12bd8022b2cc11002de98c/ghc >--------------------------------------------------------------- commit 05b3ebe6911890145c12bd8022b2cc11002de98c Author: Zhen Zhang Date: Tue Jul 18 23:12:22 2017 +0800 Add ghc-iserv wrapper (#367) >--------------------------------------------------------------- 05b3ebe6911890145c12bd8022b2cc11002de98c src/GHC.hs | 9 +++++---- src/Rules/Program.hs | 26 +++++++++++++++++++++++++- src/Rules/Wrappers.hs | 24 ++++++++++++++++++++++-- src/Settings.hs | 2 +- src/Settings/Path.hs | 13 +++++++------ 5 files changed, 60 insertions(+), 14 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0f5e2fb..ce88cb0 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -116,10 +116,11 @@ builderProvenance = \case -- 'Library', the function simply returns its name. programName :: Context -> String programName Context {..} - | package == ghc = "ghc-stage" ++ show (fromEnum stage + 1) - | package == hpcBin = "hpc" - | package == runGhc = "runhaskell" - | otherwise = pkgNameString package + | package == ghc = "ghc-stage" ++ show (fromEnum stage + 1) + | package == hpcBin = "hpc" + | package == runGhc = "runhaskell" + | package == iservBin = "ghc-iserv" + | otherwise = pkgNameString package -- | Some contexts are special: their packages do have @.cabal@ metadata or -- we cannot run @ghc-cabal@ on them, e.g. because the latter hasn't been built diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 12e661b..8c9a7ab 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -34,11 +34,35 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do inplaceBinPath -/- programName context <.> exe %> \bin -> do binStage <- installStage buildBinaryAndWrapper rs (context { stage = binStage }) bin - -- We build only unwrapped binaries in inplace/lib/bin + inplaceLibBinPath -/- programName context <.> exe %> \bin -> do binStage <- installStage + if package /= iservBin then + -- We *normally* build only unwrapped binaries in inplace/lib/bin, + buildBinary rs (context { stage = binStage }) bin + else + -- build both binary and wrapper in inplace/lib/bin + -- for ghc-iserv on *nix platform now + buildBinaryAndWrapperLib rs (context { stage = binStage }) bin + + inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> do + binStage <- installStage buildBinary rs (context { stage = binStage }) bin +buildBinaryAndWrapperLib :: [(Resource, Int)] -> Context -> FilePath -> Action () +buildBinaryAndWrapperLib rs context bin = do + windows <- windowsHost + if windows + then buildBinary rs context bin -- We don't build wrappers on Windows + else case lookup context inplaceWrappers of + Nothing -> buildBinary rs context bin -- No wrapper found + Just wrapper -> do + top <- topDirectory + let libdir = top -/- inplaceLibPath + let wrappedBin = inplaceLibBinPath -/- programName context <.> "bin" + need [wrappedBin] + buildWrapper context wrapper bin (WrappedBinary libdir (takeFileName wrappedBin)) + buildBinaryAndWrapper :: [(Resource, Int)] -> Context -> FilePath -> Action () buildBinaryAndWrapper rs context bin = do windows <- windowsHost diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs index 6adf3f7..7d90067 100644 --- a/src/Rules/Wrappers.hs +++ b/src/Rules/Wrappers.hs @@ -5,8 +5,9 @@ module Rules.Wrappers ( import Base import Expression import GHC +import Settings (getPackages, latestBuildStage) import Settings.Install (installPackageDbDirectory) -import Settings.Path (inplacePackageDbDirectory) +import Settings.Path (buildPath, inplacePackageDbDirectory) import Oracles.Path (getTopDirectory, bashPath) import Oracles.Config.Setting (SettingList(..), settingList) @@ -117,13 +118,32 @@ haddockWrapper WrappedBinary{..} = do , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " -B" ++ binaryLibPath ++ " -l" ++ binaryLibPath ++ " ${1+\"$@\"}" ] +iservBinWrapper :: WrappedBinary -> Expr String +iservBinWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + activePackages <- filter isLibrary <$> getPackages + -- TODO: Figure our the reason of this hardcoded exclusion + let pkgs = activePackages \\ [ cabal, process, haskeline + , terminfo, ghcCompact, hpc, compiler ] + contexts <- catMaybes <$> mapM (\p -> do + m <- lift $ latestBuildStage p + return $ fmap (\s -> vanillaContext s p) m + ) pkgs + let buildPaths = map buildPath contexts + return $ unlines + [ "#!/bin/bash" + , "export DYLD_LIBRARY_PATH=\"" ++ intercalate ":" buildPaths ++ + "${DYLD_LIBRARY_PATH:+:$DYLD_LIBRARY_PATH}\"" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ] + wrappersCommon :: [(Context, Wrapper)] wrappersCommon = [ (vanillaContext Stage0 ghc , ghcWrapper) , (vanillaContext Stage1 ghc , ghcWrapper) , (vanillaContext Stage1 hp2ps , hp2psWrapper) , (vanillaContext Stage1 hpc , hpcWrapper) , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) - , (vanillaContext Stage2 haddock, haddockWrapper)] + , (vanillaContext Stage2 haddock, haddockWrapper) + , (vanillaContext Stage1 iservBin, iservBinWrapper) ] -- | List of wrappers for inplace artefacts inplaceWrappers :: [(Context, Wrapper)] diff --git a/src/Settings.hs b/src/Settings.hs index 8152a6e..2f75095 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -112,7 +112,7 @@ programPath context at Context {..} = do maybeLatest <- latestBuildStage package return $ do install <- (\l -> l == stage || package == ghc) <$> maybeLatest - let path = if install then installPath package else buildPath context + let path = if install then inplaceInstallPath package else buildPath context return $ path -/- programName context <.> exe pkgConfInstallPath :: FilePath diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 8814620..1b0dc13 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -5,7 +5,7 @@ module Settings.Path ( rtsContext, rtsBuildPath, rtsConfIn, shakeFilesPath,inplacePackageDbDirectory, pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, - installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, + inplaceInstallPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, pkgSetupConfigFile ) where @@ -190,11 +190,12 @@ objectPath context at Context {..} src -- | Given a 'Package', return the path where the corresponding program is -- installed. Most programs are installed in 'programInplacePath'. -installPath :: Package -> FilePath -installPath pkg - | pkg == touchy = inplaceLibBinPath - | pkg == unlit = inplaceLibBinPath - | otherwise = inplaceBinPath +inplaceInstallPath :: Package -> FilePath +inplaceInstallPath pkg + | pkg == touchy = inplaceLibBinPath + | pkg == unlit = inplaceLibBinPath + | pkg == iservBin = inplaceLibBinPath + | otherwise = inplaceBinPath -- | @ghc-split@ is a Perl script used by GHC with @-split-objs@ flag. It is -- generated in "Rules.Generators.GhcSplit". From git at git.haskell.org Fri Oct 27 00:34:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set dynamicGhcPrograms = False (85b4b52) Message-ID: <20171027003452.5339B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/85b4b524df1734d0a96c7a5ac66724c0c61cce28/ghc >--------------------------------------------------------------- commit 85b4b524df1734d0a96c7a5ac66724c0c61cce28 Author: Andrey Mokhov Date: Wed Jun 8 01:20:47 2016 +0100 Set dynamicGhcPrograms = False See #259. >--------------------------------------------------------------- 85b4b524df1734d0a96c7a5ac66724c0c61cce28 src/UserSettings.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 908d96d..588f196 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -78,7 +78,7 @@ buildHaddock = return cmdBuildHaddock -- TODO: Do we need to be able to set these from command line? -- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? dynamicGhcPrograms :: Bool -dynamicGhcPrograms = True +dynamicGhcPrograms = False ghciWithDebugger :: Bool ghciWithDebugger = False From git at git.haskell.org Fri Oct 27 00:34:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix typo in comment (#369) (408ef4e) Message-ID: <20171027003452.DC2FE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/408ef4e802ec0b89b5962bb839f11f47976897e2/ghc >--------------------------------------------------------------- commit 408ef4e802ec0b89b5962bb839f11f47976897e2 Author: Doug Wilson Date: Wed Jul 19 06:57:15 2017 +1200 Fix typo in comment (#369) [skip ci] >--------------------------------------------------------------- 408ef4e802ec0b89b5962bb839f11f47976897e2 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index ce88cb0..231eab6 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -122,7 +122,7 @@ programName Context {..} | package == iservBin = "ghc-iserv" | otherwise = pkgNameString package --- | Some contexts are special: their packages do have @.cabal@ metadata or +-- | Some contexts are special: their packages do not have @.cabal@ metadata or -- we cannot run @ghc-cabal@ on them, e.g. because the latter hasn't been built -- yet (this is the case with the 'ghcCabal' package in 'Stage0'). nonCabalContext :: Context -> Bool From git at git.haskell.org Fri Oct 27 00:34:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reset GHC_PACKAGE_PATH varialbe (5th try). (9ba5daa) Message-ID: <20171027003452.F362B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9ba5daa863d59d5b2a7bd8fabdd9caa0b8fe4521/ghc >--------------------------------------------------------------- commit 9ba5daa863d59d5b2a7bd8fabdd9caa0b8fe4521 Author: Andrey Mokhov Date: Sat Jan 9 19:10:44 2016 +0000 Reset GHC_PACKAGE_PATH varialbe (5th try). See #110. >--------------------------------------------------------------- 9ba5daa863d59d5b2a7bd8fabdd9caa0b8fe4521 build.bat | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/build.bat b/build.bat index 2901686..07e355a 100644 --- a/build.bat +++ b/build.bat @@ -16,7 +16,11 @@ ".." ^ %* - at rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains - at set GHC_PACKAGE_PATH= - at ghc %ghcArgs% && .shake\build %shakeArgs% + at ghc %ghcArgs% + + at if %ERRORLEVEL% EQU 0 ( + @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains + @set GHC_PACKAGE_PATH= + @.shake\build %shakeArgs% +) From git at git.haskell.org Fri Oct 27 00:34:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Note on nm on OS X (5422e92) Message-ID: <20171027003455.BD8C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5422e921b215ccb4a9041689a9b6cab4aa4af646/ghc >--------------------------------------------------------------- commit 5422e921b215ccb4a9041689a9b6cab4aa4af646 Author: Alex Biehl Date: Wed Jun 8 12:47:49 2016 +0200 Note on nm on OS X >--------------------------------------------------------------- 5422e921b215ccb4a9041689a9b6cab4aa4af646 README.md | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/README.md b/README.md index d99d2b7..6b5b234 100644 --- a/README.md +++ b/README.md @@ -43,6 +43,13 @@ runs the `boot` and `configure` scripts automatically on the first build, so tha need to. Use `--skip-configure` to suppress this behaviour (see overview of command line flags below). +* Also note on OS X newer versions of XCode ship with a broken `nm` tool ([#1174](https://ghc.haskell.org/trac/ghc/ticket/11744)). To mitigate the problem place something like + ````haskell + userArgs :: Args + userArgs = builder (Configure ".") ? arg "--with-nm=$(xcrun --find nm-classic)" + ```` + in your `UserSettings.hs`. + Using the build system ---------------------- Once your first build is successful, simply run `build` to rebuild. Most build artefacts From git at git.haskell.org Fri Oct 27 00:34:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to the projects webpage (4bdc4a4) Message-ID: <20171027003456.B185E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4bdc4a4747801dba02d755ce08d356d81ede18a3/ghc >--------------------------------------------------------------- commit 4bdc4a4747801dba02d755ce08d356d81ede18a3 Author: Andrey Mokhov Date: Wed Jul 19 00:32:51 2017 +0100 Link to the projects webpage [skip ci] >--------------------------------------------------------------- 4bdc4a4747801dba02d755ce08d356d81ede18a3 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 3e5318a..8404496 100644 --- a/README.md +++ b/README.md @@ -148,6 +148,8 @@ at present and we expect a lot of further refactoring. If you would like to work on a particular issue, please let everyone know by adding a comment about this. The issues that are currently on the critical path and therefore require particular attention are listed in [#239](https://github.com/snowleopard/hadrian/issues/239). +Also have a look at [projects](https://github.com/snowleopard/hadrian/projects) +where open issues and pull requests are grouped into categories. Acknowledgements ---------------- From git at git.haskell.org Fri Oct 27 00:34:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor generators, add makeExecutable action. (3dff957) Message-ID: <20171027003456.C59893A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3dff95749258bfaa8a21ad0e2588a391ade36649/ghc >--------------------------------------------------------------- commit 3dff95749258bfaa8a21ad0e2588a391ade36649 Author: Andrey Mokhov Date: Sat Jan 9 20:09:51 2016 +0000 Refactor generators, add makeExecutable action. >--------------------------------------------------------------- 3dff95749258bfaa8a21ad0e2588a391ade36649 src/GHC.hs | 8 ++++++-- src/Rules/Actions.hs | 7 ++++++- src/Rules/Generate.hs | 17 +++++++---------- src/Rules/Generators/Common.hs | 20 ++++++++++++++++++++ src/Rules/Generators/ConfigHs.hs | 10 +++------- src/Rules/Generators/GhcAutoconfH.hs | 5 ++--- src/Rules/Generators/GhcBootPlatformH.hs | 8 +++----- src/Rules/Generators/GhcPlatformH.hs | 6 ++---- src/Rules/Generators/GhcSplit.hs | 21 ++++++++++----------- src/Rules/Generators/GhcVersionH.hs | 6 ++---- src/Rules/Generators/VersionHs.hs | 5 ++--- src/Rules/Perl.hs | 17 +++-------------- src/Rules/Program.hs | 2 +- 13 files changed, 67 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3dff95749258bfaa8a21ad0e2588a391ade36649 From git at git.haskell.org Fri Oct 27 00:34:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:34:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #262 from alexbiehl/patch-1 (920e7bb) Message-ID: <20171027003459.432CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/920e7bba89b3d398c162e7d90d5a3581551e1edb/ghc >--------------------------------------------------------------- commit 920e7bba89b3d398c162e7d90d5a3581551e1edb Merge: 85b4b52 5422e92 Author: Andrey Mokhov Date: Thu Jun 9 10:46:52 2016 +0100 Merge pull request #262 from alexbiehl/patch-1 Note on nm on OS X >--------------------------------------------------------------- 920e7bba89b3d398c162e7d90d5a3581551e1edb README.md | 7 +++++++ 1 file changed, 7 insertions(+) From git at git.haskell.org Fri Oct 27 00:35:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build stage1 GHC only on appveyor to fit into the time limit. (4745578) Message-ID: <20171027003500.35B723A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4745578604163225043051c6963284c0a52affef/ghc >--------------------------------------------------------------- commit 4745578604163225043051c6963284c0a52affef Author: Andrey Mokhov Date: Sat Jan 9 20:14:31 2016 +0000 Build stage1 GHC only on appveyor to fit into the time limit. See #110. [skip ci] >--------------------------------------------------------------- 4745578604163225043051c6963284c0a52affef .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index 16de309..99196db 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -24,4 +24,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 00:35:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:35:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (061dcf1) Message-ID: <20171027003500.2E05C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/061dcf1f9b7a9dd7e907e6393ad20751054fba99/ghc >--------------------------------------------------------------- commit 061dcf1f9b7a9dd7e907e6393ad20751054fba99 Author: Andrey Mokhov Date: Wed Jul 19 01:27:44 2017 +0100 Minor revision See #238 >--------------------------------------------------------------- 061dcf1f9b7a9dd7e907e6393ad20751054fba99 src/Rules/Library.hs | 45 +++++++++++++++++---------------------------- 1 file changed, 17 insertions(+), 28 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b746279..d832264 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,6 +1,5 @@ module Rules.Library ( - buildPackageLibrary, buildPackageGhciLibrary, - buildDynamicLib + buildPackageLibrary, buildPackageGhciLibrary, buildDynamicLib ) where import Data.Char @@ -13,15 +12,15 @@ import Flavour import GHC import Oracles.ModuleFiles import Oracles.PackageData -import Oracles.Dependencies (contextDependencies) +import Oracles.Dependencies import Settings import Settings.Path import Target import UserSettings import Util -getLibraryObjs :: Context -> Action [FilePath] -getLibraryObjs context at Context{..} = do +libraryObjects :: Context -> Action [FilePath] +libraryObjects context at Context{..} = do hsObjs <- hsObjects context noHsObjs <- nonHsObjects context @@ -31,34 +30,26 @@ getLibraryObjs context at Context{..} = do split <- interpretInContext context $ splitObjects flavour let getSplitObjs = concatForM hsObjs $ \obj -> do - let dir = dropExtension obj ++ "_" ++ osuf way ++ "_split" - contents <- liftIO $ IO.getDirectoryContents dir - return . map (dir -/-) $ filter (not . all (== '.')) contents + let dir = dropExtension obj ++ "_" ++ osuf way ++ "_split" + contents <- liftIO $ IO.getDirectoryContents dir + return . map (dir -/-) $ filter (not . all (== '.')) contents (noHsObjs ++) <$> if split then getSplitObjs else return hsObjs buildDynamicLib :: Context -> Rules () buildDynamicLib context at Context{..} = do - -- macOS - matchGhcVersionedFilePath libPrefix "dylib" ?> buildDynamicLibUNIX + let path = buildPath context + libPrefix = path -/- "libHS" ++ pkgNameString package + -- OS X + matchGhcVersionedFilePath libPrefix "dylib" ?> buildDynamicLibUnix -- Linux - matchGhcVersionedFilePath libPrefix "so" ?> buildDynamicLibUNIX + matchGhcVersionedFilePath libPrefix "so" ?> buildDynamicLibUnix -- TODO: Windows where - path = buildPath context - libPrefix = path -/- "libHS" ++ pkgNameString package - - buildDynamicLibUNIX so = do + buildDynamicLibUnix so = do deps <- contextDependencies context - - forM_ deps $ \dep -> do - lib <- pkgLibraryFile dep - need [lib] - - removeFile so - - objs <- getLibraryObjs context - + need =<< mapM pkgLibraryFile deps + objs <- libraryObjects context build $ Target context (Ghc LinkHs stage) objs [so] buildPackageLibrary :: Context -> Rules () @@ -66,12 +57,10 @@ buildPackageLibrary context at Context {..} = do let path = buildPath context libPrefix = path -/- "libHS" ++ pkgNameString package matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do - removeFile a - - objs <- getLibraryObjs context - + objs <- libraryObjects context asuf <- libsuf way let isLib0 = ("//*-0" ++ asuf) ?== a + removeFile a if isLib0 then build $ Target context (Ar stage) [] [a] -- TODO: Scan for dlls else build $ Target context (Ar stage) objs [a] From git at git.haskell.org Fri Oct 27 00:37:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix GHC location before Stack install (b2fc154) Message-ID: <20171027003722.6F2B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2fc1542ca069e5efb3abaa8dcb2213bd1ed8308/ghc >--------------------------------------------------------------- commit b2fc1542ca069e5efb3abaa8dcb2213bd1ed8308 Author: Andrey Mokhov Date: Fri Jul 22 12:17:52 2016 +0200 Fix GHC location before Stack install >--------------------------------------------------------------- b2fc1542ca069e5efb3abaa8dcb2213bd1ed8308 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4c3e714..30e3bcf 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -23,13 +23,13 @@ install: - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - ghc --version - stack --version - alex --version - happy --version - stack exec -- ghc-pkg list - - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" From git at git.haskell.org Fri Oct 27 00:37:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace Config oracle with generic key-value text file oracle (da27a1f) Message-ID: <20171027003723.B2A173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da27a1fec4ba6565faca24362f0007aa477105f0/ghc >--------------------------------------------------------------- commit da27a1fec4ba6565faca24362f0007aa477105f0 Author: Andrey Mokhov Date: Wed Aug 9 23:39:23 2017 +0100 Replace Config oracle with generic key-value text file oracle See #347 >--------------------------------------------------------------- da27a1fec4ba6565faca24362f0007aa477105f0 hadrian.cabal | 2 +- src/Hadrian/Oracles/Config.hs | 34 --------------------------------- src/Hadrian/Oracles/KeyValue.hs | 42 +++++++++++++++++++++++++++++++++++++++++ src/Oracles/Flag.hs | 4 ++-- src/Oracles/ModuleFiles.hs | 6 +++--- src/Oracles/PackageData.hs | 26 ++++++------------------- src/Oracles/Setting.hs | 6 +++--- src/Rules/Oracles.hs | 6 ++---- src/Settings.hs | 4 ++-- 9 files changed, 61 insertions(+), 69 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 da27a1fec4ba6565faca24362f0007aa477105f0 From git at git.haskell.org Fri Oct 27 00:37:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify oracles (acf66a3) Message-ID: <20171027003720.3ECB43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acf66a3c7bb4834f2a9b631eb5492dfc92149026/ghc >--------------------------------------------------------------- commit acf66a3c7bb4834f2a9b631eb5492dfc92149026 Author: Andrey Mokhov Date: Tue Aug 8 22:53:25 2017 +0100 Simplify oracles >--------------------------------------------------------------- acf66a3c7bb4834f2a9b631eb5492dfc92149026 src/Hadrian/Oracles/ArgsHash.hs | 6 +++--- src/Hadrian/Oracles/Config.hs | 6 +++--- src/Oracles/Dependencies.hs | 18 +++++------------- 3 files changed, 11 insertions(+), 19 deletions(-) diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index e07fc3f..8ac2c38 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -35,16 +35,16 @@ trackArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action () trackArgsHash t = do let hashedInputs = [ show $ hash (inputs t) ] hashedTarget = target (context t) (builder t) hashedInputs (outputs t) - void (askOracle $ ArgsHashKey hashedTarget :: Action Int) + void (askOracle $ ArgsHash hashedTarget :: Action Int) -newtype ArgsHashKey c b = ArgsHashKey (Target c b) +newtype ArgsHash c b = ArgsHash (Target c b) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -- | This oracle stores per-target argument list hashes in the Shake database, -- allowing the user to track them between builds using 'trackArgsHash' queries. argsHashOracle :: (ShakeValue c, ShakeValue b) => TrackArgument c b -> Args c b -> Rules () argsHashOracle trackArgument args = void $ - addOracle $ \(ArgsHashKey target) -> do + addOracle $ \(ArgsHash target) -> do argList <- interpret target args let trackedArgList = filter (trackArgument target) argList return $ hash trackedArgList diff --git a/src/Hadrian/Oracles/Config.hs b/src/Hadrian/Oracles/Config.hs index 0b12616..1263f1a 100644 --- a/src/Hadrian/Oracles/Config.hs +++ b/src/Hadrian/Oracles/Config.hs @@ -10,7 +10,7 @@ import Development.Shake.Config import Hadrian.Utilities -newtype ConfigKey = ConfigKey String +newtype Config = Config String deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -- | Lookup a configuration setting raising an error if the key is not found. @@ -21,7 +21,7 @@ unsafeAskConfig key = (fromMaybe $ error msg) <$> askConfig key -- | Lookup a configuration setting. askConfig :: String -> Action (Maybe String) -askConfig = askOracle . ConfigKey +askConfig = askOracle . Config -- | This oracle reads and parses a configuration file consisting of key-value -- pairs @key = value@ and answers 'askConfig' queries tracking the results. @@ -31,4 +31,4 @@ configOracle configFile = void $ do need [configFile] putLoud $ "Reading " ++ configFile ++ "..." liftIO $ readConfigFile configFile - addOracle $ \(ConfigKey key) -> Map.lookup key <$> cfg () + addOracle $ \(Config key) -> Map.lookup key <$> cfg () diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 04ebbfd..6ae0b0d 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -15,7 +15,7 @@ import Settings import Settings.Builders.GhcCabal import Settings.Path -newtype ObjDepsKey = ObjDepsKey (FilePath, FilePath) +newtype Dependency = Dependency (FilePath, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -- | 'Action' @fileDependencies context file@ looks up dependencies of a @file@ @@ -26,15 +26,12 @@ newtype ObjDepsKey = ObjDepsKey (FilePath, FilePath) fileDependencies :: Context -> FilePath -> Action (FilePath, [FilePath]) fileDependencies context obj = do let path = buildPath context -/- ".dependencies" - deps <- askOracle $ ObjDepsKey (path, obj) + deps <- askOracle $ Dependency (path, obj) case deps of Nothing -> error $ "No dependencies found for file " ++ obj Just [] -> error $ "No source file found for file " ++ obj Just (source : files) -> return (source, files) -newtype PkgDepsKey = PkgDepsKey String - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -- | Given a 'Context' this 'Action' looks up its package dependencies in -- 'Settings.Paths.packageDependencies' using 'packageDependenciesOracle', and -- wraps found dependencies in appropriate contexts. The only subtlety here is @@ -45,7 +42,7 @@ contextDependencies :: Context -> Action [Context] contextDependencies context at Context {..} = do let pkgContext = \pkg -> Context (min stage Stage1) pkg way unpack = fromMaybe . error $ "No dependencies for " ++ show context - deps <- unpack <$> askOracle (PkgDepsKey $ pkgNameString package) + deps <- unpack <$> askOracle (Dependency (packageDependencies, pkgNameString package)) pkgs <- sort <$> interpretInContext (pkgContext package) getPackages return . map pkgContext $ intersectOrd (compare . pkgNameString) pkgs deps @@ -74,16 +71,11 @@ needLibrary cs = need =<< concatMapM libraryTargets cs -- | Oracles for the package dependencies and 'path/dist/.dependencies' files. dependenciesOracles :: Rules () dependenciesOracles = do - deps <- newCache readDependencies - void $ addOracle $ \(ObjDepsKey (file, obj)) -> Map.lookup obj <$> deps file - - pkgDeps <- newCache $ \_ -> readDependencies packageDependencies - void $ addOracle $ \(PkgDepsKey pkg) -> Map.lookup pkg <$> pkgDeps () - where - readDependencies file = do + deps <- newCache $ \file -> do putLoud $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return $ Map.fromList [ (key, values) | (key:values) <- contents ] + void $ addOracle $ \(Dependency (file, key)) -> Map.lookup key <$> deps file -- | Topological sort of packages according to their dependencies. -- HACK (izgzhen): See https://github.com/snowleopard/hadrian/issues/344 for details From git at git.haskell.org Fri Oct 27 00:37:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change the stack configuration to use the local Cabal lib (1281be4) Message-ID: <20171027003710.CBFD33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1281be42949bb986c62e0464032145b060649fe4/ghc >--------------------------------------------------------------- commit 1281be42949bb986c62e0464032145b060649fe4 Author: Michal Terepeta Date: Fri Jul 22 11:30:50 2016 +0200 Change the stack configuration to use the local Cabal lib Hadrian should be built with a local Cabal from within the GHC codebase. This makes the stack pick it up, instead of using the released version of Cabal. Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 1281be42949bb986c62e0464032145b060649fe4 hadrian.cabal | 2 +- stack.yaml | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 3429424..63bd164 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* || == 1.24.* + , Cabal == 1.22.* || == 1.24.* || == 1.25.* , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 diff --git a/stack.yaml b/stack.yaml index f6deca8..9eb4cfb 100644 --- a/stack.yaml +++ b/stack.yaml @@ -6,6 +6,7 @@ resolver: lts-5.17 # Local packages, usually specified by relative directory name packages: - '.' +- '../libraries/Cabal/Cabal' # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: From git at git.haskell.org Fri Oct 27 00:37:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update the docs for chunksOfSize (916d5a9) Message-ID: <20171027003726.32A823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/916d5a93c7dba53c730e49e00a0c0656e75e602b/ghc >--------------------------------------------------------------- commit 916d5a93c7dba53c730e49e00a0c0656e75e602b Author: Neil Mitchell Date: Mon Jan 11 11:14:12 2016 +0000 Update the docs for chunksOfSize >--------------------------------------------------------------- 916d5a93c7dba53c730e49e00a0c0656e75e602b src/Settings/Builders/Ar.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ar.hs b/src/Settings/Builders/Ar.hs index 8cf175f..59b70b8 100644 --- a/src/Settings/Builders/Ar.hs +++ b/src/Settings/Builders/Ar.hs @@ -46,7 +46,7 @@ useSuccessiveInvocations path flagArgs fileArgs = do unit . cmd [path] $ flagArgs ++ argsChunk -- | @chunksOfSize size strings@ splits a given list of strings into chunks not --- exceeding the given @size at . +-- exceeding the given @size at . If that is impossible, it uses singleton chunks. chunksOfSize :: Int -> [String] -> [[String]] chunksOfSize n = repeatedly f where f xs = splitAt (max 1 $ length $ takeWhile (<= n) $ scanl1 (+) $ map length xs) xs From git at git.haskell.org Fri Oct 27 00:37:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix inability to find gmp.h when building concurrently (b3bcd0f) Message-ID: <20171027003726.784603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3bcd0ffe22fa51b78aa28caf406b7cb74b04ae8/ghc >--------------------------------------------------------------- commit b3bcd0ffe22fa51b78aa28caf406b7cb74b04ae8 Author: Matthew Pickering Date: Fri Jul 22 14:03:07 2016 +0200 Fix inability to find gmp.h when building concurrently There were situations when building concurrently when we would request `gmp.h` before it had been built (or copied). This was occuring when we generated the list of dependents for the c files in the `integer-gmp` folder. Thus, when generating the dependents for this library we now require `gmp.h`. >--------------------------------------------------------------- b3bcd0ffe22fa51b78aa28caf406b7cb74b04ae8 src/Rules/Dependencies.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index f78c488..c64a4e6 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -11,6 +11,8 @@ import Rules.Actions import Settings.Paths import Target import UserSettings +import GHC + buildPackageDependencies :: [(Resource, Int)] -> Context -> Rules () buildPackageDependencies rs context at Context {..} = @@ -20,6 +22,7 @@ buildPackageDependencies rs context at Context {..} = fmap (path ++) [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do let src = dep2src context out + when (package == integerGmp) (need [gmpLibraryH]) need [src] build $ Target context (Cc FindDependencies stage) [src] [out] From git at git.haskell.org Fri Oct 27 00:37:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (72bf4b1) Message-ID: <20171027003727.429163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72bf4b180dffa10fb650046b571b756b5262097a/ghc >--------------------------------------------------------------- commit 72bf4b180dffa10fb650046b571b756b5262097a Author: Andrey Mokhov Date: Sat Aug 12 21:51:16 2017 +0100 Minor revision >--------------------------------------------------------------- 72bf4b180dffa10fb650046b571b756b5262097a src/Base.hs | 29 ++--------------------------- src/Hadrian/Utilities.hs | 23 ++++++++++++++++++++++- src/Rules/Library.hs | 15 +++++++-------- src/Rules/Register.hs | 2 +- 4 files changed, 32 insertions(+), 37 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 6ae3ead..df14d3d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -17,15 +17,13 @@ module Base ( configPath, configFile, sourcePath, -- * Miscellaneous utilities - unifyPath, quote, (-/-), matchVersionedFilePath, matchGhcVersionedFilePath, - putColoured + unifyPath, quote, (-/-), putColoured ) where import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader import Data.Bifunctor -import Data.Char import Data.Function import Data.List.Extra import Data.Maybe @@ -58,30 +56,7 @@ configFile = configPath -/- "system.config" sourcePath :: FilePath sourcePath = hadrianPath -/- "src" --- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the --- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string --- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: --- ---- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'False'@ ---- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ ---- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar-" "a" "foo/bar-0.1.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False'@ -matchVersionedFilePath :: String -> String -> FilePath -> Bool -matchVersionedFilePath prefix suffix filePath = - case stripPrefix prefix filePath >>= stripSuffix suffix of - Nothing -> False - Just version -> all (\c -> isDigit c || c == '-' || c == '.') version - -matchGhcVersionedFilePath :: String -> String -> FilePath -> Bool -matchGhcVersionedFilePath prefix ext filePath = - case stripPrefix prefix filePath >>= stripSuffix ext of - Nothing -> False - Just _ -> True - --- | A more colourful version of Shake's putNormal. +-- | A more colourful version of Shake's 'putNormal'. putColoured :: ColorIntensity -> Color -> String -> Action () putColoured intensity colour msg = do c <- useColour diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 56b53ce..f26a444 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -7,9 +7,11 @@ module Hadrian.Utilities ( quote, yesNo, -- * FilePath manipulation - unifyPath, (-/-) + unifyPath, (-/-), matchVersionedFilePath ) where +import Data.Char +import Data.List.Extra import Development.Shake.FilePath -- | Extract a value from a singleton list, or terminate with an error message @@ -79,3 +81,22 @@ a -/- b | otherwise = a ++ '/' : b infixr 6 -/- + +-- | Given a @prefix@ and a @suffix@ check whether a 'FilePath' matches the +-- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string +-- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: +-- +-- @ +-- 'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'False' +-- 'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False' +-- 'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar-" "a" "foo/bar-0.1.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False' +-- @ +matchVersionedFilePath :: String -> String -> FilePath -> Bool +matchVersionedFilePath prefix suffix filePath = + case stripPrefix prefix filePath >>= stripSuffix suffix of + Nothing -> False + Just version -> all (\c -> isDigit c || c == '-' || c == '.') version diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index ba3138a..7b32f55 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -3,6 +3,7 @@ module Rules.Library ( ) where import Data.Char +import Hadrian.Utilities import qualified System.Directory as IO import Base @@ -38,24 +39,22 @@ libraryObjects context at Context{..} = do buildDynamicLib :: Context -> Rules () buildDynamicLib context at Context{..} = do - let path = buildPath context - libPrefix = path -/- "libHS" ++ pkgNameString package + let libPrefix = buildPath context -/- "libHS" ++ pkgNameString package -- OS X - matchGhcVersionedFilePath libPrefix "dylib" ?> buildDynamicLibUnix + libPrefix ++ "*.dylib" %> buildDynamicLibUnix -- Linux - matchGhcVersionedFilePath libPrefix "so" ?> buildDynamicLibUnix + libPrefix ++ "*.so" %> buildDynamicLibUnix -- TODO: Windows where - buildDynamicLibUnix so = do + buildDynamicLibUnix lib = do deps <- contextDependencies context need =<< mapM pkgLibraryFile deps objs <- libraryObjects context - build $ target context (Ghc LinkHs stage) objs [so] + build $ target context (Ghc LinkHs stage) objs [lib] buildPackageLibrary :: Context -> Rules () buildPackageLibrary context at Context {..} = do - let path = buildPath context - libPrefix = path -/- "libHS" ++ pkgNameString package + let libPrefix = buildPath context -/- "libHS" ++ pkgNameString package matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do objs <- libraryObjects context asuf <- libsuf way diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 1f5f64a..7ec8bcd 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -16,7 +16,7 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do let confIn = pkgInplaceConfig context dir = inplacePackageDbDirectory stage - matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do + dir -/- pkgNameString package ++ "*.conf" %> \conf -> do need [confIn] buildWithResources rs $ target context (GhcPkg Update stage) [confIn] [conf] From git at git.haskell.org Fri Oct 27 00:37:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #151, add a call to selftest (c5cb061) Message-ID: <20171027003729.ACEDA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5cb0617314c3b6fcb201246a76b6a02cb93350f/ghc >--------------------------------------------------------------- commit c5cb0617314c3b6fcb201246a76b6a02cb93350f Author: Neil Mitchell Date: Mon Jan 11 11:39:47 2016 +0000 #151, add a call to selftest >--------------------------------------------------------------- c5cb0617314c3b6fcb201246a76b6a02cb93350f .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index dd3bd12..0dc23c1 100644 --- a/.travis.yml +++ b/.travis.yml @@ -62,6 +62,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) + - ./ghc/shake-build/build.sh selftest - ./ghc/shake-build/build.sh -j --no-progress $TARGET cache: From git at git.haskell.org Fri Oct 27 00:37:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #273 from mpickering/master (4a7016b) Message-ID: <20171027003730.1500B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a7016b71f1a393cfbd9f2360802b07f0a7e9b06/ghc >--------------------------------------------------------------- commit 4a7016b71f1a393cfbd9f2360802b07f0a7e9b06 Merge: b2fc154 b3bcd0f Author: Andrey Mokhov Date: Fri Jul 22 15:09:40 2016 +0200 Merge pull request #273 from mpickering/master Fix inability to find gmp.h when building concurrently >--------------------------------------------------------------- 4a7016b71f1a393cfbd9f2360802b07f0a7e9b06 src/Rules/Dependencies.hs | 3 +++ 1 file changed, 3 insertions(+) From git at git.haskell.org Fri Oct 27 00:37:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix package registration (78878b7) Message-ID: <20171027003730.C6FEA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/78878b77fecd6a2e277cfcee5d2bcb3a3832e385/ghc >--------------------------------------------------------------- commit 78878b77fecd6a2e277cfcee5d2bcb3a3832e385 Author: Andrey Mokhov Date: Sat Aug 12 22:27:54 2017 +0100 Fix package registration >--------------------------------------------------------------- 78878b77fecd6a2e277cfcee5d2bcb3a3832e385 src/Rules/Register.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 7ec8bcd..6f4f5b4 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -1,5 +1,7 @@ module Rules.Register (registerPackage) where +import Hadrian.Utilities + import Base import Context import Expression @@ -16,7 +18,7 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do let confIn = pkgInplaceConfig context dir = inplacePackageDbDirectory stage - dir -/- pkgNameString package ++ "*.conf" %> \conf -> do + matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do need [confIn] buildWithResources rs $ target context (GhcPkg Update stage) [confIn] [conf] From git at git.haskell.org Fri Oct 27 00:37:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #151 from ndmitchell/master (5f80d4f) Message-ID: <20171027003733.B4D7A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f80d4f2a5269a8546a5040edbd26502fab7bc26/ghc >--------------------------------------------------------------- commit 5f80d4f2a5269a8546a5040edbd26502fab7bc26 Merge: 754ed41 c5cb061 Author: Andrey Mokhov Date: Mon Jan 11 14:29:39 2016 +0000 Merge pull request #151 from ndmitchell/master Add tests >--------------------------------------------------------------- 5f80d4f2a5269a8546a5040edbd26502fab7bc26 .appveyor.yml | 1 + .travis.yml | 1 + shaking-up-ghc.cabal | 3 +++ src/Main.hs | 4 +++- src/Settings/Builders/Ar.hs | 16 ++++------------ src/Test.hs | 28 ++++++++++++++++++++++++++++ src/Way.hs | 2 +- 7 files changed, 41 insertions(+), 14 deletions(-) From git at git.haskell.org Fri Oct 27 00:37:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split CompilerMode for GHC and CC (a8abbc9) Message-ID: <20171027003733.E07A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8abbc961fcfcd360e9a731fc42c28b93332bc8b/ghc >--------------------------------------------------------------- commit a8abbc961fcfcd360e9a731fc42c28b93332bc8b Author: Michal Terepeta Date: Sat Jul 23 16:57:19 2016 +0200 Split CompilerMode for GHC and CC Signed-off-by: Michal Terepeta >--------------------------------------------------------------- a8abbc961fcfcd360e9a731fc42c28b93332bc8b src/Builder.hs | 27 +++++++++++++++++---------- src/Predicate.hs | 8 +++++++- src/Rules/Compile.hs | 6 +++--- src/Rules/Dependencies.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Test.hs | 4 ++-- src/Settings/Builders/Cc.hs | 4 ++-- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- 13 files changed, 46 insertions(+), 33 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 a8abbc961fcfcd360e9a731fc42c28b93332bc8b From git at git.haskell.org Fri Oct 27 00:37:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move putColoured to the library (a395dd7) Message-ID: <20171027003734.A4A013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a395dd71438e58c29448f5f34cf4bb17e9fcbe5d/ghc >--------------------------------------------------------------- commit a395dd71438e58c29448f5f34cf4bb17e9fcbe5d Author: Andrey Mokhov Date: Sun Aug 13 00:49:18 2017 +0100 Move putColoured to the library See #347 >--------------------------------------------------------------- a395dd71438e58c29448f5f34cf4bb17e9fcbe5d src/Base.hs | 27 +-------------------------- src/CmdLineFlag.hs | 16 ++++++++-------- src/Hadrian/Utilities.hs | 23 ++++++++++++++++++++++- src/UserSettings.hs | 6 ++++-- 4 files changed, 35 insertions(+), 37 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index df14d3d..f4f4c4b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -17,7 +17,7 @@ module Base ( configPath, configFile, sourcePath, -- * Miscellaneous utilities - unifyPath, quote, (-/-), putColoured + unifyPath, quote, (-/-) ) where import Control.Applicative @@ -32,11 +32,6 @@ import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import Hadrian.Utilities -import System.Console.ANSI -import System.IO -import System.Info - -import CmdLineFlag -- TODO: reexport Stage, etc.? @@ -55,23 +50,3 @@ configFile = configPath -/- "system.config" -- sourcePath -/- "Base.hs". We use this to `need` some of the source files. sourcePath :: FilePath sourcePath = hadrianPath -/- "src" - --- | A more colourful version of Shake's 'putNormal'. -putColoured :: ColorIntensity -> Color -> String -> Action () -putColoured intensity colour msg = do - c <- useColour - when c . liftIO $ setSGR [SetColor Foreground intensity colour] - putNormal msg - when c . liftIO $ do - setSGR [] - hFlush stdout - -useColour :: Action Bool -useColour = case cmdProgressColour of - Never -> return False - Always -> return True - Auto -> do - supported <- liftIO $ hSupportsANSI stdout - -- An ugly hack to always try to print colours when on mingw and cygwin. - let windows = any (`isPrefixOf` os) ["mingw", "cygwin"] - return $ windows || supported diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 961a033..ff35f1f 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,11 +1,12 @@ module CmdLineFlag ( putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, - cmdProgressColour, ProgressColour (..), cmdProgressInfo, ProgressInfo (..), - cmdSkipConfigure, cmdSplitObjects + cmdProgressColour, cmdProgressInfo, ProgressInfo (..), cmdSkipConfigure, + cmdSplitObjects ) where import Data.IORef import Data.List.Extra +import Hadrian.Utilities import System.Console.GetOpt import System.IO.Unsafe @@ -16,14 +17,13 @@ data Untracked = Untracked { buildHaddock :: Bool , flavour :: Maybe String , integerSimple :: Bool - , progressColour :: ProgressColour + , progressColour :: UseColour , progressInfo :: ProgressInfo , skipConfigure :: Bool , splitObjects :: Bool } deriving (Eq, Show) -data ProgressColour = Never | Auto | Always deriving (Eq, Show) -data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) +data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked @@ -49,12 +49,12 @@ readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) readProgressColour ms = maybe (Left "Cannot parse progress-colour") (Right . set) (go =<< lower <$> ms) where - go :: String -> Maybe ProgressColour + go :: String -> Maybe UseColour go "never" = Just Never go "auto" = Just Auto go "always" = Just Always go _ = Nothing - set :: ProgressColour -> Untracked -> Untracked + set :: UseColour -> Untracked -> Untracked set flag flags = flags { progressColour = flag } readProgressInfo :: Maybe String -> Either String (Untracked -> Untracked) @@ -115,7 +115,7 @@ cmdFlavour = flavour getCmdLineFlags cmdIntegerSimple :: Bool cmdIntegerSimple = integerSimple getCmdLineFlags -cmdProgressColour :: ProgressColour +cmdProgressColour :: UseColour cmdProgressColour = progressColour getCmdLineFlags cmdProgressInfo :: ProgressInfo diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index f26a444..bf9a9ac 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -7,12 +7,20 @@ module Hadrian.Utilities ( quote, yesNo, -- * FilePath manipulation - unifyPath, (-/-), matchVersionedFilePath + unifyPath, (-/-), matchVersionedFilePath, + + -- * Miscellaneous + UseColour (..), putColoured ) where +import Control.Monad import Data.Char import Data.List.Extra +import Development.Shake import Development.Shake.FilePath +import System.Console.ANSI +import System.Info.Extra +import System.IO -- | Extract a value from a singleton list, or terminate with an error message -- if the list does not contain exactly one value. @@ -100,3 +108,16 @@ matchVersionedFilePath prefix suffix filePath = case stripPrefix prefix filePath >>= stripSuffix suffix of Nothing -> False Just version -> all (\c -> isDigit c || c == '-' || c == '.') version + +data UseColour = Never | Auto | Always deriving (Eq, Show) + +-- | A more colourful version of Shake's 'putNormal'. +putColoured :: UseColour -> ColorIntensity -> Color -> String -> Action () +putColoured useColour intensity colour msg = do + supported <- liftIO $ hSupportsANSI stdout + let c Never = False + c Auto = supported || isWindows -- Colours do work on Windows + c Always = True + when (c useColour) . liftIO $ setSGR [SetColor Foreground intensity colour] + putNormal msg + when (c useColour) . liftIO $ setSGR [] >> hFlush stdout diff --git a/src/UserSettings.hs b/src/UserSettings.hs index e2aa674..debd7cd 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -7,9 +7,11 @@ module UserSettings ( putBuild, putSuccess, defaultDestDir, defaultStage1Only ) where +import Hadrian.Utilities import System.Console.ANSI import Base +import CmdLineFlag import Flavour import Expression @@ -37,11 +39,11 @@ verboseCommands = return False -- | Customise build progress messages (e.g. executing a build command). putBuild :: String -> Action () -putBuild = putColoured Dull Magenta +putBuild = putColoured cmdProgressColour Dull Magenta -- | Customise build success messages (e.g. a package is built successfully). putSuccess :: String -> Action () -putSuccess = putColoured Dull Green +putSuccess = putColoured cmdProgressColour Dull Green -- | Path to the GHC install destination. It is empty by default, which -- corresponds to the root of the file system. You can replace it by a specific From git at git.haskell.org Fri Oct 27 00:37:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use shallow git clone. (0c3a659) Message-ID: <20171027003737.1EB003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c3a65984127a8e17cde5cec4257ed8b023487db/ghc >--------------------------------------------------------------- commit 0c3a65984127a8e17cde5cec4257ed8b023487db Author: Andrey Mokhov Date: Mon Jan 11 14:48:30 2016 +0000 Use shallow git clone. See #110. [skip ci] >--------------------------------------------------------------- 0c3a65984127a8e17cde5cec4257ed8b023487db .appveyor.yml | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index f0d0e69..68c1fd8 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -16,7 +16,14 @@ install: - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - git clone --recursive git://git.haskell.org/ghc.git C:\msys64\home\ghc\tmp + + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ + - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ + - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ + - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ + - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot From git at git.haskell.org Fri Oct 27 00:37:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #275 from michalt/compilermode/1 (e89ab5c) Message-ID: <20171027003737.9D0113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e89ab5c63394d13793b32b391923945154c4c87d/ghc >--------------------------------------------------------------- commit e89ab5c63394d13793b32b391923945154c4c87d Merge: 4a7016b a8abbc9 Author: Andrey Mokhov Date: Sat Jul 23 20:03:13 2016 +0200 Merge pull request #275 from michalt/compilermode/1 Split CompilerMode for GHC and CC >--------------------------------------------------------------- e89ab5c63394d13793b32b391923945154c4c87d src/Builder.hs | 27 +++++++++++++++++---------- src/Predicate.hs | 8 +++++++- src/Rules/Compile.hs | 6 +++--- src/Rules/Dependencies.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Test.hs | 4 ++-- src/Settings/Builders/Cc.hs | 4 ++-- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- 13 files changed, 46 insertions(+), 33 deletions(-) diff --cc src/Rules/Dependencies.hs index c64a4e6,94a9542..8aeecf5 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@@ -22,9 -20,8 +22,9 @@@ buildPackageDependencies rs context at Con fmap (path ++) [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do let src = dep2src context out + when (package == integerGmp) (need [gmpLibraryH]) need [src] - build $ Target context (Cc FindDependencies stage) [src] [out] + build $ Target context (Cc FindCDependencies stage) [src] [out] hDepFile %> \out -> do srcs <- haskellSources context From git at git.haskell.org Fri Oct 27 00:37:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export basic data type definitions from Base (4f0b5a1) Message-ID: <20171027003738.5E5753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4f0b5a138391303ea7be0cd9bab49076ebc9d6a9/ghc >--------------------------------------------------------------- commit 4f0b5a138391303ea7be0cd9bab49076ebc9d6a9 Author: Andrey Mokhov Date: Sun Aug 13 03:20:46 2017 +0100 Re-export basic data type definitions from Base >--------------------------------------------------------------- 4f0b5a138391303ea7be0cd9bab49076ebc9d6a9 src/Base.hs | 29 +++++-- src/Builder.hs | 43 +-------- src/Context.hs | 10 ++- src/Expression.hs | 54 ++++++++---- src/Oracles/Dependencies.hs | 1 - src/Oracles/ModuleFiles.hs | 2 - src/Oracles/Setting.hs | 39 ++++++++- src/Package.hs | 41 ++++----- src/Rules/Cabal.hs | 1 - src/Rules/Clean.hs | 1 - src/Rules/Compile.hs | 2 - src/Rules/Configure.hs | 3 - src/Rules/Dependencies.hs | 3 +- src/Rules/Generate.hs | 2 - src/Rules/Gmp.hs | 5 -- src/Rules/Library.hs | 4 +- src/Rules/Perl.hs | 1 - src/Rules/Register.hs | 3 - src/Rules/Selftest.hs | 4 +- src/Rules/SourceDist.hs | 1 - src/Rules/Test.hs | 3 - src/Settings/Builders/Common.hs | 2 + src/Settings/Packages/Rts.hs | 2 - src/Settings/Path.hs | 188 ++++++++++++++++++++-------------------- src/Stage.hs | 10 +-- src/Target.hs | 2 +- src/UserSettings.hs | 2 +- src/Util.hs | 1 - src/Way.hs | 51 ++++------- 29 files changed, 252 insertions(+), 258 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 4f0b5a138391303ea7be0cd9bab49076ebc9d6a9 From git at git.haskell.org Fri Oct 27 00:37:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix parallel invocations of DeriveConstants builder. (9178de2) Message-ID: <20171027003742.02F0F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9178de2bd2483148777975b5bab48d96ce2884ad/ghc >--------------------------------------------------------------- commit 9178de2bd2483148777975b5bab48d96ce2884ad Author: Andrey Mokhov Date: Mon Jan 11 16:06:21 2016 +0000 Fix parallel invocations of DeriveConstants builder. See #137. >--------------------------------------------------------------- 9178de2bd2483148777975b5bab48d96ce2884ad src/Rules/Generate.hs | 9 ++++++--- src/Settings/Builders/DeriveConstants.hs | 14 +++++--------- 2 files changed, 11 insertions(+), 12 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 4fd7da6..025f1ee 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -19,7 +19,6 @@ import Rules.Gmp import Rules.Libffi import Rules.Resources (Resources) import Settings -import Settings.Builders.DeriveConstants installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" @@ -53,6 +52,9 @@ ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> [ "GHC/PrimopWrappers.hs" , "autogen/GHC/Prim.hs" ] +derivedConstantsPath :: FilePath +derivedConstantsPath = "includes/dist-derivedconstants/header" + derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) [ "DerivedConstants.h" @@ -178,9 +180,10 @@ generateRules = do generate ghcSplit emptyTarget generateGhcSplit makeExecutable ghcSplit - -- TODO: simplify + -- TODO: simplify, get rid of fake rts target derivedConstantsPath ++ "//*" %> \file -> do - build $ fullTarget (PartialTarget Stage1 rts) DeriveConstants [] [file] + withTempDir $ \dir -> build $ + fullTarget (PartialTarget Stage1 rts) DeriveConstants [] [file, dir] where file <~ gen = file %> \out -> generate out emptyTarget gen diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 6f4828a..fb578f5 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -1,6 +1,4 @@ -module Settings.Builders.DeriveConstants ( - derivedConstantsPath, deriveConstantsBuilderArgs - ) where +module Settings.Builders.DeriveConstants (deriveConstantsBuilderArgs) where import Base import Expression @@ -9,21 +7,19 @@ import Oracles.Config.Setting import Predicates (builder, file) import Settings.Builders.Common -derivedConstantsPath :: FilePath -derivedConstantsPath = "includes/dist-derivedconstants/header" - -- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? deriveConstantsBuilderArgs :: Args deriveConstantsBuilderArgs = builder DeriveConstants ? do - cFlags <- fromDiffExpr includeCcArgs + cFlags <- fromDiffExpr includeCcArgs + [output, tempDir] <- getOutputs mconcat [ file "//DerivedConstants.h" ? arg "--gen-header" , file "//GHCConstantsHaskellType.hs" ? arg "--gen-haskell-type" , file "//platformConstants" ? arg "--gen-haskell-value" , file "//GHCConstantsHaskellWrappers.hs" ? arg "--gen-haskell-wrappers" , file "//GHCConstantsHaskellExports.hs" ? arg "--gen-haskell-exports" - , arg "-o", arg =<< getOutput - , arg "--tmpdir", arg derivedConstantsPath + , arg "-o", arg output + , arg "--tmpdir", arg tempDir , arg "--gcc-program", arg =<< getBuilderPath (Gcc Stage1) , append . concat $ map (\a -> ["--gcc-flag", a]) cFlags , arg "--nm-program", arg =<< getBuilderPath Nm From git at git.haskell.org Fri Oct 27 00:37:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use nm-classic instead of nm when host is Darwin (3c31edc) Message-ID: <20171027003742.7FAF63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c31edcca75f477bfeb54cd844c9d2f575037c3c/ghc >--------------------------------------------------------------- commit 3c31edcca75f477bfeb54cd844c9d2f575037c3c Author: Tomas Carnecky Date: Sun Jul 24 00:03:59 2016 +0200 Use nm-classic instead of nm when host is Darwin >--------------------------------------------------------------- 3c31edcca75f477bfeb54cd844c9d2f575037c3c README.md | 8 -------- src/Settings/Builders/Configure.hs | 7 +++++++ 2 files changed, 7 insertions(+), 8 deletions(-) diff --git a/README.md b/README.md index 4ce3b3a..d99d2b7 100644 --- a/README.md +++ b/README.md @@ -43,14 +43,6 @@ runs the `boot` and `configure` scripts automatically on the first build, so tha need to. Use `--skip-configure` to suppress this behaviour (see overview of command line flags below). -* Also note on OS X newer versions of XCode ship with a broken `nm` tool -([#11744](https://ghc.haskell.org/trac/ghc/ticket/11744)). One way to mitigate the -problem is to add the following into your `UserSettings.hs`: - ````haskell - userArgs :: Args - userArgs = builder (Configure ".") ? arg "--with-nm=$(xcrun --find nm-classic)" - ```` - Using the build system ---------------------- Once your first build is successful, simply run `build` to rebuild. Most build artefacts diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index c95a5da..6482df1 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -1,5 +1,7 @@ module Settings.Builders.Configure (configureBuilderArgs) where +import qualified System.Info as System + import Base import Oracles.Config.Setting import Oracles.WindowsPath @@ -23,4 +25,9 @@ configureBuilderArgs = mconcat , "--enable-static=yes" , "--enable-shared=no" -- TODO: add support for yes , "--host=" ++ targetPlatform ] + + -- On OS X, use "nm-classic" instead of "nm" due to a bug in the later. + -- See https://ghc.haskell.org/trac/ghc/ticket/11744 + , builder (Configure ".") ? System.os == "darwin" ? + arg "--with-nm=$(xcrun --find nm-classic)" ] From git at git.haskell.org Fri Oct 27 00:37:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge Rules.Oracles into Rules (709ffb7) Message-ID: <20171027003742.D357B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/709ffb71d43a55e93a82577bd79b37d169b9754a/ghc >--------------------------------------------------------------- commit 709ffb71d43a55e93a82577bd79b37d169b9754a Author: Andrey Mokhov Date: Sun Aug 13 16:34:01 2017 +0100 Merge Rules.Oracles into Rules >--------------------------------------------------------------- 709ffb71d43a55e93a82577bd79b37d169b9754a hadrian.cabal | 1 - src/Base.hs | 0 src/Main.hs | 9 ++++----- src/Rules.hs | 30 ++++++++++++++++++++++++------ src/Rules/Oracles.hs | 21 --------------------- 5 files changed, 28 insertions(+), 33 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index c39df50..c964f3b 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -52,7 +52,6 @@ executable hadrian , Rules.Install , Rules.Libffi , Rules.Library - , Rules.Oracles , Rules.Perl , Rules.Program , Rules.Register diff --git a/src/Main.hs b/src/Main.hs index 0f65ecf..6843140 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -7,7 +7,6 @@ import qualified Environment import qualified Rules import qualified Rules.Clean import qualified Rules.Install -import qualified Rules.Oracles import qualified Rules.SourceDist import qualified Rules.Selftest import qualified Rules.Test @@ -23,14 +22,14 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do where rules :: Rules () rules = do + Rules.buildRules Rules.Clean.cleanRules - Rules.Oracles.oracleRules - Rules.SourceDist.sourceDistRules + Rules.Install.installRules + Rules.oracleRules Rules.Selftest.selftestRules + Rules.SourceDist.sourceDistRules Rules.Test.testRules - Rules.buildRules Rules.topLevelTargets - Rules.Install.installRules options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest diff --git a/src/Rules.hs b/src/Rules.hs index 359d3e9..335c4c3 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,10 +1,19 @@ -module Rules (topLevelTargets, packageTargets, buildRules) where +module Rules ( + buildRules, oracleRules, packageTargets, topLevelTargets + ) where + +import qualified Hadrian.Oracles.ArgsHash +import qualified Hadrian.Oracles.DirectoryContents +import qualified Hadrian.Oracles.KeyValue +import qualified Hadrian.Oracles.Path import Base import Context import Expression import Flavour import GHC +import qualified Oracles.Dependencies +import qualified Oracles.ModuleFiles import qualified Rules.Compile import qualified Rules.Data import qualified Rules.Dependencies @@ -18,9 +27,9 @@ import qualified Rules.Library import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register -import Oracles.Dependencies import Settings import Settings.Path +import Target allStages :: [Stage] allStages = [minBound ..] @@ -52,7 +61,7 @@ packageTargets stage pkg = do ways <- interpretInContext context getLibraryWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour - more <- libraryTargets context + more <- Oracles.Dependencies.libraryTargets context return $ [ pkgSetupConfigFile context | nonCabalContext context ] ++ [ pkgHaddockFile context | docs && stage == Stage1 ] ++ libs ++ more @@ -102,8 +111,17 @@ buildRules = do packageRules Rules.Perl.perlScriptRules +oracleRules :: Rules () +oracleRules = do + Hadrian.Oracles.ArgsHash.argsHashOracle trackArgument getArgs + Hadrian.Oracles.DirectoryContents.directoryContentsOracle + Hadrian.Oracles.KeyValue.keyValueOracle + Hadrian.Oracles.Path.pathOracle + Oracles.Dependencies.dependenciesOracles + Oracles.ModuleFiles.moduleFilesOracle + programsStage1Only :: [Package] programsStage1Only = - [ deriveConstants, genprimopcode, hp2ps, runGhc - , ghcCabal, hpc, dllSplit, ghcPkg, hsc2hs - , genapply, ghc ] + [ deriveConstants, genprimopcode, hp2ps, runGhc + , ghcCabal, hpc, dllSplit, ghcPkg, hsc2hs + , genapply, ghc ] diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs deleted file mode 100644 index 5f1f55e..0000000 --- a/src/Rules/Oracles.hs +++ /dev/null @@ -1,21 +0,0 @@ -module Rules.Oracles (oracleRules) where - -import qualified Hadrian.Oracles.ArgsHash -import qualified Hadrian.Oracles.DirectoryContents -import qualified Hadrian.Oracles.KeyValue -import qualified Hadrian.Oracles.Path - -import Base -import qualified Oracles.Dependencies -import qualified Oracles.ModuleFiles -import Target -import Settings - -oracleRules :: Rules () -oracleRules = do - Hadrian.Oracles.ArgsHash.argsHashOracle trackArgument getArgs - Hadrian.Oracles.DirectoryContents.directoryContentsOracle - Hadrian.Oracles.KeyValue.keyValueOracle - Hadrian.Oracles.Path.pathOracle - Oracles.Dependencies.dependenciesOracles - Oracles.ModuleFiles.moduleFilesOracle From git at git.haskell.org Fri Oct 27 00:37:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Report success on IRC only if the build was fixed (462f78f) Message-ID: <20171027003745.9DBC63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/462f78f8a676120ae0505c083afa93a14ccd7418/ghc >--------------------------------------------------------------- commit 462f78f8a676120ae0505c083afa93a14ccd7418 Author: David Luposchainsky Date: Mon Jan 11 18:35:25 2016 +0100 Report success on IRC only if the build was fixed >--------------------------------------------------------------- 462f78f8a676120ae0505c083afa93a14ccd7418 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0dc23c1..4ff35ec 100644 --- a/.travis.yml +++ b/.travis.yml @@ -72,7 +72,7 @@ cache: notifications: irc: - on_success: always # always/never/change + on_success: change # always/never/change on_failure: always channels: - "chat.freenode.net#shaking-up-ghc" From git at git.haskell.org Fri Oct 27 00:37:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #152 from snowleopard/report-on-fix (27f303f) Message-ID: <20171027003749.34B673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27f303f3cedbd506c7373318e4f785354dc6ddaf/ghc >--------------------------------------------------------------- commit 27f303f3cedbd506c7373318e4f785354dc6ddaf Merge: 9178de2 462f78f Author: Andrey Mokhov Date: Mon Jan 11 17:51:16 2016 +0000 Merge pull request #152 from snowleopard/report-on-fix Report success on IRC only if the build was fixed [skip ci] >--------------------------------------------------------------- 27f303f3cedbd506c7373318e4f785354dc6ddaf .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:37:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: build.cabal.sh: Use CABAL variable (fd48c37) Message-ID: <20171027003750.5A23E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd48c372feb33e9c58c19c04929f9c63492c3b4d/ghc >--------------------------------------------------------------- commit fd48c372feb33e9c58c19c04929f9c63492c3b4d Author: Kai Harries Date: Sun Jul 24 12:15:55 2016 +0200 build.cabal.sh: Use CABAL variable >--------------------------------------------------------------- fd48c372feb33e9c58c19c04929f9c63492c3b4d build.cabal.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index be2a117..3b6bef5 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -63,7 +63,7 @@ else "$CABAL" sandbox init ( cd ../libraries/Cabal/Cabal ln -s "$absoluteRoot/cabal.sandbox.config" cabal.sandbox.config - cabal install + "$CABAL" install rm cabal.sandbox.config ) "$CABAL" install \ From git at git.haskell.org Fri Oct 27 00:37:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use in-tree cabal in build.cabal.sh (works for cabal < 1.24) (fc4c968) Message-ID: <20171027003746.6AC853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fc4c968378c1d4467cf59e8bbaefa66f473526f7/ghc >--------------------------------------------------------------- commit fc4c968378c1d4467cf59e8bbaefa66f473526f7 Author: Kai Harries Date: Sun Jul 24 11:37:08 2016 +0200 Use in-tree cabal in build.cabal.sh (works for cabal < 1.24) Partial fix of #274 This installs the in-tree Cabal into the cabal-sandbox before building hadrian itself. This only works if the installed cabal version is < 1.24, because I have not yet figured out how it can be done with the newly introduced `new-build` command. >--------------------------------------------------------------- fc4c968378c1d4467cf59e8bbaefa66f473526f7 build.cabal.sh | 5 +++++ hadrian.cabal | 2 +- 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index 4a24dac..be2a117 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -61,6 +61,11 @@ else # Initialize sandbox if necessary if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then "$CABAL" sandbox init + ( cd ../libraries/Cabal/Cabal + ln -s "$absoluteRoot/cabal.sandbox.config" cabal.sandbox.config + cabal install + rm cabal.sandbox.config + ) "$CABAL" install \ --dependencies-only \ --disable-library-profiling \ diff --git a/hadrian.cabal b/hadrian.cabal index 63bd164..c07cef1 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* || == 1.24.* || == 1.25.* + , Cabal >= 1.25 , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 00:37:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch off -split-objs by default, fix #153. (1b226d9) Message-ID: <20171027003752.F04D03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b226d992e53e3dee36fbfe22c0218477bc2bacb/ghc >--------------------------------------------------------------- commit 1b226d992e53e3dee36fbfe22c0218477bc2bacb Author: Andrey Mokhov Date: Tue Jan 12 02:08:58 2016 +0000 Switch off -split-objs by default, fix #153. >--------------------------------------------------------------- 1b226d992e53e3dee36fbfe22c0218477bc2bacb src/Settings/User.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 35eb86e..3cebe13 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -62,9 +62,9 @@ trackBuildSystem = True validating :: Bool validating = False --- To switch off split objects change to 'return False' +-- To switch on split objects use 'splitObjects = defaultSplitObjects', see #153 splitObjects :: Predicate -splitObjects = defaultSplitObjects +splitObjects = return False dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Fri Oct 27 00:37:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert raising of the cabal version in the build-dependency (564b125) Message-ID: <20171027003754.562EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/564b125e3d6df089ca849392be4d97c682e4ae64/ghc >--------------------------------------------------------------- commit 564b125e3d6df089ca849392be4d97c682e4ae64 Author: Kai Harries Date: Sun Jul 24 12:24:16 2016 +0200 Revert raising of the cabal version in the build-dependency Travis was failing because it uses `cabal install --only-dependencies` in the .travis.yml >--------------------------------------------------------------- 564b125e3d6df089ca849392be4d97c682e4ae64 hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index c07cef1..63bd164 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal >= 1.25 + , Cabal == 1.22.* || == 1.24.* || == 1.25.* , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 00:37:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Extend KeyValue oracle to handle lists of values (1a0a80b) Message-ID: <20171027003746.C5D843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a0a80ba27c1ab1a8fcf388c6e286705d860f6ab/ghc >--------------------------------------------------------------- commit 1a0a80ba27c1ab1a8fcf388c6e286705d860f6ab Author: Andrey Mokhov Date: Sun Aug 13 18:26:45 2017 +0100 Extend KeyValue oracle to handle lists of values >--------------------------------------------------------------- 1a0a80ba27c1ab1a8fcf388c6e286705d860f6ab src/Hadrian/Oracles/KeyValue.hs | 46 +++++++++++++++++++++++++++++++---------- src/Oracles/Dependencies.hs | 21 ++++--------------- src/Rules.hs | 1 - 3 files changed, 39 insertions(+), 29 deletions(-) diff --git a/src/Hadrian/Oracles/KeyValue.hs b/src/Hadrian/Oracles/KeyValue.hs index b58cfda..5155e3e 100644 --- a/src/Hadrian/Oracles/KeyValue.hs +++ b/src/Hadrian/Oracles/KeyValue.hs @@ -1,6 +1,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Hadrian.Oracles.KeyValue ( - lookupValue, lookupValueOrEmpty, lookupValueOrError, keyValueOracle + lookupValue, lookupValueOrEmpty, lookupValueOrError, + lookupValues, lookupValuesOrEmpty, lookupValuesOrError, keyValueOracle ) where import Control.Monad @@ -15,28 +16,51 @@ import Hadrian.Utilities newtype KeyValue = KeyValue (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- | Lookup a value in a key-value text file, tracking the result. +newtype KeyValues = KeyValues (FilePath, String) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Lookup a value in a text file, tracking the result. Each line of the file +-- is expected to have @key = value@ format. lookupValue :: FilePath -> String -> Action (Maybe String) lookupValue file key = askOracle $ KeyValue (file, key) --- | Lookup a value in a key-value text file, tracking the result. Return the --- empty string if the key is not found. +-- | Like 'lookupValue' but returns the empty string if the key is not found. lookupValueOrEmpty :: FilePath -> String -> Action String -lookupValueOrEmpty file key = fromMaybe "" <$> askOracle (KeyValue (file, key)) +lookupValueOrEmpty file key = fromMaybe "" <$> lookupValue file key --- | Lookup a value in a key-value text file, tracking the result. Raise an --- error if the key is not found. +-- | Like 'lookupValue' but raises an error if the key is not found. lookupValueOrError :: FilePath -> String -> Action String lookupValueOrError file key = (fromMaybe $ error msg) <$> lookupValue file key where msg = "Key " ++ quote key ++ " not found in file " ++ quote file --- | This oracle reads and parses text files consisting of key-value pairs --- @key = value@ and answers 'lookupValue' queries tracking the results. +-- | Lookup a list of values in a text file, tracking the result. Each line of +-- the file is expected to have @key value1 value2 ...@ format. +lookupValues :: FilePath -> String -> Action (Maybe [String]) +lookupValues file key = askOracle $ KeyValues (file, key) + +-- | Like 'lookupValues' but returns the empty list if the key is not found. +lookupValuesOrEmpty :: FilePath -> String -> Action [String] +lookupValuesOrEmpty file key = fromMaybe [] <$> lookupValues file key + +-- | Like 'lookupValues' but raises an error if the key is not found. +lookupValuesOrError :: FilePath -> String -> Action [String] +lookupValuesOrError file key = (fromMaybe $ error msg) <$> lookupValues file key + where + msg = "Key " ++ quote key ++ " not found in file " ++ quote file + +-- | This oracle reads and parses text files to answer 'lookupValue' and +-- 'lookupValues' queries, as well as their derivatives, tracking the results. keyValueOracle :: Rules () keyValueOracle = void $ do - cache <- newCache $ \file -> do + kv <- newCache $ \file -> do need [file] putLoud $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> cache file + kvs <- newCache $ \file -> do + need [file] + putLoud $ "Reading " ++ file ++ "..." + contents <- map words <$> readFileLines file + return $ Map.fromList [ (key, values) | (key:values) <- contents ] + void $ addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> kv file + void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 748a5a2..6ed5633 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,10 +1,10 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, TupleSections #-} module Oracles.Dependencies ( fileDependencies, contextDependencies, libraryTargets, needLibrary, - dependenciesOracles, pkgDependencies, topsortPackages + pkgDependencies, topsortPackages ) where -import qualified Data.HashMap.Strict as Map +import Hadrian.Oracles.KeyValue import Base import Context @@ -14,9 +14,6 @@ import Settings import Settings.Builders.GhcCabal import Settings.Path -newtype Dependency = Dependency (FilePath, FilePath) - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -- | 'Action' @fileDependencies context file@ looks up dependencies of a @file@ -- in a generated dependency file @path/.dependencies@, where @path@ is the build -- path of the given @context at . The action returns a pair @(source, files)@, @@ -25,7 +22,7 @@ newtype Dependency = Dependency (FilePath, FilePath) fileDependencies :: Context -> FilePath -> Action (FilePath, [FilePath]) fileDependencies context obj = do let path = buildPath context -/- ".dependencies" - deps <- askOracle $ Dependency (path, obj) + deps <- lookupValues path obj case deps of Nothing -> error $ "No dependencies found for file " ++ obj Just [] -> error $ "No source file found for file " ++ obj @@ -40,8 +37,7 @@ fileDependencies context obj = do contextDependencies :: Context -> Action [Context] contextDependencies context at Context {..} = do let pkgContext = \pkg -> Context (min stage Stage1) pkg way - unpack = fromMaybe . error $ "No dependencies for " ++ show context - deps <- unpack <$> askOracle (Dependency (packageDependencies, pkgNameString package)) + deps <- lookupValuesOrError packageDependencies (pkgNameString package) pkgs <- sort <$> interpretInContext (pkgContext package) getPackages return . map pkgContext $ intersectOrd (compare . pkgNameString) pkgs deps @@ -67,15 +63,6 @@ libraryTargets context = do needLibrary :: [Context] -> Action () needLibrary cs = need =<< concatMapM libraryTargets cs --- | Oracles for the package dependencies and 'path/dist/.dependencies' files. -dependenciesOracles :: Rules () -dependenciesOracles = do - deps <- newCache $ \file -> do - putLoud $ "Reading dependencies from " ++ file ++ "..." - contents <- map words <$> readFileLines file - return $ Map.fromList [ (key, values) | (key:values) <- contents ] - void $ addOracle $ \(Dependency (file, key)) -> Map.lookup key <$> deps file - -- | Topological sort of packages according to their dependencies. -- HACK (izgzhen): See https://github.com/snowleopard/hadrian/issues/344 for details topsortPackages :: [Package] -> Action [Package] diff --git a/src/Rules.hs b/src/Rules.hs index 335c4c3..2c09e94 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -117,7 +117,6 @@ oracleRules = do Hadrian.Oracles.DirectoryContents.directoryContentsOracle Hadrian.Oracles.KeyValue.keyValueOracle Hadrian.Oracles.Path.pathOracle - Oracles.Dependencies.dependenciesOracles Oracles.ModuleFiles.moduleFilesOracle programsStage1Only :: [Package] From git at git.haskell.org Fri Oct 27 00:37:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make most extensions default, minor clean up (a56298f) Message-ID: <20171027003754.7A6B23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a56298fb9cea9f3b4d5eebdefc3d3ddced239981/ghc >--------------------------------------------------------------- commit a56298fb9cea9f3b4d5eebdefc3d3ddced239981 Author: Andrey Mokhov Date: Sun Aug 13 23:30:16 2017 +0100 Make most extensions default, minor clean up >--------------------------------------------------------------- a56298fb9cea9f3b4d5eebdefc3d3ddced239981 hadrian.cabal | 10 +++++----- src/Builder.hs | 1 - src/Context.hs | 1 - src/Expression.hs | 1 - src/GHC.hs | 2 +- src/Hadrian/Expression.hs | 3 +-- src/Hadrian/Oracles/ArgsHash.hs | 1 - src/Hadrian/Oracles/DirectoryContents.hs | 1 - src/Hadrian/Oracles/KeyValue.hs | 1 - src/Hadrian/Oracles/Path.hs | 1 - src/Hadrian/Target.hs | 1 - src/Oracles/ModuleFiles.hs | 1 - src/Package.hs | 1 - src/Rules.hs | 4 +--- src/Rules/Install.hs | 1 - src/Rules/Library.hs | 2 +- src/Rules/Selftest.hs | 1 - src/Rules/Wrappers.hs | 4 ++-- src/Settings/Install.hs | 8 +++----- src/Stage.hs | 1 - 20 files changed, 14 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a56298fb9cea9f3b4d5eebdefc3d3ddced239981 From git at git.haskell.org Fri Oct 27 00:37:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Oracles.Dependencies moving code to the library and Utilities (former Util) (1df5491) Message-ID: <20171027003750.9C0153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1df549134fdf286e374e5e3f1fef2944ea24f591/ghc >--------------------------------------------------------------- commit 1df549134fdf286e374e5e3f1fef2944ea24f591 Author: Andrey Mokhov Date: Sun Aug 13 23:20:18 2017 +0100 Drop Oracles.Dependencies moving code to the library and Utilities (former Util) >--------------------------------------------------------------- 1df549134fdf286e374e5e3f1fef2944ea24f591 hadrian.cabal | 6 +-- src/Hadrian/Oracles/KeyValue.hs | 16 +++++++- src/Oracles/Dependencies.hs | 79 --------------------------------------- src/Rules.hs | 4 +- src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 7 ++-- src/Rules/Configure.hs | 2 +- src/Rules/Data.hs | 3 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Install.hs | 3 +- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 3 +- src/Rules/Perl.hs | 2 +- src/Rules/Program.hs | 3 +- src/Rules/Register.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 2 +- src/Rules/Wrappers.hs | 2 +- src/Settings.hs | 8 +++- src/Settings/Builders/GhcCabal.hs | 9 +---- src/Settings/Packages/GhcCabal.hs | 2 +- src/{Util.hs => Utilities.hs} | 56 ++++++++++++++++++++++++++- 25 files changed, 103 insertions(+), 120 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1df549134fdf286e374e5e3f1fef2944ea24f591 From git at git.haskell.org Fri Oct 27 00:37:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Preliminary working state (5d4e182) Message-ID: <20171027003756.6942C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d4e18236b64fa400a66967cd7dbb8371b0e08b7/ghc >--------------------------------------------------------------- commit 5d4e18236b64fa400a66967cd7dbb8371b0e08b7 Author: Moritz Angermann Date: Tue Jan 12 14:56:53 2016 +0800 Preliminary working state This almost works. Yet we run into: ``` Build system error - cannot currently call askOracle: Reason: Within withResource using Resource ghc-cabal Question type: OracleQ CmdLineFlags Question value: OracleQ (CmdLineFlags ()) Move the askOracle call earlier/later ``` >--------------------------------------------------------------- 5d4e18236b64fa400a66967cd7dbb8371b0e08b7 shaking-up-ghc.cabal | 1 + src/Base.hs | 27 +++++++++++++++-- src/Main.hs | 7 ++++- src/Oracles/Config/CmdLineFlag.hs | 64 +++++++++++++++++++++++++++++++++++++++ src/Rules/Actions.hs | 20 +++++------- src/Rules/Library.hs | 9 +++--- src/Rules/Program.hs | 9 +++--- 7 files changed, 111 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5d4e18236b64fa400a66967cd7dbb8371b0e08b7 From git at git.haskell.org Fri Oct 27 00:37:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use in-tree cabal in build.cabal.sh (for cabal >= 1.24) (3724023) Message-ID: <20171027003758.0D7E63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37240234b116c9aa90a5a0e893a94813373ad158/ghc >--------------------------------------------------------------- commit 37240234b116c9aa90a5a0e893a94813373ad158 Author: Kai Harries Date: Sun Jul 24 13:48:10 2016 +0200 Use in-tree cabal in build.cabal.sh (for cabal >= 1.24) >--------------------------------------------------------------- 37240234b116c9aa90a5a0e893a94813373ad158 cabal.project | 2 ++ 1 file changed, 2 insertions(+) diff --git a/cabal.project b/cabal.project new file mode 100644 index 0000000..1ef81ca --- /dev/null +++ b/cabal.project @@ -0,0 +1,2 @@ +packages: ../libraries/Cabal/Cabal/ + ./ From git at git.haskell.org Fri Oct 27 00:37:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add default extensions to .ghci (b4977a3) Message-ID: <20171027003758.11B753A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b4977a3c7577cb135de38a20654878931e5814ea/ghc >--------------------------------------------------------------- commit b4977a3c7577cb135de38a20654878931e5814ea Author: Andrey Mokhov Date: Sun Aug 13 23:44:07 2017 +0100 Add default extensions to .ghci >--------------------------------------------------------------- b4977a3c7577cb135de38a20654878931e5814ea .ghci | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 9c0fe7a..8bb287b 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,11 @@ -:set -Wall -fno-warn-name-shadowing -isrc -i../libraries/Cabal/Cabal -XRecordWildCards +:set -Wall -fno-warn-name-shadowing -isrc -i../libraries/Cabal/Cabal +:set -XDeriveFunctor +:set -XDeriveGeneric +:set -XFlexibleInstances +:set -XGeneralizedNewtypeDeriving +:set -XLambdaCase +:set -XRecordWildCards +:set -XScopedTypeVariables +:set -XTupleSections + :load Main From git at git.haskell.org Fri Oct 27 00:37:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:37:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' into angerman/feature/build-info-flags (8dfe2b9) Message-ID: <20171027003759.E671B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8dfe2b928d8e2d8eef9f45fb148764799e844257/ghc >--------------------------------------------------------------- commit 8dfe2b928d8e2d8eef9f45fb148764799e844257 Merge: 5d4e182 27f303f Author: Moritz Angermann Date: Tue Jan 12 14:57:35 2016 +0800 Merge branch 'master' into angerman/feature/build-info-flags # Conflicts: # src/Main.hs >--------------------------------------------------------------- 8dfe2b928d8e2d8eef9f45fb148764799e844257 .appveyor.yml | 10 +++++++++- .travis.yml | 3 ++- shaking-up-ghc.cabal | 3 +++ src/Main.hs | 7 ++++++- src/Rules/Generate.hs | 9 ++++++--- src/Settings/Builders/Ar.hs | 16 ++++------------ src/Settings/Builders/DeriveConstants.hs | 14 +++++--------- src/Test.hs | 28 ++++++++++++++++++++++++++++ src/Way.hs | 2 +- 9 files changed, 64 insertions(+), 28 deletions(-) diff --cc src/Main.hs index f65483d,dea793e..6d79cb8 --- a/src/Main.hs +++ b/src/Main.hs @@@ -11,15 -11,11 +11,19 @@@ import qualified Rules.Gm import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl ++<<<<<<< HEAD +import Oracles.Config.CmdLineFlag (cmdLineOracle, flags) ++======= + import qualified Test ++>>>>>>> master main :: IO () -main = shakeArgs options rules +main = shakeArgsWith options flags $ \cmdLineFlags targets -> + return . Just $ cmdLineOracle cmdLineFlags + >> if null targets then rules else want targets + >> withoutActions rules where + rules :: Rules () rules = mconcat [ Rules.Cabal.cabalRules , Rules.Config.configRules From git at git.haskell.org Fri Oct 27 00:38:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use `add-source` instead of linking cabal.sandbox.config (ea51eaa) Message-ID: <20171027003802.1FA513A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ea51eaad8e5b8eb64183fa169224ab2df61a63b9/ghc >--------------------------------------------------------------- commit ea51eaad8e5b8eb64183fa169224ab2df61a63b9 Author: Kai Harries Date: Sun Jul 24 15:17:56 2016 +0200 Use `add-source` instead of linking cabal.sandbox.config As suggested by mpickering >--------------------------------------------------------------- ea51eaad8e5b8eb64183fa169224ab2df61a63b9 build.cabal.sh | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/build.cabal.sh b/build.cabal.sh index 3b6bef5..973cd3e 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -61,11 +61,7 @@ else # Initialize sandbox if necessary if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then "$CABAL" sandbox init - ( cd ../libraries/Cabal/Cabal - ln -s "$absoluteRoot/cabal.sandbox.config" cabal.sandbox.config - "$CABAL" install - rm cabal.sandbox.config - ) + "$CABAL" sandbox add-source ../libraries/Cabal/Cabal "$CABAL" install \ --dependencies-only \ --disable-library-profiling \ From git at git.haskell.org Fri Oct 27 00:38:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up imports (0ef2b1f) Message-ID: <20171027003802.1CED53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ef2b1f8123ba90614c24d06a0a32bda0410334e/ghc >--------------------------------------------------------------- commit 0ef2b1f8123ba90614c24d06a0a32bda0410334e Author: Andrey Mokhov Date: Mon Aug 14 00:05:10 2017 +0100 Clean up imports >--------------------------------------------------------------- 0ef2b1f8123ba90614c24d06a0a32bda0410334e src/Expression.hs | 14 ++------------ src/Hadrian/Oracles/Path.hs | 1 - src/Oracles/PackageData.hs | 5 ++--- src/Oracles/Setting.hs | 1 - src/Rules.hs | 1 - src/Rules/Install.hs | 2 +- src/Rules/Selftest.hs | 1 - src/Settings.hs | 1 - src/Settings/Install.hs | 1 - src/Utilities.hs | 1 - 10 files changed, 5 insertions(+), 23 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 34a88fb..ca8862e 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -20,25 +20,15 @@ module Expression ( getInput, getOutput, -- * Re-exports - module Data.Semigroup, - module Builder, - module Package, - module Stage, - module Way + module Base ) where -import Control.Monad.Extra -import Data.Semigroup - import qualified Hadrian.Expression as H import Hadrian.Expression hiding (Expr, Predicate, Args) -import Builder +import Base import Context (Context, vanillaContext, stageContext, getStage, getPackage, getWay) -import Package -import Stage import Target hiding (builder, inputs, outputs) -import Way -- | @Expr a@ is a computation that produces a value of type @Action a@ and can -- read parameters of the current build 'Target'. diff --git a/src/Hadrian/Oracles/Path.hs b/src/Hadrian/Oracles/Path.hs index 2c578a1..d10948b 100644 --- a/src/Hadrian/Oracles/Path.hs +++ b/src/Hadrian/Oracles/Path.hs @@ -33,7 +33,6 @@ fixAbsolutePathOnWindows path = do else return path - newtype LookupInPath = LookupInPath String deriving (Binary, Eq, Hashable, NFData, Show, Typeable) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index c813f82..208881d 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -2,10 +2,9 @@ module Oracles.PackageData ( PackageData (..), PackageDataList (..), pkgData, pkgDataList ) where -import Data.List -import Development.Shake import Hadrian.Oracles.KeyValue -import Hadrian.Utilities + +import Base data PackageData = BuildGhciLib FilePath | ComponentId FilePath diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 095dbaa..e9fe886 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -6,7 +6,6 @@ module Oracles.Setting ( topDirectory, relocatableBuild, installDocDir, installGhcLibDir, libsuf ) where -import Development.Shake import Hadrian.Expression import Hadrian.Oracles.KeyValue import Hadrian.Oracles.Path diff --git a/src/Rules.hs b/src/Rules.hs index 8a576d4..149789f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,7 +5,6 @@ import qualified Hadrian.Oracles.DirectoryContents import qualified Hadrian.Oracles.KeyValue import qualified Hadrian.Oracles.Path -import Base import Context import Expression import Flavour diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index edf2492..4b24ca2 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -5,7 +5,7 @@ import qualified System.Directory as IO import Base import Context -import Expression hiding (builder) +import Expression import GHC import Oracles.Setting import Rules diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 0112d8f..3942753 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -1,7 +1,6 @@ {-# OPTIONS_GHC -fno-warn-orphans #-} module Rules.Selftest (selftestRules) where -import Development.Shake import Test.QuickCheck import Base diff --git a/src/Settings.hs b/src/Settings.hs index 7576e7a..e285175 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -9,7 +9,6 @@ module Settings ( import Hadrian.Oracles.KeyValue import Hadrian.Oracles.Path -import Base import Context import CmdLineFlag import Expression diff --git a/src/Settings/Install.hs b/src/Settings/Install.hs index 2d18a67..086cfa2 100644 --- a/src/Settings/Install.hs +++ b/src/Settings/Install.hs @@ -1,6 +1,5 @@ module Settings.Install (installPackageDbDirectory) where -import Base import Expression import UserSettings diff --git a/src/Utilities.hs b/src/Utilities.hs index 5356c11..07b34be 100644 --- a/src/Utilities.hs +++ b/src/Utilities.hs @@ -17,7 +17,6 @@ import Hadrian.Oracles.DirectoryContents import Hadrian.Oracles.KeyValue import Hadrian.Oracles.Path -import Base import CmdLineFlag import Context import Expression hiding (builder, inputs, outputs, way, stage, package) From git at git.haskell.org Fri Oct 27 00:38:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Require Cabal 1.25 (f1f95d5) Message-ID: <20171027003822.38C783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f1f95d5e016b85411487f62d0b9603692bfcd923/ghc >--------------------------------------------------------------- commit f1f95d5e016b85411487f62d0b9603692bfcd923 Author: Andrey Mokhov Date: Fri Aug 5 17:19:36 2016 +0100 Require Cabal 1.25 See #280. >--------------------------------------------------------------- f1f95d5e016b85411487f62d0b9603692bfcd923 hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 63bd164..41cccd8 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* || == 1.24.* || == 1.25.* + , Cabal == 1.25.* , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 00:38:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow users to choose which 'make' to use. (43d5847) Message-ID: <20171027003822.64BE73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/43d5847155ff33dd67929164d49358fc82985944/ghc >--------------------------------------------------------------- commit 43d5847155ff33dd67929164d49358fc82985944 Author: Andrey Mokhov Date: Tue Jan 12 18:12:14 2016 +0000 Allow users to choose which 'make' to use. Fix #157. [skip ci] >--------------------------------------------------------------- 43d5847155ff33dd67929164d49358fc82985944 src/Rules/Actions.hs | 2 +- src/Settings/User.hs | 7 ++++++- 2 files changed, 7 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 338bec3..0600d82 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -105,7 +105,7 @@ runMake dir args = do need [dir -/- "Makefile"] let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) "make" ["-C", dir] args + quietly $ cmd Shell (EchoStdout False) makeCommand ["-C", dir] args runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 3cebe13..3d08ecd 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors, splitObjects + verboseCommands, turnWarningsIntoErrors, splitObjects, makeCommand ) where import GHC @@ -101,3 +101,8 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False + +-- | Specify which @make@ command to use, for example set to "gmake" for +-- @GNU make at . +makeCommand :: FilePath +makeCommand = "make" From git at git.haskell.org Fri Oct 27 00:38:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #154 from snowleopard/angerman/feature/build-info-flags (57c6497) Message-ID: <20171027003847.26EFA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57c6497776b08bd0548a094fa96b21977ae54254/ghc >--------------------------------------------------------------- commit 57c6497776b08bd0548a094fa96b21977ae54254 Merge: 86f3052 f794e73 Author: Andrey Mokhov Date: Tue Jan 12 22:41:37 2016 +0000 Merge pull request #154 from snowleopard/angerman/feature/build-info-flags Add Advanced render box styles [skip ci] >--------------------------------------------------------------- 57c6497776b08bd0548a094fa96b21977ae54254 shaking-up-ghc.cabal | 1 + src/Base.hs | 52 ++++++++++++++++++++++++++++++++++-- src/Main.hs | 7 ++++- src/Oracles/Config/CmdLineFlag.hs | 56 +++++++++++++++++++++++++++++++++++++++ src/Rules/Actions.hs | 20 +++++--------- src/Rules/Library.hs | 9 +++---- src/Rules/Program.hs | 11 ++++---- 7 files changed, 129 insertions(+), 27 deletions(-) From git at git.haskell.org Fri Oct 27 00:40:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to computing package version only through the Cabal library (4ce8587) Message-ID: <20171027004025.605653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ce85874126d7356b6c442e45c593797283f7108/ghc >--------------------------------------------------------------- commit 4ce85874126d7356b6c442e45c593797283f7108 Author: Andrey Mokhov Date: Sun Aug 20 17:05:30 2017 +0100 Switch to computing package version only through the Cabal library >--------------------------------------------------------------- 4ce85874126d7356b6c442e45c593797283f7108 src/Hadrian/Haskell/Cabal.hs | 36 ++++++++++++++++++++++-------------- src/Oracles/PackageData.hs | 2 -- src/Rules/Data.hs | 2 -- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 6 +++--- src/Settings/Packages/GhcCabal.hs | 4 ++-- 6 files changed, 29 insertions(+), 25 deletions(-) diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs index 02fcd82..23cfdc7 100644 --- a/src/Hadrian/Haskell/Cabal.hs +++ b/src/Hadrian/Haskell/Cabal.hs @@ -10,35 +10,43 @@ -- @.cabal@ files. ----------------------------------------------------------------------------- module Hadrian.Haskell.Cabal ( - pkgNameVersion, pkgIdentifier, pkgDependencies + pkgVersion, pkgIdentifier, pkgDependencies ) where +import Control.Monad import Development.Shake import Hadrian.Haskell.Cabal.Parse import Hadrian.Haskell.Package import Hadrian.Oracles.TextFile +import Hadrian.Utilities --- | Read the @.cabal@ file of a given package and return the package name and --- version. The @.cabal@ file is tracked. -pkgNameVersion :: Package -> Action (PackageName, String) -pkgNameVersion pkg = do +-- | Read the @.cabal@ file of a given package and return the package version. +-- The @.cabal@ file is tracked. +pkgVersion :: Package -> Action String +pkgVersion pkg = do cabal <- readCabalFile (pkgCabalFile pkg) - return (name cabal, version cabal) + return (version cabal) --- | Read the @.cabal@ file of a given package and return the package identifier. --- If the @.cabal@ file does not exist return the package name. If the @.cabal@ --- file exists it is tracked. +-- | Read the @.cabal@ file of a given package and return the package identifier, +-- e.g. @base-4.10.0.0 at . If the @.cabal@ file does not exist return just the +-- package name, e.g. @rts at . If the @.cabal@ file exists then it is tracked, and +-- furthermore we check that the recorded package name matches the name of the +-- package passed as the parameter and raise an error otherwise. pkgIdentifier :: Package -> Action String pkgIdentifier pkg = do cabalExists <- doesFileExist (pkgCabalFile pkg) - if cabalExists - then do + if not cabalExists + then return (pkgName pkg) + else do cabal <- readCabalFile (pkgCabalFile pkg) + when (pkgName pkg /= name cabal) $ + error $ "[Hadrian.Haskell.Cabal] Inconsistent package name: expected " + ++ quote (pkgName pkg) ++ ", but " ++ quote (pkgCabalFile pkg) + ++ " specifies " ++ quote (name cabal) ++ "." return $ if (null $ version cabal) - then name cabal - else name cabal ++ "-" ++ version cabal - else return (pkgName pkg) + then pkgName pkg + else pkgName pkg ++ "-" ++ version cabal -- | Read the @.cabal@ file of a given package and return the sorted list of its -- dependencies. The current version does not take care of Cabal conditionals diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 991caf1..7d98c98 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -8,7 +8,6 @@ import Base data PackageData = BuildGhciLib FilePath | Synopsis FilePath - | Version FilePath data PackageDataList = AsmSrcs FilePath | CcArgs FilePath @@ -40,7 +39,6 @@ pkgData :: PackageData -> Action String pkgData packageData = case packageData of BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" Synopsis path -> askPackageData path "SYNOPSIS" - Version path -> askPackageData path "VERSION" -- | @PackageDataList path@ is used for multiple string options separated by -- spaces, such as @path_MODULES = Data.Array Data.Array.Base ... at . diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index ef2f017..194bf62 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -61,9 +61,7 @@ generatePackageData context at Context {..} file = do cSrcs <- packageCSources package cmmSrcs <- packageCmmSources package genPath <- buildRoot <&> (-/- generatedDir) - let pkgKey = if isLibrary package then "COMPONENT_ID = " else "PROGNAME = " writeFileChanged file . unlines $ - [ pkgKey ++ pkgName package ] ++ [ "S_SRCS = " ++ unwords asmSrcs ] ++ [ "C_SRCS = " ++ unwords cSrcs ] ++ [ "CMM_SRCS = " ++ unwords cmmSrcs ] ++ diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index ba1de93..cf6bcb3 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -95,8 +95,8 @@ bootPackageConstraints = stage0 ? do bootPkgs <- expr $ stagePackages Stage0 let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- expr $ forM (sort pkgs) $ \pkg -> do - (name, version) <- pkgNameVersion pkg - return (name ++ " == " ++ version) + version <- pkgVersion pkg + return (pkgName pkg ++ " == " ++ version) pure $ concat [ ["--constraint", c] | c <- constraints ] cppArgs :: Args diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 7319f80..bc3ebf4 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -1,6 +1,7 @@ module Settings.Builders.Haddock (haddockBuilderArgs) where import Hadrian.Utilities +import Hadrian.Haskell.Cabal import Rules.Documentation import Settings.Builders.Common @@ -17,12 +18,11 @@ haddockBuilderArgs = builder Haddock ? do output <- getOutput pkg <- getPackage path <- getBuildPath - version <- getPkgData Version + version <- expr $ pkgVersion pkg synopsis <- getPkgData Synopsis deps <- getPkgDataList Deps haddocks <- expr . haddockDependencies =<< getContext - progPath <- expr $ buildPath (vanillaContext Stage2 haddock) - hVersion <- expr $ pkgData (Version progPath) + hVersion <- expr $ pkgVersion haddock ghcOpts <- haddockGhcArgs mconcat [ arg $ "--odir=" ++ takeDirectory output diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 0a0fe15..3c07c67 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -9,8 +9,8 @@ import Utilities ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do - cabalDeps <- expr $ stage1Dependencies cabal - (_, cabalVersion) <- expr $ pkgNameVersion cabal + cabalDeps <- expr $ stage1Dependencies cabal + cabalVersion <- expr $ pkgVersion cabal mconcat [ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps, pkg /= parsec ] , arg "--make" From git at git.haskell.org Fri Oct 27 00:40:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make error message more helpful. (b4f0b5c) Message-ID: <20171027004025.DC3A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b4f0b5c264583fbd2410fd3d720fa9004f0490b9/ghc >--------------------------------------------------------------- commit b4f0b5c264583fbd2410fd3d720fa9004f0490b9 Author: Andrey Mokhov Date: Fri Jan 15 14:48:29 2016 +0000 Make error message more helpful. [skip ci] >--------------------------------------------------------------- b4f0b5c264583fbd2410fd3d720fa9004f0490b9 src/Builder.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 353c00f..96cb608 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -93,9 +93,9 @@ builderKey builder = case builder of -- TODO: Paths to some builders should be determined using 'defaultProgramPath' builderPath :: Builder -> Action FilePath builderPath builder = do - path <- askConfigWithDefault (builderKey builder) $ - putError $ "\nCannot find path to '" ++ (builderKey builder) - ++ "' in configuration files." + path <- askConfigWithDefault (builderKey builder) . putError $ + "\nCannot find path to '" ++ (builderKey builder) + ++ "' in configuration files. Have you forgot to run configure?" windows <- windowsHost case (path, windows) of ("", _) -> return path From git at git.haskell.org Fri Oct 27 00:40:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop TODOs (456a10b) Message-ID: <20171027004028.7498E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/456a10bc8d12b8b2ac17c28279f35f5b675702d8/ghc >--------------------------------------------------------------- commit 456a10bc8d12b8b2ac17c28279f35f5b675702d8 Author: Andrey Mokhov Date: Mon Oct 3 01:21:11 2016 +0900 Drop TODOs See #113 >--------------------------------------------------------------- 456a10bc8d12b8b2ac17c28279f35f5b675702d8 src/Rules/Generate.hs | 1 - src/Rules/Library.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 1 - 3 files changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index d7068cf..266141f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -40,7 +40,6 @@ primopsTxt stage = buildPath (vanillaContext stage compiler) -/- "primops.txt" platformH :: Stage -> FilePath platformH stage = buildPath (vanillaContext stage compiler) -/- "ghc_boot_platform.h" --- TODO: move generated files to buildRootPath, see #113 includesDependencies :: [FilePath] includesDependencies = fmap (generatedPath -/-) [ "ghcautoconf.h" diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index c2d56b4..00a6be2 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -97,6 +97,6 @@ hSources context = do extraObjects :: Context -> Action [FilePath] extraObjects context | context == gmpContext = do - need [gmpLibraryH] -- TODO: Move this dependency elsewhere, #113? + need [gmpLibraryH] map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 7de3846..93ab4ed 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -6,7 +6,6 @@ import Oracles.Config.Setting import Predicate import Settings.Paths --- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" -- libraries/integer-gmp_CONFIGURE_OPTS += --with-gmp-framework-preferred From git at git.haskell.org Fri Oct 27 00:40:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compute package synopsis directly from Cabal files (9105fc6) Message-ID: <20171027004028.C82893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9105fc6a676cbd97b26ec5edb86a15e681073cf9/ghc >--------------------------------------------------------------- commit 9105fc6a676cbd97b26ec5edb86a15e681073cf9 Author: Andrey Mokhov Date: Sun Aug 20 17:58:01 2017 +0100 Compute package synopsis directly from Cabal files >--------------------------------------------------------------- 9105fc6a676cbd97b26ec5edb86a15e681073cf9 src/Hadrian/Haskell/Cabal.hs | 16 ++++++++++++++-- src/Hadrian/Haskell/Cabal/Parse.hs | 8 +++++--- src/Hadrian/Utilities.hs | 23 +++++++++++++++-------- src/Oracles/PackageData.hs | 2 -- src/Rules/Data.hs | 3 +-- src/Rules/Library.hs | 6 +++--- src/Rules/Program.hs | 8 +++----- src/Settings/Builders/Haddock.hs | 2 +- 8 files changed, 42 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9105fc6a676cbd97b26ec5edb86a15e681073cf9 From git at git.haskell.org Fri Oct 27 00:40:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't track integer-gmp.buildinfo. (d684612) Message-ID: <20171027004029.7532A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6846121743a4b61cb2cef6d57afa322b3fb6076/ghc >--------------------------------------------------------------- commit d6846121743a4b61cb2cef6d57afa322b3fb6076 Author: Andrey Mokhov Date: Fri Jan 15 16:07:28 2016 +0000 Don't track integer-gmp.buildinfo. See #173. >--------------------------------------------------------------- d6846121743a4b61cb2cef6d57afa322b3fb6076 src/Rules/Gmp.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index cfd8c53..d8cf707 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -82,18 +82,19 @@ gmpRules = do createDirectory $ takeDirectory gmpLibraryH -- We don't use system GMP on Windows. TODO: fix? + -- TODO: we do not track "config.mk" and "integer-gmp.buildinfo", see #173 windows <- windowsHost configMk <- liftIO . readFile $ gmpBase -/- "config.mk" if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - buildInfo <- readFileLines $ pkgPath integerGmp -/- "integer-gmp.buildinfo" + buildInfo <- liftIO . readFile $ pkgPath integerGmp -/- "integer-gmp.buildinfo" let prefix = "extra-libraries: " libs s = case stripPrefix prefix s of Nothing -> [] Just value -> words value - writeFileChanged gmpLibNameCache . unlines $ concatMap libs buildInfo + writeFileChanged gmpLibNameCache . unlines . concatMap libs $ lines buildInfo else do putBuild "| No GMP library/framework detected; in tree GMP will be built" writeFileChanged gmpLibNameCache "" From git at git.haskell.org Fri Oct 27 00:40:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix generated includes (c6cb106) Message-ID: <20171027004031.E94833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6cb106cf0d437ff1352b95b57224d6a2c2a4744/ghc >--------------------------------------------------------------- commit c6cb106cf0d437ff1352b95b57224d6a2c2a4744 Author: Andrey Mokhov Date: Mon Oct 3 04:58:54 2016 +0900 Fix generated includes See #113. >--------------------------------------------------------------- c6cb106cf0d437ff1352b95b57224d6a2c2a4744 src/Rules/Generate.hs | 4 ++++ src/Settings/Builders/Common.hs | 2 ++ src/Settings/Builders/DeriveConstants.hs | 2 ++ src/Settings/Builders/Ghc.hs | 2 ++ src/Settings/Builders/GhcCabal.hs | 4 +++- src/Settings/Packages/Compiler.hs | 4 +--- src/Settings/Packages/Rts.hs | 3 +-- 7 files changed, 15 insertions(+), 6 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 266141f..035318f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -45,6 +45,8 @@ includesDependencies = fmap (generatedPath -/-) [ "ghcautoconf.h" , "ghcplatform.h" , "ghcversion.h" ] + ++ -- TODO: This is a temporary fix, see #113: + [ "includes/ghcversion.h"] ghcPrimDependencies :: Expr [FilePath] ghcPrimDependencies = do @@ -165,6 +167,8 @@ copyRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs rtsBuildPath -/- "sm/Evac_thr.c" %> copyFile (pkgPath rts -/- "sm/Evac.c") rtsBuildPath -/- "sm/Scav_thr.c" %> copyFile (pkgPath rts -/- "sm/Scav.c") + -- TODO: This is a temporary fix, see #113: + "includes/ghcversion.h" <~ generatedPath where file <~ dir = file %> copyFile (dir -/- takeFileName file) diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 49e5f30..698b343 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -9,6 +9,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.PackageData import Settings +import Settings.Paths import UserSettings cIncludeArgs :: Args @@ -18,6 +19,7 @@ cIncludeArgs = do incDirs <- getPkgDataList IncludeDirs depDirs <- getPkgDataList DepIncludeDirs mconcat [ arg "-Iincludes" + , arg $ "-I" ++ generatedPath , arg $ "-I" ++ path , arg $ "-I" ++ path -/- "autogen" , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 9cfd9dd..621a225 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -5,6 +5,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Predicate import Settings.Builders.Common +import Settings.Paths -- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? deriveConstantsBuilderArgs :: Args @@ -34,5 +35,6 @@ includeCcArgs = mconcat , flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER" , arg "-Irts" , arg "-Iincludes" + , arg $ "-I" ++ generatedPath , notM ghcWithSMP ? arg "-DNOSMP" , arg "-fcommon" ] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index d2cd761..475c9b3 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -135,6 +135,8 @@ includeGhcArgs = do , arg $ "-i" ++ path -/- "autogen" , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] , cIncludeArgs + , arg $ "-I" ++ generatedPath + , arg $ "-optc-I" ++ generatedPath , arg "-optP-include" , arg $ "-optP" ++ path -/- "autogen/cabal_macros.h" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 7a3b3a0..14c1254 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -64,10 +64,12 @@ libraryArgs = do -- TODO: WARNING: unrecognized options: --with-compiler, --with-gmp-libraries, --with-cc configureArgs :: Args configureArgs = do + top <- getTopDirectory let conf key = appendSubD $ "--configure-option=" ++ key cFlags = mconcat [ cArgs , remove ["-Werror"] - , argStagedSettingList ConfCcArgs ] + , argStagedSettingList ConfCcArgs + , arg $ "-I" ++ top -/- generatedPath ] ldFlags = ldArgs <> (argStagedSettingList ConfGccLinkerArgs) cppFlags = cppArgs <> (argStagedSettingList ConfCppArgs) mconcat diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 1866a1b..df9020d 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -16,9 +16,7 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder Ghc ? mconcat - [ arg $ "-I" ++ path - , arg $ "-optP-I" ++ generatedPath ] + , builder Ghc ? arg ("-I" ++ path) , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index a4ed2a1..f3f2e43 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -9,7 +9,6 @@ import Oracles.Config.Setting import Oracles.WindowsPath import Predicate import Settings -import Settings.Paths rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" @@ -92,7 +91,7 @@ rtsPackageArgs = package rts ? do , input "//Evac_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] , input "//Scav_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] ] - , builder Ghc ? arg "-Irts" <> arg ("-I" ++ generatedPath) + , builder Ghc ? arg "-Irts" , builder (GhcPkg Stage1) ? mconcat [ remove ["rts/stage1/inplace-pkg-config"] -- TODO: fix, see #113 From git at git.haskell.org Fri Oct 27 00:40:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install rule: copy gmp header (#398) (8972c19) Message-ID: <20171027004032.62D383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8972c19ff590b61510677ea4057c2021869c4a74/ghc >--------------------------------------------------------------- commit 8972c19ff590b61510677ea4057c2021869c4a74 Author: Zhen Zhang Date: Wed Aug 23 18:51:25 2017 +0800 Install rule: copy gmp header (#398) >--------------------------------------------------------------- 8972c19ff590b61510677ea4057c2021869c4a74 src/Rules/Install.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 0d7336b..4858f40 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -185,6 +185,9 @@ installPackages = do installLibPkgs <- topsortPackages (filter isLibrary activePackages) + -- TODO (izgzhen): figure out what is the root cause of the missing ghc-gmp.h error + copyFile (pkgPath integerGmp -/- "gmp/ghc-gmp.h") (pkgPath integerGmp -/- "ghc-gmp.h") + forM_ installLibPkgs $ \pkg -> do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do From git at git.haskell.org Fri Oct 27 00:40:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Make builder. (ba5f163) Message-ID: <20171027004033.155853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba5f16377f357f009e932b1301a0e3fbcc4b8578/ghc >--------------------------------------------------------------- commit ba5f16377f357f009e932b1301a0e3fbcc4b8578 Author: Andrey Mokhov Date: Fri Jan 15 23:13:05 2016 +0000 Add Make builder. See #167. >--------------------------------------------------------------- ba5f16377f357f009e932b1301a0e3fbcc4b8578 cfg/system.config.in | 1 + src/Builder.hs | 2 ++ 2 files changed, 3 insertions(+) diff --git a/cfg/system.config.in b/cfg/system.config.in index 4539979..dfde8e3 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -36,6 +36,7 @@ ar = @ArCmd@ happy = @HappyCmd@ hscolour = @HSCOLOUR@ ld = @LdCmd@ +make = @MakeCmd@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ diff --git a/src/Builder.hs b/src/Builder.hs index 96cb608..560f734 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -38,6 +38,7 @@ data Builder = Alex | HsCpp | Hsc2Hs | Ld + | Make | Nm | Objdump | Patch @@ -81,6 +82,7 @@ builderKey builder = case builder of Hsc2Hs -> "hsc2hs" HsCpp -> "hs-cpp" Ld -> "ld" + Make -> "make" Nm -> "nm" Objdump -> "objdump" Patch -> "patch" From git at git.haskell.org Fri Oct 27 00:40:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to ghcversion.h header (0ff86b4) Message-ID: <20171027004036.548203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ff86b4b7071cead9d50310090c86d4a18c068fa/ghc >--------------------------------------------------------------- commit 0ff86b4b7071cead9d50310090c86d4a18c068fa Author: Andrey Mokhov Date: Mon Oct 3 05:52:00 2016 +0900 Fix path to ghcversion.h header See #113. >--------------------------------------------------------------- 0ff86b4b7071cead9d50310090c86d4a18c068fa src/Rules/Generate.hs | 4 ---- src/Rules/Register.hs | 3 ++- 2 files changed, 2 insertions(+), 5 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 035318f..266141f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -45,8 +45,6 @@ includesDependencies = fmap (generatedPath -/-) [ "ghcautoconf.h" , "ghcplatform.h" , "ghcversion.h" ] - ++ -- TODO: This is a temporary fix, see #113: - [ "includes/ghcversion.h"] ghcPrimDependencies :: Expr [FilePath] ghcPrimDependencies = do @@ -167,8 +165,6 @@ copyRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs rtsBuildPath -/- "sm/Evac_thr.c" %> copyFile (pkgPath rts -/- "sm/Evac.c") rtsBuildPath -/- "sm/Scav_thr.c" %> copyFile (pkgPath rts -/- "sm/Scav.c") - -- TODO: This is a temporary fix, see #113: - "includes/ghcversion.h" <~ generatedPath where file <~ dir = file %> copyFile (dir -/- takeFileName file) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index ec33668..272e27b 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -46,7 +46,8 @@ registerPackage rs context at Context {..} = do let fixRtsConf = unlines . map ( replace "\"\"" "" - . replace "rts/dist/build" rtsBuildPath ) + . replace "rts/dist/build" rtsBuildPath + . replace "includes/dist-derivedconstants/header" generatedPath ) . filter (not . null) . lines From git at git.haskell.org Fri Oct 27 00:40:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop defaultDestDir and use Shake's verbosity to control verbose commands (#400) (b25faf5) Message-ID: <20171027004036.B02CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b25faf58f70159b741d6e13da7da329388914d65/ghc >--------------------------------------------------------------- commit b25faf58f70159b741d6e13da7da329388914d65 Author: Zhen Zhang Date: Thu Aug 24 02:44:47 2017 +0800 Drop defaultDestDir and use Shake's verbosity to control verbose commands (#400) >--------------------------------------------------------------- b25faf58f70159b741d6e13da7da329388914d65 README.md | 7 +++++-- src/UserSettings.hs | 14 ++++---------- 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/README.md b/README.md index ecf9728..ad61ef3 100644 --- a/README.md +++ b/README.md @@ -110,9 +110,12 @@ To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` tar To build and install GHC artifacts, run the `install` target. -By default, the artifacts will be installed to `` on your system. For example, -`ghc` will be installed to `/usr/local/bin`. By setting flag `--install-destdir=[DESTDIR]`, +By default, the artifacts will be installed to `` on your system +(in this case, the `DESTDIR` is empty, corresponds to the root of the file system). +For example on UNIX, `ghc` will be installed to `/usr/local/bin`. By setting flag `--install-destdir=[DESTDIR]`, you can install things to non-system path `DESTDIR/` instead. +Make sure you use correct absolute path on Windows, e.g. `C:/path`, +i.e. GHC is installed into `C:/path/usr/local` for the above example. #### Testing diff --git a/src/UserSettings.hs b/src/UserSettings.hs index d77d998..4a1db5b 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -4,7 +4,7 @@ -- accidentally commit them. module UserSettings ( userBuildRoot, userFlavours, userKnownPackages, verboseCommands, - buildProgressColour, successColour, defaultDestDir, defaultStage1Only + buildProgressColour, successColour, defaultStage1Only ) where import Hadrian.Utilities @@ -33,7 +33,9 @@ userKnownPackages = [] -- this is a 'Predicate', hence you can enable verbose output only for certain -- targets, e.g.: @verboseCommands = package ghcPrim at . verboseCommands :: Predicate -verboseCommands = return False +verboseCommands = do + verbosity <- expr getVerbosity + return $ verbosity >= Loud -- | Set colour for build progress messages (e.g. executing a build command). buildProgressColour :: BuildProgressColour @@ -43,14 +45,6 @@ buildProgressColour = BuildProgressColour (Dull, Magenta) successColour :: SuccessColour successColour = SuccessColour (Dull, Green) --- | Path to the GHC install destination. It is empty by default, which --- corresponds to the root of the file system. You can replace it by a specific --- directory. Make sure you use correct absolute path on Windows, e.g. "C:/path". --- The destination directory is used with a @prefix@, commonly @/usr/local@, --- i.e. GHC is installed into "C:/path/usr/local" for the above example. -defaultDestDir :: FilePath -defaultDestDir = "" - {- Stage1Only=YES means: - don't build ghc-stage2 (the executable) From git at git.haskell.org Fri Oct 27 00:40:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop makeCommand, use make detected by configure. (266461a) Message-ID: <20171027004037.279BB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/266461a38790c86451a441db5b308341df3c6e61/ghc >--------------------------------------------------------------- commit 266461a38790c86451a441db5b308341df3c6e61 Author: Andrey Mokhov Date: Fri Jan 15 23:57:49 2016 +0000 Drop makeCommand, use make detected by configure. Fix #167. >--------------------------------------------------------------- 266461a38790c86451a441db5b308341df3c6e61 src/Rules/Actions.hs | 21 ++++++++++++++++----- src/Rules/Gmp.hs | 1 - src/Settings/User.hs | 7 +------ 3 files changed, 17 insertions(+), 12 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index a0a88ff..429f241 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -6,18 +6,18 @@ module Rules.Actions ( ) where import qualified System.Directory as IO +import System.Console.ANSI import Base import Expression import Oracles import Oracles.ArgsHash +import Oracles.Config.CmdLineFlag (buildInfo, BuildInfoFlag(..)) import Settings import Settings.Args import Settings.Builders.Ar import qualified Target -import Oracles.Config.CmdLineFlag (buildInfo, BuildInfoFlag(..)) - -- Build a given target using an appropriate builder and acquiring necessary -- resources. Force a rebuilt if the argument list has changed since the last -- built (that is, track changes in the build system). @@ -107,15 +107,26 @@ runConfigure dir opts args = do runMake :: FilePath -> [String] -> Action () runMake dir args = do need [dir -/- "Makefile"] + path <- builderPath Make + + -- FIXME: temporary safety net for those who are not on GHC HEAD, see #167 + fixPath <- if path == "@MakeCmd@" <.> exe + then do + putColoured Red $ "You are behind GHC HEAD, make autodetection is disabled." + return "make" + else do + needBuilder False Make + return path + let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) makeCommand ["-C", dir] args + putBuild $ "| Run " ++ fixPath ++ " " ++ note ++ " in " ++ dir ++ "..." + quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch need [file] - needBuilder False Patch + needBuilder False Patch -- TODO: add a specialised version ~needBuilderFalse? path <- builderPath Patch putBuild $ "| Apply patch " ++ file quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index d8cf707..8df337b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -109,7 +109,6 @@ gmpRules = do ++ "(found: " ++ show tarballs ++ ")." need tarballs - createDirectory gmpBuildPath build $ fullTarget gmpTarget Tar tarballs [gmpBuildPath] forM_ gmpPatches $ \src -> do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 3d08ecd..3cebe13 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,7 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors, splitObjects, makeCommand + verboseCommands, turnWarningsIntoErrors, splitObjects ) where import GHC @@ -101,8 +101,3 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False - --- | Specify which @make@ command to use, for example set to "gmake" for --- @GNU make at . -makeCommand :: FilePath -makeCommand = "make" From git at git.haskell.org Fri Oct 27 00:40:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass configure Cc and Cpp options to GHC (79575b3) Message-ID: <20171027004040.41D3B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79575b395e32de2ad6dec3bf4e11d30767779ee6/ghc >--------------------------------------------------------------- commit 79575b395e32de2ad6dec3bf4e11d30767779ee6 Author: Andrey Mokhov Date: Sun Oct 2 23:30:15 2016 +0100 Pass configure Cc and Cpp options to GHC >--------------------------------------------------------------- 79575b395e32de2ad6dec3bf4e11d30767779ee6 src/Settings/Builders/Ghc.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 475c9b3..6eaf8ae 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -78,7 +78,8 @@ commonGhcArgs :: Args commonGhcArgs = do way <- getWay path <- getBuildPath - hsArgs <- getPkgDataList HsArgs + confCc <- getSettingList . ConfCcArgs =<< getStage + confCpp <- getSettingList . ConfCppArgs =<< getStage cppArgs <- getPkgDataList CppArgs mconcat [ arg "-hisuf", arg $ hisuf way , arg "-osuf" , arg $ osuf way @@ -86,7 +87,9 @@ commonGhcArgs = do , wayGhcArgs , packageGhcArgs , includeGhcArgs - , append hsArgs + , append =<< getPkgDataList HsArgs + , append $ map ("-optc" ++) confCc + , append $ map ("-optP" ++) confCpp , append $ map ("-optP" ++) cppArgs , arg "-odir" , arg path , arg "-hidir" , arg path From git at git.haskell.org Fri Oct 27 00:40:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove unnecessary use of -DGENERICS flag (#402) (f189ed4) Message-ID: <20171027004040.7C9543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f189ed4db11f35a9f73e8e7bf7ae311a734aefb0/ghc >--------------------------------------------------------------- commit f189ed4db11f35a9f73e8e7bf7ae311a734aefb0 Author: Ryan Scott Date: Sat Aug 26 11:16:04 2017 -0400 Remove unnecessary use of -DGENERICS flag (#402) Mirroring a change made to GHC in http://git.haskell.org/ghc.git/commit/a28a55211d6fb8d3182b0a9e47656ff9ca8a3766 >--------------------------------------------------------------- f189ed4db11f35a9f73e8e7bf7ae311a734aefb0 src/Settings/Packages/GhcCabal.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 3c07c67..dba4f9b 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -18,7 +18,6 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" - , arg "-DGENERICS" , arg "-optP-include" , arg $ "-optP" ++ pkgPath ghcCabal -/- "cabal_macros_boot.h" , arg "-ilibraries/Cabal/Cabal" From git at git.haskell.org Fri Oct 27 00:40:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need make (fails on Windows). (ba74f58) Message-ID: <20171027004040.BFE513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba74f58ab49363b488eef09e2b78c85302b61427/ghc >--------------------------------------------------------------- commit ba74f58ab49363b488eef09e2b78c85302b61427 Author: Andrey Mokhov Date: Sat Jan 16 00:51:33 2016 +0000 Don't need make (fails on Windows). See #167. >--------------------------------------------------------------- ba74f58ab49363b488eef09e2b78c85302b61427 src/Rules/Actions.hs | 7 +++---- src/Settings/Builders/Ghc.hs | 6 ++++-- 2 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 429f241..21d134f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -110,16 +110,15 @@ runMake dir args = do path <- builderPath Make -- FIXME: temporary safety net for those who are not on GHC HEAD, see #167 + -- TODO: add need [path] once lookupInPath is enabled on Windows fixPath <- if path == "@MakeCmd@" <.> exe then do putColoured Red $ "You are behind GHC HEAD, make autodetection is disabled." return "make" - else do - needBuilder False Make - return path + else return path let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run " ++ fixPath ++ " " ++ note ++ " in " ++ dir ++ "..." + putBuild $ "| Run " ++ fixPath ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 40b5a0f..2e40bcb 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -24,7 +24,8 @@ ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output libs <- getPkgDataList DepExtraLibs gmpLibs <- lift $ readFileLines gmpLibNameCache libDirs <- getPkgDataList DepLibDirs @@ -40,7 +41,8 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" , append =<< getInputs - , arg "-o", arg =<< getOutput ] + , buildHi ? append ["-fno-code", "-fwrite-interface"] + , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do From git at git.haskell.org Fri Oct 27 00:40:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to Cabal library changes (10154e7) Message-ID: <20171027004044.368643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/10154e73137208ba1808c4b19a9e507e0943de8f/ghc >--------------------------------------------------------------- commit 10154e73137208ba1808c4b19a9e507e0943de8f Author: Andrey Mokhov Date: Mon Oct 3 09:30:05 2016 +0100 Adapt to Cabal library changes >--------------------------------------------------------------- 10154e73137208ba1808c4b19a9e507e0943de8f src/Rules/Cabal.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index ed72f93..e12ab33 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,10 +1,11 @@ module Rules.Cabal (cabalRules) where -import Data.Version import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse +import Distribution.Text import Distribution.Verbosity +import Text.PrettyPrint import Base import Expression @@ -22,9 +23,8 @@ cabalRules = do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg let identifier = package . packageDescription $ pd - version = showVersion . pkgVersion $ identifier - DP.PackageName name = DP.pkgName identifier - return $ name ++ " == " ++ version + version = render . disp . pkgVersion $ identifier + return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version writeFileChanged out . unlines $ constraints -- Cache package dependencies. @@ -38,7 +38,7 @@ cabalRules = do let depsLib = collectDeps $ condLibrary pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes - depNames = [ name | Dependency (DP.PackageName name) _ <- deps ] + depNames = [ unPackageName name | Dependency name _ <- deps ] return . unwords $ pkgNameString pkg : sort depNames writeFileChanged out . unlines $ pkgDeps From git at git.haskell.org Fri Oct 27 00:40:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Undo irrelevant changes in previous commit. (f33acd3) Message-ID: <20171027004044.903023A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f33acd3ee4d702751a4ce766efa57e02666f926a/ghc >--------------------------------------------------------------- commit f33acd3ee4d702751a4ce766efa57e02666f926a Author: Andrey Mokhov Date: Sat Jan 16 00:56:11 2016 +0000 Undo irrelevant changes in previous commit. See #167. >--------------------------------------------------------------- f33acd3ee4d702751a4ce766efa57e02666f926a src/Settings/Builders/Ghc.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 2e40bcb..40b5a0f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -24,8 +24,7 @@ ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output - buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output libs <- getPkgDataList DepExtraLibs gmpLibs <- lift $ readFileLines gmpLibNameCache libDirs <- getPkgDataList DepLibDirs @@ -41,8 +40,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] , buildObj ? arg "-c" , append =<< getInputs - , buildHi ? append ["-fno-code", "-fwrite-interface"] - , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] + , arg "-o", arg =<< getOutput ] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do From git at git.haskell.org Fri Oct 27 00:40:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop mkUserGuidePart (74a6561) Message-ID: <20171027004044.ACD063A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/74a6561d67efe0d2719072cb15885a87fae35696/ghc >--------------------------------------------------------------- commit 74a6561d67efe0d2719072cb15885a87fae35696 Author: Andrey Mokhov Date: Sat Aug 26 17:34:23 2017 +0100 Drop mkUserGuidePart See #402 >--------------------------------------------------------------- 74a6561d67efe0d2719072cb15885a87fae35696 src/GHC.hs | 15 +++++++-------- src/Settings/Default.hs | 1 - 2 files changed, 7 insertions(+), 9 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index b790983..0adf259 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -5,10 +5,10 @@ module GHC ( compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, - hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, - mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm, - templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix, - win32, xhtml, defaultKnownPackages, + hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, + parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, + terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml, + defaultKnownPackages, -- * Package information builderProvenance, programName, nonCabalContext, nonHsMainPackage, autogenPath, @@ -36,9 +36,9 @@ defaultKnownPackages = , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi - , mkUserGuidePart, mtl, parsec, parallel, pretty, primitive, process, rts - , runGhc, stm, templateHaskell, terminfo, text, time, touchy, transformers - , unlit, unix, win32, xhtml ] + , mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm + , templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix + , win32, xhtml ] -- | Package definitions, see 'Package'. array = lib "array" @@ -77,7 +77,6 @@ integerGmp = lib "integer-gmp" integerSimple = lib "integer-simple" iservBin = prg "iserv-bin" `setPath` "iserv" libffi = top "libffi" -mkUserGuidePart = util "mkUserGuidePart" mtl = lib "mtl" parsec = lib "parsec" parallel = lib "parallel" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index c97b79f..d28df6c 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -115,7 +115,6 @@ stage0Packages = do , hsc2hs , hp2ps , hpc - , mkUserGuidePart , mtl , parsec , templateHaskell From git at git.haskell.org Fri Oct 27 00:40:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Text.PrettyPrint dependency (4afc5a4) Message-ID: <20171027004048.A55C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4afc5a4ddf3511bfefc3abcaa15144844536d8b6/ghc >--------------------------------------------------------------- commit 4afc5a4ddf3511bfefc3abcaa15144844536d8b6 Author: Andrey Mokhov Date: Mon Oct 3 09:45:34 2016 +0100 Drop Text.PrettyPrint dependency >--------------------------------------------------------------- 4afc5a4ddf3511bfefc3abcaa15144844536d8b6 src/Rules/Cabal.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index e12ab33..69cdd51 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -5,7 +5,6 @@ import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Text import Distribution.Verbosity -import Text.PrettyPrint import Base import Expression @@ -23,7 +22,7 @@ cabalRules = do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg let identifier = package . packageDescription $ pd - version = render . disp . pkgVersion $ identifier + version = display . pkgVersion $ identifier return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version writeFileChanged out . unlines $ constraints From git at git.haskell.org Fri Oct 27 00:40:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop repeated argument (e0de028) Message-ID: <20171027004052.B2F483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e0de0283e09eab974e22c6e37f36479597f3fc78/ghc >--------------------------------------------------------------- commit e0de0283e09eab974e22c6e37f36479597f3fc78 Author: Andrey Mokhov Date: Mon Oct 3 17:23:05 2016 +0100 Drop repeated argument >--------------------------------------------------------------- e0de0283e09eab974e22c6e37f36479597f3fc78 src/Settings/Packages/Compiler.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index df9020d..f33dc18 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -16,8 +16,6 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder Ghc ? arg ("-I" ++ path) - , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) , arg "--disable-library-for-ghci" From git at git.haskell.org Fri Oct 27 00:40:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Differentiate between C and Haskell package (5ef696e) Message-ID: <20171027004049.5CA6F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe/ghc >--------------------------------------------------------------- commit 5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe Author: Andrey Mokhov Date: Sat Aug 26 23:31:31 2017 +0100 Differentiate between C and Haskell package >--------------------------------------------------------------- 5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe hadrian.cabal | 2 +- src/Base.hs | 4 +- src/Context.hs | 37 ++++++--- src/GHC.hs | 153 +++++++++++++++++++------------------ src/Hadrian/Haskell/Cabal.hs | 70 ++++++----------- src/Hadrian/Haskell/Cabal/Parse.hs | 10 +-- src/Hadrian/Haskell/Package.hs | 87 --------------------- src/Hadrian/Package.hs | 119 +++++++++++++++++++++++++++++ src/Rules/Data.hs | 2 +- src/Rules/Install.hs | 7 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Settings/Builders/Ghc.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 6 +- src/Settings/Builders/Haddock.hs | 8 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Utilities.hs | 8 +- 17 files changed, 275 insertions(+), 249 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 5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe From git at git.haskell.org Fri Oct 27 00:40:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't rerun configure for integerGmp package. (16c89e4) Message-ID: <20171027004049.3F2163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/16c89e4739ae570e6e8548ac1fe8092df6353911/ghc >--------------------------------------------------------------- commit 16c89e4739ae570e6e8548ac1fe8092df6353911 Author: Andrey Mokhov Date: Sat Jan 16 03:10:54 2016 +0000 Don't rerun configure for integerGmp package. [skip ci] >--------------------------------------------------------------- 16c89e4739ae570e6e8548ac1fe8092df6353911 src/Rules/Gmp.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 8df337b..61a0a6f 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -75,10 +75,14 @@ gmpRules = do liftIO $ removeFiles gmpBuildPath ["//*"] - -- TODO: currently we configure integerGmp package twice -- optimise - args <- configureIntGmpArguments envs <- configureEnvironment - runConfigure (pkgPath integerGmp) envs args + -- TODO: without the optimisation below we configure integerGmp package + -- twice -- think how this can be optimised (shall we solve #18 first?) + -- TODO: this is a hacky optimisation: we do not rerun configure of + -- integerGmp package if we detect the results of the previous run + unlessM (doesFileExist $ gmpBase -/- "config.mk") $ do + args <- configureIntGmpArguments + runConfigure (pkgPath integerGmp) envs args createDirectory $ takeDirectory gmpLibraryH -- We don't use system GMP on Windows. TODO: fix? From git at git.haskell.org Fri Oct 27 00:40:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify package lists (fc564b8) Message-ID: <20171027004056.99A2D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fc564b8b05ed8e01493437635266df40dd125311/ghc >--------------------------------------------------------------- commit fc564b8b05ed8e01493437635266df40dd125311 Author: Andrey Mokhov Date: Sun Aug 27 03:08:20 2017 +0100 Simplify package lists See #403 >--------------------------------------------------------------- fc564b8b05ed8e01493437635266df40dd125311 src/Expression.hs | 3 +- src/Flavour.hs | 38 +++++++++++++-------- src/GHC.hs | 79 +++++++++++++++++++++++++++++++++++++++++++- src/Rules.hs | 2 +- src/Rules/Wrappers.hs | 3 +- src/Settings.hs | 9 +++-- src/Settings/Default.hs | 75 +---------------------------------------- src/Settings/Default.hs-boot | 4 +-- src/Utilities.hs | 7 ++-- 9 files changed, 117 insertions(+), 103 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 fc564b8b05ed8e01493437635266df40dd125311 From git at git.haskell.org Fri Oct 27 00:40:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do not run CI in verbose mode (f7c9b8b) Message-ID: <20171027004053.209B23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f7c9b8bf7a9816bedaf4e65271bd4993c1571143/ghc >--------------------------------------------------------------- commit f7c9b8bf7a9816bedaf4e65271bd4993c1571143 Author: Andrey Mokhov Date: Sun Aug 27 00:47:05 2017 +0100 Do not run CI in verbose mode >--------------------------------------------------------------- f7c9b8bf7a9816bedaf4e65271bd4993c1571143 .travis.yml | 6 +++--- appveyor.yml | 2 +- circle.yml | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 48ed171..9082ef6 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - ./build.cabal.sh selftest # Build GHC - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- - os: linux env: MODE="--flavour=quickest --integer-simple" @@ -40,7 +40,7 @@ matrix: script: # Build GHC - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. @@ -56,7 +56,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- install: # Add Cabal to PATH diff --git a/appveyor.yml b/appveyor.yml index 3b2e43b..451d5d5 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -33,7 +33,7 @@ build_script: - stack exec hadrian -- --directory ".." selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- + - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-info=brief --progress-colour=never --profile=- # Test GHC binary - cd .. diff --git a/circle.yml b/circle.yml index 606664a..b038689 100644 --- a/circle.yml +++ b/circle.yml @@ -33,7 +33,7 @@ compile: - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- test: override: From git at git.haskell.org Fri Oct 27 00:40:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch compileInterfaceFilesSeparately off by default. (c9ec473) Message-ID: <20171027004056.F15973A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9ec473baba6bde9097a456e82dedfcc3bb1252e/ghc >--------------------------------------------------------------- commit c9ec473baba6bde9097a456e82dedfcc3bb1252e Author: Andrey Mokhov Date: Sat Jan 16 03:12:55 2016 +0000 Switch compileInterfaceFilesSeparately off by default. See #174. >--------------------------------------------------------------- c9ec473baba6bde9097a456e82dedfcc3bb1252e src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 5b82571..2a1471d 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -105,4 +105,4 @@ turnWarningsIntoErrors = return False -- | Decouple the compilation of @*.hi@ and @*.o@ files by setting to True. compileInterfaceFilesSeparately :: Bool -compileInterfaceFilesSeparately = True +compileInterfaceFilesSeparately = False From git at git.haskell.org Fri Oct 27 00:41:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor GHC/user packages, move builder-specific functions into Builder (0781e16) Message-ID: <20171027004100.93D9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0781e16f1184adc1b35921924326df410ded3e31/ghc >--------------------------------------------------------------- commit 0781e16f1184adc1b35921924326df410ded3e31 Author: Andrey Mokhov Date: Mon Aug 28 01:56:06 2017 +0100 Refactor GHC/user packages, move builder-specific functions into Builder See #403 >--------------------------------------------------------------- 0781e16f1184adc1b35921924326df410ded3e31 src/Base.hs | 2 - src/Builder.hs | 91 +++++++++++++++++++++++++++++++++++- src/Expression.hs | 4 +- src/GHC.hs | 97 +++++++++++---------------------------- src/Oracles/ModuleFiles.hs | 1 + src/Rules.hs | 6 ++- src/Rules/Documentation.hs | 2 +- src/Rules/Perl.hs | 2 + src/Rules/SourceDist.hs | 1 + src/Settings.hs | 37 ++------------- src/Settings/Builders/Ghc.hs | 6 +-- src/Settings/Builders/GhcCabal.hs | 10 ++-- src/Target.hs | 3 +- src/UserSettings.hs | 8 ++-- src/Utilities.hs | 13 +----- 15 files changed, 148 insertions(+), 135 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 0781e16f1184adc1b35921924326df410ded3e31 From git at git.haskell.org Fri Oct 27 00:40:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for separate interface file compilation. (6b532ba) Message-ID: <20171027004053.1114E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b532baa0dd71e5c61229c0be832d871bf0bf705/ghc >--------------------------------------------------------------- commit 6b532baa0dd71e5c61229c0be832d871bf0bf705 Author: Andrey Mokhov Date: Sat Jan 16 03:11:31 2016 +0000 Add support for separate interface file compilation. See #174. >--------------------------------------------------------------- 6b532baa0dd71e5c61229c0be832d871bf0bf705 src/Rules/Compile.hs | 16 ++++++++++++++-- src/Settings/Builders/Ghc.hs | 15 +++++++++------ src/Settings/User.hs | 7 ++++++- 3 files changed, 29 insertions(+), 9 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 2fb315c..2065415 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,10 +12,22 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let buildPath = targetPath stage pkg -/- "build" matchBuildResult buildPath "hi" ?> \hi -> - need [ hi -<.> osuf (detectWay hi) ] + if compileInterfaceFilesSeparately + then do + let way = detectWay hi + (src, deps) <- dependencies buildPath $ hi -<.> osuf way + need $ src : deps + build $ fullTargetWithWay target (Ghc stage) way [src] [hi] + else need [ hi -<.> osuf (detectWay hi) ] matchBuildResult buildPath "hi-boot" ?> \hiboot -> - need [ hiboot -<.> obootsuf (detectWay hiboot) ] + if compileInterfaceFilesSeparately + then do + let way = detectWay hiboot + (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf way + need $ src : deps + build $ fullTargetWithWay target (Ghc stage) way [src] [hiboot] + else need [ hiboot -<.> obootsuf (detectWay hiboot) ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) matchBuildResult buildPath "o" ?> \obj -> do diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 40b5a0f..0f1fc32 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -24,7 +24,9 @@ ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput way <- getWay - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output + buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output + buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs gmpLibs <- lift $ readFileLines gmpLibNameCache libDirs <- getPkgDataList DepLibDirs @@ -35,12 +37,13 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , not buildObj ? arg "-no-auto-link-packages" - , not buildObj ? append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] - , not buildObj ? append [ "-optl-L" ++ dir | dir <- libDirs ] - , buildObj ? arg "-c" + , buildProg ? arg "-no-auto-link-packages" + , buildProg ? append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] + , buildProg ? append [ "-optl-L" ++ dir | dir <- libDirs ] + , not buildProg ? arg "-c" , append =<< getInputs - , arg "-o", arg =<< getOutput ] + , buildHi ? append ["-fno-code", "-fwrite-interface"] + , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 3cebe13..5b82571 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -3,7 +3,8 @@ module Settings.User ( userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, - verboseCommands, turnWarningsIntoErrors, splitObjects + verboseCommands, turnWarningsIntoErrors, splitObjects, + compileInterfaceFilesSeparately ) where import GHC @@ -101,3 +102,7 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False + +-- | Decouple the compilation of @*.hi@ and @*.o@ files by setting to True. +compileInterfaceFilesSeparately :: Bool +compileInterfaceFilesSeparately = True From git at git.haskell.org Fri Oct 27 00:41:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix lint error on doesFileExist 'config.mk'. (f63e9db) Message-ID: <20171027004101.1F23B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f63e9db131bfd9860db988b01d4a581a6541d796/ghc >--------------------------------------------------------------- commit f63e9db131bfd9860db988b01d4a581a6541d796 Author: Andrey Mokhov Date: Sat Jan 16 12:16:29 2016 +0000 Fix lint error on doesFileExist 'config.mk'. >--------------------------------------------------------------- f63e9db131bfd9860db988b01d4a581a6541d796 src/Rules/Gmp.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 61a0a6f..ec14b36 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -2,6 +2,8 @@ module Rules.Gmp ( gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH, gmpDependencies ) where +import qualified System.Directory as IO + import Base import Expression import GHC @@ -80,7 +82,7 @@ gmpRules = do -- twice -- think how this can be optimised (shall we solve #18 first?) -- TODO: this is a hacky optimisation: we do not rerun configure of -- integerGmp package if we detect the results of the previous run - unlessM (doesFileExist $ gmpBase -/- "config.mk") $ do + unlessM (liftIO . IO.doesFileExist $ gmpBase -/- "config.mk") $ do args <- configureIntGmpArguments runConfigure (pkgPath integerGmp) envs args From git at git.haskell.org Fri Oct 27 00:41:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add cross compilation (#401) (cbc2f63) Message-ID: <20171027004105.2067C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbc2f63dc60e084ffda3557c64a68856de924634/ghc >--------------------------------------------------------------- commit cbc2f63dc60e084ffda3557c64a68856de924634 Author: Zhen Zhang Date: Mon Aug 28 18:26:27 2017 +0800 Add cross compilation (#401) Tested with arm-linux-gnueabihf. >--------------------------------------------------------------- cbc2f63dc60e084ffda3557c64a68856de924634 doc/cross-compile.md | 57 ++++++++++++++++++++++++++++++++++++++ hadrian.cabal | 2 ++ src/Oracles/Flag.hs | 5 +--- src/Rules.hs | 1 + src/Settings.hs | 7 +---- src/Settings/Builders/Common.hs | 3 +- src/Settings/Default.hs | 6 +++- src/Settings/Packages/Compiler.hs | 2 ++ src/Settings/Packages/Ghc.hs | 4 ++- src/Settings/Packages/GhcPkg.hs | 8 ++++++ src/Settings/Packages/Haskeline.hs | 10 +++++++ src/UserSettings.hs | 12 ++++++-- 12 files changed, 101 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 cbc2f63dc60e084ffda3557c64a68856de924634 From git at git.haskell.org Fri Oct 27 00:41:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor libffi build rule (c391842) Message-ID: <20171027004100.E66463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3918421098ab7da0d6c62689ccfbe37abe26b24/ghc >--------------------------------------------------------------- commit c3918421098ab7da0d6c62689ccfbe37abe26b24 Author: Andrey Mokhov Date: Mon Oct 3 18:22:48 2016 +0100 Refactor libffi build rule See #289 >--------------------------------------------------------------- c3918421098ab7da0d6c62689ccfbe37abe26b24 src/Rules/Libffi.hs | 79 ++++++++++++++++++++++++++--------------------------- 1 file changed, 39 insertions(+), 40 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 4434f50..5ca17ea 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -6,6 +6,7 @@ import Expression import GHC import Oracles.Config.Flag import Oracles.Config.Setting +import Oracles.WindowsPath import Rules.Actions import Settings.Builders.Common import Settings.Packages.Rts @@ -30,11 +31,11 @@ libffiLibrary = libffiBuildPath -/- "inst/lib/libffi.a" libffiMakefile :: FilePath libffiMakefile = libffiBuildPath -/- "Makefile" -fixLibffiMakefile :: String -> String -fixLibffiMakefile = +fixLibffiMakefile :: FilePath -> String -> String +fixLibffiMakefile top = replace "-MD" "-MMD" . replace "@toolexeclibdir@" "$(libdir)" - . replace "@INSTALL@" "$(subst ../install-sh,C:/msys/home/chEEtah/ghc/install-sh, at INSTALL@)" + . replace "@INSTALL@" ("$(subst ../install-sh," ++ top ++ "/install-sh, at INSTALL@)") -- TODO: remove code duplication (see Settings/Builders/GhcCabal.hs) -- TODO: check code duplication w.r.t. ConfCcArgs @@ -53,12 +54,9 @@ configureEnvironment = do , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w" , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ] --- TODO: remove code duplication (need sourcePath) --- TODO: split into multiple rules libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - need [sourcePath -/- "Rules/Libffi.hs"] useSystemFfi <- flag UseSystemFfi if useSystemFfi then do @@ -68,44 +66,45 @@ libffiRules = do copyFile (ffiIncludeDir -/- file) (rtsBuildPath -/- file) putSuccess $ "| Successfully copied system FFI library header files" else do - removeDirectory libffiBuildPath - createDirectory $ buildRootPath -/- stageString Stage0 - - tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "libffiRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - - need [tarball] - let libname = dropExtension . dropExtension $ takeFileName tarball - - removeDirectory (buildRootPath -/- libname) - -- TODO: Simplify. - actionFinally (do - build $ Target libffiContext Tar [tarball] [buildRootPath] - moveDirectory (buildRootPath -/- libname) libffiBuildPath) $ - removeFiles buildRootPath [libname "*"] - - fixFile (libffiMakefile <.> "in") fixLibffiMakefile - - forM_ ["config.guess", "config.sub"] $ \file -> - copyFile file (libffiBuildPath -/- file) - - env <- configureEnvironment - buildWithCmdOptions env $ - Target libffiContext (Configure libffiBuildPath) - [libffiMakefile <.> "in"] [libffiMakefile] - - -- The old build system did runMake libffiBuildPath ["MAKEFLAGS="] - -- TODO: Find out why. It seems redundant, so I removed it. build $ Target libffiContext (Make libffiBuildPath) [] [] - let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" - forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - copyFile (ffiHDir -/- file) (rtsBuildPath -/- file) + hs <- getDirectoryFiles "" [libffiBuildPath -/- "inst/lib/*/include/*"] + forM_ hs $ \header -> + copyFile header (rtsBuildPath -/- takeFileName header) libffiName <- rtsLibffiLibraryName copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") putSuccess $ "| Successfully built custom library 'libffi'" + + libffiMakefile <.> "in" %> \mkIn -> do + removeDirectory libffiBuildPath + createDirectory $ buildRootPath -/- stageString Stage0 + + tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] + tarball <- case tarballs of -- TODO: Drop code duplication. + [file] -> return $ unifyPath file + _ -> error $ "libffiRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + + need [tarball] + let libname = dropExtension . dropExtension $ takeFileName tarball + + removeDirectory (buildRootPath -/- libname) + -- TODO: Simplify. + actionFinally (do + build $ Target libffiContext Tar [tarball] [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuildPath) $ + removeFiles buildRootPath [libname "*"] + + top <- topDirectory + fixFile mkIn (fixLibffiMakefile top) + + libffiMakefile %> \mk -> do + need [mk <.> "in"] + forM_ ["config.guess", "config.sub"] $ \file -> + copyFile file (libffiBuildPath -/- file) + + env <- configureEnvironment + buildWithCmdOptions env $ + Target libffiContext (Configure libffiBuildPath) [mk <.> "in"] [mk] From git at git.haskell.org Fri Oct 27 00:40:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify paths when printing progress info (6adb600) Message-ID: <20171027004056.B52ED3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6adb60093ae65970bbec17f9b24227b20f5a71f5/ghc >--------------------------------------------------------------- commit 6adb60093ae65970bbec17f9b24227b20f5a71f5 Author: Andrey Mokhov Date: Mon Oct 3 18:22:23 2016 +0100 Unify paths when printing progress info >--------------------------------------------------------------- 6adb60093ae65970bbec17f9b24227b20f5a71f5 src/Rules/Actions.hs | 15 +++++++-------- 1 file changed, 7 insertions(+), 8 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index cbca810..e30bc01 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -200,16 +200,15 @@ putProgressInfo :: String -> Action () putProgressInfo msg = when (cmdProgressInfo /= None) $ putBuild msg -- | Render an action. -renderAction :: String -> String -> String -> String +renderAction :: String -> FilePath -> FilePath -> String renderAction what input output = case cmdProgressInfo of - Normal -> renderBox [ what - , " input: " ++ input - , " => output: " ++ output ] - Brief -> "| " ++ what ++ ": " ++ input ++ " => " ++ output - Unicorn -> renderUnicorn [ what - , " input: " ++ input - , " => output: " ++ output ] + Normal -> renderBox [ what, " input: " ++ i, " => output: " ++ o ] + Brief -> "| " ++ what ++ ": " ++ i ++ " => " ++ o + Unicorn -> renderUnicorn [ what, " input: " ++ i, " => output: " ++ o ] None -> "" + where + i = unifyPath input + o = unifyPath output -- | Render the successful build of a program renderProgram :: String -> String -> String -> String From git at git.haskell.org Fri Oct 27 00:41:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't track -jN arguments passed to Make (b096f1e) Message-ID: <20171027004105.542AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b096f1e48ba8df3e1636c8671ec867fc6b636c29/ghc >--------------------------------------------------------------- commit b096f1e48ba8df3e1636c8671ec867fc6b636c29 Author: Andrey Mokhov Date: Wed Oct 5 13:28:28 2016 +0100 Don't track -jN arguments passed to Make See #289. >--------------------------------------------------------------- b096f1e48ba8df3e1636c8671ec867fc6b636c29 src/Builder.hs | 13 +++++++++++-- src/Oracles/ArgsHash.hs | 6 +++++- 2 files changed, 16 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 1974eff..704947d 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,10 +1,11 @@ {-# LANGUAGE DeriveGeneric, LambdaCase #-} module Builder ( - CcMode (..), GhcMode (..), Builder (..), - builderPath, getBuilderPath, builderEnvironment, specified, needBuilder + CcMode (..), GhcMode (..), Builder (..), builderPath, getBuilderPath, + builderEnvironment, specified, trackedArgument, needBuilder ) where import Control.Monad.Trans.Reader +import Data.Char import GHC.Generics (Generic) import Base @@ -149,6 +150,14 @@ builderEnvironment variable builder = do specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath +-- | Some arguments do not affect build results and therefore do not need to be +-- tracked by the build system. A notable example is "-jN" that controls Make's +-- parallelism. Given a 'Builder' and an argument, this function should return +-- 'True' only if the argument needs to be tracked. +trackedArgument :: Builder -> String -> Bool +trackedArgument (Make _) ('-' : 'j' : xs) = not $ all isDigit xs +trackedArgument _ _ = True + -- | Make sure a Builder exists on the given path and rebuild it if out of date. needBuilder :: Builder -> Action () needBuilder = \case diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 660edd9..f9cec24 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -2,6 +2,7 @@ module Oracles.ArgsHash (checkArgsHash, argsHashOracle) where import Base +import Builder import Expression import Settings import Target @@ -28,4 +29,7 @@ checkArgsHash target = do -- | Oracle for storing per-target argument list hashes. argsHashOracle :: Rules () argsHashOracle = void $ - addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs + addOracle $ \(ArgsHashKey target) -> do + argList <- interpret target getArgs + let trackedArgList = filter (trackedArgument $ builder target) argList + return $ hash trackedArgList From git at git.haskell.org Fri Oct 27 00:41:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make the build badges follow the master branch only (e9013dc) Message-ID: <20171027004105.6951B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e9013dcf7a13d9b55e353bb5e1527c4a75726b4d/ghc >--------------------------------------------------------------- commit e9013dcf7a13d9b55e353bb5e1527c4a75726b4d Author: Andrey Mokhov Date: Sat Jan 16 15:40:59 2016 +0000 Make the build badges follow the master branch only [skip ci] >--------------------------------------------------------------- e9013dcf7a13d9b55e353bb5e1527c4a75726b4d README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index f5b8117..8651b9b 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Shaking up GHC ============== -[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) As part of my 6-month research secondment to Microsoft Research in Cambridge From git at git.haskell.org Fri Oct 27 00:41:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor refactoring: re-export Context and GHC from Expression (241ceff) Message-ID: <20171027004109.527043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/241cefff1dfeb0729640996609f25c944b06bf38/ghc >--------------------------------------------------------------- commit 241cefff1dfeb0729640996609f25c944b06bf38 Author: Andrey Mokhov Date: Mon Aug 28 18:12:39 2017 +0100 Minor refactoring: re-export Context and GHC from Expression >--------------------------------------------------------------- 241cefff1dfeb0729640996609f25c944b06bf38 src/Expression.hs | 15 +++++++-------- src/Rules.hs | 2 -- src/Rules/Data.hs | 1 - src/Rules/Generate.hs | 2 -- src/Rules/Install.hs | 2 -- src/Rules/Library.hs | 1 - src/Rules/Program.hs | 1 - src/Rules/Test.hs | 1 - src/Rules/Wrappers.hs | 2 -- src/Settings.hs | 2 -- src/Settings/Builders/Common.hs | 4 ---- src/Settings/Default.hs | 1 - src/Settings/Packages/Base.hs | 1 - src/Settings/Packages/Cabal.hs | 1 - src/Settings/Packages/Compiler.hs | 1 - src/Settings/Packages/Ghc.hs | 2 -- src/Settings/Packages/GhcCabal.hs | 1 - src/Settings/Packages/GhcPkg.hs | 1 - src/Settings/Packages/GhcPrim.hs | 1 - src/Settings/Packages/Ghci.hs | 1 - src/Settings/Packages/Haddock.hs | 1 - src/Settings/Packages/Haskeline.hs | 2 -- src/Settings/Packages/IntegerGmp.hs | 1 - src/Settings/Packages/Rts.hs | 2 -- src/Settings/Packages/RunGhc.hs | 1 - src/Utilities.hs | 1 - 26 files changed, 7 insertions(+), 44 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 241cefff1dfeb0729640996609f25c944b06bf38 From git at git.haskell.org Fri Oct 27 00:41:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor paths to auxiliary build files. (4a90b33) Message-ID: <20171027004109.68E163A5EC@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a90b33ef70df26624fc064cdd4508677a0b7eec/ghc >--------------------------------------------------------------- commit 4a90b33ef70df26624fc064cdd4508677a0b7eec Author: Andrey Mokhov Date: Sat Jan 16 18:08:51 2016 +0000 Refactor paths to auxiliary build files. See #176. >--------------------------------------------------------------- 4a90b33ef70df26624fc064cdd4508677a0b7eec src/Rules/Actions.hs | 2 -- src/Settings/Builders/Ghc.hs | 4 ---- src/Settings/Packages/IntegerGmp.hs | 6 +----- src/Settings/Paths.hs | 16 ++++++++++++---- 4 files changed, 13 insertions(+), 15 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 21d134f..663f53d 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -157,13 +157,11 @@ putInfo Target.Target {..} = putProgressInfo $ renderAction digest [x] = x digest (x:xs) = x ++ " (and " ++ show (length xs) ++ " more)" - -- | Switch for @putBuild@ filtered through @buildInfo@ putProgressInfo :: String -> Action () putProgressInfo s | buildInfo /= None = putBuild s putProgressInfo _ = pure () - -- | Render an action. renderAction :: String -> String -> String -> String renderAction what input output = case buildInfo of diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 0f1fc32..c97cd56 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -11,10 +11,6 @@ import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) import Settings.Builders.Common (cIncludeArgs) --- GMP library names extracted from integer-gmp.buildinfo -gmpLibNameCache :: FilePath -gmpLibNameCache = shakeFilesPath -/- "gmp-lib-names" - -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 8b100b3..7122457 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -4,11 +4,7 @@ import Base import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) -import Settings.User - --- TODO: move elsewhere -gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage0/gmp" +import Settings.Paths -- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index bec143b..0513d6c 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,6 +1,7 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgGhciLibraryFile, packageConfiguration, packageConfigurationInitialised + pkgGhciLibraryFile, packageConfiguration, packageConfigurationInitialised, + gmpBuildPath, gmpLibNameCache ) where import Base @@ -47,6 +48,13 @@ packageConfiguration _ = "inplace/lib/package.conf.d" -- StageN, N > 0, share the same packageConfiguration (see above) packageConfigurationInitialised :: Stage -> FilePath -packageConfigurationInitialised stage = - shakeFilesPath -/- "package-configuration-initialised-" - ++ stageString (min stage Stage1) +packageConfigurationInitialised stage = packageConfiguration stage -/- + "package-configuration-initialised-" ++ stageString (min stage Stage1) + +-- This is the build directory for in-tree GMP library +gmpBuildPath :: FilePath +gmpBuildPath = buildRootPath -/- "stage0/gmp" + +-- GMP library names extracted from integer-gmp.buildinfo +gmpLibNameCache :: FilePath +gmpLibNameCache = gmpBuildPath -/- "gmp-lib-names" From git at git.haskell.org Fri Oct 27 00:41:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Support several variants of -jN flag, add tests (73b9b7b) Message-ID: <20171027004109.681273A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73b9b7b47f9c33506be8238d355eba2363470ce9/ghc >--------------------------------------------------------------- commit 73b9b7b47f9c33506be8238d355eba2363470ce9 Author: Andrey Mokhov Date: Wed Oct 5 15:31:26 2016 +0100 Support several variants of -jN flag, add tests See #289. >--------------------------------------------------------------- 73b9b7b47f9c33506be8238d355eba2363470ce9 src/Builder.hs | 7 +++++-- src/Rules/Selftest.hs | 22 ++++++++++++++++------ 2 files changed, 21 insertions(+), 8 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 704947d..55d561e 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -155,8 +155,11 @@ specified = fmap (not . null) . builderPath -- parallelism. Given a 'Builder' and an argument, this function should return -- 'True' only if the argument needs to be tracked. trackedArgument :: Builder -> String -> Bool -trackedArgument (Make _) ('-' : 'j' : xs) = not $ all isDigit xs -trackedArgument _ _ = True +trackedArgument (Make _) = not . threadArg +trackedArgument _ = const True + +threadArg :: String -> Bool +threadArg s = dropWhileEnd isDigit s `elem` ["-j", "MAKEFLAGS=-j", "THREADS="] -- | Make sure a Builder exists on the given path and rebuild it if out of date. needBuilder :: Builder -> Action () diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f53a5db..3b20f14 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,6 +6,7 @@ import Development.Shake import Test.QuickCheck import Base +import Builder import Oracles.ModuleFiles import Settings.Builders.Ar import UserSettings @@ -23,14 +24,23 @@ test = liftIO . quickCheck selftestRules :: Rules () selftestRules = "selftest" ~> do - testWays + testBuilder + testWay testChunksOfSize testMatchVersionedFilePath - testModuleNames + testModuleName testLookupAll -testWays :: Action () -testWays = do +testBuilder :: Action () +testBuilder = do + putBuild $ "==== trackedArgument" + test $ forAll (elements ["-j", "MAKEFLAGS=-j", "THREADS="]) + $ \prefix -> \(NonNegative n) -> + trackedArgument (Make undefined) prefix == False && + trackedArgument (Make undefined) ("-j" ++ show (n :: Int)) == False + +testWay :: Action () +testWay = do putBuild $ "==== Read Way, Show Way" test $ \(x :: Way) -> read (show x) == x @@ -59,8 +69,8 @@ testMatchVersionedFilePath = do where versions = listOf . elements $ '-' : '.' : ['0'..'9'] -testModuleNames :: Action () -testModuleNames = do +testModuleName :: Action () +testModuleName = do putBuild $ "==== Encode/decode module name" test $ encodeModule "Data/Functor" "Identity.hs" == "Data.Functor.Identity" test $ encodeModule "" "Prelude" == "Prelude" From git at git.haskell.org Fri Oct 27 00:41:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (1c877aa) Message-ID: <20171027004112.EBB033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c877aa89595d8d6e30f2673e8031d23cdeabdfa/ghc >--------------------------------------------------------------- commit 1c877aa89595d8d6e30f2673e8031d23cdeabdfa Merge: 4a90b33 e9013dc Author: Andrey Mokhov Date: Sat Jan 16 18:10:49 2016 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 1c877aa89595d8d6e30f2673e8031d23cdeabdfa README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:41:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision of install stages (9dcd2a6) Message-ID: <20171027004113.28B313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dcd2a6fd2a4799ec807af2418f52ab90f164273/ghc >--------------------------------------------------------------- commit 9dcd2a6fd2a4799ec807af2418f52ab90f164273 Author: Andrey Mokhov Date: Tue Aug 29 00:28:55 2017 +0100 Minor revision of install stages See #403 >--------------------------------------------------------------- 9dcd2a6fd2a4799ec807af2418f52ab90f164273 src/GHC.hs | 20 +++++++++---- src/Rules/Install.hs | 79 ++++++++++++++++++++++++--------------------------- src/Rules/Program.hs | 15 ++++++---- src/Rules/Wrappers.hs | 7 ++--- src/Settings.hs | 9 +----- 5 files changed, 64 insertions(+), 66 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9dcd2a6fd2a4799ec807af2418f52ab90f164273 From git at git.haskell.org Fri Oct 27 00:41:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix warnings (8cfa6ef) Message-ID: <20171027004113.519E03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8cfa6efa9fb742b90b2c3019536365f711392b75/ghc >--------------------------------------------------------------- commit 8cfa6efa9fb742b90b2c3019536365f711392b75 Author: Andrey Mokhov Date: Wed Oct 5 15:31:45 2016 +0100 Fix warnings >--------------------------------------------------------------- 8cfa6efa9fb742b90b2c3019536365f711392b75 src/Oracles/ArgsHash.hs | 6 +++--- src/Settings/Packages/Compiler.hs | 1 - 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index f9cec24..36a0cdd 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -30,6 +30,6 @@ checkArgsHash target = do argsHashOracle :: Rules () argsHashOracle = void $ addOracle $ \(ArgsHashKey target) -> do - argList <- interpret target getArgs - let trackedArgList = filter (trackedArgument $ builder target) argList - return $ hash trackedArgList + argList <- interpret target getArgs + let trackedArgList = filter (trackedArgument $ builder target) argList + return $ hash trackedArgList diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index f33dc18..03b8081 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -7,7 +7,6 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Predicate import Settings -import Settings.Paths compilerPackageArgs :: Args compilerPackageArgs = package compiler ? do From git at git.haskell.org Fri Oct 27 00:41:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix wrapper build (090e00a) Message-ID: <20171027004117.27AA23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/090e00af68efad88b82ae94e8f7a3a97375b6054/ghc >--------------------------------------------------------------- commit 090e00af68efad88b82ae94e8f7a3a97375b6054 Author: Andrey Mokhov Date: Tue Aug 29 00:46:19 2017 +0100 Fix wrapper build See #403 >--------------------------------------------------------------- 090e00af68efad88b82ae94e8f7a3a97375b6054 src/Rules/Program.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index c8a725e..b13f8a2 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -17,7 +17,7 @@ import Utilities -- TODO: Drop way in build rule generation? buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do - let installStage = do + let installStage = if package == ghc then return stage else do stages <- installStages package case stages of [s] -> return s @@ -33,7 +33,7 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do -- Some binaries in inplace/bin are wrapped inplaceBinPath -/- programName context <.> exe %> \bin -> do context' <- programContext stage package - binStage <- if package == ghc then return stage else installStage + binStage <- installStage buildBinaryAndWrapper rs (context' { stage = binStage }) bin inplaceLibBinPath -/- programName context <.> exe %> \bin -> do From git at git.haskell.org Fri Oct 27 00:41:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (9233793) Message-ID: <20171027004117.44AAD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9233793b86b2b14efa3ae1adb5f95f378bf15ef8/ghc >--------------------------------------------------------------- commit 9233793b86b2b14efa3ae1adb5f95f378bf15ef8 Author: Andrey Mokhov Date: Wed Oct 5 17:35:44 2016 +0100 Minor revision >--------------------------------------------------------------- 9233793b86b2b14efa3ae1adb5f95f378bf15ef8 src/Rules/Selftest.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 +++----- 2 files changed, 4 insertions(+), 6 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 3b20f14..e7f5dbb 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -35,7 +35,7 @@ testBuilder :: Action () testBuilder = do putBuild $ "==== trackedArgument" test $ forAll (elements ["-j", "MAKEFLAGS=-j", "THREADS="]) - $ \prefix -> \(NonNegative n) -> + $ \prefix (NonNegative n) -> trackedArgument (Make undefined) prefix == False && trackedArgument (Make undefined) ("-j" ++ show (n :: Int)) == False diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 6eaf8ae..7f54af9 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -36,15 +36,13 @@ ghcLinkArgs :: Args ghcLinkArgs = builder (Ghc LinkHs) ? do stage <- getStage libs <- getPkgDataList DepExtraLibs + libDirs <- getPkgDataList DepLibDirs gmpLibs <- if stage > Stage0 then do -- TODO: get this data more gracefully + let strip = fromMaybe "" . stripPrefix "extra-libraries: " buildInfo <- lift $ readFileLines gmpBuildInfoPath - let extract s = case stripPrefix "extra-libraries: " s of - Nothing -> [] - Just value -> words value - return $ concatMap extract buildInfo + return $ concatMap (words . strip) buildInfo else return [] - libDirs <- getPkgDataList DepLibDirs mconcat [ arg "-no-auto-link-packages" , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] From git at git.haskell.org Fri Oct 27 00:41:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Limit Make's thread (703429d) Message-ID: <20171027004120.F01663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/703429d917a4349d0a7ec8809dfb41c8b3433937/ghc >--------------------------------------------------------------- commit 703429d917a4349d0a7ec8809dfb41c8b3433937 Author: Andrey Mokhov Date: Wed Oct 5 17:36:32 2016 +0100 Limit Make's thread See #289. >--------------------------------------------------------------- 703429d917a4349d0a7ec8809dfb41c8b3433937 src/Settings/Builders/Make.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index d6b7dbf..1e55d9a 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -7,7 +7,7 @@ import Settings.Paths makeBuilderArgs :: Args makeBuilderArgs = do threads <- shakeThreads <$> lift getShakeOptions - let t = show threads + let t = show $ max 4 (threads - 2) -- Don't use all Shake's threads mconcat [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=-j" ++ t] , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=-j" ++ t, "install"] From git at git.haskell.org Fri Oct 27 00:41:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor program build rules (7a5c384) Message-ID: <20171027004121.1C0D13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67/ghc >--------------------------------------------------------------- commit 7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67 Author: Andrey Mokhov Date: Tue Aug 29 04:02:10 2017 +0100 Refactor program build rules See #403 >--------------------------------------------------------------- 7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67 src/GHC.hs | 49 +++++++++++++++++++-------------------- src/Rules.hs | 4 +++- src/Rules/Install.hs | 20 ++++++++-------- src/Rules/Program.hs | 63 ++++++++++++++++++++++++++------------------------- src/Rules/Wrappers.hs | 8 +++---- 5 files changed, 75 insertions(+), 69 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 7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67 From git at git.haskell.org Fri Oct 27 00:41:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (f5dff68) Message-ID: <20171027004116.C223A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5dff684386aaec9ed079364423524c91b5be2cd/ghc >--------------------------------------------------------------- commit f5dff684386aaec9ed079364423524c91b5be2cd Author: Andrey Mokhov Date: Sat Jan 16 23:56:57 2016 +0000 Minor revision. [skip ci] >--------------------------------------------------------------- f5dff684386aaec9ed079364423524c91b5be2cd src/Predicates.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 497fca5..1e56993 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -9,15 +9,15 @@ import Expression -- | Is the build currently in the provided stage? stage :: Stage -> Predicate -stage s = fmap (s ==) getStage +stage s = (s ==) <$> getStage -- | Is a particular package being built? package :: Package -> Predicate -package p = fmap (p ==) getPackage +package p = (p ==) <$> getPackage -- | Is an unstaged builder is being used such as /GhcCabal/? builder :: Builder -> Predicate -builder b = fmap (b ==) getBuilder +builder b = (b ==) <$> getBuilder -- | Is a certain builder used in the current stage? stagedBuilder :: (Stage -> Builder) -> Predicate @@ -35,11 +35,11 @@ builderGhc = stagedBuilder Ghc ||^ stagedBuilder GhcM -- | Does any of the output files match a given pattern? file :: FilePattern -> Predicate -file f = fmap (any (f ?==)) getOutputs +file f = any (f ?==) <$> getOutputs -- | Is the current build 'Way' equal to a certain value? way :: Way -> Predicate -way w = fmap (w ==) getWay +way w = (w ==) <$> getWay -- | Is the build currently in stage 0? stage0 :: Predicate From git at git.haskell.org Fri Oct 27 00:41:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor ways, revise comments. (3ff1fc1) Message-ID: <20171027004120.80CB93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ff1fc1097d98f17ab081be3c9f1379bea69d04a/ghc >--------------------------------------------------------------- commit 3ff1fc1097d98f17ab081be3c9f1379bea69d04a Author: Andrey Mokhov Date: Sat Jan 16 23:58:20 2016 +0000 Refactor ways, revise comments. See #100. >--------------------------------------------------------------- 3ff1fc1097d98f17ab081be3c9f1379bea69d04a src/Rules/Program.hs | 2 +- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/User.hs | 24 +++++++++++++----------- src/Settings/Ways.hs | 33 +++++++++++++++------------------ src/Way.hs | 1 + 6 files changed, 32 insertions(+), 32 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 93a6d6c..d472e88 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -77,7 +77,7 @@ buildBinary target @ (PartialTarget stage pkg) bin = do ++ [ buildPath -/- "Paths_hsc2hs.o" | pkg == hsc2hs ] ++ [ buildPath -/- "Paths_haddock.o" | pkg == haddock ] objs = cObjs ++ hObjs - ways <- interpretPartial target getWays + ways <- interpretPartial target getLibraryWays depNames <- interpretPartial target $ getPkgDataList TransitiveDepNames let libStage = min stage Stage1 -- libraries are built only in Stage0/1 libTarget = PartialTarget libStage pkg diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index c97cd56..3537aed 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -48,7 +48,7 @@ splitObjectsArgs = splitObjects ? do ghcMBuilderArgs :: Args ghcMBuilderArgs = stagedBuilder GhcM ? do - ways <- getWays + ways <- getLibraryWays mconcat [ arg "-M" , commonGhcArgs , arg "-include-pkg-deps" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 8591bd5..afd3def 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -49,7 +49,7 @@ ghcCabalHsColourBuilderArgs = builder GhcCabalHsColour ? do -- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci? libraryArgs :: Args libraryArgs = do - ways <- getWays + ways <- getLibraryWays withGhci <- lift ghcWithInterpreter append [ if vanilla `elem` ways then "--enable-library-vanilla" diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 2a1471d..f57a2ac 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,6 +1,6 @@ module Settings.User ( buildRootPath, userTargetDirectory, userProgramPath, trackBuildSystem, - userArgs, userPackages, userLibWays, userRtsWays, userKnownPackages, + userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, laxDependencies, buildSystemConfigFile, verboseCommands, turnWarningsIntoErrors, splitObjects, @@ -36,24 +36,26 @@ userPackages = mempty userKnownPackages :: [Package] userKnownPackages = [] --- Control which ways libraries and rts are built --- TODO: skip profiling for speed, skip dynamic since it's currently broken -userLibWays :: Ways -userLibWays = remove [profiling, dynamic] +-- | Control which ways library packages are built +-- FIXME: skip profiling for speed +-- FIXME: skip dynamic since it's currently broken #4 +userLibraryWays :: Ways +userLibraryWays = remove [profiling, dynamic] +-- | Control which ways the 'rts' package is built userRtsWays :: Ways userRtsWays = mempty --- Choose integer library: integerGmp, integerGmp2 or integerSimple +-- | Choose the integer library: integerGmp or integerSimple integerLibrary :: Package integerLibrary = integerGmp --- User-defined flags. Note the following type semantics: +-- | User-defined flags. Note the following type semantics: -- * Bool: a plain Boolean flag whose value is known at compile time -- * Action Bool: a flag whose value can depend on the build environment -- * Predicate: a flag depending on the build environment and the current target --- Set this to True if you are making any changes in the build system and want +-- | Set this to True if you are making any changes in the build system and want -- appropriate rebuilds to be initiated. Switching this to False speeds things -- up a little (particularly zero builds). -- WARNING: a complete rebuild is required when changing this setting. @@ -80,7 +82,7 @@ ghcProfiled = False ghcDebugged :: Bool ghcDebugged = False --- When laxDependencies flag is set to True, dependencies on the GHC executable +-- | When laxDependencies is set to True, dependencies on the GHC executable -- are turned into order-only dependencies to avoid needless recompilation when -- making changes to GHC's sources. In certain situations this can lead to build -- failures, in which case you should reset the flag (at least temporarily). @@ -93,8 +95,8 @@ buildHaddock = return False -- FIXME: should be return True, see #98 buildSystemConfigFile :: Bool buildSystemConfigFile = False --- Set to True to print full command lines during the build process. Note, this --- is a Predicate, hence you can enable verbose output for a chosen package +-- | Set to True to print full command lines during the build process. Note, +-- this is a Predicate, hence you can enable verbose output for a chosen package -- only, e.g.: verboseCommands = package ghcPrim verboseCommands :: Predicate verboseCommands = return False diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 8376213..223bc79 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,34 +1,31 @@ -module Settings.Ways (getWays, getLibWays, getRtsWays) where +module Settings.Ways (getLibraryWays, getRtsWays) where -import Data.Monoid +import Base import Expression import Predicates import Settings.User import Oracles.Config.Flag --- TODO: use a single expression Ways parameterised by package instead of --- expressions libWays and rtsWays - --- Combining default ways with user modifications -getLibWays :: Expr [Way] -getLibWays = fromDiffExpr $ defaultLibWays <> userLibWays - --- In Stage0 we only build vanilla -getWays :: Expr [Way] -getWays = mconcat [ stage0 ? return [vanilla], notStage0 ? getLibWays ] +-- | Combine default ways with user modifications +getLibraryWays :: Expr [Way] +getLibraryWays = fromDiffExpr $ defaultLibraryWays <> userLibraryWays getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays --- These are default ways -defaultLibWays :: Ways -defaultLibWays = mconcat - [ append [vanilla, profiling] - , platformSupportsSharedLibs ? append [dynamic] ] +-- These are default ways for library packages: +-- * We always build 'vanilla' way. +-- * We build 'profiling' way when stage > Stage0. +-- * We build 'dynamic' way when stage > Stage0 and the platform supports it. +defaultLibraryWays :: Ways +defaultLibraryWays = mconcat + [ append [vanilla] + , notStage0 ? append [profiling] + , notStage0 ? platformSupportsSharedLibs ? append [dynamic] ] defaultRtsWays :: Ways defaultRtsWays = do - ways <- getLibWays + ways <- getLibraryWays mconcat [ append [ logging, debug, threaded, threadedDebug, threadedLogging ] , (profiling `elem` ways) ? append [threadedProfiling] diff --git a/src/Way.hs b/src/Way.hs index ba20bd7..8923571 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -101,6 +101,7 @@ granSim = wayFromUnits [GranSim] -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? +-- See compiler/main/DynFlags.hs. threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, threadedDynamic, threadedDebugDynamic, From git at git.haskell.org Fri Oct 27 00:41:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix wrapper build rules (9da5e17) Message-ID: <20171027004124.CB5523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9da5e17c26e1c9d256052fa065e8c331635b4c5b/ghc >--------------------------------------------------------------- commit 9da5e17c26e1c9d256052fa065e8c331635b4c5b Author: Andrey Mokhov Date: Tue Aug 29 10:23:52 2017 +0100 Fix wrapper build rules See #403 >--------------------------------------------------------------- 9da5e17c26e1c9d256052fa065e8c331635b4c5b src/Rules/Program.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 13bfd34..0211cfe 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -14,6 +14,7 @@ import Settings.Packages.Rts import Target import Utilities +-- | TODO: Drop code duplication buildProgram :: [(Resource, Int)] -> Package -> Rules () buildProgram rs package = do forM_ [Stage0 ..] $ \stage -> do @@ -25,11 +26,19 @@ buildProgram rs package = do buildBinaryAndWrapper rs context' bin -- Rules for the GHC package, which is built 'inplace' - when (package == ghc) $ + when (package == ghc) $ do inplaceBinPath -/- programName context <.> exe %> \bin -> do context' <- programContext stage package buildBinaryAndWrapper rs context' bin + inplaceLibBinPath -/- programName context <.> exe %> \bin -> do + context' <- programContext stage package + buildBinary rs context' bin + + inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> do + context' <- programContext stage package + buildBinary rs context' bin + -- Rules for other programs built in inplace directories when (package /= ghc) $ do let context0 = vanillaContext Stage0 package -- TODO: get rid of context0 From git at git.haskell.org Fri Oct 27 00:41:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Further work on #174. (1300254) Message-ID: <20171027004124.AA8593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/130025463ea2a8b50decceae44c2618198466acd/ghc >--------------------------------------------------------------- commit 130025463ea2a8b50decceae44c2618198466acd Author: Andrey Mokhov Date: Sun Jan 17 03:01:26 2016 +0000 Further work on #174. >--------------------------------------------------------------- 130025463ea2a8b50decceae44c2618198466acd src/Rules/Compile.hs | 14 ++++++++++---- src/Settings/Packages/RunGhc.hs | 2 +- 2 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 2065415..b27d36e 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,7 +12,7 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let buildPath = targetPath stage pkg -/- "build" matchBuildResult buildPath "hi" ?> \hi -> - if compileInterfaceFilesSeparately + if compileInterfaceFilesSeparately && not ("//HpcParser.*" ?== hi) then do let way = detectWay hi (src, deps) <- dependencies buildPath $ hi -<.> osuf way @@ -32,16 +32,22 @@ compilePackage _ target @ (PartialTarget stage pkg) = do -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) matchBuildResult buildPath "o" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need $ src : deps if ("//*.c" ?== src) - then build $ fullTarget target (Gcc stage) [src] [obj] + then do + need $ src : deps + build $ fullTarget target (Gcc stage) [src] [obj] else do let way = detectWay obj + if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) + then need $ (obj -<.> hisuf (detectWay obj)) : src : deps + else need $ src : deps build $ fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases matchBuildResult buildPath "o-boot" ?> \obj -> do (src, deps) <- dependencies buildPath obj - need $ src : deps let way = detectWay obj + if compileInterfaceFilesSeparately + then need $ (obj -<.> hibootsuf (detectWay obj)) : src : deps + else need $ src : deps build $ fullTargetWithWay target (Ghc stage) way [src] [obj] diff --git a/src/Settings/Packages/RunGhc.hs b/src/Settings/Packages/RunGhc.hs index 37cdb95..e982fe6 100644 --- a/src/Settings/Packages/RunGhc.hs +++ b/src/Settings/Packages/RunGhc.hs @@ -9,5 +9,5 @@ runGhcPackageArgs :: Args runGhcPackageArgs = package runGhc ? do version <- getSetting ProjectVersion mconcat [ builderGhc ? - file "//Main.o" ? + file "//Main.*" ? append ["-cpp", "-DVERSION=\"" ++ version ++ "\""] ] From git at git.haskell.org Fri Oct 27 00:41:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reduce verbosity of ghc-cabal and ghc-pkg (d3d00b0) Message-ID: <20171027004125.28F3F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3d00b0c412d964891f63fbd6c52bc457d6b3233/ghc >--------------------------------------------------------------- commit d3d00b0c412d964891f63fbd6c52bc457d6b3233 Author: Andrey Mokhov Date: Wed Oct 5 17:36:54 2016 +0100 Reduce verbosity of ghc-cabal and ghc-pkg >--------------------------------------------------------------- d3d00b0c412d964891f63fbd6c52bc457d6b3233 src/Settings/Builders/GhcCabal.hs | 37 ++++++++++++++++++++----------------- src/Settings/Builders/GhcPkg.hs | 2 ++ 2 files changed, 22 insertions(+), 17 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 14c1254..fffb2c0 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -17,23 +17,26 @@ import Settings.Builders.Common import Settings.Paths ghcCabalBuilderArgs :: Args -ghcCabalBuilderArgs = builder GhcCabal ? mconcat - [ arg "configure" - , arg =<< getPackagePath - , arg =<< getContextDirectory - , dll0Args - , withStaged $ Ghc CompileHs - , withStaged GhcPkg - , bootPackageDatabaseArgs - , libraryArgs - , with HsColour - , configureArgs - , packageConstraints - , withStaged $ Cc CompileC - , notStage0 ? with Ld - , with Ar - , with Alex - , with Happy ] +ghcCabalBuilderArgs = builder GhcCabal ? do + verbosity <- lift $ getVerbosity + mconcat [ arg "configure" + , arg =<< getPackagePath + , arg =<< getContextDirectory + , dll0Args + , withStaged $ Ghc CompileHs + , withStaged GhcPkg + , bootPackageDatabaseArgs + , libraryArgs + , with HsColour + , configureArgs + , packageConstraints + , withStaged $ Cc CompileC + , notStage0 ? with Ld + , with Ar + , with Alex + , with Happy + , verbosity < Chatty ? append [ "-v0", "--configure-option=--quiet" + , "--configure-option=--disable-option-checking" ] ] ghcCabalHsColourBuilderArgs :: Args ghcCabalHsColourBuilderArgs = builder GhcCabalHsColour ? do diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index ed6843a..b221b9d 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -20,7 +20,9 @@ updateArgs :: Args updateArgs = notM initPredicate ? do pkg <- getPackage dir <- getContextDirectory + verbosity <- lift $ getVerbosity mconcat [ arg "update" , arg "--force" + , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs , arg $ pkgPath pkg -/- dir -/- "inplace-pkg-config" ] From git at git.haskell.org Fri Oct 27 00:41:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix handling of FFI library configure params (6abfdfa) Message-ID: <20171027004128.520143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6abfdfaec035057a956ded2dad8695c4c600e24c/ghc >--------------------------------------------------------------- commit 6abfdfaec035057a956ded2dad8695c4c600e24c Author: Karel Gardas Date: Sun Jan 17 22:55:57 2016 +0100 fix handling of FFI library configure params >--------------------------------------------------------------- 6abfdfaec035057a956ded2dad8695c4c600e24c cfg/system.config.in | 3 ++ src/Oracles/Config/Setting.hs | 6 +++ src/Rules/Libffi.hs | 87 ++++++++++++++++++++++++------------------- src/Settings/Packages/Rts.hs | 8 +++- 4 files changed, 65 insertions(+), 39 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index dfde8e3..ecbf18d 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -127,6 +127,9 @@ iconv-lib-dirs = @ICONV_LIB_DIRS@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ +use-system-ffi = @UseSystemLibFFI@ +ffi-include-dirs = @FFIIncludeDir@ +ffi-lib-dirs = @FFILibDir@ # Optional Dependencies: #======================= diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 46d0d33..7b5d71e 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -47,6 +47,7 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor + | UseSystemFfi data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -57,6 +58,8 @@ data SettingList = ConfCcArgs Stage | HsCppArgs | IconvIncludeDirs | IconvLibDirs + | FfiIncludeDirs + | FfiLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of @@ -88,6 +91,7 @@ setting key = askConfig $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" + UseSystemFfi -> "use-system-ffi" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -100,6 +104,8 @@ settingList key = fmap words $ askConfig $ case key of HsCppArgs -> "hs-cpp-args" IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" + FfiIncludeDirs -> "ffi-include-dirs" + FfiLibDirs -> "ffi-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index dbf50dc..5f23cad 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,44 +70,55 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - removeDirectory libffiBuild - createDirectory $ buildRootPath -/- stageString Stage0 - - tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - when (length tarballs /= 1) $ - putError $ "libffiRules: exactly one libffi tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - - need tarballs - let libname = dropExtension . dropExtension . takeFileName $ head tarballs - - removeDirectory (buildRootPath -/- libname) - actionFinally (do - build $ fullTarget libffiTarget Tar tarballs [buildRootPath] - moveDirectory (buildRootPath -/- libname) libffiBuild) $ - removeFiles buildRootPath [libname "*"] - - fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile - - forM_ ["config.guess", "config.sub"] $ \file -> - copyFile file (libffiBuild -/- file) - - envs <- configureEnvironment - args <- configureArguments - runConfigure libffiBuild envs args - - runMake libffiBuild ["MAKEFLAGS="] - runMake libffiBuild ["MAKEFLAGS=", "install"] - - forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file - copyFile src (rtsBuildPath -/- file) - - libffiName <- rtsLibffiLibraryName - copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") - - putSuccess $ "| Successfully built custom library 'libffi'" + use_system_ffi <- setting UseSystemFfi + ffi_header_dirs <- settingList FfiIncludeDirs + if use_system_ffi == "YES" + then do + putBuild "| System supplied FFI library will be used" + let ffi_header_dir = head ffi_header_dirs + forM_ ["ffi.h", "ffitarget.h"] $ \file -> do + let src = ffi_header_dir -/- file + copyFile src (rtsBuildPath -/- file) + putSuccess $ "| Successfully copied system supplied FFI library header files" + else do + when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] + removeDirectory libffiBuild + createDirectory $ buildRootPath -/- stageString Stage0 + + tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] + when (length tarballs /= 1) $ + putError $ "libffiRules: exactly one libffi tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + + need tarballs + let libname = dropExtension . dropExtension . takeFileName $ head tarballs + + removeDirectory (buildRootPath -/- libname) + actionFinally (do + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] + + fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile + + forM_ ["config.guess", "config.sub"] $ \file -> + copyFile file (libffiBuild -/- file) + + envs <- configureEnvironment + args <- configureArguments + runConfigure libffiBuild envs args + + runMake libffiBuild ["MAKEFLAGS="] + runMake libffiBuild ["MAKEFLAGS=", "install"] + + forM_ ["ffi.h", "ffitarget.h"] $ \file -> do + let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file + copyFile src (rtsBuildPath -/- file) + + libffiName <- rtsLibffiLibraryName + copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") + + putSuccess $ "| Successfully built custom library 'libffi'" -- chmod +x libffi/ln -- # wc on OS X has spaces in its output, which libffi's Makefile diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index f1d67d9..26fce73 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,8 +20,14 @@ rtsConf = pkgPath rts -/- targetDirectory Stage1 rts -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do + use_system_ffi <- setting UseSystemFfi windows <- windowsHost - return $ if windows then "Cffi-6" else "Cffi" + case (use_system_ffi, windows) of + ("YES", False) -> return "ffi" + ("NO", False) -> return "Cffi" + (_, True) -> return "Cffi-6" + (_, _) -> error "Unsupported FFI library configuration case" + rtsPackageArgs :: Args rtsPackageArgs = package rts ? do From git at git.haskell.org Fri Oct 27 00:41:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (de975b7) Message-ID: <20171027004128.5FB4D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de975b7282e8bdb003297e4804b58b090b89c61d/ghc >--------------------------------------------------------------- commit de975b7282e8bdb003297e4804b58b090b89c61d Author: Andrey Mokhov Date: Wed Aug 30 01:29:03 2017 +0100 Minor revision See #403 >--------------------------------------------------------------- de975b7282e8bdb003297e4804b58b090b89c61d src/Rules/Program.hs | 54 +++++++++++++++++++++++----------------------------- 1 file changed, 24 insertions(+), 30 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 0211cfe..ba4dab0 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -21,54 +21,48 @@ buildProgram rs package = do let context = vanillaContext stage package -- Rules for programs built in 'buildRoot' - "//" ++ contextDir context -/- programName context <.> exe %> \bin -> do - context' <- programContext stage package - buildBinaryAndWrapper rs context' bin + "//" ++ contextDir context -/- programName context <.> exe %> \bin -> + buildBinaryAndWrapper rs bin =<< programContext stage package -- Rules for the GHC package, which is built 'inplace' when (package == ghc) $ do - inplaceBinPath -/- programName context <.> exe %> \bin -> do - context' <- programContext stage package - buildBinaryAndWrapper rs context' bin + inplaceBinPath -/- programName context <.> exe %> \bin -> + buildBinaryAndWrapper rs bin =<< programContext stage package - inplaceLibBinPath -/- programName context <.> exe %> \bin -> do - context' <- programContext stage package - buildBinary rs context' bin + inplaceLibBinPath -/- programName context <.> exe %> \bin -> + buildBinary rs bin =<< programContext stage package - inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> do - context' <- programContext stage package - buildBinary rs context' bin + inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> + buildBinary rs bin =<< programContext stage package -- Rules for other programs built in inplace directories when (package /= ghc) $ do let context0 = vanillaContext Stage0 package -- TODO: get rid of context0 inplaceBinPath -/- programName context0 <.> exe %> \bin -> do - stage <- installStage package -- TODO: get rid of fromJust - context <- programContext (fromJust stage) package - buildBinaryAndWrapper rs context bin + stage <- installStage package -- TODO: get rid of fromJust + buildBinaryAndWrapper rs bin =<< programContext (fromJust stage) package inplaceLibBinPath -/- programName context0 <.> exe %> \bin -> do stage <- installStage package -- TODO: get rid of fromJust context <- programContext (fromJust stage) package if package /= iservBin then -- We *normally* build only unwrapped binaries in inplace/lib/bin - buildBinary rs context bin + buildBinary rs bin context else -- Build both binary and wrapper in inplace/lib/bin for iservBin - buildBinaryAndWrapperLib rs context bin + buildBinaryAndWrapperLib rs bin context inplaceLibBinPath -/- programName context0 <.> "bin" %> \bin -> do - stage <- installStage package -- TODO: get rid of fromJust - context <- programContext (fromJust stage) package - buildBinary rs context bin + stage <- installStage package -- TODO: get rid of fromJust + buildBinary rs bin =<< programContext (fromJust stage) package -buildBinaryAndWrapperLib :: [(Resource, Int)] -> Context -> FilePath -> Action () -buildBinaryAndWrapperLib rs context bin = do +buildBinaryAndWrapperLib :: [(Resource, Int)] -> FilePath -> Context -> Action () +buildBinaryAndWrapperLib rs bin context = do windows <- windowsHost if windows - then buildBinary rs context bin -- We don't build wrappers on Windows + then buildBinary rs bin context -- We don't build wrappers on Windows else case lookup context inplaceWrappers of - Nothing -> buildBinary rs context bin -- No wrapper found + Nothing -> buildBinary rs bin context -- No wrapper found Just wrapper -> do top <- topDirectory let libdir = top -/- inplaceLibPath @@ -76,13 +70,13 @@ buildBinaryAndWrapperLib rs context bin = do need [wrappedBin] buildWrapper context wrapper bin (WrappedBinary libdir (takeFileName wrappedBin)) -buildBinaryAndWrapper :: [(Resource, Int)] -> Context -> FilePath -> Action () -buildBinaryAndWrapper rs context bin = do +buildBinaryAndWrapper :: [(Resource, Int)] -> FilePath -> Context -> Action () +buildBinaryAndWrapper rs bin context = do windows <- windowsHost if windows - then buildBinary rs context bin -- We don't build wrappers on Windows + then buildBinary rs bin context -- We don't build wrappers on Windows else case lookup context inplaceWrappers of - Nothing -> buildBinary rs context bin -- No wrapper found + Nothing -> buildBinary rs bin context -- No wrapper found Just wrapper -> do top <- topDirectory let libPath = top -/- inplaceLibPath @@ -99,8 +93,8 @@ buildWrapper context at Context {..} wrapper wrapperPath wrapped = do quote (pkgName package) ++ " (" ++ show stage ++ ")." -- TODO: Get rid of the Paths_hsc2hs.o hack. -buildBinary :: [(Resource, Int)] -> Context -> FilePath -> Action () -buildBinary rs context at Context {..} bin = do +buildBinary :: [(Resource, Int)] -> FilePath -> Context -> Action () +buildBinary rs bin context at Context {..} = do binDeps <- if stage == Stage0 && package == ghcCabal then hsSources context else do From git at git.haskell.org Fri Oct 27 00:41:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Eliminate some uses of fromJust (8657341) Message-ID: <20171027004128.E0D1B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8657341ded43e9671c48929627814e1e64b22ead/ghc >--------------------------------------------------------------- commit 8657341ded43e9671c48929627814e1e64b22ead Author: Ben Gamari Date: Sat Oct 8 15:10:33 2016 -0400 Eliminate some uses of fromJust >--------------------------------------------------------------- 8657341ded43e9671c48929627814e1e64b22ead src/Builder.hs | 7 +++++-- src/Rules.hs | 8 +++++++- 2 files changed, 12 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 55d561e..6f892f2 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -98,11 +98,14 @@ isOptional = \case Objdump -> True _ -> False --- TODO: Get rid of fromJust. -- | Determine the location of a 'Builder'. builderPath :: Builder -> Action FilePath builderPath builder = case builderProvenance builder of - Just context -> return . fromJust $ programPath context + Just context + | Just path <- programPath context -> return path + | otherwise -> + error $ "Cannot determine builderPath for " ++ show builder + ++ " in context " ++ show context Nothing -> case builder of Alex -> fromKey "alex" Ar -> fromKey "ar" diff --git a/src/Rules.hs b/src/Rules.hs index f69cc95..e62ecc7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -49,7 +49,13 @@ topLevelTargets = do docs <- interpretInContext context $ buildHaddock flavour need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else do -- otherwise build a program - need [ fromJust $ programPath context ] -- TODO: drop fromJust + need [ getProgramPath context ] + where + getProgramPath context = + case programPath context of + Nothing -> error $ "topLevelTargets: Can't determine program path for context " + ++ show context + Just path -> path packageRules :: Rules () packageRules = do From git at git.haskell.org Fri Oct 27 00:41:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dll-split (12e7d5f) Message-ID: <20171027004131.E8E8B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12e7d5fc30e3776c29f3aba16985c72888f1a109/ghc >--------------------------------------------------------------- commit 12e7d5fc30e3776c29f3aba16985c72888f1a109 Author: Andrey Mokhov Date: Wed Aug 30 02:13:03 2017 +0100 Drop dll-split See #404 >--------------------------------------------------------------- 12e7d5fc30e3776c29f3aba16985c72888f1a109 src/GHC.hs | 17 +++++++---------- src/Rules.hs | 4 ++-- 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 7a9ff560..554cdae 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -2,7 +2,7 @@ module GHC ( -- * GHC packages array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, - compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, + compiler, containers, deepseq, deriveConstants, directory, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, @@ -30,13 +30,12 @@ import Oracles.Setting ghcPackages :: [Package] ghcPackages = [ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes - , compiler, containers, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal - , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs - , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi - , mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm - , templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix - , win32, xhtml ] + , compiler, containers, deepseq, deriveConstants, directory, filepath + , genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact + , ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc + , hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, parallel + , pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo + , text, time, touchy, transformers, unlit, unix, win32, xhtml ] -- TODO: Optimise by switching to sets of packages. isGhcPackage :: Package -> Bool @@ -55,7 +54,6 @@ containers = hsLib "containers" deepseq = hsLib "deepseq" deriveConstants = hsUtil "deriveConstants" directory = hsLib "directory" -dllSplit = hsUtil "dll-split" filepath = hsLib "filepath" genapply = hsUtil "genapply" genprimopcode = hsUtil "genprimopcode" @@ -144,7 +142,6 @@ stage0Packages = do , compareSizes , compiler , deriveConstants - , dllSplit , genapply , genprimopcode , ghc diff --git a/src/Rules.hs b/src/Rules.hs index 09610d7..fcf3f65 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -126,5 +126,5 @@ oracleRules = do Oracles.ModuleFiles.moduleFilesOracle programsStage1Only :: [Package] -programsStage1Only = [ deriveConstants, dllSplit, genapply, genprimopcode, ghc - , ghcCabal, ghcPkg, hp2ps, hpc, hsc2hs, runGhc ] +programsStage1Only = [ deriveConstants, genapply, genprimopcode, ghc, ghcCabal + , ghcPkg, hp2ps, hpc, hsc2hs, runGhc ] From git at git.haskell.org Fri Oct 27 00:41:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: use flag instead of setting for use system ffi value (afc4d05) Message-ID: <20171027004132.1522D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/afc4d05a9f33555887df3217adb6c70ebe806d2f/ghc >--------------------------------------------------------------- commit afc4d05a9f33555887df3217adb6c70ebe806d2f Author: Karel Gardas Date: Sun Jan 17 23:52:48 2016 +0100 use flag instead of setting for use system ffi value >--------------------------------------------------------------- afc4d05a9f33555887df3217adb6c70ebe806d2f src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 2 -- src/Rules/Libffi.hs | 4 ++-- src/Settings/Packages/Rts.hs | 6 +++--- 4 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 44e8a17..9d33445 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -19,6 +19,7 @@ data Flag = ArSupportsAtFile | SolarisBrokenShld | SplitObjectsBroken | WithLibdw + | UseSystemFfi -- Note, if a flag is set to empty string we treat it as set to NO. This seems -- fragile, but some flags do behave like this, e.g. GccIsClang. @@ -34,6 +35,7 @@ flag f = do SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" WithLibdw -> "with-libdw" + UseSystemFfi -> "use-system-ffi" value <- askConfigWithDefault key . putError $ "\nFlag '" ++ key ++ "' not set in configuration files." unless (value == "YES" || value == "NO" || value == "") . putError diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 7b5d71e..56ef1ca 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -47,7 +47,6 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor - | UseSystemFfi data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -91,7 +90,6 @@ setting key = askConfig $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" - UseSystemFfi -> "use-system-ffi" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 5f23cad..fea58ab 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,9 +70,9 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - use_system_ffi <- setting UseSystemFfi ffi_header_dirs <- settingList FfiIncludeDirs - if use_system_ffi == "YES" + use_system_ffi <- flag UseSystemFfi + if use_system_ffi then do putBuild "| System supplied FFI library will be used" let ffi_header_dir = head ffi_header_dirs diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 26fce73..e684b7a 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,11 +20,11 @@ rtsConf = pkgPath rts -/- targetDirectory Stage1 rts -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do - use_system_ffi <- setting UseSystemFfi + use_system_ffi <- flag UseSystemFfi windows <- windowsHost case (use_system_ffi, windows) of - ("YES", False) -> return "ffi" - ("NO", False) -> return "Cffi" + (True, False) -> return "ffi" + (False, False) -> return "Cffi" (_, True) -> return "Cffi-6" (_, _) -> error "Unsupported FFI library configuration case" From git at git.haskell.org Fri Oct 27 00:41:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build mkUserGuidePart with stage-0 (a86f2b1) Message-ID: <20171027004132.9EEBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a86f2b1e97fb7fa0ef08327f083049a41b278513/ghc >--------------------------------------------------------------- commit a86f2b1e97fb7fa0ef08327f083049a41b278513 Author: Ben Gamari Date: Sat Oct 8 15:10:43 2016 -0400 Build mkUserGuidePart with stage-0 This addresses GHC #12619, allowing the users guide to be built with only the stage 0 compiler. >--------------------------------------------------------------- a86f2b1e97fb7fa0ef08327f083049a41b278513 src/Builder.hs | 1 + src/GHC.hs | 5 ++++- src/Settings/Default.hs | 4 ++-- 3 files changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 6f892f2..09b87cb 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -104,6 +104,7 @@ builderPath builder = case builderProvenance builder of Just context | Just path <- programPath context -> return path | otherwise -> + -- TODO: Make builderPath total. error $ "Cannot determine builderPath for " ++ show builder ++ " in context " ++ show context Nothing -> case builder of diff --git a/src/GHC.hs b/src/GHC.hs index 0bfd131..3521e54 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -102,7 +102,10 @@ ghcSplit = "inplace/lib/bin/ghc-split" programPath :: Context -> Maybe FilePath programPath context at Context {..} | package == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) - | package `elem` [checkApiAnnotations, ghcTags, haddock, mkUserGuidePart] = + | package `elem` [mkUserGuidePart] = + case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package + _ -> Nothing + | package `elem` [checkApiAnnotations, ghcTags, haddock] = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString package _ -> Nothing | package `elem` [touchy, unlit] = case stage of diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index e35fea0..4588c4b 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -108,7 +108,7 @@ packagesStage0 = mconcat , ghcPkg, hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode - , hp2ps, unlit ] + , hp2ps, unlit, mkUserGuidePart ] , stage0 ? windowsHost ? append [touchy] , notM windowsHost ? notM iosHost ? append [terminfo] ] @@ -127,7 +127,7 @@ packagesStage1 = mconcat -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages packagesStage2 = mconcat - [ append [checkApiAnnotations, ghcTags, mkUserGuidePart] + [ append [checkApiAnnotations, ghcTags ] , buildHaddock flavour ? append [haddock] ] -- TODO: What about profilingDynamic way? Do we need platformSupportsSharedLibs? From git at git.haskell.org Fri Oct 27 00:41:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build unlit. (51c24a8) Message-ID: <20171027004136.2047E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/51c24a8f1320013d75ac9b06df60f3834b5bc0be/ghc >--------------------------------------------------------------- commit 51c24a8f1320013d75ac9b06df60f3834b5bc0be Author: Andrey Mokhov Date: Sun Jan 17 23:33:28 2016 +0000 Build unlit. See #181. [skip ci] >--------------------------------------------------------------- 51c24a8f1320013d75ac9b06df60f3834b5bc0be src/Settings/Packages.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index b7e2dac..691cd78 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -24,7 +24,8 @@ packagesStage0 = mconcat [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg , hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps] + , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode + , hp2ps, unlit ] , stage0 ? windowsHost ? append [touchy] , notM windowsHost ? notM iosHost ? append [terminfo] ] From git at git.haskell.org Fri Oct 27 00:41:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dll-split related arguments to ghc-cabal (8f5ad00) Message-ID: <20171027004136.258893A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f5ad00e81b98ab84708737d24d90457250e3873/ghc >--------------------------------------------------------------- commit 8f5ad00e81b98ab84708737d24d90457250e3873 Author: Andrey Mokhov Date: Wed Aug 30 10:47:16 2017 +0100 Drop dll-split related arguments to ghc-cabal See #404 >--------------------------------------------------------------- 8f5ad00e81b98ab84708737d24d90457250e3873 src/Settings/Builders/GhcCabal.hs | 173 -------------------------------------- 1 file changed, 173 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 4fd598b..475cc65 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -18,7 +18,6 @@ ghcCabalBuilderArgs = builder GhcCabal ? do mconcat [ arg "configure" , arg =<< pkgPath <$> getPackage , arg $ top -/- path - , dll0Args , withStaged $ Ghc CompileHs , withStaged (GhcPkg Update) , bootPackageDatabaseArgs @@ -127,175 +126,3 @@ with b = do withStaged :: (Stage -> Builder) -> Args withStaged sb = with . sb =<< getStage --- This is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument; --- * otherwise, we must collapse it into one space-separated string. -dll0Args :: Args -dll0Args = do - context <- getContext - dll0 <- expr $ buildDll0 context - withGhci <- expr ghcWithInterpreter - arg . unwords . concat $ [ modules | dll0 ] - ++ [ ghciModules | dll0 && withGhci ] -- see #9552 - where - modules = [ "Annotations" - , "ApiAnnotation" - , "Avail" - , "Bag" - , "BasicTypes" - , "Binary" - , "BooleanFormula" - , "BreakArray" - , "BufWrite" - , "Class" - , "CmdLineParser" - , "CmmType" - , "CoAxiom" - , "ConLike" - , "Coercion" - , "Config" - , "Constants" - , "CoreArity" - , "CoreFVs" - , "CoreSubst" - , "CoreSyn" - , "CoreTidy" - , "CoreUnfold" - , "CoreUtils" - , "CoreSeq" - , "CoreStats" - , "CostCentre" - , "Ctype" - , "DataCon" - , "Demand" - , "Digraph" - , "DriverPhases" - , "DynFlags" - , "Encoding" - , "ErrUtils" - , "Exception" - , "ExtsCompat46" - , "FamInstEnv" - , "FastFunctions" - , "FastMutInt" - , "FastString" - , "FastTypes" - , "Fingerprint" - , "FiniteMap" - , "ForeignCall" - , "Hooks" - , "HsBinds" - , "HsDecls" - , "HsDoc" - , "HsExpr" - , "HsImpExp" - , "HsLit" - , "PlaceHolder" - , "HsPat" - , "HsSyn" - , "HsTypes" - , "HsUtils" - , "HscTypes" - , "IOEnv" - , "Id" - , "IdInfo" - , "IfaceSyn" - , "IfaceType" - , "InstEnv" - , "Kind" - , "Lexeme" - , "Lexer" - , "ListSetOps" - , "Literal" - , "Maybes" - , "MkCore" - , "MkId" - , "Module" - , "MonadUtils" - , "Name" - , "NameEnv" - , "NameSet" - , "OccName" - , "OccurAnal" - , "OptCoercion" - , "OrdList" - , "Outputable" - , "PackageConfig" - , "Packages" - , "Pair" - , "Panic" - , "PatSyn" - , "PipelineMonad" - , "Platform" - , "PlatformConstants" - , "PprCore" - , "PrelNames" - , "PrelRules" - , "Pretty" - , "PrimOp" - , "RdrName" - , "Rules" - , "Serialized" - , "SrcLoc" - , "StaticFlags" - , "StringBuffer" - , "TcEvidence" - , "TcRnTypes" - , "TcType" - , "TrieMap" - , "TyCon" - , "Type" - , "TypeRep" - , "TysPrim" - , "TysWiredIn" - , "Unify" - , "UniqFM" - , "UniqSet" - , "UniqSupply" - , "Unique" - , "Util" - , "Var" - , "VarEnv" - , "VarSet" ] - ghciModules = [ "Bitmap" - , "BlockId" - , "ByteCodeAsm" - , "ByteCodeInstr" - , "ByteCodeItbls" - , "CLabel" - , "Cmm" - , "CmmCallConv" - , "CmmExpr" - , "CmmInfo" - , "CmmMachOp" - , "CmmNode" - , "CmmSwitch" - , "CmmUtils" - , "CodeGen.Platform" - , "CodeGen.Platform.ARM" - , "CodeGen.Platform.ARM64" - , "CodeGen.Platform.NoRegs" - , "CodeGen.Platform.PPC" - , "CodeGen.Platform.PPC_Darwin" - , "CodeGen.Platform.SPARC" - , "CodeGen.Platform.X86" - , "CodeGen.Platform.X86_64" - , "FastBool" - , "InteractiveEvalTypes" - , "MkGraph" - , "PprCmm" - , "PprCmmDecl" - , "PprCmmExpr" - , "Reg" - , "RegClass" - , "SMRep" - , "StgCmmArgRep" - , "StgCmmClosure" - , "StgCmmEnv" - , "StgCmmLayout" - , "StgCmmMonad" - , "StgCmmProf" - , "StgCmmTicky" - , "StgCmmUtils" - , "StgSyn" - , "Stream" ] From git at git.haskell.org Fri Oct 27 00:41:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #290 from bgamari/master (b7948dd) Message-ID: <20171027004136.442F73A5EC@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b7948dd53ed2fd905c2f9dda6d30ae5280c9fd6f/ghc >--------------------------------------------------------------- commit b7948dd53ed2fd905c2f9dda6d30ae5280c9fd6f Merge: d3d00b0 a86f2b1 Author: Andrey Mokhov Date: Mon Oct 10 00:27:14 2016 +0100 Merge pull request #290 from bgamari/master Build mkUserGuidePart with stage-0 >--------------------------------------------------------------- b7948dd53ed2fd905c2f9dda6d30ae5280c9fd6f src/Builder.hs | 8 ++++++-- src/GHC.hs | 5 ++++- src/Rules.hs | 8 +++++++- src/Settings/Default.hs | 4 ++-- 4 files changed, 19 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 00:41:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out common builder-related functionality into the library (29046aa) Message-ID: <20171027004140.3C1E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/29046aa3b29a26e69db1bf38015f9376bfad2ff0/ghc >--------------------------------------------------------------- commit 29046aa3b29a26e69db1bf38015f9376bfad2ff0 Author: Andrey Mokhov Date: Thu Aug 31 03:24:11 2017 +0100 Factor out common builder-related functionality into the library See #347 >--------------------------------------------------------------- 29046aa3b29a26e69db1bf38015f9376bfad2ff0 hadrian.cabal | 1 + src/Builder.hs | 127 +++++++++++++++++++++++++++++++++++++------- src/Hadrian/Builder.hs | 118 ++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Expression.hs | 9 +++- src/Hadrian/Utilities.hs | 9 +++- src/Main.hs | 4 +- src/Rules/Configure.hs | 1 + src/Rules/Install.hs | 2 +- src/Rules/Perl.hs | 3 +- src/Rules/Selftest.hs | 1 - src/Rules/SourceDist.hs | 6 +-- src/Settings/Builders/Ar.hs | 42 +-------------- src/UserSettings.hs | 8 +-- src/Utilities.hs | 117 ++++------------------------------------ 14 files changed, 266 insertions(+), 182 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 29046aa3b29a26e69db1bf38015f9376bfad2ff0 From git at git.haskell.org Fri Oct 27 00:41:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy ghc-usage.txt and ghci-usage.txt. (b5d0778) Message-ID: <20171027004140.402CB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b5d0778726fd75fd7547b89864ee8e2859ce0ccf/ghc >--------------------------------------------------------------- commit b5d0778726fd75fd7547b89864ee8e2859ce0ccf Author: Andrey Mokhov Date: Sun Jan 17 23:37:01 2016 +0000 Copy ghc-usage.txt and ghci-usage.txt. Fix #181. >--------------------------------------------------------------- b5d0778726fd75fd7547b89864ee8e2859ce0ccf src/Rules/Generate.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 025f1ee..c5386e4 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -23,7 +23,9 @@ import Settings installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" , "inplace/lib/platformConstants" - , "inplace/lib/settings" ] + , "inplace/lib/settings" + , "inplace/lib/ghc-usage.txt" + , "inplace/lib/ghci-usage.txt" ] primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -167,6 +169,8 @@ copyRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." + "inplace/lib/ghc-usage.txt" <~ "driver" + "inplace/lib/ghci-usage.txt" <~ "driver" where file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file From git at git.haskell.org Fri Oct 27 00:41:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Whitespace only (325db89) Message-ID: <20171027004144.060243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/325db89df96215ee0897187972197372e2ef34b9/ghc >--------------------------------------------------------------- commit 325db89df96215ee0897187972197372e2ef34b9 Author: Andrey Mokhov Date: Sun Oct 16 00:45:17 2016 +0100 Whitespace only >--------------------------------------------------------------- 325db89df96215ee0897187972197372e2ef34b9 src/Oracles/PackageData.hs | 68 +++++++++++++++++++++++----------------------- 1 file changed, 34 insertions(+), 34 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 84d552f..55ea812 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -13,23 +13,23 @@ data PackageData = BuildGhciLib FilePath | Synopsis FilePath | Version FilePath -data PackageDataList = CcArgs FilePath - | CSrcs FilePath - | CppArgs FilePath - | DepCcArgs FilePath - | DepExtraLibs FilePath - | DepIds FilePath - | DepIncludeDirs FilePath - | DepLdArgs FilePath - | DepLibDirs FilePath - | DepNames FilePath - | Deps FilePath - | HiddenModules FilePath - | HsArgs FilePath - | IncludeDirs FilePath - | LdArgs FilePath - | Modules FilePath - | SrcDirs FilePath +data PackageDataList = CcArgs FilePath + | CSrcs FilePath + | CppArgs FilePath + | DepCcArgs FilePath + | DepExtraLibs FilePath + | DepIds FilePath + | DepIncludeDirs FilePath + | DepLdArgs FilePath + | DepLibDirs FilePath + | DepNames FilePath + | Deps FilePath + | HiddenModules FilePath + | HsArgs FilePath + | IncludeDirs FilePath + | LdArgs FilePath + | Modules FilePath + | SrcDirs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -55,23 +55,23 @@ pkgData packageData = case packageData of -- @pkgListData Modules@ therefore returns ["Data.Array", "Data.Array.Base", ...] pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = fmap (map unquote . words) $ case packageData of - CcArgs path -> askPackageData path "CC_OPTS" - CSrcs path -> askPackageData path "C_SRCS" - CppArgs path -> askPackageData path "CPP_OPTS" - DepCcArgs path -> askPackageData path "DEP_CC_OPTS" - DepExtraLibs path -> askPackageData path "DEP_EXTRA_LIBS" - DepIds path -> askPackageData path "DEP_IPIDS" - DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" - DepLibDirs path -> askPackageData path "DEP_LIB_DIRS_SINGLE_QUOTED" - DepLdArgs path -> askPackageData path "DEP_LD_OPTS" - DepNames path -> askPackageData path "DEP_NAMES" - Deps path -> askPackageData path "DEPS" - HiddenModules path -> askPackageData path "HIDDEN_MODULES" - HsArgs path -> askPackageData path "HC_OPTS" - IncludeDirs path -> askPackageData path "INCLUDE_DIRS" - LdArgs path -> askPackageData path "LD_OPTS" - Modules path -> askPackageData path "MODULES" - SrcDirs path -> askPackageData path "HS_SRC_DIRS" + CcArgs path -> askPackageData path "CC_OPTS" + CSrcs path -> askPackageData path "C_SRCS" + CppArgs path -> askPackageData path "CPP_OPTS" + DepCcArgs path -> askPackageData path "DEP_CC_OPTS" + DepExtraLibs path -> askPackageData path "DEP_EXTRA_LIBS" + DepIds path -> askPackageData path "DEP_IPIDS" + DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" + DepLibDirs path -> askPackageData path "DEP_LIB_DIRS_SINGLE_QUOTED" + DepLdArgs path -> askPackageData path "DEP_LD_OPTS" + DepNames path -> askPackageData path "DEP_NAMES" + Deps path -> askPackageData path "DEPS" + HiddenModules path -> askPackageData path "HIDDEN_MODULES" + HsArgs path -> askPackageData path "HC_OPTS" + IncludeDirs path -> askPackageData path "INCLUDE_DIRS" + LdArgs path -> askPackageData path "LD_OPTS" + Modules path -> askPackageData path "MODULES" + SrcDirs path -> askPackageData path "HS_SRC_DIRS" where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') From git at git.haskell.org Fri Oct 27 00:41:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Builder.hs. (40b7920) Message-ID: <20171027004144.92E883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/40b792062cfe1289460323228a0b6c7487300980/ghc >--------------------------------------------------------------- commit 40b792062cfe1289460323228a0b6c7487300980 Author: Andrey Mokhov Date: Mon Jan 18 01:31:06 2016 +0000 Refactor Builder.hs. Fix #124. >--------------------------------------------------------------- 40b792062cfe1289460323228a0b6c7487300980 cfg/system.config.in | 74 ++++++++++------------------ src/Builder.hs | 126 ++++++++++++++++++++++++++---------------------- src/GHC.hs | 35 +++++++++++++- src/Settings.hs | 5 +- src/Settings/Default.hs | 34 +------------ src/Settings/Paths.hs | 5 +- src/Settings/User.hs | 14 +----- 7 files changed, 134 insertions(+), 159 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 40b792062cfe1289460323228a0b6c7487300980 From git at git.haskell.org Fri Oct 27 00:41:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: change from using "dirs" to "dir" for FFI library configuration (a3afd03) Message-ID: <20171027004148.4E6DB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a3afd03cf3b46e3344c3274606a3d42b1b08a254/ghc >--------------------------------------------------------------- commit a3afd03cf3b46e3344c3274606a3d42b1b08a254 Author: Karel Gardas Date: Mon Jan 18 10:24:42 2016 +0100 change from using "dirs" to "dir" for FFI library configuration >--------------------------------------------------------------- a3afd03cf3b46e3344c3274606a3d42b1b08a254 cfg/system.config.in | 4 ++-- src/Oracles/Config/Setting.hs | 8 ++++---- src/Rules/Libffi.hs | 3 +-- 3 files changed, 7 insertions(+), 8 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index ecbf18d..94058df 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -128,8 +128,8 @@ gmp-include-dirs = @GMP_INCLUDE_DIRS@ gmp-lib-dirs = @GMP_LIB_DIRS@ use-system-ffi = @UseSystemLibFFI@ -ffi-include-dirs = @FFIIncludeDir@ -ffi-lib-dirs = @FFILibDir@ +ffi-include-dir = @FFIIncludeDir@ +ffi-lib-dir = @FFILibDir@ # Optional Dependencies: #======================= diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 56ef1ca..f4540cc 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -47,6 +47,8 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor + | FfiIncludeDir + | FfiLibDir data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -57,8 +59,6 @@ data SettingList = ConfCcArgs Stage | HsCppArgs | IconvIncludeDirs | IconvLibDirs - | FfiIncludeDirs - | FfiLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of @@ -90,6 +90,8 @@ setting key = askConfig $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" + FfiIncludeDir -> "ffi-include-dir" + FfiLibDir -> "ffi-lib-dir" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -102,8 +104,6 @@ settingList key = fmap words $ askConfig $ case key of HsCppArgs -> "hs-cpp-args" IconvIncludeDirs -> "iconv-include-dirs" IconvLibDirs -> "iconv-lib-dirs" - FfiIncludeDirs -> "ffi-include-dirs" - FfiLibDirs -> "ffi-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index fea58ab..518389e 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,12 +70,11 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - ffi_header_dirs <- settingList FfiIncludeDirs + ffi_header_dir <- setting FfiIncludeDir use_system_ffi <- flag UseSystemFfi if use_system_ffi then do putBuild "| System supplied FFI library will be used" - let ffi_header_dir = head ffi_header_dirs forM_ ["ffi.h", "ffitarget.h"] $ \file -> do let src = ffi_header_dir -/- file copyFile src (rtsBuildPath -/- file) From git at git.haskell.org Fri Oct 27 00:41:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision: move builder-related functionality to Builder modules (f970bfc) Message-ID: <20171027004144.C66443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f970bfc05c13768aa980400ff5bf7c0c4652a224/ghc >--------------------------------------------------------------- commit f970bfc05c13768aa980400ff5bf7c0c4652a224 Author: Andrey Mokhov Date: Fri Sep 1 23:31:38 2017 +0100 Minor revision: move builder-related functionality to Builder modules >--------------------------------------------------------------- f970bfc05c13768aa980400ff5bf7c0c4652a224 src/Builder.hs | 60 ++++++++++++++++++++++++++++++++++++++++++- src/Hadrian/Builder.hs | 10 +++++++- src/Utilities.hs | 70 +++----------------------------------------------- 3 files changed, 71 insertions(+), 69 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 f970bfc05c13768aa980400ff5bf7c0c4652a224 From git at git.haskell.org Fri Oct 27 00:41:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add links to Hadrian paper and talk (2a20ce5) Message-ID: <20171027004139.D3D353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2a20ce5d54ddf43bebb63cee31e7fea363a931e5/ghc >--------------------------------------------------------------- commit 2a20ce5d54ddf43bebb63cee31e7fea363a931e5 Author: Andrey Mokhov Date: Sun Oct 16 00:37:26 2016 +0100 Add links to Hadrian paper and talk >--------------------------------------------------------------- 2a20ce5d54ddf43bebb63cee31e7fea363a931e5 README.md | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/README.md b/README.md index c39071e..01132cd 100644 --- a/README.md +++ b/README.md @@ -5,9 +5,9 @@ Hadrian Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current -[`make`-based build system][make]. If you are curious about the rationale and initial -ideas behind the project you can find more details on the [wiki page][ghc-shake-wiki] -and in this [blog post][blog-post-1]. This project was formerly known as *Shaking-up-GHC*. +[`make`-based build system][make]. If you are curious about the rationale behind the +project and the architecture of the new build system you can find more details in +this [Haskell Symposium 2016 paper][paper] and this [Haskell eXchange 2016 talk][talk]. The new build system can work side-by-side with the existing build system. Note, there is some interaction between them: they put (some) build results in the same directories, @@ -154,8 +154,8 @@ helped me endure and enjoy the project. [ghc]: https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler [shake]: https://github.com/ndmitchell/shake/blob/master/README.md [make]: https://ghc.haskell.org/trac/ghc/wiki/Building/Architecture -[ghc-shake-wiki]: https://ghc.haskell.org/trac/ghc/wiki/Building/Shake -[blog-post-1]: https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc +[paper]: https://www.staff.ncl.ac.uk/andrey.mokhov/Hadrian.pdf +[talk]: https://skillsmatter.com/skillscasts/8722-meet-hadrian-a-new-build-system-for-ghc [issues]: https://github.com/snowleopard/hadrian/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild From git at git.haskell.org Fri Oct 27 00:41:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove old issues (a20d473) Message-ID: <20171027004147.670CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a20d4738dad9c0f45f4f01e7722ee4027cfab398/ghc >--------------------------------------------------------------- commit a20d4738dad9c0f45f4f01e7722ee4027cfab398 Author: Andrey Mokhov Date: Tue Oct 18 16:14:16 2016 +0100 Remove old issues >--------------------------------------------------------------- a20d4738dad9c0f45f4f01e7722ee4027cfab398 README.md | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 01132cd..7aa4b67 100644 --- a/README.md +++ b/README.md @@ -135,11 +135,11 @@ How to contribute ----------------- The best way to contribute is to try the new build system, report the issues -you found, and attempt to fix them. Please note the codebase is very unstable -at present and we expect a lot of further refactoring. The documentation is -currently non-existent, but we are working on it: [#55][comments-issue], -[#56][doc-issue]. See also [#239](https://github.com/snowleopard/hadrian/issues/239) -for a list of issues on the critical path. +you found, and attempt to fix them. Please note: the codebase is very unstable +at present and we expect a lot of further refactoring. If you would like to +work on a particular issue, please let everyone know by adding a comment about +this. The issues that are currently on the critical path are listed in +[#239](https://github.com/snowleopard/hadrian/issues/239). Acknowledgements ---------------- @@ -169,6 +169,4 @@ helped me endure and enjoy the project. [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 [milestones]: https://github.com/snowleopard/hadrian/milestones -[comments-issue]: https://github.com/snowleopard/hadrian/issues/55 -[doc-issue]: https://github.com/snowleopard/hadrian/issues/56 [contributors]: https://github.com/snowleopard/hadrian/graphs/contributors From git at git.haskell.org Fri Oct 27 00:41:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out common Ar functionality into the library (655d175) Message-ID: <20171027004148.963DE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/655d175354db5afb5c3519cb13672209e66e5f95/ghc >--------------------------------------------------------------- commit 655d175354db5afb5c3519cb13672209e66e5f95 Author: Andrey Mokhov Date: Sun Sep 3 00:38:06 2017 +0100 Factor out common Ar functionality into the library See #347 >--------------------------------------------------------------- 655d175354db5afb5c3519cb13672209e66e5f95 hadrian.cabal | 2 +- src/Builder.hs | 40 ++++--------------------------- src/Hadrian/Builder/Ar.hs | 57 +++++++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Utilities.hs | 17 +++++++++++++- src/Oracles/Setting.hs | 17 -------------- src/Settings/Builders/Ar.hs | 8 ------- src/Settings/Default.hs | 5 ++-- 7 files changed, 82 insertions(+), 64 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 655d175354db5afb5c3519cb13672209e66e5f95 From git at git.haskell.org Fri Oct 27 00:41:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (2d60196) Message-ID: <20171027004150.E7B3E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d60196c8661bf75324525b2db37f35ccba76aa4/ghc >--------------------------------------------------------------- commit 2d60196c8661bf75324525b2db37f35ccba76aa4 Author: Andrey Mokhov Date: Tue Oct 18 16:15:58 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- 2d60196c8661bf75324525b2db37f35ccba76aa4 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 7aa4b67..ee3df66 100644 --- a/README.md +++ b/README.md @@ -138,8 +138,8 @@ The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note: the codebase is very unstable at present and we expect a lot of further refactoring. If you would like to work on a particular issue, please let everyone know by adding a comment about -this. The issues that are currently on the critical path are listed in -[#239](https://github.com/snowleopard/hadrian/issues/239). +this. The issues that are currently on the critical path and therefore require +particular attention are listed in [#239](https://github.com/snowleopard/hadrian/issues/239). Acknowledgements ---------------- From git at git.haskell.org Fri Oct 27 00:41:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' into fix_ffi_args (680766b) Message-ID: <20171027004152.27C7D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/680766bbf029a391d4c4334648aa4739274cb25f/ghc >--------------------------------------------------------------- commit 680766bbf029a391d4c4334648aa4739274cb25f Merge: a3afd03 40b7920 Author: Karel Gardas Date: Mon Jan 18 12:49:15 2016 +0100 Merge branch 'master' into fix_ffi_args Conflicts: cfg/system.config.in >--------------------------------------------------------------- 680766bbf029a391d4c4334648aa4739274cb25f cfg/system.config.in | 73 ++++++++++----------------- src/Builder.hs | 126 ++++++++++++++++++++++++++--------------------- src/GHC.hs | 35 ++++++++++++- src/Rules/Generate.hs | 6 ++- src/Settings.hs | 5 +- src/Settings/Default.hs | 34 +------------ src/Settings/Packages.hs | 3 +- src/Settings/Paths.hs | 5 +- src/Settings/User.hs | 14 +----- 9 files changed, 141 insertions(+), 160 deletions(-) From git at git.haskell.org Fri Oct 27 00:41:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ArMode to distinguish packing and unpacking of archives (46a37b1) Message-ID: <20171027004152.7C2D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46a37b154ae7b749c074c32efbcfb772d40502a8/ghc >--------------------------------------------------------------- commit 46a37b154ae7b749c074c32efbcfb772d40502a8 Author: Andrey Mokhov Date: Sun Sep 3 13:31:00 2017 +0100 Add ArMode to distinguish packing and unpacking of archives >--------------------------------------------------------------- 46a37b154ae7b749c074c32efbcfb772d40502a8 src/Builder.hs | 44 ++++++++++++++------------------------- src/Hadrian/Builder/Ar.hs | 19 +++++++++++++---- src/Rules/Gmp.hs | 7 ++++--- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Default.hs | 3 ++- 7 files changed, 42 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 46a37b154ae7b749c074c32efbcfb772d40502a8 From git at git.haskell.org Fri Oct 27 00:41:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify package database directory tracking (3e37d73) Message-ID: <20171027004154.798DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e37d7350458218964134a981125a19f095de63a/ghc >--------------------------------------------------------------- commit 3e37d7350458218964134a981125a19f095de63a Author: Andrey Mokhov Date: Tue Oct 18 23:03:50 2016 +0100 Simplify package database directory tracking >--------------------------------------------------------------- 3e37d7350458218964134a981125a19f095de63a hadrian.cabal | 1 - src/Oracles/PackageDatabase.hs | 23 ----------------------- src/Rules/Oracles.hs | 2 -- src/Rules/Register.hs | 22 +++++++++++++++------- src/Settings/Builders/GhcCabal.hs | 11 ++--------- src/Settings/Paths.hs | 6 +++++- 6 files changed, 22 insertions(+), 43 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 3e34b16..6039b01 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -35,7 +35,6 @@ executable hadrian , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData - , Oracles.PackageDatabase , Oracles.WindowsPath , Package , Predicate diff --git a/src/Oracles/PackageDatabase.hs b/src/Oracles/PackageDatabase.hs deleted file mode 100644 index efaf9ca..0000000 --- a/src/Oracles/PackageDatabase.hs +++ /dev/null @@ -1,23 +0,0 @@ -module Oracles.PackageDatabase (packageDatabaseOracle) where - -import qualified System.Directory as IO - -import Base -import Context -import Builder -import GHC -import Rules.Actions -import Settings.Builders.GhcCabal -import Settings.Paths -import Target -import UserSettings - -packageDatabaseOracle :: Rules () -packageDatabaseOracle = void $ - addOracle $ \(PackageDatabaseKey stage) -> do - let dir = packageDbDirectory stage - file = dir -/- "package.cache" - unlessM (liftIO $ IO.doesFileExist file) $ do - removeDirectory dir - build $ Target (vanillaContext stage ghcPkg) (GhcPkg stage) [] [dir] - putSuccess $ "| Successfully initialised " ++ dir diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 10767b5..af03b17 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -8,7 +8,6 @@ import qualified Oracles.DirectoryContent import qualified Oracles.LookupInPath import qualified Oracles.ModuleFiles import qualified Oracles.PackageData -import qualified Oracles.PackageDatabase import qualified Oracles.WindowsPath oracleRules :: Rules () @@ -20,5 +19,4 @@ oracleRules = do Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle - Oracles.PackageDatabase.packageDatabaseOracle Oracles.WindowsPath.windowsPathOracle diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 272e27b..d4799e3 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -9,20 +9,22 @@ import Rules.Libffi import Settings.Packages.Rts import Settings.Paths import Target +import UserSettings --- | Build package-data.mk by processing the .cabal file with ghc-cabal utility. +-- | Build rules for registering packages and initialising package databases +-- by running the @ghc-pkg@ utility. registerPackage :: [(Resource, Int)] -> Context -> Rules () -registerPackage rs context at Context {..} = do - let path = buildPath context - oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 - pkgConf = packageDbDirectory stage -/- pkgNameString package +registerPackage rs context at Context {..} = when (stage <= Stage1) $ do + let dir = packageDbDirectory stage - when (stage <= Stage1) $ matchVersionedFilePath pkgConf "conf" ?> \conf -> do + matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do -- This produces inplace-pkg-config. TODO: Add explicit tracking. need [pkgDataFile context] -- Post-process inplace-pkg-config. TODO: remove, see #113, #148. - let pkgConfig = oldPath -/- "inplace-pkg-config" + let path = buildPath context + oldPath = pkgPath package -/- contextDirectory context + pkgConfig = oldPath -/- "inplace-pkg-config" oldBuildPath = oldPath -/- "build" fixPkgConf = unlines . map @@ -52,3 +54,9 @@ registerPackage rs context at Context {..} = do . lines fixFile rtsConf fixRtsConf + + when (package == ghc) $ packageDbStamp stage %> \stamp -> do + removeDirectory dir + buildWithResources rs $ Target (vanillaContext stage ghc) (GhcPkg stage) [] [dir] + writeFileLines stamp [] + putSuccess $ "| Successfully initialised " ++ dir diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index fffb2c0..5569ba0 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,7 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( - ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, - PackageDatabaseKey (..), buildDll0 + ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, buildDll0 ) where import Base @@ -87,16 +86,10 @@ configureArgs = do , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" $ argStagedBuilderPath (Cc CompileC) ] -newtype PackageDatabaseKey = PackageDatabaseKey Stage - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -initialisePackageDatabase :: Stage -> Action () -initialisePackageDatabase = askOracle . PackageDatabaseKey - bootPackageDatabaseArgs :: Args bootPackageDatabaseArgs = do stage <- getStage - lift $ initialisePackageDatabase stage + lift $ need [packageDbStamp stage] stage0 ? do path <- getTopDirectory prefix <- ifM (builder Ghc) (return "-package-db ") (return "--package-db=") diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index ad200f8..6382fcc 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -2,7 +2,7 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, - packageDbDirectory, bootPackageConstraints, packageDependencies + packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies ) where import Base @@ -92,6 +92,10 @@ packageDbDirectory :: Stage -> FilePath packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" +-- | We use a stamp file to track the existence of a package database. +packageDbStamp :: Stage -> FilePath +packageDbStamp stage = packageDbDirectory stage -/- ".stamp" + -- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do From git at git.haskell.org Fri Oct 27 00:41:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: pass ffi include/library directories to HsCpp (39f0e7a) Message-ID: <20171027004155.E0F8B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39f0e7a2fe46ea6e6fc1cc86685fd8729a4cf4c7/ghc >--------------------------------------------------------------- commit 39f0e7a2fe46ea6e6fc1cc86685fd8729a4cf4c7 Author: Karel Gardas Date: Mon Jan 18 20:06:55 2016 +0100 pass ffi include/library directories to HsCpp >--------------------------------------------------------------- 39f0e7a2fe46ea6e6fc1cc86685fd8729a4cf4c7 src/Settings/Packages/Rts.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e684b7a..58b76cf 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -51,6 +51,8 @@ rtsPackageArgs = package rts ? do path <- getTargetPath top <- getTopDirectory libffiName <- lift $ rtsLibffiLibraryName + ffiIncludeDir <- getSetting FfiIncludeDir + ffiLibraryDir <- getSetting FfiLibDir mconcat [ builderGcc ? mconcat [ arg "-Irts" @@ -92,8 +94,8 @@ rtsPackageArgs = package rts ? do , builder HsCpp ? mconcat [ arg ("-DTOP=" ++ quote top) - , arg "-DFFI_INCLUDE_DIR=" - , arg "-DFFI_LIB_DIR=" + , arg ("-DFFI_INCLUDE_DIR=" ++ quote ffiIncludeDir) + , arg ("-DFFI_LIB_DIR=" ++ quote ffiLibraryDir) , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] From git at git.haskell.org Fri Oct 27 00:41:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Mark as temporarily out-of-date (c3f0f40) Message-ID: <20171027004156.3AA533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3f0f40954cedc37bc2d0e5c724ccd20d7fa51ed/ghc >--------------------------------------------------------------- commit c3f0f40954cedc37bc2d0e5c724ccd20d7fa51ed Author: Andrey Mokhov Date: Fri Sep 8 23:38:45 2017 +0100 Mark as temporarily out-of-date >--------------------------------------------------------------- c3f0f40954cedc37bc2d0e5c724ccd20d7fa51ed doc/user-settings.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/doc/user-settings.md b/doc/user-settings.md index 9207f7f..1898dcd 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,3 +1,6 @@ +**Note:** This document is currently out-of-date and will be fixed after +[a major refactoring](https://github.com/snowleopard/hadrian/issues/347). + # User settings You can customise Hadrian by copying the file `hadrian/src/UserSettings.hs` to From git at git.haskell.org Fri Oct 27 00:45:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build hpc-bin. (0c06eac) Message-ID: <20171027004529.C73EB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c06eaca884d2e2606cc7ccb0726fdb520164b5d/ghc >--------------------------------------------------------------- commit 0c06eaca884d2e2606cc7ccb0726fdb520164b5d Author: Andrey Mokhov Date: Fri Jan 29 01:07:51 2016 +0000 Build hpc-bin. See #187. >--------------------------------------------------------------- 0c06eaca884d2e2606cc7ccb0726fdb520164b5d src/Builder.hs | 2 ++ src/GHC.hs | 3 +++ 2 files changed, 5 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index bfb757f..71399a7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -36,6 +36,7 @@ data Builder = Alex | GhcPkg Stage | Haddock | Happy + | Hpc | HsColour | HsCpp | Hsc2Hs @@ -63,6 +64,7 @@ builderProvenance = \case GhcCabalHsColour -> builderProvenance $ GhcCabal GhcPkg stage -> if stage > Stage0 then Just (Stage0, ghcPkg) else Nothing Haddock -> Just (Stage2, haddock) + Hpc -> Just (Stage1, hpcBin) Hsc2Hs -> Just (Stage0, hsc2hs) Unlit -> Just (Stage0, unlit) _ -> Nothing diff --git a/src/GHC.hs b/src/GHC.hs index 7504c27..0262243 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -112,6 +112,9 @@ programPath stage pkg | pkg `elem` [touchy, unlit] = case stage of Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe _ -> Nothing + | pkg == hpcBin = case stage of + Stage1 -> Just $ inplaceProgram "hpc" + _ -> Nothing | isProgram pkg = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString pkg _ -> Just . installProgram $ pkgNameString pkg From git at git.haskell.org Fri Oct 27 00:45:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't generate in-tree directories by ghc-cabal (94c88da) Message-ID: <20171027004533.E9BD33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/94c88da1c738815f2986439a956d93fdbc707237/ghc >--------------------------------------------------------------- commit 94c88da1c738815f2986439a956d93fdbc707237 Author: Andrey Mokhov Date: Sat Nov 26 23:38:35 2016 +0000 Don't generate in-tree directories by ghc-cabal See #113 >--------------------------------------------------------------- 94c88da1c738815f2986439a956d93fdbc707237 src/Oracles/ModuleFiles.hs | 5 ++-- src/Oracles/PackageData.hs | 6 ++--- src/Rules/Data.hs | 57 +++++++++------------------------------ src/Rules/Register.hs | 18 +++++-------- src/Settings/Builders/Common.hs | 1 - src/Settings/Builders/Ghc.hs | 5 ++-- src/Settings/Builders/GhcCabal.hs | 4 ++- src/Settings/Builders/GhcPkg.hs | 6 ++--- src/Settings/Builders/Hsc2Hs.hs | 4 +-- src/Settings/Packages/GhcCabal.hs | 6 ++--- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Packages/Touchy.hs | 2 +- src/Settings/Packages/Unlit.hs | 2 +- src/Settings/Path.hs | 18 ++++++++++--- 14 files changed, 56 insertions(+), 80 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 94c88da1c738815f2986439a956d93fdbc707237 From git at git.haskell.org Fri Oct 27 00:45:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision, don't copy Hadrian binaries (6d420eb) Message-ID: <20171027004529.BF42F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d420eb40cf4ebe18c4b556b0449972b6500eeb2/ghc >--------------------------------------------------------------- commit 6d420eb40cf4ebe18c4b556b0449972b6500eeb2 Author: Andrey Mokhov Date: Wed Nov 2 01:55:16 2016 +0000 Minor revision, don't copy Hadrian binaries >--------------------------------------------------------------- 6d420eb40cf4ebe18c4b556b0449972b6500eeb2 src/Rules/SourceDist.hs | 156 +++++++++++++++++++++++++----------------------- 1 file changed, 80 insertions(+), 76 deletions(-) diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index d56eb38..7a60238 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -12,18 +12,18 @@ sourceDistRules = do "sdist-ghc" ~> do version <- setting ProjectVersion need ["sdistprep/ghc-" ++ version ++ "-src.tar.xz"] - putSuccess "| Done. " + putSuccess "| Done" "sdistprep/ghc-*-src.tar.xz" %> \fname -> do - let tarName = takeFileName fname - treePath = "sdistprep/ghc" -/- dropTarXz tarName + let tarName = takeFileName fname + dropTarXz = dropExtension . dropExtension + treePath = "sdistprep/ghc" -/- dropTarXz tarName prepareTree treePath - runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." -/- tarName, dropTarXz tarName] + runBuilderWith [Cwd "sdistprep/ghc"] Tar + ["cJf", ".." -/- tarName, dropTarXz tarName] "GIT_COMMIT_ID" %> \fname -> - setting ProjectGitCommitId >>= writeFileChanged fname + writeFileChanged fname =<< setting ProjectGitCommitId "VERSION" %> \fname -> - setting ProjectVersion >>= writeFileChanged fname - where - dropTarXz = dropExtension . dropExtension + writeFileChanged fname =<< setting ProjectVersion prepareTree :: FilePath -> Action () prepareTree dest = do @@ -31,74 +31,78 @@ prepareTree dest = do mapM_ cpFile srcFiles where cpFile a = copyFile a (dest -/- a) - cpDir a = copyDirectoryContents (Not excluded) a (dest -/- takeFileName a) + cpDir a = copyDirectoryContents (Not excluded) a (dest -/- a) excluded = Or - [ Test "//.*" - , Test "//#*" - , Test "//*-SAVE" - , Test "//*.orig" - , Test "//*.rej" - , Test "//*~" - , Test "//autom4te*" - , Test "//dist" - , Test "//log" - , Test "//stage0" - , Test "//stage1" - , Test "//stage2" - , Test "//stage3" - , Test "hadrian/cabal.sandbox.config" - , Test "hadrian/cfg/system.config" - , Test "hadrian/dist" - , Test "hadrian/UserSettings.hs" - , Test "libraries//*.buildinfo" - , Test "libraries//GNUmakefile" - , Test "libraries//config.log" - , Test "libraries//config.status" - , Test "libraries//configure" - , Test "libraries//ghc.mk" - , Test "libraries//include/Hs*Config.h" - , Test "libraries/dph" - , Test "libraries/parallel" - , Test "libraries/primitive" - , Test "libraries/random" - , Test "libraries/stm" - , Test "libraries/vector" - , Test "mk/build.mk" ] + [ Test "//.*" + , Test "//#*" + , Test "//*-SAVE" + , Test "//*.orig" + , Test "//*.rej" + , Test "//*~" + , Test "//autom4te*" + , Test "//dist" + , Test "//log" + , Test "//stage0" + , Test "//stage1" + , Test "//stage2" + , Test "//stage3" + , Test "hadrian/.cabal-sandbox" + , Test "hadrian/.stack-work" + , Test "hadrian/UserSettings.hs" + , Test "hadrian/cabal.sandbox.config" + , Test "hadrian/cfg/system.config" + , Test "hadrian/bin" + , Test "hadrian/dist" + , Test "hadrian/dist-newstyle" + , Test "libraries//*.buildinfo" + , Test "libraries//GNUmakefile" + , Test "libraries//config.log" + , Test "libraries//config.status" + , Test "libraries//configure" + , Test "libraries//ghc.mk" + , Test "libraries//include/Hs*Config.h" + , Test "libraries/dph" + , Test "libraries/parallel" + , Test "libraries/primitive" + , Test "libraries/random" + , Test "libraries/stm" + , Test "libraries/vector" + , Test "mk/build.mk" ] srcDirs = - [ "bindisttest" - , "compiler" - , "distrib" - , "docs" - , "docs" - , "driver" - , "ghc" - , "hadrian" - , "includes" - , "iserv" - , "libffi" - , "libffi-tarballs" - , "libraries" - , "mk" - , "rts" - , "rules" - , "utils" ] + [ "bindisttest" + , "compiler" + , "distrib" + , "docs" + , "docs" + , "driver" + , "ghc" + , "hadrian" + , "includes" + , "iserv" + , "libffi" + , "libffi-tarballs" + , "libraries" + , "mk" + , "rts" + , "rules" + , "utils" ] srcFiles = - [ "ANNOUNCE" - , "GIT_COMMIT_ID" - , "HACKING.md" - , "INSTALL.md" - , "LICENSE" - , "MAKEHELP.md" - , "Makefile" - , "README.md" - , "VERSION" - , "aclocal.m4" - , "boot" - , "config.guess" - , "config.sub" - , "configure" - , "configure.ac" - , "ghc.mk" - , "install-sh" - , "packages" - , "settings.in" ] + [ "ANNOUNCE" + , "GIT_COMMIT_ID" + , "HACKING.md" + , "INSTALL.md" + , "LICENSE" + , "MAKEHELP.md" + , "Makefile" + , "README.md" + , "VERSION" + , "aclocal.m4" + , "boot" + , "config.guess" + , "config.sub" + , "configure" + , "configure.ac" + , "ghc.mk" + , "install-sh" + , "packages" + , "settings.in" ] From git at git.haskell.org Fri Oct 27 00:45:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add validate target. (a9f9876) Message-ID: <20171027004533.E17313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9f98769fbd07b93342cd263f6dcf3c6e51e4afd/ghc >--------------------------------------------------------------- commit a9f98769fbd07b93342cd263f6dcf3c6e51e4afd Author: Andrey Mokhov Date: Fri Jan 29 01:18:51 2016 +0000 Add validate target. See #187. >--------------------------------------------------------------- a9f98769fbd07b93342cd263f6dcf3c6e51e4afd src/Rules/Actions.hs | 16 ++++++++++++---- src/Test.hs | 6 +++++- 2 files changed, 17 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 0e4961f..d85e0dc 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,8 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, - moveDirectory, fixFile, runConfigure, runMake, applyPatch, renderLibrary, - renderProgram, runBuilder, makeExecutable + moveDirectory, fixFile, runConfigure, runMake, runMakeVerbose, applyPatch, + renderLibrary, renderProgram, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -111,7 +111,13 @@ runConfigure dir opts args = do opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] runMake :: FilePath -> [String] -> Action () -runMake dir args = do +runMake = runMakeWithVerbosity False + +runMakeVerbose :: FilePath -> [String] -> Action () +runMakeVerbose = runMakeWithVerbosity True + +runMakeWithVerbosity :: Bool -> FilePath -> [String] -> Action () +runMakeWithVerbosity verbose dir args = do need [dir -/- "Makefile"] path <- builderPath Make @@ -125,7 +131,9 @@ runMake dir args = do let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ fixPath ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args + if verbose + then cmd Shell fixPath ["-C", dir] args + else quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do diff --git a/src/Test.hs b/src/Test.hs index 547e286..06c82eb 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -7,12 +7,16 @@ import GHC (rts, libffi) import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory +import Rules.Actions import Settings.Packages import Settings.User -- TODO: clean up after testing testRules :: Rules () -testRules = +testRules = do + "validate" ~> do + runMakeVerbose "testsuite/tests" ["fast"] + "test" ~> do let quote s = "\"" ++ s ++ "\"" yesNo x = quote $ if x then "YES" else "NO" From git at git.haskell.org Fri Oct 27 00:45:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on Stage2 GHC, ghc-pkg and hpc in validate target. (304840f) Message-ID: <20171027004537.7F25B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/304840f8073ef7b3369601a97afb0605326e79e3/ghc >--------------------------------------------------------------- commit 304840f8073ef7b3369601a97afb0605326e79e3 Author: Andrey Mokhov Date: Sat Jan 30 23:58:57 2016 +0000 Depend on Stage2 GHC, ghc-pkg and hpc in validate target. See #187. [skip ci] >--------------------------------------------------------------- 304840f8073ef7b3369601a97afb0605326e79e3 src/Builder.hs | 2 ++ src/Test.hs | 3 +++ 2 files changed, 5 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index 71399a7..80fc4ba 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -124,6 +124,8 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath +-- TODO: split into two functions: needBuilder (without laxDependencies) and +-- unsafeNeedBuilder (with the laxDependencies parameter) -- | Make sure a builder exists on the given path and rebuild it if out of date. -- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). diff --git a/src/Test.hs b/src/Test.hs index 06c82eb..a79c9fc 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -15,6 +15,9 @@ import Settings.User testRules :: Rules () testRules = do "validate" ~> do + needBuilder False $ Ghc Stage2 -- TODO: get rid of False parameters + needBuilder False $ GhcPkg Stage1 + needBuilder False $ Hpc runMakeVerbose "testsuite/tests" ["fast"] "test" ~> do From git at git.haskell.org Fri Oct 27 00:45:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant clean up after ghc-cabal (e93f7a4) Message-ID: <20171027004537.814763A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e93f7a4181308147b3d2c9211eb6d63e51cea188/ghc >--------------------------------------------------------------- commit e93f7a4181308147b3d2c9211eb6d63e51cea188 Author: Andrey Mokhov Date: Sun Nov 27 00:32:02 2016 +0000 Drop redundant clean up after ghc-cabal See #113 >--------------------------------------------------------------- e93f7a4181308147b3d2c9211eb6d63e51cea188 src/Rules/Clean.hs | 6 ------ 1 file changed, 6 deletions(-) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index eebb26d..a2cf849 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -1,8 +1,6 @@ module Rules.Clean (cleanRules) where import Base -import Package -import Settings import Settings.Path import Stage import UserSettings @@ -16,10 +14,6 @@ cleanRules = do removeDirectory programInplacePath removeDirectory "inplace/lib" removeDirectory "sdistprep" - putBuild $ "| Remove files generated by ghc-cabal..." - forM_ knownPackages $ \pkg -> - forM_ [Stage0 ..] $ \stage -> - quietly . removeDirectory $ pkgPath pkg -/- stageDirectory stage putBuild $ "| Remove Hadrian files..." removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " From git at git.haskell.org Fri Oct 27 00:45:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on validate target (4cc0abb) Message-ID: <20171027004541.672003A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4cc0abb94f94db16533a6737de3e892409e389fc/ghc >--------------------------------------------------------------- commit 4cc0abb94f94db16533a6737de3e892409e389fc Author: Andrey Mokhov Date: Sun Jan 31 00:00:48 2016 +0000 Add a note on validate target See #187. [skip ci] >--------------------------------------------------------------- 4cc0abb94f94db16533a6737de3e892409e389fc README.md | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 56e13ad..0a60d11 100644 --- a/README.md +++ b/README.md @@ -83,8 +83,13 @@ the previous build are still in the GHC tree. #### Testing -* `shake-build/build.sh test` runs GHC tests. The current implementation is very -limited and cannot replace the `validate` script (see [#187][validation-issue]). +* `shake-build/build.sh validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` +directory. This can be used instead of `sh validate --fast --no-clean` in the existing build system. +Note: this will rebuild Stage2 GHC, `ghc-pkg` and `hpc` if they are out of date. + +* `shake-build/build.sh test` runs GHC tests by calling the `testsuite/driver/runtests.py` python +script with appropriate flags. The current implementation is limited and cannot replace the +`validate` script (see [#187][validation-issue]). * `shake-build/build.sh selftest` runs tests of the build system. Current test coverage is close to zero (see [#197][test-issue]). From git at git.haskell.org Fri Oct 27 00:45:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Put RTS's package configuration into inplace-pkg-config for consistency (e3b5f08) Message-ID: <20171027004541.6294C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3b5f08db5ea710b36a696e38f10263c955b86eb/ghc >--------------------------------------------------------------- commit e3b5f08db5ea710b36a696e38f10263c955b86eb Author: Andrey Mokhov Date: Sun Nov 27 01:01:03 2016 +0000 Put RTS's package configuration into inplace-pkg-config for consistency >--------------------------------------------------------------- e3b5f08db5ea710b36a696e38f10263c955b86eb src/Rules/Register.hs | 4 ++-- src/Settings/Builders/GhcPkg.hs | 3 +-- src/Settings/Packages/Rts.hs | 6 +----- src/Settings/Path.hs | 6 +++++- 4 files changed, 9 insertions(+), 10 deletions(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index f912b20..b7e12d1 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -22,10 +22,10 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do -- This produces inplace-pkg-config. TODO: Add explicit tracking. need [pkgDataFile context] - -- Post-process inplace-pkg-config. TODO: remove, see #113, #148. + -- Post-process inplace-pkg-config. top <- topDirectory let path = buildPath context - pkgConfig = path -/- "inplace-pkg-config" + pkgConfig = inplacePkgConfig context oldPath = top -/- path "build" fixFile pkgConfig $ unlines . map (replace oldPath path) . lines diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index b17f36a..5156d71 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -13,10 +13,9 @@ initArgs = initPredicate ? mconcat [ arg "init", arg =<< getOutput ] updateArgs :: Args updateArgs = notM initPredicate ? do - path <- getBuildPath verbosity <- lift $ getVerbosity mconcat [ arg "update" , arg "--force" , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs - , arg $ path -/- "inplace-pkg-config" ] + , arg . inplacePkgConfig =<< getContext ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 4c3cc99..40b85e4 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -18,7 +18,7 @@ rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" rtsConf :: FilePath -rtsConf = buildPath rtsContext -/- "package.conf.inplace" +rtsConf = inplacePkgConfig rtsContext rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do @@ -96,10 +96,6 @@ rtsPackageArgs = package rts ? do , builder Ghc ? arg "-Irts" - , builder (GhcPkg Stage1) ? mconcat - [ remove [path -/- "inplace-pkg-config"] - , arg rtsConf ] - , builder HsCpp ? append [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 0a22077..cbe1612 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -4,7 +4,7 @@ module Settings.Path ( gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath + installPath, autogenPath, inplacePkgConfig ) where import Base @@ -60,6 +60,10 @@ autogenPath context at Context {..} where autogen dir = buildPath context -/- dir -/- "autogen" +-- | Path to inplace package configuration of a given 'Context'. +inplacePkgConfig :: Context -> FilePath +inplacePkgConfig context = buildPath context -/- "inplace-pkg-config" + -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath pkgDataFile context = buildPath context -/- "package-data.mk" From git at git.haskell.org Fri Oct 27 00:45:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: #189, clear PWD so we can be sure it has the Unix-style path even on Windows (fce6921) Message-ID: <20171027004545.57EE53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fce6921fca6c3dd14f9a1b0a4c0940db2a8f7841/ghc >--------------------------------------------------------------- commit fce6921fca6c3dd14f9a1b0a4c0940db2a8f7841 Author: Neil Mitchell Date: Mon Feb 1 20:57:56 2016 +0000 #189, clear PWD so we can be sure it has the Unix-style path even on Windows >--------------------------------------------------------------- fce6921fca6c3dd14f9a1b0a4c0940db2a8f7841 src/Environment.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Environment.hs b/src/Environment.hs index fd207ed..e674f83 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -11,6 +11,11 @@ setupEnvironment = do -- ghc-cabal refuses to work when GHC_PACKAGE_PATH is set (e.g. by Stack) unsetEnv "GHC_PACKAGE_PATH" + -- in MinGW if PWD is set to a Windows "C:\\" style path then configure + -- `pwd` will return the Windows path, and then modifying $PATH will fail. + -- See https://github.com/snowleopard/shaking-up-ghc/issues/189 for details. + unsetEnv "PWD" + -- On Windows, some path variables start a prefix like "C:\\" which may -- lead to failures of scripts such as autoreconf. One particular variable -- which causes issues is ACLOCAL_PATH. At the moment we simply reset it From git at git.haskell.org Fri Oct 27 00:45:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Data and Register build rules (7ebb204) Message-ID: <20171027004545.5F5093A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ebb2045222d9c800d523ed93e32680d8b07fc10/ghc >--------------------------------------------------------------- commit 7ebb2045222d9c800d523ed93e32680d8b07fc10 Author: Andrey Mokhov Date: Sun Nov 27 01:48:25 2016 +0000 Refactor Data and Register build rules >--------------------------------------------------------------- 7ebb2045222d9c800d523ed93e32680d8b07fc10 src/Rules/Data.hs | 21 ++++++++++++++++++++- src/Rules/Register.hs | 39 ++++----------------------------------- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Path.hs | 6 +++--- 5 files changed, 29 insertions(+), 41 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index e16f03b..1314cc4 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -9,6 +9,7 @@ import Oracles.Dependencies import Oracles.Path import Rules.Generate import Rules.Libffi +import Settings.Packages.Rts import Settings.Path import Target import UserSettings @@ -17,7 +18,8 @@ import Util -- | Build @package-data.mk@ by using ghc-cabal utility to process .cabal files. buildPackageData :: Context -> Rules () buildPackageData context at Context {..} = do - let cabalFile = pkgCabalFile package + let path = buildPath context + cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile context @@ -35,6 +37,23 @@ buildPackageData context at Context {..} = do build $ Target context GhcCabal [cabalFile] [mk] postProcessPackageData context mk + pkgInplaceConfig context %> \conf -> do + need [dataFile] -- ghc-cabal builds inplace package configuration file + if package == rts + then do + need [rtsConfIn] + build $ Target context HsCpp [rtsConfIn] [conf] + fixFile conf $ unlines + . map + ( replace "\"\"" "" + . replace "rts/dist/build" rtsBuildPath + . replace "includes/dist-derivedconstants/header" generatedPath ) + . lines + else do + top <- topDirectory + let oldPath = top -/- path "build" + fixFile conf $ unlines . map (replace oldPath path) . lines + -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps. priority 2.0 $ do when (package `elem` [hp2ps, rts, touchy, unlit]) $ dataFile %> diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index b7e12d1..19ce0e3 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -4,9 +4,6 @@ import Base import Context import Expression import GHC -import Oracles.Path -import Rules.Libffi -import Settings.Packages.Rts import Settings.Path import Target import UserSettings @@ -16,40 +13,12 @@ import Util -- by running the @ghc-pkg@ utility. registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context at Context {..} = when (stage <= Stage1) $ do - let dir = packageDbDirectory stage + let confIn = pkgInplaceConfig context + dir = packageDbDirectory stage matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do - -- This produces inplace-pkg-config. TODO: Add explicit tracking. - need [pkgDataFile context] - - -- Post-process inplace-pkg-config. - top <- topDirectory - let path = buildPath context - pkgConfig = inplacePkgConfig context - oldPath = top -/- path "build" - - fixFile pkgConfig $ unlines . map (replace oldPath path) . lines - - buildWithResources rs $ Target context (GhcPkg stage) [pkgConfig] [conf] - - when (package == rts && stage == Stage1) $ do - packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do - need [rtsConf] - buildWithResources rs $ Target context (GhcPkg stage) [rtsConf] [conf] - - rtsConf %> \_ -> do - need [pkgDataFile rtsContext, rtsConfIn] - build $ Target context HsCpp [rtsConfIn] [rtsConf] - - let fixRtsConf = unlines - . map - ( replace "\"\"" "" - . replace "rts/dist/build" rtsBuildPath - . replace "includes/dist-derivedconstants/header" generatedPath ) - . filter (not . null) - . lines - - fixFile rtsConf fixRtsConf + need [confIn] + buildWithResources rs $ Target context (GhcPkg stage) [confIn] [conf] when (package == ghc) $ packageDbStamp stage %> \stamp -> do removeDirectory dir diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index 5156d71..15d5249 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -18,4 +18,4 @@ updateArgs = notM initPredicate ? do , arg "--force" , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs - , arg . inplacePkgConfig =<< getContext ] + , arg . pkgInplaceConfig =<< getContext ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 40b85e4..e7c3a60 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -18,7 +18,7 @@ rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" rtsConf :: FilePath -rtsConf = inplacePkgConfig rtsContext +rtsConf = pkgInplaceConfig rtsContext rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index cbe1612..934a0ec 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -4,7 +4,7 @@ module Settings.Path ( gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath, inplacePkgConfig + installPath, autogenPath, pkgInplaceConfig ) where import Base @@ -61,8 +61,8 @@ autogenPath context at Context {..} autogen dir = buildPath context -/- dir -/- "autogen" -- | Path to inplace package configuration of a given 'Context'. -inplacePkgConfig :: Context -> FilePath -inplacePkgConfig context = buildPath context -/- "inplace-pkg-config" +pkgInplaceConfig :: Context -> FilePath +pkgInplaceConfig context = buildPath context -/- "inplace-pkg-config" -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath From git at git.haskell.org Fri Oct 27 00:45:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #199 from ndmitchell/master (0cf18c9) Message-ID: <20171027004549.6D89D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0cf18c9864f5524260c6cad87ec390ce06ad20ff/ghc >--------------------------------------------------------------- commit 0cf18c9864f5524260c6cad87ec390ce06ad20ff Merge: 4cc0abb fce6921 Author: Andrey Mokhov Date: Mon Feb 1 21:02:57 2016 +0000 Merge pull request #199 from ndmitchell/master Clear PWD >--------------------------------------------------------------- 0cf18c9864f5524260c6cad87ec390ce06ad20ff src/Environment.hs | 5 +++++ 1 file changed, 5 insertions(+) From git at git.haskell.org Fri Oct 27 00:45:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move RTS path settings to Settings.Path (46ef16f) Message-ID: <20171027004549.7DF283A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46ef16f18f752ad2df2c92fafdf5c208a4589e2c/ghc >--------------------------------------------------------------- commit 46ef16f18f752ad2df2c92fafdf5c208a4589e2c Author: Andrey Mokhov Date: Sun Nov 27 11:42:25 2016 +0000 Move RTS path settings to Settings.Path >--------------------------------------------------------------- 46ef16f18f752ad2df2c92fafdf5c208a4589e2c src/Rules.hs | 1 - src/Rules/Data.hs | 1 - src/Rules/Generate.hs | 1 - src/Settings/Packages/Rts.hs | 14 +------------- src/Settings/Path.hs | 10 +++++++++- 5 files changed, 10 insertions(+), 17 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 506fe2c..832bf4c 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -19,7 +19,6 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings -import Settings.Packages.Rts import Settings.Path allStages :: [Stage] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 1314cc4..5c8a63b 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -9,7 +9,6 @@ import Oracles.Dependencies import Oracles.Path import Rules.Generate import Rules.Libffi -import Settings.Packages.Rts import Settings.Path import Target import UserSettings diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index e84313a..5d557b4 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -17,7 +17,6 @@ import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Rules.Libffi -import Settings.Packages.Rts import Settings.Path import Target import UserSettings diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e7c3a60..d10c6f0 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,6 +1,4 @@ -module Settings.Packages.Rts ( - rtsPackageArgs, rtsConfIn, rtsConf, rtsContext, rtsLibffiLibraryName - ) where +module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibraryName) where import Base import GHC @@ -9,16 +7,6 @@ import Oracles.Config.Setting import Oracles.Path import Predicate import Settings -import Settings.Path - -rtsContext :: Context -rtsContext = vanillaContext Stage1 rts - -rtsConfIn :: FilePath -rtsConfIn = pkgPath rts -/- "package.conf.in" - -rtsConf :: FilePath -rtsConf = pkgInplaceConfig rtsContext rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 934a0ec..8999300 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -4,7 +4,7 @@ module Settings.Path ( gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath, pkgInplaceConfig + installPath, autogenPath, pkgInplaceConfig, rtsContext, rtsConfIn ) where import Base @@ -100,6 +100,14 @@ pkgFile context prefix suffix = do componentId <- pkgData $ ComponentId path return $ path -/- prefix ++ componentId ++ suffix +-- | RTS is considered a Stage1 package. This determines RTS build path. +rtsContext :: Context +rtsContext = vanillaContext Stage1 rts + +-- | Path to RTS package configuration file, to be processed by HsCpp. +rtsConfIn :: FilePath +rtsConfIn = pkgPath rts -/- "package.conf.in" + -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" From git at git.haskell.org Fri Oct 27 00:45:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add includesDependencies to primops.txt rule. (1329a94) Message-ID: <20171027004552.E8EF63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1329a948ad88a8dec33834a4394024bae715df3b/ghc >--------------------------------------------------------------- commit 1329a948ad88a8dec33834a4394024bae715df3b Author: Andrey Mokhov Date: Tue Feb 2 12:26:45 2016 +0000 Add includesDependencies to primops.txt rule. Fix #201. >--------------------------------------------------------------- 1329a948ad88a8dec33834a4394024bae715df3b src/Rules/Generate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index d98527c..7538470 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -134,7 +134,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = -- TODO: needing platformH is ugly and fragile when (pkg == compiler) $ primopsTxt stage %> \file -> do - need [platformH stage, primopsSource] + need $ [platformH stage, primopsSource] ++ includesDependencies build $ fullTarget target HsCpp [primopsSource] [file] -- TODO: why different folders for generated files? From git at git.haskell.org Fri Oct 27 00:45:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move custom contexts to Settings.Path (72a08b0) Message-ID: <20171027004553.09F113A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72a08b0e226c62396437c29e019a61dba03e48fd/ghc >--------------------------------------------------------------- commit 72a08b0e226c62396437c29e019a61dba03e48fd Author: Andrey Mokhov Date: Sun Nov 27 12:01:41 2016 +0000 Move custom contexts to Settings.Path >--------------------------------------------------------------- 72a08b0e226c62396437c29e019a61dba03e48fd src/Rules/Data.hs | 1 - src/Rules/Gmp.hs | 3 --- src/Rules/Libffi.hs | 9 +-------- src/Settings/Path.hs | 31 ++++++++++++++++++++++--------- 4 files changed, 23 insertions(+), 21 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 5c8a63b..58164d8 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -8,7 +8,6 @@ import Oracles.Config.Setting import Oracles.Dependencies import Oracles.Path import Rules.Generate -import Rules.Libffi import Settings.Path import Target import UserSettings diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 2409b6e..1442118 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -14,9 +14,6 @@ import Util gmpBase :: FilePath gmpBase = pkgPath integerGmp -/- "gmp" -gmpContext :: Context -gmpContext = vanillaContext Stage1 integerGmp - gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 8d72017..989288e 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,21 +1,14 @@ -module Rules.Libffi (rtsBuildPath, libffiRules, libffiDependencies) where +module Rules.Libffi (libffiRules, libffiDependencies) where import Settings.Builders.Common import Settings.Packages.Rts import Target import Util --- TODO: this should be moved elsewhere -rtsBuildPath :: FilePath -rtsBuildPath = buildPath rtsContext - -- TODO: Why copy these include files into rts? Keep in libffi! libffiDependencies :: [FilePath] libffiDependencies = (rtsBuildPath -/-) <$> [ "ffi.h", "ffitarget.h" ] -libffiContext :: Context -libffiContext = vanillaContext Stage1 libffi - libffiLibrary :: FilePath libffiLibrary = libffiBuildPath -/- "inst/lib/libffi.a" diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 8999300..9e88ca6 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -1,10 +1,11 @@ module Settings.Path ( stageDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, - gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, - pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, - packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath, pkgInplaceConfig, rtsContext, rtsConfIn + pkgLibraryFile0, pkgGhciLibraryFile, gmpContext, gmpBuildPath, gmpObjects, + gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiContext, libffiBuildPath, + rtsContext, rtsBuildPath, rtsConfIn, shakeFilesPath,packageDbDirectory, + pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, + objectPath, programInplacePath, programInplaceLibPath, installPath, + autogenPath, pkgInplaceConfig ) where import Base @@ -100,17 +101,25 @@ pkgFile context prefix suffix = do componentId <- pkgData $ ComponentId path return $ path -/- prefix ++ componentId ++ suffix --- | RTS is considered a Stage1 package. This determines RTS build path. +-- | RTS is considered a Stage1 package. This determines RTS build directory. rtsContext :: Context rtsContext = vanillaContext Stage1 rts +-- | Path to the RTS build directory. +rtsBuildPath :: FilePath +rtsBuildPath = buildPath rtsContext + -- | Path to RTS package configuration file, to be processed by HsCpp. rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" +-- | GMP is considered a Stage1 package. This determines GMP build directory. +gmpContext :: Context +gmpContext = vanillaContext Stage1 integerGmp + -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage1/gmp" +gmpBuildPath = buildRootPath -/- stageDirectory (stage gmpContext) -/- "gmp" -- | Path to the GMP library header. gmpLibraryH :: FilePath @@ -124,9 +133,13 @@ gmpObjects = gmpBuildPath -/- "objs" gmpBuildInfoPath :: FilePath gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" --- | Build directory for in-tree libffi library. +-- | Libffi is considered a Stage1 package. This determines its build directory. +libffiContext :: Context +libffiContext = vanillaContext Stage1 libffi + +-- | Build directory for in-tree Libffi library. libffiBuildPath :: FilePath -libffiBuildPath = buildRootPath -/- "stage1/libffi" +libffiBuildPath = buildPath libffiContext -- TODO: Move to buildRootPath, see #113. -- | Path to package database directory of a given 'Stage'. Note: StageN, N > 0, From git at git.haskell.org Fri Oct 27 00:45:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add configFile to Base, track building ./settings (acd13b4) Message-ID: <20171027004556.74EAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acd13b473853eab11eac680a67c3e4ab2f7f82ad/ghc >--------------------------------------------------------------- commit acd13b473853eab11eac680a67c3e4ab2f7f82ad Author: Andrey Mokhov Date: Tue Feb 2 15:11:11 2016 +0000 Add configFile to Base, track building ./settings See #200. >--------------------------------------------------------------- acd13b473853eab11eac680a67c3e4ab2f7f82ad src/Base.hs | 5 ++++- src/Oracles/Config.hs | 3 --- src/Rules/Config.hs | 10 ++++++---- 3 files changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 37f4716..464c1c9 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,7 +16,7 @@ module Base ( module Development.Shake.FilePath, -- * Paths - shakeFilesPath, configPath, sourcePath, programInplacePath, + shakeFilesPath, configPath, configFile, sourcePath, programInplacePath, bootPackageConstraints, packageDependencies, -- * Output @@ -54,6 +54,9 @@ shakeFilesPath = shakePath -/- ".db" configPath :: FilePath configPath = shakePath -/- "cfg" +configFile :: FilePath +configFile = configPath -/- "system.config" + -- | Path to source files of the build system, e.g. this file is located at -- sourcePath -/- "Base.hs". We use this to `need` some of the source files. sourcePath :: FilePath diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index cde2383..7801208 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -8,9 +8,6 @@ import Development.Shake.Config newtype ConfigKey = ConfigKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -configFile :: FilePath -configFile = configPath -/- "system.config" - askConfig :: String -> Action String askConfig key = askConfigWithDefault key . putError $ "Cannot find key '" ++ key ++ "' in configuration files." diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 7b6e8fa..eea61c6 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -8,12 +8,14 @@ configRules :: Rules () configRules = do -- We always rerun the configure script in this mode, because the flags -- passed to it can affect the contents of system.config file. - configPath -/- "system.config" %> \out -> do + [configFile, "settings"] &%> \[cfg, settings] -> do alwaysRerun case cmdConfigure of - RunConfigure args -> runConfigure "." [] [args] - SkipConfigure -> unlessM (doesFileExist out) $ - putError $ "Configuration file " ++ out ++ " is missing.\n" + RunConfigure args -> do + need [ settings <.> "in" ] + runConfigure "." [] [args] + SkipConfigure -> unlessM (doesFileExist cfg) $ + putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " ++ "build system by passing --configure[=ARGS] flag." From git at git.haskell.org Fri Oct 27 00:45:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify handling of non-Cabal contexts (e3be330) Message-ID: <20171027004556.90F2E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3be330a3ff24cf3ead50323e104c217e32f4285/ghc >--------------------------------------------------------------- commit e3be330a3ff24cf3ead50323e104c217e32f4285 Author: Andrey Mokhov Date: Sun Nov 27 14:34:52 2016 +0000 Simplify handling of non-Cabal contexts >--------------------------------------------------------------- e3be330a3ff24cf3ead50323e104c217e32f4285 src/Expression.hs | 12 +----------- src/GHC.hs | 9 ++++++++- src/Rules/Data.hs | 12 ++---------- src/Rules/Libffi.hs | 1 - src/Settings/Builders/Ghc.hs | 7 ++++--- src/Settings/Packages/GhcCabal.hs | 4 ---- src/Settings/Packages/Hp2ps.hs | 9 ++------- src/Settings/Packages/Touchy.hs | 9 ++------- src/Settings/Packages/Unlit.hs | 9 ++------- 9 files changed, 21 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 e3be330a3ff24cf3ead50323e104c217e32f4285 From git at git.haskell.org Fri Oct 27 00:45:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't print progress info too early. (e5e7221) Message-ID: <20171027004559.D8D043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e5e722178f227e3b81d27c8f66c152002d375aad/ghc >--------------------------------------------------------------- commit e5e722178f227e3b81d27c8f66c152002d375aad Author: Andrey Mokhov Date: Tue Feb 2 15:11:53 2016 +0000 Don't print progress info too early. See #200. >--------------------------------------------------------------- e5e722178f227e3b81d27c8f66c152002d375aad src/Rules/Actions.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d85e0dc..658ba17 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -67,6 +67,7 @@ captureStdout target path argList = do copyFile :: FilePath -> FilePath -> Action () copyFile source target = do + need [source] -- Guarantee source is built before printing progress info. putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target From git at git.haskell.org Fri Oct 27 00:45:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify handling of programs with no Haskell main (e2761b2) Message-ID: <20171027004600.0029F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2761b27d9c01828650a48e854ce1f3980dc29b4/ghc >--------------------------------------------------------------- commit e2761b27d9c01828650a48e854ce1f3980dc29b4 Author: Andrey Mokhov Date: Sun Nov 27 15:36:50 2016 +0000 Simplify handling of programs with no Haskell main >--------------------------------------------------------------- e2761b27d9c01828650a48e854ce1f3980dc29b4 hadrian.cabal | 4 ---- src/GHC.hs | 7 ++++++- src/Settings/Builders/Ghc.hs | 4 +++- src/Settings/Default.hs | 10 +--------- src/Settings/Packages/Ghc.hs | 7 ++----- src/Settings/Packages/Hp2ps.hs | 9 --------- src/Settings/Packages/IservBin.hs | 7 ------- src/Settings/Packages/Touchy.hs | 9 --------- src/Settings/Packages/Unlit.hs | 9 --------- 9 files changed, 12 insertions(+), 54 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 0663643..30ed256 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -94,13 +94,9 @@ executable hadrian , Settings.Packages.GhcCabal , Settings.Packages.GhcPrim , Settings.Packages.Haddock - , Settings.Packages.Hp2ps , Settings.Packages.IntegerGmp - , Settings.Packages.IservBin , Settings.Packages.Rts , Settings.Packages.RunGhc - , Settings.Packages.Touchy - , Settings.Packages.Unlit , Settings.Path , Stage , Target diff --git a/src/GHC.hs b/src/GHC.hs index 9111d64..4521679 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -9,7 +9,8 @@ module GHC ( parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, builderProvenance, programName, nonCabalContext + defaultKnownPackages, builderProvenance, programName, nonCabalContext, + nonHsMainPackage ) where import Builder @@ -130,3 +131,7 @@ programName Context {..} nonCabalContext :: Context -> Bool nonCabalContext Context {..} = (package `elem` [hp2ps, rts, touchy, unlit]) || package == ghcCabal && stage == Stage0 + +-- | Some program packages should not be linked with Haskell main function. +nonHsMainPackage :: Package -> Bool +nonHsMainPackage = (`elem` [ghc, hp2ps, iservBin, touchy, unlit]) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 0c4c569..f5b13e1 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -22,6 +22,7 @@ ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do ghcLinkArgs :: Args ghcLinkArgs = builder (Ghc LinkHs) ? do stage <- getStage + pkg <- getPackage libs <- getPkgDataList DepExtraLibs libDirs <- getPkgDataList DepLibDirs gmpLibs <- if stage > Stage0 @@ -31,6 +32,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do return $ concatMap (words . strip) buildInfo else return [] mconcat [ arg "-no-auto-link-packages" + , nonHsMainPackage pkg ? arg "-no-hs-main" , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] @@ -75,7 +77,7 @@ commonGhcArgs = do , arg "-odir" , arg path , arg "-hidir" , arg path , arg "-stubdir" , arg path - , arg "-rtsopts" ] -- TODO: ifeq "$(HC_VERSION_GE_6_13)" "YES" + , (not . nonHsMainPackage) <$> getPackage ? arg "-rtsopts" ] -- TODO: Do '-ticky' in all debug ways? wayGhcArgs :: Args diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index c863a9e..6f56c5d 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -34,13 +34,9 @@ import Settings.Packages.Ghc import Settings.Packages.GhcCabal import Settings.Packages.GhcPrim import Settings.Packages.Haddock -import Settings.Packages.Hp2ps import Settings.Packages.IntegerGmp -import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc -import Settings.Packages.Touchy -import Settings.Packages.Unlit import UserSettings -- | All default command line arguments. @@ -203,10 +199,6 @@ defaultPackageArgs = mconcat , ghcCabalPackageArgs , ghcPrimPackageArgs , haddockPackageArgs - , hp2psPackageArgs , integerGmpPackageArgs - , iservBinPackageArgs , rtsPackageArgs - , runGhcPackageArgs - , touchyPackageArgs - , unlitPackageArgs ] + , runGhcPackageArgs ] diff --git a/src/Settings/Packages/Ghc.hs b/src/Settings/Packages/Ghc.hs index b069c23..a95bda6 100644 --- a/src/Settings/Packages/Ghc.hs +++ b/src/Settings/Packages/Ghc.hs @@ -8,10 +8,7 @@ import Settings.Path ghcPackageArgs :: Args ghcPackageArgs = package ghc ? do stage <- getStage - mconcat [ builder Ghc ? mconcat - [ arg $ "-I" ++ buildPath (vanillaContext stage compiler) - , arg "-no-hs-main" ] + mconcat [ builder Ghc ? arg ("-I" ++ buildPath (vanillaContext stage compiler)) , builder GhcCabal ? - ghcWithInterpreter ? notStage0 ? arg "--flags=ghci" - ] + ghcWithInterpreter ? notStage0 ? arg "--flags=ghci" ] diff --git a/src/Settings/Packages/Hp2ps.hs b/src/Settings/Packages/Hp2ps.hs deleted file mode 100644 index a5c62c2..0000000 --- a/src/Settings/Packages/Hp2ps.hs +++ /dev/null @@ -1,9 +0,0 @@ -module Settings.Packages.Hp2ps (hp2psPackageArgs) where - -import GHC -import Predicate - -hp2psPackageArgs :: Args -hp2psPackageArgs = package hp2ps ? - builder Ghc ? mconcat [ arg "-no-hs-main" - , remove ["-hide-all-packages"] ] diff --git a/src/Settings/Packages/IservBin.hs b/src/Settings/Packages/IservBin.hs deleted file mode 100644 index 40b2101..0000000 --- a/src/Settings/Packages/IservBin.hs +++ /dev/null @@ -1,7 +0,0 @@ -module Settings.Packages.IservBin (iservBinPackageArgs) where - -import GHC -import Predicate - -iservBinPackageArgs :: Args -iservBinPackageArgs = package iservBin ? builder Ghc ? arg "-no-hs-main" diff --git a/src/Settings/Packages/Touchy.hs b/src/Settings/Packages/Touchy.hs deleted file mode 100644 index 7c2e04c..0000000 --- a/src/Settings/Packages/Touchy.hs +++ /dev/null @@ -1,9 +0,0 @@ -module Settings.Packages.Touchy (touchyPackageArgs) where - -import GHC -import Predicate - -touchyPackageArgs :: Args -touchyPackageArgs = package touchy ? - builder Ghc ? mconcat [ arg "-no-hs-main" - , remove ["-hide-all-packages"] ] diff --git a/src/Settings/Packages/Unlit.hs b/src/Settings/Packages/Unlit.hs deleted file mode 100644 index a959699..0000000 --- a/src/Settings/Packages/Unlit.hs +++ /dev/null @@ -1,9 +0,0 @@ -module Settings.Packages.Unlit (unlitPackageArgs) where - -import GHC -import Predicate - -unlitPackageArgs :: Args -unlitPackageArgs = package unlit ? - builder Ghc ? mconcat [ arg "-no-hs-main" - , remove ["-hide-all-packages"] ] From git at git.haskell.org Fri Oct 27 00:46:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify ghcCabalPackageArgs (4e80495) Message-ID: <20171027004603.92ADE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e8049531d734957c1c71fdbe3f18a52db2e2f2d/ghc >--------------------------------------------------------------- commit 4e8049531d734957c1c71fdbe3f18a52db2e2f2d Author: Andrey Mokhov Date: Sun Nov 27 15:56:22 2016 +0000 Simplify ghcCabalPackageArgs >--------------------------------------------------------------- 4e8049531d734957c1c71fdbe3f18a52db2e2f2d src/Settings/Packages/GhcCabal.hs | 21 ++++++--------------- 1 file changed, 6 insertions(+), 15 deletions(-) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index f41053f..8e5837c 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -6,21 +6,12 @@ import Oracles.Config.Setting import Predicate ghcCabalPackageArgs :: Args -ghcCabalPackageArgs = package ghcCabal ? - builder Ghc ? mconcat [ ghcCabalBootArgs - , remove ["-no-auto-link-packages"] ] - --- TODO: do we need -DCABAL_VERSION=$(CABAL_VERSION)? -ghcCabalBootArgs :: Args -ghcCabalBootArgs = stage0 ? do - -- Note: We could have computed 'cabalDeps' instead of hard-coding it - -- but this doesn't worth the effort, since we plan to drop ghc-cabal - -- altogether at some point. See #18. - cabalDeps <- fromDiffExpr $ mconcat - [ append [ array, base, bytestring, containers, deepseq, directory - , pretty, process, time ] - , notM windowsHost ? append [unix] - , windowsHost ? append [win32] ] +ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do + -- Note: We could compute 'cabalDeps' instead of hard-coding it but this + -- seems unnecessary since we plan to drop @ghc-cabal@ altogether, #18. + win <- lift windowsHost + let cabalDeps = [ array, base, bytestring, containers, deepseq, directory + , pretty, process, time, if win then win32 else unix ] mconcat [ append [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , arg "--make" From git at git.haskell.org Fri Oct 27 00:46:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Sort list items. (d1fb3de) Message-ID: <20171027004603.784D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1fb3de6d250c1d30ba86612595c3f48c2661c1a/ghc >--------------------------------------------------------------- commit d1fb3de6d250c1d30ba86612595c3f48c2661c1a Author: Andrey Mokhov Date: Tue Feb 2 15:16:21 2016 +0000 Sort list items. See #200. >--------------------------------------------------------------- d1fb3de6d250c1d30ba86612595c3f48c2661c1a src/Rules/Generate.hs | 46 +++++++++++++++++++++++----------------------- 1 file changed, 23 insertions(+), 23 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 7538470..9c67760 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -21,11 +21,11 @@ import Rules.Resources (Resources) import Settings installTargets :: [FilePath] -installTargets = [ "inplace/lib/template-hsc.h" +installTargets = [ "inplace/lib/ghc-usage.txt" + , "inplace/lib/ghci-usage.txt" , "inplace/lib/platformConstants" , "inplace/lib/settings" - , "inplace/lib/ghc-usage.txt" - , "inplace/lib/ghci-usage.txt" ] + , "inplace/lib/template-hsc.h" ] primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" @@ -45,8 +45,8 @@ includesDependencies = ("includes" -/-) <$> ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> - [ "GHC/PrimopWrappers.hs" - , "autogen/GHC/Prim.hs" ] + [ "autogen/GHC/Prim.hs" + , "GHC/PrimopWrappers.hs" ] derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" @@ -54,9 +54,9 @@ derivedConstantsPath = "includes/dist-derivedconstants/header" derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) [ "DerivedConstants.h" + , "GHCConstantsHaskellExports.hs" , "GHCConstantsHaskellType.hs" - , "GHCConstantsHaskellWrappers.hs" - , "GHCConstantsHaskellExports.hs" ] + , "GHCConstantsHaskellWrappers.hs" ] compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = @@ -66,21 +66,21 @@ compilerDependencies stage = ++ filter (const $ stage > Stage0) libffiDependencies ++ derivedConstantsDependencies ++ fmap ((targetPath stage compiler -/- "build") -/-) - [ "primop-vector-uniques.hs-incl" + [ "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" , "primop-data-decl.hs-incl" - , "primop-tag.hs-incl" - , "primop-list.hs-incl" - , "primop-strictness.hs-incl" , "primop-fixity.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-out-of-line.hs-incl" , "primop-has-side-effects.hs-incl" - , "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-vector-tys-exports.hs-incl" + , "primop-list.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-strictness.hs-incl" + , "primop-tag.hs-incl" , "primop-vector-tycons.hs-incl" - , "primop-vector-tys.hs-incl" ] + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tys.hs-incl" + , "primop-vector-uniques.hs-incl" ] -- TODO: Turn this into a FilePaths expression generatedDependencies :: Stage -> Package -> [FilePath] @@ -139,8 +139,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = -- TODO: why different folders for generated files? fmap (buildPath -/-) - [ "GHC/PrimopWrappers.hs" - , "autogen/GHC/Prim.hs" + [ "autogen/GHC/Prim.hs" + , "GHC/PrimopWrappers.hs" , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] build $ fullTarget target GenPrimopCode [primopsTxt stage] [file] @@ -164,11 +164,11 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = copyRules :: Rules () copyRules = do - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs - "inplace/lib/platformConstants" <~ derivedConstantsPath - "inplace/lib/settings" <~ "." "inplace/lib/ghc-usage.txt" <~ "driver" "inplace/lib/ghci-usage.txt" <~ "driver" + "inplace/lib/platformConstants" <~ derivedConstantsPath + "inplace/lib/settings" <~ "." + "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs where file <~ dir = file %> \_ -> copyFile (dir -/- takeFileName file) file From git at git.haskell.org Fri Oct 27 00:46:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build top-level targets in parallel. (1441846) Message-ID: <20171027004607.4E3523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1441846ddc4fa070a8fa9351ec6386b8645b176e/ghc >--------------------------------------------------------------- commit 1441846ddc4fa070a8fa9351ec6386b8645b176e Author: Andrey Mokhov Date: Tue Feb 2 15:17:05 2016 +0000 Build top-level targets in parallel. See #200. >--------------------------------------------------------------- 1441846ddc4fa070a8fa9351ec6386b8645b176e src/Main.hs | 2 +- src/Package.hs | 3 ++- src/Rules.hs | 48 +++++++++++++++++++++++++++++------------------- 3 files changed, 32 insertions(+), 21 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 2c944d4..79601d8 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -36,7 +36,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules , Rules.Perl.perlScriptRules - , Rules.generateTargets + , Rules.topLevelTargets , Rules.packageRules , Selftest.selftestRules , Test.testRules ] diff --git a/src/Package.hs b/src/Package.hs index b34dc02..43eb480 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -21,7 +21,8 @@ newtype PackageName = PackageName { getPackageName :: String } instance Show PackageName where show (PackageName name) = name --- TODO: make PackageType more precise, #12 +-- TODO: Make PackageType more precise, #12 +-- TODO: Turn Program to Program FilePath thereby getting rid of programPath -- | We regard packages as either being libraries or programs. This is -- bit of a convenient lie as Cabal packages can be both, but it works -- for now. diff --git a/src/Rules.hs b/src/Rules.hs index 5f505b3..b22e028 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,10 +1,11 @@ -module Rules (generateTargets, packageRules) where +module Rules (topLevelTargets, packageRules) where import Base import Data.Foldable import Expression import GHC -import Rules.Generate +import Oracles.PackageData +import qualified Rules.Generate import Rules.Package import Rules.Resources import Settings @@ -13,23 +14,32 @@ allStages :: [Stage] allStages = [minBound ..] -- | 'need' all top-level build targets -generateTargets :: Rules () -generateTargets = action $ do - targets <- fmap concat (traverse targetsForStage allStages) - rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla - rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded - need $ targets ++ installTargets ++ [ rtsLib, rtsThrLib ] - -targetsForStage :: Stage -> Action [String] -targetsForStage stage = do - pkgs <- interpretWithStage stage getPackages - let libPkgs = filter isLibrary pkgs \\ [rts, libffi] - libTargets <- fmap concat . forM libPkgs $ \pkg -> do - let target = PartialTarget stage pkg - needHaddock <- interpretPartial target buildHaddock - return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ] - let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ] - return $ libTargets ++ programTargets +topLevelTargets :: Rules () +topLevelTargets = do + + want $ Rules.Generate.installTargets + + -- TODO: do we want libffiLibrary to be a top-level target? + + action $ do -- TODO: Add support for all rtsWays + rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla + rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded + need [ rtsLib, rtsThrLib ] + + for_ allStages $ \stage -> + for_ (knownPackages \\ [rts, libffi]) $ \pkg -> action $ do + let target = PartialTarget stage pkg + activePackages <- interpretPartial target getPackages + when (pkg `elem` activePackages) $ + if isLibrary pkg + then do -- build a library + ways <- interpretPartial target getLibraryWays + compId <- interpretPartial target $ getPkgData ComponentId + libs <- traverse (pkgLibraryFile stage pkg compId) ways + haddock <- interpretPartial target buildHaddock + need $ libs ++ [ pkgHaddockFile pkg | haddock && stage == Stage1 ] + else do -- otherwise build a program + need [ fromJust $ programPath stage pkg ] -- TODO: drop fromJust packageRules :: Rules () packageRules = do From git at git.haskell.org Fri Oct 27 00:46:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop old TODOs (92b5c35) Message-ID: <20171027004607.75DF73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92b5c3507f296b1676cb7711c09d3e78ec2dfbef/ghc >--------------------------------------------------------------- commit 92b5c3507f296b1676cb7711c09d3e78ec2dfbef Author: Andrey Mokhov Date: Sun Nov 27 17:51:57 2016 +0000 Drop old TODOs See #113 >--------------------------------------------------------------- 92b5c3507f296b1676cb7711c09d3e78ec2dfbef src/Settings/Path.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 9e88ca6..13ef02a 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -37,7 +37,6 @@ generatedPath = buildRootPath -/- "generated" stageDirectory :: Stage -> FilePath stageDirectory = stageString --- TODO: Move to buildRootPath, see #113. -- | Directory for binaries that are built "in place". programInplacePath :: FilePath programInplacePath = "inplace/bin" @@ -141,7 +140,6 @@ libffiContext = vanillaContext Stage1 libffi libffiBuildPath :: FilePath libffiBuildPath = buildPath libffiContext --- TODO: Move to buildRootPath, see #113. -- | Path to package database directory of a given 'Stage'. Note: StageN, N > 0, -- share the same packageDbDirectory. packageDbDirectory :: Stage -> FilePath From git at git.haskell.org Fri Oct 27 00:46:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track mk/config.h.in (adfff77) Message-ID: <20171027004614.24FD53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/adfff77a8843662c4d5034076702101443460deb/ghc >--------------------------------------------------------------- commit adfff77a8843662c4d5034076702101443460deb Author: Andrey Mokhov Date: Tue Feb 2 15:52:51 2016 +0000 Track mk/config.h.in See #200. >--------------------------------------------------------------- adfff77a8843662c4d5034076702101443460deb src/Rules/Config.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index f258674..89434cb 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -20,6 +20,6 @@ configRules = do ++ "Run the configure script either manually or via the " ++ "build system by passing --configure[=ARGS] flag." - "configure" %> \_ -> do + ["configure", configH <.> "in"] &%> \_ -> do putBuild "| Running boot..." quietly $ cmd (EchoStdout False) "perl boot" From git at git.haskell.org Fri Oct 27 00:46:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do a full build on both Travis instances. (be9a21c) Message-ID: <20171027004618.2E8793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/be9a21c630f2d8585ba2c349cc97eb8f749abc80/ghc >--------------------------------------------------------------- commit be9a21c630f2d8585ba2c349cc97eb8f749abc80 Author: Andrey Mokhov Date: Tue Feb 2 19:13:55 2016 +0000 Do a full build on both Travis instances. 1000th commit! >--------------------------------------------------------------- be9a21c630f2d8585ba2c349cc97eb8f749abc80 .travis.yml | 7 ++----- 1 file changed, 2 insertions(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 84bb380..cf2f1cb 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: false matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 addons: apt: packages: @@ -21,7 +21,6 @@ matrix: - cabal update - os: osx - env: TARGET=inplace/bin/ghc-stage1 before_install: - brew update - brew install ghc cabal-install @@ -30,9 +29,7 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH - install: - - env - ghc --version - cabal --version @@ -64,7 +61,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET + - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick cache: directories: From git at git.haskell.org Fri Oct 27 00:46:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop references to #113 (0412d60) Message-ID: <20171027004614.630143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0412d60aef702d221af1b7c12ed96f1421c8d199/ghc >--------------------------------------------------------------- commit 0412d60aef702d221af1b7c12ed96f1421c8d199 Author: Andrey Mokhov Date: Sun Nov 27 18:23:04 2016 +0000 Drop references to #113 [skip ci] >--------------------------------------------------------------- 0412d60aef702d221af1b7c12ed96f1421c8d199 README.md | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index d869f4b..0d7b3d8 100644 --- a/README.md +++ b/README.md @@ -45,8 +45,8 @@ flags below). Using the build system ---------------------- -Once your first build is successful, simply run `build` to rebuild. Most build artefacts -are placed into `_build` and `inplace` directories ([#113][build-artefacts-issue]). +Once your first build is successful, simply run `build` to rebuild. Build results +are placed into `_build` and `inplace` directories. #### Command line flags @@ -92,11 +92,10 @@ use `hadrian/UserSettings.hs` for the same purpose, see [documentation](doc/user #### Clean and full rebuild -* `build clean` removes all build artefacts. Note, we are working towards a -complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `build clean` removes all build artefacts. -* `build -B` forces Shake to rerun all rules, even if results of the previous build -are still in the GHC tree. +* `build -B` forces Shake to rerun all rules, even if the previous build results are +are still up-to-date. #### Source distribution @@ -156,7 +155,6 @@ helped me endure and enjoy the project. [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild [windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md -[build-artefacts-issue]: https://github.com/snowleopard/hadrian/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 From git at git.haskell.org Fri Oct 27 00:46:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track mk/config.h (af2d086) Message-ID: <20171027004610.B53DF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/af2d08616055124477b86b14f9f602b2c306a768/ghc >--------------------------------------------------------------- commit af2d08616055124477b86b14f9f602b2c306a768 Author: Andrey Mokhov Date: Tue Feb 2 15:41:50 2016 +0000 Track mk/config.h See #200. >--------------------------------------------------------------- af2d08616055124477b86b14f9f602b2c306a768 src/Rules/Config.hs | 5 +++-- src/Rules/Generators/GhcAutoconfH.hs | 2 +- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index eea61c6..f258674 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -3,16 +3,17 @@ module Rules.Config (configRules) where import Base import CmdLineFlag import Rules.Actions +import Rules.Generators.GhcAutoconfH configRules :: Rules () configRules = do -- We always rerun the configure script in this mode, because the flags -- passed to it can affect the contents of system.config file. - [configFile, "settings"] &%> \[cfg, settings] -> do + [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do alwaysRerun case cmdConfigure of RunConfigure args -> do - need [ settings <.> "in" ] + need [ settings <.> "in", cfgH <.> "in" ] runConfigure "." [] [args] SkipConfigure -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" diff --git a/src/Rules/Generators/GhcAutoconfH.hs b/src/Rules/Generators/GhcAutoconfH.hs index d6e783f..9d93744 100644 --- a/src/Rules/Generators/GhcAutoconfH.hs +++ b/src/Rules/Generators/GhcAutoconfH.hs @@ -1,4 +1,4 @@ -module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH) where +module Rules.Generators.GhcAutoconfH (generateGhcAutoconfH, configH) where import Base import Expression From git at git.haskell.org Fri Oct 27 00:46:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcPkgMode (31c6109) Message-ID: <20171027004610.E5C353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31c6109cce4304c1a978fad6b399b91fbb7fe9d0/ghc >--------------------------------------------------------------- commit 31c6109cce4304c1a978fad6b399b91fbb7fe9d0 Author: Andrey Mokhov Date: Sun Nov 27 18:11:58 2016 +0000 Add GhcPkgMode >--------------------------------------------------------------- 31c6109cce4304c1a978fad6b399b91fbb7fe9d0 src/Builder.hs | 12 ++++++++++-- src/GHC.hs | 4 ++-- src/Oracles/Path.hs | 38 +++++++++++++++++++------------------- src/Rules/Register.hs | 6 ++++-- src/Rules/Test.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 20 ++++++++++---------- src/Settings/Builders/GhcPkg.hs | 26 ++++++++++---------------- 7 files changed, 57 insertions(+), 53 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 31c6109cce4304c1a978fad6b399b91fbb7fe9d0 From git at git.haskell.org Fri Oct 27 00:46:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Need touchy when calling ghc-stageN, N > 0, on Windows. (fc040db) Message-ID: <20171027004621.A10173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fc040dbd72081339e3eff5083dcb13d145f69ded/ghc >--------------------------------------------------------------- commit fc040dbd72081339e3eff5083dcb13d145f69ded Author: Andrey Mokhov Date: Tue Feb 2 22:06:22 2016 +0000 Need touchy when calling ghc-stageN, N > 0, on Windows. >--------------------------------------------------------------- fc040dbd72081339e3eff5083dcb13d145f69ded src/Settings/Builders/Ghc.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index c79fc50..74381eb 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -21,6 +21,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput stage <- getStage way <- getWay + when (stage > Stage0) . lift $ needTouchy let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output buildProg = not (buildObj || buildHi) @@ -44,6 +45,9 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , buildHi ? append ["-fno-code", "-fwrite-interface"] , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] +needTouchy :: Action () +needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy ] + splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do lift $ need [ghcSplit] From git at git.haskell.org Fri Oct 27 00:46:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths in inplace-pkg-config files (e081b08) Message-ID: <20171027004625.9ED233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e081b081214295de8a31631e9d00642965f7fc23/ghc >--------------------------------------------------------------- commit e081b081214295de8a31631e9d00642965f7fc23 Author: Andrey Mokhov Date: Fri Dec 16 01:27:46 2016 +0000 Fix paths in inplace-pkg-config files >--------------------------------------------------------------- e081b081214295de8a31631e9d00642965f7fc23 src/Rules/Data.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index dc53654..cff0896 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -47,10 +47,8 @@ buildPackageData context at Context {..} = do . replace "rts/dist/build" rtsBuildPath . replace "includes/dist-derivedconstants/header" generatedPath ) . lines - else do - top <- topDirectory - let oldPath = top -/- path "build" - fixFile conf $ unlines . map (replace oldPath path) . lines + else + fixFile conf $ unlines . map (replace (path "build") path) . lines priority 2.0 $ when (nonCabalContext context) $ dataFile %> generatePackageData context From git at git.haskell.org Fri Oct 27 00:46:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (6552aff) Message-ID: <20171027004621.DB9A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6552aff7cf7fde37106b03b851e6d4cdbe515b74/ghc >--------------------------------------------------------------- commit 6552aff7cf7fde37106b03b851e6d4cdbe515b74 Author: Andrey Mokhov Date: Sun Nov 27 22:39:42 2016 +0000 Minor revision >--------------------------------------------------------------- 6552aff7cf7fde37106b03b851e6d4cdbe515b74 src/Settings/Builders/Cc.hs | 5 ++--- src/Settings/Builders/Haddock.hs | 3 +-- src/Settings/Packages/Compiler.hs | 6 ++---- src/Settings/Packages/IntegerGmp.hs | 4 +--- src/Settings/Packages/Rts.hs | 11 +++++------ src/Settings/Packages/RunGhc.hs | 5 ++--- 6 files changed, 13 insertions(+), 21 deletions(-) diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index b0a5f0e..b5d85df 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -8,9 +8,8 @@ ccBuilderArgs = builder Cc ? mconcat , argSettingList . ConfCcArgs =<< getStage , cIncludeArgs - , builder (Cc CompileC) ? - mconcat [ arg "-c", arg =<< getInput - , arg "-o", arg =<< getOutput ] + , builder (Cc CompileC) ? mconcat [ arg "-c", arg =<< getInput + , arg "-o", arg =<< getOutput ] , builder (Cc FindCDependencies) ? do output <- getOutput diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 312124a..3fff015 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -16,7 +16,6 @@ haddockBuilderArgs = builder Haddock ? do path <- getBuildPath version <- getPkgData Version synopsis <- getPkgData Synopsis - hidden <- getPkgDataList HiddenModules deps <- getPkgDataList Deps depNames <- getPkgDataList DepNames hVersion <- lift . pkgData . Version $ buildPath (vanillaContext Stage2 haddock) @@ -31,7 +30,7 @@ haddockBuilderArgs = builder Haddock ? do , arg $ "--title=" ++ pkgNameString pkg ++ "-" ++ version ++ ": " ++ synopsis , arg $ "--prologue=" ++ path -/- "haddock-prologue.txt" , arg $ "--optghc=-D__HADDOCK_VERSION__=" ++ show (versionToInt hVersion) - , append $ map ("--hide=" ++) hidden + , append . map ("--hide=" ++) =<< getPkgDataList HiddenModules , append $ [ "--read-interface=../" ++ dep ++ ",../" ++ dep ++ "/src/%{MODULE/./-}.html\\#%{NAME}," ++ pkgHaddockFile (vanillaContext Stage1 depPkg) diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 03b8081..308b3c2 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -35,8 +35,6 @@ compilerPackageArgs = package compiler ? do ghciWithDebugger flavour ? notStage0 ? arg "--ghc-option=-DDEBUGGER" , ghcProfiled flavour ? - notStage0 ? arg "--ghc-pkg-option=--force" - ] + notStage0 ? arg "--ghc-pkg-option=--force" ] - , builder Haddock ? arg ("--optghc=-I" ++ path) - ] + , builder Haddock ? arg ("--optghc=-I" ++ path) ] diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index def2021..7dfcb2f 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -15,12 +15,10 @@ integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" gmpIncludeDir <- getSetting GmpIncludeDir gmpLibDir <- getSetting GmpLibDir - mconcat [ builder Cc ? arg includeGmp , builder GhcCabal ? mconcat [ (null gmpIncludeDir && null gmpLibDir) ? arg "--configure-option=--with-intree-gmp" , appendSub "--configure-option=CFLAGS" [includeGmp] - , appendSub "--gcc-options" [includeGmp] ] - ] + , appendSub "--gcc-options" [includeGmp] ] ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index d10c6f0..7d844fa 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -12,10 +12,10 @@ rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do useSystemFfi <- flag UseSystemFfi windows <- windowsHost - case (useSystemFfi, windows) of - (True , False) -> return "ffi" - (False, False) -> return "Cffi" - (_ , True ) -> return "Cffi-6" + return $ case (useSystemFfi, windows) of + (True , False) -> "ffi" + (False, False) -> "Cffi" + (_ , True ) -> "Cffi-6" rtsPackageArgs :: Args rtsPackageArgs = package rts ? do @@ -88,8 +88,7 @@ rtsPackageArgs = package rts ? do [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir , "-DFFI_LIB_DIR=" ++ show ffiLibraryDir - , "-DFFI_LIB=" ++ show libffiName ] - ] + , "-DFFI_LIB=" ++ show libffiName ] ] -- # If we're compiling on windows, enforce that we only support XP+ -- # Adding this here means it doesn't have to be done in individual .c files diff --git a/src/Settings/Packages/RunGhc.hs b/src/Settings/Packages/RunGhc.hs index 6880344..dc8ab1f 100644 --- a/src/Settings/Packages/RunGhc.hs +++ b/src/Settings/Packages/RunGhc.hs @@ -5,7 +5,6 @@ import Oracles.Config.Setting import Predicate runGhcPackageArgs :: Args -runGhcPackageArgs = package runGhc ? do +runGhcPackageArgs = package runGhc ? builder Ghc ? input "//Main.hs" ? do version <- getSetting ProjectVersion - builder Ghc ? input "//Main.hs" ? - append ["-cpp", "-DVERSION=" ++ show version] + append ["-cpp", "-DVERSION=" ++ show version] From git at git.haskell.org Fri Oct 27 00:46:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Directory package no longer needs special treatment (1eff9b4) Message-ID: <20171027004618.6B4C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1eff9b4e3114eb38e935def533b54ce0235a6331/ghc >--------------------------------------------------------------- commit 1eff9b4e3114eb38e935def533b54ce0235a6331 Author: Andrey Mokhov Date: Sun Nov 27 22:18:41 2016 +0000 Directory package no longer needs special treatment >--------------------------------------------------------------- 1eff9b4e3114eb38e935def533b54ce0235a6331 hadrian.cabal | 1 - src/Settings/Default.hs | 2 -- src/Settings/Packages/Directory.hs | 12 ------------ 3 files changed, 15 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 30ed256..374b5a0 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -89,7 +89,6 @@ executable hadrian , Settings.Flavours.Quickest , Settings.Packages.Base , Settings.Packages.Compiler - , Settings.Packages.Directory , Settings.Packages.Ghc , Settings.Packages.GhcCabal , Settings.Packages.GhcPrim diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 6f56c5d..b5df4b5 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -29,7 +29,6 @@ import Settings.Builders.Make import Settings.Builders.Tar import Settings.Packages.Base import Settings.Packages.Compiler -import Settings.Packages.Directory import Settings.Packages.Ghc import Settings.Packages.GhcCabal import Settings.Packages.GhcPrim @@ -194,7 +193,6 @@ defaultPackageArgs :: Args defaultPackageArgs = mconcat [ basePackageArgs , compilerPackageArgs - , directoryPackageArgs , ghcPackageArgs , ghcCabalPackageArgs , ghcPrimPackageArgs diff --git a/src/Settings/Packages/Directory.hs b/src/Settings/Packages/Directory.hs deleted file mode 100644 index 5b5d96b..0000000 --- a/src/Settings/Packages/Directory.hs +++ /dev/null @@ -1,12 +0,0 @@ -module Settings.Packages.Directory (directoryPackageArgs) where - -import GHC -import Predicate - --- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is --- effectively empty. I presume it was expected that GHC will be used for --- compiling all C files, but I don't know why. It seems that directory.c is the --- only file which requires special treatment when using GCC. -directoryPackageArgs :: Args -directoryPackageArgs = package directory ? - builder Cc ? arg "-D__GLASGOW_HASKELL__" From git at git.haskell.org Fri Oct 27 00:46:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build GhcPkg Stage1 on OS X Travis. (f8bd699) Message-ID: <20171027004625.645CE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8bd699693493f3ba8eb10e025c5db72a75b8495/ghc >--------------------------------------------------------------- commit f8bd699693493f3ba8eb10e025c5db72a75b8495 Author: Andrey Mokhov Date: Tue Feb 2 22:07:07 2016 +0000 Build GhcPkg Stage1 on OS X Travis. >--------------------------------------------------------------- f8bd699693493f3ba8eb10e025c5db72a75b8495 .travis.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index cf2f1cb..4642d70 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: false matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 + env: CABALVER=1.22 GHCVER=7.10.3 TARGET= addons: apt: packages: @@ -21,6 +21,7 @@ matrix: - cabal update - os: osx + env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg.exe before_install: - brew update - brew install ghc cabal-install @@ -61,7 +62,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick + - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET cache: directories: From git at git.haskell.org Fri Oct 27 00:46:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop exe extension. (c3fc983) Message-ID: <20171027004628.C4D573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3fc983e3fe68c4e2ae74aec45e9bf2d8fa0dcf1/ghc >--------------------------------------------------------------- commit c3fc983e3fe68c4e2ae74aec45e9bf2d8fa0dcf1 Author: Andrey Mokhov Date: Tue Feb 2 22:31:37 2016 +0000 Drop exe extension. >--------------------------------------------------------------- c3fc983e3fe68c4e2ae74aec45e9bf2d8fa0dcf1 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 4642d70..d7e58c3 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - cabal update - os: osx - env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg.exe + env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Fri Oct 27 00:46:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle Make correctly in needBuilder, refactor customBuild (7f62b5a) Message-ID: <20171027004629.144DA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7f62b5a774b790a750651a834cc0de6ffaf61943/ghc >--------------------------------------------------------------- commit 7f62b5a774b790a750651a834cc0de6ffaf61943 Author: Andrey Mokhov Date: Fri Dec 16 21:07:13 2016 +0000 Handle Make correctly in needBuilder, refactor customBuild See #295 >--------------------------------------------------------------- 7f62b5a774b790a750651a834cc0de6ffaf61943 src/Util.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index 81f67dd..b6d9536 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -61,7 +61,6 @@ customBuild rs opts target at Target {..} = do cmd [Cwd output] [path] "x" (top -/- input) Configure dir -> do - need [dir -/- "configure"] -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" cmd Shell cmdEcho env [Cwd dir] [path] opts argList @@ -76,9 +75,7 @@ customBuild rs opts target at Target {..} = do Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output - Make dir -> do - need [dir -/- "Makefile"] - cmd Shell cmdEcho path ["-C", dir] argList + Make dir -> cmd Shell cmdEcho path ["-C", dir] argList _ -> cmd [path] argList @@ -170,6 +167,7 @@ isInternal = isJust . builderProvenance -- | Make sure a 'Builder' exists and rebuild it if out of date. needBuilder :: Builder -> Action () needBuilder (Configure dir) = need [dir -/- "configure"] +needBuilder (Make dir) = need [dir -/- "Makefile"] needBuilder builder = when (isInternal builder) $ do path <- builderPath builder need [path] From git at git.haskell.org Fri Oct 27 00:46:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop registerPackage predicate. (8424eb5) Message-ID: <20171027004632.847D33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8424eb5e1b4a462c4a04f499c4f08cee65585fed/ghc >--------------------------------------------------------------- commit 8424eb5e1b4a462c4a04f499c4f08cee65585fed Author: Andrey Mokhov Date: Wed Feb 3 00:36:29 2016 +0000 Drop registerPackage predicate. See #200. >--------------------------------------------------------------- 8424eb5e1b4a462c4a04f499c4f08cee65585fed src/Predicates.hs | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index 1e56993..c0f6095 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -1,7 +1,7 @@ -- | Convenient predicates module Predicates ( stage, package, builder, stagedBuilder, builderGcc, builderGhc, file, way, - stage0, stage1, stage2, notStage0, notPackage, registerPackage + stage0, stage1, stage2, notStage0, notPackage ) where import Base @@ -60,9 +60,3 @@ notStage0 = notM stage0 -- | Is a certain package /not/ built right now? notPackage :: Package -> Predicate notPackage = notM . package - --- TODO: Actually, we don't register compiler in some circumstances -- fix. --- | Do we need to run @ghc-pkg update@ on the currently built package? --- See "Rules.Data". -registerPackage :: Predicate -registerPackage = return True From git at git.haskell.org Fri Oct 27 00:46:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to Cabal library changes (6984895) Message-ID: <20171027004632.BE58D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/69848955eb325f901ee8a2d387147e5b223e0363/ghc >--------------------------------------------------------------- commit 69848955eb325f901ee8a2d387147e5b223e0363 Author: Andrey Mokhov Date: Fri Dec 30 23:05:50 2016 +0000 Adapt to Cabal library changes >--------------------------------------------------------------- 69848955eb325f901ee8a2d387147e5b223e0363 src/Rules/Cabal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 370bda2..6adaf44 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -4,6 +4,7 @@ import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Text +import Distribution.Types.Dependency import Distribution.Verbosity import Base From git at git.haskell.org Fri Oct 27 00:46:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Settings.Paths, add pkgConfFile. (c1364e5) Message-ID: <20171027004636.868FB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1364e54b2178d83410dfa12ff468423e51728fa/ghc >--------------------------------------------------------------- commit c1364e54b2178d83410dfa12ff468423e51728fa Author: Andrey Mokhov Date: Wed Feb 3 00:38:41 2016 +0000 Refactor Settings.Paths, add pkgConfFile. See #200. >--------------------------------------------------------------- c1364e54b2178d83410dfa12ff468423e51728fa src/Rules.hs | 8 +++----- src/Rules/Program.hs | 9 ++++----- src/Settings/Paths.hs | 33 ++++++++++++++++++++++++--------- 3 files changed, 31 insertions(+), 19 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index b22e028..1d92baf 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -4,7 +4,6 @@ import Base import Data.Foldable import Expression import GHC -import Oracles.PackageData import qualified Rules.Generate import Rules.Package import Rules.Resources @@ -22,8 +21,8 @@ topLevelTargets = do -- TODO: do we want libffiLibrary to be a top-level target? action $ do -- TODO: Add support for all rtsWays - rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla - rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded + rtsLib <- pkgLibraryFile Stage1 rts vanilla + rtsThrLib <- pkgLibraryFile Stage1 rts threaded need [ rtsLib, rtsThrLib ] for_ allStages $ \stage -> @@ -34,8 +33,7 @@ topLevelTargets = do if isLibrary pkg then do -- build a library ways <- interpretPartial target getLibraryWays - compId <- interpretPartial target $ getPkgData ComponentId - libs <- traverse (pkgLibraryFile stage pkg compId) ways + libs <- traverse (pkgLibraryFile stage pkg) ways haddock <- interpretPartial target buildHaddock need $ libs ++ [ pkgHaddockFile pkg | haddock && stage == Stage1 ] else do -- otherwise build a program diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index d472e88..9a5b501 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -86,14 +86,13 @@ buildBinary target @ (PartialTarget stage pkg) bin = do let deps = matchPackageNames (sort pkgs) (map PackageName $ sort depNames) ghci = ghciFlag == "YES" && stage == Stage1 libs <- fmap concat . forM deps $ \dep -> do - let depTarget = PartialTarget libStage dep - compId <- interpretPartial depTarget $ getPkgData ComponentId libFiles <- fmap concat . forM ways $ \way -> do - libFile <- pkgLibraryFile libStage dep compId way - lib0File <- pkgLibraryFile libStage dep (compId ++ "-0") way + libFile <- pkgLibraryFile libStage dep way + lib0File <- pkgLibraryFile0 libStage dep way dll0 <- needDll0 libStage dep return $ libFile : [ lib0File | dll0 ] - return $ libFiles ++ [ pkgGhciLibraryFile libStage dep compId | ghci ] + ghciLib <- pkgGhciLibraryFile libStage dep + return $ libFiles ++ [ ghciLib | ghci ] let binDeps = if pkg == ghcCabal && stage == Stage0 then [ pkgPath pkg -/- src <.> "hs" | src <- hSrcs ] else objs diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index a152f9a..20f4721 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,11 +1,13 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgGhciLibraryFile, gmpBuildPath, gmpLibNameCache, packageDbDirectory + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibNameCache, + packageDbDirectory, pkgConfFile ) where import Base import Expression import GHC +import Oracles.PackageData import Settings.User -- Path to the target directory from GHC source root @@ -24,18 +26,26 @@ pkgHaddockFile pkg = -- Relative path to a package library file, e.g.: -- "libraries/array/stage2/build/libHSarray-0.5.1.0.a" --- TODO: remove code duplication for computing buildPath -pkgLibraryFile :: Stage -> Package -> String -> Way -> Action FilePath -pkgLibraryFile stage pkg componentId way = do +pkgLibraryFile :: Stage -> Package -> Way -> Action FilePath +pkgLibraryFile stage pkg way = do extension <- libsuf way - let buildPath = targetPath stage pkg -/- "build" - return $ buildPath -/- "libHS" ++ componentId ++ extension + pkgFile stage pkg "build/libHS" extension + +pkgLibraryFile0 :: Stage -> Package -> Way -> Action FilePath +pkgLibraryFile0 stage pkg way = do + extension <- libsuf way + pkgFile stage pkg "build/libHS" ("-0" ++ extension) -- Relative path to a package ghci library file, e.g.: -- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" -pkgGhciLibraryFile :: Stage -> Package -> String -> FilePath -pkgGhciLibraryFile stage pkg componentId = - targetPath stage pkg -/- "build" -/- "HS" ++ componentId <.> "o" +pkgGhciLibraryFile :: Stage -> Package -> Action FilePath +pkgGhciLibraryFile stage pkg = pkgFile stage pkg "build/HS" ".o" + +pkgFile :: Stage -> Package -> String -> String -> Action FilePath +pkgFile stage pkg prefix suffix = do + let path = targetPath stage pkg + componentId <- pkgData $ ComponentId path + return $ path -/- prefix ++ componentId ++ suffix -- This is the build directory for in-tree GMP library gmpBuildPath :: FilePath @@ -50,3 +60,8 @@ gmpLibNameCache = gmpBuildPath -/- "gmp-lib-names" packageDbDirectory :: Stage -> FilePath packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" + +pkgConfFile :: Stage -> Package -> Action FilePath +pkgConfFile stage pkg = do + componentId <- pkgData . ComponentId $ targetPath stage pkg + return $ packageDbDirectory stage -/- componentId <.> "conf" From git at git.haskell.org Fri Oct 27 00:46:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghci library in Stage0 (8e3cb44) Message-ID: <20171027004636.C6EB83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e3cb447a9476196099fc7a6b22d0d177795263f/ghc >--------------------------------------------------------------- commit 8e3cb447a9476196099fc7a6b22d0d177795263f Author: Andrey Mokhov Date: Fri Dec 30 23:19:27 2016 +0000 Build ghci library in Stage0 >--------------------------------------------------------------- 8e3cb447a9476196099fc7a6b22d0d177795263f src/Settings/Default.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index b5df4b5..ba4ef79 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -67,6 +67,7 @@ stage0Packages = do , ghcBoot , ghcBootTh , ghcCabal + , ghci , ghcPkg , hsc2hs , hoopl From git at git.haskell.org Fri Oct 27 00:46:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Decouple buildPackageData and registerPackage rules. (9129e8b) Message-ID: <20171027004640.4A69E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9129e8bc158dab081094554abc4dcbef3f8b2a5f/ghc >--------------------------------------------------------------- commit 9129e8bc158dab081094554abc4dcbef3f8b2a5f Author: Andrey Mokhov Date: Wed Feb 3 00:39:32 2016 +0000 Decouple buildPackageData and registerPackage rules. See #200. >--------------------------------------------------------------- 9129e8bc158dab081094554abc4dcbef3f8b2a5f shaking-up-ghc.cabal | 1 + src/Rules/Data.hs | 26 ++++---------------------- src/Rules/Documentation.hs | 3 ++- src/Rules/Package.hs | 30 ++++++++++++++++-------------- src/Rules/Register.hs | 39 +++++++++++++++++++++++++++++++++++++++ 5 files changed, 62 insertions(+), 37 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index f00c7c6..0807ff3 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -62,6 +62,7 @@ executable ghc-shake , Rules.Package , Rules.Perl , Rules.Program + , Rules.Register , Rules.Resources , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index fbe22db..f2e3d43 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -6,7 +6,6 @@ import Base import Expression import GHC import Oracles -import Predicates (registerPackage) import Rules.Actions import Rules.Generate import Rules.Libffi @@ -29,14 +28,14 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do orderOnly $ generatedDependencies stage pkg -- GhcCabal may run the configure script, so we depend on it - -- We don't know who built the configure script from configure.ac whenM (doesFileExist $ configure <.> "ac") $ need [configure] - -- We configure packages in the order of their dependencies + -- Before we configure a package its dependencies need to be registered deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - orderOnly $ map (pkgDataFile stage) depPkgs + depConfs <- traverse (pkgConfFile stage) depPkgs + orderOnly depConfs -- TODO: get rid of this, see #113 let inTreeMk = oldPath -/- takeFileName dataFile @@ -52,23 +51,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do forM_ autogenFiles $ \file -> do copyFile (oldPath -/- file) (targetPath stage pkg -/- file) - -- ghc-pkg produces inplace-pkg-config when run on packages with - -- library components only - when (isLibrary pkg) . - whenM (interpretPartial target registerPackage) $ do - - -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 - let fixPkgConf = unlines - . map (replace oldPath (targetPath stage pkg) - . replace (replaceSeparators '\\' $ oldPath) - (targetPath stage pkg) ) - . lines - - fixFile (oldPath -/- "inplace-pkg-config") fixPkgConf - - buildWithResources [(resGhcPkg rs, 1)] $ - fullTarget target (GhcPkg stage) [cabalFile] [] - postProcessPackageData stage pkg dataFile -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps @@ -141,7 +123,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do [ "C_SRCS = " ++ unwords (cSrcs ++ cmmSrcs ++ sSrcs ++ extraSrcs) , "CC_OPTS = " ++ unwords includes - , "COMPONENT_ID = " ++ "rts" ] + , "COMPONENT_ID = rts" ] writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index cb74952..e235bfc 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -26,7 +26,8 @@ buildPackageDocumentation _ target @ (PartialTarget stage pkg) = -- HsColour sources whenM (specified HsColour) $ do - need [cabalFile, pkgDataFile stage pkg ] + pkgConf <- pkgConfFile stage pkg + need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf build $ fullTarget target GhcCabalHsColour [cabalFile] [] -- Build Haddock documentation diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs index 7a7d854..28fe635 100644 --- a/src/Rules/Package.hs +++ b/src/Rules/Package.hs @@ -1,22 +1,24 @@ module Rules.Package (buildPackage) where import Base -import Rules.Compile -import Rules.Data -import Rules.Dependencies -import Rules.Documentation -import Rules.Generate -import Rules.Library -import Rules.Program +import qualified Rules.Compile +import qualified Rules.Data +import qualified Rules.Dependencies +import qualified Rules.Documentation +import qualified Rules.Generate +import qualified Rules.Library +import qualified Rules.Program +import qualified Rules.Register import Rules.Resources import Target buildPackage :: Resources -> PartialTarget -> Rules () buildPackage = mconcat - [ buildPackageData - , buildPackageDependencies - , generatePackageCode - , compilePackage - , buildPackageLibrary - , buildPackageDocumentation - , buildProgram ] + [ Rules.Compile.compilePackage + , Rules.Data.buildPackageData + , Rules.Dependencies.buildPackageDependencies + , Rules.Documentation.buildPackageDocumentation + , Rules.Generate.generatePackageCode + , Rules.Library.buildPackageLibrary + , Rules.Program.buildProgram + , Rules.Register.registerPackage ] diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs new file mode 100644 index 0000000..8c3ec73 --- /dev/null +++ b/src/Rules/Register.hs @@ -0,0 +1,39 @@ +module Rules.Register (registerPackage) where + +import Data.Char + +import Base +import Expression +import GHC +import Rules.Actions +import Rules.Resources +import Settings + +-- matchPkgConf :: FilePath -> Bool +-- matchPkgConf file = + +-- Build package-data.mk by using GhcCabal to process pkgCabal file +registerPackage :: Resources -> PartialTarget -> Rules () +registerPackage rs target @ (PartialTarget stage pkg) = do + let oldPath = pkgPath pkg -/- targetDirectory stage pkg -- TODO: remove, #113 + pkgConf = packageDbDirectory stage -/- pkgNameString pkg + match f = case stripPrefix (pkgConf ++ "-") f of + Nothing -> False + Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf" + + when (stage <= Stage1) $ match ?> \_ -> do + -- This produces pkgConfig. TODO: Add explicit tracking + need [pkgDataFile stage pkg] + + -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 + let pkgConfig = oldPath -/- "inplace-pkg-config" + fixPkgConf = unlines + . map (replace oldPath (targetPath stage pkg) + . replace (replaceSeparators '\\' $ oldPath) + (targetPath stage pkg) ) + . lines + + fixFile pkgConfig fixPkgConf + + buildWithResources [(resGhcPkg rs, 1)] $ + fullTarget target (GhcPkg stage) [pkgConfig] [] From git at git.haskell.org Fri Oct 27 00:46:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build internal ghci support in Stage1 (552bb90) Message-ID: <20171027004640.8B02B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/552bb90ed6b3408018c8c9952c5c0f1b28323694/ghc >--------------------------------------------------------------- commit 552bb90ed6b3408018c8c9952c5c0f1b28323694 Author: Andrey Mokhov Date: Sat Dec 31 01:03:52 2016 +0000 Build internal ghci support in Stage1 >--------------------------------------------------------------- 552bb90ed6b3408018c8c9952c5c0f1b28323694 hadrian.cabal | 1 + src/Settings/Default.hs | 2 ++ src/Settings/Packages/Ghci.hs | 7 +++++++ 3 files changed, 10 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 374b5a0..a186d7d 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -91,6 +91,7 @@ executable hadrian , Settings.Packages.Compiler , Settings.Packages.Ghc , Settings.Packages.GhcCabal + , Settings.Packages.Ghci , Settings.Packages.GhcPrim , Settings.Packages.Haddock , Settings.Packages.IntegerGmp diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index ba4ef79..37fcdfa 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -31,6 +31,7 @@ import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Ghc import Settings.Packages.GhcCabal +import Settings.Packages.Ghci import Settings.Packages.GhcPrim import Settings.Packages.Haddock import Settings.Packages.IntegerGmp @@ -196,6 +197,7 @@ defaultPackageArgs = mconcat , compilerPackageArgs , ghcPackageArgs , ghcCabalPackageArgs + , ghciPackageArgs , ghcPrimPackageArgs , haddockPackageArgs , integerGmpPackageArgs diff --git a/src/Settings/Packages/Ghci.hs b/src/Settings/Packages/Ghci.hs new file mode 100644 index 0000000..3d14691 --- /dev/null +++ b/src/Settings/Packages/Ghci.hs @@ -0,0 +1,7 @@ +module Settings.Packages.Ghci (ghciPackageArgs) where + +import GHC +import Predicate + +ghciPackageArgs :: Args +ghciPackageArgs = notStage0 ? package ghci ? builder GhcCabal ? arg "--flags=ghci" From git at git.haskell.org Fri Oct 27 00:46:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop ghc-cabal resource. (13d735f) Message-ID: <20171027004644.665893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13d735f298d0a51a83c422a34e9844058ca5e89d/ghc >--------------------------------------------------------------- commit 13d735f298d0a51a83c422a34e9844058ca5e89d Author: Andrey Mokhov Date: Wed Feb 3 01:03:46 2016 +0000 Drop ghc-cabal resource. See #200. >--------------------------------------------------------------- 13d735f298d0a51a83c422a34e9844058ca5e89d src/Rules/Data.hs | 3 +-- src/Rules/Resources.hs | 10 +++------- 2 files changed, 4 insertions(+), 9 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index f2e3d43..ade93fd 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -41,8 +41,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do let inTreeMk = oldPath -/- takeFileName dataFile need [cabalFile] - buildWithResources [(resGhcCabal rs, 1)] $ - fullTarget target GhcCabal [cabalFile] [inTreeMk] + build $ fullTarget target GhcCabal [cabalFile] [inTreeMk] -- TODO: get rid of this, see #113 liftIO $ IO.copyFile inTreeMk dataFile diff --git a/src/Rules/Resources.hs b/src/Rules/Resources.hs index 514a222..d5e58fe 100644 --- a/src/Rules/Resources.hs +++ b/src/Rules/Resources.hs @@ -4,13 +4,9 @@ import Base data Resources = Resources { - resGhcCabal :: Resource, - resGhcPkg :: Resource + resGhcPkg :: Resource } --- Unfortunately parallel invokations of ghc-cabal or ghc-pkg do not work: --- * https://mail.haskell.org/pipermail/ghc-commits/2013-May/001712.html --- * ghc.mk: see comment about parallel ghc-pkg invokations +-- We cannot register multiple packages in parallel: resourceRules :: Rules Resources -resourceRules = liftM2 Resources (newResource "ghc-cabal" 1) - (newResource "ghc-pkg" 1) +resourceRules = Resources <$> newResource "ghc-pkg" 1 From git at git.haskell.org Fri Oct 27 00:46:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build compact library (374b10a) Message-ID: <20171027004644.A56953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/374b10aa7af36884484e05d7e6ac02295be60957/ghc >--------------------------------------------------------------- commit 374b10aa7af36884484e05d7e6ac02295be60957 Author: Andrey Mokhov Date: Sat Dec 31 01:04:40 2016 +0000 Build compact library >--------------------------------------------------------------- 374b10aa7af36884484e05d7e6ac02295be60957 src/GHC.hs | 33 ++++++++++++++++++--------------- src/Settings/Default.hs | 3 ++- 2 files changed, 20 insertions(+), 16 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 1fff56f..f8abeb8 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,13 +1,14 @@ {-# LANGUAGE OverloadedStrings, LambdaCase #-} {-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( - array, base, binary, bytestring, cabal, checkApiAnnotations, compiler, - containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, - filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, - ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, - hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, - parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, - terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, + array, base, binary, bytestring, cabal, checkApiAnnotations, compact, + compareSizes, compiler, containers, deepseq, deriveConstants, directory, + dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, + ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, + hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, + libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, + stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, + win32, xhtml, defaultKnownPackages, builderProvenance, programName, nonCabalContext, nonHsMainPackage @@ -25,13 +26,14 @@ import Stage -- be overridden in @hadrian/src/UserSettings.hs at . defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, binary, bytestring, cabal, checkApiAnnotations, compiler - , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci - , ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc - , hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart - , parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell - , terminfo, time, touchy, transformers, unlit, unix, win32, xhtml ] + [ array, base, binary, bytestring, cabal, checkApiAnnotations, compact + , compareSizes, compiler, containers, deepseq, deriveConstants, directory + , dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh + , ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs + , hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi + , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm + , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 + , xhtml ] -- | Package definitions, see 'Package'. array = library "array" @@ -40,9 +42,10 @@ binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" checkApiAnnotations = utility "check-api-annotations" +compact = library "compact" +compareSizes = utility "compareSizes" `setPath` "utils/compare_sizes" compiler = topLevel "ghc" `setPath` "compiler" containers = library "containers" -compareSizes = utility "compareSizes" `setPath` "utils/compare_sizes" deepseq = library "deepseq" deriveConstants = utility "deriveConstants" directory = library "directory" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 37fcdfa..67b0d5d 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -90,8 +90,9 @@ stage1Packages = do , append $ [ array , base , bytestring - , containers + , compact , compareSizes + , containers , deepseq , directory , filepath From git at git.haskell.org Fri Oct 27 00:46:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update stack.yaml to lts-5.1 (82b665e) Message-ID: <20171027004647.DDD403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82b665e184a92fb27bc894e6f0fe2d186ea1fbe0/ghc >--------------------------------------------------------------- commit 82b665e184a92fb27bc894e6f0fe2d186ea1fbe0 Author: Joe Hillenbrand Date: Wed Feb 3 10:35:55 2016 -0800 Update stack.yaml to lts-5.1 I don't plan to change this file every time there is a new stackage lts, but lts-4.x has a bug with aeson. >--------------------------------------------------------------- 82b665e184a92fb27bc894e6f0fe2d186ea1fbe0 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index 2bc3b0e..0772c76 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,7 +1,7 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-4.2 +resolver: lts-5.1 # Local packages, usually specified by relative directory name packages: From git at git.haskell.org Fri Oct 27 00:46:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add perf flavour (6508f4b) Message-ID: <20171027004648.562163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6508f4b94dd9f0c476269191ce2a083856ef2d60/ghc >--------------------------------------------------------------- commit 6508f4b94dd9f0c476269191ce2a083856ef2d60 Author: Andrey Mokhov Date: Fri Jan 6 00:59:26 2017 +0000 Add perf flavour >--------------------------------------------------------------- 6508f4b94dd9f0c476269191ce2a083856ef2d60 hadrian.cabal | 1 + src/Settings.hs | 3 ++- src/Settings/Flavours/Perf.hs | 21 +++++++++++++++++++++ 3 files changed, 24 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index a186d7d..4f3c2f6 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -85,6 +85,7 @@ executable hadrian , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default + , Settings.Flavours.Perf , Settings.Flavours.Quick , Settings.Flavours.Quickest , Settings.Packages.Base diff --git a/src/Settings.hs b/src/Settings.hs index bef47f1..18dd15b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -14,6 +14,7 @@ import GHC import Oracles.PackageData import Oracles.Path import {-# SOURCE #-} Settings.Default +import Settings.Flavours.Perf import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Path @@ -50,7 +51,7 @@ getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getBuildPath hadrianFlavours :: [Flavour] -hadrianFlavours = [defaultFlavour, quickFlavour, quickestFlavour] +hadrianFlavours = [defaultFlavour, perfFlavour, quickFlavour, quickestFlavour] flavour :: Flavour flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours diff --git a/src/Settings/Flavours/Perf.hs b/src/Settings/Flavours/Perf.hs new file mode 100644 index 0000000..d246b15 --- /dev/null +++ b/src/Settings/Flavours/Perf.hs @@ -0,0 +1,21 @@ +module Settings.Flavours.Perf (perfFlavour) where + +import Context +import Flavour +import GHC +import Predicate +import {-# SOURCE #-} Settings.Default + +perfFlavour :: Flavour +perfFlavour = defaultFlavour + { name = "perf" + , args = defaultArgs <> perfArgs } + +optimise :: Context -> Bool +optimise Context {..} = + package `elem` [compiler, ghc] && stage == Stage2 || isLibrary package + +perfArgs :: Args +perfArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O2" else arg "-O" From git at git.haskell.org Fri Oct 27 00:46:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #202 from joehillen/patch-1 (793587b) Message-ID: <20171027004651.E37F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/793587bd5c2a0981221e7d11fe57071f5367e021/ghc >--------------------------------------------------------------- commit 793587bd5c2a0981221e7d11fe57071f5367e021 Merge: 13d735f 82b665e Author: Andrey Mokhov Date: Wed Feb 3 18:50:40 2016 +0000 Merge pull request #202 from joehillen/patch-1 Update stack.yaml to lts-5.1 [skip ci] >--------------------------------------------------------------- 793587bd5c2a0981221e7d11fe57071f5367e021 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:46:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing profiling flags (9c8d9bf) Message-ID: <20171027004652.421DE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c8d9bf40b129f2faa8f50525c3fac5b322d808f/ghc >--------------------------------------------------------------- commit 9c8d9bf40b129f2faa8f50525c3fac5b322d808f Author: Andrey Mokhov Date: Fri Jan 6 01:59:23 2017 +0000 Add missing profiling flags >--------------------------------------------------------------- 9c8d9bf40b129f2faa8f50525c3fac5b322d808f src/Predicate.hs | 10 +++++++++- src/Settings/Packages/Compiler.hs | 3 +++ 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/src/Predicate.hs b/src/Predicate.hs index d38d9d5..5da5c54 100644 --- a/src/Predicate.hs +++ b/src/Predicate.hs @@ -2,7 +2,7 @@ -- | Convenient predicates module Predicate ( module Expression, stage, stage0, stage1, stage2, notStage0, builder, - package, notPackage, input, output, way + package, notPackage, input, inputs, output, outputs, way ) where import Base @@ -52,10 +52,18 @@ instance BuilderLike a => BuilderLike (FilePath -> a) where input :: FilePattern -> Predicate input f = any (f ?==) <$> getInputs +-- | Does any of the input files match any of the given patterns? +inputs :: [FilePattern] -> Predicate +inputs = anyM input + -- | Does any of the output files match a given pattern? output :: FilePattern -> Predicate output f = any (f ?==) <$> getOutputs +-- | Does any of the output files match any of the given patterns? +outputs :: [FilePattern] -> Predicate +outputs = anyM output + -- | Is the current build 'Way' equal to a certain value? way :: Way -> Predicate way w = (w ==) <$> getWay diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 308b3c2..9280a81 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -15,6 +15,9 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" + , builder (Ghc CompileHs) ? + inputs ["//GHC.hs", "//GhcMake.hs"] ? arg "-fprof-auto" + , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) , arg "--disable-library-for-ghci" From git at git.haskell.org Fri Oct 27 00:46:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't print empty arguments. (2bde60d) Message-ID: <20171027004655.B711B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2bde60d83dd71c50b88f385efefef71bf27220d0/ghc >--------------------------------------------------------------- commit 2bde60d83dd71c50b88f385efefef71bf27220d0 Author: Andrey Mokhov Date: Fri Feb 5 01:07:48 2016 +0000 Don't print empty arguments. See #204. >--------------------------------------------------------------- 2bde60d83dd71c50b88f385efefef71bf27220d0 src/Rules/Actions.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 658ba17..daa4c5e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -98,7 +98,8 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] - let note = if null args || args == [""] then "" else " (" ++ intercalate ", " args ++ ")" + let args' = filter (not . null) args + note = if null args' then "" else " (" ++ intercalate ", " args' ++ ")" if dir == "." then do putBuild $ "| Run configure" ++ note ++ "..." From git at git.haskell.org Fri Oct 27 00:46:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add prof flavour (bc44c00) Message-ID: <20171027004656.1FF203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc44c00792276d7834258db442af9fe687d22a01/ghc >--------------------------------------------------------------- commit bc44c00792276d7834258db442af9fe687d22a01 Author: Andrey Mokhov Date: Fri Jan 6 02:00:02 2017 +0000 Add prof flavour >--------------------------------------------------------------- bc44c00792276d7834258db442af9fe687d22a01 hadrian.cabal | 1 + src/Settings.hs | 4 +++- src/Settings/Flavours/Prof.hs | 21 +++++++++++++++++++++ 3 files changed, 25 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 4f3c2f6..712d4c6 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -86,6 +86,7 @@ executable hadrian , Settings.Builders.Tar , Settings.Default , Settings.Flavours.Perf + , Settings.Flavours.Prof , Settings.Flavours.Quick , Settings.Flavours.Quickest , Settings.Packages.Base diff --git a/src/Settings.hs b/src/Settings.hs index 18dd15b..8f94e5b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -15,6 +15,7 @@ import Oracles.PackageData import Oracles.Path import {-# SOURCE #-} Settings.Default import Settings.Flavours.Perf +import Settings.Flavours.Prof import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Path @@ -51,7 +52,8 @@ getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getBuildPath hadrianFlavours :: [Flavour] -hadrianFlavours = [defaultFlavour, perfFlavour, quickFlavour, quickestFlavour] +hadrianFlavours = [ defaultFlavour, perfFlavour, profFlavour, quickFlavour + , quickestFlavour ] flavour :: Flavour flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours diff --git a/src/Settings/Flavours/Prof.hs b/src/Settings/Flavours/Prof.hs new file mode 100644 index 0000000..4dee8fc --- /dev/null +++ b/src/Settings/Flavours/Prof.hs @@ -0,0 +1,21 @@ +module Settings.Flavours.Prof (profFlavour) where + +import Context +import Flavour +import GHC +import Predicate +import {-# SOURCE #-} Settings.Default + +profFlavour :: Flavour +profFlavour = defaultFlavour + { name = "prof" + , args = defaultArgs <> profArgs + , ghcProfiled = True } + +optimise :: Context -> Bool +optimise Context {..} = package `elem` [compiler, ghc] || isLibrary package + +profArgs :: Args +profArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O" else arg "-O0" From git at git.haskell.org Fri Oct 27 00:46:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:46:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass --enable-tarballs-autodownload to configure by default on Windows. (1562315) Message-ID: <20171027004659.A64AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1562315b94894f4e8098da8ac35ce2a007f2dc1f/ghc >--------------------------------------------------------------- commit 1562315b94894f4e8098da8ac35ce2a007f2dc1f Author: Andrey Mokhov Date: Fri Feb 5 01:08:31 2016 +0000 Pass --enable-tarballs-autodownload to configure by default on Windows. See #204. >--------------------------------------------------------------- 1562315b94894f4e8098da8ac35ce2a007f2dc1f src/Rules/Config.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 89434cb..1016be9 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -1,5 +1,7 @@ module Rules.Config (configRules) where +import qualified System.Info + import Base import CmdLineFlag import Rules.Actions @@ -14,7 +16,11 @@ configRules = do case cmdConfigure of RunConfigure args -> do need [ settings <.> "in", cfgH <.> "in" ] - runConfigure "." [] [args] + -- We cannot use windowsHost here due to a cyclic dependency + let defaultArgs = if System.Info.os == "mingw32" + then [ "--enable-tarballs-autodownload" ] + else [] + runConfigure "." [] $ defaultArgs ++ [args] SkipConfigure -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " From git at git.haskell.org Fri Oct 27 00:47:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing flags for Parser module (3201312) Message-ID: <20171027004700.0D7CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3201312c71ea91128a11942ff66792f175bed255/ghc >--------------------------------------------------------------- commit 3201312c71ea91128a11942ff66792f175bed255 Author: Andrey Mokhov Date: Fri Jan 6 02:33:02 2017 +0000 Add missing flags for Parser module See #268 >--------------------------------------------------------------- 3201312c71ea91128a11942ff66792f175bed255 src/Settings/Flavours/Perf.hs | 2 +- src/Settings/Flavours/Prof.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/Quickest.hs | 2 +- src/Settings/Packages/Compiler.hs | 6 ++++-- 5 files changed, 8 insertions(+), 6 deletions(-) diff --git a/src/Settings/Flavours/Perf.hs b/src/Settings/Flavours/Perf.hs index d246b15..7641657 100644 --- a/src/Settings/Flavours/Perf.hs +++ b/src/Settings/Flavours/Perf.hs @@ -9,7 +9,7 @@ import {-# SOURCE #-} Settings.Default perfFlavour :: Flavour perfFlavour = defaultFlavour { name = "perf" - , args = defaultArgs <> perfArgs } + , args = defaultBuilderArgs <> perfArgs <> defaultPackageArgs } optimise :: Context -> Bool optimise Context {..} = diff --git a/src/Settings/Flavours/Prof.hs b/src/Settings/Flavours/Prof.hs index 4dee8fc..6d94b90 100644 --- a/src/Settings/Flavours/Prof.hs +++ b/src/Settings/Flavours/Prof.hs @@ -9,7 +9,7 @@ import {-# SOURCE #-} Settings.Default profFlavour :: Flavour profFlavour = defaultFlavour { name = "prof" - , args = defaultArgs <> profArgs + , args = defaultBuilderArgs <> profArgs <> defaultPackageArgs , ghcProfiled = True } optimise :: Context -> Bool diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 448a875..1e4f5c0 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -9,7 +9,7 @@ import {-# SOURCE #-} Settings.Default quickFlavour :: Flavour quickFlavour = defaultFlavour { name = "quick" - , args = defaultArgs <> quickArgs + , args = defaultBuilderArgs <> quickArgs <> defaultPackageArgs , libraryWays = defaultLibraryWays <> quickLibraryWays } optimise :: Context -> Bool diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 9f9b85b..477a245 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -7,7 +7,7 @@ import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour quickestFlavour = defaultFlavour { name = "quickest" - , args = defaultArgs <> quickestArgs + , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs , libraryWays = defaultLibraryWays <> quickestLibraryWays } quickestArgs :: Args diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 9280a81..8cc05cb 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -15,8 +15,10 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder (Ghc CompileHs) ? - inputs ["//GHC.hs", "//GhcMake.hs"] ? arg "-fprof-auto" + , builder (Ghc CompileHs) ? mconcat + [ inputs ["//GHC.hs", "//GhcMake.hs"] ? arg "-fprof-auto" + , input "//Parser.hs" ? + append ["-O0", "-fno-ignore-interface-pragmas", "-fcmm-sink" ] ] , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) From git at git.haskell.org Fri Oct 27 00:47:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use --configure by default, add --enable-tarballs-autodownload flag on Windows. (2825f93) Message-ID: <20171027004703.6960D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2825f9345544b96b4f904c2db64b82d1982a3c0a/ghc >--------------------------------------------------------------- commit 2825f9345544b96b4f904c2db64b82d1982a3c0a Author: Andrey Mokhov Date: Fri Feb 5 01:34:35 2016 +0000 Don't use --configure by default, add --enable-tarballs-autodownload flag on Windows. See #204. [skip ci] >--------------------------------------------------------------- 2825f9345544b96b4f904c2db64b82d1982a3c0a README.md | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/README.md b/README.md index 0a60d11..f048ee4 100644 --- a/README.md +++ b/README.md @@ -27,29 +27,26 @@ follow these steps: * This build system is written in Haskell (obviously) and depends on the following Haskell packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. -* Get the sources. It is important for the build system to be in the `shake-build` directory of the GHC source tree: +* Get the sources and run standard configuration scripts. It is important for the build +system to be in the `shake-build` directory of the GHC source tree: ```bash git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/shaking-up-ghc shake-build + ./boot + ./configure # On Windows run ./configure --enable-tarballs-autodownload ``` -* Start your first build (you might want to enable parallelism with `-j`): - ```bash - shake-build/build.sh --configure - ``` -On Windows, use `build.bat` instead and pass an extra flag to configure (also see [building on Windows][ghc-windows-quick-build]): - ```bash - shake-build/build.bat --configure=--enable-tarballs-autodownload - ``` -If you are interested in building in a Cabal sandbox or using Stack, have a look at `shake-build/build.cabal.sh` and `shake-build/build.stack.sh` scripts. +* Build GHC using `shake-build/build.sh` or `shake-build/build.bat` (on Windows) instead +of `make`. You might want to enable parallelism with `-j`. We will further refer to the +build script simply as `build`. If you are interested in building in a Cabal sandbox +or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Using the build system ---------------------- -Once your first build is successful, simply run `shake-build/build.sh` or `shake-build/build.bat` -to rebuild (you no longer need to use the `--configure` flag). Most build artefacts are placed -into `.build` and `inplace` directories ([#113][build-artefacts-issue]). +Once your first build is successful, simply run `build` to rebuild. Most build artefacts +are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue]). #### Command line flags @@ -58,7 +55,10 @@ currently supports several others: * `--configure[=ARGS]`: run the `configure` script forwarding `ARGS` as command line arguments; also run the `boot` script to create the `configure` script if necessary. You do not have to use this functionality of the new build system; feel free to run -`boot` and `configure` scripts manually, as you do when using `make`. +`boot` and `configure` scripts manually, as you do when using `make`. Note: on Windows +we automatically add flag `--enable-tarballs-autodownload` to `ARGS`, so you +don't have to do it manually. Beware, this uses network I/O which may sometimes be +undesirable. * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). * `--progress-info=STYLE`: choose how build progress info is printed. There are four From git at git.haskell.org Fri Oct 27 00:47:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (25a6441) Message-ID: <20171027004703.B0A623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/25a64411df44615296349aec133c180b8f008762/ghc >--------------------------------------------------------------- commit 25a64411df44615296349aec133c180b8f008762 Author: Andrey Mokhov Date: Fri Jan 6 02:59:20 2017 +0000 Minor revision >--------------------------------------------------------------- 25a64411df44615296349aec133c180b8f008762 src/Settings/Packages/Rts.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 7d844fa..8e71c87 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -56,7 +56,7 @@ rtsPackageArgs = package rts ? do , way == threaded ? arg "-DTHREADED_RTS" - , (input "//RtsMessages.c" ||^ input "//Trace.c") ? + , inputs ["//RtsMessages.c", "//Trace.c"] ? arg ("-DProjectVersion=" ++ show projectVersion) , input "//RtsUtils.c" ? append @@ -76,11 +76,10 @@ rtsPackageArgs = package rts ? do , "-DGhcUnregisterised=" ++ show ghcUnreg , "-DGhcEnableTablesNextToCode=" ++ show ghcEnableTNC ] - , input "//Evac.c" ? arg "-funroll-loops" - , input "//Evac_thr.c" ? arg "-funroll-loops" + , inputs ["//Evac.c", "//Evac_thr.c"] ? arg "-funroll-loops" - , input "//Evac_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] - , input "//Scav_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] ] + , inputs ["//Evac_thr.c", "//Scav_thr.c"] ? + append [ "-DPARALLEL_GC", "-Irts/sm" ] ] , builder Ghc ? arg "-Irts" From git at git.haskell.org Fri Oct 27 00:47:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refer to the build script simple as 'build'. (b9af374) Message-ID: <20171027004707.924EC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b9af374ec77c17971166f3a37c7409710bd7d8c5/ghc >--------------------------------------------------------------- commit b9af374ec77c17971166f3a37c7409710bd7d8c5 Author: Andrey Mokhov Date: Fri Feb 5 01:37:29 2016 +0000 Refer to the build script simple as 'build'. [skip ci] >--------------------------------------------------------------- b9af374ec77c17971166f3a37c7409710bd7d8c5 README.md | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/README.md b/README.md index f048ee4..37a144e 100644 --- a/README.md +++ b/README.md @@ -75,24 +75,24 @@ experiment following the Haddock comments. #### Clean and full rebuild -* `shake-build/build.sh clean` removes all build artefacts. Note, we are working -towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `build clean` removes all build artefacts. Note, we are working towards a +complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. -* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of -the previous build are still in the GHC tree. +* `build -B` forces Shake to rerun all rules, even if results of the previous build +are still in the GHC tree. #### Testing -* `shake-build/build.sh validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` -directory. This can be used instead of `sh validate --fast --no-clean` in the existing build system. -Note: this will rebuild Stage2 GHC, `ghc-pkg` and `hpc` if they are out of date. +* `build validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` +directory. This can be used instead of `sh validate --fast --no-clean` in the existing +build system. Note: this will rebuild Stage2 GHC, `ghc-pkg` and `hpc` if they are out of date. -* `shake-build/build.sh test` runs GHC tests by calling the `testsuite/driver/runtests.py` python -script with appropriate flags. The current implementation is limited and cannot replace the -`validate` script (see [#187][validation-issue]). +* `build test` runs GHC tests by calling the `testsuite/driver/runtests.py` python +script with appropriate flags. The current implementation is limited and cannot +replace the `validate` script (see [#187][validation-issue]). -* `shake-build/build.sh selftest` runs tests of the build system. Current test -coverage is close to zero (see [#197][test-issue]). +* `build selftest` runs tests of the build system. Current test coverage is close to +zero (see [#197][test-issue]). Current limitations ------------------- From git at git.haskell.org Fri Oct 27 00:47:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move -Wall before custom package settings, drop tab warnings (ab1c922) Message-ID: <20171027004707.D7D7F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ab1c922d6531519e91ebed34b47070ba6fdc4170/ghc >--------------------------------------------------------------- commit ab1c922d6531519e91ebed34b47070ba6fdc4170 Author: Andrey Mokhov Date: Fri Jan 6 16:34:21 2017 +0000 Move -Wall before custom package settings, drop tab warnings See #296 >--------------------------------------------------------------- ab1c922d6531519e91ebed34b47070ba6fdc4170 src/Settings/Builders/Ghc.hs | 5 ++--- src/Settings/Default.hs | 5 +---- 2 files changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index f5b13e1..98e5e39 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -7,12 +7,11 @@ import Settings.Builders.Common ghcBuilderArgs :: Args ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do needTouchy - mconcat [ commonGhcArgs + mconcat [ arg "-Wall" + , commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" , notStage0 ? arg "-O2" - , arg "-Wall" - , arg "-fwarn-tabs" , splitObjectsArgs , ghcLinkArgs , builder (Ghc CompileHs) ? arg "-c" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 67b0d5d..061d4ae 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -41,10 +41,7 @@ import UserSettings -- | All default command line arguments. defaultArgs :: Args -defaultArgs = mconcat - [ defaultBuilderArgs - , defaultPackageArgs - , builder Ghc ? remove ["-Wall", "-fwarn-tabs"] ] -- TODO: Fix warning Args. +defaultArgs = defaultBuilderArgs <> defaultPackageArgs -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". From git at git.haskell.org Fri Oct 27 00:47:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on package configuration when compiling package sources with GHC. (83c1e5e) Message-ID: <20171027004711.1D1123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/83c1e5e78010487dbe053c39b921c917ddb7f282/ghc >--------------------------------------------------------------- commit 83c1e5e78010487dbe053c39b921c917ddb7f282 Author: Andrey Mokhov Date: Sat Feb 6 02:39:27 2016 +0000 Depend on package configuration when compiling package sources with GHC. See #205. >--------------------------------------------------------------- 83c1e5e78010487dbe053c39b921c917ddb7f282 src/Settings/Builders/Ghc.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 74381eb..cc2afd5 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -103,9 +103,13 @@ wayGhcArgs = do -- TODO: Improve handling of "-hide-all-packages" packageGhcArgs :: Args packageGhcArgs = do + stage <- getStage pkg <- getPackage compId <- getPkgData ComponentId pkgDepIds <- getPkgDataList DepIds + lift . when (isLibrary pkg) $ do + conf <- pkgConfFile stage pkg + need [conf] mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" From git at git.haskell.org Fri Oct 27 00:47:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Duplicate libffi library for each build way (c88fc78) Message-ID: <20171027004711.612763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c88fc78440eb105ba5fe7d9a8bede47b30de36d6/ghc >--------------------------------------------------------------- commit c88fc78440eb105ba5fe7d9a8bede47b30de36d6 Author: Andrey Mokhov Date: Sat Jan 7 02:50:04 2017 +0000 Duplicate libffi library for each build way >--------------------------------------------------------------- c88fc78440eb105ba5fe7d9a8bede47b30de36d6 src/Rules/Libffi.hs | 4 ++-- src/Settings/Packages/Rts.hs | 11 +++++++++-- 2 files changed, 11 insertions(+), 4 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 65ec1d7..0f703d9 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -55,8 +55,8 @@ libffiRules = do forM_ hs $ \header -> copyFile header (rtsBuildPath -/- takeFileName header) - libffiName <- rtsLibffiLibraryName - copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") + ways <- interpretInContext libffiContext (getLibraryWays <> getRtsWays) + forM_ ways $ \way -> copyFile libffiLibrary =<< rtsLibffiLibrary way putSuccess $ "| Successfully built custom library 'libffi'" diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 8e71c87..e8000c8 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,4 +1,4 @@ -module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibraryName) where +module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibrary) where import Base import GHC @@ -7,6 +7,7 @@ import Oracles.Config.Setting import Oracles.Path import Predicate import Settings +import Settings.Path rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do @@ -17,6 +18,12 @@ rtsLibffiLibraryName = do (False, False) -> "Cffi" (_ , True ) -> "Cffi-6" +rtsLibffiLibrary :: Way -> Action FilePath +rtsLibffiLibrary way = do + name <- rtsLibffiLibraryName + suf <- libsuf way + return $ rtsBuildPath -/- "lib" ++ name ++ suf + rtsPackageArgs :: Args rtsPackageArgs = package rts ? do let yesNo = lift . fmap (\x -> if x then "YES" else "NO") @@ -38,7 +45,7 @@ rtsPackageArgs = package rts ? do way <- getWay path <- getBuildPath top <- getTopDirectory - libffiName <- lift $ rtsLibffiLibraryName + libffiName <- lift rtsLibffiLibraryName ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir mconcat From git at git.haskell.org Fri Oct 27 00:47:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't run GHC concurrently with ghc-pkg. (116bf85) Message-ID: <20171027004715.0EA963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/116bf853352b305eccf1392561d699c551cb07aa/ghc >--------------------------------------------------------------- commit 116bf853352b305eccf1392561d699c551cb07aa Author: Andrey Mokhov Date: Sat Feb 6 02:40:15 2016 +0000 Don't run GHC concurrently with ghc-pkg. Fix #205. >--------------------------------------------------------------- 116bf853352b305eccf1392561d699c551cb07aa src/Rules/Compile.hs | 14 +++++++++----- src/Rules/Data.hs | 24 ++---------------------- src/Rules/Register.hs | 30 ++++++++++++++++++++++++------ src/Rules/Resources.hs | 13 +++++++++---- 4 files changed, 44 insertions(+), 37 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index b27d36e..13af013 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -8,7 +8,7 @@ import Rules.Resources import Settings compilePackage :: Resources -> PartialTarget -> Rules () -compilePackage _ target @ (PartialTarget stage pkg) = do +compilePackage rs target @ (PartialTarget stage pkg) = do let buildPath = targetPath stage pkg -/- "build" matchBuildResult buildPath "hi" ?> \hi -> @@ -17,7 +17,8 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let way = detectWay hi (src, deps) <- dependencies buildPath $ hi -<.> osuf way need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [hi] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [hi] else need [ hi -<.> osuf (detectWay hi) ] matchBuildResult buildPath "hi-boot" ?> \hiboot -> @@ -26,7 +27,8 @@ compilePackage _ target @ (PartialTarget stage pkg) = do let way = detectWay hiboot (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf way need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [hiboot] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [hiboot] else need [ hiboot -<.> obootsuf (detectWay hiboot) ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) @@ -41,7 +43,8 @@ compilePackage _ target @ (PartialTarget stage pkg) = do if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) then need $ (obj -<.> hisuf (detectWay obj)) : src : deps else need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [obj] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [obj] -- TODO: get rid of these special cases matchBuildResult buildPath "o-boot" ?> \obj -> do @@ -50,4 +53,5 @@ compilePackage _ target @ (PartialTarget stage pkg) = do if compileInterfaceFilesSeparately then need $ (obj -<.> hibootsuf (detectWay obj)) : src : deps else need $ src : deps - build $ fullTargetWithWay target (Ghc stage) way [src] [obj] + buildWithResources [(resPackageDb rs, 1)] $ + fullTargetWithWay target (Ghc stage) way [src] [obj] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index ade93fd..00ec163 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -12,11 +12,10 @@ import Rules.Libffi import Rules.Resources import Settings import Settings.Builders.Common -import Settings.Packages.Rts -- Build package-data.mk by using GhcCabal to process pkgCabal file buildPackageData :: Resources -> PartialTarget -> Rules () -buildPackageData rs target @ (PartialTarget stage pkg) = do +buildPackageData _ target @ (PartialTarget stage pkg) = do let cabalFile = pkgCabalFile pkg configure = pkgPath pkg -/- "configure" dataFile = pkgDataFile stage pkg @@ -34,8 +33,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do deps <- packageDeps pkg pkgs <- interpretPartial target getPackages let depPkgs = matchPackageNames (sort pkgs) deps - depConfs <- traverse (pkgConfFile stage) depPkgs - orderOnly depConfs + need =<< traverse (pkgConfFile stage) depPkgs -- TODO: get rid of this, see #113 let inTreeMk = oldPath -/- takeFileName dataFile @@ -126,24 +124,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do writeFileChanged mk contents putSuccess $ "| Successfully generated '" ++ mk ++ "'." - need [rtsConf] - buildWithResources [(resGhcPkg rs, 1)] $ - fullTarget target (GhcPkg stage) [rtsConf] [] - - rtsConf %> \_ -> do - orderOnly $ generatedDependencies stage pkg - need [ rtsConfIn ] - build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] - - let fixRtsConf = unlines - . map - ( replace "\"\"" "" - . replace "rts/dist/build" rtsBuildPath ) - . filter (not . null) - . lines - - fixFile rtsConf fixRtsConf - -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' -- For example, get rid of diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 8c3ec73..d1b5312 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -6,11 +6,10 @@ import Base import Expression import GHC import Rules.Actions +import Rules.Libffi import Rules.Resources import Settings - --- matchPkgConf :: FilePath -> Bool --- matchPkgConf file = +import Settings.Packages.Rts -- Build package-data.mk by using GhcCabal to process pkgCabal file registerPackage :: Resources -> PartialTarget -> Rules () @@ -21,7 +20,7 @@ registerPackage rs target @ (PartialTarget stage pkg) = do Nothing -> False Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf" - when (stage <= Stage1) $ match ?> \_ -> do + when (stage <= Stage1) $ match ?> \conf -> do -- This produces pkgConfig. TODO: Add explicit tracking need [pkgDataFile stage pkg] @@ -35,5 +34,24 @@ registerPackage rs target @ (PartialTarget stage pkg) = do fixFile pkgConfig fixPkgConf - buildWithResources [(resGhcPkg rs, 1)] $ - fullTarget target (GhcPkg stage) [pkgConfig] [] + buildWithResources [(resPackageDb rs, resPackageDbLimit)] $ + fullTarget target (GhcPkg stage) [pkgConfig] [conf] + + when (pkg == rts && stage == Stage1) $ do + packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do + need [rtsConf] + buildWithResources [(resPackageDb rs, resPackageDbLimit)] $ + fullTarget target (GhcPkg stage) [rtsConf] [conf] + + rtsConf %> \_ -> do + need [ pkgDataFile Stage1 rts, rtsConfIn ] + build $ fullTarget target HsCpp [rtsConfIn] [rtsConf] + + let fixRtsConf = unlines + . map + ( replace "\"\"" "" + . replace "rts/dist/build" rtsBuildPath ) + . filter (not . null) + . lines + + fixFile rtsConf fixRtsConf diff --git a/src/Rules/Resources.hs b/src/Rules/Resources.hs index d5e58fe..40939e0 100644 --- a/src/Rules/Resources.hs +++ b/src/Rules/Resources.hs @@ -1,12 +1,17 @@ -module Rules.Resources (resourceRules, Resources (..)) where +module Rules.Resources (resourceRules, Resources (..), resPackageDbLimit) where import Base data Resources = Resources { - resGhcPkg :: Resource + resPackageDb :: Resource } --- We cannot register multiple packages in parallel: +-- We cannot register multiple packages in parallel. Also we cannot run GHC +-- when the package database is being mutated by "ghc-pkg". This is a classic +-- concurrent read exclusive write (CREW) conflict. resourceRules :: Rules Resources -resourceRules = Resources <$> newResource "ghc-pkg" 1 +resourceRules = Resources <$> newResource "package-db" resPackageDbLimit + +resPackageDbLimit :: Int +resPackageDbLimit = 1000 From git at git.haskell.org Fri Oct 27 00:47:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix way-specific flags (8e7685c) Message-ID: <20171027004715.6A5113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e7685c496e1ef4627d3f3b9d0850e6d5b487e07/ghc >--------------------------------------------------------------- commit 8e7685c496e1ef4627d3f3b9d0850e6d5b487e07 Author: Andrey Mokhov Date: Sat Jan 7 02:50:41 2017 +0000 Fix way-specific flags >--------------------------------------------------------------- 8e7685c496e1ef4627d3f3b9d0850e6d5b487e07 src/Settings/Packages/Rts.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e8000c8..6855402 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -61,7 +61,10 @@ rtsPackageArgs = package rts ? do -- be inlined. See also #90. , arg "-O2" - , way == threaded ? arg "-DTHREADED_RTS" + , Debug `wayUnit` way ? arg "-DDEBUG" + , way `elem` [debug, debugDynamic] ? arg "-DTICKY_TICKY" + , Profiling `wayUnit` way ? arg "-DPROFILING" + , Threaded `wayUnit` way ? arg "-DTHREADED_RTS" , inputs ["//RtsMessages.c", "//Trace.c"] ? arg ("-DProjectVersion=" ++ show projectVersion) From git at git.haskell.org Fri Oct 27 00:47:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix profiled GHC (76de227) Message-ID: <20171027004719.BB87E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/76de227586804a1bf4b4a98e0307f09966348609/ghc >--------------------------------------------------------------- commit 76de227586804a1bf4b4a98e0307f09966348609 Author: Andrey Mokhov Date: Sat Jan 7 02:55:48 2017 +0000 Fix profiled GHC See #239 >--------------------------------------------------------------- 76de227586804a1bf4b4a98e0307f09966348609 src/Rules.hs | 7 ++++--- src/Rules/Program.hs | 7 +++---- src/Settings.hs | 7 ++++++- 3 files changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 832bf4c..be7c89b 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -49,7 +49,7 @@ topLevelTargets = do docs <- interpretInContext context $ buildHaddock flavour need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else do -- otherwise build a program - need =<< maybeToList <$> programPath context + need =<< maybeToList <$> programPath (programContext stage pkg) packageRules :: Rules () packageRules = do @@ -61,21 +61,22 @@ packageRules = do let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] - -- TODO: not all build rules make sense for all stage/package combinations let contexts = liftM3 Context allStages knownPackages allWays vanillaContexts = liftM2 vanillaContext allStages knownPackages + programContexts = liftM2 programContext allStages knownPackages forM_ contexts $ mconcat [ Rules.Compile.compilePackage readPackageDb , Rules.Library.buildPackageLibrary ] + forM_ programContexts $ Rules.Program.buildProgram readPackageDb + forM_ vanillaContexts $ mconcat [ Rules.Data.buildPackageData , Rules.Dependencies.buildPackageDependencies readPackageDb , Rules.Documentation.buildPackageDocumentation , Rules.Library.buildPackageGhciLibrary , Rules.Generate.generatePackageCode - , Rules.Program.buildProgram readPackageDb , Rules.Register.registerPackage writePackageDb ] buildRules :: Rules () diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 319ca72..92aa4c1 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -30,7 +30,7 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do let installStage = do - latest <- latestBuildStage package -- isJust below is safe + latest <- latestBuildStage package -- fromJust below is safe return $ if package == ghc then stage else fromJust latest buildPath context -/- programName context <.> exe %> @@ -68,15 +68,14 @@ buildWrapper context at Context {..} wrapper wrapperPath binPath = do quote (pkgNameString package) ++ " (" ++ show stage ++ ")." -- TODO: Get rid of the Paths_hsc2hs.o hack. --- TODO: Do we need to consider other ways when building programs? buildBinary :: [(Resource, Int)] -> Context -> FilePath -> Action () buildBinary rs context at Context {..} bin = do binDeps <- if stage == Stage0 && package == ghcCabal then hsSources context else do - ways <- interpretInContext context getLibraryWays deps <- contextDependencies context - needContext [ dep { way = w } | dep <- deps, w <- ways ] + ways <- interpretInContext context (getLibraryWays <> getRtsWays) + needContext $ deps ++ [ rtsContext { way = w } | w <- ways ] let path = buildPath context cObjs <- map (objectPath context) <$> pkgDataList (CSrcs path) hsObjs <- hsObjects context diff --git a/src/Settings.hs b/src/Settings.hs index 8f94e5b..c455e0b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,7 +2,7 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, getContextDirectory, getBuildPath, stagePackages, builderPath, - getBuilderPath, isSpecified, latestBuildStage, programPath + getBuilderPath, isSpecified, latestBuildStage, programPath, programContext ) where import Base @@ -62,6 +62,11 @@ flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours flavours = hadrianFlavours ++ userFlavours flavourName = fromMaybe "default" cmdFlavour +programContext :: Stage -> Package -> Context +programContext stage pkg + | pkg == ghc && ghcProfiled flavour = Context stage pkg profiling + | otherwise = vanillaContext stage pkg + -- TODO: switch to Set Package as the order of packages should not matter? -- Otherwise we have to keep remembering to sort packages from time to time. knownPackages :: [Package] From git at git.haskell.org Fri Oct 27 00:47:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't run GHC -M concurrently with ghc-pkg. (44fd16d) Message-ID: <20171027004719.C00613A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44fd16dbaabe96205c493952930da708e774febd/ghc >--------------------------------------------------------------- commit 44fd16dbaabe96205c493952930da708e774febd Author: Andrey Mokhov Date: Sat Feb 6 14:53:29 2016 +0000 Don't run GHC -M concurrently with ghc-pkg. See #205. >--------------------------------------------------------------- 44fd16dbaabe96205c493952930da708e774febd src/Rules/Dependencies.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 92ac8db..30a5232 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -10,7 +10,7 @@ import Development.Shake.Util (parseMakefile) -- TODO: simplify handling of AutoApply.cmm buildPackageDependencies :: Resources -> PartialTarget -> Rules () -buildPackageDependencies _ target @ (PartialTarget stage pkg) = +buildPackageDependencies rs target @ (PartialTarget stage pkg) = let path = targetPath stage pkg buildPath = path -/- "build" dropBuild = (pkgPath pkg ++) . drop (length buildPath) @@ -29,7 +29,8 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) = need srcs if srcs == [] then writeFileChanged out "" - else build $ fullTarget target (GhcM stage) srcs [out] + else buildWithResources [(resPackageDb rs, 1)] $ + fullTarget target (GhcM stage) srcs [out] removeFileIfExists $ out <.> "bak" -- TODO: don't accumulate *.deps into .dependencies From git at git.haskell.org Fri Oct 27 00:47:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on RTS only when building GHC program (3ae4e1d) Message-ID: <20171027004723.A6ABD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ae4e1d0016ae2c28030da32180e5a5bda18de57/ghc >--------------------------------------------------------------- commit 3ae4e1d0016ae2c28030da32180e5a5bda18de57 Author: Andrey Mokhov Date: Sat Jan 7 03:22:41 2017 +0000 Depend on RTS only when building GHC program >--------------------------------------------------------------- 3ae4e1d0016ae2c28030da32180e5a5bda18de57 src/Rules/Program.hs | 7 ++++--- src/Settings/Flavours/Quickest.hs | 6 ++---- 2 files changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 92aa4c1..b1577e2 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -73,9 +73,10 @@ buildBinary rs context at Context {..} bin = do binDeps <- if stage == Stage0 && package == ghcCabal then hsSources context else do - deps <- contextDependencies context - ways <- interpretInContext context (getLibraryWays <> getRtsWays) - needContext $ deps ++ [ rtsContext { way = w } | w <- ways ] + needContext =<< contextDependencies context + when (package == ghc) $ do + ways <- interpretInContext context (getLibraryWays <> getRtsWays) + needContext [ rtsContext { way = w } | w <- ways ] let path = buildPath context cObjs <- map (objectPath context) <$> pkgDataList (CSrcs path) hsObjs <- hsObjects context diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 477a245..9f95957 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -8,10 +8,8 @@ quickestFlavour :: Flavour quickestFlavour = defaultFlavour { name = "quickest" , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs - , libraryWays = defaultLibraryWays <> quickestLibraryWays } + , libraryWays = append [vanilla] + , rtsWays = append [vanilla] } quickestArgs :: Args quickestArgs = builder Ghc ? arg "-O0" - -quickestLibraryWays :: Ways -quickestLibraryWays = remove [profiling] From git at git.haskell.org Fri Oct 27 00:47:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add copyDirectory to Rules.Actions. (63bbebf) Message-ID: <20171027004723.B5C133A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac/ghc >--------------------------------------------------------------- commit 63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac Author: Andrey Mokhov Date: Sun Feb 7 01:13:05 2016 +0000 Add copyDirectory to Rules.Actions. See #98. >--------------------------------------------------------------- 63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac src/Rules/Actions.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index daa4c5e..9275207 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,8 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, - moveDirectory, fixFile, runConfigure, runMake, runMakeVerbose, applyPatch, - renderLibrary, renderProgram, runBuilder, makeExecutable + copyDirectory, moveDirectory, applyPatch, fixFile, runConfigure, runMake, + runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -82,6 +82,12 @@ removeDirectory dir = do removeDirectoryIfExists dir -- Note, the source directory is untracked +copyDirectory :: FilePath -> FilePath -> Action () +copyDirectory source target = do + putProgressInfo $ renderAction "Copy directory" source target + quietly $ cmd (EchoStdout False) ["cp", "-r", source, target] + +-- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target From git at git.haskell.org Fri Oct 27 00:47:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove dependency on rts for programs built in Stage0 (daa4b7c) Message-ID: <20171027004727.1624B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/daa4b7c1ff6f55a5c8141c33fd36414581828392/ghc >--------------------------------------------------------------- commit daa4b7c1ff6f55a5c8141c33fd36414581828392 Author: Andrey Mokhov Date: Sat Jan 7 14:32:20 2017 +0000 Remove dependency on rts for programs built in Stage0 >--------------------------------------------------------------- daa4b7c1ff6f55a5c8141c33fd36414581828392 src/Rules/Program.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index b1577e2..254284a 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -74,7 +74,7 @@ buildBinary rs context at Context {..} bin = do then hsSources context else do needContext =<< contextDependencies context - when (package == ghc) $ do + when (stage > Stage0) $ do ways <- interpretInContext context (getLibraryWays <> getRtsWays) needContext [ rtsContext { way = w } | w <- ways ] let path = buildPath context From git at git.haskell.org Fri Oct 27 00:47:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --haddock command line flag. (7f2c6a1) Message-ID: <20171027004727.271B73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7f2c6a1a360d5351fadc3ab9a6cfa322a56b797e/ghc >--------------------------------------------------------------- commit 7f2c6a1a360d5351fadc3ab9a6cfa322a56b797e Author: Andrey Mokhov Date: Sun Feb 7 02:31:37 2016 +0000 Add --haddock command line flag. See #98. >--------------------------------------------------------------- 7f2c6a1a360d5351fadc3ab9a6cfa322a56b797e src/CmdLineFlag.hs | 18 ++++++++++++++---- src/Settings/User.hs | 2 +- 2 files changed, 15 insertions(+), 5 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 0142abb..84d4f11 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,6 +1,6 @@ module CmdLineFlag ( - putCmdLineFlags, cmdFlags, cmdConfigure, Configure (..), cmdFlavour, - Flavour (..), cmdProgressInfo, ProgressInfo (..), cmdSplitObjects + putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdConfigure, Configure (..), + cmdFlavour, Flavour (..), cmdProgressInfo, ProgressInfo (..), cmdSplitObjects ) where import Data.List.Extra @@ -18,7 +18,8 @@ data Flavour = Default | Quick deriving (Eq, Show) -- command line. These flags are not tracked, that is they do not force any -- build rules to be rurun. data Untracked = Untracked - { configure :: Configure + { buildHaddock :: Bool + , configure :: Configure , flavour :: Flavour , progressInfo :: ProgressInfo , splitObjects :: Bool } @@ -27,11 +28,15 @@ data Untracked = Untracked -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked defaultUntracked = Untracked - { configure = SkipConfigure + { buildHaddock = False + , configure = SkipConfigure , flavour = Default , progressInfo = Normal , splitObjects = False } +readBuildHaddock :: Either String (Untracked -> Untracked) +readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } + readConfigure :: Maybe String -> Either String (Untracked -> Untracked) readConfigure ms = maybe (Left "Cannot parse configure") (Right . set) (go $ lower <$> ms) @@ -75,6 +80,8 @@ cmdFlags = "Run configure with ARGS (also run boot if necessary)." , Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") "Build flavour (Default or Quick)." + , Option [] ["haddock"] (NoArg readBuildHaddock) + "Generate Haddock documentation." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") "Progress info style (None, Brief, Normal, or Unicorn)." , Option [] ["split-objects"] (NoArg readSplitObjects) @@ -93,6 +100,9 @@ putCmdLineFlags flags = modifyIORef cmdLineFlags (\f -> foldl (flip id) f flags) getCmdLineFlags :: Untracked getCmdLineFlags = unsafePerformIO $ readIORef cmdLineFlags +cmdBuildHaddock :: Bool +cmdBuildHaddock = buildHaddock getCmdLineFlags + cmdConfigure :: Configure cmdConfigure = configure getCmdLineFlags diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 2cf39aa..dd6150a 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -84,7 +84,7 @@ laxDependencies :: Bool laxDependencies = False buildHaddock :: Predicate -buildHaddock = return False -- FIXME: should be return True, see #98 +buildHaddock = return cmdBuildHaddock -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package From git at git.haskell.org Fri Oct 27 00:47:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant top-level rts target (cf73599) Message-ID: <20171027004731.0ABEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf7359904f868be93defcdf4a9a65974d8224cb4/ghc >--------------------------------------------------------------- commit cf7359904f868be93defcdf4a9a65974d8224cb4 Author: Andrey Mokhov Date: Sat Jan 7 14:33:25 2017 +0000 Drop redundant top-level rts target >--------------------------------------------------------------- cf7359904f868be93defcdf4a9a65974d8224cb4 src/Rules.hs | 10 +--------- 1 file changed, 1 insertion(+), 9 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index be7c89b..8db01f4 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -27,16 +27,8 @@ allStages = [minBound ..] -- | This rule 'need' all top-level build targets. topLevelTargets :: Rules () topLevelTargets = do - want $ Rules.Generate.installTargets - -- TODO: Do we want libffiLibrary to be a top-level target? - - action $ do -- TODO: Add support for all rtsWays - rtsLib <- pkgLibraryFile $ rtsContext { way = vanilla } - rtsThrLib <- pkgLibraryFile $ rtsContext { way = threaded } - need [ rtsLib, rtsThrLib ] - forM_ allStages $ \stage -> forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> action $ do let context = vanillaContext stage pkg @@ -48,7 +40,7 @@ topLevelTargets = do libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] - else do -- otherwise build a program + else -- otherwise build a program need =<< maybeToList <$> programPath (programContext stage pkg) packageRules :: Rules () From git at git.haskell.org Fri Oct 27 00:47:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy generated files to old build directories. (90c59d1) Message-ID: <20171027004731.15D213A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90c59d1382021802b10c385b93b70a6967a25719/ghc >--------------------------------------------------------------- commit 90c59d1382021802b10c385b93b70a6967a25719 Author: Andrey Mokhov Date: Sun Feb 7 02:32:32 2016 +0000 Copy generated files to old build directories. See #98. >--------------------------------------------------------------- 90c59d1382021802b10c385b93b70a6967a25719 src/Rules/Generate.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 9c67760..4ced436 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -3,6 +3,8 @@ module Rules.Generate ( includesDependencies, derivedConstantsPath, generatedDependencies ) where +import qualified System.Directory as IO + import Base import Expression import GHC @@ -144,19 +146,32 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] build $ fullTarget target GenPrimopCode [primopsTxt stage] [file] + -- TODO: this is temporary hack, get rid of this (#113) + let oldPath = pkgPath pkg -/- targetDirectory stage pkg -/- "build" + newFile = oldPath ++ (drop (length buildPath) file) + createDirectory $ takeDirectory newFile + liftIO $ IO.copyFile file newFile + putSuccess $ "| Duplicate file " ++ file ++ " -> " ++ newFile when (pkg == rts) $ buildPath -/- "AutoApply.cmm" %> \file -> do build $ fullTarget target GenApply [] [file] priority 2.0 $ do + -- TODO: this is temporary hack, get rid of this (#113) + let oldPath = pkgPath pkg -/- targetDirectory stage pkg -/- "build" + olden f = oldPath ++ (drop (length buildPath) f) + when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs + olden file <~ generateConfigHs -- TODO: get rid of this (#113) when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH + olden file <~ generateGhcBootPlatformH -- TODO: get rid of this (#113) when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do file <~ generateVersionHs + olden file <~ generateVersionHs -- TODO: get rid of this (#113) when (pkg == runGhc) $ buildPath -/- "Main.hs" %> \file -> do copyFileChanged (pkgPath pkg -/- "runghc.hs") file From git at git.haskell.org Fri Oct 27 00:47:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make quick and quickest flavours more precise (c27e8cb) Message-ID: <20171027004734.DCA423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c27e8cbe776256e9698957c1c3dda4a62b185bbe/ghc >--------------------------------------------------------------- commit c27e8cbe776256e9698957c1c3dda4a62b185bbe Author: Andrey Mokhov Date: Sat Jan 7 18:43:32 2017 +0000 Make quick and quickest flavours more precise >--------------------------------------------------------------- c27e8cbe776256e9698957c1c3dda4a62b185bbe src/Settings/Flavours/Quick.hs | 6 ++---- src/Settings/Flavours/Quickest.hs | 13 +++++++++---- 2 files changed, 11 insertions(+), 8 deletions(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 1e4f5c0..6935544 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -10,7 +10,8 @@ quickFlavour :: Flavour quickFlavour = defaultFlavour { name = "quick" , args = defaultBuilderArgs <> quickArgs <> defaultPackageArgs - , libraryWays = defaultLibraryWays <> quickLibraryWays } + , libraryWays = append [vanilla] + , rtsWays = append [vanilla, threaded] } optimise :: Context -> Bool optimise Context {..} = @@ -20,6 +21,3 @@ quickArgs :: Args quickArgs = builder Ghc ? do context <- getContext if optimise context then arg "-O" else arg "-O0" - -quickLibraryWays :: Ways -quickLibraryWays = remove [profiling] diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 9f95957..62ad43e 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -6,10 +6,15 @@ import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour quickestFlavour = defaultFlavour - { name = "quickest" - , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs - , libraryWays = append [vanilla] - , rtsWays = append [vanilla] } + { name = "quickest" + , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs + , libraryWays = append [vanilla] + , rtsWays = quickestRtsWays } quickestArgs :: Args quickestArgs = builder Ghc ? arg "-O0" + +quickestRtsWays :: Ways +quickestRtsWays = mconcat + [ append [vanilla] + , buildHaddock defaultFlavour ? append [threaded] ] From git at git.haskell.org Fri Oct 27 00:47:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Copy haddock-prologue.txt to new build directory. (7122295) Message-ID: <20171027004734.ED5FF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7122295adffb0c254bfbd39a394e8915ac0e806a/ghc >--------------------------------------------------------------- commit 7122295adffb0c254bfbd39a394e8915ac0e806a Author: Andrey Mokhov Date: Sun Feb 7 02:33:04 2016 +0000 Copy haddock-prologue.txt to new build directory. See #98. >--------------------------------------------------------------- 7122295adffb0c254bfbd39a394e8915ac0e806a src/Rules/Data.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 00ec163..dc77d21 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -47,6 +47,8 @@ buildPackageData _ target @ (PartialTarget stage pkg) = do createDirectory $ targetPath stage pkg -/- "build/autogen" forM_ autogenFiles $ \file -> do copyFile (oldPath -/- file) (targetPath stage pkg -/- file) + let haddockPrologue = "haddock-prologue.txt" + copyFile (oldPath -/- haddockPrologue) (targetPath stage pkg -/- haddockPrologue) postProcessPackageData stage pkg dataFile From git at git.haskell.org Fri Oct 27 00:47:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (12aa4ef) Message-ID: <20171027004738.7FBBB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12aa4ef0c4e6f8e0a89f2aa899d66a42ac2e3eb9/ghc >--------------------------------------------------------------- commit 12aa4ef0c4e6f8e0a89f2aa899d66a42ac2e3eb9 Author: Andrey Mokhov Date: Sat Jan 7 22:40:55 2017 +0000 Minor revision >--------------------------------------------------------------- 12aa4ef0c4e6f8e0a89f2aa899d66a42ac2e3eb9 src/Settings/Default.hs | 1 - src/Settings/Flavours/Quick.hs | 3 +-- src/Settings/Flavours/Quickest.hs | 8 ++++---- 3 files changed, 5 insertions(+), 7 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 061d4ae..92089ab 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -118,7 +118,6 @@ stage2Packages = do , ghcTags ] ++ [ haddock | doc ] --- TODO: What about profilingDynamic way? Do we need platformSupportsSharedLibs? -- | Default build ways for library packages: -- * We always build 'vanilla' way. -- * We build 'profiling' way when stage > Stage0. diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 6935544..324ec85 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -10,8 +10,7 @@ quickFlavour :: Flavour quickFlavour = defaultFlavour { name = "quick" , args = defaultBuilderArgs <> quickArgs <> defaultPackageArgs - , libraryWays = append [vanilla] - , rtsWays = append [vanilla, threaded] } + , libraryWays = append [vanilla] } optimise :: Context -> Bool optimise Context {..} = diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 62ad43e..4d64cd0 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -6,10 +6,10 @@ import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour quickestFlavour = defaultFlavour - { name = "quickest" - , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs - , libraryWays = append [vanilla] - , rtsWays = quickestRtsWays } + { name = "quickest" + , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs + , libraryWays = append [vanilla] + , rtsWays = quickestRtsWays } quickestArgs :: Args quickestArgs = builder Ghc ? arg "-O0" From git at git.haskell.org Fri Oct 27 00:47:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Haddock documentation. (e1b6c56) Message-ID: <20171027004738.9219E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1b6c5688198e78d8c1a6261479f69efdc640e1f/ghc >--------------------------------------------------------------- commit e1b6c5688198e78d8c1a6261479f69efdc640e1f Author: Andrey Mokhov Date: Sun Feb 7 02:34:27 2016 +0000 Fix Haddock documentation. Fix #98. >--------------------------------------------------------------- e1b6c5688198e78d8c1a6261479f69efdc640e1f src/Rules/Documentation.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index e235bfc..533ea47 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -8,6 +8,9 @@ import Rules.Actions import Rules.Resources import Settings +haddockHtmlLib :: FilePath +haddockHtmlLib = "inplace/lib/html/haddock-util.js" + -- Note: this build rule creates plenty of files, not just the .haddock one. -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. @@ -22,9 +25,10 @@ buildPackageDocumentation _ target @ (PartialTarget stage pkg) = let haddocks = [ pkgHaddockFile depPkg | Just depPkg <- map findKnownPackage deps , depPkg /= rts ] - need $ srcs ++ haddocks + need $ srcs ++ haddocks ++ [haddockHtmlLib] -- HsColour sources + -- TODO: what is the output of GhcCabalHsColour? whenM (specified HsColour) $ do pkgConf <- pkgConfFile stage pkg need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf @@ -34,6 +38,11 @@ buildPackageDocumentation _ target @ (PartialTarget stage pkg) = let haddockWay = if dynamicGhcPrograms then dynamic else vanilla build $ fullTargetWithWay target Haddock haddockWay srcs [file] + when (pkg == haddock) $ haddockHtmlLib %> \_ -> do + let dir = takeDirectory haddockHtmlLib + liftIO $ removeFiles dir ["//*"] + copyDirectory "utils/haddock/haddock-api/resources/html" dir + -- # Make the haddocking depend on the library .a file, to ensure -- # that we wait until the library is fully built before we haddock it -- $$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) : $$($1_$2_$$(HADDOCK_WAY)_LIB) From git at git.haskell.org Fri Oct 27 00:47:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move integerLibrary to flavour (6b35c2c) Message-ID: <20171027004742.52CA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b35c2c39cc41a548582483476c84e68798687b8/ghc >--------------------------------------------------------------- commit 6b35c2c39cc41a548582483476c84e68798687b8 Author: Andrey Mokhov Date: Sun Jan 8 01:28:06 2017 +0000 Move integerLibrary to flavour See #179 >--------------------------------------------------------------- 6b35c2c39cc41a548582483476c84e68798687b8 src/Flavour.hs | 1 + src/Rules/Generators/ConfigHs.hs | 11 +++++------ src/Settings.hs | 6 +++++- src/Settings/Default.hs | 4 ++-- src/Settings/Packages/Base.hs | 5 ++--- src/UserSettings.hs | 7 +------ 6 files changed, 16 insertions(+), 18 deletions(-) diff --git a/src/Flavour.hs b/src/Flavour.hs index ad658c4..b195767 100644 --- a/src/Flavour.hs +++ b/src/Flavour.hs @@ -8,6 +8,7 @@ data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. , args :: Args -- ^ Use these command line arguments. , packages :: Packages -- ^ Build these packages. + , integerLibrary :: Package -- ^ Either 'integerGmp' or 'integerSimple'. , libraryWays :: Ways -- ^ Build libraries these ways. , rtsWays :: Ways -- ^ Build RTS these ways. , splitObjects :: Predicate -- ^ Build split objects. diff --git a/src/Rules/Generators/ConfigHs.hs b/src/Rules/Generators/ConfigHs.hs index c5ad0cc..ffe0cfc 100644 --- a/src/Rules/Generators/ConfigHs.hs +++ b/src/Rules/Generators/ConfigHs.hs @@ -8,7 +8,6 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Rules.Generators.Common import Settings -import UserSettings generateConfigHs :: Expr String generateConfigHs = do @@ -21,10 +20,10 @@ generateConfigHs = do cProjectPatchLevel1 <- getSetting ProjectPatchLevel1 cProjectPatchLevel2 <- getSetting ProjectPatchLevel2 cBooterVersion <- getSetting GhcVersion - let cIntegerLibraryType | integerLibrary == integerGmp = "IntegerGMP" - | integerLibrary == integerSimple = "IntegerSimple" - | otherwise = error $ "Unknown integer library: " - ++ show integerLibrary ++ "." + let cIntegerLibraryType + | integerLibrary flavour == integerGmp = "IntegerGMP" + | integerLibrary flavour == integerSimple = "IntegerSimple" + | otherwise = error $ "Unknown integer library: " ++ integerLibraryName cSupportsSplitObjs <- yesNo supportsSplitObjects cGhcWithInterpreter <- yesNo ghcWithInterpreter cGhcWithNativeCodeGen <- yesNo ghcWithNativeCodeGen @@ -72,7 +71,7 @@ generateConfigHs = do , "cStage :: String" , "cStage = show (STAGE :: Int)" , "cIntegerLibrary :: String" - , "cIntegerLibrary = " ++ show (pkgNameString integerLibrary) + , "cIntegerLibrary = " ++ show integerLibraryName , "cIntegerLibraryType :: IntegerLibrary" , "cIntegerLibraryType = " ++ cIntegerLibraryType , "cSupportsSplitObjs :: String" diff --git a/src/Settings.hs b/src/Settings.hs index c455e0b..09b58f8 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,7 +2,8 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, getContextDirectory, getBuildPath, stagePackages, builderPath, - getBuilderPath, isSpecified, latestBuildStage, programPath, programContext + getBuilderPath, isSpecified, latestBuildStage, programPath, programContext, + integerLibraryName ) where import Base @@ -62,6 +63,9 @@ flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours flavours = hadrianFlavours ++ userFlavours flavourName = fromMaybe "default" cmdFlavour +integerLibraryName :: String +integerLibraryName = pkgNameString $ integerLibrary flavour + programContext :: Stage -> Package -> Context programContext stage pkg | pkg == ghc && ghcProfiled flavour = Context stage pkg profiling diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 92089ab..103c432 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -37,7 +37,6 @@ import Settings.Packages.Haddock import Settings.Packages.IntegerGmp import Settings.Packages.Rts import Settings.Packages.RunGhc -import UserSettings -- | All default command line arguments. defaultArgs :: Args @@ -100,7 +99,7 @@ stage1Packages = do , haskeline , hpcBin , hsc2hs - , integerLibrary + , integerLibrary flavour , pretty , process , rts @@ -147,6 +146,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages + , integerLibrary = integerGmp , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects diff --git a/src/Settings/Packages/Base.hs b/src/Settings/Packages/Base.hs index dce49e7..219c9d4 100644 --- a/src/Settings/Packages/Base.hs +++ b/src/Settings/Packages/Base.hs @@ -1,11 +1,10 @@ module Settings.Packages.Base (basePackageArgs) where -import Base import GHC import Predicate -import UserSettings +import Settings basePackageArgs :: Args basePackageArgs = package base ? mconcat - [ builder GhcCabal ? arg ("--flags=" ++ takeFileName (pkgPath integerLibrary)) + [ builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) , builder Cc ? arg "-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. diff --git a/src/UserSettings.hs b/src/UserSettings.hs index b952363..e16cf49 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,7 +3,7 @@ -- If you don't copy the file your changes will be tracked by git and you can -- accidentally commit them. module UserSettings ( - buildRootPath, userFlavours, userKnownPackages, integerLibrary, validating, + buildRootPath, userFlavours, userKnownPackages, validating, turnWarningsIntoErrors, verboseCommands, putBuild, putSuccess ) where @@ -11,7 +11,6 @@ import System.Console.ANSI import Base import Flavour -import GHC import Predicate -- See doc/user-settings.md for instructions. @@ -30,10 +29,6 @@ userFlavours = [] userKnownPackages :: [Package] userKnownPackages = [] --- | Choose the integer library: 'integerGmp' or 'integerSimple'. -integerLibrary :: Package -integerLibrary = integerGmp - -- | User defined flags. Note the following type semantics: -- * @Bool@: a plain Boolean flag whose value is known at compile time. -- * @Action Bool@: a flag whose value can depend on the build environment. From git at git.haskell.org Fri Oct 27 00:47:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --haddock flag. (52b915f) Message-ID: <20171027004742.61CF13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/52b915f9193a726c4a93ccea5e22ebfedcafbe3f/ghc >--------------------------------------------------------------- commit 52b915f9193a726c4a93ccea5e22ebfedcafbe3f Author: Andrey Mokhov Date: Sun Feb 7 02:42:27 2016 +0000 Add --haddock flag. See #98. [skip ci] >--------------------------------------------------------------- 52b915f9193a726c4a93ccea5e22ebfedcafbe3f README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 37a144e..35f8ac3 100644 --- a/README.md +++ b/README.md @@ -61,6 +61,7 @@ don't have to do it manually. Beware, this uses network I/O which may sometimes undesirable. * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). +* `--haddock`: build Haddock documentation. * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). @@ -98,8 +99,8 @@ Current limitations ------------------- The new build system still lacks many important features: * We only build `vanilla` way: [#4][dynamic-issue], [#186][profiling-issue]. -* Documentation is broken: [#98][haddock-issue]. * Validation is not implemented: [#187][validation-issue]. +* Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. @@ -138,7 +139,6 @@ helped me endure and enjoy the project. [test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 [profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 -[haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 From git at git.haskell.org Fri Oct 27 00:47:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on GMP only when using integerGmp (4ac02f6) Message-ID: <20171027004746.7B44A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ac02f6d213ff80fdb3659fb246688ada9886bbd/ghc >--------------------------------------------------------------- commit 4ac02f6d213ff80fdb3659fb246688ada9886bbd Author: Andrey Mokhov Date: Sun Jan 8 01:29:35 2017 +0000 Depend on GMP only when using integerGmp See #179 >--------------------------------------------------------------- 4ac02f6d213ff80fdb3659fb246688ada9886bbd src/Rules/Generate.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 5d557b4..51bec60 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -6,6 +6,7 @@ module Rules.Generate ( import Base import Context hiding (package) import Expression +import Flavour import GHC import Oracles.ModuleFiles import Predicate @@ -17,6 +18,7 @@ import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Rules.Libffi +import Settings import Settings.Path import Target import UserSettings @@ -70,7 +72,8 @@ compilerDependencies = do mconcat [ return [platformH stage] , return includesDependencies , return derivedConstantsDependencies - , notStage0 ? return (gmpLibraryH : libffiDependencies) + , notStage0 ? integerLibrary flavour == integerGmp ? return [gmpLibraryH] + , notStage0 ? return libffiDependencies , return $ fmap (path -/-) [ "primop-can-fail.hs-incl" , "primop-code-size.hs-incl" From git at git.haskell.org Fri Oct 27 00:47:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop duplication of ghc_boot_platform.h (8b24f9f) Message-ID: <20171027004746.820B93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8b24f9f05a7daf8b158748f4d04b4872085ec254/ghc >--------------------------------------------------------------- commit 8b24f9f05a7daf8b158748f4d04b4872085ec254 Author: Andrey Mokhov Date: Sun Feb 7 12:30:28 2016 +0000 Drop duplication of ghc_boot_platform.h See #98. >--------------------------------------------------------------- 8b24f9f05a7daf8b158748f4d04b4872085ec254 src/Rules/Generate.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 4ced436..1258d3f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -158,8 +158,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = priority 2.0 $ do -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- targetDirectory stage pkg -/- "build" - olden f = oldPath ++ (drop (length buildPath) f) + let oldPath = pkgPath pkg -/- targetDirectory stage pkg + olden f = oldPath ++ (drop (length (targetPath stage pkg)) f) when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do file <~ generateConfigHs @@ -167,7 +167,6 @@ generatePackageCode _ target @ (PartialTarget stage pkg) = when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH - olden file <~ generateGhcBootPlatformH -- TODO: get rid of this (#113) when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do file <~ generateVersionHs From git at git.haskell.org Fri Oct 27 00:47:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (7be13bf) Message-ID: <20171027004749.F0FD53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7be13bfa70a63ff190245cbfc6779e675e5d6816/ghc >--------------------------------------------------------------- commit 7be13bfa70a63ff190245cbfc6779e675e5d6816 Merge: 8b24f9f 52b915f Author: Andrey Mokhov Date: Sun Feb 7 12:30:56 2016 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 7be13bfa70a63ff190245cbfc6779e675e5d6816 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 00:47:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test integerSimple on CI (0c08cc6) Message-ID: <20171027004749.F07A73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c08cc6871a95c987d9a559bd805cc91238eea37/ghc >--------------------------------------------------------------- commit 0c08cc6871a95c987d9a559bd805cc91238eea37 Author: Andrey Mokhov Date: Sun Jan 8 01:30:31 2017 +0000 Test integerSimple on CI See #179 >--------------------------------------------------------------- 0c08cc6871a95c987d9a559bd805cc91238eea37 src/Settings/Default.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 103c432..0fb54f6 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -146,7 +146,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages - , integerLibrary = integerGmp + , integerLibrary = integerSimple -- FIXME after testing, #179! , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects From git at git.haskell.org Fri Oct 27 00:47:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (7e8bfbb) Message-ID: <20171027004754.2B32C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e8bfbbe5cf6a1ea303bdaebd862ea74b51eb843/ghc >--------------------------------------------------------------- commit 7e8bfbbe5cf6a1ea303bdaebd862ea74b51eb843 Author: Andrey Mokhov Date: Mon Feb 8 03:09:14 2016 +0000 Minor revision. >--------------------------------------------------------------- 7e8bfbbe5cf6a1ea303bdaebd862ea74b51eb843 src/Builder.hs | 2 +- src/Package.hs | 12 +++++------- src/Target.hs | 16 +++++++--------- 3 files changed, 13 insertions(+), 17 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 80fc4ba..d1a2cc3 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -58,7 +58,7 @@ builderProvenance = \case DeriveConstants -> Just (Stage0, deriveConstants) GenApply -> Just (Stage0, genapply) GenPrimopCode -> Just (Stage0, genprimopcode) - Ghc stage -> if stage > Stage0 then Just (pred stage, ghc) else Nothing + Ghc stage -> if stage == Stage0 then Nothing else Just (pred stage, ghc) GhcM stage -> builderProvenance $ Ghc stage GhcCabal -> Just (Stage0, ghcCabal) GhcCabalHsColour -> builderProvenance $ GhcCabal diff --git a/src/Package.hs b/src/Package.hs index 43eb480..4b6fbc6 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -29,13 +29,11 @@ instance Show PackageName where data PackageType = Program | Library deriving Generic data Package = Package - { - pkgName :: PackageName, -- ^ Examples: "ghc", "Cabal" - pkgPath :: FilePath, -- ^ pkgPath is the path to the source code relative to the root. - -- e.g. "compiler", "libraries/Cabal/Cabal" - pkgType :: PackageType - } - deriving Generic + { pkgName :: PackageName -- ^ Examples: "ghc", "Cabal" + , pkgPath :: FilePath -- ^ pkgPath is the path to the source code relative to the root. + -- e.g. "compiler", "libraries/Cabal/Cabal" + , pkgType :: PackageType + } deriving Generic -- | Prettyprint Package name. pkgNameString :: Package -> String diff --git a/src/Target.hs b/src/Target.hs index d2cbfce..8c39ac7 100644 --- a/src/Target.hs +++ b/src/Target.hs @@ -18,15 +18,13 @@ import Way -- | Parameters relevant to the current build target. data Target = Target - { - stage :: Stage, -- ^ Stage being built - package :: Package, -- ^ Package being built - builder :: Builder, -- ^ Builder to be invoked - way :: Way, -- ^ Way to build (set to vanilla for most targets) - inputs :: [FilePath], -- ^ Source files passed to the builder - outputs :: [FilePath] -- ^ Files to be produced - } - deriving (Show, Eq, Generic) + { stage :: Stage -- ^ Stage being built + , package :: Package -- ^ Package being built + , builder :: Builder -- ^ Builder to be invoked + , way :: Way -- ^ Way to build (set to vanilla for most targets) + , inputs :: [FilePath] -- ^ Source files passed to the builder + , outputs :: [FilePath] -- ^ Files to be produced + } deriving (Show, Eq, Generic) -- | If values of type @a@ form a 'Monoid' then we can also derive a 'Monoid' -- instance for values of type @'ReaderT' 'Target' 'Action' a@: From git at git.haskell.org Fri Oct 27 00:47:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert to integerGmp (de151a9) Message-ID: <20171027004754.349C03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de151a9b7b8b5c595aa2084c160663340d7e5c3c/ghc >--------------------------------------------------------------- commit de151a9b7b8b5c595aa2084c160663340d7e5c3c Author: Andrey Mokhov Date: Sun Jan 8 02:11:38 2017 +0000 Revert to integerGmp Fix #179. >--------------------------------------------------------------- de151a9b7b8b5c595aa2084c160663340d7e5c3c src/Settings/Default.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 0fb54f6..103c432 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -146,7 +146,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages - , integerLibrary = integerSimple -- FIXME after testing, #179! + , integerLibrary = integerGmp , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects From git at git.haskell.org Fri Oct 27 00:47:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -fno-warn-name-shadowing. (7d7802d) Message-ID: <20171027004758.606123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7d7802d73a03dd913d43aad6e36ec6e72c6744ae/ghc >--------------------------------------------------------------- commit 7d7802d73a03dd913d43aad6e36ec6e72c6744ae Author: Andrey Mokhov Date: Mon Feb 8 23:17:49 2016 +0000 Add -fno-warn-name-shadowing. >--------------------------------------------------------------- 7d7802d73a03dd913d43aad6e36ec6e72c6744ae build.sh | 1 + 1 file changed, 1 insertion(+) diff --git a/build.sh b/build.sh index 719e85e..77c9fa4 100755 --- a/build.sh +++ b/build.sh @@ -35,6 +35,7 @@ mkdir -p "$root/.shake" ghc \ "$root/src/Main.hs" \ -Wall \ + -fno-warn-name-shadowing \ -i"$root/src" \ -rtsopts \ -with-rtsopts=-I0 \ From git at git.haskell.org Fri Oct 27 00:47:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:47:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update section on integerLibrary, expand build ways example (60c8172) Message-ID: <20171027004758.6F4ED3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/60c8172861fdc8e4b66b68ae971c91ccc794ebba/ghc >--------------------------------------------------------------- commit 60c8172861fdc8e4b66b68ae971c91ccc794ebba Author: Andrey Mokhov Date: Sun Jan 8 02:39:51 2017 +0000 Update section on integerLibrary, expand build ways example See #179 >--------------------------------------------------------------- 60c8172861fdc8e4b66b68ae971c91ccc794ebba doc/user-settings.md | 25 ++++++++++++++++--------- 1 file changed, 16 insertions(+), 9 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index d4f0f95..9d776ea 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -24,6 +24,7 @@ data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. , args :: Args -- ^ Use these command line arguments. , packages :: Packages -- ^ Build these packages. + , integerLibrary :: Package -- ^ Either 'integerGmp' or 'integerSimple'. , libraryWays :: Ways -- ^ Build libraries these ways. , rtsWays :: Ways -- ^ Build RTS these ways. , splitObjects :: Predicate -- ^ Build split objects. @@ -111,24 +112,30 @@ userPackage = library "user-package" You will also need to add `userPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. -You can choose which integer library to use when builing GHC by setting -`integerLibrary`. Possible values are: `integerGmp` (default) and `integerSimple`. +You can choose which integer library to use when builing GHC using the +`integerLibrary` setting of the build flavour. Possible values are: `integerGmp` +(default) and `integerSimple`. ```haskell --- | Choose the integer library: 'integerGmp' or 'integerSimple'. -integerLibrary :: Package -integerLibrary = integerGmp +simpleFlavour :: Flavour +simpleFlavour = defaultFlavour { name = "simple", integerLibrary = integerSimple } ``` ## Build ways Packages can be built in a number of ways, such as `vanilla`, `profiling` (with profiling information enabled), and many others as defined in `src/Way.hs`. You can change the default build ways by modifying `libraryWays` and `rtsWays` fields -of the `Flavour` record as required. As an example, below we remove `dynamic` -from the list of library ways but keep `rts` package ways unchanged: +of the `Flavour` record as required. As an example, below we remove `profiling` +from the list of library ways: ```haskell -userFlavour :: Flavour -userFlavour = defaultFlavour { name = "user", libraryWays = defaultLibraryWays <> remove [dynamic] } +noProfilingFlavour :: Flavour +noProfilingFlavour = defaultFlavour + { name = "no-profiling" + , libraryWays = defaultLibraryWays <> remove [profiling] + , ghcProfiled = False } -- Can't build profiled GHC without profiled libraries ``` +Note that `rtsWays` is computed from `libraryWays` by default, therefore the above +change will lead to the removal of `threadedProfiling` way from `rtsWays`. To +change this behaviour, you can override the default `rtsWays` setting. ## Verbose command lines From git at git.haskell.org Fri Oct 27 00:48:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Rules.Config to Rules.Setup. (d5e2d92) Message-ID: <20171027004802.A1C543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d5e2d9278d4590fa370fb73900447a573fc37e2f/ghc >--------------------------------------------------------------- commit d5e2d9278d4590fa370fb73900447a573fc37e2f Author: Andrey Mokhov Date: Mon Feb 8 23:19:35 2016 +0000 Rename Rules.Config to Rules.Setup. See #204. >--------------------------------------------------------------- d5e2d9278d4590fa370fb73900447a573fc37e2f shaking-up-ghc.cabal | 2 +- src/Main.hs | 4 ++-- src/Rules/{Config.hs => Setup.hs} | 6 +++--- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 0807ff3..254617d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -42,7 +42,6 @@ executable ghc-shake , Rules.Cabal , Rules.Clean , Rules.Compile - , Rules.Config , Rules.Data , Rules.Dependencies , Rules.Documentation @@ -64,6 +63,7 @@ executable ghc-shake , Rules.Program , Rules.Register , Rules.Resources + , Rules.Setup , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg , Selftest diff --git a/src/Main.hs b/src/Main.hs index 79601d8..544987d 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -8,12 +8,12 @@ import qualified Environment import qualified Rules import qualified Rules.Cabal import qualified Rules.Clean -import qualified Rules.Config import qualified Rules.Generate import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl +import qualified Rules.Setup import qualified Selftest import qualified Test @@ -29,13 +29,13 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do rules = mconcat [ Rules.Cabal.cabalRules , Rules.Clean.cleanRules - , Rules.Config.configRules , Rules.Generate.generateRules , Rules.Generate.copyRules , Rules.Gmp.gmpRules , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules , Rules.Perl.perlScriptRules + , Rules.Setup.setupRules , Rules.topLevelTargets , Rules.packageRules , Selftest.selftestRules diff --git a/src/Rules/Config.hs b/src/Rules/Setup.hs similarity index 93% rename from src/Rules/Config.hs rename to src/Rules/Setup.hs index 1016be9..a88084c 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Setup.hs @@ -1,4 +1,4 @@ -module Rules.Config (configRules) where +module Rules.Setup (setupRules) where import qualified System.Info @@ -7,8 +7,8 @@ import CmdLineFlag import Rules.Actions import Rules.Generators.GhcAutoconfH -configRules :: Rules () -configRules = do +setupRules :: Rules () +setupRules = do -- We always rerun the configure script in this mode, because the flags -- passed to it can affect the contents of system.config file. [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do From git at git.haskell.org Fri Oct 27 00:48:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop no longer relevant bits (1774b40) Message-ID: <20171027004802.B1D653A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1774b40d0be398953bc0ad03bc364a951d971a7b/ghc >--------------------------------------------------------------- commit 1774b40d0be398953bc0ad03bc364a951d971a7b Author: Andrey Mokhov Date: Sun Jan 8 02:56:18 2017 +0000 Drop no longer relevant bits >--------------------------------------------------------------- 1774b40d0be398953bc0ad03bc364a951d971a7b src/Flavour.hs | 6 +++++- src/Settings/Builders/Common.hs | 6 ++---- src/UserSettings.hs | 19 ++----------------- 3 files changed, 9 insertions(+), 22 deletions(-) diff --git a/src/Flavour.hs b/src/Flavour.hs index b195767..3283eda 100644 --- a/src/Flavour.hs +++ b/src/Flavour.hs @@ -2,8 +2,12 @@ module Flavour (Flavour (..)) where import Expression --- TODO: Merge {libraryWays, rtsWays}, and {dynamicGhcPrograms, ghcProfiled...}. -- | 'Flavour' is a collection of build settings that fully define a GHC build. +-- Note the following type semantics: +-- * @Bool@: a plain Boolean flag whose value is known at compile time. +-- * @Action Bool@: a flag whose value can depend on the build environment. +-- * @Predicate@: a flag whose value can depend on the build environment and +-- on the current build target. data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. , args :: Args -- ^ Use these command line arguments. diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 271851e..a6b8198 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -41,16 +41,14 @@ cIncludeArgs = do ldArgs :: Args ldArgs = mempty --- TODO: put all validating options together in one file cArgs :: Args -cArgs = validating ? cWarnings +cArgs = mempty -- TODO: should be in a different file cWarnings :: Args cWarnings = do let gccGe46 = notM $ (flag GccIsClang ||^ flag GccLt46) - mconcat [ turnWarningsIntoErrors ? arg "-Werror" - , arg "-Wall" + mconcat [ arg "-Wall" , flag GccIsClang ? arg "-Wno-unknown-pragmas" , gccGe46 ? notM windowsHost ? arg "-Werror=unused-but-set-variable" , gccGe46 ? arg "-Wno-error=inline" ] diff --git a/src/UserSettings.hs b/src/UserSettings.hs index e16cf49..09d70e1 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,8 +3,8 @@ -- If you don't copy the file your changes will be tracked by git and you can -- accidentally commit them. module UserSettings ( - buildRootPath, userFlavours, userKnownPackages, validating, - turnWarningsIntoErrors, verboseCommands, putBuild, putSuccess + buildRootPath, userFlavours, userKnownPackages, verboseCommands, + putBuild, putSuccess ) where import System.Console.ANSI @@ -29,21 +29,6 @@ userFlavours = [] userKnownPackages :: [Package] userKnownPackages = [] --- | User defined flags. Note the following type semantics: --- * @Bool@: a plain Boolean flag whose value is known at compile time. --- * @Action Bool@: a flag whose value can depend on the build environment. --- * @Predicate@: a flag whose value can depend on the build environment and --- on the current build target. - --- TODO: This should be set automatically when validating. -validating :: Bool -validating = False - --- TODO: Replace with stage2 ? arg "-Werror"? Also see #251. --- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. -turnWarningsIntoErrors :: Predicate -turnWarningsIntoErrors = return False - -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output only for certain -- targets, e.g.: @verboseCommands = package ghcPrim at . From git at git.haskell.org Fri Oct 27 00:48:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run mk/get-win32-tarballs.sh on Windows. (0678acb) Message-ID: <20171027004806.602D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0678acb67ab59b4af9f2401959e1d71ef27d77bc/ghc >--------------------------------------------------------------- commit 0678acb67ab59b4af9f2401959e1d71ef27d77bc Author: Andrey Mokhov Date: Mon Feb 8 23:37:58 2016 +0000 Run mk/get-win32-tarballs.sh on Windows. See #204. >--------------------------------------------------------------- 0678acb67ab59b4af9f2401959e1d71ef27d77bc src/Rules/Setup.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index a88084c..ac53592 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -17,10 +17,13 @@ setupRules = do RunConfigure args -> do need [ settings <.> "in", cfgH <.> "in" ] -- We cannot use windowsHost here due to a cyclic dependency - let defaultArgs = if System.Info.os == "mingw32" - then [ "--enable-tarballs-autodownload" ] - else [] - runConfigure "." [] $ defaultArgs ++ [args] + when (System.Info.os == "mingw32") $ do + putBuild "| Checking for Windows tarballs..." + quietly $ cmd [ "bash" + , "mk/get-win32-tarballs.sh" + , "download" + , System.Info.arch ] + runConfigure "." [] [args] SkipConfigure -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " From git at git.haskell.org Fri Oct 27 00:48:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add development flavours (d6e7919) Message-ID: <20171027004806.6B2E23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6e7919a7d67462ee29a3019f46d6e7899bb4c50/ghc >--------------------------------------------------------------- commit d6e7919a7d67462ee29a3019f46d6e7899bb4c50 Author: Andrey Mokhov Date: Mon Jan 9 01:24:57 2017 +0000 Add development flavours See #188, #268 >--------------------------------------------------------------- d6e7919a7d67462ee29a3019f46d6e7899bb4c50 hadrian.cabal | 1 + src/CmdLineFlag.hs | 4 ++-- src/Settings.hs | 6 ++++-- src/Settings/Builders/Ghc.hs | 3 --- src/Settings/Default.hs | 5 ++++- src/Settings/Flavours/Development.hs | 26 ++++++++++++++++++++++++++ 6 files changed, 37 insertions(+), 8 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 712d4c6..598bd27 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -85,6 +85,7 @@ executable hadrian , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default + , Settings.Flavours.Development , Settings.Flavours.Perf , Settings.Flavours.Prof , Settings.Flavours.Quick diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index b58df7b..ebe907a 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -38,7 +38,7 @@ readBuildHaddock :: Either String (Untracked -> Untracked) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } readFlavour :: Maybe String -> Either String (Untracked -> Untracked) -readFlavour ms = Right $ \flags -> flags { flavour = ms } +readFlavour ms = Right $ \flags -> flags { flavour = lower <$> ms } readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) readProgressColour ms = @@ -74,7 +74,7 @@ readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") - "Build flavour (default, quick or quickest)." + "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") diff --git a/src/Settings.hs b/src/Settings.hs index 09b58f8..01ee122 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -15,6 +15,7 @@ import GHC import Oracles.PackageData import Oracles.Path import {-# SOURCE #-} Settings.Default +import Settings.Flavours.Development import Settings.Flavours.Perf import Settings.Flavours.Prof import Settings.Flavours.Quick @@ -53,8 +54,9 @@ getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getBuildPath hadrianFlavours :: [Flavour] -hadrianFlavours = [ defaultFlavour, perfFlavour, profFlavour, quickFlavour - , quickestFlavour ] +hadrianFlavours = + [ defaultFlavour, developmentFlavour Stage1, developmentFlavour Stage2 + , perfFlavour, profFlavour, quickFlavour, quickestFlavour ] flavour :: Flavour flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 98e5e39..669900f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -9,9 +9,6 @@ ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do needTouchy mconcat [ arg "-Wall" , commonGhcArgs - , arg "-H32m" - , stage0 ? arg "-O" - , notStage0 ? arg "-O2" , splitObjectsArgs , ghcLinkArgs , builder (Ghc CompileHs) ? arg "-c" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 103c432..6db669e 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -40,7 +40,10 @@ import Settings.Packages.RunGhc -- | All default command line arguments. defaultArgs :: Args -defaultArgs = defaultBuilderArgs <> defaultPackageArgs +defaultArgs = mconcat + [ defaultBuilderArgs + , builder Ghc ? mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2", arg "-H32m"] + , defaultPackageArgs ] -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs new file mode 100644 index 0000000..afe42d5 --- /dev/null +++ b/src/Settings/Flavours/Development.hs @@ -0,0 +1,26 @@ +module Settings.Flavours.Development (developmentFlavour) where + +import Flavour +import GHC +import Predicate +import {-# SOURCE #-} Settings.Default + +-- TODO: Implement an equivalent of LAX_DEPENDENCIES = YES setting, see #250. +developmentFlavour :: Stage -> Flavour +developmentFlavour ghcStage = defaultFlavour + { name = "devel" ++ show (fromEnum ghcStage) + , args = developmentArgs ghcStage + , libraryWays = append [vanilla] } + +developmentArgs :: Stage -> Args +developmentArgs ghcStage = do + stage <- getStage + pkg <- getPackage + let now = succ stage == ghcStage + mconcat [ defaultBuilderArgs + , builder Ghc ? mconcat + [ append ["-O", "-H64m"] + , now ? pkg == compiler ? append ["-O0", "-DDEBUG", "-dcore-lint"] + , now ? pkg == ghc ? append ["-O0", "-DDEBUG"] + , notStage0 ? isLibrary pkg ? arg "-dcore-lint" ] + , defaultPackageArgs ] From git at git.haskell.org Fri Oct 27 00:48:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor build flavours (b2ca3dd) Message-ID: <20171027004810.799293A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2ca3dd7366f8f8eaf598597c52e99465124ab2c/ghc >--------------------------------------------------------------- commit b2ca3dd7366f8f8eaf598597c52e99465124ab2c Author: Andrey Mokhov Date: Mon Jan 9 03:30:19 2017 +0000 Refactor build flavours >--------------------------------------------------------------- b2ca3dd7366f8f8eaf598597c52e99465124ab2c hadrian.cabal | 5 +++-- src/Settings.hs | 6 +++--- src/Settings/Default.hs | 11 ++++++++++- src/Settings/Flavours/Development.hs | 20 ++++++++------------ src/Settings/Flavours/Perf.hs | 21 --------------------- src/Settings/Flavours/Performance.hs | 18 ++++++++++++++++++ src/Settings/Flavours/Prof.hs | 21 --------------------- src/Settings/Flavours/Profiled.hs | 19 +++++++++++++++++++ src/Settings/Flavours/Quick.hs | 16 +++++++--------- src/Settings/Flavours/Quickest.hs | 7 ++++++- src/Settings/Optimisation.hs | 21 +++++++++++++++++++++ 11 files changed, 95 insertions(+), 70 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 b2ca3dd7366f8f8eaf598597c52e99465124ab2c From git at git.haskell.org Fri Oct 27 00:48:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (507f48d) Message-ID: <20171027004810.72CF03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/507f48d12b6715d0943ae1b6bc4d7e8b6c676870/ghc >--------------------------------------------------------------- commit 507f48d12b6715d0943ae1b6bc4d7e8b6c676870 Author: Andrey Mokhov Date: Mon Feb 8 23:52:38 2016 +0000 Minor revision. >--------------------------------------------------------------- 507f48d12b6715d0943ae1b6bc4d7e8b6c676870 src/Rules/Actions.hs | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9275207..1a6fbf8 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -106,17 +106,16 @@ runConfigure dir opts args = do need [dir -/- "configure"] let args' = filter (not . null) args note = if null args' then "" else " (" ++ intercalate ", " args' ++ ")" + -- Always configure with bash. + -- This also injects /bin/bash into `libtool`, instead of /bin/sh + opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] if dir == "." then do putBuild $ "| Run configure" ++ note ++ "..." - quietly $ cmd Shell (EchoStdout False) "bash configure" opts' args + quietly $ cmd Shell (EchoStdout False) "bash configure" opts' args' else do putBuild $ "| Run configure" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args - where - -- Always configure with bash. - -- This also injects /bin/bash into `libtool`, instead of /bin/sh - opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"] + quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args' runMake :: FilePath -> [String] -> Action () runMake = runMakeWithVerbosity False From git at git.haskell.org Fri Oct 27 00:48:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename the --configure flag to --setup. (4cef7ec) Message-ID: <20171027004814.857833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1/ghc >--------------------------------------------------------------- commit 4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1 Author: Andrey Mokhov Date: Mon Feb 8 23:53:19 2016 +0000 Rename the --configure flag to --setup. See #204. >--------------------------------------------------------------- 4cef7ecc4f7c3e63c55a2d0800a7370c09a85aa1 src/CmdLineFlag.hs | 40 ++++++++++++++++++++-------------------- src/Rules/Setup.hs | 10 +++++----- 2 files changed, 25 insertions(+), 25 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 84d4f11..c7d2b35 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,5 +1,5 @@ module CmdLineFlag ( - putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdConfigure, Configure (..), + putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdSetup, Setup (..), cmdFlavour, Flavour (..), cmdProgressInfo, ProgressInfo (..), cmdSplitObjects ) where @@ -11,7 +11,7 @@ import System.IO.Unsafe (unsafePerformIO) -- Command line flags data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -data Configure = SkipConfigure | RunConfigure String deriving (Eq, Show) +data Setup = SkipSetup | RunSetup String deriving (Eq, Show) data Flavour = Default | Quick deriving (Eq, Show) -- | 'CmdLineFlag.Untracked' is a collection of flags that can be passed via the @@ -19,9 +19,9 @@ data Flavour = Default | Quick deriving (Eq, Show) -- build rules to be rurun. data Untracked = Untracked { buildHaddock :: Bool - , configure :: Configure , flavour :: Flavour , progressInfo :: ProgressInfo + , setup :: Setup , splitObjects :: Bool } deriving (Eq, Show) @@ -29,24 +29,14 @@ data Untracked = Untracked defaultUntracked :: Untracked defaultUntracked = Untracked { buildHaddock = False - , configure = SkipConfigure , flavour = Default , progressInfo = Normal + , setup = SkipSetup , splitObjects = False } readBuildHaddock :: Either String (Untracked -> Untracked) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } -readConfigure :: Maybe String -> Either String (Untracked -> Untracked) -readConfigure ms = - maybe (Left "Cannot parse configure") (Right . set) (go $ lower <$> ms) - where - go :: Maybe String -> Maybe Configure - go (Just args) = Just $ RunConfigure args - go Nothing = Just $ RunConfigure "" - set :: Configure -> Untracked -> Untracked - set flag flags = flags { configure = flag } - readFlavour :: Maybe String -> Either String (Untracked -> Untracked) readFlavour ms = maybe (Left "Cannot parse flavour") (Right . set) (go =<< lower <$> ms) @@ -71,19 +61,29 @@ readProgressInfo ms = set :: ProgressInfo -> Untracked -> Untracked set flag flags = flags { progressInfo = flag } +readSetup :: Maybe String -> Either String (Untracked -> Untracked) +readSetup ms = + maybe (Left "Cannot parse setup") (Right . set) (go $ lower <$> ms) + where + go :: Maybe String -> Maybe Setup + go (Just args) = Just $ RunSetup args + go Nothing = Just $ RunSetup "" + set :: Setup -> Untracked -> Untracked + set flag flags = flags { setup = flag } + readSplitObjects :: Either String (Untracked -> Untracked) readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = - [ Option [] ["configure"] (OptArg readConfigure "ARGS") - "Run configure with ARGS (also run boot if necessary)." - , Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") + [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") "Build flavour (Default or Quick)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") "Progress info style (None, Brief, Normal, or Unicorn)." + , Option [] ["setup"] (OptArg readSetup "CONFIGURE_ARGS") + "Setup the build system, pass CONFIGURE_ARGS to ./configure." , Option [] ["split-objects"] (NoArg readSplitObjects) "Generate split objects (requires a full clean rebuild)." ] @@ -103,14 +103,14 @@ getCmdLineFlags = unsafePerformIO $ readIORef cmdLineFlags cmdBuildHaddock :: Bool cmdBuildHaddock = buildHaddock getCmdLineFlags -cmdConfigure :: Configure -cmdConfigure = configure getCmdLineFlags - cmdFlavour :: Flavour cmdFlavour = flavour getCmdLineFlags cmdProgressInfo :: ProgressInfo cmdProgressInfo = progressInfo getCmdLineFlags +cmdSetup :: Setup +cmdSetup = setup getCmdLineFlags + cmdSplitObjects :: Bool cmdSplitObjects = splitObjects getCmdLineFlags diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index ac53592..c99c8be 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -13,8 +13,8 @@ setupRules = do -- passed to it can affect the contents of system.config file. [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do alwaysRerun - case cmdConfigure of - RunConfigure args -> do + case cmdSetup of + RunSetup configureArgs -> do need [ settings <.> "in", cfgH <.> "in" ] -- We cannot use windowsHost here due to a cyclic dependency when (System.Info.os == "mingw32") $ do @@ -23,11 +23,11 @@ setupRules = do , "mk/get-win32-tarballs.sh" , "download" , System.Info.arch ] - runConfigure "." [] [args] - SkipConfigure -> unlessM (doesFileExist cfg) $ + runConfigure "." [] [configureArgs] + SkipSetup -> unlessM (doesFileExist cfg) $ putError $ "Configuration file " ++ cfg ++ " is missing.\n" ++ "Run the configure script either manually or via the " - ++ "build system by passing --configure[=ARGS] flag." + ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." ["configure", configH <.> "in"] &%> \_ -> do putBuild "| Running boot..." From git at git.haskell.org Fri Oct 27 00:48:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a doc on build flavours (ff9e5b6) Message-ID: <20171027004814.984EF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff9e5b6362b5112a06f7018a5462639c9ef4d83c/ghc >--------------------------------------------------------------- commit ff9e5b6362b5112a06f7018a5462639c9ef4d83c Author: Andrey Mokhov Date: Thu Jan 12 01:00:53 2017 +0000 Add a doc on build flavours See #239, #268. >--------------------------------------------------------------- ff9e5b6362b5112a06f7018a5462639c9ef4d83c doc/flavours.md | 162 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 162 insertions(+) diff --git a/doc/flavours.md b/doc/flavours.md new file mode 100644 index 0000000..dc672a9 --- /dev/null +++ b/doc/flavours.md @@ -0,0 +1,162 @@ +# Build flavours + +Hadrian supports a few predefined _build flavours_, i.e. collections of build +settings that fully define a GHC build (see `src/Flavour.hs`). Users can add their +own build flavours if need be, as described +[here](https://github.com/snowleopard/hadrian/blob/master/doc/user-settings.md#build-flavour). + +## Arguments + +The following table summarises extra arguments passed to GHC in different build flavours. +There are four groups of arguments: arguments in `hsDefault` are passed to GHC for all Haskell +source files, `hsLibrary` arguments are added when compiling libraries, `hsCompiler` +when compiling the `compiler` library, and `hsGhc` when compiling/linking the GHC program. + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
FlavourExtra arguments
hsDefault + hsLibrary + hsCompiler + hsGhc +
stage0 + stage1+ + stage0 + stage1+ + stage0 + stage1+ + stage0 + stage1+ +
default
+
-O
-H32
-O2
-H32m
quick + -O0
-H64
-O0
-H64
-O-O-O
quickest + -O0
-H64
-O0
-H64
perf + -O
-H64
-O
-H64
-O2-O-O2-O-O2
prof + -O0
-H64
-O0
-H64
-O-O-O-O-O
devel1 + -O
-H64
-O
-H64
-dcore-lint-O0
-DDEBUG
-O0
-DDEBUG
devel2 + -O
-H64
-O
-H64
-dcore-lint-O0
-DDEBUG
-O0
-DDEBUG
+ +## Ways + +Libraries and GHC can be built in different _ways_, e.g. with or without profiling +information. The following table lists ways that are built in different flavours. + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
FlavourLibrary waysRTS waysProfiled GHC
stage0 + stage1+ + stage0 + stage1+ + stage0 + stage1+ +
default
perf
prof
devel1
devel2 +
vanillavanilla
profiling
logging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
threadedProfiling
Only in
prof
flavour
Only in
prof
flavour
quick + vanillavanillalogging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
NoNo
quickest + vanillavanillavanilla
threaded (when --haddock)
vanilla
threaded (when --haddock)
NoNo
From git at git.haskell.org Fri Oct 27 00:48:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename --configure to --setup. (2fe68f0) Message-ID: <20171027004818.218BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2fe68f0a0c1e737ed2ba1f8d4a606a6953497f74/ghc >--------------------------------------------------------------- commit 2fe68f0a0c1e737ed2ba1f8d4a606a6953497f74 Author: Andrey Mokhov Date: Tue Feb 9 00:07:10 2016 +0000 Rename --configure to --setup. Fix #204. [skip ci] >--------------------------------------------------------------- 2fe68f0a0c1e737ed2ba1f8d4a606a6953497f74 README.md | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 35f8ac3..96b3106 100644 --- a/README.md +++ b/README.md @@ -52,19 +52,19 @@ are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue In addition to standard Shake flags (try `--help`), the build system currently supports several others: -* `--configure[=ARGS]`: run the `configure` script forwarding `ARGS` as command line -arguments; also run the `boot` script to create the `configure` script if necessary. -You do not have to use this functionality of the new build system; feel free to run -`boot` and `configure` scripts manually, as you do when using `make`. Note: on Windows -we automatically add flag `--enable-tarballs-autodownload` to `ARGS`, so you -don't have to do it manually. Beware, this uses network I/O which may sometimes be -undesirable. * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). * `--haddock`: build Haddock documentation. * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). +* `--setup[=CONFIGURE_ARGS]`: setup the build system by running the `configure` script +with `CONFIGURE_ARGS` arguments; also run the `boot` script to create the `configure` +script if necessary. On Windows, download the required tarballs by executing +`mk/get-win32-tarballs.sh` with appropriate parameters. You do not have to +use this functionality of the new build system; feel free to run `boot` and `configure` +scripts manually, as you do when using `make`. Beware: `--setup` uses network I/O +which may sometimes be undesirable. * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. From git at git.haskell.org Fri Oct 27 00:48:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to build flavours doc (e03bcf6) Message-ID: <20171027004818.360BF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e03bcf6b16e3ded4948bd370daab3a05098e32d5/ghc >--------------------------------------------------------------- commit e03bcf6b16e3ded4948bd370daab3a05098e32d5 Author: Andrey Mokhov Date: Thu Jan 12 01:03:13 2017 +0000 Link to build flavours doc [skip ci] >--------------------------------------------------------------- e03bcf6b16e3ded4948bd370daab3a05098e32d5 doc/user-settings.md | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 9d776ea..9207f7f 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -34,7 +34,9 @@ data Flavour = Flavour , ghcProfiled :: Bool -- ^ Build profiled GHC. , ghcDebugged :: Bool } -- ^ Build GHC with debug information. ``` -Hadrian provides several built-in flavours (`defaultFlavour`, `quickFlavour`, and +Hadrian provides several +[built-in flavours](https://github.com/snowleopard/hadrian/blob/master/doc/flavours.md) +(`defaultFlavour`, `quickFlavour`, and a few others), which can be activated from the command line, e.g. `--flavour=quick`. Users can define new build flavours by adding them to `userFlavours` list: ```haskell From git at git.haskell.org Fri Oct 27 00:48:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement path lookup on Windows. (f5299c8) Message-ID: <20171027004821.B7A4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f5299c86b5e89909488e1a5997a8c98c595f5d25/ghc >--------------------------------------------------------------- commit f5299c86b5e89909488e1a5997a8c98c595f5d25 Author: Andrey Mokhov Date: Tue Feb 9 15:05:09 2016 +0000 Implement path lookup on Windows. >--------------------------------------------------------------- f5299c86b5e89909488e1a5997a8c98c595f5d25 shaking-up-ghc.cabal | 2 +- src/Oracles.hs | 4 ++-- src/Oracles/WindowsPath.hs | 41 +++++++++++++++++++++++++++++++++++++ src/Oracles/WindowsRoot.hs | 51 ---------------------------------------------- src/Rules/Oracles.hs | 2 +- src/Test.hs | 2 +- 6 files changed, 46 insertions(+), 56 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 254617d..035bb9d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -34,7 +34,7 @@ executable ghc-shake , Oracles.PackageData , Oracles.PackageDb , Oracles.PackageDeps - , Oracles.WindowsRoot + , Oracles.WindowsPath , Package , Predicates , Rules diff --git a/src/Oracles.hs b/src/Oracles.hs index 564c7bb..eb37b47 100644 --- a/src/Oracles.hs +++ b/src/Oracles.hs @@ -6,7 +6,7 @@ module Oracles ( module Oracles.LookupInPath, module Oracles.PackageData, module Oracles.PackageDeps, - module Oracles.WindowsRoot + module Oracles.WindowsPath ) where import Oracles.Config @@ -16,4 +16,4 @@ import Oracles.Dependencies import Oracles.LookupInPath import Oracles.PackageData import Oracles.PackageDeps -import Oracles.WindowsRoot +import Oracles.WindowsPath diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs new file mode 100644 index 0000000..189c329 --- /dev/null +++ b/src/Oracles/WindowsPath.hs @@ -0,0 +1,41 @@ +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +module Oracles.WindowsPath ( + fixAbsolutePathOnWindows, topDirectory, windowsPathOracle + ) where + +import Data.Char (isSpace) +import Base +import Oracles.Config.Setting + +newtype WindowsPath = WindowsPath FilePath + deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + +topDirectory :: Action FilePath +topDirectory = do + ghcSourcePath <- setting GhcSourcePath + fixAbsolutePathOnWindows ghcSourcePath + +-- Fix an absolute path on Windows: +-- * "/c/" => "C:/" +-- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" +fixAbsolutePathOnWindows :: FilePath -> Action FilePath +fixAbsolutePathOnWindows path = do + windows <- windowsHost + if windows + then do + let (dir, file) = splitFileName path + winDir <- askOracle $ WindowsPath dir + return $ winDir -/- file + else + return path + +-- Detecting path mapping on Windows. This is slow and requires caching. +windowsPathOracle :: Rules () +windowsPathOracle = do + answer <- newCache $ \path -> do + Stdout out <- quietly $ cmd ["cygpath", "-m", path] + let windowsPath = dropWhileEnd isSpace out + putOracle $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath + return windowsPath + _ <- addOracle $ \(WindowsPath query) -> answer query + return () diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs deleted file mode 100644 index 413f289..0000000 --- a/src/Oracles/WindowsRoot.hs +++ /dev/null @@ -1,51 +0,0 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} -module Oracles.WindowsRoot ( - windowsRoot, fixAbsolutePathOnWindows, topDirectory, windowsRootOracle - ) where - -import Data.Char (isSpace) -import Base -import Oracles.Config.Setting - -newtype WindowsRoot = WindowsRoot () - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) - --- Looks up cygwin/msys root on Windows -windowsRoot :: Action String -windowsRoot = askOracle $ WindowsRoot () - -topDirectory :: Action FilePath -topDirectory = do - ghcSourcePath <- setting GhcSourcePath - fixAbsolutePathOnWindows ghcSourcePath - --- TODO: this is fragile, e.g. we currently only handle C: drive --- On Windows: --- * if the path starts with "/c/" change the prefix to "C:/" --- * otherwise, if the path starts with "/", prepend it with the correct path --- to the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe" -fixAbsolutePathOnWindows :: FilePath -> Action FilePath -fixAbsolutePathOnWindows path = do - windows <- windowsHost - -- Note, below is different from FilePath.isAbsolute: - if (windows && "/" `isPrefixOf` path) - then do - if ("/c/" `isPrefixOf` path) - then return $ "C:" ++ drop 2 path - else do - root <- windowsRoot - return . unifyPath $ root ++ drop 1 path - else - return path - --- Oracle for windowsRoot. This operation requires caching as looking up --- the root is slow (at least the current implementation). -windowsRootOracle :: Rules () -windowsRootOracle = do - root <- newCache $ \_ -> do - Stdout out <- quietly $ cmd ["cygpath", "-m", "/"] - let root = dropWhileEnd isSpace out - putOracle $ "Detected root on Windows: " ++ root - return root - _ <- addOracle $ \WindowsRoot{} -> root () - return () diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 55f7aee..1bc1606 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -17,4 +17,4 @@ oracleRules = do packageDataOracle -- see Oracles.PackageData packageDbOracle -- see Oracles.PackageData packageDepsOracle -- see Oracles.PackageDeps - windowsRootOracle -- see Oracles.WindowsRoot + windowsPathOracle -- see Oracles.WindowsRoot diff --git a/src/Test.hs b/src/Test.hs index a79c9fc..f8e93e7 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -6,7 +6,7 @@ import Expression import GHC (rts, libffi) import Oracles.Config.Flag import Oracles.Config.Setting -import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory +import Oracles.WindowsPath import Rules.Actions import Settings.Packages import Settings.User From git at git.haskell.org Fri Oct 27 00:48:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update notes on build ways and flavours (3d4e548) Message-ID: <20171027004821.C22E83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d4e54873fceedee20c3e0c0fbb56598030252a9/ghc >--------------------------------------------------------------- commit 3d4e54873fceedee20c3e0c0fbb56598030252a9 Author: Andrey Mokhov Date: Thu Jan 12 01:15:19 2017 +0000 Update notes on build ways and flavours [skip ci] >--------------------------------------------------------------- 3d4e54873fceedee20c3e0c0fbb56598030252a9 README.md | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 0d7b3d8..109f7f0 100644 --- a/README.md +++ b/README.md @@ -6,7 +6,7 @@ Hadrian Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current [`make`-based build system][make]. If you are curious about the rationale behind the -project and the architecture of the new build system you can find more details in +project and the architecture of the build system you can find more details in this [Haskell Symposium 2016 paper][paper] and this [Haskell eXchange 2016 talk][talk]. The new build system can work side-by-side with the existing build system. Note, there is @@ -52,9 +52,11 @@ are placed into `_build` and `inplace` directories. In addition to standard Shake flags (try `--help`), the build system currently supports several others: -* `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: -`default` and `quick` (adds `-O0` flag to all GHC invocations and disables library -profiling, which speeds up builds by 3-4x). +* `--flavour=FLAVOUR`: choose a build flavour. The following settings are currently supported: +`default`, `quick`, `quickest`, `perf`, `prof`, `devel1` and `devel2`. As an example, the +`quickest` flavour adds `-O0` flag to all GHC invocations and builds libraries only in the +`vanilla` way, which speeds up builds by 3-4x. Build flavours are documented +[here](https://github.com/snowleopard/hadrian/blob/master/doc/flavours.md). * `--haddock`: build Haddock documentation. @@ -117,10 +119,10 @@ zero (see [#197][test-issue]). Current limitations ------------------- The new build system still lacks many important features: -* We only build `vanilla` and `profiling` way: [#4][dynamic-issue]. +* There is currently no support for the `dynamic` build way: [#4][dynamic-issue]. * Validation is not implemented: [#187][validation-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). -* Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. +* Not all modes of the old build system are supported, e.g. [#250][freeze-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. * There is no support for installation or binary distribution: [#219][install-issue]. @@ -159,7 +161,7 @@ helped me endure and enjoy the project. [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 -[flavours-issue]: https://github.com/snowleopard/hadrian/issues/188 +[freeze-issue]: https://github.com/snowleopard/hadrian/issues/250 [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 [milestones]: https://github.com/snowleopard/hadrian/milestones From git at git.haskell.org Fri Oct 27 00:48:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't modify ways in development flavours (084ce3b) Message-ID: <20171027004825.386073A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/084ce3b4f5fdfbfa83786d96805698a9170b9b0f/ghc >--------------------------------------------------------------- commit 084ce3b4f5fdfbfa83786d96805698a9170b9b0f Author: Andrey Mokhov Date: Thu Jan 12 01:24:26 2017 +0000 Don't modify ways in development flavours >--------------------------------------------------------------- 084ce3b4f5fdfbfa83786d96805698a9170b9b0f src/Settings/Flavours/Development.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index 4314a64..a90c157 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -9,8 +9,7 @@ import Settings.Optimisation developmentFlavour :: Stage -> Flavour developmentFlavour ghcStage = defaultFlavour { name = "devel" ++ show (fromEnum ghcStage) - , args = defaultBuilderArgs <> developmentArgs ghcStage <> defaultPackageArgs - , libraryWays = append [vanilla] } + , args = defaultBuilderArgs <> developmentArgs ghcStage <> defaultPackageArgs } developmentArgs :: Stage -> Args developmentArgs ghcStage = do From git at git.haskell.org Fri Oct 27 00:48:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix executable lookup. (68cf604) Message-ID: <20171027004825.2D80C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68cf6048ac5a08b158282d9284868002ecc28a8e/ghc >--------------------------------------------------------------- commit 68cf6048ac5a08b158282d9284868002ecc28a8e Author: Andrey Mokhov Date: Tue Feb 9 15:59:04 2016 +0000 Fix executable lookup. >--------------------------------------------------------------- 68cf6048ac5a08b158282d9284868002ecc28a8e src/Builder.hs | 10 +++++----- src/Oracles/LookupInPath.hs | 24 ++++++++++-------------- 2 files changed, 15 insertions(+), 19 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index d1a2cc3..1826875 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -112,11 +112,11 @@ builderPath builder = case builderProvenance builder of path <- askConfigWithDefault builderKey . putError $ "\nCannot find path to '" ++ builderKey ++ "' in configuration files. Have you forgot to run configure?" - windows <- windowsHost - case (path, windows) of - ("", _ ) -> return path - (p , True ) -> fixAbsolutePathOnWindows (p -<.> exe) - (p , False) -> lookupInPath p + if path == "" -- TODO: get rid of "" paths + then return "" + else do + path' <- lookupInPath path + fixAbsolutePathOnWindows $ path' -<.> exe getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index a9dc995..6bf2bba 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -1,29 +1,25 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where +import System.Directory + import Base newtype LookupInPath = LookupInPath String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) --- | Fetches the absolute FilePath to a given FilePath using the oracle. -commandPath :: FilePath -> Action FilePath -commandPath = askOracle . LookupInPath - --- | Lookup a @command@ in @PATH@ environment. +-- | Lookup an executable in @PATH at . lookupInPath :: FilePath -> Action FilePath -lookupInPath c - | c /= takeFileName c = return c - | otherwise = commandPath c +lookupInPath name + | name == takeFileName name = askOracle $ LookupInPath name + | otherwise = return name lookupInPathOracle :: Rules () lookupInPathOracle = do answer <- newCache $ \query -> do - envPaths <- wordsBy (== ':') <$> getEnvWithDefault "" "PATH" - let candidates = map (-/- query) envPaths - -- this will crash if we do not find any valid candidate. - fullCommand <- head <$> filterM doesFileExist candidates - putOracle $ "Found '" ++ query ++ "' at " ++ "'" ++ fullCommand ++ "'" - return fullCommand + maybePath <- liftIO $ findExecutable query + let path = fromMaybe query maybePath + putOracle $ "Lookup executable '" ++ query ++ "': " ++ path + return path _ <- addOracle $ \(LookupInPath query) -> answer query return () From git at git.haskell.org Fri Oct 27 00:48:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use qualified imports. (bd405c1) Message-ID: <20171027004828.96B113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bd405c1006be30c99cb718a30dd779c1462baf61/ghc >--------------------------------------------------------------- commit bd405c1006be30c99cb718a30dd779c1462baf61 Author: Andrey Mokhov Date: Wed Feb 10 01:03:56 2016 +0000 Use qualified imports. >--------------------------------------------------------------- bd405c1006be30c99cb718a30dd779c1462baf61 src/Rules/Oracles.hs | 32 ++++++++++++++++++-------------- 1 file changed, 18 insertions(+), 14 deletions(-) diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 1bc1606..108c5ce 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -1,20 +1,24 @@ module Rules.Oracles (oracleRules) where import Base -import Oracles -import Oracles.ArgsHash -import Oracles.PackageDb -import Oracles.ModuleFiles +import qualified Oracles.Config +import qualified Oracles.Dependencies +import qualified Oracles.LookupInPath +import qualified Oracles.PackageData +import qualified Oracles.PackageDeps +import qualified Oracles.WindowsPath +import qualified Oracles.ArgsHash +import qualified Oracles.ModuleFiles +import qualified Oracles.PackageDb --- TODO: replace comments with qualified imports oracleRules :: Rules () oracleRules = do - argsHashOracle -- see Oracles.ArgsHash - configOracle -- see Oracles.Config - dependenciesOracle -- see Oracles.Dependencies - lookupInPathOracle -- see Oracles.LookupInPath - moduleFilesOracle -- see Oracles.ModuleFiles - packageDataOracle -- see Oracles.PackageData - packageDbOracle -- see Oracles.PackageData - packageDepsOracle -- see Oracles.PackageDeps - windowsPathOracle -- see Oracles.WindowsRoot + Oracles.ArgsHash.argsHashOracle + Oracles.Config.configOracle + Oracles.Dependencies.dependenciesOracle + Oracles.LookupInPath.lookupInPathOracle + Oracles.ModuleFiles.moduleFilesOracle + Oracles.PackageData.packageDataOracle + Oracles.PackageDb.packageDbOracle + Oracles.PackageDeps.packageDepsOracle + Oracles.WindowsPath.windowsPathOracle From git at git.haskell.org Fri Oct 27 00:48:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Settings.Optimisation to Settings.SourceArgs (71b2b96) Message-ID: <20171027004828.A8CEF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/71b2b96820f4ac6100840c3782d7d9fbabc6dac7/ghc >--------------------------------------------------------------- commit 71b2b96820f4ac6100840c3782d7d9fbabc6dac7 Author: Andrey Mokhov Date: Thu Jan 12 12:21:54 2017 +0000 Rename Settings.Optimisation to Settings.SourceArgs >--------------------------------------------------------------- 71b2b96820f4ac6100840c3782d7d9fbabc6dac7 hadrian.cabal | 2 +- src/Settings/Default.hs | 8 ++++---- src/Settings/Flavours/Development.hs | 4 ++-- src/Settings/Flavours/Performance.hs | 4 ++-- src/Settings/Flavours/Profiled.hs | 4 ++-- src/Settings/Flavours/Quick.hs | 4 ++-- src/Settings/Flavours/Quickest.hs | 4 ++-- src/Settings/{Optimisation.hs => SourceArgs.hs} | 10 +++++----- 8 files changed, 20 insertions(+), 20 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index d3ef74c..c8cb0b7 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -90,7 +90,7 @@ executable hadrian , Settings.Flavours.Profiled , Settings.Flavours.Quick , Settings.Flavours.Quickest - , Settings.Optimisation + , Settings.SourceArgs , Settings.Packages.Base , Settings.Packages.Compiler , Settings.Packages.Ghc diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 2a9fae4..3aa3a65 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -27,7 +27,7 @@ import Settings.Builders.HsCpp import Settings.Builders.Ld import Settings.Builders.Make import Settings.Builders.Tar -import Settings.Optimisation +import Settings.SourceArgs import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Ghc @@ -43,12 +43,12 @@ import Settings.Packages.RunGhc defaultArgs :: Args defaultArgs = mconcat [ defaultBuilderArgs - , optimisationArgs defaultOptimisation + , sourceArgs defaultSourceArgs , defaultPackageArgs ] -- | Default optimisation settings. -defaultOptimisation :: Optimisation -defaultOptimisation = Optimisation +defaultSourceArgs :: SourceArgs +defaultSourceArgs = SourceArgs { hsDefault = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2", arg "-H32m"] , hsLibrary = mempty , hsCompiler = mempty diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index a90c157..f3f9499 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Development (developmentFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs -- TODO: Implement an equivalent of LAX_DEPENDENCIES = YES setting, see #250. developmentFlavour :: Stage -> Flavour @@ -14,7 +14,7 @@ developmentFlavour ghcStage = defaultFlavour developmentArgs :: Stage -> Args developmentArgs ghcStage = do stage <- getStage - optimisationArgs $ Optimisation + sourceArgs $ SourceArgs { hsDefault = append ["-O", "-H64m"] , hsLibrary = notStage0 ? arg "-dcore-lint" , hsCompiler = succ stage == ghcStage ? append ["-O0", "-DDEBUG"] diff --git a/src/Settings/Flavours/Performance.hs b/src/Settings/Flavours/Performance.hs index 69e244a..ae3197e 100644 --- a/src/Settings/Flavours/Performance.hs +++ b/src/Settings/Flavours/Performance.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Performance (performanceFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs performanceFlavour :: Flavour performanceFlavour = defaultFlavour @@ -11,7 +11,7 @@ performanceFlavour = defaultFlavour , args = defaultBuilderArgs <> performanceArgs <> defaultPackageArgs } performanceArgs :: Args -performanceArgs = optimisationArgs $ Optimisation +performanceArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O", "-H64m"] , hsLibrary = notStage0 ? arg "-O2" , hsCompiler = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2"] diff --git a/src/Settings/Flavours/Profiled.hs b/src/Settings/Flavours/Profiled.hs index 0a1a6ed..b3f9117 100644 --- a/src/Settings/Flavours/Profiled.hs +++ b/src/Settings/Flavours/Profiled.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Profiled (profiledFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs profiledFlavour :: Flavour profiledFlavour = defaultFlavour @@ -12,7 +12,7 @@ profiledFlavour = defaultFlavour , ghcProfiled = True } profiledArgs :: Args -profiledArgs = optimisationArgs $ Optimisation +profiledArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O0", "-H64m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = arg "-O" diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index dd9cd58..565e748 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Quick (quickFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs quickFlavour :: Flavour quickFlavour = defaultFlavour @@ -13,7 +13,7 @@ quickFlavour = defaultFlavour -- TODO: the hsLibrary setting seems wrong, but it matches mk/flavours/quick.mk quickArgs :: Args -quickArgs = optimisationArgs $ Optimisation +quickArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O0", "-H64m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = stage0 ? arg "-O" diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 0473dc6..abb2ccf 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Quickest (quickestFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs quickestFlavour :: Flavour quickestFlavour = defaultFlavour @@ -13,7 +13,7 @@ quickestFlavour = defaultFlavour , rtsWays = quickestRtsWays } quickestArgs :: Args -quickestArgs = optimisationArgs $ Optimisation +quickestArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O0", "-H64m"] , hsLibrary = mempty , hsCompiler = mempty diff --git a/src/Settings/Optimisation.hs b/src/Settings/SourceArgs.hs similarity index 66% rename from src/Settings/Optimisation.hs rename to src/Settings/SourceArgs.hs index 6d47941..0c638ca 100644 --- a/src/Settings/Optimisation.hs +++ b/src/Settings/SourceArgs.hs @@ -1,17 +1,17 @@ -module Settings.Optimisation (Optimisation (..), optimisationArgs) where +module Settings.SourceArgs (SourceArgs (..), sourceArgs) where import GHC import Predicate --- TODO: Move C optimisation settings here -data Optimisation = Optimisation +-- TODO: Move C source arguments here +data SourceArgs = SourceArgs { hsDefault :: Args , hsLibrary :: Args , hsCompiler :: Args , hsGhc :: Args } -optimisationArgs :: Optimisation -> Args -optimisationArgs Optimisation {..} = do +sourceArgs :: SourceArgs -> Args +sourceArgs SourceArgs {..} = do hsCompile <- builder $ Ghc CompileHs hsLink <- builder $ Ghc LinkHs pkg <- getPackage From git at git.haskell.org Fri Oct 27 00:48:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reorder source arguments (a63d835) Message-ID: <20171027004832.323E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a63d83530f324bab9b3f0860d53f7198072ffd81/ghc >--------------------------------------------------------------- commit a63d83530f324bab9b3f0860d53f7198072ffd81 Author: Andrey Mokhov Date: Thu Jan 12 20:20:41 2017 +0000 Reorder source arguments >--------------------------------------------------------------- a63d83530f324bab9b3f0860d53f7198072ffd81 hadrian.cabal | 1 - src/Settings/Builders/Ghc.hs | 8 +++++--- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Default.hs | 27 +++++++++++++++++++++++---- src/Settings/Default.hs-boot | 13 +++++++++++-- src/Settings/Flavours/Development.hs | 1 - src/Settings/Flavours/Performance.hs | 1 - src/Settings/Flavours/Profiled.hs | 1 - src/Settings/Flavours/Quick.hs | 2 -- src/Settings/Flavours/Quickest.hs | 1 - src/Settings/SourceArgs.hs | 21 --------------------- 11 files changed, 40 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 a63d83530f324bab9b3f0860d53f7198072ffd81 From git at git.haskell.org Fri Oct 27 00:48:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop top-level Oracles.hs (3178d82) Message-ID: <20171027004832.428FB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3178d829038e5216c474f5ce6f8f7bd7b09b02f9/ghc >--------------------------------------------------------------- commit 3178d829038e5216c474f5ce6f8f7bd7b09b02f9 Author: Andrey Mokhov Date: Wed Feb 10 01:20:56 2016 +0000 Drop top-level Oracles.hs >--------------------------------------------------------------- 3178d829038e5216c474f5ce6f8f7bd7b09b02f9 shaking-up-ghc.cabal | 1 - src/Builder.hs | 4 +++- src/Oracles.hs | 19 ------------------- src/Rules/Actions.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 3 ++- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generators/ConfigHs.hs | 3 ++- src/Rules/Generators/GhcAutoconfH.hs | 3 ++- src/Rules/Generators/GhcBootPlatformH.hs | 2 +- src/Rules/Generators/GhcPlatformH.hs | 3 ++- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Generators/GhcVersionH.hs | 2 +- src/Rules/Generators/VersionHs.hs | 2 +- src/Rules/Libffi.hs | 4 +++- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 3 ++- src/Settings.hs | 3 ++- src/Settings/Builders/Ar.hs | 3 ++- src/Settings/Builders/Gcc.hs | 2 +- src/Settings/Builders/Ghc.hs | 3 ++- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 4 +++- src/Settings/Builders/Ld.hs | 2 +- src/Way.hs | 2 +- 27 files changed, 39 insertions(+), 45 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 3178d829038e5216c474f5ce6f8f7bd7b09b02f9 From git at git.haskell.org Fri Oct 27 00:48:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --integer-simple command line argument (b42cac6) Message-ID: <20171027004835.998853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b42cac65d1a65a101179613dba66d3b711948b84/ghc >--------------------------------------------------------------- commit b42cac65d1a65a101179613dba66d3b711948b84 Author: Andrey Mokhov Date: Thu Jan 12 23:31:50 2017 +0000 Add --integer-simple command line argument See #179 >--------------------------------------------------------------- b42cac65d1a65a101179613dba66d3b711948b84 src/CmdLineFlag.hs | 16 +++++++++++++--- src/Settings/Default.hs | 2 +- 2 files changed, 14 insertions(+), 4 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index ebe907a..961a033 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,7 +1,7 @@ module CmdLineFlag ( - putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, cmdProgressColour, - ProgressColour (..), cmdProgressInfo, ProgressInfo (..), cmdSkipConfigure, - cmdSplitObjects + putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, + cmdProgressColour, ProgressColour (..), cmdProgressInfo, ProgressInfo (..), + cmdSkipConfigure, cmdSplitObjects ) where import Data.IORef @@ -15,6 +15,7 @@ import System.IO.Unsafe data Untracked = Untracked { buildHaddock :: Bool , flavour :: Maybe String + , integerSimple :: Bool , progressColour :: ProgressColour , progressInfo :: ProgressInfo , skipConfigure :: Bool @@ -29,6 +30,7 @@ defaultUntracked :: Untracked defaultUntracked = Untracked { buildHaddock = False , flavour = Nothing + , integerSimple = False , progressColour = Auto , progressInfo = Normal , skipConfigure = False @@ -40,6 +42,9 @@ readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } readFlavour :: Maybe String -> Either String (Untracked -> Untracked) readFlavour ms = Right $ \flags -> flags { flavour = lower <$> ms } +readIntegerSimple :: Either String (Untracked -> Untracked) +readIntegerSimple = Right $ \flags -> flags { integerSimple = True } + readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) readProgressColour ms = maybe (Left "Cannot parse progress-colour") (Right . set) (go =<< lower <$> ms) @@ -77,6 +82,8 @@ cmdFlags = "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." + , Option [] ["integer-simple"] (NoArg readIntegerSimple) + "Build GHC with integer-simple library." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") "Use colours in progress info (Never, Auto or Always)." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") @@ -105,6 +112,9 @@ cmdBuildHaddock = buildHaddock getCmdLineFlags cmdFlavour :: Maybe String cmdFlavour = flavour getCmdLineFlags +cmdIntegerSimple :: Bool +cmdIntegerSimple = integerSimple getCmdLineFlags + cmdProgressColour :: ProgressColour cmdProgressColour = progressColour getCmdLineFlags diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 18f0ae0..351d780 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -177,7 +177,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages - , integerLibrary = integerGmp + , integerLibrary = if cmdIntegerSimple then integerSimple else integerGmp , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects From git at git.haskell.org Fri Oct 27 00:48:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Report an error if an executable is not found, unify paths. (05e7242) Message-ID: <20171027004835.A66103A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/05e7242655e0b8d5657c487e2ed2f392dd520429/ghc >--------------------------------------------------------------- commit 05e7242655e0b8d5657c487e2ed2f392dd520429 Author: Andrey Mokhov Date: Wed Feb 10 11:27:03 2016 +0000 Report an error if an executable is not found, unify paths. >--------------------------------------------------------------- 05e7242655e0b8d5657c487e2ed2f392dd520429 src/Oracles/LookupInPath.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 6bf2bba..2f6e713 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -18,8 +18,10 @@ lookupInPathOracle :: Rules () lookupInPathOracle = do answer <- newCache $ \query -> do maybePath <- liftIO $ findExecutable query - let path = fromMaybe query maybePath - putOracle $ "Lookup executable '" ++ query ++ "': " ++ path + path <- case maybePath of + Just value -> return $ unifyPath value + Nothing -> putError $ "Cannot find executable '" ++ query ++ "'." + putOracle $ "Executable found: " ++ query ++ " => " ++ path return path _ <- addOracle $ \(LookupInPath query) -> answer query return () From git at git.haskell.org Fri Oct 27 00:48:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Speed up Travis OSX build by --integer-simple (77840e7) Message-ID: <20171027004839.5BAC03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/77840e7930d55597dc575ec29b2c35afd5516d1f/ghc >--------------------------------------------------------------- commit 77840e7930d55597dc575ec29b2c35afd5516d1f Author: Andrey Mokhov Date: Thu Jan 12 23:32:36 2017 +0000 Speed up Travis OSX build by --integer-simple >--------------------------------------------------------------- 77840e7930d55597dc575ec29b2c35afd5516d1f .travis.yml | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0209cab..35ae3b7 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,6 +3,7 @@ sudo: true matrix: include: - os: linux + env: MODE="--flavour=quickest" addons: apt: packages: @@ -15,9 +16,11 @@ matrix: - PATH="/opt/cabal/1.22/bin:$PATH" - os: osx + env: MODE="--flavour=quickest --integer-simple" before_install: - brew update - brew install ghc cabal-install + - install: # Add Cabal to PATH @@ -45,7 +48,7 @@ script: - ./build.sh selftest # Build GHC - - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 00:48:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify paths. (56d3256) Message-ID: <20171027004839.73EF53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56d32568e5f290d9c93f11568b63e206caa0b9e1/ghc >--------------------------------------------------------------- commit 56d32568e5f290d9c93f11568b63e206caa0b9e1 Author: Andrey Mokhov Date: Wed Feb 10 11:27:21 2016 +0000 Unify paths. >--------------------------------------------------------------- 56d32568e5f290d9c93f11568b63e206caa0b9e1 src/Oracles/WindowsPath.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index 189c329..3cbf1f1 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -34,7 +34,7 @@ windowsPathOracle :: Rules () windowsPathOracle = do answer <- newCache $ \path -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] - let windowsPath = dropWhileEnd isSpace out + let windowsPath = unifyPath $ dropWhileEnd isSpace out putOracle $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath _ <- addOracle $ \(WindowsPath query) -> answer query From git at git.haskell.org Fri Oct 27 00:48:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on --integer-simple command line flag (5ca4af3) Message-ID: <20171027004842.CB8953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ca4af3f65b77af080508655a12c6f48b7d5ce31/ghc >--------------------------------------------------------------- commit 5ca4af3f65b77af080508655a12c6f48b7d5ce31 Author: Andrey Mokhov Date: Fri Jan 13 00:49:58 2017 +0000 Add a note on --integer-simple command line flag See #179. [skip ci] >--------------------------------------------------------------- 5ca4af3f65b77af080508655a12c6f48b7d5ce31 README.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/README.md b/README.md index 109f7f0..038bde5 100644 --- a/README.md +++ b/README.md @@ -60,6 +60,9 @@ currently supports several others: * `--haddock`: build Haddock documentation. +* `--integer-simple`: build GHC using the `integer-simple` integer library (instead +of `integer-gmp`). + * `--progress-colour=MODE`: choose whether to use colours when printing build progress info. There are three settings: `never` (do not use colours), `auto` (attempt to detect whether the console supports colours; this is the default setting), and `always` (use From git at git.haskell.org Fri Oct 27 00:48:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop alwaysRerun from setup rules. (b3e25ee) Message-ID: <20171027004842.EC8163A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3e25ee579ad44a35b4cbf243b05728c4f63c5d1/ghc >--------------------------------------------------------------- commit b3e25ee579ad44a35b4cbf243b05728c4f63c5d1 Author: Andrey Mokhov Date: Wed Feb 10 12:42:54 2016 +0000 Drop alwaysRerun from setup rules. >--------------------------------------------------------------- b3e25ee579ad44a35b4cbf243b05728c4f63c5d1 src/Rules/Setup.hs | 27 ++++++++++++++++++--------- 1 file changed, 18 insertions(+), 9 deletions(-) diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index c99c8be..a17fb59 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -9,13 +9,10 @@ import Rules.Generators.GhcAutoconfH setupRules :: Rules () setupRules = do - -- We always rerun the configure script in this mode, because the flags - -- passed to it can affect the contents of system.config file. [configFile, "settings", configH] &%> \[cfg, settings, cfgH] -> do - alwaysRerun + need [ settings <.> "in", cfgH <.> "in", "configure" ] case cmdSetup of RunSetup configureArgs -> do - need [ settings <.> "in", cfgH <.> "in" ] -- We cannot use windowsHost here due to a cyclic dependency when (System.Info.os == "mingw32") $ do putBuild "| Checking for Windows tarballs..." @@ -24,11 +21,23 @@ setupRules = do , "download" , System.Info.arch ] runConfigure "." [] [configureArgs] - SkipSetup -> unlessM (doesFileExist cfg) $ - putError $ "Configuration file " ++ cfg ++ " is missing.\n" - ++ "Run the configure script either manually or via the " + SkipSetup -> do + cfgExists <- doesFileExist cfg + if cfgExists + then putError $ "Configuration file " ++ cfg ++ " is out-of-date." + ++ "\nRerun the configure script either manually or via the " + ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." + else putError $ "Configuration file " ++ cfg ++ " is missing." + ++ "\nRun the configure script either manually or via the " ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." ["configure", configH <.> "in"] &%> \_ -> do - putBuild "| Running boot..." - quietly $ cmd (EchoStdout False) "perl boot" + need ["configure.ac"] + case cmdSetup of + RunSetup _ -> do + putBuild "| Running boot..." + quietly $ cmd (EchoStdout False) "perl boot" + SkipSetup -> do + putError $ "The configure script is out-of-date." + ++ "\nRun the boot script either manually or via the " + ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." From git at git.haskell.org Fri Oct 27 00:48:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need the GMP library when building with integerSimple (f39305c) Message-ID: <20171027004846.A13C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f39305c46467b30b7697ad42c1a817be9ec90670/ghc >--------------------------------------------------------------- commit f39305c46467b30b7697ad42c1a817be9ec90670 Author: Andrey Mokhov Date: Fri Jan 13 02:12:31 2017 +0000 Don't need the GMP library when building with integerSimple >--------------------------------------------------------------- f39305c46467b30b7697ad42c1a817be9ec90670 src/Settings/Builders/Ghc.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index f30b8e6..006d9f8 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -21,7 +21,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do pkg <- getPackage libs <- getPkgDataList DepExtraLibs libDirs <- getPkgDataList DepLibDirs - gmpLibs <- if stage > Stage0 + gmpLibs <- if stage > Stage0 && integerLibrary flavour == integerGmp then do -- TODO: get this data more gracefully let strip = fromMaybe "" . stripPrefix "extra-libraries: " buildInfo <- lift $ readFileLines gmpBuildInfoPath From git at git.haskell.org Fri Oct 27 00:48:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop support for old configure.ac. (0b0996b) Message-ID: <20171027004846.C8ABF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b0996b12437a70eeeac0739b493ed505b2c8b89/ghc >--------------------------------------------------------------- commit 0b0996b12437a70eeeac0739b493ed505b2c8b89 Author: Andrey Mokhov Date: Wed Feb 10 12:45:40 2016 +0000 Drop support for old configure.ac. >--------------------------------------------------------------- 0b0996b12437a70eeeac0739b493ed505b2c8b89 src/Rules/Actions.hs | 16 +++------------- 1 file changed, 3 insertions(+), 13 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index d81b838..f8f4925 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -6,7 +6,6 @@ module Rules.Actions ( ) where import qualified System.Directory as IO -import System.Console.ANSI import Base import CmdLineFlag @@ -127,20 +126,11 @@ runMakeWithVerbosity :: Bool -> FilePath -> [String] -> Action () runMakeWithVerbosity verbose dir args = do need [dir -/- "Makefile"] path <- builderPath Make - - -- FIXME: temporary safety net for those who are not on GHC HEAD, see #167 - -- TODO: add need [path] once lookupInPath is enabled on Windows - fixPath <- if path == "@MakeCmd@" <.> exe - then do - putColoured Red $ "You are behind GHC HEAD, make autodetection is disabled." - return "make" - else return path - let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run " ++ fixPath ++ note ++ " in " ++ dir ++ "..." + putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." if verbose - then cmd Shell fixPath ["-C", dir] args - else quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args + then cmd Shell path ["-C", dir] args + else quietly $ cmd Shell (EchoStdout False) path ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do From git at git.haskell.org Fri Oct 27 00:48:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Filter out repeated ways when copying libffi (b94612d) Message-ID: <20171027004850.6383D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b94612d33b8febed57d26bc696c9454b883f4aed/ghc >--------------------------------------------------------------- commit b94612d33b8febed57d26bc696c9454b883f4aed Author: Andrey Mokhov Date: Fri Jan 13 11:43:58 2017 +0000 Filter out repeated ways when copying libffi >--------------------------------------------------------------- b94612d33b8febed57d26bc696c9454b883f4aed src/Rules/Libffi.hs | 3 ++- src/Way.hs | 5 ++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0f703d9..99b77c8 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -56,7 +56,8 @@ libffiRules = do copyFile header (rtsBuildPath -/- takeFileName header) ways <- interpretInContext libffiContext (getLibraryWays <> getRtsWays) - forM_ ways $ \way -> copyFile libffiLibrary =<< rtsLibffiLibrary way + forM_ (nubOrd ways) $ \way -> + copyFile libffiLibrary =<< rtsLibffiLibrary way putSuccess $ "| Successfully built custom library 'libffi'" diff --git a/src/Way.hs b/src/Way.hs index 22ae6fa8..cb73f04 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -24,7 +24,7 @@ data WayUnit = Threaded | Profiling | Logging | Dynamic - deriving (Eq, Enum, Bounded) + deriving (Bounded, Enum, Eq, Ord) -- TODO: get rid of non-derived Show instances instance Show WayUnit where @@ -74,6 +74,9 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b +instance Ord Way where + compare (Way a) (Way b) = compare a b + -- | Build default _vanilla_ way. vanilla :: Way vanilla = wayFromUnits [] From git at git.haskell.org Fri Oct 27 00:48:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't fail if configuration file is out-of-date. (d17c1f5) Message-ID: <20171027004850.9E1143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d17c1f538b14b86405bb0be4f3fc4100a2ec8bec/ghc >--------------------------------------------------------------- commit d17c1f538b14b86405bb0be4f3fc4100a2ec8bec Author: Andrey Mokhov Date: Wed Feb 10 13:39:50 2016 +0000 Don't fail if configuration file is out-of-date. >--------------------------------------------------------------- d17c1f538b14b86405bb0be4f3fc4100a2ec8bec src/Rules/Setup.hs | 13 ++++--------- 1 file changed, 4 insertions(+), 9 deletions(-) diff --git a/src/Rules/Setup.hs b/src/Rules/Setup.hs index a17fb59..e0cd729 100644 --- a/src/Rules/Setup.hs +++ b/src/Rules/Setup.hs @@ -21,13 +21,8 @@ setupRules = do , "download" , System.Info.arch ] runConfigure "." [] [configureArgs] - SkipSetup -> do - cfgExists <- doesFileExist cfg - if cfgExists - then putError $ "Configuration file " ++ cfg ++ " is out-of-date." - ++ "\nRerun the configure script either manually or via the " - ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." - else putError $ "Configuration file " ++ cfg ++ " is missing." + SkipSetup -> unlessM (doesFileExist cfg) $ + putError $ "Configuration file " ++ cfg ++ " is missing." ++ "\nRun the configure script either manually or via the " ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." @@ -37,7 +32,7 @@ setupRules = do RunSetup _ -> do putBuild "| Running boot..." quietly $ cmd (EchoStdout False) "perl boot" - SkipSetup -> do - putError $ "The configure script is out-of-date." + SkipSetup -> unlessM (doesFileExist "configure") $ + putError $ "The configure script is missing." ++ "\nRun the boot script either manually or via the " ++ "build system by passing --setup[=CONFIGURE_ARGS] flag." From git at git.haskell.org Fri Oct 27 00:48:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use -H32m in all build flavours (a7b1494) Message-ID: <20171027004854.654653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7b149453928e5cf7c8051d4c6329ef9db3246f1/ghc >--------------------------------------------------------------- commit a7b149453928e5cf7c8051d4c6329ef9db3246f1 Author: Andrey Mokhov Date: Fri Jan 13 11:47:27 2017 +0000 Use -H32m in all build flavours See #268 >--------------------------------------------------------------- a7b149453928e5cf7c8051d4c6329ef9db3246f1 src/Settings/Flavours/Development.hs | 2 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/Quickest.hs | 2 +- 5 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index 7cfd7da..4e1ee2d 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -14,7 +14,7 @@ developmentArgs :: Stage -> Args developmentArgs ghcStage = do stage <- getStage sourceArgs $ SourceArgs - { hsDefault = append ["-O", "-H64m"] + { hsDefault = append ["-O", "-H32m"] , hsLibrary = notStage0 ? arg "-dcore-lint" , hsCompiler = succ stage == ghcStage ? append ["-O0", "-DDEBUG"] , hsGhc = succ stage == ghcStage ? append ["-O0", "-DDEBUG"] } diff --git a/src/Settings/Flavours/Performance.hs b/src/Settings/Flavours/Performance.hs index 0e07c71..a9cef4d 100644 --- a/src/Settings/Flavours/Performance.hs +++ b/src/Settings/Flavours/Performance.hs @@ -11,7 +11,7 @@ performanceFlavour = defaultFlavour performanceArgs :: Args performanceArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O", "-H64m"] + { hsDefault = append ["-O", "-H32m"] , hsLibrary = notStage0 ? arg "-O2" , hsCompiler = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2"] , hsGhc = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2"] } diff --git a/src/Settings/Flavours/Profiled.hs b/src/Settings/Flavours/Profiled.hs index 2f5dc74..861c66c 100644 --- a/src/Settings/Flavours/Profiled.hs +++ b/src/Settings/Flavours/Profiled.hs @@ -12,7 +12,7 @@ profiledFlavour = defaultFlavour profiledArgs :: Args profiledArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O0", "-H64m"] + { hsDefault = append ["-O0", "-H32m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = arg "-O" , hsGhc = arg "-O" } diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 6fe3353..5cbd1e4 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -12,7 +12,7 @@ quickFlavour = defaultFlavour quickArgs :: Args quickArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O0", "-H64m"] + { hsDefault = append ["-O0", "-H32m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = stage0 ? arg "-O" , hsGhc = stage0 ? arg "-O" } diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 0560b39..d5dff73 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -13,7 +13,7 @@ quickestFlavour = defaultFlavour quickestArgs :: Args quickestArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O0", "-H64m"] + { hsDefault = append ["-O0", "-H32m"] , hsLibrary = mempty , hsCompiler = mempty , hsGhc = mempty } From git at git.haskell.org Fri Oct 27 00:48:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting, drop old comments. (0123303) Message-ID: <20171027004854.B090C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/01233034d1790dd831b59e0233e48cebaa8a4579/ghc >--------------------------------------------------------------- commit 01233034d1790dd831b59e0233e48cebaa8a4579 Author: Andrey Mokhov Date: Wed Feb 10 16:55:50 2016 +0000 Fix formatting, drop old comments. >--------------------------------------------------------------- 01233034d1790dd831b59e0233e48cebaa8a4579 src/Rules/Libffi.hs | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 99922d0..f1837c4 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -72,15 +72,14 @@ libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - ffiHeaderDir <- setting FfiIncludeDir useSystemFfi <- flag UseSystemFfi if useSystemFfi then do - putBuild "| System supplied FFI library will be used" - forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = ffiHeaderDir -/- file - copyFile src (rtsBuildPath -/- file) - putSuccess $ "| Successfully copied system supplied FFI library header files" + ffiIncludeDir <- setting FfiIncludeDir + putBuild "| System supplied FFI library will be used" + forM_ ["ffi.h", "ffitarget.h"] $ \file -> + copyFile (ffiIncludeDir -/- file) (rtsBuildPath -/- file) + putSuccess $ "| Successfully copied system FFI library header files" else do removeDirectory libffiBuild createDirectory $ buildRootPath -/- stageString Stage0 @@ -94,15 +93,16 @@ libffiRules = do let libname = dropExtension . dropExtension . takeFileName $ head tarballs removeDirectory (buildRootPath -/- libname) + -- TODO: Simplify. actionFinally (do - build $ fullTarget libffiTarget Tar tarballs [buildRootPath] - moveDirectory (buildRootPath -/- libname) libffiBuild) $ - removeFiles buildRootPath [libname "*"] + build $ fullTarget libffiTarget Tar tarballs [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuild) $ + removeFiles buildRootPath [libname "*"] fixFile (libffiBuild -/- "Makefile.in") fixLibffiMakefile forM_ ["config.guess", "config.sub"] $ \file -> - copyFile file (libffiBuild -/- file) + copyFile file (libffiBuild -/- file) envs <- configureEnvironment args <- configureArguments @@ -111,17 +111,11 @@ libffiRules = do runMake libffiBuild ["MAKEFLAGS="] runMake libffiBuild ["MAKEFLAGS=", "install"] + let ffiHDir = libffiBuild -/- "inst/lib" -/- libname -/- "include" forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file - copyFile src (rtsBuildPath -/- file) + copyFile (ffiHDir -/- file) (rtsBuildPath -/- file) libffiName <- rtsLibffiLibraryName copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") putSuccess $ "| Successfully built custom library 'libffi'" - --- chmod +x libffi/ln --- # wc on OS X has spaces in its output, which libffi's Makefile --- # doesn't expect, so we tweak it to sed them out --- mv libffi/build/Makefile libffi/build/Makefile.orig --- sed "s#wc -w#wc -w | sed 's/ //g'#" < libffi/build/Makefile.orig > libffi/build/Makefile From git at git.haskell.org Fri Oct 27 00:48:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use -H32m in all build flavours (2ef6390) Message-ID: <20171027004857.F28EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ef6390e2893eec4d3b7aadd334fa37fd822946b/ghc >--------------------------------------------------------------- commit 2ef6390e2893eec4d3b7aadd334fa37fd822946b Author: Andrey Mokhov Date: Fri Jan 13 12:55:22 2017 +0000 Use -H32m in all build flavours See #268 >--------------------------------------------------------------- 2ef6390e2893eec4d3b7aadd334fa37fd822946b doc/flavours.md | 26 +++++++++++++------------- 1 file changed, 13 insertions(+), 13 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index dc672a9..9fe2239 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -35,7 +35,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH default
- -O
-H32
+ -O
-H32m
-O2
-H32m @@ -46,8 +46,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quick - -O0
-H64 - -O0
-H64 + -O0
-H32m + -O0
-H32m -O -O @@ -57,8 +57,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quickest - -O0
-H64 - -O0
-H64 + -O0
-H32m + -O0
-H32m @@ -68,8 +68,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH perf - -O
-H64 - -O
-H64 + -O
-H32m + -O
-H32m -O2 -O @@ -79,8 +79,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH prof - -O0
-H64 - -O0
-H64 + -O0
-H32m + -O0
-H32m -O -O @@ -90,8 +90,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel1 - -O
-H64 - -O
-H64 + -O
-H32m + -O
-H32m -dcore-lint -O0
-DDEBUG @@ -101,8 +101,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel2 - -O
-H64 - -O
-H64 + -O
-H32m + -O
-H32m -dcore-lint From git at git.haskell.org Fri Oct 27 00:49:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move checkApiAnnotations, compareSizes and ghcTags to Stage0 (ebee16a) Message-ID: <20171027004901.D39123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ebee16a9e7d37ea14a2e0cd180c0bf6e88c3873c/ghc >--------------------------------------------------------------- commit ebee16a9e7d37ea14a2e0cd180c0bf6e88c3873c Author: Andrey Mokhov Date: Thu Jan 19 02:46:21 2017 +0000 Move checkApiAnnotations, compareSizes and ghcTags to Stage0 See #246 >--------------------------------------------------------------- ebee16a9e7d37ea14a2e0cd180c0bf6e88c3873c src/Settings/Default.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 351d780..318b0a0 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -86,6 +86,8 @@ stage0Packages = do ios <- lift iosHost append $ [ binary , cabal + , checkApiAnnotations + , compareSizes , compiler , deriveConstants , dllSplit @@ -97,6 +99,7 @@ stage0Packages = do , ghcCabal , ghci , ghcPkg + , ghcTags , hsc2hs , hoopl , hp2ps @@ -118,7 +121,6 @@ stage1Packages = do , base , bytestring , compact - , compareSizes , containers , deepseq , directory @@ -142,11 +144,7 @@ stage1Packages = do [ xhtml | doc ] ] stage2Packages :: Packages -stage2Packages = do - doc <- buildHaddock flavour - append $ [ checkApiAnnotations - , ghcTags ] ++ - [ haddock | doc ] +stage2Packages = buildHaddock flavour ? append [ haddock ] -- | Default build ways for library packages: -- * We always build 'vanilla' way. From git at git.haskell.org Fri Oct 27 00:48:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:48:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make fixFile more robust. (27317cf) Message-ID: <20171027004858.3EF6F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27317cf1ebcc6e89bd0e42b449cc2059f74673e6/ghc >--------------------------------------------------------------- commit 27317cf1ebcc6e89bd0e42b449cc2059f74673e6 Author: Andrey Mokhov Date: Wed Feb 10 22:51:09 2016 +0000 Make fixFile more robust. See #206. >--------------------------------------------------------------- 27317cf1ebcc6e89bd0e42b449cc2059f74673e6 src/Rules/Actions.hs | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index f8f4925..e815bcf 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -5,7 +5,9 @@ module Rules.Actions ( runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable ) where -import qualified System.Directory as IO +import qualified System.Directory as IO +import qualified System.IO as IO +import qualified Control.Exception.Base as IO import Base import CmdLineFlag @@ -96,9 +98,12 @@ moveDirectory source target = do fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do putBuild $ "| Fix " ++ file - old <- liftIO $ readFile file - let new = f old - length new `seq` liftIO $ writeFile file new + contents <- liftIO $ IO.withFile file IO.ReadMode $ \h -> do + old <- IO.hGetContents h + let new = f old + IO.evaluate $ rnf new + return new + liftIO $ writeFile file contents runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do From git at git.haskell.org Fri Oct 27 00:49:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of gmpLibNameCache. (d4b6ee5) Message-ID: <20171027004902.28F8C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd/ghc >--------------------------------------------------------------- commit d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd Author: Andrey Mokhov Date: Wed Feb 10 23:40:49 2016 +0000 Get rid of gmpLibNameCache. Fix #206. >--------------------------------------------------------------- d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd src/Rules/Gmp.hs | 17 +++++------------ src/Settings/Builders/Ghc.hs | 10 +++++----- src/Settings/Paths.hs | 8 ++------ 3 files changed, 12 insertions(+), 23 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index ab25495..3e1acea 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -7,7 +7,6 @@ import Expression import GHC import Oracles.Config.Setting import Rules.Actions -import Settings.Builders.Ghc import Settings.Packages.IntegerGmp import Settings.User @@ -67,7 +66,7 @@ gmpRules :: Rules () gmpRules = do -- TODO: split into multiple rules - [gmpLibraryH, gmpLibNameCache] &%> \_ -> do + gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] liftIO $ removeFiles gmpBuildPath ["//*"] @@ -83,22 +82,16 @@ gmpRules = do createDirectory $ takeDirectory gmpLibraryH -- We don't use system GMP on Windows. TODO: fix? - -- TODO: we do not track "config.mk" and "integer-gmp.buildinfo", see #173 - windows <- windowsHost + -- TODO: we don't track "config.mk" & "integer-gmp.buildinfo", see #173 + windows <- windowsHost configMk <- liftIO . readFile $ gmpBase -/- "config.mk" - if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] + if not windows && any (`isInfixOf` configMk) + [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH - buildInfo <- liftIO . readFile $ pkgPath integerGmp -/- "integer-gmp.buildinfo" - let prefix = "extra-libraries: " - libs s = case stripPrefix prefix s of - Nothing -> [] - Just value -> words value - writeFileChanged gmpLibNameCache . unlines . concatMap libs $ lines buildInfo else do putBuild "| No GMP library/framework detected; in tree GMP will be built" - writeFileChanged gmpLibNameCache "" -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index b3bca31..c9f8ddc 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,5 +1,5 @@ module Settings.Builders.Ghc ( - ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs, gmpLibNameCache + ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs ) where import Base @@ -23,12 +23,12 @@ ghcBuilderArgs = stagedBuilder Ghc ? do stage <- getStage way <- getWay when (stage > Stage0) . lift $ needTouchy - let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output - buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output + let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] + buildHi = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf] buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs gmpLibs <- if stage > Stage0 && buildProg - then lift $ readFileLines gmpLibNameCache -- TODO: use oracles + then words <$> getSetting GmpLibDir else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs @@ -47,7 +47,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] needTouchy :: Action () -needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy ] +needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy] splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 20f4721..99a4962 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,7 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibNameCache, - packageDbDirectory, pkgConfFile + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, packageDbDirectory, + pkgConfFile ) where import Base @@ -51,10 +51,6 @@ pkgFile stage pkg prefix suffix = do gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" --- GMP library names extracted from integer-gmp.buildinfo -gmpLibNameCache :: FilePath -gmpLibNameCache = gmpBuildPath -/- "gmp-lib-names" - -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory packageDbDirectory :: Stage -> FilePath From git at git.haskell.org Fri Oct 27 00:49:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix breakage due to changes in Cabal API (e908a4a) Message-ID: <20171027004905.A8BEF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e908a4a28964908ee30346a04aae23a4d314e8b2/ghc >--------------------------------------------------------------- commit e908a4a28964908ee30346a04aae23a4d314e8b2 Author: Andrey Mokhov Date: Wed Jan 25 17:45:48 2017 +0000 Fix breakage due to changes in Cabal API >--------------------------------------------------------------- e908a4a28964908ee30346a04aae23a4d314e8b2 src/Rules/Cabal.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 6adaf44..0df267f 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -4,6 +4,7 @@ import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Text +import Distribution.Types.CondTree import Distribution.Types.Dependency import Distribution.Verbosity @@ -49,4 +50,4 @@ collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] collectDeps (Just (CondNode _ deps ifs)) = deps ++ concatMap f ifs where - f (_, t, mt) = collectDeps (Just t) ++ collectDeps mt + f (CondBranch _ t mt) = collectDeps (Just t) ++ collectDeps mt From git at git.haskell.org Fri Oct 27 00:49:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add TODO. (d07b5b2) Message-ID: <20171027004905.D5CE63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d07b5b20b922d45967d22a29db3f00f9fd0e4247/ghc >--------------------------------------------------------------- commit d07b5b20b922d45967d22a29db3f00f9fd0e4247 Author: Andrey Mokhov Date: Thu Feb 11 01:17:31 2016 +0000 Add TODO. >--------------------------------------------------------------- d07b5b20b922d45967d22a29db3f00f9fd0e4247 src/Settings/Builders/GhcCabal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 51d0e6b..4a46b84 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -66,6 +66,7 @@ libraryArgs = do else "--disable-shared" ] -- TODO: LD_OPTS? +-- TODO: WARNING: unrecognized options: --with-compiler, --with-gmp-libraries, --with-cc configureArgs :: Args configureArgs = do let conf key = appendSubD $ "--configure-option=" ++ key From git at git.haskell.org Fri Oct 27 00:49:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on integerGmp configure in gmpRules. (e9106e8) Message-ID: <20171027004909.60A673A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e9106e8ddca0a1bc5677a03c682bc26d345826bd/ghc >--------------------------------------------------------------- commit e9106e8ddca0a1bc5677a03c682bc26d345826bd Author: Andrey Mokhov Date: Thu Feb 11 01:18:48 2016 +0000 Depend on integerGmp configure in gmpRules. See #159. >--------------------------------------------------------------- e9106e8ddca0a1bc5677a03c682bc26d345826bd src/Rules/Gmp.hs | 28 ++++++++-------------------- 1 file changed, 8 insertions(+), 20 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 3e1acea..4c7a480 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,7 +1,5 @@ module Rules.Gmp (gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH) where -import qualified System.Directory as IO - import Base import Expression import GHC @@ -9,6 +7,7 @@ import Oracles.Config.Setting import Rules.Actions import Settings.Packages.IntegerGmp import Settings.User +import Settings.Paths gmpBase :: FilePath gmpBase = "libraries/integer-gmp/gmp" @@ -64,27 +63,15 @@ configureIntGmpArguments = do -- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do - -- TODO: split into multiple rules gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - liftIO $ removeFiles gmpBuildPath ["//*"] - - -- TODO: without the optimisation below we configure integerGmp package - -- twice -- think how this can be optimised (shall we solve #18 first?) - -- TODO: this is a hacky optimisation: we do not rerun configure of - -- integerGmp package if we detect the results of the previous run - envs <- configureEnvironment - unlessM (liftIO . IO.doesFileExist $ gmpBase -/- "config.mk") $ do - args <- configureIntGmpArguments - runConfigure (pkgPath integerGmp) envs args - createDirectory $ takeDirectory gmpLibraryH + -- We don't use system GMP on Windows. TODO: fix? - -- TODO: we don't track "config.mk" & "integer-gmp.buildinfo", see #173 windows <- windowsHost - configMk <- liftIO . readFile $ gmpBase -/- "config.mk" + configMk <- readFile' $ gmpBase -/- "config.mk" if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do @@ -111,8 +98,6 @@ gmpRules = do copyFile src patchPath applyPatch gmpBuildPath patch - -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? - let filename = dropExtension . dropExtension . takeFileName $ head tarballs suffix = "-nodoc-patched" unless (suffix `isSuffixOf` filename) $ @@ -121,8 +106,9 @@ gmpRules = do let libName = take (length filename - length suffix) filename libPath = gmpBuildPath -/- libName - args2 <- configureArguments - runConfigure libPath envs args2 + envs <- configureEnvironment + args <- configureArguments + runConfigure libPath envs args runMake libPath ["MAKEFLAGS="] @@ -139,3 +125,5 @@ gmpRules = do putSuccess "| Successfully built custom library 'gmp'" gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] + + gmpBase -/- "config.mk" %> \_ -> need [pkgDataFile Stage1 integerGmp] From git at git.haskell.org Fri Oct 27 00:49:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -Wno-sync-nand to ghcPrim's cbits/atomic.c (6e73b4d) Message-ID: <20171027004909.5DE8A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e73b4d370755518491bdd82f5542b04d2eedf66/ghc >--------------------------------------------------------------- commit 6e73b4d370755518491bdd82f5542b04d2eedf66 Author: Andrey Mokhov Date: Mon Feb 6 02:21:05 2017 +0100 Add -Wno-sync-nand to ghcPrim's cbits/atomic.c See GHC ticket #9678 >--------------------------------------------------------------- 6e73b4d370755518491bdd82f5542b04d2eedf66 cfg/system.config.in | 1 + src/Oracles/Config/Flag.hs | 2 ++ src/Settings/Packages/GhcPrim.hs | 9 +++++++-- 3 files changed, 10 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 9ea0f44..667a22d 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -30,6 +30,7 @@ ar-supports-at-file = @ArSupportsAtFile@ cc-clang-backend = @CC_CLANG_BACKEND@ cc-llvm-backend = @CC_LLVM_BACKEND@ gcc-is-clang = @GccIsClang@ +gcc-lt-44 = @GccLT44@ gcc-lt-46 = @GccLT46@ hs-cpp-args = @HaskellCPPArgs@ diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 6c5879d..8ac753f 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -12,6 +12,7 @@ import Oracles.Config.Setting data Flag = ArSupportsAtFile | CrossCompiling | GccIsClang + | GccLt44 | GccLt46 | GhcUnregisterised | LeadingUnderscore @@ -29,6 +30,7 @@ flag f = do ArSupportsAtFile -> "ar-supports-at-file" CrossCompiling -> "cross-compiling" GccIsClang -> "gcc-is-clang" + GccLt44 -> "gcc-lt-44" GccLt46 -> "gcc-lt-46" GhcUnregisterised -> "ghc-unregisterised" LeadingUnderscore -> "leading-underscore" diff --git a/src/Settings/Packages/GhcPrim.hs b/src/Settings/Packages/GhcPrim.hs index 225ff56..bed8345 100644 --- a/src/Settings/Packages/GhcPrim.hs +++ b/src/Settings/Packages/GhcPrim.hs @@ -1,8 +1,13 @@ module Settings.Packages.GhcPrim (ghcPrimPackageArgs) where import GHC +import Oracles.Config.Flag import Predicate ghcPrimPackageArgs :: Args -ghcPrimPackageArgs = package ghcPrim ? - builder GhcCabal ? arg "--flag=include-ghc-prim" +ghcPrimPackageArgs = package ghcPrim ? mconcat + [ builder GhcCabal ? arg "--flag=include-ghc-prim" + + , builder (Cc CompileC) ? + (not <$> flag GccLt44) ? + input "//cbits/atomic.c" ? arg "-Wno-sync-nand" ] From git at git.haskell.org Fri Oct 27 00:49:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop configureIntGmpArguments. (cc10288) Message-ID: <20171027004913.2C56C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cc102887b32e84005d553c4adbef1ca5f5c43a1a/ghc >--------------------------------------------------------------- commit cc102887b32e84005d553c4adbef1ca5f5c43a1a Author: Andrey Mokhov Date: Thu Feb 11 01:51:10 2016 +0000 Drop configureIntGmpArguments. See #159. >--------------------------------------------------------------- cc102887b32e84005d553c4adbef1ca5f5c43a1a src/Rules/Gmp.hs | 7 ------- 1 file changed, 7 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 4c7a480..9916ad6 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -53,13 +53,6 @@ configureArguments = do , "--host=" ++ hostPlatform , "--build=" ++ buildPlatform] -configureIntGmpArguments :: Action [String] -configureIntGmpArguments = do - includes <- setting GmpIncludeDir - libs <- setting GmpLibDir - return $ map ("--with-gmp-includes=" ++) (words includes) - ++ map ("--with-gmp-libraries=" ++) (words libs) - -- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do From git at git.haskell.org Fri Oct 27 00:49:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to new GMP library (0dc5fdf) Message-ID: <20171027004913.370573A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0dc5fdf1820c19dc3264d103d325c08c7d93902c/ghc >--------------------------------------------------------------- commit 0dc5fdf1820c19dc3264d103d325c08c7d93902c Author: Andrey Mokhov Date: Mon Feb 6 02:59:37 2017 +0100 Switch to new GMP library See GHC ticket 7655 >--------------------------------------------------------------- 0dc5fdf1820c19dc3264d103d325c08c7d93902c src/Rules/Gmp.hs | 17 +++++++---------- 1 file changed, 7 insertions(+), 10 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1442118..a3e32d3 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -23,9 +23,6 @@ gmpLibrary = gmpBuildPath -/- ".libs/libgmp.a" gmpMakefile :: FilePath gmpMakefile = gmpBuildPath -/- "Makefile" -gmpPatches :: [FilePath] -gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] - configureEnvironment :: Action [CmdOption] configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 , builderEnvironment "AR" Ar @@ -77,21 +74,21 @@ gmpRules = do -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. tarball <- unifyPath . getSingleton "Exactly one GMP tarball is expected" - <$> getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] + <$> getDirectoryFiles "" [gmpBase -/- "gmp-tarballs/gmp*.tar.bz2"] withTempDir $ \dir -> do let tmp = unifyPath dir need [tarball] build $ Target gmpContext Tar [tarball] [tmp] - forM_ gmpPatches $ \src -> do - let patch = takeFileName src - copyFile src $ tmp -/- patch - applyPatch tmp patch + let patch = gmpBase -/- "gmpsrc.patch" + patchName = takeFileName patch + copyFile patch $ tmp -/- patchName + applyPatch tmp patchName let name = dropExtension . dropExtension $ takeFileName tarball unpack = fromMaybe . error $ "gmpRules: expected suffix " - ++ "-nodoc-patched (found: " ++ name ++ ")." - libName = unpack $ stripSuffix "-nodoc-patched" name + ++ "-nodoc (found: " ++ name ++ ")." + libName = unpack $ stripSuffix "-nodoc" name moveDirectory (tmp -/- libName) gmpBuildPath From git at git.haskell.org Fri Oct 27 00:49:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Extract gmpLibs from integer-gmp.buildinfo directly. (aafa9ad) Message-ID: <20171027004917.5415B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aafa9add2e1c98059b7ffa6ded7c86195f9967e1/ghc >--------------------------------------------------------------- commit aafa9add2e1c98059b7ffa6ded7c86195f9967e1 Author: Andrey Mokhov Date: Thu Feb 11 01:52:55 2016 +0000 Extract gmpLibs from integer-gmp.buildinfo directly. See #159, #206. >--------------------------------------------------------------- aafa9add2e1c98059b7ffa6ded7c86195f9967e1 src/Settings/Builders/Ghc.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index c9f8ddc..b7aef56 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -12,6 +12,9 @@ import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) import Settings.Builders.Common (cIncludeArgs) +buildInfoPath :: FilePath +buildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" + -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ @@ -28,7 +31,12 @@ ghcBuilderArgs = stagedBuilder Ghc ? do buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs gmpLibs <- if stage > Stage0 && buildProg - then words <$> getSetting GmpLibDir + then do -- TODO: get this data more gracefully + buildInfo <- lift $ readFileLines buildInfoPath + let extract s = case stripPrefix "extra-libraries: " s of + Nothing -> [] + Just value -> words value + return $ concatMap extract buildInfo else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs From git at git.haskell.org Fri Oct 27 00:49:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use --depth 1 for git clone (#298) (c3e8242) Message-ID: <20171027004917.5E8BD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3e8242cf0954fb785868019fa73a338cfddfaba/ghc >--------------------------------------------------------------- commit c3e8242cf0954fb785868019fa73a338cfddfaba Author: Gracjan Polak Date: Sat Feb 11 23:32:07 2017 +0100 Use --depth 1 for git clone (#298) * Use --depth 1 for git clone * Update .travis.yml Try separating git commands * Update .travis.yml Try github * Update .travis.yml * Update .travis.yml * Update .travis.yml * Update .travis.yml * Update .travis.yml * Update .travis.yml >--------------------------------------------------------------- c3e8242cf0954fb785868019fa73a338cfddfaba .travis.yml | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 35ae3b7..f6eda04 100644 --- a/.travis.yml +++ b/.travis.yml @@ -28,12 +28,18 @@ install: - export PATH - env + # Fetch GHC sources into ./ghc + - git --version + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git clone --depth 1 --recursive git://github.com/ghc/ghc + # --shallow-submodules is not supported on travis standard git 1.8 (linux), but it is supported + # on Travis Mac OS X machines. But it does not work with github mirrors because it cannot + # find commits. + # Install all Hadrian and GHC build dependencies - cabal update - cabal install alex happy ansi-terminal mtl shake quickcheck - # Fetch GHC sources into ./ghc - - git clone --recursive git://git.haskell.org/ghc.git --quiet # Travis has already cloned Hadrian into ./ and we need to move it # to ./ghc/hadrian -- one way to do it is to move the .git directory From git at git.haskell.org Fri Oct 27 00:49:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add extra to the list of dependencies (cb5035a) Message-ID: <20171027004921.AFA373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb5035a49c5eee7706d3634c007520e6b1f4c2a5/ghc >--------------------------------------------------------------- commit cb5035a49c5eee7706d3634c007520e6b1f4c2a5 Author: Andrey Mokhov Date: Tue Feb 14 23:50:42 2017 +0100 Add extra to the list of dependencies >--------------------------------------------------------------- cb5035a49c5eee7706d3634c007520e6b1f4c2a5 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 038bde5..2256fbf 100644 --- a/README.md +++ b/README.md @@ -23,7 +23,7 @@ follow these steps: * If you have never built GHC before, start with the [preparation guide][ghc-preparation]. * This build system is written in Haskell (obviously) and depends on the following Haskell -packages, which need to be installed: `ansi-terminal mtl shake quickcheck`. +packages, which need to be installed: `ansi-terminal extra mtl quickcheck shake`. * Get the sources. It is important for the build system to be in the `hadrian` directory of the GHC source tree: From git at git.haskell.org Fri Oct 27 00:49:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track gmpBuildInfoPath explicitly. (2c21908) Message-ID: <20171027004921.B55493A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c219087e3f7ec91e7ab02edbfd3466818402c73/ghc >--------------------------------------------------------------- commit 2c219087e3f7ec91e7ab02edbfd3466818402c73 Author: Andrey Mokhov Date: Thu Feb 11 11:40:42 2016 +0000 Track gmpBuildInfoPath explicitly. See #159. >--------------------------------------------------------------- 2c219087e3f7ec91e7ab02edbfd3466818402c73 src/Rules/Gmp.hs | 4 +++- src/Settings/Builders/Ghc.hs | 5 +---- src/Settings/Paths.hs | 8 ++++++-- 3 files changed, 10 insertions(+), 7 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 9916ad6..b70b840 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -119,4 +119,6 @@ gmpRules = do gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] - gmpBase -/- "config.mk" %> \_ -> need [pkgDataFile Stage1 integerGmp] + -- This causes integerGmp package to be configured, hence creating the files + [gmpBase -/- "config.mk", gmpBuildInfoPath] &%> \_ -> + need [pkgDataFile Stage1 integerGmp] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index b7aef56..51fde7f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -12,9 +12,6 @@ import Settings import Settings.Builders.GhcCabal (bootPackageDbArgs) import Settings.Builders.Common (cIncludeArgs) -buildInfoPath :: FilePath -buildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" - -- TODO: add support for -dyno -- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ @@ -32,7 +29,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do libs <- getPkgDataList DepExtraLibs gmpLibs <- if stage > Stage0 && buildProg then do -- TODO: get this data more gracefully - buildInfo <- lift $ readFileLines buildInfoPath + buildInfo <- lift $ readFileLines gmpBuildInfoPath let extract s = case stripPrefix "extra-libraries: " s of Nothing -> [] Just value -> words value diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 99a4962..96cd3bf 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,7 @@ module Settings.Paths ( targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, packageDbDirectory, - pkgConfFile + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpBuildInfoPath, + packageDbDirectory, pkgConfFile ) where import Base @@ -51,6 +51,10 @@ pkgFile stage pkg prefix suffix = do gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" +-- We extract system gmp library name from this file +gmpBuildInfoPath :: FilePath +gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" + -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory packageDbDirectory :: Stage -> FilePath From git at git.haskell.org Fri Oct 27 00:49:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move -rtsopts to linker options (e561f80) Message-ID: <20171027004925.9C08C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e561f8042ad86c40fda1e4181099c84518e359ad/ghc >--------------------------------------------------------------- commit e561f8042ad86c40fda1e4181099c84518e359ad Author: Andrey Mokhov Date: Thu Mar 16 00:41:56 2017 +0000 Move -rtsopts to linker options >--------------------------------------------------------------- e561f8042ad86c40fda1e4181099c84518e359ad src/Settings/Builders/Ghc.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 006d9f8..8020848 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -28,7 +28,8 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do return $ concatMap (words . strip) buildInfo else return [] mconcat [ arg "-no-auto-link-packages" - , nonHsMainPackage pkg ? arg "-no-hs-main" + , nonHsMainPackage pkg ? arg "-no-hs-main" + , not (nonHsMainPackage pkg) ? arg "-rtsopts" , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] @@ -74,8 +75,7 @@ commonGhcArgs = do , append $ map ("-optP" ++) cppArgs , arg "-odir" , arg path , arg "-hidir" , arg path - , arg "-stubdir" , arg path - , (not . nonHsMainPackage) <$> getPackage ? arg "-rtsopts" ] + , arg "-stubdir" , arg path ] -- TODO: Do '-ticky' in all debug ways? wayGhcArgs :: Args From git at git.haskell.org Fri Oct 27 00:49:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out Context from Target. (e8b62f7) Message-ID: <20171027004925.A7D793A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e8b62f7e939cb19194fea1ff0123ae8df1788e61/ghc >--------------------------------------------------------------- commit e8b62f7e939cb19194fea1ff0123ae8df1788e61 Author: Andrey Mokhov Date: Fri Feb 12 01:22:58 2016 +0000 Factor out Context from Target. See #207. >--------------------------------------------------------------- e8b62f7e939cb19194fea1ff0123ae8df1788e61 shaking-up-ghc.cabal | 1 + src/Context.hs | 28 ++++++++++++++++++ src/Expression.hs | 24 +++++++-------- src/Oracles/PackageDb.hs | 4 +-- src/Rules.hs | 12 ++++---- src/Rules/Actions.hs | 22 +++++++------- src/Rules/Cabal.hs | 4 +-- src/Rules/Compile.hs | 32 +++++++++++--------- src/Rules/Data.hs | 67 ++++++++++++++++++++++-------------------- src/Rules/Dependencies.hs | 20 ++++++++----- src/Rules/Documentation.hs | 23 ++++++++------- src/Rules/Generate.hs | 34 +++++++++++---------- src/Rules/Gmp.hs | 15 +++++----- src/Rules/Libffi.hs | 17 ++++++----- src/Rules/Library.hs | 64 +++++++++++++++++++++------------------- src/Rules/Package.hs | 4 +-- src/Rules/Program.hs | 73 ++++++++++++++++++++++++---------------------- src/Rules/Register.hs | 26 ++++++++++------- src/Target.hs | 67 ++++++------------------------------------ src/Test.hs | 13 ++++----- 20 files changed, 278 insertions(+), 272 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 e8b62f7e939cb19194fea1ff0123ae8df1788e61 From git at git.haskell.org Fri Oct 27 00:49:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/snowleopard/hadrian (f8bd794) Message-ID: <20171027004929.9419D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8bd7949c12c99aae2b6d0388fdf3b6d9143d23e/ghc >--------------------------------------------------------------- commit f8bd7949c12c99aae2b6d0388fdf3b6d9143d23e Merge: e561f80 cb5035a Author: Andrey Mokhov Date: Thu Mar 16 00:42:05 2017 +0000 Merge branch 'master' of https://github.com/snowleopard/hadrian >--------------------------------------------------------------- f8bd7949c12c99aae2b6d0388fdf3b6d9143d23e .travis.yml | 10 ++++++++-- README.md | 2 +- 2 files changed, 9 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:49:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (6482e6a) Message-ID: <20171027004929.CED573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6482e6a90e68c54b7d0202d0ae5d9d600873646d/ghc >--------------------------------------------------------------- commit 6482e6a90e68c54b7d0202d0ae5d9d600873646d Author: Andrey Mokhov Date: Sun Feb 14 21:18:57 2016 +0000 Add comments. >--------------------------------------------------------------- 6482e6a90e68c54b7d0202d0ae5d9d600873646d src/Context.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Context.hs b/src/Context.hs index 9bf8020..b578208 100644 --- a/src/Context.hs +++ b/src/Context.hs @@ -20,6 +20,8 @@ data Context = Context vanillaContext :: Stage -> Package -> Context vanillaContext s p = Context s p vanilla +-- | Partial context with undefined 'Package' field. Useful for 'Packages' +-- expressions that only read the environment and current 'Stage'. stageContext :: Stage -> Context stageContext s = vanillaContext s $ error "stageContext: package not set" From git at git.haskell.org Fri Oct 27 00:49:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on the exact version of the in-tree Cabal library (e664431) Message-ID: <20171027004933.1AA603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e664431fb9a240599f512474cf611c51d5d701cb/ghc >--------------------------------------------------------------- commit e664431fb9a240599f512474cf611c51d5d701cb Author: Andrey Mokhov Date: Thu Mar 16 00:56:50 2017 +0000 Depend on the exact version of the in-tree Cabal library >--------------------------------------------------------------- e664431fb9a240599f512474cf611c51d5d701cb hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 18361f3..fd6c036 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -117,7 +117,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.25.* + , Cabal == 2.0.0.0 , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 00:49:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move mkUserGuidePart to Stage2. (9497fbe) Message-ID: <20171027004933.761EC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9497fbee97634610c2d9af6115f139f794c5fb0f/ghc >--------------------------------------------------------------- commit 9497fbee97634610c2d9af6115f139f794c5fb0f Author: Andrey Mokhov Date: Sun Feb 14 21:54:25 2016 +0000 Move mkUserGuidePart to Stage2. >--------------------------------------------------------------- 9497fbee97634610c2d9af6115f139f794c5fb0f src/Settings/Packages.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 691cd78..ef8fc26 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -34,8 +34,7 @@ packagesStage1 = mconcat [ packagesStage0 , append [ array, base, bytestring, containers, compareSizes, deepseq , directory, filepath, ghci, ghcPrim, haskeline, hpcBin - , integerLibrary, mkUserGuidePart, pretty, process, rts, runGhc - , time ] + , integerLibrary, pretty, process, rts, runGhc, time ] , windowsHost ? append [win32] , notM windowsHost ? append [unix] , notM windowsHost ? append [iservBin] @@ -45,7 +44,7 @@ packagesStage1 = mconcat -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages packagesStage2 = mconcat - [ append [ghcTags] + [ append [ghcTags, mkUserGuidePart] , buildHaddock ? append [haddock] ] -- TODO: switch to Set Package as the order of packages should not matter? From git at git.haskell.org Fri Oct 27 00:49:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename compact to ghc-compact (30708a4) Message-ID: <20171027004936.89FBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30708a47a3456f68bca6951232c02b26dda86585/ghc >--------------------------------------------------------------- commit 30708a47a3456f68bca6951232c02b26dda86585 Author: Andrey Mokhov Date: Thu Mar 16 01:17:01 2017 +0000 Rename compact to ghc-compact >--------------------------------------------------------------- 30708a47a3456f68bca6951232c02b26dda86585 src/GHC.hs | 25 ++++++++++++------------- src/Settings/Default.hs | 2 +- 2 files changed, 13 insertions(+), 14 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index f8abeb8..33af662 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,14 +1,13 @@ {-# LANGUAGE OverloadedStrings, LambdaCase #-} {-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( - array, base, binary, bytestring, cabal, checkApiAnnotations, compact, - compareSizes, compiler, containers, deepseq, deriveConstants, directory, - dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, - ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, - hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, - libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, - stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, - win32, xhtml, + array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, + compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, + genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, + ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, + hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, + parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, + terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, defaultKnownPackages, builderProvenance, programName, nonCabalContext, nonHsMainPackage @@ -26,10 +25,10 @@ import Stage -- be overridden in @hadrian/src/UserSettings.hs at . defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, binary, bytestring, cabal, checkApiAnnotations, compact - , compareSizes, compiler, containers, deepseq, deriveConstants, directory - , dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh - , ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs + [ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes + , compiler, containers, deepseq, deriveConstants, directory, dllSplit + , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal + , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs , hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 @@ -42,7 +41,6 @@ binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" checkApiAnnotations = utility "check-api-annotations" -compact = library "compact" compareSizes = utility "compareSizes" `setPath` "utils/compare_sizes" compiler = topLevel "ghc" `setPath` "compiler" containers = library "containers" @@ -57,6 +55,7 @@ ghc = topLevel "ghc-bin" `setPath` "ghc" `setType` Progra ghcBoot = library "ghc-boot" ghcBootTh = library "ghc-boot-th" ghcCabal = utility "ghc-cabal" +ghcCompact = library "ghc-compact" ghci = library "ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 318b0a0..89db236 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -120,13 +120,13 @@ stage1Packages = do , append $ [ array , base , bytestring - , compact , containers , deepseq , directory , filepath , ghc , ghcCabal + , ghcCompact , ghci , ghcPrim , haskeline From git at git.haskell.org Fri Oct 27 00:49:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install mkUserGuidePart binary to inplace/bin. (d1ec507) Message-ID: <20171027004936.ED7103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1ec507d7b4d837ee0161f08e9eab0b5630f2797/ghc >--------------------------------------------------------------- commit d1ec507d7b4d837ee0161f08e9eab0b5630f2797 Author: Andrey Mokhov Date: Sun Feb 14 22:55:38 2016 +0000 Install mkUserGuidePart binary to inplace/bin. >--------------------------------------------------------------- d1ec507d7b4d837ee0161f08e9eab0b5630f2797 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0262243..d29cbbf 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -106,7 +106,7 @@ ghcSplit = "inplace/lib/bin/ghc-split" programPath :: Stage -> Package -> Maybe FilePath programPath stage pkg | pkg == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) - | pkg == haddock || pkg == ghcTags = case stage of + | pkg `elem` [ghcTags, haddock, mkUserGuidePart] = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString pkg _ -> Nothing | pkg `elem` [touchy, unlit] = case stage of From git at git.haskell.org Fri Oct 27 00:49:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename readPackageDescription to readGenericPackageDescription to fix the warning (198abb4) Message-ID: <20171027004940.46A2D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/198abb4fff538fb67ab9262aa0a7ca5b8bd86c0f/ghc >--------------------------------------------------------------- commit 198abb4fff538fb67ab9262aa0a7ca5b8bd86c0f Author: Andrey Mokhov Date: Thu Mar 16 01:17:36 2017 +0000 Rename readPackageDescription to readGenericPackageDescription to fix the warning >--------------------------------------------------------------- 198abb4fff538fb67ab9262aa0a7ca5b8bd86c0f src/Rules/Cabal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 0df267f..b45af42 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -23,7 +23,7 @@ cabalRules = do let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] - pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg + pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg let identifier = package . packageDescription $ pd version = display . pkgVersion $ identifier return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version @@ -37,7 +37,7 @@ cabalRules = do if not exists then return $ pkgNameString pkg else do need [pkgCabalFile pkg] - pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg + pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg let depsLib = collectDeps $ condLibrary pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes From git at git.haskell.org Fri Oct 27 00:49:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop repetition in the list of packages, fixing Hadrian's selftest (7b90c76) Message-ID: <20171027004943.C73063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b90c7636c20de71b133dba2a1c0bae4ee591dbe/ghc >--------------------------------------------------------------- commit 7b90c7636c20de71b133dba2a1c0bae4ee591dbe Author: Andrey Mokhov Date: Thu Mar 16 11:31:47 2017 +0000 Drop repetition in the list of packages, fixing Hadrian's selftest >--------------------------------------------------------------- 7b90c7636c20de71b133dba2a1c0bae4ee591dbe src/Settings/Default.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 89db236..d242502 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -127,7 +127,6 @@ stage1Packages = do , ghc , ghcCabal , ghcCompact - , ghci , ghcPrim , haskeline , hpcBin From git at git.haskell.org Fri Oct 27 00:49:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix incorrect context when reading BuildGhciLib flag. (9207f25) Message-ID: <20171027004940.ACD003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9207f2530763c2bace7708cac77c767e596035da/ghc >--------------------------------------------------------------- commit 9207f2530763c2bace7708cac77c767e596035da Author: Andrey Mokhov Date: Sun Feb 14 22:57:17 2016 +0000 Fix incorrect context when reading BuildGhciLib flag. >--------------------------------------------------------------- 9207f2530763c2bace7708cac77c767e596035da src/Rules/Program.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index f00dd59..00f4c52 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -85,18 +85,18 @@ buildBinary context @ (Context stage package _) bin = do depNames <- interpretInContext context $ getPkgDataList TransitiveDepNames let libStage = min stage Stage1 -- libraries are built only in Stage0/1 libContext = vanillaContext libStage package - pkgs <- interpretInContext libContext getPackages - ghciFlag <- interpretInContext libContext $ getPkgData BuildGhciLib + pkgs <- interpretInContext libContext getPackages let deps = matchPackageNames (sort pkgs) (map PackageName $ sort depNames) - ghci = ghciFlag == "YES" && stage == Stage1 libs <- fmap concat . forM deps $ \dep -> do + let depContext = vanillaContext libStage dep + ghciFlag <- interpretInContext depContext $ getPkgData BuildGhciLib libFiles <- fmap concat . forM ways $ \way -> do libFile <- pkgLibraryFile libStage dep way lib0File <- pkgLibraryFile0 libStage dep way dll0 <- needDll0 libStage dep return $ libFile : [ lib0File | dll0 ] ghciLib <- pkgGhciLibraryFile libStage dep - return $ libFiles ++ [ ghciLib | ghci ] + return $ libFiles ++ [ ghciLib | ghciFlag == "YES" && stage == Stage1 ] let binDeps = if package == ghcCabal && stage == Stage0 then [ pkgPath package -/- src <.> "hs" | src <- hSrcs ] else objs From git at git.haskell.org Fri Oct 27 00:49:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out build rules into Rules.buildRules. (e7f8710) Message-ID: <20171027004944.78B1B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7f8710c591d5329e4a06df538ca0aa789b065a0/ghc >--------------------------------------------------------------- commit e7f8710c591d5329e4a06df538ca0aa789b065a0 Author: Andrey Mokhov Date: Sun Feb 14 22:59:11 2016 +0000 Factor out build rules into Rules.buildRules. >--------------------------------------------------------------- e7f8710c591d5329e4a06df538ca0aa789b065a0 src/Main.hs | 17 ++--------------- src/Rules.hs | 39 ++++++++++++++++++++++++++++----------- 2 files changed, 30 insertions(+), 26 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 544987d..e028597 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -6,14 +6,8 @@ import qualified Base import qualified CmdLineFlag import qualified Environment import qualified Rules -import qualified Rules.Cabal import qualified Rules.Clean -import qualified Rules.Generate -import qualified Rules.Gmp -import qualified Rules.Libffi import qualified Rules.Oracles -import qualified Rules.Perl -import qualified Rules.Setup import qualified Selftest import qualified Test @@ -27,17 +21,10 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do where rules :: Rules () rules = mconcat - [ Rules.Cabal.cabalRules - , Rules.Clean.cleanRules - , Rules.Generate.generateRules - , Rules.Generate.copyRules - , Rules.Gmp.gmpRules - , Rules.Libffi.libffiRules + [ Rules.Clean.cleanRules , Rules.Oracles.oracleRules - , Rules.Perl.perlScriptRules - , Rules.Setup.setupRules + , Rules.buildRules , Rules.topLevelTargets - , Rules.packageRules , Selftest.selftestRules , Test.testRules ] options = shakeOptions diff --git a/src/Rules.hs b/src/Rules.hs index 34cea4c..5cbfa7e 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,12 +1,18 @@ -module Rules (topLevelTargets, packageRules) where +module Rules (topLevelTargets, buildRules) where -import Base import Data.Foldable + +import Base import Expression -import GHC hiding (haddock) +import GHC import qualified Rules.Generate -import Rules.Package -import Rules.Resources +import qualified Rules.Package +import qualified Rules.Resources +import qualified Rules.Cabal +import qualified Rules.Gmp +import qualified Rules.Libffi +import qualified Rules.Perl +import qualified Rules.Setup import Settings allStages :: [Stage] @@ -32,16 +38,27 @@ topLevelTargets = do when (pkg `elem` activePackages) $ if isLibrary pkg then do -- build a library - ways <- interpretInContext context getLibraryWays - libs <- traverse (pkgLibraryFile stage pkg) ways - haddock <- interpretInContext context buildHaddock - need $ libs ++ [ pkgHaddockFile pkg | haddock && stage == Stage1 ] + ways <- interpretInContext context getLibraryWays + libs <- traverse (pkgLibraryFile stage pkg) ways + docs <- interpretInContext context buildHaddock + need $ libs ++ [ pkgHaddockFile pkg | docs && stage == Stage1 ] else do -- otherwise build a program need [ fromJust $ programPath stage pkg ] -- TODO: drop fromJust packageRules :: Rules () packageRules = do - resources <- resourceRules + resources <- Rules.Resources.resourceRules for_ allStages $ \stage -> for_ knownPackages $ \pkg -> - buildPackage resources $ vanillaContext stage pkg + Rules.Package.buildPackage resources $ vanillaContext stage pkg + +buildRules :: Rules () +buildRules = mconcat + [ Rules.Cabal.cabalRules + , Rules.Generate.generateRules + , Rules.Generate.copyRules + , Rules.Gmp.gmpRules + , Rules.Libffi.libffiRules + , Rules.Perl.perlScriptRules + , Rules.Setup.setupRules + , Rules.packageRules ] From git at git.haskell.org Fri Oct 27 00:49:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Added a note about git line-ending settings (#303) (295c781) Message-ID: <20171027004947.B6D203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/295c7812ab8fe8e34e6812127e039220a850a344/ghc >--------------------------------------------------------------- commit 295c7812ab8fe8e34e6812127e039220a850a344 Author: Ivan Poliakov Date: Fri Mar 31 23:54:46 2017 +0100 Added a note about git line-ending settings (#303) >--------------------------------------------------------------- 295c7812ab8fe8e34e6812127e039220a850a344 doc/windows.md | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/doc/windows.md b/doc/windows.md index 73804df..510b986 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -5,6 +5,14 @@ Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). +Note that `git` should be configured to check out Unix-style line endings. The default behaviour of `git` on Windows is to check out Windows-style line endings which can cause issues during the build. This can be changed using the following command: + + git config --global core.autocrlf false + +If you would like to restore the default behaviour later run: + + git config --global core.autocrlf true + ```sh # Get GHC and Hadrian sources git clone --recursive git://git.haskell.org/ghc.git From git at git.haskell.org Fri Oct 27 00:49:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Selftest and Test rules into Rules directory. (d81e041) Message-ID: <20171027004948.4B48F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d81e041691644e1f99a84691ac0d0fb94c96b263/ghc >--------------------------------------------------------------- commit d81e041691644e1f99a84691ac0d0fb94c96b263 Author: Andrey Mokhov Date: Sun Feb 14 23:02:46 2016 +0000 Move Selftest and Test rules into Rules directory. >--------------------------------------------------------------- d81e041691644e1f99a84691ac0d0fb94c96b263 shaking-up-ghc.cabal | 4 ++-- src/Main.hs | 10 +++++----- src/{ => Rules}/Selftest.hs | 2 +- src/{ => Rules}/Test.hs | 2 +- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 2ab8ee7..6435d30 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -63,10 +63,11 @@ executable ghc-shake , Rules.Program , Rules.Register , Rules.Resources + , Rules.Selftest , Rules.Setup + , Rules.Test , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg - , Selftest , Settings , Settings.Args , Settings.Builders.Alex @@ -106,7 +107,6 @@ executable ghc-shake , Settings.Ways , Stage , Target - , Test , Way default-language: Haskell2010 diff --git a/src/Main.hs b/src/Main.hs index e028597..5de50ad 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -8,8 +8,8 @@ import qualified Environment import qualified Rules import qualified Rules.Clean import qualified Rules.Oracles -import qualified Selftest -import qualified Test +import qualified Rules.Selftest +import qualified Rules.Test main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -23,10 +23,10 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do rules = mconcat [ Rules.Clean.cleanRules , Rules.Oracles.oracleRules + , Rules.Selftest.selftestRules + , Rules.Test.testRules , Rules.buildRules - , Rules.topLevelTargets - , Selftest.selftestRules - , Test.testRules ] + , Rules.topLevelTargets ] options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Selftest.hs b/src/Rules/Selftest.hs similarity index 94% rename from src/Selftest.hs rename to src/Rules/Selftest.hs index 4800ca8..a3cc089 100644 --- a/src/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -module Selftest (selftestRules) where +module Rules.Selftest (selftestRules) where import Development.Shake import Settings.Builders.Ar (chunksOfSize) diff --git a/src/Test.hs b/src/Rules/Test.hs similarity index 98% rename from src/Test.hs rename to src/Rules/Test.hs index 3ef0d1d..0448b2b 100644 --- a/src/Test.hs +++ b/src/Rules/Test.hs @@ -1,4 +1,4 @@ -module Test (testRules) where +module Rules.Test (testRules) where import Base import Builder From git at git.haskell.org Fri Oct 27 00:49:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add wrapper for Runhaskell, Fix #304 (#305) (c158014) Message-ID: <20171027004951.AC2D43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c158014fbb90046a43d1d6d78b888a687ce341c6/ghc >--------------------------------------------------------------- commit c158014fbb90046a43d1d6d78b888a687ce341c6 Author: Zhen Zhang Date: Sun Apr 16 04:08:33 2017 +0800 Add wrapper for Runhaskell, Fix #304 (#305) >--------------------------------------------------------------- c158014fbb90046a43d1d6d78b888a687ce341c6 .gitignore | 3 +++ src/Rules/Program.hs | 2 ++ src/Rules/Wrappers/Runhaskell.hs | 15 +++++++++++++++ 3 files changed, 20 insertions(+) diff --git a/.gitignore b/.gitignore index 6b06fea..2e3581b 100644 --- a/.gitignore +++ b/.gitignore @@ -17,3 +17,6 @@ cabal.sandbox.config # the user settings /UserSettings.hs + +# Mostly temp file by emacs +*~ diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 254284a..71fb8b7 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -12,6 +12,7 @@ import Oracles.ModuleFiles import Oracles.PackageData import Rules.Wrappers.Ghc import Rules.Wrappers.GhcPkg +import Rules.Wrappers.Runhaskell import Settings import Settings.Path import Target @@ -25,6 +26,7 @@ type Wrapper = FilePath -> Expr String wrappers :: [(Context, Wrapper)] wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) + , (vanillaContext Stage1 runGhc, runhaskellWrapper) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper) ] buildProgram :: [(Resource, Int)] -> Context -> Rules () diff --git a/src/Rules/Wrappers/Runhaskell.hs b/src/Rules/Wrappers/Runhaskell.hs new file mode 100644 index 0000000..521b41a --- /dev/null +++ b/src/Rules/Wrappers/Runhaskell.hs @@ -0,0 +1,15 @@ +module Rules.Wrappers.Runhaskell (runhaskellWrapper) where + +import Base +import Expression +import Oracles.Path + +runhaskellWrapper :: FilePath -> Expr String +runhaskellWrapper program = do + lift $ need [sourcePath -/- "Rules/Wrappers/Runhaskell.hs"] + top <- getTopDirectory + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (top -/- program) + ++ " -f" ++ (top -/- "inplace/lib/bin/ghc-stage2") -- HACK + ++ " -B" ++ (top -/- "inplace/lib") ++ " ${1+\"$@\"}" ] From git at git.haskell.org Fri Oct 27 00:49:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Rules/Package.hs into Rules.hs. (a10669a) Message-ID: <20171027004952.19CC73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a10669a6788da387e9e5a3e6fe35383589f22ac1/ghc >--------------------------------------------------------------- commit a10669a6788da387e9e5a3e6fe35383589f22ac1 Author: Andrey Mokhov Date: Sun Feb 14 23:21:54 2016 +0000 Move Rules/Package.hs into Rules.hs. >--------------------------------------------------------------- a10669a6788da387e9e5a3e6fe35383589f22ac1 shaking-up-ghc.cabal | 1 - src/Rules.hs | 21 +++++++++++++++++++-- src/Rules/Package.hs | 24 ------------------------ 3 files changed, 19 insertions(+), 27 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 6435d30..193b04e 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -58,7 +58,6 @@ executable ghc-shake , Rules.Libffi , Rules.Library , Rules.Oracles - , Rules.Package , Rules.Perl , Rules.Program , Rules.Register diff --git a/src/Rules.hs b/src/Rules.hs index 5cbfa7e..cea2c0d 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,13 +5,19 @@ import Data.Foldable import Base import Expression import GHC +import qualified Rules.Compile +import qualified Rules.Data +import qualified Rules.Dependencies +import qualified Rules.Documentation import qualified Rules.Generate -import qualified Rules.Package import qualified Rules.Resources import qualified Rules.Cabal import qualified Rules.Gmp import qualified Rules.Libffi +import qualified Rules.Library import qualified Rules.Perl +import qualified Rules.Program +import qualified Rules.Register import qualified Rules.Setup import Settings @@ -50,7 +56,18 @@ packageRules = do resources <- Rules.Resources.resourceRules for_ allStages $ \stage -> for_ knownPackages $ \pkg -> - Rules.Package.buildPackage resources $ vanillaContext stage pkg + buildPackage resources $ vanillaContext stage pkg + +buildPackage :: Rules.Resources.Resources -> Context -> Rules () +buildPackage = mconcat + [ Rules.Compile.compilePackage + , Rules.Data.buildPackageData + , Rules.Dependencies.buildPackageDependencies + , Rules.Documentation.buildPackageDocumentation + , Rules.Generate.generatePackageCode + , Rules.Library.buildPackageLibrary + , Rules.Program.buildProgram + , Rules.Register.registerPackage ] buildRules :: Rules () buildRules = mconcat diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs deleted file mode 100644 index 26de923..0000000 --- a/src/Rules/Package.hs +++ /dev/null @@ -1,24 +0,0 @@ -module Rules.Package (buildPackage) where - -import Base -import Context -import qualified Rules.Compile -import qualified Rules.Data -import qualified Rules.Dependencies -import qualified Rules.Documentation -import qualified Rules.Generate -import qualified Rules.Library -import qualified Rules.Program -import qualified Rules.Register -import Rules.Resources - -buildPackage :: Resources -> Context -> Rules () -buildPackage = mconcat - [ Rules.Compile.compilePackage - , Rules.Data.buildPackageData - , Rules.Dependencies.buildPackageDependencies - , Rules.Documentation.buildPackageDocumentation - , Rules.Generate.generatePackageCode - , Rules.Library.buildPackageLibrary - , Rules.Program.buildProgram - , Rules.Register.registerPackage ] From git at git.haskell.org Fri Oct 27 00:49:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow cmm files in non-custom packages (5b9f6e9) Message-ID: <20171027004955.B5F8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b9f6e901eb3613544aaf941d33419fb9f8368d0/ghc >--------------------------------------------------------------- commit 5b9f6e901eb3613544aaf941d33419fb9f8368d0 Author: Andrey Mokhov Date: Wed Apr 26 01:53:28 2017 +0100 Allow cmm files in non-custom packages >--------------------------------------------------------------- 5b9f6e901eb3613544aaf941d33419fb9f8368d0 src/Rules/Data.hs | 9 ++++++--- src/Rules/Library.hs | 21 ++++++++++++++------- 2 files changed, 20 insertions(+), 10 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index cff0896..0538f6c 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -102,13 +102,16 @@ packageCmmSources pkg -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$'. For example, get rid of -- @libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ...@ --- Reason: we don't need them and we can't parse them. +-- and replace it with a tracked call to getDirectoryFiles. -- 2) Drop path prefixes to individual settings. -- For example, @libraries/deepseq/dist-install_VERSION = 1.4.0.0@ -- is replaced by @VERSION = 1.4.0.0 at . -- Reason: Shake's built-in makefile parser doesn't recognise slashes postProcessPackageData :: Context -> FilePath -> Action () postProcessPackageData context at Context {..} file = do - top <- topDirectory + top <- topDirectory + cmmSrcs <- getDirectoryFiles (pkgPath package) ["cbits/*.cmm"] let len = length (pkgPath package) + length (top -/- buildPath context) + 2 - fixFile file $ unlines . map (drop len) . filter ('$' `notElem`) . lines + fixFile file $ unlines + . (++ ["CMM_SRCS = " ++ unwords (map unifyPath cmmSrcs) ]) + . map (drop len) . filter ('$' `notElem`) . lines diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 2deb6f9..32db232 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -23,12 +23,8 @@ buildPackageLibrary context at Context {..} = do -- TODO: handle dynamic libraries matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do removeFile a - asmObjs <- map (objectPath context) <$> pkgDataList (AsmSrcs path) - cObjs <- cObjects context - cmmObjs <- map (objectPath context) <$> pkgDataList (CmmSrcs path) - eObjs <- extraObjects context - hsObjs <- hsObjects context - let noHsObjs = asmObjs ++ cObjs ++ cmmObjs ++ eObjs + hsObjs <- hsObjects context + noHsObjs <- nonHsObjects context -- This will create split objects if required (we don't track them -- explicitly as this would needlessly bloat the Shake database). @@ -56,10 +52,21 @@ buildPackageGhciLibrary :: Context -> Rules () buildPackageGhciLibrary context at Context {..} = priority 2 $ do let libPrefix = buildPath context -/- "HS" ++ pkgNameString package matchVersionedFilePath libPrefix (waySuffix way <.> "o") ?> \obj -> do - objs <- concatMapM ($ context) [cObjects, hsObjects, extraObjects] + objs <- allObjects context need objs build $ Target context Ld objs [obj] +allObjects :: Context -> Action [FilePath] +allObjects context = (++) <$> nonHsObjects context <*> hsObjects context + +nonHsObjects :: Context -> Action [FilePath] +nonHsObjects context = do + let path = buildPath context + cObjs <- cObjects context + cmmObjs <- map (objectPath context) <$> pkgDataList (CmmSrcs path) + eObjs <- extraObjects context + return $ cObjs ++ cmmObjs ++ eObjs + cObjects :: Context -> Action [FilePath] cObjects context = do objs <- map (objectPath context) <$> pkgDataList (CSrcs $ buildPath context) From git at git.haskell.org Fri Oct 27 00:49:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused Resources parameter. (010fb8c) Message-ID: <20171027004956.18F953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/010fb8c148ae0d0c08236c19e74e214968d45410/ghc >--------------------------------------------------------------- commit 010fb8c148ae0d0c08236c19e74e214968d45410 Author: Andrey Mokhov Date: Sun Feb 14 23:30:15 2016 +0000 Drop unused Resources parameter. >--------------------------------------------------------------- 010fb8c148ae0d0c08236c19e74e214968d45410 src/Rules.hs | 23 ++++++++++------------- src/Rules/Data.hs | 5 ++--- src/Rules/Documentation.hs | 5 ++--- src/Rules/Generate.hs | 5 ++--- src/Rules/Library.hs | 5 ++--- src/Rules/Program.hs | 5 ++--- 6 files changed, 20 insertions(+), 28 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index cea2c0d..be71d2f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -55,19 +55,16 @@ packageRules :: Rules () packageRules = do resources <- Rules.Resources.resourceRules for_ allStages $ \stage -> - for_ knownPackages $ \pkg -> - buildPackage resources $ vanillaContext stage pkg - -buildPackage :: Rules.Resources.Resources -> Context -> Rules () -buildPackage = mconcat - [ Rules.Compile.compilePackage - , Rules.Data.buildPackageData - , Rules.Dependencies.buildPackageDependencies - , Rules.Documentation.buildPackageDocumentation - , Rules.Generate.generatePackageCode - , Rules.Library.buildPackageLibrary - , Rules.Program.buildProgram - , Rules.Register.registerPackage ] + for_ knownPackages $ \package -> do + let context = vanillaContext stage package + Rules.Compile.compilePackage resources context + Rules.Data.buildPackageData context + Rules.Dependencies.buildPackageDependencies resources context + Rules.Documentation.buildPackageDocumentation context + Rules.Generate.generatePackageCode context + Rules.Library.buildPackageLibrary context + Rules.Program.buildProgram context + Rules.Register.registerPackage resources context buildRules :: Rules () buildRules = mconcat diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 7386003..f47e8d0 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -12,14 +12,13 @@ import Oracles.PackageDeps import Rules.Actions import Rules.Generate import Rules.Libffi -import Rules.Resources import Settings import Settings.Builders.Common import Target -- Build package-data.mk by using GhcCabal to process pkgCabal file -buildPackageData :: Resources -> Context -> Rules () -buildPackageData _ context @ (Context {..}) = do +buildPackageData :: Context -> Rules () +buildPackageData context @ (Context {..}) = do let cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile stage package diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 95a5667..848a3fa 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -7,7 +7,6 @@ import Expression import GHC import Oracles.PackageData import Rules.Actions -import Rules.Resources import Settings import Target @@ -17,8 +16,8 @@ haddockHtmlLib = "inplace/lib/html/haddock-util.js" -- Note: this build rule creates plenty of files, not just the .haddock one. -- All of them go into the 'doc' subdirectory. Pedantically tracking all built -- files in the Shake databases seems fragile and unnecesarry. -buildPackageDocumentation :: Resources -> Context -> Rules () -buildPackageDocumentation _ context @ (Context {..}) = +buildPackageDocumentation :: Context -> Rules () +buildPackageDocumentation context @ (Context {..}) = let cabalFile = pkgCabalFile package haddockFile = pkgHaddockFile package in when (stage == Stage1) $ do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 1a8a239..050f83c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -20,7 +20,6 @@ import Oracles.ModuleFiles import Rules.Actions import Rules.Gmp import Rules.Libffi -import Rules.Resources (Resources) import Settings import Target hiding (builder, context) @@ -114,8 +113,8 @@ generate file context expr = do writeFileChanged file contents putSuccess $ "| Successfully generated '" ++ file ++ "'." -generatePackageCode :: Resources -> Context -> Rules () -generatePackageCode _ context @ (Context stage pkg _) = +generatePackageCode :: Context -> Rules () +generatePackageCode context @ (Context stage pkg _) = let buildPath = targetPath stage pkg -/- "build" dropBuild = drop (length buildPath + 1) generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index be8f158..79b4952 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -11,13 +11,12 @@ import GHC import Oracles.PackageData import Rules.Actions import Rules.Gmp -import Rules.Resources import Settings import Target -- TODO: Use way from Context, #207 -buildPackageLibrary :: Resources -> Context -> Rules () -buildPackageLibrary _ context @ (Context {..}) = do +buildPackageLibrary :: Context -> Rules () +buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" -- TODO: handle dynamic libraries diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 00f4c52..d7fdaad 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -11,7 +11,6 @@ import Oracles.Config.Setting import Oracles.PackageData import Rules.Actions import Rules.Library -import Rules.Resources import Rules.Wrappers.Ghc import Rules.Wrappers.GhcPkg import Settings @@ -32,8 +31,8 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper)] -buildProgram :: Resources -> Context -> Rules () -buildProgram _ context @ (Context {..}) = do +buildProgram :: Context -> Rules () +buildProgram context @ (Context {..}) = do let match file = case programPath stage package of Nothing -> False Just program -> program == file From git at git.haskell.org Fri Oct 27 00:49:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop package self-dependencies (ff322d9) Message-ID: <20171027004959.5A8643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff322d9a37a5c9a406e28eab703334737ae20cba/ghc >--------------------------------------------------------------- commit ff322d9a37a5c9a406e28eab703334737ae20cba Author: Andrey Mokhov Date: Thu Apr 27 00:20:42 2017 +0100 Drop package self-dependencies This occurs in iserv-bin package, which contains both a library and an executable. See #12 >--------------------------------------------------------------- ff322d9a37a5c9a406e28eab703334737ae20cba src/Rules/Cabal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index b45af42..ad1312f 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -42,7 +42,7 @@ cabalRules = do depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes depNames = [ unPackageName name | Dependency name _ <- deps ] - return . unwords $ pkgNameString pkg : sort depNames + return . unwords $ pkgNameString pkg : (sort depNames \\ [pkgNameString pkg]) writeFileChanged out $ unlines pkgDeps putSuccess $ "| Successfully computed package dependencies" From git at git.haskell.org Fri Oct 27 00:49:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:49:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use do notation to combine Rules. (b820539) Message-ID: <20171027004959.C6CC83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b82053913f31548325da535ba769bb21aa4338ec/ghc >--------------------------------------------------------------- commit b82053913f31548325da535ba769bb21aa4338ec Author: Andrey Mokhov Date: Sun Feb 14 23:34:37 2016 +0000 Use do notation to combine Rules. >--------------------------------------------------------------- b82053913f31548325da535ba769bb21aa4338ec src/Main.hs | 14 +++++++------- src/Rules.hs | 18 +++++++++--------- 2 files changed, 16 insertions(+), 16 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 5de50ad..96639d2 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -20,13 +20,13 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do else want targets >> withoutActions rules where rules :: Rules () - rules = mconcat - [ Rules.Clean.cleanRules - , Rules.Oracles.oracleRules - , Rules.Selftest.selftestRules - , Rules.Test.testRules - , Rules.buildRules - , Rules.topLevelTargets ] + rules = do + Rules.Clean.cleanRules + Rules.Oracles.oracleRules + Rules.Selftest.selftestRules + Rules.Test.testRules + Rules.buildRules + Rules.topLevelTargets options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Rules.hs b/src/Rules.hs index be71d2f..e817fc1 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -67,12 +67,12 @@ packageRules = do Rules.Register.registerPackage resources context buildRules :: Rules () -buildRules = mconcat - [ Rules.Cabal.cabalRules - , Rules.Generate.generateRules - , Rules.Generate.copyRules - , Rules.Gmp.gmpRules - , Rules.Libffi.libffiRules - , Rules.Perl.perlScriptRules - , Rules.Setup.setupRules - , Rules.packageRules ] +buildRules = do + Rules.Cabal.cabalRules + Rules.Generate.generateRules + Rules.Generate.copyRules + Rules.Gmp.gmpRules + Rules.Libffi.libffiRules + Rules.Perl.perlScriptRules + Rules.Setup.setupRules + Rules.packageRules From git at git.haskell.org Fri Oct 27 00:50:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GHC ticket 13583 has been resolved, so the workaround is no longer needed (4347b0d) Message-ID: <20171027005003.101CE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4347b0dc3265faec235672b1ba889bb56b38798a/ghc >--------------------------------------------------------------- commit 4347b0dc3265faec235672b1ba889bb56b38798a Author: Andrey Mokhov Date: Thu Apr 27 00:43:14 2017 +0100 GHC ticket 13583 has been resolved, so the workaround is no longer needed See #276 >--------------------------------------------------------------- 4347b0dc3265faec235672b1ba889bb56b38798a src/Settings/Builders/Configure.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 3ab3286..b6142d7 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -1,7 +1,5 @@ module Settings.Builders.Configure (configureBuilderArgs) where -import qualified System.Info as System - import Settings.Builders.Common configureBuilderArgs :: Args @@ -20,9 +18,4 @@ configureBuilderArgs = mconcat , "--libdir=" ++ top -/- libffiBuildPath -/- "inst/lib" , "--enable-static=yes" , "--enable-shared=no" -- TODO: add support for yes - , "--host=" ++ targetPlatform ] - - -- On OS X, use "nm-classic" instead of "nm" due to a bug in the latter. - -- See https://ghc.haskell.org/trac/ghc/ticket/11744 - , builder (Configure ".") ? System.os == "darwin" ? - arg "--with-nm=$(xcrun --find nm-classic)" ] + , "--host=" ++ targetPlatform ] ] From git at git.haskell.org Fri Oct 27 00:50:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use xcode8 image (b3339d4) Message-ID: <20171027005007.229AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3339d475a56c2c1617bb5803e742509eb2b6821/ghc >--------------------------------------------------------------- commit b3339d475a56c2c1617bb5803e742509eb2b6821 Author: Andrey Mokhov Date: Thu Apr 27 01:08:41 2017 +0100 Use xcode8 image >--------------------------------------------------------------- b3339d475a56c2c1617bb5803e742509eb2b6821 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index f6eda04..dd6af26 100644 --- a/.travis.yml +++ b/.travis.yml @@ -16,6 +16,7 @@ matrix: - PATH="/opt/cabal/1.22/bin:$PATH" - os: osx + osx_image: xcode8 env: MODE="--flavour=quickest --integer-simple" before_install: - brew update From git at git.haskell.org Fri Oct 27 00:50:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Rules.Resources, move packageDb resource to buildRules. (2fc7bd3) Message-ID: <20171027005007.A195C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2fc7bd3ee96d07862b240e8ddcfb584de56a040c/ghc >--------------------------------------------------------------- commit 2fc7bd3ee96d07862b240e8ddcfb584de56a040c Author: Andrey Mokhov Date: Mon Feb 15 23:20:41 2016 +0000 Drop Rules.Resources, move packageDb resource to buildRules. >--------------------------------------------------------------- 2fc7bd3ee96d07862b240e8ddcfb584de56a040c shaking-up-ghc.cabal | 1 - src/Rules.hs | 26 ++++++++++++++++---------- src/Rules/Compile.hs | 11 +++++------ src/Rules/Dependencies.hs | 5 ++--- src/Rules/Register.hs | 7 +++---- src/Rules/Resources.hs | 17 ----------------- 6 files changed, 26 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2fc7bd3ee96d07862b240e8ddcfb584de56a040c From git at git.haskell.org Fri Oct 27 00:50:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename runHaskell wrapper to runGhc for consistency (c4e2e45) Message-ID: <20171027005010.951C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4e2e45be2e11e5785b033ab10511455c2dd00fc/ghc >--------------------------------------------------------------- commit c4e2e45be2e11e5785b033ab10511455c2dd00fc Author: Andrey Mokhov Date: Thu Apr 27 21:39:41 2017 +0100 Rename runHaskell wrapper to runGhc for consistency See #305 >--------------------------------------------------------------- c4e2e45be2e11e5785b033ab10511455c2dd00fc hadrian.cabal | 1 + src/Rules/Program.hs | 4 ++-- src/Rules/Wrappers/{Runhaskell.hs => RunGhc.hs} | 8 ++++---- 3 files changed, 7 insertions(+), 6 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index fd6c036..15c3a2b 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -66,6 +66,7 @@ executable hadrian , Rules.Test , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg + , Rules.Wrappers.RunGhc , Settings , Settings.Builders.Alex , Settings.Builders.Ar diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 71fb8b7..62d4b24 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -12,7 +12,7 @@ import Oracles.ModuleFiles import Oracles.PackageData import Rules.Wrappers.Ghc import Rules.Wrappers.GhcPkg -import Rules.Wrappers.Runhaskell +import Rules.Wrappers.RunGhc import Settings import Settings.Path import Target @@ -26,7 +26,7 @@ type Wrapper = FilePath -> Expr String wrappers :: [(Context, Wrapper)] wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) - , (vanillaContext Stage1 runGhc, runhaskellWrapper) + , (vanillaContext Stage1 runGhc, runGhcWrapper) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper) ] buildProgram :: [(Resource, Int)] -> Context -> Rules () diff --git a/src/Rules/Wrappers/Runhaskell.hs b/src/Rules/Wrappers/RunGhc.hs similarity index 59% rename from src/Rules/Wrappers/Runhaskell.hs rename to src/Rules/Wrappers/RunGhc.hs index 521b41a..95b5700 100644 --- a/src/Rules/Wrappers/Runhaskell.hs +++ b/src/Rules/Wrappers/RunGhc.hs @@ -1,12 +1,12 @@ -module Rules.Wrappers.Runhaskell (runhaskellWrapper) where +module Rules.Wrappers.RunGhc (runGhcWrapper) where import Base import Expression import Oracles.Path -runhaskellWrapper :: FilePath -> Expr String -runhaskellWrapper program = do - lift $ need [sourcePath -/- "Rules/Wrappers/Runhaskell.hs"] +runGhcWrapper :: FilePath -> Expr String +runGhcWrapper program = do + lift $ need [sourcePath -/- "Rules/Wrappers/RunGhc.hs"] top <- getTopDirectory return $ unlines [ "#!/bin/bash" From git at git.haskell.org Fri Oct 27 00:50:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop GranSim way unit. (de8ca62) Message-ID: <20171027005011.146303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de8ca62e36c5202e8e430c6649313228f529d226/ghc >--------------------------------------------------------------- commit de8ca62e36c5202e8e430c6649313228f529d226 Author: Andrey Mokhov Date: Tue Feb 16 00:01:47 2016 +0000 Drop GranSim way unit. >--------------------------------------------------------------- de8ca62e36c5202e8e430c6649313228f529d226 src/Settings/Builders/Ghc.hs | 1 - src/Way.hs | 7 +------ 2 files changed, 1 insertion(+), 7 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 51fde7f..96737f4 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -102,7 +102,6 @@ wayGhcArgs = do , (Profiling `wayUnit` way) ? arg "-prof" , (Logging `wayUnit` way) ? arg "-eventlog" , (Parallel `wayUnit` way) ? arg "-parallel" - , (GranSim `wayUnit` way) ? arg "-gransim" , (way == debug || way == debugDynamic) ? append ["-ticky", "-DTICKY_TICKY"] ] diff --git a/src/Way.hs b/src/Way.hs index a301afe..59bbbc9 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, wayFromUnits, - vanilla, profiling, logging, parallel, granSim, + vanilla, profiling, logging, parallel, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, @@ -27,7 +27,6 @@ data WayUnit = Threaded | Logging | Dynamic | Parallel - | GranSim deriving (Eq, Enum, Bounded) -- TODO: get rid of non-derived Show instances @@ -39,7 +38,6 @@ instance Show WayUnit where Logging -> "l" Dynamic -> "dyn" Parallel -> "mp" - GranSim -> "gm" instance Read WayUnit where readsPrec _ s = [(unit, "") | unit <- [minBound ..], show unit == s] @@ -96,9 +94,6 @@ logging = wayFromUnits [Logging] parallel :: Way parallel = wayFromUnits [Parallel] -granSim :: Way -granSim = wayFromUnits [GranSim] - -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? -- See compiler/main/DynFlags.hs. From git at git.haskell.org Fri Oct 27 00:50:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (6a9772a) Message-ID: <20171027005003.71B5E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a9772a11c4bb3284cf6f3993c4ba25896301a74/ghc >--------------------------------------------------------------- commit 6a9772a11c4bb3284cf6f3993c4ba25896301a74 Author: Andrey Mokhov Date: Sun Feb 14 23:42:17 2016 +0000 Minor revision. >--------------------------------------------------------------- 6a9772a11c4bb3284cf6f3993c4ba25896301a74 src/Main.hs | 1 + src/Rules.hs | 62 ++++++++++++++++++++++++++++++------------------------------ 2 files changed, 32 insertions(+), 31 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 96639d2..cf45cc3 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -27,6 +27,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do Rules.Test.testRules Rules.buildRules Rules.topLevelTargets + options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Rules.hs b/src/Rules.hs index e817fc1..f3db558 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,20 +5,20 @@ import Data.Foldable import Base import Expression import GHC -import qualified Rules.Compile -import qualified Rules.Data -import qualified Rules.Dependencies -import qualified Rules.Documentation -import qualified Rules.Generate -import qualified Rules.Resources -import qualified Rules.Cabal -import qualified Rules.Gmp -import qualified Rules.Libffi -import qualified Rules.Library -import qualified Rules.Perl -import qualified Rules.Program -import qualified Rules.Register -import qualified Rules.Setup +import Rules.Compile +import Rules.Data +import Rules.Dependencies +import Rules.Documentation +import Rules.Generate +import Rules.Resources +import Rules.Cabal +import Rules.Gmp +import Rules.Libffi +import Rules.Library +import Rules.Perl +import Rules.Program +import Rules.Register +import Rules.Setup import Settings allStages :: [Stage] @@ -53,26 +53,26 @@ topLevelTargets = do packageRules :: Rules () packageRules = do - resources <- Rules.Resources.resourceRules + resources <- resourceRules for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package - Rules.Compile.compilePackage resources context - Rules.Data.buildPackageData context - Rules.Dependencies.buildPackageDependencies resources context - Rules.Documentation.buildPackageDocumentation context - Rules.Generate.generatePackageCode context - Rules.Library.buildPackageLibrary context - Rules.Program.buildProgram context - Rules.Register.registerPackage resources context + compilePackage resources context + buildPackageData context + buildPackageDependencies resources context + buildPackageDocumentation context + generatePackageCode context + buildPackageLibrary context + buildProgram context + registerPackage resources context buildRules :: Rules () buildRules = do - Rules.Cabal.cabalRules - Rules.Generate.generateRules - Rules.Generate.copyRules - Rules.Gmp.gmpRules - Rules.Libffi.libffiRules - Rules.Perl.perlScriptRules - Rules.Setup.setupRules - Rules.packageRules + cabalRules + generateRules + copyRules + gmpRules + libffiRules + perlScriptRules + setupRules + packageRules From git at git.haskell.org Fri Oct 27 00:50:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable some warnings (#307) (3ea149a) Message-ID: <20171027005014.13FE23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ea149adad2311ea711bc58950e288d081fde79a/ghc >--------------------------------------------------------------- commit 3ea149adad2311ea711bc58950e288d081fde79a Author: Zhen Zhang Date: Fri Apr 28 23:28:04 2017 +0800 Disable some warnings (#307) >--------------------------------------------------------------- 3ea149adad2311ea711bc58950e288d081fde79a src/Settings/Default.hs | 42 +++++++++++++++++++++++++++++++++++++++++- 1 file changed, 41 insertions(+), 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index d242502..90e2db0 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -215,6 +215,43 @@ defaultBuilderArgs = mconcat , makeBuilderArgs , tarBuilderArgs ] +-- | Disable some warnings in packages we use +-- | https://github.com/ghc/ghc/blob/master/mk/warnings.mk#L46 +disableWarningArgsStage0 :: Args +disableWarningArgsStage0 = stage Stage0 ? builder Ghc ? mconcat + [ package transformers ? append [ "-fno-warn-unused-matches", "-fno-warn-unused-imports" ] + , package terminfo ? append [ "-fno-warn-unused-imports" ] ] + +disableWarningArgsStage1 :: Args +disableWarningArgsStage1 = notStage0 ? builder Ghc ? mconcat + [ package bytestring ? append [ "-Wno-inline-rule-shadowing" ] + , package haddock ? append [ "-Wno-unused-imports", "-Wno-deprecations" ] + , package directory ? append [ "-Wno-unused-imports" ] + , package binary ? append [ "-Wno-deprecations" ] + , package haskeline ? append [ "-Wno-deprecations", "-Wno-unused-imports", + "-Wno-redundant-constraints", + "-Wno-simplifiable-class-constraints" ] + , package pretty ? append [ "-Wno-unused-imports" ] + , package primitive ? append [ "-Wno-unused-imports", "-Wno-deprecations" ] + , package terminfo ? append [ "-Wno-unused-imports" ] + , package xhtml ? append [ "-Wno-unused-imports", "-Wno-tabs" ] + , package transformers ? append [ "-Wno-unused-matches", "-Wno-unused-imports", + "-Wno-redundant-constraints", "-Wno-orphans" ] + , package base ? append [ "-Wno-trustworthy-safe" ] + , package ghcPrim ? append [ "-Wno-trustworthy-safe" ] + , package win32 ? append [ "-Wno-trustworthy-safe" ] ] + +-- GhcLibExtraHcOpts += -Wno-deprecated-flags +-- GhcBootLibExtraHcOpts += -fno-warn-deprecated-flags +disableWarningArgsLibs :: Args +disableWarningArgsLibs = do + pkg <- getPackage + isLibrary pkg ? builder Ghc ? mconcat + [ notStage0 ? arg "-Wno-deprecated-flags" + , stage Stage0 ? arg "-fno-warn-deprecated-flags"] + +-- TODO: Disable warnings for Windows specifics + -- | All 'Package'-dependent command line arguments. defaultPackageArgs :: Args defaultPackageArgs = mconcat @@ -227,4 +264,7 @@ defaultPackageArgs = mconcat , haddockPackageArgs , integerGmpPackageArgs , rtsPackageArgs - , runGhcPackageArgs ] + , runGhcPackageArgs + , disableWarningArgsStage0 + , disableWarningArgsStage1 + , disableWarningArgsLibs ] From git at git.haskell.org Fri Oct 27 00:50:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Werror to CC and HC (#309) (4952e80) Message-ID: <20171027005017.AE8813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4952e8022f805d31035c3ecfd354518c72d07557/ghc >--------------------------------------------------------------- commit 4952e8022f805d31035c3ecfd354518c72d07557 Author: Zhen Zhang Date: Wed May 3 08:58:34 2017 -0700 Add Werror to CC and HC (#309) >--------------------------------------------------------------- 4952e8022f805d31035c3ecfd354518c72d07557 src/Settings/Builders/Cc.hs | 5 ++++- src/Settings/Default.hs | 16 +++++++++++++++- src/Settings/Packages/GhcPrim.hs | 1 + src/Settings/Packages/Rts.hs | 4 +++- 4 files changed, 23 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index b5d85df..38a1665 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -8,7 +8,10 @@ ccBuilderArgs = builder Cc ? mconcat , argSettingList . ConfCcArgs =<< getStage , cIncludeArgs - , builder (Cc CompileC) ? mconcat [ arg "-c", arg =<< getInput + , builder (Cc CompileC) ? mconcat [ arg "-Werror" + -- mk/warning.mk: + -- SRC_CC_OPTS += -Wall $(WERROR) + , arg "-c", arg =<< getInput , arg "-o", arg =<< getOutput ] , builder (Cc FindCDependencies) ? do diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 90e2db0..619fca1 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -65,10 +65,24 @@ defaultArgs = mconcat , sourceArgs defaultSourceArgs , defaultPackageArgs ] +-- | Default flags about Werror +-- | mk/warnings.mk +defaultErrorGhcFlags :: Args +defaultErrorGhcFlags = + mconcat [ notStage0 ? arg "-Werror" + , (not <$> flag GccIsClang) ? mconcat [ + (not <$> flag GccLt46) ? (not <$> windowsHost) ? + arg "-Werror=unused-but-set-variable" + , (not <$> flag GccLt44) ? arg "-Wno-error=inline" ] + , flag GccIsClang ? arg "-Wno-unknown-pragmas" ] + -- | Default source arguments, e.g. optimisation settings. defaultSourceArgs :: SourceArgs defaultSourceArgs = SourceArgs - { hsDefault = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2", arg "-H32m"] + { hsDefault = mconcat [ stage0 ? arg "-O" + , notStage0 ? arg "-O2" + , arg "-H32m" + , defaultErrorGhcFlags ] , hsLibrary = mempty , hsCompiler = mempty , hsGhc = mempty } diff --git a/src/Settings/Packages/GhcPrim.hs b/src/Settings/Packages/GhcPrim.hs index bed8345..af3c0d5 100644 --- a/src/Settings/Packages/GhcPrim.hs +++ b/src/Settings/Packages/GhcPrim.hs @@ -10,4 +10,5 @@ ghcPrimPackageArgs = package ghcPrim ? mconcat , builder (Cc CompileC) ? (not <$> flag GccLt44) ? + (not <$> flag GccIsClang) ? input "//cbits/atomic.c" ? arg "-Wno-sync-nand" ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 6855402..e278204 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -89,7 +89,9 @@ rtsPackageArgs = package rts ? do , inputs ["//Evac.c", "//Evac_thr.c"] ? arg "-funroll-loops" , inputs ["//Evac_thr.c", "//Scav_thr.c"] ? - append [ "-DPARALLEL_GC", "-Irts/sm" ] ] + append [ "-DPARALLEL_GC", "-Irts/sm" ] + + , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr" ] , builder Ghc ? arg "-Irts" From git at git.haskell.org Fri Oct 27 00:50:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do not hide Shake.parallel (we no longer have conflicting Way.parallel). (cfb1331) Message-ID: <20171027005018.2163D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cfb1331d6c0f338fb3998c6fd3a25759fbd9f4c9/ghc >--------------------------------------------------------------- commit cfb1331d6c0f338fb3998c6fd3a25759fbd9f4c9 Author: Andrey Mokhov Date: Tue Feb 16 00:08:25 2016 +0000 Do not hide Shake.parallel (we no longer have conflicting Way.parallel). >--------------------------------------------------------------- cfb1331d6c0f338fb3998c6fd3a25759fbd9f4c9 src/Base.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 464c1c9..1a06120 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel - module Base ( -- * General utilities module Control.Applicative, @@ -35,7 +33,7 @@ import Data.Function import Data.List.Extra import Data.Maybe import Data.Monoid -import Development.Shake hiding (parallel, unit, (*>), Normal) +import Development.Shake hiding (unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Fri Oct 27 00:50:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add copyFileUntracked (#313) (bc32262) Message-ID: <20171027005021.9628E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc32262d3aa0e6586daee0c0d6edef98310ebe98/ghc >--------------------------------------------------------------- commit bc32262d3aa0e6586daee0c0d6edef98310ebe98 Author: Zhen Zhang Date: Tue May 16 13:13:17 2017 -0700 Add copyFileUntracked (#313) >--------------------------------------------------------------- bc32262d3aa0e6586daee0c0d6edef98310ebe98 src/Rules/Libffi.hs | 4 ++-- src/Util.hs | 12 ++++++++++-- 2 files changed, 12 insertions(+), 4 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 99b77c8..57f6263 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -39,7 +39,7 @@ configureEnvironment = do libffiRules :: Rules () libffiRules = do - libffiDependencies &%> \_ -> do + (libffiLibrary : libffiDependencies) &%> \_ -> do useSystemFfi <- flag UseSystemFfi if useSystemFfi then do @@ -57,7 +57,7 @@ libffiRules = do ways <- interpretInContext libffiContext (getLibraryWays <> getRtsWays) forM_ (nubOrd ways) $ \way -> - copyFile libffiLibrary =<< rtsLibffiLibrary way + copyFileUntracked libffiLibrary =<< rtsLibffiLibrary way putSuccess $ "| Successfully built custom library 'libffi'" diff --git a/src/Util.hs b/src/Util.hs index b6d9536..1fd19f8 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -3,7 +3,7 @@ module Util ( removeFile, copyDirectory, copyDirectoryContents, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, makeExecutable, renderProgram, renderLibrary, Match(..), builderEnvironment, - needBuilder + needBuilder, copyFileUntracked ) where import qualified System.Directory.Extra as IO @@ -94,10 +94,18 @@ copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. let dir = takeDirectory target - unlessM (liftIO $ IO.doesDirectoryExist dir) $ createDirectory dir + liftIO $ IO.createDirectoryIfMissing True dir putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target +-- Same as copyFile, but not tracking the source as a build dependency +copyFileUntracked :: FilePath -> FilePath -> Action () +copyFileUntracked source target = do + let dir = takeDirectory target + liftIO $ IO.createDirectoryIfMissing True dir + putProgressInfo $ renderAction "Copy file (Untracked)" source target + liftIO $ IO.copyFile source target + -- | Move a file; we cannot track the source, because it is moved. moveFile :: FilePath -> FilePath -> Action () moveFile source target = do From git at git.haskell.org Fri Oct 27 00:50:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Parallel way unit. (49a7cb2) Message-ID: <20171027005014.932AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49a7cb2fb676a1b0a7a9b4235aaa198b9ce0d8db/ghc >--------------------------------------------------------------- commit 49a7cb2fb676a1b0a7a9b4235aaa198b9ce0d8db Author: Andrey Mokhov Date: Tue Feb 16 00:04:46 2016 +0000 Drop Parallel way unit. >--------------------------------------------------------------- 49a7cb2fb676a1b0a7a9b4235aaa198b9ce0d8db src/Settings/Builders/Ghc.hs | 1 - src/Way.hs | 8 +------- 2 files changed, 1 insertion(+), 8 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 96737f4..ef3130f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -101,7 +101,6 @@ wayGhcArgs = do , (Debug `wayUnit` way) ? arg "-optc-DDEBUG" , (Profiling `wayUnit` way) ? arg "-prof" , (Logging `wayUnit` way) ? arg "-eventlog" - , (Parallel `wayUnit` way) ? arg "-parallel" , (way == debug || way == debugDynamic) ? append ["-ticky", "-DTICKY_TICKY"] ] diff --git a/src/Way.hs b/src/Way.hs index 59bbbc9..6d034e9 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,7 +1,7 @@ module Way ( WayUnit (..), Way, wayUnit, wayFromUnits, - vanilla, profiling, logging, parallel, + vanilla, profiling, logging, threaded, threadedProfiling, threadedLogging, debug, debugProfiling, threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, threadedProfilingDynamic, @@ -26,7 +26,6 @@ data WayUnit = Threaded | Profiling | Logging | Dynamic - | Parallel deriving (Eq, Enum, Bounded) -- TODO: get rid of non-derived Show instances @@ -37,7 +36,6 @@ instance Show WayUnit where Profiling -> "p" Logging -> "l" Dynamic -> "dyn" - Parallel -> "mp" instance Read WayUnit where readsPrec _ s = [(unit, "") | unit <- [minBound ..], show unit == s] @@ -90,10 +88,6 @@ profiling = wayFromUnits [Profiling] logging :: Way logging = wayFromUnits [Logging] --- | Build in parallel. -parallel :: Way -parallel = wayFromUnits [Parallel] - -- RTS only ways -- TODO: do we need to define *only* these? Shall we generalise/simplify? -- See compiler/main/DynFlags.hs. From git at git.haskell.org Fri Oct 27 00:50:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix separation into full and RTS-only ways, add comments. (799b809) Message-ID: <20171027005022.08D3F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/799b8090941e4c0e9c601890a480511052e36f8f/ghc >--------------------------------------------------------------- commit 799b8090941e4c0e9c601890a480511052e36f8f Author: Andrey Mokhov Date: Tue Feb 16 00:31:32 2016 +0000 Fix separation into full and RTS-only ways, add comments. >--------------------------------------------------------------- 799b8090941e4c0e9c601890a480511052e36f8f src/Way.hs | 42 ++++++++++++++++++++++++------------------ 1 file changed, 24 insertions(+), 18 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index 6d034e9..01b18d2 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -76,7 +76,7 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b --- | Build with no 'WayUnit's at all. +-- | Build default _vanilla_ way. vanilla :: Way vanilla = wayFromUnits [] @@ -84,33 +84,39 @@ vanilla = wayFromUnits [] profiling :: Way profiling = wayFromUnits [Profiling] --- | Build with logging. +-- | Build with dynamic linking. +dynamic :: Way +dynamic = wayFromUnits [Dynamic] + +-- RTS only ways. See compiler/main/DynFlags.hs. +-- | Build RTS with event logging. logging :: Way logging = wayFromUnits [Logging] --- RTS only ways --- TODO: do we need to define *only* these? Shall we generalise/simplify? --- See compiler/main/DynFlags.hs. -threaded, threadedProfiling, threadedLogging, debug, debugProfiling, - threadedDebug, threadedDebugProfiling, dynamic, profilingDynamic, - threadedProfilingDynamic, threadedDynamic, threadedDebugDynamic, - debugDynamic, loggingDynamic, threadedLoggingDynamic :: Way +-- | Build multithreaded RTS. +threaded :: Way +threaded = wayFromUnits [Threaded] + +-- | Build RTS with debug information. +debug :: Way +debug = wayFromUnits [Debug] -threaded = wayFromUnits [Threaded] +threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, + threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, + threadedLoggingDynamic, debugProfiling, debugDynamic, profilingDynamic, + loggingDynamic :: Way +threadedDebug = wayFromUnits [Threaded, Debug] threadedProfiling = wayFromUnits [Threaded, Profiling] threadedLogging = wayFromUnits [Threaded, Logging] -debug = wayFromUnits [Debug] -debugProfiling = wayFromUnits [Debug, Profiling] -threadedDebug = wayFromUnits [Threaded, Debug] -threadedDebugProfiling = wayFromUnits [Threaded, Debug, Profiling] -dynamic = wayFromUnits [Dynamic] -profilingDynamic = wayFromUnits [Profiling, Dynamic] -threadedProfilingDynamic = wayFromUnits [Threaded, Profiling, Dynamic] threadedDynamic = wayFromUnits [Threaded, Dynamic] +threadedDebugProfiling = wayFromUnits [Threaded, Debug, Profiling] threadedDebugDynamic = wayFromUnits [Threaded, Debug, Dynamic] +threadedProfilingDynamic = wayFromUnits [Threaded, Profiling, Dynamic] +threadedLoggingDynamic = wayFromUnits [Threaded, Logging, Dynamic] +debugProfiling = wayFromUnits [Debug, Profiling] debugDynamic = wayFromUnits [Debug, Dynamic] +profilingDynamic = wayFromUnits [Profiling, Dynamic] loggingDynamic = wayFromUnits [Logging, Dynamic] -threadedLoggingDynamic = wayFromUnits [Threaded, Logging, Dynamic] wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" From git at git.haskell.org Fri Oct 27 00:50:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CABAL_VERSION argument in building ghc-cabal (#319) (1fd9854) Message-ID: <20171027005025.4BE753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fd9854b798e2a003649baa6cfcc76c9150c0421/ghc >--------------------------------------------------------------- commit 1fd9854b798e2a003649baa6cfcc76c9150c0421 Author: Zhen Zhang Date: Mon Jun 5 18:54:54 2017 +0800 Fix CABAL_VERSION argument in building ghc-cabal (#319) >--------------------------------------------------------------- 1fd9854b798e2a003649baa6cfcc76c9150c0421 src/Settings/Packages/GhcCabal.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 8e5837c..3c830ae 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -1,9 +1,17 @@ module Settings.Packages.GhcCabal (ghcCabalPackageArgs) where +import Distribution.PackageDescription.Parse + import Base import GHC import Oracles.Config.Setting import Predicate +import Package (pkgCabalFile) +import Distribution.Verbosity (silent) +import Distribution.Text (display) +import Distribution.Package (pkgVersion) +import Distribution.PackageDescription (packageDescription) +import qualified Distribution.PackageDescription as DP ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do @@ -12,10 +20,17 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do win <- lift windowsHost let cabalDeps = [ array, base, bytestring, containers, deepseq, directory , pretty, process, time, if win then win32 else unix ] + + lift $ need [pkgCabalFile cabal] + pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile cabal + let identifier = DP.package . packageDescription $ pd + cabalVersion = display . pkgVersion $ identifier + mconcat [ append [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , arg "--make" , arg "-j" + , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" , arg "-DGENERICS" From git at git.haskell.org Fri Oct 27 00:50:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move profilingDynamic to full ways. (3c88f16) Message-ID: <20171027005025.A942A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c88f16cf2ff282481a06abcf0ad839abe1c5fab/ghc >--------------------------------------------------------------- commit 3c88f16cf2ff282481a06abcf0ad839abe1c5fab Author: Andrey Mokhov Date: Tue Feb 16 00:44:44 2016 +0000 Move profilingDynamic to full ways. >--------------------------------------------------------------- 3c88f16cf2ff282481a06abcf0ad839abe1c5fab src/Settings/Ways.hs | 1 + src/Way.hs | 11 +++++++---- 2 files changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 223bc79..0fee897 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -13,6 +13,7 @@ getLibraryWays = fromDiffExpr $ defaultLibraryWays <> userLibraryWays getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays +-- TODO: what about profilingDynamic way? Do we need platformSupportsSharedLibs? -- These are default ways for library packages: -- * We always build 'vanilla' way. -- * We build 'profiling' way when stage > Stage0. diff --git a/src/Way.hs b/src/Way.hs index 01b18d2..b297e79 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -88,7 +88,11 @@ profiling = wayFromUnits [Profiling] dynamic :: Way dynamic = wayFromUnits [Dynamic] --- RTS only ways. See compiler/main/DynFlags.hs. +-- | Build with profiling and dynamic linking. +profilingDynamic :: Way +profilingDynamic = wayFromUnits [Profiling, Dynamic] + +-- RTS only ways below. See compiler/main/DynFlags.hs. -- | Build RTS with event logging. logging :: Way logging = wayFromUnits [Logging] @@ -101,10 +105,10 @@ threaded = wayFromUnits [Threaded] debug :: Way debug = wayFromUnits [Debug] +-- | Various combinations of RTS only ways. threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, - threadedLoggingDynamic, debugProfiling, debugDynamic, profilingDynamic, - loggingDynamic :: Way + threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic :: Way threadedDebug = wayFromUnits [Threaded, Debug] threadedProfiling = wayFromUnits [Threaded, Profiling] threadedLogging = wayFromUnits [Threaded, Logging] @@ -115,7 +119,6 @@ threadedProfilingDynamic = wayFromUnits [Threaded, Profiling, Dynamic] threadedLoggingDynamic = wayFromUnits [Threaded, Logging, Dynamic] debugProfiling = wayFromUnits [Debug, Profiling] debugDynamic = wayFromUnits [Debug, Dynamic] -profilingDynamic = wayFromUnits [Profiling, Dynamic] loggingDynamic = wayFromUnits [Logging, Dynamic] wayPrefix :: Way -> String From git at git.haskell.org Fri Oct 27 00:50:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more utilities including install and symbolic link (#316) (8299d14) Message-ID: <20171027005029.086BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8299d146c112c16c528b3681a6e4404eb47c6375/ghc >--------------------------------------------------------------- commit 8299d146c112c16c528b3681a6e4404eb47c6375 Author: Zhen Zhang Date: Tue Jun 6 08:53:14 2017 +0800 Add more utilities including install and symbolic link (#316) >--------------------------------------------------------------- 8299d146c112c16c528b3681a6e4404eb47c6375 cfg/system.config.in | 15 +++++++++++++ src/Oracles/Config/Setting.hs | 50 ++++++++++++++++++++++++++++++++++++++++++- src/Util.hs | 44 ++++++++++++++++++++++++++++++++++++- 3 files changed, 107 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 667a22d..56a7c7f 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -22,6 +22,7 @@ system-ghc-pkg = @GhcPkgCmd@ tar = @TarCmd@ patch = @PatchCmd@ perl = @PerlCmd@ +ln-s = @LN_S@ # Information about builders: #============================ @@ -117,3 +118,17 @@ ffi-lib-dir = @FFILibDir@ #======================= with-libdw = @UseLibdw@ + +# Installation: +#======================= + +install-prefix = @prefix@ +install-bindir = @prefix@/bin +install-libdir = @prefix@/lib +install-datarootdir = @prefix@/share + +install = @INSTALL@ +install-program = @INSTALL@ -m 755 +install-script = @INSTALL@ -m 755 +install-data = @INSTALL@ -m 644 +install-dir = @INSTALL@ -m 755 -d diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 0b28112..8bdc387 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -2,7 +2,8 @@ module Oracles.Config.Setting ( Setting (..), SettingList (..), setting, settingList, getSetting, getSettingList, anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, - ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost + ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost, + relocatableBuild, installDocDir, installGhcLibDir ) where import Control.Monad.Trans.Reader @@ -51,6 +52,19 @@ data Setting = BuildArch | GmpLibDir | IconvIncludeDir | IconvLibDir + -- Paths to where GHC is installed + | InstallPrefix + | InstallBinDir + | InstallLibDir + | InstallDataRootDir + -- "install" utility + | Install + | InstallData + | InstallProgram + | InstallScript + | InstallDir + -- symbolic link + | LnS data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -94,6 +108,16 @@ setting key = unsafeAskConfig $ case key of GmpLibDir -> "gmp-lib-dir" IconvIncludeDir -> "iconv-include-dir" IconvLibDir -> "iconv-lib-dir" + InstallPrefix -> "install-prefix" + InstallBinDir -> "install-bindir" + InstallLibDir -> "install-libdir" + InstallDataRootDir -> "install-datarootdir" + Install -> "install" + InstallDir -> "install-dir" + InstallProgram -> "install-program" + InstallScript -> "install-script" + InstallData -> "install-data" + LnS -> "ln-s" settingList :: SettingList -> Action [String] settingList key = fmap words $ unsafeAskConfig $ case key of @@ -173,3 +197,27 @@ cmdLineLengthLimit = do (False, True) -> 200000 -- On all other systems, we try this: _ -> 4194304 -- Cabal library needs a bit more than 2MB! + +-- | On Windows we normally want to make a relocatable bindist, +-- to we ignore flags like libdir +-- ref: mk/config.mk.in:232 +relocatableBuild :: Action Bool +relocatableBuild = windowsHost + +installDocDir :: Action String +installDocDir = do + version <- setting ProjectVersion + (-/- ("doc/ghc-" ++ version)) <$> setting InstallDataRootDir + +-- | Unix: override libdir and datadir to put ghc-specific stuff in +-- a subdirectory with the version number included. +-- ref: mk/install.mk:101 +-- TODO: CroosCompilePrefix +installGhcLibDir :: Action String +installGhcLibDir = do + r <- relocatableBuild + libdir <- setting InstallLibDir + if r then return libdir + else do + v <- setting ProjectVersion + return (libdir -/- ("ghc-" ++ v)) diff --git a/src/Util.hs b/src/Util.hs index 1fd19f8..a7310be 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -3,7 +3,8 @@ module Util ( removeFile, copyDirectory, copyDirectoryContents, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, makeExecutable, renderProgram, renderLibrary, Match(..), builderEnvironment, - needBuilder, copyFileUntracked + needBuilder, copyFileUntracked, installDir, installData, installScript, + installProgram, linkSymbolic ) where import qualified System.Directory.Extra as IO @@ -18,6 +19,7 @@ import GHC import Oracles.ArgsHash import Oracles.DirectoryContents import Oracles.Path +import Oracles.Config.Setting import Settings import Settings.Builders.Ar import Target @@ -169,6 +171,46 @@ applyPatch dir patch = do putBuild $ "| Apply patch " ++ file quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] +-- | Install a directory +installDir :: FilePath -> Action () +installDir dir = do + i <- setting InstallDir + putBuild $ "| Install directory" ++ dir + quietly $ cmd i dir + +-- | Install data file to a directory +installData :: [FilePath] -> FilePath -> Action () +installData fs dir = do + i <- setting InstallData + forM_ fs $ \f -> + putBuild $ "| Install data " ++ f ++ " to " ++ dir + quietly $ cmd i fs dir + +-- | Install executable file to a directory +installProgram :: FilePath -> FilePath -> Action () +installProgram f dir = do + i <- setting InstallProgram + putBuild $ "| Install program " ++ f ++ " to " ++ dir + quietly $ cmd i f dir + +-- | Install executable script to a directory +installScript :: FilePath -> FilePath -> Action () +installScript f dir = do + i <- setting InstallScript + putBuild $ "| Install script " ++ f ++ " to " ++ dir + quietly $ cmd i f dir + +-- | Create a symbolic link from source file to target file when supported +linkSymbolic :: FilePath -> FilePath -> Action () +linkSymbolic source target = do + lns <- setting LnS + when (lns /= "") $ do + need [source] -- Guarantee source is built before printing progress info. + let dir = takeDirectory target + liftIO $ IO.createDirectoryIfMissing True dir + putProgressInfo $ renderAction "Create symbolic link" source target + quietly $ cmd lns source target + isInternal :: Builder -> Bool isInternal = isJust . builderProvenance From git at git.haskell.org Fri Oct 27 00:50:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add allWays. (575d82f) Message-ID: <20171027005029.55B8D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/575d82fe621956b8a6c293eb381a19896aed2366/ghc >--------------------------------------------------------------- commit 575d82fe621956b8a6c293eb381a19896aed2366 Author: Andrey Mokhov Date: Tue Feb 16 00:53:44 2016 +0000 Add allWays. >--------------------------------------------------------------- 575d82fe621956b8a6c293eb381a19896aed2366 src/Way.hs | 22 ++++++++++++++-------- 1 file changed, 14 insertions(+), 8 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index b297e79..668ed63 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,14 +1,12 @@ module Way ( WayUnit (..), Way, wayUnit, wayFromUnits, - vanilla, profiling, logging, - threaded, threadedProfiling, threadedLogging, - debug, debugProfiling, threadedDebug, threadedDebugProfiling, - dynamic, profilingDynamic, threadedProfilingDynamic, - threadedDynamic, threadedDebugDynamic, debugDynamic, - loggingDynamic, threadedLoggingDynamic, - - wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, + vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging, + threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, + threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, + threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic, + + allWays, wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, safeDetectWay, detectWay, matchBuildResult ) where @@ -121,6 +119,14 @@ debugProfiling = wayFromUnits [Debug, Profiling] debugDynamic = wayFromUnits [Debug, Dynamic] loggingDynamic = wayFromUnits [Logging, Dynamic] +-- | All ways supported by the build system. +allWays :: [Way] +allWays = + [ vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging + , threadedDebug, threadedProfiling, threadedLogging, threadedDynamic + , threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic + , threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic ] + wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" From git at git.haskell.org Fri Oct 27 00:50:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compute cabalDeps in GhcCabal build (#320) (0589a9e) Message-ID: <20171027005032.7BE1F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c/ghc >--------------------------------------------------------------- commit 0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c Author: Zhen Zhang Date: Tue Jun 6 23:46:11 2017 +0800 Compute cabalDeps in GhcCabal build (#320) >--------------------------------------------------------------- 0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c src/Oracles/Dependencies.hs | 9 ++++++++- src/Settings/Packages/GhcCabal.hs | 7 ++----- 2 files changed, 10 insertions(+), 6 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 2d6a404..167047d 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,6 +1,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Dependencies ( - fileDependencies, contextDependencies, needContext, dependenciesOracles + fileDependencies, contextDependencies, needContext, dependenciesOracles, + pkgDependencies ) where import qualified Data.HashMap.Strict as Map @@ -47,6 +48,12 @@ contextDependencies context at Context {..} = do pkgs <- sort <$> interpretInContext (pkgContext package) getPackages return . map pkgContext $ intersectOrd (compare . pkgNameString) pkgs deps +-- | Given a `Package`, this `Action` looks up its package dependencies +-- 'Settings.Paths.packageDependencies' using 'packageDependenciesOracle' +-- The context will be the vanilla context with stage equal to 1 +pkgDependencies :: Package -> Action [Package] +pkgDependencies = fmap (map Context.package) . contextDependencies . vanillaContext Stage1 + -- | Coarse-grain 'need': make sure given contexts are fully built. needContext :: [Context] -> Action () needContext cs = do diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 3c830ae..57147e4 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -5,6 +5,7 @@ import Distribution.PackageDescription.Parse import Base import GHC import Oracles.Config.Setting +import Oracles.Dependencies (pkgDependencies) import Predicate import Package (pkgCabalFile) import Distribution.Verbosity (silent) @@ -15,12 +16,8 @@ import qualified Distribution.PackageDescription as DP ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do - -- Note: We could compute 'cabalDeps' instead of hard-coding it but this - -- seems unnecessary since we plan to drop @ghc-cabal@ altogether, #18. win <- lift windowsHost - let cabalDeps = [ array, base, bytestring, containers, deepseq, directory - , pretty, process, time, if win then win32 else unix ] - + cabalDeps <- lift $ pkgDependencies cabal lift $ need [pkgCabalFile cabal] pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile cabal let identifier = DP.package . packageDescription $ pd From git at git.haskell.org Fri Oct 27 00:50:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass way to compilePackage via Context. (23d501a) Message-ID: <20171027005032.BEFC63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23d501a474266920e395e60d4d6c69369785608f/ghc >--------------------------------------------------------------- commit 23d501a474266920e395e60d4d6c69369785608f Author: Andrey Mokhov Date: Tue Feb 16 02:24:35 2016 +0000 Pass way to compilePackage via Context. See #207. >--------------------------------------------------------------- 23d501a474266920e395e60d4d6c69369785608f src/Rules.hs | 10 +++++++--- src/Rules/Compile.hs | 37 ++++++++++++++----------------------- 2 files changed, 21 insertions(+), 26 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index e12fc1c..f765b5e 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -3,6 +3,7 @@ module Rules (topLevelTargets, buildRules) where import Data.Foldable import Base +import Context hiding (stage, package, way) import Expression import GHC import Rules.Compile @@ -52,18 +53,21 @@ topLevelTargets = do packageRules :: Rules () packageRules = do - -- We cannot register multiple packages in parallel. Also we cannot run GHC - -- when the package database is being mutated by "ghc-pkg". This is a + -- We cannot register multiple GHC packages in parallel. Also we cannot run + -- GHC when the package database is being mutated by "ghc-pkg". This is a -- classic concurrent read exclusive write (CREW) conflict. let maxConcurrentReaders = 1000 packageDb <- newResource "package-db" maxConcurrentReaders let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] + let contexts = liftM3 Context allStages knownPackages allWays + + traverse_ (compilePackage readPackageDb) contexts + for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package - compilePackage readPackageDb context buildPackageData context buildPackageDependencies readPackageDb context buildPackageDocumentation context diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index b583f5a..14e71ee 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -9,52 +9,43 @@ import Rules.Actions import Settings import Target hiding (context) --- TODO: Use way from Context, #207 compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" - matchBuildResult buildPath "hi" ?> \hi -> + buildPath "*" <.> hisuf way %> \hi -> if compileInterfaceFilesSeparately && not ("//HpcParser.*" ?== hi) then do - let w = detectWay hi - (src, deps) <- dependencies buildPath $ hi -<.> osuf w + (src, deps) <- dependencies buildPath $ hi -<.> osuf way need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [hi] - else need [ hi -<.> osuf (detectWay hi) ] + buildWithResources rs $ Target context (Ghc stage) [src] [hi] + else need [ hi -<.> osuf way ] - matchBuildResult buildPath "hi-boot" ?> \hiboot -> + buildPath "*" <.> hibootsuf way %> \hiboot -> if compileInterfaceFilesSeparately then do - let w = detectWay hiboot - (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf w + (src, deps) <- dependencies buildPath $ hiboot -<.> obootsuf way need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [hiboot] - else need [ hiboot -<.> obootsuf (detectWay hiboot) ] + buildWithResources rs $ Target context (Ghc stage) [src] [hiboot] + else need [ hiboot -<.> obootsuf way ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) - matchBuildResult buildPath "o" ?> \obj -> do + buildPath "*" <.> osuf way %> \obj -> do (src, deps) <- dependencies buildPath obj if ("//*.c" ?== src) then do need $ src : deps build $ Target context (Gcc stage) [src] [obj] else do - let w = detectWay obj if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) - then need $ (obj -<.> hisuf (detectWay obj)) : src : deps + then need $ (obj -<.> hisuf way) : src : deps else need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [obj] + buildWithResources rs $ Target context (Ghc stage) [src] [obj] -- TODO: get rid of these special cases - matchBuildResult buildPath "o-boot" ?> \obj -> do + buildPath "*" <.> obootsuf way %> \obj -> do (src, deps) <- dependencies buildPath obj - let w = detectWay obj if compileInterfaceFilesSeparately - then need $ (obj -<.> hibootsuf (detectWay obj)) : src : deps + then need $ (obj -<.> hibootsuf way) : src : deps else need $ src : deps - buildWithResources rs $ - Target (context { way = w }) (Ghc stage) [src] [obj] + buildWithResources rs $ Target context (Ghc stage) [src] [obj] From git at git.haskell.org Fri Oct 27 00:50:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix implicit assumption about inplace installation etc. (#315) (02351ac) Message-ID: <20171027005036.04C683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02351ac97f66df4b8c02b0df587e4dde7c4201c8/ghc >--------------------------------------------------------------- commit 02351ac97f66df4b8c02b0df587e4dde7c4201c8 Author: Zhen Zhang Date: Wed Jun 7 09:04:28 2017 +0800 Fix implicit assumption about inplace installation etc. (#315) >--------------------------------------------------------------- 02351ac97f66df4b8c02b0df587e4dde7c4201c8 hadrian.cabal | 5 ++-- src/GHC.hs | 8 +---- src/Rules.hs | 2 +- src/Rules/Cabal.hs | 1 - src/Rules/Clean.hs | 4 +-- src/Rules/Generate.hs | 37 +++++++++++++---------- src/Rules/Generators/GhcSplit.hs | 8 +++-- src/Rules/Program.hs | 34 +++++++++++----------- src/Rules/Register.hs | 2 +- src/Rules/Wrappers.hs | 63 ++++++++++++++++++++++++++++++++++++++++ src/Rules/Wrappers/Ghc.hs | 14 --------- src/Rules/Wrappers/GhcPkg.hs | 19 ------------ src/Rules/Wrappers/RunGhc.hs | 15 ---------- src/Settings/Builders/Common.hs | 2 +- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Install.hs | 14 +++++++++ src/Settings/Path.hs | 39 +++++++++++++++---------- 17 files changed, 154 insertions(+), 116 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 02351ac97f66df4b8c02b0df587e4dde7c4201c8 From git at git.haskell.org Fri Oct 27 00:50:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop workaround for GHC bug #11331. (8478284) Message-ID: <20171027005036.337483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/84782844c149c729e5277f79ee80c8001f05c095/ghc >--------------------------------------------------------------- commit 84782844c149c729e5277f79ee80c8001f05c095 Author: Andrey Mokhov Date: Tue Feb 16 02:26:08 2016 +0000 Drop workaround for GHC bug #11331. See #174. >--------------------------------------------------------------- 84782844c149c729e5277f79ee80c8001f05c095 src/Rules/Compile.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 14e71ee..a52edef 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -14,7 +14,7 @@ compilePackage rs context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" buildPath "*" <.> hisuf way %> \hi -> - if compileInterfaceFilesSeparately && not ("//HpcParser.*" ?== hi) + if compileInterfaceFilesSeparately then do (src, deps) <- dependencies buildPath $ hi -<.> osuf way need $ src : deps @@ -37,7 +37,7 @@ compilePackage rs context @ (Context {..}) = do need $ src : deps build $ Target context (Gcc stage) [src] [obj] else do - if compileInterfaceFilesSeparately && "//*.hs" ?== src && not ("//HpcParser.*" ?== src) + if compileInterfaceFilesSeparately && "//*.hs" ?== src then need $ (obj -<.> hisuf way) : src : deps else need $ src : deps buildWithResources rs $ Target context (Ghc stage) [src] [obj] From git at git.haskell.org Fri Oct 27 00:50:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (0ddf3b4) Message-ID: <20171027005040.701F93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ddf3b4d341a31ce66d78b5c840b2e55929ab5e3/ghc >--------------------------------------------------------------- commit 0ddf3b4d341a31ce66d78b5c840b2e55929ab5e3 Author: Andrey Mokhov Date: Tue Feb 16 02:40:38 2016 +0000 Minor revision. See #207. >--------------------------------------------------------------- 0ddf3b4d341a31ce66d78b5c840b2e55929ab5e3 src/Rules.hs | 7 ++++--- src/Rules/Compile.hs | 2 +- src/Rules/Dependencies.hs | 9 ++++----- 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index f765b5e..a3d67cb 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -61,15 +61,16 @@ packageRules = do let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] - let contexts = liftM3 Context allStages knownPackages allWays + let contexts = liftM3 Context allStages knownPackages allWays + vanillaContexts = liftM2 vanillaContext allStages knownPackages - traverse_ (compilePackage readPackageDb) contexts + traverse_ (compilePackage readPackageDb) contexts + traverse_ (buildPackageDependencies readPackageDb) vanillaContexts for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package buildPackageData context - buildPackageDependencies readPackageDb context buildPackageDocumentation context generatePackageCode context buildPackageLibrary context diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index a52edef..f62c644 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -7,7 +7,7 @@ import Expression import Oracles.Dependencies import Rules.Actions import Settings -import Target hiding (context) +import Target compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context @ (Context {..}) = do diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 45a8f8c..330c821 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -19,7 +19,7 @@ buildPackageDependencies rs context @ (Context {..}) = dropBuild = (pkgPath package ++) . drop (length buildPath) hDepFile = buildPath -/- ".hs-dependencies" in do - fmap (buildPath++) + fmap (buildPath ++) [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do let srcFile = if "//AutoApply.*" ?== out then dropExtension out @@ -32,19 +32,18 @@ buildPackageDependencies rs context @ (Context {..}) = need srcs if srcs == [] then writeFileChanged out "" - else buildWithResources rs $ - Target context (GhcM stage) srcs [out] + else buildWithResources rs $ Target context (GhcM stage) srcs [out] removeFileIfExists $ out <.> "bak" -- TODO: don't accumulate *.deps into .dependencies - (buildPath -/- ".dependencies") %> \out -> do + buildPath -/- ".dependencies" %> \out -> do cSrcs <- pkgDataList $ CSrcs path let cDepFiles = [ buildPath -/- src <.> "deps" | src <- cSrcs , not ("//AutoApply.cmm" ?== src) ] ++ [ src <.> "deps" | src <- cSrcs, "//AutoApply.cmm" ?== src ] need $ hDepFile : cDepFiles -- need all for more parallelism - cDeps <- fmap concat $ mapM readFile' cDepFiles + cDeps <- fmap concat $ traverse readFile' cDepFiles hDeps <- readFile' hDepFile let result = unlines . map (\(src, deps) -> unwords $ src : deps) From git at git.haskell.org Fri Oct 27 00:50:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add binary wrappers for hp2ps, hpc, hsc2hs (#321) (49835af) Message-ID: <20171027005040.475523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49835aff3bd03dd24d00e9c89aaed0339e4aa3a5/ghc >--------------------------------------------------------------- commit 49835aff3bd03dd24d00e9c89aaed0339e4aa3a5 Author: Zhen Zhang Date: Wed Jun 7 18:15:03 2017 +0800 Add binary wrappers for hp2ps, hpc, hsc2hs (#321) >--------------------------------------------------------------- 49835aff3bd03dd24d00e9c89aaed0339e4aa3a5 src/Rules/Program.hs | 12 ++++++++---- src/Rules/Wrappers.hs | 36 ++++++++++++++++++++++++++++++++++-- 2 files changed, 42 insertions(+), 6 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 79f01f2..5b2e66f 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -12,7 +12,8 @@ import Oracles.ModuleFiles import Oracles.PackageData import Oracles.Path (topDirectory) import Rules.Wrappers (WrappedBinary(..), Wrapper, - ghcWrapper, runGhcWrapper, inplaceGhcPkgWrapper) + ghcWrapper, runGhcWrapper, inplaceGhcPkgWrapper, + hpcWrapper, hp2psWrapper, hsc2hsWrapper) import Settings import Settings.Path (buildPath, inplaceLibBinPath, rtsContext, objectPath, inplaceLibPath, inplaceBinPath) @@ -22,10 +23,13 @@ import Util -- | List of wrappers we build. wrappers :: [(Context, Wrapper)] -wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) - , (vanillaContext Stage1 ghc , ghcWrapper ) +wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper) + , (vanillaContext Stage1 ghc , ghcWrapper) , (vanillaContext Stage1 runGhc, runGhcWrapper) - , (vanillaContext Stage0 ghcPkg, inplaceGhcPkgWrapper) ] + , (vanillaContext Stage0 ghcPkg, inplaceGhcPkgWrapper) + , (vanillaContext Stage1 hp2ps , hp2psWrapper) + , (vanillaContext Stage1 hpc , hpcWrapper) + , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) ] buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs index 93dfee0..246d28a 100644 --- a/src/Rules/Wrappers.hs +++ b/src/Rules/Wrappers.hs @@ -1,13 +1,15 @@ module Rules.Wrappers ( WrappedBinary(..), Wrapper, ghcWrapper, runGhcWrapper, - inplaceGhcPkgWrapper, installGhcPkgWrapper + inplaceGhcPkgWrapper, installGhcPkgWrapper, hp2psWrapper, + hpcWrapper, hsc2hsWrapper ) where import Base -import Expression (Expr, getStage) +import Expression import Settings.Install (installPackageDbDirectory) import Settings.Path (inplacePackageDbDirectory) import Oracles.Path (getTopDirectory) +import Oracles.Config.Setting (SettingList(..), settingList) -- | Wrapper is an expression depending on the 'FilePath' to the -- | library path and name of the wrapped binary. @@ -61,3 +63,33 @@ installGhcPkgWrapper WrappedBinary{..} = do [ "#!/bin/bash" , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " --global-package-db " ++ packageDb ++ " ${1+\"$@\"}" ] + +hp2psWrapper :: WrappedBinary -> Expr String +hp2psWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ] + +hpcWrapper :: WrappedBinary -> Expr String +hpcWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ] + +hsc2hsWrapper :: WrappedBinary -> Expr String +hsc2hsWrapper WrappedBinary{..} = do + top <- getTopDirectory + lift $ need [ sourcePath -/- "Rules/Wrappers.hs" ] + contents <- lift $ readFile' $ top -/- "utils/hsc2hs/hsc2hs.wrapper" + let executableName = binaryLibPath -/- "bin" -/- binaryName + confCcArgs <- lift $ settingList (ConfCcArgs Stage1) + confGccLinkerArgs <- lift $ settingList (ConfGccLinkerArgs Stage1) + let hsc2hsExtra = unwords (map ("-cflags=" ++) confCcArgs) ++ " " ++ + unwords (map ("-lflags=" ++) confGccLinkerArgs) + return $ unlines + [ "#!/bin/bash" + , "executablename=\"" ++ executableName ++ "\"" + , "HSC2HS_EXTRA=\"" ++ hsc2hsExtra ++ "\"" + , contents ] From git at git.haskell.org Fri Oct 27 00:50:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass way to buildPackageLibrary via Context, minor revision. (98b1f8c) Message-ID: <20171027005044.8DEA83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/98b1f8c2e233d4b9504dfe359b0f538f7af9095e/ghc >--------------------------------------------------------------- commit 98b1f8c2e233d4b9504dfe359b0f538f7af9095e Author: Andrey Mokhov Date: Tue Feb 16 03:01:56 2016 +0000 Pass way to buildPackageLibrary via Context, minor revision. See #207. >--------------------------------------------------------------- 98b1f8c2e233d4b9504dfe359b0f538f7af9095e src/Rules.hs | 15 +++++++++------ src/Rules/Documentation.hs | 1 + src/Rules/Library.hs | 13 +++++-------- src/Way.hs | 4 ++-- 4 files changed, 17 insertions(+), 16 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index a3d67cb..4592b4a 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -64,16 +64,19 @@ packageRules = do let contexts = liftM3 Context allStages knownPackages allWays vanillaContexts = liftM2 vanillaContext allStages knownPackages - traverse_ (compilePackage readPackageDb) contexts - traverse_ (buildPackageDependencies readPackageDb) vanillaContexts + for_ contexts $ mconcat + [ compilePackage readPackageDb + , buildPackageLibrary ] + + for_ vanillaContexts $ mconcat + [ buildPackageData + , buildPackageDependencies readPackageDb + , buildPackageDocumentation + , generatePackageCode ] for_ allStages $ \stage -> for_ knownPackages $ \package -> do let context = vanillaContext stage package - buildPackageData context - buildPackageDocumentation context - generatePackageCode context - buildPackageLibrary context buildProgram context registerPackage writePackageDb context diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 848a3fa..e3b0e7d 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -37,6 +37,7 @@ buildPackageDocumentation context @ (Context {..}) = build $ Target context GhcCabalHsColour [cabalFile] [] -- Build Haddock documentation + -- TODO: pass the correct way from Rules via Context let haddockWay = if dynamicGhcPrograms then dynamic else vanilla build $ Target (context {way = haddockWay}) Haddock srcs [file] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 79b4952..d77d58e 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -14,24 +14,21 @@ import Rules.Gmp import Settings import Target --- TODO: Use way from Context, #207 buildPackageLibrary :: Context -> Rules () buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" -- TODO: handle dynamic libraries - matchBuildResult buildPath "a" ?> \a -> do - + buildPath "*" ++ waySuffix way ++ ".a" %> \a -> do removeFileIfExists a cSrcs <- cSources context hSrcs <- hSources context - -- TODO: simplify handling of AutoApply.cmm - let w = detectWay a -- TODO: eliminate differences below - cObjs = [ buildPath -/- src -<.> osuf w | src <- cSrcs + -- TODO: simplify handling of AutoApply.cmm, eliminate differences below + let cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs , not ("//AutoApply.cmm" ?== src) ] - ++ [ src -<.> osuf w | src <- cSrcs, "//AutoApply.cmm" ?== src ] - hObjs = [ buildPath -/- src <.> osuf w | src <- hSrcs ] + ++ [ src -<.> osuf way | src <- cSrcs, "//AutoApply.cmm" ?== src ] + hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ] -- This will create split objects if required (we don't track them -- explicitly as this would needlessly bloat the Shake database). diff --git a/src/Way.hs b/src/Way.hs index 668ed63..c393437 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -6,8 +6,8 @@ module Way ( threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic, - allWays, wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf, - safeDetectWay, detectWay, matchBuildResult + allWays, wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, + libsuf, safeDetectWay, detectWay, matchBuildResult ) where import Base hiding (unit) From git at git.haskell.org Fri Oct 27 00:50:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Finalise generation of build rules from contexts. (f6a9d2f) Message-ID: <20171027005048.606413A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f6a9d2f4e67a163ba8255d8e66def0668dd492a1/ghc >--------------------------------------------------------------- commit f6a9d2f4e67a163ba8255d8e66def0668dd492a1 Author: Andrey Mokhov Date: Tue Feb 16 03:08:24 2016 +0000 Finalise generation of build rules from contexts. See #207. >--------------------------------------------------------------- f6a9d2f4e67a163ba8255d8e66def0668dd492a1 src/Rules.hs | 10 +++------- src/Rules/Register.hs | 1 - 2 files changed, 3 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 4592b4a..74ffe30 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -72,13 +72,9 @@ packageRules = do [ buildPackageData , buildPackageDependencies readPackageDb , buildPackageDocumentation - , generatePackageCode ] - - for_ allStages $ \stage -> - for_ knownPackages $ \package -> do - let context = vanillaContext stage package - buildProgram context - registerPackage writePackageDb context + , generatePackageCode + , buildProgram + , registerPackage writePackageDb ] buildRules :: Rules () buildRules = do diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 2bbfcfc..01d8ab9 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -13,7 +13,6 @@ import Settings import Settings.Packages.Rts import Target --- TODO: Use way from Context, #207 -- Build package-data.mk by using GhcCabal to process pkgCabal file registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context @ (Context {..}) = do From git at git.haskell.org Fri Oct 27 00:50:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Install Rules (#312) (3935e97) Message-ID: <20171027005048.58CD93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3935e97df7496458482dc1b47b6e63c5950dbfc6/ghc >--------------------------------------------------------------- commit 3935e97df7496458482dc1b47b6e63c5950dbfc6 Author: Zhen Zhang Date: Mon Jun 26 01:37:20 2017 +0800 Add Install Rules (#312) >--------------------------------------------------------------- 3935e97df7496458482dc1b47b6e63c5950dbfc6 hadrian.cabal | 1 + src/GHC.hs | 3 +- src/Main.hs | 2 + src/Oracles/Config/Setting.hs | 1 + src/Rules.hs | 29 ++-- src/Rules/Generate.hs | 4 +- src/Rules/Install.hs | 310 ++++++++++++++++++++++++++++++++++++++ src/Rules/Program.hs | 16 +- src/Rules/Wrappers.hs | 39 ++++- src/Settings.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 7 +- src/Settings/Packages/Rts.hs | 18 ++- src/Settings/Path.hs | 17 ++- src/UserSettings.hs | 9 +- 14 files changed, 417 insertions(+), 44 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 3935e97df7496458482dc1b47b6e63c5950dbfc6 From git at git.haskell.org Fri Oct 27 00:50:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dependency on hoopl (#328) (ffc905cf) Message-ID: <20171027005044.789613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffc905cf864570cbbc2699ef54570614f9fd6af8/ghc >--------------------------------------------------------------- commit ffc905cf864570cbbc2699ef54570614f9fd6af8 Author: Zhen Zhang Date: Sun Jun 25 17:02:16 2017 +0800 Drop dependency on hoopl (#328) >--------------------------------------------------------------- ffc905cf864570cbbc2699ef54570614f9fd6af8 src/GHC.hs | 5 ++--- src/Settings/Builders/GhcCabal.hs | 2 -- src/Settings/Default.hs | 1 - 3 files changed, 2 insertions(+), 6 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 441f068..78bb356 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,7 +4,7 @@ module GHC ( array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, - ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, + ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, @@ -28,7 +28,7 @@ defaultKnownPackages = , compiler, containers, deepseq, deriveConstants, directory, dllSplit , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs - , hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi + , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 , xhtml ] @@ -62,7 +62,6 @@ ghcTags = utility "ghctags" haddock = utility "haddock" haskeline = library "haskeline" hsc2hs = utility "hsc2hs" -hoopl = library "hoopl" hp2ps = utility "hp2ps" hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 1c50729..428c376 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -269,8 +269,6 @@ dll0Args = do , "CodeGen.Platform.X86" , "CodeGen.Platform.X86_64" , "FastBool" - , "Hoopl" - , "Hoopl.Dataflow" , "InteractiveEvalTypes" , "MkGraph" , "PprCmm" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 619fca1..d7059bf 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -115,7 +115,6 @@ stage0Packages = do , ghcPkg , ghcTags , hsc2hs - , hoopl , hp2ps , hpc , mkUserGuidePart From git at git.haskell.org Fri Oct 27 00:50:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add matchVersionedFilePath and use for matching library targets. (5fcb480) Message-ID: <20171027005056.80F763A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5fcb480b9e5efc1aea8c4b32965d65cdae5da766/ghc >--------------------------------------------------------------- commit 5fcb480b9e5efc1aea8c4b32965d65cdae5da766 Author: Andrey Mokhov Date: Tue Feb 16 17:30:13 2016 +0000 Add matchVersionedFilePath and use for matching library targets. >--------------------------------------------------------------- 5fcb480b9e5efc1aea8c4b32965d65cdae5da766 src/Base.hs | 19 ++++++++++++++++++- src/Rules/Library.hs | 22 ++++++++++++---------- 2 files changed, 30 insertions(+), 11 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 1a06120..feec868 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,12 +23,13 @@ module Base ( -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - removeFileIfExists, removeDirectoryIfExists + removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath ) where import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader +import Data.Char import Data.Function import Data.List.Extra import Data.Maybe @@ -175,3 +176,19 @@ removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f removeDirectoryIfExists :: FilePath -> Action () removeDirectoryIfExists d = liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d + +-- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the +-- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string +-- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: +-- +--- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ +--- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar-" "a" "foo/bar-0.1.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False'@ +matchVersionedFilePath :: String -> String -> FilePath -> Bool +matchVersionedFilePath prefix suffix filePath = + case stripPrefix prefix (unifyPath filePath) >>= stripSuffix suffix of + Nothing -> False + Just version -> all (\c -> isDigit c || c == '-' || c == '.') version diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index d77d58e..e53355f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -17,9 +17,10 @@ import Target buildPackageLibrary :: Context -> Rules () buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" + libHs = buildPath -/- "libHS" ++ pkgNameString package -- TODO: handle dynamic libraries - buildPath "*" ++ waySuffix way ++ ".a" %> \a -> do + matchVersionedFilePath libHs (waySuffix way <.> "a") ?> \a -> do removeFileIfExists a cSrcs <- cSources context hSrcs <- hSources context @@ -61,15 +62,16 @@ buildPackageLibrary context @ (Context {..}) = do -- TODO: this looks fragile as haskell objects can match this rule if their -- names start with "HS" and they are on top of the module hierarchy. -- This happens with hsc2hs, which has top-level file HSCParser.hs. - when (package /= hsc2hs) $ priority 2 $ (buildPath -/- "HS*.o") %> \obj -> do - cSrcs <- cSources context - hSrcs <- hSources context - let cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs - , not ("//AutoApply.cmm" ?== src) ] - ++ [ src -<.> "o" | src <- cSrcs, "//AutoApply.cmm" ?== src ] - hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] - need $ cObjs ++ hObjs - build $ Target context Ld (cObjs ++ hObjs) [obj] + priority 2 $ when (package /= hsc2hs && way == vanilla) $ + (buildPath -/- "HS*.o") %> \obj -> do + cSrcs <- cSources context + hSrcs <- hSources context + let cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs + , not ("//AutoApply.cmm" ?== src) ] + ++ [ src -<.> "o" | src <- cSrcs, "//AutoApply.cmm" ?== src ] + hObjs = [ buildPath -/- src <.> "o" | src <- hSrcs ] + need $ cObjs ++ hObjs + build $ Target context Ld (cObjs ++ hObjs) [obj] cSources :: Context -> Action [FilePath] cSources context = interpretInContext context $ getPkgDataList CSrcs From git at git.haskell.org Fri Oct 27 00:50:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop matchBuildResult and associated functions. (1aec72e) Message-ID: <20171027005052.721803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1aec72e34e0e3da138c6e0105c509f20592f6bc6/ghc >--------------------------------------------------------------- commit 1aec72e34e0e3da138c6e0105c509f20592f6bc6 Author: Andrey Mokhov Date: Tue Feb 16 03:12:11 2016 +0000 Drop matchBuildResult and associated functions. See #207. >--------------------------------------------------------------- 1aec72e34e0e3da138c6e0105c509f20592f6bc6 src/Way.hs | 36 ++---------------------------------- 1 file changed, 2 insertions(+), 34 deletions(-) diff --git a/src/Way.hs b/src/Way.hs index c393437..340321c 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -1,13 +1,12 @@ module Way ( - WayUnit (..), Way, wayUnit, wayFromUnits, + WayUnit (..), Way, wayUnit, wayFromUnits, allWays, vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging, threadedDebug, threadedProfiling, threadedLogging, threadedDynamic, threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic, threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic, - allWays, wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, - libsuf, safeDetectWay, detectWay, matchBuildResult + wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf ) where import Base hiding (unit) @@ -160,37 +159,6 @@ libsuf way @ (Way set) = -- e.g., p_ghc7.11.20141222.dll (the result) return $ prefix ++ "ghc" ++ version ++ extension --- | Detect way from a given 'FilePath'. Returns 'Nothing' if there is no match. --- --- * @'safeDetectWay' "foo/bar.hi" '==' 'Just' vanilla@ --- * @'safeDetectWay' "baz.thr_p_o" '==' 'Just' threadedProfiling@ --- * @'safeDetectWay' "qwe.ph_i" '==' 'Nothing' (expected "qwe.p_hi")@ --- * @'safeDetectWay' "xru.p_ghc7.11.123.so" '==' 'Just' profiling@ -safeDetectWay :: FilePath -> Maybe Way -safeDetectWay file = case reads prefix of - [(way, "")] -> Just way - _ -> Nothing - where - extension = takeExtension file - prefixed = if extension `notElem` [".so", ".dll", ".dynlib"] - then extension - else takeExtension . dropExtension . - dropExtension . dropExtension $ file - prefix = if extension == "a" - then drop 1 . dropWhile (/= '_') $ takeBaseName file - else drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed - --- Unsafe version of safeDetectWay. Useful when matchBuildResult has succeeded. -detectWay :: FilePath -> Way -detectWay = fromJust . safeDetectWay - --- Given a path, an extension suffix, and a file name check: --- 1) the file conforms to pattern 'path//*suffix' --- 2) file's extension has a valid way tag (i.e., safeDetectWay does not fail) -matchBuildResult :: FilePath -> String -> FilePath -> Bool -matchBuildResult path suffix file = - (path "*" ++ suffix) ?== file && isJust (safeDetectWay file) - -- Instances for storing in the Shake database instance Binary Way where put = put . show From git at git.haskell.org Fri Oct 27 00:50:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't pass gcc warning options to ghc (#329) (ae7358b) Message-ID: <20171027005056.7B5B33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae7358b596831a2f7683c51e04274099b73c2f20/ghc >--------------------------------------------------------------- commit ae7358b596831a2f7683c51e04274099b73c2f20 Author: Ben Gamari Date: Wed Jun 28 03:48:47 2017 -0400 Don't pass gcc warning options to ghc (#329) We would previously pass -Werror=unused-but-set-variable and -Wno-error=inline to ghc, despite the fact that they are gcc flags. >--------------------------------------------------------------- ae7358b596831a2f7683c51e04274099b73c2f20 src/Settings/Default.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 49ffcb6..3ad1fab 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -72,9 +72,9 @@ defaultErrorGhcFlags = mconcat [ notStage0 ? arg "-Werror" , (not <$> flag GccIsClang) ? mconcat [ (not <$> flag GccLt46) ? (not <$> windowsHost) ? - arg "-Werror=unused-but-set-variable" - , (not <$> flag GccLt44) ? arg "-Wno-error=inline" ] - , flag GccIsClang ? arg "-Wno-unknown-pragmas" ] + arg "-optc-Werror=unused-but-set-variable" + , (not <$> flag GccLt44) ? arg "-optc-Wno-error=inline" ] + , flag GccIsClang ? arg "-optc-Wno-unknown-pragmas" ] -- | Default source arguments, e.g. optimisation settings. defaultSourceArgs :: SourceArgs From git at git.haskell.org Fri Oct 27 00:50:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:50:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build dynamic libs (#325) (49b13b8) Message-ID: <20171027005052.7B6823A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49b13b8c749a49d53e2e1749d2ee46b18261e3ce/ghc >--------------------------------------------------------------- commit 49b13b8c749a49d53e2e1749d2ee46b18261e3ce Author: Zhen Zhang Date: Mon Jun 26 14:47:18 2017 +0800 Build dynamic libs (#325) >--------------------------------------------------------------- 49b13b8c749a49d53e2e1749d2ee46b18261e3ce src/Base.hs | 8 ++++- src/Rules.hs | 4 +++ src/Rules/Library.hs | 62 +++++++++++++++++++++++++++++---------- src/Settings/Builders/Cc.hs | 6 +++- src/Settings/Builders/Ghc.hs | 5 +++- src/Settings/Default.hs | 5 ++-- src/Settings/Flavours/Quick.hs | 5 +++- src/Settings/Flavours/Quickest.hs | 1 + src/Way.hs | 2 +- 9 files changed, 75 insertions(+), 23 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 49b13b8c749a49d53e2e1749d2ee46b18261e3ce From git at git.haskell.org Fri Oct 27 00:51:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hide Shake.parallel. Again. (89c79cd) Message-ID: <20171027005100.2FDC63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/89c79cdb52a9feeb949148348afffdd8cc150450/ghc >--------------------------------------------------------------- commit 89c79cdb52a9feeb949148348afffdd8cc150450 Author: Andrey Mokhov Date: Tue Feb 16 18:00:52 2016 +0000 Hide Shake.parallel. Again. >--------------------------------------------------------------- 89c79cdb52a9feeb949148348afffdd8cc150450 src/Base.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index feec868..a794ea8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel module Base ( -- * General utilities module Control.Applicative, @@ -34,7 +35,7 @@ import Data.Function import Data.List.Extra import Data.Maybe import Data.Monoid -import Development.Shake hiding (unit, (*>), Normal) +import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI From git at git.haskell.org Fri Oct 27 00:51:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Various portability fixes (#331) (edd539f) Message-ID: <20171027005100.43DBC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/edd539fc138d3e4b346b9375a63e4e52dafe9020/ghc >--------------------------------------------------------------- commit edd539fc138d3e4b346b9375a63e4e52dafe9020 Author: Ben Gamari Date: Fri Jun 30 13:45:23 2017 -0400 Various portability fixes (#331) * Don't assume location of bash interpreter * Pass curses library directory path to configure >--------------------------------------------------------------- edd539fc138d3e4b346b9375a63e4e52dafe9020 cfg/system.config.in | 2 ++ src/Oracles/Config/Setting.hs | 3 +++ src/Oracles/Path.hs | 9 ++++++--- src/Rules/Wrappers.hs | 26 +++++++++++++++++--------- src/Settings/Builders/GhcCabal.hs | 1 + src/Util.hs | 6 ++++-- 6 files changed, 33 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc edd539fc138d3e4b346b9375a63e4e52dafe9020 From git at git.haskell.org Fri Oct 27 00:51:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out buildPackageGhciLibrary from buildPackageLibrary and make it more robust. (c0b1a37) Message-ID: <20171027005103.DD60A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c0b1a37c9681fb98ed85bbccb4004fad993c58f2/ghc >--------------------------------------------------------------- commit c0b1a37c9681fb98ed85bbccb4004fad993c58f2 Author: Andrey Mokhov Date: Tue Feb 16 19:15:47 2016 +0000 Factor out buildPackageGhciLibrary from buildPackageLibrary and make it more robust. See #207. >--------------------------------------------------------------- c0b1a37c9681fb98ed85bbccb4004fad993c58f2 src/Rules.hs | 2 ++ src/Rules/Library.hs | 19 +++++++++++-------- 2 files changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 74ffe30..444a2cb 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -61,6 +61,7 @@ packageRules = do let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] + -- TODO: not all build rules make sense for all stage/package combinations let contexts = liftM3 Context allStages knownPackages allWays vanillaContexts = liftM2 vanillaContext allStages knownPackages @@ -72,6 +73,7 @@ packageRules = do [ buildPackageData , buildPackageDependencies readPackageDb , buildPackageDocumentation + , buildPackageGhciLibrary , generatePackageCode , buildProgram , registerPackage writePackageDb ] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index e53355f..c6d92a5 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,5 +1,7 @@ {-# LANGUAGE RecordWildCards #-} -module Rules.Library (buildPackageLibrary, cSources, hSources) where +module Rules.Library ( + buildPackageLibrary, buildPackageGhciLibrary, cSources, hSources + ) where import Data.Char import qualified System.Directory as IO @@ -17,10 +19,10 @@ import Target buildPackageLibrary :: Context -> Rules () buildPackageLibrary context @ (Context {..}) = do let buildPath = targetPath stage package -/- "build" - libHs = buildPath -/- "libHS" ++ pkgNameString package + libPrefix = buildPath -/- "libHS" ++ pkgNameString package -- TODO: handle dynamic libraries - matchVersionedFilePath libHs (waySuffix way <.> "a") ?> \a -> do + matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do removeFileIfExists a cSrcs <- cSources context hSrcs <- hSources context @@ -58,12 +60,13 @@ buildPackageLibrary context @ (Context {..}) = do a (dropWhileEnd isPunctuation synopsis) +buildPackageGhciLibrary :: Context -> Rules () +buildPackageGhciLibrary context @ (Context {..}) = priority 2 $ do + let buildPath = targetPath stage package -/- "build" + libPrefix = buildPath -/- "HS" ++ pkgNameString package + -- TODO: simplify handling of AutoApply.cmm - -- TODO: this looks fragile as haskell objects can match this rule if their - -- names start with "HS" and they are on top of the module hierarchy. - -- This happens with hsc2hs, which has top-level file HSCParser.hs. - priority 2 $ when (package /= hsc2hs && way == vanilla) $ - (buildPath -/- "HS*.o") %> \obj -> do + matchVersionedFilePath libPrefix (waySuffix way <.> "o") ?> \obj -> do cSrcs <- cSources context hSrcs <- hSources context let cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs From git at git.haskell.org Fri Oct 27 00:51:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix setup-config dependency (#334) (6d46b39) Message-ID: <20171027005104.09D863A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d46b39a971e8b833b5ffd8f0666c3361fd79bc0/ghc >--------------------------------------------------------------- commit 6d46b39a971e8b833b5ffd8f0666c3361fd79bc0 Author: Zhen Zhang Date: Mon Jul 3 04:05:13 2017 +0800 Fix setup-config dependency (#334) >--------------------------------------------------------------- 6d46b39a971e8b833b5ffd8f0666c3361fd79bc0 src/Rules.hs | 2 ++ src/Rules/Data.hs | 6 ++++-- src/Rules/Install.hs | 3 ++- src/Settings/Path.hs | 8 +++++++- 4 files changed, 15 insertions(+), 4 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 6e9f5d7..e5835c0 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -39,6 +39,8 @@ buildLib stage pkg = do when (pkg `elem` activePackages) $ if isLibrary pkg then do -- build a library + when (nonCabalContext context) $ + need [pkgSetupConfigFile context] ways <- interpretInContext context getLibraryWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 0538f6c..0c19b2a 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -20,8 +20,9 @@ buildPackageData context at Context {..} = do cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile context + setupConfigFile = pkgSetupConfigFile context - dataFile %> \mk -> do + [dataFile, setupConfigFile] &%> \(mk:setupConfig:_) -> do -- Make sure all generated dependencies are in place before proceeding. orderOnly =<< interpretInContext context generatedDependencies @@ -32,7 +33,7 @@ buildPackageData context at Context {..} = do need =<< mapM pkgConfFile =<< contextDependencies context need [cabalFile] - build $ Target context GhcCabal [cabalFile] [mk] + build $ Target context GhcCabal [cabalFile] [mk, setupConfig] postProcessPackageData context mk pkgInplaceConfig context %> \conf -> do @@ -107,6 +108,7 @@ packageCmmSources pkg -- For example, @libraries/deepseq/dist-install_VERSION = 1.4.0.0@ -- is replaced by @VERSION = 1.4.0.0 at . -- Reason: Shake's built-in makefile parser doesn't recognise slashes +-- TODO (izgzhen): should fix DEP_LIB_REL_DIRS_SEARCHPATH postProcessPackageData :: Context -> FilePath -> Action () postProcessPackageData context at Context {..} file = do top <- topDirectory diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 3499b26..e7c6d41 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -18,7 +18,7 @@ import Oracles.Config.Setting import Oracles.PackageData import Oracles.Path -import qualified System.Directory.Extra as IO +import qualified System.Directory as IO {- | Install the built binaries etc. to the @destDir ++ prefix at . @@ -133,6 +133,7 @@ withLatestBuildStage pkg m = do installPackageConf :: Action () installPackageConf = do let context = vanillaContext Stage0 rts + liftIO $ IO.createDirectoryIfMissing True (takeDirectory pkgConfInstallPath) build $ Target context HsCpp [ pkgPath rts -/- "package.conf.in" ] [ pkgConfInstallPath <.> "raw" ] Stdout out <- cmd ("grep" :: String) [ "-v", "^#pragma GCC" diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 240f992..8814620 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -5,7 +5,8 @@ module Settings.Path ( rtsContext, rtsBuildPath, rtsConfIn, shakeFilesPath,inplacePackageDbDirectory, pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, - installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath + installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, + pkgSetupConfigFile ) where import Base @@ -74,6 +75,11 @@ pkgInplaceConfig context = buildPath context -/- "inplace-pkg-config" pkgDataFile :: Context -> FilePath pkgDataFile context = buildPath context -/- "package-data.mk" + +-- | Path to the @setup-config@ of a given 'Context'. +pkgSetupConfigFile :: Context -> FilePath +pkgSetupConfigFile context = buildPath context -/- "setup-config" + -- | Path to the haddock file of a given 'Context', e.g.: -- "_build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath From git at git.haskell.org Fri Oct 27 00:51:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use matchVersionedFilePath in registerPackage build rule. (f0f4193) Message-ID: <20171027005107.DD0713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f0f4193049fabd48cd1c0b5e37849319849b9bf5/ghc >--------------------------------------------------------------- commit f0f4193049fabd48cd1c0b5e37849319849b9bf5 Author: Andrey Mokhov Date: Tue Feb 16 19:16:33 2016 +0000 Use matchVersionedFilePath in registerPackage build rule. See #207. >--------------------------------------------------------------- f0f4193049fabd48cd1c0b5e37849319849b9bf5 src/Rules/Register.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 01d8ab9..85fac80 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -1,8 +1,6 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Register (registerPackage) where -import Data.Char - import Base import Context import Expression @@ -18,12 +16,9 @@ registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context @ (Context {..}) = do let oldPath = pkgPath package -/- targetDirectory stage package -- TODO: remove, #113 pkgConf = packageDbDirectory stage -/- pkgNameString package - match f = case stripPrefix (pkgConf ++ "-") f of - Nothing -> False - Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf" - when (stage <= Stage1) $ match ?> \conf -> do - -- This produces pkgConfig. TODO: Add explicit tracking + when (stage <= Stage1) $ matchVersionedFilePath pkgConf "conf" ?> \conf -> do + -- This produces inplace-pkg-config. TODO: Add explicit tracking need [pkgDataFile stage package] -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 From git at git.haskell.org Fri Oct 27 00:51:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Stage1Only rule (#340) (b245f0e) Message-ID: <20171027005108.087A83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b245f0e8ce176399dd87de283c7ad77125033bf5/ghc >--------------------------------------------------------------- commit b245f0e8ce176399dd87de283c7ad77125033bf5 Author: Zhen Zhang Date: Thu Jul 6 14:11:00 2017 +0800 Add Stage1Only rule (#340) >--------------------------------------------------------------- b245f0e8ce176399dd87de283c7ad77125033bf5 src/Oracles/Dependencies.hs | 2 +- src/Rules.hs | 36 ++++++++++++++++++++++++++++-------- src/Rules/Install.hs | 2 +- src/Settings.hs | 12 +++++++++++- src/UserSettings.hs | 21 ++++++++++++++++++--- 5 files changed, 59 insertions(+), 14 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 167047d..2775b3e 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -63,7 +63,7 @@ needContext cs = do lib0 <- buildDll0 context ghciLib <- pkgGhciLibraryFile context ghciFlag <- interpretInContext context $ getPkgData BuildGhciLib - let ghci = ghciFlag == "YES" && stage context == Stage1 + let ghci = ghciFlag == "YES" && (stage context == Stage1 || stage1Only) return $ [ libFile ] ++ [ lib0File | lib0 ] ++ [ ghciLib | ghci ] confs <- mapM pkgConfFile cs need $ libs ++ confs diff --git a/src/Rules.hs b/src/Rules.hs index e5835c0..3ba6ba7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,4 +1,4 @@ -module Rules (topLevelTargets, buildLib, buildRules) where +module Rules (topLevelTargets, buildPackage, buildRules) where import Base import Context @@ -18,22 +18,35 @@ import qualified Rules.Library import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register +import Oracles.Dependencies (needContext) +import Util (needBuilder) import Settings import Settings.Path allStages :: [Stage] allStages = [minBound ..] --- | This rule 'need' all top-level build targets. +-- | This rule 'need' all top-level build targets +-- or Stage1Only targets topLevelTargets :: Rules () -topLevelTargets = do - want $ Rules.Generate.inplaceLibCopyTargets +topLevelTargets = action $ do + need $ Rules.Generate.inplaceLibCopyTargets - forM_ allStages $ \stage -> - forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> action (buildLib stage pkg) + if stage1Only + then do + forAllPkgs $ \stg pkg -> + when (isLibrary pkg) $ + buildPackage stg pkg + forM_ programsStage1Only $ buildPackage Stage0 + else + forAllPkgs buildPackage + where + forAllPkgs f = + forM_ allStages $ \stage -> + forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> f stage pkg -buildLib :: Stage -> Package -> Action () -buildLib stage pkg = do +buildPackage :: Stage -> Package -> Action () +buildPackage stage pkg = do let context = vanillaContext stage pkg activePackages <- interpretInContext context getPackages when (pkg `elem` activePackages) $ @@ -44,6 +57,7 @@ buildLib stage pkg = do ways <- interpretInContext context getLibraryWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour + needContext [context] need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else -- otherwise build a program need =<< maybeToList <$> programPath (programContext stage pkg) @@ -90,3 +104,9 @@ buildRules = do Rules.Libffi.libffiRules packageRules Rules.Perl.perlScriptRules + +programsStage1Only :: [Package] +programsStage1Only = + [ deriveConstants, genprimopcode, hp2ps, runGhc + , ghcCabal, hpc, dllSplit, ghcPkg, hsc2hs + , genapply, ghc ] diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index e7c6d41..0492a62 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -191,7 +191,7 @@ installPackages = do let context = vanillaContext stg pkg top <- interpretInContext context getTopDirectory let installDistDir = top -/- buildPath context - buildLib stg pkg + buildPackage stg pkg docDir <- installDocDir ghclibDir <- installGhcLibDir version <- interpretInContext context (getPkgData Version) diff --git a/src/Settings.hs b/src/Settings.hs index d09fa31..8152a6e 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -3,7 +3,7 @@ module Settings ( findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, getContextDirectory, getBuildPath, stagePackages, builderPath, getBuilderPath, isSpecified, latestBuildStage, programPath, programContext, - integerLibraryName, destDir, pkgConfInstallPath + integerLibraryName, destDir, pkgConfInstallPath, stage1Only ) where import Base @@ -117,3 +117,13 @@ programPath context at Context {..} = do pkgConfInstallPath :: FilePath pkgConfInstallPath = buildPath (vanillaContext Stage0 rts) -/- "package.conf.install" + +-- | Stage1Only flag +-- TODO: Set this by cmdline flags +stage1Only :: Bool +stage1Only = defaultStage1Only + +-- | Install's DESTDIR flag +-- TODO: Set this by cmdline flags +destDir :: FilePath +destDir = defaultDestDir diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 96e6f4b..4398700 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -4,7 +4,7 @@ -- accidentally commit them. module UserSettings ( buildRootPath, userFlavours, userKnownPackages, verboseCommands, - putBuild, putSuccess, destDir + putBuild, putSuccess, defaultDestDir, defaultStage1Only ) where import System.Console.ANSI @@ -47,5 +47,20 @@ putSuccess = putColoured Dull Green -- It is by default empty, representing the root of file system, -- or it might be a directory. -- It is usually used with @prefix@, like @/usr/local@ -destDir :: FilePath -destDir = "" +defaultDestDir :: FilePath +defaultDestDir = "" + +{- + Stage1Only=YES means: + - don't build ghc-stage2 (the executable) + - don't build utils that rely on ghc-stage2 + See Note [No stage2 packages when CrossCompiling or Stage1Only] in + ./ghc.mk. + - install ghc-stage1 instead of ghc-stage2 + - install the ghc-pkg that was built with the stage0 compiler + - (*do* still build compiler/stage2 (i.e. the ghc library)) + - (*do* still build all other libraries) +-} +-- | Stage1Only flag, default off +defaultStage1Only :: Bool +defaultStage1Only = False From git at git.haskell.org Fri Oct 27 00:51:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't unify paths as it seems prone to surprises. (a849c93) Message-ID: <20171027005115.1A3F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a849c93a1f092e6c611d1bd4fae68b91612bfadb/ghc >--------------------------------------------------------------- commit a849c93a1f092e6c611d1bd4fae68b91612bfadb Author: Andrey Mokhov Date: Tue Feb 16 23:09:34 2016 +0000 Don't unify paths as it seems prone to surprises. >--------------------------------------------------------------- a849c93a1f092e6c611d1bd4fae68b91612bfadb src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 372ec78..769fdc4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -183,7 +183,7 @@ removeDirectoryIfExists d = -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: -- --- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'False'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ --- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ @@ -191,6 +191,6 @@ removeDirectoryIfExists d = --- * @'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False'@ matchVersionedFilePath :: String -> String -> FilePath -> Bool matchVersionedFilePath prefix suffix filePath = - case stripPrefix prefix (unifyPath filePath) >>= stripSuffix suffix of + case stripPrefix prefix filePath >>= stripSuffix suffix of Nothing -> False Just version -> all (\c -> isDigit c || c == '-' || c == '.') version From git at git.haskell.org Fri Oct 27 00:51:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add tests for matchVersionedFilePath. (0b68ae8) Message-ID: <20171027005111.8556E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b68ae8b754a400577dbd05e646764742251ec27/ghc >--------------------------------------------------------------- commit 0b68ae8b754a400577dbd05e646764742251ec27 Author: Andrey Mokhov Date: Tue Feb 16 19:26:37 2016 +0000 Add tests for matchVersionedFilePath. >--------------------------------------------------------------- 0b68ae8b754a400577dbd05e646764742251ec27 src/Base.hs | 1 + src/Rules/Selftest.hs | 13 ++++++++++++- 2 files changed, 13 insertions(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index a794ea8..372ec78 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -183,6 +183,7 @@ removeDirectoryIfExists d = -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: -- --- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ +--- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'True'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ --- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ --- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index a3cc089..5fafda5 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -3,8 +3,10 @@ module Rules.Selftest (selftestRules) where import Development.Shake -import Settings.Builders.Ar (chunksOfSize) import Test.QuickCheck + +import Base +import Settings.Builders.Ar (chunksOfSize) import Way instance Arbitrary Way where @@ -22,6 +24,15 @@ selftestRules = in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res test $ chunksOfSize 3 ["a","b","c","defg","hi","jk"] == [["a","b","c"],["defg"],["hi"],["jk"]] + test $ matchVersionedFilePath "foo/bar" ".a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" ".a" "foo\\bar.a" == True + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" "" "foo/bar.a" == False + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar-" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar/" "a" "foo/bar-0.1.a" == False + + -- TODO: add automated tests for matchVersionedFilePath too test :: Testable a => a -> Action () test = liftIO . quickCheck From git at git.haskell.org Fri Oct 27 00:51:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Automate dependency analysis of installed packages (#342) (5f0e385) Message-ID: <20171027005111.AB3E23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f0e385d4377c5d51997ed3f51340d1405095c5d/ghc >--------------------------------------------------------------- commit 5f0e385d4377c5d51997ed3f51340d1405095c5d Author: Zhen Zhang Date: Sat Jul 8 20:35:23 2017 +0800 Automate dependency analysis of installed packages (#342) >--------------------------------------------------------------- 5f0e385d4377c5d51997ed3f51340d1405095c5d src/Oracles/Dependencies.hs | 19 +++++++++++++++++-- src/Rules.hs | 1 - src/Rules/Install.hs | 20 +++++++------------- 3 files changed, 24 insertions(+), 16 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 2775b3e..447df25 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,7 +1,7 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, TupleSections #-} module Oracles.Dependencies ( fileDependencies, contextDependencies, needContext, dependenciesOracles, - pkgDependencies + pkgDependencies, sortPkgsByDep ) where import qualified Data.HashMap.Strict as Map @@ -81,3 +81,18 @@ dependenciesOracles = do putLoud $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return $ Map.fromList [ (key, values) | (key:values) <- contents ] + +-- | Sort packages by their dependency +-- HACK (izgzhen): See https://github.com/snowleopard/hadrian/issues/344 for details +sortPkgsByDep :: [Package] -> Action [Package] +sortPkgsByDep pkgs = do + elems <- mapM (\p -> (p,) <$> pkgDependencies p) pkgs + return $ map fst $ topSort elems + where + annotateInDeg es e = + (foldr (\e' s -> if fst e' `elem` snd e then s + 1 else s) 0 es, e) + topSort [] = [] + topSort es = + let annotated = map (annotateInDeg es) es + inDegZero = map snd $ filter ((== 0). fst) annotated + in inDegZero ++ topSort (es \\ inDegZero) diff --git a/src/Rules.hs b/src/Rules.hs index 3ba6ba7..2081585 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -19,7 +19,6 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Oracles.Dependencies (needContext) -import Util (needBuilder) import Settings import Settings.Path diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 0492a62..8530f50 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -15,7 +15,7 @@ import Rules.Libffi import Rules.Generate import Settings.Packages.Rts import Oracles.Config.Setting -import Oracles.PackageData +import Oracles.Dependencies (sortPkgsByDep) import Oracles.Path import qualified System.Directory as IO @@ -81,7 +81,6 @@ installLibExecs = do (destDir ++ libExecDir -/- "ghc" <.> exe) -- | Binaries to install --- TODO: Consider Stage1Only installBinPkgs :: [Package] installBinPkgs = [ ghc, ghcPkg, ghcSplit, hp2ps @@ -176,14 +175,10 @@ installPackages = do copyFile ghcBootPlatformHeader (pkgPath compiler -/- "ghc_boot_platform.h") - -- TODO: Consider Stage1Only - -- TODO: Use automatic dependency analysis, rather than hardcoding - -- the ordering - let installLibPkgs = [ ghcPrim, integerSimple, base, filepath - , array, deepseq, bytestring, containers, time, unix - , directory, process, hpc, pretty, binary, cabal - , ghcBootTh, ghcBoot, templateHaskell - , transformers, terminfo, haskeline, ghci, compiler ] + activePackages <- filterM ((isJust <$>) . latestBuildStage) + (knownPackages \\ [rts, libffi]) + + installLibPkgs <- sortPkgsByDep (filter isLibrary activePackages) forM_ installLibPkgs $ \pkg at Package{..} -> do when (isLibrary pkg) $ @@ -194,10 +189,9 @@ installPackages = do buildPackage stg pkg docDir <- installDocDir ghclibDir <- installGhcLibDir - version <- interpretInContext context (getPkgData Version) + -- Copy over packages - let targetDest = destDir ++ ghclibDir -/- - pkgNameString pkg ++ "-" ++ version + strip <- stripCmdPath context ways <- interpretInContext context getLibraryWays let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" -- HACK? From git at git.haskell.org Fri Oct 27 00:51:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Selftest, add more tests for matchVersionedFilePath. (8ae1c56) Message-ID: <20171027005118.DFDB33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ae1c564d861871d9b587d3525c704e3625a4864/ghc >--------------------------------------------------------------- commit 8ae1c564d861871d9b587d3525c704e3625a4864 Author: Andrey Mokhov Date: Tue Feb 16 23:10:12 2016 +0000 Refactor Selftest, add more tests for matchVersionedFilePath. >--------------------------------------------------------------- 8ae1c564d861871d9b587d3525c704e3625a4864 src/Rules/Selftest.hs | 54 ++++++++++++++++++++++++++++++++++----------------- 1 file changed, 36 insertions(+), 18 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 5fafda5..70a4023 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -15,24 +15,42 @@ instance Arbitrary Way where instance Arbitrary WayUnit where arbitrary = arbitraryBoundedEnum +test :: Testable a => a -> Action () +test = liftIO . quickCheck + selftestRules :: Rules () selftestRules = "selftest" ~> do - test $ \(x :: Way) -> read (show x) == x - test $ \n xs -> - let res = chunksOfSize n xs - in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res - test $ chunksOfSize 3 ["a","b","c","defg","hi","jk"] == [["a","b","c"],["defg"],["hi"],["jk"]] - - test $ matchVersionedFilePath "foo/bar" ".a" "foo/bar.a" == True - test $ matchVersionedFilePath "foo/bar" ".a" "foo\\bar.a" == True - test $ matchVersionedFilePath "foo/bar" "a" "foo/bar.a" == True - test $ matchVersionedFilePath "foo/bar" "" "foo/bar.a" == False - test $ matchVersionedFilePath "foo/bar" "a" "foo/bar-0.1.a" == True - test $ matchVersionedFilePath "foo/bar-" "a" "foo/bar-0.1.a" == True - test $ matchVersionedFilePath "foo/bar/" "a" "foo/bar-0.1.a" == False - - -- TODO: add automated tests for matchVersionedFilePath too - -test :: Testable a => a -> Action () -test = liftIO . quickCheck + testWays + testChunksOfSize + testMatchVersionedFilePath + +testWays :: Action () +testWays = do + putBuild $ "==== Read Way, Show Way" + test $ \(x :: Way) -> read (show x) == x + +testChunksOfSize :: Action () +testChunksOfSize = do + putBuild $ "==== chunksOfSize" + test $ chunksOfSize 3 [ "a", "b", "c" , "defg" , "hi" , "jk" ] + == [ ["a", "b", "c"], ["defg"], ["hi"], ["jk"] ] + test $ \n xs -> + let res = chunksOfSize n xs + in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res + +testMatchVersionedFilePath :: Action () +testMatchVersionedFilePath = do + putBuild $ "==== matchVersionedFilePath" + test $ matchVersionedFilePath "foo/bar" ".a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" ".a" "foo\\bar.a" == False + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar.a" == True + test $ matchVersionedFilePath "foo/bar" "" "foo/bar.a" == False + test $ matchVersionedFilePath "foo/bar" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar-" "a" "foo/bar-0.1.a" == True + test $ matchVersionedFilePath "foo/bar/" "a" "foo/bar-0.1.a" == False + + test $ \prefix suffix -> forAll versions $ \version -> + matchVersionedFilePath prefix suffix (prefix ++ version ++ suffix) + where + versions = listOf . elements $ '-' : '.' : ['0'..'9'] From git at git.haskell.org Fri Oct 27 00:51:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Data.Bifunctor.bimap as it is now available on bootstrapping GHC. (cbbbc63) Message-ID: <20171027005122.BF3693A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbbbc63883b41b794d154efbb7a166ea659980db/ghc >--------------------------------------------------------------- commit cbbbc63883b41b794d154efbb7a166ea659980db Author: Andrey Mokhov Date: Wed Feb 17 01:59:11 2016 +0000 Use Data.Bifunctor.bimap as it is now available on bootstrapping GHC. >--------------------------------------------------------------- cbbbc63883b41b794d154efbb7a166ea659980db src/Base.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 769fdc4..7d63fa0 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -3,6 +3,7 @@ module Base ( -- * General utilities module Control.Applicative, module Control.Monad.Extra, + module Data.Bifunctor, module Data.Function, module Data.List.Extra, module Data.Maybe, @@ -22,7 +23,7 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, -- * Miscellaneous utilities - bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, + minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath ) where @@ -30,6 +31,7 @@ module Base ( import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader +import Data.Bifunctor import Data.Char import Data.Function import Data.List.Extra @@ -142,11 +144,6 @@ putError msg = do putColoured Red msg error $ "GHC build system error: " ++ msg --- Explicit definition to avoid dependency on Data.Bifunctor --- | Bifunctor bimap. -bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) -bimap f g (x, y) = (f x, g y) - -- Explicit definition to avoid dependency on Data.List.Ordered -- | Difference of two ordered lists. minusOrd :: Ord a => [a] -> [a] -> [a] From git at git.haskell.org Fri Oct 27 00:51:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Better tracking of dependence in installation (#353) (d8e1759) Message-ID: <20171027005115.3DEE83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d8e17590fc8efcbd87f97bb1d85a1775b85272d3/ghc >--------------------------------------------------------------- commit d8e17590fc8efcbd87f97bb1d85a1775b85272d3 Author: Zhen Zhang Date: Sat Jul 8 21:02:17 2017 +0800 Better tracking of dependence in installation (#353) >--------------------------------------------------------------- d8e17590fc8efcbd87f97bb1d85a1775b85272d3 src/Rules/Install.hs | 27 ++++++++++++--------------- src/Util.hs | 3 +++ 2 files changed, 15 insertions(+), 15 deletions(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 8530f50..4c91316 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedStrings, FlexibleContexts #-} +{-# LANGUAGE FlexibleContexts #-} module Rules.Install (installRules) where import Base @@ -39,8 +39,8 @@ XXX (izgzhen): Do we need @INSTALL_OPTS@ in the make scripts? installRules :: Rules () installRules = do "install" ~> do - installPackageConf installIncludes + installPackageConf installCommonLibs installLibExecs installLibExecScripts @@ -54,7 +54,6 @@ getLibExecDir = (-/- "bin") <$> installGhcLibDir -- ref: ghc.mk installLibExecScripts :: Action () installLibExecScripts = do - need libExecScripts libExecDir <- getLibExecDir installDir (destDir ++ libExecDir) forM_ libExecScripts $ \script -> do @@ -74,7 +73,6 @@ installLibExecs = do withLatestBuildStage pkg $ \stg -> do let context = programContext stg pkg let bin = inplaceLibBinPath -/- programName context <.> exe - need [bin] installProgram bin (destDir ++ libExecDir) when (pkg == ghc) $ do moveFile (destDir ++ libExecDir -/- programName context <.> exe) @@ -111,10 +109,9 @@ installBins = do contents <- interpretInContext context $ wrapper (WrappedBinary (destDir ++ libDir) symName) - withTempDir $ \tmp -> do - let tmpfile = tmp -/- binName - writeFileChanged tmpfile contents - installProgram tmpfile (destDir ++ binDir) + let wrapperPath = destDir ++ binDir -/- binName + writeFileChanged wrapperPath contents + makeExecutable wrapperPath unlessM windowsHost $ linkSymbolic (destDir ++ binDir -/- binName) (destDir ++ binDir -/- symName) @@ -135,13 +132,12 @@ installPackageConf = do liftIO $ IO.createDirectoryIfMissing True (takeDirectory pkgConfInstallPath) build $ Target context HsCpp [ pkgPath rts -/- "package.conf.in" ] [ pkgConfInstallPath <.> "raw" ] - Stdout out <- cmd ("grep" :: String) [ "-v", "^#pragma GCC" - , pkgConfInstallPath <.> "raw" ] + Stdout content <- cmd "grep" [ "-v", "^#pragma GCC" + , pkgConfInstallPath <.> "raw" ] withTempFile $ \tmp -> do - liftIO $ writeFile tmp out - Stdout out' <- cmd ("sed" :: String) - [ "-e", "s/\"\"//g", "-e", "s/:[ ]*,/: /g", tmp ] - liftIO $ writeFile pkgConfInstallPath out' + liftIO $ writeFile tmp content + Stdout content' <- cmd "sed" [ "-e", "s/\"\"//g", "-e", "s/:[ ]*,/: /g", tmp ] + liftIO $ writeFile pkgConfInstallPath content' -- | Install packages to @prefix/lib@ -- ref: ghc.mk @@ -195,6 +191,7 @@ installPackages = do strip <- stripCmdPath context ways <- interpretInContext context getLibraryWays let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" -- HACK? + need [ ghcCabalInplace ] -- HACK (#318): copy stuff back to the place favored by ghc-cabal quietly $ copyDirectoryContents (Not excluded) @@ -250,7 +247,7 @@ installPackages = do [ "--force", "--global-package-db" , installedPackageConf, "recache" ] where - createData f = unit $ cmd ("chmod" :: String) [ "644", f ] + createData f = unit $ cmd "chmod" [ "644", f ] excluded = Or [ Test "//haddock-prologue.txt" , Test "//package-data.mk" diff --git a/src/Util.hs b/src/Util.hs index c2335c2..da12e21 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -184,6 +184,7 @@ installDir dir = do installData :: [FilePath] -> FilePath -> Action () installData fs dir = do i <- setting InstallData + need fs forM_ fs $ \f -> putBuild $ "| Install data " ++ f ++ " to " ++ dir quietly $ cmd i fs dir @@ -192,6 +193,7 @@ installData fs dir = do installProgram :: FilePath -> FilePath -> Action () installProgram f dir = do i <- setting InstallProgram + need [f] putBuild $ "| Install program " ++ f ++ " to " ++ dir quietly $ cmd i f dir @@ -199,6 +201,7 @@ installProgram f dir = do installScript :: FilePath -> FilePath -> Action () installScript f dir = do i <- setting InstallScript + need [f] putBuild $ "| Install script " ++ f ++ " to " ++ dir quietly $ cmd i f dir From git at git.haskell.org Fri Oct 27 00:51:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (#352) (e93f583d) Message-ID: <20171027005119.101583A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e93f583d1d684e9db069c558967dc38d19a180e8/ghc >--------------------------------------------------------------- commit e93f583d1d684e9db069c558967dc38d19a180e8 Author: Zhen Zhang Date: Sat Jul 8 21:25:06 2017 +0800 Update README.md (#352) >--------------------------------------------------------------- e93f583d1d684e9db069c558967dc38d19a180e8 README.md | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index 2256fbf..d65b98c 100644 --- a/README.md +++ b/README.md @@ -106,6 +106,14 @@ are still up-to-date. To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` target. +#### Installation + +To build and install GHC artifacts, run the `install` target. + +By default, the artifacts will be installed to `` on your system. For example, +`ghc` will be installed to `/usr/local/bin`. By modifying `defaultDestDir` in `UserSettings.hs`, +you can install things to non-system path `DESTDIR/` instead. + #### Testing * `build validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` @@ -122,12 +130,12 @@ zero (see [#197][test-issue]). Current limitations ------------------- The new build system still lacks many important features: -* There is currently no support for the `dynamic` build way: [#4][dynamic-issue]. * Validation is not implemented: [#187][validation-issue]. +* Dynamic linking on Windows is not supported [#343][dynamic-windows-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). * Not all modes of the old build system are supported, e.g. [#250][freeze-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. -* There is no support for installation or binary distribution: [#219][install-issue]. +* There is no support for binary distribution: [#219][install-issue]. Check out [milestones] to see when we hope to resolve the above limitations. @@ -162,8 +170,8 @@ helped me endure and enjoy the project. [windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [test-issue]: https://github.com/snowleopard/hadrian/issues/197 -[dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 +[dynamic-windows-issue]: https://github.com/snowleopard/hadrian/issues/343 [freeze-issue]: https://github.com/snowleopard/hadrian/issues/250 [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 From git at git.haskell.org Fri Oct 27 00:51:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Ensure that if ghc compilation fails then we return a non-zero error code from build.bat (e40e2e0) Message-ID: <20171027005126.8E8503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e40e2e0e80d81f88d374a6e917b660befdde46b4/ghc >--------------------------------------------------------------- commit e40e2e0e80d81f88d374a6e917b660befdde46b4 Author: Neil Mitchell Date: Wed Feb 17 16:24:19 2016 +0000 Ensure that if ghc compilation fails then we return a non-zero error code from build.bat >--------------------------------------------------------------- e40e2e0e80d81f88d374a6e917b660befdde46b4 build.bat | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/build.bat b/build.bat index 348537d..10a6969 100644 --- a/build.bat +++ b/build.bat @@ -21,8 +21,8 @@ @ghc %ghcArgs% - at if %ERRORLEVEL% EQU 0 ( - @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains - @set GHC_PACKAGE_PATH= - @.shake\build %shakeArgs% -) + at if %ERRORLEVEL% NEQ 0 EXIT /B %ERRORLEVEL% + + at rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains + at set GHC_PACKAGE_PATH= + at .shake\build %shakeArgs% From git at git.haskell.org Fri Oct 27 00:51:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/ndmitchell/shaking-up-ghc (f98836e) Message-ID: <20171027005130.062B43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f98836ec1bae9809c167277232e0629647af1145/ghc >--------------------------------------------------------------- commit f98836ec1bae9809c167277232e0629647af1145 Merge: e40e2e0 cbbbc63 Author: Neil Mitchell Date: Wed Feb 17 16:25:50 2016 +0000 Merge branch 'master' of https://github.com/ndmitchell/shaking-up-ghc >--------------------------------------------------------------- f98836ec1bae9809c167277232e0629647af1145 src/Base.hs | 12 +++++------- src/Rules.hs | 2 ++ src/Rules/Library.hs | 19 +++++++++++-------- src/Rules/Register.hs | 9 ++------- src/Rules/Selftest.hs | 45 +++++++++++++++++++++++++++++++++++++-------- 5 files changed, 57 insertions(+), 30 deletions(-) From git at git.haskell.org Fri Oct 27 00:51:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix documentation rules (#324) (13023bc) Message-ID: <20171027005126.D45DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13023bc3e13dcd003efbf00a83a7ab780c2727c3/ghc >--------------------------------------------------------------- commit 13023bc3e13dcd003efbf00a83a7ab780c2727c3 Author: Zhen Zhang Date: Sun Jul 9 18:21:31 2017 +0800 Fix documentation rules (#324) >--------------------------------------------------------------- 13023bc3e13dcd003efbf00a83a7ab780c2727c3 src/Rules/Documentation.hs | 17 ++++++++++------- src/Rules/Install.hs | 14 ++++++++++++++ src/Rules/Wrappers.hs | 12 ++++++++++-- 3 files changed, 34 insertions(+), 9 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index cf54e0a..5ee6818 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -7,11 +7,14 @@ import Flavour import GHC import Oracles.ModuleFiles import Oracles.PackageData +import Oracles.Path (getTopDirectory) import Settings import Settings.Path import Target import Util +import qualified System.Directory as IO + haddockHtmlLib :: FilePath haddockHtmlLib = "inplace/lib/html/haddock-util.js" @@ -31,13 +34,6 @@ buildPackageDocumentation context at Context {..} = , depPkg /= rts ] need $ srcs ++ haddocks ++ [haddockHtmlLib] - -- HsColour sources - -- TODO: what is the output of GhcCabalHsColour? - whenM (isSpecified HsColour) $ do - pkgConf <- pkgConfFile context - need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf - build $ Target context GhcCabalHsColour [cabalFile] [] - -- Build Haddock documentation -- TODO: pass the correct way from Rules via Context let haddockWay = if dynamicGhcPrograms flavour then dynamic else vanilla @@ -47,6 +43,13 @@ buildPackageDocumentation context at Context {..} = let dir = takeDirectory haddockHtmlLib liftIO $ removeFiles dir ["//*"] copyDirectory "utils/haddock/haddock-api/resources/html" dir + where + excluded = Or + [ Test "//haddock-prologue.txt" + , Test "//package-data.mk" + , Test "//setup-config" + , Test "//inplace-pkg-config" + , Test "//build" ] -- # Make the haddocking depend on the library .a file, to ensure -- # that we wait until the library is fully built before we haddock it diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 4c91316..553f8d1 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -193,6 +193,20 @@ installPackages = do let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" -- HACK? need [ ghcCabalInplace ] + let cabalFile = pkgCabalFile pkg + -- HsColour sources + -- QUESTION: what is the output of GhcCabalHsColour? + whenM (isSpecified HsColour) $ do + top <- interpretInContext context getTopDirectory + let installDistDir = top -/- buildPath context + -- HACK: copy stuff back to the place favored by ghc-cabal + quietly $ copyDirectoryContents (Not excluded) + installDistDir (installDistDir -/- "build") + + pkgConf <- pkgConfFile context + need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf + build $ Target context GhcCabalHsColour [cabalFile] [] + -- HACK (#318): copy stuff back to the place favored by ghc-cabal quietly $ copyDirectoryContents (Not excluded) installDistDir (installDistDir -/- "build") diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs index b6f1266..6adf3f7 100644 --- a/src/Rules/Wrappers.hs +++ b/src/Rules/Wrappers.hs @@ -109,12 +109,21 @@ hsc2hsWrapper WrappedBinary{..} = do , "HSC2HS_EXTRA=\"" ++ hsc2hsExtra ++ "\"" , contents ] +haddockWrapper :: WrappedBinary -> Expr String +haddockWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) + ++ " -B" ++ binaryLibPath ++ " -l" ++ binaryLibPath ++ " ${1+\"$@\"}" ] + wrappersCommon :: [(Context, Wrapper)] wrappersCommon = [ (vanillaContext Stage0 ghc , ghcWrapper) , (vanillaContext Stage1 ghc , ghcWrapper) , (vanillaContext Stage1 hp2ps , hp2psWrapper) , (vanillaContext Stage1 hpc , hpcWrapper) - , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) ] + , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) + , (vanillaContext Stage2 haddock, haddockWrapper)] -- | List of wrappers for inplace artefacts inplaceWrappers :: [(Context, Wrapper)] @@ -127,4 +136,3 @@ installWrappers :: [(Context, Wrapper)] installWrappers = wrappersCommon ++ [ (vanillaContext Stage0 ghcPkg, installGhcPkgWrapper) , (vanillaContext Stage1 runGhc, installRunGhcWrapper) ] - From git at git.haskell.org Fri Oct 27 00:51:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use correct ar for host/target (#356) (b7550b2) Message-ID: <20171027005130.4EA6C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b7550b2bdbd148e80e3d5b06419549bcb7ca92ee/ghc >--------------------------------------------------------------- commit b7550b2bdbd148e80e3d5b06419549bcb7ca92ee Author: Ben Gamari Date: Mon Jul 10 13:40:54 2017 -0400 Use correct ar for host/target (#356) Previously we would always use the ar of the target; this is incorrect. Fixes #350. >--------------------------------------------------------------- b7550b2bdbd148e80e3d5b06419549bcb7ca92ee cfg/system.config.in | 1 + src/Builder.hs | 2 +- src/Oracles/Path.hs | 3 ++- src/Rules/Gmp.hs | 4 ++-- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Util.hs | 2 +- 8 files changed, 12 insertions(+), 10 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 078e1ec..34ef7b9 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -16,6 +16,7 @@ make = @MakeCmd@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ +system-ar = @AR_STAGE0@ system-cc = @CC_STAGE0@ system-ghc = @WithGhc@ system-ghc-pkg = @GhcPkgCmd@ diff --git a/src/Builder.hs b/src/Builder.hs index b2fbca3..7937319 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -28,7 +28,7 @@ data GhcPkgMode = Init | Update deriving (Eq, Generic, Show) -- @GhcPkg Stage0@ is the bootstrapping @GhcPkg at . -- @GhcPkg Stage1@ is the one built in Stage0. data Builder = Alex - | Ar + | Ar Stage | DeriveConstants | Cc CcMode Stage | Configure FilePath diff --git a/src/Oracles/Path.hs b/src/Oracles/Path.hs index a1c56f5..2ec2773 100644 --- a/src/Oracles/Path.hs +++ b/src/Oracles/Path.hs @@ -24,7 +24,8 @@ getTopDirectory = lift topDirectory systemBuilderPath :: Builder -> Action FilePath systemBuilderPath builder = case builder of Alex -> fromKey "alex" - Ar -> fromKey "ar" + Ar Stage0 -> fromKey "system-ar" + Ar _ -> fromKey "ar" Cc _ Stage0 -> fromKey "system-cc" Cc _ _ -> fromKey "cc" -- We can't ask configure for the path to configure! diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index a3e32d3..ee8eb82 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -25,7 +25,7 @@ gmpMakefile = gmpBuildPath -/- "Makefile" configureEnvironment :: Action [CmdOption] configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 - , builderEnvironment "AR" Ar + , builderEnvironment "AR" (Ar Stage1) , builderEnvironment "NM" Nm ] gmpRules :: Rules () @@ -43,7 +43,7 @@ gmpRules = do putBuild "| No GMP library/framework detected; in tree GMP will be built" need [gmpLibrary] createDirectory gmpObjects - build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] + build $ Target gmpContext (Ar Stage1) [gmpLibrary] [gmpObjects] copyFile (gmpBuildPath -/- "gmp.h") header copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 57f6263..bac9970 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -31,7 +31,7 @@ configureEnvironment = do sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 , builderEnvironment "CXX" $ Cc CompileC Stage1 , builderEnvironment "LD" Ld - , builderEnvironment "AR" Ar + , builderEnvironment "AR" (Ar Stage1) , builderEnvironment "NM" Nm , builderEnvironment "RANLIB" Ranlib , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w" diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 455c57c..b746279 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -72,8 +72,8 @@ buildPackageLibrary context at Context {..} = do asuf <- libsuf way let isLib0 = ("//*-0" ++ asuf) ?== a - if isLib0 then build $ Target context Ar [] [a] -- TODO: Scan for dlls - else build $ Target context Ar objs [a] + if isLib0 then build $ Target context (Ar stage) [] [a] -- TODO: Scan for dlls + else build $ Target context (Ar stage) objs [a] synopsis <- interpretInContext context $ getPkgData Synopsis unless isLib0 . putSuccess $ renderLibrary diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 9ddfe15..18816e1 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -25,7 +25,7 @@ ghcCabalBuilderArgs = builder GhcCabal ? do , packageConstraints , withStaged $ Cc CompileC , notStage0 ? with Ld - , with Ar + , withStaged Ar , with Alex , with Happy , verbosity < Chatty ? append [ "-v0", "--configure-option=--quiet" @@ -91,7 +91,7 @@ cppArgs = arg $ "-I" ++ generatedPath withBuilderKey :: Builder -> String withBuilderKey b = case b of - Ar -> "--with-ar=" + Ar _ -> "--with-ar=" Ld -> "--with-ld=" Cc _ _ -> "--with-gcc=" Ghc _ _ -> "--with-ghc=" diff --git a/src/Util.hs b/src/Util.hs index da12e21..944e8e5 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -53,7 +53,7 @@ customBuild rs opts target at Target {..} = do withResources rs $ do putInfo target quietlyUnlessVerbose $ case builder of - Ar -> do + Ar _ -> do output <- interpret target getOutput if "//*.a" ?== output then arCmd path argList From git at git.haskell.org Fri Oct 27 00:51:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #208 from ndmitchell/master (d1dacae) Message-ID: <20171027005133.67E743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1dacaea037b9d63b3747c1d1b30e5b3b9fe5dcd/ghc >--------------------------------------------------------------- commit d1dacaea037b9d63b3747c1d1b30e5b3b9fe5dcd Merge: cbbbc63 f98836e Author: Andrey Mokhov Date: Wed Feb 17 17:09:24 2016 +0000 Merge pull request #208 from ndmitchell/master Ensure that if ghc compilation fails then we return a non-zero error code from build.bat >--------------------------------------------------------------- d1dacaea037b9d63b3747c1d1b30e5b3b9fe5dcd build.bat | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Oct 27 00:51:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update flavours doc (#338) (9dde04c) Message-ID: <20171027005123.023943A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dde04c09058e7f07e7683fa3d334a096c911b2d/ghc >--------------------------------------------------------------- commit 9dde04c09058e7f07e7683fa3d334a096c911b2d Author: Zhen Zhang Date: Sat Jul 8 23:58:07 2017 +0800 Update flavours doc (#338) >--------------------------------------------------------------- 9dde04c09058e7f07e7683fa3d334a096c911b2d doc/flavours.md | 70 ++++++++++++++++++++++++++++++++++----------------------- 1 file changed, 42 insertions(+), 28 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index 9fe2239..3bf0c30 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -118,45 +118,59 @@ Libraries and GHC can be built in different _ways_, e.g. with or without profili information. The following table lists ways that are built in different flavours. - - - - - - - - - + + + + + + + + + + + + + + + - - - + + + - - - + + + - - + + + - - - + + - +
FlavourLibrary waysRTS waysProfiled GHC
stage0 - stage1+ - stage0 - stage1+ - stage0 - stage1+ -
FlavourLibrary waysRTS waysProfiled GHC
stage0stage1+stage0stage1+stage0stage1+
default
perf
prof
devel1
devel2
vanillavanilla
profiling
logging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
threadedProfiling
vanilla
profiling
dynamic
logging
debug
threaded
threadedDebug
threadedLogging +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
+ logging
debug
threaded
threadedDebug
+ threadedLogging
threadedProfiling +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
Only in
prof
flavour
Only in
prof
flavour
quick - vanilla
quick vanillalogging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
vanilla
dynamic
logging
debug
threaded
threadedDebug
threadedLogging +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
logging
debug
threaded
threadedDebug
threadedLogging +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
No No
quickest +
quickest vanilla vanilla vanilla
threaded (when --haddock)
vanilla
threaded (when --haddock)
No No
From git at git.haskell.org Fri Oct 27 00:51:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix warnings (e8abab2) Message-ID: <20171027005133.BDE693A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e8abab220113b10ef22e1080d7771216b2488b0b/ghc >--------------------------------------------------------------- commit e8abab220113b10ef22e1080d7771216b2488b0b Author: Andrey Mokhov Date: Tue Jul 11 18:07:53 2017 +0100 Fix warnings See #358 >--------------------------------------------------------------- e8abab220113b10ef22e1080d7771216b2488b0b src/Oracles/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 13 +------------ src/Settings/Builders/Ghc.hs | 1 - src/Settings/Flavours/Quickest.hs | 1 - src/Settings/Packages/GhcCabal.hs | 3 --- 5 files changed, 2 insertions(+), 18 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 447df25..3aaabfa 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -90,7 +90,7 @@ sortPkgsByDep pkgs = do return $ map fst $ topSort elems where annotateInDeg es e = - (foldr (\e' s -> if fst e' `elem` snd e then s + 1 else s) 0 es, e) + (foldr (\e' s -> if fst e' `elem` snd e then s + 1 else s) (0 :: Int) es, e) topSort [] = [] topSort es = let annotated = map (annotateInDeg es) es diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 5ee6818..a3a7b7c 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -7,14 +7,11 @@ import Flavour import GHC import Oracles.ModuleFiles import Oracles.PackageData -import Oracles.Path (getTopDirectory) import Settings import Settings.Path import Target import Util -import qualified System.Directory as IO - haddockHtmlLib :: FilePath haddockHtmlLib = "inplace/lib/html/haddock-util.js" @@ -23,8 +20,7 @@ haddockHtmlLib = "inplace/lib/html/haddock-util.js" -- files in the Shake database seems fragile and unnecessary. buildPackageDocumentation :: Context -> Rules () buildPackageDocumentation context at Context {..} = - let cabalFile = pkgCabalFile package - haddockFile = pkgHaddockFile context + let haddockFile = pkgHaddockFile context in when (stage == Stage1) $ do haddockFile %> \file -> do srcs <- hsSources context @@ -43,13 +39,6 @@ buildPackageDocumentation context at Context {..} = let dir = takeDirectory haddockHtmlLib liftIO $ removeFiles dir ["//*"] copyDirectory "utils/haddock/haddock-api/resources/html" dir - where - excluded = Or - [ Test "//haddock-prologue.txt" - , Test "//package-data.mk" - , Test "//setup-config" - , Test "//inplace-pkg-config" - , Test "//build" ] -- # Make the haddocking depend on the library .a file, to ensure -- # that we wait until the library is fully built before we haddock it diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index aa6303e..9864946 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,7 +2,6 @@ module Settings.Builders.Ghc (ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs) w import Flavour import GHC -import Settings.Path (ghcSplitPath) import Settings.Builders.Common ghcBuilderArgs :: Args diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index fa7cad5..d5dff73 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -2,7 +2,6 @@ module Settings.Flavours.Quickest (quickestFlavour) where import Flavour import Predicate -import Oracles.Config.Flag (platformSupportsSharedLibs) import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 57147e4..983292f 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -4,10 +4,8 @@ import Distribution.PackageDescription.Parse import Base import GHC -import Oracles.Config.Setting import Oracles.Dependencies (pkgDependencies) import Predicate -import Package (pkgCabalFile) import Distribution.Verbosity (silent) import Distribution.Text (display) import Distribution.Package (pkgVersion) @@ -16,7 +14,6 @@ import qualified Distribution.PackageDescription as DP ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do - win <- lift windowsHost cabalDeps <- lift $ pkgDependencies cabal lift $ need [pkgCabalFile cabal] pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile cabal From git at git.haskell.org Fri Oct 27 00:51:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --profile=- to CI build scripts. (6dc581c) Message-ID: <20171027005137.72DE33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6dc581c2a9b8c1c68980fd59fd3ceee4569d05d3/ghc >--------------------------------------------------------------- commit 6dc581c2a9b8c1c68980fd59fd3ceee4569d05d3 Author: Andrey Mokhov Date: Thu Feb 18 00:25:54 2016 +0000 Add --profile=- to CI build scripts. Fix #209. >--------------------------------------------------------------- 6dc581c2a9b8c1c68980fd59fd3ceee4569d05d3 .appveyor.yml | 2 +- .travis.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index 7ffabc3..537983c 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -39,4 +39,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --profile=- --flavour=quick inplace/bin/ghc-stage1.exe diff --git a/.travis.yml b/.travis.yml index d7e58c3..9547914 100644 --- a/.travis.yml +++ b/.travis.yml @@ -62,7 +62,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET + - ./ghc/shake-build/build.sh -j --no-progress --profile=- --flavour=quick $TARGET cache: directories: From git at git.haskell.org Fri Oct 27 00:51:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't optimize cabal stage0 build (#357) (e1aadf3) Message-ID: <20171027005137.C60A83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1aadf31f565128c609765f550e5213adbfab35d/ghc >--------------------------------------------------------------- commit e1aadf31f565128c609765f550e5213adbfab35d Author: Ben Gamari Date: Tue Jul 11 17:24:01 2017 -0400 Don't optimize cabal stage0 build (#357) >--------------------------------------------------------------- e1aadf31f565128c609765f550e5213adbfab35d hadrian.cabal | 1 + src/Settings/Default.hs | 5 ++++- src/Settings/Packages/Cabal.hs | 11 +++++++++++ 3 files changed, 16 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index fbda4b0..1178cb4 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -91,6 +91,7 @@ executable hadrian , Settings.Flavours.Quick , Settings.Flavours.Quickest , Settings.Packages.Base + , Settings.Packages.Cabal , Settings.Packages.Compiler , Settings.Packages.Ghc , Settings.Packages.GhcCabal diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 3ad1fab..19c6937 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -30,6 +30,7 @@ import Settings.Builders.Ld import Settings.Builders.Make import Settings.Builders.Tar import Settings.Packages.Base +import Settings.Packages.Cabal import Settings.Packages.Compiler import Settings.Packages.Ghc import Settings.Packages.GhcCabal @@ -268,6 +269,7 @@ disableWarningArgsLibs = do defaultPackageArgs :: Args defaultPackageArgs = mconcat [ basePackageArgs + , cabalPackageArgs , compilerPackageArgs , ghcPackageArgs , ghcCabalPackageArgs @@ -279,4 +281,5 @@ defaultPackageArgs = mconcat , runGhcPackageArgs , disableWarningArgsStage0 , disableWarningArgsStage1 - , disableWarningArgsLibs ] + , disableWarningArgsLibs + ] diff --git a/src/Settings/Packages/Cabal.hs b/src/Settings/Packages/Cabal.hs new file mode 100644 index 0000000..eddee75 --- /dev/null +++ b/src/Settings/Packages/Cabal.hs @@ -0,0 +1,11 @@ +module Settings.Packages.Cabal where + +import GHC +import Predicate + +cabalPackageArgs :: Args +cabalPackageArgs = package cabal ? do + -- Cabal is a rather large library and quite slow to compile. Moreover, we + -- build it for stage0 only so we can link ghc-pkg against it, so there is + -- little reason to spend the effort to optimize it. + stage Stage0 ? builder Ghc ? append [ "-O0" ] From git at git.haskell.org Fri Oct 27 00:51:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing resource dependency to buildBinary. (dfce0db) Message-ID: <20171027005141.8BC453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfce0db830f71511065a5475934a9791c0eb9524/ghc >--------------------------------------------------------------- commit dfce0db830f71511065a5475934a9791c0eb9524 Author: Andrey Mokhov Date: Thu Feb 18 08:36:38 2016 +0000 Add missing resource dependency to buildBinary. See #206. >--------------------------------------------------------------- dfce0db830f71511065a5475934a9791c0eb9524 src/Rules.hs | 2 +- src/Rules/Program.hs | 16 ++++++++-------- 2 files changed, 9 insertions(+), 9 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 444a2cb..0136c27 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -75,7 +75,7 @@ packageRules = do , buildPackageDocumentation , buildPackageGhciLibrary , generatePackageCode - , buildProgram + , buildProgram readPackageDb , registerPackage writePackageDb ] buildRules :: Rules () diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index d7fdaad..6eaa821 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -31,8 +31,8 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper)] -buildProgram :: Context -> Rules () -buildProgram context @ (Context {..}) = do +buildProgram :: [(Resource, Int)] -> Context -> Rules () +buildProgram rs context @ (Context {..}) = do let match file = case programPath stage package of Nothing -> False Just program -> program == file @@ -45,15 +45,15 @@ buildProgram context @ (Context {..}) = do match ?> \bin -> do windows <- windowsHost if windows - then buildBinary context bin -- We don't build wrappers on Windows + then buildBinary rs context bin -- We don't build wrappers on Windows else case find ((== context) . fst) wrappers of - Nothing -> buildBinary context bin -- No wrapper found + Nothing -> buildBinary rs context bin -- No wrapper found Just (_, wrapper) -> do let Just wrappedBin = computeWrappedPath bin need [wrappedBin] buildWrapper context wrapper bin wrappedBin - matchWrapped ?> \bin -> buildBinary context bin + matchWrapped ?> \bin -> buildBinary rs context bin -- Replace programInplacePath with programInplaceLibPath in a given path computeWrappedPath :: FilePath -> Maybe FilePath @@ -70,8 +70,8 @@ buildWrapper context @ (Context stage package _) wrapper wrapperPath binPath = d -- TODO: Get rid of the Paths_hsc2hs.o hack. -- TODO: Do we need to consider other ways when building programs? -buildBinary :: Context -> FilePath -> Action () -buildBinary context @ (Context stage package _) bin = do +buildBinary :: [(Resource, Int)] -> Context -> FilePath -> Action () +buildBinary rs context @ (Context stage package _) bin = do let buildPath = targetPath stage package -/- "build" cSrcs <- cSources context -- TODO: remove code duplication (Library.hs) hSrcs <- hSources context @@ -100,7 +100,7 @@ buildBinary context @ (Context stage package _) bin = do then [ pkgPath package -/- src <.> "hs" | src <- hSrcs ] else objs need $ binDeps ++ libs - build $ Target context (Ghc stage) binDeps [bin] + buildWithResources rs $ Target context (Ghc stage) binDeps [bin] synopsis <- interpretInContext context $ getPkgData Synopsis putSuccess $ renderProgram ("'" ++ pkgNameString package ++ "' (" ++ show stage ++ ").") From git at git.haskell.org Fri Oct 27 00:51:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix validate's dependency on generated files (#362) (31f9640) Message-ID: <20171027005141.F17423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31f9640125cf74dd96b1c210143cb3772656bd35/ghc >--------------------------------------------------------------- commit 31f9640125cf74dd96b1c210143cb3772656bd35 Author: Zhen Zhang Date: Sat Jul 15 21:02:05 2017 +0800 Fix validate's dependency on generated files (#362) >--------------------------------------------------------------- 31f9640125cf74dd96b1c210143cb3772656bd35 src/Rules/Test.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 08eca05..fc059ab 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -5,6 +5,7 @@ import Builder import Expression import Flavour import GHC +import qualified Rules.Generate import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Path @@ -16,6 +17,7 @@ import Util testRules :: Rules () testRules = do "validate" ~> do + need $ Rules.Generate.inplaceLibCopyTargets needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc From git at git.haskell.org Fri Oct 27 00:51:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (9a34338) Message-ID: <20171027005145.AAC623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a34338c6dd82ea5df18d0443e63e0a66b1b123e/ghc >--------------------------------------------------------------- commit 9a34338c6dd82ea5df18d0443e63e0a66b1b123e Author: Andrey Mokhov Date: Sun Jul 16 23:55:02 2017 +0100 Minor revision >--------------------------------------------------------------- 9a34338c6dd82ea5df18d0443e63e0a66b1b123e src/Predicate.hs | 6 ++- src/Settings/Builders/Cc.hs | 14 +++--- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Default.hs | 111 +++++++++++++++++++++---------------------- 4 files changed, 66 insertions(+), 68 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 9a34338c6dd82ea5df18d0443e63e0a66b1b123e From git at git.haskell.org Fri Oct 27 00:51:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to install-related commands on Windows. Minor revision. (31890f3) Message-ID: <20171027005149.780103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31890f39222ffffff7a17343925a70c5f13df83b/ghc >--------------------------------------------------------------- commit 31890f39222ffffff7a17343925a70c5f13df83b Author: Andrey Mokhov Date: Mon Jul 17 01:28:24 2017 +0100 Fix paths to install-related commands on Windows. Minor revision. See #345 >--------------------------------------------------------------- 31890f39222ffffff7a17343925a70c5f13df83b src/Oracles/Path.hs | 3 ++- src/Rules/Install.hs | 18 ++++++++-------- src/Util.hs | 60 ++++++++++++++++++++++++++++------------------------ 3 files changed, 43 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 31890f39222ffffff7a17343925a70c5f13df83b From git at git.haskell.org Fri Oct 27 00:51:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make RecordWildCards a default extension. (548a30b) Message-ID: <20171027005145.3C22A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/548a30b993efcdad064a6d9b14deb5b7a40b681d/ghc >--------------------------------------------------------------- commit 548a30b993efcdad064a6d9b14deb5b7a40b681d Author: Andrey Mokhov Date: Fri Feb 19 00:00:14 2016 +0000 Make RecordWildCards a default extension. See #207. >--------------------------------------------------------------- 548a30b993efcdad064a6d9b14deb5b7a40b681d build.bat | 1 + build.sh | 1 + shaking-up-ghc.cabal | 2 +- src/Rules/Actions.hs | 1 - src/Rules/Compile.hs | 1 - src/Rules/Data.hs | 1 - src/Rules/Dependencies.hs | 1 - src/Rules/Documentation.hs | 1 - src/Rules/Library.hs | 1 - src/Rules/Program.hs | 1 - src/Rules/Register.hs | 1 - 11 files changed, 3 insertions(+), 9 deletions(-) diff --git a/build.bat b/build.bat index 10a6969..465d957 100644 --- a/build.bat +++ b/build.bat @@ -4,6 +4,7 @@ @set ghcArgs=--make ^ -Wall ^ -fno-warn-name-shadowing ^ + -XRecordWildCards ^ src/Main.hs ^ -isrc ^ -rtsopts ^ diff --git a/build.sh b/build.sh index 77c9fa4..7c070e9 100755 --- a/build.sh +++ b/build.sh @@ -36,6 +36,7 @@ ghc \ "$root/src/Main.hs" \ -Wall \ -fno-warn-name-shadowing \ + -XRecordWildCards \ -i"$root/src" \ -rtsopts \ -with-rtsopts=-I0 \ diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 684e89e..fc0744d 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -108,13 +108,13 @@ executable ghc-shake , Way default-language: Haskell2010 + default-extensions: RecordWildCards other-extensions: DeriveDataTypeable , DeriveGeneric , FlexibleInstances , GeneralizedNewtypeDeriving , LambdaCase , OverloadedStrings - , RecordWildCards , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5f8f583..c69298e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, applyPatch, fixFile, runConfigure, runMake, diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index f62c644..c9a1bba 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Compile (compilePackage) where import Base diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index f47e8d0..0e27699 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Data (buildPackageData) where import qualified System.Directory as IO diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 330c821..f2a2141 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Dependencies (buildPackageDependencies) where import Development.Shake.Util (parseMakefile) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index e3b0e7d..7e98e27 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Documentation (buildPackageDocumentation) where import Base diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index c6d92a5..980139f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Library ( buildPackageLibrary, buildPackageGhciLibrary, cSources, hSources ) where diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 6eaa821..af6023d 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Program (buildProgram) where import Data.Char diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 85fac80..bddce8a 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE RecordWildCards #-} module Rules.Register (registerPackage) where import Base From git at git.haskell.org Fri Oct 27 00:51:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant newCache. (57c623d) Message-ID: <20171027005149.18CF83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57c623dbc3e8eed480ed5b0812aa8282bea22064/ghc >--------------------------------------------------------------- commit 57c623dbc3e8eed480ed5b0812aa8282bea22064 Author: Andrey Mokhov Date: Fri Feb 19 00:30:00 2016 +0000 Drop redundant newCache. See #210. >--------------------------------------------------------------- 57c623dbc3e8eed480ed5b0812aa8282bea22064 src/Oracles/ModuleFiles.hs | 7 ++----- 1 file changed, 2 insertions(+), 5 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 391990e..d8b1ae7 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -38,8 +38,8 @@ haskellModuleFiles stage pkg = do return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) moduleFilesOracle :: Rules () -moduleFilesOracle = do - answer <- newCache $ \(modules, dirs) -> do +moduleFilesOracle = void $ + addOracle $ \(ModuleFilesKey (modules, dirs)) -> do let decodedPairs = map decodeModule modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedPairs @@ -55,6 +55,3 @@ moduleFilesOracle = do return (map (fullDir -/-) found, mDir) return $ sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] - - _ <- addOracle $ \(ModuleFilesKey query) -> answer query - return () From git at git.haskell.org Fri Oct 27 00:51:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (e1d05c5) Message-ID: <20171027005153.1FC323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1d05c561f1ab7d939dc4decf5ca143a3bd07a5e/ghc >--------------------------------------------------------------- commit e1d05c561f1ab7d939dc4decf5ca143a3bd07a5e Author: Andrey Mokhov Date: Fri Feb 19 00:35:44 2016 +0000 Add comments. See #210. >--------------------------------------------------------------- e1d05c561f1ab7d939dc4decf5ca143a3bd07a5e src/Oracles/ModuleFiles.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index d8b1ae7..b831f76 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -37,6 +37,16 @@ haskellModuleFiles stage pkg = do return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) +-- | This is an important oracle whose role is to find and cache module source +-- files. More specifically, it takes a list of module names @modules@ and a +-- list of directories @dirs@ as arguments, and computes a sorted list of pairs +-- of the form @(A.B.C, dir/A/B/C.extension)@, such that @A.B.C@ belongs to +-- @modules@, @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists. +-- For example, for 'compiler' package given +-- @modules = ["CodeGen.Platform.ARM", "Lexer"]@, and +-- @dirs = ["codeGen", "parser"]@, it produces +-- @[("CodeGen.Platform.ARM", "codeGen/CodeGen/Platform/ARM.hs"), +-- ("Lexer", "parser/Lexer.x")]@. moduleFilesOracle :: Rules () moduleFilesOracle = void $ addOracle $ \(ModuleFilesKey (modules, dirs)) -> do From git at git.haskell.org Fri Oct 27 00:51:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use mv command to move files (374d7b1) Message-ID: <20171027005153.733D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/374d7b124f474ff8bf6b327fb63cb41860f2aef3/ghc >--------------------------------------------------------------- commit 374d7b124f474ff8bf6b327fb63cb41860f2aef3 Author: Andrey Mokhov Date: Mon Jul 17 01:35:18 2017 +0100 Use mv command to move files See #345 >--------------------------------------------------------------- 374d7b124f474ff8bf6b327fb63cb41860f2aef3 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 5f60fc1..e873ddc 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -115,7 +115,7 @@ copyFileUntracked source target = do moveFile :: FilePath -> FilePath -> Action () moveFile source target = do putProgressInfo $ renderAction "Move file" source target - liftIO $ IO.renameFile source target + quietly $ cmd ["mv", source, target] -- | Remove a file that doesn't necessarily exist. removeFile :: FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:51:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor oracles, drop redundant newCache. (13ad050) Message-ID: <20171027005156.9C22C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13ad050070d32c5c6267af8fba60125af878147c/ghc >--------------------------------------------------------------- commit 13ad050070d32c5c6267af8fba60125af878147c Author: Andrey Mokhov Date: Fri Feb 19 01:15:10 2016 +0000 Refactor oracles, drop redundant newCache. >--------------------------------------------------------------- 13ad050070d32c5c6267af8fba60125af878147c src/Oracles/ArgsHash.hs | 5 ++--- src/Oracles/Dependencies.hs | 1 - src/Oracles/LookupInPath.hs | 12 +++++------- src/Oracles/PackageData.hs | 5 ++--- src/Oracles/PackageDb.hs | 5 ++--- src/Oracles/PackageDeps.hs | 8 ++++---- src/Oracles/WindowsPath.hs | 10 ++++------ 7 files changed, 19 insertions(+), 27 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 796e753..aec0dc9 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -29,6 +29,5 @@ checkArgsHash target = when trackBuildSystem $ do -- Oracle for storing per-target argument list hashes argsHashOracle :: Rules () -argsHashOracle = do - _ <- addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs - return () +argsHashOracle = void $ + addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 8895758..b34535b 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -33,6 +33,5 @@ dependenciesOracle = do putOracle $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return . Map.fromList $ map (\(x:xs) -> (x, xs)) contents - _ <- addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file return () diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 2f6e713..0ea03fd 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -15,13 +15,11 @@ lookupInPath name | otherwise = return name lookupInPathOracle :: Rules () -lookupInPathOracle = do - answer <- newCache $ \query -> do - maybePath <- liftIO $ findExecutable query +lookupInPathOracle = void $ + addOracle $ \(LookupInPath name) -> do + maybePath <- liftIO $ findExecutable name path <- case maybePath of Just value -> return $ unifyPath value - Nothing -> putError $ "Cannot find executable '" ++ query ++ "'." - putOracle $ "Executable found: " ++ query ++ " => " ++ path + Nothing -> putError $ "Cannot find executable '" ++ name ++ "'." + putOracle $ "Executable found: " ++ name ++ " => " ++ path return path - _ <- addOracle $ \(LookupInPath query) -> answer query - return () diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index d176839..ba3e205 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -86,10 +86,9 @@ pkgDataList packageData = fmap (map unquote . words) $ case packageData of -- Oracle for 'package-data.mk' files packageDataOracle :: Rules () packageDataOracle = do - pkgDataContents <- newCache $ \file -> do + keys <- newCache $ \file -> do need [file] putOracle $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - _ <- addOracle $ \(PackageDataKey (file, key)) -> - Map.lookup key <$> pkgDataContents file + _ <- addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file return () diff --git a/src/Oracles/PackageDb.hs b/src/Oracles/PackageDb.hs index 97a2a5c..b644989 100644 --- a/src/Oracles/PackageDb.hs +++ b/src/Oracles/PackageDb.hs @@ -12,12 +12,11 @@ import Settings.Paths import Target packageDbOracle :: Rules () -packageDbOracle = do - _ <- addOracle $ \(PackageDbKey stage) -> do +packageDbOracle = void $ + addOracle $ \(PackageDbKey stage) -> do let dir = packageDbDirectory stage file = dir -/- "package.cache" unlessM (liftIO $ IO.doesFileExist file) $ do removeDirectoryIfExists dir build $ Target (vanillaContext stage ghcPkg) (GhcPkg stage) [] [dir] putSuccess $ "| Successfully initialised " ++ dir - return () diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 94cdd91..6a5f7dd 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -8,9 +8,9 @@ import Package newtype PackageDepsKey = PackageDepsKey PackageName deriving (Show, Typeable, Eq, Hashable, Binary, NFData) --- packageDeps name is an action that given a package looks up its dependencies --- in Base.packageDependencies file. The dependencies need to be computed by --- scanning package cabal files (see Rules.Cabal). +-- @packageDeps name@ is an action that given a 'Package' looks up its +-- dependencies in 'Base.packageDependencies' file. The dependencies need to be +-- computed by scanning package cabal files (see Rules.Cabal). packageDeps :: Package -> Action [PackageName] packageDeps pkg = do res <- askOracle . PackageDepsKey . pkgName $ pkg @@ -23,6 +23,6 @@ packageDepsOracle = do putOracle $ "Reading package dependencies..." contents <- readFileLines packageDependencies return . Map.fromList $ - [ (head ps, tail ps) | line <- contents, let ps = map PackageName $ words line ] + [ (p, ps) | line <- contents, let p:ps = map PackageName $ words line ] _ <- addOracle $ \(PackageDepsKey pkg) -> Map.lookup pkg <$> deps () return () diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index 3cbf1f1..a0343fb 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -15,7 +15,7 @@ topDirectory = do ghcSourcePath <- setting GhcSourcePath fixAbsolutePathOnWindows ghcSourcePath --- Fix an absolute path on Windows: +-- | Fix an absolute path on Windows: -- * "/c/" => "C:/" -- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" fixAbsolutePathOnWindows :: FilePath -> Action FilePath @@ -29,13 +29,11 @@ fixAbsolutePathOnWindows path = do else return path --- Detecting path mapping on Windows. This is slow and requires caching. +-- | Compute path mapping on Windows. This is slow and requires caching. windowsPathOracle :: Rules () -windowsPathOracle = do - answer <- newCache $ \path -> do +windowsPathOracle = void $ + addOracle $ \(WindowsPath path) -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] let windowsPath = unifyPath $ dropWhileEnd isSpace out putOracle $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath - _ <- addOracle $ \(WindowsPath query) -> answer query - return () From git at git.haskell.org Fri Oct 27 00:51:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:51:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CircleCI script (#364) (076e53f) Message-ID: <20171027005156.F35B53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/076e53fe9637ed6dbc3d4a926b0d87d597666666/ghc >--------------------------------------------------------------- commit 076e53fe9637ed6dbc3d4a926b0d87d597666666 Author: Zhen Zhang Date: Tue Jul 18 01:05:45 2017 +0800 Add CircleCI script (#364) >--------------------------------------------------------------- 076e53fe9637ed6dbc3d4a926b0d87d597666666 circle.yml | 41 +++++++++++++++++++++++++++++++++++++++++ 1 file changed, 41 insertions(+) diff --git a/circle.yml b/circle.yml new file mode 100644 index 0000000..457add7 --- /dev/null +++ b/circle.yml @@ -0,0 +1,41 @@ +machine: + xcode: + version: 8.0 + environment: + MODE: --flavour=quickest --integer-simple + +dependencies: + override: + - brew update + - brew install ghc cabal-install + - cabal update + - cabal install alex happy ansi-terminal mtl shake quickcheck + cache_directories: + - $HOME/.cabal + - $HOME/.ghc + +compile: + override: + # Fetch GHC sources into ./ghc + - git --version + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git clone --depth 1 --recursive git://github.com/ghc/ghc + + - mkdir ghc/hadrian + # move hadrian's .git into ./ghc/hadrian and perform a hard reset in order to regenerate Hadrian files + - mv .git ghc/hadrian + # NOTE: we must write them in the same line because each line + # in CircleCI is a separate process, thus you can't "cd" for the other lines + - cd ghc/hadrian; git reset --hard HEAD + + # XXX: export PATH doesn't work well either, so we use inline env + # Self test + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh selftest + + # Build GHC + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + +test: + override: + # Test GHC binary + - ghc/inplace/bin/ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:52:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor paths using Context. (badd551) Message-ID: <20171027005200.351273A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/badd551338ac11ef851d8882b2496de6c31d004f/ghc >--------------------------------------------------------------- commit badd551338ac11ef851d8882b2496de6c31d004f Author: Andrey Mokhov Date: Fri Feb 19 02:49:11 2016 +0000 Refactor paths using Context. See #207. >--------------------------------------------------------------- badd551338ac11ef851d8882b2496de6c31d004f src/Builder.hs | 31 +++++++++++++------------ src/Expression.hs | 18 +++++++++------ src/GHC.hs | 36 ++++++++++++++++------------- src/Oracles/ModuleFiles.hs | 20 ++++++++-------- src/Rules.hs | 12 +++++----- src/Rules/Clean.hs | 3 ++- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 30 ++++++++++++------------ src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 6 ++--- src/Rules/Generate.hs | 23 +++++++++++-------- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Rules/Program.hs | 12 +++++----- src/Rules/Register.hs | 10 ++++---- src/Settings.hs | 22 ++++++++---------- src/Settings/Builders/Common.hs | 4 ++-- src/Settings/Builders/Ghc.hs | 11 +++++---- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Builders/GhcPkg.hs | 6 ++--- src/Settings/Builders/Haddock.hs | 6 ++--- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/Hp2ps.hs | 2 +- src/Settings/Packages/Rts.hs | 6 ++--- src/Settings/Packages/Touchy.hs | 2 +- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/Paths.hs | 48 ++++++++++++++++++++------------------- 32 files changed, 177 insertions(+), 161 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 badd551338ac11ef851d8882b2496de6c31d004f From git at git.haskell.org Fri Oct 27 00:52:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CircleCI badge (1400b14) Message-ID: <20171027005200.77E0E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1400b148157e781c55165bfaf4d706477f3d36be/ghc >--------------------------------------------------------------- commit 1400b148157e781c55165bfaf4d706477f3d36be Author: Andrey Mokhov Date: Mon Jul 17 19:12:04 2017 +0100 Add CircleCI badge [skip ci] >--------------------------------------------------------------- 1400b148157e781c55165bfaf4d706477f3d36be README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index d65b98c..3e5318a 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Hadrian ======= -[![Linux & OS X status](https://img.shields.io/travis/snowleopard/hadrian/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/hadrian) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/hadrian/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/hadrian) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) [![OS X status](https://img.shields.io/circleci/project/github/snowleopard/hadrian.svg?label=OS%20X)](https://circleci.com/gh/snowleopard/hadrian) Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current From git at git.haskell.org Fri Oct 27 00:52:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor moduleFilesOracle, work in progress. (903ab6c) Message-ID: <20171027005204.0CA203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/903ab6c7579627c52c07af7f9f8965a864af0187/ghc >--------------------------------------------------------------- commit 903ab6c7579627c52c07af7f9f8965a864af0187 Author: Andrey Mokhov Date: Fri Feb 19 18:31:30 2016 +0000 Refactor moduleFilesOracle, work in progress. See #210. >--------------------------------------------------------------- 903ab6c7579627c52c07af7f9f8965a864af0187 src/Oracles/ModuleFiles.hs | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 67d68f3..a5e40ed 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -7,7 +7,7 @@ import Oracles.PackageData import Package import Settings.Paths -newtype ModuleFilesKey = ModuleFilesKey ([String], [FilePath]) +newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) moduleFiles :: Context -> Action [FilePath] @@ -16,7 +16,7 @@ moduleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (modules, dirs) + found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (dirs, modules) return $ map snd found haskellModuleFiles :: Context -> Action ([FilePath], [String]) @@ -27,8 +27,8 @@ haskellModuleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - foundSrcDirs <- askOracle $ ModuleFilesKey (modules, dirs ) - foundAutogen <- askOracle $ ModuleFilesKey (modules, [autogen]) + foundSrcDirs <- askOracle $ ModuleFilesKey (dirs , modules) + foundAutogen <- askOracle $ ModuleFilesKey ([autogen], modules) let found = foundSrcDirs ++ foundAutogen missingMods = modules `minusOrd` (sort $ map fst found) @@ -38,18 +38,18 @@ haskellModuleFiles context @ (Context {..}) = do return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) -- | This is an important oracle whose role is to find and cache module source --- files. More specifically, it takes a list of module names @modules@ and a --- list of directories @dirs@ as arguments, and computes a sorted list of pairs --- of the form @(A.B.C, dir/A/B/C.extension)@, such that @A.B.C@ belongs to --- @modules@, @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists. --- For example, for 'compiler' package given --- @modules = ["CodeGen.Platform.ARM", "Lexer"]@, and --- @dirs = ["codeGen", "parser"]@, it produces --- @[("CodeGen.Platform.ARM", "codeGen/CodeGen/Platform/ARM.hs"), --- ("Lexer", "parser/Lexer.x")]@. +-- files. More specifically, it takes a list of directories @dirs@ and a sorted +-- list of module names @modules@ as arguments, and for each module, e.g. +-- @A.B.C@, returns a FilePath of the form @dir/A/B/C.extension@, such that +-- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or Nothing +-- if there is no such file. If more than one matching file is found an error is +-- raised. For example, for the 'compiler' package given +-- @dirs = ["codeGen", "parser"]@, and +-- @modules = ["CodeGen.Platform.ARM", "Lexer", "Missing.Module"]@, it produces +-- @[Just "codeGen/CodeGen/Platform/ARM.hs", Just "parser/Lexer.x", Nothing]@. moduleFilesOracle :: Rules () moduleFilesOracle = void $ - addOracle $ \(ModuleFilesKey (modules, dirs)) -> do + addOracle $ \(ModuleFilesKey (dirs, modules)) -> do let decodedPairs = map decodeModule modules modDirFiles = map (bimap head sort . unzip) . groupBy ((==) `on` fst) $ decodedPairs From git at git.haskell.org Fri Oct 27 00:52:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Untrack copied artifacts (#365) (6395cf5) Message-ID: <20171027005204.3CA483A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6395cf549921934602563cfae645e6707b171fac/ghc >--------------------------------------------------------------- commit 6395cf549921934602563cfae645e6707b171fac Author: Zhen Zhang Date: Tue Jul 18 05:26:00 2017 +0800 Untrack copied artifacts (#365) >--------------------------------------------------------------- 6395cf549921934602563cfae645e6707b171fac src/Rules/Install.hs | 13 ++++--------- 1 file changed, 4 insertions(+), 9 deletions(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 57cf008..058e160 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -194,22 +194,17 @@ installPackages = do need [ ghcCabalInplace ] let cabalFile = pkgCabalFile pkg - -- HsColour sources - -- QUESTION: what is the output of GhcCabalHsColour? - whenM (isSpecified HsColour) $ do - top <- interpretInContext context getTopDirectory - let installDistDir = top -/- buildPath context - -- HACK: copy stuff back to the place favored by ghc-cabal - quietly $ copyDirectoryContents (Not excluded) - installDistDir (installDistDir -/- "build") pkgConf <- pkgConfFile context need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf - build $ Target context GhcCabalHsColour [cabalFile] [] -- HACK (#318): copy stuff back to the place favored by ghc-cabal quietly $ copyDirectoryContents (Not excluded) installDistDir (installDistDir -/- "build") + + whenM (isSpecified HsColour) $ + build $ Target context GhcCabalHsColour [cabalFile] [] + pref <- setting InstallPrefix unit $ cmd ghcCabalInplace [ "copy" From git at git.haskell.org Fri Oct 27 00:52:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Document and test encode/decodeModule. (5e32c91) Message-ID: <20171027005207.7A78A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e32c9147ba23b886ae6154200fc7961481f4bd9/ghc >--------------------------------------------------------------- commit 5e32c9147ba23b886ae6154200fc7961481f4bd9 Author: Andrey Mokhov Date: Sat Feb 20 22:40:41 2016 +0000 Document and test encode/decodeModule. See #197, #210. >--------------------------------------------------------------- 5e32c9147ba23b886ae6154200fc7961481f4bd9 src/Base.hs | 7 +++++-- src/Rules/Selftest.hs | 14 ++++++++++++++ 2 files changed, 19 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7d63fa0..7217834 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -98,13 +98,16 @@ versionToInt s = major * 1000 + minor * 10 + patch -- | Given a module name extract the directory and file name, e.g.: -- --- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity") +-- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") +-- > decodeModule "Prelude" == ("./", "Prelude") decodeModule :: String -> (FilePath, String) decodeModule = splitFileName . replaceEq '.' '/' -- | Given the directory and file name find the corresponding module name, e.g.: -- --- > encodeModule "Data/Functor/" "Identity.hs" = "Data.Functor.Identity" +-- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" +-- > encodeModule "./" "Prelude" == "Prelude" +-- > uncurry encodeModule (decodeModule name) == name encodeModule :: FilePath -> String -> String encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 70a4023..c156b44 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -24,6 +24,7 @@ selftestRules = testWays testChunksOfSize testMatchVersionedFilePath + testModuleNames testWays :: Action () testWays = do @@ -54,3 +55,16 @@ testMatchVersionedFilePath = do matchVersionedFilePath prefix suffix (prefix ++ version ++ suffix) where versions = listOf . elements $ '-' : '.' : ['0'..'9'] + +testModuleNames :: Action () +testModuleNames = do + putBuild $ "==== Encode/decode module name" + test $ encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" + test $ encodeModule "./" "Prelude" == "Prelude" + + test $ decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") + test $ decodeModule "Prelude" == ("./", "Prelude") + + test $ forAll names $ \n -> uncurry encodeModule (decodeModule n) == n + where + names = intercalate "." <$> listOf1 (listOf1 $ elements "abcABC123_'") From git at git.haskell.org Fri Oct 27 00:52:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix on Windows install (0ca5f3a) Message-ID: <20171027005207.B1E313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ca5f3a8245b92f844e4e68ce511e92ff186bbdc/ghc >--------------------------------------------------------------- commit 0ca5f3a8245b92f844e4e68ce511e92ff186bbdc Author: Andrey Mokhov Date: Tue Jul 18 00:12:29 2017 +0100 Fix on Windows install See #345 >--------------------------------------------------------------- 0ca5f3a8245b92f844e4e68ce511e92ff186bbdc src/Oracles/DirectoryContents.hs | 7 +- src/Rules/Install.hs | 204 +++++++++++++++++++-------------------- src/Util.hs | 4 +- 3 files changed, 109 insertions(+), 106 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 0ca5f3a8245b92f844e4e68ce511e92ff186bbdc From git at git.haskell.org Fri Oct 27 00:52:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add lookupAll and test it. (e054479) Message-ID: <20171027005210.E4E0E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e0544796443fa3f220ac77f68891b6c4fc0f09bb/ghc >--------------------------------------------------------------- commit e0544796443fa3f220ac77f68891b6c4fc0f09bb Author: Andrey Mokhov Date: Sun Feb 21 00:01:08 2016 +0000 Add lookupAll and test it. See #210. >--------------------------------------------------------------- e0544796443fa3f220ac77f68891b6c4fc0f09bb src/Base.hs | 22 ++++++++++++++++++---- src/Rules/Selftest.hs | 15 +++++++++++++++ 2 files changed, 33 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 7217834..324feb8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,7 +23,7 @@ module Base ( putColoured, putOracle, putBuild, putSuccess, putError, -- * Miscellaneous utilities - minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, + minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath ) where @@ -165,9 +165,23 @@ intersectOrd cmp = loop loop [] _ = [] loop _ [] = [] loop (x:xs) (y:ys) = case cmp x y of - LT -> loop xs (y:ys) - EQ -> x : loop xs ys - GT -> loop (x:xs) ys + LT -> loop xs (y:ys) + EQ -> x : loop xs ys + GT -> loop (x:xs) ys + +-- | Lookup all elements of a given sorted list in a given sorted dictionary. +-- @lookupAll list dict@ is equivalent to @map (flip lookup dict) list@ but has +-- linear complexity O(|list| + |dist|) instead of quadratic O(|list| * |dict|). +-- +-- > lookupAll ["b", "c"] [("a", 1), ("c", 3), ("d", 4)] == [Nothing, Just 3] +-- > list & dict are sorted: lookupAll list dict == map (flip lookup dict) list +lookupAll :: Ord a => [a] -> [(a, b)] -> [Maybe b] +lookupAll [] _ = [] +lookupAll (_:xs) [] = Nothing : lookupAll xs [] +lookupAll (x:xs) (y:ys) = case compare x (fst y) of + LT -> Nothing : lookupAll xs (y:ys) + EQ -> Just (snd y) : lookupAll xs (y:ys) + GT -> lookupAll (x:xs) ys -- | Remove a file that doesn't necessarily exist removeFileIfExists :: FilePath -> Action () diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index c156b44..f549b0f 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -25,6 +25,7 @@ selftestRules = testChunksOfSize testMatchVersionedFilePath testModuleNames + testLookupAll testWays :: Action () testWays = do @@ -68,3 +69,17 @@ testModuleNames = do test $ forAll names $ \n -> uncurry encodeModule (decodeModule n) == n where names = intercalate "." <$> listOf1 (listOf1 $ elements "abcABC123_'") + +testLookupAll :: Action () +testLookupAll = do + putBuild $ "==== lookupAll" + test $ lookupAll ["b" , "c" ] [("a", 1), ("c", 3), ("d", 4)] + == [Nothing, Just (3 :: Int)] + test $ forAll dicts $ \dict -> forAll extras $ \extra -> + let items = sort $ map fst dict ++ extra + in lookupAll items (sort dict) == map (flip lookup dict) items + where + dicts :: Gen [(Int, Int)] + dicts = nubBy ((==) `on` fst) <$> vector 20 + extras :: Gen [Int] + extras = vector 20 From git at git.haskell.org Fri Oct 27 00:52:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghc-iserv wrapper (#367) (05b3ebe) Message-ID: <20171027005211.3DA4C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/05b3ebe6911890145c12bd8022b2cc11002de98c/ghc >--------------------------------------------------------------- commit 05b3ebe6911890145c12bd8022b2cc11002de98c Author: Zhen Zhang Date: Tue Jul 18 23:12:22 2017 +0800 Add ghc-iserv wrapper (#367) >--------------------------------------------------------------- 05b3ebe6911890145c12bd8022b2cc11002de98c src/GHC.hs | 9 +++++---- src/Rules/Program.hs | 26 +++++++++++++++++++++++++- src/Rules/Wrappers.hs | 24 ++++++++++++++++++++++-- src/Settings.hs | 2 +- src/Settings/Path.hs | 13 +++++++------ 5 files changed, 60 insertions(+), 14 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0f5e2fb..ce88cb0 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -116,10 +116,11 @@ builderProvenance = \case -- 'Library', the function simply returns its name. programName :: Context -> String programName Context {..} - | package == ghc = "ghc-stage" ++ show (fromEnum stage + 1) - | package == hpcBin = "hpc" - | package == runGhc = "runhaskell" - | otherwise = pkgNameString package + | package == ghc = "ghc-stage" ++ show (fromEnum stage + 1) + | package == hpcBin = "hpc" + | package == runGhc = "runhaskell" + | package == iservBin = "ghc-iserv" + | otherwise = pkgNameString package -- | Some contexts are special: their packages do have @.cabal@ metadata or -- we cannot run @ghc-cabal@ on them, e.g. because the latter hasn't been built diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 12e661b..8c9a7ab 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -34,11 +34,35 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do inplaceBinPath -/- programName context <.> exe %> \bin -> do binStage <- installStage buildBinaryAndWrapper rs (context { stage = binStage }) bin - -- We build only unwrapped binaries in inplace/lib/bin + inplaceLibBinPath -/- programName context <.> exe %> \bin -> do binStage <- installStage + if package /= iservBin then + -- We *normally* build only unwrapped binaries in inplace/lib/bin, + buildBinary rs (context { stage = binStage }) bin + else + -- build both binary and wrapper in inplace/lib/bin + -- for ghc-iserv on *nix platform now + buildBinaryAndWrapperLib rs (context { stage = binStage }) bin + + inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> do + binStage <- installStage buildBinary rs (context { stage = binStage }) bin +buildBinaryAndWrapperLib :: [(Resource, Int)] -> Context -> FilePath -> Action () +buildBinaryAndWrapperLib rs context bin = do + windows <- windowsHost + if windows + then buildBinary rs context bin -- We don't build wrappers on Windows + else case lookup context inplaceWrappers of + Nothing -> buildBinary rs context bin -- No wrapper found + Just wrapper -> do + top <- topDirectory + let libdir = top -/- inplaceLibPath + let wrappedBin = inplaceLibBinPath -/- programName context <.> "bin" + need [wrappedBin] + buildWrapper context wrapper bin (WrappedBinary libdir (takeFileName wrappedBin)) + buildBinaryAndWrapper :: [(Resource, Int)] -> Context -> FilePath -> Action () buildBinaryAndWrapper rs context bin = do windows <- windowsHost diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs index 6adf3f7..7d90067 100644 --- a/src/Rules/Wrappers.hs +++ b/src/Rules/Wrappers.hs @@ -5,8 +5,9 @@ module Rules.Wrappers ( import Base import Expression import GHC +import Settings (getPackages, latestBuildStage) import Settings.Install (installPackageDbDirectory) -import Settings.Path (inplacePackageDbDirectory) +import Settings.Path (buildPath, inplacePackageDbDirectory) import Oracles.Path (getTopDirectory, bashPath) import Oracles.Config.Setting (SettingList(..), settingList) @@ -117,13 +118,32 @@ haddockWrapper WrappedBinary{..} = do , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " -B" ++ binaryLibPath ++ " -l" ++ binaryLibPath ++ " ${1+\"$@\"}" ] +iservBinWrapper :: WrappedBinary -> Expr String +iservBinWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + activePackages <- filter isLibrary <$> getPackages + -- TODO: Figure our the reason of this hardcoded exclusion + let pkgs = activePackages \\ [ cabal, process, haskeline + , terminfo, ghcCompact, hpc, compiler ] + contexts <- catMaybes <$> mapM (\p -> do + m <- lift $ latestBuildStage p + return $ fmap (\s -> vanillaContext s p) m + ) pkgs + let buildPaths = map buildPath contexts + return $ unlines + [ "#!/bin/bash" + , "export DYLD_LIBRARY_PATH=\"" ++ intercalate ":" buildPaths ++ + "${DYLD_LIBRARY_PATH:+:$DYLD_LIBRARY_PATH}\"" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ] + wrappersCommon :: [(Context, Wrapper)] wrappersCommon = [ (vanillaContext Stage0 ghc , ghcWrapper) , (vanillaContext Stage1 ghc , ghcWrapper) , (vanillaContext Stage1 hp2ps , hp2psWrapper) , (vanillaContext Stage1 hpc , hpcWrapper) , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) - , (vanillaContext Stage2 haddock, haddockWrapper)] + , (vanillaContext Stage2 haddock, haddockWrapper) + , (vanillaContext Stage1 iservBin, iservBinWrapper) ] -- | List of wrappers for inplace artefacts inplaceWrappers :: [(Context, Wrapper)] diff --git a/src/Settings.hs b/src/Settings.hs index 8152a6e..2f75095 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -112,7 +112,7 @@ programPath context at Context {..} = do maybeLatest <- latestBuildStage package return $ do install <- (\l -> l == stage || package == ghc) <$> maybeLatest - let path = if install then installPath package else buildPath context + let path = if install then inplaceInstallPath package else buildPath context return $ path -/- programName context <.> exe pkgConfInstallPath :: FilePath diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 8814620..1b0dc13 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -5,7 +5,7 @@ module Settings.Path ( rtsContext, rtsBuildPath, rtsConfIn, shakeFilesPath,inplacePackageDbDirectory, pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, - installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, + inplaceInstallPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, pkgSetupConfigFile ) where @@ -190,11 +190,12 @@ objectPath context at Context {..} src -- | Given a 'Package', return the path where the corresponding program is -- installed. Most programs are installed in 'programInplacePath'. -installPath :: Package -> FilePath -installPath pkg - | pkg == touchy = inplaceLibBinPath - | pkg == unlit = inplaceLibBinPath - | otherwise = inplaceBinPath +inplaceInstallPath :: Package -> FilePath +inplaceInstallPath pkg + | pkg == touchy = inplaceLibBinPath + | pkg == unlit = inplaceLibBinPath + | pkg == iservBin = inplaceLibBinPath + | otherwise = inplaceBinPath -- | @ghc-split@ is a Perl script used by GHC with @-split-objs@ flag. It is -- generated in "Rules.Generators.GhcSplit". From git at git.haskell.org Fri Oct 27 00:52:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep duplicates in the intersection. (2ec9f84) Message-ID: <20171027005214.D47DE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ec9f84bce2ad28a16802b7ac901685495a6b4ff/ghc >--------------------------------------------------------------- commit 2ec9f84bce2ad28a16802b7ac901685495a6b4ff Author: Andrey Mokhov Date: Sun Feb 21 01:27:24 2016 +0000 Keep duplicates in the intersection. >--------------------------------------------------------------- 2ec9f84bce2ad28a16802b7ac901685495a6b4ff src/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 324feb8..871cd3c 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -157,7 +157,7 @@ minusOrd (x:xs) (y:ys) = case compare x y of EQ -> minusOrd xs ys GT -> minusOrd (x:xs) ys --- Explicit definition to avoid dependency on Data.List.Ordered +-- Explicit definition to avoid dependency on Data.List.Ordered. TODO: add tests -- | Intersection of two ordered lists by a predicate. intersectOrd :: (a -> b -> Ordering) -> [a] -> [b] -> [a] intersectOrd cmp = loop @@ -166,7 +166,7 @@ intersectOrd cmp = loop loop _ [] = [] loop (x:xs) (y:ys) = case cmp x y of LT -> loop xs (y:ys) - EQ -> x : loop xs ys + EQ -> x : loop xs (y:ys) GT -> loop (x:xs) ys -- | Lookup all elements of a given sorted list in a given sorted dictionary. From git at git.haskell.org Fri Oct 27 00:52:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to the projects webpage (4bdc4a4) Message-ID: <20171027005219.500203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4bdc4a4747801dba02d755ce08d356d81ede18a3/ghc >--------------------------------------------------------------- commit 4bdc4a4747801dba02d755ce08d356d81ede18a3 Author: Andrey Mokhov Date: Wed Jul 19 00:32:51 2017 +0100 Link to the projects webpage [skip ci] >--------------------------------------------------------------- 4bdc4a4747801dba02d755ce08d356d81ede18a3 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 3e5318a..8404496 100644 --- a/README.md +++ b/README.md @@ -148,6 +148,8 @@ at present and we expect a lot of further refactoring. If you would like to work on a particular issue, please let everyone know by adding a comment about this. The issues that are currently on the critical path and therefore require particular attention are listed in [#239](https://github.com/snowleopard/hadrian/issues/239). +Also have a look at [projects](https://github.com/snowleopard/hadrian/projects) +where open issues and pull requests are grouped into categories. Acknowledgements ---------------- From git at git.haskell.org Fri Oct 27 00:52:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop duplication of module names in moduleFilesOracle. (59d7bf1) Message-ID: <20171027005219.03A5E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59d7bf155a356bd662a3e74f11b4c2532464b10b/ghc >--------------------------------------------------------------- commit 59d7bf155a356bd662a3e74f11b4c2532464b10b Author: Andrey Mokhov Date: Sun Feb 21 01:28:12 2016 +0000 Drop duplication of module names in moduleFilesOracle. See #210. >--------------------------------------------------------------- 59d7bf155a356bd662a3e74f11b4c2532464b10b src/Oracles/ModuleFiles.hs | 28 +++++++++++++++++++++------- 1 file changed, 21 insertions(+), 7 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index a5e40ed..bced848 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -16,8 +16,7 @@ moduleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - found :: [(String, FilePath)] <- askOracle $ ModuleFilesKey (dirs, modules) - return $ map snd found + fmap catMaybes . askOracle $ ModuleFilesKey (dirs, modules) haskellModuleFiles :: Context -> Action ([FilePath], [String]) haskellModuleFiles context @ (Context {..}) = do @@ -29,13 +28,17 @@ haskellModuleFiles context @ (Context {..}) = do let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] foundSrcDirs <- askOracle $ ModuleFilesKey (dirs , modules) foundAutogen <- askOracle $ ModuleFilesKey ([autogen], modules) + found <- sequence $ zipWith3 addSources modules foundSrcDirs foundAutogen - let found = foundSrcDirs ++ foundAutogen - missingMods = modules `minusOrd` (sort $ map fst found) + let missingMods = map fst . filter (isNothing . snd) $ zip modules found otherFileToMod = replaceEq '/' '.' . dropExtension . dropPkgPath - (haskellFiles, otherFiles) = partition ("//*hs" ?==) (map snd found) + (haskellFiles, otherFiles) = partition ("//*hs" ?==) $ catMaybes found return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) + where + addSources _ Nothing r = return r + addSources _ l Nothing = return l + addSources m (Just f1) (Just f2) = errorMultipleSources m f1 f2 -- | This is an important oracle whose role is to find and cache module source -- files. More specifically, it takes a list of directories @dirs@ and a sorted @@ -51,7 +54,7 @@ moduleFilesOracle :: Rules () moduleFilesOracle = void $ addOracle $ \(ModuleFilesKey (dirs, modules)) -> do let decodedPairs = map decodeModule modules - modDirFiles = map (bimap head sort . unzip) + modDirFiles = map (bimap head id . unzip) . groupBy ((==) `on` fst) $ decodedPairs result <- fmap concat . forM dirs $ \dir -> do @@ -64,4 +67,15 @@ moduleFilesOracle = void $ found = intersectOrd cmp noBoot mFiles return (map (fullDir -/-) found, mDir) - return $ sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] + let pairs = sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] + multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ] + + unless (null multi) $ do + let (m, f1, f2) = head multi + errorMultipleSources m f1 f2 + + return $ lookupAll modules pairs + +errorMultipleSources :: String -> FilePath -> FilePath -> Action a +errorMultipleSources m f1 f2 = putError $ "Module " ++ m ++ + " has more than one source file: " ++ f1 ++ " and " ++ f2 ++ "." From git at git.haskell.org Fri Oct 27 00:52:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add findModuleFiles and export it. (9039a4f) Message-ID: <20171027005222.F2C0C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9039a4f1dfedbc9606d2ccef35d81d7736993f11/ghc >--------------------------------------------------------------- commit 9039a4f1dfedbc9606d2ccef35d81d7736993f11 Author: Andrey Mokhov Date: Sun Feb 21 02:21:00 2016 +0000 Add findModuleFiles and export it. See #210. >--------------------------------------------------------------- 9039a4f1dfedbc9606d2ccef35d81d7736993f11 src/Oracles/ModuleFiles.hs | 22 ++++++++++++++-------- 1 file changed, 14 insertions(+), 8 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index bced848..501bc89 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,5 +1,7 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} -module Oracles.ModuleFiles (moduleFiles, haskellModuleFiles, moduleFilesOracle) where +module Oracles.ModuleFiles ( + moduleFiles, haskellModuleFiles, moduleFilesOracle, findModuleFiles + ) where import Base import Context @@ -16,7 +18,7 @@ moduleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - fmap catMaybes . askOracle $ ModuleFilesKey (dirs, modules) + fmap catMaybes $ findModuleFiles dirs modules haskellModuleFiles :: Context -> Action ([FilePath], [String]) haskellModuleFiles context @ (Context {..}) = do @@ -26,8 +28,8 @@ haskellModuleFiles context @ (Context {..}) = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - foundSrcDirs <- askOracle $ ModuleFilesKey (dirs , modules) - foundAutogen <- askOracle $ ModuleFilesKey ([autogen], modules) + foundSrcDirs <- findModuleFiles dirs modules + foundAutogen <- findModuleFiles [autogen] modules found <- sequence $ zipWith3 addSources modules foundSrcDirs foundAutogen let missingMods = map fst . filter (isNothing . snd) $ zip modules found @@ -43,13 +45,17 @@ haskellModuleFiles context @ (Context {..}) = do -- | This is an important oracle whose role is to find and cache module source -- files. More specifically, it takes a list of directories @dirs@ and a sorted -- list of module names @modules@ as arguments, and for each module, e.g. --- @A.B.C@, returns a FilePath of the form @dir/A/B/C.extension@, such that --- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or Nothing +-- @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, such that +-- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or 'Nothing' -- if there is no such file. If more than one matching file is found an error is -- raised. For example, for the 'compiler' package given --- @dirs = ["codeGen", "parser"]@, and +-- @dirs = ["compiler/codeGen", "compiler/parser"]@, and -- @modules = ["CodeGen.Platform.ARM", "Lexer", "Missing.Module"]@, it produces --- @[Just "codeGen/CodeGen/Platform/ARM.hs", Just "parser/Lexer.x", Nothing]@. +-- @[Just "compiler/codeGen/CodeGen/Platform/ARM.hs", +-- Just "compiler/parser/Lexer.x", Nothing]@. +findModuleFiles :: [FilePath] -> [String] -> Action [Maybe FilePath] +findModuleFiles dirs modules = askOracle $ ModuleFilesKey (dirs, modules) + moduleFilesOracle :: Rules () moduleFilesOracle = void $ addOracle $ \(ModuleFilesKey (dirs, modules)) -> do From git at git.haskell.org Fri Oct 27 00:52:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test findModuleFiles. (1136a62) Message-ID: <20171027005226.6780B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1136a62c35dfe9df3774667b1e501494e2a496b1/ghc >--------------------------------------------------------------- commit 1136a62c35dfe9df3774667b1e501494e2a496b1 Author: Andrey Mokhov Date: Sun Feb 21 02:22:26 2016 +0000 Test findModuleFiles. See #197, #210. >--------------------------------------------------------------- 1136a62c35dfe9df3774667b1e501494e2a496b1 src/Rules/Selftest.hs | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f549b0f..f4890b0 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,6 +6,7 @@ import Development.Shake import Test.QuickCheck import Base +import Oracles.ModuleFiles import Settings.Builders.Ar (chunksOfSize) import Way @@ -26,6 +27,7 @@ selftestRules = testMatchVersionedFilePath testModuleNames testLookupAll + testModuleFilesOracle testWays :: Action () testWays = do @@ -83,3 +85,14 @@ testLookupAll = do dicts = nubBy ((==) `on` fst) <$> vector 20 extras :: Gen [Int] extras = vector 20 + +testModuleFilesOracle :: Action () +testModuleFilesOracle = do + putBuild $ "==== moduleFilesOracle" + result <- findModuleFiles ["compiler/codeGen", "compiler/parser"] + [ "CodeGen.Platform.ARM" + , "Lexer" + , "Missing.Module"] + test $ result == [ Just "compiler/codeGen/CodeGen/Platform/ARM.hs" + , Just "compiler/parser/Lexer.x" + , Nothing] From git at git.haskell.org Fri Oct 27 00:52:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix typo in comment (#369) (408ef4e) Message-ID: <20171027005215.2BA713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/408ef4e802ec0b89b5962bb839f11f47976897e2/ghc >--------------------------------------------------------------- commit 408ef4e802ec0b89b5962bb839f11f47976897e2 Author: Doug Wilson Date: Wed Jul 19 06:57:15 2017 +1200 Fix typo in comment (#369) [skip ci] >--------------------------------------------------------------- 408ef4e802ec0b89b5962bb839f11f47976897e2 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index ce88cb0..231eab6 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -122,7 +122,7 @@ programName Context {..} | package == iservBin = "ghc-iserv" | otherwise = pkgNameString package --- | Some contexts are special: their packages do have @.cabal@ metadata or +-- | Some contexts are special: their packages do not have @.cabal@ metadata or -- we cannot run @ghc-cabal@ on them, e.g. because the latter hasn't been built -- yet (this is the case with the 'ghcCabal' package in 'Stage0'). nonCabalContext :: Context -> Bool From git at git.haskell.org Fri Oct 27 00:52:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (061dcf1) Message-ID: <20171027005223.8F0663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/061dcf1f9b7a9dd7e907e6393ad20751054fba99/ghc >--------------------------------------------------------------- commit 061dcf1f9b7a9dd7e907e6393ad20751054fba99 Author: Andrey Mokhov Date: Wed Jul 19 01:27:44 2017 +0100 Minor revision See #238 >--------------------------------------------------------------- 061dcf1f9b7a9dd7e907e6393ad20751054fba99 src/Rules/Library.hs | 45 +++++++++++++++++---------------------------- 1 file changed, 17 insertions(+), 28 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b746279..d832264 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,6 +1,5 @@ module Rules.Library ( - buildPackageLibrary, buildPackageGhciLibrary, - buildDynamicLib + buildPackageLibrary, buildPackageGhciLibrary, buildDynamicLib ) where import Data.Char @@ -13,15 +12,15 @@ import Flavour import GHC import Oracles.ModuleFiles import Oracles.PackageData -import Oracles.Dependencies (contextDependencies) +import Oracles.Dependencies import Settings import Settings.Path import Target import UserSettings import Util -getLibraryObjs :: Context -> Action [FilePath] -getLibraryObjs context at Context{..} = do +libraryObjects :: Context -> Action [FilePath] +libraryObjects context at Context{..} = do hsObjs <- hsObjects context noHsObjs <- nonHsObjects context @@ -31,34 +30,26 @@ getLibraryObjs context at Context{..} = do split <- interpretInContext context $ splitObjects flavour let getSplitObjs = concatForM hsObjs $ \obj -> do - let dir = dropExtension obj ++ "_" ++ osuf way ++ "_split" - contents <- liftIO $ IO.getDirectoryContents dir - return . map (dir -/-) $ filter (not . all (== '.')) contents + let dir = dropExtension obj ++ "_" ++ osuf way ++ "_split" + contents <- liftIO $ IO.getDirectoryContents dir + return . map (dir -/-) $ filter (not . all (== '.')) contents (noHsObjs ++) <$> if split then getSplitObjs else return hsObjs buildDynamicLib :: Context -> Rules () buildDynamicLib context at Context{..} = do - -- macOS - matchGhcVersionedFilePath libPrefix "dylib" ?> buildDynamicLibUNIX + let path = buildPath context + libPrefix = path -/- "libHS" ++ pkgNameString package + -- OS X + matchGhcVersionedFilePath libPrefix "dylib" ?> buildDynamicLibUnix -- Linux - matchGhcVersionedFilePath libPrefix "so" ?> buildDynamicLibUNIX + matchGhcVersionedFilePath libPrefix "so" ?> buildDynamicLibUnix -- TODO: Windows where - path = buildPath context - libPrefix = path -/- "libHS" ++ pkgNameString package - - buildDynamicLibUNIX so = do + buildDynamicLibUnix so = do deps <- contextDependencies context - - forM_ deps $ \dep -> do - lib <- pkgLibraryFile dep - need [lib] - - removeFile so - - objs <- getLibraryObjs context - + need =<< mapM pkgLibraryFile deps + objs <- libraryObjects context build $ Target context (Ghc LinkHs stage) objs [so] buildPackageLibrary :: Context -> Rules () @@ -66,12 +57,10 @@ buildPackageLibrary context at Context {..} = do let path = buildPath context libPrefix = path -/- "libHS" ++ pkgNameString package matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do - removeFile a - - objs <- getLibraryObjs context - + objs <- libraryObjects context asuf <- libsuf way let isLib0 = ("//*-0" ++ asuf) ?== a + removeFile a if isLib0 then build $ Target context (Ar stage) [] [a] -- TODO: Scan for dlls else build $ Target context (Ar stage) objs [a] From git at git.haskell.org Fri Oct 27 00:52:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make OS X build faster and Add GHC 8.0.2 build on Travis CI (#370) (b7fff3b) Message-ID: <20171027005227.1E7A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b7fff3b6749a01a2ad486bff68e6e0fdeab338e4/ghc >--------------------------------------------------------------- commit b7fff3b6749a01a2ad486bff68e6e0fdeab338e4 Author: Zhen Zhang Date: Wed Jul 19 22:44:42 2017 +0800 Make OS X build faster and Add GHC 8.0.2 build on Travis CI (#370) >--------------------------------------------------------------- b7fff3b6749a01a2ad486bff68e6e0fdeab338e4 .travis.yml | 58 +++++++++++++++++++++++++++++++++++++++++++++------------- 1 file changed, 45 insertions(+), 13 deletions(-) diff --git a/.travis.yml b/.travis.yml index dd6af26..d85291a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,9 +1,36 @@ sudo: true - +language: haskell matrix: include: - os: linux env: MODE="--flavour=quickest" + compiler: "GHC 8.0.2" + addons: + apt: + packages: + - ghc-8.0.2 + - cabal-install-2.0 + - zlib1g-dev + sources: hvr-ghc + + before_install: + - PATH="/opt/ghc/8.0.2/bin:$PATH" + - PATH="/opt/cabal/2.0/bin:$PATH" + + script: + # Run internal Hadrian tests + - ./build.sh selftest + + # Build GHC + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + + # Test GHC binary + - cd .. + - inplace/bin/ghc-stage2 -e 1+2 + + - os: linux + env: MODE="--flavour=quickest" + compiler: "GHC 7.10.3" addons: apt: packages: @@ -11,17 +38,33 @@ matrix: - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc + before_install: - PATH="/opt/ghc/7.10.3/bin:$PATH" - PATH="/opt/cabal/1.22/bin:$PATH" + script: + # Run internal Hadrian tests + - ./build.sh selftest + + # Build GHC + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + + # Test GHC binary + - cd .. + - inplace/bin/ghc-stage2 -e 1+2 + - os: osx osx_image: xcode8 env: MODE="--flavour=quickest --integer-simple" before_install: - brew update - brew install ghc cabal-install - - + + script: + # Due to timeout limit of OS X build on Travis CI, + # we will ignore selftest and build only stage1 + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 install: # Add Cabal to PATH @@ -50,17 +93,6 @@ install: - cd ghc/hadrian - git reset --hard HEAD -script: - # Run internal Hadrian tests - - ./build.sh selftest - - # Build GHC - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- - - # Test GHC binary - - cd .. - - inplace/bin/ghc-stage2 -e 1+2 - cache: directories: - $HOME/.cabal From git at git.haskell.org Fri Oct 27 00:52:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (599381f) Message-ID: <20171027005230.965983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/599381f0fda1ea8fbae64b748b7b09727189f53b/ghc >--------------------------------------------------------------- commit 599381f0fda1ea8fbae64b748b7b09727189f53b Author: Andrey Mokhov Date: Wed Jul 19 16:03:35 2017 +0100 Minor revision >--------------------------------------------------------------- 599381f0fda1ea8fbae64b748b7b09727189f53b src/Oracles/Config/Setting.hs | 20 ++++++++++---------- src/Rules/Install.hs | 9 +++++---- src/Settings/Path.hs | 12 ++++++------ 3 files changed, 21 insertions(+), 20 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index c4ed10e..1bf9186 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -53,19 +53,18 @@ data Setting = BuildArch | IconvIncludeDir | IconvLibDir | CursesLibDir - -- Paths to where GHC is installed - -- ref: mk/install.mk + -- Paths to where GHC is installed (ref: mk/install.mk) | InstallPrefix | InstallBinDir | InstallLibDir | InstallDataRootDir - -- "install" utility + -- Command lines for invoking the @install@ utility | Install | InstallData | InstallProgram | InstallScript | InstallDir - -- symbolic link + -- Command line for creating a symbolic link | LnS data SettingList = ConfCcArgs Stage @@ -202,9 +201,10 @@ cmdLineLengthLimit = do -- On all other systems, we try this: _ -> 4194304 -- Cabal library needs a bit more than 2MB! --- | On Windows we normally want to make a relocatable bindist, --- to we ignore flags like libdir --- ref: mk/config.mk.in:232 +-- ref: https://ghc.haskell.org/trac/ghc/wiki/Building/Installing#HowGHCfindsitsfiles +-- | On Windows we normally build a relocatable installation, which assumes that +-- the library directory @libdir@ is in a fixed location relative to the GHC +-- binary, namely @../lib at . relocatableBuild :: Action Bool relocatableBuild = windowsHost @@ -213,10 +213,10 @@ installDocDir = do version <- setting ProjectVersion (-/- ("doc/ghc-" ++ version)) <$> setting InstallDataRootDir --- | Unix: override libdir and datadir to put ghc-specific stuff in --- a subdirectory with the version number included. -- ref: mk/install.mk:101 -- TODO: CroosCompilePrefix +-- | Unix: override @libdir@ and @datadir@ to put GHC-specific files in a +-- subdirectory with the version number included. installGhcLibDir :: Action String installGhcLibDir = do r <- relocatableBuild @@ -224,4 +224,4 @@ installGhcLibDir = do if r then return libdir else do v <- setting ProjectVersion - return (libdir -/- ("ghc-" ++ v)) + return $ libdir -/- ("ghc-" ++ v) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 525746b..77e340e 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -128,6 +128,7 @@ withLatestBuildStage pkg m = do Nothing -> return () -- ref: rules/manual-package-conf.mk +-- TODO: Should we use a temporary file instead of pkgConfInstallPath? -- | Install @package.conf.install@ for each package. Note that it will be -- recreated each time. installPackageConf :: Action () @@ -161,7 +162,7 @@ installPackages = do -- Install RTS let rtsDir = destDir ++ ghcLibDir -/- "rts" installDirectory rtsDir - ways <- interpretInContext (vanillaContext Stage1 rts) getRtsWays + ways <- interpretInContext (vanillaContext Stage1 rts) getRtsWays rtsLibs <- mapM pkgLibraryFile $ map (Context Stage1 rts) ways ffiLibs <- sequence $ map rtsLibffiLibrary ways @@ -183,14 +184,14 @@ installPackages = do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg - top <- interpretInContext context getTopDirectory + top <- topDirectory let installDistDir = top -/- buildPath context buildPackage stage pkg docDir <- installDocDir ghclibDir <- installGhcLibDir -- Copy over packages - strip <- stripCmdPath context + strip <- stripCmdPath ways <- interpretInContext context getLibraryWays let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" <.> exe -- HACK? need [ghcCabalInplace] @@ -230,7 +231,7 @@ installPackages = do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg - top <- interpretInContext context getTopDirectory + top <- topDirectory let installDistDir = top -/- buildPath context -- TODO: better reference to the built inplace binary path let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 1b0dc13..0be1838 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -14,8 +14,8 @@ import Context import Expression import GHC import Oracles.PackageData -import Oracles.Config.Setting (setting, Setting(..)) -import Oracles.Path (getTopDirectory) +import Oracles.Config.Setting +import Oracles.Path import UserSettings -- | Path to the directory containing the Shake database and other auxiliary @@ -202,12 +202,12 @@ inplaceInstallPath pkg ghcSplitPath :: FilePath ghcSplitPath = inplaceLibBinPath -/- "ghc-split" --- | Command line tool for stripping -- ref: mk/config.mk -stripCmdPath :: Context -> Action FilePath -stripCmdPath ctx = do +-- | Command line tool for stripping. +stripCmdPath :: Action FilePath +stripCmdPath = do targetPlatform <- setting TargetPlatform - top <- interpretInContext ctx getTopDirectory + top <- topDirectory case targetPlatform of "x86_64-unknown-mingw32" -> return (top -/- "inplace/mingw/bin/strip.exe") From git at git.haskell.org Fri Oct 27 00:52:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependencies. (41778b0) Message-ID: <20171027005236.CDEBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/41778b07cc7fbbb8fa0006343213a65d2c12afaf/ghc >--------------------------------------------------------------- commit 41778b07cc7fbbb8fa0006343213a65d2c12afaf Author: Andrey Mokhov Date: Fri Feb 26 00:46:11 2016 +0000 Add missing dependencies. >--------------------------------------------------------------- 41778b07cc7fbbb8fa0006343213a65d2c12afaf src/Rules/Data.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 360eb5a..1eca7d9 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -57,6 +57,7 @@ buildPackageData context @ Context {..} = do -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps priority 2.0 $ do when (package == hp2ps) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package includes <- interpretInContext context $ fromDiffExpr includesArgs let prefix = fixKey (contextPath context) ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" @@ -73,6 +74,7 @@ buildPackageData context @ Context {..} = do putSuccess $ "| Successfully generated '" ++ mk ++ "'." when (package == unlit) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package let prefix = fixKey (contextPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = unlit" @@ -82,6 +84,7 @@ buildPackageData context @ Context {..} = do putSuccess $ "| Successfully generated '" ++ mk ++ "'." when (package == touchy) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package let prefix = fixKey (contextPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = touchy" @@ -93,6 +96,7 @@ buildPackageData context @ Context {..} = do -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. when (package == ghcCabal && stage == Stage0) $ dataFile %> \mk -> do + orderOnly $ generatedDependencies stage package let prefix = fixKey (contextPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = ghc-cabal" From git at git.haskell.org Fri Oct 27 00:52:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop language in Travis CI config (#372) (2741b3c) Message-ID: <20171027005237.90F043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2741b3c419ece51e914bc22e38e18c25476b296b/ghc >--------------------------------------------------------------- commit 2741b3c419ece51e914bc22e38e18c25476b296b Author: Zhen Zhang Date: Thu Jul 20 02:25:36 2017 +0800 Drop language in Travis CI config (#372) >--------------------------------------------------------------- 2741b3c419ece51e914bc22e38e18c25476b296b .travis.yml | 1 - 1 file changed, 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index d85291a..ba67ae3 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,5 +1,4 @@ sudo: true -language: haskell matrix: include: - os: linux From git at git.haskell.org Fri Oct 27 00:52:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an acknowledgement to Zhen Zhang (44b279b) Message-ID: <20171027005234.21F8C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44b279be9b1cc97bcc6cd73d3d0f73de6a7a3149/ghc >--------------------------------------------------------------- commit 44b279be9b1cc97bcc6cd73d3d0f73de6a7a3149 Author: Andrey Mokhov Date: Wed Jul 19 16:17:31 2017 +0100 Add an acknowledgement to Zhen Zhang Fix #371 [skip ci] >--------------------------------------------------------------- 44b279be9b1cc97bcc6cd73d3d0f73de6a7a3149 README.md | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index 8404496..5e49393 100644 --- a/README.md +++ b/README.md @@ -157,9 +157,12 @@ Acknowledgements I started this project as part of my 6-month research visit to Microsoft Research Cambridge, which was funded by Newcastle University, EPSRC, and Microsoft Research. I would like to thank Simon Peyton Jones, Neil Mitchell -and Simon Marlow for kick-starting the project and for their guidance. Last -but not least, big thanks to the project [contributors][contributors], who -helped me endure and enjoy the project. +and Simon Marlow for kick-starting the project and for their guidance. +Zhen Zhang has done fantastic work on Hadrian as part of his Summer of +Haskell 2017 [project](https://summer.haskell.org/ideas.html#hadrian-ghc), +solving a few heavy and long-overdue issues. Last but not least, big thanks +to all other project [contributors][contributors], who helped me endure and +enjoy the project. [ghc]: https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler [shake]: https://github.com/ndmitchell/shake/blob/master/README.md From git at git.haskell.org Fri Oct 27 00:52:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify and refactor moduleFiles oracle. (3d9c2fd) Message-ID: <20171027005233.63F5E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d9c2fdaf006a7aada8454295469cc5d8aa23938/ghc >--------------------------------------------------------------- commit 3d9c2fdaf006a7aada8454295469cc5d8aa23938 Author: Andrey Mokhov Date: Thu Feb 25 23:15:18 2016 +0000 Simplify and refactor moduleFiles oracle. See #210. >--------------------------------------------------------------- 3d9c2fdaf006a7aada8454295469cc5d8aa23938 src/Oracles/ModuleFiles.hs | 31 ++++++++++++++++++------------- src/Rules/Dependencies.hs | 3 ++- src/Rules/Documentation.hs | 3 ++- src/Settings.hs | 16 +--------------- 4 files changed, 23 insertions(+), 30 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index cf33e20..4c74265 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,12 +1,12 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} module Oracles.ModuleFiles ( - moduleFiles, haskellModuleFiles, moduleFilesOracle, findModuleFiles + moduleFiles, haskellSources, moduleFilesOracle, findModuleFiles ) where import Base import Context +import Expression import Oracles.PackageData -import Package import Settings.Paths newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) @@ -14,11 +14,12 @@ newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) moduleFiles :: Context -> Action [FilePath] moduleFiles context @ Context {..} = do - let path = contextPath context + let path = contextPath context + autogen = path -/- "build/autogen" srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - fmap catMaybes $ findModuleFiles dirs modules + catMaybes <$> findModuleFiles (autogen : dirs) modules haskellModuleFiles :: Context -> Action ([FilePath], [String]) haskellModuleFiles context @ Context {..} = do @@ -28,19 +29,23 @@ haskellModuleFiles context @ Context {..} = do srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - foundSrcDirs <- findModuleFiles dirs modules - foundAutogen <- findModuleFiles [autogen] modules - found <- sequence $ zipWith3 addSources modules foundSrcDirs foundAutogen - + found <- findModuleFiles (autogen : dirs) modules let missingMods = map fst . filter (isNothing . snd) $ zip modules found otherFileToMod = replaceEq '/' '.' . dropExtension . dropPkgPath (haskellFiles, otherFiles) = partition ("//*hs" ?==) $ catMaybes found - return (haskellFiles, missingMods ++ map otherFileToMod otherFiles) - where - addSources _ Nothing r = return r - addSources _ l Nothing = return l - addSources m (Just f1) (Just f2) = errorMultipleSources m f1 f2 + +-- | Find all Haskell source files for the current context +haskellSources :: Context -> Action [FilePath] +haskellSources context = do + let buildPath = contextPath context -/- "build" + autogen = buildPath -/- "autogen" + (found, missingMods) <- haskellModuleFiles context + -- Generated source files live in buildPath and have extension "hs"... + let generated = [ buildPath -/- (replaceEq '.' '/' m) <.> "hs" | m <- missingMods ] + -- ...except that GHC/Prim.hs lives in autogen. TODO: fix the inconsistency? + fixGhcPrim = replaceEq (buildPath -/- "GHC/Prim.hs") (autogen -/- "GHC/Prim.hs") + return $ found ++ fixGhcPrim generated -- | This is an important oracle whose role is to find and cache module source -- files. More specifically, it takes a list of directories @dirs@ and a sorted diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 16d2c0e..04cffc2 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -5,6 +5,7 @@ import Development.Shake.Util (parseMakefile) import Base import Context import Expression +import Oracles.ModuleFiles import Oracles.PackageData import Rules.Actions import Settings @@ -27,7 +28,7 @@ buildPackageDependencies rs context @ Context {..} = build $ Target context (GccM stage) [srcFile] [out] hDepFile %> \out -> do - srcs <- interpretInContext context getPackageSources + srcs <- haskellSources context need srcs if srcs == [] then writeFileChanged out "" diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 4e96571..b9407bc 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -4,6 +4,7 @@ import Base import Context import Expression import GHC +import Oracles.ModuleFiles import Oracles.PackageData import Rules.Actions import Settings @@ -21,7 +22,7 @@ buildPackageDocumentation context @ Context {..} = haddockFile = pkgHaddockFile context in when (stage == Stage1) $ do haddockFile %> \file -> do - srcs <- interpretInContext context getPackageSources + srcs <- haskellSources context deps <- map PackageName <$> interpretInContext context (getPkgDataList DepNames) let haddocks = [ pkgHaddockFile $ vanillaContext Stage1 depPkg | Just depPkg <- map findKnownPackage deps diff --git a/src/Settings.hs b/src/Settings.hs index e134fbc..9f52026 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -4,12 +4,11 @@ module Settings ( module Settings.User, module Settings.Ways, getPkgData, getPkgDataList, getTopDirectory, isLibrary, - getPackagePath, getContextDirectory, getContextPath, getPackageSources + getPackagePath, getContextDirectory, getContextPath ) where import Base import Expression -import Oracles.ModuleFiles import Oracles.PackageData import Oracles.WindowsPath import Settings.Packages @@ -34,16 +33,3 @@ getPkgDataList key = lift . pkgDataList . key =<< getContextPath getTopDirectory :: Expr FilePath getTopDirectory = lift topDirectory - --- | Find all Haskell source files for the current target -getPackageSources :: Expr [FilePath] -getPackageSources = do - context <- getContext - let buildPath = contextPath context -/- "build" - autogen = buildPath -/- "autogen" - (found, missingMods) <- lift $ haskellModuleFiles context - -- Generated source files live in buildPath and have extension "hs"... - let generated = [ buildPath -/- (replaceEq '.' '/' m) <.> "hs" | m <- missingMods ] - -- ...except that GHC/Prim.hs lives in autogen. TODO: fix the inconsistency? - fixGhcPrim = replaceEq (buildPath -/- "GHC/Prim.hs") (autogen -/- "GHC/Prim.hs") - return $ found ++ fixGhcPrim generated From git at git.haskell.org Fri Oct 27 00:52:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant brackets. (a09185a) Message-ID: <20171027005229.DB1D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a09185a4d6a5aa90930ecab25724830bcddb9fa2/ghc >--------------------------------------------------------------- commit a09185a4d6a5aa90930ecab25724830bcddb9fa2 Author: Andrey Mokhov Date: Tue Feb 23 02:46:06 2016 +0000 Drop redundant brackets. >--------------------------------------------------------------- a09185a4d6a5aa90930ecab25724830bcddb9fa2 src/GHC.hs | 4 ++-- src/Oracles/ModuleFiles.hs | 4 ++-- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 4 ++-- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 2 +- src/Settings/Paths.hs | 10 +++++----- 10 files changed, 18 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a09185a4d6a5aa90930ecab25724830bcddb9fa2 From git at git.haskell.org Fri Oct 27 00:52:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (d396ba3) Message-ID: <20171027005240.6778B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d396ba3d8f4d2ce6e15d3149404fbb94118bddc3/ghc >--------------------------------------------------------------- commit d396ba3d8f4d2ce6e15d3149404fbb94118bddc3 Author: Andrey Mokhov Date: Fri Feb 26 01:54:51 2016 +0000 Minor revision. >--------------------------------------------------------------- d396ba3d8f4d2ce6e15d3149404fbb94118bddc3 src/Oracles/Dependencies.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index b34535b..aa54d86 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,10 +1,11 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.Dependencies (dependencies, dependenciesOracle) where -import Base import Control.Monad.Trans.Maybe import qualified Data.HashMap.Strict as Map +import Base + newtype DependenciesKey = DependenciesKey (FilePath, FilePath) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) @@ -28,10 +29,9 @@ dependencies path obj = do -- Oracle for 'path/dist/.dependencies' files dependenciesOracle :: Rules () -dependenciesOracle = do +dependenciesOracle = void $ do deps <- newCache $ \file -> do putOracle $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return . Map.fromList $ map (\(x:xs) -> (x, xs)) contents - _ <- addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file - return () + addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file From git at git.haskell.org Fri Oct 27 00:52:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comments only (58e2120) Message-ID: <20171027005241.261FF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/58e21200a04bc17f5cb7c8fb8dbd36cecc03d36a/ghc >--------------------------------------------------------------- commit 58e21200a04bc17f5cb7c8fb8dbd36cecc03d36a Author: Andrey Mokhov Date: Wed Jul 19 20:17:07 2017 +0100 Comments only See #345 >--------------------------------------------------------------- 58e21200a04bc17f5cb7c8fb8dbd36cecc03d36a src/UserSettings.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 4398700..a3a65ab 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -43,10 +43,11 @@ putBuild = putColoured Dull Magenta putSuccess :: String -> Action () putSuccess = putColoured Dull Green --- | Path to the GHC install destination --- It is by default empty, representing the root of file system, --- or it might be a directory. --- It is usually used with @prefix@, like @/usr/local@ +-- | Path to the GHC install destination. It is empty by default, which +-- corresponds to the root of the file system. You can replace it by a specific +-- directory. Make sure you use correct absolute path on Windows, e.g. "C:/path". +-- The destination directory is used with a @prefix@, commonly @/usr/local@, +-- i.e. GHC is installed into "C:/path/usr/local" for the above example. defaultDestDir :: FilePath defaultDestDir = "" From git at git.haskell.org Fri Oct 27 00:52:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add findGenerator, refactor Oracles.ModuleFiles. (79858ef) Message-ID: <20171027005244.102F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79858ef2f73d7444b74cac12680dfc234fbacda9/ghc >--------------------------------------------------------------- commit 79858ef2f73d7444b74cac12680dfc234fbacda9 Author: Andrey Mokhov Date: Fri Feb 26 02:25:44 2016 +0000 Add findGenerator, refactor Oracles.ModuleFiles. See #210. >--------------------------------------------------------------- 79858ef2f73d7444b74cac12680dfc234fbacda9 src/Oracles/ModuleFiles.hs | 94 +++++++++++++++++++++++++++------------------- src/Rules/Generate.hs | 25 ++---------- 2 files changed, 60 insertions(+), 59 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 79858ef2f73d7444b74cac12680dfc234fbacda9 From git at git.haskell.org Fri Oct 27 00:52:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Need all top-level dependencies in one go for better parallelism. Minor revision. (145999c) Message-ID: <20171027005244.A298F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/145999cfde98ff857abee0c4abd96ebc637ca04b/ghc >--------------------------------------------------------------- commit 145999cfde98ff857abee0c4abd96ebc637ca04b Author: Andrey Mokhov Date: Thu Jul 20 00:28:33 2017 +0100 Need all top-level dependencies in one go for better parallelism. Minor revision. See #200. >--------------------------------------------------------------- 145999cfde98ff857abee0c4abd96ebc637ca04b src/Oracles/Dependencies.hs | 38 +++++++++++++++++---------------- src/Rules.hs | 51 ++++++++++++++++++++++----------------------- src/Rules/Compile.hs | 2 +- src/Rules/Install.hs | 6 +++--- src/Rules/Program.hs | 4 ++-- 5 files changed, 51 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 145999cfde98ff857abee0c4abd96ebc637ca04b From git at git.haskell.org Fri Oct 27 00:52:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop testModuleFilesOracle. (50663a4) Message-ID: <20171027005247.C2B953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/50663a4d4e5a04653e4a30034e688bf1dbd549ec/ghc >--------------------------------------------------------------- commit 50663a4d4e5a04653e4a30034e688bf1dbd549ec Author: Andrey Mokhov Date: Fri Feb 26 03:36:31 2016 +0000 Drop testModuleFilesOracle. See #210. >--------------------------------------------------------------- 50663a4d4e5a04653e4a30034e688bf1dbd549ec src/Rules/Selftest.hs | 13 ------------- 1 file changed, 13 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f4890b0..f549b0f 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,7 +6,6 @@ import Development.Shake import Test.QuickCheck import Base -import Oracles.ModuleFiles import Settings.Builders.Ar (chunksOfSize) import Way @@ -27,7 +26,6 @@ selftestRules = testMatchVersionedFilePath testModuleNames testLookupAll - testModuleFilesOracle testWays :: Action () testWays = do @@ -85,14 +83,3 @@ testLookupAll = do dicts = nubBy ((==) `on` fst) <$> vector 20 extras :: Gen [Int] extras = vector 20 - -testModuleFilesOracle :: Action () -testModuleFilesOracle = do - putBuild $ "==== moduleFilesOracle" - result <- findModuleFiles ["compiler/codeGen", "compiler/parser"] - [ "CodeGen.Platform.ARM" - , "Lexer" - , "Missing.Module"] - test $ result == [ Just "compiler/codeGen/CodeGen/Platform/ARM.hs" - , Just "compiler/parser/Lexer.x" - , Nothing] From git at git.haskell.org Fri Oct 27 00:52:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix builder dependencies on generated files (#363) (d9c97e8) Message-ID: <20171027005248.5E7663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9c97e8f96f482fe7d84e01d61682e82e1edad59/ghc >--------------------------------------------------------------- commit d9c97e8f96f482fe7d84e01d61682e82e1edad59 Author: Zhen Zhang Date: Fri Jul 21 01:14:15 2017 +0800 Fix builder dependencies on generated files (#363) >--------------------------------------------------------------- d9c97e8f96f482fe7d84e01d61682e82e1edad59 src/Rules.hs | 1 - src/Rules/Generate.hs | 14 +------------- src/Rules/Program.hs | 4 +++- src/Rules/Test.hs | 3 ++- src/Settings/Builders/GhcCabal.hs | 4 +++- src/Settings/Builders/Hsc2Hs.hs | 7 ++----- src/Settings/Path.hs | 17 ++++++++++++++++- src/Util.hs | 1 + 8 files changed, 28 insertions(+), 23 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 69fcaee..359d3e9 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -29,7 +29,6 @@ allStages = [minBound ..] -- or Stage1Only targets topLevelTargets :: Rules () topLevelTargets = action $ do - need $ Rules.Generate.inplaceLibCopyTargets let libraryPackages = filter isLibrary (knownPackages \\ [rts, libffi]) need =<< if stage1Only then do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 3507027..80eca91 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( isGeneratedCFile, isGeneratedCmmFile, generatePackageCode, generateRules, - copyRules, includesDependencies, generatedDependencies, inplaceLibCopyTargets + copyRules, includesDependencies, generatedDependencies ) where import Base @@ -24,18 +24,6 @@ import Target import UserSettings import Util --- | Files that need to be copied over to inplace/lib --- ref: ghc/ghc.mk:142 --- ref: driver/ghc.mk --- ref: utils/hsc2hs/ghc.mk:35 -inplaceLibCopyTargets :: [FilePath] -inplaceLibCopyTargets = map (inplaceLibPath -/-) - [ "ghc-usage.txt" - , "ghci-usage.txt" - , "platformConstants" - , "settings" - , "template-hsc.h" ] - primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 846c694..710829b 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -14,7 +14,7 @@ import Oracles.Path (topDirectory) import Rules.Wrappers (WrappedBinary(..), Wrapper, inplaceWrappers) import Settings import Settings.Path (buildPath, inplaceLibBinPath, rtsContext, objectPath, - inplaceLibPath, inplaceBinPath) + inplaceLibPath, inplaceBinPath, inplaceLibCopyTargets) import Target import UserSettings import Util @@ -28,6 +28,8 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do buildPath context -/- programName context <.> exe %> buildBinaryAndWrapper rs context + when (package == ghc) $ want inplaceLibCopyTargets + -- Rules for programs built in install directories when (stage == Stage0 || package == ghc) $ do -- Some binaries in inplace/bin are wrapped diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index fc059ab..93e97c2 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -10,6 +10,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Path import Settings +import Settings.Path (inplaceLibCopyTargets) import Target import Util @@ -17,7 +18,7 @@ import Util testRules :: Rules () testRules = do "validate" ~> do - need $ Rules.Generate.inplaceLibCopyTargets + need inplaceLibCopyTargets needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 18816e1..33a7b99 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -4,7 +4,7 @@ module Settings.Builders.GhcCabal ( import Context import Flavour -import Settings.Builders.Common +import Settings.Builders.Common hiding (package) import Util ghcCabalBuilderArgs :: Args @@ -12,6 +12,8 @@ ghcCabalBuilderArgs = builder GhcCabal ? do verbosity <- lift $ getVerbosity top <- getTopDirectory context <- getContext + when (package context /= deriveConstants) $ + lift (need inplaceLibCopyTargets) mconcat [ arg "configure" , arg =<< getPackagePath , arg $ top -/- buildPath context diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index ba98654..a9ec9c5 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -1,9 +1,7 @@ module Settings.Builders.Hsc2Hs (hsc2hsBuilderArgs) where import Settings.Builders.Common - -templateHsc :: FilePath -templateHsc = "inplace/lib/template-hsc.h" +import Settings.Path (templateHscPath) hsc2hsBuilderArgs :: Args hsc2hsBuilderArgs = builder Hsc2Hs ? do @@ -20,7 +18,6 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do version <- if stage == Stage0 then lift ghcCanonVersion else getSetting ProjectVersionInt - lift $ need [templateHsc] mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" @@ -33,7 +30,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) , arg $ "--cflag=-D__GLASGOW_HASKELL__=" ++ version - , arg $ "--template=" ++ top -/- templateHsc + , arg $ "--template=" ++ top -/- templateHscPath , arg $ "-I" ++ top -/- "inplace/lib/include/" , arg =<< getInput , arg "-o", arg =<< getOutput ] diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 0be1838..c8153bf 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -6,7 +6,7 @@ module Settings.Path ( pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, inplaceInstallPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, - pkgSetupConfigFile + pkgSetupConfigFile, inplaceLibCopyTargets, templateHscPath ) where import Base @@ -214,3 +214,18 @@ stripCmdPath = do "arm-unknown-linux" -> return ":" -- HACK: from the make-based system, see the ref above _ -> return "strip" + +-- | Files that need to be copied over to inplace/lib +-- ref: ghc/ghc.mk:142 +-- ref: driver/ghc.mk +-- ref: utils/hsc2hs/ghc.mk:35 +inplaceLibCopyTargets :: [FilePath] +inplaceLibCopyTargets = map (inplaceLibPath -/-) + [ "ghc-usage.txt" + , "ghci-usage.txt" + , "platformConstants" + , "settings" + , "template-hsc.h" ] + +templateHscPath :: FilePath +templateHscPath = "inplace/lib/template-hsc.h" diff --git a/src/Util.hs b/src/Util.hs index 37743c0..7ea567e 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -22,6 +22,7 @@ import Oracles.Path import Oracles.Config.Setting import Settings import Settings.Builders.Ar +import Settings.Path import Target import UserSettings From git at git.haskell.org Fri Oct 27 00:52:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Context as key to moduleFilesOracle. (1fd2368) Message-ID: <20171027005251.9EA2F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fd23681fe3f63fcdff82ab7b1d65eeedf5227aa/ghc >--------------------------------------------------------------- commit 1fd23681fe3f63fcdff82ab7b1d65eeedf5227aa Author: Andrey Mokhov Date: Fri Feb 26 03:37:22 2016 +0000 Use Context as key to moduleFilesOracle. See #210. >--------------------------------------------------------------- 1fd23681fe3f63fcdff82ab7b1d65eeedf5227aa src/Oracles/ModuleFiles.hs | 42 ++++++++++++++++++------------------------ 1 file changed, 18 insertions(+), 24 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 73ec6eb..630a05f 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,6 +1,6 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, LambdaCase #-} +{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.ModuleFiles ( - findGenerator, haskellSources, moduleFilesOracle, findModuleFiles + findGenerator, haskellSources, moduleFilesOracle ) where import qualified Data.HashMap.Strict as Map @@ -11,7 +11,7 @@ import Expression import Oracles.PackageData import Settings.Paths -newtype ModuleFilesKey = ModuleFilesKey ([FilePath], [String]) +newtype ModuleFilesKey = ModuleFilesKey Context deriving (Show, Typeable, Eq, Hashable, Binary, NFData) newtype Generator = Generator (Context, FilePath) @@ -55,32 +55,29 @@ generatedFile context moduleName = contextFiles :: Context -> Action [(String, Maybe FilePath)] contextFiles context @ Context {..} = do let path = contextPath context - srcDirs <- fmap sort . pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - let dirs = [ pkgPath package -/- dir | dir <- srcDirs ] - zip modules <$> findModuleFiles (path -/- "build/autogen" : dirs) modules + zip modules <$> askOracle (ModuleFilesKey context) -- | This is an important oracle whose role is to find and cache module source --- files. More specifically, it takes a list of directories @dirs@ and a sorted --- list of module names @modules@ as arguments, and for each module, e.g. +-- files. It takes a 'Context', looks up corresponding source directories @dirs@ +-- and sorted list of module names @modules@, and for each module, e.g. -- @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, such that -- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or 'Nothing' -- if there is no such file. If more than one matching file is found an error is --- raised. For example, for the 'compiler' package given --- @dirs = ["compiler/codeGen", "compiler/parser"]@, and --- @modules = ["CodeGen.Platform.ARM", "Lexer", "Missing.Module"]@, it produces --- @[Just "compiler/codeGen/CodeGen/Platform/ARM.hs", --- Just "compiler/parser/Lexer.x", Nothing]@. -findModuleFiles :: [FilePath] -> [String] -> Action [Maybe FilePath] -findModuleFiles dirs modules = askOracle $ ModuleFilesKey (dirs, modules) - +-- raised. For example, for @Context Stage1 compiler vanilla@, @dirs@ will +-- contain ["compiler/codeGen", "compiler/parser"], and @modules@ will contain +-- ["CodeGen.Platform.ARM", "Config", "Lexer"]; the oracle will produce a list +-- containing [Just "compiler/codeGen/CodeGen/Platform/ARM.hs", Nothing, +-- Just "compiler/parser/Lexer.x"]. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do - void $ addOracle $ \(ModuleFilesKey (dirs, modules)) -> do - let decodedPairs = map decodeModule modules - modDirFiles = map (bimap head id . unzip) - . groupBy ((==) `on` fst) $ decodedPairs - + void $ addOracle $ \(ModuleFilesKey context) -> do + let path = contextPath context + autogen = path -/- "build/autogen" + srcDirs <- pkgDataList $ SrcDirs path + modules <- fmap sort . pkgDataList $ Modules path + let dirs = autogen : map (pkgPath (package context) -/-) srcDirs + modDirFiles = groupSort $ map decodeModule modules result <- fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do @@ -90,15 +87,12 @@ moduleFilesOracle = void $ do cmp fe f = compare (dropExtension fe) f found = intersectOrd cmp noBoot mFiles return (map (fullDir -/-) found, mDir) - let pairs = sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ] - unless (null multi) $ do let (m, f1, f2) = head multi putError $ "Module " ++ m ++ " has more than one source file: " ++ f1 ++ " and " ++ f2 ++ "." - return $ lookupAll modules pairs gens <- newCache $ \context -> do From git at git.haskell.org Fri Oct 27 00:52:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix validate's executable dependency (#375) (2555a5f) Message-ID: <20171027005252.5273F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2555a5f03040aaf56e44e32c8b133cc5ead87616/ghc >--------------------------------------------------------------- commit 2555a5f03040aaf56e44e32c8b133cc5ead87616 Author: Zhen Zhang Date: Sun Jul 23 20:37:29 2017 +0800 Fix validate's executable dependency (#375) >--------------------------------------------------------------- 2555a5f03040aaf56e44e32c8b133cc5ead87616 src/Rules/Test.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 93e97c2..0f46f6c 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -22,6 +22,8 @@ testRules = do needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc + needBuilder Hsc2Hs + need ["inplace/bin/hp2ps"] -- TODO: Eliminate explicit filepaths in "need" (#376) build $ Target (vanillaContext Stage2 compiler) (Make "testsuite/tests") [] [] "test" ~> do From git at git.haskell.org Fri Oct 27 00:52:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (9171856) Message-ID: <20171027005255.696613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9171856f647213aea42005a8dfec9bff0ff7223c/ghc >--------------------------------------------------------------- commit 9171856f647213aea42005a8dfec9bff0ff7223c Author: Andrey Mokhov Date: Fri Feb 26 11:37:00 2016 +0000 Minor revision. See #210. >--------------------------------------------------------------- 9171856f647213aea42005a8dfec9bff0ff7223c src/Oracles/ModuleFiles.hs | 18 ++++++++++++------ 1 file changed, 12 insertions(+), 6 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 630a05f..508b554 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -34,7 +34,12 @@ determineBuilder file = case takeExtension file of -- ".build/stage1/base/build/Prelude.hs" -- == Nothing findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder)) -findGenerator context file = askOracle $ Generator (context, file) +findGenerator context file = do + maybeSource <- askOracle $ Generator (context, file) + return $ do + source <- maybeSource + builder <- determineBuilder source + return (source, builder) -- | Find all Haskell source files for a given 'Context'. haskellSources :: Context -> Action [FilePath] @@ -44,8 +49,9 @@ haskellSources context = do -- that GHC/Prim.hs lives in build/autogen/. TODO: fix the inconsistency? let modFile ("GHC.Prim", _) = autogen -/- "GHC/Prim.hs" modFile (m, Nothing ) = generatedFile context m - modFile (m, Just file ) | "//*hs" ?== file = file - | otherwise = modFile (m, Nothing) + modFile (m, Just file ) + | takeExtension file `elem` [".hs", ".lhs"] = file + | otherwise = generatedFile context m map modFile <$> contextFiles context generatedFile :: Context -> String -> FilePath @@ -53,7 +59,7 @@ generatedFile context moduleName = contextPath context -/- "build" -/- replaceEq '.' '/' moduleName <.> "hs" contextFiles :: Context -> Action [(String, Maybe FilePath)] -contextFiles context @ Context {..} = do +contextFiles context at Context {..} = do let path = contextPath context modules <- fmap sort . pkgDataList $ Modules path zip modules <$> askOracle (ModuleFilesKey context) @@ -97,8 +103,8 @@ moduleFilesOracle = void $ do gens <- newCache $ \context -> do files <- contextFiles context - return $ Map.fromList [ (generatedFile context modName, (src, builder)) + return $ Map.fromList [ (generatedFile context modName, src) | (modName, Just src) <- files - , let Just builder = determineBuilder src ] + , takeExtension src `notElem` [".hs", ".lhs"] ] addOracle $ \(Generator (context, file)) -> Map.lookup file <$> gens context From git at git.haskell.org Fri Oct 27 00:52:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix validate's hsc2hs dependency (#375) (#378) (fd5cd07) Message-ID: <20171027005256.14EE13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd5cd0756dd1d9a0071c4f3378e6c64cee0e2f63/ghc >--------------------------------------------------------------- commit fd5cd0756dd1d9a0071c4f3378e6c64cee0e2f63 Author: Zhen Zhang Date: Mon Jul 24 02:08:42 2017 +0800 Fix validate's hsc2hs dependency (#375) (#378) >--------------------------------------------------------------- fd5cd0756dd1d9a0071c4f3378e6c64cee0e2f63 src/Rules/Test.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 0f46f6c..5f6d678 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -22,8 +22,9 @@ testRules = do needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc - needBuilder Hsc2Hs - need ["inplace/bin/hp2ps"] -- TODO: Eliminate explicit filepaths in "need" (#376) + need ["inplace/bin/hp2ps", "inplace/bin/hsc2hs"] + -- TODO: Eliminate explicit filepaths in "need" (#376) + -- FIXME: needBuilder Hsc2Hs doesn't work build $ Target (vanillaContext Stage2 compiler) (Make "testsuite/tests") [] [] "test" ~> do From git at git.haskell.org Fri Oct 27 00:52:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use conventional whitespacing for @. (31515fa) Message-ID: <20171027005259.012F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31515fad107d28f83b47d6249dd7b8c1eeb3bc70/ghc >--------------------------------------------------------------- commit 31515fad107d28f83b47d6249dd7b8c1eeb3bc70 Author: Andrey Mokhov Date: Fri Feb 26 11:37:47 2016 +0000 Use conventional whitespacing for @. See #210. >--------------------------------------------------------------- 31515fad107d28f83b47d6249dd7b8c1eeb3bc70 src/GHC.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 4 ++-- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Rules/Program.hs | 6 +++--- src/Rules/Register.hs | 2 +- src/Settings/Paths.hs | 10 +++++----- src/Way.hs | 2 +- 12 files changed, 20 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 31515fad107d28f83b47d6249dd7b8c1eeb3bc70 From git at git.haskell.org Fri Oct 27 00:52:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:52:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant imports (776cf70) Message-ID: <20171027005259.883BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/776cf701a457c0970c7126a840cf8f4afefece2f/ghc >--------------------------------------------------------------- commit 776cf701a457c0970c7126a840cf8f4afefece2f Author: Andrey Mokhov Date: Wed Jul 26 23:07:14 2017 +0100 Drop redundant imports >--------------------------------------------------------------- 776cf701a457c0970c7126a840cf8f4afefece2f src/Rules/Test.hs | 1 - src/Settings/Builders/Hsc2Hs.hs | 1 - src/Util.hs | 1 - 3 files changed, 3 deletions(-) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 5f6d678..335964c 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -5,7 +5,6 @@ import Builder import Expression import Flavour import GHC -import qualified Rules.Generate import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Path diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index a9ec9c5..217636b 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -1,7 +1,6 @@ module Settings.Builders.Hsc2Hs (hsc2hsBuilderArgs) where import Settings.Builders.Common -import Settings.Path (templateHscPath) hsc2hsBuilderArgs :: Args hsc2hsBuilderArgs = builder Hsc2Hs ? do diff --git a/src/Util.hs b/src/Util.hs index 7ea567e..37743c0 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -22,7 +22,6 @@ import Oracles.Path import Oracles.Config.Setting import Settings import Settings.Builders.Ar -import Settings.Path import Target import UserSettings From git at git.haskell.org Fri Oct 27 00:53:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (e2fbf4c) Message-ID: <20171027005302.CE2893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2fbf4c8b06e6e9692473dca31b390fe30953256/ghc >--------------------------------------------------------------- commit e2fbf4c8b06e6e9692473dca31b390fe30953256 Author: Andrey Mokhov Date: Fri Feb 26 12:09:40 2016 +0000 Add comments. See #210. >--------------------------------------------------------------- e2fbf4c8b06e6e9692473dca31b390fe30953256 src/Oracles/ModuleFiles.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 508b554..5cb7a5b 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -101,6 +101,8 @@ moduleFilesOracle = void $ do ++ f1 ++ " and " ++ f2 ++ "." return $ lookupAll modules pairs + -- Optimisation: we discard .(l)hs files here, because they are never used + -- as generators, and hence would be discarded in 'findGenerator' anyway. gens <- newCache $ \context -> do files <- contextFiles context return $ Map.fromList [ (generatedFile context modName, src) From git at git.haskell.org Fri Oct 27 00:53:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bump Cabal library version, fix AppVeyor build (345deee) Message-ID: <20171027005303.554BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/345deee0c3850479ab6047920314c3ac30d7dad0/ghc >--------------------------------------------------------------- commit 345deee0c3850479ab6047920314c3ac30d7dad0 Author: Andrey Mokhov Date: Wed Jul 26 23:35:27 2017 +0100 Bump Cabal library version, fix AppVeyor build >--------------------------------------------------------------- 345deee0c3850479ab6047920314c3ac30d7dad0 hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 1178cb4..77fc54c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -119,7 +119,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 2.0.0.0 + , Cabal == 2.0.0.2 , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 00:53:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use (Stage, Package) as the key for moduleFilesOracle. (39f61a4) Message-ID: <20171027005306.85C343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39f61a41680e0abcf2cfe185f6115213b1dbc649/ghc >--------------------------------------------------------------- commit 39f61a41680e0abcf2cfe185f6115213b1dbc649 Author: Andrey Mokhov Date: Fri Feb 26 13:35:33 2016 +0000 Use (Stage, Package) as the key for moduleFilesOracle. See #210. >--------------------------------------------------------------- 39f61a41680e0abcf2cfe185f6115213b1dbc649 src/Oracles/ModuleFiles.hs | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 5cb7a5b..96e66ac 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -11,10 +11,10 @@ import Expression import Oracles.PackageData import Settings.Paths -newtype ModuleFilesKey = ModuleFilesKey Context +newtype ModuleFilesKey = ModuleFilesKey (Stage, Package) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -newtype Generator = Generator (Context, FilePath) +newtype Generator = Generator (Stage, Package, FilePath) deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- The following generators and corresponding source extensions are supported: @@ -34,8 +34,8 @@ determineBuilder file = case takeExtension file of -- ".build/stage1/base/build/Prelude.hs" -- == Nothing findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder)) -findGenerator context file = do - maybeSource <- askOracle $ Generator (context, file) +findGenerator Context {..} file = do + maybeSource <- askOracle $ Generator (stage, package, file) return $ do source <- maybeSource builder <- determineBuilder source @@ -62,7 +62,7 @@ contextFiles :: Context -> Action [(String, Maybe FilePath)] contextFiles context at Context {..} = do let path = contextPath context modules <- fmap sort . pkgDataList $ Modules path - zip modules <$> askOracle (ModuleFilesKey context) + zip modules <$> askOracle (ModuleFilesKey (stage, package)) -- | This is an important oracle whose role is to find and cache module source -- files. It takes a 'Context', looks up corresponding source directories @dirs@ @@ -77,12 +77,12 @@ contextFiles context at Context {..} = do -- Just "compiler/parser/Lexer.x"]. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do - void $ addOracle $ \(ModuleFilesKey context) -> do - let path = contextPath context + void $ addOracle $ \(ModuleFilesKey (stage, package)) -> do + let path = contextPath $ vanillaContext stage package autogen = path -/- "build/autogen" srcDirs <- pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path - let dirs = autogen : map (pkgPath (package context) -/-) srcDirs + let dirs = autogen : map (pkgPath package -/-) srcDirs modDirFiles = groupSort $ map decodeModule modules result <- fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles @@ -103,10 +103,12 @@ moduleFilesOracle = void $ do -- Optimisation: we discard .(l)hs files here, because they are never used -- as generators, and hence would be discarded in 'findGenerator' anyway. - gens <- newCache $ \context -> do + generators <- newCache $ \(stage, package) -> do + let context = vanillaContext stage package files <- contextFiles context return $ Map.fromList [ (generatedFile context modName, src) | (modName, Just src) <- files , takeExtension src `notElem` [".hs", ".lhs"] ] - addOracle $ \(Generator (context, file)) -> Map.lookup file <$> gens context + addOracle $ \(Generator (stage, package, file)) -> + Map.lookup file <$> generators (stage, package) From git at git.haskell.org Fri Oct 27 00:53:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Part 1 of the Great Refactoring of the Expression (9c75620) Message-ID: <20171027005307.1C7CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c75620168d77d91814d6a3aa562cd58405bfe5a/ghc >--------------------------------------------------------------- commit 9c75620168d77d91814d6a3aa562cd58405bfe5a Author: Andrey Mokhov Date: Thu Jul 27 02:58:55 2017 +0100 Part 1 of the Great Refactoring of the Expression See #347 >--------------------------------------------------------------- 9c75620168d77d91814d6a3aa562cd58405bfe5a hadrian.cabal | 3 +- src/Base.hs | 1 - src/Expression.hs | 154 +++++++++++++------------------ src/Oracles/Config/Flag.hs | 7 +- src/Oracles/Config/Setting.hs | 12 +-- src/Oracles/Path.hs | 6 +- src/Rules/Generators/Common.hs | 4 +- src/Rules/Generators/ConfigHs.hs | 2 +- src/Rules/Generators/GhcAutoconfH.hs | 4 +- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Libffi.hs | 4 +- src/Rules/Wrappers.hs | 46 ++++----- src/Settings.hs | 16 ++-- src/Settings/Builders/Cc.hs | 2 +- src/Settings/Builders/Common.hs | 17 ++-- src/Settings/Builders/DeriveConstants.hs | 6 +- src/Settings/Builders/Ghc.hs | 10 +- src/Settings/Builders/GhcCabal.hs | 38 ++++---- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 4 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 10 +- src/Settings/Builders/Make.hs | 2 +- src/Settings/Default.hs | 12 +-- src/Settings/Packages/GhcCabal.hs | 6 +- src/Settings/Packages/IntegerGmp.hs | 4 +- src/Settings/Packages/Rts.hs | 7 +- 27 files changed, 167 insertions(+), 216 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 9c75620168d77d91814d6a3aa562cd58405bfe5a From git at git.haskell.org Fri Oct 27 00:53:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix outdated comments. (0273e3e) Message-ID: <20171027005310.8827F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0273e3ea2449f646c46059d2be4a7261571511c0/ghc >--------------------------------------------------------------- commit 0273e3ea2449f646c46059d2be4a7261571511c0 Author: Andrey Mokhov Date: Fri Feb 26 15:47:56 2016 +0000 Fix outdated comments. See #210. >--------------------------------------------------------------- 0273e3ea2449f646c46059d2be4a7261571511c0 src/Oracles/ModuleFiles.hs | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 96e66ac..b38929c 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -65,16 +65,16 @@ contextFiles context at Context {..} = do zip modules <$> askOracle (ModuleFilesKey (stage, package)) -- | This is an important oracle whose role is to find and cache module source --- files. It takes a 'Context', looks up corresponding source directories @dirs@ --- and sorted list of module names @modules@, and for each module, e.g. --- @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, such that --- @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or 'Nothing' --- if there is no such file. If more than one matching file is found an error is --- raised. For example, for @Context Stage1 compiler vanilla@, @dirs@ will +-- files. It takes a 'Stage' and a 'Package', looks up corresponding source +-- directories @dirs@ and a sorted list of module names @modules@, and for each +-- module, e.g. @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, +-- such that @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or +-- 'Nothing' if there is no such file. If more than one matching file is found +-- an error is raised. For example, for 'Stage1' and 'compiler', @dirs@ will -- contain ["compiler/codeGen", "compiler/parser"], and @modules@ will contain -- ["CodeGen.Platform.ARM", "Config", "Lexer"]; the oracle will produce a list -- containing [Just "compiler/codeGen/CodeGen/Platform/ARM.hs", Nothing, --- Just "compiler/parser/Lexer.x"]. +-- Just "compiler/parser/Lexer.x"]. The oracle ignores @.(l)hs-boot@ files. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do void $ addOracle $ \(ModuleFilesKey (stage, package)) -> do From git at git.haskell.org Fri Oct 27 00:53:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't echo (227d8d7) Message-ID: <20171027005310.ED2DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/227d8d7d669f0dc99e7947391521259b0ce28186/ghc >--------------------------------------------------------------- commit 227d8d7d669f0dc99e7947391521259b0ce28186 Author: Andrey Mokhov Date: Fri Jul 28 22:22:18 2017 +0100 Don't echo >--------------------------------------------------------------- 227d8d7d669f0dc99e7947391521259b0ce28186 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 37743c0..e6fd6bf 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -76,7 +76,7 @@ customBuild rs opts target at Target {..} = do src <- interpret target getInput file <- interpret target getOutput input <- readFile' src - Stdout output <- cmd cmdEcho (Stdin input) [path] argList + Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output Make dir -> cmd Shell cmdEcho path ["-C", dir] argList From git at git.haskell.org Fri Oct 27 00:53:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (d8a249b) Message-ID: <20171027005314.2CC373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d8a249b43b494428675b85fab7e53dff4ce859d9/ghc >--------------------------------------------------------------- commit d8a249b43b494428675b85fab7e53dff4ce859d9 Author: Andrey Mokhov Date: Fri Feb 26 19:00:31 2016 +0000 Add comments. See #55. >--------------------------------------------------------------- d8a249b43b494428675b85fab7e53dff4ce859d9 src/Settings/Paths.hs | 31 ++++++++++++++++++------------- 1 file changed, 18 insertions(+), 13 deletions(-) diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 6ad6b9d..629d6d0 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -11,58 +11,63 @@ import GHC import Oracles.PackageData import Settings.User --- Path to the target directory from GHC source root +-- | Path to the directory containing build artefacts of a given 'Context'. contextPath :: Context -> FilePath contextPath context at Context {..} = buildRootPath -/- contextDirectory context -/- pkgPath package +-- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath pkgDataFile context = contextPath context -/- "package-data.mk" --- Relative path to a package haddock file, e.g.: --- "libraries/array/dist-install/doc/html/array/array.haddock" +-- | Path to the haddock file of a given 'Context', e.g.: +-- ".build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = contextPath context -/- "doc/html" -/- name -/- name <.> "haddock" where name = pkgNameString package --- Relative path to a package library file, e.g.: --- "libraries/array/stage2/build/libHSarray-0.5.1.0.a" +-- | Path to the library file of a given 'Context', e.g.: +-- ".build/stage1/libraries/array/build/libHSarray-0.5.1.0.a". pkgLibraryFile :: Context -> Action FilePath pkgLibraryFile context at Context {..} = do extension <- libsuf way - pkgFile context "build/libHS" extension + pkgFile context "libHS" extension +-- | Path to the auxiliary library file of a given 'Context', e.g.: +-- ".build/stage1/compiler/build/libHSghc-8.1-0.a". pkgLibraryFile0 :: Context -> Action FilePath pkgLibraryFile0 context at Context {..} = do extension <- libsuf way - pkgFile context "build/libHS" ("-0" ++ extension) + pkgFile context "libHS" ("-0" ++ extension) --- Relative path to a package ghci library file, e.g.: --- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" +-- | Path to the GHCi library file of a given 'Context', e.g.: +-- ".build/stage1/libraries/array/build/HSarray-0.5.1.0.o". pkgGhciLibraryFile :: Context -> Action FilePath -pkgGhciLibraryFile context = pkgFile context "build/HS" ".o" +pkgGhciLibraryFile context = pkgFile context "HS" ".o" pkgFile :: Context -> String -> String -> Action FilePath pkgFile context prefix suffix = do let path = contextPath context componentId <- pkgData $ ComponentId path - return $ path -/- prefix ++ componentId ++ suffix + return $ path -/- "build" -/- prefix ++ componentId ++ suffix --- This is the build directory for in-tree GMP library +-- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" --- We extract system gmp library name from this file +-- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory +-- | Path to package database directory of a given 'Stage'. packageDbDirectory :: Stage -> FilePath packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" +-- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do componentId <- pkgData . ComponentId $ contextPath context From git at git.haskell.org Fri Oct 27 00:53:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable parallel garbage collection (#385) (57cfa03) Message-ID: <20171027005314.8AE7C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57cfa03c23047bb0c731428e97ca716d9a1cf312/ghc >--------------------------------------------------------------- commit 57cfa03c23047bb0c731428e97ca716d9a1cf312 Author: Ben Gamari Date: Sat Jul 29 06:28:14 2017 -0400 Disable parallel garbage collection (#385) This brings productivity from roughly 40% to 95%. With parallel GC we generally spend much of our time synchronizing between the GC threads and relatively little time doing productive work. >--------------------------------------------------------------- 57cfa03c23047bb0c731428e97ca716d9a1cf312 hadrian.cabal | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 4eb43db..af5fd6c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -133,5 +133,11 @@ executable hadrian , happy >= 1.19.4 ghc-options: -Wall -fno-warn-name-shadowing - -rtsopts -with-rtsopts=-I0 + -rtsopts + -- Disable idle GC to avoid redundant GCs while waiting + -- for external processes + -with-rtsopts=-I0 + -- Don't use parallel GC as the synchronization time tends to eat any + -- benefit. + -with-rtsopts=-qg0 -threaded From git at git.haskell.org Fri Oct 27 00:53:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant 'build' component in build paths, rename contextPath to buildPath. (0d7891b) Message-ID: <20171027005318.174753A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0d7891b43ae5f3bd4dd6b271749187cfd4a24f77/ghc >--------------------------------------------------------------- commit 0d7891b43ae5f3bd4dd6b271749187cfd4a24f77 Author: Andrey Mokhov Date: Fri Feb 26 22:36:38 2016 +0000 Drop redundant 'build' component in build paths, rename contextPath to buildPath. >--------------------------------------------------------------- 0d7891b43ae5f3bd4dd6b271749187cfd4a24f77 src/Oracles/ModuleFiles.hs | 16 +++++++--------- src/Rules/Compile.hs | 18 +++++++++--------- src/Rules/Data.hs | 18 +++++++++--------- src/Rules/Dependencies.hs | 15 +++++++-------- src/Rules/Generate.hs | 29 +++++++++++++---------------- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 18 +++++++++--------- src/Rules/Program.hs | 10 +++++----- src/Rules/Register.hs | 13 +++++++------ src/Settings.hs | 10 +++++----- src/Settings/Builders/Common.hs | 7 +++---- src/Settings/Builders/Ghc.hs | 19 ++++++++----------- src/Settings/Builders/Haddock.hs | 4 ++-- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 4 ++-- src/Settings/Packages/Hp2ps.hs | 2 +- src/Settings/Packages/Rts.hs | 4 ++-- src/Settings/Packages/Touchy.hs | 4 ++-- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/Paths.hs | 16 ++++++++-------- 23 files changed, 107 insertions(+), 116 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 0d7891b43ae5f3bd4dd6b271749187cfd4a24f77 From git at git.haskell.org Fri Oct 27 00:53:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use GHC to compile C files (#380) (e6dcd1b) Message-ID: <20171027005318.5A1073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8/ghc >--------------------------------------------------------------- commit e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8 Author: Zhen Zhang Date: Sat Jul 29 18:37:58 2017 +0800 Use GHC to compile C files (#380) >--------------------------------------------------------------- e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8 src/Builder.hs | 4 ++-- src/Rules/Compile.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 24 +++++++++++++++++++++++- src/Settings/Default.hs | 1 + src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Rts.hs | 7 ++++--- 6 files changed, 34 insertions(+), 10 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 7937319..4112900 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -15,8 +15,8 @@ import Stage -- * Extracting source dependencies, e.g. by passing @-M@ command line argument; -- * Linking object files & static libraries into an executable. -- We have CcMode for C compiler and GhcMode for GHC. -data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show) -data GhcMode = CompileHs | FindHsDependencies | LinkHs +data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show) +data GhcMode = CompileCWithGhc | CompileHs | FindHsDependencies | LinkHs deriving (Eq, Generic, Show) -- | GhcPkg can initialise a package database and register packages in it. diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 87fc39a..d3d2ed5 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -28,9 +28,9 @@ compilePackage rs context at Context {..} = do buildWithResources rs $ Target context (Ghc CompileHs stage) [src] [obj] priority 2.0 $ do - nonHs "c" %> compile (Cc CompileC ) (obj2src "c" isGeneratedCFile ) - nonHs "cmm" %> compile (Ghc CompileHs) (obj2src "cmm" isGeneratedCmmFile) - nonHs "s" %> compile (Ghc CompileHs) (obj2src "S" $ const False ) + nonHs "c" %> compile (Ghc CompileCWithGhc) (obj2src "c" isGeneratedCFile ) + nonHs "cmm" %> compile (Ghc CompileHs) (obj2src "cmm" isGeneratedCmmFile) + nonHs "s" %> compile (Ghc CompileHs) (obj2src "S" $ const False ) -- TODO: Add dependencies for #include of .h and .hs-incl files (gcc -MM?). [ path "*" <.> suf way | suf <- [ osuf, hisuf] ] &%> compileHs diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index bb7c1e0..b7d5d70 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,4 +1,7 @@ -module Settings.Builders.Ghc (ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs) where +module Settings.Builders.Ghc ( + ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs, + ghcCbuilderArgs +) where import Flavour import GHC @@ -15,6 +18,25 @@ ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do , append =<< getInputs , arg "-o", arg =<< getOutput ] +ghcCbuilderArgs :: Args +ghcCbuilderArgs = + builder (Ghc CompileCWithGhc) ? do + way <- getWay + let ccArgs = [ append =<< getPkgDataList CcArgs + , getSettingList . ConfCcArgs =<< getStage + , cIncludeArgs + , arg "-Werror" + , Dynamic `wayUnit` way ? append [ "-fPIC", "-DDYNAMIC" ] ] + + mconcat [ arg "-Wall" + , ghcLinkArgs + , commonGhcArgs + , mconcat (map (map ("-optc" ++) <$>) ccArgs) + , arg "-c" + , append =<< getInputs + , arg "-o" + , arg =<< getOutput ] + ghcLinkArgs :: Args ghcLinkArgs = builder (Ghc LinkHs) ? do stage <- getStage diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index b65e86a..2940406 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -212,6 +212,7 @@ defaultBuilderArgs = mconcat , deriveConstantsBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs + , ghcCbuilderArgs , ghcCabalBuilderArgs , ghcCabalHsColourBuilderArgs , ghcMBuilderArgs diff --git a/src/Settings/Packages/Base.hs b/src/Settings/Packages/Base.hs index 219c9d4..07c19ce 100644 --- a/src/Settings/Packages/Base.hs +++ b/src/Settings/Packages/Base.hs @@ -7,4 +7,4 @@ import Settings basePackageArgs :: Args basePackageArgs = package base ? mconcat [ builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) - , builder Cc ? arg "-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. + , builder (Ghc CompileCWithGhc) ? arg "-optc-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 5a76eae..87e1fe8 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -48,8 +48,7 @@ rtsPackageArgs = package rts ? do ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir ghclibDir <- expr installGhcLibDir - mconcat - [ builder Cc ? mconcat + let cArgs = [ arg "-Irts" , arg $ "-I" ++ path , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" @@ -96,8 +95,10 @@ rtsPackageArgs = package rts ? do append [ "-Wno-incompatible-pointer-types" ] ] + mconcat + [ builder (Cc FindCDependencies) ? mconcat cArgs + , builder (Ghc CompileCWithGhc) ? mconcat (map (map ("-optc" ++) <$>) cArgs) , builder Ghc ? arg "-Irts" - , builder HsCpp ? append [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir From git at git.haskell.org Fri Oct 27 00:53:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use default project name on AppVeyor. (2e3ec0c) Message-ID: <20171027005321.ABE1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2e3ec0cce02a1f125b5672b2f7a5fb85afee0605/ghc >--------------------------------------------------------------- commit 2e3ec0cce02a1f125b5672b2f7a5fb85afee0605 Author: Andrey Mokhov Date: Fri Feb 26 22:55:25 2016 +0000 Use default project name on AppVeyor. >--------------------------------------------------------------- 2e3ec0cce02a1f125b5672b2f7a5fb85afee0605 .appveyor.yml => appveyor.yml | 0 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/.appveyor.yml b/appveyor.yml similarity index 100% rename from .appveyor.yml rename to appveyor.yml From git at git.haskell.org Fri Oct 27 00:53:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix profiled GHC context (7b4fdfb) Message-ID: <20171027005321.F0A963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b4fdfba5f8a58c742a23a70b70085830f540e0e/ghc >--------------------------------------------------------------- commit 7b4fdfba5f8a58c742a23a70b70085830f540e0e Author: Andrey Mokhov Date: Tue Aug 1 01:39:38 2017 +0100 Fix profiled GHC context See #387 >--------------------------------------------------------------- 7b4fdfba5f8a58c742a23a70b70085830f540e0e src/Settings.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings.hs b/src/Settings.hs index c1d4fbb..b65a17b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -70,7 +70,7 @@ integerLibraryName = pkgNameString $ integerLibrary flavour programContext :: Stage -> Package -> Context programContext stage pkg - | pkg == ghc && ghcProfiled flavour = Context stage pkg profiling + | pkg == ghc && ghcProfiled flavour && stage > Stage0 = Context stage pkg profiling | otherwise = vanillaContext stage pkg -- TODO: switch to Set Package as the order of packages should not matter? From git at git.haskell.org Fri Oct 27 00:53:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing arguments for rts package. (13b1491) Message-ID: <20171027005325.2C06D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13b1491faf02d9e03385ad61a26bf90cbc951fda/ghc >--------------------------------------------------------------- commit 13b1491faf02d9e03385ad61a26bf90cbc951fda Author: Andrey Mokhov Date: Sun Feb 28 23:47:46 2016 +0000 Add missing arguments for rts package. >--------------------------------------------------------------- 13b1491faf02d9e03385ad61a26bf90cbc951fda src/Settings/Packages/Rts.hs | 16 +++++++--------- 1 file changed, 7 insertions(+), 9 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 334a712..ba79289 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -62,7 +62,9 @@ rtsPackageArgs = package rts ? do -- there is a non-inlined variant to use instead. But rts does not -- provide non-inlined alternatives and hence needs the function to -- be inlined. See also Issue #90 - , arg $ "-O2" + , arg "-O2" + + , way == threaded ? arg "-DTHREADED_RTS" , (file "//RtsMessages.*" ||^ file "//Trace.*") ? arg ("-DProjectVersion=" ++ quote projectVersion) @@ -82,7 +84,10 @@ rtsPackageArgs = package rts ? do , "-DTargetOS=" ++ quote targetOs , "-DTargetVendor=" ++ quote targetVendor , "-DGhcUnregisterised=" ++ quote ghcUnreg - , "-DGhcEnableTablesNextToCode=" ++ quote ghcEnableTNC ] ] + , "-DGhcEnableTablesNextToCode=" ++ quote ghcEnableTNC ] + + , (file "//Evac_thr.*" ||^ file "//Scav_thr.*") ? + append [ "-DPARALLEL_GC", "-Irts/sm" ] ] , builderGhc ? (arg "-Irts" <> includesArgs) @@ -233,10 +238,3 @@ rtsPackageArgs = package rts ? do -- # -O3 helps unroll some loops (especially in copy() with a constant argument). -- rts/sm/Evac_CC_OPTS += -funroll-loops -- rts/dist/build/sm/Evac_thr_HC_OPTS += -optc-funroll-loops - --- # These files are just copies of sm/Evac.c and sm/Scav.c respectively, --- # but compiled with -DPARALLEL_GC. --- rts/dist/build/sm/Evac_thr_CC_OPTS += -DPARALLEL_GC -Irts/sm --- rts/dist/build/sm/Scav_thr_CC_OPTS += -DPARALLEL_GC -Irts/sm - --- #----------------------------------------------------------------------------- From git at git.haskell.org Fri Oct 27 00:53:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bump to lts-9.0 (b6be67c) Message-ID: <20171027005325.7E4393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6be67c1c801bda7574a0cd1bb7ca9630deb637f/ghc >--------------------------------------------------------------- commit b6be67c1c801bda7574a0cd1bb7ca9630deb637f Author: Andrey Mokhov Date: Wed Aug 2 00:11:18 2017 +0100 Bump to lts-9.0 See #292, #336 >--------------------------------------------------------------- b6be67c1c801bda7574a0cd1bb7ca9630deb637f hadrian.cabal | 4 ++-- stack.yaml | 36 +++++++++--------------------------- 2 files changed, 11 insertions(+), 29 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index af5fd6c..da905ff 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -122,10 +122,10 @@ executable hadrian , ansi-terminal == 0.6.* , Cabal == 2.0.0.2 , containers == 0.5.* - , directory == 1.2.* + , directory >= 1.2 && < 1.4 , extra >= 1.4.7 , mtl == 2.2.* - , QuickCheck >= 2.6 && < 2.9 + , QuickCheck >= 2.6 && < 2.10 , shake >= 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* diff --git a/stack.yaml b/stack.yaml index 5fa9f94..a05f2cd 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,36 +1,18 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-6.12 +resolver: lts-9.0 # Local packages, usually specified by relative directory name packages: - '.' - '../libraries/Cabal/Cabal' -# Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) -extra-deps: - -# Override default flag values for local packages and extra-deps -flags: {} - -# Extra package databases containing global packages -extra-package-dbs: [] - -# Control whether we use the GHC we find on the path -# system-ghc: false - -# Require a specific version of stack, using version ranges -# require-stack-version: -any # Default -# require-stack-version: >= 1.0.0 - -# Override the architecture used by stack, especially useful on Windows -# arch: i386 -# arch: x86_64 - -# Extra directories used by stack for building -# extra-include-dirs: [/path/to/dir] -# extra-lib-dirs: [/path/to/dir] - -# Allow a newer minor version of GHC than the snapshot specifies -# compiler-check: newer-minor +nix: + packages: + - autoconf + - automake + - gcc + - git + - ncurses + - perl From git at git.haskell.org Fri Oct 27 00:53:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix haddock. (7e7497a) Message-ID: <20171027005328.B1E7D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1/ghc >--------------------------------------------------------------- commit 7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1 Author: Andrey Mokhov Date: Mon Feb 29 02:02:53 2016 +0000 Fix haddock. >--------------------------------------------------------------- 7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1 src/Rules/Data.hs | 18 +++++++++--------- src/Rules/Dependencies.hs | 35 ++++++++++++++++++++++++----------- src/Rules/Generate.hs | 16 +++++++++------- src/Rules/Library.hs | 33 +++++++++++++++++++++------------ src/Settings/Packages/Rts.hs | 19 +++++++++---------- 5 files changed, 72 insertions(+), 49 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 7e7497a8da9e1f4e6c73e169638a8d55b0bcd8b1 From git at git.haskell.org Fri Oct 27 00:53:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix AppVeyor (c8b08a2) Message-ID: <20171027005328.EF6923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8b08a2231e4b8e34f45bf0a983f39fb0b075b6c/ghc >--------------------------------------------------------------- commit c8b08a2231e4b8e34f45bf0a983f39fb0b075b6c Author: Andrey Mokhov Date: Wed Aug 2 00:56:08 2017 +0100 Fix AppVeyor See #336 >--------------------------------------------------------------- c8b08a2231e4b8e34f45bf0a983f39fb0b075b6c appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/appveyor.yml b/appveyor.yml index b80008c..3b2e43b 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -26,6 +26,7 @@ install: build_script: # Build Hadrian + - stack build alex happy # Otherwise 'stack build' fails on AppVeyor - stack build # Run internal Hadrian tests From git at git.haskell.org Fri Oct 27 00:53:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add docs for how to compile on Windows, with a list of complete instructions (3dcbe7a) Message-ID: <20171027005332.1E73F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3dcbe7a62e7ad62016456000c925d6493e509a2e/ghc >--------------------------------------------------------------- commit 3dcbe7a62e7ad62016456000c925d6493e509a2e Author: Neil Mitchell Date: Thu Mar 3 20:52:50 2016 +0000 Add docs for how to compile on Windows, with a list of complete instructions >--------------------------------------------------------------- 3dcbe7a62e7ad62016456000c925d6493e509a2e doc/windows.md | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) diff --git a/doc/windows.md b/doc/windows.md new file mode 100644 index 0000000..2d823e7 --- /dev/null +++ b/doc/windows.md @@ -0,0 +1,26 @@ +# Compiling on Windows + +Here are a list of instructions to compile GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. + +The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_64-installer) (I just accepted all the defaults), then open a command prompt and run: + + stack setup + stack install happy alex + stack exec -- pacman -S gcc binutils git automake-wrapper tar make patch autoconf --noconfirm + stack exec -- git clone --recursive git://git.haskell.org/ghc.git + cd ghc + stack exec -- git clone git://github.com/snowleopard/shaking-up-ghc shake-build + stack build --stack-yaml=shake-build/stack.yaml --only-dependencies + stack exec -- perl boot + stack exec -- bash configure --enable-tarballs-autodownload + stack exec --stack-yaml=shake-build/stack.yaml -- shake-build/build.bat -j + +The entire process should take about an hour. + +#### Future ideas + +Here are some alternatives that have been considered, but not yet tested. Use the instructions above. + +* Use `shake-build/build.bat --setup` to replace `boot` and `configure`. +* The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. +* Can Happy/Alex be installed by adding them as tool dependencies to the Stack file? From git at git.haskell.org Fri Oct 27 00:53:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to building using GHC 8.0.2 and GHC 8.2.1 on Travis (3a39f38) Message-ID: <20171027005332.6B5773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3a39f383a05863a78b63a2ca445e863e75bede19/ghc >--------------------------------------------------------------- commit 3a39f383a05863a78b63a2ca445e863e75bede19 Author: Andrey Mokhov Date: Wed Aug 2 01:02:58 2017 +0100 Switch to building using GHC 8.0.2 and GHC 8.2.1 on Travis >--------------------------------------------------------------- 3a39f383a05863a78b63a2ca445e863e75bede19 .travis.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index ba67ae3..49fac80 100644 --- a/.travis.yml +++ b/.travis.yml @@ -29,17 +29,17 @@ matrix: - os: linux env: MODE="--flavour=quickest" - compiler: "GHC 7.10.3" + compiler: "GHC 8.2.1" addons: apt: packages: - - ghc-7.10.3 + - ghc-8.2.1 - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc before_install: - - PATH="/opt/ghc/7.10.3/bin:$PATH" + - PATH="/opt/ghc/8.2.1/bin:$PATH" - PATH="/opt/cabal/1.22/bin:$PATH" script: From git at git.haskell.org Fri Oct 27 00:53:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on how to install Happy/Alex better (2d02668) Message-ID: <20171027005335.8E84D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d0266864b16b273b7e6d296a42fa60bf75d9bd0/ghc >--------------------------------------------------------------- commit 2d0266864b16b273b7e6d296a42fa60bf75d9bd0 Author: Neil Mitchell Date: Thu Mar 3 23:18:44 2016 +0000 Add a note on how to install Happy/Alex better >--------------------------------------------------------------- 2d0266864b16b273b7e6d296a42fa60bf75d9bd0 doc/windows.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/windows.md b/doc/windows.md index 2d823e7..aa7a560 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -23,4 +23,4 @@ Here are some alternatives that have been considered, but not yet tested. Use th * Use `shake-build/build.bat --setup` to replace `boot` and `configure`. * The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. -* Can Happy/Alex be installed by adding them as tool dependencies to the Stack file? +* Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:53:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean the source tree before building source distribution (e918ec1) Message-ID: <20171027005335.D19FE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e918ec1d54a5e1b02bc6d466d0487cece77172a4/ghc >--------------------------------------------------------------- commit e918ec1d54a5e1b02bc6d466d0487cece77172a4 Author: Andrey Mokhov Date: Wed Aug 2 02:51:38 2017 +0100 Clean the source tree before building source distribution See #384 >--------------------------------------------------------------- e918ec1d54a5e1b02bc6d466d0487cece77172a4 src/Rules/Clean.hs | 28 +++++++++++++++++----------- src/Rules/SourceDist.hs | 3 +++ 2 files changed, 20 insertions(+), 11 deletions(-) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 33f1e3e..a8528e8 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -1,4 +1,4 @@ -module Rules.Clean (cleanRules) where +module Rules.Clean (clean, cleanSourceTree, cleanRules) where import Base import Settings.Path @@ -6,14 +6,20 @@ import Stage import UserSettings import Util +clean :: Action () +clean = do + cleanSourceTree + putBuild $ "| Remove Hadrian files..." + removeDirectory generatedPath + removeFilesAfter buildRootPath ["//*"] + putSuccess $ "| Done. " + +cleanSourceTree :: Action () +cleanSourceTree = do + forM_ [Stage0 ..] $ removeDirectory . (buildRootPath -/-) . stageString + removeDirectory inplaceBinPath + removeDirectory inplaceLibPath + removeDirectory "sdistprep" + cleanRules :: Rules () -cleanRules = do - "clean" ~> do - forM_ [Stage0 ..] $ removeDirectory . (buildRootPath -/-) . stageString - removeDirectory generatedPath - removeDirectory inplaceBinPath - removeDirectory inplaceLibPath - removeDirectory "sdistprep" - putBuild $ "| Remove Hadrian files..." - removeFilesAfter buildRootPath ["//*"] - putSuccess $ "| Done. " +cleanRules = "clean" ~> clean diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index 7a60238..40a4156 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -4,12 +4,14 @@ import Base import Builder import Oracles.Config.Setting import Oracles.DirectoryContents +import Rules.Clean import UserSettings import Util sourceDistRules :: Rules () sourceDistRules = do "sdist-ghc" ~> do + cleanSourceTree -- We clean the source tree first, see #384 version <- setting ProjectVersion need ["sdistprep/ghc-" ++ version ++ "-src.tar.xz"] putSuccess "| Done" @@ -41,6 +43,7 @@ prepareTree dest = do , Test "//*~" , Test "//autom4te*" , Test "//dist" + , Test "//dist-install" , Test "//log" , Test "//stage0" , Test "//stage1" From git at git.haskell.org Fri Oct 27 00:53:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #212 from ndmitchell/master (a5a37b9) Message-ID: <20171027005339.B82593A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a5a37b93f8d6e4a521a3770bc0a4b8b6c8bc5fe4/ghc >--------------------------------------------------------------- commit a5a37b93f8d6e4a521a3770bc0a4b8b6c8bc5fe4 Merge: 7e7497a 2d02668 Author: Andrey Mokhov Date: Thu Mar 3 23:40:30 2016 +0000 Merge pull request #212 from ndmitchell/master Add docs for how to compile on Windows [skip ci] >--------------------------------------------------------------- a5a37b93f8d6e4a521a3770bc0a4b8b6c8bc5fe4 doc/windows.md | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) From git at git.haskell.org Fri Oct 27 00:53:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: cabal-install-2.x can new-build (#386) (6e8b0af) Message-ID: <20171027005339.E4BB53A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e8b0afa1be2fd735784f7e1213a79694b512aa7/ghc >--------------------------------------------------------------- commit 6e8b0afa1be2fd735784f7e1213a79694b512aa7 Author: Oleg Grenrus Date: Wed Aug 2 13:33:09 2017 +0300 cabal-install-2.x can new-build (#386) >--------------------------------------------------------------- 6e8b0afa1be2fd735784f7e1213a79694b512aa7 .gitignore | 1 + build.cabal.sh | 4 ++-- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/.gitignore b/.gitignore index 2e3581b..4b026f2 100644 --- a/.gitignore +++ b/.gitignore @@ -11,6 +11,7 @@ cabal.sandbox.config # build.cabal-new.sh specific /dist-newstyle/ +.ghc.environment.* # build.stack.sh and build.stack.bat specific /.stack-work/ diff --git a/build.cabal.sh b/build.cabal.sh index 973cd3e..0dd9731 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -42,14 +42,14 @@ CABVERSTR=$("$CABAL" --numeric-version) CABVER=( ${CABVERSTR//./ } ) -if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then +if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then # New enough cabal version detected, so # let's use the superior 'cabal new-build' mode # there's no 'cabal new-run' yet, but it's easy to emulate "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" - "./dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ + $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ --lint \ --directory "$absoluteRoot/.." \ "$@" From git at git.haskell.org Fri Oct 27 00:53:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to Stack-based build instructions for Windows. (42bce9a) Message-ID: <20171027005343.DB9A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/42bce9aa45d72ad571223b3c23996177ca22cef1/ghc >--------------------------------------------------------------- commit 42bce9aa45d72ad571223b3c23996177ca22cef1 Author: Andrey Mokhov Date: Fri Mar 4 00:18:18 2016 +0000 Link to Stack-based build instructions for Windows. >--------------------------------------------------------------- 42bce9aa45d72ad571223b3c23996177ca22cef1 README.md | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 96b3106..aca17ea 100644 --- a/README.md +++ b/README.md @@ -41,7 +41,8 @@ system to be in the `shake-build` directory of the GHC source tree: * Build GHC using `shake-build/build.sh` or `shake-build/build.bat` (on Windows) instead of `make`. You might want to enable parallelism with `-j`. We will further refer to the build script simply as `build`. If you are interested in building in a Cabal sandbox -or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. +or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Also +see [instructions for building GHC on Windows using Stack][windows-build]. Using the build system ---------------------- @@ -133,6 +134,7 @@ helped me endure and enjoy the project. [issues]: https://github.com/snowleopard/shaking-up-ghc/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild +[windows-build]: https://github.com/snowleopard/shaking-up-ghc/blob/master/doc/windows.md [build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs From git at git.haskell.org Fri Oct 27 00:53:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant line (dd4270a) Message-ID: <20171027005344.126EF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dd4270a359f5e62e6264064b725aaf427001edc1/ghc >--------------------------------------------------------------- commit dd4270a359f5e62e6264064b725aaf427001edc1 Author: Andrey Mokhov Date: Wed Aug 2 11:39:41 2017 +0100 Drop redundant line See #386 >--------------------------------------------------------------- dd4270a359f5e62e6264064b725aaf427001edc1 build.cabal.sh | 1 - 1 file changed, 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index 0dd9731..2a0e8a7 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -48,7 +48,6 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th # there's no 'cabal new-run' yet, but it's easy to emulate "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ --lint \ --directory "$absoluteRoot/.." \ From git at git.haskell.org Fri Oct 27 00:53:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (f1157df) Message-ID: <20171027005348.875AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f1157df657dbb3f09dd6520331f4699108507bb6/ghc >--------------------------------------------------------------- commit f1157df657dbb3f09dd6520331f4699108507bb6 Author: Andrey Mokhov Date: Fri Mar 4 00:20:39 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- f1157df657dbb3f09dd6520331f4699108507bb6 doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index aa7a560..7fc8dcf 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -1,6 +1,6 @@ -# Compiling on Windows +# Building on Windows -Here are a list of instructions to compile GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. +Here are a list of instructions to build GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_64-installer) (I just accepted all the defaults), then open a command prompt and run: From git at git.haskell.org Fri Oct 27 00:53:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix warnings (81fecb8) Message-ID: <20171027005348.B1B443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/81fecb8b3f23e6e09441b43ae874f0554cedf50b/ghc >--------------------------------------------------------------- commit 81fecb8b3f23e6e09441b43ae874f0554cedf50b Author: Andrey Mokhov Date: Fri Aug 4 21:15:29 2017 +0100 Fix warnings >--------------------------------------------------------------- 81fecb8b3f23e6e09441b43ae874f0554cedf50b hadrian.cabal | 22 ++++++++++++---------- src/Base.hs | 4 ++-- src/Expression.hs | 22 +++++++++++++--------- src/Settings/Builders/Haddock.hs | 6 +++--- 4 files changed, 30 insertions(+), 24 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index da905ff..6dab6d0 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -131,13 +131,15 @@ executable hadrian , unordered-containers == 0.2.* build-tools: alex >= 3.1 , happy >= 1.19.4 - ghc-options: -Wall - -fno-warn-name-shadowing - -rtsopts - -- Disable idle GC to avoid redundant GCs while waiting - -- for external processes - -with-rtsopts=-I0 - -- Don't use parallel GC as the synchronization time tends to eat any - -- benefit. - -with-rtsopts=-qg0 - -threaded + ghc-options: -Wall + -Wincomplete-record-updates + -Wredundant-constraints + -fno-warn-name-shadowing + -rtsopts + -- Disable idle GC to avoid redundant GCs while waiting + -- for external processes + -with-rtsopts=-I0 + -- Don't use parallel GC as the synchronization time tends to eat any + -- benefit. + -with-rtsopts=-qg0 + -threaded diff --git a/src/Base.hs b/src/Base.hs index d717f2a..9e2922b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -6,7 +6,7 @@ module Base ( module Data.Function, module Data.List.Extra, module Data.Maybe, - module Data.Monoid, + module Data.Semigroup, -- * Shake module Development.Shake, @@ -29,7 +29,7 @@ import Data.Char import Data.Function import Data.List.Extra import Data.Maybe -import Data.Monoid +import Data.Semigroup import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath diff --git a/src/Expression.hs b/src/Expression.hs index a09bb8c..251c04f 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -19,7 +19,7 @@ module Expression ( getTopDirectory, -- * Re-exports - module Data.Monoid, + module Data.Semigroup, module Builder, module Package, module Stage, @@ -28,7 +28,7 @@ module Expression ( import Control.Monad.Trans.Reader import Control.Monad.Trans -import Data.Monoid +import Data.Semigroup import Base import Builder @@ -52,9 +52,13 @@ expr = Expr . lift exprIO :: IO a -> Expr a exprIO = Expr . liftIO -instance Monoid a => Monoid (Expr a) where - mempty = Expr $ return mempty - mappend (Expr x) (Expr y) = Expr $ (<>) <$> x <*> y +instance Semigroup a => Semigroup (Expr a) where + Expr x <> Expr y = Expr $ (<>) <$> x <*> y + +-- TODO: The 'Semigroup a' constraint will at some point become redundant. +instance (Semigroup a, Monoid a) => Monoid (Expr a) where + mempty = pure mempty + mappend = (<>) instance Applicative Expr where pure = Expr . pure @@ -78,15 +82,15 @@ type Ways = Expr [Way] -- Basic operations on expressions: -- | Append something to an expression. -append :: Monoid a => a -> Expr a -append = Expr . return +append :: a -> Expr a +append = pure -- | Remove given elements from a list expression. remove :: Eq a => [a] -> Expr [a] -> Expr [a] remove xs e = filter (`notElem` xs) <$> e -- | Apply a predicate to an expression. -applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a +applyPredicate :: (Monoid a, Semigroup a) => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate if bool then expr else mempty @@ -97,7 +101,7 @@ arg = append . return -- | A convenient operator for predicate application. class PredicateLike a where - (?) :: Monoid m => a -> Expr m -> Expr m + (?) :: (Monoid m, Semigroup m) => a -> Expr m -> Expr m infixr 3 ? diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index bb37d0b..4c6f862 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -5,9 +5,9 @@ import Settings.Builders.Ghc -- | Given a version string such as "2.16.2" produce an integer equivalent. versionToInt :: String -> Int -versionToInt s = major * 1000 + minor * 10 + patch - where - [major, minor, patch] = map read . words $ replaceEq '.' ' ' s +versionToInt s = case map read . words $ replaceEq '.' ' ' s of + [major, minor, patch] -> major * 1000 + minor * 10 + patch + _ -> error "versionToInt: cannot parse version." haddockBuilderArgs :: Args haddockBuilderArgs = builder Haddock ? do From git at git.haskell.org Fri Oct 27 00:53:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Error when a non-optional builder is not specified. (8ba5cff) Message-ID: <20171027005353.1F3463A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ba5cfffa37a1992567104a90566d506b4d83f56/ghc >--------------------------------------------------------------- commit 8ba5cfffa37a1992567104a90566d506b4d83f56 Author: Andrey Mokhov Date: Fri Mar 4 01:43:30 2016 +0000 Error when a non-optional builder is not specified. See #211. >--------------------------------------------------------------- 8ba5cfffa37a1992567104a90566d506b4d83f56 src/Builder.hs | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 75d3d4e..eee24cb 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -86,6 +86,11 @@ isStaged = \case (GhcPkg _) -> True _ -> False +isOptional :: Builder -> Bool +isOptional = \case + HsColour -> True + _ -> False + -- TODO: get rid of fromJust -- | Determine the location of a 'Builder' builderPath :: Builder -> Action FilePath @@ -116,9 +121,13 @@ builderPath builder = case builderProvenance builder of _ -> error $ "Cannot determine builderKey for " ++ show builder path <- askConfigWithDefault builderKey . putError $ "\nCannot find path to '" ++ builderKey - ++ "' in configuration files. Have you forgot to run configure?" - if path == "" -- TODO: get rid of "" paths - then return "" + ++ "' in system.config file. Have you forgot to run configure?" + if null path + then do + if isOptional builder + then return "" + else putError $ "Builder '" ++ builderKey ++ "' is not specified in" + ++ " system.config file. Cannot proceed without it." else do path' <- lookupInPath path fixAbsolutePathOnWindows $ path' -<.> exe From git at git.haskell.org Fri Oct 27 00:53:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out generic build infrastructure (48e8b6f) Message-ID: <20171027005353.18D033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/48e8b6f223154b9806081e6018099c66dad5a396/ghc >--------------------------------------------------------------- commit 48e8b6f223154b9806081e6018099c66dad5a396 Author: Andrey Mokhov Date: Sat Aug 5 01:02:57 2017 +0100 Factor out generic build infrastructure See #347 >--------------------------------------------------------------- 48e8b6f223154b9806081e6018099c66dad5a396 hadrian.cabal | 2 + src/Expression.hs | 130 ++++++--------------------------------------- src/Hadrian/Expression.hs | 125 +++++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Target.hs | 31 +++++++++++ src/Oracles/ArgsHash.hs | 8 +-- src/Rules/Compile.hs | 6 +-- src/Rules/Configure.hs | 2 +- src/Rules/Data.hs | 4 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 10 ++-- src/Rules/Gmp.hs | 8 +-- src/Rules/Install.hs | 6 +-- src/Rules/Libffi.hs | 6 +-- src/Rules/Library.hs | 8 +-- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 4 +- src/Rules/Test.hs | 2 +- src/Target.hs | 35 ++---------- src/Util.hs | 21 ++++---- 20 files changed, 225 insertions(+), 189 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 48e8b6f223154b9806081e6018099c66dad5a396 From git at git.haskell.org Fri Oct 27 00:53:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Cabal build scripts on CI (fe857d0) Message-ID: <20171027005356.F19603A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fe857d074b30bf657216acdda98067aae3577440/ghc >--------------------------------------------------------------- commit fe857d074b30bf657216acdda98067aae3577440 Author: Andrey Mokhov Date: Sat Aug 5 11:34:34 2017 +0100 Use Cabal build scripts on CI >--------------------------------------------------------------- fe857d074b30bf657216acdda98067aae3577440 .travis.yml | 10 +++++----- circle.yml | 4 ++-- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/.travis.yml b/.travis.yml index 49fac80..c23e92a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,10 +18,10 @@ matrix: script: # Run internal Hadrian tests - - ./build.sh selftest + - ./build.cabal.sh selftest # Build GHC - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. @@ -44,10 +44,10 @@ matrix: script: # Run internal Hadrian tests - - ./build.sh selftest + - ./build.cabal.sh selftest # Build GHC - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. @@ -63,7 +63,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 install: # Add Cabal to PATH diff --git a/circle.yml b/circle.yml index 457add7..606664a 100644 --- a/circle.yml +++ b/circle.yml @@ -30,10 +30,10 @@ compile: # XXX: export PATH doesn't work well either, so we use inline env # Self test - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh selftest + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- test: override: From git at git.haskell.org Fri Oct 27 00:53:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:53:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make Objdump builder optional. (d89358f) Message-ID: <20171027005356.EC6EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d89358f615755e5482e526c38d52cef76cfb3b7e/ghc >--------------------------------------------------------------- commit d89358f615755e5482e526c38d52cef76cfb3b7e Author: Andrey Mokhov Date: Sat Mar 5 13:17:23 2016 +0000 Make Objdump builder optional. See #211. >--------------------------------------------------------------- d89358f615755e5482e526c38d52cef76cfb3b7e src/Builder.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index eee24cb..e8011e7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -86,9 +86,14 @@ isStaged = \case (GhcPkg _) -> True _ -> False +-- TODO: Some builders are required only on certain platforms. For example, +-- Objdump is only required on OpenBSD and AIX, as mentioned in #211. Add +-- support for platform-specific optional builders as soon as we can reliably +-- test this feature. isOptional :: Builder -> Bool isOptional = \case HsColour -> True + Objdump -> True _ -> False -- TODO: get rid of fromJust From git at git.haskell.org Fri Oct 27 00:54:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split buildPackageData rule. (c1adff7) Message-ID: <20171027005400.DABC83A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c1adff7f36f088712b52c310eb0fb925e72d2549/ghc >--------------------------------------------------------------- commit c1adff7f36f088712b52c310eb0fb925e72d2549 Author: Andrey Mokhov Date: Sat Mar 5 14:07:47 2016 +0000 Split buildPackageData rule. See #206. >--------------------------------------------------------------- c1adff7f36f088712b52c310eb0fb925e72d2549 src/Rules/Data.hs | 18 +++++++----------- 1 file changed, 7 insertions(+), 11 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index fee310f..719352f 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -1,7 +1,5 @@ module Rules.Data (buildPackageData) where -import qualified System.Directory as IO - import Base import Context import Expression @@ -22,8 +20,9 @@ buildPackageData context at Context {..} = do configure = pkgPath package -/- "configure" dataFile = pkgDataFile context oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 + inTreeMk = oldPath -/- takeFileName dataFile -- TODO: remove, #113 - [dataFile, oldPath -/- "package-data.mk"] &%> \_ -> do + inTreeMk %> \mk -> do -- The first thing we do with any package is make sure all generated -- dependencies are in place before proceeding. orderOnly $ generatedDependencies stage package @@ -37,22 +36,19 @@ buildPackageData context at Context {..} = do let depPkgs = matchPackageNames (sort pkgs) deps need =<< traverse (pkgConfFile . vanillaContext stage) depPkgs - -- TODO: get rid of this, see #113 - let inTreeMk = oldPath -/- takeFileName dataFile - need [cabalFile] - build $ Target context GhcCabal [cabalFile] [inTreeMk] + build $ Target context GhcCabal [cabalFile] [mk] - -- TODO: get rid of this, see #113 - liftIO $ IO.copyFile inTreeMk dataFile + -- TODO: get rid of this, see #113 + dataFile %> \mk -> do + copyFile inTreeMk mk autogenFiles <- getDirectoryFiles (oldPath -/- "build") ["autogen/*"] createDirectory $ buildPath context -/- "autogen" forM_ autogenFiles $ \file -> do copyFile (oldPath -/- "build" -/- file) (buildPath context -/- file) let haddockPrologue = "haddock-prologue.txt" copyFile (oldPath -/- haddockPrologue) (buildPath context -/- haddockPrologue) - - postProcessPackageData context dataFile + postProcessPackageData context mk -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps priority 2.0 $ do From git at git.haskell.org Fri Oct 27 00:54:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move ArgsHash oracle to the library (a432cff) Message-ID: <20171027005400.D7A8E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a432cffccd145a0cb8e7822333fac87e54c02753/ghc >--------------------------------------------------------------- commit a432cffccd145a0cb8e7822333fac87e54c02753 Author: Andrey Mokhov Date: Sun Aug 6 00:55:44 2017 +0100 Move ArgsHash oracle to the library See #347 >--------------------------------------------------------------- a432cffccd145a0cb8e7822333fac87e54c02753 hadrian.cabal | 2 +- src/Builder.hs | 15 +------------ src/Hadrian/Oracles/ArgsHash.hs | 49 +++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Target.hs | 3 +-- src/Oracles/ArgsHash.hs | 35 ----------------------------- src/Rules/Oracles.hs | 7 ++++-- src/Rules/Selftest.hs | 8 ++++--- src/Target.hs | 22 +++++++++++++++--- src/Util.hs | 3 ++- 9 files changed, 83 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 a432cffccd145a0cb8e7822333fac87e54c02753 From git at git.haskell.org Fri Oct 27 00:54:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out general functionality of path oracles to the library (df8e5aa) Message-ID: <20171027005412.5666B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd/ghc >--------------------------------------------------------------- commit df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd Author: Andrey Mokhov Date: Sun Aug 6 02:17:59 2017 +0100 Factor out general functionality of path oracles to the library See #347 >--------------------------------------------------------------- df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd hadrian.cabal | 2 +- src/Base.hs | 4 -- src/Expression.hs | 5 -- src/Hadrian/Oracles/ArgsHash.hs | 6 +- src/Hadrian/Oracles/DirectoryContents.hs | 6 +- src/Hadrian/Oracles/Path.hs | 57 ++++++++++++++++++ src/Hadrian/Utilities.hs | 8 +++ src/Oracles/Path.hs | 99 -------------------------------- src/Rules/Data.hs | 1 - src/Rules/Install.hs | 5 +- src/Rules/Oracles.hs | 4 +- src/Rules/Program.hs | 6 +- src/Rules/Test.hs | 3 +- src/Rules/Wrappers.hs | 16 +++--- src/Settings.hs | 40 ++++++++++++- src/Settings/Builders/Common.hs | 4 +- src/Settings/Builders/Configure.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 8 +-- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Path.hs | 9 ++- src/Util.hs | 9 ++- 22 files changed, 148 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 df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd From git at git.haskell.org Fri Oct 27 00:54:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Hash Target inputs in ArgsHashOracle. (ad44a95) Message-ID: <20171027005405.166A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ad44a95b78bc2ed712c44f55b691203787b3df93/ghc >--------------------------------------------------------------- commit ad44a95b78bc2ed712c44f55b691203787b3df93 Author: Andrey Mokhov Date: Tue Mar 8 01:35:17 2016 +0000 Hash Target inputs in ArgsHashOracle. See #217. >--------------------------------------------------------------- ad44a95b78bc2ed712c44f55b691203787b3df93 src/Oracles/ArgsHash.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index aec0dc9..d3bfd61 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -23,8 +23,8 @@ newtype ArgsHashKey = ArgsHashKey Target -- TODO: Hash Target to improve accuracy and performance. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do - let firstInput = take 1 $ inputs target - _ <- askOracle . ArgsHashKey $ target { inputs = firstInput } :: Action Int + let hashed = [ show . hash $ inputs target ] + _ <- askOracle . ArgsHashKey $ target { inputs = hashed } :: Action Int return () -- Oracle for storing per-target argument list hashes From git at git.haskell.org Fri Oct 27 00:54:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable library profiling in quick build flavour. (c7a4165) Message-ID: <20171027005408.C71ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7a41657a0393aa1a1d5d5b7219c0f8c7c2e31dc/ghc >--------------------------------------------------------------- commit c7a41657a0393aa1a1d5d5b7219c0f8c7c2e31dc Author: Andrey Mokhov Date: Wed Mar 9 23:47:34 2016 +0000 Disable library profiling in quick build flavour. See #188. >--------------------------------------------------------------- c7a41657a0393aa1a1d5d5b7219c0f8c7c2e31dc src/Settings/Flavours/Quick.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 1f2def1..97af880 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -1,9 +1,10 @@ -module Settings.Flavours.Quick (quickFlavourArgs) where +module Settings.Flavours.Quick (quickFlavourArgs, quickFlavourWays) where import Expression import Predicates (builderGhc) --- TODO: consider putting all flavours in a single file --- TODO: handle other, non Args, settings affected by flavours quickFlavourArgs :: Args quickFlavourArgs = builderGhc ? arg "-O0" + +quickFlavourWays :: Ways +quickFlavourWays = remove [profiling] From git at git.haskell.org Fri Oct 27 00:54:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow build flavours to control Ways. (0b327b5) Message-ID: <20171027005412.9148B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b327b564fbab286b6999040565046b5d6bf60c8/ghc >--------------------------------------------------------------- commit 0b327b564fbab286b6999040565046b5d6bf60c8 Author: Andrey Mokhov Date: Wed Mar 9 23:48:54 2016 +0000 Allow build flavours to control Ways. See #188, #218. >--------------------------------------------------------------- 0b327b564fbab286b6999040565046b5d6bf60c8 src/Settings/Ways.hs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 0fee897..7e46406 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -1,14 +1,18 @@ module Settings.Ways (getLibraryWays, getRtsWays) where +import CmdLineFlag import Base import Expression +import Oracles.Config.Flag import Predicates +import Settings.Flavours.Quick import Settings.User -import Oracles.Config.Flag -- | Combine default ways with user modifications getLibraryWays :: Expr [Way] -getLibraryWays = fromDiffExpr $ defaultLibraryWays <> userLibraryWays +getLibraryWays = fromDiffExpr $ mconcat [ defaultLibraryWays + , userLibraryWays + , flavourLibraryWays ] getRtsWays :: Expr [Way] getRtsWays = fromDiffExpr $ defaultRtsWays <> userRtsWays @@ -24,6 +28,10 @@ defaultLibraryWays = mconcat , notStage0 ? append [profiling] , notStage0 ? platformSupportsSharedLibs ? append [dynamic] ] +flavourLibraryWays :: Ways +flavourLibraryWays = mconcat + [ cmdFlavour == Quick ? quickFlavourWays ] + defaultRtsWays :: Ways defaultRtsWays = do ways <- getLibraryWays From git at git.haskell.org Fri Oct 27 00:54:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge all generators into a single file, factor our common functionality into the library. (8e97252) Message-ID: <20171027005416.9240C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e97252efa426ec9caff762de839ebeded401692/ghc >--------------------------------------------------------------- commit 8e97252efa426ec9caff762de839ebeded401692 Author: Andrey Mokhov Date: Sun Aug 6 14:17:06 2017 +0100 Merge all generators into a single file, factor our common functionality into the library. See #347 >--------------------------------------------------------------- 8e97252efa426ec9caff762de839ebeded401692 hadrian.cabal | 8 - src/Base.hs | 51 +---- src/Expression.hs | 2 +- src/Hadrian/Expression.hs | 13 +- src/Hadrian/Utilities.hs | 56 +++++- src/Oracles/Dependencies.hs | 1 + src/Oracles/ModuleFiles.hs | 1 + src/Rules/Configure.hs | 2 +- src/Rules/Generate.hs | 310 ++++++++++++++++++++++++++++++- src/Rules/Generators/Common.hs | 18 -- src/Rules/Generators/ConfigHs.hs | 102 ---------- src/Rules/Generators/GhcAutoconfH.hs | 37 ---- src/Rules/Generators/GhcBootPlatformH.hs | 57 ------ src/Rules/Generators/GhcPlatformH.hs | 56 ------ src/Rules/Generators/GhcSplit.hs | 27 --- src/Rules/Generators/GhcVersionH.hs | 35 ---- src/Rules/Generators/VersionHs.hs | 18 -- src/Rules/Gmp.hs | 7 +- src/Rules/Libffi.hs | 4 +- src/Rules/Selftest.hs | 1 + src/Rules/Test.hs | 5 +- src/Settings/Builders/Haddock.hs | 2 + src/Settings/Packages/Rts.hs | 7 +- src/Settings/Path.hs | 7 +- src/Way.hs | 3 +- 25 files changed, 394 insertions(+), 436 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 8e97252efa426ec9caff762de839ebeded401692 From git at git.haskell.org Fri Oct 27 00:54:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge Predicate into Expression (2bdb94f) Message-ID: <20171027005420.4900A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c/ghc >--------------------------------------------------------------- commit 2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c Author: Andrey Mokhov Date: Sun Aug 6 22:27:23 2017 +0100 Merge Predicate into Expression >--------------------------------------------------------------- 2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c hadrian.cabal | 1 - src/Builder.hs | 85 +++++++++++++++++++++++--------- src/Context.hs | 24 ++++++++-- src/Expression.hs | 76 +++++++++++++++++++++++------ src/Oracles/Dependencies.hs | 2 +- src/Predicate.hs | 93 ------------------------------------ src/Rules/Cabal.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 1 - src/Rules/Install.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Settings/Builders/Common.hs | 2 - src/Settings/Default.hs | 2 +- src/Settings/Default.hs-boot | 2 +- src/Settings/Flavours/Development.hs | 2 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/Quickest.hs | 2 +- src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Cabal.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 12 ++--- src/Settings/Packages/GhcPrim.hs | 8 ++-- src/Settings/Packages/Ghci.hs | 4 +- src/Settings/Packages/Haddock.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/Path.hs | 2 +- src/Target.hs | 2 +- src/UserSettings.hs | 2 +- src/Util.hs | 2 +- 35 files changed, 181 insertions(+), 175 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 2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c From git at git.haskell.org Fri Oct 27 00:54:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move DirectoryContents oracle to the library (7ff841e) Message-ID: <20171027005408.6231A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ff841eb492e16bedfb1d72152e5fc0de4d52c77/ghc >--------------------------------------------------------------- commit 7ff841eb492e16bedfb1d72152e5fc0de4d52c77 Author: Andrey Mokhov Date: Sun Aug 6 01:31:02 2017 +0100 Move DirectoryContents oracle to the library See #347 >--------------------------------------------------------------- 7ff841eb492e16bedfb1d72152e5fc0de4d52c77 hadrian.cabal | 3 ++- src/Base.hs | 14 +------------- src/{ => Hadrian}/Oracles/DirectoryContents.hs | 18 +++++++++++------- src/Hadrian/Utilities.hs | 19 +++++++++++++++++++ src/Rules/Install.hs | 3 ++- src/Rules/Oracles.hs | 4 ++-- src/Rules/SourceDist.hs | 3 ++- src/Util.hs | 2 +- 8 files changed, 40 insertions(+), 26 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 121ba74..b757549 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -28,12 +28,13 @@ executable hadrian , GHC , Hadrian.Expression , Hadrian.Oracles.ArgsHash + , Hadrian.Oracles.DirectoryContents , Hadrian.Target + , Hadrian.Utilities , Oracles.Config , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies - , Oracles.DirectoryContents , Oracles.ModuleFiles , Oracles.PackageData , Oracles.Path diff --git a/src/Base.hs b/src/Base.hs index 9e2922b..7443438 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -33,6 +33,7 @@ import Data.Semigroup import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath +import Hadrian.Utilities import System.Console.ANSI import System.IO import System.Info @@ -72,19 +73,6 @@ replaceWhen p to = map (\from -> if p from then to else from) quote :: String -> String quote s = "'" ++ s ++ "'" --- | Normalise a path and convert all path separators to @/@, even on Windows. -unifyPath :: FilePath -> FilePath -unifyPath = toStandard . normaliseEx - --- | Combine paths with a forward slash regardless of platform. -(-/-) :: FilePath -> FilePath -> FilePath -"" -/- b = b -a -/- b - | last a == '/' = a ++ b - | otherwise = a ++ '/' : b - -infixr 6 -/- - -- Explicit definition to avoid dependency on Data.List.Ordered -- | Difference of two ordered lists. minusOrd :: Ord a => [a] -> [a] -> [a] diff --git a/src/Oracles/DirectoryContents.hs b/src/Hadrian/Oracles/DirectoryContents.hs similarity index 82% rename from src/Oracles/DirectoryContents.hs rename to src/Hadrian/Oracles/DirectoryContents.hs index 1f016ff..e52c5c5 100644 --- a/src/Oracles/DirectoryContents.hs +++ b/src/Hadrian/Oracles/DirectoryContents.hs @@ -1,12 +1,15 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} -module Oracles.DirectoryContents ( +module Hadrian.Oracles.DirectoryContents ( directoryContents, directoryContentsOracle, Match (..), matchAll ) where -import System.Directory.Extra +import Control.Monad +import Development.Shake +import Development.Shake.Classes import GHC.Generics +import System.Directory.Extra -import Base +import Hadrian.Utilities newtype DirectoryContents = DirectoryContents (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -14,6 +17,10 @@ newtype DirectoryContents = DirectoryContents (Match, FilePath) data Match = Test FilePattern | Not Match | And [Match] | Or [Match] deriving (Generic, Eq, Show, Typeable) +instance Binary Match +instance Hashable Match +instance NFData Match + -- | A 'Match' expression that always evaluates to 'True' (i.e. always matches). matchAll :: Match matchAll = And [] @@ -30,11 +37,8 @@ matches (Or ms) f = any (`matches` f) ms directoryContents :: Match -> FilePath -> Action [FilePath] directoryContents expr dir = askOracle $ DirectoryContents (expr, dir) +-- | This oracle answers 'directoryContents' queries and tracks the results. directoryContentsOracle :: Rules () directoryContentsOracle = void $ addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ map unifyPath . filter (matches expr) <$> listFilesInside (return . matches expr) dir - -instance Binary Match -instance Hashable Match -instance NFData Match diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs new file mode 100644 index 0000000..2103452 --- /dev/null +++ b/src/Hadrian/Utilities.hs @@ -0,0 +1,19 @@ +module Hadrian.Utilities ( + -- * FilePath manipulation + unifyPath, (-/-) + ) where + +import Development.Shake.FilePath + +-- | Normalise a path and convert all path separators to @/@, even on Windows. +unifyPath :: FilePath -> FilePath +unifyPath = toStandard . normaliseEx + +-- | Combine paths with a forward slash regardless of platform. +(-/-) :: FilePath -> FilePath -> FilePath +"" -/- b = b +a -/- b + | last a == '/' = a ++ b + | otherwise = a ++ '/' : b + +infixr 6 -/- diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 66e57bf..f90b480 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -1,6 +1,8 @@ {-# LANGUAGE FlexibleContexts #-} module Rules.Install (installRules) where +import Hadrian.Oracles.DirectoryContents + import Base import Target import Context @@ -16,7 +18,6 @@ import Rules.Generate import Settings.Packages.Rts import Oracles.Config.Setting import Oracles.Dependencies -import Oracles.DirectoryContents import Oracles.Path import qualified System.Directory as IO diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index a12bec4..59b55d9 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -1,11 +1,11 @@ module Rules.Oracles (oracleRules) where import qualified Hadrian.Oracles.ArgsHash +import qualified Hadrian.Oracles.DirectoryContents import Base import qualified Oracles.Config import qualified Oracles.Dependencies -import qualified Oracles.DirectoryContents import qualified Oracles.ModuleFiles import qualified Oracles.PackageData import qualified Oracles.Path @@ -15,9 +15,9 @@ import Settings oracleRules :: Rules () oracleRules = do Hadrian.Oracles.ArgsHash.argsHashOracle trackArgument getArgs + Hadrian.Oracles.DirectoryContents.directoryContentsOracle Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles - Oracles.DirectoryContents.directoryContentsOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle Oracles.Path.pathOracle diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index 40a4156..879ae34 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -1,9 +1,10 @@ module Rules.SourceDist (sourceDistRules) where +import Hadrian.Oracles.DirectoryContents + import Base import Builder import Oracles.Config.Setting -import Oracles.DirectoryContents import Rules.Clean import UserSettings import Util diff --git a/src/Util.hs b/src/Util.hs index c4b888d..a616b04 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -12,13 +12,13 @@ import qualified System.IO as IO import qualified Control.Exception.Base as IO import Hadrian.Oracles.ArgsHash +import Hadrian.Oracles.DirectoryContents import Base import CmdLineFlag import Context import Expression import GHC -import Oracles.DirectoryContents import Oracles.Path import Oracles.Config.Setting import Settings From git at git.haskell.org Fri Oct 27 00:54:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Quick flavour now disables library profiling (9b68950) Message-ID: <20171027005420.65E123A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b68950fd0a53a33dbe902ed6e55b627f6ecb516/ghc >--------------------------------------------------------------- commit 9b68950fd0a53a33dbe902ed6e55b627f6ecb516 Author: Andrey Mokhov Date: Thu Mar 10 00:01:55 2016 +0000 Quick flavour now disables library profiling See #188. [skip ci] >--------------------------------------------------------------- 9b68950fd0a53a33dbe902ed6e55b627f6ecb516 README.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index aca17ea..b6d762b 100644 --- a/README.md +++ b/README.md @@ -54,7 +54,8 @@ are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue In addition to standard Shake flags (try `--help`), the build system currently supports several others: * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: -`default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). +`default` and `quick` (adds `-O0` flag to all GHC invocations and disables library +profiling, which speeds up builds by 3-4x). * `--haddock`: build Haddock documentation. * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per From git at git.haskell.org Fri Oct 27 00:54:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (5e1d004) Message-ID: <20171027005404.A2EEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e1d004c4d92f9847f6d96e38c27815429239fea/ghc >--------------------------------------------------------------- commit 5e1d004c4d92f9847f6d96e38c27815429239fea Author: Andrey Mokhov Date: Sun Aug 6 01:24:06 2017 +0100 Minor revision >--------------------------------------------------------------- 5e1d004c4d92f9847f6d96e38c27815429239fea src/Hadrian/Oracles/ArgsHash.hs | 9 +++++---- src/Util.hs | 2 +- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index 0eba6c2..80a170d 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Hadrian.Oracles.ArgsHash ( - TrackArgument, trackAllArguments, checkArgsHash, argsHashOracle + TrackArgument, trackAllArguments, trackArgsHash, argsHashOracle ) where import Control.Monad @@ -34,13 +34,14 @@ newtype ArgsHashKey c b = ArgsHashKey (Target c b) -- in the Shake database. This optimisation is normally harmless, because -- argument list constructors are assumed not to examine target sources, but -- only append them to argument lists where appropriate. -checkArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action () -checkArgsHash t = do +trackArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action () +trackArgsHash t = do let hashedInputs = [ show $ hash (inputs t) ] hashedTarget = target (context t) (builder t) hashedInputs (outputs t) void (askOracle $ ArgsHashKey hashedTarget :: Action Int) --- | Oracle for storing per-target argument list hashes. +-- | This oracle stores per-target argument list hashes in the Shake database, +-- allowing the user to track them between builds using 'trackArgsHash' queries. argsHashOracle :: (ShakeValue c, ShakeValue b) => TrackArgument c b -> Args c b -> Rules () argsHashOracle trackArgument args = void $ addOracle $ \(ArgsHashKey target) -> do diff --git a/src/Util.hs b/src/Util.hs index ed535fe..c4b888d 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -51,7 +51,7 @@ customBuild rs opts target = do argList <- interpret target getArgs verbose <- interpret target verboseCommands let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly - checkArgsHash target -- Rerun the rule if the hash of argList has changed. + trackArgsHash target -- Rerun the rule if the hash of argList has changed. withResources rs $ do putInfo target quietlyUnlessVerbose $ case targetBuilder of From git at git.haskell.org Fri Oct 27 00:54:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build profiled libraries by default. (56526ff) Message-ID: <20171027005416.BC5473A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56526ffc8dde7873fc35db912d9793eba1e63734/ghc >--------------------------------------------------------------- commit 56526ffc8dde7873fc35db912d9793eba1e63734 Author: Andrey Mokhov Date: Wed Mar 9 23:49:48 2016 +0000 Build profiled libraries by default. See #186, #218. >--------------------------------------------------------------- 56526ffc8dde7873fc35db912d9793eba1e63734 src/Settings/User.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index dd6150a..6fc5536 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -30,10 +30,9 @@ userKnownPackages :: [Package] userKnownPackages = [] -- | Control which ways library packages are built --- FIXME: skip profiling for speed -- FIXME: skip dynamic since it's currently broken #4 userLibraryWays :: Ways -userLibraryWays = remove [profiling, dynamic] +userLibraryWays = remove [dynamic] -- | Control which ways the 'rts' package is built userRtsWays :: Ways From git at git.haskell.org Fri Oct 27 00:54:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out generic predicates into the library (65c5d7c) Message-ID: <20171027005423.DCB063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65c5d7c6f75a583439b6c52ce4a89e6026cf76dc/ghc >--------------------------------------------------------------- commit 65c5d7c6f75a583439b6c52ce4a89e6026cf76dc Author: Andrey Mokhov Date: Sun Aug 6 23:18:51 2017 +0100 Factor out generic predicates into the library See #347 >--------------------------------------------------------------- 65c5d7c6f75a583439b6c52ce4a89e6026cf76dc hadrian.cabal | 3 ++- src/Expression.hs | 16 --------------- src/Hadrian/Expression.hs | 43 +++++++++++++++++++++++++++++++---------- src/Hadrian/Oracles/ArgsHash.hs | 2 +- 4 files changed, 36 insertions(+), 28 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index e1505aa..93a755c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -102,7 +102,6 @@ executable hadrian , UserSettings , Util , Way - default-language: Haskell2010 default-extensions: RecordWildCards other-extensions: DeriveFunctor @@ -110,8 +109,10 @@ executable hadrian , FlexibleInstances , GeneralizedNewtypeDeriving , LambdaCase + , MultiParamTypeClasses , OverloadedStrings , ScopedTypeVariables + , TypeFamilies build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* , Cabal == 2.0.0.2 diff --git a/src/Expression.hs b/src/Expression.hs index 274613c..0442c23 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -29,7 +29,6 @@ module Expression ( import Control.Monad.Extra import Data.Semigroup -import Development.Shake import qualified Hadrian.Expression as H import Hadrian.Expression hiding (Expr, Predicate, Args) @@ -107,18 +106,3 @@ notPackage = notM . package libraryPackage :: Predicate libraryPackage = isLibrary <$> getPackage --- | Does any of the input files match a given pattern? -input :: FilePattern -> Predicate -input f = any (f ?==) <$> getInputs - --- | Does any of the input files match any of the given patterns? -inputs :: [FilePattern] -> Predicate -inputs = anyM input - --- | Does any of the output files match a given pattern? -output :: FilePattern -> Predicate -output f = any (f ?==) <$> getOutputs - --- | Does any of the output files match any of the given patterns? -outputs :: [FilePattern] -> Predicate -outputs = anyM output diff --git a/src/Hadrian/Expression.hs b/src/Hadrian/Expression.hs index 8010695..4022f02 100644 --- a/src/Hadrian/Expression.hs +++ b/src/Hadrian/Expression.hs @@ -1,11 +1,14 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} module Hadrian.Expression ( -- * Expressions Expr, Predicate, Args, -- ** Construction and modification - expr, exprIO, arg, remove, (?), + expr, exprIO, arg, remove, + + -- ** Predicates + (?), input, inputs, output, outputs, -- ** Evaluation interpret, interpretInContext, @@ -14,12 +17,14 @@ module Hadrian.Expression ( getContext, getBuilder, getOutputs, getInputs, getInput, getOutput ) where +import Control.Monad.Extra import Control.Monad.Trans import Control.Monad.Trans.Reader import Data.Semigroup import Development.Shake -import Hadrian.Target +import qualified Hadrian.Target as Target +import Hadrian.Target (Target, target) import Hadrian.Utilities -- | 'Expr' @c b a@ is a computation that produces a value of type 'Action' @a@ @@ -71,7 +76,7 @@ p ? e = do bool <- toPredicate p if bool then e else mempty -instance ToPredicate (Predicate c b) c b where +instance (c ~ c', b ~ b') => ToPredicate (Predicate c b) c' b' where toPredicate = id instance ToPredicate Bool c b where @@ -93,28 +98,46 @@ interpretInContext c = interpret $ target c -- | Get the current build 'Context'. getContext :: Expr c b c -getContext = Expr $ asks context +getContext = Expr $ asks Target.context -- | Get the 'Builder' for the current 'Target'. getBuilder :: Expr c b b -getBuilder = Expr $ asks builder +getBuilder = Expr $ asks Target.builder -- | Get the input files of the current 'Target'. getInputs :: Expr c b [FilePath] -getInputs = Expr $ asks inputs +getInputs = Expr $ asks Target.inputs -- | Run 'getInputs' and check that the result contains one input file only. getInput :: (Show b, Show c) => Expr c b FilePath getInput = Expr $ do target <- ask - fromSingleton ("Exactly one input file expected in " ++ show target) <$> asks inputs + fromSingleton ("Exactly one input file expected in " ++ show target) <$> + asks Target.inputs -- | Get the files produced by the current 'Target'. getOutputs :: Expr c b [FilePath] -getOutputs = Expr $ asks outputs +getOutputs = Expr $ asks Target.outputs -- | Run 'getOutputs' and check that the result contains one output file only. getOutput :: (Show b, Show c) => Expr c b FilePath getOutput = Expr $ do target <- ask - fromSingleton ("Exactly one output file expected in " ++ show target) <$> asks outputs + fromSingleton ("Exactly one output file expected in " ++ show target) <$> + asks Target.outputs + +-- | Does any of the input files match a given pattern? +input :: FilePattern -> Predicate c b +input f = any (f ?==) <$> getInputs + +-- | Does any of the input files match any of the given patterns? +inputs :: [FilePattern] -> Predicate c b +inputs = anyM input + +-- | Does any of the output files match a given pattern? +output :: FilePattern -> Predicate c b +output f = any (f ?==) <$> getOutputs + +-- | Does any of the output files match any of the given patterns? +outputs :: [FilePattern] -> Predicate c b +outputs = anyM output \ No newline at end of file diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index 68b67e2..e07fc3f 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -7,7 +7,7 @@ import Control.Monad import Development.Shake import Development.Shake.Classes -import Hadrian.Expression +import Hadrian.Expression hiding (inputs, outputs) import Hadrian.Target -- | 'TrackArgument' is used to specify the arguments that should be tracked by From git at git.haskell.org Fri Oct 27 00:54:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: We can now build profiling way (b052ae7) Message-ID: <20171027005424.19EFD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b052ae700aa9a6831dc824824617bbebc4494351/ghc >--------------------------------------------------------------- commit b052ae700aa9a6831dc824824617bbebc4494351 Author: Andrey Mokhov Date: Thu Mar 10 00:26:04 2016 +0000 We can now build profiling way See #186. [skip ci] >--------------------------------------------------------------- b052ae700aa9a6831dc824824617bbebc4494351 README.md | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/README.md b/README.md index b6d762b..7317384 100644 --- a/README.md +++ b/README.md @@ -100,7 +100,7 @@ zero (see [#197][test-issue]). Current limitations ------------------- The new build system still lacks many important features: -* We only build `vanilla` way: [#4][dynamic-issue], [#186][profiling-issue]. +* We only build `vanilla` and `profiling` way: [#4][dynamic-issue]. * Validation is not implemented: [#187][validation-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. @@ -141,7 +141,6 @@ helped me endure and enjoy the project. [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs [test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 -[profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 From git at git.haskell.org Fri Oct 27 00:54:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop append, simplify (e37a5f7) Message-ID: <20171027005427.73A5A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e37a5f773ae3c5584095d487cd831d5674357670/ghc >--------------------------------------------------------------- commit e37a5f773ae3c5584095d487cd831d5674357670 Author: Andrey Mokhov Date: Mon Aug 7 00:25:42 2017 +0100 Drop append, simplify >--------------------------------------------------------------- e37a5f773ae3c5584095d487cd831d5674357670 src/Expression.hs | 12 +-- src/Hadrian/Expression.hs | 0 src/Rules/Libffi.hs | 2 +- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Cc.hs | 6 +- src/Settings/Builders/Common.hs | 19 +--- src/Settings/Builders/Configure.hs | 16 +-- src/Settings/Builders/DeriveConstants.hs | 4 +- src/Settings/Builders/Ghc.hs | 46 ++++----- src/Settings/Builders/GhcCabal.hs | 50 ++++----- src/Settings/Builders/Haddock.hs | 22 ++-- src/Settings/Builders/Hsc2Hs.hs | 30 +++--- src/Settings/Builders/Ld.hs | 4 +- src/Settings/Builders/Make.hs | 6 +- src/Settings/Default.hs | 168 +++++++++++++++---------------- src/Settings/Flavours/Development.hs | 6 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 6 +- src/Settings/Flavours/Quickest.hs | 8 +- src/Settings/Packages/Cabal.hs | 4 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/Haddock.hs | 2 +- src/Settings/Packages/Rts.hs | 18 ++-- src/Settings/Packages/RunGhc.hs | 2 +- 26 files changed, 206 insertions(+), 235 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 e37a5f773ae3c5584095d487cd831d5674357670 From git at git.haskell.org Fri Oct 27 00:54:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (5dd20f0) Message-ID: <20171027005431.5047F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5dd20f0de9043e46bb2a2bdbed94f86c68e33672/ghc >--------------------------------------------------------------- commit 5dd20f0de9043e46bb2a2bdbed94f86c68e33672 Author: Andrey Mokhov Date: Mon Aug 7 01:19:34 2017 +0100 Minor revision >--------------------------------------------------------------- 5dd20f0de9043e46bb2a2bdbed94f86c68e33672 src/Expression.hs | 17 +++++++---------- src/Rules/Generate.hs | 6 +++--- src/Settings.hs | 28 +++++++++++----------------- src/Settings/Builders/Ghc.hs | 20 +++++++++----------- src/Settings/Builders/GhcCabal.hs | 4 ++-- 5 files changed, 32 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 5dd20f0de9043e46bb2a2bdbed94f86c68e33672 From git at git.haskell.org Fri Oct 27 00:54:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update limitations (acf3623) Message-ID: <20171027005427.AAD103A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acf362369999eacdd9d3c73abc83e0e607c315b5/ghc >--------------------------------------------------------------- commit acf362369999eacdd9d3c73abc83e0e607c315b5 Author: Andrey Mokhov Date: Thu Mar 10 11:57:53 2016 +0000 Update limitations See #219. [skip ci] >--------------------------------------------------------------- acf362369999eacdd9d3c73abc83e0e607c315b5 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 7317384..c61f5c6 100644 --- a/README.md +++ b/README.md @@ -105,6 +105,7 @@ The new build system still lacks many important features: * Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. +* There is no support for installation or binary/source distribution: [#219][install-issue]. Check out [milestones] to see when we hope to resolve the above limitations. @@ -144,6 +145,7 @@ helped me endure and enjoy the project. [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 +[install-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/219 [milestones]: https://github.com/snowleopard/shaking-up-ghc/milestones [comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 [doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 From git at git.haskell.org Fri Oct 27 00:54:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Experiment with a more efficient version of -/- in Settings.Paths (c50799d) Message-ID: <20171027005431.70ACF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c50799d46b53afbde517be8ca1626ef37a626d8f/ghc >--------------------------------------------------------------- commit c50799d46b53afbde517be8ca1626ef37a626d8f Author: Andrey Mokhov Date: Thu Mar 10 12:34:51 2016 +0000 Experiment with a more efficient version of -/- in Settings.Paths See #218. >--------------------------------------------------------------- c50799d46b53afbde517be8ca1626ef37a626d8f src/Settings/Paths.hs | 21 +++++++++++++-------- 1 file changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 62a5c57..678ed92 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -11,20 +11,25 @@ import GHC import Oracles.PackageData import Settings.User +-- A more efficient version of '-/-' which assumes that given FilePaths have +-- already been unified. See #218. TODO: Switch to 'newtype FilePath'. +(~/~) :: FilePath -> FilePath -> FilePath +x ~/~ y = x ++ '/' : y + -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath buildPath context at Context {..} = - buildRootPath -/- contextDirectory context -/- pkgPath package + buildRootPath ~/~ contextDirectory context ~/~ pkgPath package -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath -pkgDataFile context = buildPath context -/- "package-data.mk" +pkgDataFile context = buildPath context ~/~ "package-data.mk" -- | Path to the haddock file of a given 'Context', e.g.: -- ".build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = - buildPath context -/- "doc/html" -/- name -/- name <.> "haddock" + buildPath context ~/~ "doc/html" ~/~ name ~/~ name <.> "haddock" where name = pkgNameString package -- | Path to the library file of a given 'Context', e.g.: @@ -50,25 +55,25 @@ pkgFile :: Context -> String -> String -> Action FilePath pkgFile context prefix suffix = do let path = buildPath context componentId <- pkgData $ ComponentId path - return $ path -/- prefix ++ componentId ++ suffix + return $ path ~/~ prefix ++ componentId ++ suffix -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage1/gmp" +gmpBuildPath = buildRootPath ~/~ "stage1/gmp" -- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath -gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" +gmpBuildInfoPath = pkgPath integerGmp ~/~ "integer-gmp.buildinfo" -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory -- | Path to package database directory of a given 'Stage'. packageDbDirectory :: Stage -> FilePath -packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" +packageDbDirectory Stage0 = buildRootPath ~/~ "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" -- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do componentId <- pkgData . ComponentId $ buildPath context - return $ packageDbDirectory stage -/- componentId <.> "conf" + return $ packageDbDirectory stage ~/~ componentId <.> "conf" From git at git.haskell.org Fri Oct 27 00:54:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move the Config oracle to the library (d3ef19d) Message-ID: <20171027005435.5CE733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3ef19d2fa04f9213bb67409869303d08fa52aee/ghc >--------------------------------------------------------------- commit d3ef19d2fa04f9213bb67409869303d08fa52aee Author: Andrey Mokhov Date: Mon Aug 7 01:58:05 2017 +0100 Move the Config oracle to the library See #347 >--------------------------------------------------------------- d3ef19d2fa04f9213bb67409869303d08fa52aee hadrian.cabal | 6 +++--- src/Expression.hs | 2 +- src/{ => Hadrian}/Oracles/Config.hs | 17 ++++++++++++----- src/Oracles/{Config => }/Flag.hs | 7 ++++--- src/Oracles/{Config => }/Setting.hs | 22 ++++++++++++---------- src/Rules/Data.hs | 2 +- src/Rules/Generate.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Install.hs | 17 ++++++++--------- src/Rules/Oracles.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Selftest.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 4 ++-- src/Rules/Wrappers.hs | 2 +- src/Settings.hs | 2 +- src/Settings/Builders/Common.hs | 8 ++++---- src/Settings/Default.hs | 4 ++-- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Packages/Compiler.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcPrim.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/Rts.hs | 4 ++-- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/Path.hs | 2 +- src/Util.hs | 2 +- src/Way.hs | 2 +- 28 files changed, 71 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 d3ef19d2fa04f9213bb67409869303d08fa52aee From git at git.haskell.org Fri Oct 27 00:54:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of git://github.com/snowleopard/shaking-up-ghc (950ac6b) Message-ID: <20171027005435.879B33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/950ac6b7dc479aebfc367db3c459130cb71668e0/ghc >--------------------------------------------------------------- commit 950ac6b7dc479aebfc367db3c459130cb71668e0 Merge: c50799d acf3623 Author: Andrey Mokhov Date: Thu Mar 10 12:37:03 2016 +0000 Merge branch 'master' of git://github.com/snowleopard/shaking-up-ghc >--------------------------------------------------------------- 950ac6b7dc479aebfc367db3c459130cb71668e0 README.md | 2 ++ 1 file changed, 2 insertions(+) From git at git.haskell.org Fri Oct 27 00:54:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -threaded to ghc options. (bf60359) Message-ID: <20171027005439.CA79C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf60359360e91bf41773efbd7facdfda3b399c7c/ghc >--------------------------------------------------------------- commit bf60359360e91bf41773efbd7facdfda3b399c7c Author: Andrey Mokhov Date: Mon Apr 11 00:27:21 2016 +0100 Add -threaded to ghc options. >--------------------------------------------------------------- bf60359360e91bf41773efbd7facdfda3b399c7c build.bat | 1 + build.sh | 1 + shaking-up-ghc.cabal | 5 ++++- 3 files changed, 6 insertions(+), 1 deletion(-) diff --git a/build.bat b/build.bat index 465d957..2f6d4cd 100644 --- a/build.bat +++ b/build.bat @@ -6,6 +6,7 @@ -fno-warn-name-shadowing ^ -XRecordWildCards ^ src/Main.hs ^ + -threaded ^ -isrc ^ -rtsopts ^ -with-rtsopts=-I0 ^ diff --git a/build.sh b/build.sh index 7c070e9..95de2e6 100755 --- a/build.sh +++ b/build.sh @@ -40,6 +40,7 @@ ghc \ -i"$root/src" \ -rtsopts \ -with-rtsopts=-I0 \ + -threaded \ -outputdir="$root/.shake" \ -j -O \ -o "$root/.shake/build" diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index fc0744d..8ef820f 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -127,4 +127,7 @@ executable ghc-shake , shake == 0.15.* , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* - ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 + ghc-options: -Wall + -fno-warn-name-shadowing + -rtsopts -with-rtsopts=-I0 + -threaded From git at git.haskell.org Fri Oct 27 00:54:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace Config oracle with generic key-value text file oracle (da27a1f) Message-ID: <20171027005443.9637B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da27a1fec4ba6565faca24362f0007aa477105f0/ghc >--------------------------------------------------------------- commit da27a1fec4ba6565faca24362f0007aa477105f0 Author: Andrey Mokhov Date: Wed Aug 9 23:39:23 2017 +0100 Replace Config oracle with generic key-value text file oracle See #347 >--------------------------------------------------------------- da27a1fec4ba6565faca24362f0007aa477105f0 hadrian.cabal | 2 +- src/Hadrian/Oracles/Config.hs | 34 --------------------------------- src/Hadrian/Oracles/KeyValue.hs | 42 +++++++++++++++++++++++++++++++++++++++++ src/Oracles/Flag.hs | 4 ++-- src/Oracles/ModuleFiles.hs | 6 +++--- src/Oracles/PackageData.hs | 26 ++++++------------------- src/Oracles/Setting.hs | 6 +++--- src/Rules/Oracles.hs | 6 ++---- src/Settings.hs | 4 ++-- 9 files changed, 61 insertions(+), 69 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 da27a1fec4ba6565faca24362f0007aa477105f0 From git at git.haskell.org Fri Oct 27 00:54:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify oracles (acf66a3) Message-ID: <20171027005439.BC5093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acf66a3c7bb4834f2a9b631eb5492dfc92149026/ghc >--------------------------------------------------------------- commit acf66a3c7bb4834f2a9b631eb5492dfc92149026 Author: Andrey Mokhov Date: Tue Aug 8 22:53:25 2017 +0100 Simplify oracles >--------------------------------------------------------------- acf66a3c7bb4834f2a9b631eb5492dfc92149026 src/Hadrian/Oracles/ArgsHash.hs | 6 +++--- src/Hadrian/Oracles/Config.hs | 6 +++--- src/Oracles/Dependencies.hs | 18 +++++------------- 3 files changed, 11 insertions(+), 19 deletions(-) diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index e07fc3f..8ac2c38 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -35,16 +35,16 @@ trackArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action () trackArgsHash t = do let hashedInputs = [ show $ hash (inputs t) ] hashedTarget = target (context t) (builder t) hashedInputs (outputs t) - void (askOracle $ ArgsHashKey hashedTarget :: Action Int) + void (askOracle $ ArgsHash hashedTarget :: Action Int) -newtype ArgsHashKey c b = ArgsHashKey (Target c b) +newtype ArgsHash c b = ArgsHash (Target c b) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -- | This oracle stores per-target argument list hashes in the Shake database, -- allowing the user to track them between builds using 'trackArgsHash' queries. argsHashOracle :: (ShakeValue c, ShakeValue b) => TrackArgument c b -> Args c b -> Rules () argsHashOracle trackArgument args = void $ - addOracle $ \(ArgsHashKey target) -> do + addOracle $ \(ArgsHash target) -> do argList <- interpret target args let trackedArgList = filter (trackArgument target) argList return $ hash trackedArgList diff --git a/src/Hadrian/Oracles/Config.hs b/src/Hadrian/Oracles/Config.hs index 0b12616..1263f1a 100644 --- a/src/Hadrian/Oracles/Config.hs +++ b/src/Hadrian/Oracles/Config.hs @@ -10,7 +10,7 @@ import Development.Shake.Config import Hadrian.Utilities -newtype ConfigKey = ConfigKey String +newtype Config = Config String deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -- | Lookup a configuration setting raising an error if the key is not found. @@ -21,7 +21,7 @@ unsafeAskConfig key = (fromMaybe $ error msg) <$> askConfig key -- | Lookup a configuration setting. askConfig :: String -> Action (Maybe String) -askConfig = askOracle . ConfigKey +askConfig = askOracle . Config -- | This oracle reads and parses a configuration file consisting of key-value -- pairs @key = value@ and answers 'askConfig' queries tracking the results. @@ -31,4 +31,4 @@ configOracle configFile = void $ do need [configFile] putLoud $ "Reading " ++ configFile ++ "..." liftIO $ readConfigFile configFile - addOracle $ \(ConfigKey key) -> Map.lookup key <$> cfg () + addOracle $ \(Config key) -> Map.lookup key <$> cfg () diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 04ebbfd..6ae0b0d 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -15,7 +15,7 @@ import Settings import Settings.Builders.GhcCabal import Settings.Path -newtype ObjDepsKey = ObjDepsKey (FilePath, FilePath) +newtype Dependency = Dependency (FilePath, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -- | 'Action' @fileDependencies context file@ looks up dependencies of a @file@ @@ -26,15 +26,12 @@ newtype ObjDepsKey = ObjDepsKey (FilePath, FilePath) fileDependencies :: Context -> FilePath -> Action (FilePath, [FilePath]) fileDependencies context obj = do let path = buildPath context -/- ".dependencies" - deps <- askOracle $ ObjDepsKey (path, obj) + deps <- askOracle $ Dependency (path, obj) case deps of Nothing -> error $ "No dependencies found for file " ++ obj Just [] -> error $ "No source file found for file " ++ obj Just (source : files) -> return (source, files) -newtype PkgDepsKey = PkgDepsKey String - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -- | Given a 'Context' this 'Action' looks up its package dependencies in -- 'Settings.Paths.packageDependencies' using 'packageDependenciesOracle', and -- wraps found dependencies in appropriate contexts. The only subtlety here is @@ -45,7 +42,7 @@ contextDependencies :: Context -> Action [Context] contextDependencies context at Context {..} = do let pkgContext = \pkg -> Context (min stage Stage1) pkg way unpack = fromMaybe . error $ "No dependencies for " ++ show context - deps <- unpack <$> askOracle (PkgDepsKey $ pkgNameString package) + deps <- unpack <$> askOracle (Dependency (packageDependencies, pkgNameString package)) pkgs <- sort <$> interpretInContext (pkgContext package) getPackages return . map pkgContext $ intersectOrd (compare . pkgNameString) pkgs deps @@ -74,16 +71,11 @@ needLibrary cs = need =<< concatMapM libraryTargets cs -- | Oracles for the package dependencies and 'path/dist/.dependencies' files. dependenciesOracles :: Rules () dependenciesOracles = do - deps <- newCache readDependencies - void $ addOracle $ \(ObjDepsKey (file, obj)) -> Map.lookup obj <$> deps file - - pkgDeps <- newCache $ \_ -> readDependencies packageDependencies - void $ addOracle $ \(PkgDepsKey pkg) -> Map.lookup pkg <$> pkgDeps () - where - readDependencies file = do + deps <- newCache $ \file -> do putLoud $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return $ Map.fromList [ (key, values) | (key:values) <- contents ] + void $ addOracle $ \(Dependency (file, key)) -> Map.lookup key <$> deps file -- | Topological sort of packages according to their dependencies. -- HACK (izgzhen): See https://github.com/snowleopard/hadrian/issues/344 for details From git at git.haskell.org Fri Oct 27 00:54:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install alex and happy using cabal to fix Travis failure (67e3104) Message-ID: <20171027005443.ABA423A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/67e31045fb749fdcb4cb67248931e5ce403e012b/ghc >--------------------------------------------------------------- commit 67e31045fb749fdcb4cb67248931e5ce403e012b Author: Andrey Mokhov Date: Mon Apr 11 00:43:59 2016 +0100 Install alex and happy using cabal to fix Travis failure >--------------------------------------------------------------- 67e31045fb749fdcb4cb67248931e5ce403e012b .travis.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 9547914..21bf769 100644 --- a/.travis.yml +++ b/.travis.yml @@ -8,8 +8,6 @@ matrix: apt: packages: - ghc-7.10.3 - - alex-3.1.4 - - happy-1.19.5 - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc @@ -19,6 +17,7 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH - cabal update + - cabal install alex happy - os: osx env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg From git at git.haskell.org Fri Oct 27 00:54:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass conf-cc-args-stageN to Gcc builder. (0e27bf4) Message-ID: <20171027005447.5648D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0e27bf4172aa629796af44dfe3642967eace1dba/ghc >--------------------------------------------------------------- commit 0e27bf4172aa629796af44dfe3642967eace1dba Author: Andrey Mokhov Date: Mon Apr 11 23:18:19 2016 +0100 Pass conf-cc-args-stageN to Gcc builder. See #221. >--------------------------------------------------------------- 0e27bf4172aa629796af44dfe3642967eace1dba src/Settings/Builders/Gcc.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Settings/Builders/Gcc.hs b/src/Settings/Builders/Gcc.hs index 4902ea3..7c237da 100644 --- a/src/Settings/Builders/Gcc.hs +++ b/src/Settings/Builders/Gcc.hs @@ -2,6 +2,7 @@ module Settings.Builders.Gcc (gccBuilderArgs, gccMBuilderArgs) where import Development.Shake.FilePath import Expression +import Oracles.Config.Setting import Oracles.PackageData import Predicates (stagedBuilder) import Settings @@ -30,4 +31,5 @@ gccMBuilderArgs = stagedBuilder GccM ? do commonGccArgs :: Args commonGccArgs = mconcat [ append =<< getPkgDataList CcArgs + , append =<< getSettingList . ConfCcArgs =<< getStage , cIncludeArgs ] From git at git.haskell.org Fri Oct 27 00:54:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (72bf4b1) Message-ID: <20171027005447.5AA5F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72bf4b180dffa10fb650046b571b756b5262097a/ghc >--------------------------------------------------------------- commit 72bf4b180dffa10fb650046b571b756b5262097a Author: Andrey Mokhov Date: Sat Aug 12 21:51:16 2017 +0100 Minor revision >--------------------------------------------------------------- 72bf4b180dffa10fb650046b571b756b5262097a src/Base.hs | 29 ++--------------------------- src/Hadrian/Utilities.hs | 23 ++++++++++++++++++++++- src/Rules/Library.hs | 15 +++++++-------- src/Rules/Register.hs | 2 +- 4 files changed, 32 insertions(+), 37 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 6ae3ead..df14d3d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -17,15 +17,13 @@ module Base ( configPath, configFile, sourcePath, -- * Miscellaneous utilities - unifyPath, quote, (-/-), matchVersionedFilePath, matchGhcVersionedFilePath, - putColoured + unifyPath, quote, (-/-), putColoured ) where import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader import Data.Bifunctor -import Data.Char import Data.Function import Data.List.Extra import Data.Maybe @@ -58,30 +56,7 @@ configFile = configPath -/- "system.config" sourcePath :: FilePath sourcePath = hadrianPath -/- "src" --- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the --- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string --- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: --- ---- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'False'@ ---- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ ---- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar-" "a" "foo/bar-0.1.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False'@ -matchVersionedFilePath :: String -> String -> FilePath -> Bool -matchVersionedFilePath prefix suffix filePath = - case stripPrefix prefix filePath >>= stripSuffix suffix of - Nothing -> False - Just version -> all (\c -> isDigit c || c == '-' || c == '.') version - -matchGhcVersionedFilePath :: String -> String -> FilePath -> Bool -matchGhcVersionedFilePath prefix ext filePath = - case stripPrefix prefix filePath >>= stripSuffix ext of - Nothing -> False - Just _ -> True - --- | A more colourful version of Shake's putNormal. +-- | A more colourful version of Shake's 'putNormal'. putColoured :: ColorIntensity -> Color -> String -> Action () putColoured intensity colour msg = do c <- useColour diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 56b53ce..f26a444 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -7,9 +7,11 @@ module Hadrian.Utilities ( quote, yesNo, -- * FilePath manipulation - unifyPath, (-/-) + unifyPath, (-/-), matchVersionedFilePath ) where +import Data.Char +import Data.List.Extra import Development.Shake.FilePath -- | Extract a value from a singleton list, or terminate with an error message @@ -79,3 +81,22 @@ a -/- b | otherwise = a ++ '/' : b infixr 6 -/- + +-- | Given a @prefix@ and a @suffix@ check whether a 'FilePath' matches the +-- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string +-- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: +-- +-- @ +-- 'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'False' +-- 'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False' +-- 'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar-" "a" "foo/bar-0.1.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False' +-- @ +matchVersionedFilePath :: String -> String -> FilePath -> Bool +matchVersionedFilePath prefix suffix filePath = + case stripPrefix prefix filePath >>= stripSuffix suffix of + Nothing -> False + Just version -> all (\c -> isDigit c || c == '-' || c == '.') version diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index ba3138a..7b32f55 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -3,6 +3,7 @@ module Rules.Library ( ) where import Data.Char +import Hadrian.Utilities import qualified System.Directory as IO import Base @@ -38,24 +39,22 @@ libraryObjects context at Context{..} = do buildDynamicLib :: Context -> Rules () buildDynamicLib context at Context{..} = do - let path = buildPath context - libPrefix = path -/- "libHS" ++ pkgNameString package + let libPrefix = buildPath context -/- "libHS" ++ pkgNameString package -- OS X - matchGhcVersionedFilePath libPrefix "dylib" ?> buildDynamicLibUnix + libPrefix ++ "*.dylib" %> buildDynamicLibUnix -- Linux - matchGhcVersionedFilePath libPrefix "so" ?> buildDynamicLibUnix + libPrefix ++ "*.so" %> buildDynamicLibUnix -- TODO: Windows where - buildDynamicLibUnix so = do + buildDynamicLibUnix lib = do deps <- contextDependencies context need =<< mapM pkgLibraryFile deps objs <- libraryObjects context - build $ target context (Ghc LinkHs stage) objs [so] + build $ target context (Ghc LinkHs stage) objs [lib] buildPackageLibrary :: Context -> Rules () buildPackageLibrary context at Context {..} = do - let path = buildPath context - libPrefix = path -/- "libHS" ++ pkgNameString package + let libPrefix = buildPath context -/- "libHS" ++ pkgNameString package matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do objs <- libraryObjects context asuf <- libsuf way diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 1f5f64a..7ec8bcd 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -16,7 +16,7 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do let confIn = pkgInplaceConfig context dir = inplacePackageDbDirectory stage - matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do + dir -/- pkgNameString package ++ "*.conf" %> \conf -> do need [confIn] buildWithResources rs $ target context (GhcPkg Update stage) [confIn] [conf] From git at git.haskell.org Fri Oct 27 00:54:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor tweaks (5b49f64) Message-ID: <20171027005450.F298C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b49f649a2f4b9a4fcb0ea6a46f5a40480ee0375/ghc >--------------------------------------------------------------- commit 5b49f649a2f4b9a4fcb0ea6a46f5a40480ee0375 Author: Andrey Mokhov Date: Tue Apr 12 01:04:31 2016 +0100 Minor tweaks >--------------------------------------------------------------- 5b49f649a2f4b9a4fcb0ea6a46f5a40480ee0375 src/Predicates.hs | 4 +--- src/Settings/Builders/Common.hs | 6 +++--- src/Settings/Builders/GhcCabal.hs | 2 +- 3 files changed, 5 insertions(+), 7 deletions(-) diff --git a/src/Predicates.hs b/src/Predicates.hs index c0f6095..1c5ce38 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -21,9 +21,7 @@ builder b = (b ==) <$> getBuilder -- | Is a certain builder used in the current stage? stagedBuilder :: (Stage -> Builder) -> Predicate -stagedBuilder stageBuilder = do - s <- getStage - builder (stageBuilder s) +stagedBuilder stageBuilder = builder . stageBuilder =<< getStage -- | Are we building with GCC? builderGcc :: Predicate diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 4ecf1d4..1f1d33b 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -51,10 +51,10 @@ argSetting :: Setting -> Args argSetting = argM . setting argSettingList :: SettingList -> Args -argSettingList = (append =<<) . lift . settingList +argSettingList = (append =<<) . getSettingList argStagedSettingList :: (Stage -> SettingList) -> Args -argStagedSettingList ss = (argSettingList . ss) =<< getStage +argStagedSettingList ss = argSettingList . ss =<< getStage argStagedBuilderPath :: (Stage -> Builder) -> Args -argStagedBuilderPath sb = (argM . builderPath . sb) =<< getStage +argStagedBuilderPath sb = argM . builderPath . sb =<< getStage diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index be89546..24b7d7d 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -131,7 +131,7 @@ with b = specified b ? do append [withBuilderKey b ++ top -/- path] withStaged :: (Stage -> Builder) -> Args -withStaged sb = (with . sb) =<< getStage +withStaged sb = with . sb =<< getStage needDll0 :: Stage -> Package -> Action Bool needDll0 stage pkg = do From git at git.haskell.org Fri Oct 27 00:54:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix package registration (78878b7) Message-ID: <20171027005451.24C773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/78878b77fecd6a2e277cfcee5d2bcb3a3832e385/ghc >--------------------------------------------------------------- commit 78878b77fecd6a2e277cfcee5d2bcb3a3832e385 Author: Andrey Mokhov Date: Sat Aug 12 22:27:54 2017 +0100 Fix package registration >--------------------------------------------------------------- 78878b77fecd6a2e277cfcee5d2bcb3a3832e385 src/Rules/Register.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 7ec8bcd..6f4f5b4 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -1,5 +1,7 @@ module Rules.Register (registerPackage) where +import Hadrian.Utilities + import Base import Context import Expression @@ -16,7 +18,7 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do let confIn = pkgInplaceConfig context dir = inplacePackageDbDirectory stage - dir -/- pkgNameString package ++ "*.conf" %> \conf -> do + matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do need [confIn] buildWithResources rs $ target context (GhcPkg Update stage) [confIn] [conf] From git at git.haskell.org Fri Oct 27 00:54:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't add exe extension to builder paths on Windows. (e23dab7) Message-ID: <20171027005455.39E483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e23dab7cab22ecd9ba7f69ba735c43878a7b6c3a/ghc >--------------------------------------------------------------- commit e23dab7cab22ecd9ba7f69ba735c43878a7b6c3a Author: Andrey Mokhov Date: Tue Apr 12 18:45:50 2016 +0100 Don't add exe extension to builder paths on Windows. See #221, #222. >--------------------------------------------------------------- e23dab7cab22ecd9ba7f69ba735c43878a7b6c3a src/Builder.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index e8011e7..a0cc093 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -133,9 +133,7 @@ builderPath builder = case builderProvenance builder of then return "" else putError $ "Builder '" ++ builderKey ++ "' is not specified in" ++ " system.config file. Cannot proceed without it." - else do - path' <- lookupInPath path - fixAbsolutePathOnWindows $ path' -<.> exe + else fixAbsolutePathOnWindows =<< lookupInPath path getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath From git at git.haskell.org Fri Oct 27 00:54:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move putColoured to the library (a395dd7) Message-ID: <20171027005455.674923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a395dd71438e58c29448f5f34cf4bb17e9fcbe5d/ghc >--------------------------------------------------------------- commit a395dd71438e58c29448f5f34cf4bb17e9fcbe5d Author: Andrey Mokhov Date: Sun Aug 13 00:49:18 2017 +0100 Move putColoured to the library See #347 >--------------------------------------------------------------- a395dd71438e58c29448f5f34cf4bb17e9fcbe5d src/Base.hs | 27 +-------------------------- src/CmdLineFlag.hs | 16 ++++++++-------- src/Hadrian/Utilities.hs | 23 ++++++++++++++++++++++- src/UserSettings.hs | 6 ++++-- 4 files changed, 35 insertions(+), 37 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index df14d3d..f4f4c4b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -17,7 +17,7 @@ module Base ( configPath, configFile, sourcePath, -- * Miscellaneous utilities - unifyPath, quote, (-/-), putColoured + unifyPath, quote, (-/-) ) where import Control.Applicative @@ -32,11 +32,6 @@ import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import Hadrian.Utilities -import System.Console.ANSI -import System.IO -import System.Info - -import CmdLineFlag -- TODO: reexport Stage, etc.? @@ -55,23 +50,3 @@ configFile = configPath -/- "system.config" -- sourcePath -/- "Base.hs". We use this to `need` some of the source files. sourcePath :: FilePath sourcePath = hadrianPath -/- "src" - --- | A more colourful version of Shake's 'putNormal'. -putColoured :: ColorIntensity -> Color -> String -> Action () -putColoured intensity colour msg = do - c <- useColour - when c . liftIO $ setSGR [SetColor Foreground intensity colour] - putNormal msg - when c . liftIO $ do - setSGR [] - hFlush stdout - -useColour :: Action Bool -useColour = case cmdProgressColour of - Never -> return False - Always -> return True - Auto -> do - supported <- liftIO $ hSupportsANSI stdout - -- An ugly hack to always try to print colours when on mingw and cygwin. - let windows = any (`isPrefixOf` os) ["mingw", "cygwin"] - return $ windows || supported diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 961a033..ff35f1f 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,11 +1,12 @@ module CmdLineFlag ( putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, - cmdProgressColour, ProgressColour (..), cmdProgressInfo, ProgressInfo (..), - cmdSkipConfigure, cmdSplitObjects + cmdProgressColour, cmdProgressInfo, ProgressInfo (..), cmdSkipConfigure, + cmdSplitObjects ) where import Data.IORef import Data.List.Extra +import Hadrian.Utilities import System.Console.GetOpt import System.IO.Unsafe @@ -16,14 +17,13 @@ data Untracked = Untracked { buildHaddock :: Bool , flavour :: Maybe String , integerSimple :: Bool - , progressColour :: ProgressColour + , progressColour :: UseColour , progressInfo :: ProgressInfo , skipConfigure :: Bool , splitObjects :: Bool } deriving (Eq, Show) -data ProgressColour = Never | Auto | Always deriving (Eq, Show) -data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) +data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked @@ -49,12 +49,12 @@ readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) readProgressColour ms = maybe (Left "Cannot parse progress-colour") (Right . set) (go =<< lower <$> ms) where - go :: String -> Maybe ProgressColour + go :: String -> Maybe UseColour go "never" = Just Never go "auto" = Just Auto go "always" = Just Always go _ = Nothing - set :: ProgressColour -> Untracked -> Untracked + set :: UseColour -> Untracked -> Untracked set flag flags = flags { progressColour = flag } readProgressInfo :: Maybe String -> Either String (Untracked -> Untracked) @@ -115,7 +115,7 @@ cmdFlavour = flavour getCmdLineFlags cmdIntegerSimple :: Bool cmdIntegerSimple = integerSimple getCmdLineFlags -cmdProgressColour :: ProgressColour +cmdProgressColour :: UseColour cmdProgressColour = progressColour getCmdLineFlags cmdProgressInfo :: ProgressInfo diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index f26a444..bf9a9ac 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -7,12 +7,20 @@ module Hadrian.Utilities ( quote, yesNo, -- * FilePath manipulation - unifyPath, (-/-), matchVersionedFilePath + unifyPath, (-/-), matchVersionedFilePath, + + -- * Miscellaneous + UseColour (..), putColoured ) where +import Control.Monad import Data.Char import Data.List.Extra +import Development.Shake import Development.Shake.FilePath +import System.Console.ANSI +import System.Info.Extra +import System.IO -- | Extract a value from a singleton list, or terminate with an error message -- if the list does not contain exactly one value. @@ -100,3 +108,16 @@ matchVersionedFilePath prefix suffix filePath = case stripPrefix prefix filePath >>= stripSuffix suffix of Nothing -> False Just version -> all (\c -> isDigit c || c == '-' || c == '.') version + +data UseColour = Never | Auto | Always deriving (Eq, Show) + +-- | A more colourful version of Shake's 'putNormal'. +putColoured :: UseColour -> ColorIntensity -> Color -> String -> Action () +putColoured useColour intensity colour msg = do + supported <- liftIO $ hSupportsANSI stdout + let c Never = False + c Auto = supported || isWindows -- Colours do work on Windows + c Always = True + when (c useColour) . liftIO $ setSGR [SetColor Foreground intensity colour] + putNormal msg + when (c useColour) . liftIO $ setSGR [] >> hFlush stdout diff --git a/src/UserSettings.hs b/src/UserSettings.hs index e2aa674..debd7cd 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -7,9 +7,11 @@ module UserSettings ( putBuild, putSuccess, defaultDestDir, defaultStage1Only ) where +import Hadrian.Utilities import System.Console.ANSI import Base +import CmdLineFlag import Flavour import Expression @@ -37,11 +39,11 @@ verboseCommands = return False -- | Customise build progress messages (e.g. executing a build command). putBuild :: String -> Action () -putBuild = putColoured Dull Magenta +putBuild = putColoured cmdProgressColour Dull Magenta -- | Customise build success messages (e.g. a package is built successfully). putSuccess :: String -> Action () -putSuccess = putColoured Dull Green +putSuccess = putColoured cmdProgressColour Dull Green -- | Path to the GHC install destination. It is empty by default, which -- corresponds to the root of the file system. You can replace it by a specific From git at git.haskell.org Fri Oct 27 00:54:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Gcc(M) to Cc(M). (96dec14) Message-ID: <20171027005458.C3FF73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/96dec1490c1a95e7e5a4c58f736e617773ff9d32/ghc >--------------------------------------------------------------- commit 96dec1490c1a95e7e5a4c58f736e617773ff9d32 Author: Andrey Mokhov Date: Thu Apr 14 01:41:02 2016 +0100 Rename Gcc(M) to Cc(M). See #222, #223. >--------------------------------------------------------------- 96dec1490c1a95e7e5a4c58f736e617773ff9d32 cfg/system.config.in | 4 +-- shaking-up-ghc.cabal | 2 +- src/Builder.hs | 62 ++++++++++++++++---------------- src/Predicates.hs | 6 ++-- src/Rules/Compile.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 +-- src/Settings/Args.hs | 6 ++-- src/Settings/Builders/{Gcc.hs => Cc.hs} | 22 ++++++------ src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 8 ++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Directory.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 4 +-- src/Settings/Packages/Rts.hs | 4 +-- 16 files changed, 67 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 96dec1490c1a95e7e5a4c58f736e617773ff9d32 From git at git.haskell.org Fri Oct 27 00:54:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:54:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export basic data type definitions from Base (4f0b5a1) Message-ID: <20171027005458.E676C3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4f0b5a138391303ea7be0cd9bab49076ebc9d6a9/ghc >--------------------------------------------------------------- commit 4f0b5a138391303ea7be0cd9bab49076ebc9d6a9 Author: Andrey Mokhov Date: Sun Aug 13 03:20:46 2017 +0100 Re-export basic data type definitions from Base >--------------------------------------------------------------- 4f0b5a138391303ea7be0cd9bab49076ebc9d6a9 src/Base.hs | 29 +++++-- src/Builder.hs | 43 +-------- src/Context.hs | 10 ++- src/Expression.hs | 54 ++++++++---- src/Oracles/Dependencies.hs | 1 - src/Oracles/ModuleFiles.hs | 2 - src/Oracles/Setting.hs | 39 ++++++++- src/Package.hs | 41 ++++----- src/Rules/Cabal.hs | 1 - src/Rules/Clean.hs | 1 - src/Rules/Compile.hs | 2 - src/Rules/Configure.hs | 3 - src/Rules/Dependencies.hs | 3 +- src/Rules/Generate.hs | 2 - src/Rules/Gmp.hs | 5 -- src/Rules/Library.hs | 4 +- src/Rules/Perl.hs | 1 - src/Rules/Register.hs | 3 - src/Rules/Selftest.hs | 4 +- src/Rules/SourceDist.hs | 1 - src/Rules/Test.hs | 3 - src/Settings/Builders/Common.hs | 2 + src/Settings/Packages/Rts.hs | 2 - src/Settings/Path.hs | 188 ++++++++++++++++++++-------------------- src/Stage.hs | 10 +-- src/Target.hs | 2 +- src/UserSettings.hs | 2 +- src/Util.hs | 1 - src/Way.hs | 51 ++++------- 29 files changed, 252 insertions(+), 258 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 4f0b5a138391303ea7be0cd9bab49076ebc9d6a9 From git at git.haskell.org Fri Oct 27 00:55:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CompilerMode to Cc and Ghc builders. (897ba61) Message-ID: <20171027005502.84DB93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/897ba61daec64836092aa46fe097743013cd7bc5/ghc >--------------------------------------------------------------- commit 897ba61daec64836092aa46fe097743013cd7bc5 Author: Andrey Mokhov Date: Fri Apr 15 02:23:37 2016 +0100 Add CompilerMode to Cc and Ghc builders. See #223. >--------------------------------------------------------------- 897ba61daec64836092aa46fe097743013cd7bc5 src/Builder.hs | 80 ++++++++++++++++---------------- src/Predicates.hs | 13 ++++-- src/Rules/Compile.hs | 10 ++-- src/Rules/Dependencies.hs | 5 +- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 +- src/Rules/Program.hs | 3 +- src/Rules/Test.hs | 4 +- src/Settings/Args.hs | 1 - src/Settings/Builders/Cc.hs | 38 +++++++-------- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/Ghc.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 10 ++-- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Directory.hs | 4 +- 15 files changed, 95 insertions(+), 87 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 897ba61daec64836092aa46fe097743013cd7bc5 From git at git.haskell.org Fri Oct 27 00:55:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge Rules.Oracles into Rules (709ffb7) Message-ID: <20171027005502.B13DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/709ffb71d43a55e93a82577bd79b37d169b9754a/ghc >--------------------------------------------------------------- commit 709ffb71d43a55e93a82577bd79b37d169b9754a Author: Andrey Mokhov Date: Sun Aug 13 16:34:01 2017 +0100 Merge Rules.Oracles into Rules >--------------------------------------------------------------- 709ffb71d43a55e93a82577bd79b37d169b9754a hadrian.cabal | 1 - src/Base.hs | 0 src/Main.hs | 9 ++++----- src/Rules.hs | 30 ++++++++++++++++++++++++------ src/Rules/Oracles.hs | 21 --------------------- 5 files changed, 28 insertions(+), 33 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index c39df50..c964f3b 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -52,7 +52,6 @@ executable hadrian , Rules.Install , Rules.Libffi , Rules.Library - , Rules.Oracles , Rules.Perl , Rules.Program , Rules.Register diff --git a/src/Main.hs b/src/Main.hs index 0f65ecf..6843140 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -7,7 +7,6 @@ import qualified Environment import qualified Rules import qualified Rules.Clean import qualified Rules.Install -import qualified Rules.Oracles import qualified Rules.SourceDist import qualified Rules.Selftest import qualified Rules.Test @@ -23,14 +22,14 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do where rules :: Rules () rules = do + Rules.buildRules Rules.Clean.cleanRules - Rules.Oracles.oracleRules - Rules.SourceDist.sourceDistRules + Rules.Install.installRules + Rules.oracleRules Rules.Selftest.selftestRules + Rules.SourceDist.sourceDistRules Rules.Test.testRules - Rules.buildRules Rules.topLevelTargets - Rules.Install.installRules options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest diff --git a/src/Rules.hs b/src/Rules.hs index 359d3e9..335c4c3 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,10 +1,19 @@ -module Rules (topLevelTargets, packageTargets, buildRules) where +module Rules ( + buildRules, oracleRules, packageTargets, topLevelTargets + ) where + +import qualified Hadrian.Oracles.ArgsHash +import qualified Hadrian.Oracles.DirectoryContents +import qualified Hadrian.Oracles.KeyValue +import qualified Hadrian.Oracles.Path import Base import Context import Expression import Flavour import GHC +import qualified Oracles.Dependencies +import qualified Oracles.ModuleFiles import qualified Rules.Compile import qualified Rules.Data import qualified Rules.Dependencies @@ -18,9 +27,9 @@ import qualified Rules.Library import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register -import Oracles.Dependencies import Settings import Settings.Path +import Target allStages :: [Stage] allStages = [minBound ..] @@ -52,7 +61,7 @@ packageTargets stage pkg = do ways <- interpretInContext context getLibraryWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour - more <- libraryTargets context + more <- Oracles.Dependencies.libraryTargets context return $ [ pkgSetupConfigFile context | nonCabalContext context ] ++ [ pkgHaddockFile context | docs && stage == Stage1 ] ++ libs ++ more @@ -102,8 +111,17 @@ buildRules = do packageRules Rules.Perl.perlScriptRules +oracleRules :: Rules () +oracleRules = do + Hadrian.Oracles.ArgsHash.argsHashOracle trackArgument getArgs + Hadrian.Oracles.DirectoryContents.directoryContentsOracle + Hadrian.Oracles.KeyValue.keyValueOracle + Hadrian.Oracles.Path.pathOracle + Oracles.Dependencies.dependenciesOracles + Oracles.ModuleFiles.moduleFilesOracle + programsStage1Only :: [Package] programsStage1Only = - [ deriveConstants, genprimopcode, hp2ps, runGhc - , ghcCabal, hpc, dllSplit, ghcPkg, hsc2hs - , genapply, ghc ] + [ deriveConstants, genprimopcode, hp2ps, runGhc + , ghcCabal, hpc, dllSplit, ghcPkg, hsc2hs + , genapply, ghc ] diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs deleted file mode 100644 index 5f1f55e..0000000 --- a/src/Rules/Oracles.hs +++ /dev/null @@ -1,21 +0,0 @@ -module Rules.Oracles (oracleRules) where - -import qualified Hadrian.Oracles.ArgsHash -import qualified Hadrian.Oracles.DirectoryContents -import qualified Hadrian.Oracles.KeyValue -import qualified Hadrian.Oracles.Path - -import Base -import qualified Oracles.Dependencies -import qualified Oracles.ModuleFiles -import Target -import Settings - -oracleRules :: Rules () -oracleRules = do - Hadrian.Oracles.ArgsHash.argsHashOracle trackArgument getArgs - Hadrian.Oracles.DirectoryContents.directoryContentsOracle - Hadrian.Oracles.KeyValue.keyValueOracle - Hadrian.Oracles.Path.pathOracle - Oracles.Dependencies.dependenciesOracles - Oracles.ModuleFiles.moduleFilesOracle From git at git.haskell.org Fri Oct 27 00:55:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Extend KeyValue oracle to handle lists of values (1a0a80b) Message-ID: <20171027005506.5C8A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a0a80ba27c1ab1a8fcf388c6e286705d860f6ab/ghc >--------------------------------------------------------------- commit 1a0a80ba27c1ab1a8fcf388c6e286705d860f6ab Author: Andrey Mokhov Date: Sun Aug 13 18:26:45 2017 +0100 Extend KeyValue oracle to handle lists of values >--------------------------------------------------------------- 1a0a80ba27c1ab1a8fcf388c6e286705d860f6ab src/Hadrian/Oracles/KeyValue.hs | 46 +++++++++++++++++++++++++++++++---------- src/Oracles/Dependencies.hs | 21 ++++--------------- src/Rules.hs | 1 - 3 files changed, 39 insertions(+), 29 deletions(-) diff --git a/src/Hadrian/Oracles/KeyValue.hs b/src/Hadrian/Oracles/KeyValue.hs index b58cfda..5155e3e 100644 --- a/src/Hadrian/Oracles/KeyValue.hs +++ b/src/Hadrian/Oracles/KeyValue.hs @@ -1,6 +1,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Hadrian.Oracles.KeyValue ( - lookupValue, lookupValueOrEmpty, lookupValueOrError, keyValueOracle + lookupValue, lookupValueOrEmpty, lookupValueOrError, + lookupValues, lookupValuesOrEmpty, lookupValuesOrError, keyValueOracle ) where import Control.Monad @@ -15,28 +16,51 @@ import Hadrian.Utilities newtype KeyValue = KeyValue (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- | Lookup a value in a key-value text file, tracking the result. +newtype KeyValues = KeyValues (FilePath, String) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Lookup a value in a text file, tracking the result. Each line of the file +-- is expected to have @key = value@ format. lookupValue :: FilePath -> String -> Action (Maybe String) lookupValue file key = askOracle $ KeyValue (file, key) --- | Lookup a value in a key-value text file, tracking the result. Return the --- empty string if the key is not found. +-- | Like 'lookupValue' but returns the empty string if the key is not found. lookupValueOrEmpty :: FilePath -> String -> Action String -lookupValueOrEmpty file key = fromMaybe "" <$> askOracle (KeyValue (file, key)) +lookupValueOrEmpty file key = fromMaybe "" <$> lookupValue file key --- | Lookup a value in a key-value text file, tracking the result. Raise an --- error if the key is not found. +-- | Like 'lookupValue' but raises an error if the key is not found. lookupValueOrError :: FilePath -> String -> Action String lookupValueOrError file key = (fromMaybe $ error msg) <$> lookupValue file key where msg = "Key " ++ quote key ++ " not found in file " ++ quote file --- | This oracle reads and parses text files consisting of key-value pairs --- @key = value@ and answers 'lookupValue' queries tracking the results. +-- | Lookup a list of values in a text file, tracking the result. Each line of +-- the file is expected to have @key value1 value2 ...@ format. +lookupValues :: FilePath -> String -> Action (Maybe [String]) +lookupValues file key = askOracle $ KeyValues (file, key) + +-- | Like 'lookupValues' but returns the empty list if the key is not found. +lookupValuesOrEmpty :: FilePath -> String -> Action [String] +lookupValuesOrEmpty file key = fromMaybe [] <$> lookupValues file key + +-- | Like 'lookupValues' but raises an error if the key is not found. +lookupValuesOrError :: FilePath -> String -> Action [String] +lookupValuesOrError file key = (fromMaybe $ error msg) <$> lookupValues file key + where + msg = "Key " ++ quote key ++ " not found in file " ++ quote file + +-- | This oracle reads and parses text files to answer 'lookupValue' and +-- 'lookupValues' queries, as well as their derivatives, tracking the results. keyValueOracle :: Rules () keyValueOracle = void $ do - cache <- newCache $ \file -> do + kv <- newCache $ \file -> do need [file] putLoud $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> cache file + kvs <- newCache $ \file -> do + need [file] + putLoud $ "Reading " ++ file ++ "..." + contents <- map words <$> readFileLines file + return $ Map.fromList [ (key, values) | (key:values) <- contents ] + void $ addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> kv file + void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 748a5a2..6ed5633 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,10 +1,10 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, TupleSections #-} module Oracles.Dependencies ( fileDependencies, contextDependencies, libraryTargets, needLibrary, - dependenciesOracles, pkgDependencies, topsortPackages + pkgDependencies, topsortPackages ) where -import qualified Data.HashMap.Strict as Map +import Hadrian.Oracles.KeyValue import Base import Context @@ -14,9 +14,6 @@ import Settings import Settings.Builders.GhcCabal import Settings.Path -newtype Dependency = Dependency (FilePath, FilePath) - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -- | 'Action' @fileDependencies context file@ looks up dependencies of a @file@ -- in a generated dependency file @path/.dependencies@, where @path@ is the build -- path of the given @context at . The action returns a pair @(source, files)@, @@ -25,7 +22,7 @@ newtype Dependency = Dependency (FilePath, FilePath) fileDependencies :: Context -> FilePath -> Action (FilePath, [FilePath]) fileDependencies context obj = do let path = buildPath context -/- ".dependencies" - deps <- askOracle $ Dependency (path, obj) + deps <- lookupValues path obj case deps of Nothing -> error $ "No dependencies found for file " ++ obj Just [] -> error $ "No source file found for file " ++ obj @@ -40,8 +37,7 @@ fileDependencies context obj = do contextDependencies :: Context -> Action [Context] contextDependencies context at Context {..} = do let pkgContext = \pkg -> Context (min stage Stage1) pkg way - unpack = fromMaybe . error $ "No dependencies for " ++ show context - deps <- unpack <$> askOracle (Dependency (packageDependencies, pkgNameString package)) + deps <- lookupValuesOrError packageDependencies (pkgNameString package) pkgs <- sort <$> interpretInContext (pkgContext package) getPackages return . map pkgContext $ intersectOrd (compare . pkgNameString) pkgs deps @@ -67,15 +63,6 @@ libraryTargets context = do needLibrary :: [Context] -> Action () needLibrary cs = need =<< concatMapM libraryTargets cs --- | Oracles for the package dependencies and 'path/dist/.dependencies' files. -dependenciesOracles :: Rules () -dependenciesOracles = do - deps <- newCache $ \file -> do - putLoud $ "Reading dependencies from " ++ file ++ "..." - contents <- map words <$> readFileLines file - return $ Map.fromList [ (key, values) | (key:values) <- contents ] - void $ addOracle $ \(Dependency (file, key)) -> Map.lookup key <$> deps file - -- | Topological sort of packages according to their dependencies. -- HACK (izgzhen): See https://github.com/snowleopard/hadrian/issues/344 for details topsortPackages :: [Package] -> Action [Package] diff --git a/src/Rules.hs b/src/Rules.hs index 335c4c3..2c09e94 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -117,7 +117,6 @@ oracleRules = do Hadrian.Oracles.DirectoryContents.directoryContentsOracle Hadrian.Oracles.KeyValue.keyValueOracle Hadrian.Oracles.Path.pathOracle - Oracles.Dependencies.dependenciesOracles Oracles.ModuleFiles.moduleFilesOracle programsStage1Only :: [Package] From git at git.haskell.org Fri Oct 27 00:55:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to @WhatIsGcc@ being renamed to @CC@ in GHC HEAD (1c137b3) Message-ID: <20171027005506.6F5053A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c137b3d58a85d01eb9018eca927616077d87098/ghc >--------------------------------------------------------------- commit 1c137b3d58a85d01eb9018eca927616077d87098 Author: Herbert Valerio Riedel Date: Sun Apr 17 15:46:06 2016 +0200 Adapt to @WhatIsGcc@ being renamed to @CC@ in GHC HEAD >--------------------------------------------------------------- 1c137b3d58a85d01eb9018eca927616077d87098 cfg/system.config.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 0b2e1f1..3c74076 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -7,7 +7,7 @@ alex = @AlexCmd@ ar = @ArCmd@ -cc = @WhatGccIsCalled@ +cc = @CC@ happy = @HappyCmd@ hs-cpp = @HaskellCPPCmd@ hscolour = @HSCOLOUR@ From git at git.haskell.org Fri Oct 27 00:55:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Convert cfg/system.config.in to use unix line-endings (3bab113) Message-ID: <20171027005510.95F6D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3bab11333ae35906dc030f1d8652d765e92db879/ghc >--------------------------------------------------------------- commit 3bab11333ae35906dc030f1d8652d765e92db879 Author: Herbert Valerio Riedel Date: Sun Apr 17 15:46:57 2016 +0200 Convert cfg/system.config.in to use unix line-endings >--------------------------------------------------------------- 3bab11333ae35906dc030f1d8652d765e92db879 cfg/system.config.in | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Fri Oct 27 00:55:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Oracles.Dependencies moving code to the library and Utilities (former Util) (1df5491) Message-ID: <20171027005510.8F75F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1df549134fdf286e374e5e3f1fef2944ea24f591/ghc >--------------------------------------------------------------- commit 1df549134fdf286e374e5e3f1fef2944ea24f591 Author: Andrey Mokhov Date: Sun Aug 13 23:20:18 2017 +0100 Drop Oracles.Dependencies moving code to the library and Utilities (former Util) >--------------------------------------------------------------- 1df549134fdf286e374e5e3f1fef2944ea24f591 hadrian.cabal | 6 +-- src/Hadrian/Oracles/KeyValue.hs | 16 +++++++- src/Oracles/Dependencies.hs | 79 --------------------------------------- src/Rules.hs | 4 +- src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 7 ++-- src/Rules/Configure.hs | 2 +- src/Rules/Data.hs | 3 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Install.hs | 3 +- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 3 +- src/Rules/Perl.hs | 2 +- src/Rules/Program.hs | 3 +- src/Rules/Register.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 2 +- src/Rules/Wrappers.hs | 2 +- src/Settings.hs | 8 +++- src/Settings/Builders/GhcCabal.hs | 9 +---- src/Settings/Packages/GhcCabal.hs | 2 +- src/{Util.hs => Utilities.hs} | 56 ++++++++++++++++++++++++++- 25 files changed, 103 insertions(+), 120 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1df549134fdf286e374e5e3f1fef2944ea24f591 From git at git.haskell.org Fri Oct 27 00:55:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #225 from hvr/pr/systemcfg-fixes (1099f62) Message-ID: <20171027005514.13E1B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1099f6232570c8124afb27a13097272f436dd596/ghc >--------------------------------------------------------------- commit 1099f6232570c8124afb27a13097272f436dd596 Merge: 897ba61 3bab113 Author: Andrey Mokhov Date: Sun Apr 17 17:00:15 2016 +0100 Merge pull request #225 from hvr/pr/systemcfg-fixes Misc `system.config.in` fixes >--------------------------------------------------------------- 1099f6232570c8124afb27a13097272f436dd596 cfg/system.config.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:55:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make most extensions default, minor clean up (a56298f) Message-ID: <20171027005514.29C133A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a56298fb9cea9f3b4d5eebdefc3d3ddced239981/ghc >--------------------------------------------------------------- commit a56298fb9cea9f3b4d5eebdefc3d3ddced239981 Author: Andrey Mokhov Date: Sun Aug 13 23:30:16 2017 +0100 Make most extensions default, minor clean up >--------------------------------------------------------------- a56298fb9cea9f3b4d5eebdefc3d3ddced239981 hadrian.cabal | 10 +++++----- src/Builder.hs | 1 - src/Context.hs | 1 - src/Expression.hs | 1 - src/GHC.hs | 2 +- src/Hadrian/Expression.hs | 3 +-- src/Hadrian/Oracles/ArgsHash.hs | 1 - src/Hadrian/Oracles/DirectoryContents.hs | 1 - src/Hadrian/Oracles/KeyValue.hs | 1 - src/Hadrian/Oracles/Path.hs | 1 - src/Hadrian/Target.hs | 1 - src/Oracles/ModuleFiles.hs | 1 - src/Package.hs | 1 - src/Rules.hs | 4 +--- src/Rules/Install.hs | 1 - src/Rules/Library.hs | 2 +- src/Rules/Selftest.hs | 1 - src/Rules/Wrappers.hs | 4 ++-- src/Settings/Install.hs | 8 +++----- src/Stage.hs | 1 - 20 files changed, 14 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a56298fb9cea9f3b4d5eebdefc3d3ddced239981 From git at git.haskell.org Fri Oct 27 00:55:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep up with recent GHC changes, see #215. (e34e7e2) Message-ID: <20171027005517.A9EAF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e34e7e287864bd8028e1b1d2e4b526135106787a/ghc >--------------------------------------------------------------- commit e34e7e287864bd8028e1b1d2e4b526135106787a Author: Andrey Mokhov Date: Mon Apr 18 01:19:21 2016 +0100 Keep up with recent GHC changes, see #215. >--------------------------------------------------------------- e34e7e287864bd8028e1b1d2e4b526135106787a cfg/system.config.in | 2 ++ shaking-up-ghc.cabal | 2 +- src/Oracles/Config/Flag.hs | 2 ++ src/Settings/Builders/Ghc.hs | 8 +++++++- src/Settings/Packages/GhcCabal.hs | 10 ++++++++-- 5 files changed, 20 insertions(+), 4 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index d053e65..f235f19 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -70,6 +70,8 @@ ghc-major-version = @GhcMajVersion@ ghc-minor-version = @GhcMinVersion@ ghc-patch-level = @GhcPatchLevel@ +supports-this-unit-id = @SUPPORTS_THIS_UNIT_ID@ + project-name = @ProjectName@ project-version = @ProjectVersion@ project-version-int = @ProjectVersionInt@ diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 17b48f0..92be3c7 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -118,7 +118,7 @@ executable ghc-shake , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* + , Cabal == 1.22.* || == 1.24.* , containers == 0.5.* , directory == 1.2.* , extra == 1.4.* diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 9d33445..449e2b2 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -18,6 +18,7 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken + | SupportsThisUnitId | WithLibdw | UseSystemFfi @@ -34,6 +35,7 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" + SupportsThisUnitId -> "supports-this-unit-id" WithLibdw -> "with-libdw" UseSystemFfi -> "use-system-ffi" value <- askConfigWithDefault key . putError diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 067c76e..a07c512 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -5,6 +5,7 @@ module Settings.Builders.Ghc ( import Base import Expression import GHC +import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.PackageData import Predicates hiding (way, stage) @@ -114,11 +115,16 @@ packageGhcArgs = do lift . when (isLibrary pkg) $ do conf <- pkgConfFile context need [conf] + -- FIXME: Get rid of to-be-deprecated -this-package-key. + thisArg <- do + not0 <- notStage0 + unit <- getFlag SupportsThisUnitId + return $ if not0 || unit then "-this-unit-id " else "-this-package-key " mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" , bootPackageDbArgs - , isLibrary pkg ? (arg $ "-this-package-key " ++ compId) + , isLibrary pkg ? (arg $ thisArg ++ compId) , append $ map ("-package-id " ++) pkgDepIds ] -- TODO: Improve handling of "cabal_macros.h" diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 762720f..80bda57 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -2,7 +2,8 @@ module Settings.Packages.GhcCabal (ghcCabalPackageArgs) where import Base import Expression -import GHC (ghcCabal) +import GHC +import Oracles.Config.Setting import Predicates (builderGhc, package, stage0) import Settings @@ -19,8 +20,13 @@ ghcCabalBootArgs = stage0 ? do path <- getBuildPath let cabalMacros = path -/- "autogen/cabal_macros.h" cabalMacrosBoot = pkgPath ghcCabal -/- "cabal_macros_boot.h" + cabalDeps <- fromDiffExpr $ mconcat + [ append [ array, base, bytestring, containers, deepseq, directory + , pretty, process, time ] + , notM windowsHost ? append [unix] + , windowsHost ? append [win32] ] mconcat - [ remove ["-hide-all-packages"] + [ append [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , removePair "-optP-include" $ "-optP" ++ cabalMacros , arg "--make" , arg "-j" From git at git.haskell.org Fri Oct 27 00:55:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add default extensions to .ghci (b4977a3) Message-ID: <20171027005517.C29913A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b4977a3c7577cb135de38a20654878931e5814ea/ghc >--------------------------------------------------------------- commit b4977a3c7577cb135de38a20654878931e5814ea Author: Andrey Mokhov Date: Sun Aug 13 23:44:07 2017 +0100 Add default extensions to .ghci >--------------------------------------------------------------- b4977a3c7577cb135de38a20654878931e5814ea .ghci | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 9c0fe7a..8bb287b 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,11 @@ -:set -Wall -fno-warn-name-shadowing -isrc -i../libraries/Cabal/Cabal -XRecordWildCards +:set -Wall -fno-warn-name-shadowing -isrc -i../libraries/Cabal/Cabal +:set -XDeriveFunctor +:set -XDeriveGeneric +:set -XFlexibleInstances +:set -XGeneralizedNewtypeDeriving +:set -XLambdaCase +:set -XRecordWildCards +:set -XScopedTypeVariables +:set -XTupleSections + :load Main From git at git.haskell.org Fri Oct 27 00:55:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on cabalDeps list. (d1c8ba4) Message-ID: <20171027005521.7D2A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1c8ba4b5787d0995538cc0b69a4aa93969f6488/ghc >--------------------------------------------------------------- commit d1c8ba4b5787d0995538cc0b69a4aa93969f6488 Author: Andrey Mokhov Date: Mon Apr 18 10:16:13 2016 +0100 Add a note on cabalDeps list. See #215. [skip ci] >--------------------------------------------------------------- d1c8ba4b5787d0995538cc0b69a4aa93969f6488 src/Settings/Packages/GhcCabal.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 80bda57..1dac541 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -20,6 +20,9 @@ ghcCabalBootArgs = stage0 ? do path <- getBuildPath let cabalMacros = path -/- "autogen/cabal_macros.h" cabalMacrosBoot = pkgPath ghcCabal -/- "cabal_macros_boot.h" + -- Note: We could have computed 'cabalDeps' instead of hard-coding it + -- but this doesn't worth the effort, since we plan to drop ghc-cabal + -- altogether at some point. See #18. cabalDeps <- fromDiffExpr $ mconcat [ append [ array, base, bytestring, containers, deepseq, directory , pretty, process, time ] From git at git.haskell.org Fri Oct 27 00:55:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up imports (0ef2b1f) Message-ID: <20171027005521.9331D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ef2b1f8123ba90614c24d06a0a32bda0410334e/ghc >--------------------------------------------------------------- commit 0ef2b1f8123ba90614c24d06a0a32bda0410334e Author: Andrey Mokhov Date: Mon Aug 14 00:05:10 2017 +0100 Clean up imports >--------------------------------------------------------------- 0ef2b1f8123ba90614c24d06a0a32bda0410334e src/Expression.hs | 14 ++------------ src/Hadrian/Oracles/Path.hs | 1 - src/Oracles/PackageData.hs | 5 ++--- src/Oracles/Setting.hs | 1 - src/Rules.hs | 1 - src/Rules/Install.hs | 2 +- src/Rules/Selftest.hs | 1 - src/Settings.hs | 1 - src/Settings/Install.hs | 1 - src/Utilities.hs | 1 - 10 files changed, 5 insertions(+), 23 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 34a88fb..ca8862e 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -20,25 +20,15 @@ module Expression ( getInput, getOutput, -- * Re-exports - module Data.Semigroup, - module Builder, - module Package, - module Stage, - module Way + module Base ) where -import Control.Monad.Extra -import Data.Semigroup - import qualified Hadrian.Expression as H import Hadrian.Expression hiding (Expr, Predicate, Args) -import Builder +import Base import Context (Context, vanillaContext, stageContext, getStage, getPackage, getWay) -import Package -import Stage import Target hiding (builder, inputs, outputs) -import Way -- | @Expr a@ is a computation that produces a value of type @Action a@ and can -- read parameters of the current build 'Target'. diff --git a/src/Hadrian/Oracles/Path.hs b/src/Hadrian/Oracles/Path.hs index 2c578a1..d10948b 100644 --- a/src/Hadrian/Oracles/Path.hs +++ b/src/Hadrian/Oracles/Path.hs @@ -33,7 +33,6 @@ fixAbsolutePathOnWindows path = do else return path - newtype LookupInPath = LookupInPath String deriving (Binary, Eq, Hashable, NFData, Show, Typeable) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index c813f82..208881d 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -2,10 +2,9 @@ module Oracles.PackageData ( PackageData (..), PackageDataList (..), pkgData, pkgDataList ) where -import Data.List -import Development.Shake import Hadrian.Oracles.KeyValue -import Hadrian.Utilities + +import Base data PackageData = BuildGhciLib FilePath | ComponentId FilePath diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 095dbaa..e9fe886 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -6,7 +6,6 @@ module Oracles.Setting ( topDirectory, relocatableBuild, installDocDir, installGhcLibDir, libsuf ) where -import Development.Shake import Hadrian.Expression import Hadrian.Oracles.KeyValue import Hadrian.Oracles.Path diff --git a/src/Rules.hs b/src/Rules.hs index 8a576d4..149789f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,7 +5,6 @@ import qualified Hadrian.Oracles.DirectoryContents import qualified Hadrian.Oracles.KeyValue import qualified Hadrian.Oracles.Path -import Base import Context import Expression import Flavour diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index edf2492..4b24ca2 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -5,7 +5,7 @@ import qualified System.Directory as IO import Base import Context -import Expression hiding (builder) +import Expression import GHC import Oracles.Setting import Rules diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 0112d8f..3942753 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -1,7 +1,6 @@ {-# OPTIONS_GHC -fno-warn-orphans #-} module Rules.Selftest (selftestRules) where -import Development.Shake import Test.QuickCheck import Base diff --git a/src/Settings.hs b/src/Settings.hs index 7576e7a..e285175 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -9,7 +9,6 @@ module Settings ( import Hadrian.Oracles.KeyValue import Hadrian.Oracles.Path -import Base import Context import CmdLineFlag import Expression diff --git a/src/Settings/Install.hs b/src/Settings/Install.hs index 2d18a67..086cfa2 100644 --- a/src/Settings/Install.hs +++ b/src/Settings/Install.hs @@ -1,6 +1,5 @@ module Settings.Install (installPackageDbDirectory) where -import Base import Expression import UserSettings diff --git a/src/Utilities.hs b/src/Utilities.hs index 5356c11..07b34be 100644 --- a/src/Utilities.hs +++ b/src/Utilities.hs @@ -17,7 +17,6 @@ import Hadrian.Oracles.DirectoryContents import Hadrian.Oracles.KeyValue import Hadrian.Oracles.Path -import Base import CmdLineFlag import Context import Expression hiding (builder, inputs, outputs, way, stage, package) From git at git.haskell.org Fri Oct 27 00:55:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Provide more useful ToPredicate instances (db56cf4) Message-ID: <20171027005525.503963A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db56cf4eaf15378c3023de4e66a1285376eb6599/ghc >--------------------------------------------------------------- commit db56cf4eaf15378c3023de4e66a1285376eb6599 Author: Andrey Mokhov Date: Mon Aug 14 23:07:05 2017 +0100 Provide more useful ToPredicate instances >--------------------------------------------------------------- db56cf4eaf15378c3023de4e66a1285376eb6599 src/Hadrian/Expression.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Hadrian/Expression.hs b/src/Hadrian/Expression.hs index dad9d32..b781cdd 100644 --- a/src/Hadrian/Expression.hs +++ b/src/Hadrian/Expression.hs @@ -75,14 +75,14 @@ p ? e = do bool <- toPredicate p if bool then e else mempty -instance (c ~ c', b ~ b') => ToPredicate (Predicate c b) c' b' where - toPredicate = id - instance ToPredicate Bool c b where toPredicate = pure -instance ToPredicate (Action Bool) c b where - toPredicate = expr +instance ToPredicate p c b => ToPredicate (Action p) c b where + toPredicate = toPredicate . expr + +instance (c ~ c', b ~ b', ToPredicate p c' b') => ToPredicate (Expr c b p) c' b' where + toPredicate p = toPredicate =<< p -- | Interpret a given expression according to the given 'Target'. interpret :: Target c b -> Expr c b a -> Action a From git at git.haskell.org Fri Oct 27 00:55:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run ghc-pkg list through stack (e29218a) Message-ID: <20171027005529.44B823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e29218a5f8df4e9c03e30b2f0579d5f8ea8ac647/ghc >--------------------------------------------------------------- commit e29218a5f8df4e9c03e30b2f0579d5f8ea8ac647 Author: Andrey Mokhov Date: Fri Apr 22 13:04:44 2016 +0100 Run ghc-pkg list through stack >--------------------------------------------------------------- e29218a5f8df4e9c03e30b2f0579d5f8ea8ac647 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 88ca776..6cc17b6 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -35,7 +35,7 @@ install: - stack --version - alex --version - happy --version - - ghc-pkg list + - stack exec -- ghc-pkg list build_script: - cd C:\msys64\home\ghc\shake-build From git at git.haskell.org Fri Oct 27 00:55:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: List installed packages in CI (61032aa) Message-ID: <20171027005525.4C71F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/61032aa99bc8f1afab5e0f3487202c30488243fb/ghc >--------------------------------------------------------------- commit 61032aa99bc8f1afab5e0f3487202c30488243fb Author: Andrey Mokhov Date: Fri Apr 22 12:21:26 2016 +0100 List installed packages in CI >--------------------------------------------------------------- 61032aa99bc8f1afab5e0f3487202c30488243fb .travis.yml | 1 + appveyor.yml | 1 + 2 files changed, 2 insertions(+) diff --git a/.travis.yml b/.travis.yml index 21bf769..0e59864 100644 --- a/.travis.yml +++ b/.travis.yml @@ -57,6 +57,7 @@ install: - ( cd ghc && ./boot ) - ( cd ghc && ./configure ) - cat ghc/shake-build/cfg/system.config + - ghc-pkg list script: - ( cd ghc/shake-build && cabal haddock --internal ) diff --git a/appveyor.yml b/appveyor.yml index 537983c..88ca776 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -35,6 +35,7 @@ install: - stack --version - alex --version - happy --version + - ghc-pkg list build_script: - cd C:\msys64\home\ghc\shake-build From git at git.haskell.org Fri Oct 27 00:55:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor command line arguments and flavours (0530e0d) Message-ID: <20171027005529.5C4693A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0530e0df5b9076b1643a2d3b6a4abf4f31041f3c/ghc >--------------------------------------------------------------- commit 0530e0df5b9076b1643a2d3b6a4abf4f31041f3c Author: Andrey Mokhov Date: Mon Aug 14 23:12:52 2017 +0100 Refactor command line arguments and flavours * Get rid of unsafePerformIO using shakeExtra * Move diagnostic info utilities to the library See #347 >--------------------------------------------------------------- 0530e0df5b9076b1643a2d3b6a4abf4f31041f3c hadrian.cabal | 2 +- src/CmdLineFlag.hs | 128 ------------------------------ src/CommandLine.hs | 128 ++++++++++++++++++++++++++++++ src/Flavour.hs | 24 +++--- src/Hadrian/Utilities.hs | 160 ++++++++++++++++++++++++++++++++++++-- src/Main.hs | 58 ++++++++------ src/Rules.hs | 9 +-- src/Rules/Cabal.hs | 1 - src/Rules/Configure.hs | 9 ++- src/Rules/Data.hs | 1 - src/Rules/Documentation.hs | 3 +- src/Rules/Generate.hs | 18 +++-- src/Rules/Gmp.hs | 1 - src/Rules/Install.hs | 6 +- src/Rules/Library.hs | 3 +- src/Rules/Program.hs | 18 +++-- src/Rules/Register.hs | 1 - src/Rules/Selftest.hs | 1 - src/Rules/SourceDist.hs | 1 - src/Rules/Test.hs | 3 +- src/Settings.hs | 40 +++++----- src/Settings/Builders/Ghc.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 7 +- src/Settings/Default.hs | 18 +++-- src/Settings/Packages/Base.hs | 8 +- src/Settings/Packages/Compiler.hs | 4 +- src/UserSettings.hs | 20 +++-- src/Utilities.hs | 131 ++++++------------------------- 28 files changed, 443 insertions(+), 365 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 0530e0df5b9076b1643a2d3b6a4abf4f31041f3c From git at git.haskell.org Fri Oct 27 00:55:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use Docker on Travis. (ee592f4) Message-ID: <20171027005533.578413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee592f4254da5b9f2db59ea465fd55adf66b771f/ghc >--------------------------------------------------------------- commit ee592f4254da5b9f2db59ea465fd55adf66b771f Author: Andrey Mokhov Date: Fri Apr 22 13:08:07 2016 +0100 Don't use Docker on Travis. See #229. >--------------------------------------------------------------- ee592f4254da5b9f2db59ea465fd55adf66b771f .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0e59864..2f0739a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,4 +1,4 @@ -sudo: false +sudo: true matrix: include: From git at git.haskell.org Fri Oct 27 00:55:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move file system operations to the library (58e2d05) Message-ID: <20171027005533.700F13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/58e2d05064d8102914c7b887df6e2090c1d906db/ghc >--------------------------------------------------------------- commit 58e2d05064d8102914c7b887df6e2090c1d906db Author: Andrey Mokhov Date: Tue Aug 15 00:31:47 2017 +0100 Move file system operations to the library See #347 >--------------------------------------------------------------- 58e2d05064d8102914c7b887df6e2090c1d906db src/Hadrian/Oracles/DirectoryContents.hs | 17 +++++- src/Hadrian/Oracles/Path.hs | 6 +- src/Hadrian/Utilities.hs | 96 ++++++++++++++++++++++++++++--- src/Rules/Clean.hs | 1 - src/Rules/Wrappers.hs | 3 +- src/Utilities.hs | 97 ++------------------------------ 6 files changed, 112 insertions(+), 108 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 58e2d05064d8102914c7b887df6e2090c1d906db From git at git.haskell.org Fri Oct 27 00:55:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix compile error on GHC 8.2+ (5026b9c) Message-ID: <20171027005537.840E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5026b9c6f145f748e0e8b1621e3af482c475b00d/ghc >--------------------------------------------------------------- commit 5026b9c6f145f748e0e8b1621e3af482c475b00d Author: Andrey Mokhov Date: Tue Aug 15 00:44:24 2017 +0100 Fix compile error on GHC 8.2+ >--------------------------------------------------------------- 5026b9c6f145f748e0e8b1621e3af482c475b00d src/CommandLine.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index 18ce2ec..dbcf41f 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -3,10 +3,11 @@ module CommandLine ( cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects ) where -import Data.Dynamic +import Data.Dynamic (Dynamic) import Data.Either import qualified Data.HashMap.Strict as Map import Data.List.Extra +import Data.Typeable (TypeRep) import Development.Shake hiding (Normal) import Hadrian.Utilities import System.Console.GetOpt From git at git.haskell.org Fri Oct 27 00:55:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try full build on Mac OS X. (219da37) Message-ID: <20171027005537.9652E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/219da3757e6f5ee6761c672099a005987156849e/ghc >--------------------------------------------------------------- commit 219da3757e6f5ee6761c672099a005987156849e Author: Andrey Mokhov Date: Fri Apr 22 13:47:29 2016 +0100 Try full build on Mac OS X. >--------------------------------------------------------------- 219da3757e6f5ee6761c672099a005987156849e .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 2f0739a..d6092fb 100644 --- a/.travis.yml +++ b/.travis.yml @@ -20,7 +20,7 @@ matrix: - cabal install alex happy - os: osx - env: TARGET=utils/ghc-pkg/stage1/build/tmp/ghc-pkg + env: TARGET= before_install: - brew update - brew install ghc cabal-install From git at git.haskell.org Fri Oct 27 00:55:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to shake-0.15.6. (cf5ab9a) Message-ID: <20171027005541.CDD9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf5ab9ad72cf29153cc0cbfdd510465fc6abcbc9/ghc >--------------------------------------------------------------- commit cf5ab9ad72cf29153cc0cbfdd510465fc6abcbc9 Author: Andrey Mokhov Date: Fri Apr 22 17:05:28 2016 +0100 Switch to shake-0.15.6. >--------------------------------------------------------------- cf5ab9ad72cf29153cc0cbfdd510465fc6abcbc9 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 92be3c7..da19de1 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -124,7 +124,7 @@ executable ghc-shake , extra == 1.4.* , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.9 - , shake == 0.15.* + , shake == 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* ghc-options: -Wall From git at git.haskell.org Fri Oct 27 00:55:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export Dynamic and Typeable bits (d2ca01b) Message-ID: <20171027005541.DD2E13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2ca01bbdf7354c0e88af711696ac333040d2374/ghc >--------------------------------------------------------------- commit d2ca01bbdf7354c0e88af711696ac333040d2374 Author: Andrey Mokhov Date: Tue Aug 15 02:11:02 2017 +0100 Re-export Dynamic and Typeable bits >--------------------------------------------------------------- d2ca01bbdf7354c0e88af711696ac333040d2374 src/CommandLine.hs | 2 -- src/Hadrian/Utilities.hs | 5 ++++- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index dbcf41f..5688d6f 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -3,11 +3,9 @@ module CommandLine ( cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects ) where -import Data.Dynamic (Dynamic) import Data.Either import qualified Data.HashMap.Strict as Map import Data.List.Extra -import Data.Typeable (TypeRep) import Development.Shake hiding (Normal) import Hadrian.Utilities import System.Console.GetOpt diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 0791d44..74c10b4 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -19,7 +19,10 @@ module Hadrian.Utilities ( UseColour (..), putColoured, BuildProgressColour (..), putBuild, SuccessColour (..), putSuccess, ProgressInfo (..), putProgressInfo, renderAction, renderProgram, renderLibrary, renderBox, - renderUnicorn + renderUnicorn, + + -- * Useful re-exports + Dynamic, fromDynamic, toDyn, TypeRep, typeOf ) where import Control.Monad.Extra From git at git.haskell.org Fri Oct 27 00:55:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move need of inplaceLibCopyTargets to top-level (#388) (0c67f7d) Message-ID: <20171027005545.A29833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c67f7d21536a4ca305758516bce7ccd0f40db7b/ghc >--------------------------------------------------------------- commit 0c67f7d21536a4ca305758516bce7ccd0f40db7b Author: Zhen Zhang Date: Tue Aug 15 20:34:32 2017 +0800 Move need of inplaceLibCopyTargets to top-level (#388) >--------------------------------------------------------------- 0c67f7d21536a4ca305758516bce7ccd0f40db7b src/Rules.hs | 12 +++++++----- src/Rules/Program.hs | 5 ++--- 2 files changed, 9 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index d55a578..4077dc6 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -24,7 +24,8 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings -import Settings.Path +import Settings.Path (inplaceLibCopyTargets, pkgLibraryFile, + pkgSetupConfigFile, pkgHaddockFile) import Target import Utilities @@ -41,10 +42,11 @@ topLevelTargets = action $ do libs <- concatForM [Stage0, Stage1] $ \stage -> concatForM libraryPackages $ packageTargets stage prgs <- concatForM programsStage1Only $ packageTargets Stage0 - return $ libs ++ prgs - else - concatForM allStages $ \stage -> - concatForM (knownPackages \\ [rts, libffi]) $ packageTargets stage + return $ libs ++ prgs ++ inplaceLibCopyTargets + else do + targets <- concatForM allStages $ \stage -> + concatForM (knownPackages \\ [rts, libffi]) $ packageTargets stage + return $ targets ++ inplaceLibCopyTargets -- | Return the list of targets associated with a given 'Stage' and 'Package'. packageTargets :: Stage -> Package -> Action [FilePath] diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 6ca514f..edef17f 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -11,7 +11,8 @@ import Oracles.PackageData import Oracles.Setting import Rules.Wrappers import Settings -import Settings.Path +import Settings.Path (buildPath, inplaceLibBinPath, rtsContext, objectPath, + inplaceLibPath, inplaceBinPath) import Target import Utilities @@ -26,8 +27,6 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do context' <- programContext stage package buildBinaryAndWrapper rs context' bin - when (package == ghc) $ want inplaceLibCopyTargets - -- Rules for programs built in install directories when (stage == Stage0 || package == ghc) $ do -- Some binaries in inplace/bin are wrapped From git at git.haskell.org Fri Oct 27 00:55:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add shake-0.15.6 to stack extra-deps (028ef28) Message-ID: <20171027005545.AD7C13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/028ef285adb1b4c4ada79c1ec2ee891e240b0c59/ghc >--------------------------------------------------------------- commit 028ef285adb1b4c4ada79c1ec2ee891e240b0c59 Author: Moritz Kiefer Date: Fri Apr 22 18:24:35 2016 +0200 Add shake-0.15.6 to stack extra-deps >--------------------------------------------------------------- 028ef285adb1b4c4ada79c1ec2ee891e240b0c59 stack.yaml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index 0772c76..0d8809b 100644 --- a/stack.yaml +++ b/stack.yaml @@ -8,7 +8,8 @@ packages: - '.' # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) -extra-deps: [] +extra-deps: +- shake-0.15.6 # Override default flag values for local packages and extra-deps flags: {} From git at git.haskell.org Fri Oct 27 00:55:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #230 from cocreature/stack-shake-0.15.6 (6826d14) Message-ID: <20171027005549.6233B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6826d14069396002e5a1fbee6b8c9c1a54cda815/ghc >--------------------------------------------------------------- commit 6826d14069396002e5a1fbee6b8c9c1a54cda815 Merge: cf5ab9a 028ef28 Author: Andrey Mokhov Date: Fri Apr 22 19:44:30 2016 +0100 Merge pull request #230 from cocreature/stack-shake-0.15.6 Add shake-0.15.6 to stack extra-deps >--------------------------------------------------------------- 6826d14069396002e5a1fbee6b8c9c1a54cda815 stack.yaml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:55:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Major refactoring of path settings (9b70568) Message-ID: <20171027005549.87D103A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b70568615e2763ff782279be28286373b59d8ff/ghc >--------------------------------------------------------------- commit 9b70568615e2763ff782279be28286373b59d8ff Author: Andrey Mokhov Date: Wed Aug 16 03:45:51 2017 +0100 Major refactoring of path settings * Move buildRoot into the Action monad, so it can be configured from command line in future * Move settings from Setting.Path to Base and Context * Simplify build rule matching and prepare to factoring out common build rules into the library, #347 >--------------------------------------------------------------- 9b70568615e2763ff782279be28286373b59d8ff hadrian.cabal | 2 - src/Base.hs | 76 +++++++++- src/Context.hs | 101 ++++++++++++- src/Expression.hs | 6 +- src/GHC.hs | 70 ++++++++- src/Hadrian/Expression.hs | 6 +- src/Hadrian/Utilities.hs | 64 ++++---- src/Main.hs | 9 +- src/Oracles/ModuleFiles.hs | 32 ++-- src/Rules.hs | 15 +- src/Rules/Cabal.hs | 9 +- src/Rules/Clean.hs | 10 +- src/Rules/Compile.hs | 24 +-- src/Rules/Data.hs | 36 +++-- src/Rules/Dependencies.hs | 3 +- src/Rules/Documentation.hs | 45 +++--- src/Rules/Generate.hs | 100 +++++++------ src/Rules/Gmp.hs | 77 ++++++---- src/Rules/Install.hs | 36 +++-- src/Rules/Libffi.hs | 60 +++++--- src/Rules/Library.hs | 26 ++-- src/Rules/Program.hs | 8 +- src/Rules/Register.hs | 47 ++++-- src/Rules/Selftest.hs | 17 --- src/Rules/Test.hs | 1 - src/Rules/Wrappers.hs | 41 +++--- src/Settings.hs | 19 +-- src/Settings/Builders/Common.hs | 17 ++- src/Settings/Builders/Configure.hs | 34 +++-- src/Settings/Builders/DeriveConstants.hs | 21 +-- src/Settings/Builders/Ghc.hs | 12 +- src/Settings/Builders/GhcCabal.hs | 21 ++- src/Settings/Builders/GhcPkg.hs | 4 +- src/Settings/Builders/Haddock.hs | 11 +- src/Settings/Builders/HsCpp.hs | 8 +- src/Settings/Builders/Hsc2Hs.hs | 5 +- src/Settings/Builders/Make.hs | 10 +- src/Settings/Install.hs | 11 -- src/Settings/Packages/Ghc.hs | 9 +- src/Settings/Packages/IntegerGmp.hs | 7 +- src/Settings/Packages/Rts.hs | 8 +- src/Settings/Path.hs | 245 ------------------------------- src/UserSettings.hs | 8 +- src/Utilities.hs | 14 +- 44 files changed, 733 insertions(+), 652 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 9b70568615e2763ff782279be28286373b59d8ff From git at git.haskell.org Fri Oct 27 00:55:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Tweak shake constraint. (98041b2) Message-ID: <20171027005553.D63733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/98041b2607cbe3fab8208bb41c0381bce021fbf2/ghc >--------------------------------------------------------------- commit 98041b2607cbe3fab8208bb41c0381bce021fbf2 Author: Andrey Mokhov Date: Fri Apr 22 19:47:18 2016 +0100 Tweak shake constraint. See #230. >--------------------------------------------------------------- 98041b2607cbe3fab8208bb41c0381bce021fbf2 shaking-up-ghc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index da19de1..a5e6d22 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -124,7 +124,7 @@ executable ghc-shake , extra == 1.4.* , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.9 - , shake == 0.15.6 + , shake >= 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* ghc-options: -Wall From git at git.haskell.org Fri Oct 27 00:55:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix merge conflicts (1ade885) Message-ID: <20171027005553.F13F63A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ade88547a2c3256c6b6e6de8c546a04dc1ae1d3/ghc >--------------------------------------------------------------- commit 1ade88547a2c3256c6b6e6de8c546a04dc1ae1d3 Merge: 9b70568 0c67f7d Author: Andrey Mokhov Date: Wed Aug 16 03:47:39 2017 +0100 Fix merge conflicts >--------------------------------------------------------------- 1ade88547a2c3256c6b6e6de8c546a04dc1ae1d3 src/Rules.hs | 9 +++++---- src/Rules/Program.hs | 2 -- 2 files changed, 5 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 00:55:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CompilerMode Link. (7bc4867) Message-ID: <20171027005557.A29B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7bc48677710d37d905a1e1b005e8113b28abb473/ghc >--------------------------------------------------------------- commit 7bc48677710d37d905a1e1b005e8113b28abb473 Author: Andrey Mokhov Date: Mon Apr 25 23:51:58 2016 +0100 Add CompilerMode Link. See #223. >--------------------------------------------------------------- 7bc48677710d37d905a1e1b005e8113b28abb473 src/Builder.hs | 16 +++++++++------- src/Rules/Program.hs | 3 +-- src/Settings/Builders/Ghc.hs | 34 ++++++++++++++++++++-------------- 3 files changed, 30 insertions(+), 23 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 348e7e9..09e4ab9 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -15,11 +15,14 @@ import Oracles.LookupInPath import Oracles.WindowsPath import Stage --- TODO: Add Link mode? --- | A C or Haskell compiler can be used in two modes: for compiling sources --- into object files, or for extracting source dependencies, e.g. by passing -M --- command line option. -data CompilerMode = Compile | FindDependencies deriving (Show, Eq, Generic) +-- | A compiler can typically be used in one of three modes: +-- 1) Compiling sources into object files. +-- 2) Extracting source dependencies, e.g. by passing -M command line argument. +-- 3) Linking object files & static libraries into an executable. +data CompilerMode = Compile + | FindDependencies + | Link + deriving (Show, Eq, Generic) -- TODO: Do we really need HsCpp builder? Can't we use Cc instead? -- | A 'Builder' is an external command invoked in separate process using 'Shake.cmd' @@ -138,8 +141,7 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- TODO: split into two functions: needBuilder (without laxDependencies) and --- unsafeNeedBuilder (with the laxDependencies parameter) +-- TODO: Get rid of laxDependencies -- we no longer need it (use Shake's skip). -- | Make sure a builder exists on the given path and rebuild it if out of date. -- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of -- date (can save a lot of build time when changing GHC). diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 975be85..2cee06c 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -99,8 +99,7 @@ buildBinary rs context@(Context stage package _) bin = do then [ pkgPath package -/- src <.> "hs" | src <- hSrcs ] else objs need $ binDeps ++ libs - -- TODO: Use Link mode instead of Compile. - buildWithResources rs $ Target context (Ghc Compile stage) binDeps [bin] + buildWithResources rs $ Target context (Ghc Link stage) binDeps [bin] synopsis <- interpretInContext context $ getPkgData Synopsis putSuccess $ renderProgram ("'" ++ pkgNameString package ++ "' (" ++ show stage ++ ").") diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a07c512..7152526 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -18,8 +18,9 @@ import Settings.Builders.Common (cIncludeArgs) -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ -- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) +-- TODO: Simplify ghcBuilderArgs :: Args -ghcBuilderArgs = stagedBuilder (Ghc Compile) ? do +ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do output <- getOutput stage <- getStage way <- getWay @@ -27,16 +28,6 @@ ghcBuilderArgs = stagedBuilder (Ghc Compile) ? do let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] buildHi = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf] buildProg = not (buildObj || buildHi) - libs <- getPkgDataList DepExtraLibs - gmpLibs <- if stage > Stage0 && buildProg - then do -- TODO: get this data more gracefully - buildInfo <- lift $ readFileLines gmpBuildInfoPath - let extract s = case stripPrefix "extra-libraries: " s of - Nothing -> [] - Just value -> words value - return $ concatMap extract buildInfo - else return [] - libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -44,14 +35,29 @@ ghcBuilderArgs = stagedBuilder (Ghc Compile) ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , buildProg ? arg "-no-auto-link-packages" - , buildProg ? append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] - , buildProg ? append [ "-optl-L" ++ dir | dir <- libDirs ] + , buildProg ? ghcLinkArgs , not buildProg ? arg "-c" , append =<< getInputs , buildHi ? append ["-fno-code", "-fwrite-interface"] , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] +ghcLinkArgs :: Args +ghcLinkArgs = stagedBuilder (Ghc Link) ? do + stage <- getStage + libs <- getPkgDataList DepExtraLibs + gmpLibs <- if stage > Stage0 + then do -- TODO: get this data more gracefully + buildInfo <- lift $ readFileLines gmpBuildInfoPath + let extract s = case stripPrefix "extra-libraries: " s of + Nothing -> [] + Just value -> words value + return $ concatMap extract buildInfo + else return [] + libDirs <- getPkgDataList DepLibDirs + mconcat [ arg "-no-auto-link-packages" + , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] + , append [ "-optl-L" ++ dir | dir <- libDirs ] ] + needTouchy :: Action () needTouchy = whenM windowsHost $ need [fromJust $ programPath (vanillaContext Stage0 touchy)] From git at git.haskell.org Fri Oct 27 00:55:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:55:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (7792fbb) Message-ID: <20171027005557.D857B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7792fbbebbb68f8f2b2e95d29a6365f74376b398/ghc >--------------------------------------------------------------- commit 7792fbbebbb68f8f2b2e95d29a6365f74376b398 Author: Andrey Mokhov Date: Wed Aug 16 13:33:16 2017 +0100 Minor revision >--------------------------------------------------------------- 7792fbbebbb68f8f2b2e95d29a6365f74376b398 src/Expression.hs | 13 +++++++++++-- src/GHC.hs | 6 +++++- src/Settings.hs | 13 ------------- 3 files changed, 16 insertions(+), 16 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 8da4a6f..647c057 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -16,8 +16,8 @@ module Expression ( Context, vanillaContext, stageContext, Target, -- * Convenient accessors - getBuildRoot, getBuildPath, getContext, getStage, getPackage, getBuilder, - getOutputs, getInputs, getWay, getInput, getOutput, + getBuildRoot, getBuildPath, getContext, getPkgData, getPkgDataList, getStage, + getPackage, getBuilder, getOutputs, getInputs, getWay, getInput, getOutput, -- * Re-exports module Base @@ -28,6 +28,7 @@ import Hadrian.Expression hiding (Expr, Predicate, Args) import Base import Context (Context, vanillaContext, stageContext, getBuildPath, getStage, getPackage, getWay) +import Oracles.PackageData import Target hiding (builder, inputs, outputs) -- | @Expr a@ is a computation that produces a value of type @Action a@ and can @@ -42,6 +43,14 @@ type Args = H.Args Context Builder type Packages = Expr [Package] type Ways = Expr [Way] +-- | Get a value from the @package-data.mk@ file of the current context. +getPkgData :: (FilePath -> PackageData) -> Expr String +getPkgData key = expr . pkgData . key =<< getBuildPath + +-- | Get a list of values from the @package-data.mk@ file of the current context. +getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] +getPkgDataList key = expr . pkgDataList . key =<< getBuildPath + -- | Is the build currently in the provided stage? stage :: Stage -> Predicate stage s = (s ==) <$> getStage diff --git a/src/GHC.hs b/src/GHC.hs index 6d49630..1141030 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -18,7 +18,7 @@ module GHC ( rtsContext, rtsBuildPath, rtsConfIn, -- * Miscellaneous - ghcSplitPath, stripCmdPath, inplaceInstallPath + ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 ) where import Base @@ -192,3 +192,7 @@ rtsBuildPath = buildPath rtsContext rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" +buildDll0 :: Context -> Action Bool +buildDll0 Context {..} = do + windows <- windowsHost + return $ windows && stage == Stage1 && package == compiler diff --git a/src/Settings.hs b/src/Settings.hs index 2b4b0ef..f25265b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -13,8 +13,6 @@ import CommandLine import Expression import Flavour import GHC -import Oracles.PackageData -import Oracles.Setting import {-# SOURCE #-} Settings.Default import Settings.Flavours.Development import Settings.Flavours.Performance @@ -38,12 +36,6 @@ getPackages = expr flavour >>= packages stagePackages :: Stage -> Action [Package] stagePackages stage = interpretInContext (stageContext stage) getPackages -getPkgData :: (FilePath -> PackageData) -> Expr String -getPkgData key = expr . pkgData . key =<< getBuildPath - -getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] -getPkgDataList key = expr . pkgDataList . key =<< getBuildPath - hadrianFlavours :: [Flavour] hadrianFlavours = [ defaultFlavour, developmentFlavour Stage1, developmentFlavour Stage2 @@ -154,8 +146,3 @@ stage1Only = defaultStage1Only -- | Install's DESTDIR setting. destDir :: FilePath destDir = defaultDestDir - -buildDll0 :: Context -> Action Bool -buildDll0 Context {..} = do - windows <- windowsHost - return $ windows && stage == Stage1 && package == compiler From git at git.haskell.org Fri Oct 27 00:56:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop experimental code for #174. (64ae7fe) Message-ID: <20171027005601.A8AB83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/64ae7fe8fd907dffd6b6221b95111d24f1bf6372/ghc >--------------------------------------------------------------- commit 64ae7fe8fd907dffd6b6221b95111d24f1bf6372 Author: Andrey Mokhov Date: Tue Apr 26 00:25:12 2016 +0100 Drop experimental code for #174. >--------------------------------------------------------------- 64ae7fe8fd907dffd6b6221b95111d24f1bf6372 src/Rules/Compile.hs | 24 ++++-------------------- src/Settings/Builders/Ghc.hs | 12 ++++-------- src/Settings/User.hs | 13 ++++--------- 3 files changed, 12 insertions(+), 37 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index a3c970d..93503bd 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -12,21 +12,9 @@ compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context - path "*" <.> hisuf way %> \hi -> - if compileInterfaceFilesSeparately - then do - (src, deps) <- dependencies path $ hi -<.> osuf way - need $ src : deps - buildWithResources rs $ Target context (Ghc Compile stage) [src] [hi] - else need [ hi -<.> osuf way ] + path "*" <.> hisuf way %> \hi -> need [ hi -<.> osuf way ] - path "*" <.> hibootsuf way %> \hiboot -> - if compileInterfaceFilesSeparately - then do - (src, deps) <- dependencies path $ hiboot -<.> obootsuf way - need $ src : deps - buildWithResources rs $ Target context (Ghc Compile stage) [src] [hiboot] - else need [ hiboot -<.> obootsuf way ] + path "*" <.> hibootsuf way %> \hiboot -> need [ hiboot -<.> obootsuf way ] -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?) path "*" <.> osuf way %> \obj -> do @@ -36,15 +24,11 @@ compilePackage rs context at Context {..} = do need $ src : deps build $ Target context (Cc Compile stage) [src] [obj] else do - if compileInterfaceFilesSeparately && "//*.hs" ?== src - then need $ (obj -<.> hisuf way) : src : deps - else need $ src : deps + need $ src : deps buildWithResources rs $ Target context (Ghc Compile stage) [src] [obj] -- TODO: get rid of these special cases path "*" <.> obootsuf way %> \obj -> do (src, deps) <- dependencies path obj - if compileInterfaceFilesSeparately - then need $ (obj -<.> hibootsuf way) : src : deps - else need $ src : deps + need $ src : deps buildWithResources rs $ Target context (Ghc Compile stage) [src] [obj] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 7152526..8dabda6 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -18,16 +18,13 @@ import Settings.Builders.Common (cIncludeArgs) -- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ -- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) --- TODO: Simplify ghcBuilderArgs :: Args ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do output <- getOutput stage <- getStage way <- getWay when (stage > Stage0) . lift $ needTouchy - let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] - buildHi = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf] - buildProg = not (buildObj || buildHi) + let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -35,11 +32,10 @@ ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , buildProg ? ghcLinkArgs - , not buildProg ? arg "-c" + , not buildObj ? ghcLinkArgs + , buildObj ? arg "-c" , append =<< getInputs - , buildHi ? append ["-fno-code", "-fwrite-interface"] - , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ] + , arg "-o", arg =<< getOutput ] ghcLinkArgs :: Args ghcLinkArgs = stagedBuilder (Ghc Link) ? do diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 6fc5536..9f2302b 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -1,9 +1,8 @@ module Settings.User ( - buildRootPath, trackBuildSystem, compileInterfaceFilesSeparately, - userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, - integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, - ghcDebugged, dynamicGhcPrograms, laxDependencies, verboseCommands, - turnWarningsIntoErrors, splitObjects + buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays, + userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, + ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, + laxDependencies, verboseCommands, turnWarningsIntoErrors, splitObjects ) where import Base @@ -94,7 +93,3 @@ verboseCommands = return False -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False - --- | Decouple the compilation of @*.hi@ and @*.o@ files by setting to True. -compileInterfaceFilesSeparately :: Bool -compileInterfaceFilesSeparately = False From git at git.haskell.org Fri Oct 27 00:56:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move systemBuilderPath to GHC (8fc676e) Message-ID: <20171027005601.B41423A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8fc676e400d02448dea520c0977d64c140b1a560/ghc >--------------------------------------------------------------- commit 8fc676e400d02448dea520c0977d64c140b1a560 Author: Andrey Mokhov Date: Wed Aug 16 15:24:08 2017 +0100 Move systemBuilderPath to GHC >--------------------------------------------------------------- 8fc676e400d02448dea520c0977d64c140b1a560 src/GHC.hs | 42 +++++++++++++++++++++++++++++++++++++++++- src/Settings.hs | 39 --------------------------------------- 2 files changed, 41 insertions(+), 40 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 1141030..2210889 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -18,9 +18,12 @@ module GHC ( rtsContext, rtsBuildPath, rtsConfIn, -- * Miscellaneous - ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 + systemBuilderPath, ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 ) where +import Hadrian.Oracles.KeyValue +import Hadrian.Oracles.Path + import Base import Context import Oracles.Setting @@ -118,6 +121,43 @@ builderProvenance = \case where context s p = Just $ vanillaContext s p +-- | Determine the location of a system 'Builder'. +systemBuilderPath :: Builder -> Action FilePath +systemBuilderPath builder = case builder of + Alex -> fromKey "alex" + Ar Stage0 -> fromKey "system-ar" + Ar _ -> fromKey "ar" + Cc _ Stage0 -> fromKey "system-cc" + Cc _ _ -> fromKey "cc" + -- We can't ask configure for the path to configure! + Configure _ -> return "sh configure" + Ghc _ Stage0 -> fromKey "system-ghc" + GhcPkg _ Stage0 -> fromKey "system-ghc-pkg" + Happy -> fromKey "happy" + HsColour -> fromKey "hscolour" + HsCpp -> fromKey "hs-cpp" + Ld -> fromKey "ld" + Make _ -> fromKey "make" + Nm -> fromKey "nm" + Objdump -> fromKey "objdump" + Patch -> fromKey "patch" + Perl -> fromKey "perl" + Ranlib -> fromKey "ranlib" + Tar -> fromKey "tar" + _ -> error $ "No entry for " ++ show builder ++ inCfg + where + inCfg = " in " ++ quote configFile ++ " file." + fromKey key = do + let unpack = fromMaybe . error $ "Cannot find path to builder " + ++ quote key ++ inCfg ++ " Did you skip configure?" + path <- unpack <$> lookupValue configFile key + if null path + then do + unless (isOptional builder) . error $ "Non optional builder " + ++ quote key ++ " is not specified" ++ inCfg + return "" -- TODO: Use a safe interface. + else fixAbsolutePathOnWindows =<< lookupInPath path + -- | Given a 'Context', compute the name of the program that is built in it -- assuming that the corresponding package's type is 'Program'. For example, GHC -- built in 'Stage0' is called @ghc-stage1 at . If the given package is a diff --git a/src/Settings.hs b/src/Settings.hs index f25265b..fdce8a7 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -5,9 +5,6 @@ module Settings ( programContext, integerLibraryName, destDir, stage1Only, buildDll0 ) where -import Hadrian.Oracles.KeyValue -import Hadrian.Oracles.Path - import Context import CommandLine import Expression @@ -68,42 +65,6 @@ knownPackages = sort $ defaultKnownPackages ++ userKnownPackages findKnownPackage :: PackageName -> Maybe Package findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages --- | Determine the location of a system 'Builder'. -systemBuilderPath :: Builder -> Action FilePath -systemBuilderPath builder = case builder of - Alex -> fromKey "alex" - Ar Stage0 -> fromKey "system-ar" - Ar _ -> fromKey "ar" - Cc _ Stage0 -> fromKey "system-cc" - Cc _ _ -> fromKey "cc" - -- We can't ask configure for the path to configure! - Configure _ -> return "sh configure" - Ghc _ Stage0 -> fromKey "system-ghc" - GhcPkg _ Stage0 -> fromKey "system-ghc-pkg" - Happy -> fromKey "happy" - HsColour -> fromKey "hscolour" - HsCpp -> fromKey "hs-cpp" - Ld -> fromKey "ld" - Make _ -> fromKey "make" - Nm -> fromKey "nm" - Objdump -> fromKey "objdump" - Patch -> fromKey "patch" - Perl -> fromKey "perl" - Ranlib -> fromKey "ranlib" - Tar -> fromKey "tar" - _ -> error $ "No system.config entry for " ++ show builder - where - fromKey key = do - let unpack = fromMaybe . error $ "Cannot find path to builder " - ++ quote key ++ " in system.config file. Did you skip configure?" - path <- unpack <$> lookupValue configFile key - if null path - then do - unless (isOptional builder) . error $ "Non optional builder " - ++ quote key ++ " is not specified in system.config file." - return "" -- TODO: Use a safe interface. - else fixAbsolutePathOnWindows =<< lookupInPath path - -- | Determine the location of a 'Builder'. builderPath :: Builder -> Action FilePath builderPath builder = case builderProvenance builder of From git at git.haskell.org Fri Oct 27 00:56:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (366b35b) Message-ID: <20171027005605.C78953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/366b35b27d1a33cb2a752fb0b6c927658496047e/ghc >--------------------------------------------------------------- commit 366b35b27d1a33cb2a752fb0b6c927658496047e Author: Andrey Mokhov Date: Tue Apr 26 00:46:58 2016 +0100 Minor revision. >--------------------------------------------------------------- 366b35b27d1a33cb2a752fb0b6c927658496047e src/Settings/Builders/Ghc.hs | 23 +++++++++++++---------- 1 file changed, 13 insertions(+), 10 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 8dabda6..37fbc34 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,6 +2,8 @@ module Settings.Builders.Ghc ( ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs ) where +import Control.Monad.Trans.Reader + import Base import Expression import GHC @@ -20,11 +22,7 @@ import Settings.Builders.Common (cIncludeArgs) -- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) ghcBuilderArgs :: Args ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do - output <- getOutput - stage <- getStage - way <- getWay - when (stage > Stage0) . lift $ needTouchy - let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf, obootsuf] + needTouchy mconcat [ commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" @@ -32,8 +30,8 @@ ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do , arg "-Wall" , arg "-fwarn-tabs" , splitObjectsArgs - , not buildObj ? ghcLinkArgs - , buildObj ? arg "-c" + , ghcLinkArgs + , stagedBuilder (Ghc Compile) ? arg "-c" , append =<< getInputs , arg "-o", arg =<< getOutput ] @@ -54,10 +52,15 @@ ghcLinkArgs = stagedBuilder (Ghc Link) ? do , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ dir | dir <- libDirs ] ] -needTouchy :: Action () -needTouchy = - whenM windowsHost $ need [fromJust $ programPath (vanillaContext Stage0 touchy)] +-- TODO: Add Touchy builder and use needBuilder. +needTouchy :: ReaderT Target Action () +needTouchy = do + stage <- getStage + windows <- lift $ windowsHost + lift . when (stage > Stage0 && windows) $ + need [fromJust $ programPath (vanillaContext Stage0 touchy)] +-- TODO: Add GhcSplit builder and use needBuilder. splitObjectsArgs :: Args splitObjectsArgs = splitObjects ? do lift $ need [ghcSplit] From git at git.haskell.org Fri Oct 27 00:56:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out cabal parsing functionality into the library (4a46d14) Message-ID: <20171027005605.E1EA23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a46d14ec3631672d2a3733c45f0aa61eb861eab/ghc >--------------------------------------------------------------- commit 4a46d14ec3631672d2a3733c45f0aa61eb861eab Author: Andrey Mokhov Date: Wed Aug 16 22:18:45 2017 +0100 Factor out cabal parsing functionality into the library See #347 >--------------------------------------------------------------- 4a46d14ec3631672d2a3733c45f0aa61eb861eab hadrian.cabal | 1 + src/Hadrian/Haskell/Cabal.hs | 38 ++++++++++++++++++++++++++++++++++++++ src/Rules/Cabal.hs | 31 ++++++------------------------- src/Settings/Packages/GhcCabal.hs | 13 ++----------- 4 files changed, 47 insertions(+), 36 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 8ad971f..1520881 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -27,6 +27,7 @@ executable hadrian , Flavour , GHC , Hadrian.Expression + , Hadrian.Haskell.Cabal , Hadrian.Oracles.ArgsHash , Hadrian.Oracles.DirectoryContents , Hadrian.Oracles.KeyValue diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs new file mode 100644 index 0000000..b8f874c --- /dev/null +++ b/src/Hadrian/Haskell/Cabal.hs @@ -0,0 +1,38 @@ +module Hadrian.Haskell.Cabal (readCabal, cabalNameVersion, cabalDependencies) where + +import Development.Shake +import Distribution.Package +import Distribution.PackageDescription +import Distribution.PackageDescription.Parse +import Distribution.Text +import Distribution.Types.CondTree +import Distribution.Verbosity + +-- TODO: Track the values? + +-- | Read a given @.cabal@ file and return the 'GenericPackageDescription'. +readCabal :: FilePath -> Action GenericPackageDescription +readCabal cabal = do + need [cabal] + liftIO $ readGenericPackageDescription silent cabal + +-- | Read a given @.cabal@ file and return the package name and version. +cabalNameVersion :: FilePath -> Action (String, String) +cabalNameVersion cabal = do + identifier <- package . packageDescription <$> readCabal cabal + return (unPackageName $ pkgName identifier, display $ pkgVersion identifier) + +-- | Read a given @.cabal@ file and return the package dependencies. +cabalDependencies :: FilePath -> Action [String] +cabalDependencies cabal = do + gpd <- readCabal cabal + let depsLib = collectDeps $ condLibrary gpd + depsExes = map (collectDeps . Just . snd) $ condExecutables gpd + deps = concat $ depsLib : depsExes + return $ [ unPackageName name | Dependency name _ <- deps ] + +collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] +collectDeps Nothing = [] +collectDeps (Just (CondNode _ deps ifs)) = deps ++ concatMap f ifs + where + f (CondBranch _ t mt) = collectDeps (Just t) ++ collectDeps mt diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index a9a9b51..ab8c6f9 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,11 +1,6 @@ module Rules.Cabal (cabalRules) where -import Distribution.Package as DP -import Distribution.PackageDescription -import Distribution.PackageDescription.Parse -import Distribution.Text -import Distribution.Types.CondTree -import Distribution.Verbosity +import Hadrian.Haskell.Cabal import Base import GHC @@ -18,32 +13,18 @@ cabalRules = do bootPkgs <- stagePackages Stage0 let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do - need [pkgCabalFile pkg] - pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg - let identifier = package . packageDescription $ pd - version = display . pkgVersion $ identifier - return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version + (name, version) <- cabalNameVersion (pkgCabalFile pkg) + return $ name ++ " == " ++ version writeFileChanged out . unlines $ constraints putSuccess $ "| Successfully generated boot package constraints" -- Cache package dependencies. "//" -/- packageDependencies %> \out -> do pkgDeps <- forM (sort knownPackages) $ \pkg -> do - exists <- doesFileExist $ pkgCabalFile pkg + exists <- doesFileExist (pkgCabalFile pkg) if not exists then return $ pkgNameString pkg else do - need [pkgCabalFile pkg] - pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg - let depsLib = collectDeps $ condLibrary pd - depsExes = map (collectDeps . Just . snd) $ condExecutables pd - deps = concat $ depsLib : depsExes - depNames = [ unPackageName name | Dependency name _ <- deps ] - return . unwords $ pkgNameString pkg : (sort depNames \\ [pkgNameString pkg]) + deps <- sort <$> cabalDependencies (pkgCabalFile pkg) + return . unwords $ pkgNameString pkg : (deps \\ [pkgNameString pkg]) writeFileChanged out $ unlines pkgDeps putSuccess $ "| Successfully generated package dependencies" - -collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] -collectDeps Nothing = [] -collectDeps (Just (CondNode _ deps ifs)) = deps ++ concatMap f ifs - where - f (CondBranch _ t mt) = collectDeps (Just t) ++ collectDeps mt diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index c7b82ca..79e92c7 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -1,11 +1,6 @@ module Settings.Packages.GhcCabal (ghcCabalPackageArgs) where -import Distribution.Package (pkgVersion) -import Distribution.PackageDescription (packageDescription) -import Distribution.PackageDescription.Parse -import qualified Distribution.PackageDescription as DP -import Distribution.Text (display) -import Distribution.Verbosity (silent) +import Hadrian.Haskell.Cabal import Base import Expression @@ -15,11 +10,7 @@ import Utilities ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do cabalDeps <- expr $ pkgDependencies cabal - expr $ need [pkgCabalFile cabal] - pd <- exprIO . readGenericPackageDescription silent $ pkgCabalFile cabal - let identifier = DP.package . packageDescription $ pd - cabalVersion = display . pkgVersion $ identifier - + (_, cabalVersion) <- expr $ cabalNameVersion (pkgCabalFile cabal) mconcat [ pure [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , arg "--make" From git at git.haskell.org Fri Oct 27 00:56:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge builder, stagedBuilder, builderGhc/Cc into builder. (e532385) Message-ID: <20171027005609.D8BA23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e53238583d64f7218e57d055651087f594e3a98c/ghc >--------------------------------------------------------------- commit e53238583d64f7218e57d055651087f594e3a98c Author: Andrey Mokhov Date: Tue Apr 26 01:04:04 2016 +0100 Merge builder, stagedBuilder, builderGhc/Cc into builder. See #223. >--------------------------------------------------------------- e53238583d64f7218e57d055651087f594e3a98c src/Predicates.hs | 33 ++++++++++++--------------------- src/Settings/Builders/Cc.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Flavours/Quick.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 4 ++-- src/Settings/Packages/Directory.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 4 ++-- src/Settings/Packages/GhcCabal.hs | 4 ++-- src/Settings/Packages/Hp2ps.hs | 4 ++-- src/Settings/Packages/IntegerGmp.hs | 4 ++-- src/Settings/Packages/IservBin.hs | 4 ++-- src/Settings/Packages/Rts.hs | 6 +++--- src/Settings/Packages/RunGhc.hs | 4 ++-- src/Settings/Packages/Touchy.hs | 4 ++-- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/User.hs | 2 +- 18 files changed, 47 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e53238583d64f7218e57d055651087f594e3a98c From git at git.haskell.org Fri Oct 27 00:56:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to MIT license (46a0061) Message-ID: <20171027005609.E6B6E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46a00614fc68bd489f0d21391ceadf85abf3dae3/ghc >--------------------------------------------------------------- commit 46a00614fc68bd489f0d21391ceadf85abf3dae3 Author: Andrey Mokhov Date: Wed Aug 16 23:04:59 2017 +0100 Switch to MIT license >--------------------------------------------------------------- 46a00614fc68bd489f0d21391ceadf85abf3dae3 LICENSE | 42 +++++++++++++++++------------------------- 1 file changed, 17 insertions(+), 25 deletions(-) diff --git a/LICENSE b/LICENSE index fbedb41..ff60fa8 100644 --- a/LICENSE +++ b/LICENSE @@ -1,29 +1,21 @@ -BSD License +MIT License -Copyright (c) 2014, Andrey Mokhov -All rights reserved. +Copyright (c) 2014-2017 Andrey Mokhov -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are met: +Permission is hereby granted, free of charge, to any person obtaining a copy +of this software and associated documentation files (the "Software"), to deal +in the Software without restriction, including without limitation the rights +to use, copy, modify, merge, publish, distribute, sublicense, and/or sell +copies of the Software, and to permit persons to whom the Software is +furnished to do so, subject to the following conditions: -* Redistributions of source code must retain the above copyright notice, this - list of conditions and the following disclaimer. +The above copyright notice and this permission notice shall be included in all +copies or substantial portions of the Software. -* Redistributions in binary form must reproduce the above copyright notice, - this list of conditions and the following disclaimer in the documentation - and/or other materials provided with the distribution. - -* Neither the name of the Hadrian project nor the names of its - contributors may be used to endorse or promote products derived from - this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" -AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE -IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE -DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE -FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL -DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR -SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER -CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, -OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR +IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, +FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE +AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER +LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, +OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE +SOFTWARE. From git at git.haskell.org Fri Oct 27 00:56:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop workaround a Shake getDirectoryFiles bug. (ab5a70f) Message-ID: <20171027005613.6599B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ab5a70fd6fe2e175749b6c55b6395871fe069c77/ghc >--------------------------------------------------------------- commit ab5a70fd6fe2e175749b6c55b6395871fe069c77 Author: Andrey Mokhov Date: Tue Apr 26 01:28:55 2016 +0100 Drop workaround a Shake getDirectoryFiles bug. >--------------------------------------------------------------- ab5a70fd6fe2e175749b6c55b6395871fe069c77 src/Rules/Library.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b74baf8..8e09162 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -97,9 +97,5 @@ extraObjects :: Context -> Action [FilePath] extraObjects (Context _ package _) | package == integerGmp = do orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? - -- FIXME: simplify after Shake's getDirectoryFiles bug is fixed, #168 - exists <- doesDirectoryExist gmpObjects - if exists - then map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] - else return [] + map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:56:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add docs, minor revision (b85602d) Message-ID: <20171027005613.A21E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b85602dc64ccb927839a2368b9636e2bd91cd232/ghc >--------------------------------------------------------------- commit b85602dc64ccb927839a2368b9636e2bd91cd232 Author: Andrey Mokhov Date: Wed Aug 16 23:15:34 2017 +0100 Add docs, minor revision >--------------------------------------------------------------- b85602dc64ccb927839a2368b9636e2bd91cd232 src/Hadrian/Haskell/Cabal.hs | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs index b8f874c..d579de6 100644 --- a/src/Hadrian/Haskell/Cabal.hs +++ b/src/Hadrian/Haskell/Cabal.hs @@ -1,3 +1,14 @@ +----------------------------------------------------------------------------- +-- | +-- Module : Hadrian.Haskell.Cabal +-- Copyright : (c) Andrey Mokhov 2014-2017 +-- License : MIT (see the file LICENSE) +-- Maintainer : andrey.mokhov at gmail.com +-- Stability : experimental +-- +-- Basic functionality for extracting Haskell package metadata stored in +-- @.cabal@ files. +----------------------------------------------------------------------------- module Hadrian.Haskell.Cabal (readCabal, cabalNameVersion, cabalDependencies) where import Development.Shake @@ -8,28 +19,28 @@ import Distribution.Text import Distribution.Types.CondTree import Distribution.Verbosity --- TODO: Track the values? - --- | Read a given @.cabal@ file and return the 'GenericPackageDescription'. +-- | Read a given @.cabal@ file and return the 'GenericPackageDescription'. The +-- @.cabal@ file is tracked. readCabal :: FilePath -> Action GenericPackageDescription readCabal cabal = do need [cabal] liftIO $ readGenericPackageDescription silent cabal --- | Read a given @.cabal@ file and return the package name and version. +-- | Read a given @.cabal@ file and return the package name and version. The +-- @.cabal@ file is tracked. cabalNameVersion :: FilePath -> Action (String, String) cabalNameVersion cabal = do identifier <- package . packageDescription <$> readCabal cabal return (unPackageName $ pkgName identifier, display $ pkgVersion identifier) --- | Read a given @.cabal@ file and return the package dependencies. +-- | Read a given @.cabal@ file and return the package dependencies. The +-- @.cabal@ file is tracked. cabalDependencies :: FilePath -> Action [String] cabalDependencies cabal = do gpd <- readCabal cabal - let depsLib = collectDeps $ condLibrary gpd - depsExes = map (collectDeps . Just . snd) $ condExecutables gpd - deps = concat $ depsLib : depsExes - return $ [ unPackageName name | Dependency name _ <- deps ] + let libDeps = collectDeps (condLibrary gpd) + exeDeps = map (collectDeps . Just . snd) (condExecutables gpd) + return [ unPackageName p | Dependency p _ <- concat (libDeps : exeDeps) ] collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] From git at git.haskell.org Fri Oct 27 00:56:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comment on unicode build info. (ed4cdd8) Message-ID: <20171027005617.5F7153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ed4cdd8c37bcb13e7bf5dda89b1945a29e2ee1bf/ghc >--------------------------------------------------------------- commit ed4cdd8c37bcb13e7bf5dda89b1945a29e2ee1bf Author: Andrey Mokhov Date: Tue Apr 26 01:42:15 2016 +0100 Add comment on unicode build info. [skip ci] >--------------------------------------------------------------- ed4cdd8c37bcb13e7bf5dda89b1945a29e2ee1bf src/Rules/Actions.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5f0fac0..3b12249 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -237,7 +237,8 @@ renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot] -- Minimum total width of the box in characters minimumBoxWidth = 32 - -- FIXME: See Shake #364. + -- TODO: Make this setting configurable? Setting to True by default seems + -- to work poorly with many fonts. useUnicode = False -- Characters to draw the box From git at git.haskell.org Fri Oct 27 00:56:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out file cache functionality into the library (4fca3ae) Message-ID: <20171027005617.BFE683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fca3ae5301a19abc621dc8ec08051c4b2a954ac/ghc >--------------------------------------------------------------- commit 4fca3ae5301a19abc621dc8ec08051c4b2a954ac Author: Andrey Mokhov Date: Thu Aug 17 02:16:45 2017 +0100 Factor out file cache functionality into the library See #347 >--------------------------------------------------------------- 4fca3ae5301a19abc621dc8ec08051c4b2a954ac hadrian.cabal | 2 +- src/Base.hs | 6 ++--- src/Hadrian/Oracles/FileCache.hs | 49 +++++++++++++++++++++++++++++++++++++++ src/Rules.hs | 19 ++++++++------- src/Rules/Cabal.hs | 30 ------------------------ src/Settings/Builders/GhcCabal.hs | 17 ++++++++++++-- src/Utilities.hs | 17 ++++++++++++-- 7 files changed, 93 insertions(+), 47 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 4fca3ae5301a19abc621dc8ec08051c4b2a954ac From git at git.haskell.org Fri Oct 27 00:56:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop laxDependencies. To be replaced by Shake's skip feature. (8d0581e) Message-ID: <20171027005620.D509E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8d0581ed811c1b180981d4a767e3862e5dd490de/ghc >--------------------------------------------------------------- commit 8d0581ed811c1b180981d4a767e3862e5dd490de Author: Andrey Mokhov Date: Tue Apr 26 09:44:41 2016 +0100 Drop laxDependencies. To be replaced by Shake's skip feature. >--------------------------------------------------------------- 8d0581ed811c1b180981d4a767e3862e5dd490de src/Builder.hs | 18 ++++-------------- src/Predicates.hs | 1 - src/Rules/Actions.hs | 6 +++--- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Test.hs | 6 +++--- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/User.hs | 9 +-------- 8 files changed, 14 insertions(+), 32 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 09e4ab9..8f711e0 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -141,21 +141,11 @@ getBuilderPath = lift . builderPath specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath --- TODO: Get rid of laxDependencies -- we no longer need it (use Shake's skip). --- | Make sure a builder exists on the given path and rebuild it if out of date. --- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of --- date (can save a lot of build time when changing GHC). -needBuilder :: Bool -> Builder -> Action () -needBuilder laxDependencies builder = when (isInternal builder) $ do +-- | Make sure a Builder exists on the given path and rebuild it if out of date. +needBuilder :: Builder -> Action () +needBuilder builder = when (isInternal builder) $ do path <- builderPath builder - if laxDependencies && allowOrderOnlyDependency builder - then orderOnly [path] - else need [path] - where - allowOrderOnlyDependency :: Builder -> Bool - allowOrderOnlyDependency = \case - Ghc _ _ -> True - _ -> False + need [path] -- Instances for storing in the Shake database instance Binary CompilerMode diff --git a/src/Predicates.hs b/src/Predicates.hs index 1f87386..0ae18e9 100644 --- a/src/Predicates.hs +++ b/src/Predicates.hs @@ -15,7 +15,6 @@ stage s = (s ==) <$> getStage package :: Package -> Predicate package p = (p ==) <$> getPackage --- TODO: Also add needBuilder, builderPath, etc. -- | Is a particular builder being used? class BuilderLike a where builder :: a -> Predicate diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 3b12249..10bcbd2 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -24,7 +24,7 @@ import Target -- built (that is, track changes in the build system). buildWithResources :: [(Resource, Int)] -> Target -> Action () buildWithResources rs target at Target {..} = do - needBuilder laxDependencies builder + needBuilder builder path <- builderPath builder argList <- interpret target getArgs verbose <- interpret target verboseCommands @@ -140,14 +140,14 @@ applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch need [file] - needBuilder False Patch -- TODO: add a specialised version ~needBuilderFalse? + needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do - needBuilder laxDependencies builder + needBuilder builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ show builder ++ note diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index ae73104..99dda79 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -42,7 +42,7 @@ configureEnvironment = do , builderEnv "NM" Nm ] where builderEnv var bld = do - needBuilder False bld + needBuilder bld path <- builderPath bld return $ AddEnv var path diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 18c328b..8dce6d1 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -53,7 +53,7 @@ configureEnvironment = do , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ] where builderEnv var bld = do - needBuilder False bld + needBuilder bld path <- builderPath bld return $ AddEnv var path diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 0604236..7faf62d 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -15,9 +15,9 @@ import Settings.User testRules :: Rules () testRules = do "validate" ~> do - needBuilder False $ Ghc Compile Stage2 -- TODO: get rid of False - needBuilder False $ GhcPkg Stage1 - needBuilder False $ Hpc + needBuilder $ Ghc Compile Stage2 + needBuilder $ GhcPkg Stage1 + needBuilder Hpc runMakeVerbose "testsuite/tests" ["fast"] "test" ~> do diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 1750604..9f6c6e2 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -127,7 +127,7 @@ with :: Builder -> Args with b = specified b ? do top <- getTopDirectory path <- getBuilderPath b - lift $ needBuilder laxDependencies b + lift $ needBuilder b append [withBuilderKey b ++ top -/- path] withStaged :: (Stage -> Builder) -> Args diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 49a3a1d..b147665 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -2,7 +2,7 @@ module Settings.User ( buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, - laxDependencies, verboseCommands, turnWarningsIntoErrors, splitObjects + verboseCommands, turnWarningsIntoErrors, splitObjects ) where import Base @@ -74,13 +74,6 @@ ghcProfiled = False ghcDebugged :: Bool ghcDebugged = False --- | When laxDependencies is set to True, dependencies on the GHC executable --- are turned into order-only dependencies to avoid needless recompilation when --- making changes to GHC's sources. In certain situations this can lead to build --- failures, in which case you should reset the flag (at least temporarily). -laxDependencies :: Bool -laxDependencies = False - buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock From git at git.haskell.org Fri Oct 27 00:56:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix overlapping build rules and generalise the pattern (e815c5f) Message-ID: <20171027005621.3BCF03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e815c5f5100fa218415e19ea9a577c5428f8ec0a/ghc >--------------------------------------------------------------- commit e815c5f5100fa218415e19ea9a577c5428f8ec0a Author: Andrey Mokhov Date: Thu Aug 17 19:59:54 2017 +0100 Fix overlapping build rules and generalise the pattern See #391 >--------------------------------------------------------------- e815c5f5100fa218415e19ea9a577c5428f8ec0a src/Hadrian/Utilities.hs | 11 ++++++++++- src/Rules/Library.hs | 2 +- src/Rules/Register.hs | 10 ++++------ 3 files changed, 15 insertions(+), 8 deletions(-) diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 3fe389d..0765891 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -25,7 +25,7 @@ module Hadrian.Utilities ( renderUnicorn, -- * Miscellaneous - (<&>), + (<&>), (%%>), -- * Useful re-exports Dynamic, fromDynamic, toDyn, TypeRep, typeOf @@ -116,6 +116,15 @@ a -/- b infixr 6 -/- +-- | Like Shake's '%>' but gives higher priority to longer patterns. Useful +-- in situations when a family of build rules, e.g. @"//*.a"@ and @"//*_p.a"@ +-- can be matched by the same file, such as @library_p.a at . We break the tie +-- by preferring longer matches, which correpond to longer patterns. +(%%>) :: FilePattern -> (FilePath -> Action ()) -> Rules () +p %%> a = priority (fromIntegral (length p) + 1) $ p %> a + +infix 1 %%> + -- | Insert a value into Shake's type-indexed map. insertExtra :: Typeable a => a -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic insertExtra value = Map.insert (typeOf value) (toDyn value) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index f4259fb..f3a162e 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -53,7 +53,7 @@ buildDynamicLib context at Context{..} = do buildPackageLibrary :: Context -> Rules () buildPackageLibrary context at Context {..} = do let libPrefix = "//" ++ contextDir context -/- "libHS" ++ pkgNameString package - libPrefix ++ "*" ++ (waySuffix way <.> "a") %> \a -> do + libPrefix ++ "*" ++ (waySuffix way <.> "a") %%> \a -> do objs <- libraryObjects context asuf <- libsuf way let isLib0 = ("//*-0" ++ asuf) ?== a diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 261f142..cd48d91 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -15,17 +15,15 @@ registerPackage rs context at Context {..} = do -- Packages @ghc-boot@ and @ghc-boot-th@ both match the @ghc-boot*@ -- pattern, therefore we need to use priorities to match the right rule. -- TODO: Get rid of this hack. - priority (fromIntegral . length $ pkgNameString package) $ - "//" ++ stage0PackageDbDir -/- pkgNameString package ++ "*.conf" %> - buildConf rs context + "//" ++ stage0PackageDbDir -/- pkgNameString package ++ "*.conf" %%> + buildConf rs context when (package == ghc) $ "//" ++ stage0PackageDbDir -/- packageDbStamp %> buildStamp rs context when (stage == Stage1) $ do - priority (fromIntegral . length $ pkgNameString package) $ - inplacePackageDbPath -/- pkgNameString package ++ "*.conf" %> - buildConf rs context + inplacePackageDbPath -/- pkgNameString package ++ "*.conf" %%> + buildConf rs context when (package == ghc) $ inplacePackageDbPath -/- packageDbStamp %> buildStamp rs context From git at git.haskell.org Fri Oct 27 00:56:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build with '--integer-simple' on Linux GHC 8.0.2 CI (67ae38d) Message-ID: <20171027005625.1F4D33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/67ae38d6586cf7f528b7b088a97421f76e029e0e/ghc >--------------------------------------------------------------- commit 67ae38d6586cf7f528b7b088a97421f76e029e0e Author: Andrey Mokhov Date: Thu Aug 17 22:06:32 2017 +0100 Build with '--integer-simple' on Linux GHC 8.0.2 CI >--------------------------------------------------------------- 67ae38d6586cf7f528b7b088a97421f76e029e0e .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index c23e92a..4fecbfc 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,7 +2,7 @@ sudo: true matrix: include: - os: linux - env: MODE="--flavour=quickest" + env: MODE="--flavour=quickest --integer-simple" compiler: "GHC 8.0.2" addons: apt: From git at git.haskell.org Fri Oct 27 00:56:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian (b08a8f6) Message-ID: <20171027005624.B14073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b08a8f64c8d6d7137aa470f83e4fe28f9d39aa07/ghc >--------------------------------------------------------------- commit b08a8f64c8d6d7137aa470f83e4fe28f9d39aa07 Author: Andrey Mokhov Date: Wed Apr 27 00:10:35 2016 +0100 Rename to Hadrian [skip ci] >--------------------------------------------------------------- b08a8f64c8d6d7137aa470f83e4fe28f9d39aa07 README.md | 44 +++++++++++++++++++++----------------------- 1 file changed, 21 insertions(+), 23 deletions(-) diff --git a/README.md b/README.md index c61f5c6..375e4f8 100644 --- a/README.md +++ b/README.md @@ -1,20 +1,18 @@ -Shaking up GHC -============== +Hadrian +======= [![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) -This is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based +Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current [`make`-based build system][make]. If you are curious about the rationale and initial ideas behind the project you can find more details on the [wiki page][ghc-shake-wiki] -and in this [blog post][blog-post-1]. +and in this [blog post][blog-post-1]. This project was formerly known as *Shaking-up-GHC*. The new build system can work side-by-side with the existing build system. Note, there is some interaction between them: they put (some) build results in the same directories, e.g. `inplace/bin/ghc-stage1`. -[Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc). - Your first build ---------------- @@ -28,17 +26,17 @@ follow these steps: packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. * Get the sources and run standard configuration scripts. It is important for the build -system to be in the `shake-build` directory of the GHC source tree: +system to be in the `hadrian` directory of the GHC source tree: ```bash git clone --recursive git://git.haskell.org/ghc.git cd ghc - git clone git://github.com/snowleopard/shaking-up-ghc shake-build + git clone git://github.com/snowleopard/hadrian ./boot ./configure # On Windows run ./configure --enable-tarballs-autodownload ``` -* Build GHC using `shake-build/build.sh` or `shake-build/build.bat` (on Windows) instead +* Build GHC using `hadrian/build.sh` or `hadrian/build.bat` (on Windows) instead of `make`. You might want to enable parallelism with `-j`. We will further refer to the build script simply as `build`. If you are interested in building in a Cabal sandbox or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Also @@ -133,20 +131,20 @@ helped me endure and enjoy the project. [make]: https://ghc.haskell.org/trac/ghc/wiki/Building/Architecture [ghc-shake-wiki]: https://ghc.haskell.org/trac/ghc/wiki/Building/Shake [blog-post-1]: https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc -[issues]: https://github.com/snowleopard/shaking-up-ghc/issues +[issues]: https://github.com/snowleopard/hadrian/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild -[windows-build]: https://github.com/snowleopard/shaking-up-ghc/blob/master/doc/windows.md -[build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 +[windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md +[build-artefacts-issue]: https://github.com/snowleopard/hadrian/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 -[user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs -[test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 -[dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 -[validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 -[flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 -[cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 -[install-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/219 -[milestones]: https://github.com/snowleopard/shaking-up-ghc/milestones -[comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 -[doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 -[contributors]: https://github.com/snowleopard/shaking-up-ghc/graphs/contributors +[user-settings]: https://github.com/snowleopard/hadrian/blob/master/src/Settings/User.hs +[test-issue]: https://github.com/snowleopard/hadrian/issues/197 +[dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 +[validation-issue]: https://github.com/snowleopard/hadrian/issues/187 +[flavours-issue]: https://github.com/snowleopard/hadrian/issues/188 +[cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 +[install-issue]: https://github.com/snowleopard/hadrian/issues/219 +[milestones]: https://github.com/snowleopard/hadrian/milestones +[comments-issue]: https://github.com/snowleopard/hadrian/issues/55 +[doc-issue]: https://github.com/snowleopard/hadrian/issues/56 +[contributors]: https://github.com/snowleopard/hadrian/graphs/contributors From git at git.haskell.org Fri Oct 27 00:56:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian. (cf2b1da) Message-ID: <20171027005628.314923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf2b1da44222a8abc3f1d8cbc66c800631348114/ghc >--------------------------------------------------------------- commit cf2b1da44222a8abc3f1d8cbc66c800631348114 Author: Andrey Mokhov Date: Wed Apr 27 00:34:46 2016 +0100 Rename to Hadrian. [skip ci] >--------------------------------------------------------------- cf2b1da44222a8abc3f1d8cbc66c800631348114 shaking-up-ghc.cabal => hadrian.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/shaking-up-ghc.cabal b/hadrian.cabal similarity index 97% rename from shaking-up-ghc.cabal rename to hadrian.cabal index a5e6d22..a2df30a 100644 --- a/shaking-up-ghc.cabal +++ b/hadrian.cabal @@ -1,18 +1,18 @@ -name: shaking-up-ghc +name: hadrian version: 0.1.0.0 synopsis: GHC build system license: BSD3 license-file: LICENSE author: Andrey Mokhov , github: @snowleopard maintainer: Andrey Mokhov , github: @snowleopard -copyright: Andrey Mokhov 2014-2015 +copyright: Andrey Mokhov 2014-2016 category: Development build-type: Simple cabal-version: >=1.10 source-repository head type: git - location: https://github.com/snowleopard/shaking-up-ghc + location: https://github.com/snowleopard/hadrian executable ghc-shake main-is: Main.hs From git at git.haskell.org Fri Oct 27 00:56:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: .bat file tidy up plus shake-0.16 compatibility (#392) (df4848c) Message-ID: <20171027005628.9FEE83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/df4848c98c729212840b7de291dcad15fe679451/ghc >--------------------------------------------------------------- commit df4848c98c729212840b7de291dcad15fe679451 Author: Neil Mitchell Date: Fri Aug 18 00:07:13 2017 +0100 .bat file tidy up plus shake-0.16 compatibility (#392) * Switch from @ to @echo off in the batch files * Make sure the .bat files do setlocal - ensures if it fails you don't keep the directory change * Give RuleResult instances to all the oracles, as required by the forthcoming shake-0.16 >--------------------------------------------------------------- df4848c98c729212840b7de291dcad15fe679451 build.bat | 52 +++++++++++++++++--------------- build.stack.bat | 16 +++++----- src/Hadrian/Oracles/ArgsHash.hs | 3 ++ src/Hadrian/Oracles/DirectoryContents.hs | 2 ++ src/Hadrian/Oracles/FileCache.hs | 2 ++ src/Hadrian/Oracles/KeyValue.hs | 3 ++ src/Hadrian/Oracles/Path.hs | 3 ++ src/Hadrian/Utilities.hs | 7 +++++ src/Oracles/ModuleFiles.hs | 3 ++ 9 files changed, 59 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc df4848c98c729212840b7de291dcad15fe679451 From git at git.haskell.org Fri Oct 27 00:56:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian (2736806) Message-ID: <20171027005631.C103D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/27368067f3c22a5313ab507f5f5beede19bcf9bf/ghc >--------------------------------------------------------------- commit 27368067f3c22a5313ab507f5f5beede19bcf9bf Author: Andrey Mokhov Date: Wed Apr 27 00:37:25 2016 +0100 Rename to Hadrian [skip ci] >--------------------------------------------------------------- 27368067f3c22a5313ab507f5f5beede19bcf9bf LICENSE | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/LICENSE b/LICENSE index 9ee6e34..fbedb41 100644 --- a/LICENSE +++ b/LICENSE @@ -1,6 +1,6 @@ BSD License -Copyright (c) 2015, Andrey Mokhov +Copyright (c) 2014, Andrey Mokhov All rights reserved. Redistribution and use in source and binary forms, with or without @@ -13,7 +13,7 @@ modification, are permitted provided that the following conditions are met: this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. -* Neither the name of Shaking up GHC nor the names of its +* Neither the name of the Hadrian project nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. From git at git.haskell.org Fri Oct 27 00:56:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Package to the library (14aec31) Message-ID: <20171027005632.332053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14aec31f12e398f7cab12e23c95c8eda1d8c9f4a/ghc >--------------------------------------------------------------- commit 14aec31f12e398f7cab12e23c95c8eda1d8c9f4a Author: Andrey Mokhov Date: Fri Aug 18 00:56:33 2017 +0100 Move Package to the library See #347 >--------------------------------------------------------------- 14aec31f12e398f7cab12e23c95c8eda1d8c9f4a hadrian.cabal | 2 +- src/Base.hs | 4 ++-- src/{ => Hadrian/Haskell}/Package.hs | 23 ++++++++++++++--------- 3 files changed, 17 insertions(+), 12 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 7c45af6..93e4707 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -28,6 +28,7 @@ executable hadrian , GHC , Hadrian.Expression , Hadrian.Haskell.Cabal + , Hadrian.Haskell.Package , Hadrian.Oracles.ArgsHash , Hadrian.Oracles.DirectoryContents , Hadrian.Oracles.FileCache @@ -39,7 +40,6 @@ executable hadrian , Oracles.Setting , Oracles.ModuleFiles , Oracles.PackageData - , Package , Rules , Rules.Clean , Rules.Compile diff --git a/src/Base.hs b/src/Base.hs index 8c81706..310d7c4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -15,7 +15,7 @@ module Base ( -- * Basic data types module Builder, - module Package, + module Hadrian.Haskell.Package, module Stage, module Way, @@ -37,9 +37,9 @@ import Development.Shake.Classes import Development.Shake.FilePath import Development.Shake.Util import Hadrian.Utilities +import Hadrian.Haskell.Package import Builder -import Package import Stage import Way diff --git a/src/Package.hs b/src/Hadrian/Haskell/Package.hs similarity index 79% rename from src/Package.hs rename to src/Hadrian/Haskell/Package.hs index 93e8ee0..d7dd3df 100644 --- a/src/Package.hs +++ b/src/Hadrian/Haskell/Package.hs @@ -1,4 +1,4 @@ -module Package ( +module Hadrian.Haskell.Package ( Package (..), PackageName (..), PackageType (..), -- * Queries pkgNameString, pkgCabalFile, @@ -12,20 +12,25 @@ import Development.Shake.FilePath import GHC.Generics import Hadrian.Utilities --- | The name of a Cabal package. +-- | The name of a Haskell package. newtype PackageName = PackageName { fromPackageName :: String } deriving (Binary, Eq, Generic, Hashable, IsString, NFData, Ord, Typeable) -- TODO: Make PackageType more precise, #12. --- | We regard packages as either being libraries or programs. This is bit of a --- convenient lie as Cabal packages can be both, but it works for now. +-- | We regard packages as either being libraries or programs. This is a bit of +-- a convenient lie as Haskell packages can be both, but it works for now. data PackageType = Library | Program deriving Generic -data Package = Package - { pkgName :: PackageName -- ^ Examples: "ghc", "Cabal". - , pkgPath :: FilePath -- ^ pkgPath is the path to the source code relative - -- to the root, e.g. "compiler", "libraries/Cabal/Cabal". - , pkgType :: PackageType -- ^ A library or a program. +-- | A Haskell package. +data Package = Package { + -- | The name of a Haskell package. Examples: @Cabal@, @ghc-bin at . + pkgName :: PackageName, + -- | The path to the package source code relative to the root of the build + -- system. For example, @libraries/Cabal/Cabal@ and @ghc@ are paths to the + -- @Cabal@ and @ghc-bin@ packages in GHC. + pkgPath :: FilePath, + -- | A library (e.g. @Cabal@) or a program (e.g. @ghc-bin@). + pkgType :: PackageType } deriving Generic -- TODO: Get rid of non-derived Show instances. From git at git.haskell.org Fri Oct 27 00:56:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian (0c5fe5b) Message-ID: <20171027005635.854883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c5fe5b08bc591073351b60a5e76c9a0a09ad686/ghc >--------------------------------------------------------------- commit 0c5fe5b08bc591073351b60a5e76c9a0a09ad686 Author: Andrey Mokhov Date: Wed Apr 27 00:39:10 2016 +0100 Rename to Hadrian [skip ci] >--------------------------------------------------------------- 0c5fe5b08bc591073351b60a5e76c9a0a09ad686 doc/windows.md | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 7fc8dcf..7afd97c 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -9,11 +9,11 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ stack exec -- pacman -S gcc binutils git automake-wrapper tar make patch autoconf --noconfirm stack exec -- git clone --recursive git://git.haskell.org/ghc.git cd ghc - stack exec -- git clone git://github.com/snowleopard/shaking-up-ghc shake-build - stack build --stack-yaml=shake-build/stack.yaml --only-dependencies + stack exec -- git clone git://github.com/snowleopard/hadrian + stack build --stack-yaml=hadrian/stack.yaml --only-dependencies stack exec -- perl boot stack exec -- bash configure --enable-tarballs-autodownload - stack exec --stack-yaml=shake-build/stack.yaml -- shake-build/build.bat -j + stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j The entire process should take about an hour. @@ -21,6 +21,6 @@ The entire process should take about an hour. Here are some alternatives that have been considered, but not yet tested. Use the instructions above. -* Use `shake-build/build.bat --setup` to replace `boot` and `configure`. +* Use `hadrian/build.bat --setup` to replace `boot` and `configure`. * The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. * Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:56:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make Package datatype abstract (39a2b89) Message-ID: <20171027005635.E6AEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39a2b89543e584f7349800db14ab6d1182f7c2fc/ghc >--------------------------------------------------------------- commit 39a2b89543e584f7349800db14ab6d1182f7c2fc Author: Andrey Mokhov Date: Fri Aug 18 01:03:42 2017 +0100 Make Package datatype abstract >--------------------------------------------------------------- 39a2b89543e584f7349800db14ab6d1182f7c2fc src/Hadrian/Haskell/Package.hs | 4 ++-- src/Rules/Install.hs | 8 ++++---- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Hadrian/Haskell/Package.hs b/src/Hadrian/Haskell/Package.hs index d7dd3df..cd63589 100644 --- a/src/Hadrian/Haskell/Package.hs +++ b/src/Hadrian/Haskell/Package.hs @@ -1,7 +1,7 @@ module Hadrian.Haskell.Package ( - Package (..), PackageName (..), PackageType (..), + Package, PackageName (..), PackageType (..), -- * Queries - pkgNameString, pkgCabalFile, + pkgName, pkgPath, pkgType, pkgNameString, pkgCabalFile, -- * Helpers for constructing and using 'Package's setPath, topLevel, library, utility, setType, isLibrary, isProgram ) where diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 1d0cd9e..a13e8eb 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -181,7 +181,7 @@ installPackages = do installLibPkgs <- topsortPackages (filter isLibrary activePackages) - forM_ installLibPkgs $ \pkg at Package{..} -> do + forM_ installLibPkgs $ \pkg -> do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg @@ -211,7 +211,7 @@ installPackages = do pref <- setting InstallPrefix unit $ cmd ghcCabalInplace [ "copy" - , pkgPath + , pkgPath pkg , installDistDir , strip , destDir @@ -228,7 +228,7 @@ installPackages = do , installedPackageConf, "update" , confPath ] - forM_ installLibPkgs $ \pkg at Package{..} -> do + forM_ installLibPkgs $ \pkg -> do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg @@ -241,7 +241,7 @@ installPackages = do r <- relocatableBuild unit $ cmd ghcCabalInplace [ "register" - , pkgPath + , pkgPath pkg , installDistDir , installedGhcReal , installedGhcPkgReal From git at git.haskell.org Fri Oct 27 00:56:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian. (11759a8) Message-ID: <20171027005639.380583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/11759a8ee0d735e2331d4d617031dd3dcc3069f6/ghc >--------------------------------------------------------------- commit 11759a8ee0d735e2331d4d617031dd3dcc3069f6 Author: Andrey Mokhov Date: Wed Apr 27 00:45:38 2016 +0100 Rename to Hadrian. [skip ci] >--------------------------------------------------------------- 11759a8ee0d735e2331d4d617031dd3dcc3069f6 .travis.yml | 18 +++++++++--------- appveyor.yml | 6 +++--- 2 files changed, 12 insertions(+), 12 deletions(-) diff --git a/.travis.yml b/.travis.yml index d6092fb..6832cd8 100644 --- a/.travis.yml +++ b/.travis.yml @@ -47,22 +47,22 @@ install: # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake # ".git" directory into the appropriate location, and perform a hard reset # in order to regenerate the GHC-Shake files. - - mkdir ghc/shake-build - - mv .git ghc/shake-build - - ( cd ghc/shake-build && git reset --hard HEAD ) + - mkdir ghc/hadrian + - mv .git ghc/hadrian + - ( cd ghc/hadrian && git reset --hard HEAD ) - - ( cd ghc/shake-build && cabal install --only-dependencies ) - - ( cd ghc/shake-build && cabal configure ) + - ( cd ghc/hadrian && cabal install --only-dependencies ) + - ( cd ghc/hadrian && cabal configure ) - ( cd ghc && ./boot ) - ( cd ghc && ./configure ) - - cat ghc/shake-build/cfg/system.config + - cat ghc/hadrian/cfg/system.config - ghc-pkg list script: - - ( cd ghc/shake-build && cabal haddock --internal ) - - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress --profile=- --flavour=quick $TARGET + - ( cd ghc/hadrian && cabal haddock --internal ) + - ./ghc/hadrian/build.sh selftest + - ./ghc/hadrian/build.sh -j --no-progress --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index 6cc17b6..3918779 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -1,4 +1,4 @@ -clone_folder: "C:\\msys64\\home\\ghc\\shake-build" +clone_folder: "C:\\msys64\\home\\ghc\\hadrian" environment: global: STACK_ROOT: "c:\\sr" @@ -30,7 +30,7 @@ install: - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c65e0982e8fee2a23438e46de22023fb9d5836d/ghc >--------------------------------------------------------------- commit 7c65e0982e8fee2a23438e46de22023fb9d5836d Author: Andrey Mokhov Date: Fri Aug 18 02:37:00 2017 +0100 Simplify Package data type >--------------------------------------------------------------- 7c65e0982e8fee2a23438e46de22023fb9d5836d hadrian.cabal | 1 - src/Context.hs | 4 +- src/GHC.hs | 138 ++++++++++++++++++++++---------------- src/Hadrian/Haskell/Package.hs | 105 ++++++++++++++--------------- src/Rules/Data.hs | 2 +- src/Rules/Documentation.hs | 3 +- src/Rules/Generate.hs | 4 +- src/Rules/Install.hs | 3 +- src/Rules/Library.hs | 8 +-- src/Rules/Program.hs | 4 +- src/Rules/Register.hs | 4 +- src/Settings.hs | 4 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Utilities.hs | 10 +-- 15 files changed, 153 insertions(+), 141 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 7c65e0982e8fee2a23438e46de22023fb9d5836d From git at git.haskell.org Fri Oct 27 00:56:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename project executable to hadrian. (affe0bd) Message-ID: <20171027005642.AEDB73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/affe0bd9add35be2a801a68a0cc1309f2bdb176a/ghc >--------------------------------------------------------------- commit affe0bd9add35be2a801a68a0cc1309f2bdb176a Author: Andrey Mokhov Date: Wed Apr 27 00:50:27 2016 +0100 Rename project executable to hadrian. >--------------------------------------------------------------- affe0bd9add35be2a801a68a0cc1309f2bdb176a build.cabal-new.sh | 8 ++++---- build.cabal.sh | 2 +- build.stack.sh | 2 +- hadrian.cabal | 2 +- src/Environment.hs | 2 +- 5 files changed, 8 insertions(+), 8 deletions(-) diff --git a/build.cabal-new.sh b/build.cabal-new.sh index 96c194e..bca8c7c 100755 --- a/build.cabal-new.sh +++ b/build.cabal-new.sh @@ -38,16 +38,16 @@ mkdir -p "$root/.shake" # Notes/Random thoughts: # # - if ghc.git had a top-level `cabal.project` file, we could maybe avoid the -# boilerplate above, as we could simply say `cabal exec ghc-shake` from within +# boilerplate above, as we could simply say `cabal exec hadrian` from within # any GHC folder not shadowed by a nearer shadowing `cabal.project` file. pushd "$root/" -cabal new-build --disable-profiling --disable-documentation -j exe:ghc-shake +cabal new-build --disable-profiling --disable-documentation -j exe:hadrian -PKGVER="$(awk '/^version:/ { print $2 }' shaking-up-ghc.cabal)" +PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" -cp -v "$root/dist-newstyle/build/shaking-up-ghc-${PKGVER}/build/ghc-shake/ghc-shake" \ +cp -v "$root/dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ "$root/.shake/build" popd diff --git a/build.cabal.sh b/build.cabal.sh index 5f20c1b..f2e320e 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -40,7 +40,7 @@ if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then --disable-shared fi -cabal run ghc-shake -- \ +cabal run hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ --colour \ diff --git a/build.stack.sh b/build.stack.sh index 578e7eb..b5607b1 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -33,7 +33,7 @@ cd "$absoluteRoot" stack build --no-library-profiling -stack exec ghc-shake -- \ +stack exec hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ --colour \ diff --git a/hadrian.cabal b/hadrian.cabal index a2df30a..4bf5a4c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -14,7 +14,7 @@ source-repository head type: git location: https://github.com/snowleopard/hadrian -executable ghc-shake +executable hadrian main-is: Main.hs hs-source-dirs: src other-modules: Base diff --git a/src/Environment.hs b/src/Environment.hs index e674f83..d4d9853 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -13,7 +13,7 @@ setupEnvironment = do -- in MinGW if PWD is set to a Windows "C:\\" style path then configure -- `pwd` will return the Windows path, and then modifying $PATH will fail. - -- See https://github.com/snowleopard/shaking-up-ghc/issues/189 for details. + -- See https://github.com/snowleopard/hadrian/issues/189 for details. unsetEnv "PWD" -- On Windows, some path variables start a prefix like "C:\\" which may From git at git.haskell.org Fri Oct 27 00:56:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move RTS-specific paths to Settings.Packages.Rts (f0fb1be) Message-ID: <20171027005643.081683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f0fb1be5d3c234d40314f4743d1e45f0d891718e/ghc >--------------------------------------------------------------- commit f0fb1be5d3c234d40314f4743d1e45f0d891718e Author: Andrey Mokhov Date: Fri Aug 18 02:46:30 2017 +0100 Move RTS-specific paths to Settings.Packages.Rts >--------------------------------------------------------------- f0fb1be5d3c234d40314f4743d1e45f0d891718e src/GHC.hs | 16 ---------------- src/Rules/Data.hs | 1 + src/Rules/Generate.hs | 1 + src/Rules/Program.hs | 1 + src/Settings/Packages/Rts.hs | 17 ++++++++++++++++- 5 files changed, 19 insertions(+), 17 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 13142bd..0b3d035 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -13,9 +13,6 @@ module GHC ( -- * Package information builderProvenance, programName, nonCabalContext, nonHsMainPackage, autogenPath, - -- * RTS library - rtsContext, rtsBuildPath, rtsConfIn, - -- * Miscellaneous systemBuilderPath, ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 ) where @@ -239,19 +236,6 @@ stripCmdPath = do return ":" -- HACK: from the make-based system, see the ref above _ -> return "strip" --- TODO: Move to RTS-specific package? --- | RTS is considered a Stage1 package. This determines RTS build directory. -rtsContext :: Context -rtsContext = vanillaContext Stage1 rts - --- | Path to the RTS build directory. -rtsBuildPath :: Action FilePath -rtsBuildPath = buildPath rtsContext - --- | Path to RTS package configuration file, to be processed by HsCpp. -rtsConfIn :: FilePath -rtsConfIn = pkgPath rts -/- "package.conf.in" - buildDll0 :: Context -> Action Bool buildDll0 Context {..} = do windows <- windowsHost diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 975f3fa..ef2f017 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -6,6 +6,7 @@ import Expression import GHC import Oracles.Setting import Rules.Generate +import Settings.Packages.Rts import Target import Utilities diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 0057bf8..e5dffcc 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -14,6 +14,7 @@ import Oracles.Setting import Rules.Gmp import Rules.Libffi import Settings +import Settings.Packages.Rts import Target import Utilities diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index c88ddd8..efdd7f4 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -11,6 +11,7 @@ import Oracles.PackageData import Oracles.Setting import Rules.Wrappers import Settings +import Settings.Packages.Rts import Target import Utilities diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index fe490dd..0ae764f 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,12 +1,27 @@ -module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibrary) where +module Settings.Packages.Rts ( + rtsContext, rtsBuildPath, rtsConfIn, rtsPackageArgs, rtsLibffiLibrary + ) where import Base +import Context (buildPath) import Expression import GHC import Oracles.Flag import Oracles.Setting import Settings +-- | RTS is considered a Stage1 package. This determines RTS build directory. +rtsContext :: Context +rtsContext = vanillaContext Stage1 rts + +-- | Path to the RTS build directory. +rtsBuildPath :: Action FilePath +rtsBuildPath = buildPath rtsContext + +-- | Path to RTS package configuration file, to be processed by HsCpp. +rtsConfIn :: FilePath +rtsConfIn = pkgPath rts -/- "package.conf.in" + rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do useSystemFfi <- flag UseSystemFfi From git at git.haskell.org Fri Oct 27 00:56:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add TODOs. (c32b33d) Message-ID: <20171027005646.820A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c32b33d53a3952658d714c975832bb84984b5fe5/ghc >--------------------------------------------------------------- commit c32b33d53a3952658d714c975832bb84984b5fe5 Author: Andrey Mokhov Date: Wed Apr 27 00:58:40 2016 +0100 Add TODOs. [skip ci] >--------------------------------------------------------------- c32b33d53a3952658d714c975832bb84984b5fe5 src/Settings/User.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index b147665..ef08df0 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -12,6 +12,7 @@ import Expression import Predicates import Settings.Default +-- TODO: Rename to _build. -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath buildRootPath = ".build" @@ -83,6 +84,7 @@ buildHaddock = return cmdBuildHaddock verboseCommands :: Predicate verboseCommands = return False +-- TODO: Replace with stage2 ? arg "-Werror"? -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False From git at git.haskell.org Fri Oct 27 00:56:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Travis timeout (7231dd5) Message-ID: <20171027005646.C5F4A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7231dd5a3d512bbafbd65aa4ad70ecdf6a924243/ghc >--------------------------------------------------------------- commit 7231dd5a3d512bbafbd65aa4ad70ecdf6a924243 Author: Andrey Mokhov Date: Fri Aug 18 02:50:01 2017 +0100 Fix Travis timeout See #393 >--------------------------------------------------------------- 7231dd5a3d512bbafbd65aa4ad70ecdf6a924243 .travis.yml | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4fecbfc..fdd83d4 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,7 +2,7 @@ sudo: true matrix: include: - os: linux - env: MODE="--flavour=quickest --integer-simple" + env: MODE="--flavour=quickest inplace/bin/ghc-stage1" compiler: "GHC 8.0.2" addons: apt: @@ -28,7 +28,7 @@ matrix: - inplace/bin/ghc-stage2 -e 1+2 - os: linux - env: MODE="--flavour=quickest" + env: MODE="--flavour=quickest --integer-simple" compiler: "GHC 8.2.1" addons: apt: @@ -55,7 +55,7 @@ matrix: - os: osx osx_image: xcode8 - env: MODE="--flavour=quickest --integer-simple" + env: MODE="--flavour=quickest --integer-simple inplace/bin/ghc-stage1" before_install: - brew update - brew install ghc cabal-install @@ -63,7 +63,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- install: # Add Cabal to PATH From git at git.haskell.org Fri Oct 27 00:56:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename shakePath to hadrian. (d2051cd) Message-ID: <20171027005650.5C4F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2051cdb91e00d19b02e7cab47e75411c1a29e33/ghc >--------------------------------------------------------------- commit d2051cdb91e00d19b02e7cab47e75411c1a29e33 Author: Andrey Mokhov Date: Wed Apr 27 00:59:24 2016 +0100 Rename shakePath to hadrian. [skip ci] >--------------------------------------------------------------- d2051cdb91e00d19b02e7cab47e75411c1a29e33 src/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index 871cd3c..b94648e 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -48,7 +48,7 @@ import System.IO -- Build system files and paths shakePath :: FilePath -shakePath = "shake-build" +shakePath = "hadrian" shakeFilesPath :: FilePath shakeFilesPath = shakePath -/- ".db" From git at git.haskell.org Fri Oct 27 00:56:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run ranlib directly (e91b0c2) Message-ID: <20171027005650.A3CDC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e91b0c248df89e26d56bd5c34a48fa4e1aebacbb/ghc >--------------------------------------------------------------- commit e91b0c248df89e26d56bd5c34a48fa4e1aebacbb Author: Andrey Mokhov Date: Fri Aug 18 02:59:59 2017 +0100 Run ranlib directly >--------------------------------------------------------------- e91b0c248df89e26d56bd5c34a48fa4e1aebacbb src/Rules/Install.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index e3f7fe6..12135b4 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -281,8 +281,7 @@ installLibsTo libs dir = do ".a" -> do let out = dir -/- takeFileName lib installData [out] dir - -- TODO: Get rid of meaningless context for certain builder like ranlib - build $ target (stageContext Stage0) Ranlib [out] [out] + runBuilder Ranlib [out] _ -> installData [lib] dir -- ref: includes/ghc.mk From git at git.haskell.org Fri Oct 27 00:56:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename build directory (5f40553) Message-ID: <20171027005653.E2FA13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f405539ffaa3f453d244a53f86e9ee4ee0e8e6e/ghc >--------------------------------------------------------------- commit 5f405539ffaa3f453d244a53f86e9ee4ee0e8e6e Author: Andrey Mokhov Date: Thu Apr 28 23:43:28 2016 +0100 Rename build directory >--------------------------------------------------------------- 5f405539ffaa3f453d244a53f86e9ee4ee0e8e6e src/Settings/User.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index ef08df0..0893579 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -12,10 +12,9 @@ import Expression import Predicates import Settings.Default --- TODO: Rename to _build. -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath -buildRootPath = ".build" +buildRootPath = "_build" -- Control user-specific settings userArgs :: Args From git at git.haskell.org Fri Oct 27 00:56:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Travis (23c8602) Message-ID: <20171027005654.2EC2C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23c860257546f48deb024d2842e2171581f072bb/ghc >--------------------------------------------------------------- commit 23c860257546f48deb024d2842e2171581f072bb Author: Andrey Mokhov Date: Fri Aug 18 11:33:04 2017 +0100 Fix Travis See #393 >--------------------------------------------------------------- 23c860257546f48deb024d2842e2171581f072bb .travis.yml | 7 ------- 1 file changed, 7 deletions(-) diff --git a/.travis.yml b/.travis.yml index fdd83d4..878136c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -23,10 +23,6 @@ matrix: # Build GHC - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- - # Test GHC binary - - cd .. - - inplace/bin/ghc-stage2 -e 1+2 - - os: linux env: MODE="--flavour=quickest --integer-simple" compiler: "GHC 8.2.1" @@ -43,9 +39,6 @@ matrix: - PATH="/opt/cabal/1.22/bin:$PATH" script: - # Run internal Hadrian tests - - ./build.cabal.sh selftest - # Build GHC - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- From git at git.haskell.org Fri Oct 27 00:56:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update CI links (5779105) Message-ID: <20171027005657.5194D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/577910572ec2a02cef51889666d9c40d4e961bf1/ghc >--------------------------------------------------------------- commit 577910572ec2a02cef51889666d9c40d4e961bf1 Author: Andrey Mokhov Date: Fri Apr 29 00:01:49 2016 +0100 Update CI links >--------------------------------------------------------------- 577910572ec2a02cef51889666d9c40d4e961bf1 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 375e4f8..d4adfb1 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Hadrian ======= -[![Linux & OS X status](https://img.shields.io/travis/snowleopard/shaking-up-ghc/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/shaking-up-ghc) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/shaking-up-ghc/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/shaking-up-ghc) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/hadrian/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/hadrian) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current From git at git.haskell.org Fri Oct 27 00:56:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:56:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add mtl, parsec and text as Stage0 packages (d2dddad) Message-ID: <20171027005657.A25D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2dddad4564c6597d497d226fcfbf5e3f7b70c18/ghc >--------------------------------------------------------------- commit d2dddad4564c6597d497d226fcfbf5e3f7b70c18 Author: Andrey Mokhov Date: Fri Aug 18 23:41:24 2017 +0100 Add mtl, parsec and text as Stage0 packages See #393, #395 >--------------------------------------------------------------- d2dddad4564c6597d497d226fcfbf5e3f7b70c18 src/GHC.hs | 15 +++++++++------ src/Settings/Default.hs | 3 +++ src/Settings/Packages/GhcCabal.hs | 2 +- 3 files changed, 13 insertions(+), 7 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0b3d035..2a641e5 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -6,9 +6,9 @@ module GHC ( genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, - parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, - terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, + mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm, + templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix, + win32, xhtml, defaultKnownPackages, -- * Package information builderProvenance, programName, nonCabalContext, nonHsMainPackage, autogenPath, @@ -36,9 +36,9 @@ defaultKnownPackages = , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi - , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm - , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 - , xhtml ] + , mkUserGuidePart, mtl, parsec, parallel, pretty, primitive, process, rts + , runGhc, stm, templateHaskell, terminfo, text, time, touchy, transformers + , unlit, unix, win32, xhtml ] -- | Package definitions, see 'Package'. array = lib "array" @@ -78,6 +78,8 @@ integerSimple = lib "integer-simple" iservBin = prg "iserv-bin" `setPath` "iserv" libffi = top "libffi" mkUserGuidePart = util "mkUserGuidePart" +mtl = lib "mtl" +parsec = lib "parsec" parallel = lib "parallel" pretty = lib "pretty" primitive = lib "primitive" @@ -87,6 +89,7 @@ runGhc = util "runghc" stm = lib "stm" templateHaskell = lib "template-haskell" terminfo = lib "terminfo" +text = lib "text" time = lib "time" touchy = util "touchy" transformers = lib "transformers" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 707bc6f..c97b79f 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -116,7 +116,10 @@ stage0Packages = do , hp2ps , hpc , mkUserGuidePart + , mtl + , parsec , templateHaskell + , text , transformers , unlit ] ++ [ terminfo | not win, not ios ] ++ diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index fb23297..17ea482 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -12,7 +12,7 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do cabalDeps <- expr $ pkgDependencies cabal (_, cabalVersion) <- expr $ cabalNameVersion (pkgCabalFile cabal) mconcat - [ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps ] + [ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps, pkg /= parsec ] , arg "--make" , arg "-j" , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) From git at git.haskell.org Fri Oct 27 00:57:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (9fa04f0) Message-ID: <20171027005701.2F3B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9fa04f066032ce5c8ab753f0aa2a71660dfb466c/ghc >--------------------------------------------------------------- commit 9fa04f066032ce5c8ab753f0aa2a71660dfb466c Author: Andrey Mokhov Date: Sat Aug 19 00:31:39 2017 +0100 Minor revision >--------------------------------------------------------------- 9fa04f066032ce5c8ab753f0aa2a71660dfb466c src/GHC.hs | 8 ++--- src/Hadrian/Haskell/Cabal.hs | 63 ++++++++++++++++++++------------------- src/Hadrian/Haskell/Package.hs | 20 +++++++------ src/Settings.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 4 +-- src/Utilities.hs | 13 ++++---- 7 files changed, 59 insertions(+), 53 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 9fa04f066032ce5c8ab753f0aa2a71660dfb466c From git at git.haskell.org Fri Oct 27 00:57:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build Hadrian in _build. (1317c88) Message-ID: <20171027005700.B492A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1317c886fe1293c3d21389e85ee154790a710cbd/ghc >--------------------------------------------------------------- commit 1317c886fe1293c3d21389e85ee154790a710cbd Author: Andrey Mokhov Date: Sat Apr 30 02:40:55 2016 +0100 Build Hadrian in _build. >--------------------------------------------------------------- 1317c886fe1293c3d21389e85ee154790a710cbd build.bat | 38 +++++++++++++++++++------------------- build.sh | 32 ++++++++++++++++---------------- src/Base.hs | 1 + src/Rules/Clean.hs | 18 ++++++++++-------- 4 files changed, 46 insertions(+), 43 deletions(-) diff --git a/build.bat b/build.bat index 2f6d4cd..19a2a05 100644 --- a/build.bat +++ b/build.bat @@ -1,24 +1,24 @@ @cd %~dp0 - at mkdir .shake 2> nul + at mkdir ../_build 2> nul - at set ghcArgs=--make ^ - -Wall ^ - -fno-warn-name-shadowing ^ - -XRecordWildCards ^ - src/Main.hs ^ - -threaded ^ - -isrc ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=.shake ^ - -j ^ - -O ^ - -o .shake/build + at set ghcArgs=--make ^ + -Wall ^ + -fno-warn-name-shadowing ^ + -XRecordWildCards ^ + src/Main.hs ^ + -threaded ^ + -isrc ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=../_build/hadrian ^ + -j ^ + -O ^ + -o ../_build/hadrian - at set shakeArgs=--lint ^ - --directory ^ - ".." ^ - %* + at set hadrianArgs=--lint ^ + --directory ^ + ".." ^ + %* @ghc %ghcArgs% @@ -27,4 +27,4 @@ @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains @set GHC_PACKAGE_PATH= - at .shake\build %shakeArgs% + at ..\_build\hadrian %hadrianArgs% diff --git a/build.sh b/build.sh index 95de2e6..8b53f81 100755 --- a/build.sh +++ b/build.sh @@ -30,22 +30,22 @@ function rl { root="$(dirname "$(rl "$0")")" -mkdir -p "$root/.shake" - -ghc \ - "$root/src/Main.hs" \ - -Wall \ - -fno-warn-name-shadowing \ - -XRecordWildCards \ - -i"$root/src" \ - -rtsopts \ - -with-rtsopts=-I0 \ - -threaded \ - -outputdir="$root/.shake" \ - -j -O \ - -o "$root/.shake/build" - -"$root/.shake/build" \ +mkdir -p "$root/../_build" + +ghc \ + "$root/src/Main.hs" \ + -Wall \ + -fno-warn-name-shadowing \ + -XRecordWildCards \ + -i"$root/src" \ + -rtsopts \ + -with-rtsopts=-I0 \ + -threaded \ + -outputdir="$root/../_build/hadrian" \ + -j -O \ + -o "$root/../_build/hadrian" + +"$root/../_build/hadrian" \ --lint \ --directory "$root/.." \ --colour \ diff --git a/src/Base.hs b/src/Base.hs index b94648e..53bb197 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -50,6 +50,7 @@ import System.IO shakePath :: FilePath shakePath = "hadrian" +-- TODO: Move to buildRootPath. shakeFilesPath :: FilePath shakeFilesPath = shakePath -/- ".db" diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index ea1cc37..357ac34 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -9,17 +9,19 @@ import Settings.Paths import Settings.User import Stage +clean :: FilePath -> Action () +clean dir = do + putBuild $ "| Remove files in " ++ dir ++ "..." + removeDirectoryIfExists dir + cleanRules :: Rules () cleanRules = do "clean" ~> do - putBuild $ "| Remove files in " ++ buildRootPath ++ "..." - liftIO $ removeFiles buildRootPath ["//*"] - putBuild $ "| Remove files in " ++ programInplacePath ++ "..." - liftIO $ removeFiles programInplacePath ["//*"] - putBuild $ "| Remove files in inplace/lib..." - liftIO $ removeFiles "inplace/lib" ["//*"] - putBuild $ "| Remove files in " ++ derivedConstantsPath ++ "..." - liftIO $ removeFiles derivedConstantsPath ["//*"] + forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) + clean (buildRootPath -/- "hadrian") + clean programInplacePath + clean "inplace/lib" + clean derivedConstantsPath forM_ includesDependencies $ \file -> do putBuild $ "| Remove " ++ file removeFileIfExists file From git at git.haskell.org Fri Oct 27 00:57:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Appveyor CI. (f76a8be) Message-ID: <20171027005704.848233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f76a8bea7b7b5d797880621af089f9ee22cc1035/ghc >--------------------------------------------------------------- commit f76a8bea7b7b5d797880621af089f9ee22cc1035 Author: Andrey Mokhov Date: Sat Apr 30 13:01:49 2016 +0100 Fix Appveyor CI. >--------------------------------------------------------------- f76a8bea7b7b5d797880621af089f9ee22cc1035 appveyor.yml | 3 +++ 1 file changed, 3 insertions(+) diff --git a/appveyor.yml b/appveyor.yml index 3918779..8850273 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -36,6 +36,9 @@ install: - alex --version - happy --version - stack exec -- ghc-pkg list + - mkdir _build + - cd _build + - mkdir hadrian build_script: - cd C:\msys64\home\ghc\hadrian From git at git.haskell.org Fri Oct 27 00:57:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop double installation of Hadrian dependencies (48ad1e7) Message-ID: <20171027005705.2CDAB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/48ad1e76030a4b8054641a0e7875c5921c2d6658/ghc >--------------------------------------------------------------- commit 48ad1e76030a4b8054641a0e7875c5921c2d6658 Author: Andrey Mokhov Date: Sat Aug 19 00:39:20 2017 +0100 Drop double installation of Hadrian dependencies See #393 >--------------------------------------------------------------- 48ad1e76030a4b8054641a0e7875c5921c2d6658 .travis.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 878136c..48ed171 100644 --- a/.travis.yml +++ b/.travis.yml @@ -74,8 +74,7 @@ install: # Install all Hadrian and GHC build dependencies - cabal update - - cabal install alex happy ansi-terminal mtl shake quickcheck - + - cabal install alex happy # Travis has already cloned Hadrian into ./ and we need to move it # to ./ghc/hadrian -- one way to do it is to move the .git directory From git at git.haskell.org Fri Oct 27 00:57:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Travis CI. (a37ad75) Message-ID: <20171027005708.6FC1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a37ad7507e8fef44d94e7e339c521e272bcdaa7e/ghc >--------------------------------------------------------------- commit a37ad7507e8fef44d94e7e339c521e272bcdaa7e Author: Andrey Mokhov Date: Sat Apr 30 13:03:56 2016 +0100 Fix Travis CI. >--------------------------------------------------------------- a37ad7507e8fef44d94e7e339c521e272bcdaa7e .travis.yml | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.travis.yml b/.travis.yml index 6832cd8..251f6ba 100644 --- a/.travis.yml +++ b/.travis.yml @@ -48,6 +48,8 @@ install: # ".git" directory into the appropriate location, and perform a hard reset # in order to regenerate the GHC-Shake files. - mkdir ghc/hadrian + - mkdir ghc/_build + - mkdir ghc/_build/hadrian - mv .git ghc/hadrian - ( cd ghc/hadrian && git reset --hard HEAD ) From git at git.haskell.org Fri Oct 27 00:57:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix install rules by untracking copy files and use relative path (#396) (942ed27) Message-ID: <20171027005709.301483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/942ed27a622576252ef7178040f0b1fdbf08ca1c/ghc >--------------------------------------------------------------- commit 942ed27a622576252ef7178040f0b1fdbf08ca1c Author: Zhen Zhang Date: Sat Aug 19 09:39:25 2017 +0800 Fix install rules by untracking copy files and use relative path (#396) >--------------------------------------------------------------- 942ed27a622576252ef7178040f0b1fdbf08ca1c src/Hadrian/Oracles/DirectoryContents.hs | 10 +++++++++- src/Rules/Install.hs | 8 +++++--- 2 files changed, 14 insertions(+), 4 deletions(-) diff --git a/src/Hadrian/Oracles/DirectoryContents.hs b/src/Hadrian/Oracles/DirectoryContents.hs index 19a5192..f302af9 100644 --- a/src/Hadrian/Oracles/DirectoryContents.hs +++ b/src/Hadrian/Oracles/DirectoryContents.hs @@ -1,6 +1,6 @@ {-# LANGUAGE TypeFamilies #-} module Hadrian.Oracles.DirectoryContents ( - directoryContents, copyDirectoryContents, directoryContentsOracle, + directoryContents, copyDirectoryContents, directoryContentsOracle, copyDirectoryContentsUntracked, Match (..), matches, matchAll ) where @@ -45,6 +45,14 @@ copyDirectoryContents expr source target = do let cp file = copyFile file $ target -/- makeRelative source file mapM_ cp =<< directoryContents expr source +-- | Copy the contents of the source directory that matches a given 'Match' +-- expression into the target directory. The copied contents is untracked. +copyDirectoryContentsUntracked :: Match -> FilePath -> FilePath -> Action () +copyDirectoryContentsUntracked expr source target = do + putProgressInfo =<< renderAction "Copy directory contents (untracked)" source target + let cp file = copyFileUntracked file $ target -/- makeRelative source file + mapM_ cp =<< directoryContents expr source + newtype DirectoryContents = DirectoryContents (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) type instance RuleResult DirectoryContents = [FilePath] diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 12135b4..2400933 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -186,7 +186,9 @@ installPackages = do withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg top <- topDirectory - installDistDir <- (top -/-) <$> buildPath context + installDistDir <- buildPath context + let absInstallDistDir = top -/- installDistDir + need =<< packageTargets stage pkg docDir <- installDocDir ghclibDir <- installGhcLibDir @@ -203,7 +205,7 @@ installPackages = do need [cabalFile, pkgConf] -- TODO: check if need pkgConf -- HACK (#318): copy stuff back to the place favored by ghc-cabal - quietly $ copyDirectoryContents (Not excluded) + quietly $ copyDirectoryContentsUntracked (Not excluded) installDistDir (installDistDir -/- "build") whenM (isSpecified HsColour) $ @@ -212,7 +214,7 @@ installPackages = do pref <- setting InstallPrefix unit $ cmd ghcCabalInplace [ "copy" , pkgPath pkg - , installDistDir + , absInstallDistDir , strip , destDir , pref From git at git.haskell.org Fri Oct 27 00:57:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Hadrian executable to /hadrian. (666f5c2) Message-ID: <20171027005712.0A4AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/666f5c246d0465fd7c11bce4dadeacd46152edf5/ghc >--------------------------------------------------------------- commit 666f5c246d0465fd7c11bce4dadeacd46152edf5 Author: Andrey Mokhov Date: Sat Apr 30 14:35:22 2016 +0100 Move Hadrian executable to /hadrian. >--------------------------------------------------------------- 666f5c246d0465fd7c11bce4dadeacd46152edf5 .gitignore | 5 ++++- .travis.yml | 2 -- appveyor.yml | 3 --- build.bat | 6 +++--- build.sh | 6 +++--- src/Rules/Clean.hs | 3 +-- 6 files changed, 11 insertions(+), 14 deletions(-) diff --git a/.gitignore b/.gitignore index 967be07..b7bfddb 100644 --- a/.gitignore +++ b/.gitignore @@ -1,7 +1,10 @@ -/.shake/ /.db/ cfg/system.config +# build.bat and build.sh specific +/hadrian +/hadrian.exe + # build.cabal.sh specific /dist/ /.cabal-sandbox/ diff --git a/.travis.yml b/.travis.yml index 251f6ba..6832cd8 100644 --- a/.travis.yml +++ b/.travis.yml @@ -48,8 +48,6 @@ install: # ".git" directory into the appropriate location, and perform a hard reset # in order to regenerate the GHC-Shake files. - mkdir ghc/hadrian - - mkdir ghc/_build - - mkdir ghc/_build/hadrian - mv .git ghc/hadrian - ( cd ghc/hadrian && git reset --hard HEAD ) diff --git a/appveyor.yml b/appveyor.yml index 8850273..3918779 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -36,9 +36,6 @@ install: - alex --version - happy --version - stack exec -- ghc-pkg list - - mkdir _build - - cd _build - - mkdir hadrian build_script: - cd C:\msys64\home\ghc\hadrian diff --git a/build.bat b/build.bat index 19a2a05..f9f0b9a 100644 --- a/build.bat +++ b/build.bat @@ -1,5 +1,5 @@ @cd %~dp0 - at mkdir ../_build 2> nul + at mkdir ../_build/hadrian 2> nul @set ghcArgs=--make ^ -Wall ^ @@ -13,7 +13,7 @@ -outputdir=../_build/hadrian ^ -j ^ -O ^ - -o ../_build/hadrian + -o hadrian @set hadrianArgs=--lint ^ --directory ^ @@ -27,4 +27,4 @@ @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains @set GHC_PACKAGE_PATH= - at ..\_build\hadrian %hadrianArgs% + at hadrian %hadrianArgs% diff --git a/build.sh b/build.sh index 8b53f81..f7d06c2 100755 --- a/build.sh +++ b/build.sh @@ -30,7 +30,7 @@ function rl { root="$(dirname "$(rl "$0")")" -mkdir -p "$root/../_build" +mkdir -p "$root/../_build/hadrian" ghc \ "$root/src/Main.hs" \ @@ -43,9 +43,9 @@ ghc \ -threaded \ -outputdir="$root/../_build/hadrian" \ -j -O \ - -o "$root/../_build/hadrian" + -o "$root/hadrian" -"$root/../_build/hadrian" \ +"$root/hadrian" \ --lint \ --directory "$root/.." \ --colour \ diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 357ac34..0bff316 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -17,8 +17,7 @@ clean dir = do cleanRules :: Rules () cleanRules = do "clean" ~> do - forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) - clean (buildRootPath -/- "hadrian") + clean buildRootPath clean programInplacePath clean "inplace/lib" clean derivedConstantsPath From git at git.haskell.org Fri Oct 27 00:57:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve infrastructure for Cabal file parsing (4b6707a) Message-ID: <20171027005712.B09213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b6707a616478a0f664585a49de0d0ed6431d231/ghc >--------------------------------------------------------------- commit 4b6707a616478a0f664585a49de0d0ed6431d231 Author: Andrey Mokhov Date: Sat Aug 19 03:45:33 2017 +0100 Improve infrastructure for Cabal file parsing >--------------------------------------------------------------- 4b6707a616478a0f664585a49de0d0ed6431d231 hadrian.cabal | 4 +- src/Base.hs | 14 ++---- src/GHC.hs | 2 +- src/Hadrian/Haskell/Cabal.hs | 39 +++++---------- src/Hadrian/Haskell/Cabal/Parse.hs | 60 ++++++++++++++++++++++++ src/Hadrian/Oracles/FileCache.hs | 51 -------------------- src/Hadrian/Oracles/{KeyValue.hs => TextFile.hs} | 54 ++++++++++++++++++--- src/Oracles/Flag.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/Setting.hs | 2 +- src/Rules.hs | 11 +---- src/Rules/Compile.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 20 +++----- src/Utilities.hs | 38 +++++---------- 14 files changed, 149 insertions(+), 152 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 4b6707a616478a0f664585a49de0d0ed6431d231 From git at git.haskell.org Fri Oct 27 00:57:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/snowleopard/hadrian (8586ab8) Message-ID: <20171027005716.794663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8586ab84fbac7e250d23844bbd39c147f87ce092/ghc >--------------------------------------------------------------- commit 8586ab84fbac7e250d23844bbd39c147f87ce092 Merge: 4b6707a 942ed27 Author: Andrey Mokhov Date: Sat Aug 19 03:45:40 2017 +0100 Merge branch 'master' of https://github.com/snowleopard/hadrian >--------------------------------------------------------------- 8586ab84fbac7e250d23844bbd39c147f87ce092 src/Hadrian/Oracles/DirectoryContents.hs | 10 +++++++++- src/Rules/Install.hs | 8 +++++--- 2 files changed, 14 insertions(+), 4 deletions(-) From git at git.haskell.org Fri Oct 27 00:57:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Shake files into _build/hadrian (185af60) Message-ID: <20171027005715.B7DA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/185af600e91c5294fe8f49158ca8d73aec6ec646/ghc >--------------------------------------------------------------- commit 185af600e91c5294fe8f49158ca8d73aec6ec646 Author: Andrey Mokhov Date: Sat Apr 30 23:04:41 2016 +0100 Move Shake files into _build/hadrian >--------------------------------------------------------------- 185af600e91c5294fe8f49158ca8d73aec6ec646 src/Base.hs | 13 +------------ src/Main.hs | 4 ++-- src/Oracles/PackageDeps.hs | 4 +++- src/Rules/Clean.hs | 6 +++--- src/Settings/Paths.hs | 12 +++++++++++- 5 files changed, 20 insertions(+), 19 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 53bb197..a38ea51 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -16,8 +16,7 @@ module Base ( module Development.Shake.FilePath, -- * Paths - shakeFilesPath, configPath, configFile, sourcePath, programInplacePath, - bootPackageConstraints, packageDependencies, + configPath, configFile, sourcePath, programInplacePath, -- * Output putColoured, putOracle, putBuild, putSuccess, putError, @@ -50,10 +49,6 @@ import System.IO shakePath :: FilePath shakePath = "hadrian" --- TODO: Move to buildRootPath. -shakeFilesPath :: FilePath -shakeFilesPath = shakePath -/- ".db" - configPath :: FilePath configPath = shakePath -/- "cfg" @@ -69,12 +64,6 @@ sourcePath = shakePath -/- "src" programInplacePath :: FilePath programInplacePath = "inplace/bin" -bootPackageConstraints :: FilePath -bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" - -packageDependencies :: FilePath -packageDependencies = shakeFilesPath -/- "package-dependencies" - -- Utility functions -- | Find and replace all occurrences of a value in a list replaceEq :: Eq a => a -> a -> [a] -> [a] diff --git a/src/Main.hs b/src/Main.hs index cf45cc3..66f897f 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,7 +2,6 @@ module Main (main) where import Development.Shake -import qualified Base import qualified CmdLineFlag import qualified Environment import qualified Rules @@ -10,6 +9,7 @@ import qualified Rules.Clean import qualified Rules.Oracles import qualified Rules.Selftest import qualified Rules.Test +import qualified Settings.Paths main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -30,6 +30,6 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest - , shakeFiles = Base.shakeFilesPath + , shakeFiles = Settings.Paths.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 6a5f7dd..a2a9234 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -1,9 +1,11 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.PackageDeps (packageDeps, packageDepsOracle) where -import Base import qualified Data.HashMap.Strict as Map + +import Base import Package +import Settings.Paths newtype PackageDepsKey = PackageDepsKey PackageName deriving (Show, Typeable, Eq, Hashable, Binary, NFData) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 0bff316..ca5c062 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -17,7 +17,7 @@ clean dir = do cleanRules :: Rules () cleanRules = do "clean" ~> do - clean buildRootPath + forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) clean programInplacePath clean "inplace/lib" clean derivedConstantsPath @@ -29,6 +29,6 @@ cleanRules = do forM_ [Stage0 ..] $ \stage -> do let dir = pkgPath pkg -/- contextDirectory (vanillaContext stage pkg) removeDirectoryIfExists dir - putBuild $ "| Remove the Shake database " ++ shakeFilesPath ++ "..." - removeFilesAfter shakeFilesPath ["//*"] + putBuild $ "| Remove Hadrian files..." + removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 678ed92..77fb5a5 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,8 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpBuildInfoPath, - packageDbDirectory, pkgConfFile + packageDbDirectory, pkgConfFile, shakeFilesPath, bootPackageConstraints, + packageDependencies ) where import Base @@ -16,6 +17,15 @@ import Settings.User (~/~) :: FilePath -> FilePath -> FilePath x ~/~ y = x ++ '/' : y +shakeFilesPath :: FilePath +shakeFilesPath = buildRootPath -/- "hadrian/shake-files" + +bootPackageConstraints :: FilePath +bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints" + +packageDependencies :: FilePath +packageDependencies = shakeFilesPath -/- "package-dependencies" + -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath buildPath context at Context {..} = From git at git.haskell.org Fri Oct 27 00:57:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use in-tree Cabal library. (e6373a0) Message-ID: <20171027005719.55ED83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e6373a064cac830b4ee1a1651d888c5b64b9ca80/ghc >--------------------------------------------------------------- commit e6373a064cac830b4ee1a1651d888c5b64b9ca80 Author: Andrey Mokhov Date: Sun May 1 00:40:08 2016 +0100 Use in-tree Cabal library. See #228. >--------------------------------------------------------------- e6373a064cac830b4ee1a1651d888c5b64b9ca80 build.bat | 1 + build.sh | 1 + 2 files changed, 2 insertions(+) diff --git a/build.bat b/build.bat index f9f0b9a..6e86d42 100644 --- a/build.bat +++ b/build.bat @@ -11,6 +11,7 @@ -rtsopts ^ -with-rtsopts=-I0 ^ -outputdir=../_build/hadrian ^ + -i../libraries/Cabal/Cabal ^ -j ^ -O ^ -o hadrian diff --git a/build.sh b/build.sh index f7d06c2..fff8df4 100755 --- a/build.sh +++ b/build.sh @@ -38,6 +38,7 @@ ghc \ -fno-warn-name-shadowing \ -XRecordWildCards \ -i"$root/src" \ + -i"$root/../libraries/Cabal/Cabal" \ -rtsopts \ -with-rtsopts=-I0 \ -threaded \ From git at git.haskell.org Fri Oct 27 00:57:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (268155a) Message-ID: <20171027005720.123353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/268155a0e615fda224d72d029749f1e2df0fa59b/ghc >--------------------------------------------------------------- commit 268155a0e615fda224d72d029749f1e2df0fa59b Author: Andrey Mokhov Date: Sat Aug 19 13:12:09 2017 +0100 Minor revision >--------------------------------------------------------------- 268155a0e615fda224d72d029749f1e2df0fa59b src/Hadrian/Haskell/Cabal.hs | 3 +-- src/Hadrian/Haskell/Cabal/Parse.hs | 8 ++++---- src/Hadrian/Oracles/Path.hs | 4 ++-- src/Hadrian/Oracles/TextFile.hs | 23 +++++++++++++---------- 4 files changed, 20 insertions(+), 18 deletions(-) diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs index bf21b18..6da1e51 100644 --- a/src/Hadrian/Haskell/Cabal.hs +++ b/src/Hadrian/Haskell/Cabal.hs @@ -11,7 +11,6 @@ ----------------------------------------------------------------------------- module Hadrian.Haskell.Cabal (pkgNameVersion, pkgDependencies) where -import Data.List import Development.Shake import Hadrian.Haskell.Cabal.Parse @@ -32,4 +31,4 @@ pkgNameVersion pkg = do pkgDependencies :: Package -> Action [PackageName] pkgDependencies pkg = do cabal <- readCabalFile (pkgCabalFile pkg) - return (dependencies cabal \\ [pkgName pkg]) + return (dependencies cabal) diff --git a/src/Hadrian/Haskell/Cabal/Parse.hs b/src/Hadrian/Haskell/Cabal/Parse.hs index ec18781..bc234d4 100644 --- a/src/Hadrian/Haskell/Cabal/Parse.hs +++ b/src/Hadrian/Haskell/Cabal/Parse.hs @@ -44,14 +44,14 @@ parseCabal :: FilePath -> IO Cabal parseCabal file = do gpd <- liftIO $ C.readGenericPackageDescription C.silent file let pkgId = C.package (C.packageDescription gpd) + name = C.unPackageName (C.pkgName pkgId) + version = C.display (C.pkgVersion pkgId) libDeps = collectDeps (C.condLibrary gpd) exeDeps = map (collectDeps . Just . snd) (C.condExecutables gpd) allDeps = concat (libDeps : exeDeps) sorted = sort [ C.unPackageName p | C.Dependency p _ <- allDeps ] - return $ Cabal - (C.unPackageName $ C.pkgName pkgId) - (C.display $ C.pkgVersion pkgId) - (nubOrd sorted) + deps = nubOrd sorted \\ [name] + return $ Cabal name version deps collectDeps :: Maybe (C.CondTree v [C.Dependency] a) -> [C.Dependency] collectDeps Nothing = [] diff --git a/src/Hadrian/Oracles/Path.hs b/src/Hadrian/Oracles/Path.hs index cab8aa1..4f6406c 100644 --- a/src/Hadrian/Oracles/Path.hs +++ b/src/Hadrian/Oracles/Path.hs @@ -52,11 +52,11 @@ pathOracle = do void $ addOracle $ \(WindowsPath path) -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] let windowsPath = unifyPath $ dropWhileEnd isSpace out - putLoud $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath + putLoud $ "| Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath void $ addOracle $ \(LookupInPath name) -> do let unpack = fromMaybe . error $ "Cannot find executable " ++ quote name path <- unifyPath <$> unpack <$> liftIO (findExecutable name) - putLoud $ "Executable found: " ++ name ++ " => " ++ path + putLoud $ "| Executable found: " ++ name ++ " => " ++ path return path diff --git a/src/Hadrian/Oracles/TextFile.hs b/src/Hadrian/Oracles/TextFile.hs index 7f80c75..c2ecb4c 100644 --- a/src/Hadrian/Oracles/TextFile.hs +++ b/src/Hadrian/Oracles/TextFile.hs @@ -23,8 +23,8 @@ import Development.Shake import Development.Shake.Classes import Development.Shake.Config -import Hadrian.Utilities import Hadrian.Haskell.Cabal.Parse +import Hadrian.Utilities newtype TextFile = TextFile FilePath deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -32,7 +32,7 @@ type instance RuleResult TextFile = String newtype CabalFile = CabalFile FilePath deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -type instance RuleResult CabalFile = String +type instance RuleResult CabalFile = Cabal newtype KeyValue = KeyValue (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -99,22 +99,25 @@ textFileOracle :: Rules () textFileOracle = do text <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| TextFile oracle: reading " ++ quote file ++ "..." liftIO $ readFile file + void $ addOracle $ \(TextFile file) -> text file + kv <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| KeyValue oracle: reading " ++ quote file ++ "..." liftIO $ readConfigFile file + void $ addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> kv file + kvs <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| KeyValues oracle: reading " ++ quote file ++ "..." contents <- map words <$> readFileLines file return $ Map.fromList [ (key, values) | (key:values) <- contents ] + void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file + cabal <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| CabalFile oracle: reading " ++ quote file ++ "..." liftIO $ parseCabal file - void $ addOracle $ \(TextFile file ) -> text file - void $ addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> kv file - void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file - void $ addOracle $ \(CabalFile file ) -> cabal file + void $ addOracle $ \(CabalFile file) -> cabal file From git at git.haskell.org Fri Oct 27 00:57:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Turn Configure into a Builder. (72f6ec6) Message-ID: <20171027005722.E4D9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72f6ec653e2f8801fc275ffa5d294a85e6e34ee8/ghc >--------------------------------------------------------------- commit 72f6ec653e2f8801fc275ffa5d294a85e6e34ee8 Author: Andrey Mokhov Date: Mon May 2 02:49:30 2016 +0100 Turn Configure into a Builder. >--------------------------------------------------------------- 72f6ec653e2f8801fc275ffa5d294a85e6e34ee8 hadrian.cabal | 1 + src/Builder.hs | 70 ++++++++++++++++++-------------------- src/Predicates.hs | 17 +++++++-- src/Rules/Actions.hs | 53 ++++++++++++++--------------- src/Rules/Gmp.hs | 19 ++++------- src/Rules/Libffi.hs | 51 ++++++++++++--------------- src/Rules/Setup.hs | 19 +++++++---- src/Settings/Args.hs | 2 ++ src/Settings/Builders/Configure.hs | 30 ++++++++++++++++ src/Settings/Paths.hs | 6 +++- src/Settings/User.hs | 2 +- 11 files changed, 155 insertions(+), 115 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 72f6ec653e2f8801fc275ffa5d294a85e6e34ee8 From git at git.haskell.org Fri Oct 27 00:57:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix MonadFail warning (a8cbd16) Message-ID: <20171027005723.A7B7C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8cbd160e3e6b90bdb618620fd6eb4cc53179ae5/ghc >--------------------------------------------------------------- commit a8cbd160e3e6b90bdb618620fd6eb4cc53179ae5 Author: Andrey Mokhov Date: Sat Aug 19 16:21:27 2017 +0100 Fix MonadFail warning >--------------------------------------------------------------- a8cbd160e3e6b90bdb618620fd6eb4cc53179ae5 src/Settings/Builders/DeriveConstants.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index b8846be..7a6e863 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -5,8 +5,11 @@ import Settings.Builders.Common -- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? deriveConstantsBuilderArgs :: Args deriveConstantsBuilderArgs = builder DeriveConstants ? do - cFlags <- includeCcArgs - [outputFile, tempDir] <- getOutputs + cFlags <- includeCcArgs + outs <- getOutputs + let (outputFile, tempDir) = case outs of + [a, b] -> (a, b) + _ -> error $ "DeriveConstants: expected two outputs, got " ++ show outs mconcat [ output "//DerivedConstants.h" ? arg "--gen-header" , output "//GHCConstantsHaskellType.hs" ? arg "--gen-haskell-type" From git at git.haskell.org Fri Oct 27 00:57:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do putInfo even in verbose mode, minor revision. (0b6c0aa) Message-ID: <20171027005726.7BDAE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0b6c0aa0b4dcbbc3eb65a101edf7db64c72043b4/ghc >--------------------------------------------------------------- commit 0b6c0aa0b4dcbbc3eb65a101edf7db64c72043b4 Author: Andrey Mokhov Date: Mon May 2 03:08:10 2016 +0100 Do putInfo even in verbose mode, minor revision. >--------------------------------------------------------------- 0b6c0aa0b4dcbbc3eb65a101edf7db64c72043b4 src/Rules/Actions.hs | 3 ++- src/Settings/User.hs | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 5af1ce4..f006947 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -46,7 +46,7 @@ customBuild rs opts target at Target {..} = do -- The line below forces the rule to be rerun if the args hash has changed checkArgsHash target withResources rs $ do - unless verbose $ putInfo target + putInfo target quietlyUnlessVerbose $ case builder of Ar -> do output <- interpret target getOutput @@ -59,6 +59,7 @@ customBuild rs opts target at Target {..} = do Configure dir -> do need [dir -/- "configure"] + -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" cmd Shell (EchoStdout False) [Cwd dir] [path] (env:opts) argList diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 215a05b..0893579 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -81,7 +81,7 @@ buildHaddock = return cmdBuildHaddock -- this is a Predicate, hence you can enable verbose output for a chosen package -- only, e.g.: verboseCommands = package ghcPrim verboseCommands :: Predicate -verboseCommands = builder Configure +verboseCommands = return False -- TODO: Replace with stage2 ? arg "-Werror"? -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. From git at git.haskell.org Fri Oct 27 00:57:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghcid.txt (8f244c4) Message-ID: <20171027005727.393603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f244c413c7e3444285b32c8f90f839511a367ce/ghc >--------------------------------------------------------------- commit 8f244c413c7e3444285b32c8f90f839511a367ce Author: Andrey Mokhov Date: Sat Aug 19 16:22:54 2017 +0100 Add ghcid.txt >--------------------------------------------------------------- 8f244c413c7e3444285b32c8f90f839511a367ce .gitignore | 3 +++ 1 file changed, 3 insertions(+) diff --git a/.gitignore b/.gitignore index 4b026f2..697afc9 100644 --- a/.gitignore +++ b/.gitignore @@ -21,3 +21,6 @@ cabal.sandbox.config # Mostly temp file by emacs *~ + +# ghcid output +/ghcid.txt \ No newline at end of file From git at git.haskell.org Fri Oct 27 00:57:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Print version info before running configure (759dff3) Message-ID: <20171027005730.2A42F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/759dff36f7d30aba45bd3b6f9947328b4c0a8c77/ghc >--------------------------------------------------------------- commit 759dff36f7d30aba45bd3b6f9947328b4c0a8c77 Author: Andrey Mokhov Date: Mon May 2 03:45:49 2016 +0100 Print version info before running configure >--------------------------------------------------------------- 759dff36f7d30aba45bd3b6f9947328b4c0a8c77 appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 3918779..76ccbe1 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -24,6 +24,11 @@ install: - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - ghc --version + - stack --version + - alex --version + - happy --version + - stack exec -- ghc-pkg list - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - stack exec -- perl boot @@ -31,11 +36,6 @@ install: - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef47d7b35d17bff791763c8bf3d46caaaf1a1108/ghc >--------------------------------------------------------------- commit ef47d7b35d17bff791763c8bf3d46caaaf1a1108 Author: Andrey Mokhov Date: Sun Aug 20 01:12:39 2017 +0100 Fix performance bug: do not call ghc-cabal to determine package targets See #393 >--------------------------------------------------------------- ef47d7b35d17bff791763c8bf3d46caaaf1a1108 src/Context.hs | 19 +++++++++---------- src/Hadrian/Haskell/Cabal.hs | 18 +++++++++++++++++- src/Hadrian/Haskell/Cabal/Parse.hs | 7 ++++--- src/Oracles/PackageData.hs | 2 -- src/Rules.hs | 21 +++++++++++++++------ src/Rules/Install.hs | 2 +- src/Settings/Builders/Ghc.hs | 7 +++++-- src/Utilities.hs | 13 ++++++++----- 8 files changed, 59 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 ef47d7b35d17bff791763c8bf3d46caaaf1a1108 From git at git.haskell.org Fri Oct 27 00:57:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move gmp library instead of copying it. Add moveFile. (de4f7bc) Message-ID: <20171027005734.222563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de4f7bcc27596946d26f708782f74a6266706842/ghc >--------------------------------------------------------------- commit de4f7bcc27596946d26f708782f74a6266706842 Author: Andrey Mokhov Date: Mon May 2 03:59:52 2016 +0100 Move gmp library instead of copying it. Add moveFile. See #163. >--------------------------------------------------------------- de4f7bcc27596946d26f708782f74a6266706842 src/Rules/Actions.hs | 13 ++++++++++--- src/Rules/Gmp.hs | 3 +-- 2 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index f006947..edf98eb 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,7 +1,8 @@ module Rules.Actions ( - build, buildWithResources, buildWithCmdOptions, copyFile, createDirectory, - removeDirectory, copyDirectory, moveDirectory, applyPatch, fixFile, runMake, - runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable + build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, + createDirectory, removeDirectory, copyDirectory, moveDirectory, + applyPatch, fixFile, runMake, runMakeVerbose, renderLibrary, renderProgram, + runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -87,6 +88,12 @@ copyFile source target = do putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target +-- Note, moveFile cannot track the source, because it is moved. +moveFile :: FilePath -> FilePath -> Action () +moveFile source target = do + putProgressInfo $ renderAction "Move file" source target + liftIO $ IO.renameFile source target + createDirectory :: FilePath -> Action () createDirectory dir = do putBuild $ "| Create directory " ++ dir diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index e2502dd..1e962ec 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -103,8 +103,7 @@ gmpRules = do copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH copyFile (libPath -/- "gmp.h") gmpLibraryH - -- TODO: why copy library, can we move it instead? - copyFile (libPath -/- ".libs/libgmp.a") gmpLibrary + moveFile (libPath -/- ".libs/libgmp.a") gmpLibrary createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] From git at git.haskell.org Fri Oct 27 00:57:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: delete cfg/config.h.in (#390) (c413722) Message-ID: <20171027005734.D069D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c413722eae49a7999293a8940547f626a33d0632/ghc >--------------------------------------------------------------- commit c413722eae49a7999293a8940547f626a33d0632 Author: Zhen Zhang Date: Sun Aug 20 19:09:47 2017 +0800 delete cfg/config.h.in (#390) >--------------------------------------------------------------- c413722eae49a7999293a8940547f626a33d0632 cfg/config.h.in | 463 -------------------------------------------------------- 1 file changed, 463 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 c413722eae49a7999293a8940547f626a33d0632 From git at git.haskell.org Fri Oct 27 00:57:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of git://github.com/snowleopard/hadrian (2674950) Message-ID: <20171027005737.9BE793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2674950daed5ab709cd3e5bab576b6343805d2e0/ghc >--------------------------------------------------------------- commit 2674950daed5ab709cd3e5bab576b6343805d2e0 Merge: de4f7bc 759dff3 Author: Andrey Mokhov Date: Mon May 2 04:00:12 2016 +0100 Merge branch 'master' of git://github.com/snowleopard/hadrian >--------------------------------------------------------------- 2674950daed5ab709cd3e5bab576b6343805d2e0 appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Oct 27 00:57:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add DESTDIR to command line arguments (#397) (176bfd4) Message-ID: <20171027005738.610FF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/176bfd4d524c59c64a182f8e04dd0084a9c5e482/ghc >--------------------------------------------------------------- commit 176bfd4d524c59c64a182f8e04dd0084a9c5e482 Author: Zhen Zhang Date: Sun Aug 20 19:29:36 2017 +0800 Add DESTDIR to command line arguments (#397) >--------------------------------------------------------------- 176bfd4d524c59c64a182f8e04dd0084a9c5e482 README.md | 2 +- src/CommandLine.hs | 13 ++++++++++++- src/Rules/Install.hs | 6 ++++++ src/Settings.hs | 7 +++---- src/Settings/Packages/Rts.hs | 1 + 5 files changed, 23 insertions(+), 6 deletions(-) diff --git a/README.md b/README.md index 5e49393..ecf9728 100644 --- a/README.md +++ b/README.md @@ -111,7 +111,7 @@ To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` tar To build and install GHC artifacts, run the `install` target. By default, the artifacts will be installed to `` on your system. For example, -`ghc` will be installed to `/usr/local/bin`. By modifying `defaultDestDir` in `UserSettings.hs`, +`ghc` will be installed to `/usr/local/bin`. By setting flag `--install-destdir=[DESTDIR]`, you can install things to non-system path `DESTDIR/` instead. #### Testing diff --git a/src/CommandLine.hs b/src/CommandLine.hs index 5688d6f..fbf3e07 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -1,6 +1,7 @@ module CommandLine ( optDescrs, cmdLineArgsMap, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, - cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects + cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects, + cmdInstallDestDir ) where import Data.Either @@ -14,6 +15,7 @@ import System.Environment -- | All arguments that can be passed to Hadrian via the command line. data CommandLineArgs = CommandLineArgs { buildHaddock :: Bool + , installDestDir :: Maybe String , flavour :: Maybe String , integerSimple :: Bool , progressColour :: UseColour @@ -27,6 +29,7 @@ defaultCommandLineArgs :: CommandLineArgs defaultCommandLineArgs = CommandLineArgs { buildHaddock = False , flavour = Nothing + , installDestDir = Nothing , integerSimple = False , progressColour = Auto , progressInfo = Normal @@ -39,6 +42,9 @@ readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } readFlavour :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs) readFlavour ms = Right $ \flags -> flags { flavour = lower <$> ms } +readInstallDestDir :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs) +readInstallDestDir ms = Right $ \flags -> flags { installDestDir = ms } + readIntegerSimple :: Either String (CommandLineArgs -> CommandLineArgs) readIntegerSimple = Right $ \flags -> flags { integerSimple = True } @@ -80,6 +86,8 @@ optDescrs = "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." + , Option [] ["install-destdir"] (OptArg readInstallDestDir "DESTDIR") + "Installation destination directory." , Option [] ["integer-simple"] (NoArg readIntegerSimple) "Build GHC with integer-simple library." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") @@ -107,6 +115,9 @@ cmdLineArgs = userSetting defaultCommandLineArgs cmdBuildHaddock :: Action Bool cmdBuildHaddock = buildHaddock <$> cmdLineArgs +cmdInstallDestDir :: Action (Maybe String) +cmdInstallDestDir = installDestDir <$> cmdLineArgs + cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 24d7703..0d7336b 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -60,6 +60,7 @@ getLibExecDir = (-/- "bin") <$> installGhcLibDir installLibExecScripts :: Action () installLibExecScripts = do libExecDir <- getLibExecDir + destDir <- getDestDir installDirectory (destDir ++ libExecDir) forM_ libExecScripts $ \script -> do installScript script (destDir ++ libExecDir) @@ -72,6 +73,7 @@ installLibExecScripts = do installLibExecs :: Action () installLibExecs = do libExecDir <- getLibExecDir + destDir <- getDestDir installDirectory (destDir ++ libExecDir) forM_ installBinPkgs $ \pkg -> do withLatestBuildStage pkg $ \stage -> do @@ -88,6 +90,7 @@ installBins :: Action () installBins = do binDir <- setting InstallBinDir libDir <- installGhcLibDir + destDir <- getDestDir installDirectory (destDir ++ binDir) win <- windowsHost when win $ @@ -153,6 +156,7 @@ installPackages = do ghcLibDir <- installGhcLibDir binDir <- setting InstallBinDir + destDir <- getDestDir -- Install package.conf let installedPackageConf = destDir ++ ghcLibDir -/- "package.conf.d" @@ -271,6 +275,7 @@ installPackages = do installCommonLibs :: Action () installCommonLibs = do ghcLibDir <- installGhcLibDir + destDir <- getDestDir installLibsTo inplaceLibCopyTargets (destDir ++ ghcLibDir) -- ref: ghc.mk @@ -296,6 +301,7 @@ includeHSubdirs = [".", "rts", "rts/prof", "rts/storage", "stg"] installIncludes :: Action () installIncludes = do ghclibDir <- installGhcLibDir + destDir <- getDestDir let ghcheaderDir = ghclibDir -/- "include" installDirectory (destDir ++ ghcheaderDir) forM_ includeHSubdirs $ \dir -> do diff --git a/src/Settings.hs b/src/Settings.hs index 9fafd1e..52c36ad 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,7 +2,7 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, stagePackages, builderPath, getBuilderPath, isSpecified, latestBuildStage, programPath, - programContext, integerLibraryName, destDir, stage1Only, buildDll0 + programContext, integerLibraryName, getDestDir, stage1Only, buildDll0 ) where import Context @@ -103,7 +103,6 @@ programPath context at Context {..} = do stage1Only :: Bool stage1Only = defaultStage1Only --- TODO: Set this from command line -- | Install's DESTDIR setting. -destDir :: FilePath -destDir = defaultDestDir +getDestDir :: Action FilePath +getDestDir = fromMaybe "" <$> cmdInstallDestDir diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 0ae764f..a54e618 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -62,6 +62,7 @@ rtsPackageArgs = package rts ? do ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir ghclibDir <- expr installGhcLibDir + destDir <- expr getDestDir let cArgs = [ arg "-Irts" , arg $ "-I" ++ path From git at git.haskell.org Fri Oct 27 00:57:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run configure via stack exec. (d842e0f) Message-ID: <20171027005741.2DB863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d842e0f8e336d17a017c94c1d70d9d66a58a3a22/ghc >--------------------------------------------------------------- commit d842e0f8e336d17a017c94c1d70d9d66a58a3a22 Author: Andrey Mokhov Date: Mon May 2 04:10:18 2016 +0100 Run configure via stack exec. >--------------------------------------------------------------- d842e0f8e336d17a017c94c1d70d9d66a58a3a22 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 76ccbe1..7b2e53b 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -34,7 +34,7 @@ install: - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acd5c37535be71bc36dbf73ae09a772af5d63fda/ghc >--------------------------------------------------------------- commit acd5c37535be71bc36dbf73ae09a772af5d63fda Author: Andrey Mokhov Date: Sun Aug 20 15:23:24 2017 +0100 Minor revision >--------------------------------------------------------------- acd5c37535be71bc36dbf73ae09a772af5d63fda src/CommandLine.hs | 9 ++++----- src/Hadrian/Utilities.hs | 2 +- 2 files changed, 5 insertions(+), 6 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index fbf3e07..cc6f944 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -15,8 +15,8 @@ import System.Environment -- | All arguments that can be passed to Hadrian via the command line. data CommandLineArgs = CommandLineArgs { buildHaddock :: Bool - , installDestDir :: Maybe String , flavour :: Maybe String + , installDestDir :: Maybe String , integerSimple :: Bool , progressColour :: UseColour , progressInfo :: ProgressInfo @@ -115,12 +115,12 @@ cmdLineArgs = userSetting defaultCommandLineArgs cmdBuildHaddock :: Action Bool cmdBuildHaddock = buildHaddock <$> cmdLineArgs -cmdInstallDestDir :: Action (Maybe String) -cmdInstallDestDir = installDestDir <$> cmdLineArgs - cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs +cmdInstallDestDir :: Action (Maybe String) +cmdInstallDestDir = installDestDir <$> cmdLineArgs + cmdIntegerSimple :: Action Bool cmdIntegerSimple = integerSimple <$> cmdLineArgs @@ -135,4 +135,3 @@ cmdSkipConfigure = skipConfigure <$> cmdLineArgs cmdSplitObjects :: Action Bool cmdSplitObjects = splitObjects <$> cmdLineArgs - diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index f1db28e..4051347 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -177,7 +177,7 @@ copyFile source target = do let dir = takeDirectory target liftIO $ IO.createDirectoryIfMissing True dir putProgressInfo =<< renderAction "Copy file" source target - copyFileChanged source target + quietly $ copyFileChanged source target -- | Copy a file without tracking the source. Create the target directory if missing. copyFileUntracked :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:57:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix Appveyor failure (b8dda5c) Message-ID: <20171027005745.0A09E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b8dda5c646545ea11c18c70a3f657871b870d1ec/ghc >--------------------------------------------------------------- commit b8dda5c646545ea11c18c70a3f657871b870d1ec Author: Andrey Mokhov Date: Mon May 2 12:28:32 2016 +0100 Attempt to fix Appveyor failure >--------------------------------------------------------------- b8dda5c646545ea11c18c70a3f657871b870d1ec appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 7b2e53b..459cecd 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -34,7 +34,7 @@ install: - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - echo "" | stack --no-terminal exec -- bash "configure --enable-tarballs-autodownload" + - echo "" | stack --no-terminal exec -- bash -lc "cd /home/ghc; configure --enable-tarballs-autodownload" - bash -lc "cat /home/ghc/hadrian/cfg/system.config" build_script: From git at git.haskell.org Fri Oct 27 00:57:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to computing package version only through the Cabal library (4ce8587) Message-ID: <20171027005745.8F4D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ce85874126d7356b6c442e45c593797283f7108/ghc >--------------------------------------------------------------- commit 4ce85874126d7356b6c442e45c593797283f7108 Author: Andrey Mokhov Date: Sun Aug 20 17:05:30 2017 +0100 Switch to computing package version only through the Cabal library >--------------------------------------------------------------- 4ce85874126d7356b6c442e45c593797283f7108 src/Hadrian/Haskell/Cabal.hs | 36 ++++++++++++++++++++++-------------- src/Oracles/PackageData.hs | 2 -- src/Rules/Data.hs | 2 -- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 6 +++--- src/Settings/Packages/GhcCabal.hs | 4 ++-- 6 files changed, 29 insertions(+), 25 deletions(-) diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs index 02fcd82..23cfdc7 100644 --- a/src/Hadrian/Haskell/Cabal.hs +++ b/src/Hadrian/Haskell/Cabal.hs @@ -10,35 +10,43 @@ -- @.cabal@ files. ----------------------------------------------------------------------------- module Hadrian.Haskell.Cabal ( - pkgNameVersion, pkgIdentifier, pkgDependencies + pkgVersion, pkgIdentifier, pkgDependencies ) where +import Control.Monad import Development.Shake import Hadrian.Haskell.Cabal.Parse import Hadrian.Haskell.Package import Hadrian.Oracles.TextFile +import Hadrian.Utilities --- | Read the @.cabal@ file of a given package and return the package name and --- version. The @.cabal@ file is tracked. -pkgNameVersion :: Package -> Action (PackageName, String) -pkgNameVersion pkg = do +-- | Read the @.cabal@ file of a given package and return the package version. +-- The @.cabal@ file is tracked. +pkgVersion :: Package -> Action String +pkgVersion pkg = do cabal <- readCabalFile (pkgCabalFile pkg) - return (name cabal, version cabal) + return (version cabal) --- | Read the @.cabal@ file of a given package and return the package identifier. --- If the @.cabal@ file does not exist return the package name. If the @.cabal@ --- file exists it is tracked. +-- | Read the @.cabal@ file of a given package and return the package identifier, +-- e.g. @base-4.10.0.0 at . If the @.cabal@ file does not exist return just the +-- package name, e.g. @rts at . If the @.cabal@ file exists then it is tracked, and +-- furthermore we check that the recorded package name matches the name of the +-- package passed as the parameter and raise an error otherwise. pkgIdentifier :: Package -> Action String pkgIdentifier pkg = do cabalExists <- doesFileExist (pkgCabalFile pkg) - if cabalExists - then do + if not cabalExists + then return (pkgName pkg) + else do cabal <- readCabalFile (pkgCabalFile pkg) + when (pkgName pkg /= name cabal) $ + error $ "[Hadrian.Haskell.Cabal] Inconsistent package name: expected " + ++ quote (pkgName pkg) ++ ", but " ++ quote (pkgCabalFile pkg) + ++ " specifies " ++ quote (name cabal) ++ "." return $ if (null $ version cabal) - then name cabal - else name cabal ++ "-" ++ version cabal - else return (pkgName pkg) + then pkgName pkg + else pkgName pkg ++ "-" ++ version cabal -- | Read the @.cabal@ file of a given package and return the sorted list of its -- dependencies. The current version does not take care of Cabal conditionals diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 991caf1..7d98c98 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -8,7 +8,6 @@ import Base data PackageData = BuildGhciLib FilePath | Synopsis FilePath - | Version FilePath data PackageDataList = AsmSrcs FilePath | CcArgs FilePath @@ -40,7 +39,6 @@ pkgData :: PackageData -> Action String pkgData packageData = case packageData of BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" Synopsis path -> askPackageData path "SYNOPSIS" - Version path -> askPackageData path "VERSION" -- | @PackageDataList path@ is used for multiple string options separated by -- spaces, such as @path_MODULES = Data.Array Data.Array.Base ... at . diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index ef2f017..194bf62 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -61,9 +61,7 @@ generatePackageData context at Context {..} file = do cSrcs <- packageCSources package cmmSrcs <- packageCmmSources package genPath <- buildRoot <&> (-/- generatedDir) - let pkgKey = if isLibrary package then "COMPONENT_ID = " else "PROGNAME = " writeFileChanged file . unlines $ - [ pkgKey ++ pkgName package ] ++ [ "S_SRCS = " ++ unwords asmSrcs ] ++ [ "C_SRCS = " ++ unwords cSrcs ] ++ [ "CMM_SRCS = " ++ unwords cmmSrcs ] ++ diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index ba1de93..cf6bcb3 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -95,8 +95,8 @@ bootPackageConstraints = stage0 ? do bootPkgs <- expr $ stagePackages Stage0 let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- expr $ forM (sort pkgs) $ \pkg -> do - (name, version) <- pkgNameVersion pkg - return (name ++ " == " ++ version) + version <- pkgVersion pkg + return (pkgName pkg ++ " == " ++ version) pure $ concat [ ["--constraint", c] | c <- constraints ] cppArgs :: Args diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 7319f80..bc3ebf4 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -1,6 +1,7 @@ module Settings.Builders.Haddock (haddockBuilderArgs) where import Hadrian.Utilities +import Hadrian.Haskell.Cabal import Rules.Documentation import Settings.Builders.Common @@ -17,12 +18,11 @@ haddockBuilderArgs = builder Haddock ? do output <- getOutput pkg <- getPackage path <- getBuildPath - version <- getPkgData Version + version <- expr $ pkgVersion pkg synopsis <- getPkgData Synopsis deps <- getPkgDataList Deps haddocks <- expr . haddockDependencies =<< getContext - progPath <- expr $ buildPath (vanillaContext Stage2 haddock) - hVersion <- expr $ pkgData (Version progPath) + hVersion <- expr $ pkgVersion haddock ghcOpts <- haddockGhcArgs mconcat [ arg $ "--odir=" ++ takeDirectory output diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 0a0fe15..3c07c67 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -9,8 +9,8 @@ import Utilities ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do - cabalDeps <- expr $ stage1Dependencies cabal - (_, cabalVersion) <- expr $ pkgNameVersion cabal + cabalDeps <- expr $ stage1Dependencies cabal + cabalVersion <- expr $ pkgVersion cabal mconcat [ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps, pkg /= parsec ] , arg "--make" From git at git.haskell.org Fri Oct 27 00:57:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add PATH to happy. (70fd668) Message-ID: <20171027005748.A92FC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/70fd668dc76660a348e732f370f8cf816a08f0fa/ghc >--------------------------------------------------------------- commit 70fd668dc76660a348e732f370f8cf816a08f0fa Author: Andrey Mokhov Date: Mon May 2 13:33:45 2016 +0100 Add PATH to happy. >--------------------------------------------------------------- 70fd668dc76660a348e732f370f8cf816a08f0fa appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 459cecd..16a1277 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -34,7 +34,7 @@ install: - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - echo "" | stack --no-terminal exec -- bash -lc "cd /home/ghc; configure --enable-tarballs-autodownload" + - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9105fc6a676cbd97b26ec5edb86a15e681073cf9/ghc >--------------------------------------------------------------- commit 9105fc6a676cbd97b26ec5edb86a15e681073cf9 Author: Andrey Mokhov Date: Sun Aug 20 17:58:01 2017 +0100 Compute package synopsis directly from Cabal files >--------------------------------------------------------------- 9105fc6a676cbd97b26ec5edb86a15e681073cf9 src/Hadrian/Haskell/Cabal.hs | 16 ++++++++++++++-- src/Hadrian/Haskell/Cabal/Parse.hs | 8 +++++--- src/Hadrian/Utilities.hs | 23 +++++++++++++++-------- src/Oracles/PackageData.hs | 2 -- src/Rules/Data.hs | 3 +-- src/Rules/Library.hs | 6 +++--- src/Rules/Program.hs | 8 +++----- src/Settings/Builders/Haddock.hs | 2 +- 8 files changed, 42 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9105fc6a676cbd97b26ec5edb86a15e681073cf9 From git at git.haskell.org Fri Oct 27 00:57:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop support for shake-0.15.5 (0015942) Message-ID: <20171027005752.3F3DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/00159421655dd8c82a983a8249aa4bc373613893/ghc >--------------------------------------------------------------- commit 00159421655dd8c82a983a8249aa4bc373613893 Author: Andrey Mokhov Date: Mon May 2 14:42:10 2016 +0100 Drop support for shake-0.15.5 >--------------------------------------------------------------- 00159421655dd8c82a983a8249aa4bc373613893 src/Base.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index a38ea51..5e66a27 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel module Base ( -- * General utilities module Control.Applicative, From git at git.haskell.org Fri Oct 27 00:57:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install rule: copy gmp header (#398) (8972c19) Message-ID: <20171027005752.C78EB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8972c19ff590b61510677ea4057c2021869c4a74/ghc >--------------------------------------------------------------- commit 8972c19ff590b61510677ea4057c2021869c4a74 Author: Zhen Zhang Date: Wed Aug 23 18:51:25 2017 +0800 Install rule: copy gmp header (#398) >--------------------------------------------------------------- 8972c19ff590b61510677ea4057c2021869c4a74 src/Rules/Install.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 0d7336b..4858f40 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -185,6 +185,9 @@ installPackages = do installLibPkgs <- topsortPackages (filter isLibrary activePackages) + -- TODO (izgzhen): figure out what is the root cause of the missing ghc-gmp.h error + copyFile (pkgPath integerGmp -/- "gmp/ghc-gmp.h") (pkgPath integerGmp -/- "ghc-gmp.h") + forM_ installLibPkgs $ \pkg -> do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do From git at git.haskell.org Fri Oct 27 00:57:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot and configure by default. (7166d12) Message-ID: <20171027005756.80BAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7166d12eaa68317d97c8b5663d6b342042432081/ghc >--------------------------------------------------------------- commit 7166d12eaa68317d97c8b5663d6b342042432081 Author: Andrey Mokhov Date: Wed May 4 23:48:15 2016 +0100 Run boot and configure by default. See #234. >--------------------------------------------------------------- 7166d12eaa68317d97c8b5663d6b342042432081 .travis.yml | 2 +- appveyor.yml | 2 +- hadrian.cabal | 2 +- src/CmdLineFlag.hs | 46 ++++++++++++++++---------------------- src/Rules.hs | 4 ++-- src/Rules/Configure.hs | 44 ++++++++++++++++++++++++++++++++++++ src/Rules/Setup.hs | 45 ------------------------------------- src/Settings/Builders/Configure.hs | 7 +----- 8 files changed, 69 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7166d12eaa68317d97c8b5663d6b342042432081 From git at git.haskell.org Fri Oct 27 00:57:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:57:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop defaultDestDir and use Shake's verbosity to control verbose commands (#400) (b25faf5) Message-ID: <20171027005756.D336C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b25faf58f70159b741d6e13da7da329388914d65/ghc >--------------------------------------------------------------- commit b25faf58f70159b741d6e13da7da329388914d65 Author: Zhen Zhang Date: Thu Aug 24 02:44:47 2017 +0800 Drop defaultDestDir and use Shake's verbosity to control verbose commands (#400) >--------------------------------------------------------------- b25faf58f70159b741d6e13da7da329388914d65 README.md | 7 +++++-- src/UserSettings.hs | 14 ++++---------- 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/README.md b/README.md index ecf9728..ad61ef3 100644 --- a/README.md +++ b/README.md @@ -110,9 +110,12 @@ To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` tar To build and install GHC artifacts, run the `install` target. -By default, the artifacts will be installed to `` on your system. For example, -`ghc` will be installed to `/usr/local/bin`. By setting flag `--install-destdir=[DESTDIR]`, +By default, the artifacts will be installed to `` on your system +(in this case, the `DESTDIR` is empty, corresponds to the root of the file system). +For example on UNIX, `ghc` will be installed to `/usr/local/bin`. By setting flag `--install-destdir=[DESTDIR]`, you can install things to non-system path `DESTDIR/` instead. +Make sure you use correct absolute path on Windows, e.g. `C:/path`, +i.e. GHC is installed into `C:/path/usr/local` for the above example. #### Testing diff --git a/src/UserSettings.hs b/src/UserSettings.hs index d77d998..4a1db5b 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -4,7 +4,7 @@ -- accidentally commit them. module UserSettings ( userBuildRoot, userFlavours, userKnownPackages, verboseCommands, - buildProgressColour, successColour, defaultDestDir, defaultStage1Only + buildProgressColour, successColour, defaultStage1Only ) where import Hadrian.Utilities @@ -33,7 +33,9 @@ userKnownPackages = [] -- this is a 'Predicate', hence you can enable verbose output only for certain -- targets, e.g.: @verboseCommands = package ghcPrim at . verboseCommands :: Predicate -verboseCommands = return False +verboseCommands = do + verbosity <- expr getVerbosity + return $ verbosity >= Loud -- | Set colour for build progress messages (e.g. executing a build command). buildProgressColour :: BuildProgressColour @@ -43,14 +45,6 @@ buildProgressColour = BuildProgressColour (Dull, Magenta) successColour :: SuccessColour successColour = SuccessColour (Dull, Green) --- | Path to the GHC install destination. It is empty by default, which --- corresponds to the root of the file system. You can replace it by a specific --- directory. Make sure you use correct absolute path on Windows, e.g. "C:/path". --- The destination directory is used with a @prefix@, commonly @/usr/local@, --- i.e. GHC is installed into "C:/path/usr/local" for the above example. -defaultDestDir :: FilePath -defaultDestDir = "" - {- Stage1Only=YES means: - don't build ghc-stage2 (the executable) From git at git.haskell.org Fri Oct 27 00:58:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use qualified imports in Rules.hs for better readability. (56be38d) Message-ID: <20171027005800.74B903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/56be38d48f28022d370edb1f7d3663630dde9c45/ghc >--------------------------------------------------------------- commit 56be38d48f28022d370edb1f7d3663630dde9c45 Author: Andrey Mokhov Date: Thu May 5 00:16:54 2016 +0100 Use qualified imports in Rules.hs for better readability. >--------------------------------------------------------------- 56be38d48f28022d370edb1f7d3663630dde9c45 src/Rules.hs | 58 +++++++++++++++++++++++++++++----------------------------- 1 file changed, 29 insertions(+), 29 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 2f84917..e3caf6c 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -6,19 +6,19 @@ import Base import Context import Expression import GHC -import Rules.Compile -import Rules.Data -import Rules.Dependencies -import Rules.Documentation -import Rules.Generate -import Rules.Cabal -import Rules.Configure -import Rules.Gmp -import Rules.Libffi -import Rules.Library -import Rules.Perl -import Rules.Program -import Rules.Register +import qualified Rules.Compile +import qualified Rules.Data +import qualified Rules.Dependencies +import qualified Rules.Documentation +import qualified Rules.Generate +import qualified Rules.Cabal +import qualified Rules.Configure +import qualified Rules.Gmp +import qualified Rules.Libffi +import qualified Rules.Library +import qualified Rules.Perl +import qualified Rules.Program +import qualified Rules.Register import Settings allStages :: [Stage] @@ -66,25 +66,25 @@ packageRules = do vanillaContexts = liftM2 vanillaContext allStages knownPackages for_ contexts $ mconcat - [ compilePackage readPackageDb - , buildPackageLibrary ] + [ Rules.Compile.compilePackage readPackageDb + , Rules.Library.buildPackageLibrary ] for_ vanillaContexts $ mconcat - [ buildPackageData - , buildPackageDependencies readPackageDb - , buildPackageDocumentation - , buildPackageGhciLibrary - , generatePackageCode - , buildProgram readPackageDb - , registerPackage writePackageDb ] + [ Rules.Data.buildPackageData + , Rules.Dependencies.buildPackageDependencies readPackageDb + , Rules.Documentation.buildPackageDocumentation + , Rules.Library.buildPackageGhciLibrary + , Rules.Generate.generatePackageCode + , Rules.Program.buildProgram readPackageDb + , Rules.Register.registerPackage writePackageDb ] buildRules :: Rules () buildRules = do - cabalRules - configureRules - generateRules - copyRules - gmpRules - libffiRules - perlScriptRules + Rules.Cabal.cabalRules + Rules.Configure.configureRules + Rules.Generate.copyRules + Rules.Generate.generateRules + Rules.Gmp.gmpRules + Rules.Libffi.libffiRules packageRules + Rules.Perl.perlScriptRules From git at git.haskell.org Fri Oct 27 00:58:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove unnecessary use of -DGENERICS flag (#402) (f189ed4) Message-ID: <20171027005800.C72E13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f189ed4db11f35a9f73e8e7bf7ae311a734aefb0/ghc >--------------------------------------------------------------- commit f189ed4db11f35a9f73e8e7bf7ae311a734aefb0 Author: Ryan Scott Date: Sat Aug 26 11:16:04 2017 -0400 Remove unnecessary use of -DGENERICS flag (#402) Mirroring a change made to GHC in http://git.haskell.org/ghc.git/commit/a28a55211d6fb8d3182b0a9e47656ff9ca8a3766 >--------------------------------------------------------------- f189ed4db11f35a9f73e8e7bf7ae311a734aefb0 src/Settings/Packages/GhcCabal.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 3c07c67..dba4f9b 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -18,7 +18,6 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" - , arg "-DGENERICS" , arg "-optP-include" , arg $ "-optP" ++ pkgPath ghcCabal -/- "cabal_macros_boot.h" , arg "-ilibraries/Cabal/Cabal" From git at git.haskell.org Fri Oct 27 00:58:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot and configure from Hadrian. (dd4f887) Message-ID: <20171027005804.7E8773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dd4f8871b08a1063dcd40770ca7a14caaca09c7a/ghc >--------------------------------------------------------------- commit dd4f8871b08a1063dcd40770ca7a14caaca09c7a Author: Andrey Mokhov Date: Thu May 5 00:43:42 2016 +0100 Run boot and configure from Hadrian. See #234. >--------------------------------------------------------------- dd4f8871b08a1063dcd40770ca7a14caaca09c7a .travis.yml | 5 +---- appveyor.yml | 5 +---- 2 files changed, 2 insertions(+), 8 deletions(-) diff --git a/.travis.yml b/.travis.yml index 2b2e7f5..7d5b699 100644 --- a/.travis.yml +++ b/.travis.yml @@ -54,15 +54,12 @@ install: - ( cd ghc/hadrian && cabal install --only-dependencies ) - ( cd ghc/hadrian && cabal configure ) - - ( cd ghc && ./boot ) - - ( cd ghc && ./configure ) - - cat ghc/hadrian/cfg/system.config - ghc-pkg list script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --skip-configure --no-progress --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --no-progress --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index 0bcf7d7..bb78b80 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -31,13 +31,10 @@ install: - stack exec -- ghc-pkg list - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - - stack exec -- perl boot - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/74a6561d67efe0d2719072cb15885a87fae35696/ghc >--------------------------------------------------------------- commit 74a6561d67efe0d2719072cb15885a87fae35696 Author: Andrey Mokhov Date: Sat Aug 26 17:34:23 2017 +0100 Drop mkUserGuidePart See #402 >--------------------------------------------------------------- 74a6561d67efe0d2719072cb15885a87fae35696 src/GHC.hs | 15 +++++++-------- src/Settings/Default.hs | 1 - 2 files changed, 7 insertions(+), 9 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index b790983..0adf259 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -5,10 +5,10 @@ module GHC ( compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, - hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, - mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm, - templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix, - win32, xhtml, defaultKnownPackages, + hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, + parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, + terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml, + defaultKnownPackages, -- * Package information builderProvenance, programName, nonCabalContext, nonHsMainPackage, autogenPath, @@ -36,9 +36,9 @@ defaultKnownPackages = , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi - , mkUserGuidePart, mtl, parsec, parallel, pretty, primitive, process, rts - , runGhc, stm, templateHaskell, terminfo, text, time, touchy, transformers - , unlit, unix, win32, xhtml ] + , mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm + , templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix + , win32, xhtml ] -- | Package definitions, see 'Package'. array = lib "array" @@ -77,7 +77,6 @@ integerGmp = lib "integer-gmp" integerSimple = lib "integer-simple" iservBin = prg "iserv-bin" `setPath` "iserv" libffi = top "libffi" -mkUserGuidePart = util "mkUserGuidePart" mtl = lib "mtl" parsec = lib "parsec" parallel = lib "parallel" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index c97b79f..d28df6c 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -115,7 +115,6 @@ stage0Packages = do , hsc2hs , hp2ps , hpc - , mkUserGuidePart , mtl , parsec , templateHaskell From git at git.haskell.org Fri Oct 27 00:58:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Differentiate between C and Haskell package (5ef696e) Message-ID: <20171027005808.3D6313A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe/ghc >--------------------------------------------------------------- commit 5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe Author: Andrey Mokhov Date: Sat Aug 26 23:31:31 2017 +0100 Differentiate between C and Haskell package >--------------------------------------------------------------- 5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe hadrian.cabal | 2 +- src/Base.hs | 4 +- src/Context.hs | 37 ++++++--- src/GHC.hs | 153 +++++++++++++++++++------------------ src/Hadrian/Haskell/Cabal.hs | 70 ++++++----------- src/Hadrian/Haskell/Cabal/Parse.hs | 10 +-- src/Hadrian/Haskell/Package.hs | 87 --------------------- src/Hadrian/Package.hs | 119 +++++++++++++++++++++++++++++ src/Rules/Data.hs | 2 +- src/Rules/Install.hs | 7 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Settings/Builders/Ghc.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 6 +- src/Settings/Builders/Haddock.hs | 8 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Utilities.hs | 8 +- 17 files changed, 275 insertions(+), 249 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 5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe From git at git.haskell.org Fri Oct 27 00:58:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop --setup, add --skip-configure. (7cb590a) Message-ID: <20171027005808.12B663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7cb590a6ede9ccfe521e31a116767f46503945c8/ghc >--------------------------------------------------------------- commit 7cb590a6ede9ccfe521e31a116767f46503945c8 Author: Andrey Mokhov Date: Thu May 5 01:37:48 2016 +0100 Drop --setup, add --skip-configure. See #234. [skip ci] >--------------------------------------------------------------- 7cb590a6ede9ccfe521e31a116767f46503945c8 README.md | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/README.md b/README.md index d4adfb1..e0053b0 100644 --- a/README.md +++ b/README.md @@ -32,8 +32,6 @@ system to be in the `hadrian` directory of the GHC source tree: git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/hadrian - ./boot - ./configure # On Windows run ./configure --enable-tarballs-autodownload ``` * Build GHC using `hadrian/build.sh` or `hadrian/build.bat` (on Windows) instead @@ -45,7 +43,7 @@ see [instructions for building GHC on Windows using Stack][windows-build]. Using the build system ---------------------- Once your first build is successful, simply run `build` to rebuild. Most build artefacts -are placed into `.build` and `inplace` directories ([#113][build-artefacts-issue]). +are placed into `_build` and `inplace` directories ([#113][build-artefacts-issue]). #### Command line flags @@ -58,13 +56,17 @@ profiling, which speeds up builds by 3-4x). * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). -* `--setup[=CONFIGURE_ARGS]`: setup the build system by running the `configure` script -with `CONFIGURE_ARGS` arguments; also run the `boot` script to create the `configure` -script if necessary. On Windows, download the required tarballs by executing -`mk/get-win32-tarballs.sh` with appropriate parameters. You do not have to -use this functionality of the new build system; feel free to run `boot` and `configure` -scripts manually, as you do when using `make`. Beware: `--setup` uses network I/O -which may sometimes be undesirable. +* `--skip-configure`: use this flag to suppress the default behaviour of Hadrian that +runs the `boot` and `configure` scripts automatically if need be, so that you don't have +to remember to run them manually. With `--skip-configure` you will need to manually run: + + ```bash + ./boot + ./configure # On Windows run ./configure --enable-tarballs-autodownload + ``` +as you normally do when using `make`. Beware, by default Hadrian may do network I/O on +Windows to download necessary tarballs, which may sometimes be undesirable; `--skip-configure` +is your friend in such cases. * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. From git at git.haskell.org Fri Oct 27 00:58:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify package lists (fc564b8) Message-ID: <20171027005815.7FFA83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fc564b8b05ed8e01493437635266df40dd125311/ghc >--------------------------------------------------------------- commit fc564b8b05ed8e01493437635266df40dd125311 Author: Andrey Mokhov Date: Sun Aug 27 03:08:20 2017 +0100 Simplify package lists See #403 >--------------------------------------------------------------- fc564b8b05ed8e01493437635266df40dd125311 src/Expression.hs | 3 +- src/Flavour.hs | 38 +++++++++++++-------- src/GHC.hs | 79 +++++++++++++++++++++++++++++++++++++++++++- src/Rules.hs | 2 +- src/Rules/Wrappers.hs | 3 +- src/Settings.hs | 9 +++-- src/Settings/Default.hs | 75 +---------------------------------------- src/Settings/Default.hs-boot | 4 +-- src/Utilities.hs | 7 ++-- 9 files changed, 117 insertions(+), 103 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 fc564b8b05ed8e01493437635266df40dd125311 From git at git.haskell.org Fri Oct 27 00:58:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do not run CI in verbose mode (f7c9b8b) Message-ID: <20171027005811.B61973A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f7c9b8bf7a9816bedaf4e65271bd4993c1571143/ghc >--------------------------------------------------------------- commit f7c9b8bf7a9816bedaf4e65271bd4993c1571143 Author: Andrey Mokhov Date: Sun Aug 27 00:47:05 2017 +0100 Do not run CI in verbose mode >--------------------------------------------------------------- f7c9b8bf7a9816bedaf4e65271bd4993c1571143 .travis.yml | 6 +++--- appveyor.yml | 2 +- circle.yml | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 48ed171..9082ef6 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - ./build.cabal.sh selftest # Build GHC - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- - os: linux env: MODE="--flavour=quickest --integer-simple" @@ -40,7 +40,7 @@ matrix: script: # Build GHC - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. @@ -56,7 +56,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- install: # Add Cabal to PATH diff --git a/appveyor.yml b/appveyor.yml index 3b2e43b..451d5d5 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -33,7 +33,7 @@ build_script: - stack exec hadrian -- --directory ".." selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- + - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-info=brief --progress-colour=never --profile=- # Test GHC binary - cd .. diff --git a/circle.yml b/circle.yml index 606664a..b038689 100644 --- a/circle.yml +++ b/circle.yml @@ -33,7 +33,7 @@ compile: - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- test: override: From git at git.haskell.org Fri Oct 27 00:58:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of partial functions. (a7adf8c) Message-ID: <20171027005815.32EF13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7adf8c5b2719aed8c17b029a74ebc190360df28/ghc >--------------------------------------------------------------- commit a7adf8c5b2719aed8c17b029a74ebc190360df28 Author: Andrey Mokhov Date: Thu May 5 03:13:49 2016 +0100 Get rid of partial functions. >--------------------------------------------------------------- a7adf8c5b2719aed8c17b029a74ebc190360df28 src/Rules/Gmp.hs | 23 +++++++++++------------ 1 file changed, 11 insertions(+), 12 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index cceda8e..d98bc3b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -71,14 +71,15 @@ gmpRules = do -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] - when (length tarballs /= 1) $ - putError $ "gmpRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." + tarball <- case tarballs of + [file] -> return $ unifyPath file + _ -> putError $ "gmpRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." - need tarballs withTempDir $ \dir -> do let tmp = unifyPath dir - build $ Target gmpContext Tar tarballs [tmp] + need [tarball] + build $ Target gmpContext Tar [tarball] [tmp] forM_ gmpPatches $ \src -> do let patch = takeFileName src @@ -86,13 +87,11 @@ gmpRules = do copyFile src patchPath applyPatch tmp patch - let filename = dropExtension . dropExtension . takeFileName - $ head tarballs - suffix = "-nodoc-patched" - unless (suffix `isSuffixOf` filename) $ - putError $ "gmpRules: expected suffix " ++ suffix - ++ " (found: " ++ filename ++ ")." - let libName = take (length filename - length suffix) filename + let name = dropExtension . dropExtension $ takeFileName tarball + libName <- case stripSuffix "-nodoc-patched" name of + Just rest -> return rest + Nothing -> putError $ "gmpRules: expected suffix " + ++ "-nodoc-patched (found: " ++ name ++ ")." moveDirectory (tmp -/- libName) gmpBuildPath From git at git.haskell.org Fri Oct 27 00:58:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor GHC/user packages, move builder-specific functions into Builder (0781e16) Message-ID: <20171027005819.74F5A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0781e16f1184adc1b35921924326df410ded3e31/ghc >--------------------------------------------------------------- commit 0781e16f1184adc1b35921924326df410ded3e31 Author: Andrey Mokhov Date: Mon Aug 28 01:56:06 2017 +0100 Refactor GHC/user packages, move builder-specific functions into Builder See #403 >--------------------------------------------------------------- 0781e16f1184adc1b35921924326df410ded3e31 src/Base.hs | 2 - src/Builder.hs | 91 +++++++++++++++++++++++++++++++++++- src/Expression.hs | 4 +- src/GHC.hs | 97 +++++++++++---------------------------- src/Oracles/ModuleFiles.hs | 1 + src/Rules.hs | 6 ++- src/Rules/Documentation.hs | 2 +- src/Rules/Perl.hs | 2 + src/Rules/SourceDist.hs | 1 + src/Settings.hs | 37 ++------------- src/Settings/Builders/Ghc.hs | 6 +-- src/Settings/Builders/GhcCabal.hs | 10 ++-- src/Target.hs | 3 +- src/UserSettings.hs | 8 ++-- src/Utilities.hs | 13 +----- 15 files changed, 148 insertions(+), 135 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 0781e16f1184adc1b35921924326df410ded3e31 From git at git.haskell.org Fri Oct 27 00:58:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add cross compilation (#401) (cbc2f63) Message-ID: <20171027005823.9058D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbc2f63dc60e084ffda3557c64a68856de924634/ghc >--------------------------------------------------------------- commit cbc2f63dc60e084ffda3557c64a68856de924634 Author: Zhen Zhang Date: Mon Aug 28 18:26:27 2017 +0800 Add cross compilation (#401) Tested with arm-linux-gnueabihf. >--------------------------------------------------------------- cbc2f63dc60e084ffda3557c64a68856de924634 doc/cross-compile.md | 57 ++++++++++++++++++++++++++++++++++++++ hadrian.cabal | 2 ++ src/Oracles/Flag.hs | 5 +--- src/Rules.hs | 1 + src/Settings.hs | 7 +---- src/Settings/Builders/Common.hs | 3 +- src/Settings/Default.hs | 6 +++- src/Settings/Packages/Compiler.hs | 2 ++ src/Settings/Packages/Ghc.hs | 4 ++- src/Settings/Packages/GhcPkg.hs | 8 ++++++ src/Settings/Packages/Haskeline.hs | 10 +++++++ src/UserSettings.hs | 12 ++++++-- 12 files changed, 101 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 cbc2f63dc60e084ffda3557c64a68856de924634 From git at git.haskell.org Fri Oct 27 00:58:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Get rid of partial functions. (fa57784) Message-ID: <20171027005827.4CA583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fa57784081e696d90b305601b9cfd960841f082c/ghc >--------------------------------------------------------------- commit fa57784081e696d90b305601b9cfd960841f082c Author: Andrey Mokhov Date: Thu May 5 03:24:45 2016 +0100 Get rid of partial functions. >--------------------------------------------------------------- fa57784081e696d90b305601b9cfd960841f082c src/Rules/Libffi.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 17067ad..424b552 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -76,17 +76,18 @@ libffiRules = do createDirectory $ buildRootPath -/- stageString Stage0 tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - when (length tarballs /= 1) $ - putError $ "libffiRules: exactly one libffi tarball expected" - ++ "(found: " ++ show tarballs ++ ")." + tarball <- case tarballs of + [file] -> return $ unifyPath file + _ -> putError $ "libffiRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." - need tarballs - let libname = dropExtension . dropExtension . takeFileName $ head tarballs + need [tarball] + let libname = dropExtension . dropExtension $ takeFileName tarball removeDirectory (buildRootPath -/- libname) -- TODO: Simplify. actionFinally (do - build $ Target libffiContext Tar tarballs [buildRootPath] + build $ Target libffiContext Tar [tarball] [buildRootPath] moveDirectory (buildRootPath -/- libname) libffiBuildPath) $ removeFiles buildRootPath [libname "*"] From git at git.haskell.org Fri Oct 27 00:58:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need patch file by default. (6a09a6b) Message-ID: <20171027005823.446F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6a09a6b9720f8782224eddd39db9f4ec9cd3164b/ghc >--------------------------------------------------------------- commit 6a09a6b9720f8782224eddd39db9f4ec9cd3164b Author: Andrey Mokhov Date: Thu May 5 03:19:02 2016 +0100 Don't need patch file by default. >--------------------------------------------------------------- 6a09a6b9720f8782224eddd39db9f4ec9cd3164b src/Rules/Actions.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index edf98eb..32d2544 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -146,7 +146,6 @@ runMakeWithVerbosity verbose dir args = do applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch - need [file] needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file From git at git.haskell.org Fri Oct 27 00:25:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix GenApply arguments (e3aedfe) Message-ID: <20171027002525.B5FD73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3aedfef1d68e98b59d19307203a16895ac98de6/ghc >--------------------------------------------------------------- commit e3aedfef1d68e98b59d19307203a16895ac98de6 Author: Andrey Mokhov Date: Sun Oct 23 01:58:24 2016 +0100 Fix GenApply arguments >--------------------------------------------------------------- e3aedfef1d68e98b59d19307203a16895ac98de6 src/Settings/Builders/GenApply.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/Builders/GenApply.hs b/src/Settings/Builders/GenApply.hs index 6ebb295..b268c07 100644 --- a/src/Settings/Builders/GenApply.hs +++ b/src/Settings/Builders/GenApply.hs @@ -2,6 +2,5 @@ module Settings.Builders.GenApply (genApplyBuilderArgs) where import Settings.Builders.Common --- TODO: Dead code? ifeq "$(GhcUnregisterised)" "YES" GENAPPLY_OPTS = -u genApplyBuilderArgs :: Args -genApplyBuilderArgs = mempty +genApplyBuilderArgs = builder GenApply ? flag GhcUnregisterised ? arg "-u" From git at git.haskell.org Fri Oct 27 00:25:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix integer-gmp problem on Travis, see #103. (ae6f58d) Message-ID: <20171027002528.7B87F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8/ghc >--------------------------------------------------------------- commit ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8 Author: Andrey Mokhov Date: Tue Jan 5 17:02:55 2016 +0000 Attempt to fix integer-gmp problem on Travis, see #103. >--------------------------------------------------------------- ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8 src/Rules/Generate.hs | 16 ++++++---------- src/Rules/IntegerGmp.hs | 48 ++++++++++++++++++++++++++++++++---------------- src/Rules/Library.hs | 8 ++++++-- 3 files changed, 44 insertions(+), 28 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 921c672..2b33a53 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -14,6 +14,8 @@ import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles import Rules.Actions +import Rules.IntegerGmp +import Rules.Libffi import Rules.Resources (Resources) import Settings import Settings.Builders.DeriveConstants @@ -33,13 +35,12 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -libffiDependencies :: [FilePath] -libffiDependencies = (targetPath Stage1 rts -/-) <$> - [ "build/ffi.h" - , "build/ffitarget.h" ] +integerGmpDependencies :: [FilePath] +integerGmpDependencies = [integerGmpLibraryH] defaultDependencies :: [FilePath] -defaultDependencies = includesDependencies ++ libffiDependencies +defaultDependencies = + includesDependencies ++ libffiDependencies ++ integerGmpDependencies derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = (derivedConstantsPath -/-) <$> @@ -69,15 +70,10 @@ compilerDependencies stage = , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] -integerGmpDependencies :: [FilePath] -integerGmpDependencies = ((pkgPath integerGmp -/- "gmp") -/-) <$> - [ "gmp.h" ] -- identical to integerGmpLibraryH, but doesn't require the import. - generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == rts = derivedConstantsDependencies - | pkg == integerGmp = integerGmpDependencies | stage == Stage0 = defaultDependencies | otherwise = [] diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 9bbf482..91ca074 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -1,4 +1,4 @@ -module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary, integerGmpLibraryH) where +module Rules.IntegerGmp (integerGmpRules, integerGmpObjects, integerGmpLibraryH) where import Base import Expression @@ -8,16 +8,25 @@ import Rules.Actions import Settings.User integerGmpBase :: FilePath -integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp" +integerGmpBase = "libraries/integer-gmp/gmp" integerGmpBuild :: FilePath integerGmpBuild = integerGmpBase -/- "gmpbuild" +integerGmpObjects :: FilePath +integerGmpObjects = integerGmpBase -/- "objs" + integerGmpLibrary :: FilePath integerGmpLibrary = integerGmpBase -/- "libgmp.a" +integerGmpLibraryInTreeH :: FilePath +integerGmpLibraryInTreeH = integerGmpBase -/- "gmp.h" + integerGmpLibraryH :: FilePath -integerGmpLibraryH = integerGmpBase -/- "gmp.h" +integerGmpLibraryH = pkgPath integerGmp -/- "include/ghc-gmp.h" + +integerGmpLibraryFakeH :: FilePath +integerGmpLibraryFakeH = integerGmpBase -/- "ghc-gmp.h" -- relative to integerGmpBuild integerGmpPatch :: FilePath @@ -49,12 +58,14 @@ configureArguments = do -- TODO: we rebuild integer-gmp every time. integerGmpRules :: Rules () integerGmpRules = do - integerGmpLibrary %> \_ -> do + + -- TODO: split into multiple rules + integerGmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/IntegerGmp.hs"] -- remove the old build folder, if it exists. liftIO $ removeFiles integerGmpBuild ["//*"] - liftIO $ removeFiles (integerGmpBase -/- "objs") ["//*"] + liftIO $ removeFiles (integerGmpObjects) ["//*"] -- unpack the gmp tarball. -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is @@ -91,19 +102,24 @@ integerGmpRules = do args <- configureArguments runConfigure integerGmpBuild envs args - runMake integerGmpBuild [] + -- check whether we need to build in tree gmp + -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` + configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" + if "HaveFrameworkGMP = YES" `isInfixOf` configMk + then do + putBuild "\n| GMP framework detected and will be used" + copyFile integerGmpLibraryFakeH integerGmpLibraryH + else do + putBuild "\n| No GMP framework detected" + runMake integerGmpBuild [] - -- copy library and header - -- TODO: why copy library, can we move it instead? - forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> - copyFile (integerGmpBuild -/- file) (integerGmpBase -/- takeFileName file) + copyFile integerGmpLibraryInTreeH integerGmpLibraryH + -- TODO: why copy library, can we move it instead? + copyFile (integerGmpBuild -/- ".libs/libgmp.a") integerGmpLibrary - let objsDir = integerGmpBase -/- "objs" - createDirectory objsDir - build $ fullTarget target Ar [integerGmpLibrary] [objsDir] + createDirectory integerGmpObjects + build $ fullTarget target Ar [integerGmpLibrary] [integerGmpObjects] - runBuilder Ranlib [integerGmpLibrary] + runBuilder Ranlib [integerGmpLibrary] putSuccess "| Successfully built custom library 'integer-gmp'" - - integerGmpLibraryH %> \_ -> need [integerGmpLibrary] diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index d9a1a48..41e7b3d 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -79,6 +79,10 @@ hSources target = do extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do - need [integerGmpLibrary] - getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"] + need [integerGmpLibraryH] + objsExist <- doesDirectoryExist integerGmpObjects + putBuild $ "objsExist = " ++ show objsExist + if objsExist + then getDirectoryFiles "" [integerGmpObjects -/- "*.o"] + else return [] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:25:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to @WhatIsGcc@ being renamed to @CC@ in GHC HEAD (1c137b3) Message-ID: <20171027002529.096A43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1c137b3d58a85d01eb9018eca927616077d87098/ghc >--------------------------------------------------------------- commit 1c137b3d58a85d01eb9018eca927616077d87098 Author: Herbert Valerio Riedel Date: Sun Apr 17 15:46:06 2016 +0200 Adapt to @WhatIsGcc@ being renamed to @CC@ in GHC HEAD >--------------------------------------------------------------- 1c137b3d58a85d01eb9018eca927616077d87098 cfg/system.config.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 0b2e1f1..3c74076 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -7,7 +7,7 @@ alex = @AlexCmd@ ar = @ArCmd@ -cc = @WhatGccIsCalled@ +cc = @CC@ happy = @HappyCmd@ hs-cpp = @HaskellCPPCmd@ hscolour = @HSCOLOUR@ From git at git.haskell.org Fri Oct 27 00:25:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't generate files into the source tree (7303fcf) Message-ID: <20171027002529.82A133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7303fcf142de20186728a5b7fdea62e5a8fc83d6/ghc >--------------------------------------------------------------- commit 7303fcf142de20186728a5b7fdea62e5a8fc83d6 Author: Andrey Mokhov Date: Sun Oct 23 02:27:32 2016 +0100 Don't generate files into the source tree See #113. >--------------------------------------------------------------- 7303fcf142de20186728a5b7fdea62e5a8fc83d6 src/Rules/Generate.hs | 10 ---------- 1 file changed, 10 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 0a4305c..698299d 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -143,24 +143,14 @@ generatePackageCode context@(Context stage pkg _) = build $ Target context GenApply [] [file] priority 2.0 $ do - -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- contextDirectory context -/- "build" - olden f = oldPath ++ (drop (length (buildPath context)) f) - when (pkg == compiler) $ path -/- "Config.hs" %> \file -> do file <~ generateConfigHs - olden file <~ generateConfigHs -- TODO: get rid of this (#113) when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH when (pkg == ghcPkg) $ path -/- "Version.hs" %> \file -> do file <~ generateVersionHs - olden file <~ generateVersionHs -- TODO: get rid of this (#113) - - when (pkg == runGhc) $ path -/- "Main.hs" %> \file -> do - copyFileChanged (pkgPath pkg -/- "runghc.hs") file - putSuccess $ "| Successfully generated " ++ file ++ "." copyRules :: Rules () copyRules = do From git at git.haskell.org Fri Oct 27 00:25:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Force integerGmp package to be configured before reading config.mk file, see #103. (a33ab01) Message-ID: <20171027002532.752643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a33ab012f0e9e997035d7bd6c3ce0535cc9cbed2/ghc >--------------------------------------------------------------- commit a33ab012f0e9e997035d7bd6c3ce0535cc9cbed2 Author: Andrey Mokhov Date: Tue Jan 5 19:35:34 2016 +0000 Force integerGmp package to be configured before reading config.mk file, see #103. >--------------------------------------------------------------- a33ab012f0e9e997035d7bd6c3ce0535cc9cbed2 src/Rules/IntegerGmp.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs index 91ca074..f86371c 100644 --- a/src/Rules/IntegerGmp.hs +++ b/src/Rules/IntegerGmp.hs @@ -6,6 +6,7 @@ import GHC import Oracles.Config.Setting import Rules.Actions import Settings.User +import Settings.TargetDirectory integerGmpBase :: FilePath integerGmpBase = "libraries/integer-gmp/gmp" @@ -104,6 +105,7 @@ integerGmpRules = do -- check whether we need to build in tree gmp -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` + need [pkgDataFile Stage1 integerGmp] configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk" if "HaveFrameworkGMP = YES" `isInfixOf` configMk then do From git at git.haskell.org Fri Oct 27 00:28:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop support for shake-0.15.5 (0015942) Message-ID: <20171027002821.75D103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/00159421655dd8c82a983a8249aa4bc373613893/ghc >--------------------------------------------------------------- commit 00159421655dd8c82a983a8249aa4bc373613893 Author: Andrey Mokhov Date: Mon May 2 14:42:10 2016 +0100 Drop support for shake-0.15.5 >--------------------------------------------------------------- 00159421655dd8c82a983a8249aa4bc373613893 src/Base.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Base.hs b/src/Base.hs index a38ea51..5e66a27 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -fno-warn-dodgy-imports #-} -- for Development.Shake.parallel module Base ( -- * General utilities module Control.Applicative, From git at git.haskell.org Fri Oct 27 00:28:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Data and Register build rules (7ebb204) Message-ID: <20171027002822.659033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ebb2045222d9c800d523ed93e32680d8b07fc10/ghc >--------------------------------------------------------------- commit 7ebb2045222d9c800d523ed93e32680d8b07fc10 Author: Andrey Mokhov Date: Sun Nov 27 01:48:25 2016 +0000 Refactor Data and Register build rules >--------------------------------------------------------------- 7ebb2045222d9c800d523ed93e32680d8b07fc10 src/Rules/Data.hs | 21 ++++++++++++++++++++- src/Rules/Register.hs | 39 ++++----------------------------------- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Path.hs | 6 +++--- 5 files changed, 29 insertions(+), 41 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index e16f03b..1314cc4 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -9,6 +9,7 @@ import Oracles.Dependencies import Oracles.Path import Rules.Generate import Rules.Libffi +import Settings.Packages.Rts import Settings.Path import Target import UserSettings @@ -17,7 +18,8 @@ import Util -- | Build @package-data.mk@ by using ghc-cabal utility to process .cabal files. buildPackageData :: Context -> Rules () buildPackageData context at Context {..} = do - let cabalFile = pkgCabalFile package + let path = buildPath context + cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile context @@ -35,6 +37,23 @@ buildPackageData context at Context {..} = do build $ Target context GhcCabal [cabalFile] [mk] postProcessPackageData context mk + pkgInplaceConfig context %> \conf -> do + need [dataFile] -- ghc-cabal builds inplace package configuration file + if package == rts + then do + need [rtsConfIn] + build $ Target context HsCpp [rtsConfIn] [conf] + fixFile conf $ unlines + . map + ( replace "\"\"" "" + . replace "rts/dist/build" rtsBuildPath + . replace "includes/dist-derivedconstants/header" generatedPath ) + . lines + else do + top <- topDirectory + let oldPath = top -/- path "build" + fixFile conf $ unlines . map (replace oldPath path) . lines + -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps. priority 2.0 $ do when (package `elem` [hp2ps, rts, touchy, unlit]) $ dataFile %> diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index b7e12d1..19ce0e3 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -4,9 +4,6 @@ import Base import Context import Expression import GHC -import Oracles.Path -import Rules.Libffi -import Settings.Packages.Rts import Settings.Path import Target import UserSettings @@ -16,40 +13,12 @@ import Util -- by running the @ghc-pkg@ utility. registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context at Context {..} = when (stage <= Stage1) $ do - let dir = packageDbDirectory stage + let confIn = pkgInplaceConfig context + dir = packageDbDirectory stage matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do - -- This produces inplace-pkg-config. TODO: Add explicit tracking. - need [pkgDataFile context] - - -- Post-process inplace-pkg-config. - top <- topDirectory - let path = buildPath context - pkgConfig = inplacePkgConfig context - oldPath = top -/- path "build" - - fixFile pkgConfig $ unlines . map (replace oldPath path) . lines - - buildWithResources rs $ Target context (GhcPkg stage) [pkgConfig] [conf] - - when (package == rts && stage == Stage1) $ do - packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do - need [rtsConf] - buildWithResources rs $ Target context (GhcPkg stage) [rtsConf] [conf] - - rtsConf %> \_ -> do - need [pkgDataFile rtsContext, rtsConfIn] - build $ Target context HsCpp [rtsConfIn] [rtsConf] - - let fixRtsConf = unlines - . map - ( replace "\"\"" "" - . replace "rts/dist/build" rtsBuildPath - . replace "includes/dist-derivedconstants/header" generatedPath ) - . filter (not . null) - . lines - - fixFile rtsConf fixRtsConf + need [confIn] + buildWithResources rs $ Target context (GhcPkg stage) [confIn] [conf] when (package == ghc) $ packageDbStamp stage %> \stamp -> do removeDirectory dir diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index 5156d71..15d5249 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -18,4 +18,4 @@ updateArgs = notM initPredicate ? do , arg "--force" , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs - , arg . inplacePkgConfig =<< getContext ] + , arg . pkgInplaceConfig =<< getContext ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 40b85e4..e7c3a60 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -18,7 +18,7 @@ rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" rtsConf :: FilePath -rtsConf = inplacePkgConfig rtsContext +rtsConf = pkgInplaceConfig rtsContext rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index cbe1612..934a0ec 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -4,7 +4,7 @@ module Settings.Path ( gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath, inplacePkgConfig + installPath, autogenPath, pkgInplaceConfig ) where import Base @@ -61,8 +61,8 @@ autogenPath context at Context {..} autogen dir = buildPath context -/- dir -/- "autogen" -- | Path to inplace package configuration of a given 'Context'. -inplacePkgConfig :: Context -> FilePath -inplacePkgConfig context = buildPath context -/- "inplace-pkg-config" +pkgInplaceConfig :: Context -> FilePath +pkgInplaceConfig context = buildPath context -/- "inplace-pkg-config" -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath From git at git.haskell.org Fri Oct 27 00:28:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move cabal folder inside /home/ghc. (3008453) Message-ID: <20171027002822.C57EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3008453094756facfea0d45fcc0b5823c1c54b01/ghc >--------------------------------------------------------------- commit 3008453094756facfea0d45fcc0b5823c1c54b01 Author: Andrey Mokhov Date: Wed Jan 6 22:32:46 2016 +0000 Move cabal folder inside /home/ghc. See #110. [skip ci] >--------------------------------------------------------------- 3008453094756facfea0d45fcc0b5823c1c54b01 .appveyor.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index eb57bd8..a3dd1ef 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,22 +1,22 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" cache: - - "C:\\msys64\\home\\cabal" + - "C:\\msys64\\home\\ghc\\.cabal" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /home/cabal" + - bash -lc "mkdir -p /home/ghc/.cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal --config-file=/home/cabal update" - - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" + - bash -lc "cabal --config-file=/home/ghc/.cabal update" + - bash -lc "cabal --config-file=/home/ghc/.cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal \install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/ghc/.cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:28:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot and configure by default. (7166d12) Message-ID: <20171027002825.16AFB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7166d12eaa68317d97c8b5663d6b342042432081/ghc >--------------------------------------------------------------- commit 7166d12eaa68317d97c8b5663d6b342042432081 Author: Andrey Mokhov Date: Wed May 4 23:48:15 2016 +0100 Run boot and configure by default. See #234. >--------------------------------------------------------------- 7166d12eaa68317d97c8b5663d6b342042432081 .travis.yml | 2 +- appveyor.yml | 2 +- hadrian.cabal | 2 +- src/CmdLineFlag.hs | 46 ++++++++++++++++---------------------- src/Rules.hs | 4 ++-- src/Rules/Configure.hs | 44 ++++++++++++++++++++++++++++++++++++ src/Rules/Setup.hs | 45 ------------------------------------- src/Settings/Builders/Configure.hs | 7 +----- 8 files changed, 69 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7166d12eaa68317d97c8b5663d6b342042432081 From git at git.haskell.org Fri Oct 27 00:28:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move RTS path settings to Settings.Path (46ef16f) Message-ID: <20171027002826.4B1663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46ef16f18f752ad2df2c92fafdf5c208a4589e2c/ghc >--------------------------------------------------------------- commit 46ef16f18f752ad2df2c92fafdf5c208a4589e2c Author: Andrey Mokhov Date: Sun Nov 27 11:42:25 2016 +0000 Move RTS path settings to Settings.Path >--------------------------------------------------------------- 46ef16f18f752ad2df2c92fafdf5c208a4589e2c src/Rules.hs | 1 - src/Rules/Data.hs | 1 - src/Rules/Generate.hs | 1 - src/Settings/Packages/Rts.hs | 14 +------------- src/Settings/Path.hs | 10 +++++++++- 5 files changed, 10 insertions(+), 17 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 506fe2c..832bf4c 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -19,7 +19,6 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings -import Settings.Packages.Rts import Settings.Path allStages :: [Stage] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 1314cc4..5c8a63b 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -9,7 +9,6 @@ import Oracles.Dependencies import Oracles.Path import Rules.Generate import Rules.Libffi -import Settings.Packages.Rts import Settings.Path import Target import UserSettings diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index e84313a..5d557b4 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -17,7 +17,6 @@ import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Rules.Libffi -import Settings.Packages.Rts import Settings.Path import Target import UserSettings diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e7c3a60..d10c6f0 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,6 +1,4 @@ -module Settings.Packages.Rts ( - rtsPackageArgs, rtsConfIn, rtsConf, rtsContext, rtsLibffiLibraryName - ) where +module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibraryName) where import Base import GHC @@ -9,16 +7,6 @@ import Oracles.Config.Setting import Oracles.Path import Predicate import Settings -import Settings.Path - -rtsContext :: Context -rtsContext = vanillaContext Stage1 rts - -rtsConfIn :: FilePath -rtsConfIn = pkgPath rts -/- "package.conf.in" - -rtsConf :: FilePath -rtsConf = pkgInplaceConfig rtsContext rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 934a0ec..8999300 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -4,7 +4,7 @@ module Settings.Path ( gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath, pkgInplaceConfig + installPath, autogenPath, pkgInplaceConfig, rtsContext, rtsConfIn ) where import Base @@ -100,6 +100,14 @@ pkgFile context prefix suffix = do componentId <- pkgData $ ComponentId path return $ path -/- prefix ++ componentId ++ suffix +-- | RTS is considered a Stage1 package. This determines RTS build path. +rtsContext :: Context +rtsContext = vanillaContext Stage1 rts + +-- | Path to RTS package configuration file, to be processed by HsCpp. +rtsConfIn :: FilePath +rtsConfIn = pkgPath rts -/- "package.conf.in" + -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" From git at git.haskell.org Fri Oct 27 00:28:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:28:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Keep experimenting with cabal folder. (d913235) Message-ID: <20171027002826.CD5D73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d913235b1f6e907a63ee8974e1f09c20b711bf0a/ghc >--------------------------------------------------------------- commit d913235b1f6e907a63ee8974e1f09c20b711bf0a Author: Andrey Mokhov Date: Wed Jan 6 22:44:46 2016 +0000 Keep experimenting with cabal folder. See #110. [skip ci] >--------------------------------------------------------------- d913235b1f6e907a63ee8974e1f09c20b711bf0a .appveyor.yml | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/.appveyor.yml b/.appveyor.yml index a3dd1ef..751bc1f 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -1,22 +1,23 @@ clone_folder: "C:\\msys64\\home\\ghc\\shake-build" cache: - - "C:\\msys64\\home\\ghc\\.cabal" + - "C:\\msys64\\home\\cabal" install: - set MSYSTEM=MINGW64 - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\local\bin;C:\msys64\usr\bin;%PATH% - bash -lc "pacman -S --noconfirm git binutils p7zip gcc" - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.1/ghc-7.10.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - bash -lc "mkdir -p /home/ghc/.cabal" + - bash -lc "mkdir -p /home/cabal" + - bash -lc "chmod -R 777 /home/cabal" - bash -lc "mkdir -p /usr/local" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -LsS https://www.haskell.org/cabal/release/cabal-install-1.22.0.0/cabal-1.22.0.0-i386-unknown-mingw32.tar.gz | tar -xz -C /usr/local/bin" - bash -lc "mv /usr/local/bin/cabal-1.22.0.0-i386-unknown-mingw32.exe /usr/local/bin/cabal.exe" - - bash -lc "cabal --config-file=/home/ghc/.cabal update" - - bash -lc "cabal --config-file=/home/ghc/.cabal install -j --prefix=/usr/local alex happy" + - bash -lc "cabal --config-file=/home/cabal update" + - bash -lc "cabal --config-file=/home/cabal install -j --prefix=/usr/local alex happy" - bash -lc "git clone --recursive git://git.haskell.org/ghc.git /home/ghc" - - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/ghc/.cabal install --only-dependencies" + - bash -lc "cd /home/ghc/shake-build && cabal --config-file=/home/cabal install --only-dependencies" build_script: - bash -lc "cd /home/ghc && ./boot" From git at git.haskell.org Fri Oct 27 00:38:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to MIT license (46a0061) Message-ID: <20171027003848.5741E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46a00614fc68bd489f0d21391ceadf85abf3dae3/ghc >--------------------------------------------------------------- commit 46a00614fc68bd489f0d21391ceadf85abf3dae3 Author: Andrey Mokhov Date: Wed Aug 16 23:04:59 2017 +0100 Switch to MIT license >--------------------------------------------------------------- 46a00614fc68bd489f0d21391ceadf85abf3dae3 LICENSE | 42 +++++++++++++++++------------------------- 1 file changed, 17 insertions(+), 25 deletions(-) diff --git a/LICENSE b/LICENSE index fbedb41..ff60fa8 100644 --- a/LICENSE +++ b/LICENSE @@ -1,29 +1,21 @@ -BSD License +MIT License -Copyright (c) 2014, Andrey Mokhov -All rights reserved. +Copyright (c) 2014-2017 Andrey Mokhov -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are met: +Permission is hereby granted, free of charge, to any person obtaining a copy +of this software and associated documentation files (the "Software"), to deal +in the Software without restriction, including without limitation the rights +to use, copy, modify, merge, publish, distribute, sublicense, and/or sell +copies of the Software, and to permit persons to whom the Software is +furnished to do so, subject to the following conditions: -* Redistributions of source code must retain the above copyright notice, this - list of conditions and the following disclaimer. +The above copyright notice and this permission notice shall be included in all +copies or substantial portions of the Software. -* Redistributions in binary form must reproduce the above copyright notice, - this list of conditions and the following disclaimer in the documentation - and/or other materials provided with the distribution. - -* Neither the name of the Hadrian project nor the names of its - contributors may be used to endorse or promote products derived from - this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" -AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE -IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE -DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE -FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL -DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR -SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER -CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, -OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR +IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, +FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE +AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER +LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, +OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE +SOFTWARE. From git at git.haskell.org Fri Oct 27 00:38:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use --flavour=quickest (0cfd96d) Message-ID: <20171027003848.563953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0cfd96d4dd23ca565f9922357c64c769b78863c1/ghc >--------------------------------------------------------------- commit 0cfd96d4dd23ca565f9922357c64c769b78863c1 Author: Andrey Mokhov Date: Sat Aug 20 17:28:48 2016 +0100 Use --flavour=quickest >--------------------------------------------------------------- 0cfd96d4dd23ca565f9922357c64c769b78863c1 doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 4674ff4..a70f85a 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -11,9 +11,9 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ cd ghc stack exec -- git clone git://github.com/snowleopard/hadrian stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quick + stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quickest -The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quick` flag from the last command line (this will slow down the build to about an hour). +The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quickest` flag from the last command line (this will slow down the build to about an hour). #### Future ideas From git at git.haskell.org Fri Oct 27 00:38:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: In the removeDirectory operation, use removeIfExists (2dd57cc) Message-ID: <20171027003850.872CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2dd57cc06f172145f668a89d29756de6dccceb0f/ghc >--------------------------------------------------------------- commit 2dd57cc06f172145f668a89d29756de6dccceb0f Author: Neil Mitchell Date: Tue Jan 12 22:43:01 2016 +0000 In the removeDirectory operation, use removeIfExists >--------------------------------------------------------------- 2dd57cc06f172145f668a89d29756de6dccceb0f src/Rules/Actions.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index a968160..55f81dd 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -77,7 +77,7 @@ createDirectory dir = do removeDirectory :: FilePath -> Action () removeDirectory dir = do putBuild $ "| Remove directory " ++ dir - liftIO $ IO.removeDirectoryRecursive dir + removeDirectoryIfExists dir -- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:38:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:38:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a Stack build script for Windows (bbd884c) Message-ID: <20171027003852.C06473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbd884c841d8508abb3dabbbb5cf5abe2e69f4da/ghc >--------------------------------------------------------------- commit bbd884c841d8508abb3dabbbb5cf5abe2e69f4da Author: Andrey Mokhov Date: Sat Aug 20 18:02:33 2016 +0100 Add a Stack build script for Windows See #283 >--------------------------------------------------------------- bbd884c841d8508abb3dabbbb5cf5abe2e69f4da build.stack.bat | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/build.stack.bat b/build.stack.bat new file mode 100644 index 0000000..3586290 --- /dev/null +++ b/build.stack.bat @@ -0,0 +1,8 @@ + at rem Change the current directory to the one containing this script + at cd %~dp0 + + at rem Build Hadrian and dependencies + at stack build + + at rem Run Hadrian in GHC top directory forwarding additional user arguments + at stack exec hadrian -- --lint --directory ".." %* From git at git.haskell.org Fri Oct 27 00:39:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Final tweaks (7987366) Message-ID: <20171027003936.7A8643A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79873665328d089b35b8a75141afe75b0d84dcbf/ghc >--------------------------------------------------------------- commit 79873665328d089b35b8a75141afe75b0d84dcbf Author: Andrey Mokhov Date: Thu Sep 1 21:02:05 2016 +0100 Final tweaks >--------------------------------------------------------------- 79873665328d089b35b8a75141afe75b0d84dcbf appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index def4dd9..5d13d29 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -12,7 +12,7 @@ install: - 7z x stack.zip stack.exe # Fetch GHC sources into c:\ghc - # Note: Appveyor has already cloned Hadrian into c:\ghc\hadrian, so it's tricky + # Note: AppVeyor has already cloned Hadrian into c:\ghc\hadrian, so it's tricky - cd .. - git init - git remote add origin git://git.haskell.org/ghc.git @@ -30,7 +30,7 @@ build_script: # Run internal Hadrian tests - stack exec hadrian -- selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- # Test GHC binary - cd .. - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:39:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #168 from kgardas/fix_gmp_args (dc90c3c) Message-ID: <20171027003936.7535E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dc90c3ce5301a08b3d149d551580cf88e7221e5c/ghc >--------------------------------------------------------------- commit dc90c3ce5301a08b3d149d551580cf88e7221e5c Merge: 6934485 86a3fe5 Author: Andrey Mokhov Date: Thu Jan 14 12:32:46 2016 +0000 Merge pull request #168 from kgardas/fix_gmp_args fix handling of --with-gmp-* configure arguments [skip ci] >--------------------------------------------------------------- dc90c3ce5301a08b3d149d551580cf88e7221e5c src/Rules/Gmp.hs | 32 +++++++++++++++++++++----------- 1 file changed, 21 insertions(+), 11 deletions(-) From git at git.haskell.org Fri Oct 27 00:39:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add mtl, parsec and text as Stage0 packages (d2dddad) Message-ID: <20171027003937.6965A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2dddad4564c6597d497d226fcfbf5e3f7b70c18/ghc >--------------------------------------------------------------- commit d2dddad4564c6597d497d226fcfbf5e3f7b70c18 Author: Andrey Mokhov Date: Fri Aug 18 23:41:24 2017 +0100 Add mtl, parsec and text as Stage0 packages See #393, #395 >--------------------------------------------------------------- d2dddad4564c6597d497d226fcfbf5e3f7b70c18 src/GHC.hs | 15 +++++++++------ src/Settings/Default.hs | 3 +++ src/Settings/Packages/GhcCabal.hs | 2 +- 3 files changed, 13 insertions(+), 7 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0b3d035..2a641e5 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -6,9 +6,9 @@ module GHC ( genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, - parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, - terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, + mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm, + templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix, + win32, xhtml, defaultKnownPackages, -- * Package information builderProvenance, programName, nonCabalContext, nonHsMainPackage, autogenPath, @@ -36,9 +36,9 @@ defaultKnownPackages = , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi - , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm - , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 - , xhtml ] + , mkUserGuidePart, mtl, parsec, parallel, pretty, primitive, process, rts + , runGhc, stm, templateHaskell, terminfo, text, time, touchy, transformers + , unlit, unix, win32, xhtml ] -- | Package definitions, see 'Package'. array = lib "array" @@ -78,6 +78,8 @@ integerSimple = lib "integer-simple" iservBin = prg "iserv-bin" `setPath` "iserv" libffi = top "libffi" mkUserGuidePart = util "mkUserGuidePart" +mtl = lib "mtl" +parsec = lib "parsec" parallel = lib "parallel" pretty = lib "pretty" primitive = lib "primitive" @@ -87,6 +89,7 @@ runGhc = util "runghc" stm = lib "stm" templateHaskell = lib "template-haskell" terminfo = lib "terminfo" +text = lib "text" time = lib "time" touchy = util "touchy" transformers = lib "transformers" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 707bc6f..c97b79f 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -116,7 +116,10 @@ stage0Packages = do , hp2ps , hpc , mkUserGuidePart + , mtl + , parsec , templateHaskell + , text , transformers , unlit ] ++ [ terminfo | not win, not ios ] ++ diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index fb23297..17ea482 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -12,7 +12,7 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do cabalDeps <- expr $ pkgDependencies cabal (_, cabalVersion) <- expr $ cabalNameVersion (pkgCabalFile cabal) mconcat - [ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps ] + [ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps, pkg /= parsec ] , arg "--make" , arg "-j" , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) From git at git.haskell.org Fri Oct 27 00:39:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use doesDirectoryExist to workaround a getDirectoryContents bug. (34c999b) Message-ID: <20171027003940.4609A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34c999b8e9d78b848ef75f8b439b408eafdf7166/ghc >--------------------------------------------------------------- commit 34c999b8e9d78b848ef75f8b439b408eafdf7166 Author: Andrey Mokhov Date: Thu Jan 14 13:01:48 2016 +0000 Use doesDirectoryExist to workaround a getDirectoryContents bug. See #168. >--------------------------------------------------------------- 34c999b8e9d78b848ef75f8b439b408eafdf7166 src/Rules/Gmp.hs | 4 +--- src/Rules/Library.hs | 5 ++++- 2 files changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index f6d6fe8..c788ed2 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -118,10 +118,8 @@ gmpRules = do createDirectory $ takeDirectory gmpLibraryH -- check whether we need to build in tree gmp - -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk` configMk <- liftIO . readFile $ gmpBase -/- "config.mk" - if "HaveFrameworkGMP = YES" `isInfixOf` configMk - || "HaveLibGmp = YES" `isInfixOf` configMk + if any (`isInfixOf` configMk) ["HaveFrameworkGMP = YES", "HaveLibGmp = YES"] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 6b2180c..0ffaf3f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -84,5 +84,8 @@ extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? - getDirectoryFiles "" [gmpObjects -/- "*.o"] + exists <- doesDirectoryExist gmpObjects + if exists + then getDirectoryFiles "" [gmpObjects -/- "*.o"] + else return [] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:39:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Whitespace (5905138) Message-ID: <20171027003940.3F07C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59051380365b8ef66d7c95cb63a038a89b482326/ghc >--------------------------------------------------------------- commit 59051380365b8ef66d7c95cb63a038a89b482326 Author: Andrey Mokhov Date: Thu Sep 1 21:29:15 2016 +0100 Whitespace >--------------------------------------------------------------- 59051380365b8ef66d7c95cb63a038a89b482326 appveyor.yml | 3 +++ 1 file changed, 3 insertions(+) diff --git a/appveyor.yml b/appveyor.yml index 5d13d29..7552a56 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -27,10 +27,13 @@ install: build_script: # Build Hadrian - stack build + # Run internal Hadrian tests - stack exec hadrian -- selftest + # Build GHC - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- + # Test GHC binary - cd .. - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 00:39:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use system GMP on Windows. (ff0194b) Message-ID: <20171027003943.D54A33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff0194b7a49cd554065fc68e209e1188be133bff/ghc >--------------------------------------------------------------- commit ff0194b7a49cd554065fc68e209e1188be133bff Author: Andrey Mokhov Date: Thu Jan 14 13:22:16 2016 +0000 Don't use system GMP on Windows. See #168. >--------------------------------------------------------------- ff0194b7a49cd554065fc68e209e1188be133bff src/Rules/Gmp.hs | 6 ++++-- src/Rules/Library.hs | 1 + 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index c788ed2..069dd28 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -117,9 +117,11 @@ gmpRules = do runConfigure (pkgPath integerGmp) envs intGmpArgs createDirectory $ takeDirectory gmpLibraryH - -- check whether we need to build in tree gmp + -- We don't use system GMP on Windows. TODO: fix? + windows <- windowsHost configMk <- liftIO . readFile $ gmpBase -/- "config.mk" - if any (`isInfixOf` configMk) ["HaveFrameworkGMP = YES", "HaveLibGmp = YES"] + if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES" + , "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" copyFile gmpLibraryFakeH gmpLibraryH diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 0ffaf3f..b53c472 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -84,6 +84,7 @@ extraObjects :: PartialTarget -> Action [FilePath] extraObjects (PartialTarget _ pkg) | pkg == integerGmp = do orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? + -- FIXME: simplify after Shake's getDirectoryFiles bug is fixed, #168 exists <- doesDirectoryExist gmpObjects if exists then getDirectoryFiles "" [gmpObjects -/- "*.o"] From git at git.haskell.org Fri Oct 27 00:39:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop double installation of Hadrian dependencies (48ad1e7) Message-ID: <20171027003944.B247F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/48ad1e76030a4b8054641a0e7875c5921c2d6658/ghc >--------------------------------------------------------------- commit 48ad1e76030a4b8054641a0e7875c5921c2d6658 Author: Andrey Mokhov Date: Sat Aug 19 00:39:20 2017 +0100 Drop double installation of Hadrian dependencies See #393 >--------------------------------------------------------------- 48ad1e76030a4b8054641a0e7875c5921c2d6658 .travis.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 878136c..48ed171 100644 --- a/.travis.yml +++ b/.travis.yml @@ -74,8 +74,7 @@ install: # Install all Hadrian and GHC build dependencies - cabal update - - cabal install alex happy ansi-terminal mtl shake quickcheck - + - cabal install alex happy # Travis has already cloned Hadrian into ./ and we need to move it # to ./ghc/hadrian -- one way to do it is to move the .git directory From git at git.haskell.org Fri Oct 27 00:39:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (9fa04f0) Message-ID: <20171027003940.E84093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9fa04f066032ce5c8ab753f0aa2a71660dfb466c/ghc >--------------------------------------------------------------- commit 9fa04f066032ce5c8ab753f0aa2a71660dfb466c Author: Andrey Mokhov Date: Sat Aug 19 00:31:39 2017 +0100 Minor revision >--------------------------------------------------------------- 9fa04f066032ce5c8ab753f0aa2a71660dfb466c src/GHC.hs | 8 ++--- src/Hadrian/Haskell/Cabal.hs | 63 ++++++++++++++++++++------------------- src/Hadrian/Haskell/Package.hs | 20 +++++++------ src/Settings.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 4 +-- src/Utilities.hs | 13 ++++---- 7 files changed, 59 insertions(+), 53 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 9fa04f066032ce5c8ab753f0aa2a71660dfb466c From git at git.haskell.org Fri Oct 27 00:39:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting in renderAction. (14e5009) Message-ID: <20171027003947.3EEE43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14e50095ba46d4ab28cffda306008c41b00167e7/ghc >--------------------------------------------------------------- commit 14e50095ba46d4ab28cffda306008c41b00167e7 Author: Andrey Mokhov Date: Thu Jan 14 14:19:54 2016 +0000 Fix formatting in renderAction. [skip ci] >--------------------------------------------------------------- 14e50095ba46d4ab28cffda306008c41b00167e7 src/Base.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index be3ff1b..27fe5c1 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -145,12 +145,12 @@ putError msg = do renderAction :: String -> String -> String -> String renderAction what input output = case buildInfo of Normal -> renderBox [ what - , " input:" ++ input - , " => output:" ++ output ] + , " input: " ++ input + , " => output: " ++ output ] Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output Pony -> renderPony [ what - , " input:" ++ input - , " => output:" ++ output ] + , " input: " ++ input + , " => output: " ++ output ] Dot -> "." None -> "" From git at git.haskell.org Fri Oct 27 00:39:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to GHC binary (cc72f0c) Message-ID: <20171027003947.A7D823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cc72f0caf4547d27774cf6ed551c41ced9f9c9f3/ghc >--------------------------------------------------------------- commit cc72f0caf4547d27774cf6ed551c41ced9f9c9f3 Author: Andrey Mokhov Date: Thu Sep 1 22:15:17 2016 +0100 Fix path to GHC binary >--------------------------------------------------------------- cc72f0caf4547d27774cf6ed551c41ced9f9c9f3 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 5b26bbd..0209cab 100644 --- a/.travis.yml +++ b/.travis.yml @@ -49,7 +49,7 @@ script: # Test GHC binary - cd .. - - ghc/inplace/bin/ghc-stage2 -e 1+2 + - inplace/bin/ghc-stage2 -e 1+2 cache: directories: From git at git.haskell.org Fri Oct 27 00:39:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Print out system.config when running CI. (e094834) Message-ID: <20171027003950.BCA4D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e094834509c6280ea2d049fea51e1a129ccac2ae/ghc >--------------------------------------------------------------- commit e094834509c6280ea2d049fea51e1a129ccac2ae Author: Andrey Mokhov Date: Thu Jan 14 17:53:50 2016 +0000 Print out system.config when running CI. >--------------------------------------------------------------- e094834509c6280ea2d049fea51e1a129ccac2ae .appveyor.yml | 1 + .travis.yml | 1 + 2 files changed, 2 insertions(+) diff --git a/.appveyor.yml b/.appveyor.yml index 68c1fd8..d8854cc 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -30,6 +30,7 @@ install: - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" - bash -lc "cd /home/ghc; exec 0 Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f79278948b635567c1b0830a9539b97551db8dd5/ghc >--------------------------------------------------------------- commit f79278948b635567c1b0830a9539b97551db8dd5 Author: Andrey Mokhov Date: Thu Jan 14 17:59:21 2016 +0000 Fix comments. [skip ci] >--------------------------------------------------------------- f79278948b635567c1b0830a9539b97551db8dd5 cfg/system.config.in | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 498f78c..8b5b553 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -1,5 +1,6 @@ -# Edit 'user.config' to override these settings. -#=============================================== +# This file is processed by the configure script +# See 'Settings/User.hs' for user-defined settings +#================================================= # Paths to builders: #=================== From git at git.haskell.org Fri Oct 27 00:39:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor and simplify (3218044) Message-ID: <20171027003944.2DEAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/321804478393dbf33c80eaa8ad53e0f859d94171/ghc >--------------------------------------------------------------- commit 321804478393dbf33c80eaa8ad53e0f859d94171 Author: Andrey Mokhov Date: Thu Sep 1 21:29:34 2016 +0100 Refactor and simplify >--------------------------------------------------------------- 321804478393dbf33c80eaa8ad53e0f859d94171 .travis.yml | 69 ++++++++++++++++++++++--------------------------------------- 1 file changed, 25 insertions(+), 44 deletions(-) diff --git a/.travis.yml b/.travis.yml index 33c1738..5b26bbd 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,6 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quickest TARGET= addons: apt: packages: @@ -12,65 +11,47 @@ matrix: - zlib1g-dev sources: hvr-ghc before_install: - - PATH="/opt/ghc/$GHCVER/bin:$PATH" - - PATH="/opt/cabal/$CABALVER/bin:$PATH" - - PATH="$HOME/.cabal/bin:$PATH" - - export PATH - - cabal update - - cabal install alex happy ansi-terminal mtl shake quickcheck + - PATH="/opt/ghc/7.10.3/bin:$PATH" + - PATH="/opt/cabal/1.22/bin:$PATH" - os: osx - env: FLAVOUR=quickest TARGET= before_install: - brew update - brew install ghc cabal-install - - cabal update - - cabal install alex happy ansi-terminal mtl shake quickcheck - - PATH="$HOME/.cabal/bin:$PATH" - - export PATH install: + # Add Cabal to PATH + - PATH="$HOME/.cabal/bin:$PATH" + - export PATH - env - - ghc --version - - cabal --version - - alex --version - - happy --version - - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ - - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ - - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - - travis_retry git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 + # Install all Hadrian and GHC build dependencies + - cabal update + - cabal install alex happy ansi-terminal mtl shake quickcheck - # Travis clones the project into ".", but we need it as a child directory - # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake - # ".git" directory into the appropriate location, and perform a hard reset - # in order to regenerate the GHC-Shake files. + # Fetch GHC sources into ./ghc + - git clone --recursive git://git.haskell.org/ghc.git --quiet + + # Travis has already cloned Hadrian into ./ and we need to move it + # to ./ghc/hadrian -- one way to do it is to move the .git directory + # and perform a hard reset in order to regenerate Hadrian files - mkdir ghc/hadrian - mv .git ghc/hadrian - - ( cd ghc/hadrian && git reset --hard HEAD ) - - - ghc-pkg list + - cd ghc/hadrian + - git reset --hard HEAD script: - - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=$FLAVOUR $TARGET - - ./ghc/inplace/bin/ghc-stage2 -e 1+2 + # Run internal Hadrian tests + - ./build.sh selftest + + # Build GHC + - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + + # Test GHC binary + - cd .. + - ghc/inplace/bin/ghc-stage2 -e 1+2 cache: directories: - $HOME/.cabal - $HOME/.ghc - -notifications: - irc: - on_success: change # always/never/change - on_failure: always - channels: - - "chat.freenode.net#shaking-up-ghc" - template: - - "#%{build_number} finished in %{duration}. %{message}" - - "Repo: %{repository_slug}, branch: %{branch}" - - "%{author}: %{commit_subject}" - - "Build details: %{build_url}" From git at git.haskell.org Fri Oct 27 00:39:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix install rules by untracking copy files and use relative path (#396) (942ed27) Message-ID: <20171027003948.38BEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/942ed27a622576252ef7178040f0b1fdbf08ca1c/ghc >--------------------------------------------------------------- commit 942ed27a622576252ef7178040f0b1fdbf08ca1c Author: Zhen Zhang Date: Sat Aug 19 09:39:25 2017 +0800 Fix install rules by untracking copy files and use relative path (#396) >--------------------------------------------------------------- 942ed27a622576252ef7178040f0b1fdbf08ca1c src/Hadrian/Oracles/DirectoryContents.hs | 10 +++++++++- src/Rules/Install.hs | 8 +++++--- 2 files changed, 14 insertions(+), 4 deletions(-) diff --git a/src/Hadrian/Oracles/DirectoryContents.hs b/src/Hadrian/Oracles/DirectoryContents.hs index 19a5192..f302af9 100644 --- a/src/Hadrian/Oracles/DirectoryContents.hs +++ b/src/Hadrian/Oracles/DirectoryContents.hs @@ -1,6 +1,6 @@ {-# LANGUAGE TypeFamilies #-} module Hadrian.Oracles.DirectoryContents ( - directoryContents, copyDirectoryContents, directoryContentsOracle, + directoryContents, copyDirectoryContents, directoryContentsOracle, copyDirectoryContentsUntracked, Match (..), matches, matchAll ) where @@ -45,6 +45,14 @@ copyDirectoryContents expr source target = do let cp file = copyFile file $ target -/- makeRelative source file mapM_ cp =<< directoryContents expr source +-- | Copy the contents of the source directory that matches a given 'Match' +-- expression into the target directory. The copied contents is untracked. +copyDirectoryContentsUntracked :: Match -> FilePath -> FilePath -> Action () +copyDirectoryContentsUntracked expr source target = do + putProgressInfo =<< renderAction "Copy directory contents (untracked)" source target + let cp file = copyFileUntracked file $ target -/- makeRelative source file + mapM_ cp =<< directoryContents expr source + newtype DirectoryContents = DirectoryContents (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) type instance RuleResult DirectoryContents = [FilePath] diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 12135b4..2400933 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -186,7 +186,9 @@ installPackages = do withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg top <- topDirectory - installDistDir <- (top -/-) <$> buildPath context + installDistDir <- buildPath context + let absInstallDistDir = top -/- installDistDir + need =<< packageTargets stage pkg docDir <- installDocDir ghclibDir <- installGhcLibDir @@ -203,7 +205,7 @@ installPackages = do need [cabalFile, pkgConf] -- TODO: check if need pkgConf -- HACK (#318): copy stuff back to the place favored by ghc-cabal - quietly $ copyDirectoryContents (Not excluded) + quietly $ copyDirectoryContentsUntracked (Not excluded) installDistDir (installDistDir -/- "build") whenM (isSpecified HsColour) $ @@ -212,7 +214,7 @@ installPackages = do pref <- setting InstallPrefix unit $ cmd ghcCabalInplace [ "copy" , pkgPath pkg - , installDistDir + , absInstallDistDir , strip , destDir , pref From git at git.haskell.org Fri Oct 27 00:39:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve infrastructure for Cabal file parsing (4b6707a) Message-ID: <20171027003952.553963A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b6707a616478a0f664585a49de0d0ed6431d231/ghc >--------------------------------------------------------------- commit 4b6707a616478a0f664585a49de0d0ed6431d231 Author: Andrey Mokhov Date: Sat Aug 19 03:45:33 2017 +0100 Improve infrastructure for Cabal file parsing >--------------------------------------------------------------- 4b6707a616478a0f664585a49de0d0ed6431d231 hadrian.cabal | 4 +- src/Base.hs | 14 ++---- src/GHC.hs | 2 +- src/Hadrian/Haskell/Cabal.hs | 39 +++++---------- src/Hadrian/Haskell/Cabal/Parse.hs | 60 ++++++++++++++++++++++++ src/Hadrian/Oracles/FileCache.hs | 51 -------------------- src/Hadrian/Oracles/{KeyValue.hs => TextFile.hs} | 54 ++++++++++++++++++--- src/Oracles/Flag.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/Setting.hs | 2 +- src/Rules.hs | 11 +---- src/Rules/Compile.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 20 +++----- src/Utilities.hs | 38 +++++---------- 14 files changed, 149 insertions(+), 152 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 4b6707a616478a0f664585a49de0d0ed6431d231 From git at git.haskell.org Fri Oct 27 00:39:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify instructions, add CI badge (1fa2cb1) Message-ID: <20171027003951.983A43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fa2cb1b470674a5b478a4e4d5e8b931a45b36d6/ghc >--------------------------------------------------------------- commit 1fa2cb1b470674a5b478a4e4d5e8b931a45b36d6 Author: Andrey Mokhov Date: Thu Sep 1 23:20:05 2016 +0100 Simplify instructions, add CI badge [skip ci] >--------------------------------------------------------------- 1fa2cb1b470674a5b478a4e4d5e8b931a45b36d6 doc/windows.md | 69 ++++++++++++++++++++++++++++++++++++++++++++-------------- 1 file changed, 53 insertions(+), 16 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index a70f85a..efbaeb2 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -1,23 +1,60 @@ -# Building on Windows +# Building GHC on Windows -Here are a list of instructions to build GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. +[![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) -The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_64-installer) (I just accepted all the defaults), then open a command prompt and run: +Here is how you can build GHC, from source, on Windows. We assume that you +already have `git` and `stack` installed. - stack setup - stack install happy alex - stack exec -- pacman -S gcc binutils git automake-wrapper tar make patch autoconf --noconfirm - stack exec -- git clone --recursive git://git.haskell.org/ghc.git - cd ghc - stack exec -- git clone git://github.com/snowleopard/hadrian - stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quickest +```sh +# Get GHC and Hadrian sources +git clone --recursive git://git.haskell.org/ghc.git +cd ghc +git clone git://github.com/snowleopard/hadrian +cd hadrian -The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quickest` flag from the last command line (this will slow down the build to about an hour). +# Download and install the bootstrapping GHC and MSYS2 +stack setup -#### Future ideas +# Install utilities required during the GHC build process +stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm -Here are some alternatives that have been considered, but not yet tested. Use the instructions above. +# Build Hadrian and dependencies (including GHC dependencies Alex and Happy) +stack build + +# Build GHC +stack exec hadrian -- --directory ".." -j --flavour=quickest + +# Test GHC +cd .. +inplace\bin\ghc-stage2 -e 1+2 +``` + +The entire process should take about 20 minutes. Note, this will build GHC without +optimisations. If you need an optimised GHC, drop the `--flavour=quickest` flag from +the build command line (this will slow down the build to about an hour). + +These are currently not the +[official GHC building instructions](https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows), +but are much simpler and may also be more robust. + +The `stack build` and `stack exec hadrian` commands can be replaced by an invocation +of Hadrian's Stack-based build script: `build.stack.bat -j --flavour=quickest`. Use this +script if you plan to work on Hadrian and/or rebuild GHC often. + +## Prerequisites + +The above works on a clean machine with `git` and `stack` installed (tested with default +installation settings), which you can get from https://git-scm.com/download/win and +https://www.stackage.org/stack/windows-x86_64-installer. + +## Testing + +These instructions have been tested on a clean Windows 10 machine using the +[free VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/), +and are also routinely tested on +[Hadrian's AppVeyor CI instance](https://ci.appveyor.com/project/snowleopard/hadrian/history). + +## Notes + +Beware of the [current limitations of Hadrian](https://github.com/snowleopard/hadrian#current-limitations). -* The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. -* Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:39:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to prerequisites (633fad1) Message-ID: <20171027003955.198C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/633fad17054268f6c02e360bed5ab4df5e2559ba/ghc >--------------------------------------------------------------- commit 633fad17054268f6c02e360bed5ab4df5e2559ba Author: Andrey Mokhov Date: Thu Sep 1 23:24:34 2016 +0100 Link to prerequisites [skip ci] >--------------------------------------------------------------- 633fad17054268f6c02e360bed5ab4df5e2559ba doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index efbaeb2..1296b76 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -2,8 +2,8 @@ [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) -Here is how you can build GHC, from source, on Windows. We assume that you -already have `git` and `stack` installed. +Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are +installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). ```sh # Get GHC and Hadrian sources From git at git.haskell.org Fri Oct 27 00:39:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/snowleopard/hadrian (8586ab8) Message-ID: <20171027003955.C057D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8586ab84fbac7e250d23844bbd39c147f87ce092/ghc >--------------------------------------------------------------- commit 8586ab84fbac7e250d23844bbd39c147f87ce092 Merge: 4b6707a 942ed27 Author: Andrey Mokhov Date: Sat Aug 19 03:45:40 2017 +0100 Merge branch 'master' of https://github.com/snowleopard/hadrian >--------------------------------------------------------------- 8586ab84fbac7e250d23844bbd39c147f87ce092 src/Hadrian/Oracles/DirectoryContents.hs | 10 +++++++++- src/Rules/Install.hs | 8 +++++--- 2 files changed, 14 insertions(+), 4 deletions(-) From git at git.haskell.org Fri Oct 27 00:39:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Detect the right patch command and use it when building gmp. (79cf2e3) Message-ID: <20171027003957.AA9AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79cf2e3d1f5d48ff731060f4c0f17cd7e8310514/ghc >--------------------------------------------------------------- commit 79cf2e3d1f5d48ff731060f4c0f17cd7e8310514 Author: Andrey Mokhov Date: Thu Jan 14 23:41:31 2016 +0000 Detect the right patch command and use it when building gmp. See #158. >--------------------------------------------------------------- 79cf2e3d1f5d48ff731060f4c0f17cd7e8310514 cfg/system.config.in | 5 +++-- src/Builder.hs | 2 ++ src/Rules/Actions.hs | 11 ++++++++++- src/Rules/Gmp.hs | 6 +----- 4 files changed, 16 insertions(+), 8 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 8b5b553..4539979 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -1,6 +1,6 @@ # This file is processed by the configure script -# See 'Settings/User.hs' for user-defined settings -#================================================= +# See 'src/Settings/User.hs' for user-defined settings +#===================================================== # Paths to builders: #=================== @@ -40,6 +40,7 @@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ tar = @TarCmd@ +patch = @PatchCmd@ perl = @PerlCmd@ # Information about builders: diff --git a/src/Builder.hs b/src/Builder.hs index efc3216..353c00f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -40,6 +40,7 @@ data Builder = Alex | Ld | Nm | Objdump + | Patch | Perl | Ranlib | Tar @@ -82,6 +83,7 @@ builderKey builder = case builder of Ld -> "ld" Nm -> "nm" Objdump -> "objdump" + Patch -> "patch" Perl -> "perl" Ranlib -> "ranlib" Tar -> "tar" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index eb37630..7692c86 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,7 +1,7 @@ {-# LANGUAGE RecordWildCards #-} module Rules.Actions ( build, buildWithResources, copyFile, createDirectory, removeDirectory, moveDirectory, - fixFile, runConfigure, runMake, runBuilder, makeExecutable + fixFile, runConfigure, runMake, applyPatch, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -108,6 +108,15 @@ runMake dir args = do putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) makeCommand ["-C", dir] args +applyPatch :: FilePath -> FilePath -> Action () +applyPatch dir patch = do + let file = dir -/- patch + need [file] + needBuilder False Patch + path <- builderPath Patch + putBuild $ "| Apply patch " ++ file + quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] + runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do needBuilder laxDependencies builder diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 069dd28..eb1158e 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -73,7 +73,6 @@ gmpRules = do gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - -- Do we need this step? liftIO $ removeFiles gmpBuildPath ["//*"] -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is @@ -86,17 +85,14 @@ gmpRules = do ++ "(found: " ++ show tarballs ++ ")." need tarballs - createDirectory gmpBuildPath build $ fullTarget gmpTarget Tar tarballs [gmpBuildPath] - -- TODO: replace "patch" with PATCH_CMD forM_ gmpPatches $ \src -> do let patch = takeFileName src patchPath = gmpBuildPath -/- patch copyFile src patchPath - putBuild $ "| Apply " ++ patchPath - unit . quietly $ cmd Shell (EchoStdout False) [Cwd gmpBuildPath] "patch -p0 <" [patch] + applyPatch gmpBuildPath patch -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for? From git at git.haskell.org Fri Oct 27 00:39:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Tweak instructions (fd7dd6f) Message-ID: <20171027003958.973153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd7dd6f7f32eebb7ff1a00ee2b36a0a75fb51e14/ghc >--------------------------------------------------------------- commit fd7dd6f7f32eebb7ff1a00ee2b36a0a75fb51e14 Author: Andrey Mokhov Date: Thu Sep 1 23:27:33 2016 +0100 Tweak instructions [skip ci] >--------------------------------------------------------------- fd7dd6f7f32eebb7ff1a00ee2b36a0a75fb51e14 doc/windows.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/windows.md b/doc/windows.md index 1296b76..73804df 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -10,9 +10,9 @@ installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/maste git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/hadrian -cd hadrian # Download and install the bootstrapping GHC and MSYS2 +cd hadrian stack setup # Install utilities required during the GHC build process From git at git.haskell.org Fri Oct 27 00:39:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:39:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (268155a) Message-ID: <20171027003959.486E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/268155a0e615fda224d72d029749f1e2df0fa59b/ghc >--------------------------------------------------------------- commit 268155a0e615fda224d72d029749f1e2df0fa59b Author: Andrey Mokhov Date: Sat Aug 19 13:12:09 2017 +0100 Minor revision >--------------------------------------------------------------- 268155a0e615fda224d72d029749f1e2df0fa59b src/Hadrian/Haskell/Cabal.hs | 3 +-- src/Hadrian/Haskell/Cabal/Parse.hs | 8 ++++---- src/Hadrian/Oracles/Path.hs | 4 ++-- src/Hadrian/Oracles/TextFile.hs | 23 +++++++++++++---------- 4 files changed, 20 insertions(+), 18 deletions(-) diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs index bf21b18..6da1e51 100644 --- a/src/Hadrian/Haskell/Cabal.hs +++ b/src/Hadrian/Haskell/Cabal.hs @@ -11,7 +11,6 @@ ----------------------------------------------------------------------------- module Hadrian.Haskell.Cabal (pkgNameVersion, pkgDependencies) where -import Data.List import Development.Shake import Hadrian.Haskell.Cabal.Parse @@ -32,4 +31,4 @@ pkgNameVersion pkg = do pkgDependencies :: Package -> Action [PackageName] pkgDependencies pkg = do cabal <- readCabalFile (pkgCabalFile pkg) - return (dependencies cabal \\ [pkgName pkg]) + return (dependencies cabal) diff --git a/src/Hadrian/Haskell/Cabal/Parse.hs b/src/Hadrian/Haskell/Cabal/Parse.hs index ec18781..bc234d4 100644 --- a/src/Hadrian/Haskell/Cabal/Parse.hs +++ b/src/Hadrian/Haskell/Cabal/Parse.hs @@ -44,14 +44,14 @@ parseCabal :: FilePath -> IO Cabal parseCabal file = do gpd <- liftIO $ C.readGenericPackageDescription C.silent file let pkgId = C.package (C.packageDescription gpd) + name = C.unPackageName (C.pkgName pkgId) + version = C.display (C.pkgVersion pkgId) libDeps = collectDeps (C.condLibrary gpd) exeDeps = map (collectDeps . Just . snd) (C.condExecutables gpd) allDeps = concat (libDeps : exeDeps) sorted = sort [ C.unPackageName p | C.Dependency p _ <- allDeps ] - return $ Cabal - (C.unPackageName $ C.pkgName pkgId) - (C.display $ C.pkgVersion pkgId) - (nubOrd sorted) + deps = nubOrd sorted \\ [name] + return $ Cabal name version deps collectDeps :: Maybe (C.CondTree v [C.Dependency] a) -> [C.Dependency] collectDeps Nothing = [] diff --git a/src/Hadrian/Oracles/Path.hs b/src/Hadrian/Oracles/Path.hs index cab8aa1..4f6406c 100644 --- a/src/Hadrian/Oracles/Path.hs +++ b/src/Hadrian/Oracles/Path.hs @@ -52,11 +52,11 @@ pathOracle = do void $ addOracle $ \(WindowsPath path) -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] let windowsPath = unifyPath $ dropWhileEnd isSpace out - putLoud $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath + putLoud $ "| Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath void $ addOracle $ \(LookupInPath name) -> do let unpack = fromMaybe . error $ "Cannot find executable " ++ quote name path <- unifyPath <$> unpack <$> liftIO (findExecutable name) - putLoud $ "Executable found: " ++ name ++ " => " ++ path + putLoud $ "| Executable found: " ++ name ++ " => " ++ path return path diff --git a/src/Hadrian/Oracles/TextFile.hs b/src/Hadrian/Oracles/TextFile.hs index 7f80c75..c2ecb4c 100644 --- a/src/Hadrian/Oracles/TextFile.hs +++ b/src/Hadrian/Oracles/TextFile.hs @@ -23,8 +23,8 @@ import Development.Shake import Development.Shake.Classes import Development.Shake.Config -import Hadrian.Utilities import Hadrian.Haskell.Cabal.Parse +import Hadrian.Utilities newtype TextFile = TextFile FilePath deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -32,7 +32,7 @@ type instance RuleResult TextFile = String newtype CabalFile = CabalFile FilePath deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -type instance RuleResult CabalFile = String +type instance RuleResult CabalFile = Cabal newtype KeyValue = KeyValue (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -99,22 +99,25 @@ textFileOracle :: Rules () textFileOracle = do text <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| TextFile oracle: reading " ++ quote file ++ "..." liftIO $ readFile file + void $ addOracle $ \(TextFile file) -> text file + kv <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| KeyValue oracle: reading " ++ quote file ++ "..." liftIO $ readConfigFile file + void $ addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> kv file + kvs <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| KeyValues oracle: reading " ++ quote file ++ "..." contents <- map words <$> readFileLines file return $ Map.fromList [ (key, values) | (key:values) <- contents ] + void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file + cabal <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| CabalFile oracle: reading " ++ quote file ++ "..." liftIO $ parseCabal file - void $ addOracle $ \(TextFile file ) -> text file - void $ addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> kv file - void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file - void $ addOracle $ \(CabalFile file ) -> cabal file + void $ addOracle $ \(CabalFile file) -> cabal file From git at git.haskell.org Fri Oct 27 00:40:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Determine system GMP library name and pass it via -optl. (2024396) Message-ID: <20171027004001.22DDA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20243965783cfb5ba75096ebe375517d63cf37c8/ghc >--------------------------------------------------------------- commit 20243965783cfb5ba75096ebe375517d63cf37c8 Author: Andrey Mokhov Date: Fri Jan 15 01:11:36 2016 +0000 Determine system GMP library name and pass it via -optl. See #173. >--------------------------------------------------------------- 20243965783cfb5ba75096ebe375517d63cf37c8 src/Rules/Gmp.hs | 113 +++++++++++++++++++++++-------------------- src/Settings/Builders/Ghc.hs | 11 ++++- 2 files changed, 69 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 20243965783cfb5ba75096ebe375517d63cf37c8 From git at git.haskell.org Fri Oct 27 00:40:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Lowercase flavour names in --help (73c72a6) Message-ID: <20171027004002.5ED1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73c72a633398eb0f021fdd4081e2e559a10105f5/ghc >--------------------------------------------------------------- commit 73c72a633398eb0f021fdd4081e2e559a10105f5 Author: Moritz Kiefer Date: Sat Sep 3 12:51:23 2016 +0200 Lowercase flavour names in --help >--------------------------------------------------------------- 73c72a633398eb0f021fdd4081e2e559a10105f5 src/CmdLineFlag.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index cc0eb7f..b58df7b 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -74,7 +74,7 @@ readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") - "Build flavour (Default, Quick or Quickest)." + "Build flavour (default, quick or quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") From git at git.haskell.org Fri Oct 27 00:40:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix MonadFail warning (a8cbd16) Message-ID: <20171027004003.09E713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8cbd160e3e6b90bdb618620fd6eb4cc53179ae5/ghc >--------------------------------------------------------------- commit a8cbd160e3e6b90bdb618620fd6eb4cc53179ae5 Author: Andrey Mokhov Date: Sat Aug 19 16:21:27 2017 +0100 Fix MonadFail warning >--------------------------------------------------------------- a8cbd160e3e6b90bdb618620fd6eb4cc53179ae5 src/Settings/Builders/DeriveConstants.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index b8846be..7a6e863 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -5,8 +5,11 @@ import Settings.Builders.Common -- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? deriveConstantsBuilderArgs :: Args deriveConstantsBuilderArgs = builder DeriveConstants ? do - cFlags <- includeCcArgs - [outputFile, tempDir] <- getOutputs + cFlags <- includeCcArgs + outs <- getOutputs + let (outputFile, tempDir) = case outs of + [a, b] -> (a, b) + _ -> error $ "DeriveConstants: expected two outputs, got " ++ show outs mconcat [ output "//DerivedConstants.h" ? arg "--gen-header" , output "//GHCConstantsHaskellType.hs" ? arg "--gen-haskell-type" From git at git.haskell.org Fri Oct 27 00:40:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drops dot, adds none; renames pony to unicorn (da96a23) Message-ID: <20171027004004.9E8643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da96a236f4678b2e64535bfe7a57928275d5aca1/ghc >--------------------------------------------------------------- commit da96a236f4678b2e64535bfe7a57928275d5aca1 Author: Moritz Angermann Date: Fri Jan 15 15:22:17 2016 +0800 Drops dot, adds none; renames pony to unicorn >--------------------------------------------------------------- da96a236f4678b2e64535bfe7a57928275d5aca1 shaking-up-ghc.cabal | 2 -- src/Base.hs | 23 ++++++++++------------- src/Main.hs | 27 --------------------------- src/Oracles/Config/CmdLineFlag.hs | 14 +++++++------- 4 files changed, 17 insertions(+), 49 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 123870d..b38feac 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -116,7 +116,6 @@ executable ghc-shake , ScopedTypeVariables build-depends: base , ansi-terminal >= 0.6 - , bytestring >= 0.10.6 , Cabal >= 1.22 , containers >= 0.5 , directory >= 1.2 @@ -126,6 +125,5 @@ executable ghc-shake , shake >= 0.15 , transformers >= 0.4 , unordered-containers >= 0.2 - , utf8-string >= 1.0.1 default-language: Haskell2010 ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j diff --git a/src/Base.hs b/src/Base.hs index b9c7f72..07b21e4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -115,16 +115,11 @@ a -/- b = unifyPath $ a b infixr 6 -/- --- | A wrapper around shakes @putNormal@ that substitutes --- any message for a fullstop if @buildInfo@ is @Dot at . -putNormal' :: String -> Action () -putNormal' = if buildInfo == Dot then putNormal . const "." else putNormal - -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do liftIO $ setSGR [SetColor Foreground Vivid colour] - putNormal' msg + putNormal msg liftIO $ setSGR [] liftIO $ hFlush stdout @@ -134,7 +129,9 @@ putOracle = putColoured Blue -- | Make build output more distinguishable putBuild :: String -> Action () -putBuild = putColoured White +putBuild = if buildInfo /= None + then putColoured White + else const (pure ()) -- | A more colourful version of success message putSuccess :: String -> Action () @@ -149,14 +146,14 @@ putError msg = do -- | Render an action. renderAction :: String -> String -> String -> String renderAction what input output = case buildInfo of - Normal -> renderBox [ what - , " input:" ++ input - , " => output:" ++ output ] - Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output - Pony -> renderPony [ what + Normal -> renderBox [ what , " input:" ++ input , " => output:" ++ output ] - Dot -> "." + Brief -> "> " ++ what ++ ": " ++ input ++ " => " ++ output + Unicorn -> renderPony [ what + , " input:" ++ input + , " => output:" ++ output ] + None -> "" -- | Render the successful build of a program renderProgram :: String -> String -> String -> String diff --git a/src/Main.hs b/src/Main.hs index 14f3554..e9d1e56 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -14,10 +14,6 @@ import qualified Rules.Perl import qualified Test import Oracles.Config.CmdLineFlag (putOptions, flags) -import qualified Data.ByteString.Char8 as BS -import qualified Data.ByteString.UTF8 as UTF8 -import Data.Char (chr) - main :: IO () main = shakeArgsWith options flags $ \cmdLineFlags targets -> do putOptions cmdLineFlags @@ -41,27 +37,4 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True - , shakeOutput = const putMsg } - --- | Dynamic switch for @putStr@ and @putStrLn@ depending on the @msg at . -putMsg :: String -> IO () -putMsg msg | dropEscSequence msg == "." = BS.putStr . UTF8.fromString $ msg -putMsg msg = BS.putStrLn . UTF8.fromString $ msg - --- | Drops ANSI Escape sequences from a string. -dropEscSequence :: String -> String -dropEscSequence = go - where - esc :: Char - esc = Data.Char.chr 27 - go :: String -> String - go [] = [] - go [x] = [x] - go (x:xs) | x == esc = skip xs - go (x:xs) | otherwise = x:go xs - skip :: String -> String - skip [] = [] - skip ['m'] = [] - skip ('m':xs) = go xs - skip (_ :xs) = skip xs diff --git a/src/Oracles/Config/CmdLineFlag.hs b/src/Oracles/Config/CmdLineFlag.hs index 47dbbbc..4b97c72 100644 --- a/src/Oracles/Config/CmdLineFlag.hs +++ b/src/Oracles/Config/CmdLineFlag.hs @@ -8,7 +8,7 @@ import Data.IORef -- Flags -data BuildInfoFlag = Normal | Brief | Pony | Dot deriving (Eq, Show) +data BuildInfoFlag = None | Brief | Normal | Unicorn deriving (Eq, Show) data CmdLineOptions = CmdLineOptions { flagBuildInfo :: BuildInfoFlag @@ -25,16 +25,16 @@ readBuildInfoFlag ms = (go =<< fmap (map toLower) ms) where go :: String -> Maybe BuildInfoFlag - go "normal" = Just Normal - go "brief" = Just Brief - go "pony" = Just Pony - go "dot" = Just Dot - go _ = Nothing -- Left "no parse" + go "none" = Just None + go "brief" = Just Brief + go "normal" = Just Normal + go "unicorn" = Just Unicorn + go _ = Nothing -- Left "no parse" mkClosure :: BuildInfoFlag -> CmdLineOptions -> CmdLineOptions mkClosure flag opts = opts { flagBuildInfo = flag } flags :: [OptDescr (Either String (CmdLineOptions -> CmdLineOptions))] -flags = [Option [] ["build-info"] (OptArg readBuildInfoFlag "") "Build Info Style (Normal, Brief, Pony, Dot, or None)"] +flags = [Option [] ["progress-info"] (OptArg readBuildInfoFlag "") "Build Info Style (None, Brief, Normal, or Unicorn)"] -- IO -- We use IO here instead of Oracles, as Oracles form part of shakes cache -- hence, changing command line arguments, would cause a full rebuild. And we From git at git.haskell.org Fri Oct 27 00:40:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghcid.txt (8f244c4) Message-ID: <20171027004006.AEDAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f244c413c7e3444285b32c8f90f839511a367ce/ghc >--------------------------------------------------------------- commit 8f244c413c7e3444285b32c8f90f839511a367ce Author: Andrey Mokhov Date: Sat Aug 19 16:22:54 2017 +0100 Add ghcid.txt >--------------------------------------------------------------- 8f244c413c7e3444285b32c8f90f839511a367ce .gitignore | 3 +++ 1 file changed, 3 insertions(+) diff --git a/.gitignore b/.gitignore index 4b026f2..697afc9 100644 --- a/.gitignore +++ b/.gitignore @@ -21,3 +21,6 @@ cabal.sandbox.config # Mostly temp file by emacs *~ + +# ghcid output +/ghcid.txt \ No newline at end of file From git at git.haskell.org Fri Oct 27 00:40:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Space leak. (c2f1abd) Message-ID: <20171027004008.25BF83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c2f1abd4d8ef56134168afb6b208c05b29008c34/ghc >--------------------------------------------------------------- commit c2f1abd4d8ef56134168afb6b208c05b29008c34 Author: Moritz Angermann Date: Fri Jan 15 15:23:21 2016 +0800 Space leak. >--------------------------------------------------------------- c2f1abd4d8ef56134168afb6b208c05b29008c34 src/Main.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index e9d1e56..e3f1a34 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -36,5 +36,4 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do options = shakeOptions { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple - , shakeTimings = True - } + , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:40:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add path to generated includes for compiler package (57d6c69) Message-ID: <20171027004009.C06AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57d6c69843a0c2f7fd89a0c9cbc49742c6347414/ghc >--------------------------------------------------------------- commit 57d6c69843a0c2f7fd89a0c9cbc49742c6347414 Author: Andrey Mokhov Date: Sun Sep 25 01:29:46 2016 +0900 Add path to generated includes for compiler package Fix #288. >--------------------------------------------------------------- 57d6c69843a0c2f7fd89a0c9cbc49742c6347414 src/Settings/Builders/Common.hs | 2 +- src/Settings/Packages/Compiler.hs | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index d036f8a..b276102 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -1,5 +1,5 @@ module Settings.Builders.Common ( - includesArgs, cIncludeArgs, ldArgs, cArgs, cWarnings, + includes, includesArgs, cIncludeArgs, ldArgs, cArgs, cWarnings, argSetting, argSettingList, argStagedBuilderPath, argStagedSettingList ) where diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 7dbbaa3..65ced17 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -7,6 +7,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Predicate import Settings +import Settings.Builders.Common compilerPackageArgs :: Args compilerPackageArgs = package compiler ? do @@ -15,7 +16,10 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder Ghc ? arg ("-I" ++ path) + , builder Ghc ? mconcat + [ arg ("-I" ++ path) + , includesArgs + , append [ "-optP-I" ++ dir | dir <- includes ] ] , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) From git at git.haskell.org Fri Oct 27 00:40:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix performance bug: do not call ghc-cabal to determine package targets (ef47d7b) Message-ID: <20171027004010.45D1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef47d7b35d17bff791763c8bf3d46caaaf1a1108/ghc >--------------------------------------------------------------- commit ef47d7b35d17bff791763c8bf3d46caaaf1a1108 Author: Andrey Mokhov Date: Sun Aug 20 01:12:39 2017 +0100 Fix performance bug: do not call ghc-cabal to determine package targets See #393 >--------------------------------------------------------------- ef47d7b35d17bff791763c8bf3d46caaaf1a1108 src/Context.hs | 19 +++++++++---------- src/Hadrian/Haskell/Cabal.hs | 18 +++++++++++++++++- src/Hadrian/Haskell/Cabal/Parse.hs | 7 ++++--- src/Oracles/PackageData.hs | 2 -- src/Rules.hs | 21 +++++++++++++++------ src/Rules/Install.hs | 2 +- src/Settings/Builders/Ghc.hs | 7 +++++-- src/Utilities.hs | 13 ++++++++----- 8 files changed, 59 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 ef47d7b35d17bff791763c8bf3d46caaaf1a1108 From git at git.haskell.org Fri Oct 27 00:40:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: adds putBuildInfo (ade3088) Message-ID: <20171027004011.8ABE53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ade30882bd45c0f4e4747ba9c6d19b2ec08846de/ghc >--------------------------------------------------------------- commit ade30882bd45c0f4e4747ba9c6d19b2ec08846de Author: Moritz Angermann Date: Fri Jan 15 15:31:23 2016 +0800 adds putBuildInfo >--------------------------------------------------------------- ade30882bd45c0f4e4747ba9c6d19b2ec08846de src/Base.hs | 13 ++++++++----- src/Rules/Actions.hs | 6 +++--- 2 files changed, 11 insertions(+), 8 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 07b21e4..68a223b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -20,8 +20,8 @@ module Base ( bootPackageConstraints, packageDependencies, -- * Output - putColoured, putOracle, putBuild, putSuccess, putError, renderAction, - renderLibrary, renderProgram, + putColoured, putOracle, putBuild, putBuildInfo, putSuccess, putError, + renderAction, renderLibrary, renderProgram, -- * Miscellaneous utilities bimap, minusOrd, intersectOrd, replaceEq, quote, replaceSeparators, @@ -129,9 +129,12 @@ putOracle = putColoured Blue -- | Make build output more distinguishable putBuild :: String -> Action () -putBuild = if buildInfo /= None - then putColoured White - else const (pure ()) +putBuild = putColoured White + +-- | Switch for @putBuild@ filtered through @buildInfo@ +putBuildInfo :: String -> Action () +putBuildInfo s | buildInfo /= None = putBuild s +putBuildInfo _ = pure () -- | A more colourful version of success message putSuccess :: String -> Action () diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index eb37630..77d283b 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -64,7 +64,7 @@ captureStdout target path argList = do copyFile :: FilePath -> FilePath -> Action () copyFile source target = do - putBuild $ renderAction "Copy file" source target + putBuildInfo $ renderAction "Copy file" source target copyFileChanged source target createDirectory :: FilePath -> Action () @@ -80,7 +80,7 @@ removeDirectory dir = do -- Note, the source directory is untracked moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do - putBuild $ renderAction "Move directory" source target + putBuildInfo $ renderAction "Move directory" source target liftIO $ IO.renameDirectory source target -- Transform a given file by applying a function to its contents @@ -123,7 +123,7 @@ makeExecutable file = do -- Print out key information about the command being executed putInfo :: Target.Target -> Action () -putInfo Target.Target {..} = putBuild $ renderAction +putInfo Target.Target {..} = putBuildInfo $ renderAction ("Run " ++ show builder ++ " (" ++ stageInfo ++ "package = " ++ pkgNameString package ++ wayInfo ++ ")") (digest inputs) From git at git.haskell.org Fri Oct 27 00:40:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #286 from cocreature/lowercase-flavour (e5b4b0c) Message-ID: <20171027004006.31D143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e5b4b0cbef54b3c2c32238cb810a5cebcb9270e7/ghc >--------------------------------------------------------------- commit e5b4b0cbef54b3c2c32238cb810a5cebcb9270e7 Merge: fd7dd6f 73c72a6 Author: Andrey Mokhov Date: Sat Sep 3 12:20:06 2016 +0100 Merge pull request #286 from cocreature/lowercase-flavour Lowercase flavour names in --help >--------------------------------------------------------------- e5b4b0cbef54b3c2c32238cb810a5cebcb9270e7 src/CmdLineFlag.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:40:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor GMP build rule (6836711) Message-ID: <20171027004013.60CF93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68367119d7f5d1f01a94a0eab87a53900c54fe3e/ghc >--------------------------------------------------------------- commit 68367119d7f5d1f01a94a0eab87a53900c54fe3e Author: Andrey Mokhov Date: Sun Oct 2 10:40:16 2016 +0900 Refactor GMP build rule See #289. >--------------------------------------------------------------- 68367119d7f5d1f01a94a0eab87a53900c54fe3e src/Rules/Gmp.hs | 92 ++++++++++++++++++++++++--------------------------- src/Settings/Paths.hs | 8 ++--- 2 files changed, 45 insertions(+), 55 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 7fc3e18..66d6c0b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -17,10 +17,12 @@ gmpBase = pkgPath integerGmp -/- "gmp" gmpContext :: Context gmpContext = vanillaContext Stage1 integerGmp --- TODO: Noone needs this file, but we build it. Why? gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" +gmpLibrary :: FilePath +gmpLibrary = gmpBuildPath -/- ".libs/libgmp.a" + gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] @@ -29,76 +31,68 @@ configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 , builderEnvironment "AR" Ar , builderEnvironment "NM" Nm ] --- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do - -- TODO: split into multiple rules gmpLibraryH %> \_ -> do - need [sourcePath -/- "Rules/Gmp.hs"] - removeDirectory gmpBuildPath - - -- We don't use system GMP on Windows. TODO: fix? windows <- windowsHost configMk <- readFile' $ gmpBase -/- "config.mk" - if not windows && any (`isInfixOf` configMk) - [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] + if not windows && -- TODO: We don't use system GMP on Windows. Fix? + any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" createDirectory $ takeDirectory gmpLibraryH copyFile (gmpBase -/- "ghc-gmp.h") gmpLibraryH else do putBuild "| No GMP library/framework detected; in tree GMP will be built" - - -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is - -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. - -- That's because the doc/ directory contents are under the GFDL, - -- which causes problems for Debian. - tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "gmpRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - - withTempDir $ \dir -> do - let tmp = unifyPath dir - need [tarball] - build $ Target gmpContext Tar [tarball] [tmp] - - forM_ gmpPatches $ \src -> do - let patch = takeFileName src - patchPath = tmp -/- patch - copyFile src patchPath - applyPatch tmp patch - - let name = dropExtension . dropExtension $ takeFileName tarball - unpack = fromMaybe . error $ "gmpRules: expected suffix " - ++ "-nodoc-patched (found: " ++ name ++ ")." - libName = unpack $ stripSuffix "-nodoc-patched" name - - moveDirectory (tmp -/- libName) gmpBuildPath - - env <- configureEnvironment - buildWithCmdOptions env $ - Target gmpContext (Configure gmpBuildPath) - [gmpBuildPath -/- "Makefile.in"] - [gmpBuildPath -/- "Makefile"] - build $ Target gmpContext (Make gmpBuildPath) [] [] - createDirectory $ takeDirectory gmpLibraryH copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH - moveFile (gmpBuildPath -/- ".libs/libgmp.a") gmpLibrary - createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] - runBuilder Ranlib [gmpLibrary] - putSuccess "| Successfully built custom library 'gmp'" + -- In-tree GMP header is built in the gmpLibraryH rule gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] -- This causes integerGmp package to be configured, hence creating the files [gmpBase -/- "config.mk", gmpBuildInfoPath] &%> \_ -> need [pkgDataFile gmpContext] + + -- Extract in-tree GMP sources and apply patches + gmpBuildPath -/- "Makefile.in" %> \_ -> do + removeDirectory gmpBuildPath + -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is + -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. + -- That's because the doc/ directory contents are under the GFDL, + -- which causes problems for Debian. + tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] + tarball <- case tarballs of -- TODO: Drop code duplication. + [file] -> return $ unifyPath file + _ -> error $ "gmpRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + + withTempDir $ \dir -> do + let tmp = unifyPath dir + need [tarball] + build $ Target gmpContext Tar [tarball] [tmp] + + forM_ gmpPatches $ \src -> do + let patch = takeFileName src + copyFile src $ tmp -/- patch + applyPatch tmp patch + + let name = dropExtension . dropExtension $ takeFileName tarball + unpack = fromMaybe . error $ "gmpRules: expected suffix " + ++ "-nodoc-patched (found: " ++ name ++ ")." + libName = unpack $ stripSuffix "-nodoc-patched" name + + moveDirectory (tmp -/- libName) gmpBuildPath + + -- Run GMP's configure script + gmpBuildPath -/- "Makefile" %> \mk -> do + env <- configureEnvironment + need [mk <.> "in"] + buildWithCmdOptions env $ + Target gmpContext (Configure gmpBuildPath) [mk <.> "in"] [mk] diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 51e92e2..9c770f3 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,7 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibrary, gmpObjects, - gmpLibraryH, gmpBuildInfoPath, libffiBuildPath, shakeFilesPath, pkgConfFile, + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, + gmpBuildInfoPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, bootPackageConstraints, packageDependencies ) where @@ -66,10 +66,6 @@ pkgFile context prefix suffix = do gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" --- | Path to the GMP library. -gmpLibrary :: FilePath -gmpLibrary = gmpBuildPath -/- "libgmp.a" - -- | Path to the GMP library header. gmpLibraryH :: FilePath gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" From git at git.haskell.org Fri Oct 27 00:40:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: delete cfg/config.h.in (#390) (c413722) Message-ID: <20171027004013.CF46A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c413722eae49a7999293a8940547f626a33d0632/ghc >--------------------------------------------------------------- commit c413722eae49a7999293a8940547f626a33d0632 Author: Zhen Zhang Date: Sun Aug 20 19:09:47 2017 +0800 delete cfg/config.h.in (#390) >--------------------------------------------------------------- c413722eae49a7999293a8940547f626a33d0632 cfg/config.h.in | 463 -------------------------------------------------------- 1 file changed, 463 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 c413722eae49a7999293a8940547f626a33d0632 From git at git.haskell.org Fri Oct 27 00:40:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge remote-tracking branch 'snowleopard/master' into angerman/feature/advanced-render-box (ee95b14) Message-ID: <20171027004015.15C1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ee95b14e13491cc42329afed8ae038e9e94527cb/ghc >--------------------------------------------------------------- commit ee95b14e13491cc42329afed8ae038e9e94527cb Merge: ade3088 2024396 Author: Moritz Angermann Date: Fri Jan 15 15:59:02 2016 +0800 Merge remote-tracking branch 'snowleopard/master' into angerman/feature/advanced-render-box # Conflicts: # src/Base.hs >--------------------------------------------------------------- ee95b14e13491cc42329afed8ae038e9e94527cb .appveyor.yml | 1 + .travis.yml | 1 + cfg/system.config.in | 6 ++- src/Builder.hs | 2 + src/Rules/Actions.hs | 11 ++++- src/Rules/Gmp.hs | 101 ++++++++++++++++++++++++------------------- src/Rules/Library.hs | 6 ++- src/Settings/Builders/Ghc.hs | 11 ++++- 8 files changed, 89 insertions(+), 50 deletions(-) From git at git.haskell.org Fri Oct 27 00:40:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split the GMP build rule even further (d12066d) Message-ID: <20171027004017.119313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d12066d8d457e2ea7dbc4afa37e8acaac6afa413/ghc >--------------------------------------------------------------- commit d12066d8d457e2ea7dbc4afa37e8acaac6afa413 Author: Andrey Mokhov Date: Sun Oct 2 03:23:42 2016 +0100 Split the GMP build rule even further See #289. >--------------------------------------------------------------- d12066d8d457e2ea7dbc4afa37e8acaac6afa413 src/Rules/Gmp.hs | 36 +++++++++++++++++++++--------------- 1 file changed, 21 insertions(+), 15 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 66d6c0b..0a53102 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -23,6 +23,9 @@ gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" gmpLibrary :: FilePath gmpLibrary = gmpBuildPath -/- ".libs/libgmp.a" +gmpMakefile :: FilePath +gmpMakefile = gmpBuildPath -/- "Makefile" + gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] @@ -33,24 +36,27 @@ configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 gmpRules :: Rules () gmpRules = do - gmpLibraryH %> \_ -> do + -- Copy appropriate GMP header and object files + gmpLibraryH %> \header -> do + createDirectory $ takeDirectory header windows <- windowsHost configMk <- readFile' $ gmpBase -/- "config.mk" if not windows && -- TODO: We don't use system GMP on Windows. Fix? any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" - createDirectory $ takeDirectory gmpLibraryH - copyFile (gmpBase -/- "ghc-gmp.h") gmpLibraryH + copyFile (gmpBase -/- "ghc-gmp.h") header else do putBuild "| No GMP library/framework detected; in tree GMP will be built" - build $ Target gmpContext (Make gmpBuildPath) [] [] - createDirectory $ takeDirectory gmpLibraryH - copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH - copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH + need [gmpLibrary] createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] + copyFile (gmpBuildPath -/- "gmp.h") header + copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH + -- Build in-tree GMP library + gmpLibrary %> \lib -> do + build $ Target gmpContext (Make gmpBuildPath) [gmpMakefile] [lib] putSuccess "| Successfully built custom library 'gmp'" -- In-tree GMP header is built in the gmpLibraryH rule @@ -60,8 +66,15 @@ gmpRules = do [gmpBase -/- "config.mk", gmpBuildInfoPath] &%> \_ -> need [pkgDataFile gmpContext] + -- Run GMP's configure script + gmpMakefile %> \mk -> do + env <- configureEnvironment + need [mk <.> "in"] + buildWithCmdOptions env $ + Target gmpContext (Configure gmpBuildPath) [mk <.> "in"] [mk] + -- Extract in-tree GMP sources and apply patches - gmpBuildPath -/- "Makefile.in" %> \_ -> do + gmpMakefile <.> "in" %> \_ -> do removeDirectory gmpBuildPath -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. @@ -89,10 +102,3 @@ gmpRules = do libName = unpack $ stripSuffix "-nodoc-patched" name moveDirectory (tmp -/- libName) gmpBuildPath - - -- Run GMP's configure script - gmpBuildPath -/- "Makefile" %> \mk -> do - env <- configureEnvironment - need [mk <.> "in"] - buildWithCmdOptions env $ - Target gmpContext (Configure gmpBuildPath) [mk <.> "in"] [mk] From git at git.haskell.org Fri Oct 27 00:40:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add DESTDIR to command line arguments (#397) (176bfd4) Message-ID: <20171027004017.6341C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/176bfd4d524c59c64a182f8e04dd0084a9c5e482/ghc >--------------------------------------------------------------- commit 176bfd4d524c59c64a182f8e04dd0084a9c5e482 Author: Zhen Zhang Date: Sun Aug 20 19:29:36 2017 +0800 Add DESTDIR to command line arguments (#397) >--------------------------------------------------------------- 176bfd4d524c59c64a182f8e04dd0084a9c5e482 README.md | 2 +- src/CommandLine.hs | 13 ++++++++++++- src/Rules/Install.hs | 6 ++++++ src/Settings.hs | 7 +++---- src/Settings/Packages/Rts.hs | 1 + 5 files changed, 23 insertions(+), 6 deletions(-) diff --git a/README.md b/README.md index 5e49393..ecf9728 100644 --- a/README.md +++ b/README.md @@ -111,7 +111,7 @@ To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` tar To build and install GHC artifacts, run the `install` target. By default, the artifacts will be installed to `` on your system. For example, -`ghc` will be installed to `/usr/local/bin`. By modifying `defaultDestDir` in `UserSettings.hs`, +`ghc` will be installed to `/usr/local/bin`. By setting flag `--install-destdir=[DESTDIR]`, you can install things to non-system path `DESTDIR/` instead. #### Testing diff --git a/src/CommandLine.hs b/src/CommandLine.hs index 5688d6f..fbf3e07 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -1,6 +1,7 @@ module CommandLine ( optDescrs, cmdLineArgsMap, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, - cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects + cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects, + cmdInstallDestDir ) where import Data.Either @@ -14,6 +15,7 @@ import System.Environment -- | All arguments that can be passed to Hadrian via the command line. data CommandLineArgs = CommandLineArgs { buildHaddock :: Bool + , installDestDir :: Maybe String , flavour :: Maybe String , integerSimple :: Bool , progressColour :: UseColour @@ -27,6 +29,7 @@ defaultCommandLineArgs :: CommandLineArgs defaultCommandLineArgs = CommandLineArgs { buildHaddock = False , flavour = Nothing + , installDestDir = Nothing , integerSimple = False , progressColour = Auto , progressInfo = Normal @@ -39,6 +42,9 @@ readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } readFlavour :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs) readFlavour ms = Right $ \flags -> flags { flavour = lower <$> ms } +readInstallDestDir :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs) +readInstallDestDir ms = Right $ \flags -> flags { installDestDir = ms } + readIntegerSimple :: Either String (CommandLineArgs -> CommandLineArgs) readIntegerSimple = Right $ \flags -> flags { integerSimple = True } @@ -80,6 +86,8 @@ optDescrs = "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." + , Option [] ["install-destdir"] (OptArg readInstallDestDir "DESTDIR") + "Installation destination directory." , Option [] ["integer-simple"] (NoArg readIntegerSimple) "Build GHC with integer-simple library." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") @@ -107,6 +115,9 @@ cmdLineArgs = userSetting defaultCommandLineArgs cmdBuildHaddock :: Action Bool cmdBuildHaddock = buildHaddock <$> cmdLineArgs +cmdInstallDestDir :: Action (Maybe String) +cmdInstallDestDir = installDestDir <$> cmdLineArgs + cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 24d7703..0d7336b 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -60,6 +60,7 @@ getLibExecDir = (-/- "bin") <$> installGhcLibDir installLibExecScripts :: Action () installLibExecScripts = do libExecDir <- getLibExecDir + destDir <- getDestDir installDirectory (destDir ++ libExecDir) forM_ libExecScripts $ \script -> do installScript script (destDir ++ libExecDir) @@ -72,6 +73,7 @@ installLibExecScripts = do installLibExecs :: Action () installLibExecs = do libExecDir <- getLibExecDir + destDir <- getDestDir installDirectory (destDir ++ libExecDir) forM_ installBinPkgs $ \pkg -> do withLatestBuildStage pkg $ \stage -> do @@ -88,6 +90,7 @@ installBins :: Action () installBins = do binDir <- setting InstallBinDir libDir <- installGhcLibDir + destDir <- getDestDir installDirectory (destDir ++ binDir) win <- windowsHost when win $ @@ -153,6 +156,7 @@ installPackages = do ghcLibDir <- installGhcLibDir binDir <- setting InstallBinDir + destDir <- getDestDir -- Install package.conf let installedPackageConf = destDir ++ ghcLibDir -/- "package.conf.d" @@ -271,6 +275,7 @@ installPackages = do installCommonLibs :: Action () installCommonLibs = do ghcLibDir <- installGhcLibDir + destDir <- getDestDir installLibsTo inplaceLibCopyTargets (destDir ++ ghcLibDir) -- ref: ghc.mk @@ -296,6 +301,7 @@ includeHSubdirs = [".", "rts", "rts/prof", "rts/storage", "stg"] installIncludes :: Action () installIncludes = do ghclibDir <- installGhcLibDir + destDir <- getDestDir let ghcheaderDir = ghclibDir -/- "include" installDirectory (destDir ++ ghcheaderDir) forM_ includeHSubdirs $ \dir -> do diff --git a/src/Settings.hs b/src/Settings.hs index 9fafd1e..52c36ad 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,7 +2,7 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, stagePackages, builderPath, getBuilderPath, isSpecified, latestBuildStage, programPath, - programContext, integerLibraryName, destDir, stage1Only, buildDll0 + programContext, integerLibraryName, getDestDir, stage1Only, buildDll0 ) where import Context @@ -103,7 +103,6 @@ programPath context at Context {..} = do stage1Only :: Bool stage1Only = defaultStage1Only --- TODO: Set this from command line -- | Install's DESTDIR setting. -destDir :: FilePath -destDir = defaultDestDir +getDestDir :: Action FilePath +getDestDir = fromMaybe "" <$> cmdInstallDestDir diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 0ae764f..a54e618 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -62,6 +62,7 @@ rtsPackageArgs = package rts ? do ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir ghclibDir <- expr installGhcLibDir + destDir <- expr getDestDir let cArgs = [ arg "-Irts" , arg $ "-I" ++ path From git at git.haskell.org Fri Oct 27 00:40:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move rendering to Actions. (c7c45fc) Message-ID: <20171027004018.8CB673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7c45fc3ec57e888fc6560e77a29617f18c3a46c/ghc >--------------------------------------------------------------- commit c7c45fc3ec57e888fc6560e77a29617f18c3a46c Author: Moritz Angermann Date: Fri Jan 15 21:36:36 2016 +0800 Move rendering to Actions. >--------------------------------------------------------------- c7c45fc3ec57e888fc6560e77a29617f18c3a46c src/Base.hs | 98 +--------------------------------------------- src/Rules/Actions.hs | 107 +++++++++++++++++++++++++++++++++++++++++++++++++-- 2 files changed, 104 insertions(+), 101 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 c7c45fc3ec57e888fc6560e77a29617f18c3a46c From git at git.haskell.org Fri Oct 27 00:40:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing directory (c9ae45b) Message-ID: <20171027004021.4A73B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9ae45b4c7757a54b40f84c6a8532f2d5c2a5418/ghc >--------------------------------------------------------------- commit c9ae45b4c7757a54b40f84c6a8532f2d5c2a5418 Author: Andrey Mokhov Date: Sun Oct 2 18:38:31 2016 +0900 Fix missing directory See #289. >--------------------------------------------------------------- c9ae45b4c7757a54b40f84c6a8532f2d5c2a5418 src/Rules/Gmp.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 0a53102..50c548b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -38,19 +38,20 @@ gmpRules :: Rules () gmpRules = do -- Copy appropriate GMP header and object files gmpLibraryH %> \header -> do - createDirectory $ takeDirectory header windows <- windowsHost configMk <- readFile' $ gmpBase -/- "config.mk" if not windows && -- TODO: We don't use system GMP on Windows. Fix? any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" + createDirectory $ takeDirectory header copyFile (gmpBase -/- "ghc-gmp.h") header else do putBuild "| No GMP library/framework detected; in tree GMP will be built" need [gmpLibrary] createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] + createDirectory $ takeDirectory header copyFile (gmpBuildPath -/- "gmp.h") header copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH From git at git.haskell.org Fri Oct 27 00:40:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (acd5c37) Message-ID: <20171027004021.AD1463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acd5c37535be71bc36dbf73ae09a772af5d63fda/ghc >--------------------------------------------------------------- commit acd5c37535be71bc36dbf73ae09a772af5d63fda Author: Andrey Mokhov Date: Sun Aug 20 15:23:24 2017 +0100 Minor revision >--------------------------------------------------------------- acd5c37535be71bc36dbf73ae09a772af5d63fda src/CommandLine.hs | 9 ++++----- src/Hadrian/Utilities.hs | 2 +- 2 files changed, 5 insertions(+), 6 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index fbf3e07..cc6f944 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -15,8 +15,8 @@ import System.Environment -- | All arguments that can be passed to Hadrian via the command line. data CommandLineArgs = CommandLineArgs { buildHaddock :: Bool - , installDestDir :: Maybe String , flavour :: Maybe String + , installDestDir :: Maybe String , integerSimple :: Bool , progressColour :: UseColour , progressInfo :: ProgressInfo @@ -115,12 +115,12 @@ cmdLineArgs = userSetting defaultCommandLineArgs cmdBuildHaddock :: Action Bool cmdBuildHaddock = buildHaddock <$> cmdLineArgs -cmdInstallDestDir :: Action (Maybe String) -cmdInstallDestDir = installDestDir <$> cmdLineArgs - cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs +cmdInstallDestDir :: Action (Maybe String) +cmdInstallDestDir = installDestDir <$> cmdLineArgs + cmdIntegerSimple :: Action Bool cmdIntegerSimple = integerSimple <$> cmdLineArgs @@ -135,4 +135,3 @@ cmdSkipConfigure = skipConfigure <$> cmdLineArgs cmdSplitObjects :: Action Bool cmdSplitObjects = splitObjects <$> cmdLineArgs - diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index f1db28e..4051347 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -177,7 +177,7 @@ copyFile source target = do let dir = takeDirectory target liftIO $ IO.createDirectoryIfMissing True dir putProgressInfo =<< renderAction "Copy file" source target - copyFileChanged source target + quietly $ copyFileChanged source target -- | Copy a file without tracking the source. Create the target directory if missing. copyFileUntracked :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:40:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #171 from snowleopard/angerman/feature/advanced-render-box (8a0380a) Message-ID: <20171027004022.6B5CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8a0380a71035774db6a874567e962e37d61089a5/ghc >--------------------------------------------------------------- commit 8a0380a71035774db6a874567e962e37d61089a5 Merge: 2024396 c7c45fc Author: Andrey Mokhov Date: Fri Jan 15 13:41:06 2016 +0000 Merge pull request #171 from snowleopard/angerman/feature/advanced-render-box advanced render box, fix #134 [skip ci] >--------------------------------------------------------------- 8a0380a71035774db6a874567e962e37d61089a5 src/Base.hs | 94 +-------------------------------- src/Oracles/Config/CmdLineFlag.hs | 15 +++--- src/Rules/Actions.hs | 107 ++++++++++++++++++++++++++++++++++++-- 3 files changed, 111 insertions(+), 105 deletions(-) From git at git.haskell.org Fri Oct 27 00:40:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:40:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move generated includes to build directory (f2cff6f) Message-ID: <20171027004024.EA2703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f2cff6f69f43c83c33f53971c96e770a68030ca5/ghc >--------------------------------------------------------------- commit f2cff6f69f43c83c33f53971c96e770a68030ca5 Author: Andrey Mokhov Date: Mon Oct 3 00:47:32 2016 +0900 Move generated includes to build directory See #113. >--------------------------------------------------------------- f2cff6f69f43c83c33f53971c96e770a68030ca5 src/Rules/Clean.hs | 4 +--- src/Rules/Data.hs | 7 ++---- src/Rules/Generate.hs | 20 +++++++--------- src/Settings/Builders/Cc.hs | 24 +++++++------------ src/Settings/Builders/Common.hs | 13 ++++------- src/Settings/Builders/DeriveConstants.hs | 21 ++++++++--------- src/Settings/Builders/GhcCabal.hs | 40 +++++++++++++++----------------- src/Settings/Builders/HsCpp.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 7 +++--- src/Settings/Packages/IntegerGmp.hs | 3 +-- src/Settings/Packages/Rts.hs | 8 +++---- src/Settings/Paths.hs | 5 +++- 12 files changed, 66 insertions(+), 90 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 f2cff6f69f43c83c33f53971c96e770a68030ca5 From git at git.haskell.org Fri Oct 27 00:41:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused extension (0d8713a) Message-ID: <20171027004157.EDB0A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0d8713a49c11732343f0a8b3d098ace401778acf/ghc >--------------------------------------------------------------- commit 0d8713a49c11732343f0a8b3d098ace401778acf Author: Andrey Mokhov Date: Tue Oct 18 23:21:24 2016 +0100 Drop unused extension >--------------------------------------------------------------- 0d8713a49c11732343f0a8b3d098ace401778acf src/Settings/Builders/GhcCabal.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 5569ba0..535454e 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, buildDll0 ) where From git at git.haskell.org Fri Oct 27 00:41:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:41:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix tracking of changes to Libffi rules file (efc92c5) Message-ID: <20171027004159.BBCC63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/efc92c529a00d16f18f2708dd5898ce0ae564cd6/ghc >--------------------------------------------------------------- commit efc92c529a00d16f18f2708dd5898ce0ae564cd6 Author: Karel Gardas Date: Mon Jan 18 20:23:40 2016 +0100 fix tracking of changes to Libffi rules file >--------------------------------------------------------------- efc92c529a00d16f18f2708dd5898ce0ae564cd6 src/Rules/Libffi.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 518389e..97ebc2d 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,6 +70,7 @@ configureArguments = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do + when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] ffi_header_dir <- setting FfiIncludeDir use_system_ffi <- flag UseSystemFfi if use_system_ffi @@ -80,7 +81,6 @@ libffiRules = do copyFile src (rtsBuildPath -/- file) putSuccess $ "| Successfully copied system supplied FFI library header files" else do - when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] removeDirectory libffiBuild createDirectory $ buildRootPath -/- stageString Stage0 From git at git.haskell.org Fri Oct 27 00:42:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for llvm-targets (6d14f09) Message-ID: <20171027004200.2A3853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d14f09c81f490704d2798693236f0db68e6e438/ghc >--------------------------------------------------------------- commit 6d14f09c81f490704d2798693236f0db68e6e438 Author: Andrey Mokhov Date: Sat Sep 9 11:39:57 2017 +0100 Add support for llvm-targets See #412 >--------------------------------------------------------------- 6d14f09c81f490704d2798693236f0db68e6e438 cfg/system.config.in | 1 + src/Base.hs | 1 + src/Oracles/Setting.hs | 2 ++ src/Rules/Generate.hs | 5 ++++- 4 files changed, 8 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 34ef7b9..0b05259 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -63,6 +63,7 @@ target-platform-full = @TargetPlatformFull@ target-arch = @TargetArch_CPP@ target-os = @TargetOS_CPP@ target-vendor = @TargetVendor_CPP@ +llvm-target = @LLVMTarget_CPP@ cross-compiling = @CrossCompiling@ diff --git a/src/Base.hs b/src/Base.hs index 942b272..76e8f2b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -106,6 +106,7 @@ inplaceLibCopyTargets :: [FilePath] inplaceLibCopyTargets = map (inplaceLibPath -/-) [ "ghc-usage.txt" , "ghci-usage.txt" + , "llvm-targets" , "platformConstants" , "settings" , "template-hsc.h" ] diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 8af8f38..5f148d4 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -46,6 +46,7 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor + | LlvmTarget | FfiIncludeDir | FfiLibDir | GmpIncludeDir @@ -104,6 +105,7 @@ setting key = lookupValueOrError configFile $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" + LlvmTarget -> "llvm-target" FfiIncludeDir -> "ffi-include-dir" FfiLibDir -> "ffi-lib-dir" GmpIncludeDir -> "gmp-include-dir" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index b23b72d..413abe5 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -11,9 +11,9 @@ import Oracles.ModuleFiles import Oracles.Setting import Rules.Gmp import Rules.Libffi +import Target import Settings import Settings.Packages.Rts -import Target import Utilities -- | Track this file to rebuild generated files whenever it changes. @@ -145,6 +145,7 @@ copyRules :: Rules () copyRules = do (inplaceLibPath -/- "ghc-usage.txt") <~ return "driver" (inplaceLibPath -/- "ghci-usage.txt" ) <~ return "driver" + (inplaceLibPath -/- "llvm-targets") <~ return "." (inplaceLibPath -/- "platformConstants") <~ (buildRoot <&> (-/- generatedDir)) (inplaceLibPath -/- "settings") <~ return "." (inplaceLibPath -/- "template-hsc.h") <~ return (pkgPath hsc2hs) @@ -394,6 +395,7 @@ generateGhcBootPlatformH = do hostVendor <- chooseSetting HostVendor TargetVendor targetPlatform <- getSetting TargetPlatform targetArch <- getSetting TargetArch + llvmTarget <- getSetting LlvmTarget targetOs <- getSetting TargetOs targetVendor <- getSetting TargetVendor return $ unlines @@ -414,6 +416,7 @@ generateGhcBootPlatformH = do , "#define BUILD_ARCH " ++ show buildArch , "#define HOST_ARCH " ++ show hostArch , "#define TARGET_ARCH " ++ show targetArch + , "#define LLVM_TARGET " ++ show llvmTarget , "" , "#define " ++ buildOs ++ "_BUILD_OS 1" , "#define " ++ hostOs ++ "_HOST_OS 1" From git at git.haskell.org Fri Oct 27 00:42:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (a0afb98) Message-ID: <20171027004201.7DCBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a0afb987569ba2ac617b1bcd035f124c93463da3/ghc >--------------------------------------------------------------- commit a0afb987569ba2ac617b1bcd035f124c93463da3 Author: Andrey Mokhov Date: Wed Oct 19 00:03:58 2016 +0100 Minor revision >--------------------------------------------------------------- a0afb987569ba2ac617b1bcd035f124c93463da3 src/Expression.hs | 4 ++-- src/Rules/Gmp.hs | 11 ++++------- src/Rules/Libffi.hs | 10 +++------- src/Rules/Library.hs | 4 ++-- 4 files changed, 11 insertions(+), 18 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 114bfe4..a572c2c 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -16,7 +16,7 @@ module Expression ( -- * Convenient accessors getContext, getStage, getPackage, getBuilder, getOutputs, getInputs, getWay, - getInput, getOutput, + getInput, getOutput, getSingleton, -- * Re-exports module Control.Monad.Trans.Reader, @@ -206,7 +206,7 @@ getOutput = do getSingleton getOutputs $ "getOutput: exactly one output file expected in target " ++ show target -getSingleton :: Expr [a] -> String -> Expr a +getSingleton :: Monad m => m [a] -> String -> m a getSingleton expr msg = expr >>= \case [res] -> return res _ -> error msg diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 50c548b..3693ad4 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,4 +1,4 @@ -module Rules.Gmp (gmpRules, gmpContext) where +module Rules.Gmp (gmpRules) where import Base import Builder @@ -81,12 +81,9 @@ gmpRules = do -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. - tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "gmpRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - + let tarballs = gmpBase -/- "tarball/gmp*.tar.bz2" + tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) + "Exactly one GMP tarball is expected." withTempDir $ \dir -> do let tmp = unifyPath dir need [tarball] diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 5ca17ea..6dd92bc 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -80,13 +80,9 @@ libffiRules = do libffiMakefile <.> "in" %> \mkIn -> do removeDirectory libffiBuildPath createDirectory $ buildRootPath -/- stageString Stage0 - - tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "libffiRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - + let tarballs = "libffi-tarballs/libffi*.tar.gz" + tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) + "Exactly one LibFFI tarball is expected." need [tarball] let libname = dropExtension . dropExtension $ takeFileName tarball diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 00a6be2..731bb7b 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -9,9 +9,9 @@ import Base import Context import Expression import Flavour +import GHC import Oracles.PackageData import Rules.Actions -import Rules.Gmp import Settings import Settings.Paths import Target @@ -96,7 +96,7 @@ hSources context = do extraObjects :: Context -> Action [FilePath] extraObjects context - | context == gmpContext = do + | package context == integerGmp = do need [gmpLibraryH] map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Fri Oct 27 00:42:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #182 from kgardas/fix_ffi_args (9a4bdc7) Message-ID: <20171027004203.C35413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a4bdc7c11538e6984a93bda483aa72d7e4aae0e/ghc >--------------------------------------------------------------- commit 9a4bdc7c11538e6984a93bda483aa72d7e4aae0e Merge: 40b7920 efc92c5 Author: Andrey Mokhov Date: Mon Jan 18 23:43:30 2016 +0000 Merge pull request #182 from kgardas/fix_ffi_args fix handling of FFI library configure params >--------------------------------------------------------------- 9a4bdc7c11538e6984a93bda483aa72d7e4aae0e cfg/system.config.in | 4 +++ src/Oracles/Config/Flag.hs | 2 ++ src/Oracles/Config/Setting.hs | 4 +++ src/Rules/Libffi.hs | 84 ++++++++++++++++++++++++------------------- src/Settings/Packages/Rts.hs | 14 ++++++-- 5 files changed, 68 insertions(+), 40 deletions(-) From git at git.haskell.org Fri Oct 27 00:42:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop support for -this-package-key (95a23a6) Message-ID: <20171027004204.3E96E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95a23a6667824592499775d746a71ee2b8de07fe/ghc >--------------------------------------------------------------- commit 95a23a6667824592499775d746a71ee2b8de07fe Author: Andrey Mokhov Date: Sun Sep 10 23:45:34 2017 +0100 Drop support for -this-package-key >--------------------------------------------------------------- 95a23a6667824592499775d746a71ee2b8de07fe src/Oracles/Flag.hs | 4 +--- src/Settings/Builders/Ghc.hs | 9 ++------- 2 files changed, 3 insertions(+), 10 deletions(-) diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 20aca1f..510b9d2 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -17,7 +17,6 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken - | SupportsThisUnitId | WithLibdw | UseSystemFfi @@ -35,12 +34,11 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" - SupportsThisUnitId -> "supports-this-unit-id" WithLibdw -> "with-libdw" UseSystemFfi -> "use-system-ffi" value <- lookupValueOrError configFile key when (value `notElem` ["YES", "NO", ""]) . error $ "Configuration flag " - ++ quote (key ++ " = " ++ value) ++ "cannot be parsed." + ++ quote (key ++ " = " ++ value) ++ " cannot be parsed." return $ value == "YES" platformSupportsSharedLibs :: Action Bool diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a186e08..7f942f6 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -115,18 +115,13 @@ wayGhcArgs = do , (way == debug || way == debugDynamic) ? pure ["-ticky", "-DTICKY_TICKY"] ] --- FIXME: Get rid of to-be-deprecated -this-package-key. packageGhcArgs :: Args packageGhcArgs = withHsPackage $ \cabalFile -> do - pkgId <- expr $ pkgIdentifier cabalFile - thisArg <- do - not0 <- notStage0 - unit <- expr $ flag SupportsThisUnitId - return $ if not0 || unit then "-this-unit-id " else "-this-package-key " + pkgId <- expr $ pkgIdentifier cabalFile mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" , bootPackageDatabaseArgs - , libraryPackage ? arg (thisArg ++ pkgId) + , libraryPackage ? arg ("-this-unit-id " ++ pkgId) , map ("-package-id " ++) <$> getPkgDataList DepIds ] includeGhcArgs :: Args From git at git.haskell.org Fri Oct 27 00:42:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify getSingleton, add comments (fbe22e6) Message-ID: <20171027004205.0C4773A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fbe22e6f83bb5e9f14960b63f1ad40dbbfdd7c86/ghc >--------------------------------------------------------------- commit fbe22e6f83bb5e9f14960b63f1ad40dbbfdd7c86 Author: Andrey Mokhov Date: Wed Oct 19 00:25:01 2016 +0100 Simplify getSingleton, add comments >--------------------------------------------------------------- fbe22e6f83bb5e9f14960b63f1ad40dbbfdd7c86 src/Expression.hs | 19 ++++++++++--------- src/Rules/Gmp.hs | 6 +++--- src/Rules/Libffi.hs | 6 +++--- 3 files changed, 16 insertions(+), 15 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index a572c2c..45967c9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -192,8 +192,8 @@ getInputs = asks inputs getInput :: Expr FilePath getInput = do target <- ask - getSingleton getInputs $ - "getInput: exactly one input file expected in target " ++ show target + getSingleton ("Exactly one input file expected in " ++ show target) + <$> getInputs -- | Get the files produced by the current 'Target'. getOutputs :: Expr [FilePath] @@ -203,10 +203,11 @@ getOutputs = asks outputs getOutput :: Expr FilePath getOutput = do target <- ask - getSingleton getOutputs $ - "getOutput: exactly one output file expected in target " ++ show target - -getSingleton :: Monad m => m [a] -> String -> m a -getSingleton expr msg = expr >>= \case - [res] -> return res - _ -> error msg + getSingleton ("Exactly one output file expected in " ++ show target) + <$> getOutputs + +-- | Extract a value from a singleton list, or raise an error if the list does +-- not contain exactly one value. +getSingleton :: String -> [a] -> a +getSingleton _ [res] = res +getSingleton msg _ = error msg diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 3693ad4..412bea0 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -81,9 +81,9 @@ gmpRules = do -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. - let tarballs = gmpBase -/- "tarball/gmp*.tar.bz2" - tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) - "Exactly one GMP tarball is expected." + tarball <- unifyPath . getSingleton "Exactly one GMP tarball is expected" + <$> getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] + withTempDir $ \dir -> do let tmp = unifyPath dir need [tarball] diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 6dd92bc..9560dbf 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -80,9 +80,9 @@ libffiRules = do libffiMakefile <.> "in" %> \mkIn -> do removeDirectory libffiBuildPath createDirectory $ buildRootPath -/- stageString Stage0 - let tarballs = "libffi-tarballs/libffi*.tar.gz" - tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) - "Exactly one LibFFI tarball is expected." + tarball <- unifyPath . getSingleton "Exactly one LibFFI tarball is expected" + <$> getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] + need [tarball] let libname = dropExtension . dropExtension $ takeFileName tarball From git at git.haskell.org Fri Oct 27 00:42:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Create package database directories using oracles. (6e00b02) Message-ID: <20171027004207.676193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e00b0238ebb28460f69ed0aa68c54d52d7e223a/ghc >--------------------------------------------------------------- commit 6e00b0238ebb28460f69ed0aa68c54d52d7e223a Author: Andrey Mokhov Date: Tue Jan 19 03:14:31 2016 +0000 Create package database directories using oracles. Fix #176. >--------------------------------------------------------------- 6e00b0238ebb28460f69ed0aa68c54d52d7e223a shaking-up-ghc.cabal | 1 + src/Oracles/PackageDb.hs | 23 +++++++++++++++++++++++ src/Rules/Actions.hs | 6 +++--- src/Rules/Cabal.hs | 14 -------------- src/Rules/Oracles.hs | 3 +++ src/Rules/Wrappers/GhcPkg.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 15 +++++++++++---- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Paths.hs | 19 +++++++------------ 9 files changed, 51 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 6e00b0238ebb28460f69ed0aa68c54d52d7e223a From git at git.haskell.org Fri Oct 27 00:42:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop cabal_macros_boot.h (bece422) Message-ID: <20171027004207.CE87D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bece42266ac98ebbcd901efd62d1ffaf68a482ef/ghc >--------------------------------------------------------------- commit bece42266ac98ebbcd901efd62d1ffaf68a482ef Author: Andrey Mokhov Date: Mon Sep 11 00:03:59 2017 +0100 Drop cabal_macros_boot.h >--------------------------------------------------------------- bece42266ac98ebbcd901efd62d1ffaf68a482ef src/Settings/Packages/GhcCabal.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 0e6e1ea..b525c31 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -17,8 +17,6 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" - , arg "-optP-include" - , arg $ "-optP" ++ pkgPath ghcCabal -/- "cabal_macros_boot.h" , arg "-ilibraries/Cabal/Cabal" , arg "-ilibraries/binary/src" , arg "-ilibraries/filepath" From git at git.haskell.org Fri Oct 27 00:42:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split compilation of Haskell and non-Haskell files (b61423d) Message-ID: <20171027004208.78C2A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b61423dfdb36c96a902f26b14c07e6bc39621a94/ghc >--------------------------------------------------------------- commit b61423dfdb36c96a902f26b14c07e6bc39621a94 Author: Andrey Mokhov Date: Thu Oct 20 02:44:02 2016 +0100 Split compilation of Haskell and non-Haskell files See #216, #264, #267. >--------------------------------------------------------------- b61423dfdb36c96a902f26b14c07e6bc39621a94 src/Oracles/Dependencies.hs | 5 ++- src/Oracles/PackageData.hs | 6 +++- src/Rules/Compile.hs | 58 ++++++++++++++++---------------- src/Rules/Data.hs | 17 +++++----- src/Rules/Dependencies.hs | 77 ++++++++++--------------------------------- src/Rules/Generate.hs | 17 +++++++--- src/Rules/Library.hs | 80 ++++++++++++++++++++++++++++----------------- src/Rules/Program.hs | 12 +++---- 8 files changed, 132 insertions(+), 140 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 b61423dfdb36c96a902f26b14c07e6bc39621a94 From git at git.haskell.org Fri Oct 27 00:42:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix "dirs" to "dir" for gmp and iconv libraries (36b7f4d) Message-ID: <20171027004211.518EC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/36b7f4de03fd661e6439b84a3d03b4ca00ca6bcc/ghc >--------------------------------------------------------------- commit 36b7f4de03fd661e6439b84a3d03b4ca00ca6bcc Author: Karel Gardas Date: Tue Jan 19 07:38:52 2016 +0100 fix "dirs" to "dir" for gmp and iconv libraries >--------------------------------------------------------------- 36b7f4de03fd661e6439b84a3d03b4ca00ca6bcc cfg/system.config.in | 8 ++++---- src/Oracles/Config/Setting.hs | 16 ++++++++-------- src/Rules/Gmp.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 8 ++++---- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- 5 files changed, 22 insertions(+), 22 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 126387f..0eb775a 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -100,11 +100,11 @@ conf-ld-linker-args-stage2 = @CONF_LD_LINKER_OPTS_STAGE2@ # Include and library directories: #================================= -iconv-include-dirs = @ICONV_INCLUDE_DIRS@ -iconv-lib-dirs = @ICONV_LIB_DIRS@ +iconv-include-dir = @ICONV_INCLUDE_DIRS@ +iconv-lib-dir = @ICONV_LIB_DIRS@ -gmp-include-dirs = @GMP_INCLUDE_DIRS@ -gmp-lib-dirs = @GMP_LIB_DIRS@ +gmp-include-dir = @GMP_INCLUDE_DIRS@ +gmp-lib-dir = @GMP_LIB_DIRS@ use-system-ffi = @UseSystemLibFFI@ ffi-include-dir = @FFIIncludeDir@ diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index f4540cc..3502929 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -49,16 +49,16 @@ data Setting = BuildArch | TargetVendor | FfiIncludeDir | FfiLibDir + | GmpIncludeDir + | GmpLibDir + | IconvIncludeDir + | IconvLibDir data SettingList = ConfCcArgs Stage | ConfCppArgs Stage | ConfGccLinkerArgs Stage | ConfLdLinkerArgs Stage - | GmpIncludeDirs - | GmpLibDirs | HsCppArgs - | IconvIncludeDirs - | IconvLibDirs setting :: Setting -> Action String setting key = askConfig $ case key of @@ -92,6 +92,10 @@ setting key = askConfig $ case key of TargetVendor -> "target-vendor" FfiIncludeDir -> "ffi-include-dir" FfiLibDir -> "ffi-lib-dir" + GmpIncludeDir -> "gmp-include-dir" + GmpLibDir -> "gmp-lib-dir" + IconvIncludeDir -> "iconv-include-dir" + IconvLibDir -> "iconv-lib-dir" settingList :: SettingList -> Action [String] settingList key = fmap words $ askConfig $ case key of @@ -99,11 +103,7 @@ settingList key = fmap words $ askConfig $ case key of ConfCppArgs stage -> "conf-cpp-args-" ++ stageString stage ConfGccLinkerArgs stage -> "conf-gcc-linker-args-" ++ stageString stage ConfLdLinkerArgs stage -> "conf-ld-linker-args-" ++ stageString stage - GmpIncludeDirs -> "gmp-include-dirs" - GmpLibDirs -> "gmp-lib-dirs" HsCppArgs -> "hs-cpp-args" - IconvIncludeDirs -> "iconv-include-dirs" - IconvLibDirs -> "iconv-lib-dirs" getSetting :: Setting -> ReaderT a Action String getSetting = lift . setting diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index ec14b36..702e645 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -62,10 +62,10 @@ configureArguments = do configureIntGmpArguments :: Action [String] configureIntGmpArguments = do - includes <- settingList GmpIncludeDirs - libs <- settingList GmpLibDirs - return $ map ("--with-gmp-includes=" ++) includes - ++ map ("--with-gmp-libraries=" ++) libs + includes <- setting GmpIncludeDir + libs <- setting GmpLibDir + return $ map ("--with-gmp-includes=" ++) [includes] + ++ map ("--with-gmp-libraries=" ++) [libs] -- TODO: we rebuild gmp every time. gmpRules :: Rules () diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 06787c5..51d0e6b 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -79,10 +79,10 @@ configureArgs = do , conf "LDFLAGS" ldFlags , conf "CPPFLAGS" cppFlags , appendSubD "--gcc-options" $ cFlags <> ldFlags - , conf "--with-iconv-includes" $ argSettingList IconvIncludeDirs - , conf "--with-iconv-libraries" $ argSettingList IconvLibDirs - , conf "--with-gmp-includes" $ argSettingList GmpIncludeDirs - , conf "--with-gmp-libraries" $ argSettingList GmpLibDirs + , conf "--with-iconv-includes" $ argSetting IconvIncludeDir + , conf "--with-iconv-libraries" $ argSetting IconvLibDir + , conf "--with-gmp-includes" $ argSetting GmpIncludeDir + , conf "--with-gmp-libraries" $ argSetting GmpLibDir , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" $ argStagedBuilderPath Gcc ] diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index c4e518b..4529af8 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -17,7 +17,7 @@ hsc2hsBuilderArgs :: Args hsc2hsBuilderArgs = builder Hsc2Hs ? do stage <- getStage ccPath <- lift . builderPath $ Gcc stage - gmpDirs <- getSettingList GmpIncludeDirs + gmpDir <- getSetting GmpIncludeDir cFlags <- getCFlags lFlags <- getLFlags top <- getTopDirectory @@ -32,7 +32,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" - , append $ map ("-I" ++) gmpDirs + , append $ map ("-I" ++) [gmpDir] , append $ map ("--cflag=" ++) cFlags , append $ map ("--lflag=" ++) lFlags , notStage0 ? crossCompiling ? arg "--cross-compile" From git at git.haskell.org Fri Oct 27 00:42:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refine cross-compilation implementation (#410) (ae1f7c1) Message-ID: <20171027004211.ED1E83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c/ghc >--------------------------------------------------------------- commit ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c Author: Zhen Zhang Date: Tue Sep 12 00:54:29 2017 +0800 Refine cross-compilation implementation (#410) * Update minimum heap size * Refine cross-compilation implementation >--------------------------------------------------------------- ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c hadrian.cabal | 1 + src/GHC.hs | 4 +++- src/Oracles/Flag.hs | 5 ++++- src/Settings.hs | 4 +++- src/Settings/Builders/Common.hs | 3 ++- src/Settings/Flavours/Development.hs | 2 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/QuickCross.hs | 23 +++++++++++++++++++++++ src/Settings/Flavours/Quickest.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcPkg.hs | 4 ++-- src/Settings/Packages/Haskeline.hs | 2 +- src/UserSettings.hs | 7 +------ 16 files changed, 47 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c From git at git.haskell.org Fri Oct 27 00:42:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor discovery of generated dependencies (bb43f24) Message-ID: <20171027004212.36DA13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bb43f249ba63559f988fedac9b5180bfdc28d1cf/ghc >--------------------------------------------------------------- commit bb43f249ba63559f988fedac9b5180bfdc28d1cf Author: Andrey Mokhov Date: Fri Oct 21 01:30:10 2016 +0100 Refactor discovery of generated dependencies See #285, #267. >--------------------------------------------------------------- bb43f249ba63559f988fedac9b5180bfdc28d1cf src/Builder.hs | 8 ++---- src/Rules/Compile.hs | 59 +++++++++++++++++++++++---------------------- src/Rules/Generate.hs | 17 +------------ src/Settings/Builders/Cc.hs | 12 ++------- 4 files changed, 35 insertions(+), 61 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 09b87cb..860034e 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -20,12 +20,8 @@ import Stage -- 1) Compiling sources into object files. -- 2) Extracting source dependencies, e.g. by passing -M command line argument. -- 3) Linking object files & static libraries into an executable. --- We have CcMode for CC and GhcMode for GHC. - --- TODO: Consider merging FindCDependencies and FindMissingInclude -data CcMode = CompileC | FindCDependencies | FindMissingInclude - deriving (Eq, Generic, Show) - +-- We have CcMode for C compiler and GhcMode for GHC. +data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show) data GhcMode = CompileHs | FindHsDependencies | LinkHs deriving (Eq, Generic, Show) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 535758c..285abe0 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -1,5 +1,7 @@ module Rules.Compile (compilePackage) where +import Development.Shake.Util + import Base import Context import Expression @@ -9,21 +11,14 @@ import Rules.Generate import Settings.Paths import Target -import Development.Shake.Util - -import qualified Data.Set as Set - compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context nonHs extension = path extension "*" <.> osuf way compile compiler obj2src obj = do - let depFile = obj -<.> "d" - src = obj2src context obj + let src = obj2src context obj need [src] - needGenerated context src - build $ Target context (Cc FindCDependencies stage) [src] [depFile] - needMakefileDependencies depFile -- TODO: Is this actually needed? + needDependencies context src $ obj <.> "d" build $ Target context (compiler stage) [src] [obj] compileHs = \[obj, _] -> do (src, deps) <- fileDependencies context obj @@ -41,28 +36,27 @@ compilePackage rs context at Context {..} = do [ path "*" <.> suf way | suf <- [ osuf, hisuf] ] &%> compileHs [ path "*" <.> suf way | suf <- [obootsuf, hibootsuf] ] &%> compileHs --- TODO: Simplify. -needGenerated :: Context -> FilePath -> Action () -needGenerated context origFile = go Set.empty +-- | Discover dependencies of a given source file by iteratively calling @gcc@ +-- in the @-MM -MG@ mode and building generated dependencies if they are missing +-- until reaching a fixed point. +needDependencies :: Context -> FilePath -> FilePath -> Action () +needDependencies context at Context {..} src depFile = discover where - go :: Set.Set String -> Action () - go done = withTempFile $ \outFile -> do - let builder = Cc FindMissingInclude $ stage context - target = Target context builder [origFile] [outFile] - build target - deps <- parseFile outFile - - -- Get the full path if the include refers to a generated file and call - -- `need` on it. - needed <- liftM catMaybes $ - interpretInContext context (mapM getPathIfGenerated deps) - need needed + discover = do + build $ Target context (Cc FindCDependencies stage) [src] [depFile] + deps <- parseFile depFile + -- Generated dependencies, if not yet built, will not be found and hence + -- will be referred to simply by their file names. + let notFound = filter (\file -> file == takeFileName file) deps + -- We find the full paths to generated dependencies, so we can request + -- to build them by calling 'need'. + todo <- catMaybes <$> mapM (fullPathIfGenerated context) notFound - let newdone = Set.fromList needed `Set.union` done - -- If we added a new file to the set of needed files, let's try one more - -- time, since the new file might include a genreated header of itself - -- (which we'll `need`). - when (Set.size newdone > Set.size done) (go newdone) + if null todo + then need deps -- The list of dependencies is final, need all + else do + need todo -- Build newly discovered generated dependencies + discover -- Continue the discovery process parseFile :: FilePath -> Action [String] parseFile file = do @@ -71,6 +65,13 @@ needGenerated context origFile = go Set.empty [(_file, deps)] -> return deps _ -> return [] +-- | Find a given 'FilePath' in the list of generated files in the given +-- 'Context' and return its full path. +fullPathIfGenerated :: Context -> FilePath -> Action (Maybe FilePath) +fullPathIfGenerated context file = interpretInContext context $ do + generated <- generatedDependencies + return $ find ((== file) . takeFileName) generated + obj2src :: String -> (FilePath -> Bool) -> Context -> FilePath -> FilePath obj2src extension isGenerated context at Context {..} obj | isGenerated src = src diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index ceeb182..bfede1a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,7 +1,6 @@ module Rules.Generate ( isGeneratedCFile, isGeneratedCmmFile, generatePackageCode, generateRules, - installTargets, copyRules, includesDependencies, generatedDependencies, - getPathIfGenerated + installTargets, copyRules, includesDependencies, generatedDependencies ) where import qualified System.Directory as IO @@ -199,17 +198,3 @@ generateRules = do emptyTarget :: Context emptyTarget = vanillaContext (error "Rules.Generate.emptyTarget: unknown stage") (error "Rules.Generate.emptyTarget: unknown package") - -getPathIfGenerated :: FilePath -> Expr (Maybe FilePath) -getPathIfGenerated include = do - generated <- generatedFiles - -- For includes of generated files, we cannot get the full path of the file - -- (since it might be included due to some include dir, i.e., through `-I`). - -- So here we try both the name and the path. - let nameOrPath (name, path) = include == name || include == path - return . fmap snd $ find nameOrPath generated - -generatedFiles :: Expr [(FilePath, FilePath)] -generatedFiles = do - deps <- generatedDependencies - return [ (takeFileName fp, fp) | fp <- deps ] diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index 41a8466..595feab 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -21,19 +21,11 @@ ccBuilderArgs = builder Cc ? mconcat output <- getOutput mconcat [ arg "-E" , arg "-MM" + , arg "-MG" , arg "-MF" , arg output , arg "-MT" , arg $ dropExtension output -<.> "o" , arg "-x" , arg "c" - , arg =<< getInput ] - - , builder (Cc FindMissingInclude) ? - mconcat [ arg "-E" - , arg "-MM" - , arg "-MG" - , arg "-MF" - , arg =<< getOutput - , arg =<< getInput ] - ] + , arg =<< getInput ] ] From git at git.haskell.org Fri Oct 27 00:42:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #183 from kgardas/fix_dirs_to_dir (875d9ca) Message-ID: <20171027004214.D24723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/875d9ca47a82c58c2e5e99864f67dc5f3559dffc/ghc >--------------------------------------------------------------- commit 875d9ca47a82c58c2e5e99864f67dc5f3559dffc Merge: 6e00b02 36b7f4d Author: Andrey Mokhov Date: Tue Jan 19 08:54:29 2016 +0000 Merge pull request #183 from kgardas/fix_dirs_to_dir fix "dirs" to "dir" for gmp and iconv libraries >--------------------------------------------------------------- 875d9ca47a82c58c2e5e99864f67dc5f3559dffc cfg/system.config.in | 8 ++++---- src/Oracles/Config/Setting.hs | 16 ++++++++-------- src/Rules/Gmp.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 8 ++++---- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- 5 files changed, 22 insertions(+), 22 deletions(-) From git at git.haskell.org Fri Oct 27 00:42:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix performance bug: Stage0 packages do not depend on inplaceLibCopyTargets (17be7a1) Message-ID: <20171027004215.75CE63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/17be7a10e780a792e7082aa1f8bef0b0887957a5/ghc >--------------------------------------------------------------- commit 17be7a10e780a792e7082aa1f8bef0b0887957a5 Author: Andrey Mokhov Date: Thu Sep 14 01:13:37 2017 +0100 Fix performance bug: Stage0 packages do not depend on inplaceLibCopyTargets See #393 >--------------------------------------------------------------- 17be7a10e780a792e7082aa1f8bef0b0887957a5 src/Settings/Builders/GhcCabal.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index fc39637..c555bf0 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -6,15 +6,14 @@ import Hadrian.Haskell.Cabal import Context import Flavour -import Settings.Builders.Common hiding (package) +import Settings.Builders.Common ghcCabalBuilderArgs :: Args ghcCabalBuilderArgs = builder GhcCabal ? do verbosity <- expr getVerbosity top <- expr topDirectory - context <- getContext path <- getBuildPath - when (package context /= deriveConstants) $ expr (need inplaceLibCopyTargets) + notStage0 ? expr (need inplaceLibCopyTargets) mconcat [ arg "configure" , arg =<< pkgPath <$> getPackage , arg $ top -/- path From git at git.haskell.org Fri Oct 27 00:42:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify, drop code duplication, add comments (ffff1b3) Message-ID: <20171027004215.BE69A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffff1b38a54fcf55e4a809cc6c403a60016d1492/ghc >--------------------------------------------------------------- commit ffff1b38a54fcf55e4a809cc6c403a60016d1492 Author: Andrey Mokhov Date: Sat Oct 22 00:47:53 2016 +0100 Simplify, drop code duplication, add comments >--------------------------------------------------------------- ffff1b38a54fcf55e4a809cc6c403a60016d1492 src/Oracles/ModuleFiles.hs | 21 +++++++--- src/Rules/Compile.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 4 +- src/Rules/Library.hs | 99 ++++++++++++---------------------------------- src/Rules/Program.hs | 45 +++++++++------------ src/Settings/Paths.hs | 29 +++++++++++++- 7 files changed, 92 insertions(+), 110 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 ffff1b38a54fcf55e4a809cc6c403a60016d1492 From git at git.haskell.org Fri Oct 27 00:42:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CI regression, minor revision. (8f68b8b) Message-ID: <20171027004218.6985A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f68b8bc8dc40a17eb8c0816437a4b474b9def78/ghc >--------------------------------------------------------------- commit 8f68b8bc8dc40a17eb8c0816437a4b474b9def78 Author: Andrey Mokhov Date: Tue Jan 19 09:34:35 2016 +0000 Fix CI regression, minor revision. See #183. >--------------------------------------------------------------- 8f68b8bc8dc40a17eb8c0816437a4b474b9def78 cfg/system.config.in | 2 +- src/Rules/Gmp.hs | 4 ++-- src/Rules/Libffi.hs | 8 ++++---- src/Settings/Builders/Hsc2Hs.hs | 2 +- 4 files changed, 8 insertions(+), 8 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 0eb775a..43730a2 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -106,7 +106,7 @@ iconv-lib-dir = @ICONV_LIB_DIRS@ gmp-include-dir = @GMP_INCLUDE_DIRS@ gmp-lib-dir = @GMP_LIB_DIRS@ -use-system-ffi = @UseSystemLibFFI@ +use-system-ffi = @UseSystemLibFFI@ ffi-include-dir = @FFIIncludeDir@ ffi-lib-dir = @FFILibDir@ diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 702e645..b6bfdf0 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -64,8 +64,8 @@ configureIntGmpArguments :: Action [String] configureIntGmpArguments = do includes <- setting GmpIncludeDir libs <- setting GmpLibDir - return $ map ("--with-gmp-includes=" ++) [includes] - ++ map ("--with-gmp-libraries=" ++) [libs] + return $ map ("--with-gmp-includes=" ++) (words includes) + ++ map ("--with-gmp-libraries=" ++) (words libs) -- TODO: we rebuild gmp every time. gmpRules :: Rules () diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 97ebc2d..0f4e05a 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -71,13 +71,13 @@ libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] - ffi_header_dir <- setting FfiIncludeDir - use_system_ffi <- flag UseSystemFfi - if use_system_ffi + ffiHeaderDir <- setting FfiIncludeDir + useSystemFfi <- flag UseSystemFfi + if useSystemFfi then do putBuild "| System supplied FFI library will be used" forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - let src = ffi_header_dir -/- file + let src = ffiHeaderDir -/- file copyFile src (rtsBuildPath -/- file) putSuccess $ "| Successfully copied system supplied FFI library header files" else do diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 4529af8..ffa3b1a 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -32,7 +32,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" - , append $ map ("-I" ++) [gmpDir] + , append . map ("-I" ++) $ words gmpDir , append $ map ("--cflag=" ++) cFlags , append $ map ("--lflag=" ++) lFlags , notStage0 ? crossCompiling ? arg "--cross-compile" From git at git.haskell.org Fri Oct 27 00:43:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install python3 on Travis OS X (6eb3059) Message-ID: <20171027004346.1AC683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6eb305962ccba06aeae22812e5733b5998843dcb/ghc >--------------------------------------------------------------- commit 6eb305962ccba06aeae22812e5733b5998843dcb Author: Andrey Mokhov Date: Thu Oct 5 11:34:12 2017 +0100 Install python3 on Travis OS X See #314 >--------------------------------------------------------------- 6eb305962ccba06aeae22812e5733b5998843dcb .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 9082ef6..203ee82 100644 --- a/.travis.yml +++ b/.travis.yml @@ -51,7 +51,7 @@ matrix: env: MODE="--flavour=quickest --integer-simple inplace/bin/ghc-stage1" before_install: - brew update - - brew install ghc cabal-install + - brew install ghc cabal-install python3 script: # Due to timeout limit of OS X build on Travis CI, From git at git.haskell.org Fri Oct 27 00:43:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify builderPath (058cb92) Message-ID: <20171027004346.1A67E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/058cb92e8f1f21c271073d892d8b504726a345a2/ghc >--------------------------------------------------------------- commit 058cb92e8f1f21c271073d892d8b504726a345a2 Author: Andrey Mokhov Date: Sat Oct 29 02:42:29 2016 +0100 Simplify builderPath >--------------------------------------------------------------- 058cb92e8f1f21c271073d892d8b504726a345a2 src/Builder.hs | 11 +++-------- src/GHC.hs | 2 +- src/Package.hs | 1 - 3 files changed, 4 insertions(+), 10 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index c5dc9fb..61960c7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -94,14 +94,9 @@ isOptional = \case -- | Determine the location of a 'Builder'. builderPath :: Builder -> Action FilePath -builderPath builder = case builderProvenance builder of - Just context - | Just path <- programPath context -> return path - | otherwise -> - -- TODO: Make builderPath total. - error $ "Cannot determine builderPath for " ++ show builder - ++ " in context " ++ show context - Nothing -> case builder of +builderPath builder = case programPath =<< builderProvenance builder of + Just path -> return path + Nothing -> case builder of Alex -> fromKey "alex" Ar -> fromKey "ar" Cc _ Stage0 -> fromKey "system-cc" diff --git a/src/GHC.hs b/src/GHC.hs index 2af8923..91987c6 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -86,7 +86,7 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" --- | ghc-split is a perl script used by GHC with @-split-objs@ flag. It is +-- | @ghc-split@ is a Perl script used by GHC with @-split-objs@ flag. It is -- generated in "Rules.Generators.GhcSplit". ghcSplit :: FilePath ghcSplit = "inplace/lib/bin/ghc-split" diff --git a/src/Package.hs b/src/Package.hs index bee5640..8a1a8d2 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -17,7 +17,6 @@ newtype PackageName = PackageName { fromPackageName :: String } deriving (Binary, Eq, Generic, Hashable, IsString, NFData, Ord, Typeable) -- TODO: Make PackageType more precise, #12. --- TODO: Turn Program to Program FilePath thereby getting rid of programPath -- | We regard packages as either being libraries or programs. This is bit of a -- convenient lie as Cabal packages can be both, but it works for now. data PackageType = Library | Program deriving Generic From git at git.haskell.org Fri Oct 27 00:43:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: fix typos in build.*.sh (4aa3bb6) Message-ID: <20171027004348.21FB23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4aa3bb622b08d7f7b2fe0b45c32c4127f5ca972a/ghc >--------------------------------------------------------------- commit 4aa3bb622b08d7f7b2fe0b45c32c4127f5ca972a Author: Joe Hillenbrand Date: Fri Jan 22 16:24:41 2016 -0800 fix typos in build.*.sh >--------------------------------------------------------------- 4aa3bb622b08d7f7b2fe0b45c32c4127f5ca972a build.cabal.sh | 6 +++--- build.stack.sh | 6 +++--- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/build.cabal.sh b/build.cabal.sh index 8add516..5f20c1b 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -28,8 +28,8 @@ function rl { echo "$RESULT" } -absoltueRoot="$(dirname "$(rl "$0")")" -cd "$absoltueRoot" +absoluteRoot="$(dirname "$(rl "$0")")" +cd "$absoluteRoot" # Initialize sandbox if necessary if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then @@ -42,6 +42,6 @@ fi cabal run ghc-shake -- \ --lint \ - --directory "$absoltueRoot/.." \ + --directory "$absoluteRoot/.." \ --colour \ "$@" diff --git a/build.stack.sh b/build.stack.sh index 1cc968b..578e7eb 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -28,13 +28,13 @@ function rl { echo "$RESULT" } -absoltueRoot="$(dirname "$(rl "$0")")" -cd "$absoltueRoot" +absoluteRoot="$(dirname "$(rl "$0")")" +cd "$absoluteRoot" stack build --no-library-profiling stack exec ghc-shake -- \ --lint \ - --directory "$absoltueRoot/.." \ + --directory "$absoluteRoot/.." \ --colour \ "$@" From git at git.haskell.org Fri Oct 27 00:43:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update docs (c70f765) Message-ID: <20171027004350.130E13A5E9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c70f765b7aaecaa4bfed5c39e33e1e5111b1ce30/ghc >--------------------------------------------------------------- commit c70f765b7aaecaa4bfed5c39e33e1e5111b1ce30 Author: Andrey Mokhov Date: Thu Oct 5 12:43:25 2017 +0100 Update docs See #314 >--------------------------------------------------------------- c70f765b7aaecaa4bfed5c39e33e1e5111b1ce30 doc/windows.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/windows.md b/doc/windows.md index 510b986..f644f03 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -24,7 +24,7 @@ cd hadrian stack setup # Install utilities required during the GHC build process -stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm +stack exec -- pacman -S autoconf automake-wrapper make patch python tar --noconfirm # Build Hadrian and dependencies (including GHC dependencies Alex and Happy) stack build From git at git.haskell.org Fri Oct 27 00:43:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor programPath (44f7374) Message-ID: <20171027004350.129F13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44f7374237aa86baf551860bb943b1707fc286a8/ghc >--------------------------------------------------------------- commit 44f7374237aa86baf551860bb943b1707fc286a8 Author: Andrey Mokhov Date: Sat Oct 29 03:53:46 2016 +0100 Refactor programPath >--------------------------------------------------------------- 44f7374237aa86baf551860bb943b1707fc286a8 src/GHC.hs | 67 ++++++++++++++++++++++++++++++++++++++------------------------ 1 file changed, 41 insertions(+), 26 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 91987c6..6c1e147 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -96,31 +96,46 @@ stageDirectory :: Stage -> FilePath stageDirectory = stageString -- TODO: move to buildRootPath, see #113 --- TODO: simplify, add programInplaceLibPath --- | The relative path to the program executable +-- | The 'FilePath' to a program executable in a given 'Context'. programPath :: Context -> Maybe FilePath -programPath Context {..} - | package == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) - | package `elem` [mkUserGuidePart] = - case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package - _ -> Nothing - | package `elem` [checkApiAnnotations, ghcTags, haddock] = - case stage of Stage2 -> Just . inplaceProgram $ pkgNameString package - _ -> Nothing - | package `elem` [touchy, unlit] = case stage of - Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString package <.> exe - _ -> Nothing - | package == hpcBin = case stage of - Stage1 -> Just $ inplaceProgram "hpc" - _ -> Nothing - | package == runGhc = case stage of - Stage1 -> Just $ inplaceProgram "runhaskell" - _ -> Nothing - | isProgram package = case stage of - Stage0 -> Just . inplaceProgram $ pkgNameString package - _ -> Just . installProgram $ pkgNameString package - | otherwise = Nothing +programPath Context {..} = lookup (stage, package) exes where - inplaceProgram name = programInplacePath -/- name <.> exe - installProgram name = pkgPath package -/- stageDirectory stage - -/- "build/tmp" -/- name <.> exe + exes = [ inplace2 checkApiAnnotations + , install1 compareSizes + , inplace0 deriveConstants + , inplace0 dllSplit + , inplace0 genapply + , inplace0 genprimopcode + , inplace0 ghc `setFile` "ghc-stage1" + , inplace1 ghc `setFile` "ghc-stage2" + , install0 ghcCabal + , inplace1 ghcCabal + , inplace0 ghcPkg + , install1 ghcPkg + , inplace2 ghcTags + , inplace2 haddock + , inplace0 hp2ps + , inplace1 hpcBin `setFile` "hpc" + , inplace0 hsc2hs + , install1 hsc2hs + , inplace0 mkUserGuidePart + , inplace1 runGhc `setFile` "runhaskell" + , inplace0 touchy `setDir` "inplace/lib/bin" + , inplace0 unlit `setDir` "inplace/lib/bin" ] + inplace pkg = programInplacePath -/- pkgNameString pkg <.> exe + inplace0 pkg = ((Stage0, pkg), inplace pkg) + inplace1 pkg = ((Stage1, pkg), inplace pkg) + inplace2 pkg = ((Stage2, pkg), inplace pkg) + install stage pkg = pkgPath package -/- stageDirectory stage -/- "build" + -/- pkgNameString pkg <.> exe + install0 pkg = ((Stage0, pkg), install Stage0 pkg) + install1 pkg = ((Stage1, pkg), install Stage1 pkg) + setFile ((stage, pkg), x) y = ((stage, pkg), takeDirectory x -/- y <.> exe) + setDir ((stage, pkg), x) y = ((stage, pkg), y -/- takeFileName x) + + -- | isProgram package = case stage of + -- Stage0 -> Just . inplaceProgram $ pkgNameString package + -- _ -> Just . installProgram $ pkgNameString package + -- | otherwise = Nothing + -- where + -- inplaceProgram name = programInplacePath -/- name <.> exe From git at git.haskell.org Fri Oct 27 00:43:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #190 from joehillen/stack (ce71b6d) Message-ID: <20171027004351.C5A693A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ce71b6dde7bf070e847b9d04673508b4d42066df/ghc >--------------------------------------------------------------- commit ce71b6dde7bf070e847b9d04673508b4d42066df Merge: 0bde9c1 4aa3bb6 Author: Andrey Mokhov Date: Sat Jan 23 00:36:13 2016 +0000 Merge pull request #190 from joehillen/stack Allow building ghc-shake with stack >--------------------------------------------------------------- ce71b6dde7bf070e847b9d04673508b4d42066df .gitignore | 1 + build.cabal.sh | 6 +++--- build.cabal.sh => build.stack.sh | 21 +++++++-------------- stack.yaml | 35 +++++++++++++++++++++++++++++++++++ 4 files changed, 46 insertions(+), 17 deletions(-) From git at git.haskell.org Fri Oct 27 00:43:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build iservBin, fix comments (28f2675) Message-ID: <20171027004353.851153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28f26751efa6336fac0798eb2e07795eeeb134b2/ghc >--------------------------------------------------------------- commit 28f26751efa6336fac0798eb2e07795eeeb134b2 Author: Andrey Mokhov Date: Sat Oct 29 11:15:33 2016 +0100 Build iservBin, fix comments >--------------------------------------------------------------- 28f26751efa6336fac0798eb2e07795eeeb134b2 src/GHC.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 6c1e147..c3242c6 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -95,6 +95,7 @@ ghcSplit = "inplace/lib/bin/ghc-split" stageDirectory :: Stage -> FilePath stageDirectory = stageString +-- TODO: Create a separate rule for copying executables to inplace/bin -- TODO: move to buildRootPath, see #113 -- | The 'FilePath' to a program executable in a given 'Context'. programPath :: Context -> Maybe FilePath @@ -118,6 +119,7 @@ programPath Context {..} = lookup (stage, package) exes , inplace1 hpcBin `setFile` "hpc" , inplace0 hsc2hs , install1 hsc2hs + , install1 iservBin , inplace0 mkUserGuidePart , inplace1 runGhc `setFile` "runhaskell" , inplace0 touchy `setDir` "inplace/lib/bin" @@ -132,10 +134,3 @@ programPath Context {..} = lookup (stage, package) exes install1 pkg = ((Stage1, pkg), install Stage1 pkg) setFile ((stage, pkg), x) y = ((stage, pkg), takeDirectory x -/- y <.> exe) setDir ((stage, pkg), x) y = ((stage, pkg), y -/- takeFileName x) - - -- | isProgram package = case stage of - -- Stage0 -> Just . inplaceProgram $ pkgNameString package - -- _ -> Just . installProgram $ pkgNameString package - -- | otherwise = Nothing - -- where - -- inplaceProgram name = programInplacePath -/- name <.> exe From git at git.haskell.org Fri Oct 27 00:43:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (c6efd3f) Message-ID: <20171027004353.8E27A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6efd3f68521f20632a0a173e1568aa772c0ea48/ghc >--------------------------------------------------------------- commit c6efd3f68521f20632a0a173e1568aa772c0ea48 Author: Andrey Mokhov Date: Thu Oct 5 17:58:20 2017 +0100 Minor revision >--------------------------------------------------------------- c6efd3f68521f20632a0a173e1568aa772c0ea48 doc/windows.md | 25 +++++++++++++------------ 1 file changed, 13 insertions(+), 12 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index f644f03..b374074 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -2,19 +2,11 @@ [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) -Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are -installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). - -Note that `git` should be configured to check out Unix-style line endings. The default behaviour of `git` on Windows is to check out Windows-style line endings which can cause issues during the build. This can be changed using the following command: - - git config --global core.autocrlf false - -If you would like to restore the default behaviour later run: - - git config --global core.autocrlf true +Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are installed +(see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). ```sh -# Get GHC and Hadrian sources +# Get GHC and Hadrian sources; git core.autocrlf should be set to false (see Prerequisites section) git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/hadrian @@ -55,6 +47,16 @@ The above works on a clean machine with `git` and `stack` installed (tested with installation settings), which you can get from https://git-scm.com/download/win and https://www.stackage.org/stack/windows-x86_64-installer. +Note that `git` should be configured to check out Unix-style line endings. The default behaviour +of `git` on Windows is to check out Windows-style line endings which can cause issues during the +build. This can be changed using the following command: + + git config --global core.autocrlf false + +If you would like to restore the default behaviour later run: + + git config --global core.autocrlf true + ## Testing These instructions have been tested on a clean Windows 10 machine using the @@ -65,4 +67,3 @@ and are also routinely tested on ## Notes Beware of the [current limitations of Hadrian](https://github.com/snowleopard/hadrian#current-limitations). - From git at git.haskell.org Fri Oct 27 00:43:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on build.stack.sh. (cf5d338) Message-ID: <20171027004355.3515B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf5d3387e960ae9ebdec5c08113e84195618dc3f/ghc >--------------------------------------------------------------- commit cf5d3387e960ae9ebdec5c08113e84195618dc3f Author: Andrey Mokhov Date: Sat Jan 23 00:42:04 2016 +0000 Add a note on build.stack.sh. [skip ci] >--------------------------------------------------------------- cf5d3387e960ae9ebdec5c08113e84195618dc3f README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 602148b..b8fd40f 100644 --- a/README.md +++ b/README.md @@ -39,7 +39,7 @@ On Windows, use `build.bat` instead and pass an extra flag to configure (also se ```bash shake-build/build.bat --configure=--enable-tarballs-autodownload ``` -If you are interested in building in a Cabal sandbox, have a look at `shake-build/build.cabal.sh`. +If you are interested in building in a Cabal sandbox or using Stack, have a look at `shake-build/build.cabal.sh` and `shake-build/build.stack.sh` scripts. Using the build system ---------------------- From git at git.haskell.org Fri Oct 27 00:43:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring back tmp directory for in-tree build artefacts (c93cf69) Message-ID: <20171027004357.674713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c93cf69f4cade6af063fcc26ebe13598f0eb9b56/ghc >--------------------------------------------------------------- commit c93cf69f4cade6af063fcc26ebe13598f0eb9b56 Author: Andrey Mokhov Date: Sat Oct 29 11:50:13 2016 +0100 Bring back tmp directory for in-tree build artefacts >--------------------------------------------------------------- c93cf69f4cade6af063fcc26ebe13598f0eb9b56 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index c3242c6..810c63d 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -128,7 +128,7 @@ programPath Context {..} = lookup (stage, package) exes inplace0 pkg = ((Stage0, pkg), inplace pkg) inplace1 pkg = ((Stage1, pkg), inplace pkg) inplace2 pkg = ((Stage2, pkg), inplace pkg) - install stage pkg = pkgPath package -/- stageDirectory stage -/- "build" + install stage pkg = pkgPath package -/- stageDirectory stage -/- "build/tmp" -/- pkgNameString pkg <.> exe install0 pkg = ((Stage0, pkg), install Stage0 pkg) install1 pkg = ((Stage1, pkg), install Stage1 pkg) From git at git.haskell.org Fri Oct 27 00:43:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant code (830567e) Message-ID: <20171027004357.7FB643A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/830567e388a89b90a80c0140379c983de3cec8aa/ghc >--------------------------------------------------------------- commit 830567e388a89b90a80c0140379c983de3cec8aa Author: Andrey Mokhov Date: Thu Oct 5 20:08:35 2017 +0100 Drop redundant code See #314 >--------------------------------------------------------------- 830567e388a89b90a80c0140379c983de3cec8aa src/Environment.hs | 12 ------------ 1 file changed, 12 deletions(-) diff --git a/src/Environment.hs b/src/Environment.hs index d92e067..de43efa 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -2,8 +2,6 @@ module Environment (setupEnvironment) where import System.Environment -import Base - -- | The build system invokes many external builders whose behaviour is -- influenced by the environment variables. We need to modify some of them -- for better robustness of the build system. @@ -16,13 +14,3 @@ setupEnvironment = do -- `pwd` will return the Windows path, and then modifying $PATH will fail. -- See https://github.com/snowleopard/hadrian/issues/189 for details. unsetEnv "PWD" - - -- On Windows, some path variables start a prefix like "C:\\" which may - -- lead to failures of scripts such as autoreconf. One particular variable - -- which causes issues is ACLOCAL_PATH. At the moment we simply reset it - -- if it contains a problematic Windows path. - -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. - aclocal <- lookupEnv "ACLOCAL_PATH" - case aclocal of - Nothing -> return () - Just s -> when (":\\" `isPrefixOf` drop 1 s) $ unsetEnv "ACLOCAL_PATH" From git at git.haskell.org Fri Oct 27 00:43:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move GMP build to Stage1. (3f74e8b) Message-ID: <20171027004358.A529E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3f74e8bf2c170740f46279b98659d57b47721afa/ghc >--------------------------------------------------------------- commit 3f74e8bf2c170740f46279b98659d57b47721afa Author: Andrey Mokhov Date: Sat Jan 23 15:36:20 2016 +0000 Move GMP build to Stage1. Should make AppVeyor CI fit in 1 hr. >--------------------------------------------------------------- 3f74e8bf2c170740f46279b98659d57b47721afa src/Rules/Generate.hs | 13 +++++++------ src/Rules/Gmp.hs | 15 ++++----------- src/Settings/Builders/Ghc.hs | 5 ++++- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Paths.hs | 2 +- 5 files changed, 17 insertions(+), 20 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 73b160a..f329228 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -43,11 +43,12 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -defaultDependencies :: [FilePath] -defaultDependencies = concat +defaultDependencies :: Stage -> [FilePath] +defaultDependencies stage = concat [ includesDependencies - , libffiDependencies - , gmpDependencies ] + , libffiDependencies ] + ++ + [ gmpLibraryH | stage > Stage0 ] ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> @@ -67,7 +68,7 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = [ platformH stage ] - ++ defaultDependencies ++ derivedConstantsDependencies + ++ defaultDependencies stage ++ derivedConstantsDependencies ++ fmap ((targetPath stage compiler -/- "build") -/-) [ "primop-vector-uniques.hs-incl" , "primop-data-decl.hs-incl" @@ -91,7 +92,7 @@ generatedDependencies stage pkg | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = libffiDependencies ++ includesDependencies ++ derivedConstantsDependencies - | stage == Stage0 = defaultDependencies + | stage == Stage0 = defaultDependencies Stage0 | otherwise = [] -- The following generators and corresponding source extensions are supported: diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index b6bfdf0..b384b68 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,6 +1,4 @@ -module Rules.Gmp ( - gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH, gmpDependencies - ) where +module Rules.Gmp (gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH) where import qualified System.Directory as IO @@ -17,7 +15,7 @@ gmpBase :: FilePath gmpBase = "libraries/integer-gmp/gmp" gmpTarget :: PartialTarget -gmpTarget = PartialTarget Stage0 integerGmp +gmpTarget = PartialTarget Stage1 integerGmp gmpObjects :: FilePath gmpObjects = gmpBuildPath -/- "objs" @@ -34,9 +32,6 @@ gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" gmpLibraryFakeH :: FilePath gmpLibraryFakeH = gmpBase -/- "ghc-gmp.h" -gmpDependencies :: [FilePath] -gmpDependencies = [gmpLibraryH] - gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] @@ -77,11 +72,11 @@ gmpRules = do liftIO $ removeFiles gmpBuildPath ["//*"] - envs <- configureEnvironment -- TODO: without the optimisation below we configure integerGmp package -- twice -- think how this can be optimised (shall we solve #18 first?) -- TODO: this is a hacky optimisation: we do not rerun configure of -- integerGmp package if we detect the results of the previous run + envs <- configureEnvironment unlessM (liftIO . IO.doesFileExist $ gmpBase -/- "config.mk") $ do args <- configureIntGmpArguments runConfigure (pkgPath integerGmp) envs args @@ -148,6 +143,4 @@ gmpRules = do runBuilder Ranlib [gmpLibrary] - putSuccess "| Successfully built custom library 'integer-gmp'" - - -- gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] + putSuccess "| Successfully built custom library 'gmp'" diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 3537aed..c79fc50 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -19,12 +19,15 @@ import Settings.Builders.Common (cIncludeArgs) ghcBuilderArgs :: Args ghcBuilderArgs = stagedBuilder Ghc ? do output <- getOutput + stage <- getStage way <- getWay let buildObj = ("//*." ++ osuf way) ?== output || ("//*." ++ obootsuf way) ?== output buildHi = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output buildProg = not (buildObj || buildHi) libs <- getPkgDataList DepExtraLibs - gmpLibs <- lift $ readFileLines gmpLibNameCache + gmpLibs <- if stage > Stage0 && buildProg + then lift $ readFileLines gmpLibNameCache -- TODO: use oracles + else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ commonGhcArgs , arg "-H32m" diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 9ad160f..0640e52 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -16,7 +16,7 @@ integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" gmpIncludeDir <- getSetting GmpIncludeDir - gmpLibDir <- getSetting GmpLibDir + gmpLibDir <- getSetting GmpLibDir mconcat [ builder GhcCabal ? mconcat [ (null gmpIncludeDir && null gmpLibDir) ? diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 3e9fec9..ed217a8 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -39,7 +39,7 @@ pkgGhciLibraryFile stage pkg componentId = -- This is the build directory for in-tree GMP library gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage0/gmp" +gmpBuildPath = buildRootPath -/- "stage1/gmp" -- GMP library names extracted from integer-gmp.buildinfo gmpLibNameCache :: FilePath From git at git.haskell.org Fri Oct 27 00:44:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor builder path manipulation (8ee46b1) Message-ID: <20171027004401.552C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2/ghc >--------------------------------------------------------------- commit 8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2 Author: Andrey Mokhov Date: Sun Oct 30 01:54:14 2016 +0100 Refactor builder path manipulation >--------------------------------------------------------------- 8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2 hadrian.cabal | 2 +- src/Builder.hs | 92 +------------------------------- src/GHC.hs | 67 ++++++++--------------- src/Oracles/WindowsPath.hs | 45 ---------------- src/Rules/Actions.hs | 24 ++++++++- src/Rules/Documentation.hs | 2 +- src/Rules/Generators/ConfigHs.hs | 1 + src/Rules/Generators/GhcSplit.hs | 1 + src/Rules/Oracles.hs | 4 +- src/Rules/Program.hs | 5 -- src/Rules/Test.hs | 3 +- src/Rules/Wrappers/Ghc.hs | 2 +- src/Rules/Wrappers/GhcPkg.hs | 2 +- src/Settings/Builders/Common.hs | 4 +- src/Settings/Builders/DeriveConstants.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 3 +- src/Settings/Builders/Haddock.hs | 7 ++- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Paths.hs | 64 +++++++++++++++++++++- 19 files changed, 128 insertions(+), 206 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 8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2 From git at git.haskell.org Fri Oct 27 00:44:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop the redundant build rule for literate Perl scripts (a69c73f) Message-ID: <20171027004401.565373A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a69c73fe0d051d87cfc6fd95c72089faa92c5a0f/ghc >--------------------------------------------------------------- commit a69c73fe0d051d87cfc6fd95c72089faa92c5a0f Author: Andrey Mokhov Date: Sat Oct 7 23:26:08 2017 +0100 Drop the redundant build rule for literate Perl scripts >--------------------------------------------------------------- a69c73fe0d051d87cfc6fd95c72089faa92c5a0f hadrian.cabal | 1 - src/Rules.hs | 2 -- src/Rules/Perl.hs | 13 ------------- 3 files changed, 16 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 97b283a..48514e1 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -54,7 +54,6 @@ executable hadrian , Rules.Install , Rules.Libffi , Rules.Library - , Rules.Perl , Rules.Program , Rules.Register , Rules.Selftest diff --git a/src/Rules.hs b/src/Rules.hs index ea3df45..730823f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -17,7 +17,6 @@ import qualified Rules.Configure import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Library -import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings @@ -115,7 +114,6 @@ buildRules = do Rules.Gmp.gmpRules Rules.Libffi.libffiRules packageRules - Rules.Perl.perlScriptRules oracleRules :: Rules () oracleRules = do diff --git a/src/Rules/Perl.hs b/src/Rules/Perl.hs deleted file mode 100644 index bc8b01f..0000000 --- a/src/Rules/Perl.hs +++ /dev/null @@ -1,13 +0,0 @@ -module Rules.Perl (perlScriptRules) where - -import Base -import Builder - --- TODO: Do we need this build rule? --- | Build Perl scripts, such as @ghc-split@, from their literate Perl sources. -perlScriptRules :: Rules () -perlScriptRules = do - "//*.prl" %> \out -> do - let src = out -<.> "lprl" - need [src] - runBuilder Unlit [src, out] [src] [out] From git at git.haskell.org Fri Oct 27 00:44:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move libffi build to Stage1. (48d0ee0) Message-ID: <20171027004402.4F1B53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/48d0ee0e397abc8fb447db6e3c858b4d5be2f863/ghc >--------------------------------------------------------------- commit 48d0ee0e397abc8fb447db6e3c858b4d5be2f863 Author: Andrey Mokhov Date: Sat Jan 23 17:04:11 2016 +0000 Move libffi build to Stage1. Should make AppVeyor CI fit in 1 hr. >--------------------------------------------------------------- 48d0ee0e397abc8fb447db6e3c858b4d5be2f863 src/Rules/Generate.hs | 15 ++++++--------- src/Rules/Libffi.hs | 5 ++--- 2 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index f329228..d98527c 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -43,13 +43,6 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -defaultDependencies :: Stage -> [FilePath] -defaultDependencies stage = concat - [ includesDependencies - , libffiDependencies ] - ++ - [ gmpLibraryH | stage > Stage0 ] - ghcPrimDependencies :: Stage -> [FilePath] ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$> [ "GHC/PrimopWrappers.hs" @@ -68,7 +61,10 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) compilerDependencies :: Stage -> [FilePath] compilerDependencies stage = [ platformH stage ] - ++ defaultDependencies stage ++ derivedConstantsDependencies + ++ includesDependencies + ++ [ gmpLibraryH | stage > Stage0 ] + ++ filter (const $ stage > Stage0) libffiDependencies + ++ derivedConstantsDependencies ++ fmap ((targetPath stage compiler -/- "build") -/-) [ "primop-vector-uniques.hs-incl" , "primop-data-decl.hs-incl" @@ -86,13 +82,14 @@ compilerDependencies stage = , "primop-vector-tycons.hs-incl" , "primop-vector-tys.hs-incl" ] +-- TODO: Turn this into a FilePaths expression generatedDependencies :: Stage -> Package -> [FilePath] generatedDependencies stage pkg | pkg == compiler = compilerDependencies stage | pkg == ghcPrim = ghcPrimDependencies stage | pkg == rts = libffiDependencies ++ includesDependencies ++ derivedConstantsDependencies - | stage == Stage0 = defaultDependencies Stage0 + | stage == Stage0 = includesDependencies | otherwise = [] -- The following generators and corresponding source extensions are supported: diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0f4e05a..d2742eb 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -19,10 +19,10 @@ libffiDependencies :: [FilePath] libffiDependencies = (rtsBuildPath -/-) <$> [ "ffi.h", "ffitarget.h" ] libffiTarget :: PartialTarget -libffiTarget = PartialTarget Stage0 libffi +libffiTarget = PartialTarget Stage1 libffi libffiBuild :: FilePath -libffiBuild = buildRootPath -/- "stage0/libffi" +libffiBuild = buildRootPath -/- "stage1/libffi" libffiLibrary :: FilePath libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" @@ -33,7 +33,6 @@ fixLibffiMakefile = . replace "@toolexeclibdir@" "$(libdir)" . replace "@INSTALL@" "$(subst ../install-sh,C:/msys/home/chEEtah/ghc/install-sh, at INSTALL@)" - -- TODO: remove code duplication (see Settings/Builders/GhcCabal.hs) configureEnvironment :: Action [CmdOption] configureEnvironment = do From git at git.haskell.org Fri Oct 27 00:44:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing src/Oracles/Path.hs (e1e2621) Message-ID: <20171027004405.71C523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1e2621d6bdd5ebe98fb3787733d134fa4d2fd70/ghc >--------------------------------------------------------------- commit e1e2621d6bdd5ebe98fb3787733d134fa4d2fd70 Author: Andrey Mokhov Date: Sun Oct 30 01:01:43 2016 +0000 Add missing src/Oracles/Path.hs >--------------------------------------------------------------- e1e2621d6bdd5ebe98fb3787733d134fa4d2fd70 src/Oracles/Path.hs | 83 +++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 83 insertions(+) diff --git a/src/Oracles/Path.hs b/src/Oracles/Path.hs new file mode 100644 index 0000000..7db1400 --- /dev/null +++ b/src/Oracles/Path.hs @@ -0,0 +1,83 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module Oracles.Path ( + fixAbsolutePathOnWindows, topDirectory, getTopDirectory, windowsPathOracle, + systemBuilderPath + ) where + +import Control.Monad.Trans.Reader +import Data.Char + +import Base +import Builder +import Oracles.Config +import Oracles.Config.Setting +import Oracles.LookupInPath +import Stage + +newtype WindowsPath = WindowsPath FilePath + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Path to the GHC source tree. +topDirectory :: Action FilePath +topDirectory = fixAbsolutePathOnWindows =<< setting GhcSourcePath + +getTopDirectory :: ReaderT a Action FilePath +getTopDirectory = lift topDirectory + +-- | Determine the location of a system 'Builder'. +systemBuilderPath :: Builder -> Action FilePath +systemBuilderPath builder = case builder of + Alex -> fromKey "alex" + Ar -> fromKey "ar" + Cc _ Stage0 -> fromKey "system-cc" + Cc _ _ -> fromKey "cc" + -- We can't ask configure for the path to configure! + Configure _ -> return "bash configure" + Ghc _ Stage0 -> fromKey "system-ghc" + GhcPkg Stage0 -> fromKey "system-ghc-pkg" + Happy -> fromKey "happy" + HsColour -> fromKey "hscolour" + HsCpp -> fromKey "hs-cpp" + Ld -> fromKey "ld" + Make _ -> fromKey "make" + Nm -> fromKey "nm" + Objdump -> fromKey "objdump" + Patch -> fromKey "patch" + Perl -> fromKey "perl" + Ranlib -> fromKey "ranlib" + Tar -> fromKey "tar" + _ -> error $ "No system.config entry for " ++ show builder + where + fromKey key = do + let unpack = fromMaybe . error $ "Cannot find path to builder " + ++ quote key ++ " in system.config file. Did you skip configure?" + path <- unpack <$> askConfig key + if null path + then do + unless (isOptional builder) . error $ "Non optional builder " + ++ quote key ++ " is not specified in system.config file." + return "" -- TODO: Use a safe interface. + else fixAbsolutePathOnWindows =<< lookupInPath path + +-- | Fix an absolute path on Windows: +-- * "/c/" => "C:/" +-- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" +fixAbsolutePathOnWindows :: FilePath -> Action FilePath +fixAbsolutePathOnWindows path = do + windows <- windowsHost + if windows + then do + let (dir, file) = splitFileName path + winDir <- askOracle $ WindowsPath dir + return $ winDir -/- file + else + return path + +-- | Compute path mapping on Windows. This is slow and requires caching. +windowsPathOracle :: Rules () +windowsPathOracle = void $ + addOracle $ \(WindowsPath path) -> do + Stdout out <- quietly $ cmd ["cygpath", "-m", path] + let windowsPath = unifyPath $ dropWhileEnd isSpace out + putLoud $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath + return windowsPath From git at git.haskell.org Fri Oct 27 00:44:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement Stage1 GHC freezing (837675c) Message-ID: <20171027004405.7CBFC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/837675cdf374040b554dd04491b7e59aa631abd4/ghc >--------------------------------------------------------------- commit 837675cdf374040b554dd04491b7e59aa631abd4 Author: Andrey Mokhov Date: Mon Oct 9 01:14:54 2017 +0100 Implement Stage1 GHC freezing See #250 >--------------------------------------------------------------- 837675cdf374040b554dd04491b7e59aa631abd4 src/CommandLine.hs | 19 ++++++++++++++++--- src/Main.hs | 4 ++++ 2 files changed, 20 insertions(+), 3 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index cc6f944..a069c0e 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -1,10 +1,11 @@ module CommandLine ( - optDescrs, cmdLineArgsMap, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, - cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects, - cmdInstallDestDir + optDescrs, cmdLineArgsMap, cmdBuildHaddock, cmdFlavour, lookupFreeze1, + cmdIntegerSimple, cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, + cmdSplitObjects, cmdInstallDestDir ) where import Data.Either +import Data.Maybe import qualified Data.HashMap.Strict as Map import Data.List.Extra import Development.Shake hiding (Normal) @@ -16,6 +17,7 @@ import System.Environment data CommandLineArgs = CommandLineArgs { buildHaddock :: Bool , flavour :: Maybe String + , freeze1 :: Bool , installDestDir :: Maybe String , integerSimple :: Bool , progressColour :: UseColour @@ -29,6 +31,7 @@ defaultCommandLineArgs :: CommandLineArgs defaultCommandLineArgs = CommandLineArgs { buildHaddock = False , flavour = Nothing + , freeze1 = False , installDestDir = Nothing , integerSimple = False , progressColour = Auto @@ -36,6 +39,9 @@ defaultCommandLineArgs = CommandLineArgs , skipConfigure = False , splitObjects = False } +readFreeze1 :: Either String (CommandLineArgs -> CommandLineArgs) +readFreeze1 = Right $ \flags -> flags { freeze1 = True } + readBuildHaddock :: Either String (CommandLineArgs -> CommandLineArgs) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } @@ -84,6 +90,8 @@ optDescrs :: [OptDescr (Either String (CommandLineArgs -> CommandLineArgs))] optDescrs = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." + , Option [] ["freeze1"] (NoArg readFreeze1) + "Freeze Stage1 GHC." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["install-destdir"] (OptArg readInstallDestDir "DESTDIR") @@ -118,6 +126,11 @@ cmdBuildHaddock = buildHaddock <$> cmdLineArgs cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs +lookupFreeze1 :: Map.HashMap TypeRep Dynamic -> Bool +lookupFreeze1 m = fromMaybe (freeze1 defaultCommandLineArgs) (freeze1 <$> maybeValue) + where + maybeValue = fromDynamic =<< Map.lookup (typeOf defaultCommandLineArgs) m + cmdInstallDestDir :: Action (Maybe String) cmdInstallDestDir = installDestDir <$> cmdLineArgs diff --git a/src/Main.hs b/src/Main.hs index 91580dd..52af0ad 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -28,11 +28,15 @@ main = do BuildRoot buildRoot = UserSettings.userBuildRoot + rebuild = [ (RebuildLater, buildRoot -/- "stage0//*") + | CommandLine.lookupFreeze1 argsMap ] + options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = buildRoot -/- Base.shakeFilesDir , shakeProgress = progressSimple + , shakeRebuild = rebuild , shakeTimings = True , shakeExtra = extra } From git at git.haskell.org Fri Oct 27 00:44:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Force AppVeyor CI to succeed and store the cache. (e01bf2f) Message-ID: <20171027004406.1C4BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e01bf2f9e665a83e2cd5eae7f5a20df755ae67a9/ghc >--------------------------------------------------------------- commit e01bf2f9e665a83e2cd5eae7f5a20df755ae67a9 Author: Andrey Mokhov Date: Sat Jan 23 20:55:07 2016 +0000 Force AppVeyor CI to succeed and store the cache. [skip ci] >--------------------------------------------------------------- e01bf2f9e665a83e2cd5eae7f5a20df755ae67a9 .appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.appveyor.yml b/.appveyor.yml index d8854cc..dce914b 100644 --- a/.appveyor.yml +++ b/.appveyor.yml @@ -39,4 +39,4 @@ install: build_script: - cd C:\msys64\home\ghc\shake-build - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress inplace/bin/ghc-cabal.exe From git at git.haskell.org Fri Oct 27 00:44:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge LookupInPath and Path oracles (b42f4fd) Message-ID: <20171027004409.721833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b42f4fdd21227f799c0f3ed52b2f7bfe0225f4d9/ghc >--------------------------------------------------------------- commit b42f4fdd21227f799c0f3ed52b2f7bfe0225f4d9 Author: Andrey Mokhov Date: Sun Oct 30 01:11:22 2016 +0000 Merge LookupInPath and Path oracles >--------------------------------------------------------------- b42f4fdd21227f799c0f3ed52b2f7bfe0225f4d9 hadrian.cabal | 1 - src/Oracles/LookupInPath.hs | 23 ----------------------- src/Oracles/Path.hs | 35 +++++++++++++++++++++++++---------- src/Rules/Oracles.hs | 4 +--- 4 files changed, 26 insertions(+), 37 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 954b1d6..378aff7 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -32,7 +32,6 @@ executable hadrian , Oracles.Config.Setting , Oracles.Dependencies , Oracles.DirectoryContent - , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData , Oracles.Path diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs deleted file mode 100644 index 87e8adf..0000000 --- a/src/Oracles/LookupInPath.hs +++ /dev/null @@ -1,23 +0,0 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where - -import System.Directory - -import Base - -newtype LookupInPath = LookupInPath String - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - --- | Lookup an executable in @PATH at . -lookupInPath :: FilePath -> Action FilePath -lookupInPath name - | name == takeFileName name = askOracle $ LookupInPath name - | otherwise = return name - -lookupInPathOracle :: Rules () -lookupInPathOracle = void $ - addOracle $ \(LookupInPath name) -> do - let unpack = fromMaybe . error $ "Cannot find executable " ++ quote name - path <- unifyPath <$> unpack <$> liftIO (findExecutable name) - putLoud $ "Executable found: " ++ name ++ " => " ++ path - return path diff --git a/src/Oracles/Path.hs b/src/Oracles/Path.hs index 7db1400..1a74915 100644 --- a/src/Oracles/Path.hs +++ b/src/Oracles/Path.hs @@ -1,22 +1,18 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Path ( - fixAbsolutePathOnWindows, topDirectory, getTopDirectory, windowsPathOracle, - systemBuilderPath + topDirectory, getTopDirectory, systemBuilderPath, pathOracle ) where import Control.Monad.Trans.Reader import Data.Char +import System.Directory import Base import Builder import Oracles.Config import Oracles.Config.Setting -import Oracles.LookupInPath import Stage -newtype WindowsPath = WindowsPath FilePath - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -- | Path to the GHC source tree. topDirectory :: Action FilePath topDirectory = fixAbsolutePathOnWindows =<< setting GhcSourcePath @@ -59,6 +55,12 @@ systemBuilderPath builder = case builder of return "" -- TODO: Use a safe interface. else fixAbsolutePathOnWindows =<< lookupInPath path +-- | Lookup an executable in @PATH at . +lookupInPath :: FilePath -> Action FilePath +lookupInPath name + | name == takeFileName name = askOracle $ LookupInPath name + | otherwise = return name + -- | Fix an absolute path on Windows: -- * "/c/" => "C:/" -- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" @@ -73,11 +75,24 @@ fixAbsolutePathOnWindows path = do else return path --- | Compute path mapping on Windows. This is slow and requires caching. -windowsPathOracle :: Rules () -windowsPathOracle = void $ - addOracle $ \(WindowsPath path) -> do +newtype LookupInPath = LookupInPath String + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +newtype WindowsPath = WindowsPath FilePath + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Oracles for looking up paths. These are slow and require caching. +pathOracle :: Rules () +pathOracle = do + void $ addOracle $ \(WindowsPath path) -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] let windowsPath = unifyPath $ dropWhileEnd isSpace out putLoud $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath + + void $ addOracle $ \(LookupInPath name) -> do + let unpack = fromMaybe . error $ "Cannot find executable " ++ quote name + path <- unifyPath <$> unpack <$> liftIO (findExecutable name) + putLoud $ "Executable found: " ++ name ++ " => " ++ path + return path + diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 39fbd00..6c5ace4 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -5,7 +5,6 @@ import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies import qualified Oracles.DirectoryContent -import qualified Oracles.LookupInPath import qualified Oracles.ModuleFiles import qualified Oracles.PackageData import qualified Oracles.Path @@ -16,7 +15,6 @@ oracleRules = do Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles Oracles.DirectoryContent.directoryContentOracle - Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle - Oracles.Path.windowsPathOracle + Oracles.Path.pathOracle From git at git.haskell.org Fri Oct 27 00:44:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision, drop old TODO (cbee74b) Message-ID: <20171027004409.C67AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbee74bfe89e6b2b552c6ae560265ce2d9f5fb17/ghc >--------------------------------------------------------------- commit cbee74bfe89e6b2b552c6ae560265ce2d9f5fb17 Author: Andrey Mokhov Date: Tue Oct 10 00:37:42 2017 +0100 Minor revision, drop old TODO See #250 >--------------------------------------------------------------- cbee74bfe89e6b2b552c6ae560265ce2d9f5fb17 src/CommandLine.hs | 5 +---- src/Hadrian/Utilities.hs | 11 ++++++++--- src/Settings/Flavours/Development.hs | 1 - 3 files changed, 9 insertions(+), 8 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index a069c0e..ed6441c 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -5,7 +5,6 @@ module CommandLine ( ) where import Data.Either -import Data.Maybe import qualified Data.HashMap.Strict as Map import Data.List.Extra import Development.Shake hiding (Normal) @@ -127,9 +126,7 @@ cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs lookupFreeze1 :: Map.HashMap TypeRep Dynamic -> Bool -lookupFreeze1 m = fromMaybe (freeze1 defaultCommandLineArgs) (freeze1 <$> maybeValue) - where - maybeValue = fromDynamic =<< Map.lookup (typeOf defaultCommandLineArgs) m +lookupFreeze1 = freeze1 . lookupExtra defaultCommandLineArgs cmdInstallDestDir :: Action (Maybe String) cmdInstallDestDir = installDestDir <$> cmdLineArgs diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 06ee663..4d2ae48 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -10,7 +10,7 @@ module Hadrian.Utilities ( unifyPath, (-/-), -- * Accessing Shake's type-indexed map - insertExtra, userSetting, + insertExtra, lookupExtra, userSetting, -- * Paths BuildRoot (..), buildRoot, isGeneratedSource, @@ -153,13 +153,18 @@ cmdLineLengthLimit | isWindows = 31000 insertExtra :: Typeable a => a -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic insertExtra value = Map.insert (typeOf value) (toDyn value) +-- | Lookup a value in Shake's type-indexed map. +lookupExtra :: Typeable a => a -> Map.HashMap TypeRep Dynamic -> a +lookupExtra defaultValue extra = fromMaybe defaultValue maybeValue + where + maybeValue = fromDynamic =<< Map.lookup (typeOf defaultValue) extra + -- | Lookup a user setting in Shake's type-indexed map 'shakeExtra'. If the -- setting is not found, return the provided default value instead. userSetting :: Typeable a => a -> Action a userSetting defaultValue = do extra <- shakeExtra <$> getShakeOptions - let maybeValue = fromDynamic =<< Map.lookup (typeOf defaultValue) extra - return $ fromMaybe defaultValue maybeValue + return $ lookupExtra defaultValue extra newtype BuildRoot = BuildRoot FilePath deriving Typeable diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index a6a2892..713e409 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -4,7 +4,6 @@ import Flavour import Expression import {-# SOURCE #-} Settings.Default --- TODO: Implement an equivalent of LAX_DEPENDENCIES = YES setting, see #250. developmentFlavour :: Stage -> Flavour developmentFlavour ghcStage = defaultFlavour { name = "devel" ++ show (fromEnum ghcStage) From git at git.haskell.org Fri Oct 27 00:44:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Environment module for setting up environment variables. (f6cd23d) Message-ID: <20171027004410.178FF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f6cd23dc4b92bcedc230754f06b4c3f11438f6ae/ghc >--------------------------------------------------------------- commit f6cd23dc4b92bcedc230754f06b4c3f11438f6ae Author: Andrey Mokhov Date: Sun Jan 24 01:35:03 2016 +0000 Add Environment module for setting up environment variables. Fix #191. >--------------------------------------------------------------- f6cd23dc4b92bcedc230754f06b4c3f11438f6ae shaking-up-ghc.cabal | 1 + src/Environment.hs | 22 ++++++++++++++++++++++ src/Main.hs | 14 ++++++++------ src/Rules/Config.hs | 8 +------- 4 files changed, 32 insertions(+), 13 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index bd21d28..cdd512a 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -20,6 +20,7 @@ executable ghc-shake other-modules: Base , Builder , CmdLineFlag + , Environment , Expression , GHC , Oracles diff --git a/src/Environment.hs b/src/Environment.hs new file mode 100644 index 0000000..fd207ed --- /dev/null +++ b/src/Environment.hs @@ -0,0 +1,22 @@ +module Environment (setupEnvironment) where + +import Base +import System.Environment + +-- | The build system invokes many external builders whose behaviour is +-- influenced by the environment variables. We need to modify some of them +-- for better robustness of the build system. +setupEnvironment :: IO () +setupEnvironment = do + -- ghc-cabal refuses to work when GHC_PACKAGE_PATH is set (e.g. by Stack) + unsetEnv "GHC_PACKAGE_PATH" + + -- On Windows, some path variables start a prefix like "C:\\" which may + -- lead to failures of scripts such as autoreconf. One particular variable + -- which causes issues is ACLOCAL_PATH. At the moment we simply reset it + -- if it contains a problematic Windows path. + -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. + aclocal <- lookupEnv "ACLOCAL_PATH" + case aclocal of + Nothing -> return () + Just s -> when (":\\" `isPrefixOf` drop 1 s) $ unsetEnv "ACLOCAL_PATH" diff --git a/src/Main.hs b/src/Main.hs index 7321f88..69f739b 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -3,7 +3,8 @@ module Main (main) where import Development.Shake import qualified Base -import CmdLineFlag +import qualified CmdLineFlag +import qualified Environment import qualified Rules import qualified Rules.Cabal import qualified Rules.Clean @@ -16,8 +17,9 @@ import qualified Rules.Perl import qualified Test main :: IO () -main = shakeArgsWith options flags $ \cmdLineFlags targets -> do - putCmdLineFlags cmdLineFlags +main = shakeArgsWith options CmdLineFlag.flags $ \cmdLineFlags targets -> do + CmdLineFlag.putCmdLineFlags cmdLineFlags + Environment.setupEnvironment return . Just $ if null targets then rules else want targets >> withoutActions rules @@ -27,13 +29,13 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do [ Rules.Cabal.cabalRules , Rules.Clean.cleanRules , Rules.Config.configRules - , Rules.Generate.copyRules , Rules.Generate.generateRules - , Rules.Perl.perlScriptRules - , Rules.generateTargets + , Rules.Generate.copyRules , Rules.Gmp.gmpRules , Rules.Libffi.libffiRules , Rules.Oracles.oracleRules + , Rules.Perl.perlScriptRules + , Rules.generateTargets , Rules.packageRules , Test.testRules ] options = shakeOptions diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 77ac1ac..1297825 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -21,10 +21,4 @@ configRules = do -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. "configure" %> \_ -> do putBuild "| Running boot..." - aclocal <- getEnv "ACLOCAL_PATH" - let env = case aclocal of - Nothing -> [] - Just s -> if ":\\" `isPrefixOf` (drop 1 s) - then [AddEnv "ACLOCAL_PATH" ""] - else [] - quietly $ cmd (EchoStdout False) env "perl boot" + quietly $ cmd (EchoStdout False) "perl boot" From git at git.haskell.org Fri Oct 27 00:44:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename src/Settings/Paths.hs -> src/Settings/Path.hs (e31cb51) Message-ID: <20171027004413.886DB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e31cb5136a66213f8afb744c2b7c81344fc3975a/ghc >--------------------------------------------------------------- commit e31cb5136a66213f8afb744c2b7c81344fc3975a Author: Andrey Mokhov Date: Sun Oct 30 01:20:01 2016 +0000 Rename src/Settings/Paths.hs -> src/Settings/Path.hs >--------------------------------------------------------------- e31cb5136a66213f8afb744c2b7c81344fc3975a hadrian.cabal | 2 +- src/Main.hs | 4 ++-- src/Oracles/Dependencies.hs | 2 +- src/Oracles/ModuleFiles.hs | 2 +- src/Rules.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 2 +- src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Generators/ConfigHs.hs | 2 +- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 2 +- src/Rules/Test.hs | 2 +- src/Rules/Wrappers/GhcPkg.hs | 2 +- src/Settings.hs | 2 +- src/Settings/Builders/Common.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/{Paths.hs => Path.hs} | 2 +- 27 files changed, 29 insertions(+), 29 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e31cb5136a66213f8afb744c2b7c81344fc3975a From git at git.haskell.org Fri Oct 27 00:44:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up, build stage 1 GHC on AppVeyor. (73d8de1) Message-ID: <20171027004413.E16743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73d8de188efbf8c07d750416bfd74ef567ffacec/ghc >--------------------------------------------------------------- commit 73d8de188efbf8c07d750416bfd74ef567ffacec Author: Andrey Mokhov Date: Sun Jan 24 02:15:57 2016 +0000 Clean up, build stage 1 GHC on AppVeyor. >--------------------------------------------------------------- 73d8de188efbf8c07d750416bfd74ef567ffacec .appveyor.yml | 2 +- src/GHC.hs | 4 ++-- src/Package.hs | 14 ++++++++++++-- src/Rules.hs | 3 +-- src/Rules/Config.hs | 2 -- src/Rules/Libffi.hs | 2 +- src/Stage.hs | 23 +++++++++++------------ src/Target.hs | 2 +- src/Test.hs | 7 +++---- 9 files changed, 32 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 73d8de188efbf8c07d750416bfd74ef567ffacec From git at git.haskell.org Fri Oct 27 00:44:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Document the --freeze1 flag (7c507e1) Message-ID: <20171027004414.0371F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c507e1c6e0bdc622b033d75f3d5c75790e751b0/ghc >--------------------------------------------------------------- commit 7c507e1c6e0bdc622b033d75f3d5c75790e751b0 Author: Andrey Mokhov Date: Tue Oct 10 14:02:17 2017 +0100 Document the --freeze1 flag See #250 >--------------------------------------------------------------- 7c507e1c6e0bdc622b033d75f3d5c75790e751b0 README.md | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index ad61ef3..9eb759e 100644 --- a/README.md +++ b/README.md @@ -58,6 +58,12 @@ currently supports several others: `vanilla` way, which speeds up builds by 3-4x. Build flavours are documented [here](https://github.com/snowleopard/hadrian/blob/master/doc/flavours.md). +* `--freeze1`: freeze Stage1 GHC, i.e. do not rebuild it even if some of its source files +are out-of-date. This allows to significantly reduce the rebuild time when you are working +on a feature that affects both Stage1 and Stage2 compilers, but may lead to incorrect +build results. To unfreeze Stage1 GHC simply drop the `--freeze1` flag and Hadrian will +rebuild all out-of-date files. + * `--haddock`: build Haddock documentation. * `--integer-simple`: build GHC using the `integer-simple` integer library (instead @@ -136,7 +142,6 @@ The new build system still lacks many important features: * Validation is not implemented: [#187][validation-issue]. * Dynamic linking on Windows is not supported [#343][dynamic-windows-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). -* Not all modes of the old build system are supported, e.g. [#250][freeze-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. * There is no support for binary distribution: [#219][install-issue]. @@ -180,7 +185,6 @@ enjoy the project. [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 [dynamic-windows-issue]: https://github.com/snowleopard/hadrian/issues/343 -[freeze-issue]: https://github.com/snowleopard/hadrian/issues/250 [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 [milestones]: https://github.com/snowleopard/hadrian/milestones From git at git.haskell.org Fri Oct 27 00:44:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename src/Rules/Actions.hs -> src/Util.hs (fb30a88) Message-ID: <20171027004417.5BFF03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fb30a88d4b90d9bbac63d45fd9d92223a7947947/ghc >--------------------------------------------------------------- commit fb30a88d4b90d9bbac63d45fd9d92223a7947947 Author: Andrey Mokhov Date: Sun Oct 30 01:29:51 2016 +0000 Rename src/Rules/Actions.hs -> src/Util.hs >--------------------------------------------------------------- fb30a88d4b90d9bbac63d45fd9d92223a7947947 hadrian.cabal | 2 +- src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Configure.hs | 2 +- src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Perl.hs | 2 +- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/{Rules/Actions.hs => Util.hs} | 2 +- 18 files changed, 18 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fb30a88d4b90d9bbac63d45fd9d92223a7947947 From git at git.haskell.org Fri Oct 27 00:44:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't print boot's diagnostic info by default (dffda59) Message-ID: <20171027004417.A8D373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dffda59ac338bef1ab53e9ed4299ead89bbbeff7/ghc >--------------------------------------------------------------- commit dffda59ac338bef1ab53e9ed4299ead89bbbeff7 Author: Andrey Mokhov Date: Tue Oct 10 15:18:15 2017 +0100 Don't print boot's diagnostic info by default >--------------------------------------------------------------- dffda59ac338bef1ab53e9ed4299ead89bbbeff7 src/Rules/Configure.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index a4ef084..dd016c1 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -38,4 +38,5 @@ configureRules = do else do need ["configure.ac"] putBuild "| Running boot..." - quietly $ cmd "python3 boot" + verbosity <- getVerbosity + quietly $ cmd [EchoStdout (verbosity >= Loud)] "python3 boot" From git at git.haskell.org Fri Oct 27 00:44:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Register the access to the package database when compiling with GHC (03ebefd) Message-ID: <20171027004421.2D4ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03ebefdfaf33592d86105ad63de960adb9143d11/ghc >--------------------------------------------------------------- commit 03ebefdfaf33592d86105ad63de960adb9143d11 Author: Andrey Mokhov Date: Tue Oct 10 15:38:30 2017 +0100 Register the access to the package database when compiling with GHC >--------------------------------------------------------------- 03ebefdfaf33592d86105ad63de960adb9143d11 src/Rules/Compile.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index c71079a..a4b1278 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -17,7 +17,7 @@ compilePackage rs context at Context {..} = do src <- obj2src context obj need [src] needDependencies context src $ obj <.> "d" - build $ target context (compiler stage) [src] [obj] + buildWithResources rs $ target context (compiler stage) [src] [obj] compileHs = \[obj, _hi] -> do path <- buildPath context (src, deps) <- lookupDependencies (path -/- ".dependencies") obj From git at git.haskell.org Fri Oct 27 00:44:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make .cabal meta-data more accurate (f9e5109) Message-ID: <20171027004417.C36863A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f9e510913956bc01201ad74bab60767794424034/ghc >--------------------------------------------------------------- commit f9e510913956bc01201ad74bab60767794424034 Author: Herbert Valerio Riedel Date: Sun Jan 24 10:07:01 2016 +0100 Make .cabal meta-data more accurate We need this so cabal (this is even more important with the upcoming nix-style cabal features) can do a proper job so this is a pre-requisite for the new build-system being used by default for GHC anyway, as we need to be as accurate as possible with the build specification to give `git bisect` a chance of remaining usable. >--------------------------------------------------------------- f9e510913956bc01201ad74bab60767794424034 shaking-up-ghc.cabal | 32 +++++++++++++++----------------- 1 file changed, 15 insertions(+), 17 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index cdd512a..674d6f0 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -107,26 +107,24 @@ executable ghc-shake , Test , Way - default-extensions: BangPatterns - , LambdaCase - , MultiWayIf - , TupleSections + default-language: Haskell2010 other-extensions: DeriveDataTypeable , DeriveGeneric , FlexibleInstances + , GeneralizedNewtypeDeriving + , LambdaCase , OverloadedStrings , RecordWildCards , ScopedTypeVariables - build-depends: base - , ansi-terminal >= 0.6 - , Cabal >= 1.22 - , containers >= 0.5 - , directory >= 1.2 - , extra >= 1.4 - , mtl >= 2.2 - , QuickCheck >= 2.6 - , shake >= 0.15 - , transformers >= 0.4 - , unordered-containers >= 0.2 - default-language: Haskell2010 - ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 -j + build-depends: base >= 4.8 && < 5 + , ansi-terminal == 0.6.* + , Cabal == 1.22.* + , containers == 0.5.* + , directory == 1.2.* + , extra == 1.4.* + , mtl == 2.2.* + , QuickCheck >= 2.6 && < 2.9 + , shake == 0.15.* + , transformers >= 0.4 && < 0.6 + , unordered-containers == 0.2.* + ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 From git at git.haskell.org Fri Oct 27 00:44:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify defaultPackages definition (75281f2) Message-ID: <20171027004421.5B8E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/75281f2899cc8e3a890dc1af25a06cd81afb6c1e/ghc >--------------------------------------------------------------- commit 75281f2899cc8e3a890dc1af25a06cd81afb6c1e Author: Andrey Mokhov Date: Sun Oct 30 02:18:53 2016 +0000 Simplify defaultPackages definition >--------------------------------------------------------------- 75281f2899cc8e3a890dc1af25a06cd81afb6c1e src/Settings/Default.hs | 96 ++++++++++++++++++++++++++++++++++++------------- 1 file changed, 71 insertions(+), 25 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index f7ef62e..9f61ff7 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -90,42 +90,88 @@ defaultArgs = mconcat , defaultPackageArgs , builder Ghc ? remove ["-Wall", "-fwarn-tabs"] ] -- TODO: Fix warning Args. --- TODO: Simplify. -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". defaultPackages :: Packages -defaultPackages = mconcat - [ stage0 ? packagesStage0 - , stage1 ? packagesStage1 - , stage2 ? packagesStage2 ] +defaultPackages = mconcat [ packagesStage0, packagesStage1, packagesStage2 ] packagesStage0 :: Packages -packagesStage0 = mconcat - [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcBootTh, ghcCabal - , ghcPkg, hsc2hs, hoopl, hpc, templateHaskell, transformers ] - -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode - , hp2ps, unlit, mkUserGuidePart ] - , stage0 ? windowsHost ? append [touchy] - , notM windowsHost ? notM iosHost ? append [terminfo] ] +packagesStage0 = stage0 ? do + win <- lift windowsHost + ios <- lift iosHost + append $ [ binary + , cabal + , compiler + , deriveConstants + , dllSplit + , genapply + , genprimopcode + , ghc + , ghcBoot + , ghcBootTh + , ghcCabal + , ghcPkg + , hsc2hs + , hoopl + , hp2ps + , hpc + , mkUserGuidePart + , templateHaskell + , transformers + , unlit ] ++ + [ terminfo | not win, not ios ] ++ + [ touchy | win ] packagesStage1 :: Packages -packagesStage1 = mconcat - [ packagesStage0 - , append [ array, base, bytestring, containers, compareSizes, deepseq - , directory, filepath, ghci, ghcPrim, haskeline, hpcBin - , integerLibrary, pretty, process, rts, runGhc, time ] - , windowsHost ? append [win32] - , notM windowsHost ? append [unix] - , notM windowsHost ? append [iservBin] - , buildHaddock flavour ? append [xhtml] ] +packagesStage1 = stage1 ? do + win <- lift windowsHost + ios <- lift iosHost + doc <- buildHaddock flavour + append $ [ array + , base + , binary + , bytestring + , cabal + , containers + , compareSizes + , compiler + , deepseq + , directory + , filepath + , ghc + , ghcBoot + , ghcBootTh + , ghcCabal + , ghci + , ghcPkg + , ghcPrim + , haskeline + , hoopl + , hpc + , hpcBin + , hsc2hs + , integerLibrary + , pretty + , process + , rts + , runGhc + , templateHaskell + , time + , transformers ] ++ + [ iservBin | not win ] ++ + [ terminfo | not win, not ios ] ++ + [ unix | not win ] ++ + [ win32 | win ] ++ + [ xhtml | doc ] -- TODO: Currently there is an unchecked assumption that we build only programs -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages -packagesStage2 = mconcat - [ append [checkApiAnnotations, ghcTags ] - , buildHaddock flavour ? append [haddock] ] +packagesStage2 = stage2 ? do + doc <- buildHaddock flavour + append $ [ checkApiAnnotations + , ghcTags ] ++ + [ haddock | doc ] -- TODO: What about profilingDynamic way? Do we need platformSupportsSharedLibs? -- | Default build ways for library packages: From git at git.haskell.org Fri Oct 27 00:44:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add `cabal new-build` based wrapper script (6432f0c) Message-ID: <20171027004421.C766A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6432f0c241ea173bd5d7f7de4833085d6155c47f/ghc >--------------------------------------------------------------- commit 6432f0c241ea173bd5d7f7de4833085d6155c47f Author: Herbert Valerio Riedel Date: Sun Jan 24 10:43:43 2016 +0100 Add `cabal new-build` based wrapper script This makes use of the new nix-store cache for the shake library and other pre-requisities, rather than using the reinstall-breakage-prone old-style global pkg-db >--------------------------------------------------------------- 6432f0c241ea173bd5d7f7de4833085d6155c47f .gitignore | 17 ++++++++++++----- build.sh => build.cabal-new.sh | 28 +++++++++++++++++++--------- 2 files changed, 31 insertions(+), 14 deletions(-) diff --git a/.gitignore b/.gitignore index 6cc5501..967be07 100644 --- a/.gitignore +++ b/.gitignore @@ -1,7 +1,14 @@ -.shake/ -.db/ +/.shake/ +/.db/ cfg/system.config + +# build.cabal.sh specific +/dist/ +/.cabal-sandbox/ cabal.sandbox.config -dist/ -.cabal-sandbox/ -.stack-work/ + +# build.cabal-new.sh specific +/dist-newstyle/ + +# build.stack.sh specific +/.stack-work/ diff --git a/build.sh b/build.cabal-new.sh similarity index 60% copy from build.sh copy to build.cabal-new.sh index 719e85e..96c194e 100755 --- a/build.sh +++ b/build.cabal-new.sh @@ -1,5 +1,8 @@ #!/usr/bin/env bash +# This wrapper scripts makes use of cabal 1.24+'s nix-store; +# In order to clean/reset, remove the `dist-newstyle/` folder + set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -32,15 +35,22 @@ root="$(dirname "$(rl "$0")")" mkdir -p "$root/.shake" -ghc \ - "$root/src/Main.hs" \ - -Wall \ - -i"$root/src" \ - -rtsopts \ - -with-rtsopts=-I0 \ - -outputdir="$root/.shake" \ - -j -O \ - -o "$root/.shake/build" +# Notes/Random thoughts: +# +# - if ghc.git had a top-level `cabal.project` file, we could maybe avoid the +# boilerplate above, as we could simply say `cabal exec ghc-shake` from within +# any GHC folder not shadowed by a nearer shadowing `cabal.project` file. + +pushd "$root/" + +cabal new-build --disable-profiling --disable-documentation -j exe:ghc-shake + +PKGVER="$(awk '/^version:/ { print $2 }' shaking-up-ghc.cabal)" + +cp -v "$root/dist-newstyle/build/shaking-up-ghc-${PKGVER}/build/ghc-shake/ghc-shake" \ + "$root/.shake/build" + +popd "$root/.shake/build" \ --lint \ From git at git.haskell.org Fri Oct 27 00:44:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix usage of -with-rtsopts (#429) (e4f9829) Message-ID: <20171027004424.BA4713A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4f982978c82a274d7befec8be19b3bd2d238c5d/ghc >--------------------------------------------------------------- commit e4f982978c82a274d7befec8be19b3bd2d238c5d Author: Ben Gamari Date: Tue Oct 10 18:43:37 2017 -0400 Fix usage of -with-rtsopts (#429) When I added `-qg` to the default RTS options in 57cfa03c23047bb0c731428e97ca716d9a1cf312 (#385) I neglected to consider that it the -with-rtsopts flag would override the previous flag setting `-I0`. This had the effect of reenabling idle GC, causing GC time to regress terribly. I likely didn't notice this since I had passed the flags directly to the `hadrian` executable with `+RTS` while testing. Moreover, I mistakenly wrote `-qg0`, which (somewhat confusingly) actually *enables* parallel GC. Instead I wanted to write `-qg`. >--------------------------------------------------------------- e4f982978c82a274d7befec8be19b3bd2d238c5d hadrian.cabal | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 48514e1..8e583c7 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -133,10 +133,9 @@ executable hadrian -Wredundant-constraints -fno-warn-name-shadowing -rtsopts - -- Disable idle GC to avoid redundant GCs while waiting - -- for external processes - -with-rtsopts=-I0 - -- Don't use parallel GC as the synchronization time tends to eat any - -- benefit. - -with-rtsopts=-qg0 + -- * -I0: Disable idle GC to avoid redundant GCs while + -- waiting for external processes + -- * -qg: Don't use parallel GC as the synchronization + -- time tends to eat any benefit. + "-with-rtsopts=-I0 -qg" -threaded From git at git.haskell.org Fri Oct 27 00:44:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (223d161) Message-ID: <20171027004425.3AB9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/223d16102070b2d1061197ebb111ca3c9d2ffd45/ghc >--------------------------------------------------------------- commit 223d16102070b2d1061197ebb111ca3c9d2ffd45 Author: Andrey Mokhov Date: Sun Oct 30 13:28:09 2016 +0000 Minor revision >--------------------------------------------------------------- 223d16102070b2d1061197ebb111ca3c9d2ffd45 src/Settings/Default.hs | 163 +++++++++++++++++++++++------------------------- 1 file changed, 77 insertions(+), 86 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 9f61ff7..b59ceeb 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -43,46 +43,6 @@ import Settings.Packages.Touchy import Settings.Packages.Unlit import UserSettings --- | All 'Builder'-dependent command line arguments. -defaultBuilderArgs :: Args -defaultBuilderArgs = mconcat - [ alexBuilderArgs - , arBuilderArgs - , ccBuilderArgs - , configureBuilderArgs - , deriveConstantsBuilderArgs - , genPrimopCodeBuilderArgs - , ghcBuilderArgs - , ghcCabalBuilderArgs - , ghcCabalHsColourBuilderArgs - , ghcMBuilderArgs - , ghcPkgBuilderArgs - , haddockBuilderArgs - , happyBuilderArgs - , hsc2hsBuilderArgs - , hsCppBuilderArgs - , ldBuilderArgs - , makeBuilderArgs - , tarBuilderArgs ] - --- | All 'Package'-dependent command line arguments. -defaultPackageArgs :: Args -defaultPackageArgs = mconcat - [ basePackageArgs - , compilerPackageArgs - , directoryPackageArgs - , ghcPackageArgs - , ghcCabalPackageArgs - , ghcPrimPackageArgs - , haddockPackageArgs - , hp2psPackageArgs - , integerGmpPackageArgs - , iservBinPackageArgs - , rtsPackageArgs - , runGhcPackageArgs - , touchyPackageArgs - , unlitPackageArgs ] - -- | All default command line arguments. defaultArgs :: Args defaultArgs = mconcat @@ -93,10 +53,12 @@ defaultArgs = mconcat -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". defaultPackages :: Packages -defaultPackages = mconcat [ packagesStage0, packagesStage1, packagesStage2 ] +defaultPackages = mconcat [ stage0 ? stage0Packages + , stage1 ? stage1Packages + , stage2 ? stage2Packages ] -packagesStage0 :: Packages -packagesStage0 = stage0 ? do +stage0Packages :: Packages +stage0Packages = do win <- lift windowsHost ios <- lift iosHost append $ [ binary @@ -122,52 +84,41 @@ packagesStage0 = stage0 ? do [ terminfo | not win, not ios ] ++ [ touchy | win ] -packagesStage1 :: Packages -packagesStage1 = stage1 ? do +stage1Packages :: Packages +stage1Packages = do win <- lift windowsHost - ios <- lift iosHost doc <- buildHaddock flavour - append $ [ array - , base - , binary - , bytestring - , cabal - , containers - , compareSizes - , compiler - , deepseq - , directory - , filepath - , ghc - , ghcBoot - , ghcBootTh - , ghcCabal - , ghci - , ghcPkg - , ghcPrim - , haskeline - , hoopl - , hpc - , hpcBin - , hsc2hs - , integerLibrary - , pretty - , process - , rts - , runGhc - , templateHaskell - , time - , transformers ] ++ - [ iservBin | not win ] ++ - [ terminfo | not win, not ios ] ++ - [ unix | not win ] ++ - [ win32 | win ] ++ - [ xhtml | doc ] + mconcat [ stage0Packages + , apply (filter isLibrary) -- Build all Stage0 libraries in Stage1 + , append $ [ array + , base + , bytestring + , containers + , compareSizes + , deepseq + , directory + , filepath + , ghc + , ghcCabal + , ghci + , ghcPkg + , ghcPrim + , haskeline + , hpcBin + , hsc2hs + , integerLibrary + , pretty + , process + , rts + , runGhc + , time ] ++ + [ iservBin | not win ] ++ + [ unix | not win ] ++ + [ win32 | win ] ++ + [ xhtml | doc ] ] --- TODO: Currently there is an unchecked assumption that we build only programs --- in Stage2 and Stage3. Can we check this in compile time? -packagesStage2 :: Packages -packagesStage2 = stage2 ? do +stage2Packages :: Packages +stage2Packages = do doc <- buildHaddock flavour append $ [ checkApiAnnotations , ghcTags ] ++ @@ -220,3 +171,43 @@ defaultSplitObjects = do supported <- lift supportsSplitObjects let goodPackage = isLibrary pkg && pkg /= compiler && pkg /= rts return $ cmdSplitObjects && goodStage && goodPackage && supported + +-- | All 'Builder'-dependent command line arguments. +defaultBuilderArgs :: Args +defaultBuilderArgs = mconcat + [ alexBuilderArgs + , arBuilderArgs + , ccBuilderArgs + , configureBuilderArgs + , deriveConstantsBuilderArgs + , genPrimopCodeBuilderArgs + , ghcBuilderArgs + , ghcCabalBuilderArgs + , ghcCabalHsColourBuilderArgs + , ghcMBuilderArgs + , ghcPkgBuilderArgs + , haddockBuilderArgs + , happyBuilderArgs + , hsc2hsBuilderArgs + , hsCppBuilderArgs + , ldBuilderArgs + , makeBuilderArgs + , tarBuilderArgs ] + +-- | All 'Package'-dependent command line arguments. +defaultPackageArgs :: Args +defaultPackageArgs = mconcat + [ basePackageArgs + , compilerPackageArgs + , directoryPackageArgs + , ghcPackageArgs + , ghcCabalPackageArgs + , ghcPrimPackageArgs + , haddockPackageArgs + , hp2psPackageArgs + , integerGmpPackageArgs + , iservBinPackageArgs + , rtsPackageArgs + , runGhcPackageArgs + , touchyPackageArgs + , unlitPackageArgs ] From git at git.haskell.org Fri Oct 27 00:44:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make Brief the default setting of the --progress-info flag (10b8358) Message-ID: <20171027004428.3679C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/10b8358882867ebfef0a48b9ba28d08fcf37eedb/ghc >--------------------------------------------------------------- commit 10b8358882867ebfef0a48b9ba28d08fcf37eedb Author: Andrey Mokhov Date: Wed Oct 11 00:03:56 2017 +0100 Make Brief the default setting of the --progress-info flag See #428 >--------------------------------------------------------------- 10b8358882867ebfef0a48b9ba28d08fcf37eedb .travis.yml | 6 +++--- README.md | 4 ++-- appveyor.yml | 2 +- circle.yml | 2 +- src/CommandLine.hs | 2 +- src/Hadrian/Utilities.hs | 2 +- 6 files changed, 9 insertions(+), 9 deletions(-) diff --git a/.travis.yml b/.travis.yml index 203ee82..e14f962 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - ./build.cabal.sh selftest # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- - os: linux env: MODE="--flavour=quickest --integer-simple" @@ -40,7 +40,7 @@ matrix: script: # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. @@ -56,7 +56,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- install: # Add Cabal to PATH diff --git a/README.md b/README.md index 9eb759e..2530714 100644 --- a/README.md +++ b/README.md @@ -75,8 +75,8 @@ whether the console supports colours; this is the default setting), and `always` colours). * `--progress-info=STYLE`: choose how build progress info is printed. There are four -settings: `none`, `brief` (one line per build command), `normal` (typically a box per -build command; this is the default setting), and `unicorn` (when `normal` just won't do). +settings: `none`, `brief` (one line per build command; this is the default setting), +`normal` (typically a box per build command), and `unicorn` (when `normal` just won't do). * `--skip-configure`: use this flag to suppress the default behaviour of Hadrian that runs the `boot` and `configure` scripts automatically if need be, so that you don't have diff --git a/appveyor.yml b/appveyor.yml index c51983a..2f4653a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -33,7 +33,7 @@ build_script: - stack exec hadrian -- --directory ".." selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-info=brief --progress-colour=never --profile=- + - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. diff --git a/circle.yml b/circle.yml index 93cf47f..48653e8 100644 --- a/circle.yml +++ b/circle.yml @@ -33,7 +33,7 @@ compile: - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- test: override: diff --git a/src/CommandLine.hs b/src/CommandLine.hs index ed6441c..978a420 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -34,7 +34,7 @@ defaultCommandLineArgs = CommandLineArgs , installDestDir = Nothing , integerSimple = False , progressColour = Auto - , progressInfo = Normal + , progressInfo = Brief , skipConfigure = False , splitObjects = False } diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 4d2ae48..1cd22b1 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -313,7 +313,7 @@ putProgressInfo msg = do -- | Render an action. renderAction :: String -> FilePath -> FilePath -> Action String renderAction what input output = do - progressInfo <- userSetting Normal + progressInfo <- userSetting Brief return $ case progressInfo of None -> "" Brief -> "| " ++ what ++ ": " ++ i ++ " => " ++ o From git at git.haskell.org Fri Oct 27 00:44:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #192 from hvr/pr/fix-cabal-metadata (45e208e) Message-ID: <20171027004429.6D85A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45e208eda37617737650d02ad7a6427e4618e1bf/ghc >--------------------------------------------------------------- commit 45e208eda37617737650d02ad7a6427e4618e1bf Merge: 21eef1e f9e5109 Author: Andrey Mokhov Date: Sun Jan 24 13:48:25 2016 +0000 Merge pull request #192 from hvr/pr/fix-cabal-metadata Make .cabal meta-data more accurate [skip ci] >--------------------------------------------------------------- 45e208eda37617737650d02ad7a6427e4618e1bf shaking-up-ghc.cabal | 32 +++++++++++++++----------------- 1 file changed, 15 insertions(+), 17 deletions(-) From git at git.haskell.org Fri Oct 27 00:44:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Temporarily disable ChangeModtimeAndDigest (test AppVeyor speed up). (21eef1e) Message-ID: <20171027004425.86F013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21eef1e36c8592c04724fa59a61f0826fd2b94cd/ghc >--------------------------------------------------------------- commit 21eef1e36c8592c04724fa59a61f0826fd2b94cd Author: Andrey Mokhov Date: Sun Jan 24 13:06:56 2016 +0000 Temporarily disable ChangeModtimeAndDigest (test AppVeyor speed up). [skip ci] >--------------------------------------------------------------- 21eef1e36c8592c04724fa59a61f0826fd2b94cd src/Main.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 69f739b..0f0d450 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -39,7 +39,6 @@ main = shakeArgsWith options CmdLineFlag.flags $ \cmdLineFlags targets -> do , Rules.packageRules , Test.testRules ] options = shakeOptions - { shakeChange = ChangeModtimeAndDigest - , shakeFiles = Base.shakeFilesPath + { shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:44:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run selftest in GHC tree (f808265) Message-ID: <20171027004432.E41453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f808265388e8356810b450acf72531475b18d340/ghc >--------------------------------------------------------------- commit f808265388e8356810b450acf72531475b18d340 Author: Andrey Mokhov Date: Sun Oct 30 17:46:37 2016 +0000 Run selftest in GHC tree >--------------------------------------------------------------- f808265388e8356810b450acf72531475b18d340 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 7687500..b80008c 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -29,7 +29,7 @@ build_script: - stack build # Run internal Hadrian tests - - stack exec hadrian -- selftest + - stack exec hadrian -- --directory ".." selftest # Build GHC - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- From git at git.haskell.org Fri Oct 27 00:44:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #193 from hvr/pr/cabal-nix (e2271ac) Message-ID: <20171027004433.1A1373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2271ac0a67bec50c9fd45bef036e98e19e83d21/ghc >--------------------------------------------------------------- commit e2271ac0a67bec50c9fd45bef036e98e19e83d21 Merge: 45e208e 6432f0c Author: Andrey Mokhov Date: Sun Jan 24 13:49:25 2016 +0000 Merge pull request #193 from hvr/pr/cabal-nix Add `cabal new-build`-based wrapper script [skip ci] >--------------------------------------------------------------- e2271ac0a67bec50c9fd45bef036e98e19e83d21 .gitignore | 17 ++++++++++++----- build.sh => build.cabal-new.sh | 28 +++++++++++++++++++--------- 2 files changed, 31 insertions(+), 14 deletions(-) From git at git.haskell.org Fri Oct 27 00:44:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a selftest for Packages (e2871fc) Message-ID: <20171027004429.2AEE43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2871fc28f9f8de741326bdc9b7ad48aa1936393/ghc >--------------------------------------------------------------- commit e2871fc28f9f8de741326bdc9b7ad48aa1936393 Author: Andrey Mokhov Date: Sun Oct 30 17:26:46 2016 +0000 Add a selftest for Packages >--------------------------------------------------------------- e2871fc28f9f8de741326bdc9b7ad48aa1936393 src/Rules/Selftest.hs | 53 ++++++++++++++++++++++++++++++--------------------- 1 file changed, 31 insertions(+), 22 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index e7f5dbb..58de8fb 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,11 +6,11 @@ import Development.Shake import Test.QuickCheck import Base -import Builder +import Expression import Oracles.ModuleFiles +import Settings import Settings.Builders.Ar import UserSettings -import Way instance Arbitrary Way where arbitrary = wayFromUnits <$> arbitrary @@ -25,11 +25,12 @@ selftestRules :: Rules () selftestRules = "selftest" ~> do testBuilder - testWay testChunksOfSize + testLookupAll testMatchVersionedFilePath testModuleName - testLookupAll + testPackages + testWay testBuilder :: Action () testBuilder = do @@ -39,11 +40,6 @@ testBuilder = do trackedArgument (Make undefined) prefix == False && trackedArgument (Make undefined) ("-j" ++ show (n :: Int)) == False -testWay :: Action () -testWay = do - putBuild $ "==== Read Way, Show Way" - test $ \(x :: Way) -> read (show x) == x - testChunksOfSize :: Action () testChunksOfSize = do putBuild $ "==== chunksOfSize" @@ -53,6 +49,20 @@ testChunksOfSize = do let res = chunksOfSize n xs in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res +testLookupAll :: Action () +testLookupAll = do + putBuild $ "==== lookupAll" + test $ lookupAll ["b" , "c" ] [("a", 1), ("c", 3), ("d", 4)] + == [Nothing, Just (3 :: Int)] + test $ forAll dicts $ \dict -> forAll extras $ \extra -> + let items = sort $ map fst dict ++ extra + in lookupAll items (sort dict) == map (flip lookup dict) items + where + dicts :: Gen [(Int, Int)] + dicts = nubBy ((==) `on` fst) <$> vector 20 + extras :: Gen [Int] + extras = vector 20 + testMatchVersionedFilePath :: Action () testMatchVersionedFilePath = do putBuild $ "==== matchVersionedFilePath" @@ -82,16 +92,15 @@ testModuleName = do where names = intercalate "." <$> listOf1 (listOf1 $ elements "abcABC123_'") -testLookupAll :: Action () -testLookupAll = do - putBuild $ "==== lookupAll" - test $ lookupAll ["b" , "c" ] [("a", 1), ("c", 3), ("d", 4)] - == [Nothing, Just (3 :: Int)] - test $ forAll dicts $ \dict -> forAll extras $ \extra -> - let items = sort $ map fst dict ++ extra - in lookupAll items (sort dict) == map (flip lookup dict) items - where - dicts :: Gen [(Int, Int)] - dicts = nubBy ((==) `on` fst) <$> vector 20 - extras :: Gen [Int] - extras = vector 20 +testPackages :: Action () +testPackages = do + putBuild $ "==== Packages, interpretInContext" + forM_ [Stage0 ..] $ \stage -> do + pkgs <- stagePackages stage + test $ pkgs == nubOrd pkgs + +testWay :: Action () +testWay = do + putBuild $ "==== Read Way, Show Way" + test $ \(x :: Way) -> read (show x) == x + From git at git.haskell.org Fri Oct 27 00:44:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rearrange unix build scripts. (#430) (45da08b) Message-ID: <20171027004431.AD08E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45da08bb3c8b6806c0b3484e32abaeb4358cc6c1/ghc >--------------------------------------------------------------- commit 45da08bb3c8b6806c0b3484e32abaeb4358cc6c1 Author: Doug Wilson Date: Wed Oct 11 14:32:35 2017 +1300 Rearrange unix build scripts. (#430) Addresses Issue #428 >--------------------------------------------------------------- 45da08bb3c8b6806c0b3484e32abaeb4358cc6c1 .travis.yml | 8 ++--- build.cabal.sh => build.global-db.sh | 0 build.sh | 69 +++++++++++++++++++++--------------- build.stack.sh => build.stack.nix.sh | 8 +---- build.stack.sh | 2 +- circle.yml | 4 +-- stack.yaml | 1 + 7 files changed, 50 insertions(+), 42 deletions(-) diff --git a/.travis.yml b/.travis.yml index e14f962..e2455b2 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,10 +18,10 @@ matrix: script: # Run internal Hadrian tests - - ./build.cabal.sh selftest + - ./build.sh selftest # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - ./build.sh -j $MODE --no-progress --progress-colour=never --profile=- - os: linux env: MODE="--flavour=quickest --integer-simple" @@ -40,7 +40,7 @@ matrix: script: # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - ./build.sh -j $MODE --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. @@ -56,7 +56,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - ./build.sh -j $MODE --no-progress --progress-colour=never --profile=- install: # Add Cabal to PATH diff --git a/build.cabal.sh b/build.global-db.sh similarity index 100% rename from build.cabal.sh rename to build.global-db.sh diff --git a/build.sh b/build.sh index 0f957cf..2a0e8a7 100755 --- a/build.sh +++ b/build.sh @@ -1,5 +1,7 @@ #!/usr/bin/env bash +CABAL=cabal + set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -28,34 +30,45 @@ function rl { echo "$RESULT" } -root="$(dirname "$(rl "$0")")" +absoluteRoot="$(dirname "$(rl "$0")")" +cd "$absoluteRoot" -if type cabal > /dev/null 2>&1; then - CABVERSTR=$(cabal --numeric-version) - CABVER=( ${CABVERSTR//./ } ) - if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then - echo "** Cabal 1.24 or later detected. Please consider using the 'build.cabal.sh' script **" - echo "" - fi +if ! type "$CABAL" > /dev/null; then + echo "Please make sure 'cabal' is in your PATH" + exit 2 fi -mkdir -p "$root/bin" - -ghc \ - "$root/src/Main.hs" \ - -Wall \ - -fno-warn-name-shadowing \ - -XRecordWildCards \ - -i"$root/src" \ - -i"$root/../libraries/Cabal/Cabal" \ - -rtsopts \ - -with-rtsopts=-I0 \ - -threaded \ - -outputdir="$root/bin" \ - -j -O \ - -o "$root/bin/hadrian" - -"$root/bin/hadrian" \ - --lint \ - --directory "$root/.." \ - "$@" +CABVERSTR=$("$CABAL" --numeric-version) + +CABVER=( ${CABVERSTR//./ } ) + +if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then + # New enough cabal version detected, so + # let's use the superior 'cabal new-build' mode + + # there's no 'cabal new-run' yet, but it's easy to emulate + "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian + $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" + +else + # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals + echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." + + # Initialize sandbox if necessary + if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then + "$CABAL" sandbox init + "$CABAL" sandbox add-source ../libraries/Cabal/Cabal + "$CABAL" install \ + --dependencies-only \ + --disable-library-profiling \ + --disable-shared + fi + + "$CABAL" run hadrian -- \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" +fi diff --git a/build.stack.sh b/build.stack.nix.sh similarity index 82% copy from build.stack.sh copy to build.stack.nix.sh index 23f4833..59ac061 100755 --- a/build.stack.sh +++ b/build.stack.nix.sh @@ -29,11 +29,5 @@ function rl { } absoluteRoot="$(dirname "$(rl "$0")")" -cd "$absoluteRoot" -stack build --no-library-profiling - -stack exec hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" +HADRIAN_NIX=YES ${absoluteRoot}/build.stack.sh diff --git a/build.stack.sh b/build.stack.sh index 23f4833..2b1ff1d 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -31,7 +31,7 @@ function rl { absoluteRoot="$(dirname "$(rl "$0")")" cd "$absoluteRoot" -stack build --no-library-profiling +stack build --no-library-profiling ${HADRIAN_NIX:+--nix} stack exec hadrian -- \ --lint \ diff --git a/circle.yml b/circle.yml index 48653e8..a386d72 100644 --- a/circle.yml +++ b/circle.yml @@ -30,10 +30,10 @@ compile: # XXX: export PATH doesn't work well either, so we use inline env # Self test - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh -j $MODE --no-progress --progress-colour=never --profile=- test: override: diff --git a/stack.yaml b/stack.yaml index 2a92f26..da03763 100644 --- a/stack.yaml +++ b/stack.yaml @@ -12,6 +12,7 @@ extra-deps: - shake-0.16 nix: + enable: false packages: - autoconf - automake From git at git.haskell.org Fri Oct 27 00:44:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: build.cabal.sh: Use cabal new-run (#435) (6942b2d) Message-ID: <20171027004435.2A2093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6942b2dc08832f1521e2e8c46993c5ab977d2cb7/ghc >--------------------------------------------------------------- commit 6942b2dc08832f1521e2e8c46993c5ab977d2cb7 Author: Ben Gamari Date: Thu Oct 12 18:17:50 2017 -0400 build.cabal.sh: Use cabal new-run (#435) The previous approach was terribly unreliable, leading me to waste an hour debugging #425. >--------------------------------------------------------------- 6942b2dc08832f1521e2e8c46993c5ab977d2cb7 build.sh | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/build.sh b/build.sh index 2a0e8a7..5d1c2c2 100755 --- a/build.sh +++ b/build.sh @@ -46,9 +46,8 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th # New enough cabal version detected, so # let's use the superior 'cabal new-build' mode - # there's no 'cabal new-run' yet, but it's easy to emulate "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ + "$CABAL" new-run -- hadrian \ --lint \ --directory "$absoluteRoot/.." \ "$@" From git at git.haskell.org Fri Oct 27 00:44:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test conditions for building win32 and unix packages (63ba250) Message-ID: <20171027004436.9E6B73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/63ba25048c8c4ccf62f96704deb2ebfffefb2040/ghc >--------------------------------------------------------------- commit 63ba25048c8c4ccf62f96704deb2ebfffefb2040 Author: Andrey Mokhov Date: Sun Oct 30 17:58:54 2016 +0000 Test conditions for building win32 and unix packages See #197 >--------------------------------------------------------------- 63ba25048c8c4ccf62f96704deb2ebfffefb2040 src/Rules/Selftest.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 58de8fb..0a63641 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -7,6 +7,8 @@ import Test.QuickCheck import Base import Expression +import GHC +import Oracles.Config.Setting import Oracles.ModuleFiles import Settings import Settings.Builders.Ar @@ -94,9 +96,13 @@ testModuleName = do testPackages :: Action () testPackages = do - putBuild $ "==== Packages, interpretInContext" + putBuild $ "==== Check system configuration" + win <- windowsHost -- This depends on the @boot@ and @configure@ scripts. + putBuild $ "==== Packages, interpretInContext, configuration flags" forM_ [Stage0 ..] $ \stage -> do pkgs <- stagePackages stage + when (win32 `elem` pkgs) . test $ win + when (unix `elem` pkgs) . test $ not win test $ pkgs == nubOrd pkgs testWay :: Action () From git at git.haskell.org Fri Oct 27 00:44:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring ChangeModtimeAndDigest back. (dfabde8) Message-ID: <20171027004436.C5EBA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dfabde88d19471916a86c73a977d6f320f271978/ghc >--------------------------------------------------------------- commit dfabde88d19471916a86c73a977d6f320f271978 Author: Andrey Mokhov Date: Sun Jan 24 17:06:09 2016 +0000 Bring ChangeModtimeAndDigest back. [skip ci] >--------------------------------------------------------------- dfabde88d19471916a86c73a977d6f320f271978 src/Main.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index 0f0d450..69f739b 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -39,6 +39,7 @@ main = shakeArgsWith options CmdLineFlag.flags $ \cmdLineFlags targets -> do , Rules.packageRules , Test.testRules ] options = shakeOptions - { shakeFiles = Base.shakeFilesPath + { shakeChange = ChangeModtimeAndDigest + , shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:44:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix the list of Hadrian arguments (4b42da3) Message-ID: <20171027004438.942E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b42da3ca484718708b157889bd0780b3076f4b0/ghc >--------------------------------------------------------------- commit 4b42da3ca484718708b157889bd0780b3076f4b0 Author: Andrey Mokhov Date: Thu Oct 12 23:29:00 2017 +0100 Fix the list of Hadrian arguments See #435 >--------------------------------------------------------------- 4b42da3ca484718708b157889bd0780b3076f4b0 build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 5d1c2c2..6c2c038 100755 --- a/build.sh +++ b/build.sh @@ -47,7 +47,7 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th # let's use the superior 'cabal new-build' mode "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - "$CABAL" new-run -- hadrian \ + "$CABAL" new-run hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ "$@" From git at git.haskell.org Fri Oct 27 00:44:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify needTouchy, drop old comments (47a1e7d) Message-ID: <20171027004440.4C84D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47a1e7db3a6c815925389f1c7a7a69fd66ab1bea/ghc >--------------------------------------------------------------- commit 47a1e7db3a6c815925389f1c7a7a69fd66ab1bea Author: Andrey Mokhov Date: Sun Oct 30 23:33:07 2016 +0000 Simplify needTouchy, drop old comments >--------------------------------------------------------------- 47a1e7db3a6c815925389f1c7a7a69fd66ab1bea src/Settings/Builders/Ghc.hs | 97 ++------------------------------------------ 1 file changed, 3 insertions(+), 94 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 64fbacb..e12e35c 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -3,11 +3,6 @@ module Settings.Builders.Ghc (ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs) wh import Flavour import Settings.Builders.Common --- TODO: Add support for -dyno. --- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot --- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ --- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno --- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) ghcBuilderArgs :: Args ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do needTouchy @@ -38,15 +33,11 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] --- TODO: Add Touchy builder and use needBuilder. needTouchy :: ReaderT Target Action () -needTouchy = do - stage <- getStage - windows <- lift $ windowsHost - lift . when (stage > Stage0 && windows) $ - need [fromJust $ programPath (vanillaContext Stage0 touchy)] +needTouchy = notStage0 ? do + maybePath <- lift $ programPath (vanillaContext Stage0 touchy) + lift . whenJust maybePath $ \path -> need [path] --- TODO: Add GhcSplit builder and use needBuilder. splitObjectsArgs :: Args splitObjectsArgs = splitObjects flavour ? do lift $ need [ghcSplit] @@ -99,7 +90,6 @@ wayGhcArgs = do , (way == debug || way == debugDynamic) ? append ["-ticky", "-DTICKY_TICKY"] ] --- TODO: Improve handling of "-hide-all-packages". packageGhcArgs :: Args packageGhcArgs = do pkg <- getPackage @@ -131,84 +121,3 @@ includeGhcArgs = do , arg $ "-optc-I" ++ generatedPath , arg "-optP-include" , arg $ "-optP" ++ path -/- "autogen/cabal_macros.h" ] - --- # Options for passing to plain ld --- $1_$2_$3_ALL_LD_OPTS = \ --- $$(WAY_$3_LD_OPTS) \ --- $$($1_$2_DIST_LD_OPTS) \ --- $$($1_$2_$3_LD_OPTS) \ --- $$($1_$2_EXTRA_LD_OPTS) \ --- $$(EXTRA_LD_OPTS) - --- # Options for passing to GHC when we use it for linking --- $1_$2_$3_GHC_LD_OPTS = \ --- $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ --- $$($1_$2_$3_MOST_HC_OPTS) - --- TODO: add support for TargetElf and darwin --- ifeq "$3" "dyn" --- ifneq "$4" "0" --- ifeq "$$(TargetElf)" "YES" --- $1_$2_$3_GHC_LD_OPTS += \ --- -fno-use-rpaths \ --- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'$$$$ORIGIN/../$$d') -optl-Wl,-zorigin --- else ifeq "$$(TargetOS_CPP)" "darwin" --- $1_$2_$3_GHC_LD_OPTS += \ --- -fno-use-rpaths \ --- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') - --- ifeq "$$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS)" "" --- # We don't want to link the GHC RTS into C-only programs. There's no --- # point, and it confuses the test that all GHC-compiled programs --- # were compiled with the right GHC. --- $1_$2_$$($1_$2_PROGRAM_WAY)_GHC_LD_OPTS += -no-auto-link-packages -no-hs-main --- endif - --- # Link a dynamic library --- # On windows we have to supply the extra libs this one links to when building it. --- ifeq "$$(HostOS_CPP)" "mingw32" --- $$($1_$2_$3_LIB) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) --- ifneq "$$($1_$2_$3_LIB0)" "" --- $$(call build-dll,$1,$2,$3, --- -L$1/$2/build -l$$($1_$2_$3_LIB0_ROOT), --- $$(filter-out $$($1_$2_dll0_HS_OBJS),$$($1_$2_$3_HS_OBJS)) --- $$($1_$2_$3_NON_HS_OBJS),$$@) --- else --- $$(call build-dll,$1,$2,$3,,$$($1_$2_$3_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$@) --- endif - --- ifneq "$$($1_$2_$3_LIB0)" "" --- $$($1_$2_$3_LIB) : $$($1_$2_$3_LIB0) --- $$($1_$2_$3_LIB0) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) --- $$(call build-dll,$1,$2,$3,,$$($1_$2_dll0_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$($1_$2_$3_LIB0)) --- endif - - - --- # $1 = dir --- # $2 = distdir --- # $3 = way --- # $4 = extra flags --- # $5 = object files to link --- # $6 = output filename --- define build-dll --- $(call cmd,$1_$2_HC) $($1_$2_$3_ALL_HC_OPTS) $($1_$2_$3_GHC_LD_OPTS) $4 $5 \ --- -shared -dynamic -dynload deploy \ --- $(addprefix -l,$($1_$2_EXTRA_LIBRARIES)) \ --- -no-auto-link-packages \ --- -o $6 --- # Now check that the DLL doesn't have too many symbols. See trac #5987. --- SYMBOLS=`$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail -n +2 | wc -l`; echo "Number of symbols in $6: $$SYMBOLS" --- case `$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | grep "\[ *0\]" | wc -l` in 1) echo DLL $6 OK;; 0) echo No symbols in DLL $6; exit 1;; [0-9]*) echo Too many symbols in DLL $6; $(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail; exit 1;; *) echo bad DLL $6; exit 1;; esac --- endef - - - --- TODO: add -dynamic-too? --- # $1_$2_$3_ALL_HC_OPTS: this is all the options we will pass to GHC --- # for a given ($1,$2,$3). --- $1_$2_$3_ALL_HC_OPTS = \ --- -hisuf $$($3_hisuf) -osuf $$($3_osuf) -hcsuf $$($3_hcsuf) \ --- $$($1_$2_$3_MOST_DIR_HC_OPTS) \ --- $$(if $$(findstring YES,$$($1_$2_SplitObjs)),$$(if $$(findstring dyn,$3),,-split-objs),) \ --- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),$$(if $$(findstring v,$3),-dynamic-too)) From git at git.haskell.org Fri Oct 27 00:44:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build flavours, implement a simple quick flavour. (8738dd2) Message-ID: <20171027004440.57A3D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8738dd20c48b8728a353858e771a107a5ca883ad/ghc >--------------------------------------------------------------- commit 8738dd20c48b8728a353858e771a107a5ca883ad Author: Andrey Mokhov Date: Sun Jan 24 22:16:48 2016 +0000 Add build flavours, implement a simple quick flavour. See #188. >--------------------------------------------------------------- 8738dd20c48b8728a353858e771a107a5ca883ad .appveyor.yml | 2 +- src/CmdLineFlag.hs | 80 ++++++++++++++++++++++++++---------------- src/Expression.hs | 2 +- src/Main.hs | 2 +- src/Settings/Args.hs | 13 +++++-- src/Settings/Flavours/Quick.hs | 9 +++++ 6 files changed, 72 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 8738dd20c48b8728a353858e771a107a5ca883ad From git at git.haskell.org Fri Oct 27 00:44:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Restore the original build script relying on the global package database (2f88f30) Message-ID: <20171027004442.3788F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f88f30099934a46fb9ceceb4267924e3975ecaa/ghc >--------------------------------------------------------------- commit 2f88f30099934a46fb9ceceb4267924e3975ecaa Author: Andrey Mokhov Date: Sat Oct 14 23:44:49 2017 +0100 Restore the original build script relying on the global package database See #435, #430 >--------------------------------------------------------------- 2f88f30099934a46fb9ceceb4267924e3975ecaa build.global-db.sh | 66 ++++++++++++++++++------------------------------------ 1 file changed, 22 insertions(+), 44 deletions(-) diff --git a/build.global-db.sh b/build.global-db.sh index 2a0e8a7..5f1579b 100755 --- a/build.global-db.sh +++ b/build.global-db.sh @@ -1,7 +1,5 @@ #!/usr/bin/env bash -CABAL=cabal - set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -30,45 +28,25 @@ function rl { echo "$RESULT" } -absoluteRoot="$(dirname "$(rl "$0")")" -cd "$absoluteRoot" - -if ! type "$CABAL" > /dev/null; then - echo "Please make sure 'cabal' is in your PATH" - exit 2 -fi - -CABVERSTR=$("$CABAL" --numeric-version) - -CABVER=( ${CABVERSTR//./ } ) - -if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then - # New enough cabal version detected, so - # let's use the superior 'cabal new-build' mode - - # there's no 'cabal new-run' yet, but it's easy to emulate - "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" - -else - # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals - echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." - - # Initialize sandbox if necessary - if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then - "$CABAL" sandbox init - "$CABAL" sandbox add-source ../libraries/Cabal/Cabal - "$CABAL" install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared - fi - - "$CABAL" run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" -fi +root="$(dirname "$(rl "$0")")" + +mkdir -p "$root/bin" + +ghc \ + "$root/src/Main.hs" \ + -Wall \ + -fno-warn-name-shadowing \ + -XRecordWildCards \ + -i"$root/src" \ + -i"$root/../libraries/Cabal/Cabal" \ + -rtsopts \ + -with-rtsopts=-I0 \ + -threaded \ + -outputdir="$root/bin" \ + -j -O \ + -o "$root/bin/hadrian" + +"$root/bin/hadrian" \ + --lint \ + --directory "$root/.." \ + "$@" \ No newline at end of file From git at git.haskell.org Fri Oct 27 00:44:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't build ghcPkg in Stage1 (bf83d95) Message-ID: <20171027004443.D1D7E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf83d95c4770330e0b5ec582448ddc70ec9ebc92/ghc >--------------------------------------------------------------- commit bf83d95c4770330e0b5ec582448ddc70ec9ebc92 Author: Andrey Mokhov Date: Sun Oct 30 23:34:46 2016 +0000 Don't build ghcPkg in Stage1 >--------------------------------------------------------------- bf83d95c4770330e0b5ec582448ddc70ec9ebc92 src/Settings/Default.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index b59ceeb..c863a9e 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -101,7 +101,6 @@ stage1Packages = do , ghc , ghcCabal , ghci - , ghcPkg , ghcPrim , haskeline , hpcBin From git at git.haskell.org Fri Oct 27 00:44:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use `new-build` for pre-2.1 Cabal (65bcdcb) Message-ID: <20171027004445.9ECCD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65bcdcbe7dd61dace537fd956b5d5d40aed6d8c9/ghc >--------------------------------------------------------------- commit 65bcdcbe7dd61dace537fd956b5d5d40aed6d8c9 Author: Andrey Mokhov Date: Tue Oct 17 23:38:17 2017 +0100 Don't use `new-build` for pre-2.1 Cabal See #438 >--------------------------------------------------------------- 65bcdcbe7dd61dace537fd956b5d5d40aed6d8c9 build.sh | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/build.sh b/build.sh index 6c2c038..d2bdb85 100755 --- a/build.sh +++ b/build.sh @@ -42,9 +42,10 @@ CABVERSTR=$("$CABAL" --numeric-version) CABVER=( ${CABVERSTR//./ } ) -if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then - # New enough cabal version detected, so - # let's use the superior 'cabal new-build' mode +if [ "${CABVER[0]}" -gt 2 -o "${CABVER[0]}" -eq 2 -a "${CABVER[1]}" -ge 1 ]; then + # New enough Cabal version detected, so let's use the superior new-build + new-run + # modes. Note that pre-2.1 Cabal does not support passing additional parameters + # to the executable (hadrian) after the separator '--', see #438. "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian "$CABAL" new-run hadrian -- \ @@ -53,8 +54,8 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th "$@" else - # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals - echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." + # The logic below is quite fragile, but it's better than nothing for pre-2.1 Cabal. + echo "Old pre cabal 2.1 version detected. Falling back to legacy 'cabal sandbox' mode." # Initialize sandbox if necessary if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then From git at git.haskell.org Fri Oct 27 00:44:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor programPath (5d12adf) Message-ID: <20171027004447.E34C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d12adf142c16b5214fc01c8a1fab16c81544c89/ghc >--------------------------------------------------------------- commit 5d12adf142c16b5214fc01c8a1fab16c81544c89 Author: Andrey Mokhov Date: Sun Oct 30 23:37:10 2016 +0000 Refactor programPath >--------------------------------------------------------------- 5d12adf142c16b5214fc01c8a1fab16c81544c89 src/GHC.hs | 16 +++++++++-- src/Rules.hs | 8 +----- src/Rules/Generators/ConfigHs.hs | 1 - src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Program.hs | 37 +++++++++++++----------- src/Rules/Test.hs | 1 - src/Settings.hs | 42 ++++++++++++++++++++++----- src/Settings/Path.hs | 61 ++++++---------------------------------- src/Util.hs | 1 - 9 files changed, 79 insertions(+), 90 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 5d12adf142c16b5214fc01c8a1fab16c81544c89 From git at git.haskell.org Fri Oct 27 00:44:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a new command line flag: build flavour. (5286213) Message-ID: <20171027004447.ADB4A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/528621354633d9d1af4ae6ed7572c9b727a13460/ghc >--------------------------------------------------------------- commit 528621354633d9d1af4ae6ed7572c9b727a13460 Author: Andrey Mokhov Date: Mon Jan 25 00:19:39 2016 +0000 Add a new command line flag: build flavour. See #188. >--------------------------------------------------------------- 528621354633d9d1af4ae6ed7572c9b727a13460 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index b8fd40f..85b9cbe 100644 --- a/README.md +++ b/README.md @@ -55,6 +55,8 @@ currently supports several others: arguments; also run the `boot` script to create the `configure` script if necessary. You do not have to use this functionality of the new build system; feel free to run `boot` and `configure` scripts manually, as you do when using `make`. +* `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: +`default` and `quick` (adds `-O0` flag to all GHC invocations speeding up builds by 3x). * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). From git at git.haskell.org Fri Oct 27 00:44:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Rules.Data to Rules.PackageData (4df3e2d) Message-ID: <20171027004449.3E86B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4df3e2dc441a5d5b6ff61f75573ff4b9a74e562f/ghc >--------------------------------------------------------------- commit 4df3e2dc441a5d5b6ff61f75573ff4b9a74e562f Author: Andrey Mokhov Date: Wed Oct 18 00:44:28 2017 +0100 Rename Rules.Data to Rules.PackageData See #433 >--------------------------------------------------------------- 4df3e2dc441a5d5b6ff61f75573ff4b9a74e562f hadrian.cabal | 2 +- src/Rules.hs | 4 ++-- src/Rules/{Data.hs => PackageData.hs} | 2 +- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 8e583c7..54a0273 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -46,7 +46,7 @@ executable hadrian , Rules.Clean , Rules.Compile , Rules.Configure - , Rules.Data + , Rules.PackageData , Rules.Dependencies , Rules.Documentation , Rules.Generate diff --git a/src/Rules.hs b/src/Rules.hs index 730823f..97270a6 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -9,7 +9,7 @@ import Expression import Flavour import qualified Oracles.ModuleFiles import qualified Rules.Compile -import qualified Rules.Data +import qualified Rules.PackageData import qualified Rules.Dependencies import qualified Rules.Documentation import qualified Rules.Generate @@ -99,7 +99,7 @@ packageRules = do Rules.Program.buildProgram readPackageDb forM_ vanillaContexts $ mconcat - [ Rules.Data.buildPackageData + [ Rules.PackageData.buildPackageData , Rules.Dependencies.buildPackageDependencies readPackageDb , Rules.Documentation.buildPackageDocumentation , Rules.Library.buildPackageGhciLibrary diff --git a/src/Rules/Data.hs b/src/Rules/PackageData.hs similarity index 99% rename from src/Rules/Data.hs rename to src/Rules/PackageData.hs index c6d894b..2442b03 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/PackageData.hs @@ -1,4 +1,4 @@ -module Rules.Data (buildPackageData) where +module Rules.PackageData (buildPackageData) where import Base import Context From git at git.haskell.org Fri Oct 27 00:44:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't change extension of files found in PATH. (3787444) Message-ID: <20171027004451.C1F5B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37874441d3ff2255fea40d60420d4353245ed930/ghc >--------------------------------------------------------------- commit 37874441d3ff2255fea40d60420d4353245ed930 Author: Andrey Mokhov Date: Mon Jan 25 14:04:03 2016 +0000 Don't change extension of files found in PATH. See #194. >--------------------------------------------------------------- 37874441d3ff2255fea40d60420d4353245ed930 src/Builder.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 22723a5..bfb757f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -112,9 +112,9 @@ builderPath builder = case builderProvenance builder of ++ "' in configuration files. Have you forgot to run configure?" windows <- windowsHost case (path, windows) of - ("", _) -> return path - (p, True) -> fixAbsolutePathOnWindows (p -<.> exe) - (p, False) -> lookupInPath (p -<.> exe) + ("", _ ) -> return path + (p , True ) -> fixAbsolutePathOnWindows (p -<.> exe) + (p , False) -> lookupInPath p getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath From git at git.haskell.org Fri Oct 27 00:44:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move programInplacePath to Settings.Path (c5ba8b9) Message-ID: <20171027004451.D53973A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5ba8b94b6e04cf95392f8520ff649d2538530a2/ghc >--------------------------------------------------------------- commit c5ba8b94b6e04cf95392f8520ff649d2538530a2 Author: Andrey Mokhov Date: Sun Oct 30 23:45:21 2016 +0000 Move programInplacePath to Settings.Path >--------------------------------------------------------------- c5ba8b94b6e04cf95392f8520ff649d2538530a2 src/Base.hs | 6 +----- src/Settings/Path.hs | 8 ++++++-- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index cb040d4..eb8685d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -15,7 +15,7 @@ module Base ( module Development.Shake.FilePath, -- * Paths - configPath, configFile, sourcePath, programInplacePath, + configPath, configFile, sourcePath, -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, replaceSeparators, unifyPath, @@ -58,10 +58,6 @@ configFile = configPath -/- "system.config" sourcePath :: FilePath sourcePath = hadrianPath -/- "src" --- TODO: move to buildRootPath, see #113 -programInplacePath :: FilePath -programInplacePath = "inplace/bin" - -- | Find and replace all occurrences of a value in a list. replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceWhen (== from) diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 9993f9e..6b2e67d 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -3,7 +3,7 @@ module Settings.Path ( pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, - objectPath, programInplaceLibPath, installPath + objectPath, programInplacePath, programInplaceLibPath, installPath ) where import Base @@ -36,7 +36,11 @@ stageDirectory :: Stage -> FilePath stageDirectory = stageString -- TODO: Move to buildRootPath, see #113. --- | Directory for wrapped binaries. +-- | Directory for binaries that are built "in place". +programInplacePath :: FilePath +programInplacePath = "inplace/bin" + +-- | Directory for binary wrappers, and auxiliary binaries such as @touchy at . programInplaceLibPath :: FilePath programInplaceLibPath = "inplace/lib/bin" From git at git.haskell.org Fri Oct 27 00:44:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use quick flavour on Travis. (5ed8f3a) Message-ID: <20171027004443.BB3923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ed8f3a48e8e6c401302988547fc10f73c9340c7/ghc >--------------------------------------------------------------- commit 5ed8f3a48e8e6c401302988547fc10f73c9340c7 Author: Andrey Mokhov Date: Sun Jan 24 23:08:16 2016 +0000 Use quick flavour on Travis. See #188. >--------------------------------------------------------------- 5ed8f3a48e8e6c401302988547fc10f73c9340c7 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 1b96c78..84bb380 100644 --- a/.travis.yml +++ b/.travis.yml @@ -64,7 +64,7 @@ install: script: - ( cd ghc/shake-build && cabal haddock --internal ) - ./ghc/shake-build/build.sh selftest - - ./ghc/shake-build/build.sh -j --no-progress $TARGET + - ./ghc/shake-build/build.sh -j --no-progress --flavour=quick $TARGET cache: directories: From git at git.haskell.org Fri Oct 27 00:44:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix buildProgram (7b00fa7) Message-ID: <20171027004455.CC2A63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b00fa7081555a5753c90ba8b48d2579cc59be9c/ghc >--------------------------------------------------------------- commit 7b00fa7081555a5753c90ba8b48d2579cc59be9c Author: Andrey Mokhov Date: Sun Oct 30 23:57:13 2016 +0000 Fix buildProgram >--------------------------------------------------------------- 7b00fa7081555a5753c90ba8b48d2579cc59be9c src/Rules/Program.hs | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 98922a5..319ca72 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -29,15 +29,23 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do + let installStage = do + latest <- latestBuildStage package -- isJust below is safe + return $ if package == ghc then stage else fromJust latest + buildPath context -/- programName context <.> exe %> buildBinaryAndWrapper rs context -- Rules for programs built in install directories - when (stage == Stage0 || package == ghc) $ - installPath package -/- programName context <.> exe %> \bin -> do - latest <- latestBuildStage package -- isJust below is safe - let binStage = if package == ghc then stage else fromJust latest + when (stage == Stage0 || package == ghc) $ do + -- Some binaries in programInplacePath are wrapped + programInplacePath -/- programName context <.> exe %> \bin -> do + binStage <- installStage buildBinaryAndWrapper rs (context { stage = binStage }) bin + -- We build only unwrapped binaries in programInplaceLibPath + programInplaceLibPath -/- programName context <.> exe %> \bin -> do + binStage <- installStage + buildBinary rs (context { stage = binStage }) bin buildBinaryAndWrapper :: [(Resource, Int)] -> Context -> FilePath -> Action () buildBinaryAndWrapper rs context bin = do From git at git.haskell.org Fri Oct 27 00:44:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve the clean and rebuild section. (f6355ec) Message-ID: <20171027004455.89A093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f6355ecd2d3cd047a0b550636dc9cf3f2924f9b2/ghc >--------------------------------------------------------------- commit f6355ecd2d3cd047a0b550636dc9cf3f2924f9b2 Author: Andrey Mokhov Date: Mon Jan 25 15:06:32 2016 +0000 Improve the clean and rebuild section. See #194. [skip ci] >--------------------------------------------------------------- f6355ecd2d3cd047a0b550636dc9cf3f2924f9b2 README.md | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/README.md b/README.md index 85b9cbe..057b864 100644 --- a/README.md +++ b/README.md @@ -69,12 +69,11 @@ The `make`-based build system uses `mk/build.mk` to specify user build settings. use [`src/Settings/User.hs`][user-settings] for the same purpose. Feel free to experiment following the Haddock comments. -#### Resetting the build +#### Clean and full rebuild -To reset the new build system run the build script with `-B` flag. This forces Shake -to rerun all rules, even if results of the previous build are still in the GHC tree. -To remove all build artefacts, run the build script with `clean` target. Note, we are -working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `shake-build/build.sh clean` removes all build artefacts. Note, we are working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. + +* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. Current limitations ------------------- From git at git.haskell.org Fri Oct 27 00:44:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build.sh call the default build script (build.cabal.sh) (0aa31f9) Message-ID: <20171027004452.B214A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0aa31f9717e1ecb1a0b73a605a6695f8ee11e28a/ghc >--------------------------------------------------------------- commit 0aa31f9717e1ecb1a0b73a605a6695f8ee11e28a Author: Andrey Mokhov Date: Mon Oct 23 21:33:32 2017 +0100 Make build.sh call the default build script (build.cabal.sh) See #428. Also see #440: build.sh may later be relocated to the top of the GHC tree. >--------------------------------------------------------------- 0aa31f9717e1ecb1a0b73a605a6695f8ee11e28a build.sh => build.cabal.sh | 0 build.sh | 74 ++-------------------------------------------- 2 files changed, 2 insertions(+), 72 deletions(-) diff --git a/build.sh b/build.cabal.sh old mode 100755 new mode 100644 similarity index 100% copy from build.sh copy to build.cabal.sh diff --git a/build.sh b/build.sh index d2bdb85..460fdc1 100755 --- a/build.sh +++ b/build.sh @@ -1,74 +1,4 @@ #!/usr/bin/env bash -CABAL=cabal - -set -euo pipefail - -# readlink on os x, doesn't support -f, to prevent the -# need of installing coreutils (e.g. through brew, just -# for readlink, we use the follownig substitute. -# -# source: http://stackoverflow.com/a/1116890 -function rl { - TARGET_FILE="$1" - - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - - # Iterate down a (possible) chain of symlinks - while [ -L "$TARGET_FILE" ] - do - TARGET_FILE="$(readlink "$TARGET_FILE")" - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - done - - # Compute the canonicalized name by finding the physical path - # for the directory we're in and appending the target file. - PHYS_DIR="$(pwd -P)" - RESULT="$PHYS_DIR/$TARGET_FILE" - echo "$RESULT" -} - -absoluteRoot="$(dirname "$(rl "$0")")" -cd "$absoluteRoot" - -if ! type "$CABAL" > /dev/null; then - echo "Please make sure 'cabal' is in your PATH" - exit 2 -fi - -CABVERSTR=$("$CABAL" --numeric-version) - -CABVER=( ${CABVERSTR//./ } ) - -if [ "${CABVER[0]}" -gt 2 -o "${CABVER[0]}" -eq 2 -a "${CABVER[1]}" -ge 1 ]; then - # New enough Cabal version detected, so let's use the superior new-build + new-run - # modes. Note that pre-2.1 Cabal does not support passing additional parameters - # to the executable (hadrian) after the separator '--', see #438. - - "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - "$CABAL" new-run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" - -else - # The logic below is quite fragile, but it's better than nothing for pre-2.1 Cabal. - echo "Old pre cabal 2.1 version detected. Falling back to legacy 'cabal sandbox' mode." - - # Initialize sandbox if necessary - if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then - "$CABAL" sandbox init - "$CABAL" sandbox add-source ../libraries/Cabal/Cabal - "$CABAL" install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared - fi - - "$CABAL" run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" -fi +# By default on Linux/MacOS we build Hadrian using Cabal +./build.cabal.sh "$@" From git at git.haskell.org Fri Oct 27 00:44:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build.bat call the default build script on Windows (build.stack.bat) (f68d527) Message-ID: <20171027004456.79D5A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f68d527a2f040cc16a7f03a5ce25864ed0acaa58/ghc >--------------------------------------------------------------- commit f68d527a2f040cc16a7f03a5ce25864ed0acaa58 Author: Andrey Mokhov Date: Mon Oct 23 21:36:37 2017 +0100 Make build.bat call the default build script on Windows (build.stack.bat) See #428. Note that building Hadrian with Cabal currently fails on Windows, hence using Stack. Also see #440: build.bat may later be relocated to the top of the GHC tree. >--------------------------------------------------------------- f68d527a2f040cc16a7f03a5ce25864ed0acaa58 build.bat | 33 ++------------------------------- build.bat => build.global-db.bat | 1 - 2 files changed, 2 insertions(+), 32 deletions(-) diff --git a/build.bat b/build.bat index 722f3d7..18cf6cb 100644 --- a/build.bat +++ b/build.bat @@ -1,33 +1,4 @@ @echo off -setlocal -cd %~dp0 -mkdir bin 2> nul -set ghcArgs=--make ^ - -Wall ^ - -fno-warn-name-shadowing ^ - -XRecordWildCards ^ - src\Main.hs ^ - -threaded ^ - -isrc ^ - -i..\libraries\Cabal\Cabal ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=bin ^ - -j ^ - -O ^ - -o bin\hadrian - -set hadrianArgs=--lint ^ - --directory ^ - ".." ^ - %* - - -ghc %ghcArgs% - -if %ERRORLEVEL% NEQ 0 EXIT /B %ERRORLEVEL% - -rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains -set GHC_PACKAGE_PATH= -bin\hadrian %hadrianArgs% +rem By default on Windows we build Hadrian using Stack +./build.stack.bat %* diff --git a/build.bat b/build.global-db.bat similarity index 99% copy from build.bat copy to build.global-db.bat index 722f3d7..0d6a696 100644 --- a/build.bat +++ b/build.global-db.bat @@ -23,7 +23,6 @@ set hadrianArgs=--lint ^ ".." ^ %* - ghc %ghcArgs% if %ERRORLEVEL% NEQ 0 EXIT /B %ERRORLEVEL% From git at git.haskell.org Fri Oct 27 00:44:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note about interaction of the new and existing build systems. (92a3ffb) Message-ID: <20171027004459.ADBF23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92a3ffba8b0f61ed772f942c16a3ca1a0495f1d8/ghc >--------------------------------------------------------------- commit 92a3ffba8b0f61ed772f942c16a3ca1a0495f1d8 Author: Andrey Mokhov Date: Tue Jan 26 20:02:05 2016 +0000 Add a note about interaction of the new and existing build systems. [skip ci] >--------------------------------------------------------------- 92a3ffba8b0f61ed772f942c16a3ca1a0495f1d8 README.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README.md b/README.md index 057b864..18ba8f6 100644 --- a/README.md +++ b/README.md @@ -9,6 +9,10 @@ on [Shake][shake] and we hope that it will eventually replace the current ideas behind the project you can find more details on the [wiki page][ghc-shake-wiki] and in this [blog post][blog-post-1]. +The new build system can work side-by-side with the existing build system. Note, there is +some interaction between them: they put (some) build results in the same directories, +e.g. `inplace/bin/ghc-stage1`. + [Join us on #shaking-up-ghc on Freenode](irc://chat.freenode.net/#shaking-up-ghc). Your first build From git at git.haskell.org Fri Oct 27 00:45:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch AppVeyor to use the default build.bat script (04cdf78) Message-ID: <20171027004500.812C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/04cdf78cae2e02db1129068db5d7b5c7fc9847e5/ghc >--------------------------------------------------------------- commit 04cdf78cae2e02db1129068db5d7b5c7fc9847e5 Author: Andrey Mokhov Date: Mon Oct 23 21:37:07 2017 +0100 Switch AppVeyor to use the default build.bat script See #428 >--------------------------------------------------------------- 04cdf78cae2e02db1129068db5d7b5c7fc9847e5 appveyor.yml | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 2f4653a..fbedf8f 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -26,14 +26,13 @@ install: build_script: # Build Hadrian - - stack build alex happy # Otherwise 'stack build' fails on AppVeyor - - stack build + - stack build alex happy # Otherwise 'build' fails on AppVeyor # Run internal Hadrian tests - - stack exec hadrian -- --directory ".." selftest + - build selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-colour=never --profile=- + - build -j --flavour=quickest --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 00:44:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:44:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (d9b059b) Message-ID: <20171027004459.CB8CE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9b059b3471b2a897b4b0fe8370a6340011310b6/ghc >--------------------------------------------------------------- commit d9b059b3471b2a897b4b0fe8370a6340011310b6 Author: Andrey Mokhov Date: Mon Oct 31 18:25:18 2016 +0000 Minor revision >--------------------------------------------------------------- d9b059b3471b2a897b4b0fe8370a6340011310b6 hadrian.cabal | 2 +- .../{DirectoryContent.hs => DirectoryContents.hs} | 19 +++++++++-------- src/Rules/Oracles.hs | 4 ++-- src/Rules/SourceDist.hs | 4 ++-- src/Util.hs | 24 ++++++++++------------ 5 files changed, 26 insertions(+), 27 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index b20b17d..0663643 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -31,7 +31,7 @@ executable hadrian , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies - , Oracles.DirectoryContent + , Oracles.DirectoryContents , Oracles.ModuleFiles , Oracles.PackageData , Oracles.Path diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContents.hs similarity index 53% rename from src/Oracles/DirectoryContent.hs rename to src/Oracles/DirectoryContents.hs index 3139c6c..6dd3439 100644 --- a/src/Oracles/DirectoryContent.hs +++ b/src/Oracles/DirectoryContents.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} -module Oracles.DirectoryContent ( - directoryContent, directoryContentOracle, Match (..) +module Oracles.DirectoryContents ( + directoryContents, directoryContentsOracle, Match (..) ) where import System.Directory.Extra @@ -8,7 +8,7 @@ import GHC.Generics import Base -newtype DirectoryContent = DirectoryContent (Match, FilePath) +newtype DirectoryContents = DirectoryContents (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) data Match = Test FilePattern | Not Match | And [Match] | Or [Match] @@ -20,13 +20,14 @@ matches (Not m) f = not $ matches m f matches (And ms) f = all (`matches` f) ms matches (Or ms) f = any (`matches` f) ms --- | Get the directory content recursively. -directoryContent :: Match -> FilePath -> Action [FilePath] -directoryContent expr dir = askOracle $ DirectoryContent (expr, dir) +-- | Given a 'Match' expression and a directory, recursively traverse it and all +-- its subdirectories to find and return all matching contents. +directoryContents :: Match -> FilePath -> Action [FilePath] +directoryContents expr dir = askOracle $ DirectoryContents (expr, dir) -directoryContentOracle :: Rules () -directoryContentOracle = void $ - addOracle $ \(DirectoryContent (expr, dir)) -> liftIO $ +directoryContentsOracle :: Rules () +directoryContentsOracle = void $ + addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ filter (matches expr) <$> listFilesInside (return . matches expr) dir instance Binary Match diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 6c5ace4..8f53369 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -4,7 +4,7 @@ import Base import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies -import qualified Oracles.DirectoryContent +import qualified Oracles.DirectoryContents import qualified Oracles.ModuleFiles import qualified Oracles.PackageData import qualified Oracles.Path @@ -14,7 +14,7 @@ oracleRules = do Oracles.ArgsHash.argsHashOracle Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles - Oracles.DirectoryContent.directoryContentOracle + Oracles.DirectoryContents.directoryContentsOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle Oracles.Path.pathOracle diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index 9c49878..d51fe75 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -3,7 +3,7 @@ module Rules.SourceDist (sourceDistRules) where import Base import Builder import Oracles.Config.Setting -import Oracles.DirectoryContent +import Oracles.DirectoryContents import UserSettings import Util @@ -32,7 +32,7 @@ prepareTree dest = do mapM_ cpFile srcFiles where cpFile a = copyFile a (dest a) - cpDir a = copyDirectoryContent (Not excluded) a (dest takeFileName a) + cpDir a = copyDirectoryContents (Not excluded) a (dest takeFileName a) excluded = Or [ Test "//.*" , Test "//#*" diff --git a/src/Util.hs b/src/Util.hs index dbafd85..f2e6516 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,6 @@ module Util ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, - removeFile, copyDirectory, copyDirectoryContent, createDirectory, + removeFile, copyDirectory, copyDirectoryContents, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, makeExecutable, renderProgram, renderLibrary, Match(..), builderEnvironment, needBuilder @@ -16,7 +16,7 @@ import Context import Expression import GHC import Oracles.ArgsHash -import Oracles.DirectoryContent +import Oracles.DirectoryContents import Oracles.Path import Settings import Settings.Builders.Ar @@ -96,6 +96,8 @@ captureStdout target path argList = do copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. + let dir = takeDirectory target + unlessM (liftIO $ IO.doesDirectoryExist dir) $ createDirectory dir putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target @@ -129,17 +131,13 @@ copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd cmdEcho ["cp", "-r", source, target] --- | Copy the content of the source directory into the target directory. --- The copied content is tracked. -copyDirectoryContent :: Match -> FilePath -> FilePath -> Action () -copyDirectoryContent expr source target = do - putProgressInfo $ renderAction "Copy directory content" source target - mapM_ cp =<< directoryContent expr source - where - cp file = do - let newFile = target -/- drop (length source) file - createDirectory $ dropFileName newFile -- TODO: Why do it for each file? - copyFile file newFile +-- | Copy the contents of the source directory that matches a given 'Match' +-- expression into the target directory. The copied contents is tracked. +copyDirectoryContents :: Match -> FilePath -> FilePath -> Action () +copyDirectoryContents expr source target = do + putProgressInfo $ renderAction "Copy directory contents" source target + let cp file = copyFile file $ target -/- makeRelative source file + mapM_ cp =<< directoryContents expr source -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:45:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path separators (8be3f76) Message-ID: <20171027004504.0E0C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8be3f76d78e9806bdbef6a2d2db7bbf341aba0ea/ghc >--------------------------------------------------------------- commit 8be3f76d78e9806bdbef6a2d2db7bbf341aba0ea Author: Andrey Mokhov Date: Mon Oct 31 19:19:19 2016 +0000 Fix path separators >--------------------------------------------------------------- 8be3f76d78e9806bdbef6a2d2db7bbf341aba0ea src/Oracles/DirectoryContents.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/SourceDist.hs | 9 ++++----- 3 files changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Oracles/DirectoryContents.hs b/src/Oracles/DirectoryContents.hs index 6dd3439..d854c7d 100644 --- a/src/Oracles/DirectoryContents.hs +++ b/src/Oracles/DirectoryContents.hs @@ -27,7 +27,7 @@ directoryContents expr dir = askOracle $ DirectoryContents (expr, dir) directoryContentsOracle :: Rules () directoryContentsOracle = void $ - addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ + addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ map unifyPath . filter (matches expr) <$> listFilesInside (return . matches expr) dir instance Binary Match diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 64f8ea9..2d3eb4a 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -14,7 +14,7 @@ import Util compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context - nonHs extension = path extension "*" <.> osuf way + nonHs extension = path -/- extension "*" <.> osuf way compile compiler obj2src obj = do let src = obj2src context obj need [src] diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index d51fe75..d56eb38 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -15,9 +15,9 @@ sourceDistRules = do putSuccess "| Done. " "sdistprep/ghc-*-src.tar.xz" %> \fname -> do let tarName = takeFileName fname - treePath = "sdistprep/ghc" dropTarXz tarName + treePath = "sdistprep/ghc" -/- dropTarXz tarName prepareTree treePath - runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." tarName, dropTarXz tarName] + runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." -/- tarName, dropTarXz tarName] "GIT_COMMIT_ID" %> \fname -> setting ProjectGitCommitId >>= writeFileChanged fname "VERSION" %> \fname -> @@ -25,14 +25,13 @@ sourceDistRules = do where dropTarXz = dropExtension . dropExtension - prepareTree :: FilePath -> Action () prepareTree dest = do mapM_ cpDir srcDirs mapM_ cpFile srcFiles where - cpFile a = copyFile a (dest a) - cpDir a = copyDirectoryContents (Not excluded) a (dest takeFileName a) + cpFile a = copyFile a (dest -/- a) + cpDir a = copyDirectoryContents (Not excluded) a (dest -/- takeFileName a) excluded = Or [ Test "//.*" , Test "//#*" From git at git.haskell.org Fri Oct 27 00:45:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Test to Selftest. (b06bae8) Message-ID: <20171027004504.145683A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b06bae88a40b7ee645b0aecda8019a601d567dce/ghc >--------------------------------------------------------------- commit b06bae88a40b7ee645b0aecda8019a601d567dce Author: Andrey Mokhov Date: Wed Jan 27 23:29:51 2016 +0000 Rename Test to Selftest. >--------------------------------------------------------------- b06bae88a40b7ee645b0aecda8019a601d567dce shaking-up-ghc.cabal | 2 +- src/Main.hs | 4 ++-- src/{Test.hs => Selftest.hs} | 6 +++--- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 674d6f0..60f3c34 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -65,6 +65,7 @@ executable ghc-shake , Rules.Resources , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg + , Selftest , Settings , Settings.Args , Settings.Builders.Alex @@ -104,7 +105,6 @@ executable ghc-shake , Settings.Ways , Stage , Target - , Test , Way default-language: Haskell2010 diff --git a/src/Main.hs b/src/Main.hs index 12ec014..befb6e7 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -14,7 +14,7 @@ import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl -import qualified Test +import qualified Selftest main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -37,7 +37,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do , Rules.Perl.perlScriptRules , Rules.generateTargets , Rules.packageRules - , Test.testRules ] + , Selftest.selftestRules ] options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Test.hs b/src/Selftest.hs similarity index 89% rename from src/Test.hs rename to src/Selftest.hs index 3c88ed4..4800ca8 100644 --- a/src/Test.hs +++ b/src/Selftest.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -module Test (testRules) where +module Selftest (selftestRules) where import Development.Shake import Settings.Builders.Ar (chunksOfSize) @@ -13,8 +13,8 @@ instance Arbitrary Way where instance Arbitrary WayUnit where arbitrary = arbitraryBoundedEnum -testRules :: Rules () -testRules = +selftestRules :: Rules () +selftestRules = "selftest" ~> do test $ \(x :: Way) -> read (show x) == x test $ \n xs -> From git at git.haskell.org Fri Oct 27 00:45:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix the call to another script (9e4a9c1) Message-ID: <20171027004504.9CFC03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e4a9c1090ac800f6f2cf44d5adeeea2152dd80a/ghc >--------------------------------------------------------------- commit 9e4a9c1090ac800f6f2cf44d5adeeea2152dd80a Author: Andrey Mokhov Date: Mon Oct 23 23:04:06 2017 +0100 Fix the call to another script >--------------------------------------------------------------- 9e4a9c1090ac800f6f2cf44d5adeeea2152dd80a build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 460fdc1..434b3a3 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,4 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -./build.cabal.sh "$@" +( ./build.cabal.sh "$@" ) From git at git.haskell.org Fri Oct 27 00:45:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CI by calling default script via bash (14c2c27) Message-ID: <20171027004508.BB2D73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14c2c279aa49b272f9cae73269bd9e99bf887b2e/ghc >--------------------------------------------------------------- commit 14c2c279aa49b272f9cae73269bd9e99bf887b2e Author: Andrey Mokhov Date: Mon Oct 23 23:18:13 2017 +0100 Fix CI by calling default script via bash >--------------------------------------------------------------- 14c2c279aa49b272f9cae73269bd9e99bf887b2e build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 434b3a3..f40e06e 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,4 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -( ./build.cabal.sh "$@" ) +bash './build.cabal.sh "$@"' From git at git.haskell.org Fri Oct 27 00:45:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add basic validation support (GHC tests). (e9abc61) Message-ID: <20171027004508.83AB13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101/ghc >--------------------------------------------------------------- commit e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101 Author: Andrey Mokhov Date: Thu Jan 28 02:51:12 2016 +0000 Add basic validation support (GHC tests). See #187. >--------------------------------------------------------------- e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101 shaking-up-ghc.cabal | 1 + src/Main.hs | 4 +++- src/Test.hs | 63 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 67 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index 60f3c34..f00c7c6 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -105,6 +105,7 @@ executable ghc-shake , Settings.Ways , Stage , Target + , Test , Way default-language: Haskell2010 diff --git a/src/Main.hs b/src/Main.hs index befb6e7..2c944d4 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -15,6 +15,7 @@ import qualified Rules.Libffi import qualified Rules.Oracles import qualified Rules.Perl import qualified Selftest +import qualified Test main :: IO () main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do @@ -37,7 +38,8 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do , Rules.Perl.perlScriptRules , Rules.generateTargets , Rules.packageRules - , Selftest.selftestRules ] + , Selftest.selftestRules + , Test.testRules ] options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = Base.shakeFilesPath diff --git a/src/Test.hs b/src/Test.hs new file mode 100644 index 0000000..547e286 --- /dev/null +++ b/src/Test.hs @@ -0,0 +1,63 @@ +module Test (testRules) where + +import Base +import Builder +import Expression +import GHC (rts, libffi) +import Oracles.Config.Flag +import Oracles.Config.Setting +import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory +import Settings.Packages +import Settings.User + +-- TODO: clean up after testing +testRules :: Rules () +testRules = + "test" ~> do + let quote s = "\"" ++ s ++ "\"" + yesNo x = quote $ if x then "YES" else "NO" + pkgs <- interpretWithStage Stage1 getPackages + tests <- filterM doesDirectoryExist $ concat + [ [ pkgPath pkg -/- "tests", pkgPath pkg -/- "tests-ghc" ] + | pkg <- pkgs, isLibrary pkg, pkg /= rts, pkg /= libffi ] + windows <- windowsHost + top <- topDirectory + compiler <- builderPath $ Ghc Stage2 + ghcPkg <- builderPath $ GhcPkg Stage1 + haddock <- builderPath Haddock + threads <- shakeThreads <$> getShakeOptions + ghcWithNativeCodeGenInt <- fromEnum <$> ghcWithNativeCodeGen + ghcWithInterpreterInt <- fromEnum <$> ghcWithInterpreter + ghcUnregisterisedInt <- fromEnum <$> flag GhcUnregisterised + quietly . cmd "python2" $ + [ "testsuite/driver/runtests.py" ] + ++ map ("--rootdir="++) tests ++ + [ "-e", "windows=" ++ show windows + , "-e", "config.speed=2" + , "-e", "ghc_compiler_always_flags=" ++ quote "-fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts" + , "-e", "ghc_with_native_codegen=" ++ show ghcWithNativeCodeGenInt + , "-e", "ghc_debugged=" ++ yesNo ghcDebugged + , "-e", "ghc_with_vanilla=1" -- TODO: do we always build vanilla? + , "-e", "ghc_with_dynamic=0" -- TODO: support dynamic + , "-e", "ghc_with_profiling=0" -- TODO: support profiling + , "-e", "ghc_with_interpreter=" ++ show ghcWithInterpreterInt + , "-e", "ghc_unregisterised=" ++ show ghcUnregisterisedInt + , "-e", "ghc_with_threaded_rts=0" -- TODO: support threaded + , "-e", "ghc_with_dynamic_rts=0" -- TODO: support dynamic + , "-e", "ghc_dynamic_by_default=False" -- TODO: support dynamic + , "-e", "ghc_dynamic=0" -- TODO: support dynamic + , "-e", "ghc_with_llvm=0" -- TODO: support LLVM + , "-e", "in_tree_compiler=True" -- TODO: when is it equal to False? + , "-e", "clean_only=False" -- TODO: do we need to support True? + , "--configfile=testsuite/config/ghc" + , "--config", "compiler=" ++ quote (top -/- compiler) + , "--config", "ghc_pkg=" ++ quote (top -/- ghcPkg) + , "--config", "haddock=" ++ quote (top -/- haddock) + , "--summary-file", "testsuite_summary.txt" + , "--threads=" ++ show threads + ] + + -- , "--config", "hp2ps=" ++ quote ("hp2ps") + -- , "--config", "hpc=" ++ quote ("hpc") + -- , "--config", "gs=$(call quote_path,$(GS))" + -- , "--config", "timeout_prog=$(call quote_path,$(TIMEOUT_PROGRAM))" From git at git.haskell.org Fri Oct 27 00:45:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant createDirectory calls (7041682) Message-ID: <20171027004508.7E8D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7041682e77204d718def64aee7d0c768ffd685bd/ghc >--------------------------------------------------------------- commit 7041682e77204d718def64aee7d0c768ffd685bd Author: Andrey Mokhov Date: Mon Oct 31 19:50:36 2016 +0000 Drop redundant createDirectory calls >--------------------------------------------------------------- 7041682e77204d718def64aee7d0c768ffd685bd src/Rules/Data.hs | 1 - src/Rules/Gmp.hs | 2 -- src/Rules/Libffi.hs | 1 - src/Util.hs | 2 +- 4 files changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 65c6392..ab8ac97 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -47,7 +47,6 @@ buildPackageData context at Context {..} = do | otherwise = oldPath -/- "build" -/- pkgNameString package copyFile inTreeMk mk autogenFiles <- getDirectoryFiles oldBuild ["autogen/*"] - createDirectory $ buildPath context -/- "autogen" forM_ autogenFiles $ \file' -> do let file = unifyPath file' copyFile (oldBuild -/- file) (buildPath context -/- file) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1024533..2409b6e 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -44,14 +44,12 @@ gmpRules = do any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" - createDirectory $ takeDirectory header copyFile (gmpBase -/- "ghc-gmp.h") header else do putBuild "| No GMP library/framework detected; in tree GMP will be built" need [gmpLibrary] createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] - createDirectory $ takeDirectory header copyFile (gmpBuildPath -/- "gmp.h") header copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index ae1c06f..8d72017 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,7 +70,6 @@ libffiRules = do libffiMakefile <.> "in" %> \mkIn -> do removeDirectory libffiBuildPath - createDirectory $ buildRootPath -/- stageString Stage0 tarball <- unifyPath . getSingleton "Exactly one LibFFI tarball is expected" <$> getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] diff --git a/src/Util.hs b/src/Util.hs index f2e6516..81f67dd 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -92,7 +92,7 @@ captureStdout target path argList = do Stdout output <- cmd [path] argList writeFileChanged file output --- | Copy a file tracking the source. +-- | Copy a file tracking the source, create the target directory if missing. copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. From git at git.haskell.org Fri Oct 27 00:45:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify, remove old hacks (4fd513a) Message-ID: <20171027004513.123F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fd513a325e1689e971f72941975ee20912bd647/ghc >--------------------------------------------------------------- commit 4fd513a325e1689e971f72941975ee20912bd647 Author: Andrey Mokhov Date: Mon Oct 31 23:52:34 2016 +0000 Simplify, remove old hacks >--------------------------------------------------------------- 4fd513a325e1689e971f72941975ee20912bd647 src/Rules/Generate.hs | 39 +++++++++++++-------------------------- 1 file changed, 13 insertions(+), 26 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 0141f29..d13d2bb 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -3,8 +3,6 @@ module Rules.Generate ( installTargets, copyRules, includesDependencies, generatedDependencies ) where -import qualified System.Directory as IO - import Base import Context hiding (package) import Expression @@ -110,21 +108,27 @@ generatePackageCode :: Context -> Rules () generatePackageCode context@(Context stage pkg _) = let path = buildPath context generated f = (path ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) - file <~ gen = generate file context gen + go gen file = generate file context gen in do generated ?> \file -> do let unpack = fromMaybe . error $ "No generator for " ++ file ++ "." (src, builder) <- unpack <$> findGenerator context file need [src] build $ Target context builder [src] [file] - let srcBoot = src -<.> "hs-boot" - whenM (doesFileExist srcBoot) $ - copyFile srcBoot $ file -<.> "hs-boot" + let boot = src -<.> "hs-boot" + whenM (doesFileExist boot) . copyFile boot $ file -<.> "hs-boot" + + priority 2.0 $ do + when (pkg == compiler) $ path -/- "Config.hs" %> go generateConfigHs + when (pkg == ghcPkg) $ path -/- "Version.hs" %> go generateVersionHs -- TODO: needing platformH is ugly and fragile - when (pkg == compiler) $ primopsTxt stage %> \file -> do - need $ [platformH stage, primopsSource] ++ includesDependencies - build $ Target context HsCpp [primopsSource] [file] + when (pkg == compiler) $ do + primopsTxt stage %> \file -> do + need $ [platformH stage, primopsSource] ++ includesDependencies + build $ Target context HsCpp [primopsSource] [file] + + platformH stage %> go generateGhcBootPlatformH -- TODO: why different folders for generated files? fmap (path -/-) @@ -133,26 +137,10 @@ generatePackageCode context@(Context stage pkg _) = , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] build $ Target context GenPrimopCode [primopsTxt stage] [file] - -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- stageDirectory stage -/- "build" - newFile = oldPath ++ (drop (length path) file) - createDirectory $ takeDirectory newFile - liftIO $ IO.copyFile file newFile - putBuild $ "| Duplicate file " ++ file ++ " -> " ++ newFile when (pkg == rts) $ path -/- "cmm/AutoApply.cmm" %> \file -> build $ Target context GenApply [] [file] - priority 2.0 $ do - when (pkg == compiler) $ path -/- "Config.hs" %> \file -> do - file <~ generateConfigHs - - when (pkg == compiler) $ platformH stage %> \file -> do - file <~ generateGhcBootPlatformH - - when (pkg == ghcPkg) $ path -/- "Version.hs" %> \file -> do - file <~ generateVersionHs - copyRules :: Rules () copyRules = do "inplace/lib/ghc-usage.txt" <~ "driver" @@ -179,7 +167,6 @@ generateRules = do generatedPath ++ "//*" %> \file -> do withTempDir $ \dir -> build $ Target rtsContext DeriveConstants [] [file, dir] - where file <~ gen = file %> \out -> generate out emptyTarget gen From git at git.haskell.org Fri Oct 27 00:45:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop quotes (4e7d0f9) Message-ID: <20171027004513.44CEF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e7d0f99d807a876dcc5ff420a42f5793c854250/ghc >--------------------------------------------------------------- commit 4e7d0f99d807a876dcc5ff420a42f5793c854250 Author: Andrey Mokhov Date: Mon Oct 23 23:25:42 2017 +0100 Drop quotes >--------------------------------------------------------------- 4e7d0f99d807a876dcc5ff420a42f5793c854250 build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index f40e06e..fa331fa 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,4 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -bash './build.cabal.sh "$@"' +bash ./build.cabal.sh "$@" From git at git.haskell.org Fri Oct 27 00:45:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependencies on generated files (010dd78) Message-ID: <20171027004517.BB2EC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/010dd78b1e574c648f9a93d2a636ff9ae05422ff/ghc >--------------------------------------------------------------- commit 010dd78b1e574c648f9a93d2a636ff9ae05422ff Author: Andrey Mokhov Date: Mon Oct 31 23:55:27 2016 +0000 Add missing dependencies on generated files See #285. >--------------------------------------------------------------- 010dd78b1e574c648f9a93d2a636ff9ae05422ff src/Rules/Dependencies.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 04c4f1f..192e24c 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -6,6 +6,7 @@ import Base import Context import Expression import Oracles.ModuleFiles +import Rules.Generate import Settings.Path import Target import Util @@ -15,6 +16,7 @@ buildPackageDependencies rs context at Context {..} = buildPath context -/- ".dependencies" %> \deps -> do srcs <- hsSources context need srcs + orderOnly =<< interpretInContext context generatedDependencies let mk = deps <.> "mk" if srcs == [] then writeFileChanged mk "" From git at git.haskell.org Fri Oct 27 00:45:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add testing section (eee29dc) Message-ID: <20171027004513.20CBB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eee29dc165adceebda020444214e28d0d7456860/ghc >--------------------------------------------------------------- commit eee29dc165adceebda020444214e28d0d7456860 Author: Andrey Mokhov Date: Thu Jan 28 02:51:52 2016 +0000 Add testing section [skip ci] >--------------------------------------------------------------- eee29dc165adceebda020444214e28d0d7456860 README.md | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 18ba8f6..56e13ad 100644 --- a/README.md +++ b/README.md @@ -75,9 +75,19 @@ experiment following the Haddock comments. #### Clean and full rebuild -* `shake-build/build.sh clean` removes all build artefacts. Note, we are working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `shake-build/build.sh clean` removes all build artefacts. Note, we are working +towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. -* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. +* `shake-build/build.sh -B` forces Shake to rerun all rules, even if results of +the previous build are still in the GHC tree. + +#### Testing + +* `shake-build/build.sh test` runs GHC tests. The current implementation is very +limited and cannot replace the `validate` script (see [#187][validation-issue]). + +* `shake-build/build.sh selftest` runs tests of the build system. Current test +coverage is close to zero (see [#197][test-issue]). Current limitations ------------------- @@ -120,6 +130,7 @@ helped me endure and enjoy the project. [build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs +[test-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/197 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 [profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 From git at git.haskell.org Fri Oct 27 00:45:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use libHS*_thr.a instead of libHS*.thr_a naming convention for libraries. (c760627) Message-ID: <20171027004517.AB2243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7606279a186f145d5e7751f65be8c2be8aefb80/ghc >--------------------------------------------------------------- commit c7606279a186f145d5e7751f65be8c2be8aefb80 Author: Andrey Mokhov Date: Fri Jan 29 01:05:48 2016 +0000 Use libHS*_thr.a instead of libHS*.thr_a naming convention for libraries. See #98. >--------------------------------------------------------------- c7606279a186f145d5e7751f65be8c2be8aefb80 src/Rules/Library.hs | 2 +- src/Settings/Paths.hs | 2 +- src/Way.hs | 14 ++++++++------ 3 files changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b53c472..2cde962 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -46,7 +46,7 @@ buildPackageLibrary _ target @ (PartialTarget stage pkg) = do let objs = cObjs ++ splitObjs ++ eObjs asuf <- libsuf way - let isLib0 = ("//*-0" <.> asuf) ?== a + let isLib0 = ("//*-0" ++ asuf) ?== a if isLib0 then build $ fullTarget target Ar [] [a] -- TODO: scan for dlls else build $ fullTarget target Ar objs [a] diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index ed217a8..a152f9a 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -29,7 +29,7 @@ pkgLibraryFile :: Stage -> Package -> String -> Way -> Action FilePath pkgLibraryFile stage pkg componentId way = do extension <- libsuf way let buildPath = targetPath stage pkg -/- "build" - return $ buildPath -/- "libHS" ++ componentId <.> extension + return $ buildPath -/- "libHS" ++ componentId ++ extension -- Relative path to a package ghci library file, e.g.: -- "libraries/array/dist-install/build/HSarray-0.5.1.0.o" diff --git a/src/Way.hs b/src/Way.hs index 8923571..da986a8 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -127,6 +127,10 @@ wayPrefix :: Way -> String wayPrefix way | way == vanilla = "" | otherwise = show way ++ "_" +waySuffix :: Way -> String +waySuffix way | way == vanilla = "" + | otherwise = "_" ++ show way + osuf, ssuf, hisuf, hcsuf, obootsuf, hibootsuf :: Way -> String osuf = (++ "o" ) . wayPrefix ssuf = (++ "s" ) . wayPrefix @@ -135,10 +139,6 @@ hcsuf = (++ "hc" ) . wayPrefix obootsuf = (++ "o-boot" ) . wayPrefix hibootsuf = (++ "hi-boot") . wayPrefix --- Note: in the previous build system libsuf was mysteriously different --- from other suffixes. For example, in the profiling way it used to be --- "_p.a" instead of ".p_a" which is how other suffixes work. I decided --- to make all suffixes consistent: ".way_extension". -- TODO: find out why we need version number in the dynamic suffix -- The current theory: dynamic libraries are eventually placed in a single -- giant directory in the load path of the dynamic linker, and hence we must @@ -148,7 +148,7 @@ hibootsuf = (++ "hi-boot") . wayPrefix libsuf :: Way -> Action String libsuf way @ (Way set) = if (not . wayUnit Dynamic $ way) - then return $ wayPrefix way ++ "a" -- e.g., p_a + then return $ waySuffix way ++ ".a" -- e.g., _p.a else do extension <- setting DynamicExtension -- e.g., .dll or .so version <- setting ProjectVersion -- e.g., 7.11.20141222 @@ -172,7 +172,9 @@ safeDetectWay file = case reads prefix of then extension else takeExtension . dropExtension . dropExtension . dropExtension $ file - prefix = drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed + prefix = if extension == "a" + then drop 1 . dropWhile (/= '_') $ takeBaseName file + else drop 1 . dropWhileEnd (== '_') . dropWhileEnd (/= '_') $ prefixed -- Unsafe version of safeDetectWay. Useful when matchBuildResult has succeeded. detectWay :: FilePath -> Way From git at git.haskell.org Fri Oct 27 00:45:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CI (#441) (4b60862) Message-ID: <20171027004517.EA77D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b60862b82d50a6946ac130f113c6e693f7a346d/ghc >--------------------------------------------------------------- commit 4b60862b82d50a6946ac130f113c6e693f7a346d Author: Andrey Mokhov Date: Tue Oct 24 14:02:55 2017 +0100 Fix CI (#441) * Fix CI * Another attempt * Another tweak >--------------------------------------------------------------- 4b60862b82d50a6946ac130f113c6e693f7a346d build.sh | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/build.sh b/build.sh index fa331fa..8e58b66 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,5 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -bash ./build.cabal.sh "$@" +chmod a+x ./build.cabal.sh +(. ./build.cabal.sh "$@") From git at git.haskell.org Fri Oct 27 00:45:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add 'hadrian/' from commit '4b60862b82d50a6946ac130f113c6e693f7a346d' (b2d1daa) Message-ID: <20171027004521.294E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2d1daac23cc16baac69e718f1094a568f2edec1/ghc >--------------------------------------------------------------- commit b2d1daac23cc16baac69e718f1094a568f2edec1 Merge: d91a6b6 4b60862 Author: Ben Gamari Date: Thu Oct 26 09:50:56 2017 -0400 Add 'hadrian/' from commit '4b60862b82d50a6946ac130f113c6e693f7a346d' git-subtree-dir: hadrian git-subtree-mainline: d91a6b6c1d7699b6e9ace1988974d4453a20dab6 git-subtree-split: 4b60862b82d50a6946ac130f113c6e693f7a346d >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b2d1daac23cc16baac69e718f1094a568f2edec1 From git at git.haskell.org Fri Oct 27 00:45:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a rule to build gmpLibraryInTreeH. (3b0fdab) Message-ID: <20171027004521.6CFCC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b0fdab49988b9f1981e238c903a08fd75419cc3/ghc >--------------------------------------------------------------- commit 3b0fdab49988b9f1981e238c903a08fd75419cc3 Author: Andrey Mokhov Date: Fri Jan 29 01:06:24 2016 +0000 Add a rule to build gmpLibraryInTreeH. >--------------------------------------------------------------- 3b0fdab49988b9f1981e238c903a08fd75419cc3 src/Rules/Gmp.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index b384b68..ab25495 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -144,3 +144,5 @@ gmpRules = do runBuilder Ranlib [gmpLibrary] putSuccess "| Successfully built custom library 'gmp'" + + gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] From git at git.haskell.org Fri Oct 27 00:45:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move GHC/Prim.hs outside of autogen directory (eca7b6a) Message-ID: <20171027004521.6575E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eca7b6a6d9a17e44854cb8f696cec03140052208/ghc >--------------------------------------------------------------- commit eca7b6a6d9a17e44854cb8f696cec03140052208 Author: Andrey Mokhov Date: Tue Nov 1 19:27:32 2016 +0000 Move GHC/Prim.hs outside of autogen directory >--------------------------------------------------------------- eca7b6a6d9a17e44854cb8f696cec03140052208 src/Oracles/ModuleFiles.hs | 6 +----- src/Rules/Generate.hs | 4 ++-- 2 files changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index a9bae04..70a7a9f 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -75,11 +75,7 @@ findGenerator Context {..} file = do -- | Find all Haskell source files for a given 'Context'. hsSources :: Context -> Action [FilePath] hsSources context = do - let autogen = buildPath context -/- "autogen" - -- Generated source files live in buildPath and have extension "hs", except - -- for GHC/Prim.hs that lives in autogen. TODO: fix the inconsistency? - modFile ("GHC.Prim", _) = autogen -/- "GHC/Prim.hs" - modFile (m, Nothing ) = generatedFile context m + let modFile (m, Nothing ) = generatedFile context m modFile (m, Just file ) | takeExtension file `elem` haskellExtensions = file | otherwise = generatedFile context m diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index d13d2bb..e84313a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -55,7 +55,7 @@ ghcPrimDependencies :: Expr [FilePath] ghcPrimDependencies = do stage <- getStage let path = buildPath $ vanillaContext stage ghcPrim - return [path -/- "autogen/GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"] + return [path -/- "GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"] derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = installTargets ++ fmap (generatedPath -/-) @@ -132,7 +132,7 @@ generatePackageCode context@(Context stage pkg _) = -- TODO: why different folders for generated files? fmap (path -/-) - [ "autogen/GHC/Prim.hs" + [ "GHC/Prim.hs" , "GHC/PrimopWrappers.hs" , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] From git at git.haskell.org Fri Oct 27 00:45:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't ignore hadrian/ (2f11b17) Message-ID: <20171027004524.0C1733A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f11b17af7ef8f1b5f518dff7dbae6173e7d0515/ghc >--------------------------------------------------------------- commit 2f11b17af7ef8f1b5f518dff7dbae6173e7d0515 Author: Ben Gamari Date: Thu Oct 26 09:51:02 2017 -0400 Don't ignore hadrian/ >--------------------------------------------------------------- 2f11b17af7ef8f1b5f518dff7dbae6173e7d0515 .gitignore | 1 - 1 file changed, 1 deletion(-) diff --git a/.gitignore b/.gitignore index 710c6bf..f1b38d6 100644 --- a/.gitignore +++ b/.gitignore @@ -49,7 +49,6 @@ stage0 stage1 stage2 _build -hadrian # ----------------------------------------------------------------------------- # Ignore any overlapped darcs repos and back up files From git at git.haskell.org Fri Oct 27 00:45:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build dependencies for all known packages that exist (95ee1ab) Message-ID: <20171027004525.976E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95ee1ab41659c3e6f4d64455faed96aebaeb0cbf/ghc >--------------------------------------------------------------- commit 95ee1ab41659c3e6f4d64455faed96aebaeb0cbf Author: Andrey Mokhov Date: Tue Nov 1 21:30:15 2016 +0000 Build dependencies for all known packages that exist >--------------------------------------------------------------- 95ee1ab41659c3e6f4d64455faed96aebaeb0cbf src/Rules/Cabal.hs | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index b2bd630..370bda2 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -11,6 +11,7 @@ import Expression import GHC import Settings import Settings.Path +import UserSettings cabalRules :: Rules () cabalRules = do @@ -25,13 +26,13 @@ cabalRules = do version = display . pkgVersion $ identifier return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version writeFileChanged out . unlines $ constraints + putSuccess $ "| Successfully computed boot package constraints" -- Cache package dependencies. packageDependencies %> \out -> do - pkgs <- concatMapM stagePackages [Stage0 .. Stage2] - pkgDeps <- forM (sort pkgs) $ \pkg -> - if pkg `elem` [hp2ps, libffi, rts, touchy, unlit] - then return $ pkgNameString pkg + pkgDeps <- forM (sort knownPackages) $ \pkg -> do + exists <- doesFileExist $ pkgCabalFile pkg + if not exists then return $ pkgNameString pkg else do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg @@ -40,7 +41,8 @@ cabalRules = do deps = concat $ depsLib : depsExes depNames = [ unPackageName name | Dependency name _ <- deps ] return . unwords $ pkgNameString pkg : sort depNames - writeFileChanged out . unlines $ pkgDeps + writeFileChanged out $ unlines pkgDeps + putSuccess $ "| Successfully computed package dependencies" collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] From git at git.haskell.org Fri Oct 27 00:45:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a target for threaded rts library. (8f9dd7e) Message-ID: <20171027004525.9DF0D3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f9dd7ed189b075faecea5224fb147b7743b16f7/ghc >--------------------------------------------------------------- commit 8f9dd7ed189b075faecea5224fb147b7743b16f7 Author: Andrey Mokhov Date: Fri Jan 29 01:07:11 2016 +0000 Add a target for threaded rts library. See #98. >--------------------------------------------------------------- 8f9dd7ed189b075faecea5224fb147b7743b16f7 src/Rules.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 31489f3..5f505b3 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -15,9 +15,10 @@ allStages = [minBound ..] -- | 'need' all top-level build targets generateTargets :: Rules () generateTargets = action $ do - targets <- fmap concat (traverse targetsForStage allStages) - rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla - need $ targets ++ installTargets ++ [ rtsLib ] + targets <- fmap concat (traverse targetsForStage allStages) + rtsLib <- pkgLibraryFile Stage1 rts "rts" vanilla + rtsThrLib <- pkgLibraryFile Stage1 rts "rts" threaded + need $ targets ++ installTargets ++ [ rtsLib, rtsThrLib ] targetsForStage :: Stage -> Action [String] targetsForStage stage = do From git at git.haskell.org Fri Oct 27 00:45:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:45:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: base: Implement file locking in terms of POSIX locks (1cd7473) Message-ID: <20171027004526.D92883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1cd7473f8e800a99e95180579480a0e62e98040b/ghc >--------------------------------------------------------------- commit 1cd7473f8e800a99e95180579480a0e62e98040b Author: Ben Gamari Date: Thu Oct 26 10:40:11 2017 -0400 base: Implement file locking in terms of POSIX locks Hopefully these are more robust to NFS malfunction than BSD flock-style locks. See #13945. >--------------------------------------------------------------- 1cd7473f8e800a99e95180579480a0e62e98040b libraries/base/GHC/IO/Handle/Lock.hsc | 74 ++++++++++++++++++++++++++++++++++- libraries/base/configure.ac | 7 +++- 2 files changed, 78 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/IO/Handle/Lock.hsc b/libraries/base/GHC/IO/Handle/Lock.hsc index daf407c..b0a3449 100644 --- a/libraries/base/GHC/IO/Handle/Lock.hsc +++ b/libraries/base/GHC/IO/Handle/Lock.hsc @@ -104,7 +104,76 @@ hUnlock = unlockImpl ---------------------------------------- -#if HAVE_FLOCK +#if HAVE_OFD_LOCKING +-- Linux open file descriptor locking. +-- +-- We prefer this over BSD locking (e.g. flock) since the latter appears to +-- break in some NFS configurations. Note that we intentionally do not try to +-- use ordinary POSIX file locking due to its peculiar semantics under +-- multi-threaded environments. + +foreign import ccall interruptible "fcntl" + c_fcntl :: CInt -> CInt -> Ptr () -> IO CInt + +data FLock = FLock { l_type :: CShort + , l_whence :: CShort + , l_start :: COff + , l_len :: COff + , l_pid :: CPid + } + +instance Storable FLock where + sizeOf _ = #{size flock} + alignment _ = #{alignment flock} + poke ptr x = do + fillBytes ptr 0 (sizeOf x) + #{poke flock, l_type} ptr (l_type x) + #{poke flock, l_whence} ptr (l_whence x) + #{poke flock, l_start} ptr (l_start x) + #{poke flock, l_len} ptr (l_len x) + #{poke flock, l_pid} ptr (l_pid x) + peek ptr = do + FLock <$> #{peek flock, l_type} ptr + <*> #{peek flock, l_whence} ptr + <*> #{peek flock, l_start} ptr + <*> #{peek flock, l_len} ptr + <*> #{peek flock, l_pid} ptr + +lockImpl :: Handle -> String -> LockMode -> Bool -> IO Bool +lockImpl h ctx mode block = do + FD{fdFD = fd} <- handleToFd h + with flock $ \flock_ptr -> fix $ \retry -> do + ret <- with flock $ fcntl fd mode flock_ptr + case ret of + 0 -> return True + _ -> getErrno >>= \errno -> if + | not block && errno == eWOULDBLOCK -> return False + | errno == eINTR -> retry + | otherwise -> ioException $ errnoToIOError ctx errno (Just h) Nothing + where + flock = FLock { l_type = case mode of + SharedLock -> #{const F_RDLCK} + ExclusiveLock -> #{const F_WRLCK} + , l_whence = #{const SEEK_SET} + , l_start = 0 + , l_len = 0 + } + mode + | block = #{const F_SETLKW} + | otherwise = #{const F_SETLK} + +unlockImpl :: Handle -> IO () +unlockImpl h = do + FD{fdFD = fd} <- handleToFd h + let flock = FLock { l_type = #{const F_UNLCK} + , l_whence = #{const SEEK_SET} + , l_start = 0 + , l_len = 0 + } + throwErrnoIfMinus1_ "hUnlock" + $ with flock $ c_fcntl fd #{const F_SETLK} + +#elif HAVE_FLOCK lockImpl :: Handle -> String -> LockMode -> Bool -> IO Bool lockImpl h ctx mode block = do @@ -113,7 +182,8 @@ lockImpl h ctx mode block = do fix $ \retry -> c_flock fd flags >>= \case 0 -> return True _ -> getErrno >>= \errno -> if - | not block && errno == eWOULDBLOCK -> return False + | not block + , errno == eAGAIN || errno == eACCES -> return False | errno == eINTR -> retry | otherwise -> ioException $ errnoToIOError ctx errno (Just h) Nothing where diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index af041a7..69ea800 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -69,7 +69,12 @@ if test "$ac_cv_header_poll_h" = yes && test "$ac_cv_func_poll" = yes; then AC_DEFINE([HAVE_POLL], [1], [Define if you have poll support.]) fi -#flock +# Linux open file description locks +AC_CHECK_DECL([F_OFD_SETLK], [ + AC_DEFINE([HAVE_OFD_LOCKING], [1], [Define if you have open file descriptor lock support.]) +]) + +# flock AC_CHECK_FUNCS([flock]) if test "$ac_cv_header_sys_file_h" = yes && test "$ac_cv_func_flock" = yes; then AC_DEFINE([HAVE_FLOCK], [1], [Define if you have flock support.]) From git at git.haskell.org Fri Oct 27 00:58:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Call GMP's configure in gmpBuildPath. (a228b96) Message-ID: <20171027005811.851E23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a228b96c3ab519968384ff1a5f88353225ff3544/ghc >--------------------------------------------------------------- commit a228b96c3ab519968384ff1a5f88353225ff3544 Author: Andrey Mokhov Date: Thu May 5 03:01:40 2016 +0100 Call GMP's configure in gmpBuildPath. >--------------------------------------------------------------- a228b96c3ab519968384ff1a5f88353225ff3544 src/Rules/Gmp.hs | 54 ++++++++++++++++++++------------------ src/Settings/Builders/Configure.hs | 2 +- 2 files changed, 30 insertions(+), 26 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1e962ec..cceda8e 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -52,8 +52,7 @@ gmpRules = do -- TODO: split into multiple rules gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - liftIO $ removeFiles gmpBuildPath ["//*"] - createDirectory $ takeDirectory gmpLibraryH + removeDirectoryIfExists gmpBuildPath -- We don't use system GMP on Windows. TODO: fix? windows <- windowsHost @@ -62,6 +61,7 @@ gmpRules = do [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" + createDirectory $ takeDirectory gmpLibraryH copyFile gmpLibraryFakeH gmpLibraryH else do putBuild "| No GMP library/framework detected; in tree GMP will be built" @@ -76,34 +76,38 @@ gmpRules = do ++ "(found: " ++ show tarballs ++ ")." need tarballs - build $ Target gmpContext Tar tarballs [gmpBuildPath] - - forM_ gmpPatches $ \src -> do - let patch = takeFileName src - patchPath = gmpBuildPath -/- patch - copyFile src patchPath - applyPatch gmpBuildPath patch - - let filename = dropExtension . dropExtension . takeFileName $ head tarballs - suffix = "-nodoc-patched" - unless (suffix `isSuffixOf` filename) $ - putError $ "gmpRules: expected suffix " ++ suffix - ++ " (found: " ++ filename ++ ")." - let libName = take (length filename - length suffix) filename - libPath = gmpBuildPath -/- "lib" - - moveDirectory (gmpBuildPath -/- libName) libPath + withTempDir $ \dir -> do + let tmp = unifyPath dir + build $ Target gmpContext Tar tarballs [tmp] + + forM_ gmpPatches $ \src -> do + let patch = takeFileName src + patchPath = tmp -/- patch + copyFile src patchPath + applyPatch tmp patch + + let filename = dropExtension . dropExtension . takeFileName + $ head tarballs + suffix = "-nodoc-patched" + unless (suffix `isSuffixOf` filename) $ + putError $ "gmpRules: expected suffix " ++ suffix + ++ " (found: " ++ filename ++ ")." + let libName = take (length filename - length suffix) filename + + moveDirectory (tmp -/- libName) gmpBuildPath env <- configureEnvironment buildWithCmdOptions env $ - Target gmpContext (Configure libPath) - [libPath -/- "Makefile.in"] [libPath -/- "Makefile"] + Target gmpContext (Configure gmpBuildPath) + [gmpBuildPath -/- "Makefile.in"] + [gmpBuildPath -/- "Makefile"] - runMake libPath ["MAKEFLAGS="] + runMake gmpBuildPath ["MAKEFLAGS="] - copyFile (libPath -/- "gmp.h") gmpLibraryInTreeH - copyFile (libPath -/- "gmp.h") gmpLibraryH - moveFile (libPath -/- ".libs/libgmp.a") gmpLibrary + createDirectory $ takeDirectory gmpLibraryH + copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH + copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH + moveFile (gmpBuildPath -/- ".libs/libgmp.a") gmpLibrary createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 45bca37..813b79d 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -17,7 +17,7 @@ configureArgs = mconcat , arg $ "--enable-shared=no" -- TODO: add support for yes , arg $ "--host=" ++ targetPlatform ] - , builder (Configure $ gmpBuildPath -/- "lib") ? do + , builder (Configure gmpBuildPath) ? do hostPlatform <- getSetting HostPlatform buildPlatform <- getSetting BuildPlatform mconcat [ arg $ "--enable-shared=no" From git at git.haskell.org Fri Oct 27 00:58:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor refactoring: re-export Context and GHC from Expression (241ceff) Message-ID: <20171027005827.9A4C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/241cefff1dfeb0729640996609f25c944b06bf38/ghc >--------------------------------------------------------------- commit 241cefff1dfeb0729640996609f25c944b06bf38 Author: Andrey Mokhov Date: Mon Aug 28 18:12:39 2017 +0100 Minor refactoring: re-export Context and GHC from Expression >--------------------------------------------------------------- 241cefff1dfeb0729640996609f25c944b06bf38 src/Expression.hs | 15 +++++++-------- src/Rules.hs | 2 -- src/Rules/Data.hs | 1 - src/Rules/Generate.hs | 2 -- src/Rules/Install.hs | 2 -- src/Rules/Library.hs | 1 - src/Rules/Program.hs | 1 - src/Rules/Test.hs | 1 - src/Rules/Wrappers.hs | 2 -- src/Settings.hs | 2 -- src/Settings/Builders/Common.hs | 4 ---- src/Settings/Default.hs | 1 - src/Settings/Packages/Base.hs | 1 - src/Settings/Packages/Cabal.hs | 1 - src/Settings/Packages/Compiler.hs | 1 - src/Settings/Packages/Ghc.hs | 2 -- src/Settings/Packages/GhcCabal.hs | 1 - src/Settings/Packages/GhcPkg.hs | 1 - src/Settings/Packages/GhcPrim.hs | 1 - src/Settings/Packages/Ghci.hs | 1 - src/Settings/Packages/Haddock.hs | 1 - src/Settings/Packages/Haskeline.hs | 2 -- src/Settings/Packages/IntegerGmp.hs | 1 - src/Settings/Packages/Rts.hs | 2 -- src/Settings/Packages/RunGhc.hs | 1 - src/Utilities.hs | 1 - 26 files changed, 7 insertions(+), 44 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 241cefff1dfeb0729640996609f25c944b06bf38 From git at git.haskell.org Fri Oct 27 00:58:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename to Hadrian. (3be1a41) Message-ID: <20171027005819.294DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3be1a417e326d35b5756a056e93ce2b828bf8790/ghc >--------------------------------------------------------------- commit 3be1a417e326d35b5756a056e93ce2b828bf8790 Author: Andrey Mokhov Date: Thu May 5 03:16:20 2016 +0100 Rename to Hadrian. >--------------------------------------------------------------- 3be1a417e326d35b5756a056e93ce2b828bf8790 src/Base.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 5e66a27..625dfd8 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -45,11 +45,11 @@ import System.IO -- TODO: reexport Stage, etc.? -- Build system files and paths -shakePath :: FilePath -shakePath = "hadrian" +hadrianPath :: FilePath +hadrianPath = "hadrian" configPath :: FilePath -configPath = shakePath -/- "cfg" +configPath = hadrianPath -/- "cfg" configFile :: FilePath configFile = configPath -/- "system.config" @@ -57,7 +57,7 @@ configFile = configPath -/- "system.config" -- | Path to source files of the build system, e.g. this file is located at -- sourcePath -/- "Base.hs". We use this to `need` some of the source files. sourcePath :: FilePath -sourcePath = shakePath -/- "src" +sourcePath = hadrianPath -/- "src" -- TODO: move to buildRootPath, see #113 programInplacePath :: FilePath From git at git.haskell.org Fri Oct 27 00:58:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop removeDirectoryIfExists. (ad53022) Message-ID: <20171027005830.BD1903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ad53022e5f3da17d8b744b922c32756dba6408d2/ghc >--------------------------------------------------------------- commit ad53022e5f3da17d8b744b922c32756dba6408d2 Author: Andrey Mokhov Date: Thu May 5 03:52:19 2016 +0100 Drop removeDirectoryIfExists. See #163. >--------------------------------------------------------------- ad53022e5f3da17d8b744b922c32756dba6408d2 src/Base.hs | 7 +------ src/Oracles/PackageDb.hs | 2 +- src/Rules/Actions.hs | 3 ++- src/Rules/Clean.hs | 16 ++++++---------- src/Rules/Gmp.hs | 2 +- 5 files changed, 11 insertions(+), 19 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 625dfd8..ccadd22 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,7 +23,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - removeFileIfExists, removeDirectoryIfExists, matchVersionedFilePath + removeFileIfExists, matchVersionedFilePath ) where import Control.Applicative @@ -176,11 +176,6 @@ lookupAll (x:xs) (y:ys) = case compare x (fst y) of removeFileIfExists :: FilePath -> Action () removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f --- | Remove a directory that doesn't necessarily exist -removeDirectoryIfExists :: FilePath -> Action () -removeDirectoryIfExists d = - liftIO . whenM (IO.doesDirectoryExist d) $ IO.removeDirectoryRecursive d - -- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the -- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: diff --git a/src/Oracles/PackageDb.hs b/src/Oracles/PackageDb.hs index b644989..760f2a7 100644 --- a/src/Oracles/PackageDb.hs +++ b/src/Oracles/PackageDb.hs @@ -17,6 +17,6 @@ packageDbOracle = void $ let dir = packageDbDirectory stage file = dir -/- "package.cache" unlessM (liftIO $ IO.doesFileExist file) $ do - removeDirectoryIfExists dir + removeDirectory dir build $ Target (vanillaContext stage ghcPkg) (GhcPkg stage) [] [dir] putSuccess $ "| Successfully initialised " ++ dir diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 32d2544..25bf72e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -99,10 +99,11 @@ createDirectory dir = do putBuild $ "| Create directory " ++ dir liftIO $ IO.createDirectoryIfMissing True dir +-- | Remove a directory that doesn't necessarily exist. removeDirectory :: FilePath -> Action () removeDirectory dir = do putBuild $ "| Remove directory " ++ dir - removeDirectoryIfExists dir + liftIO . whenM (IO.doesDirectoryExist dir) $ IO.removeDirectoryRecursive dir -- Note, the source directory is untracked copyDirectory :: FilePath -> FilePath -> Action () diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index ca5c062..f615e54 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -3,24 +3,20 @@ module Rules.Clean (cleanRules) where import Base import Context import Package +import Rules.Actions import Rules.Generate import Settings.Packages import Settings.Paths import Settings.User import Stage -clean :: FilePath -> Action () -clean dir = do - putBuild $ "| Remove files in " ++ dir ++ "..." - removeDirectoryIfExists dir - cleanRules :: Rules () cleanRules = do "clean" ~> do - forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage) - clean programInplacePath - clean "inplace/lib" - clean derivedConstantsPath + forM_ [Stage0 ..] $ removeDirectory . (buildRootPath -/-) . stageString + removeDirectory programInplacePath + removeDirectory "inplace/lib" + removeDirectory derivedConstantsPath forM_ includesDependencies $ \file -> do putBuild $ "| Remove " ++ file removeFileIfExists file @@ -28,7 +24,7 @@ cleanRules = do forM_ knownPackages $ \pkg -> forM_ [Stage0 ..] $ \stage -> do let dir = pkgPath pkg -/- contextDirectory (vanillaContext stage pkg) - removeDirectoryIfExists dir + quietly $ removeDirectory dir putBuild $ "| Remove Hadrian files..." removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index d98bc3b..9cec3a3 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -52,7 +52,7 @@ gmpRules = do -- TODO: split into multiple rules gmpLibraryH %> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] - removeDirectoryIfExists gmpBuildPath + removeDirectory gmpBuildPath -- We don't use system GMP on Windows. TODO: fix? windows <- windowsHost From git at git.haskell.org Fri Oct 27 00:58:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision of install stages (9dcd2a6) Message-ID: <20171027005831.1AA813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dcd2a6fd2a4799ec807af2418f52ab90f164273/ghc >--------------------------------------------------------------- commit 9dcd2a6fd2a4799ec807af2418f52ab90f164273 Author: Andrey Mokhov Date: Tue Aug 29 00:28:55 2017 +0100 Minor revision of install stages See #403 >--------------------------------------------------------------- 9dcd2a6fd2a4799ec807af2418f52ab90f164273 src/GHC.hs | 20 +++++++++---- src/Rules/Install.hs | 79 ++++++++++++++++++++++++--------------------------- src/Rules/Program.hs | 15 ++++++---- src/Rules/Wrappers.hs | 7 ++--- src/Settings.hs | 9 +----- 5 files changed, 64 insertions(+), 66 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9dcd2a6fd2a4799ec807af2418f52ab90f164273 From git at git.haskell.org Fri Oct 27 00:58:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix wrapper build (090e00a) Message-ID: <20171027005834.C7C273A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/090e00af68efad88b82ae94e8f7a3a97375b6054/ghc >--------------------------------------------------------------- commit 090e00af68efad88b82ae94e8f7a3a97375b6054 Author: Andrey Mokhov Date: Tue Aug 29 00:46:19 2017 +0100 Fix wrapper build See #403 >--------------------------------------------------------------- 090e00af68efad88b82ae94e8f7a3a97375b6054 src/Rules/Program.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index c8a725e..b13f8a2 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -17,7 +17,7 @@ import Utilities -- TODO: Drop way in build rule generation? buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do - let installStage = do + let installStage = if package == ghc then return stage else do stages <- installStages package case stages of [s] -> return s @@ -33,7 +33,7 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do -- Some binaries in inplace/bin are wrapped inplaceBinPath -/- programName context <.> exe %> \bin -> do context' <- programContext stage package - binStage <- if package == ghc then return stage else installStage + binStage <- installStage buildBinaryAndWrapper rs (context' { stage = binStage }) bin inplaceLibBinPath -/- programName context <.> exe %> \bin -> do From git at git.haskell.org Fri Oct 27 00:58:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Base.removeFileIfExists to Rules.Actions.removeFile. (658d373) Message-ID: <20171027005834.872543A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/658d373c5b823792758e7d3ccb0577b6ecb24c82/ghc >--------------------------------------------------------------- commit 658d373c5b823792758e7d3ccb0577b6ecb24c82 Author: Andrey Mokhov Date: Thu May 5 03:59:50 2016 +0100 Move Base.removeFileIfExists to Rules.Actions.removeFile. See #163. >--------------------------------------------------------------- 658d373c5b823792758e7d3ccb0577b6ecb24c82 src/Base.hs | 7 +------ src/Rules/Actions.hs | 8 +++++++- src/Rules/Clean.hs | 4 +--- src/Rules/Dependencies.hs | 2 +- src/Rules/Library.hs | 2 +- 5 files changed, 11 insertions(+), 12 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index ccadd22..a26fea1 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -23,7 +23,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - removeFileIfExists, matchVersionedFilePath + matchVersionedFilePath ) where import Control.Applicative @@ -39,7 +39,6 @@ import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI -import qualified System.Directory as IO import System.IO -- TODO: reexport Stage, etc.? @@ -172,10 +171,6 @@ lookupAll (x:xs) (y:ys) = case compare x (fst y) of EQ -> Just (snd y) : lookupAll xs (y:ys) GT -> lookupAll (x:xs) ys --- | Remove a file that doesn't necessarily exist -removeFileIfExists :: FilePath -> Action () -removeFileIfExists f = liftIO . whenM (IO.doesFileExist f) $ IO.removeFile f - -- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the -- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string -- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 25bf72e..9910ce5 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,6 +1,6 @@ module Rules.Actions ( build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, - createDirectory, removeDirectory, copyDirectory, moveDirectory, + removeFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, applyPatch, fixFile, runMake, runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable ) where @@ -94,6 +94,12 @@ moveFile source target = do putProgressInfo $ renderAction "Move file" source target liftIO $ IO.renameFile source target +-- | Remove a file that doesn't necessarily exist. +removeFile :: FilePath -> Action () +removeFile file = do + putBuild $ "| Remove file " ++ file + liftIO . whenM (IO.doesFileExist file) $ IO.removeFile file + createDirectory :: FilePath -> Action () createDirectory dir = do putBuild $ "| Create directory " ++ dir diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index f615e54..613073a 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -17,9 +17,7 @@ cleanRules = do removeDirectory programInplacePath removeDirectory "inplace/lib" removeDirectory derivedConstantsPath - forM_ includesDependencies $ \file -> do - putBuild $ "| Remove " ++ file - removeFileIfExists file + forM_ includesDependencies removeFile putBuild $ "| Remove files generated by ghc-cabal..." forM_ knownPackages $ \pkg -> forM_ [Stage0 ..] $ \stage -> do diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 9059b3d..f5d781a 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -29,7 +29,7 @@ buildPackageDependencies rs context at Context {..} = then writeFileChanged out "" else buildWithResources rs $ Target context (Ghc FindDependencies stage) srcs [out] - removeFileIfExists $ out <.> "bak" + removeFile $ out <.> "bak" -- TODO: don't accumulate *.deps into .dependencies path -/- ".dependencies" %> \out -> do diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 8e09162..2b90d1f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -22,7 +22,7 @@ buildPackageLibrary context at Context {..} = do -- TODO: handle dynamic libraries matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do - removeFileIfExists a + removeFile a cSrcs <- cSources context hSrcs <- hSources context From git at git.haskell.org Fri Oct 27 00:58:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Show output of boot and configure. (72cbd44) Message-ID: <20171027005838.401E43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72cbd44066d9a9e30c5c9613884d4f778afe42e5/ghc >--------------------------------------------------------------- commit 72cbd44066d9a9e30c5c9613884d4f778afe42e5 Author: Andrey Mokhov Date: Thu May 5 04:22:57 2016 +0100 Show output of boot and configure. See #234. >--------------------------------------------------------------- 72cbd44066d9a9e30c5c9613884d4f778afe42e5 src/Rules/Actions.hs | 2 +- src/Rules/Configure.hs | 11 ++++------- 2 files changed, 5 insertions(+), 8 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9910ce5..a312ce9 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -62,7 +62,7 @@ customBuild rs opts target at Target {..} = do need [dir -/- "configure"] -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" - cmd Shell (EchoStdout False) [Cwd dir] [path] (env:opts) argList + cmd Shell [Cwd dir] [path] (env:opts) argList HsCpp -> captureStdout target path argList GenApply -> captureStdout target path argList diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index d1c7cf2..44ed75c 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -1,6 +1,6 @@ module Rules.Configure (configureRules) where -import qualified System.Info +import qualified System.Info as System import Base import Builder @@ -22,12 +22,9 @@ configureRules = do ++ "--skip-configure flag." else do -- We cannot use windowsHost here due to a cyclic dependency. - when (System.Info.os == "mingw32") $ do + when (System.os == "mingw32") $ do putBuild "| Checking for Windows tarballs..." - quietly $ cmd [ "bash" - , "mk/get-win32-tarballs.sh" - , "download" - , System.Info.arch ] + quietly $ cmd ["bash mk/get-win32-tarballs.sh download", System.arch] let srcs = map (<.> "in") outs context = vanillaContext Stage0 compiler need srcs @@ -41,4 +38,4 @@ configureRules = do else do need ["configure.ac"] putBuild "| Running boot..." - quietly $ cmd (EchoStdout False) "perl boot" + quietly $ cmd "perl boot" From git at git.haskell.org Fri Oct 27 00:58:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor program build rules (7a5c384) Message-ID: <20171027005838.7E6CE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67/ghc >--------------------------------------------------------------- commit 7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67 Author: Andrey Mokhov Date: Tue Aug 29 04:02:10 2017 +0100 Refactor program build rules See #403 >--------------------------------------------------------------- 7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67 src/GHC.hs | 49 +++++++++++++++++++-------------------- src/Rules.hs | 4 +++- src/Rules/Install.hs | 20 ++++++++-------- src/Rules/Program.hs | 63 ++++++++++++++++++++++++++------------------------- src/Rules/Wrappers.hs | 8 +++---- 5 files changed, 75 insertions(+), 69 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 7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67 From git at git.haskell.org Fri Oct 27 00:58:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix get-win32-tarballs command line. (32a2526) Message-ID: <20171027005842.289C03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/32a25268694276e609343dfc28361444a5fa7287/ghc >--------------------------------------------------------------- commit 32a25268694276e609343dfc28361444a5fa7287 Author: Andrey Mokhov Date: Thu May 5 04:25:47 2016 +0100 Fix get-win32-tarballs command line. >--------------------------------------------------------------- 32a25268694276e609343dfc28361444a5fa7287 src/Rules/Configure.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index 44ed75c..d36542a 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -24,7 +24,7 @@ configureRules = do -- We cannot use windowsHost here due to a cyclic dependency. when (System.os == "mingw32") $ do putBuild "| Checking for Windows tarballs..." - quietly $ cmd ["bash mk/get-win32-tarballs.sh download", System.arch] + quietly $ cmd ["bash", "mk/get-win32-tarballs.sh", "download", System.arch] let srcs = map (<.> "in") outs context = vanillaContext Stage0 compiler need srcs From git at git.haskell.org Fri Oct 27 00:58:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix wrapper build rules (9da5e17) Message-ID: <20171027005842.66D7B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9da5e17c26e1c9d256052fa065e8c331635b4c5b/ghc >--------------------------------------------------------------- commit 9da5e17c26e1c9d256052fa065e8c331635b4c5b Author: Andrey Mokhov Date: Tue Aug 29 10:23:52 2017 +0100 Fix wrapper build rules See #403 >--------------------------------------------------------------- 9da5e17c26e1c9d256052fa065e8c331635b4c5b src/Rules/Program.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 13bfd34..0211cfe 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -14,6 +14,7 @@ import Settings.Packages.Rts import Target import Utilities +-- | TODO: Drop code duplication buildProgram :: [(Resource, Int)] -> Package -> Rules () buildProgram rs package = do forM_ [Stage0 ..] $ \stage -> do @@ -25,11 +26,19 @@ buildProgram rs package = do buildBinaryAndWrapper rs context' bin -- Rules for the GHC package, which is built 'inplace' - when (package == ghc) $ + when (package == ghc) $ do inplaceBinPath -/- programName context <.> exe %> \bin -> do context' <- programContext stage package buildBinaryAndWrapper rs context' bin + inplaceLibBinPath -/- programName context <.> exe %> \bin -> do + context' <- programContext stage package + buildBinary rs context' bin + + inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> do + context' <- programContext stage package + buildBinary rs context' bin + -- Rules for other programs built in inplace directories when (package /= ghc) $ do let context0 = vanillaContext Stage0 package -- TODO: get rid of context0 From git at git.haskell.org Fri Oct 27 00:58:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move decode/encodeModule to Oracles.ModuleFiles. (9c45e4d) Message-ID: <20171027005846.3DE2F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c45e4df1b88c2f726c84a651cb45b8e40f5b7c2/ghc >--------------------------------------------------------------- commit 9c45e4df1b88c2f726c84a651cb45b8e40f5b7c2 Author: Andrey Mokhov Date: Thu May 5 04:56:09 2016 +0100 Move decode/encodeModule to Oracles.ModuleFiles. >--------------------------------------------------------------- 9c45e4df1b88c2f726c84a651cb45b8e40f5b7c2 src/Base.hs | 18 +----------------- src/Oracles/ModuleFiles.hs | 17 ++++++++++++++++- src/Rules/Selftest.hs | 1 + 3 files changed, 18 insertions(+), 18 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index a26fea1..1fcbae7 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,8 +22,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, - decodeModule, encodeModule, unifyPath, (-/-), versionToInt, - matchVersionedFilePath + unifyPath, (-/-), versionToInt, matchVersionedFilePath ) where import Control.Applicative @@ -84,21 +83,6 @@ versionToInt s = major * 1000 + minor * 10 + patch where [major, minor, patch] = map read . words $ replaceEq '.' ' ' s --- | Given a module name extract the directory and file name, e.g.: --- --- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") --- > decodeModule "Prelude" == ("./", "Prelude") -decodeModule :: String -> (FilePath, String) -decodeModule = splitFileName . replaceEq '.' '/' - --- | Given the directory and file name find the corresponding module name, e.g.: --- --- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" --- > encodeModule "./" "Prelude" == "Prelude" --- > uncurry encodeModule (decodeModule name) == name -encodeModule :: FilePath -> String -> String -encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file - -- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 70cf983..652eb9a 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} module Oracles.ModuleFiles ( - findGenerator, haskellSources, moduleFilesOracle + decodeModule, encodeModule, findGenerator, haskellSources, moduleFilesOracle ) where import qualified Data.HashMap.Strict as Map @@ -26,6 +26,21 @@ determineBuilder file = case takeExtension file of ".hsc" -> Just Hsc2Hs _ -> Nothing +-- | Given a module name extract the directory and file name, e.g.: +-- +-- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") +-- > decodeModule "Prelude" == ("./", "Prelude") +decodeModule :: String -> (FilePath, String) +decodeModule = splitFileName . replaceEq '.' '/' + +-- | Given the directory and file name find the corresponding module name, e.g.: +-- +-- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" +-- > encodeModule "./" "Prelude" == "Prelude" +-- > uncurry encodeModule (decodeModule name) == name +encodeModule :: FilePath -> String -> String +encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file + -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) -- ".build/stage1/compiler/build/Lexer.hs" diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f549b0f..8037682 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,6 +6,7 @@ import Development.Shake import Test.QuickCheck import Base +import Oracles.ModuleFiles (decodeModule, encodeModule) import Settings.Builders.Ar (chunksOfSize) import Way From git at git.haskell.org Fri Oct 27 00:58:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dll-split (12e7d5f) Message-ID: <20171027005849.CAAD63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12e7d5fc30e3776c29f3aba16985c72888f1a109/ghc >--------------------------------------------------------------- commit 12e7d5fc30e3776c29f3aba16985c72888f1a109 Author: Andrey Mokhov Date: Wed Aug 30 02:13:03 2017 +0100 Drop dll-split See #404 >--------------------------------------------------------------- 12e7d5fc30e3776c29f3aba16985c72888f1a109 src/GHC.hs | 17 +++++++---------- src/Rules.hs | 4 ++-- 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 7a9ff560..554cdae 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -2,7 +2,7 @@ module GHC ( -- * GHC packages array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, - compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, + compiler, containers, deepseq, deriveConstants, directory, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, @@ -30,13 +30,12 @@ import Oracles.Setting ghcPackages :: [Package] ghcPackages = [ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes - , compiler, containers, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal - , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs - , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi - , mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm - , templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix - , win32, xhtml ] + , compiler, containers, deepseq, deriveConstants, directory, filepath + , genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact + , ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc + , hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, parallel + , pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo + , text, time, touchy, transformers, unlit, unix, win32, xhtml ] -- TODO: Optimise by switching to sets of packages. isGhcPackage :: Package -> Bool @@ -55,7 +54,6 @@ containers = hsLib "containers" deepseq = hsLib "deepseq" deriveConstants = hsUtil "deriveConstants" directory = hsLib "directory" -dllSplit = hsUtil "dll-split" filepath = hsLib "filepath" genapply = hsUtil "genapply" genprimopcode = hsUtil "genprimopcode" @@ -144,7 +142,6 @@ stage0Packages = do , compareSizes , compiler , deriveConstants - , dllSplit , genapply , genprimopcode , ghc diff --git a/src/Rules.hs b/src/Rules.hs index 09610d7..fcf3f65 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -126,5 +126,5 @@ oracleRules = do Oracles.ModuleFiles.moduleFilesOracle programsStage1Only :: [Package] -programsStage1Only = [ deriveConstants, dllSplit, genapply, genprimopcode, ghc - , ghcCabal, ghcPkg, hp2ps, hpc, hsc2hs, runGhc ] +programsStage1Only = [ deriveConstants, genapply, genprimopcode, ghc, ghcCabal + , ghcPkg, hp2ps, hpc, hsc2hs, runGhc ] From git at git.haskell.org Fri Oct 27 00:58:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move GMP paths to Settings.Paths. (a88253a) Message-ID: <20171027005849.E13D33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a88253a92b436358af15ab6ff5c99b5270ed6024/ghc >--------------------------------------------------------------- commit a88253a92b436358af15ab6ff5c99b5270ed6024 Author: Andrey Mokhov Date: Thu May 5 05:15:22 2016 +0100 Move GMP paths to Settings.Paths. >--------------------------------------------------------------- a88253a92b436358af15ab6ff5c99b5270ed6024 src/Rules/Generate.hs | 1 - src/Rules/Gmp.hs | 11 +---------- src/Rules/Library.hs | 1 - src/Settings/Paths.hs | 26 +++++++++++++++++++------- 4 files changed, 20 insertions(+), 19 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8d04e8d..78326dd 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -18,7 +18,6 @@ import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Oracles.ModuleFiles import Rules.Actions -import Rules.Gmp import Rules.Libffi import Settings import Target hiding (builder, context) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 9cec3a3..2de1878 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,4 +1,4 @@ -module Rules.Gmp (gmpRules, gmpBuildPath, gmpObjects, gmpLibraryH) where +module Rules.Gmp (gmpRules) where import Base import Expression @@ -16,18 +16,9 @@ gmpBase = "libraries/integer-gmp/gmp" gmpContext :: Context gmpContext = vanillaContext Stage1 integerGmp -gmpObjects :: FilePath -gmpObjects = gmpBuildPath -/- "objs" - -gmpLibrary :: FilePath -gmpLibrary = gmpBuildPath -/- "libgmp.a" - gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" -gmpLibraryH :: FilePath -gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" - gmpLibraryFakeH :: FilePath gmpLibraryFakeH = gmpBase -/- "ghc-gmp.h" diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 2b90d1f..0538e4e 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -11,7 +11,6 @@ import Expression import GHC import Oracles.PackageData import Rules.Actions -import Rules.Gmp import Settings import Target diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 01b3b16..7174a94 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,8 +1,8 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpBuildInfoPath, - packageDbDirectory, pkgConfFile, shakeFilesPath, bootPackageConstraints, - packageDependencies, libffiBuildPath + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibrary, gmpObjects, + gmpLibraryH, gmpBuildInfoPath, libffiBuildPath, shakeFilesPath, pkgConfFile, + packageDbDirectory, bootPackageConstraints, packageDependencies ) where import Base @@ -67,18 +67,30 @@ pkgFile context prefix suffix = do componentId <- pkgData $ ComponentId path return $ path ~/~ prefix ++ componentId ++ suffix --- | Build directory for in-tree libffi library. -libffiBuildPath :: FilePath -libffiBuildPath = buildRootPath -/- "stage1/libffi" - -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath gmpBuildPath = buildRootPath ~/~ "stage1/gmp" +-- | Path to the GMP library. +gmpLibrary :: FilePath +gmpLibrary = gmpBuildPath -/- "libgmp.a" + +-- | Path to the GMP library header. +gmpLibraryH :: FilePath +gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" + +-- | Path to the GMP library object files. +gmpObjects :: FilePath +gmpObjects = gmpBuildPath -/- "objs" + -- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath gmpBuildInfoPath = pkgPath integerGmp ~/~ "integer-gmp.buildinfo" +-- | Build directory for in-tree libffi library. +libffiBuildPath :: FilePath +libffiBuildPath = buildRootPath -/- "stage1/libffi" + -- TODO: move to buildRootPath, see #113 -- StageN, N > 0, share the same packageDbDirectory -- | Path to package database directory of a given 'Stage'. From git at git.haskell.org Fri Oct 27 00:58:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (de975b7) Message-ID: <20171027005846.193003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de975b7282e8bdb003297e4804b58b090b89c61d/ghc >--------------------------------------------------------------- commit de975b7282e8bdb003297e4804b58b090b89c61d Author: Andrey Mokhov Date: Wed Aug 30 01:29:03 2017 +0100 Minor revision See #403 >--------------------------------------------------------------- de975b7282e8bdb003297e4804b58b090b89c61d src/Rules/Program.hs | 54 +++++++++++++++++++++++----------------------------- 1 file changed, 24 insertions(+), 30 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 0211cfe..ba4dab0 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -21,54 +21,48 @@ buildProgram rs package = do let context = vanillaContext stage package -- Rules for programs built in 'buildRoot' - "//" ++ contextDir context -/- programName context <.> exe %> \bin -> do - context' <- programContext stage package - buildBinaryAndWrapper rs context' bin + "//" ++ contextDir context -/- programName context <.> exe %> \bin -> + buildBinaryAndWrapper rs bin =<< programContext stage package -- Rules for the GHC package, which is built 'inplace' when (package == ghc) $ do - inplaceBinPath -/- programName context <.> exe %> \bin -> do - context' <- programContext stage package - buildBinaryAndWrapper rs context' bin + inplaceBinPath -/- programName context <.> exe %> \bin -> + buildBinaryAndWrapper rs bin =<< programContext stage package - inplaceLibBinPath -/- programName context <.> exe %> \bin -> do - context' <- programContext stage package - buildBinary rs context' bin + inplaceLibBinPath -/- programName context <.> exe %> \bin -> + buildBinary rs bin =<< programContext stage package - inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> do - context' <- programContext stage package - buildBinary rs context' bin + inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> + buildBinary rs bin =<< programContext stage package -- Rules for other programs built in inplace directories when (package /= ghc) $ do let context0 = vanillaContext Stage0 package -- TODO: get rid of context0 inplaceBinPath -/- programName context0 <.> exe %> \bin -> do - stage <- installStage package -- TODO: get rid of fromJust - context <- programContext (fromJust stage) package - buildBinaryAndWrapper rs context bin + stage <- installStage package -- TODO: get rid of fromJust + buildBinaryAndWrapper rs bin =<< programContext (fromJust stage) package inplaceLibBinPath -/- programName context0 <.> exe %> \bin -> do stage <- installStage package -- TODO: get rid of fromJust context <- programContext (fromJust stage) package if package /= iservBin then -- We *normally* build only unwrapped binaries in inplace/lib/bin - buildBinary rs context bin + buildBinary rs bin context else -- Build both binary and wrapper in inplace/lib/bin for iservBin - buildBinaryAndWrapperLib rs context bin + buildBinaryAndWrapperLib rs bin context inplaceLibBinPath -/- programName context0 <.> "bin" %> \bin -> do - stage <- installStage package -- TODO: get rid of fromJust - context <- programContext (fromJust stage) package - buildBinary rs context bin + stage <- installStage package -- TODO: get rid of fromJust + buildBinary rs bin =<< programContext (fromJust stage) package -buildBinaryAndWrapperLib :: [(Resource, Int)] -> Context -> FilePath -> Action () -buildBinaryAndWrapperLib rs context bin = do +buildBinaryAndWrapperLib :: [(Resource, Int)] -> FilePath -> Context -> Action () +buildBinaryAndWrapperLib rs bin context = do windows <- windowsHost if windows - then buildBinary rs context bin -- We don't build wrappers on Windows + then buildBinary rs bin context -- We don't build wrappers on Windows else case lookup context inplaceWrappers of - Nothing -> buildBinary rs context bin -- No wrapper found + Nothing -> buildBinary rs bin context -- No wrapper found Just wrapper -> do top <- topDirectory let libdir = top -/- inplaceLibPath @@ -76,13 +70,13 @@ buildBinaryAndWrapperLib rs context bin = do need [wrappedBin] buildWrapper context wrapper bin (WrappedBinary libdir (takeFileName wrappedBin)) -buildBinaryAndWrapper :: [(Resource, Int)] -> Context -> FilePath -> Action () -buildBinaryAndWrapper rs context bin = do +buildBinaryAndWrapper :: [(Resource, Int)] -> FilePath -> Context -> Action () +buildBinaryAndWrapper rs bin context = do windows <- windowsHost if windows - then buildBinary rs context bin -- We don't build wrappers on Windows + then buildBinary rs bin context -- We don't build wrappers on Windows else case lookup context inplaceWrappers of - Nothing -> buildBinary rs context bin -- No wrapper found + Nothing -> buildBinary rs bin context -- No wrapper found Just wrapper -> do top <- topDirectory let libPath = top -/- inplaceLibPath @@ -99,8 +93,8 @@ buildWrapper context at Context {..} wrapper wrapperPath wrapped = do quote (pkgName package) ++ " (" ++ show stage ++ ")." -- TODO: Get rid of the Paths_hsc2hs.o hack. -buildBinary :: [(Resource, Int)] -> Context -> FilePath -> Action () -buildBinary rs context at Context {..} bin = do +buildBinary :: [(Resource, Int)] -> FilePath -> Context -> Action () +buildBinary rs bin context at Context {..} = do binDeps <- if stage == Stage0 && package == ghcCabal then hsSources context else do From git at git.haskell.org Fri Oct 27 00:58:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dll-split related arguments to ghc-cabal (8f5ad00) Message-ID: <20171027005854.381B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f5ad00e81b98ab84708737d24d90457250e3873/ghc >--------------------------------------------------------------- commit 8f5ad00e81b98ab84708737d24d90457250e3873 Author: Andrey Mokhov Date: Wed Aug 30 10:47:16 2017 +0100 Drop dll-split related arguments to ghc-cabal See #404 >--------------------------------------------------------------- 8f5ad00e81b98ab84708737d24d90457250e3873 src/Settings/Builders/GhcCabal.hs | 173 -------------------------------------- 1 file changed, 173 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 4fd598b..475cc65 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -18,7 +18,6 @@ ghcCabalBuilderArgs = builder GhcCabal ? do mconcat [ arg "configure" , arg =<< pkgPath <$> getPackage , arg $ top -/- path - , dll0Args , withStaged $ Ghc CompileHs , withStaged (GhcPkg Update) , bootPackageDatabaseArgs @@ -127,175 +126,3 @@ with b = do withStaged :: (Stage -> Builder) -> Args withStaged sb = with . sb =<< getStage --- This is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument; --- * otherwise, we must collapse it into one space-separated string. -dll0Args :: Args -dll0Args = do - context <- getContext - dll0 <- expr $ buildDll0 context - withGhci <- expr ghcWithInterpreter - arg . unwords . concat $ [ modules | dll0 ] - ++ [ ghciModules | dll0 && withGhci ] -- see #9552 - where - modules = [ "Annotations" - , "ApiAnnotation" - , "Avail" - , "Bag" - , "BasicTypes" - , "Binary" - , "BooleanFormula" - , "BreakArray" - , "BufWrite" - , "Class" - , "CmdLineParser" - , "CmmType" - , "CoAxiom" - , "ConLike" - , "Coercion" - , "Config" - , "Constants" - , "CoreArity" - , "CoreFVs" - , "CoreSubst" - , "CoreSyn" - , "CoreTidy" - , "CoreUnfold" - , "CoreUtils" - , "CoreSeq" - , "CoreStats" - , "CostCentre" - , "Ctype" - , "DataCon" - , "Demand" - , "Digraph" - , "DriverPhases" - , "DynFlags" - , "Encoding" - , "ErrUtils" - , "Exception" - , "ExtsCompat46" - , "FamInstEnv" - , "FastFunctions" - , "FastMutInt" - , "FastString" - , "FastTypes" - , "Fingerprint" - , "FiniteMap" - , "ForeignCall" - , "Hooks" - , "HsBinds" - , "HsDecls" - , "HsDoc" - , "HsExpr" - , "HsImpExp" - , "HsLit" - , "PlaceHolder" - , "HsPat" - , "HsSyn" - , "HsTypes" - , "HsUtils" - , "HscTypes" - , "IOEnv" - , "Id" - , "IdInfo" - , "IfaceSyn" - , "IfaceType" - , "InstEnv" - , "Kind" - , "Lexeme" - , "Lexer" - , "ListSetOps" - , "Literal" - , "Maybes" - , "MkCore" - , "MkId" - , "Module" - , "MonadUtils" - , "Name" - , "NameEnv" - , "NameSet" - , "OccName" - , "OccurAnal" - , "OptCoercion" - , "OrdList" - , "Outputable" - , "PackageConfig" - , "Packages" - , "Pair" - , "Panic" - , "PatSyn" - , "PipelineMonad" - , "Platform" - , "PlatformConstants" - , "PprCore" - , "PrelNames" - , "PrelRules" - , "Pretty" - , "PrimOp" - , "RdrName" - , "Rules" - , "Serialized" - , "SrcLoc" - , "StaticFlags" - , "StringBuffer" - , "TcEvidence" - , "TcRnTypes" - , "TcType" - , "TrieMap" - , "TyCon" - , "Type" - , "TypeRep" - , "TysPrim" - , "TysWiredIn" - , "Unify" - , "UniqFM" - , "UniqSet" - , "UniqSupply" - , "Unique" - , "Util" - , "Var" - , "VarEnv" - , "VarSet" ] - ghciModules = [ "Bitmap" - , "BlockId" - , "ByteCodeAsm" - , "ByteCodeInstr" - , "ByteCodeItbls" - , "CLabel" - , "Cmm" - , "CmmCallConv" - , "CmmExpr" - , "CmmInfo" - , "CmmMachOp" - , "CmmNode" - , "CmmSwitch" - , "CmmUtils" - , "CodeGen.Platform" - , "CodeGen.Platform.ARM" - , "CodeGen.Platform.ARM64" - , "CodeGen.Platform.NoRegs" - , "CodeGen.Platform.PPC" - , "CodeGen.Platform.PPC_Darwin" - , "CodeGen.Platform.SPARC" - , "CodeGen.Platform.X86" - , "CodeGen.Platform.X86_64" - , "FastBool" - , "InteractiveEvalTypes" - , "MkGraph" - , "PprCmm" - , "PprCmmDecl" - , "PprCmmExpr" - , "Reg" - , "RegClass" - , "SMRep" - , "StgCmmArgRep" - , "StgCmmClosure" - , "StgCmmEnv" - , "StgCmmLayout" - , "StgCmmMonad" - , "StgCmmProf" - , "StgCmmTicky" - , "StgCmmUtils" - , "StgSyn" - , "Stream" ] From git at git.haskell.org Fri Oct 27 00:59:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision: move builder-related functionality to Builder modules (f970bfc) Message-ID: <20171027005902.AD1EE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f970bfc05c13768aa980400ff5bf7c0c4652a224/ghc >--------------------------------------------------------------- commit f970bfc05c13768aa980400ff5bf7c0c4652a224 Author: Andrey Mokhov Date: Fri Sep 1 23:31:38 2017 +0100 Minor revision: move builder-related functionality to Builder modules >--------------------------------------------------------------- f970bfc05c13768aa980400ff5bf7c0c4652a224 src/Builder.hs | 60 ++++++++++++++++++++++++++++++++++++++++++- src/Hadrian/Builder.hs | 10 +++++++- src/Utilities.hs | 70 +++----------------------------------------------- 3 files changed, 71 insertions(+), 69 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 f970bfc05c13768aa980400ff5bf7c0c4652a224 From git at git.haskell.org Fri Oct 27 00:59:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make only install target in libffi. (2249b40) Message-ID: <20171027005902.A44F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2249b4037ad429640404e79056efa4043888c9e3/ghc >--------------------------------------------------------------- commit 2249b4037ad429640404e79056efa4043888c9e3 Author: Andrey Mokhov Date: Thu May 5 05:57:20 2016 +0100 Make only install target in libffi. >--------------------------------------------------------------- 2249b4037ad429640404e79056efa4043888c9e3 src/Rules/Libffi.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0a000aa..8ca0bfc9 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -97,7 +97,7 @@ libffiRules = do Target libffiContext (Configure libffiBuildPath) [libffiMakefile <.> "in"] [libffiMakefile] - runMake libffiBuildPath ["MAKEFLAGS="] + --runMake libffiBuildPath ["MAKEFLAGS="] runMake libffiBuildPath ["MAKEFLAGS=", "install"] let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" From git at git.haskell.org Fri Oct 27 00:58:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (acf2160) Message-ID: <20171027005858.3E8F23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acf2160ea8c2ac705e32e4774c02ea7d806261f6/ghc >--------------------------------------------------------------- commit acf2160ea8c2ac705e32e4774c02ea7d806261f6 Author: Andrey Mokhov Date: Thu May 5 05:42:48 2016 +0100 Add comments. See #55. [skip ci] >--------------------------------------------------------------- acf2160ea8c2ac705e32e4774c02ea7d806261f6 src/Rules/Actions.hs | 15 +++++++++------ 1 file changed, 9 insertions(+), 6 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index a312ce9..9a9e51e 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -44,7 +44,7 @@ customBuild rs opts target at Target {..} = do argList <- interpret target getArgs verbose <- interpret target verboseCommands let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly - -- The line below forces the rule to be rerun if the args hash has changed + -- The line below forces the rule to be rerun if the args hash has changed. checkArgsHash target withResources rs $ do putInfo target @@ -76,19 +76,21 @@ customBuild rs opts target at Target {..} = do _ -> cmd [path] argList +-- | Run a builder, capture the standard output, and write it to a given file. captureStdout :: Target -> FilePath -> [String] -> Action () captureStdout target path argList = do file <- interpret target getOutput Stdout output <- cmd [path] argList writeFileChanged file output +-- | Copy a file tracking the source. copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target --- Note, moveFile cannot track the source, because it is moved. +-- | Move a file; we cannot track the source, because it is moved. moveFile :: FilePath -> FilePath -> Action () moveFile source target = do putProgressInfo $ renderAction "Move file" source target @@ -100,6 +102,7 @@ removeFile file = do putBuild $ "| Remove file " ++ file liftIO . whenM (IO.doesFileExist file) $ IO.removeFile file +-- | Create a directory if it does not already exist. createDirectory :: FilePath -> Action () createDirectory dir = do putBuild $ "| Create directory " ++ dir @@ -111,19 +114,19 @@ removeDirectory dir = do putBuild $ "| Remove directory " ++ dir liftIO . whenM (IO.doesDirectoryExist dir) $ IO.removeDirectoryRecursive dir --- Note, the source directory is untracked +-- | Copy a directory. The contents of the source directory is untracked. copyDirectory :: FilePath -> FilePath -> Action () copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd (EchoStdout False) ["cp", "-r", source, target] --- Note, the source directory is untracked +-- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target liftIO $ IO.renameDirectory source target --- Transform a given file by applying a function to its contents +-- | Transform a given file by applying a function to its contents. fixFile :: FilePath -> (String -> String) -> Action () fixFile file f = do putBuild $ "| Fix " ++ file @@ -171,7 +174,7 @@ makeExecutable file = do putBuild $ "| Make '" ++ file ++ "' executable." quietly $ cmd "chmod +x " [file] --- Print out key information about the command being executed +-- | Print out information about the command being executed. putInfo :: Target -> Action () putInfo Target {..} = putProgressInfo $ renderAction ("Run " ++ show builder ++ contextInfo) (digest inputs) (digest outputs) From git at git.haskell.org Fri Oct 27 00:58:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Gmp and Libffi rules. (f0781a7) Message-ID: <20171027005854.3C5903A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f0781a7c0c1124d7e0150298ca39b08a849ac338/ghc >--------------------------------------------------------------- commit f0781a7c0c1124d7e0150298ca39b08a849ac338 Author: Andrey Mokhov Date: Thu May 5 05:30:22 2016 +0100 Refactor Gmp and Libffi rules. >--------------------------------------------------------------- f0781a7c0c1124d7e0150298ca39b08a849ac338 src/Builder.hs | 9 ++++++++- src/Rules/Gmp.hs | 22 +++++++--------------- src/Rules/Libffi.hs | 18 +++++++----------- 3 files changed, 22 insertions(+), 27 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index fa76097..a205067 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveGeneric, LambdaCase #-} module Builder ( CompilerMode (..), Builder (..), - builderPath, getBuilderPath, specified, needBuilder + builderPath, getBuilderPath, builderEnvironment, specified, needBuilder ) where import Control.Monad.Trans.Reader @@ -134,6 +134,13 @@ builderPath builder = case builderProvenance builder of getBuilderPath :: Builder -> ReaderT a Action FilePath getBuilderPath = lift . builderPath +-- | Write a Builder's path into a given environment variable. +builderEnvironment :: String -> Builder -> Action CmdOption +builderEnvironment variable builder = do + needBuilder builder + path <- builderPath builder + return $ AddEnv variable path + specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 2de1878..1121d5d 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,6 +1,7 @@ module Rules.Gmp (gmpRules) where import Base +import Builder import Expression import GHC import Oracles.Config.Setting @@ -11,31 +12,22 @@ import Settings.Paths import Target gmpBase :: FilePath -gmpBase = "libraries/integer-gmp/gmp" +gmpBase = pkgPath integerGmp -/- "gmp" gmpContext :: Context gmpContext = vanillaContext Stage1 integerGmp +-- TODO: Noone needs this file, but we build it. Why? gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" -gmpLibraryFakeH :: FilePath -gmpLibraryFakeH = gmpBase -/- "ghc-gmp.h" - gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] --- TODO: See Libffi.hs about removing code duplication. configureEnvironment :: Action [CmdOption] -configureEnvironment = do - sequence [ builderEnv "CC" $ Cc Compile Stage1 - , builderEnv "AR" Ar - , builderEnv "NM" Nm ] - where - builderEnv var bld = do - needBuilder bld - path <- builderPath bld - return $ AddEnv var path +configureEnvironment = sequence [ builderEnvironment "CC" $ Cc Compile Stage1 + , builderEnvironment "AR" Ar + , builderEnvironment "NM" Nm ] -- TODO: we rebuild gmp every time. gmpRules :: Rules () @@ -53,7 +45,7 @@ gmpRules = do then do putBuild "| GMP library/framework detected and will be used" createDirectory $ takeDirectory gmpLibraryH - copyFile gmpLibraryFakeH gmpLibraryH + copyFile (gmpBase -/- "ghc-gmp.h") gmpLibraryH else do putBuild "| No GMP library/framework detected; in tree GMP will be built" diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 424b552..0a000aa 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,6 +1,7 @@ module Rules.Libffi (rtsBuildPath, libffiRules, libffiDependencies) where import Base +import Builder import Expression import GHC import Oracles.Config.Flag @@ -43,19 +44,14 @@ configureEnvironment = do [ cArgs , argStagedSettingList ConfCcArgs ] ldFlags <- interpretInContext libffiContext $ fromDiffExpr ldArgs - sequence [ builderEnv "CC" $ Cc Compile Stage1 - , builderEnv "CXX" $ Cc Compile Stage1 - , builderEnv "LD" Ld - , builderEnv "AR" Ar - , builderEnv "NM" Nm - , builderEnv "RANLIB" Ranlib + sequence [ builderEnvironment "CC" $ Cc Compile Stage1 + , builderEnvironment "CXX" $ Cc Compile Stage1 + , builderEnvironment "LD" Ld + , builderEnvironment "AR" Ar + , builderEnvironment "NM" Nm + , builderEnvironment "RANLIB" Ranlib , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w" , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ] - where - builderEnv var b = do - needBuilder b - path <- builderPath b - return $ AddEnv var path -- TODO: remove code duplication (need sourcePath) -- TODO: split into multiple rules From git at git.haskell.org Fri Oct 27 00:58:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:58:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out common builder-related functionality into the library (29046aa) Message-ID: <20171027005858.407BF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/29046aa3b29a26e69db1bf38015f9376bfad2ff0/ghc >--------------------------------------------------------------- commit 29046aa3b29a26e69db1bf38015f9376bfad2ff0 Author: Andrey Mokhov Date: Thu Aug 31 03:24:11 2017 +0100 Factor out common builder-related functionality into the library See #347 >--------------------------------------------------------------- 29046aa3b29a26e69db1bf38015f9376bfad2ff0 hadrian.cabal | 1 + src/Builder.hs | 127 +++++++++++++++++++++++++++++++++++++------- src/Hadrian/Builder.hs | 118 ++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Expression.hs | 9 +++- src/Hadrian/Utilities.hs | 9 +++- src/Main.hs | 4 +- src/Rules/Configure.hs | 1 + src/Rules/Install.hs | 2 +- src/Rules/Perl.hs | 3 +- src/Rules/Selftest.hs | 1 - src/Rules/SourceDist.hs | 6 +-- src/Settings/Builders/Ar.hs | 42 +-------------- src/UserSettings.hs | 8 +-- src/Utilities.hs | 117 ++++------------------------------------ 14 files changed, 266 insertions(+), 182 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 29046aa3b29a26e69db1bf38015f9376bfad2ff0 From git at git.haskell.org Fri Oct 27 00:59:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add comments. (6828f4a) Message-ID: <20171027005906.1A1763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6828f4af2d959e352415f7c6c89dd408e8409dcf/ghc >--------------------------------------------------------------- commit 6828f4af2d959e352415f7c6c89dd408e8409dcf Author: Andrey Mokhov Date: Thu May 5 13:07:07 2016 +0100 Add comments. >--------------------------------------------------------------- 6828f4af2d959e352415f7c6c89dd408e8409dcf src/Rules/Libffi.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 8ca0bfc9..20d5acf 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -97,7 +97,8 @@ libffiRules = do Target libffiContext (Configure libffiBuildPath) [libffiMakefile <.> "in"] [libffiMakefile] - --runMake libffiBuildPath ["MAKEFLAGS="] + -- The old build system did runMake libffiBuildPath ["MAKEFLAGS="] + -- TODO: Find out why. It seems redundant, so I removed it. runMake libffiBuildPath ["MAKEFLAGS=", "install"] let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" From git at git.haskell.org Fri Oct 27 00:59:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out common Ar functionality into the library (655d175) Message-ID: <20171027005906.2BB883A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/655d175354db5afb5c3519cb13672209e66e5f95/ghc >--------------------------------------------------------------- commit 655d175354db5afb5c3519cb13672209e66e5f95 Author: Andrey Mokhov Date: Sun Sep 3 00:38:06 2017 +0100 Factor out common Ar functionality into the library See #347 >--------------------------------------------------------------- 655d175354db5afb5c3519cb13672209e66e5f95 hadrian.cabal | 2 +- src/Builder.hs | 40 ++++--------------------------- src/Hadrian/Builder/Ar.hs | 57 +++++++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Utilities.hs | 17 +++++++++++++- src/Oracles/Setting.hs | 17 -------------- src/Settings/Builders/Ar.hs | 8 ------- src/Settings/Default.hs | 5 ++-- 7 files changed, 82 insertions(+), 64 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 655d175354db5afb5c3519cb13672209e66e5f95 From git at git.haskell.org Fri Oct 27 00:59:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Actions: use `mv` instead of renameDirectory (fixes #236) (d04a83f) Message-ID: <20171027005910.0F5FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d04a83ffa5a94de6215997229c6e4dc0afe21640/ghc >--------------------------------------------------------------- commit d04a83ffa5a94de6215997229c6e4dc0afe21640 Author: Michal Terepeta Date: Thu May 5 17:05:24 2016 +0200 Actions: use `mv` instead of renameDirectory (fixes #236) Implementing `moveDirectory` by calling into `renameDirectory` is problematic because it doesn't work across file-systems (e.g., a tmpfs based `/tmp`). This fixes the problem by calling into `mv` instead (similarly to what we do for `copyDirectory`). >--------------------------------------------------------------- d04a83ffa5a94de6215997229c6e4dc0afe21640 src/Rules/Actions.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 9a9e51e..fd117ae 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -124,7 +124,7 @@ copyDirectory source target = do moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target - liftIO $ IO.renameDirectory source target + quietly $ cmd (EchoStdout False) ["mv", source, target] -- | Transform a given file by applying a function to its contents. fixFile :: FilePath -> (String -> String) -> Action () From git at git.haskell.org Fri Oct 27 00:59:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ArMode to distinguish packing and unpacking of archives (46a37b1) Message-ID: <20171027005910.230B83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46a37b154ae7b749c074c32efbcfb772d40502a8/ghc >--------------------------------------------------------------- commit 46a37b154ae7b749c074c32efbcfb772d40502a8 Author: Andrey Mokhov Date: Sun Sep 3 13:31:00 2017 +0100 Add ArMode to distinguish packing and unpacking of archives >--------------------------------------------------------------- 46a37b154ae7b749c074c32efbcfb772d40502a8 src/Builder.hs | 44 ++++++++++++++------------------------- src/Hadrian/Builder/Ar.hs | 19 +++++++++++++---- src/Rules/Gmp.hs | 7 ++++--- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Default.hs | 3 ++- 7 files changed, 42 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 46a37b154ae7b749c074c32efbcfb772d40502a8 From git at git.haskell.org Fri Oct 27 00:59:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Mark as temporarily out-of-date (c3f0f40) Message-ID: <20171027005913.94F123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3f0f40954cedc37bc2d0e5c724ccd20d7fa51ed/ghc >--------------------------------------------------------------- commit c3f0f40954cedc37bc2d0e5c724ccd20d7fa51ed Author: Andrey Mokhov Date: Fri Sep 8 23:38:45 2017 +0100 Mark as temporarily out-of-date >--------------------------------------------------------------- c3f0f40954cedc37bc2d0e5c724ccd20d7fa51ed doc/user-settings.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/doc/user-settings.md b/doc/user-settings.md index 9207f7f..1898dcd 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,3 +1,6 @@ +**Note:** This document is currently out-of-date and will be fixed after +[a major refactoring](https://github.com/snowleopard/hadrian/issues/347). + # User settings You can customise Hadrian by copying the file `hadrian/src/UserSettings.hs` to From git at git.haskell.org Fri Oct 27 00:59:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #237 from michalt/movedirectory-fix/1 (e61bd40) Message-ID: <20171027005913.9B96A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e61bd4021b696a17c72c8d259adf55621f9c3959/ghc >--------------------------------------------------------------- commit e61bd4021b696a17c72c8d259adf55621f9c3959 Merge: 6828f4a d04a83f Author: Andrey Mokhov Date: Thu May 5 17:59:09 2016 +0100 Merge pull request #237 from michalt/movedirectory-fix/1 Actions: use `mv` instead of renameDirectory (fixes #236) >--------------------------------------------------------------- e61bd4021b696a17c72c8d259adf55621f9c3959 src/Rules/Actions.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 00:59:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run boot and configure via Hadrian (13f3e0c) Message-ID: <20171027005917.79F243A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13f3e0c5cb075eb22785886be439f8235009b766/ghc >--------------------------------------------------------------- commit 13f3e0c5cb075eb22785886be439f8235009b766 Author: Andrey Mokhov Date: Thu May 5 20:20:38 2016 +0100 Run boot and configure via Hadrian [skip ci] >--------------------------------------------------------------- 13f3e0c5cb075eb22785886be439f8235009b766 doc/windows.md | 3 --- 1 file changed, 3 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 7afd97c..79dfcc2 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -11,8 +11,6 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ cd ghc stack exec -- git clone git://github.com/snowleopard/hadrian stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec -- perl boot - stack exec -- bash configure --enable-tarballs-autodownload stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j The entire process should take about an hour. @@ -21,6 +19,5 @@ The entire process should take about an hour. Here are some alternatives that have been considered, but not yet tested. Use the instructions above. -* Use `hadrian/build.bat --setup` to replace `boot` and `configure`. * The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. * Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 00:59:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use --flavour=quick (da2ce2e) Message-ID: <20171027005921.7B40D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da2ce2e21529a6e9a4c2dcc8a033996bdca33be5/ghc >--------------------------------------------------------------- commit da2ce2e21529a6e9a4c2dcc8a033996bdca33be5 Author: Andrey Mokhov Date: Fri May 6 00:18:12 2016 +0100 Use --flavour=quick See #234. [skip ci] >--------------------------------------------------------------- da2ce2e21529a6e9a4c2dcc8a033996bdca33be5 doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 79dfcc2..4674ff4 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -11,9 +11,9 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ cd ghc stack exec -- git clone git://github.com/snowleopard/hadrian stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j + stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quick -The entire process should take about an hour. +The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quick` flag from the last command line (this will slow down the build to about an hour). #### Future ideas From git at git.haskell.org Fri Oct 27 01:00:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop checkApiAnnotations utility (6abcec9) Message-ID: <20171027010030.EFF1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6abcec9b1a92c1d35a15d9c01c38e6ecc06c4e87/ghc >--------------------------------------------------------------- commit 6abcec9b1a92c1d35a15d9c01c38e6ecc06c4e87 Author: Andrey Mokhov Date: Wed Sep 27 23:36:24 2017 +0100 Drop checkApiAnnotations utility See https://phabricator.haskell.org/D4039 >--------------------------------------------------------------- 6abcec9b1a92c1d35a15d9c01c38e6ecc06c4e87 src/GHC.hs | 32 +++++++++++++++----------------- 1 file changed, 15 insertions(+), 17 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 32676cd..77a63e9 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,14 +1,14 @@ {-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( -- * GHC packages - array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, - compiler, containers, deepseq, deriveConstants, directory, filepath, - genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, - ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, - hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, - parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, - terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml, - ghcPackages, isGhcPackage, defaultPackages, + array, base, binary, bytestring, cabal, compareSizes, compiler, containers, + deepseq, deriveConstants, directory, filepath, genapply, genprimopcode, ghc, + ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, + ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, + integerSimple, iservBin, libffi, mtl, parsec, parallel, pretty, primitive, + process, rts, runGhc, stm, templateHaskell, terminfo, text, time, touchy, + transformers, unlit, unix, win32, xhtml, ghcPackages, isGhcPackage, + defaultPackages, -- * Package information programName, nonCabalContext, nonHsMainPackage, autogenPath, installStage, @@ -30,13 +30,13 @@ import Oracles.Flag (crossCompiling) -- modify build default build conditions in "UserSettings". ghcPackages :: [Package] ghcPackages = - [ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes - , compiler, containers, deepseq, deriveConstants, directory, filepath - , genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact - , ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc - , hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, parallel - , pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo - , text, time, touchy, transformers, unlit, unix, win32, xhtml ] + [ array, base, binary, bytestring, cabal, compareSizes, compiler, containers + , deepseq, deriveConstants, directory, filepath, genapply, genprimopcode + , ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim + , ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp + , integerSimple, iservBin, libffi, mtl, parsec, parallel, pretty, primitive + , process, rts, runGhc, stm, templateHaskell, terminfo, text, time, touchy + , transformers, unlit, unix, win32, xhtml ] -- TODO: Optimise by switching to sets of packages. isGhcPackage :: Package -> Bool @@ -48,7 +48,6 @@ base = hsLib "base" binary = hsLib "binary" bytestring = hsLib "bytestring" cabal = hsLib "Cabal" `setPath` "libraries/Cabal/Cabal" -checkApiAnnotations = hsUtil "check-api-annotations" compareSizes = hsUtil "compareSizes" `setPath` "utils/compare_sizes" compiler = hsTop "ghc" `setPath` "compiler" containers = hsLib "containers" @@ -140,7 +139,6 @@ stage0Packages = do cross <- crossCompiling return $ [ binary , cabal - , checkApiAnnotations , compareSizes , compiler , deriveConstants From git at git.haskell.org Fri Oct 27 01:00:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to isWindows (88a7b4e) Message-ID: <20171027010034.B56783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88a7b4e31616f06ea9c0f75d3565ae11936009e0/ghc >--------------------------------------------------------------- commit 88a7b4e31616f06ea9c0f75d3565ae11936009e0 Author: Andrey Mokhov Date: Thu Sep 28 23:49:12 2017 +0100 Switch to isWindows >--------------------------------------------------------------- 88a7b4e31616f06ea9c0f75d3565ae11936009e0 src/Rules/Configure.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index 5e29116..492d91c 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -1,6 +1,6 @@ module Rules.Configure (configureRules) where -import qualified System.Info as System +import qualified System.Info.Extra as System import Base import Builder @@ -21,7 +21,7 @@ configureRules = do ++ "--skip-configure flag." else do -- We cannot use windowsHost here due to a cyclic dependency. - when (System.os == "mingw32") $ do + when System.isWindows $ do putBuild "| Checking for Windows tarballs..." quietly $ cmd ["bash", "mk/get-win32-tarballs.sh", "download", System.arch] let srcs = map (<.> "in") outs From git at git.haskell.org Fri Oct 27 01:00:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unix line endings, match Haddock comments in Settings/User.hs (3ff4183) Message-ID: <20171027010034.816B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ff4183c5741ca780fb4e4b7274b7d951430fdde/ghc >--------------------------------------------------------------- commit 3ff4183c5741ca780fb4e4b7274b7d951430fdde Author: Andrey Mokhov Date: Sun May 15 00:11:25 2016 +0100 Unix line endings, match Haddock comments in Settings/User.hs [skip ci] >--------------------------------------------------------------- 3ff4183c5741ca780fb4e4b7274b7d951430fdde doc/user-settings.md | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index dc718ed..e6b81f8 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -8,7 +8,7 @@ You can customise Hadrian by specifying user build settings in file Hadrian puts build results into `_build` directory by default, which is specified by `buildRootPath`: ```haskell --- | All build artefacts are stored in 'buildRootPath' directory. +-- | All build results are put into 'buildRootPath' directory. buildRootPath :: FilePath buildRootPath = "_build" ``` @@ -22,7 +22,7 @@ affected build rules during the next build, without requiring a full rebuild. For example, here is how to pass an extra argument `-O0` to all invocations of GHC when compiling package `cabal`: ```haskell --- | Control user-specific command line arguments. +-- | Modify default build command line arguments. userArgs :: Args userArgs = builder Ghc ? package cabal ? arg "-O0" ``` @@ -52,7 +52,7 @@ To add or remove a package from a particular build stage, use `userPackages`. As an example, below we add package `base` to Stage0 and remove package `haskeline` from Stage1: ```haskell --- | Control which packages get to be built. +-- | Modify the set of packages that are built by default in each stage. userPackages :: Packages userPackages = mconcat [ stage0 ? append [base] @@ -61,7 +61,7 @@ userPackages = mconcat If you are working on a new GHC package you need to let Hadrian know about it by setting `userKnownPackages`: ```haskell --- | Add new user-defined packages. +-- | Add user defined packages. Don't forget to add them to 'userPackages' too. userKnownPackages :: [Package] userKnownPackages = [myPackage] @@ -73,9 +73,9 @@ Note, you will also need to add `myPackage` to a specific build stage by modifyi `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting -`integerLibrary`: +`integerLibrary`. Possible values are: `integerGmp` (default) and `integerSimple`. ```haskell --- | Choose the integer library: integerGmp or integerSimple. +-- | Choose the integer library: 'integerGmp' or 'integerSimple'. integerLibrary :: Package integerLibrary = integerGmp ``` @@ -87,11 +87,11 @@ can change the default build ways using `userLibraryWays` and `userRtsWays` sett As an example, below we remove `dynamic` from the list of library ways but keep `rts` package ways unchanged: ```haskell --- | Control which ways library packages are built. +-- | Modify the set of ways in which library packages are built. userLibraryWays :: Ways userLibraryWays = remove [dynamic] --- | Control which ways the 'rts' package is built. +-- | Modify the set of ways in which the 'rts' package is built. userRtsWays :: Ways userRtsWays = mempty ``` @@ -103,8 +103,8 @@ and instead prints short human readable digests for each executed command. You can suppress this behaviour completely or partially using `verboseCommands` setting: ```haskell -- | Set to True to print full command lines during the build process. Note, --- this is a Predicate, hence you can enable verbose output for a chosen package --- only, e.g.: verboseCommands = package ghcPrim +-- this is a Predicate, hence you can enable verbose output only for certain +-- targets, e.g.: @verboseCommands = package ghcPrim at . verboseCommands :: Predicate verboseCommands = return False ``` @@ -140,7 +140,7 @@ to building split objects and Haddock documentation. splitObjects :: Predicate splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects --- | Control when to build documentation. +-- | Control when to build Haddock documentation. buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock ``` From git at git.haskell.org Fri Oct 27 01:00:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix predicate (c8725b2) Message-ID: <20171027010038.04E9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8725b225655b0d7f320cff4ebff1fb1918311f4/ghc >--------------------------------------------------------------- commit c8725b225655b0d7f320cff4ebff1fb1918311f4 Author: Andrey Mokhov Date: Sun May 15 00:14:34 2016 +0100 Fix predicate [skip ci] >--------------------------------------------------------------- c8725b225655b0d7f320cff4ebff1fb1918311f4 doc/user-settings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index e6b81f8..4624e2d 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -123,7 +123,7 @@ verboseCommands = builder (Ghc Link) verboseCommands = builder (Gcc Compile) &&^ package compiler -- Use patterns when matching files: -verboseCommands = file "//rts/sm/*" &&^ way threaded +verboseCommands = output "//rts/sm/*" &&^ way threaded -- Print all commands: verboseCommands = return True From git at git.haskell.org Fri Oct 27 01:00:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing dependency on package configuration (c6d7b2a) Message-ID: <20171027010038.32DE33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6d7b2a33e6ff987e7112c57555425c285c380e9/ghc >--------------------------------------------------------------- commit c6d7b2a33e6ff987e7112c57555425c285c380e9 Author: Andrey Mokhov Date: Fri Sep 29 00:37:35 2017 +0100 Fix missing dependency on package configuration Also a minor revision. See #421 >--------------------------------------------------------------- c6d7b2a33e6ff987e7112c57555425c285c380e9 src/Base.hs | 7 ++++++- src/Builder.hs | 12 ++++++------ src/Settings/Builders/Common.hs | 8 +++----- src/Settings/Builders/Ghc.hs | 14 +++++++++----- src/Settings/Default.hs | 2 +- 5 files changed, 25 insertions(+), 18 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 76e8f2b..38c8792 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,7 +22,7 @@ module Base ( hadrianPath, configPath, configFile, sourcePath, configH, shakeFilesDir, generatedDir, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, inplaceLibCopyTargets, templateHscPath, stage0PackageDbDir, - inplacePackageDbPath, packageDbStamp + inplacePackageDbPath, packageDbPath, packageDbStamp ) where import Control.Applicative @@ -82,6 +82,11 @@ stage0PackageDbDir = "stage0/bootstrapping.conf" inplacePackageDbPath :: FilePath inplacePackageDbPath = "inplace/lib/package.conf.d" +-- | Path to the package database used in a given 'Stage'. +packageDbPath :: Stage -> Action FilePath +packageDbPath Stage0 = buildRoot <&> (-/- stage0PackageDbDir) +packageDbPath _ = return inplacePackageDbPath + -- | We use a stamp file to track the existence of a package database. packageDbStamp :: FilePath packageDbStamp = ".stamp" diff --git a/src/Builder.hs b/src/Builder.hs index 355878f..fdd73e7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -149,13 +149,13 @@ instance H.Builder Builder where Just context -> programPath context needBuilder :: Builder -> Action () - needBuilder (Configure dir) = need [dir -/- "configure"] - needBuilder Hsc2Hs = do path <- H.builderPath Hsc2Hs - need [path, templateHscPath] - needBuilder (Make dir) = need [dir -/- "Makefile"] - needBuilder builder = when (isJust $ builderProvenance builder) $ do + needBuilder builder = do path <- H.builderPath builder - need [path] + case builder of + Configure dir -> need [dir -/- "configure"] + Hsc2Hs -> need [path, templateHscPath] + Make dir -> need [dir -/- "Makefile"] + _ -> when (isJust $ builderProvenance builder) $ need [path] runBuilderWith :: Builder -> BuildInfo -> Action () runBuilderWith builder BuildInfo {..} = do diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 6da7ea8..e7af38b 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -49,11 +49,9 @@ cWarnings = do bootPackageDatabaseArgs :: Args bootPackageDatabaseArgs = do - root <- getBuildRoot - stage <- getStage - let dbDir | stage == Stage0 = root -/- stage0PackageDbDir - | otherwise = inplacePackageDbPath - expr $ need [dbDir -/- packageDbStamp] + stage <- getStage + dbPath <- expr $ packageDbPath stage + expr $ need [dbPath -/- packageDbStamp] stage0 ? do top <- expr topDirectory root <- getBuildRoot diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 7f942f6..94b5b21 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,5 +1,5 @@ module Settings.Builders.Ghc ( - ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs, ghcCbuilderArgs + ghcBuilderArgs, ghcCBuilderArgs, ghcMBuilderArgs, haddockGhcArgs ) where import Hadrian.Haskell.Cabal @@ -24,9 +24,8 @@ needTouchy = notStage0 ? windowsHost ? do touchyPath <- expr $ programPath (vanillaContext Stage0 touchy) expr $ need [touchyPath] -ghcCbuilderArgs :: Args -ghcCbuilderArgs = - builder (Ghc CompileCWithGhc) ? do +ghcCBuilderArgs :: Args +ghcCBuilderArgs = builder (Ghc CompileCWithGhc) ? do way <- getWay let ccArgs = [ getPkgDataList CcArgs , getStagedSettingList ConfCcArgs @@ -83,11 +82,16 @@ ghcMBuilderArgs = builder (Ghc FindHsDependencies) ? do haddockGhcArgs :: Args haddockGhcArgs = mconcat [ commonGhcArgs, getPkgDataList HsArgs ] --- This is included into ghcBuilderArgs, ghcMBuilderArgs and haddockGhcArgs. +-- Used in ghcBuilderArgs, ghcCBuilderArgs, ghcMBuilderArgs and haddockGhcArgs. commonGhcArgs :: Args commonGhcArgs = do way <- getWay path <- getBuildPath + pkg <- getPackage + when (isLibrary pkg) $ do + context <- getContext + conf <- expr $ pkgConfFile context + expr $ need [conf] mconcat [ arg "-hisuf", arg $ hisuf way , arg "-osuf" , arg $ osuf way , arg "-hcsuf", arg $ hcsuf way diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 10ec84f..cf0047f 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -148,8 +148,8 @@ defaultBuilderArgs = mconcat , deriveConstantsBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs - , ghcCbuilderArgs , ghcCabalBuilderArgs + , ghcCBuilderArgs , ghcMBuilderArgs , ghcPkgBuilderArgs , haddockBuilderArgs From git at git.haskell.org Fri Oct 27 01:00:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify (2ac9e71) Message-ID: <20171027010042.252B73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ac9e71747347801d70e80e9d603a5c79c8f5d5a/ghc >--------------------------------------------------------------- commit 2ac9e71747347801d70e80e9d603a5c79c8f5d5a Author: Andrey Mokhov Date: Sun May 15 00:20:54 2016 +0100 Simplify >--------------------------------------------------------------- 2ac9e71747347801d70e80e9d603a5c79c8f5d5a src/Settings/Packages/Rts.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 60fdf7a..35a1f95 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -96,13 +96,13 @@ rtsPackageArgs = package rts ? do , builder (GhcPkg Stage1) ? mconcat [ remove ["rts/stage1/inplace-pkg-config"] -- TODO: fix, see #113 - , arg $ rtsConf ] + , arg rtsConf ] - , builder HsCpp ? mconcat - [ arg ("-DTOP=" ++ quote top) - , arg ("-DFFI_INCLUDE_DIR=" ++ quote ffiIncludeDir) - , arg ("-DFFI_LIB_DIR=" ++ quote ffiLibraryDir) - , arg $ "-DFFI_LIB=" ++ quote libffiName ] ] + , builder HsCpp ? append + [ "-DTOP=" ++ quote top + , "-DFFI_INCLUDE_DIR=" ++ quote ffiIncludeDir + , "-DFFI_LIB_DIR=" ++ quote ffiLibraryDir + , "-DFFI_LIB=" ++ quote libffiName ] ] -- # If we're compiling on windows, enforce that we only support XP+ From git at git.haskell.org Fri Oct 27 01:00:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build man page (#424) (e1c9afa) Message-ID: <20171027010042.58EEF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1c9afa3c5e29a7cea8d3853a06e08005d06f83b/ghc >--------------------------------------------------------------- commit e1c9afa3c5e29a7cea8d3853a06e08005d06f83b Author: Zhen Zhang Date: Sun Oct 1 05:01:28 2017 +0800 Build man page (#424) >--------------------------------------------------------------- e1c9afa3c5e29a7cea8d3853a06e08005d06f83b src/Rules/Documentation.hs | 15 +++++++++++++++ src/Settings/Builders/Sphinx.hs | 2 +- 2 files changed, 16 insertions(+), 1 deletion(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index bafb1b2..2cdd4d5 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -22,12 +22,17 @@ documentationRules = do buildHtmlDocumentation buildPdfDocumentation buildDocumentationArchives + buildManPage "docs" ~> do root <- buildRoot let html = htmlRoot -/- "index.html" archives = map pathArchive docPaths pdfs = map pathPdf $ docPaths \\ [ "libraries" ] need $ map (root -/-) $ [html] ++ archives ++ pdfs + need [manPagePath] + +manPagePath :: FilePath +manPagePath = "_build/docs/users_guide/build-man/ghc.1" -- TODO: Add support for Documentation Packages so we can -- run the builders without this hack. @@ -176,3 +181,13 @@ buildArchive path = do src = root -/- pathIndex path need [src] build $ target context (Tar Create) [takeDirectory src] [file] + +-- | build man page +buildManPage :: Rules () +buildManPage = do + manPagePath %> \file -> do + need ["docs/users_guide/ghc.rst"] + let context = vanillaContext Stage0 docPackage + withTempDir $ \dir -> do + build $ target context (Sphinx Man) ["docs/users_guide"] [dir] + copyFileUntracked (dir -/- "ghc.1") file diff --git a/src/Settings/Builders/Sphinx.hs b/src/Settings/Builders/Sphinx.hs index 6ac88a0..2338cfc 100644 --- a/src/Settings/Builders/Sphinx.hs +++ b/src/Settings/Builders/Sphinx.hs @@ -16,7 +16,7 @@ sphinxBuilderArgs = do , arg =<< getInput , arg outPath ] , builder (Sphinx Man) ? mconcat - [ arg "-b", arg "latex" + [ arg "-b", arg "man" , arg "-d", arg $ outPath -/- ".doctrees-man" , arg =<< getInput , arg outPath ] ] From git at git.haskell.org Fri Oct 27 01:00:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop non-derived Show instance for PackageName (dc0bae1) Message-ID: <20171027010045.F23F23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dc0bae1e5aeb05e5704e38a8aa5c64887165fcc6/ghc >--------------------------------------------------------------- commit dc0bae1e5aeb05e5704e38a8aa5c64887165fcc6 Author: Andrey Mokhov Date: Sun May 15 00:47:13 2016 +0100 Drop non-derived Show instance for PackageName >--------------------------------------------------------------- dc0bae1e5aeb05e5704e38a8aa5c64887165fcc6 src/Oracles/PackageDeps.hs | 8 ++++---- src/Package.hs | 21 +++++++++------------ 2 files changed, 13 insertions(+), 16 deletions(-) diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index a2a9234..7983c7f 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -7,7 +7,7 @@ import Base import Package import Settings.Paths -newtype PackageDepsKey = PackageDepsKey PackageName +newtype PackageDepsKey = PackageDepsKey String deriving (Show, Typeable, Eq, Hashable, Binary, NFData) -- @packageDeps name@ is an action that given a 'Package' looks up its @@ -15,8 +15,8 @@ newtype PackageDepsKey = PackageDepsKey PackageName -- computed by scanning package cabal files (see Rules.Cabal). packageDeps :: Package -> Action [PackageName] packageDeps pkg = do - res <- askOracle . PackageDepsKey . pkgName $ pkg - return . fromMaybe [] $ res + res <- askOracle . PackageDepsKey $ pkgNameString pkg + return . map PackageName $ fromMaybe [] res -- Oracle for the package dependencies file packageDepsOracle :: Rules () @@ -25,6 +25,6 @@ packageDepsOracle = do putOracle $ "Reading package dependencies..." contents <- readFileLines packageDependencies return . Map.fromList $ - [ (p, ps) | line <- contents, let p:ps = map PackageName $ words line ] + [ (p, ps) | line <- contents, let p:ps = words line ] _ <- addOracle $ \(PackageDepsKey pkg) -> Map.lookup pkg <$> deps () return () diff --git a/src/Package.hs b/src/Package.hs index 4b6fbc6..1fc1ac9 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -15,12 +15,9 @@ import GHC.Generics (Generic) import Data.String -- | The name of a Cabal package -newtype PackageName = PackageName { getPackageName :: String } +newtype PackageName = PackageName { fromPackageName :: String } deriving (Eq, Ord, IsString, Generic, Binary, Hashable, Typeable, NFData) -instance Show PackageName where - show (PackageName name) = name - -- TODO: Make PackageType more precise, #12 -- TODO: Turn Program to Program FilePath thereby getting rid of programPath -- | We regard packages as either being libraries or programs. This is @@ -37,23 +34,23 @@ data Package = Package -- | Prettyprint Package name. pkgNameString :: Package -> String -pkgNameString = getPackageName . pkgName +pkgNameString = fromPackageName . pkgName -- | Relative path to cabal file, e.g.: "libraries/Cabal/Cabal/Cabal.cabal" pkgCabalFile :: Package -> FilePath -pkgCabalFile pkg = pkgPath pkg -/- getPackageName (pkgName pkg) <.> "cabal" +pkgCabalFile pkg = pkgPath pkg -/- pkgNameString pkg <.> "cabal" -- | Smart constructor for a top-level package, e.g. 'compiler'. topLevel :: PackageName -> Package -topLevel name = Package name (getPackageName name) Library +topLevel name = Package name (fromPackageName name) Library -- | Smart constructor for a library package, e.g. 'array'. library :: PackageName -> Package -library name = Package name ("libraries" -/- getPackageName name) Library +library name = Package name ("libraries" -/- fromPackageName name) Library -- | Smart constructor for a utility package, e.g. 'haddock'. utility :: PackageName -> Package -utility name = Package name ("utils" -/- getPackageName name) Program +utility name = Package name ("utils" -/- fromPackageName name) Program -- | Amend package path. Useful when a package name doesn't match its path. setPath :: Package -> FilePath -> Package @@ -65,17 +62,17 @@ setType pkg ty = pkg { pkgType = ty } -- | Check whether a package is a library. isLibrary :: Package -> Bool -isLibrary (Package {pkgType=Library}) = True +isLibrary (Package _ _ Library) = True isLibrary _ = False -- | Check whether a package is a program. isProgram :: Package -> Bool -isProgram (Package {pkgType=Program}) = True +isProgram (Package _ _ Program) = True isProgram _ = False -- TODO: Get rid of non-derived Show instances. instance Show Package where - show = show . pkgName + show = pkgNameString instance Eq Package where (==) = (==) `on` pkgName From git at git.haskell.org Fri Oct 27 01:00:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to the python based boot script (18539d0) Message-ID: <20171027010046.24D0A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/18539d0ca551e312a81f2d9bda5ad055a657906a/ghc >--------------------------------------------------------------- commit 18539d0ca551e312a81f2d9bda5ad055a657906a Author: Andrey Mokhov Date: Wed Oct 4 12:38:48 2017 +0100 Switch to the python based boot script See #314 >--------------------------------------------------------------- 18539d0ca551e312a81f2d9bda5ad055a657906a src/Rules/Configure.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index 492d91c..a4ef084 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -38,4 +38,4 @@ configureRules = do else do need ["configure.ac"] putBuild "| Running boot..." - quietly $ cmd "perl boot" + quietly $ cmd "python3 boot" From git at git.haskell.org Fri Oct 27 01:00:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix libffil build (d6fd6fe) Message-ID: <20171027010049.E98C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6fd6feb85cd846dfd707703da839056d43c92a8/ghc >--------------------------------------------------------------- commit d6fd6feb85cd846dfd707703da839056d43c92a8 Author: Andrey Mokhov Date: Thu Oct 5 10:50:56 2017 +0100 Fix libffil build See #426 >--------------------------------------------------------------- d6fd6feb85cd846dfd707703da839056d43c92a8 src/Rules/Libffi.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 68040be..9641b66 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -64,7 +64,7 @@ libffiRules = do libffiPath <- libffiBuildPath build $ target libffiContext (Make libffiPath) [] [] - hs <- getDirectoryFiles "" [libffiPath -/- "inst/lib/*/include/*"] + hs <- getDirectoryFiles "" [libffiPath -/- "inst/include/*"] forM_ hs $ \header -> copyFile header (rtsPath -/- takeFileName header) @@ -82,7 +82,8 @@ libffiRules = do <$> getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] need [tarball] - let libname = dropExtension . dropExtension $ takeFileName tarball + -- Go from 'libffi-3.99999+git20171002+77e130c.tar.gz' to 'libffi-3.99999' + let libname = takeWhile (/= '+') $ takeFileName tarball root <- buildRoot removeDirectory (root -/- libname) From git at git.haskell.org Fri Oct 27 01:00:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (3c5998c) Message-ID: <20171027010049.ED5DE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c5998cddf477e84ee2e0b98de7a7d26bb0da710/ghc >--------------------------------------------------------------- commit 3c5998cddf477e84ee2e0b98de7a7d26bb0da710 Author: Andrey Mokhov Date: Sun May 15 01:02:51 2016 +0100 Minor revision >--------------------------------------------------------------- 3c5998cddf477e84ee2e0b98de7a7d26bb0da710 src/Oracles/PackageData.hs | 20 +++++++++----------- 1 file changed, 9 insertions(+), 11 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index ba3e205..dba1192 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -5,17 +5,10 @@ module Oracles.PackageData ( ) where import Development.Shake.Config -import Base import qualified Data.HashMap.Strict as Map --- For each (PackageData path) the file 'path/package-data.mk' contains --- a line of the form 'path_VERSION = 1.2.3.4'. --- pkgData $ PackageData path is an action that consults the file and --- returns "1.2.3.4". --- --- PackageDataList is used for multiple string options separated by spaces, --- such as 'path_MODULES = Data.Array Data.Array.Base ...'. --- pkgListData Modules therefore returns ["Data.Array", "Data.Array.Base", ...] +import Base + data PackageData = BuildGhciLib FilePath | ComponentId FilePath | Synopsis FilePath @@ -51,8 +44,10 @@ askPackageData path key = do case maybeValue of Nothing -> return "" Just value -> return value - -- Nothing -> putError $ "No key '" ++ key ++ "' in " ++ file ++ "." +-- | For each @PackageData path@ the file 'path/package-data.mk' contains a line +-- of the form 'path_VERSION = 1.2.3.4'. @pkgData (PackageData path)@ is an +-- Action that consults the file and returns "1.2.3.4". pkgData :: PackageData -> Action String pkgData packageData = case packageData of BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" @@ -60,6 +55,9 @@ pkgData packageData = case packageData of Synopsis path -> askPackageData path "SYNOPSIS" Version path -> askPackageData path "VERSION" +-- | @PackageDataList path@ is used for multiple string options separated by +-- spaces, such as @path_MODULES = Data.Array Data.Array.Base ... at . +-- @pkgListData Modules@ therefore returns ["Data.Array", "Data.Array.Base", ...] pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = fmap (map unquote . words) $ case packageData of CcArgs path -> askPackageData path "CC_OPTS" @@ -83,7 +81,7 @@ pkgDataList packageData = fmap (map unquote . words) $ case packageData of where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') --- Oracle for 'package-data.mk' files +-- | Oracle for 'package-data.mk' files. packageDataOracle :: Rules () packageDataOracle = do keys <- newCache $ \file -> do From git at git.haskell.org Fri Oct 27 01:00:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install python on CI (c13806a) Message-ID: <20171027010053.8A2C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c13806a2f5857075f769ec45280cbd3f298e3044/ghc >--------------------------------------------------------------- commit c13806a2f5857075f769ec45280cbd3f298e3044 Author: Andrey Mokhov Date: Thu Oct 5 10:59:49 2017 +0100 Install python on CI See #314 >--------------------------------------------------------------- c13806a2f5857075f769ec45280cbd3f298e3044 appveyor.yml | 2 +- circle.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 451d5d5..c51983a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -22,7 +22,7 @@ install: # Install all Hadrian and GHC build dependencies - cd hadrian - stack setup > nul - - appveyor-retry stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm + - appveyor-retry stack exec -- pacman -S autoconf automake-wrapper make patch python tar --noconfirm build_script: # Build Hadrian diff --git a/circle.yml b/circle.yml index b038689..592b9f4 100644 --- a/circle.yml +++ b/circle.yml @@ -7,7 +7,7 @@ machine: dependencies: override: - brew update - - brew install ghc cabal-install + - brew install ghc cabal-install python - cabal update - cabal install alex happy ansi-terminal mtl shake quickcheck cache_directories: From git at git.haskell.org Fri Oct 27 01:00:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop DeriveDataTypeable extension (fda4673) Message-ID: <20171027010053.9FAAA3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fda46732212cd1f052734ac796dafb3b3f7526a8/ghc >--------------------------------------------------------------- commit fda46732212cd1f052734ac796dafb3b3f7526a8 Author: Andrey Mokhov Date: Sun May 15 01:03:32 2016 +0100 Drop DeriveDataTypeable extension >--------------------------------------------------------------- fda46732212cd1f052734ac796dafb3b3f7526a8 hadrian.cabal | 3 +-- src/Oracles/ArgsHash.hs | 2 +- src/Oracles/Config.hs | 2 +- src/Oracles/Dependencies.hs | 2 +- src/Oracles/LookupInPath.hs | 2 +- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/PackageDeps.hs | 2 +- src/Oracles/WindowsPath.hs | 2 +- src/Package.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- 11 files changed, 11 insertions(+), 12 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 5c13f7a..7f03057 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -112,8 +112,7 @@ executable hadrian default-language: Haskell2010 default-extensions: RecordWildCards - other-extensions: DeriveDataTypeable - , DeriveGeneric + other-extensions: DeriveGeneric , FlexibleInstances , GeneralizedNewtypeDeriving , LambdaCase diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index d3bfd61..c26efd4 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.ArgsHash (checkArgsHash, argsHashOracle) where import Base diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs index 7801208..95facc8 100644 --- a/src/Oracles/Config.hs +++ b/src/Oracles/Config.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Config (askConfig, askConfigWithDefault, configOracle) where import Base diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index aa54d86..08b3afa 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Dependencies (dependencies, dependenciesOracle) where import Control.Monad.Trans.Maybe diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs index 0ea03fd..18c990b 100644 --- a/src/Oracles/LookupInPath.hs +++ b/src/Oracles/LookupInPath.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where import System.Directory diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 233cdc0..f2b03f3 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.ModuleFiles ( decodeModule, encodeModule, findGenerator, haskellSources, moduleFilesOracle ) where diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index dba1192..6a01692 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( PackageData (..), PackageDataList (..), pkgData, pkgDataList, packageDataOracle diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs index 7983c7f..c70b959 100644 --- a/src/Oracles/PackageDeps.hs +++ b/src/Oracles/PackageDeps.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.PackageDeps (packageDeps, packageDepsOracle) where import qualified Data.HashMap.Strict as Map diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index e252bba..2a3336d 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.WindowsPath ( fixAbsolutePathOnWindows, topDirectory, windowsPathOracle ) where diff --git a/src/Package.hs b/src/Package.hs index 1fc1ac9..7517d87 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving, DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving #-} module Package ( Package (..), PackageName (..), PackageType (..), diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index faeb99d..9df0fdb 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDbArgs, PackageDbKey (..), cppArgs, needDll0 From git at git.haskell.org Fri Oct 27 01:00:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install python3 on CircleCI (81a6d1a) Message-ID: <20171027010057.5B5E73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/81a6d1a961ed6e0327f2f34e4955f8628729498a/ghc >--------------------------------------------------------------- commit 81a6d1a961ed6e0327f2f34e4955f8628729498a Author: Andrey Mokhov Date: Thu Oct 5 11:15:17 2017 +0100 Install python3 on CircleCI See #314 >--------------------------------------------------------------- 81a6d1a961ed6e0327f2f34e4955f8628729498a circle.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/circle.yml b/circle.yml index 592b9f4..93cf47f 100644 --- a/circle.yml +++ b/circle.yml @@ -7,7 +7,7 @@ machine: dependencies: override: - brew update - - brew install ghc cabal-install python + - brew install ghc cabal-install python3 - cabal update - cabal install alex happy ansi-terminal mtl shake quickcheck cache_directories: From git at git.haskell.org Fri Oct 27 01:00:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (f50439d) Message-ID: <20171027010057.6ECF33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f50439d081f137ee3e7abfbdc2f19e4b37620bbd/ghc >--------------------------------------------------------------- commit f50439d081f137ee3e7abfbdc2f19e4b37620bbd Author: Andrey Mokhov Date: Mon May 16 00:26:02 2016 +0100 Minor revision >--------------------------------------------------------------- f50439d081f137ee3e7abfbdc2f19e4b37620bbd src/Rules/Register.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index cd3649b..f35413a 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -10,38 +10,37 @@ import Settings import Settings.Packages.Rts import Target --- Build package-data.mk by using GhcCabal to process pkgCabal file +-- | Build package-data.mk by processing the .cabal file with ghc-cabal utility. registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context at Context {..} = do - let oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 + let path = buildPath context + oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 pkgConf = packageDbDirectory stage -/- pkgNameString package when (stage <= Stage1) $ matchVersionedFilePath pkgConf "conf" ?> \conf -> do - -- This produces inplace-pkg-config. TODO: Add explicit tracking + -- This produces inplace-pkg-config. TODO: Add explicit tracking. need [pkgDataFile context] -- Post-process inplace-pkg-config. TODO: remove, see #113, #148 let pkgConfig = oldPath -/- "inplace-pkg-config" oldBuildPath = oldPath -/- "build" fixPkgConf = unlines - . map (replace oldBuildPath (buildPath context) - . replace (replaceSeparators '\\' $ oldBuildPath) - (buildPath context) ) + . map + ( replace oldBuildPath path + . replace (replaceSeparators '\\' oldBuildPath) path ) . lines fixFile pkgConfig fixPkgConf - buildWithResources rs $ - Target context (GhcPkg stage) [pkgConfig] [conf] + buildWithResources rs $ Target context (GhcPkg stage) [pkgConfig] [conf] when (package == rts && stage == Stage1) $ do packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do need [rtsConf] - buildWithResources rs $ - Target context (GhcPkg stage) [rtsConf] [conf] + buildWithResources rs $ Target context (GhcPkg stage) [rtsConf] [conf] rtsConf %> \_ -> do - need [ pkgDataFile rtsContext, rtsConfIn ] + need [pkgDataFile rtsContext, rtsConfIn] build $ Target context HsCpp [rtsConfIn] [rtsConf] let fixRtsConf = unlines From git at git.haskell.org Fri Oct 27 01:01:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install python3 on Travis OS X (6eb3059) Message-ID: <20171027010101.6D7E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6eb305962ccba06aeae22812e5733b5998843dcb/ghc >--------------------------------------------------------------- commit 6eb305962ccba06aeae22812e5733b5998843dcb Author: Andrey Mokhov Date: Thu Oct 5 11:34:12 2017 +0100 Install python3 on Travis OS X See #314 >--------------------------------------------------------------- 6eb305962ccba06aeae22812e5733b5998843dcb .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 9082ef6..203ee82 100644 --- a/.travis.yml +++ b/.travis.yml @@ -51,7 +51,7 @@ matrix: env: MODE="--flavour=quickest --integer-simple inplace/bin/ghc-stage1" before_install: - brew update - - brew install ghc cabal-install + - brew install ghc cabal-install python3 script: # Due to timeout limit of OS X build on Travis CI, From git at git.haskell.org Fri Oct 27 01:01:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't add redundant path separator in -/- (d1780e4) Message-ID: <20171027010101.75AA13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d1780e499e3e5a3f4adb21f6be366b26ae3ec6a4/ghc >--------------------------------------------------------------- commit d1780e499e3e5a3f4adb21f6be366b26ae3ec6a4 Author: Andrey Mokhov Date: Mon May 16 01:31:02 2016 +0100 Don't add redundant path separator in -/- >--------------------------------------------------------------- d1780e499e3e5a3f4adb21f6be366b26ae3ec6a4 src/Base.hs | 5 ++++- src/Oracles/WindowsPath.hs | 5 +++-- 2 files changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index bd80f47..339a61d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -89,7 +89,10 @@ unifyPath = toStandard . normaliseEx -- | Combine paths with a forward slash regardless of platform. (-/-) :: FilePath -> FilePath -> FilePath -a -/- b = a ++ '/' : b +"" -/- b = b +a -/- b + | last a == '/' = a ++ b + | otherwise = a ++ '/' : b infixr 6 -/- diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index 2a3336d..3cbf73b 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -3,7 +3,8 @@ module Oracles.WindowsPath ( fixAbsolutePathOnWindows, topDirectory, windowsPathOracle ) where -import Data.Char (isSpace) +import Data.Char + import Base import Oracles.Config.Setting @@ -25,7 +26,7 @@ fixAbsolutePathOnWindows path = do then do let (dir, file) = splitFileName path winDir <- askOracle $ WindowsPath dir - return $ winDir ++ file + return $ winDir -/- file else return path From git at git.haskell.org Fri Oct 27 01:01:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up imports (improve consistency) (e982476) Message-ID: <20171027010105.379C53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e982476cf7b80add369365d78718e9954a3944d0/ghc >--------------------------------------------------------------- commit e982476cf7b80add369365d78718e9954a3944d0 Author: Andrey Mokhov Date: Mon May 16 01:33:39 2016 +0100 Clean up imports (improve consistency) >--------------------------------------------------------------- e982476cf7b80add369365d78718e9954a3944d0 src/Builder.hs | 2 +- src/CmdLineFlag.hs | 14 ++++++-------- src/Environment.hs | 3 ++- src/Expression.hs | 2 +- src/Oracles/Config.hs | 3 ++- src/Package.hs | 5 +++-- src/Rules/Cabal.hs | 3 ++- src/Rules/Configure.hs | 4 ++-- src/Rules/Generate.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Perl.hs | 2 +- src/Rules/Selftest.hs | 4 ++-- src/Rules/Test.hs | 2 +- src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/Ar.hs | 4 ++-- src/Settings/Builders/Cc.hs | 6 +++--- src/Settings/Builders/Common.hs | 2 +- src/Settings/Builders/Configure.hs | 2 +- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 +++----- src/Settings/Builders/GhcCabal.hs | 9 +++------ src/Settings/Builders/Haddock.hs | 1 - src/Settings/Builders/Happy.hs | 2 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 4 ++-- src/Settings/Builders/Make.hs | 2 +- src/Settings/Builders/Tar.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Packages/Base.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 6 +++--- src/Settings/Packages/Directory.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 4 ++-- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/GhcPrim.hs | 4 ++-- src/Settings/Packages/Haddock.hs | 4 ++-- src/Settings/Packages/Hp2ps.hs | 4 ++-- src/Settings/Packages/IntegerGmp.hs | 6 +++--- src/Settings/Packages/IservBin.hs | 7 +++---- src/Settings/Packages/Rts.hs | 4 ++-- src/Settings/Packages/RunGhc.hs | 4 ++-- src/Settings/Packages/Touchy.hs | 4 ++-- src/Settings/Packages/Unlit.hs | 4 ++-- src/Settings/Ways.hs | 5 +++-- src/Way.hs | 3 ++- 45 files changed, 84 insertions(+), 87 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 e982476cf7b80add369365d78718e9954a3944d0 From git at git.haskell.org Fri Oct 27 01:01:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update docs (c70f765) Message-ID: <20171027010105.39A8F3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c70f765b7aaecaa4bfed5c39e33e1e5111b1ce30/ghc >--------------------------------------------------------------- commit c70f765b7aaecaa4bfed5c39e33e1e5111b1ce30 Author: Andrey Mokhov Date: Thu Oct 5 12:43:25 2017 +0100 Update docs See #314 >--------------------------------------------------------------- c70f765b7aaecaa4bfed5c39e33e1e5111b1ce30 doc/windows.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/windows.md b/doc/windows.md index 510b986..f644f03 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -24,7 +24,7 @@ cd hadrian stack setup # Install utilities required during the GHC build process -stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm +stack exec -- pacman -S autoconf automake-wrapper make patch python tar --noconfirm # Build Hadrian and dependencies (including GHC dependencies Alex and Happy) stack build From git at git.haskell.org Fri Oct 27 01:01:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export Expression from Predicates (12dc4c5) Message-ID: <20171027010108.EF17A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12dc4c5b7faaf774031fef8539947459cd9b20a5/ghc >--------------------------------------------------------------- commit 12dc4c5b7faaf774031fef8539947459cd9b20a5 Author: Andrey Mokhov Date: Mon May 16 01:47:31 2016 +0100 Re-export Expression from Predicates >--------------------------------------------------------------- 12dc4c5b7faaf774031fef8539947459cd9b20a5 src/Expression.hs | 1 + src/Predicates.hs | 1 + src/Settings/Builders/Alex.hs | 1 - src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Cc.hs | 1 - src/Settings/Builders/Configure.hs | 1 - src/Settings/Builders/DeriveConstants.hs | 1 - src/Settings/Builders/GenApply.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 1 - src/Settings/Builders/Ghc.hs | 3 --- src/Settings/Builders/GhcCabal.hs | 1 - src/Settings/Builders/GhcPkg.hs | 1 - src/Settings/Builders/Haddock.hs | 3 +-- src/Settings/Builders/Happy.hs | 1 - src/Settings/Builders/HsCpp.hs | 1 - src/Settings/Builders/Hsc2Hs.hs | 4 ---- src/Settings/Builders/Ld.hs | 3 +-- src/Settings/Builders/Make.hs | 1 - src/Settings/Builders/Tar.hs | 1 - src/Settings/Default.hs | 3 +-- src/Settings/Flavours/Quick.hs | 1 - src/Settings/Packages.hs | 1 - src/Settings/Packages/Base.hs | 1 - src/Settings/Packages/Compiler.hs | 1 - src/Settings/Packages/Directory.hs | 1 - src/Settings/Packages/Ghc.hs | 1 - src/Settings/Packages/GhcCabal.hs | 1 - src/Settings/Packages/GhcPrim.hs | 1 - src/Settings/Packages/Haddock.hs | 1 - src/Settings/Packages/Hp2ps.hs | 1 - src/Settings/Packages/IntegerGmp.hs | 1 - src/Settings/Packages/IservBin.hs | 1 - src/Settings/Packages/Rts.hs | 1 - src/Settings/Packages/RunGhc.hs | 1 - src/Settings/Packages/Touchy.hs | 1 - src/Settings/Packages/Unlit.hs | 1 - src/Settings/User.hs | 1 - src/Settings/Ways.hs | 1 - 38 files changed, 6 insertions(+), 44 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 12dc4c5b7faaf774031fef8539947459cd9b20a5 From git at git.haskell.org Fri Oct 27 01:01:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (c6efd3f) Message-ID: <20171027010108.EE1D53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6efd3f68521f20632a0a173e1568aa772c0ea48/ghc >--------------------------------------------------------------- commit c6efd3f68521f20632a0a173e1568aa772c0ea48 Author: Andrey Mokhov Date: Thu Oct 5 17:58:20 2017 +0100 Minor revision >--------------------------------------------------------------- c6efd3f68521f20632a0a173e1568aa772c0ea48 doc/windows.md | 25 +++++++++++++------------ 1 file changed, 13 insertions(+), 12 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index f644f03..b374074 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -2,19 +2,11 @@ [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) -Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are -installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). - -Note that `git` should be configured to check out Unix-style line endings. The default behaviour of `git` on Windows is to check out Windows-style line endings which can cause issues during the build. This can be changed using the following command: - - git config --global core.autocrlf false - -If you would like to restore the default behaviour later run: - - git config --global core.autocrlf true +Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are installed +(see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). ```sh -# Get GHC and Hadrian sources +# Get GHC and Hadrian sources; git core.autocrlf should be set to false (see Prerequisites section) git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/hadrian @@ -55,6 +47,16 @@ The above works on a clean machine with `git` and `stack` installed (tested with installation settings), which you can get from https://git-scm.com/download/win and https://www.stackage.org/stack/windows-x86_64-installer. +Note that `git` should be configured to check out Unix-style line endings. The default behaviour +of `git` on Windows is to check out Windows-style line endings which can cause issues during the +build. This can be changed using the following command: + + git config --global core.autocrlf false + +If you would like to restore the default behaviour later run: + + git config --global core.autocrlf true + ## Testing These instructions have been tested on a clean Windows 10 machine using the @@ -65,4 +67,3 @@ and are also routinely tested on ## Notes Beware of the [current limitations of Hadrian](https://github.com/snowleopard/hadrian#current-limitations). - From git at git.haskell.org Fri Oct 27 01:01:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant code (830567e) Message-ID: <20171027010112.AA82A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/830567e388a89b90a80c0140379c983de3cec8aa/ghc >--------------------------------------------------------------- commit 830567e388a89b90a80c0140379c983de3cec8aa Author: Andrey Mokhov Date: Thu Oct 5 20:08:35 2017 +0100 Drop redundant code See #314 >--------------------------------------------------------------- 830567e388a89b90a80c0140379c983de3cec8aa src/Environment.hs | 12 ------------ 1 file changed, 12 deletions(-) diff --git a/src/Environment.hs b/src/Environment.hs index d92e067..de43efa 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -2,8 +2,6 @@ module Environment (setupEnvironment) where import System.Environment -import Base - -- | The build system invokes many external builders whose behaviour is -- influenced by the environment variables. We need to modify some of them -- for better robustness of the build system. @@ -16,13 +14,3 @@ setupEnvironment = do -- `pwd` will return the Windows path, and then modifying $PATH will fail. -- See https://github.com/snowleopard/hadrian/issues/189 for details. unsetEnv "PWD" - - -- On Windows, some path variables start a prefix like "C:\\" which may - -- lead to failures of scripts such as autoreconf. One particular variable - -- which causes issues is ACLOCAL_PATH. At the moment we simply reset it - -- if it contains a problematic Windows path. - -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. - aclocal <- lookupEnv "ACLOCAL_PATH" - case aclocal of - Nothing -> return () - Just s -> when (":\\" `isPrefixOf` drop 1 s) $ unsetEnv "ACLOCAL_PATH" From git at git.haskell.org Fri Oct 27 01:01:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename module Predicates to Predicate (03f89a6) Message-ID: <20171027010112.B7A643A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7/ghc >--------------------------------------------------------------- commit 03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7 Author: Andrey Mokhov Date: Mon May 16 01:51:17 2016 +0100 Rename module Predicates to Predicate >--------------------------------------------------------------- 03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7 hadrian.cabal | 2 +- src/{Predicates.hs => Predicate.hs} | 2 +- src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Cc.hs | 2 +- src/Settings/Builders/Configure.hs | 2 +- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/GenApply.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 2 +- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Builders/Happy.hs | 2 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Builders/Ld.hs | 2 +- src/Settings/Builders/Make.hs | 2 +- src/Settings/Builders/Tar.hs | 2 +- src/Settings/Default.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Directory.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/GhcPrim.hs | 2 +- src/Settings/Packages/Haddock.hs | 2 +- src/Settings/Packages/Hp2ps.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/IservBin.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/Packages/Touchy.hs | 2 +- src/Settings/Packages/Unlit.hs | 2 +- src/Settings/User.hs | 2 +- src/Settings/Ways.hs | 2 +- 38 files changed, 38 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 03f89a63101dc1a6e8b2ffabee1a6462c60c8cf7 From git at git.haskell.org Fri Oct 27 01:01:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop the redundant build rule for literate Perl scripts (a69c73f) Message-ID: <20171027010116.C32613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a69c73fe0d051d87cfc6fd95c72089faa92c5a0f/ghc >--------------------------------------------------------------- commit a69c73fe0d051d87cfc6fd95c72089faa92c5a0f Author: Andrey Mokhov Date: Sat Oct 7 23:26:08 2017 +0100 Drop the redundant build rule for literate Perl scripts >--------------------------------------------------------------- a69c73fe0d051d87cfc6fd95c72089faa92c5a0f hadrian.cabal | 1 - src/Rules.hs | 2 -- src/Rules/Perl.hs | 13 ------------- 3 files changed, 16 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 97b283a..48514e1 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -54,7 +54,6 @@ executable hadrian , Rules.Install , Rules.Libffi , Rules.Library - , Rules.Perl , Rules.Program , Rules.Register , Rules.Selftest diff --git a/src/Rules.hs b/src/Rules.hs index ea3df45..730823f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -17,7 +17,6 @@ import qualified Rules.Configure import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Library -import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings @@ -115,7 +114,6 @@ buildRules = do Rules.Gmp.gmpRules Rules.Libffi.libffiRules packageRules - Rules.Perl.perlScriptRules oracleRules :: Rules () oracleRules = do diff --git a/src/Rules/Perl.hs b/src/Rules/Perl.hs deleted file mode 100644 index bc8b01f..0000000 --- a/src/Rules/Perl.hs +++ /dev/null @@ -1,13 +0,0 @@ -module Rules.Perl (perlScriptRules) where - -import Base -import Builder - --- TODO: Do we need this build rule? --- | Build Perl scripts, such as @ghc-split@, from their literate Perl sources. -perlScriptRules :: Rules () -perlScriptRules = do - "//*.prl" %> \out -> do - let src = out -<.> "lprl" - need [src] - runBuilder Unlit [src, out] [src] [out] From git at git.haskell.org Fri Oct 27 01:01:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement Stage1 GHC freezing (837675c) Message-ID: <20171027010120.8BBC13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/837675cdf374040b554dd04491b7e59aa631abd4/ghc >--------------------------------------------------------------- commit 837675cdf374040b554dd04491b7e59aa631abd4 Author: Andrey Mokhov Date: Mon Oct 9 01:14:54 2017 +0100 Implement Stage1 GHC freezing See #250 >--------------------------------------------------------------- 837675cdf374040b554dd04491b7e59aa631abd4 src/CommandLine.hs | 19 ++++++++++++++++--- src/Main.hs | 4 ++++ 2 files changed, 20 insertions(+), 3 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index cc6f944..a069c0e 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -1,10 +1,11 @@ module CommandLine ( - optDescrs, cmdLineArgsMap, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, - cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects, - cmdInstallDestDir + optDescrs, cmdLineArgsMap, cmdBuildHaddock, cmdFlavour, lookupFreeze1, + cmdIntegerSimple, cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, + cmdSplitObjects, cmdInstallDestDir ) where import Data.Either +import Data.Maybe import qualified Data.HashMap.Strict as Map import Data.List.Extra import Development.Shake hiding (Normal) @@ -16,6 +17,7 @@ import System.Environment data CommandLineArgs = CommandLineArgs { buildHaddock :: Bool , flavour :: Maybe String + , freeze1 :: Bool , installDestDir :: Maybe String , integerSimple :: Bool , progressColour :: UseColour @@ -29,6 +31,7 @@ defaultCommandLineArgs :: CommandLineArgs defaultCommandLineArgs = CommandLineArgs { buildHaddock = False , flavour = Nothing + , freeze1 = False , installDestDir = Nothing , integerSimple = False , progressColour = Auto @@ -36,6 +39,9 @@ defaultCommandLineArgs = CommandLineArgs , skipConfigure = False , splitObjects = False } +readFreeze1 :: Either String (CommandLineArgs -> CommandLineArgs) +readFreeze1 = Right $ \flags -> flags { freeze1 = True } + readBuildHaddock :: Either String (CommandLineArgs -> CommandLineArgs) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } @@ -84,6 +90,8 @@ optDescrs :: [OptDescr (Either String (CommandLineArgs -> CommandLineArgs))] optDescrs = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." + , Option [] ["freeze1"] (NoArg readFreeze1) + "Freeze Stage1 GHC." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["install-destdir"] (OptArg readInstallDestDir "DESTDIR") @@ -118,6 +126,11 @@ cmdBuildHaddock = buildHaddock <$> cmdLineArgs cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs +lookupFreeze1 :: Map.HashMap TypeRep Dynamic -> Bool +lookupFreeze1 m = fromMaybe (freeze1 defaultCommandLineArgs) (freeze1 <$> maybeValue) + where + maybeValue = fromDynamic =<< Map.lookup (typeOf defaultCommandLineArgs) m + cmdInstallDestDir :: Action (Maybe String) cmdInstallDestDir = installDestDir <$> cmdLineArgs diff --git a/src/Main.hs b/src/Main.hs index 91580dd..52af0ad 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -28,11 +28,15 @@ main = do BuildRoot buildRoot = UserSettings.userBuildRoot + rebuild = [ (RebuildLater, buildRoot -/- "stage0//*") + | CommandLine.lookupFreeze1 argsMap ] + options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = buildRoot -/- Base.shakeFilesDir , shakeProgress = progressSimple + , shakeRebuild = rebuild , shakeTimings = True , shakeExtra = extra } From git at git.haskell.org Fri Oct 27 01:01:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Check if the output supports colors (fixes #244) (0f7bc96) Message-ID: <20171027010116.D57E83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0f7bc96a2c8940181818594ffc71bf928ab8aed2/ghc >--------------------------------------------------------------- commit 0f7bc96a2c8940181818594ffc71bf928ab8aed2 Author: Michal Terepeta Date: Sun May 15 17:31:30 2016 +0200 Check if the output supports colors (fixes #244) This avoids using colors when the output is, e.g., redirected to a file. This requried a change to avoid passing the `--colour` flag to shake (so that hadrian is in charge of colors). Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 0f7bc96a2c8940181818594ffc71bf928ab8aed2 build.cabal-new.sh | 1 - build.cabal.sh | 1 - build.sh | 1 - build.stack.sh | 1 - src/Base.hs | 12 ++++++++++-- 5 files changed, 10 insertions(+), 6 deletions(-) diff --git a/build.cabal-new.sh b/build.cabal-new.sh index bca8c7c..65e222a 100755 --- a/build.cabal-new.sh +++ b/build.cabal-new.sh @@ -55,5 +55,4 @@ popd "$root/.shake/build" \ --lint \ --directory "$root/.." \ - --colour \ "$@" diff --git a/build.cabal.sh b/build.cabal.sh index f2e320e..08ff972 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -43,5 +43,4 @@ fi cabal run hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ - --colour \ "$@" diff --git a/build.sh b/build.sh index fff8df4..24fdc2f 100755 --- a/build.sh +++ b/build.sh @@ -49,5 +49,4 @@ ghc \ "$root/hadrian" \ --lint \ --directory "$root/.." \ - --colour \ "$@" diff --git a/build.stack.sh b/build.stack.sh index b5607b1..23f4833 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -36,5 +36,4 @@ stack build --no-library-profiling stack exec hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ - --colour \ "$@" diff --git a/src/Base.hs b/src/Base.hs index bd80f47..488be04 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -38,6 +38,7 @@ import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import System.Console.ANSI +import qualified System.Info as Info import System.IO -- TODO: reexport Stage, etc.? @@ -96,10 +97,17 @@ infixr 6 -/- -- | A more colourful version of Shake's putNormal putColoured :: Color -> String -> Action () putColoured colour msg = do - liftIO $ setSGR [SetColor Foreground Vivid colour] + liftIO $ set [SetColor Foreground Vivid colour] putNormal msg - liftIO $ setSGR [] + liftIO $ set [] liftIO $ hFlush stdout + where + set a = do + supported <- hSupportsANSI stdout + when (win || supported) $ setSGR a + -- An ugly hack to always try to print colours when on mingw and cygwin. + -- See: https://github.com/snowleopard/hadrian/pull/253 + win = "mingw" `isPrefixOf` Info.os || "cygwin" `isPrefixOf` Info.os -- | Make oracle output more distinguishable putOracle :: String -> Action () From git at git.haskell.org Fri Oct 27 01:01:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #253 from michalt/colors/1 (a9f43e5) Message-ID: <20171027010120.C59023A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a9f43e59a1f84108a779b1ce835b5357f47b8e0f/ghc >--------------------------------------------------------------- commit a9f43e59a1f84108a779b1ce835b5357f47b8e0f Merge: 03f89a6 0f7bc96 Author: Andrey Mokhov Date: Mon May 16 13:46:36 2016 +0100 Merge pull request #253 from michalt/colors/1 Check if the output supports colors, see #244 >--------------------------------------------------------------- a9f43e59a1f84108a779b1ce835b5357f47b8e0f build.cabal-new.sh | 1 - build.cabal.sh | 1 - build.sh | 1 - build.stack.sh | 1 - src/Base.hs | 12 ++++++++++-- 5 files changed, 10 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 01:01:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision, drop old TODO (cbee74b) Message-ID: <20171027010124.947673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbee74bfe89e6b2b552c6ae560265ce2d9f5fb17/ghc >--------------------------------------------------------------- commit cbee74bfe89e6b2b552c6ae560265ce2d9f5fb17 Author: Andrey Mokhov Date: Tue Oct 10 00:37:42 2017 +0100 Minor revision, drop old TODO See #250 >--------------------------------------------------------------- cbee74bfe89e6b2b552c6ae560265ce2d9f5fb17 src/CommandLine.hs | 5 +---- src/Hadrian/Utilities.hs | 11 ++++++++--- src/Settings/Flavours/Development.hs | 1 - 3 files changed, 9 insertions(+), 8 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index a069c0e..ed6441c 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -5,7 +5,6 @@ module CommandLine ( ) where import Data.Either -import Data.Maybe import qualified Data.HashMap.Strict as Map import Data.List.Extra import Development.Shake hiding (Normal) @@ -127,9 +126,7 @@ cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs lookupFreeze1 :: Map.HashMap TypeRep Dynamic -> Bool -lookupFreeze1 m = fromMaybe (freeze1 defaultCommandLineArgs) (freeze1 <$> maybeValue) - where - maybeValue = fromDynamic =<< Map.lookup (typeOf defaultCommandLineArgs) m +lookupFreeze1 = freeze1 . lookupExtra defaultCommandLineArgs cmdInstallDestDir :: Action (Maybe String) cmdInstallDestDir = installDestDir <$> cmdLineArgs diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 06ee663..4d2ae48 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -10,7 +10,7 @@ module Hadrian.Utilities ( unifyPath, (-/-), -- * Accessing Shake's type-indexed map - insertExtra, userSetting, + insertExtra, lookupExtra, userSetting, -- * Paths BuildRoot (..), buildRoot, isGeneratedSource, @@ -153,13 +153,18 @@ cmdLineLengthLimit | isWindows = 31000 insertExtra :: Typeable a => a -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic insertExtra value = Map.insert (typeOf value) (toDyn value) +-- | Lookup a value in Shake's type-indexed map. +lookupExtra :: Typeable a => a -> Map.HashMap TypeRep Dynamic -> a +lookupExtra defaultValue extra = fromMaybe defaultValue maybeValue + where + maybeValue = fromDynamic =<< Map.lookup (typeOf defaultValue) extra + -- | Lookup a user setting in Shake's type-indexed map 'shakeExtra'. If the -- setting is not found, return the provided default value instead. userSetting :: Typeable a => a -> Action a userSetting defaultValue = do extra <- shakeExtra <$> getShakeOptions - let maybeValue = fromDynamic =<< Map.lookup (typeOf defaultValue) extra - return $ fromMaybe defaultValue maybeValue + return $ lookupExtra defaultValue extra newtype BuildRoot = BuildRoot FilePath deriving Typeable diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index a6a2892..713e409 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -4,7 +4,6 @@ import Flavour import Expression import {-# SOURCE #-} Settings.Default --- TODO: Implement an equivalent of LAX_DEPENDENCIES = YES setting, see #250. developmentFlavour :: Stage -> Flavour developmentFlavour ghcStage = defaultFlavour { name = "devel" ++ show (fromEnum ghcStage) From git at git.haskell.org Fri Oct 27 01:01:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Track only files of known extensions when looking for module files (f910a1c) Message-ID: <20171027010124.C42B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f910a1c96f8e34171e0190931f907becfa40e2e9/ghc >--------------------------------------------------------------- commit f910a1c96f8e34171e0190931f907becfa40e2e9 Author: Andrey Mokhov Date: Mon May 16 21:46:41 2016 +0100 Track only files of known extensions when looking for module files Fix #254 >--------------------------------------------------------------- f910a1c96f8e34171e0190931f907becfa40e2e9 src/Oracles/ModuleFiles.hs | 47 +++++++++++++++++++++++++++++----------------- 1 file changed, 30 insertions(+), 17 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index f2b03f3..43a5f00 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -12,19 +12,31 @@ import Oracles.PackageData import Settings.Paths newtype ModuleFilesKey = ModuleFilesKey (Stage, Package) - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) newtype Generator = Generator (Stage, Package, FilePath) - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- The following generators and corresponding source extensions are supported: +-- | We scan for the following Haskell source extensions when looking for module +-- files. Note, we do not list "*.(l)hs-boot" files here, as they can never +-- appear by themselves and always have accompanying "*.(l)hs" master files. +haskellExtensions :: [String] +haskellExtensions = [".hs", ".lhs"] + +-- | Non-Haskell source extensions and corresponding builders. +otherExtensions :: [(String, Builder)] +otherExtensions = [ (".x" , Alex ) + , (".y" , Happy ) + , (".ly" , Happy ) + , (".hsc", Hsc2Hs) ] + +-- | We match the following file patterns when looking for module files. +moduleFilePatterns :: [FilePattern] +moduleFilePatterns = map ("*" ++) $ haskellExtensions ++ map fst otherExtensions + +-- | Given a FilePath determine the corresponding builder. determineBuilder :: FilePath -> Maybe Builder -determineBuilder file = case takeExtension file of - ".x" -> Just Alex - ".y" -> Just Happy - ".ly" -> Just Happy - ".hsc" -> Just Hsc2Hs - _ -> Nothing +determineBuilder file = lookup (takeExtension file) otherExtensions -- | Given a module name extract the directory and file name, e.g.: -- @@ -69,14 +81,16 @@ haskellSources context = do let modFile ("GHC.Prim", _) = autogen -/- "GHC/Prim.hs" modFile (m, Nothing ) = generatedFile context m modFile (m, Just file ) - | takeExtension file `elem` [".hs", ".lhs"] = file + | takeExtension file `elem` haskellExtensions = file | otherwise = generatedFile context m map modFile <$> contextFiles context +-- | Generated module files live in the 'Context' specific build directory. generatedFile :: Context -> String -> FilePath generatedFile context moduleName = buildPath context -/- replaceEq '.' '/' moduleName <.> "hs" +-- | Module files for a given 'Context'. contextFiles :: Context -> Action [(String, Maybe FilePath)] contextFiles context at Context {..} = do modules <- fmap sort . pkgDataList . Modules $ buildPath context @@ -95,7 +109,7 @@ contextFiles context at Context {..} = do -- Just "compiler/parser/Lexer.x"]. The oracle ignores @.(l)hs-boot@ files. moduleFilesOracle :: Rules () moduleFilesOracle = void $ do - void $ addOracle $ \(ModuleFilesKey (stage, package)) -> do + void . addOracle $ \(ModuleFilesKey (stage, package)) -> do let path = buildPath $ vanillaContext stage package srcDirs <- pkgDataList $ SrcDirs path modules <- fmap sort . pkgDataList $ Modules path @@ -105,10 +119,9 @@ moduleFilesOracle = void $ do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do let fullDir = unifyPath $ dir -/- mDir - files <- getDirectoryFiles fullDir ["*"] - let noBoot = filter (not . (isSuffixOf "-boot")) files - cmp fe f = compare (dropExtension fe) f - found = intersectOrd cmp noBoot mFiles + files <- getDirectoryFiles fullDir moduleFilePatterns + let cmp fe f = compare (dropExtension fe) f + found = intersectOrd cmp files mFiles return (map (fullDir -/-) found, mDir) let pairs = sort [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ] @@ -118,14 +131,14 @@ moduleFilesOracle = void $ do ++ f1 ++ " and " ++ f2 ++ "." return $ lookupAll modules pairs - -- Optimisation: we discard .(l)hs files here, because they are never used + -- Optimisation: we discard Haskell files here, because they are never used -- as generators, and hence would be discarded in 'findGenerator' anyway. generators <- newCache $ \(stage, package) -> do let context = vanillaContext stage package files <- contextFiles context return $ Map.fromList [ (generatedFile context modName, src) | (modName, Just src) <- files - , takeExtension src `notElem` [".hs", ".lhs"] ] + , takeExtension src `notElem` haskellExtensions ] addOracle $ \(Generator (stage, package, file)) -> Map.lookup file <$> generators (stage, package) From git at git.haskell.org Fri Oct 27 01:01:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Document the --freeze1 flag (7c507e1) Message-ID: <20171027010128.229E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c507e1c6e0bdc622b033d75f3d5c75790e751b0/ghc >--------------------------------------------------------------- commit 7c507e1c6e0bdc622b033d75f3d5c75790e751b0 Author: Andrey Mokhov Date: Tue Oct 10 14:02:17 2017 +0100 Document the --freeze1 flag See #250 >--------------------------------------------------------------- 7c507e1c6e0bdc622b033d75f3d5c75790e751b0 README.md | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index ad61ef3..9eb759e 100644 --- a/README.md +++ b/README.md @@ -58,6 +58,12 @@ currently supports several others: `vanilla` way, which speeds up builds by 3-4x. Build flavours are documented [here](https://github.com/snowleopard/hadrian/blob/master/doc/flavours.md). +* `--freeze1`: freeze Stage1 GHC, i.e. do not rebuild it even if some of its source files +are out-of-date. This allows to significantly reduce the rebuild time when you are working +on a feature that affects both Stage1 and Stage2 compilers, but may lead to incorrect +build results. To unfreeze Stage1 GHC simply drop the `--freeze1` flag and Hadrian will +rebuild all out-of-date files. + * `--haddock`: build Haddock documentation. * `--integer-simple`: build GHC using the `integer-simple` integer library (instead @@ -136,7 +142,6 @@ The new build system still lacks many important features: * Validation is not implemented: [#187][validation-issue]. * Dynamic linking on Windows is not supported [#343][dynamic-windows-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). -* Not all modes of the old build system are supported, e.g. [#250][freeze-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. * There is no support for binary distribution: [#219][install-issue]. @@ -180,7 +185,6 @@ enjoy the project. [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 [dynamic-windows-issue]: https://github.com/snowleopard/hadrian/issues/343 -[freeze-issue]: https://github.com/snowleopard/hadrian/issues/250 [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 [milestones]: https://github.com/snowleopard/hadrian/milestones From git at git.haskell.org Fri Oct 27 01:01:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghc-boot-th package (e91daa3) Message-ID: <20171027010128.6535F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e91daa3eb50b46441619d5ba43852c8dc1f9a164/ghc >--------------------------------------------------------------- commit e91daa3eb50b46441619d5ba43852c8dc1f9a164 Author: Andrey Mokhov Date: Mon May 16 23:10:48 2016 +0100 Add ghc-boot-th package >--------------------------------------------------------------- e91daa3eb50b46441619d5ba43852c8dc1f9a164 src/GHC.hs | 17 +++++++++-------- src/Settings/Packages.hs | 4 ++-- 2 files changed, 11 insertions(+), 10 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 02c76f9..303beca 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -2,11 +2,11 @@ module GHC ( array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, - ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, - primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unlit, unix, win32, xhtml, + genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim, + ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, + integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, + pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, + time, touchy, transformers, unlit, unix, win32, xhtml, defaultKnownPackages, programPath, contextDirectory, rtsContext ) where @@ -25,7 +25,7 @@ defaultKnownPackages :: [Package] defaultKnownPackages = [ array, base, binary, bytestring, cabal, compiler, containers, compareSizes , deepseq, deriveConstants, directory, dllSplit, filepath, genapply - , genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim + , genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim , ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp , integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time @@ -34,8 +34,8 @@ defaultKnownPackages = -- | Package definitions, see 'Package'. array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, - haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, + genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim, + ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml :: Package @@ -57,6 +57,7 @@ genapply = utility "genapply" genprimopcode = utility "genprimopcode" ghc = topLevel "ghc-bin" `setPath` "ghc" `setType` Program ghcBoot = library "ghc-boot" +ghcBootTh = library "ghc-boot-th" ghcCabal = utility "ghc-cabal" ghci = library "ghci" ghcPkg = utility "ghc-pkg" diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs index 6888d0a..40d9ebf 100644 --- a/src/Settings/Packages.hs +++ b/src/Settings/Packages.hs @@ -20,8 +20,8 @@ defaultPackages = mconcat packagesStage0 :: Packages packagesStage0 = mconcat - [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg - , hsc2hs, hoopl, hpc, templateHaskell, transformers ] + [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcBootTh, ghcCabal + , ghcPkg, hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode , hp2ps, unlit ] From git at git.haskell.org Fri Oct 27 01:01:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't print boot's diagnostic info by default (dffda59) Message-ID: <20171027010132.90E213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dffda59ac338bef1ab53e9ed4299ead89bbbeff7/ghc >--------------------------------------------------------------- commit dffda59ac338bef1ab53e9ed4299ead89bbbeff7 Author: Andrey Mokhov Date: Tue Oct 10 15:18:15 2017 +0100 Don't print boot's diagnostic info by default >--------------------------------------------------------------- dffda59ac338bef1ab53e9ed4299ead89bbbeff7 src/Rules/Configure.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index a4ef084..dd016c1 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -38,4 +38,5 @@ configureRules = do else do need ["configure.ac"] putBuild "| Running boot..." - quietly $ cmd "python3 boot" + verbosity <- getVerbosity + quietly $ cmd [EchoStdout (verbosity >= Loud)] "python3 boot" From git at git.haskell.org Fri Oct 27 01:01:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dreary package signagures (34545e3) Message-ID: <20171027010132.A036A3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/34545e3d0d54223512f0c05909a23bdb61ad3755/ghc >--------------------------------------------------------------- commit 34545e3d0d54223512f0c05909a23bdb61ad3755 Author: Andrey Mokhov Date: Mon May 16 23:16:59 2016 +0100 Drop dreary package signagures >--------------------------------------------------------------- 34545e3d0d54223512f0c05909a23bdb61ad3755 src/GHC.hs | 12 +++--------- 1 file changed, 3 insertions(+), 9 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 303beca..d75a046 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,4 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( array, base, binary, bytestring, cabal, compiler, containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, @@ -18,7 +19,7 @@ import Stage -- | These are all GHC packages we know about. Build rules will be generated for -- all of them. However, not all of these packages will be built. For example, --- package /win32/ is built only on Windows. +-- package 'win32' is built only on Windows. -- "Packages" defines default conditions for building each package, which can -- be overridden in "Settings.User". defaultKnownPackages :: [Package] @@ -32,14 +33,6 @@ defaultKnownPackages = , touchy, transformers, unlit, unix, win32, xhtml ] -- | Package definitions, see 'Package'. -array, base, binary, bytestring, cabal, compiler, containers, compareSizes, - deepseq, deriveConstants, directory, dllSplit, filepath, genapply, - genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, ghcPkg, ghcPrim, - ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, - primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, - touchy, transformers, unlit, unix, win32, xhtml :: Package - array = library "array" base = library "base" binary = library "binary" @@ -126,6 +119,7 @@ programPath context at Context {..} installProgram name = pkgPath package -/- contextDirectory context -/- "build/tmp" -/- name <.> exe +-- TODO: Move this elsewhere. rtsContext :: Context rtsContext = vanillaContext Stage1 rts From git at git.haskell.org Fri Oct 27 01:01:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Register the access to the package database when compiling with GHC (03ebefd) Message-ID: <20171027010136.1A8983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03ebefdfaf33592d86105ad63de960adb9143d11/ghc >--------------------------------------------------------------- commit 03ebefdfaf33592d86105ad63de960adb9143d11 Author: Andrey Mokhov Date: Tue Oct 10 15:38:30 2017 +0100 Register the access to the package database when compiling with GHC >--------------------------------------------------------------- 03ebefdfaf33592d86105ad63de960adb9143d11 src/Rules/Compile.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index c71079a..a4b1278 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -17,7 +17,7 @@ compilePackage rs context at Context {..} = do src <- obj2src context obj need [src] needDependencies context src $ obj <.> "d" - build $ target context (compiler stage) [src] [obj] + buildWithResources rs $ target context (compiler stage) [src] [obj] compileHs = \[obj, _hi] -> do path <- buildPath context (src, deps) <- lookupDependencies (path -/- ".dependencies") obj From git at git.haskell.org Fri Oct 27 01:01:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build progress info colours customisable, drop putError and putOracle. (fa77d93) Message-ID: <20171027010136.4E6BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fa77d934a2f15509e33c3ee1aafb88cb20abc1d1/ghc >--------------------------------------------------------------- commit fa77d934a2f15509e33c3ee1aafb88cb20abc1d1 Author: Andrey Mokhov Date: Tue May 17 23:36:41 2016 +0100 Make build progress info colours customisable, drop putError and putOracle. See #244. >--------------------------------------------------------------- fa77d934a2f15509e33c3ee1aafb88cb20abc1d1 src/Base.hs | 64 +++++++++++++++------------------------------ src/Builder.hs | 4 +-- src/Expression.hs | 2 +- src/Oracles/Config.hs | 4 +-- src/Oracles/Config/Flag.hs | 4 +-- src/Oracles/Dependencies.hs | 6 ++--- src/Oracles/LookupInPath.hs | 4 +-- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/PackageDb.hs | 3 ++- src/Oracles/PackageDeps.hs | 2 +- src/Oracles/WindowsPath.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Configure.hs | 5 ++-- src/Rules/Generate.hs | 6 ++--- src/Rules/Gmp.hs | 4 +-- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Rules/Selftest.hs | 1 + src/Settings/User.hs | 20 ++++++++++---- 21 files changed, 67 insertions(+), 76 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 fa77d934a2f15509e33c3ee1aafb88cb20abc1d1 From git at git.haskell.org Fri Oct 27 01:01:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix usage of -with-rtsopts (#429) (e4f9829) Message-ID: <20171027010140.352A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4f982978c82a274d7befec8be19b3bd2d238c5d/ghc >--------------------------------------------------------------- commit e4f982978c82a274d7befec8be19b3bd2d238c5d Author: Ben Gamari Date: Tue Oct 10 18:43:37 2017 -0400 Fix usage of -with-rtsopts (#429) When I added `-qg` to the default RTS options in 57cfa03c23047bb0c731428e97ca716d9a1cf312 (#385) I neglected to consider that it the -with-rtsopts flag would override the previous flag setting `-I0`. This had the effect of reenabling idle GC, causing GC time to regress terribly. I likely didn't notice this since I had passed the flags directly to the `hadrian` executable with `+RTS` while testing. Moreover, I mistakenly wrote `-qg0`, which (somewhat confusingly) actually *enables* parallel GC. Instead I wanted to write `-qg`. >--------------------------------------------------------------- e4f982978c82a274d7befec8be19b3bd2d238c5d hadrian.cabal | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 48514e1..8e583c7 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -133,10 +133,9 @@ executable hadrian -Wredundant-constraints -fno-warn-name-shadowing -rtsopts - -- Disable idle GC to avoid redundant GCs while waiting - -- for external processes - -with-rtsopts=-I0 - -- Don't use parallel GC as the synchronization time tends to eat any - -- benefit. - -with-rtsopts=-qg0 + -- * -I0: Disable idle GC to avoid redundant GCs while + -- waiting for external processes + -- * -qg: Don't use parallel GC as the synchronization + -- time tends to eat any benefit. + "-with-rtsopts=-I0 -qg" -threaded From git at git.haskell.org Fri Oct 27 01:01:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move versionToInt to Settings/Builders/Haddock (acc2c7e) Message-ID: <20171027010140.632673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acc2c7eef93e5372ce355de6c49cc24f9c507dab/ghc >--------------------------------------------------------------- commit acc2c7eef93e5372ce355de6c49cc24f9c507dab Author: Andrey Mokhov Date: Tue May 17 23:41:55 2016 +0100 Move versionToInt to Settings/Builders/Haddock >--------------------------------------------------------------- acc2c7eef93e5372ce355de6c49cc24f9c507dab src/Base.hs | 8 +------- src/Settings/Builders/Haddock.hs | 6 ++++++ 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 328eb98..8f02865 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -19,7 +19,7 @@ module Base ( -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, quote, replaceSeparators, - unifyPath, (-/-), versionToInt, matchVersionedFilePath, putColoured + unifyPath, (-/-), matchVersionedFilePath, putColoured ) where import Control.Applicative @@ -74,12 +74,6 @@ replaceWhen p to = map (\from -> if p from then to else from) quote :: String -> String quote s = "\"" ++ s ++ "\"" --- | Given a version string such as "2.16.2" produce an integer equivalent. -versionToInt :: String -> Int -versionToInt s = major * 1000 + minor * 10 + patch - where - [major, minor, patch] = map read . words $ replaceEq '.' ' ' s - -- | Normalise a path and convert all path separators to @/@, even on Windows. unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 37964b4..4c0b6f7 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -8,6 +8,12 @@ import Predicate import Settings import Settings.Builders.Ghc +-- | Given a version string such as "2.16.2" produce an integer equivalent. +versionToInt :: String -> Int +versionToInt s = major * 1000 + minor * 10 + patch + where + [major, minor, patch] = map read . words $ replaceEq '.' ' ' s + haddockBuilderArgs :: Args haddockBuilderArgs = builder Haddock ? do output <- getOutput From git at git.haskell.org Fri Oct 27 01:01:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make Brief the default setting of the --progress-info flag (10b8358) Message-ID: <20171027010144.2EFAC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/10b8358882867ebfef0a48b9ba28d08fcf37eedb/ghc >--------------------------------------------------------------- commit 10b8358882867ebfef0a48b9ba28d08fcf37eedb Author: Andrey Mokhov Date: Wed Oct 11 00:03:56 2017 +0100 Make Brief the default setting of the --progress-info flag See #428 >--------------------------------------------------------------- 10b8358882867ebfef0a48b9ba28d08fcf37eedb .travis.yml | 6 +++--- README.md | 4 ++-- appveyor.yml | 2 +- circle.yml | 2 +- src/CommandLine.hs | 2 +- src/Hadrian/Utilities.hs | 2 +- 6 files changed, 9 insertions(+), 9 deletions(-) diff --git a/.travis.yml b/.travis.yml index 203ee82..e14f962 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - ./build.cabal.sh selftest # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- - os: linux env: MODE="--flavour=quickest --integer-simple" @@ -40,7 +40,7 @@ matrix: script: # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. @@ -56,7 +56,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- install: # Add Cabal to PATH diff --git a/README.md b/README.md index 9eb759e..2530714 100644 --- a/README.md +++ b/README.md @@ -75,8 +75,8 @@ whether the console supports colours; this is the default setting), and `always` colours). * `--progress-info=STYLE`: choose how build progress info is printed. There are four -settings: `none`, `brief` (one line per build command), `normal` (typically a box per -build command; this is the default setting), and `unicorn` (when `normal` just won't do). +settings: `none`, `brief` (one line per build command; this is the default setting), +`normal` (typically a box per build command), and `unicorn` (when `normal` just won't do). * `--skip-configure`: use this flag to suppress the default behaviour of Hadrian that runs the `boot` and `configure` scripts automatically if need be, so that you don't have diff --git a/appveyor.yml b/appveyor.yml index c51983a..2f4653a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -33,7 +33,7 @@ build_script: - stack exec hadrian -- --directory ".." selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-info=brief --progress-colour=never --profile=- + - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. diff --git a/circle.yml b/circle.yml index 93cf47f..48653e8 100644 --- a/circle.yml +++ b/circle.yml @@ -33,7 +33,7 @@ compile: - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- test: override: diff --git a/src/CommandLine.hs b/src/CommandLine.hs index ed6441c..978a420 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -34,7 +34,7 @@ defaultCommandLineArgs = CommandLineArgs , installDestDir = Nothing , integerSimple = False , progressColour = Auto - , progressInfo = Normal + , progressInfo = Brief , skipConfigure = False , splitObjects = False } diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 4d2ae48..1cd22b1 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -313,7 +313,7 @@ putProgressInfo msg = do -- | Render an action. renderAction :: String -> FilePath -> FilePath -> Action String renderAction what input output = do - progressInfo <- userSetting Normal + progressInfo <- userSetting Brief return $ case progressInfo of None -> "" Brief -> "| " ++ what ++ ": " ++ i ++ " => " ++ o From git at git.haskell.org Fri Oct 27 01:01:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't celebrate duplication (a2b39be) Message-ID: <20171027010144.499A73A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a2b39be6d48c9844f7d4519406c72857d38dd233/ghc >--------------------------------------------------------------- commit a2b39be6d48c9844f7d4519406c72857d38dd233 Author: Andrey Mokhov Date: Tue May 17 23:45:39 2016 +0100 Don't celebrate duplication >--------------------------------------------------------------- a2b39be6d48c9844f7d4519406c72857d38dd233 src/Rules/Generate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index daebe5d..d19ceac 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -134,7 +134,7 @@ generatePackageCode context@(Context stage pkg _) = newFile = oldPath ++ (drop (length path) file) createDirectory $ takeDirectory newFile liftIO $ IO.copyFile file newFile - putSuccess $ "| Duplicate file " ++ file ++ " -> " ++ newFile + putBuild $ "| Duplicate file " ++ file ++ " -> " ++ newFile when (pkg == rts) $ path -/- "AutoApply.cmm" %> \file -> do build $ Target context GenApply [] [file] From git at git.haskell.org Fri Oct 27 01:01:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rearrange unix build scripts. (#430) (45da08b) Message-ID: <20171027010147.F32403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45da08bb3c8b6806c0b3484e32abaeb4358cc6c1/ghc >--------------------------------------------------------------- commit 45da08bb3c8b6806c0b3484e32abaeb4358cc6c1 Author: Doug Wilson Date: Wed Oct 11 14:32:35 2017 +1300 Rearrange unix build scripts. (#430) Addresses Issue #428 >--------------------------------------------------------------- 45da08bb3c8b6806c0b3484e32abaeb4358cc6c1 .travis.yml | 8 ++--- build.cabal.sh => build.global-db.sh | 0 build.sh | 69 +++++++++++++++++++++--------------- build.stack.sh => build.stack.nix.sh | 8 +---- build.stack.sh | 2 +- circle.yml | 4 +-- stack.yaml | 1 + 7 files changed, 50 insertions(+), 42 deletions(-) diff --git a/.travis.yml b/.travis.yml index e14f962..e2455b2 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,10 +18,10 @@ matrix: script: # Run internal Hadrian tests - - ./build.cabal.sh selftest + - ./build.sh selftest # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - ./build.sh -j $MODE --no-progress --progress-colour=never --profile=- - os: linux env: MODE="--flavour=quickest --integer-simple" @@ -40,7 +40,7 @@ matrix: script: # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - ./build.sh -j $MODE --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. @@ -56,7 +56,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - ./build.sh -j $MODE --no-progress --progress-colour=never --profile=- install: # Add Cabal to PATH diff --git a/build.cabal.sh b/build.global-db.sh similarity index 100% rename from build.cabal.sh rename to build.global-db.sh diff --git a/build.sh b/build.sh index 0f957cf..2a0e8a7 100755 --- a/build.sh +++ b/build.sh @@ -1,5 +1,7 @@ #!/usr/bin/env bash +CABAL=cabal + set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -28,34 +30,45 @@ function rl { echo "$RESULT" } -root="$(dirname "$(rl "$0")")" +absoluteRoot="$(dirname "$(rl "$0")")" +cd "$absoluteRoot" -if type cabal > /dev/null 2>&1; then - CABVERSTR=$(cabal --numeric-version) - CABVER=( ${CABVERSTR//./ } ) - if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then - echo "** Cabal 1.24 or later detected. Please consider using the 'build.cabal.sh' script **" - echo "" - fi +if ! type "$CABAL" > /dev/null; then + echo "Please make sure 'cabal' is in your PATH" + exit 2 fi -mkdir -p "$root/bin" - -ghc \ - "$root/src/Main.hs" \ - -Wall \ - -fno-warn-name-shadowing \ - -XRecordWildCards \ - -i"$root/src" \ - -i"$root/../libraries/Cabal/Cabal" \ - -rtsopts \ - -with-rtsopts=-I0 \ - -threaded \ - -outputdir="$root/bin" \ - -j -O \ - -o "$root/bin/hadrian" - -"$root/bin/hadrian" \ - --lint \ - --directory "$root/.." \ - "$@" +CABVERSTR=$("$CABAL" --numeric-version) + +CABVER=( ${CABVERSTR//./ } ) + +if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then + # New enough cabal version detected, so + # let's use the superior 'cabal new-build' mode + + # there's no 'cabal new-run' yet, but it's easy to emulate + "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian + $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" + +else + # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals + echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." + + # Initialize sandbox if necessary + if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then + "$CABAL" sandbox init + "$CABAL" sandbox add-source ../libraries/Cabal/Cabal + "$CABAL" install \ + --dependencies-only \ + --disable-library-profiling \ + --disable-shared + fi + + "$CABAL" run hadrian -- \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" +fi diff --git a/build.stack.sh b/build.stack.nix.sh similarity index 82% copy from build.stack.sh copy to build.stack.nix.sh index 23f4833..59ac061 100755 --- a/build.stack.sh +++ b/build.stack.nix.sh @@ -29,11 +29,5 @@ function rl { } absoluteRoot="$(dirname "$(rl "$0")")" -cd "$absoluteRoot" -stack build --no-library-profiling - -stack exec hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" +HADRIAN_NIX=YES ${absoluteRoot}/build.stack.sh diff --git a/build.stack.sh b/build.stack.sh index 23f4833..2b1ff1d 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -31,7 +31,7 @@ function rl { absoluteRoot="$(dirname "$(rl "$0")")" cd "$absoluteRoot" -stack build --no-library-profiling +stack build --no-library-profiling ${HADRIAN_NIX:+--nix} stack exec hadrian -- \ --lint \ diff --git a/circle.yml b/circle.yml index 48653e8..a386d72 100644 --- a/circle.yml +++ b/circle.yml @@ -30,10 +30,10 @@ compile: # XXX: export PATH doesn't work well either, so we use inline env # Self test - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh -j $MODE --no-progress --progress-colour=never --profile=- test: override: diff --git a/stack.yaml b/stack.yaml index 2a92f26..da03763 100644 --- a/stack.yaml +++ b/stack.yaml @@ -12,6 +12,7 @@ extra-deps: - shake-0.16 nix: + enable: false packages: - autoconf - automake From git at git.haskell.org Fri Oct 27 01:01:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a paragraph on customising progress messages (2c77b71) Message-ID: <20171027010148.212B93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c77b7107ccf663598b9b64a22f3a4c5bc39b568/ghc >--------------------------------------------------------------- commit 2c77b7107ccf663598b9b64a22f3a4c5bc39b568 Author: Andrey Mokhov Date: Tue May 17 23:55:16 2016 +0100 Add a paragraph on customising progress messages See #244. [skip ci] >--------------------------------------------------------------- 2c77b7107ccf663598b9b64a22f3a4c5bc39b568 doc/user-settings.md | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/doc/user-settings.md b/doc/user-settings.md index 4624e2d..1433ae9 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -144,3 +144,20 @@ splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock ``` + +Hadrian prints various progress info during the build. You can customise how this +info is printed by overriding `putBuild` and `putSuccess` commands: + +```haskell +-- | Customise build progress messages (e.g. executing a build command). +putBuild :: String -> Action () +putBuild = putColoured Vivid White + +-- | Customise build success messages (e.g. a package is built successfully). +putSuccess :: String -> Action () +putSuccess = putColoured Vivid Green +``` + +You can tune colours for your favourite terminal and also change the verbosity +level, e.g. by setting `putSuccess = putLoud`, which will hide success messages +unless Hadrian is called with `--verbose` flag. From git at git.haskell.org Fri Oct 27 01:01:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: build.cabal.sh: Use cabal new-run (#435) (6942b2d) Message-ID: <20171027010152.3E6AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6942b2dc08832f1521e2e8c46993c5ab977d2cb7/ghc >--------------------------------------------------------------- commit 6942b2dc08832f1521e2e8c46993c5ab977d2cb7 Author: Ben Gamari Date: Thu Oct 12 18:17:50 2017 -0400 build.cabal.sh: Use cabal new-run (#435) The previous approach was terribly unreliable, leading me to waste an hour debugging #425. >--------------------------------------------------------------- 6942b2dc08832f1521e2e8c46993c5ab977d2cb7 build.sh | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/build.sh b/build.sh index 2a0e8a7..5d1c2c2 100755 --- a/build.sh +++ b/build.sh @@ -46,9 +46,8 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th # New enough cabal version detected, so # let's use the superior 'cabal new-build' mode - # there's no 'cabal new-run' yet, but it's easy to emulate "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ + "$CABAL" new-run -- hadrian \ --lint \ --directory "$absoluteRoot/.." \ "$@" From git at git.haskell.org Fri Oct 27 01:01:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace quote by show (d6a0d7a) Message-ID: <20171027010152.45A9B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6a0d7af44a6365e784cfa3e1d0da114b958e3f1/ghc >--------------------------------------------------------------- commit d6a0d7af44a6365e784cfa3e1d0da114b958e3f1 Author: Andrey Mokhov Date: Wed May 18 00:11:12 2016 +0100 Replace quote by show >--------------------------------------------------------------- d6a0d7af44a6365e784cfa3e1d0da114b958e3f1 src/Base.hs | 11 ++++----- src/Rules/Generators/ConfigHs.hs | 36 ++++++++++++++-------------- src/Rules/Generators/GhcBootPlatformH.hs | 24 +++++++++---------- src/Rules/Generators/GhcPlatformH.hs | 16 ++++++------- src/Rules/Generators/GhcSplit.hs | 4 ++-- src/Rules/Generators/VersionHs.hs | 6 ++--- src/Settings/Packages/Rts.hs | 40 ++++++++++++++++---------------- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/User.hs | 2 +- 9 files changed, 69 insertions(+), 72 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 d6a0d7af44a6365e784cfa3e1d0da114b958e3f1 From git at git.haskell.org Fri Oct 27 01:01:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix the list of Hadrian arguments (4b42da3) Message-ID: <20171027010156.3093A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b42da3ca484718708b157889bd0780b3076f4b0/ghc >--------------------------------------------------------------- commit 4b42da3ca484718708b157889bd0780b3076f4b0 Author: Andrey Mokhov Date: Thu Oct 12 23:29:00 2017 +0100 Fix the list of Hadrian arguments See #435 >--------------------------------------------------------------- 4b42da3ca484718708b157889bd0780b3076f4b0 build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 5d1c2c2..6c2c038 100755 --- a/build.sh +++ b/build.sh @@ -47,7 +47,7 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th # let's use the superior 'cabal new-build' mode "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - "$CABAL" new-run -- hadrian \ + "$CABAL" new-run hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ "$@" From git at git.haskell.org Fri Oct 27 01:01:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:01:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add quote function (c81dc684f7) Message-ID: <20171027010156.366D33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c81dc684f7206ebabf877d54c8a740398e5e425a/ghc >--------------------------------------------------------------- commit c81dc684f7206ebabf877d54c8a740398e5e425a Author: Andrey Mokhov Date: Wed May 18 00:28:08 2016 +0100 Add quote function >--------------------------------------------------------------- c81dc684f7206ebabf877d54c8a740398e5e425a src/Base.hs | 6 +++++- src/Builder.hs | 6 +++--- src/Oracles/Config.hs | 2 +- src/Oracles/Config/Flag.hs | 6 +++--- src/Oracles/Dependencies.hs | 4 ++-- src/Rules/Actions.hs | 2 +- src/Rules/Data.hs | 10 +++++----- src/Rules/Generate.hs | 4 ++-- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 6 +++--- 10 files changed, 26 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c81dc684f7206ebabf877d54c8a740398e5e425a From git at git.haskell.org Fri Oct 27 01:02:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Restore the original build script relying on the global package database (2f88f30) Message-ID: <20171027010200.184D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f88f30099934a46fb9ceceb4267924e3975ecaa/ghc >--------------------------------------------------------------- commit 2f88f30099934a46fb9ceceb4267924e3975ecaa Author: Andrey Mokhov Date: Sat Oct 14 23:44:49 2017 +0100 Restore the original build script relying on the global package database See #435, #430 >--------------------------------------------------------------- 2f88f30099934a46fb9ceceb4267924e3975ecaa build.global-db.sh | 66 ++++++++++++++++++------------------------------------ 1 file changed, 22 insertions(+), 44 deletions(-) diff --git a/build.global-db.sh b/build.global-db.sh index 2a0e8a7..5f1579b 100755 --- a/build.global-db.sh +++ b/build.global-db.sh @@ -1,7 +1,5 @@ #!/usr/bin/env bash -CABAL=cabal - set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -30,45 +28,25 @@ function rl { echo "$RESULT" } -absoluteRoot="$(dirname "$(rl "$0")")" -cd "$absoluteRoot" - -if ! type "$CABAL" > /dev/null; then - echo "Please make sure 'cabal' is in your PATH" - exit 2 -fi - -CABVERSTR=$("$CABAL" --numeric-version) - -CABVER=( ${CABVERSTR//./ } ) - -if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then - # New enough cabal version detected, so - # let's use the superior 'cabal new-build' mode - - # there's no 'cabal new-run' yet, but it's easy to emulate - "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" - -else - # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals - echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." - - # Initialize sandbox if necessary - if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then - "$CABAL" sandbox init - "$CABAL" sandbox add-source ../libraries/Cabal/Cabal - "$CABAL" install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared - fi - - "$CABAL" run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" -fi +root="$(dirname "$(rl "$0")")" + +mkdir -p "$root/bin" + +ghc \ + "$root/src/Main.hs" \ + -Wall \ + -fno-warn-name-shadowing \ + -XRecordWildCards \ + -i"$root/src" \ + -i"$root/../libraries/Cabal/Cabal" \ + -rtsopts \ + -with-rtsopts=-I0 \ + -threaded \ + -outputdir="$root/bin" \ + -j -O \ + -o "$root/bin/hadrian" + +"$root/bin/hadrian" \ + --lint \ + --directory "$root/.." \ + "$@" \ No newline at end of file From git at git.haskell.org Fri Oct 27 01:02:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix putSuccess (1080ebf) Message-ID: <20171027010200.2B2D83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1080ebfc611e8cdae0b4efb166f166a9cebfa6e8/ghc >--------------------------------------------------------------- commit 1080ebfc611e8cdae0b4efb166f166a9cebfa6e8 Author: Andrey Mokhov Date: Wed May 18 00:53:54 2016 +0100 Fix putSuccess >--------------------------------------------------------------- 1080ebfc611e8cdae0b4efb166f166a9cebfa6e8 src/Settings/User.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 60aeb89..16c7c25 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -102,4 +102,4 @@ putBuild = putColoured Vivid White -- | Customise build success messages (e.g. a package is built successfully). putSuccess :: String -> Action () -putSuccess = withVerbosity Loud . putColoured Vivid Green +putSuccess = putColoured Vivid Green From git at git.haskell.org Fri Oct 27 01:02:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use `new-build` for pre-2.1 Cabal (65bcdcb) Message-ID: <20171027010204.0BCDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65bcdcbe7dd61dace537fd956b5d5d40aed6d8c9/ghc >--------------------------------------------------------------- commit 65bcdcbe7dd61dace537fd956b5d5d40aed6d8c9 Author: Andrey Mokhov Date: Tue Oct 17 23:38:17 2017 +0100 Don't use `new-build` for pre-2.1 Cabal See #438 >--------------------------------------------------------------- 65bcdcbe7dd61dace537fd956b5d5d40aed6d8c9 build.sh | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/build.sh b/build.sh index 6c2c038..d2bdb85 100755 --- a/build.sh +++ b/build.sh @@ -42,9 +42,10 @@ CABVERSTR=$("$CABAL" --numeric-version) CABVER=( ${CABVERSTR//./ } ) -if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then - # New enough cabal version detected, so - # let's use the superior 'cabal new-build' mode +if [ "${CABVER[0]}" -gt 2 -o "${CABVER[0]}" -eq 2 -a "${CABVER[1]}" -ge 1 ]; then + # New enough Cabal version detected, so let's use the superior new-build + new-run + # modes. Note that pre-2.1 Cabal does not support passing additional parameters + # to the executable (hadrian) after the separator '--', see #438. "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian "$CABAL" new-run hadrian -- \ @@ -53,8 +54,8 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th "$@" else - # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals - echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." + # The logic below is quite fragile, but it's better than nothing for pre-2.1 Cabal. + echo "Old pre cabal 2.1 version detected. Falling back to legacy 'cabal sandbox' mode." # Initialize sandbox if necessary if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then From git at git.haskell.org Fri Oct 27 01:02:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --progress-colour command line flag (aa9c65b) Message-ID: <20171027010204.132543A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aa9c65b3adb91b56c1974a0db39ef3c5082e816c/ghc >--------------------------------------------------------------- commit aa9c65b3adb91b56c1974a0db39ef3c5082e816c Author: Andrey Mokhov Date: Wed May 18 02:54:23 2016 +0100 Add --progress-colour command line flag Fix #244. >--------------------------------------------------------------- aa9c65b3adb91b56c1974a0db39ef3c5082e816c src/Base.hs | 27 +++++++++++++++++---------- src/CmdLineFlag.hs | 51 ++++++++++++++++++++++++++++++++++++--------------- 2 files changed, 53 insertions(+), 25 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 6fe8ac1..cb040d4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -38,6 +38,8 @@ import System.Console.ANSI import System.IO import System.Info +import CmdLineFlag + -- TODO: reexport Stage, etc.? -- | Hadrian lives in 'hadrianPath' directory of the GHC tree. @@ -144,14 +146,19 @@ matchVersionedFilePath prefix suffix filePath = -- | A more colourful version of Shake's putNormal. putColoured :: ColorIntensity -> Color -> String -> Action () putColoured intensity colour msg = do - liftIO $ set [SetColor Foreground intensity colour] + c <- useColour + when c . liftIO $ setSGR [SetColor Foreground intensity colour] putNormal msg - liftIO $ set [] - liftIO $ hFlush stdout - where - set a = do - supported <- hSupportsANSI stdout - when (win || supported) $ setSGR a - -- An ugly hack to always try to print colours when on mingw and cygwin. - -- See: https://github.com/snowleopard/hadrian/pull/253 - win = "mingw" `isPrefixOf` os || "cygwin" `isPrefixOf` os + when c . liftIO $ do + setSGR [] + hFlush stdout + +useColour :: Action Bool +useColour = case cmdProgressColour of + Never -> return False + Always -> return True + Auto -> do + supported <- liftIO $ hSupportsANSI stdout + -- An ugly hack to always try to print colours when on mingw and cygwin. + let windows = any (`isPrefixOf` os) ["mingw", "cygwin"] + return $ windows || supported diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 8fc1487..10c39f2 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,35 +1,39 @@ module CmdLineFlag ( putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, Flavour (..), - cmdProgressInfo, ProgressInfo (..), cmdSkipConfigure, cmdSplitObjects + cmdProgressColour, ProgressColour (..), cmdProgressInfo, ProgressInfo (..), + cmdSkipConfigure, cmdSplitObjects ) where import Data.IORef import Data.List.Extra import System.Console.GetOpt -import System.IO.Unsafe (unsafePerformIO) +import System.IO.Unsafe -- | 'CmdLineFlag.Untracked' is a collection of flags that can be passed via the -- command line. These flags are not tracked, that is they do not force any -- build rules to be rurun. data Untracked = Untracked - { buildHaddock :: Bool - , flavour :: Flavour - , progressInfo :: ProgressInfo - , skipConfigure :: Bool - , splitObjects :: Bool } + { buildHaddock :: Bool + , flavour :: Flavour + , progressColour :: ProgressColour + , progressInfo :: ProgressInfo + , skipConfigure :: Bool + , splitObjects :: Bool } deriving (Eq, Show) -data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -data Flavour = Default | Quick deriving (Eq, Show) +data Flavour = Default | Quick deriving (Eq, Show) +data ProgressColour = Never | Auto | Always deriving (Eq, Show) +data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked defaultUntracked = Untracked - { buildHaddock = False - , flavour = Default - , progressInfo = Normal - , skipConfigure = False - , splitObjects = False } + { buildHaddock = False + , flavour = Default + , progressColour = Auto + , progressInfo = Normal + , skipConfigure = False + , splitObjects = False } readBuildHaddock :: Either String (Untracked -> Untracked) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } @@ -45,6 +49,18 @@ readFlavour ms = set :: Flavour -> Untracked -> Untracked set flag flags = flags { flavour = flag } +readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) +readProgressColour ms = + maybe (Left "Cannot parse progress-colour") (Right . set) (go =<< lower <$> ms) + where + go :: String -> Maybe ProgressColour + go "never" = Just Never + go "auto" = Just Auto + go "always" = Just Always + go _ = Nothing + set :: ProgressColour -> Untracked -> Untracked + set flag flags = flags { progressColour = flag } + readProgressInfo :: Maybe String -> Either String (Untracked -> Untracked) readProgressInfo ms = maybe (Left "Cannot parse progress-info") (Right . set) (go =<< lower <$> ms) @@ -70,8 +86,10 @@ cmdFlags = "Build flavour (Default or Quick)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." + , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") + "Use colours in progress info (Never, Auto or Always)." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") - "Progress info style (None, Brief, Normal, or Unicorn)." + "Progress info style (None, Brief, Normal or Unicorn)." , Option [] ["skip-configure"] (NoArg readSkipConfigure) "Skip the boot and configure scripts (if you want to run them manually)." , Option [] ["split-objects"] (NoArg readSplitObjects) @@ -96,6 +114,9 @@ cmdBuildHaddock = buildHaddock getCmdLineFlags cmdFlavour :: Flavour cmdFlavour = flavour getCmdLineFlags +cmdProgressColour :: ProgressColour +cmdProgressColour = progressColour getCmdLineFlags + cmdProgressInfo :: ProgressInfo cmdProgressInfo = progressInfo getCmdLineFlags From git at git.haskell.org Fri Oct 27 01:02:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use colours on CI (5ca3853) Message-ID: <20171027010208.398E03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ca3853fd62d8dd8566b610a2e1534cf573e9e0d/ghc >--------------------------------------------------------------- commit 5ca3853fd62d8dd8566b610a2e1534cf573e9e0d Author: Andrey Mokhov Date: Wed May 18 02:57:50 2016 +0100 Don't use colours on CI See #244 >--------------------------------------------------------------- 5ca3853fd62d8dd8566b610a2e1534cf573e9e0d .travis.yml | 2 +- appveyor.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 7d5b699..4ec6721 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,7 +59,7 @@ install: script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --no-progress --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index bb78b80..09baa2e 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --profile=- --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 01:02:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Rules.Data to Rules.PackageData (4df3e2d) Message-ID: <20171027010208.2F3033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4df3e2dc441a5d5b6ff61f75573ff4b9a74e562f/ghc >--------------------------------------------------------------- commit 4df3e2dc441a5d5b6ff61f75573ff4b9a74e562f Author: Andrey Mokhov Date: Wed Oct 18 00:44:28 2017 +0100 Rename Rules.Data to Rules.PackageData See #433 >--------------------------------------------------------------- 4df3e2dc441a5d5b6ff61f75573ff4b9a74e562f hadrian.cabal | 2 +- src/Rules.hs | 4 ++-- src/Rules/{Data.hs => PackageData.hs} | 2 +- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 8e583c7..54a0273 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -46,7 +46,7 @@ executable hadrian , Rules.Clean , Rules.Compile , Rules.Configure - , Rules.Data + , Rules.PackageData , Rules.Dependencies , Rules.Documentation , Rules.Generate diff --git a/src/Rules.hs b/src/Rules.hs index 730823f..97270a6 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -9,7 +9,7 @@ import Expression import Flavour import qualified Oracles.ModuleFiles import qualified Rules.Compile -import qualified Rules.Data +import qualified Rules.PackageData import qualified Rules.Dependencies import qualified Rules.Documentation import qualified Rules.Generate @@ -99,7 +99,7 @@ packageRules = do Rules.Program.buildProgram readPackageDb forM_ vanillaContexts $ mconcat - [ Rules.Data.buildPackageData + [ Rules.PackageData.buildPackageData , Rules.Dependencies.buildPackageDependencies readPackageDb , Rules.Documentation.buildPackageDocumentation , Rules.Library.buildPackageGhciLibrary diff --git a/src/Rules/Data.hs b/src/Rules/PackageData.hs similarity index 99% rename from src/Rules/Data.hs rename to src/Rules/PackageData.hs index c6d894b..2442b03 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/PackageData.hs @@ -1,4 +1,4 @@ -module Rules.Data (buildPackageData) where +module Rules.PackageData (buildPackageData) where import Base import Context From git at git.haskell.org Fri Oct 27 01:03:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test the resulting GHC binary (5ad9fad) Message-ID: <20171027010352.744243A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ad9fad8be600b7042f60cf81d61a2f3ac151dbb/ghc >--------------------------------------------------------------- commit 5ad9fad8be600b7042f60cf81d61a2f3ac151dbb Author: Andrey Mokhov Date: Wed Jun 1 09:15:00 2016 +0100 Test the resulting GHC binary See #259. >--------------------------------------------------------------- 5ad9fad8be600b7042f60cf81d61a2f3ac151dbb .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 3b61256..18ede46 100644 --- a/.travis.yml +++ b/.travis.yml @@ -60,6 +60,7 @@ script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET + - ./ghc/inplace/bin/ghc-stage2 -e 1+2 cache: directories: From git at git.haskell.org Fri Oct 27 01:03:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to UseLibdw (119bda5) Message-ID: <20171027010355.E339D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/119bda593291be9748b21dc45b3a3777a980a532/ghc >--------------------------------------------------------------- commit 119bda593291be9748b21dc45b3a3777a980a532 Author: Andrey Mokhov Date: Wed Jun 1 09:48:32 2016 +0100 Switch to UseLibdw See #259. >--------------------------------------------------------------- 119bda593291be9748b21dc45b3a3777a980a532 cfg/system.config.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index f235f19..b580f86 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -115,4 +115,4 @@ ffi-lib-dir = @FFILibDir@ # Optional Dependencies: #======================= -with-libdw = @HaveLibdw@ +with-libdw = @UseLibdw@ From git at git.haskell.org Fri Oct 27 01:03:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to user settings (d58dabf) Message-ID: <20171027010359.783BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d58dabfd7ca07e50374b7c859f81b8ed55dc600c/ghc >--------------------------------------------------------------- commit d58dabfd7ca07e50374b7c859f81b8ed55dc600c Author: Andrey Mokhov Date: Thu Jun 2 23:19:21 2016 +0100 Fix path to user settings [skip ci] >--------------------------------------------------------------- d58dabfd7ca07e50374b7c859f81b8ed55dc600c README.md | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/README.md b/README.md index b1da6f7..d99d2b7 100644 --- a/README.md +++ b/README.md @@ -88,8 +88,7 @@ by Shake oracles. #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We -use `./UserSettings.hs` for the same purpose, see -[documentation](doc/user-settings.md). +use `hadrian/UserSettings.hs` for the same purpose, see [documentation](doc/user-settings.md). #### Clean and full rebuild From git at git.haskell.org Fri Oct 27 01:04:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to user settings (157b855) Message-ID: <20171027010402.F33923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/157b855a026ca48b69ba0dba6a473c34f23cfaa4/ghc >--------------------------------------------------------------- commit 157b855a026ca48b69ba0dba6a473c34f23cfaa4 Author: Andrey Mokhov Date: Thu Jun 2 23:27:10 2016 +0100 Fix paths to user settings [skip ci] >--------------------------------------------------------------- 157b855a026ca48b69ba0dba6a473c34f23cfaa4 doc/user-settings.md | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index a5185ad..1dbfd6f 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,8 +1,9 @@ # User settings -You can customise Hadrian by copying the file ./src/UserSettings.hs to -./UserSettings.hs and specifying user build settings in -`./UserSettings.hs`. Here we document currently supported settings. +You can customise Hadrian by copying the file `hadrian/src/UserSettings.hs` to +`hadrian/UserSettings.hs` and overriding the default build settings (if you don't +copy the file your changes will be tracked by `git` and you can accidentally commit +them). Here we document currently supported settings. ## Build directory From git at git.haskell.org Fri Oct 27 01:04:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge build.cabal-new.sh into build.cabal.sh (af6a040) Message-ID: <20171027010406.7A9553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/af6a040742b654d018bfd2fe4dc839a94aa083db/ghc >--------------------------------------------------------------- commit af6a040742b654d018bfd2fe4dc839a94aa083db Author: Herbert Valerio Riedel Date: Fri Jun 3 22:19:36 2016 +0200 Merge build.cabal-new.sh into build.cabal.sh The script now detect the cabal version and uses either the robust and fast 'new-build'-logic (for version 1.24 or later), or falls back to the fragile sandbox-based legacy logic. >--------------------------------------------------------------- af6a040742b654d018bfd2fe4dc839a94aa083db build.cabal-new.sh | 58 ------------------------------------------------------ build.cabal.sh | 50 +++++++++++++++++++++++++++++++++++----------- build.sh | 9 +++++++++ 3 files changed, 48 insertions(+), 69 deletions(-) diff --git a/build.cabal-new.sh b/build.cabal-new.sh deleted file mode 100755 index 65e222a..0000000 --- a/build.cabal-new.sh +++ /dev/null @@ -1,58 +0,0 @@ -#!/usr/bin/env bash - -# This wrapper scripts makes use of cabal 1.24+'s nix-store; -# In order to clean/reset, remove the `dist-newstyle/` folder - -set -euo pipefail - -# readlink on os x, doesn't support -f, to prevent the -# need of installing coreutils (e.g. through brew, just -# for readlink, we use the follownig substitute. -# -# source: http://stackoverflow.com/a/1116890 -function rl { - TARGET_FILE="$1" - - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - - # Iterate down a (possible) chain of symlinks - while [ -L "$TARGET_FILE" ] - do - TARGET_FILE="$(readlink "$TARGET_FILE")" - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - done - - # Compute the canonicalized name by finding the physical path - # for the directory we're in and appending the target file. - PHYS_DIR="$(pwd -P)" - RESULT="$PHYS_DIR/$TARGET_FILE" - echo "$RESULT" -} - -root="$(dirname "$(rl "$0")")" - -mkdir -p "$root/.shake" - -# Notes/Random thoughts: -# -# - if ghc.git had a top-level `cabal.project` file, we could maybe avoid the -# boilerplate above, as we could simply say `cabal exec hadrian` from within -# any GHC folder not shadowed by a nearer shadowing `cabal.project` file. - -pushd "$root/" - -cabal new-build --disable-profiling --disable-documentation -j exe:hadrian - -PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" - -cp -v "$root/dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ - "$root/.shake/build" - -popd - -"$root/.shake/build" \ - --lint \ - --directory "$root/.." \ - "$@" diff --git a/build.cabal.sh b/build.cabal.sh index 08ff972..4a24dac 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -1,5 +1,7 @@ #!/usr/bin/env bash +CABAL=cabal + set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -31,16 +33,42 @@ function rl { absoluteRoot="$(dirname "$(rl "$0")")" cd "$absoluteRoot" -# Initialize sandbox if necessary -if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then - cabal sandbox init - cabal install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared +if ! type "$CABAL" > /dev/null; then + echo "Please make sure 'cabal' is in your PATH" + exit 2 fi -cabal run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" +CABVERSTR=$("$CABAL" --numeric-version) + +CABVER=( ${CABVERSTR//./ } ) + +if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then + # New enough cabal version detected, so + # let's use the superior 'cabal new-build' mode + + # there's no 'cabal new-run' yet, but it's easy to emulate + "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian + PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" + "./dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" + +else + # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals + echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." + + # Initialize sandbox if necessary + if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then + "$CABAL" sandbox init + "$CABAL" install \ + --dependencies-only \ + --disable-library-profiling \ + --disable-shared + fi + + "$CABAL" run hadrian -- \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" +fi diff --git a/build.sh b/build.sh index 24fdc2f..d627c58 100755 --- a/build.sh +++ b/build.sh @@ -30,6 +30,15 @@ function rl { root="$(dirname "$(rl "$0")")" +if type cabal > /dev/null 2>&1; then + CABVERSTR=$(cabal --numeric-version) + CABVER=( ${CABVERSTR//./ } ) + if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then + echo "** Cabal 1.24 or later detected. Please consider using the 'build.cabal.sh' script **" + echo "" + fi +fi + mkdir -p "$root/../_build/hadrian" ghc \ From git at git.haskell.org Fri Oct 27 01:04:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (c9e7570) Message-ID: <20171027010409.F07FA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9e7570bea7562ca05b6c1469759dfdf9e675e06/ghc >--------------------------------------------------------------- commit c9e7570bea7562ca05b6c1469759dfdf9e675e06 Author: Andrey Mokhov Date: Sat Jun 4 21:56:12 2016 +0100 Minor revision >--------------------------------------------------------------- c9e7570bea7562ca05b6c1469759dfdf9e675e06 src/Settings/Builders/Make.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index afb46d7..7283b4b 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -7,8 +7,8 @@ import Settings makeBuilderArgs :: Args makeBuilderArgs = do threads <- shakeThreads <$> lift getShakeOptions - let j = "-j" ++ show threads + let t = show threads mconcat - [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=" ++ j] - , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=" ++ j, "install"] - , builder (Make "testsuite/tests") ? append ["THREADS=" ++ show threads, "fast"] ] + [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=-j" ++ t] + , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=-j" ++ t, "install"] + , builder (Make "testsuite/tests") ? append ["THREADS=" ++ t, "fast"] ] From git at git.haskell.org Fri Oct 27 01:04:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up switching from Settings.User to UserSettings (39f0509) Message-ID: <20171027010413.777353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39f05090304de772238002ed16ff6a2b8023201d/ghc >--------------------------------------------------------------- commit 39f05090304de772238002ed16ff6a2b8023201d Author: Andrey Mokhov Date: Sat Jun 4 23:40:52 2016 +0100 Clean up switching from Settings.User to UserSettings >--------------------------------------------------------------- 39f05090304de772238002ed16ff6a2b8023201d cfg/system.config.in | 6 +++--- hadrian.cabal | 2 +- src/GHC.hs | 2 +- src/Oracles/PackageDatabase.hs | 2 +- src/Rules/Clean.hs | 2 +- src/Rules/Configure.hs | 2 +- src/Rules/Generators/Common.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Selftest.hs | 2 +- src/Rules/Test.hs | 2 +- src/Settings.hs | 4 ++-- src/Settings/Args.hs | 2 +- src/Settings/Packages.hs | 2 +- src/Settings/Paths.hs | 2 +- src/Settings/User.hs | 12 ------------ src/Settings/Ways.hs | 2 +- src/UserSettings.hs | 10 +++++----- 18 files changed, 25 insertions(+), 37 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 39f05090304de772238002ed16ff6a2b8023201d From git at git.haskell.org Fri Oct 27 01:04:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #260 from hvr/pr/unify-cabal-script (24d6d50) Message-ID: <20171027010417.15F173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/24d6d50c5d605aa32cfc5efcd2328480597cfda4/ghc >--------------------------------------------------------------- commit 24d6d50c5d605aa32cfc5efcd2328480597cfda4 Merge: 39f0509 af6a040 Author: Andrey Mokhov Date: Sat Jun 4 23:41:34 2016 +0100 Merge pull request #260 from hvr/pr/unify-cabal-script Merge build.cabal-new.sh into build.cabal.sh >--------------------------------------------------------------- 24d6d50c5d605aa32cfc5efcd2328480597cfda4 build.cabal-new.sh | 58 ------------------------------------------------------ build.cabal.sh | 50 +++++++++++++++++++++++++++++++++++----------- build.sh | 9 +++++++++ 3 files changed, 48 insertions(+), 69 deletions(-) From git at git.haskell.org Fri Oct 27 01:04:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix formatting (49c2df8) Message-ID: <20171027010420.A026C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49c2df80afe3754b2c24fae8337d1e1f13e923c3/ghc >--------------------------------------------------------------- commit 49c2df80afe3754b2c24fae8337d1e1f13e923c3 Author: Andrey Mokhov Date: Wed Jun 8 01:20:03 2016 +0100 Fix formatting >--------------------------------------------------------------- 49c2df80afe3754b2c24fae8337d1e1f13e923c3 src/Rules/Library.hs | 18 ++++++++---------- 1 file changed, 8 insertions(+), 10 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index dd144d1..a45ef51 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -62,17 +62,15 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do let path = buildPath context libPrefix = path -/- "HS" ++ pkgNameString package - -- TODO: simplify handling of AutoApply.cmm matchVersionedFilePath libPrefix (waySuffix way <.> "o") ?> \obj -> do - cSrcs <- cSources context - hSrcs <- hSources context - - eObjs <- extraObjects context - let cObjs = map (objFile context) cSrcs - hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] - objs = cObjs ++ hObjs ++ eObjs - need objs - build $ Target context Ld objs [obj] + cSrcs <- cSources context + hSrcs <- hSources context + eObjs <- extraObjects context + let cObjs = map (objFile context) cSrcs + hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] + objs = cObjs ++ hObjs ++ eObjs + need objs + build $ Target context Ld objs [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. -- | Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' From git at git.haskell.org Fri Oct 27 01:04:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set dynamicGhcPrograms = False (85b4b52) Message-ID: <20171027010424.1E68B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/85b4b524df1734d0a96c7a5ac66724c0c61cce28/ghc >--------------------------------------------------------------- commit 85b4b524df1734d0a96c7a5ac66724c0c61cce28 Author: Andrey Mokhov Date: Wed Jun 8 01:20:47 2016 +0100 Set dynamicGhcPrograms = False See #259. >--------------------------------------------------------------- 85b4b524df1734d0a96c7a5ac66724c0c61cce28 src/UserSettings.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 908d96d..588f196 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -78,7 +78,7 @@ buildHaddock = return cmdBuildHaddock -- TODO: Do we need to be able to set these from command line? -- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? dynamicGhcPrograms :: Bool -dynamicGhcPrograms = True +dynamicGhcPrograms = False ghciWithDebugger :: Bool ghciWithDebugger = False From git at git.haskell.org Fri Oct 27 01:04:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Note on nm on OS X (5422e92) Message-ID: <20171027010427.9881C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5422e921b215ccb4a9041689a9b6cab4aa4af646/ghc >--------------------------------------------------------------- commit 5422e921b215ccb4a9041689a9b6cab4aa4af646 Author: Alex Biehl Date: Wed Jun 8 12:47:49 2016 +0200 Note on nm on OS X >--------------------------------------------------------------- 5422e921b215ccb4a9041689a9b6cab4aa4af646 README.md | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/README.md b/README.md index d99d2b7..6b5b234 100644 --- a/README.md +++ b/README.md @@ -43,6 +43,13 @@ runs the `boot` and `configure` scripts automatically on the first build, so tha need to. Use `--skip-configure` to suppress this behaviour (see overview of command line flags below). +* Also note on OS X newer versions of XCode ship with a broken `nm` tool ([#1174](https://ghc.haskell.org/trac/ghc/ticket/11744)). To mitigate the problem place something like + ````haskell + userArgs :: Args + userArgs = builder (Configure ".") ? arg "--with-nm=$(xcrun --find nm-classic)" + ```` + in your `UserSettings.hs`. + Using the build system ---------------------- Once your first build is successful, simply run `build` to rebuild. Most build artefacts From git at git.haskell.org Fri Oct 27 01:04:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #262 from alexbiehl/patch-1 (920e7bb) Message-ID: <20171027010431.2747C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/920e7bba89b3d398c162e7d90d5a3581551e1edb/ghc >--------------------------------------------------------------- commit 920e7bba89b3d398c162e7d90d5a3581551e1edb Merge: 85b4b52 5422e92 Author: Andrey Mokhov Date: Thu Jun 9 10:46:52 2016 +0100 Merge pull request #262 from alexbiehl/patch-1 Note on nm on OS X >--------------------------------------------------------------- 920e7bba89b3d398c162e7d90d5a3581551e1edb README.md | 7 +++++++ 1 file changed, 7 insertions(+) From git at git.haskell.org Fri Oct 27 01:04:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change default colours to fit both B-on-W and W-on-B terminals (1ff9ead) Message-ID: <20171027010434.B6FC23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ff9eadbf2daee253e62994dd0717c7f016f1548/ghc >--------------------------------------------------------------- commit 1ff9eadbf2daee253e62994dd0717c7f016f1548 Author: Andrey Mokhov Date: Sun Jun 12 19:58:12 2016 +0100 Change default colours to fit both B-on-W and W-on-B terminals See #263. >--------------------------------------------------------------- 1ff9eadbf2daee253e62994dd0717c7f016f1548 src/UserSettings.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 588f196..23380ce 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -102,8 +102,8 @@ verboseCommands = return False -- | Customise build progress messages (e.g. executing a build command). putBuild :: String -> Action () -putBuild = putColoured Vivid White +putBuild = putColoured Dull Magenta -- | Customise build success messages (e.g. a package is built successfully). putSuccess :: String -> Action () -putSuccess = putColoured Vivid Green +putSuccess = putColoured Dull Green From git at git.haskell.org Fri Oct 27 01:04:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add actions copyDirectoryContent and runBuilderWith (e592fb1) Message-ID: <20171027010438.35AE33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e592fb1f438317d4be4893bf9b07b098ffb28085/ghc >--------------------------------------------------------------- commit e592fb1f438317d4be4893bf9b07b098ffb28085 Author: Kai Harries Date: Fri Jun 17 17:23:54 2016 +0200 Add actions copyDirectoryContent and runBuilderWith These new functions will be helpful when implementing the 'sdist' and 'install' rules. >--------------------------------------------------------------- e592fb1f438317d4be4893bf9b07b098ffb28085 src/Rules/Actions.hs | 26 ++++++++++++++++++++++---- 1 file changed, 22 insertions(+), 4 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 6b6c352..8fbe6c0 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,12 +1,14 @@ module Rules.Actions ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, - removeFile, copyDirectory, createDirectory, moveDirectory, removeDirectory, - applyPatch, runBuilder, makeExecutable, renderProgram, renderLibrary + removeFile, copyDirectory, copyDirectoryContent, createDirectory, + moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, + makeExecutable, renderProgram, renderLibrary ) where import qualified System.Directory as IO import qualified System.IO as IO import qualified Control.Exception.Base as IO +import qualified System.Directory.Extra as X import Base import CmdLineFlag @@ -126,6 +128,18 @@ copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd cmdEcho ["cp", "-r", source, target] +-- | Copy the content of the source directory into the target directory. Only +-- the files and directories for which the predicate returns True are copied. +copyDirectoryContent :: (FilePath -> IO Bool) -> FilePath -> FilePath -> Action () +copyDirectoryContent test source target = do + putProgressInfo $ renderAction "Copy directory" source target + liftIO $ X.listFilesInside test' source >>= mapM_ cp + where + target' a = target -/- fromJust (stripPrefix source a) + test' a = ifM (test a) (mkdir a >> return True) (return False) + mkdir a = IO.createDirectoryIfMissing True $ target' a + cp a = whenM (test a) $ IO.copyFile a $ target' a + -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do @@ -152,12 +166,16 @@ applyPatch dir patch = do quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () -runBuilder builder args = do +runBuilder = + runBuilderWith [] + +runBuilderWith :: [CmdOption] -> Builder -> [String] -> Action () +runBuilderWith options builder args = do needBuilder builder path <- builderPath builder let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run " ++ show builder ++ note - quietly $ cmd [path] args + quietly $ cmd options [path] args makeExecutable :: FilePath -> Action () makeExecutable file = do From git at git.haskell.org Fri Oct 27 01:04:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove excessive whitespace (787cb4f) Message-ID: <20171027010445.443FE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/787cb4f1f82c4928d6a4d0259da6694f3fd0fe64/ghc >--------------------------------------------------------------- commit 787cb4f1f82c4928d6a4d0259da6694f3fd0fe64 Author: Kai Harries Date: Sun Jun 19 09:36:04 2016 +0200 Remove excessive whitespace >--------------------------------------------------------------- 787cb4f1f82c4928d6a4d0259da6694f3fd0fe64 src/Rules/Actions.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 7221441..734cb91 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -165,8 +165,7 @@ applyPatch dir patch = do quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () -runBuilder = - runBuilderWith [] +runBuilder = runBuilderWith [] runBuilderWith :: [CmdOption] -> Builder -> [String] -> Action () runBuilderWith options builder args = do From git at git.haskell.org Fri Oct 27 01:04:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Quickest build flavour (d7c80c8) Message-ID: <20171027010448.C12073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d7c80c8303b7bc4596c9d04b569c365128cfd958/ghc >--------------------------------------------------------------- commit d7c80c8303b7bc4596c9d04b569c365128cfd958 Author: Andrey Mokhov Date: Mon Jun 20 03:07:24 2016 +0100 Add Quickest build flavour See #259, #268. >--------------------------------------------------------------- d7c80c8303b7bc4596c9d04b569c365128cfd958 hadrian.cabal | 1 + src/CmdLineFlag.hs | 11 ++++++----- src/Settings/Args.hs | 7 +++++-- src/Settings/Flavours/Quickest.hs | 16 ++++++++++++++++ src/Settings/Ways.hs | 7 +++++-- 5 files changed, 33 insertions(+), 9 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 5ffcb65..2b773ee 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -88,6 +88,7 @@ executable hadrian , Settings.Builders.Tar , Settings.Default , Settings.Flavours.Quick + , Settings.Flavours.Quickest , Settings.Packages , Settings.Packages.Base , Settings.Packages.Compiler diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 10c39f2..df3af5b 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -21,7 +21,7 @@ data Untracked = Untracked , splitObjects :: Bool } deriving (Eq, Show) -data Flavour = Default | Quick deriving (Eq, Show) +data Flavour = Default | Quick | Quickest deriving (Eq, Show) data ProgressColour = Never | Auto | Always deriving (Eq, Show) data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) @@ -43,9 +43,10 @@ readFlavour ms = maybe (Left "Cannot parse flavour") (Right . set) (go =<< lower <$> ms) where go :: String -> Maybe Flavour - go "default" = Just Default - go "quick" = Just Quick - go _ = Nothing + go "default" = Just Default + go "quick" = Just Quick + go "quickest" = Just Quickest + go _ = Nothing set :: Flavour -> Untracked -> Untracked set flag flags = flags { flavour = flag } @@ -83,7 +84,7 @@ readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") - "Build flavour (Default or Quick)." + "Build flavour (Default, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index 18079a2..2ff071a 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -20,6 +20,7 @@ import Settings.Builders.Ld import Settings.Builders.Make import Settings.Builders.Tar import Settings.Flavours.Quick +import Settings.Flavours.Quickest import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Directory @@ -88,5 +89,7 @@ defaultPackageArgs = mconcat , unlitPackageArgs ] flavourArgs :: Args -flavourArgs = mconcat - [ cmdFlavour == Quick ? quickFlavourArgs ] +flavourArgs = case cmdFlavour of + Default -> mempty + Quick -> quickFlavourArgs + Quickest -> quickestFlavourArgs diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs new file mode 100644 index 0000000..cc1de6b --- /dev/null +++ b/src/Settings/Flavours/Quickest.hs @@ -0,0 +1,16 @@ +module Settings.Flavours.Quickest (quickestFlavourArgs, quickestFlavourWays) where + +import Context +import GHC +import Predicate + +optimise :: Context -> Bool +optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] + +quickestFlavourArgs :: Args +quickestFlavourArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O" else arg "-O0" + +quickestFlavourWays :: Ways +quickestFlavourWays = remove [profiling] diff --git a/src/Settings/Ways.hs b/src/Settings/Ways.hs index 79dd164..95301e1 100644 --- a/src/Settings/Ways.hs +++ b/src/Settings/Ways.hs @@ -5,6 +5,7 @@ import CmdLineFlag import Oracles.Config.Flag import Predicate import Settings.Flavours.Quick +import Settings.Flavours.Quickest import UserSettings -- | Combine default library ways with user modifications. @@ -29,8 +30,10 @@ defaultLibraryWays = mconcat , notStage0 ? platformSupportsSharedLibs ? append [dynamic] ] flavourLibraryWays :: Ways -flavourLibraryWays = mconcat - [ cmdFlavour == Quick ? quickFlavourWays ] +flavourLibraryWays = case cmdFlavour of + Default -> mempty + Quick -> quickFlavourWays + Quickest -> quickestFlavourWays defaultRtsWays :: Ways defaultRtsWays = do From git at git.haskell.org Fri Oct 27 01:04:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove explicit import of 'System.Directory' (73970d5) Message-ID: <20171027010441.CB8333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73970d51a9d40c79ec8ed2aea4d36b5c3ff723b0/ghc >--------------------------------------------------------------- commit 73970d51a9d40c79ec8ed2aea4d36b5c3ff723b0 Author: Kai Harries Date: Sun Jun 19 09:34:15 2016 +0200 Remove explicit import of 'System.Directory' >--------------------------------------------------------------- 73970d51a9d40c79ec8ed2aea4d36b5c3ff723b0 src/Rules/Actions.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 8fbe6c0..7221441 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -5,10 +5,9 @@ module Rules.Actions ( makeExecutable, renderProgram, renderLibrary ) where -import qualified System.Directory as IO +import qualified System.Directory.Extra as IO import qualified System.IO as IO import qualified Control.Exception.Base as IO -import qualified System.Directory.Extra as X import Base import CmdLineFlag @@ -133,7 +132,7 @@ copyDirectory source target = do copyDirectoryContent :: (FilePath -> IO Bool) -> FilePath -> FilePath -> Action () copyDirectoryContent test source target = do putProgressInfo $ renderAction "Copy directory" source target - liftIO $ X.listFilesInside test' source >>= mapM_ cp + liftIO $ IO.listFilesInside test' source >>= mapM_ cp where target' a = target -/- fromJust (stripPrefix source a) test' a = ifM (test a) (mkdir a >> return True) (return False) From git at git.haskell.org Fri Oct 27 01:04:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Quickest flavour on Appveyor (3a04d34) Message-ID: <20171027010452.5A90F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3a04d3425a06ff9ad62eb71d20ddd7cce26ae0a0/ghc >--------------------------------------------------------------- commit 3a04d3425a06ff9ad62eb71d20ddd7cce26ae0a0 Author: Andrey Mokhov Date: Mon Jun 20 03:08:10 2016 +0100 Use Quickest flavour on Appveyor See #259, #268. >--------------------------------------------------------------- 3a04d3425a06ff9ad62eb71d20ddd7cce26ae0a0 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index bb5620e..e4d7d52 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 01:04:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Quick flavour (6d6834a) Message-ID: <20171027010455.C7ECB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d6834a6abebaff0d4aa60e615a027d68ed964d9/ghc >--------------------------------------------------------------- commit 6d6834a6abebaff0d4aa60e615a027d68ed964d9 Author: Andrey Mokhov Date: Mon Jun 20 03:08:45 2016 +0100 Fix Quick flavour See #259, #268. >--------------------------------------------------------------- 6d6834a6abebaff0d4aa60e615a027d68ed964d9 src/Settings/Flavours/Quick.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index e3f0a5d..81fe178 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -1,9 +1,17 @@ module Settings.Flavours.Quick (quickFlavourArgs, quickFlavourWays) where +import Context +import GHC import Predicate +optimise :: Context -> Bool +optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] + || stage == Stage1 && isLibrary package + quickFlavourArgs :: Args -quickFlavourArgs = builder Ghc ? arg "-O0" +quickFlavourArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O" else arg "-O0" quickFlavourWays :: Ways quickFlavourWays = remove [profiling] From git at git.haskell.org Fri Oct 27 01:04:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:04:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Quickest flavour on Mac OSX (1f1a7b3) Message-ID: <20171027010459.40B6F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1f1a7b3297c7a4747b5e7a89ae47335ea8d79a56/ghc >--------------------------------------------------------------- commit 1f1a7b3297c7a4747b5e7a89ae47335ea8d79a56 Author: Andrey Mokhov Date: Tue Jun 21 01:22:18 2016 +0100 Use Quickest flavour on Mac OSX See #259 >--------------------------------------------------------------- 1f1a7b3297c7a4747b5e7a89ae47335ea8d79a56 .travis.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index 18ede46..b066e89 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quick TARGET= addons: apt: packages: @@ -20,7 +20,7 @@ matrix: - cabal install alex happy - os: osx - env: TARGET= + env: FLAVOUR=quickest TARGET= before_install: - brew update - brew install ghc cabal-install @@ -59,7 +59,7 @@ install: script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=$FLAVOUR $TARGET - ./ghc/inplace/bin/ghc-stage2 -e 1+2 cache: From git at git.haskell.org Fri Oct 27 01:05:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to optimise ghc-stage2 in Quick flavour (b299acb) Message-ID: <20171027010503.005073A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b299acb4ec05bbf8a3b08a67175f8b2eb2f2aded/ghc >--------------------------------------------------------------- commit b299acb4ec05bbf8a3b08a67175f8b2eb2f2aded Author: Andrey Mokhov Date: Tue Jun 21 01:56:20 2016 +0100 Attempt to optimise ghc-stage2 in Quick flavour See #259 >--------------------------------------------------------------- b299acb4ec05bbf8a3b08a67175f8b2eb2f2aded src/Settings/Flavours/Quick.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 81fe178..834a72b 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -5,7 +5,7 @@ import GHC import Predicate optimise :: Context -> Bool -optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] +optimise Context {..} = package `elem` [compiler, ghc] || stage == Stage1 && isLibrary package quickFlavourArgs :: Args From git at git.haskell.org Fri Oct 27 01:05:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't optimise GHC in Quickest flavour (0955d43) Message-ID: <20171027010506.709D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0955d43bbbde1ee3ab71d3a01bf3d2f6e53afbe9/ghc >--------------------------------------------------------------- commit 0955d43bbbde1ee3ab71d3a01bf3d2f6e53afbe9 Author: Andrey Mokhov Date: Tue Jun 21 20:10:31 2016 +0100 Don't optimise GHC in Quickest flavour See #259, #268. >--------------------------------------------------------------- 0955d43bbbde1ee3ab71d3a01bf3d2f6e53afbe9 src/Settings/Flavours/Quickest.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index cc1de6b..3696237 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -1,16 +1,9 @@ module Settings.Flavours.Quickest (quickestFlavourArgs, quickestFlavourWays) where -import Context -import GHC import Predicate -optimise :: Context -> Bool -optimise Context {..} = stage == Stage0 && package `elem` [compiler, ghc] - quickestFlavourArgs :: Args -quickestFlavourArgs = builder Ghc ? do - context <- getContext - if optimise context then arg "-O" else arg "-O0" +quickestFlavourArgs = builder Ghc ? arg "-O0" quickestFlavourWays :: Ways quickestFlavourWays = remove [profiling] From git at git.haskell.org Fri Oct 27 01:05:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (0579308) Message-ID: <20171027010509.E46933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0579308f9cb7444e28a230867c8ba462238747dd/ghc >--------------------------------------------------------------- commit 0579308f9cb7444e28a230867c8ba462238747dd Author: Andrey Mokhov Date: Fri Jun 24 00:54:42 2016 +0100 Minor revision >--------------------------------------------------------------- 0579308f9cb7444e28a230867c8ba462238747dd README.md | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 6b5b234..4ce3b3a 100644 --- a/README.md +++ b/README.md @@ -43,12 +43,13 @@ runs the `boot` and `configure` scripts automatically on the first build, so tha need to. Use `--skip-configure` to suppress this behaviour (see overview of command line flags below). -* Also note on OS X newer versions of XCode ship with a broken `nm` tool ([#1174](https://ghc.haskell.org/trac/ghc/ticket/11744)). To mitigate the problem place something like +* Also note on OS X newer versions of XCode ship with a broken `nm` tool +([#11744](https://ghc.haskell.org/trac/ghc/ticket/11744)). One way to mitigate the +problem is to add the following into your `UserSettings.hs`: ````haskell userArgs :: Args userArgs = builder (Configure ".") ? arg "--with-nm=$(xcrun --find nm-classic)" ```` - in your `UserSettings.hs`. Using the build system ---------------------- From git at git.haskell.org Fri Oct 27 01:05:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Oracle 'DirectoryContent' (21f3e05) Message-ID: <20171027010513.5E3A93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/21f3e0562f3d4685e384f2ba374898dc6868ce0e/ghc >--------------------------------------------------------------- commit 21f3e0562f3d4685e384f2ba374898dc6868ce0e Author: Kai Harries Date: Tue Jun 28 09:39:55 2016 +0200 Add Oracle 'DirectoryContent' >--------------------------------------------------------------- 21f3e0562f3d4685e384f2ba374898dc6868ce0e hadrian.cabal | 1 + src/Oracles/DirectoryContent.hs | 31 +++++++++++++++++++++++++++++++ src/Rules/Oracles.hs | 2 ++ 3 files changed, 34 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 5ffcb65..df2a4a5 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -30,6 +30,7 @@ executable hadrian , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies + , Oracles.DirectoryContent , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContent.hs new file mode 100644 index 0000000..6211222 --- /dev/null +++ b/src/Oracles/DirectoryContent.hs @@ -0,0 +1,31 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module Oracles.DirectoryContent ( + getDirectoryContent, directoryContentOracle, Exclude(..), ExcludeNot(..) + ) where + +import Base +import System.Directory.Extra + +newtype DirectoryContent = DirectoryContent (Exclude, ExcludeNot, FilePath) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) +newtype Exclude = Exclude [FilePattern] + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) +newtype ExcludeNot = ExcludeNot [FilePattern] + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Get the directory content. 'Exclude' and 'ExcludeNot' are a list of file +-- patterns matched with '?=='. +getDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> Action [FilePath] +getDirectoryContent exclude excludeNot dir = + askOracle $ DirectoryContent (exclude, excludeNot, dir) + +directoryContentOracle :: Rules () +directoryContentOracle = void $ addOracle oracle + where + oracle :: DirectoryContent -> Action [FilePath] + oracle (DirectoryContent (Exclude exclude, ExcludeNot excludeNot, dir)) = + liftIO $ filter test <$> listFilesInside (return . test) dir + where + test a = include' a || not (exclude' a) + exclude' a = any (?== a) exclude + include' a = any (?== a) excludeNot diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 7beb67f..10767b5 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -4,6 +4,7 @@ import Base import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies +import qualified Oracles.DirectoryContent import qualified Oracles.LookupInPath import qualified Oracles.ModuleFiles import qualified Oracles.PackageData @@ -15,6 +16,7 @@ oracleRules = do Oracles.ArgsHash.argsHashOracle Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles + Oracles.DirectoryContent.directoryContentOracle Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle From git at git.haskell.org Fri Oct 27 01:05:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rework copyDirectoryContent (5439f0e) Message-ID: <20171027010516.C742E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5439f0ee49094ad46574a38b217f741ba4f6ea35/ghc >--------------------------------------------------------------- commit 5439f0ee49094ad46574a38b217f741ba4f6ea35 Author: Kai Harries Date: Tue Jun 28 09:43:52 2016 +0200 Rework copyDirectoryContent >--------------------------------------------------------------- 5439f0ee49094ad46574a38b217f741ba4f6ea35 src/Rules/Actions.hs | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 734cb91..c3680f9 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -2,7 +2,7 @@ module Rules.Actions ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, removeFile, copyDirectory, copyDirectoryContent, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, - makeExecutable, renderProgram, renderLibrary + makeExecutable, renderProgram, renderLibrary, Exclude(..), ExcludeNot(..) ) where import qualified System.Directory.Extra as IO @@ -14,6 +14,7 @@ import CmdLineFlag import Context import Expression import Oracles.ArgsHash +import Oracles.DirectoryContent import Oracles.WindowsPath import Settings import Settings.Args @@ -127,17 +128,18 @@ copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd cmdEcho ["cp", "-r", source, target] --- | Copy the content of the source directory into the target directory. Only --- the files and directories for which the predicate returns True are copied. -copyDirectoryContent :: (FilePath -> IO Bool) -> FilePath -> FilePath -> Action () -copyDirectoryContent test source target = do - putProgressInfo $ renderAction "Copy directory" source target - liftIO $ IO.listFilesInside test' source >>= mapM_ cp +-- | Copy the content of the source directory into the target directory. +-- 'Exclude' and 'ExcludeNot' are a list of file patterns matched with '?=='. +-- The copied content is tracked. +copyDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> FilePath -> Action () +copyDirectoryContent exclude excludeNot source target = do + putProgressInfo $ renderAction "Copy directory content" source target + getDirectoryContent exclude excludeNot source >>= mapM_ cp where + cp a = do + createDirectory $ dropFileName $ target' a + copyFile a $ target' a target' a = target -/- fromJust (stripPrefix source a) - test' a = ifM (test a) (mkdir a >> return True) (return False) - mkdir a = IO.createDirectoryIfMissing True $ target' a - cp a = whenM (test a) $ IO.copyFile a $ target' a -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 01:05:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: getDirectoryContent: Implement an AST for matching (5999957) Message-ID: <20171027010520.5B2A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59999579eb089d578b0bed928bfe338b8705cace/ghc >--------------------------------------------------------------- commit 59999579eb089d578b0bed928bfe338b8705cace Author: Kai Harries Date: Fri Jul 1 15:30:56 2016 +0200 getDirectoryContent: Implement an AST for matching >--------------------------------------------------------------- 59999579eb089d578b0bed928bfe338b8705cace src/Oracles/DirectoryContent.hs | 44 ++++++++++++++++++++++++----------------- src/Rules/Actions.hs | 9 ++++----- 2 files changed, 30 insertions(+), 23 deletions(-) diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContent.hs index 6211222..45afa92 100644 --- a/src/Oracles/DirectoryContent.hs +++ b/src/Oracles/DirectoryContent.hs @@ -1,31 +1,39 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} module Oracles.DirectoryContent ( - getDirectoryContent, directoryContentOracle, Exclude(..), ExcludeNot(..) + getDirectoryContent, directoryContentOracle, Match(..) ) where import Base +import GHC.Generics import System.Directory.Extra -newtype DirectoryContent = DirectoryContent (Exclude, ExcludeNot, FilePath) - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -newtype Exclude = Exclude [FilePattern] - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -newtype ExcludeNot = ExcludeNot [FilePattern] +newtype DirectoryContent = DirectoryContent (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- | Get the directory content. 'Exclude' and 'ExcludeNot' are a list of file --- patterns matched with '?=='. -getDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> Action [FilePath] -getDirectoryContent exclude excludeNot dir = - askOracle $ DirectoryContent (exclude, excludeNot, dir) +data Match = Test FilePattern | Not (Match) | And [Match] | Or [Match] + deriving (Generic, Eq, Show, Typeable) +instance Binary Match +instance Hashable Match +instance NFData Match + +matches :: Match -> FilePath -> Bool +matches (Test m) f = m ?== f +matches (Not m) f = not $ matches m f +matches (And []) _ = True +matches (And (m:ms)) f | matches m f = matches (And ms) f + | otherwise = False +matches (Or []) _ = False +matches (Or (m:ms)) f | matches m f = True + | otherwise = matches (Or ms) f + +-- | Get the directory content recursively. +getDirectoryContent :: Match -> FilePath -> Action [FilePath] +getDirectoryContent expr dir = + askOracle $ DirectoryContent (expr, dir) directoryContentOracle :: Rules () directoryContentOracle = void $ addOracle oracle where oracle :: DirectoryContent -> Action [FilePath] - oracle (DirectoryContent (Exclude exclude, ExcludeNot excludeNot, dir)) = - liftIO $ filter test <$> listFilesInside (return . test) dir - where - test a = include' a || not (exclude' a) - exclude' a = any (?== a) exclude - include' a = any (?== a) excludeNot + oracle (DirectoryContent (expr, dir)) = + liftIO $ filter (matches expr) <$> listFilesInside (return . matches expr) dir diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index c3680f9..7b4c46c 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -2,7 +2,7 @@ module Rules.Actions ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, removeFile, copyDirectory, copyDirectoryContent, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, - makeExecutable, renderProgram, renderLibrary, Exclude(..), ExcludeNot(..) + makeExecutable, renderProgram, renderLibrary, Match(..) ) where import qualified System.Directory.Extra as IO @@ -129,12 +129,11 @@ copyDirectory source target = do quietly $ cmd cmdEcho ["cp", "-r", source, target] -- | Copy the content of the source directory into the target directory. --- 'Exclude' and 'ExcludeNot' are a list of file patterns matched with '?=='. -- The copied content is tracked. -copyDirectoryContent :: Exclude -> ExcludeNot -> FilePath -> FilePath -> Action () -copyDirectoryContent exclude excludeNot source target = do +copyDirectoryContent :: Match -> FilePath -> FilePath -> Action () +copyDirectoryContent expr source target = do putProgressInfo $ renderAction "Copy directory content" source target - getDirectoryContent exclude excludeNot source >>= mapM_ cp + getDirectoryContent expr source >>= mapM_ cp where cp a = do createDirectory $ dropFileName $ target' a From git at git.haskell.org Fri Oct 27 01:05:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #266 from KaiHa/copyDirectoryContent (df3ad6d) Message-ID: <20171027010523.CE6003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/df3ad6da2a9e7865bd535499412fd453d29f8a94/ghc >--------------------------------------------------------------- commit df3ad6da2a9e7865bd535499412fd453d29f8a94 Merge: 0579308 5999957 Author: Andrey Mokhov Date: Fri Jul 1 15:44:33 2016 +0100 Merge pull request #266 from KaiHa/copyDirectoryContent Add actions copyDirectoryContent and runBuilderWith >--------------------------------------------------------------- df3ad6da2a9e7865bd535499412fd453d29f8a94 hadrian.cabal | 1 + src/Oracles/DirectoryContent.hs | 39 +++++++++++++++++++++++++++++++++++++++ src/Rules/Actions.hs | 27 ++++++++++++++++++++++----- src/Rules/Oracles.hs | 2 ++ 4 files changed, 64 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Oct 27 01:05:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused folder (88b495c) Message-ID: <20171027010527.5DFF03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88b495c3dec700e76501319a995e2902a159d838/ghc >--------------------------------------------------------------- commit 88b495c3dec700e76501319a995e2902a159d838 Author: Andrey Mokhov Date: Wed Jul 13 00:44:16 2016 +0100 Drop unused folder >--------------------------------------------------------------- 88b495c3dec700e76501319a995e2902a159d838 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 5307cdd..6fbc3b2 100644 --- a/.gitignore +++ b/.gitignore @@ -1,4 +1,4 @@ -/.db/ +# generated by the configure script cfg/system.config # build.bat and build.sh specific From git at git.haskell.org Fri Oct 27 01:05:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Enable RecordWildCards (fa4ca65) Message-ID: <20171027010530.C8C503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fa4ca65a88bd883758888df5665d78844138c69f/ghc >--------------------------------------------------------------- commit fa4ca65a88bd883758888df5665d78844138c69f Author: Andrey Mokhov Date: Wed Jul 13 00:37:22 2016 +0100 Enable RecordWildCards >--------------------------------------------------------------- fa4ca65a88bd883758888df5665d78844138c69f .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 2f24ebe..85dfc94 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,2 @@ -:set -Wall -fno-warn-name-shadowing -isrc +:set -Wall -fno-warn-name-shadowing -isrc -XRecordWildCards :load Main From git at git.haskell.org Fri Oct 27 01:05:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor build flavours (3be52c5) Message-ID: <20171027010534.663C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46/ghc >--------------------------------------------------------------- commit 3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46 Author: Andrey Mokhov Date: Wed Jul 13 00:43:38 2016 +0100 Refactor build flavours See #268. >--------------------------------------------------------------- 3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46 hadrian.cabal | 4 +- src/CmdLineFlag.hs | 24 ++---- src/Flavour.hs | 18 ++++ src/Oracles/ArgsHash.hs | 2 +- src/Oracles/Dependencies.hs | 1 + src/Oracles/WindowsPath.hs | 8 +- src/Rules.hs | 18 ++-- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 1 + src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 3 +- src/Rules/Dependencies.hs | 3 +- src/Rules/Documentation.hs | 4 +- src/Rules/Generate.hs | 3 +- src/Rules/Generators/ConfigHs.hs | 6 +- src/Rules/Library.hs | 5 +- src/Rules/Program.hs | 2 + src/Rules/Register.hs | 2 +- src/Rules/Test.hs | 6 +- src/Rules/Wrappers/Ghc.hs | 2 +- src/Rules/Wrappers/GhcPkg.hs | 3 +- src/Settings.hs | 58 ++++++++++--- src/Settings/Args.hs | 95 --------------------- src/Settings/Builders/Cc.hs | 2 +- src/Settings/Builders/Common.hs | 1 + src/Settings/Builders/Configure.hs | 3 +- src/Settings/Builders/Ghc.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 5 +- src/Settings/Builders/GhcPkg.hs | 1 + src/Settings/Builders/Haddock.hs | 1 + src/Settings/Builders/Hsc2Hs.hs | 1 + src/Settings/Builders/Make.hs | 2 +- src/Settings/Default.hs | 169 ++++++++++++++++++++++++++++++++++++- src/Settings/Default.hs-boot | 13 +++ src/Settings/Flavours/Quick.hs | 22 +++-- src/Settings/Flavours/Quickest.hs | 18 ++-- src/Settings/Packages.hs | 57 ------------- src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Compiler.hs | 5 +- src/Settings/Packages/Rts.hs | 1 + src/Settings/Ways.hs | 46 ---------- src/UserSettings.hs | 57 +++---------- 43 files changed, 360 insertions(+), 324 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 3be52c5aa3b70732f3ca8b5c9cbd90f56949fc46 From git at git.haskell.org Fri Oct 27 01:05:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch from condLibrary to condLibraries in Cabal (54a8e15) Message-ID: <20171027010537.DD53B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/54a8e1579314b79890635323ff0e317834b720c9/ghc >--------------------------------------------------------------- commit 54a8e1579314b79890635323ff0e317834b720c9 Author: Andrey Mokhov Date: Thu Jul 14 00:26:35 2016 +0100 Switch from condLibrary to condLibraries in Cabal See #269. >--------------------------------------------------------------- 54a8e1579314b79890635323ff0e317834b720c9 src/Rules/Cabal.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index ed72f93..e2cdb0f 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -35,7 +35,8 @@ cabalRules = do else do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - let depsLib = collectDeps $ condLibrary pd + -- TODO: Support more than one Cabal library per package. + let depsLib = collectDeps . fmap snd . listToMaybe $ condLibraries pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes depNames = [ name | Dependency (DP.PackageName name) _ <- deps ] From git at git.haskell.org Fri Oct 27 01:05:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Support autogen paths of new Cabal (5fe4668) Message-ID: <20171027010541.602C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5fe46687bbbde9a82577e9b117378d3f9c027ee1/ghc >--------------------------------------------------------------- commit 5fe46687bbbde9a82577e9b117378d3f9c027ee1 Author: Andrey Mokhov Date: Thu Jul 14 01:28:02 2016 +0100 Support autogen paths of new Cabal See #269. >--------------------------------------------------------------- 5fe46687bbbde9a82577e9b117378d3f9c027ee1 src/Rules/Data.hs | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 2da6f86..034b2f4 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -38,12 +38,19 @@ buildPackageData context at Context {..} = do -- TODO: Get rid of this, see #113. dataFile %> \mk -> do + -- TODO: This is a hack. Add a proper support for autogen directory + -- structure of the new Cabal (probably only after #113). + let oldBuild + | isLibrary package = oldPath -/- "build" + | package == ghc = oldPath -/- "build/ghc" + | package == hpcBin = oldPath -/- "build/hpc" + | otherwise = oldPath -/- "build" -/- pkgNameString package copyFile inTreeMk mk - autogenFiles <- getDirectoryFiles (oldPath -/- "build") ["autogen/*"] + autogenFiles <- getDirectoryFiles oldBuild ["autogen/*"] createDirectory $ buildPath context -/- "autogen" forM_ autogenFiles $ \file' -> do let file = unifyPath file' - copyFile (oldPath -/- "build" -/- file) (buildPath context -/- file) + copyFile (oldBuild -/- file) (buildPath context -/- file) let haddockPrologue = "haddock-prologue.txt" copyFile (oldPath -/- haddockPrologue) (buildPath context -/- haddockPrologue) postProcessPackageData context mk From git at git.haskell.org Fri Oct 27 01:05:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Point to in-tree Cabal sources (6369ef0) Message-ID: <20171027010544.D1B3B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6369ef04c8ba978c7670c4b79fe85c16e7a11139/ghc >--------------------------------------------------------------- commit 6369ef04c8ba978c7670c4b79fe85c16e7a11139 Author: Andrey Mokhov Date: Thu Jul 14 02:04:08 2016 +0100 Point to in-tree Cabal sources >--------------------------------------------------------------- 6369ef04c8ba978c7670c4b79fe85c16e7a11139 .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 85dfc94..9c0fe7a 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,2 @@ -:set -Wall -fno-warn-name-shadowing -isrc -XRecordWildCards +:set -Wall -fno-warn-name-shadowing -isrc -i../libraries/Cabal/Cabal -XRecordWildCards :load Main From git at git.haskell.org Fri Oct 27 01:05:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop trackBuildSystem setting (4ad8082) Message-ID: <20171027010548.4DCB03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ad80828794f13c3e9139a68f06f3f2b6db1428f/ghc >--------------------------------------------------------------- commit 4ad80828794f13c3e9139a68f06f3f2b6db1428f Author: Andrey Mokhov Date: Thu Jul 14 02:04:32 2016 +0100 Drop trackBuildSystem setting >--------------------------------------------------------------- 4ad80828794f13c3e9139a68f06f3f2b6db1428f src/Oracles/ArgsHash.hs | 3 +-- src/Rules/Generators/Common.hs | 6 ++---- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/UserSettings.hs | 13 ++----------- 5 files changed, 7 insertions(+), 19 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index d1ebc68..660edd9 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -5,7 +5,6 @@ import Base import Expression import Settings import Target -import UserSettings newtype ArgsHashKey = ArgsHashKey Target deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -21,7 +20,7 @@ newtype ArgsHashKey = ArgsHashKey Target -- argument list constructors are assumed not to examine target sources, but -- only append them to argument lists where appropriate. checkArgsHash :: Target -> Action () -checkArgsHash target = when trackBuildSystem $ do +checkArgsHash target = do let hashed = [ show . hash $ inputs target ] _ <- askOracle . ArgsHashKey $ target { inputs = hashed } :: Action Int return () diff --git a/src/Rules/Generators/Common.hs b/src/Rules/Generators/Common.hs index e97d536..b01ad2f 100644 --- a/src/Rules/Generators/Common.hs +++ b/src/Rules/Generators/Common.hs @@ -2,12 +2,10 @@ module Rules.Generators.Common (trackSource, yesNo, cppify) where import Base import Expression -import UserSettings --- | Track a given source file when constructing an expression if the user --- enabled 'trackBuildSystem' in @hadrian/src/UserSettings.hs at . +-- | Track a given source file when constructing an expression. trackSource :: FilePath -> Expr () -trackSource file = lift $ when trackBuildSystem $ need [ sourcePath -/- file ] +trackSource file = lift $ need [ sourcePath -/- file ] -- | Turn a 'Bool' computed by an 'Action' into a 'String' expression returning -- "YES" (when the Boolean is 'True') or "NO" (when the Boolean is 'False'). diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index efe9144..0cf5b91 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -34,7 +34,7 @@ gmpRules :: Rules () gmpRules = do -- TODO: split into multiple rules gmpLibraryH %> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"] + need [sourcePath -/- "Rules/Gmp.hs"] removeDirectory gmpBuildPath -- We don't use system GMP on Windows. TODO: fix? diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 3ee3307..99b97df 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -58,7 +58,7 @@ configureEnvironment = do libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] + need [sourcePath -/- "Rules/Libffi.hs"] useSystemFfi <- flag UseSystemFfi if useSystemFfi then do diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 1f73efa..a0a5d49 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,9 +3,8 @@ -- If you don't copy the file your changes will be tracked by git and you can -- accidentally commit them. module UserSettings ( - buildRootPath, userFlavours, userKnownPackages, integerLibrary, - trackBuildSystem, validating, turnWarningsIntoErrors, verboseCommands, - putBuild, putSuccess + buildRootPath, userFlavours, userKnownPackages, integerLibrary, validating, + turnWarningsIntoErrors, verboseCommands, putBuild, putSuccess ) where import System.Console.ANSI @@ -42,14 +41,6 @@ integerLibrary = integerGmp -- * @Predicate@: a flag whose value can depend on the build environment and -- on the current build target. --- TODO: Drop 'trackBuildSystem' as it brings negligible gains. --- | Set this to True if you are making any changes in the build system and want --- appropriate rebuilds to be initiated. Switching this to False speeds things --- up a little (particularly zero builds). --- WARNING: a complete rebuild is required when changing this setting. -trackBuildSystem :: Bool -trackBuildSystem = True - -- TODO: This should be set automatically when validating. validating :: Bool validating = False From git at git.haskell.org Fri Oct 27 01:05:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix autogen path for iserv (38d1f55) Message-ID: <20171027010552.10DD73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/38d1f551cbd1dd94d33da9290e98bacca394f285/ghc >--------------------------------------------------------------- commit 38d1f551cbd1dd94d33da9290e98bacca394f285 Author: Andrey Mokhov Date: Thu Jul 14 02:07:25 2016 +0100 Fix autogen path for iserv See #269. >--------------------------------------------------------------- 38d1f551cbd1dd94d33da9290e98bacca394f285 src/Rules/Data.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 034b2f4..959a7ec 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -41,10 +41,11 @@ buildPackageData context at Context {..} = do -- TODO: This is a hack. Add a proper support for autogen directory -- structure of the new Cabal (probably only after #113). let oldBuild - | isLibrary package = oldPath -/- "build" - | package == ghc = oldPath -/- "build/ghc" - | package == hpcBin = oldPath -/- "build/hpc" - | otherwise = oldPath -/- "build" -/- pkgNameString package + | isLibrary package = oldPath -/- "build" + | package == ghc = oldPath -/- "build/ghc" + | package == hpcBin = oldPath -/- "build/hpc" + | package == iservBin = oldPath -/- "build/iserv" + | otherwise = oldPath -/- "build" -/- pkgNameString package copyFile inTreeMk mk autogenFiles <- getDirectoryFiles oldBuild ["autogen/*"] createDirectory $ buildPath context -/- "autogen" From git at git.haskell.org Fri Oct 27 01:05:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try full build on AppVeyor (b05a328) Message-ID: <20171027010555.89CE83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b05a3287007421b0390a1f19f44874899d0c33f9/ghc >--------------------------------------------------------------- commit b05a3287007421b0390a1f19f44874899d0c33f9 Author: Andrey Mokhov Date: Thu Jul 14 22:32:54 2016 +0100 Try full build on AppVeyor >--------------------------------------------------------------- b05a3287007421b0390a1f19f44874899d0c33f9 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index e4d7d52..a3de01a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest From git at git.haskell.org Fri Oct 27 01:05:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:05:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test Stage2 GHC after the build (29c2402) Message-ID: <20171027010559.1988F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/29c2402924e4d7af440771b6eff4a019c37b24c3/ghc >--------------------------------------------------------------- commit 29c2402924e4d7af440771b6eff4a019c37b24c3 Author: Andrey Mokhov Date: Thu Jul 14 23:21:43 2016 +0100 Test Stage2 GHC after the build >--------------------------------------------------------------- 29c2402924e4d7af440771b6eff4a019c37b24c3 appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/appveyor.yml b/appveyor.yml index a3de01a..4f55e5a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -38,3 +38,4 @@ build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + - stack exec -- C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 From git at git.haskell.org Fri Oct 27 01:06:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to run Stage2 GHC without Stack (868ffae) Message-ID: <20171027010602.D44843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/868ffae9e2af3e603dc6675b6e6c5a58e4396430/ghc >--------------------------------------------------------------- commit 868ffae9e2af3e603dc6675b6e6c5a58e4396430 Author: Andrey Mokhov Date: Fri Jul 15 00:03:27 2016 +0100 Attempt to run Stage2 GHC without Stack >--------------------------------------------------------------- 868ffae9e2af3e603dc6675b6e6c5a58e4396430 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4f55e5a..4392abe 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -38,4 +38,4 @@ build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest - - stack exec -- C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 + - C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 From git at git.haskell.org Fri Oct 27 01:06:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try default build flavour on Travis Linux (abfd4e7) Message-ID: <20171027010606.5B0513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/abfd4e73326d967c15ac2254f303cf622ae2af40/ghc >--------------------------------------------------------------- commit abfd4e73326d967c15ac2254f303cf622ae2af40 Author: Andrey Mokhov Date: Fri Jul 15 17:24:29 2016 +0100 Try default build flavour on Travis Linux >--------------------------------------------------------------- abfd4e73326d967c15ac2254f303cf622ae2af40 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index b066e89..2b2379f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quick TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=default TARGET= addons: apt: packages: From git at git.haskell.org Fri Oct 27 01:06:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update build flavour related text (59b07fd) Message-ID: <20171027010609.C4D663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59b07fddd177b3813a4dcc5704efbde4dca7857d/ghc >--------------------------------------------------------------- commit 59b07fddd177b3813a4dcc5704efbde4dca7857d Author: Andrey Mokhov Date: Sat Jul 16 17:57:07 2016 +0100 Update build flavour related text See #268. [skip ci] >--------------------------------------------------------------- 59b07fddd177b3813a4dcc5704efbde4dca7857d doc/user-settings.md | 90 +++++++++++++++++++++++++++++++++------------------- 1 file changed, 57 insertions(+), 33 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 1dbfd6f..01c3831 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -15,6 +15,39 @@ buildRootPath :: FilePath buildRootPath = "_build" ``` +## Build flavour + +Build _flavour_ is a collection of build settings that fully define a GHC build: +```haskell +data Flavour = Flavour + { name :: String -- ^ Flavour name, to set from command line. + , args :: Args -- ^ Use these command line arguments. + , packages :: Packages -- ^ Build these packages. + , libraryWays :: Ways -- ^ Build libraries these ways. + , rtsWays :: Ways -- ^ Build RTS these ways. + , splitObjects :: Predicate -- ^ Build split objects. + , buildHaddock :: Predicate -- ^ Build Haddock and documentation. + , dynamicGhcPrograms :: Bool -- ^ Build dynamic GHC programs. + , ghciWithDebugger :: Bool -- ^ Enable GHCi debugger. + , ghcProfiled :: Bool -- ^ Build profiled GHC. + , ghcDebugged :: Bool } -- ^ Build GHC with debug information. +``` +Hadrian provides several built-in flavours (`defaultFlavour`, `quickFlavour`, and +a few others), which can be activated from the command line, e.g. `--flavour=quick`. +Users can define new build flavours by adding them to `userFlavours` list: +```haskell +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default flavour + +userFlavours :: [Flavour] +userFlavours = [userFlavour] +``` +Now `--flavour=user` will run Hadrian with `userFlavour` settings. Note: +`defaultFlavour` is defined in module `Settings.Default`, which must be +imported as `import {-# SOURCE #-} Settings.Default` to handle cyclic +module dependencies. In the following sections we look at specific fields of +the `Flavour` record in more detail. + ## Command line arguments One of the key features of Hadrian is that users can modify any build command by @@ -24,7 +57,9 @@ affected build rules during the next build, without requiring a full rebuild. For example, here is how to pass an extra argument `-O0` to all invocations of GHC when compiling package `cabal`: ```haskell --- | Modify default build command line arguments. +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", args = defaultArgs <> userArgs } + userArgs :: Args userArgs = builder Ghc ? package cabal ? arg "-O0" ``` @@ -50,28 +85,28 @@ path component, excluding any separators. ## Packages -To add or remove a package from a particular build stage, use `userPackages`. As -an example, below we add package `base` to Stage0 and remove package `haskeline` -from Stage1: +Users can add and remove packages from particular build stages. As an example, +below we add package `base` to Stage0 and remove package `haskeline` from Stage1: ```haskell --- | Modify the set of packages that are built by default in each stage. +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", packages = defaultPackages <> userPackages } + userPackages :: Packages userPackages = mconcat [ stage0 ? append [base] , stage1 ? remove [haskeline] ] ``` If you are working on a new GHC package you need to let Hadrian know about it -by setting `userKnownPackages`: +by adding it to `userKnownPackages`: ```haskell --- | Add user defined packages. Don't forget to add them to 'userPackages' too. userKnownPackages :: [Package] -userKnownPackages = [myPackage] +userKnownPackages = [userPackage] --- An example package that lives in "libraries/my-package" directory. -myPackage :: Package -myPackage = library "my-package" +-- An example package that lives in "libraries/user-package" directory. +userPackage :: Package +userPackage = library "user-package" ``` -Note, you will also need to add `myPackage` to a specific build stage by modifying +Note, you will also need to add `userPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting @@ -85,17 +120,12 @@ integerLibrary = integerGmp Packages can be built in a number of ways, such as `vanilla`, `profiling` (with profiling information enabled), and many others as defined in `src/Way.hs`. You -can change the default build ways using `userLibraryWays` and `userRtsWays` settings. -As an example, below we remove `dynamic` from the list of library ways but keep -`rts` package ways unchanged: +can change the default build ways by modifying `libraryWays` and `rtsWays` fields +of the `Flavour` record as required. As an example, below we remove `dynamic` +from the list of library ways but keep `rts` package ways unchanged: ```haskell --- | Modify the set of ways in which library packages are built. -userLibraryWays :: Ways -userLibraryWays = remove [dynamic] - --- | Modify the set of ways in which the 'rts' package is built. -userRtsWays :: Ways -userRtsWays = mempty +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", libraryWays = defaultLibraryWays <> remove [dynamic] } ``` ## Verbose command lines @@ -133,18 +163,12 @@ verboseCommands = return True ## Miscellaneous -Use the following settings to change the default behaviour of Hadrian with respect -to building split objects and Haddock documentation. - +To change the default behaviour of Hadrian with respect to building split +objects and Haddock documentation, override `splitObjects` and `buildHaddock` +fields of the `Flavour` record, for example: ```haskell --- | Control when split objects are generated. Note, due to the GHC bug #11315 --- it is necessary to do a full clean rebuild when changing this option. -splitObjects :: Predicate -splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects - --- | Control when to build Haddock documentation. -buildHaddock :: Predicate -buildHaddock = return cmdBuildHaddock +userFlavour :: Flavour +userFlavour = defaultFlavour { name = "user", splitObjects = return False, buildHaddock = return True } ``` Hadrian prints various progress info during the build. You can customise how this From git at git.haskell.org Fri Oct 27 01:06:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (0053526) Message-ID: <20171027010613.3D6193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0053526eac7df90feba32fe90541c5e4a413da07/ghc >--------------------------------------------------------------- commit 0053526eac7df90feba32fe90541c5e4a413da07 Author: Andrey Mokhov Date: Sat Jul 16 18:09:07 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- 0053526eac7df90feba32fe90541c5e4a413da07 doc/user-settings.md | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 01c3831..1b0a05e 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -17,7 +17,8 @@ buildRootPath = "_build" ## Build flavour -Build _flavour_ is a collection of build settings that fully define a GHC build: +Build _flavour_ is a collection of build settings that fully define a GHC build +(see `src/Flavour.hs`): ```haskell data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. @@ -37,21 +38,22 @@ a few others), which can be activated from the command line, e.g. `--flavour=qui Users can define new build flavours by adding them to `userFlavours` list: ```haskell userFlavour :: Flavour -userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default flavour +userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default build flavour userFlavours :: [Flavour] userFlavours = [userFlavour] ``` -Now `--flavour=user` will run Hadrian with `userFlavour` settings. Note: -`defaultFlavour` is defined in module `Settings.Default`, which must be -imported as `import {-# SOURCE #-} Settings.Default` to handle cyclic -module dependencies. In the following sections we look at specific fields of -the `Flavour` record in more detail. +Now `--flavour=user` will run Hadrian with `userFlavour` settings. In the +following sections we look at specific fields of the `Flavour` record in +more detail. Note: `defaultFlavour`, as well as its individual fields such +as `defaultArgs`, `defaultPackages`, etc. that we use below, are defined in module +`Settings.Default`. Import it as +`import {-# SOURCE #-} Settings.Default` to handle cyclic module dependencies. ## Command line arguments -One of the key features of Hadrian is that users can modify any build command by -changing `userArgs`. The build system will detect the change and will rerun all +One of the key features of Hadrian is that users can easily modify any build command. +The build system will detect the change and will rerun all affected build rules during the next build, without requiring a full rebuild. For example, here is how to pass an extra argument `-O0` to all invocations of @@ -106,7 +108,7 @@ userKnownPackages = [userPackage] userPackage :: Package userPackage = library "user-package" ``` -Note, you will also need to add `userPackage` to a specific build stage by modifying +You will also need to add `userPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting From git at git.haskell.org Fri Oct 27 01:06:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Typo (e1b6e52) Message-ID: <20171027010616.BC5033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1b6e522c1ca78cede5a3a4e45d2a7e05ef1aa0c/ghc >--------------------------------------------------------------- commit e1b6e522c1ca78cede5a3a4e45d2a7e05ef1aa0c Author: Gabor Greif Date: Sat Jul 16 19:18:30 2016 +0200 Typo >--------------------------------------------------------------- e1b6e522c1ca78cede5a3a4e45d2a7e05ef1aa0c doc/user-settings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 1b0a05e..d4f0f95 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -38,7 +38,7 @@ a few others), which can be activated from the command line, e.g. `--flavour=qui Users can define new build flavours by adding them to `userFlavours` list: ```haskell userFlavour :: Flavour -userFlavour = defaultFlavour { name = "user", ... } -- mofidy the default build flavour +userFlavour = defaultFlavour { name = "user", ... } -- modify the default build flavour userFlavours :: [Flavour] userFlavours = [userFlavour] From git at git.haskell.org Fri Oct 27 01:06:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #270 from ggreif/patch-1 (03ffd8e) Message-ID: <20171027010620.405AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03ffd8e37ba2b55bbba5b97b5a8aa4dfed2afa84/ghc >--------------------------------------------------------------- commit 03ffd8e37ba2b55bbba5b97b5a8aa4dfed2afa84 Merge: 0053526 e1b6e52 Author: Andrey Mokhov Date: Sat Jul 16 18:22:33 2016 +0100 Merge pull request #270 from ggreif/patch-1 Typo [skip ci] >--------------------------------------------------------------- 03ffd8e37ba2b55bbba5b97b5a8aa4dfed2afa84 doc/user-settings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 01:06:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop TODO (3b0fab4) Message-ID: <20171027010623.A84463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3b0fab4ddaf709c17757d97416a84a9e3547ce6b/ghc >--------------------------------------------------------------- commit 3b0fab4ddaf709c17757d97416a84a9e3547ce6b Author: Andrey Mokhov Date: Sat Jul 16 23:52:17 2016 +0100 Drop TODO >--------------------------------------------------------------- 3b0fab4ddaf709c17757d97416a84a9e3547ce6b src/UserSettings.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index a0a5d49..b952363 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -14,7 +14,6 @@ import Flavour import GHC import Predicate --- TODO: Update the docs. -- See doc/user-settings.md for instructions. -- | All build results are put into 'buildRootPath' directory. From git at git.haskell.org Fri Oct 27 01:06:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert to quickest build flavour on Travis Linux (118adf2) Message-ID: <20171027010627.21FF73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/118adf2fa6476460270c3d06d9e935ffcb28ab7d/ghc >--------------------------------------------------------------- commit 118adf2fa6476460270c3d06d9e935ffcb28ab7d Author: Andrey Mokhov Date: Sun Jul 17 00:09:07 2016 +0100 Revert to quickest build flavour on Travis Linux >--------------------------------------------------------------- 118adf2fa6476460270c3d06d9e935ffcb28ab7d .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 2b2379f..dd74f25 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,7 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=default TARGET= + env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quickest TARGET= addons: apt: packages: From git at git.haskell.org Fri Oct 27 01:06:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix the 'unknown symbol stat' issue on Travis Linux (116e64d) Message-ID: <20171027010630.937DA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/116e64d5596233dcacff48ce7e5e0531f730e6bd/ghc >--------------------------------------------------------------- commit 116e64d5596233dcacff48ce7e5e0531f730e6bd Author: Andrey Mokhov Date: Sun Jul 17 00:52:00 2016 +0100 Attempt to fix the 'unknown symbol stat' issue on Travis Linux See #259. >--------------------------------------------------------------- 116e64d5596233dcacff48ce7e5e0531f730e6bd src/Settings/Packages/Base.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages/Base.hs b/src/Settings/Packages/Base.hs index 261c2bb..dce49e7 100644 --- a/src/Settings/Packages/Base.hs +++ b/src/Settings/Packages/Base.hs @@ -6,5 +6,6 @@ import Predicate import UserSettings basePackageArgs :: Args -basePackageArgs = package base ? - builder GhcCabal ? arg ("--flags=" ++ takeFileName (pkgPath integerLibrary)) +basePackageArgs = package base ? mconcat + [ builder GhcCabal ? arg ("--flags=" ++ takeFileName (pkgPath integerLibrary)) + , builder Cc ? arg "-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. From git at git.haskell.org Fri Oct 27 01:06:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Change the stack configuration to use the local Cabal lib (1281be4) Message-ID: <20171027010634.089CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1281be42949bb986c62e0464032145b060649fe4/ghc >--------------------------------------------------------------- commit 1281be42949bb986c62e0464032145b060649fe4 Author: Michal Terepeta Date: Fri Jul 22 11:30:50 2016 +0200 Change the stack configuration to use the local Cabal lib Hadrian should be built with a local Cabal from within the GHC codebase. This makes the stack pick it up, instead of using the released version of Cabal. Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 1281be42949bb986c62e0464032145b060649fe4 hadrian.cabal | 2 +- stack.yaml | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 3429424..63bd164 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* || == 1.24.* + , Cabal == 1.22.* || == 1.24.* || == 1.25.* , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 diff --git a/stack.yaml b/stack.yaml index f6deca8..9eb4cfb 100644 --- a/stack.yaml +++ b/stack.yaml @@ -6,6 +6,7 @@ resolver: lts-5.17 # Local packages, usually specified by relative directory name packages: - '.' +- '../libraries/Cabal/Cabal' # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: From git at git.haskell.org Fri Oct 27 01:06:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #271 from michalt/stack-localcabal/1 (3380e0d) Message-ID: <20171027010637.713903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3380e0d6c1f90a502229390a19298a82d84c14b8/ghc >--------------------------------------------------------------- commit 3380e0d6c1f90a502229390a19298a82d84c14b8 Merge: 116e64d 1281be4 Author: Andrey Mokhov Date: Fri Jul 22 11:45:34 2016 +0200 Merge pull request #271 from michalt/stack-localcabal/1 Change the stack configuration to use the local Cabal lib >--------------------------------------------------------------- 3380e0d6c1f90a502229390a19298a82d84c14b8 hadrian.cabal | 2 +- stack.yaml | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 01:06:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install only after GHC sources are fetched (9e22012) Message-ID: <20171027010640.E394A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e2201243a40e63e010d923005a87dbb26f1b305/ghc >--------------------------------------------------------------- commit 9e2201243a40e63e010d923005a87dbb26f1b305 Author: Andrey Mokhov Date: Fri Jul 22 11:55:50 2016 +0200 Install only after GHC sources are fetched >--------------------------------------------------------------- 9e2201243a40e63e010d923005a87dbb26f1b305 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4392abe..4c3e714 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -15,7 +15,6 @@ install: - 7z x stack.zip stack.exe - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ @@ -24,6 +23,7 @@ install: - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - ghc --version - stack --version - alex --version From git at git.haskell.org Fri Oct 27 01:06:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix GHC location before Stack install (b2fc154) Message-ID: <20171027010644.7C3113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2fc1542ca069e5efb3abaa8dcb2213bd1ed8308/ghc >--------------------------------------------------------------- commit b2fc1542ca069e5efb3abaa8dcb2213bd1ed8308 Author: Andrey Mokhov Date: Fri Jul 22 12:17:52 2016 +0200 Fix GHC location before Stack install >--------------------------------------------------------------- b2fc1542ca069e5efb3abaa8dcb2213bd1ed8308 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4c3e714..30e3bcf 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -23,13 +23,13 @@ install: - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + - bash -lc "mv /home/ghc/tmp/* /home/ghc" - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - ghc --version - stack --version - alex --version - happy --version - stack exec -- ghc-pkg list - - bash -lc "mv /home/ghc/tmp/* /home/ghc" - cd C:\msys64\home\ghc - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" From git at git.haskell.org Fri Oct 27 01:06:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix inability to find gmp.h when building concurrently (b3bcd0f) Message-ID: <20171027010647.F1ACA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3bcd0ffe22fa51b78aa28caf406b7cb74b04ae8/ghc >--------------------------------------------------------------- commit b3bcd0ffe22fa51b78aa28caf406b7cb74b04ae8 Author: Matthew Pickering Date: Fri Jul 22 14:03:07 2016 +0200 Fix inability to find gmp.h when building concurrently There were situations when building concurrently when we would request `gmp.h` before it had been built (or copied). This was occuring when we generated the list of dependents for the c files in the `integer-gmp` folder. Thus, when generating the dependents for this library we now require `gmp.h`. >--------------------------------------------------------------- b3bcd0ffe22fa51b78aa28caf406b7cb74b04ae8 src/Rules/Dependencies.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index f78c488..c64a4e6 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -11,6 +11,8 @@ import Rules.Actions import Settings.Paths import Target import UserSettings +import GHC + buildPackageDependencies :: [(Resource, Int)] -> Context -> Rules () buildPackageDependencies rs context at Context {..} = @@ -20,6 +22,7 @@ buildPackageDependencies rs context at Context {..} = fmap (path ++) [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do let src = dep2src context out + when (package == integerGmp) (need [gmpLibraryH]) need [src] build $ Target context (Cc FindDependencies stage) [src] [out] From git at git.haskell.org Fri Oct 27 01:06:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #273 from mpickering/master (4a7016b) Message-ID: <20171027010651.C7E293A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a7016b71f1a393cfbd9f2360802b07f0a7e9b06/ghc >--------------------------------------------------------------- commit 4a7016b71f1a393cfbd9f2360802b07f0a7e9b06 Merge: b2fc154 b3bcd0f Author: Andrey Mokhov Date: Fri Jul 22 15:09:40 2016 +0200 Merge pull request #273 from mpickering/master Fix inability to find gmp.h when building concurrently >--------------------------------------------------------------- 4a7016b71f1a393cfbd9f2360802b07f0a7e9b06 src/Rules/Dependencies.hs | 3 +++ 1 file changed, 3 insertions(+) From git at git.haskell.org Fri Oct 27 01:06:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split CompilerMode for GHC and CC (a8abbc9) Message-ID: <20171027010655.5A7133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8abbc961fcfcd360e9a731fc42c28b93332bc8b/ghc >--------------------------------------------------------------- commit a8abbc961fcfcd360e9a731fc42c28b93332bc8b Author: Michal Terepeta Date: Sat Jul 23 16:57:19 2016 +0200 Split CompilerMode for GHC and CC Signed-off-by: Michal Terepeta >--------------------------------------------------------------- a8abbc961fcfcd360e9a731fc42c28b93332bc8b src/Builder.hs | 27 +++++++++++++++++---------- src/Predicate.hs | 8 +++++++- src/Rules/Compile.hs | 6 +++--- src/Rules/Dependencies.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Test.hs | 4 ++-- src/Settings/Builders/Cc.hs | 4 ++-- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- 13 files changed, 46 insertions(+), 33 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 a8abbc961fcfcd360e9a731fc42c28b93332bc8b From git at git.haskell.org Fri Oct 27 01:06:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:06:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #275 from michalt/compilermode/1 (e89ab5c) Message-ID: <20171027010658.E10EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e89ab5c63394d13793b32b391923945154c4c87d/ghc >--------------------------------------------------------------- commit e89ab5c63394d13793b32b391923945154c4c87d Merge: 4a7016b a8abbc9 Author: Andrey Mokhov Date: Sat Jul 23 20:03:13 2016 +0200 Merge pull request #275 from michalt/compilermode/1 Split CompilerMode for GHC and CC >--------------------------------------------------------------- e89ab5c63394d13793b32b391923945154c4c87d src/Builder.hs | 27 +++++++++++++++++---------- src/Predicate.hs | 8 +++++++- src/Rules/Compile.hs | 6 +++--- src/Rules/Dependencies.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Test.hs | 4 ++-- src/Settings/Builders/Cc.hs | 4 ++-- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 ++++---- src/Settings/Builders/GhcCabal.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- 13 files changed, 46 insertions(+), 33 deletions(-) diff --cc src/Rules/Dependencies.hs index c64a4e6,94a9542..8aeecf5 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@@ -22,9 -20,8 +22,9 @@@ buildPackageDependencies rs context at Con fmap (path ++) [ "//*.c.deps", "//*.cmm.deps", "//*.S.deps" ] |%> \out -> do let src = dep2src context out + when (package == integerGmp) (need [gmpLibraryH]) need [src] - build $ Target context (Cc FindDependencies stage) [src] [out] + build $ Target context (Cc FindCDependencies stage) [src] [out] hDepFile %> \out -> do srcs <- haskellSources context From git at git.haskell.org Fri Oct 27 01:07:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use nm-classic instead of nm when host is Darwin (3c31edc) Message-ID: <20171027010702.E5D793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3c31edcca75f477bfeb54cd844c9d2f575037c3c/ghc >--------------------------------------------------------------- commit 3c31edcca75f477bfeb54cd844c9d2f575037c3c Author: Tomas Carnecky Date: Sun Jul 24 00:03:59 2016 +0200 Use nm-classic instead of nm when host is Darwin >--------------------------------------------------------------- 3c31edcca75f477bfeb54cd844c9d2f575037c3c README.md | 8 -------- src/Settings/Builders/Configure.hs | 7 +++++++ 2 files changed, 7 insertions(+), 8 deletions(-) diff --git a/README.md b/README.md index 4ce3b3a..d99d2b7 100644 --- a/README.md +++ b/README.md @@ -43,14 +43,6 @@ runs the `boot` and `configure` scripts automatically on the first build, so tha need to. Use `--skip-configure` to suppress this behaviour (see overview of command line flags below). -* Also note on OS X newer versions of XCode ship with a broken `nm` tool -([#11744](https://ghc.haskell.org/trac/ghc/ticket/11744)). One way to mitigate the -problem is to add the following into your `UserSettings.hs`: - ````haskell - userArgs :: Args - userArgs = builder (Configure ".") ? arg "--with-nm=$(xcrun --find nm-classic)" - ```` - Using the build system ---------------------- Once your first build is successful, simply run `build` to rebuild. Most build artefacts diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index c95a5da..6482df1 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -1,5 +1,7 @@ module Settings.Builders.Configure (configureBuilderArgs) where +import qualified System.Info as System + import Base import Oracles.Config.Setting import Oracles.WindowsPath @@ -23,4 +25,9 @@ configureBuilderArgs = mconcat , "--enable-static=yes" , "--enable-shared=no" -- TODO: add support for yes , "--host=" ++ targetPlatform ] + + -- On OS X, use "nm-classic" instead of "nm" due to a bug in the later. + -- See https://ghc.haskell.org/trac/ghc/ticket/11744 + , builder (Configure ".") ? System.os == "darwin" ? + arg "--with-nm=$(xcrun --find nm-classic)" ] From git at git.haskell.org Fri Oct 27 01:07:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use in-tree cabal in build.cabal.sh (works for cabal < 1.24) (fc4c968) Message-ID: <20171027010706.B90AB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fc4c968378c1d4467cf59e8bbaefa66f473526f7/ghc >--------------------------------------------------------------- commit fc4c968378c1d4467cf59e8bbaefa66f473526f7 Author: Kai Harries Date: Sun Jul 24 11:37:08 2016 +0200 Use in-tree cabal in build.cabal.sh (works for cabal < 1.24) Partial fix of #274 This installs the in-tree Cabal into the cabal-sandbox before building hadrian itself. This only works if the installed cabal version is < 1.24, because I have not yet figured out how it can be done with the newly introduced `new-build` command. >--------------------------------------------------------------- fc4c968378c1d4467cf59e8bbaefa66f473526f7 build.cabal.sh | 5 +++++ hadrian.cabal | 2 +- 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index 4a24dac..be2a117 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -61,6 +61,11 @@ else # Initialize sandbox if necessary if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then "$CABAL" sandbox init + ( cd ../libraries/Cabal/Cabal + ln -s "$absoluteRoot/cabal.sandbox.config" cabal.sandbox.config + cabal install + rm cabal.sandbox.config + ) "$CABAL" install \ --dependencies-only \ --disable-library-profiling \ diff --git a/hadrian.cabal b/hadrian.cabal index 63bd164..c07cef1 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* || == 1.24.* || == 1.25.* + , Cabal >= 1.25 , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 01:07:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: build.cabal.sh: Use CABAL variable (fd48c37) Message-ID: <20171027010710.68DBA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd48c372feb33e9c58c19c04929f9c63492c3b4d/ghc >--------------------------------------------------------------- commit fd48c372feb33e9c58c19c04929f9c63492c3b4d Author: Kai Harries Date: Sun Jul 24 12:15:55 2016 +0200 build.cabal.sh: Use CABAL variable >--------------------------------------------------------------- fd48c372feb33e9c58c19c04929f9c63492c3b4d build.cabal.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index be2a117..3b6bef5 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -63,7 +63,7 @@ else "$CABAL" sandbox init ( cd ../libraries/Cabal/Cabal ln -s "$absoluteRoot/cabal.sandbox.config" cabal.sandbox.config - cabal install + "$CABAL" install rm cabal.sandbox.config ) "$CABAL" install \ From git at git.haskell.org Fri Oct 27 01:07:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert raising of the cabal version in the build-dependency (564b125) Message-ID: <20171027010713.D95CE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/564b125e3d6df089ca849392be4d97c682e4ae64/ghc >--------------------------------------------------------------- commit 564b125e3d6df089ca849392be4d97c682e4ae64 Author: Kai Harries Date: Sun Jul 24 12:24:16 2016 +0200 Revert raising of the cabal version in the build-dependency Travis was failing because it uses `cabal install --only-dependencies` in the .travis.yml >--------------------------------------------------------------- 564b125e3d6df089ca849392be4d97c682e4ae64 hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index c07cef1..63bd164 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal >= 1.25 + , Cabal == 1.22.* || == 1.24.* || == 1.25.* , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 01:07:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use in-tree cabal in build.cabal.sh (for cabal >= 1.24) (3724023) Message-ID: <20171027010717.5B2C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/37240234b116c9aa90a5a0e893a94813373ad158/ghc >--------------------------------------------------------------- commit 37240234b116c9aa90a5a0e893a94813373ad158 Author: Kai Harries Date: Sun Jul 24 13:48:10 2016 +0200 Use in-tree cabal in build.cabal.sh (for cabal >= 1.24) >--------------------------------------------------------------- 37240234b116c9aa90a5a0e893a94813373ad158 cabal.project | 2 ++ 1 file changed, 2 insertions(+) diff --git a/cabal.project b/cabal.project new file mode 100644 index 0000000..1ef81ca --- /dev/null +++ b/cabal.project @@ -0,0 +1,2 @@ +packages: ../libraries/Cabal/Cabal/ + ./ From git at git.haskell.org Fri Oct 27 01:07:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use `add-source` instead of linking cabal.sandbox.config (ea51eaa) Message-ID: <20171027010720.D544A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ea51eaad8e5b8eb64183fa169224ab2df61a63b9/ghc >--------------------------------------------------------------- commit ea51eaad8e5b8eb64183fa169224ab2df61a63b9 Author: Kai Harries Date: Sun Jul 24 15:17:56 2016 +0200 Use `add-source` instead of linking cabal.sandbox.config As suggested by mpickering >--------------------------------------------------------------- ea51eaad8e5b8eb64183fa169224ab2df61a63b9 build.cabal.sh | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/build.cabal.sh b/build.cabal.sh index 3b6bef5..973cd3e 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -61,11 +61,7 @@ else # Initialize sandbox if necessary if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then "$CABAL" sandbox init - ( cd ../libraries/Cabal/Cabal - ln -s "$absoluteRoot/cabal.sandbox.config" cabal.sandbox.config - "$CABAL" install - rm cabal.sandbox.config - ) + "$CABAL" sandbox add-source ../libraries/Cabal/Cabal "$CABAL" install \ --dependencies-only \ --disable-library-profiling \ From git at git.haskell.org Fri Oct 27 01:07:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #277 from KaiHa/ticket274 (eff3e36) Message-ID: <20171027010724.536C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eff3e36640d0c72e34411acdcbaef71646d884ae/ghc >--------------------------------------------------------------- commit eff3e36640d0c72e34411acdcbaef71646d884ae Merge: e89ab5c ea51eaa Author: Andrey Mokhov Date: Sun Jul 24 17:51:26 2016 +0200 Merge pull request #277 from KaiHa/ticket274 Use in-tree cabal in build.cabal.sh >--------------------------------------------------------------- eff3e36640d0c72e34411acdcbaef71646d884ae build.cabal.sh | 1 + cabal.project | 2 ++ 2 files changed, 3 insertions(+) From git at git.haskell.org Fri Oct 27 01:07:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make generatedDependencies an Expr [FilePath] (234b41b) Message-ID: <20171027010727.C63AA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/234b41b171ad31ecbfec476f8f47202cac6f10cc/ghc >--------------------------------------------------------------- commit 234b41b171ad31ecbfec476f8f47202cac6f10cc Author: Michal Terepeta Date: Sun Jul 24 16:37:11 2016 +0200 Make generatedDependencies an Expr [FilePath] This fixes a TODO to change the `generatedDependencies` to use `Expr`. Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 234b41b171ad31ecbfec476f8f47202cac6f10cc src/Rules/Data.hs | 12 ++++---- src/Rules/Generate.hs | 79 ++++++++++++++++++++++++++++----------------------- 2 files changed, 49 insertions(+), 42 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 959a7ec..4208570 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -25,7 +25,7 @@ buildPackageData context at Context {..} = do inTreeMk %> \mk -> do -- Make sure all generated dependencies are in place before proceeding. - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies -- GhcCabal may run the configure script, so we depend on it. whenM (doesFileExist $ configure <.> "ac") $ need [configure] @@ -59,7 +59,7 @@ buildPackageData context at Context {..} = do -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps. priority 2.0 $ do when (package == hp2ps) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies includes <- interpretInContext context $ fromDiffExpr includesArgs let prefix = fixKey (buildPath context) ++ "_" cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" @@ -76,7 +76,7 @@ buildPackageData context at Context {..} = do putSuccess $ "| Successfully generated " ++ mk when (package == unlit) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies let prefix = fixKey (buildPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = unlit" @@ -86,7 +86,7 @@ buildPackageData context at Context {..} = do putSuccess $ "| Successfully generated " ++ mk when (package == touchy) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies let prefix = fixKey (buildPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = touchy" @@ -98,7 +98,7 @@ buildPackageData context at Context {..} = do -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. when (package == ghcCabal && stage == Stage0) $ dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies let prefix = fixKey (buildPath context) ++ "_" contents = unlines $ map (prefix++) [ "PROGNAME = ghc-cabal" @@ -110,7 +110,7 @@ buildPackageData context at Context {..} = do when (package == rts && stage == Stage1) $ do dataFile %> \mk -> do - orderOnly $ generatedDependencies stage package + orderOnly =<< interpretInContext context generatedDependencies windows <- windowsHost let prefix = fixKey (buildPath context) ++ "_" dirs = [ ".", "hooks", "sm", "eventlog", "linker" ] diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 17f51a5..415692b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -10,6 +10,8 @@ import Context import Expression import GHC import Oracles.ModuleFiles +import Predicate ( (?) ) +import qualified Predicate as Predicate import Rules.Actions import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH @@ -46,10 +48,11 @@ includesDependencies = ("includes" -/-) <$> , "ghcplatform.h" , "ghcversion.h" ] -ghcPrimDependencies :: Stage -> [FilePath] -ghcPrimDependencies stage = (buildPath (vanillaContext stage ghcPrim) -/-) <$> - [ "autogen/GHC/Prim.hs" - , "GHC/PrimopWrappers.hs" ] +ghcPrimDependencies :: Expr [FilePath] +ghcPrimDependencies = getStage >>= \stage -> + let prependPath x = buildPath (vanillaContext stage ghcPrim) -/- x + in return $ + fmap prependPath [ "autogen/GHC/Prim.hs" , "GHC/PrimopWrappers.hs" ] derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" @@ -61,39 +64,43 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) , "GHCConstantsHaskellType.hs" , "GHCConstantsHaskellWrappers.hs" ] -compilerDependencies :: Stage -> [FilePath] -compilerDependencies stage = - [ platformH stage ] - ++ includesDependencies - ++ [ gmpLibraryH | stage > Stage0 ] - ++ filter (const $ stage > Stage0) libffiDependencies - ++ derivedConstantsDependencies - ++ fmap (buildPath (vanillaContext stage compiler) -/-) - [ "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-fixity.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-list.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-strictness.hs-incl" - , "primop-tag.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tys.hs-incl" - , "primop-vector-uniques.hs-incl" ] - --- TODO: Turn this into a FilePaths expression -generatedDependencies :: Stage -> Package -> [FilePath] -generatedDependencies stage pkg - | pkg == compiler = compilerDependencies stage - | pkg == ghcPrim = ghcPrimDependencies stage - | pkg == rts = libffiDependencies ++ includesDependencies +compilerDependencies :: Expr [FilePath] +compilerDependencies = getStage >>= \stage -> + let prependBuildPath x = buildPath (vanillaContext stage compiler) -/- x + in mconcat $ + [ return $ (platformH stage) + : includesDependencies ++ derivedConstantsDependencies - | stage == Stage0 = includesDependencies - | otherwise = [] + , Predicate.notStage0 ? return (gmpLibraryH : libffiDependencies) + , return $ fmap prependBuildPath + [ "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-fixity.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-list.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-strictness.hs-incl" + , "primop-tag.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tys.hs-incl" + , "primop-vector-uniques.hs-incl" + ] + ] + +generatedDependencies :: Expr [FilePath] +generatedDependencies = mconcat + [ Predicate.package compiler ? compilerDependencies + , Predicate.package ghcPrim ? ghcPrimDependencies + , Predicate.package rts ? return ( + libffiDependencies + ++ includesDependencies + ++ derivedConstantsDependencies) + , Predicate.stage0 ? return includesDependencies + ] generate :: FilePath -> Context -> Expr String -> Action () generate file context expr = do From git at git.haskell.org Fri Oct 27 01:07:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #278 from michalt/generated-dependencies/1 (14a596a) Message-ID: <20171027010731.475283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14a596a8086249053dc291e8cb6b306b6e196cf5/ghc >--------------------------------------------------------------- commit 14a596a8086249053dc291e8cb6b306b6e196cf5 Merge: eff3e36 234b41b Author: Andrey Mokhov Date: Tue Aug 2 00:00:07 2016 +0200 Merge pull request #278 from michalt/generated-dependencies/1 Make generatedDependencies an Expr [FilePath] >--------------------------------------------------------------- 14a596a8086249053dc291e8cb6b306b6e196cf5 src/Rules/Data.hs | 12 ++++---- src/Rules/Generate.hs | 79 ++++++++++++++++++++++++++++----------------------- 2 files changed, 49 insertions(+), 42 deletions(-) From git at git.haskell.org Fri Oct 27 01:07:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (c547d12) Message-ID: <20171027010734.B722E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c547d12d30964f07671974d5f43c5d5e3cf56b7d/ghc >--------------------------------------------------------------- commit c547d12d30964f07671974d5f43c5d5e3cf56b7d Author: Andrey Mokhov Date: Tue Aug 2 02:27:30 2016 +0200 Minor revision See #278 >--------------------------------------------------------------- c547d12d30964f07671974d5f43c5d5e3cf56b7d src/Rules/Generate.hs | 77 ++++++++++++++++++++++++--------------------------- 1 file changed, 36 insertions(+), 41 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 415692b..988b3d7 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -6,12 +6,11 @@ module Rules.Generate ( import qualified System.Directory as IO import Base -import Context +import Context hiding (package) import Expression import GHC import Oracles.ModuleFiles -import Predicate ( (?) ) -import qualified Predicate as Predicate +import Predicate import Rules.Actions import Rules.Generators.ConfigHs import Rules.Generators.GhcAutoconfH @@ -43,16 +42,16 @@ platformH stage = buildPath (vanillaContext stage compiler) -/- "ghc_boot_platfo -- TODO: move generated files to buildRootPath, see #113 includesDependencies :: [FilePath] -includesDependencies = ("includes" -/-) <$> +includesDependencies = fmap ("includes" -/-) [ "ghcautoconf.h" , "ghcplatform.h" , "ghcversion.h" ] ghcPrimDependencies :: Expr [FilePath] -ghcPrimDependencies = getStage >>= \stage -> - let prependPath x = buildPath (vanillaContext stage ghcPrim) -/- x - in return $ - fmap prependPath [ "autogen/GHC/Prim.hs" , "GHC/PrimopWrappers.hs" ] +ghcPrimDependencies = do + stage <- getStage + let path = buildPath $ vanillaContext stage ghcPrim + return [path -/- "autogen/GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"] derivedConstantsPath :: FilePath derivedConstantsPath = "includes/dist-derivedconstants/header" @@ -65,42 +64,38 @@ derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-) , "GHCConstantsHaskellWrappers.hs" ] compilerDependencies :: Expr [FilePath] -compilerDependencies = getStage >>= \stage -> - let prependBuildPath x = buildPath (vanillaContext stage compiler) -/- x - in mconcat $ - [ return $ (platformH stage) - : includesDependencies - ++ derivedConstantsDependencies - , Predicate.notStage0 ? return (gmpLibraryH : libffiDependencies) - , return $ fmap prependBuildPath - [ "primop-can-fail.hs-incl" - , "primop-code-size.hs-incl" - , "primop-commutable.hs-incl" - , "primop-data-decl.hs-incl" - , "primop-fixity.hs-incl" - , "primop-has-side-effects.hs-incl" - , "primop-list.hs-incl" - , "primop-out-of-line.hs-incl" - , "primop-primop-info.hs-incl" - , "primop-strictness.hs-incl" - , "primop-tag.hs-incl" - , "primop-vector-tycons.hs-incl" - , "primop-vector-tys-exports.hs-incl" - , "primop-vector-tys.hs-incl" - , "primop-vector-uniques.hs-incl" - ] - ] +compilerDependencies = do + stage <- getStage + let path = buildPath $ vanillaContext stage compiler + mconcat [ return [platformH stage] + , return includesDependencies + , return derivedConstantsDependencies + , notStage0 ? return (gmpLibraryH : libffiDependencies) + , return $ fmap (path -/-) + [ "primop-can-fail.hs-incl" + , "primop-code-size.hs-incl" + , "primop-commutable.hs-incl" + , "primop-data-decl.hs-incl" + , "primop-fixity.hs-incl" + , "primop-has-side-effects.hs-incl" + , "primop-list.hs-incl" + , "primop-out-of-line.hs-incl" + , "primop-primop-info.hs-incl" + , "primop-strictness.hs-incl" + , "primop-tag.hs-incl" + , "primop-vector-tycons.hs-incl" + , "primop-vector-tys-exports.hs-incl" + , "primop-vector-tys.hs-incl" + , "primop-vector-uniques.hs-incl" ] ] generatedDependencies :: Expr [FilePath] generatedDependencies = mconcat - [ Predicate.package compiler ? compilerDependencies - , Predicate.package ghcPrim ? ghcPrimDependencies - , Predicate.package rts ? return ( - libffiDependencies - ++ includesDependencies - ++ derivedConstantsDependencies) - , Predicate.stage0 ? return includesDependencies - ] + [ package compiler ? compilerDependencies + , package ghcPrim ? ghcPrimDependencies + , package rts ? return (libffiDependencies + ++ includesDependencies + ++ derivedConstantsDependencies) + , stage0 ? return includesDependencies ] generate :: FilePath -> Context -> Expr String -> Action () generate file context expr = do From git at git.haskell.org Fri Oct 27 01:07:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Require Cabal 1.25 (f1f95d5) Message-ID: <20171027010738.37CC03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f1f95d5e016b85411487f62d0b9603692bfcd923/ghc >--------------------------------------------------------------- commit f1f95d5e016b85411487f62d0b9603692bfcd923 Author: Andrey Mokhov Date: Fri Aug 5 17:19:36 2016 +0100 Require Cabal 1.25 See #280. >--------------------------------------------------------------- f1f95d5e016b85411487f62d0b9603692bfcd923 hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 63bd164..41cccd8 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -120,7 +120,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.22.* || == 1.24.* || == 1.25.* + , Cabal == 1.25.* , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 01:07:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make dependencies easier to copy (9467c06) Message-ID: <20171027010741.DE8E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9467c0611db45c494aba051e2a5e8bd2f3cc86c1/ghc >--------------------------------------------------------------- commit 9467c0611db45c494aba051e2a5e8bd2f3cc86c1 Author: Andrey Mokhov Date: Fri Aug 5 18:53:09 2016 +0100 Make dependencies easier to copy [skip ci] >--------------------------------------------------------------- 9467c0611db45c494aba051e2a5e8bd2f3cc86c1 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 4ce3b3a..be42f82 100644 --- a/README.md +++ b/README.md @@ -23,7 +23,7 @@ follow these steps: * If you have never built GHC before, start with the [preparation guide][ghc-preparation]. * This build system is written in Haskell (obviously) and depends on the following Haskell -packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. +packages, which need to be installed: `ansi-terminal mtl shake QuickCheck`. * Get the sources. It is important for the build system to be in the `hadrian` directory of the GHC source tree: From git at git.haskell.org Fri Oct 27 01:07:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't capitalise 'quickcheck' (9b474d3) Message-ID: <20171027010745.6C01E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b474d34ffa182b021956944d669aee0528291ad/ghc >--------------------------------------------------------------- commit 9b474d34ffa182b021956944d669aee0528291ad Author: Andrey Mokhov Date: Fri Aug 5 18:56:33 2016 +0100 Don't capitalise 'quickcheck' [skip ci] >--------------------------------------------------------------- 9b474d34ffa182b021956944d669aee0528291ad README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index be42f82..c39071e 100644 --- a/README.md +++ b/README.md @@ -23,7 +23,7 @@ follow these steps: * If you have never built GHC before, start with the [preparation guide][ghc-preparation]. * This build system is written in Haskell (obviously) and depends on the following Haskell -packages, which need to be installed: `ansi-terminal mtl shake QuickCheck`. +packages, which need to be installed: `ansi-terminal mtl shake quickcheck`. * Get the sources. It is important for the build system to be in the `hadrian` directory of the GHC source tree: From git at git.haskell.org Fri Oct 27 01:07:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't run cabal on Hadrian (ae1fa1a) Message-ID: <20171027010748.F384D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae1fa1ac3c153c6110174ada2641607e17bd534c/ghc >--------------------------------------------------------------- commit ae1fa1ac3c153c6110174ada2641607e17bd534c Author: Andrey Mokhov Date: Fri Aug 5 18:58:08 2016 +0100 Don't run cabal on Hadrian >--------------------------------------------------------------- ae1fa1ac3c153c6110174ada2641607e17bd534c .travis.yml | 8 ++------ 1 file changed, 2 insertions(+), 6 deletions(-) diff --git a/.travis.yml b/.travis.yml index dd74f25..33c1738 100644 --- a/.travis.yml +++ b/.travis.yml @@ -17,7 +17,7 @@ matrix: - PATH="$HOME/.cabal/bin:$PATH" - export PATH - cabal update - - cabal install alex happy + - cabal install alex happy ansi-terminal mtl shake quickcheck - os: osx env: FLAVOUR=quickest TARGET= @@ -25,7 +25,7 @@ matrix: - brew update - brew install ghc cabal-install - cabal update - - cabal install alex happy + - cabal install alex happy ansi-terminal mtl shake quickcheck - PATH="$HOME/.cabal/bin:$PATH" - export PATH @@ -51,13 +51,9 @@ install: - mv .git ghc/hadrian - ( cd ghc/hadrian && git reset --hard HEAD ) - - ( cd ghc/hadrian && cabal install --only-dependencies ) - - ( cd ghc/hadrian && cabal configure ) - - ghc-pkg list script: - - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=$FLAVOUR $TARGET - ./ghc/inplace/bin/ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 01:07:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to Cabal library API changes (a931066) Message-ID: <20171027010752.941303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a931066df88efc745bdd310b3c64aa25834ba243/ghc >--------------------------------------------------------------- commit a931066df88efc745bdd310b3c64aa25834ba243 Author: Andrey Mokhov Date: Thu Aug 11 00:41:02 2016 +0100 Adapt to Cabal library API changes Fix #282. >--------------------------------------------------------------- a931066df88efc745bdd310b3c64aa25834ba243 src/Rules/Cabal.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index e2cdb0f..ed72f93 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -35,8 +35,7 @@ cabalRules = do else do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg - -- TODO: Support more than one Cabal library per package. - let depsLib = collectDeps . fmap snd . listToMaybe $ condLibraries pd + let depsLib = collectDeps $ condLibrary pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes depNames = [ name | Dependency (DP.PackageName name) _ <- deps ] From git at git.haskell.org Fri Oct 27 01:07:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #279 from michalt/gcc-mm-mg/1 (197ca35) Message-ID: <20171027010759.8FA603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/197ca35ae05c95d3cf710c453630bd2ce399542a/ghc >--------------------------------------------------------------- commit 197ca35ae05c95d3cf710c453630bd2ce399542a Merge: a931066 c2d7e2a Author: Andrey Mokhov Date: Wed Aug 17 19:36:55 2016 +0100 Merge pull request #279 from michalt/gcc-mm-mg/1 Use GCC's `-MM`/`-MG` to find missing dependencies >--------------------------------------------------------------- 197ca35ae05c95d3cf710c453630bd2ce399542a src/Builder.hs | 3 ++- src/Rules/Compile.hs | 40 ++++++++++++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 17 ++++++++++++++++- src/Settings/Builders/Cc.hs | 13 ++++++++++++- 4 files changed, 70 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 01:07:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:07:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Initial version of FindMissingInclude (c2d7e2a) Message-ID: <20171027010756.17E9A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c2d7e2aa683c89d9b1464734ea9ae68ff735655c/ghc >--------------------------------------------------------------- commit c2d7e2aa683c89d9b1464734ea9ae68ff735655c Author: Michal Terepeta Date: Sat Jul 23 16:50:31 2016 +0200 Initial version of FindMissingInclude This allows finding missing includes for `.c` files (this is important for all the cases where we generate the includes during the build process). We're using GCC's `-MM` `-MG` options and iterate as long as we get new includes. Since this would return all includes verbatim from the `#include`, we check which ones are actually generated and what are their final paths. Note: this is currently applied only to `.c` files and does not (yet?) work for `.hs` files (there are issues with things like ifdefs for package versions that cause GCC to error out). Signed-off-by: Michal Terepeta >--------------------------------------------------------------- c2d7e2aa683c89d9b1464734ea9ae68ff735655c src/Builder.hs | 3 ++- src/Rules/Compile.hs | 40 ++++++++++++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 17 ++++++++++++++++- src/Settings/Builders/Cc.hs | 13 ++++++++++++- 4 files changed, 70 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 17198e7..1974eff 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -21,7 +21,8 @@ import Stage -- 3) Linking object files & static libraries into an executable. -- We have CcMode for CC and GhcMode for GHC. -data CcMode = CompileC | FindCDependencies +-- TODO: Consider merging FindCDependencies and FindMissingInclude +data CcMode = CompileC | FindCDependencies | FindMissingInclude deriving (Eq, Generic, Show) data GhcMode = CompileHs | FindHsDependencies | LinkHs diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index fd6cd32..001068a 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -5,9 +5,16 @@ import Context import Expression import Oracles.Dependencies import Rules.Actions +import Rules.Generate import Settings.Paths import Target +import Development.Shake.Util + +import Data.Maybe +import Data.List +import qualified Data.Set as Set + compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context @@ -22,6 +29,9 @@ compilePackage rs context at Context {..} = do if ("//*.c" ?== src) then do need $ src : deps + -- TODO: Improve parallelism by collecting all dependencies and + -- need'ing them all at once + mapM_ (needGenerated context) . filter ("//*.c" ?==) $ src : deps build $ Target context (Cc CompileC stage) [src] [obj] else do need $ src : deps @@ -39,3 +49,33 @@ needCompileDependencies :: Context -> Action () needCompileDependencies context at Context {..} = do when (isLibrary package) $ need =<< return <$> pkgConfFile context needContext =<< contextDependencies context + +needGenerated :: Context -> FilePath -> Action () +needGenerated context origFile = go Set.empty + where + go :: Set.Set String -> Action () + go done = withTempFile $ \outFile -> do + let builder = Cc FindMissingInclude $ stage context + target = Target context builder [origFile] [outFile] + build target + deps <- parseFile outFile + + -- Get the full path if the include refers to a generated file and call + -- `need` on it. + needed <- liftM catMaybes $ + interpretInContext context (mapM getPathIfGenerated deps) + need needed + + let newdone = Set.fromList needed `Set.union` done + -- If we added a new file to the set of needed files, let's try one more + -- time, since the new file might include a genreated header of itself + -- (which we'll `need`). + when (Set.size newdone > Set.size done) (go newdone) + + parseFile :: FilePath -> Action [String] + parseFile file = do + input <- liftIO $ readFile file + case parseMakefile input of + [(_file, deps)] -> return deps + _ -> return [] + diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 988b3d7..34874db 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,7 @@ module Rules.Generate ( generatePackageCode, generateRules, installTargets, copyRules, - includesDependencies, derivedConstantsPath, generatedDependencies + includesDependencies, derivedConstantsPath, generatedDependencies, + getPathIfGenerated ) where import qualified System.Directory as IO @@ -196,3 +197,17 @@ generateRules = do emptyTarget :: Context emptyTarget = vanillaContext (error "Rules.Generate.emptyTarget: unknown stage") (error "Rules.Generate.emptyTarget: unknown package") + +getPathIfGenerated :: FilePath -> Expr (Maybe FilePath) +getPathIfGenerated include = do + generated <- generatedFiles + -- For includes of generated files, we cannot get the full path of the file + -- (since it might be included due to some include dir, i.e., through `-I`). + -- So here we try both the name and the path. + let nameOrPath (name, path) = include == name || include == path + return . fmap snd $ find nameOrPath generated + +generatedFiles :: Expr [(FilePath, FilePath)] +generatedFiles = do + deps <- generatedDependencies + return [ (takeFileName fp, fp) | fp <- deps ] diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index 354d2b4..36a172e 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -26,7 +26,18 @@ ccBuilderArgs = mconcat , arg $ dropExtension output -<.> "o" , arg "-x" , arg "c" - , arg =<< getInput ] ] + , arg =<< getInput ] + + , builder (Cc FindMissingInclude) ? do + mconcat [ arg "-E" + , arg "-MM" + , arg "-MG" + , commonCcArgs + , arg "-MF" + , arg =<< getOutput + , arg =<< getInput + ] + ] commonCcArgs :: Args commonCcArgs = mconcat [ append =<< getPkgDataList CcArgs From git at git.haskell.org Fri Oct 27 01:08:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use --flavour=quickest (0cfd96d) Message-ID: <20171027010803.1EB323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0cfd96d4dd23ca565f9922357c64c769b78863c1/ghc >--------------------------------------------------------------- commit 0cfd96d4dd23ca565f9922357c64c769b78863c1 Author: Andrey Mokhov Date: Sat Aug 20 17:28:48 2016 +0100 Use --flavour=quickest >--------------------------------------------------------------- 0cfd96d4dd23ca565f9922357c64c769b78863c1 doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index 4674ff4..a70f85a 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -11,9 +11,9 @@ The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_ cd ghc stack exec -- git clone git://github.com/snowleopard/hadrian stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quick + stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quickest -The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quick` flag from the last command line (this will slow down the build to about an hour). +The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quickest` flag from the last command line (this will slow down the build to about an hour). #### Future ideas From git at git.haskell.org Fri Oct 27 01:08:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant imports (082f17b) Message-ID: <20171027010810.09A053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/082f17b3c86e559d45e117226094e85923883013/ghc >--------------------------------------------------------------- commit 082f17b3c86e559d45e117226094e85923883013 Author: Andrey Mokhov Date: Sat Aug 20 18:17:37 2016 +0100 Drop redundant imports >--------------------------------------------------------------- 082f17b3c86e559d45e117226094e85923883013 src/Rules/Compile.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 001068a..8f8d92a 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -11,8 +11,6 @@ import Target import Development.Shake.Util -import Data.Maybe -import Data.List import qualified Data.Set as Set compilePackage :: [(Resource, Int)] -> Context -> Rules () From git at git.haskell.org Fri Oct 27 01:08:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a Stack build script for Windows (bbd884c) Message-ID: <20171027010806.8D6E83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbd884c841d8508abb3dabbbb5cf5abe2e69f4da/ghc >--------------------------------------------------------------- commit bbd884c841d8508abb3dabbbb5cf5abe2e69f4da Author: Andrey Mokhov Date: Sat Aug 20 18:02:33 2016 +0100 Add a Stack build script for Windows See #283 >--------------------------------------------------------------- bbd884c841d8508abb3dabbbb5cf5abe2e69f4da build.stack.bat | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/build.stack.bat b/build.stack.bat new file mode 100644 index 0000000..3586290 --- /dev/null +++ b/build.stack.bat @@ -0,0 +1,8 @@ + at rem Change the current directory to the one containing this script + at cd %~dp0 + + at rem Build Hadrian and dependencies + at stack build + + at rem Run Hadrian in GHC top directory forwarding additional user arguments + at stack exec hadrian -- --lint --directory ".." %* From git at git.haskell.org Fri Oct 27 01:08:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix comments (676ec2e) Message-ID: <20171027010813.793123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/676ec2eabce5fd13ad9deb172d5041d461be01e7/ghc >--------------------------------------------------------------- commit 676ec2eabce5fd13ad9deb172d5041d461be01e7 Author: Andrey Mokhov Date: Sat Aug 20 19:57:26 2016 +0100 Fix comments [skip ci] >--------------------------------------------------------------- 676ec2eabce5fd13ad9deb172d5041d461be01e7 .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 6fbc3b2..87bedb8 100644 --- a/.gitignore +++ b/.gitignore @@ -13,7 +13,7 @@ cabal.sandbox.config # build.cabal-new.sh specific /dist-newstyle/ -# build.stack.sh specific +# build.stack.sh and build.stack.bat specific /.stack-work/ # the user settings From git at git.haskell.org Fri Oct 27 01:08:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bump stack to lts-6.12 and remove extra pkg from extra-deps (e789d21) Message-ID: <20171027010816.E63763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e789d211296f7abc031af5e1ab19d2633f7de745/ghc >--------------------------------------------------------------- commit e789d211296f7abc031af5e1ab19d2633f7de745 Author: Michal Terepeta Date: Sun Aug 21 13:46:48 2016 +0200 Bump stack to lts-6.12 and remove extra pkg from extra-deps Signed-off-by: Michal Terepeta >--------------------------------------------------------------- e789d211296f7abc031af5e1ab19d2633f7de745 stack.yaml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/stack.yaml b/stack.yaml index 9eb4cfb..5fa9f94 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,7 +1,7 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-5.17 +resolver: lts-6.12 # Local packages, usually specified by relative directory name packages: @@ -10,7 +10,6 @@ packages: # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: -- extra-1.4.7 # Override default flag values for local packages and extra-deps flags: {} From git at git.haskell.org Fri Oct 27 01:08:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #284 from michalt/stack/lts612extra (c7f8ae2) Message-ID: <20171027010820.6E85A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c7f8ae2442955879660752c880405c0c3780f7f4/ghc >--------------------------------------------------------------- commit c7f8ae2442955879660752c880405c0c3780f7f4 Merge: 676ec2e e789d21 Author: Andrey Mokhov Date: Sun Aug 21 17:03:02 2016 +0100 Merge pull request #284 from michalt/stack/lts612extra Bump stack to lts-6.12 and remove extra pkg from extra-deps >--------------------------------------------------------------- c7f8ae2442955879660752c880405c0c3780f7f4 stack.yaml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 01:08:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build-tools Alex and Happy. (4e58441) Message-ID: <20171027010823.EBECF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e584418c121e02029e6dfdd52bbd397e8bb034b/ghc >--------------------------------------------------------------- commit 4e584418c121e02029e6dfdd52bbd397e8bb034b Author: Andrey Mokhov Date: Thu Sep 1 15:42:33 2016 +0100 Add build-tools Alex and Happy. >--------------------------------------------------------------- 4e584418c121e02029e6dfdd52bbd397e8bb034b hadrian.cabal | 2 ++ 1 file changed, 2 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 41cccd8..3e34b16 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -129,6 +129,8 @@ executable hadrian , shake >= 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* + build-tools: alex >= 3.1 + , happy >= 1.19.4 ghc-options: -Wall -fno-warn-name-shadowing -rtsopts -with-rtsopts=-I0 From git at git.haskell.org Fri Oct 27 01:08:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Stack to download bootstrapping GHC and install MSYS2. (f644b3f) Message-ID: <20171027010827.6530F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f644b3fc638631388a343c533f9eb5c49957ffe0/ghc >--------------------------------------------------------------- commit f644b3fc638631388a343c533f9eb5c49957ffe0 Author: Andrey Mokhov Date: Thu Sep 1 17:43:53 2016 +0100 Use Stack to download bootstrapping GHC and install MSYS2. >--------------------------------------------------------------- f644b3fc638631388a343c533f9eb5c49957ffe0 appveyor.yml | 51 +++++++++++++++++++++++---------------------------- 1 file changed, 23 insertions(+), 28 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 30e3bcf..ffca700 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -1,41 +1,36 @@ -clone_folder: "C:\\msys64\\home\\ghc\\hadrian" +clone_folder: "c:\\ghc\\hadrian" environment: global: STACK_ROOT: "c:\\sr" cache: - - "c:\\sr" + - "c:\\sr -> appveyor.yml" install: - - cd - - set MSYSTEM=MINGW64 - - set PATH=C:\msys64\mingw64\bin;C:\msys64\usr\bin;C:\msys64;%PATH% - - set PATH=%PATH%;C:\Users\appveyor\AppData\Roaming\local\bin\;%APPVEYOR_BUILD_FOLDER% + # Get Stack - curl -ostack.zip -LsS --insecure https://www.stackage.org/stack/windows-x86_64 - 7z x stack.zip stack.exe - - bash -lc "curl -LsS http://www.haskell.org/ghc/dist/7.10.3/ghc-7.10.3-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - - stack exec -- pacman -S --noconfirm gcc binutils p7zip git - - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ - - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ - - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - - git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 C:\msys64\home\ghc\tmp + # Fetch GHC sources into c:\ghc + # Note: Appveyor has already cloned Hadrian into c:\ghc\hadrian, so it's tricky + - cd .. + - git init + - git remote add origin git://git.haskell.org/ghc.git + - git pull --recurse-submodules origin master + - git submodule update --init --recursive - - bash -lc "mv /home/ghc/tmp/* /home/ghc" - - echo "" | stack --no-terminal install alex happy shake ansi-terminal mtl - - ghc --version - - stack --version - - alex --version - - happy --version - - stack exec -- ghc-pkg list - - cd C:\msys64\home\ghc - - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/mingw-w64/x86_64/" - - bash -lc "cd /home/ghc; mkdir -p ghc-tarballs/perl/" + # Install all Hadrian and GHC build dependencies + - cd hadrian + - stack setup + - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: - - cd C:\msys64\home\ghc\hadrian - - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest - - C:\msys64\home\ghc\inplace\bin\ghc-stage2.exe -e 1+2 + # Build Hadrian + - stack build + # Run internal Hadrian tests + - stack exec hadrian -- selftest + # Build GHC + - echo "" | stack --no-terminal exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + # Test GHC binary + - cd .. + - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 01:08:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Exit the build script if Hadrian cannot be built (f937d80) Message-ID: <20171027010830.D38DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f937d806ea8397132405eeede17f2662d8b0c85f/ghc >--------------------------------------------------------------- commit f937d806ea8397132405eeede17f2662d8b0c85f Author: Andrey Mokhov Date: Thu Sep 1 17:58:44 2016 +0100 Exit the build script if Hadrian cannot be built >--------------------------------------------------------------- f937d806ea8397132405eeede17f2662d8b0c85f build.stack.bat | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/build.stack.bat b/build.stack.bat index 3586290..919854e 100644 --- a/build.stack.bat +++ b/build.stack.bat @@ -1,8 +1,9 @@ @rem Change the current directory to the one containing this script @cd %~dp0 - at rem Build Hadrian and dependencies + at rem Build Hadrian and dependencies and exit the script if the build failed @stack build + at if %errorlevel% neq 0 exit /B %errorlevel% @rem Run Hadrian in GHC top directory forwarding additional user arguments @stack exec hadrian -- --lint --directory ".." %* From git at git.haskell.org Fri Oct 27 01:08:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Try to drop the 'echo' hack. (fe19fc3) Message-ID: <20171027010834.4729A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fe19fc382f56b37e7936a0c086e1bddd87c0e168/ghc >--------------------------------------------------------------- commit fe19fc382f56b37e7936a0c086e1bddd87c0e168 Author: Andrey Mokhov Date: Thu Sep 1 19:10:40 2016 +0100 Try to drop the 'echo' hack. >--------------------------------------------------------------- fe19fc382f56b37e7936a0c086e1bddd87c0e168 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index ffca700..07619c8 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -30,7 +30,7 @@ build_script: # Run internal Hadrian tests - stack exec hadrian -- selftest # Build GHC - - echo "" | stack --no-terminal exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + - stack exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest # Test GHC binary - cd .. - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 01:08:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run stack setup in silent mode (4b682d2) Message-ID: <20171027010837.AC88C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b682d2db950154907885acc006a46ea47d9c019/ghc >--------------------------------------------------------------- commit 4b682d2db950154907885acc006a46ea47d9c019 Author: Andrey Mokhov Date: Thu Sep 1 19:59:57 2016 +0100 Run stack setup in silent mode >--------------------------------------------------------------- 4b682d2db950154907885acc006a46ea47d9c019 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 07619c8..ab3ed8c 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -21,7 +21,7 @@ install: # Install all Hadrian and GHC build dependencies - cd hadrian - - stack setup + - stack setup --silent - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: From git at git.haskell.org Fri Oct 27 01:08:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reduce verbosity (80e986b) Message-ID: <20171027010841.2FFEE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/80e986ba99c5764f78f6c4b54abc0c24953d836c/ghc >--------------------------------------------------------------- commit 80e986ba99c5764f78f6c4b54abc0c24953d836c Author: Andrey Mokhov Date: Thu Sep 1 20:14:01 2016 +0100 Reduce verbosity >--------------------------------------------------------------- 80e986ba99c5764f78f6c4b54abc0c24953d836c appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index ab3ed8c..def4dd9 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -17,11 +17,11 @@ install: - git init - git remote add origin git://git.haskell.org/ghc.git - git pull --recurse-submodules origin master - - git submodule update --init --recursive + - git submodule update --init --recursive --quiet # Install all Hadrian and GHC build dependencies - cd hadrian - - stack setup --silent + - stack setup > nul - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: From git at git.haskell.org Fri Oct 27 01:08:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Final tweaks (7987366) Message-ID: <20171027010844.AB99A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79873665328d089b35b8a75141afe75b0d84dcbf/ghc >--------------------------------------------------------------- commit 79873665328d089b35b8a75141afe75b0d84dcbf Author: Andrey Mokhov Date: Thu Sep 1 21:02:05 2016 +0100 Final tweaks >--------------------------------------------------------------- 79873665328d089b35b8a75141afe75b0d84dcbf appveyor.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index def4dd9..5d13d29 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -12,7 +12,7 @@ install: - 7z x stack.zip stack.exe # Fetch GHC sources into c:\ghc - # Note: Appveyor has already cloned Hadrian into c:\ghc\hadrian, so it's tricky + # Note: AppVeyor has already cloned Hadrian into c:\ghc\hadrian, so it's tricky - cd .. - git init - git remote add origin git://git.haskell.org/ghc.git @@ -30,7 +30,7 @@ build_script: # Run internal Hadrian tests - stack exec hadrian -- selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quickest + - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- # Test GHC binary - cd .. - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 01:08:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Whitespace (5905138) Message-ID: <20171027010848.27F063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/59051380365b8ef66d7c95cb63a038a89b482326/ghc >--------------------------------------------------------------- commit 59051380365b8ef66d7c95cb63a038a89b482326 Author: Andrey Mokhov Date: Thu Sep 1 21:29:15 2016 +0100 Whitespace >--------------------------------------------------------------- 59051380365b8ef66d7c95cb63a038a89b482326 appveyor.yml | 3 +++ 1 file changed, 3 insertions(+) diff --git a/appveyor.yml b/appveyor.yml index 5d13d29..7552a56 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -27,10 +27,13 @@ install: build_script: # Build Hadrian - stack build + # Run internal Hadrian tests - stack exec hadrian -- selftest + # Build GHC - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- + # Test GHC binary - cd .. - inplace\bin\ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 01:08:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor and simplify (3218044) Message-ID: <20171027010851.E57D93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/321804478393dbf33c80eaa8ad53e0f859d94171/ghc >--------------------------------------------------------------- commit 321804478393dbf33c80eaa8ad53e0f859d94171 Author: Andrey Mokhov Date: Thu Sep 1 21:29:34 2016 +0100 Refactor and simplify >--------------------------------------------------------------- 321804478393dbf33c80eaa8ad53e0f859d94171 .travis.yml | 69 ++++++++++++++++++++++--------------------------------------- 1 file changed, 25 insertions(+), 44 deletions(-) diff --git a/.travis.yml b/.travis.yml index 33c1738..5b26bbd 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,7 +3,6 @@ sudo: true matrix: include: - os: linux - env: CABALVER=1.22 GHCVER=7.10.3 FLAVOUR=quickest TARGET= addons: apt: packages: @@ -12,65 +11,47 @@ matrix: - zlib1g-dev sources: hvr-ghc before_install: - - PATH="/opt/ghc/$GHCVER/bin:$PATH" - - PATH="/opt/cabal/$CABALVER/bin:$PATH" - - PATH="$HOME/.cabal/bin:$PATH" - - export PATH - - cabal update - - cabal install alex happy ansi-terminal mtl shake quickcheck + - PATH="/opt/ghc/7.10.3/bin:$PATH" + - PATH="/opt/cabal/1.22/bin:$PATH" - os: osx - env: FLAVOUR=quickest TARGET= before_install: - brew update - brew install ghc cabal-install - - cabal update - - cabal install alex happy ansi-terminal mtl shake quickcheck - - PATH="$HOME/.cabal/bin:$PATH" - - export PATH install: + # Add Cabal to PATH + - PATH="$HOME/.cabal/bin:$PATH" + - export PATH - env - - ghc --version - - cabal --version - - alex --version - - happy --version - - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ - - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ - - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - - travis_retry git clone https://github.com/ghc/ghc --recurse-submodules --depth 1 + # Install all Hadrian and GHC build dependencies + - cabal update + - cabal install alex happy ansi-terminal mtl shake quickcheck - # Travis clones the project into ".", but we need it as a child directory - # of "ghc/". For this reason, we - rather hackily - move the GHC-Shake - # ".git" directory into the appropriate location, and perform a hard reset - # in order to regenerate the GHC-Shake files. + # Fetch GHC sources into ./ghc + - git clone --recursive git://git.haskell.org/ghc.git --quiet + + # Travis has already cloned Hadrian into ./ and we need to move it + # to ./ghc/hadrian -- one way to do it is to move the .git directory + # and perform a hard reset in order to regenerate Hadrian files - mkdir ghc/hadrian - mv .git ghc/hadrian - - ( cd ghc/hadrian && git reset --hard HEAD ) - - - ghc-pkg list + - cd ghc/hadrian + - git reset --hard HEAD script: - - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=$FLAVOUR $TARGET - - ./ghc/inplace/bin/ghc-stage2 -e 1+2 + # Run internal Hadrian tests + - ./build.sh selftest + + # Build GHC + - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + + # Test GHC binary + - cd .. + - ghc/inplace/bin/ghc-stage2 -e 1+2 cache: directories: - $HOME/.cabal - $HOME/.ghc - -notifications: - irc: - on_success: change # always/never/change - on_failure: always - channels: - - "chat.freenode.net#shaking-up-ghc" - template: - - "#%{build_number} finished in %{duration}. %{message}" - - "Repo: %{repository_slug}, branch: %{branch}" - - "%{author}: %{commit_subject}" - - "Build details: %{build_url}" From git at git.haskell.org Fri Oct 27 01:08:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to GHC binary (cc72f0c) Message-ID: <20171027010855.4FBB03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cc72f0caf4547d27774cf6ed551c41ced9f9c9f3/ghc >--------------------------------------------------------------- commit cc72f0caf4547d27774cf6ed551c41ced9f9c9f3 Author: Andrey Mokhov Date: Thu Sep 1 22:15:17 2016 +0100 Fix path to GHC binary >--------------------------------------------------------------- cc72f0caf4547d27774cf6ed551c41ced9f9c9f3 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 5b26bbd..0209cab 100644 --- a/.travis.yml +++ b/.travis.yml @@ -49,7 +49,7 @@ script: # Test GHC binary - cd .. - - ghc/inplace/bin/ghc-stage2 -e 1+2 + - inplace/bin/ghc-stage2 -e 1+2 cache: directories: From git at git.haskell.org Fri Oct 27 01:08:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:08:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify instructions, add CI badge (1fa2cb1) Message-ID: <20171027010858.E570C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fa2cb1b470674a5b478a4e4d5e8b931a45b36d6/ghc >--------------------------------------------------------------- commit 1fa2cb1b470674a5b478a4e4d5e8b931a45b36d6 Author: Andrey Mokhov Date: Thu Sep 1 23:20:05 2016 +0100 Simplify instructions, add CI badge [skip ci] >--------------------------------------------------------------- 1fa2cb1b470674a5b478a4e4d5e8b931a45b36d6 doc/windows.md | 69 ++++++++++++++++++++++++++++++++++++++++++++-------------- 1 file changed, 53 insertions(+), 16 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index a70f85a..efbaeb2 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -1,23 +1,60 @@ -# Building on Windows +# Building GHC on Windows -Here are a list of instructions to build GHC, from source, on Windows. I tested these instructions on a clean machine using the [free Windows 10 VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/) (I bumped the VM CPUs to 4, and RAM to 4096Mb). These instructions are not currently the official GHC building instructions, but might be simpler and more robust than those. +[![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) -The first step is to [install Stack](https://www.stackage.org/stack/windows-x86_64-installer) (I just accepted all the defaults), then open a command prompt and run: +Here is how you can build GHC, from source, on Windows. We assume that you +already have `git` and `stack` installed. - stack setup - stack install happy alex - stack exec -- pacman -S gcc binutils git automake-wrapper tar make patch autoconf --noconfirm - stack exec -- git clone --recursive git://git.haskell.org/ghc.git - cd ghc - stack exec -- git clone git://github.com/snowleopard/hadrian - stack build --stack-yaml=hadrian/stack.yaml --only-dependencies - stack exec --stack-yaml=hadrian/stack.yaml -- hadrian/build.bat -j --flavour=quickest +```sh +# Get GHC and Hadrian sources +git clone --recursive git://git.haskell.org/ghc.git +cd ghc +git clone git://github.com/snowleopard/hadrian +cd hadrian -The entire process should take about 20 minutes. Note, this will build GHC without optimisations. If you need an optimised GHC, drop the `--flavour=quickest` flag from the last command line (this will slow down the build to about an hour). +# Download and install the bootstrapping GHC and MSYS2 +stack setup -#### Future ideas +# Install utilities required during the GHC build process +stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm -Here are some alternatives that have been considered, but not yet tested. Use the instructions above. +# Build Hadrian and dependencies (including GHC dependencies Alex and Happy) +stack build + +# Build GHC +stack exec hadrian -- --directory ".." -j --flavour=quickest + +# Test GHC +cd .. +inplace\bin\ghc-stage2 -e 1+2 +``` + +The entire process should take about 20 minutes. Note, this will build GHC without +optimisations. If you need an optimised GHC, drop the `--flavour=quickest` flag from +the build command line (this will slow down the build to about an hour). + +These are currently not the +[official GHC building instructions](https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows), +but are much simpler and may also be more robust. + +The `stack build` and `stack exec hadrian` commands can be replaced by an invocation +of Hadrian's Stack-based build script: `build.stack.bat -j --flavour=quickest`. Use this +script if you plan to work on Hadrian and/or rebuild GHC often. + +## Prerequisites + +The above works on a clean machine with `git` and `stack` installed (tested with default +installation settings), which you can get from https://git-scm.com/download/win and +https://www.stackage.org/stack/windows-x86_64-installer. + +## Testing + +These instructions have been tested on a clean Windows 10 machine using the +[free VirtualBox image](https://dev.windows.com/en-us/microsoft-edge/tools/vms/windows/), +and are also routinely tested on +[Hadrian's AppVeyor CI instance](https://ci.appveyor.com/project/snowleopard/hadrian/history). + +## Notes + +Beware of the [current limitations of Hadrian](https://github.com/snowleopard/hadrian#current-limitations). -* The `pacman` install of `gcc` is probably not necessary, but it does pull in a lot of tools, some of which probably are necessary. Ideally thin the list down. -* Happy/Alex should be able to be installed by adding them as `build-tools` in the Cabal file. From git at git.haskell.org Fri Oct 27 01:09:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to prerequisites (633fad1) Message-ID: <20171027010902.6EDAB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/633fad17054268f6c02e360bed5ab4df5e2559ba/ghc >--------------------------------------------------------------- commit 633fad17054268f6c02e360bed5ab4df5e2559ba Author: Andrey Mokhov Date: Thu Sep 1 23:24:34 2016 +0100 Link to prerequisites [skip ci] >--------------------------------------------------------------- 633fad17054268f6c02e360bed5ab4df5e2559ba doc/windows.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index efbaeb2..1296b76 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -2,8 +2,8 @@ [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) -Here is how you can build GHC, from source, on Windows. We assume that you -already have `git` and `stack` installed. +Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are +installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). ```sh # Get GHC and Hadrian sources From git at git.haskell.org Fri Oct 27 01:09:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Tweak instructions (fd7dd6f) Message-ID: <20171027010905.E37003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd7dd6f7f32eebb7ff1a00ee2b36a0a75fb51e14/ghc >--------------------------------------------------------------- commit fd7dd6f7f32eebb7ff1a00ee2b36a0a75fb51e14 Author: Andrey Mokhov Date: Thu Sep 1 23:27:33 2016 +0100 Tweak instructions [skip ci] >--------------------------------------------------------------- fd7dd6f7f32eebb7ff1a00ee2b36a0a75fb51e14 doc/windows.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/windows.md b/doc/windows.md index 1296b76..73804df 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -10,9 +10,9 @@ installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/maste git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/hadrian -cd hadrian # Download and install the bootstrapping GHC and MSYS2 +cd hadrian stack setup # Install utilities required during the GHC build process From git at git.haskell.org Fri Oct 27 01:09:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Lowercase flavour names in --help (73c72a6) Message-ID: <20171027010909.628C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73c72a633398eb0f021fdd4081e2e559a10105f5/ghc >--------------------------------------------------------------- commit 73c72a633398eb0f021fdd4081e2e559a10105f5 Author: Moritz Kiefer Date: Sat Sep 3 12:51:23 2016 +0200 Lowercase flavour names in --help >--------------------------------------------------------------- 73c72a633398eb0f021fdd4081e2e559a10105f5 src/CmdLineFlag.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index cc0eb7f..b58df7b 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -74,7 +74,7 @@ readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") - "Build flavour (Default, Quick or Quickest)." + "Build flavour (default, quick or quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") From git at git.haskell.org Fri Oct 27 01:09:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #286 from cocreature/lowercase-flavour (e5b4b0c) Message-ID: <20171027010913.055C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e5b4b0cbef54b3c2c32238cb810a5cebcb9270e7/ghc >--------------------------------------------------------------- commit e5b4b0cbef54b3c2c32238cb810a5cebcb9270e7 Merge: fd7dd6f 73c72a6 Author: Andrey Mokhov Date: Sat Sep 3 12:20:06 2016 +0100 Merge pull request #286 from cocreature/lowercase-flavour Lowercase flavour names in --help >--------------------------------------------------------------- e5b4b0cbef54b3c2c32238cb810a5cebcb9270e7 src/CmdLineFlag.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 01:09:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add path to generated includes for compiler package (57d6c69) Message-ID: <20171027010916.6AFE93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57d6c69843a0c2f7fd89a0c9cbc49742c6347414/ghc >--------------------------------------------------------------- commit 57d6c69843a0c2f7fd89a0c9cbc49742c6347414 Author: Andrey Mokhov Date: Sun Sep 25 01:29:46 2016 +0900 Add path to generated includes for compiler package Fix #288. >--------------------------------------------------------------- 57d6c69843a0c2f7fd89a0c9cbc49742c6347414 src/Settings/Builders/Common.hs | 2 +- src/Settings/Packages/Compiler.hs | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index d036f8a..b276102 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -1,5 +1,5 @@ module Settings.Builders.Common ( - includesArgs, cIncludeArgs, ldArgs, cArgs, cWarnings, + includes, includesArgs, cIncludeArgs, ldArgs, cArgs, cWarnings, argSetting, argSettingList, argStagedBuilderPath, argStagedSettingList ) where diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 7dbbaa3..65ced17 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -7,6 +7,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Predicate import Settings +import Settings.Builders.Common compilerPackageArgs :: Args compilerPackageArgs = package compiler ? do @@ -15,7 +16,10 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder Ghc ? arg ("-I" ++ path) + , builder Ghc ? mconcat + [ arg ("-I" ++ path) + , includesArgs + , append [ "-optP-I" ++ dir | dir <- includes ] ] , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) From git at git.haskell.org Fri Oct 27 01:09:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor GMP build rule (6836711) Message-ID: <20171027010919.D66803A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68367119d7f5d1f01a94a0eab87a53900c54fe3e/ghc >--------------------------------------------------------------- commit 68367119d7f5d1f01a94a0eab87a53900c54fe3e Author: Andrey Mokhov Date: Sun Oct 2 10:40:16 2016 +0900 Refactor GMP build rule See #289. >--------------------------------------------------------------- 68367119d7f5d1f01a94a0eab87a53900c54fe3e src/Rules/Gmp.hs | 92 ++++++++++++++++++++++++--------------------------- src/Settings/Paths.hs | 8 ++--- 2 files changed, 45 insertions(+), 55 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 7fc3e18..66d6c0b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -17,10 +17,12 @@ gmpBase = pkgPath integerGmp -/- "gmp" gmpContext :: Context gmpContext = vanillaContext Stage1 integerGmp --- TODO: Noone needs this file, but we build it. Why? gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" +gmpLibrary :: FilePath +gmpLibrary = gmpBuildPath -/- ".libs/libgmp.a" + gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] @@ -29,76 +31,68 @@ configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 , builderEnvironment "AR" Ar , builderEnvironment "NM" Nm ] --- TODO: we rebuild gmp every time. gmpRules :: Rules () gmpRules = do - -- TODO: split into multiple rules gmpLibraryH %> \_ -> do - need [sourcePath -/- "Rules/Gmp.hs"] - removeDirectory gmpBuildPath - - -- We don't use system GMP on Windows. TODO: fix? windows <- windowsHost configMk <- readFile' $ gmpBase -/- "config.mk" - if not windows && any (`isInfixOf` configMk) - [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] + if not windows && -- TODO: We don't use system GMP on Windows. Fix? + any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" createDirectory $ takeDirectory gmpLibraryH copyFile (gmpBase -/- "ghc-gmp.h") gmpLibraryH else do putBuild "| No GMP library/framework detected; in tree GMP will be built" - - -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is - -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. - -- That's because the doc/ directory contents are under the GFDL, - -- which causes problems for Debian. - tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "gmpRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - - withTempDir $ \dir -> do - let tmp = unifyPath dir - need [tarball] - build $ Target gmpContext Tar [tarball] [tmp] - - forM_ gmpPatches $ \src -> do - let patch = takeFileName src - patchPath = tmp -/- patch - copyFile src patchPath - applyPatch tmp patch - - let name = dropExtension . dropExtension $ takeFileName tarball - unpack = fromMaybe . error $ "gmpRules: expected suffix " - ++ "-nodoc-patched (found: " ++ name ++ ")." - libName = unpack $ stripSuffix "-nodoc-patched" name - - moveDirectory (tmp -/- libName) gmpBuildPath - - env <- configureEnvironment - buildWithCmdOptions env $ - Target gmpContext (Configure gmpBuildPath) - [gmpBuildPath -/- "Makefile.in"] - [gmpBuildPath -/- "Makefile"] - build $ Target gmpContext (Make gmpBuildPath) [] [] - createDirectory $ takeDirectory gmpLibraryH copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH - moveFile (gmpBuildPath -/- ".libs/libgmp.a") gmpLibrary - createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] - runBuilder Ranlib [gmpLibrary] - putSuccess "| Successfully built custom library 'gmp'" + -- In-tree GMP header is built in the gmpLibraryH rule gmpLibraryInTreeH %> \_ -> need [gmpLibraryH] -- This causes integerGmp package to be configured, hence creating the files [gmpBase -/- "config.mk", gmpBuildInfoPath] &%> \_ -> need [pkgDataFile gmpContext] + + -- Extract in-tree GMP sources and apply patches + gmpBuildPath -/- "Makefile.in" %> \_ -> do + removeDirectory gmpBuildPath + -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is + -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. + -- That's because the doc/ directory contents are under the GFDL, + -- which causes problems for Debian. + tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] + tarball <- case tarballs of -- TODO: Drop code duplication. + [file] -> return $ unifyPath file + _ -> error $ "gmpRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + + withTempDir $ \dir -> do + let tmp = unifyPath dir + need [tarball] + build $ Target gmpContext Tar [tarball] [tmp] + + forM_ gmpPatches $ \src -> do + let patch = takeFileName src + copyFile src $ tmp -/- patch + applyPatch tmp patch + + let name = dropExtension . dropExtension $ takeFileName tarball + unpack = fromMaybe . error $ "gmpRules: expected suffix " + ++ "-nodoc-patched (found: " ++ name ++ ")." + libName = unpack $ stripSuffix "-nodoc-patched" name + + moveDirectory (tmp -/- libName) gmpBuildPath + + -- Run GMP's configure script + gmpBuildPath -/- "Makefile" %> \mk -> do + env <- configureEnvironment + need [mk <.> "in"] + buildWithCmdOptions env $ + Target gmpContext (Configure gmpBuildPath) [mk <.> "in"] [mk] diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 51e92e2..9c770f3 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,7 +1,7 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibrary, gmpObjects, - gmpLibraryH, gmpBuildInfoPath, libffiBuildPath, shakeFilesPath, pkgConfFile, + pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, + gmpBuildInfoPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, bootPackageConstraints, packageDependencies ) where @@ -66,10 +66,6 @@ pkgFile context prefix suffix = do gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" --- | Path to the GMP library. -gmpLibrary :: FilePath -gmpLibrary = gmpBuildPath -/- "libgmp.a" - -- | Path to the GMP library header. gmpLibraryH :: FilePath gmpLibraryH = gmpBuildPath -/- "include/ghc-gmp.h" From git at git.haskell.org Fri Oct 27 01:09:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split the GMP build rule even further (d12066d) Message-ID: <20171027010923.5B2DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d12066d8d457e2ea7dbc4afa37e8acaac6afa413/ghc >--------------------------------------------------------------- commit d12066d8d457e2ea7dbc4afa37e8acaac6afa413 Author: Andrey Mokhov Date: Sun Oct 2 03:23:42 2016 +0100 Split the GMP build rule even further See #289. >--------------------------------------------------------------- d12066d8d457e2ea7dbc4afa37e8acaac6afa413 src/Rules/Gmp.hs | 36 +++++++++++++++++++++--------------- 1 file changed, 21 insertions(+), 15 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 66d6c0b..0a53102 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -23,6 +23,9 @@ gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" gmpLibrary :: FilePath gmpLibrary = gmpBuildPath -/- ".libs/libgmp.a" +gmpMakefile :: FilePath +gmpMakefile = gmpBuildPath -/- "Makefile" + gmpPatches :: [FilePath] gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] @@ -33,24 +36,27 @@ configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 gmpRules :: Rules () gmpRules = do - gmpLibraryH %> \_ -> do + -- Copy appropriate GMP header and object files + gmpLibraryH %> \header -> do + createDirectory $ takeDirectory header windows <- windowsHost configMk <- readFile' $ gmpBase -/- "config.mk" if not windows && -- TODO: We don't use system GMP on Windows. Fix? any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" - createDirectory $ takeDirectory gmpLibraryH - copyFile (gmpBase -/- "ghc-gmp.h") gmpLibraryH + copyFile (gmpBase -/- "ghc-gmp.h") header else do putBuild "| No GMP library/framework detected; in tree GMP will be built" - build $ Target gmpContext (Make gmpBuildPath) [] [] - createDirectory $ takeDirectory gmpLibraryH - copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH - copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH + need [gmpLibrary] createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] + copyFile (gmpBuildPath -/- "gmp.h") header + copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH + -- Build in-tree GMP library + gmpLibrary %> \lib -> do + build $ Target gmpContext (Make gmpBuildPath) [gmpMakefile] [lib] putSuccess "| Successfully built custom library 'gmp'" -- In-tree GMP header is built in the gmpLibraryH rule @@ -60,8 +66,15 @@ gmpRules = do [gmpBase -/- "config.mk", gmpBuildInfoPath] &%> \_ -> need [pkgDataFile gmpContext] + -- Run GMP's configure script + gmpMakefile %> \mk -> do + env <- configureEnvironment + need [mk <.> "in"] + buildWithCmdOptions env $ + Target gmpContext (Configure gmpBuildPath) [mk <.> "in"] [mk] + -- Extract in-tree GMP sources and apply patches - gmpBuildPath -/- "Makefile.in" %> \_ -> do + gmpMakefile <.> "in" %> \_ -> do removeDirectory gmpBuildPath -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. @@ -89,10 +102,3 @@ gmpRules = do libName = unpack $ stripSuffix "-nodoc-patched" name moveDirectory (tmp -/- libName) gmpBuildPath - - -- Run GMP's configure script - gmpBuildPath -/- "Makefile" %> \mk -> do - env <- configureEnvironment - need [mk <.> "in"] - buildWithCmdOptions env $ - Target gmpContext (Configure gmpBuildPath) [mk <.> "in"] [mk] From git at git.haskell.org Fri Oct 27 01:09:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing directory (c9ae45b) Message-ID: <20171027010926.CD9503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9ae45b4c7757a54b40f84c6a8532f2d5c2a5418/ghc >--------------------------------------------------------------- commit c9ae45b4c7757a54b40f84c6a8532f2d5c2a5418 Author: Andrey Mokhov Date: Sun Oct 2 18:38:31 2016 +0900 Fix missing directory See #289. >--------------------------------------------------------------- c9ae45b4c7757a54b40f84c6a8532f2d5c2a5418 src/Rules/Gmp.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 0a53102..50c548b 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -38,19 +38,20 @@ gmpRules :: Rules () gmpRules = do -- Copy appropriate GMP header and object files gmpLibraryH %> \header -> do - createDirectory $ takeDirectory header windows <- windowsHost configMk <- readFile' $ gmpBase -/- "config.mk" if not windows && -- TODO: We don't use system GMP on Windows. Fix? any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" + createDirectory $ takeDirectory header copyFile (gmpBase -/- "ghc-gmp.h") header else do putBuild "| No GMP library/framework detected; in tree GMP will be built" need [gmpLibrary] createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] + createDirectory $ takeDirectory header copyFile (gmpBuildPath -/- "gmp.h") header copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH From git at git.haskell.org Fri Oct 27 01:09:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move generated includes to build directory (f2cff6f) Message-ID: <20171027010930.581463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f2cff6f69f43c83c33f53971c96e770a68030ca5/ghc >--------------------------------------------------------------- commit f2cff6f69f43c83c33f53971c96e770a68030ca5 Author: Andrey Mokhov Date: Mon Oct 3 00:47:32 2016 +0900 Move generated includes to build directory See #113. >--------------------------------------------------------------- f2cff6f69f43c83c33f53971c96e770a68030ca5 src/Rules/Clean.hs | 4 +--- src/Rules/Data.hs | 7 ++---- src/Rules/Generate.hs | 20 +++++++--------- src/Settings/Builders/Cc.hs | 24 +++++++------------ src/Settings/Builders/Common.hs | 13 ++++------- src/Settings/Builders/DeriveConstants.hs | 21 ++++++++--------- src/Settings/Builders/GhcCabal.hs | 40 +++++++++++++++----------------- src/Settings/Builders/HsCpp.hs | 4 ++-- src/Settings/Packages/Compiler.hs | 7 +++--- src/Settings/Packages/IntegerGmp.hs | 3 +-- src/Settings/Packages/Rts.hs | 8 +++---- src/Settings/Paths.hs | 5 +++- 12 files changed, 66 insertions(+), 90 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 f2cff6f69f43c83c33f53971c96e770a68030ca5 From git at git.haskell.org Fri Oct 27 01:09:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop TODOs (456a10b) Message-ID: <20171027010933.F367A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/456a10bc8d12b8b2ac17c28279f35f5b675702d8/ghc >--------------------------------------------------------------- commit 456a10bc8d12b8b2ac17c28279f35f5b675702d8 Author: Andrey Mokhov Date: Mon Oct 3 01:21:11 2016 +0900 Drop TODOs See #113 >--------------------------------------------------------------- 456a10bc8d12b8b2ac17c28279f35f5b675702d8 src/Rules/Generate.hs | 1 - src/Rules/Library.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 1 - 3 files changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index d7068cf..266141f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -40,7 +40,6 @@ primopsTxt stage = buildPath (vanillaContext stage compiler) -/- "primops.txt" platformH :: Stage -> FilePath platformH stage = buildPath (vanillaContext stage compiler) -/- "ghc_boot_platform.h" --- TODO: move generated files to buildRootPath, see #113 includesDependencies :: [FilePath] includesDependencies = fmap (generatedPath -/-) [ "ghcautoconf.h" diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index c2d56b4..00a6be2 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -97,6 +97,6 @@ hSources context = do extraObjects :: Context -> Action [FilePath] extraObjects context | context == gmpContext = do - need [gmpLibraryH] -- TODO: Move this dependency elsewhere, #113? + need [gmpLibraryH] map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 7de3846..93ab4ed 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -6,7 +6,6 @@ import Oracles.Config.Setting import Predicate import Settings.Paths --- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? -- ifeq "$(GMP_PREFER_FRAMEWORK)" "YES" -- libraries/integer-gmp_CONFIGURE_OPTS += --with-gmp-framework-preferred From git at git.haskell.org Fri Oct 27 01:09:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix generated includes (c6cb106) Message-ID: <20171027010937.6CC763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6cb106cf0d437ff1352b95b57224d6a2c2a4744/ghc >--------------------------------------------------------------- commit c6cb106cf0d437ff1352b95b57224d6a2c2a4744 Author: Andrey Mokhov Date: Mon Oct 3 04:58:54 2016 +0900 Fix generated includes See #113. >--------------------------------------------------------------- c6cb106cf0d437ff1352b95b57224d6a2c2a4744 src/Rules/Generate.hs | 4 ++++ src/Settings/Builders/Common.hs | 2 ++ src/Settings/Builders/DeriveConstants.hs | 2 ++ src/Settings/Builders/Ghc.hs | 2 ++ src/Settings/Builders/GhcCabal.hs | 4 +++- src/Settings/Packages/Compiler.hs | 4 +--- src/Settings/Packages/Rts.hs | 3 +-- 7 files changed, 15 insertions(+), 6 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 266141f..035318f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -45,6 +45,8 @@ includesDependencies = fmap (generatedPath -/-) [ "ghcautoconf.h" , "ghcplatform.h" , "ghcversion.h" ] + ++ -- TODO: This is a temporary fix, see #113: + [ "includes/ghcversion.h"] ghcPrimDependencies :: Expr [FilePath] ghcPrimDependencies = do @@ -165,6 +167,8 @@ copyRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs rtsBuildPath -/- "sm/Evac_thr.c" %> copyFile (pkgPath rts -/- "sm/Evac.c") rtsBuildPath -/- "sm/Scav_thr.c" %> copyFile (pkgPath rts -/- "sm/Scav.c") + -- TODO: This is a temporary fix, see #113: + "includes/ghcversion.h" <~ generatedPath where file <~ dir = file %> copyFile (dir -/- takeFileName file) diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 49e5f30..698b343 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -9,6 +9,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.PackageData import Settings +import Settings.Paths import UserSettings cIncludeArgs :: Args @@ -18,6 +19,7 @@ cIncludeArgs = do incDirs <- getPkgDataList IncludeDirs depDirs <- getPkgDataList DepIncludeDirs mconcat [ arg "-Iincludes" + , arg $ "-I" ++ generatedPath , arg $ "-I" ++ path , arg $ "-I" ++ path -/- "autogen" , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index 9cfd9dd..621a225 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -5,6 +5,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Predicate import Settings.Builders.Common +import Settings.Paths -- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? deriveConstantsBuilderArgs :: Args @@ -34,5 +35,6 @@ includeCcArgs = mconcat , flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER" , arg "-Irts" , arg "-Iincludes" + , arg $ "-I" ++ generatedPath , notM ghcWithSMP ? arg "-DNOSMP" , arg "-fcommon" ] diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index d2cd761..475c9b3 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -135,6 +135,8 @@ includeGhcArgs = do , arg $ "-i" ++ path -/- "autogen" , append [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ] , cIncludeArgs + , arg $ "-I" ++ generatedPath + , arg $ "-optc-I" ++ generatedPath , arg "-optP-include" , arg $ "-optP" ++ path -/- "autogen/cabal_macros.h" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 7a3b3a0..14c1254 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -64,10 +64,12 @@ libraryArgs = do -- TODO: WARNING: unrecognized options: --with-compiler, --with-gmp-libraries, --with-cc configureArgs :: Args configureArgs = do + top <- getTopDirectory let conf key = appendSubD $ "--configure-option=" ++ key cFlags = mconcat [ cArgs , remove ["-Werror"] - , argStagedSettingList ConfCcArgs ] + , argStagedSettingList ConfCcArgs + , arg $ "-I" ++ top -/- generatedPath ] ldFlags = ldArgs <> (argStagedSettingList ConfGccLinkerArgs) cppFlags = cppArgs <> (argStagedSettingList ConfCppArgs) mconcat diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 1866a1b..df9020d 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -16,9 +16,7 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder Ghc ? mconcat - [ arg $ "-I" ++ path - , arg $ "-optP-I" ++ generatedPath ] + , builder Ghc ? arg ("-I" ++ path) , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index a4ed2a1..f3f2e43 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -9,7 +9,6 @@ import Oracles.Config.Setting import Oracles.WindowsPath import Predicate import Settings -import Settings.Paths rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" @@ -92,7 +91,7 @@ rtsPackageArgs = package rts ? do , input "//Evac_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] , input "//Scav_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] ] - , builder Ghc ? arg "-Irts" <> arg ("-I" ++ generatedPath) + , builder Ghc ? arg "-Irts" , builder (GhcPkg Stage1) ? mconcat [ remove ["rts/stage1/inplace-pkg-config"] -- TODO: fix, see #113 From git at git.haskell.org Fri Oct 27 01:09:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path to ghcversion.h header (0ff86b4) Message-ID: <20171027010940.D52643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ff86b4b7071cead9d50310090c86d4a18c068fa/ghc >--------------------------------------------------------------- commit 0ff86b4b7071cead9d50310090c86d4a18c068fa Author: Andrey Mokhov Date: Mon Oct 3 05:52:00 2016 +0900 Fix path to ghcversion.h header See #113. >--------------------------------------------------------------- 0ff86b4b7071cead9d50310090c86d4a18c068fa src/Rules/Generate.hs | 4 ---- src/Rules/Register.hs | 3 ++- 2 files changed, 2 insertions(+), 5 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 035318f..266141f 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -45,8 +45,6 @@ includesDependencies = fmap (generatedPath -/-) [ "ghcautoconf.h" , "ghcplatform.h" , "ghcversion.h" ] - ++ -- TODO: This is a temporary fix, see #113: - [ "includes/ghcversion.h"] ghcPrimDependencies :: Expr [FilePath] ghcPrimDependencies = do @@ -167,8 +165,6 @@ copyRules = do "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs rtsBuildPath -/- "sm/Evac_thr.c" %> copyFile (pkgPath rts -/- "sm/Evac.c") rtsBuildPath -/- "sm/Scav_thr.c" %> copyFile (pkgPath rts -/- "sm/Scav.c") - -- TODO: This is a temporary fix, see #113: - "includes/ghcversion.h" <~ generatedPath where file <~ dir = file %> copyFile (dir -/- takeFileName file) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index ec33668..272e27b 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -46,7 +46,8 @@ registerPackage rs context at Context {..} = do let fixRtsConf = unlines . map ( replace "\"\"" "" - . replace "rts/dist/build" rtsBuildPath ) + . replace "rts/dist/build" rtsBuildPath + . replace "includes/dist-derivedconstants/header" generatedPath ) . filter (not . null) . lines From git at git.haskell.org Fri Oct 27 01:09:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass configure Cc and Cpp options to GHC (79575b3) Message-ID: <20171027010944.4BCB33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/79575b395e32de2ad6dec3bf4e11d30767779ee6/ghc >--------------------------------------------------------------- commit 79575b395e32de2ad6dec3bf4e11d30767779ee6 Author: Andrey Mokhov Date: Sun Oct 2 23:30:15 2016 +0100 Pass configure Cc and Cpp options to GHC >--------------------------------------------------------------- 79575b395e32de2ad6dec3bf4e11d30767779ee6 src/Settings/Builders/Ghc.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 475c9b3..6eaf8ae 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -78,7 +78,8 @@ commonGhcArgs :: Args commonGhcArgs = do way <- getWay path <- getBuildPath - hsArgs <- getPkgDataList HsArgs + confCc <- getSettingList . ConfCcArgs =<< getStage + confCpp <- getSettingList . ConfCppArgs =<< getStage cppArgs <- getPkgDataList CppArgs mconcat [ arg "-hisuf", arg $ hisuf way , arg "-osuf" , arg $ osuf way @@ -86,7 +87,9 @@ commonGhcArgs = do , wayGhcArgs , packageGhcArgs , includeGhcArgs - , append hsArgs + , append =<< getPkgDataList HsArgs + , append $ map ("-optc" ++) confCc + , append $ map ("-optP" ++) confCpp , append $ map ("-optP" ++) cppArgs , arg "-odir" , arg path , arg "-hidir" , arg path From git at git.haskell.org Fri Oct 27 01:09:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to Cabal library changes (10154e7) Message-ID: <20171027010947.AF9C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/10154e73137208ba1808c4b19a9e507e0943de8f/ghc >--------------------------------------------------------------- commit 10154e73137208ba1808c4b19a9e507e0943de8f Author: Andrey Mokhov Date: Mon Oct 3 09:30:05 2016 +0100 Adapt to Cabal library changes >--------------------------------------------------------------- 10154e73137208ba1808c4b19a9e507e0943de8f src/Rules/Cabal.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index ed72f93..e12ab33 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,10 +1,11 @@ module Rules.Cabal (cabalRules) where -import Data.Version import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse +import Distribution.Text import Distribution.Verbosity +import Text.PrettyPrint import Base import Expression @@ -22,9 +23,8 @@ cabalRules = do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg let identifier = package . packageDescription $ pd - version = showVersion . pkgVersion $ identifier - DP.PackageName name = DP.pkgName identifier - return $ name ++ " == " ++ version + version = render . disp . pkgVersion $ identifier + return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version writeFileChanged out . unlines $ constraints -- Cache package dependencies. @@ -38,7 +38,7 @@ cabalRules = do let depsLib = collectDeps $ condLibrary pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes - depNames = [ name | Dependency (DP.PackageName name) _ <- deps ] + depNames = [ unPackageName name | Dependency name _ <- deps ] return . unwords $ pkgNameString pkg : sort depNames writeFileChanged out . unlines $ pkgDeps From git at git.haskell.org Fri Oct 27 01:09:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Text.PrettyPrint dependency (4afc5a4) Message-ID: <20171027010951.3F92E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4afc5a4ddf3511bfefc3abcaa15144844536d8b6/ghc >--------------------------------------------------------------- commit 4afc5a4ddf3511bfefc3abcaa15144844536d8b6 Author: Andrey Mokhov Date: Mon Oct 3 09:45:34 2016 +0100 Drop Text.PrettyPrint dependency >--------------------------------------------------------------- 4afc5a4ddf3511bfefc3abcaa15144844536d8b6 src/Rules/Cabal.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index e12ab33..69cdd51 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -5,7 +5,6 @@ import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Text import Distribution.Verbosity -import Text.PrettyPrint import Base import Expression @@ -23,7 +22,7 @@ cabalRules = do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg let identifier = package . packageDescription $ pd - version = render . disp . pkgVersion $ identifier + version = display . pkgVersion $ identifier return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version writeFileChanged out . unlines $ constraints From git at git.haskell.org Fri Oct 27 01:09:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop repeated argument (e0de028) Message-ID: <20171027010954.C46633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e0de0283e09eab974e22c6e37f36479597f3fc78/ghc >--------------------------------------------------------------- commit e0de0283e09eab974e22c6e37f36479597f3fc78 Author: Andrey Mokhov Date: Mon Oct 3 17:23:05 2016 +0100 Drop repeated argument >--------------------------------------------------------------- e0de0283e09eab974e22c6e37f36479597f3fc78 src/Settings/Packages/Compiler.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index df9020d..f33dc18 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -16,8 +16,6 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder Ghc ? arg ("-I" ++ path) - , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) , arg "--disable-library-for-ghci" From git at git.haskell.org Fri Oct 27 01:09:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:09:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify paths when printing progress info (6adb600) Message-ID: <20171027010958.5DE1C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6adb60093ae65970bbec17f9b24227b20f5a71f5/ghc >--------------------------------------------------------------- commit 6adb60093ae65970bbec17f9b24227b20f5a71f5 Author: Andrey Mokhov Date: Mon Oct 3 18:22:23 2016 +0100 Unify paths when printing progress info >--------------------------------------------------------------- 6adb60093ae65970bbec17f9b24227b20f5a71f5 src/Rules/Actions.hs | 15 +++++++-------- 1 file changed, 7 insertions(+), 8 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index cbca810..e30bc01 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -200,16 +200,15 @@ putProgressInfo :: String -> Action () putProgressInfo msg = when (cmdProgressInfo /= None) $ putBuild msg -- | Render an action. -renderAction :: String -> String -> String -> String +renderAction :: String -> FilePath -> FilePath -> String renderAction what input output = case cmdProgressInfo of - Normal -> renderBox [ what - , " input: " ++ input - , " => output: " ++ output ] - Brief -> "| " ++ what ++ ": " ++ input ++ " => " ++ output - Unicorn -> renderUnicorn [ what - , " input: " ++ input - , " => output: " ++ output ] + Normal -> renderBox [ what, " input: " ++ i, " => output: " ++ o ] + Brief -> "| " ++ what ++ ": " ++ i ++ " => " ++ o + Unicorn -> renderUnicorn [ what, " input: " ++ i, " => output: " ++ o ] None -> "" + where + i = unifyPath input + o = unifyPath output -- | Render the successful build of a program renderProgram :: String -> String -> String -> String From git at git.haskell.org Fri Oct 27 01:10:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't track -jN arguments passed to Make (b096f1e) Message-ID: <20171027011005.7B7203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b096f1e48ba8df3e1636c8671ec867fc6b636c29/ghc >--------------------------------------------------------------- commit b096f1e48ba8df3e1636c8671ec867fc6b636c29 Author: Andrey Mokhov Date: Wed Oct 5 13:28:28 2016 +0100 Don't track -jN arguments passed to Make See #289. >--------------------------------------------------------------- b096f1e48ba8df3e1636c8671ec867fc6b636c29 src/Builder.hs | 13 +++++++++++-- src/Oracles/ArgsHash.hs | 6 +++++- 2 files changed, 16 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 1974eff..704947d 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -1,10 +1,11 @@ {-# LANGUAGE DeriveGeneric, LambdaCase #-} module Builder ( - CcMode (..), GhcMode (..), Builder (..), - builderPath, getBuilderPath, builderEnvironment, specified, needBuilder + CcMode (..), GhcMode (..), Builder (..), builderPath, getBuilderPath, + builderEnvironment, specified, trackedArgument, needBuilder ) where import Control.Monad.Trans.Reader +import Data.Char import GHC.Generics (Generic) import Base @@ -149,6 +150,14 @@ builderEnvironment variable builder = do specified :: Builder -> Action Bool specified = fmap (not . null) . builderPath +-- | Some arguments do not affect build results and therefore do not need to be +-- tracked by the build system. A notable example is "-jN" that controls Make's +-- parallelism. Given a 'Builder' and an argument, this function should return +-- 'True' only if the argument needs to be tracked. +trackedArgument :: Builder -> String -> Bool +trackedArgument (Make _) ('-' : 'j' : xs) = not $ all isDigit xs +trackedArgument _ _ = True + -- | Make sure a Builder exists on the given path and rebuild it if out of date. needBuilder :: Builder -> Action () needBuilder = \case diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index 660edd9..f9cec24 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -2,6 +2,7 @@ module Oracles.ArgsHash (checkArgsHash, argsHashOracle) where import Base +import Builder import Expression import Settings import Target @@ -28,4 +29,7 @@ checkArgsHash target = do -- | Oracle for storing per-target argument list hashes. argsHashOracle :: Rules () argsHashOracle = void $ - addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs + addOracle $ \(ArgsHashKey target) -> do + argList <- interpret target getArgs + let trackedArgList = filter (trackedArgument $ builder target) argList + return $ hash trackedArgList From git at git.haskell.org Fri Oct 27 01:10:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor libffi build rule (c391842) Message-ID: <20171027011001.E72033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3918421098ab7da0d6c62689ccfbe37abe26b24/ghc >--------------------------------------------------------------- commit c3918421098ab7da0d6c62689ccfbe37abe26b24 Author: Andrey Mokhov Date: Mon Oct 3 18:22:48 2016 +0100 Refactor libffi build rule See #289 >--------------------------------------------------------------- c3918421098ab7da0d6c62689ccfbe37abe26b24 src/Rules/Libffi.hs | 79 ++++++++++++++++++++++++++--------------------------- 1 file changed, 39 insertions(+), 40 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 4434f50..5ca17ea 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -6,6 +6,7 @@ import Expression import GHC import Oracles.Config.Flag import Oracles.Config.Setting +import Oracles.WindowsPath import Rules.Actions import Settings.Builders.Common import Settings.Packages.Rts @@ -30,11 +31,11 @@ libffiLibrary = libffiBuildPath -/- "inst/lib/libffi.a" libffiMakefile :: FilePath libffiMakefile = libffiBuildPath -/- "Makefile" -fixLibffiMakefile :: String -> String -fixLibffiMakefile = +fixLibffiMakefile :: FilePath -> String -> String +fixLibffiMakefile top = replace "-MD" "-MMD" . replace "@toolexeclibdir@" "$(libdir)" - . replace "@INSTALL@" "$(subst ../install-sh,C:/msys/home/chEEtah/ghc/install-sh, at INSTALL@)" + . replace "@INSTALL@" ("$(subst ../install-sh," ++ top ++ "/install-sh, at INSTALL@)") -- TODO: remove code duplication (see Settings/Builders/GhcCabal.hs) -- TODO: check code duplication w.r.t. ConfCcArgs @@ -53,12 +54,9 @@ configureEnvironment = do , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w" , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ] --- TODO: remove code duplication (need sourcePath) --- TODO: split into multiple rules libffiRules :: Rules () libffiRules = do libffiDependencies &%> \_ -> do - need [sourcePath -/- "Rules/Libffi.hs"] useSystemFfi <- flag UseSystemFfi if useSystemFfi then do @@ -68,44 +66,45 @@ libffiRules = do copyFile (ffiIncludeDir -/- file) (rtsBuildPath -/- file) putSuccess $ "| Successfully copied system FFI library header files" else do - removeDirectory libffiBuildPath - createDirectory $ buildRootPath -/- stageString Stage0 - - tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "libffiRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - - need [tarball] - let libname = dropExtension . dropExtension $ takeFileName tarball - - removeDirectory (buildRootPath -/- libname) - -- TODO: Simplify. - actionFinally (do - build $ Target libffiContext Tar [tarball] [buildRootPath] - moveDirectory (buildRootPath -/- libname) libffiBuildPath) $ - removeFiles buildRootPath [libname "*"] - - fixFile (libffiMakefile <.> "in") fixLibffiMakefile - - forM_ ["config.guess", "config.sub"] $ \file -> - copyFile file (libffiBuildPath -/- file) - - env <- configureEnvironment - buildWithCmdOptions env $ - Target libffiContext (Configure libffiBuildPath) - [libffiMakefile <.> "in"] [libffiMakefile] - - -- The old build system did runMake libffiBuildPath ["MAKEFLAGS="] - -- TODO: Find out why. It seems redundant, so I removed it. build $ Target libffiContext (Make libffiBuildPath) [] [] - let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" - forM_ ["ffi.h", "ffitarget.h"] $ \file -> do - copyFile (ffiHDir -/- file) (rtsBuildPath -/- file) + hs <- getDirectoryFiles "" [libffiBuildPath -/- "inst/lib/*/include/*"] + forM_ hs $ \header -> + copyFile header (rtsBuildPath -/- takeFileName header) libffiName <- rtsLibffiLibraryName copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") putSuccess $ "| Successfully built custom library 'libffi'" + + libffiMakefile <.> "in" %> \mkIn -> do + removeDirectory libffiBuildPath + createDirectory $ buildRootPath -/- stageString Stage0 + + tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] + tarball <- case tarballs of -- TODO: Drop code duplication. + [file] -> return $ unifyPath file + _ -> error $ "libffiRules: exactly one tarball expected" + ++ "(found: " ++ show tarballs ++ ")." + + need [tarball] + let libname = dropExtension . dropExtension $ takeFileName tarball + + removeDirectory (buildRootPath -/- libname) + -- TODO: Simplify. + actionFinally (do + build $ Target libffiContext Tar [tarball] [buildRootPath] + moveDirectory (buildRootPath -/- libname) libffiBuildPath) $ + removeFiles buildRootPath [libname "*"] + + top <- topDirectory + fixFile mkIn (fixLibffiMakefile top) + + libffiMakefile %> \mk -> do + need [mk <.> "in"] + forM_ ["config.guess", "config.sub"] $ \file -> + copyFile file (libffiBuildPath -/- file) + + env <- configureEnvironment + buildWithCmdOptions env $ + Target libffiContext (Configure libffiBuildPath) [mk <.> "in"] [mk] From git at git.haskell.org Fri Oct 27 01:10:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Support several variants of -jN flag, add tests (73b9b7b) Message-ID: <20171027011008.F128E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73b9b7b47f9c33506be8238d355eba2363470ce9/ghc >--------------------------------------------------------------- commit 73b9b7b47f9c33506be8238d355eba2363470ce9 Author: Andrey Mokhov Date: Wed Oct 5 15:31:26 2016 +0100 Support several variants of -jN flag, add tests See #289. >--------------------------------------------------------------- 73b9b7b47f9c33506be8238d355eba2363470ce9 src/Builder.hs | 7 +++++-- src/Rules/Selftest.hs | 22 ++++++++++++++++------ 2 files changed, 21 insertions(+), 8 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 704947d..55d561e 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -155,8 +155,11 @@ specified = fmap (not . null) . builderPath -- parallelism. Given a 'Builder' and an argument, this function should return -- 'True' only if the argument needs to be tracked. trackedArgument :: Builder -> String -> Bool -trackedArgument (Make _) ('-' : 'j' : xs) = not $ all isDigit xs -trackedArgument _ _ = True +trackedArgument (Make _) = not . threadArg +trackedArgument _ = const True + +threadArg :: String -> Bool +threadArg s = dropWhileEnd isDigit s `elem` ["-j", "MAKEFLAGS=-j", "THREADS="] -- | Make sure a Builder exists on the given path and rebuild it if out of date. needBuilder :: Builder -> Action () diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index f53a5db..3b20f14 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,6 +6,7 @@ import Development.Shake import Test.QuickCheck import Base +import Builder import Oracles.ModuleFiles import Settings.Builders.Ar import UserSettings @@ -23,14 +24,23 @@ test = liftIO . quickCheck selftestRules :: Rules () selftestRules = "selftest" ~> do - testWays + testBuilder + testWay testChunksOfSize testMatchVersionedFilePath - testModuleNames + testModuleName testLookupAll -testWays :: Action () -testWays = do +testBuilder :: Action () +testBuilder = do + putBuild $ "==== trackedArgument" + test $ forAll (elements ["-j", "MAKEFLAGS=-j", "THREADS="]) + $ \prefix -> \(NonNegative n) -> + trackedArgument (Make undefined) prefix == False && + trackedArgument (Make undefined) ("-j" ++ show (n :: Int)) == False + +testWay :: Action () +testWay = do putBuild $ "==== Read Way, Show Way" test $ \(x :: Way) -> read (show x) == x @@ -59,8 +69,8 @@ testMatchVersionedFilePath = do where versions = listOf . elements $ '-' : '.' : ['0'..'9'] -testModuleNames :: Action () -testModuleNames = do +testModuleName :: Action () +testModuleName = do putBuild $ "==== Encode/decode module name" test $ encodeModule "Data/Functor" "Identity.hs" == "Data.Functor.Identity" test $ encodeModule "" "Prelude" == "Prelude" From git at git.haskell.org Fri Oct 27 01:10:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix warnings (8cfa6ef) Message-ID: <20171027011012.742913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8cfa6efa9fb742b90b2c3019536365f711392b75/ghc >--------------------------------------------------------------- commit 8cfa6efa9fb742b90b2c3019536365f711392b75 Author: Andrey Mokhov Date: Wed Oct 5 15:31:45 2016 +0100 Fix warnings >--------------------------------------------------------------- 8cfa6efa9fb742b90b2c3019536365f711392b75 src/Oracles/ArgsHash.hs | 6 +++--- src/Settings/Packages/Compiler.hs | 1 - 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index f9cec24..36a0cdd 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -30,6 +30,6 @@ checkArgsHash target = do argsHashOracle :: Rules () argsHashOracle = void $ addOracle $ \(ArgsHashKey target) -> do - argList <- interpret target getArgs - let trackedArgList = filter (trackedArgument $ builder target) argList - return $ hash trackedArgList + argList <- interpret target getArgs + let trackedArgList = filter (trackedArgument $ builder target) argList + return $ hash trackedArgList diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index f33dc18..03b8081 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -7,7 +7,6 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Predicate import Settings -import Settings.Paths compilerPackageArgs :: Args compilerPackageArgs = package compiler ? do From git at git.haskell.org Fri Oct 27 01:10:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (9233793) Message-ID: <20171027011015.EA6AC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9233793b86b2b14efa3ae1adb5f95f378bf15ef8/ghc >--------------------------------------------------------------- commit 9233793b86b2b14efa3ae1adb5f95f378bf15ef8 Author: Andrey Mokhov Date: Wed Oct 5 17:35:44 2016 +0100 Minor revision >--------------------------------------------------------------- 9233793b86b2b14efa3ae1adb5f95f378bf15ef8 src/Rules/Selftest.hs | 2 +- src/Settings/Builders/Ghc.hs | 8 +++----- 2 files changed, 4 insertions(+), 6 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 3b20f14..e7f5dbb 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -35,7 +35,7 @@ testBuilder :: Action () testBuilder = do putBuild $ "==== trackedArgument" test $ forAll (elements ["-j", "MAKEFLAGS=-j", "THREADS="]) - $ \prefix -> \(NonNegative n) -> + $ \prefix (NonNegative n) -> trackedArgument (Make undefined) prefix == False && trackedArgument (Make undefined) ("-j" ++ show (n :: Int)) == False diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 6eaf8ae..7f54af9 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -36,15 +36,13 @@ ghcLinkArgs :: Args ghcLinkArgs = builder (Ghc LinkHs) ? do stage <- getStage libs <- getPkgDataList DepExtraLibs + libDirs <- getPkgDataList DepLibDirs gmpLibs <- if stage > Stage0 then do -- TODO: get this data more gracefully + let strip = fromMaybe "" . stripPrefix "extra-libraries: " buildInfo <- lift $ readFileLines gmpBuildInfoPath - let extract s = case stripPrefix "extra-libraries: " s of - Nothing -> [] - Just value -> words value - return $ concatMap extract buildInfo + return $ concatMap (words . strip) buildInfo else return [] - libDirs <- getPkgDataList DepLibDirs mconcat [ arg "-no-auto-link-packages" , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] From git at git.haskell.org Fri Oct 27 01:10:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Limit Make's thread (703429d) Message-ID: <20171027011019.7845B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/703429d917a4349d0a7ec8809dfb41c8b3433937/ghc >--------------------------------------------------------------- commit 703429d917a4349d0a7ec8809dfb41c8b3433937 Author: Andrey Mokhov Date: Wed Oct 5 17:36:32 2016 +0100 Limit Make's thread See #289. >--------------------------------------------------------------- 703429d917a4349d0a7ec8809dfb41c8b3433937 src/Settings/Builders/Make.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index d6b7dbf..1e55d9a 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -7,7 +7,7 @@ import Settings.Paths makeBuilderArgs :: Args makeBuilderArgs = do threads <- shakeThreads <$> lift getShakeOptions - let t = show threads + let t = show $ max 4 (threads - 2) -- Don't use all Shake's threads mconcat [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=-j" ++ t] , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=-j" ++ t, "install"] From git at git.haskell.org Fri Oct 27 01:10:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reduce verbosity of ghc-cabal and ghc-pkg (d3d00b0) Message-ID: <20171027011023.07D6F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3d00b0c412d964891f63fbd6c52bc457d6b3233/ghc >--------------------------------------------------------------- commit d3d00b0c412d964891f63fbd6c52bc457d6b3233 Author: Andrey Mokhov Date: Wed Oct 5 17:36:54 2016 +0100 Reduce verbosity of ghc-cabal and ghc-pkg >--------------------------------------------------------------- d3d00b0c412d964891f63fbd6c52bc457d6b3233 src/Settings/Builders/GhcCabal.hs | 37 ++++++++++++++++++++----------------- src/Settings/Builders/GhcPkg.hs | 2 ++ 2 files changed, 22 insertions(+), 17 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 14c1254..fffb2c0 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -17,23 +17,26 @@ import Settings.Builders.Common import Settings.Paths ghcCabalBuilderArgs :: Args -ghcCabalBuilderArgs = builder GhcCabal ? mconcat - [ arg "configure" - , arg =<< getPackagePath - , arg =<< getContextDirectory - , dll0Args - , withStaged $ Ghc CompileHs - , withStaged GhcPkg - , bootPackageDatabaseArgs - , libraryArgs - , with HsColour - , configureArgs - , packageConstraints - , withStaged $ Cc CompileC - , notStage0 ? with Ld - , with Ar - , with Alex - , with Happy ] +ghcCabalBuilderArgs = builder GhcCabal ? do + verbosity <- lift $ getVerbosity + mconcat [ arg "configure" + , arg =<< getPackagePath + , arg =<< getContextDirectory + , dll0Args + , withStaged $ Ghc CompileHs + , withStaged GhcPkg + , bootPackageDatabaseArgs + , libraryArgs + , with HsColour + , configureArgs + , packageConstraints + , withStaged $ Cc CompileC + , notStage0 ? with Ld + , with Ar + , with Alex + , with Happy + , verbosity < Chatty ? append [ "-v0", "--configure-option=--quiet" + , "--configure-option=--disable-option-checking" ] ] ghcCabalHsColourBuilderArgs :: Args ghcCabalHsColourBuilderArgs = builder GhcCabalHsColour ? do diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index ed6843a..b221b9d 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -20,7 +20,9 @@ updateArgs :: Args updateArgs = notM initPredicate ? do pkg <- getPackage dir <- getContextDirectory + verbosity <- lift $ getVerbosity mconcat [ arg "update" , arg "--force" + , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs , arg $ pkgPath pkg -/- dir -/- "inplace-pkg-config" ] From git at git.haskell.org Fri Oct 27 01:10:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Eliminate some uses of fromJust (8657341) Message-ID: <20171027011026.904CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8657341ded43e9671c48929627814e1e64b22ead/ghc >--------------------------------------------------------------- commit 8657341ded43e9671c48929627814e1e64b22ead Author: Ben Gamari Date: Sat Oct 8 15:10:33 2016 -0400 Eliminate some uses of fromJust >--------------------------------------------------------------- 8657341ded43e9671c48929627814e1e64b22ead src/Builder.hs | 7 +++++-- src/Rules.hs | 8 +++++++- 2 files changed, 12 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 55d561e..6f892f2 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -98,11 +98,14 @@ isOptional = \case Objdump -> True _ -> False --- TODO: Get rid of fromJust. -- | Determine the location of a 'Builder'. builderPath :: Builder -> Action FilePath builderPath builder = case builderProvenance builder of - Just context -> return . fromJust $ programPath context + Just context + | Just path <- programPath context -> return path + | otherwise -> + error $ "Cannot determine builderPath for " ++ show builder + ++ " in context " ++ show context Nothing -> case builder of Alex -> fromKey "alex" Ar -> fromKey "ar" diff --git a/src/Rules.hs b/src/Rules.hs index f69cc95..e62ecc7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -49,7 +49,13 @@ topLevelTargets = do docs <- interpretInContext context $ buildHaddock flavour need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else do -- otherwise build a program - need [ fromJust $ programPath context ] -- TODO: drop fromJust + need [ getProgramPath context ] + where + getProgramPath context = + case programPath context of + Nothing -> error $ "topLevelTargets: Can't determine program path for context " + ++ show context + Just path -> path packageRules :: Rules () packageRules = do From git at git.haskell.org Fri Oct 27 01:10:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build mkUserGuidePart with stage-0 (a86f2b1) Message-ID: <20171027011030.2BF993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a86f2b1e97fb7fa0ef08327f083049a41b278513/ghc >--------------------------------------------------------------- commit a86f2b1e97fb7fa0ef08327f083049a41b278513 Author: Ben Gamari Date: Sat Oct 8 15:10:43 2016 -0400 Build mkUserGuidePart with stage-0 This addresses GHC #12619, allowing the users guide to be built with only the stage 0 compiler. >--------------------------------------------------------------- a86f2b1e97fb7fa0ef08327f083049a41b278513 src/Builder.hs | 1 + src/GHC.hs | 5 ++++- src/Settings/Default.hs | 4 ++-- 3 files changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 6f892f2..09b87cb 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -104,6 +104,7 @@ builderPath builder = case builderProvenance builder of Just context | Just path <- programPath context -> return path | otherwise -> + -- TODO: Make builderPath total. error $ "Cannot determine builderPath for " ++ show builder ++ " in context " ++ show context Nothing -> case builder of diff --git a/src/GHC.hs b/src/GHC.hs index 0bfd131..3521e54 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -102,7 +102,10 @@ ghcSplit = "inplace/lib/bin/ghc-split" programPath :: Context -> Maybe FilePath programPath context at Context {..} | package == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) - | package `elem` [checkApiAnnotations, ghcTags, haddock, mkUserGuidePart] = + | package `elem` [mkUserGuidePart] = + case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package + _ -> Nothing + | package `elem` [checkApiAnnotations, ghcTags, haddock] = case stage of Stage2 -> Just . inplaceProgram $ pkgNameString package _ -> Nothing | package `elem` [touchy, unlit] = case stage of diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index e35fea0..4588c4b 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -108,7 +108,7 @@ packagesStage0 = mconcat , ghcPkg, hsc2hs, hoopl, hpc, templateHaskell, transformers ] -- the stage0 predicate makes sure these packages are built only in Stage0 , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode - , hp2ps, unlit ] + , hp2ps, unlit, mkUserGuidePart ] , stage0 ? windowsHost ? append [touchy] , notM windowsHost ? notM iosHost ? append [terminfo] ] @@ -127,7 +127,7 @@ packagesStage1 = mconcat -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages packagesStage2 = mconcat - [ append [checkApiAnnotations, ghcTags, mkUserGuidePart] + [ append [checkApiAnnotations, ghcTags ] , buildHaddock flavour ? append [haddock] ] -- TODO: What about profilingDynamic way? Do we need platformSupportsSharedLibs? From git at git.haskell.org Fri Oct 27 01:10:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #290 from bgamari/master (b7948dd) Message-ID: <20171027011033.C38253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b7948dd53ed2fd905c2f9dda6d30ae5280c9fd6f/ghc >--------------------------------------------------------------- commit b7948dd53ed2fd905c2f9dda6d30ae5280c9fd6f Merge: d3d00b0 a86f2b1 Author: Andrey Mokhov Date: Mon Oct 10 00:27:14 2016 +0100 Merge pull request #290 from bgamari/master Build mkUserGuidePart with stage-0 >--------------------------------------------------------------- b7948dd53ed2fd905c2f9dda6d30ae5280c9fd6f src/Builder.hs | 8 ++++++-- src/GHC.hs | 5 ++++- src/Rules.hs | 8 +++++++- src/Settings/Default.hs | 4 ++-- 4 files changed, 19 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 01:10:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add links to Hadrian paper and talk (2a20ce5) Message-ID: <20171027011037.EB05A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2a20ce5d54ddf43bebb63cee31e7fea363a931e5/ghc >--------------------------------------------------------------- commit 2a20ce5d54ddf43bebb63cee31e7fea363a931e5 Author: Andrey Mokhov Date: Sun Oct 16 00:37:26 2016 +0100 Add links to Hadrian paper and talk >--------------------------------------------------------------- 2a20ce5d54ddf43bebb63cee31e7fea363a931e5 README.md | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/README.md b/README.md index c39071e..01132cd 100644 --- a/README.md +++ b/README.md @@ -5,9 +5,9 @@ Hadrian Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current -[`make`-based build system][make]. If you are curious about the rationale and initial -ideas behind the project you can find more details on the [wiki page][ghc-shake-wiki] -and in this [blog post][blog-post-1]. This project was formerly known as *Shaking-up-GHC*. +[`make`-based build system][make]. If you are curious about the rationale behind the +project and the architecture of the new build system you can find more details in +this [Haskell Symposium 2016 paper][paper] and this [Haskell eXchange 2016 talk][talk]. The new build system can work side-by-side with the existing build system. Note, there is some interaction between them: they put (some) build results in the same directories, @@ -154,8 +154,8 @@ helped me endure and enjoy the project. [ghc]: https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler [shake]: https://github.com/ndmitchell/shake/blob/master/README.md [make]: https://ghc.haskell.org/trac/ghc/wiki/Building/Architecture -[ghc-shake-wiki]: https://ghc.haskell.org/trac/ghc/wiki/Building/Shake -[blog-post-1]: https://blogs.ncl.ac.uk/andreymokhov/shaking-up-ghc +[paper]: https://www.staff.ncl.ac.uk/andrey.mokhov/Hadrian.pdf +[talk]: https://skillsmatter.com/skillscasts/8722-meet-hadrian-a-new-build-system-for-ghc [issues]: https://github.com/snowleopard/hadrian/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild From git at git.haskell.org Fri Oct 27 01:10:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Whitespace only (325db89) Message-ID: <20171027011041.A31D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/325db89df96215ee0897187972197372e2ef34b9/ghc >--------------------------------------------------------------- commit 325db89df96215ee0897187972197372e2ef34b9 Author: Andrey Mokhov Date: Sun Oct 16 00:45:17 2016 +0100 Whitespace only >--------------------------------------------------------------- 325db89df96215ee0897187972197372e2ef34b9 src/Oracles/PackageData.hs | 68 +++++++++++++++++++++++----------------------- 1 file changed, 34 insertions(+), 34 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 84d552f..55ea812 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -13,23 +13,23 @@ data PackageData = BuildGhciLib FilePath | Synopsis FilePath | Version FilePath -data PackageDataList = CcArgs FilePath - | CSrcs FilePath - | CppArgs FilePath - | DepCcArgs FilePath - | DepExtraLibs FilePath - | DepIds FilePath - | DepIncludeDirs FilePath - | DepLdArgs FilePath - | DepLibDirs FilePath - | DepNames FilePath - | Deps FilePath - | HiddenModules FilePath - | HsArgs FilePath - | IncludeDirs FilePath - | LdArgs FilePath - | Modules FilePath - | SrcDirs FilePath +data PackageDataList = CcArgs FilePath + | CSrcs FilePath + | CppArgs FilePath + | DepCcArgs FilePath + | DepExtraLibs FilePath + | DepIds FilePath + | DepIncludeDirs FilePath + | DepLdArgs FilePath + | DepLibDirs FilePath + | DepNames FilePath + | Deps FilePath + | HiddenModules FilePath + | HsArgs FilePath + | IncludeDirs FilePath + | LdArgs FilePath + | Modules FilePath + | SrcDirs FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -55,23 +55,23 @@ pkgData packageData = case packageData of -- @pkgListData Modules@ therefore returns ["Data.Array", "Data.Array.Base", ...] pkgDataList :: PackageDataList -> Action [String] pkgDataList packageData = fmap (map unquote . words) $ case packageData of - CcArgs path -> askPackageData path "CC_OPTS" - CSrcs path -> askPackageData path "C_SRCS" - CppArgs path -> askPackageData path "CPP_OPTS" - DepCcArgs path -> askPackageData path "DEP_CC_OPTS" - DepExtraLibs path -> askPackageData path "DEP_EXTRA_LIBS" - DepIds path -> askPackageData path "DEP_IPIDS" - DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" - DepLibDirs path -> askPackageData path "DEP_LIB_DIRS_SINGLE_QUOTED" - DepLdArgs path -> askPackageData path "DEP_LD_OPTS" - DepNames path -> askPackageData path "DEP_NAMES" - Deps path -> askPackageData path "DEPS" - HiddenModules path -> askPackageData path "HIDDEN_MODULES" - HsArgs path -> askPackageData path "HC_OPTS" - IncludeDirs path -> askPackageData path "INCLUDE_DIRS" - LdArgs path -> askPackageData path "LD_OPTS" - Modules path -> askPackageData path "MODULES" - SrcDirs path -> askPackageData path "HS_SRC_DIRS" + CcArgs path -> askPackageData path "CC_OPTS" + CSrcs path -> askPackageData path "C_SRCS" + CppArgs path -> askPackageData path "CPP_OPTS" + DepCcArgs path -> askPackageData path "DEP_CC_OPTS" + DepExtraLibs path -> askPackageData path "DEP_EXTRA_LIBS" + DepIds path -> askPackageData path "DEP_IPIDS" + DepIncludeDirs path -> askPackageData path "DEP_INCLUDE_DIRS_SINGLE_QUOTED" + DepLibDirs path -> askPackageData path "DEP_LIB_DIRS_SINGLE_QUOTED" + DepLdArgs path -> askPackageData path "DEP_LD_OPTS" + DepNames path -> askPackageData path "DEP_NAMES" + Deps path -> askPackageData path "DEPS" + HiddenModules path -> askPackageData path "HIDDEN_MODULES" + HsArgs path -> askPackageData path "HC_OPTS" + IncludeDirs path -> askPackageData path "INCLUDE_DIRS" + LdArgs path -> askPackageData path "LD_OPTS" + Modules path -> askPackageData path "MODULES" + SrcDirs path -> askPackageData path "HS_SRC_DIRS" where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') From git at git.haskell.org Fri Oct 27 01:10:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove old issues (a20d473) Message-ID: <20171027011045.B85903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a20d4738dad9c0f45f4f01e7722ee4027cfab398/ghc >--------------------------------------------------------------- commit a20d4738dad9c0f45f4f01e7722ee4027cfab398 Author: Andrey Mokhov Date: Tue Oct 18 16:14:16 2016 +0100 Remove old issues >--------------------------------------------------------------- a20d4738dad9c0f45f4f01e7722ee4027cfab398 README.md | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 01132cd..7aa4b67 100644 --- a/README.md +++ b/README.md @@ -135,11 +135,11 @@ How to contribute ----------------- The best way to contribute is to try the new build system, report the issues -you found, and attempt to fix them. Please note the codebase is very unstable -at present and we expect a lot of further refactoring. The documentation is -currently non-existent, but we are working on it: [#55][comments-issue], -[#56][doc-issue]. See also [#239](https://github.com/snowleopard/hadrian/issues/239) -for a list of issues on the critical path. +you found, and attempt to fix them. Please note: the codebase is very unstable +at present and we expect a lot of further refactoring. If you would like to +work on a particular issue, please let everyone know by adding a comment about +this. The issues that are currently on the critical path are listed in +[#239](https://github.com/snowleopard/hadrian/issues/239). Acknowledgements ---------------- @@ -169,6 +169,4 @@ helped me endure and enjoy the project. [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 [milestones]: https://github.com/snowleopard/hadrian/milestones -[comments-issue]: https://github.com/snowleopard/hadrian/issues/55 -[doc-issue]: https://github.com/snowleopard/hadrian/issues/56 [contributors]: https://github.com/snowleopard/hadrian/graphs/contributors From git at git.haskell.org Fri Oct 27 01:10:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (2d60196) Message-ID: <20171027011049.82D3B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2d60196c8661bf75324525b2db37f35ccba76aa4/ghc >--------------------------------------------------------------- commit 2d60196c8661bf75324525b2db37f35ccba76aa4 Author: Andrey Mokhov Date: Tue Oct 18 16:15:58 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- 2d60196c8661bf75324525b2db37f35ccba76aa4 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 7aa4b67..ee3df66 100644 --- a/README.md +++ b/README.md @@ -138,8 +138,8 @@ The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note: the codebase is very unstable at present and we expect a lot of further refactoring. If you would like to work on a particular issue, please let everyone know by adding a comment about -this. The issues that are currently on the critical path are listed in -[#239](https://github.com/snowleopard/hadrian/issues/239). +this. The issues that are currently on the critical path and therefore require +particular attention are listed in [#239](https://github.com/snowleopard/hadrian/issues/239). Acknowledgements ---------------- From git at git.haskell.org Fri Oct 27 01:10:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify package database directory tracking (3e37d73) Message-ID: <20171027011053.1D1493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3e37d7350458218964134a981125a19f095de63a/ghc >--------------------------------------------------------------- commit 3e37d7350458218964134a981125a19f095de63a Author: Andrey Mokhov Date: Tue Oct 18 23:03:50 2016 +0100 Simplify package database directory tracking >--------------------------------------------------------------- 3e37d7350458218964134a981125a19f095de63a hadrian.cabal | 1 - src/Oracles/PackageDatabase.hs | 23 ----------------------- src/Rules/Oracles.hs | 2 -- src/Rules/Register.hs | 22 +++++++++++++++------- src/Settings/Builders/GhcCabal.hs | 11 ++--------- src/Settings/Paths.hs | 6 +++++- 6 files changed, 22 insertions(+), 43 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 3e34b16..6039b01 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -35,7 +35,6 @@ executable hadrian , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData - , Oracles.PackageDatabase , Oracles.WindowsPath , Package , Predicate diff --git a/src/Oracles/PackageDatabase.hs b/src/Oracles/PackageDatabase.hs deleted file mode 100644 index efaf9ca..0000000 --- a/src/Oracles/PackageDatabase.hs +++ /dev/null @@ -1,23 +0,0 @@ -module Oracles.PackageDatabase (packageDatabaseOracle) where - -import qualified System.Directory as IO - -import Base -import Context -import Builder -import GHC -import Rules.Actions -import Settings.Builders.GhcCabal -import Settings.Paths -import Target -import UserSettings - -packageDatabaseOracle :: Rules () -packageDatabaseOracle = void $ - addOracle $ \(PackageDatabaseKey stage) -> do - let dir = packageDbDirectory stage - file = dir -/- "package.cache" - unlessM (liftIO $ IO.doesFileExist file) $ do - removeDirectory dir - build $ Target (vanillaContext stage ghcPkg) (GhcPkg stage) [] [dir] - putSuccess $ "| Successfully initialised " ++ dir diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 10767b5..af03b17 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -8,7 +8,6 @@ import qualified Oracles.DirectoryContent import qualified Oracles.LookupInPath import qualified Oracles.ModuleFiles import qualified Oracles.PackageData -import qualified Oracles.PackageDatabase import qualified Oracles.WindowsPath oracleRules :: Rules () @@ -20,5 +19,4 @@ oracleRules = do Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle - Oracles.PackageDatabase.packageDatabaseOracle Oracles.WindowsPath.windowsPathOracle diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 272e27b..d4799e3 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -9,20 +9,22 @@ import Rules.Libffi import Settings.Packages.Rts import Settings.Paths import Target +import UserSettings --- | Build package-data.mk by processing the .cabal file with ghc-cabal utility. +-- | Build rules for registering packages and initialising package databases +-- by running the @ghc-pkg@ utility. registerPackage :: [(Resource, Int)] -> Context -> Rules () -registerPackage rs context at Context {..} = do - let path = buildPath context - oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 - pkgConf = packageDbDirectory stage -/- pkgNameString package +registerPackage rs context at Context {..} = when (stage <= Stage1) $ do + let dir = packageDbDirectory stage - when (stage <= Stage1) $ matchVersionedFilePath pkgConf "conf" ?> \conf -> do + matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do -- This produces inplace-pkg-config. TODO: Add explicit tracking. need [pkgDataFile context] -- Post-process inplace-pkg-config. TODO: remove, see #113, #148. - let pkgConfig = oldPath -/- "inplace-pkg-config" + let path = buildPath context + oldPath = pkgPath package -/- contextDirectory context + pkgConfig = oldPath -/- "inplace-pkg-config" oldBuildPath = oldPath -/- "build" fixPkgConf = unlines . map @@ -52,3 +54,9 @@ registerPackage rs context at Context {..} = do . lines fixFile rtsConf fixRtsConf + + when (package == ghc) $ packageDbStamp stage %> \stamp -> do + removeDirectory dir + buildWithResources rs $ Target (vanillaContext stage ghc) (GhcPkg stage) [] [dir] + writeFileLines stamp [] + putSuccess $ "| Successfully initialised " ++ dir diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index fffb2c0..5569ba0 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,7 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( - ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, - PackageDatabaseKey (..), buildDll0 + ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, buildDll0 ) where import Base @@ -87,16 +86,10 @@ configureArgs = do , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" $ argStagedBuilderPath (Cc CompileC) ] -newtype PackageDatabaseKey = PackageDatabaseKey Stage - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -initialisePackageDatabase :: Stage -> Action () -initialisePackageDatabase = askOracle . PackageDatabaseKey - bootPackageDatabaseArgs :: Args bootPackageDatabaseArgs = do stage <- getStage - lift $ initialisePackageDatabase stage + lift $ need [packageDbStamp stage] stage0 ? do path <- getTopDirectory prefix <- ifM (builder Ghc) (return "-package-db ") (return "--package-db=") diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index ad200f8..6382fcc 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -2,7 +2,7 @@ module Settings.Paths ( contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, - packageDbDirectory, bootPackageConstraints, packageDependencies + packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies ) where import Base @@ -92,6 +92,10 @@ packageDbDirectory :: Stage -> FilePath packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" +-- | We use a stamp file to track the existence of a package database. +packageDbStamp :: Stage -> FilePath +packageDbStamp stage = packageDbDirectory stage -/- ".stamp" + -- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do From git at git.haskell.org Fri Oct 27 01:10:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:10:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop unused extension (0d8713a) Message-ID: <20171027011056.D2F493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0d8713a49c11732343f0a8b3d098ace401778acf/ghc >--------------------------------------------------------------- commit 0d8713a49c11732343f0a8b3d098ace401778acf Author: Andrey Mokhov Date: Tue Oct 18 23:21:24 2016 +0100 Drop unused extension >--------------------------------------------------------------- 0d8713a49c11732343f0a8b3d098ace401778acf src/Settings/Builders/GhcCabal.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 5569ba0..535454e 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, buildDll0 ) where From git at git.haskell.org Fri Oct 27 01:11:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (a0afb98) Message-ID: <20171027011100.509633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a0afb987569ba2ac617b1bcd035f124c93463da3/ghc >--------------------------------------------------------------- commit a0afb987569ba2ac617b1bcd035f124c93463da3 Author: Andrey Mokhov Date: Wed Oct 19 00:03:58 2016 +0100 Minor revision >--------------------------------------------------------------- a0afb987569ba2ac617b1bcd035f124c93463da3 src/Expression.hs | 4 ++-- src/Rules/Gmp.hs | 11 ++++------- src/Rules/Libffi.hs | 10 +++------- src/Rules/Library.hs | 4 ++-- 4 files changed, 11 insertions(+), 18 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 114bfe4..a572c2c 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -16,7 +16,7 @@ module Expression ( -- * Convenient accessors getContext, getStage, getPackage, getBuilder, getOutputs, getInputs, getWay, - getInput, getOutput, + getInput, getOutput, getSingleton, -- * Re-exports module Control.Monad.Trans.Reader, @@ -206,7 +206,7 @@ getOutput = do getSingleton getOutputs $ "getOutput: exactly one output file expected in target " ++ show target -getSingleton :: Expr [a] -> String -> Expr a +getSingleton :: Monad m => m [a] -> String -> m a getSingleton expr msg = expr >>= \case [res] -> return res _ -> error msg diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 50c548b..3693ad4 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,4 +1,4 @@ -module Rules.Gmp (gmpRules, gmpContext) where +module Rules.Gmp (gmpRules) where import Base import Builder @@ -81,12 +81,9 @@ gmpRules = do -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. - tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "gmpRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - + let tarballs = gmpBase -/- "tarball/gmp*.tar.bz2" + tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) + "Exactly one GMP tarball is expected." withTempDir $ \dir -> do let tmp = unifyPath dir need [tarball] diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 5ca17ea..6dd92bc 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -80,13 +80,9 @@ libffiRules = do libffiMakefile <.> "in" %> \mkIn -> do removeDirectory libffiBuildPath createDirectory $ buildRootPath -/- stageString Stage0 - - tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] - tarball <- case tarballs of -- TODO: Drop code duplication. - [file] -> return $ unifyPath file - _ -> error $ "libffiRules: exactly one tarball expected" - ++ "(found: " ++ show tarballs ++ ")." - + let tarballs = "libffi-tarballs/libffi*.tar.gz" + tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) + "Exactly one LibFFI tarball is expected." need [tarball] let libname = dropExtension . dropExtension $ takeFileName tarball diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 00a6be2..731bb7b 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -9,9 +9,9 @@ import Base import Context import Expression import Flavour +import GHC import Oracles.PackageData import Rules.Actions -import Rules.Gmp import Settings import Settings.Paths import Target @@ -96,7 +96,7 @@ hSources context = do extraObjects :: Context -> Action [FilePath] extraObjects context - | context == gmpContext = do + | package context == integerGmp = do need [gmpLibraryH] map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Fri Oct 27 01:11:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify getSingleton, add comments (fbe22e6) Message-ID: <20171027011103.D1BBC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fbe22e6f83bb5e9f14960b63f1ad40dbbfdd7c86/ghc >--------------------------------------------------------------- commit fbe22e6f83bb5e9f14960b63f1ad40dbbfdd7c86 Author: Andrey Mokhov Date: Wed Oct 19 00:25:01 2016 +0100 Simplify getSingleton, add comments >--------------------------------------------------------------- fbe22e6f83bb5e9f14960b63f1ad40dbbfdd7c86 src/Expression.hs | 19 ++++++++++--------- src/Rules/Gmp.hs | 6 +++--- src/Rules/Libffi.hs | 6 +++--- 3 files changed, 16 insertions(+), 15 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index a572c2c..45967c9 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -192,8 +192,8 @@ getInputs = asks inputs getInput :: Expr FilePath getInput = do target <- ask - getSingleton getInputs $ - "getInput: exactly one input file expected in target " ++ show target + getSingleton ("Exactly one input file expected in " ++ show target) + <$> getInputs -- | Get the files produced by the current 'Target'. getOutputs :: Expr [FilePath] @@ -203,10 +203,11 @@ getOutputs = asks outputs getOutput :: Expr FilePath getOutput = do target <- ask - getSingleton getOutputs $ - "getOutput: exactly one output file expected in target " ++ show target - -getSingleton :: Monad m => m [a] -> String -> m a -getSingleton expr msg = expr >>= \case - [res] -> return res - _ -> error msg + getSingleton ("Exactly one output file expected in " ++ show target) + <$> getOutputs + +-- | Extract a value from a singleton list, or raise an error if the list does +-- not contain exactly one value. +getSingleton :: String -> [a] -> a +getSingleton _ [res] = res +getSingleton msg _ = error msg diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 3693ad4..412bea0 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -81,9 +81,9 @@ gmpRules = do -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents. -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. - let tarballs = gmpBase -/- "tarball/gmp*.tar.bz2" - tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) - "Exactly one GMP tarball is expected." + tarball <- unifyPath . getSingleton "Exactly one GMP tarball is expected" + <$> getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] + withTempDir $ \dir -> do let tmp = unifyPath dir need [tarball] diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 6dd92bc..9560dbf 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -80,9 +80,9 @@ libffiRules = do libffiMakefile <.> "in" %> \mkIn -> do removeDirectory libffiBuildPath createDirectory $ buildRootPath -/- stageString Stage0 - let tarballs = "libffi-tarballs/libffi*.tar.gz" - tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs]) - "Exactly one LibFFI tarball is expected." + tarball <- unifyPath . getSingleton "Exactly one LibFFI tarball is expected" + <$> getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] + need [tarball] let libname = dropExtension . dropExtension $ takeFileName tarball From git at git.haskell.org Fri Oct 27 01:11:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Split compilation of Haskell and non-Haskell files (b61423d) Message-ID: <20171027011107.67BF73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b61423dfdb36c96a902f26b14c07e6bc39621a94/ghc >--------------------------------------------------------------- commit b61423dfdb36c96a902f26b14c07e6bc39621a94 Author: Andrey Mokhov Date: Thu Oct 20 02:44:02 2016 +0100 Split compilation of Haskell and non-Haskell files See #216, #264, #267. >--------------------------------------------------------------- b61423dfdb36c96a902f26b14c07e6bc39621a94 src/Oracles/Dependencies.hs | 5 ++- src/Oracles/PackageData.hs | 6 +++- src/Rules/Compile.hs | 58 ++++++++++++++++---------------- src/Rules/Data.hs | 17 +++++----- src/Rules/Dependencies.hs | 77 ++++++++++--------------------------------- src/Rules/Generate.hs | 17 +++++++--- src/Rules/Library.hs | 80 ++++++++++++++++++++++++++++----------------- src/Rules/Program.hs | 12 +++---- 8 files changed, 132 insertions(+), 140 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 b61423dfdb36c96a902f26b14c07e6bc39621a94 From git at git.haskell.org Fri Oct 27 01:11:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor discovery of generated dependencies (bb43f24) Message-ID: <20171027011110.CB5C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bb43f249ba63559f988fedac9b5180bfdc28d1cf/ghc >--------------------------------------------------------------- commit bb43f249ba63559f988fedac9b5180bfdc28d1cf Author: Andrey Mokhov Date: Fri Oct 21 01:30:10 2016 +0100 Refactor discovery of generated dependencies See #285, #267. >--------------------------------------------------------------- bb43f249ba63559f988fedac9b5180bfdc28d1cf src/Builder.hs | 8 ++---- src/Rules/Compile.hs | 59 +++++++++++++++++++++++---------------------- src/Rules/Generate.hs | 17 +------------ src/Settings/Builders/Cc.hs | 12 ++------- 4 files changed, 35 insertions(+), 61 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 09b87cb..860034e 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -20,12 +20,8 @@ import Stage -- 1) Compiling sources into object files. -- 2) Extracting source dependencies, e.g. by passing -M command line argument. -- 3) Linking object files & static libraries into an executable. --- We have CcMode for CC and GhcMode for GHC. - --- TODO: Consider merging FindCDependencies and FindMissingInclude -data CcMode = CompileC | FindCDependencies | FindMissingInclude - deriving (Eq, Generic, Show) - +-- We have CcMode for C compiler and GhcMode for GHC. +data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show) data GhcMode = CompileHs | FindHsDependencies | LinkHs deriving (Eq, Generic, Show) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 535758c..285abe0 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -1,5 +1,7 @@ module Rules.Compile (compilePackage) where +import Development.Shake.Util + import Base import Context import Expression @@ -9,21 +11,14 @@ import Rules.Generate import Settings.Paths import Target -import Development.Shake.Util - -import qualified Data.Set as Set - compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context nonHs extension = path extension "*" <.> osuf way compile compiler obj2src obj = do - let depFile = obj -<.> "d" - src = obj2src context obj + let src = obj2src context obj need [src] - needGenerated context src - build $ Target context (Cc FindCDependencies stage) [src] [depFile] - needMakefileDependencies depFile -- TODO: Is this actually needed? + needDependencies context src $ obj <.> "d" build $ Target context (compiler stage) [src] [obj] compileHs = \[obj, _] -> do (src, deps) <- fileDependencies context obj @@ -41,28 +36,27 @@ compilePackage rs context at Context {..} = do [ path "*" <.> suf way | suf <- [ osuf, hisuf] ] &%> compileHs [ path "*" <.> suf way | suf <- [obootsuf, hibootsuf] ] &%> compileHs --- TODO: Simplify. -needGenerated :: Context -> FilePath -> Action () -needGenerated context origFile = go Set.empty +-- | Discover dependencies of a given source file by iteratively calling @gcc@ +-- in the @-MM -MG@ mode and building generated dependencies if they are missing +-- until reaching a fixed point. +needDependencies :: Context -> FilePath -> FilePath -> Action () +needDependencies context at Context {..} src depFile = discover where - go :: Set.Set String -> Action () - go done = withTempFile $ \outFile -> do - let builder = Cc FindMissingInclude $ stage context - target = Target context builder [origFile] [outFile] - build target - deps <- parseFile outFile - - -- Get the full path if the include refers to a generated file and call - -- `need` on it. - needed <- liftM catMaybes $ - interpretInContext context (mapM getPathIfGenerated deps) - need needed + discover = do + build $ Target context (Cc FindCDependencies stage) [src] [depFile] + deps <- parseFile depFile + -- Generated dependencies, if not yet built, will not be found and hence + -- will be referred to simply by their file names. + let notFound = filter (\file -> file == takeFileName file) deps + -- We find the full paths to generated dependencies, so we can request + -- to build them by calling 'need'. + todo <- catMaybes <$> mapM (fullPathIfGenerated context) notFound - let newdone = Set.fromList needed `Set.union` done - -- If we added a new file to the set of needed files, let's try one more - -- time, since the new file might include a genreated header of itself - -- (which we'll `need`). - when (Set.size newdone > Set.size done) (go newdone) + if null todo + then need deps -- The list of dependencies is final, need all + else do + need todo -- Build newly discovered generated dependencies + discover -- Continue the discovery process parseFile :: FilePath -> Action [String] parseFile file = do @@ -71,6 +65,13 @@ needGenerated context origFile = go Set.empty [(_file, deps)] -> return deps _ -> return [] +-- | Find a given 'FilePath' in the list of generated files in the given +-- 'Context' and return its full path. +fullPathIfGenerated :: Context -> FilePath -> Action (Maybe FilePath) +fullPathIfGenerated context file = interpretInContext context $ do + generated <- generatedDependencies + return $ find ((== file) . takeFileName) generated + obj2src :: String -> (FilePath -> Bool) -> Context -> FilePath -> FilePath obj2src extension isGenerated context at Context {..} obj | isGenerated src = src diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index ceeb182..bfede1a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,7 +1,6 @@ module Rules.Generate ( isGeneratedCFile, isGeneratedCmmFile, generatePackageCode, generateRules, - installTargets, copyRules, includesDependencies, generatedDependencies, - getPathIfGenerated + installTargets, copyRules, includesDependencies, generatedDependencies ) where import qualified System.Directory as IO @@ -199,17 +198,3 @@ generateRules = do emptyTarget :: Context emptyTarget = vanillaContext (error "Rules.Generate.emptyTarget: unknown stage") (error "Rules.Generate.emptyTarget: unknown package") - -getPathIfGenerated :: FilePath -> Expr (Maybe FilePath) -getPathIfGenerated include = do - generated <- generatedFiles - -- For includes of generated files, we cannot get the full path of the file - -- (since it might be included due to some include dir, i.e., through `-I`). - -- So here we try both the name and the path. - let nameOrPath (name, path) = include == name || include == path - return . fmap snd $ find nameOrPath generated - -generatedFiles :: Expr [(FilePath, FilePath)] -generatedFiles = do - deps <- generatedDependencies - return [ (takeFileName fp, fp) | fp <- deps ] diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index 41a8466..595feab 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -21,19 +21,11 @@ ccBuilderArgs = builder Cc ? mconcat output <- getOutput mconcat [ arg "-E" , arg "-MM" + , arg "-MG" , arg "-MF" , arg output , arg "-MT" , arg $ dropExtension output -<.> "o" , arg "-x" , arg "c" - , arg =<< getInput ] - - , builder (Cc FindMissingInclude) ? - mconcat [ arg "-E" - , arg "-MM" - , arg "-MG" - , arg "-MF" - , arg =<< getOutput - , arg =<< getInput ] - ] + , arg =<< getInput ] ] From git at git.haskell.org Fri Oct 27 01:11:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify, drop code duplication, add comments (ffff1b3) Message-ID: <20171027011114.44FA23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffff1b38a54fcf55e4a809cc6c403a60016d1492/ghc >--------------------------------------------------------------- commit ffff1b38a54fcf55e4a809cc6c403a60016d1492 Author: Andrey Mokhov Date: Sat Oct 22 00:47:53 2016 +0100 Simplify, drop code duplication, add comments >--------------------------------------------------------------- ffff1b38a54fcf55e4a809cc6c403a60016d1492 src/Oracles/ModuleFiles.hs | 21 +++++++--- src/Rules/Compile.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 4 +- src/Rules/Library.hs | 99 ++++++++++++---------------------------------- src/Rules/Program.hs | 45 +++++++++------------ src/Settings/Paths.hs | 29 +++++++++++++- 7 files changed, 92 insertions(+), 110 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 ffff1b38a54fcf55e4a809cc6c403a60016d1492 From git at git.haskell.org Fri Oct 27 01:11:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix Travis MacOSX instance (c391fea) Message-ID: <20171027011117.C13613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c391feaa87a406da4f19e3384b0329fb086d8268/ghc >--------------------------------------------------------------- commit c391feaa87a406da4f19e3384b0329fb086d8268 Author: Andrey Mokhov Date: Sat Oct 22 01:39:25 2016 +0100 Attempt to fix Travis MacOSX instance >--------------------------------------------------------------- c391feaa87a406da4f19e3384b0329fb086d8268 .travis.yml | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0209cab..217a7d5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -39,13 +39,17 @@ install: - mv .git ghc/hadrian - cd ghc/hadrian - git reset --hard HEAD + - cd .. + - ./boot + - ./configure + - cd hadrian script: # Run internal Hadrian tests - ./build.sh selftest # Build GHC - - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.sh -j --skip-configure --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 01:11:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use nm-classic when running on Travis (90e3e97) Message-ID: <20171027011121.4B97E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90e3e973e62788d98d47fc3942ecd8c50e7fe92b/ghc >--------------------------------------------------------------- commit 90e3e973e62788d98d47fc3942ecd8c50e7fe92b Author: Andrey Mokhov Date: Sat Oct 22 01:48:38 2016 +0100 Use nm-classic when running on Travis >--------------------------------------------------------------- 90e3e973e62788d98d47fc3942ecd8c50e7fe92b .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 217a7d5..187c009 100644 --- a/.travis.yml +++ b/.travis.yml @@ -41,7 +41,7 @@ install: - git reset --hard HEAD - cd .. - ./boot - - ./configure + - ./configure --with-nm=$(xcrun --find nm-classic) - cd hadrian script: From git at git.haskell.org Fri Oct 27 01:11:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #276 from wereHamster/osx-use-nm-classic (99404de) Message-ID: <20171027011124.CAA823A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/99404defcfbec85ff25963f480e64c26adcb9f16/ghc >--------------------------------------------------------------- commit 99404defcfbec85ff25963f480e64c26adcb9f16 Merge: 90e3e97 3c31edc Author: Andrey Mokhov Date: Sat Oct 22 02:02:32 2016 +0100 Merge pull request #276 from wereHamster/osx-use-nm-classic Use nm-classic instead of nm when host is Darwin >--------------------------------------------------------------- 99404defcfbec85ff25963f480e64c26adcb9f16 README.md | 8 -------- src/Settings/Builders/Configure.hs | 7 +++++++ 2 files changed, 7 insertions(+), 8 deletions(-) From git at git.haskell.org Fri Oct 27 01:11:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert to running the configure script from Hadrian (4378fcf) Message-ID: <20171027011128.3B6CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4378fcfe96fc58328bb03378f45529e6d13a7122/ghc >--------------------------------------------------------------- commit 4378fcfe96fc58328bb03378f45529e6d13a7122 Author: Andrey Mokhov Date: Sat Oct 22 02:06:18 2016 +0100 Revert to running the configure script from Hadrian See #276. >--------------------------------------------------------------- 4378fcfe96fc58328bb03378f45529e6d13a7122 .travis.yml | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 187c009..0209cab 100644 --- a/.travis.yml +++ b/.travis.yml @@ -39,17 +39,13 @@ install: - mv .git ghc/hadrian - cd ghc/hadrian - git reset --hard HEAD - - cd .. - - ./boot - - ./configure --with-nm=$(xcrun --find nm-classic) - - cd hadrian script: # Run internal Hadrian tests - ./build.sh selftest # Build GHC - - ./build.sh -j --skip-configure --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 01:11:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix typo (2895999) Message-ID: <20171027011131.BA0CF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2895999d7ac18fe9f90e6f6feb47c4e71a84202f/ghc >--------------------------------------------------------------- commit 2895999d7ac18fe9f90e6f6feb47c4e71a84202f Author: Andrey Mokhov Date: Sat Oct 22 11:27:01 2016 +0100 Fix typo >--------------------------------------------------------------- 2895999d7ac18fe9f90e6f6feb47c4e71a84202f src/Settings/Builders/Configure.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 6482df1..deab649 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -26,8 +26,7 @@ configureBuilderArgs = mconcat , "--enable-shared=no" -- TODO: add support for yes , "--host=" ++ targetPlatform ] - -- On OS X, use "nm-classic" instead of "nm" due to a bug in the later. + -- On OS X, use "nm-classic" instead of "nm" due to a bug in the latter. -- See https://ghc.haskell.org/trac/ghc/ticket/11744 , builder (Configure ".") ? System.os == "darwin" ? - arg "--with-nm=$(xcrun --find nm-classic)" - ] + arg "--with-nm=$(xcrun --find nm-classic)" ] From git at git.haskell.org Fri Oct 27 01:11:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move package.conf.inplace to build directory (038dfb4) Message-ID: <20171027011135.2BBDF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/038dfb43604a5316e0b44f745e9367a09fb6a217/ghc >--------------------------------------------------------------- commit 038dfb43604a5316e0b44f745e9367a09fb6a217 Author: Andrey Mokhov Date: Sat Oct 22 23:47:39 2016 +0100 Move package.conf.inplace to build directory >--------------------------------------------------------------- 038dfb43604a5316e0b44f745e9367a09fb6a217 src/Settings/Packages/Rts.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index f3f2e43..f2b4035 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -9,13 +9,13 @@ import Oracles.Config.Setting import Oracles.WindowsPath import Predicate import Settings +import Settings.Paths rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" --- TODO: move to buildRootPath, see #113 rtsConf :: FilePath -rtsConf = pkgPath rts -/- contextDirectory rtsContext -/- "package.conf.inplace" +rtsConf = buildPath rtsContext -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do From git at git.haskell.org Fri Oct 27 01:11:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify (f52e582) Message-ID: <20171027011139.E0B413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f52e582d9cc21ad369411dc7bc832332e97ff224/ghc >--------------------------------------------------------------- commit f52e582d9cc21ad369411dc7bc832332e97ff224 Author: Andrey Mokhov Date: Sun Oct 23 00:41:23 2016 +0100 Simplify See #265 >--------------------------------------------------------------- f52e582d9cc21ad369411dc7bc832332e97ff224 src/Oracles/DirectoryContent.hs | 41 ++++++++++++++++++----------------------- src/Rules/Actions.hs | 13 ++++++------- 2 files changed, 24 insertions(+), 30 deletions(-) diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContent.hs index 45afa92..3139c6c 100644 --- a/src/Oracles/DirectoryContent.hs +++ b/src/Oracles/DirectoryContent.hs @@ -1,39 +1,34 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} module Oracles.DirectoryContent ( - getDirectoryContent, directoryContentOracle, Match(..) + directoryContent, directoryContentOracle, Match (..) ) where -import Base -import GHC.Generics import System.Directory.Extra +import GHC.Generics + +import Base newtype DirectoryContent = DirectoryContent (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -data Match = Test FilePattern | Not (Match) | And [Match] | Or [Match] +data Match = Test FilePattern | Not Match | And [Match] | Or [Match] deriving (Generic, Eq, Show, Typeable) -instance Binary Match -instance Hashable Match -instance NFData Match matches :: Match -> FilePath -> Bool -matches (Test m) f = m ?== f -matches (Not m) f = not $ matches m f -matches (And []) _ = True -matches (And (m:ms)) f | matches m f = matches (And ms) f - | otherwise = False -matches (Or []) _ = False -matches (Or (m:ms)) f | matches m f = True - | otherwise = matches (Or ms) f +matches (Test p) f = p ?== f +matches (Not m) f = not $ matches m f +matches (And ms) f = all (`matches` f) ms +matches (Or ms) f = any (`matches` f) ms -- | Get the directory content recursively. -getDirectoryContent :: Match -> FilePath -> Action [FilePath] -getDirectoryContent expr dir = - askOracle $ DirectoryContent (expr, dir) +directoryContent :: Match -> FilePath -> Action [FilePath] +directoryContent expr dir = askOracle $ DirectoryContent (expr, dir) directoryContentOracle :: Rules () -directoryContentOracle = void $ addOracle oracle - where - oracle :: DirectoryContent -> Action [FilePath] - oracle (DirectoryContent (expr, dir)) = - liftIO $ filter (matches expr) <$> listFilesInside (return . matches expr) dir +directoryContentOracle = void $ + addOracle $ \(DirectoryContent (expr, dir)) -> liftIO $ + filter (matches expr) <$> listFilesInside (return . matches expr) dir + +instance Binary Match +instance Hashable Match +instance NFData Match diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index e30bc01..cccda24 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -45,8 +45,7 @@ customBuild rs opts target at Target {..} = do argList <- interpret target getArgs verbose <- interpret target verboseCommands let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly - -- The line below forces the rule to be rerun if the args hash has changed. - checkArgsHash target + checkArgsHash target -- Rerun the rule if the hash of argList has changed. withResources rs $ do putInfo target quietlyUnlessVerbose $ case builder of @@ -133,12 +132,12 @@ copyDirectory source target = do copyDirectoryContent :: Match -> FilePath -> FilePath -> Action () copyDirectoryContent expr source target = do putProgressInfo $ renderAction "Copy directory content" source target - getDirectoryContent expr source >>= mapM_ cp + mapM_ cp =<< directoryContent expr source where - cp a = do - createDirectory $ dropFileName $ target' a - copyFile a $ target' a - target' a = target -/- fromJust (stripPrefix source a) + cp file = do + let newFile = target -/- drop (length source) file + createDirectory $ dropFileName newFile -- TODO: Why do it for each file? + copyFile file newFile -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 01:11:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve code consistency, simplify, fix comments (9d13cd8) Message-ID: <20171027011143.B54D33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d13cd844b9eabbb5d826a9f518c27bb8756b390/ghc >--------------------------------------------------------------- commit 9d13cd844b9eabbb5d826a9f518c27bb8756b390 Author: Andrey Mokhov Date: Sun Oct 23 01:03:22 2016 +0100 Improve code consistency, simplify, fix comments >--------------------------------------------------------------- 9d13cd844b9eabbb5d826a9f518c27bb8756b390 src/Builder.hs | 31 ++++++++++++++----------------- src/Context.hs | 4 ++-- src/Package.hs | 4 +--- src/Rules/Cabal.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Perl.hs | 5 ++--- src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Cc.hs | 12 ++++-------- src/Settings/Builders/GenApply.hs | 1 - src/Settings/Builders/GenPrimopCode.hs | 1 - src/Settings/Builders/GhcCabal.hs | 1 - src/Settings/Builders/HsCpp.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Builders/Ld.hs | 11 +++++------ src/Settings/Builders/Tar.hs | 11 +++++------ src/Stage.hs | 3 +-- src/Target.hs | 5 ++--- src/Way.hs | 1 - 19 files changed, 43 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 9d13cd844b9eabbb5d826a9f518c27bb8756b390 From git at git.haskell.org Fri Oct 27 01:11:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports in Settings/Builders (2f74254) Message-ID: <20171027011147.320913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc/ghc >--------------------------------------------------------------- commit 2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc Author: Andrey Mokhov Date: Sun Oct 23 01:25:50 2016 +0100 Refactor imports in Settings/Builders >--------------------------------------------------------------- 2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc src/Rules/Libffi.hs | 9 --------- src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/Ar.hs | 5 +---- src/Settings/Builders/Cc.hs | 5 ----- src/Settings/Builders/Common.hs | 25 ++++++++++++++++++++++++- src/Settings/Builders/Configure.hs | 6 +----- src/Settings/Builders/DeriveConstants.hs | 5 ----- src/Settings/Builders/GenApply.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 2 +- src/Settings/Builders/Ghc.hs | 9 --------- src/Settings/Builders/GhcCabal.hs | 19 +------------------ src/Settings/Builders/GhcPkg.hs | 6 +----- src/Settings/Builders/Haddock.hs | 7 +------ src/Settings/Builders/Happy.hs | 2 +- src/Settings/Builders/HsCpp.hs | 4 ---- src/Settings/Builders/Hsc2Hs.hs | 7 ------- src/Settings/Builders/Ld.hs | 2 -- src/Settings/Builders/Make.hs | 4 +--- src/Settings/Builders/Tar.hs | 2 +- 19 files changed, 35 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 2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc From git at git.haskell.org Fri Oct 27 01:11:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix GenApply arguments (e3aedfe) Message-ID: <20171027011150.A695D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3aedfef1d68e98b59d19307203a16895ac98de6/ghc >--------------------------------------------------------------- commit e3aedfef1d68e98b59d19307203a16895ac98de6 Author: Andrey Mokhov Date: Sun Oct 23 01:58:24 2016 +0100 Fix GenApply arguments >--------------------------------------------------------------- e3aedfef1d68e98b59d19307203a16895ac98de6 src/Settings/Builders/GenApply.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/Builders/GenApply.hs b/src/Settings/Builders/GenApply.hs index 6ebb295..b268c07 100644 --- a/src/Settings/Builders/GenApply.hs +++ b/src/Settings/Builders/GenApply.hs @@ -2,6 +2,5 @@ module Settings.Builders.GenApply (genApplyBuilderArgs) where import Settings.Builders.Common --- TODO: Dead code? ifeq "$(GhcUnregisterised)" "YES" GENAPPLY_OPTS = -u genApplyBuilderArgs :: Args -genApplyBuilderArgs = mempty +genApplyBuilderArgs = builder GenApply ? flag GhcUnregisterised ? arg "-u" From git at git.haskell.org Fri Oct 27 01:11:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't generate files into the source tree (7303fcf) Message-ID: <20171027011154.388313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7303fcf142de20186728a5b7fdea62e5a8fc83d6/ghc >--------------------------------------------------------------- commit 7303fcf142de20186728a5b7fdea62e5a8fc83d6 Author: Andrey Mokhov Date: Sun Oct 23 02:27:32 2016 +0100 Don't generate files into the source tree See #113. >--------------------------------------------------------------- 7303fcf142de20186728a5b7fdea62e5a8fc83d6 src/Rules/Generate.hs | 10 ---------- 1 file changed, 10 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 0a4305c..698299d 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -143,24 +143,14 @@ generatePackageCode context@(Context stage pkg _) = build $ Target context GenApply [] [file] priority 2.0 $ do - -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- contextDirectory context -/- "build" - olden f = oldPath ++ (drop (length (buildPath context)) f) - when (pkg == compiler) $ path -/- "Config.hs" %> \file -> do file <~ generateConfigHs - olden file <~ generateConfigHs -- TODO: get rid of this (#113) when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH when (pkg == ghcPkg) $ path -/- "Version.hs" %> \file -> do file <~ generateVersionHs - olden file <~ generateVersionHs -- TODO: get rid of this (#113) - - when (pkg == runGhc) $ path -/- "Main.hs" %> \file -> do - copyFileChanged (pkgPath pkg -/- "runghc.hs") file - putSuccess $ "| Successfully generated " ++ file ++ "." copyRules :: Rules () copyRules = do From git at git.haskell.org Fri Oct 27 01:11:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:11:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build runGhc executable (b2f49f0) Message-ID: <20171027011157.AAF203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2f49f06bbcda51400711d6370d1a276f01087da/ghc >--------------------------------------------------------------- commit b2f49f06bbcda51400711d6370d1a276f01087da Author: Andrey Mokhov Date: Sun Oct 23 02:35:58 2016 +0100 Build runGhc executable >--------------------------------------------------------------- b2f49f06bbcda51400711d6370d1a276f01087da src/GHC.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/GHC.hs b/src/GHC.hs index 3521e54..7cabff5 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -114,6 +114,9 @@ programPath context at Context {..} | package == hpcBin = case stage of Stage1 -> Just $ inplaceProgram "hpc" _ -> Nothing + | package == runGhc = case stage of + Stage1 -> Just $ inplaceProgram "runhaskell" + _ -> Nothing | isProgram package = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package _ -> Just . installProgram $ pkgNameString package From git at git.haskell.org Fri Oct 27 01:12:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop GenApply arguments, as it actually needs none. (0bec73c) Message-ID: <20171027011201.3178D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0bec73c1eb86a91e15cfa8df53d14264ff854160/ghc >--------------------------------------------------------------- commit 0bec73c1eb86a91e15cfa8df53d14264ff854160 Author: Andrey Mokhov Date: Sun Oct 23 18:15:51 2016 +0100 Drop GenApply arguments, as it actually needs none. >--------------------------------------------------------------- 0bec73c1eb86a91e15cfa8df53d14264ff854160 hadrian.cabal | 1 - src/Settings/Builders/GenApply.hs | 6 ------ src/Settings/Default.hs | 2 -- 3 files changed, 9 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 6039b01..3b19557 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -74,7 +74,6 @@ executable hadrian , Settings.Builders.Cc , Settings.Builders.Configure , Settings.Builders.DeriveConstants - , Settings.Builders.GenApply , Settings.Builders.GenPrimopCode , Settings.Builders.Ghc , Settings.Builders.GhcCabal diff --git a/src/Settings/Builders/GenApply.hs b/src/Settings/Builders/GenApply.hs deleted file mode 100644 index b268c07..0000000 --- a/src/Settings/Builders/GenApply.hs +++ /dev/null @@ -1,6 +0,0 @@ -module Settings.Builders.GenApply (genApplyBuilderArgs) where - -import Settings.Builders.Common - -genApplyBuilderArgs :: Args -genApplyBuilderArgs = builder GenApply ? flag GhcUnregisterised ? arg "-u" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 4588c4b..f529019 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -16,7 +16,6 @@ import Settings.Builders.Ar import Settings.Builders.DeriveConstants import Settings.Builders.Cc import Settings.Builders.Configure -import Settings.Builders.GenApply import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc import Settings.Builders.GhcCabal @@ -52,7 +51,6 @@ defaultBuilderArgs = mconcat , ccBuilderArgs , configureBuilderArgs , deriveConstantsBuilderArgs - , genApplyBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs , ghcCabalBuilderArgs From git at git.haskell.org Fri Oct 27 01:12:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move auxiliary build files to _build/hadrian (aa6bba1) Message-ID: <20171027011204.A719F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aa6bba126fecd412920fa7ca1e90fe9716b328d0/ghc >--------------------------------------------------------------- commit aa6bba126fecd412920fa7ca1e90fe9716b328d0 Author: Andrey Mokhov Date: Sun Oct 23 19:05:51 2016 +0100 Move auxiliary build files to _build/hadrian >--------------------------------------------------------------- aa6bba126fecd412920fa7ca1e90fe9716b328d0 src/Settings/Paths.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 2727696..7147264 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -16,7 +16,7 @@ import UserSettings -- | Path to the directory containing the Shake database and other auxiliary -- files generated by Hadrian. shakeFilesPath :: FilePath -shakeFilesPath = buildRootPath -/- "hadrian/shake-files" +shakeFilesPath = buildRootPath -/- "hadrian" -- | Boot package versions extracted from @.cabal@ files. bootPackageConstraints :: FilePath From git at git.haskell.org Fri Oct 27 01:12:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build Hadrian in /hadrian/bin (179f5b1) Message-ID: <20171027011208.2C3603A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/179f5b14a138c41cd06423c17a41684157fcdb89/ghc >--------------------------------------------------------------- commit 179f5b14a138c41cd06423c17a41684157fcdb89 Author: Andrey Mokhov Date: Sun Oct 23 19:06:09 2016 +0100 Build Hadrian in /hadrian/bin >--------------------------------------------------------------- 179f5b14a138c41cd06423c17a41684157fcdb89 .gitignore | 3 +-- build.bat | 32 ++++++++++++++++---------------- build.sh | 8 ++++---- 3 files changed, 21 insertions(+), 22 deletions(-) diff --git a/.gitignore b/.gitignore index 87bedb8..6b06fea 100644 --- a/.gitignore +++ b/.gitignore @@ -2,8 +2,7 @@ cfg/system.config # build.bat and build.sh specific -/hadrian -/hadrian.exe +/bin/ # build.cabal.sh specific /dist/ diff --git a/build.bat b/build.bat index 6e86d42..2bc9a95 100644 --- a/build.bat +++ b/build.bat @@ -1,20 +1,20 @@ @cd %~dp0 - at mkdir ../_build/hadrian 2> nul + at mkdir bin 2> nul - at set ghcArgs=--make ^ - -Wall ^ - -fno-warn-name-shadowing ^ - -XRecordWildCards ^ - src/Main.hs ^ - -threaded ^ - -isrc ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=../_build/hadrian ^ - -i../libraries/Cabal/Cabal ^ - -j ^ - -O ^ - -o hadrian + at set ghcArgs=--make ^ + -Wall ^ + -fno-warn-name-shadowing ^ + -XRecordWildCards ^ + src\Main.hs ^ + -threaded ^ + -isrc ^ + -i..\libraries\Cabal\Cabal ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=bin ^ + -j ^ + -O ^ + -o bin\hadrian @set hadrianArgs=--lint ^ --directory ^ @@ -28,4 +28,4 @@ @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains @set GHC_PACKAGE_PATH= - at hadrian %hadrianArgs% + at bin\hadrian %hadrianArgs% diff --git a/build.sh b/build.sh index d627c58..0f957cf 100755 --- a/build.sh +++ b/build.sh @@ -39,7 +39,7 @@ if type cabal > /dev/null 2>&1; then fi fi -mkdir -p "$root/../_build/hadrian" +mkdir -p "$root/bin" ghc \ "$root/src/Main.hs" \ @@ -51,11 +51,11 @@ ghc \ -rtsopts \ -with-rtsopts=-I0 \ -threaded \ - -outputdir="$root/../_build/hadrian" \ + -outputdir="$root/bin" \ -j -O \ - -o "$root/hadrian" + -o "$root/bin/hadrian" -"$root/hadrian" \ +"$root/bin/hadrian" \ --lint \ --directory "$root/.." \ "$@" From git at git.haskell.org Fri Oct 27 01:12:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compute package dependencies only for packages we build (67f433b) Message-ID: <20171027011211.9EBC23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/67f433bf028ec4c4251b928fa476ff1302e8299c/ghc >--------------------------------------------------------------- commit 67f433bf028ec4c4251b928fa476ff1302e8299c Author: Andrey Mokhov Date: Thu Oct 27 20:00:58 2016 +0100 Compute package dependencies only for packages we build See #265 >--------------------------------------------------------------- 67f433bf028ec4c4251b928fa476ff1302e8299c src/Rules/Cabal.hs | 5 +++-- src/Rules/Test.hs | 2 +- src/Settings.hs | 5 ++++- src/Settings/Default.hs | 1 - 4 files changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 409ca1b..8848268 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -16,7 +16,7 @@ cabalRules :: Rules () cabalRules = do -- Cache boot package constraints (to be used in 'cabalArgs'). bootPackageConstraints %> \out -> do - bootPkgs <- interpretInContext (stageContext Stage0) getPackages + bootPkgs <- stagePackages Stage0 let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] @@ -28,7 +28,8 @@ cabalRules = do -- Cache package dependencies. packageDependencies %> \out -> do - pkgDeps <- forM (sort knownPackages) $ \pkg -> + pkgs <- concatMapM stagePackages [Stage0 .. Stage2] + pkgDeps <- forM (sort pkgs) $ \pkg -> if pkg `elem` [hp2ps, libffi, rts, touchy, unlit] then return $ pkgNameString pkg else do diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 3b2fd1b..18513a7 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -23,7 +23,7 @@ testRules = do "test" ~> do let yesNo x = show $ if x then "YES" else "NO" - pkgs <- interpretInContext (stageContext Stage1) getPackages + pkgs <- stagePackages Stage1 tests <- filterM doesDirectoryExist $ concat [ [ pkgPath pkg -/- "tests", pkgPath pkg -/- "tests-ghc" ] | pkg <- pkgs, isLibrary pkg, pkg /= rts, pkg /= libffi ] diff --git a/src/Settings.hs b/src/Settings.hs index 3fdf14f..0a71c90 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,7 +1,7 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, - getContextDirectory, getBuildPath + getContextDirectory, getBuildPath, stagePackages ) where import Base @@ -28,6 +28,9 @@ getRtsWays = fromDiffExpr $ rtsWays flavour getPackages :: Expr [Package] getPackages = fromDiffExpr $ packages flavour +stagePackages :: Stage -> Action [Package] +stagePackages stage = interpretInContext (stageContext stage) getPackages + getPackagePath :: Expr FilePath getPackagePath = pkgPath <$> getPackage diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index f529019..f7ef62e 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -65,7 +65,6 @@ defaultBuilderArgs = mconcat , makeBuilderArgs , tarBuilderArgs ] - -- | All 'Package'-dependent command line arguments. defaultPackageArgs :: Args defaultPackageArgs = mconcat From git at git.haskell.org Fri Oct 27 01:12:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add rule 'sdist-ghc' (d4d9c03) Message-ID: <20171027011215.1B7063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4d9c03de0be0762f973f106d2d4f4b2000d63f1/ghc >--------------------------------------------------------------- commit d4d9c03de0be0762f973f106d2d4f4b2000d63f1 Author: Kai Harries Date: Thu Jun 9 21:50:24 2016 +0200 Add rule 'sdist-ghc' See #219 >--------------------------------------------------------------- d4d9c03de0be0762f973f106d2d4f4b2000d63f1 hadrian.cabal | 1 + src/Main.hs | 2 + src/Rules/Clean.hs | 1 + src/Rules/SourceDist.hs | 105 ++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 109 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 3b19557..4d6fbdf 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -64,6 +64,7 @@ executable hadrian , Rules.Program , Rules.Register , Rules.Selftest + , Rules.SourceDist , Rules.Test , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg diff --git a/src/Main.hs b/src/Main.hs index 66f897f..b4c2d42 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -7,6 +7,7 @@ import qualified Environment import qualified Rules import qualified Rules.Clean import qualified Rules.Oracles +import qualified Rules.SourceDist import qualified Rules.Selftest import qualified Rules.Test import qualified Settings.Paths @@ -23,6 +24,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do rules = do Rules.Clean.cleanRules Rules.Oracles.oracleRules + Rules.SourceDist.sourceDistRules Rules.Selftest.selftestRules Rules.Test.testRules Rules.buildRules diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 4678054..50edd20 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -16,6 +16,7 @@ cleanRules = do removeDirectory generatedPath removeDirectory programInplacePath removeDirectory "inplace/lib" + removeDirectory "sdistprep" putBuild $ "| Remove files generated by ghc-cabal..." forM_ knownPackages $ \pkg -> forM_ [Stage0 ..] $ \stage -> do diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs new file mode 100644 index 0000000..a2cc8f4 --- /dev/null +++ b/src/Rules/SourceDist.hs @@ -0,0 +1,105 @@ +module Rules.SourceDist (sourceDistRules) where + +import Base +import Builder +import Oracles.Config.Setting +import Oracles.DirectoryContent +import Rules.Actions +import UserSettings + +sourceDistRules :: Rules () +sourceDistRules = do + "sdist-ghc" ~> do + version <- setting ProjectVersion + need ["sdistprep/ghc-" ++ version ++ "-src.tar.xz"] + putSuccess "| Done. " + "sdistprep/ghc-*-src.tar.xz" %> \fname -> do + let tarName = takeFileName fname + treePath = "sdistprep/ghc" dropTarXz tarName + prepareTree treePath + runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." tarName, dropTarXz tarName] + "GIT_COMMIT_ID" %> \fname -> + setting ProjectGitCommitId >>= writeFileChanged fname + "VERSION" %> \fname -> + setting ProjectVersion >>= writeFileChanged fname + where + dropTarXz = dropExtension . dropExtension + + +prepareTree :: FilePath -> Action () +prepareTree dest = do + mapM_ cpDir srcDirs + mapM_ cpFile srcFiles + where + cpFile a = copyFile a (dest a) + cpDir a = copyDirectoryContent (Not excluded) a (dest takeFileName a) + excluded = Or + [ Test "//.*" + , Test "//#*" + , Test "//*-SAVE" + , Test "//*.orig" + , Test "//*.rej" + , Test "//*~" + , Test "//autom4te*" + , Test "//dist" + , Test "//log" + , Test "//stage0" + , Test "//stage1" + , Test "//stage2" + , Test "//stage3" + , Test "hadrian/cabal.sandbox.config" + , Test "hadrian/cfg/system.config" + , Test "hadrian/dist" + , Test "hadrian/UserSettings.hs" + , Test "libraries//*.buildinfo" + , Test "libraries//GNUmakefile" + , Test "libraries//config.log" + , Test "libraries//config.status" + , Test "libraries//configure" + , Test "libraries//ghc.mk" + , Test "libraries//include/Hs*Config.h" + , Test "libraries/dph" + , Test "libraries/parallel" + , Test "libraries/primitive" + , Test "libraries/random" + , Test "libraries/stm" + , Test "libraries/vector" + , Test "mk/build.mk" ] + srcDirs = + [ "bindisttest" + , "compiler" + , "distrib" + , "docs" + , "docs" + , "driver" + , "ghc" + , "hadrian" + , "includes" + , "iserv" + , "libffi" + , "libffi-tarballs" + , "libraries" + , "mk" + , "rts" + , "rules" + , "utils" ] + srcFiles = + [ "ANNOUNCE" + , "GIT_COMMIT_ID" + , "HACKING.md" + , "INSTALL.md" + , "LICENSE" + , "MAKEHELP.md" + , "Makefile" + , "README.md" + , "VERSION" + , "aclocal.m4" + , "boot" + , "config.guess" + , "config.sub" + , "configure" + , "configure.ac" + , "ghc.mk" + , "install-sh" + , "packages" + , "settings.in" ] From git at git.haskell.org Fri Oct 27 01:12:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #265 from KaiHa/wip/ticket219 (0bfadf3) Message-ID: <20171027011218.9C9353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0bfadf34ec199a40c4276c0935ba8c725cf51171/ghc >--------------------------------------------------------------- commit 0bfadf34ec199a40c4276c0935ba8c725cf51171 Merge: 67f433b d4d9c03 Author: Andrey Mokhov Date: Thu Oct 27 23:19:12 2016 +0100 Merge pull request #265 from KaiHa/wip/ticket219 Implement 'sdist-ghc' rule >--------------------------------------------------------------- 0bfadf34ec199a40c4276c0935ba8c725cf51171 hadrian.cabal | 1 + src/Main.hs | 2 + src/Rules/Clean.hs | 1 + src/Rules/SourceDist.hs | 105 ++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 109 insertions(+) From git at git.haskell.org Fri Oct 27 01:12:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on source distribution (0959e45) Message-ID: <20171027011222.2B8A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0959e45fab08b850fdb5b555ea7250e493386976/ghc >--------------------------------------------------------------- commit 0959e45fab08b850fdb5b555ea7250e493386976 Author: Andrey Mokhov Date: Fri Oct 28 17:33:11 2016 +0100 Add a note on source distribution See #219. >--------------------------------------------------------------- 0959e45fab08b850fdb5b555ea7250e493386976 README.md | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 718421f..d869f4b 100644 --- a/README.md +++ b/README.md @@ -98,6 +98,10 @@ complete separation of GHC sources and build artefacts: [#113][build-artefacts-i * `build -B` forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. +#### Source distribution + +To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` target. + #### Testing * `build validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` @@ -119,7 +123,7 @@ The new build system still lacks many important features: * Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. -* There is no support for installation or binary/source distribution: [#219][install-issue]. +* There is no support for installation or binary distribution: [#219][install-issue]. Check out [milestones] to see when we hope to resolve the above limitations. From git at git.haskell.org Fri Oct 27 01:12:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Retry pacman package downloads on AppVeyor to make CI more robust (6596774) Message-ID: <20171027011225.989D23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65967740632fed04975ead2f3ea9fe2225e45671/ghc >--------------------------------------------------------------- commit 65967740632fed04975ead2f3ea9fe2225e45671 Author: Andrey Mokhov Date: Fri Oct 28 23:03:05 2016 +0100 Retry pacman package downloads on AppVeyor to make CI more robust >--------------------------------------------------------------- 65967740632fed04975ead2f3ea9fe2225e45671 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 7552a56..7687500 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -22,7 +22,7 @@ install: # Install all Hadrian and GHC build dependencies - cd hadrian - stack setup > nul - - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm + - appveyor-retry stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: # Build Hadrian From git at git.haskell.org Fri Oct 27 01:12:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor package-data generation for custom packages (cfecd73) Message-ID: <20171027011229.08D423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cfecd733f3e9df9c5ae6e657588a72153871d549/ghc >--------------------------------------------------------------- commit cfecd733f3e9df9c5ae6e657588a72153871d549 Author: Andrey Mokhov Date: Sat Oct 29 01:19:03 2016 +0100 Refactor package-data generation for custom packages >--------------------------------------------------------------- cfecd733f3e9df9c5ae6e657588a72153871d549 src/Rules/Data.hs | 119 +++++++++++++++++++++++------------------------------- 1 file changed, 50 insertions(+), 69 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 502fc3c..cefd2fa 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -57,80 +57,61 @@ buildPackageData context at Context {..} = do -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps. priority 2.0 $ do - when (package == hp2ps) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" - , "Reorder.c", "TopTwenty.c", "AuxFile.c" - , "Deviation.c", "HpFile.c", "Marks.c", "Scale.c" - , "TraceElement.c", "Axes.c", "Dimensions.c", "Key.c" - , "PsFile.c", "Shade.c", "Utilities.c" ] - contents = unlines $ map (prefix++) - [ "PROGNAME = hp2ps" - , "C_SRCS = " ++ unwords cSrcs - , "DEP_EXTRA_LIBS = m" - , "CC_OPTS = -I" ++ generatedPath ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk - - when (package == unlit) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - contents = unlines $ map (prefix++) - [ "PROGNAME = unlit" - , "C_SRCS = unlit.c" - , "SYNOPSIS = Literate script filter." ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk - - when (package == touchy) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - contents = unlines $ map (prefix++) - [ "PROGNAME = touchy" - , "C_SRCS = touchy.c" ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk + when (package `elem` [hp2ps, rts, touchy, unlit]) $ dataFile %> + generatePackageData context -- Bootstrapping `ghcCabal`: although `ghcCabal` is a proper cabal -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. - when (package == ghcCabal && stage == Stage0) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - contents = unlines $ map (prefix++) - [ "PROGNAME = ghc-cabal" - , "MODULES = Main" - , "SYNOPSIS = Bootstrapped ghc-cabal utility." - , "HS_SRC_DIRS = ." ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk + when (package == ghcCabal && stage == Stage0) $ dataFile %> + generatePackageData context + +generatePackageData :: Context -> FilePath -> Action () +generatePackageData context at Context {..} file = do + orderOnly =<< interpretInContext context generatedDependencies + asmSrcs <- packageAsmSources package + cSrcs <- packageCSources package + cmmSrcs <- packageCmmSources package + let prefix = fixKey (buildPath context) ++ "_" + pkgKey = if isLibrary package then "COMPONENT_ID = " else "PROGNAME = " + writeFileChanged file . unlines . map (prefix ++) $ + [ pkgKey ++ pkgNameString package ] ++ + [ "S_SRCS = " ++ unwords asmSrcs ] ++ + [ "C_SRCS = " ++ unwords cSrcs ] ++ + [ "CMM_SRCS = " ++ unwords cmmSrcs ] ++ + [ "DEP_EXTRA_LIBS = m" | package == hp2ps ] ++ + [ "CC_OPTS = -I" ++ generatedPath | package `elem` [hp2ps, rts]] ++ + [ "MODULES = Main" | package == ghcCabal ] ++ + [ "HS_SRC_DIRS = ." | package == ghcCabal ] ++ + [ "SYNOPSIS = Bootstrapped ghc-cabal." | package == ghcCabal ] + putSuccess $ "| Successfully generated " ++ file + +packageCSources :: Package -> Action [FilePath] +packageCSources pkg + | pkg /= rts = getDirectoryFiles (pkgPath pkg) ["*.c"] + | otherwise = do + windows <- windowsHost + sources <- fmap (map unifyPath) . getDirectoryFiles (pkgPath pkg) . + map (-/- "*.c") $ [ ".", "hooks", "sm", "eventlog", "linker" ] ++ + [ if windows then "win32" else "posix" ] + return $ sources ++ [ rtsBuildPath -/- "c/sm/Evac_thr.c" ] + ++ [ rtsBuildPath -/- "c/sm/Scav_thr.c" ] + +packageAsmSources :: Package -> Action [FilePath] +packageAsmSources pkg + | pkg /= rts = return [] + | otherwise = do + buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] + buildStgCRunAsm <- anyTargetArch ["powerpc64le"] + return $ [ "AdjustorAsm.S" | buildAdjustor ] + ++ [ "StgCRunAsm.S" | buildStgCRunAsm ] - when (package == rts && stage == Stage1) $ do - dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - windows <- windowsHost - let prefix = fixKey (buildPath context) ++ "_" - dirs = [ ".", "hooks", "sm", "eventlog", "linker" ] - ++ [ if windows then "win32" else "posix" ] - cSrcs <- map unifyPath <$> - getDirectoryFiles (pkgPath package) (map (-/- "*.c") dirs) - cmmSrcs <- getDirectoryFiles (pkgPath package) ["*.cmm"] - buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] - buildStgCRunAsm <- anyTargetArch ["powerpc64le"] - let extraCSrcs = [ rtsBuildPath -/- "c/sm/Evac_thr.c" ] - ++ [ rtsBuildPath -/- "c/sm/Scav_thr.c" ] - extraCmmSrcs = [ rtsBuildPath -/- "cmm/AutoApply.cmm" ] - extraAsmSrcs = [ "AdjustorAsm.S" | buildAdjustor ] - ++ [ "StgCRunAsm.S" | buildStgCRunAsm ] - let contents = unlines $ map (prefix ++) - [ "C_SRCS = " ++ unwords (cSrcs ++ extraCSrcs) - , "CMM_SRCS = " ++ unwords (cmmSrcs ++ extraCmmSrcs) - , "S_SRCS = " ++ unwords extraAsmSrcs - , "CC_OPTS = -I" ++ generatedPath - , "COMPONENT_ID = rts" ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk +packageCmmSources :: Package -> Action [FilePath] +packageCmmSources pkg + | pkg /= rts = return [] + | otherwise = do + sources <- getDirectoryFiles (pkgPath pkg) ["*.cmm"] + return $ sources ++ [ rtsBuildPath -/- "cmm/AutoApply.cmm" ] -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' From git at git.haskell.org Fri Oct 27 01:12:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Turn contextDirectory into stageDirectory (241d59a) Message-ID: <20171027011232.91C793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/241d59a5f814d5139ca9d6d9bfa0ea127357f505/ghc >--------------------------------------------------------------- commit 241d59a5f814d5139ca9d6d9bfa0ea127357f505 Author: Andrey Mokhov Date: Sat Oct 29 02:11:59 2016 +0100 Turn contextDirectory into stageDirectory >--------------------------------------------------------------- 241d59a5f814d5139ca9d6d9bfa0ea127357f505 src/GHC.hs | 23 ++++++----------------- src/Rules/Clean.hs | 6 ++---- src/Rules/Data.hs | 6 +++--- src/Rules/Generate.hs | 2 +- src/Rules/Register.hs | 2 +- src/Settings.hs | 2 +- src/Settings/Paths.hs | 5 ++--- 7 files changed, 16 insertions(+), 30 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 7cabff5..0312a3e 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -9,7 +9,7 @@ module GHC ( parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, programPath, contextDirectory, rtsContext + defaultKnownPackages, stageDirectory, rtsContext, programPath ) where import Base @@ -91,16 +91,15 @@ xhtml = library "xhtml" ghcSplit :: FilePath ghcSplit = "inplace/lib/bin/ghc-split" --- TODO: The following utils are not included into the build system because --- they seem to be unused or unrelated to the build process: checkUniques, --- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, --- lndir, mkdirhier, testremove, vagrant +-- | Relative path to the directory containing build artefacts of a given 'Stage'. +stageDirectory :: Stage -> FilePath +stageDirectory = stageString -- TODO: move to buildRootPath, see #113 -- TODO: simplify, add programInplaceLibPath -- | The relative path to the program executable programPath :: Context -> Maybe FilePath -programPath context at Context {..} +programPath Context {..} | package == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) | package `elem` [mkUserGuidePart] = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package @@ -123,19 +122,9 @@ programPath context at Context {..} | otherwise = Nothing where inplaceProgram name = programInplacePath -/- name <.> exe - installProgram name = pkgPath package -/- contextDirectory context + installProgram name = pkgPath package -/- stageDirectory stage -/- "build/tmp" -/- name <.> exe -- TODO: Move this elsewhere. rtsContext :: Context rtsContext = vanillaContext Stage1 rts - --- | GHC build results will be placed into target directories with the --- following typical structure: - --- * @build/@ contains compiled object code --- * @doc/@ is produced by haddock --- * @package-data.mk@ contains output of ghc-cabal applied to pkgCabal -contextDirectory :: Context -> FilePath -contextDirectory Context {..} = stageString stage - diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 50edd20..e212048 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -1,7 +1,6 @@ module Rules.Clean (cleanRules) where import Base -import Context import Package import Rules.Actions import Settings @@ -19,9 +18,8 @@ cleanRules = do removeDirectory "sdistprep" putBuild $ "| Remove files generated by ghc-cabal..." forM_ knownPackages $ \pkg -> - forM_ [Stage0 ..] $ \stage -> do - let dir = pkgPath pkg -/- contextDirectory (vanillaContext stage pkg) - quietly $ removeDirectory dir + forM_ [Stage0 ..] $ \stage -> + quietly . removeDirectory $ pkgPath pkg -/- stageDirectory stage putBuild $ "| Remove Hadrian files..." removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index cefd2fa..5a4d103 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -19,7 +19,7 @@ buildPackageData context at Context {..} = do let cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile context - oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 + oldPath = pkgPath package -/- stageDirectory stage -- TODO: remove, #113 inTreeMk = oldPath -/- takeFileName dataFile -- TODO: remove, #113 inTreeMk %> \mk -> do @@ -123,7 +123,7 @@ packageCmmSources pkg -- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 -- Reason: Shake's built-in makefile parser doesn't recognise slashes postProcessPackageData :: Context -> FilePath -> Action () -postProcessPackageData context at Context {..} file = fixFile file fixPackageData +postProcessPackageData Context {..} file = fixFile file fixPackageData where fixPackageData = unlines . map processLine . filter (not . null) . filter ('$' `notElem`) . lines processLine line = fixKey fixedPrefix ++ suffix @@ -132,7 +132,7 @@ postProcessPackageData context at Context {..} file = fixFile file fixPackageData -- Change package/path/targetDir to takeDirectory file -- This is a temporary hack until we get rid of ghc-cabal fixedPrefix = takeDirectory file ++ drop len prefix - len = length (pkgPath package -/- contextDirectory context) + len = length (pkgPath package -/- stageDirectory stage) -- TODO: Remove, see #113. fixKey :: String -> String diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 698299d..f8cf345 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -133,7 +133,7 @@ generatePackageCode context@(Context stage pkg _) = need [primopsTxt stage] build $ Target context GenPrimopCode [primopsTxt stage] [file] -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- contextDirectory context -/- "build" + let oldPath = pkgPath pkg -/- stageDirectory stage -/- "build" newFile = oldPath ++ (drop (length path) file) createDirectory $ takeDirectory newFile liftIO $ IO.copyFile file newFile diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index d4799e3..6b3e239 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -23,7 +23,7 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do -- Post-process inplace-pkg-config. TODO: remove, see #113, #148. let path = buildPath context - oldPath = pkgPath package -/- contextDirectory context + oldPath = pkgPath package -/- stageDirectory stage pkgConfig = oldPath -/- "inplace-pkg-config" oldBuildPath = oldPath -/- "build" fixPkgConf = unlines diff --git a/src/Settings.hs b/src/Settings.hs index 0a71c90..3aab9ac 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -35,7 +35,7 @@ getPackagePath :: Expr FilePath getPackagePath = pkgPath <$> getPackage getContextDirectory :: Expr FilePath -getContextDirectory = contextDirectory <$> getContext +getContextDirectory = stageDirectory <$> getStage getBuildPath :: Expr FilePath getBuildPath = buildPath <$> getContext diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 7147264..07c762a 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,5 +1,5 @@ module Settings.Paths ( - contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, + stageDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, @@ -33,8 +33,7 @@ generatedPath = buildRootPath -/- "generated" -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath -buildPath context at Context {..} = - buildRootPath -/- contextDirectory context -/- pkgPath package +buildPath Context {..} = buildRootPath -/- stageDirectory stage -/- pkgPath package -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath From git at git.haskell.org Fri Oct 27 01:12:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor programPath (44f7374) Message-ID: <20171027011242.ED9833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44f7374237aa86baf551860bb943b1707fc286a8/ghc >--------------------------------------------------------------- commit 44f7374237aa86baf551860bb943b1707fc286a8 Author: Andrey Mokhov Date: Sat Oct 29 03:53:46 2016 +0100 Refactor programPath >--------------------------------------------------------------- 44f7374237aa86baf551860bb943b1707fc286a8 src/GHC.hs | 67 ++++++++++++++++++++++++++++++++++++++------------------------ 1 file changed, 41 insertions(+), 26 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 91987c6..6c1e147 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -96,31 +96,46 @@ stageDirectory :: Stage -> FilePath stageDirectory = stageString -- TODO: move to buildRootPath, see #113 --- TODO: simplify, add programInplaceLibPath --- | The relative path to the program executable +-- | The 'FilePath' to a program executable in a given 'Context'. programPath :: Context -> Maybe FilePath -programPath Context {..} - | package == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) - | package `elem` [mkUserGuidePart] = - case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package - _ -> Nothing - | package `elem` [checkApiAnnotations, ghcTags, haddock] = - case stage of Stage2 -> Just . inplaceProgram $ pkgNameString package - _ -> Nothing - | package `elem` [touchy, unlit] = case stage of - Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString package <.> exe - _ -> Nothing - | package == hpcBin = case stage of - Stage1 -> Just $ inplaceProgram "hpc" - _ -> Nothing - | package == runGhc = case stage of - Stage1 -> Just $ inplaceProgram "runhaskell" - _ -> Nothing - | isProgram package = case stage of - Stage0 -> Just . inplaceProgram $ pkgNameString package - _ -> Just . installProgram $ pkgNameString package - | otherwise = Nothing +programPath Context {..} = lookup (stage, package) exes where - inplaceProgram name = programInplacePath -/- name <.> exe - installProgram name = pkgPath package -/- stageDirectory stage - -/- "build/tmp" -/- name <.> exe + exes = [ inplace2 checkApiAnnotations + , install1 compareSizes + , inplace0 deriveConstants + , inplace0 dllSplit + , inplace0 genapply + , inplace0 genprimopcode + , inplace0 ghc `setFile` "ghc-stage1" + , inplace1 ghc `setFile` "ghc-stage2" + , install0 ghcCabal + , inplace1 ghcCabal + , inplace0 ghcPkg + , install1 ghcPkg + , inplace2 ghcTags + , inplace2 haddock + , inplace0 hp2ps + , inplace1 hpcBin `setFile` "hpc" + , inplace0 hsc2hs + , install1 hsc2hs + , inplace0 mkUserGuidePart + , inplace1 runGhc `setFile` "runhaskell" + , inplace0 touchy `setDir` "inplace/lib/bin" + , inplace0 unlit `setDir` "inplace/lib/bin" ] + inplace pkg = programInplacePath -/- pkgNameString pkg <.> exe + inplace0 pkg = ((Stage0, pkg), inplace pkg) + inplace1 pkg = ((Stage1, pkg), inplace pkg) + inplace2 pkg = ((Stage2, pkg), inplace pkg) + install stage pkg = pkgPath package -/- stageDirectory stage -/- "build" + -/- pkgNameString pkg <.> exe + install0 pkg = ((Stage0, pkg), install Stage0 pkg) + install1 pkg = ((Stage1, pkg), install Stage1 pkg) + setFile ((stage, pkg), x) y = ((stage, pkg), takeDirectory x -/- y <.> exe) + setDir ((stage, pkg), x) y = ((stage, pkg), y -/- takeFileName x) + + -- | isProgram package = case stage of + -- Stage0 -> Just . inplaceProgram $ pkgNameString package + -- _ -> Just . installProgram $ pkgNameString package + -- | otherwise = Nothing + -- where + -- inplaceProgram name = programInplacePath -/- name <.> exe From git at git.haskell.org Fri Oct 27 01:12:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify builderPath (058cb92) Message-ID: <20171027011239.836043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/058cb92e8f1f21c271073d892d8b504726a345a2/ghc >--------------------------------------------------------------- commit 058cb92e8f1f21c271073d892d8b504726a345a2 Author: Andrey Mokhov Date: Sat Oct 29 02:42:29 2016 +0100 Simplify builderPath >--------------------------------------------------------------- 058cb92e8f1f21c271073d892d8b504726a345a2 src/Builder.hs | 11 +++-------- src/GHC.hs | 2 +- src/Package.hs | 1 - 3 files changed, 4 insertions(+), 10 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index c5dc9fb..61960c7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -94,14 +94,9 @@ isOptional = \case -- | Determine the location of a 'Builder'. builderPath :: Builder -> Action FilePath -builderPath builder = case builderProvenance builder of - Just context - | Just path <- programPath context -> return path - | otherwise -> - -- TODO: Make builderPath total. - error $ "Cannot determine builderPath for " ++ show builder - ++ " in context " ++ show context - Nothing -> case builder of +builderPath builder = case programPath =<< builderProvenance builder of + Just path -> return path + Nothing -> case builder of Alex -> fromKey "alex" Ar -> fromKey "ar" Cc _ Stage0 -> fromKey "system-cc" diff --git a/src/GHC.hs b/src/GHC.hs index 2af8923..91987c6 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -86,7 +86,7 @@ unix = library "unix" win32 = library "Win32" xhtml = library "xhtml" --- | ghc-split is a perl script used by GHC with @-split-objs@ flag. It is +-- | @ghc-split@ is a Perl script used by GHC with @-split-objs@ flag. It is -- generated in "Rules.Generators.GhcSplit". ghcSplit :: FilePath ghcSplit = "inplace/lib/bin/ghc-split" diff --git a/src/Package.hs b/src/Package.hs index bee5640..8a1a8d2 100644 --- a/src/Package.hs +++ b/src/Package.hs @@ -17,7 +17,6 @@ newtype PackageName = PackageName { fromPackageName :: String } deriving (Binary, Eq, Generic, Hashable, IsString, NFData, Ord, Typeable) -- TODO: Make PackageType more precise, #12. --- TODO: Turn Program to Program FilePath thereby getting rid of programPath -- | We regard packages as either being libraries or programs. This is bit of a -- convenient lie as Cabal packages can be both, but it works for now. data PackageType = Library | Program deriving Generic From git at git.haskell.org Fri Oct 27 01:12:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move rtsContext to Settings.Packages.Rts (fd0cb1f) Message-ID: <20171027011236.146353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd0cb1f72339c7ec09962f81d4174e14224a6609/ghc >--------------------------------------------------------------- commit fd0cb1f72339c7ec09962f81d4174e14224a6609 Author: Andrey Mokhov Date: Sat Oct 29 02:15:08 2016 +0100 Move rtsContext to Settings.Packages.Rts >--------------------------------------------------------------- fd0cb1f72339c7ec09962f81d4174e14224a6609 src/GHC.hs | 6 +----- src/Rules.hs | 1 + src/Rules/Generate.hs | 1 + src/Settings/Packages/Rts.hs | 5 ++++- 4 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0312a3e..2af8923 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -9,7 +9,7 @@ module GHC ( parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, stageDirectory, rtsContext, programPath + defaultKnownPackages, stageDirectory, programPath ) where import Base @@ -124,7 +124,3 @@ programPath Context {..} inplaceProgram name = programInplacePath -/- name <.> exe installProgram name = pkgPath package -/- stageDirectory stage -/- "build/tmp" -/- name <.> exe - --- TODO: Move this elsewhere. -rtsContext :: Context -rtsContext = vanillaContext Stage1 rts diff --git a/src/Rules.hs b/src/Rules.hs index e62ecc7..68a06c7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -19,6 +19,7 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings +import Settings.Packages.Rts import Settings.Paths allStages :: [Stage] diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index f8cf345..94bcc40 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -20,6 +20,7 @@ import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Rules.Libffi +import Settings.Packages.Rts import Settings.Paths import Target import UserSettings diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index f2b4035..b3b86a9 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,5 +1,5 @@ module Settings.Packages.Rts ( - rtsPackageArgs, rtsConfIn, rtsConf, rtsLibffiLibraryName + rtsPackageArgs, rtsConfIn, rtsConf, rtsContext, rtsLibffiLibraryName ) where import Base @@ -11,6 +11,9 @@ import Predicate import Settings import Settings.Paths +rtsContext :: Context +rtsContext = vanillaContext Stage1 rts + rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" From git at git.haskell.org Fri Oct 27 01:12:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build iservBin, fix comments (28f2675) Message-ID: <20171027011246.699F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/28f26751efa6336fac0798eb2e07795eeeb134b2/ghc >--------------------------------------------------------------- commit 28f26751efa6336fac0798eb2e07795eeeb134b2 Author: Andrey Mokhov Date: Sat Oct 29 11:15:33 2016 +0100 Build iservBin, fix comments >--------------------------------------------------------------- 28f26751efa6336fac0798eb2e07795eeeb134b2 src/GHC.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 6c1e147..c3242c6 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -95,6 +95,7 @@ ghcSplit = "inplace/lib/bin/ghc-split" stageDirectory :: Stage -> FilePath stageDirectory = stageString +-- TODO: Create a separate rule for copying executables to inplace/bin -- TODO: move to buildRootPath, see #113 -- | The 'FilePath' to a program executable in a given 'Context'. programPath :: Context -> Maybe FilePath @@ -118,6 +119,7 @@ programPath Context {..} = lookup (stage, package) exes , inplace1 hpcBin `setFile` "hpc" , inplace0 hsc2hs , install1 hsc2hs + , install1 iservBin , inplace0 mkUserGuidePart , inplace1 runGhc `setFile` "runhaskell" , inplace0 touchy `setDir` "inplace/lib/bin" @@ -132,10 +134,3 @@ programPath Context {..} = lookup (stage, package) exes install1 pkg = ((Stage1, pkg), install Stage1 pkg) setFile ((stage, pkg), x) y = ((stage, pkg), takeDirectory x -/- y <.> exe) setDir ((stage, pkg), x) y = ((stage, pkg), y -/- takeFileName x) - - -- | isProgram package = case stage of - -- Stage0 -> Just . inplaceProgram $ pkgNameString package - -- _ -> Just . installProgram $ pkgNameString package - -- | otherwise = Nothing - -- where - -- inplaceProgram name = programInplacePath -/- name <.> exe From git at git.haskell.org Fri Oct 27 01:12:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bring back tmp directory for in-tree build artefacts (c93cf69) Message-ID: <20171027011249.D2EDC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c93cf69f4cade6af063fcc26ebe13598f0eb9b56/ghc >--------------------------------------------------------------- commit c93cf69f4cade6af063fcc26ebe13598f0eb9b56 Author: Andrey Mokhov Date: Sat Oct 29 11:50:13 2016 +0100 Bring back tmp directory for in-tree build artefacts >--------------------------------------------------------------- c93cf69f4cade6af063fcc26ebe13598f0eb9b56 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index c3242c6..810c63d 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -128,7 +128,7 @@ programPath Context {..} = lookup (stage, package) exes inplace0 pkg = ((Stage0, pkg), inplace pkg) inplace1 pkg = ((Stage1, pkg), inplace pkg) inplace2 pkg = ((Stage2, pkg), inplace pkg) - install stage pkg = pkgPath package -/- stageDirectory stage -/- "build" + install stage pkg = pkgPath package -/- stageDirectory stage -/- "build/tmp" -/- pkgNameString pkg <.> exe install0 pkg = ((Stage0, pkg), install Stage0 pkg) install1 pkg = ((Stage1, pkg), install Stage1 pkg) From git at git.haskell.org Fri Oct 27 01:12:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor builder path manipulation (8ee46b1) Message-ID: <20171027011253.65DB93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2/ghc >--------------------------------------------------------------- commit 8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2 Author: Andrey Mokhov Date: Sun Oct 30 01:54:14 2016 +0100 Refactor builder path manipulation >--------------------------------------------------------------- 8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2 hadrian.cabal | 2 +- src/Builder.hs | 92 +------------------------------- src/GHC.hs | 67 ++++++++--------------- src/Oracles/WindowsPath.hs | 45 ---------------- src/Rules/Actions.hs | 24 ++++++++- src/Rules/Documentation.hs | 2 +- src/Rules/Generators/ConfigHs.hs | 1 + src/Rules/Generators/GhcSplit.hs | 1 + src/Rules/Oracles.hs | 4 +- src/Rules/Program.hs | 5 -- src/Rules/Test.hs | 3 +- src/Rules/Wrappers/Ghc.hs | 2 +- src/Rules/Wrappers/GhcPkg.hs | 2 +- src/Settings/Builders/Common.hs | 4 +- src/Settings/Builders/DeriveConstants.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 3 +- src/Settings/Builders/Haddock.hs | 7 ++- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Paths.hs | 64 +++++++++++++++++++++- 19 files changed, 128 insertions(+), 206 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 8ee46b1a40dcbf73f12d360203b1f2ec5d78d3c2 From git at git.haskell.org Fri Oct 27 01:12:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:12:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing src/Oracles/Path.hs (e1e2621) Message-ID: <20171027011256.CD8F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1e2621d6bdd5ebe98fb3787733d134fa4d2fd70/ghc >--------------------------------------------------------------- commit e1e2621d6bdd5ebe98fb3787733d134fa4d2fd70 Author: Andrey Mokhov Date: Sun Oct 30 01:01:43 2016 +0000 Add missing src/Oracles/Path.hs >--------------------------------------------------------------- e1e2621d6bdd5ebe98fb3787733d134fa4d2fd70 src/Oracles/Path.hs | 83 +++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 83 insertions(+) diff --git a/src/Oracles/Path.hs b/src/Oracles/Path.hs new file mode 100644 index 0000000..7db1400 --- /dev/null +++ b/src/Oracles/Path.hs @@ -0,0 +1,83 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module Oracles.Path ( + fixAbsolutePathOnWindows, topDirectory, getTopDirectory, windowsPathOracle, + systemBuilderPath + ) where + +import Control.Monad.Trans.Reader +import Data.Char + +import Base +import Builder +import Oracles.Config +import Oracles.Config.Setting +import Oracles.LookupInPath +import Stage + +newtype WindowsPath = WindowsPath FilePath + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Path to the GHC source tree. +topDirectory :: Action FilePath +topDirectory = fixAbsolutePathOnWindows =<< setting GhcSourcePath + +getTopDirectory :: ReaderT a Action FilePath +getTopDirectory = lift topDirectory + +-- | Determine the location of a system 'Builder'. +systemBuilderPath :: Builder -> Action FilePath +systemBuilderPath builder = case builder of + Alex -> fromKey "alex" + Ar -> fromKey "ar" + Cc _ Stage0 -> fromKey "system-cc" + Cc _ _ -> fromKey "cc" + -- We can't ask configure for the path to configure! + Configure _ -> return "bash configure" + Ghc _ Stage0 -> fromKey "system-ghc" + GhcPkg Stage0 -> fromKey "system-ghc-pkg" + Happy -> fromKey "happy" + HsColour -> fromKey "hscolour" + HsCpp -> fromKey "hs-cpp" + Ld -> fromKey "ld" + Make _ -> fromKey "make" + Nm -> fromKey "nm" + Objdump -> fromKey "objdump" + Patch -> fromKey "patch" + Perl -> fromKey "perl" + Ranlib -> fromKey "ranlib" + Tar -> fromKey "tar" + _ -> error $ "No system.config entry for " ++ show builder + where + fromKey key = do + let unpack = fromMaybe . error $ "Cannot find path to builder " + ++ quote key ++ " in system.config file. Did you skip configure?" + path <- unpack <$> askConfig key + if null path + then do + unless (isOptional builder) . error $ "Non optional builder " + ++ quote key ++ " is not specified in system.config file." + return "" -- TODO: Use a safe interface. + else fixAbsolutePathOnWindows =<< lookupInPath path + +-- | Fix an absolute path on Windows: +-- * "/c/" => "C:/" +-- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" +fixAbsolutePathOnWindows :: FilePath -> Action FilePath +fixAbsolutePathOnWindows path = do + windows <- windowsHost + if windows + then do + let (dir, file) = splitFileName path + winDir <- askOracle $ WindowsPath dir + return $ winDir -/- file + else + return path + +-- | Compute path mapping on Windows. This is slow and requires caching. +windowsPathOracle :: Rules () +windowsPathOracle = void $ + addOracle $ \(WindowsPath path) -> do + Stdout out <- quietly $ cmd ["cygpath", "-m", path] + let windowsPath = unifyPath $ dropWhileEnd isSpace out + putLoud $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath + return windowsPath From git at git.haskell.org Fri Oct 27 01:13:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge LookupInPath and Path oracles (b42f4fd) Message-ID: <20171027011300.4A96B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b42f4fdd21227f799c0f3ed52b2f7bfe0225f4d9/ghc >--------------------------------------------------------------- commit b42f4fdd21227f799c0f3ed52b2f7bfe0225f4d9 Author: Andrey Mokhov Date: Sun Oct 30 01:11:22 2016 +0000 Merge LookupInPath and Path oracles >--------------------------------------------------------------- b42f4fdd21227f799c0f3ed52b2f7bfe0225f4d9 hadrian.cabal | 1 - src/Oracles/LookupInPath.hs | 23 ----------------------- src/Oracles/Path.hs | 35 +++++++++++++++++++++++++---------- src/Rules/Oracles.hs | 4 +--- 4 files changed, 26 insertions(+), 37 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 954b1d6..378aff7 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -32,7 +32,6 @@ executable hadrian , Oracles.Config.Setting , Oracles.Dependencies , Oracles.DirectoryContent - , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData , Oracles.Path diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs deleted file mode 100644 index 87e8adf..0000000 --- a/src/Oracles/LookupInPath.hs +++ /dev/null @@ -1,23 +0,0 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where - -import System.Directory - -import Base - -newtype LookupInPath = LookupInPath String - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - --- | Lookup an executable in @PATH at . -lookupInPath :: FilePath -> Action FilePath -lookupInPath name - | name == takeFileName name = askOracle $ LookupInPath name - | otherwise = return name - -lookupInPathOracle :: Rules () -lookupInPathOracle = void $ - addOracle $ \(LookupInPath name) -> do - let unpack = fromMaybe . error $ "Cannot find executable " ++ quote name - path <- unifyPath <$> unpack <$> liftIO (findExecutable name) - putLoud $ "Executable found: " ++ name ++ " => " ++ path - return path diff --git a/src/Oracles/Path.hs b/src/Oracles/Path.hs index 7db1400..1a74915 100644 --- a/src/Oracles/Path.hs +++ b/src/Oracles/Path.hs @@ -1,22 +1,18 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Path ( - fixAbsolutePathOnWindows, topDirectory, getTopDirectory, windowsPathOracle, - systemBuilderPath + topDirectory, getTopDirectory, systemBuilderPath, pathOracle ) where import Control.Monad.Trans.Reader import Data.Char +import System.Directory import Base import Builder import Oracles.Config import Oracles.Config.Setting -import Oracles.LookupInPath import Stage -newtype WindowsPath = WindowsPath FilePath - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -- | Path to the GHC source tree. topDirectory :: Action FilePath topDirectory = fixAbsolutePathOnWindows =<< setting GhcSourcePath @@ -59,6 +55,12 @@ systemBuilderPath builder = case builder of return "" -- TODO: Use a safe interface. else fixAbsolutePathOnWindows =<< lookupInPath path +-- | Lookup an executable in @PATH at . +lookupInPath :: FilePath -> Action FilePath +lookupInPath name + | name == takeFileName name = askOracle $ LookupInPath name + | otherwise = return name + -- | Fix an absolute path on Windows: -- * "/c/" => "C:/" -- * "/usr/bin/tar.exe" => "C:/msys/usr/bin/tar.exe" @@ -73,11 +75,24 @@ fixAbsolutePathOnWindows path = do else return path --- | Compute path mapping on Windows. This is slow and requires caching. -windowsPathOracle :: Rules () -windowsPathOracle = void $ - addOracle $ \(WindowsPath path) -> do +newtype LookupInPath = LookupInPath String + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +newtype WindowsPath = WindowsPath FilePath + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Oracles for looking up paths. These are slow and require caching. +pathOracle :: Rules () +pathOracle = do + void $ addOracle $ \(WindowsPath path) -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] let windowsPath = unifyPath $ dropWhileEnd isSpace out putLoud $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath + + void $ addOracle $ \(LookupInPath name) -> do + let unpack = fromMaybe . error $ "Cannot find executable " ++ quote name + path <- unifyPath <$> unpack <$> liftIO (findExecutable name) + putLoud $ "Executable found: " ++ name ++ " => " ++ path + return path + diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 39fbd00..6c5ace4 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -5,7 +5,6 @@ import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies import qualified Oracles.DirectoryContent -import qualified Oracles.LookupInPath import qualified Oracles.ModuleFiles import qualified Oracles.PackageData import qualified Oracles.Path @@ -16,7 +15,6 @@ oracleRules = do Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles Oracles.DirectoryContent.directoryContentOracle - Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle - Oracles.Path.windowsPathOracle + Oracles.Path.pathOracle From git at git.haskell.org Fri Oct 27 01:13:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename src/Settings/Paths.hs -> src/Settings/Path.hs (e31cb51) Message-ID: <20171027011303.C6BB83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e31cb5136a66213f8afb744c2b7c81344fc3975a/ghc >--------------------------------------------------------------- commit e31cb5136a66213f8afb744c2b7c81344fc3975a Author: Andrey Mokhov Date: Sun Oct 30 01:20:01 2016 +0000 Rename src/Settings/Paths.hs -> src/Settings/Path.hs >--------------------------------------------------------------- e31cb5136a66213f8afb744c2b7c81344fc3975a hadrian.cabal | 2 +- src/Main.hs | 4 ++-- src/Oracles/Dependencies.hs | 2 +- src/Oracles/ModuleFiles.hs | 2 +- src/Rules.hs | 2 +- src/Rules/Actions.hs | 2 +- src/Rules/Cabal.hs | 2 +- src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Generators/ConfigHs.hs | 2 +- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 2 +- src/Rules/Test.hs | 2 +- src/Rules/Wrappers/GhcPkg.hs | 2 +- src/Settings.hs | 2 +- src/Settings/Builders/Common.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/{Paths.hs => Path.hs} | 2 +- 27 files changed, 29 insertions(+), 29 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e31cb5136a66213f8afb744c2b7c81344fc3975a From git at git.haskell.org Fri Oct 27 01:13:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename src/Rules/Actions.hs -> src/Util.hs (fb30a88) Message-ID: <20171027011307.470563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fb30a88d4b90d9bbac63d45fd9d92223a7947947/ghc >--------------------------------------------------------------- commit fb30a88d4b90d9bbac63d45fd9d92223a7947947 Author: Andrey Mokhov Date: Sun Oct 30 01:29:51 2016 +0000 Rename src/Rules/Actions.hs -> src/Util.hs >--------------------------------------------------------------- fb30a88d4b90d9bbac63d45fd9d92223a7947947 hadrian.cabal | 2 +- src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Configure.hs | 2 +- src/Rules/Data.hs | 2 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Perl.hs | 2 +- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/{Rules/Actions.hs => Util.hs} | 2 +- 18 files changed, 18 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fb30a88d4b90d9bbac63d45fd9d92223a7947947 From git at git.haskell.org Fri Oct 27 01:13:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify defaultPackages definition (75281f2) Message-ID: <20171027011310.B534E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/75281f2899cc8e3a890dc1af25a06cd81afb6c1e/ghc >--------------------------------------------------------------- commit 75281f2899cc8e3a890dc1af25a06cd81afb6c1e Author: Andrey Mokhov Date: Sun Oct 30 02:18:53 2016 +0000 Simplify defaultPackages definition >--------------------------------------------------------------- 75281f2899cc8e3a890dc1af25a06cd81afb6c1e src/Settings/Default.hs | 96 ++++++++++++++++++++++++++++++++++++------------- 1 file changed, 71 insertions(+), 25 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index f7ef62e..9f61ff7 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -90,42 +90,88 @@ defaultArgs = mconcat , defaultPackageArgs , builder Ghc ? remove ["-Wall", "-fwarn-tabs"] ] -- TODO: Fix warning Args. --- TODO: Simplify. -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". defaultPackages :: Packages -defaultPackages = mconcat - [ stage0 ? packagesStage0 - , stage1 ? packagesStage1 - , stage2 ? packagesStage2 ] +defaultPackages = mconcat [ packagesStage0, packagesStage1, packagesStage2 ] packagesStage0 :: Packages -packagesStage0 = mconcat - [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcBootTh, ghcCabal - , ghcPkg, hsc2hs, hoopl, hpc, templateHaskell, transformers ] - -- the stage0 predicate makes sure these packages are built only in Stage0 - , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode - , hp2ps, unlit, mkUserGuidePart ] - , stage0 ? windowsHost ? append [touchy] - , notM windowsHost ? notM iosHost ? append [terminfo] ] +packagesStage0 = stage0 ? do + win <- lift windowsHost + ios <- lift iosHost + append $ [ binary + , cabal + , compiler + , deriveConstants + , dllSplit + , genapply + , genprimopcode + , ghc + , ghcBoot + , ghcBootTh + , ghcCabal + , ghcPkg + , hsc2hs + , hoopl + , hp2ps + , hpc + , mkUserGuidePart + , templateHaskell + , transformers + , unlit ] ++ + [ terminfo | not win, not ios ] ++ + [ touchy | win ] packagesStage1 :: Packages -packagesStage1 = mconcat - [ packagesStage0 - , append [ array, base, bytestring, containers, compareSizes, deepseq - , directory, filepath, ghci, ghcPrim, haskeline, hpcBin - , integerLibrary, pretty, process, rts, runGhc, time ] - , windowsHost ? append [win32] - , notM windowsHost ? append [unix] - , notM windowsHost ? append [iservBin] - , buildHaddock flavour ? append [xhtml] ] +packagesStage1 = stage1 ? do + win <- lift windowsHost + ios <- lift iosHost + doc <- buildHaddock flavour + append $ [ array + , base + , binary + , bytestring + , cabal + , containers + , compareSizes + , compiler + , deepseq + , directory + , filepath + , ghc + , ghcBoot + , ghcBootTh + , ghcCabal + , ghci + , ghcPkg + , ghcPrim + , haskeline + , hoopl + , hpc + , hpcBin + , hsc2hs + , integerLibrary + , pretty + , process + , rts + , runGhc + , templateHaskell + , time + , transformers ] ++ + [ iservBin | not win ] ++ + [ terminfo | not win, not ios ] ++ + [ unix | not win ] ++ + [ win32 | win ] ++ + [ xhtml | doc ] -- TODO: Currently there is an unchecked assumption that we build only programs -- in Stage2 and Stage3. Can we check this in compile time? packagesStage2 :: Packages -packagesStage2 = mconcat - [ append [checkApiAnnotations, ghcTags ] - , buildHaddock flavour ? append [haddock] ] +packagesStage2 = stage2 ? do + doc <- buildHaddock flavour + append $ [ checkApiAnnotations + , ghcTags ] ++ + [ haddock | doc ] -- TODO: What about profilingDynamic way? Do we need platformSupportsSharedLibs? -- | Default build ways for library packages: From git at git.haskell.org Fri Oct 27 01:14:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop old TODOs (92b5c35) Message-ID: <20171027011446.877EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/92b5c3507f296b1676cb7711c09d3e78ec2dfbef/ghc >--------------------------------------------------------------- commit 92b5c3507f296b1676cb7711c09d3e78ec2dfbef Author: Andrey Mokhov Date: Sun Nov 27 17:51:57 2016 +0000 Drop old TODOs See #113 >--------------------------------------------------------------- 92b5c3507f296b1676cb7711c09d3e78ec2dfbef src/Settings/Path.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 9e88ca6..13ef02a 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -37,7 +37,6 @@ generatedPath = buildRootPath -/- "generated" stageDirectory :: Stage -> FilePath stageDirectory = stageString --- TODO: Move to buildRootPath, see #113. -- | Directory for binaries that are built "in place". programInplacePath :: FilePath programInplacePath = "inplace/bin" @@ -141,7 +140,6 @@ libffiContext = vanillaContext Stage1 libffi libffiBuildPath :: FilePath libffiBuildPath = buildPath libffiContext --- TODO: Move to buildRootPath, see #113. -- | Path to package database directory of a given 'Stage'. Note: StageN, N > 0, -- share the same packageDbDirectory. packageDbDirectory :: Stage -> FilePath From git at git.haskell.org Fri Oct 27 01:14:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add GhcPkgMode (31c6109) Message-ID: <20171027011450.5CABB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31c6109cce4304c1a978fad6b399b91fbb7fe9d0/ghc >--------------------------------------------------------------- commit 31c6109cce4304c1a978fad6b399b91fbb7fe9d0 Author: Andrey Mokhov Date: Sun Nov 27 18:11:58 2016 +0000 Add GhcPkgMode >--------------------------------------------------------------- 31c6109cce4304c1a978fad6b399b91fbb7fe9d0 src/Builder.hs | 12 ++++++++++-- src/GHC.hs | 4 ++-- src/Oracles/Path.hs | 38 +++++++++++++++++++------------------- src/Rules/Register.hs | 6 ++++-- src/Rules/Test.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 20 ++++++++++---------- src/Settings/Builders/GhcPkg.hs | 26 ++++++++++---------------- 7 files changed, 57 insertions(+), 53 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 31c6109cce4304c1a978fad6b399b91fbb7fe9d0 From git at git.haskell.org Fri Oct 27 01:14:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop references to #113 (0412d60) Message-ID: <20171027011453.D5A5D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0412d60aef702d221af1b7c12ed96f1421c8d199/ghc >--------------------------------------------------------------- commit 0412d60aef702d221af1b7c12ed96f1421c8d199 Author: Andrey Mokhov Date: Sun Nov 27 18:23:04 2016 +0000 Drop references to #113 [skip ci] >--------------------------------------------------------------- 0412d60aef702d221af1b7c12ed96f1421c8d199 README.md | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index d869f4b..0d7b3d8 100644 --- a/README.md +++ b/README.md @@ -45,8 +45,8 @@ flags below). Using the build system ---------------------- -Once your first build is successful, simply run `build` to rebuild. Most build artefacts -are placed into `_build` and `inplace` directories ([#113][build-artefacts-issue]). +Once your first build is successful, simply run `build` to rebuild. Build results +are placed into `_build` and `inplace` directories. #### Command line flags @@ -92,11 +92,10 @@ use `hadrian/UserSettings.hs` for the same purpose, see [documentation](doc/user #### Clean and full rebuild -* `build clean` removes all build artefacts. Note, we are working towards a -complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. +* `build clean` removes all build artefacts. -* `build -B` forces Shake to rerun all rules, even if results of the previous build -are still in the GHC tree. +* `build -B` forces Shake to rerun all rules, even if the previous build results are +are still up-to-date. #### Source distribution @@ -156,7 +155,6 @@ helped me endure and enjoy the project. [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild [windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md -[build-artefacts-issue]: https://github.com/snowleopard/hadrian/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 From git at git.haskell.org Fri Oct 27 01:14:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Directory package no longer needs special treatment (1eff9b4) Message-ID: <20171027011457.87C723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1eff9b4e3114eb38e935def533b54ce0235a6331/ghc >--------------------------------------------------------------- commit 1eff9b4e3114eb38e935def533b54ce0235a6331 Author: Andrey Mokhov Date: Sun Nov 27 22:18:41 2016 +0000 Directory package no longer needs special treatment >--------------------------------------------------------------- 1eff9b4e3114eb38e935def533b54ce0235a6331 hadrian.cabal | 1 - src/Settings/Default.hs | 2 -- src/Settings/Packages/Directory.hs | 12 ------------ 3 files changed, 15 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 30ed256..374b5a0 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -89,7 +89,6 @@ executable hadrian , Settings.Flavours.Quickest , Settings.Packages.Base , Settings.Packages.Compiler - , Settings.Packages.Directory , Settings.Packages.Ghc , Settings.Packages.GhcCabal , Settings.Packages.GhcPrim diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 6f56c5d..b5df4b5 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -29,7 +29,6 @@ import Settings.Builders.Make import Settings.Builders.Tar import Settings.Packages.Base import Settings.Packages.Compiler -import Settings.Packages.Directory import Settings.Packages.Ghc import Settings.Packages.GhcCabal import Settings.Packages.GhcPrim @@ -194,7 +193,6 @@ defaultPackageArgs :: Args defaultPackageArgs = mconcat [ basePackageArgs , compilerPackageArgs - , directoryPackageArgs , ghcPackageArgs , ghcCabalPackageArgs , ghcPrimPackageArgs diff --git a/src/Settings/Packages/Directory.hs b/src/Settings/Packages/Directory.hs deleted file mode 100644 index 5b5d96b..0000000 --- a/src/Settings/Packages/Directory.hs +++ /dev/null @@ -1,12 +0,0 @@ -module Settings.Packages.Directory (directoryPackageArgs) where - -import GHC -import Predicate - --- TODO: I had to define symbol __GLASGOW_HASKELL__ as otherwise directory.c is --- effectively empty. I presume it was expected that GHC will be used for --- compiling all C files, but I don't know why. It seems that directory.c is the --- only file which requires special treatment when using GCC. -directoryPackageArgs :: Args -directoryPackageArgs = package directory ? - builder Cc ? arg "-D__GLASGOW_HASKELL__" From git at git.haskell.org Fri Oct 27 01:15:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (6552aff) Message-ID: <20171027011501.131453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6552aff7cf7fde37106b03b851e6d4cdbe515b74/ghc >--------------------------------------------------------------- commit 6552aff7cf7fde37106b03b851e6d4cdbe515b74 Author: Andrey Mokhov Date: Sun Nov 27 22:39:42 2016 +0000 Minor revision >--------------------------------------------------------------- 6552aff7cf7fde37106b03b851e6d4cdbe515b74 src/Settings/Builders/Cc.hs | 5 ++--- src/Settings/Builders/Haddock.hs | 3 +-- src/Settings/Packages/Compiler.hs | 6 ++---- src/Settings/Packages/IntegerGmp.hs | 4 +--- src/Settings/Packages/Rts.hs | 11 +++++------ src/Settings/Packages/RunGhc.hs | 5 ++--- 6 files changed, 13 insertions(+), 21 deletions(-) diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index b0a5f0e..b5d85df 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -8,9 +8,8 @@ ccBuilderArgs = builder Cc ? mconcat , argSettingList . ConfCcArgs =<< getStage , cIncludeArgs - , builder (Cc CompileC) ? - mconcat [ arg "-c", arg =<< getInput - , arg "-o", arg =<< getOutput ] + , builder (Cc CompileC) ? mconcat [ arg "-c", arg =<< getInput + , arg "-o", arg =<< getOutput ] , builder (Cc FindCDependencies) ? do output <- getOutput diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 312124a..3fff015 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -16,7 +16,6 @@ haddockBuilderArgs = builder Haddock ? do path <- getBuildPath version <- getPkgData Version synopsis <- getPkgData Synopsis - hidden <- getPkgDataList HiddenModules deps <- getPkgDataList Deps depNames <- getPkgDataList DepNames hVersion <- lift . pkgData . Version $ buildPath (vanillaContext Stage2 haddock) @@ -31,7 +30,7 @@ haddockBuilderArgs = builder Haddock ? do , arg $ "--title=" ++ pkgNameString pkg ++ "-" ++ version ++ ": " ++ synopsis , arg $ "--prologue=" ++ path -/- "haddock-prologue.txt" , arg $ "--optghc=-D__HADDOCK_VERSION__=" ++ show (versionToInt hVersion) - , append $ map ("--hide=" ++) hidden + , append . map ("--hide=" ++) =<< getPkgDataList HiddenModules , append $ [ "--read-interface=../" ++ dep ++ ",../" ++ dep ++ "/src/%{MODULE/./-}.html\\#%{NAME}," ++ pkgHaddockFile (vanillaContext Stage1 depPkg) diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 03b8081..308b3c2 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -35,8 +35,6 @@ compilerPackageArgs = package compiler ? do ghciWithDebugger flavour ? notStage0 ? arg "--ghc-option=-DDEBUGGER" , ghcProfiled flavour ? - notStage0 ? arg "--ghc-pkg-option=--force" - ] + notStage0 ? arg "--ghc-pkg-option=--force" ] - , builder Haddock ? arg ("--optghc=-I" ++ path) - ] + , builder Haddock ? arg ("--optghc=-I" ++ path) ] diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index def2021..7dfcb2f 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -15,12 +15,10 @@ integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" gmpIncludeDir <- getSetting GmpIncludeDir gmpLibDir <- getSetting GmpLibDir - mconcat [ builder Cc ? arg includeGmp , builder GhcCabal ? mconcat [ (null gmpIncludeDir && null gmpLibDir) ? arg "--configure-option=--with-intree-gmp" , appendSub "--configure-option=CFLAGS" [includeGmp] - , appendSub "--gcc-options" [includeGmp] ] - ] + , appendSub "--gcc-options" [includeGmp] ] ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index d10c6f0..7d844fa 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -12,10 +12,10 @@ rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do useSystemFfi <- flag UseSystemFfi windows <- windowsHost - case (useSystemFfi, windows) of - (True , False) -> return "ffi" - (False, False) -> return "Cffi" - (_ , True ) -> return "Cffi-6" + return $ case (useSystemFfi, windows) of + (True , False) -> "ffi" + (False, False) -> "Cffi" + (_ , True ) -> "Cffi-6" rtsPackageArgs :: Args rtsPackageArgs = package rts ? do @@ -88,8 +88,7 @@ rtsPackageArgs = package rts ? do [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir , "-DFFI_LIB_DIR=" ++ show ffiLibraryDir - , "-DFFI_LIB=" ++ show libffiName ] - ] + , "-DFFI_LIB=" ++ show libffiName ] ] -- # If we're compiling on windows, enforce that we only support XP+ -- # Adding this here means it doesn't have to be done in individual .c files diff --git a/src/Settings/Packages/RunGhc.hs b/src/Settings/Packages/RunGhc.hs index 6880344..dc8ab1f 100644 --- a/src/Settings/Packages/RunGhc.hs +++ b/src/Settings/Packages/RunGhc.hs @@ -5,7 +5,6 @@ import Oracles.Config.Setting import Predicate runGhcPackageArgs :: Args -runGhcPackageArgs = package runGhc ? do +runGhcPackageArgs = package runGhc ? builder Ghc ? input "//Main.hs" ? do version <- getSetting ProjectVersion - builder Ghc ? input "//Main.hs" ? - append ["-cpp", "-DVERSION=" ++ show version] + append ["-cpp", "-DVERSION=" ++ show version] From git at git.haskell.org Fri Oct 27 01:15:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths in inplace-pkg-config files (e081b08) Message-ID: <20171027011504.9B7C83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e081b081214295de8a31631e9d00642965f7fc23/ghc >--------------------------------------------------------------- commit e081b081214295de8a31631e9d00642965f7fc23 Author: Andrey Mokhov Date: Fri Dec 16 01:27:46 2016 +0000 Fix paths in inplace-pkg-config files >--------------------------------------------------------------- e081b081214295de8a31631e9d00642965f7fc23 src/Rules/Data.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index dc53654..cff0896 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -47,10 +47,8 @@ buildPackageData context at Context {..} = do . replace "rts/dist/build" rtsBuildPath . replace "includes/dist-derivedconstants/header" generatedPath ) . lines - else do - top <- topDirectory - let oldPath = top -/- path "build" - fixFile conf $ unlines . map (replace oldPath path) . lines + else + fixFile conf $ unlines . map (replace (path "build") path) . lines priority 2.0 $ when (nonCabalContext context) $ dataFile %> generatePackageData context From git at git.haskell.org Fri Oct 27 01:15:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Handle Make correctly in needBuilder, refactor customBuild (7f62b5a) Message-ID: <20171027011508.2C3CC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7f62b5a774b790a750651a834cc0de6ffaf61943/ghc >--------------------------------------------------------------- commit 7f62b5a774b790a750651a834cc0de6ffaf61943 Author: Andrey Mokhov Date: Fri Dec 16 21:07:13 2016 +0000 Handle Make correctly in needBuilder, refactor customBuild See #295 >--------------------------------------------------------------- 7f62b5a774b790a750651a834cc0de6ffaf61943 src/Util.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Util.hs b/src/Util.hs index 81f67dd..b6d9536 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -61,7 +61,6 @@ customBuild rs opts target at Target {..} = do cmd [Cwd output] [path] "x" (top -/- input) Configure dir -> do - need [dir -/- "configure"] -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" cmd Shell cmdEcho env [Cwd dir] [path] opts argList @@ -76,9 +75,7 @@ customBuild rs opts target at Target {..} = do Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output - Make dir -> do - need [dir -/- "Makefile"] - cmd Shell cmdEcho path ["-C", dir] argList + Make dir -> cmd Shell cmdEcho path ["-C", dir] argList _ -> cmd [path] argList @@ -170,6 +167,7 @@ isInternal = isJust . builderProvenance -- | Make sure a 'Builder' exists and rebuild it if out of date. needBuilder :: Builder -> Action () needBuilder (Configure dir) = need [dir -/- "configure"] +needBuilder (Make dir) = need [dir -/- "Makefile"] needBuilder builder = when (isInternal builder) $ do path <- builderPath builder need [path] From git at git.haskell.org Fri Oct 27 01:15:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Adapt to Cabal library changes (6984895) Message-ID: <20171027011511.976E33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/69848955eb325f901ee8a2d387147e5b223e0363/ghc >--------------------------------------------------------------- commit 69848955eb325f901ee8a2d387147e5b223e0363 Author: Andrey Mokhov Date: Fri Dec 30 23:05:50 2016 +0000 Adapt to Cabal library changes >--------------------------------------------------------------- 69848955eb325f901ee8a2d387147e5b223e0363 src/Rules/Cabal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 370bda2..6adaf44 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -4,6 +4,7 @@ import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Text +import Distribution.Types.Dependency import Distribution.Verbosity import Base From git at git.haskell.org Fri Oct 27 01:15:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build ghci library in Stage0 (8e3cb44) Message-ID: <20171027011515.216473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e3cb447a9476196099fc7a6b22d0d177795263f/ghc >--------------------------------------------------------------- commit 8e3cb447a9476196099fc7a6b22d0d177795263f Author: Andrey Mokhov Date: Fri Dec 30 23:19:27 2016 +0000 Build ghci library in Stage0 >--------------------------------------------------------------- 8e3cb447a9476196099fc7a6b22d0d177795263f src/Settings/Default.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index b5df4b5..ba4ef79 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -67,6 +67,7 @@ stage0Packages = do , ghcBoot , ghcBootTh , ghcCabal + , ghci , ghcPkg , hsc2hs , hoopl From git at git.haskell.org Fri Oct 27 01:15:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build internal ghci support in Stage1 (552bb90) Message-ID: <20171027011518.907E63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/552bb90ed6b3408018c8c9952c5c0f1b28323694/ghc >--------------------------------------------------------------- commit 552bb90ed6b3408018c8c9952c5c0f1b28323694 Author: Andrey Mokhov Date: Sat Dec 31 01:03:52 2016 +0000 Build internal ghci support in Stage1 >--------------------------------------------------------------- 552bb90ed6b3408018c8c9952c5c0f1b28323694 hadrian.cabal | 1 + src/Settings/Default.hs | 2 ++ src/Settings/Packages/Ghci.hs | 7 +++++++ 3 files changed, 10 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 374b5a0..a186d7d 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -91,6 +91,7 @@ executable hadrian , Settings.Packages.Compiler , Settings.Packages.Ghc , Settings.Packages.GhcCabal + , Settings.Packages.Ghci , Settings.Packages.GhcPrim , Settings.Packages.Haddock , Settings.Packages.IntegerGmp diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index ba4ef79..37fcdfa 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -31,6 +31,7 @@ import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Ghc import Settings.Packages.GhcCabal +import Settings.Packages.Ghci import Settings.Packages.GhcPrim import Settings.Packages.Haddock import Settings.Packages.IntegerGmp @@ -196,6 +197,7 @@ defaultPackageArgs = mconcat , compilerPackageArgs , ghcPackageArgs , ghcCabalPackageArgs + , ghciPackageArgs , ghcPrimPackageArgs , haddockPackageArgs , integerGmpPackageArgs diff --git a/src/Settings/Packages/Ghci.hs b/src/Settings/Packages/Ghci.hs new file mode 100644 index 0000000..3d14691 --- /dev/null +++ b/src/Settings/Packages/Ghci.hs @@ -0,0 +1,7 @@ +module Settings.Packages.Ghci (ghciPackageArgs) where + +import GHC +import Predicate + +ghciPackageArgs :: Args +ghciPackageArgs = notStage0 ? package ghci ? builder GhcCabal ? arg "--flags=ghci" From git at git.haskell.org Fri Oct 27 01:15:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build compact library (374b10a) Message-ID: <20171027011522.3357C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/374b10aa7af36884484e05d7e6ac02295be60957/ghc >--------------------------------------------------------------- commit 374b10aa7af36884484e05d7e6ac02295be60957 Author: Andrey Mokhov Date: Sat Dec 31 01:04:40 2016 +0000 Build compact library >--------------------------------------------------------------- 374b10aa7af36884484e05d7e6ac02295be60957 src/GHC.hs | 33 ++++++++++++++++++--------------- src/Settings/Default.hs | 3 ++- 2 files changed, 20 insertions(+), 16 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 1fff56f..f8abeb8 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,13 +1,14 @@ {-# LANGUAGE OverloadedStrings, LambdaCase #-} {-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( - array, base, binary, bytestring, cabal, checkApiAnnotations, compiler, - containers, compareSizes, deepseq, deriveConstants, directory, dllSplit, - filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci, - ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, - hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, - parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, - terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, + array, base, binary, bytestring, cabal, checkApiAnnotations, compact, + compareSizes, compiler, containers, deepseq, deriveConstants, directory, + dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, + ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, + hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, + libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, + stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, + win32, xhtml, defaultKnownPackages, builderProvenance, programName, nonCabalContext, nonHsMainPackage @@ -25,13 +26,14 @@ import Stage -- be overridden in @hadrian/src/UserSettings.hs at . defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, binary, bytestring, cabal, checkApiAnnotations, compiler - , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci - , ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc - , hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart - , parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell - , terminfo, time, touchy, transformers, unlit, unix, win32, xhtml ] + [ array, base, binary, bytestring, cabal, checkApiAnnotations, compact + , compareSizes, compiler, containers, deepseq, deriveConstants, directory + , dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh + , ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs + , hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi + , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm + , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 + , xhtml ] -- | Package definitions, see 'Package'. array = library "array" @@ -40,9 +42,10 @@ binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" checkApiAnnotations = utility "check-api-annotations" +compact = library "compact" +compareSizes = utility "compareSizes" `setPath` "utils/compare_sizes" compiler = topLevel "ghc" `setPath` "compiler" containers = library "containers" -compareSizes = utility "compareSizes" `setPath` "utils/compare_sizes" deepseq = library "deepseq" deriveConstants = utility "deriveConstants" directory = library "directory" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 37fcdfa..67b0d5d 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -90,8 +90,9 @@ stage1Packages = do , append $ [ array , base , bytestring - , containers + , compact , compareSizes + , containers , deepseq , directory , filepath From git at git.haskell.org Fri Oct 27 01:15:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add perf flavour (6508f4b) Message-ID: <20171027011525.DFBB23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6508f4b94dd9f0c476269191ce2a083856ef2d60/ghc >--------------------------------------------------------------- commit 6508f4b94dd9f0c476269191ce2a083856ef2d60 Author: Andrey Mokhov Date: Fri Jan 6 00:59:26 2017 +0000 Add perf flavour >--------------------------------------------------------------- 6508f4b94dd9f0c476269191ce2a083856ef2d60 hadrian.cabal | 1 + src/Settings.hs | 3 ++- src/Settings/Flavours/Perf.hs | 21 +++++++++++++++++++++ 3 files changed, 24 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index a186d7d..4f3c2f6 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -85,6 +85,7 @@ executable hadrian , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default + , Settings.Flavours.Perf , Settings.Flavours.Quick , Settings.Flavours.Quickest , Settings.Packages.Base diff --git a/src/Settings.hs b/src/Settings.hs index bef47f1..18dd15b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -14,6 +14,7 @@ import GHC import Oracles.PackageData import Oracles.Path import {-# SOURCE #-} Settings.Default +import Settings.Flavours.Perf import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Path @@ -50,7 +51,7 @@ getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getBuildPath hadrianFlavours :: [Flavour] -hadrianFlavours = [defaultFlavour, quickFlavour, quickestFlavour] +hadrianFlavours = [defaultFlavour, perfFlavour, quickFlavour, quickestFlavour] flavour :: Flavour flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours diff --git a/src/Settings/Flavours/Perf.hs b/src/Settings/Flavours/Perf.hs new file mode 100644 index 0000000..d246b15 --- /dev/null +++ b/src/Settings/Flavours/Perf.hs @@ -0,0 +1,21 @@ +module Settings.Flavours.Perf (perfFlavour) where + +import Context +import Flavour +import GHC +import Predicate +import {-# SOURCE #-} Settings.Default + +perfFlavour :: Flavour +perfFlavour = defaultFlavour + { name = "perf" + , args = defaultArgs <> perfArgs } + +optimise :: Context -> Bool +optimise Context {..} = + package `elem` [compiler, ghc] && stage == Stage2 || isLibrary package + +perfArgs :: Args +perfArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O2" else arg "-O" From git at git.haskell.org Fri Oct 27 01:15:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing profiling flags (9c8d9bf) Message-ID: <20171027011529.5937E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c8d9bf40b129f2faa8f50525c3fac5b322d808f/ghc >--------------------------------------------------------------- commit 9c8d9bf40b129f2faa8f50525c3fac5b322d808f Author: Andrey Mokhov Date: Fri Jan 6 01:59:23 2017 +0000 Add missing profiling flags >--------------------------------------------------------------- 9c8d9bf40b129f2faa8f50525c3fac5b322d808f src/Predicate.hs | 10 +++++++++- src/Settings/Packages/Compiler.hs | 3 +++ 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/src/Predicate.hs b/src/Predicate.hs index d38d9d5..5da5c54 100644 --- a/src/Predicate.hs +++ b/src/Predicate.hs @@ -2,7 +2,7 @@ -- | Convenient predicates module Predicate ( module Expression, stage, stage0, stage1, stage2, notStage0, builder, - package, notPackage, input, output, way + package, notPackage, input, inputs, output, outputs, way ) where import Base @@ -52,10 +52,18 @@ instance BuilderLike a => BuilderLike (FilePath -> a) where input :: FilePattern -> Predicate input f = any (f ?==) <$> getInputs +-- | Does any of the input files match any of the given patterns? +inputs :: [FilePattern] -> Predicate +inputs = anyM input + -- | Does any of the output files match a given pattern? output :: FilePattern -> Predicate output f = any (f ?==) <$> getOutputs +-- | Does any of the output files match any of the given patterns? +outputs :: [FilePattern] -> Predicate +outputs = anyM output + -- | Is the current build 'Way' equal to a certain value? way :: Way -> Predicate way w = (w ==) <$> getWay diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 308b3c2..9280a81 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -15,6 +15,9 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" + , builder (Ghc CompileHs) ? + inputs ["//GHC.hs", "//GhcMake.hs"] ? arg "-fprof-auto" + , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) , arg "--disable-library-for-ghci" From git at git.haskell.org Fri Oct 27 01:15:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add prof flavour (bc44c00) Message-ID: <20171027011532.E43FF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc44c00792276d7834258db442af9fe687d22a01/ghc >--------------------------------------------------------------- commit bc44c00792276d7834258db442af9fe687d22a01 Author: Andrey Mokhov Date: Fri Jan 6 02:00:02 2017 +0000 Add prof flavour >--------------------------------------------------------------- bc44c00792276d7834258db442af9fe687d22a01 hadrian.cabal | 1 + src/Settings.hs | 4 +++- src/Settings/Flavours/Prof.hs | 21 +++++++++++++++++++++ 3 files changed, 25 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 4f3c2f6..712d4c6 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -86,6 +86,7 @@ executable hadrian , Settings.Builders.Tar , Settings.Default , Settings.Flavours.Perf + , Settings.Flavours.Prof , Settings.Flavours.Quick , Settings.Flavours.Quickest , Settings.Packages.Base diff --git a/src/Settings.hs b/src/Settings.hs index 18dd15b..8f94e5b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -15,6 +15,7 @@ import Oracles.PackageData import Oracles.Path import {-# SOURCE #-} Settings.Default import Settings.Flavours.Perf +import Settings.Flavours.Prof import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Path @@ -51,7 +52,8 @@ getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getBuildPath hadrianFlavours :: [Flavour] -hadrianFlavours = [defaultFlavour, perfFlavour, quickFlavour, quickestFlavour] +hadrianFlavours = [ defaultFlavour, perfFlavour, profFlavour, quickFlavour + , quickestFlavour ] flavour :: Flavour flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours diff --git a/src/Settings/Flavours/Prof.hs b/src/Settings/Flavours/Prof.hs new file mode 100644 index 0000000..4dee8fc --- /dev/null +++ b/src/Settings/Flavours/Prof.hs @@ -0,0 +1,21 @@ +module Settings.Flavours.Prof (profFlavour) where + +import Context +import Flavour +import GHC +import Predicate +import {-# SOURCE #-} Settings.Default + +profFlavour :: Flavour +profFlavour = defaultFlavour + { name = "prof" + , args = defaultArgs <> profArgs + , ghcProfiled = True } + +optimise :: Context -> Bool +optimise Context {..} = package `elem` [compiler, ghc] || isLibrary package + +profArgs :: Args +profArgs = builder Ghc ? do + context <- getContext + if optimise context then arg "-O" else arg "-O0" From git at git.haskell.org Fri Oct 27 01:15:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing flags for Parser module (3201312) Message-ID: <20171027011536.714DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3201312c71ea91128a11942ff66792f175bed255/ghc >--------------------------------------------------------------- commit 3201312c71ea91128a11942ff66792f175bed255 Author: Andrey Mokhov Date: Fri Jan 6 02:33:02 2017 +0000 Add missing flags for Parser module See #268 >--------------------------------------------------------------- 3201312c71ea91128a11942ff66792f175bed255 src/Settings/Flavours/Perf.hs | 2 +- src/Settings/Flavours/Prof.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/Quickest.hs | 2 +- src/Settings/Packages/Compiler.hs | 6 ++++-- 5 files changed, 8 insertions(+), 6 deletions(-) diff --git a/src/Settings/Flavours/Perf.hs b/src/Settings/Flavours/Perf.hs index d246b15..7641657 100644 --- a/src/Settings/Flavours/Perf.hs +++ b/src/Settings/Flavours/Perf.hs @@ -9,7 +9,7 @@ import {-# SOURCE #-} Settings.Default perfFlavour :: Flavour perfFlavour = defaultFlavour { name = "perf" - , args = defaultArgs <> perfArgs } + , args = defaultBuilderArgs <> perfArgs <> defaultPackageArgs } optimise :: Context -> Bool optimise Context {..} = diff --git a/src/Settings/Flavours/Prof.hs b/src/Settings/Flavours/Prof.hs index 4dee8fc..6d94b90 100644 --- a/src/Settings/Flavours/Prof.hs +++ b/src/Settings/Flavours/Prof.hs @@ -9,7 +9,7 @@ import {-# SOURCE #-} Settings.Default profFlavour :: Flavour profFlavour = defaultFlavour { name = "prof" - , args = defaultArgs <> profArgs + , args = defaultBuilderArgs <> profArgs <> defaultPackageArgs , ghcProfiled = True } optimise :: Context -> Bool diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 448a875..1e4f5c0 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -9,7 +9,7 @@ import {-# SOURCE #-} Settings.Default quickFlavour :: Flavour quickFlavour = defaultFlavour { name = "quick" - , args = defaultArgs <> quickArgs + , args = defaultBuilderArgs <> quickArgs <> defaultPackageArgs , libraryWays = defaultLibraryWays <> quickLibraryWays } optimise :: Context -> Bool diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 9f9b85b..477a245 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -7,7 +7,7 @@ import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour quickestFlavour = defaultFlavour { name = "quickest" - , args = defaultArgs <> quickestArgs + , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs , libraryWays = defaultLibraryWays <> quickestLibraryWays } quickestArgs :: Args diff --git a/src/Settings/Packages/Compiler.hs b/src/Settings/Packages/Compiler.hs index 9280a81..8cc05cb 100644 --- a/src/Settings/Packages/Compiler.hs +++ b/src/Settings/Packages/Compiler.hs @@ -15,8 +15,10 @@ compilerPackageArgs = package compiler ? do path <- getBuildPath mconcat [ builder Alex ? arg "--latin1" - , builder (Ghc CompileHs) ? - inputs ["//GHC.hs", "//GhcMake.hs"] ? arg "-fprof-auto" + , builder (Ghc CompileHs) ? mconcat + [ inputs ["//GHC.hs", "//GhcMake.hs"] ? arg "-fprof-auto" + , input "//Parser.hs" ? + append ["-O0", "-fno-ignore-interface-pragmas", "-fcmm-sink" ] ] , builder GhcCabal ? mconcat [ arg $ "--ghc-option=-DSTAGE=" ++ show (fromEnum stage + 1) From git at git.haskell.org Fri Oct 27 01:15:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (25a6441) Message-ID: <20171027011539.E35F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/25a64411df44615296349aec133c180b8f008762/ghc >--------------------------------------------------------------- commit 25a64411df44615296349aec133c180b8f008762 Author: Andrey Mokhov Date: Fri Jan 6 02:59:20 2017 +0000 Minor revision >--------------------------------------------------------------- 25a64411df44615296349aec133c180b8f008762 src/Settings/Packages/Rts.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 7d844fa..8e71c87 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -56,7 +56,7 @@ rtsPackageArgs = package rts ? do , way == threaded ? arg "-DTHREADED_RTS" - , (input "//RtsMessages.c" ||^ input "//Trace.c") ? + , inputs ["//RtsMessages.c", "//Trace.c"] ? arg ("-DProjectVersion=" ++ show projectVersion) , input "//RtsUtils.c" ? append @@ -76,11 +76,10 @@ rtsPackageArgs = package rts ? do , "-DGhcUnregisterised=" ++ show ghcUnreg , "-DGhcEnableTablesNextToCode=" ++ show ghcEnableTNC ] - , input "//Evac.c" ? arg "-funroll-loops" - , input "//Evac_thr.c" ? arg "-funroll-loops" + , inputs ["//Evac.c", "//Evac_thr.c"] ? arg "-funroll-loops" - , input "//Evac_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] - , input "//Scav_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] ] + , inputs ["//Evac_thr.c", "//Scav_thr.c"] ? + append [ "-DPARALLEL_GC", "-Irts/sm" ] ] , builder Ghc ? arg "-Irts" From git at git.haskell.org Fri Oct 27 01:15:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move -Wall before custom package settings, drop tab warnings (ab1c922) Message-ID: <20171027011543.7403E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ab1c922d6531519e91ebed34b47070ba6fdc4170/ghc >--------------------------------------------------------------- commit ab1c922d6531519e91ebed34b47070ba6fdc4170 Author: Andrey Mokhov Date: Fri Jan 6 16:34:21 2017 +0000 Move -Wall before custom package settings, drop tab warnings See #296 >--------------------------------------------------------------- ab1c922d6531519e91ebed34b47070ba6fdc4170 src/Settings/Builders/Ghc.hs | 5 ++--- src/Settings/Default.hs | 5 +---- 2 files changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index f5b13e1..98e5e39 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -7,12 +7,11 @@ import Settings.Builders.Common ghcBuilderArgs :: Args ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do needTouchy - mconcat [ commonGhcArgs + mconcat [ arg "-Wall" + , commonGhcArgs , arg "-H32m" , stage0 ? arg "-O" , notStage0 ? arg "-O2" - , arg "-Wall" - , arg "-fwarn-tabs" , splitObjectsArgs , ghcLinkArgs , builder (Ghc CompileHs) ? arg "-c" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 67b0d5d..061d4ae 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -41,10 +41,7 @@ import UserSettings -- | All default command line arguments. defaultArgs :: Args -defaultArgs = mconcat - [ defaultBuilderArgs - , defaultPackageArgs - , builder Ghc ? remove ["-Wall", "-fwarn-tabs"] ] -- TODO: Fix warning Args. +defaultArgs = defaultBuilderArgs <> defaultPackageArgs -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". From git at git.haskell.org Fri Oct 27 01:15:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Duplicate libffi library for each build way (c88fc78) Message-ID: <20171027011546.F2BD63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c88fc78440eb105ba5fe7d9a8bede47b30de36d6/ghc >--------------------------------------------------------------- commit c88fc78440eb105ba5fe7d9a8bede47b30de36d6 Author: Andrey Mokhov Date: Sat Jan 7 02:50:04 2017 +0000 Duplicate libffi library for each build way >--------------------------------------------------------------- c88fc78440eb105ba5fe7d9a8bede47b30de36d6 src/Rules/Libffi.hs | 4 ++-- src/Settings/Packages/Rts.hs | 11 +++++++++-- 2 files changed, 11 insertions(+), 4 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 65ec1d7..0f703d9 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -55,8 +55,8 @@ libffiRules = do forM_ hs $ \header -> copyFile header (rtsBuildPath -/- takeFileName header) - libffiName <- rtsLibffiLibraryName - copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") + ways <- interpretInContext libffiContext (getLibraryWays <> getRtsWays) + forM_ ways $ \way -> copyFile libffiLibrary =<< rtsLibffiLibrary way putSuccess $ "| Successfully built custom library 'libffi'" diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 8e71c87..e8000c8 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,4 +1,4 @@ -module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibraryName) where +module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibrary) where import Base import GHC @@ -7,6 +7,7 @@ import Oracles.Config.Setting import Oracles.Path import Predicate import Settings +import Settings.Path rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do @@ -17,6 +18,12 @@ rtsLibffiLibraryName = do (False, False) -> "Cffi" (_ , True ) -> "Cffi-6" +rtsLibffiLibrary :: Way -> Action FilePath +rtsLibffiLibrary way = do + name <- rtsLibffiLibraryName + suf <- libsuf way + return $ rtsBuildPath -/- "lib" ++ name ++ suf + rtsPackageArgs :: Args rtsPackageArgs = package rts ? do let yesNo = lift . fmap (\x -> if x then "YES" else "NO") @@ -38,7 +45,7 @@ rtsPackageArgs = package rts ? do way <- getWay path <- getBuildPath top <- getTopDirectory - libffiName <- lift $ rtsLibffiLibraryName + libffiName <- lift rtsLibffiLibraryName ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir mconcat From git at git.haskell.org Fri Oct 27 01:15:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix way-specific flags (8e7685c) Message-ID: <20171027011550.988AD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e7685c496e1ef4627d3f3b9d0850e6d5b487e07/ghc >--------------------------------------------------------------- commit 8e7685c496e1ef4627d3f3b9d0850e6d5b487e07 Author: Andrey Mokhov Date: Sat Jan 7 02:50:41 2017 +0000 Fix way-specific flags >--------------------------------------------------------------- 8e7685c496e1ef4627d3f3b9d0850e6d5b487e07 src/Settings/Packages/Rts.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e8000c8..6855402 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -61,7 +61,10 @@ rtsPackageArgs = package rts ? do -- be inlined. See also #90. , arg "-O2" - , way == threaded ? arg "-DTHREADED_RTS" + , Debug `wayUnit` way ? arg "-DDEBUG" + , way `elem` [debug, debugDynamic] ? arg "-DTICKY_TICKY" + , Profiling `wayUnit` way ? arg "-DPROFILING" + , Threaded `wayUnit` way ? arg "-DTHREADED_RTS" , inputs ["//RtsMessages.c", "//Trace.c"] ? arg ("-DProjectVersion=" ++ show projectVersion) From git at git.haskell.org Fri Oct 27 01:15:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix profiled GHC (76de227) Message-ID: <20171027011554.115AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/76de227586804a1bf4b4a98e0307f09966348609/ghc >--------------------------------------------------------------- commit 76de227586804a1bf4b4a98e0307f09966348609 Author: Andrey Mokhov Date: Sat Jan 7 02:55:48 2017 +0000 Fix profiled GHC See #239 >--------------------------------------------------------------- 76de227586804a1bf4b4a98e0307f09966348609 src/Rules.hs | 7 ++++--- src/Rules/Program.hs | 7 +++---- src/Settings.hs | 7 ++++++- 3 files changed, 13 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 832bf4c..be7c89b 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -49,7 +49,7 @@ topLevelTargets = do docs <- interpretInContext context $ buildHaddock flavour need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else do -- otherwise build a program - need =<< maybeToList <$> programPath context + need =<< maybeToList <$> programPath (programContext stage pkg) packageRules :: Rules () packageRules = do @@ -61,21 +61,22 @@ packageRules = do let readPackageDb = [(packageDb, 1)] writePackageDb = [(packageDb, maxConcurrentReaders)] - -- TODO: not all build rules make sense for all stage/package combinations let contexts = liftM3 Context allStages knownPackages allWays vanillaContexts = liftM2 vanillaContext allStages knownPackages + programContexts = liftM2 programContext allStages knownPackages forM_ contexts $ mconcat [ Rules.Compile.compilePackage readPackageDb , Rules.Library.buildPackageLibrary ] + forM_ programContexts $ Rules.Program.buildProgram readPackageDb + forM_ vanillaContexts $ mconcat [ Rules.Data.buildPackageData , Rules.Dependencies.buildPackageDependencies readPackageDb , Rules.Documentation.buildPackageDocumentation , Rules.Library.buildPackageGhciLibrary , Rules.Generate.generatePackageCode - , Rules.Program.buildProgram readPackageDb , Rules.Register.registerPackage writePackageDb ] buildRules :: Rules () diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 319ca72..92aa4c1 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -30,7 +30,7 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do let installStage = do - latest <- latestBuildStage package -- isJust below is safe + latest <- latestBuildStage package -- fromJust below is safe return $ if package == ghc then stage else fromJust latest buildPath context -/- programName context <.> exe %> @@ -68,15 +68,14 @@ buildWrapper context at Context {..} wrapper wrapperPath binPath = do quote (pkgNameString package) ++ " (" ++ show stage ++ ")." -- TODO: Get rid of the Paths_hsc2hs.o hack. --- TODO: Do we need to consider other ways when building programs? buildBinary :: [(Resource, Int)] -> Context -> FilePath -> Action () buildBinary rs context at Context {..} bin = do binDeps <- if stage == Stage0 && package == ghcCabal then hsSources context else do - ways <- interpretInContext context getLibraryWays deps <- contextDependencies context - needContext [ dep { way = w } | dep <- deps, w <- ways ] + ways <- interpretInContext context (getLibraryWays <> getRtsWays) + needContext $ deps ++ [ rtsContext { way = w } | w <- ways ] let path = buildPath context cObjs <- map (objectPath context) <$> pkgDataList (CSrcs path) hsObjs <- hsObjects context diff --git a/src/Settings.hs b/src/Settings.hs index 8f94e5b..c455e0b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,7 +2,7 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, getContextDirectory, getBuildPath, stagePackages, builderPath, - getBuilderPath, isSpecified, latestBuildStage, programPath + getBuilderPath, isSpecified, latestBuildStage, programPath, programContext ) where import Base @@ -62,6 +62,11 @@ flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours flavours = hadrianFlavours ++ userFlavours flavourName = fromMaybe "default" cmdFlavour +programContext :: Stage -> Package -> Context +programContext stage pkg + | pkg == ghc && ghcProfiled flavour = Context stage pkg profiling + | otherwise = vanillaContext stage pkg + -- TODO: switch to Set Package as the order of packages should not matter? -- Otherwise we have to keep remembering to sort packages from time to time. knownPackages :: [Package] From git at git.haskell.org Fri Oct 27 01:15:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:15:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on RTS only when building GHC program (3ae4e1d) Message-ID: <20171027011557.7CEC73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ae4e1d0016ae2c28030da32180e5a5bda18de57/ghc >--------------------------------------------------------------- commit 3ae4e1d0016ae2c28030da32180e5a5bda18de57 Author: Andrey Mokhov Date: Sat Jan 7 03:22:41 2017 +0000 Depend on RTS only when building GHC program >--------------------------------------------------------------- 3ae4e1d0016ae2c28030da32180e5a5bda18de57 src/Rules/Program.hs | 7 ++++--- src/Settings/Flavours/Quickest.hs | 6 ++---- 2 files changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 92aa4c1..b1577e2 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -73,9 +73,10 @@ buildBinary rs context at Context {..} bin = do binDeps <- if stage == Stage0 && package == ghcCabal then hsSources context else do - deps <- contextDependencies context - ways <- interpretInContext context (getLibraryWays <> getRtsWays) - needContext $ deps ++ [ rtsContext { way = w } | w <- ways ] + needContext =<< contextDependencies context + when (package == ghc) $ do + ways <- interpretInContext context (getLibraryWays <> getRtsWays) + needContext [ rtsContext { way = w } | w <- ways ] let path = buildPath context cObjs <- map (objectPath context) <$> pkgDataList (CSrcs path) hsObjs <- hsObjects context diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 477a245..9f95957 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -8,10 +8,8 @@ quickestFlavour :: Flavour quickestFlavour = defaultFlavour { name = "quickest" , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs - , libraryWays = defaultLibraryWays <> quickestLibraryWays } + , libraryWays = append [vanilla] + , rtsWays = append [vanilla] } quickestArgs :: Args quickestArgs = builder Ghc ? arg "-O0" - -quickestLibraryWays :: Ways -quickestLibraryWays = remove [profiling] From git at git.haskell.org Fri Oct 27 01:16:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove dependency on rts for programs built in Stage0 (daa4b7c) Message-ID: <20171027011600.E54F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/daa4b7c1ff6f55a5c8141c33fd36414581828392/ghc >--------------------------------------------------------------- commit daa4b7c1ff6f55a5c8141c33fd36414581828392 Author: Andrey Mokhov Date: Sat Jan 7 14:32:20 2017 +0000 Remove dependency on rts for programs built in Stage0 >--------------------------------------------------------------- daa4b7c1ff6f55a5c8141c33fd36414581828392 src/Rules/Program.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index b1577e2..254284a 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -74,7 +74,7 @@ buildBinary rs context at Context {..} bin = do then hsSources context else do needContext =<< contextDependencies context - when (package == ghc) $ do + when (stage > Stage0) $ do ways <- interpretInContext context (getLibraryWays <> getRtsWays) needContext [ rtsContext { way = w } | w <- ways ] let path = buildPath context From git at git.haskell.org Fri Oct 27 01:16:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant top-level rts target (cf73599) Message-ID: <20171027011604.7E7573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cf7359904f868be93defcdf4a9a65974d8224cb4/ghc >--------------------------------------------------------------- commit cf7359904f868be93defcdf4a9a65974d8224cb4 Author: Andrey Mokhov Date: Sat Jan 7 14:33:25 2017 +0000 Drop redundant top-level rts target >--------------------------------------------------------------- cf7359904f868be93defcdf4a9a65974d8224cb4 src/Rules.hs | 10 +--------- 1 file changed, 1 insertion(+), 9 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index be7c89b..8db01f4 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -27,16 +27,8 @@ allStages = [minBound ..] -- | This rule 'need' all top-level build targets. topLevelTargets :: Rules () topLevelTargets = do - want $ Rules.Generate.installTargets - -- TODO: Do we want libffiLibrary to be a top-level target? - - action $ do -- TODO: Add support for all rtsWays - rtsLib <- pkgLibraryFile $ rtsContext { way = vanilla } - rtsThrLib <- pkgLibraryFile $ rtsContext { way = threaded } - need [ rtsLib, rtsThrLib ] - forM_ allStages $ \stage -> forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> action $ do let context = vanillaContext stage pkg @@ -48,7 +40,7 @@ topLevelTargets = do libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] - else do -- otherwise build a program + else -- otherwise build a program need =<< maybeToList <$> programPath (programContext stage pkg) packageRules :: Rules () From git at git.haskell.org Fri Oct 27 01:16:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make quick and quickest flavours more precise (c27e8cb) Message-ID: <20171027011608.0CBDC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c27e8cbe776256e9698957c1c3dda4a62b185bbe/ghc >--------------------------------------------------------------- commit c27e8cbe776256e9698957c1c3dda4a62b185bbe Author: Andrey Mokhov Date: Sat Jan 7 18:43:32 2017 +0000 Make quick and quickest flavours more precise >--------------------------------------------------------------- c27e8cbe776256e9698957c1c3dda4a62b185bbe src/Settings/Flavours/Quick.hs | 6 ++---- src/Settings/Flavours/Quickest.hs | 13 +++++++++---- 2 files changed, 11 insertions(+), 8 deletions(-) diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 1e4f5c0..6935544 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -10,7 +10,8 @@ quickFlavour :: Flavour quickFlavour = defaultFlavour { name = "quick" , args = defaultBuilderArgs <> quickArgs <> defaultPackageArgs - , libraryWays = defaultLibraryWays <> quickLibraryWays } + , libraryWays = append [vanilla] + , rtsWays = append [vanilla, threaded] } optimise :: Context -> Bool optimise Context {..} = @@ -20,6 +21,3 @@ quickArgs :: Args quickArgs = builder Ghc ? do context <- getContext if optimise context then arg "-O" else arg "-O0" - -quickLibraryWays :: Ways -quickLibraryWays = remove [profiling] diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 9f95957..62ad43e 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -6,10 +6,15 @@ import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour quickestFlavour = defaultFlavour - { name = "quickest" - , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs - , libraryWays = append [vanilla] - , rtsWays = append [vanilla] } + { name = "quickest" + , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs + , libraryWays = append [vanilla] + , rtsWays = quickestRtsWays } quickestArgs :: Args quickestArgs = builder Ghc ? arg "-O0" + +quickestRtsWays :: Ways +quickestRtsWays = mconcat + [ append [vanilla] + , buildHaddock defaultFlavour ? append [threaded] ] From git at git.haskell.org Fri Oct 27 01:16:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update section on integerLibrary, expand build ways example (60c8172) Message-ID: <20171027011628.E21C23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/60c8172861fdc8e4b66b68ae971c91ccc794ebba/ghc >--------------------------------------------------------------- commit 60c8172861fdc8e4b66b68ae971c91ccc794ebba Author: Andrey Mokhov Date: Sun Jan 8 02:39:51 2017 +0000 Update section on integerLibrary, expand build ways example See #179 >--------------------------------------------------------------- 60c8172861fdc8e4b66b68ae971c91ccc794ebba doc/user-settings.md | 25 ++++++++++++++++--------- 1 file changed, 16 insertions(+), 9 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index d4f0f95..9d776ea 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -24,6 +24,7 @@ data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. , args :: Args -- ^ Use these command line arguments. , packages :: Packages -- ^ Build these packages. + , integerLibrary :: Package -- ^ Either 'integerGmp' or 'integerSimple'. , libraryWays :: Ways -- ^ Build libraries these ways. , rtsWays :: Ways -- ^ Build RTS these ways. , splitObjects :: Predicate -- ^ Build split objects. @@ -111,24 +112,30 @@ userPackage = library "user-package" You will also need to add `userPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. -You can choose which integer library to use when builing GHC by setting -`integerLibrary`. Possible values are: `integerGmp` (default) and `integerSimple`. +You can choose which integer library to use when builing GHC using the +`integerLibrary` setting of the build flavour. Possible values are: `integerGmp` +(default) and `integerSimple`. ```haskell --- | Choose the integer library: 'integerGmp' or 'integerSimple'. -integerLibrary :: Package -integerLibrary = integerGmp +simpleFlavour :: Flavour +simpleFlavour = defaultFlavour { name = "simple", integerLibrary = integerSimple } ``` ## Build ways Packages can be built in a number of ways, such as `vanilla`, `profiling` (with profiling information enabled), and many others as defined in `src/Way.hs`. You can change the default build ways by modifying `libraryWays` and `rtsWays` fields -of the `Flavour` record as required. As an example, below we remove `dynamic` -from the list of library ways but keep `rts` package ways unchanged: +of the `Flavour` record as required. As an example, below we remove `profiling` +from the list of library ways: ```haskell -userFlavour :: Flavour -userFlavour = defaultFlavour { name = "user", libraryWays = defaultLibraryWays <> remove [dynamic] } +noProfilingFlavour :: Flavour +noProfilingFlavour = defaultFlavour + { name = "no-profiling" + , libraryWays = defaultLibraryWays <> remove [profiling] + , ghcProfiled = False } -- Can't build profiled GHC without profiled libraries ``` +Note that `rtsWays` is computed from `libraryWays` by default, therefore the above +change will lead to the removal of `threadedProfiling` way from `rtsWays`. To +change this behaviour, you can override the default `rtsWays` setting. ## Verbose command lines From git at git.haskell.org Fri Oct 27 01:16:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop no longer relevant bits (1774b40) Message-ID: <20171027011632.570163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1774b40d0be398953bc0ad03bc364a951d971a7b/ghc >--------------------------------------------------------------- commit 1774b40d0be398953bc0ad03bc364a951d971a7b Author: Andrey Mokhov Date: Sun Jan 8 02:56:18 2017 +0000 Drop no longer relevant bits >--------------------------------------------------------------- 1774b40d0be398953bc0ad03bc364a951d971a7b src/Flavour.hs | 6 +++++- src/Settings/Builders/Common.hs | 6 ++---- src/UserSettings.hs | 19 ++----------------- 3 files changed, 9 insertions(+), 22 deletions(-) diff --git a/src/Flavour.hs b/src/Flavour.hs index b195767..3283eda 100644 --- a/src/Flavour.hs +++ b/src/Flavour.hs @@ -2,8 +2,12 @@ module Flavour (Flavour (..)) where import Expression --- TODO: Merge {libraryWays, rtsWays}, and {dynamicGhcPrograms, ghcProfiled...}. -- | 'Flavour' is a collection of build settings that fully define a GHC build. +-- Note the following type semantics: +-- * @Bool@: a plain Boolean flag whose value is known at compile time. +-- * @Action Bool@: a flag whose value can depend on the build environment. +-- * @Predicate@: a flag whose value can depend on the build environment and +-- on the current build target. data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. , args :: Args -- ^ Use these command line arguments. diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 271851e..a6b8198 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -41,16 +41,14 @@ cIncludeArgs = do ldArgs :: Args ldArgs = mempty --- TODO: put all validating options together in one file cArgs :: Args -cArgs = validating ? cWarnings +cArgs = mempty -- TODO: should be in a different file cWarnings :: Args cWarnings = do let gccGe46 = notM $ (flag GccIsClang ||^ flag GccLt46) - mconcat [ turnWarningsIntoErrors ? arg "-Werror" - , arg "-Wall" + mconcat [ arg "-Wall" , flag GccIsClang ? arg "-Wno-unknown-pragmas" , gccGe46 ? notM windowsHost ? arg "-Werror=unused-but-set-variable" , gccGe46 ? arg "-Wno-error=inline" ] diff --git a/src/UserSettings.hs b/src/UserSettings.hs index e16cf49..09d70e1 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,8 +3,8 @@ -- If you don't copy the file your changes will be tracked by git and you can -- accidentally commit them. module UserSettings ( - buildRootPath, userFlavours, userKnownPackages, validating, - turnWarningsIntoErrors, verboseCommands, putBuild, putSuccess + buildRootPath, userFlavours, userKnownPackages, verboseCommands, + putBuild, putSuccess ) where import System.Console.ANSI @@ -29,21 +29,6 @@ userFlavours = [] userKnownPackages :: [Package] userKnownPackages = [] --- | User defined flags. Note the following type semantics: --- * @Bool@: a plain Boolean flag whose value is known at compile time. --- * @Action Bool@: a flag whose value can depend on the build environment. --- * @Predicate@: a flag whose value can depend on the build environment and --- on the current build target. - --- TODO: This should be set automatically when validating. -validating :: Bool -validating = False - --- TODO: Replace with stage2 ? arg "-Werror"? Also see #251. --- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. -turnWarningsIntoErrors :: Predicate -turnWarningsIntoErrors = return False - -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output only for certain -- targets, e.g.: @verboseCommands = package ghcPrim at . From git at git.haskell.org Fri Oct 27 01:16:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add development flavours (d6e7919) Message-ID: <20171027011635.C48B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6e7919a7d67462ee29a3019f46d6e7899bb4c50/ghc >--------------------------------------------------------------- commit d6e7919a7d67462ee29a3019f46d6e7899bb4c50 Author: Andrey Mokhov Date: Mon Jan 9 01:24:57 2017 +0000 Add development flavours See #188, #268 >--------------------------------------------------------------- d6e7919a7d67462ee29a3019f46d6e7899bb4c50 hadrian.cabal | 1 + src/CmdLineFlag.hs | 4 ++-- src/Settings.hs | 6 ++++-- src/Settings/Builders/Ghc.hs | 3 --- src/Settings/Default.hs | 5 ++++- src/Settings/Flavours/Development.hs | 26 ++++++++++++++++++++++++++ 6 files changed, 37 insertions(+), 8 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 712d4c6..598bd27 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -85,6 +85,7 @@ executable hadrian , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default + , Settings.Flavours.Development , Settings.Flavours.Perf , Settings.Flavours.Prof , Settings.Flavours.Quick diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index b58df7b..ebe907a 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -38,7 +38,7 @@ readBuildHaddock :: Either String (Untracked -> Untracked) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } readFlavour :: Maybe String -> Either String (Untracked -> Untracked) -readFlavour ms = Right $ \flags -> flags { flavour = ms } +readFlavour ms = Right $ \flags -> flags { flavour = lower <$> ms } readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) readProgressColour ms = @@ -74,7 +74,7 @@ readSplitObjects = Right $ \flags -> flags { splitObjects = True } cmdFlags :: [OptDescr (Either String (Untracked -> Untracked))] cmdFlags = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") - "Build flavour (default, quick or quickest)." + "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") diff --git a/src/Settings.hs b/src/Settings.hs index 09b58f8..01ee122 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -15,6 +15,7 @@ import GHC import Oracles.PackageData import Oracles.Path import {-# SOURCE #-} Settings.Default +import Settings.Flavours.Development import Settings.Flavours.Perf import Settings.Flavours.Prof import Settings.Flavours.Quick @@ -53,8 +54,9 @@ getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] getPkgDataList key = lift . pkgDataList . key =<< getBuildPath hadrianFlavours :: [Flavour] -hadrianFlavours = [ defaultFlavour, perfFlavour, profFlavour, quickFlavour - , quickestFlavour ] +hadrianFlavours = + [ defaultFlavour, developmentFlavour Stage1, developmentFlavour Stage2 + , perfFlavour, profFlavour, quickFlavour, quickestFlavour ] flavour :: Flavour flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 98e5e39..669900f 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -9,9 +9,6 @@ ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do needTouchy mconcat [ arg "-Wall" , commonGhcArgs - , arg "-H32m" - , stage0 ? arg "-O" - , notStage0 ? arg "-O2" , splitObjectsArgs , ghcLinkArgs , builder (Ghc CompileHs) ? arg "-c" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 103c432..6db669e 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -40,7 +40,10 @@ import Settings.Packages.RunGhc -- | All default command line arguments. defaultArgs :: Args -defaultArgs = defaultBuilderArgs <> defaultPackageArgs +defaultArgs = mconcat + [ defaultBuilderArgs + , builder Ghc ? mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2", arg "-H32m"] + , defaultPackageArgs ] -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs new file mode 100644 index 0000000..afe42d5 --- /dev/null +++ b/src/Settings/Flavours/Development.hs @@ -0,0 +1,26 @@ +module Settings.Flavours.Development (developmentFlavour) where + +import Flavour +import GHC +import Predicate +import {-# SOURCE #-} Settings.Default + +-- TODO: Implement an equivalent of LAX_DEPENDENCIES = YES setting, see #250. +developmentFlavour :: Stage -> Flavour +developmentFlavour ghcStage = defaultFlavour + { name = "devel" ++ show (fromEnum ghcStage) + , args = developmentArgs ghcStage + , libraryWays = append [vanilla] } + +developmentArgs :: Stage -> Args +developmentArgs ghcStage = do + stage <- getStage + pkg <- getPackage + let now = succ stage == ghcStage + mconcat [ defaultBuilderArgs + , builder Ghc ? mconcat + [ append ["-O", "-H64m"] + , now ? pkg == compiler ? append ["-O0", "-DDEBUG", "-dcore-lint"] + , now ? pkg == ghc ? append ["-O0", "-DDEBUG"] + , notStage0 ? isLibrary pkg ? arg "-dcore-lint" ] + , defaultPackageArgs ] From git at git.haskell.org Fri Oct 27 01:16:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor build flavours (b2ca3dd) Message-ID: <20171027011639.71D1A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2ca3dd7366f8f8eaf598597c52e99465124ab2c/ghc >--------------------------------------------------------------- commit b2ca3dd7366f8f8eaf598597c52e99465124ab2c Author: Andrey Mokhov Date: Mon Jan 9 03:30:19 2017 +0000 Refactor build flavours >--------------------------------------------------------------- b2ca3dd7366f8f8eaf598597c52e99465124ab2c hadrian.cabal | 5 +++-- src/Settings.hs | 6 +++--- src/Settings/Default.hs | 11 ++++++++++- src/Settings/Flavours/Development.hs | 20 ++++++++------------ src/Settings/Flavours/Perf.hs | 21 --------------------- src/Settings/Flavours/Performance.hs | 18 ++++++++++++++++++ src/Settings/Flavours/Prof.hs | 21 --------------------- src/Settings/Flavours/Profiled.hs | 19 +++++++++++++++++++ src/Settings/Flavours/Quick.hs | 16 +++++++--------- src/Settings/Flavours/Quickest.hs | 7 ++++++- src/Settings/Optimisation.hs | 21 +++++++++++++++++++++ 11 files changed, 95 insertions(+), 70 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 b2ca3dd7366f8f8eaf598597c52e99465124ab2c From git at git.haskell.org Fri Oct 27 01:16:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a doc on build flavours (ff9e5b6) Message-ID: <20171027011642.E35383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff9e5b6362b5112a06f7018a5462639c9ef4d83c/ghc >--------------------------------------------------------------- commit ff9e5b6362b5112a06f7018a5462639c9ef4d83c Author: Andrey Mokhov Date: Thu Jan 12 01:00:53 2017 +0000 Add a doc on build flavours See #239, #268. >--------------------------------------------------------------- ff9e5b6362b5112a06f7018a5462639c9ef4d83c doc/flavours.md | 162 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 162 insertions(+) diff --git a/doc/flavours.md b/doc/flavours.md new file mode 100644 index 0000000..dc672a9 --- /dev/null +++ b/doc/flavours.md @@ -0,0 +1,162 @@ +# Build flavours + +Hadrian supports a few predefined _build flavours_, i.e. collections of build +settings that fully define a GHC build (see `src/Flavour.hs`). Users can add their +own build flavours if need be, as described +[here](https://github.com/snowleopard/hadrian/blob/master/doc/user-settings.md#build-flavour). + +## Arguments + +The following table summarises extra arguments passed to GHC in different build flavours. +There are four groups of arguments: arguments in `hsDefault` are passed to GHC for all Haskell +source files, `hsLibrary` arguments are added when compiling libraries, `hsCompiler` +when compiling the `compiler` library, and `hsGhc` when compiling/linking the GHC program. + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
FlavourExtra arguments
hsDefault + hsLibrary + hsCompiler + hsGhc +
stage0 + stage1+ + stage0 + stage1+ + stage0 + stage1+ + stage0 + stage1+ +
default
+
-O
-H32
-O2
-H32m
quick + -O0
-H64
-O0
-H64
-O-O-O
quickest + -O0
-H64
-O0
-H64
perf + -O
-H64
-O
-H64
-O2-O-O2-O-O2
prof + -O0
-H64
-O0
-H64
-O-O-O-O-O
devel1 + -O
-H64
-O
-H64
-dcore-lint-O0
-DDEBUG
-O0
-DDEBUG
devel2 + -O
-H64
-O
-H64
-dcore-lint-O0
-DDEBUG
-O0
-DDEBUG
+ +## Ways + +Libraries and GHC can be built in different _ways_, e.g. with or without profiling +information. The following table lists ways that are built in different flavours. + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
FlavourLibrary waysRTS waysProfiled GHC
stage0 + stage1+ + stage0 + stage1+ + stage0 + stage1+ +
default
perf
prof
devel1
devel2 +
vanillavanilla
profiling
logging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
threadedProfiling
Only in
prof
flavour
Only in
prof
flavour
quick + vanillavanillalogging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
NoNo
quickest + vanillavanillavanilla
threaded (when --haddock)
vanilla
threaded (when --haddock)
NoNo
From git at git.haskell.org Fri Oct 27 01:16:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to build flavours doc (e03bcf6) Message-ID: <20171027011646.56EE33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e03bcf6b16e3ded4948bd370daab3a05098e32d5/ghc >--------------------------------------------------------------- commit e03bcf6b16e3ded4948bd370daab3a05098e32d5 Author: Andrey Mokhov Date: Thu Jan 12 01:03:13 2017 +0000 Link to build flavours doc [skip ci] >--------------------------------------------------------------- e03bcf6b16e3ded4948bd370daab3a05098e32d5 doc/user-settings.md | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index 9d776ea..9207f7f 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -34,7 +34,9 @@ data Flavour = Flavour , ghcProfiled :: Bool -- ^ Build profiled GHC. , ghcDebugged :: Bool } -- ^ Build GHC with debug information. ``` -Hadrian provides several built-in flavours (`defaultFlavour`, `quickFlavour`, and +Hadrian provides several +[built-in flavours](https://github.com/snowleopard/hadrian/blob/master/doc/flavours.md) +(`defaultFlavour`, `quickFlavour`, and a few others), which can be activated from the command line, e.g. `--flavour=quick`. Users can define new build flavours by adding them to `userFlavours` list: ```haskell From git at git.haskell.org Fri Oct 27 01:16:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update notes on build ways and flavours (3d4e548) Message-ID: <20171027011649.C0A283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d4e54873fceedee20c3e0c0fbb56598030252a9/ghc >--------------------------------------------------------------- commit 3d4e54873fceedee20c3e0c0fbb56598030252a9 Author: Andrey Mokhov Date: Thu Jan 12 01:15:19 2017 +0000 Update notes on build ways and flavours [skip ci] >--------------------------------------------------------------- 3d4e54873fceedee20c3e0c0fbb56598030252a9 README.md | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index 0d7b3d8..109f7f0 100644 --- a/README.md +++ b/README.md @@ -6,7 +6,7 @@ Hadrian Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current [`make`-based build system][make]. If you are curious about the rationale behind the -project and the architecture of the new build system you can find more details in +project and the architecture of the build system you can find more details in this [Haskell Symposium 2016 paper][paper] and this [Haskell eXchange 2016 talk][talk]. The new build system can work side-by-side with the existing build system. Note, there is @@ -52,9 +52,11 @@ are placed into `_build` and `inplace` directories. In addition to standard Shake flags (try `--help`), the build system currently supports several others: -* `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: -`default` and `quick` (adds `-O0` flag to all GHC invocations and disables library -profiling, which speeds up builds by 3-4x). +* `--flavour=FLAVOUR`: choose a build flavour. The following settings are currently supported: +`default`, `quick`, `quickest`, `perf`, `prof`, `devel1` and `devel2`. As an example, the +`quickest` flavour adds `-O0` flag to all GHC invocations and builds libraries only in the +`vanilla` way, which speeds up builds by 3-4x. Build flavours are documented +[here](https://github.com/snowleopard/hadrian/blob/master/doc/flavours.md). * `--haddock`: build Haddock documentation. @@ -117,10 +119,10 @@ zero (see [#197][test-issue]). Current limitations ------------------- The new build system still lacks many important features: -* We only build `vanilla` and `profiling` way: [#4][dynamic-issue]. +* There is currently no support for the `dynamic` build way: [#4][dynamic-issue]. * Validation is not implemented: [#187][validation-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). -* Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. +* Not all modes of the old build system are supported, e.g. [#250][freeze-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. * There is no support for installation or binary distribution: [#219][install-issue]. @@ -159,7 +161,7 @@ helped me endure and enjoy the project. [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 -[flavours-issue]: https://github.com/snowleopard/hadrian/issues/188 +[freeze-issue]: https://github.com/snowleopard/hadrian/issues/250 [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 [milestones]: https://github.com/snowleopard/hadrian/milestones From git at git.haskell.org Fri Oct 27 01:16:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't modify ways in development flavours (084ce3b) Message-ID: <20171027011653.54EE73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/084ce3b4f5fdfbfa83786d96805698a9170b9b0f/ghc >--------------------------------------------------------------- commit 084ce3b4f5fdfbfa83786d96805698a9170b9b0f Author: Andrey Mokhov Date: Thu Jan 12 01:24:26 2017 +0000 Don't modify ways in development flavours >--------------------------------------------------------------- 084ce3b4f5fdfbfa83786d96805698a9170b9b0f src/Settings/Flavours/Development.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index 4314a64..a90c157 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -9,8 +9,7 @@ import Settings.Optimisation developmentFlavour :: Stage -> Flavour developmentFlavour ghcStage = defaultFlavour { name = "devel" ++ show (fromEnum ghcStage) - , args = defaultBuilderArgs <> developmentArgs ghcStage <> defaultPackageArgs - , libraryWays = append [vanilla] } + , args = defaultBuilderArgs <> developmentArgs ghcStage <> defaultPackageArgs } developmentArgs :: Stage -> Args developmentArgs ghcStage = do From git at git.haskell.org Fri Oct 27 01:16:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Settings.Optimisation to Settings.SourceArgs (71b2b96) Message-ID: <20171027011656.CF8F63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/71b2b96820f4ac6100840c3782d7d9fbabc6dac7/ghc >--------------------------------------------------------------- commit 71b2b96820f4ac6100840c3782d7d9fbabc6dac7 Author: Andrey Mokhov Date: Thu Jan 12 12:21:54 2017 +0000 Rename Settings.Optimisation to Settings.SourceArgs >--------------------------------------------------------------- 71b2b96820f4ac6100840c3782d7d9fbabc6dac7 hadrian.cabal | 2 +- src/Settings/Default.hs | 8 ++++---- src/Settings/Flavours/Development.hs | 4 ++-- src/Settings/Flavours/Performance.hs | 4 ++-- src/Settings/Flavours/Profiled.hs | 4 ++-- src/Settings/Flavours/Quick.hs | 4 ++-- src/Settings/Flavours/Quickest.hs | 4 ++-- src/Settings/{Optimisation.hs => SourceArgs.hs} | 10 +++++----- 8 files changed, 20 insertions(+), 20 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index d3ef74c..c8cb0b7 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -90,7 +90,7 @@ executable hadrian , Settings.Flavours.Profiled , Settings.Flavours.Quick , Settings.Flavours.Quickest - , Settings.Optimisation + , Settings.SourceArgs , Settings.Packages.Base , Settings.Packages.Compiler , Settings.Packages.Ghc diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 2a9fae4..3aa3a65 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -27,7 +27,7 @@ import Settings.Builders.HsCpp import Settings.Builders.Ld import Settings.Builders.Make import Settings.Builders.Tar -import Settings.Optimisation +import Settings.SourceArgs import Settings.Packages.Base import Settings.Packages.Compiler import Settings.Packages.Ghc @@ -43,12 +43,12 @@ import Settings.Packages.RunGhc defaultArgs :: Args defaultArgs = mconcat [ defaultBuilderArgs - , optimisationArgs defaultOptimisation + , sourceArgs defaultSourceArgs , defaultPackageArgs ] -- | Default optimisation settings. -defaultOptimisation :: Optimisation -defaultOptimisation = Optimisation +defaultSourceArgs :: SourceArgs +defaultSourceArgs = SourceArgs { hsDefault = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2", arg "-H32m"] , hsLibrary = mempty , hsCompiler = mempty diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index a90c157..f3f9499 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Development (developmentFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs -- TODO: Implement an equivalent of LAX_DEPENDENCIES = YES setting, see #250. developmentFlavour :: Stage -> Flavour @@ -14,7 +14,7 @@ developmentFlavour ghcStage = defaultFlavour developmentArgs :: Stage -> Args developmentArgs ghcStage = do stage <- getStage - optimisationArgs $ Optimisation + sourceArgs $ SourceArgs { hsDefault = append ["-O", "-H64m"] , hsLibrary = notStage0 ? arg "-dcore-lint" , hsCompiler = succ stage == ghcStage ? append ["-O0", "-DDEBUG"] diff --git a/src/Settings/Flavours/Performance.hs b/src/Settings/Flavours/Performance.hs index 69e244a..ae3197e 100644 --- a/src/Settings/Flavours/Performance.hs +++ b/src/Settings/Flavours/Performance.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Performance (performanceFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs performanceFlavour :: Flavour performanceFlavour = defaultFlavour @@ -11,7 +11,7 @@ performanceFlavour = defaultFlavour , args = defaultBuilderArgs <> performanceArgs <> defaultPackageArgs } performanceArgs :: Args -performanceArgs = optimisationArgs $ Optimisation +performanceArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O", "-H64m"] , hsLibrary = notStage0 ? arg "-O2" , hsCompiler = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2"] diff --git a/src/Settings/Flavours/Profiled.hs b/src/Settings/Flavours/Profiled.hs index 0a1a6ed..b3f9117 100644 --- a/src/Settings/Flavours/Profiled.hs +++ b/src/Settings/Flavours/Profiled.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Profiled (profiledFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs profiledFlavour :: Flavour profiledFlavour = defaultFlavour @@ -12,7 +12,7 @@ profiledFlavour = defaultFlavour , ghcProfiled = True } profiledArgs :: Args -profiledArgs = optimisationArgs $ Optimisation +profiledArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O0", "-H64m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = arg "-O" diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index dd9cd58..565e748 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Quick (quickFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs quickFlavour :: Flavour quickFlavour = defaultFlavour @@ -13,7 +13,7 @@ quickFlavour = defaultFlavour -- TODO: the hsLibrary setting seems wrong, but it matches mk/flavours/quick.mk quickArgs :: Args -quickArgs = optimisationArgs $ Optimisation +quickArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O0", "-H64m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = stage0 ? arg "-O" diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 0473dc6..abb2ccf 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -3,7 +3,7 @@ module Settings.Flavours.Quickest (quickestFlavour) where import Flavour import Predicate import {-# SOURCE #-} Settings.Default -import Settings.Optimisation +import Settings.SourceArgs quickestFlavour :: Flavour quickestFlavour = defaultFlavour @@ -13,7 +13,7 @@ quickestFlavour = defaultFlavour , rtsWays = quickestRtsWays } quickestArgs :: Args -quickestArgs = optimisationArgs $ Optimisation +quickestArgs = sourceArgs $ SourceArgs { hsDefault = append ["-O0", "-H64m"] , hsLibrary = mempty , hsCompiler = mempty diff --git a/src/Settings/Optimisation.hs b/src/Settings/SourceArgs.hs similarity index 66% rename from src/Settings/Optimisation.hs rename to src/Settings/SourceArgs.hs index 6d47941..0c638ca 100644 --- a/src/Settings/Optimisation.hs +++ b/src/Settings/SourceArgs.hs @@ -1,17 +1,17 @@ -module Settings.Optimisation (Optimisation (..), optimisationArgs) where +module Settings.SourceArgs (SourceArgs (..), sourceArgs) where import GHC import Predicate --- TODO: Move C optimisation settings here -data Optimisation = Optimisation +-- TODO: Move C source arguments here +data SourceArgs = SourceArgs { hsDefault :: Args , hsLibrary :: Args , hsCompiler :: Args , hsGhc :: Args } -optimisationArgs :: Optimisation -> Args -optimisationArgs Optimisation {..} = do +sourceArgs :: SourceArgs -> Args +sourceArgs SourceArgs {..} = do hsCompile <- builder $ Ghc CompileHs hsLink <- builder $ Ghc LinkHs pkg <- getPackage From git at git.haskell.org Fri Oct 27 01:17:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Reorder source arguments (a63d835) Message-ID: <20171027011700.459133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a63d83530f324bab9b3f0860d53f7198072ffd81/ghc >--------------------------------------------------------------- commit a63d83530f324bab9b3f0860d53f7198072ffd81 Author: Andrey Mokhov Date: Thu Jan 12 20:20:41 2017 +0000 Reorder source arguments >--------------------------------------------------------------- a63d83530f324bab9b3f0860d53f7198072ffd81 hadrian.cabal | 1 - src/Settings/Builders/Ghc.hs | 8 +++++--- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Default.hs | 27 +++++++++++++++++++++++---- src/Settings/Default.hs-boot | 13 +++++++++++-- src/Settings/Flavours/Development.hs | 1 - src/Settings/Flavours/Performance.hs | 1 - src/Settings/Flavours/Profiled.hs | 1 - src/Settings/Flavours/Quick.hs | 2 -- src/Settings/Flavours/Quickest.hs | 1 - src/Settings/SourceArgs.hs | 21 --------------------- 11 files changed, 40 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 a63d83530f324bab9b3f0860d53f7198072ffd81 From git at git.haskell.org Fri Oct 27 01:17:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add --integer-simple command line argument (b42cac6) Message-ID: <20171027011703.B44BE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b42cac65d1a65a101179613dba66d3b711948b84/ghc >--------------------------------------------------------------- commit b42cac65d1a65a101179613dba66d3b711948b84 Author: Andrey Mokhov Date: Thu Jan 12 23:31:50 2017 +0000 Add --integer-simple command line argument See #179 >--------------------------------------------------------------- b42cac65d1a65a101179613dba66d3b711948b84 src/CmdLineFlag.hs | 16 +++++++++++++--- src/Settings/Default.hs | 2 +- 2 files changed, 14 insertions(+), 4 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index ebe907a..961a033 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,7 +1,7 @@ module CmdLineFlag ( - putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, cmdProgressColour, - ProgressColour (..), cmdProgressInfo, ProgressInfo (..), cmdSkipConfigure, - cmdSplitObjects + putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, + cmdProgressColour, ProgressColour (..), cmdProgressInfo, ProgressInfo (..), + cmdSkipConfigure, cmdSplitObjects ) where import Data.IORef @@ -15,6 +15,7 @@ import System.IO.Unsafe data Untracked = Untracked { buildHaddock :: Bool , flavour :: Maybe String + , integerSimple :: Bool , progressColour :: ProgressColour , progressInfo :: ProgressInfo , skipConfigure :: Bool @@ -29,6 +30,7 @@ defaultUntracked :: Untracked defaultUntracked = Untracked { buildHaddock = False , flavour = Nothing + , integerSimple = False , progressColour = Auto , progressInfo = Normal , skipConfigure = False @@ -40,6 +42,9 @@ readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } readFlavour :: Maybe String -> Either String (Untracked -> Untracked) readFlavour ms = Right $ \flags -> flags { flavour = lower <$> ms } +readIntegerSimple :: Either String (Untracked -> Untracked) +readIntegerSimple = Right $ \flags -> flags { integerSimple = True } + readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) readProgressColour ms = maybe (Left "Cannot parse progress-colour") (Right . set) (go =<< lower <$> ms) @@ -77,6 +82,8 @@ cmdFlags = "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." + , Option [] ["integer-simple"] (NoArg readIntegerSimple) + "Build GHC with integer-simple library." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") "Use colours in progress info (Never, Auto or Always)." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") @@ -105,6 +112,9 @@ cmdBuildHaddock = buildHaddock getCmdLineFlags cmdFlavour :: Maybe String cmdFlavour = flavour getCmdLineFlags +cmdIntegerSimple :: Bool +cmdIntegerSimple = integerSimple getCmdLineFlags + cmdProgressColour :: ProgressColour cmdProgressColour = progressColour getCmdLineFlags diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 18f0ae0..351d780 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -177,7 +177,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages - , integerLibrary = integerGmp + , integerLibrary = if cmdIntegerSimple then integerSimple else integerGmp , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects From git at git.haskell.org Fri Oct 27 01:17:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Speed up Travis OSX build by --integer-simple (77840e7) Message-ID: <20171027011707.4ECE13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/77840e7930d55597dc575ec29b2c35afd5516d1f/ghc >--------------------------------------------------------------- commit 77840e7930d55597dc575ec29b2c35afd5516d1f Author: Andrey Mokhov Date: Thu Jan 12 23:32:36 2017 +0000 Speed up Travis OSX build by --integer-simple >--------------------------------------------------------------- 77840e7930d55597dc575ec29b2c35afd5516d1f .travis.yml | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0209cab..35ae3b7 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,6 +3,7 @@ sudo: true matrix: include: - os: linux + env: MODE="--flavour=quickest" addons: apt: packages: @@ -15,9 +16,11 @@ matrix: - PATH="/opt/cabal/1.22/bin:$PATH" - os: osx + env: MODE="--flavour=quickest --integer-simple" before_install: - brew update - brew install ghc cabal-install + - install: # Add Cabal to PATH @@ -45,7 +48,7 @@ script: - ./build.sh selftest # Build GHC - - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 01:17:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on --integer-simple command line flag (5ca4af3) Message-ID: <20171027011710.C93373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ca4af3f65b77af080508655a12c6f48b7d5ce31/ghc >--------------------------------------------------------------- commit 5ca4af3f65b77af080508655a12c6f48b7d5ce31 Author: Andrey Mokhov Date: Fri Jan 13 00:49:58 2017 +0000 Add a note on --integer-simple command line flag See #179. [skip ci] >--------------------------------------------------------------- 5ca4af3f65b77af080508655a12c6f48b7d5ce31 README.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/README.md b/README.md index 109f7f0..038bde5 100644 --- a/README.md +++ b/README.md @@ -60,6 +60,9 @@ currently supports several others: * `--haddock`: build Haddock documentation. +* `--integer-simple`: build GHC using the `integer-simple` integer library (instead +of `integer-gmp`). + * `--progress-colour=MODE`: choose whether to use colours when printing build progress info. There are three settings: `never` (do not use colours), `auto` (attempt to detect whether the console supports colours; this is the default setting), and `always` (use From git at git.haskell.org Fri Oct 27 01:17:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't need the GMP library when building with integerSimple (f39305c) Message-ID: <20171027011714.4BFA83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f39305c46467b30b7697ad42c1a817be9ec90670/ghc >--------------------------------------------------------------- commit f39305c46467b30b7697ad42c1a817be9ec90670 Author: Andrey Mokhov Date: Fri Jan 13 02:12:31 2017 +0000 Don't need the GMP library when building with integerSimple >--------------------------------------------------------------- f39305c46467b30b7697ad42c1a817be9ec90670 src/Settings/Builders/Ghc.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index f30b8e6..006d9f8 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -21,7 +21,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do pkg <- getPackage libs <- getPkgDataList DepExtraLibs libDirs <- getPkgDataList DepLibDirs - gmpLibs <- if stage > Stage0 + gmpLibs <- if stage > Stage0 && integerLibrary flavour == integerGmp then do -- TODO: get this data more gracefully let strip = fromMaybe "" . stripPrefix "extra-libraries: " buildInfo <- lift $ readFileLines gmpBuildInfoPath From git at git.haskell.org Fri Oct 27 01:17:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Filter out repeated ways when copying libffi (b94612d) Message-ID: <20171027011717.B3E913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b94612d33b8febed57d26bc696c9454b883f4aed/ghc >--------------------------------------------------------------- commit b94612d33b8febed57d26bc696c9454b883f4aed Author: Andrey Mokhov Date: Fri Jan 13 11:43:58 2017 +0000 Filter out repeated ways when copying libffi >--------------------------------------------------------------- b94612d33b8febed57d26bc696c9454b883f4aed src/Rules/Libffi.hs | 3 ++- src/Way.hs | 5 ++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 0f703d9..99b77c8 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -56,7 +56,8 @@ libffiRules = do copyFile header (rtsBuildPath -/- takeFileName header) ways <- interpretInContext libffiContext (getLibraryWays <> getRtsWays) - forM_ ways $ \way -> copyFile libffiLibrary =<< rtsLibffiLibrary way + forM_ (nubOrd ways) $ \way -> + copyFile libffiLibrary =<< rtsLibffiLibrary way putSuccess $ "| Successfully built custom library 'libffi'" diff --git a/src/Way.hs b/src/Way.hs index 22ae6fa8..cb73f04 100644 --- a/src/Way.hs +++ b/src/Way.hs @@ -24,7 +24,7 @@ data WayUnit = Threaded | Profiling | Logging | Dynamic - deriving (Eq, Enum, Bounded) + deriving (Bounded, Enum, Eq, Ord) -- TODO: get rid of non-derived Show instances instance Show WayUnit where @@ -74,6 +74,9 @@ instance Read Way where instance Eq Way where Way a == Way b = a == b +instance Ord Way where + compare (Way a) (Way b) = compare a b + -- | Build default _vanilla_ way. vanilla :: Way vanilla = wayFromUnits [] From git at git.haskell.org Fri Oct 27 01:17:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use -H32m in all build flavours (a7b1494) Message-ID: <20171027011721.47E523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a7b149453928e5cf7c8051d4c6329ef9db3246f1/ghc >--------------------------------------------------------------- commit a7b149453928e5cf7c8051d4c6329ef9db3246f1 Author: Andrey Mokhov Date: Fri Jan 13 11:47:27 2017 +0000 Use -H32m in all build flavours See #268 >--------------------------------------------------------------- a7b149453928e5cf7c8051d4c6329ef9db3246f1 src/Settings/Flavours/Development.hs | 2 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/Quickest.hs | 2 +- 5 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index 7cfd7da..4e1ee2d 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -14,7 +14,7 @@ developmentArgs :: Stage -> Args developmentArgs ghcStage = do stage <- getStage sourceArgs $ SourceArgs - { hsDefault = append ["-O", "-H64m"] + { hsDefault = append ["-O", "-H32m"] , hsLibrary = notStage0 ? arg "-dcore-lint" , hsCompiler = succ stage == ghcStage ? append ["-O0", "-DDEBUG"] , hsGhc = succ stage == ghcStage ? append ["-O0", "-DDEBUG"] } diff --git a/src/Settings/Flavours/Performance.hs b/src/Settings/Flavours/Performance.hs index 0e07c71..a9cef4d 100644 --- a/src/Settings/Flavours/Performance.hs +++ b/src/Settings/Flavours/Performance.hs @@ -11,7 +11,7 @@ performanceFlavour = defaultFlavour performanceArgs :: Args performanceArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O", "-H64m"] + { hsDefault = append ["-O", "-H32m"] , hsLibrary = notStage0 ? arg "-O2" , hsCompiler = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2"] , hsGhc = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2"] } diff --git a/src/Settings/Flavours/Profiled.hs b/src/Settings/Flavours/Profiled.hs index 2f5dc74..861c66c 100644 --- a/src/Settings/Flavours/Profiled.hs +++ b/src/Settings/Flavours/Profiled.hs @@ -12,7 +12,7 @@ profiledFlavour = defaultFlavour profiledArgs :: Args profiledArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O0", "-H64m"] + { hsDefault = append ["-O0", "-H32m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = arg "-O" , hsGhc = arg "-O" } diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 6fe3353..5cbd1e4 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -12,7 +12,7 @@ quickFlavour = defaultFlavour quickArgs :: Args quickArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O0", "-H64m"] + { hsDefault = append ["-O0", "-H32m"] , hsLibrary = notStage0 ? arg "-O" , hsCompiler = stage0 ? arg "-O" , hsGhc = stage0 ? arg "-O" } diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 0560b39..d5dff73 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -13,7 +13,7 @@ quickestFlavour = defaultFlavour quickestArgs :: Args quickestArgs = sourceArgs $ SourceArgs - { hsDefault = append ["-O0", "-H64m"] + { hsDefault = append ["-O0", "-H32m"] , hsLibrary = mempty , hsCompiler = mempty , hsGhc = mempty } From git at git.haskell.org Fri Oct 27 01:17:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use -H32m in all build flavours (2ef6390) Message-ID: <20171027011724.C36463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2ef6390e2893eec4d3b7aadd334fa37fd822946b/ghc >--------------------------------------------------------------- commit 2ef6390e2893eec4d3b7aadd334fa37fd822946b Author: Andrey Mokhov Date: Fri Jan 13 12:55:22 2017 +0000 Use -H32m in all build flavours See #268 >--------------------------------------------------------------- 2ef6390e2893eec4d3b7aadd334fa37fd822946b doc/flavours.md | 26 +++++++++++++------------- 1 file changed, 13 insertions(+), 13 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index dc672a9..9fe2239 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -35,7 +35,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH default
- -O
-H32
+ -O
-H32m
-O2
-H32m @@ -46,8 +46,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quick - -O0
-H64 - -O0
-H64 + -O0
-H32m + -O0
-H32m -O -O @@ -57,8 +57,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quickest - -O0
-H64 - -O0
-H64 + -O0
-H32m + -O0
-H32m @@ -68,8 +68,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH perf - -O
-H64 - -O
-H64 + -O
-H32m + -O
-H32m -O2 -O @@ -79,8 +79,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH prof - -O0
-H64 - -O0
-H64 + -O0
-H32m + -O0
-H32m -O -O @@ -90,8 +90,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel1 - -O
-H64 - -O
-H64 + -O
-H32m + -O
-H32m -dcore-lint -O0
-DDEBUG @@ -101,8 +101,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel2 - -O
-H64 - -O
-H64 + -O
-H32m + -O
-H32m -dcore-lint From git at git.haskell.org Fri Oct 27 01:17:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move checkApiAnnotations, compareSizes and ghcTags to Stage0 (ebee16a) Message-ID: <20171027011728.7536C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ebee16a9e7d37ea14a2e0cd180c0bf6e88c3873c/ghc >--------------------------------------------------------------- commit ebee16a9e7d37ea14a2e0cd180c0bf6e88c3873c Author: Andrey Mokhov Date: Thu Jan 19 02:46:21 2017 +0000 Move checkApiAnnotations, compareSizes and ghcTags to Stage0 See #246 >--------------------------------------------------------------- ebee16a9e7d37ea14a2e0cd180c0bf6e88c3873c src/Settings/Default.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 351d780..318b0a0 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -86,6 +86,8 @@ stage0Packages = do ios <- lift iosHost append $ [ binary , cabal + , checkApiAnnotations + , compareSizes , compiler , deriveConstants , dllSplit @@ -97,6 +99,7 @@ stage0Packages = do , ghcCabal , ghci , ghcPkg + , ghcTags , hsc2hs , hoopl , hp2ps @@ -118,7 +121,6 @@ stage1Packages = do , base , bytestring , compact - , compareSizes , containers , deepseq , directory @@ -142,11 +144,7 @@ stage1Packages = do [ xhtml | doc ] ] stage2Packages :: Packages -stage2Packages = do - doc <- buildHaddock flavour - append $ [ checkApiAnnotations - , ghcTags ] ++ - [ haddock | doc ] +stage2Packages = buildHaddock flavour ? append [ haddock ] -- | Default build ways for library packages: -- * We always build 'vanilla' way. From git at git.haskell.org Fri Oct 27 01:17:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix breakage due to changes in Cabal API (e908a4a) Message-ID: <20171027011732.0775F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e908a4a28964908ee30346a04aae23a4d314e8b2/ghc >--------------------------------------------------------------- commit e908a4a28964908ee30346a04aae23a4d314e8b2 Author: Andrey Mokhov Date: Wed Jan 25 17:45:48 2017 +0000 Fix breakage due to changes in Cabal API >--------------------------------------------------------------- e908a4a28964908ee30346a04aae23a4d314e8b2 src/Rules/Cabal.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 6adaf44..0df267f 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -4,6 +4,7 @@ import Distribution.Package as DP import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Text +import Distribution.Types.CondTree import Distribution.Types.Dependency import Distribution.Verbosity @@ -49,4 +50,4 @@ collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] collectDeps (Just (CondNode _ deps ifs)) = deps ++ concatMap f ifs where - f (_, t, mt) = collectDeps (Just t) ++ collectDeps mt + f (CondBranch _ t mt) = collectDeps (Just t) ++ collectDeps mt From git at git.haskell.org Fri Oct 27 01:17:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add -Wno-sync-nand to ghcPrim's cbits/atomic.c (6e73b4d) Message-ID: <20171027011735.6CE213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e73b4d370755518491bdd82f5542b04d2eedf66/ghc >--------------------------------------------------------------- commit 6e73b4d370755518491bdd82f5542b04d2eedf66 Author: Andrey Mokhov Date: Mon Feb 6 02:21:05 2017 +0100 Add -Wno-sync-nand to ghcPrim's cbits/atomic.c See GHC ticket #9678 >--------------------------------------------------------------- 6e73b4d370755518491bdd82f5542b04d2eedf66 cfg/system.config.in | 1 + src/Oracles/Config/Flag.hs | 2 ++ src/Settings/Packages/GhcPrim.hs | 9 +++++++-- 3 files changed, 10 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 9ea0f44..667a22d 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -30,6 +30,7 @@ ar-supports-at-file = @ArSupportsAtFile@ cc-clang-backend = @CC_CLANG_BACKEND@ cc-llvm-backend = @CC_LLVM_BACKEND@ gcc-is-clang = @GccIsClang@ +gcc-lt-44 = @GccLT44@ gcc-lt-46 = @GccLT46@ hs-cpp-args = @HaskellCPPArgs@ diff --git a/src/Oracles/Config/Flag.hs b/src/Oracles/Config/Flag.hs index 6c5879d..8ac753f 100644 --- a/src/Oracles/Config/Flag.hs +++ b/src/Oracles/Config/Flag.hs @@ -12,6 +12,7 @@ import Oracles.Config.Setting data Flag = ArSupportsAtFile | CrossCompiling | GccIsClang + | GccLt44 | GccLt46 | GhcUnregisterised | LeadingUnderscore @@ -29,6 +30,7 @@ flag f = do ArSupportsAtFile -> "ar-supports-at-file" CrossCompiling -> "cross-compiling" GccIsClang -> "gcc-is-clang" + GccLt44 -> "gcc-lt-44" GccLt46 -> "gcc-lt-46" GhcUnregisterised -> "ghc-unregisterised" LeadingUnderscore -> "leading-underscore" diff --git a/src/Settings/Packages/GhcPrim.hs b/src/Settings/Packages/GhcPrim.hs index 225ff56..bed8345 100644 --- a/src/Settings/Packages/GhcPrim.hs +++ b/src/Settings/Packages/GhcPrim.hs @@ -1,8 +1,13 @@ module Settings.Packages.GhcPrim (ghcPrimPackageArgs) where import GHC +import Oracles.Config.Flag import Predicate ghcPrimPackageArgs :: Args -ghcPrimPackageArgs = package ghcPrim ? - builder GhcCabal ? arg "--flag=include-ghc-prim" +ghcPrimPackageArgs = package ghcPrim ? mconcat + [ builder GhcCabal ? arg "--flag=include-ghc-prim" + + , builder (Cc CompileC) ? + (not <$> flag GccLt44) ? + input "//cbits/atomic.c" ? arg "-Wno-sync-nand" ] From git at git.haskell.org Fri Oct 27 01:17:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to new GMP library (0dc5fdf) Message-ID: <20171027011738.D4FD73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0dc5fdf1820c19dc3264d103d325c08c7d93902c/ghc >--------------------------------------------------------------- commit 0dc5fdf1820c19dc3264d103d325c08c7d93902c Author: Andrey Mokhov Date: Mon Feb 6 02:59:37 2017 +0100 Switch to new GMP library See GHC ticket 7655 >--------------------------------------------------------------- 0dc5fdf1820c19dc3264d103d325c08c7d93902c src/Rules/Gmp.hs | 17 +++++++---------- 1 file changed, 7 insertions(+), 10 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1442118..a3e32d3 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -23,9 +23,6 @@ gmpLibrary = gmpBuildPath -/- ".libs/libgmp.a" gmpMakefile :: FilePath gmpMakefile = gmpBuildPath -/- "Makefile" -gmpPatches :: [FilePath] -gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"] - configureEnvironment :: Action [CmdOption] configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 , builderEnvironment "AR" Ar @@ -77,21 +74,21 @@ gmpRules = do -- That's because the doc/ directory contents are under the GFDL, -- which causes problems for Debian. tarball <- unifyPath . getSingleton "Exactly one GMP tarball is expected" - <$> getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"] + <$> getDirectoryFiles "" [gmpBase -/- "gmp-tarballs/gmp*.tar.bz2"] withTempDir $ \dir -> do let tmp = unifyPath dir need [tarball] build $ Target gmpContext Tar [tarball] [tmp] - forM_ gmpPatches $ \src -> do - let patch = takeFileName src - copyFile src $ tmp -/- patch - applyPatch tmp patch + let patch = gmpBase -/- "gmpsrc.patch" + patchName = takeFileName patch + copyFile patch $ tmp -/- patchName + applyPatch tmp patchName let name = dropExtension . dropExtension $ takeFileName tarball unpack = fromMaybe . error $ "gmpRules: expected suffix " - ++ "-nodoc-patched (found: " ++ name ++ ")." - libName = unpack $ stripSuffix "-nodoc-patched" name + ++ "-nodoc (found: " ++ name ++ ")." + libName = unpack $ stripSuffix "-nodoc" name moveDirectory (tmp -/- libName) gmpBuildPath From git at git.haskell.org Fri Oct 27 01:17:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use --depth 1 for git clone (#298) (c3e8242) Message-ID: <20171027011742.5A8313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3e8242cf0954fb785868019fa73a338cfddfaba/ghc >--------------------------------------------------------------- commit c3e8242cf0954fb785868019fa73a338cfddfaba Author: Gracjan Polak Date: Sat Feb 11 23:32:07 2017 +0100 Use --depth 1 for git clone (#298) * Use --depth 1 for git clone * Update .travis.yml Try separating git commands * Update .travis.yml Try github * Update .travis.yml * Update .travis.yml * Update .travis.yml * Update .travis.yml * Update .travis.yml * Update .travis.yml >--------------------------------------------------------------- c3e8242cf0954fb785868019fa73a338cfddfaba .travis.yml | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 35ae3b7..f6eda04 100644 --- a/.travis.yml +++ b/.travis.yml @@ -28,12 +28,18 @@ install: - export PATH - env + # Fetch GHC sources into ./ghc + - git --version + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git clone --depth 1 --recursive git://github.com/ghc/ghc + # --shallow-submodules is not supported on travis standard git 1.8 (linux), but it is supported + # on Travis Mac OS X machines. But it does not work with github mirrors because it cannot + # find commits. + # Install all Hadrian and GHC build dependencies - cabal update - cabal install alex happy ansi-terminal mtl shake quickcheck - # Fetch GHC sources into ./ghc - - git clone --recursive git://git.haskell.org/ghc.git --quiet # Travis has already cloned Hadrian into ./ and we need to move it # to ./ghc/hadrian -- one way to do it is to move the .git directory From git at git.haskell.org Fri Oct 27 01:17:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add extra to the list of dependencies (cb5035a) Message-ID: <20171027011745.E2EC93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cb5035a49c5eee7706d3634c007520e6b1f4c2a5/ghc >--------------------------------------------------------------- commit cb5035a49c5eee7706d3634c007520e6b1f4c2a5 Author: Andrey Mokhov Date: Tue Feb 14 23:50:42 2017 +0100 Add extra to the list of dependencies >--------------------------------------------------------------- cb5035a49c5eee7706d3634c007520e6b1f4c2a5 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 038bde5..2256fbf 100644 --- a/README.md +++ b/README.md @@ -23,7 +23,7 @@ follow these steps: * If you have never built GHC before, start with the [preparation guide][ghc-preparation]. * This build system is written in Haskell (obviously) and depends on the following Haskell -packages, which need to be installed: `ansi-terminal mtl shake quickcheck`. +packages, which need to be installed: `ansi-terminal extra mtl quickcheck shake`. * Get the sources. It is important for the build system to be in the `hadrian` directory of the GHC source tree: From git at git.haskell.org Fri Oct 27 01:17:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move -rtsopts to linker options (e561f80) Message-ID: <20171027011749.7E8F93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e561f8042ad86c40fda1e4181099c84518e359ad/ghc >--------------------------------------------------------------- commit e561f8042ad86c40fda1e4181099c84518e359ad Author: Andrey Mokhov Date: Thu Mar 16 00:41:56 2017 +0000 Move -rtsopts to linker options >--------------------------------------------------------------- e561f8042ad86c40fda1e4181099c84518e359ad src/Settings/Builders/Ghc.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 006d9f8..8020848 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -28,7 +28,8 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do return $ concatMap (words . strip) buildInfo else return [] mconcat [ arg "-no-auto-link-packages" - , nonHsMainPackage pkg ? arg "-no-hs-main" + , nonHsMainPackage pkg ? arg "-no-hs-main" + , not (nonHsMainPackage pkg) ? arg "-rtsopts" , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] @@ -74,8 +75,7 @@ commonGhcArgs = do , append $ map ("-optP" ++) cppArgs , arg "-odir" , arg path , arg "-hidir" , arg path - , arg "-stubdir" , arg path - , (not . nonHsMainPackage) <$> getPackage ? arg "-rtsopts" ] + , arg "-stubdir" , arg path ] -- TODO: Do '-ticky' in all debug ways? wayGhcArgs :: Args From git at git.haskell.org Fri Oct 27 01:17:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/snowleopard/hadrian (f8bd794) Message-ID: <20171027011753.09D723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f8bd7949c12c99aae2b6d0388fdf3b6d9143d23e/ghc >--------------------------------------------------------------- commit f8bd7949c12c99aae2b6d0388fdf3b6d9143d23e Merge: e561f80 cb5035a Author: Andrey Mokhov Date: Thu Mar 16 00:42:05 2017 +0000 Merge branch 'master' of https://github.com/snowleopard/hadrian >--------------------------------------------------------------- f8bd7949c12c99aae2b6d0388fdf3b6d9143d23e .travis.yml | 10 ++++++++-- README.md | 2 +- 2 files changed, 9 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 01:17:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:17:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on the exact version of the in-tree Cabal library (e664431) Message-ID: <20171027011756.838273A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e664431fb9a240599f512474cf611c51d5d701cb/ghc >--------------------------------------------------------------- commit e664431fb9a240599f512474cf611c51d5d701cb Author: Andrey Mokhov Date: Thu Mar 16 00:56:50 2017 +0000 Depend on the exact version of the in-tree Cabal library >--------------------------------------------------------------- e664431fb9a240599f512474cf611c51d5d701cb hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 18361f3..fd6c036 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -117,7 +117,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 1.25.* + , Cabal == 2.0.0.0 , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 01:18:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename compact to ghc-compact (30708a4) Message-ID: <20171027011800.0090D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30708a47a3456f68bca6951232c02b26dda86585/ghc >--------------------------------------------------------------- commit 30708a47a3456f68bca6951232c02b26dda86585 Author: Andrey Mokhov Date: Thu Mar 16 01:17:01 2017 +0000 Rename compact to ghc-compact >--------------------------------------------------------------- 30708a47a3456f68bca6951232c02b26dda86585 src/GHC.hs | 25 ++++++++++++------------- src/Settings/Default.hs | 2 +- 2 files changed, 13 insertions(+), 14 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index f8abeb8..33af662 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,14 +1,13 @@ {-# LANGUAGE OverloadedStrings, LambdaCase #-} {-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( - array, base, binary, bytestring, cabal, checkApiAnnotations, compact, - compareSizes, compiler, containers, deepseq, deriveConstants, directory, - dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, - ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, - hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, - libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, - stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, - win32, xhtml, + array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, + compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, + genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, + ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps, + hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, + parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, + terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, defaultKnownPackages, builderProvenance, programName, nonCabalContext, nonHsMainPackage @@ -26,10 +25,10 @@ import Stage -- be overridden in @hadrian/src/UserSettings.hs at . defaultKnownPackages :: [Package] defaultKnownPackages = - [ array, base, binary, bytestring, cabal, checkApiAnnotations, compact - , compareSizes, compiler, containers, deepseq, deriveConstants, directory - , dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh - , ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs + [ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes + , compiler, containers, deepseq, deriveConstants, directory, dllSplit + , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal + , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs , hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 @@ -42,7 +41,6 @@ binary = library "binary" bytestring = library "bytestring" cabal = library "Cabal" `setPath` "libraries/Cabal/Cabal" checkApiAnnotations = utility "check-api-annotations" -compact = library "compact" compareSizes = utility "compareSizes" `setPath` "utils/compare_sizes" compiler = topLevel "ghc" `setPath` "compiler" containers = library "containers" @@ -57,6 +55,7 @@ ghc = topLevel "ghc-bin" `setPath` "ghc" `setType` Progra ghcBoot = library "ghc-boot" ghcBootTh = library "ghc-boot-th" ghcCabal = utility "ghc-cabal" +ghcCompact = library "ghc-compact" ghci = library "ghci" ghcPkg = utility "ghc-pkg" ghcPrim = library "ghc-prim" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 318b0a0..89db236 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -120,13 +120,13 @@ stage1Packages = do , append $ [ array , base , bytestring - , compact , containers , deepseq , directory , filepath , ghc , ghcCabal + , ghcCompact , ghci , ghcPrim , haskeline From git at git.haskell.org Fri Oct 27 01:18:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename readPackageDescription to readGenericPackageDescription to fix the warning (198abb4) Message-ID: <20171027011804.5DC433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/198abb4fff538fb67ab9262aa0a7ca5b8bd86c0f/ghc >--------------------------------------------------------------- commit 198abb4fff538fb67ab9262aa0a7ca5b8bd86c0f Author: Andrey Mokhov Date: Thu Mar 16 01:17:36 2017 +0000 Rename readPackageDescription to readGenericPackageDescription to fix the warning >--------------------------------------------------------------- 198abb4fff538fb67ab9262aa0a7ca5b8bd86c0f src/Rules/Cabal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 0df267f..b45af42 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -23,7 +23,7 @@ cabalRules = do let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] - pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg + pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg let identifier = package . packageDescription $ pd version = display . pkgVersion $ identifier return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version @@ -37,7 +37,7 @@ cabalRules = do if not exists then return $ pkgNameString pkg else do need [pkgCabalFile pkg] - pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg + pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg let depsLib = collectDeps $ condLibrary pd depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes From git at git.haskell.org Fri Oct 27 01:18:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop repetition in the list of packages, fixing Hadrian's selftest (7b90c76) Message-ID: <20171027011808.1E53B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b90c7636c20de71b133dba2a1c0bae4ee591dbe/ghc >--------------------------------------------------------------- commit 7b90c7636c20de71b133dba2a1c0bae4ee591dbe Author: Andrey Mokhov Date: Thu Mar 16 11:31:47 2017 +0000 Drop repetition in the list of packages, fixing Hadrian's selftest >--------------------------------------------------------------- 7b90c7636c20de71b133dba2a1c0bae4ee591dbe src/Settings/Default.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 89db236..d242502 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -127,7 +127,6 @@ stage1Packages = do , ghc , ghcCabal , ghcCompact - , ghci , ghcPrim , haskeline , hpcBin From git at git.haskell.org Fri Oct 27 01:18:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Added a note about git line-ending settings (#303) (295c781) Message-ID: <20171027011811.A50EA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/295c7812ab8fe8e34e6812127e039220a850a344/ghc >--------------------------------------------------------------- commit 295c7812ab8fe8e34e6812127e039220a850a344 Author: Ivan Poliakov Date: Fri Mar 31 23:54:46 2017 +0100 Added a note about git line-ending settings (#303) >--------------------------------------------------------------- 295c7812ab8fe8e34e6812127e039220a850a344 doc/windows.md | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/doc/windows.md b/doc/windows.md index 73804df..510b986 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -5,6 +5,14 @@ Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). +Note that `git` should be configured to check out Unix-style line endings. The default behaviour of `git` on Windows is to check out Windows-style line endings which can cause issues during the build. This can be changed using the following command: + + git config --global core.autocrlf false + +If you would like to restore the default behaviour later run: + + git config --global core.autocrlf true + ```sh # Get GHC and Hadrian sources git clone --recursive git://git.haskell.org/ghc.git From git at git.haskell.org Fri Oct 27 01:18:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Allow cmm files in non-custom packages (5b9f6e9) Message-ID: <20171027011818.DE00D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b9f6e901eb3613544aaf941d33419fb9f8368d0/ghc >--------------------------------------------------------------- commit 5b9f6e901eb3613544aaf941d33419fb9f8368d0 Author: Andrey Mokhov Date: Wed Apr 26 01:53:28 2017 +0100 Allow cmm files in non-custom packages >--------------------------------------------------------------- 5b9f6e901eb3613544aaf941d33419fb9f8368d0 src/Rules/Data.hs | 9 ++++++--- src/Rules/Library.hs | 21 ++++++++++++++------- 2 files changed, 20 insertions(+), 10 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index cff0896..0538f6c 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -102,13 +102,16 @@ packageCmmSources pkg -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$'. For example, get rid of -- @libraries/Win32_dist-install_CMM_SRCS := $(addprefix cbits/,$(notdir ...@ --- Reason: we don't need them and we can't parse them. +-- and replace it with a tracked call to getDirectoryFiles. -- 2) Drop path prefixes to individual settings. -- For example, @libraries/deepseq/dist-install_VERSION = 1.4.0.0@ -- is replaced by @VERSION = 1.4.0.0 at . -- Reason: Shake's built-in makefile parser doesn't recognise slashes postProcessPackageData :: Context -> FilePath -> Action () postProcessPackageData context at Context {..} file = do - top <- topDirectory + top <- topDirectory + cmmSrcs <- getDirectoryFiles (pkgPath package) ["cbits/*.cmm"] let len = length (pkgPath package) + length (top -/- buildPath context) + 2 - fixFile file $ unlines . map (drop len) . filter ('$' `notElem`) . lines + fixFile file $ unlines + . (++ ["CMM_SRCS = " ++ unwords (map unifyPath cmmSrcs) ]) + . map (drop len) . filter ('$' `notElem`) . lines diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 2deb6f9..32db232 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -23,12 +23,8 @@ buildPackageLibrary context at Context {..} = do -- TODO: handle dynamic libraries matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do removeFile a - asmObjs <- map (objectPath context) <$> pkgDataList (AsmSrcs path) - cObjs <- cObjects context - cmmObjs <- map (objectPath context) <$> pkgDataList (CmmSrcs path) - eObjs <- extraObjects context - hsObjs <- hsObjects context - let noHsObjs = asmObjs ++ cObjs ++ cmmObjs ++ eObjs + hsObjs <- hsObjects context + noHsObjs <- nonHsObjects context -- This will create split objects if required (we don't track them -- explicitly as this would needlessly bloat the Shake database). @@ -56,10 +52,21 @@ buildPackageGhciLibrary :: Context -> Rules () buildPackageGhciLibrary context at Context {..} = priority 2 $ do let libPrefix = buildPath context -/- "HS" ++ pkgNameString package matchVersionedFilePath libPrefix (waySuffix way <.> "o") ?> \obj -> do - objs <- concatMapM ($ context) [cObjects, hsObjects, extraObjects] + objs <- allObjects context need objs build $ Target context Ld objs [obj] +allObjects :: Context -> Action [FilePath] +allObjects context = (++) <$> nonHsObjects context <*> hsObjects context + +nonHsObjects :: Context -> Action [FilePath] +nonHsObjects context = do + let path = buildPath context + cObjs <- cObjects context + cmmObjs <- map (objectPath context) <$> pkgDataList (CmmSrcs path) + eObjs <- extraObjects context + return $ cObjs ++ cmmObjs ++ eObjs + cObjects :: Context -> Action [FilePath] cObjects context = do objs <- map (objectPath context) <$> pkgDataList (CSrcs $ buildPath context) From git at git.haskell.org Fri Oct 27 01:18:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add wrapper for Runhaskell, Fix #304 (#305) (c158014) Message-ID: <20171027011815.401533A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c158014fbb90046a43d1d6d78b888a687ce341c6/ghc >--------------------------------------------------------------- commit c158014fbb90046a43d1d6d78b888a687ce341c6 Author: Zhen Zhang Date: Sun Apr 16 04:08:33 2017 +0800 Add wrapper for Runhaskell, Fix #304 (#305) >--------------------------------------------------------------- c158014fbb90046a43d1d6d78b888a687ce341c6 .gitignore | 3 +++ src/Rules/Program.hs | 2 ++ src/Rules/Wrappers/Runhaskell.hs | 15 +++++++++++++++ 3 files changed, 20 insertions(+) diff --git a/.gitignore b/.gitignore index 6b06fea..2e3581b 100644 --- a/.gitignore +++ b/.gitignore @@ -17,3 +17,6 @@ cabal.sandbox.config # the user settings /UserSettings.hs + +# Mostly temp file by emacs +*~ diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 254284a..71fb8b7 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -12,6 +12,7 @@ import Oracles.ModuleFiles import Oracles.PackageData import Rules.Wrappers.Ghc import Rules.Wrappers.GhcPkg +import Rules.Wrappers.Runhaskell import Settings import Settings.Path import Target @@ -25,6 +26,7 @@ type Wrapper = FilePath -> Expr String wrappers :: [(Context, Wrapper)] wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) + , (vanillaContext Stage1 runGhc, runhaskellWrapper) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper) ] buildProgram :: [(Resource, Int)] -> Context -> Rules () diff --git a/src/Rules/Wrappers/Runhaskell.hs b/src/Rules/Wrappers/Runhaskell.hs new file mode 100644 index 0000000..521b41a --- /dev/null +++ b/src/Rules/Wrappers/Runhaskell.hs @@ -0,0 +1,15 @@ +module Rules.Wrappers.Runhaskell (runhaskellWrapper) where + +import Base +import Expression +import Oracles.Path + +runhaskellWrapper :: FilePath -> Expr String +runhaskellWrapper program = do + lift $ need [sourcePath -/- "Rules/Wrappers/Runhaskell.hs"] + top <- getTopDirectory + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (top -/- program) + ++ " -f" ++ (top -/- "inplace/lib/bin/ghc-stage2") -- HACK + ++ " -B" ++ (top -/- "inplace/lib") ++ " ${1+\"$@\"}" ] From git at git.haskell.org Fri Oct 27 01:18:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop package self-dependencies (ff322d9) Message-ID: <20171027011822.83F4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ff322d9a37a5c9a406e28eab703334737ae20cba/ghc >--------------------------------------------------------------- commit ff322d9a37a5c9a406e28eab703334737ae20cba Author: Andrey Mokhov Date: Thu Apr 27 00:20:42 2017 +0100 Drop package self-dependencies This occurs in iserv-bin package, which contains both a library and an executable. See #12 >--------------------------------------------------------------- ff322d9a37a5c9a406e28eab703334737ae20cba src/Rules/Cabal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index b45af42..ad1312f 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -42,7 +42,7 @@ cabalRules = do depsExes = map (collectDeps . Just . snd) $ condExecutables pd deps = concat $ depsLib : depsExes depNames = [ unPackageName name | Dependency name _ <- deps ] - return . unwords $ pkgNameString pkg : sort depNames + return . unwords $ pkgNameString pkg : (sort depNames \\ [pkgNameString pkg]) writeFileChanged out $ unlines pkgDeps putSuccess $ "| Successfully computed package dependencies" From git at git.haskell.org Fri Oct 27 01:18:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: GHC ticket 13583 has been resolved, so the workaround is no longer needed (4347b0d) Message-ID: <20171027011826.0364C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4347b0dc3265faec235672b1ba889bb56b38798a/ghc >--------------------------------------------------------------- commit 4347b0dc3265faec235672b1ba889bb56b38798a Author: Andrey Mokhov Date: Thu Apr 27 00:43:14 2017 +0100 GHC ticket 13583 has been resolved, so the workaround is no longer needed See #276 >--------------------------------------------------------------- 4347b0dc3265faec235672b1ba889bb56b38798a src/Settings/Builders/Configure.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 3ab3286..b6142d7 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -1,7 +1,5 @@ module Settings.Builders.Configure (configureBuilderArgs) where -import qualified System.Info as System - import Settings.Builders.Common configureBuilderArgs :: Args @@ -20,9 +18,4 @@ configureBuilderArgs = mconcat , "--libdir=" ++ top -/- libffiBuildPath -/- "inst/lib" , "--enable-static=yes" , "--enable-shared=no" -- TODO: add support for yes - , "--host=" ++ targetPlatform ] - - -- On OS X, use "nm-classic" instead of "nm" due to a bug in the latter. - -- See https://ghc.haskell.org/trac/ghc/ticket/11744 - , builder (Configure ".") ? System.os == "darwin" ? - arg "--with-nm=$(xcrun --find nm-classic)" ] + , "--host=" ++ targetPlatform ] ] From git at git.haskell.org Fri Oct 27 01:18:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use xcode8 image (b3339d4) Message-ID: <20171027011829.ADCAC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b3339d475a56c2c1617bb5803e742509eb2b6821/ghc >--------------------------------------------------------------- commit b3339d475a56c2c1617bb5803e742509eb2b6821 Author: Andrey Mokhov Date: Thu Apr 27 01:08:41 2017 +0100 Use xcode8 image >--------------------------------------------------------------- b3339d475a56c2c1617bb5803e742509eb2b6821 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index f6eda04..dd6af26 100644 --- a/.travis.yml +++ b/.travis.yml @@ -16,6 +16,7 @@ matrix: - PATH="/opt/cabal/1.22/bin:$PATH" - os: osx + osx_image: xcode8 env: MODE="--flavour=quickest --integer-simple" before_install: - brew update From git at git.haskell.org Fri Oct 27 01:18:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename runHaskell wrapper to runGhc for consistency (c4e2e45) Message-ID: <20171027011833.50A6C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c4e2e45be2e11e5785b033ab10511455c2dd00fc/ghc >--------------------------------------------------------------- commit c4e2e45be2e11e5785b033ab10511455c2dd00fc Author: Andrey Mokhov Date: Thu Apr 27 21:39:41 2017 +0100 Rename runHaskell wrapper to runGhc for consistency See #305 >--------------------------------------------------------------- c4e2e45be2e11e5785b033ab10511455c2dd00fc hadrian.cabal | 1 + src/Rules/Program.hs | 4 ++-- src/Rules/Wrappers/{Runhaskell.hs => RunGhc.hs} | 8 ++++---- 3 files changed, 7 insertions(+), 6 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index fd6c036..15c3a2b 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -66,6 +66,7 @@ executable hadrian , Rules.Test , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg + , Rules.Wrappers.RunGhc , Settings , Settings.Builders.Alex , Settings.Builders.Ar diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 71fb8b7..62d4b24 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -12,7 +12,7 @@ import Oracles.ModuleFiles import Oracles.PackageData import Rules.Wrappers.Ghc import Rules.Wrappers.GhcPkg -import Rules.Wrappers.Runhaskell +import Rules.Wrappers.RunGhc import Settings import Settings.Path import Target @@ -26,7 +26,7 @@ type Wrapper = FilePath -> Expr String wrappers :: [(Context, Wrapper)] wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) , (vanillaContext Stage1 ghc , ghcWrapper ) - , (vanillaContext Stage1 runGhc, runhaskellWrapper) + , (vanillaContext Stage1 runGhc, runGhcWrapper) , (vanillaContext Stage0 ghcPkg, ghcPkgWrapper) ] buildProgram :: [(Resource, Int)] -> Context -> Rules () diff --git a/src/Rules/Wrappers/Runhaskell.hs b/src/Rules/Wrappers/RunGhc.hs similarity index 59% rename from src/Rules/Wrappers/Runhaskell.hs rename to src/Rules/Wrappers/RunGhc.hs index 521b41a..95b5700 100644 --- a/src/Rules/Wrappers/Runhaskell.hs +++ b/src/Rules/Wrappers/RunGhc.hs @@ -1,12 +1,12 @@ -module Rules.Wrappers.Runhaskell (runhaskellWrapper) where +module Rules.Wrappers.RunGhc (runGhcWrapper) where import Base import Expression import Oracles.Path -runhaskellWrapper :: FilePath -> Expr String -runhaskellWrapper program = do - lift $ need [sourcePath -/- "Rules/Wrappers/Runhaskell.hs"] +runGhcWrapper :: FilePath -> Expr String +runGhcWrapper program = do + lift $ need [sourcePath -/- "Rules/Wrappers/RunGhc.hs"] top <- getTopDirectory return $ unlines [ "#!/bin/bash" From git at git.haskell.org Fri Oct 27 01:18:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable some warnings (#307) (3ea149a) Message-ID: <20171027011836.C94CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3ea149adad2311ea711bc58950e288d081fde79a/ghc >--------------------------------------------------------------- commit 3ea149adad2311ea711bc58950e288d081fde79a Author: Zhen Zhang Date: Fri Apr 28 23:28:04 2017 +0800 Disable some warnings (#307) >--------------------------------------------------------------- 3ea149adad2311ea711bc58950e288d081fde79a src/Settings/Default.hs | 42 +++++++++++++++++++++++++++++++++++++++++- 1 file changed, 41 insertions(+), 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index d242502..90e2db0 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -215,6 +215,43 @@ defaultBuilderArgs = mconcat , makeBuilderArgs , tarBuilderArgs ] +-- | Disable some warnings in packages we use +-- | https://github.com/ghc/ghc/blob/master/mk/warnings.mk#L46 +disableWarningArgsStage0 :: Args +disableWarningArgsStage0 = stage Stage0 ? builder Ghc ? mconcat + [ package transformers ? append [ "-fno-warn-unused-matches", "-fno-warn-unused-imports" ] + , package terminfo ? append [ "-fno-warn-unused-imports" ] ] + +disableWarningArgsStage1 :: Args +disableWarningArgsStage1 = notStage0 ? builder Ghc ? mconcat + [ package bytestring ? append [ "-Wno-inline-rule-shadowing" ] + , package haddock ? append [ "-Wno-unused-imports", "-Wno-deprecations" ] + , package directory ? append [ "-Wno-unused-imports" ] + , package binary ? append [ "-Wno-deprecations" ] + , package haskeline ? append [ "-Wno-deprecations", "-Wno-unused-imports", + "-Wno-redundant-constraints", + "-Wno-simplifiable-class-constraints" ] + , package pretty ? append [ "-Wno-unused-imports" ] + , package primitive ? append [ "-Wno-unused-imports", "-Wno-deprecations" ] + , package terminfo ? append [ "-Wno-unused-imports" ] + , package xhtml ? append [ "-Wno-unused-imports", "-Wno-tabs" ] + , package transformers ? append [ "-Wno-unused-matches", "-Wno-unused-imports", + "-Wno-redundant-constraints", "-Wno-orphans" ] + , package base ? append [ "-Wno-trustworthy-safe" ] + , package ghcPrim ? append [ "-Wno-trustworthy-safe" ] + , package win32 ? append [ "-Wno-trustworthy-safe" ] ] + +-- GhcLibExtraHcOpts += -Wno-deprecated-flags +-- GhcBootLibExtraHcOpts += -fno-warn-deprecated-flags +disableWarningArgsLibs :: Args +disableWarningArgsLibs = do + pkg <- getPackage + isLibrary pkg ? builder Ghc ? mconcat + [ notStage0 ? arg "-Wno-deprecated-flags" + , stage Stage0 ? arg "-fno-warn-deprecated-flags"] + +-- TODO: Disable warnings for Windows specifics + -- | All 'Package'-dependent command line arguments. defaultPackageArgs :: Args defaultPackageArgs = mconcat @@ -227,4 +264,7 @@ defaultPackageArgs = mconcat , haddockPackageArgs , integerGmpPackageArgs , rtsPackageArgs - , runGhcPackageArgs ] + , runGhcPackageArgs + , disableWarningArgsStage0 + , disableWarningArgsStage1 + , disableWarningArgsLibs ] From git at git.haskell.org Fri Oct 27 01:18:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Werror to CC and HC (#309) (4952e80) Message-ID: <20171027011840.512103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4952e8022f805d31035c3ecfd354518c72d07557/ghc >--------------------------------------------------------------- commit 4952e8022f805d31035c3ecfd354518c72d07557 Author: Zhen Zhang Date: Wed May 3 08:58:34 2017 -0700 Add Werror to CC and HC (#309) >--------------------------------------------------------------- 4952e8022f805d31035c3ecfd354518c72d07557 src/Settings/Builders/Cc.hs | 5 ++++- src/Settings/Default.hs | 16 +++++++++++++++- src/Settings/Packages/GhcPrim.hs | 1 + src/Settings/Packages/Rts.hs | 4 +++- 4 files changed, 23 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Cc.hs b/src/Settings/Builders/Cc.hs index b5d85df..38a1665 100644 --- a/src/Settings/Builders/Cc.hs +++ b/src/Settings/Builders/Cc.hs @@ -8,7 +8,10 @@ ccBuilderArgs = builder Cc ? mconcat , argSettingList . ConfCcArgs =<< getStage , cIncludeArgs - , builder (Cc CompileC) ? mconcat [ arg "-c", arg =<< getInput + , builder (Cc CompileC) ? mconcat [ arg "-Werror" + -- mk/warning.mk: + -- SRC_CC_OPTS += -Wall $(WERROR) + , arg "-c", arg =<< getInput , arg "-o", arg =<< getOutput ] , builder (Cc FindCDependencies) ? do diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 90e2db0..619fca1 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -65,10 +65,24 @@ defaultArgs = mconcat , sourceArgs defaultSourceArgs , defaultPackageArgs ] +-- | Default flags about Werror +-- | mk/warnings.mk +defaultErrorGhcFlags :: Args +defaultErrorGhcFlags = + mconcat [ notStage0 ? arg "-Werror" + , (not <$> flag GccIsClang) ? mconcat [ + (not <$> flag GccLt46) ? (not <$> windowsHost) ? + arg "-Werror=unused-but-set-variable" + , (not <$> flag GccLt44) ? arg "-Wno-error=inline" ] + , flag GccIsClang ? arg "-Wno-unknown-pragmas" ] + -- | Default source arguments, e.g. optimisation settings. defaultSourceArgs :: SourceArgs defaultSourceArgs = SourceArgs - { hsDefault = mconcat [stage0 ? arg "-O", notStage0 ? arg "-O2", arg "-H32m"] + { hsDefault = mconcat [ stage0 ? arg "-O" + , notStage0 ? arg "-O2" + , arg "-H32m" + , defaultErrorGhcFlags ] , hsLibrary = mempty , hsCompiler = mempty , hsGhc = mempty } diff --git a/src/Settings/Packages/GhcPrim.hs b/src/Settings/Packages/GhcPrim.hs index bed8345..af3c0d5 100644 --- a/src/Settings/Packages/GhcPrim.hs +++ b/src/Settings/Packages/GhcPrim.hs @@ -10,4 +10,5 @@ ghcPrimPackageArgs = package ghcPrim ? mconcat , builder (Cc CompileC) ? (not <$> flag GccLt44) ? + (not <$> flag GccIsClang) ? input "//cbits/atomic.c" ? arg "-Wno-sync-nand" ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 6855402..e278204 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -89,7 +89,9 @@ rtsPackageArgs = package rts ? do , inputs ["//Evac.c", "//Evac_thr.c"] ? arg "-funroll-loops" , inputs ["//Evac_thr.c", "//Scav_thr.c"] ? - append [ "-DPARALLEL_GC", "-Irts/sm" ] ] + append [ "-DPARALLEL_GC", "-Irts/sm" ] + + , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr" ] , builder Ghc ? arg "-Irts" From git at git.haskell.org Fri Oct 27 01:18:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add copyFileUntracked (#313) (bc32262) Message-ID: <20171027011843.CA4343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc32262d3aa0e6586daee0c0d6edef98310ebe98/ghc >--------------------------------------------------------------- commit bc32262d3aa0e6586daee0c0d6edef98310ebe98 Author: Zhen Zhang Date: Tue May 16 13:13:17 2017 -0700 Add copyFileUntracked (#313) >--------------------------------------------------------------- bc32262d3aa0e6586daee0c0d6edef98310ebe98 src/Rules/Libffi.hs | 4 ++-- src/Util.hs | 12 ++++++++++-- 2 files changed, 12 insertions(+), 4 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 99b77c8..57f6263 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -39,7 +39,7 @@ configureEnvironment = do libffiRules :: Rules () libffiRules = do - libffiDependencies &%> \_ -> do + (libffiLibrary : libffiDependencies) &%> \_ -> do useSystemFfi <- flag UseSystemFfi if useSystemFfi then do @@ -57,7 +57,7 @@ libffiRules = do ways <- interpretInContext libffiContext (getLibraryWays <> getRtsWays) forM_ (nubOrd ways) $ \way -> - copyFile libffiLibrary =<< rtsLibffiLibrary way + copyFileUntracked libffiLibrary =<< rtsLibffiLibrary way putSuccess $ "| Successfully built custom library 'libffi'" diff --git a/src/Util.hs b/src/Util.hs index b6d9536..1fd19f8 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -3,7 +3,7 @@ module Util ( removeFile, copyDirectory, copyDirectoryContents, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, makeExecutable, renderProgram, renderLibrary, Match(..), builderEnvironment, - needBuilder + needBuilder, copyFileUntracked ) where import qualified System.Directory.Extra as IO @@ -94,10 +94,18 @@ copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. let dir = takeDirectory target - unlessM (liftIO $ IO.doesDirectoryExist dir) $ createDirectory dir + liftIO $ IO.createDirectoryIfMissing True dir putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target +-- Same as copyFile, but not tracking the source as a build dependency +copyFileUntracked :: FilePath -> FilePath -> Action () +copyFileUntracked source target = do + let dir = takeDirectory target + liftIO $ IO.createDirectoryIfMissing True dir + putProgressInfo $ renderAction "Copy file (Untracked)" source target + liftIO $ IO.copyFile source target + -- | Move a file; we cannot track the source, because it is moved. moveFile :: FilePath -> FilePath -> Action () moveFile source target = do From git at git.haskell.org Fri Oct 27 01:18:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CABAL_VERSION argument in building ghc-cabal (#319) (1fd9854) Message-ID: <20171027011847.763EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1fd9854b798e2a003649baa6cfcc76c9150c0421/ghc >--------------------------------------------------------------- commit 1fd9854b798e2a003649baa6cfcc76c9150c0421 Author: Zhen Zhang Date: Mon Jun 5 18:54:54 2017 +0800 Fix CABAL_VERSION argument in building ghc-cabal (#319) >--------------------------------------------------------------- 1fd9854b798e2a003649baa6cfcc76c9150c0421 src/Settings/Packages/GhcCabal.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 8e5837c..3c830ae 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -1,9 +1,17 @@ module Settings.Packages.GhcCabal (ghcCabalPackageArgs) where +import Distribution.PackageDescription.Parse + import Base import GHC import Oracles.Config.Setting import Predicate +import Package (pkgCabalFile) +import Distribution.Verbosity (silent) +import Distribution.Text (display) +import Distribution.Package (pkgVersion) +import Distribution.PackageDescription (packageDescription) +import qualified Distribution.PackageDescription as DP ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do @@ -12,10 +20,17 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do win <- lift windowsHost let cabalDeps = [ array, base, bytestring, containers, deepseq, directory , pretty, process, time, if win then win32 else unix ] + + lift $ need [pkgCabalFile cabal] + pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile cabal + let identifier = DP.package . packageDescription $ pd + cabalVersion = display . pkgVersion $ identifier + mconcat [ append [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , arg "--make" , arg "-j" + , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" , arg "-DGENERICS" From git at git.haskell.org Fri Oct 27 01:18:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add more utilities including install and symbolic link (#316) (8299d14) Message-ID: <20171027011851.1A52C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8299d146c112c16c528b3681a6e4404eb47c6375/ghc >--------------------------------------------------------------- commit 8299d146c112c16c528b3681a6e4404eb47c6375 Author: Zhen Zhang Date: Tue Jun 6 08:53:14 2017 +0800 Add more utilities including install and symbolic link (#316) >--------------------------------------------------------------- 8299d146c112c16c528b3681a6e4404eb47c6375 cfg/system.config.in | 15 +++++++++++++ src/Oracles/Config/Setting.hs | 50 ++++++++++++++++++++++++++++++++++++++++++- src/Util.hs | 44 ++++++++++++++++++++++++++++++++++++- 3 files changed, 107 insertions(+), 2 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 667a22d..56a7c7f 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -22,6 +22,7 @@ system-ghc-pkg = @GhcPkgCmd@ tar = @TarCmd@ patch = @PatchCmd@ perl = @PerlCmd@ +ln-s = @LN_S@ # Information about builders: #============================ @@ -117,3 +118,17 @@ ffi-lib-dir = @FFILibDir@ #======================= with-libdw = @UseLibdw@ + +# Installation: +#======================= + +install-prefix = @prefix@ +install-bindir = @prefix@/bin +install-libdir = @prefix@/lib +install-datarootdir = @prefix@/share + +install = @INSTALL@ +install-program = @INSTALL@ -m 755 +install-script = @INSTALL@ -m 755 +install-data = @INSTALL@ -m 644 +install-dir = @INSTALL@ -m 755 -d diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index 0b28112..8bdc387 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -2,7 +2,8 @@ module Oracles.Config.Setting ( Setting (..), SettingList (..), setting, settingList, getSetting, getSettingList, anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, - ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost + ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost, + relocatableBuild, installDocDir, installGhcLibDir ) where import Control.Monad.Trans.Reader @@ -51,6 +52,19 @@ data Setting = BuildArch | GmpLibDir | IconvIncludeDir | IconvLibDir + -- Paths to where GHC is installed + | InstallPrefix + | InstallBinDir + | InstallLibDir + | InstallDataRootDir + -- "install" utility + | Install + | InstallData + | InstallProgram + | InstallScript + | InstallDir + -- symbolic link + | LnS data SettingList = ConfCcArgs Stage | ConfCppArgs Stage @@ -94,6 +108,16 @@ setting key = unsafeAskConfig $ case key of GmpLibDir -> "gmp-lib-dir" IconvIncludeDir -> "iconv-include-dir" IconvLibDir -> "iconv-lib-dir" + InstallPrefix -> "install-prefix" + InstallBinDir -> "install-bindir" + InstallLibDir -> "install-libdir" + InstallDataRootDir -> "install-datarootdir" + Install -> "install" + InstallDir -> "install-dir" + InstallProgram -> "install-program" + InstallScript -> "install-script" + InstallData -> "install-data" + LnS -> "ln-s" settingList :: SettingList -> Action [String] settingList key = fmap words $ unsafeAskConfig $ case key of @@ -173,3 +197,27 @@ cmdLineLengthLimit = do (False, True) -> 200000 -- On all other systems, we try this: _ -> 4194304 -- Cabal library needs a bit more than 2MB! + +-- | On Windows we normally want to make a relocatable bindist, +-- to we ignore flags like libdir +-- ref: mk/config.mk.in:232 +relocatableBuild :: Action Bool +relocatableBuild = windowsHost + +installDocDir :: Action String +installDocDir = do + version <- setting ProjectVersion + (-/- ("doc/ghc-" ++ version)) <$> setting InstallDataRootDir + +-- | Unix: override libdir and datadir to put ghc-specific stuff in +-- a subdirectory with the version number included. +-- ref: mk/install.mk:101 +-- TODO: CroosCompilePrefix +installGhcLibDir :: Action String +installGhcLibDir = do + r <- relocatableBuild + libdir <- setting InstallLibDir + if r then return libdir + else do + v <- setting ProjectVersion + return (libdir -/- ("ghc-" ++ v)) diff --git a/src/Util.hs b/src/Util.hs index 1fd19f8..a7310be 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -3,7 +3,8 @@ module Util ( removeFile, copyDirectory, copyDirectoryContents, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, makeExecutable, renderProgram, renderLibrary, Match(..), builderEnvironment, - needBuilder, copyFileUntracked + needBuilder, copyFileUntracked, installDir, installData, installScript, + installProgram, linkSymbolic ) where import qualified System.Directory.Extra as IO @@ -18,6 +19,7 @@ import GHC import Oracles.ArgsHash import Oracles.DirectoryContents import Oracles.Path +import Oracles.Config.Setting import Settings import Settings.Builders.Ar import Target @@ -169,6 +171,46 @@ applyPatch dir patch = do putBuild $ "| Apply patch " ++ file quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] +-- | Install a directory +installDir :: FilePath -> Action () +installDir dir = do + i <- setting InstallDir + putBuild $ "| Install directory" ++ dir + quietly $ cmd i dir + +-- | Install data file to a directory +installData :: [FilePath] -> FilePath -> Action () +installData fs dir = do + i <- setting InstallData + forM_ fs $ \f -> + putBuild $ "| Install data " ++ f ++ " to " ++ dir + quietly $ cmd i fs dir + +-- | Install executable file to a directory +installProgram :: FilePath -> FilePath -> Action () +installProgram f dir = do + i <- setting InstallProgram + putBuild $ "| Install program " ++ f ++ " to " ++ dir + quietly $ cmd i f dir + +-- | Install executable script to a directory +installScript :: FilePath -> FilePath -> Action () +installScript f dir = do + i <- setting InstallScript + putBuild $ "| Install script " ++ f ++ " to " ++ dir + quietly $ cmd i f dir + +-- | Create a symbolic link from source file to target file when supported +linkSymbolic :: FilePath -> FilePath -> Action () +linkSymbolic source target = do + lns <- setting LnS + when (lns /= "") $ do + need [source] -- Guarantee source is built before printing progress info. + let dir = takeDirectory target + liftIO $ IO.createDirectoryIfMissing True dir + putProgressInfo $ renderAction "Create symbolic link" source target + quietly $ cmd lns source target + isInternal :: Builder -> Bool isInternal = isJust . builderProvenance From git at git.haskell.org Fri Oct 27 01:18:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compute cabalDeps in GhcCabal build (#320) (0589a9e) Message-ID: <20171027011854.963933A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c/ghc >--------------------------------------------------------------- commit 0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c Author: Zhen Zhang Date: Tue Jun 6 23:46:11 2017 +0800 Compute cabalDeps in GhcCabal build (#320) >--------------------------------------------------------------- 0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c src/Oracles/Dependencies.hs | 9 ++++++++- src/Settings/Packages/GhcCabal.hs | 7 ++----- 2 files changed, 10 insertions(+), 6 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 2d6a404..167047d 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,6 +1,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.Dependencies ( - fileDependencies, contextDependencies, needContext, dependenciesOracles + fileDependencies, contextDependencies, needContext, dependenciesOracles, + pkgDependencies ) where import qualified Data.HashMap.Strict as Map @@ -47,6 +48,12 @@ contextDependencies context at Context {..} = do pkgs <- sort <$> interpretInContext (pkgContext package) getPackages return . map pkgContext $ intersectOrd (compare . pkgNameString) pkgs deps +-- | Given a `Package`, this `Action` looks up its package dependencies +-- 'Settings.Paths.packageDependencies' using 'packageDependenciesOracle' +-- The context will be the vanilla context with stage equal to 1 +pkgDependencies :: Package -> Action [Package] +pkgDependencies = fmap (map Context.package) . contextDependencies . vanillaContext Stage1 + -- | Coarse-grain 'need': make sure given contexts are fully built. needContext :: [Context] -> Action () needContext cs = do diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 3c830ae..57147e4 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -5,6 +5,7 @@ import Distribution.PackageDescription.Parse import Base import GHC import Oracles.Config.Setting +import Oracles.Dependencies (pkgDependencies) import Predicate import Package (pkgCabalFile) import Distribution.Verbosity (silent) @@ -15,12 +16,8 @@ import qualified Distribution.PackageDescription as DP ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do - -- Note: We could compute 'cabalDeps' instead of hard-coding it but this - -- seems unnecessary since we plan to drop @ghc-cabal@ altogether, #18. win <- lift windowsHost - let cabalDeps = [ array, base, bytestring, containers, deepseq, directory - , pretty, process, time, if win then win32 else unix ] - + cabalDeps <- lift $ pkgDependencies cabal lift $ need [pkgCabalFile cabal] pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile cabal let identifier = DP.package . packageDescription $ pd From git at git.haskell.org Fri Oct 27 01:18:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:18:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix implicit assumption about inplace installation etc. (#315) (02351ac) Message-ID: <20171027011858.2205C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/02351ac97f66df4b8c02b0df587e4dde7c4201c8/ghc >--------------------------------------------------------------- commit 02351ac97f66df4b8c02b0df587e4dde7c4201c8 Author: Zhen Zhang Date: Wed Jun 7 09:04:28 2017 +0800 Fix implicit assumption about inplace installation etc. (#315) >--------------------------------------------------------------- 02351ac97f66df4b8c02b0df587e4dde7c4201c8 hadrian.cabal | 5 ++-- src/GHC.hs | 8 +---- src/Rules.hs | 2 +- src/Rules/Cabal.hs | 1 - src/Rules/Clean.hs | 4 +-- src/Rules/Generate.hs | 37 +++++++++++++---------- src/Rules/Generators/GhcSplit.hs | 8 +++-- src/Rules/Program.hs | 34 +++++++++++----------- src/Rules/Register.hs | 2 +- src/Rules/Wrappers.hs | 63 ++++++++++++++++++++++++++++++++++++++++ src/Rules/Wrappers/Ghc.hs | 14 --------- src/Rules/Wrappers/GhcPkg.hs | 19 ------------ src/Rules/Wrappers/RunGhc.hs | 15 ---------- src/Settings/Builders/Common.hs | 2 +- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Install.hs | 14 +++++++++ src/Settings/Path.hs | 39 +++++++++++++++---------- 17 files changed, 154 insertions(+), 116 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 02351ac97f66df4b8c02b0df587e4dde7c4201c8 From git at git.haskell.org Fri Oct 27 01:19:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add binary wrappers for hp2ps, hpc, hsc2hs (#321) (49835af) Message-ID: <20171027011901.C22843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49835aff3bd03dd24d00e9c89aaed0339e4aa3a5/ghc >--------------------------------------------------------------- commit 49835aff3bd03dd24d00e9c89aaed0339e4aa3a5 Author: Zhen Zhang Date: Wed Jun 7 18:15:03 2017 +0800 Add binary wrappers for hp2ps, hpc, hsc2hs (#321) >--------------------------------------------------------------- 49835aff3bd03dd24d00e9c89aaed0339e4aa3a5 src/Rules/Program.hs | 12 ++++++++---- src/Rules/Wrappers.hs | 36 ++++++++++++++++++++++++++++++++++-- 2 files changed, 42 insertions(+), 6 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 79f01f2..5b2e66f 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -12,7 +12,8 @@ import Oracles.ModuleFiles import Oracles.PackageData import Oracles.Path (topDirectory) import Rules.Wrappers (WrappedBinary(..), Wrapper, - ghcWrapper, runGhcWrapper, inplaceGhcPkgWrapper) + ghcWrapper, runGhcWrapper, inplaceGhcPkgWrapper, + hpcWrapper, hp2psWrapper, hsc2hsWrapper) import Settings import Settings.Path (buildPath, inplaceLibBinPath, rtsContext, objectPath, inplaceLibPath, inplaceBinPath) @@ -22,10 +23,13 @@ import Util -- | List of wrappers we build. wrappers :: [(Context, Wrapper)] -wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) - , (vanillaContext Stage1 ghc , ghcWrapper ) +wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper) + , (vanillaContext Stage1 ghc , ghcWrapper) , (vanillaContext Stage1 runGhc, runGhcWrapper) - , (vanillaContext Stage0 ghcPkg, inplaceGhcPkgWrapper) ] + , (vanillaContext Stage0 ghcPkg, inplaceGhcPkgWrapper) + , (vanillaContext Stage1 hp2ps , hp2psWrapper) + , (vanillaContext Stage1 hpc , hpcWrapper) + , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) ] buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs index 93dfee0..246d28a 100644 --- a/src/Rules/Wrappers.hs +++ b/src/Rules/Wrappers.hs @@ -1,13 +1,15 @@ module Rules.Wrappers ( WrappedBinary(..), Wrapper, ghcWrapper, runGhcWrapper, - inplaceGhcPkgWrapper, installGhcPkgWrapper + inplaceGhcPkgWrapper, installGhcPkgWrapper, hp2psWrapper, + hpcWrapper, hsc2hsWrapper ) where import Base -import Expression (Expr, getStage) +import Expression import Settings.Install (installPackageDbDirectory) import Settings.Path (inplacePackageDbDirectory) import Oracles.Path (getTopDirectory) +import Oracles.Config.Setting (SettingList(..), settingList) -- | Wrapper is an expression depending on the 'FilePath' to the -- | library path and name of the wrapped binary. @@ -61,3 +63,33 @@ installGhcPkgWrapper WrappedBinary{..} = do [ "#!/bin/bash" , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " --global-package-db " ++ packageDb ++ " ${1+\"$@\"}" ] + +hp2psWrapper :: WrappedBinary -> Expr String +hp2psWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ] + +hpcWrapper :: WrappedBinary -> Expr String +hpcWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ] + +hsc2hsWrapper :: WrappedBinary -> Expr String +hsc2hsWrapper WrappedBinary{..} = do + top <- getTopDirectory + lift $ need [ sourcePath -/- "Rules/Wrappers.hs" ] + contents <- lift $ readFile' $ top -/- "utils/hsc2hs/hsc2hs.wrapper" + let executableName = binaryLibPath -/- "bin" -/- binaryName + confCcArgs <- lift $ settingList (ConfCcArgs Stage1) + confGccLinkerArgs <- lift $ settingList (ConfGccLinkerArgs Stage1) + let hsc2hsExtra = unwords (map ("-cflags=" ++) confCcArgs) ++ " " ++ + unwords (map ("-lflags=" ++) confGccLinkerArgs) + return $ unlines + [ "#!/bin/bash" + , "executablename=\"" ++ executableName ++ "\"" + , "HSC2HS_EXTRA=\"" ++ hsc2hsExtra ++ "\"" + , contents ] From git at git.haskell.org Fri Oct 27 01:19:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dependency on hoopl (#328) (ffc905cf) Message-ID: <20171027011905.879513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffc905cf864570cbbc2699ef54570614f9fd6af8/ghc >--------------------------------------------------------------- commit ffc905cf864570cbbc2699ef54570614f9fd6af8 Author: Zhen Zhang Date: Sun Jun 25 17:02:16 2017 +0800 Drop dependency on hoopl (#328) >--------------------------------------------------------------- ffc905cf864570cbbc2699ef54570614f9fd6af8 src/GHC.hs | 5 ++--- src/Settings/Builders/GhcCabal.hs | 2 -- src/Settings/Default.hs | 1 - 3 files changed, 2 insertions(+), 6 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 441f068..78bb356 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -4,7 +4,7 @@ module GHC ( array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, - ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, + ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, @@ -28,7 +28,7 @@ defaultKnownPackages = , compiler, containers, deepseq, deriveConstants, directory, dllSplit , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs - , hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi + , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 , xhtml ] @@ -62,7 +62,6 @@ ghcTags = utility "ghctags" haddock = utility "haddock" haskeline = library "haskeline" hsc2hs = utility "hsc2hs" -hoopl = library "hoopl" hp2ps = utility "hp2ps" hpc = library "hpc" hpcBin = utility "hpc-bin" `setPath` "utils/hpc" diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 1c50729..428c376 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -269,8 +269,6 @@ dll0Args = do , "CodeGen.Platform.X86" , "CodeGen.Platform.X86_64" , "FastBool" - , "Hoopl" - , "Hoopl.Dataflow" , "InteractiveEvalTypes" , "MkGraph" , "PprCmm" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 619fca1..d7059bf 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -115,7 +115,6 @@ stage0Packages = do , ghcPkg , ghcTags , hsc2hs - , hoopl , hp2ps , hpc , mkUserGuidePart From git at git.haskell.org Fri Oct 27 01:19:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Install Rules (#312) (3935e97) Message-ID: <20171027011909.0FCE53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3935e97df7496458482dc1b47b6e63c5950dbfc6/ghc >--------------------------------------------------------------- commit 3935e97df7496458482dc1b47b6e63c5950dbfc6 Author: Zhen Zhang Date: Mon Jun 26 01:37:20 2017 +0800 Add Install Rules (#312) >--------------------------------------------------------------- 3935e97df7496458482dc1b47b6e63c5950dbfc6 hadrian.cabal | 1 + src/GHC.hs | 3 +- src/Main.hs | 2 + src/Oracles/Config/Setting.hs | 1 + src/Rules.hs | 29 ++-- src/Rules/Generate.hs | 4 +- src/Rules/Install.hs | 310 ++++++++++++++++++++++++++++++++++++++ src/Rules/Program.hs | 16 +- src/Rules/Wrappers.hs | 39 ++++- src/Settings.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 7 +- src/Settings/Packages/Rts.hs | 18 ++- src/Settings/Path.hs | 17 ++- src/UserSettings.hs | 9 +- 14 files changed, 417 insertions(+), 44 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 3935e97df7496458482dc1b47b6e63c5950dbfc6 From git at git.haskell.org Fri Oct 27 01:19:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build dynamic libs (#325) (49b13b8) Message-ID: <20171027011912.821DB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/49b13b8c749a49d53e2e1749d2ee46b18261e3ce/ghc >--------------------------------------------------------------- commit 49b13b8c749a49d53e2e1749d2ee46b18261e3ce Author: Zhen Zhang Date: Mon Jun 26 14:47:18 2017 +0800 Build dynamic libs (#325) >--------------------------------------------------------------- 49b13b8c749a49d53e2e1749d2ee46b18261e3ce src/Base.hs | 8 ++++- src/Rules.hs | 4 +++ src/Rules/Library.hs | 62 +++++++++++++++++++++++++++++---------- src/Settings/Builders/Cc.hs | 6 +++- src/Settings/Builders/Ghc.hs | 5 +++- src/Settings/Default.hs | 5 ++-- src/Settings/Flavours/Quick.hs | 5 +++- src/Settings/Flavours/Quickest.hs | 1 + src/Way.hs | 2 +- 9 files changed, 75 insertions(+), 23 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 49b13b8c749a49d53e2e1749d2ee46b18261e3ce From git at git.haskell.org Fri Oct 27 01:19:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't pass gcc warning options to ghc (#329) (ae7358b) Message-ID: <20171027011916.0B1EC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae7358b596831a2f7683c51e04274099b73c2f20/ghc >--------------------------------------------------------------- commit ae7358b596831a2f7683c51e04274099b73c2f20 Author: Ben Gamari Date: Wed Jun 28 03:48:47 2017 -0400 Don't pass gcc warning options to ghc (#329) We would previously pass -Werror=unused-but-set-variable and -Wno-error=inline to ghc, despite the fact that they are gcc flags. >--------------------------------------------------------------- ae7358b596831a2f7683c51e04274099b73c2f20 src/Settings/Default.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 49ffcb6..3ad1fab 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -72,9 +72,9 @@ defaultErrorGhcFlags = mconcat [ notStage0 ? arg "-Werror" , (not <$> flag GccIsClang) ? mconcat [ (not <$> flag GccLt46) ? (not <$> windowsHost) ? - arg "-Werror=unused-but-set-variable" - , (not <$> flag GccLt44) ? arg "-Wno-error=inline" ] - , flag GccIsClang ? arg "-Wno-unknown-pragmas" ] + arg "-optc-Werror=unused-but-set-variable" + , (not <$> flag GccLt44) ? arg "-optc-Wno-error=inline" ] + , flag GccIsClang ? arg "-optc-Wno-unknown-pragmas" ] -- | Default source arguments, e.g. optimisation settings. defaultSourceArgs :: SourceArgs From git at git.haskell.org Fri Oct 27 01:19:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Various portability fixes (#331) (edd539f) Message-ID: <20171027011919.7663C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/edd539fc138d3e4b346b9375a63e4e52dafe9020/ghc >--------------------------------------------------------------- commit edd539fc138d3e4b346b9375a63e4e52dafe9020 Author: Ben Gamari Date: Fri Jun 30 13:45:23 2017 -0400 Various portability fixes (#331) * Don't assume location of bash interpreter * Pass curses library directory path to configure >--------------------------------------------------------------- edd539fc138d3e4b346b9375a63e4e52dafe9020 cfg/system.config.in | 2 ++ src/Oracles/Config/Setting.hs | 3 +++ src/Oracles/Path.hs | 9 ++++++--- src/Rules/Wrappers.hs | 26 +++++++++++++++++--------- src/Settings/Builders/GhcCabal.hs | 1 + src/Util.hs | 6 ++++-- 6 files changed, 33 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc edd539fc138d3e4b346b9375a63e4e52dafe9020 From git at git.haskell.org Fri Oct 27 01:19:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix setup-config dependency (#334) (6d46b39) Message-ID: <20171027011923.062C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d46b39a971e8b833b5ffd8f0666c3361fd79bc0/ghc >--------------------------------------------------------------- commit 6d46b39a971e8b833b5ffd8f0666c3361fd79bc0 Author: Zhen Zhang Date: Mon Jul 3 04:05:13 2017 +0800 Fix setup-config dependency (#334) >--------------------------------------------------------------- 6d46b39a971e8b833b5ffd8f0666c3361fd79bc0 src/Rules.hs | 2 ++ src/Rules/Data.hs | 6 ++++-- src/Rules/Install.hs | 3 ++- src/Settings/Path.hs | 8 +++++++- 4 files changed, 15 insertions(+), 4 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 6e9f5d7..e5835c0 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -39,6 +39,8 @@ buildLib stage pkg = do when (pkg `elem` activePackages) $ if isLibrary pkg then do -- build a library + when (nonCabalContext context) $ + need [pkgSetupConfigFile context] ways <- interpretInContext context getLibraryWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 0538f6c..0c19b2a 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -20,8 +20,9 @@ buildPackageData context at Context {..} = do cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile context + setupConfigFile = pkgSetupConfigFile context - dataFile %> \mk -> do + [dataFile, setupConfigFile] &%> \(mk:setupConfig:_) -> do -- Make sure all generated dependencies are in place before proceeding. orderOnly =<< interpretInContext context generatedDependencies @@ -32,7 +33,7 @@ buildPackageData context at Context {..} = do need =<< mapM pkgConfFile =<< contextDependencies context need [cabalFile] - build $ Target context GhcCabal [cabalFile] [mk] + build $ Target context GhcCabal [cabalFile] [mk, setupConfig] postProcessPackageData context mk pkgInplaceConfig context %> \conf -> do @@ -107,6 +108,7 @@ packageCmmSources pkg -- For example, @libraries/deepseq/dist-install_VERSION = 1.4.0.0@ -- is replaced by @VERSION = 1.4.0.0 at . -- Reason: Shake's built-in makefile parser doesn't recognise slashes +-- TODO (izgzhen): should fix DEP_LIB_REL_DIRS_SEARCHPATH postProcessPackageData :: Context -> FilePath -> Action () postProcessPackageData context at Context {..} file = do top <- topDirectory diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 3499b26..e7c6d41 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -18,7 +18,7 @@ import Oracles.Config.Setting import Oracles.PackageData import Oracles.Path -import qualified System.Directory.Extra as IO +import qualified System.Directory as IO {- | Install the built binaries etc. to the @destDir ++ prefix at . @@ -133,6 +133,7 @@ withLatestBuildStage pkg m = do installPackageConf :: Action () installPackageConf = do let context = vanillaContext Stage0 rts + liftIO $ IO.createDirectoryIfMissing True (takeDirectory pkgConfInstallPath) build $ Target context HsCpp [ pkgPath rts -/- "package.conf.in" ] [ pkgConfInstallPath <.> "raw" ] Stdout out <- cmd ("grep" :: String) [ "-v", "^#pragma GCC" diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 240f992..8814620 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -5,7 +5,8 @@ module Settings.Path ( rtsContext, rtsBuildPath, rtsConfIn, shakeFilesPath,inplacePackageDbDirectory, pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, - installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath + installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, + pkgSetupConfigFile ) where import Base @@ -74,6 +75,11 @@ pkgInplaceConfig context = buildPath context -/- "inplace-pkg-config" pkgDataFile :: Context -> FilePath pkgDataFile context = buildPath context -/- "package-data.mk" + +-- | Path to the @setup-config@ of a given 'Context'. +pkgSetupConfigFile :: Context -> FilePath +pkgSetupConfigFile context = buildPath context -/- "setup-config" + -- | Path to the haddock file of a given 'Context', e.g.: -- "_build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath From git at git.haskell.org Fri Oct 27 01:19:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Stage1Only rule (#340) (b245f0e) Message-ID: <20171027011926.830BD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b245f0e8ce176399dd87de283c7ad77125033bf5/ghc >--------------------------------------------------------------- commit b245f0e8ce176399dd87de283c7ad77125033bf5 Author: Zhen Zhang Date: Thu Jul 6 14:11:00 2017 +0800 Add Stage1Only rule (#340) >--------------------------------------------------------------- b245f0e8ce176399dd87de283c7ad77125033bf5 src/Oracles/Dependencies.hs | 2 +- src/Rules.hs | 36 ++++++++++++++++++++++++++++-------- src/Rules/Install.hs | 2 +- src/Settings.hs | 12 +++++++++++- src/UserSettings.hs | 21 ++++++++++++++++++--- 5 files changed, 59 insertions(+), 14 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 167047d..2775b3e 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -63,7 +63,7 @@ needContext cs = do lib0 <- buildDll0 context ghciLib <- pkgGhciLibraryFile context ghciFlag <- interpretInContext context $ getPkgData BuildGhciLib - let ghci = ghciFlag == "YES" && stage context == Stage1 + let ghci = ghciFlag == "YES" && (stage context == Stage1 || stage1Only) return $ [ libFile ] ++ [ lib0File | lib0 ] ++ [ ghciLib | ghci ] confs <- mapM pkgConfFile cs need $ libs ++ confs diff --git a/src/Rules.hs b/src/Rules.hs index e5835c0..3ba6ba7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,4 +1,4 @@ -module Rules (topLevelTargets, buildLib, buildRules) where +module Rules (topLevelTargets, buildPackage, buildRules) where import Base import Context @@ -18,22 +18,35 @@ import qualified Rules.Library import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register +import Oracles.Dependencies (needContext) +import Util (needBuilder) import Settings import Settings.Path allStages :: [Stage] allStages = [minBound ..] --- | This rule 'need' all top-level build targets. +-- | This rule 'need' all top-level build targets +-- or Stage1Only targets topLevelTargets :: Rules () -topLevelTargets = do - want $ Rules.Generate.inplaceLibCopyTargets +topLevelTargets = action $ do + need $ Rules.Generate.inplaceLibCopyTargets - forM_ allStages $ \stage -> - forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> action (buildLib stage pkg) + if stage1Only + then do + forAllPkgs $ \stg pkg -> + when (isLibrary pkg) $ + buildPackage stg pkg + forM_ programsStage1Only $ buildPackage Stage0 + else + forAllPkgs buildPackage + where + forAllPkgs f = + forM_ allStages $ \stage -> + forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> f stage pkg -buildLib :: Stage -> Package -> Action () -buildLib stage pkg = do +buildPackage :: Stage -> Package -> Action () +buildPackage stage pkg = do let context = vanillaContext stage pkg activePackages <- interpretInContext context getPackages when (pkg `elem` activePackages) $ @@ -44,6 +57,7 @@ buildLib stage pkg = do ways <- interpretInContext context getLibraryWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour + needContext [context] need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else -- otherwise build a program need =<< maybeToList <$> programPath (programContext stage pkg) @@ -90,3 +104,9 @@ buildRules = do Rules.Libffi.libffiRules packageRules Rules.Perl.perlScriptRules + +programsStage1Only :: [Package] +programsStage1Only = + [ deriveConstants, genprimopcode, hp2ps, runGhc + , ghcCabal, hpc, dllSplit, ghcPkg, hsc2hs + , genapply, ghc ] diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index e7c6d41..0492a62 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -191,7 +191,7 @@ installPackages = do let context = vanillaContext stg pkg top <- interpretInContext context getTopDirectory let installDistDir = top -/- buildPath context - buildLib stg pkg + buildPackage stg pkg docDir <- installDocDir ghclibDir <- installGhcLibDir version <- interpretInContext context (getPkgData Version) diff --git a/src/Settings.hs b/src/Settings.hs index d09fa31..8152a6e 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -3,7 +3,7 @@ module Settings ( findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, getContextDirectory, getBuildPath, stagePackages, builderPath, getBuilderPath, isSpecified, latestBuildStage, programPath, programContext, - integerLibraryName, destDir, pkgConfInstallPath + integerLibraryName, destDir, pkgConfInstallPath, stage1Only ) where import Base @@ -117,3 +117,13 @@ programPath context at Context {..} = do pkgConfInstallPath :: FilePath pkgConfInstallPath = buildPath (vanillaContext Stage0 rts) -/- "package.conf.install" + +-- | Stage1Only flag +-- TODO: Set this by cmdline flags +stage1Only :: Bool +stage1Only = defaultStage1Only + +-- | Install's DESTDIR flag +-- TODO: Set this by cmdline flags +destDir :: FilePath +destDir = defaultDestDir diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 96e6f4b..4398700 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -4,7 +4,7 @@ -- accidentally commit them. module UserSettings ( buildRootPath, userFlavours, userKnownPackages, verboseCommands, - putBuild, putSuccess, destDir + putBuild, putSuccess, defaultDestDir, defaultStage1Only ) where import System.Console.ANSI @@ -47,5 +47,20 @@ putSuccess = putColoured Dull Green -- It is by default empty, representing the root of file system, -- or it might be a directory. -- It is usually used with @prefix@, like @/usr/local@ -destDir :: FilePath -destDir = "" +defaultDestDir :: FilePath +defaultDestDir = "" + +{- + Stage1Only=YES means: + - don't build ghc-stage2 (the executable) + - don't build utils that rely on ghc-stage2 + See Note [No stage2 packages when CrossCompiling or Stage1Only] in + ./ghc.mk. + - install ghc-stage1 instead of ghc-stage2 + - install the ghc-pkg that was built with the stage0 compiler + - (*do* still build compiler/stage2 (i.e. the ghc library)) + - (*do* still build all other libraries) +-} +-- | Stage1Only flag, default off +defaultStage1Only :: Bool +defaultStage1Only = False From git at git.haskell.org Fri Oct 27 01:19:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Automate dependency analysis of installed packages (#342) (5f0e385) Message-ID: <20171027011930.152CB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5f0e385d4377c5d51997ed3f51340d1405095c5d/ghc >--------------------------------------------------------------- commit 5f0e385d4377c5d51997ed3f51340d1405095c5d Author: Zhen Zhang Date: Sat Jul 8 20:35:23 2017 +0800 Automate dependency analysis of installed packages (#342) >--------------------------------------------------------------- 5f0e385d4377c5d51997ed3f51340d1405095c5d src/Oracles/Dependencies.hs | 19 +++++++++++++++++-- src/Rules.hs | 1 - src/Rules/Install.hs | 20 +++++++------------- 3 files changed, 24 insertions(+), 16 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 2775b3e..447df25 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,7 +1,7 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, TupleSections #-} module Oracles.Dependencies ( fileDependencies, contextDependencies, needContext, dependenciesOracles, - pkgDependencies + pkgDependencies, sortPkgsByDep ) where import qualified Data.HashMap.Strict as Map @@ -81,3 +81,18 @@ dependenciesOracles = do putLoud $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return $ Map.fromList [ (key, values) | (key:values) <- contents ] + +-- | Sort packages by their dependency +-- HACK (izgzhen): See https://github.com/snowleopard/hadrian/issues/344 for details +sortPkgsByDep :: [Package] -> Action [Package] +sortPkgsByDep pkgs = do + elems <- mapM (\p -> (p,) <$> pkgDependencies p) pkgs + return $ map fst $ topSort elems + where + annotateInDeg es e = + (foldr (\e' s -> if fst e' `elem` snd e then s + 1 else s) 0 es, e) + topSort [] = [] + topSort es = + let annotated = map (annotateInDeg es) es + inDegZero = map snd $ filter ((== 0). fst) annotated + in inDegZero ++ topSort (es \\ inDegZero) diff --git a/src/Rules.hs b/src/Rules.hs index 3ba6ba7..2081585 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -19,7 +19,6 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Oracles.Dependencies (needContext) -import Util (needBuilder) import Settings import Settings.Path diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 0492a62..8530f50 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -15,7 +15,7 @@ import Rules.Libffi import Rules.Generate import Settings.Packages.Rts import Oracles.Config.Setting -import Oracles.PackageData +import Oracles.Dependencies (sortPkgsByDep) import Oracles.Path import qualified System.Directory as IO @@ -81,7 +81,6 @@ installLibExecs = do (destDir ++ libExecDir -/- "ghc" <.> exe) -- | Binaries to install --- TODO: Consider Stage1Only installBinPkgs :: [Package] installBinPkgs = [ ghc, ghcPkg, ghcSplit, hp2ps @@ -176,14 +175,10 @@ installPackages = do copyFile ghcBootPlatformHeader (pkgPath compiler -/- "ghc_boot_platform.h") - -- TODO: Consider Stage1Only - -- TODO: Use automatic dependency analysis, rather than hardcoding - -- the ordering - let installLibPkgs = [ ghcPrim, integerSimple, base, filepath - , array, deepseq, bytestring, containers, time, unix - , directory, process, hpc, pretty, binary, cabal - , ghcBootTh, ghcBoot, templateHaskell - , transformers, terminfo, haskeline, ghci, compiler ] + activePackages <- filterM ((isJust <$>) . latestBuildStage) + (knownPackages \\ [rts, libffi]) + + installLibPkgs <- sortPkgsByDep (filter isLibrary activePackages) forM_ installLibPkgs $ \pkg at Package{..} -> do when (isLibrary pkg) $ @@ -194,10 +189,9 @@ installPackages = do buildPackage stg pkg docDir <- installDocDir ghclibDir <- installGhcLibDir - version <- interpretInContext context (getPkgData Version) + -- Copy over packages - let targetDest = destDir ++ ghclibDir -/- - pkgNameString pkg ++ "-" ++ version + strip <- stripCmdPath context ways <- interpretInContext context getLibraryWays let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" -- HACK? From git at git.haskell.org Fri Oct 27 01:19:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Better tracking of dependence in installation (#353) (d8e1759) Message-ID: <20171027011933.8E1DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d8e17590fc8efcbd87f97bb1d85a1775b85272d3/ghc >--------------------------------------------------------------- commit d8e17590fc8efcbd87f97bb1d85a1775b85272d3 Author: Zhen Zhang Date: Sat Jul 8 21:02:17 2017 +0800 Better tracking of dependence in installation (#353) >--------------------------------------------------------------- d8e17590fc8efcbd87f97bb1d85a1775b85272d3 src/Rules/Install.hs | 27 ++++++++++++--------------- src/Util.hs | 3 +++ 2 files changed, 15 insertions(+), 15 deletions(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 8530f50..4c91316 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedStrings, FlexibleContexts #-} +{-# LANGUAGE FlexibleContexts #-} module Rules.Install (installRules) where import Base @@ -39,8 +39,8 @@ XXX (izgzhen): Do we need @INSTALL_OPTS@ in the make scripts? installRules :: Rules () installRules = do "install" ~> do - installPackageConf installIncludes + installPackageConf installCommonLibs installLibExecs installLibExecScripts @@ -54,7 +54,6 @@ getLibExecDir = (-/- "bin") <$> installGhcLibDir -- ref: ghc.mk installLibExecScripts :: Action () installLibExecScripts = do - need libExecScripts libExecDir <- getLibExecDir installDir (destDir ++ libExecDir) forM_ libExecScripts $ \script -> do @@ -74,7 +73,6 @@ installLibExecs = do withLatestBuildStage pkg $ \stg -> do let context = programContext stg pkg let bin = inplaceLibBinPath -/- programName context <.> exe - need [bin] installProgram bin (destDir ++ libExecDir) when (pkg == ghc) $ do moveFile (destDir ++ libExecDir -/- programName context <.> exe) @@ -111,10 +109,9 @@ installBins = do contents <- interpretInContext context $ wrapper (WrappedBinary (destDir ++ libDir) symName) - withTempDir $ \tmp -> do - let tmpfile = tmp -/- binName - writeFileChanged tmpfile contents - installProgram tmpfile (destDir ++ binDir) + let wrapperPath = destDir ++ binDir -/- binName + writeFileChanged wrapperPath contents + makeExecutable wrapperPath unlessM windowsHost $ linkSymbolic (destDir ++ binDir -/- binName) (destDir ++ binDir -/- symName) @@ -135,13 +132,12 @@ installPackageConf = do liftIO $ IO.createDirectoryIfMissing True (takeDirectory pkgConfInstallPath) build $ Target context HsCpp [ pkgPath rts -/- "package.conf.in" ] [ pkgConfInstallPath <.> "raw" ] - Stdout out <- cmd ("grep" :: String) [ "-v", "^#pragma GCC" - , pkgConfInstallPath <.> "raw" ] + Stdout content <- cmd "grep" [ "-v", "^#pragma GCC" + , pkgConfInstallPath <.> "raw" ] withTempFile $ \tmp -> do - liftIO $ writeFile tmp out - Stdout out' <- cmd ("sed" :: String) - [ "-e", "s/\"\"//g", "-e", "s/:[ ]*,/: /g", tmp ] - liftIO $ writeFile pkgConfInstallPath out' + liftIO $ writeFile tmp content + Stdout content' <- cmd "sed" [ "-e", "s/\"\"//g", "-e", "s/:[ ]*,/: /g", tmp ] + liftIO $ writeFile pkgConfInstallPath content' -- | Install packages to @prefix/lib@ -- ref: ghc.mk @@ -195,6 +191,7 @@ installPackages = do strip <- stripCmdPath context ways <- interpretInContext context getLibraryWays let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" -- HACK? + need [ ghcCabalInplace ] -- HACK (#318): copy stuff back to the place favored by ghc-cabal quietly $ copyDirectoryContents (Not excluded) @@ -250,7 +247,7 @@ installPackages = do [ "--force", "--global-package-db" , installedPackageConf, "recache" ] where - createData f = unit $ cmd ("chmod" :: String) [ "644", f ] + createData f = unit $ cmd "chmod" [ "644", f ] excluded = Or [ Test "//haddock-prologue.txt" , Test "//package-data.mk" diff --git a/src/Util.hs b/src/Util.hs index c2335c2..da12e21 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -184,6 +184,7 @@ installDir dir = do installData :: [FilePath] -> FilePath -> Action () installData fs dir = do i <- setting InstallData + need fs forM_ fs $ \f -> putBuild $ "| Install data " ++ f ++ " to " ++ dir quietly $ cmd i fs dir @@ -192,6 +193,7 @@ installData fs dir = do installProgram :: FilePath -> FilePath -> Action () installProgram f dir = do i <- setting InstallProgram + need [f] putBuild $ "| Install program " ++ f ++ " to " ++ dir quietly $ cmd i f dir @@ -199,6 +201,7 @@ installProgram f dir = do installScript :: FilePath -> FilePath -> Action () installScript f dir = do i <- setting InstallScript + need [f] putBuild $ "| Install script " ++ f ++ " to " ++ dir quietly $ cmd i f dir From git at git.haskell.org Fri Oct 27 01:19:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update README.md (#352) (e93f583d) Message-ID: <20171027011937.26FE03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e93f583d1d684e9db069c558967dc38d19a180e8/ghc >--------------------------------------------------------------- commit e93f583d1d684e9db069c558967dc38d19a180e8 Author: Zhen Zhang Date: Sat Jul 8 21:25:06 2017 +0800 Update README.md (#352) >--------------------------------------------------------------- e93f583d1d684e9db069c558967dc38d19a180e8 README.md | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index 2256fbf..d65b98c 100644 --- a/README.md +++ b/README.md @@ -106,6 +106,14 @@ are still up-to-date. To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` target. +#### Installation + +To build and install GHC artifacts, run the `install` target. + +By default, the artifacts will be installed to `` on your system. For example, +`ghc` will be installed to `/usr/local/bin`. By modifying `defaultDestDir` in `UserSettings.hs`, +you can install things to non-system path `DESTDIR/` instead. + #### Testing * `build validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` @@ -122,12 +130,12 @@ zero (see [#197][test-issue]). Current limitations ------------------- The new build system still lacks many important features: -* There is currently no support for the `dynamic` build way: [#4][dynamic-issue]. * Validation is not implemented: [#187][validation-issue]. +* Dynamic linking on Windows is not supported [#343][dynamic-windows-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). * Not all modes of the old build system are supported, e.g. [#250][freeze-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. -* There is no support for installation or binary distribution: [#219][install-issue]. +* There is no support for binary distribution: [#219][install-issue]. Check out [milestones] to see when we hope to resolve the above limitations. @@ -162,8 +170,8 @@ helped me endure and enjoy the project. [windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [test-issue]: https://github.com/snowleopard/hadrian/issues/197 -[dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 +[dynamic-windows-issue]: https://github.com/snowleopard/hadrian/issues/343 [freeze-issue]: https://github.com/snowleopard/hadrian/issues/250 [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 From git at git.haskell.org Fri Oct 27 01:19:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update flavours doc (#338) (9dde04c) Message-ID: <20171027011940.967ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dde04c09058e7f07e7683fa3d334a096c911b2d/ghc >--------------------------------------------------------------- commit 9dde04c09058e7f07e7683fa3d334a096c911b2d Author: Zhen Zhang Date: Sat Jul 8 23:58:07 2017 +0800 Update flavours doc (#338) >--------------------------------------------------------------- 9dde04c09058e7f07e7683fa3d334a096c911b2d doc/flavours.md | 70 ++++++++++++++++++++++++++++++++++----------------------- 1 file changed, 42 insertions(+), 28 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index 9fe2239..3bf0c30 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -118,45 +118,59 @@ Libraries and GHC can be built in different _ways_, e.g. with or without profili information. The following table lists ways that are built in different flavours. - - - - - - - - - + + + + + + + + + + + + + + + - - - + + + - - - + + + - - + + + - - - + + - +
FlavourLibrary waysRTS waysProfiled GHC
stage0 - stage1+ - stage0 - stage1+ - stage0 - stage1+ -
FlavourLibrary waysRTS waysProfiled GHC
stage0stage1+stage0stage1+stage0stage1+
default
perf
prof
devel1
devel2
vanillavanilla
profiling
logging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
threadedProfiling
vanilla
profiling
dynamic
logging
debug
threaded
threadedDebug
threadedLogging +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
+ logging
debug
threaded
threadedDebug
+ threadedLogging
threadedProfiling +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
Only in
prof
flavour
Only in
prof
flavour
quick - vanilla
quick vanillalogging
debug
threaded
threadedDebug
threadedLogging
logging
debug
threaded
threadedDebug
threadedLogging
vanilla
dynamic
logging
debug
threaded
threadedDebug
threadedLogging +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
logging
debug
threaded
threadedDebug
threadedLogging +
debugDynamic
threadedDynamic
threadedDebugDynamic +
loggingDynamic
threadedLoggingDynamic +
No No
quickest +
quickest vanilla vanilla vanilla
threaded (when --haddock)
vanilla
threaded (when --haddock)
No No
From git at git.haskell.org Fri Oct 27 01:19:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix documentation rules (#324) (13023bc) Message-ID: <20171027011944.0F8353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13023bc3e13dcd003efbf00a83a7ab780c2727c3/ghc >--------------------------------------------------------------- commit 13023bc3e13dcd003efbf00a83a7ab780c2727c3 Author: Zhen Zhang Date: Sun Jul 9 18:21:31 2017 +0800 Fix documentation rules (#324) >--------------------------------------------------------------- 13023bc3e13dcd003efbf00a83a7ab780c2727c3 src/Rules/Documentation.hs | 17 ++++++++++------- src/Rules/Install.hs | 14 ++++++++++++++ src/Rules/Wrappers.hs | 12 ++++++++++-- 3 files changed, 34 insertions(+), 9 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index cf54e0a..5ee6818 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -7,11 +7,14 @@ import Flavour import GHC import Oracles.ModuleFiles import Oracles.PackageData +import Oracles.Path (getTopDirectory) import Settings import Settings.Path import Target import Util +import qualified System.Directory as IO + haddockHtmlLib :: FilePath haddockHtmlLib = "inplace/lib/html/haddock-util.js" @@ -31,13 +34,6 @@ buildPackageDocumentation context at Context {..} = , depPkg /= rts ] need $ srcs ++ haddocks ++ [haddockHtmlLib] - -- HsColour sources - -- TODO: what is the output of GhcCabalHsColour? - whenM (isSpecified HsColour) $ do - pkgConf <- pkgConfFile context - need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf - build $ Target context GhcCabalHsColour [cabalFile] [] - -- Build Haddock documentation -- TODO: pass the correct way from Rules via Context let haddockWay = if dynamicGhcPrograms flavour then dynamic else vanilla @@ -47,6 +43,13 @@ buildPackageDocumentation context at Context {..} = let dir = takeDirectory haddockHtmlLib liftIO $ removeFiles dir ["//*"] copyDirectory "utils/haddock/haddock-api/resources/html" dir + where + excluded = Or + [ Test "//haddock-prologue.txt" + , Test "//package-data.mk" + , Test "//setup-config" + , Test "//inplace-pkg-config" + , Test "//build" ] -- # Make the haddocking depend on the library .a file, to ensure -- # that we wait until the library is fully built before we haddock it diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 4c91316..553f8d1 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -193,6 +193,20 @@ installPackages = do let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" -- HACK? need [ ghcCabalInplace ] + let cabalFile = pkgCabalFile pkg + -- HsColour sources + -- QUESTION: what is the output of GhcCabalHsColour? + whenM (isSpecified HsColour) $ do + top <- interpretInContext context getTopDirectory + let installDistDir = top -/- buildPath context + -- HACK: copy stuff back to the place favored by ghc-cabal + quietly $ copyDirectoryContents (Not excluded) + installDistDir (installDistDir -/- "build") + + pkgConf <- pkgConfFile context + need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf + build $ Target context GhcCabalHsColour [cabalFile] [] + -- HACK (#318): copy stuff back to the place favored by ghc-cabal quietly $ copyDirectoryContents (Not excluded) installDistDir (installDistDir -/- "build") diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs index b6f1266..6adf3f7 100644 --- a/src/Rules/Wrappers.hs +++ b/src/Rules/Wrappers.hs @@ -109,12 +109,21 @@ hsc2hsWrapper WrappedBinary{..} = do , "HSC2HS_EXTRA=\"" ++ hsc2hsExtra ++ "\"" , contents ] +haddockWrapper :: WrappedBinary -> Expr String +haddockWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + return $ unlines + [ "#!/bin/bash" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) + ++ " -B" ++ binaryLibPath ++ " -l" ++ binaryLibPath ++ " ${1+\"$@\"}" ] + wrappersCommon :: [(Context, Wrapper)] wrappersCommon = [ (vanillaContext Stage0 ghc , ghcWrapper) , (vanillaContext Stage1 ghc , ghcWrapper) , (vanillaContext Stage1 hp2ps , hp2psWrapper) , (vanillaContext Stage1 hpc , hpcWrapper) - , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) ] + , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) + , (vanillaContext Stage2 haddock, haddockWrapper)] -- | List of wrappers for inplace artefacts inplaceWrappers :: [(Context, Wrapper)] @@ -127,4 +136,3 @@ installWrappers :: [(Context, Wrapper)] installWrappers = wrappersCommon ++ [ (vanillaContext Stage0 ghcPkg, installGhcPkgWrapper) , (vanillaContext Stage1 runGhc, installRunGhcWrapper) ] - From git at git.haskell.org Fri Oct 27 01:19:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use correct ar for host/target (#356) (b7550b2) Message-ID: <20171027011947.75E8E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b7550b2bdbd148e80e3d5b06419549bcb7ca92ee/ghc >--------------------------------------------------------------- commit b7550b2bdbd148e80e3d5b06419549bcb7ca92ee Author: Ben Gamari Date: Mon Jul 10 13:40:54 2017 -0400 Use correct ar for host/target (#356) Previously we would always use the ar of the target; this is incorrect. Fixes #350. >--------------------------------------------------------------- b7550b2bdbd148e80e3d5b06419549bcb7ca92ee cfg/system.config.in | 1 + src/Builder.hs | 2 +- src/Oracles/Path.hs | 3 ++- src/Rules/Gmp.hs | 4 ++-- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Util.hs | 2 +- 8 files changed, 12 insertions(+), 10 deletions(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 078e1ec..34ef7b9 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -16,6 +16,7 @@ make = @MakeCmd@ nm = @NmCmd@ objdump = @ObjdumpCmd@ ranlib = @REAL_RANLIB_CMD@ +system-ar = @AR_STAGE0@ system-cc = @CC_STAGE0@ system-ghc = @WithGhc@ system-ghc-pkg = @GhcPkgCmd@ diff --git a/src/Builder.hs b/src/Builder.hs index b2fbca3..7937319 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -28,7 +28,7 @@ data GhcPkgMode = Init | Update deriving (Eq, Generic, Show) -- @GhcPkg Stage0@ is the bootstrapping @GhcPkg at . -- @GhcPkg Stage1@ is the one built in Stage0. data Builder = Alex - | Ar + | Ar Stage | DeriveConstants | Cc CcMode Stage | Configure FilePath diff --git a/src/Oracles/Path.hs b/src/Oracles/Path.hs index a1c56f5..2ec2773 100644 --- a/src/Oracles/Path.hs +++ b/src/Oracles/Path.hs @@ -24,7 +24,8 @@ getTopDirectory = lift topDirectory systemBuilderPath :: Builder -> Action FilePath systemBuilderPath builder = case builder of Alex -> fromKey "alex" - Ar -> fromKey "ar" + Ar Stage0 -> fromKey "system-ar" + Ar _ -> fromKey "ar" Cc _ Stage0 -> fromKey "system-cc" Cc _ _ -> fromKey "cc" -- We can't ask configure for the path to configure! diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index a3e32d3..ee8eb82 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -25,7 +25,7 @@ gmpMakefile = gmpBuildPath -/- "Makefile" configureEnvironment :: Action [CmdOption] configureEnvironment = sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 - , builderEnvironment "AR" Ar + , builderEnvironment "AR" (Ar Stage1) , builderEnvironment "NM" Nm ] gmpRules :: Rules () @@ -43,7 +43,7 @@ gmpRules = do putBuild "| No GMP library/framework detected; in tree GMP will be built" need [gmpLibrary] createDirectory gmpObjects - build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] + build $ Target gmpContext (Ar Stage1) [gmpLibrary] [gmpObjects] copyFile (gmpBuildPath -/- "gmp.h") header copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 57f6263..bac9970 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -31,7 +31,7 @@ configureEnvironment = do sequence [ builderEnvironment "CC" $ Cc CompileC Stage1 , builderEnvironment "CXX" $ Cc CompileC Stage1 , builderEnvironment "LD" Ld - , builderEnvironment "AR" Ar + , builderEnvironment "AR" (Ar Stage1) , builderEnvironment "NM" Nm , builderEnvironment "RANLIB" Ranlib , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w" diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 455c57c..b746279 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -72,8 +72,8 @@ buildPackageLibrary context at Context {..} = do asuf <- libsuf way let isLib0 = ("//*-0" ++ asuf) ?== a - if isLib0 then build $ Target context Ar [] [a] -- TODO: Scan for dlls - else build $ Target context Ar objs [a] + if isLib0 then build $ Target context (Ar stage) [] [a] -- TODO: Scan for dlls + else build $ Target context (Ar stage) objs [a] synopsis <- interpretInContext context $ getPkgData Synopsis unless isLib0 . putSuccess $ renderLibrary diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 9ddfe15..18816e1 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -25,7 +25,7 @@ ghcCabalBuilderArgs = builder GhcCabal ? do , packageConstraints , withStaged $ Cc CompileC , notStage0 ? with Ld - , with Ar + , withStaged Ar , with Alex , with Happy , verbosity < Chatty ? append [ "-v0", "--configure-option=--quiet" @@ -91,7 +91,7 @@ cppArgs = arg $ "-I" ++ generatedPath withBuilderKey :: Builder -> String withBuilderKey b = case b of - Ar -> "--with-ar=" + Ar _ -> "--with-ar=" Ld -> "--with-ld=" Cc _ _ -> "--with-gcc=" Ghc _ _ -> "--with-ghc=" diff --git a/src/Util.hs b/src/Util.hs index da12e21..944e8e5 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -53,7 +53,7 @@ customBuild rs opts target at Target {..} = do withResources rs $ do putInfo target quietlyUnlessVerbose $ case builder of - Ar -> do + Ar _ -> do output <- interpret target getOutput if "//*.a" ?== output then arCmd path argList From git at git.haskell.org Fri Oct 27 01:19:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix warnings (e8abab2) Message-ID: <20171027011950.E6DD13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e8abab220113b10ef22e1080d7771216b2488b0b/ghc >--------------------------------------------------------------- commit e8abab220113b10ef22e1080d7771216b2488b0b Author: Andrey Mokhov Date: Tue Jul 11 18:07:53 2017 +0100 Fix warnings See #358 >--------------------------------------------------------------- e8abab220113b10ef22e1080d7771216b2488b0b src/Oracles/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 13 +------------ src/Settings/Builders/Ghc.hs | 1 - src/Settings/Flavours/Quickest.hs | 1 - src/Settings/Packages/GhcCabal.hs | 3 --- 5 files changed, 2 insertions(+), 18 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 447df25..3aaabfa 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -90,7 +90,7 @@ sortPkgsByDep pkgs = do return $ map fst $ topSort elems where annotateInDeg es e = - (foldr (\e' s -> if fst e' `elem` snd e then s + 1 else s) 0 es, e) + (foldr (\e' s -> if fst e' `elem` snd e then s + 1 else s) (0 :: Int) es, e) topSort [] = [] topSort es = let annotated = map (annotateInDeg es) es diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 5ee6818..a3a7b7c 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -7,14 +7,11 @@ import Flavour import GHC import Oracles.ModuleFiles import Oracles.PackageData -import Oracles.Path (getTopDirectory) import Settings import Settings.Path import Target import Util -import qualified System.Directory as IO - haddockHtmlLib :: FilePath haddockHtmlLib = "inplace/lib/html/haddock-util.js" @@ -23,8 +20,7 @@ haddockHtmlLib = "inplace/lib/html/haddock-util.js" -- files in the Shake database seems fragile and unnecessary. buildPackageDocumentation :: Context -> Rules () buildPackageDocumentation context at Context {..} = - let cabalFile = pkgCabalFile package - haddockFile = pkgHaddockFile context + let haddockFile = pkgHaddockFile context in when (stage == Stage1) $ do haddockFile %> \file -> do srcs <- hsSources context @@ -43,13 +39,6 @@ buildPackageDocumentation context at Context {..} = let dir = takeDirectory haddockHtmlLib liftIO $ removeFiles dir ["//*"] copyDirectory "utils/haddock/haddock-api/resources/html" dir - where - excluded = Or - [ Test "//haddock-prologue.txt" - , Test "//package-data.mk" - , Test "//setup-config" - , Test "//inplace-pkg-config" - , Test "//build" ] -- # Make the haddocking depend on the library .a file, to ensure -- # that we wait until the library is fully built before we haddock it diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index aa6303e..9864946 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -2,7 +2,6 @@ module Settings.Builders.Ghc (ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs) w import Flavour import GHC -import Settings.Path (ghcSplitPath) import Settings.Builders.Common ghcBuilderArgs :: Args diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index fa7cad5..d5dff73 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -2,7 +2,6 @@ module Settings.Flavours.Quickest (quickestFlavour) where import Flavour import Predicate -import Oracles.Config.Flag (platformSupportsSharedLibs) import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 57147e4..983292f 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -4,10 +4,8 @@ import Distribution.PackageDescription.Parse import Base import GHC -import Oracles.Config.Setting import Oracles.Dependencies (pkgDependencies) import Predicate -import Package (pkgCabalFile) import Distribution.Verbosity (silent) import Distribution.Text (display) import Distribution.Package (pkgVersion) @@ -16,7 +14,6 @@ import qualified Distribution.PackageDescription as DP ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do - win <- lift windowsHost cabalDeps <- lift $ pkgDependencies cabal lift $ need [pkgCabalFile cabal] pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile cabal From git at git.haskell.org Fri Oct 27 01:19:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't optimize cabal stage0 build (#357) (e1aadf3) Message-ID: <20171027011954.6CA843A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1aadf31f565128c609765f550e5213adbfab35d/ghc >--------------------------------------------------------------- commit e1aadf31f565128c609765f550e5213adbfab35d Author: Ben Gamari Date: Tue Jul 11 17:24:01 2017 -0400 Don't optimize cabal stage0 build (#357) >--------------------------------------------------------------- e1aadf31f565128c609765f550e5213adbfab35d hadrian.cabal | 1 + src/Settings/Default.hs | 5 ++++- src/Settings/Packages/Cabal.hs | 11 +++++++++++ 3 files changed, 16 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index fbda4b0..1178cb4 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -91,6 +91,7 @@ executable hadrian , Settings.Flavours.Quick , Settings.Flavours.Quickest , Settings.Packages.Base + , Settings.Packages.Cabal , Settings.Packages.Compiler , Settings.Packages.Ghc , Settings.Packages.GhcCabal diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 3ad1fab..19c6937 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -30,6 +30,7 @@ import Settings.Builders.Ld import Settings.Builders.Make import Settings.Builders.Tar import Settings.Packages.Base +import Settings.Packages.Cabal import Settings.Packages.Compiler import Settings.Packages.Ghc import Settings.Packages.GhcCabal @@ -268,6 +269,7 @@ disableWarningArgsLibs = do defaultPackageArgs :: Args defaultPackageArgs = mconcat [ basePackageArgs + , cabalPackageArgs , compilerPackageArgs , ghcPackageArgs , ghcCabalPackageArgs @@ -279,4 +281,5 @@ defaultPackageArgs = mconcat , runGhcPackageArgs , disableWarningArgsStage0 , disableWarningArgsStage1 - , disableWarningArgsLibs ] + , disableWarningArgsLibs + ] diff --git a/src/Settings/Packages/Cabal.hs b/src/Settings/Packages/Cabal.hs new file mode 100644 index 0000000..eddee75 --- /dev/null +++ b/src/Settings/Packages/Cabal.hs @@ -0,0 +1,11 @@ +module Settings.Packages.Cabal where + +import GHC +import Predicate + +cabalPackageArgs :: Args +cabalPackageArgs = package cabal ? do + -- Cabal is a rather large library and quite slow to compile. Moreover, we + -- build it for stage0 only so we can link ghc-pkg against it, so there is + -- little reason to spend the effort to optimize it. + stage Stage0 ? builder Ghc ? append [ "-O0" ] From git at git.haskell.org Fri Oct 27 01:19:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:19:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix validate's dependency on generated files (#362) (31f9640) Message-ID: <20171027011957.DB9D23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31f9640125cf74dd96b1c210143cb3772656bd35/ghc >--------------------------------------------------------------- commit 31f9640125cf74dd96b1c210143cb3772656bd35 Author: Zhen Zhang Date: Sat Jul 15 21:02:05 2017 +0800 Fix validate's dependency on generated files (#362) >--------------------------------------------------------------- 31f9640125cf74dd96b1c210143cb3772656bd35 src/Rules/Test.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 08eca05..fc059ab 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -5,6 +5,7 @@ import Builder import Expression import Flavour import GHC +import qualified Rules.Generate import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Path @@ -16,6 +17,7 @@ import Util testRules :: Rules () testRules = do "validate" ~> do + need $ Rules.Generate.inplaceLibCopyTargets needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc From git at git.haskell.org Fri Oct 27 01:20:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (9a34338) Message-ID: <20171027012001.5960E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a34338c6dd82ea5df18d0443e63e0a66b1b123e/ghc >--------------------------------------------------------------- commit 9a34338c6dd82ea5df18d0443e63e0a66b1b123e Author: Andrey Mokhov Date: Sun Jul 16 23:55:02 2017 +0100 Minor revision >--------------------------------------------------------------- 9a34338c6dd82ea5df18d0443e63e0a66b1b123e src/Predicate.hs | 6 ++- src/Settings/Builders/Cc.hs | 14 +++--- src/Settings/Builders/Ghc.hs | 3 +- src/Settings/Default.hs | 111 +++++++++++++++++++++---------------------- 4 files changed, 66 insertions(+), 68 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 9a34338c6dd82ea5df18d0443e63e0a66b1b123e From git at git.haskell.org Fri Oct 27 01:20:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix paths to install-related commands on Windows. Minor revision. (31890f3) Message-ID: <20171027012004.DCF313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/31890f39222ffffff7a17343925a70c5f13df83b/ghc >--------------------------------------------------------------- commit 31890f39222ffffff7a17343925a70c5f13df83b Author: Andrey Mokhov Date: Mon Jul 17 01:28:24 2017 +0100 Fix paths to install-related commands on Windows. Minor revision. See #345 >--------------------------------------------------------------- 31890f39222ffffff7a17343925a70c5f13df83b src/Oracles/Path.hs | 3 ++- src/Rules/Install.hs | 18 ++++++++-------- src/Util.hs | 60 ++++++++++++++++++++++++++++------------------------ 3 files changed, 43 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 31890f39222ffffff7a17343925a70c5f13df83b From git at git.haskell.org Fri Oct 27 01:20:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use mv command to move files (374d7b1) Message-ID: <20171027012008.527573A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/374d7b124f474ff8bf6b327fb63cb41860f2aef3/ghc >--------------------------------------------------------------- commit 374d7b124f474ff8bf6b327fb63cb41860f2aef3 Author: Andrey Mokhov Date: Mon Jul 17 01:35:18 2017 +0100 Use mv command to move files See #345 >--------------------------------------------------------------- 374d7b124f474ff8bf6b327fb63cb41860f2aef3 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 5f60fc1..e873ddc 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -115,7 +115,7 @@ copyFileUntracked source target = do moveFile :: FilePath -> FilePath -> Action () moveFile source target = do putProgressInfo $ renderAction "Move file" source target - liftIO $ IO.renameFile source target + quietly $ cmd ["mv", source, target] -- | Remove a file that doesn't necessarily exist. removeFile :: FilePath -> Action () From git at git.haskell.org Fri Oct 27 01:20:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CircleCI script (#364) (076e53f) Message-ID: <20171027012011.C7CD03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/076e53fe9637ed6dbc3d4a926b0d87d597666666/ghc >--------------------------------------------------------------- commit 076e53fe9637ed6dbc3d4a926b0d87d597666666 Author: Zhen Zhang Date: Tue Jul 18 01:05:45 2017 +0800 Add CircleCI script (#364) >--------------------------------------------------------------- 076e53fe9637ed6dbc3d4a926b0d87d597666666 circle.yml | 41 +++++++++++++++++++++++++++++++++++++++++ 1 file changed, 41 insertions(+) diff --git a/circle.yml b/circle.yml new file mode 100644 index 0000000..457add7 --- /dev/null +++ b/circle.yml @@ -0,0 +1,41 @@ +machine: + xcode: + version: 8.0 + environment: + MODE: --flavour=quickest --integer-simple + +dependencies: + override: + - brew update + - brew install ghc cabal-install + - cabal update + - cabal install alex happy ansi-terminal mtl shake quickcheck + cache_directories: + - $HOME/.cabal + - $HOME/.ghc + +compile: + override: + # Fetch GHC sources into ./ghc + - git --version + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git clone --depth 1 --recursive git://github.com/ghc/ghc + + - mkdir ghc/hadrian + # move hadrian's .git into ./ghc/hadrian and perform a hard reset in order to regenerate Hadrian files + - mv .git ghc/hadrian + # NOTE: we must write them in the same line because each line + # in CircleCI is a separate process, thus you can't "cd" for the other lines + - cd ghc/hadrian; git reset --hard HEAD + + # XXX: export PATH doesn't work well either, so we use inline env + # Self test + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh selftest + + # Build GHC + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + +test: + override: + # Test GHC binary + - ghc/inplace/bin/ghc-stage2 -e 1+2 From git at git.haskell.org Fri Oct 27 01:20:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CircleCI badge (1400b14) Message-ID: <20171027012015.42D883A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1400b148157e781c55165bfaf4d706477f3d36be/ghc >--------------------------------------------------------------- commit 1400b148157e781c55165bfaf4d706477f3d36be Author: Andrey Mokhov Date: Mon Jul 17 19:12:04 2017 +0100 Add CircleCI badge [skip ci] >--------------------------------------------------------------- 1400b148157e781c55165bfaf4d706477f3d36be README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index d65b98c..3e5318a 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ Hadrian ======= -[![Linux & OS X status](https://img.shields.io/travis/snowleopard/hadrian/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/hadrian) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) +[![Linux & OS X status](https://img.shields.io/travis/snowleopard/hadrian/master.svg?label=Linux%20%26%20OS%20X)](https://travis-ci.org/snowleopard/hadrian) [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) [![OS X status](https://img.shields.io/circleci/project/github/snowleopard/hadrian.svg?label=OS%20X)](https://circleci.com/gh/snowleopard/hadrian) Hadrian is a new build system for the [Glasgow Haskell Compiler][ghc]. It is based on [Shake][shake] and we hope that it will eventually replace the current From git at git.haskell.org Fri Oct 27 01:20:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix on Windows install (0ca5f3a) Message-ID: <20171027012022.502983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ca5f3a8245b92f844e4e68ce511e92ff186bbdc/ghc >--------------------------------------------------------------- commit 0ca5f3a8245b92f844e4e68ce511e92ff186bbdc Author: Andrey Mokhov Date: Tue Jul 18 00:12:29 2017 +0100 Fix on Windows install See #345 >--------------------------------------------------------------- 0ca5f3a8245b92f844e4e68ce511e92ff186bbdc src/Oracles/DirectoryContents.hs | 7 +- src/Rules/Install.hs | 204 +++++++++++++++++++-------------------- src/Util.hs | 4 +- 3 files changed, 109 insertions(+), 106 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 0ca5f3a8245b92f844e4e68ce511e92ff186bbdc From git at git.haskell.org Fri Oct 27 01:20:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Untrack copied artifacts (#365) (6395cf5) Message-ID: <20171027012018.A731B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6395cf549921934602563cfae645e6707b171fac/ghc >--------------------------------------------------------------- commit 6395cf549921934602563cfae645e6707b171fac Author: Zhen Zhang Date: Tue Jul 18 05:26:00 2017 +0800 Untrack copied artifacts (#365) >--------------------------------------------------------------- 6395cf549921934602563cfae645e6707b171fac src/Rules/Install.hs | 13 ++++--------- 1 file changed, 4 insertions(+), 9 deletions(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 57cf008..058e160 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -194,22 +194,17 @@ installPackages = do need [ ghcCabalInplace ] let cabalFile = pkgCabalFile pkg - -- HsColour sources - -- QUESTION: what is the output of GhcCabalHsColour? - whenM (isSpecified HsColour) $ do - top <- interpretInContext context getTopDirectory - let installDistDir = top -/- buildPath context - -- HACK: copy stuff back to the place favored by ghc-cabal - quietly $ copyDirectoryContents (Not excluded) - installDistDir (installDistDir -/- "build") pkgConf <- pkgConfFile context need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf - build $ Target context GhcCabalHsColour [cabalFile] [] -- HACK (#318): copy stuff back to the place favored by ghc-cabal quietly $ copyDirectoryContents (Not excluded) installDistDir (installDistDir -/- "build") + + whenM (isSpecified HsColour) $ + build $ Target context GhcCabalHsColour [cabalFile] [] + pref <- setting InstallPrefix unit $ cmd ghcCabalInplace [ "copy" From git at git.haskell.org Fri Oct 27 01:20:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghc-iserv wrapper (#367) (05b3ebe) Message-ID: <20171027012025.D44F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/05b3ebe6911890145c12bd8022b2cc11002de98c/ghc >--------------------------------------------------------------- commit 05b3ebe6911890145c12bd8022b2cc11002de98c Author: Zhen Zhang Date: Tue Jul 18 23:12:22 2017 +0800 Add ghc-iserv wrapper (#367) >--------------------------------------------------------------- 05b3ebe6911890145c12bd8022b2cc11002de98c src/GHC.hs | 9 +++++---- src/Rules/Program.hs | 26 +++++++++++++++++++++++++- src/Rules/Wrappers.hs | 24 ++++++++++++++++++++++-- src/Settings.hs | 2 +- src/Settings/Path.hs | 13 +++++++------ 5 files changed, 60 insertions(+), 14 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0f5e2fb..ce88cb0 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -116,10 +116,11 @@ builderProvenance = \case -- 'Library', the function simply returns its name. programName :: Context -> String programName Context {..} - | package == ghc = "ghc-stage" ++ show (fromEnum stage + 1) - | package == hpcBin = "hpc" - | package == runGhc = "runhaskell" - | otherwise = pkgNameString package + | package == ghc = "ghc-stage" ++ show (fromEnum stage + 1) + | package == hpcBin = "hpc" + | package == runGhc = "runhaskell" + | package == iservBin = "ghc-iserv" + | otherwise = pkgNameString package -- | Some contexts are special: their packages do have @.cabal@ metadata or -- we cannot run @ghc-cabal@ on them, e.g. because the latter hasn't been built diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 12e661b..8c9a7ab 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -34,11 +34,35 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do inplaceBinPath -/- programName context <.> exe %> \bin -> do binStage <- installStage buildBinaryAndWrapper rs (context { stage = binStage }) bin - -- We build only unwrapped binaries in inplace/lib/bin + inplaceLibBinPath -/- programName context <.> exe %> \bin -> do binStage <- installStage + if package /= iservBin then + -- We *normally* build only unwrapped binaries in inplace/lib/bin, + buildBinary rs (context { stage = binStage }) bin + else + -- build both binary and wrapper in inplace/lib/bin + -- for ghc-iserv on *nix platform now + buildBinaryAndWrapperLib rs (context { stage = binStage }) bin + + inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> do + binStage <- installStage buildBinary rs (context { stage = binStage }) bin +buildBinaryAndWrapperLib :: [(Resource, Int)] -> Context -> FilePath -> Action () +buildBinaryAndWrapperLib rs context bin = do + windows <- windowsHost + if windows + then buildBinary rs context bin -- We don't build wrappers on Windows + else case lookup context inplaceWrappers of + Nothing -> buildBinary rs context bin -- No wrapper found + Just wrapper -> do + top <- topDirectory + let libdir = top -/- inplaceLibPath + let wrappedBin = inplaceLibBinPath -/- programName context <.> "bin" + need [wrappedBin] + buildWrapper context wrapper bin (WrappedBinary libdir (takeFileName wrappedBin)) + buildBinaryAndWrapper :: [(Resource, Int)] -> Context -> FilePath -> Action () buildBinaryAndWrapper rs context bin = do windows <- windowsHost diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs index 6adf3f7..7d90067 100644 --- a/src/Rules/Wrappers.hs +++ b/src/Rules/Wrappers.hs @@ -5,8 +5,9 @@ module Rules.Wrappers ( import Base import Expression import GHC +import Settings (getPackages, latestBuildStage) import Settings.Install (installPackageDbDirectory) -import Settings.Path (inplacePackageDbDirectory) +import Settings.Path (buildPath, inplacePackageDbDirectory) import Oracles.Path (getTopDirectory, bashPath) import Oracles.Config.Setting (SettingList(..), settingList) @@ -117,13 +118,32 @@ haddockWrapper WrappedBinary{..} = do , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " -B" ++ binaryLibPath ++ " -l" ++ binaryLibPath ++ " ${1+\"$@\"}" ] +iservBinWrapper :: WrappedBinary -> Expr String +iservBinWrapper WrappedBinary{..} = do + lift $ need [sourcePath -/- "Rules/Wrappers.hs"] + activePackages <- filter isLibrary <$> getPackages + -- TODO: Figure our the reason of this hardcoded exclusion + let pkgs = activePackages \\ [ cabal, process, haskeline + , terminfo, ghcCompact, hpc, compiler ] + contexts <- catMaybes <$> mapM (\p -> do + m <- lift $ latestBuildStage p + return $ fmap (\s -> vanillaContext s p) m + ) pkgs + let buildPaths = map buildPath contexts + return $ unlines + [ "#!/bin/bash" + , "export DYLD_LIBRARY_PATH=\"" ++ intercalate ":" buildPaths ++ + "${DYLD_LIBRARY_PATH:+:$DYLD_LIBRARY_PATH}\"" + , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ] + wrappersCommon :: [(Context, Wrapper)] wrappersCommon = [ (vanillaContext Stage0 ghc , ghcWrapper) , (vanillaContext Stage1 ghc , ghcWrapper) , (vanillaContext Stage1 hp2ps , hp2psWrapper) , (vanillaContext Stage1 hpc , hpcWrapper) , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) - , (vanillaContext Stage2 haddock, haddockWrapper)] + , (vanillaContext Stage2 haddock, haddockWrapper) + , (vanillaContext Stage1 iservBin, iservBinWrapper) ] -- | List of wrappers for inplace artefacts inplaceWrappers :: [(Context, Wrapper)] diff --git a/src/Settings.hs b/src/Settings.hs index 8152a6e..2f75095 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -112,7 +112,7 @@ programPath context at Context {..} = do maybeLatest <- latestBuildStage package return $ do install <- (\l -> l == stage || package == ghc) <$> maybeLatest - let path = if install then installPath package else buildPath context + let path = if install then inplaceInstallPath package else buildPath context return $ path -/- programName context <.> exe pkgConfInstallPath :: FilePath diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 8814620..1b0dc13 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -5,7 +5,7 @@ module Settings.Path ( rtsContext, rtsBuildPath, rtsConfIn, shakeFilesPath,inplacePackageDbDirectory, pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, - installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, + inplaceInstallPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, pkgSetupConfigFile ) where @@ -190,11 +190,12 @@ objectPath context at Context {..} src -- | Given a 'Package', return the path where the corresponding program is -- installed. Most programs are installed in 'programInplacePath'. -installPath :: Package -> FilePath -installPath pkg - | pkg == touchy = inplaceLibBinPath - | pkg == unlit = inplaceLibBinPath - | otherwise = inplaceBinPath +inplaceInstallPath :: Package -> FilePath +inplaceInstallPath pkg + | pkg == touchy = inplaceLibBinPath + | pkg == unlit = inplaceLibBinPath + | pkg == iservBin = inplaceLibBinPath + | otherwise = inplaceBinPath -- | @ghc-split@ is a Perl script used by GHC with @-split-objs@ flag. It is -- generated in "Rules.Generators.GhcSplit". From git at git.haskell.org Fri Oct 27 01:20:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix typo in comment (#369) (408ef4e) Message-ID: <20171027012029.57B003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/408ef4e802ec0b89b5962bb839f11f47976897e2/ghc >--------------------------------------------------------------- commit 408ef4e802ec0b89b5962bb839f11f47976897e2 Author: Doug Wilson Date: Wed Jul 19 06:57:15 2017 +1200 Fix typo in comment (#369) [skip ci] >--------------------------------------------------------------- 408ef4e802ec0b89b5962bb839f11f47976897e2 src/GHC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC.hs b/src/GHC.hs index ce88cb0..231eab6 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -122,7 +122,7 @@ programName Context {..} | package == iservBin = "ghc-iserv" | otherwise = pkgNameString package --- | Some contexts are special: their packages do have @.cabal@ metadata or +-- | Some contexts are special: their packages do not have @.cabal@ metadata or -- we cannot run @ghc-cabal@ on them, e.g. because the latter hasn't been built -- yet (this is the case with the 'ghcCabal' package in 'Stage0'). nonCabalContext :: Context -> Bool From git at git.haskell.org Fri Oct 27 01:20:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link to the projects webpage (4bdc4a4) Message-ID: <20171027012032.CD9AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4bdc4a4747801dba02d755ce08d356d81ede18a3/ghc >--------------------------------------------------------------- commit 4bdc4a4747801dba02d755ce08d356d81ede18a3 Author: Andrey Mokhov Date: Wed Jul 19 00:32:51 2017 +0100 Link to the projects webpage [skip ci] >--------------------------------------------------------------- 4bdc4a4747801dba02d755ce08d356d81ede18a3 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 3e5318a..8404496 100644 --- a/README.md +++ b/README.md @@ -148,6 +148,8 @@ at present and we expect a lot of further refactoring. If you would like to work on a particular issue, please let everyone know by adding a comment about this. The issues that are currently on the critical path and therefore require particular attention are listed in [#239](https://github.com/snowleopard/hadrian/issues/239). +Also have a look at [projects](https://github.com/snowleopard/hadrian/projects) +where open issues and pull requests are grouped into categories. Acknowledgements ---------------- From git at git.haskell.org Fri Oct 27 01:20:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (061dcf1) Message-ID: <20171027012036.4B3D23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/061dcf1f9b7a9dd7e907e6393ad20751054fba99/ghc >--------------------------------------------------------------- commit 061dcf1f9b7a9dd7e907e6393ad20751054fba99 Author: Andrey Mokhov Date: Wed Jul 19 01:27:44 2017 +0100 Minor revision See #238 >--------------------------------------------------------------- 061dcf1f9b7a9dd7e907e6393ad20751054fba99 src/Rules/Library.hs | 45 +++++++++++++++++---------------------------- 1 file changed, 17 insertions(+), 28 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index b746279..d832264 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -1,6 +1,5 @@ module Rules.Library ( - buildPackageLibrary, buildPackageGhciLibrary, - buildDynamicLib + buildPackageLibrary, buildPackageGhciLibrary, buildDynamicLib ) where import Data.Char @@ -13,15 +12,15 @@ import Flavour import GHC import Oracles.ModuleFiles import Oracles.PackageData -import Oracles.Dependencies (contextDependencies) +import Oracles.Dependencies import Settings import Settings.Path import Target import UserSettings import Util -getLibraryObjs :: Context -> Action [FilePath] -getLibraryObjs context at Context{..} = do +libraryObjects :: Context -> Action [FilePath] +libraryObjects context at Context{..} = do hsObjs <- hsObjects context noHsObjs <- nonHsObjects context @@ -31,34 +30,26 @@ getLibraryObjs context at Context{..} = do split <- interpretInContext context $ splitObjects flavour let getSplitObjs = concatForM hsObjs $ \obj -> do - let dir = dropExtension obj ++ "_" ++ osuf way ++ "_split" - contents <- liftIO $ IO.getDirectoryContents dir - return . map (dir -/-) $ filter (not . all (== '.')) contents + let dir = dropExtension obj ++ "_" ++ osuf way ++ "_split" + contents <- liftIO $ IO.getDirectoryContents dir + return . map (dir -/-) $ filter (not . all (== '.')) contents (noHsObjs ++) <$> if split then getSplitObjs else return hsObjs buildDynamicLib :: Context -> Rules () buildDynamicLib context at Context{..} = do - -- macOS - matchGhcVersionedFilePath libPrefix "dylib" ?> buildDynamicLibUNIX + let path = buildPath context + libPrefix = path -/- "libHS" ++ pkgNameString package + -- OS X + matchGhcVersionedFilePath libPrefix "dylib" ?> buildDynamicLibUnix -- Linux - matchGhcVersionedFilePath libPrefix "so" ?> buildDynamicLibUNIX + matchGhcVersionedFilePath libPrefix "so" ?> buildDynamicLibUnix -- TODO: Windows where - path = buildPath context - libPrefix = path -/- "libHS" ++ pkgNameString package - - buildDynamicLibUNIX so = do + buildDynamicLibUnix so = do deps <- contextDependencies context - - forM_ deps $ \dep -> do - lib <- pkgLibraryFile dep - need [lib] - - removeFile so - - objs <- getLibraryObjs context - + need =<< mapM pkgLibraryFile deps + objs <- libraryObjects context build $ Target context (Ghc LinkHs stage) objs [so] buildPackageLibrary :: Context -> Rules () @@ -66,12 +57,10 @@ buildPackageLibrary context at Context {..} = do let path = buildPath context libPrefix = path -/- "libHS" ++ pkgNameString package matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do - removeFile a - - objs <- getLibraryObjs context - + objs <- libraryObjects context asuf <- libsuf way let isLib0 = ("//*-0" ++ asuf) ?== a + removeFile a if isLib0 then build $ Target context (Ar stage) [] [a] -- TODO: Scan for dlls else build $ Target context (Ar stage) objs [a] From git at git.haskell.org Fri Oct 27 01:20:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make OS X build faster and Add GHC 8.0.2 build on Travis CI (#370) (b7fff3b) Message-ID: <20171027012039.B5F433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b7fff3b6749a01a2ad486bff68e6e0fdeab338e4/ghc >--------------------------------------------------------------- commit b7fff3b6749a01a2ad486bff68e6e0fdeab338e4 Author: Zhen Zhang Date: Wed Jul 19 22:44:42 2017 +0800 Make OS X build faster and Add GHC 8.0.2 build on Travis CI (#370) >--------------------------------------------------------------- b7fff3b6749a01a2ad486bff68e6e0fdeab338e4 .travis.yml | 58 +++++++++++++++++++++++++++++++++++++++++++++------------- 1 file changed, 45 insertions(+), 13 deletions(-) diff --git a/.travis.yml b/.travis.yml index dd6af26..d85291a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,9 +1,36 @@ sudo: true - +language: haskell matrix: include: - os: linux env: MODE="--flavour=quickest" + compiler: "GHC 8.0.2" + addons: + apt: + packages: + - ghc-8.0.2 + - cabal-install-2.0 + - zlib1g-dev + sources: hvr-ghc + + before_install: + - PATH="/opt/ghc/8.0.2/bin:$PATH" + - PATH="/opt/cabal/2.0/bin:$PATH" + + script: + # Run internal Hadrian tests + - ./build.sh selftest + + # Build GHC + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + + # Test GHC binary + - cd .. + - inplace/bin/ghc-stage2 -e 1+2 + + - os: linux + env: MODE="--flavour=quickest" + compiler: "GHC 7.10.3" addons: apt: packages: @@ -11,17 +38,33 @@ matrix: - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc + before_install: - PATH="/opt/ghc/7.10.3/bin:$PATH" - PATH="/opt/cabal/1.22/bin:$PATH" + script: + # Run internal Hadrian tests + - ./build.sh selftest + + # Build GHC + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + + # Test GHC binary + - cd .. + - inplace/bin/ghc-stage2 -e 1+2 + - os: osx osx_image: xcode8 env: MODE="--flavour=quickest --integer-simple" before_install: - brew update - brew install ghc cabal-install - - + + script: + # Due to timeout limit of OS X build on Travis CI, + # we will ignore selftest and build only stage1 + - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 install: # Add Cabal to PATH @@ -50,17 +93,6 @@ install: - cd ghc/hadrian - git reset --hard HEAD -script: - # Run internal Hadrian tests - - ./build.sh selftest - - # Build GHC - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- - - # Test GHC binary - - cd .. - - inplace/bin/ghc-stage2 -e 1+2 - cache: directories: - $HOME/.cabal From git at git.haskell.org Fri Oct 27 01:20:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (599381f) Message-ID: <20171027012043.29C633A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/599381f0fda1ea8fbae64b748b7b09727189f53b/ghc >--------------------------------------------------------------- commit 599381f0fda1ea8fbae64b748b7b09727189f53b Author: Andrey Mokhov Date: Wed Jul 19 16:03:35 2017 +0100 Minor revision >--------------------------------------------------------------- 599381f0fda1ea8fbae64b748b7b09727189f53b src/Oracles/Config/Setting.hs | 20 ++++++++++---------- src/Rules/Install.hs | 9 +++++---- src/Settings/Path.hs | 12 ++++++------ 3 files changed, 21 insertions(+), 20 deletions(-) diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs index c4ed10e..1bf9186 100644 --- a/src/Oracles/Config/Setting.hs +++ b/src/Oracles/Config/Setting.hs @@ -53,19 +53,18 @@ data Setting = BuildArch | IconvIncludeDir | IconvLibDir | CursesLibDir - -- Paths to where GHC is installed - -- ref: mk/install.mk + -- Paths to where GHC is installed (ref: mk/install.mk) | InstallPrefix | InstallBinDir | InstallLibDir | InstallDataRootDir - -- "install" utility + -- Command lines for invoking the @install@ utility | Install | InstallData | InstallProgram | InstallScript | InstallDir - -- symbolic link + -- Command line for creating a symbolic link | LnS data SettingList = ConfCcArgs Stage @@ -202,9 +201,10 @@ cmdLineLengthLimit = do -- On all other systems, we try this: _ -> 4194304 -- Cabal library needs a bit more than 2MB! --- | On Windows we normally want to make a relocatable bindist, --- to we ignore flags like libdir --- ref: mk/config.mk.in:232 +-- ref: https://ghc.haskell.org/trac/ghc/wiki/Building/Installing#HowGHCfindsitsfiles +-- | On Windows we normally build a relocatable installation, which assumes that +-- the library directory @libdir@ is in a fixed location relative to the GHC +-- binary, namely @../lib at . relocatableBuild :: Action Bool relocatableBuild = windowsHost @@ -213,10 +213,10 @@ installDocDir = do version <- setting ProjectVersion (-/- ("doc/ghc-" ++ version)) <$> setting InstallDataRootDir --- | Unix: override libdir and datadir to put ghc-specific stuff in --- a subdirectory with the version number included. -- ref: mk/install.mk:101 -- TODO: CroosCompilePrefix +-- | Unix: override @libdir@ and @datadir@ to put GHC-specific files in a +-- subdirectory with the version number included. installGhcLibDir :: Action String installGhcLibDir = do r <- relocatableBuild @@ -224,4 +224,4 @@ installGhcLibDir = do if r then return libdir else do v <- setting ProjectVersion - return (libdir -/- ("ghc-" ++ v)) + return $ libdir -/- ("ghc-" ++ v) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 525746b..77e340e 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -128,6 +128,7 @@ withLatestBuildStage pkg m = do Nothing -> return () -- ref: rules/manual-package-conf.mk +-- TODO: Should we use a temporary file instead of pkgConfInstallPath? -- | Install @package.conf.install@ for each package. Note that it will be -- recreated each time. installPackageConf :: Action () @@ -161,7 +162,7 @@ installPackages = do -- Install RTS let rtsDir = destDir ++ ghcLibDir -/- "rts" installDirectory rtsDir - ways <- interpretInContext (vanillaContext Stage1 rts) getRtsWays + ways <- interpretInContext (vanillaContext Stage1 rts) getRtsWays rtsLibs <- mapM pkgLibraryFile $ map (Context Stage1 rts) ways ffiLibs <- sequence $ map rtsLibffiLibrary ways @@ -183,14 +184,14 @@ installPackages = do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg - top <- interpretInContext context getTopDirectory + top <- topDirectory let installDistDir = top -/- buildPath context buildPackage stage pkg docDir <- installDocDir ghclibDir <- installGhcLibDir -- Copy over packages - strip <- stripCmdPath context + strip <- stripCmdPath ways <- interpretInContext context getLibraryWays let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" <.> exe -- HACK? need [ghcCabalInplace] @@ -230,7 +231,7 @@ installPackages = do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg - top <- interpretInContext context getTopDirectory + top <- topDirectory let installDistDir = top -/- buildPath context -- TODO: better reference to the built inplace binary path let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 1b0dc13..0be1838 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -14,8 +14,8 @@ import Context import Expression import GHC import Oracles.PackageData -import Oracles.Config.Setting (setting, Setting(..)) -import Oracles.Path (getTopDirectory) +import Oracles.Config.Setting +import Oracles.Path import UserSettings -- | Path to the directory containing the Shake database and other auxiliary @@ -202,12 +202,12 @@ inplaceInstallPath pkg ghcSplitPath :: FilePath ghcSplitPath = inplaceLibBinPath -/- "ghc-split" --- | Command line tool for stripping -- ref: mk/config.mk -stripCmdPath :: Context -> Action FilePath -stripCmdPath ctx = do +-- | Command line tool for stripping. +stripCmdPath :: Action FilePath +stripCmdPath = do targetPlatform <- setting TargetPlatform - top <- interpretInContext ctx getTopDirectory + top <- topDirectory case targetPlatform of "x86_64-unknown-mingw32" -> return (top -/- "inplace/mingw/bin/strip.exe") From git at git.haskell.org Fri Oct 27 01:20:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add an acknowledgement to Zhen Zhang (44b279b) Message-ID: <20171027012046.97B163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/44b279be9b1cc97bcc6cd73d3d0f73de6a7a3149/ghc >--------------------------------------------------------------- commit 44b279be9b1cc97bcc6cd73d3d0f73de6a7a3149 Author: Andrey Mokhov Date: Wed Jul 19 16:17:31 2017 +0100 Add an acknowledgement to Zhen Zhang Fix #371 [skip ci] >--------------------------------------------------------------- 44b279be9b1cc97bcc6cd73d3d0f73de6a7a3149 README.md | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index 8404496..5e49393 100644 --- a/README.md +++ b/README.md @@ -157,9 +157,12 @@ Acknowledgements I started this project as part of my 6-month research visit to Microsoft Research Cambridge, which was funded by Newcastle University, EPSRC, and Microsoft Research. I would like to thank Simon Peyton Jones, Neil Mitchell -and Simon Marlow for kick-starting the project and for their guidance. Last -but not least, big thanks to the project [contributors][contributors], who -helped me endure and enjoy the project. +and Simon Marlow for kick-starting the project and for their guidance. +Zhen Zhang has done fantastic work on Hadrian as part of his Summer of +Haskell 2017 [project](https://summer.haskell.org/ideas.html#hadrian-ghc), +solving a few heavy and long-overdue issues. Last but not least, big thanks +to all other project [contributors][contributors], who helped me endure and +enjoy the project. [ghc]: https://en.wikipedia.org/wiki/Glasgow_Haskell_Compiler [shake]: https://github.com/ndmitchell/shake/blob/master/README.md From git at git.haskell.org Fri Oct 27 01:20:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop language in Travis CI config (#372) (2741b3c) Message-ID: <20171027012050.1EA493A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2741b3c419ece51e914bc22e38e18c25476b296b/ghc >--------------------------------------------------------------- commit 2741b3c419ece51e914bc22e38e18c25476b296b Author: Zhen Zhang Date: Thu Jul 20 02:25:36 2017 +0800 Drop language in Travis CI config (#372) >--------------------------------------------------------------- 2741b3c419ece51e914bc22e38e18c25476b296b .travis.yml | 1 - 1 file changed, 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index d85291a..ba67ae3 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,5 +1,4 @@ sudo: true -language: haskell matrix: include: - os: linux From git at git.haskell.org Fri Oct 27 01:20:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comments only (58e2120) Message-ID: <20171027012053.A11EF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/58e21200a04bc17f5cb7c8fb8dbd36cecc03d36a/ghc >--------------------------------------------------------------- commit 58e21200a04bc17f5cb7c8fb8dbd36cecc03d36a Author: Andrey Mokhov Date: Wed Jul 19 20:17:07 2017 +0100 Comments only See #345 >--------------------------------------------------------------- 58e21200a04bc17f5cb7c8fb8dbd36cecc03d36a src/UserSettings.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/src/UserSettings.hs b/src/UserSettings.hs index 4398700..a3a65ab 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -43,10 +43,11 @@ putBuild = putColoured Dull Magenta putSuccess :: String -> Action () putSuccess = putColoured Dull Green --- | Path to the GHC install destination --- It is by default empty, representing the root of file system, --- or it might be a directory. --- It is usually used with @prefix@, like @/usr/local@ +-- | Path to the GHC install destination. It is empty by default, which +-- corresponds to the root of the file system. You can replace it by a specific +-- directory. Make sure you use correct absolute path on Windows, e.g. "C:/path". +-- The destination directory is used with a @prefix@, commonly @/usr/local@, +-- i.e. GHC is installed into "C:/path/usr/local" for the above example. defaultDestDir :: FilePath defaultDestDir = "" From git at git.haskell.org Fri Oct 27 01:20:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:20:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Need all top-level dependencies in one go for better parallelism. Minor revision. (145999c) Message-ID: <20171027012057.413FC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/145999cfde98ff857abee0c4abd96ebc637ca04b/ghc >--------------------------------------------------------------- commit 145999cfde98ff857abee0c4abd96ebc637ca04b Author: Andrey Mokhov Date: Thu Jul 20 00:28:33 2017 +0100 Need all top-level dependencies in one go for better parallelism. Minor revision. See #200. >--------------------------------------------------------------- 145999cfde98ff857abee0c4abd96ebc637ca04b src/Oracles/Dependencies.hs | 38 +++++++++++++++++---------------- src/Rules.hs | 51 ++++++++++++++++++++++----------------------- src/Rules/Compile.hs | 2 +- src/Rules/Install.hs | 6 +++--- src/Rules/Program.hs | 4 ++-- 5 files changed, 51 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 145999cfde98ff857abee0c4abd96ebc637ca04b From git at git.haskell.org Fri Oct 27 01:21:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix builder dependencies on generated files (#363) (d9c97e8) Message-ID: <20171027012100.C1F0D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9c97e8f96f482fe7d84e01d61682e82e1edad59/ghc >--------------------------------------------------------------- commit d9c97e8f96f482fe7d84e01d61682e82e1edad59 Author: Zhen Zhang Date: Fri Jul 21 01:14:15 2017 +0800 Fix builder dependencies on generated files (#363) >--------------------------------------------------------------- d9c97e8f96f482fe7d84e01d61682e82e1edad59 src/Rules.hs | 1 - src/Rules/Generate.hs | 14 +------------- src/Rules/Program.hs | 4 +++- src/Rules/Test.hs | 3 ++- src/Settings/Builders/GhcCabal.hs | 4 +++- src/Settings/Builders/Hsc2Hs.hs | 7 ++----- src/Settings/Path.hs | 17 ++++++++++++++++- src/Util.hs | 1 + 8 files changed, 28 insertions(+), 23 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 69fcaee..359d3e9 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -29,7 +29,6 @@ allStages = [minBound ..] -- or Stage1Only targets topLevelTargets :: Rules () topLevelTargets = action $ do - need $ Rules.Generate.inplaceLibCopyTargets let libraryPackages = filter isLibrary (knownPackages \\ [rts, libffi]) need =<< if stage1Only then do diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 3507027..80eca91 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( isGeneratedCFile, isGeneratedCmmFile, generatePackageCode, generateRules, - copyRules, includesDependencies, generatedDependencies, inplaceLibCopyTargets + copyRules, includesDependencies, generatedDependencies ) where import Base @@ -24,18 +24,6 @@ import Target import UserSettings import Util --- | Files that need to be copied over to inplace/lib --- ref: ghc/ghc.mk:142 --- ref: driver/ghc.mk --- ref: utils/hsc2hs/ghc.mk:35 -inplaceLibCopyTargets :: [FilePath] -inplaceLibCopyTargets = map (inplaceLibPath -/-) - [ "ghc-usage.txt" - , "ghci-usage.txt" - , "platformConstants" - , "settings" - , "template-hsc.h" ] - primopsSource :: FilePath primopsSource = "compiler/prelude/primops.txt.pp" diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 846c694..710829b 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -14,7 +14,7 @@ import Oracles.Path (topDirectory) import Rules.Wrappers (WrappedBinary(..), Wrapper, inplaceWrappers) import Settings import Settings.Path (buildPath, inplaceLibBinPath, rtsContext, objectPath, - inplaceLibPath, inplaceBinPath) + inplaceLibPath, inplaceBinPath, inplaceLibCopyTargets) import Target import UserSettings import Util @@ -28,6 +28,8 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do buildPath context -/- programName context <.> exe %> buildBinaryAndWrapper rs context + when (package == ghc) $ want inplaceLibCopyTargets + -- Rules for programs built in install directories when (stage == Stage0 || package == ghc) $ do -- Some binaries in inplace/bin are wrapped diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index fc059ab..93e97c2 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -10,6 +10,7 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Path import Settings +import Settings.Path (inplaceLibCopyTargets) import Target import Util @@ -17,7 +18,7 @@ import Util testRules :: Rules () testRules = do "validate" ~> do - need $ Rules.Generate.inplaceLibCopyTargets + need inplaceLibCopyTargets needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 18816e1..33a7b99 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -4,7 +4,7 @@ module Settings.Builders.GhcCabal ( import Context import Flavour -import Settings.Builders.Common +import Settings.Builders.Common hiding (package) import Util ghcCabalBuilderArgs :: Args @@ -12,6 +12,8 @@ ghcCabalBuilderArgs = builder GhcCabal ? do verbosity <- lift $ getVerbosity top <- getTopDirectory context <- getContext + when (package context /= deriveConstants) $ + lift (need inplaceLibCopyTargets) mconcat [ arg "configure" , arg =<< getPackagePath , arg $ top -/- buildPath context diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index ba98654..a9ec9c5 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -1,9 +1,7 @@ module Settings.Builders.Hsc2Hs (hsc2hsBuilderArgs) where import Settings.Builders.Common - -templateHsc :: FilePath -templateHsc = "inplace/lib/template-hsc.h" +import Settings.Path (templateHscPath) hsc2hsBuilderArgs :: Args hsc2hsBuilderArgs = builder Hsc2Hs ? do @@ -20,7 +18,6 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do version <- if stage == Stage0 then lift ghcCanonVersion else getSetting ProjectVersionInt - lift $ need [templateHsc] mconcat [ arg $ "--cc=" ++ ccPath , arg $ "--ld=" ++ ccPath , notM windowsHost ? arg "--cross-safe" @@ -33,7 +30,7 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do , notStage0 ? arg ("--cflag=-D" ++ tArch ++ "_HOST_ARCH=1") , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) , arg $ "--cflag=-D__GLASGOW_HASKELL__=" ++ version - , arg $ "--template=" ++ top -/- templateHsc + , arg $ "--template=" ++ top -/- templateHscPath , arg $ "-I" ++ top -/- "inplace/lib/include/" , arg =<< getInput , arg "-o", arg =<< getOutput ] diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 0be1838..c8153bf 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -6,7 +6,7 @@ module Settings.Path ( pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, inplaceInstallPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath, - pkgSetupConfigFile + pkgSetupConfigFile, inplaceLibCopyTargets, templateHscPath ) where import Base @@ -214,3 +214,18 @@ stripCmdPath = do "arm-unknown-linux" -> return ":" -- HACK: from the make-based system, see the ref above _ -> return "strip" + +-- | Files that need to be copied over to inplace/lib +-- ref: ghc/ghc.mk:142 +-- ref: driver/ghc.mk +-- ref: utils/hsc2hs/ghc.mk:35 +inplaceLibCopyTargets :: [FilePath] +inplaceLibCopyTargets = map (inplaceLibPath -/-) + [ "ghc-usage.txt" + , "ghci-usage.txt" + , "platformConstants" + , "settings" + , "template-hsc.h" ] + +templateHscPath :: FilePath +templateHscPath = "inplace/lib/template-hsc.h" diff --git a/src/Util.hs b/src/Util.hs index 37743c0..7ea567e 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -22,6 +22,7 @@ import Oracles.Path import Oracles.Config.Setting import Settings import Settings.Builders.Ar +import Settings.Path import Target import UserSettings From git at git.haskell.org Fri Oct 27 01:21:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix validate's executable dependency (#375) (2555a5f) Message-ID: <20171027012104.4C68D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2555a5f03040aaf56e44e32c8b133cc5ead87616/ghc >--------------------------------------------------------------- commit 2555a5f03040aaf56e44e32c8b133cc5ead87616 Author: Zhen Zhang Date: Sun Jul 23 20:37:29 2017 +0800 Fix validate's executable dependency (#375) >--------------------------------------------------------------- 2555a5f03040aaf56e44e32c8b133cc5ead87616 src/Rules/Test.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 93e97c2..0f46f6c 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -22,6 +22,8 @@ testRules = do needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc + needBuilder Hsc2Hs + need ["inplace/bin/hp2ps"] -- TODO: Eliminate explicit filepaths in "need" (#376) build $ Target (vanillaContext Stage2 compiler) (Make "testsuite/tests") [] [] "test" ~> do From git at git.haskell.org Fri Oct 27 01:21:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix validate's hsc2hs dependency (#375) (#378) (fd5cd07) Message-ID: <20171027012107.C7B673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd5cd0756dd1d9a0071c4f3378e6c64cee0e2f63/ghc >--------------------------------------------------------------- commit fd5cd0756dd1d9a0071c4f3378e6c64cee0e2f63 Author: Zhen Zhang Date: Mon Jul 24 02:08:42 2017 +0800 Fix validate's hsc2hs dependency (#375) (#378) >--------------------------------------------------------------- fd5cd0756dd1d9a0071c4f3378e6c64cee0e2f63 src/Rules/Test.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 0f46f6c..5f6d678 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -22,8 +22,9 @@ testRules = do needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 needBuilder Hpc - needBuilder Hsc2Hs - need ["inplace/bin/hp2ps"] -- TODO: Eliminate explicit filepaths in "need" (#376) + need ["inplace/bin/hp2ps", "inplace/bin/hsc2hs"] + -- TODO: Eliminate explicit filepaths in "need" (#376) + -- FIXME: needBuilder Hsc2Hs doesn't work build $ Target (vanillaContext Stage2 compiler) (Make "testsuite/tests") [] [] "test" ~> do From git at git.haskell.org Fri Oct 27 01:21:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant imports (776cf70) Message-ID: <20171027012111.4F1FD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/776cf701a457c0970c7126a840cf8f4afefece2f/ghc >--------------------------------------------------------------- commit 776cf701a457c0970c7126a840cf8f4afefece2f Author: Andrey Mokhov Date: Wed Jul 26 23:07:14 2017 +0100 Drop redundant imports >--------------------------------------------------------------- 776cf701a457c0970c7126a840cf8f4afefece2f src/Rules/Test.hs | 1 - src/Settings/Builders/Hsc2Hs.hs | 1 - src/Util.hs | 1 - 3 files changed, 3 deletions(-) diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 5f6d678..335964c 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -5,7 +5,6 @@ import Builder import Expression import Flavour import GHC -import qualified Rules.Generate import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.Path diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index a9ec9c5..217636b 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -1,7 +1,6 @@ module Settings.Builders.Hsc2Hs (hsc2hsBuilderArgs) where import Settings.Builders.Common -import Settings.Path (templateHscPath) hsc2hsBuilderArgs :: Args hsc2hsBuilderArgs = builder Hsc2Hs ? do diff --git a/src/Util.hs b/src/Util.hs index 7ea567e..37743c0 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -22,7 +22,6 @@ import Oracles.Path import Oracles.Config.Setting import Settings import Settings.Builders.Ar -import Settings.Path import Target import UserSettings From git at git.haskell.org Fri Oct 27 01:21:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bump Cabal library version, fix AppVeyor build (345deee) Message-ID: <20171027012114.B8B1B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/345deee0c3850479ab6047920314c3ac30d7dad0/ghc >--------------------------------------------------------------- commit 345deee0c3850479ab6047920314c3ac30d7dad0 Author: Andrey Mokhov Date: Wed Jul 26 23:35:27 2017 +0100 Bump Cabal library version, fix AppVeyor build >--------------------------------------------------------------- 345deee0c3850479ab6047920314c3ac30d7dad0 hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 1178cb4..77fc54c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -119,7 +119,7 @@ executable hadrian , ScopedTypeVariables build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* - , Cabal == 2.0.0.0 + , Cabal == 2.0.0.2 , containers == 0.5.* , directory == 1.2.* , extra >= 1.4.7 From git at git.haskell.org Fri Oct 27 01:21:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Part 1 of the Great Refactoring of the Expression (9c75620) Message-ID: <20171027012118.394263A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9c75620168d77d91814d6a3aa562cd58405bfe5a/ghc >--------------------------------------------------------------- commit 9c75620168d77d91814d6a3aa562cd58405bfe5a Author: Andrey Mokhov Date: Thu Jul 27 02:58:55 2017 +0100 Part 1 of the Great Refactoring of the Expression See #347 >--------------------------------------------------------------- 9c75620168d77d91814d6a3aa562cd58405bfe5a hadrian.cabal | 3 +- src/Base.hs | 1 - src/Expression.hs | 154 +++++++++++++------------------ src/Oracles/Config/Flag.hs | 7 +- src/Oracles/Config/Setting.hs | 12 +-- src/Oracles/Path.hs | 6 +- src/Rules/Generators/Common.hs | 4 +- src/Rules/Generators/ConfigHs.hs | 2 +- src/Rules/Generators/GhcAutoconfH.hs | 4 +- src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Libffi.hs | 4 +- src/Rules/Wrappers.hs | 46 ++++----- src/Settings.hs | 16 ++-- src/Settings/Builders/Cc.hs | 2 +- src/Settings/Builders/Common.hs | 17 ++-- src/Settings/Builders/DeriveConstants.hs | 6 +- src/Settings/Builders/Ghc.hs | 10 +- src/Settings/Builders/GhcCabal.hs | 38 ++++---- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 4 +- src/Settings/Builders/HsCpp.hs | 2 +- src/Settings/Builders/Hsc2Hs.hs | 10 +- src/Settings/Builders/Make.hs | 2 +- src/Settings/Default.hs | 12 +-- src/Settings/Packages/GhcCabal.hs | 6 +- src/Settings/Packages/IntegerGmp.hs | 4 +- src/Settings/Packages/Rts.hs | 7 +- 27 files changed, 167 insertions(+), 216 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 9c75620168d77d91814d6a3aa562cd58405bfe5a From git at git.haskell.org Fri Oct 27 01:21:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't echo (227d8d7) Message-ID: <20171027012121.CF8923A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/227d8d7d669f0dc99e7947391521259b0ce28186/ghc >--------------------------------------------------------------- commit 227d8d7d669f0dc99e7947391521259b0ce28186 Author: Andrey Mokhov Date: Fri Jul 28 22:22:18 2017 +0100 Don't echo >--------------------------------------------------------------- 227d8d7d669f0dc99e7947391521259b0ce28186 src/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Util.hs b/src/Util.hs index 37743c0..e6fd6bf 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -76,7 +76,7 @@ customBuild rs opts target at Target {..} = do src <- interpret target getInput file <- interpret target getOutput input <- readFile' src - Stdout output <- cmd cmdEcho (Stdin input) [path] argList + Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output Make dir -> cmd Shell cmdEcho path ["-C", dir] argList From git at git.haskell.org Fri Oct 27 01:21:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Disable parallel garbage collection (#385) (57cfa03) Message-ID: <20171027012125.50ECF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/57cfa03c23047bb0c731428e97ca716d9a1cf312/ghc >--------------------------------------------------------------- commit 57cfa03c23047bb0c731428e97ca716d9a1cf312 Author: Ben Gamari Date: Sat Jul 29 06:28:14 2017 -0400 Disable parallel garbage collection (#385) This brings productivity from roughly 40% to 95%. With parallel GC we generally spend much of our time synchronizing between the GC threads and relatively little time doing productive work. >--------------------------------------------------------------- 57cfa03c23047bb0c731428e97ca716d9a1cf312 hadrian.cabal | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 4eb43db..af5fd6c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -133,5 +133,11 @@ executable hadrian , happy >= 1.19.4 ghc-options: -Wall -fno-warn-name-shadowing - -rtsopts -with-rtsopts=-I0 + -rtsopts + -- Disable idle GC to avoid redundant GCs while waiting + -- for external processes + -with-rtsopts=-I0 + -- Don't use parallel GC as the synchronization time tends to eat any + -- benefit. + -with-rtsopts=-qg0 -threaded From git at git.haskell.org Fri Oct 27 01:21:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use GHC to compile C files (#380) (e6dcd1b) Message-ID: <20171027012128.CEE6C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8/ghc >--------------------------------------------------------------- commit e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8 Author: Zhen Zhang Date: Sat Jul 29 18:37:58 2017 +0800 Use GHC to compile C files (#380) >--------------------------------------------------------------- e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8 src/Builder.hs | 4 ++-- src/Rules/Compile.hs | 6 +++--- src/Settings/Builders/Ghc.hs | 24 +++++++++++++++++++++++- src/Settings/Default.hs | 1 + src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Rts.hs | 7 ++++--- 6 files changed, 34 insertions(+), 10 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 7937319..4112900 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -15,8 +15,8 @@ import Stage -- * Extracting source dependencies, e.g. by passing @-M@ command line argument; -- * Linking object files & static libraries into an executable. -- We have CcMode for C compiler and GhcMode for GHC. -data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show) -data GhcMode = CompileHs | FindHsDependencies | LinkHs +data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show) +data GhcMode = CompileCWithGhc | CompileHs | FindHsDependencies | LinkHs deriving (Eq, Generic, Show) -- | GhcPkg can initialise a package database and register packages in it. diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 87fc39a..d3d2ed5 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -28,9 +28,9 @@ compilePackage rs context at Context {..} = do buildWithResources rs $ Target context (Ghc CompileHs stage) [src] [obj] priority 2.0 $ do - nonHs "c" %> compile (Cc CompileC ) (obj2src "c" isGeneratedCFile ) - nonHs "cmm" %> compile (Ghc CompileHs) (obj2src "cmm" isGeneratedCmmFile) - nonHs "s" %> compile (Ghc CompileHs) (obj2src "S" $ const False ) + nonHs "c" %> compile (Ghc CompileCWithGhc) (obj2src "c" isGeneratedCFile ) + nonHs "cmm" %> compile (Ghc CompileHs) (obj2src "cmm" isGeneratedCmmFile) + nonHs "s" %> compile (Ghc CompileHs) (obj2src "S" $ const False ) -- TODO: Add dependencies for #include of .h and .hs-incl files (gcc -MM?). [ path "*" <.> suf way | suf <- [ osuf, hisuf] ] &%> compileHs diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index bb7c1e0..b7d5d70 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,4 +1,7 @@ -module Settings.Builders.Ghc (ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs) where +module Settings.Builders.Ghc ( + ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs, + ghcCbuilderArgs +) where import Flavour import GHC @@ -15,6 +18,25 @@ ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do , append =<< getInputs , arg "-o", arg =<< getOutput ] +ghcCbuilderArgs :: Args +ghcCbuilderArgs = + builder (Ghc CompileCWithGhc) ? do + way <- getWay + let ccArgs = [ append =<< getPkgDataList CcArgs + , getSettingList . ConfCcArgs =<< getStage + , cIncludeArgs + , arg "-Werror" + , Dynamic `wayUnit` way ? append [ "-fPIC", "-DDYNAMIC" ] ] + + mconcat [ arg "-Wall" + , ghcLinkArgs + , commonGhcArgs + , mconcat (map (map ("-optc" ++) <$>) ccArgs) + , arg "-c" + , append =<< getInputs + , arg "-o" + , arg =<< getOutput ] + ghcLinkArgs :: Args ghcLinkArgs = builder (Ghc LinkHs) ? do stage <- getStage diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index b65e86a..2940406 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -212,6 +212,7 @@ defaultBuilderArgs = mconcat , deriveConstantsBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs + , ghcCbuilderArgs , ghcCabalBuilderArgs , ghcCabalHsColourBuilderArgs , ghcMBuilderArgs diff --git a/src/Settings/Packages/Base.hs b/src/Settings/Packages/Base.hs index 219c9d4..07c19ce 100644 --- a/src/Settings/Packages/Base.hs +++ b/src/Settings/Packages/Base.hs @@ -7,4 +7,4 @@ import Settings basePackageArgs :: Args basePackageArgs = package base ? mconcat [ builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) - , builder Cc ? arg "-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. + , builder (Ghc CompileCWithGhc) ? arg "-optc-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 5a76eae..87e1fe8 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -48,8 +48,7 @@ rtsPackageArgs = package rts ? do ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir ghclibDir <- expr installGhcLibDir - mconcat - [ builder Cc ? mconcat + let cArgs = [ arg "-Irts" , arg $ "-I" ++ path , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" @@ -96,8 +95,10 @@ rtsPackageArgs = package rts ? do append [ "-Wno-incompatible-pointer-types" ] ] + mconcat + [ builder (Cc FindCDependencies) ? mconcat cArgs + , builder (Ghc CompileCWithGhc) ? mconcat (map (map ("-optc" ++) <$>) cArgs) , builder Ghc ? arg "-Irts" - , builder HsCpp ? append [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir From git at git.haskell.org Fri Oct 27 01:21:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix profiled GHC context (7b4fdfb) Message-ID: <20171027012132.5F7E83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b4fdfba5f8a58c742a23a70b70085830f540e0e/ghc >--------------------------------------------------------------- commit 7b4fdfba5f8a58c742a23a70b70085830f540e0e Author: Andrey Mokhov Date: Tue Aug 1 01:39:38 2017 +0100 Fix profiled GHC context See #387 >--------------------------------------------------------------- 7b4fdfba5f8a58c742a23a70b70085830f540e0e src/Settings.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings.hs b/src/Settings.hs index c1d4fbb..b65a17b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -70,7 +70,7 @@ integerLibraryName = pkgNameString $ integerLibrary flavour programContext :: Stage -> Package -> Context programContext stage pkg - | pkg == ghc && ghcProfiled flavour = Context stage pkg profiling + | pkg == ghc && ghcProfiled flavour && stage > Stage0 = Context stage pkg profiling | otherwise = vanillaContext stage pkg -- TODO: switch to Set Package as the order of packages should not matter? From git at git.haskell.org Fri Oct 27 01:21:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Bump to lts-9.0 (b6be67c) Message-ID: <20171027012135.D858D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6be67c1c801bda7574a0cd1bb7ca9630deb637f/ghc >--------------------------------------------------------------- commit b6be67c1c801bda7574a0cd1bb7ca9630deb637f Author: Andrey Mokhov Date: Wed Aug 2 00:11:18 2017 +0100 Bump to lts-9.0 See #292, #336 >--------------------------------------------------------------- b6be67c1c801bda7574a0cd1bb7ca9630deb637f hadrian.cabal | 4 ++-- stack.yaml | 36 +++++++++--------------------------- 2 files changed, 11 insertions(+), 29 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index af5fd6c..da905ff 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -122,10 +122,10 @@ executable hadrian , ansi-terminal == 0.6.* , Cabal == 2.0.0.2 , containers == 0.5.* - , directory == 1.2.* + , directory >= 1.2 && < 1.4 , extra >= 1.4.7 , mtl == 2.2.* - , QuickCheck >= 2.6 && < 2.9 + , QuickCheck >= 2.6 && < 2.10 , shake >= 0.15.6 , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* diff --git a/stack.yaml b/stack.yaml index 5fa9f94..a05f2cd 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,36 +1,18 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-6.12 +resolver: lts-9.0 # Local packages, usually specified by relative directory name packages: - '.' - '../libraries/Cabal/Cabal' -# Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) -extra-deps: - -# Override default flag values for local packages and extra-deps -flags: {} - -# Extra package databases containing global packages -extra-package-dbs: [] - -# Control whether we use the GHC we find on the path -# system-ghc: false - -# Require a specific version of stack, using version ranges -# require-stack-version: -any # Default -# require-stack-version: >= 1.0.0 - -# Override the architecture used by stack, especially useful on Windows -# arch: i386 -# arch: x86_64 - -# Extra directories used by stack for building -# extra-include-dirs: [/path/to/dir] -# extra-lib-dirs: [/path/to/dir] - -# Allow a newer minor version of GHC than the snapshot specifies -# compiler-check: newer-minor +nix: + packages: + - autoconf + - automake + - gcc + - git + - ncurses + - perl From git at git.haskell.org Fri Oct 27 01:21:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix AppVeyor (c8b08a2) Message-ID: <20171027012139.5FAA13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c8b08a2231e4b8e34f45bf0a983f39fb0b075b6c/ghc >--------------------------------------------------------------- commit c8b08a2231e4b8e34f45bf0a983f39fb0b075b6c Author: Andrey Mokhov Date: Wed Aug 2 00:56:08 2017 +0100 Fix AppVeyor See #336 >--------------------------------------------------------------- c8b08a2231e4b8e34f45bf0a983f39fb0b075b6c appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/appveyor.yml b/appveyor.yml index b80008c..3b2e43b 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -26,6 +26,7 @@ install: build_script: # Build Hadrian + - stack build alex happy # Otherwise 'stack build' fails on AppVeyor - stack build # Run internal Hadrian tests From git at git.haskell.org Fri Oct 27 01:21:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to building using GHC 8.0.2 and GHC 8.2.1 on Travis (3a39f38) Message-ID: <20171027012142.D16F73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3a39f383a05863a78b63a2ca445e863e75bede19/ghc >--------------------------------------------------------------- commit 3a39f383a05863a78b63a2ca445e863e75bede19 Author: Andrey Mokhov Date: Wed Aug 2 01:02:58 2017 +0100 Switch to building using GHC 8.0.2 and GHC 8.2.1 on Travis >--------------------------------------------------------------- 3a39f383a05863a78b63a2ca445e863e75bede19 .travis.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index ba67ae3..49fac80 100644 --- a/.travis.yml +++ b/.travis.yml @@ -29,17 +29,17 @@ matrix: - os: linux env: MODE="--flavour=quickest" - compiler: "GHC 7.10.3" + compiler: "GHC 8.2.1" addons: apt: packages: - - ghc-7.10.3 + - ghc-8.2.1 - cabal-install-1.22 - zlib1g-dev sources: hvr-ghc before_install: - - PATH="/opt/ghc/7.10.3/bin:$PATH" + - PATH="/opt/ghc/8.2.1/bin:$PATH" - PATH="/opt/cabal/1.22/bin:$PATH" script: From git at git.haskell.org Fri Oct 27 01:21:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean the source tree before building source distribution (e918ec1) Message-ID: <20171027012146.6185E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e918ec1d54a5e1b02bc6d466d0487cece77172a4/ghc >--------------------------------------------------------------- commit e918ec1d54a5e1b02bc6d466d0487cece77172a4 Author: Andrey Mokhov Date: Wed Aug 2 02:51:38 2017 +0100 Clean the source tree before building source distribution See #384 >--------------------------------------------------------------- e918ec1d54a5e1b02bc6d466d0487cece77172a4 src/Rules/Clean.hs | 28 +++++++++++++++++----------- src/Rules/SourceDist.hs | 3 +++ 2 files changed, 20 insertions(+), 11 deletions(-) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 33f1e3e..a8528e8 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -1,4 +1,4 @@ -module Rules.Clean (cleanRules) where +module Rules.Clean (clean, cleanSourceTree, cleanRules) where import Base import Settings.Path @@ -6,14 +6,20 @@ import Stage import UserSettings import Util +clean :: Action () +clean = do + cleanSourceTree + putBuild $ "| Remove Hadrian files..." + removeDirectory generatedPath + removeFilesAfter buildRootPath ["//*"] + putSuccess $ "| Done. " + +cleanSourceTree :: Action () +cleanSourceTree = do + forM_ [Stage0 ..] $ removeDirectory . (buildRootPath -/-) . stageString + removeDirectory inplaceBinPath + removeDirectory inplaceLibPath + removeDirectory "sdistprep" + cleanRules :: Rules () -cleanRules = do - "clean" ~> do - forM_ [Stage0 ..] $ removeDirectory . (buildRootPath -/-) . stageString - removeDirectory generatedPath - removeDirectory inplaceBinPath - removeDirectory inplaceLibPath - removeDirectory "sdistprep" - putBuild $ "| Remove Hadrian files..." - removeFilesAfter buildRootPath ["//*"] - putSuccess $ "| Done. " +cleanRules = "clean" ~> clean diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index 7a60238..40a4156 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -4,12 +4,14 @@ import Base import Builder import Oracles.Config.Setting import Oracles.DirectoryContents +import Rules.Clean import UserSettings import Util sourceDistRules :: Rules () sourceDistRules = do "sdist-ghc" ~> do + cleanSourceTree -- We clean the source tree first, see #384 version <- setting ProjectVersion need ["sdistprep/ghc-" ++ version ++ "-src.tar.xz"] putSuccess "| Done" @@ -41,6 +43,7 @@ prepareTree dest = do , Test "//*~" , Test "//autom4te*" , Test "//dist" + , Test "//dist-install" , Test "//log" , Test "//stage0" , Test "//stage1" From git at git.haskell.org Fri Oct 27 01:21:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: cabal-install-2.x can new-build (#386) (6e8b0af) Message-ID: <20171027012149.DFDC43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e8b0afa1be2fd735784f7e1213a79694b512aa7/ghc >--------------------------------------------------------------- commit 6e8b0afa1be2fd735784f7e1213a79694b512aa7 Author: Oleg Grenrus Date: Wed Aug 2 13:33:09 2017 +0300 cabal-install-2.x can new-build (#386) >--------------------------------------------------------------- 6e8b0afa1be2fd735784f7e1213a79694b512aa7 .gitignore | 1 + build.cabal.sh | 4 ++-- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/.gitignore b/.gitignore index 2e3581b..4b026f2 100644 --- a/.gitignore +++ b/.gitignore @@ -11,6 +11,7 @@ cabal.sandbox.config # build.cabal-new.sh specific /dist-newstyle/ +.ghc.environment.* # build.stack.sh and build.stack.bat specific /.stack-work/ diff --git a/build.cabal.sh b/build.cabal.sh index 973cd3e..0dd9731 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -42,14 +42,14 @@ CABVERSTR=$("$CABAL" --numeric-version) CABVER=( ${CABVERSTR//./ } ) -if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then +if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then # New enough cabal version detected, so # let's use the superior 'cabal new-build' mode # there's no 'cabal new-run' yet, but it's easy to emulate "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" - "./dist-newstyle/build/hadrian-${PKGVER}/build/hadrian/hadrian" \ + $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ --lint \ --directory "$absoluteRoot/.." \ "$@" From git at git.haskell.org Fri Oct 27 01:21:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant line (dd4270a) Message-ID: <20171027012153.66BC53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dd4270a359f5e62e6264064b725aaf427001edc1/ghc >--------------------------------------------------------------- commit dd4270a359f5e62e6264064b725aaf427001edc1 Author: Andrey Mokhov Date: Wed Aug 2 11:39:41 2017 +0100 Drop redundant line See #386 >--------------------------------------------------------------- dd4270a359f5e62e6264064b725aaf427001edc1 build.cabal.sh | 1 - 1 file changed, 1 deletion(-) diff --git a/build.cabal.sh b/build.cabal.sh index 0dd9731..2a0e8a7 100755 --- a/build.cabal.sh +++ b/build.cabal.sh @@ -48,7 +48,6 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th # there's no 'cabal new-run' yet, but it's easy to emulate "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - PKGVER="$(awk '/^version:/ { print $2 }' hadrian.cabal)" $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ --lint \ --directory "$absoluteRoot/.." \ From git at git.haskell.org Fri Oct 27 01:21:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:21:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix warnings (81fecb8) Message-ID: <20171027012156.DDC053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/81fecb8b3f23e6e09441b43ae874f0554cedf50b/ghc >--------------------------------------------------------------- commit 81fecb8b3f23e6e09441b43ae874f0554cedf50b Author: Andrey Mokhov Date: Fri Aug 4 21:15:29 2017 +0100 Fix warnings >--------------------------------------------------------------- 81fecb8b3f23e6e09441b43ae874f0554cedf50b hadrian.cabal | 22 ++++++++++++---------- src/Base.hs | 4 ++-- src/Expression.hs | 22 +++++++++++++--------- src/Settings/Builders/Haddock.hs | 6 +++--- 4 files changed, 30 insertions(+), 24 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index da905ff..6dab6d0 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -131,13 +131,15 @@ executable hadrian , unordered-containers == 0.2.* build-tools: alex >= 3.1 , happy >= 1.19.4 - ghc-options: -Wall - -fno-warn-name-shadowing - -rtsopts - -- Disable idle GC to avoid redundant GCs while waiting - -- for external processes - -with-rtsopts=-I0 - -- Don't use parallel GC as the synchronization time tends to eat any - -- benefit. - -with-rtsopts=-qg0 - -threaded + ghc-options: -Wall + -Wincomplete-record-updates + -Wredundant-constraints + -fno-warn-name-shadowing + -rtsopts + -- Disable idle GC to avoid redundant GCs while waiting + -- for external processes + -with-rtsopts=-I0 + -- Don't use parallel GC as the synchronization time tends to eat any + -- benefit. + -with-rtsopts=-qg0 + -threaded diff --git a/src/Base.hs b/src/Base.hs index d717f2a..9e2922b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -6,7 +6,7 @@ module Base ( module Data.Function, module Data.List.Extra, module Data.Maybe, - module Data.Monoid, + module Data.Semigroup, -- * Shake module Development.Shake, @@ -29,7 +29,7 @@ import Data.Char import Data.Function import Data.List.Extra import Data.Maybe -import Data.Monoid +import Data.Semigroup import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath diff --git a/src/Expression.hs b/src/Expression.hs index a09bb8c..251c04f 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -19,7 +19,7 @@ module Expression ( getTopDirectory, -- * Re-exports - module Data.Monoid, + module Data.Semigroup, module Builder, module Package, module Stage, @@ -28,7 +28,7 @@ module Expression ( import Control.Monad.Trans.Reader import Control.Monad.Trans -import Data.Monoid +import Data.Semigroup import Base import Builder @@ -52,9 +52,13 @@ expr = Expr . lift exprIO :: IO a -> Expr a exprIO = Expr . liftIO -instance Monoid a => Monoid (Expr a) where - mempty = Expr $ return mempty - mappend (Expr x) (Expr y) = Expr $ (<>) <$> x <*> y +instance Semigroup a => Semigroup (Expr a) where + Expr x <> Expr y = Expr $ (<>) <$> x <*> y + +-- TODO: The 'Semigroup a' constraint will at some point become redundant. +instance (Semigroup a, Monoid a) => Monoid (Expr a) where + mempty = pure mempty + mappend = (<>) instance Applicative Expr where pure = Expr . pure @@ -78,15 +82,15 @@ type Ways = Expr [Way] -- Basic operations on expressions: -- | Append something to an expression. -append :: Monoid a => a -> Expr a -append = Expr . return +append :: a -> Expr a +append = pure -- | Remove given elements from a list expression. remove :: Eq a => [a] -> Expr [a] -> Expr [a] remove xs e = filter (`notElem` xs) <$> e -- | Apply a predicate to an expression. -applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a +applyPredicate :: (Monoid a, Semigroup a) => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate if bool then expr else mempty @@ -97,7 +101,7 @@ arg = append . return -- | A convenient operator for predicate application. class PredicateLike a where - (?) :: Monoid m => a -> Expr m -> Expr m + (?) :: (Monoid m, Semigroup m) => a -> Expr m -> Expr m infixr 3 ? diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index bb37d0b..4c6f862 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -5,9 +5,9 @@ import Settings.Builders.Ghc -- | Given a version string such as "2.16.2" produce an integer equivalent. versionToInt :: String -> Int -versionToInt s = major * 1000 + minor * 10 + patch - where - [major, minor, patch] = map read . words $ replaceEq '.' ' ' s +versionToInt s = case map read . words $ replaceEq '.' ' ' s of + [major, minor, patch] -> major * 1000 + minor * 10 + patch + _ -> error "versionToInt: cannot parse version." haddockBuilderArgs :: Args haddockBuilderArgs = builder Haddock ? do From git at git.haskell.org Fri Oct 27 01:22:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out generic build infrastructure (48e8b6f) Message-ID: <20171027012200.6B9C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/48e8b6f223154b9806081e6018099c66dad5a396/ghc >--------------------------------------------------------------- commit 48e8b6f223154b9806081e6018099c66dad5a396 Author: Andrey Mokhov Date: Sat Aug 5 01:02:57 2017 +0100 Factor out generic build infrastructure See #347 >--------------------------------------------------------------- 48e8b6f223154b9806081e6018099c66dad5a396 hadrian.cabal | 2 + src/Expression.hs | 130 ++++++--------------------------------------- src/Hadrian/Expression.hs | 125 +++++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Target.hs | 31 +++++++++++ src/Oracles/ArgsHash.hs | 8 +-- src/Rules/Compile.hs | 6 +-- src/Rules/Configure.hs | 2 +- src/Rules/Data.hs | 4 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 10 ++-- src/Rules/Gmp.hs | 8 +-- src/Rules/Install.hs | 6 +-- src/Rules/Libffi.hs | 6 +-- src/Rules/Library.hs | 8 +-- src/Rules/Program.hs | 2 +- src/Rules/Register.hs | 4 +- src/Rules/Test.hs | 2 +- src/Target.hs | 35 ++---------- src/Util.hs | 21 ++++---- 20 files changed, 225 insertions(+), 189 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 48e8b6f223154b9806081e6018099c66dad5a396 From git at git.haskell.org Fri Oct 27 01:22:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use Cabal build scripts on CI (fe857d0) Message-ID: <20171027012203.F23C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fe857d074b30bf657216acdda98067aae3577440/ghc >--------------------------------------------------------------- commit fe857d074b30bf657216acdda98067aae3577440 Author: Andrey Mokhov Date: Sat Aug 5 11:34:34 2017 +0100 Use Cabal build scripts on CI >--------------------------------------------------------------- fe857d074b30bf657216acdda98067aae3577440 .travis.yml | 10 +++++----- circle.yml | 4 ++-- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/.travis.yml b/.travis.yml index 49fac80..c23e92a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,10 +18,10 @@ matrix: script: # Run internal Hadrian tests - - ./build.sh selftest + - ./build.cabal.sh selftest # Build GHC - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. @@ -44,10 +44,10 @@ matrix: script: # Run internal Hadrian tests - - ./build.sh selftest + - ./build.cabal.sh selftest # Build GHC - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. @@ -63,7 +63,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 install: # Add Cabal to PATH diff --git a/circle.yml b/circle.yml index 457add7..606664a 100644 --- a/circle.yml +++ b/circle.yml @@ -30,10 +30,10 @@ compile: # XXX: export PATH doesn't work well either, so we use inline env # Self test - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh selftest + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- test: override: From git at git.haskell.org Fri Oct 27 01:22:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move ArgsHash oracle to the library (a432cff) Message-ID: <20171027012207.7F72F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a432cffccd145a0cb8e7822333fac87e54c02753/ghc >--------------------------------------------------------------- commit a432cffccd145a0cb8e7822333fac87e54c02753 Author: Andrey Mokhov Date: Sun Aug 6 00:55:44 2017 +0100 Move ArgsHash oracle to the library See #347 >--------------------------------------------------------------- a432cffccd145a0cb8e7822333fac87e54c02753 hadrian.cabal | 2 +- src/Builder.hs | 15 +------------ src/Hadrian/Oracles/ArgsHash.hs | 49 +++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Target.hs | 3 +-- src/Oracles/ArgsHash.hs | 35 ----------------------------- src/Rules/Oracles.hs | 7 ++++-- src/Rules/Selftest.hs | 8 ++++--- src/Target.hs | 22 +++++++++++++++--- src/Util.hs | 3 ++- 9 files changed, 83 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 a432cffccd145a0cb8e7822333fac87e54c02753 From git at git.haskell.org Fri Oct 27 01:22:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (5e1d004) Message-ID: <20171027012211.1DCEA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5e1d004c4d92f9847f6d96e38c27815429239fea/ghc >--------------------------------------------------------------- commit 5e1d004c4d92f9847f6d96e38c27815429239fea Author: Andrey Mokhov Date: Sun Aug 6 01:24:06 2017 +0100 Minor revision >--------------------------------------------------------------- 5e1d004c4d92f9847f6d96e38c27815429239fea src/Hadrian/Oracles/ArgsHash.hs | 9 +++++---- src/Util.hs | 2 +- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index 0eba6c2..80a170d 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Hadrian.Oracles.ArgsHash ( - TrackArgument, trackAllArguments, checkArgsHash, argsHashOracle + TrackArgument, trackAllArguments, trackArgsHash, argsHashOracle ) where import Control.Monad @@ -34,13 +34,14 @@ newtype ArgsHashKey c b = ArgsHashKey (Target c b) -- in the Shake database. This optimisation is normally harmless, because -- argument list constructors are assumed not to examine target sources, but -- only append them to argument lists where appropriate. -checkArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action () -checkArgsHash t = do +trackArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action () +trackArgsHash t = do let hashedInputs = [ show $ hash (inputs t) ] hashedTarget = target (context t) (builder t) hashedInputs (outputs t) void (askOracle $ ArgsHashKey hashedTarget :: Action Int) --- | Oracle for storing per-target argument list hashes. +-- | This oracle stores per-target argument list hashes in the Shake database, +-- allowing the user to track them between builds using 'trackArgsHash' queries. argsHashOracle :: (ShakeValue c, ShakeValue b) => TrackArgument c b -> Args c b -> Rules () argsHashOracle trackArgument args = void $ addOracle $ \(ArgsHashKey target) -> do diff --git a/src/Util.hs b/src/Util.hs index ed535fe..c4b888d 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -51,7 +51,7 @@ customBuild rs opts target = do argList <- interpret target getArgs verbose <- interpret target verboseCommands let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly - checkArgsHash target -- Rerun the rule if the hash of argList has changed. + trackArgsHash target -- Rerun the rule if the hash of argList has changed. withResources rs $ do putInfo target quietlyUnlessVerbose $ case targetBuilder of From git at git.haskell.org Fri Oct 27 01:22:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move DirectoryContents oracle to the library (7ff841e) Message-ID: <20171027012214.9EE3B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ff841eb492e16bedfb1d72152e5fc0de4d52c77/ghc >--------------------------------------------------------------- commit 7ff841eb492e16bedfb1d72152e5fc0de4d52c77 Author: Andrey Mokhov Date: Sun Aug 6 01:31:02 2017 +0100 Move DirectoryContents oracle to the library See #347 >--------------------------------------------------------------- 7ff841eb492e16bedfb1d72152e5fc0de4d52c77 hadrian.cabal | 3 ++- src/Base.hs | 14 +------------- src/{ => Hadrian}/Oracles/DirectoryContents.hs | 18 +++++++++++------- src/Hadrian/Utilities.hs | 19 +++++++++++++++++++ src/Rules/Install.hs | 3 ++- src/Rules/Oracles.hs | 4 ++-- src/Rules/SourceDist.hs | 3 ++- src/Util.hs | 2 +- 8 files changed, 40 insertions(+), 26 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 121ba74..b757549 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -28,12 +28,13 @@ executable hadrian , GHC , Hadrian.Expression , Hadrian.Oracles.ArgsHash + , Hadrian.Oracles.DirectoryContents , Hadrian.Target + , Hadrian.Utilities , Oracles.Config , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies - , Oracles.DirectoryContents , Oracles.ModuleFiles , Oracles.PackageData , Oracles.Path diff --git a/src/Base.hs b/src/Base.hs index 9e2922b..7443438 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -33,6 +33,7 @@ import Data.Semigroup import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath +import Hadrian.Utilities import System.Console.ANSI import System.IO import System.Info @@ -72,19 +73,6 @@ replaceWhen p to = map (\from -> if p from then to else from) quote :: String -> String quote s = "'" ++ s ++ "'" --- | Normalise a path and convert all path separators to @/@, even on Windows. -unifyPath :: FilePath -> FilePath -unifyPath = toStandard . normaliseEx - --- | Combine paths with a forward slash regardless of platform. -(-/-) :: FilePath -> FilePath -> FilePath -"" -/- b = b -a -/- b - | last a == '/' = a ++ b - | otherwise = a ++ '/' : b - -infixr 6 -/- - -- Explicit definition to avoid dependency on Data.List.Ordered -- | Difference of two ordered lists. minusOrd :: Ord a => [a] -> [a] -> [a] diff --git a/src/Oracles/DirectoryContents.hs b/src/Hadrian/Oracles/DirectoryContents.hs similarity index 82% rename from src/Oracles/DirectoryContents.hs rename to src/Hadrian/Oracles/DirectoryContents.hs index 1f016ff..e52c5c5 100644 --- a/src/Oracles/DirectoryContents.hs +++ b/src/Hadrian/Oracles/DirectoryContents.hs @@ -1,12 +1,15 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} -module Oracles.DirectoryContents ( +module Hadrian.Oracles.DirectoryContents ( directoryContents, directoryContentsOracle, Match (..), matchAll ) where -import System.Directory.Extra +import Control.Monad +import Development.Shake +import Development.Shake.Classes import GHC.Generics +import System.Directory.Extra -import Base +import Hadrian.Utilities newtype DirectoryContents = DirectoryContents (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -14,6 +17,10 @@ newtype DirectoryContents = DirectoryContents (Match, FilePath) data Match = Test FilePattern | Not Match | And [Match] | Or [Match] deriving (Generic, Eq, Show, Typeable) +instance Binary Match +instance Hashable Match +instance NFData Match + -- | A 'Match' expression that always evaluates to 'True' (i.e. always matches). matchAll :: Match matchAll = And [] @@ -30,11 +37,8 @@ matches (Or ms) f = any (`matches` f) ms directoryContents :: Match -> FilePath -> Action [FilePath] directoryContents expr dir = askOracle $ DirectoryContents (expr, dir) +-- | This oracle answers 'directoryContents' queries and tracks the results. directoryContentsOracle :: Rules () directoryContentsOracle = void $ addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ map unifyPath . filter (matches expr) <$> listFilesInside (return . matches expr) dir - -instance Binary Match -instance Hashable Match -instance NFData Match diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs new file mode 100644 index 0000000..2103452 --- /dev/null +++ b/src/Hadrian/Utilities.hs @@ -0,0 +1,19 @@ +module Hadrian.Utilities ( + -- * FilePath manipulation + unifyPath, (-/-) + ) where + +import Development.Shake.FilePath + +-- | Normalise a path and convert all path separators to @/@, even on Windows. +unifyPath :: FilePath -> FilePath +unifyPath = toStandard . normaliseEx + +-- | Combine paths with a forward slash regardless of platform. +(-/-) :: FilePath -> FilePath -> FilePath +"" -/- b = b +a -/- b + | last a == '/' = a ++ b + | otherwise = a ++ '/' : b + +infixr 6 -/- diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 66e57bf..f90b480 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -1,6 +1,8 @@ {-# LANGUAGE FlexibleContexts #-} module Rules.Install (installRules) where +import Hadrian.Oracles.DirectoryContents + import Base import Target import Context @@ -16,7 +18,6 @@ import Rules.Generate import Settings.Packages.Rts import Oracles.Config.Setting import Oracles.Dependencies -import Oracles.DirectoryContents import Oracles.Path import qualified System.Directory as IO diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index a12bec4..59b55d9 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -1,11 +1,11 @@ module Rules.Oracles (oracleRules) where import qualified Hadrian.Oracles.ArgsHash +import qualified Hadrian.Oracles.DirectoryContents import Base import qualified Oracles.Config import qualified Oracles.Dependencies -import qualified Oracles.DirectoryContents import qualified Oracles.ModuleFiles import qualified Oracles.PackageData import qualified Oracles.Path @@ -15,9 +15,9 @@ import Settings oracleRules :: Rules () oracleRules = do Hadrian.Oracles.ArgsHash.argsHashOracle trackArgument getArgs + Hadrian.Oracles.DirectoryContents.directoryContentsOracle Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles - Oracles.DirectoryContents.directoryContentsOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle Oracles.Path.pathOracle diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index 40a4156..879ae34 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -1,9 +1,10 @@ module Rules.SourceDist (sourceDistRules) where +import Hadrian.Oracles.DirectoryContents + import Base import Builder import Oracles.Config.Setting -import Oracles.DirectoryContents import Rules.Clean import UserSettings import Util diff --git a/src/Util.hs b/src/Util.hs index c4b888d..a616b04 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -12,13 +12,13 @@ import qualified System.IO as IO import qualified Control.Exception.Base as IO import Hadrian.Oracles.ArgsHash +import Hadrian.Oracles.DirectoryContents import Base import CmdLineFlag import Context import Expression import GHC -import Oracles.DirectoryContents import Oracles.Path import Oracles.Config.Setting import Settings From git at git.haskell.org Fri Oct 27 01:22:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out general functionality of path oracles to the library (df8e5aa) Message-ID: <20171027012218.2E8B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd/ghc >--------------------------------------------------------------- commit df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd Author: Andrey Mokhov Date: Sun Aug 6 02:17:59 2017 +0100 Factor out general functionality of path oracles to the library See #347 >--------------------------------------------------------------- df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd hadrian.cabal | 2 +- src/Base.hs | 4 -- src/Expression.hs | 5 -- src/Hadrian/Oracles/ArgsHash.hs | 6 +- src/Hadrian/Oracles/DirectoryContents.hs | 6 +- src/Hadrian/Oracles/Path.hs | 57 ++++++++++++++++++ src/Hadrian/Utilities.hs | 8 +++ src/Oracles/Path.hs | 99 -------------------------------- src/Rules/Data.hs | 1 - src/Rules/Install.hs | 5 +- src/Rules/Oracles.hs | 4 +- src/Rules/Program.hs | 6 +- src/Rules/Test.hs | 3 +- src/Rules/Wrappers.hs | 16 +++--- src/Settings.hs | 40 ++++++++++++- src/Settings/Builders/Common.hs | 4 +- src/Settings/Builders/Configure.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 8 +-- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Path.hs | 9 ++- src/Util.hs | 9 ++- 22 files changed, 148 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 df8e5aa83d5a41b8e62e93de33f7bee3a8e08fbd From git at git.haskell.org Fri Oct 27 01:22:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge all generators into a single file, factor our common functionality into the library. (8e97252) Message-ID: <20171027012221.BD7A53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8e97252efa426ec9caff762de839ebeded401692/ghc >--------------------------------------------------------------- commit 8e97252efa426ec9caff762de839ebeded401692 Author: Andrey Mokhov Date: Sun Aug 6 14:17:06 2017 +0100 Merge all generators into a single file, factor our common functionality into the library. See #347 >--------------------------------------------------------------- 8e97252efa426ec9caff762de839ebeded401692 hadrian.cabal | 8 - src/Base.hs | 51 +---- src/Expression.hs | 2 +- src/Hadrian/Expression.hs | 13 +- src/Hadrian/Utilities.hs | 56 +++++- src/Oracles/Dependencies.hs | 1 + src/Oracles/ModuleFiles.hs | 1 + src/Rules/Configure.hs | 2 +- src/Rules/Generate.hs | 310 ++++++++++++++++++++++++++++++- src/Rules/Generators/Common.hs | 18 -- src/Rules/Generators/ConfigHs.hs | 102 ---------- src/Rules/Generators/GhcAutoconfH.hs | 37 ---- src/Rules/Generators/GhcBootPlatformH.hs | 57 ------ src/Rules/Generators/GhcPlatformH.hs | 56 ------ src/Rules/Generators/GhcSplit.hs | 27 --- src/Rules/Generators/GhcVersionH.hs | 35 ---- src/Rules/Generators/VersionHs.hs | 18 -- src/Rules/Gmp.hs | 7 +- src/Rules/Libffi.hs | 4 +- src/Rules/Selftest.hs | 1 + src/Rules/Test.hs | 5 +- src/Settings/Builders/Haddock.hs | 2 + src/Settings/Packages/Rts.hs | 7 +- src/Settings/Path.hs | 7 +- src/Way.hs | 3 +- 25 files changed, 394 insertions(+), 436 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 8e97252efa426ec9caff762de839ebeded401692 From git at git.haskell.org Fri Oct 27 01:22:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge Predicate into Expression (2bdb94f) Message-ID: <20171027012225.390A13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c/ghc >--------------------------------------------------------------- commit 2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c Author: Andrey Mokhov Date: Sun Aug 6 22:27:23 2017 +0100 Merge Predicate into Expression >--------------------------------------------------------------- 2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c hadrian.cabal | 1 - src/Builder.hs | 85 +++++++++++++++++++++++--------- src/Context.hs | 24 ++++++++-- src/Expression.hs | 76 +++++++++++++++++++++++------ src/Oracles/Dependencies.hs | 2 +- src/Predicate.hs | 93 ------------------------------------ src/Rules/Cabal.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 1 - src/Rules/Install.hs | 2 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Settings/Builders/Common.hs | 2 - src/Settings/Default.hs | 2 +- src/Settings/Default.hs-boot | 2 +- src/Settings/Flavours/Development.hs | 2 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/Quickest.hs | 2 +- src/Settings/Packages/Base.hs | 2 +- src/Settings/Packages/Cabal.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 12 ++--- src/Settings/Packages/GhcPrim.hs | 8 ++-- src/Settings/Packages/Ghci.hs | 4 +- src/Settings/Packages/Haddock.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/Path.hs | 2 +- src/Target.hs | 2 +- src/UserSettings.hs | 2 +- src/Util.hs | 2 +- 35 files changed, 181 insertions(+), 175 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 2bdb94fda55a4a4b34c8ae1403e3ec07bd7b653c From git at git.haskell.org Fri Oct 27 01:22:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out generic predicates into the library (65c5d7c) Message-ID: <20171027012228.B33B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65c5d7c6f75a583439b6c52ce4a89e6026cf76dc/ghc >--------------------------------------------------------------- commit 65c5d7c6f75a583439b6c52ce4a89e6026cf76dc Author: Andrey Mokhov Date: Sun Aug 6 23:18:51 2017 +0100 Factor out generic predicates into the library See #347 >--------------------------------------------------------------- 65c5d7c6f75a583439b6c52ce4a89e6026cf76dc hadrian.cabal | 3 ++- src/Expression.hs | 16 --------------- src/Hadrian/Expression.hs | 43 +++++++++++++++++++++++++++++++---------- src/Hadrian/Oracles/ArgsHash.hs | 2 +- 4 files changed, 36 insertions(+), 28 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index e1505aa..93a755c 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -102,7 +102,6 @@ executable hadrian , UserSettings , Util , Way - default-language: Haskell2010 default-extensions: RecordWildCards other-extensions: DeriveFunctor @@ -110,8 +109,10 @@ executable hadrian , FlexibleInstances , GeneralizedNewtypeDeriving , LambdaCase + , MultiParamTypeClasses , OverloadedStrings , ScopedTypeVariables + , TypeFamilies build-depends: base >= 4.8 && < 5 , ansi-terminal == 0.6.* , Cabal == 2.0.0.2 diff --git a/src/Expression.hs b/src/Expression.hs index 274613c..0442c23 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -29,7 +29,6 @@ module Expression ( import Control.Monad.Extra import Data.Semigroup -import Development.Shake import qualified Hadrian.Expression as H import Hadrian.Expression hiding (Expr, Predicate, Args) @@ -107,18 +106,3 @@ notPackage = notM . package libraryPackage :: Predicate libraryPackage = isLibrary <$> getPackage --- | Does any of the input files match a given pattern? -input :: FilePattern -> Predicate -input f = any (f ?==) <$> getInputs - --- | Does any of the input files match any of the given patterns? -inputs :: [FilePattern] -> Predicate -inputs = anyM input - --- | Does any of the output files match a given pattern? -output :: FilePattern -> Predicate -output f = any (f ?==) <$> getOutputs - --- | Does any of the output files match any of the given patterns? -outputs :: [FilePattern] -> Predicate -outputs = anyM output diff --git a/src/Hadrian/Expression.hs b/src/Hadrian/Expression.hs index 8010695..4022f02 100644 --- a/src/Hadrian/Expression.hs +++ b/src/Hadrian/Expression.hs @@ -1,11 +1,14 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} module Hadrian.Expression ( -- * Expressions Expr, Predicate, Args, -- ** Construction and modification - expr, exprIO, arg, remove, (?), + expr, exprIO, arg, remove, + + -- ** Predicates + (?), input, inputs, output, outputs, -- ** Evaluation interpret, interpretInContext, @@ -14,12 +17,14 @@ module Hadrian.Expression ( getContext, getBuilder, getOutputs, getInputs, getInput, getOutput ) where +import Control.Monad.Extra import Control.Monad.Trans import Control.Monad.Trans.Reader import Data.Semigroup import Development.Shake -import Hadrian.Target +import qualified Hadrian.Target as Target +import Hadrian.Target (Target, target) import Hadrian.Utilities -- | 'Expr' @c b a@ is a computation that produces a value of type 'Action' @a@ @@ -71,7 +76,7 @@ p ? e = do bool <- toPredicate p if bool then e else mempty -instance ToPredicate (Predicate c b) c b where +instance (c ~ c', b ~ b') => ToPredicate (Predicate c b) c' b' where toPredicate = id instance ToPredicate Bool c b where @@ -93,28 +98,46 @@ interpretInContext c = interpret $ target c -- | Get the current build 'Context'. getContext :: Expr c b c -getContext = Expr $ asks context +getContext = Expr $ asks Target.context -- | Get the 'Builder' for the current 'Target'. getBuilder :: Expr c b b -getBuilder = Expr $ asks builder +getBuilder = Expr $ asks Target.builder -- | Get the input files of the current 'Target'. getInputs :: Expr c b [FilePath] -getInputs = Expr $ asks inputs +getInputs = Expr $ asks Target.inputs -- | Run 'getInputs' and check that the result contains one input file only. getInput :: (Show b, Show c) => Expr c b FilePath getInput = Expr $ do target <- ask - fromSingleton ("Exactly one input file expected in " ++ show target) <$> asks inputs + fromSingleton ("Exactly one input file expected in " ++ show target) <$> + asks Target.inputs -- | Get the files produced by the current 'Target'. getOutputs :: Expr c b [FilePath] -getOutputs = Expr $ asks outputs +getOutputs = Expr $ asks Target.outputs -- | Run 'getOutputs' and check that the result contains one output file only. getOutput :: (Show b, Show c) => Expr c b FilePath getOutput = Expr $ do target <- ask - fromSingleton ("Exactly one output file expected in " ++ show target) <$> asks outputs + fromSingleton ("Exactly one output file expected in " ++ show target) <$> + asks Target.outputs + +-- | Does any of the input files match a given pattern? +input :: FilePattern -> Predicate c b +input f = any (f ?==) <$> getInputs + +-- | Does any of the input files match any of the given patterns? +inputs :: [FilePattern] -> Predicate c b +inputs = anyM input + +-- | Does any of the output files match a given pattern? +output :: FilePattern -> Predicate c b +output f = any (f ?==) <$> getOutputs + +-- | Does any of the output files match any of the given patterns? +outputs :: [FilePattern] -> Predicate c b +outputs = anyM output \ No newline at end of file diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index 68b67e2..e07fc3f 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -7,7 +7,7 @@ import Control.Monad import Development.Shake import Development.Shake.Classes -import Hadrian.Expression +import Hadrian.Expression hiding (inputs, outputs) import Hadrian.Target -- | 'TrackArgument' is used to specify the arguments that should be tracked by From git at git.haskell.org Fri Oct 27 01:22:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop append, simplify (e37a5f7) Message-ID: <20171027012232.39FFB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e37a5f773ae3c5584095d487cd831d5674357670/ghc >--------------------------------------------------------------- commit e37a5f773ae3c5584095d487cd831d5674357670 Author: Andrey Mokhov Date: Mon Aug 7 00:25:42 2017 +0100 Drop append, simplify >--------------------------------------------------------------- e37a5f773ae3c5584095d487cd831d5674357670 src/Expression.hs | 12 +-- src/Hadrian/Expression.hs | 0 src/Rules/Libffi.hs | 2 +- src/Settings/Builders/Ar.hs | 2 +- src/Settings/Builders/Cc.hs | 6 +- src/Settings/Builders/Common.hs | 19 +--- src/Settings/Builders/Configure.hs | 16 +-- src/Settings/Builders/DeriveConstants.hs | 4 +- src/Settings/Builders/Ghc.hs | 46 ++++----- src/Settings/Builders/GhcCabal.hs | 50 ++++----- src/Settings/Builders/Haddock.hs | 22 ++-- src/Settings/Builders/Hsc2Hs.hs | 30 +++--- src/Settings/Builders/Ld.hs | 4 +- src/Settings/Builders/Make.hs | 6 +- src/Settings/Default.hs | 168 +++++++++++++++---------------- src/Settings/Flavours/Development.hs | 6 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 6 +- src/Settings/Flavours/Quickest.hs | 8 +- src/Settings/Packages/Cabal.hs | 4 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Settings/Packages/Haddock.hs | 2 +- src/Settings/Packages/Rts.hs | 18 ++-- src/Settings/Packages/RunGhc.hs | 2 +- 26 files changed, 206 insertions(+), 235 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 e37a5f773ae3c5584095d487cd831d5674357670 From git at git.haskell.org Fri Oct 27 01:22:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (5dd20f0) Message-ID: <20171027012235.B80E53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5dd20f0de9043e46bb2a2bdbed94f86c68e33672/ghc >--------------------------------------------------------------- commit 5dd20f0de9043e46bb2a2bdbed94f86c68e33672 Author: Andrey Mokhov Date: Mon Aug 7 01:19:34 2017 +0100 Minor revision >--------------------------------------------------------------- 5dd20f0de9043e46bb2a2bdbed94f86c68e33672 src/Expression.hs | 17 +++++++---------- src/Rules/Generate.hs | 6 +++--- src/Settings.hs | 28 +++++++++++----------------- src/Settings/Builders/Ghc.hs | 20 +++++++++----------- src/Settings/Builders/GhcCabal.hs | 4 ++-- 5 files changed, 32 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 5dd20f0de9043e46bb2a2bdbed94f86c68e33672 From git at git.haskell.org Fri Oct 27 01:22:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move the Config oracle to the library (d3ef19d) Message-ID: <20171027012239.488C63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d3ef19d2fa04f9213bb67409869303d08fa52aee/ghc >--------------------------------------------------------------- commit d3ef19d2fa04f9213bb67409869303d08fa52aee Author: Andrey Mokhov Date: Mon Aug 7 01:58:05 2017 +0100 Move the Config oracle to the library See #347 >--------------------------------------------------------------- d3ef19d2fa04f9213bb67409869303d08fa52aee hadrian.cabal | 6 +++--- src/Expression.hs | 2 +- src/{ => Hadrian}/Oracles/Config.hs | 17 ++++++++++++----- src/Oracles/{Config => }/Flag.hs | 7 ++++--- src/Oracles/{Config => }/Setting.hs | 22 ++++++++++++---------- src/Rules/Data.hs | 2 +- src/Rules/Generate.hs | 4 ++-- src/Rules/Gmp.hs | 2 +- src/Rules/Install.hs | 17 ++++++++--------- src/Rules/Oracles.hs | 4 ++-- src/Rules/Program.hs | 2 +- src/Rules/Selftest.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 4 ++-- src/Rules/Wrappers.hs | 2 +- src/Settings.hs | 2 +- src/Settings/Builders/Common.hs | 8 ++++---- src/Settings/Default.hs | 4 ++-- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Packages/Compiler.hs | 4 ++-- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcPrim.hs | 2 +- src/Settings/Packages/IntegerGmp.hs | 2 +- src/Settings/Packages/Rts.hs | 4 ++-- src/Settings/Packages/RunGhc.hs | 2 +- src/Settings/Path.hs | 2 +- src/Util.hs | 2 +- src/Way.hs | 2 +- 28 files changed, 71 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 d3ef19d2fa04f9213bb67409869303d08fa52aee From git at git.haskell.org Fri Oct 27 00:25:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor libffi rules. (709026d) Message-ID: <20171027002524.B4CD73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/709026de4920d45ad83a9e6a98153b9328533d1a/ghc >--------------------------------------------------------------- commit 709026de4920d45ad83a9e6a98153b9328533d1a Author: Andrey Mokhov Date: Tue Jan 5 17:00:37 2016 +0000 Refactor libffi rules. >--------------------------------------------------------------- 709026de4920d45ad83a9e6a98153b9328533d1a src/Rules/Copy.hs | 14 -------------- src/Rules/Libffi.hs | 26 +++++++++++++++++++------- 2 files changed, 19 insertions(+), 21 deletions(-) diff --git a/src/Rules/Copy.hs b/src/Rules/Copy.hs index b1f9760..7454fd9 100644 --- a/src/Rules/Copy.hs +++ b/src/Rules/Copy.hs @@ -5,9 +5,6 @@ import Expression import GHC import Rules.Actions import Rules.Generate -import Rules.Libffi -import Settings.Packages.Rts -import Settings.TargetDirectory installTargets :: [FilePath] installTargets = [ "inplace/lib/template-hsc.h" @@ -16,17 +13,6 @@ installTargets = [ "inplace/lib/template-hsc.h" copyRules :: Rules () copyRules = do - targetPath Stage1 rts -/- "build/ffi*.h" %> \ffih -> do - need [libffiLibrary] - ffiHPaths <- getDirectoryFiles "" ["libffi/build/inst/lib/*/include/ffi.h"] - when (length ffiHPaths /= 1) $ - putError $ "copyRules: exactly one ffi.h header expected" - ++ "(found: " ++ show ffiHPaths ++ ")." - - copyFile (takeDirectory (head ffiHPaths) -/- takeFileName ffih) ffih - libffiName <- rtsLibffiLibraryName - copyFile libffiLibrary (targetPath Stage1 rts -/- "build/lib" ++ libffiName <.> "a") - "inplace/lib/template-hsc.h" <~ pkgPath hsc2hs "inplace/lib/platformConstants" <~ derivedConstantsPath "inplace/lib/settings" <~ "." diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 603b35f..041650f 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,4 +1,4 @@ -module Rules.Libffi (libffiRules, libffiLibrary) where +module Rules.Libffi (libffiRules, libffiDependencies) where import Base import Expression @@ -6,15 +6,22 @@ import GHC import Oracles import Rules.Actions import Settings.Builders.Common +import Settings.Packages.Rts +import Settings.TargetDirectory import Settings.User --- We use this file to track the whole libffi library -libffiLibrary :: FilePath -libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" +rtsBuildPath :: FilePath +rtsBuildPath = targetPath Stage1 rts -/- "build" + +libffiDependencies :: [FilePath] +libffiDependencies = (rtsBuildPath -/-) <$> [ "ffi.h", "ffitarget.h" ] libffiBuild :: FilePath libffiBuild = "libffi/build" +libffiLibrary :: FilePath +libffiLibrary = libffiBuild -/- "inst/lib/libffi.a" + libffiMakefile :: FilePath libffiMakefile = libffiBuild -/- "Makefile.in" @@ -61,7 +68,7 @@ configureArguments = do libffiRules :: Rules () libffiRules = do - libffiLibrary %> \_ -> do + libffiDependencies &%> \_ -> do when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"] liftIO $ removeFiles libffiBuild ["//*"] tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] @@ -87,9 +94,14 @@ libffiRules = do runMake libffiBuild [] runMake libffiBuild ["install"] - putSuccess $ "| Successfully built custom library 'libffi'" + forM_ ["ffi.h", "ffitarget.h"] $ \file -> do + let src = libffiBuild -/- "inst/lib" -/- libname -/- "include" -/- file + copyFile src (rtsBuildPath -/- file) - "libffi/build/inst/lib/*/include/*.h" %> \_ -> need [libffiLibrary] + libffiName <- rtsLibffiLibraryName + copyFile libffiLibrary (rtsBuildPath -/- "lib" ++ libffiName <.> "a") + + putSuccess $ "| Successfully built custom library 'libffi'" -- chmod +x libffi/ln -- # wc on OS X has spaces in its output, which libffi's Makefile From git at git.haskell.org Fri Oct 27 00:25:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:25:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add CompilerMode to Cc and Ghc builders. (897ba61) Message-ID: <20171027002525.00A7B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/897ba61daec64836092aa46fe097743013cd7bc5/ghc >--------------------------------------------------------------- commit 897ba61daec64836092aa46fe097743013cd7bc5 Author: Andrey Mokhov Date: Fri Apr 15 02:23:37 2016 +0100 Add CompilerMode to Cc and Ghc builders. See #223. >--------------------------------------------------------------- 897ba61daec64836092aa46fe097743013cd7bc5 src/Builder.hs | 80 ++++++++++++++++---------------- src/Predicates.hs | 13 ++++-- src/Rules/Compile.hs | 10 ++-- src/Rules/Dependencies.hs | 5 +- src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 4 +- src/Rules/Program.hs | 3 +- src/Rules/Test.hs | 4 +- src/Settings/Args.hs | 1 - src/Settings/Builders/Cc.hs | 38 +++++++-------- src/Settings/Builders/DeriveConstants.hs | 2 +- src/Settings/Builders/Ghc.hs | 4 +- src/Settings/Builders/GhcCabal.hs | 10 ++-- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Packages/Directory.hs | 4 +- 15 files changed, 95 insertions(+), 87 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 897ba61daec64836092aa46fe097743013cd7bc5 From git at git.haskell.org Fri Oct 27 00:42:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependency of hsc2hs on template-hsc.h (fdd223e) Message-ID: <20171027004219.449433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fdd223e91e2d5226bc6f589e3a17808b5b8eef6a/ghc >--------------------------------------------------------------- commit fdd223e91e2d5226bc6f589e3a17808b5b8eef6a Author: Andrey Mokhov Date: Thu Sep 14 12:54:59 2017 +0100 Add missing dependency of hsc2hs on template-hsc.h >--------------------------------------------------------------- fdd223e91e2d5226bc6f589e3a17808b5b8eef6a src/Builder.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index d70ecab..2e8aca1 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -124,6 +124,8 @@ instance H.Builder Builder where needBuilder :: Builder -> Action () needBuilder (Configure dir) = need [dir -/- "configure"] + needBuilder Hsc2Hs = do path <- H.builderPath Hsc2Hs + need [path, templateHscPath] needBuilder (Make dir) = need [dir -/- "Makefile"] needBuilder builder = when (isJust $ builderProvenance builder) $ do path <- H.builderPath builder From git at git.haskell.org Fri Oct 27 00:42:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Attempt to fix Travis MacOSX instance (c391fea) Message-ID: <20171027004219.9F3433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c391feaa87a406da4f19e3384b0329fb086d8268/ghc >--------------------------------------------------------------- commit c391feaa87a406da4f19e3384b0329fb086d8268 Author: Andrey Mokhov Date: Sat Oct 22 01:39:25 2016 +0100 Attempt to fix Travis MacOSX instance >--------------------------------------------------------------- c391feaa87a406da4f19e3384b0329fb086d8268 .travis.yml | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0209cab..217a7d5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -39,13 +39,17 @@ install: - mv .git ghc/hadrian - cd ghc/hadrian - git reset --hard HEAD + - cd .. + - ./boot + - ./configure + - cd hadrian script: # Run internal Hadrian tests - ./build.sh selftest # Build GHC - - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.sh -j --skip-configure --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 00:42:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant case. (bbbf03c) Message-ID: <20171027004221.DCE1E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bbbf03c99d8c0264317aa5527baec180caf94388/ghc >--------------------------------------------------------------- commit bbbf03c99d8c0264317aa5527baec180caf94388 Author: Andrey Mokhov Date: Tue Jan 19 11:56:35 2016 +0000 Drop redundant case. [skip ci] >--------------------------------------------------------------- bbbf03c99d8c0264317aa5527baec180caf94388 src/Settings/Packages/Rts.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 58b76cf..e41e2bf 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -23,11 +23,9 @@ rtsLibffiLibraryName = do use_system_ffi <- flag UseSystemFfi windows <- windowsHost case (use_system_ffi, windows) of - (True, False) -> return "ffi" + (True , False) -> return "ffi" (False, False) -> return "Cffi" - (_, True) -> return "Cffi-6" - (_, _) -> error "Unsupported FFI library configuration case" - + (_ , True ) -> return "Cffi-6" rtsPackageArgs :: Args rtsPackageArgs = package rts ? do From git at git.haskell.org Fri Oct 27 00:42:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Need rts at the top-level to allow more parallelism (adc8e35) Message-ID: <20171027004223.074433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/adc8e3531a5e301b4c00eaf4372c8a3b8a0205cc/ghc >--------------------------------------------------------------- commit adc8e3531a5e301b4c00eaf4372c8a3b8a0205cc Author: Andrey Mokhov Date: Thu Sep 14 18:23:47 2017 +0100 Need rts at the top-level to allow more parallelism See #393 >--------------------------------------------------------------- adc8e3531a5e301b4c00eaf4372c8a3b8a0205cc src/Rules.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index fcf3f65..ea3df45 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -32,7 +32,7 @@ allStages = [minBound ..] -- 'Stage1Only' flag. topLevelTargets :: Rules () topLevelTargets = action $ do - let libraryPackages = filter isLibrary (knownPackages \\ [rts, libffi]) + let libraryPackages = filter isLibrary (knownPackages \\ [libffi]) need =<< if stage1Only then do libs <- concatForM [Stage0, Stage1] $ \stage -> @@ -41,11 +41,10 @@ topLevelTargets = action $ do return $ libs ++ prgs ++ inplaceLibCopyTargets else do targets <- concatForM allStages $ \stage -> - concatForM (knownPackages \\ [rts, libffi]) $ + concatForM (knownPackages \\ [libffi]) $ packageTargets False stage return $ targets ++ inplaceLibCopyTargets - -- TODO: Get rid of the @includeGhciLib@ hack. -- | Return the list of targets associated with a given 'Stage' and 'Package'. -- By setting the Boolean parameter to False it is possible to exclude the GHCi @@ -62,14 +61,15 @@ packageTargets includeGhciLib stage pkg = do then return [] -- Skip inactive packages. else if isLibrary pkg then do -- Collect all targets of a library package. - ways <- interpretInContext context getLibraryWays + let pkgWays = if pkg == rts then getRtsWays else getLibraryWays + ways <- interpretInContext context pkgWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context =<< buildHaddock <$> flavour more <- libraryTargets includeGhciLib context setup <- pkgSetupConfigFile context haddock <- pkgHaddockFile context - return $ [ setup | nonCabalContext context ] - ++ [ haddock | docs && stage == Stage1 ] + return $ [ setup | not $ nonCabalContext context ] + ++ [ haddock | pkg /= rts && docs && stage == Stage1 ] ++ libs ++ more else do -- The only target of a program package is the executable. prgContext <- programContext stage pkg From git at git.haskell.org Fri Oct 27 00:42:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use nm-classic when running on Travis (90e3e97) Message-ID: <20171027004223.665C03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/90e3e973e62788d98d47fc3942ecd8c50e7fe92b/ghc >--------------------------------------------------------------- commit 90e3e973e62788d98d47fc3942ecd8c50e7fe92b Author: Andrey Mokhov Date: Sat Oct 22 01:48:38 2016 +0100 Use nm-classic when running on Travis >--------------------------------------------------------------- 90e3e973e62788d98d47fc3942ecd8c50e7fe92b .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 217a7d5..187c009 100644 --- a/.travis.yml +++ b/.travis.yml @@ -41,7 +41,7 @@ install: - git reset --hard HEAD - cd .. - ./boot - - ./configure + - ./configure --with-nm=$(xcrun --find nm-classic) - cd hadrian script: From git at git.haskell.org Fri Oct 27 00:42:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (11f78b1) Message-ID: <20171027004225.4AF743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/11f78b18b914bb72e1f1cff75cadc9d7c4012ac2/ghc >--------------------------------------------------------------- commit 11f78b18b914bb72e1f1cff75cadc9d7c4012ac2 Author: Andrey Mokhov Date: Tue Jan 19 12:02:52 2016 +0000 Minor revision. [skip ci] >--------------------------------------------------------------- 11f78b18b914bb72e1f1cff75cadc9d7c4012ac2 src/Settings/Packages/Rts.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e41e2bf..f67b709 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,9 +20,9 @@ rtsConf = pkgPath rts -/- targetDirectory Stage1 rts -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do - use_system_ffi <- flag UseSystemFfi - windows <- windowsHost - case (use_system_ffi, windows) of + useSystemFfi <- flag UseSystemFfi + windows <- windowsHost + case (useSystemFfi, windows) of (True , False) -> return "ffi" (False, False) -> return "Cffi" (_ , True ) -> return "Cffi-6" From git at git.haskell.org Fri Oct 27 00:42:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise stage1 compiler (9a1b659) Message-ID: <20171027004226.7631E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a1b6591a9a91097ac93dd1d461d8fac2856ed66/ghc >--------------------------------------------------------------- commit 9a1b6591a9a91097ac93dd1d461d8fac2856ed66 Author: Andrey Mokhov Date: Fri Sep 15 00:46:38 2017 +0100 Optimise stage1 compiler See #393 >--------------------------------------------------------------- 9a1b6591a9a91097ac93dd1d461d8fac2856ed66 doc/flavours.md | 4 ++-- src/Settings/Flavours/Quickest.hs | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index 3bf0c30..042475e 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -61,9 +61,9 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O0
-H32m + -O - - + -O diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 3c507bc..88922ec 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -15,8 +15,8 @@ quickestArgs :: Args quickestArgs = sourceArgs $ SourceArgs { hsDefault = pure ["-O0", "-H64m"] , hsLibrary = mempty - , hsCompiler = mempty - , hsGhc = mempty } + , hsCompiler = stage0 ? arg "-O" + , hsGhc = stage0 ? arg "-O" } quickestRtsWays :: Ways quickestRtsWays = mconcat From git at git.haskell.org Fri Oct 27 00:42:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #276 from wereHamster/osx-use-nm-classic (99404de) Message-ID: <20171027004226.F22093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/99404defcfbec85ff25963f480e64c26adcb9f16/ghc >--------------------------------------------------------------- commit 99404defcfbec85ff25963f480e64c26adcb9f16 Merge: 90e3e97 3c31edc Author: Andrey Mokhov Date: Sat Oct 22 02:02:32 2016 +0100 Merge pull request #276 from wereHamster/osx-use-nm-classic Use nm-classic instead of nm when host is Darwin >--------------------------------------------------------------- 99404defcfbec85ff25963f480e64c26adcb9f16 README.md | 8 -------- src/Settings/Builders/Configure.hs | 7 +++++++ 2 files changed, 7 insertions(+), 8 deletions(-) From git at git.haskell.org Fri Oct 27 00:42:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: do not pass --with-intree-gmp to configure when system gmp is used (dc8dbcc) Message-ID: <20171027004229.4D3683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dc8dbcc5a9c621a3eb4fb99b0e7d24b2e1a5a967/ghc >--------------------------------------------------------------- commit dc8dbcc5a9c621a3eb4fb99b0e7d24b2e1a5a967 Author: Karel Gardas Date: Tue Jan 19 21:42:08 2016 +0100 do not pass --with-intree-gmp to configure when system gmp is used >--------------------------------------------------------------- dc8dbcc5a9c621a3eb4fb99b0e7d24b2e1a5a967 src/Settings/Packages/IntegerGmp.hs | 18 +++++++++++++----- 1 file changed, 13 insertions(+), 5 deletions(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 7122457..fbb7101 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -4,7 +4,9 @@ import Base import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) +import Settings.Builders.Common import Settings.Paths +import Oracles.Config.Setting -- TODO: move build artefacts to buildRootPath, see #113 -- TODO: Is this needed? @@ -14,11 +16,17 @@ import Settings.Paths integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" + gmp_includedir <- getSetting GmpIncludeDir + gmp_libdir <- getSetting GmpLibDir + let gmp_args = if (gmp_includedir == "" && gmp_libdir == "") + then + [ arg "--configure-option=--with-intree-gmp" ] + else + [] + mconcat [ builder GhcCabal ? mconcat - [ arg "--configure-option=--with-intree-gmp" - , appendSub "--configure-option=CFLAGS" [includeGmp] - , appendSub "--gcc-options" [includeGmp] ] + (gmp_args ++ + [ appendSub "--configure-option=CFLAGS" [includeGmp] + , appendSub "--gcc-options" [includeGmp] ] ) , builderGcc ? arg includeGmp ] - where - From git at git.haskell.org Fri Oct 27 00:42:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert to running the configure script from Hadrian (4378fcf) Message-ID: <20171027004231.5C57E3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4378fcfe96fc58328bb03378f45529e6d13a7122/ghc >--------------------------------------------------------------- commit 4378fcfe96fc58328bb03378f45529e6d13a7122 Author: Andrey Mokhov Date: Sat Oct 22 02:06:18 2016 +0100 Revert to running the configure script from Hadrian See #276. >--------------------------------------------------------------- 4378fcfe96fc58328bb03378f45529e6d13a7122 .travis.yml | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 187c009..0209cab 100644 --- a/.travis.yml +++ b/.travis.yml @@ -39,17 +39,13 @@ install: - mv .git ghc/hadrian - cd ghc/hadrian - git reset --hard HEAD - - cd .. - - ./boot - - ./configure --with-nm=$(xcrun --find nm-classic) - - cd hadrian script: # Run internal Hadrian tests - ./build.sh selftest # Build GHC - - ./build.sh -j --skip-configure --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.sh -j --flavour=quickest --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 00:42:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: remove redundant Settings.Builders.Common import (88af41c) Message-ID: <20171027004232.BD8D03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88af41cfff4e4c8e349693cdc423661a8f571c02/ghc >--------------------------------------------------------------- commit 88af41cfff4e4c8e349693cdc423661a8f571c02 Author: Karel Gardas Date: Tue Jan 19 22:06:12 2016 +0100 remove redundant Settings.Builders.Common import >--------------------------------------------------------------- 88af41cfff4e4c8e349693cdc423661a8f571c02 src/Settings/Packages/IntegerGmp.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index fbb7101..657eed0 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -4,7 +4,6 @@ import Base import Expression import GHC (integerGmp) import Predicates (builder, builderGcc, package) -import Settings.Builders.Common import Settings.Paths import Oracles.Config.Setting From git at git.haskell.org Fri Oct 27 00:42:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement documentation building (#413) (97fa508) Message-ID: <20171027004234.CD7203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d/ghc >--------------------------------------------------------------- commit 97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d Author: Patrick Dougherty Date: Sat Sep 16 07:14:30 2017 -0500 Implement documentation building (#413) * Implement documentation building * Clean up for merge >--------------------------------------------------------------- 97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d cfg/system.config.in | 3 +- hadrian.cabal | 2 + src/Builder.hs | 55 +++++++++++--- src/Context.hs | 6 +- src/Main.hs | 2 + src/Rules/Documentation.hs | 155 +++++++++++++++++++++++++++++++++++--- src/Rules/Gmp.hs | 2 +- src/Rules/Install.hs | 3 - src/Rules/Libffi.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 11 +-- src/Settings/Builders/Haddock.hs | 92 +++++++++++----------- src/Settings/Builders/Sphinx.hs | 22 ++++++ src/Settings/Builders/Tar.hs | 20 +++-- src/Settings/Builders/Xelatex.hs | 7 ++ src/Settings/Default.hs | 7 +- src/Settings/Packages/Compiler.hs | 2 +- 18 files changed, 298 insertions(+), 97 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 97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d From git at git.haskell.org Fri Oct 27 00:42:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix typo (2895999) Message-ID: <20171027004234.F0DEC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2895999d7ac18fe9f90e6f6feb47c4e71a84202f/ghc >--------------------------------------------------------------- commit 2895999d7ac18fe9f90e6f6feb47c4e71a84202f Author: Andrey Mokhov Date: Sat Oct 22 11:27:01 2016 +0100 Fix typo >--------------------------------------------------------------- 2895999d7ac18fe9f90e6f6feb47c4e71a84202f src/Settings/Builders/Configure.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 6482df1..deab649 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -26,8 +26,7 @@ configureBuilderArgs = mconcat , "--enable-shared=no" -- TODO: add support for yes , "--host=" ++ targetPlatform ] - -- On OS X, use "nm-classic" instead of "nm" due to a bug in the later. + -- On OS X, use "nm-classic" instead of "nm" due to a bug in the latter. -- See https://ghc.haskell.org/trac/ghc/ticket/11744 , builder (Configure ".") ? System.os == "darwin" ? - arg "--with-nm=$(xcrun --find nm-classic)" - ] + arg "--with-nm=$(xcrun --find nm-classic)" ] From git at git.haskell.org Fri Oct 27 00:42:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: simplify code and fix naming conventions based on Andrey's comments (06fb099) Message-ID: <20171027004236.3FF473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/06fb099d3fe8a253d79f7af4aa7d67cc5ef91bcc/ghc >--------------------------------------------------------------- commit 06fb099d3fe8a253d79f7af4aa7d67cc5ef91bcc Author: Karel Gardas Date: Tue Jan 19 22:27:36 2016 +0100 simplify code and fix naming conventions based on Andrey's comments >--------------------------------------------------------------- 06fb099d3fe8a253d79f7af4aa7d67cc5ef91bcc src/Settings/Packages/IntegerGmp.hs | 16 ++++++---------- 1 file changed, 6 insertions(+), 10 deletions(-) diff --git a/src/Settings/Packages/IntegerGmp.hs b/src/Settings/Packages/IntegerGmp.hs index 657eed0..9ad160f 100644 --- a/src/Settings/Packages/IntegerGmp.hs +++ b/src/Settings/Packages/IntegerGmp.hs @@ -15,17 +15,13 @@ import Oracles.Config.Setting integerGmpPackageArgs :: Args integerGmpPackageArgs = package integerGmp ? do let includeGmp = "-I" ++ gmpBuildPath -/- "include" - gmp_includedir <- getSetting GmpIncludeDir - gmp_libdir <- getSetting GmpLibDir - let gmp_args = if (gmp_includedir == "" && gmp_libdir == "") - then - [ arg "--configure-option=--with-intree-gmp" ] - else - [] + gmpIncludeDir <- getSetting GmpIncludeDir + gmpLibDir <- getSetting GmpLibDir mconcat [ builder GhcCabal ? mconcat - (gmp_args ++ - [ appendSub "--configure-option=CFLAGS" [includeGmp] - , appendSub "--gcc-options" [includeGmp] ] ) + [ (null gmpIncludeDir && null gmpLibDir) ? + arg "--configure-option=--with-intree-gmp" + , appendSub "--configure-option=CFLAGS" [includeGmp] + , appendSub "--gcc-options" [includeGmp] ] , builderGcc ? arg includeGmp ] From git at git.haskell.org Fri Oct 27 00:42:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid running commands with the Shell option, which breaks due to spaces in paths (f479c5d) Message-ID: <20171027004238.7F6AF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f479c5d51dfee88abaad7dc3aeb19ea518948a19/ghc >--------------------------------------------------------------- commit f479c5d51dfee88abaad7dc3aeb19ea518948a19 Author: Andrey Mokhov Date: Sun Sep 17 00:41:12 2017 +0100 Avoid running commands with the Shell option, which breaks due to spaces in paths * Fixes the docs build rule on Windows See #414 >--------------------------------------------------------------- f479c5d51dfee88abaad7dc3aeb19ea518948a19 src/Builder.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 72cbb15..355878f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -185,7 +185,7 @@ instance H.Builder Builder where -- otherwise Windows breaks. TODO: Figure out why. bash <- bashPath let env = AddEnv "CONFIG_SHELL" bash - cmd Shell echo env [Cwd dir] [path] buildOptions buildArgs + cmd echo env [Cwd dir] ["sh", path] buildOptions buildArgs HsCpp -> captureStdout GenApply -> captureStdout @@ -195,16 +195,15 @@ instance H.Builder Builder where Stdout stdout <- cmd (Stdin stdin) [path] buildArgs writeFileChanged output stdout - Make dir -> cmd Shell echo path ["-C", dir] buildArgs + Make dir -> cmd echo path ["-C", dir] buildArgs Xelatex -> do - unit $ cmd Shell [Cwd output] [path] buildArgs - unit $ cmd Shell [Cwd output] [path] buildArgs - unit $ cmd Shell [Cwd output] [path] buildArgs - unit $ cmd Shell [Cwd output] ["makeindex"] - (input -<.> "idx") - unit $ cmd Shell [Cwd output] [path] buildArgs - cmd Shell [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] ["makeindex"] (input -<.> "idx") + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs _ -> cmd echo [path] buildArgs @@ -226,7 +225,7 @@ systemBuilderPath builder = case builder of Cc _ Stage0 -> fromKey "system-cc" Cc _ _ -> fromKey "cc" -- We can't ask configure for the path to configure! - Configure _ -> return "sh configure" + Configure _ -> return "configure" Ghc _ Stage0 -> fromKey "system-ghc" GhcPkg _ Stage0 -> fromKey "system-ghc-pkg" Happy -> fromKey "happy" @@ -266,7 +265,7 @@ applyPatch dir patch = do needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file - quietly $ cmd Shell [Cwd dir] [path, "-p0 <", patch] + quietly $ cmd [Cwd dir, FileStdin file] [path, "-p0"] -- | Install a directory. installDirectory :: FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:42:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update docs to list -H64m (101d787) Message-ID: <20171027004231.4C3663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/101d78755ac2f1afd71eb7c9165afb9a84705c9a/ghc >--------------------------------------------------------------- commit 101d78755ac2f1afd71eb7c9165afb9a84705c9a Author: Andrey Mokhov Date: Fri Sep 15 01:24:53 2017 +0100 Update docs to list -H64m [skip ci] >--------------------------------------------------------------- 101d78755ac2f1afd71eb7c9165afb9a84705c9a doc/flavours.md | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index 042475e..185cf6b 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -35,8 +35,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH default
- -O
-H32m
- -O2
-H32m + -O
-H64m
+ -O2
-H64m @@ -46,8 +46,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quick - -O0
-H32m - -O0
-H32m + -O0
-H64m + -O0
-H64m -O -O @@ -57,8 +57,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quickest - -O0
-H32m - -O0
-H32m + -O0
-H64m + -O0
-H64m -O @@ -68,8 +68,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH perf - -O
-H32m - -O
-H32m + -O
-H64m + -O
-H64m -O2 -O @@ -79,8 +79,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH prof - -O0
-H32m - -O0
-H32m + -O0
-H64m + -O0
-H64m -O -O @@ -90,8 +90,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel1 - -O
-H32m - -O
-H32m + -O
-H64m + -O
-H64m -dcore-lint -O0
-DDEBUG @@ -101,8 +101,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel2 - -O
-H32m - -O
-H32m + -O
-H64m + -O
-H64m -dcore-lint From git at git.haskell.org Fri Oct 27 00:42:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move package.conf.inplace to build directory (038dfb4) Message-ID: <20171027004238.767693A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/038dfb43604a5316e0b44f745e9367a09fb6a217/ghc >--------------------------------------------------------------- commit 038dfb43604a5316e0b44f745e9367a09fb6a217 Author: Andrey Mokhov Date: Sat Oct 22 23:47:39 2016 +0100 Move package.conf.inplace to build directory >--------------------------------------------------------------- 038dfb43604a5316e0b44f745e9367a09fb6a217 src/Settings/Packages/Rts.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index f3f2e43..f2b4035 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -9,13 +9,13 @@ import Oracles.Config.Setting import Oracles.WindowsPath import Predicate import Settings +import Settings.Paths rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" --- TODO: move to buildRootPath, see #113 rtsConf :: FilePath -rtsConf = pkgPath rts -/- contextDirectory rtsContext -/- "package.conf.inplace" +rtsConf = buildPath rtsContext -/- "package.conf.inplace" rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do From git at git.haskell.org Fri Oct 27 00:42:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #185 from kgardas/fix_gmp_cabal_args (30883f8) Message-ID: <20171027004239.B63433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30883f8d1e5289a8b90213ebfee0ee99e1712899/ghc >--------------------------------------------------------------- commit 30883f8d1e5289a8b90213ebfee0ee99e1712899 Merge: 11f78b1 06fb099 Author: Andrey Mokhov Date: Tue Jan 19 22:49:58 2016 +0000 Merge pull request #185 from kgardas/fix_gmp_cabal_args do not pass --with-intree-gmp to configure when system gmp is used >--------------------------------------------------------------- 30883f8d1e5289a8b90213ebfee0ee99e1712899 src/Settings/Packages/IntegerGmp.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 27 00:42:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Config.hs to import GhcPrelude (#417) (fcdecad) Message-ID: <20171027004242.6675C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fcdecad4f1ab2f5a6126013004211acef23cf775/ghc >--------------------------------------------------------------- commit fcdecad4f1ab2f5a6126013004211acef23cf775 Author: Zhen Zhang Date: Thu Sep 21 00:47:21 2017 +0800 Fix Config.hs to import GhcPrelude (#417) >--------------------------------------------------------------- fcdecad4f1ab2f5a6126013004211acef23cf775 src/Rules/Generate.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 413abe5..e777e1b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -291,6 +291,8 @@ generateConfigHs = do [ "{-# LANGUAGE CPP #-}" , "module Config where" , "" + , "import GhcPrelude" + , "" , "#include \"ghc_boot_platform.h\"" , "" , "data IntegerLibrary = IntegerGMP" From git at git.haskell.org Fri Oct 27 00:42:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor CmdLineFlag.hs. (c50e0dc) Message-ID: <20171027004243.A43EF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c50e0dc4eb0200dae1d4b50e824db4764e95b827/ghc >--------------------------------------------------------------- commit c50e0dc4eb0200dae1d4b50e824db4764e95b827 Author: Andrey Mokhov Date: Wed Jan 20 00:11:45 2016 +0000 Refactor CmdLineFlag.hs. >--------------------------------------------------------------- c50e0dc4eb0200dae1d4b50e824db4764e95b827 shaking-up-ghc.cabal | 2 +- src/CmdLineFlag.hs | 56 +++++++++++++++++++++++++++++++++++++++ src/Main.hs | 9 ++++--- src/Oracles/Config/CmdLineFlag.hs | 55 -------------------------------------- src/Rules/Actions.hs | 33 ++++++++++++----------- 5 files changed, 80 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 c50e0dc4eb0200dae1d4b50e824db4764e95b827 From git at git.haskell.org Fri Oct 27 00:42:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve code consistency, simplify, fix comments (9d13cd8) Message-ID: <20171027004246.1D6783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9d13cd844b9eabbb5d826a9f518c27bb8756b390/ghc >--------------------------------------------------------------- commit 9d13cd844b9eabbb5d826a9f518c27bb8756b390 Author: Andrey Mokhov Date: Sun Oct 23 01:03:22 2016 +0100 Improve code consistency, simplify, fix comments >--------------------------------------------------------------- 9d13cd844b9eabbb5d826a9f518c27bb8756b390 src/Builder.hs | 31 ++++++++++++++----------------- src/Context.hs | 4 ++-- src/Package.hs | 4 +--- src/Rules/Cabal.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Perl.hs | 5 ++--- src/Settings/Builders/Ar.hs | 1 - src/Settings/Builders/Cc.hs | 12 ++++-------- src/Settings/Builders/GenApply.hs | 1 - src/Settings/Builders/GenPrimopCode.hs | 1 - src/Settings/Builders/GhcCabal.hs | 1 - src/Settings/Builders/HsCpp.hs | 6 +++--- src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Builders/Ld.hs | 11 +++++------ src/Settings/Builders/Tar.hs | 11 +++++------ src/Stage.hs | 3 +-- src/Target.hs | 5 ++--- src/Way.hs | 1 - 19 files changed, 43 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 9d13cd844b9eabbb5d826a9f518c27bb8756b390 From git at git.haskell.org Fri Oct 27 00:42:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update shake and add stm to stage1 packages (#419) (907cad6) Message-ID: <20171027004246.8921E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/907cad60863a4ea2b940fa7aa6c73b0da82eab7c/ghc >--------------------------------------------------------------- commit 907cad60863a4ea2b940fa7aa6c73b0da82eab7c Author: Zhen Zhang Date: Fri Sep 22 17:53:09 2017 +0800 Update shake and add stm to stage1 packages (#419) * Update shake * Add stm to Stage 1 packages >--------------------------------------------------------------- 907cad60863a4ea2b940fa7aa6c73b0da82eab7c hadrian.cabal | 2 +- src/GHC.hs | 1 + src/Hadrian/Utilities.hs | 6 ------ stack.yaml | 3 +++ 4 files changed, 5 insertions(+), 7 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index b01d866..97b283a 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -124,7 +124,7 @@ executable hadrian , extra >= 1.4.7 , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.10 - , shake >= 0.15.6 + , shake == 0.16.* , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* build-tools: alex >= 3.1 diff --git a/src/GHC.hs b/src/GHC.hs index ab6f93b..32676cd 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -191,6 +191,7 @@ stage1Packages = do , process , rts , runGhc + , stm , time ] ++ [ iservBin | not win ] ++ [ unix | not win ] diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 8f6f4cc..06ee663 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -25,9 +25,6 @@ module Hadrian.Utilities ( putProgressInfo, renderAction, renderProgram, renderLibrary, renderBox, renderUnicorn, - -- * Shake compatibility - RuleResult, - -- * Miscellaneous (<&>), (%%>), cmdLineLengthLimit, @@ -183,9 +180,6 @@ buildRoot = do infixl 1 <&> --- | Introduced in shake-0.16, so use to make the rest of the code compatible -type family RuleResult a - -- | Given a 'FilePath' to a source file, return 'True' if it is generated. -- The current implementation simply assumes that a file is generated if it -- lives in the 'buildRoot' directory. Since most files are not generated the diff --git a/stack.yaml b/stack.yaml index a05f2cd..2a92f26 100644 --- a/stack.yaml +++ b/stack.yaml @@ -8,6 +8,9 @@ packages: - '.' - '../libraries/Cabal/Cabal' +extra-deps: +- shake-0.16 + nix: packages: - autoconf From git at git.haskell.org Fri Oct 27 00:42:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify (f52e582) Message-ID: <20171027004242.325443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f52e582d9cc21ad369411dc7bc832332e97ff224/ghc >--------------------------------------------------------------- commit f52e582d9cc21ad369411dc7bc832332e97ff224 Author: Andrey Mokhov Date: Sun Oct 23 00:41:23 2016 +0100 Simplify See #265 >--------------------------------------------------------------- f52e582d9cc21ad369411dc7bc832332e97ff224 src/Oracles/DirectoryContent.hs | 41 ++++++++++++++++++----------------------- src/Rules/Actions.hs | 13 ++++++------- 2 files changed, 24 insertions(+), 30 deletions(-) diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContent.hs index 45afa92..3139c6c 100644 --- a/src/Oracles/DirectoryContent.hs +++ b/src/Oracles/DirectoryContent.hs @@ -1,39 +1,34 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} module Oracles.DirectoryContent ( - getDirectoryContent, directoryContentOracle, Match(..) + directoryContent, directoryContentOracle, Match (..) ) where -import Base -import GHC.Generics import System.Directory.Extra +import GHC.Generics + +import Base newtype DirectoryContent = DirectoryContent (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -data Match = Test FilePattern | Not (Match) | And [Match] | Or [Match] +data Match = Test FilePattern | Not Match | And [Match] | Or [Match] deriving (Generic, Eq, Show, Typeable) -instance Binary Match -instance Hashable Match -instance NFData Match matches :: Match -> FilePath -> Bool -matches (Test m) f = m ?== f -matches (Not m) f = not $ matches m f -matches (And []) _ = True -matches (And (m:ms)) f | matches m f = matches (And ms) f - | otherwise = False -matches (Or []) _ = False -matches (Or (m:ms)) f | matches m f = True - | otherwise = matches (Or ms) f +matches (Test p) f = p ?== f +matches (Not m) f = not $ matches m f +matches (And ms) f = all (`matches` f) ms +matches (Or ms) f = any (`matches` f) ms -- | Get the directory content recursively. -getDirectoryContent :: Match -> FilePath -> Action [FilePath] -getDirectoryContent expr dir = - askOracle $ DirectoryContent (expr, dir) +directoryContent :: Match -> FilePath -> Action [FilePath] +directoryContent expr dir = askOracle $ DirectoryContent (expr, dir) directoryContentOracle :: Rules () -directoryContentOracle = void $ addOracle oracle - where - oracle :: DirectoryContent -> Action [FilePath] - oracle (DirectoryContent (expr, dir)) = - liftIO $ filter (matches expr) <$> listFilesInside (return . matches expr) dir +directoryContentOracle = void $ + addOracle $ \(DirectoryContent (expr, dir)) -> liftIO $ + filter (matches expr) <$> listFilesInside (return . matches expr) dir + +instance Binary Match +instance Hashable Match +instance NFData Match diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index e30bc01..cccda24 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -45,8 +45,7 @@ customBuild rs opts target at Target {..} = do argList <- interpret target getArgs verbose <- interpret target verboseCommands let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly - -- The line below forces the rule to be rerun if the args hash has changed. - checkArgsHash target + checkArgsHash target -- Rerun the rule if the hash of argList has changed. withResources rs $ do putInfo target quietlyUnlessVerbose $ case builder of @@ -133,12 +132,12 @@ copyDirectory source target = do copyDirectoryContent :: Match -> FilePath -> FilePath -> Action () copyDirectoryContent expr source target = do putProgressInfo $ renderAction "Copy directory content" source target - getDirectoryContent expr source >>= mapM_ cp + mapM_ cp =<< directoryContent expr source where - cp a = do - createDirectory $ dropFileName $ target' a - copyFile a $ target' a - target' a = target -/- fromJust (stripPrefix source a) + cp file = do + let newFile = target -/- drop (length source) file + createDirectory $ dropFileName newFile -- TODO: Why do it for each file? + copyFile file newFile -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:42:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision. (e7377d1) Message-ID: <20171027004247.4408F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7377d1113d34ca56881cfc46b25e2ad8a6ba3aa/ghc >--------------------------------------------------------------- commit e7377d1113d34ca56881cfc46b25e2ad8a6ba3aa Author: Andrey Mokhov Date: Wed Jan 20 00:33:27 2016 +0000 Minor revision. [skip ci] >--------------------------------------------------------------- e7377d1113d34ca56881cfc46b25e2ad8a6ba3aa src/Expression.hs | 59 ++++++++++++++++++++++++++++--------------------------- 1 file changed, 30 insertions(+), 29 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 932ed80..1d1dc27 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -36,17 +36,18 @@ import Stage import Target import Way --- | @Expr a@ is a computation that produces a value of type @Action a@ and can read --- parameters of the current build 'Target'. +-- | @Expr a@ is a computation that produces a value of type @Action a@ and can +-- read parameters of the current build 'Target'. type Expr a = ReaderT Target Action a -- | @Diff a@ is a /difference list/ containing values of type @a at . A difference --- list is a list with efficient concatenation, encoded as a value @a -> a at . --- We could use @Dual (Endo a)@ instead of @Diff a@, but the former may look scary. +-- list is a list with efficient concatenation, encoded as a value @a -> a at . We +-- could use @Dual (Endo a)@ instead of @Diff a@, but the former may look scary. newtype Diff a = Diff { fromDiff :: a -> a } --- | @DiffExpr a@ is a computation that builds a difference list (i.e., a function --- of type @'Action' (a -> a)@) and can read parameters of the current build ''Target'. +-- | @DiffExpr a@ is a computation that builds a difference list (i.e., a +-- function of type @'Action' (a -> a)@) and can read parameters of the current +-- build 'Target'. type DiffExpr a = Expr (Diff a) -- Note the reverse order of function composition (y . x), which ensures that @@ -65,19 +66,19 @@ type Packages = DiffExpr [Package] type Ways = DiffExpr [Way] -- Basic operations on expressions: --- | Transform an expression by applying a given function +-- | Transform an expression by applying a given function. apply :: (a -> a) -> DiffExpr a apply = return . Diff --- | Append something to an expression +-- | Append something to an expression. append :: Monoid a => a -> DiffExpr a append x = apply (<> x) --- | Remove given elements from a list expression +-- | Remove given elements from a list expression. remove :: Eq a => [a] -> DiffExpr [a] remove xs = apply $ filter (`notElem` xs) --- | Remove given pair of elements from a list expression +-- | Remove given pair of elements from a list expression. -- Example: removePair "-flag" "b" ["-flag", "a", "-flag", "b"] = ["-flag", "a"] removePair :: Eq a => a -> a -> DiffExpr [a] removePair x y = apply filterPair @@ -87,30 +88,30 @@ removePair x y = apply filterPair else z1 : filterPair (z2 : zs) filterPair zs = zs --- | Apply a predicate to an expression +-- | Apply a predicate to an expression. applyPredicate :: Monoid a => Predicate -> Expr a -> Expr a applyPredicate predicate expr = do bool <- predicate if bool then expr else return mempty --- | Add a single argument to 'Args' +-- | Add a single argument to 'Args'. arg :: String -> Args arg = append . return --- | A convenient operator for predicate application +-- | A convenient operator for predicate application. class PredicateLike a where - (?) :: Monoid m => a -> Expr m -> Expr m + (?) :: Monoid m => a -> Expr m -> Expr m infixr 8 ? instance PredicateLike Predicate where - (?) = applyPredicate + (?) = applyPredicate instance PredicateLike Bool where - (?) = applyPredicate . return + (?) = applyPredicate . return instance PredicateLike (Action Bool) where - (?) = applyPredicate . lift + (?) = applyPredicate . lift -- | @appendSub@ appends a list of sub-arguments to all arguments starting with a -- given prefix. If there is no argument with such prefix then a new argument @@ -141,11 +142,11 @@ filterSub prefix p = apply $ map filterSubstr | otherwise = s -- | Remove given elements from a list of sub-arguments with a given prefix --- Example: removeSub "--configure-option=CFLAGS" ["-Werror"] +-- Example: removeSub "--configure-option=CFLAGS" ["-Werror"]. removeSub :: String -> [String] -> Args removeSub prefix xs = filterSub prefix (`notElem` xs) --- | Interpret a given expression in a given environment +-- | Interpret a given expression in a given environment. interpret :: Target -> Expr a -> Action a interpret = flip runReaderT @@ -156,46 +157,46 @@ interpretWithStage :: Stage -> Expr a -> Action a interpretWithStage s = interpretPartial $ PartialTarget s (error "interpretWithStage: package not set") --- | Extract an expression from a difference expression +-- | Extract an expression from a difference expression. fromDiffExpr :: Monoid a => DiffExpr a -> Expr a fromDiffExpr = fmap (($ mempty) . fromDiff) --- | Interpret a given difference expression in a given environment +-- | Interpret a given difference expression in a given environment. interpretDiff :: Monoid a => Target -> DiffExpr a -> Action a interpretDiff target = interpret target . fromDiffExpr --- | Convenient getters for target parameters +-- | Convenient getters for target parameters. getStage :: Expr Stage getStage = asks stage --- | Get the 'Package' of the current 'Target' +-- | Get the 'Package' of the current 'Target'. getPackage :: Expr Package getPackage = asks package --- | Get the 'Builder' for the current 'Target' +-- | Get the 'Builder' for the current 'Target'. getBuilder :: Expr Builder getBuilder = asks builder --- | Get the 'Way' of the current 'Target' +-- | Get the 'Way' of the current 'Target'. getWay :: Expr Way getWay = asks way --- | Get the input files of the current 'Target' +-- | Get the input files of the current 'Target'. getInputs :: Expr [FilePath] getInputs = asks inputs --- | Run 'getInputs' and check that the result contains a single input file only +-- | Run 'getInputs' and check that the result contains one input file only. getInput :: Expr FilePath getInput = do target <- ask getSingleton getInputs $ "getInput: exactly one input file expected in target " ++ show target --- | Get the files produced by the current 'Target' +-- | Get the files produced by the current 'Target'. getOutputs :: Expr [FilePath] getOutputs = asks outputs --- | Run 'getOutputs' and check that the result contains a output file only +-- | Run 'getOutputs' and check that the result contains one output file only. getOutput :: Expr FilePath getOutput = do target <- ask From git at git.haskell.org Fri Oct 27 00:42:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor imports in Settings/Builders (2f74254) Message-ID: <20171027004249.B94093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc/ghc >--------------------------------------------------------------- commit 2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc Author: Andrey Mokhov Date: Sun Oct 23 01:25:50 2016 +0100 Refactor imports in Settings/Builders >--------------------------------------------------------------- 2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc src/Rules/Libffi.hs | 9 --------- src/Settings/Builders/Alex.hs | 2 +- src/Settings/Builders/Ar.hs | 5 +---- src/Settings/Builders/Cc.hs | 5 ----- src/Settings/Builders/Common.hs | 25 ++++++++++++++++++++++++- src/Settings/Builders/Configure.hs | 6 +----- src/Settings/Builders/DeriveConstants.hs | 5 ----- src/Settings/Builders/GenApply.hs | 2 +- src/Settings/Builders/GenPrimopCode.hs | 2 +- src/Settings/Builders/Ghc.hs | 9 --------- src/Settings/Builders/GhcCabal.hs | 19 +------------------ src/Settings/Builders/GhcPkg.hs | 6 +----- src/Settings/Builders/Haddock.hs | 7 +------ src/Settings/Builders/Happy.hs | 2 +- src/Settings/Builders/HsCpp.hs | 4 ---- src/Settings/Builders/Hsc2Hs.hs | 7 ------- src/Settings/Builders/Ld.hs | 2 -- src/Settings/Builders/Make.hs | 4 +--- src/Settings/Builders/Tar.hs | 2 +- 19 files changed, 35 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 2f7425482adb002ffce4bb2c4f9fa0103cfd2bdc From git at git.haskell.org Fri Oct 27 00:42:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Complete RTS compiler args (#418) (706d35e) Message-ID: <20171027004250.1EEBD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/706d35ea81f8f290f21ab9ab6869b3e4cc575056/ghc >--------------------------------------------------------------- commit 706d35ea81f8f290f21ab9ab6869b3e4cc575056 Author: Zhen Zhang Date: Sun Sep 24 03:55:22 2017 +0800 Complete RTS compiler args (#418) >--------------------------------------------------------------- 706d35ea81f8f290f21ab9ab6869b3e4cc575056 cfg/system.config.in | 1 + src/Oracles/Flag.hs | 2 + src/Settings/Packages/Rts.hs | 227 ++++++++++++++++++------------------------- 3 files changed, 95 insertions(+), 135 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 706d35ea81f8f290f21ab9ab6869b3e4cc575056 From git at git.haskell.org Fri Oct 27 00:42:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:50 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for --split-object command line flag. (87c6fae) Message-ID: <20171027004250.CE1993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/87c6fae6c8073315ca8f5aba0e2e5501500437db/ghc >--------------------------------------------------------------- commit 87c6fae6c8073315ca8f5aba0e2e5501500437db Author: Andrey Mokhov Date: Wed Jan 20 01:00:50 2016 +0000 Add support for --split-object command line flag. See #132. >--------------------------------------------------------------- 87c6fae6c8073315ca8f5aba0e2e5501500437db src/CmdLineFlag.hs | 22 ++++++++++++++++------ src/Settings/User.hs | 8 ++++++-- 2 files changed, 22 insertions(+), 8 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 444940a..05b74e5 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,5 +1,5 @@ module CmdLineFlag ( - putCmdLineFlags, flags, cmdProgressInfo, ProgressInfo (..) + putCmdLineFlags, flags, cmdProgressInfo, ProgressInfo (..), cmdSplitObjects ) where import Base @@ -16,13 +16,15 @@ data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -- command line. These flags are not tracked, that is they do not force any -- build rules to be rurun. data Untracked = Untracked - { progressInfo :: ProgressInfo } + { progressInfo :: ProgressInfo + , splitObjects :: Bool } deriving (Eq, Show) -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked defaultUntracked = Untracked - { progressInfo = Normal } + { progressInfo = Normal + , splitObjects = False } readProgressInfo :: Maybe String -> Either String (Untracked -> Untracked) readProgressInfo ms = @@ -35,11 +37,16 @@ readProgressInfo ms = go "unicorn" = Just Unicorn go _ = Nothing -- Left "no parse" mkClosure :: ProgressInfo -> Untracked -> Untracked - mkClosure flag opts = opts { progressInfo = flag } + mkClosure flag flags = flags { progressInfo = flag } + +readSplitObjects :: Either String (Untracked -> Untracked) +readSplitObjects = Right $ \flags -> flags { splitObjects = True } flags :: [OptDescr (Either String (Untracked -> Untracked))] flags = [ Option [] ["progress-info"] (OptArg readProgressInfo "") - "Progress Info Style (None, Brief, Normal, or Unicorn)" ] + "Progress Info Style (None, Brief, Normal, or Unicorn)" + , Option [] ["split-objects"] (NoArg readSplitObjects) + "Generate split objects (requires a full clean rebuild)." ] -- TODO: Get rid of unsafePerformIO by using shakeExtra. {-# NOINLINE cmdLineFlags #-} @@ -47,10 +54,13 @@ cmdLineFlags :: IORef Untracked cmdLineFlags = unsafePerformIO $ newIORef defaultUntracked putCmdLineFlags :: [Untracked -> Untracked] -> IO () -putCmdLineFlags opts = modifyIORef cmdLineFlags (\o -> foldl (flip id) o opts) +putCmdLineFlags flags = modifyIORef cmdLineFlags (\f -> foldl (flip id) f flags) getCmdLineFlags :: Action Untracked getCmdLineFlags = liftIO $ readIORef cmdLineFlags cmdProgressInfo :: Action ProgressInfo cmdProgressInfo = progressInfo <$> getCmdLineFlags + +cmdSplitObjects :: Action Bool +cmdSplitObjects = splitObjects <$> getCmdLineFlags diff --git a/src/Settings/User.hs b/src/Settings/User.hs index fb6ffb6..096f6ef 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -6,9 +6,12 @@ module Settings.User ( verboseCommands, turnWarningsIntoErrors, splitObjects ) where +import Base +import CmdLineFlag import GHC import Expression import Predicates +import Settings.Default -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath @@ -55,9 +58,10 @@ trackBuildSystem = True validating :: Bool validating = False --- To switch on split objects use 'splitObjects = defaultSplitObjects', see #153 +-- | Control when split objects are generated. Note, due to the GHC bug #11315 +-- it is necessary to do a full clean rebuild when changing this option. splitObjects :: Predicate -splitObjects = return False +splitObjects = (lift $ cmdSplitObjects) &&^ defaultSplitObjects dynamicGhcPrograms :: Bool dynamicGhcPrograms = False From git at git.haskell.org Fri Oct 27 00:42:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix GenApply arguments (e3aedfe) Message-ID: <20171027004253.5B12B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3aedfef1d68e98b59d19307203a16895ac98de6/ghc >--------------------------------------------------------------- commit e3aedfef1d68e98b59d19307203a16895ac98de6 Author: Andrey Mokhov Date: Sun Oct 23 01:58:24 2016 +0100 Fix GenApply arguments >--------------------------------------------------------------- e3aedfef1d68e98b59d19307203a16895ac98de6 src/Settings/Builders/GenApply.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Settings/Builders/GenApply.hs b/src/Settings/Builders/GenApply.hs index 6ebb295..b268c07 100644 --- a/src/Settings/Builders/GenApply.hs +++ b/src/Settings/Builders/GenApply.hs @@ -2,6 +2,5 @@ module Settings.Builders.GenApply (genApplyBuilderArgs) where import Settings.Builders.Common --- TODO: Dead code? ifeq "$(GhcUnregisterised)" "YES" GENAPPLY_OPTS = -u genApplyBuilderArgs :: Args -genApplyBuilderArgs = mempty +genApplyBuilderArgs = builder GenApply ? flag GhcUnregisterised ? arg "-u" From git at git.haskell.org Fri Oct 27 00:42:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant import (07b7d5f) Message-ID: <20171027004253.959BD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/07b7d5fcd2890137e2d71e1b136d8cc0da0fa1ad/ghc >--------------------------------------------------------------- commit 07b7d5fcd2890137e2d71e1b136d8cc0da0fa1ad Author: Andrey Mokhov Date: Sat Sep 23 23:06:26 2017 +0200 Drop redundant import >--------------------------------------------------------------- 07b7d5fcd2890137e2d71e1b136d8cc0da0fa1ad src/Hadrian/Oracles/ArgsHash.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index da13a95..bae2fdb 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -9,7 +9,6 @@ import Development.Shake.Classes import Hadrian.Expression hiding (inputs, outputs) import Hadrian.Target -import Hadrian.Utilities -- | 'TrackArgument' is used to specify the arguments that should be tracked by -- the @ArgsHash@ oracle. The safest option is to track all arguments, but some From git at git.haskell.org Fri Oct 27 00:42:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't generate files into the source tree (7303fcf) Message-ID: <20171027004257.49AF13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7303fcf142de20186728a5b7fdea62e5a8fc83d6/ghc >--------------------------------------------------------------- commit 7303fcf142de20186728a5b7fdea62e5a8fc83d6 Author: Andrey Mokhov Date: Sun Oct 23 02:27:32 2016 +0100 Don't generate files into the source tree See #113. >--------------------------------------------------------------- 7303fcf142de20186728a5b7fdea62e5a8fc83d6 src/Rules/Generate.hs | 10 ---------- 1 file changed, 10 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 0a4305c..698299d 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -143,24 +143,14 @@ generatePackageCode context@(Context stage pkg _) = build $ Target context GenApply [] [file] priority 2.0 $ do - -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- contextDirectory context -/- "build" - olden f = oldPath ++ (drop (length (buildPath context)) f) - when (pkg == compiler) $ path -/- "Config.hs" %> \file -> do file <~ generateConfigHs - olden file <~ generateConfigHs -- TODO: get rid of this (#113) when (pkg == compiler) $ platformH stage %> \file -> do file <~ generateGhcBootPlatformH when (pkg == ghcPkg) $ path -/- "Version.hs" %> \file -> do file <~ generateVersionHs - olden file <~ generateVersionHs -- TODO: get rid of this (#113) - - when (pkg == runGhc) $ path -/- "Main.hs" %> \file -> do - copyFileChanged (pkgPath pkg -/- "runghc.hs") file - putSuccess $ "| Successfully generated " ++ file ++ "." copyRules :: Rules () copyRules = do From git at git.haskell.org Fri Oct 27 00:42:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:57 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add RTS args related to libffi (6abbbd0) Message-ID: <20171027004257.E7E253A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6abbbd0696f55f8d6b7bcd33c4c4915f934b4045/ghc >--------------------------------------------------------------- commit 6abbbd0696f55f8d6b7bcd33c4c4915f934b4045 Author: Andrey Mokhov Date: Mon Sep 25 22:27:47 2017 +0200 Add RTS args related to libffi >--------------------------------------------------------------- 6abbbd0696f55f8d6b7bcd33c4c4915f934b4045 src/Settings/Packages/Rts.hs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 10940e4..c9d6359 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -38,15 +38,14 @@ rtsLibffiLibraryName = do (False, False) -> "Cffi" (_ , True ) -> "Cffi-6" -rtsLibffiIncludeArgs :: Args -rtsLibffiIncludeArgs = package libffi ? builder (Ghc CompileCWithGhc) ? do - useSystemFfi <- expr $ flag UseSystemFfi - ffiIncludeDir <- getSetting FfiIncludeDir - mconcat [ - useSystemFfi ? pure (map ("-I" ++) $ words ffiIncludeDir), - -- ffi.h triggers prototype warnings, so disable them here: - inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? - arg "-Wno-strict-prototypes" ] +rtsLibffiArgs :: Args +rtsLibffiArgs = builder (Ghc CompileCWithGhc) ? do + useSystemFfi <- expr $ flag UseSystemFfi + ffiIncludeDir <- getSetting FfiIncludeDir + mconcat [ useSystemFfi ? pure (map ("-I" ++) $ words ffiIncludeDir) + -- ffi.h triggers prototype warnings, so we disable them here + , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? + arg "-Wno-strict-prototypes" ] rtsLibffiLibrary :: Way -> Action FilePath rtsLibffiLibrary way = do @@ -195,7 +194,8 @@ rtsPackageArgs = package rts ? do , ghcRtsWithLibDw ? arg "-DUSE_LIBDW" ] mconcat - [ builder (Cc FindCDependencies) ? mconcat cArgs + [ rtsLibffiArgs + , builder (Cc FindCDependencies) ? mconcat cArgs , builder (Ghc CompileCWithGhc) ? mconcat (map (map ("-optc" ++) <$>) cArgs) , builder Ghc ? arg "-Irts" , builder HsCpp ? pure From git at git.haskell.org Fri Oct 27 00:42:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add initial support for --configure command line flag. (e874fed) Message-ID: <20171027004254.600983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e874fed8e68f9941d2cbd0ed4a64680a7f09586f/ghc >--------------------------------------------------------------- commit e874fed8e68f9941d2cbd0ed4a64680a7f09586f Author: Andrey Mokhov Date: Thu Jan 21 11:13:34 2016 +0000 Add initial support for --configure command line flag. >--------------------------------------------------------------- e874fed8e68f9941d2cbd0ed4a64680a7f09586f src/CmdLineFlag.hs | 56 +++++++++++++++++++++++++++++++++++----------------- src/Rules/Actions.hs | 39 ++++++++++++++++++------------------ src/Rules/Cabal.hs | 1 - src/Rules/Config.hs | 21 ++++++++++---------- src/Settings/User.hs | 9 +++------ 5 files changed, 72 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 e874fed8e68f9941d2cbd0ed4a64680a7f09586f From git at git.haskell.org Fri Oct 27 00:43:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build runGhc executable (b2f49f0) Message-ID: <20171027004301.D237A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2f49f06bbcda51400711d6370d1a276f01087da/ghc >--------------------------------------------------------------- commit b2f49f06bbcda51400711d6370d1a276f01087da Author: Andrey Mokhov Date: Sun Oct 23 02:35:58 2016 +0100 Build runGhc executable >--------------------------------------------------------------- b2f49f06bbcda51400711d6370d1a276f01087da src/GHC.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/GHC.hs b/src/GHC.hs index 3521e54..7cabff5 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -114,6 +114,9 @@ programPath context at Context {..} | package == hpcBin = case stage of Stage1 -> Just $ inplaceProgram "hpc" _ -> Nothing + | package == runGhc = case stage of + Stage1 -> Just $ inplaceProgram "runhaskell" + _ -> Nothing | isProgram package = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package _ -> Just . installProgram $ pkgNameString package From git at git.haskell.org Fri Oct 27 00:43:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop outdated RTS arguments, fix Windows build (0e193c0) Message-ID: <20171027004302.E657B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0e193c084f1ee8d9f044e612b319cf9963a5053d/ghc >--------------------------------------------------------------- commit 0e193c084f1ee8d9f044e612b319cf9963a5053d Author: Andrey Mokhov Date: Tue Sep 26 20:17:50 2017 +0200 Drop outdated RTS arguments, fix Windows build >--------------------------------------------------------------- 0e193c084f1ee8d9f044e612b319cf9963a5053d src/Settings/Packages/Rts.hs | 14 ++------------ 1 file changed, 2 insertions(+), 12 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index c9d6359..c71b729 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -54,13 +54,6 @@ rtsLibffiLibrary way = do rtsPath <- rtsBuildPath return $ rtsPath -/- "lib" ++ name ++ suf --- ref: mk/config.mk.in -ghcRtsWithLibDw :: Action Bool -ghcRtsWithLibDw = do - goodArch <- anyTargetArch ["i386", "x86_64"] - withLibDw <- flag HaveLibMingwEx - return $ goodArch && withLibDw - -- Compile various performance-critical pieces *without* -fPIC -dynamic -- even when building a shared library. If we don't do this, then the -- GC runs about 50% slower on x86 due to the overheads of PIC. The @@ -190,8 +183,7 @@ rtsPackageArgs = package rts ? do , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr" , input "//RetainerProfile.c" ? flag GccIsClang ? pure [ "-Wno-incompatible-pointer-types" ] - , targetOs == "mingw32" ? arg ("-DWINVER=" ++ rtsWindowsVersion) - , ghcRtsWithLibDw ? arg "-DUSE_LIBDW" ] + , windowsHost ? arg ("-DWINVER=" ++ rtsWindowsVersion) ] mconcat [ rtsLibffiArgs @@ -210,6 +202,4 @@ rtsPackageArgs = package rts ? do pure [ "-DINSTALLING" , "-DLIB_DIR=\"" ++ destDir ++ ghclibDir ++ "\"" , "-DINCLUDE_DIR=\"" ++ destDir ++ ghclibDir -/- "include\"" ] - , builder HsCpp ? mconcat - [ ghcRtsWithLibDw ? arg "-DUSE_LIBDW" - , flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ] ] + , builder HsCpp ? flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ] From git at git.haskell.org Fri Oct 27 00:42:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:42:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add full support for --configure command line flag. (4460146) Message-ID: <20171027004258.6938F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/446014681874982a340c245d3c279229eeb6f121/ghc >--------------------------------------------------------------- commit 446014681874982a340c245d3c279229eeb6f121 Author: Andrey Mokhov Date: Thu Jan 21 17:36:50 2016 +0000 Add full support for --configure command line flag. >--------------------------------------------------------------- 446014681874982a340c245d3c279229eeb6f121 src/CmdLineFlag.hs | 2 +- src/Rules/Actions.hs | 5 +++-- src/Rules/Config.hs | 31 ++++++++++++++++++++++--------- 3 files changed, 26 insertions(+), 12 deletions(-) diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 9e33397..249070a 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -61,7 +61,7 @@ flags = [ Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") , Option [] ["split-objects"] (NoArg readSplitObjects) "Generate split objects (requires a full clean rebuild)." , Option [] ["configure"] (OptArg readConfigure "ARGS") - "Run boot and configure scripts (passing ARGS to the latter)." ] + "Run configure with ARGS (also run boot if necessary)." ] -- TODO: Avoid unsafePerformIO by using shakeExtra (awaiting Shake's release) {-# NOINLINE cmdLineFlags #-} diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 2b05207..0e4961f 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -97,12 +97,13 @@ fixFile file f = do runConfigure :: FilePath -> [CmdOption] -> [String] -> Action () runConfigure dir opts args = do need [dir -/- "configure"] + let note = if null args || args == [""] then "" else " (" ++ intercalate ", " args ++ ")" if dir == "." then do - putBuild $ "| Run configure..." + putBuild $ "| Run configure" ++ note ++ "..." quietly $ cmd Shell (EchoStdout False) "bash configure" opts' args else do - putBuild $ "| Run configure in " ++ dir ++ "..." + putBuild $ "| Run configure" ++ note ++ " in " ++ dir ++ "..." quietly $ cmd Shell (EchoStdout False) [Cwd dir] "bash configure" opts' args where -- Always configure with bash. diff --git a/src/Rules/Config.hs b/src/Rules/Config.hs index 6f0447f..77ac1ac 100644 --- a/src/Rules/Config.hs +++ b/src/Rules/Config.hs @@ -5,13 +5,26 @@ import CmdLineFlag import Rules.Actions configRules :: Rules () -configRules = case cmdConfigure of - SkipConfigure -> mempty - RunConfigure args -> do - configPath -/- "system.config" %> \_ -> do - need [configPath -/- "system.config.in"] - runConfigure "." [] [args] +configRules = do + -- We always rerun the configure script in this mode, because the flags + -- passed to it can affect the contents of system.config file. + configPath -/- "system.config" %> \out -> do + alwaysRerun + case cmdConfigure of + RunConfigure args -> runConfigure "." [] [args] + SkipConfigure -> unlessM (doesFileExist out) $ + putError $ "Configuration file " ++ out ++ " is missing.\n" + ++ "Run the configure script either manually or via the " + ++ "build system by passing --configure[=ARGS] flag." - "configure" %> \_ -> do - putBuild "| Running boot..." - unit $ cmd "perl boot" + -- When we detect Windows paths in ACLOCAL_PATH we reset it. + -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. + "configure" %> \_ -> do + putBuild "| Running boot..." + aclocal <- getEnv "ACLOCAL_PATH" + let env = case aclocal of + Nothing -> [] + Just s -> if ":\\" `isPrefixOf` (drop 1 s) + then [AddEnv "ACLOCAL_PATH" ""] + else [] + quietly $ cmd (EchoStdout False) env "perl boot" From git at git.haskell.org Fri Oct 27 00:43:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch on ChangeModtimeAndDigest by default. (c9b2b76) Message-ID: <20171027004303.250363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c9b2b7633dea28eb1e5e0f6001f9cc12b34c8584/ghc >--------------------------------------------------------------- commit c9b2b7633dea28eb1e5e0f6001f9cc12b34c8584 Author: Andrey Mokhov Date: Thu Jan 21 19:14:08 2016 +0000 Switch on ChangeModtimeAndDigest by default. >--------------------------------------------------------------- c9b2b7633dea28eb1e5e0f6001f9cc12b34c8584 src/Main.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Main.hs b/src/Main.hs index 5c62479..f83734c 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -35,6 +35,7 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do , Rules.packageRules , Test.testRules ] options = shakeOptions - { shakeFiles = Base.shakeFilesPath + { shakeChange = ChangeModtimeAndDigest + , shakeFiles = Base.shakeFilesPath , shakeProgress = progressSimple , shakeTimings = True } From git at git.haskell.org Fri Oct 27 00:43:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop GenApply arguments, as it actually needs none. (0bec73c) Message-ID: <20171027004305.59EA03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0bec73c1eb86a91e15cfa8df53d14264ff854160/ghc >--------------------------------------------------------------- commit 0bec73c1eb86a91e15cfa8df53d14264ff854160 Author: Andrey Mokhov Date: Sun Oct 23 18:15:51 2016 +0100 Drop GenApply arguments, as it actually needs none. >--------------------------------------------------------------- 0bec73c1eb86a91e15cfa8df53d14264ff854160 hadrian.cabal | 1 - src/Settings/Builders/GenApply.hs | 6 ------ src/Settings/Default.hs | 2 -- 3 files changed, 9 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 6039b01..3b19557 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -74,7 +74,6 @@ executable hadrian , Settings.Builders.Cc , Settings.Builders.Configure , Settings.Builders.DeriveConstants - , Settings.Builders.GenApply , Settings.Builders.GenPrimopCode , Settings.Builders.Ghc , Settings.Builders.GhcCabal diff --git a/src/Settings/Builders/GenApply.hs b/src/Settings/Builders/GenApply.hs deleted file mode 100644 index b268c07..0000000 --- a/src/Settings/Builders/GenApply.hs +++ /dev/null @@ -1,6 +0,0 @@ -module Settings.Builders.GenApply (genApplyBuilderArgs) where - -import Settings.Builders.Common - -genApplyBuilderArgs :: Args -genApplyBuilderArgs = builder GenApply ? flag GhcUnregisterised ? arg "-u" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 4588c4b..f529019 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -16,7 +16,6 @@ import Settings.Builders.Ar import Settings.Builders.DeriveConstants import Settings.Builders.Cc import Settings.Builders.Configure -import Settings.Builders.GenApply import Settings.Builders.GenPrimopCode import Settings.Builders.Ghc import Settings.Builders.GhcCabal @@ -52,7 +51,6 @@ defaultBuilderArgs = mconcat , ccBuilderArgs , configureBuilderArgs , deriveConstantsBuilderArgs - , genApplyBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs , ghcCabalBuilderArgs From git at git.haskell.org Fri Oct 27 00:43:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Major rewrite before the first release (6bdb902) Message-ID: <20171027004307.311E03A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6bdb90260373d6ab3af2836d2e621d60beb13815/ghc >--------------------------------------------------------------- commit 6bdb90260373d6ab3af2836d2e621d60beb13815 Author: Andrey Mokhov Date: Fri Jan 22 02:07:49 2016 +0000 Major rewrite before the first release >--------------------------------------------------------------- 6bdb90260373d6ab3af2836d2e621d60beb13815 README.md | 146 +++++++++++++++++++++++++++++++++++++++----------------------- 1 file changed, 92 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 6bdb90260373d6ab3af2836d2e621d60beb13815 From git at git.haskell.org Fri Oct 27 00:43:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up RTS arguments (b2d06c6) Message-ID: <20171027004307.07C383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2d06c68c31265fa85dc764b6a29400c8845b640/ghc >--------------------------------------------------------------- commit b2d06c68c31265fa85dc764b6a29400c8845b640 Author: Andrey Mokhov Date: Tue Sep 26 20:48:21 2017 +0200 Clean up RTS arguments >--------------------------------------------------------------- b2d06c68c31265fa85dc764b6a29400c8845b640 src/Settings/Packages/Rts.hs | 70 +++++++++++++++++++++----------------------- 1 file changed, 33 insertions(+), 37 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index c71b729..a7ed021 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,17 +20,17 @@ rtsBuildPath = buildPath rtsContext rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" --- | Minimum supported Windows version. -- These numbers can be found at: -- https://msdn.microsoft.com/en-us/library/windows/desktop/aa383745(v=vs.85).aspx -- If we're compiling on windows, enforce that we only support Vista SP1+ -- Adding this here means it doesn't have to be done in individual .c files -- and also centralizes the versioning. -rtsWindowsVersion :: String -rtsWindowsVersion = "0x06000100" +-- | Minimum supported Windows version. +windowsVersion :: String +windowsVersion = "0x06000100" -rtsLibffiLibraryName :: Action FilePath -rtsLibffiLibraryName = do +libffiLibraryName :: Action FilePath +libffiLibraryName = do useSystemFfi <- flag UseSystemFfi windows <- windowsHost return $ case (useSystemFfi, windows) of @@ -38,18 +38,9 @@ rtsLibffiLibraryName = do (False, False) -> "Cffi" (_ , True ) -> "Cffi-6" -rtsLibffiArgs :: Args -rtsLibffiArgs = builder (Ghc CompileCWithGhc) ? do - useSystemFfi <- expr $ flag UseSystemFfi - ffiIncludeDir <- getSetting FfiIncludeDir - mconcat [ useSystemFfi ? pure (map ("-I" ++) $ words ffiIncludeDir) - -- ffi.h triggers prototype warnings, so we disable them here - , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? - arg "-Wno-strict-prototypes" ] - rtsLibffiLibrary :: Way -> Action FilePath rtsLibffiLibrary way = do - name <- rtsLibffiLibraryName + name <- libffiLibraryName suf <- libsuf way rtsPath <- rtsBuildPath return $ rtsPath -/- "lib" ++ name ++ suf @@ -108,12 +99,12 @@ rtsPackageArgs = package rts ? do way <- getWay path <- getBuildPath top <- expr topDirectory - libffiName <- expr rtsLibffiLibraryName + libffiName <- expr libffiLibraryName ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir ghclibDir <- expr installGhcLibDir destDir <- expr getDestDir - let cArgs = + let cArgs = mconcat [ arg "-Irts" , arg $ "-I" ++ path , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" @@ -156,41 +147,45 @@ rtsPackageArgs = package rts ? do inputs [ "//Evac.c", "//Evac_thr.c" , "//Scav.c", "//Scav_thr.c" , "//Compact.c", "//GC.c" ] ? arg "-fno-PIC" - -- -static is also necessary for these bits, otherwise the NCG - -- generates dynamic references: + -- -static is also necessary for these bits, otherwise the NCG + -- generates dynamic references: , speedHack ? inputs [ "//Updates.c", "//StgMiscClosures.c" , "//PrimOps.c", "//Apply.c" - , "//AutoApply.c" ] ? pure [ "-fno-PIC", "-static" ] - -- inlining warnings happen in Compact + , "//AutoApply.c" ] ? pure ["-fno-PIC", "-static"] + + -- inlining warnings happen in Compact , inputs ["//Compact.c"] ? arg "-Wno-inline" - -- emits warnings about call-clobbered registers on x86_64 - , inputs [ "//StgCRun.c", "//RetainerProfile.c" + + -- emits warnings about call-clobbered registers on x86_64 + , inputs [ "//RetainerProfile.c", "//StgCRun.c" , "//win32/ConsoleHandler.c", "//win32/ThrIOManager.c"] ? arg "-w" , inputs ["//RetainerSet.c"] ? arg "-Wno-format" - -- The above warning suppression flags are a temporary kludge. - -- While working on this module you are encouraged to remove it and fix - -- any warnings in the module. See - -- http://ghc.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings - -- for details + -- The above warning suppression flags are a temporary kludge. + -- While working on this module you are encouraged to remove it and fix + -- any warnings in the module. See: + -- http://ghc.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings , (not <$> flag GccIsClang) ? inputs ["//Compact.c"] ? arg "-finline-limit=2500" , inputs ["//Evac_thr.c", "//Scav_thr.c"] ? - pure [ "-DPARALLEL_GC", "-Irts/sm" ] + pure ["-DPARALLEL_GC", "-Irts/sm"] , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr" , input "//RetainerProfile.c" ? flag GccIsClang ? - pure [ "-Wno-incompatible-pointer-types" ] - , windowsHost ? arg ("-DWINVER=" ++ rtsWindowsVersion) ] - + arg "-Wno-incompatible-pointer-types" + , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? + arg "-Wno-strict-prototypes" + , windowsHost ? arg ("-DWINVER=" ++ windowsVersion) ] mconcat - [ rtsLibffiArgs - , builder (Cc FindCDependencies) ? mconcat cArgs - , builder (Ghc CompileCWithGhc) ? mconcat (map (map ("-optc" ++) <$>) cArgs) - , builder Ghc ? arg "-Irts" - , builder HsCpp ? pure + [ builder (Cc FindCDependencies) ? cArgs + , builder (Ghc CompileCWithGhc) ? map ("-optc" ++) <$> cArgs + , builder Ghc ? mconcat + [ arg "-Irts" + , flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir) ] + + , builder HsCpp ? pure [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir , "-DFFI_LIB_DIR=" ++ show ffiLibraryDir @@ -202,4 +197,5 @@ rtsPackageArgs = package rts ? do pure [ "-DINSTALLING" , "-DLIB_DIR=\"" ++ destDir ++ ghclibDir ++ "\"" , "-DINCLUDE_DIR=\"" ++ destDir ++ ghclibDir -/- "include\"" ] + , builder HsCpp ? flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ] From git at git.haskell.org Fri Oct 27 00:43:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move auxiliary build files to _build/hadrian (aa6bba1) Message-ID: <20171027004308.C6D303A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aa6bba126fecd412920fa7ca1e90fe9716b328d0/ghc >--------------------------------------------------------------- commit aa6bba126fecd412920fa7ca1e90fe9716b328d0 Author: Andrey Mokhov Date: Sun Oct 23 19:05:51 2016 +0100 Move auxiliary build files to _build/hadrian >--------------------------------------------------------------- aa6bba126fecd412920fa7ca1e90fe9716b328d0 src/Settings/Paths.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 2727696..7147264 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -16,7 +16,7 @@ import UserSettings -- | Path to the directory containing the Shake database and other auxiliary -- files generated by Hadrian. shakeFilesPath :: FilePath -shakeFilesPath = buildRootPath -/- "hadrian/shake-files" +shakeFilesPath = buildRootPath -/- "hadrian" -- | Boot package versions extracted from @.cabal@ files. bootPackageConstraints :: FilePath From git at git.haskell.org Fri Oct 27 00:43:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move ffiIncludeDir to C arguments (68446ab) Message-ID: <20171027004310.6F10C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68446abeab92087492baba6c746ab94c3bb7c2bb/ghc >--------------------------------------------------------------- commit 68446abeab92087492baba6c746ab94c3bb7c2bb Author: Andrey Mokhov Date: Tue Sep 26 20:56:28 2017 +0200 Move ffiIncludeDir to C arguments >--------------------------------------------------------------- 68446abeab92087492baba6c746ab94c3bb7c2bb src/Settings/Packages/Rts.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index a7ed021..7282a0e 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -107,6 +107,7 @@ rtsPackageArgs = package rts ? do let cArgs = mconcat [ arg "-Irts" , arg $ "-I" ++ path + , flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir) , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" -- rts *must* be compiled with optimisations. The INLINE_HEADER macro -- requires that functions are inlined to work as expected. Inlining @@ -181,9 +182,7 @@ rtsPackageArgs = package rts ? do mconcat [ builder (Cc FindCDependencies) ? cArgs , builder (Ghc CompileCWithGhc) ? map ("-optc" ++) <$> cArgs - , builder Ghc ? mconcat - [ arg "-Irts" - , flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir) ] + , builder Ghc ? arg "-Irts" , builder HsCpp ? pure [ "-DTOP=" ++ show top From git at git.haskell.org Fri Oct 27 00:43:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build Hadrian in /hadrian/bin (179f5b1) Message-ID: <20171027004312.53AD13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/179f5b14a138c41cd06423c17a41684157fcdb89/ghc >--------------------------------------------------------------- commit 179f5b14a138c41cd06423c17a41684157fcdb89 Author: Andrey Mokhov Date: Sun Oct 23 19:06:09 2016 +0100 Build Hadrian in /hadrian/bin >--------------------------------------------------------------- 179f5b14a138c41cd06423c17a41684157fcdb89 .gitignore | 3 +-- build.bat | 32 ++++++++++++++++---------------- build.sh | 8 ++++---- 3 files changed, 21 insertions(+), 22 deletions(-) diff --git a/.gitignore b/.gitignore index 87bedb8..6b06fea 100644 --- a/.gitignore +++ b/.gitignore @@ -2,8 +2,7 @@ cfg/system.config # build.bat and build.sh specific -/hadrian -/hadrian.exe +/bin/ # build.cabal.sh specific /dist/ diff --git a/build.bat b/build.bat index 6e86d42..2bc9a95 100644 --- a/build.bat +++ b/build.bat @@ -1,20 +1,20 @@ @cd %~dp0 - at mkdir ../_build/hadrian 2> nul + at mkdir bin 2> nul - at set ghcArgs=--make ^ - -Wall ^ - -fno-warn-name-shadowing ^ - -XRecordWildCards ^ - src/Main.hs ^ - -threaded ^ - -isrc ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=../_build/hadrian ^ - -i../libraries/Cabal/Cabal ^ - -j ^ - -O ^ - -o hadrian + at set ghcArgs=--make ^ + -Wall ^ + -fno-warn-name-shadowing ^ + -XRecordWildCards ^ + src\Main.hs ^ + -threaded ^ + -isrc ^ + -i..\libraries\Cabal\Cabal ^ + -rtsopts ^ + -with-rtsopts=-I0 ^ + -outputdir=bin ^ + -j ^ + -O ^ + -o bin\hadrian @set hadrianArgs=--lint ^ --directory ^ @@ -28,4 +28,4 @@ @rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains @set GHC_PACKAGE_PATH= - at hadrian %hadrianArgs% + at bin\hadrian %hadrianArgs% diff --git a/build.sh b/build.sh index d627c58..0f957cf 100755 --- a/build.sh +++ b/build.sh @@ -39,7 +39,7 @@ if type cabal > /dev/null 2>&1; then fi fi -mkdir -p "$root/../_build/hadrian" +mkdir -p "$root/bin" ghc \ "$root/src/Main.hs" \ @@ -51,11 +51,11 @@ ghc \ -rtsopts \ -with-rtsopts=-I0 \ -threaded \ - -outputdir="$root/../_build/hadrian" \ + -outputdir="$root/bin" \ -j -O \ - -o "$root/hadrian" + -o "$root/bin/hadrian" -"$root/hadrian" \ +"$root/bin/hadrian" \ --lint \ --directory "$root/.." \ "$@" From git at git.haskell.org Fri Oct 27 00:43:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (82a7fa5) Message-ID: <20171027004310.9E81A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82a7fa5557590ec395af8cd506d50cb6d4c5805b/ghc >--------------------------------------------------------------- commit 82a7fa5557590ec395af8cd506d50cb6d4c5805b Author: Andrey Mokhov Date: Fri Jan 22 11:39:44 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- 82a7fa5557590ec395af8cd506d50cb6d4c5805b README.md | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index e51e1e0..1f96505 100644 --- a/README.md +++ b/README.md @@ -30,7 +30,7 @@ packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickChe cd ghc git clone git://github.com/snowleopard/shaking-up-ghc shake-build ``` -* Start your first build: +* Start your first build (you might want to enable parallelism with `-j`): ```bash shake-build/build.sh --configure @@ -44,7 +44,8 @@ If you are interested in building in a Cabal sandbox, have a look at `shake-buil Using the build system ---------------------- Once your first build is successful, simply run `shake-build/build.sh` or `shake-build/build.bat` -to rebuild (you no longer need to use the `--configure` flag). Use `-j` flag to enable parallelism. +to rebuild (you no longer need to use the `--configure` flag). Most build artefacts are placed +into `.build` and `inplace` directories. ### Command line flags From git at git.haskell.org Fri Oct 27 00:43:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop checkApiAnnotations utility (6abcec9) Message-ID: <20171027004314.16AFC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6abcec9b1a92c1d35a15d9c01c38e6ecc06c4e87/ghc >--------------------------------------------------------------- commit 6abcec9b1a92c1d35a15d9c01c38e6ecc06c4e87 Author: Andrey Mokhov Date: Wed Sep 27 23:36:24 2017 +0100 Drop checkApiAnnotations utility See https://phabricator.haskell.org/D4039 >--------------------------------------------------------------- 6abcec9b1a92c1d35a15d9c01c38e6ecc06c4e87 src/GHC.hs | 32 +++++++++++++++----------------- 1 file changed, 15 insertions(+), 17 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 32676cd..77a63e9 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,14 +1,14 @@ {-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( -- * GHC packages - array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, - compiler, containers, deepseq, deriveConstants, directory, filepath, - genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, - ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, - hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, - parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, - terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml, - ghcPackages, isGhcPackage, defaultPackages, + array, base, binary, bytestring, cabal, compareSizes, compiler, containers, + deepseq, deriveConstants, directory, filepath, genapply, genprimopcode, ghc, + ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, + ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, + integerSimple, iservBin, libffi, mtl, parsec, parallel, pretty, primitive, + process, rts, runGhc, stm, templateHaskell, terminfo, text, time, touchy, + transformers, unlit, unix, win32, xhtml, ghcPackages, isGhcPackage, + defaultPackages, -- * Package information programName, nonCabalContext, nonHsMainPackage, autogenPath, installStage, @@ -30,13 +30,13 @@ import Oracles.Flag (crossCompiling) -- modify build default build conditions in "UserSettings". ghcPackages :: [Package] ghcPackages = - [ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes - , compiler, containers, deepseq, deriveConstants, directory, filepath - , genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact - , ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc - , hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, parallel - , pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo - , text, time, touchy, transformers, unlit, unix, win32, xhtml ] + [ array, base, binary, bytestring, cabal, compareSizes, compiler, containers + , deepseq, deriveConstants, directory, filepath, genapply, genprimopcode + , ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim + , ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp + , integerSimple, iservBin, libffi, mtl, parsec, parallel, pretty, primitive + , process, rts, runGhc, stm, templateHaskell, terminfo, text, time, touchy + , transformers, unlit, unix, win32, xhtml ] -- TODO: Optimise by switching to sets of packages. isGhcPackage :: Package -> Bool @@ -48,7 +48,6 @@ base = hsLib "base" binary = hsLib "binary" bytestring = hsLib "bytestring" cabal = hsLib "Cabal" `setPath` "libraries/Cabal/Cabal" -checkApiAnnotations = hsUtil "check-api-annotations" compareSizes = hsUtil "compareSizes" `setPath` "utils/compare_sizes" compiler = hsTop "ghc" `setPath` "compiler" containers = hsLib "containers" @@ -140,7 +139,6 @@ stage0Packages = do cross <- crossCompiling return $ [ binary , cabal - , checkApiAnnotations , compareSizes , compiler , deriveConstants From git at git.haskell.org Fri Oct 27 00:43:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add and link to important issues. (3d335e1) Message-ID: <20171027004314.355113A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3d335e1eca20caaf40bb8227ffbf85e9a675c187/ghc >--------------------------------------------------------------- commit 3d335e1eca20caaf40bb8227ffbf85e9a675c187 Author: Andrey Mokhov Date: Fri Jan 22 12:16:12 2016 +0000 Add and link to important issues. [skip ci] >--------------------------------------------------------------- 3d335e1eca20caaf40bb8227ffbf85e9a675c187 README.md | 29 +++++++++++++++++++---------- 1 file changed, 19 insertions(+), 10 deletions(-) diff --git a/README.md b/README.md index 1f96505..a368c01 100644 --- a/README.md +++ b/README.md @@ -45,9 +45,9 @@ Using the build system ---------------------- Once your first build is successful, simply run `shake-build/build.sh` or `shake-build/build.bat` to rebuild (you no longer need to use the `--configure` flag). Most build artefacts are placed -into `.build` and `inplace` directories. +into `.build` and `inplace` directories ([#113][build-artefacts-issue]). -### Command line flags +#### Command line flags In addition to standard Shake flags (try `--help`), the build system currently supports several others: @@ -61,13 +61,13 @@ build command; this is the default setting), and `unicorn` (when `normal` just w * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. -### User settings +#### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We use [`src/Settings/User.hs`][user-settings] for the same purpose. Feel free to -experiment. +experiment following the Haddock comments. -### Resetting the build +#### Resetting the build To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. @@ -76,11 +76,11 @@ This is a temporary solution; we are working on proper reset functionality ([#13 Current limitations ------------------- The new build system still lacks many important features: -* We only build `vanilla` way. +* We only build `vanilla` way: [#4][dynamic-issue], [#186][profiling-issue]. * Documentation is broken: [#98][haddock-issue]. -* Validation is not implemented. -* Build flavours and conventional command line flags are not implemented. -* Cross-compilation is not implemented. +* Validation is not implemented: [#187][validation-issue]. +* Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. +* Cross-compilation is not implemented: [#177][cross-compilation-issue]. How to contribute ----------------- @@ -88,7 +88,8 @@ How to contribute The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note the codebase is very unstable at present and we expect a lot of further refactoring. The documentation is -currently non-existent, but we are working on it. +currently non-existent, but we are working on it: [#55][comments-issue], +[#56][doc-issue]. Acknowledgements ---------------- @@ -108,8 +109,16 @@ helped me endure and enjoy the project. [issues]: https://github.com/snowleopard/shaking-up-ghc/issues [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild +[build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs [reset-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/131 +[dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 +[profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 +[validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 +[flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 +[cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 +[comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 +[doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 [contributors]: https://github.com/snowleopard/shaking-up-ghc/graphs/contributors From git at git.haskell.org Fri Oct 27 00:43:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compute package dependencies only for packages we build (67f433b) Message-ID: <20171027004315.BD9213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/67f433bf028ec4c4251b928fa476ff1302e8299c/ghc >--------------------------------------------------------------- commit 67f433bf028ec4c4251b928fa476ff1302e8299c Author: Andrey Mokhov Date: Thu Oct 27 20:00:58 2016 +0100 Compute package dependencies only for packages we build See #265 >--------------------------------------------------------------- 67f433bf028ec4c4251b928fa476ff1302e8299c src/Rules/Cabal.hs | 5 +++-- src/Rules/Test.hs | 2 +- src/Settings.hs | 5 ++++- src/Settings/Default.hs | 1 - 4 files changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 409ca1b..8848268 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -16,7 +16,7 @@ cabalRules :: Rules () cabalRules = do -- Cache boot package constraints (to be used in 'cabalArgs'). bootPackageConstraints %> \out -> do - bootPkgs <- interpretInContext (stageContext Stage0) getPackages + bootPkgs <- stagePackages Stage0 let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do need [pkgCabalFile pkg] @@ -28,7 +28,8 @@ cabalRules = do -- Cache package dependencies. packageDependencies %> \out -> do - pkgDeps <- forM (sort knownPackages) $ \pkg -> + pkgs <- concatMapM stagePackages [Stage0 .. Stage2] + pkgDeps <- forM (sort pkgs) $ \pkg -> if pkg `elem` [hp2ps, libffi, rts, touchy, unlit] then return $ pkgNameString pkg else do diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 3b2fd1b..18513a7 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -23,7 +23,7 @@ testRules = do "test" ~> do let yesNo x = show $ if x then "YES" else "NO" - pkgs <- interpretInContext (stageContext Stage1) getPackages + pkgs <- stagePackages Stage1 tests <- filterM doesDirectoryExist $ concat [ [ pkgPath pkg -/- "tests", pkgPath pkg -/- "tests-ghc" ] | pkg <- pkgs, isLibrary pkg, pkg /= rts, pkg /= libffi ] diff --git a/src/Settings.hs b/src/Settings.hs index 3fdf14f..0a71c90 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -1,7 +1,7 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, - getContextDirectory, getBuildPath + getContextDirectory, getBuildPath, stagePackages ) where import Base @@ -28,6 +28,9 @@ getRtsWays = fromDiffExpr $ rtsWays flavour getPackages :: Expr [Package] getPackages = fromDiffExpr $ packages flavour +stagePackages :: Stage -> Action [Package] +stagePackages stage = interpretInContext (stageContext stage) getPackages + getPackagePath :: Expr FilePath getPackagePath = pkgPath <$> getPackage diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index f529019..f7ef62e 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -65,7 +65,6 @@ defaultBuilderArgs = mconcat , makeBuilderArgs , tarBuilderArgs ] - -- | All 'Package'-dependent command line arguments. defaultPackageArgs :: Args defaultPackageArgs = mconcat From git at git.haskell.org Fri Oct 27 00:43:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to isWindows (88a7b4e) Message-ID: <20171027004317.B8EE63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88a7b4e31616f06ea9c0f75d3565ae11936009e0/ghc >--------------------------------------------------------------- commit 88a7b4e31616f06ea9c0f75d3565ae11936009e0 Author: Andrey Mokhov Date: Thu Sep 28 23:49:12 2017 +0100 Switch to isWindows >--------------------------------------------------------------- 88a7b4e31616f06ea9c0f75d3565ae11936009e0 src/Rules/Configure.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index 5e29116..492d91c 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -1,6 +1,6 @@ module Rules.Configure (configureRules) where -import qualified System.Info as System +import qualified System.Info.Extra as System import Base import Builder @@ -21,7 +21,7 @@ configureRules = do ++ "--skip-configure flag." else do -- We cannot use windowsHost here due to a cyclic dependency. - when (System.os == "mingw32") $ do + when System.isWindows $ do putBuild "| Checking for Windows tarballs..." quietly $ cmd ["bash", "mk/get-win32-tarballs.sh", "download", System.arch] let srcs = map (<.> "in") outs From git at git.haskell.org Fri Oct 27 00:43:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (e2b0201) Message-ID: <20171027004317.D7AFA3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2b0201a4b8694955bd2701deaca22c4be15c155/ghc >--------------------------------------------------------------- commit e2b0201a4b8694955bd2701deaca22c4be15c155 Author: Andrey Mokhov Date: Fri Jan 22 12:18:22 2016 +0000 Minor revision [skip ci] >--------------------------------------------------------------- e2b0201a4b8694955bd2701deaca22c4be15c155 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index a368c01..9845e17 100644 --- a/README.md +++ b/README.md @@ -95,7 +95,7 @@ Acknowledgements ---------------- I started this project as part of my 6-month research visit to Microsoft -Research in Cambridge. It was funded by Newcastle University, EPSRC, and +Research in Cambridge, which was funded by Newcastle University, EPSRC, and Microsoft Research. I would like to thank Simon Peyton Jones, Neil Mitchell and Simon Marlow for kick-starting the project and for their guidance. Last but not least, big thanks to the project [contributors][contributors], who From git at git.haskell.org Fri Oct 27 00:43:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add rule 'sdist-ghc' (d4d9c03) Message-ID: <20171027004319.403F33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d4d9c03de0be0762f973f106d2d4f4b2000d63f1/ghc >--------------------------------------------------------------- commit d4d9c03de0be0762f973f106d2d4f4b2000d63f1 Author: Kai Harries Date: Thu Jun 9 21:50:24 2016 +0200 Add rule 'sdist-ghc' See #219 >--------------------------------------------------------------- d4d9c03de0be0762f973f106d2d4f4b2000d63f1 hadrian.cabal | 1 + src/Main.hs | 2 + src/Rules/Clean.hs | 1 + src/Rules/SourceDist.hs | 105 ++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 109 insertions(+) diff --git a/hadrian.cabal b/hadrian.cabal index 3b19557..4d6fbdf 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -64,6 +64,7 @@ executable hadrian , Rules.Program , Rules.Register , Rules.Selftest + , Rules.SourceDist , Rules.Test , Rules.Wrappers.Ghc , Rules.Wrappers.GhcPkg diff --git a/src/Main.hs b/src/Main.hs index 66f897f..b4c2d42 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -7,6 +7,7 @@ import qualified Environment import qualified Rules import qualified Rules.Clean import qualified Rules.Oracles +import qualified Rules.SourceDist import qualified Rules.Selftest import qualified Rules.Test import qualified Settings.Paths @@ -23,6 +24,7 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do rules = do Rules.Clean.cleanRules Rules.Oracles.oracleRules + Rules.SourceDist.sourceDistRules Rules.Selftest.selftestRules Rules.Test.testRules Rules.buildRules diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 4678054..50edd20 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -16,6 +16,7 @@ cleanRules = do removeDirectory generatedPath removeDirectory programInplacePath removeDirectory "inplace/lib" + removeDirectory "sdistprep" putBuild $ "| Remove files generated by ghc-cabal..." forM_ knownPackages $ \pkg -> forM_ [Stage0 ..] $ \stage -> do diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs new file mode 100644 index 0000000..a2cc8f4 --- /dev/null +++ b/src/Rules/SourceDist.hs @@ -0,0 +1,105 @@ +module Rules.SourceDist (sourceDistRules) where + +import Base +import Builder +import Oracles.Config.Setting +import Oracles.DirectoryContent +import Rules.Actions +import UserSettings + +sourceDistRules :: Rules () +sourceDistRules = do + "sdist-ghc" ~> do + version <- setting ProjectVersion + need ["sdistprep/ghc-" ++ version ++ "-src.tar.xz"] + putSuccess "| Done. " + "sdistprep/ghc-*-src.tar.xz" %> \fname -> do + let tarName = takeFileName fname + treePath = "sdistprep/ghc" dropTarXz tarName + prepareTree treePath + runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." tarName, dropTarXz tarName] + "GIT_COMMIT_ID" %> \fname -> + setting ProjectGitCommitId >>= writeFileChanged fname + "VERSION" %> \fname -> + setting ProjectVersion >>= writeFileChanged fname + where + dropTarXz = dropExtension . dropExtension + + +prepareTree :: FilePath -> Action () +prepareTree dest = do + mapM_ cpDir srcDirs + mapM_ cpFile srcFiles + where + cpFile a = copyFile a (dest a) + cpDir a = copyDirectoryContent (Not excluded) a (dest takeFileName a) + excluded = Or + [ Test "//.*" + , Test "//#*" + , Test "//*-SAVE" + , Test "//*.orig" + , Test "//*.rej" + , Test "//*~" + , Test "//autom4te*" + , Test "//dist" + , Test "//log" + , Test "//stage0" + , Test "//stage1" + , Test "//stage2" + , Test "//stage3" + , Test "hadrian/cabal.sandbox.config" + , Test "hadrian/cfg/system.config" + , Test "hadrian/dist" + , Test "hadrian/UserSettings.hs" + , Test "libraries//*.buildinfo" + , Test "libraries//GNUmakefile" + , Test "libraries//config.log" + , Test "libraries//config.status" + , Test "libraries//configure" + , Test "libraries//ghc.mk" + , Test "libraries//include/Hs*Config.h" + , Test "libraries/dph" + , Test "libraries/parallel" + , Test "libraries/primitive" + , Test "libraries/random" + , Test "libraries/stm" + , Test "libraries/vector" + , Test "mk/build.mk" ] + srcDirs = + [ "bindisttest" + , "compiler" + , "distrib" + , "docs" + , "docs" + , "driver" + , "ghc" + , "hadrian" + , "includes" + , "iserv" + , "libffi" + , "libffi-tarballs" + , "libraries" + , "mk" + , "rts" + , "rules" + , "utils" ] + srcFiles = + [ "ANNOUNCE" + , "GIT_COMMIT_ID" + , "HACKING.md" + , "INSTALL.md" + , "LICENSE" + , "MAKEHELP.md" + , "Makefile" + , "README.md" + , "VERSION" + , "aclocal.m4" + , "boot" + , "config.guess" + , "config.sub" + , "configure" + , "configure.ac" + , "ghc.mk" + , "install-sh" + , "packages" + , "settings.in" ] From git at git.haskell.org Fri Oct 27 00:43:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a link to milestones. (1b08589) Message-ID: <20171027004321.C56233A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1b08589b98dc1c354042d62c004640d394485c39/ghc >--------------------------------------------------------------- commit 1b08589b98dc1c354042d62c004640d394485c39 Author: Andrey Mokhov Date: Fri Jan 22 12:26:18 2016 +0000 Add a link to milestones. [skip ci] >--------------------------------------------------------------- 1b08589b98dc1c354042d62c004640d394485c39 README.md | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 9845e17..b80b621 100644 --- a/README.md +++ b/README.md @@ -82,6 +82,8 @@ The new build system still lacks many important features: * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. +Check out [milestones] to see when we hope to resolve the above limitations. + How to contribute ----------------- @@ -95,7 +97,7 @@ Acknowledgements ---------------- I started this project as part of my 6-month research visit to Microsoft -Research in Cambridge, which was funded by Newcastle University, EPSRC, and +Research Cambridge, which was funded by Newcastle University, EPSRC, and Microsoft Research. I would like to thank Simon Peyton Jones, Neil Mitchell and Simon Marlow for kick-starting the project and for their guidance. Last but not least, big thanks to the project [contributors][contributors], who @@ -119,6 +121,7 @@ helped me endure and enjoy the project. [validation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/187 [flavours-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/188 [cross-compilation-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/177 +[milestones]: https://github.com/snowleopard/shaking-up-ghc/milestones [comments-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/55 [doc-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/56 [contributors]: https://github.com/snowleopard/shaking-up-ghc/graphs/contributors From git at git.haskell.org Fri Oct 27 00:43:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #265 from KaiHa/wip/ticket219 (0bfadf3) Message-ID: <20171027004322.C37423A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0bfadf34ec199a40c4276c0935ba8c725cf51171/ghc >--------------------------------------------------------------- commit 0bfadf34ec199a40c4276c0935ba8c725cf51171 Merge: 67f433b d4d9c03 Author: Andrey Mokhov Date: Thu Oct 27 23:19:12 2016 +0100 Merge pull request #265 from KaiHa/wip/ticket219 Implement 'sdist-ghc' rule >--------------------------------------------------------------- 0bfadf34ec199a40c4276c0935ba8c725cf51171 hadrian.cabal | 1 + src/Main.hs | 2 + src/Rules/Clean.hs | 1 + src/Rules/SourceDist.hs | 105 ++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 109 insertions(+) From git at git.haskell.org Fri Oct 27 00:43:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing dependency on package configuration (c6d7b2a) Message-ID: <20171027004321.D02103A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6d7b2a33e6ff987e7112c57555425c285c380e9/ghc >--------------------------------------------------------------- commit c6d7b2a33e6ff987e7112c57555425c285c380e9 Author: Andrey Mokhov Date: Fri Sep 29 00:37:35 2017 +0100 Fix missing dependency on package configuration Also a minor revision. See #421 >--------------------------------------------------------------- c6d7b2a33e6ff987e7112c57555425c285c380e9 src/Base.hs | 7 ++++++- src/Builder.hs | 12 ++++++------ src/Settings/Builders/Common.hs | 8 +++----- src/Settings/Builders/Ghc.hs | 14 +++++++++----- src/Settings/Default.hs | 2 +- 5 files changed, 25 insertions(+), 18 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 76e8f2b..38c8792 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,7 +22,7 @@ module Base ( hadrianPath, configPath, configFile, sourcePath, configH, shakeFilesDir, generatedDir, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, inplaceLibCopyTargets, templateHscPath, stage0PackageDbDir, - inplacePackageDbPath, packageDbStamp + inplacePackageDbPath, packageDbPath, packageDbStamp ) where import Control.Applicative @@ -82,6 +82,11 @@ stage0PackageDbDir = "stage0/bootstrapping.conf" inplacePackageDbPath :: FilePath inplacePackageDbPath = "inplace/lib/package.conf.d" +-- | Path to the package database used in a given 'Stage'. +packageDbPath :: Stage -> Action FilePath +packageDbPath Stage0 = buildRoot <&> (-/- stage0PackageDbDir) +packageDbPath _ = return inplacePackageDbPath + -- | We use a stamp file to track the existence of a package database. packageDbStamp :: FilePath packageDbStamp = ".stamp" diff --git a/src/Builder.hs b/src/Builder.hs index 355878f..fdd73e7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -149,13 +149,13 @@ instance H.Builder Builder where Just context -> programPath context needBuilder :: Builder -> Action () - needBuilder (Configure dir) = need [dir -/- "configure"] - needBuilder Hsc2Hs = do path <- H.builderPath Hsc2Hs - need [path, templateHscPath] - needBuilder (Make dir) = need [dir -/- "Makefile"] - needBuilder builder = when (isJust $ builderProvenance builder) $ do + needBuilder builder = do path <- H.builderPath builder - need [path] + case builder of + Configure dir -> need [dir -/- "configure"] + Hsc2Hs -> need [path, templateHscPath] + Make dir -> need [dir -/- "Makefile"] + _ -> when (isJust $ builderProvenance builder) $ need [path] runBuilderWith :: Builder -> BuildInfo -> Action () runBuilderWith builder BuildInfo {..} = do diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 6da7ea8..e7af38b 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -49,11 +49,9 @@ cWarnings = do bootPackageDatabaseArgs :: Args bootPackageDatabaseArgs = do - root <- getBuildRoot - stage <- getStage - let dbDir | stage == Stage0 = root -/- stage0PackageDbDir - | otherwise = inplacePackageDbPath - expr $ need [dbDir -/- packageDbStamp] + stage <- getStage + dbPath <- expr $ packageDbPath stage + expr $ need [dbPath -/- packageDbStamp] stage0 ? do top <- expr topDirectory root <- getBuildRoot diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 7f942f6..94b5b21 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,5 +1,5 @@ module Settings.Builders.Ghc ( - ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs, ghcCbuilderArgs + ghcBuilderArgs, ghcCBuilderArgs, ghcMBuilderArgs, haddockGhcArgs ) where import Hadrian.Haskell.Cabal @@ -24,9 +24,8 @@ needTouchy = notStage0 ? windowsHost ? do touchyPath <- expr $ programPath (vanillaContext Stage0 touchy) expr $ need [touchyPath] -ghcCbuilderArgs :: Args -ghcCbuilderArgs = - builder (Ghc CompileCWithGhc) ? do +ghcCBuilderArgs :: Args +ghcCBuilderArgs = builder (Ghc CompileCWithGhc) ? do way <- getWay let ccArgs = [ getPkgDataList CcArgs , getStagedSettingList ConfCcArgs @@ -83,11 +82,16 @@ ghcMBuilderArgs = builder (Ghc FindHsDependencies) ? do haddockGhcArgs :: Args haddockGhcArgs = mconcat [ commonGhcArgs, getPkgDataList HsArgs ] --- This is included into ghcBuilderArgs, ghcMBuilderArgs and haddockGhcArgs. +-- Used in ghcBuilderArgs, ghcCBuilderArgs, ghcMBuilderArgs and haddockGhcArgs. commonGhcArgs :: Args commonGhcArgs = do way <- getWay path <- getBuildPath + pkg <- getPackage + when (isLibrary pkg) $ do + context <- getContext + conf <- expr $ pkgConfFile context + expr $ need [conf] mconcat [ arg "-hisuf", arg $ hisuf way , arg "-osuf" , arg $ osuf way , arg "-hcsuf", arg $ hcsuf way diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 10ec84f..cf0047f 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -148,8 +148,8 @@ defaultBuilderArgs = mconcat , deriveConstantsBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs - , ghcCbuilderArgs , ghcCabalBuilderArgs + , ghcCBuilderArgs , ghcMBuilderArgs , ghcPkgBuilderArgs , haddockBuilderArgs From git at git.haskell.org Fri Oct 27 00:43:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build man page (#424) (e1c9afa) Message-ID: <20171027004326.569653A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1c9afa3c5e29a7cea8d3853a06e08005d06f83b/ghc >--------------------------------------------------------------- commit e1c9afa3c5e29a7cea8d3853a06e08005d06f83b Author: Zhen Zhang Date: Sun Oct 1 05:01:28 2017 +0800 Build man page (#424) >--------------------------------------------------------------- e1c9afa3c5e29a7cea8d3853a06e08005d06f83b src/Rules/Documentation.hs | 15 +++++++++++++++ src/Settings/Builders/Sphinx.hs | 2 +- 2 files changed, 16 insertions(+), 1 deletion(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index bafb1b2..2cdd4d5 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -22,12 +22,17 @@ documentationRules = do buildHtmlDocumentation buildPdfDocumentation buildDocumentationArchives + buildManPage "docs" ~> do root <- buildRoot let html = htmlRoot -/- "index.html" archives = map pathArchive docPaths pdfs = map pathPdf $ docPaths \\ [ "libraries" ] need $ map (root -/-) $ [html] ++ archives ++ pdfs + need [manPagePath] + +manPagePath :: FilePath +manPagePath = "_build/docs/users_guide/build-man/ghc.1" -- TODO: Add support for Documentation Packages so we can -- run the builders without this hack. @@ -176,3 +181,13 @@ buildArchive path = do src = root -/- pathIndex path need [src] build $ target context (Tar Create) [takeDirectory src] [file] + +-- | build man page +buildManPage :: Rules () +buildManPage = do + manPagePath %> \file -> do + need ["docs/users_guide/ghc.rst"] + let context = vanillaContext Stage0 docPackage + withTempDir $ \dir -> do + build $ target context (Sphinx Man) ["docs/users_guide"] [dir] + copyFileUntracked (dir -/- "ghc.1") file diff --git a/src/Settings/Builders/Sphinx.hs b/src/Settings/Builders/Sphinx.hs index 6ac88a0..2338cfc 100644 --- a/src/Settings/Builders/Sphinx.hs +++ b/src/Settings/Builders/Sphinx.hs @@ -16,7 +16,7 @@ sphinxBuilderArgs = do , arg =<< getInput , arg outPath ] , builder (Sphinx Man) ? mconcat - [ arg "-b", arg "latex" + [ arg "-b", arg "man" , arg "-d", arg $ outPath -/- ".doctrees-man" , arg =<< getInput , arg outPath ] ] From git at git.haskell.org Fri Oct 27 00:43:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement clean target. (a730d9b) Message-ID: <20171027004326.373783A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a730d9bd25ac701cd9b6bd22b4f4fb14f88902dd/ghc >--------------------------------------------------------------- commit a730d9bd25ac701cd9b6bd22b4f4fb14f88902dd Author: Andrey Mokhov Date: Fri Jan 22 12:57:14 2016 +0000 Implement clean target. Fix #131. >--------------------------------------------------------------- a730d9bd25ac701cd9b6bd22b4f4fb14f88902dd shaking-up-ghc.cabal | 1 + src/Main.hs | 2 ++ src/Rules/Clean.hs | 30 ++++++++++++++++++++++++++++++ src/Rules/Generate.hs | 2 +- 4 files changed, 34 insertions(+), 1 deletion(-) diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal index b6a42d5..bd21d28 100644 --- a/shaking-up-ghc.cabal +++ b/shaking-up-ghc.cabal @@ -39,6 +39,7 @@ executable ghc-shake , Rules , Rules.Actions , Rules.Cabal + , Rules.Clean , Rules.Compile , Rules.Config , Rules.Data diff --git a/src/Main.hs b/src/Main.hs index f83734c..7321f88 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -6,6 +6,7 @@ import qualified Base import CmdLineFlag import qualified Rules import qualified Rules.Cabal +import qualified Rules.Clean import qualified Rules.Config import qualified Rules.Generate import qualified Rules.Gmp @@ -24,6 +25,7 @@ main = shakeArgsWith options flags $ \cmdLineFlags targets -> do rules :: Rules () rules = mconcat [ Rules.Cabal.cabalRules + , Rules.Clean.cleanRules , Rules.Config.configRules , Rules.Generate.copyRules , Rules.Generate.generateRules diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs new file mode 100644 index 0000000..6ab5309 --- /dev/null +++ b/src/Rules/Clean.hs @@ -0,0 +1,30 @@ +module Rules.Clean (cleanRules) where + +import Base +import Package +import Rules.Generate +import Settings.Packages +import Settings.Paths +import Settings.User +import Stage + +cleanRules :: Rules () +cleanRules = do + "clean" ~> do + putBuild $ "| Remove files in " ++ buildRootPath ++ "..." + removeFilesAfter buildRootPath ["//*"] + putBuild $ "| Remove files in " ++ programInplacePath ++ "..." + removeFilesAfter programInplacePath ["//*"] + putBuild $ "| Remove files in inplace/lib..." + removeFilesAfter "inplace/lib" ["//*"] + putBuild $ "| Remove files in " ++ derivedConstantsPath ++ "..." + removeFilesAfter derivedConstantsPath ["//*"] + forM_ includesDependencies $ \file -> do + putBuild $ "| Remove " ++ file + removeFileIfExists file + putBuild $ "| Remove files generated by ghc-cabal..." + forM_ knownPackages $ \pkg -> + forM_ [Stage0 ..] $ \stage -> do + let dir = pkgPath pkg -/- targetDirectory stage pkg + removeDirectoryIfExists dir + putSuccess $ "| Done. " diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index c5386e4..73b160a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( generatePackageCode, generateRules, installTargets, copyRules, - derivedConstantsPath, generatedDependencies + includesDependencies, derivedConstantsPath, generatedDependencies ) where import Base From git at git.haskell.org Fri Oct 27 00:43:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on source distribution (0959e45) Message-ID: <20171027004326.DD4BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0959e45fab08b850fdb5b555ea7250e493386976/ghc >--------------------------------------------------------------- commit 0959e45fab08b850fdb5b555ea7250e493386976 Author: Andrey Mokhov Date: Fri Oct 28 17:33:11 2016 +0100 Add a note on source distribution See #219. >--------------------------------------------------------------- 0959e45fab08b850fdb5b555ea7250e493386976 README.md | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 718421f..d869f4b 100644 --- a/README.md +++ b/README.md @@ -98,6 +98,10 @@ complete separation of GHC sources and build artefacts: [#113][build-artefacts-i * `build -B` forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. +#### Source distribution + +To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` target. + #### Testing * `build validate` runs GHC tests by simply executing `make fast` in `testsuite/tests` @@ -119,7 +123,7 @@ The new build system still lacks many important features: * Only HTML Haddock documentation is supported (use `--haddock` flag). * Build flavours and conventional command line flags are not implemented: [#188][flavours-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. -* There is no support for installation or binary/source distribution: [#219][install-issue]. +* There is no support for installation or binary distribution: [#219][install-issue]. Check out [milestones] to see when we hope to resolve the above limitations. From git at git.haskell.org Fri Oct 27 00:43:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on clean target (497f750) Message-ID: <20171027004330.351213A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/497f75095c1265b19025077a2fec0633604d1abf/ghc >--------------------------------------------------------------- commit 497f75095c1265b19025077a2fec0633604d1abf Author: Andrey Mokhov Date: Fri Jan 22 13:04:34 2016 +0000 Add a note on clean target [skip ci] >--------------------------------------------------------------- 497f75095c1265b19025077a2fec0633604d1abf README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index b80b621..602148b 100644 --- a/README.md +++ b/README.md @@ -71,7 +71,8 @@ experiment following the Haddock comments. To reset the new build system run the build script with `-B` flag. This forces Shake to rerun all rules, even if results of the previous build are still in the GHC tree. -This is a temporary solution; we are working on proper reset functionality ([#131][reset-issue]). +To remove all build artefacts, run the build script with `clean` target. Note, we are +working towards a complete separation of GHC sources and build artefacts: [#113][build-artefacts-issue]. Current limitations ------------------- @@ -114,7 +115,6 @@ helped me endure and enjoy the project. [build-artefacts-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [user-settings]: https://github.com/snowleopard/shaking-up-ghc/blob/master/src/Settings/User.hs -[reset-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/131 [dynamic-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/4 [profiling-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/186 [haddock-issue]: https://github.com/snowleopard/shaking-up-ghc/issues/98 From git at git.haskell.org Fri Oct 27 00:43:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to the python based boot script (18539d0) Message-ID: <20171027004330.7E26D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/18539d0ca551e312a81f2d9bda5ad055a657906a/ghc >--------------------------------------------------------------- commit 18539d0ca551e312a81f2d9bda5ad055a657906a Author: Andrey Mokhov Date: Wed Oct 4 12:38:48 2017 +0100 Switch to the python based boot script See #314 >--------------------------------------------------------------- 18539d0ca551e312a81f2d9bda5ad055a657906a src/Rules/Configure.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index 492d91c..a4ef084 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -38,4 +38,4 @@ configureRules = do else do need ["configure.ac"] putBuild "| Running boot..." - quietly $ cmd "perl boot" + quietly $ cmd "python3 boot" From git at git.haskell.org Fri Oct 27 00:43:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Retry pacman package downloads on AppVeyor to make CI more robust (6596774) Message-ID: <20171027004330.D9A333A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65967740632fed04975ead2f3ea9fe2225e45671/ghc >--------------------------------------------------------------- commit 65967740632fed04975ead2f3ea9fe2225e45671 Author: Andrey Mokhov Date: Fri Oct 28 23:03:05 2016 +0100 Retry pacman package downloads on AppVeyor to make CI more robust >--------------------------------------------------------------- 65967740632fed04975ead2f3ea9fe2225e45671 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 7552a56..7687500 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -22,7 +22,7 @@ install: # Install all Hadrian and GHC build dependencies - cd hadrian - stack setup > nul - - stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm + - appveyor-retry stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm build_script: # Build Hadrian From git at git.haskell.org Fri Oct 27 00:43:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use removeFiles instead of removeFilesAfter. (a8ea524) Message-ID: <20171027004333.E6BDC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8ea524634d870e75c3dc13bc96d174b064849ae/ghc >--------------------------------------------------------------- commit a8ea524634d870e75c3dc13bc96d174b064849ae Author: Andrey Mokhov Date: Fri Jan 22 13:08:36 2016 +0000 Use removeFiles instead of removeFilesAfter. See #131. >--------------------------------------------------------------- a8ea524634d870e75c3dc13bc96d174b064849ae src/Rules/Clean.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 6ab5309..2b4094a 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -12,13 +12,13 @@ cleanRules :: Rules () cleanRules = do "clean" ~> do putBuild $ "| Remove files in " ++ buildRootPath ++ "..." - removeFilesAfter buildRootPath ["//*"] + liftIO $ removeFiles buildRootPath ["//*"] putBuild $ "| Remove files in " ++ programInplacePath ++ "..." - removeFilesAfter programInplacePath ["//*"] + liftIO $ removeFiles programInplacePath ["//*"] putBuild $ "| Remove files in inplace/lib..." - removeFilesAfter "inplace/lib" ["//*"] + liftIO $ removeFiles "inplace/lib" ["//*"] putBuild $ "| Remove files in " ++ derivedConstantsPath ++ "..." - removeFilesAfter derivedConstantsPath ["//*"] + liftIO $ removeFiles derivedConstantsPath ["//*"] forM_ includesDependencies $ \file -> do putBuild $ "| Remove " ++ file removeFileIfExists file From git at git.haskell.org Fri Oct 27 00:43:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix libffil build (d6fd6fe) Message-ID: <20171027004334.90CEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6fd6feb85cd846dfd707703da839056d43c92a8/ghc >--------------------------------------------------------------- commit d6fd6feb85cd846dfd707703da839056d43c92a8 Author: Andrey Mokhov Date: Thu Oct 5 10:50:56 2017 +0100 Fix libffil build See #426 >--------------------------------------------------------------- d6fd6feb85cd846dfd707703da839056d43c92a8 src/Rules/Libffi.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 68040be..9641b66 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -64,7 +64,7 @@ libffiRules = do libffiPath <- libffiBuildPath build $ target libffiContext (Make libffiPath) [] [] - hs <- getDirectoryFiles "" [libffiPath -/- "inst/lib/*/include/*"] + hs <- getDirectoryFiles "" [libffiPath -/- "inst/include/*"] forM_ hs $ \header -> copyFile header (rtsPath -/- takeFileName header) @@ -82,7 +82,8 @@ libffiRules = do <$> getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] need [tarball] - let libname = dropExtension . dropExtension $ takeFileName tarball + -- Go from 'libffi-3.99999+git20171002+77e130c.tar.gz' to 'libffi-3.99999' + let libname = takeWhile (/= '+') $ takeFileName tarball root <- buildRoot removeDirectory (root -/- libname) From git at git.haskell.org Fri Oct 27 00:43:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of github.com:snowleopard/shaking-up-ghc (30a3d91) Message-ID: <20171027004337.7634F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/30a3d9199fe606b08b26b387bc9b8b932dc2098d/ghc >--------------------------------------------------------------- commit 30a3d9199fe606b08b26b387bc9b8b932dc2098d Merge: a8ea524 497f750 Author: Andrey Mokhov Date: Fri Jan 22 13:08:56 2016 +0000 Merge branch 'master' of github.com:snowleopard/shaking-up-ghc >--------------------------------------------------------------- 30a3d9199fe606b08b26b387bc9b8b932dc2098d README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Oct 27 00:43:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor package-data generation for custom packages (cfecd73) Message-ID: <20171027004334.D1BF13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cfecd733f3e9df9c5ae6e657588a72153871d549/ghc >--------------------------------------------------------------- commit cfecd733f3e9df9c5ae6e657588a72153871d549 Author: Andrey Mokhov Date: Sat Oct 29 01:19:03 2016 +0100 Refactor package-data generation for custom packages >--------------------------------------------------------------- cfecd733f3e9df9c5ae6e657588a72153871d549 src/Rules/Data.hs | 119 +++++++++++++++++++++++------------------------------- 1 file changed, 50 insertions(+), 69 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 502fc3c..cefd2fa 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -57,80 +57,61 @@ buildPackageData context at Context {..} = do -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps. priority 2.0 $ do - when (package == hp2ps) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - cSrcs = [ "AreaBelow.c", "Curves.c", "Error.c", "Main.c" - , "Reorder.c", "TopTwenty.c", "AuxFile.c" - , "Deviation.c", "HpFile.c", "Marks.c", "Scale.c" - , "TraceElement.c", "Axes.c", "Dimensions.c", "Key.c" - , "PsFile.c", "Shade.c", "Utilities.c" ] - contents = unlines $ map (prefix++) - [ "PROGNAME = hp2ps" - , "C_SRCS = " ++ unwords cSrcs - , "DEP_EXTRA_LIBS = m" - , "CC_OPTS = -I" ++ generatedPath ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk - - when (package == unlit) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - contents = unlines $ map (prefix++) - [ "PROGNAME = unlit" - , "C_SRCS = unlit.c" - , "SYNOPSIS = Literate script filter." ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk - - when (package == touchy) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - contents = unlines $ map (prefix++) - [ "PROGNAME = touchy" - , "C_SRCS = touchy.c" ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk + when (package `elem` [hp2ps, rts, touchy, unlit]) $ dataFile %> + generatePackageData context -- Bootstrapping `ghcCabal`: although `ghcCabal` is a proper cabal -- package, we cannot generate the corresponding `package-data.mk` file -- by running by running `ghcCabal`, because it has not yet been built. - when (package == ghcCabal && stage == Stage0) $ dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - let prefix = fixKey (buildPath context) ++ "_" - contents = unlines $ map (prefix++) - [ "PROGNAME = ghc-cabal" - , "MODULES = Main" - , "SYNOPSIS = Bootstrapped ghc-cabal utility." - , "HS_SRC_DIRS = ." ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk + when (package == ghcCabal && stage == Stage0) $ dataFile %> + generatePackageData context + +generatePackageData :: Context -> FilePath -> Action () +generatePackageData context at Context {..} file = do + orderOnly =<< interpretInContext context generatedDependencies + asmSrcs <- packageAsmSources package + cSrcs <- packageCSources package + cmmSrcs <- packageCmmSources package + let prefix = fixKey (buildPath context) ++ "_" + pkgKey = if isLibrary package then "COMPONENT_ID = " else "PROGNAME = " + writeFileChanged file . unlines . map (prefix ++) $ + [ pkgKey ++ pkgNameString package ] ++ + [ "S_SRCS = " ++ unwords asmSrcs ] ++ + [ "C_SRCS = " ++ unwords cSrcs ] ++ + [ "CMM_SRCS = " ++ unwords cmmSrcs ] ++ + [ "DEP_EXTRA_LIBS = m" | package == hp2ps ] ++ + [ "CC_OPTS = -I" ++ generatedPath | package `elem` [hp2ps, rts]] ++ + [ "MODULES = Main" | package == ghcCabal ] ++ + [ "HS_SRC_DIRS = ." | package == ghcCabal ] ++ + [ "SYNOPSIS = Bootstrapped ghc-cabal." | package == ghcCabal ] + putSuccess $ "| Successfully generated " ++ file + +packageCSources :: Package -> Action [FilePath] +packageCSources pkg + | pkg /= rts = getDirectoryFiles (pkgPath pkg) ["*.c"] + | otherwise = do + windows <- windowsHost + sources <- fmap (map unifyPath) . getDirectoryFiles (pkgPath pkg) . + map (-/- "*.c") $ [ ".", "hooks", "sm", "eventlog", "linker" ] ++ + [ if windows then "win32" else "posix" ] + return $ sources ++ [ rtsBuildPath -/- "c/sm/Evac_thr.c" ] + ++ [ rtsBuildPath -/- "c/sm/Scav_thr.c" ] + +packageAsmSources :: Package -> Action [FilePath] +packageAsmSources pkg + | pkg /= rts = return [] + | otherwise = do + buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] + buildStgCRunAsm <- anyTargetArch ["powerpc64le"] + return $ [ "AdjustorAsm.S" | buildAdjustor ] + ++ [ "StgCRunAsm.S" | buildStgCRunAsm ] - when (package == rts && stage == Stage1) $ do - dataFile %> \mk -> do - orderOnly =<< interpretInContext context generatedDependencies - windows <- windowsHost - let prefix = fixKey (buildPath context) ++ "_" - dirs = [ ".", "hooks", "sm", "eventlog", "linker" ] - ++ [ if windows then "win32" else "posix" ] - cSrcs <- map unifyPath <$> - getDirectoryFiles (pkgPath package) (map (-/- "*.c") dirs) - cmmSrcs <- getDirectoryFiles (pkgPath package) ["*.cmm"] - buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] - buildStgCRunAsm <- anyTargetArch ["powerpc64le"] - let extraCSrcs = [ rtsBuildPath -/- "c/sm/Evac_thr.c" ] - ++ [ rtsBuildPath -/- "c/sm/Scav_thr.c" ] - extraCmmSrcs = [ rtsBuildPath -/- "cmm/AutoApply.cmm" ] - extraAsmSrcs = [ "AdjustorAsm.S" | buildAdjustor ] - ++ [ "StgCRunAsm.S" | buildStgCRunAsm ] - let contents = unlines $ map (prefix ++) - [ "C_SRCS = " ++ unwords (cSrcs ++ extraCSrcs) - , "CMM_SRCS = " ++ unwords (cmmSrcs ++ extraCmmSrcs) - , "S_SRCS = " ++ unwords extraAsmSrcs - , "CC_OPTS = -I" ++ generatedPath - , "COMPONENT_ID = rts" ] - writeFileChanged mk contents - putSuccess $ "| Successfully generated " ++ mk +packageCmmSources :: Package -> Action [FilePath] +packageCmmSources pkg + | pkg /= rts = return [] + | otherwise = do + sources <- getDirectoryFiles (pkgPath pkg) ["*.cmm"] + return $ sources ++ [ rtsBuildPath -/- "cmm/AutoApply.cmm" ] -- Prepare a given 'packaga-data.mk' file for parsing by readConfigFile: -- 1) Drop lines containing '$' From git at git.haskell.org Fri Oct 27 00:43:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install python on CI (c13806a) Message-ID: <20171027004338.4FD8C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c13806a2f5857075f769ec45280cbd3f298e3044/ghc >--------------------------------------------------------------- commit c13806a2f5857075f769ec45280cbd3f298e3044 Author: Andrey Mokhov Date: Thu Oct 5 10:59:49 2017 +0100 Install python on CI See #314 >--------------------------------------------------------------- c13806a2f5857075f769ec45280cbd3f298e3044 appveyor.yml | 2 +- circle.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 451d5d5..c51983a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -22,7 +22,7 @@ install: # Install all Hadrian and GHC build dependencies - cd hadrian - stack setup > nul - - appveyor-retry stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm + - appveyor-retry stack exec -- pacman -S autoconf automake-wrapper make patch python tar --noconfirm build_script: # Build Hadrian diff --git a/circle.yml b/circle.yml index b038689..592b9f4 100644 --- a/circle.yml +++ b/circle.yml @@ -7,7 +7,7 @@ machine: dependencies: override: - brew update - - brew install ghc cabal-install + - brew install ghc cabal-install python - cabal update - cabal install alex happy ansi-terminal mtl shake quickcheck cache_directories: From git at git.haskell.org Fri Oct 27 00:43:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove Shake database on clean. (0bde9c1) Message-ID: <20171027004341.2BE583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0bde9c13cd854c1297296a77be53ec7940045f71/ghc >--------------------------------------------------------------- commit 0bde9c13cd854c1297296a77be53ec7940045f71 Author: Andrey Mokhov Date: Fri Jan 22 14:38:21 2016 +0000 Remove Shake database on clean. See #131. [skip ci] >--------------------------------------------------------------- 0bde9c13cd854c1297296a77be53ec7940045f71 src/Rules/Clean.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 2b4094a..eb7f8de 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -27,4 +27,6 @@ cleanRules = do forM_ [Stage0 ..] $ \stage -> do let dir = pkgPath pkg -/- targetDirectory stage pkg removeDirectoryIfExists dir + putBuild $ "| Remove the Shake database " ++ shakeFilesPath ++ "..." + removeFilesAfter shakeFilesPath ["//*"] putSuccess $ "| Done. " From git at git.haskell.org Fri Oct 27 00:43:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Turn contextDirectory into stageDirectory (241d59a) Message-ID: <20171027004338.809583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/241d59a5f814d5139ca9d6d9bfa0ea127357f505/ghc >--------------------------------------------------------------- commit 241d59a5f814d5139ca9d6d9bfa0ea127357f505 Author: Andrey Mokhov Date: Sat Oct 29 02:11:59 2016 +0100 Turn contextDirectory into stageDirectory >--------------------------------------------------------------- 241d59a5f814d5139ca9d6d9bfa0ea127357f505 src/GHC.hs | 23 ++++++----------------- src/Rules/Clean.hs | 6 ++---- src/Rules/Data.hs | 6 +++--- src/Rules/Generate.hs | 2 +- src/Rules/Register.hs | 2 +- src/Settings.hs | 2 +- src/Settings/Paths.hs | 5 ++--- 7 files changed, 16 insertions(+), 30 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 7cabff5..0312a3e 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -9,7 +9,7 @@ module GHC ( parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, programPath, contextDirectory, rtsContext + defaultKnownPackages, stageDirectory, rtsContext, programPath ) where import Base @@ -91,16 +91,15 @@ xhtml = library "xhtml" ghcSplit :: FilePath ghcSplit = "inplace/lib/bin/ghc-split" --- TODO: The following utils are not included into the build system because --- they seem to be unused or unrelated to the build process: checkUniques, --- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs, --- lndir, mkdirhier, testremove, vagrant +-- | Relative path to the directory containing build artefacts of a given 'Stage'. +stageDirectory :: Stage -> FilePath +stageDirectory = stageString -- TODO: move to buildRootPath, see #113 -- TODO: simplify, add programInplaceLibPath -- | The relative path to the program executable programPath :: Context -> Maybe FilePath -programPath context at Context {..} +programPath Context {..} | package == ghc = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1) | package `elem` [mkUserGuidePart] = case stage of Stage0 -> Just . inplaceProgram $ pkgNameString package @@ -123,19 +122,9 @@ programPath context at Context {..} | otherwise = Nothing where inplaceProgram name = programInplacePath -/- name <.> exe - installProgram name = pkgPath package -/- contextDirectory context + installProgram name = pkgPath package -/- stageDirectory stage -/- "build/tmp" -/- name <.> exe -- TODO: Move this elsewhere. rtsContext :: Context rtsContext = vanillaContext Stage1 rts - --- | GHC build results will be placed into target directories with the --- following typical structure: - --- * @build/@ contains compiled object code --- * @doc/@ is produced by haddock --- * @package-data.mk@ contains output of ghc-cabal applied to pkgCabal -contextDirectory :: Context -> FilePath -contextDirectory Context {..} = stageString stage - diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index 50edd20..e212048 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -1,7 +1,6 @@ module Rules.Clean (cleanRules) where import Base -import Context import Package import Rules.Actions import Settings @@ -19,9 +18,8 @@ cleanRules = do removeDirectory "sdistprep" putBuild $ "| Remove files generated by ghc-cabal..." forM_ knownPackages $ \pkg -> - forM_ [Stage0 ..] $ \stage -> do - let dir = pkgPath pkg -/- contextDirectory (vanillaContext stage pkg) - quietly $ removeDirectory dir + forM_ [Stage0 ..] $ \stage -> + quietly . removeDirectory $ pkgPath pkg -/- stageDirectory stage putBuild $ "| Remove Hadrian files..." removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index cefd2fa..5a4d103 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -19,7 +19,7 @@ buildPackageData context at Context {..} = do let cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile context - oldPath = pkgPath package -/- contextDirectory context -- TODO: remove, #113 + oldPath = pkgPath package -/- stageDirectory stage -- TODO: remove, #113 inTreeMk = oldPath -/- takeFileName dataFile -- TODO: remove, #113 inTreeMk %> \mk -> do @@ -123,7 +123,7 @@ packageCmmSources pkg -- is replaced by libraries_deepseq_dist-install_VERSION = 1.4.0.0 -- Reason: Shake's built-in makefile parser doesn't recognise slashes postProcessPackageData :: Context -> FilePath -> Action () -postProcessPackageData context at Context {..} file = fixFile file fixPackageData +postProcessPackageData Context {..} file = fixFile file fixPackageData where fixPackageData = unlines . map processLine . filter (not . null) . filter ('$' `notElem`) . lines processLine line = fixKey fixedPrefix ++ suffix @@ -132,7 +132,7 @@ postProcessPackageData context at Context {..} file = fixFile file fixPackageData -- Change package/path/targetDir to takeDirectory file -- This is a temporary hack until we get rid of ghc-cabal fixedPrefix = takeDirectory file ++ drop len prefix - len = length (pkgPath package -/- contextDirectory context) + len = length (pkgPath package -/- stageDirectory stage) -- TODO: Remove, see #113. fixKey :: String -> String diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 698299d..f8cf345 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -133,7 +133,7 @@ generatePackageCode context@(Context stage pkg _) = need [primopsTxt stage] build $ Target context GenPrimopCode [primopsTxt stage] [file] -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- contextDirectory context -/- "build" + let oldPath = pkgPath pkg -/- stageDirectory stage -/- "build" newFile = oldPath ++ (drop (length path) file) createDirectory $ takeDirectory newFile liftIO $ IO.copyFile file newFile diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index d4799e3..6b3e239 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -23,7 +23,7 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do -- Post-process inplace-pkg-config. TODO: remove, see #113, #148. let path = buildPath context - oldPath = pkgPath package -/- contextDirectory context + oldPath = pkgPath package -/- stageDirectory stage pkgConfig = oldPath -/- "inplace-pkg-config" oldBuildPath = oldPath -/- "build" fixPkgConf = unlines diff --git a/src/Settings.hs b/src/Settings.hs index 0a71c90..3aab9ac 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -35,7 +35,7 @@ getPackagePath :: Expr FilePath getPackagePath = pkgPath <$> getPackage getContextDirectory :: Expr FilePath -getContextDirectory = contextDirectory <$> getContext +getContextDirectory = stageDirectory <$> getStage getBuildPath :: Expr FilePath getBuildPath = buildPath <$> getContext diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 7147264..07c762a 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -1,5 +1,5 @@ module Settings.Paths ( - contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, + stageDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, @@ -33,8 +33,7 @@ generatedPath = buildRootPath -/- "generated" -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath -buildPath context at Context {..} = - buildRootPath -/- contextDirectory context -/- pkgPath package +buildPath Context {..} = buildRootPath -/- stageDirectory stage -/- pkgPath package -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath From git at git.haskell.org Fri Oct 27 00:43:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install python3 on CircleCI (81a6d1a) Message-ID: <20171027004342.2EB363A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/81a6d1a961ed6e0327f2f34e4955f8628729498a/ghc >--------------------------------------------------------------- commit 81a6d1a961ed6e0327f2f34e4955f8628729498a Author: Andrey Mokhov Date: Thu Oct 5 11:15:17 2017 +0100 Install python3 on CircleCI See #314 >--------------------------------------------------------------- 81a6d1a961ed6e0327f2f34e4955f8628729498a circle.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/circle.yml b/circle.yml index 592b9f4..93cf47f 100644 --- a/circle.yml +++ b/circle.yml @@ -7,7 +7,7 @@ machine: dependencies: override: - brew update - - brew install ghc cabal-install python + - brew install ghc cabal-install python3 - cabal update - cabal install alex happy ansi-terminal mtl shake quickcheck cache_directories: From git at git.haskell.org Fri Oct 27 00:43:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move rtsContext to Settings.Packages.Rts (fd0cb1f) Message-ID: <20171027004342.3C4F13A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fd0cb1f72339c7ec09962f81d4174e14224a6609/ghc >--------------------------------------------------------------- commit fd0cb1f72339c7ec09962f81d4174e14224a6609 Author: Andrey Mokhov Date: Sat Oct 29 02:15:08 2016 +0100 Move rtsContext to Settings.Packages.Rts >--------------------------------------------------------------- fd0cb1f72339c7ec09962f81d4174e14224a6609 src/GHC.hs | 6 +----- src/Rules.hs | 1 + src/Rules/Generate.hs | 1 + src/Settings/Packages/Rts.hs | 5 ++++- 4 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0312a3e..2af8923 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -9,7 +9,7 @@ module GHC ( parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, stageDirectory, rtsContext, programPath + defaultKnownPackages, stageDirectory, programPath ) where import Base @@ -124,7 +124,3 @@ programPath Context {..} inplaceProgram name = programInplacePath -/- name <.> exe installProgram name = pkgPath package -/- stageDirectory stage -/- "build/tmp" -/- name <.> exe - --- TODO: Move this elsewhere. -rtsContext :: Context -rtsContext = vanillaContext Stage1 rts diff --git a/src/Rules.hs b/src/Rules.hs index e62ecc7..68a06c7 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -19,6 +19,7 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings +import Settings.Packages.Rts import Settings.Paths allStages :: [Stage] diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index f8cf345..94bcc40 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -20,6 +20,7 @@ import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Rules.Libffi +import Settings.Packages.Rts import Settings.Paths import Target import UserSettings diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index f2b4035..b3b86a9 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,5 +1,5 @@ module Settings.Packages.Rts ( - rtsPackageArgs, rtsConfIn, rtsConf, rtsLibffiLibraryName + rtsPackageArgs, rtsConfIn, rtsConf, rtsContext, rtsLibffiLibraryName ) where import Base @@ -11,6 +11,9 @@ import Predicate import Settings import Settings.Paths +rtsContext :: Context +rtsContext = vanillaContext Stage1 rts + rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" From git at git.haskell.org Fri Oct 27 00:43:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:43:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add build.stack.sh (93605e1) Message-ID: <20171027004344.AD7093A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/93605e1d7e6644f011c7202f2a3431e927f0d87f/ghc >--------------------------------------------------------------- commit 93605e1d7e6644f011c7202f2a3431e927f0d87f Author: Joe Hillenbrand Date: Fri Jan 22 15:41:24 2016 -0800 Add build.stack.sh >--------------------------------------------------------------- 93605e1d7e6644f011c7202f2a3431e927f0d87f .gitignore | 1 + build.cabal.sh => build.stack.sh | 13 +++---------- stack.yaml | 35 +++++++++++++++++++++++++++++++++++ 3 files changed, 39 insertions(+), 10 deletions(-) diff --git a/.gitignore b/.gitignore index 39cd693..6cc5501 100644 --- a/.gitignore +++ b/.gitignore @@ -4,3 +4,4 @@ cfg/system.config cabal.sandbox.config dist/ .cabal-sandbox/ +.stack-work/ diff --git a/build.cabal.sh b/build.stack.sh similarity index 77% copy from build.cabal.sh copy to build.stack.sh index 8add516..1cc968b 100755 --- a/build.cabal.sh +++ b/build.stack.sh @@ -31,16 +31,9 @@ function rl { absoltueRoot="$(dirname "$(rl "$0")")" cd "$absoltueRoot" -# Initialize sandbox if necessary -if ! ( cabal sandbox hc-pkg list 2>&1 > /dev/null ); then - cabal sandbox init - cabal install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared -fi - -cabal run ghc-shake -- \ +stack build --no-library-profiling + +stack exec ghc-shake -- \ --lint \ --directory "$absoltueRoot/.." \ --colour \ diff --git a/stack.yaml b/stack.yaml new file mode 100644 index 0000000..2bc3b0e --- /dev/null +++ b/stack.yaml @@ -0,0 +1,35 @@ +# For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html + +# Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) +resolver: lts-4.2 + +# Local packages, usually specified by relative directory name +packages: +- '.' + +# Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) +extra-deps: [] + +# Override default flag values for local packages and extra-deps +flags: {} + +# Extra package databases containing global packages +extra-package-dbs: [] + +# Control whether we use the GHC we find on the path +# system-ghc: false + +# Require a specific version of stack, using version ranges +# require-stack-version: -any # Default +# require-stack-version: >= 1.0.0 + +# Override the architecture used by stack, especially useful on Windows +# arch: i386 +# arch: x86_64 + +# Extra directories used by stack for building +# extra-include-dirs: [/path/to/dir] +# extra-lib-dirs: [/path/to/dir] + +# Allow a newer minor version of GHC than the snapshot specifies +# compiler-check: newer-minor From git at git.haskell.org Fri Oct 27 00:59:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop support for -this-package-key (95a23a6) Message-ID: <20171027005921.880083A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95a23a6667824592499775d746a71ee2b8de07fe/ghc >--------------------------------------------------------------- commit 95a23a6667824592499775d746a71ee2b8de07fe Author: Andrey Mokhov Date: Sun Sep 10 23:45:34 2017 +0100 Drop support for -this-package-key >--------------------------------------------------------------- 95a23a6667824592499775d746a71ee2b8de07fe src/Oracles/Flag.hs | 4 +--- src/Settings/Builders/Ghc.hs | 9 ++------- 2 files changed, 3 insertions(+), 10 deletions(-) diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 20aca1f..510b9d2 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -17,7 +17,6 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken - | SupportsThisUnitId | WithLibdw | UseSystemFfi @@ -35,12 +34,11 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" - SupportsThisUnitId -> "supports-this-unit-id" WithLibdw -> "with-libdw" UseSystemFfi -> "use-system-ffi" value <- lookupValueOrError configFile key when (value `notElem` ["YES", "NO", ""]) . error $ "Configuration flag " - ++ quote (key ++ " = " ++ value) ++ "cannot be parsed." + ++ quote (key ++ " = " ++ value) ++ " cannot be parsed." return $ value == "YES" platformSupportsSharedLibs :: Action Bool diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a186e08..7f942f6 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -115,18 +115,13 @@ wayGhcArgs = do , (way == debug || way == debugDynamic) ? pure ["-ticky", "-DTICKY_TICKY"] ] --- FIXME: Get rid of to-be-deprecated -this-package-key. packageGhcArgs :: Args packageGhcArgs = withHsPackage $ \cabalFile -> do - pkgId <- expr $ pkgIdentifier cabalFile - thisArg <- do - not0 <- notStage0 - unit <- expr $ flag SupportsThisUnitId - return $ if not0 || unit then "-this-unit-id " else "-this-package-key " + pkgId <- expr $ pkgIdentifier cabalFile mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" , bootPackageDatabaseArgs - , libraryPackage ? arg (thisArg ++ pkgId) + , libraryPackage ? arg ("-this-unit-id " ++ pkgId) , map ("-package-id " ++) <$> getPkgDataList DepIds ] includeGhcArgs :: Args From git at git.haskell.org Fri Oct 27 00:59:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop cabal_macros_boot.h (bece422) Message-ID: <20171027005925.682103A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bece42266ac98ebbcd901efd62d1ffaf68a482ef/ghc >--------------------------------------------------------------- commit bece42266ac98ebbcd901efd62d1ffaf68a482ef Author: Andrey Mokhov Date: Mon Sep 11 00:03:59 2017 +0100 Drop cabal_macros_boot.h >--------------------------------------------------------------- bece42266ac98ebbcd901efd62d1ffaf68a482ef src/Settings/Packages/GhcCabal.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 0e6e1ea..b525c31 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -17,8 +17,6 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" - , arg "-optP-include" - , arg $ "-optP" ++ pkgPath ghcCabal -/- "cabal_macros_boot.h" , arg "-ilibraries/Cabal/Cabal" , arg "-ilibraries/binary/src" , arg "-ilibraries/filepath" From git at git.haskell.org Fri Oct 27 00:59:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on automated run of boot and configure (6864e8b) Message-ID: <20171027005925.5EF003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6864e8b3d1d1e89b7f37f816caf6851d6052d930/ghc >--------------------------------------------------------------- commit 6864e8b3d1d1e89b7f37f816caf6851d6052d930 Author: Andrey Mokhov Date: Sat May 7 11:46:35 2016 +0100 Add a note on automated run of boot and configure See #234. [skip ci] >--------------------------------------------------------------- 6864e8b3d1d1e89b7f37f816caf6851d6052d930 README.md | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index e0053b0..a8ca935 100644 --- a/README.md +++ b/README.md @@ -25,8 +25,8 @@ follow these steps: * This build system is written in Haskell (obviously) and depends on the following Haskell packages, which need to be installed: `ansi-terminal`, `mtl`, `shake`, `QuickCheck`. -* Get the sources and run standard configuration scripts. It is important for the build -system to be in the `hadrian` directory of the GHC source tree: +* Get the sources. It is important for the build system to be in the `hadrian` directory +of the GHC source tree: ```bash git clone --recursive git://git.haskell.org/ghc.git @@ -38,7 +38,10 @@ system to be in the `hadrian` directory of the GHC source tree: of `make`. You might want to enable parallelism with `-j`. We will further refer to the build script simply as `build`. If you are interested in building in a Cabal sandbox or using Stack, have a look at `build.cabal.sh` and `build.stack.sh` scripts. Also -see [instructions for building GHC on Windows using Stack][windows-build]. +see [instructions for building GHC on Windows using Stack][windows-build]. Note, Hadrian +runs the `boot` and `configure` scripts automatically on the first build, so that you don't +need to. Use `--skip-configure` to suppress this behaviour (see overview of command line +flags below). Using the build system ---------------------- @@ -52,10 +55,13 @@ currently supports several others: * `--flavour=FLAVOUR`: choose a build flavour. Two settings are currently supported: `default` and `quick` (adds `-O0` flag to all GHC invocations and disables library profiling, which speeds up builds by 3-4x). + * `--haddock`: build Haddock documentation. + * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). + * `--skip-configure`: use this flag to suppress the default behaviour of Hadrian that runs the `boot` and `configure` scripts automatically if need be, so that you don't have to remember to run them manually. With `--skip-configure` you will need to manually run: @@ -67,6 +73,7 @@ to remember to run them manually. With `--skip-configure` you will need to manua as you normally do when using `make`. Beware, by default Hadrian may do network I/O on Windows to download necessary tarballs, which may sometimes be undesirable; `--skip-configure` is your friend in such cases. + * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. From git at git.haskell.org Fri Oct 27 00:59:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Echo stdout only if --progress-info={normal, unicorn}. (6ef09f4) Message-ID: <20171027005929.8BD383A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6ef09f44f4c6128971ecaafda61b22cb0befa35c/ghc >--------------------------------------------------------------- commit 6ef09f44f4c6128971ecaafda61b22cb0befa35c Author: Andrey Mokhov Date: Mon May 9 23:31:47 2016 +0100 Echo stdout only if --progress-info={normal, unicorn}. See #235. >--------------------------------------------------------------- 6ef09f44f4c6128971ecaafda61b22cb0befa35c src/Rules/Actions.hs | 27 +++++++++++---------------- src/Rules/Test.hs | 2 +- 2 files changed, 12 insertions(+), 17 deletions(-) diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index fd117ae..4928e00 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,8 @@ module Rules.Actions ( build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, removeFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, - applyPatch, fixFile, runMake, runMakeVerbose, renderLibrary, renderProgram, - runBuilder, makeExecutable + applyPatch, fixFile, runMake, renderLibrary, renderProgram, runBuilder, + makeExecutable ) where import qualified System.Directory as IO @@ -62,7 +62,7 @@ customBuild rs opts target at Target {..} = do need [dir -/- "configure"] -- Inject /bin/bash into `libtool`, instead of /bin/sh let env = AddEnv "CONFIG_SHELL" "/bin/bash" - cmd Shell [Cwd dir] [path] (env:opts) argList + cmd Shell cmdEcho env [Cwd dir] [path] opts argList HsCpp -> captureStdout target path argList GenApply -> captureStdout target path argList @@ -76,6 +76,9 @@ customBuild rs opts target at Target {..} = do _ -> cmd [path] argList +cmdEcho :: CmdOption +cmdEcho = EchoStdout $ cmdProgressInfo `elem` [Normal, Unicorn] + -- | Run a builder, capture the standard output, and write it to a given file. captureStdout :: Target -> FilePath -> [String] -> Action () captureStdout target path argList = do @@ -118,13 +121,13 @@ removeDirectory dir = do copyDirectory :: FilePath -> FilePath -> Action () copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target - quietly $ cmd (EchoStdout False) ["cp", "-r", source, target] + quietly $ cmd cmdEcho ["cp", "-r", source, target] -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () moveDirectory source target = do putProgressInfo $ renderAction "Move directory" source target - quietly $ cmd (EchoStdout False) ["mv", source, target] + quietly $ cmd cmdEcho ["mv", source, target] -- | Transform a given file by applying a function to its contents. fixFile :: FilePath -> (String -> String) -> Action () @@ -138,20 +141,12 @@ fixFile file f = do liftIO $ writeFile file contents runMake :: FilePath -> [String] -> Action () -runMake = runMakeWithVerbosity False - -runMakeVerbose :: FilePath -> [String] -> Action () -runMakeVerbose = runMakeWithVerbosity True - -runMakeWithVerbosity :: Bool -> FilePath -> [String] -> Action () -runMakeWithVerbosity verbose dir args = do +runMake dir args = do need [dir -/- "Makefile"] path <- builderPath Make let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - if verbose - then cmd Shell path ["-C", dir] args - else quietly $ cmd Shell (EchoStdout False) path ["-C", dir] args + quietly $ cmd Shell cmdEcho path ["-C", dir] args applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do @@ -159,7 +154,7 @@ applyPatch dir patch = do needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file - quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch] + quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch] runBuilder :: Builder -> [String] -> Action () runBuilder builder args = do diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 7faf62d..544b5d9 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -18,7 +18,7 @@ testRules = do needBuilder $ Ghc Compile Stage2 needBuilder $ GhcPkg Stage1 needBuilder Hpc - runMakeVerbose "testsuite/tests" ["fast"] + runMake "testsuite/tests" ["fast"] "test" ~> do let yesNo x = show $ if x then "YES" else "NO" From git at git.haskell.org Fri Oct 27 00:59:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refine cross-compilation implementation (#410) (ae1f7c1) Message-ID: <20171027005929.A1CD23A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c/ghc >--------------------------------------------------------------- commit ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c Author: Zhen Zhang Date: Tue Sep 12 00:54:29 2017 +0800 Refine cross-compilation implementation (#410) * Update minimum heap size * Refine cross-compilation implementation >--------------------------------------------------------------- ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c hadrian.cabal | 1 + src/GHC.hs | 4 +++- src/Oracles/Flag.hs | 5 ++++- src/Settings.hs | 4 +++- src/Settings/Builders/Common.hs | 3 ++- src/Settings/Flavours/Development.hs | 2 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/QuickCross.hs | 23 +++++++++++++++++++++++ src/Settings/Flavours/Quickest.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcPkg.hs | 4 ++-- src/Settings/Packages/Haskeline.hs | 2 +- src/UserSettings.hs | 7 +------ 16 files changed, 47 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c From git at git.haskell.org Fri Oct 27 00:59:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for llvm-targets (6d14f09) Message-ID: <20171027005917.746AF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d14f09c81f490704d2798693236f0db68e6e438/ghc >--------------------------------------------------------------- commit 6d14f09c81f490704d2798693236f0db68e6e438 Author: Andrey Mokhov Date: Sat Sep 9 11:39:57 2017 +0100 Add support for llvm-targets See #412 >--------------------------------------------------------------- 6d14f09c81f490704d2798693236f0db68e6e438 cfg/system.config.in | 1 + src/Base.hs | 1 + src/Oracles/Setting.hs | 2 ++ src/Rules/Generate.hs | 5 ++++- 4 files changed, 8 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 34ef7b9..0b05259 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -63,6 +63,7 @@ target-platform-full = @TargetPlatformFull@ target-arch = @TargetArch_CPP@ target-os = @TargetOS_CPP@ target-vendor = @TargetVendor_CPP@ +llvm-target = @LLVMTarget_CPP@ cross-compiling = @CrossCompiling@ diff --git a/src/Base.hs b/src/Base.hs index 942b272..76e8f2b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -106,6 +106,7 @@ inplaceLibCopyTargets :: [FilePath] inplaceLibCopyTargets = map (inplaceLibPath -/-) [ "ghc-usage.txt" , "ghci-usage.txt" + , "llvm-targets" , "platformConstants" , "settings" , "template-hsc.h" ] diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 8af8f38..5f148d4 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -46,6 +46,7 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor + | LlvmTarget | FfiIncludeDir | FfiLibDir | GmpIncludeDir @@ -104,6 +105,7 @@ setting key = lookupValueOrError configFile $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" + LlvmTarget -> "llvm-target" FfiIncludeDir -> "ffi-include-dir" FfiLibDir -> "ffi-lib-dir" GmpIncludeDir -> "gmp-include-dir" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index b23b72d..413abe5 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -11,9 +11,9 @@ import Oracles.ModuleFiles import Oracles.Setting import Rules.Gmp import Rules.Libffi +import Target import Settings import Settings.Packages.Rts -import Target import Utilities -- | Track this file to rebuild generated files whenever it changes. @@ -145,6 +145,7 @@ copyRules :: Rules () copyRules = do (inplaceLibPath -/- "ghc-usage.txt") <~ return "driver" (inplaceLibPath -/- "ghci-usage.txt" ) <~ return "driver" + (inplaceLibPath -/- "llvm-targets") <~ return "." (inplaceLibPath -/- "platformConstants") <~ (buildRoot <&> (-/- generatedDir)) (inplaceLibPath -/- "settings") <~ return "." (inplaceLibPath -/- "template-hsc.h") <~ return (pkgPath hsc2hs) @@ -394,6 +395,7 @@ generateGhcBootPlatformH = do hostVendor <- chooseSetting HostVendor TargetVendor targetPlatform <- getSetting TargetPlatform targetArch <- getSetting TargetArch + llvmTarget <- getSetting LlvmTarget targetOs <- getSetting TargetOs targetVendor <- getSetting TargetVendor return $ unlines @@ -414,6 +416,7 @@ generateGhcBootPlatformH = do , "#define BUILD_ARCH " ++ show buildArch , "#define HOST_ARCH " ++ show hostArch , "#define TARGET_ARCH " ++ show targetArch + , "#define LLVM_TARGET " ++ show llvmTarget , "" , "#define " ++ buildOs ++ "_BUILD_OS 1" , "#define " ++ hostOs ++ "_HOST_OS 1" From git at git.haskell.org Fri Oct 27 00:59:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add Make builder. (f31a7de) Message-ID: <20171027005933.A9C683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f31a7de2d4a6886edc64ff5bfb3301bbdee7cc2c/ghc >--------------------------------------------------------------- commit f31a7de2d4a6886edc64ff5bfb3301bbdee7cc2c Author: Andrey Mokhov Date: Tue May 10 00:32:04 2016 +0100 Add Make builder. >--------------------------------------------------------------- f31a7de2d4a6886edc64ff5bfb3301bbdee7cc2c hadrian.cabal | 1 + src/Builder.hs | 4 ++-- src/Rules/Actions.hs | 19 +++++++------------ src/Rules/Gmp.hs | 2 +- src/Rules/Libffi.hs | 2 +- src/Rules/Test.hs | 5 +++-- src/Settings/Args.hs | 2 ++ 7 files changed, 17 insertions(+), 18 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 160a5d0..2dfd9e9 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -84,6 +84,7 @@ executable hadrian , Settings.Builders.Hsc2Hs , Settings.Builders.HsCpp , Settings.Builders.Ld + , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default , Settings.Packages diff --git a/src/Builder.hs b/src/Builder.hs index a205067..76f0988 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -49,7 +49,7 @@ data Builder = Alex | HsCpp | Hsc2Hs | Ld - | Make + | Make FilePath | Nm | Objdump | Patch @@ -111,7 +111,7 @@ builderPath builder = case builderProvenance builder of HsColour -> fromKey "hscolour" HsCpp -> fromKey "hs-cpp" Ld -> fromKey "ld" - Make -> fromKey "make" + Make _ -> fromKey "make" Nm -> fromKey "nm" Objdump -> fromKey "objdump" Patch -> fromKey "patch" diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs index 4928e00..4a0844b 100644 --- a/src/Rules/Actions.hs +++ b/src/Rules/Actions.hs @@ -1,8 +1,7 @@ module Rules.Actions ( - build, buildWithResources, buildWithCmdOptions, copyFile, moveFile, - removeFile, createDirectory, removeDirectory, copyDirectory, moveDirectory, - applyPatch, fixFile, runMake, renderLibrary, renderProgram, runBuilder, - makeExecutable + build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, + removeFile, copyDirectory, createDirectory, moveDirectory, removeDirectory, + applyPatch, renderLibrary, renderProgram, runBuilder, makeExecutable ) where import qualified System.Directory as IO @@ -74,6 +73,10 @@ customBuild rs opts target at Target {..} = do Stdout output <- cmd (Stdin input) [path] argList writeFileChanged file output + Make dir -> do + need [dir -/- "Makefile"] + cmd Shell cmdEcho path ["-C", dir] argList + _ -> cmd [path] argList cmdEcho :: CmdOption @@ -140,14 +143,6 @@ fixFile file f = do return new liftIO $ writeFile file contents -runMake :: FilePath -> [String] -> Action () -runMake dir args = do - need [dir -/- "Makefile"] - path <- builderPath Make - let note = if null args then "" else " (" ++ intercalate ", " args ++ ")" - putBuild $ "| Run make" ++ note ++ " in " ++ dir ++ "..." - quietly $ cmd Shell cmdEcho path ["-C", dir] args - applyPatch :: FilePath -> FilePath -> Action () applyPatch dir patch = do let file = dir -/- patch diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1121d5d..fe5b684 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -84,7 +84,7 @@ gmpRules = do [gmpBuildPath -/- "Makefile.in"] [gmpBuildPath -/- "Makefile"] - runMake gmpBuildPath ["MAKEFLAGS="] + build $ Target gmpContext (Make gmpBuildPath) [] [] createDirectory $ takeDirectory gmpLibraryH copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryH diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 20d5acf..3269a31 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -99,7 +99,7 @@ libffiRules = do -- The old build system did runMake libffiBuildPath ["MAKEFLAGS="] -- TODO: Find out why. It seems redundant, so I removed it. - runMake libffiBuildPath ["MAKEFLAGS=", "install"] + build $ Target libffiContext (Make libffiBuildPath) [] [] let ffiHDir = libffiBuildPath -/- "inst/lib" -/- libname -/- "include" forM_ ["ffi.h", "ffitarget.h"] $ \file -> do diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 544b5d9..7ec5e04 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -3,13 +3,14 @@ module Rules.Test (testRules) where import Base import Builder import Expression -import GHC (rts, libffi) +import GHC (compiler, rts, libffi) import Oracles.Config.Flag import Oracles.Config.Setting import Oracles.WindowsPath import Rules.Actions import Settings.Packages import Settings.User +import Target -- TODO: clean up after testing testRules :: Rules () @@ -18,7 +19,7 @@ testRules = do needBuilder $ Ghc Compile Stage2 needBuilder $ GhcPkg Stage1 needBuilder Hpc - runMake "testsuite/tests" ["fast"] + build $ Target (vanillaContext Stage2 compiler) (Make "testsuite/tests") [] [] "test" ~> do let yesNo x = show $ if x then "YES" else "NO" diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index b7c369f..d8c3649 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -17,6 +17,7 @@ import Settings.Builders.Happy import Settings.Builders.Hsc2Hs import Settings.Builders.HsCpp import Settings.Builders.Ld +import Settings.Builders.Make import Settings.Builders.Tar import Settings.Flavours.Quick import Settings.Packages.Base @@ -66,6 +67,7 @@ defaultBuilderArgs = mconcat , hsc2hsBuilderArgs , hsCppBuilderArgs , ldBuilderArgs + , makeBuilderArgs , tarBuilderArgs ] defaultPackageArgs :: Args From git at git.haskell.org Fri Oct 27 00:59:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix performance bug: Stage0 packages do not depend on inplaceLibCopyTargets (17be7a1) Message-ID: <20171027005933.CA6CE3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/17be7a10e780a792e7082aa1f8bef0b0887957a5/ghc >--------------------------------------------------------------- commit 17be7a10e780a792e7082aa1f8bef0b0887957a5 Author: Andrey Mokhov Date: Thu Sep 14 01:13:37 2017 +0100 Fix performance bug: Stage0 packages do not depend on inplaceLibCopyTargets See #393 >--------------------------------------------------------------- 17be7a10e780a792e7082aa1f8bef0b0887957a5 src/Settings/Builders/GhcCabal.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index fc39637..c555bf0 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -6,15 +6,14 @@ import Hadrian.Haskell.Cabal import Context import Flavour -import Settings.Builders.Common hiding (package) +import Settings.Builders.Common ghcCabalBuilderArgs :: Args ghcCabalBuilderArgs = builder GhcCabal ? do verbosity <- expr getVerbosity top <- expr topDirectory - context <- getContext path <- getBuildPath - when (package context /= deriveConstants) $ expr (need inplaceLibCopyTargets) + notStage0 ? expr (need inplaceLibCopyTargets) mconcat [ arg "configure" , arg =<< pkgPath <$> getPackage , arg $ top -/- path From git at git.haskell.org Fri Oct 27 00:59:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing Settings.Flavours.Quick module. (6da6b45) Message-ID: <20171027005937.259743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6da6b454c1a8ff2df7e54a165b28e103d5e6a0f2/ghc >--------------------------------------------------------------- commit 6da6b454c1a8ff2df7e54a165b28e103d5e6a0f2 Author: Andrey Mokhov Date: Tue May 10 01:05:59 2016 +0100 Add missing Settings.Flavours.Quick module. >--------------------------------------------------------------- 6da6b454c1a8ff2df7e54a165b28e103d5e6a0f2 hadrian.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/hadrian.cabal b/hadrian.cabal index 2dfd9e9..5c13f7a 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -87,6 +87,7 @@ executable hadrian , Settings.Builders.Make , Settings.Builders.Tar , Settings.Default + , Settings.Flavours.Quick , Settings.Packages , Settings.Packages.Base , Settings.Packages.Compiler From git at git.haskell.org Fri Oct 27 00:59:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependency of hsc2hs on template-hsc.h (fdd223e) Message-ID: <20171027005937.4144B3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fdd223e91e2d5226bc6f589e3a17808b5b8eef6a/ghc >--------------------------------------------------------------- commit fdd223e91e2d5226bc6f589e3a17808b5b8eef6a Author: Andrey Mokhov Date: Thu Sep 14 12:54:59 2017 +0100 Add missing dependency of hsc2hs on template-hsc.h >--------------------------------------------------------------- fdd223e91e2d5226bc6f589e3a17808b5b8eef6a src/Builder.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index d70ecab..2e8aca1 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -124,6 +124,8 @@ instance H.Builder Builder where needBuilder :: Builder -> Action () needBuilder (Configure dir) = need [dir -/- "configure"] + needBuilder Hsc2Hs = do path <- H.builderPath Hsc2Hs + need [path, templateHscPath] needBuilder (Make dir) = need [dir -/- "Makefile"] needBuilder builder = when (isJust $ builderProvenance builder) $ do path <- H.builderPath builder From git at git.haskell.org Fri Oct 27 00:59:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix configureBuilderArgs name. (e19cd9f) Message-ID: <20171027005941.0B26F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e19cd9ffd1cf551529d8f00a4715d2a53048154a/ghc >--------------------------------------------------------------- commit e19cd9ffd1cf551529d8f00a4715d2a53048154a Author: Andrey Mokhov Date: Tue May 10 01:06:35 2016 +0100 Fix configureBuilderArgs name. >--------------------------------------------------------------- e19cd9ffd1cf551529d8f00a4715d2a53048154a src/Settings/Args.hs | 2 +- src/Settings/Builders/Configure.hs | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs index d8c3649..1e239a4 100644 --- a/src/Settings/Args.hs +++ b/src/Settings/Args.hs @@ -53,7 +53,7 @@ defaultBuilderArgs = mconcat [ alexBuilderArgs , arBuilderArgs , ccBuilderArgs - , configureArgs + , configureBuilderArgs , deriveConstantsBuilderArgs , genApplyBuilderArgs , genPrimopCodeBuilderArgs diff --git a/src/Settings/Builders/Configure.hs b/src/Settings/Builders/Configure.hs index 813b79d..b0cb4bd 100644 --- a/src/Settings/Builders/Configure.hs +++ b/src/Settings/Builders/Configure.hs @@ -1,4 +1,4 @@ -module Settings.Builders.Configure (configureArgs) where +module Settings.Builders.Configure (configureBuilderArgs) where import Base import Expression @@ -6,8 +6,8 @@ import Oracles.Config.Setting import Predicates (builder) import Settings -configureArgs :: Args -configureArgs = mconcat +configureBuilderArgs :: Args +configureBuilderArgs = mconcat [ builder (Configure libffiBuildPath) ? do top <- getTopDirectory targetPlatform <- getSetting TargetPlatform From git at git.haskell.org Fri Oct 27 00:59:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Need rts at the top-level to allow more parallelism (adc8e35) Message-ID: <20171027005941.2C5CC3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/adc8e3531a5e301b4c00eaf4372c8a3b8a0205cc/ghc >--------------------------------------------------------------- commit adc8e3531a5e301b4c00eaf4372c8a3b8a0205cc Author: Andrey Mokhov Date: Thu Sep 14 18:23:47 2017 +0100 Need rts at the top-level to allow more parallelism See #393 >--------------------------------------------------------------- adc8e3531a5e301b4c00eaf4372c8a3b8a0205cc src/Rules.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index fcf3f65..ea3df45 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -32,7 +32,7 @@ allStages = [minBound ..] -- 'Stage1Only' flag. topLevelTargets :: Rules () topLevelTargets = action $ do - let libraryPackages = filter isLibrary (knownPackages \\ [rts, libffi]) + let libraryPackages = filter isLibrary (knownPackages \\ [libffi]) need =<< if stage1Only then do libs <- concatForM [Stage0, Stage1] $ \stage -> @@ -41,11 +41,10 @@ topLevelTargets = action $ do return $ libs ++ prgs ++ inplaceLibCopyTargets else do targets <- concatForM allStages $ \stage -> - concatForM (knownPackages \\ [rts, libffi]) $ + concatForM (knownPackages \\ [libffi]) $ packageTargets False stage return $ targets ++ inplaceLibCopyTargets - -- TODO: Get rid of the @includeGhciLib@ hack. -- | Return the list of targets associated with a given 'Stage' and 'Package'. -- By setting the Boolean parameter to False it is possible to exclude the GHCi @@ -62,14 +61,15 @@ packageTargets includeGhciLib stage pkg = do then return [] -- Skip inactive packages. else if isLibrary pkg then do -- Collect all targets of a library package. - ways <- interpretInContext context getLibraryWays + let pkgWays = if pkg == rts then getRtsWays else getLibraryWays + ways <- interpretInContext context pkgWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context =<< buildHaddock <$> flavour more <- libraryTargets includeGhciLib context setup <- pkgSetupConfigFile context haddock <- pkgHaddockFile context - return $ [ setup | nonCabalContext context ] - ++ [ haddock | docs && stage == Stage1 ] + return $ [ setup | not $ nonCabalContext context ] + ++ [ haddock | pkg /= rts && docs && stage == Stage1 ] ++ libs ++ more else do -- The only target of a program package is the executable. prgContext <- programContext stage pkg From git at git.haskell.org Fri Oct 27 00:59:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise stage1 compiler (9a1b659) Message-ID: <20171027005944.97B623A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a1b6591a9a91097ac93dd1d461d8fac2856ed66/ghc >--------------------------------------------------------------- commit 9a1b6591a9a91097ac93dd1d461d8fac2856ed66 Author: Andrey Mokhov Date: Fri Sep 15 00:46:38 2017 +0100 Optimise stage1 compiler See #393 >--------------------------------------------------------------- 9a1b6591a9a91097ac93dd1d461d8fac2856ed66 doc/flavours.md | 4 ++-- src/Settings/Flavours/Quickest.hs | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index 3bf0c30..042475e 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -61,9 +61,9 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O0
-H32m + -O - - + -O diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 3c507bc..88922ec 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -15,8 +15,8 @@ quickestArgs :: Args quickestArgs = sourceArgs $ SourceArgs { hsDefault = pure ["-O0", "-H64m"] , hsLibrary = mempty - , hsCompiler = mempty - , hsGhc = mempty } + , hsCompiler = stage0 ? arg "-O" + , hsGhc = stage0 ? arg "-O" } quickestRtsWays :: Ways quickestRtsWays = mconcat From git at git.haskell.org Fri Oct 27 00:59:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add makeBuilderArgs. (d27501d) Message-ID: <20171027005944.7DFE23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d27501d1f279c145fd4c76809c6fab272f53cc4c/ghc >--------------------------------------------------------------- commit d27501d1f279c145fd4c76809c6fab272f53cc4c Author: Andrey Mokhov Date: Tue May 10 01:07:25 2016 +0100 Add makeBuilderArgs. >--------------------------------------------------------------- d27501d1f279c145fd4c76809c6fab272f53cc4c src/Settings/Builders/Make.hs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs new file mode 100644 index 0000000..85f16ac --- /dev/null +++ b/src/Settings/Builders/Make.hs @@ -0,0 +1,11 @@ +module Settings.Builders.Make (makeBuilderArgs) where + +import Expression +import Predicates (builder) +import Settings + +makeBuilderArgs :: Args +makeBuilderArgs = mconcat + [ builder (Make "testsuite/tests") ? arg "fast" + , builder (Make gmpBuildPath ) ? arg "MAKEFLAGS=" + , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=", "install"] ] From git at git.haskell.org Fri Oct 27 00:59:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do not unify paths on each -/- invocation. (6e953f1) Message-ID: <20171027005948.181743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6e953f10e2c445addda3ade10191c60d90546ef4/ghc >--------------------------------------------------------------- commit 6e953f10e2c445addda3ade10191c60d90546ef4 Author: Andrey Mokhov Date: Tue May 10 02:26:26 2016 +0100 Do not unify paths on each -/- invocation. See #220. >--------------------------------------------------------------- 6e953f10e2c445addda3ade10191c60d90546ef4 src/Base.hs | 4 ++-- src/Oracles/ModuleFiles.hs | 4 +++- src/Oracles/WindowsPath.hs | 2 +- src/Rules/Wrappers/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Paths.hs | 21 ++++++++------------- 6 files changed, 16 insertions(+), 19 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 1fcbae7..bd80f47 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -87,9 +87,9 @@ versionToInt s = major * 1000 + minor * 10 + patch unifyPath :: FilePath -> FilePath unifyPath = toStandard . normaliseEx --- | Combine paths using '' and apply 'unifyPath' to the result +-- | Combine paths with a forward slash regardless of platform. (-/-) :: FilePath -> FilePath -> FilePath -a -/- b = unifyPath $ a b +a -/- b = a ++ '/' : b infixr 6 -/- diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 652eb9a..897b2e0 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -39,7 +39,9 @@ decodeModule = splitFileName . replaceEq '.' '/' -- > encodeModule "./" "Prelude" == "Prelude" -- > uncurry encodeModule (decodeModule name) == name encodeModule :: FilePath -> String -> String -encodeModule dir file = replaceEq '/' '.' $ dir -/- takeBaseName file +encodeModule dir file + | dir == "./" = replaceEq '/' '.' $ takeBaseName file + | otherwise = replaceEq '/' '.' $ dir ++ takeBaseName file -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs index a0343fb..e252bba 100644 --- a/src/Oracles/WindowsPath.hs +++ b/src/Oracles/WindowsPath.hs @@ -25,7 +25,7 @@ fixAbsolutePathOnWindows path = do then do let (dir, file) = splitFileName path winDir <- askOracle $ WindowsPath dir - return $ winDir -/- file + return $ winDir ++ file else return path diff --git a/src/Rules/Wrappers/Ghc.hs b/src/Rules/Wrappers/Ghc.hs index 343f780..7338450 100644 --- a/src/Rules/Wrappers/Ghc.hs +++ b/src/Rules/Wrappers/Ghc.hs @@ -11,4 +11,4 @@ ghcWrapper program = do return $ unlines [ "#!/bin/bash" , "exec " ++ (top -/- program) - ++ " -B" ++ (top -/- "inplace" -/- "lib") ++ " ${1+\"$@\"}" ] + ++ " -B" ++ (top -/- "inplace/lib") ++ " ${1+\"$@\"}" ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 9f6c6e2..faeb99d 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -128,7 +128,7 @@ with b = specified b ? do top <- getTopDirectory path <- getBuilderPath b lift $ needBuilder b - append [withBuilderKey b ++ top -/- path] + arg $ withBuilderKey b ++ unifyPath (top path) withStaged :: (Stage -> Builder) -> Args withStaged sb = with . sb =<< getStage diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 7174a94..288544b 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -12,11 +12,6 @@ import GHC import Oracles.PackageData import Settings.User --- A more efficient version of '-/-' which assumes that given FilePaths have --- already been unified. See #218. TODO: Switch to 'newtype FilePath'. -(~/~) :: FilePath -> FilePath -> FilePath -x ~/~ y = x ++ '/' : y - shakeFilesPath :: FilePath shakeFilesPath = buildRootPath -/- "hadrian/shake-files" @@ -29,17 +24,17 @@ packageDependencies = shakeFilesPath -/- "package-dependencies" -- | Path to the directory containing build artefacts of a given 'Context'. buildPath :: Context -> FilePath buildPath context at Context {..} = - buildRootPath ~/~ contextDirectory context ~/~ pkgPath package + buildRootPath -/- contextDirectory context -/- pkgPath package -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath -pkgDataFile context = buildPath context ~/~ "package-data.mk" +pkgDataFile context = buildPath context -/- "package-data.mk" -- | Path to the haddock file of a given 'Context', e.g.: -- ".build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = - buildPath context ~/~ "doc/html" ~/~ name ~/~ name <.> "haddock" + buildPath context -/- "doc/html" -/- name -/- name <.> "haddock" where name = pkgNameString package -- | Path to the library file of a given 'Context', e.g.: @@ -65,11 +60,11 @@ pkgFile :: Context -> String -> String -> Action FilePath pkgFile context prefix suffix = do let path = buildPath context componentId <- pkgData $ ComponentId path - return $ path ~/~ prefix ++ componentId ++ suffix + return $ path -/- prefix ++ componentId ++ suffix -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath ~/~ "stage1/gmp" +gmpBuildPath = buildRootPath -/- "stage1/gmp" -- | Path to the GMP library. gmpLibrary :: FilePath @@ -85,7 +80,7 @@ gmpObjects = gmpBuildPath -/- "objs" -- | Path to the GMP library buildinfo file. gmpBuildInfoPath :: FilePath -gmpBuildInfoPath = pkgPath integerGmp ~/~ "integer-gmp.buildinfo" +gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" -- | Build directory for in-tree libffi library. libffiBuildPath :: FilePath @@ -95,11 +90,11 @@ libffiBuildPath = buildRootPath -/- "stage1/libffi" -- StageN, N > 0, share the same packageDbDirectory -- | Path to package database directory of a given 'Stage'. packageDbDirectory :: Stage -> FilePath -packageDbDirectory Stage0 = buildRootPath ~/~ "stage0/bootstrapping.conf" +packageDbDirectory Stage0 = buildRootPath -/- "stage0/bootstrapping.conf" packageDbDirectory _ = "inplace/lib/package.conf.d" -- | Path to the configuration file of a given 'Context'. pkgConfFile :: Context -> Action FilePath pkgConfFile context at Context {..} = do componentId <- pkgData . ComponentId $ buildPath context - return $ packageDbDirectory stage ~/~ componentId <.> "conf" + return $ packageDbDirectory stage -/- componentId <.> "conf" From git at git.haskell.org Fri Oct 27 00:59:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update docs to list -H64m (101d787) Message-ID: <20171027005948.2D7723A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/101d78755ac2f1afd71eb7c9165afb9a84705c9a/ghc >--------------------------------------------------------------- commit 101d78755ac2f1afd71eb7c9165afb9a84705c9a Author: Andrey Mokhov Date: Fri Sep 15 01:24:53 2017 +0100 Update docs to list -H64m [skip ci] >--------------------------------------------------------------- 101d78755ac2f1afd71eb7c9165afb9a84705c9a doc/flavours.md | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index 042475e..185cf6b 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -35,8 +35,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH default
- -O
-H32m
- -O2
-H32m + -O
-H64m
+ -O2
-H64m @@ -46,8 +46,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quick - -O0
-H32m - -O0
-H32m + -O0
-H64m + -O0
-H64m -O -O @@ -57,8 +57,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quickest - -O0
-H32m - -O0
-H32m + -O0
-H64m + -O0
-H64m -O @@ -68,8 +68,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH perf - -O
-H32m - -O
-H32m + -O
-H64m + -O
-H64m -O2 -O @@ -79,8 +79,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH prof - -O0
-H32m - -O0
-H32m + -O0
-H64m + -O0
-H64m -O -O @@ -90,8 +90,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel1 - -O
-H32m - -O
-H32m + -O
-H64m + -O
-H64m -dcore-lint -O0
-DDEBUG @@ -101,8 +101,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel2 - -O
-H32m - -O
-H32m + -O
-H64m + -O
-H64m -dcore-lint From git at git.haskell.org Fri Oct 27 00:59:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update comments. (7239000) Message-ID: <20171027005952.379123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7239000ffaeada9c33343aeddc28e121c3366af4/ghc >--------------------------------------------------------------- commit 7239000ffaeada9c33343aeddc28e121c3366af4 Author: Andrey Mokhov Date: Tue May 10 02:31:16 2016 +0100 Update comments. [skip ci] >--------------------------------------------------------------- 7239000ffaeada9c33343aeddc28e121c3366af4 src/Oracles/ModuleFiles.hs | 4 ++-- src/Rules/Dependencies.hs | 8 ++++---- src/Rules/Library.hs | 4 ++-- src/Settings/Paths.hs | 8 ++++---- 4 files changed, 12 insertions(+), 12 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index 897b2e0..e77d2ba 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -45,10 +45,10 @@ encodeModule dir file -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) --- ".build/stage1/compiler/build/Lexer.hs" +-- "_build/stage1/compiler/build/Lexer.hs" -- == Just ("compiler/parser/Lexer.x", Alex) -- findGenerator (Context Stage1 base vanilla) --- ".build/stage1/base/build/Prelude.hs" +-- "_build/stage1/base/build/Prelude.hs" -- == Nothing findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder)) findGenerator Context {..} file = do diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index f5d781a..78f4d40 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -49,8 +49,8 @@ buildPackageDependencies rs context at Context {..} = -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' -- to its dependencies. For example, in vanillaContext Stage1 rts: --- * "Task.c" -> ".build/stage1/rts/Task.c.deps" --- * ".build/stage1/rts/AutoApply.cmm" -> ".build/stage1/rts/AutoApply.cmm.deps" +-- * "Task.c" -> "_build/stage1/rts/Task.c.deps" +-- * "_build/stage1/rts/AutoApply.cmm" -> "_build/stage1/rts/AutoApply.cmm.deps" src2dep :: Context -> FilePath -> FilePath src2dep context src | buildRootPath `isPrefixOf` src = src <.> "deps" @@ -58,8 +58,8 @@ src2dep context src -- Given a 'Context' and a 'FilePath' to a file with dependencies, compute the -- 'FilePath' to the source file. For example, in vanillaContext Stage1 rts: --- * ".build/stage1/rts/Task.c.deps" -> "Task.c" --- * ".build/stage1/rts/AutoApply.cmm.deps" -> ".build/stage1/rts/AutoApply.cmm" +-- * "_build/stage1/rts/Task.c.deps" -> "Task.c" +-- * "_build/stage1/rts/AutoApply.cmm.deps" -> "_build/stage1/rts/AutoApply.cmm" dep2src :: Context -> FilePath -> FilePath dep2src context at Context {..} dep | takeBaseName dep `elem` [ "AutoApply.cmm", "Evac_thr.c", "Scav_thr.c" ] = src diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 0538e4e..a45b591 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -76,8 +76,8 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do -- TODO: Get rid of code duplication and simplify. See also src2dep. -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' -- to its object file. For example, in Context Stage1 rts threaded: --- * "Task.c" -> ".build/stage1/rts/Task.thr_o" --- * ".build/stage1/rts/sm/Evac_thr.c" -> ".build/stage1/rts/sm/Evac_thr.thr_o" +-- * "Task.c" -> "_build/stage1/rts/Task.thr_o" +-- * "_build/stage1/rts/sm/Evac_thr.c" -> "_build/stage1/rts/sm/Evac_thr.thr_o" objFile :: Context -> FilePath -> FilePath objFile context at Context {..} src | buildRootPath `isPrefixOf` src = src -<.> osuf way diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs index 288544b..c39b12b 100644 --- a/src/Settings/Paths.hs +++ b/src/Settings/Paths.hs @@ -31,28 +31,28 @@ pkgDataFile :: Context -> FilePath pkgDataFile context = buildPath context -/- "package-data.mk" -- | Path to the haddock file of a given 'Context', e.g.: --- ".build/stage1/libraries/array/doc/html/array/array.haddock". +-- "_build/stage1/libraries/array/doc/html/array/array.haddock". pkgHaddockFile :: Context -> FilePath pkgHaddockFile context at Context {..} = buildPath context -/- "doc/html" -/- name -/- name <.> "haddock" where name = pkgNameString package -- | Path to the library file of a given 'Context', e.g.: --- ".build/stage1/libraries/array/build/libHSarray-0.5.1.0.a". +-- "_build/stage1/libraries/array/build/libHSarray-0.5.1.0.a". pkgLibraryFile :: Context -> Action FilePath pkgLibraryFile context at Context {..} = do extension <- libsuf way pkgFile context "libHS" extension -- | Path to the auxiliary library file of a given 'Context', e.g.: --- ".build/stage1/compiler/build/libHSghc-8.1-0.a". +-- "_build/stage1/compiler/build/libHSghc-8.1-0.a". pkgLibraryFile0 :: Context -> Action FilePath pkgLibraryFile0 context at Context {..} = do extension <- libsuf way pkgFile context "libHS" ("-0" ++ extension) -- | Path to the GHCi library file of a given 'Context', e.g.: --- ".build/stage1/libraries/array/build/HSarray-0.5.1.0.o". +-- "_build/stage1/libraries/array/build/HSarray-0.5.1.0.o". pkgGhciLibraryFile :: Context -> Action FilePath pkgGhciLibraryFile context = pkgFile context "HS" ".o" From git at git.haskell.org Fri Oct 27 00:59:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement documentation building (#413) (97fa508) Message-ID: <20171027005952.581FD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d/ghc >--------------------------------------------------------------- commit 97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d Author: Patrick Dougherty Date: Sat Sep 16 07:14:30 2017 -0500 Implement documentation building (#413) * Implement documentation building * Clean up for merge >--------------------------------------------------------------- 97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d cfg/system.config.in | 3 +- hadrian.cabal | 2 + src/Builder.hs | 55 +++++++++++--- src/Context.hs | 6 +- src/Main.hs | 2 + src/Rules/Documentation.hs | 155 +++++++++++++++++++++++++++++++++++--- src/Rules/Gmp.hs | 2 +- src/Rules/Install.hs | 3 - src/Rules/Libffi.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 11 +-- src/Settings/Builders/Haddock.hs | 92 +++++++++++----------- src/Settings/Builders/Sphinx.hs | 22 ++++++ src/Settings/Builders/Tar.hs | 20 +++-- src/Settings/Builders/Xelatex.hs | 7 ++ src/Settings/Default.hs | 7 +- src/Settings/Packages/Compiler.hs | 2 +- 18 files changed, 298 insertions(+), 97 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 97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d From git at git.haskell.org Fri Oct 27 00:59:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add predicate input, rename predicate file to output. (caf0d6a) Message-ID: <20171027005956.4FE553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8/ghc >--------------------------------------------------------------- commit caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8 Author: Andrey Mokhov Date: Wed May 11 23:29:15 2016 +0100 Add predicate input, rename predicate file to output. See #245. >--------------------------------------------------------------- caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8 src/Predicates.hs | 11 ++++++--- src/Settings/Builders/DeriveConstants.hs | 16 +++++++------- src/Settings/Builders/GenPrimopCode.hs | 38 ++++++++++++++++---------------- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Packages/Rts.hs | 14 ++++++------ src/Settings/Packages/RunGhc.hs | 4 ++-- 7 files changed, 46 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc caf0d6a617bd6e83c9e19df5ecd60e8c2ce253a8 From git at git.haskell.org Fri Oct 27 00:59:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid running commands with the Shell option, which breaks due to spaces in paths (f479c5d) Message-ID: <20171027005956.781083A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f479c5d51dfee88abaad7dc3aeb19ea518948a19/ghc >--------------------------------------------------------------- commit f479c5d51dfee88abaad7dc3aeb19ea518948a19 Author: Andrey Mokhov Date: Sun Sep 17 00:41:12 2017 +0100 Avoid running commands with the Shell option, which breaks due to spaces in paths * Fixes the docs build rule on Windows See #414 >--------------------------------------------------------------- f479c5d51dfee88abaad7dc3aeb19ea518948a19 src/Builder.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 72cbb15..355878f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -185,7 +185,7 @@ instance H.Builder Builder where -- otherwise Windows breaks. TODO: Figure out why. bash <- bashPath let env = AddEnv "CONFIG_SHELL" bash - cmd Shell echo env [Cwd dir] [path] buildOptions buildArgs + cmd echo env [Cwd dir] ["sh", path] buildOptions buildArgs HsCpp -> captureStdout GenApply -> captureStdout @@ -195,16 +195,15 @@ instance H.Builder Builder where Stdout stdout <- cmd (Stdin stdin) [path] buildArgs writeFileChanged output stdout - Make dir -> cmd Shell echo path ["-C", dir] buildArgs + Make dir -> cmd echo path ["-C", dir] buildArgs Xelatex -> do - unit $ cmd Shell [Cwd output] [path] buildArgs - unit $ cmd Shell [Cwd output] [path] buildArgs - unit $ cmd Shell [Cwd output] [path] buildArgs - unit $ cmd Shell [Cwd output] ["makeindex"] - (input -<.> "idx") - unit $ cmd Shell [Cwd output] [path] buildArgs - cmd Shell [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] ["makeindex"] (input -<.> "idx") + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs _ -> cmd echo [path] buildArgs @@ -226,7 +225,7 @@ systemBuilderPath builder = case builder of Cc _ Stage0 -> fromKey "system-cc" Cc _ _ -> fromKey "cc" -- We can't ask configure for the path to configure! - Configure _ -> return "sh configure" + Configure _ -> return "configure" Ghc _ Stage0 -> fromKey "system-ghc" GhcPkg _ Stage0 -> fromKey "system-ghc-pkg" Happy -> fromKey "happy" @@ -266,7 +265,7 @@ applyPatch dir patch = do needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file - quietly $ cmd Shell [Cwd dir] [path, "-p0 <", patch] + quietly $ cmd [Cwd dir, FileStdin file] [path, "-p0"] -- | Install a directory. installDirectory :: FilePath -> Action () From git at git.haskell.org Fri Oct 27 00:59:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 00:59:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing path unifications. (bc5b5e1) Message-ID: <20171027005959.EE1813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bc5b5e167368ecbf4e53cbbf9833cdfca9604211/ghc >--------------------------------------------------------------- commit bc5b5e167368ecbf4e53cbbf9833cdfca9604211 Author: Andrey Mokhov Date: Thu May 12 01:05:08 2016 +0100 Add missing path unifications. >--------------------------------------------------------------- bc5b5e167368ecbf4e53cbbf9833cdfca9604211 src/Oracles/ModuleFiles.hs | 20 +++++++++++--------- src/Rules/Data.hs | 6 ++++-- src/Rules/Selftest.hs | 8 ++++---- 3 files changed, 19 insertions(+), 15 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index e77d2ba..233cdc0 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -28,20 +28,22 @@ determineBuilder file = case takeExtension file of -- | Given a module name extract the directory and file name, e.g.: -- --- > decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") --- > decodeModule "Prelude" == ("./", "Prelude") +-- > decodeModule "Data.Functor.Identity" == ("Data/Functor", "Identity") +-- > decodeModule "Prelude" == ("", "Prelude") decodeModule :: String -> (FilePath, String) -decodeModule = splitFileName . replaceEq '.' '/' +decodeModule modName = (intercalate "/" (init xs), last xs) + where + xs = words $ replaceEq '.' ' ' modName -- | Given the directory and file name find the corresponding module name, e.g.: -- --- > encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" --- > encodeModule "./" "Prelude" == "Prelude" --- > uncurry encodeModule (decodeModule name) == name +-- > encodeModule "Data/Functor" "Identity.hs" == "Data.Functor.Identity" +-- > encodeModule "" "Prelude" == "Prelude" +-- > uncurry encodeModule (decodeModule name) == name encodeModule :: FilePath -> String -> String encodeModule dir file - | dir == "./" = replaceEq '/' '.' $ takeBaseName file - | otherwise = replaceEq '/' '.' $ dir ++ takeBaseName file + | dir == "" = takeBaseName file + | otherwise = replaceEq '/' '.' dir ++ '.' : takeBaseName file -- | Find the generator for a given 'Context' and a source file. For example: -- findGenerator (Context Stage1 compiler vanilla) @@ -102,7 +104,7 @@ moduleFilesOracle = void $ do result <- fmap concat . forM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do - let fullDir = dir -/- mDir + let fullDir = unifyPath $ dir -/- mDir files <- getDirectoryFiles fullDir ["*"] let noBoot = filter (not . (isSuffixOf "-boot")) files cmp fe f = compare (dropExtension fe) f diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 719352f..f901069 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -44,7 +44,8 @@ buildPackageData context at Context {..} = do copyFile inTreeMk mk autogenFiles <- getDirectoryFiles (oldPath -/- "build") ["autogen/*"] createDirectory $ buildPath context -/- "autogen" - forM_ autogenFiles $ \file -> do + forM_ autogenFiles $ \file' -> do + let file = unifyPath file' copyFile (oldPath -/- "build" -/- file) (buildPath context -/- file) let haddockPrologue = "haddock-prologue.txt" copyFile (oldPath -/- haddockPrologue) (buildPath context -/- haddockPrologue) @@ -111,7 +112,8 @@ buildPackageData context at Context {..} = do ++ [ "posix" | not windows ] ++ [ "win32" | windows ] -- TODO: adding cmm/S sources to C_SRCS is a hack; rethink after #18 - cSrcs <- getDirectoryFiles (pkgPath package) (map (-/- "*.c") dirs) + cSrcs <- map unifyPath <$> + getDirectoryFiles (pkgPath package) (map (-/- "*.c") dirs) cmmSrcs <- getDirectoryFiles (pkgPath package) ["*.cmm"] buildAdjustor <- anyTargetArch ["i386", "powerpc", "powerpc64"] buildStgCRunAsm <- anyTargetArch ["powerpc64le"] diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 8037682..9ba4524 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -61,11 +61,11 @@ testMatchVersionedFilePath = do testModuleNames :: Action () testModuleNames = do putBuild $ "==== Encode/decode module name" - test $ encodeModule "Data/Functor/" "Identity.hs" == "Data.Functor.Identity" - test $ encodeModule "./" "Prelude" == "Prelude" + test $ encodeModule "Data/Functor" "Identity.hs" == "Data.Functor.Identity" + test $ encodeModule "" "Prelude" == "Prelude" - test $ decodeModule "Data.Functor.Identity" == ("Data/Functor/", "Identity") - test $ decodeModule "Prelude" == ("./", "Prelude") + test $ decodeModule "Data.Functor.Identity" == ("Data/Functor", "Identity") + test $ decodeModule "Prelude" == ("", "Prelude") test $ forAll names $ \n -> uncurry encodeModule (decodeModule n) == n where From git at git.haskell.org Fri Oct 27 01:00:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Config.hs to import GhcPrelude (#417) (fcdecad) Message-ID: <20171027010000.1E3913A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fcdecad4f1ab2f5a6126013004211acef23cf775/ghc >--------------------------------------------------------------- commit fcdecad4f1ab2f5a6126013004211acef23cf775 Author: Zhen Zhang Date: Thu Sep 21 00:47:21 2017 +0800 Fix Config.hs to import GhcPrelude (#417) >--------------------------------------------------------------- fcdecad4f1ab2f5a6126013004211acef23cf775 src/Rules/Generate.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 413abe5..e777e1b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -291,6 +291,8 @@ generateConfigHs = do [ "{-# LANGUAGE CPP #-}" , "module Config where" , "" + , "import GhcPrelude" + , "" , "#include \"ghc_boot_platform.h\"" , "" , "data IntegerLibrary = IntegerGMP" From git at git.haskell.org Fri Oct 27 01:00:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add link to MVP issue (82ead73) Message-ID: <20171027010003.E8C043A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/82ead7329fffd487907579625213da513ca4094f/ghc >--------------------------------------------------------------- commit 82ead7329fffd487907579625213da513ca4094f Author: Andrey Mokhov Date: Fri May 13 20:11:02 2016 +0100 Add link to MVP issue See #239. >--------------------------------------------------------------- 82ead7329fffd487907579625213da513ca4094f README.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index a8ca935..5c950dd 100644 --- a/README.md +++ b/README.md @@ -123,7 +123,8 @@ The best way to contribute is to try the new build system, report the issues you found, and attempt to fix them. Please note the codebase is very unstable at present and we expect a lot of further refactoring. The documentation is currently non-existent, but we are working on it: [#55][comments-issue], -[#56][doc-issue]. +[#56][doc-issue]. See also [#239](https://github.com/snowleopard/hadrian/issues/239) +for a list of issues on the critical path. Acknowledgements ---------------- From git at git.haskell.org Fri Oct 27 01:00:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:04 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update shake and add stm to stage1 packages (#419) (907cad6) Message-ID: <20171027010004.24A723A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/907cad60863a4ea2b940fa7aa6c73b0da82eab7c/ghc >--------------------------------------------------------------- commit 907cad60863a4ea2b940fa7aa6c73b0da82eab7c Author: Zhen Zhang Date: Fri Sep 22 17:53:09 2017 +0800 Update shake and add stm to stage1 packages (#419) * Update shake * Add stm to Stage 1 packages >--------------------------------------------------------------- 907cad60863a4ea2b940fa7aa6c73b0da82eab7c hadrian.cabal | 2 +- src/GHC.hs | 1 + src/Hadrian/Utilities.hs | 6 ------ stack.yaml | 3 +++ 4 files changed, 5 insertions(+), 7 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index b01d866..97b283a 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -124,7 +124,7 @@ executable hadrian , extra >= 1.4.7 , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.10 - , shake >= 0.15.6 + , shake == 0.16.* , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* build-tools: alex >= 3.1 diff --git a/src/GHC.hs b/src/GHC.hs index ab6f93b..32676cd 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -191,6 +191,7 @@ stage1Packages = do , process , rts , runGhc + , stm , time ] ++ [ iservBin | not win ] ++ [ unix | not win ] diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 8f6f4cc..06ee663 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -25,9 +25,6 @@ module Hadrian.Utilities ( putProgressInfo, renderAction, renderProgram, renderLibrary, renderBox, renderUnicorn, - -- * Shake compatibility - RuleResult, - -- * Miscellaneous (<&>), (%%>), cmdLineLengthLimit, @@ -183,9 +180,6 @@ buildRoot = do infixl 1 <&> --- | Introduced in shake-0.16, so use to make the rest of the code compatible -type family RuleResult a - -- | Given a 'FilePath' to a source file, return 'True' if it is generated. -- The current implementation simply assumes that a file is generated if it -- lives in the 'buildRoot' directory. Since most files are not generated the diff --git a/stack.yaml b/stack.yaml index a05f2cd..2a92f26 100644 --- a/stack.yaml +++ b/stack.yaml @@ -8,6 +8,9 @@ packages: - '.' - '../libraries/Cabal/Cabal' +extra-deps: +- shake-0.16 + nix: packages: - autoconf From git at git.haskell.org Fri Oct 27 01:00:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add user settings documentation (b56f4eb) Message-ID: <20171027010008.177673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b56f4eb4034f51dbb5364ff57752900c8d9f417b/ghc >--------------------------------------------------------------- commit b56f4eb4034f51dbb5364ff57752900c8d9f417b Author: Andrey Mokhov Date: Sat May 14 13:58:21 2016 +0100 Add user settings documentation See #56, #245. >--------------------------------------------------------------- b56f4eb4034f51dbb5364ff57752900c8d9f417b doc/user-settings.md | 124 +++++++++++++++++++++++++++++++++++++++++++++++++++ src/Settings/User.hs | 20 ++++----- 2 files changed, 134 insertions(+), 10 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md new file mode 100644 index 0000000..a7f1469 --- /dev/null +++ b/doc/user-settings.md @@ -0,0 +1,124 @@ +# User settings + +Users can customise Hadrian by specifying user build settings in file +`src/Settings/User.hs`. Here we document currently supported settings. + +## Build directory + +Hadrian puts build results into `_build` directory by default, which is +controlled by `buildRootPath`: +```haskell +-- | All build artefacts are stored in 'buildRootPath' directory. +buildRootPath :: FilePath +buildRootPath = "_build" +``` + +## Command line arguments + +One of the key features of Hadrian is that users can modify any build command by +changing `userArgs`. The build system will detect the change and will rerun all +affected build rules during the next build, without requiring a full rebuild. + +As an example, here is how to pass an extra argument `-O0` to all invocations of +GHC when compiling package `cabal`: +```haskell +-- | Control user-specific command line arguments. +userArgs :: Args +userArgs = builder Ghc ? package cabal ? arg "-O0" +``` +Builders such as `Ghc` are defined in `src/Builder.hs`, and all packages that +are currently built as part of the GHC are defined in `src/GHC.hs` (also see +`src/Package.hs`). + +It is possible to specify several custom command line arguments combining the +list with `mconcat`: +```haskell +userArgs :: Args +userArgs = mconcat + [ builder Ghc ? package cabal ? arg "-O0" + , package rts ? input "//Evac\_thr.c" ? append [ "-DPARALLEL\_GC", "-Irts/sm" ] + , builder Ghc ? output "//Prelude.\*" ? remove ["-Wall", "-fwarn-tabs"] ] +``` +The above example also demostrates the use of `append` for adding more than one +argument and `remove` for removing arguments that Hadrian uses by default. It is +possible to match any combination of the current `builder`, `stage`, `package`, +`way`, `input` and `output` using predicates. File patterns such as +`"//Prelude.\*"` can be used when matching input and output files where `//` +matches an arbitrary number of path components and `\*` matches an entire path component, excluding any separators. + +## Packages + +To add or remove a package from a particular build stage, use `userPackages`. As +an example, below we add package `base` to Stage0 and remove package `haskeline` +from Stage1: +```haskell +-- | Control which packages get to be built. +userPackages :: Packages +userPackages = mconcat + [ stage0 ? append [base] + , stage1 ? remove [haskeline] ] +``` +If you are working on a new GHC package you need to let Hadrian know about it +by setting `userKnownPackages`: +```haskell +-- | Add new user-defined packages. +userKnownPackages :: [Package] +userKnownPackages = [] +``` +To control which integer library to use when builing GHC, set `integerLibrary`: +```haskell +-- | Choose the integer library: integerGmp or integerSimple. +integerLibrary :: Package +integerLibrary = integerGmp +``` + +## Build ways + +Libraries can be built in a number of ways, such as `vanilla`, `profiling` (with +profiling information enabled), and many others as defined in `src/Way.hs`. To +control which ways particular packages are built, set `userLibraryWays` and +`userRtsWays`. As an example, below we remove `dynamic` from the list of library +ways and keep `rts` package ways unchanged: +```haskell +-- | Control which ways library packages are built. +userLibraryWays :: Ways +userLibraryWays = remove [dynamic] + +-- | Control which ways the 'rts' package is built. +userRtsWays :: Ways +userRtsWays = mempty +``` + +## Verbose command lines + +By default Hadrian does not print full command lines during the build process +and instead prints short human readable digests for each executed command. It is +possible to suppress this behaviour completely or partially using +`verboseCommands` setting: +```haskell +-- | Set to True to print full command lines during the build process. Note, +-- this is a Predicate, hence you can enable verbose output for a chosen package +-- only, e.g.: verboseCommands = package ghcPrim +verboseCommands :: Predicate +verboseCommands = return False +``` +For example, to print the full command lines used to compile GHC executables, +set `verboseCommands` to: +```haskell +verboseCommands :: Predicate +verboseCommands = input "ghc/Main.hs" +``` +Below are a few other examples: +```haskell +-- Print command lines for all Ghc Link invocations: +verboseCommands = builder (Ghc Link) + +-- Print command lines when compiling files in package compiler using Gcc: +verboseCommands = builder (Gcc Compile) &&^ package compiler + +-- Use patterns when matching files: +verboseCommands = file "//rts/sm/*" &&^ way threaded + +-- Show all commands: +verboseCommands = return True +``` \ No newline at end of file diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 0893579..cc48684 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -16,31 +16,31 @@ import Settings.Default buildRootPath :: FilePath buildRootPath = "_build" --- Control user-specific settings +-- | Control user-specific command line arguments. userArgs :: Args userArgs = builder Ghc ? remove ["-Wall", "-fwarn-tabs"] --- Control which packages get to be built +-- | Control which packages get to be built. userPackages :: Packages userPackages = mempty --- Add new user-defined packages +-- | Add new user-defined packages. userKnownPackages :: [Package] userKnownPackages = [] --- | Control which ways library packages are built +-- | Choose the integer library: integerGmp or integerSimple. +integerLibrary :: Package +integerLibrary = integerGmp + +-- | Control which ways library packages are built. -- FIXME: skip dynamic since it's currently broken #4 userLibraryWays :: Ways userLibraryWays = remove [dynamic] --- | Control which ways the 'rts' package is built +-- | Control which ways the 'rts' package is built. userRtsWays :: Ways userRtsWays = mempty --- | Choose the integer library: integerGmp or integerSimple -integerLibrary :: Package -integerLibrary = integerGmp - -- | User-defined flags. Note the following type semantics: -- * Bool: a plain Boolean flag whose value is known at compile time -- * Action Bool: a flag whose value can depend on the build environment @@ -79,7 +79,7 @@ buildHaddock = return cmdBuildHaddock -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package --- only, e.g.: verboseCommands = package ghcPrim +-- only, e.g.: verboseCommands = package ghcPrim. verboseCommands :: Predicate verboseCommands = return False From git at git.haskell.org Fri Oct 27 01:00:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:08 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Complete RTS compiler args (#418) (706d35e) Message-ID: <20171027010008.3F4183A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/706d35ea81f8f290f21ab9ab6869b3e4cc575056/ghc >--------------------------------------------------------------- commit 706d35ea81f8f290f21ab9ab6869b3e4cc575056 Author: Zhen Zhang Date: Sun Sep 24 03:55:22 2017 +0800 Complete RTS compiler args (#418) >--------------------------------------------------------------- 706d35ea81f8f290f21ab9ab6869b3e4cc575056 cfg/system.config.in | 1 + src/Oracles/Flag.hs | 2 + src/Settings/Packages/Rts.hs | 227 ++++++++++++++++++------------------------- 3 files changed, 95 insertions(+), 135 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 706d35ea81f8f290f21ab9ab6869b3e4cc575056 From git at git.haskell.org Fri Oct 27 01:00:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a link to the user settings doc (f715a27) Message-ID: <20171027010011.BB2E03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f715a274f7ef2e07625f22401f755a30dfbce001/ghc >--------------------------------------------------------------- commit f715a274f7ef2e07625f22401f755a30dfbce001 Author: Andrey Mokhov Date: Sat May 14 14:05:05 2016 +0100 Add a link to the user settings doc See #245. [skip ci] >--------------------------------------------------------------- f715a274f7ef2e07625f22401f755a30dfbce001 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 5c950dd..fdbdbc5 100644 --- a/README.md +++ b/README.md @@ -80,8 +80,8 @@ a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this f #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We -use [`src/Settings/User.hs`][user-settings] for the same purpose. Feel free to -experiment following the Haddock comments. +use [`src/Settings/User.hs`][user-settings] for the same purpose, see +[documentation](doc/user-settings.md). #### Clean and full rebuild From git at git.haskell.org Fri Oct 27 01:00:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant import (07b7d5f) Message-ID: <20171027010011.E9A5F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/07b7d5fcd2890137e2d71e1b136d8cc0da0fa1ad/ghc >--------------------------------------------------------------- commit 07b7d5fcd2890137e2d71e1b136d8cc0da0fa1ad Author: Andrey Mokhov Date: Sat Sep 23 23:06:26 2017 +0200 Drop redundant import >--------------------------------------------------------------- 07b7d5fcd2890137e2d71e1b136d8cc0da0fa1ad src/Hadrian/Oracles/ArgsHash.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index da13a95..bae2fdb 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -9,7 +9,6 @@ import Development.Shake.Classes import Hadrian.Expression hiding (inputs, outputs) import Hadrian.Target -import Hadrian.Utilities -- | 'TrackArgument' is used to specify the arguments that should be tracked by -- the @ArgsHash@ oracle. The safest option is to track all arguments, but some From git at git.haskell.org Fri Oct 27 01:00:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (4b0dc2f) Message-ID: <20171027010015.9FF2D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b0dc2fe52989ff18dc5e0202a1bd48f00689772/ghc >--------------------------------------------------------------- commit 4b0dc2fe52989ff18dc5e0202a1bd48f00689772 Author: Andrey Mokhov Date: Sat May 14 18:10:51 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- 4b0dc2fe52989ff18dc5e0202a1bd48f00689772 doc/user-settings.md | 45 ++++++++++++++++++++++++++------------------- 1 file changed, 26 insertions(+), 19 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index a7f1469..e9bea77 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,12 +1,12 @@ # User settings -Users can customise Hadrian by specifying user build settings in file +You can customise Hadrian by specifying user build settings in file `src/Settings/User.hs`. Here we document currently supported settings. ## Build directory Hadrian puts build results into `_build` directory by default, which is -controlled by `buildRootPath`: +specified by `buildRootPath`: ```haskell -- | All build artefacts are stored in 'buildRootPath' directory. buildRootPath :: FilePath @@ -19,7 +19,7 @@ One of the key features of Hadrian is that users can modify any build command by changing `userArgs`. The build system will detect the change and will rerun all affected build rules during the next build, without requiring a full rebuild. -As an example, here is how to pass an extra argument `-O0` to all invocations of +For example, here is how to pass an extra argument `-O0` to all invocations of GHC when compiling package `cabal`: ```haskell -- | Control user-specific command line arguments. @@ -27,24 +27,24 @@ userArgs :: Args userArgs = builder Ghc ? package cabal ? arg "-O0" ``` Builders such as `Ghc` are defined in `src/Builder.hs`, and all packages that -are currently built as part of the GHC are defined in `src/GHC.hs` (also see -`src/Package.hs`). +are currently built as part of the GHC are defined in `src/GHC.hs`. See also +`src/Package.hs`. -It is possible to specify several custom command line arguments combining the -list with `mconcat`: +You can combine several custom command line settings using `mconcat`: ```haskell userArgs :: Args userArgs = mconcat [ builder Ghc ? package cabal ? arg "-O0" - , package rts ? input "//Evac\_thr.c" ? append [ "-DPARALLEL\_GC", "-Irts/sm" ] - , builder Ghc ? output "//Prelude.\*" ? remove ["-Wall", "-fwarn-tabs"] ] + , package rts ? input "//Evac_thr.c" ? append [ "-DPARALLEL_GC", "-Irts/sm" ] + , builder Ghc ? output "//Prelude.*" ? remove ["-Wall", "-fwarn-tabs"] ] ``` The above example also demostrates the use of `append` for adding more than one -argument and `remove` for removing arguments that Hadrian uses by default. It is -possible to match any combination of the current `builder`, `stage`, `package`, -`way`, `input` and `output` using predicates. File patterns such as -`"//Prelude.\*"` can be used when matching input and output files where `//` -matches an arbitrary number of path components and `\*` matches an entire path component, excluding any separators. +argument and `remove` for removing arguments that Hadrian uses by default. You +can match any combination of the `builder`, `stage`, `package`, `way`, `input` +and `output` when specifying custom command line arguments. File patterns such as +`"//Prelude.*"` can be used when matching input and output files where `//` +matches an arbitrary number of path components and `*` matches an entire path +component, excluding any separators. ## Packages @@ -63,20 +63,27 @@ by setting `userKnownPackages`: ```haskell -- | Add new user-defined packages. userKnownPackages :: [Package] -userKnownPackages = [] +userKnownPackages = [myPackage] + +-- An example package that lives in "libraries/my-package" directory. +myPackage :: Package +myPackage = library "my-package" ``` -To control which integer library to use when builing GHC, set `integerLibrary`: +Note, you will also need to add it to a specific build stage by modifying +`userPackages` as otherwise it will not be built. + +You can choose which integer library to use when builing GHC by setting +`integerLibrary`: ```haskell -- | Choose the integer library: integerGmp or integerSimple. integerLibrary :: Package integerLibrary = integerGmp ``` - ## Build ways Libraries can be built in a number of ways, such as `vanilla`, `profiling` (with profiling information enabled), and many others as defined in `src/Way.hs`. To -control which ways particular packages are built, set `userLibraryWays` and +control which ways particular ways are built, set `userLibraryWays` and `userRtsWays`. As an example, below we remove `dynamic` from the list of library ways and keep `rts` package ways unchanged: ```haskell @@ -119,6 +126,6 @@ verboseCommands = builder (Gcc Compile) &&^ package compiler -- Use patterns when matching files: verboseCommands = file "//rts/sm/*" &&^ way threaded --- Show all commands: +-- Print all commands: verboseCommands = return True ``` From git at git.haskell.org Fri Oct 27 01:00:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add RTS args related to libffi (6abbbd0) Message-ID: <20171027010015.C6C453A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6abbbd0696f55f8d6b7bcd33c4c4915f934b4045/ghc >--------------------------------------------------------------- commit 6abbbd0696f55f8d6b7bcd33c4c4915f934b4045 Author: Andrey Mokhov Date: Mon Sep 25 22:27:47 2017 +0200 Add RTS args related to libffi >--------------------------------------------------------------- 6abbbd0696f55f8d6b7bcd33c4c4915f934b4045 src/Settings/Packages/Rts.hs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 10940e4..c9d6359 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -38,15 +38,14 @@ rtsLibffiLibraryName = do (False, False) -> "Cffi" (_ , True ) -> "Cffi-6" -rtsLibffiIncludeArgs :: Args -rtsLibffiIncludeArgs = package libffi ? builder (Ghc CompileCWithGhc) ? do - useSystemFfi <- expr $ flag UseSystemFfi - ffiIncludeDir <- getSetting FfiIncludeDir - mconcat [ - useSystemFfi ? pure (map ("-I" ++) $ words ffiIncludeDir), - -- ffi.h triggers prototype warnings, so disable them here: - inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? - arg "-Wno-strict-prototypes" ] +rtsLibffiArgs :: Args +rtsLibffiArgs = builder (Ghc CompileCWithGhc) ? do + useSystemFfi <- expr $ flag UseSystemFfi + ffiIncludeDir <- getSetting FfiIncludeDir + mconcat [ useSystemFfi ? pure (map ("-I" ++) $ words ffiIncludeDir) + -- ffi.h triggers prototype warnings, so we disable them here + , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? + arg "-Wno-strict-prototypes" ] rtsLibffiLibrary :: Way -> Action FilePath rtsLibffiLibrary way = do @@ -195,7 +194,8 @@ rtsPackageArgs = package rts ? do , ghcRtsWithLibDw ? arg "-DUSE_LIBDW" ] mconcat - [ builder (Cc FindCDependencies) ? mconcat cArgs + [ rtsLibffiArgs + , builder (Cc FindCDependencies) ? mconcat cArgs , builder (Ghc CompileCWithGhc) ? mconcat (map (map ("-optc" ++) <$>) cArgs) , builder Ghc ? arg "-Irts" , builder HsCpp ? pure From git at git.haskell.org Fri Oct 27 01:00:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (be59fae) Message-ID: <20171027010019.202CE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/be59faec5e11a7338888227ffdc36a2513c1fd00/ghc >--------------------------------------------------------------- commit be59faec5e11a7338888227ffdc36a2513c1fd00 Author: Andrey Mokhov Date: Sat May 14 18:15:10 2016 +0100 Minor revision [skip ci] >--------------------------------------------------------------- be59faec5e11a7338888227ffdc36a2513c1fd00 doc/user-settings.md | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index e9bea77..e395ea2 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -41,10 +41,10 @@ userArgs = mconcat The above example also demostrates the use of `append` for adding more than one argument and `remove` for removing arguments that Hadrian uses by default. You can match any combination of the `builder`, `stage`, `package`, `way`, `input` -and `output` when specifying custom command line arguments. File patterns such as -`"//Prelude.*"` can be used when matching input and output files where `//` -matches an arbitrary number of path components and `*` matches an entire path -component, excluding any separators. +and `output` predicates when specifying custom command line arguments. File +patterns such as `"//Prelude.*"` can be used when matching input and output files, +where `//` matches an arbitrary number of path components and `*` matches an entire +path component, excluding any separators. ## Packages @@ -69,7 +69,7 @@ userKnownPackages = [myPackage] myPackage :: Package myPackage = library "my-package" ``` -Note, you will also need to add it to a specific build stage by modifying +Note, you will also need to add `myPackage` to a specific build stage by modifying `userPackages` as otherwise it will not be built. You can choose which integer library to use when builing GHC by setting From git at git.haskell.org Fri Oct 27 01:00:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop outdated RTS arguments, fix Windows build (0e193c0) Message-ID: <20171027010019.68C513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0e193c084f1ee8d9f044e612b319cf9963a5053d/ghc >--------------------------------------------------------------- commit 0e193c084f1ee8d9f044e612b319cf9963a5053d Author: Andrey Mokhov Date: Tue Sep 26 20:17:50 2017 +0200 Drop outdated RTS arguments, fix Windows build >--------------------------------------------------------------- 0e193c084f1ee8d9f044e612b319cf9963a5053d src/Settings/Packages/Rts.hs | 14 ++------------ 1 file changed, 2 insertions(+), 12 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index c9d6359..c71b729 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -54,13 +54,6 @@ rtsLibffiLibrary way = do rtsPath <- rtsBuildPath return $ rtsPath -/- "lib" ++ name ++ suf --- ref: mk/config.mk.in -ghcRtsWithLibDw :: Action Bool -ghcRtsWithLibDw = do - goodArch <- anyTargetArch ["i386", "x86_64"] - withLibDw <- flag HaveLibMingwEx - return $ goodArch && withLibDw - -- Compile various performance-critical pieces *without* -fPIC -dynamic -- even when building a shared library. If we don't do this, then the -- GC runs about 50% slower on x86 due to the overheads of PIC. The @@ -190,8 +183,7 @@ rtsPackageArgs = package rts ? do , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr" , input "//RetainerProfile.c" ? flag GccIsClang ? pure [ "-Wno-incompatible-pointer-types" ] - , targetOs == "mingw32" ? arg ("-DWINVER=" ++ rtsWindowsVersion) - , ghcRtsWithLibDw ? arg "-DUSE_LIBDW" ] + , windowsHost ? arg ("-DWINVER=" ++ rtsWindowsVersion) ] mconcat [ rtsLibffiArgs @@ -210,6 +202,4 @@ rtsPackageArgs = package rts ? do pure [ "-DINSTALLING" , "-DLIB_DIR=\"" ++ destDir ++ ghclibDir ++ "\"" , "-DINCLUDE_DIR=\"" ++ destDir ++ ghclibDir -/- "include\"" ] - , builder HsCpp ? mconcat - [ ghcRtsWithLibDw ? arg "-DUSE_LIBDW" - , flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ] ] + , builder HsCpp ? flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ] From git at git.haskell.org Fri Oct 27 01:00:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add TODOs. (86ae5c7) Message-ID: <20171027010022.AA6F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/86ae5c73a514bea9a5035128f673833b071e5dc9/ghc >--------------------------------------------------------------- commit 86ae5c73a514bea9a5035128f673833b071e5dc9 Author: Andrey Mokhov Date: Sat May 14 18:29:43 2016 +0100 Add TODOs. >--------------------------------------------------------------- 86ae5c73a514bea9a5035128f673833b071e5dc9 src/Settings/User.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index cc48684..2294fc7 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -53,6 +53,7 @@ userRtsWays = mempty trackBuildSystem :: Bool trackBuildSystem = True +-- TODO: This should be set automatically when validating. validating :: Bool validating = False @@ -61,6 +62,12 @@ validating = False splitObjects :: Predicate splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects +-- | Control when to build documentation. +buildHaddock :: Predicate +buildHaddock = return cmdBuildHaddock + +-- TODO: Do we need to be able to set these from command line? +-- TODO: Turn below into ghcWays? dynamicGhcPrograms :: Bool dynamicGhcPrograms = False @@ -70,13 +77,9 @@ ghciWithDebugger = False ghcProfiled :: Bool ghcProfiled = False --- TODO: do we need to be able to set this from command line? ghcDebugged :: Bool ghcDebugged = False -buildHaddock :: Predicate -buildHaddock = return cmdBuildHaddock - -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package -- only, e.g.: verboseCommands = package ghcPrim. From git at git.haskell.org Fri Oct 27 01:00:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up RTS arguments (b2d06c6) Message-ID: <20171027010023.102523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2d06c68c31265fa85dc764b6a29400c8845b640/ghc >--------------------------------------------------------------- commit b2d06c68c31265fa85dc764b6a29400c8845b640 Author: Andrey Mokhov Date: Tue Sep 26 20:48:21 2017 +0200 Clean up RTS arguments >--------------------------------------------------------------- b2d06c68c31265fa85dc764b6a29400c8845b640 src/Settings/Packages/Rts.hs | 70 +++++++++++++++++++++----------------------- 1 file changed, 33 insertions(+), 37 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index c71b729..a7ed021 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,17 +20,17 @@ rtsBuildPath = buildPath rtsContext rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" --- | Minimum supported Windows version. -- These numbers can be found at: -- https://msdn.microsoft.com/en-us/library/windows/desktop/aa383745(v=vs.85).aspx -- If we're compiling on windows, enforce that we only support Vista SP1+ -- Adding this here means it doesn't have to be done in individual .c files -- and also centralizes the versioning. -rtsWindowsVersion :: String -rtsWindowsVersion = "0x06000100" +-- | Minimum supported Windows version. +windowsVersion :: String +windowsVersion = "0x06000100" -rtsLibffiLibraryName :: Action FilePath -rtsLibffiLibraryName = do +libffiLibraryName :: Action FilePath +libffiLibraryName = do useSystemFfi <- flag UseSystemFfi windows <- windowsHost return $ case (useSystemFfi, windows) of @@ -38,18 +38,9 @@ rtsLibffiLibraryName = do (False, False) -> "Cffi" (_ , True ) -> "Cffi-6" -rtsLibffiArgs :: Args -rtsLibffiArgs = builder (Ghc CompileCWithGhc) ? do - useSystemFfi <- expr $ flag UseSystemFfi - ffiIncludeDir <- getSetting FfiIncludeDir - mconcat [ useSystemFfi ? pure (map ("-I" ++) $ words ffiIncludeDir) - -- ffi.h triggers prototype warnings, so we disable them here - , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? - arg "-Wno-strict-prototypes" ] - rtsLibffiLibrary :: Way -> Action FilePath rtsLibffiLibrary way = do - name <- rtsLibffiLibraryName + name <- libffiLibraryName suf <- libsuf way rtsPath <- rtsBuildPath return $ rtsPath -/- "lib" ++ name ++ suf @@ -108,12 +99,12 @@ rtsPackageArgs = package rts ? do way <- getWay path <- getBuildPath top <- expr topDirectory - libffiName <- expr rtsLibffiLibraryName + libffiName <- expr libffiLibraryName ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir ghclibDir <- expr installGhcLibDir destDir <- expr getDestDir - let cArgs = + let cArgs = mconcat [ arg "-Irts" , arg $ "-I" ++ path , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" @@ -156,41 +147,45 @@ rtsPackageArgs = package rts ? do inputs [ "//Evac.c", "//Evac_thr.c" , "//Scav.c", "//Scav_thr.c" , "//Compact.c", "//GC.c" ] ? arg "-fno-PIC" - -- -static is also necessary for these bits, otherwise the NCG - -- generates dynamic references: + -- -static is also necessary for these bits, otherwise the NCG + -- generates dynamic references: , speedHack ? inputs [ "//Updates.c", "//StgMiscClosures.c" , "//PrimOps.c", "//Apply.c" - , "//AutoApply.c" ] ? pure [ "-fno-PIC", "-static" ] - -- inlining warnings happen in Compact + , "//AutoApply.c" ] ? pure ["-fno-PIC", "-static"] + + -- inlining warnings happen in Compact , inputs ["//Compact.c"] ? arg "-Wno-inline" - -- emits warnings about call-clobbered registers on x86_64 - , inputs [ "//StgCRun.c", "//RetainerProfile.c" + + -- emits warnings about call-clobbered registers on x86_64 + , inputs [ "//RetainerProfile.c", "//StgCRun.c" , "//win32/ConsoleHandler.c", "//win32/ThrIOManager.c"] ? arg "-w" , inputs ["//RetainerSet.c"] ? arg "-Wno-format" - -- The above warning suppression flags are a temporary kludge. - -- While working on this module you are encouraged to remove it and fix - -- any warnings in the module. See - -- http://ghc.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings - -- for details + -- The above warning suppression flags are a temporary kludge. + -- While working on this module you are encouraged to remove it and fix + -- any warnings in the module. See: + -- http://ghc.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings , (not <$> flag GccIsClang) ? inputs ["//Compact.c"] ? arg "-finline-limit=2500" , inputs ["//Evac_thr.c", "//Scav_thr.c"] ? - pure [ "-DPARALLEL_GC", "-Irts/sm" ] + pure ["-DPARALLEL_GC", "-Irts/sm"] , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr" , input "//RetainerProfile.c" ? flag GccIsClang ? - pure [ "-Wno-incompatible-pointer-types" ] - , windowsHost ? arg ("-DWINVER=" ++ rtsWindowsVersion) ] - + arg "-Wno-incompatible-pointer-types" + , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? + arg "-Wno-strict-prototypes" + , windowsHost ? arg ("-DWINVER=" ++ windowsVersion) ] mconcat - [ rtsLibffiArgs - , builder (Cc FindCDependencies) ? mconcat cArgs - , builder (Ghc CompileCWithGhc) ? mconcat (map (map ("-optc" ++) <$>) cArgs) - , builder Ghc ? arg "-Irts" - , builder HsCpp ? pure + [ builder (Cc FindCDependencies) ? cArgs + , builder (Ghc CompileCWithGhc) ? map ("-optc" ++) <$> cArgs + , builder Ghc ? mconcat + [ arg "-Irts" + , flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir) ] + + , builder HsCpp ? pure [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir , "-DFFI_LIB_DIR=" ++ show ffiLibraryDir @@ -202,4 +197,5 @@ rtsPackageArgs = package rts ? do pure [ "-DINSTALLING" , "-DLIB_DIR=\"" ++ destDir ++ ghclibDir ++ "\"" , "-DINCLUDE_DIR=\"" ++ destDir ++ ghclibDir -/- "include\"" ] + , builder HsCpp ? flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ] From git at git.haskell.org Fri Oct 27 01:00:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add miscellaneous, minor revision (8c6a188) Message-ID: <20171027010026.6F53D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8c6a188fc3ecea807a6536ce0442dda6244b7b92/ghc >--------------------------------------------------------------- commit 8c6a188fc3ecea807a6536ce0442dda6244b7b92 Author: Andrey Mokhov Date: Sat May 14 18:33:55 2016 +0100 Add miscellaneous, minor revision [skip ci] >--------------------------------------------------------------- 8c6a188fc3ecea807a6536ce0442dda6244b7b92 doc/user-settings.md | 31 +++++++++++++++++++++++-------- 1 file changed, 23 insertions(+), 8 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index e395ea2..dc718ed 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -81,11 +81,11 @@ integerLibrary = integerGmp ``` ## Build ways -Libraries can be built in a number of ways, such as `vanilla`, `profiling` (with -profiling information enabled), and many others as defined in `src/Way.hs`. To -control which ways particular ways are built, set `userLibraryWays` and -`userRtsWays`. As an example, below we remove `dynamic` from the list of library -ways and keep `rts` package ways unchanged: +Packages can be built in a number of ways, such as `vanilla`, `profiling` (with +profiling information enabled), and many others as defined in `src/Way.hs`. You +can change the default build ways using `userLibraryWays` and `userRtsWays` settings. +As an example, below we remove `dynamic` from the list of library ways but keep +`rts` package ways unchanged: ```haskell -- | Control which ways library packages are built. userLibraryWays :: Ways @@ -99,9 +99,8 @@ userRtsWays = mempty ## Verbose command lines By default Hadrian does not print full command lines during the build process -and instead prints short human readable digests for each executed command. It is -possible to suppress this behaviour completely or partially using -`verboseCommands` setting: +and instead prints short human readable digests for each executed command. You +can suppress this behaviour completely or partially using `verboseCommands` setting: ```haskell -- | Set to True to print full command lines during the build process. Note, -- this is a Predicate, hence you can enable verbose output for a chosen package @@ -129,3 +128,19 @@ verboseCommands = file "//rts/sm/*" &&^ way threaded -- Print all commands: verboseCommands = return True ``` + +## Miscellaneous + +Use the following settings to change the default behaviour of Hadrian with respect +to building split objects and Haddock documentation. + +```haskell +-- | Control when split objects are generated. Note, due to the GHC bug #11315 +-- it is necessary to do a full clean rebuild when changing this option. +splitObjects :: Predicate +splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects + +-- | Control when to build documentation. +buildHaddock :: Predicate +buildHaddock = return cmdBuildHaddock +``` From git at git.haskell.org Fri Oct 27 01:00:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move ffiIncludeDir to C arguments (68446ab) Message-ID: <20171027010026.BF8F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68446abeab92087492baba6c746ab94c3bb7c2bb/ghc >--------------------------------------------------------------- commit 68446abeab92087492baba6c746ab94c3bb7c2bb Author: Andrey Mokhov Date: Tue Sep 26 20:56:28 2017 +0200 Move ffiIncludeDir to C arguments >--------------------------------------------------------------- 68446abeab92087492baba6c746ab94c3bb7c2bb src/Settings/Packages/Rts.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index a7ed021..7282a0e 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -107,6 +107,7 @@ rtsPackageArgs = package rts ? do let cArgs = mconcat [ arg "-Irts" , arg $ "-I" ++ path + , flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir) , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" -- rts *must* be compiled with optimisations. The INLINE_HEADER macro -- requires that functions are inlined to work as expected. Inlining @@ -181,9 +182,7 @@ rtsPackageArgs = package rts ? do mconcat [ builder (Cc FindCDependencies) ? cArgs , builder (Ghc CompileCWithGhc) ? map ("-optc" ++) <$> cArgs - , builder Ghc ? mconcat - [ arg "-Irts" - , flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir) ] + , builder Ghc ? arg "-Irts" , builder HsCpp ? pure [ "-DTOP=" ++ show top From git at git.haskell.org Fri Oct 27 01:00:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:00:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Comments (b91d515) Message-ID: <20171027010030.B74473A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b91d5152c1979d7c36cb2ab16821abec8da7ec1c/ghc >--------------------------------------------------------------- commit b91d5152c1979d7c36cb2ab16821abec8da7ec1c Author: Andrey Mokhov Date: Sun May 15 00:03:12 2016 +0100 Comments [skip ci] >--------------------------------------------------------------- b91d5152c1979d7c36cb2ab16821abec8da7ec1c src/Settings/User.hs | 38 +++++++++++++++++++++----------------- 1 file changed, 21 insertions(+), 17 deletions(-) diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 2294fc7..7cf9997 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -12,40 +12,44 @@ import Expression import Predicates import Settings.Default --- | All build artefacts are stored in 'buildRootPath' directory. +-- See doc/user-settings.md for instructions. + +-- | All build results are put into 'buildRootPath' directory. buildRootPath :: FilePath buildRootPath = "_build" --- | Control user-specific command line arguments. +-- | Modify default build command line arguments. userArgs :: Args userArgs = builder Ghc ? remove ["-Wall", "-fwarn-tabs"] --- | Control which packages get to be built. +-- | Modify the set of packages that are built by default in each stage. userPackages :: Packages userPackages = mempty --- | Add new user-defined packages. +-- | Add user defined packages. Don't forget to add them to 'userPackages' too. userKnownPackages :: [Package] userKnownPackages = [] --- | Choose the integer library: integerGmp or integerSimple. +-- | Choose the integer library: 'integerGmp' or 'integerSimple'. integerLibrary :: Package integerLibrary = integerGmp --- | Control which ways library packages are built. --- FIXME: skip dynamic since it's currently broken #4 +-- FIXME: We skip 'dynamic' since it's currently broken #4. +-- | Modify the set of ways in which library packages are built. userLibraryWays :: Ways userLibraryWays = remove [dynamic] --- | Control which ways the 'rts' package is built. +-- | Modify the set of ways in which the 'rts' package is built. userRtsWays :: Ways userRtsWays = mempty --- | User-defined flags. Note the following type semantics: --- * Bool: a plain Boolean flag whose value is known at compile time --- * Action Bool: a flag whose value can depend on the build environment --- * Predicate: a flag depending on the build environment and the current target +-- | User defined flags. Note the following type semantics: +-- * @Bool@: a plain Boolean flag whose value is known at compile time. +-- * @Action Bool@: a flag whose value can depend on the build environment. +-- * @Predicate@: a flag whose value can depend on the build environment and +-- on the current build target. +-- TODO: Drop 'trackBuildSystem' as it brings negligible gains. -- | Set this to True if you are making any changes in the build system and want -- appropriate rebuilds to be initiated. Switching this to False speeds things -- up a little (particularly zero builds). @@ -62,12 +66,12 @@ validating = False splitObjects :: Predicate splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects --- | Control when to build documentation. +-- | Control when to build Haddock documentation. buildHaddock :: Predicate buildHaddock = return cmdBuildHaddock -- TODO: Do we need to be able to set these from command line? --- TODO: Turn below into ghcWays? +-- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? dynamicGhcPrograms :: Bool dynamicGhcPrograms = False @@ -81,12 +85,12 @@ ghcDebugged :: Bool ghcDebugged = False -- | Set to True to print full command lines during the build process. Note, --- this is a Predicate, hence you can enable verbose output for a chosen package --- only, e.g.: verboseCommands = package ghcPrim. +-- this is a Predicate, hence you can enable verbose output only for certain +-- targets, e.g.: @verboseCommands = package ghcPrim at . verboseCommands :: Predicate verboseCommands = return False --- TODO: Replace with stage2 ? arg "-Werror"? +-- TODO: Replace with stage2 ? arg "-Werror"? Also see #251. -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. turnWarningsIntoErrors :: Predicate turnWarningsIntoErrors = return False From git at git.haskell.org Fri Oct 27 01:02:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run CI in verbose mode (dd3d592) Message-ID: <20171027010212.08BE93A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dd3d592331fb12f33b117f098e0fb19b388e4eae/ghc >--------------------------------------------------------------- commit dd3d592331fb12f33b117f098e0fb19b388e4eae Author: Andrey Mokhov Date: Wed May 18 09:34:51 2016 +0100 Run CI in verbose mode >--------------------------------------------------------------- dd3d592331fb12f33b117f098e0fb19b388e4eae .travis.yml | 2 +- appveyor.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4ec6721..3b61256 100644 --- a/.travis.yml +++ b/.travis.yml @@ -59,7 +59,7 @@ install: script: - ( cd ghc/hadrian && cabal haddock --internal ) - ./ghc/hadrian/build.sh selftest - - ./ghc/hadrian/build.sh -j --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET + - ./ghc/hadrian/build.sh -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick $TARGET cache: directories: diff --git a/appveyor.yml b/appveyor.yml index 09baa2e..bb5620e 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -37,4 +37,4 @@ install: build_script: - cd C:\msys64\home\ghc\hadrian - echo "" | stack --no-terminal exec -- build.bat selftest - - echo "" | stack --no-terminal exec -- build.bat -j --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe + - echo "" | stack --no-terminal exec -- build.bat -j --verbose --no-progress --progress-colour=never --profile=- --flavour=quick inplace/bin/ghc-stage1.exe From git at git.haskell.org Fri Oct 27 01:02:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build.sh call the default build script (build.cabal.sh) (0aa31f9) Message-ID: <20171027010212.0259B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0aa31f9717e1ecb1a0b73a605a6695f8ee11e28a/ghc >--------------------------------------------------------------- commit 0aa31f9717e1ecb1a0b73a605a6695f8ee11e28a Author: Andrey Mokhov Date: Mon Oct 23 21:33:32 2017 +0100 Make build.sh call the default build script (build.cabal.sh) See #428. Also see #440: build.sh may later be relocated to the top of the GHC tree. >--------------------------------------------------------------- 0aa31f9717e1ecb1a0b73a605a6695f8ee11e28a build.sh => build.cabal.sh | 0 build.sh | 74 ++-------------------------------------------- 2 files changed, 2 insertions(+), 72 deletions(-) diff --git a/build.sh b/build.cabal.sh old mode 100755 new mode 100644 similarity index 100% copy from build.sh copy to build.cabal.sh diff --git a/build.sh b/build.sh index d2bdb85..460fdc1 100755 --- a/build.sh +++ b/build.sh @@ -1,74 +1,4 @@ #!/usr/bin/env bash -CABAL=cabal - -set -euo pipefail - -# readlink on os x, doesn't support -f, to prevent the -# need of installing coreutils (e.g. through brew, just -# for readlink, we use the follownig substitute. -# -# source: http://stackoverflow.com/a/1116890 -function rl { - TARGET_FILE="$1" - - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - - # Iterate down a (possible) chain of symlinks - while [ -L "$TARGET_FILE" ] - do - TARGET_FILE="$(readlink "$TARGET_FILE")" - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - done - - # Compute the canonicalized name by finding the physical path - # for the directory we're in and appending the target file. - PHYS_DIR="$(pwd -P)" - RESULT="$PHYS_DIR/$TARGET_FILE" - echo "$RESULT" -} - -absoluteRoot="$(dirname "$(rl "$0")")" -cd "$absoluteRoot" - -if ! type "$CABAL" > /dev/null; then - echo "Please make sure 'cabal' is in your PATH" - exit 2 -fi - -CABVERSTR=$("$CABAL" --numeric-version) - -CABVER=( ${CABVERSTR//./ } ) - -if [ "${CABVER[0]}" -gt 2 -o "${CABVER[0]}" -eq 2 -a "${CABVER[1]}" -ge 1 ]; then - # New enough Cabal version detected, so let's use the superior new-build + new-run - # modes. Note that pre-2.1 Cabal does not support passing additional parameters - # to the executable (hadrian) after the separator '--', see #438. - - "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - "$CABAL" new-run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" - -else - # The logic below is quite fragile, but it's better than nothing for pre-2.1 Cabal. - echo "Old pre cabal 2.1 version detected. Falling back to legacy 'cabal sandbox' mode." - - # Initialize sandbox if necessary - if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then - "$CABAL" sandbox init - "$CABAL" sandbox add-source ../libraries/Cabal/Cabal - "$CABAL" install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared - fi - - "$CABAL" run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" -fi +# By default on Linux/MacOS we build Hadrian using Cabal +./build.cabal.sh "$@" From git at git.haskell.org Fri Oct 27 01:02:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Unify include and link paths (13b80f7) Message-ID: <20171027010215.85A2C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/13b80f771aac9e9d4a5363632c474261914d5e18/ghc >--------------------------------------------------------------- commit 13b80f771aac9e9d4a5363632c474261914d5e18 Author: Andrey Mokhov Date: Thu May 19 00:45:14 2016 +0100 Unify include and link paths >--------------------------------------------------------------- 13b80f771aac9e9d4a5363632c474261914d5e18 src/Settings/Builders/Common.hs | 2 +- src/Settings/Builders/Ghc.hs | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 3f53dec..252667f 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -25,7 +25,7 @@ cIncludeArgs = do mconcat [ arg $ "-I" ++ path , arg $ "-I" ++ path -/- "autogen" , append [ "-I" ++ pkgPath pkg -/- dir | dir <- incDirs ] - , append [ "-I" ++ dir | dir <- depDirs ] ] + , append [ "-I" ++ unifyPath dir | dir <- depDirs ] ] ldArgs :: Args ldArgs = mempty diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 66c009b..2199874 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -44,8 +44,8 @@ ghcLinkArgs = builder (Ghc Link) ? do else return [] libDirs <- getPkgDataList DepLibDirs mconcat [ arg "-no-auto-link-packages" - , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] - , append [ "-optl-L" ++ dir | dir <- libDirs ] ] + , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] + , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] -- TODO: Add Touchy builder and use needBuilder. needTouchy :: ReaderT Target Action () From git at git.haskell.org Fri Oct 27 01:02:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build.bat call the default build script on Windows (build.stack.bat) (f68d527) Message-ID: <20171027010215.868FD3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f68d527a2f040cc16a7f03a5ce25864ed0acaa58/ghc >--------------------------------------------------------------- commit f68d527a2f040cc16a7f03a5ce25864ed0acaa58 Author: Andrey Mokhov Date: Mon Oct 23 21:36:37 2017 +0100 Make build.bat call the default build script on Windows (build.stack.bat) See #428. Note that building Hadrian with Cabal currently fails on Windows, hence using Stack. Also see #440: build.bat may later be relocated to the top of the GHC tree. >--------------------------------------------------------------- f68d527a2f040cc16a7f03a5ce25864ed0acaa58 build.bat | 33 ++------------------------------- build.bat => build.global-db.bat | 1 - 2 files changed, 2 insertions(+), 32 deletions(-) diff --git a/build.bat b/build.bat index 722f3d7..18cf6cb 100644 --- a/build.bat +++ b/build.bat @@ -1,33 +1,4 @@ @echo off -setlocal -cd %~dp0 -mkdir bin 2> nul -set ghcArgs=--make ^ - -Wall ^ - -fno-warn-name-shadowing ^ - -XRecordWildCards ^ - src\Main.hs ^ - -threaded ^ - -isrc ^ - -i..\libraries\Cabal\Cabal ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=bin ^ - -j ^ - -O ^ - -o bin\hadrian - -set hadrianArgs=--lint ^ - --directory ^ - ".." ^ - %* - - -ghc %ghcArgs% - -if %ERRORLEVEL% NEQ 0 EXIT /B %ERRORLEVEL% - -rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains -set GHC_PACKAGE_PATH= -bin\hadrian %hadrianArgs% +rem By default on Windows we build Hadrian using Stack +./build.stack.bat %* diff --git a/build.bat b/build.global-db.bat similarity index 99% copy from build.bat copy to build.global-db.bat index 722f3d7..0d6a696 100644 --- a/build.bat +++ b/build.global-db.bat @@ -23,7 +23,6 @@ set hadrianArgs=--lint ^ ".." ^ %* - ghc %ghcArgs% if %ERRORLEVEL% NEQ 0 EXIT /B %ERRORLEVEL% From git at git.haskell.org Fri Oct 27 01:02:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (7053d0c) Message-ID: <20171027010219.1020F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7053d0caad3fd13f471a62c681d4d7a91ad843ba/ghc >--------------------------------------------------------------- commit 7053d0caad3fd13f471a62c681d4d7a91ad843ba Author: Andrey Mokhov Date: Thu May 19 22:32:41 2016 +0100 Minor revision >--------------------------------------------------------------- 7053d0caad3fd13f471a62c681d4d7a91ad843ba src/Settings/Builders/Configure.hs | 27 ++++++++++++++------------- src/Settings/Builders/DeriveConstants.hs | 19 +++++++++---------- src/Settings/Builders/Ghc.hs | 13 ++++++------- src/Settings/Builders/GhcCabal.hs | 7 ++----- src/Settings/Builders/GhcPkg.hs | 5 +---- src/Settings/Builders/Haddock.hs | 1 - src/Settings/Builders/Hsc2Hs.hs | 2 +- src/Settings/Builders/Make.hs | 6 +++--- src/Settings/Builders/Tar.hs | 8 +++----- src/Settings/Packages/Compiler.hs | 6 ++++-- src/Settings/Packages/Ghc.hs | 3 ++- src/Settings/Packages/GhcCabal.hs | 15 ++++++--------- src/Settings/Packages/Hp2ps.hs | 7 +++---- src/Settings/Packages/IntegerGmp.hs | 10 ++++++---- src/Settings/Packages/Rts.hs | 6 ++++-- src/Settings/Packages/RunGhc.hs | 5 ++--- src/Settings/Packages/Touchy.hs | 7 +++---- src/Settings/Packages/Unlit.hs | 7 +++---- 18 files changed, 72 insertions(+), 82 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 7053d0caad3fd13f471a62c681d4d7a91ad843ba From git at git.haskell.org Fri Oct 27 01:02:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch AppVeyor to use the default build.bat script (04cdf78) Message-ID: <20171027010219.277693A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/04cdf78cae2e02db1129068db5d7b5c7fc9847e5/ghc >--------------------------------------------------------------- commit 04cdf78cae2e02db1129068db5d7b5c7fc9847e5 Author: Andrey Mokhov Date: Mon Oct 23 21:37:07 2017 +0100 Switch AppVeyor to use the default build.bat script See #428 >--------------------------------------------------------------- 04cdf78cae2e02db1129068db5d7b5c7fc9847e5 appveyor.yml | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 2f4653a..fbedf8f 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -26,14 +26,13 @@ install: build_script: # Build Hadrian - - stack build alex happy # Otherwise 'stack build' fails on AppVeyor - - stack build + - stack build alex happy # Otherwise 'build' fails on AppVeyor # Run internal Hadrian tests - - stack exec hadrian -- --directory ".." selftest + - build selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-colour=never --profile=- + - build -j --flavour=quickest --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 01:02:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Link gmp objects to integerGmp library (5b75d12) Message-ID: <20171027010222.A174B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5b75d126eb0716e44be9be27dc4895a915d78a52/ghc >--------------------------------------------------------------- commit 5b75d126eb0716e44be9be27dc4895a915d78a52 Author: Andrey Mokhov Date: Thu May 19 22:55:32 2016 +0100 Link gmp objects to integerGmp library Fix #241 >--------------------------------------------------------------- 5b75d126eb0716e44be9be27dc4895a915d78a52 src/Rules/Library.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 637dbaa..3fff65f 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -69,9 +69,10 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do let cObjs = map (objFile context) cSrcs hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] + gObjs = [ gmpObjects -/- "*.o" | package == integerGmp ] objs = cObjs ++ hObjs need objs - build $ Target context Ld objs [obj] + build $ Target context Ld (objs ++ gObjs) [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' From git at git.haskell.org Fri Oct 27 01:02:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix the call to another script (9e4a9c1) Message-ID: <20171027010222.BB7AF3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e4a9c1090ac800f6f2cf44d5adeeea2152dd80a/ghc >--------------------------------------------------------------- commit 9e4a9c1090ac800f6f2cf44d5adeeea2152dd80a Author: Andrey Mokhov Date: Mon Oct 23 23:04:06 2017 +0100 Fix the call to another script >--------------------------------------------------------------- 9e4a9c1090ac800f6f2cf44d5adeeea2152dd80a build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 460fdc1..434b3a3 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,4 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -./build.cabal.sh "$@" +( ./build.cabal.sh "$@" ) From git at git.haskell.org Fri Oct 27 01:02:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revise comments (816b0ac) Message-ID: <20171027010226.324F83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/816b0acda7a57cdb3c7a88831b445bb17405975b/ghc >--------------------------------------------------------------- commit 816b0acda7a57cdb3c7a88831b445bb17405975b Author: Andrey Mokhov Date: Thu May 19 23:39:15 2016 +0100 Revise comments >--------------------------------------------------------------- 816b0acda7a57cdb3c7a88831b445bb17405975b src/Oracles/ArgsHash.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs index c26efd4..bb597c4 100644 --- a/src/Oracles/ArgsHash.hs +++ b/src/Oracles/ArgsHash.hs @@ -8,26 +8,25 @@ import Settings.Args import Target newtype ArgsHashKey = ArgsHashKey Target - deriving (Show, Eq, Typeable, Binary, Hashable, NFData) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- This is an action that given a full target determines the corresponding --- argument list and computes its hash. The resulting value is tracked in a --- Shake oracle, hence initiating rebuilts when the hash is changed (a hash --- change indicates changes in the build system). +-- TODO: Hash Target to improve accuracy and performance. +-- | Given a full target this Action determines the corresponding argument list +-- and computes its hash. The resulting value is tracked in a Shake oracle, +-- hence initiating rebuilds when the hash changes (a hash change indicates +-- changes in the build command for the given target). -- Note: we keep only the first target input for performance reasons -- to -- avoid storing long lists of source files passed to some builders (e.g. Ar) --- in the Shake database. This optimisation is harmless, because argument list --- constructors are assumed not to examine target sources, but only append them --- to argument lists where appropriate. --- TODO: enforce the above assumption via type trickery? --- TODO: Hash Target to improve accuracy and performance. +-- in the Shake database. This optimisation is normally harmless, because +-- argument list constructors are assumed not to examine target sources, but +-- only append them to argument lists where appropriate. checkArgsHash :: Target -> Action () checkArgsHash target = when trackBuildSystem $ do let hashed = [ show . hash $ inputs target ] _ <- askOracle . ArgsHashKey $ target { inputs = hashed } :: Action Int return () --- Oracle for storing per-target argument list hashes +-- | Oracle for storing per-target argument list hashes. argsHashOracle :: Rules () argsHashOracle = void $ addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs From git at git.haskell.org Fri Oct 27 01:02:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CI by calling default script via bash (14c2c27) Message-ID: <20171027010226.46ECB3A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14c2c279aa49b272f9cae73269bd9e99bf887b2e/ghc >--------------------------------------------------------------- commit 14c2c279aa49b272f9cae73269bd9e99bf887b2e Author: Andrey Mokhov Date: Mon Oct 23 23:18:13 2017 +0100 Fix CI by calling default script via bash >--------------------------------------------------------------- 14c2c279aa49b272f9cae73269bd9e99bf887b2e build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 434b3a3..f40e06e 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,4 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -( ./build.cabal.sh "$@" ) +bash './build.cabal.sh "$@"' From git at git.haskell.org Fri Oct 27 01:02:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop quotes (4e7d0f9) Message-ID: <20171027010230.0ED283A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e7d0f99d807a876dcc5ff420a42f5793c854250/ghc >--------------------------------------------------------------- commit 4e7d0f99d807a876dcc5ff420a42f5793c854250 Author: Andrey Mokhov Date: Mon Oct 23 23:25:42 2017 +0100 Drop quotes >--------------------------------------------------------------- 4e7d0f99d807a876dcc5ff420a42f5793c854250 build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index f40e06e..fa331fa 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,4 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -bash './build.cabal.sh "$@"' +bash ./build.cabal.sh "$@" From git at git.haskell.org Fri Oct 27 01:02:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependency (ba108c0) Message-ID: <20171027010230.11EA33A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ba108c0198cc3ee6cd758273f9bd8fea14ba93a5/ghc >--------------------------------------------------------------- commit ba108c0198cc3ee6cd758273f9bd8fea14ba93a5 Author: Andrey Mokhov Date: Thu May 19 23:50:46 2016 +0100 Add missing dependency See #241. >--------------------------------------------------------------- ba108c0198cc3ee6cd758273f9bd8fea14ba93a5 src/Rules/Library.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 3fff65f..a198c64 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -71,6 +71,7 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] gObjs = [ gmpObjects -/- "*.o" | package == integerGmp ] objs = cObjs ++ hObjs + when (package == integerGmp) $ orderOnly [gmpLibraryH] need objs build $ Target context Ld (objs ++ gObjs) [obj] From git at git.haskell.org Fri Oct 27 01:02:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CI (#441) (4b60862) Message-ID: <20171027010233.9DA123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b60862b82d50a6946ac130f113c6e693f7a346d/ghc >--------------------------------------------------------------- commit 4b60862b82d50a6946ac130f113c6e693f7a346d Author: Andrey Mokhov Date: Tue Oct 24 14:02:55 2017 +0100 Fix CI (#441) * Fix CI * Another attempt * Another tweak >--------------------------------------------------------------- 4b60862b82d50a6946ac130f113c6e693f7a346d build.sh | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/build.sh b/build.sh index fa331fa..8e58b66 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,5 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -bash ./build.cabal.sh "$@" +chmod a+x ./build.cabal.sh +(. ./build.cabal.sh "$@") From git at git.haskell.org Fri Oct 27 01:02:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Pass GMP objects to Ld explicitly (aaead2a) Message-ID: <20171027010233.C45B83A5EB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/aaead2a5caa9fa96cc8a9f8a2762582bec70126f/ghc >--------------------------------------------------------------- commit aaead2a5caa9fa96cc8a9f8a2762582bec70126f Author: Andrey Mokhov Date: Fri May 20 00:23:50 2016 +0100 Pass GMP objects to Ld explicitly See #241. >--------------------------------------------------------------- aaead2a5caa9fa96cc8a9f8a2762582bec70126f src/Rules/Library.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index a198c64..2e59755 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -67,13 +67,12 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do cSrcs <- cSources context hSrcs <- hSources context + eObjs <- extraObjects context let cObjs = map (objFile context) cSrcs hObjs = [ path -/- src <.> osuf way | src <- hSrcs ] - gObjs = [ gmpObjects -/- "*.o" | package == integerGmp ] - objs = cObjs ++ hObjs - when (package == integerGmp) $ orderOnly [gmpLibraryH] + objs = cObjs ++ hObjs ++ eObjs need objs - build $ Target context Ld (objs ++ gObjs) [obj] + build $ Target context Ld objs [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. -- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' From git at git.haskell.org Fri Oct 27 01:02:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add 'hadrian/' from commit '4b60862b82d50a6946ac130f113c6e693f7a346d' (b2d1daa) Message-ID: <20171027010236.CFC6C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2d1daac23cc16baac69e718f1094a568f2edec1/ghc >--------------------------------------------------------------- commit b2d1daac23cc16baac69e718f1094a568f2edec1 Merge: d91a6b6 4b60862 Author: Ben Gamari Date: Thu Oct 26 09:50:56 2017 -0400 Add 'hadrian/' from commit '4b60862b82d50a6946ac130f113c6e693f7a346d' git-subtree-dir: hadrian git-subtree-mainline: d91a6b6c1d7699b6e9ace1988974d4453a20dab6 git-subtree-split: 4b60862b82d50a6946ac130f113c6e693f7a346d >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b2d1daac23cc16baac69e718f1094a568f2edec1 From git at git.haskell.org Fri Oct 27 01:02:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on --progress-colour (ffcc3d9) Message-ID: <20171027010237.50AC53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ffcc3d939e3854b8f7041814cb6d64761cf59822/ghc >--------------------------------------------------------------- commit ffcc3d939e3854b8f7041814cb6d64761cf59822 Author: Andrey Mokhov Date: Sat May 21 00:41:58 2016 +0100 Add a note on --progress-colour [skip ci] >--------------------------------------------------------------- ffcc3d939e3854b8f7041814cb6d64761cf59822 README.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/README.md b/README.md index fdbdbc5..9e7c6ca 100644 --- a/README.md +++ b/README.md @@ -58,6 +58,11 @@ profiling, which speeds up builds by 3-4x). * `--haddock`: build Haddock documentation. +* `--progress-colour=MODE`: choose whether to use colours when printing build progress +info. There are three settings: `never` (do not use colours), `auto` (attempt to detect +whether the console supports colours; this is the default setting), and `always` (use +colours). + * `--progress-info=STYLE`: choose how build progress info is printed. There are four settings: `none`, `brief` (one line per build command), `normal` (typically a box per build command; this is the default setting), and `unicorn` (when `normal` just won't do). From git at git.haskell.org Fri Oct 27 01:02:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't ignore hadrian/ (2f11b17) Message-ID: <20171027010239.AFF7E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f11b17af7ef8f1b5f518dff7dbae6173e7d0515/ghc >--------------------------------------------------------------- commit 2f11b17af7ef8f1b5f518dff7dbae6173e7d0515 Author: Ben Gamari Date: Thu Oct 26 09:51:02 2017 -0400 Don't ignore hadrian/ >--------------------------------------------------------------- 2f11b17af7ef8f1b5f518dff7dbae6173e7d0515 .gitignore | 1 - 1 file changed, 1 deletion(-) diff --git a/.gitignore b/.gitignore index 710c6bf..f1b38d6 100644 --- a/.gitignore +++ b/.gitignore @@ -49,7 +49,6 @@ stage0 stage1 stage2 _build -hadrian # ----------------------------------------------------------------------------- # Ignore any overlapped darcs repos and back up files From git at git.haskell.org Fri Oct 27 01:02:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a note on --verbose (1054490) Message-ID: <20171027010240.DF8F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/10544904eab3383c145c6904ad6d4bb19cc55329/ghc >--------------------------------------------------------------- commit 10544904eab3383c145c6904ad6d4bb19cc55329 Author: Andrey Mokhov Date: Sat May 21 00:48:01 2016 +0100 Add a note on --verbose [skip ci] >--------------------------------------------------------------- 10544904eab3383c145c6904ad6d4bb19cc55329 README.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/README.md b/README.md index 9e7c6ca..e4fb7dc 100644 --- a/README.md +++ b/README.md @@ -82,6 +82,9 @@ is your friend in such cases. * `--split-objects`: generate split objects, which are switched off by default. Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using this flag. +* `--verbose`: run Hadrian in verbose mode. In particular this prints diagnostic messages +by Shake oracles. + #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We From git at git.haskell.org Fri Oct 27 01:02:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: base: Implement file locking in terms of POSIX locks (1cd7473) Message-ID: <20171027010242.929483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1cd7473f8e800a99e95180579480a0e62e98040b/ghc >--------------------------------------------------------------- commit 1cd7473f8e800a99e95180579480a0e62e98040b Author: Ben Gamari Date: Thu Oct 26 10:40:11 2017 -0400 base: Implement file locking in terms of POSIX locks Hopefully these are more robust to NFS malfunction than BSD flock-style locks. See #13945. >--------------------------------------------------------------- 1cd7473f8e800a99e95180579480a0e62e98040b libraries/base/GHC/IO/Handle/Lock.hsc | 74 ++++++++++++++++++++++++++++++++++- libraries/base/configure.ac | 7 +++- 2 files changed, 78 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/IO/Handle/Lock.hsc b/libraries/base/GHC/IO/Handle/Lock.hsc index daf407c..b0a3449 100644 --- a/libraries/base/GHC/IO/Handle/Lock.hsc +++ b/libraries/base/GHC/IO/Handle/Lock.hsc @@ -104,7 +104,76 @@ hUnlock = unlockImpl ---------------------------------------- -#if HAVE_FLOCK +#if HAVE_OFD_LOCKING +-- Linux open file descriptor locking. +-- +-- We prefer this over BSD locking (e.g. flock) since the latter appears to +-- break in some NFS configurations. Note that we intentionally do not try to +-- use ordinary POSIX file locking due to its peculiar semantics under +-- multi-threaded environments. + +foreign import ccall interruptible "fcntl" + c_fcntl :: CInt -> CInt -> Ptr () -> IO CInt + +data FLock = FLock { l_type :: CShort + , l_whence :: CShort + , l_start :: COff + , l_len :: COff + , l_pid :: CPid + } + +instance Storable FLock where + sizeOf _ = #{size flock} + alignment _ = #{alignment flock} + poke ptr x = do + fillBytes ptr 0 (sizeOf x) + #{poke flock, l_type} ptr (l_type x) + #{poke flock, l_whence} ptr (l_whence x) + #{poke flock, l_start} ptr (l_start x) + #{poke flock, l_len} ptr (l_len x) + #{poke flock, l_pid} ptr (l_pid x) + peek ptr = do + FLock <$> #{peek flock, l_type} ptr + <*> #{peek flock, l_whence} ptr + <*> #{peek flock, l_start} ptr + <*> #{peek flock, l_len} ptr + <*> #{peek flock, l_pid} ptr + +lockImpl :: Handle -> String -> LockMode -> Bool -> IO Bool +lockImpl h ctx mode block = do + FD{fdFD = fd} <- handleToFd h + with flock $ \flock_ptr -> fix $ \retry -> do + ret <- with flock $ fcntl fd mode flock_ptr + case ret of + 0 -> return True + _ -> getErrno >>= \errno -> if + | not block && errno == eWOULDBLOCK -> return False + | errno == eINTR -> retry + | otherwise -> ioException $ errnoToIOError ctx errno (Just h) Nothing + where + flock = FLock { l_type = case mode of + SharedLock -> #{const F_RDLCK} + ExclusiveLock -> #{const F_WRLCK} + , l_whence = #{const SEEK_SET} + , l_start = 0 + , l_len = 0 + } + mode + | block = #{const F_SETLKW} + | otherwise = #{const F_SETLK} + +unlockImpl :: Handle -> IO () +unlockImpl h = do + FD{fdFD = fd} <- handleToFd h + let flock = FLock { l_type = #{const F_UNLCK} + , l_whence = #{const SEEK_SET} + , l_start = 0 + , l_len = 0 + } + throwErrnoIfMinus1_ "hUnlock" + $ with flock $ c_fcntl fd #{const F_SETLK} + +#elif HAVE_FLOCK lockImpl :: Handle -> String -> LockMode -> Bool -> IO Bool lockImpl h ctx mode block = do @@ -113,7 +182,8 @@ lockImpl h ctx mode block = do fix $ \retry -> c_flock fd flags >>= \case 0 -> return True _ -> getErrno >>= \errno -> if - | not block && errno == eWOULDBLOCK -> return False + | not block + , errno == eAGAIN || errno == eACCES -> return False | errno == eINTR -> retry | otherwise -> ioException $ errnoToIOError ctx errno (Just h) Nothing where diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index af041a7..69ea800 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -69,7 +69,12 @@ if test "$ac_cv_header_poll_h" = yes && test "$ac_cv_func_poll" = yes; then AC_DEFINE([HAVE_POLL], [1], [Define if you have poll support.]) fi -#flock +# Linux open file description locks +AC_CHECK_DECL([F_OFD_SETLK], [ + AC_DEFINE([HAVE_OFD_LOCKING], [1], [Define if you have open file descriptor lock support.]) +]) + +# flock AC_CHECK_FUNCS([flock]) if test "$ac_cv_header_sys_file_h" = yes && test "$ac_cv_func_flock" = yes; then AC_DEFINE([HAVE_FLOCK], [1], [Define if you have flock support.]) From git at git.haskell.org Fri Oct 27 01:02:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build check-api-annotations (5d2c1ee) Message-ID: <20171027010244.682663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d2c1eed519b6d90bcab8f993c428b265d4cb8fd/ghc >--------------------------------------------------------------- commit 5d2c1eed519b6d90bcab8f993c428b265d4cb8fd Author: Andrey Mokhov Date: Sat May 21 00:59:42 2016 +0100 Build check-api-annotations Fix #242. >--------------------------------------------------------------- 5d2c1eed519b6d90bcab8f993c428b265d4cb8fd src/GHC.hs | 137 ++++++++++++++++++++++++----------------------- src/Settings/Packages.hs | 2 +- 2 files changed, 70 insertions(+), 69 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 5d2c1eed519b6d90bcab8f993c428b265d4cb8fd From git at git.haskell.org Fri Oct 27 01:02:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:45 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump Cabal submodule (5d02bca) Message-ID: <20171027010245.6094E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/5d02bca29596e28b0499f4706062c8c804908bd9/ghc >--------------------------------------------------------------- commit 5d02bca29596e28b0499f4706062c8c804908bd9 Author: Ben Gamari Date: Thu Oct 26 16:19:41 2017 -0400 Bump Cabal submodule >--------------------------------------------------------------- 5d02bca29596e28b0499f4706062c8c804908bd9 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index c84a3c7..b26a9ee 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit c84a3c72196d0a5361f8ab77c6d8cb63b7a5d55d +Subproject commit b26a9ee3eb062ac727141fd9fd85835c2349f380 From git at git.haskell.org Fri Oct 27 01:02:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing dependencies for Stage2 packages (2c74f92) Message-ID: <20171027010248.121DB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2c74f92cc3db93f71f294e4f0797a1866950467c/ghc >--------------------------------------------------------------- commit 2c74f92cc3db93f71f294e4f0797a1866950467c Author: Andrey Mokhov Date: Sat May 21 02:23:31 2016 +0100 Fix missing dependencies for Stage2 packages Fix #240. >--------------------------------------------------------------- 2c74f92cc3db93f71f294e4f0797a1866950467c src/Rules/Cabal.hs | 2 +- src/Rules/Data.hs | 6 ++++-- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index 05078fc..82edb3a 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -28,7 +28,7 @@ cabalRules = do -- Cache package dependencies packageDependencies %> \out -> do - pkgs <- interpretInContext (stageContext Stage1) getPackages + let pkgs = knownPackages \\ [hp2ps, libffi, touchy, unlit] pkgDeps <- forM (sort pkgs) $ \pkg -> if pkg == rts then return $ pkgNameString pkg diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 8512c3a..2ecfb37 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -31,10 +31,12 @@ buildPackageData context at Context {..} = do whenM (doesFileExist $ configure <.> "ac") $ need [configure] -- Before we configure a package its dependencies need to be registered + let depStage = min stage Stage1 -- dependencies come from Stage0/1 + depContext = vanillaContext depStage deps <- packageDeps package - pkgs <- interpretInContext context getPackages + pkgs <- interpretInContext (depContext package) getPackages let depPkgs = matchPackageNames (sort pkgs) deps - need =<< traverse (pkgConfFile . vanillaContext stage) depPkgs + need =<< traverse (pkgConfFile . depContext) depPkgs need [cabalFile] build $ Target context GhcCabal [cabalFile] [mk] From git at git.haskell.org Fri Oct 27 01:02:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor dependency oracles (b6f224c) Message-ID: <20171027010251.CEBBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b6f224c4535039fb77fd31e8229917ee4267f16f/ghc >--------------------------------------------------------------- commit b6f224c4535039fb77fd31e8229917ee4267f16f Author: Andrey Mokhov Date: Sun May 22 00:02:50 2016 +0100 Refactor dependency oracles >--------------------------------------------------------------- b6f224c4535039fb77fd31e8229917ee4267f16f hadrian.cabal | 1 - src/Oracles/Config.hs | 2 +- src/Oracles/Config/Flag.hs | 5 +- src/Oracles/Config/Setting.hs | 31 +++++----- src/Oracles/Dependencies.hs | 102 +++++++++++++++++++++++-------- src/Oracles/LookupInPath.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/PackageDeps.hs | 30 --------- src/Oracles/WindowsPath.hs | 7 +-- src/Package.hs | 35 ++++------- src/Rules/Cabal.hs | 9 ++- src/Rules/Compile.hs | 15 +++-- src/Rules/Data.hs | 29 ++++----- src/Rules/Generators/GhcBootPlatformH.hs | 1 - src/Rules/Generators/GhcPlatformH.hs | 1 - src/Rules/Generators/VersionHs.hs | 1 - src/Rules/Oracles.hs | 4 +- src/Rules/Program.hs | 56 +++++++---------- src/Rules/Register.hs | 2 +- src/Settings/Builders/Ghc.hs | 16 ++--- src/Settings/Builders/GhcCabal.hs | 14 ++--- src/Settings/Paths.hs | 6 +- 22 files changed, 175 insertions(+), 196 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b6f224c4535039fb77fd31e8229917ee4267f16f From git at git.haskell.org Fri Oct 27 01:02:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:55 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop orderOnly dependency on GMP objects (19293d9) Message-ID: <20171027010255.670E63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/19293d92469d2c80e125f62d527407ea0ac5fe4e/ghc >--------------------------------------------------------------- commit 19293d92469d2c80e125f62d527407ea0ac5fe4e Author: Andrey Mokhov Date: Sun May 22 01:19:16 2016 +0100 Drop orderOnly dependency on GMP objects >--------------------------------------------------------------- 19293d92469d2c80e125f62d527407ea0ac5fe4e src/Rules/Gmp.hs | 2 +- src/Rules/Library.hs | 12 ++++++------ 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 845ba6e..f761639 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -1,4 +1,4 @@ -module Rules.Gmp (gmpRules) where +module Rules.Gmp (gmpRules, gmpContext) where import Base import Builder diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index 2e59755..edbdb52 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -8,9 +8,9 @@ import qualified System.Directory as IO import Base import Context import Expression -import GHC import Oracles.PackageData import Rules.Actions +import Rules.Gmp import Settings import Target @@ -75,7 +75,7 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do build $ Target context Ld objs [obj] -- TODO: Get rid of code duplication and simplify. See also src2dep. --- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' +-- | Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath' -- to its object file. For example, in Context Stage1 rts threaded: -- * "Task.c" -> "_build/stage1/rts/Task.thr_o" -- * "_build/stage1/rts/sm/Evac_thr.c" -> "_build/stage1/rts/sm/Evac_thr.thr_o" @@ -90,12 +90,12 @@ cSources context = interpretInContext context $ getPkgDataList CSrcs hSources :: Context -> Action [FilePath] hSources context = do modules <- interpretInContext context $ getPkgDataList Modules - -- GHC.Prim is special: we do not build it + -- GHC.Prim is special: we do not build it. return . map (replaceEq '.' '/') . filter (/= "GHC.Prim") $ modules extraObjects :: Context -> Action [FilePath] -extraObjects (Context _ package _) - | package == integerGmp = do - orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113? +extraObjects context + | context == gmpContext = do + need [gmpLibraryH] -- TODO: Move this dependency elsewhere, #113? map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"] | otherwise = return [] From git at git.haskell.org Fri Oct 27 01:02:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:02:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run Make builder with -jN using N = shakeThreads (3de1a5a) Message-ID: <20171027010259.0094B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/3de1a5a65b7d97635ccd9a14601113b0802cd8f7/ghc >--------------------------------------------------------------- commit 3de1a5a65b7d97635ccd9a14601113b0802cd8f7 Author: Andrey Mokhov Date: Sun May 22 01:22:19 2016 +0100 Run Make builder with -jN using N = shakeThreads >--------------------------------------------------------------- 3de1a5a65b7d97635ccd9a14601113b0802cd8f7 src/Settings/Builders/Make.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index 6968cd0..3d06775 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -1,10 +1,14 @@ module Settings.Builders.Make (makeBuilderArgs) where +import Base import Predicate import Settings makeBuilderArgs :: Args -makeBuilderArgs = mconcat - [ builder (Make gmpBuildPath ) ? arg "MAKEFLAGS=" - , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=", "install"] - , builder (Make "testsuite/tests") ? arg "fast" ] +makeBuilderArgs = do + threads <- shakeThreads <$> lift getShakeOptions + let j = "-j" ++ show threads + mconcat + [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=" ++ j] + , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=" ++ j, "install"] + , builder (Make "testsuite/tests") ? arg "fast" ] From git at git.haskell.org Fri Oct 27 01:03:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop TransitiveDepNames (97d37ea) Message-ID: <20171027010302.9E0DD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9/ghc >--------------------------------------------------------------- commit 97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9 Author: Andrey Mokhov Date: Sun May 22 01:46:39 2016 +0100 Drop TransitiveDepNames >--------------------------------------------------------------- 97d37ea64e04bf18fb4ff57d2cbd3d42d05a2cf9 src/Oracles/PackageData.hs | 10 +++------- 1 file changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index af9e255..92c2e99 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -1,7 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Oracles.PackageData ( - PackageData (..), PackageDataList (..), - pkgData, pkgDataList, packageDataOracle + PackageData (..), PackageDataList (..), pkgData, pkgDataList, packageDataOracle ) where import Development.Shake.Config @@ -31,7 +30,6 @@ data PackageDataList = CcArgs FilePath | LdArgs FilePath | Modules FilePath | SrcDirs FilePath - | TransitiveDepNames FilePath newtype PackageDataKey = PackageDataKey (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -77,16 +75,14 @@ pkgDataList packageData = fmap (map unquote . words) $ case packageData of LdArgs path -> askPackageData path "LD_OPTS" Modules path -> askPackageData path "MODULES" SrcDirs path -> askPackageData path "HS_SRC_DIRS" - TransitiveDepNames path -> askPackageData path "TRANSITIVE_DEP_NAMES" where unquote = dropWhile (== '\'') . dropWhileEnd (== '\'') -- | Oracle for 'package-data.mk' files. packageDataOracle :: Rules () -packageDataOracle = do +packageDataOracle = void $ do keys <- newCache $ \file -> do need [file] putLoud $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - _ <- addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file - return () + addOracle $ \(PackageDataKey (file, key)) -> Map.lookup key <$> keys file From git at git.haskell.org Fri Oct 27 01:03:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename PackageDb to PackageDatabase (026466a) Message-ID: <20171027010306.50F833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/026466ad55688891c0e82b5de98f555dc6932223/ghc >--------------------------------------------------------------- commit 026466ad55688891c0e82b5de98f555dc6932223 Author: Andrey Mokhov Date: Sun May 22 01:48:07 2016 +0100 Rename PackageDb to PackageDatabase >--------------------------------------------------------------- 026466ad55688891c0e82b5de98f555dc6932223 hadrian.cabal | 2 +- src/Oracles/{PackageDb.hs => PackageDatabase.hs} | 8 ++++---- src/Rules/Oracles.hs | 8 ++++---- src/Settings/Builders/Ghc.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 20 ++++++++++---------- src/Settings/Builders/GhcPkg.hs | 4 ++-- 6 files changed, 22 insertions(+), 22 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index a65bbf8..95ae3a0 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -32,7 +32,7 @@ executable hadrian , Oracles.LookupInPath , Oracles.ModuleFiles , Oracles.PackageData - , Oracles.PackageDb + , Oracles.PackageDatabase , Oracles.WindowsPath , Package , Predicate diff --git a/src/Oracles/PackageDb.hs b/src/Oracles/PackageDatabase.hs similarity index 74% rename from src/Oracles/PackageDb.hs rename to src/Oracles/PackageDatabase.hs index 61b134a..f89a2cc 100644 --- a/src/Oracles/PackageDb.hs +++ b/src/Oracles/PackageDatabase.hs @@ -1,4 +1,4 @@ -module Oracles.PackageDb (packageDbOracle) where +module Oracles.PackageDatabase (packageDatabaseOracle) where import qualified System.Directory as IO @@ -12,9 +12,9 @@ import Settings.Paths import Settings.User import Target -packageDbOracle :: Rules () -packageDbOracle = void $ - addOracle $ \(PackageDbKey stage) -> do +packageDatabaseOracle :: Rules () +packageDatabaseOracle = void $ + addOracle $ \(PackageDatabaseKey stage) -> do let dir = packageDbDirectory stage file = dir -/- "package.cache" unlessM (liftIO $ IO.doesFileExist file) $ do diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 93bccfc..7beb67f 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -1,14 +1,14 @@ module Rules.Oracles (oracleRules) where import Base +import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies import qualified Oracles.LookupInPath +import qualified Oracles.ModuleFiles import qualified Oracles.PackageData +import qualified Oracles.PackageDatabase import qualified Oracles.WindowsPath -import qualified Oracles.ArgsHash -import qualified Oracles.ModuleFiles -import qualified Oracles.PackageDb oracleRules :: Rules () oracleRules = do @@ -18,5 +18,5 @@ oracleRules = do Oracles.LookupInPath.lookupInPathOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle - Oracles.PackageDb.packageDbOracle + Oracles.PackageDatabase.packageDatabaseOracle Oracles.WindowsPath.windowsPathOracle diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 02ffe4d..9b1430d 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -118,7 +118,7 @@ packageGhcArgs = do return $ if not0 || unit then "-this-unit-id " else "-this-package-key " mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" - , bootPackageDbArgs + , bootPackageDatabaseArgs , isLibrary pkg ? arg (thisArg ++ compId) , append $ map ("-package-id " ++) pkgDepIds ] diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index beaa8c7..396e69b 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -1,7 +1,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Settings.Builders.GhcCabal ( - ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDbArgs, - PackageDbKey (..), cppArgs, buildDll0 + ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDatabaseArgs, + PackageDatabaseKey (..), cppArgs, buildDll0 ) where import Base @@ -23,7 +23,7 @@ ghcCabalBuilderArgs = builder GhcCabal ? do , dll0Args , withStaged $ Ghc Compile , withStaged GhcPkg - , bootPackageDbArgs + , bootPackageDatabaseArgs , libraryArgs , with HsColour , configureArgs @@ -81,16 +81,16 @@ configureArgs = do , crossCompiling ? (conf "--host" $ argSetting TargetPlatformFull) , conf "--with-cc" $ argStagedBuilderPath (Cc Compile) ] -newtype PackageDbKey = PackageDbKey Stage - deriving (Show, Typeable, Eq, Hashable, Binary, NFData) +newtype PackageDatabaseKey = PackageDatabaseKey Stage + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -initialisePackageDb :: Stage -> Action () -initialisePackageDb stage = askOracle $ PackageDbKey stage +initialisePackageDatabase :: Stage -> Action () +initialisePackageDatabase = askOracle . PackageDatabaseKey -bootPackageDbArgs :: Args -bootPackageDbArgs = do +bootPackageDatabaseArgs :: Args +bootPackageDatabaseArgs = do stage <- getStage - lift $ initialisePackageDb stage + lift $ initialisePackageDatabase stage stage0 ? do path <- getTopDirectory prefix <- ifM (builder Ghc) (return "-package-db ") (return "--package-db=") diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index ba176ac..d6efd0b 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -14,12 +14,12 @@ initPredicate = orM $ map (output . packageDbDirectory) [Stage0 ..] initArgs :: Args initArgs = initPredicate ? mconcat [ arg "init", arg =<< getOutput ] --- TODO: move inplace-pkg-config to buildRootPath, see #113. +-- TODO: Move inplace-pkg-config to buildRootPath, see #113. updateArgs :: Args updateArgs = notM initPredicate ? do pkg <- getPackage dir <- getContextDirectory mconcat [ arg "update" , arg "--force" - , bootPackageDbArgs + , bootPackageDatabaseArgs , arg $ pkgPath pkg -/- dir -/- "inplace-pkg-config" ] From git at git.haskell.org Fri Oct 27 01:03:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use simpler mapM instead of traverse (73ad993) Message-ID: <20171027010310.164393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/73ad99359cbac01618824c65fa116a46d27a4575/ghc >--------------------------------------------------------------- commit 73ad99359cbac01618824c65fa116a46d27a4575 Author: Andrey Mokhov Date: Sun May 22 01:57:26 2016 +0100 Use simpler mapM instead of traverse >--------------------------------------------------------------- 73ad99359cbac01618824c65fa116a46d27a4575 src/Rules.hs | 2 +- src/Rules/Dependencies.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index e3caf6c..bea672d 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -45,7 +45,7 @@ topLevelTargets = do if isLibrary pkg then do -- build a library ways <- interpretInContext context getLibraryWays - libs <- traverse (pkgLibraryFile . Context stage pkg) ways + libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context buildHaddock need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ] else do -- otherwise build a program diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 78f4d40..c5f60bb 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -36,7 +36,7 @@ buildPackageDependencies rs context at Context {..} = cSrcs <- pkgDataList $ CSrcs path let cDepFiles = map (src2dep context) cSrcs need $ hDepFile : cDepFiles -- need all for more parallelism - cDeps <- fmap concat $ traverse readFile' cDepFiles + cDeps <- concatMapM readFile' cDepFiles hDeps <- readFile' hDepFile let result = unlines . map (\(src, deps) -> unwords $ src : deps) From git at git.haskell.org Fri Oct 27 01:03:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify using firstJustM (8933a3a) Message-ID: <20171027010313.841FE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8933a3a8235a642638ef8e7e5e7c91777829535b/ghc >--------------------------------------------------------------- commit 8933a3a8235a642638ef8e7e5e7c91777829535b Author: Andrey Mokhov Date: Sun May 22 02:10:55 2016 +0100 Simplify using firstJustM >--------------------------------------------------------------- 8933a3a8235a642638ef8e7e5e7c91777829535b src/Oracles/Dependencies.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index d6cdbd3..a458b6d 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -24,8 +24,7 @@ fileDependencies :: Context -> FilePath -> Action (FilePath, [FilePath]) fileDependencies context obj = do let path = buildPath context -/- ".dependencies" -- If no dependencies found, try to drop the way suffix (for *.c sources). - deps <- listToMaybe . catMaybes <$> - mapM (askOracle . ObjDepsKey . (,) path) [obj, obj -<.> "o"] + deps <- firstJustM (askOracle . ObjDepsKey . (,) path) [obj, obj -<.> "o"] case deps of Nothing -> error $ "No dependencies found for file " ++ obj Just [] -> error $ "No source file found for file " ++ obj From git at git.haskell.org Fri Oct 27 01:03:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (15acc2c) Message-ID: <20171027010317.384D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/15acc2cd1cc217335d37b55beeb421bd5c4ac48d/ghc >--------------------------------------------------------------- commit 15acc2cd1cc217335d37b55beeb421bd5c4ac48d Author: Andrey Mokhov Date: Sun May 22 20:04:30 2016 +0100 Minor revision >--------------------------------------------------------------- 15acc2cd1cc217335d37b55beeb421bd5c4ac48d src/Builder.hs | 21 +++++++++++---------- src/Expression.hs | 10 ++++------ src/Oracles/Config.hs | 22 +++++++++------------- src/Oracles/Config/Flag.hs | 32 +++++++++++++++----------------- src/Oracles/Config/Setting.hs | 4 ++-- src/Oracles/Dependencies.hs | 30 +++++++++++------------------- src/Oracles/LookupInPath.hs | 6 ++---- src/Oracles/ModuleFiles.hs | 2 +- src/Oracles/PackageData.hs | 5 +---- src/Predicate.hs | 7 +++---- src/Rules/Generate.hs | 6 ++---- src/Rules/Gmp.hs | 9 ++++----- src/Rules/Libffi.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- 14 files changed, 67 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 15acc2cd1cc217335d37b55beeb421bd5c4ac48d From git at git.haskell.org Fri Oct 27 01:03:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Set `THREADS` when running validate (e7e58aa) Message-ID: <20171027010320.AFD993A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e7e58aaff96f2f74097ea8f605b216b8fdd15443/ghc >--------------------------------------------------------------- commit e7e58aaff96f2f74097ea8f605b216b8fdd15443 Author: Michal Terepeta Date: Sun May 22 21:26:53 2016 +0200 Set `THREADS` when running validate GHC testsuite uses the `THREADS` env variable (and not the make's `-j` setting) to control the parallelism. This commit sets THREADS to the value of `shakeThreads`. >--------------------------------------------------------------- e7e58aaff96f2f74097ea8f605b216b8fdd15443 src/Settings/Builders/Make.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Builders/Make.hs b/src/Settings/Builders/Make.hs index 3d06775..afb46d7 100644 --- a/src/Settings/Builders/Make.hs +++ b/src/Settings/Builders/Make.hs @@ -11,4 +11,4 @@ makeBuilderArgs = do mconcat [ builder (Make gmpBuildPath ) ? append ["MAKEFLAGS=" ++ j] , builder (Make libffiBuildPath ) ? append ["MAKEFLAGS=" ++ j, "install"] - , builder (Make "testsuite/tests") ? arg "fast" ] + , builder (Make "testsuite/tests") ? append ["THREADS=" ++ show threads, "fast"] ] From git at git.haskell.org Fri Oct 27 01:03:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #256 from michalt/validate-threads (f24d880) Message-ID: <20171027010324.33FDC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f24d88059e6f331dfbe789999d0ec6aca58fe64b/ghc >--------------------------------------------------------------- commit f24d88059e6f331dfbe789999d0ec6aca58fe64b Merge: 15acc2c e7e58aa Author: Andrey Mokhov Date: Sun May 22 21:53:26 2016 +0100 Merge pull request #256 from michalt/validate-threads Set `THREADS` when running validate >--------------------------------------------------------------- f24d88059e6f331dfbe789999d0ec6aca58fe64b src/Settings/Builders/Make.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 01:03:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Upgrade to extra-1.4.7 (00b88a1) Message-ID: <20171027010327.B470E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/00b88a16a67cf107eaf716b55ff5016fc5732c2a/ghc >--------------------------------------------------------------- commit 00b88a16a67cf107eaf716b55ff5016fc5732c2a Author: Andrey Mokhov Date: Mon May 23 00:16:14 2016 +0100 Upgrade to extra-1.4.7 >--------------------------------------------------------------- 00b88a16a67cf107eaf716b55ff5016fc5732c2a hadrian.cabal | 2 +- src/Oracles/Dependencies.hs | 2 +- src/Oracles/ModuleFiles.hs | 2 +- src/Rules/Library.hs | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 95ae3a0..c9d5551 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -122,7 +122,7 @@ executable hadrian , Cabal == 1.22.* || == 1.24.* , containers == 0.5.* , directory == 1.2.* - , extra == 1.4.* + , extra >= 1.4.7 , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.9 , shake >= 0.15.6 diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index ce94805..1a8b587 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -50,7 +50,7 @@ contextDependencies context at Context {..} = do -- | Coarse-grain 'need': make sure given contexts are fully built. needContext :: [Context] -> Action () needContext cs = do - libs <- fmap concat . forM cs $ \context -> do + libs <- concatForM cs $ \context -> do libFile <- pkgLibraryFile context lib0File <- pkgLibraryFile0 context lib0 <- buildDll0 context diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index ece6d0b..b11ef3b 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -115,7 +115,7 @@ moduleFilesOracle = void $ do modules <- fmap sort . pkgDataList $ Modules path let dirs = (path -/- "autogen") : map (pkgPath package -/-) srcDirs modDirFiles = groupSort $ map decodeModule modules - result <- fmap concat . forM dirs $ \dir -> do + result <- concatForM dirs $ \dir -> do todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles forM todo $ \(mDir, mFiles) -> do let fullDir = unifyPath $ dir -/- mDir diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index edbdb52..dd144d1 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -36,7 +36,7 @@ buildPackageLibrary context at Context {..} = do split <- interpretInContext context splitObjects splitObjs <- if not split then return hObjs else -- TODO: make clearer! - fmap concat $ forM hSrcs $ \src -> do + concatForM hSrcs $ \src -> do let splitPath = path -/- src ++ "_" ++ osuf way ++ "_split" contents <- liftIO $ IO.getDirectoryContents splitPath return . map (splitPath -/-) From git at git.haskell.org Fri Oct 27 01:03:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop shake-0.15.6 from extra-deps, and add extra-1.4.7 (ec031af) Message-ID: <20171027010331.2CE013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ec031af8526a0187cbf6701c18ccd4687bff0160/ghc >--------------------------------------------------------------- commit ec031af8526a0187cbf6701c18ccd4687bff0160 Author: Andrey Mokhov Date: Mon May 23 00:38:19 2016 +0100 Drop shake-0.15.6 from extra-deps, and add extra-1.4.7 >--------------------------------------------------------------- ec031af8526a0187cbf6701c18ccd4687bff0160 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index 0d8809b..b20331f 100644 --- a/stack.yaml +++ b/stack.yaml @@ -9,7 +9,7 @@ packages: # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: -- shake-0.15.6 +- extra-1.4.7 # Override default flag values for local packages and extra-deps flags: {} From git at git.haskell.org Fri Oct 27 01:03:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Use LTS-5.17 (68f8eaf) Message-ID: <20171027010334.B0BCC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68f8eafed955a6b1ed895960c21144c50c0c61d1/ghc >--------------------------------------------------------------- commit 68f8eafed955a6b1ed895960c21144c50c0c61d1 Author: Andrey Mokhov Date: Mon May 23 01:31:47 2016 +0100 Use LTS-5.17 >--------------------------------------------------------------- 68f8eafed955a6b1ed895960c21144c50c0c61d1 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index b20331f..f6deca8 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,7 +1,7 @@ # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration.html # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-5.1 +resolver: lts-5.17 # Local packages, usually specified by relative directory name packages: From git at git.haskell.org Fri Oct 27 01:03:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Packages/Rts: add `linker` to RTS directories (166e3fb) Message-ID: <20171027010338.2F9813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/166e3fb4aa2e8c4040287c1d87bf022b81a07790/ghc >--------------------------------------------------------------- commit 166e3fb4aa2e8c4040287c1d87bf022b81a07790 Author: Michal Terepeta Date: Wed May 25 20:14:33 2016 +0200 Packages/Rts: add `linker` to RTS directories Recent commit split off the m32 allocator to `rts/linker/`, which broke the build using Hadrian (since it didn't know about the new directory). This fixes it. Signed-off-by: Michal Terepeta >--------------------------------------------------------------- 166e3fb4aa2e8c4040287c1d87bf022b81a07790 src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 52aac32..6c99113 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -104,7 +104,7 @@ buildPackageData context at Context {..} = do orderOnly $ generatedDependencies stage package windows <- windowsHost let prefix = fixKey (buildPath context) ++ "_" - dirs = [ ".", "hooks", "sm", "eventlog" ] + dirs = [ ".", "hooks", "sm", "eventlog", "linker" ] ++ [ if windows then "win32" else "posix" ] -- TODO: Adding cmm/S sources to C_SRCS is a hack -- refactor. cSrcs <- map unifyPath <$> From git at git.haskell.org Fri Oct 27 01:03:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #257 from michalt/rts-linker/1 (45b5f13) Message-ID: <20171027010341.D93743A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45b5f1341e3b400efeaa675ddc9d43d69268ff09/ghc >--------------------------------------------------------------- commit 45b5f1341e3b400efeaa675ddc9d43d69268ff09 Merge: 68f8eaf 166e3fb Author: Andrey Mokhov Date: Wed May 25 21:47:24 2016 +0100 Merge pull request #257 from michalt/rts-linker/1 Packages/Rts: add `linker` to RTS directories >--------------------------------------------------------------- 45b5f1341e3b400efeaa675ddc9d43d69268ff09 src/Rules/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Oct 27 01:03:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge pull request #258 from KaiHa/ticket/247 (20d7082) Message-ID: <20171027010348.EAEEF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/20d70820a2c2fc7bfecacf79906db129d157846d/ghc >--------------------------------------------------------------- commit 20d70820a2c2fc7bfecacf79906db129d157846d Merge: 45b5f13 123bdb3 Author: Andrey Mokhov Date: Tue May 31 07:10:48 2016 +0100 Merge pull request #258 from KaiHa/ticket/247 Enable optional UserSettings.hs file >--------------------------------------------------------------- 20d70820a2c2fc7bfecacf79906db129d157846d .gitignore | 3 + README.md | 3 +- doc/user-settings.md | 5 +- hadrian.cabal | 3 +- src/Settings/User.hs | 103 ++---------------------------- src/{Settings/User.hs => UserSettings.hs} | 8 ++- 6 files changed, 20 insertions(+), 105 deletions(-) From git at git.haskell.org Fri Oct 27 01:03:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:03:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Enable optional UserSettings.hs file (123bdb3) Message-ID: <20171027010345.79FFD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/123bdb37674bfe60509886ec92c99e80b0588966/ghc >--------------------------------------------------------------- commit 123bdb37674bfe60509886ec92c99e80b0588966 Author: Kai Harries Date: Sat May 28 17:53:07 2016 +0200 Enable optional UserSettings.hs file Fix #247 The defaul user settings are stored in ./src/UserSettings.hs. If the user want to override these settings, he can copy this file into ./ and make the desired changes to ./UserSettings.hs. >--------------------------------------------------------------- 123bdb37674bfe60509886ec92c99e80b0588966 .gitignore | 3 + README.md | 3 +- doc/user-settings.md | 5 +- hadrian.cabal | 3 +- src/Settings/User.hs | 103 ++---------------------------- src/{Settings/User.hs => UserSettings.hs} | 8 ++- 6 files changed, 20 insertions(+), 105 deletions(-) diff --git a/.gitignore b/.gitignore index b7bfddb..5307cdd 100644 --- a/.gitignore +++ b/.gitignore @@ -15,3 +15,6 @@ cabal.sandbox.config # build.stack.sh specific /.stack-work/ + +# the user settings +/UserSettings.hs diff --git a/README.md b/README.md index e4fb7dc..b1da6f7 100644 --- a/README.md +++ b/README.md @@ -88,7 +88,7 @@ by Shake oracles. #### User settings The `make`-based build system uses `mk/build.mk` to specify user build settings. We -use [`src/Settings/User.hs`][user-settings] for the same purpose, see +use `./UserSettings.hs` for the same purpose, see [documentation](doc/user-settings.md). #### Clean and full rebuild @@ -155,7 +155,6 @@ helped me endure and enjoy the project. [windows-build]: https://github.com/snowleopard/hadrian/blob/master/doc/windows.md [build-artefacts-issue]: https://github.com/snowleopard/hadrian/issues/113 [ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 -[user-settings]: https://github.com/snowleopard/hadrian/blob/master/src/Settings/User.hs [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [dynamic-issue]: https://github.com/snowleopard/hadrian/issues/4 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 diff --git a/doc/user-settings.md b/doc/user-settings.md index 1433ae9..a5185ad 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,7 +1,8 @@ # User settings -You can customise Hadrian by specifying user build settings in file -`src/Settings/User.hs`. Here we document currently supported settings. +You can customise Hadrian by copying the file ./src/UserSettings.hs to +./UserSettings.hs and specifying user build settings in +`./UserSettings.hs`. Here we document currently supported settings. ## Build directory diff --git a/hadrian.cabal b/hadrian.cabal index c9d5551..3bbc2dd 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -16,7 +16,8 @@ source-repository head executable hadrian main-is: Main.hs - hs-source-dirs: src + hs-source-dirs: . + , src other-modules: Base , Builder , CmdLineFlag diff --git a/src/Settings/User.hs b/src/Settings/User.hs index 16c7c25..9588297 100644 --- a/src/Settings/User.hs +++ b/src/Settings/User.hs @@ -5,101 +5,8 @@ module Settings.User ( turnWarningsIntoErrors, splitObjects, verboseCommands, putBuild, putSuccess ) where -import System.Console.ANSI - -import Base -import CmdLineFlag -import GHC -import Predicate -import Settings.Default - --- See doc/user-settings.md for instructions. - --- | All build results are put into 'buildRootPath' directory. -buildRootPath :: FilePath -buildRootPath = "_build" - --- | Modify default build command line arguments. -userArgs :: Args -userArgs = builder Ghc ? remove ["-Wall", "-fwarn-tabs"] - --- | Modify the set of packages that are built by default in each stage. -userPackages :: Packages -userPackages = mempty - --- | Add user defined packages. Don't forget to add them to 'userPackages' too. -userKnownPackages :: [Package] -userKnownPackages = [] - --- | Choose the integer library: 'integerGmp' or 'integerSimple'. -integerLibrary :: Package -integerLibrary = integerGmp - --- FIXME: We skip 'dynamic' since it's currently broken #4. --- | Modify the set of ways in which library packages are built. -userLibraryWays :: Ways -userLibraryWays = remove [dynamic] - --- | Modify the set of ways in which the 'rts' package is built. -userRtsWays :: Ways -userRtsWays = mempty - --- | User defined flags. Note the following type semantics: --- * @Bool@: a plain Boolean flag whose value is known at compile time. --- * @Action Bool@: a flag whose value can depend on the build environment. --- * @Predicate@: a flag whose value can depend on the build environment and --- on the current build target. - --- TODO: Drop 'trackBuildSystem' as it brings negligible gains. --- | Set this to True if you are making any changes in the build system and want --- appropriate rebuilds to be initiated. Switching this to False speeds things --- up a little (particularly zero builds). --- WARNING: a complete rebuild is required when changing this setting. -trackBuildSystem :: Bool -trackBuildSystem = True - --- TODO: This should be set automatically when validating. -validating :: Bool -validating = False - --- | Control when split objects are generated. Note, due to the GHC bug #11315 --- it is necessary to do a full clean rebuild when changing this option. -splitObjects :: Predicate -splitObjects = (return cmdSplitObjects) &&^ defaultSplitObjects - --- | Control when to build Haddock documentation. -buildHaddock :: Predicate -buildHaddock = return cmdBuildHaddock - --- TODO: Do we need to be able to set these from command line? --- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? -dynamicGhcPrograms :: Bool -dynamicGhcPrograms = False - -ghciWithDebugger :: Bool -ghciWithDebugger = False - -ghcProfiled :: Bool -ghcProfiled = False - -ghcDebugged :: Bool -ghcDebugged = False - --- TODO: Replace with stage2 ? arg "-Werror"? Also see #251. --- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2. -turnWarningsIntoErrors :: Predicate -turnWarningsIntoErrors = return False - --- | Set to True to print full command lines during the build process. Note, --- this is a Predicate, hence you can enable verbose output only for certain --- targets, e.g.: @verboseCommands = package ghcPrim at . -verboseCommands :: Predicate -verboseCommands = return False - --- | Customise build progress messages (e.g. executing a build command). -putBuild :: String -> Action () -putBuild = putColoured Vivid White - --- | Customise build success messages (e.g. a package is built successfully). -putSuccess :: String -> Action () -putSuccess = putColoured Vivid Green +-- Import the actual user settings from the module UserSettings. +-- The user can put an UserSettings.hs file into the hadrian root +-- folder that takes precedence over the default UserSettings.hs +-- file located in src/. +import UserSettings diff --git a/src/Settings/User.hs b/src/UserSettings.hs similarity index 94% copy from src/Settings/User.hs copy to src/UserSettings.hs index 16c7c25..7560aa1 100644 --- a/src/Settings/User.hs +++ b/src/UserSettings.hs @@ -1,4 +1,8 @@ -module Settings.User ( +-- +-- If you want to customize your build you should copy this file from +-- ./src/UserSettings.hs to ./UserSettings.hs and only edit your copy. +-- +module UserSettings ( buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms, @@ -74,7 +78,7 @@ buildHaddock = return cmdBuildHaddock -- TODO: Do we need to be able to set these from command line? -- TODO: Turn the flags below into a simple list @ghcWays :: [Way]@? dynamicGhcPrograms :: Bool -dynamicGhcPrograms = False +dynamicGhcPrograms = True ghciWithDebugger :: Bool ghciWithDebugger = False From git at git.haskell.org Fri Oct 27 01:13:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (223d161) Message-ID: <20171027011314.3A6F43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/223d16102070b2d1061197ebb111ca3c9d2ffd45/ghc >--------------------------------------------------------------- commit 223d16102070b2d1061197ebb111ca3c9d2ffd45 Author: Andrey Mokhov Date: Sun Oct 30 13:28:09 2016 +0000 Minor revision >--------------------------------------------------------------- 223d16102070b2d1061197ebb111ca3c9d2ffd45 src/Settings/Default.hs | 163 +++++++++++++++++++++++------------------------- 1 file changed, 77 insertions(+), 86 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 9f61ff7..b59ceeb 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -43,46 +43,6 @@ import Settings.Packages.Touchy import Settings.Packages.Unlit import UserSettings --- | All 'Builder'-dependent command line arguments. -defaultBuilderArgs :: Args -defaultBuilderArgs = mconcat - [ alexBuilderArgs - , arBuilderArgs - , ccBuilderArgs - , configureBuilderArgs - , deriveConstantsBuilderArgs - , genPrimopCodeBuilderArgs - , ghcBuilderArgs - , ghcCabalBuilderArgs - , ghcCabalHsColourBuilderArgs - , ghcMBuilderArgs - , ghcPkgBuilderArgs - , haddockBuilderArgs - , happyBuilderArgs - , hsc2hsBuilderArgs - , hsCppBuilderArgs - , ldBuilderArgs - , makeBuilderArgs - , tarBuilderArgs ] - --- | All 'Package'-dependent command line arguments. -defaultPackageArgs :: Args -defaultPackageArgs = mconcat - [ basePackageArgs - , compilerPackageArgs - , directoryPackageArgs - , ghcPackageArgs - , ghcCabalPackageArgs - , ghcPrimPackageArgs - , haddockPackageArgs - , hp2psPackageArgs - , integerGmpPackageArgs - , iservBinPackageArgs - , rtsPackageArgs - , runGhcPackageArgs - , touchyPackageArgs - , unlitPackageArgs ] - -- | All default command line arguments. defaultArgs :: Args defaultArgs = mconcat @@ -93,10 +53,12 @@ defaultArgs = mconcat -- | Packages that are built by default. You can change this by editing -- 'userPackages' in "UserSettings". defaultPackages :: Packages -defaultPackages = mconcat [ packagesStage0, packagesStage1, packagesStage2 ] +defaultPackages = mconcat [ stage0 ? stage0Packages + , stage1 ? stage1Packages + , stage2 ? stage2Packages ] -packagesStage0 :: Packages -packagesStage0 = stage0 ? do +stage0Packages :: Packages +stage0Packages = do win <- lift windowsHost ios <- lift iosHost append $ [ binary @@ -122,52 +84,41 @@ packagesStage0 = stage0 ? do [ terminfo | not win, not ios ] ++ [ touchy | win ] -packagesStage1 :: Packages -packagesStage1 = stage1 ? do +stage1Packages :: Packages +stage1Packages = do win <- lift windowsHost - ios <- lift iosHost doc <- buildHaddock flavour - append $ [ array - , base - , binary - , bytestring - , cabal - , containers - , compareSizes - , compiler - , deepseq - , directory - , filepath - , ghc - , ghcBoot - , ghcBootTh - , ghcCabal - , ghci - , ghcPkg - , ghcPrim - , haskeline - , hoopl - , hpc - , hpcBin - , hsc2hs - , integerLibrary - , pretty - , process - , rts - , runGhc - , templateHaskell - , time - , transformers ] ++ - [ iservBin | not win ] ++ - [ terminfo | not win, not ios ] ++ - [ unix | not win ] ++ - [ win32 | win ] ++ - [ xhtml | doc ] + mconcat [ stage0Packages + , apply (filter isLibrary) -- Build all Stage0 libraries in Stage1 + , append $ [ array + , base + , bytestring + , containers + , compareSizes + , deepseq + , directory + , filepath + , ghc + , ghcCabal + , ghci + , ghcPkg + , ghcPrim + , haskeline + , hpcBin + , hsc2hs + , integerLibrary + , pretty + , process + , rts + , runGhc + , time ] ++ + [ iservBin | not win ] ++ + [ unix | not win ] ++ + [ win32 | win ] ++ + [ xhtml | doc ] ] --- TODO: Currently there is an unchecked assumption that we build only programs --- in Stage2 and Stage3. Can we check this in compile time? -packagesStage2 :: Packages -packagesStage2 = stage2 ? do +stage2Packages :: Packages +stage2Packages = do doc <- buildHaddock flavour append $ [ checkApiAnnotations , ghcTags ] ++ @@ -220,3 +171,43 @@ defaultSplitObjects = do supported <- lift supportsSplitObjects let goodPackage = isLibrary pkg && pkg /= compiler && pkg /= rts return $ cmdSplitObjects && goodStage && goodPackage && supported + +-- | All 'Builder'-dependent command line arguments. +defaultBuilderArgs :: Args +defaultBuilderArgs = mconcat + [ alexBuilderArgs + , arBuilderArgs + , ccBuilderArgs + , configureBuilderArgs + , deriveConstantsBuilderArgs + , genPrimopCodeBuilderArgs + , ghcBuilderArgs + , ghcCabalBuilderArgs + , ghcCabalHsColourBuilderArgs + , ghcMBuilderArgs + , ghcPkgBuilderArgs + , haddockBuilderArgs + , happyBuilderArgs + , hsc2hsBuilderArgs + , hsCppBuilderArgs + , ldBuilderArgs + , makeBuilderArgs + , tarBuilderArgs ] + +-- | All 'Package'-dependent command line arguments. +defaultPackageArgs :: Args +defaultPackageArgs = mconcat + [ basePackageArgs + , compilerPackageArgs + , directoryPackageArgs + , ghcPackageArgs + , ghcCabalPackageArgs + , ghcPrimPackageArgs + , haddockPackageArgs + , hp2psPackageArgs + , integerGmpPackageArgs + , iservBinPackageArgs + , rtsPackageArgs + , runGhcPackageArgs + , touchyPackageArgs + , unlitPackageArgs ] From git at git.haskell.org Fri Oct 27 01:13:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add a selftest for Packages (e2871fc) Message-ID: <20171027011317.A445B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2871fc28f9f8de741326bdc9b7ad48aa1936393/ghc >--------------------------------------------------------------- commit e2871fc28f9f8de741326bdc9b7ad48aa1936393 Author: Andrey Mokhov Date: Sun Oct 30 17:26:46 2016 +0000 Add a selftest for Packages >--------------------------------------------------------------- e2871fc28f9f8de741326bdc9b7ad48aa1936393 src/Rules/Selftest.hs | 53 ++++++++++++++++++++++++++++++--------------------- 1 file changed, 31 insertions(+), 22 deletions(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index e7f5dbb..58de8fb 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -6,11 +6,11 @@ import Development.Shake import Test.QuickCheck import Base -import Builder +import Expression import Oracles.ModuleFiles +import Settings import Settings.Builders.Ar import UserSettings -import Way instance Arbitrary Way where arbitrary = wayFromUnits <$> arbitrary @@ -25,11 +25,12 @@ selftestRules :: Rules () selftestRules = "selftest" ~> do testBuilder - testWay testChunksOfSize + testLookupAll testMatchVersionedFilePath testModuleName - testLookupAll + testPackages + testWay testBuilder :: Action () testBuilder = do @@ -39,11 +40,6 @@ testBuilder = do trackedArgument (Make undefined) prefix == False && trackedArgument (Make undefined) ("-j" ++ show (n :: Int)) == False -testWay :: Action () -testWay = do - putBuild $ "==== Read Way, Show Way" - test $ \(x :: Way) -> read (show x) == x - testChunksOfSize :: Action () testChunksOfSize = do putBuild $ "==== chunksOfSize" @@ -53,6 +49,20 @@ testChunksOfSize = do let res = chunksOfSize n xs in concat res == xs && all (\r -> length r == 1 || length (concat r) <= n) res +testLookupAll :: Action () +testLookupAll = do + putBuild $ "==== lookupAll" + test $ lookupAll ["b" , "c" ] [("a", 1), ("c", 3), ("d", 4)] + == [Nothing, Just (3 :: Int)] + test $ forAll dicts $ \dict -> forAll extras $ \extra -> + let items = sort $ map fst dict ++ extra + in lookupAll items (sort dict) == map (flip lookup dict) items + where + dicts :: Gen [(Int, Int)] + dicts = nubBy ((==) `on` fst) <$> vector 20 + extras :: Gen [Int] + extras = vector 20 + testMatchVersionedFilePath :: Action () testMatchVersionedFilePath = do putBuild $ "==== matchVersionedFilePath" @@ -82,16 +92,15 @@ testModuleName = do where names = intercalate "." <$> listOf1 (listOf1 $ elements "abcABC123_'") -testLookupAll :: Action () -testLookupAll = do - putBuild $ "==== lookupAll" - test $ lookupAll ["b" , "c" ] [("a", 1), ("c", 3), ("d", 4)] - == [Nothing, Just (3 :: Int)] - test $ forAll dicts $ \dict -> forAll extras $ \extra -> - let items = sort $ map fst dict ++ extra - in lookupAll items (sort dict) == map (flip lookup dict) items - where - dicts :: Gen [(Int, Int)] - dicts = nubBy ((==) `on` fst) <$> vector 20 - extras :: Gen [Int] - extras = vector 20 +testPackages :: Action () +testPackages = do + putBuild $ "==== Packages, interpretInContext" + forM_ [Stage0 ..] $ \stage -> do + pkgs <- stagePackages stage + test $ pkgs == nubOrd pkgs + +testWay :: Action () +testWay = do + putBuild $ "==== Read Way, Show Way" + test $ \(x :: Way) -> read (show x) == x + From git at git.haskell.org Fri Oct 27 01:13:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run selftest in GHC tree (f808265) Message-ID: <20171027011321.484053A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f808265388e8356810b450acf72531475b18d340/ghc >--------------------------------------------------------------- commit f808265388e8356810b450acf72531475b18d340 Author: Andrey Mokhov Date: Sun Oct 30 17:46:37 2016 +0000 Run selftest in GHC tree >--------------------------------------------------------------- f808265388e8356810b450acf72531475b18d340 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 7687500..b80008c 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -29,7 +29,7 @@ build_script: - stack build # Run internal Hadrian tests - - stack exec hadrian -- selftest + - stack exec hadrian -- --directory ".." selftest # Build GHC - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- From git at git.haskell.org Fri Oct 27 01:13:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test conditions for building win32 and unix packages (63ba250) Message-ID: <20171027011324.C47BF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/63ba25048c8c4ccf62f96704deb2ebfffefb2040/ghc >--------------------------------------------------------------- commit 63ba25048c8c4ccf62f96704deb2ebfffefb2040 Author: Andrey Mokhov Date: Sun Oct 30 17:58:54 2016 +0000 Test conditions for building win32 and unix packages See #197 >--------------------------------------------------------------- 63ba25048c8c4ccf62f96704deb2ebfffefb2040 src/Rules/Selftest.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 58de8fb..0a63641 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -7,6 +7,8 @@ import Test.QuickCheck import Base import Expression +import GHC +import Oracles.Config.Setting import Oracles.ModuleFiles import Settings import Settings.Builders.Ar @@ -94,9 +96,13 @@ testModuleName = do testPackages :: Action () testPackages = do - putBuild $ "==== Packages, interpretInContext" + putBuild $ "==== Check system configuration" + win <- windowsHost -- This depends on the @boot@ and @configure@ scripts. + putBuild $ "==== Packages, interpretInContext, configuration flags" forM_ [Stage0 ..] $ \stage -> do pkgs <- stagePackages stage + when (win32 `elem` pkgs) . test $ win + when (unix `elem` pkgs) . test $ not win test $ pkgs == nubOrd pkgs testWay :: Action () From git at git.haskell.org Fri Oct 27 01:13:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't build ghcPkg in Stage1 (bf83d95) Message-ID: <20171027011331.C56A93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bf83d95c4770330e0b5ec582448ddc70ec9ebc92/ghc >--------------------------------------------------------------- commit bf83d95c4770330e0b5ec582448ddc70ec9ebc92 Author: Andrey Mokhov Date: Sun Oct 30 23:34:46 2016 +0000 Don't build ghcPkg in Stage1 >--------------------------------------------------------------- bf83d95c4770330e0b5ec582448ddc70ec9ebc92 src/Settings/Default.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index b59ceeb..c863a9e 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -101,7 +101,6 @@ stage1Packages = do , ghc , ghcCabal , ghci - , ghcPkg , ghcPrim , haskeline , hpcBin From git at git.haskell.org Fri Oct 27 01:13:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor programPath (5d12adf) Message-ID: <20171027011335.47DC93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5d12adf142c16b5214fc01c8a1fab16c81544c89/ghc >--------------------------------------------------------------- commit 5d12adf142c16b5214fc01c8a1fab16c81544c89 Author: Andrey Mokhov Date: Sun Oct 30 23:37:10 2016 +0000 Refactor programPath >--------------------------------------------------------------- 5d12adf142c16b5214fc01c8a1fab16c81544c89 src/GHC.hs | 16 +++++++++-- src/Rules.hs | 8 +----- src/Rules/Generators/ConfigHs.hs | 1 - src/Rules/Generators/GhcSplit.hs | 2 +- src/Rules/Program.hs | 37 +++++++++++++----------- src/Rules/Test.hs | 1 - src/Settings.hs | 42 ++++++++++++++++++++++----- src/Settings/Path.hs | 61 ++++++---------------------------------- src/Util.hs | 1 - 9 files changed, 79 insertions(+), 90 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 5d12adf142c16b5214fc01c8a1fab16c81544c89 From git at git.haskell.org Fri Oct 27 01:13:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify needTouchy, drop old comments (47a1e7d) Message-ID: <20171027011328.4E1B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/47a1e7db3a6c815925389f1c7a7a69fd66ab1bea/ghc >--------------------------------------------------------------- commit 47a1e7db3a6c815925389f1c7a7a69fd66ab1bea Author: Andrey Mokhov Date: Sun Oct 30 23:33:07 2016 +0000 Simplify needTouchy, drop old comments >--------------------------------------------------------------- 47a1e7db3a6c815925389f1c7a7a69fd66ab1bea src/Settings/Builders/Ghc.hs | 97 ++------------------------------------------ 1 file changed, 3 insertions(+), 94 deletions(-) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 64fbacb..e12e35c 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -3,11 +3,6 @@ module Settings.Builders.Ghc (ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs) wh import Flavour import Settings.Builders.Common --- TODO: Add support for -dyno. --- $1/$2/build/%.$$($3_o-bootsuf) : $1/$4/%.hs-boot --- $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@ --- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno --- $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@))) ghcBuilderArgs :: Args ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do needTouchy @@ -38,15 +33,11 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] --- TODO: Add Touchy builder and use needBuilder. needTouchy :: ReaderT Target Action () -needTouchy = do - stage <- getStage - windows <- lift $ windowsHost - lift . when (stage > Stage0 && windows) $ - need [fromJust $ programPath (vanillaContext Stage0 touchy)] +needTouchy = notStage0 ? do + maybePath <- lift $ programPath (vanillaContext Stage0 touchy) + lift . whenJust maybePath $ \path -> need [path] --- TODO: Add GhcSplit builder and use needBuilder. splitObjectsArgs :: Args splitObjectsArgs = splitObjects flavour ? do lift $ need [ghcSplit] @@ -99,7 +90,6 @@ wayGhcArgs = do , (way == debug || way == debugDynamic) ? append ["-ticky", "-DTICKY_TICKY"] ] --- TODO: Improve handling of "-hide-all-packages". packageGhcArgs :: Args packageGhcArgs = do pkg <- getPackage @@ -131,84 +121,3 @@ includeGhcArgs = do , arg $ "-optc-I" ++ generatedPath , arg "-optP-include" , arg $ "-optP" ++ path -/- "autogen/cabal_macros.h" ] - --- # Options for passing to plain ld --- $1_$2_$3_ALL_LD_OPTS = \ --- $$(WAY_$3_LD_OPTS) \ --- $$($1_$2_DIST_LD_OPTS) \ --- $$($1_$2_$3_LD_OPTS) \ --- $$($1_$2_EXTRA_LD_OPTS) \ --- $$(EXTRA_LD_OPTS) - --- # Options for passing to GHC when we use it for linking --- $1_$2_$3_GHC_LD_OPTS = \ --- $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ --- $$($1_$2_$3_MOST_HC_OPTS) - --- TODO: add support for TargetElf and darwin --- ifeq "$3" "dyn" --- ifneq "$4" "0" --- ifeq "$$(TargetElf)" "YES" --- $1_$2_$3_GHC_LD_OPTS += \ --- -fno-use-rpaths \ --- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'$$$$ORIGIN/../$$d') -optl-Wl,-zorigin --- else ifeq "$$(TargetOS_CPP)" "darwin" --- $1_$2_$3_GHC_LD_OPTS += \ --- -fno-use-rpaths \ --- $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') - --- ifeq "$$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS)" "" --- # We don't want to link the GHC RTS into C-only programs. There's no --- # point, and it confuses the test that all GHC-compiled programs --- # were compiled with the right GHC. --- $1_$2_$$($1_$2_PROGRAM_WAY)_GHC_LD_OPTS += -no-auto-link-packages -no-hs-main --- endif - --- # Link a dynamic library --- # On windows we have to supply the extra libs this one links to when building it. --- ifeq "$$(HostOS_CPP)" "mingw32" --- $$($1_$2_$3_LIB) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) --- ifneq "$$($1_$2_$3_LIB0)" "" --- $$(call build-dll,$1,$2,$3, --- -L$1/$2/build -l$$($1_$2_$3_LIB0_ROOT), --- $$(filter-out $$($1_$2_dll0_HS_OBJS),$$($1_$2_$3_HS_OBJS)) --- $$($1_$2_$3_NON_HS_OBJS),$$@) --- else --- $$(call build-dll,$1,$2,$3,,$$($1_$2_$3_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$@) --- endif - --- ifneq "$$($1_$2_$3_LIB0)" "" --- $$($1_$2_$3_LIB) : $$($1_$2_$3_LIB0) --- $$($1_$2_$3_LIB0) : $$($1_$2_$3_ALL_OBJS) $$(ALL_RTS_LIBS) $$($1_$2_$3_DEPS_LIBS) --- $$(call build-dll,$1,$2,$3,,$$($1_$2_dll0_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS),$$($1_$2_$3_LIB0)) --- endif - - - --- # $1 = dir --- # $2 = distdir --- # $3 = way --- # $4 = extra flags --- # $5 = object files to link --- # $6 = output filename --- define build-dll --- $(call cmd,$1_$2_HC) $($1_$2_$3_ALL_HC_OPTS) $($1_$2_$3_GHC_LD_OPTS) $4 $5 \ --- -shared -dynamic -dynload deploy \ --- $(addprefix -l,$($1_$2_EXTRA_LIBRARIES)) \ --- -no-auto-link-packages \ --- -o $6 --- # Now check that the DLL doesn't have too many symbols. See trac #5987. --- SYMBOLS=`$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail -n +2 | wc -l`; echo "Number of symbols in $6: $$SYMBOLS" --- case `$(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | grep "\[ *0\]" | wc -l` in 1) echo DLL $6 OK;; 0) echo No symbols in DLL $6; exit 1;; [0-9]*) echo Too many symbols in DLL $6; $(OBJDUMP) -p $6 | sed -n "1,/^.Ordinal\/Name Pointer/ D; p; /^$$/ q" | tail; exit 1;; *) echo bad DLL $6; exit 1;; esac --- endef - - - --- TODO: add -dynamic-too? --- # $1_$2_$3_ALL_HC_OPTS: this is all the options we will pass to GHC --- # for a given ($1,$2,$3). --- $1_$2_$3_ALL_HC_OPTS = \ --- -hisuf $$($3_hisuf) -osuf $$($3_osuf) -hcsuf $$($3_hcsuf) \ --- $$($1_$2_$3_MOST_DIR_HC_OPTS) \ --- $$(if $$(findstring YES,$$($1_$2_SplitObjs)),$$(if $$(findstring dyn,$3),,-split-objs),) \ --- $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),$$(if $$(findstring v,$3),-dynamic-too)) From git at git.haskell.org Fri Oct 27 01:13:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix buildProgram (7b00fa7) Message-ID: <20171027011342.411D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7b00fa7081555a5753c90ba8b48d2579cc59be9c/ghc >--------------------------------------------------------------- commit 7b00fa7081555a5753c90ba8b48d2579cc59be9c Author: Andrey Mokhov Date: Sun Oct 30 23:57:13 2016 +0000 Fix buildProgram >--------------------------------------------------------------- 7b00fa7081555a5753c90ba8b48d2579cc59be9c src/Rules/Program.hs | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 98922a5..319ca72 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -29,15 +29,23 @@ wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper ) buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do + let installStage = do + latest <- latestBuildStage package -- isJust below is safe + return $ if package == ghc then stage else fromJust latest + buildPath context -/- programName context <.> exe %> buildBinaryAndWrapper rs context -- Rules for programs built in install directories - when (stage == Stage0 || package == ghc) $ - installPath package -/- programName context <.> exe %> \bin -> do - latest <- latestBuildStage package -- isJust below is safe - let binStage = if package == ghc then stage else fromJust latest + when (stage == Stage0 || package == ghc) $ do + -- Some binaries in programInplacePath are wrapped + programInplacePath -/- programName context <.> exe %> \bin -> do + binStage <- installStage buildBinaryAndWrapper rs (context { stage = binStage }) bin + -- We build only unwrapped binaries in programInplaceLibPath + programInplaceLibPath -/- programName context <.> exe %> \bin -> do + binStage <- installStage + buildBinary rs (context { stage = binStage }) bin buildBinaryAndWrapper :: [(Resource, Int)] -> Context -> FilePath -> Action () buildBinaryAndWrapper rs context bin = do From git at git.haskell.org Fri Oct 27 01:13:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move programInplacePath to Settings.Path (c5ba8b9) Message-ID: <20171027011338.BA23D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c5ba8b94b6e04cf95392f8520ff649d2538530a2/ghc >--------------------------------------------------------------- commit c5ba8b94b6e04cf95392f8520ff649d2538530a2 Author: Andrey Mokhov Date: Sun Oct 30 23:45:21 2016 +0000 Move programInplacePath to Settings.Path >--------------------------------------------------------------- c5ba8b94b6e04cf95392f8520ff649d2538530a2 src/Base.hs | 6 +----- src/Settings/Path.hs | 8 ++++++-- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index cb040d4..eb8685d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -15,7 +15,7 @@ module Base ( module Development.Shake.FilePath, -- * Paths - configPath, configFile, sourcePath, programInplacePath, + configPath, configFile, sourcePath, -- * Miscellaneous utilities minusOrd, intersectOrd, lookupAll, replaceEq, replaceSeparators, unifyPath, @@ -58,10 +58,6 @@ configFile = configPath -/- "system.config" sourcePath :: FilePath sourcePath = hadrianPath -/- "src" --- TODO: move to buildRootPath, see #113 -programInplacePath :: FilePath -programInplacePath = "inplace/bin" - -- | Find and replace all occurrences of a value in a list. replaceEq :: Eq a => a -> a -> [a] -> [a] replaceEq from = replaceWhen (== from) diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 9993f9e..6b2e67d 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -3,7 +3,7 @@ module Settings.Path ( pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, - objectPath, programInplaceLibPath, installPath + objectPath, programInplacePath, programInplaceLibPath, installPath ) where import Base @@ -36,7 +36,11 @@ stageDirectory :: Stage -> FilePath stageDirectory = stageString -- TODO: Move to buildRootPath, see #113. --- | Directory for wrapped binaries. +-- | Directory for binaries that are built "in place". +programInplacePath :: FilePath +programInplacePath = "inplace/bin" + +-- | Directory for binary wrappers, and auxiliary binaries such as @touchy at . programInplaceLibPath :: FilePath programInplaceLibPath = "inplace/lib/bin" From git at git.haskell.org Fri Oct 27 01:13:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (d9b059b) Message-ID: <20171027011345.D79903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d9b059b3471b2a897b4b0fe8370a6340011310b6/ghc >--------------------------------------------------------------- commit d9b059b3471b2a897b4b0fe8370a6340011310b6 Author: Andrey Mokhov Date: Mon Oct 31 18:25:18 2016 +0000 Minor revision >--------------------------------------------------------------- d9b059b3471b2a897b4b0fe8370a6340011310b6 hadrian.cabal | 2 +- .../{DirectoryContent.hs => DirectoryContents.hs} | 19 +++++++++-------- src/Rules/Oracles.hs | 4 ++-- src/Rules/SourceDist.hs | 4 ++-- src/Util.hs | 24 ++++++++++------------ 5 files changed, 26 insertions(+), 27 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index b20b17d..0663643 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -31,7 +31,7 @@ executable hadrian , Oracles.Config.Flag , Oracles.Config.Setting , Oracles.Dependencies - , Oracles.DirectoryContent + , Oracles.DirectoryContents , Oracles.ModuleFiles , Oracles.PackageData , Oracles.Path diff --git a/src/Oracles/DirectoryContent.hs b/src/Oracles/DirectoryContents.hs similarity index 53% rename from src/Oracles/DirectoryContent.hs rename to src/Oracles/DirectoryContents.hs index 3139c6c..6dd3439 100644 --- a/src/Oracles/DirectoryContent.hs +++ b/src/Oracles/DirectoryContents.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric #-} -module Oracles.DirectoryContent ( - directoryContent, directoryContentOracle, Match (..) +module Oracles.DirectoryContents ( + directoryContents, directoryContentsOracle, Match (..) ) where import System.Directory.Extra @@ -8,7 +8,7 @@ import GHC.Generics import Base -newtype DirectoryContent = DirectoryContent (Match, FilePath) +newtype DirectoryContents = DirectoryContents (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) data Match = Test FilePattern | Not Match | And [Match] | Or [Match] @@ -20,13 +20,14 @@ matches (Not m) f = not $ matches m f matches (And ms) f = all (`matches` f) ms matches (Or ms) f = any (`matches` f) ms --- | Get the directory content recursively. -directoryContent :: Match -> FilePath -> Action [FilePath] -directoryContent expr dir = askOracle $ DirectoryContent (expr, dir) +-- | Given a 'Match' expression and a directory, recursively traverse it and all +-- its subdirectories to find and return all matching contents. +directoryContents :: Match -> FilePath -> Action [FilePath] +directoryContents expr dir = askOracle $ DirectoryContents (expr, dir) -directoryContentOracle :: Rules () -directoryContentOracle = void $ - addOracle $ \(DirectoryContent (expr, dir)) -> liftIO $ +directoryContentsOracle :: Rules () +directoryContentsOracle = void $ + addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ filter (matches expr) <$> listFilesInside (return . matches expr) dir instance Binary Match diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs index 6c5ace4..8f53369 100644 --- a/src/Rules/Oracles.hs +++ b/src/Rules/Oracles.hs @@ -4,7 +4,7 @@ import Base import qualified Oracles.ArgsHash import qualified Oracles.Config import qualified Oracles.Dependencies -import qualified Oracles.DirectoryContent +import qualified Oracles.DirectoryContents import qualified Oracles.ModuleFiles import qualified Oracles.PackageData import qualified Oracles.Path @@ -14,7 +14,7 @@ oracleRules = do Oracles.ArgsHash.argsHashOracle Oracles.Config.configOracle Oracles.Dependencies.dependenciesOracles - Oracles.DirectoryContent.directoryContentOracle + Oracles.DirectoryContents.directoryContentsOracle Oracles.ModuleFiles.moduleFilesOracle Oracles.PackageData.packageDataOracle Oracles.Path.pathOracle diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index 9c49878..d51fe75 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -3,7 +3,7 @@ module Rules.SourceDist (sourceDistRules) where import Base import Builder import Oracles.Config.Setting -import Oracles.DirectoryContent +import Oracles.DirectoryContents import UserSettings import Util @@ -32,7 +32,7 @@ prepareTree dest = do mapM_ cpFile srcFiles where cpFile a = copyFile a (dest a) - cpDir a = copyDirectoryContent (Not excluded) a (dest takeFileName a) + cpDir a = copyDirectoryContents (Not excluded) a (dest takeFileName a) excluded = Or [ Test "//.*" , Test "//#*" diff --git a/src/Util.hs b/src/Util.hs index dbafd85..f2e6516 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -1,6 +1,6 @@ module Util ( build, buildWithCmdOptions, buildWithResources, copyFile, fixFile, moveFile, - removeFile, copyDirectory, copyDirectoryContent, createDirectory, + removeFile, copyDirectory, copyDirectoryContents, createDirectory, moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith, makeExecutable, renderProgram, renderLibrary, Match(..), builderEnvironment, needBuilder @@ -16,7 +16,7 @@ import Context import Expression import GHC import Oracles.ArgsHash -import Oracles.DirectoryContent +import Oracles.DirectoryContents import Oracles.Path import Settings import Settings.Builders.Ar @@ -96,6 +96,8 @@ captureStdout target path argList = do copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. + let dir = takeDirectory target + unlessM (liftIO $ IO.doesDirectoryExist dir) $ createDirectory dir putProgressInfo $ renderAction "Copy file" source target copyFileChanged source target @@ -129,17 +131,13 @@ copyDirectory source target = do putProgressInfo $ renderAction "Copy directory" source target quietly $ cmd cmdEcho ["cp", "-r", source, target] --- | Copy the content of the source directory into the target directory. --- The copied content is tracked. -copyDirectoryContent :: Match -> FilePath -> FilePath -> Action () -copyDirectoryContent expr source target = do - putProgressInfo $ renderAction "Copy directory content" source target - mapM_ cp =<< directoryContent expr source - where - cp file = do - let newFile = target -/- drop (length source) file - createDirectory $ dropFileName newFile -- TODO: Why do it for each file? - copyFile file newFile +-- | Copy the contents of the source directory that matches a given 'Match' +-- expression into the target directory. The copied contents is tracked. +copyDirectoryContents :: Match -> FilePath -> FilePath -> Action () +copyDirectoryContents expr source target = do + putProgressInfo $ renderAction "Copy directory contents" source target + let cp file = copyFile file $ target -/- makeRelative source file + mapM_ cp =<< directoryContents expr source -- | Move a directory. The contents of the source directory is untracked. moveDirectory :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 01:13:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix path separators (8be3f76) Message-ID: <20171027011349.4A4313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8be3f76d78e9806bdbef6a2d2db7bbf341aba0ea/ghc >--------------------------------------------------------------- commit 8be3f76d78e9806bdbef6a2d2db7bbf341aba0ea Author: Andrey Mokhov Date: Mon Oct 31 19:19:19 2016 +0000 Fix path separators >--------------------------------------------------------------- 8be3f76d78e9806bdbef6a2d2db7bbf341aba0ea src/Oracles/DirectoryContents.hs | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/SourceDist.hs | 9 ++++----- 3 files changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Oracles/DirectoryContents.hs b/src/Oracles/DirectoryContents.hs index 6dd3439..d854c7d 100644 --- a/src/Oracles/DirectoryContents.hs +++ b/src/Oracles/DirectoryContents.hs @@ -27,7 +27,7 @@ directoryContents expr dir = askOracle $ DirectoryContents (expr, dir) directoryContentsOracle :: Rules () directoryContentsOracle = void $ - addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ + addOracle $ \(DirectoryContents (expr, dir)) -> liftIO $ map unifyPath . filter (matches expr) <$> listFilesInside (return . matches expr) dir instance Binary Match diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index 64f8ea9..2d3eb4a 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -14,7 +14,7 @@ import Util compilePackage :: [(Resource, Int)] -> Context -> Rules () compilePackage rs context at Context {..} = do let path = buildPath context - nonHs extension = path extension "*" <.> osuf way + nonHs extension = path -/- extension "*" <.> osuf way compile compiler obj2src obj = do let src = obj2src context obj need [src] diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index d51fe75..d56eb38 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -15,9 +15,9 @@ sourceDistRules = do putSuccess "| Done. " "sdistprep/ghc-*-src.tar.xz" %> \fname -> do let tarName = takeFileName fname - treePath = "sdistprep/ghc" dropTarXz tarName + treePath = "sdistprep/ghc" -/- dropTarXz tarName prepareTree treePath - runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." tarName, dropTarXz tarName] + runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." -/- tarName, dropTarXz tarName] "GIT_COMMIT_ID" %> \fname -> setting ProjectGitCommitId >>= writeFileChanged fname "VERSION" %> \fname -> @@ -25,14 +25,13 @@ sourceDistRules = do where dropTarXz = dropExtension . dropExtension - prepareTree :: FilePath -> Action () prepareTree dest = do mapM_ cpDir srcDirs mapM_ cpFile srcFiles where - cpFile a = copyFile a (dest a) - cpDir a = copyDirectoryContents (Not excluded) a (dest takeFileName a) + cpFile a = copyFile a (dest -/- a) + cpDir a = copyDirectoryContents (Not excluded) a (dest -/- takeFileName a) excluded = Or [ Test "//.*" , Test "//#*" From git at git.haskell.org Fri Oct 27 01:13:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant createDirectory calls (7041682) Message-ID: <20171027011352.BD1203A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7041682e77204d718def64aee7d0c768ffd685bd/ghc >--------------------------------------------------------------- commit 7041682e77204d718def64aee7d0c768ffd685bd Author: Andrey Mokhov Date: Mon Oct 31 19:50:36 2016 +0000 Drop redundant createDirectory calls >--------------------------------------------------------------- 7041682e77204d718def64aee7d0c768ffd685bd src/Rules/Data.hs | 1 - src/Rules/Gmp.hs | 2 -- src/Rules/Libffi.hs | 1 - src/Util.hs | 2 +- 4 files changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 65c6392..ab8ac97 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -47,7 +47,6 @@ buildPackageData context at Context {..} = do | otherwise = oldPath -/- "build" -/- pkgNameString package copyFile inTreeMk mk autogenFiles <- getDirectoryFiles oldBuild ["autogen/*"] - createDirectory $ buildPath context -/- "autogen" forM_ autogenFiles $ \file' -> do let file = unifyPath file' copyFile (oldBuild -/- file) (buildPath context -/- file) diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 1024533..2409b6e 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -44,14 +44,12 @@ gmpRules = do any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ] then do putBuild "| GMP library/framework detected and will be used" - createDirectory $ takeDirectory header copyFile (gmpBase -/- "ghc-gmp.h") header else do putBuild "| No GMP library/framework detected; in tree GMP will be built" need [gmpLibrary] createDirectory gmpObjects build $ Target gmpContext Ar [gmpLibrary] [gmpObjects] - createDirectory $ takeDirectory header copyFile (gmpBuildPath -/- "gmp.h") header copyFile (gmpBuildPath -/- "gmp.h") gmpLibraryInTreeH diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index ae1c06f..8d72017 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -70,7 +70,6 @@ libffiRules = do libffiMakefile <.> "in" %> \mkIn -> do removeDirectory libffiBuildPath - createDirectory $ buildRootPath -/- stageString Stage0 tarball <- unifyPath . getSingleton "Exactly one LibFFI tarball is expected" <$> getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] diff --git a/src/Util.hs b/src/Util.hs index f2e6516..81f67dd 100644 --- a/src/Util.hs +++ b/src/Util.hs @@ -92,7 +92,7 @@ captureStdout target path argList = do Stdout output <- cmd [path] argList writeFileChanged file output --- | Copy a file tracking the source. +-- | Copy a file tracking the source, create the target directory if missing. copyFile :: FilePath -> FilePath -> Action () copyFile source target = do need [source] -- Guarantee source is built before printing progress info. From git at git.haskell.org Fri Oct 27 01:13:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify, remove old hacks (4fd513a) Message-ID: <20171027011356.388CD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fd513a325e1689e971f72941975ee20912bd647/ghc >--------------------------------------------------------------- commit 4fd513a325e1689e971f72941975ee20912bd647 Author: Andrey Mokhov Date: Mon Oct 31 23:52:34 2016 +0000 Simplify, remove old hacks >--------------------------------------------------------------- 4fd513a325e1689e971f72941975ee20912bd647 src/Rules/Generate.hs | 39 +++++++++++++-------------------------- 1 file changed, 13 insertions(+), 26 deletions(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 0141f29..d13d2bb 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -3,8 +3,6 @@ module Rules.Generate ( installTargets, copyRules, includesDependencies, generatedDependencies ) where -import qualified System.Directory as IO - import Base import Context hiding (package) import Expression @@ -110,21 +108,27 @@ generatePackageCode :: Context -> Rules () generatePackageCode context@(Context stage pkg _) = let path = buildPath context generated f = (path ++ "//*.hs") ?== f && not ("//autogen/*" ?== f) - file <~ gen = generate file context gen + go gen file = generate file context gen in do generated ?> \file -> do let unpack = fromMaybe . error $ "No generator for " ++ file ++ "." (src, builder) <- unpack <$> findGenerator context file need [src] build $ Target context builder [src] [file] - let srcBoot = src -<.> "hs-boot" - whenM (doesFileExist srcBoot) $ - copyFile srcBoot $ file -<.> "hs-boot" + let boot = src -<.> "hs-boot" + whenM (doesFileExist boot) . copyFile boot $ file -<.> "hs-boot" + + priority 2.0 $ do + when (pkg == compiler) $ path -/- "Config.hs" %> go generateConfigHs + when (pkg == ghcPkg) $ path -/- "Version.hs" %> go generateVersionHs -- TODO: needing platformH is ugly and fragile - when (pkg == compiler) $ primopsTxt stage %> \file -> do - need $ [platformH stage, primopsSource] ++ includesDependencies - build $ Target context HsCpp [primopsSource] [file] + when (pkg == compiler) $ do + primopsTxt stage %> \file -> do + need $ [platformH stage, primopsSource] ++ includesDependencies + build $ Target context HsCpp [primopsSource] [file] + + platformH stage %> go generateGhcBootPlatformH -- TODO: why different folders for generated files? fmap (path -/-) @@ -133,26 +137,10 @@ generatePackageCode context@(Context stage pkg _) = , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] build $ Target context GenPrimopCode [primopsTxt stage] [file] - -- TODO: this is temporary hack, get rid of this (#113) - let oldPath = pkgPath pkg -/- stageDirectory stage -/- "build" - newFile = oldPath ++ (drop (length path) file) - createDirectory $ takeDirectory newFile - liftIO $ IO.copyFile file newFile - putBuild $ "| Duplicate file " ++ file ++ " -> " ++ newFile when (pkg == rts) $ path -/- "cmm/AutoApply.cmm" %> \file -> build $ Target context GenApply [] [file] - priority 2.0 $ do - when (pkg == compiler) $ path -/- "Config.hs" %> \file -> do - file <~ generateConfigHs - - when (pkg == compiler) $ platformH stage %> \file -> do - file <~ generateGhcBootPlatformH - - when (pkg == ghcPkg) $ path -/- "Version.hs" %> \file -> do - file <~ generateVersionHs - copyRules :: Rules () copyRules = do "inplace/lib/ghc-usage.txt" <~ "driver" @@ -179,7 +167,6 @@ generateRules = do generatedPath ++ "//*" %> \file -> do withTempDir $ \dir -> build $ Target rtsContext DeriveConstants [] [file, dir] - where file <~ gen = file %> \out -> generate out emptyTarget gen From git at git.haskell.org Fri Oct 27 01:13:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:13:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependencies on generated files (010dd78) Message-ID: <20171027011359.B00703A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/010dd78b1e574c648f9a93d2a636ff9ae05422ff/ghc >--------------------------------------------------------------- commit 010dd78b1e574c648f9a93d2a636ff9ae05422ff Author: Andrey Mokhov Date: Mon Oct 31 23:55:27 2016 +0000 Add missing dependencies on generated files See #285. >--------------------------------------------------------------- 010dd78b1e574c648f9a93d2a636ff9ae05422ff src/Rules/Dependencies.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs index 04c4f1f..192e24c 100644 --- a/src/Rules/Dependencies.hs +++ b/src/Rules/Dependencies.hs @@ -6,6 +6,7 @@ import Base import Context import Expression import Oracles.ModuleFiles +import Rules.Generate import Settings.Path import Target import Util @@ -15,6 +16,7 @@ buildPackageDependencies rs context at Context {..} = buildPath context -/- ".dependencies" %> \deps -> do srcs <- hsSources context need srcs + orderOnly =<< interpretInContext context generatedDependencies let mk = deps <.> "mk" if srcs == [] then writeFileChanged mk "" From git at git.haskell.org Fri Oct 27 01:14:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move GHC/Prim.hs outside of autogen directory (eca7b6a) Message-ID: <20171027011403.71C063A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/eca7b6a6d9a17e44854cb8f696cec03140052208/ghc >--------------------------------------------------------------- commit eca7b6a6d9a17e44854cb8f696cec03140052208 Author: Andrey Mokhov Date: Tue Nov 1 19:27:32 2016 +0000 Move GHC/Prim.hs outside of autogen directory >--------------------------------------------------------------- eca7b6a6d9a17e44854cb8f696cec03140052208 src/Oracles/ModuleFiles.hs | 6 +----- src/Rules/Generate.hs | 4 ++-- 2 files changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs index a9bae04..70a7a9f 100644 --- a/src/Oracles/ModuleFiles.hs +++ b/src/Oracles/ModuleFiles.hs @@ -75,11 +75,7 @@ findGenerator Context {..} file = do -- | Find all Haskell source files for a given 'Context'. hsSources :: Context -> Action [FilePath] hsSources context = do - let autogen = buildPath context -/- "autogen" - -- Generated source files live in buildPath and have extension "hs", except - -- for GHC/Prim.hs that lives in autogen. TODO: fix the inconsistency? - modFile ("GHC.Prim", _) = autogen -/- "GHC/Prim.hs" - modFile (m, Nothing ) = generatedFile context m + let modFile (m, Nothing ) = generatedFile context m modFile (m, Just file ) | takeExtension file `elem` haskellExtensions = file | otherwise = generatedFile context m diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index d13d2bb..e84313a 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -55,7 +55,7 @@ ghcPrimDependencies :: Expr [FilePath] ghcPrimDependencies = do stage <- getStage let path = buildPath $ vanillaContext stage ghcPrim - return [path -/- "autogen/GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"] + return [path -/- "GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"] derivedConstantsDependencies :: [FilePath] derivedConstantsDependencies = installTargets ++ fmap (generatedPath -/-) @@ -132,7 +132,7 @@ generatePackageCode context@(Context stage pkg _) = -- TODO: why different folders for generated files? fmap (path -/-) - [ "autogen/GHC/Prim.hs" + [ "GHC/Prim.hs" , "GHC/PrimopWrappers.hs" , "*.hs-incl" ] |%> \file -> do need [primopsTxt stage] From git at git.haskell.org Fri Oct 27 01:14:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build dependencies for all known packages that exist (95ee1ab) Message-ID: <20171027011407.02AD13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95ee1ab41659c3e6f4d64455faed96aebaeb0cbf/ghc >--------------------------------------------------------------- commit 95ee1ab41659c3e6f4d64455faed96aebaeb0cbf Author: Andrey Mokhov Date: Tue Nov 1 21:30:15 2016 +0000 Build dependencies for all known packages that exist >--------------------------------------------------------------- 95ee1ab41659c3e6f4d64455faed96aebaeb0cbf src/Rules/Cabal.hs | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index b2bd630..370bda2 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -11,6 +11,7 @@ import Expression import GHC import Settings import Settings.Path +import UserSettings cabalRules :: Rules () cabalRules = do @@ -25,13 +26,13 @@ cabalRules = do version = display . pkgVersion $ identifier return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version writeFileChanged out . unlines $ constraints + putSuccess $ "| Successfully computed boot package constraints" -- Cache package dependencies. packageDependencies %> \out -> do - pkgs <- concatMapM stagePackages [Stage0 .. Stage2] - pkgDeps <- forM (sort pkgs) $ \pkg -> - if pkg `elem` [hp2ps, libffi, rts, touchy, unlit] - then return $ pkgNameString pkg + pkgDeps <- forM (sort knownPackages) $ \pkg -> do + exists <- doesFileExist $ pkgCabalFile pkg + if not exists then return $ pkgNameString pkg else do need [pkgCabalFile pkg] pd <- liftIO . readPackageDescription silent $ pkgCabalFile pkg @@ -40,7 +41,8 @@ cabalRules = do deps = concat $ depsLib : depsExes depNames = [ unPackageName name | Dependency name _ <- deps ] return . unwords $ pkgNameString pkg : sort depNames - writeFileChanged out . unlines $ pkgDeps + writeFileChanged out $ unlines pkgDeps + putSuccess $ "| Successfully computed package dependencies" collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] From git at git.haskell.org Fri Oct 27 01:14:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision, don't copy Hadrian binaries (6d420eb) Message-ID: <20171027011410.7214C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d420eb40cf4ebe18c4b556b0449972b6500eeb2/ghc >--------------------------------------------------------------- commit 6d420eb40cf4ebe18c4b556b0449972b6500eeb2 Author: Andrey Mokhov Date: Wed Nov 2 01:55:16 2016 +0000 Minor revision, don't copy Hadrian binaries >--------------------------------------------------------------- 6d420eb40cf4ebe18c4b556b0449972b6500eeb2 src/Rules/SourceDist.hs | 156 +++++++++++++++++++++++++----------------------- 1 file changed, 80 insertions(+), 76 deletions(-) diff --git a/src/Rules/SourceDist.hs b/src/Rules/SourceDist.hs index d56eb38..7a60238 100644 --- a/src/Rules/SourceDist.hs +++ b/src/Rules/SourceDist.hs @@ -12,18 +12,18 @@ sourceDistRules = do "sdist-ghc" ~> do version <- setting ProjectVersion need ["sdistprep/ghc-" ++ version ++ "-src.tar.xz"] - putSuccess "| Done. " + putSuccess "| Done" "sdistprep/ghc-*-src.tar.xz" %> \fname -> do - let tarName = takeFileName fname - treePath = "sdistprep/ghc" -/- dropTarXz tarName + let tarName = takeFileName fname + dropTarXz = dropExtension . dropExtension + treePath = "sdistprep/ghc" -/- dropTarXz tarName prepareTree treePath - runBuilderWith [Cwd "sdistprep/ghc"] Tar ["cJf", ".." -/- tarName, dropTarXz tarName] + runBuilderWith [Cwd "sdistprep/ghc"] Tar + ["cJf", ".." -/- tarName, dropTarXz tarName] "GIT_COMMIT_ID" %> \fname -> - setting ProjectGitCommitId >>= writeFileChanged fname + writeFileChanged fname =<< setting ProjectGitCommitId "VERSION" %> \fname -> - setting ProjectVersion >>= writeFileChanged fname - where - dropTarXz = dropExtension . dropExtension + writeFileChanged fname =<< setting ProjectVersion prepareTree :: FilePath -> Action () prepareTree dest = do @@ -31,74 +31,78 @@ prepareTree dest = do mapM_ cpFile srcFiles where cpFile a = copyFile a (dest -/- a) - cpDir a = copyDirectoryContents (Not excluded) a (dest -/- takeFileName a) + cpDir a = copyDirectoryContents (Not excluded) a (dest -/- a) excluded = Or - [ Test "//.*" - , Test "//#*" - , Test "//*-SAVE" - , Test "//*.orig" - , Test "//*.rej" - , Test "//*~" - , Test "//autom4te*" - , Test "//dist" - , Test "//log" - , Test "//stage0" - , Test "//stage1" - , Test "//stage2" - , Test "//stage3" - , Test "hadrian/cabal.sandbox.config" - , Test "hadrian/cfg/system.config" - , Test "hadrian/dist" - , Test "hadrian/UserSettings.hs" - , Test "libraries//*.buildinfo" - , Test "libraries//GNUmakefile" - , Test "libraries//config.log" - , Test "libraries//config.status" - , Test "libraries//configure" - , Test "libraries//ghc.mk" - , Test "libraries//include/Hs*Config.h" - , Test "libraries/dph" - , Test "libraries/parallel" - , Test "libraries/primitive" - , Test "libraries/random" - , Test "libraries/stm" - , Test "libraries/vector" - , Test "mk/build.mk" ] + [ Test "//.*" + , Test "//#*" + , Test "//*-SAVE" + , Test "//*.orig" + , Test "//*.rej" + , Test "//*~" + , Test "//autom4te*" + , Test "//dist" + , Test "//log" + , Test "//stage0" + , Test "//stage1" + , Test "//stage2" + , Test "//stage3" + , Test "hadrian/.cabal-sandbox" + , Test "hadrian/.stack-work" + , Test "hadrian/UserSettings.hs" + , Test "hadrian/cabal.sandbox.config" + , Test "hadrian/cfg/system.config" + , Test "hadrian/bin" + , Test "hadrian/dist" + , Test "hadrian/dist-newstyle" + , Test "libraries//*.buildinfo" + , Test "libraries//GNUmakefile" + , Test "libraries//config.log" + , Test "libraries//config.status" + , Test "libraries//configure" + , Test "libraries//ghc.mk" + , Test "libraries//include/Hs*Config.h" + , Test "libraries/dph" + , Test "libraries/parallel" + , Test "libraries/primitive" + , Test "libraries/random" + , Test "libraries/stm" + , Test "libraries/vector" + , Test "mk/build.mk" ] srcDirs = - [ "bindisttest" - , "compiler" - , "distrib" - , "docs" - , "docs" - , "driver" - , "ghc" - , "hadrian" - , "includes" - , "iserv" - , "libffi" - , "libffi-tarballs" - , "libraries" - , "mk" - , "rts" - , "rules" - , "utils" ] + [ "bindisttest" + , "compiler" + , "distrib" + , "docs" + , "docs" + , "driver" + , "ghc" + , "hadrian" + , "includes" + , "iserv" + , "libffi" + , "libffi-tarballs" + , "libraries" + , "mk" + , "rts" + , "rules" + , "utils" ] srcFiles = - [ "ANNOUNCE" - , "GIT_COMMIT_ID" - , "HACKING.md" - , "INSTALL.md" - , "LICENSE" - , "MAKEHELP.md" - , "Makefile" - , "README.md" - , "VERSION" - , "aclocal.m4" - , "boot" - , "config.guess" - , "config.sub" - , "configure" - , "configure.ac" - , "ghc.mk" - , "install-sh" - , "packages" - , "settings.in" ] + [ "ANNOUNCE" + , "GIT_COMMIT_ID" + , "HACKING.md" + , "INSTALL.md" + , "LICENSE" + , "MAKEHELP.md" + , "Makefile" + , "README.md" + , "VERSION" + , "aclocal.m4" + , "boot" + , "config.guess" + , "config.sub" + , "configure" + , "configure.ac" + , "ghc.mk" + , "install-sh" + , "packages" + , "settings.in" ] From git at git.haskell.org Fri Oct 27 01:14:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't generate in-tree directories by ghc-cabal (94c88da) Message-ID: <20171027011414.01A483A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/94c88da1c738815f2986439a956d93fdbc707237/ghc >--------------------------------------------------------------- commit 94c88da1c738815f2986439a956d93fdbc707237 Author: Andrey Mokhov Date: Sat Nov 26 23:38:35 2016 +0000 Don't generate in-tree directories by ghc-cabal See #113 >--------------------------------------------------------------- 94c88da1c738815f2986439a956d93fdbc707237 src/Oracles/ModuleFiles.hs | 5 ++-- src/Oracles/PackageData.hs | 6 ++--- src/Rules/Data.hs | 57 +++++++++------------------------------ src/Rules/Register.hs | 18 +++++-------- src/Settings/Builders/Common.hs | 1 - src/Settings/Builders/Ghc.hs | 5 ++-- src/Settings/Builders/GhcCabal.hs | 4 ++- src/Settings/Builders/GhcPkg.hs | 6 ++--- src/Settings/Builders/Hsc2Hs.hs | 4 +-- src/Settings/Packages/GhcCabal.hs | 6 ++--- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Packages/Touchy.hs | 2 +- src/Settings/Packages/Unlit.hs | 2 +- src/Settings/Path.hs | 18 ++++++++++--- 14 files changed, 56 insertions(+), 80 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 94c88da1c738815f2986439a956d93fdbc707237 From git at git.haskell.org Fri Oct 27 01:14:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant clean up after ghc-cabal (e93f7a4) Message-ID: <20171027011417.8CB453A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e93f7a4181308147b3d2c9211eb6d63e51cea188/ghc >--------------------------------------------------------------- commit e93f7a4181308147b3d2c9211eb6d63e51cea188 Author: Andrey Mokhov Date: Sun Nov 27 00:32:02 2016 +0000 Drop redundant clean up after ghc-cabal See #113 >--------------------------------------------------------------- e93f7a4181308147b3d2c9211eb6d63e51cea188 src/Rules/Clean.hs | 6 ------ 1 file changed, 6 deletions(-) diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs index eebb26d..a2cf849 100644 --- a/src/Rules/Clean.hs +++ b/src/Rules/Clean.hs @@ -1,8 +1,6 @@ module Rules.Clean (cleanRules) where import Base -import Package -import Settings import Settings.Path import Stage import UserSettings @@ -16,10 +14,6 @@ cleanRules = do removeDirectory programInplacePath removeDirectory "inplace/lib" removeDirectory "sdistprep" - putBuild $ "| Remove files generated by ghc-cabal..." - forM_ knownPackages $ \pkg -> - forM_ [Stage0 ..] $ \stage -> - quietly . removeDirectory $ pkgPath pkg -/- stageDirectory stage putBuild $ "| Remove Hadrian files..." removeFilesAfter buildRootPath ["//*"] putSuccess $ "| Done. " From git at git.haskell.org Fri Oct 27 01:14:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Put RTS's package configuration into inplace-pkg-config for consistency (e3b5f08) Message-ID: <20171027011421.5D5153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3b5f08db5ea710b36a696e38f10263c955b86eb/ghc >--------------------------------------------------------------- commit e3b5f08db5ea710b36a696e38f10263c955b86eb Author: Andrey Mokhov Date: Sun Nov 27 01:01:03 2016 +0000 Put RTS's package configuration into inplace-pkg-config for consistency >--------------------------------------------------------------- e3b5f08db5ea710b36a696e38f10263c955b86eb src/Rules/Register.hs | 4 ++-- src/Settings/Builders/GhcPkg.hs | 3 +-- src/Settings/Packages/Rts.hs | 6 +----- src/Settings/Path.hs | 6 +++++- 4 files changed, 9 insertions(+), 10 deletions(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index f912b20..b7e12d1 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -22,10 +22,10 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do -- This produces inplace-pkg-config. TODO: Add explicit tracking. need [pkgDataFile context] - -- Post-process inplace-pkg-config. TODO: remove, see #113, #148. + -- Post-process inplace-pkg-config. top <- topDirectory let path = buildPath context - pkgConfig = path -/- "inplace-pkg-config" + pkgConfig = inplacePkgConfig context oldPath = top -/- path "build" fixFile pkgConfig $ unlines . map (replace oldPath path) . lines diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index b17f36a..5156d71 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -13,10 +13,9 @@ initArgs = initPredicate ? mconcat [ arg "init", arg =<< getOutput ] updateArgs :: Args updateArgs = notM initPredicate ? do - path <- getBuildPath verbosity <- lift $ getVerbosity mconcat [ arg "update" , arg "--force" , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs - , arg $ path -/- "inplace-pkg-config" ] + , arg . inplacePkgConfig =<< getContext ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 4c3cc99..40b85e4 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -18,7 +18,7 @@ rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" rtsConf :: FilePath -rtsConf = buildPath rtsContext -/- "package.conf.inplace" +rtsConf = inplacePkgConfig rtsContext rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do @@ -96,10 +96,6 @@ rtsPackageArgs = package rts ? do , builder Ghc ? arg "-Irts" - , builder (GhcPkg Stage1) ? mconcat - [ remove [path -/- "inplace-pkg-config"] - , arg rtsConf ] - , builder HsCpp ? append [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 0a22077..cbe1612 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -4,7 +4,7 @@ module Settings.Path ( gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath + installPath, autogenPath, inplacePkgConfig ) where import Base @@ -60,6 +60,10 @@ autogenPath context at Context {..} where autogen dir = buildPath context -/- dir -/- "autogen" +-- | Path to inplace package configuration of a given 'Context'. +inplacePkgConfig :: Context -> FilePath +inplacePkgConfig context = buildPath context -/- "inplace-pkg-config" + -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath pkgDataFile context = buildPath context -/- "package-data.mk" From git at git.haskell.org Fri Oct 27 01:14:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor Data and Register build rules (7ebb204) Message-ID: <20171027011424.DA54C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7ebb2045222d9c800d523ed93e32680d8b07fc10/ghc >--------------------------------------------------------------- commit 7ebb2045222d9c800d523ed93e32680d8b07fc10 Author: Andrey Mokhov Date: Sun Nov 27 01:48:25 2016 +0000 Refactor Data and Register build rules >--------------------------------------------------------------- 7ebb2045222d9c800d523ed93e32680d8b07fc10 src/Rules/Data.hs | 21 ++++++++++++++++++++- src/Rules/Register.hs | 39 ++++----------------------------------- src/Settings/Builders/GhcPkg.hs | 2 +- src/Settings/Packages/Rts.hs | 2 +- src/Settings/Path.hs | 6 +++--- 5 files changed, 29 insertions(+), 41 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index e16f03b..1314cc4 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -9,6 +9,7 @@ import Oracles.Dependencies import Oracles.Path import Rules.Generate import Rules.Libffi +import Settings.Packages.Rts import Settings.Path import Target import UserSettings @@ -17,7 +18,8 @@ import Util -- | Build @package-data.mk@ by using ghc-cabal utility to process .cabal files. buildPackageData :: Context -> Rules () buildPackageData context at Context {..} = do - let cabalFile = pkgCabalFile package + let path = buildPath context + cabalFile = pkgCabalFile package configure = pkgPath package -/- "configure" dataFile = pkgDataFile context @@ -35,6 +37,23 @@ buildPackageData context at Context {..} = do build $ Target context GhcCabal [cabalFile] [mk] postProcessPackageData context mk + pkgInplaceConfig context %> \conf -> do + need [dataFile] -- ghc-cabal builds inplace package configuration file + if package == rts + then do + need [rtsConfIn] + build $ Target context HsCpp [rtsConfIn] [conf] + fixFile conf $ unlines + . map + ( replace "\"\"" "" + . replace "rts/dist/build" rtsBuildPath + . replace "includes/dist-derivedconstants/header" generatedPath ) + . lines + else do + top <- topDirectory + let oldPath = top -/- path "build" + fixFile conf $ unlines . map (replace oldPath path) . lines + -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps. priority 2.0 $ do when (package `elem` [hp2ps, rts, touchy, unlit]) $ dataFile %> diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index b7e12d1..19ce0e3 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -4,9 +4,6 @@ import Base import Context import Expression import GHC -import Oracles.Path -import Rules.Libffi -import Settings.Packages.Rts import Settings.Path import Target import UserSettings @@ -16,40 +13,12 @@ import Util -- by running the @ghc-pkg@ utility. registerPackage :: [(Resource, Int)] -> Context -> Rules () registerPackage rs context at Context {..} = when (stage <= Stage1) $ do - let dir = packageDbDirectory stage + let confIn = pkgInplaceConfig context + dir = packageDbDirectory stage matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do - -- This produces inplace-pkg-config. TODO: Add explicit tracking. - need [pkgDataFile context] - - -- Post-process inplace-pkg-config. - top <- topDirectory - let path = buildPath context - pkgConfig = inplacePkgConfig context - oldPath = top -/- path "build" - - fixFile pkgConfig $ unlines . map (replace oldPath path) . lines - - buildWithResources rs $ Target context (GhcPkg stage) [pkgConfig] [conf] - - when (package == rts && stage == Stage1) $ do - packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do - need [rtsConf] - buildWithResources rs $ Target context (GhcPkg stage) [rtsConf] [conf] - - rtsConf %> \_ -> do - need [pkgDataFile rtsContext, rtsConfIn] - build $ Target context HsCpp [rtsConfIn] [rtsConf] - - let fixRtsConf = unlines - . map - ( replace "\"\"" "" - . replace "rts/dist/build" rtsBuildPath - . replace "includes/dist-derivedconstants/header" generatedPath ) - . filter (not . null) - . lines - - fixFile rtsConf fixRtsConf + need [confIn] + buildWithResources rs $ Target context (GhcPkg stage) [confIn] [conf] when (package == ghc) $ packageDbStamp stage %> \stamp -> do removeDirectory dir diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs index 5156d71..15d5249 100644 --- a/src/Settings/Builders/GhcPkg.hs +++ b/src/Settings/Builders/GhcPkg.hs @@ -18,4 +18,4 @@ updateArgs = notM initPredicate ? do , arg "--force" , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs - , arg . inplacePkgConfig =<< getContext ] + , arg . pkgInplaceConfig =<< getContext ] diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 40b85e4..e7c3a60 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -18,7 +18,7 @@ rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" rtsConf :: FilePath -rtsConf = inplacePkgConfig rtsContext +rtsConf = pkgInplaceConfig rtsContext rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index cbe1612..934a0ec 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -4,7 +4,7 @@ module Settings.Path ( gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath, inplacePkgConfig + installPath, autogenPath, pkgInplaceConfig ) where import Base @@ -61,8 +61,8 @@ autogenPath context at Context {..} autogen dir = buildPath context -/- dir -/- "autogen" -- | Path to inplace package configuration of a given 'Context'. -inplacePkgConfig :: Context -> FilePath -inplacePkgConfig context = buildPath context -/- "inplace-pkg-config" +pkgInplaceConfig :: Context -> FilePath +pkgInplaceConfig context = buildPath context -/- "inplace-pkg-config" -- | Path to the @package-data.mk@ of a given 'Context'. pkgDataFile :: Context -> FilePath From git at git.haskell.org Fri Oct 27 01:14:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move RTS path settings to Settings.Path (46ef16f) Message-ID: <20171027011428.579E13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46ef16f18f752ad2df2c92fafdf5c208a4589e2c/ghc >--------------------------------------------------------------- commit 46ef16f18f752ad2df2c92fafdf5c208a4589e2c Author: Andrey Mokhov Date: Sun Nov 27 11:42:25 2016 +0000 Move RTS path settings to Settings.Path >--------------------------------------------------------------- 46ef16f18f752ad2df2c92fafdf5c208a4589e2c src/Rules.hs | 1 - src/Rules/Data.hs | 1 - src/Rules/Generate.hs | 1 - src/Settings/Packages/Rts.hs | 14 +------------- src/Settings/Path.hs | 10 +++++++++- 5 files changed, 10 insertions(+), 17 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index 506fe2c..832bf4c 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -19,7 +19,6 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings -import Settings.Packages.Rts import Settings.Path allStages :: [Stage] diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 1314cc4..5c8a63b 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -9,7 +9,6 @@ import Oracles.Dependencies import Oracles.Path import Rules.Generate import Rules.Libffi -import Settings.Packages.Rts import Settings.Path import Target import UserSettings diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index e84313a..5d557b4 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -17,7 +17,6 @@ import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Rules.Libffi -import Settings.Packages.Rts import Settings.Path import Target import UserSettings diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index e7c3a60..d10c6f0 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,6 +1,4 @@ -module Settings.Packages.Rts ( - rtsPackageArgs, rtsConfIn, rtsConf, rtsContext, rtsLibffiLibraryName - ) where +module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibraryName) where import Base import GHC @@ -9,16 +7,6 @@ import Oracles.Config.Setting import Oracles.Path import Predicate import Settings -import Settings.Path - -rtsContext :: Context -rtsContext = vanillaContext Stage1 rts - -rtsConfIn :: FilePath -rtsConfIn = pkgPath rts -/- "package.conf.in" - -rtsConf :: FilePath -rtsConf = pkgInplaceConfig rtsContext rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 934a0ec..8999300 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -4,7 +4,7 @@ module Settings.Path ( gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath, pkgInplaceConfig + installPath, autogenPath, pkgInplaceConfig, rtsContext, rtsConfIn ) where import Base @@ -100,6 +100,14 @@ pkgFile context prefix suffix = do componentId <- pkgData $ ComponentId path return $ path -/- prefix ++ componentId ++ suffix +-- | RTS is considered a Stage1 package. This determines RTS build path. +rtsContext :: Context +rtsContext = vanillaContext Stage1 rts + +-- | Path to RTS package configuration file, to be processed by HsCpp. +rtsConfIn :: FilePath +rtsConfIn = pkgPath rts -/- "package.conf.in" + -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath gmpBuildPath = buildRootPath -/- "stage1/gmp" From git at git.haskell.org Fri Oct 27 01:14:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move custom contexts to Settings.Path (72a08b0) Message-ID: <20171027011431.D56C13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72a08b0e226c62396437c29e019a61dba03e48fd/ghc >--------------------------------------------------------------- commit 72a08b0e226c62396437c29e019a61dba03e48fd Author: Andrey Mokhov Date: Sun Nov 27 12:01:41 2016 +0000 Move custom contexts to Settings.Path >--------------------------------------------------------------- 72a08b0e226c62396437c29e019a61dba03e48fd src/Rules/Data.hs | 1 - src/Rules/Gmp.hs | 3 --- src/Rules/Libffi.hs | 9 +-------- src/Settings/Path.hs | 31 ++++++++++++++++++++++--------- 4 files changed, 23 insertions(+), 21 deletions(-) diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 5c8a63b..58164d8 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -8,7 +8,6 @@ import Oracles.Config.Setting import Oracles.Dependencies import Oracles.Path import Rules.Generate -import Rules.Libffi import Settings.Path import Target import UserSettings diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs index 2409b6e..1442118 100644 --- a/src/Rules/Gmp.hs +++ b/src/Rules/Gmp.hs @@ -14,9 +14,6 @@ import Util gmpBase :: FilePath gmpBase = pkgPath integerGmp -/- "gmp" -gmpContext :: Context -gmpContext = vanillaContext Stage1 integerGmp - gmpLibraryInTreeH :: FilePath gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h" diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 8d72017..989288e 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -1,21 +1,14 @@ -module Rules.Libffi (rtsBuildPath, libffiRules, libffiDependencies) where +module Rules.Libffi (libffiRules, libffiDependencies) where import Settings.Builders.Common import Settings.Packages.Rts import Target import Util --- TODO: this should be moved elsewhere -rtsBuildPath :: FilePath -rtsBuildPath = buildPath rtsContext - -- TODO: Why copy these include files into rts? Keep in libffi! libffiDependencies :: [FilePath] libffiDependencies = (rtsBuildPath -/-) <$> [ "ffi.h", "ffitarget.h" ] -libffiContext :: Context -libffiContext = vanillaContext Stage1 libffi - libffiLibrary :: FilePath libffiLibrary = libffiBuildPath -/- "inst/lib/libffi.a" diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs index 8999300..9e88ca6 100644 --- a/src/Settings/Path.hs +++ b/src/Settings/Path.hs @@ -1,10 +1,11 @@ module Settings.Path ( stageDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile, - pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpObjects, gmpLibraryH, - gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath, - pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints, - packageDependencies, objectPath, programInplacePath, programInplaceLibPath, - installPath, autogenPath, pkgInplaceConfig, rtsContext, rtsConfIn + pkgLibraryFile0, pkgGhciLibraryFile, gmpContext, gmpBuildPath, gmpObjects, + gmpLibraryH, gmpBuildInfoPath, generatedPath, libffiContext, libffiBuildPath, + rtsContext, rtsBuildPath, rtsConfIn, shakeFilesPath,packageDbDirectory, + pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies, + objectPath, programInplacePath, programInplaceLibPath, installPath, + autogenPath, pkgInplaceConfig ) where import Base @@ -100,17 +101,25 @@ pkgFile context prefix suffix = do componentId <- pkgData $ ComponentId path return $ path -/- prefix ++ componentId ++ suffix --- | RTS is considered a Stage1 package. This determines RTS build path. +-- | RTS is considered a Stage1 package. This determines RTS build directory. rtsContext :: Context rtsContext = vanillaContext Stage1 rts +-- | Path to the RTS build directory. +rtsBuildPath :: FilePath +rtsBuildPath = buildPath rtsContext + -- | Path to RTS package configuration file, to be processed by HsCpp. rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" +-- | GMP is considered a Stage1 package. This determines GMP build directory. +gmpContext :: Context +gmpContext = vanillaContext Stage1 integerGmp + -- | Build directory for in-tree GMP library. gmpBuildPath :: FilePath -gmpBuildPath = buildRootPath -/- "stage1/gmp" +gmpBuildPath = buildRootPath -/- stageDirectory (stage gmpContext) -/- "gmp" -- | Path to the GMP library header. gmpLibraryH :: FilePath @@ -124,9 +133,13 @@ gmpObjects = gmpBuildPath -/- "objs" gmpBuildInfoPath :: FilePath gmpBuildInfoPath = pkgPath integerGmp -/- "integer-gmp.buildinfo" --- | Build directory for in-tree libffi library. +-- | Libffi is considered a Stage1 package. This determines its build directory. +libffiContext :: Context +libffiContext = vanillaContext Stage1 libffi + +-- | Build directory for in-tree Libffi library. libffiBuildPath :: FilePath -libffiBuildPath = buildRootPath -/- "stage1/libffi" +libffiBuildPath = buildPath libffiContext -- TODO: Move to buildRootPath, see #113. -- | Path to package database directory of a given 'Stage'. Note: StageN, N > 0, From git at git.haskell.org Fri Oct 27 01:14:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify handling of non-Cabal contexts (e3be330) Message-ID: <20171027011435.88A033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e3be330a3ff24cf3ead50323e104c217e32f4285/ghc >--------------------------------------------------------------- commit e3be330a3ff24cf3ead50323e104c217e32f4285 Author: Andrey Mokhov Date: Sun Nov 27 14:34:52 2016 +0000 Simplify handling of non-Cabal contexts >--------------------------------------------------------------- e3be330a3ff24cf3ead50323e104c217e32f4285 src/Expression.hs | 12 +----------- src/GHC.hs | 9 ++++++++- src/Rules/Data.hs | 12 ++---------- src/Rules/Libffi.hs | 1 - src/Settings/Builders/Ghc.hs | 7 ++++--- src/Settings/Packages/GhcCabal.hs | 4 ---- src/Settings/Packages/Hp2ps.hs | 9 ++------- src/Settings/Packages/Touchy.hs | 9 ++------- src/Settings/Packages/Unlit.hs | 9 ++------- 9 files changed, 21 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 e3be330a3ff24cf3ead50323e104c217e32f4285 From git at git.haskell.org Fri Oct 27 01:14:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify handling of programs with no Haskell main (e2761b2) Message-ID: <20171027011439.49D613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e2761b27d9c01828650a48e854ce1f3980dc29b4/ghc >--------------------------------------------------------------- commit e2761b27d9c01828650a48e854ce1f3980dc29b4 Author: Andrey Mokhov Date: Sun Nov 27 15:36:50 2016 +0000 Simplify handling of programs with no Haskell main >--------------------------------------------------------------- e2761b27d9c01828650a48e854ce1f3980dc29b4 hadrian.cabal | 4 ---- src/GHC.hs | 7 ++++++- src/Settings/Builders/Ghc.hs | 4 +++- src/Settings/Default.hs | 10 +--------- src/Settings/Packages/Ghc.hs | 7 ++----- src/Settings/Packages/Hp2ps.hs | 9 --------- src/Settings/Packages/IservBin.hs | 7 ------- src/Settings/Packages/Touchy.hs | 9 --------- src/Settings/Packages/Unlit.hs | 9 --------- 9 files changed, 12 insertions(+), 54 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 0663643..30ed256 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -94,13 +94,9 @@ executable hadrian , Settings.Packages.GhcCabal , Settings.Packages.GhcPrim , Settings.Packages.Haddock - , Settings.Packages.Hp2ps , Settings.Packages.IntegerGmp - , Settings.Packages.IservBin , Settings.Packages.Rts , Settings.Packages.RunGhc - , Settings.Packages.Touchy - , Settings.Packages.Unlit , Settings.Path , Stage , Target diff --git a/src/GHC.hs b/src/GHC.hs index 9111d64..4521679 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -9,7 +9,8 @@ module GHC ( parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, builderProvenance, programName, nonCabalContext + defaultKnownPackages, builderProvenance, programName, nonCabalContext, + nonHsMainPackage ) where import Builder @@ -130,3 +131,7 @@ programName Context {..} nonCabalContext :: Context -> Bool nonCabalContext Context {..} = (package `elem` [hp2ps, rts, touchy, unlit]) || package == ghcCabal && stage == Stage0 + +-- | Some program packages should not be linked with Haskell main function. +nonHsMainPackage :: Package -> Bool +nonHsMainPackage = (`elem` [ghc, hp2ps, iservBin, touchy, unlit]) diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 0c4c569..f5b13e1 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -22,6 +22,7 @@ ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do ghcLinkArgs :: Args ghcLinkArgs = builder (Ghc LinkHs) ? do stage <- getStage + pkg <- getPackage libs <- getPkgDataList DepExtraLibs libDirs <- getPkgDataList DepLibDirs gmpLibs <- if stage > Stage0 @@ -31,6 +32,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do return $ concatMap (words . strip) buildInfo else return [] mconcat [ arg "-no-auto-link-packages" + , nonHsMainPackage pkg ? arg "-no-hs-main" , append [ "-optl-l" ++ lib | lib <- libs ++ gmpLibs ] , append [ "-optl-L" ++ unifyPath dir | dir <- libDirs ] ] @@ -75,7 +77,7 @@ commonGhcArgs = do , arg "-odir" , arg path , arg "-hidir" , arg path , arg "-stubdir" , arg path - , arg "-rtsopts" ] -- TODO: ifeq "$(HC_VERSION_GE_6_13)" "YES" + , (not . nonHsMainPackage) <$> getPackage ? arg "-rtsopts" ] -- TODO: Do '-ticky' in all debug ways? wayGhcArgs :: Args diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index c863a9e..6f56c5d 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -34,13 +34,9 @@ import Settings.Packages.Ghc import Settings.Packages.GhcCabal import Settings.Packages.GhcPrim import Settings.Packages.Haddock -import Settings.Packages.Hp2ps import Settings.Packages.IntegerGmp -import Settings.Packages.IservBin import Settings.Packages.Rts import Settings.Packages.RunGhc -import Settings.Packages.Touchy -import Settings.Packages.Unlit import UserSettings -- | All default command line arguments. @@ -203,10 +199,6 @@ defaultPackageArgs = mconcat , ghcCabalPackageArgs , ghcPrimPackageArgs , haddockPackageArgs - , hp2psPackageArgs , integerGmpPackageArgs - , iservBinPackageArgs , rtsPackageArgs - , runGhcPackageArgs - , touchyPackageArgs - , unlitPackageArgs ] + , runGhcPackageArgs ] diff --git a/src/Settings/Packages/Ghc.hs b/src/Settings/Packages/Ghc.hs index b069c23..a95bda6 100644 --- a/src/Settings/Packages/Ghc.hs +++ b/src/Settings/Packages/Ghc.hs @@ -8,10 +8,7 @@ import Settings.Path ghcPackageArgs :: Args ghcPackageArgs = package ghc ? do stage <- getStage - mconcat [ builder Ghc ? mconcat - [ arg $ "-I" ++ buildPath (vanillaContext stage compiler) - , arg "-no-hs-main" ] + mconcat [ builder Ghc ? arg ("-I" ++ buildPath (vanillaContext stage compiler)) , builder GhcCabal ? - ghcWithInterpreter ? notStage0 ? arg "--flags=ghci" - ] + ghcWithInterpreter ? notStage0 ? arg "--flags=ghci" ] diff --git a/src/Settings/Packages/Hp2ps.hs b/src/Settings/Packages/Hp2ps.hs deleted file mode 100644 index a5c62c2..0000000 --- a/src/Settings/Packages/Hp2ps.hs +++ /dev/null @@ -1,9 +0,0 @@ -module Settings.Packages.Hp2ps (hp2psPackageArgs) where - -import GHC -import Predicate - -hp2psPackageArgs :: Args -hp2psPackageArgs = package hp2ps ? - builder Ghc ? mconcat [ arg "-no-hs-main" - , remove ["-hide-all-packages"] ] diff --git a/src/Settings/Packages/IservBin.hs b/src/Settings/Packages/IservBin.hs deleted file mode 100644 index 40b2101..0000000 --- a/src/Settings/Packages/IservBin.hs +++ /dev/null @@ -1,7 +0,0 @@ -module Settings.Packages.IservBin (iservBinPackageArgs) where - -import GHC -import Predicate - -iservBinPackageArgs :: Args -iservBinPackageArgs = package iservBin ? builder Ghc ? arg "-no-hs-main" diff --git a/src/Settings/Packages/Touchy.hs b/src/Settings/Packages/Touchy.hs deleted file mode 100644 index 7c2e04c..0000000 --- a/src/Settings/Packages/Touchy.hs +++ /dev/null @@ -1,9 +0,0 @@ -module Settings.Packages.Touchy (touchyPackageArgs) where - -import GHC -import Predicate - -touchyPackageArgs :: Args -touchyPackageArgs = package touchy ? - builder Ghc ? mconcat [ arg "-no-hs-main" - , remove ["-hide-all-packages"] ] diff --git a/src/Settings/Packages/Unlit.hs b/src/Settings/Packages/Unlit.hs deleted file mode 100644 index a959699..0000000 --- a/src/Settings/Packages/Unlit.hs +++ /dev/null @@ -1,9 +0,0 @@ -module Settings.Packages.Unlit (unlitPackageArgs) where - -import GHC -import Predicate - -unlitPackageArgs :: Args -unlitPackageArgs = package unlit ? - builder Ghc ? mconcat [ arg "-no-hs-main" - , remove ["-hide-all-packages"] ] From git at git.haskell.org Fri Oct 27 01:14:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:14:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify ghcCabalPackageArgs (4e80495) Message-ID: <20171027011442.F31763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e8049531d734957c1c71fdbe3f18a52db2e2f2d/ghc >--------------------------------------------------------------- commit 4e8049531d734957c1c71fdbe3f18a52db2e2f2d Author: Andrey Mokhov Date: Sun Nov 27 15:56:22 2016 +0000 Simplify ghcCabalPackageArgs >--------------------------------------------------------------- 4e8049531d734957c1c71fdbe3f18a52db2e2f2d src/Settings/Packages/GhcCabal.hs | 21 ++++++--------------- 1 file changed, 6 insertions(+), 15 deletions(-) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index f41053f..8e5837c 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -6,21 +6,12 @@ import Oracles.Config.Setting import Predicate ghcCabalPackageArgs :: Args -ghcCabalPackageArgs = package ghcCabal ? - builder Ghc ? mconcat [ ghcCabalBootArgs - , remove ["-no-auto-link-packages"] ] - --- TODO: do we need -DCABAL_VERSION=$(CABAL_VERSION)? -ghcCabalBootArgs :: Args -ghcCabalBootArgs = stage0 ? do - -- Note: We could have computed 'cabalDeps' instead of hard-coding it - -- but this doesn't worth the effort, since we plan to drop ghc-cabal - -- altogether at some point. See #18. - cabalDeps <- fromDiffExpr $ mconcat - [ append [ array, base, bytestring, containers, deepseq, directory - , pretty, process, time ] - , notM windowsHost ? append [unix] - , windowsHost ? append [win32] ] +ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do + -- Note: We could compute 'cabalDeps' instead of hard-coding it but this + -- seems unnecessary since we plan to drop @ghc-cabal@ altogether, #18. + win <- lift windowsHost + let cabalDeps = [ array, base, bytestring, containers, deepseq, directory + , pretty, process, time, if win then win32 else unix ] mconcat [ append [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , arg "--make" From git at git.haskell.org Fri Oct 27 01:16:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (12aa4ef) Message-ID: <20171027011611.7D7133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12aa4ef0c4e6f8e0a89f2aa899d66a42ac2e3eb9/ghc >--------------------------------------------------------------- commit 12aa4ef0c4e6f8e0a89f2aa899d66a42ac2e3eb9 Author: Andrey Mokhov Date: Sat Jan 7 22:40:55 2017 +0000 Minor revision >--------------------------------------------------------------- 12aa4ef0c4e6f8e0a89f2aa899d66a42ac2e3eb9 src/Settings/Default.hs | 1 - src/Settings/Flavours/Quick.hs | 3 +-- src/Settings/Flavours/Quickest.hs | 8 ++++---- 3 files changed, 5 insertions(+), 7 deletions(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 061d4ae..92089ab 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -118,7 +118,6 @@ stage2Packages = do , ghcTags ] ++ [ haddock | doc ] --- TODO: What about profilingDynamic way? Do we need platformSupportsSharedLibs? -- | Default build ways for library packages: -- * We always build 'vanilla' way. -- * We build 'profiling' way when stage > Stage0. diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs index 6935544..324ec85 100644 --- a/src/Settings/Flavours/Quick.hs +++ b/src/Settings/Flavours/Quick.hs @@ -10,8 +10,7 @@ quickFlavour :: Flavour quickFlavour = defaultFlavour { name = "quick" , args = defaultBuilderArgs <> quickArgs <> defaultPackageArgs - , libraryWays = append [vanilla] - , rtsWays = append [vanilla, threaded] } + , libraryWays = append [vanilla] } optimise :: Context -> Bool optimise Context {..} = diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 62ad43e..4d64cd0 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -6,10 +6,10 @@ import {-# SOURCE #-} Settings.Default quickestFlavour :: Flavour quickestFlavour = defaultFlavour - { name = "quickest" - , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs - , libraryWays = append [vanilla] - , rtsWays = quickestRtsWays } + { name = "quickest" + , args = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs + , libraryWays = append [vanilla] + , rtsWays = quickestRtsWays } quickestArgs :: Args quickestArgs = builder Ghc ? arg "-O0" From git at git.haskell.org Fri Oct 27 01:16:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move integerLibrary to flavour (6b35c2c) Message-ID: <20171027011615.05F983A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6b35c2c39cc41a548582483476c84e68798687b8/ghc >--------------------------------------------------------------- commit 6b35c2c39cc41a548582483476c84e68798687b8 Author: Andrey Mokhov Date: Sun Jan 8 01:28:06 2017 +0000 Move integerLibrary to flavour See #179 >--------------------------------------------------------------- 6b35c2c39cc41a548582483476c84e68798687b8 src/Flavour.hs | 1 + src/Rules/Generators/ConfigHs.hs | 11 +++++------ src/Settings.hs | 6 +++++- src/Settings/Default.hs | 4 ++-- src/Settings/Packages/Base.hs | 5 ++--- src/UserSettings.hs | 7 +------ 6 files changed, 16 insertions(+), 18 deletions(-) diff --git a/src/Flavour.hs b/src/Flavour.hs index ad658c4..b195767 100644 --- a/src/Flavour.hs +++ b/src/Flavour.hs @@ -8,6 +8,7 @@ data Flavour = Flavour { name :: String -- ^ Flavour name, to set from command line. , args :: Args -- ^ Use these command line arguments. , packages :: Packages -- ^ Build these packages. + , integerLibrary :: Package -- ^ Either 'integerGmp' or 'integerSimple'. , libraryWays :: Ways -- ^ Build libraries these ways. , rtsWays :: Ways -- ^ Build RTS these ways. , splitObjects :: Predicate -- ^ Build split objects. diff --git a/src/Rules/Generators/ConfigHs.hs b/src/Rules/Generators/ConfigHs.hs index c5ad0cc..ffe0cfc 100644 --- a/src/Rules/Generators/ConfigHs.hs +++ b/src/Rules/Generators/ConfigHs.hs @@ -8,7 +8,6 @@ import Oracles.Config.Flag import Oracles.Config.Setting import Rules.Generators.Common import Settings -import UserSettings generateConfigHs :: Expr String generateConfigHs = do @@ -21,10 +20,10 @@ generateConfigHs = do cProjectPatchLevel1 <- getSetting ProjectPatchLevel1 cProjectPatchLevel2 <- getSetting ProjectPatchLevel2 cBooterVersion <- getSetting GhcVersion - let cIntegerLibraryType | integerLibrary == integerGmp = "IntegerGMP" - | integerLibrary == integerSimple = "IntegerSimple" - | otherwise = error $ "Unknown integer library: " - ++ show integerLibrary ++ "." + let cIntegerLibraryType + | integerLibrary flavour == integerGmp = "IntegerGMP" + | integerLibrary flavour == integerSimple = "IntegerSimple" + | otherwise = error $ "Unknown integer library: " ++ integerLibraryName cSupportsSplitObjs <- yesNo supportsSplitObjects cGhcWithInterpreter <- yesNo ghcWithInterpreter cGhcWithNativeCodeGen <- yesNo ghcWithNativeCodeGen @@ -72,7 +71,7 @@ generateConfigHs = do , "cStage :: String" , "cStage = show (STAGE :: Int)" , "cIntegerLibrary :: String" - , "cIntegerLibrary = " ++ show (pkgNameString integerLibrary) + , "cIntegerLibrary = " ++ show integerLibraryName , "cIntegerLibraryType :: IntegerLibrary" , "cIntegerLibraryType = " ++ cIntegerLibraryType , "cSupportsSplitObjs :: String" diff --git a/src/Settings.hs b/src/Settings.hs index c455e0b..09b58f8 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,7 +2,8 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath, getContextDirectory, getBuildPath, stagePackages, builderPath, - getBuilderPath, isSpecified, latestBuildStage, programPath, programContext + getBuilderPath, isSpecified, latestBuildStage, programPath, programContext, + integerLibraryName ) where import Base @@ -62,6 +63,9 @@ flavour = fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours flavours = hadrianFlavours ++ userFlavours flavourName = fromMaybe "default" cmdFlavour +integerLibraryName :: String +integerLibraryName = pkgNameString $ integerLibrary flavour + programContext :: Stage -> Package -> Context programContext stage pkg | pkg == ghc && ghcProfiled flavour = Context stage pkg profiling diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 92089ab..103c432 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -37,7 +37,6 @@ import Settings.Packages.Haddock import Settings.Packages.IntegerGmp import Settings.Packages.Rts import Settings.Packages.RunGhc -import UserSettings -- | All default command line arguments. defaultArgs :: Args @@ -100,7 +99,7 @@ stage1Packages = do , haskeline , hpcBin , hsc2hs - , integerLibrary + , integerLibrary flavour , pretty , process , rts @@ -147,6 +146,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages + , integerLibrary = integerGmp , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects diff --git a/src/Settings/Packages/Base.hs b/src/Settings/Packages/Base.hs index dce49e7..219c9d4 100644 --- a/src/Settings/Packages/Base.hs +++ b/src/Settings/Packages/Base.hs @@ -1,11 +1,10 @@ module Settings.Packages.Base (basePackageArgs) where -import Base import GHC import Predicate -import UserSettings +import Settings basePackageArgs :: Args basePackageArgs = package base ? mconcat - [ builder GhcCabal ? arg ("--flags=" ++ takeFileName (pkgPath integerLibrary)) + [ builder GhcCabal ? arg ("--flags=" ++ integerLibraryName) , builder Cc ? arg "-O2" ] -- Fix the 'unknown symbol stat' issue, see #259. diff --git a/src/UserSettings.hs b/src/UserSettings.hs index b952363..e16cf49 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -3,7 +3,7 @@ -- If you don't copy the file your changes will be tracked by git and you can -- accidentally commit them. module UserSettings ( - buildRootPath, userFlavours, userKnownPackages, integerLibrary, validating, + buildRootPath, userFlavours, userKnownPackages, validating, turnWarningsIntoErrors, verboseCommands, putBuild, putSuccess ) where @@ -11,7 +11,6 @@ import System.Console.ANSI import Base import Flavour -import GHC import Predicate -- See doc/user-settings.md for instructions. @@ -30,10 +29,6 @@ userFlavours = [] userKnownPackages :: [Package] userKnownPackages = [] --- | Choose the integer library: 'integerGmp' or 'integerSimple'. -integerLibrary :: Package -integerLibrary = integerGmp - -- | User defined flags. Note the following type semantics: -- * @Bool@: a plain Boolean flag whose value is known at compile time. -- * @Action Bool@: a flag whose value can depend on the build environment. From git at git.haskell.org Fri Oct 27 01:16:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:18 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Depend on GMP only when using integerGmp (4ac02f6) Message-ID: <20171027011618.768BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ac02f6d213ff80fdb3659fb246688ada9886bbd/ghc >--------------------------------------------------------------- commit 4ac02f6d213ff80fdb3659fb246688ada9886bbd Author: Andrey Mokhov Date: Sun Jan 8 01:29:35 2017 +0000 Depend on GMP only when using integerGmp See #179 >--------------------------------------------------------------- 4ac02f6d213ff80fdb3659fb246688ada9886bbd src/Rules/Generate.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 5d557b4..51bec60 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -6,6 +6,7 @@ module Rules.Generate ( import Base import Context hiding (package) import Expression +import Flavour import GHC import Oracles.ModuleFiles import Predicate @@ -17,6 +18,7 @@ import Rules.Generators.GhcSplit import Rules.Generators.GhcVersionH import Rules.Generators.VersionHs import Rules.Libffi +import Settings import Settings.Path import Target import UserSettings @@ -70,7 +72,8 @@ compilerDependencies = do mconcat [ return [platformH stage] , return includesDependencies , return derivedConstantsDependencies - , notStage0 ? return (gmpLibraryH : libffiDependencies) + , notStage0 ? integerLibrary flavour == integerGmp ? return [gmpLibraryH] + , notStage0 ? return libffiDependencies , return $ fmap (path -/-) [ "primop-can-fail.hs-incl" , "primop-code-size.hs-incl" From git at git.haskell.org Fri Oct 27 01:16:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Test integerSimple on CI (0c08cc6) Message-ID: <20171027011621.E001B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c08cc6871a95c987d9a559bd805cc91238eea37/ghc >--------------------------------------------------------------- commit 0c08cc6871a95c987d9a559bd805cc91238eea37 Author: Andrey Mokhov Date: Sun Jan 8 01:30:31 2017 +0000 Test integerSimple on CI See #179 >--------------------------------------------------------------- 0c08cc6871a95c987d9a559bd805cc91238eea37 src/Settings/Default.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 103c432..0fb54f6 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -146,7 +146,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages - , integerLibrary = integerGmp + , integerLibrary = integerSimple -- FIXME after testing, #179! , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects From git at git.haskell.org Fri Oct 27 01:16:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:16:25 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Revert to integerGmp (de151a9) Message-ID: <20171027011625.58E683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de151a9b7b8b5c595aa2084c160663340d7e5c3c/ghc >--------------------------------------------------------------- commit de151a9b7b8b5c595aa2084c160663340d7e5c3c Author: Andrey Mokhov Date: Sun Jan 8 02:11:38 2017 +0000 Revert to integerGmp Fix #179. >--------------------------------------------------------------- de151a9b7b8b5c595aa2084c160663340d7e5c3c src/Settings/Default.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 0fb54f6..103c432 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -146,7 +146,7 @@ defaultFlavour = Flavour { name = "default" , args = defaultArgs , packages = defaultPackages - , integerLibrary = integerSimple -- FIXME after testing, #179! + , integerLibrary = integerGmp , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , splitObjects = defaultSplitObjects From git at git.haskell.org Fri Oct 27 01:22:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify oracles (acf66a3) Message-ID: <20171027012242.BA1FD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acf66a3c7bb4834f2a9b631eb5492dfc92149026/ghc >--------------------------------------------------------------- commit acf66a3c7bb4834f2a9b631eb5492dfc92149026 Author: Andrey Mokhov Date: Tue Aug 8 22:53:25 2017 +0100 Simplify oracles >--------------------------------------------------------------- acf66a3c7bb4834f2a9b631eb5492dfc92149026 src/Hadrian/Oracles/ArgsHash.hs | 6 +++--- src/Hadrian/Oracles/Config.hs | 6 +++--- src/Oracles/Dependencies.hs | 18 +++++------------- 3 files changed, 11 insertions(+), 19 deletions(-) diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index e07fc3f..8ac2c38 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -35,16 +35,16 @@ trackArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action () trackArgsHash t = do let hashedInputs = [ show $ hash (inputs t) ] hashedTarget = target (context t) (builder t) hashedInputs (outputs t) - void (askOracle $ ArgsHashKey hashedTarget :: Action Int) + void (askOracle $ ArgsHash hashedTarget :: Action Int) -newtype ArgsHashKey c b = ArgsHashKey (Target c b) +newtype ArgsHash c b = ArgsHash (Target c b) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -- | This oracle stores per-target argument list hashes in the Shake database, -- allowing the user to track them between builds using 'trackArgsHash' queries. argsHashOracle :: (ShakeValue c, ShakeValue b) => TrackArgument c b -> Args c b -> Rules () argsHashOracle trackArgument args = void $ - addOracle $ \(ArgsHashKey target) -> do + addOracle $ \(ArgsHash target) -> do argList <- interpret target args let trackedArgList = filter (trackArgument target) argList return $ hash trackedArgList diff --git a/src/Hadrian/Oracles/Config.hs b/src/Hadrian/Oracles/Config.hs index 0b12616..1263f1a 100644 --- a/src/Hadrian/Oracles/Config.hs +++ b/src/Hadrian/Oracles/Config.hs @@ -10,7 +10,7 @@ import Development.Shake.Config import Hadrian.Utilities -newtype ConfigKey = ConfigKey String +newtype Config = Config String deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -- | Lookup a configuration setting raising an error if the key is not found. @@ -21,7 +21,7 @@ unsafeAskConfig key = (fromMaybe $ error msg) <$> askConfig key -- | Lookup a configuration setting. askConfig :: String -> Action (Maybe String) -askConfig = askOracle . ConfigKey +askConfig = askOracle . Config -- | This oracle reads and parses a configuration file consisting of key-value -- pairs @key = value@ and answers 'askConfig' queries tracking the results. @@ -31,4 +31,4 @@ configOracle configFile = void $ do need [configFile] putLoud $ "Reading " ++ configFile ++ "..." liftIO $ readConfigFile configFile - addOracle $ \(ConfigKey key) -> Map.lookup key <$> cfg () + addOracle $ \(Config key) -> Map.lookup key <$> cfg () diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 04ebbfd..6ae0b0d 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -15,7 +15,7 @@ import Settings import Settings.Builders.GhcCabal import Settings.Path -newtype ObjDepsKey = ObjDepsKey (FilePath, FilePath) +newtype Dependency = Dependency (FilePath, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -- | 'Action' @fileDependencies context file@ looks up dependencies of a @file@ @@ -26,15 +26,12 @@ newtype ObjDepsKey = ObjDepsKey (FilePath, FilePath) fileDependencies :: Context -> FilePath -> Action (FilePath, [FilePath]) fileDependencies context obj = do let path = buildPath context -/- ".dependencies" - deps <- askOracle $ ObjDepsKey (path, obj) + deps <- askOracle $ Dependency (path, obj) case deps of Nothing -> error $ "No dependencies found for file " ++ obj Just [] -> error $ "No source file found for file " ++ obj Just (source : files) -> return (source, files) -newtype PkgDepsKey = PkgDepsKey String - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -- | Given a 'Context' this 'Action' looks up its package dependencies in -- 'Settings.Paths.packageDependencies' using 'packageDependenciesOracle', and -- wraps found dependencies in appropriate contexts. The only subtlety here is @@ -45,7 +42,7 @@ contextDependencies :: Context -> Action [Context] contextDependencies context at Context {..} = do let pkgContext = \pkg -> Context (min stage Stage1) pkg way unpack = fromMaybe . error $ "No dependencies for " ++ show context - deps <- unpack <$> askOracle (PkgDepsKey $ pkgNameString package) + deps <- unpack <$> askOracle (Dependency (packageDependencies, pkgNameString package)) pkgs <- sort <$> interpretInContext (pkgContext package) getPackages return . map pkgContext $ intersectOrd (compare . pkgNameString) pkgs deps @@ -74,16 +71,11 @@ needLibrary cs = need =<< concatMapM libraryTargets cs -- | Oracles for the package dependencies and 'path/dist/.dependencies' files. dependenciesOracles :: Rules () dependenciesOracles = do - deps <- newCache readDependencies - void $ addOracle $ \(ObjDepsKey (file, obj)) -> Map.lookup obj <$> deps file - - pkgDeps <- newCache $ \_ -> readDependencies packageDependencies - void $ addOracle $ \(PkgDepsKey pkg) -> Map.lookup pkg <$> pkgDeps () - where - readDependencies file = do + deps <- newCache $ \file -> do putLoud $ "Reading dependencies from " ++ file ++ "..." contents <- map words <$> readFileLines file return $ Map.fromList [ (key, values) | (key:values) <- contents ] + void $ addOracle $ \(Dependency (file, key)) -> Map.lookup key <$> deps file -- | Topological sort of packages according to their dependencies. -- HACK (izgzhen): See https://github.com/snowleopard/hadrian/issues/344 for details From git at git.haskell.org Fri Oct 27 01:22:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:46 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Replace Config oracle with generic key-value text file oracle (da27a1f) Message-ID: <20171027012246.419873A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/da27a1fec4ba6565faca24362f0007aa477105f0/ghc >--------------------------------------------------------------- commit da27a1fec4ba6565faca24362f0007aa477105f0 Author: Andrey Mokhov Date: Wed Aug 9 23:39:23 2017 +0100 Replace Config oracle with generic key-value text file oracle See #347 >--------------------------------------------------------------- da27a1fec4ba6565faca24362f0007aa477105f0 hadrian.cabal | 2 +- src/Hadrian/Oracles/Config.hs | 34 --------------------------------- src/Hadrian/Oracles/KeyValue.hs | 42 +++++++++++++++++++++++++++++++++++++++++ src/Oracles/Flag.hs | 4 ++-- src/Oracles/ModuleFiles.hs | 6 +++--- src/Oracles/PackageData.hs | 26 ++++++------------------- src/Oracles/Setting.hs | 6 +++--- src/Rules/Oracles.hs | 6 ++---- src/Settings.hs | 4 ++-- 9 files changed, 61 insertions(+), 69 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 da27a1fec4ba6565faca24362f0007aa477105f0 From git at git.haskell.org Fri Oct 27 01:22:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (72bf4b1) Message-ID: <20171027012249.C15A03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/72bf4b180dffa10fb650046b571b756b5262097a/ghc >--------------------------------------------------------------- commit 72bf4b180dffa10fb650046b571b756b5262097a Author: Andrey Mokhov Date: Sat Aug 12 21:51:16 2017 +0100 Minor revision >--------------------------------------------------------------- 72bf4b180dffa10fb650046b571b756b5262097a src/Base.hs | 29 ++--------------------------- src/Hadrian/Utilities.hs | 23 ++++++++++++++++++++++- src/Rules/Library.hs | 15 +++++++-------- src/Rules/Register.hs | 2 +- 4 files changed, 32 insertions(+), 37 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 6ae3ead..df14d3d 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -17,15 +17,13 @@ module Base ( configPath, configFile, sourcePath, -- * Miscellaneous utilities - unifyPath, quote, (-/-), matchVersionedFilePath, matchGhcVersionedFilePath, - putColoured + unifyPath, quote, (-/-), putColoured ) where import Control.Applicative import Control.Monad.Extra import Control.Monad.Reader import Data.Bifunctor -import Data.Char import Data.Function import Data.List.Extra import Data.Maybe @@ -58,30 +56,7 @@ configFile = configPath -/- "system.config" sourcePath :: FilePath sourcePath = hadrianPath -/- "src" --- | Given a @prefix@ and a @suffix@ check whether a @filePath@ matches the --- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string --- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: --- ---- * @'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'False'@ ---- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False'@ ---- * @'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar-" "a" "foo/bar-0.1.a" '==' 'True'@ ---- * @'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False'@ -matchVersionedFilePath :: String -> String -> FilePath -> Bool -matchVersionedFilePath prefix suffix filePath = - case stripPrefix prefix filePath >>= stripSuffix suffix of - Nothing -> False - Just version -> all (\c -> isDigit c || c == '-' || c == '.') version - -matchGhcVersionedFilePath :: String -> String -> FilePath -> Bool -matchGhcVersionedFilePath prefix ext filePath = - case stripPrefix prefix filePath >>= stripSuffix ext of - Nothing -> False - Just _ -> True - --- | A more colourful version of Shake's putNormal. +-- | A more colourful version of Shake's 'putNormal'. putColoured :: ColorIntensity -> Color -> String -> Action () putColoured intensity colour msg = do c <- useColour diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 56b53ce..f26a444 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -7,9 +7,11 @@ module Hadrian.Utilities ( quote, yesNo, -- * FilePath manipulation - unifyPath, (-/-) + unifyPath, (-/-), matchVersionedFilePath ) where +import Data.Char +import Data.List.Extra import Development.Shake.FilePath -- | Extract a value from a singleton list, or terminate with an error message @@ -79,3 +81,22 @@ a -/- b | otherwise = a ++ '/' : b infixr 6 -/- + +-- | Given a @prefix@ and a @suffix@ check whether a 'FilePath' matches the +-- template @prefix ++ version ++ suffix@ where @version@ is an arbitrary string +-- comprising digits (@0-9@), dashes (@-@), and dots (@.@). Examples: +-- +-- @ +-- 'matchVersionedFilePath' "foo/bar" ".a" "foo/bar.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar" ".a" "foo\bar.a" '==' 'False' +-- 'matchVersionedFilePath' "foo/bar" "a" "foo/bar.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar" "" "foo/bar.a" '==' 'False' +-- 'matchVersionedFilePath' "foo/bar" "a" "foo/bar-0.1.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar-" "a" "foo/bar-0.1.a" '==' 'True' +-- 'matchVersionedFilePath' "foo/bar/" "a" "foo/bar-0.1.a" '==' 'False' +-- @ +matchVersionedFilePath :: String -> String -> FilePath -> Bool +matchVersionedFilePath prefix suffix filePath = + case stripPrefix prefix filePath >>= stripSuffix suffix of + Nothing -> False + Just version -> all (\c -> isDigit c || c == '-' || c == '.') version diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index ba3138a..7b32f55 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -3,6 +3,7 @@ module Rules.Library ( ) where import Data.Char +import Hadrian.Utilities import qualified System.Directory as IO import Base @@ -38,24 +39,22 @@ libraryObjects context at Context{..} = do buildDynamicLib :: Context -> Rules () buildDynamicLib context at Context{..} = do - let path = buildPath context - libPrefix = path -/- "libHS" ++ pkgNameString package + let libPrefix = buildPath context -/- "libHS" ++ pkgNameString package -- OS X - matchGhcVersionedFilePath libPrefix "dylib" ?> buildDynamicLibUnix + libPrefix ++ "*.dylib" %> buildDynamicLibUnix -- Linux - matchGhcVersionedFilePath libPrefix "so" ?> buildDynamicLibUnix + libPrefix ++ "*.so" %> buildDynamicLibUnix -- TODO: Windows where - buildDynamicLibUnix so = do + buildDynamicLibUnix lib = do deps <- contextDependencies context need =<< mapM pkgLibraryFile deps objs <- libraryObjects context - build $ target context (Ghc LinkHs stage) objs [so] + build $ target context (Ghc LinkHs stage) objs [lib] buildPackageLibrary :: Context -> Rules () buildPackageLibrary context at Context {..} = do - let path = buildPath context - libPrefix = path -/- "libHS" ++ pkgNameString package + let libPrefix = buildPath context -/- "libHS" ++ pkgNameString package matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do objs <- libraryObjects context asuf <- libsuf way diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 1f5f64a..7ec8bcd 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -16,7 +16,7 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do let confIn = pkgInplaceConfig context dir = inplacePackageDbDirectory stage - matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do + dir -/- pkgNameString package ++ "*.conf" %> \conf -> do need [confIn] buildWithResources rs $ target context (GhcPkg Update stage) [confIn] [conf] From git at git.haskell.org Fri Oct 27 01:22:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:53 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix package registration (78878b7) Message-ID: <20171027012253.3EFF63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/78878b77fecd6a2e277cfcee5d2bcb3a3832e385/ghc >--------------------------------------------------------------- commit 78878b77fecd6a2e277cfcee5d2bcb3a3832e385 Author: Andrey Mokhov Date: Sat Aug 12 22:27:54 2017 +0100 Fix package registration >--------------------------------------------------------------- 78878b77fecd6a2e277cfcee5d2bcb3a3832e385 src/Rules/Register.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 7ec8bcd..6f4f5b4 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -1,5 +1,7 @@ module Rules.Register (registerPackage) where +import Hadrian.Utilities + import Base import Context import Expression @@ -16,7 +18,7 @@ registerPackage rs context at Context {..} = when (stage <= Stage1) $ do let confIn = pkgInplaceConfig context dir = inplacePackageDbDirectory stage - dir -/- pkgNameString package ++ "*.conf" %> \conf -> do + matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do need [confIn] buildWithResources rs $ target context (GhcPkg Update stage) [confIn] [conf] From git at git.haskell.org Fri Oct 27 01:22:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:22:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move putColoured to the library (a395dd7) Message-ID: <20171027012256.C13A23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a395dd71438e58c29448f5f34cf4bb17e9fcbe5d/ghc >--------------------------------------------------------------- commit a395dd71438e58c29448f5f34cf4bb17e9fcbe5d Author: Andrey Mokhov Date: Sun Aug 13 00:49:18 2017 +0100 Move putColoured to the library See #347 >--------------------------------------------------------------- a395dd71438e58c29448f5f34cf4bb17e9fcbe5d src/Base.hs | 27 +-------------------------- src/CmdLineFlag.hs | 16 ++++++++-------- src/Hadrian/Utilities.hs | 23 ++++++++++++++++++++++- src/UserSettings.hs | 6 ++++-- 4 files changed, 35 insertions(+), 37 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index df14d3d..f4f4c4b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -17,7 +17,7 @@ module Base ( configPath, configFile, sourcePath, -- * Miscellaneous utilities - unifyPath, quote, (-/-), putColoured + unifyPath, quote, (-/-) ) where import Control.Applicative @@ -32,11 +32,6 @@ import Development.Shake hiding (parallel, unit, (*>), Normal) import Development.Shake.Classes import Development.Shake.FilePath import Hadrian.Utilities -import System.Console.ANSI -import System.IO -import System.Info - -import CmdLineFlag -- TODO: reexport Stage, etc.? @@ -55,23 +50,3 @@ configFile = configPath -/- "system.config" -- sourcePath -/- "Base.hs". We use this to `need` some of the source files. sourcePath :: FilePath sourcePath = hadrianPath -/- "src" - --- | A more colourful version of Shake's 'putNormal'. -putColoured :: ColorIntensity -> Color -> String -> Action () -putColoured intensity colour msg = do - c <- useColour - when c . liftIO $ setSGR [SetColor Foreground intensity colour] - putNormal msg - when c . liftIO $ do - setSGR [] - hFlush stdout - -useColour :: Action Bool -useColour = case cmdProgressColour of - Never -> return False - Always -> return True - Auto -> do - supported <- liftIO $ hSupportsANSI stdout - -- An ugly hack to always try to print colours when on mingw and cygwin. - let windows = any (`isPrefixOf` os) ["mingw", "cygwin"] - return $ windows || supported diff --git a/src/CmdLineFlag.hs b/src/CmdLineFlag.hs index 961a033..ff35f1f 100644 --- a/src/CmdLineFlag.hs +++ b/src/CmdLineFlag.hs @@ -1,11 +1,12 @@ module CmdLineFlag ( putCmdLineFlags, cmdFlags, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, - cmdProgressColour, ProgressColour (..), cmdProgressInfo, ProgressInfo (..), - cmdSkipConfigure, cmdSplitObjects + cmdProgressColour, cmdProgressInfo, ProgressInfo (..), cmdSkipConfigure, + cmdSplitObjects ) where import Data.IORef import Data.List.Extra +import Hadrian.Utilities import System.Console.GetOpt import System.IO.Unsafe @@ -16,14 +17,13 @@ data Untracked = Untracked { buildHaddock :: Bool , flavour :: Maybe String , integerSimple :: Bool - , progressColour :: ProgressColour + , progressColour :: UseColour , progressInfo :: ProgressInfo , skipConfigure :: Bool , splitObjects :: Bool } deriving (Eq, Show) -data ProgressColour = Never | Auto | Always deriving (Eq, Show) -data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) +data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show) -- | Default values for 'CmdLineFlag.Untracked'. defaultUntracked :: Untracked @@ -49,12 +49,12 @@ readProgressColour :: Maybe String -> Either String (Untracked -> Untracked) readProgressColour ms = maybe (Left "Cannot parse progress-colour") (Right . set) (go =<< lower <$> ms) where - go :: String -> Maybe ProgressColour + go :: String -> Maybe UseColour go "never" = Just Never go "auto" = Just Auto go "always" = Just Always go _ = Nothing - set :: ProgressColour -> Untracked -> Untracked + set :: UseColour -> Untracked -> Untracked set flag flags = flags { progressColour = flag } readProgressInfo :: Maybe String -> Either String (Untracked -> Untracked) @@ -115,7 +115,7 @@ cmdFlavour = flavour getCmdLineFlags cmdIntegerSimple :: Bool cmdIntegerSimple = integerSimple getCmdLineFlags -cmdProgressColour :: ProgressColour +cmdProgressColour :: UseColour cmdProgressColour = progressColour getCmdLineFlags cmdProgressInfo :: ProgressInfo diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index f26a444..bf9a9ac 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -7,12 +7,20 @@ module Hadrian.Utilities ( quote, yesNo, -- * FilePath manipulation - unifyPath, (-/-), matchVersionedFilePath + unifyPath, (-/-), matchVersionedFilePath, + + -- * Miscellaneous + UseColour (..), putColoured ) where +import Control.Monad import Data.Char import Data.List.Extra +import Development.Shake import Development.Shake.FilePath +import System.Console.ANSI +import System.Info.Extra +import System.IO -- | Extract a value from a singleton list, or terminate with an error message -- if the list does not contain exactly one value. @@ -100,3 +108,16 @@ matchVersionedFilePath prefix suffix filePath = case stripPrefix prefix filePath >>= stripSuffix suffix of Nothing -> False Just version -> all (\c -> isDigit c || c == '-' || c == '.') version + +data UseColour = Never | Auto | Always deriving (Eq, Show) + +-- | A more colourful version of Shake's 'putNormal'. +putColoured :: UseColour -> ColorIntensity -> Color -> String -> Action () +putColoured useColour intensity colour msg = do + supported <- liftIO $ hSupportsANSI stdout + let c Never = False + c Auto = supported || isWindows -- Colours do work on Windows + c Always = True + when (c useColour) . liftIO $ setSGR [SetColor Foreground intensity colour] + putNormal msg + when (c useColour) . liftIO $ setSGR [] >> hFlush stdout diff --git a/src/UserSettings.hs b/src/UserSettings.hs index e2aa674..debd7cd 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -7,9 +7,11 @@ module UserSettings ( putBuild, putSuccess, defaultDestDir, defaultStage1Only ) where +import Hadrian.Utilities import System.Console.ANSI import Base +import CmdLineFlag import Flavour import Expression @@ -37,11 +39,11 @@ verboseCommands = return False -- | Customise build progress messages (e.g. executing a build command). putBuild :: String -> Action () -putBuild = putColoured Dull Magenta +putBuild = putColoured cmdProgressColour Dull Magenta -- | Customise build success messages (e.g. a package is built successfully). putSuccess :: String -> Action () -putSuccess = putColoured Dull Green +putSuccess = putColoured cmdProgressColour Dull Green -- | Path to the GHC install destination. It is empty by default, which -- corresponds to the root of the file system. You can replace it by a specific From git at git.haskell.org Fri Oct 27 01:23:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export basic data type definitions from Base (4f0b5a1) Message-ID: <20171027012300.4075B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4f0b5a138391303ea7be0cd9bab49076ebc9d6a9/ghc >--------------------------------------------------------------- commit 4f0b5a138391303ea7be0cd9bab49076ebc9d6a9 Author: Andrey Mokhov Date: Sun Aug 13 03:20:46 2017 +0100 Re-export basic data type definitions from Base >--------------------------------------------------------------- 4f0b5a138391303ea7be0cd9bab49076ebc9d6a9 src/Base.hs | 29 +++++-- src/Builder.hs | 43 +-------- src/Context.hs | 10 ++- src/Expression.hs | 54 ++++++++---- src/Oracles/Dependencies.hs | 1 - src/Oracles/ModuleFiles.hs | 2 - src/Oracles/Setting.hs | 39 ++++++++- src/Package.hs | 41 ++++----- src/Rules/Cabal.hs | 1 - src/Rules/Clean.hs | 1 - src/Rules/Compile.hs | 2 - src/Rules/Configure.hs | 3 - src/Rules/Dependencies.hs | 3 +- src/Rules/Generate.hs | 2 - src/Rules/Gmp.hs | 5 -- src/Rules/Library.hs | 4 +- src/Rules/Perl.hs | 1 - src/Rules/Register.hs | 3 - src/Rules/Selftest.hs | 4 +- src/Rules/SourceDist.hs | 1 - src/Rules/Test.hs | 3 - src/Settings/Builders/Common.hs | 2 + src/Settings/Packages/Rts.hs | 2 - src/Settings/Path.hs | 188 ++++++++++++++++++++-------------------- src/Stage.hs | 10 +-- src/Target.hs | 2 +- src/UserSettings.hs | 2 +- src/Util.hs | 1 - src/Way.hs | 51 ++++------- 29 files changed, 252 insertions(+), 258 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 4f0b5a138391303ea7be0cd9bab49076ebc9d6a9 From git at git.haskell.org Fri Oct 27 01:23:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge Rules.Oracles into Rules (709ffb7) Message-ID: <20171027012303.BF6EC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/709ffb71d43a55e93a82577bd79b37d169b9754a/ghc >--------------------------------------------------------------- commit 709ffb71d43a55e93a82577bd79b37d169b9754a Author: Andrey Mokhov Date: Sun Aug 13 16:34:01 2017 +0100 Merge Rules.Oracles into Rules >--------------------------------------------------------------- 709ffb71d43a55e93a82577bd79b37d169b9754a hadrian.cabal | 1 - src/Base.hs | 0 src/Main.hs | 9 ++++----- src/Rules.hs | 30 ++++++++++++++++++++++++------ src/Rules/Oracles.hs | 21 --------------------- 5 files changed, 28 insertions(+), 33 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index c39df50..c964f3b 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -52,7 +52,6 @@ executable hadrian , Rules.Install , Rules.Libffi , Rules.Library - , Rules.Oracles , Rules.Perl , Rules.Program , Rules.Register diff --git a/src/Main.hs b/src/Main.hs index 0f65ecf..6843140 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -7,7 +7,6 @@ import qualified Environment import qualified Rules import qualified Rules.Clean import qualified Rules.Install -import qualified Rules.Oracles import qualified Rules.SourceDist import qualified Rules.Selftest import qualified Rules.Test @@ -23,14 +22,14 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do where rules :: Rules () rules = do + Rules.buildRules Rules.Clean.cleanRules - Rules.Oracles.oracleRules - Rules.SourceDist.sourceDistRules + Rules.Install.installRules + Rules.oracleRules Rules.Selftest.selftestRules + Rules.SourceDist.sourceDistRules Rules.Test.testRules - Rules.buildRules Rules.topLevelTargets - Rules.Install.installRules options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest diff --git a/src/Rules.hs b/src/Rules.hs index 359d3e9..335c4c3 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -1,10 +1,19 @@ -module Rules (topLevelTargets, packageTargets, buildRules) where +module Rules ( + buildRules, oracleRules, packageTargets, topLevelTargets + ) where + +import qualified Hadrian.Oracles.ArgsHash +import qualified Hadrian.Oracles.DirectoryContents +import qualified Hadrian.Oracles.KeyValue +import qualified Hadrian.Oracles.Path import Base import Context import Expression import Flavour import GHC +import qualified Oracles.Dependencies +import qualified Oracles.ModuleFiles import qualified Rules.Compile import qualified Rules.Data import qualified Rules.Dependencies @@ -18,9 +27,9 @@ import qualified Rules.Library import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register -import Oracles.Dependencies import Settings import Settings.Path +import Target allStages :: [Stage] allStages = [minBound ..] @@ -52,7 +61,7 @@ packageTargets stage pkg = do ways <- interpretInContext context getLibraryWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context $ buildHaddock flavour - more <- libraryTargets context + more <- Oracles.Dependencies.libraryTargets context return $ [ pkgSetupConfigFile context | nonCabalContext context ] ++ [ pkgHaddockFile context | docs && stage == Stage1 ] ++ libs ++ more @@ -102,8 +111,17 @@ buildRules = do packageRules Rules.Perl.perlScriptRules +oracleRules :: Rules () +oracleRules = do + Hadrian.Oracles.ArgsHash.argsHashOracle trackArgument getArgs + Hadrian.Oracles.DirectoryContents.directoryContentsOracle + Hadrian.Oracles.KeyValue.keyValueOracle + Hadrian.Oracles.Path.pathOracle + Oracles.Dependencies.dependenciesOracles + Oracles.ModuleFiles.moduleFilesOracle + programsStage1Only :: [Package] programsStage1Only = - [ deriveConstants, genprimopcode, hp2ps, runGhc - , ghcCabal, hpc, dllSplit, ghcPkg, hsc2hs - , genapply, ghc ] + [ deriveConstants, genprimopcode, hp2ps, runGhc + , ghcCabal, hpc, dllSplit, ghcPkg, hsc2hs + , genapply, ghc ] diff --git a/src/Rules/Oracles.hs b/src/Rules/Oracles.hs deleted file mode 100644 index 5f1f55e..0000000 --- a/src/Rules/Oracles.hs +++ /dev/null @@ -1,21 +0,0 @@ -module Rules.Oracles (oracleRules) where - -import qualified Hadrian.Oracles.ArgsHash -import qualified Hadrian.Oracles.DirectoryContents -import qualified Hadrian.Oracles.KeyValue -import qualified Hadrian.Oracles.Path - -import Base -import qualified Oracles.Dependencies -import qualified Oracles.ModuleFiles -import Target -import Settings - -oracleRules :: Rules () -oracleRules = do - Hadrian.Oracles.ArgsHash.argsHashOracle trackArgument getArgs - Hadrian.Oracles.DirectoryContents.directoryContentsOracle - Hadrian.Oracles.KeyValue.keyValueOracle - Hadrian.Oracles.Path.pathOracle - Oracles.Dependencies.dependenciesOracles - Oracles.ModuleFiles.moduleFilesOracle From git at git.haskell.org Fri Oct 27 01:23:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Extend KeyValue oracle to handle lists of values (1a0a80b) Message-ID: <20171027012307.41EBA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1a0a80ba27c1ab1a8fcf388c6e286705d860f6ab/ghc >--------------------------------------------------------------- commit 1a0a80ba27c1ab1a8fcf388c6e286705d860f6ab Author: Andrey Mokhov Date: Sun Aug 13 18:26:45 2017 +0100 Extend KeyValue oracle to handle lists of values >--------------------------------------------------------------- 1a0a80ba27c1ab1a8fcf388c6e286705d860f6ab src/Hadrian/Oracles/KeyValue.hs | 46 +++++++++++++++++++++++++++++++---------- src/Oracles/Dependencies.hs | 21 ++++--------------- src/Rules.hs | 1 - 3 files changed, 39 insertions(+), 29 deletions(-) diff --git a/src/Hadrian/Oracles/KeyValue.hs b/src/Hadrian/Oracles/KeyValue.hs index b58cfda..5155e3e 100644 --- a/src/Hadrian/Oracles/KeyValue.hs +++ b/src/Hadrian/Oracles/KeyValue.hs @@ -1,6 +1,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Hadrian.Oracles.KeyValue ( - lookupValue, lookupValueOrEmpty, lookupValueOrError, keyValueOracle + lookupValue, lookupValueOrEmpty, lookupValueOrError, + lookupValues, lookupValuesOrEmpty, lookupValuesOrError, keyValueOracle ) where import Control.Monad @@ -15,28 +16,51 @@ import Hadrian.Utilities newtype KeyValue = KeyValue (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) --- | Lookup a value in a key-value text file, tracking the result. +newtype KeyValues = KeyValues (FilePath, String) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) + +-- | Lookup a value in a text file, tracking the result. Each line of the file +-- is expected to have @key = value@ format. lookupValue :: FilePath -> String -> Action (Maybe String) lookupValue file key = askOracle $ KeyValue (file, key) --- | Lookup a value in a key-value text file, tracking the result. Return the --- empty string if the key is not found. +-- | Like 'lookupValue' but returns the empty string if the key is not found. lookupValueOrEmpty :: FilePath -> String -> Action String -lookupValueOrEmpty file key = fromMaybe "" <$> askOracle (KeyValue (file, key)) +lookupValueOrEmpty file key = fromMaybe "" <$> lookupValue file key --- | Lookup a value in a key-value text file, tracking the result. Raise an --- error if the key is not found. +-- | Like 'lookupValue' but raises an error if the key is not found. lookupValueOrError :: FilePath -> String -> Action String lookupValueOrError file key = (fromMaybe $ error msg) <$> lookupValue file key where msg = "Key " ++ quote key ++ " not found in file " ++ quote file --- | This oracle reads and parses text files consisting of key-value pairs --- @key = value@ and answers 'lookupValue' queries tracking the results. +-- | Lookup a list of values in a text file, tracking the result. Each line of +-- the file is expected to have @key value1 value2 ...@ format. +lookupValues :: FilePath -> String -> Action (Maybe [String]) +lookupValues file key = askOracle $ KeyValues (file, key) + +-- | Like 'lookupValues' but returns the empty list if the key is not found. +lookupValuesOrEmpty :: FilePath -> String -> Action [String] +lookupValuesOrEmpty file key = fromMaybe [] <$> lookupValues file key + +-- | Like 'lookupValues' but raises an error if the key is not found. +lookupValuesOrError :: FilePath -> String -> Action [String] +lookupValuesOrError file key = (fromMaybe $ error msg) <$> lookupValues file key + where + msg = "Key " ++ quote key ++ " not found in file " ++ quote file + +-- | This oracle reads and parses text files to answer 'lookupValue' and +-- 'lookupValues' queries, as well as their derivatives, tracking the results. keyValueOracle :: Rules () keyValueOracle = void $ do - cache <- newCache $ \file -> do + kv <- newCache $ \file -> do need [file] putLoud $ "Reading " ++ file ++ "..." liftIO $ readConfigFile file - addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> cache file + kvs <- newCache $ \file -> do + need [file] + putLoud $ "Reading " ++ file ++ "..." + contents <- map words <$> readFileLines file + return $ Map.fromList [ (key, values) | (key:values) <- contents ] + void $ addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> kv file + void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs index 748a5a2..6ed5633 100644 --- a/src/Oracles/Dependencies.hs +++ b/src/Oracles/Dependencies.hs @@ -1,10 +1,10 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, TupleSections #-} module Oracles.Dependencies ( fileDependencies, contextDependencies, libraryTargets, needLibrary, - dependenciesOracles, pkgDependencies, topsortPackages + pkgDependencies, topsortPackages ) where -import qualified Data.HashMap.Strict as Map +import Hadrian.Oracles.KeyValue import Base import Context @@ -14,9 +14,6 @@ import Settings import Settings.Builders.GhcCabal import Settings.Path -newtype Dependency = Dependency (FilePath, FilePath) - deriving (Binary, Eq, Hashable, NFData, Show, Typeable) - -- | 'Action' @fileDependencies context file@ looks up dependencies of a @file@ -- in a generated dependency file @path/.dependencies@, where @path@ is the build -- path of the given @context at . The action returns a pair @(source, files)@, @@ -25,7 +22,7 @@ newtype Dependency = Dependency (FilePath, FilePath) fileDependencies :: Context -> FilePath -> Action (FilePath, [FilePath]) fileDependencies context obj = do let path = buildPath context -/- ".dependencies" - deps <- askOracle $ Dependency (path, obj) + deps <- lookupValues path obj case deps of Nothing -> error $ "No dependencies found for file " ++ obj Just [] -> error $ "No source file found for file " ++ obj @@ -40,8 +37,7 @@ fileDependencies context obj = do contextDependencies :: Context -> Action [Context] contextDependencies context at Context {..} = do let pkgContext = \pkg -> Context (min stage Stage1) pkg way - unpack = fromMaybe . error $ "No dependencies for " ++ show context - deps <- unpack <$> askOracle (Dependency (packageDependencies, pkgNameString package)) + deps <- lookupValuesOrError packageDependencies (pkgNameString package) pkgs <- sort <$> interpretInContext (pkgContext package) getPackages return . map pkgContext $ intersectOrd (compare . pkgNameString) pkgs deps @@ -67,15 +63,6 @@ libraryTargets context = do needLibrary :: [Context] -> Action () needLibrary cs = need =<< concatMapM libraryTargets cs --- | Oracles for the package dependencies and 'path/dist/.dependencies' files. -dependenciesOracles :: Rules () -dependenciesOracles = do - deps <- newCache $ \file -> do - putLoud $ "Reading dependencies from " ++ file ++ "..." - contents <- map words <$> readFileLines file - return $ Map.fromList [ (key, values) | (key:values) <- contents ] - void $ addOracle $ \(Dependency (file, key)) -> Map.lookup key <$> deps file - -- | Topological sort of packages according to their dependencies. -- HACK (izgzhen): See https://github.com/snowleopard/hadrian/issues/344 for details topsortPackages :: [Package] -> Action [Package] diff --git a/src/Rules.hs b/src/Rules.hs index 335c4c3..2c09e94 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -117,7 +117,6 @@ oracleRules = do Hadrian.Oracles.DirectoryContents.directoryContentsOracle Hadrian.Oracles.KeyValue.keyValueOracle Hadrian.Oracles.Path.pathOracle - Oracles.Dependencies.dependenciesOracles Oracles.ModuleFiles.moduleFilesOracle programsStage1Only :: [Package] From git at git.haskell.org Fri Oct 27 01:23:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop Oracles.Dependencies moving code to the library and Utilities (former Util) (1df5491) Message-ID: <20171027012310.B6A1F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1df549134fdf286e374e5e3f1fef2944ea24f591/ghc >--------------------------------------------------------------- commit 1df549134fdf286e374e5e3f1fef2944ea24f591 Author: Andrey Mokhov Date: Sun Aug 13 23:20:18 2017 +0100 Drop Oracles.Dependencies moving code to the library and Utilities (former Util) >--------------------------------------------------------------- 1df549134fdf286e374e5e3f1fef2944ea24f591 hadrian.cabal | 6 +-- src/Hadrian/Oracles/KeyValue.hs | 16 +++++++- src/Oracles/Dependencies.hs | 79 --------------------------------------- src/Rules.hs | 4 +- src/Rules/Clean.hs | 2 +- src/Rules/Compile.hs | 7 ++-- src/Rules/Configure.hs | 2 +- src/Rules/Data.hs | 3 +- src/Rules/Dependencies.hs | 2 +- src/Rules/Documentation.hs | 2 +- src/Rules/Generate.hs | 2 +- src/Rules/Gmp.hs | 2 +- src/Rules/Install.hs | 3 +- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 3 +- src/Rules/Perl.hs | 2 +- src/Rules/Program.hs | 3 +- src/Rules/Register.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 2 +- src/Rules/Wrappers.hs | 2 +- src/Settings.hs | 8 +++- src/Settings/Builders/GhcCabal.hs | 9 +---- src/Settings/Packages/GhcCabal.hs | 2 +- src/{Util.hs => Utilities.hs} | 56 ++++++++++++++++++++++++++- 25 files changed, 103 insertions(+), 120 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1df549134fdf286e374e5e3f1fef2944ea24f591 From git at git.haskell.org Fri Oct 27 01:23:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make most extensions default, minor clean up (a56298f) Message-ID: <20171027012314.351613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a56298fb9cea9f3b4d5eebdefc3d3ddced239981/ghc >--------------------------------------------------------------- commit a56298fb9cea9f3b4d5eebdefc3d3ddced239981 Author: Andrey Mokhov Date: Sun Aug 13 23:30:16 2017 +0100 Make most extensions default, minor clean up >--------------------------------------------------------------- a56298fb9cea9f3b4d5eebdefc3d3ddced239981 hadrian.cabal | 10 +++++----- src/Builder.hs | 1 - src/Context.hs | 1 - src/Expression.hs | 1 - src/GHC.hs | 2 +- src/Hadrian/Expression.hs | 3 +-- src/Hadrian/Oracles/ArgsHash.hs | 1 - src/Hadrian/Oracles/DirectoryContents.hs | 1 - src/Hadrian/Oracles/KeyValue.hs | 1 - src/Hadrian/Oracles/Path.hs | 1 - src/Hadrian/Target.hs | 1 - src/Oracles/ModuleFiles.hs | 1 - src/Package.hs | 1 - src/Rules.hs | 4 +--- src/Rules/Install.hs | 1 - src/Rules/Library.hs | 2 +- src/Rules/Selftest.hs | 1 - src/Rules/Wrappers.hs | 4 ++-- src/Settings/Install.hs | 8 +++----- src/Stage.hs | 1 - 20 files changed, 14 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a56298fb9cea9f3b4d5eebdefc3d3ddced239981 From git at git.haskell.org Fri Oct 27 01:23:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add default extensions to .ghci (b4977a3) Message-ID: <20171027012317.9ADB83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b4977a3c7577cb135de38a20654878931e5814ea/ghc >--------------------------------------------------------------- commit b4977a3c7577cb135de38a20654878931e5814ea Author: Andrey Mokhov Date: Sun Aug 13 23:44:07 2017 +0100 Add default extensions to .ghci >--------------------------------------------------------------- b4977a3c7577cb135de38a20654878931e5814ea .ghci | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 9c0fe7a..8bb287b 100644 --- a/.ghci +++ b/.ghci @@ -1,2 +1,11 @@ -:set -Wall -fno-warn-name-shadowing -isrc -i../libraries/Cabal/Cabal -XRecordWildCards +:set -Wall -fno-warn-name-shadowing -isrc -i../libraries/Cabal/Cabal +:set -XDeriveFunctor +:set -XDeriveGeneric +:set -XFlexibleInstances +:set -XGeneralizedNewtypeDeriving +:set -XLambdaCase +:set -XRecordWildCards +:set -XScopedTypeVariables +:set -XTupleSections + :load Main From git at git.haskell.org Fri Oct 27 01:23:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up imports (0ef2b1f) Message-ID: <20171027012321.253003A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0ef2b1f8123ba90614c24d06a0a32bda0410334e/ghc >--------------------------------------------------------------- commit 0ef2b1f8123ba90614c24d06a0a32bda0410334e Author: Andrey Mokhov Date: Mon Aug 14 00:05:10 2017 +0100 Clean up imports >--------------------------------------------------------------- 0ef2b1f8123ba90614c24d06a0a32bda0410334e src/Expression.hs | 14 ++------------ src/Hadrian/Oracles/Path.hs | 1 - src/Oracles/PackageData.hs | 5 ++--- src/Oracles/Setting.hs | 1 - src/Rules.hs | 1 - src/Rules/Install.hs | 2 +- src/Rules/Selftest.hs | 1 - src/Settings.hs | 1 - src/Settings/Install.hs | 1 - src/Utilities.hs | 1 - 10 files changed, 5 insertions(+), 23 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 34a88fb..ca8862e 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -20,25 +20,15 @@ module Expression ( getInput, getOutput, -- * Re-exports - module Data.Semigroup, - module Builder, - module Package, - module Stage, - module Way + module Base ) where -import Control.Monad.Extra -import Data.Semigroup - import qualified Hadrian.Expression as H import Hadrian.Expression hiding (Expr, Predicate, Args) -import Builder +import Base import Context (Context, vanillaContext, stageContext, getStage, getPackage, getWay) -import Package -import Stage import Target hiding (builder, inputs, outputs) -import Way -- | @Expr a@ is a computation that produces a value of type @Action a@ and can -- read parameters of the current build 'Target'. diff --git a/src/Hadrian/Oracles/Path.hs b/src/Hadrian/Oracles/Path.hs index 2c578a1..d10948b 100644 --- a/src/Hadrian/Oracles/Path.hs +++ b/src/Hadrian/Oracles/Path.hs @@ -33,7 +33,6 @@ fixAbsolutePathOnWindows path = do else return path - newtype LookupInPath = LookupInPath String deriving (Binary, Eq, Hashable, NFData, Show, Typeable) diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index c813f82..208881d 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -2,10 +2,9 @@ module Oracles.PackageData ( PackageData (..), PackageDataList (..), pkgData, pkgDataList ) where -import Data.List -import Development.Shake import Hadrian.Oracles.KeyValue -import Hadrian.Utilities + +import Base data PackageData = BuildGhciLib FilePath | ComponentId FilePath diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 095dbaa..e9fe886 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -6,7 +6,6 @@ module Oracles.Setting ( topDirectory, relocatableBuild, installDocDir, installGhcLibDir, libsuf ) where -import Development.Shake import Hadrian.Expression import Hadrian.Oracles.KeyValue import Hadrian.Oracles.Path diff --git a/src/Rules.hs b/src/Rules.hs index 8a576d4..149789f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -5,7 +5,6 @@ import qualified Hadrian.Oracles.DirectoryContents import qualified Hadrian.Oracles.KeyValue import qualified Hadrian.Oracles.Path -import Base import Context import Expression import Flavour diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index edf2492..4b24ca2 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -5,7 +5,7 @@ import qualified System.Directory as IO import Base import Context -import Expression hiding (builder) +import Expression import GHC import Oracles.Setting import Rules diff --git a/src/Rules/Selftest.hs b/src/Rules/Selftest.hs index 0112d8f..3942753 100644 --- a/src/Rules/Selftest.hs +++ b/src/Rules/Selftest.hs @@ -1,7 +1,6 @@ {-# OPTIONS_GHC -fno-warn-orphans #-} module Rules.Selftest (selftestRules) where -import Development.Shake import Test.QuickCheck import Base diff --git a/src/Settings.hs b/src/Settings.hs index 7576e7a..e285175 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -9,7 +9,6 @@ module Settings ( import Hadrian.Oracles.KeyValue import Hadrian.Oracles.Path -import Base import Context import CmdLineFlag import Expression diff --git a/src/Settings/Install.hs b/src/Settings/Install.hs index 2d18a67..086cfa2 100644 --- a/src/Settings/Install.hs +++ b/src/Settings/Install.hs @@ -1,6 +1,5 @@ module Settings.Install (installPackageDbDirectory) where -import Base import Expression import UserSettings diff --git a/src/Utilities.hs b/src/Utilities.hs index 5356c11..07b34be 100644 --- a/src/Utilities.hs +++ b/src/Utilities.hs @@ -17,7 +17,6 @@ import Hadrian.Oracles.DirectoryContents import Hadrian.Oracles.KeyValue import Hadrian.Oracles.Path -import Base import CmdLineFlag import Context import Expression hiding (builder, inputs, outputs, way, stage, package) From git at git.haskell.org Fri Oct 27 01:23:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Provide more useful ToPredicate instances (db56cf4) Message-ID: <20171027012324.A8FB23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/db56cf4eaf15378c3023de4e66a1285376eb6599/ghc >--------------------------------------------------------------- commit db56cf4eaf15378c3023de4e66a1285376eb6599 Author: Andrey Mokhov Date: Mon Aug 14 23:07:05 2017 +0100 Provide more useful ToPredicate instances >--------------------------------------------------------------- db56cf4eaf15378c3023de4e66a1285376eb6599 src/Hadrian/Expression.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Hadrian/Expression.hs b/src/Hadrian/Expression.hs index dad9d32..b781cdd 100644 --- a/src/Hadrian/Expression.hs +++ b/src/Hadrian/Expression.hs @@ -75,14 +75,14 @@ p ? e = do bool <- toPredicate p if bool then e else mempty -instance (c ~ c', b ~ b') => ToPredicate (Predicate c b) c' b' where - toPredicate = id - instance ToPredicate Bool c b where toPredicate = pure -instance ToPredicate (Action Bool) c b where - toPredicate = expr +instance ToPredicate p c b => ToPredicate (Action p) c b where + toPredicate = toPredicate . expr + +instance (c ~ c', b ~ b', ToPredicate p c' b') => ToPredicate (Expr c b p) c' b' where + toPredicate p = toPredicate =<< p -- | Interpret a given expression according to the given 'Target'. interpret :: Target c b -> Expr c b a -> Action a From git at git.haskell.org Fri Oct 27 01:23:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor command line arguments and flavours (0530e0d) Message-ID: <20171027012328.245163A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0530e0df5b9076b1643a2d3b6a4abf4f31041f3c/ghc >--------------------------------------------------------------- commit 0530e0df5b9076b1643a2d3b6a4abf4f31041f3c Author: Andrey Mokhov Date: Mon Aug 14 23:12:52 2017 +0100 Refactor command line arguments and flavours * Get rid of unsafePerformIO using shakeExtra * Move diagnostic info utilities to the library See #347 >--------------------------------------------------------------- 0530e0df5b9076b1643a2d3b6a4abf4f31041f3c hadrian.cabal | 2 +- src/CmdLineFlag.hs | 128 ------------------------------ src/CommandLine.hs | 128 ++++++++++++++++++++++++++++++ src/Flavour.hs | 24 +++--- src/Hadrian/Utilities.hs | 160 ++++++++++++++++++++++++++++++++++++-- src/Main.hs | 58 ++++++++------ src/Rules.hs | 9 +-- src/Rules/Cabal.hs | 1 - src/Rules/Configure.hs | 9 ++- src/Rules/Data.hs | 1 - src/Rules/Documentation.hs | 3 +- src/Rules/Generate.hs | 18 +++-- src/Rules/Gmp.hs | 1 - src/Rules/Install.hs | 6 +- src/Rules/Library.hs | 3 +- src/Rules/Program.hs | 18 +++-- src/Rules/Register.hs | 1 - src/Rules/Selftest.hs | 1 - src/Rules/SourceDist.hs | 1 - src/Rules/Test.hs | 3 +- src/Settings.hs | 40 +++++----- src/Settings/Builders/Ghc.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 7 +- src/Settings/Default.hs | 18 +++-- src/Settings/Packages/Base.hs | 8 +- src/Settings/Packages/Compiler.hs | 4 +- src/UserSettings.hs | 20 +++-- src/Utilities.hs | 131 ++++++------------------------- 28 files changed, 443 insertions(+), 365 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 0530e0df5b9076b1643a2d3b6a4abf4f31041f3c From git at git.haskell.org Fri Oct 27 01:23:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move file system operations to the library (58e2d05) Message-ID: <20171027012331.951EB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/58e2d05064d8102914c7b887df6e2090c1d906db/ghc >--------------------------------------------------------------- commit 58e2d05064d8102914c7b887df6e2090c1d906db Author: Andrey Mokhov Date: Tue Aug 15 00:31:47 2017 +0100 Move file system operations to the library See #347 >--------------------------------------------------------------- 58e2d05064d8102914c7b887df6e2090c1d906db src/Hadrian/Oracles/DirectoryContents.hs | 17 +++++- src/Hadrian/Oracles/Path.hs | 6 +- src/Hadrian/Utilities.hs | 96 ++++++++++++++++++++++++++++--- src/Rules/Clean.hs | 1 - src/Rules/Wrappers.hs | 3 +- src/Utilities.hs | 97 ++------------------------------ 6 files changed, 112 insertions(+), 108 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 58e2d05064d8102914c7b887df6e2090c1d906db From git at git.haskell.org Fri Oct 27 01:23:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix compile error on GHC 8.2+ (5026b9c) Message-ID: <20171027012335.012F53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5026b9c6f145f748e0e8b1621e3af482c475b00d/ghc >--------------------------------------------------------------- commit 5026b9c6f145f748e0e8b1621e3af482c475b00d Author: Andrey Mokhov Date: Tue Aug 15 00:44:24 2017 +0100 Fix compile error on GHC 8.2+ >--------------------------------------------------------------- 5026b9c6f145f748e0e8b1621e3af482c475b00d src/CommandLine.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index 18ce2ec..dbcf41f 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -3,10 +3,11 @@ module CommandLine ( cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects ) where -import Data.Dynamic +import Data.Dynamic (Dynamic) import Data.Either import qualified Data.HashMap.Strict as Map import Data.List.Extra +import Data.Typeable (TypeRep) import Development.Shake hiding (Normal) import Hadrian.Utilities import System.Console.GetOpt From git at git.haskell.org Fri Oct 27 01:23:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Re-export Dynamic and Typeable bits (d2ca01b) Message-ID: <20171027012338.6DBA73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2ca01bbdf7354c0e88af711696ac333040d2374/ghc >--------------------------------------------------------------- commit d2ca01bbdf7354c0e88af711696ac333040d2374 Author: Andrey Mokhov Date: Tue Aug 15 02:11:02 2017 +0100 Re-export Dynamic and Typeable bits >--------------------------------------------------------------- d2ca01bbdf7354c0e88af711696ac333040d2374 src/CommandLine.hs | 2 -- src/Hadrian/Utilities.hs | 5 ++++- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index dbcf41f..5688d6f 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -3,11 +3,9 @@ module CommandLine ( cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects ) where -import Data.Dynamic (Dynamic) import Data.Either import qualified Data.HashMap.Strict as Map import Data.List.Extra -import Data.Typeable (TypeRep) import Development.Shake hiding (Normal) import Hadrian.Utilities import System.Console.GetOpt diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 0791d44..74c10b4 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -19,7 +19,10 @@ module Hadrian.Utilities ( UseColour (..), putColoured, BuildProgressColour (..), putBuild, SuccessColour (..), putSuccess, ProgressInfo (..), putProgressInfo, renderAction, renderProgram, renderLibrary, renderBox, - renderUnicorn + renderUnicorn, + + -- * Useful re-exports + Dynamic, fromDynamic, toDyn, TypeRep, typeOf ) where import Control.Monad.Extra From git at git.haskell.org Fri Oct 27 01:23:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move need of inplaceLibCopyTargets to top-level (#388) (0c67f7d) Message-ID: <20171027012341.ED21B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0c67f7d21536a4ca305758516bce7ccd0f40db7b/ghc >--------------------------------------------------------------- commit 0c67f7d21536a4ca305758516bce7ccd0f40db7b Author: Zhen Zhang Date: Tue Aug 15 20:34:32 2017 +0800 Move need of inplaceLibCopyTargets to top-level (#388) >--------------------------------------------------------------- 0c67f7d21536a4ca305758516bce7ccd0f40db7b src/Rules.hs | 12 +++++++----- src/Rules/Program.hs | 5 ++--- 2 files changed, 9 insertions(+), 8 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index d55a578..4077dc6 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -24,7 +24,8 @@ import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings -import Settings.Path +import Settings.Path (inplaceLibCopyTargets, pkgLibraryFile, + pkgSetupConfigFile, pkgHaddockFile) import Target import Utilities @@ -41,10 +42,11 @@ topLevelTargets = action $ do libs <- concatForM [Stage0, Stage1] $ \stage -> concatForM libraryPackages $ packageTargets stage prgs <- concatForM programsStage1Only $ packageTargets Stage0 - return $ libs ++ prgs - else - concatForM allStages $ \stage -> - concatForM (knownPackages \\ [rts, libffi]) $ packageTargets stage + return $ libs ++ prgs ++ inplaceLibCopyTargets + else do + targets <- concatForM allStages $ \stage -> + concatForM (knownPackages \\ [rts, libffi]) $ packageTargets stage + return $ targets ++ inplaceLibCopyTargets -- | Return the list of targets associated with a given 'Stage' and 'Package'. packageTargets :: Stage -> Package -> Action [FilePath] diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 6ca514f..edef17f 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -11,7 +11,8 @@ import Oracles.PackageData import Oracles.Setting import Rules.Wrappers import Settings -import Settings.Path +import Settings.Path (buildPath, inplaceLibBinPath, rtsContext, objectPath, + inplaceLibPath, inplaceBinPath) import Target import Utilities @@ -26,8 +27,6 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do context' <- programContext stage package buildBinaryAndWrapper rs context' bin - when (package == ghc) $ want inplaceLibCopyTargets - -- Rules for programs built in install directories when (stage == Stage0 || package == ghc) $ do -- Some binaries in inplace/bin are wrapped From git at git.haskell.org Fri Oct 27 01:23:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Major refactoring of path settings (9b70568) Message-ID: <20171027012345.88B5F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9b70568615e2763ff782279be28286373b59d8ff/ghc >--------------------------------------------------------------- commit 9b70568615e2763ff782279be28286373b59d8ff Author: Andrey Mokhov Date: Wed Aug 16 03:45:51 2017 +0100 Major refactoring of path settings * Move buildRoot into the Action monad, so it can be configured from command line in future * Move settings from Setting.Path to Base and Context * Simplify build rule matching and prepare to factoring out common build rules into the library, #347 >--------------------------------------------------------------- 9b70568615e2763ff782279be28286373b59d8ff hadrian.cabal | 2 - src/Base.hs | 76 +++++++++- src/Context.hs | 101 ++++++++++++- src/Expression.hs | 6 +- src/GHC.hs | 70 ++++++++- src/Hadrian/Expression.hs | 6 +- src/Hadrian/Utilities.hs | 64 ++++---- src/Main.hs | 9 +- src/Oracles/ModuleFiles.hs | 32 ++-- src/Rules.hs | 15 +- src/Rules/Cabal.hs | 9 +- src/Rules/Clean.hs | 10 +- src/Rules/Compile.hs | 24 +-- src/Rules/Data.hs | 36 +++-- src/Rules/Dependencies.hs | 3 +- src/Rules/Documentation.hs | 45 +++--- src/Rules/Generate.hs | 100 +++++++------ src/Rules/Gmp.hs | 77 ++++++---- src/Rules/Install.hs | 36 +++-- src/Rules/Libffi.hs | 60 +++++--- src/Rules/Library.hs | 26 ++-- src/Rules/Program.hs | 8 +- src/Rules/Register.hs | 47 ++++-- src/Rules/Selftest.hs | 17 --- src/Rules/Test.hs | 1 - src/Rules/Wrappers.hs | 41 +++--- src/Settings.hs | 19 +-- src/Settings/Builders/Common.hs | 17 ++- src/Settings/Builders/Configure.hs | 34 +++-- src/Settings/Builders/DeriveConstants.hs | 21 +-- src/Settings/Builders/Ghc.hs | 12 +- src/Settings/Builders/GhcCabal.hs | 21 ++- src/Settings/Builders/GhcPkg.hs | 4 +- src/Settings/Builders/Haddock.hs | 11 +- src/Settings/Builders/HsCpp.hs | 8 +- src/Settings/Builders/Hsc2Hs.hs | 5 +- src/Settings/Builders/Make.hs | 10 +- src/Settings/Install.hs | 11 -- src/Settings/Packages/Ghc.hs | 9 +- src/Settings/Packages/IntegerGmp.hs | 7 +- src/Settings/Packages/Rts.hs | 8 +- src/Settings/Path.hs | 245 ------------------------------- src/UserSettings.hs | 8 +- src/Utilities.hs | 14 +- 44 files changed, 733 insertions(+), 652 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 9b70568615e2763ff782279be28286373b59d8ff From git at git.haskell.org Fri Oct 27 01:23:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix merge conflicts (1ade885) Message-ID: <20171027012349.0E9C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1ade88547a2c3256c6b6e6de8c546a04dc1ae1d3/ghc >--------------------------------------------------------------- commit 1ade88547a2c3256c6b6e6de8c546a04dc1ae1d3 Merge: 9b70568 0c67f7d Author: Andrey Mokhov Date: Wed Aug 16 03:47:39 2017 +0100 Fix merge conflicts >--------------------------------------------------------------- 1ade88547a2c3256c6b6e6de8c546a04dc1ae1d3 src/Rules.hs | 9 +++++---- src/Rules/Program.hs | 2 -- 2 files changed, 5 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Oct 27 01:23:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (7792fbb) Message-ID: <20171027012352.9D12B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7792fbbebbb68f8f2b2e95d29a6365f74376b398/ghc >--------------------------------------------------------------- commit 7792fbbebbb68f8f2b2e95d29a6365f74376b398 Author: Andrey Mokhov Date: Wed Aug 16 13:33:16 2017 +0100 Minor revision >--------------------------------------------------------------- 7792fbbebbb68f8f2b2e95d29a6365f74376b398 src/Expression.hs | 13 +++++++++++-- src/GHC.hs | 6 +++++- src/Settings.hs | 13 ------------- 3 files changed, 16 insertions(+), 16 deletions(-) diff --git a/src/Expression.hs b/src/Expression.hs index 8da4a6f..647c057 100644 --- a/src/Expression.hs +++ b/src/Expression.hs @@ -16,8 +16,8 @@ module Expression ( Context, vanillaContext, stageContext, Target, -- * Convenient accessors - getBuildRoot, getBuildPath, getContext, getStage, getPackage, getBuilder, - getOutputs, getInputs, getWay, getInput, getOutput, + getBuildRoot, getBuildPath, getContext, getPkgData, getPkgDataList, getStage, + getPackage, getBuilder, getOutputs, getInputs, getWay, getInput, getOutput, -- * Re-exports module Base @@ -28,6 +28,7 @@ import Hadrian.Expression hiding (Expr, Predicate, Args) import Base import Context (Context, vanillaContext, stageContext, getBuildPath, getStage, getPackage, getWay) +import Oracles.PackageData import Target hiding (builder, inputs, outputs) -- | @Expr a@ is a computation that produces a value of type @Action a@ and can @@ -42,6 +43,14 @@ type Args = H.Args Context Builder type Packages = Expr [Package] type Ways = Expr [Way] +-- | Get a value from the @package-data.mk@ file of the current context. +getPkgData :: (FilePath -> PackageData) -> Expr String +getPkgData key = expr . pkgData . key =<< getBuildPath + +-- | Get a list of values from the @package-data.mk@ file of the current context. +getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] +getPkgDataList key = expr . pkgDataList . key =<< getBuildPath + -- | Is the build currently in the provided stage? stage :: Stage -> Predicate stage s = (s ==) <$> getStage diff --git a/src/GHC.hs b/src/GHC.hs index 6d49630..1141030 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -18,7 +18,7 @@ module GHC ( rtsContext, rtsBuildPath, rtsConfIn, -- * Miscellaneous - ghcSplitPath, stripCmdPath, inplaceInstallPath + ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 ) where import Base @@ -192,3 +192,7 @@ rtsBuildPath = buildPath rtsContext rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" +buildDll0 :: Context -> Action Bool +buildDll0 Context {..} = do + windows <- windowsHost + return $ windows && stage == Stage1 && package == compiler diff --git a/src/Settings.hs b/src/Settings.hs index 2b4b0ef..f25265b 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -13,8 +13,6 @@ import CommandLine import Expression import Flavour import GHC -import Oracles.PackageData -import Oracles.Setting import {-# SOURCE #-} Settings.Default import Settings.Flavours.Development import Settings.Flavours.Performance @@ -38,12 +36,6 @@ getPackages = expr flavour >>= packages stagePackages :: Stage -> Action [Package] stagePackages stage = interpretInContext (stageContext stage) getPackages -getPkgData :: (FilePath -> PackageData) -> Expr String -getPkgData key = expr . pkgData . key =<< getBuildPath - -getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String] -getPkgDataList key = expr . pkgDataList . key =<< getBuildPath - hadrianFlavours :: [Flavour] hadrianFlavours = [ defaultFlavour, developmentFlavour Stage1, developmentFlavour Stage2 @@ -154,8 +146,3 @@ stage1Only = defaultStage1Only -- | Install's DESTDIR setting. destDir :: FilePath destDir = defaultDestDir - -buildDll0 :: Context -> Action Bool -buildDll0 Context {..} = do - windows <- windowsHost - return $ windows && stage == Stage1 && package == compiler From git at git.haskell.org Fri Oct 27 01:23:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move systemBuilderPath to GHC (8fc676e) Message-ID: <20171027012356.388D83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8fc676e400d02448dea520c0977d64c140b1a560/ghc >--------------------------------------------------------------- commit 8fc676e400d02448dea520c0977d64c140b1a560 Author: Andrey Mokhov Date: Wed Aug 16 15:24:08 2017 +0100 Move systemBuilderPath to GHC >--------------------------------------------------------------- 8fc676e400d02448dea520c0977d64c140b1a560 src/GHC.hs | 42 +++++++++++++++++++++++++++++++++++++++++- src/Settings.hs | 39 --------------------------------------- 2 files changed, 41 insertions(+), 40 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 1141030..2210889 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -18,9 +18,12 @@ module GHC ( rtsContext, rtsBuildPath, rtsConfIn, -- * Miscellaneous - ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 + systemBuilderPath, ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 ) where +import Hadrian.Oracles.KeyValue +import Hadrian.Oracles.Path + import Base import Context import Oracles.Setting @@ -118,6 +121,43 @@ builderProvenance = \case where context s p = Just $ vanillaContext s p +-- | Determine the location of a system 'Builder'. +systemBuilderPath :: Builder -> Action FilePath +systemBuilderPath builder = case builder of + Alex -> fromKey "alex" + Ar Stage0 -> fromKey "system-ar" + Ar _ -> fromKey "ar" + Cc _ Stage0 -> fromKey "system-cc" + Cc _ _ -> fromKey "cc" + -- We can't ask configure for the path to configure! + Configure _ -> return "sh configure" + Ghc _ Stage0 -> fromKey "system-ghc" + GhcPkg _ Stage0 -> fromKey "system-ghc-pkg" + Happy -> fromKey "happy" + HsColour -> fromKey "hscolour" + HsCpp -> fromKey "hs-cpp" + Ld -> fromKey "ld" + Make _ -> fromKey "make" + Nm -> fromKey "nm" + Objdump -> fromKey "objdump" + Patch -> fromKey "patch" + Perl -> fromKey "perl" + Ranlib -> fromKey "ranlib" + Tar -> fromKey "tar" + _ -> error $ "No entry for " ++ show builder ++ inCfg + where + inCfg = " in " ++ quote configFile ++ " file." + fromKey key = do + let unpack = fromMaybe . error $ "Cannot find path to builder " + ++ quote key ++ inCfg ++ " Did you skip configure?" + path <- unpack <$> lookupValue configFile key + if null path + then do + unless (isOptional builder) . error $ "Non optional builder " + ++ quote key ++ " is not specified" ++ inCfg + return "" -- TODO: Use a safe interface. + else fixAbsolutePathOnWindows =<< lookupInPath path + -- | Given a 'Context', compute the name of the program that is built in it -- assuming that the corresponding package's type is 'Program'. For example, GHC -- built in 'Stage0' is called @ghc-stage1 at . If the given package is a diff --git a/src/Settings.hs b/src/Settings.hs index f25265b..fdce8a7 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -5,9 +5,6 @@ module Settings ( programContext, integerLibraryName, destDir, stage1Only, buildDll0 ) where -import Hadrian.Oracles.KeyValue -import Hadrian.Oracles.Path - import Context import CommandLine import Expression @@ -68,42 +65,6 @@ knownPackages = sort $ defaultKnownPackages ++ userKnownPackages findKnownPackage :: PackageName -> Maybe Package findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages --- | Determine the location of a system 'Builder'. -systemBuilderPath :: Builder -> Action FilePath -systemBuilderPath builder = case builder of - Alex -> fromKey "alex" - Ar Stage0 -> fromKey "system-ar" - Ar _ -> fromKey "ar" - Cc _ Stage0 -> fromKey "system-cc" - Cc _ _ -> fromKey "cc" - -- We can't ask configure for the path to configure! - Configure _ -> return "sh configure" - Ghc _ Stage0 -> fromKey "system-ghc" - GhcPkg _ Stage0 -> fromKey "system-ghc-pkg" - Happy -> fromKey "happy" - HsColour -> fromKey "hscolour" - HsCpp -> fromKey "hs-cpp" - Ld -> fromKey "ld" - Make _ -> fromKey "make" - Nm -> fromKey "nm" - Objdump -> fromKey "objdump" - Patch -> fromKey "patch" - Perl -> fromKey "perl" - Ranlib -> fromKey "ranlib" - Tar -> fromKey "tar" - _ -> error $ "No system.config entry for " ++ show builder - where - fromKey key = do - let unpack = fromMaybe . error $ "Cannot find path to builder " - ++ quote key ++ " in system.config file. Did you skip configure?" - path <- unpack <$> lookupValue configFile key - if null path - then do - unless (isOptional builder) . error $ "Non optional builder " - ++ quote key ++ " is not specified in system.config file." - return "" -- TODO: Use a safe interface. - else fixAbsolutePathOnWindows =<< lookupInPath path - -- | Determine the location of a 'Builder'. builderPath :: Builder -> Action FilePath builderPath builder = case builderProvenance builder of From git at git.haskell.org Fri Oct 27 01:23:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:23:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out cabal parsing functionality into the library (4a46d14) Message-ID: <20171027012359.ADDA93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4a46d14ec3631672d2a3733c45f0aa61eb861eab/ghc >--------------------------------------------------------------- commit 4a46d14ec3631672d2a3733c45f0aa61eb861eab Author: Andrey Mokhov Date: Wed Aug 16 22:18:45 2017 +0100 Factor out cabal parsing functionality into the library See #347 >--------------------------------------------------------------- 4a46d14ec3631672d2a3733c45f0aa61eb861eab hadrian.cabal | 1 + src/Hadrian/Haskell/Cabal.hs | 38 ++++++++++++++++++++++++++++++++++++++ src/Rules/Cabal.hs | 31 ++++++------------------------- src/Settings/Packages/GhcCabal.hs | 13 ++----------- 4 files changed, 47 insertions(+), 36 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 8ad971f..1520881 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -27,6 +27,7 @@ executable hadrian , Flavour , GHC , Hadrian.Expression + , Hadrian.Haskell.Cabal , Hadrian.Oracles.ArgsHash , Hadrian.Oracles.DirectoryContents , Hadrian.Oracles.KeyValue diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs new file mode 100644 index 0000000..b8f874c --- /dev/null +++ b/src/Hadrian/Haskell/Cabal.hs @@ -0,0 +1,38 @@ +module Hadrian.Haskell.Cabal (readCabal, cabalNameVersion, cabalDependencies) where + +import Development.Shake +import Distribution.Package +import Distribution.PackageDescription +import Distribution.PackageDescription.Parse +import Distribution.Text +import Distribution.Types.CondTree +import Distribution.Verbosity + +-- TODO: Track the values? + +-- | Read a given @.cabal@ file and return the 'GenericPackageDescription'. +readCabal :: FilePath -> Action GenericPackageDescription +readCabal cabal = do + need [cabal] + liftIO $ readGenericPackageDescription silent cabal + +-- | Read a given @.cabal@ file and return the package name and version. +cabalNameVersion :: FilePath -> Action (String, String) +cabalNameVersion cabal = do + identifier <- package . packageDescription <$> readCabal cabal + return (unPackageName $ pkgName identifier, display $ pkgVersion identifier) + +-- | Read a given @.cabal@ file and return the package dependencies. +cabalDependencies :: FilePath -> Action [String] +cabalDependencies cabal = do + gpd <- readCabal cabal + let depsLib = collectDeps $ condLibrary gpd + depsExes = map (collectDeps . Just . snd) $ condExecutables gpd + deps = concat $ depsLib : depsExes + return $ [ unPackageName name | Dependency name _ <- deps ] + +collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] +collectDeps Nothing = [] +collectDeps (Just (CondNode _ deps ifs)) = deps ++ concatMap f ifs + where + f (CondBranch _ t mt) = collectDeps (Just t) ++ collectDeps mt diff --git a/src/Rules/Cabal.hs b/src/Rules/Cabal.hs index a9a9b51..ab8c6f9 100644 --- a/src/Rules/Cabal.hs +++ b/src/Rules/Cabal.hs @@ -1,11 +1,6 @@ module Rules.Cabal (cabalRules) where -import Distribution.Package as DP -import Distribution.PackageDescription -import Distribution.PackageDescription.Parse -import Distribution.Text -import Distribution.Types.CondTree -import Distribution.Verbosity +import Hadrian.Haskell.Cabal import Base import GHC @@ -18,32 +13,18 @@ cabalRules = do bootPkgs <- stagePackages Stage0 let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- forM (sort pkgs) $ \pkg -> do - need [pkgCabalFile pkg] - pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg - let identifier = package . packageDescription $ pd - version = display . pkgVersion $ identifier - return $ unPackageName (DP.pkgName identifier) ++ " == " ++ version + (name, version) <- cabalNameVersion (pkgCabalFile pkg) + return $ name ++ " == " ++ version writeFileChanged out . unlines $ constraints putSuccess $ "| Successfully generated boot package constraints" -- Cache package dependencies. "//" -/- packageDependencies %> \out -> do pkgDeps <- forM (sort knownPackages) $ \pkg -> do - exists <- doesFileExist $ pkgCabalFile pkg + exists <- doesFileExist (pkgCabalFile pkg) if not exists then return $ pkgNameString pkg else do - need [pkgCabalFile pkg] - pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile pkg - let depsLib = collectDeps $ condLibrary pd - depsExes = map (collectDeps . Just . snd) $ condExecutables pd - deps = concat $ depsLib : depsExes - depNames = [ unPackageName name | Dependency name _ <- deps ] - return . unwords $ pkgNameString pkg : (sort depNames \\ [pkgNameString pkg]) + deps <- sort <$> cabalDependencies (pkgCabalFile pkg) + return . unwords $ pkgNameString pkg : (deps \\ [pkgNameString pkg]) writeFileChanged out $ unlines pkgDeps putSuccess $ "| Successfully generated package dependencies" - -collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] -collectDeps Nothing = [] -collectDeps (Just (CondNode _ deps ifs)) = deps ++ concatMap f ifs - where - f (CondBranch _ t mt) = collectDeps (Just t) ++ collectDeps mt diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index c7b82ca..79e92c7 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -1,11 +1,6 @@ module Settings.Packages.GhcCabal (ghcCabalPackageArgs) where -import Distribution.Package (pkgVersion) -import Distribution.PackageDescription (packageDescription) -import Distribution.PackageDescription.Parse -import qualified Distribution.PackageDescription as DP -import Distribution.Text (display) -import Distribution.Verbosity (silent) +import Hadrian.Haskell.Cabal import Base import Expression @@ -15,11 +10,7 @@ import Utilities ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do cabalDeps <- expr $ pkgDependencies cabal - expr $ need [pkgCabalFile cabal] - pd <- exprIO . readGenericPackageDescription silent $ pkgCabalFile cabal - let identifier = DP.package . packageDescription $ pd - cabalVersion = display . pkgVersion $ identifier - + (_, cabalVersion) <- expr $ cabalNameVersion (pkgCabalFile cabal) mconcat [ pure [ "-package " ++ pkgNameString pkg | pkg <- cabalDeps ] , arg "--make" From git at git.haskell.org Fri Oct 27 01:24:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to MIT license (46a0061) Message-ID: <20171027012403.401FE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46a00614fc68bd489f0d21391ceadf85abf3dae3/ghc >--------------------------------------------------------------- commit 46a00614fc68bd489f0d21391ceadf85abf3dae3 Author: Andrey Mokhov Date: Wed Aug 16 23:04:59 2017 +0100 Switch to MIT license >--------------------------------------------------------------- 46a00614fc68bd489f0d21391ceadf85abf3dae3 LICENSE | 42 +++++++++++++++++------------------------- 1 file changed, 17 insertions(+), 25 deletions(-) diff --git a/LICENSE b/LICENSE index fbedb41..ff60fa8 100644 --- a/LICENSE +++ b/LICENSE @@ -1,29 +1,21 @@ -BSD License +MIT License -Copyright (c) 2014, Andrey Mokhov -All rights reserved. +Copyright (c) 2014-2017 Andrey Mokhov -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are met: +Permission is hereby granted, free of charge, to any person obtaining a copy +of this software and associated documentation files (the "Software"), to deal +in the Software without restriction, including without limitation the rights +to use, copy, modify, merge, publish, distribute, sublicense, and/or sell +copies of the Software, and to permit persons to whom the Software is +furnished to do so, subject to the following conditions: -* Redistributions of source code must retain the above copyright notice, this - list of conditions and the following disclaimer. +The above copyright notice and this permission notice shall be included in all +copies or substantial portions of the Software. -* Redistributions in binary form must reproduce the above copyright notice, - this list of conditions and the following disclaimer in the documentation - and/or other materials provided with the distribution. - -* Neither the name of the Hadrian project nor the names of its - contributors may be used to endorse or promote products derived from - this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" -AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE -IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE -DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE -FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL -DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR -SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER -CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, -OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR +IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, +FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE +AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER +LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, +OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE +SOFTWARE. From git at git.haskell.org Fri Oct 27 01:24:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:06 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add docs, minor revision (b85602d) Message-ID: <20171027012406.AC5A73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b85602dc64ccb927839a2368b9636e2bd91cd232/ghc >--------------------------------------------------------------- commit b85602dc64ccb927839a2368b9636e2bd91cd232 Author: Andrey Mokhov Date: Wed Aug 16 23:15:34 2017 +0100 Add docs, minor revision >--------------------------------------------------------------- b85602dc64ccb927839a2368b9636e2bd91cd232 src/Hadrian/Haskell/Cabal.hs | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs index b8f874c..d579de6 100644 --- a/src/Hadrian/Haskell/Cabal.hs +++ b/src/Hadrian/Haskell/Cabal.hs @@ -1,3 +1,14 @@ +----------------------------------------------------------------------------- +-- | +-- Module : Hadrian.Haskell.Cabal +-- Copyright : (c) Andrey Mokhov 2014-2017 +-- License : MIT (see the file LICENSE) +-- Maintainer : andrey.mokhov at gmail.com +-- Stability : experimental +-- +-- Basic functionality for extracting Haskell package metadata stored in +-- @.cabal@ files. +----------------------------------------------------------------------------- module Hadrian.Haskell.Cabal (readCabal, cabalNameVersion, cabalDependencies) where import Development.Shake @@ -8,28 +19,28 @@ import Distribution.Text import Distribution.Types.CondTree import Distribution.Verbosity --- TODO: Track the values? - --- | Read a given @.cabal@ file and return the 'GenericPackageDescription'. +-- | Read a given @.cabal@ file and return the 'GenericPackageDescription'. The +-- @.cabal@ file is tracked. readCabal :: FilePath -> Action GenericPackageDescription readCabal cabal = do need [cabal] liftIO $ readGenericPackageDescription silent cabal --- | Read a given @.cabal@ file and return the package name and version. +-- | Read a given @.cabal@ file and return the package name and version. The +-- @.cabal@ file is tracked. cabalNameVersion :: FilePath -> Action (String, String) cabalNameVersion cabal = do identifier <- package . packageDescription <$> readCabal cabal return (unPackageName $ pkgName identifier, display $ pkgVersion identifier) --- | Read a given @.cabal@ file and return the package dependencies. +-- | Read a given @.cabal@ file and return the package dependencies. The +-- @.cabal@ file is tracked. cabalDependencies :: FilePath -> Action [String] cabalDependencies cabal = do gpd <- readCabal cabal - let depsLib = collectDeps $ condLibrary gpd - depsExes = map (collectDeps . Just . snd) $ condExecutables gpd - deps = concat $ depsLib : depsExes - return $ [ unPackageName name | Dependency name _ <- deps ] + let libDeps = collectDeps (condLibrary gpd) + exeDeps = map (collectDeps . Just . snd) (condExecutables gpd) + return [ unPackageName p | Dependency p _ <- concat (libDeps : exeDeps) ] collectDeps :: Maybe (CondTree v [Dependency] a) -> [Dependency] collectDeps Nothing = [] From git at git.haskell.org Fri Oct 27 01:24:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out file cache functionality into the library (4fca3ae) Message-ID: <20171027012410.38EA13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4fca3ae5301a19abc621dc8ec08051c4b2a954ac/ghc >--------------------------------------------------------------- commit 4fca3ae5301a19abc621dc8ec08051c4b2a954ac Author: Andrey Mokhov Date: Thu Aug 17 02:16:45 2017 +0100 Factor out file cache functionality into the library See #347 >--------------------------------------------------------------- 4fca3ae5301a19abc621dc8ec08051c4b2a954ac hadrian.cabal | 2 +- src/Base.hs | 6 ++--- src/Hadrian/Oracles/FileCache.hs | 49 +++++++++++++++++++++++++++++++++++++++ src/Rules.hs | 19 ++++++++------- src/Rules/Cabal.hs | 30 ------------------------ src/Settings/Builders/GhcCabal.hs | 17 ++++++++++++-- src/Utilities.hs | 17 ++++++++++++-- 7 files changed, 93 insertions(+), 47 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 4fca3ae5301a19abc621dc8ec08051c4b2a954ac From git at git.haskell.org Fri Oct 27 01:24:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:13 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix overlapping build rules and generalise the pattern (e815c5f) Message-ID: <20171027012413.A73553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e815c5f5100fa218415e19ea9a577c5428f8ec0a/ghc >--------------------------------------------------------------- commit e815c5f5100fa218415e19ea9a577c5428f8ec0a Author: Andrey Mokhov Date: Thu Aug 17 19:59:54 2017 +0100 Fix overlapping build rules and generalise the pattern See #391 >--------------------------------------------------------------- e815c5f5100fa218415e19ea9a577c5428f8ec0a src/Hadrian/Utilities.hs | 11 ++++++++++- src/Rules/Library.hs | 2 +- src/Rules/Register.hs | 10 ++++------ 3 files changed, 15 insertions(+), 8 deletions(-) diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 3fe389d..0765891 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -25,7 +25,7 @@ module Hadrian.Utilities ( renderUnicorn, -- * Miscellaneous - (<&>), + (<&>), (%%>), -- * Useful re-exports Dynamic, fromDynamic, toDyn, TypeRep, typeOf @@ -116,6 +116,15 @@ a -/- b infixr 6 -/- +-- | Like Shake's '%>' but gives higher priority to longer patterns. Useful +-- in situations when a family of build rules, e.g. @"//*.a"@ and @"//*_p.a"@ +-- can be matched by the same file, such as @library_p.a at . We break the tie +-- by preferring longer matches, which correpond to longer patterns. +(%%>) :: FilePattern -> (FilePath -> Action ()) -> Rules () +p %%> a = priority (fromIntegral (length p) + 1) $ p %> a + +infix 1 %%> + -- | Insert a value into Shake's type-indexed map. insertExtra :: Typeable a => a -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic insertExtra value = Map.insert (typeOf value) (toDyn value) diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index f4259fb..f3a162e 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -53,7 +53,7 @@ buildDynamicLib context at Context{..} = do buildPackageLibrary :: Context -> Rules () buildPackageLibrary context at Context {..} = do let libPrefix = "//" ++ contextDir context -/- "libHS" ++ pkgNameString package - libPrefix ++ "*" ++ (waySuffix way <.> "a") %> \a -> do + libPrefix ++ "*" ++ (waySuffix way <.> "a") %%> \a -> do objs <- libraryObjects context asuf <- libsuf way let isLib0 = ("//*-0" ++ asuf) ?== a diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs index 261f142..cd48d91 100644 --- a/src/Rules/Register.hs +++ b/src/Rules/Register.hs @@ -15,17 +15,15 @@ registerPackage rs context at Context {..} = do -- Packages @ghc-boot@ and @ghc-boot-th@ both match the @ghc-boot*@ -- pattern, therefore we need to use priorities to match the right rule. -- TODO: Get rid of this hack. - priority (fromIntegral . length $ pkgNameString package) $ - "//" ++ stage0PackageDbDir -/- pkgNameString package ++ "*.conf" %> - buildConf rs context + "//" ++ stage0PackageDbDir -/- pkgNameString package ++ "*.conf" %%> + buildConf rs context when (package == ghc) $ "//" ++ stage0PackageDbDir -/- packageDbStamp %> buildStamp rs context when (stage == Stage1) $ do - priority (fromIntegral . length $ pkgNameString package) $ - inplacePackageDbPath -/- pkgNameString package ++ "*.conf" %> - buildConf rs context + inplacePackageDbPath -/- pkgNameString package ++ "*.conf" %%> + buildConf rs context when (package == ghc) $ inplacePackageDbPath -/- packageDbStamp %> buildStamp rs context From git at git.haskell.org Fri Oct 27 01:24:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build with '--integer-simple' on Linux GHC 8.0.2 CI (67ae38d) Message-ID: <20171027012417.58F373A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/67ae38d6586cf7f528b7b088a97421f76e029e0e/ghc >--------------------------------------------------------------- commit 67ae38d6586cf7f528b7b088a97421f76e029e0e Author: Andrey Mokhov Date: Thu Aug 17 22:06:32 2017 +0100 Build with '--integer-simple' on Linux GHC 8.0.2 CI >--------------------------------------------------------------- 67ae38d6586cf7f528b7b088a97421f76e029e0e .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index c23e92a..4fecbfc 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,7 +2,7 @@ sudo: true matrix: include: - os: linux - env: MODE="--flavour=quickest" + env: MODE="--flavour=quickest --integer-simple" compiler: "GHC 8.0.2" addons: apt: From git at git.haskell.org Fri Oct 27 01:24:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:20 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: .bat file tidy up plus shake-0.16 compatibility (#392) (df4848c) Message-ID: <20171027012420.D2CA63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/df4848c98c729212840b7de291dcad15fe679451/ghc >--------------------------------------------------------------- commit df4848c98c729212840b7de291dcad15fe679451 Author: Neil Mitchell Date: Fri Aug 18 00:07:13 2017 +0100 .bat file tidy up plus shake-0.16 compatibility (#392) * Switch from @ to @echo off in the batch files * Make sure the .bat files do setlocal - ensures if it fails you don't keep the directory change * Give RuleResult instances to all the oracles, as required by the forthcoming shake-0.16 >--------------------------------------------------------------- df4848c98c729212840b7de291dcad15fe679451 build.bat | 52 +++++++++++++++++--------------- build.stack.bat | 16 +++++----- src/Hadrian/Oracles/ArgsHash.hs | 3 ++ src/Hadrian/Oracles/DirectoryContents.hs | 2 ++ src/Hadrian/Oracles/FileCache.hs | 2 ++ src/Hadrian/Oracles/KeyValue.hs | 3 ++ src/Hadrian/Oracles/Path.hs | 3 ++ src/Hadrian/Utilities.hs | 7 +++++ src/Oracles/ModuleFiles.hs | 3 ++ 9 files changed, 59 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc df4848c98c729212840b7de291dcad15fe679451 From git at git.haskell.org Fri Oct 27 01:24:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move Package to the library (14aec31) Message-ID: <20171027012424.53BC53A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14aec31f12e398f7cab12e23c95c8eda1d8c9f4a/ghc >--------------------------------------------------------------- commit 14aec31f12e398f7cab12e23c95c8eda1d8c9f4a Author: Andrey Mokhov Date: Fri Aug 18 00:56:33 2017 +0100 Move Package to the library See #347 >--------------------------------------------------------------- 14aec31f12e398f7cab12e23c95c8eda1d8c9f4a hadrian.cabal | 2 +- src/Base.hs | 4 ++-- src/{ => Hadrian/Haskell}/Package.hs | 23 ++++++++++++++--------- 3 files changed, 17 insertions(+), 12 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 7c45af6..93e4707 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -28,6 +28,7 @@ executable hadrian , GHC , Hadrian.Expression , Hadrian.Haskell.Cabal + , Hadrian.Haskell.Package , Hadrian.Oracles.ArgsHash , Hadrian.Oracles.DirectoryContents , Hadrian.Oracles.FileCache @@ -39,7 +40,6 @@ executable hadrian , Oracles.Setting , Oracles.ModuleFiles , Oracles.PackageData - , Package , Rules , Rules.Clean , Rules.Compile diff --git a/src/Base.hs b/src/Base.hs index 8c81706..310d7c4 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -15,7 +15,7 @@ module Base ( -- * Basic data types module Builder, - module Package, + module Hadrian.Haskell.Package, module Stage, module Way, @@ -37,9 +37,9 @@ import Development.Shake.Classes import Development.Shake.FilePath import Development.Shake.Util import Hadrian.Utilities +import Hadrian.Haskell.Package import Builder -import Package import Stage import Way diff --git a/src/Package.hs b/src/Hadrian/Haskell/Package.hs similarity index 79% rename from src/Package.hs rename to src/Hadrian/Haskell/Package.hs index 93e8ee0..d7dd3df 100644 --- a/src/Package.hs +++ b/src/Hadrian/Haskell/Package.hs @@ -1,4 +1,4 @@ -module Package ( +module Hadrian.Haskell.Package ( Package (..), PackageName (..), PackageType (..), -- * Queries pkgNameString, pkgCabalFile, @@ -12,20 +12,25 @@ import Development.Shake.FilePath import GHC.Generics import Hadrian.Utilities --- | The name of a Cabal package. +-- | The name of a Haskell package. newtype PackageName = PackageName { fromPackageName :: String } deriving (Binary, Eq, Generic, Hashable, IsString, NFData, Ord, Typeable) -- TODO: Make PackageType more precise, #12. --- | We regard packages as either being libraries or programs. This is bit of a --- convenient lie as Cabal packages can be both, but it works for now. +-- | We regard packages as either being libraries or programs. This is a bit of +-- a convenient lie as Haskell packages can be both, but it works for now. data PackageType = Library | Program deriving Generic -data Package = Package - { pkgName :: PackageName -- ^ Examples: "ghc", "Cabal". - , pkgPath :: FilePath -- ^ pkgPath is the path to the source code relative - -- to the root, e.g. "compiler", "libraries/Cabal/Cabal". - , pkgType :: PackageType -- ^ A library or a program. +-- | A Haskell package. +data Package = Package { + -- | The name of a Haskell package. Examples: @Cabal@, @ghc-bin at . + pkgName :: PackageName, + -- | The path to the package source code relative to the root of the build + -- system. For example, @libraries/Cabal/Cabal@ and @ghc@ are paths to the + -- @Cabal@ and @ghc-bin@ packages in GHC. + pkgPath :: FilePath, + -- | A library (e.g. @Cabal@) or a program (e.g. @ghc-bin@). + pkgType :: PackageType } deriving Generic -- TODO: Get rid of non-derived Show instances. From git at git.haskell.org Fri Oct 27 01:24:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:27 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make Package datatype abstract (39a2b89) Message-ID: <20171027012427.CEF143A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/39a2b89543e584f7349800db14ab6d1182f7c2fc/ghc >--------------------------------------------------------------- commit 39a2b89543e584f7349800db14ab6d1182f7c2fc Author: Andrey Mokhov Date: Fri Aug 18 01:03:42 2017 +0100 Make Package datatype abstract >--------------------------------------------------------------- 39a2b89543e584f7349800db14ab6d1182f7c2fc src/Hadrian/Haskell/Package.hs | 4 ++-- src/Rules/Install.hs | 8 ++++---- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Hadrian/Haskell/Package.hs b/src/Hadrian/Haskell/Package.hs index d7dd3df..cd63589 100644 --- a/src/Hadrian/Haskell/Package.hs +++ b/src/Hadrian/Haskell/Package.hs @@ -1,7 +1,7 @@ module Hadrian.Haskell.Package ( - Package (..), PackageName (..), PackageType (..), + Package, PackageName (..), PackageType (..), -- * Queries - pkgNameString, pkgCabalFile, + pkgName, pkgPath, pkgType, pkgNameString, pkgCabalFile, -- * Helpers for constructing and using 'Package's setPath, topLevel, library, utility, setType, isLibrary, isProgram ) where diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 1d0cd9e..a13e8eb 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -181,7 +181,7 @@ installPackages = do installLibPkgs <- topsortPackages (filter isLibrary activePackages) - forM_ installLibPkgs $ \pkg at Package{..} -> do + forM_ installLibPkgs $ \pkg -> do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg @@ -211,7 +211,7 @@ installPackages = do pref <- setting InstallPrefix unit $ cmd ghcCabalInplace [ "copy" - , pkgPath + , pkgPath pkg , installDistDir , strip , destDir @@ -228,7 +228,7 @@ installPackages = do , installedPackageConf, "update" , confPath ] - forM_ installLibPkgs $ \pkg at Package{..} -> do + forM_ installLibPkgs $ \pkg -> do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg @@ -241,7 +241,7 @@ installPackages = do r <- relocatableBuild unit $ cmd ghcCabalInplace [ "register" - , pkgPath + , pkgPath pkg , installDistDir , installedGhcReal , installedGhcPkgReal From git at git.haskell.org Fri Oct 27 01:24:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify Package data type (7c65e09) Message-ID: <20171027012431.565DA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c65e0982e8fee2a23438e46de22023fb9d5836d/ghc >--------------------------------------------------------------- commit 7c65e0982e8fee2a23438e46de22023fb9d5836d Author: Andrey Mokhov Date: Fri Aug 18 02:37:00 2017 +0100 Simplify Package data type >--------------------------------------------------------------- 7c65e0982e8fee2a23438e46de22023fb9d5836d hadrian.cabal | 1 - src/Context.hs | 4 +- src/GHC.hs | 138 ++++++++++++++++++++++---------------- src/Hadrian/Haskell/Package.hs | 105 ++++++++++++++--------------- src/Rules/Data.hs | 2 +- src/Rules/Documentation.hs | 3 +- src/Rules/Generate.hs | 4 +- src/Rules/Install.hs | 3 +- src/Rules/Library.hs | 8 +-- src/Rules/Program.hs | 4 +- src/Rules/Register.hs | 4 +- src/Settings.hs | 4 +- src/Settings/Builders/Haddock.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Utilities.hs | 10 +-- 15 files changed, 153 insertions(+), 141 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 7c65e0982e8fee2a23438e46de22023fb9d5836d From git at git.haskell.org Fri Oct 27 01:24:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:34 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move RTS-specific paths to Settings.Packages.Rts (f0fb1be) Message-ID: <20171027012434.BBC4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f0fb1be5d3c234d40314f4743d1e45f0d891718e/ghc >--------------------------------------------------------------- commit f0fb1be5d3c234d40314f4743d1e45f0d891718e Author: Andrey Mokhov Date: Fri Aug 18 02:46:30 2017 +0100 Move RTS-specific paths to Settings.Packages.Rts >--------------------------------------------------------------- f0fb1be5d3c234d40314f4743d1e45f0d891718e src/GHC.hs | 16 ---------------- src/Rules/Data.hs | 1 + src/Rules/Generate.hs | 1 + src/Rules/Program.hs | 1 + src/Settings/Packages/Rts.hs | 17 ++++++++++++++++- 5 files changed, 19 insertions(+), 17 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 13142bd..0b3d035 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -13,9 +13,6 @@ module GHC ( -- * Package information builderProvenance, programName, nonCabalContext, nonHsMainPackage, autogenPath, - -- * RTS library - rtsContext, rtsBuildPath, rtsConfIn, - -- * Miscellaneous systemBuilderPath, ghcSplitPath, stripCmdPath, inplaceInstallPath, buildDll0 ) where @@ -239,19 +236,6 @@ stripCmdPath = do return ":" -- HACK: from the make-based system, see the ref above _ -> return "strip" --- TODO: Move to RTS-specific package? --- | RTS is considered a Stage1 package. This determines RTS build directory. -rtsContext :: Context -rtsContext = vanillaContext Stage1 rts - --- | Path to the RTS build directory. -rtsBuildPath :: Action FilePath -rtsBuildPath = buildPath rtsContext - --- | Path to RTS package configuration file, to be processed by HsCpp. -rtsConfIn :: FilePath -rtsConfIn = pkgPath rts -/- "package.conf.in" - buildDll0 :: Context -> Action Bool buildDll0 Context {..} = do windows <- windowsHost diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index 975f3fa..ef2f017 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -6,6 +6,7 @@ import Expression import GHC import Oracles.Setting import Rules.Generate +import Settings.Packages.Rts import Target import Utilities diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 0057bf8..e5dffcc 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -14,6 +14,7 @@ import Oracles.Setting import Rules.Gmp import Rules.Libffi import Settings +import Settings.Packages.Rts import Target import Utilities diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index c88ddd8..efdd7f4 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -11,6 +11,7 @@ import Oracles.PackageData import Oracles.Setting import Rules.Wrappers import Settings +import Settings.Packages.Rts import Target import Utilities diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index fe490dd..0ae764f 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -1,12 +1,27 @@ -module Settings.Packages.Rts (rtsPackageArgs, rtsLibffiLibrary) where +module Settings.Packages.Rts ( + rtsContext, rtsBuildPath, rtsConfIn, rtsPackageArgs, rtsLibffiLibrary + ) where import Base +import Context (buildPath) import Expression import GHC import Oracles.Flag import Oracles.Setting import Settings +-- | RTS is considered a Stage1 package. This determines RTS build directory. +rtsContext :: Context +rtsContext = vanillaContext Stage1 rts + +-- | Path to the RTS build directory. +rtsBuildPath :: Action FilePath +rtsBuildPath = buildPath rtsContext + +-- | Path to RTS package configuration file, to be processed by HsCpp. +rtsConfIn :: FilePath +rtsConfIn = pkgPath rts -/- "package.conf.in" + rtsLibffiLibraryName :: Action FilePath rtsLibffiLibraryName = do useSystemFfi <- flag UseSystemFfi From git at git.haskell.org Fri Oct 27 01:24:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Travis timeout (7231dd5) Message-ID: <20171027012438.397F43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7231dd5a3d512bbafbd65aa4ad70ecdf6a924243/ghc >--------------------------------------------------------------- commit 7231dd5a3d512bbafbd65aa4ad70ecdf6a924243 Author: Andrey Mokhov Date: Fri Aug 18 02:50:01 2017 +0100 Fix Travis timeout See #393 >--------------------------------------------------------------- 7231dd5a3d512bbafbd65aa4ad70ecdf6a924243 .travis.yml | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4fecbfc..fdd83d4 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,7 +2,7 @@ sudo: true matrix: include: - os: linux - env: MODE="--flavour=quickest --integer-simple" + env: MODE="--flavour=quickest inplace/bin/ghc-stage1" compiler: "GHC 8.0.2" addons: apt: @@ -28,7 +28,7 @@ matrix: - inplace/bin/ghc-stage2 -e 1+2 - os: linux - env: MODE="--flavour=quickest" + env: MODE="--flavour=quickest --integer-simple" compiler: "GHC 8.2.1" addons: apt: @@ -55,7 +55,7 @@ matrix: - os: osx osx_image: xcode8 - env: MODE="--flavour=quickest --integer-simple" + env: MODE="--flavour=quickest --integer-simple inplace/bin/ghc-stage1" before_install: - brew update - brew install ghc cabal-install @@ -63,7 +63,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- inplace/bin/ghc-stage1 + - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- install: # Add Cabal to PATH From git at git.haskell.org Fri Oct 27 01:24:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:41 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Run ranlib directly (e91b0c2) Message-ID: <20171027012441.A849B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e91b0c248df89e26d56bd5c34a48fa4e1aebacbb/ghc >--------------------------------------------------------------- commit e91b0c248df89e26d56bd5c34a48fa4e1aebacbb Author: Andrey Mokhov Date: Fri Aug 18 02:59:59 2017 +0100 Run ranlib directly >--------------------------------------------------------------- e91b0c248df89e26d56bd5c34a48fa4e1aebacbb src/Rules/Install.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index e3f7fe6..12135b4 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -281,8 +281,7 @@ installLibsTo libs dir = do ".a" -> do let out = dir -/- takeFileName lib installData [out] dir - -- TODO: Get rid of meaningless context for certain builder like ranlib - build $ target (stageContext Stage0) Ranlib [out] [out] + runBuilder Ranlib [out] _ -> installData [lib] dir -- ref: includes/ghc.mk From git at git.haskell.org Fri Oct 27 01:24:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Travis (23c8602) Message-ID: <20171027012445.20E133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/23c860257546f48deb024d2842e2171581f072bb/ghc >--------------------------------------------------------------- commit 23c860257546f48deb024d2842e2171581f072bb Author: Andrey Mokhov Date: Fri Aug 18 11:33:04 2017 +0100 Fix Travis See #393 >--------------------------------------------------------------- 23c860257546f48deb024d2842e2171581f072bb .travis.yml | 7 ------- 1 file changed, 7 deletions(-) diff --git a/.travis.yml b/.travis.yml index fdd83d4..878136c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -23,10 +23,6 @@ matrix: # Build GHC - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- - # Test GHC binary - - cd .. - - inplace/bin/ghc-stage2 -e 1+2 - - os: linux env: MODE="--flavour=quickest --integer-simple" compiler: "GHC 8.2.1" @@ -43,9 +39,6 @@ matrix: - PATH="/opt/cabal/1.22/bin:$PATH" script: - # Run internal Hadrian tests - - ./build.cabal.sh selftest - # Build GHC - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- From git at git.haskell.org Fri Oct 27 01:24:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:48 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add mtl, parsec and text as Stage0 packages (d2dddad) Message-ID: <20171027012448.B96033A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d2dddad4564c6597d497d226fcfbf5e3f7b70c18/ghc >--------------------------------------------------------------- commit d2dddad4564c6597d497d226fcfbf5e3f7b70c18 Author: Andrey Mokhov Date: Fri Aug 18 23:41:24 2017 +0100 Add mtl, parsec and text as Stage0 packages See #393, #395 >--------------------------------------------------------------- d2dddad4564c6597d497d226fcfbf5e3f7b70c18 src/GHC.hs | 15 +++++++++------ src/Settings/Default.hs | 3 +++ src/Settings/Packages/GhcCabal.hs | 2 +- 3 files changed, 13 insertions(+), 7 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 0b3d035..2a641e5 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -6,9 +6,9 @@ module GHC ( genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, - parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, - terminfo, time, touchy, transformers, unlit, unix, win32, xhtml, - defaultKnownPackages, + mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm, + templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix, + win32, xhtml, defaultKnownPackages, -- * Package information builderProvenance, programName, nonCabalContext, nonHsMainPackage, autogenPath, @@ -36,9 +36,9 @@ defaultKnownPackages = , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi - , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm - , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32 - , xhtml ] + , mkUserGuidePart, mtl, parsec, parallel, pretty, primitive, process, rts + , runGhc, stm, templateHaskell, terminfo, text, time, touchy, transformers + , unlit, unix, win32, xhtml ] -- | Package definitions, see 'Package'. array = lib "array" @@ -78,6 +78,8 @@ integerSimple = lib "integer-simple" iservBin = prg "iserv-bin" `setPath` "iserv" libffi = top "libffi" mkUserGuidePart = util "mkUserGuidePart" +mtl = lib "mtl" +parsec = lib "parsec" parallel = lib "parallel" pretty = lib "pretty" primitive = lib "primitive" @@ -87,6 +89,7 @@ runGhc = util "runghc" stm = lib "stm" templateHaskell = lib "template-haskell" terminfo = lib "terminfo" +text = lib "text" time = lib "time" touchy = util "touchy" transformers = lib "transformers" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 707bc6f..c97b79f 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -116,7 +116,10 @@ stage0Packages = do , hp2ps , hpc , mkUserGuidePart + , mtl + , parsec , templateHaskell + , text , transformers , unlit ] ++ [ terminfo | not win, not ios ] ++ diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index fb23297..17ea482 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -12,7 +12,7 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do cabalDeps <- expr $ pkgDependencies cabal (_, cabalVersion) <- expr $ cabalNameVersion (pkgCabalFile cabal) mconcat - [ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps ] + [ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps, pkg /= parsec ] , arg "--make" , arg "-j" , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) From git at git.haskell.org Fri Oct 27 01:24:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (9fa04f0) Message-ID: <20171027012452.9C94F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9fa04f066032ce5c8ab753f0aa2a71660dfb466c/ghc >--------------------------------------------------------------- commit 9fa04f066032ce5c8ab753f0aa2a71660dfb466c Author: Andrey Mokhov Date: Sat Aug 19 00:31:39 2017 +0100 Minor revision >--------------------------------------------------------------- 9fa04f066032ce5c8ab753f0aa2a71660dfb466c src/GHC.hs | 8 ++--- src/Hadrian/Haskell/Cabal.hs | 63 ++++++++++++++++++++------------------- src/Hadrian/Haskell/Package.hs | 20 +++++++------ src/Settings.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 2 +- src/Settings/Packages/GhcCabal.hs | 4 +-- src/Utilities.hs | 13 ++++---- 7 files changed, 59 insertions(+), 53 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 9fa04f066032ce5c8ab753f0aa2a71660dfb466c From git at git.haskell.org Fri Oct 27 01:24:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop double installation of Hadrian dependencies (48ad1e7) Message-ID: <20171027012456.67F7A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/48ad1e76030a4b8054641a0e7875c5921c2d6658/ghc >--------------------------------------------------------------- commit 48ad1e76030a4b8054641a0e7875c5921c2d6658 Author: Andrey Mokhov Date: Sat Aug 19 00:39:20 2017 +0100 Drop double installation of Hadrian dependencies See #393 >--------------------------------------------------------------- 48ad1e76030a4b8054641a0e7875c5921c2d6658 .travis.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 878136c..48ed171 100644 --- a/.travis.yml +++ b/.travis.yml @@ -74,8 +74,7 @@ install: # Install all Hadrian and GHC build dependencies - cabal update - - cabal install alex happy ansi-terminal mtl shake quickcheck - + - cabal install alex happy # Travis has already cloned Hadrian into ./ and we need to move it # to ./ghc/hadrian -- one way to do it is to move the .git directory From git at git.haskell.org Fri Oct 27 01:24:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:24:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix install rules by untracking copy files and use relative path (#396) (942ed27) Message-ID: <20171027012459.E7EE13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/942ed27a622576252ef7178040f0b1fdbf08ca1c/ghc >--------------------------------------------------------------- commit 942ed27a622576252ef7178040f0b1fdbf08ca1c Author: Zhen Zhang Date: Sat Aug 19 09:39:25 2017 +0800 Fix install rules by untracking copy files and use relative path (#396) >--------------------------------------------------------------- 942ed27a622576252ef7178040f0b1fdbf08ca1c src/Hadrian/Oracles/DirectoryContents.hs | 10 +++++++++- src/Rules/Install.hs | 8 +++++--- 2 files changed, 14 insertions(+), 4 deletions(-) diff --git a/src/Hadrian/Oracles/DirectoryContents.hs b/src/Hadrian/Oracles/DirectoryContents.hs index 19a5192..f302af9 100644 --- a/src/Hadrian/Oracles/DirectoryContents.hs +++ b/src/Hadrian/Oracles/DirectoryContents.hs @@ -1,6 +1,6 @@ {-# LANGUAGE TypeFamilies #-} module Hadrian.Oracles.DirectoryContents ( - directoryContents, copyDirectoryContents, directoryContentsOracle, + directoryContents, copyDirectoryContents, directoryContentsOracle, copyDirectoryContentsUntracked, Match (..), matches, matchAll ) where @@ -45,6 +45,14 @@ copyDirectoryContents expr source target = do let cp file = copyFile file $ target -/- makeRelative source file mapM_ cp =<< directoryContents expr source +-- | Copy the contents of the source directory that matches a given 'Match' +-- expression into the target directory. The copied contents is untracked. +copyDirectoryContentsUntracked :: Match -> FilePath -> FilePath -> Action () +copyDirectoryContentsUntracked expr source target = do + putProgressInfo =<< renderAction "Copy directory contents (untracked)" source target + let cp file = copyFileUntracked file $ target -/- makeRelative source file + mapM_ cp =<< directoryContents expr source + newtype DirectoryContents = DirectoryContents (Match, FilePath) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) type instance RuleResult DirectoryContents = [FilePath] diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 12135b4..2400933 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -186,7 +186,9 @@ installPackages = do withLatestBuildStage pkg $ \stage -> do let context = vanillaContext stage pkg top <- topDirectory - installDistDir <- (top -/-) <$> buildPath context + installDistDir <- buildPath context + let absInstallDistDir = top -/- installDistDir + need =<< packageTargets stage pkg docDir <- installDocDir ghclibDir <- installGhcLibDir @@ -203,7 +205,7 @@ installPackages = do need [cabalFile, pkgConf] -- TODO: check if need pkgConf -- HACK (#318): copy stuff back to the place favored by ghc-cabal - quietly $ copyDirectoryContents (Not excluded) + quietly $ copyDirectoryContentsUntracked (Not excluded) installDistDir (installDistDir -/- "build") whenM (isSpecified HsColour) $ @@ -212,7 +214,7 @@ installPackages = do pref <- setting InstallPrefix unit $ cmd ghcCabalInplace [ "copy" , pkgPath pkg - , installDistDir + , absInstallDistDir , strip , destDir , pref From git at git.haskell.org Fri Oct 27 01:25:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Improve infrastructure for Cabal file parsing (4b6707a) Message-ID: <20171027012503.950613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b6707a616478a0f664585a49de0d0ed6431d231/ghc >--------------------------------------------------------------- commit 4b6707a616478a0f664585a49de0d0ed6431d231 Author: Andrey Mokhov Date: Sat Aug 19 03:45:33 2017 +0100 Improve infrastructure for Cabal file parsing >--------------------------------------------------------------- 4b6707a616478a0f664585a49de0d0ed6431d231 hadrian.cabal | 4 +- src/Base.hs | 14 ++---- src/GHC.hs | 2 +- src/Hadrian/Haskell/Cabal.hs | 39 +++++---------- src/Hadrian/Haskell/Cabal/Parse.hs | 60 ++++++++++++++++++++++++ src/Hadrian/Oracles/FileCache.hs | 51 -------------------- src/Hadrian/Oracles/{KeyValue.hs => TextFile.hs} | 54 ++++++++++++++++++--- src/Oracles/Flag.hs | 2 +- src/Oracles/PackageData.hs | 2 +- src/Oracles/Setting.hs | 2 +- src/Rules.hs | 11 +---- src/Rules/Compile.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 20 +++----- src/Utilities.hs | 38 +++++---------- 14 files changed, 149 insertions(+), 152 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 4b6707a616478a0f664585a49de0d0ed6431d231 From git at git.haskell.org Fri Oct 27 01:25:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Merge branch 'master' of https://github.com/snowleopard/hadrian (8586ab8) Message-ID: <20171027012507.1E4B93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8586ab84fbac7e250d23844bbd39c147f87ce092/ghc >--------------------------------------------------------------- commit 8586ab84fbac7e250d23844bbd39c147f87ce092 Merge: 4b6707a 942ed27 Author: Andrey Mokhov Date: Sat Aug 19 03:45:40 2017 +0100 Merge branch 'master' of https://github.com/snowleopard/hadrian >--------------------------------------------------------------- 8586ab84fbac7e250d23844bbd39c147f87ce092 src/Hadrian/Oracles/DirectoryContents.hs | 10 +++++++++- src/Rules/Install.hs | 8 +++++--- 2 files changed, 14 insertions(+), 4 deletions(-) From git at git.haskell.org Fri Oct 27 01:25:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (268155a) Message-ID: <20171027012510.A4EEB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/268155a0e615fda224d72d029749f1e2df0fa59b/ghc >--------------------------------------------------------------- commit 268155a0e615fda224d72d029749f1e2df0fa59b Author: Andrey Mokhov Date: Sat Aug 19 13:12:09 2017 +0100 Minor revision >--------------------------------------------------------------- 268155a0e615fda224d72d029749f1e2df0fa59b src/Hadrian/Haskell/Cabal.hs | 3 +-- src/Hadrian/Haskell/Cabal/Parse.hs | 8 ++++---- src/Hadrian/Oracles/Path.hs | 4 ++-- src/Hadrian/Oracles/TextFile.hs | 23 +++++++++++++---------- 4 files changed, 20 insertions(+), 18 deletions(-) diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs index bf21b18..6da1e51 100644 --- a/src/Hadrian/Haskell/Cabal.hs +++ b/src/Hadrian/Haskell/Cabal.hs @@ -11,7 +11,6 @@ ----------------------------------------------------------------------------- module Hadrian.Haskell.Cabal (pkgNameVersion, pkgDependencies) where -import Data.List import Development.Shake import Hadrian.Haskell.Cabal.Parse @@ -32,4 +31,4 @@ pkgNameVersion pkg = do pkgDependencies :: Package -> Action [PackageName] pkgDependencies pkg = do cabal <- readCabalFile (pkgCabalFile pkg) - return (dependencies cabal \\ [pkgName pkg]) + return (dependencies cabal) diff --git a/src/Hadrian/Haskell/Cabal/Parse.hs b/src/Hadrian/Haskell/Cabal/Parse.hs index ec18781..bc234d4 100644 --- a/src/Hadrian/Haskell/Cabal/Parse.hs +++ b/src/Hadrian/Haskell/Cabal/Parse.hs @@ -44,14 +44,14 @@ parseCabal :: FilePath -> IO Cabal parseCabal file = do gpd <- liftIO $ C.readGenericPackageDescription C.silent file let pkgId = C.package (C.packageDescription gpd) + name = C.unPackageName (C.pkgName pkgId) + version = C.display (C.pkgVersion pkgId) libDeps = collectDeps (C.condLibrary gpd) exeDeps = map (collectDeps . Just . snd) (C.condExecutables gpd) allDeps = concat (libDeps : exeDeps) sorted = sort [ C.unPackageName p | C.Dependency p _ <- allDeps ] - return $ Cabal - (C.unPackageName $ C.pkgName pkgId) - (C.display $ C.pkgVersion pkgId) - (nubOrd sorted) + deps = nubOrd sorted \\ [name] + return $ Cabal name version deps collectDeps :: Maybe (C.CondTree v [C.Dependency] a) -> [C.Dependency] collectDeps Nothing = [] diff --git a/src/Hadrian/Oracles/Path.hs b/src/Hadrian/Oracles/Path.hs index cab8aa1..4f6406c 100644 --- a/src/Hadrian/Oracles/Path.hs +++ b/src/Hadrian/Oracles/Path.hs @@ -52,11 +52,11 @@ pathOracle = do void $ addOracle $ \(WindowsPath path) -> do Stdout out <- quietly $ cmd ["cygpath", "-m", path] let windowsPath = unifyPath $ dropWhileEnd isSpace out - putLoud $ "Windows path mapping: " ++ path ++ " => " ++ windowsPath + putLoud $ "| Windows path mapping: " ++ path ++ " => " ++ windowsPath return windowsPath void $ addOracle $ \(LookupInPath name) -> do let unpack = fromMaybe . error $ "Cannot find executable " ++ quote name path <- unifyPath <$> unpack <$> liftIO (findExecutable name) - putLoud $ "Executable found: " ++ name ++ " => " ++ path + putLoud $ "| Executable found: " ++ name ++ " => " ++ path return path diff --git a/src/Hadrian/Oracles/TextFile.hs b/src/Hadrian/Oracles/TextFile.hs index 7f80c75..c2ecb4c 100644 --- a/src/Hadrian/Oracles/TextFile.hs +++ b/src/Hadrian/Oracles/TextFile.hs @@ -23,8 +23,8 @@ import Development.Shake import Development.Shake.Classes import Development.Shake.Config -import Hadrian.Utilities import Hadrian.Haskell.Cabal.Parse +import Hadrian.Utilities newtype TextFile = TextFile FilePath deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -32,7 +32,7 @@ type instance RuleResult TextFile = String newtype CabalFile = CabalFile FilePath deriving (Binary, Eq, Hashable, NFData, Show, Typeable) -type instance RuleResult CabalFile = String +type instance RuleResult CabalFile = Cabal newtype KeyValue = KeyValue (FilePath, String) deriving (Binary, Eq, Hashable, NFData, Show, Typeable) @@ -99,22 +99,25 @@ textFileOracle :: Rules () textFileOracle = do text <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| TextFile oracle: reading " ++ quote file ++ "..." liftIO $ readFile file + void $ addOracle $ \(TextFile file) -> text file + kv <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| KeyValue oracle: reading " ++ quote file ++ "..." liftIO $ readConfigFile file + void $ addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> kv file + kvs <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| KeyValues oracle: reading " ++ quote file ++ "..." contents <- map words <$> readFileLines file return $ Map.fromList [ (key, values) | (key:values) <- contents ] + void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file + cabal <- newCache $ \file -> do need [file] - putLoud $ "Reading " ++ file ++ "..." + putLoud $ "| CabalFile oracle: reading " ++ quote file ++ "..." liftIO $ parseCabal file - void $ addOracle $ \(TextFile file ) -> text file - void $ addOracle $ \(KeyValue (file, key)) -> Map.lookup key <$> kv file - void $ addOracle $ \(KeyValues (file, key)) -> Map.lookup key <$> kvs file - void $ addOracle $ \(CabalFile file ) -> cabal file + void $ addOracle $ \(CabalFile file) -> cabal file From git at git.haskell.org Fri Oct 27 01:25:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix MonadFail warning (a8cbd16) Message-ID: <20171027012514.16FB93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a8cbd160e3e6b90bdb618620fd6eb4cc53179ae5/ghc >--------------------------------------------------------------- commit a8cbd160e3e6b90bdb618620fd6eb4cc53179ae5 Author: Andrey Mokhov Date: Sat Aug 19 16:21:27 2017 +0100 Fix MonadFail warning >--------------------------------------------------------------- a8cbd160e3e6b90bdb618620fd6eb4cc53179ae5 src/Settings/Builders/DeriveConstants.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs index b8846be..7a6e863 100644 --- a/src/Settings/Builders/DeriveConstants.hs +++ b/src/Settings/Builders/DeriveConstants.hs @@ -5,8 +5,11 @@ import Settings.Builders.Common -- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`? deriveConstantsBuilderArgs :: Args deriveConstantsBuilderArgs = builder DeriveConstants ? do - cFlags <- includeCcArgs - [outputFile, tempDir] <- getOutputs + cFlags <- includeCcArgs + outs <- getOutputs + let (outputFile, tempDir) = case outs of + [a, b] -> (a, b) + _ -> error $ "DeriveConstants: expected two outputs, got " ++ show outs mconcat [ output "//DerivedConstants.h" ? arg "--gen-header" , output "//GHCConstantsHaskellType.hs" ? arg "--gen-haskell-type" From git at git.haskell.org Fri Oct 27 01:25:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ghcid.txt (8f244c4) Message-ID: <20171027012517.8D4013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f244c413c7e3444285b32c8f90f839511a367ce/ghc >--------------------------------------------------------------- commit 8f244c413c7e3444285b32c8f90f839511a367ce Author: Andrey Mokhov Date: Sat Aug 19 16:22:54 2017 +0100 Add ghcid.txt >--------------------------------------------------------------- 8f244c413c7e3444285b32c8f90f839511a367ce .gitignore | 3 +++ 1 file changed, 3 insertions(+) diff --git a/.gitignore b/.gitignore index 4b026f2..697afc9 100644 --- a/.gitignore +++ b/.gitignore @@ -21,3 +21,6 @@ cabal.sandbox.config # Mostly temp file by emacs *~ + +# ghcid output +/ghcid.txt \ No newline at end of file From git at git.haskell.org Fri Oct 27 01:25:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix performance bug: do not call ghc-cabal to determine package targets (ef47d7b) Message-ID: <20171027012521.07BDD3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ef47d7b35d17bff791763c8bf3d46caaaf1a1108/ghc >--------------------------------------------------------------- commit ef47d7b35d17bff791763c8bf3d46caaaf1a1108 Author: Andrey Mokhov Date: Sun Aug 20 01:12:39 2017 +0100 Fix performance bug: do not call ghc-cabal to determine package targets See #393 >--------------------------------------------------------------- ef47d7b35d17bff791763c8bf3d46caaaf1a1108 src/Context.hs | 19 +++++++++---------- src/Hadrian/Haskell/Cabal.hs | 18 +++++++++++++++++- src/Hadrian/Haskell/Cabal/Parse.hs | 7 ++++--- src/Oracles/PackageData.hs | 2 -- src/Rules.hs | 21 +++++++++++++++------ src/Rules/Install.hs | 2 +- src/Settings/Builders/Ghc.hs | 7 +++++-- src/Utilities.hs | 13 ++++++++----- 8 files changed, 59 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 ef47d7b35d17bff791763c8bf3d46caaaf1a1108 From git at git.haskell.org Fri Oct 27 01:25:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: delete cfg/config.h.in (#390) (c413722) Message-ID: <20171027012524.9D8B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c413722eae49a7999293a8940547f626a33d0632/ghc >--------------------------------------------------------------- commit c413722eae49a7999293a8940547f626a33d0632 Author: Zhen Zhang Date: Sun Aug 20 19:09:47 2017 +0800 delete cfg/config.h.in (#390) >--------------------------------------------------------------- c413722eae49a7999293a8940547f626a33d0632 cfg/config.h.in | 463 -------------------------------------------------------- 1 file changed, 463 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 c413722eae49a7999293a8940547f626a33d0632 From git at git.haskell.org Fri Oct 27 01:25:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add DESTDIR to command line arguments (#397) (176bfd4) Message-ID: <20171027012528.1CC833A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/176bfd4d524c59c64a182f8e04dd0084a9c5e482/ghc >--------------------------------------------------------------- commit 176bfd4d524c59c64a182f8e04dd0084a9c5e482 Author: Zhen Zhang Date: Sun Aug 20 19:29:36 2017 +0800 Add DESTDIR to command line arguments (#397) >--------------------------------------------------------------- 176bfd4d524c59c64a182f8e04dd0084a9c5e482 README.md | 2 +- src/CommandLine.hs | 13 ++++++++++++- src/Rules/Install.hs | 6 ++++++ src/Settings.hs | 7 +++---- src/Settings/Packages/Rts.hs | 1 + 5 files changed, 23 insertions(+), 6 deletions(-) diff --git a/README.md b/README.md index 5e49393..ecf9728 100644 --- a/README.md +++ b/README.md @@ -111,7 +111,7 @@ To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` tar To build and install GHC artifacts, run the `install` target. By default, the artifacts will be installed to `` on your system. For example, -`ghc` will be installed to `/usr/local/bin`. By modifying `defaultDestDir` in `UserSettings.hs`, +`ghc` will be installed to `/usr/local/bin`. By setting flag `--install-destdir=[DESTDIR]`, you can install things to non-system path `DESTDIR/` instead. #### Testing diff --git a/src/CommandLine.hs b/src/CommandLine.hs index 5688d6f..fbf3e07 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -1,6 +1,7 @@ module CommandLine ( optDescrs, cmdLineArgsMap, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, - cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects + cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects, + cmdInstallDestDir ) where import Data.Either @@ -14,6 +15,7 @@ import System.Environment -- | All arguments that can be passed to Hadrian via the command line. data CommandLineArgs = CommandLineArgs { buildHaddock :: Bool + , installDestDir :: Maybe String , flavour :: Maybe String , integerSimple :: Bool , progressColour :: UseColour @@ -27,6 +29,7 @@ defaultCommandLineArgs :: CommandLineArgs defaultCommandLineArgs = CommandLineArgs { buildHaddock = False , flavour = Nothing + , installDestDir = Nothing , integerSimple = False , progressColour = Auto , progressInfo = Normal @@ -39,6 +42,9 @@ readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } readFlavour :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs) readFlavour ms = Right $ \flags -> flags { flavour = lower <$> ms } +readInstallDestDir :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs) +readInstallDestDir ms = Right $ \flags -> flags { installDestDir = ms } + readIntegerSimple :: Either String (CommandLineArgs -> CommandLineArgs) readIntegerSimple = Right $ \flags -> flags { integerSimple = True } @@ -80,6 +86,8 @@ optDescrs = "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." + , Option [] ["install-destdir"] (OptArg readInstallDestDir "DESTDIR") + "Installation destination directory." , Option [] ["integer-simple"] (NoArg readIntegerSimple) "Build GHC with integer-simple library." , Option [] ["progress-colour"] (OptArg readProgressColour "MODE") @@ -107,6 +115,9 @@ cmdLineArgs = userSetting defaultCommandLineArgs cmdBuildHaddock :: Action Bool cmdBuildHaddock = buildHaddock <$> cmdLineArgs +cmdInstallDestDir :: Action (Maybe String) +cmdInstallDestDir = installDestDir <$> cmdLineArgs + cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 24d7703..0d7336b 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -60,6 +60,7 @@ getLibExecDir = (-/- "bin") <$> installGhcLibDir installLibExecScripts :: Action () installLibExecScripts = do libExecDir <- getLibExecDir + destDir <- getDestDir installDirectory (destDir ++ libExecDir) forM_ libExecScripts $ \script -> do installScript script (destDir ++ libExecDir) @@ -72,6 +73,7 @@ installLibExecScripts = do installLibExecs :: Action () installLibExecs = do libExecDir <- getLibExecDir + destDir <- getDestDir installDirectory (destDir ++ libExecDir) forM_ installBinPkgs $ \pkg -> do withLatestBuildStage pkg $ \stage -> do @@ -88,6 +90,7 @@ installBins :: Action () installBins = do binDir <- setting InstallBinDir libDir <- installGhcLibDir + destDir <- getDestDir installDirectory (destDir ++ binDir) win <- windowsHost when win $ @@ -153,6 +156,7 @@ installPackages = do ghcLibDir <- installGhcLibDir binDir <- setting InstallBinDir + destDir <- getDestDir -- Install package.conf let installedPackageConf = destDir ++ ghcLibDir -/- "package.conf.d" @@ -271,6 +275,7 @@ installPackages = do installCommonLibs :: Action () installCommonLibs = do ghcLibDir <- installGhcLibDir + destDir <- getDestDir installLibsTo inplaceLibCopyTargets (destDir ++ ghcLibDir) -- ref: ghc.mk @@ -296,6 +301,7 @@ includeHSubdirs = [".", "rts", "rts/prof", "rts/storage", "stg"] installIncludes :: Action () installIncludes = do ghclibDir <- installGhcLibDir + destDir <- getDestDir let ghcheaderDir = ghclibDir -/- "include" installDirectory (destDir ++ ghcheaderDir) forM_ includeHSubdirs $ \dir -> do diff --git a/src/Settings.hs b/src/Settings.hs index 9fafd1e..52c36ad 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -2,7 +2,7 @@ module Settings ( getArgs, getPackages, getLibraryWays, getRtsWays, flavour, knownPackages, findKnownPackage, getPkgData, getPkgDataList, isLibrary, stagePackages, builderPath, getBuilderPath, isSpecified, latestBuildStage, programPath, - programContext, integerLibraryName, destDir, stage1Only, buildDll0 + programContext, integerLibraryName, getDestDir, stage1Only, buildDll0 ) where import Context @@ -103,7 +103,6 @@ programPath context at Context {..} = do stage1Only :: Bool stage1Only = defaultStage1Only --- TODO: Set this from command line -- | Install's DESTDIR setting. -destDir :: FilePath -destDir = defaultDestDir +getDestDir :: Action FilePath +getDestDir = fromMaybe "" <$> cmdInstallDestDir diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 0ae764f..a54e618 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -62,6 +62,7 @@ rtsPackageArgs = package rts ? do ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir ghclibDir <- expr installGhcLibDir + destDir <- expr getDestDir let cArgs = [ arg "-Irts" , arg $ "-I" ++ path From git at git.haskell.org Fri Oct 27 01:25:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (acd5c37) Message-ID: <20171027012531.811A43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/acd5c37535be71bc36dbf73ae09a772af5d63fda/ghc >--------------------------------------------------------------- commit acd5c37535be71bc36dbf73ae09a772af5d63fda Author: Andrey Mokhov Date: Sun Aug 20 15:23:24 2017 +0100 Minor revision >--------------------------------------------------------------- acd5c37535be71bc36dbf73ae09a772af5d63fda src/CommandLine.hs | 9 ++++----- src/Hadrian/Utilities.hs | 2 +- 2 files changed, 5 insertions(+), 6 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index fbf3e07..cc6f944 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -15,8 +15,8 @@ import System.Environment -- | All arguments that can be passed to Hadrian via the command line. data CommandLineArgs = CommandLineArgs { buildHaddock :: Bool - , installDestDir :: Maybe String , flavour :: Maybe String + , installDestDir :: Maybe String , integerSimple :: Bool , progressColour :: UseColour , progressInfo :: ProgressInfo @@ -115,12 +115,12 @@ cmdLineArgs = userSetting defaultCommandLineArgs cmdBuildHaddock :: Action Bool cmdBuildHaddock = buildHaddock <$> cmdLineArgs -cmdInstallDestDir :: Action (Maybe String) -cmdInstallDestDir = installDestDir <$> cmdLineArgs - cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs +cmdInstallDestDir :: Action (Maybe String) +cmdInstallDestDir = installDestDir <$> cmdLineArgs + cmdIntegerSimple :: Action Bool cmdIntegerSimple = integerSimple <$> cmdLineArgs @@ -135,4 +135,3 @@ cmdSkipConfigure = skipConfigure <$> cmdLineArgs cmdSplitObjects :: Action Bool cmdSplitObjects = splitObjects <$> cmdLineArgs - diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index f1db28e..4051347 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -177,7 +177,7 @@ copyFile source target = do let dir = takeDirectory target liftIO $ IO.createDirectoryIfMissing True dir putProgressInfo =<< renderAction "Copy file" source target - copyFileChanged source target + quietly $ copyFileChanged source target -- | Copy a file without tracking the source. Create the target directory if missing. copyFileUntracked :: FilePath -> FilePath -> Action () From git at git.haskell.org Fri Oct 27 01:25:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to computing package version only through the Cabal library (4ce8587) Message-ID: <20171027012535.030553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4ce85874126d7356b6c442e45c593797283f7108/ghc >--------------------------------------------------------------- commit 4ce85874126d7356b6c442e45c593797283f7108 Author: Andrey Mokhov Date: Sun Aug 20 17:05:30 2017 +0100 Switch to computing package version only through the Cabal library >--------------------------------------------------------------- 4ce85874126d7356b6c442e45c593797283f7108 src/Hadrian/Haskell/Cabal.hs | 36 ++++++++++++++++++++++-------------- src/Oracles/PackageData.hs | 2 -- src/Rules/Data.hs | 2 -- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Builders/Haddock.hs | 6 +++--- src/Settings/Packages/GhcCabal.hs | 4 ++-- 6 files changed, 29 insertions(+), 25 deletions(-) diff --git a/src/Hadrian/Haskell/Cabal.hs b/src/Hadrian/Haskell/Cabal.hs index 02fcd82..23cfdc7 100644 --- a/src/Hadrian/Haskell/Cabal.hs +++ b/src/Hadrian/Haskell/Cabal.hs @@ -10,35 +10,43 @@ -- @.cabal@ files. ----------------------------------------------------------------------------- module Hadrian.Haskell.Cabal ( - pkgNameVersion, pkgIdentifier, pkgDependencies + pkgVersion, pkgIdentifier, pkgDependencies ) where +import Control.Monad import Development.Shake import Hadrian.Haskell.Cabal.Parse import Hadrian.Haskell.Package import Hadrian.Oracles.TextFile +import Hadrian.Utilities --- | Read the @.cabal@ file of a given package and return the package name and --- version. The @.cabal@ file is tracked. -pkgNameVersion :: Package -> Action (PackageName, String) -pkgNameVersion pkg = do +-- | Read the @.cabal@ file of a given package and return the package version. +-- The @.cabal@ file is tracked. +pkgVersion :: Package -> Action String +pkgVersion pkg = do cabal <- readCabalFile (pkgCabalFile pkg) - return (name cabal, version cabal) + return (version cabal) --- | Read the @.cabal@ file of a given package and return the package identifier. --- If the @.cabal@ file does not exist return the package name. If the @.cabal@ --- file exists it is tracked. +-- | Read the @.cabal@ file of a given package and return the package identifier, +-- e.g. @base-4.10.0.0 at . If the @.cabal@ file does not exist return just the +-- package name, e.g. @rts at . If the @.cabal@ file exists then it is tracked, and +-- furthermore we check that the recorded package name matches the name of the +-- package passed as the parameter and raise an error otherwise. pkgIdentifier :: Package -> Action String pkgIdentifier pkg = do cabalExists <- doesFileExist (pkgCabalFile pkg) - if cabalExists - then do + if not cabalExists + then return (pkgName pkg) + else do cabal <- readCabalFile (pkgCabalFile pkg) + when (pkgName pkg /= name cabal) $ + error $ "[Hadrian.Haskell.Cabal] Inconsistent package name: expected " + ++ quote (pkgName pkg) ++ ", but " ++ quote (pkgCabalFile pkg) + ++ " specifies " ++ quote (name cabal) ++ "." return $ if (null $ version cabal) - then name cabal - else name cabal ++ "-" ++ version cabal - else return (pkgName pkg) + then pkgName pkg + else pkgName pkg ++ "-" ++ version cabal -- | Read the @.cabal@ file of a given package and return the sorted list of its -- dependencies. The current version does not take care of Cabal conditionals diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs index 991caf1..7d98c98 100644 --- a/src/Oracles/PackageData.hs +++ b/src/Oracles/PackageData.hs @@ -8,7 +8,6 @@ import Base data PackageData = BuildGhciLib FilePath | Synopsis FilePath - | Version FilePath data PackageDataList = AsmSrcs FilePath | CcArgs FilePath @@ -40,7 +39,6 @@ pkgData :: PackageData -> Action String pkgData packageData = case packageData of BuildGhciLib path -> askPackageData path "BUILD_GHCI_LIB" Synopsis path -> askPackageData path "SYNOPSIS" - Version path -> askPackageData path "VERSION" -- | @PackageDataList path@ is used for multiple string options separated by -- spaces, such as @path_MODULES = Data.Array Data.Array.Base ... at . diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs index ef2f017..194bf62 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/Data.hs @@ -61,9 +61,7 @@ generatePackageData context at Context {..} file = do cSrcs <- packageCSources package cmmSrcs <- packageCmmSources package genPath <- buildRoot <&> (-/- generatedDir) - let pkgKey = if isLibrary package then "COMPONENT_ID = " else "PROGNAME = " writeFileChanged file . unlines $ - [ pkgKey ++ pkgName package ] ++ [ "S_SRCS = " ++ unwords asmSrcs ] ++ [ "C_SRCS = " ++ unwords cSrcs ] ++ [ "CMM_SRCS = " ++ unwords cmmSrcs ] ++ diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index ba1de93..cf6bcb3 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -95,8 +95,8 @@ bootPackageConstraints = stage0 ? do bootPkgs <- expr $ stagePackages Stage0 let pkgs = filter (\p -> p /= compiler && isLibrary p) bootPkgs constraints <- expr $ forM (sort pkgs) $ \pkg -> do - (name, version) <- pkgNameVersion pkg - return (name ++ " == " ++ version) + version <- pkgVersion pkg + return (pkgName pkg ++ " == " ++ version) pure $ concat [ ["--constraint", c] | c <- constraints ] cppArgs :: Args diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index 7319f80..bc3ebf4 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -1,6 +1,7 @@ module Settings.Builders.Haddock (haddockBuilderArgs) where import Hadrian.Utilities +import Hadrian.Haskell.Cabal import Rules.Documentation import Settings.Builders.Common @@ -17,12 +18,11 @@ haddockBuilderArgs = builder Haddock ? do output <- getOutput pkg <- getPackage path <- getBuildPath - version <- getPkgData Version + version <- expr $ pkgVersion pkg synopsis <- getPkgData Synopsis deps <- getPkgDataList Deps haddocks <- expr . haddockDependencies =<< getContext - progPath <- expr $ buildPath (vanillaContext Stage2 haddock) - hVersion <- expr $ pkgData (Version progPath) + hVersion <- expr $ pkgVersion haddock ghcOpts <- haddockGhcArgs mconcat [ arg $ "--odir=" ++ takeDirectory output diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 0a0fe15..3c07c67 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -9,8 +9,8 @@ import Utilities ghcCabalPackageArgs :: Args ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do - cabalDeps <- expr $ stage1Dependencies cabal - (_, cabalVersion) <- expr $ pkgNameVersion cabal + cabalDeps <- expr $ stage1Dependencies cabal + cabalVersion <- expr $ pkgVersion cabal mconcat [ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps, pkg /= parsec ] , arg "--make" From git at git.haskell.org Fri Oct 27 01:25:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Compute package synopsis directly from Cabal files (9105fc6) Message-ID: <20171027012538.838973A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9105fc6a676cbd97b26ec5edb86a15e681073cf9/ghc >--------------------------------------------------------------- commit 9105fc6a676cbd97b26ec5edb86a15e681073cf9 Author: Andrey Mokhov Date: Sun Aug 20 17:58:01 2017 +0100 Compute package synopsis directly from Cabal files >--------------------------------------------------------------- 9105fc6a676cbd97b26ec5edb86a15e681073cf9 src/Hadrian/Haskell/Cabal.hs | 16 ++++++++++++++-- src/Hadrian/Haskell/Cabal/Parse.hs | 8 +++++--- src/Hadrian/Utilities.hs | 23 +++++++++++++++-------- src/Oracles/PackageData.hs | 2 -- src/Rules/Data.hs | 3 +-- src/Rules/Library.hs | 6 +++--- src/Rules/Program.hs | 8 +++----- src/Settings/Builders/Haddock.hs | 2 +- 8 files changed, 42 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9105fc6a676cbd97b26ec5edb86a15e681073cf9 From git at git.haskell.org Fri Oct 27 01:25:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install rule: copy gmp header (#398) (8972c19) Message-ID: <20171027012542.258553A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8972c19ff590b61510677ea4057c2021869c4a74/ghc >--------------------------------------------------------------- commit 8972c19ff590b61510677ea4057c2021869c4a74 Author: Zhen Zhang Date: Wed Aug 23 18:51:25 2017 +0800 Install rule: copy gmp header (#398) >--------------------------------------------------------------- 8972c19ff590b61510677ea4057c2021869c4a74 src/Rules/Install.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs index 0d7336b..4858f40 100644 --- a/src/Rules/Install.hs +++ b/src/Rules/Install.hs @@ -185,6 +185,9 @@ installPackages = do installLibPkgs <- topsortPackages (filter isLibrary activePackages) + -- TODO (izgzhen): figure out what is the root cause of the missing ghc-gmp.h error + copyFile (pkgPath integerGmp -/- "gmp/ghc-gmp.h") (pkgPath integerGmp -/- "ghc-gmp.h") + forM_ installLibPkgs $ \pkg -> do when (isLibrary pkg) $ withLatestBuildStage pkg $ \stage -> do From git at git.haskell.org Fri Oct 27 01:25:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop defaultDestDir and use Shake's verbosity to control verbose commands (#400) (b25faf5) Message-ID: <20171027012545.D51B33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b25faf58f70159b741d6e13da7da329388914d65/ghc >--------------------------------------------------------------- commit b25faf58f70159b741d6e13da7da329388914d65 Author: Zhen Zhang Date: Thu Aug 24 02:44:47 2017 +0800 Drop defaultDestDir and use Shake's verbosity to control verbose commands (#400) >--------------------------------------------------------------- b25faf58f70159b741d6e13da7da329388914d65 README.md | 7 +++++-- src/UserSettings.hs | 14 ++++---------- 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/README.md b/README.md index ecf9728..ad61ef3 100644 --- a/README.md +++ b/README.md @@ -110,9 +110,12 @@ To build a GHC source distribution tarball, run Hadrian with the `sdist-ghc` tar To build and install GHC artifacts, run the `install` target. -By default, the artifacts will be installed to `` on your system. For example, -`ghc` will be installed to `/usr/local/bin`. By setting flag `--install-destdir=[DESTDIR]`, +By default, the artifacts will be installed to `` on your system +(in this case, the `DESTDIR` is empty, corresponds to the root of the file system). +For example on UNIX, `ghc` will be installed to `/usr/local/bin`. By setting flag `--install-destdir=[DESTDIR]`, you can install things to non-system path `DESTDIR/` instead. +Make sure you use correct absolute path on Windows, e.g. `C:/path`, +i.e. GHC is installed into `C:/path/usr/local` for the above example. #### Testing diff --git a/src/UserSettings.hs b/src/UserSettings.hs index d77d998..4a1db5b 100644 --- a/src/UserSettings.hs +++ b/src/UserSettings.hs @@ -4,7 +4,7 @@ -- accidentally commit them. module UserSettings ( userBuildRoot, userFlavours, userKnownPackages, verboseCommands, - buildProgressColour, successColour, defaultDestDir, defaultStage1Only + buildProgressColour, successColour, defaultStage1Only ) where import Hadrian.Utilities @@ -33,7 +33,9 @@ userKnownPackages = [] -- this is a 'Predicate', hence you can enable verbose output only for certain -- targets, e.g.: @verboseCommands = package ghcPrim at . verboseCommands :: Predicate -verboseCommands = return False +verboseCommands = do + verbosity <- expr getVerbosity + return $ verbosity >= Loud -- | Set colour for build progress messages (e.g. executing a build command). buildProgressColour :: BuildProgressColour @@ -43,14 +45,6 @@ buildProgressColour = BuildProgressColour (Dull, Magenta) successColour :: SuccessColour successColour = SuccessColour (Dull, Green) --- | Path to the GHC install destination. It is empty by default, which --- corresponds to the root of the file system. You can replace it by a specific --- directory. Make sure you use correct absolute path on Windows, e.g. "C:/path". --- The destination directory is used with a @prefix@, commonly @/usr/local@, --- i.e. GHC is installed into "C:/path/usr/local" for the above example. -defaultDestDir :: FilePath -defaultDestDir = "" - {- Stage1Only=YES means: - don't build ghc-stage2 (the executable) From git at git.haskell.org Fri Oct 27 01:25:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Remove unnecessary use of -DGENERICS flag (#402) (f189ed4) Message-ID: <20171027012549.61ABC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f189ed4db11f35a9f73e8e7bf7ae311a734aefb0/ghc >--------------------------------------------------------------- commit f189ed4db11f35a9f73e8e7bf7ae311a734aefb0 Author: Ryan Scott Date: Sat Aug 26 11:16:04 2017 -0400 Remove unnecessary use of -DGENERICS flag (#402) Mirroring a change made to GHC in http://git.haskell.org/ghc.git/commit/a28a55211d6fb8d3182b0a9e47656ff9ca8a3766 >--------------------------------------------------------------- f189ed4db11f35a9f73e8e7bf7ae311a734aefb0 src/Settings/Packages/GhcCabal.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 3c07c67..dba4f9b 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -18,7 +18,6 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" - , arg "-DGENERICS" , arg "-optP-include" , arg $ "-optP" ++ pkgPath ghcCabal -/- "cabal_macros_boot.h" , arg "-ilibraries/Cabal/Cabal" From git at git.haskell.org Fri Oct 27 01:25:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop mkUserGuidePart (74a6561) Message-ID: <20171027012552.EFCA63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/74a6561d67efe0d2719072cb15885a87fae35696/ghc >--------------------------------------------------------------- commit 74a6561d67efe0d2719072cb15885a87fae35696 Author: Andrey Mokhov Date: Sat Aug 26 17:34:23 2017 +0100 Drop mkUserGuidePart See #402 >--------------------------------------------------------------- 74a6561d67efe0d2719072cb15885a87fae35696 src/GHC.hs | 15 +++++++-------- src/Settings/Default.hs | 1 - 2 files changed, 7 insertions(+), 9 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index b790983..0adf259 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -5,10 +5,10 @@ module GHC ( compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, - hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart, - mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm, - templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix, - win32, xhtml, defaultKnownPackages, + hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, + parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, + terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml, + defaultKnownPackages, -- * Package information builderProvenance, programName, nonCabalContext, nonHsMainPackage, autogenPath, @@ -36,9 +36,9 @@ defaultKnownPackages = , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi - , mkUserGuidePart, mtl, parsec, parallel, pretty, primitive, process, rts - , runGhc, stm, templateHaskell, terminfo, text, time, touchy, transformers - , unlit, unix, win32, xhtml ] + , mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm + , templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix + , win32, xhtml ] -- | Package definitions, see 'Package'. array = lib "array" @@ -77,7 +77,6 @@ integerGmp = lib "integer-gmp" integerSimple = lib "integer-simple" iservBin = prg "iserv-bin" `setPath` "iserv" libffi = top "libffi" -mkUserGuidePart = util "mkUserGuidePart" mtl = lib "mtl" parsec = lib "parsec" parallel = lib "parallel" diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index c97b79f..d28df6c 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -115,7 +115,6 @@ stage0Packages = do , hsc2hs , hp2ps , hpc - , mkUserGuidePart , mtl , parsec , templateHaskell From git at git.haskell.org Fri Oct 27 01:25:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:25:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Differentiate between C and Haskell package (5ef696e) Message-ID: <20171027012556.8ACF03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe/ghc >--------------------------------------------------------------- commit 5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe Author: Andrey Mokhov Date: Sat Aug 26 23:31:31 2017 +0100 Differentiate between C and Haskell package >--------------------------------------------------------------- 5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe hadrian.cabal | 2 +- src/Base.hs | 4 +- src/Context.hs | 37 ++++++--- src/GHC.hs | 153 +++++++++++++++++++------------------ src/Hadrian/Haskell/Cabal.hs | 70 ++++++----------- src/Hadrian/Haskell/Cabal/Parse.hs | 10 +-- src/Hadrian/Haskell/Package.hs | 87 --------------------- src/Hadrian/Package.hs | 119 +++++++++++++++++++++++++++++ src/Rules/Data.hs | 2 +- src/Rules/Install.hs | 7 +- src/Rules/Library.hs | 2 +- src/Rules/Program.hs | 2 +- src/Settings/Builders/Ghc.hs | 5 +- src/Settings/Builders/GhcCabal.hs | 6 +- src/Settings/Builders/Haddock.hs | 8 +- src/Settings/Packages/GhcCabal.hs | 2 +- src/Utilities.hs | 8 +- 17 files changed, 275 insertions(+), 249 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 5ef696e4ebb7a0f7116bd89eee8bae9f7cf1bebe From git at git.haskell.org Fri Oct 27 01:26:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:00 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Do not run CI in verbose mode (f7c9b8b) Message-ID: <20171027012600.2F2E93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f7c9b8bf7a9816bedaf4e65271bd4993c1571143/ghc >--------------------------------------------------------------- commit f7c9b8bf7a9816bedaf4e65271bd4993c1571143 Author: Andrey Mokhov Date: Sun Aug 27 00:47:05 2017 +0100 Do not run CI in verbose mode >--------------------------------------------------------------- f7c9b8bf7a9816bedaf4e65271bd4993c1571143 .travis.yml | 6 +++--- appveyor.yml | 2 +- circle.yml | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 48ed171..9082ef6 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - ./build.cabal.sh selftest # Build GHC - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- - os: linux env: MODE="--flavour=quickest --integer-simple" @@ -40,7 +40,7 @@ matrix: script: # Build GHC - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- # Test GHC binary - cd .. @@ -56,7 +56,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- install: # Add Cabal to PATH diff --git a/appveyor.yml b/appveyor.yml index 3b2e43b..451d5d5 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -33,7 +33,7 @@ build_script: - stack exec hadrian -- --directory ".." selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --verbose --no-progress --progress-info=brief --progress-colour=never --profile=- + - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-info=brief --progress-colour=never --profile=- # Test GHC binary - cd .. diff --git a/circle.yml b/circle.yml index 606664a..b038689 100644 --- a/circle.yml +++ b/circle.yml @@ -33,7 +33,7 @@ compile: - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --verbose --no-progress --progress-colour=never --progress-info=brief --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- test: override: From git at git.haskell.org Fri Oct 27 01:26:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Simplify package lists (fc564b8) Message-ID: <20171027012603.BAE343A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fc564b8b05ed8e01493437635266df40dd125311/ghc >--------------------------------------------------------------- commit fc564b8b05ed8e01493437635266df40dd125311 Author: Andrey Mokhov Date: Sun Aug 27 03:08:20 2017 +0100 Simplify package lists See #403 >--------------------------------------------------------------- fc564b8b05ed8e01493437635266df40dd125311 src/Expression.hs | 3 +- src/Flavour.hs | 38 +++++++++++++-------- src/GHC.hs | 79 +++++++++++++++++++++++++++++++++++++++++++- src/Rules.hs | 2 +- src/Rules/Wrappers.hs | 3 +- src/Settings.hs | 9 +++-- src/Settings/Default.hs | 75 +---------------------------------------- src/Settings/Default.hs-boot | 4 +-- src/Utilities.hs | 7 ++-- 9 files changed, 117 insertions(+), 103 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 fc564b8b05ed8e01493437635266df40dd125311 From git at git.haskell.org Fri Oct 27 01:26:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor GHC/user packages, move builder-specific functions into Builder (0781e16) Message-ID: <20171027012607.63EA63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0781e16f1184adc1b35921924326df410ded3e31/ghc >--------------------------------------------------------------- commit 0781e16f1184adc1b35921924326df410ded3e31 Author: Andrey Mokhov Date: Mon Aug 28 01:56:06 2017 +0100 Refactor GHC/user packages, move builder-specific functions into Builder See #403 >--------------------------------------------------------------- 0781e16f1184adc1b35921924326df410ded3e31 src/Base.hs | 2 - src/Builder.hs | 91 +++++++++++++++++++++++++++++++++++- src/Expression.hs | 4 +- src/GHC.hs | 97 +++++++++++---------------------------- src/Oracles/ModuleFiles.hs | 1 + src/Rules.hs | 6 ++- src/Rules/Documentation.hs | 2 +- src/Rules/Perl.hs | 2 + src/Rules/SourceDist.hs | 1 + src/Settings.hs | 37 ++------------- src/Settings/Builders/Ghc.hs | 6 +-- src/Settings/Builders/GhcCabal.hs | 10 ++-- src/Target.hs | 3 +- src/UserSettings.hs | 8 ++-- src/Utilities.hs | 13 +----- 15 files changed, 148 insertions(+), 135 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 0781e16f1184adc1b35921924326df410ded3e31 From git at git.haskell.org Fri Oct 27 01:26:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add cross compilation (#401) (cbc2f63) Message-ID: <20171027012610.E1C8F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbc2f63dc60e084ffda3557c64a68856de924634/ghc >--------------------------------------------------------------- commit cbc2f63dc60e084ffda3557c64a68856de924634 Author: Zhen Zhang Date: Mon Aug 28 18:26:27 2017 +0800 Add cross compilation (#401) Tested with arm-linux-gnueabihf. >--------------------------------------------------------------- cbc2f63dc60e084ffda3557c64a68856de924634 doc/cross-compile.md | 57 ++++++++++++++++++++++++++++++++++++++ hadrian.cabal | 2 ++ src/Oracles/Flag.hs | 5 +--- src/Rules.hs | 1 + src/Settings.hs | 7 +---- src/Settings/Builders/Common.hs | 3 +- src/Settings/Default.hs | 6 +++- src/Settings/Packages/Compiler.hs | 2 ++ src/Settings/Packages/Ghc.hs | 4 ++- src/Settings/Packages/GhcPkg.hs | 8 ++++++ src/Settings/Packages/Haskeline.hs | 10 +++++++ src/UserSettings.hs | 12 ++++++-- 12 files changed, 101 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 cbc2f63dc60e084ffda3557c64a68856de924634 From git at git.haskell.org Fri Oct 27 01:26:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor refactoring: re-export Context and GHC from Expression (241ceff) Message-ID: <20171027012614.67E463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/241cefff1dfeb0729640996609f25c944b06bf38/ghc >--------------------------------------------------------------- commit 241cefff1dfeb0729640996609f25c944b06bf38 Author: Andrey Mokhov Date: Mon Aug 28 18:12:39 2017 +0100 Minor refactoring: re-export Context and GHC from Expression >--------------------------------------------------------------- 241cefff1dfeb0729640996609f25c944b06bf38 src/Expression.hs | 15 +++++++-------- src/Rules.hs | 2 -- src/Rules/Data.hs | 1 - src/Rules/Generate.hs | 2 -- src/Rules/Install.hs | 2 -- src/Rules/Library.hs | 1 - src/Rules/Program.hs | 1 - src/Rules/Test.hs | 1 - src/Rules/Wrappers.hs | 2 -- src/Settings.hs | 2 -- src/Settings/Builders/Common.hs | 4 ---- src/Settings/Default.hs | 1 - src/Settings/Packages/Base.hs | 1 - src/Settings/Packages/Cabal.hs | 1 - src/Settings/Packages/Compiler.hs | 1 - src/Settings/Packages/Ghc.hs | 2 -- src/Settings/Packages/GhcCabal.hs | 1 - src/Settings/Packages/GhcPkg.hs | 1 - src/Settings/Packages/GhcPrim.hs | 1 - src/Settings/Packages/Ghci.hs | 1 - src/Settings/Packages/Haddock.hs | 1 - src/Settings/Packages/Haskeline.hs | 2 -- src/Settings/Packages/IntegerGmp.hs | 1 - src/Settings/Packages/Rts.hs | 2 -- src/Settings/Packages/RunGhc.hs | 1 - src/Utilities.hs | 1 - 26 files changed, 7 insertions(+), 44 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 241cefff1dfeb0729640996609f25c944b06bf38 From git at git.haskell.org Fri Oct 27 01:26:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision of install stages (9dcd2a6) Message-ID: <20171027012617.D6DF63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9dcd2a6fd2a4799ec807af2418f52ab90f164273/ghc >--------------------------------------------------------------- commit 9dcd2a6fd2a4799ec807af2418f52ab90f164273 Author: Andrey Mokhov Date: Tue Aug 29 00:28:55 2017 +0100 Minor revision of install stages See #403 >--------------------------------------------------------------- 9dcd2a6fd2a4799ec807af2418f52ab90f164273 src/GHC.hs | 20 +++++++++---- src/Rules/Install.hs | 79 ++++++++++++++++++++++++--------------------------- src/Rules/Program.hs | 15 ++++++---- src/Rules/Wrappers.hs | 7 ++--- src/Settings.hs | 9 +----- 5 files changed, 64 insertions(+), 66 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9dcd2a6fd2a4799ec807af2418f52ab90f164273 From git at git.haskell.org Fri Oct 27 01:26:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix wrapper build (090e00a) Message-ID: <20171027012621.58FEC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/090e00af68efad88b82ae94e8f7a3a97375b6054/ghc >--------------------------------------------------------------- commit 090e00af68efad88b82ae94e8f7a3a97375b6054 Author: Andrey Mokhov Date: Tue Aug 29 00:46:19 2017 +0100 Fix wrapper build See #403 >--------------------------------------------------------------- 090e00af68efad88b82ae94e8f7a3a97375b6054 src/Rules/Program.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index c8a725e..b13f8a2 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -17,7 +17,7 @@ import Utilities -- TODO: Drop way in build rule generation? buildProgram :: [(Resource, Int)] -> Context -> Rules () buildProgram rs context at Context {..} = when (isProgram package) $ do - let installStage = do + let installStage = if package == ghc then return stage else do stages <- installStages package case stages of [s] -> return s @@ -33,7 +33,7 @@ buildProgram rs context at Context {..} = when (isProgram package) $ do -- Some binaries in inplace/bin are wrapped inplaceBinPath -/- programName context <.> exe %> \bin -> do context' <- programContext stage package - binStage <- if package == ghc then return stage else installStage + binStage <- installStage buildBinaryAndWrapper rs (context' { stage = binStage }) bin inplaceLibBinPath -/- programName context <.> exe %> \bin -> do From git at git.haskell.org Fri Oct 27 01:26:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refactor program build rules (7a5c384) Message-ID: <20171027012624.DF4123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67/ghc >--------------------------------------------------------------- commit 7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67 Author: Andrey Mokhov Date: Tue Aug 29 04:02:10 2017 +0100 Refactor program build rules See #403 >--------------------------------------------------------------- 7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67 src/GHC.hs | 49 +++++++++++++++++++-------------------- src/Rules.hs | 4 +++- src/Rules/Install.hs | 20 ++++++++-------- src/Rules/Program.hs | 63 ++++++++++++++++++++++++++------------------------- src/Rules/Wrappers.hs | 8 +++---- 5 files changed, 75 insertions(+), 69 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 7a5c384dc9cb8ae9d41c5203074d1e3a79bcca67 From git at git.haskell.org Fri Oct 27 01:26:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix wrapper build rules (9da5e17) Message-ID: <20171027012628.7FCD93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9da5e17c26e1c9d256052fa065e8c331635b4c5b/ghc >--------------------------------------------------------------- commit 9da5e17c26e1c9d256052fa065e8c331635b4c5b Author: Andrey Mokhov Date: Tue Aug 29 10:23:52 2017 +0100 Fix wrapper build rules See #403 >--------------------------------------------------------------- 9da5e17c26e1c9d256052fa065e8c331635b4c5b src/Rules/Program.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 13bfd34..0211cfe 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -14,6 +14,7 @@ import Settings.Packages.Rts import Target import Utilities +-- | TODO: Drop code duplication buildProgram :: [(Resource, Int)] -> Package -> Rules () buildProgram rs package = do forM_ [Stage0 ..] $ \stage -> do @@ -25,11 +26,19 @@ buildProgram rs package = do buildBinaryAndWrapper rs context' bin -- Rules for the GHC package, which is built 'inplace' - when (package == ghc) $ + when (package == ghc) $ do inplaceBinPath -/- programName context <.> exe %> \bin -> do context' <- programContext stage package buildBinaryAndWrapper rs context' bin + inplaceLibBinPath -/- programName context <.> exe %> \bin -> do + context' <- programContext stage package + buildBinary rs context' bin + + inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> do + context' <- programContext stage package + buildBinary rs context' bin + -- Rules for other programs built in inplace directories when (package /= ghc) $ do let context0 = vanillaContext Stage0 package -- TODO: get rid of context0 From git at git.haskell.org Fri Oct 27 01:26:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:32 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (de975b7) Message-ID: <20171027012632.0BE223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/de975b7282e8bdb003297e4804b58b090b89c61d/ghc >--------------------------------------------------------------- commit de975b7282e8bdb003297e4804b58b090b89c61d Author: Andrey Mokhov Date: Wed Aug 30 01:29:03 2017 +0100 Minor revision See #403 >--------------------------------------------------------------- de975b7282e8bdb003297e4804b58b090b89c61d src/Rules/Program.hs | 54 +++++++++++++++++++++++----------------------------- 1 file changed, 24 insertions(+), 30 deletions(-) diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs index 0211cfe..ba4dab0 100644 --- a/src/Rules/Program.hs +++ b/src/Rules/Program.hs @@ -21,54 +21,48 @@ buildProgram rs package = do let context = vanillaContext stage package -- Rules for programs built in 'buildRoot' - "//" ++ contextDir context -/- programName context <.> exe %> \bin -> do - context' <- programContext stage package - buildBinaryAndWrapper rs context' bin + "//" ++ contextDir context -/- programName context <.> exe %> \bin -> + buildBinaryAndWrapper rs bin =<< programContext stage package -- Rules for the GHC package, which is built 'inplace' when (package == ghc) $ do - inplaceBinPath -/- programName context <.> exe %> \bin -> do - context' <- programContext stage package - buildBinaryAndWrapper rs context' bin + inplaceBinPath -/- programName context <.> exe %> \bin -> + buildBinaryAndWrapper rs bin =<< programContext stage package - inplaceLibBinPath -/- programName context <.> exe %> \bin -> do - context' <- programContext stage package - buildBinary rs context' bin + inplaceLibBinPath -/- programName context <.> exe %> \bin -> + buildBinary rs bin =<< programContext stage package - inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> do - context' <- programContext stage package - buildBinary rs context' bin + inplaceLibBinPath -/- programName context <.> "bin" %> \bin -> + buildBinary rs bin =<< programContext stage package -- Rules for other programs built in inplace directories when (package /= ghc) $ do let context0 = vanillaContext Stage0 package -- TODO: get rid of context0 inplaceBinPath -/- programName context0 <.> exe %> \bin -> do - stage <- installStage package -- TODO: get rid of fromJust - context <- programContext (fromJust stage) package - buildBinaryAndWrapper rs context bin + stage <- installStage package -- TODO: get rid of fromJust + buildBinaryAndWrapper rs bin =<< programContext (fromJust stage) package inplaceLibBinPath -/- programName context0 <.> exe %> \bin -> do stage <- installStage package -- TODO: get rid of fromJust context <- programContext (fromJust stage) package if package /= iservBin then -- We *normally* build only unwrapped binaries in inplace/lib/bin - buildBinary rs context bin + buildBinary rs bin context else -- Build both binary and wrapper in inplace/lib/bin for iservBin - buildBinaryAndWrapperLib rs context bin + buildBinaryAndWrapperLib rs bin context inplaceLibBinPath -/- programName context0 <.> "bin" %> \bin -> do - stage <- installStage package -- TODO: get rid of fromJust - context <- programContext (fromJust stage) package - buildBinary rs context bin + stage <- installStage package -- TODO: get rid of fromJust + buildBinary rs bin =<< programContext (fromJust stage) package -buildBinaryAndWrapperLib :: [(Resource, Int)] -> Context -> FilePath -> Action () -buildBinaryAndWrapperLib rs context bin = do +buildBinaryAndWrapperLib :: [(Resource, Int)] -> FilePath -> Context -> Action () +buildBinaryAndWrapperLib rs bin context = do windows <- windowsHost if windows - then buildBinary rs context bin -- We don't build wrappers on Windows + then buildBinary rs bin context -- We don't build wrappers on Windows else case lookup context inplaceWrappers of - Nothing -> buildBinary rs context bin -- No wrapper found + Nothing -> buildBinary rs bin context -- No wrapper found Just wrapper -> do top <- topDirectory let libdir = top -/- inplaceLibPath @@ -76,13 +70,13 @@ buildBinaryAndWrapperLib rs context bin = do need [wrappedBin] buildWrapper context wrapper bin (WrappedBinary libdir (takeFileName wrappedBin)) -buildBinaryAndWrapper :: [(Resource, Int)] -> Context -> FilePath -> Action () -buildBinaryAndWrapper rs context bin = do +buildBinaryAndWrapper :: [(Resource, Int)] -> FilePath -> Context -> Action () +buildBinaryAndWrapper rs bin context = do windows <- windowsHost if windows - then buildBinary rs context bin -- We don't build wrappers on Windows + then buildBinary rs bin context -- We don't build wrappers on Windows else case lookup context inplaceWrappers of - Nothing -> buildBinary rs context bin -- No wrapper found + Nothing -> buildBinary rs bin context -- No wrapper found Just wrapper -> do top <- topDirectory let libPath = top -/- inplaceLibPath @@ -99,8 +93,8 @@ buildWrapper context at Context {..} wrapper wrapperPath wrapped = do quote (pkgName package) ++ " (" ++ show stage ++ ")." -- TODO: Get rid of the Paths_hsc2hs.o hack. -buildBinary :: [(Resource, Int)] -> Context -> FilePath -> Action () -buildBinary rs context at Context {..} bin = do +buildBinary :: [(Resource, Int)] -> FilePath -> Context -> Action () +buildBinary rs bin context at Context {..} = do binDeps <- if stage == Stage0 && package == ghcCabal then hsSources context else do From git at git.haskell.org Fri Oct 27 01:26:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dll-split (12e7d5f) Message-ID: <20171027012635.886C43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/12e7d5fc30e3776c29f3aba16985c72888f1a109/ghc >--------------------------------------------------------------- commit 12e7d5fc30e3776c29f3aba16985c72888f1a109 Author: Andrey Mokhov Date: Wed Aug 30 02:13:03 2017 +0100 Drop dll-split See #404 >--------------------------------------------------------------- 12e7d5fc30e3776c29f3aba16985c72888f1a109 src/GHC.hs | 17 +++++++---------- src/Rules.hs | 4 ++-- 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 7a9ff560..554cdae 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -2,7 +2,7 @@ module GHC ( -- * GHC packages array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, - compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath, + compiler, containers, deepseq, deriveConstants, directory, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, @@ -30,13 +30,12 @@ import Oracles.Setting ghcPackages :: [Package] ghcPackages = [ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes - , compiler, containers, deepseq, deriveConstants, directory, dllSplit - , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal - , ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs - , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi - , mtl, parsec, parallel, pretty, primitive, process, rts, runGhc, stm - , templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix - , win32, xhtml ] + , compiler, containers, deepseq, deriveConstants, directory, filepath + , genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact + , ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc + , hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, parallel + , pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo + , text, time, touchy, transformers, unlit, unix, win32, xhtml ] -- TODO: Optimise by switching to sets of packages. isGhcPackage :: Package -> Bool @@ -55,7 +54,6 @@ containers = hsLib "containers" deepseq = hsLib "deepseq" deriveConstants = hsUtil "deriveConstants" directory = hsLib "directory" -dllSplit = hsUtil "dll-split" filepath = hsLib "filepath" genapply = hsUtil "genapply" genprimopcode = hsUtil "genprimopcode" @@ -144,7 +142,6 @@ stage0Packages = do , compareSizes , compiler , deriveConstants - , dllSplit , genapply , genprimopcode , ghc diff --git a/src/Rules.hs b/src/Rules.hs index 09610d7..fcf3f65 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -126,5 +126,5 @@ oracleRules = do Oracles.ModuleFiles.moduleFilesOracle programsStage1Only :: [Package] -programsStage1Only = [ deriveConstants, dllSplit, genapply, genprimopcode, ghc - , ghcCabal, ghcPkg, hp2ps, hpc, hsc2hs, runGhc ] +programsStage1Only = [ deriveConstants, genapply, genprimopcode, ghc, ghcCabal + , ghcPkg, hp2ps, hpc, hsc2hs, runGhc ] From git at git.haskell.org Fri Oct 27 01:26:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:39 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop dll-split related arguments to ghc-cabal (8f5ad00) Message-ID: <20171027012639.0B1D73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/8f5ad00e81b98ab84708737d24d90457250e3873/ghc >--------------------------------------------------------------- commit 8f5ad00e81b98ab84708737d24d90457250e3873 Author: Andrey Mokhov Date: Wed Aug 30 10:47:16 2017 +0100 Drop dll-split related arguments to ghc-cabal See #404 >--------------------------------------------------------------- 8f5ad00e81b98ab84708737d24d90457250e3873 src/Settings/Builders/GhcCabal.hs | 173 -------------------------------------- 1 file changed, 173 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index 4fd598b..475cc65 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -18,7 +18,6 @@ ghcCabalBuilderArgs = builder GhcCabal ? do mconcat [ arg "configure" , arg =<< pkgPath <$> getPackage , arg $ top -/- path - , dll0Args , withStaged $ Ghc CompileHs , withStaged (GhcPkg Update) , bootPackageDatabaseArgs @@ -127,175 +126,3 @@ with b = do withStaged :: (Stage -> Builder) -> Args withStaged sb = with . sb =<< getStage --- This is a positional argument, hence: --- * if it is empty, we need to emit one empty string argument; --- * otherwise, we must collapse it into one space-separated string. -dll0Args :: Args -dll0Args = do - context <- getContext - dll0 <- expr $ buildDll0 context - withGhci <- expr ghcWithInterpreter - arg . unwords . concat $ [ modules | dll0 ] - ++ [ ghciModules | dll0 && withGhci ] -- see #9552 - where - modules = [ "Annotations" - , "ApiAnnotation" - , "Avail" - , "Bag" - , "BasicTypes" - , "Binary" - , "BooleanFormula" - , "BreakArray" - , "BufWrite" - , "Class" - , "CmdLineParser" - , "CmmType" - , "CoAxiom" - , "ConLike" - , "Coercion" - , "Config" - , "Constants" - , "CoreArity" - , "CoreFVs" - , "CoreSubst" - , "CoreSyn" - , "CoreTidy" - , "CoreUnfold" - , "CoreUtils" - , "CoreSeq" - , "CoreStats" - , "CostCentre" - , "Ctype" - , "DataCon" - , "Demand" - , "Digraph" - , "DriverPhases" - , "DynFlags" - , "Encoding" - , "ErrUtils" - , "Exception" - , "ExtsCompat46" - , "FamInstEnv" - , "FastFunctions" - , "FastMutInt" - , "FastString" - , "FastTypes" - , "Fingerprint" - , "FiniteMap" - , "ForeignCall" - , "Hooks" - , "HsBinds" - , "HsDecls" - , "HsDoc" - , "HsExpr" - , "HsImpExp" - , "HsLit" - , "PlaceHolder" - , "HsPat" - , "HsSyn" - , "HsTypes" - , "HsUtils" - , "HscTypes" - , "IOEnv" - , "Id" - , "IdInfo" - , "IfaceSyn" - , "IfaceType" - , "InstEnv" - , "Kind" - , "Lexeme" - , "Lexer" - , "ListSetOps" - , "Literal" - , "Maybes" - , "MkCore" - , "MkId" - , "Module" - , "MonadUtils" - , "Name" - , "NameEnv" - , "NameSet" - , "OccName" - , "OccurAnal" - , "OptCoercion" - , "OrdList" - , "Outputable" - , "PackageConfig" - , "Packages" - , "Pair" - , "Panic" - , "PatSyn" - , "PipelineMonad" - , "Platform" - , "PlatformConstants" - , "PprCore" - , "PrelNames" - , "PrelRules" - , "Pretty" - , "PrimOp" - , "RdrName" - , "Rules" - , "Serialized" - , "SrcLoc" - , "StaticFlags" - , "StringBuffer" - , "TcEvidence" - , "TcRnTypes" - , "TcType" - , "TrieMap" - , "TyCon" - , "Type" - , "TypeRep" - , "TysPrim" - , "TysWiredIn" - , "Unify" - , "UniqFM" - , "UniqSet" - , "UniqSupply" - , "Unique" - , "Util" - , "Var" - , "VarEnv" - , "VarSet" ] - ghciModules = [ "Bitmap" - , "BlockId" - , "ByteCodeAsm" - , "ByteCodeInstr" - , "ByteCodeItbls" - , "CLabel" - , "Cmm" - , "CmmCallConv" - , "CmmExpr" - , "CmmInfo" - , "CmmMachOp" - , "CmmNode" - , "CmmSwitch" - , "CmmUtils" - , "CodeGen.Platform" - , "CodeGen.Platform.ARM" - , "CodeGen.Platform.ARM64" - , "CodeGen.Platform.NoRegs" - , "CodeGen.Platform.PPC" - , "CodeGen.Platform.PPC_Darwin" - , "CodeGen.Platform.SPARC" - , "CodeGen.Platform.X86" - , "CodeGen.Platform.X86_64" - , "FastBool" - , "InteractiveEvalTypes" - , "MkGraph" - , "PprCmm" - , "PprCmmDecl" - , "PprCmmExpr" - , "Reg" - , "RegClass" - , "SMRep" - , "StgCmmArgRep" - , "StgCmmClosure" - , "StgCmmEnv" - , "StgCmmLayout" - , "StgCmmMonad" - , "StgCmmProf" - , "StgCmmTicky" - , "StgCmmUtils" - , "StgSyn" - , "Stream" ] From git at git.haskell.org Fri Oct 27 01:26:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out common builder-related functionality into the library (29046aa) Message-ID: <20171027012642.871393A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/29046aa3b29a26e69db1bf38015f9376bfad2ff0/ghc >--------------------------------------------------------------- commit 29046aa3b29a26e69db1bf38015f9376bfad2ff0 Author: Andrey Mokhov Date: Thu Aug 31 03:24:11 2017 +0100 Factor out common builder-related functionality into the library See #347 >--------------------------------------------------------------- 29046aa3b29a26e69db1bf38015f9376bfad2ff0 hadrian.cabal | 1 + src/Builder.hs | 127 +++++++++++++++++++++++++++++++++++++------- src/Hadrian/Builder.hs | 118 ++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Expression.hs | 9 +++- src/Hadrian/Utilities.hs | 9 +++- src/Main.hs | 4 +- src/Rules/Configure.hs | 1 + src/Rules/Install.hs | 2 +- src/Rules/Perl.hs | 3 +- src/Rules/Selftest.hs | 1 - src/Rules/SourceDist.hs | 6 +-- src/Settings/Builders/Ar.hs | 42 +-------------- src/UserSettings.hs | 8 +-- src/Utilities.hs | 117 ++++------------------------------------ 14 files changed, 266 insertions(+), 182 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 29046aa3b29a26e69db1bf38015f9376bfad2ff0 From git at git.haskell.org Fri Oct 27 01:26:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision: move builder-related functionality to Builder modules (f970bfc) Message-ID: <20171027012645.F35ED3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f970bfc05c13768aa980400ff5bf7c0c4652a224/ghc >--------------------------------------------------------------- commit f970bfc05c13768aa980400ff5bf7c0c4652a224 Author: Andrey Mokhov Date: Fri Sep 1 23:31:38 2017 +0100 Minor revision: move builder-related functionality to Builder modules >--------------------------------------------------------------- f970bfc05c13768aa980400ff5bf7c0c4652a224 src/Builder.hs | 60 ++++++++++++++++++++++++++++++++++++++++++- src/Hadrian/Builder.hs | 10 +++++++- src/Utilities.hs | 70 +++----------------------------------------------- 3 files changed, 71 insertions(+), 69 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 f970bfc05c13768aa980400ff5bf7c0c4652a224 From git at git.haskell.org Fri Oct 27 01:26:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Factor out common Ar functionality into the library (655d175) Message-ID: <20171027012649.6FE4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/655d175354db5afb5c3519cb13672209e66e5f95/ghc >--------------------------------------------------------------- commit 655d175354db5afb5c3519cb13672209e66e5f95 Author: Andrey Mokhov Date: Sun Sep 3 00:38:06 2017 +0100 Factor out common Ar functionality into the library See #347 >--------------------------------------------------------------- 655d175354db5afb5c3519cb13672209e66e5f95 hadrian.cabal | 2 +- src/Builder.hs | 40 ++++--------------------------- src/Hadrian/Builder/Ar.hs | 57 +++++++++++++++++++++++++++++++++++++++++++++ src/Hadrian/Utilities.hs | 17 +++++++++++++- src/Oracles/Setting.hs | 17 -------------- src/Settings/Builders/Ar.hs | 8 ------- src/Settings/Default.hs | 5 ++-- 7 files changed, 82 insertions(+), 64 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 655d175354db5afb5c3519cb13672209e66e5f95 From git at git.haskell.org Fri Oct 27 01:26:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add ArMode to distinguish packing and unpacking of archives (46a37b1) Message-ID: <20171027012652.DED613A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/46a37b154ae7b749c074c32efbcfb772d40502a8/ghc >--------------------------------------------------------------- commit 46a37b154ae7b749c074c32efbcfb772d40502a8 Author: Andrey Mokhov Date: Sun Sep 3 13:31:00 2017 +0100 Add ArMode to distinguish packing and unpacking of archives >--------------------------------------------------------------- 46a37b154ae7b749c074c32efbcfb772d40502a8 src/Builder.hs | 44 ++++++++++++++------------------------- src/Hadrian/Builder/Ar.hs | 19 +++++++++++++---- src/Rules/Gmp.hs | 7 ++++--- src/Rules/Libffi.hs | 2 +- src/Rules/Library.hs | 4 ++-- src/Settings/Builders/GhcCabal.hs | 4 ++-- src/Settings/Default.hs | 3 ++- 7 files changed, 42 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 46a37b154ae7b749c074c32efbcfb772d40502a8 From git at git.haskell.org Fri Oct 27 01:26:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Mark as temporarily out-of-date (c3f0f40) Message-ID: <20171027012656.6E3133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c3f0f40954cedc37bc2d0e5c724ccd20d7fa51ed/ghc >--------------------------------------------------------------- commit c3f0f40954cedc37bc2d0e5c724ccd20d7fa51ed Author: Andrey Mokhov Date: Fri Sep 8 23:38:45 2017 +0100 Mark as temporarily out-of-date >--------------------------------------------------------------- c3f0f40954cedc37bc2d0e5c724ccd20d7fa51ed doc/user-settings.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/doc/user-settings.md b/doc/user-settings.md index 9207f7f..1898dcd 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -1,3 +1,6 @@ +**Note:** This document is currently out-of-date and will be fixed after +[a major refactoring](https://github.com/snowleopard/hadrian/issues/347). + # User settings You can customise Hadrian by copying the file `hadrian/src/UserSettings.hs` to From git at git.haskell.org Fri Oct 27 01:26:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:26:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add support for llvm-targets (6d14f09) Message-ID: <20171027012659.E268E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6d14f09c81f490704d2798693236f0db68e6e438/ghc >--------------------------------------------------------------- commit 6d14f09c81f490704d2798693236f0db68e6e438 Author: Andrey Mokhov Date: Sat Sep 9 11:39:57 2017 +0100 Add support for llvm-targets See #412 >--------------------------------------------------------------- 6d14f09c81f490704d2798693236f0db68e6e438 cfg/system.config.in | 1 + src/Base.hs | 1 + src/Oracles/Setting.hs | 2 ++ src/Rules/Generate.hs | 5 ++++- 4 files changed, 8 insertions(+), 1 deletion(-) diff --git a/cfg/system.config.in b/cfg/system.config.in index 34ef7b9..0b05259 100644 --- a/cfg/system.config.in +++ b/cfg/system.config.in @@ -63,6 +63,7 @@ target-platform-full = @TargetPlatformFull@ target-arch = @TargetArch_CPP@ target-os = @TargetOS_CPP@ target-vendor = @TargetVendor_CPP@ +llvm-target = @LLVMTarget_CPP@ cross-compiling = @CrossCompiling@ diff --git a/src/Base.hs b/src/Base.hs index 942b272..76e8f2b 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -106,6 +106,7 @@ inplaceLibCopyTargets :: [FilePath] inplaceLibCopyTargets = map (inplaceLibPath -/-) [ "ghc-usage.txt" , "ghci-usage.txt" + , "llvm-targets" , "platformConstants" , "settings" , "template-hsc.h" ] diff --git a/src/Oracles/Setting.hs b/src/Oracles/Setting.hs index 8af8f38..5f148d4 100644 --- a/src/Oracles/Setting.hs +++ b/src/Oracles/Setting.hs @@ -46,6 +46,7 @@ data Setting = BuildArch | TargetPlatform | TargetPlatformFull | TargetVendor + | LlvmTarget | FfiIncludeDir | FfiLibDir | GmpIncludeDir @@ -104,6 +105,7 @@ setting key = lookupValueOrError configFile $ case key of TargetPlatform -> "target-platform" TargetPlatformFull -> "target-platform-full" TargetVendor -> "target-vendor" + LlvmTarget -> "llvm-target" FfiIncludeDir -> "ffi-include-dir" FfiLibDir -> "ffi-lib-dir" GmpIncludeDir -> "gmp-include-dir" diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index b23b72d..413abe5 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -11,9 +11,9 @@ import Oracles.ModuleFiles import Oracles.Setting import Rules.Gmp import Rules.Libffi +import Target import Settings import Settings.Packages.Rts -import Target import Utilities -- | Track this file to rebuild generated files whenever it changes. @@ -145,6 +145,7 @@ copyRules :: Rules () copyRules = do (inplaceLibPath -/- "ghc-usage.txt") <~ return "driver" (inplaceLibPath -/- "ghci-usage.txt" ) <~ return "driver" + (inplaceLibPath -/- "llvm-targets") <~ return "." (inplaceLibPath -/- "platformConstants") <~ (buildRoot <&> (-/- generatedDir)) (inplaceLibPath -/- "settings") <~ return "." (inplaceLibPath -/- "template-hsc.h") <~ return (pkgPath hsc2hs) @@ -394,6 +395,7 @@ generateGhcBootPlatformH = do hostVendor <- chooseSetting HostVendor TargetVendor targetPlatform <- getSetting TargetPlatform targetArch <- getSetting TargetArch + llvmTarget <- getSetting LlvmTarget targetOs <- getSetting TargetOs targetVendor <- getSetting TargetVendor return $ unlines @@ -414,6 +416,7 @@ generateGhcBootPlatformH = do , "#define BUILD_ARCH " ++ show buildArch , "#define HOST_ARCH " ++ show hostArch , "#define TARGET_ARCH " ++ show targetArch + , "#define LLVM_TARGET " ++ show llvmTarget , "" , "#define " ++ buildOs ++ "_BUILD_OS 1" , "#define " ++ hostOs ++ "_HOST_OS 1" From git at git.haskell.org Fri Oct 27 01:27:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop support for -this-package-key (95a23a6) Message-ID: <20171027012703.76C183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/95a23a6667824592499775d746a71ee2b8de07fe/ghc >--------------------------------------------------------------- commit 95a23a6667824592499775d746a71ee2b8de07fe Author: Andrey Mokhov Date: Sun Sep 10 23:45:34 2017 +0100 Drop support for -this-package-key >--------------------------------------------------------------- 95a23a6667824592499775d746a71ee2b8de07fe src/Oracles/Flag.hs | 4 +--- src/Settings/Builders/Ghc.hs | 9 ++------- 2 files changed, 3 insertions(+), 10 deletions(-) diff --git a/src/Oracles/Flag.hs b/src/Oracles/Flag.hs index 20aca1f..510b9d2 100644 --- a/src/Oracles/Flag.hs +++ b/src/Oracles/Flag.hs @@ -17,7 +17,6 @@ data Flag = ArSupportsAtFile | LeadingUnderscore | SolarisBrokenShld | SplitObjectsBroken - | SupportsThisUnitId | WithLibdw | UseSystemFfi @@ -35,12 +34,11 @@ flag f = do LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" SplitObjectsBroken -> "split-objects-broken" - SupportsThisUnitId -> "supports-this-unit-id" WithLibdw -> "with-libdw" UseSystemFfi -> "use-system-ffi" value <- lookupValueOrError configFile key when (value `notElem` ["YES", "NO", ""]) . error $ "Configuration flag " - ++ quote (key ++ " = " ++ value) ++ "cannot be parsed." + ++ quote (key ++ " = " ++ value) ++ " cannot be parsed." return $ value == "YES" platformSupportsSharedLibs :: Action Bool diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index a186e08..7f942f6 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -115,18 +115,13 @@ wayGhcArgs = do , (way == debug || way == debugDynamic) ? pure ["-ticky", "-DTICKY_TICKY"] ] --- FIXME: Get rid of to-be-deprecated -this-package-key. packageGhcArgs :: Args packageGhcArgs = withHsPackage $ \cabalFile -> do - pkgId <- expr $ pkgIdentifier cabalFile - thisArg <- do - not0 <- notStage0 - unit <- expr $ flag SupportsThisUnitId - return $ if not0 || unit then "-this-unit-id " else "-this-package-key " + pkgId <- expr $ pkgIdentifier cabalFile mconcat [ arg "-hide-all-packages" , arg "-no-user-package-db" , bootPackageDatabaseArgs - , libraryPackage ? arg (thisArg ++ pkgId) + , libraryPackage ? arg ("-this-unit-id " ++ pkgId) , map ("-package-id " ++) <$> getPkgDataList DepIds ] includeGhcArgs :: Args From git at git.haskell.org Fri Oct 27 01:27:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop cabal_macros_boot.h (bece422) Message-ID: <20171027012707.1D6C93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/bece42266ac98ebbcd901efd62d1ffaf68a482ef/ghc >--------------------------------------------------------------- commit bece42266ac98ebbcd901efd62d1ffaf68a482ef Author: Andrey Mokhov Date: Mon Sep 11 00:03:59 2017 +0100 Drop cabal_macros_boot.h >--------------------------------------------------------------- bece42266ac98ebbcd901efd62d1ffaf68a482ef src/Settings/Packages/GhcCabal.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index 0e6e1ea..b525c31 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -17,8 +17,6 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do , arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion) , arg "-DBOOTSTRAPPING" , arg "-DMIN_VERSION_binary_0_8_0" - , arg "-optP-include" - , arg $ "-optP" ++ pkgPath ghcCabal -/- "cabal_macros_boot.h" , arg "-ilibraries/Cabal/Cabal" , arg "-ilibraries/binary/src" , arg "-ilibraries/filepath" From git at git.haskell.org Fri Oct 27 01:27:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Refine cross-compilation implementation (#410) (ae1f7c1) Message-ID: <20171027012710.8B6DC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c/ghc >--------------------------------------------------------------- commit ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c Author: Zhen Zhang Date: Tue Sep 12 00:54:29 2017 +0800 Refine cross-compilation implementation (#410) * Update minimum heap size * Refine cross-compilation implementation >--------------------------------------------------------------- ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c hadrian.cabal | 1 + src/GHC.hs | 4 +++- src/Oracles/Flag.hs | 5 ++++- src/Settings.hs | 4 +++- src/Settings/Builders/Common.hs | 3 ++- src/Settings/Flavours/Development.hs | 2 +- src/Settings/Flavours/Performance.hs | 2 +- src/Settings/Flavours/Profiled.hs | 2 +- src/Settings/Flavours/Quick.hs | 2 +- src/Settings/Flavours/QuickCross.hs | 23 +++++++++++++++++++++++ src/Settings/Flavours/Quickest.hs | 2 +- src/Settings/Packages/Compiler.hs | 2 +- src/Settings/Packages/Ghc.hs | 2 +- src/Settings/Packages/GhcPkg.hs | 4 ++-- src/Settings/Packages/Haskeline.hs | 2 +- src/UserSettings.hs | 7 +------ 16 files changed, 47 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ae1f7c1b1317afe6ce478f5fa8a954416cb6e19c From git at git.haskell.org Fri Oct 27 01:27:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:14 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix performance bug: Stage0 packages do not depend on inplaceLibCopyTargets (17be7a1) Message-ID: <20171027012714.350D13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/17be7a10e780a792e7082aa1f8bef0b0887957a5/ghc >--------------------------------------------------------------- commit 17be7a10e780a792e7082aa1f8bef0b0887957a5 Author: Andrey Mokhov Date: Thu Sep 14 01:13:37 2017 +0100 Fix performance bug: Stage0 packages do not depend on inplaceLibCopyTargets See #393 >--------------------------------------------------------------- 17be7a10e780a792e7082aa1f8bef0b0887957a5 src/Settings/Builders/GhcCabal.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs index fc39637..c555bf0 100644 --- a/src/Settings/Builders/GhcCabal.hs +++ b/src/Settings/Builders/GhcCabal.hs @@ -6,15 +6,14 @@ import Hadrian.Haskell.Cabal import Context import Flavour -import Settings.Builders.Common hiding (package) +import Settings.Builders.Common ghcCabalBuilderArgs :: Args ghcCabalBuilderArgs = builder GhcCabal ? do verbosity <- expr getVerbosity top <- expr topDirectory - context <- getContext path <- getBuildPath - when (package context /= deriveConstants) $ expr (need inplaceLibCopyTargets) + notStage0 ? expr (need inplaceLibCopyTargets) mconcat [ arg "configure" , arg =<< pkgPath <$> getPackage , arg $ top -/- path From git at git.haskell.org Fri Oct 27 01:27:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:17 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add missing dependency of hsc2hs on template-hsc.h (fdd223e) Message-ID: <20171027012717.9C4B63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fdd223e91e2d5226bc6f589e3a17808b5b8eef6a/ghc >--------------------------------------------------------------- commit fdd223e91e2d5226bc6f589e3a17808b5b8eef6a Author: Andrey Mokhov Date: Thu Sep 14 12:54:59 2017 +0100 Add missing dependency of hsc2hs on template-hsc.h >--------------------------------------------------------------- fdd223e91e2d5226bc6f589e3a17808b5b8eef6a src/Builder.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Builder.hs b/src/Builder.hs index d70ecab..2e8aca1 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -124,6 +124,8 @@ instance H.Builder Builder where needBuilder :: Builder -> Action () needBuilder (Configure dir) = need [dir -/- "configure"] + needBuilder Hsc2Hs = do path <- H.builderPath Hsc2Hs + need [path, templateHscPath] needBuilder (Make dir) = need [dir -/- "Makefile"] needBuilder builder = when (isJust $ builderProvenance builder) $ do path <- H.builderPath builder From git at git.haskell.org Fri Oct 27 01:27:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:21 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Need rts at the top-level to allow more parallelism (adc8e35) Message-ID: <20171027012721.10CF83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/adc8e3531a5e301b4c00eaf4372c8a3b8a0205cc/ghc >--------------------------------------------------------------- commit adc8e3531a5e301b4c00eaf4372c8a3b8a0205cc Author: Andrey Mokhov Date: Thu Sep 14 18:23:47 2017 +0100 Need rts at the top-level to allow more parallelism See #393 >--------------------------------------------------------------- adc8e3531a5e301b4c00eaf4372c8a3b8a0205cc src/Rules.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Rules.hs b/src/Rules.hs index fcf3f65..ea3df45 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -32,7 +32,7 @@ allStages = [minBound ..] -- 'Stage1Only' flag. topLevelTargets :: Rules () topLevelTargets = action $ do - let libraryPackages = filter isLibrary (knownPackages \\ [rts, libffi]) + let libraryPackages = filter isLibrary (knownPackages \\ [libffi]) need =<< if stage1Only then do libs <- concatForM [Stage0, Stage1] $ \stage -> @@ -41,11 +41,10 @@ topLevelTargets = action $ do return $ libs ++ prgs ++ inplaceLibCopyTargets else do targets <- concatForM allStages $ \stage -> - concatForM (knownPackages \\ [rts, libffi]) $ + concatForM (knownPackages \\ [libffi]) $ packageTargets False stage return $ targets ++ inplaceLibCopyTargets - -- TODO: Get rid of the @includeGhciLib@ hack. -- | Return the list of targets associated with a given 'Stage' and 'Package'. -- By setting the Boolean parameter to False it is possible to exclude the GHCi @@ -62,14 +61,15 @@ packageTargets includeGhciLib stage pkg = do then return [] -- Skip inactive packages. else if isLibrary pkg then do -- Collect all targets of a library package. - ways <- interpretInContext context getLibraryWays + let pkgWays = if pkg == rts then getRtsWays else getLibraryWays + ways <- interpretInContext context pkgWays libs <- mapM (pkgLibraryFile . Context stage pkg) ways docs <- interpretInContext context =<< buildHaddock <$> flavour more <- libraryTargets includeGhciLib context setup <- pkgSetupConfigFile context haddock <- pkgHaddockFile context - return $ [ setup | nonCabalContext context ] - ++ [ haddock | docs && stage == Stage1 ] + return $ [ setup | not $ nonCabalContext context ] + ++ [ haddock | pkg /= rts && docs && stage == Stage1 ] ++ libs ++ more else do -- The only target of a program package is the executable. prgContext <- programContext stage pkg From git at git.haskell.org Fri Oct 27 01:27:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:24 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Optimise stage1 compiler (9a1b659) Message-ID: <20171027012724.9FF643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9a1b6591a9a91097ac93dd1d461d8fac2856ed66/ghc >--------------------------------------------------------------- commit 9a1b6591a9a91097ac93dd1d461d8fac2856ed66 Author: Andrey Mokhov Date: Fri Sep 15 00:46:38 2017 +0100 Optimise stage1 compiler See #393 >--------------------------------------------------------------- 9a1b6591a9a91097ac93dd1d461d8fac2856ed66 doc/flavours.md | 4 ++-- src/Settings/Flavours/Quickest.hs | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index 3bf0c30..042475e 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -61,9 +61,9 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O0
-H32m + -O - - + -O diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs index 3c507bc..88922ec 100644 --- a/src/Settings/Flavours/Quickest.hs +++ b/src/Settings/Flavours/Quickest.hs @@ -15,8 +15,8 @@ quickestArgs :: Args quickestArgs = sourceArgs $ SourceArgs { hsDefault = pure ["-O0", "-H64m"] , hsLibrary = mempty - , hsCompiler = mempty - , hsGhc = mempty } + , hsCompiler = stage0 ? arg "-O" + , hsGhc = stage0 ? arg "-O" } quickestRtsWays :: Ways quickestRtsWays = mconcat From git at git.haskell.org Fri Oct 27 01:27:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:28 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update docs to list -H64m (101d787) Message-ID: <20171027012728.24D133A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/101d78755ac2f1afd71eb7c9165afb9a84705c9a/ghc >--------------------------------------------------------------- commit 101d78755ac2f1afd71eb7c9165afb9a84705c9a Author: Andrey Mokhov Date: Fri Sep 15 01:24:53 2017 +0100 Update docs to list -H64m [skip ci] >--------------------------------------------------------------- 101d78755ac2f1afd71eb7c9165afb9a84705c9a doc/flavours.md | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/doc/flavours.md b/doc/flavours.md index 042475e..185cf6b 100644 --- a/doc/flavours.md +++ b/doc/flavours.md @@ -35,8 +35,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH default
- -O
-H32m
- -O2
-H32m + -O
-H64m
+ -O2
-H64m @@ -46,8 +46,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quick - -O0
-H32m - -O0
-H32m + -O0
-H64m + -O0
-H64m -O -O @@ -57,8 +57,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH quickest - -O0
-H32m - -O0
-H32m + -O0
-H64m + -O0
-H64m -O @@ -68,8 +68,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH perf - -O
-H32m - -O
-H32m + -O
-H64m + -O
-H64m -O2 -O @@ -79,8 +79,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH prof - -O0
-H32m - -O0
-H32m + -O0
-H64m + -O0
-H64m -O -O @@ -90,8 +90,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel1 - -O
-H32m - -O
-H32m + -O
-H64m + -O
-H64m -dcore-lint -O0
-DDEBUG @@ -101,8 +101,8 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH devel2 - -O
-H32m - -O
-H32m + -O
-H64m + -O
-H64m -dcore-lint From git at git.haskell.org Fri Oct 27 01:27:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:31 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement documentation building (#413) (97fa508) Message-ID: <20171027012731.98C183A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d/ghc >--------------------------------------------------------------- commit 97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d Author: Patrick Dougherty Date: Sat Sep 16 07:14:30 2017 -0500 Implement documentation building (#413) * Implement documentation building * Clean up for merge >--------------------------------------------------------------- 97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d cfg/system.config.in | 3 +- hadrian.cabal | 2 + src/Builder.hs | 55 +++++++++++--- src/Context.hs | 6 +- src/Main.hs | 2 + src/Rules/Documentation.hs | 155 +++++++++++++++++++++++++++++++++++--- src/Rules/Gmp.hs | 2 +- src/Rules/Install.hs | 3 - src/Rules/Libffi.hs | 2 +- src/Rules/SourceDist.hs | 2 +- src/Rules/Test.hs | 2 +- src/Settings/Builders/GhcCabal.hs | 11 +-- src/Settings/Builders/Haddock.hs | 92 +++++++++++----------- src/Settings/Builders/Sphinx.hs | 22 ++++++ src/Settings/Builders/Tar.hs | 20 +++-- src/Settings/Builders/Xelatex.hs | 7 ++ src/Settings/Default.hs | 7 +- src/Settings/Packages/Compiler.hs | 2 +- 18 files changed, 298 insertions(+), 97 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 97fa508d5ff8ebabee6623fbc3d89cc8ee953f2d From git at git.haskell.org Fri Oct 27 01:27:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:35 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Avoid running commands with the Shell option, which breaks due to spaces in paths (f479c5d) Message-ID: <20171027012735.3CA463A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f479c5d51dfee88abaad7dc3aeb19ea518948a19/ghc >--------------------------------------------------------------- commit f479c5d51dfee88abaad7dc3aeb19ea518948a19 Author: Andrey Mokhov Date: Sun Sep 17 00:41:12 2017 +0100 Avoid running commands with the Shell option, which breaks due to spaces in paths * Fixes the docs build rule on Windows See #414 >--------------------------------------------------------------- f479c5d51dfee88abaad7dc3aeb19ea518948a19 src/Builder.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index 72cbb15..355878f 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -185,7 +185,7 @@ instance H.Builder Builder where -- otherwise Windows breaks. TODO: Figure out why. bash <- bashPath let env = AddEnv "CONFIG_SHELL" bash - cmd Shell echo env [Cwd dir] [path] buildOptions buildArgs + cmd echo env [Cwd dir] ["sh", path] buildOptions buildArgs HsCpp -> captureStdout GenApply -> captureStdout @@ -195,16 +195,15 @@ instance H.Builder Builder where Stdout stdout <- cmd (Stdin stdin) [path] buildArgs writeFileChanged output stdout - Make dir -> cmd Shell echo path ["-C", dir] buildArgs + Make dir -> cmd echo path ["-C", dir] buildArgs Xelatex -> do - unit $ cmd Shell [Cwd output] [path] buildArgs - unit $ cmd Shell [Cwd output] [path] buildArgs - unit $ cmd Shell [Cwd output] [path] buildArgs - unit $ cmd Shell [Cwd output] ["makeindex"] - (input -<.> "idx") - unit $ cmd Shell [Cwd output] [path] buildArgs - cmd Shell [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] ["makeindex"] (input -<.> "idx") + unit $ cmd [Cwd output] [path] buildArgs + unit $ cmd [Cwd output] [path] buildArgs _ -> cmd echo [path] buildArgs @@ -226,7 +225,7 @@ systemBuilderPath builder = case builder of Cc _ Stage0 -> fromKey "system-cc" Cc _ _ -> fromKey "cc" -- We can't ask configure for the path to configure! - Configure _ -> return "sh configure" + Configure _ -> return "configure" Ghc _ Stage0 -> fromKey "system-ghc" GhcPkg _ Stage0 -> fromKey "system-ghc-pkg" Happy -> fromKey "happy" @@ -266,7 +265,7 @@ applyPatch dir patch = do needBuilder Patch path <- builderPath Patch putBuild $ "| Apply patch " ++ file - quietly $ cmd Shell [Cwd dir] [path, "-p0 <", patch] + quietly $ cmd [Cwd dir, FileStdin file] [path, "-p0"] -- | Install a directory. installDirectory :: FilePath -> Action () From git at git.haskell.org Fri Oct 27 01:27:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:38 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix Config.hs to import GhcPrelude (#417) (fcdecad) Message-ID: <20171027012738.D468B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/fcdecad4f1ab2f5a6126013004211acef23cf775/ghc >--------------------------------------------------------------- commit fcdecad4f1ab2f5a6126013004211acef23cf775 Author: Zhen Zhang Date: Thu Sep 21 00:47:21 2017 +0800 Fix Config.hs to import GhcPrelude (#417) >--------------------------------------------------------------- fcdecad4f1ab2f5a6126013004211acef23cf775 src/Rules/Generate.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 413abe5..e777e1b 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -291,6 +291,8 @@ generateConfigHs = do [ "{-# LANGUAGE CPP #-}" , "module Config where" , "" + , "import GhcPrelude" + , "" , "#include \"ghc_boot_platform.h\"" , "" , "data IntegerLibrary = IntegerGMP" From git at git.haskell.org Fri Oct 27 01:27:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:42 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update shake and add stm to stage1 packages (#419) (907cad6) Message-ID: <20171027012742.5AE4F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/907cad60863a4ea2b940fa7aa6c73b0da82eab7c/ghc >--------------------------------------------------------------- commit 907cad60863a4ea2b940fa7aa6c73b0da82eab7c Author: Zhen Zhang Date: Fri Sep 22 17:53:09 2017 +0800 Update shake and add stm to stage1 packages (#419) * Update shake * Add stm to Stage 1 packages >--------------------------------------------------------------- 907cad60863a4ea2b940fa7aa6c73b0da82eab7c hadrian.cabal | 2 +- src/GHC.hs | 1 + src/Hadrian/Utilities.hs | 6 ------ stack.yaml | 3 +++ 4 files changed, 5 insertions(+), 7 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index b01d866..97b283a 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -124,7 +124,7 @@ executable hadrian , extra >= 1.4.7 , mtl == 2.2.* , QuickCheck >= 2.6 && < 2.10 - , shake >= 0.15.6 + , shake == 0.16.* , transformers >= 0.4 && < 0.6 , unordered-containers == 0.2.* build-tools: alex >= 3.1 diff --git a/src/GHC.hs b/src/GHC.hs index ab6f93b..32676cd 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -191,6 +191,7 @@ stage1Packages = do , process , rts , runGhc + , stm , time ] ++ [ iservBin | not win ] ++ [ unix | not win ] diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 8f6f4cc..06ee663 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -25,9 +25,6 @@ module Hadrian.Utilities ( putProgressInfo, renderAction, renderProgram, renderLibrary, renderBox, renderUnicorn, - -- * Shake compatibility - RuleResult, - -- * Miscellaneous (<&>), (%%>), cmdLineLengthLimit, @@ -183,9 +180,6 @@ buildRoot = do infixl 1 <&> --- | Introduced in shake-0.16, so use to make the rest of the code compatible -type family RuleResult a - -- | Given a 'FilePath' to a source file, return 'True' if it is generated. -- The current implementation simply assumes that a file is generated if it -- lives in the 'buildRoot' directory. Since most files are not generated the diff --git a/stack.yaml b/stack.yaml index a05f2cd..2a92f26 100644 --- a/stack.yaml +++ b/stack.yaml @@ -8,6 +8,9 @@ packages: - '.' - '../libraries/Cabal/Cabal' +extra-deps: +- shake-0.16 + nix: packages: - autoconf From git at git.haskell.org Fri Oct 27 01:27:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:45 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Complete RTS compiler args (#418) (706d35e) Message-ID: <20171027012745.CCCDE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/706d35ea81f8f290f21ab9ab6869b3e4cc575056/ghc >--------------------------------------------------------------- commit 706d35ea81f8f290f21ab9ab6869b3e4cc575056 Author: Zhen Zhang Date: Sun Sep 24 03:55:22 2017 +0800 Complete RTS compiler args (#418) >--------------------------------------------------------------- 706d35ea81f8f290f21ab9ab6869b3e4cc575056 cfg/system.config.in | 1 + src/Oracles/Flag.hs | 2 + src/Settings/Packages/Rts.hs | 227 ++++++++++++++++++------------------------- 3 files changed, 95 insertions(+), 135 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 706d35ea81f8f290f21ab9ab6869b3e4cc575056 From git at git.haskell.org Fri Oct 27 01:27:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:49 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant import (07b7d5f) Message-ID: <20171027012749.407863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/07b7d5fcd2890137e2d71e1b136d8cc0da0fa1ad/ghc >--------------------------------------------------------------- commit 07b7d5fcd2890137e2d71e1b136d8cc0da0fa1ad Author: Andrey Mokhov Date: Sat Sep 23 23:06:26 2017 +0200 Drop redundant import >--------------------------------------------------------------- 07b7d5fcd2890137e2d71e1b136d8cc0da0fa1ad src/Hadrian/Oracles/ArgsHash.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs index da13a95..bae2fdb 100644 --- a/src/Hadrian/Oracles/ArgsHash.hs +++ b/src/Hadrian/Oracles/ArgsHash.hs @@ -9,7 +9,6 @@ import Development.Shake.Classes import Hadrian.Expression hiding (inputs, outputs) import Hadrian.Target -import Hadrian.Utilities -- | 'TrackArgument' is used to specify the arguments that should be tracked by -- the @ArgsHash@ oracle. The safest option is to track all arguments, but some From git at git.haskell.org Fri Oct 27 01:27:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:52 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add RTS args related to libffi (6abbbd0) Message-ID: <20171027012752.AAA813A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6abbbd0696f55f8d6b7bcd33c4c4915f934b4045/ghc >--------------------------------------------------------------- commit 6abbbd0696f55f8d6b7bcd33c4c4915f934b4045 Author: Andrey Mokhov Date: Mon Sep 25 22:27:47 2017 +0200 Add RTS args related to libffi >--------------------------------------------------------------- 6abbbd0696f55f8d6b7bcd33c4c4915f934b4045 src/Settings/Packages/Rts.hs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 10940e4..c9d6359 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -38,15 +38,14 @@ rtsLibffiLibraryName = do (False, False) -> "Cffi" (_ , True ) -> "Cffi-6" -rtsLibffiIncludeArgs :: Args -rtsLibffiIncludeArgs = package libffi ? builder (Ghc CompileCWithGhc) ? do - useSystemFfi <- expr $ flag UseSystemFfi - ffiIncludeDir <- getSetting FfiIncludeDir - mconcat [ - useSystemFfi ? pure (map ("-I" ++) $ words ffiIncludeDir), - -- ffi.h triggers prototype warnings, so disable them here: - inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? - arg "-Wno-strict-prototypes" ] +rtsLibffiArgs :: Args +rtsLibffiArgs = builder (Ghc CompileCWithGhc) ? do + useSystemFfi <- expr $ flag UseSystemFfi + ffiIncludeDir <- getSetting FfiIncludeDir + mconcat [ useSystemFfi ? pure (map ("-I" ++) $ words ffiIncludeDir) + -- ffi.h triggers prototype warnings, so we disable them here + , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? + arg "-Wno-strict-prototypes" ] rtsLibffiLibrary :: Way -> Action FilePath rtsLibffiLibrary way = do @@ -195,7 +194,8 @@ rtsPackageArgs = package rts ? do , ghcRtsWithLibDw ? arg "-DUSE_LIBDW" ] mconcat - [ builder (Cc FindCDependencies) ? mconcat cArgs + [ rtsLibffiArgs + , builder (Cc FindCDependencies) ? mconcat cArgs , builder (Ghc CompileCWithGhc) ? mconcat (map (map ("-optc" ++) <$>) cArgs) , builder Ghc ? arg "-Irts" , builder HsCpp ? pure From git at git.haskell.org Fri Oct 27 01:27:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:56 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop outdated RTS arguments, fix Windows build (0e193c0) Message-ID: <20171027012756.2A0623A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0e193c084f1ee8d9f044e612b319cf9963a5053d/ghc >--------------------------------------------------------------- commit 0e193c084f1ee8d9f044e612b319cf9963a5053d Author: Andrey Mokhov Date: Tue Sep 26 20:17:50 2017 +0200 Drop outdated RTS arguments, fix Windows build >--------------------------------------------------------------- 0e193c084f1ee8d9f044e612b319cf9963a5053d src/Settings/Packages/Rts.hs | 14 ++------------ 1 file changed, 2 insertions(+), 12 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index c9d6359..c71b729 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -54,13 +54,6 @@ rtsLibffiLibrary way = do rtsPath <- rtsBuildPath return $ rtsPath -/- "lib" ++ name ++ suf --- ref: mk/config.mk.in -ghcRtsWithLibDw :: Action Bool -ghcRtsWithLibDw = do - goodArch <- anyTargetArch ["i386", "x86_64"] - withLibDw <- flag HaveLibMingwEx - return $ goodArch && withLibDw - -- Compile various performance-critical pieces *without* -fPIC -dynamic -- even when building a shared library. If we don't do this, then the -- GC runs about 50% slower on x86 due to the overheads of PIC. The @@ -190,8 +183,7 @@ rtsPackageArgs = package rts ? do , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr" , input "//RetainerProfile.c" ? flag GccIsClang ? pure [ "-Wno-incompatible-pointer-types" ] - , targetOs == "mingw32" ? arg ("-DWINVER=" ++ rtsWindowsVersion) - , ghcRtsWithLibDw ? arg "-DUSE_LIBDW" ] + , windowsHost ? arg ("-DWINVER=" ++ rtsWindowsVersion) ] mconcat [ rtsLibffiArgs @@ -210,6 +202,4 @@ rtsPackageArgs = package rts ? do pure [ "-DINSTALLING" , "-DLIB_DIR=\"" ++ destDir ++ ghclibDir ++ "\"" , "-DINCLUDE_DIR=\"" ++ destDir ++ ghclibDir -/- "include\"" ] - , builder HsCpp ? mconcat - [ ghcRtsWithLibDw ? arg "-DUSE_LIBDW" - , flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ] ] + , builder HsCpp ? flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ] From git at git.haskell.org Fri Oct 27 01:27:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:27:59 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Clean up RTS arguments (b2d06c6) Message-ID: <20171027012759.993153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2d06c68c31265fa85dc764b6a29400c8845b640/ghc >--------------------------------------------------------------- commit b2d06c68c31265fa85dc764b6a29400c8845b640 Author: Andrey Mokhov Date: Tue Sep 26 20:48:21 2017 +0200 Clean up RTS arguments >--------------------------------------------------------------- b2d06c68c31265fa85dc764b6a29400c8845b640 src/Settings/Packages/Rts.hs | 70 +++++++++++++++++++++----------------------- 1 file changed, 33 insertions(+), 37 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index c71b729..a7ed021 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -20,17 +20,17 @@ rtsBuildPath = buildPath rtsContext rtsConfIn :: FilePath rtsConfIn = pkgPath rts -/- "package.conf.in" --- | Minimum supported Windows version. -- These numbers can be found at: -- https://msdn.microsoft.com/en-us/library/windows/desktop/aa383745(v=vs.85).aspx -- If we're compiling on windows, enforce that we only support Vista SP1+ -- Adding this here means it doesn't have to be done in individual .c files -- and also centralizes the versioning. -rtsWindowsVersion :: String -rtsWindowsVersion = "0x06000100" +-- | Minimum supported Windows version. +windowsVersion :: String +windowsVersion = "0x06000100" -rtsLibffiLibraryName :: Action FilePath -rtsLibffiLibraryName = do +libffiLibraryName :: Action FilePath +libffiLibraryName = do useSystemFfi <- flag UseSystemFfi windows <- windowsHost return $ case (useSystemFfi, windows) of @@ -38,18 +38,9 @@ rtsLibffiLibraryName = do (False, False) -> "Cffi" (_ , True ) -> "Cffi-6" -rtsLibffiArgs :: Args -rtsLibffiArgs = builder (Ghc CompileCWithGhc) ? do - useSystemFfi <- expr $ flag UseSystemFfi - ffiIncludeDir <- getSetting FfiIncludeDir - mconcat [ useSystemFfi ? pure (map ("-I" ++) $ words ffiIncludeDir) - -- ffi.h triggers prototype warnings, so we disable them here - , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? - arg "-Wno-strict-prototypes" ] - rtsLibffiLibrary :: Way -> Action FilePath rtsLibffiLibrary way = do - name <- rtsLibffiLibraryName + name <- libffiLibraryName suf <- libsuf way rtsPath <- rtsBuildPath return $ rtsPath -/- "lib" ++ name ++ suf @@ -108,12 +99,12 @@ rtsPackageArgs = package rts ? do way <- getWay path <- getBuildPath top <- expr topDirectory - libffiName <- expr rtsLibffiLibraryName + libffiName <- expr libffiLibraryName ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir ghclibDir <- expr installGhcLibDir destDir <- expr getDestDir - let cArgs = + let cArgs = mconcat [ arg "-Irts" , arg $ "-I" ++ path , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" @@ -156,41 +147,45 @@ rtsPackageArgs = package rts ? do inputs [ "//Evac.c", "//Evac_thr.c" , "//Scav.c", "//Scav_thr.c" , "//Compact.c", "//GC.c" ] ? arg "-fno-PIC" - -- -static is also necessary for these bits, otherwise the NCG - -- generates dynamic references: + -- -static is also necessary for these bits, otherwise the NCG + -- generates dynamic references: , speedHack ? inputs [ "//Updates.c", "//StgMiscClosures.c" , "//PrimOps.c", "//Apply.c" - , "//AutoApply.c" ] ? pure [ "-fno-PIC", "-static" ] - -- inlining warnings happen in Compact + , "//AutoApply.c" ] ? pure ["-fno-PIC", "-static"] + + -- inlining warnings happen in Compact , inputs ["//Compact.c"] ? arg "-Wno-inline" - -- emits warnings about call-clobbered registers on x86_64 - , inputs [ "//StgCRun.c", "//RetainerProfile.c" + + -- emits warnings about call-clobbered registers on x86_64 + , inputs [ "//RetainerProfile.c", "//StgCRun.c" , "//win32/ConsoleHandler.c", "//win32/ThrIOManager.c"] ? arg "-w" , inputs ["//RetainerSet.c"] ? arg "-Wno-format" - -- The above warning suppression flags are a temporary kludge. - -- While working on this module you are encouraged to remove it and fix - -- any warnings in the module. See - -- http://ghc.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings - -- for details + -- The above warning suppression flags are a temporary kludge. + -- While working on this module you are encouraged to remove it and fix + -- any warnings in the module. See: + -- http://ghc.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings , (not <$> flag GccIsClang) ? inputs ["//Compact.c"] ? arg "-finline-limit=2500" , inputs ["//Evac_thr.c", "//Scav_thr.c"] ? - pure [ "-DPARALLEL_GC", "-Irts/sm" ] + pure ["-DPARALLEL_GC", "-Irts/sm"] , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr" , input "//RetainerProfile.c" ? flag GccIsClang ? - pure [ "-Wno-incompatible-pointer-types" ] - , windowsHost ? arg ("-DWINVER=" ++ rtsWindowsVersion) ] - + arg "-Wno-incompatible-pointer-types" + , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? + arg "-Wno-strict-prototypes" + , windowsHost ? arg ("-DWINVER=" ++ windowsVersion) ] mconcat - [ rtsLibffiArgs - , builder (Cc FindCDependencies) ? mconcat cArgs - , builder (Ghc CompileCWithGhc) ? mconcat (map (map ("-optc" ++) <$>) cArgs) - , builder Ghc ? arg "-Irts" - , builder HsCpp ? pure + [ builder (Cc FindCDependencies) ? cArgs + , builder (Ghc CompileCWithGhc) ? map ("-optc" ++) <$> cArgs + , builder Ghc ? mconcat + [ arg "-Irts" + , flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir) ] + + , builder HsCpp ? pure [ "-DTOP=" ++ show top , "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir , "-DFFI_LIB_DIR=" ++ show ffiLibraryDir @@ -202,4 +197,5 @@ rtsPackageArgs = package rts ? do pure [ "-DINSTALLING" , "-DLIB_DIR=\"" ++ destDir ++ ghclibDir ++ "\"" , "-DINCLUDE_DIR=\"" ++ destDir ++ ghclibDir -/- "include\"" ] + , builder HsCpp ? flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ] From git at git.haskell.org Fri Oct 27 01:28:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:03 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Move ffiIncludeDir to C arguments (68446ab) Message-ID: <20171027012803.D9B563A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/68446abeab92087492baba6c746ab94c3bb7c2bb/ghc >--------------------------------------------------------------- commit 68446abeab92087492baba6c746ab94c3bb7c2bb Author: Andrey Mokhov Date: Tue Sep 26 20:56:28 2017 +0200 Move ffiIncludeDir to C arguments >--------------------------------------------------------------- 68446abeab92087492baba6c746ab94c3bb7c2bb src/Settings/Packages/Rts.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index a7ed021..7282a0e 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -107,6 +107,7 @@ rtsPackageArgs = package rts ? do let cArgs = mconcat [ arg "-Irts" , arg $ "-I" ++ path + , flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir) , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\"" -- rts *must* be compiled with optimisations. The INLINE_HEADER macro -- requires that functions are inlined to work as expected. Inlining @@ -181,9 +182,7 @@ rtsPackageArgs = package rts ? do mconcat [ builder (Cc FindCDependencies) ? cArgs , builder (Ghc CompileCWithGhc) ? map ("-optc" ++) <$> cArgs - , builder Ghc ? mconcat - [ arg "-Irts" - , flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir) ] + , builder Ghc ? arg "-Irts" , builder HsCpp ? pure [ "-DTOP=" ++ show top From git at git.haskell.org Fri Oct 27 01:28:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop checkApiAnnotations utility (6abcec9) Message-ID: <20171027012807.8E7913A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6abcec9b1a92c1d35a15d9c01c38e6ecc06c4e87/ghc >--------------------------------------------------------------- commit 6abcec9b1a92c1d35a15d9c01c38e6ecc06c4e87 Author: Andrey Mokhov Date: Wed Sep 27 23:36:24 2017 +0100 Drop checkApiAnnotations utility See https://phabricator.haskell.org/D4039 >--------------------------------------------------------------- 6abcec9b1a92c1d35a15d9c01c38e6ecc06c4e87 src/GHC.hs | 32 +++++++++++++++----------------- 1 file changed, 15 insertions(+), 17 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 32676cd..77a63e9 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -1,14 +1,14 @@ {-# OPTIONS_GHC -fno-warn-missing-signatures #-} module GHC ( -- * GHC packages - array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes, - compiler, containers, deepseq, deriveConstants, directory, filepath, - genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, - ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, - hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, - parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell, - terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml, - ghcPackages, isGhcPackage, defaultPackages, + array, base, binary, bytestring, cabal, compareSizes, compiler, containers, + deepseq, deriveConstants, directory, filepath, genapply, genprimopcode, ghc, + ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, + ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, + integerSimple, iservBin, libffi, mtl, parsec, parallel, pretty, primitive, + process, rts, runGhc, stm, templateHaskell, terminfo, text, time, touchy, + transformers, unlit, unix, win32, xhtml, ghcPackages, isGhcPackage, + defaultPackages, -- * Package information programName, nonCabalContext, nonHsMainPackage, autogenPath, installStage, @@ -30,13 +30,13 @@ import Oracles.Flag (crossCompiling) -- modify build default build conditions in "UserSettings". ghcPackages :: [Package] ghcPackages = - [ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes - , compiler, containers, deepseq, deriveConstants, directory, filepath - , genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact - , ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc - , hpcBin, integerGmp, integerSimple, iservBin, libffi, mtl, parsec, parallel - , pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo - , text, time, touchy, transformers, unlit, unix, win32, xhtml ] + [ array, base, binary, bytestring, cabal, compareSizes, compiler, containers + , deepseq, deriveConstants, directory, filepath, genapply, genprimopcode + , ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim + , ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp + , integerSimple, iservBin, libffi, mtl, parsec, parallel, pretty, primitive + , process, rts, runGhc, stm, templateHaskell, terminfo, text, time, touchy + , transformers, unlit, unix, win32, xhtml ] -- TODO: Optimise by switching to sets of packages. isGhcPackage :: Package -> Bool @@ -48,7 +48,6 @@ base = hsLib "base" binary = hsLib "binary" bytestring = hsLib "bytestring" cabal = hsLib "Cabal" `setPath` "libraries/Cabal/Cabal" -checkApiAnnotations = hsUtil "check-api-annotations" compareSizes = hsUtil "compareSizes" `setPath` "utils/compare_sizes" compiler = hsTop "ghc" `setPath` "compiler" containers = hsLib "containers" @@ -140,7 +139,6 @@ stage0Packages = do cross <- crossCompiling return $ [ binary , cabal - , checkApiAnnotations , compareSizes , compiler , deriveConstants From git at git.haskell.org Fri Oct 27 01:28:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:11 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to isWindows (88a7b4e) Message-ID: <20171027012811.9C0BC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/88a7b4e31616f06ea9c0f75d3565ae11936009e0/ghc >--------------------------------------------------------------- commit 88a7b4e31616f06ea9c0f75d3565ae11936009e0 Author: Andrey Mokhov Date: Thu Sep 28 23:49:12 2017 +0100 Switch to isWindows >--------------------------------------------------------------- 88a7b4e31616f06ea9c0f75d3565ae11936009e0 src/Rules/Configure.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index 5e29116..492d91c 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -1,6 +1,6 @@ module Rules.Configure (configureRules) where -import qualified System.Info as System +import qualified System.Info.Extra as System import Base import Builder @@ -21,7 +21,7 @@ configureRules = do ++ "--skip-configure flag." else do -- We cannot use windowsHost here due to a cyclic dependency. - when (System.os == "mingw32") $ do + when System.isWindows $ do putBuild "| Checking for Windows tarballs..." quietly $ cmd ["bash", "mk/get-win32-tarballs.sh", "download", System.arch] let srcs = map (<.> "in") outs From git at git.haskell.org Fri Oct 27 01:28:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:15 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix missing dependency on package configuration (c6d7b2a) Message-ID: <20171027012815.956793A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6d7b2a33e6ff987e7112c57555425c285c380e9/ghc >--------------------------------------------------------------- commit c6d7b2a33e6ff987e7112c57555425c285c380e9 Author: Andrey Mokhov Date: Fri Sep 29 00:37:35 2017 +0100 Fix missing dependency on package configuration Also a minor revision. See #421 >--------------------------------------------------------------- c6d7b2a33e6ff987e7112c57555425c285c380e9 src/Base.hs | 7 ++++++- src/Builder.hs | 12 ++++++------ src/Settings/Builders/Common.hs | 8 +++----- src/Settings/Builders/Ghc.hs | 14 +++++++++----- src/Settings/Default.hs | 2 +- 5 files changed, 25 insertions(+), 18 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 76e8f2b..38c8792 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -22,7 +22,7 @@ module Base ( hadrianPath, configPath, configFile, sourcePath, configH, shakeFilesDir, generatedDir, inplaceBinPath, inplaceLibBinPath, inplaceLibPath, inplaceLibCopyTargets, templateHscPath, stage0PackageDbDir, - inplacePackageDbPath, packageDbStamp + inplacePackageDbPath, packageDbPath, packageDbStamp ) where import Control.Applicative @@ -82,6 +82,11 @@ stage0PackageDbDir = "stage0/bootstrapping.conf" inplacePackageDbPath :: FilePath inplacePackageDbPath = "inplace/lib/package.conf.d" +-- | Path to the package database used in a given 'Stage'. +packageDbPath :: Stage -> Action FilePath +packageDbPath Stage0 = buildRoot <&> (-/- stage0PackageDbDir) +packageDbPath _ = return inplacePackageDbPath + -- | We use a stamp file to track the existence of a package database. packageDbStamp :: FilePath packageDbStamp = ".stamp" diff --git a/src/Builder.hs b/src/Builder.hs index 355878f..fdd73e7 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -149,13 +149,13 @@ instance H.Builder Builder where Just context -> programPath context needBuilder :: Builder -> Action () - needBuilder (Configure dir) = need [dir -/- "configure"] - needBuilder Hsc2Hs = do path <- H.builderPath Hsc2Hs - need [path, templateHscPath] - needBuilder (Make dir) = need [dir -/- "Makefile"] - needBuilder builder = when (isJust $ builderProvenance builder) $ do + needBuilder builder = do path <- H.builderPath builder - need [path] + case builder of + Configure dir -> need [dir -/- "configure"] + Hsc2Hs -> need [path, templateHscPath] + Make dir -> need [dir -/- "Makefile"] + _ -> when (isJust $ builderProvenance builder) $ need [path] runBuilderWith :: Builder -> BuildInfo -> Action () runBuilderWith builder BuildInfo {..} = do diff --git a/src/Settings/Builders/Common.hs b/src/Settings/Builders/Common.hs index 6da7ea8..e7af38b 100644 --- a/src/Settings/Builders/Common.hs +++ b/src/Settings/Builders/Common.hs @@ -49,11 +49,9 @@ cWarnings = do bootPackageDatabaseArgs :: Args bootPackageDatabaseArgs = do - root <- getBuildRoot - stage <- getStage - let dbDir | stage == Stage0 = root -/- stage0PackageDbDir - | otherwise = inplacePackageDbPath - expr $ need [dbDir -/- packageDbStamp] + stage <- getStage + dbPath <- expr $ packageDbPath stage + expr $ need [dbPath -/- packageDbStamp] stage0 ? do top <- expr topDirectory root <- getBuildRoot diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs index 7f942f6..94b5b21 100644 --- a/src/Settings/Builders/Ghc.hs +++ b/src/Settings/Builders/Ghc.hs @@ -1,5 +1,5 @@ module Settings.Builders.Ghc ( - ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs, ghcCbuilderArgs + ghcBuilderArgs, ghcCBuilderArgs, ghcMBuilderArgs, haddockGhcArgs ) where import Hadrian.Haskell.Cabal @@ -24,9 +24,8 @@ needTouchy = notStage0 ? windowsHost ? do touchyPath <- expr $ programPath (vanillaContext Stage0 touchy) expr $ need [touchyPath] -ghcCbuilderArgs :: Args -ghcCbuilderArgs = - builder (Ghc CompileCWithGhc) ? do +ghcCBuilderArgs :: Args +ghcCBuilderArgs = builder (Ghc CompileCWithGhc) ? do way <- getWay let ccArgs = [ getPkgDataList CcArgs , getStagedSettingList ConfCcArgs @@ -83,11 +82,16 @@ ghcMBuilderArgs = builder (Ghc FindHsDependencies) ? do haddockGhcArgs :: Args haddockGhcArgs = mconcat [ commonGhcArgs, getPkgDataList HsArgs ] --- This is included into ghcBuilderArgs, ghcMBuilderArgs and haddockGhcArgs. +-- Used in ghcBuilderArgs, ghcCBuilderArgs, ghcMBuilderArgs and haddockGhcArgs. commonGhcArgs :: Args commonGhcArgs = do way <- getWay path <- getBuildPath + pkg <- getPackage + when (isLibrary pkg) $ do + context <- getContext + conf <- expr $ pkgConfFile context + expr $ need [conf] mconcat [ arg "-hisuf", arg $ hisuf way , arg "-osuf" , arg $ osuf way , arg "-hcsuf", arg $ hcsuf way diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs index 10ec84f..cf0047f 100644 --- a/src/Settings/Default.hs +++ b/src/Settings/Default.hs @@ -148,8 +148,8 @@ defaultBuilderArgs = mconcat , deriveConstantsBuilderArgs , genPrimopCodeBuilderArgs , ghcBuilderArgs - , ghcCbuilderArgs , ghcCabalBuilderArgs + , ghcCBuilderArgs , ghcMBuilderArgs , ghcPkgBuilderArgs , haddockBuilderArgs From git at git.haskell.org Fri Oct 27 01:28:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Build man page (#424) (e1c9afa) Message-ID: <20171027012819.267C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e1c9afa3c5e29a7cea8d3853a06e08005d06f83b/ghc >--------------------------------------------------------------- commit e1c9afa3c5e29a7cea8d3853a06e08005d06f83b Author: Zhen Zhang Date: Sun Oct 1 05:01:28 2017 +0800 Build man page (#424) >--------------------------------------------------------------- e1c9afa3c5e29a7cea8d3853a06e08005d06f83b src/Rules/Documentation.hs | 15 +++++++++++++++ src/Settings/Builders/Sphinx.hs | 2 +- 2 files changed, 16 insertions(+), 1 deletion(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index bafb1b2..2cdd4d5 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -22,12 +22,17 @@ documentationRules = do buildHtmlDocumentation buildPdfDocumentation buildDocumentationArchives + buildManPage "docs" ~> do root <- buildRoot let html = htmlRoot -/- "index.html" archives = map pathArchive docPaths pdfs = map pathPdf $ docPaths \\ [ "libraries" ] need $ map (root -/-) $ [html] ++ archives ++ pdfs + need [manPagePath] + +manPagePath :: FilePath +manPagePath = "_build/docs/users_guide/build-man/ghc.1" -- TODO: Add support for Documentation Packages so we can -- run the builders without this hack. @@ -176,3 +181,13 @@ buildArchive path = do src = root -/- pathIndex path need [src] build $ target context (Tar Create) [takeDirectory src] [file] + +-- | build man page +buildManPage :: Rules () +buildManPage = do + manPagePath %> \file -> do + need ["docs/users_guide/ghc.rst"] + let context = vanillaContext Stage0 docPackage + withTempDir $ \dir -> do + build $ target context (Sphinx Man) ["docs/users_guide"] [dir] + copyFileUntracked (dir -/- "ghc.1") file diff --git a/src/Settings/Builders/Sphinx.hs b/src/Settings/Builders/Sphinx.hs index 6ac88a0..2338cfc 100644 --- a/src/Settings/Builders/Sphinx.hs +++ b/src/Settings/Builders/Sphinx.hs @@ -16,7 +16,7 @@ sphinxBuilderArgs = do , arg =<< getInput , arg outPath ] , builder (Sphinx Man) ? mconcat - [ arg "-b", arg "latex" + [ arg "-b", arg "man" , arg "-d", arg $ outPath -/- ".doctrees-man" , arg =<< getInput , arg outPath ] ] From git at git.haskell.org Fri Oct 27 01:28:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:22 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch to the python based boot script (18539d0) Message-ID: <20171027012822.A9B433A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/18539d0ca551e312a81f2d9bda5ad055a657906a/ghc >--------------------------------------------------------------- commit 18539d0ca551e312a81f2d9bda5ad055a657906a Author: Andrey Mokhov Date: Wed Oct 4 12:38:48 2017 +0100 Switch to the python based boot script See #314 >--------------------------------------------------------------- 18539d0ca551e312a81f2d9bda5ad055a657906a src/Rules/Configure.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index 492d91c..a4ef084 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -38,4 +38,4 @@ configureRules = do else do need ["configure.ac"] putBuild "| Running boot..." - quietly $ cmd "perl boot" + quietly $ cmd "python3 boot" From git at git.haskell.org Fri Oct 27 01:28:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix libffil build (d6fd6fe) Message-ID: <20171027012826.421443A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/d6fd6feb85cd846dfd707703da839056d43c92a8/ghc >--------------------------------------------------------------- commit d6fd6feb85cd846dfd707703da839056d43c92a8 Author: Andrey Mokhov Date: Thu Oct 5 10:50:56 2017 +0100 Fix libffil build See #426 >--------------------------------------------------------------- d6fd6feb85cd846dfd707703da839056d43c92a8 src/Rules/Libffi.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs index 68040be..9641b66 100644 --- a/src/Rules/Libffi.hs +++ b/src/Rules/Libffi.hs @@ -64,7 +64,7 @@ libffiRules = do libffiPath <- libffiBuildPath build $ target libffiContext (Make libffiPath) [] [] - hs <- getDirectoryFiles "" [libffiPath -/- "inst/lib/*/include/*"] + hs <- getDirectoryFiles "" [libffiPath -/- "inst/include/*"] forM_ hs $ \header -> copyFile header (rtsPath -/- takeFileName header) @@ -82,7 +82,8 @@ libffiRules = do <$> getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"] need [tarball] - let libname = dropExtension . dropExtension $ takeFileName tarball + -- Go from 'libffi-3.99999+git20171002+77e130c.tar.gz' to 'libffi-3.99999' + let libname = takeWhile (/= '+') $ takeFileName tarball root <- buildRoot removeDirectory (root -/- libname) From git at git.haskell.org Fri Oct 27 01:28:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:29 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install python on CI (c13806a) Message-ID: <20171027012829.DD1AE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c13806a2f5857075f769ec45280cbd3f298e3044/ghc >--------------------------------------------------------------- commit c13806a2f5857075f769ec45280cbd3f298e3044 Author: Andrey Mokhov Date: Thu Oct 5 10:59:49 2017 +0100 Install python on CI See #314 >--------------------------------------------------------------- c13806a2f5857075f769ec45280cbd3f298e3044 appveyor.yml | 2 +- circle.yml | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 451d5d5..c51983a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -22,7 +22,7 @@ install: # Install all Hadrian and GHC build dependencies - cd hadrian - stack setup > nul - - appveyor-retry stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm + - appveyor-retry stack exec -- pacman -S autoconf automake-wrapper make patch python tar --noconfirm build_script: # Build Hadrian diff --git a/circle.yml b/circle.yml index b038689..592b9f4 100644 --- a/circle.yml +++ b/circle.yml @@ -7,7 +7,7 @@ machine: dependencies: override: - brew update - - brew install ghc cabal-install + - brew install ghc cabal-install python - cabal update - cabal install alex happy ansi-terminal mtl shake quickcheck cache_directories: From git at git.haskell.org Fri Oct 27 01:28:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install python3 on CircleCI (81a6d1a) Message-ID: <20171027012833.5E3413A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/81a6d1a961ed6e0327f2f34e4955f8628729498a/ghc >--------------------------------------------------------------- commit 81a6d1a961ed6e0327f2f34e4955f8628729498a Author: Andrey Mokhov Date: Thu Oct 5 11:15:17 2017 +0100 Install python3 on CircleCI See #314 >--------------------------------------------------------------- 81a6d1a961ed6e0327f2f34e4955f8628729498a circle.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/circle.yml b/circle.yml index 592b9f4..93cf47f 100644 --- a/circle.yml +++ b/circle.yml @@ -7,7 +7,7 @@ machine: dependencies: override: - brew update - - brew install ghc cabal-install python + - brew install ghc cabal-install python3 - cabal update - cabal install alex happy ansi-terminal mtl shake quickcheck cache_directories: From git at git.haskell.org Fri Oct 27 01:28:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:36 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Install python3 on Travis OS X (6eb3059) Message-ID: <20171027012836.D69B23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6eb305962ccba06aeae22812e5733b5998843dcb/ghc >--------------------------------------------------------------- commit 6eb305962ccba06aeae22812e5733b5998843dcb Author: Andrey Mokhov Date: Thu Oct 5 11:34:12 2017 +0100 Install python3 on Travis OS X See #314 >--------------------------------------------------------------- 6eb305962ccba06aeae22812e5733b5998843dcb .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 9082ef6..203ee82 100644 --- a/.travis.yml +++ b/.travis.yml @@ -51,7 +51,7 @@ matrix: env: MODE="--flavour=quickest --integer-simple inplace/bin/ghc-stage1" before_install: - brew update - - brew install ghc cabal-install + - brew install ghc cabal-install python3 script: # Due to timeout limit of OS X build on Travis CI, From git at git.haskell.org Fri Oct 27 01:28:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Update docs (c70f765) Message-ID: <20171027012840.77B0A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c70f765b7aaecaa4bfed5c39e33e1e5111b1ce30/ghc >--------------------------------------------------------------- commit c70f765b7aaecaa4bfed5c39e33e1e5111b1ce30 Author: Andrey Mokhov Date: Thu Oct 5 12:43:25 2017 +0100 Update docs See #314 >--------------------------------------------------------------- c70f765b7aaecaa4bfed5c39e33e1e5111b1ce30 doc/windows.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/windows.md b/doc/windows.md index 510b986..f644f03 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -24,7 +24,7 @@ cd hadrian stack setup # Install utilities required during the GHC build process -stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm +stack exec -- pacman -S autoconf automake-wrapper make patch python tar --noconfirm # Build Hadrian and dependencies (including GHC dependencies Alex and Happy) stack build From git at git.haskell.org Fri Oct 27 01:28:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:43 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision (c6efd3f) Message-ID: <20171027012843.EB1B13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/c6efd3f68521f20632a0a173e1568aa772c0ea48/ghc >--------------------------------------------------------------- commit c6efd3f68521f20632a0a173e1568aa772c0ea48 Author: Andrey Mokhov Date: Thu Oct 5 17:58:20 2017 +0100 Minor revision >--------------------------------------------------------------- c6efd3f68521f20632a0a173e1568aa772c0ea48 doc/windows.md | 25 +++++++++++++------------ 1 file changed, 13 insertions(+), 12 deletions(-) diff --git a/doc/windows.md b/doc/windows.md index f644f03..b374074 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -2,19 +2,11 @@ [![Windows status](https://img.shields.io/appveyor/ci/snowleopard/hadrian/master.svg?label=Windows)](https://ci.appveyor.com/project/snowleopard/hadrian) -Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are -installed (see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). - -Note that `git` should be configured to check out Unix-style line endings. The default behaviour of `git` on Windows is to check out Windows-style line endings which can cause issues during the build. This can be changed using the following command: - - git config --global core.autocrlf false - -If you would like to restore the default behaviour later run: - - git config --global core.autocrlf true +Here is how you can build GHC, from source, on Windows. We assume that `git` and `stack` are installed +(see [prerequisites](https://github.com/snowleopard/hadrian/blob/master/doc/windows.md#prerequisites)). ```sh -# Get GHC and Hadrian sources +# Get GHC and Hadrian sources; git core.autocrlf should be set to false (see Prerequisites section) git clone --recursive git://git.haskell.org/ghc.git cd ghc git clone git://github.com/snowleopard/hadrian @@ -55,6 +47,16 @@ The above works on a clean machine with `git` and `stack` installed (tested with installation settings), which you can get from https://git-scm.com/download/win and https://www.stackage.org/stack/windows-x86_64-installer. +Note that `git` should be configured to check out Unix-style line endings. The default behaviour +of `git` on Windows is to check out Windows-style line endings which can cause issues during the +build. This can be changed using the following command: + + git config --global core.autocrlf false + +If you would like to restore the default behaviour later run: + + git config --global core.autocrlf true + ## Testing These instructions have been tested on a clean Windows 10 machine using the @@ -65,4 +67,3 @@ and are also routinely tested on ## Notes Beware of the [current limitations of Hadrian](https://github.com/snowleopard/hadrian#current-limitations). - From git at git.haskell.org Fri Oct 27 01:28:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop redundant code (830567e) Message-ID: <20171027012847.6CFE03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/830567e388a89b90a80c0140379c983de3cec8aa/ghc >--------------------------------------------------------------- commit 830567e388a89b90a80c0140379c983de3cec8aa Author: Andrey Mokhov Date: Thu Oct 5 20:08:35 2017 +0100 Drop redundant code See #314 >--------------------------------------------------------------- 830567e388a89b90a80c0140379c983de3cec8aa src/Environment.hs | 12 ------------ 1 file changed, 12 deletions(-) diff --git a/src/Environment.hs b/src/Environment.hs index d92e067..de43efa 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -2,8 +2,6 @@ module Environment (setupEnvironment) where import System.Environment -import Base - -- | The build system invokes many external builders whose behaviour is -- influenced by the environment variables. We need to modify some of them -- for better robustness of the build system. @@ -16,13 +14,3 @@ setupEnvironment = do -- `pwd` will return the Windows path, and then modifying $PATH will fail. -- See https://github.com/snowleopard/hadrian/issues/189 for details. unsetEnv "PWD" - - -- On Windows, some path variables start a prefix like "C:\\" which may - -- lead to failures of scripts such as autoreconf. One particular variable - -- which causes issues is ACLOCAL_PATH. At the moment we simply reset it - -- if it contains a problematic Windows path. - -- TODO: Handle Windows paths in ACLOCAL_PATH more gracefully. - aclocal <- lookupEnv "ACLOCAL_PATH" - case aclocal of - Nothing -> return () - Just s -> when (":\\" `isPrefixOf` drop 1 s) $ unsetEnv "ACLOCAL_PATH" From git at git.haskell.org Fri Oct 27 01:28:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop the redundant build rule for literate Perl scripts (a69c73f) Message-ID: <20171027012851.64B173A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/a69c73fe0d051d87cfc6fd95c72089faa92c5a0f/ghc >--------------------------------------------------------------- commit a69c73fe0d051d87cfc6fd95c72089faa92c5a0f Author: Andrey Mokhov Date: Sat Oct 7 23:26:08 2017 +0100 Drop the redundant build rule for literate Perl scripts >--------------------------------------------------------------- a69c73fe0d051d87cfc6fd95c72089faa92c5a0f hadrian.cabal | 1 - src/Rules.hs | 2 -- src/Rules/Perl.hs | 13 ------------- 3 files changed, 16 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 97b283a..48514e1 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -54,7 +54,6 @@ executable hadrian , Rules.Install , Rules.Libffi , Rules.Library - , Rules.Perl , Rules.Program , Rules.Register , Rules.Selftest diff --git a/src/Rules.hs b/src/Rules.hs index ea3df45..730823f 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -17,7 +17,6 @@ import qualified Rules.Configure import qualified Rules.Gmp import qualified Rules.Libffi import qualified Rules.Library -import qualified Rules.Perl import qualified Rules.Program import qualified Rules.Register import Settings @@ -115,7 +114,6 @@ buildRules = do Rules.Gmp.gmpRules Rules.Libffi.libffiRules packageRules - Rules.Perl.perlScriptRules oracleRules :: Rules () oracleRules = do diff --git a/src/Rules/Perl.hs b/src/Rules/Perl.hs deleted file mode 100644 index bc8b01f..0000000 --- a/src/Rules/Perl.hs +++ /dev/null @@ -1,13 +0,0 @@ -module Rules.Perl (perlScriptRules) where - -import Base -import Builder - --- TODO: Do we need this build rule? --- | Build Perl scripts, such as @ghc-split@, from their literate Perl sources. -perlScriptRules :: Rules () -perlScriptRules = do - "//*.prl" %> \out -> do - let src = out -<.> "lprl" - need [src] - runBuilder Unlit [src, out] [src] [out] From git at git.haskell.org Fri Oct 27 01:28:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Implement Stage1 GHC freezing (837675c) Message-ID: <20171027012854.DBE2E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/837675cdf374040b554dd04491b7e59aa631abd4/ghc >--------------------------------------------------------------- commit 837675cdf374040b554dd04491b7e59aa631abd4 Author: Andrey Mokhov Date: Mon Oct 9 01:14:54 2017 +0100 Implement Stage1 GHC freezing See #250 >--------------------------------------------------------------- 837675cdf374040b554dd04491b7e59aa631abd4 src/CommandLine.hs | 19 ++++++++++++++++--- src/Main.hs | 4 ++++ 2 files changed, 20 insertions(+), 3 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index cc6f944..a069c0e 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -1,10 +1,11 @@ module CommandLine ( - optDescrs, cmdLineArgsMap, cmdBuildHaddock, cmdFlavour, cmdIntegerSimple, - cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, cmdSplitObjects, - cmdInstallDestDir + optDescrs, cmdLineArgsMap, cmdBuildHaddock, cmdFlavour, lookupFreeze1, + cmdIntegerSimple, cmdProgressColour, cmdProgressInfo, cmdSkipConfigure, + cmdSplitObjects, cmdInstallDestDir ) where import Data.Either +import Data.Maybe import qualified Data.HashMap.Strict as Map import Data.List.Extra import Development.Shake hiding (Normal) @@ -16,6 +17,7 @@ import System.Environment data CommandLineArgs = CommandLineArgs { buildHaddock :: Bool , flavour :: Maybe String + , freeze1 :: Bool , installDestDir :: Maybe String , integerSimple :: Bool , progressColour :: UseColour @@ -29,6 +31,7 @@ defaultCommandLineArgs :: CommandLineArgs defaultCommandLineArgs = CommandLineArgs { buildHaddock = False , flavour = Nothing + , freeze1 = False , installDestDir = Nothing , integerSimple = False , progressColour = Auto @@ -36,6 +39,9 @@ defaultCommandLineArgs = CommandLineArgs , skipConfigure = False , splitObjects = False } +readFreeze1 :: Either String (CommandLineArgs -> CommandLineArgs) +readFreeze1 = Right $ \flags -> flags { freeze1 = True } + readBuildHaddock :: Either String (CommandLineArgs -> CommandLineArgs) readBuildHaddock = Right $ \flags -> flags { buildHaddock = True } @@ -84,6 +90,8 @@ optDescrs :: [OptDescr (Either String (CommandLineArgs -> CommandLineArgs))] optDescrs = [ Option [] ["flavour"] (OptArg readFlavour "FLAVOUR") "Build flavour (Default, Devel1, Devel2, Perf, Prof, Quick or Quickest)." + , Option [] ["freeze1"] (NoArg readFreeze1) + "Freeze Stage1 GHC." , Option [] ["haddock"] (NoArg readBuildHaddock) "Generate Haddock documentation." , Option [] ["install-destdir"] (OptArg readInstallDestDir "DESTDIR") @@ -118,6 +126,11 @@ cmdBuildHaddock = buildHaddock <$> cmdLineArgs cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs +lookupFreeze1 :: Map.HashMap TypeRep Dynamic -> Bool +lookupFreeze1 m = fromMaybe (freeze1 defaultCommandLineArgs) (freeze1 <$> maybeValue) + where + maybeValue = fromDynamic =<< Map.lookup (typeOf defaultCommandLineArgs) m + cmdInstallDestDir :: Action (Maybe String) cmdInstallDestDir = installDestDir <$> cmdLineArgs diff --git a/src/Main.hs b/src/Main.hs index 91580dd..52af0ad 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -28,11 +28,15 @@ main = do BuildRoot buildRoot = UserSettings.userBuildRoot + rebuild = [ (RebuildLater, buildRoot -/- "stage0//*") + | CommandLine.lookupFreeze1 argsMap ] + options :: ShakeOptions options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = buildRoot -/- Base.shakeFilesDir , shakeProgress = progressSimple + , shakeRebuild = rebuild , shakeTimings = True , shakeExtra = extra } From git at git.haskell.org Fri Oct 27 01:28:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:28:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Minor revision, drop old TODO (cbee74b) Message-ID: <20171027012858.5B09D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/cbee74bfe89e6b2b552c6ae560265ce2d9f5fb17/ghc >--------------------------------------------------------------- commit cbee74bfe89e6b2b552c6ae560265ce2d9f5fb17 Author: Andrey Mokhov Date: Tue Oct 10 00:37:42 2017 +0100 Minor revision, drop old TODO See #250 >--------------------------------------------------------------- cbee74bfe89e6b2b552c6ae560265ce2d9f5fb17 src/CommandLine.hs | 5 +---- src/Hadrian/Utilities.hs | 11 ++++++++--- src/Settings/Flavours/Development.hs | 1 - 3 files changed, 9 insertions(+), 8 deletions(-) diff --git a/src/CommandLine.hs b/src/CommandLine.hs index a069c0e..ed6441c 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -5,7 +5,6 @@ module CommandLine ( ) where import Data.Either -import Data.Maybe import qualified Data.HashMap.Strict as Map import Data.List.Extra import Development.Shake hiding (Normal) @@ -127,9 +126,7 @@ cmdFlavour :: Action (Maybe String) cmdFlavour = flavour <$> cmdLineArgs lookupFreeze1 :: Map.HashMap TypeRep Dynamic -> Bool -lookupFreeze1 m = fromMaybe (freeze1 defaultCommandLineArgs) (freeze1 <$> maybeValue) - where - maybeValue = fromDynamic =<< Map.lookup (typeOf defaultCommandLineArgs) m +lookupFreeze1 = freeze1 . lookupExtra defaultCommandLineArgs cmdInstallDestDir :: Action (Maybe String) cmdInstallDestDir = installDestDir <$> cmdLineArgs diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 06ee663..4d2ae48 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -10,7 +10,7 @@ module Hadrian.Utilities ( unifyPath, (-/-), -- * Accessing Shake's type-indexed map - insertExtra, userSetting, + insertExtra, lookupExtra, userSetting, -- * Paths BuildRoot (..), buildRoot, isGeneratedSource, @@ -153,13 +153,18 @@ cmdLineLengthLimit | isWindows = 31000 insertExtra :: Typeable a => a -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic insertExtra value = Map.insert (typeOf value) (toDyn value) +-- | Lookup a value in Shake's type-indexed map. +lookupExtra :: Typeable a => a -> Map.HashMap TypeRep Dynamic -> a +lookupExtra defaultValue extra = fromMaybe defaultValue maybeValue + where + maybeValue = fromDynamic =<< Map.lookup (typeOf defaultValue) extra + -- | Lookup a user setting in Shake's type-indexed map 'shakeExtra'. If the -- setting is not found, return the provided default value instead. userSetting :: Typeable a => a -> Action a userSetting defaultValue = do extra <- shakeExtra <$> getShakeOptions - let maybeValue = fromDynamic =<< Map.lookup (typeOf defaultValue) extra - return $ fromMaybe defaultValue maybeValue + return $ lookupExtra defaultValue extra newtype BuildRoot = BuildRoot FilePath deriving Typeable diff --git a/src/Settings/Flavours/Development.hs b/src/Settings/Flavours/Development.hs index a6a2892..713e409 100644 --- a/src/Settings/Flavours/Development.hs +++ b/src/Settings/Flavours/Development.hs @@ -4,7 +4,6 @@ import Flavour import Expression import {-# SOURCE #-} Settings.Default --- TODO: Implement an equivalent of LAX_DEPENDENCIES = YES setting, see #250. developmentFlavour :: Stage -> Flavour developmentFlavour ghcStage = defaultFlavour { name = "devel" ++ show (fromEnum ghcStage) From git at git.haskell.org Fri Oct 27 01:29:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:02 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Document the --freeze1 flag (7c507e1) Message-ID: <20171027012902.098C73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/7c507e1c6e0bdc622b033d75f3d5c75790e751b0/ghc >--------------------------------------------------------------- commit 7c507e1c6e0bdc622b033d75f3d5c75790e751b0 Author: Andrey Mokhov Date: Tue Oct 10 14:02:17 2017 +0100 Document the --freeze1 flag See #250 >--------------------------------------------------------------- 7c507e1c6e0bdc622b033d75f3d5c75790e751b0 README.md | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index ad61ef3..9eb759e 100644 --- a/README.md +++ b/README.md @@ -58,6 +58,12 @@ currently supports several others: `vanilla` way, which speeds up builds by 3-4x. Build flavours are documented [here](https://github.com/snowleopard/hadrian/blob/master/doc/flavours.md). +* `--freeze1`: freeze Stage1 GHC, i.e. do not rebuild it even if some of its source files +are out-of-date. This allows to significantly reduce the rebuild time when you are working +on a feature that affects both Stage1 and Stage2 compilers, but may lead to incorrect +build results. To unfreeze Stage1 GHC simply drop the `--freeze1` flag and Hadrian will +rebuild all out-of-date files. + * `--haddock`: build Haddock documentation. * `--integer-simple`: build GHC using the `integer-simple` integer library (instead @@ -136,7 +142,6 @@ The new build system still lacks many important features: * Validation is not implemented: [#187][validation-issue]. * Dynamic linking on Windows is not supported [#343][dynamic-windows-issue]. * Only HTML Haddock documentation is supported (use `--haddock` flag). -* Not all modes of the old build system are supported, e.g. [#250][freeze-issue]. * Cross-compilation is not implemented: [#177][cross-compilation-issue]. * There is no support for binary distribution: [#219][install-issue]. @@ -180,7 +185,6 @@ enjoy the project. [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 [dynamic-windows-issue]: https://github.com/snowleopard/hadrian/issues/343 -[freeze-issue]: https://github.com/snowleopard/hadrian/issues/250 [cross-compilation-issue]: https://github.com/snowleopard/hadrian/issues/177 [install-issue]: https://github.com/snowleopard/hadrian/issues/219 [milestones]: https://github.com/snowleopard/hadrian/milestones From git at git.haskell.org Fri Oct 27 01:29:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't print boot's diagnostic info by default (dffda59) Message-ID: <20171027012905.7BF9D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/dffda59ac338bef1ab53e9ed4299ead89bbbeff7/ghc >--------------------------------------------------------------- commit dffda59ac338bef1ab53e9ed4299ead89bbbeff7 Author: Andrey Mokhov Date: Tue Oct 10 15:18:15 2017 +0100 Don't print boot's diagnostic info by default >--------------------------------------------------------------- dffda59ac338bef1ab53e9ed4299ead89bbbeff7 src/Rules/Configure.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Rules/Configure.hs b/src/Rules/Configure.hs index a4ef084..dd016c1 100644 --- a/src/Rules/Configure.hs +++ b/src/Rules/Configure.hs @@ -38,4 +38,5 @@ configureRules = do else do need ["configure.ac"] putBuild "| Running boot..." - quietly $ cmd "python3 boot" + verbosity <- getVerbosity + quietly $ cmd [EchoStdout (verbosity >= Loud)] "python3 boot" From git at git.haskell.org Fri Oct 27 01:29:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:09 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Register the access to the package database when compiling with GHC (03ebefd) Message-ID: <20171027012909.0541C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/03ebefdfaf33592d86105ad63de960adb9143d11/ghc >--------------------------------------------------------------- commit 03ebefdfaf33592d86105ad63de960adb9143d11 Author: Andrey Mokhov Date: Tue Oct 10 15:38:30 2017 +0100 Register the access to the package database when compiling with GHC >--------------------------------------------------------------- 03ebefdfaf33592d86105ad63de960adb9143d11 src/Rules/Compile.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index c71079a..a4b1278 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -17,7 +17,7 @@ compilePackage rs context at Context {..} = do src <- obj2src context obj need [src] needDependencies context src $ obj <.> "d" - build $ target context (compiler stage) [src] [obj] + buildWithResources rs $ target context (compiler stage) [src] [obj] compileHs = \[obj, _hi] -> do path <- buildPath context (src, deps) <- lookupDependencies (path -/- ".dependencies") obj From git at git.haskell.org Fri Oct 27 01:29:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:12 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix usage of -with-rtsopts (#429) (e4f9829) Message-ID: <20171027012912.7B55F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/e4f982978c82a274d7befec8be19b3bd2d238c5d/ghc >--------------------------------------------------------------- commit e4f982978c82a274d7befec8be19b3bd2d238c5d Author: Ben Gamari Date: Tue Oct 10 18:43:37 2017 -0400 Fix usage of -with-rtsopts (#429) When I added `-qg` to the default RTS options in 57cfa03c23047bb0c731428e97ca716d9a1cf312 (#385) I neglected to consider that it the -with-rtsopts flag would override the previous flag setting `-I0`. This had the effect of reenabling idle GC, causing GC time to regress terribly. I likely didn't notice this since I had passed the flags directly to the `hadrian` executable with `+RTS` while testing. Moreover, I mistakenly wrote `-qg0`, which (somewhat confusingly) actually *enables* parallel GC. Instead I wanted to write `-qg`. >--------------------------------------------------------------- e4f982978c82a274d7befec8be19b3bd2d238c5d hadrian.cabal | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 48514e1..8e583c7 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -133,10 +133,9 @@ executable hadrian -Wredundant-constraints -fno-warn-name-shadowing -rtsopts - -- Disable idle GC to avoid redundant GCs while waiting - -- for external processes - -with-rtsopts=-I0 - -- Don't use parallel GC as the synchronization time tends to eat any - -- benefit. - -with-rtsopts=-qg0 + -- * -I0: Disable idle GC to avoid redundant GCs while + -- waiting for external processes + -- * -qg: Don't use parallel GC as the synchronization + -- time tends to eat any benefit. + "-with-rtsopts=-I0 -qg" -threaded From git at git.haskell.org Fri Oct 27 01:29:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:16 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make Brief the default setting of the --progress-info flag (10b8358) Message-ID: <20171027012916.27D313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/10b8358882867ebfef0a48b9ba28d08fcf37eedb/ghc >--------------------------------------------------------------- commit 10b8358882867ebfef0a48b9ba28d08fcf37eedb Author: Andrey Mokhov Date: Wed Oct 11 00:03:56 2017 +0100 Make Brief the default setting of the --progress-info flag See #428 >--------------------------------------------------------------- 10b8358882867ebfef0a48b9ba28d08fcf37eedb .travis.yml | 6 +++--- README.md | 4 ++-- appveyor.yml | 2 +- circle.yml | 2 +- src/CommandLine.hs | 2 +- src/Hadrian/Utilities.hs | 2 +- 6 files changed, 9 insertions(+), 9 deletions(-) diff --git a/.travis.yml b/.travis.yml index 203ee82..e14f962 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,7 +21,7 @@ matrix: - ./build.cabal.sh selftest # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- - os: linux env: MODE="--flavour=quickest --integer-simple" @@ -40,7 +40,7 @@ matrix: script: # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. @@ -56,7 +56,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- install: # Add Cabal to PATH diff --git a/README.md b/README.md index 9eb759e..2530714 100644 --- a/README.md +++ b/README.md @@ -75,8 +75,8 @@ whether the console supports colours; this is the default setting), and `always` colours). * `--progress-info=STYLE`: choose how build progress info is printed. There are four -settings: `none`, `brief` (one line per build command), `normal` (typically a box per -build command; this is the default setting), and `unicorn` (when `normal` just won't do). +settings: `none`, `brief` (one line per build command; this is the default setting), +`normal` (typically a box per build command), and `unicorn` (when `normal` just won't do). * `--skip-configure`: use this flag to suppress the default behaviour of Hadrian that runs the `boot` and `configure` scripts automatically if need be, so that you don't have diff --git a/appveyor.yml b/appveyor.yml index c51983a..2f4653a 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -33,7 +33,7 @@ build_script: - stack exec hadrian -- --directory ".." selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-info=brief --progress-colour=never --profile=- + - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. diff --git a/circle.yml b/circle.yml index 93cf47f..48653e8 100644 --- a/circle.yml +++ b/circle.yml @@ -33,7 +33,7 @@ compile: - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --progress-info=brief --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- test: override: diff --git a/src/CommandLine.hs b/src/CommandLine.hs index ed6441c..978a420 100644 --- a/src/CommandLine.hs +++ b/src/CommandLine.hs @@ -34,7 +34,7 @@ defaultCommandLineArgs = CommandLineArgs , installDestDir = Nothing , integerSimple = False , progressColour = Auto - , progressInfo = Normal + , progressInfo = Brief , skipConfigure = False , splitObjects = False } diff --git a/src/Hadrian/Utilities.hs b/src/Hadrian/Utilities.hs index 4d2ae48..1cd22b1 100644 --- a/src/Hadrian/Utilities.hs +++ b/src/Hadrian/Utilities.hs @@ -313,7 +313,7 @@ putProgressInfo msg = do -- | Render an action. renderAction :: String -> FilePath -> FilePath -> Action String renderAction what input output = do - progressInfo <- userSetting Normal + progressInfo <- userSetting Brief return $ case progressInfo of None -> "" Brief -> "| " ++ what ++ ": " ++ i ++ " => " ++ o From git at git.haskell.org Fri Oct 27 01:29:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:23 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: build.cabal.sh: Use cabal new-run (#435) (6942b2d) Message-ID: <20171027012923.151863A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/6942b2dc08832f1521e2e8c46993c5ab977d2cb7/ghc >--------------------------------------------------------------- commit 6942b2dc08832f1521e2e8c46993c5ab977d2cb7 Author: Ben Gamari Date: Thu Oct 12 18:17:50 2017 -0400 build.cabal.sh: Use cabal new-run (#435) The previous approach was terribly unreliable, leading me to waste an hour debugging #425. >--------------------------------------------------------------- 6942b2dc08832f1521e2e8c46993c5ab977d2cb7 build.sh | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/build.sh b/build.sh index 2a0e8a7..5d1c2c2 100755 --- a/build.sh +++ b/build.sh @@ -46,9 +46,8 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th # New enough cabal version detected, so # let's use the superior 'cabal new-build' mode - # there's no 'cabal new-run' yet, but it's easy to emulate "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ + "$CABAL" new-run -- hadrian \ --lint \ --directory "$absoluteRoot/.." \ "$@" From git at git.haskell.org Fri Oct 27 01:29:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:19 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rearrange unix build scripts. (#430) (45da08b) Message-ID: <20171027012919.9DD2D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/45da08bb3c8b6806c0b3484e32abaeb4358cc6c1/ghc >--------------------------------------------------------------- commit 45da08bb3c8b6806c0b3484e32abaeb4358cc6c1 Author: Doug Wilson Date: Wed Oct 11 14:32:35 2017 +1300 Rearrange unix build scripts. (#430) Addresses Issue #428 >--------------------------------------------------------------- 45da08bb3c8b6806c0b3484e32abaeb4358cc6c1 .travis.yml | 8 ++--- build.cabal.sh => build.global-db.sh | 0 build.sh | 69 +++++++++++++++++++++--------------- build.stack.sh => build.stack.nix.sh | 8 +---- build.stack.sh | 2 +- circle.yml | 4 +-- stack.yaml | 1 + 7 files changed, 50 insertions(+), 42 deletions(-) diff --git a/.travis.yml b/.travis.yml index e14f962..e2455b2 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,10 +18,10 @@ matrix: script: # Run internal Hadrian tests - - ./build.cabal.sh selftest + - ./build.sh selftest # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - ./build.sh -j $MODE --no-progress --progress-colour=never --profile=- - os: linux env: MODE="--flavour=quickest --integer-simple" @@ -40,7 +40,7 @@ matrix: script: # Build GHC - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - ./build.sh -j $MODE --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. @@ -56,7 +56,7 @@ matrix: script: # Due to timeout limit of OS X build on Travis CI, # we will ignore selftest and build only stage1 - - ./build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - ./build.sh -j $MODE --no-progress --progress-colour=never --profile=- install: # Add Cabal to PATH diff --git a/build.cabal.sh b/build.global-db.sh similarity index 100% rename from build.cabal.sh rename to build.global-db.sh diff --git a/build.sh b/build.sh index 0f957cf..2a0e8a7 100755 --- a/build.sh +++ b/build.sh @@ -1,5 +1,7 @@ #!/usr/bin/env bash +CABAL=cabal + set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -28,34 +30,45 @@ function rl { echo "$RESULT" } -root="$(dirname "$(rl "$0")")" +absoluteRoot="$(dirname "$(rl "$0")")" +cd "$absoluteRoot" -if type cabal > /dev/null 2>&1; then - CABVERSTR=$(cabal --numeric-version) - CABVER=( ${CABVERSTR//./ } ) - if [ "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then - echo "** Cabal 1.24 or later detected. Please consider using the 'build.cabal.sh' script **" - echo "" - fi +if ! type "$CABAL" > /dev/null; then + echo "Please make sure 'cabal' is in your PATH" + exit 2 fi -mkdir -p "$root/bin" - -ghc \ - "$root/src/Main.hs" \ - -Wall \ - -fno-warn-name-shadowing \ - -XRecordWildCards \ - -i"$root/src" \ - -i"$root/../libraries/Cabal/Cabal" \ - -rtsopts \ - -with-rtsopts=-I0 \ - -threaded \ - -outputdir="$root/bin" \ - -j -O \ - -o "$root/bin/hadrian" - -"$root/bin/hadrian" \ - --lint \ - --directory "$root/.." \ - "$@" +CABVERSTR=$("$CABAL" --numeric-version) + +CABVER=( ${CABVERSTR//./ } ) + +if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then + # New enough cabal version detected, so + # let's use the superior 'cabal new-build' mode + + # there's no 'cabal new-run' yet, but it's easy to emulate + "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian + $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" + +else + # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals + echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." + + # Initialize sandbox if necessary + if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then + "$CABAL" sandbox init + "$CABAL" sandbox add-source ../libraries/Cabal/Cabal + "$CABAL" install \ + --dependencies-only \ + --disable-library-profiling \ + --disable-shared + fi + + "$CABAL" run hadrian -- \ + --lint \ + --directory "$absoluteRoot/.." \ + "$@" +fi diff --git a/build.stack.sh b/build.stack.nix.sh similarity index 82% copy from build.stack.sh copy to build.stack.nix.sh index 23f4833..59ac061 100755 --- a/build.stack.sh +++ b/build.stack.nix.sh @@ -29,11 +29,5 @@ function rl { } absoluteRoot="$(dirname "$(rl "$0")")" -cd "$absoluteRoot" -stack build --no-library-profiling - -stack exec hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" +HADRIAN_NIX=YES ${absoluteRoot}/build.stack.sh diff --git a/build.stack.sh b/build.stack.sh index 23f4833..2b1ff1d 100755 --- a/build.stack.sh +++ b/build.stack.sh @@ -31,7 +31,7 @@ function rl { absoluteRoot="$(dirname "$(rl "$0")")" cd "$absoluteRoot" -stack build --no-library-profiling +stack build --no-library-profiling ${HADRIAN_NIX:+--nix} stack exec hadrian -- \ --lint \ diff --git a/circle.yml b/circle.yml index 48653e8..a386d72 100644 --- a/circle.yml +++ b/circle.yml @@ -30,10 +30,10 @@ compile: # XXX: export PATH doesn't work well either, so we use inline env # Self test - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh selftest + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh selftest # Build GHC - - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.cabal.sh -j $MODE --no-progress --progress-colour=never --profile=- + - PATH=$HOME/.cabal/bin:$PATH ghc/hadrian/build.sh -j $MODE --no-progress --progress-colour=never --profile=- test: override: diff --git a/stack.yaml b/stack.yaml index 2a92f26..da03763 100644 --- a/stack.yaml +++ b/stack.yaml @@ -12,6 +12,7 @@ extra-deps: - shake-0.16 nix: + enable: false packages: - autoconf - automake From git at git.haskell.org Fri Oct 27 01:29:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:26 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix the list of Hadrian arguments (4b42da3) Message-ID: <20171027012926.902653A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b42da3ca484718708b157889bd0780b3076f4b0/ghc >--------------------------------------------------------------- commit 4b42da3ca484718708b157889bd0780b3076f4b0 Author: Andrey Mokhov Date: Thu Oct 12 23:29:00 2017 +0100 Fix the list of Hadrian arguments See #435 >--------------------------------------------------------------- 4b42da3ca484718708b157889bd0780b3076f4b0 build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 5d1c2c2..6c2c038 100755 --- a/build.sh +++ b/build.sh @@ -47,7 +47,7 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th # let's use the superior 'cabal new-build' mode "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - "$CABAL" new-run -- hadrian \ + "$CABAL" new-run hadrian -- \ --lint \ --directory "$absoluteRoot/.." \ "$@" From git at git.haskell.org Fri Oct 27 01:29:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:33 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't use `new-build` for pre-2.1 Cabal (65bcdcb) Message-ID: <20171027012933.8D5FC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/65bcdcbe7dd61dace537fd956b5d5d40aed6d8c9/ghc >--------------------------------------------------------------- commit 65bcdcbe7dd61dace537fd956b5d5d40aed6d8c9 Author: Andrey Mokhov Date: Tue Oct 17 23:38:17 2017 +0100 Don't use `new-build` for pre-2.1 Cabal See #438 >--------------------------------------------------------------- 65bcdcbe7dd61dace537fd956b5d5d40aed6d8c9 build.sh | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/build.sh b/build.sh index 6c2c038..d2bdb85 100755 --- a/build.sh +++ b/build.sh @@ -42,9 +42,10 @@ CABVERSTR=$("$CABAL" --numeric-version) CABVER=( ${CABVERSTR//./ } ) -if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then - # New enough cabal version detected, so - # let's use the superior 'cabal new-build' mode +if [ "${CABVER[0]}" -gt 2 -o "${CABVER[0]}" -eq 2 -a "${CABVER[1]}" -ge 1 ]; then + # New enough Cabal version detected, so let's use the superior new-build + new-run + # modes. Note that pre-2.1 Cabal does not support passing additional parameters + # to the executable (hadrian) after the separator '--', see #438. "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian "$CABAL" new-run hadrian -- \ @@ -53,8 +54,8 @@ if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; th "$@" else - # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals - echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." + # The logic below is quite fragile, but it's better than nothing for pre-2.1 Cabal. + echo "Old pre cabal 2.1 version detected. Falling back to legacy 'cabal sandbox' mode." # Initialize sandbox if necessary if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then From git at git.haskell.org Fri Oct 27 01:29:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:30 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Restore the original build script relying on the global package database (2f88f30) Message-ID: <20171027012930.18BA43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f88f30099934a46fb9ceceb4267924e3975ecaa/ghc >--------------------------------------------------------------- commit 2f88f30099934a46fb9ceceb4267924e3975ecaa Author: Andrey Mokhov Date: Sat Oct 14 23:44:49 2017 +0100 Restore the original build script relying on the global package database See #435, #430 >--------------------------------------------------------------- 2f88f30099934a46fb9ceceb4267924e3975ecaa build.global-db.sh | 66 ++++++++++++++++++------------------------------------ 1 file changed, 22 insertions(+), 44 deletions(-) diff --git a/build.global-db.sh b/build.global-db.sh index 2a0e8a7..5f1579b 100755 --- a/build.global-db.sh +++ b/build.global-db.sh @@ -1,7 +1,5 @@ #!/usr/bin/env bash -CABAL=cabal - set -euo pipefail # readlink on os x, doesn't support -f, to prevent the @@ -30,45 +28,25 @@ function rl { echo "$RESULT" } -absoluteRoot="$(dirname "$(rl "$0")")" -cd "$absoluteRoot" - -if ! type "$CABAL" > /dev/null; then - echo "Please make sure 'cabal' is in your PATH" - exit 2 -fi - -CABVERSTR=$("$CABAL" --numeric-version) - -CABVER=( ${CABVERSTR//./ } ) - -if [ "${CABVER[0]}" -eq 2 -o "${CABVER[0]}" -eq 1 -a "${CABVER[1]}" -ge 24 ]; then - # New enough cabal version detected, so - # let's use the superior 'cabal new-build' mode - - # there's no 'cabal new-run' yet, but it's easy to emulate - "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - $(find ./dist-newstyle -type f -name hadrian | head -n 1) \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" - -else - # The logic below is quite fragile, but it's better than nothing for pre-1.24 cabals - echo "Old pre cabal 1.24 version detected. Falling back to legacy 'cabal sandbox' mode." - - # Initialize sandbox if necessary - if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then - "$CABAL" sandbox init - "$CABAL" sandbox add-source ../libraries/Cabal/Cabal - "$CABAL" install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared - fi - - "$CABAL" run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" -fi +root="$(dirname "$(rl "$0")")" + +mkdir -p "$root/bin" + +ghc \ + "$root/src/Main.hs" \ + -Wall \ + -fno-warn-name-shadowing \ + -XRecordWildCards \ + -i"$root/src" \ + -i"$root/../libraries/Cabal/Cabal" \ + -rtsopts \ + -with-rtsopts=-I0 \ + -threaded \ + -outputdir="$root/bin" \ + -j -O \ + -o "$root/bin/hadrian" + +"$root/bin/hadrian" \ + --lint \ + --directory "$root/.." \ + "$@" \ No newline at end of file From git at git.haskell.org Fri Oct 27 01:29:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:37 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Rename Rules.Data to Rules.PackageData (4df3e2d) Message-ID: <20171027012937.2B24B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4df3e2dc441a5d5b6ff61f75573ff4b9a74e562f/ghc >--------------------------------------------------------------- commit 4df3e2dc441a5d5b6ff61f75573ff4b9a74e562f Author: Andrey Mokhov Date: Wed Oct 18 00:44:28 2017 +0100 Rename Rules.Data to Rules.PackageData See #433 >--------------------------------------------------------------- 4df3e2dc441a5d5b6ff61f75573ff4b9a74e562f hadrian.cabal | 2 +- src/Rules.hs | 4 ++-- src/Rules/{Data.hs => PackageData.hs} | 2 +- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index 8e583c7..54a0273 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -46,7 +46,7 @@ executable hadrian , Rules.Clean , Rules.Compile , Rules.Configure - , Rules.Data + , Rules.PackageData , Rules.Dependencies , Rules.Documentation , Rules.Generate diff --git a/src/Rules.hs b/src/Rules.hs index 730823f..97270a6 100644 --- a/src/Rules.hs +++ b/src/Rules.hs @@ -9,7 +9,7 @@ import Expression import Flavour import qualified Oracles.ModuleFiles import qualified Rules.Compile -import qualified Rules.Data +import qualified Rules.PackageData import qualified Rules.Dependencies import qualified Rules.Documentation import qualified Rules.Generate @@ -99,7 +99,7 @@ packageRules = do Rules.Program.buildProgram readPackageDb forM_ vanillaContexts $ mconcat - [ Rules.Data.buildPackageData + [ Rules.PackageData.buildPackageData , Rules.Dependencies.buildPackageDependencies readPackageDb , Rules.Documentation.buildPackageDocumentation , Rules.Library.buildPackageGhciLibrary diff --git a/src/Rules/Data.hs b/src/Rules/PackageData.hs similarity index 99% rename from src/Rules/Data.hs rename to src/Rules/PackageData.hs index c6d894b..2442b03 100644 --- a/src/Rules/Data.hs +++ b/src/Rules/PackageData.hs @@ -1,4 +1,4 @@ -module Rules.Data (buildPackageData) where +module Rules.PackageData (buildPackageData) where import Base import Context From git at git.haskell.org Fri Oct 27 01:29:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:40 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build.sh call the default build script (build.cabal.sh) (0aa31f9) Message-ID: <20171027012940.AAEA43A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/0aa31f9717e1ecb1a0b73a605a6695f8ee11e28a/ghc >--------------------------------------------------------------- commit 0aa31f9717e1ecb1a0b73a605a6695f8ee11e28a Author: Andrey Mokhov Date: Mon Oct 23 21:33:32 2017 +0100 Make build.sh call the default build script (build.cabal.sh) See #428. Also see #440: build.sh may later be relocated to the top of the GHC tree. >--------------------------------------------------------------- 0aa31f9717e1ecb1a0b73a605a6695f8ee11e28a build.sh => build.cabal.sh | 0 build.sh | 74 ++-------------------------------------------- 2 files changed, 2 insertions(+), 72 deletions(-) diff --git a/build.sh b/build.cabal.sh old mode 100755 new mode 100644 similarity index 100% copy from build.sh copy to build.cabal.sh diff --git a/build.sh b/build.sh index d2bdb85..460fdc1 100755 --- a/build.sh +++ b/build.sh @@ -1,74 +1,4 @@ #!/usr/bin/env bash -CABAL=cabal - -set -euo pipefail - -# readlink on os x, doesn't support -f, to prevent the -# need of installing coreutils (e.g. through brew, just -# for readlink, we use the follownig substitute. -# -# source: http://stackoverflow.com/a/1116890 -function rl { - TARGET_FILE="$1" - - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - - # Iterate down a (possible) chain of symlinks - while [ -L "$TARGET_FILE" ] - do - TARGET_FILE="$(readlink "$TARGET_FILE")" - cd "$(dirname "$TARGET_FILE")" - TARGET_FILE="$(basename "$TARGET_FILE")" - done - - # Compute the canonicalized name by finding the physical path - # for the directory we're in and appending the target file. - PHYS_DIR="$(pwd -P)" - RESULT="$PHYS_DIR/$TARGET_FILE" - echo "$RESULT" -} - -absoluteRoot="$(dirname "$(rl "$0")")" -cd "$absoluteRoot" - -if ! type "$CABAL" > /dev/null; then - echo "Please make sure 'cabal' is in your PATH" - exit 2 -fi - -CABVERSTR=$("$CABAL" --numeric-version) - -CABVER=( ${CABVERSTR//./ } ) - -if [ "${CABVER[0]}" -gt 2 -o "${CABVER[0]}" -eq 2 -a "${CABVER[1]}" -ge 1 ]; then - # New enough Cabal version detected, so let's use the superior new-build + new-run - # modes. Note that pre-2.1 Cabal does not support passing additional parameters - # to the executable (hadrian) after the separator '--', see #438. - - "$CABAL" new-build --disable-profiling --disable-documentation -j exe:hadrian - "$CABAL" new-run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" - -else - # The logic below is quite fragile, but it's better than nothing for pre-2.1 Cabal. - echo "Old pre cabal 2.1 version detected. Falling back to legacy 'cabal sandbox' mode." - - # Initialize sandbox if necessary - if ! ( "$CABAL" sandbox hc-pkg list > /dev/null 2>&1); then - "$CABAL" sandbox init - "$CABAL" sandbox add-source ../libraries/Cabal/Cabal - "$CABAL" install \ - --dependencies-only \ - --disable-library-profiling \ - --disable-shared - fi - - "$CABAL" run hadrian -- \ - --lint \ - --directory "$absoluteRoot/.." \ - "$@" -fi +# By default on Linux/MacOS we build Hadrian using Cabal +./build.cabal.sh "$@" From git at git.haskell.org Fri Oct 27 01:29:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:44 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Make build.bat call the default build script on Windows (build.stack.bat) (f68d527) Message-ID: <20171027012944.2FD4A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/f68d527a2f040cc16a7f03a5ce25864ed0acaa58/ghc >--------------------------------------------------------------- commit f68d527a2f040cc16a7f03a5ce25864ed0acaa58 Author: Andrey Mokhov Date: Mon Oct 23 21:36:37 2017 +0100 Make build.bat call the default build script on Windows (build.stack.bat) See #428. Note that building Hadrian with Cabal currently fails on Windows, hence using Stack. Also see #440: build.bat may later be relocated to the top of the GHC tree. >--------------------------------------------------------------- f68d527a2f040cc16a7f03a5ce25864ed0acaa58 build.bat | 33 ++------------------------------- build.bat => build.global-db.bat | 1 - 2 files changed, 2 insertions(+), 32 deletions(-) diff --git a/build.bat b/build.bat index 722f3d7..18cf6cb 100644 --- a/build.bat +++ b/build.bat @@ -1,33 +1,4 @@ @echo off -setlocal -cd %~dp0 -mkdir bin 2> nul -set ghcArgs=--make ^ - -Wall ^ - -fno-warn-name-shadowing ^ - -XRecordWildCards ^ - src\Main.hs ^ - -threaded ^ - -isrc ^ - -i..\libraries\Cabal\Cabal ^ - -rtsopts ^ - -with-rtsopts=-I0 ^ - -outputdir=bin ^ - -j ^ - -O ^ - -o bin\hadrian - -set hadrianArgs=--lint ^ - --directory ^ - ".." ^ - %* - - -ghc %ghcArgs% - -if %ERRORLEVEL% NEQ 0 EXIT /B %ERRORLEVEL% - -rem Unset GHC_PACKAGE_PATH variable, as otherwise ghc-cabal complains -set GHC_PACKAGE_PATH= -bin\hadrian %hadrianArgs% +rem By default on Windows we build Hadrian using Stack +./build.stack.bat %* diff --git a/build.bat b/build.global-db.bat similarity index 99% copy from build.bat copy to build.global-db.bat index 722f3d7..0d6a696 100644 --- a/build.bat +++ b/build.global-db.bat @@ -23,7 +23,6 @@ set hadrianArgs=--lint ^ ".." ^ %* - ghc %ghcArgs% if %ERRORLEVEL% NEQ 0 EXIT /B %ERRORLEVEL% From git at git.haskell.org Fri Oct 27 01:29:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:47 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Switch AppVeyor to use the default build.bat script (04cdf78) Message-ID: <20171027012947.A570F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/04cdf78cae2e02db1129068db5d7b5c7fc9847e5/ghc >--------------------------------------------------------------- commit 04cdf78cae2e02db1129068db5d7b5c7fc9847e5 Author: Andrey Mokhov Date: Mon Oct 23 21:37:07 2017 +0100 Switch AppVeyor to use the default build.bat script See #428 >--------------------------------------------------------------- 04cdf78cae2e02db1129068db5d7b5c7fc9847e5 appveyor.yml | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 2f4653a..fbedf8f 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -26,14 +26,13 @@ install: build_script: # Build Hadrian - - stack build alex happy # Otherwise 'stack build' fails on AppVeyor - - stack build + - stack build alex happy # Otherwise 'build' fails on AppVeyor # Run internal Hadrian tests - - stack exec hadrian -- --directory ".." selftest + - build selftest # Build GHC - - stack exec hadrian -- --lint --directory ".." -j --flavour=quickest --no-progress --progress-colour=never --profile=- + - build -j --flavour=quickest --no-progress --progress-colour=never --profile=- # Test GHC binary - cd .. From git at git.haskell.org Fri Oct 27 01:29:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:51 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix the call to another script (9e4a9c1) Message-ID: <20171027012951.5C7893A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/9e4a9c1090ac800f6f2cf44d5adeeea2152dd80a/ghc >--------------------------------------------------------------- commit 9e4a9c1090ac800f6f2cf44d5adeeea2152dd80a Author: Andrey Mokhov Date: Mon Oct 23 23:04:06 2017 +0100 Fix the call to another script >--------------------------------------------------------------- 9e4a9c1090ac800f6f2cf44d5adeeea2152dd80a build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 460fdc1..434b3a3 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,4 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -./build.cabal.sh "$@" +( ./build.cabal.sh "$@" ) From git at git.haskell.org Fri Oct 27 01:29:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:54 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CI by calling default script via bash (14c2c27) Message-ID: <20171027012954.D16E73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/14c2c279aa49b272f9cae73269bd9e99bf887b2e/ghc >--------------------------------------------------------------- commit 14c2c279aa49b272f9cae73269bd9e99bf887b2e Author: Andrey Mokhov Date: Mon Oct 23 23:18:13 2017 +0100 Fix CI by calling default script via bash >--------------------------------------------------------------- 14c2c279aa49b272f9cae73269bd9e99bf887b2e build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index 434b3a3..f40e06e 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,4 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -( ./build.cabal.sh "$@" ) +bash './build.cabal.sh "$@"' From git at git.haskell.org Fri Oct 27 01:29:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:29:58 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Drop quotes (4e7d0f9) Message-ID: <20171027012958.4F6953A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4e7d0f99d807a876dcc5ff420a42f5793c854250/ghc >--------------------------------------------------------------- commit 4e7d0f99d807a876dcc5ff420a42f5793c854250 Author: Andrey Mokhov Date: Mon Oct 23 23:25:42 2017 +0100 Drop quotes >--------------------------------------------------------------- 4e7d0f99d807a876dcc5ff420a42f5793c854250 build.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/build.sh b/build.sh index f40e06e..fa331fa 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,4 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -bash './build.cabal.sh "$@"' +bash ./build.cabal.sh "$@" From git at git.haskell.org Fri Oct 27 01:30:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:01 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Fix CI (#441) (4b60862) Message-ID: <20171027013001.CDFDB3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/4b60862b82d50a6946ac130f113c6e693f7a346d/ghc >--------------------------------------------------------------- commit 4b60862b82d50a6946ac130f113c6e693f7a346d Author: Andrey Mokhov Date: Tue Oct 24 14:02:55 2017 +0100 Fix CI (#441) * Fix CI * Another attempt * Another tweak >--------------------------------------------------------------- 4b60862b82d50a6946ac130f113c6e693f7a346d build.sh | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/build.sh b/build.sh index fa331fa..8e58b66 100755 --- a/build.sh +++ b/build.sh @@ -1,4 +1,5 @@ #!/usr/bin/env bash # By default on Linux/MacOS we build Hadrian using Cabal -bash ./build.cabal.sh "$@" +chmod a+x ./build.cabal.sh +(. ./build.cabal.sh "$@") From git at git.haskell.org Fri Oct 27 01:30:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:05 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Add 'hadrian/' from commit '4b60862b82d50a6946ac130f113c6e693f7a346d' (b2d1daa) Message-ID: <20171027013005.1934C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/b2d1daac23cc16baac69e718f1094a568f2edec1/ghc >--------------------------------------------------------------- commit b2d1daac23cc16baac69e718f1094a568f2edec1 Merge: d91a6b6 4b60862 Author: Ben Gamari Date: Thu Oct 26 09:50:56 2017 -0400 Add 'hadrian/' from commit '4b60862b82d50a6946ac130f113c6e693f7a346d' git-subtree-dir: hadrian git-subtree-mainline: d91a6b6c1d7699b6e9ace1988974d4453a20dab6 git-subtree-split: 4b60862b82d50a6946ac130f113c6e693f7a346d >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b2d1daac23cc16baac69e718f1094a568f2edec1 From git at git.haskell.org Fri Oct 27 01:30:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:07 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: Don't ignore hadrian/ (2f11b17) Message-ID: <20171027013007.EC1E93A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/2f11b17af7ef8f1b5f518dff7dbae6173e7d0515/ghc >--------------------------------------------------------------- commit 2f11b17af7ef8f1b5f518dff7dbae6173e7d0515 Author: Ben Gamari Date: Thu Oct 26 09:51:02 2017 -0400 Don't ignore hadrian/ >--------------------------------------------------------------- 2f11b17af7ef8f1b5f518dff7dbae6173e7d0515 .gitignore | 1 - 1 file changed, 1 deletion(-) diff --git a/.gitignore b/.gitignore index 710c6bf..f1b38d6 100644 --- a/.gitignore +++ b/.gitignore @@ -49,7 +49,6 @@ stage0 stage1 stage2 _build -hadrian # ----------------------------------------------------------------------------- # Ignore any overlapped darcs repos and back up files From git at git.haskell.org Fri Oct 27 01:30:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:13 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump Cabal submodule (5d02bca) Message-ID: <20171027013013.886223A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/5d02bca29596e28b0499f4706062c8c804908bd9/ghc >--------------------------------------------------------------- commit 5d02bca29596e28b0499f4706062c8c804908bd9 Author: Ben Gamari Date: Thu Oct 26 16:19:41 2017 -0400 Bump Cabal submodule >--------------------------------------------------------------- 5d02bca29596e28b0499f4706062c8c804908bd9 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index c84a3c7..b26a9ee 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit c84a3c72196d0a5361f8ab77c6d8cb63b7a5d55d +Subproject commit b26a9ee3eb062ac727141fd9fd85835c2349f380 From git at git.haskell.org Fri Oct 27 01:30:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:10 +0000 (UTC) Subject: [commit: ghc] wip/nfs-locking: base: Implement file locking in terms of POSIX locks (1cd7473) Message-ID: <20171027013010.CC01F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nfs-locking Link : http://ghc.haskell.org/trac/ghc/changeset/1cd7473f8e800a99e95180579480a0e62e98040b/ghc >--------------------------------------------------------------- commit 1cd7473f8e800a99e95180579480a0e62e98040b Author: Ben Gamari Date: Thu Oct 26 10:40:11 2017 -0400 base: Implement file locking in terms of POSIX locks Hopefully these are more robust to NFS malfunction than BSD flock-style locks. See #13945. >--------------------------------------------------------------- 1cd7473f8e800a99e95180579480a0e62e98040b libraries/base/GHC/IO/Handle/Lock.hsc | 74 ++++++++++++++++++++++++++++++++++- libraries/base/configure.ac | 7 +++- 2 files changed, 78 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/IO/Handle/Lock.hsc b/libraries/base/GHC/IO/Handle/Lock.hsc index daf407c..b0a3449 100644 --- a/libraries/base/GHC/IO/Handle/Lock.hsc +++ b/libraries/base/GHC/IO/Handle/Lock.hsc @@ -104,7 +104,76 @@ hUnlock = unlockImpl ---------------------------------------- -#if HAVE_FLOCK +#if HAVE_OFD_LOCKING +-- Linux open file descriptor locking. +-- +-- We prefer this over BSD locking (e.g. flock) since the latter appears to +-- break in some NFS configurations. Note that we intentionally do not try to +-- use ordinary POSIX file locking due to its peculiar semantics under +-- multi-threaded environments. + +foreign import ccall interruptible "fcntl" + c_fcntl :: CInt -> CInt -> Ptr () -> IO CInt + +data FLock = FLock { l_type :: CShort + , l_whence :: CShort + , l_start :: COff + , l_len :: COff + , l_pid :: CPid + } + +instance Storable FLock where + sizeOf _ = #{size flock} + alignment _ = #{alignment flock} + poke ptr x = do + fillBytes ptr 0 (sizeOf x) + #{poke flock, l_type} ptr (l_type x) + #{poke flock, l_whence} ptr (l_whence x) + #{poke flock, l_start} ptr (l_start x) + #{poke flock, l_len} ptr (l_len x) + #{poke flock, l_pid} ptr (l_pid x) + peek ptr = do + FLock <$> #{peek flock, l_type} ptr + <*> #{peek flock, l_whence} ptr + <*> #{peek flock, l_start} ptr + <*> #{peek flock, l_len} ptr + <*> #{peek flock, l_pid} ptr + +lockImpl :: Handle -> String -> LockMode -> Bool -> IO Bool +lockImpl h ctx mode block = do + FD{fdFD = fd} <- handleToFd h + with flock $ \flock_ptr -> fix $ \retry -> do + ret <- with flock $ fcntl fd mode flock_ptr + case ret of + 0 -> return True + _ -> getErrno >>= \errno -> if + | not block && errno == eWOULDBLOCK -> return False + | errno == eINTR -> retry + | otherwise -> ioException $ errnoToIOError ctx errno (Just h) Nothing + where + flock = FLock { l_type = case mode of + SharedLock -> #{const F_RDLCK} + ExclusiveLock -> #{const F_WRLCK} + , l_whence = #{const SEEK_SET} + , l_start = 0 + , l_len = 0 + } + mode + | block = #{const F_SETLKW} + | otherwise = #{const F_SETLK} + +unlockImpl :: Handle -> IO () +unlockImpl h = do + FD{fdFD = fd} <- handleToFd h + let flock = FLock { l_type = #{const F_UNLCK} + , l_whence = #{const SEEK_SET} + , l_start = 0 + , l_len = 0 + } + throwErrnoIfMinus1_ "hUnlock" + $ with flock $ c_fcntl fd #{const F_SETLK} + +#elif HAVE_FLOCK lockImpl :: Handle -> String -> LockMode -> Bool -> IO Bool lockImpl h ctx mode block = do @@ -113,7 +182,8 @@ lockImpl h ctx mode block = do fix $ \retry -> c_flock fd flags >>= \case 0 -> return True _ -> getErrno >>= \errno -> if - | not block && errno == eWOULDBLOCK -> return False + | not block + , errno == eAGAIN || errno == eACCES -> return False | errno == eINTR -> retry | otherwise -> ioException $ errnoToIOError ctx errno (Just h) Nothing where diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index af041a7..69ea800 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -69,7 +69,12 @@ if test "$ac_cv_header_poll_h" = yes && test "$ac_cv_func_poll" = yes; then AC_DEFINE([HAVE_POLL], [1], [Define if you have poll support.]) fi -#flock +# Linux open file description locks +AC_CHECK_DECL([F_OFD_SETLK], [ + AC_DEFINE([HAVE_OFD_LOCKING], [1], [Define if you have open file descriptor lock support.]) +]) + +# flock AC_CHECK_FUNCS([flock]) if test "$ac_cv_header_sys_file_h" = yes && test "$ac_cv_func_flock" = yes; then AC_DEFINE([HAVE_FLOCK], [1], [Define if you have flock support.]) From git at git.haskell.org Fri Oct 27 01:30:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:16 +0000 (UTC) Subject: [commit: ghc] wip/T14152: simplNonRecJoinPoint: Handle Shadowing correctly (ef5fa5d) Message-ID: <20171027013016.4B7113A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/ef5fa5d7105c5a0ccc7cb067a2db70771052d6dc/ghc >--------------------------------------------------------------- commit ef5fa5d7105c5a0ccc7cb067a2db70771052d6dc Author: Joachim Breitner Date: Thu Oct 26 19:36:24 2017 -0400 simplNonRecJoinPoint: Handle Shadowing correctly Previously, (since 33452df), simplNonRecJoinPoint would do the wrong thing in the presence of shadowing: It analyzed the RHS of a join binding with the environment for the body. In particular, with foo x = join x = x * x in x where there is shadowing, it renames the inner x to x1, and should produce foo x = join x1 = x * x in x1 but because the substitution (x ↦ x1) is also used on the RHS we get the bogus foo x = join x1 = x1 * x1 in x1 The corresponding function for non-join-points, i.e. simplNonRecE, does the right thing and has done so forever, so I’ll skip creating a test case or a note for this. Differential Revision: https://phabricator.haskell.org/D4130 >--------------------------------------------------------------- ef5fa5d7105c5a0ccc7cb067a2db70771052d6dc compiler/simplCore/Simplify.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index d6b859a..3497e67 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -204,7 +204,7 @@ simplRecOrTopPair env top_lvl is_rec mb_cont old_bndr new_bndr rhs | Just cont <- mb_cont = ASSERT( isNotTopLevel top_lvl && isJoinId new_bndr ) trace_bind "join" $ - simplJoinBind env cont old_bndr new_bndr rhs + simplJoinBind env cont old_bndr new_bndr rhs env | otherwise = trace_bind "normal" $ @@ -300,10 +300,10 @@ simplJoinBind :: SimplEnv -> InId -> OutId -- Binder, both pre-and post simpl -- The OutId has IdInfo, except arity, -- unfolding - -> InExpr + -> InExpr -> SimplEnv -- The right hand side and its env -> SimplM (SimplFloats, SimplEnv) -simplJoinBind env cont old_bndr new_bndr rhs - = do { rhs' <- simplJoinRhs env old_bndr rhs cont +simplJoinBind env cont old_bndr new_bndr rhs rhs_se + = do { rhs' <- simplJoinRhs rhs_se old_bndr rhs cont ; completeBind env NotTopLevel (Just cont) old_bndr new_bndr rhs' } -------------------------- @@ -1471,7 +1471,7 @@ simplNonRecJoinPoint env bndr rhs body cont ; let res_ty = contResultType cont ; (env1, bndr1) <- simplNonRecJoinBndr env res_ty bndr ; (env2, bndr2) <- addBndrRules env1 bndr bndr1 - ; (floats1, env3) <- simplJoinBind env2 cont bndr bndr2 rhs + ; (floats1, env3) <- simplJoinBind env2 cont bndr bndr2 rhs env ; (floats2, body') <- simplExprF env3 body cont ; return (floats1 `addFloats` floats2, body') } From git at git.haskell.org Fri Oct 27 01:30:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:20 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (0fb603d) Message-ID: <20171027013020.68CD23A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/0fb603d6d3ad840a504d6ea81c9ac9a23a76e8cc/ghc >--------------------------------------------------------------- commit 0fb603d6d3ad840a504d6ea81c9ac9a23a76e8cc Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 The idea is described in #14152, and can be summarized: Float the exit path out of a joinrec, so that the simplifier can do more with it. See the test case for a nice example. The floating goes against what the simplifier usually does, hence we need to be careful not inline them back. The position of exitification in the pipeline was chosen after a small amount of experimentation, but may need to be improved. For example, exitification can allow rewrite rules to fire, but for that it would have to happen before the `simpl_phases`. Together with the next patch, perf.haskell.org reports these nice performance wins: Nofib allocations prev change gain fannkuch-redux 78446688 - 99.92% 64608 k-nucleotide 109466432 - 91.32% 9502064 simple 72424696 - 5.96% 68109560 Nofib instruction counts compress2 573354476 + 3.34% 592476104 k-nucleotide 2310080537 - 5.59% 2180917263 scs 1979135192 - 3.2% 1915880589 simple 670348375 - 4.9% 637507288 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- 0fb603d6d3ad840a504d6ea81c9ac9a23a76e8cc compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 403 +++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 13 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + testsuite/tests/simplCore/should_compile/T14152.hs | 23 ++ .../tests/simplCore/should_compile/T14152.stderr | 129 +++++++ .../tests/simplCore/should_compile/T14152a.hs | 1 + .../tests/simplCore/should_compile/T14152a.stderr | 222 ++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 2 + 17 files changed, 831 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0fb603d6d3ad840a504d6ea81c9ac9a23a76e8cc From git at git.haskell.org Fri Oct 27 01:30:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:23 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Run exitification only early (e595228) Message-ID: <20171027013023.2EDD13A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/e595228888f48ac81d8405fba8e8b09d4a9b6006/ghc >--------------------------------------------------------------- commit e595228888f48ac81d8405fba8e8b09d4a9b6006 Author: Joachim Breitner Date: Wed Oct 25 10:12:40 2017 -0400 Run exitification only early (This is series of commit to measure and optimize placement.) >--------------------------------------------------------------- e595228888f48ac81d8405fba8e8b09d4a9b6006 compiler/simplCore/SimplCore.hs | 6 ------ 1 file changed, 6 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 5ed5cb0..45823d4 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -286,8 +286,6 @@ getCoreToDo dflags simpl_phases, - runWhen exitification CoreDoExitify, - -- Phase 0: allow all Ids to be inlined now -- This gets foldr inlined before strictness analysis @@ -314,8 +312,6 @@ getCoreToDo dflags runWhen strictness demand_analyser, - runWhen exitification CoreDoExitify, - runWhen full_laziness $ CoreDoFloatOutwards FloatOutSwitches { floatOutLambdas = floatLamArgs dflags, @@ -351,8 +347,6 @@ getCoreToDo dflags maybe_rule_check (Phase 0), - runWhen exitification CoreDoExitify, - -- Final clean-up simplification: simpl_phase 0 ["final"] max_iter, From git at git.haskell.org Fri Oct 27 01:30:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:25 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Run exitification after demand analysis (369385c) Message-ID: <20171027013025.EA6663A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/369385cc0a3601d5ea4d25530016aeae9f799230/ghc >--------------------------------------------------------------- commit 369385cc0a3601d5ea4d25530016aeae9f799230 Author: Joachim Breitner Date: Thu Oct 26 09:21:38 2017 -0400 Run exitification after demand analysis >--------------------------------------------------------------- 369385cc0a3601d5ea4d25530016aeae9f799230 compiler/simplCore/SimplCore.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 10115c4..21a5c21 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -284,8 +284,6 @@ getCoreToDo dflags simpl_phases, - runWhen exitification CoreDoExitify, - -- Phase 0: allow all Ids to be inlined now -- This gets foldr inlined before strictness analysis @@ -312,6 +310,8 @@ getCoreToDo dflags runWhen strictness demand_analyser, + runWhen exitification CoreDoExitify, + runWhen full_laziness $ CoreDoFloatOutwards FloatOutSwitches { floatOutLambdas = floatLamArgs dflags, From git at git.haskell.org Fri Oct 27 01:30:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:28 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (0350a7e) Message-ID: <20171027013028.C07403A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/0350a7e9ab682c53b68d587d3ae40812159dd733/ghc >--------------------------------------------------------------- commit 0350a7e9ab682c53b68d587d3ae40812159dd733 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration because the extra jump is a bit pointless there. It still increases the number of instructions of `compress2` by 3.82%, so that needs to be investiaged. >--------------------------------------------------------------- 0350a7e9ab682c53b68d587d3ae40812159dd733 compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 6 ++++++ compiler/simplCore/SimplCore.hs | 40 +++++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 41 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0350a7e9ab682c53b68d587d3ae40812159dd733 From git at git.haskell.org Fri Oct 27 01:30:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:31 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Run exitification before the main simplifier (b094ea8) Message-ID: <20171027013031.80D193A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/b094ea8702b6e65304176c7ab42ba539fcb93ccd/ghc >--------------------------------------------------------------- commit b094ea8702b6e65304176c7ab42ba539fcb93ccd Author: Joachim Breitner Date: Thu Oct 26 09:21:20 2017 -0400 Run exitification before the main simplifier (This is series of commit to measure and optimize placement.) >--------------------------------------------------------------- b094ea8702b6e65304176c7ab42ba539fcb93ccd compiler/simplCore/SimplCore.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 45823d4..10115c4 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -282,10 +282,10 @@ getCoreToDo dflags -- StaticPtrTable. static_ptrs_float_outwards, - runWhen exitification CoreDoExitify, - simpl_phases, + runWhen exitification CoreDoExitify, + -- Phase 0: allow all Ids to be inlined now -- This gets foldr inlined before strictness analysis From git at git.haskell.org Fri Oct 27 01:30:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:34 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Run exitification before the final simplifier run (8358716) Message-ID: <20171027013034.42E353A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/8358716d93337455e5884f56596ea4973db35fcc/ghc >--------------------------------------------------------------- commit 8358716d93337455e5884f56596ea4973db35fcc Author: Joachim Breitner Date: Thu Oct 26 09:22:06 2017 -0400 Run exitification before the final simplifier run >--------------------------------------------------------------- 8358716d93337455e5884f56596ea4973db35fcc compiler/simplCore/SimplCore.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 21a5c21..a88ed63 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -310,8 +310,6 @@ getCoreToDo dflags runWhen strictness demand_analyser, - runWhen exitification CoreDoExitify, - runWhen full_laziness $ CoreDoFloatOutwards FloatOutSwitches { floatOutLambdas = floatLamArgs dflags, @@ -347,6 +345,8 @@ getCoreToDo dflags maybe_rule_check (Phase 0), + runWhen exitification CoreDoExitify, + -- Final clean-up simplification: simpl_phase 0 ["final"] max_iter, From git at git.haskell.org Fri Oct 27 01:30:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 01:30:36 +0000 (UTC) Subject: [commit: ghc] wip/T14152's head updated: Inline exit join points in the "final" simplifier iteration (0350a7e) Message-ID: <20171027013036.79B9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14152' now includes: d91a6b6 Declare upstram repo location for hsc2hs ef5fa5d simplNonRecJoinPoint: Handle Shadowing correctly 0fb603d Implement a dedicated exitfication pass #14152 e595228 Run exitification only early b094ea8 Run exitification before the main simplifier 369385c Run exitification after demand analysis 8358716 Run exitification before the final simplifier run 0350a7e Inline exit join points in the "final" simplifier iteration From git at git.haskell.org Fri Oct 27 05:32:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 05:32:24 +0000 (UTC) Subject: [commit: ghc] master: configure: Add Alpine Linux to checkVendor (9ae24bb) Message-ID: <20171027053224.269123A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9ae24bb615416b3e8d972d45ebe3dd281242d213/ghc >--------------------------------------------------------------- commit 9ae24bb615416b3e8d972d45ebe3dd281242d213 Author: Tuncer Ayaz Date: Tue Aug 1 19:25:25 2017 +0000 configure: Add Alpine Linux to checkVendor >--------------------------------------------------------------- 9ae24bb615416b3e8d972d45ebe3dd281242d213 aclocal.m4 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 64fa8bf..c8c5985 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -229,7 +229,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], checkVendor() { case [$]1 in - dec|none|unknown|hp|apple|next|sun|sgi|ibm|montavista|portbld) + dec|none|unknown|hp|apple|next|sun|sgi|ibm|montavista|portbld|alpine) ;; *) AC_MSG_WARN([Unknown vendor [$]1]) From git at git.haskell.org Fri Oct 27 05:32:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 05:32:21 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Disable index node generation (160a491) Message-ID: <20171027053221.61E323A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/160a4911f8a90e0f54d13b2aa0f6f70ebdfd1020/ghc >--------------------------------------------------------------- commit 160a4911f8a90e0f54d13b2aa0f6f70ebdfd1020 Author: Ben Gamari Date: Thu Oct 26 19:11:58 2017 -0400 users-guide: Disable index node generation This is breaking the build on some platforms. It's unclear exactly why but I don't have time to investigate at the moment. >--------------------------------------------------------------- 160a4911f8a90e0f54d13b2aa0f6f70ebdfd1020 docs/users_guide/flags.py | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/flags.py b/docs/users_guide/flags.py index 6e8788d..66b0e92 100644 --- a/docs/users_guide/flags.py +++ b/docs/users_guide/flags.py @@ -259,9 +259,10 @@ class LanguageExtension(GenericFlag): targetname = '%s-%s' % (self.objtype, name) + # FIXME: This causes some Sphinx versions to fail # Add index entries for the -XFoo flag - self.indexnode['entries'].append(('pair', '-X%s; GHC option' % name, - targetname, '', None)) + #self.indexnode['entries'].append(('pair', '-X%s; GHC option' % name, + # targetname, '', None)) # Make this also addressable using :ghc-flag:-XFoo self.env.domaindata['std']['objects']['ghc-flag', '-X%s' % name] = \ From git at git.haskell.org Fri Oct 27 05:32:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 05:32:26 +0000 (UTC) Subject: [commit: ghc] master: Don't use $SHELL in wrapper scripts (a10c2e6) Message-ID: <20171027053226.E815B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a10c2e6e9e9af3addbf91c0bb374257fb6c72553/ghc >--------------------------------------------------------------- commit a10c2e6e9e9af3addbf91c0bb374257fb6c72553 Author: Joachim Breitner Date: Tue Aug 1 19:30:09 2017 +0000 Don't use $SHELL in wrapper scripts Do not use $SHELL as $SHELL is the user's preferred interactive shell. We do not want this to leak into the wrapper scripts. >--------------------------------------------------------------- a10c2e6e9e9af3addbf91c0bb374257fb6c72553 driver/ghci/ghc.mk | 4 ++-- rules/shell-wrapper.mk | 6 +++--- utils/mkdirhier/ghc.mk | 2 +- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/driver/ghci/ghc.mk b/driver/ghci/ghc.mk index 0f31884..0e18a5f 100644 --- a/driver/ghci/ghc.mk +++ b/driver/ghci/ghc.mk @@ -21,7 +21,7 @@ install_driver_ghci: $(INSTALL_DIR) "$(DESTDIR)$(bindir)" $(call removeFiles, "$(WRAPPER)") $(CREATE_SCRIPT) "$(WRAPPER)" - echo '#!$(SHELL)' >> "$(WRAPPER)" + echo '#!/bin/sh' >> "$(WRAPPER)" echo 'exec "$(bindir)/$(CrossCompilePrefix)ghc-$(ProjectVersion)" --interactive "$$@"' >> "$(WRAPPER)" $(EXECUTABLE_FILE) "$(WRAPPER)" $(call removeFiles,"$(DESTDIR)$(bindir)/$(CrossCompilePrefix)ghci") @@ -56,7 +56,7 @@ install_driver_ghcii: GHCII_SCRIPT_VERSIONED = $(DESTDIR)$(bindir)/ghcii-$(Proje install_driver_ghcii: $(INSTALL_DIR) "$(DESTDIR)$(bindir)" $(call removeFiles,"$(GHCII_SCRIPT)") - echo "#!$(SHELL)" >> $(GHCII_SCRIPT) + echo "#!/bin/sh" >> $(GHCII_SCRIPT) echo 'exec "$$(dirname "$$0")"/ghc --interactive "$$@"' >> $(GHCII_SCRIPT) $(EXECUTABLE_FILE) $(GHCII_SCRIPT) cp $(GHCII_SCRIPT) $(GHCII_SCRIPT_VERSIONED) diff --git a/rules/shell-wrapper.mk b/rules/shell-wrapper.mk index eb7d8f1..bdab6e2 100644 --- a/rules/shell-wrapper.mk +++ b/rules/shell-wrapper.mk @@ -41,7 +41,7 @@ $$($1_$2_INPLACE_WRAPPER): $$($1_$2_SHELL_WRAPPER_NAME) endif $$($1_$2_INPLACE_WRAPPER): $$($1_$2_INPLACE) $$(call removeFiles, $$@) - echo '#!$$(SHELL)' >> $$@ + echo '#!/bin/sh' >> $$@ echo 'executablename="$$(TOP)/$$<"' >> $$@ echo 'datadir="$$(TOP)/$$(INPLACE_LIB)"' >> $$@ echo 'bindir="$$(TOP)/$$(INPLACE_BIN)"' >> $$@ @@ -80,7 +80,7 @@ install_$1_$2_wrapper: $$(INSTALL_DIR) "$$(DESTDIR)$$(bindir)" $$(call removeFiles, "$$(WRAPPER)") $$(CREATE_SCRIPT) "$$(WRAPPER)" - echo '#!$$(SHELL)' >> "$$(WRAPPER)" + echo '#!/bin/sh' >> "$$(WRAPPER)" echo 'exedir="$$(ghclibexecdir)/bin"' >> "$$(WRAPPER)" echo 'exeprog="$$($1_$2_PROG)"' >> "$$(WRAPPER)" echo 'executablename="$$$$exedir/$$$$exeprog"' >> "$$(WRAPPER)" @@ -106,7 +106,7 @@ BINDIST_EXTRAS += $$($1_$2_BINDIST_WRAPPER) $$($1_$2_BINDIST_WRAPPER): $1/$2/build/tmp/$$($1_$2_PROG) $$(call removeFiles, $$@) - echo '#!$$(SHELL)' >> $$@ + echo '#!/bin/sh' >> $$@ ifeq "$$(DYNAMIC_GHC_PROGRAMS)" "YES" echo '$$(call prependLibraryPath,$$($1_$2_DEP_LIB_REL_DIRS_SEARCHPATH))' >> $$@ endif diff --git a/utils/mkdirhier/ghc.mk b/utils/mkdirhier/ghc.mk index 55803f0..2e3a301 100644 --- a/utils/mkdirhier/ghc.mk +++ b/utils/mkdirhier/ghc.mk @@ -14,7 +14,7 @@ $(MKDIRHIER) : utils/mkdirhier/mkdirhier.sh mkdir -p $(INPLACE_BIN) mkdir -p $(INPLACE_LIB) $(call removeFiles,$@) - echo '#!$(SHELL)' >> $@ + echo '#!/bin/sh' >> $@ cat utils/mkdirhier/mkdirhier.sh >> $@ $(EXECUTABLE_FILE) $@ From git at git.haskell.org Fri Oct 27 05:39:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 05:39:33 +0000 (UTC) Subject: [commit: ghc] branch 'wip/cmmsink' created Message-ID: <20171027053933.88E153A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/cmmsink Referencing: e2b7dff7108a2b3715a04c9c22f99077446ac6dc From git at git.haskell.org Fri Oct 27 05:39:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 05:39:36 +0000 (UTC) Subject: [commit: ghc] wip/cmmsink: CmmSink: Use a UniqSet instead of a list (e2b7dff) Message-ID: <20171027053936.51BE33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cmmsink Link : http://ghc.haskell.org/trac/ghc/changeset/e2b7dff7108a2b3715a04c9c22f99077446ac6dc/ghc >--------------------------------------------------------------- commit e2b7dff7108a2b3715a04c9c22f99077446ac6dc Author: alexbiehl Date: Fri Oct 27 07:37:57 2017 +0200 CmmSink: Use a UniqSet instead of a list Vanilla: 39,547,770,160 bytes allocated in the heap 3,923,879,584 bytes copied during GC 113,403,744 bytes maximum residency (39 sample(s)) 778,848 bytes maximum slop 303 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 2595 colls, 0 par 10.290s 10.495s 0.0040s 0.3172s Gen 1 39 colls, 0 par 0.023s 0.024s 0.0006s 0.0030s TASKS: 4 (1 bound, 3 peak workers (3 total), using -N1) SPARKS: 0 (0 converted, 0 overflowed, 0 dud, 0 GC'd, 0 fizzled) INIT time 0.000s ( 0.003s elapsed) MUT time 52.526s ( 54.734s elapsed) GC time 10.314s ( 10.519s elapsed) EXIT time 0.017s ( 0.051s elapsed) Total time 62.857s ( 65.308s elapsed) Alloc rate 752,919,176 bytes per MUT second Productivity 83.6% of total user, 83.9% of total elapsed gc_alloc_block_sync: 0 whitehole_spin: 0 gen[0].sync: 0 gen[1].sync: 0 `skipped` as UniqSet: 41,426,419,720 bytes allocated in the heap 3,953,425,208 bytes copied during GC 116,264,392 bytes maximum residency (39 sample(s)) 664,480 bytes maximum slop 314 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 3244 colls, 0 par 10.307s 10.504s 0.0032s 0.3317s Gen 1 39 colls, 0 par 0.024s 0.025s 0.0006s 0.0030s TASKS: 4 (1 bound, 3 peak workers (3 total), using -N1) SPARKS: 0 (0 converted, 0 overflowed, 0 dud, 0 GC'd, 0 fizzled) INIT time 0.000s ( 0.003s elapsed) MUT time 37.890s ( 40.121s elapsed) GC time 10.331s ( 10.529s elapsed) EXIT time 0.019s ( 0.063s elapsed) Total time 48.241s ( 50.715s elapsed) Alloc rate 1,093,320,118 bytes per MUT second Productivity 78.6% of total user, 79.2% of total elapsed gc_alloc_block_sync: 0 whitehole_spin: 0 gen[0].sync: 0 gen[1].sync: 0 >--------------------------------------------------------------- e2b7dff7108a2b3715a04c9c22f99077446ac6dc compiler/cmm/CmmSink.hs | 15 ++++++++------- 1 file changed, 8 insertions(+), 7 deletions(-) diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs index a674e54..1892e28 100644 --- a/compiler/cmm/CmmSink.hs +++ b/compiler/cmm/CmmSink.hs @@ -18,6 +18,7 @@ import Platform (isARM, platformArch) import DynFlags import UniqFM +import UniqSet import PprCmm () import Data.List (partition) @@ -399,7 +400,7 @@ tryToInline , Assignments -- Remaining assignments ) -tryToInline dflags live node assigs = go usages node [] assigs +tryToInline dflags live node assigs = go usages node emptyUniqSet assigs where usages :: UniqFM Int -- Maps each LocalReg to a count of how often it is used usages = foldLocalRegsUsed dflags addUsage emptyUFM node @@ -422,7 +423,7 @@ tryToInline dflags live node assigs = go usages node [] assigs inline_and_keep = keep inl_node -- inline the assignment, keep it keep node' = (final_node, a : rest') - where (final_node, rest') = go usages' node' (l:skipped) rest + where (final_node, rest') = go usages' node' (addOneToUniqSet skipped l) rest usages' = foldLocalRegsUsed dflags (\m r -> addToUFM m r 2) usages rhs -- we must not inline anything that is mentioned in the RHS @@ -430,7 +431,7 @@ tryToInline dflags live node assigs = go usages node [] assigs -- usages of the regs on the RHS to 2. cannot_inline = skipped `regsUsedIn` rhs -- Note [dependent assignments] - || l `elem` skipped + || l `elementOfUniqSet` skipped || not (okToInline dflags rhs node) l_usages = lookupUFM usages l @@ -521,11 +522,11 @@ And we do that right here in tryToInline, just as we do cmmMachOpFold. addUsage :: UniqFM Int -> LocalReg -> UniqFM Int addUsage m r = addToUFM_C (+) m r 1 -regsUsedIn :: [LocalReg] -> CmmExpr -> Bool -regsUsedIn [] _ = False +regsUsedIn :: UniqSet LocalReg -> CmmExpr -> Bool +regsUsedIn ls _ | isEmptyUniqSet ls = False regsUsedIn ls e = wrapRecExpf f e False - where f (CmmReg (CmmLocal l)) _ | l `elem` ls = True - f (CmmRegOff (CmmLocal l) _) _ | l `elem` ls = True + where f (CmmReg (CmmLocal l)) _ | l `elementOfUniqSet` ls = True + f (CmmRegOff (CmmLocal l) _) _ | l `elementOfUniqSet` ls = True f _ z = z -- we don't inline into CmmUnsafeForeignCall if the expression refers From git at git.haskell.org Fri Oct 27 07:21:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 07:21:55 +0000 (UTC) Subject: [commit: ghc] master: Add more pprTrace to SpecConstr (debug only) (355318c) Message-ID: <20171027072155.1D34E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/355318c30f047639aba799b38315950514dec590/ghc >--------------------------------------------------------------- commit 355318c30f047639aba799b38315950514dec590 Author: Simon Peyton Jones Date: Thu Oct 26 17:12:17 2017 +0100 Add more pprTrace to SpecConstr (debug only) >--------------------------------------------------------------- 355318c30f047639aba799b38315950514dec590 compiler/specialise/SpecConstr.hs | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs index 86d7093..69df759 100644 --- a/compiler/specialise/SpecConstr.hs +++ b/compiler/specialise/SpecConstr.hs @@ -1547,7 +1547,11 @@ specRec top_lvl env body_usg rhs_infos return (usg_so_far, spec_infos) | otherwise - = do { specs_w_usg <- zipWithM (specialise env seed_calls) rhs_infos spec_infos + = -- pprTrace "specRec3" (vcat [ text "bndrs" <+> ppr (map ri_fn rhs_infos) + -- , text "iteration" <+> int n_iter + -- , text "spec_infos" <+> ppr (map (map os_pat . si_specs) spec_infos) + -- ]) $ + do { specs_w_usg <- zipWithM (specialise env seed_calls) rhs_infos spec_infos ; let (extra_usg_s, new_spec_infos) = unzip specs_w_usg extra_usg = combineUsages extra_usg_s all_usg = usg_so_far `combineUsage` extra_usg @@ -1955,7 +1959,8 @@ callsToNewPats env fn spec_info@(SI { si_specs = done_specs }) bndr_occs calls -- Discard specialisations if there are too many of them trimmed_pats = trim_pats env fn spec_info small_pats --- ; pprTrace "callsToPats" (vcat [ text "calls:" <+> ppr calls +-- ; pprTrace "callsToPats" (vcat [ text "calls to" <+> ppr fn <> colon <+> ppr calls +-- , text "done_specs:" <+> ppr (map os_pat done_specs) -- , text "good_pats:" <+> ppr good_pats ]) $ -- return () @@ -1968,7 +1973,8 @@ trim_pats env fn (SI { si_n_specs = done_spec_count }) pats | sc_force env || isNothing mb_scc || n_remaining >= n_pats - = pats -- No need to trim + = -- pprTrace "trim_pats: no-trim" (ppr (sc_force env) $$ ppr mb_scc $$ ppr n_remaining $$ ppr n_pats) + pats -- No need to trim | otherwise = emit_trace $ -- Need to trim, so keep the best ones @@ -2012,6 +2018,8 @@ trim_pats env fn (SI { si_n_specs = done_spec_count }) pats speakNOf spec_count' (text "call pattern") <> comma <+> text "but the limit is" <+> int max_specs) ] , text "Use -fspec-constr-count=n to set the bound" + , text "done_spec_count =" <+> int done_spec_count + , text "Keeping " <+> int n_remaining <> text ", out of" <+> int n_pats , text "Discarding:" <+> ppr (drop n_remaining sorted_pats) ] From git at git.haskell.org Fri Oct 27 07:21:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 07:21:57 +0000 (UTC) Subject: [commit: ghc] master: Fix an exponential-blowup case in SpecConstr (7d7d94f) Message-ID: <20171027072157.D4FCA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7d7d94fb4876dc7e58263abc9dd65921e09cddac/ghc >--------------------------------------------------------------- commit 7d7d94fb4876dc7e58263abc9dd65921e09cddac Author: Simon Peyton Jones Date: Thu Oct 26 17:24:52 2017 +0100 Fix an exponential-blowup case in SpecConstr Trac #14379 showed a case where use of "forcing" to do "damn the torpedos" specialisation without resource limits (which 'vector' does a lot) led to exponential blowup. The fix is easy. Finding it wasn't. See Note [Forcing specialisation] and the one-line change in decreaseSpecCount. >--------------------------------------------------------------- 7d7d94fb4876dc7e58263abc9dd65921e09cddac compiler/specialise/SpecConstr.hs | 53 ++++++++++++++++++++++++--------------- 1 file changed, 33 insertions(+), 20 deletions(-) diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs index 69df759..cfb9b5f 100644 --- a/compiler/specialise/SpecConstr.hs +++ b/compiler/specialise/SpecConstr.hs @@ -59,9 +59,6 @@ import Control.Monad ( zipWithM ) import Data.List import PrelNames ( specTyConName ) import Module - --- See Note [Forcing specialisation] - import TyCon ( TyCon ) import GHC.Exts( SpecConstrAnnotation(..) ) import Data.Ord( comparing ) @@ -504,6 +501,7 @@ This is all quite ugly; we ought to come up with a better design. ForceSpecConstr arguments are spotted in scExpr' and scTopBinds which then set sc_force to True when calling specLoop. This flag does four things: + * Ignore specConstrThreshold, to specialise functions of arbitrary size (see scTopBind) * Ignore specConstrCount, to make arbitrary numbers of specialisations @@ -513,22 +511,36 @@ sc_force to True when calling specLoop. This flag does four things: * Only specialise on recursive types a finite number of times (see is_too_recursive; Trac #5550; Note [Limit recursive specialisation]) -This flag is inherited for nested non-recursive bindings (which are likely to -be join points and hence should be fully specialised) but reset for nested -recursive bindings. - -What alternatives did I consider? Annotating the loop itself doesn't -work because (a) it is local and (b) it will be w/w'ed and having -w/w propagating annotations somehow doesn't seem like a good idea. The -types of the loop arguments really seem to be the most persistent -thing. - -Annotating the types that make up the loop state doesn't work, -either, because (a) it would prevent us from using types like Either -or tuples here, (b) we don't want to restrict the set of types that -can be used in Stream states and (c) some types are fixed by the user -(e.g., the accumulator here) but we still want to specialise as much -as possible. +The flag holds only for specialising a single binding group, and NOT +for nested bindings. (So really it should be passed around explicitly +and not stored in ScEnv.) Trac #14379 turned out to be caused by + f SPEC x = let g1 x = ... + in ... +We force-specialise f (becuase of the SPEC), but that generates a specialised +copy of g1 (as well as the original). Alas g1 has a nested binding g2; and +in each copy of g1 we get an unspecialised and specialised copy of g2; and so +on. Result, exponential. So the force-spec flag now only applies to one +level of bindings at a time. + +Mechanism for this one-level-only thing: + + - Switch it on at the call to specRec, in scExpr and scTopBinds + - Switch it off when doing the RHSs; + this can be done very conveneniently in decreaseSpecCount + +What alternatives did I consider? + +* Annotating the loop itself doesn't work because (a) it is local and + (b) it will be w/w'ed and having w/w propagating annotations somehow + doesn't seem like a good idea. The types of the loop arguments + really seem to be the most persistent thing. + +* Annotating the types that make up the loop state doesn't work, + either, because (a) it would prevent us from using types like Either + or tuples here, (b) we don't want to restrict the set of types that + can be used in Stream states and (c) some types are fixed by the + user (e.g., the accumulator here) but we still want to specialise as + much as possible. Alternatives to ForceSpecConstr ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -977,7 +989,8 @@ extendCaseBndrs env scrut case_bndr con alt_bndrs decreaseSpecCount :: ScEnv -> Int -> ScEnv -- See Note [Avoiding exponential blowup] decreaseSpecCount env n_specs - = env { sc_count = case sc_count env of + = env { sc_force = False -- See Note [Forcing specialisation] + , sc_count = case sc_count env of Nothing -> Nothing Just n -> Just (n `div` (n_specs + 1)) } -- The "+1" takes account of the original function; From git at git.haskell.org Fri Oct 27 13:33:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 13:33:07 +0000 (UTC) Subject: [commit: ghc] wip/T14152: simplNonRecJoinPoint: Handle Shadowing correctly (31b7d33) Message-ID: <20171027133307.44BBE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/31b7d33c898e81088e7a897f4e33eeb8da665a7e/ghc >--------------------------------------------------------------- commit 31b7d33c898e81088e7a897f4e33eeb8da665a7e Author: Joachim Breitner Date: Thu Oct 26 19:36:24 2017 -0400 simplNonRecJoinPoint: Handle Shadowing correctly Previously, (since 33452df), simplNonRecJoinPoint would do the wrong thing in the presence of shadowing: It analyzed the RHS of a join binding with the environment for the body. In particular, with foo x = join x = x * x in x where there is shadowing, it renames the inner x to x1, and should produce foo x = join x1 = x * x in x1 but because the substitution (x ↦ x1) is also used on the RHS we get the bogus foo x = join x1 = x1 * x1 in x1 The corresponding function for non-join-points, i.e. simplNonRecE, does the right thing and has done so forever, so I’ll skip creating a test case or a note for this. Differential Revision: https://phabricator.haskell.org/D4130 >--------------------------------------------------------------- 31b7d33c898e81088e7a897f4e33eeb8da665a7e compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 442 +++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 8 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 13 +- docs/users_guide/using-optimisation.rst | 10 + testsuite/tests/simplCore/should_compile/T14152.hs | 23 ++ .../tests/simplCore/should_compile/T14152.stderr | 129 ++++++ .../tests/simplCore/should_compile/T14152a.hs | 1 + .../tests/simplCore/should_compile/T14152a.stderr | 222 +++++++++++ testsuite/tests/simplCore/should_compile/all.T | 2 + 17 files changed, 870 insertions(+), 11 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 31b7d33c898e81088e7a897f4e33eeb8da665a7e From git at git.haskell.org Fri Oct 27 13:33:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 13:33:10 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (d871321) Message-ID: <20171027133310.12E6E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/d871321ce20eeaeb1eaa2d4481e8958b3fbbe8e0/ghc >--------------------------------------------------------------- commit d871321ce20eeaeb1eaa2d4481e8958b3fbbe8e0 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration because the extra jump is a bit pointless there. It still increases the number of instructions of `compress2` by 3.82%, so that needs to be investiaged. >--------------------------------------------------------------- d871321ce20eeaeb1eaa2d4481e8958b3fbbe8e0 compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 7 ++++++- compiler/simplCore/SimplCore.hs | 40 +++++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 41 insertions(+), 23 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 d871321ce20eeaeb1eaa2d4481e8958b3fbbe8e0 From git at git.haskell.org Fri Oct 27 13:33:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 13:33:12 +0000 (UTC) Subject: [commit: ghc] wip/T14152's head updated: Inline exit join points in the "final" simplifier iteration (d871321) Message-ID: <20171027133312.4D64F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14152' now includes: 160a491 users-guide: Disable index node generation 9ae24bb configure: Add Alpine Linux to checkVendor a10c2e6 Don't use $SHELL in wrapper scripts 355318c Add more pprTrace to SpecConstr (debug only) 7d7d94f Fix an exponential-blowup case in SpecConstr 31b7d33 simplNonRecJoinPoint: Handle Shadowing correctly d871321 Inline exit join points in the "final" simplifier iteration From git at git.haskell.org Fri Oct 27 13:48:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 13:48:48 +0000 (UTC) Subject: [commit: ghc] master: ApplicativeDo: handle BodyStmt (#12143) (41f9055) Message-ID: <20171027134848.CB8D33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41f905596dc2560f29657753e4c69ce695161786/ghc >--------------------------------------------------------------- commit 41f905596dc2560f29657753e4c69ce695161786 Author: Simon Marlow Date: Thu Oct 26 11:23:23 2017 +0100 ApplicativeDo: handle BodyStmt (#12143) Summary: It's simple to treat BodyStmt just like a BindStmt with a wildcard pattern, which is enough to fix #12143 without going all the way to using `<*` and `*>` (#10892). Test Plan: * new test cases in `ado004.hs` * validate Reviewers: niteria, simonpj, bgamari, austin, erikd Subscribers: rwbarton, thomie GHC Trac Issues: #12143 Differential Revision: https://phabricator.haskell.org/D4128 >--------------------------------------------------------------- 41f905596dc2560f29657753e4c69ce695161786 compiler/deSugar/Coverage.hs | 7 +++-- compiler/deSugar/DsExpr.hs | 2 +- compiler/hsSyn/HsExpr.hs | 57 +++++++++++++++++++++++++++++++++------ compiler/hsSyn/HsUtils.hs | 2 +- compiler/rename/RnExpr.hs | 11 ++++++-- compiler/typecheck/TcHsSyn.hs | 10 +++---- compiler/typecheck/TcMatches.hs | 6 ++--- testsuite/tests/ado/ado004.hs | 18 +++++++++++++ testsuite/tests/ado/ado004.stderr | 8 ++++++ 9 files changed, 99 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 41f905596dc2560f29657753e4c69ce695161786 From git at git.haskell.org Fri Oct 27 14:50:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 14:50:03 +0000 (UTC) Subject: [commit: ghc] branch 'wip/circleci' created Message-ID: <20171027145003.5E24B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/circleci Referencing: 46bd86edda505e249b31f13176bfdfa5a403cd8a From git at git.haskell.org Fri Oct 27 14:50:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 14:50:06 +0000 (UTC) Subject: [commit: ghc] wip/circleci: CircleCI: Enable documentation building (9fab3d9) Message-ID: <20171027145006.6613D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/circleci Link : http://ghc.haskell.org/trac/ghc/changeset/9fab3d9f1890b85d2dc30affb7d6e27838a0521d/ghc >--------------------------------------------------------------- commit 9fab3d9f1890b85d2dc30affb7d6e27838a0521d Author: Ben Gamari Date: Wed Oct 25 19:20:49 2017 -0400 CircleCI: Enable documentation building >--------------------------------------------------------------- 9fab3d9f1890b85d2dc30affb7d6e27838a0521d .circleci/config.yml | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 6ee6c48..24e02e8 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -10,7 +10,7 @@ jobs: name: git command: | apt-get update - apt-get install -y git openssh-client make automake autoconf gcc perl python3 + apt-get install -y git openssh-client make automake autoconf gcc perl python3 python-sphinx - checkout - run: name: submodules @@ -23,6 +23,4 @@ jobs: - run: name: build command: | - echo 'BUILD_SPHINX_HTML = NO' >> mk/validate.mk - echo 'BUILD_SPHINX_PDF = NO' >> mk/validate.mk THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --fast --quiet From git at git.haskell.org Fri Oct 27 14:50:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 14:50:09 +0000 (UTC) Subject: [commit: ghc] wip/circleci: CircleCI: Don't build PDF documentation (46bd86e) Message-ID: <20171027145009.2B2103A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/circleci Link : http://ghc.haskell.org/trac/ghc/changeset/46bd86edda505e249b31f13176bfdfa5a403cd8a/ghc >--------------------------------------------------------------- commit 46bd86edda505e249b31f13176bfdfa5a403cd8a Author: Ben Gamari Date: Thu Oct 26 11:57:39 2017 -0400 CircleCI: Don't build PDF documentation >--------------------------------------------------------------- 46bd86edda505e249b31f13176bfdfa5a403cd8a .circleci/config.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.circleci/config.yml b/.circleci/config.yml index 8449a76..d04973e 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -23,6 +23,7 @@ jobs: - run: name: build command: | + echo 'BUILD_SPHINX_PDF = NO' >> mk/validate.mk THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --quiet --build-only - run: name: test From git at git.haskell.org Fri Oct 27 14:50:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 14:50:11 +0000 (UTC) Subject: [commit: ghc] wip/circleci: CircleCI: Split up build and test steps (92ce1cf) Message-ID: <20171027145011.E0E503A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/circleci Link : http://ghc.haskell.org/trac/ghc/changeset/92ce1cf34bff41a53464da997a6fbec434839726/ghc >--------------------------------------------------------------- commit 92ce1cf34bff41a53464da997a6fbec434839726 Author: Ben Gamari Date: Wed Oct 25 19:21:02 2017 -0400 CircleCI: Split up build and test steps >--------------------------------------------------------------- 92ce1cf34bff41a53464da997a6fbec434839726 .circleci/config.yml | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 24e02e8..c3f76ca 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -23,4 +23,8 @@ jobs: - run: name: build command: | - THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --fast --quiet + THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --fast --quiet --build-only + - run: + name: test + command: | + THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --fast --quiet --testsuite-only From git at git.haskell.org Fri Oct 27 14:50:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 14:50:14 +0000 (UTC) Subject: [commit: ghc] wip/circleci: CircleCI: Perform full normal validation (1d0820a) Message-ID: <20171027145014.AAD5F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/circleci Link : http://ghc.haskell.org/trac/ghc/changeset/1d0820a8a1efbbf8fff417e3cc1b65e9718c0d32/ghc >--------------------------------------------------------------- commit 1d0820a8a1efbbf8fff417e3cc1b65e9718c0d32 Author: Ben Gamari Date: Thu Oct 26 11:54:56 2017 -0400 CircleCI: Perform full normal validation >--------------------------------------------------------------- 1d0820a8a1efbbf8fff417e3cc1b65e9718c0d32 .circleci/config.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 9ce13b4..8449a76 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -23,11 +23,11 @@ jobs: - run: name: build command: | - THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --fast --quiet --build-only + THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --quiet --build-only - run: name: test command: | - THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --fast --quiet --testsuite-only + THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --quiet --testsuite-only - run: name: build binary distribution command: | From git at git.haskell.org Fri Oct 27 14:50:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 14:50:17 +0000 (UTC) Subject: [commit: ghc] wip/circleci: CircleCI: Build and archive binary distribution (b41dbb1) Message-ID: <20171027145017.7180B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/circleci Link : http://ghc.haskell.org/trac/ghc/changeset/b41dbb11bd90bc287d0a925afdf20570eac5286f/ghc >--------------------------------------------------------------- commit b41dbb11bd90bc287d0a925afdf20570eac5286f Author: Ben Gamari Date: Wed Oct 25 20:02:15 2017 -0400 CircleCI: Build and archive binary distribution >--------------------------------------------------------------- b41dbb11bd90bc287d0a925afdf20570eac5286f .circleci/config.yml | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/.circleci/config.yml b/.circleci/config.yml index c3f76ca..9ce13b4 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -28,3 +28,14 @@ jobs: name: test command: | THREADS=8 SKIP_PERF_TESTS=YES VERBOSE=2 ./validate --fast --quiet --testsuite-only + - run: + name: build binary distribution + command: | + make binary-dist + - run: + name: build artifact directory + command: | + mkdir artifacts + cp ghc-*.tar.xz artifacts/ + - store_artifacts: + path: artifacts From git at git.haskell.org Fri Oct 27 15:24:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 15:24:31 +0000 (UTC) Subject: [commit: ghc] branch 'wip/float-join-points' created Message-ID: <20171027152431.780DF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/float-join-points Referencing: 128e4c1ffa29f3dfade7128152c143cd601aaa3a From git at git.haskell.org Fri Oct 27 15:24:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 15:24:34 +0000 (UTC) Subject: [commit: ghc] wip/float-join-points: Wip on floating join points (128e4c1) Message-ID: <20171027152434.5181F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/float-join-points Link : http://ghc.haskell.org/trac/ghc/changeset/128e4c1ffa29f3dfade7128152c143cd601aaa3a/ghc >--------------------------------------------------------------- commit 128e4c1ffa29f3dfade7128152c143cd601aaa3a Author: Simon Peyton Jones Date: Fri Oct 27 16:20:24 2017 +0100 Wip on floating join points >--------------------------------------------------------------- 128e4c1ffa29f3dfade7128152c143cd601aaa3a compiler/basicTypes/BasicTypes.hs | 5 +- compiler/basicTypes/Id.hs | 19 ++++++-- compiler/main/DynFlags.hs | 3 ++ compiler/simplCore/CoreMonad.hs | 17 +++---- compiler/simplCore/SetLevels.hs | 17 ++----- compiler/simplCore/SimplCore.hs | 54 +++++++++++----------- compiler/simplCore/SimplEnv.hs | 45 ++++++++++++++++-- compiler/simplCore/SimplUtils.hs | 87 ++++++++++++++++++----------------- compiler/simplCore/Simplify.hs | 96 +++++++++++++++++++++++++++++---------- compiler/types/Type.hs | 4 +- 10 files changed, 222 insertions(+), 125 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 128e4c1ffa29f3dfade7128152c143cd601aaa3a From git at git.haskell.org Fri Oct 27 18:02:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 18:02:42 +0000 (UTC) Subject: [commit: ghc] master: relnotes: Fix a few minor formatting issues (acd355a) Message-ID: <20171027180242.A67763A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/acd355a8fd40d0446c9f737e0f02d92fb5b7b935/ghc >--------------------------------------------------------------- commit acd355a8fd40d0446c9f737e0f02d92fb5b7b935 Author: Ben Gamari Date: Fri Oct 27 14:02:19 2017 -0400 relnotes: Fix a few minor formatting issues >--------------------------------------------------------------- acd355a8fd40d0446c9f737e0f02d92fb5b7b935 docs/users_guide/8.4.1-notes.rst | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/8.4.1-notes.rst b/docs/users_guide/8.4.1-notes.rst index b787e2e..4ed7028 100644 --- a/docs/users_guide/8.4.1-notes.rst +++ b/docs/users_guide/8.4.1-notes.rst @@ -163,10 +163,10 @@ Runtime system where module initialisation stopped requiring a call to ``hs_add_root()``. - Proper import library support added to GHC which can handle all of the libraries produced - by dlltool. The limitation of them needing to be named with the suffix .dll.a is also removed. + by ``dlltool``. The limitation of them needing to be named with the suffix .dll.a is also removed. See :ghc-ticket:`13606`, :ghc-ticket:`12499`, :ghc-ticket:`12498` -- The GHCi runtime linker on Windows now supports the `big-obj` file format. +- The GHCi runtime linker on Windows now supports the ``big-obj`` file format. - The runtime system's :ref:`native stack backtrace ` support on POSIX platforms is now triggered by ``SIGQUIT`` instead of ``SIGUSR2`` as From git at git.haskell.org Fri Oct 27 18:08:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 18:08:38 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Deal with JoinIds before void types (704cbae) Message-ID: <20171027180838.505853A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/704cbae29ee09431cfbd6b1566a6ec6856f125fc/ghc >--------------------------------------------------------------- commit 704cbae29ee09431cfbd6b1566a6ec6856f125fc Author: Simon Peyton Jones Date: Fri Mar 10 11:12:12 2017 +0000 Deal with JoinIds before void types Trac #13394, comment:4 showed up another place where we were testing for the representation of of a type; and it turned out to be a JoinId which can be rep-polymorphic. Just putting the test in the right places solves this easily. (cherry picked from commit bc0f3abd0914808e33f84229818ab90842611bdd) >--------------------------------------------------------------- 704cbae29ee09431cfbd6b1566a6ec6856f125fc compiler/codeGen/StgCmmExpr.hs | 7 ++++--- testsuite/tests/polykinds/{T13394.hs => T13394a.hs} | 2 +- testsuite/tests/polykinds/all.T | 1 + 3 files changed, 6 insertions(+), 4 deletions(-) diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index 395e8d6..39edd05 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -701,7 +701,6 @@ cgConApp con stg_args ; emitReturn [idInfoToAmode idinfo] } cgIdApp :: Id -> [StgArg] -> FCode ReturnKind -cgIdApp fun_id [] | isVoidTy (idType fun_id) = emitReturn [] cgIdApp fun_id args = do dflags <- getDynFlags fun_info <- getCgIdInfo fun_id @@ -719,9 +718,11 @@ cgIdApp fun_id args = do v_args = length $ filter (isVoidTy . stgArgType) args node_points dflags = nodeMustPointToIt dflags lf_info case getCallMethod dflags fun_name cg_fun_id lf_info n_args v_args (cg_loc fun_info) self_loop_info of - -- A value in WHNF, so we can just return it. - ReturnIt -> emitReturn [fun] -- ToDo: does ReturnIt guarantee tagged? + ReturnIt + | isVoidTy (idType fun_id) -> emitReturn [] + | otherwise -> emitReturn [fun] + -- ToDo: does ReturnIt guarantee tagged? EnterIt -> ASSERT( null args ) -- Discarding arguments emitEnter fun diff --git a/testsuite/tests/polykinds/T13394.hs b/testsuite/tests/polykinds/T13394a.hs similarity index 84% copy from testsuite/tests/polykinds/T13394.hs copy to testsuite/tests/polykinds/T13394a.hs index 88c482a..e79bf79 100644 --- a/testsuite/tests/polykinds/T13394.hs +++ b/testsuite/tests/polykinds/T13394a.hs @@ -12,4 +12,4 @@ newtype ProperName = newtype ModuleName = ModuleName [ProperName] pattern TypeDataSymbol :: ModuleName -pattern TypeDataSymbol = ModuleName [ProperName "Type"] +pattern TypeDataSymbol = ModuleName [ProperName "Type", ProperName "Data"] diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index f88f4a2..5e1678f 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -156,6 +156,7 @@ test('T12718', normal, compile, ['']) test('T12444', normal, compile_fail, ['']) test('T12885', normal, compile, ['']) test('T13267', normal, compile_fail, ['']) +test('T13394a', normal, compile, ['']) test('T13394', normal, compile, ['']) test('T13371', normal, compile, ['']) test('T13393', normal, compile_fail, ['']) From git at git.haskell.org Fri Oct 27 20:51:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 20:51:16 +0000 (UTC) Subject: [commit: ghc] wip/T14152: simplNonRecJoinPoint: Handle Shadowing correctly (4c5ffce) Message-ID: <20171027205116.73AAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/4c5ffce3d4e33ece607aa2148b60edc168378c38/ghc >--------------------------------------------------------------- commit 4c5ffce3d4e33ece607aa2148b60edc168378c38 Author: Joachim Breitner Date: Thu Oct 26 19:36:24 2017 -0400 simplNonRecJoinPoint: Handle Shadowing correctly Previously, (since 33452df), simplNonRecJoinPoint would do the wrong thing in the presence of shadowing: It analyzed the RHS of a join binding with the environment for the body. In particular, with foo x = join x = x * x in x where there is shadowing, it renames the inner x to x1, and should produce foo x = join x1 = x * x in x1 but because the substitution (x ↦ x1) is also used on the RHS we get the bogus foo x = join x1 = x1 * x1 in x1 The corresponding function for non-join-points, i.e. simplNonRecE, does the right thing and has done so forever, so I’ll skip creating a test case or a note for this. Differential Revision: https://phabricator.haskell.org/D4130 >--------------------------------------------------------------- 4c5ffce3d4e33ece607aa2148b60edc168378c38 compiler/simplCore/Simplify.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index d6b859a..3497e67 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -204,7 +204,7 @@ simplRecOrTopPair env top_lvl is_rec mb_cont old_bndr new_bndr rhs | Just cont <- mb_cont = ASSERT( isNotTopLevel top_lvl && isJoinId new_bndr ) trace_bind "join" $ - simplJoinBind env cont old_bndr new_bndr rhs + simplJoinBind env cont old_bndr new_bndr rhs env | otherwise = trace_bind "normal" $ @@ -300,10 +300,10 @@ simplJoinBind :: SimplEnv -> InId -> OutId -- Binder, both pre-and post simpl -- The OutId has IdInfo, except arity, -- unfolding - -> InExpr + -> InExpr -> SimplEnv -- The right hand side and its env -> SimplM (SimplFloats, SimplEnv) -simplJoinBind env cont old_bndr new_bndr rhs - = do { rhs' <- simplJoinRhs env old_bndr rhs cont +simplJoinBind env cont old_bndr new_bndr rhs rhs_se + = do { rhs' <- simplJoinRhs rhs_se old_bndr rhs cont ; completeBind env NotTopLevel (Just cont) old_bndr new_bndr rhs' } -------------------------- @@ -1471,7 +1471,7 @@ simplNonRecJoinPoint env bndr rhs body cont ; let res_ty = contResultType cont ; (env1, bndr1) <- simplNonRecJoinBndr env res_ty bndr ; (env2, bndr2) <- addBndrRules env1 bndr bndr1 - ; (floats1, env3) <- simplJoinBind env2 cont bndr bndr2 rhs + ; (floats1, env3) <- simplJoinBind env2 cont bndr bndr2 rhs env ; (floats2, body') <- simplExprF env3 body cont ; return (floats1 `addFloats` floats2, body') } From git at git.haskell.org Fri Oct 27 20:51:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 20:51:23 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (6204781) Message-ID: <20171027205123.6B6EE3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/6204781d1201215cb9c5b0619f7cf481a627ff75/ghc >--------------------------------------------------------------- commit 6204781d1201215cb9c5b0619f7cf481a627ff75 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration because the extra jump is a bit pointless there. It still increases the number of instructions of `compress2` by 3.82%, `fem` by 2.2% and so that needs to be investiaged. >--------------------------------------------------------------- 6204781d1201215cb9c5b0619f7cf481a627ff75 compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 7 ++++++- compiler/simplCore/SimplCore.hs | 40 +++++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 41 insertions(+), 23 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 6204781d1201215cb9c5b0619f7cf481a627ff75 From git at git.haskell.org Fri Oct 27 20:51:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 20:51:20 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (04e612c) Message-ID: <20171027205120.9A7FF3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/04e612ce45965a154b1a3d94bd39709585af97f5/ghc >--------------------------------------------------------------- commit 04e612ce45965a154b1a3d94bd39709585af97f5 Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 The idea is described in #14152, and can be summarized: Float the exit path out of a joinrec, so that the simplifier can do more with it. See the test case for a nice example. The floating goes against what the simplifier usually does, hence we need to be careful not inline them back. The position of exitification in the pipeline was chosen after a small amount of experimentation, but may need to be improved. For example, exitification can allow rewrite rules to fire, but for that it would have to happen before the `simpl_phases`. Together with the next patch, perf.haskell.org reports these nice performance wins: Nofib allocations prev change gain fannkuch-redux 78446688 - 99.92% 64608 k-nucleotide 109466432 - 91.32% 9502064 simple 72424696 - 5.96% 68109560 Nofib instruction counts compress2 573354476 + 3.34% 592476104 k-nucleotide 2310080537 - 5.59% 2180917263 scs 1979135192 - 3.2% 1915880589 simple 670348375 - 4.9% 637507288 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- 04e612ce45965a154b1a3d94bd39709585af97f5 compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 442 +++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 8 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + testsuite/tests/simplCore/should_compile/T14152.hs | 23 ++ .../tests/simplCore/should_compile/T14152.stderr | 129 ++++++ .../tests/simplCore/should_compile/T14152a.hs | 1 + .../tests/simplCore/should_compile/T14152a.stderr | 222 +++++++++++ testsuite/tests/simplCore/should_compile/all.T | 2 + 17 files changed, 865 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 04e612ce45965a154b1a3d94bd39709585af97f5 From git at git.haskell.org Fri Oct 27 22:03:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Oct 2017 22:03:25 +0000 (UTC) Subject: [commit: ghc] master: Make tagForCon non-linear (faf60e8) Message-ID: <20171027220325.2898F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/faf60e858a293affca463043c830e1edb5685003/ghc >--------------------------------------------------------------- commit faf60e858a293affca463043c830e1edb5685003 Author: Bartosz Nitka Date: Fri Oct 20 20:30:52 2017 +0100 Make tagForCon non-linear Computing the number of constructors for TyCon is linear in the number of constructors. That's wasteful if all you want to check is if that number is smaller than what fits in tag bits (usually 8 things). What this change does is to use a function that can determine the ineqaulity without computing the size. This improves compile time on a module with a data type that has 10k constructors. The variance in total time is (suspiciously) high, but going by the best of 3 the numbers are 8.186s vs 7.511s. For 1000 constructors the difference isn't noticeable: 0.646s vs 0.624s. The hot spots were cgDataCon and cgEnumerationTyCon where tagForCon is called in a loop. One alternative would be to pass down the size. Test Plan: harbormaster Reviewers: bgamari, simonmar, austin Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4116 >--------------------------------------------------------------- faf60e858a293affca463043c830e1edb5685003 compiler/codeGen/StgCmmClosure.hs | 11 ++++++++--- compiler/types/TyCon.hs | 16 +++++++++++++++- 2 files changed, 23 insertions(+), 4 deletions(-) diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs index 1da1f70..2501ec9 100644 --- a/compiler/codeGen/StgCmmClosure.hs +++ b/compiler/codeGen/StgCmmClosure.hs @@ -361,13 +361,18 @@ type DynTag = Int -- The tag on a *pointer* isSmallFamily :: DynFlags -> Int -> Bool isSmallFamily dflags fam_size = fam_size <= mAX_PTR_TAG dflags +-- | Faster version of isSmallFamily if you haven't computed the size yet. +isSmallFamilyTyCon :: DynFlags -> TyCon -> Bool +isSmallFamilyTyCon dflags tycon = + tyConFamilySizeAtMost tycon (mAX_PTR_TAG dflags) + tagForCon :: DynFlags -> DataCon -> DynTag tagForCon dflags con - | isSmallFamily dflags fam_size = con_tag - | otherwise = 1 + | isSmallFamilyTyCon dflags tycon = con_tag + | otherwise = 1 where con_tag = dataConTag con -- NB: 1-indexed - fam_size = tyConFamilySize (dataConTyCon con) + tycon = dataConTyCon con tagForArity :: DynFlags -> RepArity -> DynTag tagForArity dflags arity diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 39d2e9b..103c824 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -78,7 +78,7 @@ module TyCon( tyConDataCons, tyConDataCons_maybe, tyConSingleDataCon_maybe, tyConSingleDataCon, tyConSingleAlgDataCon_maybe, - tyConFamilySize, + tyConFamilySize, tyConFamilySizeAtMost, tyConStupidTheta, tyConArity, tyConRoles, @@ -2205,6 +2205,20 @@ tyConFamilySize tc@(AlgTyCon { algTcRhs = rhs }) _ -> pprPanic "tyConFamilySize 1" (ppr tc) tyConFamilySize tc = pprPanic "tyConFamilySize 2" (ppr tc) +-- | Determine if number of value constructors a 'TyCon' has is smaller +-- than n. Faster than tyConFamilySize tc <= n. +-- Panics if the 'TyCon' is not algebraic or a tuple +tyConFamilySizeAtMost :: TyCon -> Int -> Bool +tyConFamilySizeAtMost tc@(AlgTyCon { algTcRhs = rhs }) n + = case rhs of + DataTyCon { data_cons = cons } -> lengthAtMost cons n + NewTyCon {} -> 1 <= n + TupleTyCon {} -> 1 <= n + SumTyCon { data_cons = cons } -> lengthAtMost cons n + _ -> pprPanic "tyConFamilySizeAtMost 1" + (ppr tc) +tyConFamilySizeAtMost tc _ = pprPanic "tyConFamilySizeAtMost 2" (ppr tc) + -- | Extract an 'AlgTyConRhs' with information about data constructors from an -- algebraic or tuple 'TyCon'. Panics for any other sort of 'TyCon' algTyConRhs :: TyCon -> AlgTyConRhs From git at git.haskell.org Sat Oct 28 21:36:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Oct 2017 21:36:03 +0000 (UTC) Subject: [commit: ghc] master: Manual: The -ddump-cmm-* flags had a wrong spelling in the manual (922db3d) Message-ID: <20171028213603.9493B3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/922db3dac896b8cf364c9ebaebf1a27c2468c709/ghc >--------------------------------------------------------------- commit 922db3dac896b8cf364c9ebaebf1a27c2468c709 Author: Joachim Breitner Date: Sat Oct 28 17:35:31 2017 -0400 Manual: The -ddump-cmm-* flags had a wrong spelling in the manual >--------------------------------------------------------------- 922db3dac896b8cf364c9ebaebf1a27c2468c709 docs/users_guide/debugging.rst | 32 ++++++++++++++++++++++---------- 1 file changed, 22 insertions(+), 10 deletions(-) diff --git a/docs/users_guide/debugging.rst b/docs/users_guide/debugging.rst index 0096c71..4dbec3e 100644 --- a/docs/users_guide/debugging.rst +++ b/docs/users_guide/debugging.rst @@ -366,66 +366,78 @@ These flags dump various phases of GHC's C-- pipeline. Dump the result of STG-to-C-- conversion -.. ghc-flag:: -ddump-opt-cmm-cfg +.. ghc-flag:: -ddump-cmm-raw + :shortdesc: Dump raw C-- + :type: dynamic + + Dump the “raw” C--. + +.. ghc-flag:: -ddump-cmm-cfg :shortdesc: Dump the results of the C-- control flow optimisation pass. :type: dynamic Dump the results of the C-- control flow optimisation pass. -.. ghc-flag:: -ddump-opt-cmm-cbe +.. ghc-flag:: -ddump-cmm-cbe :shortdesc: Dump the results of common block elimination :type: dynamic Dump the results of the C-- Common Block Elimination (CBE) pass. -.. ghc-flag:: -ddump-opt-cmm-switch +.. ghc-flag:: -ddump-cmm-switch :shortdesc: Dump the results of switch lowering passes :type: dynamic Dump the results of the C-- switch lowering pass. -.. ghc-flag:: -ddump-opt-cmm-proc +.. ghc-flag:: -ddump-cmm-proc :shortdesc: Dump the results of proc-point analysis :type: dynamic Dump the results of the C-- proc-point analysis pass. -.. ghc-flag:: -ddump-opt-cmm-sp +.. ghc-flag:: -ddump-cmm-sp :shortdesc: Dump the results of the C-- stack layout pass. :type: dynamic Dump the results of the C-- stack layout pass. -.. ghc-flag:: -ddump-opt-cmm-sink +.. ghc-flag:: -ddump-cmm-sink :shortdesc: Dump the results of the C-- sinking pass. :type: dynamic Dump the results of the C-- sinking pass. -.. ghc-flag:: -ddump-opt-cmm-caf +.. ghc-flag:: -ddump-cmm-caf :shortdesc: Dump the results of the C-- CAF analysis pass. :type: dynamic Dump the results of the C-- CAF analysis pass. -.. ghc-flag:: -ddump-opt-cmm-procmap +.. ghc-flag:: -ddump-cmm-procmap :shortdesc: Dump the results of the C-- proc-point map pass. :type: dynamic Dump the results of the C-- proc-point map pass. -.. ghc-flag:: -ddump-opt-cmm-split +.. ghc-flag:: -ddump-cmm-split :shortdesc: Dump the results of the C-- proc-point splitting pass. :type: dynamic Dump the results of the C-- proc-point splitting pass. -.. ghc-flag:: -ddump-opt-cmm-info +.. ghc-flag:: -ddump-cmm-info :shortdesc: Dump the results of the C-- info table augmentation pass. :type: dynamic Dump the results of the C-- info table augmentation pass. +.. ghc-flag:: -ddump-cmm-cps + :shortdesc: Dump the results of the CPS pass + :type: dynamic + + Dump the results of the CPS pass. + .. ghc-flag:: -ddump-cmm :shortdesc: Dump the final C-- output :type: dynamic From git at git.haskell.org Sun Oct 29 04:08:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 29 Oct 2017 04:08:20 +0000 (UTC) Subject: [commit: ghc] wip/T14152: simplNonRecJoinPoint: Handle Shadowing correctly (97ca0d2) Message-ID: <20171029040820.C49B03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/97ca0d249c380a961a4cb90afb44bfcee1f632f2/ghc >--------------------------------------------------------------- commit 97ca0d249c380a961a4cb90afb44bfcee1f632f2 Author: Joachim Breitner Date: Thu Oct 26 19:36:24 2017 -0400 simplNonRecJoinPoint: Handle Shadowing correctly Previously, (since 33452df), simplNonRecJoinPoint would do the wrong thing in the presence of shadowing: It analyzed the RHS of a join binding with the environment for the body. In particular, with foo x = join x = x * x in x where there is shadowing, it renames the inner x to x1, and should produce foo x = join x1 = x * x in x1 but because the substitution (x ↦ x1) is also used on the RHS we get the bogus foo x = join x1 = x1 * x1 in x1 Fixed this by adding a `rhs_se` parameter, analogous to `simplNonRecE` and `simplLazyBind`. Differential Revision: https://phabricator.haskell.org/D4130 >--------------------------------------------------------------- 97ca0d249c380a961a4cb90afb44bfcee1f632f2 compiler/simplCore/Simplify.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index d6b859a..adcd017 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -204,7 +204,7 @@ simplRecOrTopPair env top_lvl is_rec mb_cont old_bndr new_bndr rhs | Just cont <- mb_cont = ASSERT( isNotTopLevel top_lvl && isJoinId new_bndr ) trace_bind "join" $ - simplJoinBind env cont old_bndr new_bndr rhs + simplJoinBind env cont old_bndr new_bndr rhs env | otherwise = trace_bind "normal" $ @@ -300,10 +300,11 @@ simplJoinBind :: SimplEnv -> InId -> OutId -- Binder, both pre-and post simpl -- The OutId has IdInfo, except arity, -- unfolding - -> InExpr + -> InExpr -> SimplEnv -- The right hand side and its env -> SimplM (SimplFloats, SimplEnv) -simplJoinBind env cont old_bndr new_bndr rhs - = do { rhs' <- simplJoinRhs env old_bndr rhs cont +simplJoinBind env cont old_bndr new_bndr rhs rhs_se + = do { let rhs_env = rhs_se `setInScopeFromE` env + ; rhs' <- simplJoinRhs rhs_env old_bndr rhs cont ; completeBind env NotTopLevel (Just cont) old_bndr new_bndr rhs' } -------------------------- @@ -1471,7 +1472,7 @@ simplNonRecJoinPoint env bndr rhs body cont ; let res_ty = contResultType cont ; (env1, bndr1) <- simplNonRecJoinBndr env res_ty bndr ; (env2, bndr2) <- addBndrRules env1 bndr bndr1 - ; (floats1, env3) <- simplJoinBind env2 cont bndr bndr2 rhs + ; (floats1, env3) <- simplJoinBind env2 cont bndr bndr2 rhs env ; (floats2, body') <- simplExprF env3 body cont ; return (floats1 `addFloats` floats2, body') } From git at git.haskell.org Sun Oct 29 04:08:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 29 Oct 2017 04:08:30 +0000 (UTC) Subject: [commit: ghc] wip/T14152's head updated: Inline exit join points in the "final" simplifier iteration (7ba1b5b) Message-ID: <20171029040830.0639A3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14152' now includes: 41f9055 ApplicativeDo: handle BodyStmt (#12143) acd355a relnotes: Fix a few minor formatting issues faf60e8 Make tagForCon non-linear 922db3d Manual: The -ddump-cmm-* flags had a wrong spelling in the manual 97ca0d2 simplNonRecJoinPoint: Handle Shadowing correctly 0e953da Implement a dedicated exitfication pass #14152 7ba1b5b Inline exit join points in the "final" simplifier iteration From git at git.haskell.org Sun Oct 29 04:08:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 29 Oct 2017 04:08:24 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Implement a dedicated exitfication pass #14152 (0e953da) Message-ID: <20171029040824.EC0083A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/0e953da147c405648356f75ee67eda044fffad49/ghc >--------------------------------------------------------------- commit 0e953da147c405648356f75ee67eda044fffad49 Author: Joachim Breitner Date: Sat Aug 26 14:35:50 2017 +0200 Implement a dedicated exitfication pass #14152 The idea is described in #14152, and can be summarized: Float the exit path out of a joinrec, so that the simplifier can do more with it. See the test case for a nice example. The floating goes against what the simplifier usually does, hence we need to be careful not inline them back. The position of exitification in the pipeline was chosen after a small amount of experimentation, but may need to be improved. For example, exitification can allow rewrite rules to fire, but for that it would have to happen before the `simpl_phases`. Perf.haskell.org reports these nice performance wins: Nofib allocations fannkuch-redux 78446640 - 99.92% 64560 k-nucleotide 109466384 - 91.32% 9502040 simple 72424696 - 5.96% 68109560 Nofib instruction counts fannkuch-redux 1744331636 - 3.86% 1676999519 k-nucleotide 2318221965 - 6.30% 2172067260 scs 1978470869 - 3.35% 1912263779 simple 669858104 - 3.38% 647206739 spectral-norm 186423292 - 5.37% 176411536 Differential Revision: https://phabricator.haskell.org/D3903 >--------------------------------------------------------------- 0e953da147c405648356f75ee67eda044fffad49 compiler/basicTypes/Id.hs | 6 +- compiler/basicTypes/Unique.hs | 4 + compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 10 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 6 + compiler/simplCore/CoreMonad.hs | 2 + compiler/simplCore/Exitify.hs | 442 +++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 8 + compiler/simplCore/SimplUtils.hs | 1 + compiler/simplCore/Simplify.hs | 3 + docs/users_guide/using-optimisation.rst | 10 + testsuite/tests/simplCore/should_compile/T14152.hs | 23 ++ .../tests/simplCore/should_compile/T14152.stderr | 129 ++++++ .../tests/simplCore/should_compile/T14152a.hs | 1 + .../tests/simplCore/should_compile/T14152a.stderr | 222 +++++++++++ testsuite/tests/simplCore/should_compile/all.T | 2 + 17 files changed, 865 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0e953da147c405648356f75ee67eda044fffad49 From git at git.haskell.org Sun Oct 29 04:08:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 29 Oct 2017 04:08:27 +0000 (UTC) Subject: [commit: ghc] wip/T14152: Inline exit join points in the "final" simplifier iteration (7ba1b5b) Message-ID: <20171029040827.BC8673A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14152 Link : http://ghc.haskell.org/trac/ghc/changeset/7ba1b5b3af6b0264dbee36e85357d8cab079d1a2/ghc >--------------------------------------------------------------- commit 7ba1b5b3af6b0264dbee36e85357d8cab079d1a2 Author: Joachim Breitner Date: Fri Sep 1 15:02:34 2017 +0100 Inline exit join points in the "final" simplifier iteration because the extra jump is a bit pointless there. It still increases the number of instructions of `compress2` by 3.82%, `fem` by 2.2% and so that needs to be investiaged. >--------------------------------------------------------------- 7ba1b5b3af6b0264dbee36e85357d8cab079d1a2 compiler/simplCore/CoreMonad.hs | 7 +++++-- compiler/simplCore/Exitify.hs | 7 ++++++- compiler/simplCore/SimplCore.hs | 40 +++++++++++++++++++++++----------------- compiler/simplCore/SimplUtils.hs | 7 +++++-- compiler/simplCore/Simplify.hs | 3 ++- 5 files changed, 41 insertions(+), 23 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 7ba1b5b3af6b0264dbee36e85357d8cab079d1a2 From git at git.haskell.org Sun Oct 29 22:36:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 29 Oct 2017 22:36:14 +0000 (UTC) Subject: [commit: ghc] master's head updated: Implement a dedicated exitfication pass #14152 (0e953da) Message-ID: <20171029223614.C35683A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 97ca0d2 simplNonRecJoinPoint: Handle Shadowing correctly 0e953da Implement a dedicated exitfication pass #14152 From git at git.haskell.org Mon Oct 30 01:51:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 01:51:23 +0000 (UTC) Subject: [commit: ghc] master: base: Implement file locking in terms of POSIX locks (3b784d4) Message-ID: <20171030015123.D68013A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3b784d440d4b01b4c549df7c9a3ed2058edfc780/ghc >--------------------------------------------------------------- commit 3b784d440d4b01b4c549df7c9a3ed2058edfc780 Author: Ben Gamari Date: Sun Oct 29 20:46:21 2017 -0400 base: Implement file locking in terms of POSIX locks Hopefully these are more robust to NFS malfunction than BSD flock-style locks. See #13945. Test Plan: Validate via @simonpj Reviewers: austin, hvr Subscribers: rwbarton, thomie, erikd, simonpj GHC Trac Issues: #13945 Differential Revision: https://phabricator.haskell.org/D4129 >--------------------------------------------------------------- 3b784d440d4b01b4c549df7c9a3ed2058edfc780 libraries/base/GHC/IO/Handle/Lock.hsc | 74 ++++++++++++++++++++++++++++++++++- libraries/base/configure.ac | 7 +++- 2 files changed, 78 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/IO/Handle/Lock.hsc b/libraries/base/GHC/IO/Handle/Lock.hsc index daf407c..b0a3449 100644 --- a/libraries/base/GHC/IO/Handle/Lock.hsc +++ b/libraries/base/GHC/IO/Handle/Lock.hsc @@ -104,7 +104,76 @@ hUnlock = unlockImpl ---------------------------------------- -#if HAVE_FLOCK +#if HAVE_OFD_LOCKING +-- Linux open file descriptor locking. +-- +-- We prefer this over BSD locking (e.g. flock) since the latter appears to +-- break in some NFS configurations. Note that we intentionally do not try to +-- use ordinary POSIX file locking due to its peculiar semantics under +-- multi-threaded environments. + +foreign import ccall interruptible "fcntl" + c_fcntl :: CInt -> CInt -> Ptr () -> IO CInt + +data FLock = FLock { l_type :: CShort + , l_whence :: CShort + , l_start :: COff + , l_len :: COff + , l_pid :: CPid + } + +instance Storable FLock where + sizeOf _ = #{size flock} + alignment _ = #{alignment flock} + poke ptr x = do + fillBytes ptr 0 (sizeOf x) + #{poke flock, l_type} ptr (l_type x) + #{poke flock, l_whence} ptr (l_whence x) + #{poke flock, l_start} ptr (l_start x) + #{poke flock, l_len} ptr (l_len x) + #{poke flock, l_pid} ptr (l_pid x) + peek ptr = do + FLock <$> #{peek flock, l_type} ptr + <*> #{peek flock, l_whence} ptr + <*> #{peek flock, l_start} ptr + <*> #{peek flock, l_len} ptr + <*> #{peek flock, l_pid} ptr + +lockImpl :: Handle -> String -> LockMode -> Bool -> IO Bool +lockImpl h ctx mode block = do + FD{fdFD = fd} <- handleToFd h + with flock $ \flock_ptr -> fix $ \retry -> do + ret <- with flock $ fcntl fd mode flock_ptr + case ret of + 0 -> return True + _ -> getErrno >>= \errno -> if + | not block && errno == eWOULDBLOCK -> return False + | errno == eINTR -> retry + | otherwise -> ioException $ errnoToIOError ctx errno (Just h) Nothing + where + flock = FLock { l_type = case mode of + SharedLock -> #{const F_RDLCK} + ExclusiveLock -> #{const F_WRLCK} + , l_whence = #{const SEEK_SET} + , l_start = 0 + , l_len = 0 + } + mode + | block = #{const F_SETLKW} + | otherwise = #{const F_SETLK} + +unlockImpl :: Handle -> IO () +unlockImpl h = do + FD{fdFD = fd} <- handleToFd h + let flock = FLock { l_type = #{const F_UNLCK} + , l_whence = #{const SEEK_SET} + , l_start = 0 + , l_len = 0 + } + throwErrnoIfMinus1_ "hUnlock" + $ with flock $ c_fcntl fd #{const F_SETLK} + +#elif HAVE_FLOCK lockImpl :: Handle -> String -> LockMode -> Bool -> IO Bool lockImpl h ctx mode block = do @@ -113,7 +182,8 @@ lockImpl h ctx mode block = do fix $ \retry -> c_flock fd flags >>= \case 0 -> return True _ -> getErrno >>= \errno -> if - | not block && errno == eWOULDBLOCK -> return False + | not block + , errno == eAGAIN || errno == eACCES -> return False | errno == eINTR -> retry | otherwise -> ioException $ errnoToIOError ctx errno (Just h) Nothing where diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index af041a7..69ea800 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -69,7 +69,12 @@ if test "$ac_cv_header_poll_h" = yes && test "$ac_cv_func_poll" = yes; then AC_DEFINE([HAVE_POLL], [1], [Define if you have poll support.]) fi -#flock +# Linux open file description locks +AC_CHECK_DECL([F_OFD_SETLK], [ + AC_DEFINE([HAVE_OFD_LOCKING], [1], [Define if you have open file descriptor lock support.]) +]) + +# flock AC_CHECK_FUNCS([flock]) if test "$ac_cv_header_sys_file_h" = yes && test "$ac_cv_func_flock" = yes; then AC_DEFINE([HAVE_FLOCK], [1], [Define if you have flock support.]) From git at git.haskell.org Mon Oct 30 01:51:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 01:51:26 +0000 (UTC) Subject: [commit: ghc] master: Add -falignment-sanitization flag (cecd2f2) Message-ID: <20171030015126.AE2B83A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cecd2f2d708d419878205ddd8b87bba18e6483d9/ghc >--------------------------------------------------------------- commit cecd2f2d708d419878205ddd8b87bba18e6483d9 Author: Ben Gamari Date: Sun Oct 29 20:46:45 2017 -0400 Add -falignment-sanitization flag Here we add a flag to instruct the native code generator to add alignment checks in all info table dereferences. This is helpful in catching pointer tagging issues. Thanks to @jrtc27 for uncovering the tagging issues on Sparc which inspired this flag. Test Plan: Validate Reviewers: simonmar, austin, erikd Reviewed By: simonmar Subscribers: rwbarton, trofi, thomie, jrtc27 Differential Revision: https://phabricator.haskell.org/D4101 >--------------------------------------------------------------- cecd2f2d708d419878205ddd8b87bba18e6483d9 compiler/cmm/CLabel.hs | 4 +++- compiler/cmm/CmmInfo.hs | 12 +++++++++++- compiler/cmm/CmmMachOp.hs | 9 ++++++++- compiler/cmm/PprC.hs | 2 ++ compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 4 ++++ compiler/main/DynFlags.hs | 2 ++ compiler/nativeGen/X86/CodeGen.hs | 18 ++++++++++++++++++ docs/users_guide/debugging.rst | 7 +++++++ rts/RtsMessages.c | 10 ++++++++++ rts/RtsSymbols.c | 1 + rts/StgStartup.cmm | 6 ++++++ 11 files changed, 72 insertions(+), 3 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cecd2f2d708d419878205ddd8b87bba18e6483d9 From git at git.haskell.org Mon Oct 30 01:51:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 01:51:29 +0000 (UTC) Subject: [commit: ghc] master: Turn `compareByteArrays#` out-of-line primop into inline primop (7673561) Message-ID: <20171030015129.7FCC63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7673561555ae354fd9eed8de1e57c681906e2d49/ghc >--------------------------------------------------------------- commit 7673561555ae354fd9eed8de1e57c681906e2d49 Author: alexbiehl Date: Sun Oct 29 20:47:26 2017 -0400 Turn `compareByteArrays#` out-of-line primop into inline primop Depends on D4090 Reviewers: austin, bgamari, erikd, simonmar, alexbiehl Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4091 >--------------------------------------------------------------- 7673561555ae354fd9eed8de1e57c681906e2d49 compiler/cmm/CmmMachOp.hs | 3 +++ compiler/cmm/CmmParse.y | 1 + compiler/cmm/PprC.hs | 1 + compiler/codeGen/StgCmmPrim.hs | 41 ++++++++++++++++++++++++++++++++- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 1 + compiler/nativeGen/PPC/CodeGen.hs | 1 + compiler/nativeGen/SPARC/CodeGen.hs | 1 + compiler/nativeGen/X86/CodeGen.hs | 1 + compiler/prelude/primops.txt.pp | 1 - 9 files changed, 49 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/CmmMachOp.hs b/compiler/cmm/CmmMachOp.hs index fba57be..fdbfd6e 100644 --- a/compiler/cmm/CmmMachOp.hs +++ b/compiler/cmm/CmmMachOp.hs @@ -584,6 +584,7 @@ data CallishMachOp | MO_Memcpy Int | MO_Memset Int | MO_Memmove Int + | MO_Memcmp Int | MO_PopCnt Width | MO_Clz Width @@ -616,6 +617,7 @@ callishMachOpHints op = case op of MO_Memcpy _ -> ([], [AddrHint,AddrHint,NoHint]) MO_Memset _ -> ([], [AddrHint,NoHint,NoHint]) MO_Memmove _ -> ([], [AddrHint,AddrHint,NoHint]) + MO_Memcmp _ -> ([], [AddrHint, AddrHint, NoHint]) _ -> ([],[]) -- empty lists indicate NoHint @@ -625,4 +627,5 @@ machOpMemcpyishAlign op = case op of MO_Memcpy align -> Just align MO_Memset align -> Just align MO_Memmove align -> Just align + MO_Memcmp align -> Just align _ -> Nothing diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 96019d2..7ffb4fb 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -994,6 +994,7 @@ callishMachOps = listToUFM $ ( "memcpy", memcpyLikeTweakArgs MO_Memcpy ), ( "memset", memcpyLikeTweakArgs MO_Memset ), ( "memmove", memcpyLikeTweakArgs MO_Memmove ), + ( "memcmp", memcpyLikeTweakArgs MO_Memcmp ), ("prefetch0", (,) $ MO_Prefetch_Data 0), ("prefetch1", (,) $ MO_Prefetch_Data 1), diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs index 0fcadc2..1ddd1cd 100644 --- a/compiler/cmm/PprC.hs +++ b/compiler/cmm/PprC.hs @@ -786,6 +786,7 @@ pprCallishMachOp_for_C mop MO_Memcpy _ -> text "memcpy" MO_Memset _ -> text "memset" MO_Memmove _ -> text "memmove" + MO_Memcmp _ -> text "memcmp" (MO_BSwap w) -> ptext (sLit $ bSwapLabel w) (MO_PopCnt w) -> ptext (sLit $ popCntLabel w) (MO_Clz w) -> ptext (sLit $ clzLabel w) diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index c17855e..da652bf 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -47,7 +47,7 @@ import Outputable import Util import Data.Bits ((.&.), bit) -import Control.Monad (liftM, when) +import Control.Monad (liftM, when, unless) ------------------------------------------------------------------------ -- Primitive operations and foreign calls @@ -568,6 +568,10 @@ emitPrimOp _ [] CopyAddrToByteArrayOp [src,dst,dst_off,n] = emitPrimOp _ [] SetByteArrayOp [ba,off,len,c] = doSetByteArrayOp ba off len c +-- Comparing byte arrays +emitPrimOp _ [res] CompareByteArraysOp [ba1,ba1_off,ba2,ba2_off,n] = + doCompareByteArraysOp res ba1 ba1_off ba2 ba2_off n + emitPrimOp _ [res] BSwap16Op [w] = emitBSwapCall res w W16 emitPrimOp _ [res] BSwap32Op [w] = emitBSwapCall res w W32 emitPrimOp _ [res] BSwap64Op [w] = emitBSwapCall res w W64 @@ -1720,6 +1724,17 @@ doNewByteArrayOp res_r n = do emit $ mkAssign (CmmLocal res_r) base -- ---------------------------------------------------------------------------- +-- Comparing byte arrays + +doCompareByteArraysOp :: LocalReg -> CmmExpr -> CmmExpr -> CmmExpr -> CmmExpr -> CmmExpr + -> FCode () +doCompareByteArraysOp res ba1 ba1_off ba2 ba2_off n = do + dflags <- getDynFlags + ba1_p <- assignTempE $ cmmOffsetExpr dflags (cmmOffsetB dflags ba1 (arrWordsHdrSize dflags)) ba1_off + ba2_p <- assignTempE $ cmmOffsetExpr dflags (cmmOffsetB dflags ba2 (arrWordsHdrSize dflags)) ba2_off + emitMemcmpCall res ba1_p ba2_p n 1 + +-- ---------------------------------------------------------------------------- -- Copying byte arrays -- | Takes a source 'ByteArray#', an offset in the source array, a @@ -2213,6 +2228,30 @@ emitMemsetCall dst c n align = do (MO_Memset align) [ dst, c, n ] +emitMemcmpCall :: LocalReg -> CmmExpr -> CmmExpr -> CmmExpr -> Int -> FCode () +emitMemcmpCall res ptr1 ptr2 n align = do + -- 'MO_Memcmp' is assumed to return an 32bit 'CInt' because all + -- code-gens currently call out to the @memcmp(3)@ C function. + -- This was easier than moving the sign-extensions into + -- all the code-gens. + dflags <- getDynFlags + let is32Bit = typeWidth (localRegType res) == W32 + + cres <- if is32Bit + then return res + else newTemp b32 + + emitPrimCall + [ cres ] + (MO_Memcmp align) + [ ptr1, ptr2, n ] + + unless is32Bit $ do + emit $ mkAssign (CmmLocal res) + (CmmMachOp + (mo_s_32ToWord dflags) + [(CmmReg (CmmLocal cres))]) + emitBSwapCall :: LocalReg -> CmmExpr -> Width -> FCode () emitBSwapCall res x width = do emitPrimCall diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 300ebb9..a88642b 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -728,6 +728,7 @@ cmmPrimOpFunctions mop = do MO_Memcpy _ -> fsLit $ "llvm.memcpy." ++ intrinTy1 MO_Memmove _ -> fsLit $ "llvm.memmove." ++ intrinTy1 MO_Memset _ -> fsLit $ "llvm.memset." ++ intrinTy2 + MO_Memcmp _ -> fsLit $ "memcmp" (MO_PopCnt w) -> fsLit $ "llvm.ctpop." ++ showSDoc dflags (ppr $ widthToLlvmInt w) (MO_BSwap w) -> fsLit $ "llvm.bswap." ++ showSDoc dflags (ppr $ widthToLlvmInt w) diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index d897038..b5f1a62 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -1905,6 +1905,7 @@ genCCall' dflags gcp target dest_regs args MO_Memcpy _ -> (fsLit "memcpy", False) MO_Memset _ -> (fsLit "memset", False) MO_Memmove _ -> (fsLit "memmove", False) + MO_Memcmp _ -> (fsLit "memcmp", False) MO_BSwap w -> (fsLit $ bSwapLabel w, False) MO_PopCnt w -> (fsLit $ popCntLabel w, False) diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index 04ac757..55c1d15 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -650,6 +650,7 @@ outOfLineMachOp_table mop MO_Memcpy _ -> fsLit "memcpy" MO_Memset _ -> fsLit "memset" MO_Memmove _ -> fsLit "memmove" + MO_Memcmp _ -> fsLit "memcmp" MO_BSwap w -> fsLit $ bSwapLabel w MO_PopCnt w -> fsLit $ popCntLabel w diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index d6ef6d3..6c0e0ac 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -2682,6 +2682,7 @@ outOfLineCmmOp mop res args MO_Memcpy _ -> fsLit "memcpy" MO_Memset _ -> fsLit "memset" MO_Memmove _ -> fsLit "memmove" + MO_Memcmp _ -> fsLit "memcmp" MO_PopCnt _ -> fsLit "popcnt" MO_BSwap _ -> fsLit "bswap" diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index c29e296..ce72036 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -1410,7 +1410,6 @@ primop CompareByteArraysOp "compareByteArrays#" GenPrimOp respectively, to be byte-wise lexicographically less than, to match, or be greater than the second range.} with - out_of_line = True can_fail = True primop CopyByteArrayOp "copyByteArray#" GenPrimOp From git at git.haskell.org Mon Oct 30 01:51:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 01:51:33 +0000 (UTC) Subject: [commit: ghc] master: Fix #14390 by making toIfaceTyCon aware of equality (85aa1f4) Message-ID: <20171030015133.061313A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/85aa1f4253163985fe07d172f8da73b784bb7b4b/ghc >--------------------------------------------------------------- commit 85aa1f4253163985fe07d172f8da73b784bb7b4b Author: Ryan Scott Date: Sun Oct 29 20:48:19 2017 -0400 Fix #14390 by making toIfaceTyCon aware of equality GHC was panicking when pretty-printing a heterogeneous equality type constructor (#14390) because the function which produced the type constructor, `toIfaceTyCon`, wasn't attaching the appropriate `IfaceTyConSort` for equality type constructors, which is `IfaceEqualityTyCon`. This is fixed easily enough. Test Plan: make test TEST=T14390 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14390 Differential Revision: https://phabricator.haskell.org/D4132 >--------------------------------------------------------------- 85aa1f4253163985fe07d172f8da73b784bb7b4b compiler/iface/ToIface.hs | 6 ++++++ testsuite/tests/typecheck/should_fail/T14390.hs | 4 ++++ testsuite/tests/typecheck/should_fail/T14390.stderr | 5 +++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 4 files changed, 16 insertions(+) diff --git a/compiler/iface/ToIface.hs b/compiler/iface/ToIface.hs index 9eceb6d..6f71af5 100644 --- a/compiler/iface/ToIface.hs +++ b/compiler/iface/ToIface.hs @@ -195,6 +195,12 @@ toIfaceTyCon tc | isUnboxedSumTyCon tc , Just cons <- isDataSumTyCon_maybe tc = IfaceSumTyCon (length cons) + | tyConName tc == eqTyConName || tc == eqPrimTyCon + = IfaceEqualityTyCon True + + | tc `elem` [heqTyCon, eqReprPrimTyCon] + = IfaceEqualityTyCon False + | otherwise = IfaceNormalTyCon diff --git a/testsuite/tests/typecheck/should_fail/T14390.hs b/testsuite/tests/typecheck/should_fail/T14390.hs new file mode 100644 index 0000000..5360be7 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14390.hs @@ -0,0 +1,4 @@ +module T14390 where + +import Data.Type.Equality +instance (~~) Int Int diff --git a/testsuite/tests/typecheck/should_fail/T14390.stderr b/testsuite/tests/typecheck/should_fail/T14390.stderr new file mode 100644 index 0000000..f94bf40 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14390.stderr @@ -0,0 +1,5 @@ + +T14390.hs:4:10: error: + • Illegal instance declaration for ‘(Int :: *) ~~ (Int :: *)’ + Manual instances of this class are not permitted. + • In the instance declaration for ‘(~~) Int Int’ diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 1aa23c4..ca0264b 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -460,3 +460,4 @@ test('T13929', normal, compile_fail, ['']) test('T14232', normal, compile_fail, ['']) test('T14325', normal, compile_fail, ['']) test('T14350', normal, compile_fail, ['']) +test('T14390', normal, compile_fail, ['']) From git at git.haskell.org Mon Oct 30 01:51:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 01:51:37 +0000 (UTC) Subject: [commit: ghc] master: Allow packing constructor fields (cca2d6b) Message-ID: <20171030015137.DC8513A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cca2d6b78f97bfb79bef4dc3f75d6c4d15b94680/ghc >--------------------------------------------------------------- commit cca2d6b78f97bfb79bef4dc3f75d6c4d15b94680 Author: Michal Terepeta Date: Sun Oct 29 20:49:32 2017 -0400 Allow packing constructor fields This is another step for fixing #13825 and is based on D38 by Simon Marlow. The change allows storing multiple constructor fields within the same word. This currently applies only to `Float`s, e.g., ``` data Foo = Foo {-# UNPACK #-} !Float {-# UNPACK #-} !Float ``` on 64-bit arch, will now store both fields within the same constructor word. For `WordX/IntX` we'll need to introduce new primop types. Main changes: - We now use sizes in bytes when we compute the offsets for constructor fields in `StgCmmLayout` and introduce padding if necessary (word-sized fields are still word-aligned) - `ByteCodeGen` had to be updated to correctly construct the data types. This required some new bytecode instructions to allow pushing things that are not full words onto the stack (and updating `Interpreter.c`). Note that we only use the packed stuff when constructing data types (i.e., for `PACK`), in all other cases the behavior should not change. - `RtClosureInspect` was changed to handle the new layout when extracting subterms. This seems to be used by things like `:print`. I've also added a test for this. - I deviated slightly from Simon's approach and use `PrimRep` instead of `ArgRep` for computing the size of fields. This seemed more natural and in the future we'll probably want to introduce new primitive types (e.g., `Int8#`) and `PrimRep` seems like a better place to do that (where we already have `Int64Rep` for example). `ArgRep` on the other hand seems to be more focused on calling functions. Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: bgamari, simonmar, austin, hvr, goldfire, erikd Reviewed By: bgamari Subscribers: maoe, rwbarton, thomie GHC Trac Issues: #13825 Differential Revision: https://phabricator.haskell.org/D3809 >--------------------------------------------------------------- cca2d6b78f97bfb79bef4dc3f75d6c4d15b94680 compiler/cmm/CmmCallConv.hs | 5 +- compiler/cmm/SMRep.hs | 9 +- compiler/codeGen/StgCmmBind.hs | 2 +- compiler/codeGen/StgCmmCon.hs | 15 ++- compiler/codeGen/StgCmmHeap.hs | 15 +-- compiler/codeGen/StgCmmLayout.hs | 93 ++++++++++++++--- compiler/coreSyn/CoreLint.hs | 4 +- compiler/ghci/ByteCodeAsm.hs | 15 +++ compiler/ghci/ByteCodeGen.hs | 84 +++++++++++---- compiler/ghci/ByteCodeInstr.hs | 52 ++++++++- compiler/ghci/RtClosureInspect.hs | 89 ++++++++++------ compiler/main/Constants.hs | 4 + compiler/types/TyCon.hs | 35 ++++--- includes/rts/Bytecodes.h | 116 ++++++++++++--------- includes/stg/Types.h | 4 + rts/Disassembler.c | 47 ++++++++- rts/Interpreter.c | 81 ++++++++++++++ testsuite/tests/codeGen/should_run/T13825-unit.hs | 78 ++++++++++++++ testsuite/tests/codeGen/should_run/all.T | 4 + .../tests/ghci.debugger/scripts/T13825-debugger.hs | 33 ++++++ .../ghci.debugger/scripts/T13825-debugger.script | 7 ++ .../ghci.debugger/scripts/T13825-debugger.stdout | 8 ++ testsuite/tests/ghci.debugger/scripts/all.T | 1 + testsuite/tests/ghci/should_run/T13825-ghci.hs | 38 +++++++ testsuite/tests/ghci/should_run/T13825-ghci.script | 13 +++ testsuite/tests/ghci/should_run/T13825-ghci.stdout | 4 + testsuite/tests/ghci/should_run/all.T | 1 + .../tests/primops/should_run/T13825-compile.hs | 66 ++++++++++++ .../tests/primops/should_run/T13825-compile.stdout | 3 + testsuite/tests/primops/should_run/all.T | 1 + 30 files changed, 768 insertions(+), 159 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 cca2d6b78f97bfb79bef4dc3f75d6c4d15b94680 From git at git.haskell.org Mon Oct 30 05:01:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 05:01:26 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: base: Implement file locking in terms of POSIX locks (b71db11) Message-ID: <20171030050126.DB0643A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/b71db1122de9d302febafbd3a77713c989f5b4c6/ghc >--------------------------------------------------------------- commit b71db1122de9d302febafbd3a77713c989f5b4c6 Author: Ben Gamari Date: Sun Oct 29 20:46:21 2017 -0400 base: Implement file locking in terms of POSIX locks Hopefully these are more robust to NFS malfunction than BSD flock-style locks. See #13945. Test Plan: Validate via @simonpj Reviewers: austin, hvr Subscribers: rwbarton, thomie, erikd, simonpj GHC Trac Issues: #13945 Differential Revision: https://phabricator.haskell.org/D4129 (cherry picked from commit 3b784d440d4b01b4c549df7c9a3ed2058edfc780) >--------------------------------------------------------------- b71db1122de9d302febafbd3a77713c989f5b4c6 libraries/base/GHC/IO/Handle/Lock.hsc | 74 ++++++++++++++++++++++++++++++++++- libraries/base/configure.ac | 7 +++- 2 files changed, 78 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/IO/Handle/Lock.hsc b/libraries/base/GHC/IO/Handle/Lock.hsc index cbef5e4..748c180 100644 --- a/libraries/base/GHC/IO/Handle/Lock.hsc +++ b/libraries/base/GHC/IO/Handle/Lock.hsc @@ -99,7 +99,76 @@ hTryLock h mode = lockImpl h "hTryLock" mode False ---------------------------------------- -#if HAVE_FLOCK +#if HAVE_OFD_LOCKING +-- Linux open file descriptor locking. +-- +-- We prefer this over BSD locking (e.g. flock) since the latter appears to +-- break in some NFS configurations. Note that we intentionally do not try to +-- use ordinary POSIX file locking due to its peculiar semantics under +-- multi-threaded environments. + +foreign import ccall interruptible "fcntl" + c_fcntl :: CInt -> CInt -> Ptr () -> IO CInt + +data FLock = FLock { l_type :: CShort + , l_whence :: CShort + , l_start :: COff + , l_len :: COff + , l_pid :: CPid + } + +instance Storable FLock where + sizeOf _ = #{size flock} + alignment _ = #{alignment flock} + poke ptr x = do + fillBytes ptr 0 (sizeOf x) + #{poke flock, l_type} ptr (l_type x) + #{poke flock, l_whence} ptr (l_whence x) + #{poke flock, l_start} ptr (l_start x) + #{poke flock, l_len} ptr (l_len x) + #{poke flock, l_pid} ptr (l_pid x) + peek ptr = do + FLock <$> #{peek flock, l_type} ptr + <*> #{peek flock, l_whence} ptr + <*> #{peek flock, l_start} ptr + <*> #{peek flock, l_len} ptr + <*> #{peek flock, l_pid} ptr + +lockImpl :: Handle -> String -> LockMode -> Bool -> IO Bool +lockImpl h ctx mode block = do + FD{fdFD = fd} <- handleToFd h + with flock $ \flock_ptr -> fix $ \retry -> do + ret <- with flock $ fcntl fd mode flock_ptr + case ret of + 0 -> return True + _ -> getErrno >>= \errno -> if + | not block && errno == eWOULDBLOCK -> return False + | errno == eINTR -> retry + | otherwise -> ioException $ errnoToIOError ctx errno (Just h) Nothing + where + flock = FLock { l_type = case mode of + SharedLock -> #{const F_RDLCK} + ExclusiveLock -> #{const F_WRLCK} + , l_whence = #{const SEEK_SET} + , l_start = 0 + , l_len = 0 + } + mode + | block = #{const F_SETLKW} + | otherwise = #{const F_SETLK} + +unlockImpl :: Handle -> IO () +unlockImpl h = do + FD{fdFD = fd} <- handleToFd h + let flock = FLock { l_type = #{const F_UNLCK} + , l_whence = #{const SEEK_SET} + , l_start = 0 + , l_len = 0 + } + throwErrnoIfMinus1_ "hUnlock" + $ with flock $ c_fcntl fd #{const F_SETLK} + +#elif HAVE_FLOCK lockImpl :: Handle -> String -> LockMode -> Bool -> IO Bool lockImpl h ctx mode block = do @@ -108,7 +177,8 @@ lockImpl h ctx mode block = do fix $ \retry -> c_flock fd flags >>= \case 0 -> return True _ -> getErrno >>= \errno -> if - | not block && errno == eWOULDBLOCK -> return False + | not block + , errno == eAGAIN || errno == eACCES -> return False | errno == eINTR -> retry | otherwise -> ioException $ errnoToIOError ctx errno (Just h) Nothing where diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index af041a7..69ea800 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -69,7 +69,12 @@ if test "$ac_cv_header_poll_h" = yes && test "$ac_cv_func_poll" = yes; then AC_DEFINE([HAVE_POLL], [1], [Define if you have poll support.]) fi -#flock +# Linux open file description locks +AC_CHECK_DECL([F_OFD_SETLK], [ + AC_DEFINE([HAVE_OFD_LOCKING], [1], [Define if you have open file descriptor lock support.]) +]) + +# flock AC_CHECK_FUNCS([flock]) if test "$ac_cv_header_sys_file_h" = yes && test "$ac_cv_func_flock" = yes; then AC_DEFINE([HAVE_FLOCK], [1], [Define if you have flock support.]) From git at git.haskell.org Mon Oct 30 08:44:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 08:44:03 +0000 (UTC) Subject: [commit: ghc] master: A bit more tc-tracing (82bad1a) Message-ID: <20171030084403.EEBAA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/82bad1a9e08e7ac72aecd6e5b7bde8e828c56256/ghc >--------------------------------------------------------------- commit 82bad1a9e08e7ac72aecd6e5b7bde8e828c56256 Author: Simon Peyton Jones Date: Mon Oct 16 16:15:08 2017 +0100 A bit more tc-tracing >--------------------------------------------------------------- 82bad1a9e08e7ac72aecd6e5b7bde8e828c56256 compiler/typecheck/TcCanonical.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index be8bbee..d48d04f 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -829,7 +829,8 @@ zonk_eq_types = go -> do { cts <- readTcRef ref ; case cts of Flexi -> give_up - Indirect ty' -> unSwap swapped go ty' ty } + Indirect ty' -> do { trace_indirect tv ty' + ; unSwap swapped go ty' ty } } _ -> give_up where give_up = return $ Left $ unSwap swapped Pair (mkTyVarTy tv) ty @@ -842,12 +843,17 @@ zonk_eq_types = go then go ty1' ty2' else return $ Left (Pair (TyVarTy tv1) (TyVarTy tv2)) } + trace_indirect tv ty + = traceTcS "Following filled tyvar (zonk_eq_types)" + (ppr tv <+> equals <+> ppr ty) + quick_zonk tv = case tcTyVarDetails tv of MetaTv { mtv_ref = ref } -> do { cts <- readTcRef ref ; case cts of Flexi -> return (TyVarTy tv, False) - Indirect ty' -> return (ty', True) } + Indirect ty' -> do { trace_indirect tv ty' + ; return (ty', True) } } _ -> return (TyVarTy tv, False) -- This happens for type families, too. But recall that failure From git at git.haskell.org Mon Oct 30 14:01:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 14:01:18 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in accessor name (1b115b1) Message-ID: <20171030140118.543F03A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1b115b16729a3414cc1e07fb1efe7f34c990b1f0/ghc >--------------------------------------------------------------- commit 1b115b16729a3414cc1e07fb1efe7f34c990b1f0 Author: Gabor Greif Date: Fri Oct 27 22:59:18 2017 +0200 Fix typo in accessor name and in comments >--------------------------------------------------------------- 1b115b16729a3414cc1e07fb1efe7f34c990b1f0 compiler/deSugar/Check.hs | 6 +++--- compiler/deSugar/DsBinds.hs | 2 +- compiler/specialise/SpecConstr.hs | 2 +- compiler/typecheck/TcType.hs | 2 +- libraries/base/GHC/IO/Encoding/CodePage/API.hs | 4 ++-- testsuite/mk/boilerplate.mk | 2 +- testsuite/tests/simplCore/should_compile/spec001.hs | 2 +- testsuite/tests/th/T10638.hs | 2 +- 8 files changed, 11 insertions(+), 11 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 8fb9553..d49a5c3 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -239,10 +239,10 @@ instance Monoid Provenance where mappend = (Semi.<>) data PartialResult = PartialResult { - presultProvenence :: Provenance + presultProvenance :: Provenance -- keep track of provenance because we don't want -- to warn about redundant matches if the result - -- is contaiminated with a COMPLETE pragma + -- is contaminated with a COMPLETE pragma , presultCovered :: Covered , presultUncovered :: Uncovered , presultDivergent :: Diverged } @@ -1640,7 +1640,7 @@ force_if True pres = forces pres force_if False pres = pres set_provenance :: Provenance -> PartialResult -> PartialResult -set_provenance prov pr = pr { presultProvenence = prov } +set_provenance prov pr = pr { presultProvenance = prov } -- ---------------------------------------------------------------------------- -- * Propagation of term constraints inwards when checking nested matches diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index c01cb40..e11f580 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -655,7 +655,7 @@ dsSpec mb_poly_rhs (L loc (SpecPrag poly_id spec_co spec_inl)) = putSrcSpanDs loc $ do { warnDs NoReason (text "Ignoring useless SPECIALISE pragma for NOINLINE function:" <+> quotes (ppr poly_id)) - ; return Nothing } -- Function is NOINLINE, and the specialiation inherits that + ; return Nothing } -- Function is NOINLINE, and the specialisation inherits that -- See Note [Activation pragmas for SPECIALISE] | otherwise diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs index cfb9b5f..6115a03 100644 --- a/compiler/specialise/SpecConstr.hs +++ b/compiler/specialise/SpecConstr.hs @@ -1811,7 +1811,7 @@ that specialisations didn't fire inside wrappers; see test simplCore/should_compile/spec-inline. So now I just use the inline-activation of the parent Id, as the -activation for the specialiation RULE, just like the main specialiser; +activation for the specialisation RULE, just like the main specialiser; This in turn means there is no point in specialising NOINLINE things, so we test for that. diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 75e0215..b17df08 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -958,7 +958,7 @@ Moreover, consider inert item: [G] b ~R f a We use anyRewritableTyVar to decide whether to kick out the inert item, on the grounds that the work item might rewrite it. Well, 'a' is certainly -free in [G] b ~R f a. But becuase the role of a type variable ('f' in +free in [G] b ~R f a. But because the role of a type variable ('f' in this case) is nominal, the work item can't actually rewrite the inert item. Moreover, if we were to kick out the inert item the exact same situation would re-occur and we end up with an infninite loop in which each kicks diff --git a/libraries/base/GHC/IO/Encoding/CodePage/API.hs b/libraries/base/GHC/IO/Encoding/CodePage/API.hs index f1d9d93..b31ebe9 100644 --- a/libraries/base/GHC/IO/Encoding/CodePage/API.hs +++ b/libraries/base/GHC/IO/Encoding/CodePage/API.hs @@ -285,7 +285,7 @@ cpEncode cp _max_char_size = \ibuf obuf -> do return (why2, mbuf', obuf) #else case why2 of - -- If we succesfully translate all of the UTF-16 buffer, we need to know why + -- If we successfully translate all of the UTF-16 buffer, we need to know why -- we weren't able to get any more UTF-16 out of the UTF-32 buffer InputUnderflow | isEmptyBuffer mbuf' -> return (why1, ibuf', obuf) | otherwise -> errorWithoutStackTrace "cpEncode: impossible underflown UTF-16 buffer" @@ -361,7 +361,7 @@ bSearch msg code ibuf mbuf target_to_elems = go -- -- Luckily if we have InvalidSequence/OutputUnderflow and we do not appear to have reached -- the target, what we should do is the same as normal because the fraction of ibuf that our - -- first "code" coded succesfully must be invalid-sequence-free, and ibuf will always + -- first "code" coded successfully must be invalid-sequence-free, and ibuf will always -- have been decoded as far as the first invalid sequence in it. case bufferElems mbuf `compare` target_to_elems of -- Coding n "from" chars from the input yields exactly as many "to" chars diff --git a/testsuite/mk/boilerplate.mk b/testsuite/mk/boilerplate.mk index 0b684c7..c38bf85 100644 --- a/testsuite/mk/boilerplate.mk +++ b/testsuite/mk/boilerplate.mk @@ -54,7 +54,7 @@ ifeq "$(TEST_HC)" "" # Tests should be able to handle paths with spaces. # # One of the things ./validate (without --fast) does is check if binary -# distributions can succesfully be installed and used in paths containing +# distributions can successfully be installed and used in paths containing # spaces. # # It does so in the following way: diff --git a/testsuite/tests/simplCore/should_compile/spec001.hs b/testsuite/tests/simplCore/should_compile/spec001.hs index 9af452c..5fb9685 100644 --- a/testsuite/tests/simplCore/should_compile/spec001.hs +++ b/testsuite/tests/simplCore/should_compile/spec001.hs @@ -2,7 +2,7 @@ {-# OPTIONS_GHC -O #-} -- In GHC 6.4, compiling this module gave a Core Lint failure following the --- specialier, because a function was floated out that had a RULE that +-- specialiser, because a function was floated out that had a RULE that -- mentioned another function (unpack, in fact). but the latter wasn't -- floated because we didn't take the RULES into account properly; result, -- variable out of scope. diff --git a/testsuite/tests/th/T10638.hs b/testsuite/tests/th/T10638.hs index 7dd17eb..0cf2440 100644 --- a/testsuite/tests/th/T10638.hs +++ b/testsuite/tests/th/T10638.hs @@ -10,7 +10,7 @@ import GHC.Exts headers and the static keyword. -} --- check that quasiquoting roundtrips succesfully and that the declaration +-- check that quasiquoting roundtrips successfully and that the declaration -- does not include the static keyword test1 :: String test1 = $(do (ds@[ForeignD (ImportF _ _ p _ _)]) <- From git at git.haskell.org Mon Oct 30 14:01:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 14:01:21 +0000 (UTC) Subject: [commit: ghc] master: Typofix in panic (ec356e8) Message-ID: <20171030140121.2C09F3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ec356e8a3530557638bc30df07f0253c6527fb13/ghc >--------------------------------------------------------------- commit ec356e8a3530557638bc30df07f0253c6527fb13 Author: Gabor Greif Date: Sun Oct 22 23:05:02 2017 +0200 Typofix in panic >--------------------------------------------------------------- ec356e8a3530557638bc30df07f0253c6527fb13 compiler/nativeGen/RegAlloc/Liveness.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/nativeGen/RegAlloc/Liveness.hs b/compiler/nativeGen/RegAlloc/Liveness.hs index db09b0e..d4fecf2 100644 --- a/compiler/nativeGen/RegAlloc/Liveness.hs +++ b/compiler/nativeGen/RegAlloc/Liveness.hs @@ -814,7 +814,7 @@ computeLiveness computeLiveness platform sccs = case checkIsReverseDependent sccs of Nothing -> livenessSCCs platform mapEmpty [] sccs - Just bad -> pprPanic "RegAlloc.Liveness.computeLivenss" + Just bad -> pprPanic "RegAlloc.Liveness.computeLiveness" (vcat [ text "SCCs aren't in reverse dependent order" , text "bad blockId" <+> ppr bad , ppr sccs]) From git at git.haskell.org Mon Oct 30 14:01:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 14:01:24 +0000 (UTC) Subject: [commit: ghc] master: Typofixes in comments (1569668) Message-ID: <20171030140124.00A9C3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/15696682a4ac65c359101844c212fd4ae7357dc8/ghc >--------------------------------------------------------------- commit 15696682a4ac65c359101844c212fd4ae7357dc8 Author: Gabor Greif Date: Tue Oct 24 23:25:56 2017 +0200 Typofixes in comments >--------------------------------------------------------------- 15696682a4ac65c359101844c212fd4ae7357dc8 compiler/main/DriverPipeline.hs | 2 +- compiler/main/HscMain.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 1996118..fab7fad 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -794,7 +794,7 @@ getOutputFilename stop_phase output basename dflags next_phase maybe_location -- | The fast LLVM Pipeline skips the mangler and assembler, --- emiting object code dirctly from llc. +-- emitting object code directly from llc. -- -- slow: opt -> llc -> .s -> mangler -> as -> .o -- fast: opt -> llc -> .o diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index 2d8c600..975c96f 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -533,7 +533,7 @@ makeSimpleDetails hsc_env tc_result = mkBootModDetailsTc hsc_env tc_result -------------------------------- It's the task of the compilation proper to compile Haskell, hs-boot and core -files to either byte-code, hard-code (C, asm, LLVM, ect) or to nothing at all +files to either byte-code, hard-code (C, asm, LLVM, etc.) or to nothing at all (the module is still parsed and type-checked. This feature is mostly used by IDE's and the likes). Compilation can happen in either 'one-shot', 'batch', 'nothing', or 'interactive' mode. 'One-shot' mode targets hard-code, 'batch' diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index e73fdd6..08c8dab 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -10,7 +10,7 @@ module. All the monads exported here are built on top of the same IOEnv monad. The monad functions like a Reader monad in the way it passes the environment around. This is done to allow the environment to be manipulated in a stack -like fashion when entering expressions... ect. +like fashion when entering expressions... etc. For state that is global and should be returned at the end (e.g not part of the stack mechanism), you should use a TcRef (= IORef) to store them. From git at git.haskell.org Mon Oct 30 14:01:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 14:01:26 +0000 (UTC) Subject: [commit: ghc] master: minor wordsmithing (53700a9) Message-ID: <20171030140126.BC2FC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/53700a9de48a3fb15015bd60462878fc9a2c0548/ghc >--------------------------------------------------------------- commit 53700a9de48a3fb15015bd60462878fc9a2c0548 Author: Gabor Greif Date: Mon Oct 30 12:03:30 2017 +0100 minor wordsmithing >--------------------------------------------------------------- 53700a9de48a3fb15015bd60462878fc9a2c0548 docs/users_guide/using-warnings.rst | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index 216d7ee..c6a86bb 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -1466,17 +1466,17 @@ of ``-W(no-)*``. ``other-modules``. .. ghc-flag:: -Wpartial-fields - :shortdesc: warn when define partial record field. + :shortdesc: warn when defining a partial record field. :type: dynamic :reverse: -Wno-partial-fields :category: :since: 8.4 - The option :ghc-flag:`-Wpartial-fields` warns about record field that could - fail when it is used as a function. The function ``f`` below will fail when - applied to Bar, so the compiler will emit a warning about this when - :ghc-flag:`-Wpartial-fields` is enabled. + The option :ghc-flag:`-Wpartial-fields` warns about record fields that could + fail when accessed via a lacking constructor. The function ``f`` below will + fail when applied to ``Bar``, so the compiler will emit a warning at its + definition when :ghc-flag:`-Wpartial-fields` is enabled. The warning is suppressed if the field name begins with an underscore. :: From git at git.haskell.org Mon Oct 30 14:01:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 14:01:29 +0000 (UTC) Subject: [commit: ghc] master: Catch a few more typos in comments (201b5aa) Message-ID: <20171030140129.8DF8D3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/201b5aa65109e09953caa1dc1774b75fabbf61b0/ghc >--------------------------------------------------------------- commit 201b5aa65109e09953caa1dc1774b75fabbf61b0 Author: Gabor Greif Date: Mon Oct 30 12:21:49 2017 +0100 Catch a few more typos in comments >--------------------------------------------------------------- 201b5aa65109e09953caa1dc1774b75fabbf61b0 compiler/specialise/SpecConstr.hs | 4 ++-- compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcInteract.hs | 4 ++-- compiler/typecheck/TcSMonad.hs | 6 +++--- compiler/typecheck/TcTyClsDecls.hs | 4 ++-- compiler/typecheck/TcType.hs | 2 +- ghc/Main.hs | 2 +- libraries/base/configure.ac | 2 +- utils/llvm-targets/gen-data-layout.sh | 2 +- 9 files changed, 14 insertions(+), 14 deletions(-) diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs index 6115a03..d54c1ea 100644 --- a/compiler/specialise/SpecConstr.hs +++ b/compiler/specialise/SpecConstr.hs @@ -516,7 +516,7 @@ for nested bindings. (So really it should be passed around explicitly and not stored in ScEnv.) Trac #14379 turned out to be caused by f SPEC x = let g1 x = ... in ... -We force-specialise f (becuase of the SPEC), but that generates a specialised +We force-specialise f (because of the SPEC), but that generates a specialised copy of g1 (as well as the original). Alas g1 has a nested binding g2; and in each copy of g1 we get an unspecialised and specialised copy of g2; and so on. Result, exponential. So the force-spec flag now only applies to one @@ -526,7 +526,7 @@ Mechanism for this one-level-only thing: - Switch it on at the call to specRec, in scExpr and scTopBinds - Switch it off when doing the RHSs; - this can be done very conveneniently in decreaseSpecCount + this can be done very conveniently in decreaseSpecCount What alternatives did I consider? diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index d48d04f..8a459de 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1623,7 +1623,7 @@ canEqTyVarTyVar, are these Note [Avoid unnecessary swaps] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -If we swap without actually improving matters, we can get an infnite loop. +If we swap without actually improving matters, we can get an infinite loop. Consider work item: a ~ b inert item: b ~ c diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 0413626..76c5dbd 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -2098,9 +2098,9 @@ favour of alpha. If we instead had then we would unify alpha := gamma1; and kick out the wanted constraint. But when we grough it back in, it'd look like [W] TF (gamma1, beta) ~ fuv -and exactly the same thing would happen again! Infnite loop. +and exactly the same thing would happen again! Infinite loop. -This all sesms fragile, and it might seem more robust to avoid +This all seems fragile, and it might seem more robust to avoid introducing gamma1 in the first place, in the case where the actual argument (alpha, beta) partly matches the improvement template. But that's a bit tricky, esp when we remember that the diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index c5c1102..0d936ff 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -787,7 +787,7 @@ Main Theorem [Stability under extension] Suppose we have a "work item" a -fw-> t and an inert generalised substitution S, - ThEN the extended substitution T = S+(a -fw-> t) + THEN the extended substitution T = S+(a -fw-> t) is an inert generalised substitution PROVIDED (T1) S(fw,a) = a -- LHS of work-item is a fixpoint of S(fw,_) @@ -860,9 +860,9 @@ The idea is that - (T3) guarantees (WF2). * (K2) is about inertness. Intuitively, any infinite chain T^0(f,t), - T^1(f,t), T^2(f,T).... must pass through the new work item infnitely + T^1(f,t), T^2(f,T).... must pass through the new work item infinitely often, since the substitution without the work item is inert; and must - pass through at least one of the triples in S infnitely often. + pass through at least one of the triples in S infinitely often. - (K2a): if not(fs>=fs) then there is no f that fs can rewrite (fs>=f), and hence this triple never plays a role in application S(f,a). diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index cf92638..9798183 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -2395,7 +2395,7 @@ checkValidTyCon tc fty1 = dataConFieldType con1 lbl lbl = flLabel label - checkOne (_, con2) -- Do it bothways to ensure they are structurally identical + checkOne (_, con2) -- Do it both ways to ensure they are structurally identical = do { checkFieldCompat lbl con1 con2 res1 res2 fty1 fty2 ; checkFieldCompat lbl con2 con1 res2 res1 fty2 fty1 } where @@ -2403,7 +2403,7 @@ checkValidTyCon tc fty2 = dataConFieldType con2 lbl checkPartialRecordField :: [DataCon] -> FieldLabel -> TcM () --- Check the partial record field selector, and warns. +-- Checks the partial record field selector, and warns. -- See Note [Checking partial record field] checkPartialRecordField all_cons fld = setSrcSpan loc $ diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index b17df08..d752d1e 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -961,7 +961,7 @@ on the grounds that the work item might rewrite it. Well, 'a' is certainly free in [G] b ~R f a. But because the role of a type variable ('f' in this case) is nominal, the work item can't actually rewrite the inert item. Moreover, if we were to kick out the inert item the exact same situation -would re-occur and we end up with an infninite loop in which each kicks +would re-occur and we end up with an infinite loop in which each kicks out the other (Trac #14363). -} diff --git a/ghc/Main.hs b/ghc/Main.hs index 7c406e4..74b017a 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -804,7 +804,7 @@ dumpFastStringStats dflags = do ]) -- we usually get more "has z-encoding" than "z-encoded", because -- when we z-encode a string it might hash to the exact same string, - -- which will is not counted as "z-encoded". Only strings whose + -- which is not counted as "z-encoded". Only strings whose -- Z-encoding is different from the original string are counted in -- the "z-encoded" total. putMsg dflags msg diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index 69ea800..f472319 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -69,7 +69,7 @@ if test "$ac_cv_header_poll_h" = yes && test "$ac_cv_func_poll" = yes; then AC_DEFINE([HAVE_POLL], [1], [Define if you have poll support.]) fi -# Linux open file description locks +# Linux open file descriptor locks AC_CHECK_DECL([F_OFD_SETLK], [ AC_DEFINE([HAVE_OFD_LOCKING], [1], [Define if you have open file descriptor lock support.]) ]) diff --git a/utils/llvm-targets/gen-data-layout.sh b/utils/llvm-targets/gen-data-layout.sh index 95c629c..6f2aafc 100755 --- a/utils/llvm-targets/gen-data-layout.sh +++ b/utils/llvm-targets/gen-data-layout.sh @@ -44,7 +44,7 @@ function get_cpu_and_attr() { # additional columns for opt and llc flags, we could # pass -float-abi=soft; However ghc will use float # registers unconditionally on arm, and as such true - # soft float with the registered llvm backed will is + # soft float with the registerised llvm backend is # currently not possible. +soft-float-abi) shift 2;; *) ATTR+=("$2"); shift 2;; From git at git.haskell.org Mon Oct 30 14:57:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 14:57:23 +0000 (UTC) Subject: [commit: ghc] master: Add Note [Setting the right in-scope set] (609f284) Message-ID: <20171030145723.D54583A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/609f2844b92d5aa474f34b989c6ec5ad9fdb2ce3/ghc >--------------------------------------------------------------- commit 609f2844b92d5aa474f34b989c6ec5ad9fdb2ce3 Author: Simon Peyton Jones Date: Mon Oct 30 14:56:58 2017 +0000 Add Note [Setting the right in-scope set] >--------------------------------------------------------------- 609f2844b92d5aa474f34b989c6ec5ad9fdb2ce3 compiler/simplCore/SimplEnv.hs | 27 ++++++++++++++++++++++++++- 1 file changed, 26 insertions(+), 1 deletion(-) diff --git a/compiler/simplCore/SimplEnv.hs b/compiler/simplCore/SimplEnv.hs index 0badb2a..d2cb689 100644 --- a/compiler/simplCore/SimplEnv.hs +++ b/compiler/simplCore/SimplEnv.hs @@ -337,7 +337,8 @@ setInScopeSet :: SimplEnv -> InScopeSet -> SimplEnv setInScopeSet env in_scope = env {seInScope = in_scope} setInScopeFromE :: SimplEnv -> SimplEnv -> SimplEnv -setInScopeFromE env env' = env { seInScope = seInScope env' } +-- See Note [Setting the right in-scope set] +setInScopeFromE rhs_env here_env = rhs_env { seInScope = seInScope here_env } setInScopeFromF :: SimplEnv -> SimplFloats -> SimplEnv setInScopeFromF env floats = env { seInScope = sfInScope floats } @@ -360,6 +361,30 @@ modifyInScope :: SimplEnv -> CoreBndr -> SimplEnv modifyInScope env@(SimplEnv {seInScope = in_scope}) v = env {seInScope = extendInScopeSet in_scope v} +{- Note [Setting the right in-scope set] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + \x. (let x = e in b) arg[x] +where the let shadows the lambda. Really this means something like + \x1. (let x2 = e in b) arg[x1] + +- When we capture the 'arg' in an ApplyToVal continuation, we capture + the environment, which says what 'x' is bound to, namely x1 + +- Then that continuation gets pushed under the let + +- Finally we simplify 'arg'. We want + - the static, lexical environment bindig x :-> x1 + - the in-scopeset from "here", under the 'let' which includes + both x1 and x2 + +It's important to have the right in-scope set, else we may rename a +variable to one that is already in scope. So we must pick up the +in-scope set from "here", but otherwise use the environment we +captured along with 'arg'. This transfer of in-scope set is done by +setInScopeFromE. +-} + --------------------- zapSubstEnv :: SimplEnv -> SimplEnv zapSubstEnv env = env {seTvSubst = emptyVarEnv, seCvSubst = emptyVarEnv, seIdSubst = emptyVarEnv} From git at git.haskell.org Mon Oct 30 21:29:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 21:29:11 +0000 (UTC) Subject: [commit: ghc] master: core-spec: Add join points to formalism (af0aea9) Message-ID: <20171030212911.341D63A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/af0aea9c3d5f68f2694bd7b6380788764aa3f1ff/ghc >--------------------------------------------------------------- commit af0aea9c3d5f68f2694bd7b6380788764aa3f1ff Author: Luke Maurer Date: Mon Oct 30 17:18:11 2017 -0400 core-spec: Add join points to formalism >--------------------------------------------------------------- af0aea9c3d5f68f2694bd7b6380788764aa3f1ff docs/core-spec/CoreLint.ott | 127 +++++++++++++++++++++++++++++-------------- docs/core-spec/CoreSyn.ott | 35 ++++++++++++ docs/core-spec/OpSem.ott | 4 ++ docs/core-spec/core-spec.mng | 75 +++++++++++++++++++++++-- docs/core-spec/core-spec.pdf | Bin 346103 -> 354307 bytes 5 files changed, 196 insertions(+), 45 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 af0aea9c3d5f68f2694bd7b6380788764aa3f1ff From git at git.haskell.org Mon Oct 30 23:24:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 23:24:41 +0000 (UTC) Subject: [commit: ghc] wip/T14373: Implement pointer tagging for 'big' families #14373 (b723ca6) Message-ID: <20171030232441.2132E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14373 Link : http://ghc.haskell.org/trac/ghc/changeset/b723ca6cd9b369fb2ebd46894c2c0384be95d9eb/ghc >--------------------------------------------------------------- commit b723ca6cd9b369fb2ebd46894c2c0384be95d9eb Author: Gabor Greif Date: Fri Oct 20 15:45:37 2017 +0200 Implement pointer tagging for 'big' families #14373 Formerly we punted on these and evaluated constructors always got a tag of 1. We now cascade switches because we have to check the tag first and when it is MAX_PTR_TAG then get the precise tag from the info table and switch on that. The only technically tricky part is that the default case needs (logical) duplication. To do this we emit an extra label for it and branch to that from the second switch. This avoids duplicated codegen. >--------------------------------------------------------------- b723ca6cd9b369fb2ebd46894c2c0384be95d9eb compiler/codeGen/StgCmmClosure.hs | 11 +++++-- compiler/codeGen/StgCmmExpr.hs | 67 ++++++++++++++++++++++++++++++--------- 2 files changed, 60 insertions(+), 18 deletions(-) diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs index 2501ec9..ce0f623 100644 --- a/compiler/codeGen/StgCmmClosure.hs +++ b/compiler/codeGen/StgCmmClosure.hs @@ -354,9 +354,12 @@ type DynTag = Int -- The tag on a *pointer* -- * big, otherwise. -- -- Small families can have the constructor tag in the tag bits. --- Big families only use the tag value 1 to represent evaluatedness. +-- Big families always use the tag values 1..mAX_PTR_TAG to represent +-- evaluatedness, the last one lumping together all overflowing ones. -- We don't have very many tag bits: for example, we have 2 bits on -- x86-32 and 3 bits on x86-64. +-- +-- Also see Note [tagging big families] isSmallFamily :: DynFlags -> Int -> Bool isSmallFamily dflags fam_size = fam_size <= mAX_PTR_TAG dflags @@ -369,10 +372,12 @@ isSmallFamilyTyCon dflags tycon = tagForCon :: DynFlags -> DataCon -> DynTag tagForCon dflags con | isSmallFamilyTyCon dflags tycon = con_tag - | otherwise = 1 + | con_tag <= max_tag = con_tag + | otherwise = max_tag where - con_tag = dataConTag con -- NB: 1-indexed + con_tag = dataConTag con -- NB: 1-indexed tycon = dataConTyCon con + max_tag = mAX_PTR_TAG dflags tagForArity :: DynFlags -> RepArity -> DynTag tagForArity dflags arity diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index 3fcc935..6c00cef 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -37,6 +37,7 @@ import Cmm import CmmInfo import CoreSyn import DataCon +import DynFlags ( mAX_PTR_TAG ) import ForeignCall import Id import PrimOp @@ -49,9 +50,10 @@ import Util import FastString import Outputable -import Control.Monad (unless,void) -import Control.Arrow (first) +import Control.Monad ( unless, void ) +import Control.Arrow ( first ) import Data.Function ( on ) +import Data.List ( partition ) ------------------------------------------------------------------------ -- cgExpr: the main function @@ -607,21 +609,36 @@ cgAlts gc_plan bndr (AlgAlt tycon) alts ; let fam_sz = tyConFamilySize tycon bndr_reg = CmmLocal (idToReg dflags bndr) + tag_expr = cmmConstrTag1 dflags (CmmReg bndr_reg) + branches' = [(tag+1,branch) | (tag,branch) <- branches] + maxpt = mAX_PTR_TAG dflags + (ptr, info) = partition ((< maxpt) . fst) branches' + small = isSmallFamily dflags fam_sz -- Is the constructor tag in the node reg? - ; if isSmallFamily dflags fam_sz - then do - let -- Yes, bndr_reg has constr. tag in ls bits - tag_expr = cmmConstrTag1 dflags (CmmReg bndr_reg) - branches' = [(tag+1,branch) | (tag,branch) <- branches] - emitSwitch tag_expr branches' mb_deflt 1 fam_sz - - else -- No, get tag from info table - let -- Note that ptr _always_ has tag 1 - -- when the family size is big enough - untagged_ptr = cmmRegOffB bndr_reg (-1) - tag_expr = getConstrTag dflags (untagged_ptr) - in emitSwitch tag_expr branches mb_deflt 0 (fam_sz - 1) + -- See Note [tagging big families] + ; if small || null info + then -- Yes, bndr_reg has constr. tag in ls bits + emitSwitch tag_expr branches' mb_deflt 1 (if small then fam_sz else maxpt) + + else -- No, get exact tag from info table when mAX_PTR_TAG + do + infos_lbl <- newBlockId -- branch destination for info pointer lookup + infos_scp <- getTickScope + + let catchall = (maxpt, (mkBranch infos_lbl, infos_scp)) + prelabel (Just (stmts, scp)) = + do lbl <- newBlockId + return (Just (mkLabel lbl scp <*> stmts, scp), Just (mkBranch lbl, scp)) + prelabel _ = return (Nothing, Nothing) + + (mb_deflt, mb_branch) <- prelabel mb_deflt + emitSwitch tag_expr (catchall : ptr) mb_deflt 1 maxpt + emitLabel infos_lbl + let untagged_ptr = cmmUntag dflags (CmmReg bndr_reg) + tag_expr = getConstrTag dflags untagged_ptr + info0 = (\(tag,branch)->(tag-1,branch)) <$> info + emitSwitch tag_expr info0 mb_branch (maxpt - 1) (fam_sz - 1) ; return AssignedDirectly } @@ -649,6 +666,26 @@ cgAlts _ _ _ _ = panic "cgAlts" -- x = R1 -- goto L1 + +-- Note [tagging big families] +-- +-- Previousy, only the small constructor families were tagged. +-- This penalized greater unions which overflow the tag space +-- of TAG_BITS (i.e. 3 on 32 resp. 7 constructors on 64 bit). +-- But there is a clever way of combining pointer and info-table +-- tagging. We now use 1..{2,6} as pointer-resident tags while +-- {3,7} signifies we have to fall back and get the tag from the +-- info-table. +-- Conseqently we now cascade switches because we have to check +-- the tag first and when it is MAX_PTR_TAG then get the precise +-- tag from the info table and switch on that. The only technically +-- tricky part is that the default case needs (logical) duplication. +-- To do this we emit an extra label for it and branch to that from +-- the second switch. This avoids duplicated codegen. +-- +-- Also see Note [Data constructor dynamic tags] + + ------------------- cgAlgAltRhss :: (GcPlan,ReturnKind) -> NonVoid Id -> [StgAlt] -> FCode ( Maybe CmmAGraphScoped From git at git.haskell.org Mon Oct 30 23:24:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Oct 2017 23:24:43 +0000 (UTC) Subject: [commit: ghc] wip/T14373's head updated: Implement pointer tagging for 'big' families #14373 (b723ca6) Message-ID: <20171030232443.99B273A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14373' now includes: 99c61e2 Add stack traces on crashes on Windows bb537b2 nofib submodule: Fix a problem with fasta-c.c 1e24a24 submodule nofib: Add digits-of-e1.faststdout 052ec24 submodule nofib: Add digits-of-e2.faststdout b10a768 Comments only d1eaead Temporary fix to Trac #14380 671b1ed User’s guide: Properly link to RTS flag -V 8843a39 Include usg_file_hash in ghc --show-iface output 3825b7e Remove the 'legroom' part of the timeout-accurate-pure test. b62097d Windows: Bump to GCC 7.2 for GHC 8.4 e888a1f Revert "Windows: Bump to GCC 7.2 for GHC 8.4" 561bdca Update Win32 version for GHC 8.4. f744261 ghc-cabal: Inline removed function from Cabal. 2e16a57 Revert "ghc-cabal: Inline removed function ..." b1ad0bb Revert "Update Win32 version for GHC 8.4." 61f1b46 Make language extensions their own category in the documentation bf83435 typecheck: Clarify errors mentioned in #14385 bd53b48 Add info about Github pull requests. 2a4c24e Make layLeft and reduceDoc stricter (#7258) 980e127 Windows: Update the mirror script to generate hashes and use mirror fallback 1c15d8e Fix space leak in BinIface.getSymbolTable df63668 Performance improvements linear regAlloc (#7258) f7f270e Implement `-Wpartial-fields` warning (#7169) 821adee Fix a bug in 'alexInputPrevChar' 2c23fff user-guide: Clarify default optimization flags 4c06ccb base: Enable listToMaybe to fuse via foldr/build dbd81f7 Factor out readField (#14364) d91a6b6 Declare upstram repo location for hsc2hs 160a491 users-guide: Disable index node generation 9ae24bb configure: Add Alpine Linux to checkVendor a10c2e6 Don't use $SHELL in wrapper scripts 355318c Add more pprTrace to SpecConstr (debug only) 7d7d94f Fix an exponential-blowup case in SpecConstr 41f9055 ApplicativeDo: handle BodyStmt (#12143) acd355a relnotes: Fix a few minor formatting issues faf60e8 Make tagForCon non-linear 922db3d Manual: The -ddump-cmm-* flags had a wrong spelling in the manual 97ca0d2 simplNonRecJoinPoint: Handle Shadowing correctly 0e953da Implement a dedicated exitfication pass #14152 3b784d4 base: Implement file locking in terms of POSIX locks cecd2f2 Add -falignment-sanitization flag 7673561 Turn `compareByteArrays#` out-of-line primop into inline primop 85aa1f4 Fix #14390 by making toIfaceTyCon aware of equality cca2d6b Allow packing constructor fields 82bad1a A bit more tc-tracing 1b115b1 Fix typo in accessor name ec356e8 Typofix in panic 1569668 Typofixes in comments 53700a9 minor wordsmithing 201b5aa Catch a few more typos in comments 609f284 Add Note [Setting the right in-scope set] b723ca6 Implement pointer tagging for 'big' families #14373 From git at git.haskell.org Tue Oct 31 03:34:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Oct 2017 03:34:52 +0000 (UTC) Subject: [commit: ghc] wip/T14068: Do not inline showWord (a95a849) Message-ID: <20171031033452.7F8C33A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14068 Link : http://ghc.haskell.org/trac/ghc/changeset/a95a8494d94d02c63bfe2e93eb352333d9639beb/ghc >--------------------------------------------------------------- commit a95a8494d94d02c63bfe2e93eb352333d9639beb Author: Joachim Breitner Date: Wed Aug 2 11:26:22 2017 -0400 Do not inline showWord mostly because otherwise the test setup of #7014 fails. (The test checks for the absence of certain primops in the code, but inlining showWords adds many of these.) >--------------------------------------------------------------- a95a8494d94d02c63bfe2e93eb352333d9639beb libraries/base/GHC/Show.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/libraries/base/GHC/Show.hs b/libraries/base/GHC/Show.hs index 980b4a7..03b8f95 100644 --- a/libraries/base/GHC/Show.hs +++ b/libraries/base/GHC/Show.hs @@ -196,6 +196,7 @@ showWord w# cs | otherwise = case chr# (ord# '0'# +# word2Int# (w# `remWord#` 10##)) of c# -> showWord (w# `quotWord#` 10##) (C# c# : cs) +{-# NOINLINE showWord #-} deriving instance Show a => Show (Maybe a) deriving instance Show a => Show (NonEmpty a) From git at git.haskell.org Tue Oct 31 03:34:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Oct 2017 03:34:55 +0000 (UTC) Subject: [commit: ghc] wip/T14068: Mark `eqString` as `NOINLINE` (32838c6) Message-ID: <20171031033455.5B4D73A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14068 Link : http://ghc.haskell.org/trac/ghc/changeset/32838c6c148072a2864f5fba47f61fe4528759cd/ghc >--------------------------------------------------------------- commit 32838c6c148072a2864f5fba47f61fe4528759cd Author: Joachim Breitner Date: Wed Aug 2 10:53:37 2017 -0400 Mark `eqString` as `NOINLINE` so that the built-in rule can still match. This will be a problem in general: With loopification, recursive functions can now inline (yay!) but many people out there probably rely on the fact that recursive functions cannot inline (ouch). Hopefully the recent warnings in GHC made them fix this before loopification reaches them. >--------------------------------------------------------------- 32838c6c148072a2864f5fba47f61fe4528759cd libraries/base/GHC/Base.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 052f13f..0ff4589 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -1183,6 +1183,7 @@ eqString :: String -> String -> Bool eqString [] [] = True eqString (c1:cs1) (c2:cs2) = c1 == c2 && cs1 `eqString` cs2 eqString _ _ = False +{-# NOINLINE eqString #-} {-# RULES "eqString" (==) = eqString #-} -- eqString also has a BuiltInRule in PrelRules.hs: From git at git.haskell.org Tue Oct 31 03:34:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Oct 2017 03:34:58 +0000 (UTC) Subject: [commit: ghc] wip/T14068: Implement loopification for local bindings (#14068) (8469ddd) Message-ID: <20171031033458.2DB903A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14068 Link : http://ghc.haskell.org/trac/ghc/changeset/8469ddd712612767a2b6c5cea8c24f7b1e9561ff/ghc >--------------------------------------------------------------- commit 8469ddd712612767a2b6c5cea8c24f7b1e9561ff Author: Joachim Breitner Date: Tue Aug 1 09:47:49 2017 -0400 Implement loopification for local bindings (#14068) This is a relatively prelimary version. I am sure there is a huge number of invariants that this breaks, and conditions that I am not checking etc. I do not even know if the simplifier is the right place to implement this. But it works in this simple case: module T14068 where foo p f k = let bar a = if p a then bar (f a) else a in k bar so we can iterate from here. The IdInfo of a loopified binder stays with the outer binder, e.g. RULES should stay unaffected. The local binder gets localised. During loopification, we zap occurrence info on the lambda binders If we have letrec f x[dead] = … f () … in g f loopification turns that into let f x = joinrec f x[dead] = … f () … in jump j x in g f Note that the parameter x of f is no longer dead! Disable test case for #4030 and #5644 With loopification, T4030 always goes into an infinite loop. Not nice when running the test suite. Also, with loopification, T5644 no longer runs out of heap, so it does not trigger the out-of-heap exception that the test case was testing. Mark `eqString` as `NOINLINE` so that the built-in rule can still match. This will be a problem in general: With loopification, recursive functions can now inline (yay!) but many people out there probably rely on the fact that recursive functions cannot inline (ouch). Hopefully the recent warnings in GHC made them fix this before loopification reaches them. Do not inline showWord mostly because otherwise the test setup of #7014 fails. (The test checks for the absence of certain primops in the code, but inlining showWords adds many of these.) Make the test case for #T5949 a little less bogus by actually using the result of `e`. I *believe* it still tests what we want to test, and now we get proper results with loopification. I am not so worried about the regression in the case of an unused result of `e`. >--------------------------------------------------------------- 8469ddd712612767a2b6c5cea8c24f7b1e9561ff compiler/basicTypes/BasicTypes.hs | 28 +++++++++++++----- compiler/basicTypes/IdInfo.hs | 4 +-- compiler/coreSyn/CoreOpt.hs | 45 ++++++++++++++++++++++++----- compiler/simplCore/OccurAnal.hs | 29 ++++++++++++++++--- compiler/simplCore/Simplify.hs | 28 +++++++++++++++++- compiler/types/Type.hs | 40 +++++++++++++------------ testsuite/tests/concurrent/should_run/all.T | 4 ++- testsuite/tests/perf/should_run/T5949.hs | 2 +- testsuite/tests/rts/T5644/ManyQueue.hs | 0 testsuite/tests/rts/T5644/all.T | 4 ++- 10 files changed, 141 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 8469ddd712612767a2b6c5cea8c24f7b1e9561ff From git at git.haskell.org Tue Oct 31 03:35:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Oct 2017 03:35:02 +0000 (UTC) Subject: [commit: ghc] wip/T14068's head updated: Implement loopification for local bindings (#14068) (8469ddd) Message-ID: <20171031033502.8DDDC3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14068' now includes: c13720c Drop GHC 7.10 compatibility 36fe21a Enable building Cabal with parsec 9df71bf Bump unix submodule 8ef8520 Add .gitmodules entries for text, parsec, mtl submodules d74983e Get the roles right for newtype instances f68a00c Remove unneeded uses of ImplicitParams 884bd21 Add the bootstrapping/ dir to .gitignore 394c391 Add MonadIO Q - by requiring MonadIO => Quasi a81b5b0 Remove the deprecated Typeable{1..7} type synonyms a267580 Don't warn when empty casing on Type 6ea13e9 Add forgotten > in Control.Applicative e8fe12f Fix string escaping in JSON 2f29f19 Convert examples to doctests, and add a handful of new ones 14457cf Fix EmptyCase documentation a4f347c Split out inferConstraintsDataConArgs from inferConstraints 3f05e5f Don't suppress unimplemented type family warnings with DeriveAnyClass 7d69978 Use NonEmpty lists to represent lists of duplicate elements 4f1f986 Change isClosedAlgType to be TYPE-aware, and rename it to pmIsClosedType 0bb1e84 Expand type synonyms during role inference c6462ab Add test for #14101 7c37ffe Point to FunDeps documentation on Haskell wiki ad7b945 Fix #14060 by more conservatively annotating TH-reified types 0a891c8 Properly handle dlerror() message on FreeBSD when linking linker scripts ddb870b Don't drop GHCi-defined functions with -fobject-code enabled ed7a830 Use a ReaderT in TcDeriv to avoid some tedious plumbing 21bd9b2 Recognize FreeBSD compiler as Clang. a520adc Bump mtl, parsec, text submodules 441c52d Add Semigroup/Monoid instances to ST monad b0285d1 Bump nofib submodule e054c5f Bump mtl, parsec, text submodules 6e9c8eb Bump mtl, parsec, text submodules (again) a8da0de Speed up compilation of profiling stubs b0ed07f Allow TcDerivInfer to compile with GHC 8.0.1 38260a9 Fix #13972 by producing tidier errors 039fa1b Suggest how to fix illegally nested foralls in GADT constructor type signatures c948b78 Fix #11785 by making reifyKind = reifyType af9f3fa Remove extra ` from "kind-indexed GADTs" doc 03327bf Handle ListPat in isStrictPattern 36d1b08 Doctest for Void.absurd 49ddea9 Sections with undefined operators have non-standard behavior 43b0c2c Insert missing blank line to fix Applicative doc 63397cb Add some Monoid doctests f762181 Mention the category laws explicitly a30187d Convert documentation examples to doctests for ReadP module bfa9048 Loads of doc(test)s 2c0ab47 Add missing initial version for extension doc. 0e1b6f8 Fix index entries in "separate compilation" section 3385669 user-guide: fix examples of ghci commands 69a0f01 rts: Enable USDT probes object on Linux 82ee71f user-guide: add `:type +d` and `:type +v` in release highlight dc42c0d Fix #13399 by documenting higher-rank kinds. 0385347 Remove unneeded reqlibs for mtl and parsec in the GHC testsuite c5605ae Make function intToSBigNat# preserve sign (fixes #14085) 0286214 testsuite: Add test for #13916 fee253f CSE.cseOneExpr: Set InScopeSet correctly 6257fb5 Comments about GlobalRdrEnv shadowing 118efb0 Restrict Lint's complaints about recursive INLINEs somewhat 698adb5 Tracing in OccAnal (commented out) 4c6fcd7 Comments only 61c4246 Test Trac #14110 f50e30e Doctests for Data.Tuple 6267d8c Enable -Wcpp-undef for GHC and runtime system cf8ab1c users_guide: Convert mkUserGuidePart generation to a Sphinx extension 8e5b6ec Add strict variant of iterate ee2e9ec Correct incorrect free in PE linker 1cdceb9 Revert "Add strict variant of iterate" 34bd43d Fix loading of dlls on 32bit windows 6982ee9 Fix #14125 by normalizing data family instances more aggressively a89bb80 Fix #14114 by checking for duplicate vars on pattern synonym RHSes 79b259a Fix #13885 by freshening reified GADT constructors' universal tyvars 8476097 Revise function arity mismatch errors involving TypeApplications 8fd9599 Make the Read instance for Proxy (and friends) ignore precedence afc2f79 Move validate cleaning from distclean to clean 4717ce8 Fix incorrect retypecheck loop in -j (#14075) 9afaebe StgLint: Allow join point bindings of unlifted type cd5a970 Make law for Foldable.length explicit 20c7053 Bump haddock submodule 090d896 fix typo (expreesions -> expressions) 028645c Fixed a typo in template-haskell documentation dbaa9a2 DynFlags: Add inverse of -dno-debug-output 3625728 Add support for producing position-independent executables 7463a95 users-guide: Better error messages on incomplete ghc-flag directives 74af2e7 Typo fixed 11657c4 Better pretty-printing for CHoleCan a211dca Fix defer-out-of-scope-variables aeb4bd9 Remove typeKind from Type.hs-boot 5f3d2d3 CNF: Implement compaction for small pointer arrays a0b7b10 Restrict exprOkForSpeculation/case to unlifted types 407c11b Bottoming expressions should not be expandable 33452df Refactor the Mighty Simplifier 8649535 Don't do the RhsCtxt thing for join points dd89a13 Comments, plus adjust debug print of TcTyThing(ATyVar) a67b66e Add strict variant of iterate f135fb2 rts: Fix warnings on aarch64 and clean up style 80ccea8 rts: Fix references to Note [BFD import library] 76e59a2 rts: Fix ASSERTs with space before opening paren 8f19c65 Rip out mkUserGuidePart 83484a6 Fix two typos in the ImpredicativeTypes user guide a055f24 Adjust test suite stats 682e8e6 Actually bump T12150 29da01e Make parsed AST dump output lazily 6e0e0b0 Comments only 8834d48 Better debug-printing for Outputable TyConBinder 547e4c0 A bit more -ddump-tc tracing 6f050d9 Add TcRnMonad.unlessXOptM 0257dac Refactor bindHsQTyVars and friends 86e6a5f Small refactoring of meta-tyvar cloning 4455c86 Use a well-kinded substitution to instantiate 8eead4d Improve kind-application-error message a6c448b Small refactor of getRuntimeRep aed7d43 Add HasDebugStack for typeKind 248ad30 testsuite: Add test for #14128 db3a8e1 desugar: Ensure that a module's dep_orphs doesn't contain itself 5266ab9 Remove dll-split. 895a765 Refactor type family instance abstract syntax declarations 3c6b2fc Fix decomposition error on Windows 5f6a820 Add gen-dll as replacement for dll-split f86de44 ghc-pkg: Try opening lockfiles in read-write mode first a27bb1b base: Add support for file unlocking 779b9e6 PackageDb: Explicitly unlock package database before closing 9d57d8c nativeGen: Don't index into linked lists 651b4dc StgLint: Show type of out-of-scope binders a36b34c StgLint: Enforce MultiValAlt liveness invariant only after unariser f17f106 StgLint: Give up on trying to compare types 1561525 HsExpr: Fix typo 6f1ccaa Add a Note describing #14128 567dca6 Add some traceRn and (Outputable StmtTree) 628b666 Add comments to RnTypes fca1962 Define and use HsArg 805b29b Add debugPprType 3790ea9 Small changes to ddump-tc tracing 2c133b6 Really fix Trac #14158 c0feee9 Add missing Semigroup instances to compiler b2c2e3e Add missing Semigroup instances in utils/{hpc,runghc} dd643bc Improve stm haddocks 1f052c5 Fix order of PrelRule 8a1de42 Add testcase for #14178 f089c32 Remove broken citeseer citation links 590e737 Update transformers submodule 6330b0b Document the intricacies of ForallC variable quantification better 5dd6b13 Disallow bang/lazy patterns in the RHSes of implicitly bidirectional patsyns 8e4229a Fix #14167 by using isGadtSyntaxTyCon in more places 0ec4376 Document the Generic(1) laws cb3363e Move NonEmpty definition into GHC.Base 31281a4 testsuite: Fix validation of ways b996e12 testsuite: Add test for #14129 7e5d4a0 Remember the AvailInfo for each IE b9ac9e0 Fix egregious duplication of vars in RnTypes 1300afa get-win32-tarballs: Use bash, not sh a4c2ac2 get-win32-tarballs: Use correct `find` 542f89f Replace hashing function for string keys implementation with xxhash cd857dd SetLevels: Substitute in ticks in lvlMFE 6458b8d base: Update acosh to handle -1::Complex c2881a2 StgLint: Show constructor arity in mismatch message 822abbb eventlog: Clean up profiling heap breakdown type 24e50f9 rts: Add heap breakdown type for -hT 0829821 Implicitly bind kind variables in type family instance RHSes when it's sensible 0cd467b rts: Fix use of #if 2273353 Clean up opt and llc c6726d6 Cleanups, remove commented-out code a04cfcf Update xhtml submodule fee403f Handle W80 in floatFormat d97a6fe Fix typos in diagnostics, testsuite and comments 055d73c Travis: Boot with ghc-8.2.1, and disable test suite 8ae263c Make Semigroup a superclass of Monoid (re #14191) be514a6 includes/rts: Drop trailing comma cb4878f Drop special handling of iOS and Android 011e15a Deal with unbreakable blocks in Applicative Do 22f11f1 Bump T783 expected allocations cf6b4d1 Remove now redundant CPP 122f183 Remove now redundant cabal conditionals in {ghc,template-haskell}.cabal 400ead8 Remove makefile logic for legacy -this-package-key dab0e51 Canonicalise Monoid instances in GHC 346e562 Canonicalise MonoidFail instances in GHC 838a10f Retire cabal_macros_boot.h hack fe35b85 Add testcase for #14186 fe04f37 Allow CSE'ing of work-wrapped bindings (#14186) 0ebc8dc Add a test for #14140 9ff9c35 Check if -XStaticPointers is enabled when renaming static expressions dafa012 Add regression test for #14209 b890e88 rts: Print message before SIGUSR2 backtrace d645e44 DriverMkDepend: Kill redundant import f8e383f Clarify Data.Data documentation 91262e7 Use ar for -staticlib e62391a [RTS] Harden against buffer overflow cbd4911 Make IntPtr and WordPtr as instance of Data.Data typeclass, fix #13115 8ff11c4 Fix @since annotations in GHC.Stats 6139f7f Add non-ASCII isLetter True example 2fe6f6b Option "-ddump-rn-ast" dumps imports and exports too f9bf621 Better document TypeRep patterns 4be195e Simplify Data.Type.Equality.== 4e22220 Clarify seq documentation 4cead3c rts: Add regsterCc(s)List to RTS symbols list 10a1a47 Model divergence of retry# as ThrowsExn, not Diverges 959a623 No need to check ambiguity for visible type args ab2d3d5 More refinements to debugPprType 3a27e34 Fix subtle bug in TcTyClsDecls.mkGADTVars 8bf865d Tidying could cause ill-kinded types 0390e4a Refactor to eliminate FamTyConShape a38acda Refactor tcInferApps 9218ea6 Interim fix for a nasty type-matching bug 9e46167 Remove unused variable binding b6b56dd [RTS] Make -po work 93da9f9 Add test for Trac #14232 3b68687 Test #14038 in dependent/should_compile/T14038 c813d8c Regression test for #12742 b977630 Test #12938 in indexed-types/should_compile/T12938 04bb873 Fix #13407 by suppressing invisibles better. ecb316c nativeGen: A few strictness fixes 58f1f73 Bump primitive submodule 3edbf5c testsuite: Fix dependence on grep behavior in T8129 89c8d4d Fix #13909 by tweaking an error message. e5beb6e Make rejigConRes do kind substitutions fa626f3 Fix #13929 by adding another levity polymorphism check 86e1db7 Test #13938, with expect_broken 8f99cd6 Fix #13963. 7b8827a Bump submodule nofib (Semigroup now required) f043cd5 Fix name of note 4340165 Ignore untracked in text, parsec and mtl submodules [skip ci] 9e227bb Fix missing fields warnings in empty record construction, fix #13870 f4d50a0 Fix #14228 by marking SumPats as non-irrefutable 2bfba9e base: Fix mixed tabs/spaces indentation in inputReady.c 9498c50 Renamer now preserves location for IEThingWith list items 47a9ec7 Remove dead function TcUnify.wrapFunResCoercion b099171 base: Enable TypeInType in Data.Type.Equality 4ec4ca9 base: Add missing MonadFail instance for strict ST 60a3f11 Fix pointer tagging mistake a83f17e base: Fix missing import of Control.Monad.Fail 2258a29 testsuite: Fix MonadFail test output for new ST instance cdaf5f2 [RTS] Add getObjectLoadStatus 120c568 Allow opt+llc from LLVM5 10ca801 Generalise constraint on `instance Monoid (Maybe a)` to Semigroup a2f004b Remove redundant/obsolete CPP usage 1db0f4a Fix unused-given-constraint bug 6252292 rts/RetainerProfile: Adding missing closure types to isRetainer 8b007ab nativeGen: Consistently use blockLbl to generate CLabels from BlockIds 12a92fe OccurAnal: Ensure SourceNotes don't interfere with join-point analysis f63bc73 compiler: introduce custom "GhcPrelude" Prelude 7c7914d Fix Windows build regression due to GhcPrelude change 28a115e base: fdReady(): Improve accuracy and simplify code. c2a1fa7 base: Fix fdReady() potentially running forever on Windows. 826c3b1 base: Fix fdReady() potentially running forever for Windows Char devices. 66240c9 base: Fix fdReady() returning immediately for pipes on Windows. 11c478b rts: Update comment about FreeBSD's unsigned FD_SETSIZE b7f2d12 rts: Fix typo in comment ba4dcc7 base: Make it less likely for fdReady() to fail on Windows sockets. 022455f base: Add more detail to FD_SETSIZE related error message bbb8cb9 users-guide: Mention changes necessary due to #13391 3198956 Factor mkCoreApp and mkCoreApps 7920a7d cmm/CBE: Collapse blocks equivalent up to alpha renaming of local registers 0aba999 Restore function powModSecInteger 11d9615 Make zipWith and zipWith3 inlinable. 02ff705 Add 'stm' package to the global package database d7705f2 aclocal.m4: call cygpath on mingw32 only ced2cb5 Typofixes (visiblity -> visibility) 283eb1a Initial CircleCI support. cc6be3a Typeable: Allow App to match arrow types 9e46d88 Typeable: Generalize kind of represented type 72b00c3 Identify fields by selector when type-checking (fixes #13644) acd346e testsuite: Add testcase for #14253 d86b237 testsuite: Add unboxed sum to T13929 58a7062 base: Add changelog entry for withTypeable generalization 063e0b4 Bump base to 4.11.0.0 1c92083 Also show types that subsume a hole as valid substitutions for that hole. ddb38b5 testsuite: Bump allocations of T12150 9aa7389 cmm/CBE: Use foldLocalRegsDefd feac0a3 Reexport Semigroup's <> operator from Prelude (#14191) 760b9a3 rts: Set unwind information for remaining stack frames a9d417d rts: Set unwind information for catch_frame 1755869 Implement TH addCorePlugin. d7b8da1 Fix broken LLVM code gen 5a8b843 Remove 'stm' from EXTRA_PACKAGES set 2f10438 Fix build with GhcWithInterpreter=NO 65943a3 Bump haskeline submodule c2373b7 Additional LLVM_TARGET logic. d559612 Fix AsmTempLabel d7b260f [Semigroup] fix genapply 9c7d065 Revert "Typeable: Allow App to match arrow types" b3ae47c don't allow AsmTempLabel in UNREG mode (Trac #14264) 3c74a51 Deal with large extra-contraints wildcards 7721e8e Make pprQuotedList use fsep not hsep 3b4833a Comments only 1b476ab Improve type-error reporting abed9bf Fix solving of implicit parameter constraints 0e60cc1 Document how GHC disambiguates between multiple COMPLETE sets 3804a7e Bump template-haskell to 2.13.0.0 2b2595e Ensure text mode when calling debug functions c839c57 Fix the searching of target AR tool abca29f Adds mingw64 to the valid GHC OSs. 6de1a5a Document Typeable's treatment of kind polymorphic tycons d07b8c7 Include original process name in worker thread name (#14153) 9acbeb5 integer-gmp: Fix style d11611f Add NOINLINE pragma to builtinRules 9738e8b Use SIGQUIT for DWARF backtraces instead of SIGUSR2 49c1a20 configure: Catch case where LLVM tools can't be found 65f7d87 configure: Don't hard-code strip tool 2f8e6e7 testsuite: Expect T13168 to be broken on Windows 7446c7f A bunch of typofixes c41ccbf Omit Typeable from the "naturally coherent" list 6e7c09d StgCmmMonad: Remove unnecessary use of unboxed tuples 6246407 primops: Add some notes regarding the meaning of the "type" field 1d1b991 rts: Inform kernel that we won't need reserved address space 57372a7 PrelRules: Handle Int left shifts of more than word-size bits 0ffa396 testsuite: Add test for #14272 f9f1e38 TcInteract: Remove redundant import of Typeable 3ec579d Release console for ghci wrapper 8c23b54 Rules: Show the binder type in the unbound template binder error 7fb89e8 rts: Silence missing __noreturn__ warning 1825cbd Switch VEH to VCH and allow disabling of SEH completely. 8f468fe base: fdReady(): Add note about O_NONBLOCK requirement 018c40f desugar: Catch levity polymorphism in unboxed sum expressions 30a1eee rts: Throw proper HeapOverflow exception on allocating large array 47888fd Revert "Switch VEH to VCH and allow disabling of SEH completely." 1421d87 Switch VEH to VCH and allow disabling of SEH completely. 07ddeaf GHC_LLVM_TARGET: Keep android OS 60b0645 llvm-targets: drop soft-float 4364f1e Typofixes 1e9f90a Move check-ppr and check-api-annotations to testsuite/utils 9bf6310 Add TODO about getMonotonicNSec() wrapping that can no longer happen. dddef31 fdReady(): Fix some C -Wconversion warnings. 03009aa base: fdReady(): Ensure and doc that return values are always -1/0/1 a10729f configure: Make sure we try all possible linkers 5935acd mkDataConRep: fix bug in strictness signature (#14290) 7aa000b Fix #13391 by checking for kind-GADTs 464396d Fix Raspberry Pi target name 9c05fc4 user-guide: Document -Weverything 626f045 Document a law for TH's Lift class effcd56 Don't use "character" in haddocks of Char c15c427 iserv: Don't build vanilla iserv unless vanilla libraries are built e515c7f Allow libffi snapshots e299121 Bump submodule nofib again (Semigroup now required) 00ff023 Travis: Install texinfo 11a59de CircleCI: Install texinfo 0e96812 Pretty-printer missing parens for infix class declaration c0e6c73 Rewrite boot in Python e30d9ca rel-notes: Mention libffi packaging change e462b65 Bump libffi-tarballs submodule d5e60de user-guide: Fix :since: annotation of -pie and add documentation for -fPIE d0c5d8d No libffi docs a4ee289 Adds x86 NONE relocation type a1fc7ce Comments only a8fde18 Fix bug in the short-cut solver b1e0c65 Make GHC.IO.Buffer.summaryBuffer strict dbbee1b Fix nasty bug in w/w for absence analysis cb76754 Suppress error cascade in record fields a02039c Add regression test for #9725 a36eea1 Revert installing texinfo in CI systems 55001c0 Sync base/changelog.md ec9ac20 Add ability to produce crash dumps on Windows 8d64745 Optimize linker by minimizing calls to tryGCC to avoid fork/exec overhead. ef26182 Track the order of user-written tyvars in DataCon fa8035e Implement Div, Mod, and Log for type-level nats. 377d5a2 base: Add missing @since annotations in GHC.TypeNats de1b802 genapply: Explicitly specify arguments f3f624a Include libraries which fill holes as deps when linking. 4899a86 Don't pass HscEnv to functions in the Hsc monad 361af62 base: Remove deprecated Chan combinators 3201d85 user-guide: Mention COMPLETE pragma in release notes 3030eee rts: Print newline after "Stack trace:" on barf 7109fa8 configure: Accept *-msys as a Windows OS in a triple d8d87fa Remove m_type from Match (#14313) 429fafb Add regression test for #14326 f6bca0c Testsuite update following d8d87fa 341d3a7 Incorporate changes from #11721 into Template Haskell f1d2db6 Fix #14320 by looking through HsParTy in more places f337a20 Simply Data instance context for AmbiguousFieldOcc e51e565 Split SysTools up some 7720c29 Tidy up some convoluted "child/parent" code ab1a7583 Typos in comments only 461c831 Minor refactoring c81f66c Fix over-eager error suppression in TcErrors 79ae03a Change "cobox" to "co" in debug output 3e44562 Delete two unused functions f20cf98 Remove wc_insol from WantedConstraints 9c3f731 Fix #10816 by renaming FixitySigs more consistently 6869864 Pretty-printing of derived multi-parameter classes omits parentheses 4bb54a4 Avoid creating dependent types in FloatOut 13fdca3 Add a missing zonk in TcDerivInfer.simplifyDeriv 82b77ec Do not quantify over deriving clauses 15aefb4 Add missing T14325.stderr fb050a3 Do not bind coercion variables in SpecConstr rules 3de788c Re-apply "Typeable: Allow App to match arrow types" 2be55b8 Delete obsolete docs on GADT interacton with TypeApplications 4a677f7 Remove section about ApplicativeDo & existentials (#13875) 8adb84f Fix calculation in threadStackOverflow afac6b1 Fix typo 6aa6a86 Fix typo add85cc Fix panic for `ByteArray#` arguments in CApiFFI foreign imports e3ba26f Implement new `compareByteArrays#` primop 5984a69 Override default `clearBit` method impl for `Natural` 843772b Enable testing 'Natural' type in TEST=arith011 6cc232a Implement {set,clear,complement}BitBigNat primitives 71a4235 configure: Fix CC version check on Apple compilers fd8b044 Levity polymorphic Backpack. 5dab544 FreeBSD dtrace probe support 7e790b3 rts: Label all threads created by the RTS 8536b7f users-guide: Rework and finish debug flag documentation d7f4f41 users guide: Eliminate redundant :category: tags in debugging.rst c5da84d users-guide: Fix various warnings a69fa54 rts/posix: Ensure that memory commit succeeds d6c33da RtClosureInspect: Fix inspecting Char# on 64-bit big-endian 366182a ghci: Include "Rts.h" before using TABLES_NEXT_TO_CODE 9e3add9 Flags.hsc: Peek a CBool (Word8), not a Bool (Int32) aa98268 updateThunk: indirectee can be tagged 21b7057 users-guide: Clarify -ddump-asm-regalloc-stages documentation 6cb4642 Bump ghc-prim to 0.5.2.0 and update changelog ed48d13 Simplify, no functionality change 2f43615 Fix grammaros in comments 317aa96 Improve user’s guide around deriving 74cd1be Don't deeply expand insolubles 5a66d57 Better solving for representational equalities aba7786 Typofix in comment 870020e whitespace only 20ae22b Accept test output for #14350 e023e78 Disable -XRebindableSyntax when running internal GHCi expressions 101a8c7 Error when deriving instances in hs-boot files 8846a7f Fix #14369 by making injectivity warnings finer-grained de8752e Export injectiveVarsOf{Binder,Type} from TyCoRep 7ac22b7 User's guide: Fix the category of some flags 3befc1a Bump arcanist-external-json-linter submodule 1ba2851 Expose monotonic time from GHC.Event.Clock 13758c6 Added a test for 'timeout' to be accurate. 098dc97 Give a reference to Foreign.Concurrent. b6204f7 Untag the potential AP_STACK in stg_getApStackValzh 2ca8cf6 Add Functor Bag instance afc04b2 Outputable: Add pprTraceException c1efc6e Comments and white space 3acd616 Improve kick-out in the constraint solver e375bd3 Update record-wildcard docs 99c61e2 Add stack traces on crashes on Windows bb537b2 nofib submodule: Fix a problem with fasta-c.c 1e24a24 submodule nofib: Add digits-of-e1.faststdout 052ec24 submodule nofib: Add digits-of-e2.faststdout b10a768 Comments only d1eaead Temporary fix to Trac #14380 671b1ed User’s guide: Properly link to RTS flag -V 8843a39 Include usg_file_hash in ghc --show-iface output 3825b7e Remove the 'legroom' part of the timeout-accurate-pure test. b62097d Windows: Bump to GCC 7.2 for GHC 8.4 e888a1f Revert "Windows: Bump to GCC 7.2 for GHC 8.4" 561bdca Update Win32 version for GHC 8.4. f744261 ghc-cabal: Inline removed function from Cabal. 2e16a57 Revert "ghc-cabal: Inline removed function ..." b1ad0bb Revert "Update Win32 version for GHC 8.4." 61f1b46 Make language extensions their own category in the documentation bf83435 typecheck: Clarify errors mentioned in #14385 bd53b48 Add info about Github pull requests. 2a4c24e Make layLeft and reduceDoc stricter (#7258) 980e127 Windows: Update the mirror script to generate hashes and use mirror fallback 1c15d8e Fix space leak in BinIface.getSymbolTable df63668 Performance improvements linear regAlloc (#7258) f7f270e Implement `-Wpartial-fields` warning (#7169) 821adee Fix a bug in 'alexInputPrevChar' 2c23fff user-guide: Clarify default optimization flags 4c06ccb base: Enable listToMaybe to fuse via foldr/build dbd81f7 Factor out readField (#14364) d91a6b6 Declare upstram repo location for hsc2hs 160a491 users-guide: Disable index node generation 9ae24bb configure: Add Alpine Linux to checkVendor a10c2e6 Don't use $SHELL in wrapper scripts 355318c Add more pprTrace to SpecConstr (debug only) 7d7d94f Fix an exponential-blowup case in SpecConstr 41f9055 ApplicativeDo: handle BodyStmt (#12143) acd355a relnotes: Fix a few minor formatting issues faf60e8 Make tagForCon non-linear 922db3d Manual: The -ddump-cmm-* flags had a wrong spelling in the manual 97ca0d2 simplNonRecJoinPoint: Handle Shadowing correctly 0e953da Implement a dedicated exitfication pass #14152 3b784d4 base: Implement file locking in terms of POSIX locks cecd2f2 Add -falignment-sanitization flag 7673561 Turn `compareByteArrays#` out-of-line primop into inline primop 85aa1f4 Fix #14390 by making toIfaceTyCon aware of equality cca2d6b Allow packing constructor fields 82bad1a A bit more tc-tracing 1b115b1 Fix typo in accessor name ec356e8 Typofix in panic 1569668 Typofixes in comments 53700a9 minor wordsmithing 201b5aa Catch a few more typos in comments 609f284 Add Note [Setting the right in-scope set] af0aea9 core-spec: Add join points to formalism a95a849 Do not inline showWord 32838c6 Mark `eqString` as `NOINLINE` 8469ddd Implement loopification for local bindings (#14068) From git at git.haskell.org Tue Oct 31 08:23:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Oct 2017 08:23:52 +0000 (UTC) Subject: [commit: ghc] wip/float-join-points: Wip on floating join points (07a86e6) Message-ID: <20171031082352.91BBA3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/float-join-points Link : http://ghc.haskell.org/trac/ghc/changeset/07a86e63971cda3f997c1d858e5503cdca817752/ghc >--------------------------------------------------------------- commit 07a86e63971cda3f997c1d858e5503cdca817752 Author: Simon Peyton Jones Date: Fri Oct 27 16:20:24 2017 +0100 Wip on floating join points >--------------------------------------------------------------- 07a86e63971cda3f997c1d858e5503cdca817752 compiler/basicTypes/BasicTypes.hs | 5 +- compiler/basicTypes/Id.hs | 19 ++++- compiler/coreSyn/CoreFVs.hs | 30 ++++---- compiler/main/DynFlags.hs | 3 + compiler/simplCore/CoreMonad.hs | 17 +++-- compiler/simplCore/SetLevels.hs | 17 ++--- compiler/simplCore/SimplCore.hs | 16 ++-- compiler/simplCore/SimplEnv.hs | 45 ++++++++++-- compiler/simplCore/SimplUtils.hs | 150 +++++++++++++++++++++++--------------- compiler/simplCore/Simplify.hs | 96 +++++++++++++++++------- compiler/types/TyCoRep.hs | 23 +++--- compiler/types/Type.hs | 8 +- 12 files changed, 281 insertions(+), 148 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 07a86e63971cda3f997c1d858e5503cdca817752 From git at git.haskell.org Tue Oct 31 08:23:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Oct 2017 08:23:55 +0000 (UTC) Subject: [commit: ghc] wip/float-join-points's head updated: Wip on floating join points (07a86e6) Message-ID: <20171031082355.397523A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/float-join-points' now includes: 2be55b8 Delete obsolete docs on GADT interacton with TypeApplications 4a677f7 Remove section about ApplicativeDo & existentials (#13875) 8adb84f Fix calculation in threadStackOverflow afac6b1 Fix typo 6aa6a86 Fix typo add85cc Fix panic for `ByteArray#` arguments in CApiFFI foreign imports e3ba26f Implement new `compareByteArrays#` primop 5984a69 Override default `clearBit` method impl for `Natural` 843772b Enable testing 'Natural' type in TEST=arith011 6cc232a Implement {set,clear,complement}BitBigNat primitives 71a4235 configure: Fix CC version check on Apple compilers fd8b044 Levity polymorphic Backpack. 5dab544 FreeBSD dtrace probe support 7e790b3 rts: Label all threads created by the RTS 8536b7f users-guide: Rework and finish debug flag documentation d7f4f41 users guide: Eliminate redundant :category: tags in debugging.rst c5da84d users-guide: Fix various warnings a69fa54 rts/posix: Ensure that memory commit succeeds d6c33da RtClosureInspect: Fix inspecting Char# on 64-bit big-endian 366182a ghci: Include "Rts.h" before using TABLES_NEXT_TO_CODE 9e3add9 Flags.hsc: Peek a CBool (Word8), not a Bool (Int32) aa98268 updateThunk: indirectee can be tagged 21b7057 users-guide: Clarify -ddump-asm-regalloc-stages documentation 6cb4642 Bump ghc-prim to 0.5.2.0 and update changelog ed48d13 Simplify, no functionality change 2f43615 Fix grammaros in comments 317aa96 Improve user’s guide around deriving 74cd1be Don't deeply expand insolubles 5a66d57 Better solving for representational equalities aba7786 Typofix in comment 870020e whitespace only 20ae22b Accept test output for #14350 e023e78 Disable -XRebindableSyntax when running internal GHCi expressions 101a8c7 Error when deriving instances in hs-boot files 8846a7f Fix #14369 by making injectivity warnings finer-grained de8752e Export injectiveVarsOf{Binder,Type} from TyCoRep 7ac22b7 User's guide: Fix the category of some flags 3befc1a Bump arcanist-external-json-linter submodule 1ba2851 Expose monotonic time from GHC.Event.Clock 13758c6 Added a test for 'timeout' to be accurate. 098dc97 Give a reference to Foreign.Concurrent. b6204f7 Untag the potential AP_STACK in stg_getApStackValzh 2ca8cf6 Add Functor Bag instance afc04b2 Outputable: Add pprTraceException c1efc6e Comments and white space 3acd616 Improve kick-out in the constraint solver e375bd3 Update record-wildcard docs 99c61e2 Add stack traces on crashes on Windows bb537b2 nofib submodule: Fix a problem with fasta-c.c 1e24a24 submodule nofib: Add digits-of-e1.faststdout 052ec24 submodule nofib: Add digits-of-e2.faststdout b10a768 Comments only d1eaead Temporary fix to Trac #14380 671b1ed User’s guide: Properly link to RTS flag -V 8843a39 Include usg_file_hash in ghc --show-iface output 3825b7e Remove the 'legroom' part of the timeout-accurate-pure test. b62097d Windows: Bump to GCC 7.2 for GHC 8.4 e888a1f Revert "Windows: Bump to GCC 7.2 for GHC 8.4" 561bdca Update Win32 version for GHC 8.4. f744261 ghc-cabal: Inline removed function from Cabal. 2e16a57 Revert "ghc-cabal: Inline removed function ..." b1ad0bb Revert "Update Win32 version for GHC 8.4." 61f1b46 Make language extensions their own category in the documentation bf83435 typecheck: Clarify errors mentioned in #14385 bd53b48 Add info about Github pull requests. 2a4c24e Make layLeft and reduceDoc stricter (#7258) 980e127 Windows: Update the mirror script to generate hashes and use mirror fallback 1c15d8e Fix space leak in BinIface.getSymbolTable df63668 Performance improvements linear regAlloc (#7258) f7f270e Implement `-Wpartial-fields` warning (#7169) 821adee Fix a bug in 'alexInputPrevChar' 2c23fff user-guide: Clarify default optimization flags 4c06ccb base: Enable listToMaybe to fuse via foldr/build dbd81f7 Factor out readField (#14364) d91a6b6 Declare upstram repo location for hsc2hs 160a491 users-guide: Disable index node generation 9ae24bb configure: Add Alpine Linux to checkVendor a10c2e6 Don't use $SHELL in wrapper scripts 355318c Add more pprTrace to SpecConstr (debug only) 7d7d94f Fix an exponential-blowup case in SpecConstr 41f9055 ApplicativeDo: handle BodyStmt (#12143) acd355a relnotes: Fix a few minor formatting issues faf60e8 Make tagForCon non-linear 922db3d Manual: The -ddump-cmm-* flags had a wrong spelling in the manual 97ca0d2 simplNonRecJoinPoint: Handle Shadowing correctly 0e953da Implement a dedicated exitfication pass #14152 3b784d4 base: Implement file locking in terms of POSIX locks cecd2f2 Add -falignment-sanitization flag 7673561 Turn `compareByteArrays#` out-of-line primop into inline primop 85aa1f4 Fix #14390 by making toIfaceTyCon aware of equality cca2d6b Allow packing constructor fields 82bad1a A bit more tc-tracing 1b115b1 Fix typo in accessor name ec356e8 Typofix in panic 1569668 Typofixes in comments 53700a9 minor wordsmithing 201b5aa Catch a few more typos in comments 609f284 Add Note [Setting the right in-scope set] af0aea9 core-spec: Add join points to formalism 07a86e6 Wip on floating join points From git at git.haskell.org Tue Oct 31 12:13:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Oct 2017 12:13:27 +0000 (UTC) Subject: [commit: ghc] master: Tidy up IfaceEqualityTyCon (29ae833) Message-ID: <20171031121327.F2D4E3A5EA@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/29ae83374647e227d76acd896b89590fc15590d6/ghc >--------------------------------------------------------------- commit 29ae83374647e227d76acd896b89590fc15590d6 Author: Simon Peyton Jones Date: Tue Oct 31 11:01:17 2017 +0000 Tidy up IfaceEqualityTyCon This commit commit 85aa1f4253163985fe07d172f8da73b784bb7b4b Date: Sun Oct 29 20:48:19 2017 -0400 Fix #14390 by making toIfaceTyCon aware of equality was a bit over-complicated. This patch simplifies the (horribly ad-hoc) treatement of IfaceEqualityTyCon, and documents it better. No visible change in behaviour. >--------------------------------------------------------------- 29ae83374647e227d76acd896b89590fc15590d6 compiler/iface/IfaceType.hs | 71 +++++++++++++++++++++++++-------------------- compiler/iface/ToIface.hs | 18 +++--------- 2 files changed, 44 insertions(+), 45 deletions(-) diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index c287d56..41120da 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -186,10 +186,12 @@ data IfaceTyConSort = IfaceNormalTyCon -- ^ a regular tycon | IfaceSumTyCon !Arity -- ^ e.g. @(a | b | c)@ - | IfaceEqualityTyCon !Bool - -- ^ a type equality. 'True' indicates kind-homogeneous. - -- See Note [Equality predicates in IfaceType] for - -- details. + | IfaceEqualityTyCon + -- ^ A heterogeneous equality TyCon + -- (i.e. eqPrimTyCon, eqReprPrimTyCon, heqTyCon) + -- that is actually being applied to two types + -- of the same kind. This affects pretty-printing + -- only: see Note [Equality predicates in IfaceType] deriving (Eq) {- Note [Free tyvars in IfaceType] @@ -216,24 +218,27 @@ We do the same for covars, naturally. Note [Equality predicates in IfaceType] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ GHC has several varieties of type equality (see Note [The equality types story] -in TysPrim for details) which all must be rendered with different surface syntax -during pretty-printing. Which syntax we use depends upon, - - 1. Which predicate tycon was used - 2. Whether the types being compared are of the same kind. - -Unfortunately, determining (2) from an IfaceType isn't possible since we can't -see through type synonyms. Consequently, we need to record whether the equality -is homogeneous or not in IfaceTyConSort for the purposes of pretty-printing. - -Namely we handle these cases, - - Predicate Homogeneous Heterogeneous - ---------------- ----------- ------------- - eqTyCon ~ N/A - heqTyCon ~ ~~ - eqPrimTyCon ~# ~~ - eqReprPrimTyCon Coercible Coercible +in TysPrim for details). In an effort to avoid confusing users, we suppress +the differences during "normal" pretty printing. Specifically we display them +like this: + + Predicate Pretty-printed as + Homogeneous case Heterogeneous case + ---------------- ----------------- ------------------- + (~) eqTyCon ~ N/A + (~~) heqTyCon ~ ~~ + (~#) eqPrimTyCon ~# ~~ + (~R#) eqReprPrimTyCon Coercible Coercible + +By "homogeneeous case" we mean cases where a hetero-kinded equality +(all but the first above) is actually applied to two identical kinds. +Unfortunately, determining this from an IfaceType isn't possible since +we can't see through type synonyms. Consequently, we need to record +whether this particular application is homogeneous in IfaceTyConSort +for the purposes of pretty-printing. + +All this suppresses information. To get the ground truth, use -dppr-debug +(see 'print_eqs' in 'ppr_equality'). See Note [The equality types story] in TysPrim. -} @@ -919,6 +924,11 @@ pprTyTcApp' ctxt_prec tc tys dflags style tys_wo_kinds = tcArgsIfaceTypes $ stripInvisArgs dflags tys -- | Pretty-print a type-level equality. +-- Returns (Just doc) if the argument is a /saturated/ application +-- of eqTyCon (~) +-- eqPrimTyCon (~#) +-- eqReprPrimTyCon (~R#) +-- hEqTyCon (~~) -- -- See Note [Equality predicates in IfaceType] -- and Note [The equality types story] in TysPrim @@ -936,8 +946,11 @@ ppr_equality ctxt_prec tc args = Nothing where homogeneous = case ifaceTyConSort $ ifaceTyConInfo tc of - IfaceEqualityTyCon hom -> hom - _other -> pprPanic "ppr_equality: homogeneity" (ppr tc) + IfaceEqualityTyCon -> True + _other -> False + -- True <=> a heterogeneous equality whose arguments + -- are (in this case) of the same kind + tc_name = ifaceTyConName tc pp = ppr_ty hom_eq_tc = tc_name `hasKey` eqTyConKey -- (~) @@ -950,7 +963,7 @@ ppr_equality ctxt_prec tc args print_equality' args style dflags print_equality' (ki1, ki2, ty1, ty2) style dflags - | print_eqs + | print_eqs -- No magic, just print the original TyCon = ppr_infix_eq (ppr tc) | hetero_eq_tc @@ -1154,9 +1167,7 @@ instance Binary IfaceTyConSort where put_ bh IfaceNormalTyCon = putByte bh 0 put_ bh (IfaceTupleTyCon arity sort) = putByte bh 1 >> put_ bh arity >> put_ bh sort put_ bh (IfaceSumTyCon arity) = putByte bh 2 >> put_ bh arity - put_ bh (IfaceEqualityTyCon hom) - | hom = putByte bh 3 - | otherwise = putByte bh 4 + put_ bh IfaceEqualityTyCon = putByte bh 3 get bh = do n <- getByte bh @@ -1164,9 +1175,7 @@ instance Binary IfaceTyConSort where 0 -> return IfaceNormalTyCon 1 -> IfaceTupleTyCon <$> get bh <*> get bh 2 -> IfaceSumTyCon <$> get bh - 3 -> return $ IfaceEqualityTyCon True - 4 -> return $ IfaceEqualityTyCon False - _ -> fail "Binary(IfaceTyConSort): fail" + _ -> return IfaceEqualityTyCon instance Binary IfaceTyConInfo where put_ bh (IfaceTyConInfo i s) = put_ bh i >> put_ bh s diff --git a/compiler/iface/ToIface.hs b/compiler/iface/ToIface.hs index 6f71af5..e28abdf 100644 --- a/compiler/iface/ToIface.hs +++ b/compiler/iface/ToIface.hs @@ -139,15 +139,11 @@ toIfaceTypeX fr (TyConApp tc tys) , n_tys == 2*arity = IfaceTupleTy BoxedTuple IsPromoted (toIfaceTcArgsX fr tc (drop arity tys)) - -- type equalities: see Note [Equality predicates in IfaceType] - | tyConName tc == eqTyConName - = let info = IfaceTyConInfo IsNotPromoted (IfaceEqualityTyCon True) - in IfaceTyConApp (IfaceTyCon (tyConName tc) info) (toIfaceTcArgsX fr tc tys) - | tc `elem` [ eqPrimTyCon, eqReprPrimTyCon, heqTyCon ] - , [k1, k2, _t1, _t2] <- tys - = let homogeneous = k1 `eqType` k2 - info = IfaceTyConInfo IsNotPromoted (IfaceEqualityTyCon homogeneous) + , (k1:k2:_) <- tys + = let info = IfaceTyConInfo IsNotPromoted sort + sort | k1 `eqType` k2 = IfaceEqualityTyCon + | otherwise = IfaceNormalTyCon in IfaceTyConApp (IfaceTyCon (tyConName tc) info) (toIfaceTcArgsX fr tc tys) -- other applications @@ -195,12 +191,6 @@ toIfaceTyCon tc | isUnboxedSumTyCon tc , Just cons <- isDataSumTyCon_maybe tc = IfaceSumTyCon (length cons) - | tyConName tc == eqTyConName || tc == eqPrimTyCon - = IfaceEqualityTyCon True - - | tc `elem` [heqTyCon, eqReprPrimTyCon] - = IfaceEqualityTyCon False - | otherwise = IfaceNormalTyCon